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 10358 for NEMO/branches/2018/dev_r10164_HPC09_ESIWACE_PREP_MERGE/src/SAS – NEMO

Ignore:
Timestamp:
2018-11-25T15:24:21+01:00 (5 years ago)
Author:
smasson
Message:

dev_r10164_HPC09_ESIWACE_PREP_MERGE: action 5b: by default, suppress global communication in stpctl, see #2133

Location:
NEMO/branches/2018/dev_r10164_HPC09_ESIWACE_PREP_MERGE/src/SAS
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2018/dev_r10164_HPC09_ESIWACE_PREP_MERGE/src/SAS/diawri.F90

    r10297 r10358  
    3939   USE ioipsl 
    4040#if defined key_si3 
     41   USE ice 
    4142   USE icewri 
    4243#endif 
     
    9394      ! Output the initial state and forcings 
    9495      IF( ninist == 1 ) THEN 
    95          CALL dia_wri_state( 'output.init', kt ) 
     96         CALL dia_wri_state( 'output.init' ) 
    9697         ninist = 0 
    9798      ENDIF 
     
    142143      ! Output the initial state and forcings 
    143144      IF( ninist == 1 ) THEN                        
    144          CALL dia_wri_state( 'output.init', kt ) 
     145         CALL dia_wri_state( 'output.init' ) 
    145146         ninist = 0 
    146147      ENDIF 
     
    329330#endif 
    330331 
    331    SUBROUTINE dia_wri_state( cdfile_name, kt ) 
     332   SUBROUTINE dia_wri_state( cdfile_name ) 
    332333      !!--------------------------------------------------------------------- 
    333334      !!                 ***  ROUTINE dia_wri_state  *** 
     
    343344      !!---------------------------------------------------------------------- 
    344345      CHARACTER (len=* ), INTENT( in ) ::   cdfile_name      ! name of the file created 
    345       INTEGER           , INTENT( in ) ::   kt               ! ocean time-step index 
    346       !!  
    347       CHARACTER (len=32) :: clname 
    348       CHARACTER (len=40) :: clop 
    349       INTEGER  ::   id_i , nz_i, nh_i        
    350       INTEGER, DIMENSION(1) ::   idex             ! local workspace 
    351       REAL(wp) ::   zsto, zout, zmax, zjulian 
     346      !! 
     347      INTEGER :: inum 
    352348      !!---------------------------------------------------------------------- 
    353349      !  
    354       IF( ln_timing )   CALL timing_start('dia_wri_state') 
    355  
    356       ! 0. Initialisation 
    357       ! ----------------- 
    358  
    359       ! Define name, frequency of output and means 
    360       clname = cdfile_name 
    361       IF( .NOT. Agrif_Root() ) clname = TRIM(Agrif_CFixed())//'_'//TRIM(clname) 
    362       zsto = rdt 
    363       clop = "inst(x)"           ! no use of the mask value (require less cpu time) 
    364       zout = rdt 
    365       zmax = ( nitend - nit000 + 1 ) * rdt 
    366  
    367350      IF(lwp) WRITE(numout,*) 
    368351      IF(lwp) WRITE(numout,*) 'dia_wri_state : single instantaneous ocean state' 
    369352      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~   and forcing fields file created ' 
    370       IF(lwp) WRITE(numout,*) '                and named :', clname, '.nc' 
    371  
    372  
    373       ! 1. Define NETCDF files and fields at beginning of first time step 
    374       ! ----------------------------------------------------------------- 
    375  
    376       ! Compute julian date from starting date of the run 
    377       CALL ymds2ju( nyear, nmonth, nday, rdt, zjulian )         ! time axis  
    378       zjulian = zjulian - adatrj   !   set calendar origin to the beginning of the experiment 
    379       CALL histbeg( clname, jpi, glamt, jpj, gphit,   & 
    380           1, jpi, 1, jpj, nit000-1, zjulian, rdt, nh_i, id_i, domain_id=nidom, snc4chunks=snc4set ) ! Horizontal grid : glamt and gphit 
    381       CALL histvert( id_i, "deptht", "Vertical T levels",   &    ! Vertical grid : gdept 
    382           "m", jpk, gdept_1d, nz_i, "down") 
    383  
    384       ! Declare all the output fields as NetCDF variables 
    385  
    386       CALL histdef( id_i, "sowaflup", "Net Upward Water Flux" , "Kg/m2/S",   &   ! net freshwater  
    387          &          jpi, jpj, nh_i, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    388       CALL histdef( id_i, "sohefldo", "Net Downward Heat Flux", "W/m2"   ,   &   ! net heat flux 
    389          &          jpi, jpj, nh_i, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    390       CALL histdef( id_i, "soshfldo", "Shortwave Radiation"   , "W/m2"   ,   &   ! solar flux 
    391          &          jpi, jpj, nh_i, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    392       CALL histdef( id_i, "soicecov", "Ice fraction"          , "[0,1]"  ,   &   ! fr_i 
    393          &          jpi, jpj, nh_i, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    394       CALL histdef( id_i, "sozotaux", "Zonal Wind Stress"     , "N/m2"   ,   &   ! i-wind stress 
    395          &          jpi, jpj, nh_i, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    396       CALL histdef( id_i, "sometauy", "Meridional Wind Stress", "N/m2"   ,   &   ! j-wind stress 
    397          &          jpi, jpj, nh_i, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     353      IF(lwp) WRITE(numout,*) '                and named :', cdfile_name, '...nc' 
    398354 
    399355#if defined key_si3 
    400       IF( nn_ice == 2 ) THEN   ! condition needed in case agrif + lim but no-ice in child grid 
    401          CALL ice_wri_state( kt, id_i, nh_i ) 
    402       ENDIF 
     356     CALL iom_open( TRIM(cdfile_name), inum, ldwrt = .TRUE., kiolib = jprstlib, kdlev = jpl ) 
    403357#else 
    404       CALL histend( id_i, snc4chunks=snc4set ) 
    405 #endif 
    406  
    407       ! 2. Start writing data 
    408       ! --------------------- 
    409       ! idex(1) est utilise ssi l'avant dernier argument est diffferent de  
    410       ! la taille du tableau en sortie. Dans ce cas , l'avant dernier argument 
    411       ! donne le nombre d'elements, et idex la liste des indices a sortir 
    412       idex(1) = 1   ! init to avoid compil warning 
    413  
    414       ! Write all fields on T grid 
    415       CALL histwrite( id_i, "sowaflup", kt, emp              , jpi*jpj    , idex )    ! freshwater budget 
    416       CALL histwrite( id_i, "sohefldo", kt, qsr + qns        , jpi*jpj    , idex )    ! total heat flux 
    417       CALL histwrite( id_i, "soshfldo", kt, qsr              , jpi*jpj    , idex )    ! solar heat flux 
    418       CALL histwrite( id_i, "soicecov", kt, fr_i             , jpi*jpj    , idex )    ! ice fraction 
    419       CALL histwrite( id_i, "sozotaux", kt, utau             , jpi*jpj    , idex )    ! i-wind stress 
    420       CALL histwrite( id_i, "sometauy", kt, vtau             , jpi*jpj    , idex )    ! j-wind stress 
    421  
    422       ! 3. Close the file 
    423       ! ----------------- 
    424       CALL histclo( id_i ) 
    425 #if ! defined key_iomput 
    426       IF( ninist /= 1  ) THEN 
    427          CALL histclo( nid_T ) 
    428          CALL histclo( nid_U ) 
    429          CALL histclo( nid_V ) 
    430       ENDIF 
    431 #endif 
    432       ! 
    433       IF( ln_timing )   CALL timing_stop('dia_wri_state') 
     358     CALL iom_open( TRIM(cdfile_name), inum, ldwrt = .TRUE., kiolib = jprstlib ) 
     359#endif 
     360 
     361      CALL iom_rstput( 0, 0, inum, 'votemper', tsn(:,:,:,jp_tem) )    ! now temperature 
     362      CALL iom_rstput( 0, 0, inum, 'vosaline', tsn(:,:,:,jp_sal) )    ! now salinity 
     363      CALL iom_rstput( 0, 0, inum, 'sossheig', sshn              )    ! sea surface height 
     364      CALL iom_rstput( 0, 0, inum, 'vozocrtx', un                )    ! now i-velocity 
     365      CALL iom_rstput( 0, 0, inum, 'vomecrty', vn                )    ! now j-velocity 
     366      CALL iom_rstput( 0, 0, inum, 'vovecrtz', wn                )    ! now k-velocity 
     367      CALL iom_rstput( 0, 0, inum, 'sowaflup', emp - rnf         )    ! freshwater budget 
     368      CALL iom_rstput( 0, 0, inum, 'sohefldo', qsr + qns         )    ! total heat flux 
     369      CALL iom_rstput( 0, 0, inum, 'soshfldo', qsr               )    ! solar heat flux 
     370      CALL iom_rstput( 0, 0, inum, 'soicecov', fr_i              )    ! ice fraction 
     371      CALL iom_rstput( 0, 0, inum, 'sozotaux', utau              )    ! i-wind stress 
     372      CALL iom_rstput( 0, 0, inum, 'sometauy', vtau              )    ! j-wind stress 
     373  
     374#if defined key_si3 
     375      IF( nn_ice == 2 ) THEN   ! condition needed in case agrif + ice-model but no-ice in child grid 
     376         CALL ice_wri_state( inum ) 
     377      ENDIF 
     378#endif 
     379      ! 
     380      CALL iom_close( inum ) 
    434381      ! 
    435382   END SUBROUTINE dia_wri_state 
  • NEMO/branches/2018/dev_r10164_HPC09_ESIWACE_PREP_MERGE/src/SAS/step.F90

    r10068 r10358  
    121121      IF( indic < 0  )  THEN 
    122122                             CALL ctl_stop( 'step: indic < 0' ) 
    123                              CALL dia_wri_state( 'output.abort', kstp ) 
     123                             CALL dia_wri_state( 'output.abort' ) 
    124124      ENDIF 
    125125      IF( kstp == nit000   ) CALL iom_close( numror )     ! close input  ocean restart file 
  • NEMO/branches/2018/dev_r10164_HPC09_ESIWACE_PREP_MERGE/src/SAS/stpctl.F90

    r10314 r10358  
    3232 
    3333   INTEGER  ::   idrun, idtime, idssh, idu, ids, istatus 
     34   LOGICAL  ::   lsomeoce 
    3435   !!---------------------------------------------------------------------- 
    3536   !! NEMO/SAS 4.0 , NEMO Consortium (2018) 
     
    5758      !! 
    5859      REAL(wp), DIMENSION(3) ::   zmax 
     60      CHARACTER(len=20) :: clname 
    5961      !!---------------------------------------------------------------------- 
    6062 
     
    6466         WRITE(numout,*) '~~~~~~~' 
    6567         !                                ! open time.step file 
    66          CALL ctl_opn( numstp, 'time.step', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 
     68         IF( lwm ) CALL ctl_opn( numstp, 'time.step', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 
    6769         !                                ! open run.stat file 
    68          CALL ctl_opn( numrun, 'run.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 
    69  
    70          IF( lwm ) THEN 
     70         IF( ln_ctl .AND. lwm ) THEN 
     71            CALL ctl_opn( numrun, 'run.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 
     72            clname = 'run.stat.nc' 
     73            IF( .NOT. Agrif_Root() )   clname = TRIM(Agrif_CFixed())//"_"//TRIM(clname) 
    7174            istatus = NF90_CREATE( 'run.stat.nc', NF90_CLOBBER, idrun ) 
    7275            istatus = NF90_DEF_DIM( idrun, 'time'     , NF90_UNLIMITED, idtime ) 
     
    7679            istatus = NF90_ENDDEF(idrun) 
    7780         ENDIF 
    78           
    7981      ENDIF 
     82      IF( kt == nit000 )   lsomeoce = COUNT( ssmask(:,:) == 1._wp ) > 0 
    8083      ! 
    81       IF(lwp) THEN                        !==  current time step  ==!   ("time.step" file) 
     84      IF(lwm) THEN                        !==  current time step  ==!   ("time.step" file) 
    8285         WRITE ( numstp, '(1x, i8)' )   kt 
    8386         REWIND( numstp ) 
    8487      ENDIF 
    8588      !                                   !==  test of extrema  ==! 
    86       zmax(1) = MAXVAL(      vt_i (:,:) )                                           ! max ice thickness 
    87       zmax(2) = MAXVAL( ABS( u_ice(:,:) ) )                                         ! max ice velocity (zonal only) 
    88       zmax(3) = MAXVAL(     -tm_i (:,:)+273.15_wp , mask = ssmask(:,:) == 1._wp )   ! min ice temperature 
    89       ! 
    90       IF( lk_mpp ) CALL mpp_max( "stpctl", zmax )    ! max over the global domain 
    91       ! 
    92       IF( MOD( kt, nwrite ) == 1 .AND. lwp ) THEN 
    93          WRITE(numout,*) ' ==>> time-step= ', kt, ' vt_i max: ',  zmax(1), ' |u_ice| max: ', zmax(2), ' tm_i min: ', -zmax(3) 
    94       ENDIF 
    95  
     89      IF( ln_ctl ) THEN   ! must be done by all processes because of the mpp_max 
     90         zmax(1) = MAXVAL(      vt_i (:,:) )                                           ! max ice thickness 
     91         zmax(2) = MAXVAL( ABS( u_ice(:,:) ) )                                         ! max ice velocity (zonal only) 
     92         zmax(3) = MAXVAL(     -tm_i (:,:)+273.15_wp , mask = ssmask(:,:) == 1._wp )   ! min ice temperature 
     93         IF( lk_mpp ) CALL mpp_max( "stpctl", zmax )                                   ! max over the global domain 
     94      END IF 
    9695      !                                            !==  run statistics  ==!   ("run.stat" file) 
    97       IF(lwp) WRITE(numrun,9400) kt, zmax(1), zmax(2), - zmax(3) 
    98       IF( lwm ) THEN 
     96      IF( ln_ctl .AND. lwm ) THEN 
     97         IF(lwp) WRITE(numrun,9500) kt, zmax(1), zmax(2), - zmax(3) 
    9998         istatus = NF90_PUT_VAR( idrun, idssh, (/ zmax(1)/), (/kt/), (/1/) ) 
    10099         istatus = NF90_PUT_VAR( idrun,   idu, (/ zmax(2)/), (/kt/), (/1/) ) 
     
    104103      END IF 
    105104      ! 
    106 9400  FORMAT(' it :', i8, '    vt_i_max: ', D23.16, ' |u|_max: ', D23.16,' tm_i_min: ', D23.16) 
     1059500  FORMAT(' it :', i8, '    vt_i_max: ', D23.16, ' |u|_max: ', D23.16,' tm_i_min: ', D23.16) 
    107106      ! 
    108107   END SUBROUTINE stp_ctl 
Note: See TracChangeset for help on using the changeset viewer.