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 12377 for NEMO/trunk/src/SAS/nemogcm.F90 – NEMO

Ignore:
Timestamp:
2020-02-12T15:39:06+01:00 (4 years ago)
Author:
acc
Message:

The big one. Merging all 2019 developments from the option 1 branch back onto the trunk.

This changeset reproduces 2019/dev_r11943_MERGE_2019 on the trunk using a 2-URL merge
onto a working copy of the trunk. I.e.:

svn merge --ignore-ancestry \

svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/trunk \
svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/branches/2019/dev_r11943_MERGE_2019 ./

The --ignore-ancestry flag avoids problems that may otherwise arise from the fact that
the merge history been trunk and branch may have been applied in a different order but
care has been taken before this step to ensure that all applicable fixes and updates
are present in the merge branch.

The trunk state just before this step has been branched to releases/release-4.0-HEAD
and that branch has been immediately tagged as releases/release-4.0.2. Any fixes
or additions in response to tickets on 4.0, 4.0.1 or 4.0.2 should be done on
releases/release-4.0-HEAD. From now on future 'point' releases (e.g. 4.0.2) will
remain unchanged with periodic releases as needs demand. Note release-4.0-HEAD is a
transitional naming convention. Future full releases, say 4.2, will have a release-4.2
branch which fulfills this role and the first point release (e.g. 4.2.0) will be made
immediately following the release branch creation.

2020 developments can be started from any trunk revision later than this one.

