New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
Changeset 593 – NEMO

Changeset 593


Ignore:
Timestamp:
2007-02-09T10:40:34+01:00 (17 years ago)
Author:
opalod
Message:

nemo_v2_update_001 : CT : - add non linear free surface (variable volume) with new cpp key key_vvl

Location:
trunk/NEMO/OPA_SRC
Files:
6 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/OPA_SRC/eosbn2.F90

    r474 r593  
    3636   PUBLIC eos        ! called by step.F90, inidtr.F90, tranpc.F90 and intgrd.F90 
    3737   PUBLIC bn2        ! called by step.F90 
     38   PUBLIC eos_init   ! called by step.F90 
    3839 
    3940   !! * Share module variables 
  • trunk/NEMO/OPA_SRC/istate.F90

    r558 r593  
    3939   USE zpshde          ! partial step: hor. derivative (zps_hde routine) 
    4040   USE eosbn2          ! equation of state            (eos bn2 routine) 
     41   USE domvvl          ! varying vertical mesh 
     42   USE dynspg_oce      ! pressure gradient schemes 
     43   USE dynspg_flt      ! pressure gradient schemes 
     44   USE dynspg_exp      ! pressure gradient schemes 
     45   USE dynspg_ts       ! pressure gradient schemes 
    4146    
    4247   IMPLICIT NONE 
     
    8388         !                                       ! Initialization of ocean to zero 
    8489         !     before fields       !       now fields           
    85          ;   ub   (:,:,:) = 0.e0   ;   un   (:,:,:) = 0.e0    
    86          ;   vb   (:,:,:) = 0.e0   ;   vn   (:,:,:) = 0.e0     
    87          ;   rotb (:,:,:) = 0.e0   ;   rotn (:,:,:) = 0.e0   
    88          ;   hdivb(:,:,:) = 0.e0   ;   hdivn(:,:,:) = 0.e0   
     90         ;   ub   (:,:,:) = 0.e0   ;   un   (:,:,:) = 0.e0   ; sshb(:,:) = 0.e0 
     91         ;   vb   (:,:,:) = 0.e0   ;   vn   (:,:,:) = 0.e0   ; sshn(:,:) = 0.e0 
     92         ;   rotb (:,:,:) = 0.e0   ;   rotn (:,:,:) = 0.e0 
     93         ;   hdivb(:,:,:) = 0.e0   ;   hdivn(:,:,:) = 0.e0 
    8994         ! 
    9095         IF( cp_cfg == 'eel' ) THEN 
     
    126131      ENDIF 
    127132 
     133      IF( lk_vvl ) THEN 
     134         ! read free surface arrays in restart file 
     135         IF( ln_rstart ) THEN 
     136            IF( lk_dynspg_flt )   CALL flt_rst( nit000, 'READ' )      ! read or initialize the following fields 
     137            !                                                         ! gcx, gcxb, sshb, sshn 
     138            IF( lk_dynspg_ts  )   CALL ts_rst ( nit000, 'READ' )      ! read or initialize the following fields 
     139            !                                                         ! sshb, sshn, sshb_b, sshn_b, un_b, vn_b 
     140            IF( lk_dynspg_exp )   CALL exp_rst( nit000, 'READ' )      ! read or initialize the following fields 
     141            !                                                         ! sshb, sshn 
     142         ENDIF 
     143         ! 
     144         IF( .NOT. lk_dynspg_flt ) sshbb(:,:) = sshb(:,:) 
     145         ! 
     146         CALL dom_vvl               ! ssh init and vertical grid update 
     147 
     148         CALL eos_init              ! usefull to get the equation state type neos parameter 
     149 
     150         CALL bn2( tb, sb, rn2 )    ! before Brunt Vaissala frequency 
     151 
     152         IF( .NOT. ln_rstart ) CALL wzv( nit000 )  
     153 
     154      ENDIF 
    128155 
    129156      !                                       ! Vertical velocity 
    130157      !                                       ! ----------------- 
    131       CALL wzv( nit000 )                         ! from horizontal divergence 
     158 
     159      IF( .NOT. lk_vvl )    CALL wzv( nit000 )                         ! from horizontal divergence 
    132160      ! 
    133161   END SUBROUTINE istate_init 
     
    213241      INTEGER  ::   ijloc 
    214242      REAL(wp) ::   zh1, zh2, zslope, zcst, zfcor   ! temporary scalars 
    215       REAL(wp) ::   zt1  = 12._wp,               &  ! surface temperature value (EEL R5) 
    216          &          zt2  =  2._wp,               &  ! bottom  temperature value (EEL R5) 
    217          &          zsal = 35.5_wp,              &  ! constant salinity (EEL R2, R5 and R6) 
     243      REAL(wp) ::   zt1  = 15._wp,               &  ! surface temperature value (EEL R5) 
     244         &          zt2  =  5._wp,               &  ! bottom  temperature value (EEL R5) 
     245         &          zsal = 35.0_wp,              &  ! constant salinity (EEL R2, R5 and R6) 
    218246         &          zueel = 0.1_wp                  ! constant uniform zonal velocity (EEL R5) 
    219247# if ! defined key_dynspg_rl 
     
    240268 
    241269            DO jk = 1, jpk 
    242                tn(:,:,jk) = ( zslope * fsdept(:,:,jk) + zcst ) * tmask(:,:,jk) 
     270               tn(:,:,jk) = ( zt2 + zt1 * exp( - fsdept(:,:,jk) / 1000 ) ) * tmask(:,:,jk) 
    243271               tb(:,:,jk) = tn(:,:,jk) 
    244272            END DO 
     
    291319            sshn(:,:) = sshb(:,:)                   ! set now ssh to the before value 
    292320 
    293             IF( nn_rstssh /= 1 ) THEN   
    294                nn_rstssh = 1                           ! hand-made initilization of ssh  
    295                CALL ctl_warn( 'istate_eel: force nn_rstssh = 1' ) 
     321            IF( nn_rstssh /= 0 ) THEN   
     322               nn_rstssh = 0                           ! hand-made initilization of ssh  
     323               CALL ctl_warn( 'istate_eel: force nn_rstssh = 0' ) 
    296324            ENDIF 
    297325 
  • trunk/NEMO/OPA_SRC/oce.F90

    r544 r593  
    6161   !! ------------ 
    6262   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   &   !: 
    63       sshb, sshn             !: before, now sea surface height (meters) 
     63      sshb , sshn ,        &  !: before, now sea surface height (meters) 
     64      sshu , sshv ,        &  !: sea surface height at u- and v- point 
     65      sshbb, ssha             !: before before sea surface height at t-point 
    6466 
    6567#if defined key_dynspg_rl   ||   defined key_esopa 
  • trunk/NEMO/OPA_SRC/par_EEL_R5.h90

    r443 r593  
    2222 
    2323      ! data size              !!! * size of all the input files 
    24       jpidta  = 202   ,      &  !: first horizontal dimension > or = to jpi 
    25       jpjdta  = 104   ,      &  !: second                     > or = to jpj 
    26       jpkdta  =  40   ,      &  !: number of levels           > or = to jpk 
     24      jpidta  =  66   ,      &  !: first horizontal dimension > or = to jpi 
     25      jpjdta  =  66   ,      &  !: second                     > or = to jpj 
     26      jpkdta  =  31   ,      &  !: number of levels           > or = to jpk 
    2727 
    2828      ! total domain size      !!! * full domain * 
     
    3535 
    3636      ! Domain characteristics 
    37       jperio  =   0   ,      &  !: lateral cond. type (between 0 and 6) 
     37      jperio  =   1   ,      &  !: lateral cond. type (between 0 and 6) 
    3838      jpisl   =   1   ,      &  !: number of islands 
    3939      jpnisl  = jpiglo          !: maximum number of points per island 
     
    6767      ::     &  !: 
    6868      ppglam0  =    0.0_wp,   &  !: longitude of first raw and column T-point (jphgr_msh = 1) 
    69       ppgphi0  =   35.0_wp,   &  !: latitude  of first raw and column T-point (jphgr_msh = 1) 
     69      ppgphi0  = 43.436430714_wp,   &  !: latitude  of first raw and column T-point (jphgr_msh = 1) 
    7070      !                          ! latitude for the Coriolis or Beta parameter (jphgr_msh = 2 or 3) 
    7171      ppe1_deg = pp_not_used,   &  !: zonal      grid-spacing (degrees) 
    7272      ppe2_deg = pp_not_used,   &  !: meridional grid-spacing (degrees) 
    7373      ! 
    74       ppe1_m   = 5000.0_wp,   &  !: zonal      grid-spacing (meters) 
    75       ppe2_m   = 5000.0_wp       !: meridional grid-spacing (meters) 
     74      ppe1_m   = 8000.0_wp,   &  !: zonal      grid-spacing (meters) 
     75      ppe2_m   = 8000.0_wp       !: meridional grid-spacing (meters) 
    7676   !! 
    7777   !!  Coefficients associated with the vertical coordinate system 
    7878   !! 
    7979   REAL(wp), PARAMETER  ::       &   !: 
    80       &     ppsur = pp_to_be_computed       ,  &  !: Computed in domzgr, set ppdzmin, pphmax below 
    81       &     ppa0  = pp_to_be_computed       ,  &  !: 
    82       &     ppa1  = pp_to_be_computed       ,  &  !: 
     80      &     ppsur = -4762.96143546300_wp    ,  &  !: Computed in domzgr, set ppdzmin, pphmax below 
     81      &     ppa0  =   255.58049070440_wp    ,  &  !: 
     82      &     ppa1  =   245.58132232490_wp    ,  &  !: 
    8383      ! 
    84       &     ppkth = 20._wp                  ,  &  !: (non dimensional): gives the approximate 
     84      &     ppkth =    21.43336197938_wp    ,  &  !: (non dimensional): gives the approximate 
    8585      !                                           !: layer number above which  stretching will 
    8686      !                                           !: be maximum. Usually of order jpk/2. 
    87       &     ppacr = 16.00000000000_wp             !: (non dimensional): stretching factor 
     87      &     ppacr =     3.00000000000_wp          !: (non dimensional): stretching factor 
    8888      !                                           !: for the grid. The highest zacr, the smallest 
    8989      !                                           !: the stretching. 
     
    9494   !! 
    9595   REAL(wp), PARAMETER ::        &  !: 
    96       &     ppdzmin = 120._wp               ,  &  !: (meters) vertical thickness of the top layer 
    97       &     pphmax  = 4000._wp                    !: (meters) Maximum depth of the ocean gdepw(jpk) 
     96      &     ppdzmin = pp_not_used           ,  &  !: (meters) vertical thickness of the top layer 
     97      &     pphmax  = pp_not_used                 !: (meters) Maximum depth of the ocean gdepw(jpk) 
    9898   !!--------------------------------------------------------------------- 
  • trunk/NEMO/OPA_SRC/restart.F90

    r579 r593  
    127127      CALL iom_rstput( kt, nitrst, numrow, 'un'     , un      ) 
    128128      CALL iom_rstput( kt, nitrst, numrow, 'vn'     , vn      ) 
     129      IF( lk_vvl ) CALL iom_rstput( kt, nitrst, numrow, 'wn'     , wn      ) 
    129130      CALL iom_rstput( kt, nitrst, numrow, 'tn'     , tn      ) 
    130131      CALL iom_rstput( kt, nitrst, numrow, 'sn'     , sn      ) 
     
    147148#endif 
    148149 
    149       IF( nn_dynhpg_rst == 1 ) THEN 
     150      IF( nn_dynhpg_rst == 1 .OR. lk_vvl ) THEN 
    150151         CALL iom_rstput( kt, nitrst, numrow, 'rhd' , rhd  ) 
    151152         CALL iom_rstput( kt, nitrst, numrow, 'rhop', rhop ) 
     
    271272      CALL iom_get( numror, jpdom_local, 'un'   , un    )        ! now    i-component velocity 
    272273      CALL iom_get( numror, jpdom_local, 'vn'   , vn    )        ! now    j-component velocity 
     274      IF( lk_vvl ) CALL iom_get( numror, jpdom_local, 'wn'   , wn    )        ! now    k-component velocity 
    273275      CALL iom_get( numror, jpdom_local, 'tn'   , tn    )        ! now    temperature 
    274276      CALL iom_get( numror, jpdom_local, 'sn'   , sn    )        ! now    salinity 
  • trunk/NEMO/OPA_SRC/step.F90

    r521 r593  
    119119   USE cpl             ! exchanges in coupled mode        (cpl_stp routine) 
    120120   USE prtctl          ! Print control                    (prt_ctl routine) 
     121   USE domvvl          ! variable volume                  (dom_vvl routine) 
    121122 
    122123#if defined key_agrif 
     
    385386                               CALL dyn_nxt( kstp )           ! lateral velocity at next time step 
    386387 
     388      IF( lk_vvl )             CALL dom_vvl                   ! vertical mesh at next time step 
     389 
    387390 
    388391      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
Note: See TracChangeset for help on using the changeset viewer.