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 7200 for branches/2016/dev_r6409_SIMPLIF_2_usrdef/NEMOGCM/NEMO/OPA_SRC/nemogcm.F90 – NEMO

Ignore:
Timestamp:
2016-11-06T17:31:33+01:00 (8 years ago)
Author:
gm
Message:

#1692 - branch SIMPLIF_2_usrdef: add depth_e3 module + management of ORCA family + domain_cfg filename (in&out) given in namelist

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2016/dev_r6409_SIMPLIF_2_usrdef/NEMOGCM/NEMO/OPA_SRC/nemogcm.F90

    r7188 r7200  
    4646   !!---------------------------------------------------------------------- 
    4747   USE step_oce       ! module used in the ocean time stepping module (step.F90) 
    48    USE mppini         ! shared/distributed memory setting (mpp_init routine) 
    49    USE domain         ! domain initialization             (dom_init routine) 
    50 #if defined key_nemocice_decomp 
    51    USE ice_domain_size, only: nx_global, ny_global 
    52 #endif 
     48   USE phycst         ! physical constant                  (par_cst routine) 
     49   USE domain         ! domain initialization   (dom_init & dom_cfg routines) 
     50   USE usrdef_nam     ! user defined configuration 
    5351   USE tideini        ! tidal components initialization   (tide_ini routine) 
    5452   USE bdyini         ! open boundary cond. setting       (bdy_init routine) 
     
    6058   USE ldftra         ! lateral diffusivity setting    (ldftra_init routine) 
    6159   USE zdfini         ! vertical physics setting          (zdf_init routine) 
    62    USE phycst         ! physical constant                  (par_cst routine) 
    6360   USE trdini         ! dyn/tra trends initialization     (trd_init routine) 
    6461   USE asminc         ! assimilation increments      
     
    6865   USE diaobs         ! Observation diagnostics       (dia_obs_init routine) 
    6966   USE diacfl         ! CFL diagnostics               (dia_cfl_init routine) 
    70    USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 
    7167   USE step           ! NEMO time-stepping                 (stp     routine) 
    7268   USE icbini         ! handle bergs, initialisation 
     
    7874   USE stopar         ! Stochastic param.: ??? 
    7975   USE stopts         ! Stochastic param.: ??? 
     76   USE diurnal_bulk   ! diurnal bulk SST  
     77   USE step_diu       ! diurnal bulk SST timestepping (called from here if run offline) 
     78   USE crsini         ! initialise grid coarsening utility 
     79   USE diatmb         ! Top,middle,bottom output 
     80   USE dia25h         ! 25h mean output 
     81   USE sbc_oce , ONLY : lk_oasis 
     82   USE wet_dry        ! Wetting and drying setting   (wad_init routine) 
    8083#if defined key_top 
    8184   USE trcini         ! passive tracer initialisation 
    8285#endif 
     86#if defined key_nemocice_decomp 
     87   USE ice_domain_size, only: nx_global, ny_global 
     88#endif 
     89   ! 
    8390   USE lib_mpp        ! distributed memory computing 
    84    USE diurnal_bulk   ! diurnal bulk SST  
    85    USE step_diu       ! diurnal bulk SST timestepping (called from here if run offline) 
     91   USE mppini         ! shared/distributed memory setting (mpp_init routine) 
     92   USE lbcnfd , ONLY  : isendto, nsndto, nfsloop, nfeloop   ! Setup of north fold exchanges  
     93   USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 
    8694#if defined key_iomput 
    8795   USE xios           ! xIOserver 
    8896#endif 
    89    USE crsini         ! initialise grid coarsening utility 
    90    USE lbcnfd , ONLY  : isendto, nsndto, nfsloop, nfeloop   ! Setup of north fold exchanges  
    91    USE sbc_oce, ONLY  : lk_oasis 
    92    USE diatmb         ! Top,middle,bottom output 
    93    USE dia25h         ! 25h mean output 
    94    USE wet_dry        ! Wetting and drying setting   (wad_init routine) 
    95    USE usrdef_nam     ! user defined configuration 
    9697 
    9798   IMPLICIT NONE 
     
    125126      !!              Madec, 2008, internal report, IPSL. 
    126127      !!---------------------------------------------------------------------- 
    127       INTEGER ::   istp       ! time step index 
     128      INTEGER ::   istp   ! time step index 
    128129      !!---------------------------------------------------------------------- 
    129130      ! 
     
    196197      !                            !==  finalize the run  ==! 
    197198      !                            !------------------------! 
    198       IF(lwp) WRITE(numout,cform_aaa)   ! Flag AAAAAAA 
    199       ! 
    200       IF( nstop /= 0 .AND. lwp ) THEN   ! error print 
     199      IF(lwp) WRITE(numout,cform_aaa)        ! Flag AAAAAAA 
     200      ! 
     201      IF( nstop /= 0 .AND. lwp ) THEN        ! error print 
    201202         WRITE(numout,cform_err) 
    202203         WRITE(numout,*) nstop, ' error have been found' 
     
    216217      ! 
    217218#if defined key_iomput 
    218       CALL xios_finalize                  ! end mpp communications with xios 
    219       IF( lk_oasis )   CALL cpl_finalize  ! end coupling and mpp communications with OASIS 
     219      CALL xios_finalize                     ! end mpp communications with xios 
     220      IF( lk_oasis )   CALL cpl_finalize     ! end coupling and mpp communications with OASIS 
    220221#else 
    221222      IF( lk_oasis ) THEN  
    222          CALL cpl_finalize              ! end coupling and mpp communications with OASIS 
     223         CALL cpl_finalize                   ! end coupling and mpp communications with OASIS 
    223224      ELSE 
    224          IF( lk_mpp )   CALL mppstop    ! end mpp communications 
     225         IF( lk_mpp )   CALL mppstop         ! end mpp communications 
    225226      ENDIF 
    226227#endif 
     
    235236      !! ** Purpose :   initialization of the NEMO GCM 
    236237      !!---------------------------------------------------------------------- 
    237       INTEGER  ::   ji            ! dummy loop indices 
    238       INTEGER  ::   ilocal_comm   ! local integer 
    239       INTEGER  ::   ios, inum     !   -      - 
    240       REAL(wp) ::   ziglo, zjglo, zkglo, zperio   ! local scalars 
     238      INTEGER  ::   ji                 ! dummy loop indices 
     239      INTEGER  ::   ios, ilocal_comm   ! local integer 
    241240      CHARACTER(len=120), DIMENSION(30) ::   cltxt, cltxt2, clnam 
    242241      ! 
     
    244243         &             nn_isplt , nn_jsplt, nn_jctls, nn_jctle,   & 
    245244         &             nn_timing, nn_diacfl 
    246       NAMELIST/namcfg/ ln_read_cfg, ln_write_cfg, cp_cfg, jp_cfg, ln_use_jattr 
     245      NAMELIST/namcfg/ ln_read_cfg, cn_domcfg, ln_write_cfg, cn_domcfg_out, ln_use_jattr 
    247246      !!---------------------------------------------------------------------- 
    248247      ! 
     
    260259901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namctl in reference namelist', .TRUE. ) 
    261260      ! 
    262       REWIND( numnam_cfg )              ! Namelist namctl in confguration namelist : Control prints 
     261      REWIND( numnam_cfg )              ! Namelist namctl in confguration namelist 
    263262      READ  ( numnam_cfg, namctl, IOSTAT = ios, ERR = 902 ) 
    264263902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namctl in configuration namelist', .TRUE. ) 
    265264      ! 
    266       REWIND( numnam_ref )              ! Namelist namcfg in reference namelist 
     265      REWIND( numnam_ref )              ! Namelist namcfg in reference namelist : Control prints 
    267266      READ  ( numnam_ref, namcfg, IOSTAT = ios, ERR = 903 ) 
    268267903   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namcfg in reference namelist', .TRUE. ) 
    269       ! 
    270       REWIND( numnam_cfg )              ! Namelist namcfg in confguration namelist 
     268 
     269      REWIND( numnam_cfg )              ! Namelist namcfg in confguration namelist : Control prints & Benchmark 
    271270      READ  ( numnam_cfg, namcfg, IOSTAT = ios, ERR = 904 ) 
    272271904   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namcfg in configuration namelist', .TRUE. )    
     
    275274      !                             !  Set global domain size  !   (control print return in cltxt2) 
    276275      !                             !--------------------------! 
    277       IF( ln_read_cfg ) THEN              ! Read sizes in configuration "domain_cfg" file 
    278          CALL iom_open( 'domain_cfg', inum ) 
    279          CALL iom_get( inum, 'jpiglo', ziglo  )   ;   jpiglo = INT( ziglo ) 
    280          CALL iom_get( inum, 'jpjglo', zjglo  )   ;   jpjglo = INT( zjglo ) 
    281          CALL iom_get( inum, 'jpkglo', zkglo  )   ;   jpkglo = INT( zkglo ) 
    282          CALL iom_get( inum, 'jperio', zperio )   ;   jperio = INT( zperio ) 
    283          CALL iom_close( inum ) 
    284          WRITE(cltxt2(1),*) ' '       
    285          WRITE(cltxt2(2),*) 'domain_cfg : domain size read in "domain_cfg" file '          
    286          WRITE(cltxt2(3),*) '~~~~~~~~~~    ' 
    287          WRITE(cltxt2(4),*) '   jpiglo = ', jpiglo, ' jpjglo = ', jpjglo,  ' jpkglo = ', jpkglo 
    288          WRITE(cltxt2(5),*) '   global domain type of lateral boundary   jperio = ', jperio 
    289          !         
     276      IF( ln_read_cfg ) THEN              ! Read sizes in domain configuration file 
     277         CALL domain_cfg ( cltxt2, clnam, cn_cfg, nn_cfg, jpiglo, jpjglo, jpkglo, jperio ) 
     278         ! 
    290279      ELSE                                ! user-defined namelist 
    291          CALL usr_def_nam( cltxt2, clnam, jpiglo, jpjglo, jpkglo, jperio ) 
    292       ENDIF 
    293       jpk    = jpkglo 
     280         CALL usr_def_nam( cltxt2, clnam, cn_cfg, nn_cfg, jpiglo, jpjglo, jpkglo, jperio ) 
     281      ENDIF 
     282      ! 
     283      jpk = jpkglo 
    294284      ! 
    295285#if defined key_agrif 
     
    313303      IF( Agrif_Root() ) THEN 
    314304         IF( lk_oasis ) THEN 
    315             CALL cpl_init( "oceanx", ilocal_comm )                     ! nemo local communicator given by oasis 
    316             CALL xios_initialize( "not used",local_comm=ilocal_comm )    ! send nemo communicator to xios 
     305            CALL cpl_init( "oceanx", ilocal_comm )                               ! nemo local communicator given by oasis 
     306            CALL xios_initialize( "not used"       ,local_comm= ilocal_comm )    ! send nemo communicator to xios 
    317307         ELSE 
    318308            CALL xios_initialize( "for_xios_mpi_id",return_comm=ilocal_comm )    ! nemo local communicator given by xios 
     
    324314      IF( lk_oasis ) THEN 
    325315         IF( Agrif_Root() ) THEN 
    326             CALL cpl_init( "oceanx", ilocal_comm )                      ! nemo local communicator given by oasis 
     316            CALL cpl_init( "oceanx", ilocal_comm )          ! nemo local communicator given by oasis 
    327317         ENDIF 
    328318         ! Nodes selection (control print return in cltxt) 
    329319         narea = mynode( cltxt, 'output.namelist.dyn', numnam_ref, numnam_cfg, numond , nstop, ilocal_comm ) 
    330320      ELSE 
    331          ilocal_comm = 0 
    332          ! Nodes selection (control print return in cltxt) 
     321         ilocal_comm = 0                                    ! Nodes selection (control print return in cltxt) 
    333322         narea = mynode( cltxt, 'output.namelist.dyn', numnam_ref, numnam_cfg, numond , nstop ) 
    334323      ENDIF 
     
    340329      lwp = (narea == 1) .OR. ln_ctl                        ! control of all listing output print 
    341330 
    342       IF(lwm) THEN 
    343          ! write merged namelists from earlier to output namelist now that the 
    344          ! file has been opened in call to mynode. nammpp has already been 
    345          ! written in mynode (if lk_mpp_mpi) 
     331      IF(lwm) THEN               ! write merged namelists from earlier to output namelist  
     332         !                       ! now that the file has been opened in call to mynode.  
     333         !                       ! NB: nammpp has already been written in mynode (if lk_mpp_mpi) 
    346334         WRITE( numond, namctl ) 
    347335         WRITE( numond, namcfg ) 
    348336         IF( .NOT.ln_read_cfg ) THEN 
    349337            DO ji = 1, SIZE(clnam) 
    350                IF( TRIM(clnam (ji)) /= '' )   WRITE(numond, * ) clnam(ji)    ! namusr_def print 
     338               IF( TRIM(clnam(ji)) /= '' )   WRITE(numond, * ) clnam(ji)     ! namusr_def print 
    351339            END DO 
    352340         ENDIF 
     
    394382         CALL ctl_opn( numout, 'ocean.output', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE., narea ) 
    395383         ! 
    396  
    397  
    398384         WRITE(numout,*) 
    399385         WRITE(numout,*) '   CNRS - NERC - Met OFFICE - MERCATOR-ocean - INGV - CMCC' 
    400386         WRITE(numout,*) '                       NEMO team' 
    401387         WRITE(numout,*) '            Ocean General Circulation Model' 
    402          WRITE(numout,*) '                  version 3.7  (2016) ' 
     388         WRITE(numout,*) '                NEMO version 3.7  (2016) ' 
    403389         WRITE(numout,*) 
    404390         WRITE(numout,*) 
    405391         DO ji = 1, SIZE(cltxt) 
    406             IF( TRIM(cltxt (ji)) /= '' )   WRITE(numout,*) cltxt(ji)      ! control print of mynode 
     392            IF( TRIM(cltxt (ji)) /= '' )   WRITE(numout,*) cltxt(ji)    ! control print of mynode 
    407393         END DO 
    408394         WRITE(numout,*) 
    409395         WRITE(numout,*) 
    410396         DO ji = 1, SIZE(cltxt2) 
    411             IF( cltxt2(ji) /= '' )   WRITE(numout,*) cltxt2(ji)     ! control print of domain size 
     397            IF( TRIM(cltxt2(ji)) /= '' )   WRITE(numout,*) cltxt2(ji)   ! control print of domain size 
    412398         END DO 
    413399         ! 
    414          WRITE(numout,cform_aaa)                                         ! Flag AAAAAAA 
     400         WRITE(numout,cform_aaa)                                        ! Flag AAAAAAA 
    415401         ! 
    416402      ENDIF 
     
    418404      ! Now we know the dimensions of the grid and numout has been set: we can allocate arrays 
    419405      CALL nemo_alloc() 
     406 
    420407      !                             !-------------------------------! 
    421408      !                             !  NEMO general initialization  ! 
     
    534521                            CALL dia_tmb_init  ! TMB outputs 
    535522                            CALL dia_25h_init  ! 25h mean  outputs 
    536  
    537523      ! 
    538524   END SUBROUTINE nemo_init 
     
    577563         WRITE(numout,*) '~~~~~~~ ' 
    578564         WRITE(numout,*) '   Namelist namcfg' 
    579          WRITE(numout,*) '      read configuration definition files          ln_read_cfg = ', ln_read_cfg 
    580          WRITE(numout,*) '      configuration name                               cp_cfg  = ', TRIM(cp_cfg) 
    581          WRITE(numout,*) '      configuration resolution                         jp_cfg  = ', jp_cfg 
    582          WRITE(numout,*) '      use file attribute if exists as i/p j-start ln_use_jattr = ', ln_use_jattr 
     565         WRITE(numout,*) '      read domain configuration file                ln_read_cfg      = ', ln_read_cfg 
     566         WRITE(numout,*) '         filename to be read                           cn_domcfg     = ', TRIM(cn_domcfg) 
     567         WRITE(numout,*) '      write configuration definition file           ln_write_cfg     = ', ln_write_cfg 
     568         WRITE(numout,*) '         filename to be written                        cn_domcfg_out = ', TRIM(cn_domcfg_out) 
     569         WRITE(numout,*) '      use file attribute if exists as i/p j-start   ln_use_jattr     = ', ln_use_jattr 
    583570      ENDIF 
    584571      !                             ! Parameter control 
     
    679666      !!---------------------------------------------------------------------- 
    680667      ! 
    681       ierr =        oce_alloc       ()          ! ocean 
     668      ierr =        oce_alloc       ()          ! ocean  
    682669      ierr = ierr + dia_wri_alloc   () 
    683670      ierr = ierr + dom_oce_alloc   ()          ! ocean domain 
     
    855842                IF ((sxM .gt. sxT) .AND. (sxM .lt. dxT)) THEN 
    856843                   nsndto = nsndto + 1 
    857                      isendto(nsndto) = jn 
     844                   isendto(nsndto) = jn 
    858845                ELSEIF ((sxM .le. sxT) .AND. (dxM .ge. dxT)) THEN 
    859846                   nsndto = nsndto + 1 
    860                      isendto(nsndto) = jn 
     847                   isendto(nsndto) = jn 
    861848                ELSEIF ((dxM .lt. dxT) .AND. (sxT .lt. dxM)) THEN 
    862849                   nsndto = nsndto + 1 
    863                      isendto(nsndto) = jn 
    864                 END IF 
     850                   isendto(nsndto) = jn 
     851                ENDIF 
    865852          END DO 
    866853          nfsloop = 1 
Note: See TracChangeset for help on using the changeset viewer.