Location:
NEMO/trunk
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/trunk

    • Property svn:externals
      •  

        old new  
        33^/utils/build/mk@HEAD         mk 
        44^/utils/tools@HEAD            tools 
        5 ^/vendors/AGRIF/dev@HEAD      ext/AGRIF 
         5^/vendors/AGRIF/dev_r11615_ENHANCE-04_namelists_as_internalfiles_agrif@HEAD      ext/AGRIF 
        66^/vendors/FCM@HEAD            ext/FCM 
        77^/vendors/IOIPSL@HEAD         ext/IOIPSL 
  • NEMO/trunk/src/SAS/nemogcm.F90

    r11536 r12377  
    3232   USE bdyini         ! open boundary cond. setting       (bdy_init routine). mandatory for sea-ice 
    3333   USE bdydta         ! open boundary cond. setting   (bdy_dta_init routine). mandatory for sea-ice 
     34   USE diu_layers     ! diurnal bulk SST and coolskin 
     35   USE step_diu       ! diurnal bulk SST timestepping (called from here if run offline) 
    3436   ! 
    3537   USE lib_mpp        ! distributed memory computing 
     
    5254   CHARACTER(lc) ::   cform_aaa="( /, 'AAAAAAAA', / ) "     ! flag for output listing 
    5355 
     56#if defined key_mpp_mpi 
     57   INCLUDE 'mpif.h' 
     58#endif 
     59 
    5460   !!---------------------------------------------------------------------- 
    5561   !! NEMO/SAS 4.0 , NEMO Consortium (2018) 
     
    8389      !                            !-----------------------! 
    8490#if defined key_agrif 
     91      Kbb_a = Nbb; Kmm_a = Nnn; Krhs_a = Nrhs   ! agrif_oce module copies of time level indices 
    8592      CALL Agrif_Declare_Var_dom   ! AGRIF: set the meshes for DOM 
    8693      CALL Agrif_Declare_Var       !  "      "   "   "      "  DYN/TRA  
     
    109116#if defined key_si3 
    110117      ! Recursive update from highest nested level to lowest: 
     118      Kbb_a = Nbb; Kmm_a = Nnn; Krhs_a = Nrhs   ! agrif_oce module copies of time level indices 
    111119      CALL Agrif_step_child_adj(Agrif_update_ice) 
    112120#endif 
     
    128136         ! 
    129137         DO WHILE( istp <= nitend .AND. nstop == 0 ) 
     138#if defined key_mpp_mpi 
     139            ncom_stp = istp 
     140            IF ( istp == ( nit000 + 1 ) ) elapsed_time = MPI_Wtime() 
     141            IF ( istp ==         nitend ) elapsed_time = MPI_Wtime() - elapsed_time 
     142#endif 
    130143            CALL stp        ( istp )  
    131144            istp = istp + 1 
     
    185198      INTEGER ::   ios, ilocal_comm   ! local integers 
    186199      !! 
    187       NAMELIST/namctl/ ln_ctl   , sn_cfctl, nn_print, nn_ictls, nn_ictle,   & 
     200      NAMELIST/namctl/ sn_cfctl, nn_print, nn_ictls, nn_ictle,              & 
    188201         &             nn_isplt , nn_jsplt, nn_jctls, nn_jctle,             & 
    189202         &             ln_timing, ln_diacfl 
     
    230243      ! open ocean.output as soon as possible to get all output prints (including errors messages) 
    231244      IF( lk_oasis ) THEN 
    232          IF( lwm )   CALL ctl_opn(     numout,              'sas.output', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
     245         IF( lwm )   CALL ctl_opn(     numout,               'sas.output', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
    233246         ! open reference and configuration namelist files 
    234                      CALL ctl_opn( numnam_ref,        'namelist_sas_ref',     'OLD', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
    235                      CALL ctl_opn( numnam_cfg,        'namelist_sas_cfg',     'OLD', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
    236          IF( lwm )   CALL ctl_opn(     numond, 'output.namelist_sas.dyn', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
     247                     CALL load_nml( numnam_ref,        'namelist_sas_ref',                                           -1, lwm ) 
     248                     CALL load_nml( numnam_cfg,        'namelist_sas_cfg',                                           -1, lwm ) 
     249         IF( lwm )   CALL ctl_opn(      numond, 'output.namelist_sas.dyn', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
    237250      ELSE 
    238          IF( lwm )   CALL ctl_opn(     numout,            'ocean.output', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
     251         IF( lwm )   CALL ctl_opn(      numout,            'ocean.output', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
    239252         ! open reference and configuration namelist files 
    240                      CALL ctl_opn( numnam_ref,            'namelist_ref',     'OLD', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
    241                      CALL ctl_opn( numnam_cfg,            'namelist_cfg',     'OLD', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
    242          IF( lwm )   CALL ctl_opn(     numond,     'output.namelist.dyn', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
     253                     CALL load_nml( numnam_ref,            'namelist_ref',                                           -1, lwm ) 
     254                     CALL load_nml( numnam_cfg,            'namelist_cfg',                                           -1, lwm ) 
     255         IF( lwm )   CALL ctl_opn(      numond,     'output.namelist.dyn', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
    243256      ENDIF 
    244257      ! open /dev/null file to be able to supress output write easily 
     
    246259      ! 
    247260      !                             !--------------------! 
    248       !                             ! Open listing units !  -> need ln_ctl from namctl to define lwp 
     261      !                             ! Open listing units !  -> need sn_cfctl from namctl to define lwp 
    249262      !                             !--------------------! 
    250263      ! 
    251       REWIND( numnam_ref )              ! Namelist namctl in reference namelist 
    252264      READ  ( numnam_ref, namctl, IOSTAT = ios, ERR = 901 ) 
    253265901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namctl in reference namelist' ) 
    254       REWIND( numnam_cfg )              ! Namelist namctl in confguration namelist 
    255266      READ  ( numnam_cfg, namctl, IOSTAT = ios, ERR = 902 ) 
    256267902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namctl in configuration namelist' ) 
    257268      ! 
    258       lwp = (narea == 1) .OR. ln_ctl    ! control of all listing output print 
     269      ! finalize the definition of namctl variables 
     270      IF( sn_cfctl%l_allon ) THEN 
     271         ! Turn on all options. 
     272         CALL nemo_set_cfctl( sn_cfctl, .TRUE., .TRUE. ) 
     273         ! Ensure all processors are active 
     274         sn_cfctl%procmin = 0 ; sn_cfctl%procmax = 1000000 ; sn_cfctl%procincr = 1 
     275      ELSEIF( sn_cfctl%l_config ) THEN 
     276         ! Activate finer control of report outputs 
     277         ! optionally switch off output from selected areas (note this only 
     278         ! applies to output which does not involve global communications) 
     279         IF( ( narea < sn_cfctl%procmin .OR. narea > sn_cfctl%procmax  ) .OR. & 
     280           & ( MOD( narea - sn_cfctl%procmin, sn_cfctl%procincr ) /= 0 ) )    & 
     281           &   CALL nemo_set_cfctl( sn_cfctl, .FALSE., .FALSE. ) 
     282      ELSE 
     283         ! turn off all options. 
     284         CALL nemo_set_cfctl( sn_cfctl, .FALSE., .TRUE. ) 
     285      ENDIF 
     286      ! 
     287      lwp = (narea == 1) .OR. sn_cfctl%l_oceout    ! control of all listing output print 
    259288      ! 
    260289      IF(lwp) THEN                      ! open listing units 
     
    291320         ! 
    292321      ENDIF 
    293      ! 
    294       ! finalize the definition of namctl variables 
    295       IF( sn_cfctl%l_config ) THEN 
    296          ! Activate finer control of report outputs 
    297          ! optionally switch off output from selected areas (note this only 
    298          ! applies to output which does not involve global communications) 
    299          IF( ( narea < sn_cfctl%procmin .OR. narea > sn_cfctl%procmax  ) .OR. & 
    300            & ( MOD( narea - sn_cfctl%procmin, sn_cfctl%procincr ) /= 0 ) )    & 
    301            &   CALL nemo_set_cfctl( sn_cfctl, .FALSE., .FALSE. ) 
    302       ELSE 
    303          ! Use ln_ctl to turn on or off all options. 
    304          CALL nemo_set_cfctl( sn_cfctl, ln_ctl, .TRUE. ) 
    305       ENDIF 
    306322      ! 
    307323      IF(lwm) WRITE( numond, namctl ) 
     
    311327      !                             !------------------------------------! 
    312328      ! 
    313       REWIND( numnam_ref )              ! Namelist namcfg in reference namelist 
    314329      READ  ( numnam_ref, namcfg, IOSTAT = ios, ERR = 903 ) 
    315330903   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namcfg in reference namelist' ) 
    316       REWIND( numnam_cfg )              ! Namelist namcfg in confguration namelist 
    317331      READ  ( numnam_cfg, namcfg, IOSTAT = ios, ERR = 904 ) 
    318332904   IF( ios >  0 )   CALL ctl_nam ( ios , 'namcfg in configuration namelist' )    
     
    334348      CALL nemo_alloc() 
    335349 
     350      ! Initialise time level indices 
     351      Nbb = 1; Nnn = 2; Naa = 3; Nrhs = Naa 
     352 
    336353      !                             !-------------------------------! 
    337354      !                             !  NEMO general initialization  ! 
     
    346363                           CALL phy_cst         ! Physical constants 
    347364                           CALL eos_init        ! Equation of seawater 
    348                            CALL dom_init('SAS') ! Domain 
    349       IF( ln_ctl      )    CALL prt_ctl_init    ! Print control 
     365                           CALL dom_init( Nbb, Nnn, Naa, 'SAS') ! Domain 
     366      IF( sn_cfctl%l_prtctl )   & 
     367         &                 CALL prt_ctl_init        ! Print control 
    350368       
    351369                           CALL day_init        ! model calendar (using both namelist and restart infos) 
     
    353371 
    354372      !                                      ! external forcing  
    355                            CALL sbc_init        ! Forcings : surface module  
     373                           CALL sbc_init( Nbb, Nnn, Naa )  ! Forcings : surface module  
    356374 
    357375      ! ==> clem: open boundaries init. is mandatory for sea-ice because ice BDY is not decoupled from   
     
    375393      !! ** Purpose :   control print setting 
    376394      !! 
    377       !! ** Method  : - print namctl information and check some consistencies 
     395      !! ** Method  : - print namctl and namcfg information and check some consistencies 
    378396      !!---------------------------------------------------------------------- 
    379397      ! 
     
    383401         WRITE(numout,*) '~~~~~~~~' 
    384402         WRITE(numout,*) '   Namelist namctl' 
    385          WRITE(numout,*) '      run control (for debugging)     ln_ctl     = ', ln_ctl 
     403         WRITE(numout,*) '                              sn_cfctl%l_glochk  = ', sn_cfctl%l_glochk 
     404         WRITE(numout,*) '                              sn_cfctl%l_allon   = ', sn_cfctl%l_allon 
    386405         WRITE(numout,*) '       finer control over o/p sn_cfctl%l_config  = ', sn_cfctl%l_config 
    387406         WRITE(numout,*) '                              sn_cfctl%l_runstat = ', sn_cfctl%l_runstat 
     
    389408         WRITE(numout,*) '                              sn_cfctl%l_oceout  = ', sn_cfctl%l_oceout 
    390409         WRITE(numout,*) '                              sn_cfctl%l_layout  = ', sn_cfctl%l_layout 
    391          WRITE(numout,*) '                              sn_cfctl%l_mppout  = ', sn_cfctl%l_mppout 
    392          WRITE(numout,*) '                              sn_cfctl%l_mpptop  = ', sn_cfctl%l_mpptop 
     410         WRITE(numout,*) '                              sn_cfctl%l_prtctl  = ', sn_cfctl%l_prtctl 
     411         WRITE(numout,*) '                              sn_cfctl%l_prttrc  = ', sn_cfctl%l_prttrc 
     412         WRITE(numout,*) '                              sn_cfctl%l_oasout  = ', sn_cfctl%l_oasout 
    393413         WRITE(numout,*) '                              sn_cfctl%procmin   = ', sn_cfctl%procmin   
    394414         WRITE(numout,*) '                              sn_cfctl%procmax   = ', sn_cfctl%procmax   
     
    428448      !                             ! Parameter control 
    429449      ! 
    430       IF( ln_ctl ) THEN                 ! sub-domain area indices for the control prints 
     450      IF( sn_cfctl%l_prtctl .OR. sn_cfctl%l_prttrc ) THEN              ! sub-domain area indices for the control prints 
    431451         IF( lk_mpp .AND. jpnij > 1 ) THEN 
    432452            isplt = jpni   ;   jsplt = jpnj   ;   ijsplt = jpni*jpnj   ! the domain is forced to the real split domain 
     
    489509      IF( numstp          /= -1 )   CLOSE( numstp          )   ! time-step file       
    490510      IF( numrun          /= -1 )   CLOSE( numrun          )   ! run statistics file 
    491       IF( numnam_ref      /= -1 )   CLOSE( numnam_ref      )   ! oce reference namelist 
    492       IF( numnam_cfg      /= -1 )   CLOSE( numnam_cfg      )   ! oce configuration namelist 
    493511      IF( lwm.AND.numond  /= -1 )   CLOSE( numond          )   ! oce output namelist 
    494       IF( numnam_ice_ref  /= -1 )   CLOSE( numnam_ice_ref  )   ! ice reference namelist 
    495       IF( numnam_ice_cfg  /= -1 )   CLOSE( numnam_ice_cfg  )   ! ice configuration namelist 
    496512      IF( lwm.AND.numoni  /= -1 )   CLOSE( numoni          )   ! ice output namelist 
    497513      IF( numevo_ice      /= -1 )   CLOSE( numevo_ice      )   ! ice variables (temp. evolution) 
     
    552568      sn_cfctl%l_oceout  = setto 
    553569      sn_cfctl%l_layout  = setto 
    554       sn_cfctl%l_mppout  = setto 
    555       sn_cfctl%l_mpptop  = setto 
     570      sn_cfctl%l_prtctl  = setto 
     571      sn_cfctl%l_prttrc  = setto 
     572      sn_cfctl%l_oasout  = setto 
    556573   END SUBROUTINE nemo_set_cfctl 
    557574 
Note: See TracChangeset for help on using the changeset viewer.