Changeset 12593
- Timestamp:
- 2020-03-24T16:52:17+01:00 (3 years ago)
- Location:
- NEMO/branches/2020/r12581_ticket2418
- Files:
-
- 17 edited
Legend:
- Unmodified
- Added
- Removed
-
NEMO/branches/2020/r12581_ticket2418/cfgs/SHARED/namelist_ref
r12530 r12593 1394 1394 &namctl ! Control prints (default: OFF) 1395 1395 !----------------------------------------------------------------------- 1396 sn_cfctl%l_glochk = .FALSE. ! Range sanity checks are local (F) or global (T). Set T for debugging only1397 1396 sn_cfctl%l_allon = .FALSE. ! IF T activate all options. If F deactivate all unless l_config is T 1398 1397 sn_cfctl%l_config = .TRUE. ! IF .true. then control which reports are written with the following -
NEMO/branches/2020/r12581_ticket2418/src/OCE/C1D/step_c1d.F90
r12377 r12593 56 56 ! 57 57 INTEGER :: jk ! dummy loop indice 58 INTEGER :: indic ! error indicator if < 059 58 !! --------------------------------------------------------------------- 60 61 indic = 0 ! reset to no error condition62 59 IF( kstp == nit000 ) CALL iom_init( "nemo") ! iom_put initialization (must be done after nemo_init for AGRIF+XIOS+OASIS) 63 60 IF( kstp /= nit000 ) CALL day( kstp ) ! Calendar (day was already called at nit000 in day_init) … … 139 136 ! Control and restarts 140 137 !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 141 CALL stp_ctl( kstp, Nnn , indic)138 CALL stp_ctl( kstp, Nnn ) 142 139 IF( kstp == nit000 ) CALL iom_close( numror ) ! close input ocean restart file 143 140 IF( lrst_oce ) CALL rst_write( kstp, Nbb, Nnn ) ! write output ocean restart file 144 141 ! 145 142 #if defined key_iomput 146 IF( kstp == nitend .OR. indic <0 ) CALL xios_context_finalize() ! needed for XIOS143 IF( kstp == nitend .OR. nstop > 0 ) CALL xios_context_finalize() ! needed for XIOS 147 144 ! 148 145 #endif -
NEMO/branches/2020/r12581_ticket2418/src/OCE/IOM/in_out_manager.F90
r12377 r12593 100 100 !!---------------------------------------------------------------------- 101 101 TYPE :: sn_ctl !: structure for control over output selection 102 LOGICAL :: l_glochk = .FALSE. !: range sanity checks are local (F) or global (T)103 ! Use global setting for debugging only;104 ! local breaches will still be reported105 ! and stop the code in most cases.106 102 LOGICAL :: l_allon = .FALSE. !: overall control; activate all following output options 107 103 LOGICAL :: l_config = .FALSE. !: activate/deactivate finer control -
NEMO/branches/2020/r12581_ticket2418/src/OCE/LBC/lib_mpp.F90
r12512 r12593 1145 1145 WRITE(numout,*) 'huge E-R-R-O-R : immediate stop' 1146 1146 WRITE(numout,*) 1147 CALL FLUSH(numout) 1148 CALL SLEEP(60) 1147 1149 CALL mppstop( ld_abort = .true. ) 1148 1150 ENDIF -
NEMO/branches/2020/r12581_ticket2418/src/OCE/LBC/mpp_loc_generic.h90
r10716 r12593 32 32 REAL(wp) , INTENT( out) :: pmin ! Global minimum of ptab 33 33 INDEX_TYPE(:) ! index of minimum in global frame 34 # if defined key_mpp_mpi35 34 ! 36 35 INTEGER :: ierror, ii, idim … … 56 55 ! 57 56 kindex(1) = mig( ilocs(1) ) 58 # 57 #if defined DIM_2d || defined DIM_3d /* avoid warning when kindex has 1 element */ 59 58 kindex(2) = mjg( ilocs(2) ) 60 # 61 # 59 #endif 60 #if defined DIM_3d /* avoid warning when kindex has 2 elements */ 62 61 kindex(3) = ilocs(3) 63 # 62 #endif 64 63 ! 65 64 DEALLOCATE (ilocs) 66 65 ! 67 66 index0 = kindex(1)-1 ! 1d index starting at 0 68 # 67 #if defined DIM_2d || defined DIM_3d /* avoid warning when kindex has 1 element */ 69 68 index0 = index0 + jpiglo * (kindex(2)-1) 70 # 71 # 69 #endif 70 #if defined DIM_3d /* avoid warning when kindex has 2 elements */ 72 71 index0 = index0 + jpiglo * jpjglo * (kindex(3)-1) 73 # 72 #endif 74 73 END IF 75 74 zain(1,:) = zmin … … 77 76 ! 78 77 IF( ln_timing ) CALL tic_tac(.TRUE., ld_global = .TRUE.) 78 #if defined key_mpp_mpi 79 79 CALL MPI_ALLREDUCE( zain, zaout, 1, MPI_2DOUBLE_PRECISION, MPI_OPERATION ,MPI_COMM_OCE, ierror) 80 #else 81 zaout(:,:) = zain(:,:) 82 #endif 80 83 IF( ln_timing ) CALL tic_tac(.FALSE., ld_global = .TRUE.) 81 84 ! 82 85 pmin = zaout(1,1) 83 86 index0 = NINT( zaout(2,1) ) 84 # 87 #if defined DIM_3d /* avoid warning when kindex has 2 elements */ 85 88 kindex(3) = index0 / (jpiglo*jpjglo) 86 89 index0 = index0 - kindex(3) * (jpiglo*jpjglo) 87 # 88 # 90 #endif 91 #if defined DIM_2d || defined DIM_3d /* avoid warning when kindex has 1 element */ 89 92 kindex(2) = index0 / jpiglo 90 93 index0 = index0 - kindex(2) * jpiglo 91 # 94 #endif 92 95 kindex(1) = index0 93 96 kindex(:) = kindex(:) + 1 ! start indices at 1 94 #else95 kindex = 0 ; pmin = 0.96 WRITE(*,*) 'ROUTINE_LOC: You should not have seen this print! error?'97 #endif98 97 99 98 END SUBROUTINE ROUTINE_LOC -
NEMO/branches/2020/r12581_ticket2418/src/OCE/nemogcm.F90
r12489 r12593 528 528 WRITE(numout,*) '~~~~~~~~' 529 529 WRITE(numout,*) ' Namelist namctl' 530 WRITE(numout,*) ' sn_cfctl%l_glochk = ', sn_cfctl%l_glochk531 530 WRITE(numout,*) ' sn_cfctl%l_allon = ', sn_cfctl%l_allon 532 531 WRITE(numout,*) ' finer control over o/p sn_cfctl%l_config = ', sn_cfctl%l_config -
NEMO/branches/2020/r12581_ticket2418/src/OCE/step.F90
r12489 r12593 82 82 !!---------------------------------------------------------------------- 83 83 INTEGER :: ji, jj, jk ! dummy loop indice 84 INTEGER :: indic ! error indicator if < 085 84 !!gm kcall can be removed, I guess 86 85 INTEGER :: kcall ! optional integer argument (dom_vvl_sf_nxt) … … 114 113 ! update I/O and calendar 115 114 !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 116 indic = 0 ! reset to no error condition117 118 115 IF( kstp == nit000 ) THEN ! initialize IOM context (must be done after nemo_init for AGRIF+XIOS+OASIS) 119 CALL iom_init( cxios_context, ld_closedef=.FALSE. ) ! for model grid (including p assible AGRIF zoom)116 CALL iom_init( cxios_context, ld_closedef=.FALSE. ) ! for model grid (including possible AGRIF zoom) 120 117 IF( lk_diamlr ) CALL dia_mlr_iom_init ! with additional setup for multiple-linear-regression analysis 121 118 CALL iom_init_closedef … … 323 320 ! Control 324 321 !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 325 CALL stp_ctl ( kstp, N bb, Nnn, indic)322 CALL stp_ctl ( kstp, Nnn ) 326 323 327 324 IF( kstp == nit000 ) THEN ! 1st time step only … … 338 335 ! 339 336 #if defined key_iomput 340 IF( kstp == nitend .OR. indic <0 ) THEN337 IF( kstp == nitend .OR. nstop > 0 ) THEN 341 338 CALL iom_context_finalize( cxios_context ) ! needed for XIOS+AGRIF 342 IF(lrxios) CALL iom_context_finalize( crxios_context)343 IF( ln_crs ) CALL iom_context_finalize( trim(cxios_context)//"_crs" ) !339 IF( lrxios ) CALL iom_context_finalize( crxios_context ) 340 IF( ln_crs ) CALL iom_context_finalize( TRIM(cxios_context)//"_crs" ) ! 344 341 ENDIF 345 342 #endif -
NEMO/branches/2020/r12581_ticket2418/src/OCE/stpctl.F90
r12377 r12593 33 33 PUBLIC stp_ctl ! routine called by step.F90 34 34 35 INTEGER :: idrun, idtime, idssh, idu, ids1, ids2, idt1, idt2, idc1, idw1, istatus36 LOGICAL :: lsomeoce35 INTEGER :: nrunid ! netcdf file id 36 INTEGER, DIMENSION(8) :: nvarid ! netcdf variable id 37 37 !!---------------------------------------------------------------------- 38 38 !! NEMO/OCE 4.0 , NEMO Consortium (2018) … … 42 42 CONTAINS 43 43 44 SUBROUTINE stp_ctl( kt, K bb, Kmm, kindic)44 SUBROUTINE stp_ctl( kt, Kmm ) 45 45 !!---------------------------------------------------------------------- 46 46 !! *** ROUTINE stp_ctl *** … … 50 50 !! ** Method : - Save the time step in numstp 51 51 !! - Print it each 50 time steps 52 !! - Stop the run IF problem encountered by setting indic=-352 !! - Stop the run IF problem encountered by setting nstop > 0 53 53 !! Problems checked: |ssh| maximum larger than 10 m 54 54 !! |U| maximum larger than 10 m/s … … 57 57 !! ** Actions : "time.step" file = last ocean time-step 58 58 !! "run.stat" file = run statistics 59 !! nstop indicator sheared among all local domain (lk_mpp=T)59 !! nstop indicator sheared among all local domain 60 60 !!---------------------------------------------------------------------- 61 61 INTEGER, INTENT(in ) :: kt ! ocean time-step index 62 INTEGER, INTENT(in ) :: Kbb, Kmm ! ocean time level index 63 INTEGER, INTENT(inout) :: kindic ! error indicator 62 INTEGER, INTENT(in ) :: Kmm ! ocean time level index 64 63 !! 65 INTEGER :: ji, jj, jk ! dummy loop indices 66 INTEGER, DIMENSION(2) :: ih ! min/max loc indices 67 INTEGER, DIMENSION(3) :: iu, is1, is2 ! min/max loc indices 68 REAL(wp) :: zzz ! local real 69 REAL(wp), DIMENSION(9) :: zmax 70 LOGICAL :: ll_wrtstp, ll_colruns, ll_wrtruns 71 CHARACTER(len=20) :: clname 64 INTEGER :: ji ! dummy loop indices 65 INTEGER :: idtime, istatus 66 INTEGER, DIMENSION(3,4) :: iloc ! min/max loc indices 67 REAL(wp) :: zzz ! local real 68 REAL(wp), DIMENSION(9) :: zmax, zmaxlocal, zarea 69 LOGICAL :: ll_wrtstp, ll_colruns, ll_wrtruns 70 LOGICAL, DIMENSION(jpi,jpj,jpk) :: llmsk 71 CHARACTER(len=20) :: clname 72 72 !!---------------------------------------------------------------------- 73 73 ! 74 ll_wrtstp = ( MOD( kt , sn_cfctl%ptimincr ) == 0 ) .OR. ( kt == nitend )75 ll_colruns = ll_wrtstp .AND. ( sn_cfctl%l_runstat )74 ll_wrtstp = ( MOD( kt-nit000, sn_cfctl%ptimincr ) == 0 ) .OR. ( kt == nitend ) 75 ll_colruns = ll_wrtstp .AND. sn_cfctl%l_runstat 76 76 ll_wrtruns = ll_colruns .AND. lwm 77 IF( kt == nit000 .AND. lwp ) THEN 78 WRITE(numout,*) 79 WRITE(numout,*) 'stp_ctl : time-stepping control' 80 WRITE(numout,*) '~~~~~~~' 81 ! ! open time.step file 82 IF( lwm ) CALL ctl_opn( numstp, 'time.step', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 83 ! ! open run.stat file(s) at start whatever 84 ! ! the value of sn_cfctl%ptimincr 85 IF( lwm .AND. ( sn_cfctl%l_runstat ) ) THEN 77 ! 78 IF( kt == nit000 ) THEN 79 ! 80 IF( lwp ) THEN 81 WRITE(numout,*) 82 WRITE(numout,*) 'stp_ctl : time-stepping control' 83 WRITE(numout,*) '~~~~~~~' 84 ENDIF 85 ! ! open time.step ascii file, done only by 1st subdomain 86 IF( lwm ) CALL ctl_opn( numstp, 'time.step', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 87 ! 88 IF( ll_wrtruns ) THEN 89 ! ! open run.stat ascii file, done only by 1st subdomain 86 90 CALL ctl_opn( numrun, 'run.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 91 ! ! open run.stat.nc netcdf file, done only by 1st subdomain 87 92 clname = 'run.stat.nc' 88 93 IF( .NOT. Agrif_Root() ) clname = TRIM(Agrif_CFixed())//"_"//TRIM(clname) 89 istatus = NF90_CREATE( TRIM(clname), NF90_CLOBBER, idrun)90 istatus = NF90_DEF_DIM( idrun, 'time', NF90_UNLIMITED, idtime )91 istatus = NF90_DEF_VAR( idrun, 'abs_ssh_max', NF90_DOUBLE, (/ idtime /), idssh)92 istatus = NF90_DEF_VAR( idrun, 'abs_u_max', NF90_DOUBLE, (/ idtime /), idu)93 istatus = NF90_DEF_VAR( idrun, 's_min', NF90_DOUBLE, (/ idtime /), ids1)94 istatus = NF90_DEF_VAR( idrun, 's_max', NF90_DOUBLE, (/ idtime /), ids2)95 istatus = NF90_DEF_VAR( idrun, 't_min', NF90_DOUBLE, (/ idtime /), idt1)96 istatus = NF90_DEF_VAR( idrun, 't_max', NF90_DOUBLE, (/ idtime /), idt2)94 istatus = NF90_CREATE( TRIM(clname), NF90_CLOBBER, nrunid ) 95 istatus = NF90_DEF_DIM( nrunid, 'time', NF90_UNLIMITED, idtime ) 96 istatus = NF90_DEF_VAR( nrunid, 'abs_ssh_max', NF90_DOUBLE, (/ idtime /), nvarid(1) ) 97 istatus = NF90_DEF_VAR( nrunid, 'abs_u_max', NF90_DOUBLE, (/ idtime /), nvarid(2) ) 98 istatus = NF90_DEF_VAR( nrunid, 's_min', NF90_DOUBLE, (/ idtime /), nvarid(3) ) 99 istatus = NF90_DEF_VAR( nrunid, 's_max', NF90_DOUBLE, (/ idtime /), nvarid(4) ) 100 istatus = NF90_DEF_VAR( nrunid, 't_min', NF90_DOUBLE, (/ idtime /), nvarid(5) ) 101 istatus = NF90_DEF_VAR( nrunid, 't_max', NF90_DOUBLE, (/ idtime /), nvarid(6) ) 97 102 IF( ln_zad_Aimp ) THEN 98 istatus = NF90_DEF_VAR( idrun, 'abs_wi_max', NF90_DOUBLE, (/ idtime /), idw1)99 istatus = NF90_DEF_VAR( idrun, 'Cf_max', NF90_DOUBLE, (/ idtime /), idc1)103 istatus = NF90_DEF_VAR( nrunid, 'Cf_max', NF90_DOUBLE, (/ idtime /), nvarid(7) ) 104 istatus = NF90_DEF_VAR( nrunid,'abs_wi_max',NF90_DOUBLE, (/ idtime /), nvarid(8) ) 100 105 ENDIF 101 istatus = NF90_ENDDEF(idrun) 102 zmax(8:9) = 0._wp ! initialise to zero in case ln_zad_Aimp option is not in use 103 ENDIF 104 ENDIF 105 IF( kt == nit000 ) lsomeoce = COUNT( ssmask(:,:) == 1._wp ) > 0 106 ! 107 IF(lwm .AND. ll_wrtstp) THEN !== current time step ==! ("time.step" file) 106 istatus = NF90_ENDDEF(nrunid) 107 ENDIF 108 ! 109 ENDIF 110 ! 111 ! !== write current time step ==! 112 ! !== done only by 1st subdomain at writting timestep ==! 113 IF( lwm .AND. ll_wrtstp ) THEN 108 114 WRITE ( numstp, '(1x, i8)' ) kt 109 115 REWIND( numstp ) 110 116 ENDIF 111 ! 112 ! !== test of extrema ==! 117 ! !== test of local extrema ==! 118 ! !== done by all processes at every time step ==! 119 llmsk(:,:,1) = ssmask(:,:) == 1._wp 113 120 IF( ll_wd ) THEN 114 zmax(1) = MAXVAL( ABS( ssh(:,:,Kmm) + ssh_ref*tmask(:,:,1) ) ) ! ssh max121 zmax(1) = MAXVAL( ABS( ssh(:,:,Kmm) + ssh_ref ), mask = llmsk(:,:,1) ) ! ssh max 115 122 ELSE 116 zmax(1) = MAXVAL( ABS( ssh(:,:,Kmm) ) ) ! ssh max 117 ENDIF 118 zmax(2) = MAXVAL( ABS( uu(:,:,:,Kmm) ) ) ! velocity max (zonal only) 119 zmax(3) = MAXVAL( -ts(:,:,:,jp_sal,Kmm) , mask = tmask(:,:,:) == 1._wp ) ! minus salinity max 120 zmax(4) = MAXVAL( ts(:,:,:,jp_sal,Kmm) , mask = tmask(:,:,:) == 1._wp ) ! salinity max 121 zmax(5) = MAXVAL( -ts(:,:,:,jp_tem,Kmm) , mask = tmask(:,:,:) == 1._wp ) ! minus temperature max 122 zmax(6) = MAXVAL( ts(:,:,:,jp_tem,Kmm) , mask = tmask(:,:,:) == 1._wp ) ! temperature max 123 zmax(7) = REAL( nstop , wp ) ! stop indicator 124 IF( ln_zad_Aimp ) THEN 125 zmax(8) = MAXVAL( ABS( wi(:,:,:) ) , mask = wmask(:,:,:) == 1._wp ) ! implicit vertical vel. max 126 zmax(9) = MAXVAL( Cu_adv(:,:,:) , mask = tmask(:,:,:) == 1._wp ) ! partitioning coeff. max 127 ENDIF 128 ! 123 zmax(1) = MAXVAL( ABS( ssh(:,:,Kmm) ), mask = llmsk(:,:,1) ) ! ssh max 124 ENDIF 125 llmsk(:,:,:) = umask(:,:,:) == 1._wp 126 zmax(2) = MAXVAL( ABS( uu(:,:,:,Kmm) ), mask = llmsk ) ! velocity max (zonal only) 127 llmsk(:,:,:) = tmask(:,:,:) == 1._wp 128 zmax(3) = MAXVAL( -ts(:,:,:,jp_sal,Kmm), mask = llmsk ) ! minus salinity max 129 zmax(4) = MAXVAL( ts(:,:,:,jp_sal,Kmm), mask = llmsk ) ! salinity max 130 IF( ll_colruns ) THEN ! following variables are used only in the netcdf file 131 zmax(5) = MAXVAL( -ts(:,:,:,jp_tem,Kmm), mask = llmsk ) ! minus temperature max 132 zmax(6) = MAXVAL( ts(:,:,:,jp_tem,Kmm), mask = llmsk ) ! temperature max 133 IF( ln_zad_Aimp ) THEN 134 zmax(7) = MAXVAL( Cu_adv(:,:,:) , mask = llmsk ) ! partitioning coeff. max 135 llmsk(:,:,:) = wmask(:,:,:) == 1._wp 136 zmax(8) = MAXVAL( ABS( wi(:,:,:) ) , mask = llmsk ) ! implicit vertical vel. max 137 ELSE 138 zmax(7:8) = 0._wp 139 ENDIF 140 ELSE 141 zmax(5:8) = 0._wp 142 ENDIF 143 zmax(9) = REAL( nstop, wp ) ! stop indicator 144 ! !== get global extrema ==! 145 ! !== done by all processes if writting run.stat ==! 129 146 IF( ll_colruns ) THEN 147 zmaxlocal(:) = zmax(:) 130 148 CALL mpp_max( "stpctl", zmax ) ! max over the global domain 131 nstop = NINT( zmax(7) ) ! nstop indicator sheared among all local domains 132 ENDIF 133 ! !== run statistics ==! ("run.stat" files) 149 nstop = NINT( zmax(9) ) ! update nstop indicator (now sheared among all local domains) 150 ENDIF 151 ! !== write "run.stat" files ==! 152 ! !== done only by 1st subdomain at writting timestep ==! 134 153 IF( ll_wrtruns ) THEN 135 154 WRITE(numrun,9500) kt, zmax(1), zmax(2), -zmax(3), zmax(4) 136 istatus = NF90_PUT_VAR( idrun, idssh, (/ zmax(1)/), (/kt/), (/1/) )137 istatus = NF90_PUT_VAR( idrun, idu, (/ zmax(2)/), (/kt/), (/1/) )138 istatus = NF90_PUT_VAR( idrun, ids1, (/-zmax(3)/), (/kt/), (/1/) )139 istatus = NF90_PUT_VAR( idrun, ids2, (/ zmax(4)/), (/kt/), (/1/) )140 istatus = NF90_PUT_VAR( idrun, idt1, (/-zmax(5)/), (/kt/), (/1/) )141 istatus = NF90_PUT_VAR( idrun, idt2, (/ zmax(6)/), (/kt/), (/1/) )155 istatus = NF90_PUT_VAR( nrunid, nvarid(1), (/ zmax(1)/), (/kt/), (/1/) ) 156 istatus = NF90_PUT_VAR( nrunid, nvarid(2), (/ zmax(2)/), (/kt/), (/1/) ) 157 istatus = NF90_PUT_VAR( nrunid, nvarid(3), (/-zmax(3)/), (/kt/), (/1/) ) 158 istatus = NF90_PUT_VAR( nrunid, nvarid(4), (/ zmax(4)/), (/kt/), (/1/) ) 159 istatus = NF90_PUT_VAR( nrunid, nvarid(5), (/-zmax(5)/), (/kt/), (/1/) ) 160 istatus = NF90_PUT_VAR( nrunid, nvarid(6), (/ zmax(6)/), (/kt/), (/1/) ) 142 161 IF( ln_zad_Aimp ) THEN 143 istatus = NF90_PUT_VAR( idrun, idw1, (/ zmax(8)/), (/kt/), (/1/) ) 144 istatus = NF90_PUT_VAR( idrun, idc1, (/ zmax(9)/), (/kt/), (/1/) ) 145 ENDIF 146 IF( MOD( kt , 100 ) == 0 ) istatus = NF90_SYNC(idrun) 147 IF( kt == nitend ) istatus = NF90_CLOSE(idrun) 162 istatus = NF90_PUT_VAR( nrunid, nvarid(7), (/ zmax(7)/), (/kt/), (/1/) ) 163 istatus = NF90_PUT_VAR( nrunid, nvarid(8), (/ zmax(8)/), (/kt/), (/1/) ) 164 ENDIF 165 IF( kt == nitend ) istatus = NF90_CLOSE(nrunid) 148 166 END IF 149 ! !== error handling ==! 150 IF( ( sn_cfctl%l_glochk .OR. lsomeoce ) .AND. ( & ! domain contains some ocean points, check for sensible ranges 151 & zmax(1) > 20._wp .OR. & ! too large sea surface height ( > 20 m ) 152 & zmax(2) > 10._wp .OR. & ! too large velocity ( > 10 m/s) 153 & zmax(3) >= 0._wp .OR. & ! negative or zero sea surface salinity 154 & zmax(4) >= 100._wp .OR. & ! too large sea surface salinity ( > 100 ) 155 & zmax(4) < 0._wp .OR. & ! too large sea surface salinity (keep this line for sea-ice) 156 & ISNAN( zmax(1) + zmax(2) + zmax(3) ) ) ) THEN ! NaN encounter in the tests 157 IF( lk_mpp .AND. sn_cfctl%l_glochk ) THEN 158 ! have use mpp_max (because sn_cfctl%l_glochk=.T. and distributed) 159 CALL mpp_maxloc( 'stpctl', ABS(ssh(:,:,Kmm)) , ssmask(:,:) , zzz, ih ) 160 CALL mpp_maxloc( 'stpctl', ABS(uu(:,:,:,Kmm)) , umask (:,:,:), zzz, iu ) 161 CALL mpp_minloc( 'stpctl', ts(:,:,:,jp_sal,Kmm), tmask (:,:,:), zzz, is1 ) 162 CALL mpp_maxloc( 'stpctl', ts(:,:,:,jp_sal,Kmm), tmask (:,:,:), zzz, is2 ) 163 ELSE 164 ! find local min and max locations 165 ih(:) = MAXLOC( ABS( ssh(:,:,Kmm) ) ) + (/ nimpp - 1, njmpp - 1 /) 166 iu(:) = MAXLOC( ABS( uu (:,:,:,Kmm) ) ) + (/ nimpp - 1, njmpp - 1, 0 /) 167 is1(:) = MINLOC( ts(:,:,:,jp_sal,Kmm), mask = tmask(:,:,:) == 1._wp ) + (/ nimpp - 1, njmpp - 1, 0 /) 168 is2(:) = MAXLOC( ts(:,:,:,jp_sal,Kmm), mask = tmask(:,:,:) == 1._wp ) + (/ nimpp - 1, njmpp - 1, 0 /) 169 ENDIF 170 167 ! !== error handling ==! 168 ! !== done by all processes at every time step ==! 169 ! 170 IF( zmax(1) > 20._wp .OR. & ! too large sea surface height ( > 20 m ) 171 & zmax(2) > 10._wp .OR. & ! too large velocity ( > 10 m/s) 172 & zmax(3) >= 0._wp .OR. & ! negative or zero sea surface salinity 173 & zmax(4) >= 100._wp .OR. & ! too large sea surface salinity ( > 100 ) 174 & zmax(4) < 0._wp .OR. & ! too large sea surface salinity (keep this line for sea-ice) 175 & ISNAN( zmax(1) + zmax(2) + zmax(3) ) ) THEN ! NaN encounter in the tests 176 ! 177 IF( ll_colruns ) THEN ! zmax is global, so it is the same on all subdomains -> no dead lock with mpp_maxloc 178 ! first: close the netcdf file, so we can read it 179 IF( lwm .AND. kt /= nitend ) istatus = NF90_CLOSE(nrunid) 180 ! get global loc on the min/max 181 CALL mpp_maxloc( 'stpctl', ABS(ssh(:,:, Kmm)), ssmask(:,: ), zzz, iloc(1:2,1) ) ! mpp_maxloc ok if mask = F 182 CALL mpp_maxloc( 'stpctl', ABS( uu(:,:,:, Kmm)), umask(:,:,:), zzz, iloc(1:3,2) ) 183 CALL mpp_minloc( 'stpctl', ts(:,:,:,jp_sal,Kmm) , tmask(:,:,:), zzz, iloc(1:3,3) ) 184 CALL mpp_maxloc( 'stpctl', ts(:,:,:,jp_sal,Kmm) , tmask(:,:,:), zzz, iloc(1:3,4) ) 185 ! find which subdomain has the max. 186 zarea(:) = 0._wp 187 DO ji = 1, 9 188 IF( zmaxlocal(ji) == zmax(ji) ) zarea(ji) = narea 189 END DO 190 CALL mpp_max( "stpctl", zarea ) ! max over the global domain 191 ELSE ! find local min and max locations: 192 ! if we are here, this means that the subdomain contains some oce points -> no need to test the mask used in maxloc 193 iloc(1:2,1) = MAXLOC( ABS( ssh(:,:, Kmm)), mask = ssmask(:,: ) == 1._wp ) + (/ nimpp - 1, njmpp - 1 /) 194 iloc(1:3,2) = MAXLOC( ABS( uu(:,:,:, Kmm)), mask = umask(:,:,:) == 1._wp ) + (/ nimpp - 1, njmpp - 1, 0 /) 195 iloc(1:3,3) = MINLOC( ts(:,:,:,jp_sal,Kmm) , mask = tmask(:,:,:) == 1._wp ) + (/ nimpp - 1, njmpp - 1, 0 /) 196 iloc(1:3,4) = MAXLOC( ts(:,:,:,jp_sal,Kmm) , mask = tmask(:,:,:) == 1._wp ) + (/ nimpp - 1, njmpp - 1, 0 /) 197 zarea(:) = narea ! this is local information 198 ENDIF 199 ! 171 200 WRITE(ctmp1,*) ' stp_ctl: |ssh| > 20 m or |U| > 10 m/s or S <= 0 or S >= 100 or NaN encounter in the tests' 172 WRITE(ctmp2,9100) kt, zmax(1), ih(1) , ih(2)173 WRITE(ctmp3,9200) kt, zmax(2), iu(1) , iu(2) , iu(3)174 WRITE(ctmp4,9 300) kt, - zmax(3), is1(1), is1(2), is1(3)175 WRITE(ctmp5,9 400) kt, zmax(4), is2(1), is2(2), is2(3)201 WRITE(ctmp2,9100) kt, ' |ssh| max ', zmax(1), iloc(1,1), iloc(2,1), NINT(zarea(1))-1 202 WRITE(ctmp3,9200) kt, ' |U| max ', zmax(2), iloc(1,2), iloc(2,2), iloc(3,2), NINT(zarea(2))-1 203 WRITE(ctmp4,9200) kt, ' Sal min ', -zmax(3), iloc(1,3), iloc(2,3), iloc(3,3), NINT(zarea(3))-1 204 WRITE(ctmp5,9200) kt, ' Sal max ', zmax(4), iloc(1,4), iloc(2,4), iloc(3,4), NINT(zarea(4))-1 176 205 WRITE(ctmp6,*) ' ===> output of last computed fields in output.abort.nc file' 177 206 ! 178 207 CALL dia_wri_state( Kmm, 'output.abort' ) ! create an output.abort file 179 180 IF( .NOT. sn_cfctl%l_glochk ) THEN 181 WRITE(ctmp8,*) 'E R R O R message from sub-domain: ', narea 182 CALL ctl_stop( 'STOP', ctmp1, ' ', ctmp8, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ctmp6 ) 183 ELSE 184 CALL ctl_stop( ctmp1, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ' ', ctmp6, ' ' ) 185 ENDIF 186 187 kindic = -3 188 ! 189 ENDIF 190 ! 191 9100 FORMAT (' kt=',i8,' |ssh| max: ',1pg11.4,', at i j : ',2i5) 192 9200 FORMAT (' kt=',i8,' |U| max: ',1pg11.4,', at i j k: ',3i5) 193 9300 FORMAT (' kt=',i8,' S min: ',1pg11.4,', at i j k: ',3i5) 194 9400 FORMAT (' kt=',i8,' S max: ',1pg11.4,', at i j k: ',3i5) 208 ! 209 IF( ll_colruns ) THEN ! all processes are synchronized -> use lwp to do the print in opened ocean.output files 210 IF(lwp) CALL ctl_stop( ctmp1, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ' ', ctmp6 ) 211 ELSE ! only mpi subdomains with errors are here -> STOP now 212 CALL ctl_stop( 'STOP', ctmp1, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ' ', ctmp6 ) 213 ENDIF 214 ! 215 IF( nstop == 0 ) nstop = 1 216 ! 217 ENDIF 218 ! 219 9100 FORMAT(' kt ',i8,a,1pg11.4,' at i j ',2i6, 6x,' MPI rank',i6) 220 9200 FORMAT(' kt ',i8,a,1pg11.4,' at i j k',2i6, i6,' MPI rank',i6) 195 221 9500 FORMAT(' it :', i8, ' |ssh|_max: ', D23.16, ' |U|_max: ', D23.16,' S_min: ', D23.16,' S_max: ', D23.16) 196 222 ! -
NEMO/branches/2020/r12581_ticket2418/src/OFF/nemogcm.F90
r12377 r12593 90 90 !! Madec, 2008, internal report, IPSL. 91 91 !!---------------------------------------------------------------------- 92 INTEGER :: istp , indic! time step index92 INTEGER :: istp ! time step index 93 93 !!---------------------------------------------------------------------- 94 94 … … 130 130 IF( .NOT.ln_linssh ) CALL dta_dyn_sf_interp( istp, Nnn ) ! calculate now grid parameters 131 131 #endif 132 CALL stp_ctl ( istp , indic )! Time loop: control and print132 CALL stp_ctl ( istp ) ! Time loop: control and print 133 133 istp = istp + 1 134 134 END DO … … 365 365 WRITE(numout,*) '~~~~~~~~' 366 366 WRITE(numout,*) ' Namelist namctl' 367 WRITE(numout,*) ' sn_cfctl%l_glochk = ', sn_cfctl%l_glochk368 367 WRITE(numout,*) ' sn_cfctl%l_allon = ', sn_cfctl%l_allon 369 368 WRITE(numout,*) ' finer control over o/p sn_cfctl%l_config = ', sn_cfctl%l_config … … 551 550 552 551 553 SUBROUTINE stp_ctl( kt , kindic)552 SUBROUTINE stp_ctl( kt ) 554 553 !!---------------------------------------------------------------------- 555 554 !! *** ROUTINE stp_ctl *** … … 562 561 !!---------------------------------------------------------------------- 563 562 INTEGER, INTENT(in ) :: kt ! ocean time-step index 564 INTEGER, INTENT(inout) :: kindic ! indicator of solver convergence565 563 !!---------------------------------------------------------------------- 566 564 ! -
NEMO/branches/2020/r12581_ticket2418/src/SAO/nemogcm.F90
r12377 r12593 263 263 WRITE(numout,*) '~~~~~~~~' 264 264 WRITE(numout,*) ' Namelist namctl' 265 WRITE(numout,*) ' sn_cfctl%l_glochk = ', sn_cfctl%l_glochk266 265 WRITE(numout,*) ' sn_cfctl%l_allon = ', sn_cfctl%l_allon 267 266 WRITE(numout,*) ' finer control over o/p sn_cfctl%l_config = ', sn_cfctl%l_config -
NEMO/branches/2020/r12581_ticket2418/src/SAS/diawri.F90
r12489 r12593 99 99 ! Output the initial state and forcings 100 100 IF( ninist == 1 ) THEN 101 CALL dia_wri_state( 'output.init', Kmm)101 CALL dia_wri_state( Kmm, 'output.init' ) 102 102 ninist = 0 103 103 ENDIF … … 126 126 END FUNCTION dia_wri_alloc_abl 127 127 128 SUBROUTINE dia_wri( kt )128 SUBROUTINE dia_wri( kt, Kmm ) 129 129 !!--------------------------------------------------------------------- 130 130 !! *** ROUTINE dia_wri *** … … 140 140 !! 141 141 INTEGER, INTENT( in ) :: kt ! ocean time-step index 142 INTEGER, INTENT( in ) :: Kmm ! ocean time levelindex 142 143 !! 143 144 LOGICAL :: ll_print = .FALSE. ! =T print and flush numout … … 154 155 ! Output the initial state and forcings 155 156 IF( ninist == 1 ) THEN 156 CALL dia_wri_state( 'output.init' )157 CALL dia_wri_state( Kmm, 'output.init' ) 157 158 ninist = 0 158 159 ENDIF … … 414 415 #endif 415 416 416 SUBROUTINE dia_wri_state( cdfile_name, Kmm)417 SUBROUTINE dia_wri_state( Kmm, cdfile_name ) 417 418 !!--------------------------------------------------------------------- 418 419 !! *** ROUTINE dia_wri_state *** … … 427 428 !! File 'output.abort.nc' is created in case of abnormal job end 428 429 !!---------------------------------------------------------------------- 430 INTEGER , INTENT( in ) :: Kmm ! ocean time levelindex 429 431 CHARACTER (len=* ), INTENT( in ) :: cdfile_name ! name of the file created 430 INTEGER , INTENT( in ) :: Kmm ! ocean time levelindex431 432 !! 432 433 INTEGER :: inum -
NEMO/branches/2020/r12581_ticket2418/src/SAS/nemogcm.F90
r12489 r12593 401 401 WRITE(numout,*) '~~~~~~~~' 402 402 WRITE(numout,*) ' Namelist namctl' 403 WRITE(numout,*) ' sn_cfctl%l_glochk = ', sn_cfctl%l_glochk404 403 WRITE(numout,*) ' sn_cfctl%l_allon = ', sn_cfctl%l_allon 405 404 WRITE(numout,*) ' finer control over o/p sn_cfctl%l_config = ', sn_cfctl%l_config -
NEMO/branches/2020/r12581_ticket2418/src/SAS/step.F90
r12377 r12593 74 74 !! -2- Outputs and diagnostics 75 75 !!---------------------------------------------------------------------- 76 INTEGER :: indic ! error indicator if < 077 !! ---------------------------------------------------------------------78 76 79 77 #if defined key_agrif 80 78 kstp = nit000 + Agrif_Nb_Step() 81 79 Kbb_a = Nbb; Kmm_a = Nnn; Krhs_a = Nrhs ! agrif_oce module copies of time level indices 82 IF 83 IF ( Agrif_Root() .and. lwp) Write(*,*) '---'84 IF (lwp) Write(*,*) 'Grid Number',Agrif_Fixed(),' time step ',kstp, 'int tstep',Agrif_NbStepint()80 IF( lk_agrif_debug ) THEN 81 IF( Agrif_Root() .and. lwp) WRITE(*,*) '---' 82 IF(lwp) WRITE(*,*) 'Grid Number', Agrif_Fixed(),' time step ', kstp, 'int tstep', Agrif_NbStepint() 85 83 ENDIF 86 87 IF ( kstp == (nit000 + 1) ) lk_agrif_fstep = .FALSE. 88 84 IF( kstp == nit000 + 1 ) lk_agrif_fstep = .FALSE. 89 85 # if defined key_iomput 90 86 IF( Agrif_Nbstepint() == 0 ) CALL iom_swap( cxios_context ) 91 87 # endif 92 88 #endif 93 indic = 0 ! although indic is not changed in stp_ctl94 ! need to keep the same interface95 89 IF( kstp == nit000 ) CALL iom_init( cxios_context ) ! iom_put initialization (must be done after nemo_init for AGRIF+XIOS+OASIS) 96 90 IF( kstp /= nit000 ) CALL day( kstp ) ! Calendar (day was already called at nit000 in day_init) … … 123 117 ! Control 124 118 !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 125 CALL stp_ctl( kstp, indic ) 126 IF( indic < 0 ) THEN 127 CALL ctl_stop( 'step: indic < 0' ) 128 CALL dia_wri_state( 'output.abort', Nnn ) 129 ENDIF 130 IF( kstp == nit000 ) CALL iom_close( numror ) ! close input ocean restart file 119 CALL stp_ctl( kstp, Nnn ) 120 121 IF( kstp == nit000 ) CALL iom_close( numror ) ! close input ocean restart file 131 122 132 123 !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 133 124 ! Coupled mode 134 125 !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 135 IF( lk_oasis )CALL sbc_cpl_snd( kstp, Nbb, Nnn ) ! coupled mode : field exchanges if OASIS-coupled ice126 IF( lk_oasis ) CALL sbc_cpl_snd( kstp, Nbb, Nnn ) ! coupled mode : field exchanges if OASIS-coupled ice 136 127 137 128 #if defined key_iomput … … 144 135 lrst_oce = .FALSE. 145 136 ENDIF 146 IF( kstp == nitend .OR. indic <0 ) THEN137 IF( kstp == nitend .OR. nstop > 0 ) THEN 147 138 CALL iom_context_finalize( cxios_context ) ! needed for XIOS+AGRIF 148 139 ENDIF -
NEMO/branches/2020/r12581_ticket2418/src/SAS/stpctl.F90
r12377 r12593 20 20 USE dom_oce ! ocean space and time domain variables 21 21 USE ice , ONLY : vt_i, u_ice, tm_i 22 USE diawri ! Standard run outputs (dia_wri_state routine) 22 23 ! 23 24 USE in_out_manager ! I/O manager … … 31 32 PUBLIC stp_ctl ! routine called by step.F90 32 33 33 INTEGER :: idrun, idtime, idssh, idu, ids, istatus34 LOGICAL :: lsomeoce34 INTEGER :: nrunid ! netcdf file id 35 INTEGER, DIMENSION(3) :: nvarid ! netcdf variable id 35 36 !!---------------------------------------------------------------------- 36 37 !! NEMO/SAS 4.0 , NEMO Consortium (2018) … … 38 39 !! Software governed by the CeCILL license (see ./LICENSE) 39 40 !!---------------------------------------------------------------------- 40 41 41 CONTAINS 42 42 43 SUBROUTINE stp_ctl( kt, kindic)43 SUBROUTINE stp_ctl( kt, Kmm ) 44 44 !!---------------------------------------------------------------------- 45 45 !! *** ROUTINE stp_ctl *** … … 49 49 !! ** Method : - Save the time step in numstp 50 50 !! - Print it each 50 time steps 51 !! - Stop the run IF problem encountered by setting nstop > 0 52 !! Problems checked: ice thickness maximum > 100 m 53 !! ice velocity maximum > 10 m/s 54 !! min ice temperature < -100 degC 51 55 !! 52 56 !! ** Actions : "time.step" file = last ocean time-step 53 57 !! "run.stat" file = run statistics 54 !! 58 !! nstop indicator sheared among all local domain 55 59 !!---------------------------------------------------------------------- 56 INTEGER, INTENT( in) :: kt ! ocean time-step index57 INTEGER, INTENT( inout ) :: kindic ! indicator of solver convergence60 INTEGER, INTENT(in ) :: kt ! ocean time-step index 61 INTEGER, INTENT(in ) :: Kmm ! ocean time level index 58 62 !! 59 REAL(wp), DIMENSION(3) :: zmax 60 LOGICAL :: ll_wrtstp, ll_colruns, ll_wrtruns 61 CHARACTER(len=20) :: clname 63 INTEGER :: ji ! dummy loop indices 64 INTEGER :: idtime, istatus 65 INTEGER, DIMENSION(2,3) :: iloc ! min/max loc indices 66 REAL(wp) :: zzz ! local real 67 REAL(wp), DIMENSION(4) :: zmax, zmaxlocal, zarea 68 LOGICAL :: ll_wrtstp, ll_colruns, ll_wrtruns 69 LOGICAL, DIMENSION(jpi,jpj) :: llmsk 70 CHARACTER(len=20) :: clname 62 71 !!---------------------------------------------------------------------- 63 72 ! 64 ll_wrtstp = ( MOD( kt , sn_cfctl%ptimincr ) == 0 ) .OR. ( kt == nitend )65 ll_colruns = ll_wrtstp .AND. ( sn_cfctl%l_runstat )73 ll_wrtstp = ( MOD( kt-nit000, sn_cfctl%ptimincr ) == 0 ) .OR. ( kt == nitend ) 74 ll_colruns = ll_wrtstp .AND. sn_cfctl%l_runstat 66 75 ll_wrtruns = ll_colruns .AND. lwm 67 IF( kt == nit000 .AND. lwp ) THEN 68 WRITE(numout,*) 69 WRITE(numout,*) 'stp_ctl : time-stepping control' 70 WRITE(numout,*) '~~~~~~~' 71 ! ! open time.step file 72 IF( lwm ) CALL ctl_opn( numstp, 'time.step', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 73 ! ! open run.stat file(s) at start whatever 74 ! ! the value of sn_cfctl%ptimincr 75 IF( lwm .AND. ( sn_cfctl%l_runstat ) ) THEN 76 ! 77 IF( kt == nit000 ) THEN 78 ! 79 IF( lwp ) THEN 80 WRITE(numout,*) 81 WRITE(numout,*) 'stp_ctl : time-stepping control' 82 WRITE(numout,*) '~~~~~~~' 83 ENDIF 84 ! ! open time.step ascii file, done only by 1st subdomain 85 IF( lwm ) CALL ctl_opn( numstp, 'time.step', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 86 ! 87 IF( ll_wrtruns ) THEN 88 ! ! open run.stat ascii file, done only by 1st subdomain 76 89 CALL ctl_opn( numrun, 'run.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 90 ! ! open run.stat.nc netcdf file, done only by 1st subdomain 77 91 clname = 'run.stat.nc' 78 92 IF( .NOT. Agrif_Root() ) clname = TRIM(Agrif_CFixed())//"_"//TRIM(clname) 79 istatus = NF90_CREATE( 'run.stat.nc', NF90_CLOBBER, idrun)80 istatus = NF90_DEF_DIM( idrun, 'time' , NF90_UNLIMITED, idtime )81 istatus = NF90_DEF_VAR( idrun, 'vt_i_max' , NF90_DOUBLE, (/ idtime /), idssh)82 istatus = NF90_DEF_VAR( idrun, 'abs_u_max', NF90_DOUBLE, (/ idtime /), idu)83 istatus = NF90_DEF_VAR( idrun, 'tm_i_min' , NF90_DOUBLE, (/ idtime /), ids)84 istatus = NF90_ENDDEF( idrun)93 istatus = NF90_CREATE( TRIM(clname), NF90_CLOBBER, nrunid ) 94 istatus = NF90_DEF_DIM( nrunid, 'time' , NF90_UNLIMITED, idtime ) 95 istatus = NF90_DEF_VAR( nrunid, 'vt_i_max' , NF90_DOUBLE, (/ idtime /), nvarid(1) ) 96 istatus = NF90_DEF_VAR( nrunid, 'abs_u_max', NF90_DOUBLE, (/ idtime /), nvarid(2) ) 97 istatus = NF90_DEF_VAR( nrunid, 'tm_i_min' , NF90_DOUBLE, (/ idtime /), nvarid(3) ) 98 istatus = NF90_ENDDEF(nrunid) 85 99 ENDIF 100 ! 86 101 ENDIF 87 IF( kt == nit000 ) lsomeoce = COUNT( ssmask(:,:) == 1._wp ) > 088 102 ! 89 IF(lwm .AND. ll_wrtstp) THEN !== current time step ==! ("time.step" file) 103 ! !== write current time step ==! 104 ! !== done only by 1st subdomain at writting timestep ==! 105 IF( lwm .AND. ll_wrtstp ) THEN 90 106 WRITE ( numstp, '(1x, i8)' ) kt 91 107 REWIND( numstp ) 92 108 ENDIF 93 ! !== test of extrema ==! 109 ! !== test of local extrema ==! 110 ! !== done by all processes at every time step ==! 111 llmsk(:,:) = tmask(:,:,1) == 1._wp 112 zmax(1) = MAXVAL( vt_i (:,:) , mask = llmsk ) ! max ice thickness 113 zmax(2) = MAXVAL( ABS( u_ice(:,:) ) , mask = llmsk ) ! max ice velocity (zonal only) 114 zmax(3) = MAXVAL( -tm_i (:,:) + 273.15_wp, mask = llmsk ) ! min ice temperature 115 zmax(4) = REAL( nstop, wp ) ! stop indicator 116 ! !== get global extrema ==! 117 ! !== done by all processes if writting run.stat ==! 94 118 IF( ll_colruns ) THEN 95 zmax(1) = MAXVAL( vt_i (:,:) ) ! max ice thickness 96 zmax(2) = MAXVAL( ABS( u_ice(:,:) ) ) ! max ice velocity (zonal only) 97 zmax(3) = MAXVAL( -tm_i (:,:)+273.15_wp , mask = ssmask(:,:) == 1._wp ) ! min ice temperature 98 CALL mpp_max( "stpctl", zmax ) ! max over the global domain 119 zmaxlocal(:) = zmax(:) 120 CALL mpp_max( "stpctl", zmax ) ! max over the global domain 121 nstop = NINT( zmax(9) ) ! update nstop indicator (now sheared among all local domains) 122 ENDIF 123 ! !== write "run.stat" files ==! 124 ! !== done only by 1st subdomain at writting timestep ==! 125 IF( ll_wrtruns ) THEN 126 WRITE(numrun,9500) kt, zmax(1), zmax(2), -zmax(3) 127 istatus = NF90_PUT_VAR( nrunid, nvarid(1), (/ zmax(1)/), (/kt/), (/1/) ) 128 istatus = NF90_PUT_VAR( nrunid, nvarid(2), (/ zmax(2)/), (/kt/), (/1/) ) 129 istatus = NF90_PUT_VAR( nrunid, nvarid(3), (/-zmax(3)/), (/kt/), (/1/) ) 130 IF( kt == nitend ) istatus = NF90_CLOSE(nrunid) 99 131 END IF 100 ! !== run statistics ==! ("run.stat" file) 101 IF( ll_wrtruns ) THEN 102 WRITE(numrun,9500) kt, zmax(1), zmax(2), - zmax(3) 103 istatus = NF90_PUT_VAR( idrun, idssh, (/ zmax(1)/), (/kt/), (/1/) ) 104 istatus = NF90_PUT_VAR( idrun, idu, (/ zmax(2)/), (/kt/), (/1/) ) 105 istatus = NF90_PUT_VAR( idrun, ids, (/-zmax(3)/), (/kt/), (/1/) ) 106 IF( MOD( kt , 100 ) == 0 ) istatus = NF90_SYNC(idrun) 107 IF( kt == nitend ) istatus = NF90_CLOSE(idrun) 108 END IF 132 ! !== error handling ==! 133 ! !== done by all processes at every time step ==! 109 134 ! 135 IF( zmax(1) > 100._wp .OR. & ! too large ice thickness maximum ( > 100 m) 136 & zmax(2) > 10._wp .OR. & ! too large ice velocity ( > 10 m/s) 137 & zmax(3) > 101._wp .OR. & ! too cold ice temperature ( < -100 degC) 138 & ISNAN( zmax(1) + zmax(2) + zmax(3) ) ) THEN ! NaN encounter in the tests 139 ! 140 IF( ll_colruns ) THEN ! zmax is global, so it is the same on all subdomains -> no dead lock with mpp_maxloc 141 ! first: close the netcdf file, so we can read it 142 IF( lwm .AND. kt /= nitend ) istatus = NF90_CLOSE(nrunid) 143 ! get global loc on the min/max 144 CALL mpp_maxloc( 'stpctl', vt_i(:,:) , tmask(:,:,1), zzz, iloc(1:2,1) ) ! mpp_maxloc ok if mask = F 145 CALL mpp_maxloc( 'stpctl',ABS( u_ice(:,:) ) , tmask(:,:,1), zzz, iloc(1:2,2) ) 146 CALL mpp_minloc( 'stpctl', tm_i(:,:) - 273.15_wp, tmask(:,:,1), zzz, iloc(1:2,3) ) 147 ! find which subdomain has the max. 148 zarea(:) = 0._wp 149 DO ji = 1, 4 150 IF( zmaxlocal(ji) == zmax(ji) ) zarea(ji) = narea 151 END DO 152 CALL mpp_max( "stpctl", zarea ) ! max over the global domain 153 ELSE ! find local min and max locations: 154 ! if we are here, this means that the subdomain contains some oce points -> no need to test the mask used in maxloc 155 iloc(1:2,1) = MAXLOC( vt_i(:,:) , mask = llmsk ) + (/ nimpp - 1, njmpp - 1/) 156 iloc(1:2,2) = MAXLOC( ABS( u_ice(:,:) ) , mask = llmsk ) + (/ nimpp - 1, njmpp - 1/) 157 iloc(1:2,3) = MINLOC( tm_i(:,:) - 273.15_wp, mask = llmsk ) + (/ nimpp - 1, njmpp - 1/) 158 zarea(:) = narea ! this is local information 159 ENDIF 160 ! 161 WRITE(ctmp1,*) ' stp_ctl: ice_thick > 100 m or |ice_vel| > 10 m/s or ice_temp < -100 degC or NaN encounter in the tests' 162 WRITE(ctmp2,9100) kt, ' ice_thick max', zmax(1), iloc(1,1), iloc(2,1), NINT(zarea(1))-1 163 WRITE(ctmp3,9100) kt, ' |ice_vel| max', zmax(2), iloc(1,2), iloc(2,3), NINT(zarea(2))-1 164 WRITE(ctmp4,9100) kt, ' ice_temp min', -zmax(3), iloc(1,2), iloc(2,3), NINT(zarea(3))-1 165 WRITE(ctmp6,*) ' ===> output of last computed fields in output.abort.nc file' 166 ! 167 CALL dia_wri_state( Kmm, 'output.abort' ) ! create an output.abort file 168 ! 169 IF( ll_colruns ) THEN ! all processes are synchronized -> use lwp to do the print in opened ocean.output files 170 IF(lwp) CALL ctl_stop( ctmp1, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ' ', ctmp6 ) 171 ELSE ! only mpi subdomains with errors are here -> STOP now 172 CALL ctl_stop( 'STOP', ctmp1, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ' ', ctmp6 ) 173 ENDIF 174 ! 175 IF( nstop == 0 ) nstop = 1 176 ! 177 ENDIF 178 ! 179 9100 FORMAT(' kt ',i8,a,1pg11.4,' at i j',2i6,' MPI rank',i6) 110 180 9500 FORMAT(' it :', i8, ' vt_i_max: ', D23.16, ' |u|_max: ', D23.16,' tm_i_min: ', D23.16) 111 181 ! -
NEMO/branches/2020/r12581_ticket2418/tests/STATION_ASF/MY_SRC/nemogcm.F90
r12254 r12593 311 311 WRITE(numout,*) '~~~~~~~~' 312 312 WRITE(numout,*) ' Namelist namctl' 313 WRITE(numout,*) ' sn_cfctl%l_glochk = ', sn_cfctl%l_glochk314 313 WRITE(numout,*) ' sn_cfctl%l_allon = ', sn_cfctl%l_allon 315 314 WRITE(numout,*) ' finer control over o/p sn_cfctl%l_config = ', sn_cfctl%l_config -
NEMO/branches/2020/r12581_ticket2418/tests/STATION_ASF/MY_SRC/step_c1d.F90
r12249 r12593 75 75 ! Control and restarts 76 76 !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 77 CALL stp_ctl( kstp, Nbb, Nnn , indic)77 CALL stp_ctl( kstp, Nbb, Nnn ) 78 78 IF( kstp == nit000 ) CALL iom_close( numror ) ! close input ocean restart file 79 79 IF( lrst_oce ) CALL rst_write( kstp, Nbb, Nnn ) ! write output ocean restart file 80 80 ! 81 81 #if defined key_iomput 82 IF( kstp == nitend .OR. indic <0 ) CALL xios_context_finalize() ! needed for XIOS82 IF( kstp == nitend .OR. nstop > 0 ) CALL xios_context_finalize() ! needed for XIOS 83 83 ! 84 84 #endif -
NEMO/branches/2020/r12581_ticket2418/tests/STATION_ASF/MY_SRC/stpctl.F90
r12254 r12593 31 31 PUBLIC stp_ctl ! routine called by step.F90 32 32 33 INTEGER :: idrun, idtime, idtau, idqns, idemp, istatus 34 LOGICAL :: lsomeoce 33 INTEGER :: nrunid, ntauid, nqnsid, nempid 35 34 !!---------------------------------------------------------------------- 36 35 !! NEMO/SAS 4.0 , NEMO Consortium (2018) … … 40 39 CONTAINS 41 40 42 SUBROUTINE stp_ctl( kt, Kbb, Kmm , kindic)41 SUBROUTINE stp_ctl( kt, Kbb, Kmm ) 43 42 !!---------------------------------------------------------------------- 44 43 !! *** ROUTINE stp_ctl *** … … 56 55 INTEGER, INTENT(in ) :: kt ! ocean time-step index 57 56 INTEGER, INTENT(in ) :: Kbb, Kmm ! ocean time level index 58 INTEGER, INTENT(inout) :: kindic ! error indicator59 57 !! 58 INTEGER :: idtime, istatus 60 59 REAL(wp), DIMENSION(3) :: zmax 61 60 LOGICAL :: ll_wrtstp, ll_colruns, ll_wrtruns 61 LOGICAL, DIMENSION(jpi,jpj) :: llmsk 62 62 CHARACTER(len=20) :: clname 63 63 !!---------------------------------------------------------------------- 64 64 ! 65 ll_wrtstp = ( MOD( kt , sn_cfctl%ptimincr ) == 0 ) .OR. ( kt == nitend )66 ll_colruns = ll_wrtstp .AND. ( sn_cfctl%l_runstat )65 ll_wrtstp = ( MOD( kt-nit000, sn_cfctl%ptimincr ) == 0 ) .OR. ( kt == nitend ) 66 ll_colruns = ll_wrtstp .AND. sn_cfctl%l_runstat 67 67 ll_wrtruns = ll_colruns .AND. lwm 68 IF( kt == nit000 .AND. lwp ) THEN 69 WRITE(numout,*) 70 WRITE(numout,*) 'stp_ctl : time-stepping control' 71 WRITE(numout,*) '~~~~~~~' 72 ! ! open time.step file 73 IF( lwm ) CALL ctl_opn( numstp, 'time.step', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 74 ! ! open run.stat file(s) at start whatever 75 ! ! the value of sn_cfctl%ptimincr 76 IF( lwm .AND. ( sn_cfctl%l_runstat ) ) THEN 68 ! 69 IF( kt == nit000 ) THEN 70 ! 71 IF( lwp ) THEN 72 WRITE(numout,*) 73 WRITE(numout,*) 'stp_ctl : time-stepping control' 74 WRITE(numout,*) '~~~~~~~' 75 ENDIF 76 ! ! open time.step ascii file, done only by 1st subdomain 77 IF( lwm ) CALL ctl_opn( numstp, 'time.step', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 78 ! 79 IF( ll_wrtruns ) THEN 80 ! ! open run.stat ascii file, done only by 1st subdomain 77 81 CALL ctl_opn( numrun, 'run.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 82 ! ! open run.stat.nc netcdf file, done only by 1st subdomain 78 83 clname = 'run.stat.nc' 79 84 IF( .NOT. Agrif_Root() ) clname = TRIM(Agrif_CFixed())//"_"//TRIM(clname) 80 istatus = NF90_CREATE( TRIM(clname), NF90_CLOBBER, idrun)81 istatus = NF90_DEF_DIM( idrun, 'time', NF90_UNLIMITED, idtime )82 istatus = NF90_DEF_VAR( idrun, 'tau_max', NF90_DOUBLE, (/ idtime /), idtau)83 istatus = NF90_DEF_VAR( idrun, 'qns_max', NF90_DOUBLE, (/ idtime /), idqns)84 istatus = NF90_DEF_VAR( idrun, 'emp_max', NF90_DOUBLE, (/ idtime /), idemp)85 istatus = NF90_ENDDEF( idrun)85 istatus = NF90_CREATE( TRIM(clname), NF90_CLOBBER, nrunid ) 86 istatus = NF90_DEF_DIM( nrunid, 'time', NF90_UNLIMITED, idtime ) 87 istatus = NF90_DEF_VAR( nrunid, 'tau_max', NF90_DOUBLE, (/ idtime /), ntauid ) 88 istatus = NF90_DEF_VAR( nrunid, 'qns_max', NF90_DOUBLE, (/ idtime /), nqnsid ) 89 istatus = NF90_DEF_VAR( nrunid, 'emp_max', NF90_DOUBLE, (/ idtime /), nempid ) 90 istatus = NF90_ENDDEF(nrunid) 86 91 ENDIF 92 ! 87 93 ENDIF 88 IF( kt == nit000 ) lsomeoce = COUNT( ssmask(:,:) == 1._wp ) > 089 94 ! 90 IF(lwm .AND. ll_wrtstp) THEN !== current time step ==! ("time.step" file) 95 ! !== write current time step ==! 96 ! !== done only by 1st subdomain at writting timestep ==! 97 IF( lwm .AND. ll_wrtstp ) THEN 91 98 WRITE ( numstp, '(1x, i8)' ) kt 92 99 REWIND( numstp ) 93 100 ENDIF 94 ! 95 ! !== test of extrema ==! 96 zmax(1) = MAXVAL( taum(:,:) , mask = tmask(:,:,1) == 1._wp ) ! max wind stress module 97 zmax(2) = MAXVAL( ABS( qns(:,:) ) , mask = tmask(:,:,1) == 1._wp ) ! max non-solar heat flux 98 zmax(3) = MAXVAL( ABS( emp(:,:) ) , mask = tmask(:,:,1) == 1._wp ) ! max E-P 101 ! !== test of local extrema ==! 102 ! !== done by all processes at every time step ==! 103 llmsk(:,:) = tmask(:,:,1) == 1._wp 104 zmax(1) = MAXVAL( taum(:,:) , mask = llmsk ) ! max wind stress module 105 zmax(2) = MAXVAL( ABS( qns(:,:) ) , mask = llmsk ) ! max non-solar heat flux 106 zmax(3) = MAXVAL( ABS( emp(:,:) ) , mask = llmsk ) ! max E-P 99 107 ! 100 108 IF( ll_colruns ) THEN … … 105 113 IF( ll_wrtruns ) THEN 106 114 WRITE(numrun,9500) kt, zmax(1), zmax(2), zmax(3) 107 istatus = NF90_PUT_VAR( idrun, idtau, (/ zmax(1)/), (/kt/), (/1/) )108 istatus = NF90_PUT_VAR( idrun, idqns, (/ zmax(2)/), (/kt/), (/1/) )109 istatus = NF90_PUT_VAR( idrun, idemp, (/ zmax(3)/), (/kt/), (/1/) )110 IF( MOD( kt , 100 ) == 0 ) istatus = NF90_SYNC( idrun)111 IF( kt == nitend ) istatus = NF90_CLOSE( idrun)115 istatus = NF90_PUT_VAR( nrunid, ntauid, (/ zmax(1)/), (/kt/), (/1/) ) 116 istatus = NF90_PUT_VAR( nrunid, nqnsid, (/ zmax(2)/), (/kt/), (/1/) ) 117 istatus = NF90_PUT_VAR( nrunid, nempid, (/ zmax(3)/), (/kt/), (/1/) ) 118 IF( MOD( kt , 100 ) == 0 ) istatus = NF90_SYNC(nrunid) 119 IF( kt == nitend ) istatus = NF90_CLOSE(nrunid) 112 120 END IF 113 121 ! !== error handling ==!
Note: See TracChangeset
for help on using the changeset viewer.