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 12249 for NEMO/branches/2019 – NEMO

Changeset 12249 for NEMO/branches/2019


Ignore:
Timestamp:
2019-12-13T19:48:00+01:00 (4 years ago)
Author:
laurent
Message:

Made STATION_ASF testcase fully compliant with new timestepping scheme.

Location:
NEMO/branches/2019/dev_r11943_MERGE_2019/tests/STATION_ASF
Files:
11 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r11943_MERGE_2019/tests/STATION_ASF/EXPREF/namelist_coare3p6-noskin_cfg

    r12199 r12249  
    278278&namctl        !   Control prints                                       (default: OFF) 
    279279!----------------------------------------------------------------------- 
    280 ln_ctl = .false. 
    281280/ 
    282281!----------------------------------------------------------------------- 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/tests/STATION_ASF/EXPREF/namelist_coare3p6_cfg

    r12199 r12249  
    278278&namctl        !   Control prints                                       (default: OFF) 
    279279!----------------------------------------------------------------------- 
    280 ln_ctl = .false. 
    281280/ 
    282281!----------------------------------------------------------------------- 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/tests/STATION_ASF/EXPREF/namelist_ecmwf-noskin_cfg

    r12199 r12249  
    278278&namctl        !   Control prints                                       (default: OFF) 
    279279!----------------------------------------------------------------------- 
    280 ln_ctl = .false. 
    281280/ 
    282281!----------------------------------------------------------------------- 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/tests/STATION_ASF/EXPREF/namelist_ecmwf_cfg

    r12199 r12249  
    278278&namctl        !   Control prints                                       (default: OFF) 
    279279!----------------------------------------------------------------------- 
    280 ln_ctl = .false. 
    281280/ 
    282281!----------------------------------------------------------------------- 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/tests/STATION_ASF/EXPREF/namelist_ncar_cfg

    r12199 r12249  
    278278&namctl        !   Control prints                                       (default: OFF) 
    279279!----------------------------------------------------------------------- 
    280 ln_ctl = .false. 
    281280/ 
    282281!----------------------------------------------------------------------- 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/tests/STATION_ASF/MY_SRC/diawri.F90

    r11831 r12249  
    2525   !!   dia_wri_state : create an output NetCDF file for a single instantaeous ocean state and forcing fields 
    2626   !!---------------------------------------------------------------------- 
    27    USE oce            ! ocean dynamics and tracers  
     27   USE oce            ! ocean dynamics and tracers 
    2828   USE dom_oce        ! ocean space and time domain 
    2929   USE phycst         ! physical constants 
     
    3333   USE lbclnk         ! ocean lateral boundary conditions (or mpp link) 
    3434   USE in_out_manager ! I/O manager 
    35    USE iom            !  
    36    USE ioipsl         !  
     35   USE iom            ! 
     36   USE ioipsl         ! 
    3737#if defined key_si3 
    38    USE ice  
    39    USE icewri  
     38   USE ice 
     39   USE icewri 
    4040#endif 
    4141   USE lib_mpp         ! MPP library 
     
    7474   END FUNCTION dia_wri_alloc 
    7575 
    76     
    77    SUBROUTINE dia_wri( kt ) 
     76 
     77   SUBROUTINE dia_wri( kt, Kmm ) 
    7878      !!--------------------------------------------------------------------- 
    7979      !!                  ***  ROUTINE dia_wri  *** 
    80       !!                    
    81       !! ** Purpose :   Standard output of opa: dynamics and tracer fields  
    82       !!      NETCDF format is used by default  
    83       !!      Standalone surface scheme  
     80      !! 
     81      !! ** Purpose :   Standard output of opa: dynamics and tracer fields 
     82      !!      NETCDF format is used by default 
     83      !!     STATION_ASF 
    8484      !! 
    8585      !! ** Method  :  use iom_put 
    8686      !!---------------------------------------------------------------------- 
    8787      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index 
    88       !!---------------------------------------------------------------------- 
    89       !  
     88      INTEGER, INTENT( in ) ::   Kmm     ! ocean time level index 
     89      !!---------------------------------------------------------------------- 
     90      ! 
     91      IF( ln_timing )   CALL timing_start('dia_wri') 
     92      ! 
    9093      ! Output the initial state and forcings 
    91       IF( ninist == 1 ) THEN                        
    92          CALL dia_wri_state( 'output.init' ) 
     94      IF( ninist == 1 ) THEN 
     95         CALL dia_wri_state( Kmm, 'output.init' ) 
    9396         ninist = 0 
    9497      ENDIF 
     
    99102      CALL iom_put(  "ssu", ssu_m(:,:) )    ! ocean surface current along i-axis 
    100103      CALL iom_put(  "ssv", ssv_m(:,:) )    ! ocean surface current along j-axis 
     104      ! 
     105      IF( ln_timing )   CALL timing_stop('dia_wri') 
    101106      ! 
    102107   END SUBROUTINE dia_wri 
     
    115120         &      ndex_hU(jpi*jpj) , ndex_U(jpi*jpj*jpk) ,     & 
    116121         &      ndex_hV(jpi*jpj) , ndex_V(jpi*jpj*jpk) , STAT=ierr(1) ) 
    117          ! 
     122      ! 
    118123      dia_wri_alloc = MAXVAL(ierr) 
    119124      CALL mpp_sum( 'diawri', dia_wri_alloc ) 
     
    121126   END FUNCTION dia_wri_alloc 
    122127 
    123     
    124    SUBROUTINE dia_wri( kt ) 
     128 
     129 
     130   SUBROUTINE dia_wri( kt, Kmm ) 
    125131      !!--------------------------------------------------------------------- 
    126132      !!                  ***  ROUTINE dia_wri  *** 
    127       !!                    
    128       !! ** Purpose :   Standard output of opa: dynamics and tracer fields  
    129       !!      NETCDF format is used by default  
    130       !! 
    131       !! ** Method  :   At the beginning of the first time step (nit000),  
     133      !! 
     134      !! ** Purpose :   Standard output of opa: dynamics and tracer fields 
     135      !!      NETCDF format is used by default 
     136      !! 
     137      !! ** Method  :   At the beginning of the first time step (nit000), 
    132138      !!      define all the NETCDF files and fields 
    133139      !!      At each time step call histdef to compute the mean if ncessary 
    134       !!      Each nwrite time step, output the instantaneous or mean fields 
     140      !!      Each nn_write time step, output the instantaneous or mean fields 
    135141      !!---------------------------------------------------------------------- 
    136142      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index 
     143      INTEGER, INTENT( in ) ::   Kmm  ! ocean time level index 
    137144      ! 
    138145      LOGICAL ::   ll_print = .FALSE.                        ! =T print and flush numout 
     
    144151      REAL(wp) ::   zsto, zout, zmax, zjulian                ! local scalars 
    145152      !!---------------------------------------------------------------------- 
    146       !  
     153      ! 
     154      IF( ninist == 1 ) THEN     !==  Output the initial state and forcings  ==! 
     155         CALL dia_wri_state( Kmm, 'output.init' ) 
     156         ninist = 0 
     157      ENDIF 
     158      ! 
     159      IF( nn_write == -1 )   RETURN   ! we will never do any output 
     160      ! 
    147161      IF( ln_timing )   CALL timing_start('dia_wri') 
    148       ! 
    149       IF( ninist == 1 ) THEN     !==  Output the initial state and forcings  ==! 
    150          CALL dia_wri_state( 'output.init' ) 
    151          ninist = 0 
    152       ENDIF 
    153162      ! 
    154163      ! 0. Initialisation 
     
    159168 
    160169      ! Define frequency of output and means 
    161       IF( ln_mskland )   THEN   ;   clop = "only(x)"   ! put 1.e+20 on land (very expensive!!) 
    162       ELSE                      ;   clop = "x"         ! no use of the mask value (require less cpu time) 
    163       ENDIF 
     170      clop = "x"         ! no use of the mask value (require less cpu time and otherwise the model crashes) 
    164171#if defined key_diainstant 
    165       zsto = nwrite * rdt 
     172      zsto = nn_write * rdt 
    166173      clop = "inst("//TRIM(clop)//")" 
    167174#else 
     
    169176      clop = "ave("//TRIM(clop)//")" 
    170177#endif 
    171       zout = nwrite * rdt 
     178      zout = nn_write * rdt 
    172179      zmax = ( nitend - nit000 + 1 ) * rdt 
    173180 
     
    196203            &                    ' MONTH ', nmonth, ' DAY ', nday, 'Julian day : ', zjulian 
    197204         IF(lwp)WRITE(numout,*) ' indexes of zoom = ', iimi, iima, ijmi, ijma,   & 
    198                                  ' limit storage in depth = ', ipk 
     205            ' limit storage in depth = ', ipk 
    199206 
    200207         ! WRITE root name in date.file for use by postpro 
    201208         IF(lwp) THEN 
    202             CALL dia_nam( clhstnam, nwrite,' ' ) 
     209            CALL dia_nam( clhstnam, nn_write,' ' ) 
    203210            CALL ctl_opn( inum, 'date.file', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 
    204211            WRITE(inum,*) clhstnam 
     
    208215         ! Define the T grid FILE ( nid_T ) 
    209216 
    210          CALL dia_nam( clhstnam, nwrite, 'grid_T' ) 
     217         CALL dia_nam( clhstnam, nn_write, 'grid_T' ) 
    211218         IF(lwp) WRITE(numout,*) " Name of NETCDF file ", clhstnam    ! filename 
    212219         CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,           &  ! Horizontal grid: glamt and gphit 
     
    220227         ! Define the U grid FILE ( nid_U ) 
    221228 
    222          CALL dia_nam( clhstnam, nwrite, 'grid_U' ) 
     229         CALL dia_nam( clhstnam, nn_write, 'grid_U' ) 
    223230         IF(lwp) WRITE(numout,*) " Name of NETCDF file ", clhstnam    ! filename 
    224231         CALL histbeg( clhstnam, jpi, glamu, jpj, gphiu,           &  ! Horizontal grid: glamu and gphiu 
     
    232239         ! Define the V grid FILE ( nid_V ) 
    233240 
    234          CALL dia_nam( clhstnam, nwrite, 'grid_V' )                   ! filename 
     241         CALL dia_nam( clhstnam, nn_write, 'grid_V' )                   ! filename 
    235242         IF(lwp) WRITE(numout,*) " Name of NETCDF file ", clhstnam 
    236243         CALL histbeg( clhstnam, jpi, glamv, jpj, gphiv,           &  ! Horizontal grid: glamv and gphiv 
     
    254261            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    255262         CALL histdef( nid_T, "sosfldow", "downward salt flux"                 , "PSU/m2/s",  &  ! (sfx) 
    256              &         jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     263            &         jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    257264         CALL histdef( nid_T, "sohefldo", "Net Downward Heat Flux"             , "W/m2"   ,   &  ! qns + qsr 
    258265            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     
    291298      ! --------------------- 
    292299 
    293       ! ndex(1) est utilise ssi l'avant dernier argument est different de  
     300      ! ndex(1) est utilise ssi l'avant dernier argument est different de 
    294301      ! la taille du tableau en sortie. Dans ce cas , l'avant dernier argument 
    295302      ! donne le nombre d'elements, et ndex la liste des indices a sortir 
    296303 
    297       IF( lwp .AND. MOD( itmod, nwrite ) == 0 ) THEN  
     304      IF( lwp .AND. MOD( itmod, nn_write ) == 0 ) THEN 
    298305         WRITE(numout,*) 'dia_wri : write model outputs in NetCDF files at ', kt, 'time-step' 
    299306         WRITE(numout,*) '~~~~~~ ' 
     
    304311      CALL histwrite( nid_T, "sss_m", it, sss_m, ndim_hT, ndex_hT )   ! sea surface salinity 
    305312      CALL histwrite( nid_T, "sowaflup", it, (emp - rnf )  , ndim_hT, ndex_hT )   ! upward water flux 
    306       CALL histwrite( nid_T, "sosfldow", it, sfx           , ndim_hT, ndex_hT )   ! downward salt flux  
    307                                                                                   ! (includes virtual salt flux beneath ice  
    308                                                                                   ! in linear free surface case) 
     313      CALL histwrite( nid_T, "sosfldow", it, sfx           , ndim_hT, ndex_hT )   ! downward salt flux 
     314      ! (includes virtual salt flux beneath ice 
     315      ! in linear free surface case) 
    309316 
    310317      CALL histwrite( nid_T, "sohefldo", it, qns + qsr     , ndim_hT, ndex_hT )   ! total heat flux 
    311318      CALL histwrite( nid_T, "soshfldo", it, qsr           , ndim_hT, ndex_hT )   ! solar heat flux 
    312       CALL histwrite( nid_T, "soicecov", it, fr_i          , ndim_hT, ndex_hT )   ! ice fraction    
    313       CALL histwrite( nid_T, "sowindsp", it, wndm          , ndim_hT, ndex_hT )   ! wind speed    
    314  
    315          ! Write fields on U grid 
     319      CALL histwrite( nid_T, "soicecov", it, fr_i          , ndim_hT, ndex_hT )   ! ice fraction 
     320      CALL histwrite( nid_T, "sowindsp", it, wndm          , ndim_hT, ndex_hT )   ! wind speed 
     321 
     322      ! Write fields on U grid 
    316323      CALL histwrite( nid_U, "ssu_m"   , it, ssu_m         , ndim_hU, ndex_hU )   ! i-current speed 
    317324      CALL histwrite( nid_U, "sozotaux", it, utau          , ndim_hU, ndex_hU )   ! i-wind stress 
    318325 
    319          ! Write fields on V grid 
     326      ! Write fields on V grid 
    320327      CALL histwrite( nid_V, "ssv_m"   , it, ssv_m         , ndim_hV, ndex_hV )   ! j-current speed 
    321328      CALL histwrite( nid_V, "sometauy", it, vtau          , ndim_hV, ndex_hV )   ! j-wind stress 
     
    334341#endif 
    335342 
    336    SUBROUTINE dia_wri_state( cdfile_name ) 
     343   SUBROUTINE dia_wri_state( Kmm, cdfile_name ) 
    337344      !!--------------------------------------------------------------------- 
    338345      !!                 ***  ROUTINE dia_wri_state  *** 
    339       !!         
    340       !! ** Purpose :   create a NetCDF file named cdfile_name which contains  
     346      !! 
     347      !! ** Purpose :   create a NetCDF file named cdfile_name which contains 
    341348      !!      the instantaneous ocean state and forcing fields. 
    342349      !!        Used to find errors in the initial state or save the last 
     
    347354      !!      File 'output.abort.nc' is created in case of abnormal job end 
    348355      !!---------------------------------------------------------------------- 
     356      INTEGER           , INTENT( in ) ::   Kmm              ! time level index 
    349357      CHARACTER (len=* ), INTENT( in ) ::   cdfile_name      ! name of the file created 
    350358      !! 
    351359      INTEGER :: inum 
    352360      !!---------------------------------------------------------------------- 
    353       !  
     361      ! 
    354362      IF(lwp) WRITE(numout,*) 
    355363      IF(lwp) WRITE(numout,*) 'dia_wri_state : single instantaneous ocean state' 
     
    358366 
    359367#if defined key_si3 
    360      CALL iom_open( TRIM(cdfile_name), inum, ldwrt = .TRUE., kdlev = jpl ) 
     368      CALL iom_open( TRIM(cdfile_name), inum, ldwrt = .TRUE., kdlev = jpl ) 
    361369#else 
    362      CALL iom_open( TRIM(cdfile_name), inum, ldwrt = .TRUE. ) 
    363 #endif 
    364  
    365       CALL iom_rstput( 0, 0, inum, 'votemper', tsn(:,:,:,jp_tem) )    ! now temperature 
    366       CALL iom_rstput( 0, 0, inum, 'vosaline', tsn(:,:,:,jp_sal) )    ! now salinity 
    367       CALL iom_rstput( 0, 0, inum, 'sossheig', sshn              )    ! sea surface height 
    368       CALL iom_rstput( 0, 0, inum, 'vozocrtx', un                )    ! now i-velocity 
    369       CALL iom_rstput( 0, 0, inum, 'vomecrty', vn                )    ! now j-velocity 
    370       CALL iom_rstput( 0, 0, inum, 'vovecrtz', wn                )    ! now k-velocity 
     370      CALL iom_open( TRIM(cdfile_name), inum, ldwrt = .TRUE. ) 
     371#endif 
     372 
     373      CALL iom_rstput( 0, 0, inum, 'votemper', ts(:,:,:,jp_tem,Kmm) )    ! now temperature 
     374      CALL iom_rstput( 0, 0, inum, 'vosaline', ts(:,:,:,jp_sal,Kmm) )    ! now salinity 
     375      CALL iom_rstput( 0, 0, inum, 'sossheig', ssh(:,:,Kmm)              )    ! sea surface height 
     376      CALL iom_rstput( 0, 0, inum, 'vozocrtx', uu(:,:,:,Kmm)                )    ! now i-velocity 
     377      CALL iom_rstput( 0, 0, inum, 'vomecrty', vv(:,:,:,Kmm)                )    ! now j-velocity 
     378         CALL iom_rstput( 0, 0, inum, 'vovecrtz', ww             )    ! now k-velocity 
    371379      CALL iom_rstput( 0, 0, inum, 'sowaflup', emp - rnf         )    ! freshwater budget 
    372380      CALL iom_rstput( 0, 0, inum, 'sohefldo', qsr + qns         )    ! total heat flux 
     
    375383      CALL iom_rstput( 0, 0, inum, 'sozotaux', utau              )    ! i-wind stress 
    376384      CALL iom_rstput( 0, 0, inum, 'sometauy', vtau              )    ! j-wind stress 
    377   
     385 
    378386#if defined key_si3 
    379387      IF( nn_ice == 2 ) THEN   ! condition needed in case agrif + ice-model but no-ice in child grid 
     
    383391      ! 
    384392      CALL iom_close( inum ) 
    385       !  
     393      ! 
    386394   END SUBROUTINE dia_wri_state 
    387395 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/tests/STATION_ASF/MY_SRC/nemogcm.F90

    r11831 r12249  
    88   !!             -   ! 2014-12  (G. Madec) remove KPP scheme and cross-land advection (cla) 
    99   !!            4.0  ! 2016-10  (G. Madec, S. Flavoni)  domain configuration / user defined interface 
     10   !!            4.x  ! 2019-12  (L. Brodeau)  STATION_ASF test-case 
    1011   !!---------------------------------------------------------------------- 
    1112 
     
    1819   !!---------------------------------------------------------------------- 
    1920   USE step_oce       ! module used in the ocean time stepping module (step.F90) 
    20    USE sbc_oce        ! surface boundary condition: ocean 
     21   USE sbc_oce        ! surface boundary condition: ocean #LB: rm? 
    2122   USE phycst         ! physical constant                  (par_cst routine) 
    2223   USE domain         ! domain initialization   (dom_init & dom_cfg routines) 
    2324   USE closea         ! treatment of closed seas (for ln_closea) 
    2425   USE usrdef_nam     ! user defined configuration 
     26   USE step, ONLY : Nbb, Nnn, Naa, Nrhs ! time level indices 
    2527   USE daymod         ! calendar 
    2628   USE restart        ! open  restart file 
     
    8486      istp = nit000 
    8587      ! 
    86 #if defined key_c1d 
    8788      DO WHILE ( istp <= nitend .AND. nstop == 0 )    !==  C1D time-stepping  ==! 
    8889         CALL stp_c1d( istp ) 
    8990         istp = istp + 1 
    9091      END DO 
    91 #else 
    92       ! 
    93       IF( .NOT.ln_diurnal_only ) THEN                 !==  Standard time-stepping  ==! 
    94          ! 
    95          DO WHILE( istp <= nitend .AND. nstop == 0 ) 
    96  
    97             ncom_stp = istp 
    98             IF( ln_timing ) THEN 
    99                zstptiming = MPI_Wtime() 
    100                IF ( istp == ( nit000 + 1 ) ) elapsed_time = zstptiming 
    101                IF ( istp ==         nitend ) elapsed_time = zstptiming - elapsed_time 
    102             ENDIF 
    103  
    104             CALL stp        ( istp ) 
    105             istp = istp + 1 
    106  
    107             IF( lwp .AND. ln_timing )   WRITE(numtime,*) 'timing step ', istp-1, ' : ', MPI_Wtime() - zstptiming 
    108  
    109          END DO 
    110          ! 
    111       ELSE                                            !==  diurnal SST time-steeping only  ==! 
    112          ! 
    113          DO WHILE( istp <= nitend .AND. nstop == 0 ) 
    114             CALL stp_diurnal( istp )   ! time step only the diurnal SST 
    115             istp = istp + 1 
    116          END DO 
    117          ! 
    118       ENDIF 
    119       ! 
    120 #endif 
    12192      ! 
    12293      !                            !------------------------! 
     
    158129      INTEGER ::   ios, ilocal_comm   ! local integers 
    159130      !! 
    160       NAMELIST/namctl/ ln_ctl   , sn_cfctl, nn_print, nn_ictls, nn_ictle,   & 
     131      NAMELIST/namctl/ sn_cfctl,  nn_print, nn_ictls, nn_ictle,             & 
    161132         &             nn_isplt , nn_jsplt, nn_jctls, nn_jctle,             & 
    162133         &             ln_timing, ln_diacfl 
     
    173144#if defined key_iomput 
    174145      IF( Agrif_Root() ) THEN 
    175          CALL xios_initialize( "for_xios_mpi_id", return_comm=ilocal_comm )   ! nemo local communicator given by xios 
     146            CALL xios_initialize( "for_xios_mpi_id", return_comm=ilocal_comm )   ! nemo local communicator given by xios 
    176147      ENDIF 
    177148      CALL mpp_start( ilocal_comm ) 
    178149#else 
    179       CALL mpp_start( ) 
     150         CALL mpp_start( ) 
    180151#endif 
    181152      ! 
     
    190161      IF( lwm )   CALL ctl_opn(     numout,        'ocean.output', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
    191162      ! open reference and configuration namelist files 
    192       CALL ctl_opn( numnam_ref,        'namelist_ref',     'OLD', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
    193       CALL ctl_opn( numnam_cfg,        'namelist_cfg',     'OLD', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
     163      CALL load_nml( numnam_ref,        'namelist_ref',                                           -1, lwm ) 
     164      CALL load_nml( numnam_cfg,        'namelist_cfg',                                           -1, lwm ) 
    194165      IF( lwm )   CALL ctl_opn(     numond, 'output.namelist.dyn', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
    195166      ! open /dev/null file to be able to supress output write easily 
     
    197168      ! 
    198169      !                             !--------------------! 
    199       !                             ! Open listing units !  -> need ln_ctl from namctl to define lwp 
     170      !                             ! Open listing units !  -> need sn_cfctl from namctl to define lwp 
    200171      !                             !--------------------! 
    201172      ! 
    202       REWIND( numnam_ref )              ! Namelist namctl in reference namelist 
    203173      READ  ( numnam_ref, namctl, IOSTAT = ios, ERR = 901 ) 
    204174901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namctl in reference namelist' ) 
    205       REWIND( numnam_cfg )              ! Namelist namctl in confguration namelist 
    206175      READ  ( numnam_cfg, namctl, IOSTAT = ios, ERR = 902 ) 
    207176902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namctl in configuration namelist' ) 
    208177      ! 
    209       lwp = (narea == 1) .OR. ln_ctl    ! control of all listing output print 
     178      lwp = (narea == 1) .OR. sn_cfctl%l_oceout    ! control of all listing output print 
    210179      ! 
    211180      IF(lwp) THEN                      ! open listing units 
     
    239208      ENDIF 
    240209      ! 
    241       ! finalize the definition of namctl variables 
    242       IF( sn_cfctl%l_config ) THEN 
    243          ! Activate finer control of report outputs 
    244          ! optionally switch off output from selected areas (note this only 
    245          ! applies to output which does not involve global communications) 
    246          IF( ( narea < sn_cfctl%procmin .OR. narea > sn_cfctl%procmax  ) .OR. & 
    247             & ( MOD( narea - sn_cfctl%procmin, sn_cfctl%procincr ) /= 0 ) )    & 
    248             &   CALL nemo_set_cfctl( sn_cfctl, .FALSE., .FALSE. ) 
    249       ELSE 
    250          ! Use ln_ctl to turn on or off all options. 
    251          CALL nemo_set_cfctl( sn_cfctl, ln_ctl, .TRUE. ) 
    252       ENDIF 
    253       ! 
    254210      IF(lwm) WRITE( numond, namctl ) 
    255211      ! 
     
    258214      !                             !------------------------------------! 
    259215      ! 
    260       REWIND( numnam_ref )              ! Namelist namcfg in reference namelist 
    261216      READ  ( numnam_ref, namcfg, IOSTAT = ios, ERR = 903 ) 
    262217903   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namcfg in reference namelist' ) 
    263       REWIND( numnam_cfg )              ! Namelist namcfg in confguration namelist 
    264218      READ  ( numnam_cfg, namcfg, IOSTAT = ios, ERR = 904 ) 
    265219904   IF( ios >  0 )   CALL ctl_nam ( ios , 'namcfg in configuration namelist' ) 
     
    281235      CALL nemo_alloc() 
    282236 
     237      ! Initialise time level indices 
     238      Nbb = 1; Nnn = 2; Naa = 3; Nrhs = Naa 
     239 
    283240      !                             !-------------------------------! 
    284241      !                             !  NEMO general initialization  ! 
     
    294251      CALL     eos_init        ! Equation of state 
    295252      IF( lk_c1d       )   CALL     c1d_init        ! 1D column configuration 
    296       CALL     dom_init("OPA") ! Domain 
    297       IF( ln_ctl       )   CALL prt_ctl_init        ! Print control 
    298  
    299       CALL day_init        ! model calendar (using both namelist and restart infos) 
    300       IF( ln_rstart )      CALL rst_read_open 
     253      CALL     dom_init( Nbb, Nnn, Naa, "OPA") ! Domain 
     254      IF( sn_cfctl%l_prtctl )   & 
     255         &                 CALL prt_ctl_init        ! Print control 
     256 
     257      IF( ln_rstart ) THEN                    ! Restart from a file                                                                                  
     258         !                                    ! -------------------                                                                                  
     259         CALL rst_read( Nbb, Nnn )            ! Read the restart file                                                                                
     260         CALL day_init                        ! model calendar (using both namelist and restart infos)                                               
     261         !                                                                                                                                           
     262      ELSE                                    ! Start from rest                                                                                      
     263         !                                    ! ---------------                                                                                      
     264         numror = 0                           ! define numror = 0 -> no restart file to read                                                         
     265         neuler = 0                           ! Set time-step indicator at nit000 (euler forward)                                                    
     266         CALL day_init                        ! model calendar (using both namelist and restart infos)                                               
     267      ENDIF 
     268      ! 
    301269 
    302270      !                                      ! external forcing 
    303       CALL     sbc_init    ! surface boundary conditions (including sea-ice) 
     271      CALL     sbc_init( Nbb, Nnn, Naa )    ! surface boundary conditions (including sea-ice) 
    304272 
    305273      ! 
     
    325293         WRITE(numout,*) '~~~~~~~~' 
    326294         WRITE(numout,*) '   Namelist namctl' 
    327          WRITE(numout,*) '      run control (for debugging)     ln_ctl     = ', ln_ctl 
     295         WRITE(numout,*) '                              sn_cfctl%l_glochk  = ', sn_cfctl%l_glochk 
     296         WRITE(numout,*) '                              sn_cfctl%l_allon   = ', sn_cfctl%l_allon 
    328297         WRITE(numout,*) '       finer control over o/p sn_cfctl%l_config  = ', sn_cfctl%l_config 
    329298         WRITE(numout,*) '                              sn_cfctl%l_runstat = ', sn_cfctl%l_runstat 
     
    331300         WRITE(numout,*) '                              sn_cfctl%l_oceout  = ', sn_cfctl%l_oceout 
    332301         WRITE(numout,*) '                              sn_cfctl%l_layout  = ', sn_cfctl%l_layout 
    333          WRITE(numout,*) '                              sn_cfctl%l_mppout  = ', sn_cfctl%l_mppout 
    334          WRITE(numout,*) '                              sn_cfctl%l_mpptop  = ', sn_cfctl%l_mpptop 
     302         WRITE(numout,*) '                              sn_cfctl%l_prtctl  = ', sn_cfctl%l_prtctl 
     303         WRITE(numout,*) '                              sn_cfctl%l_prttrc  = ', sn_cfctl%l_prttrc 
     304         WRITE(numout,*) '                              sn_cfctl%l_oasout  = ', sn_cfctl%l_oasout 
    335305         WRITE(numout,*) '                              sn_cfctl%procmin   = ', sn_cfctl%procmin 
    336306         WRITE(numout,*) '                              sn_cfctl%procmax   = ', sn_cfctl%procmax 
     
    370340      !                             ! Parameter control 
    371341      ! 
    372       IF( ln_ctl ) THEN                 ! sub-domain area indices for the control prints 
     342      IF( sn_cfctl%l_prtctl .OR. sn_cfctl%l_prttrc ) THEN              ! sub-domain area indices for the control prints 
    373343         IF( lk_mpp .AND. jpnij > 1 ) THEN 
    374344            isplt = jpni   ;   jsplt = jpnj   ;   ijsplt = jpni*jpnj   ! the domain is forced to the real split domain 
     
    427397      IF( numstp          /= -1 )   CLOSE( numstp          )   ! time-step file 
    428398      IF( numrun          /= -1 )   CLOSE( numrun          )   ! run statistics file 
    429       IF( numnam_ref      /= -1 )   CLOSE( numnam_ref      )   ! oce reference namelist 
    430       IF( numnam_cfg      /= -1 )   CLOSE( numnam_cfg      )   ! oce configuration namelist 
    431399      IF( lwm.AND.numond  /= -1 )   CLOSE( numond          )   ! oce output namelist 
    432       IF( numnam_ice_ref  /= -1 )   CLOSE( numnam_ice_ref  )   ! ice reference namelist 
    433       IF( numnam_ice_cfg  /= -1 )   CLOSE( numnam_ice_cfg  )   ! ice configuration namelist 
    434400      IF( lwm.AND.numoni  /= -1 )   CLOSE( numoni          )   ! ice output namelist 
    435401      IF( numevo_ice      /= -1 )   CLOSE( numevo_ice      )   ! ice variables (temp. evolution) 
     
    488454      sn_cfctl%l_oceout  = setto 
    489455      sn_cfctl%l_layout  = setto 
    490       sn_cfctl%l_mppout  = setto 
    491       sn_cfctl%l_mpptop  = setto 
     456      sn_cfctl%l_prtctl  = setto 
     457      sn_cfctl%l_prttrc  = setto 
     458      sn_cfctl%l_oasout  = setto 
    492459   END SUBROUTINE nemo_set_cfctl 
    493460 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/tests/STATION_ASF/MY_SRC/sbcssm.F90

    r11831 r12249  
    1414   USE c1d            ! 1D configuration: lk_c1d 
    1515   USE dom_oce        ! ocean domain: variables 
    16    !LB:USE zdf_oce        ! ocean vertical physics: variables 
    1716   USE sbc_oce        ! surface module: variables 
    1817   USE phycst         ! physical constants 
    1918   USE eosbn2         ! equation of state - Brunt Vaisala frequency 
    2019   USE lbclnk         ! ocean lateral boundary conditions (or mpp link) 
    21    !LB:USE zpshde         ! z-coord. with partial steps: horizontal derivatives 
    22    !LB:USE closea         ! for ln_closea 
    2320   ! 
    2421   USE in_out_manager ! I/O manager 
     
    2623   USE lib_mpp        ! distributed memory computing library 
    2724   USE prtctl         ! print control 
    28    USE fldread        ! read input fields  
     25   USE fldread        ! read input fields 
    2926   USE timing         ! Timing 
    3027 
     
    3229   PRIVATE 
    3330 
    34    PUBLIC   sbc_ssm        ! routine called by step.F90 
    35    PUBLIC   sbc_ssm_init   ! routine called by sbcmod.F90 
     31   PUBLIC   sbc_ssm_init   ! called by sbc_init 
     32   PUBLIC   sbc_ssm        ! called by sbc 
    3633 
    3734   CHARACTER(len=100) ::   cn_dir        ! Root directory for location of ssm files 
    3835   LOGICAL            ::   ln_3d_uve     ! specify whether input velocity data is 3D 
    3936   LOGICAL            ::   ln_read_frq   ! specify whether we must read frq or not 
    40     
     37 
    4138   LOGICAL            ::   l_sasread     ! Ice intilisation: =T read a file ; =F anaytical initilaistion 
    4239   LOGICAL            ::   l_initdone = .false. 
     
    6259CONTAINS 
    6360 
    64    SUBROUTINE sbc_ssm( kt ) 
     61   SUBROUTINE sbc_ssm( kt, Kbb, Kmm ) 
    6562      !!---------------------------------------------------------------------- 
    6663      !!                  ***  ROUTINE sbc_ssm  *** 
     
    6966      !!               for an off-line simulation using surface processes only 
    7067      !! 
    71       !! ** Method : calculates the position of data  
     68      !! ** Method : calculates the position of data 
    7269      !!             - interpolates data if needed 
    7370      !!---------------------------------------------------------------------- 
    7471      INTEGER, INTENT(in) ::   kt   ! ocean time-step index 
     72      INTEGER, INTENT(in) ::   Kbb, Kmm   ! ocean time level indices 
     73      ! (not needed for SAS but needed to keep a consistent interface in sbcmod.F90) 
    7574      ! 
    7675      INTEGER  ::   ji, jj     ! dummy loop indices 
     
    8079      ! 
    8180      IF( ln_timing )   CALL timing_start( 'sbc_ssm') 
    82       
     81 
    8382      IF ( l_sasread ) THEN 
    8483         IF( nfld_3d > 0 ) CALL fld_read( kt, 1, sf_ssm_3d )      !==   read data at kt time step   ==! 
    8584         IF( nfld_2d > 0 ) CALL fld_read( kt, 1, sf_ssm_2d )      !==   read data at kt time step   ==! 
    86          !  
     85         ! 
    8786         IF( ln_3d_uve ) THEN 
    8887            IF( .NOT. ln_linssh ) THEN 
    89                e3t_m(:,:) = sf_ssm_3d(jf_e3t)%fnow(:,:,1) * tmask(:,:,1) ! vertical scale factor  
     88               e3t_m(:,:) = sf_ssm_3d(jf_e3t)%fnow(:,:,1) * tmask(:,:,1) ! vertical scale factor 
    9089            ELSE 
    9190               e3t_m(:,:) = e3t_0(:,:,1)                                 ! vertical scale factor 
    9291            ENDIF 
    9392            ssu_m(:,:) = sf_ssm_3d(jf_usp)%fnow(:,:,1) * umask(:,:,1)    ! u-velocity 
    94             ssv_m(:,:) = sf_ssm_3d(jf_vsp)%fnow(:,:,1) * vmask(:,:,1)    ! v-velocity  
     93            ssv_m(:,:) = sf_ssm_3d(jf_vsp)%fnow(:,:,1) * vmask(:,:,1)    ! v-velocity 
    9594         ELSE 
    9695            IF( .NOT. ln_linssh ) THEN 
    97                e3t_m(:,:) = sf_ssm_2d(jf_e3t)%fnow(:,:,1) * tmask(:,:,1) ! vertical scale factor  
     96               e3t_m(:,:) = sf_ssm_2d(jf_e3t)%fnow(:,:,1) * tmask(:,:,1) ! vertical scale factor 
    9897            ELSE 
    9998               e3t_m(:,:) = e3t_0(:,:,1)                                 ! vertical scale factor 
    10099            ENDIF 
    101100            ssu_m(:,:) = sf_ssm_2d(jf_usp)%fnow(:,:,1) * umask(:,:,1)    ! u-velocity 
    102             ssv_m(:,:) = sf_ssm_2d(jf_vsp)%fnow(:,:,1) * vmask(:,:,1)    ! v-velocity  
     101            ssv_m(:,:) = sf_ssm_2d(jf_vsp)%fnow(:,:,1) * vmask(:,:,1)    ! v-velocity 
    103102         ENDIF 
    104103         ! 
     
    119118         IF( .NOT. ln_linssh ) e3t_m(:,:) = e3t_0(:,:,1) !clem: necessary at least for sas2D 
    120119         frq_m(:,:) = 1._wp                              !              - - 
    121          sshn (:,:) = 0._wp                              !              - - 
    122       ENDIF 
    123        
     120         ssh  (:,:,Kmm) = 0._wp                              !              - - 
     121      ENDIF 
     122 
    124123      IF ( nn_ice == 1 ) THEN 
    125          tsn(:,:,1,jp_tem) = sst_m(:,:) 
    126          tsn(:,:,1,jp_sal) = sss_m(:,:) 
    127          tsb(:,:,1,jp_tem) = sst_m(:,:) 
    128          tsb(:,:,1,jp_sal) = sss_m(:,:) 
    129       ENDIF 
    130       ub (:,:,1) = ssu_m(:,:) 
    131       vb (:,:,1) = ssv_m(:,:) 
    132   
    133       IF(ln_ctl) THEN                  ! print control 
     124         ts(:,:,1,jp_tem,Kmm) = sst_m(:,:) 
     125         ts(:,:,1,jp_sal,Kmm) = sss_m(:,:) 
     126         ts(:,:,1,jp_tem,Kbb) = sst_m(:,:) 
     127         ts(:,:,1,jp_sal,Kbb) = sss_m(:,:) 
     128      ENDIF 
     129      uu (:,:,1,Kbb) = ssu_m(:,:) 
     130      vv (:,:,1,Kbb) = ssv_m(:,:) 
     131 
     132      IF(sn_cfctl%l_prtctl) THEN            ! print control 
    134133         CALL prt_ctl(tab2d_1=sst_m, clinfo1=' sst_m   - : ', mask1=tmask   ) 
    135134         CALL prt_ctl(tab2d_1=sss_m, clinfo1=' sss_m   - : ', mask1=tmask   ) 
     
    156155 
    157156 
    158    SUBROUTINE sbc_ssm_init 
     157   SUBROUTINE sbc_ssm_init( Kbb, Kmm ) 
    159158      !!---------------------------------------------------------------------- 
    160159      !!                  ***  ROUTINE sbc_ssm_init  *** 
    161160      !! 
    162       !! ** Purpose :   Initialisation of sea surface mean data      
    163       !!---------------------------------------------------------------------- 
     161      !! ** Purpose :   Initialisation of sea surface mean data 
     162      !!---------------------------------------------------------------------- 
     163      INTEGER, INTENT(in) ::   Kbb, Kmm   ! ocean time level indices 
     164      ! (not needed for SAS but needed to keep a consistent interface in sbcmod.F90) 
    164165      INTEGER  :: ierr, ierr0, ierr1, ierr2, ierr3   ! return error code 
    165166      INTEGER  :: ifpr                               ! dummy loop indice 
     
    186187      ENDIF 
    187188      ! 
    188       REWIND( numnam_ref )              ! Namelist namsbc_sas in reference namelist : Input fields 
    189189      READ  ( numnam_ref, namsbc_sas, IOSTAT = ios, ERR = 901) 
    190190901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namsbc_sas in reference namelist' ) 
    191       REWIND( numnam_cfg )              ! Namelist namsbc_sas in configuration namelist : Input fields 
    192191      READ  ( numnam_cfg, namsbc_sas, IOSTAT = ios, ERR = 902 ) 
    193192902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namsbc_sas in configuration namelist' ) 
    194193      IF(lwm) WRITE ( numond, namsbc_sas ) 
    195       !            
     194      ! 
    196195      IF(lwp) THEN                              ! Control print 
    197196         WRITE(numout,*) '   Namelist namsbc_sas' 
    198          WRITE(numout,*) '      Initialisation using an input file                                 l_sasread   = ', l_sasread  
     197         WRITE(numout,*) '      Initialisation using an input file                                 l_sasread   = ', l_sasread 
    199198         WRITE(numout,*) '      Are we supplying a 3D u,v and e3 field                             ln_3d_uve   = ', ln_3d_uve 
    200199         WRITE(numout,*) '      Are we reading frq (fraction of qsr absorbed in the 1st T level)   ln_read_frq = ', ln_read_frq 
     
    220219         nn_fwb = 0 
    221220      ENDIF 
    222        
    223       !                   
     221 
     222      ! 
    224223      IF( l_sasread ) THEN                       ! store namelist information in an array 
    225          !  
     224         ! 
    226225         !! following code is a bit messy, but distinguishes between when u,v are 3d arrays and 
    227226         !! when we have other 3d arrays that we need to read in 
     
    269268         ENDIF 
    270269         ! 
    271          ierr1 = 0    ! default definition if slf_?d(ifpr)%ln_tint = .false.  
     270         ierr1 = 0    ! default definition if slf_?d(ifpr)%ln_tint = .false. 
    272271         IF( nfld_3d > 0 ) THEN 
    273272            ALLOCATE( sf_ssm_3d(nfld_3d), STAT=ierr )         ! set sf structure 
     
    276275            ENDIF 
    277276            DO ifpr = 1, nfld_3d 
    278                                             ALLOCATE( sf_ssm_3d(ifpr)%fnow(jpi,jpj,jpk)    , STAT=ierr0 ) 
     277               ALLOCATE( sf_ssm_3d(ifpr)%fnow(jpi,jpj,jpk)    , STAT=ierr0 ) 
    279278               IF( slf_3d(ifpr)%ln_tint )   ALLOCATE( sf_ssm_3d(ifpr)%fdta(jpi,jpj,jpk,2)  , STAT=ierr1 ) 
    280279               IF( ierr0 + ierr1 > 0 ) THEN 
     
    292291            ENDIF 
    293292            DO ifpr = 1, nfld_2d 
    294                                             ALLOCATE( sf_ssm_2d(ifpr)%fnow(jpi,jpj,1)    , STAT=ierr0 ) 
     293               ALLOCATE( sf_ssm_2d(ifpr)%fnow(jpi,jpj,1)    , STAT=ierr0 ) 
    295294               IF( slf_2d(ifpr)%ln_tint )   ALLOCATE( sf_ssm_2d(ifpr)%fdta(jpi,jpj,1,2)  , STAT=ierr1 ) 
    296295               IF( ierr0 + ierr1 > 0 ) THEN 
     
    307306      ENDIF 
    308307      ! 
    309       CALL sbc_ssm( nit000 )   ! need to define ss?_m arrays used in iceistate 
     308      CALL sbc_ssm( nit000, Kbb, Kmm )   ! need to define ss?_m arrays used in iceistate 
    310309      l_initdone = .TRUE. 
    311310      ! 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/tests/STATION_ASF/MY_SRC/step_c1d.F90

    r11930 r12249  
    66   !! History :   2.0  !  2004-04  (C. Ethe)  adapted from step.F90 for C1D 
    77   !!             3.0  !  2008-04  (G. Madec)  redo the adaptation to include SBC 
     8   !!             4.1  !  2019-08  (A. Coward, D. Storkey) rewrite in preparation for new timestepping scheme 
     9   !!             4.1  !  2019-12  (L. Brodeau) STATION_ASF test-case 
    810   !!---------------------------------------------------------------------- 
    911#if defined key_c1d 
    1012   !!---------------------------------------------------------------------- 
    1113   !!   'key_c1d'                                       1D Configuration 
    12    !!----------------------------------------------------------------------   
     14   !!---------------------------------------------------------------------- 
    1315   !!   stp_c1d        : NEMO system time-stepping in c1d case 
    1416   !!---------------------------------------------------------------------- 
    15    USE step_oce        ! time stepping definition modules  
    16    !LB:USE dyncor_c1d      ! Coriolis term (c1d case)         (dyn_cor_1d     ) 
    17    !LB:USE dynnxt          ! time-stepping                    (dyn_nxt routine) 
    18    !LB:USE dyndmp          ! U & V momentum damping           (dyn_dmp routine) 
    19    USE restart         ! restart  
     17   USE step_oce        ! time stepping definition modules 
     18   USE step, ONLY : Nbb, Nnn, Naa, Nrhs ! time level indices 
     19   USE restart         ! restart 
    2020 
    2121   IMPLICIT NONE 
    2222   PRIVATE 
    2323 
    24    PUBLIC   stp_c1d   ! called by nemogcm.F90 
     24   PUBLIC stp_c1d   ! called by nemogcm.F90 
    2525 
    2626   !!---------------------------------------------------------------------- 
     
    3434      !!---------------------------------------------------------------------- 
    3535      !!                     ***  ROUTINE stp_c1d  *** 
    36       !!                       
     36      !! 
    3737      !! ** Purpose :  - Time stepping of SBC including sea ice (dynamic and thermodynamic eqs.) 
    3838      !!               - Time stepping of OPA (momentum and active tracer eqs.) 
    3939      !!               - Time stepping of TOP (passive tracer eqs.) 
    40       !!  
    41       !! ** Method  : -1- Update forcings and data   
    42       !!              -2- Update vertical ocean physics  
    43       !!              -3- Compute the t and s trends  
    44       !!              -4- Update t and s  
     40      !! 
     41      !! ** Method  : -1- Update forcings and data 
     42      !!              -2- Update vertical ocean physics 
     43      !!              -3- Compute the t and s trends 
     44      !!              -4- Update t and s 
    4545      !!              -5- Compute the momentum trends 
    4646      !!              -6- Update the horizontal velocity 
     
    5454      !! --------------------------------------------------------------------- 
    5555 
    56                              indic = 0                ! reset to no error condition 
     56      indic = 0                ! reset to no error condition 
    5757      IF( kstp == nit000 )   CALL iom_init( "nemo")   ! iom_put initialization (must be done after nemo_init for AGRIF+XIOS+OASIS) 
    5858      IF( kstp /= nit000 )   CALL day( kstp )         ! Calendar (day was already called at nit000 in day_init) 
    59                              CALL iom_setkt( kstp - nit000 + 1, "nemo" )   ! say to iom that we are at time step kstp 
     59      CALL iom_setkt( kstp - nit000 + 1, "nemo" )   ! say to iom that we are at time step kstp 
    6060 
    61                              CALL sbc    ( kstp )         ! Sea Boundary Condition (including sea-ice) 
     61      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
     62      ! Update data, open boundaries, surface boundary condition (including sea-ice) 
     63      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
     64      CALL sbc    ( kstp, Nbb, Nnn )  ! Sea Boundary Condition (including sea-ice) 
    6265 
    63                              CALL dia_wri( kstp )         ! ocean model: outputs 
     66      CALL dia_wri( kstp, Nnn )  ! ocean model: outputs 
    6467 
    65                               
     68      ! Swap time levels 
     69      Nrhs = Nbb 
     70      Nbb = Nnn 
     71      Nnn = Naa 
     72      Naa = Nrhs 
     73 
    6674      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    67       ! Control 
     75      ! Control and restarts 
    6876      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    69                              CALL stp_ctl( kstp, indic ) 
    70       IF( indic < 0  )  THEN 
    71                              CALL ctl_stop( 'step: indic < 0' ) 
    72                              CALL dia_wri_state( 'output.abort' ) 
    73       ENDIF 
    74                               
    75       IF( kstp == nit000   ) CALL iom_close( numror )     ! close input  ocean restart file 
    76  
    77       !#LB: from C1D: 
    78       IF( lrst_oce       )   CALL rst_write( kstp )        ! write output ocean restart file 
     77      CALL stp_ctl( kstp, Nbb, Nnn, indic ) 
     78      IF( kstp == nit000 )   CALL iom_close( numror )          ! close input  ocean restart file 
     79      IF( lrst_oce       )   CALL rst_write( kstp, Nbb, Nnn )  ! write output ocean restart file 
    7980      ! 
    8081#if defined key_iomput 
    8182      IF( kstp == nitend .OR. indic < 0 )   CALL xios_context_finalize()   ! needed for XIOS 
     83      ! 
    8284#endif 
    83  
    84       !#LB: from SAS" 
    85 !#if defined key_iomput 
    86 !      IF( kstp == nitrst ) THEN 
    87 !         IF(.NOT.lwxios) THEN 
    88 !            CALL iom_close( numrow ) 
    89 !         ELSE 
    90 !            CALL iom_context_finalize( cwxios_context ) 
    91 !         ENDIF 
    92 !         lrst_oce = .FALSE. 
    93 !      ENDIF 
    94 !      IF( kstp == nitend .OR. indic < 0 ) THEN 
    95 !                             CALL iom_context_finalize( cxios_context ) ! needed for XIOS+AGRIF 
    96 !      ENDIF 
    97 !#endif 
    98 !      ! 
    99 !      IF( ln_timing .AND.  kstp == nit000  )   CALL timing_reset 
    100       ! 
    10185   END SUBROUTINE stp_c1d 
    10286 
    10387#else 
    104    !!----------------------------------------------------------------------                                                                      
    105    !!   Default key                                            NO 1D Config                                                                      
    106    !!----------------------------------------------------------------------                                                                      
     88   !!---------------------------------------------------------------------- 
     89   !!   Default key                                            NO 1D Config 
     90   !!---------------------------------------------------------------------- 
    10791CONTAINS 
    108    SUBROUTINE stp_c1d ( kt )      ! dummy routine                                                                                                
     92   SUBROUTINE stp_c1d ( kt )      ! dummy routine 
    10993      IMPLICIT NONE 
    11094      INTEGER, INTENT( in ) :: kt 
     
    11296   END SUBROUTINE stp_c1d 
    11397#endif 
    114     
     98 
    11599   !!====================================================================== 
    116100END MODULE step_c1d 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/tests/STATION_ASF/MY_SRC/stpctl.F90

    r11930 r12249  
    1212   !!            3.7  ! 2016-09  (G. Madec)  Remove solver 
    1313   !!            4.0  ! 2017-04  (G. Madec)  regroup global communications 
    14    !!            4.x  ! 2019-10  (L. Brodeau)  adapted for STATION_ASF test-case 
    1514   !!---------------------------------------------------------------------- 
    1615 
     
    1817   !!   stp_ctl      : Control the run 
    1918   !!---------------------------------------------------------------------- 
    20    !USE oce             ! ocean dynamics and tracers variables 
    2119   USE dom_oce         ! ocean space and time domain variables 
    22    !USE ice      , ONLY : vt_i, u_ice, tm_i 
    23    ! 
    2420   USE sbc_oce         ! surface fluxes and stuff 
    25    USE diawri 
     21   USE diawri          ! Standard run outputs       (dia_wri_state routine) 
    2622   ! 
    2723   USE in_out_manager  ! I/O manager 
     
    4238   !! Software governed by the CeCILL license (see ./LICENSE) 
    4339   !!---------------------------------------------------------------------- 
    44  
    4540CONTAINS 
    4641 
    47    SUBROUTINE stp_ctl( kt, kindic ) 
     42   SUBROUTINE stp_ctl( kt, Kbb, Kmm, kindic ) 
    4843      !!---------------------------------------------------------------------- 
    4944      !!                    ***  ROUTINE stp_ctl  *** 
     
    5752      !! ** Actions :   "time.step" file = last ocean time-step 
    5853      !!                "run.stat"  file = run statistics 
     54      !!                nstop indicator sheared among all local domain (lk_mpp=T) 
    5955      !!---------------------------------------------------------------------- 
    6056      INTEGER, INTENT(in   ) ::   kt       ! ocean time-step index 
     57      INTEGER, INTENT(in   ) ::   Kbb, Kmm      ! ocean time level index 
    6158      INTEGER, INTENT(inout) ::   kindic   ! error indicator 
    6259      !! 
     
    6764      ! 
    6865      ll_wrtstp  = ( MOD( kt, sn_cfctl%ptimincr ) == 0 ) .OR. ( kt == nitend ) 
    69       ll_colruns = ll_wrtstp .AND. ( ln_ctl .OR. sn_cfctl%l_runstat ) 
    70       ll_wrtruns = ll_colruns 
     66      ll_colruns = ll_wrtstp .AND. ( sn_cfctl%l_runstat ) 
     67      ll_wrtruns = ll_colruns .AND. lwm 
    7168      IF( kt == nit000 .AND. lwp ) THEN 
    7269         WRITE(numout,*) 
     
    7471         WRITE(numout,*) '~~~~~~~' 
    7572         !                                ! open time.step file 
    76          CALL ctl_opn( numstp, 'time.step', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 
     73         IF( lwm ) CALL ctl_opn( numstp, 'time.step', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 
    7774         !                                ! open run.stat file(s) at start whatever 
    7875         !                                ! the value of sn_cfctl%ptimincr 
    79          IF( ln_ctl .OR. sn_cfctl%l_runstat ) THEN 
     76         IF( lwm .AND. ( sn_cfctl%l_runstat ) ) THEN 
    8077            CALL ctl_opn( numrun, 'run.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 
    8178            clname = 'run.stat.nc' 
     
    9188      IF( kt == nit000 )   lsomeoce = COUNT( ssmask(:,:) == 1._wp ) > 0 
    9289      ! 
    93       IF(ll_wrtstp) THEN        !==  current time step  ==!   ("time.step" file) 
     90      IF(lwm .AND. ll_wrtstp) THEN        !==  current time step  ==!   ("time.step" file) 
    9491         WRITE ( numstp, '(1x, i8)' )   kt 
    9592         REWIND( numstp ) 
     
    103100      IF( ll_colruns ) THEN 
    104101         CALL mpp_max( "stpctl", zmax )          ! max over the global domain 
     102         nstop = NINT( zmax(3) )                 ! nstop indicator sheared among all local domains 
    105103      ENDIF 
    106104      !                                   !==  run statistics  ==!   ("run.stat" files) 
     
    114112      END IF 
    115113      !                                   !==  error handling  ==! 
    116       IF( ( ln_ctl .OR. lsomeoce ) .AND. (   &             ! have use mpp_max (because ln_ctl=.T.) or contains some ocean points 
     114      IF( ( sn_cfctl%l_glochk .OR. lsomeoce ) .AND. (   &  ! domain contains some ocean points, check for sensible ranges 
    117115         &  zmax(1) >    5._wp .OR.   &             ! too large wind stress ( > 5 N/m^2 ) 
    118116         &  zmax(2) > 2000._wp .OR.   &             ! too large non-solar heat flux ( > 2000 W/m^2) 
     
    126124         WRITE(ctmp6,*) '      ===> output of last computed fields in output.abort.nc file' 
    127125 
    128          CALL dia_wri_state( 'output.abort' )     ! create an output.abort file 
     126         CALL dia_wri_state( Kmm, 'output.abort' )     ! create an output.abort file 
    129127 
    130          IF( .NOT. ln_ctl ) THEN 
     128         IF( .NOT. sn_cfctl%l_glochk ) THEN 
    131129            WRITE(ctmp8,*) 'E R R O R message from sub-domain: ', narea 
    132130            CALL ctl_stop( 'STOP', ctmp1, ' ', ctmp2, ' ', ctmp6, ' ' ) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/tests/STATION_ASF/MY_SRC/usrdef_nam.F90

    r12199 r12249  
    1515   !!   usr_def_hgr   : initialize the horizontal mesh  
    1616   !!---------------------------------------------------------------------- 
    17    USE dom_oce  , ONLY: nimpp, njmpp       ! ocean space and time domain 
    18    USE dom_oce  , ONLY: ln_zco, ln_zps, ln_sco   ! flag of type of coordinate !#LB??? 
     17   USE dom_oce  , ONLY: nimpp, njmpp             ! ocean space and time domain 
     18   USE dom_oce  , ONLY: ln_zco, ln_zps, ln_sco   ! flag of type of coordinate 
    1919   USE par_oce        ! ocean space and time domain 
    2020   USE phycst         ! physical constants 
Note: See TracChangeset for help on using the changeset viewer.