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 6422 for branches/2016/dev_r6409_SIMPLIF_2_usrdef/NEMOGCM – NEMO

Ignore:
Timestamp:
2016-04-04T12:44:41+02:00 (8 years ago)
Author:
flavoni
Message:

first attempt: introduction of usr_def module for horizontal domain GYRE exemple, see ticket #1692

Location:
branches/2016/dev_r6409_SIMPLIF_2_usrdef/NEMOGCM
Files:
1 added
5 edited

Legend:

Unmodified
Added
Removed
  • branches/2016/dev_r6409_SIMPLIF_2_usrdef/NEMOGCM/CONFIG/GYRE/EXP00/namelist_cfg

    r6140 r6422  
    1818&namcfg     !   parameters of the configuration    
    1919!----------------------------------------------------------------------- 
     20   ln_read_cfg = .false.   !  flag to read (.true.) configuration definition files (coordinates, 
    2021   cp_cfg      =  "gyre"                 !  name of the configuration 
    2122   jp_cfg      =       1                 !  resolution of the configuration 
     
    4546   rn_rdt      = 7200.     !  time step for the dynamics  
    4647   jphgr_msh   =       5                 !  type of horizontal mesh 
     48   nn_msh      =    1      !  create (=1) a mesh file or not (=0) 
    4749   ppglam0     =       0.0               !  longitude of first raw and column T-point (jphgr_msh = 1) 
    4850   ppgphi0     =      29.0               ! latitude  of first raw and column T-point (jphgr_msh = 1) 
  • branches/2016/dev_r6409_SIMPLIF_2_usrdef/NEMOGCM/CONFIG/SHARED/namelist_ref

    r6152 r6422  
    7272&namcfg        !   parameters of the configuration 
    7373!----------------------------------------------------------------------- 
     74   ln_read_cfg = .false.   !  flag to read (.true.) configuration definition files (coordinates, 
     75                           !  bathymetry, boudary condition, initial state, sbc) or (.false.) to call user_defined.F90 module 
    7476   cp_cfg      = "default" !  name of the configuration 
    7577   cp_cfz      = "no zoom" !  name of the zoom of configuration 
     
    131133   rn_bathy    =    0.     !  value of the bathymetry. if (=0) bottom flat at jpkm1 
    132134   nn_closea   =    0      !  remove (=0) or keep (=1) closed seas and lakes (ORCA) 
    133    nn_msh      =    1      !  create (=1) a mesh file or not (=0) 
     135   nn_msh      =    0      !  create (=1) a mesh file or not (=0) 
    134136   rn_hmin     =   -3.     !  min depth of the ocean (>0) or min number of ocean level (<0) 
    135137   rn_isfhmin  =    1.00   !  treshold (m) to discriminate grounding ice to floating ice 
  • branches/2016/dev_r6409_SIMPLIF_2_usrdef/NEMOGCM/NEMO/OPA_SRC/DOM/domhgr.F90

    r6140 r6422  
    1616   !!            3.7  ! 2015-09  (G. Madec, S. Flavoni) add cell surface and their inverse 
    1717   !!                                       add optional read of e1e2u & e1e2v 
     18   !!             -   ! 2016-04  (S. Flavoni) change configuration's interface: 
     19   !!                            read file or CALL usr_def module to compute  
     20   !!                            horizontal grid (example given for GYRE) 
    1821   !!---------------------------------------------------------------------- 
    1922 
     
    2326   !!---------------------------------------------------------------------- 
    2427   USE dom_oce        ! ocean space and time domain 
     28   USE par_oce        ! ocean space and time domain 
    2529   USE phycst         ! physical constants 
    2630   USE domwri         ! write 'meshmask.nc' & 'coordinate_e1e2u_v.nc' files 
     
    2933   USE lib_mpp        ! MPP library 
    3034   USE timing         ! Timing 
     35   USE usrdef        ! User defined routine 
    3136 
    3237   IMPLICIT NONE 
    3338   PRIVATE 
    3439 
    35    REAL(wp) ::   glam0, gphi0   ! variables corresponding to parameters ppglam0 ppgphi0 set in par_oce 
     40   REAL(wp) ::   glam0, gphi0   ! variables corresponding to parameters ppglam0 ppgphi0 set in namelist !SF modify some routines???? 
    3641 
    3742   PUBLIC   dom_hgr   ! called by domain.F90 
     
    99104      !!                Madec, Imbard, 1996, Clim. Dyn. 
    100105      !!---------------------------------------------------------------------- 
    101       INTEGER  ::   ji, jj               ! dummy loop indices 
    102       INTEGER  ::   ii0, ii1, ij0, ij1   ! temporary integers 
    103       INTEGER  ::   ijeq                 ! index of equator T point (used in case 4) 
    104       REAL(wp) ::   zti, zui, zvi, zfi   ! local scalars 
    105       REAL(wp) ::   ztj, zuj, zvj, zfj   !   -      - 
    106       REAL(wp) ::   zphi0, zbeta, znorme ! 
     106      INTEGER  ::   ji, jj                   ! dummy loop indices 
     107      INTEGER  ::   ii0, ii1, ij0, ij1, iff  ! temporary integers 
     108      INTEGER  ::   ijeq                     ! index of equator T point (used in case 4) 
     109      REAL(wp) ::   zti, zui, zvi, zfi       ! local scalars 
     110      REAL(wp) ::   ztj, zuj, zvj, zfj       !   -      - 
     111      REAL(wp) ::   zphi0, zbeta, znorme     ! 
    107112      REAL(wp) ::   zarg, zf0, zminff, zmaxff 
    108113      REAL(wp) ::   zlam1, zcos_alpha, zim1 , zjm1 , ze1, ze1deg 
    109114      REAL(wp) ::   zphi1, zsin_alpha, zim05, zjm05 
    110       INTEGER  ::   isrow                ! index for ORCA1 starting row 
    111       INTEGER  ::   ie1e2u_v             ! fag for u- & v-surface read in coordinate file or not 
     115      INTEGER  ::   isrow                    ! index for ORCA1 starting row 
     116      INTEGER  ::   ie1e2u_v                 ! fag for u- & v-surface read in coordinate file or not 
    112117      !!---------------------------------------------------------------------- 
    113118      ! 
     
    134139         IF(lwp) WRITE(numout,*) '          curvilinear coordinate on the sphere read in "coordinate" file' 
    135140         ! 
    136          ie1e2u_v = 0                  ! set to unread e1e2u and e1e2v 
    137          ! 
    138          CALL hgr_read( ie1e2u_v )     ! read the coordinate.nc file 
     141         ie1e2u_v = 0             ! set to unread e1e2u and e1e2v 
     142         iff = 0                  ! set to unread iff 
     143         ! 
     144         CALL hgr_read( ie1e2u_v, iff )     ! read the coordinate.nc file !SF to be changed in mesh_mask 
    139145         ! 
    140146         IF( ie1e2u_v == 0 ) THEN      ! e1e2u and e1e2v have not been read: compute them 
     
    273279         IF(lwp) WRITE(numout,*) '          given by ppe1_m and ppe2_m' 
    274280         ! 
    275          ! Position coordinates (in kilometers) 
    276          !                          ========== 
    277          ! 
    278          ! angle 45deg and ze1=106.e+3 / jp_cfg forced -> zlam1 = -85deg, zphi1 = 29degN 
    279          zlam1 = -85._wp 
    280          zphi1 =  29._wp 
    281          ! resolution in meters 
    282          ze1 = 106000. / REAL( jp_cfg , wp )             
    283          ! benchmark: forced the resolution to be about 100 km 
    284          IF( nbench /= 0 )   ze1 = 106000._wp      
    285          zsin_alpha = - SQRT( 2._wp ) * 0.5_wp 
    286          zcos_alpha =   SQRT( 2._wp ) * 0.5_wp 
    287          ze1deg = ze1 / (ra * rad) 
    288          IF( nbench /= 0 )   ze1deg = ze1deg / REAL( jp_cfg , wp )   ! benchmark: keep the lat/+lon 
    289          !                                                           ! at the right jp_cfg resolution 
    290          glam0 = zlam1 + zcos_alpha * ze1deg * REAL( jpjglo-2 , wp ) 
    291          gphi0 = zphi1 + zsin_alpha * ze1deg * REAL( jpjglo-2 , wp ) 
    292          ! 
    293          IF( nprint==1 .AND. lwp )   THEN 
    294             WRITE(numout,*) '          ze1', ze1, 'cosalpha', zcos_alpha, 'sinalpha', zsin_alpha 
    295             WRITE(numout,*) '          ze1deg', ze1deg, 'glam0', glam0, 'gphi0', gphi0 
    296          ENDIF 
    297          ! 
    298          DO jj = 1, jpj 
    299             DO ji = 1, jpi 
    300                zim1 = REAL( ji + nimpp - 1 ) - 1.   ;   zim05 = REAL( ji + nimpp - 1 ) - 1.5 
    301                zjm1 = REAL( jj + njmpp - 1 ) - 1.   ;   zjm05 = REAL( jj + njmpp - 1 ) - 1.5 
    302                ! 
    303                glamf(ji,jj) = glam0 + zim1  * ze1deg * zcos_alpha + zjm1  * ze1deg * zsin_alpha 
    304                gphif(ji,jj) = gphi0 - zim1  * ze1deg * zsin_alpha + zjm1  * ze1deg * zcos_alpha 
    305                ! 
    306                glamt(ji,jj) = glam0 + zim05 * ze1deg * zcos_alpha + zjm05 * ze1deg * zsin_alpha 
    307                gphit(ji,jj) = gphi0 - zim05 * ze1deg * zsin_alpha + zjm05 * ze1deg * zcos_alpha 
    308                ! 
    309                glamu(ji,jj) = glam0 + zim1  * ze1deg * zcos_alpha + zjm05 * ze1deg * zsin_alpha 
    310                gphiu(ji,jj) = gphi0 - zim1  * ze1deg * zsin_alpha + zjm05 * ze1deg * zcos_alpha 
    311                ! 
    312                glamv(ji,jj) = glam0 + zim05 * ze1deg * zcos_alpha + zjm1  * ze1deg * zsin_alpha 
    313                gphiv(ji,jj) = gphi0 - zim05 * ze1deg * zsin_alpha + zjm1  * ze1deg * zcos_alpha 
    314             END DO 
    315          END DO 
    316          ! 
    317          ! Horizontal scale factors (in meters) 
    318          !                              ====== 
    319          e1t(:,:) =  ze1     ;      e2t(:,:) = ze1 
    320          e1u(:,:) =  ze1     ;      e2u(:,:) = ze1 
    321          e1v(:,:) =  ze1     ;      e2v(:,:) = ze1 
    322          e1f(:,:) =  ze1     ;      e2f(:,:) = ze1 
     281         IF(lwp) THEN 
     282            WRITE(numout,*) '               control print of value of ln_read_cfg     = ', ln_read_cfg 
     283         ENDIF 
     284         IF (ln_read_cfg) THEN  
     285            IF(lwp) WRITE(numout,*) '          ln_read_cfg read input files' 
     286            ie1e2u_v = 0                  ! set to unread e1e2u and e1e2v 
     287            iff = 0                       ! set to unread ff 
     288            ! 
     289            CALL hgr_read( ie1e2u_v, iff )     ! read the coordinate.nc file !SF to be changed in mesh_mask 
     290            ! 
     291            IF( ie1e2u_v == 0 ) THEN   ! e1e2u and e1e2v have not been read: compute them 
     292               !                          ! e2u and e1v does not include a 
     293               !                          reduction in some strait: apply reduction 
     294               e1e2u (:,:) = e1u(:,:) * e2u(:,:) 
     295               e1e2v (:,:) = e1v(:,:) * e2v(:,:) 
     296            ENDIF 
     297         ELSE 
     298            IF(lwp) WRITE(numout,*) '          ln_read_cfg CALL user_defined module' 
     299            CALL usr_def_hgr() 
     300            !SF CALL usr_def_hgr( nbench , jp_cfg  ,                    & 
     301            !SF &                 ff,                         & 
     302            !SF &                 glamt  , glamu   , glamv   , glamf   ,         & 
     303            !SF &                 gphit  , gphiu   , gphiv   , gphif   ,         & 
     304            !SF &                 e1t    , e1u     , e1v     , e1f     ,         & 
     305            !SF &                 e2t    , e2u     , e2v     , e2f     ,         &  
     306            !SF &                 e1e2t  , e1e2u   , e1e2v   , e1e2f   ,         &  
     307            !SF &                 e2_e1u , e1_e2v     ) 
     308            ! 
     309         ! 
     310         ENDIF 
    323311         ! 
    324312      CASE DEFAULT 
     
    420408         zf0   = 2. * omega * SIN( rad * zphi0 )                            ! compute f0 1st point south 
    421409         ! 
     410         iff = 0  
     411         CALL hgr_read( ie1e2u_v, iff )    
    422412         ff(:,:) = ( zf0 + zbeta * ABS( gphif(:,:) - zphi0 ) * rad * ra )   ! f = f0 +beta* y ( y=0 at south) 
    423413         ! 
     
    453443 
    454444 
    455    SUBROUTINE hgr_read( ke1e2u_v ) 
     445   SUBROUTINE hgr_read( ke1e2u_v, kff ) 
    456446      !!--------------------------------------------------------------------- 
    457447      !!              ***  ROUTINE hgr_read  *** 
    458448      !! 
    459       !! ** Purpose :   Read a coordinate file in NetCDF format using IOM 
     449      !! ** Purpose :   Read a mesh_mask file in NetCDF format using IOM 
    460450      !! 
    461451      !!---------------------------------------------------------------------- 
    462452      USE iom 
    463453      !! 
    464       INTEGER, INTENT( inout ) ::   ke1e2u_v   ! fag: e1e2u & e1e2v read in coordinate file (=1) or not (=0) 
     454      INTEGER, INTENT( inout ) ::   ke1e2u_v   ! fag: e1e2u & e1e2v read in mesh_mask file (=1) or not (=0) 
     455      INTEGER, INTENT( inout ) ::   kff        ! fag: kff read in mesh_mask file (=1) or not (=0) 
    465456      ! 
    466457      INTEGER ::   inum   ! temporary logical unit 
     
    469460      IF(lwp) THEN 
    470461         WRITE(numout,*) 
    471          WRITE(numout,*) 'hgr_read : read the horizontal coordinates' 
     462         WRITE(numout,*) 'hgr_read : read the horizontal coordinates in mesh_mask' 
    472463         WRITE(numout,*) '~~~~~~~~      jpiglo = ', jpiglo, ' jpjglo = ', jpjglo, ' jpk = ', jpk 
    473464      ENDIF 
    474465      ! 
    475       CALL iom_open( 'coordinates', inum ) 
     466      !SF CALL iom_open( 'coordinates', inum ) 
     467      CALL iom_open( 'mesh_mask', inum ) 
    476468      ! 
    477469      CALL iom_get( inum, jpdom_data, 'glamt', glamt, lrowattr=ln_use_jattr ) 
     
    494486      CALL iom_get( inum, jpdom_data, 'e2v'  , e2v  , lrowattr=ln_use_jattr ) 
    495487      CALL iom_get( inum, jpdom_data, 'e2f'  , e2f  , lrowattr=ln_use_jattr ) 
     488      !SF add read coriolis in mesh_mask file 
     489      CALL iom_get( inum, jpdom_data, 'ff'   , ff   , lrowattr=ln_use_jattr ) 
    496490      ! 
    497491      IF( iom_varid( inum, 'e1e2u', ldstop = .FALSE. ) > 0 ) THEN 
    498          IF(lwp) WRITE(numout,*) 'hgr_read : e1e2u & e1e2v read in coordinates file' 
     492         IF(lwp) WRITE(numout,*) 'hgr_read : e1e2u & e1e2v read in mesh_mask file' 
    499493         CALL iom_get( inum, jpdom_data, 'e1e2u'  , e1e2u  , lrowattr=ln_use_jattr ) 
    500494         CALL iom_get( inum, jpdom_data, 'e1e2v'  , e1e2v  , lrowattr=ln_use_jattr ) 
     
    502496      ELSE 
    503497         ke1e2u_v = 0 
     498      ENDIF 
     499      ! 
     500      IF( iom_varid( inum, 'kff', ldstop = .FALSE. ) > 0 ) THEN 
     501         IF(lwp) WRITE(numout,*) 'hgr_read : ff read in mesh_mask file' 
     502         CALL iom_get( inum, jpdom_data, 'ff'  , ff  , lrowattr=ln_use_jattr ) 
     503         kff = 1 
     504      ELSE 
     505         kff = 0 
    504506      ENDIF 
    505507      ! 
  • branches/2016/dev_r6409_SIMPLIF_2_usrdef/NEMOGCM/NEMO/OPA_SRC/nemogcm.F90

    r6152 r6422  
    242242         &             nn_isplt, nn_jsplt, nn_jctls, nn_jctle,   & 
    243243         &             nn_bench, nn_timing, nn_diacfl 
    244       NAMELIST/namcfg/ cp_cfg, cp_cfz, jp_cfg, jpidta, jpjdta, jpkdta, jpiglo, jpjglo, & 
     244      NAMELIST/namcfg/ ln_read_cfg, cp_cfg, cp_cfz, jp_cfg, jpidta, jpjdta, jpkdta, jpiglo, jpjglo, & 
    245245         &             jpizoom, jpjzoom, jperio, ln_use_jattr 
    246246      !!---------------------------------------------------------------------- 
     
    548548         WRITE(numout,*) '~~~~~~~ ' 
    549549         WRITE(numout,*) '   Namelist namcfg' 
     550         WRITE(numout,*) '      read configuration definition files          ln_read_cfg = ', ln_read_cfg 
    550551         WRITE(numout,*) '      configuration name                               cp_cfg  = ', TRIM(cp_cfg) 
    551552         WRITE(numout,*) '      configuration zoom name                          cp_cfz  = ', TRIM(cp_cfz) 
  • branches/2016/dev_r6409_SIMPLIF_2_usrdef/NEMOGCM/NEMO/OPA_SRC/par_oce.F90

    r5836 r6422  
    2828   !!                   namcfg namelist parameters 
    2929   !!---------------------------------------------------------------------- 
     30   LOGICAL       ::   ln_read_cfg      !: logical to read all needed files for a configuration 
    3031   CHARACTER(lc) ::   cp_cfg           !: name of the configuration 
    3132   CHARACTER(lc) ::   cp_cfz           !: name of the zoom of configuration 
Note: See TracChangeset for help on using the changeset viewer.