Changeset 14318
- Timestamp:
- 2021-01-20T11:49:35+01:00 (4 years ago)
- Location:
- NEMO/trunk
- Files:
-
- 1 added
- 6 edited
Legend:
- Unmodified
- Added
- Removed
-
NEMO/trunk/src/OCE/stpctl.F90
r14143 r14318 15 15 !!---------------------------------------------------------------------- 16 16 !! stp_ctl : Control the run 17 !! stp_ctl_SWE : Control the run (SWE only)18 17 !!---------------------------------------------------------------------- 19 18 USE oce ! ocean dynamics and tracers variables … … 34 33 35 34 PUBLIC stp_ctl ! routine called by step.F90 36 PUBLIC stp_ctl_SWE ! routine called by stpmlf.F90 37 38 INTEGER :: nrunid ! netcdf file id 39 INTEGER, DIMENSION(8) :: nvarid ! netcdf variable id 40 INTEGER, DIMENSION(2) :: nvarid_SWE ! netcdf variable id (SWE only) 35 36 INTEGER, PARAMETER :: jpvar = 8 37 INTEGER :: nrunid ! netcdf file id 38 INTEGER, DIMENSION(jpvar) :: nvarid ! netcdf variable id 41 39 !!---------------------------------------------------------------------- 42 40 !! NEMO/OCE 4.0 , NEMO Consortium (2018) … … 49 47 !!---------------------------------------------------------------------- 50 48 !! *** ROUTINE stp_ctl *** 51 !! 49 !! 52 50 !! ** Purpose : Control the run 53 51 !! … … 65 63 INTEGER, INTENT(in ) :: Kmm ! ocean time level index 66 64 !! 65 INTEGER, PARAMETER :: jptst = 4 67 66 INTEGER :: ji ! dummy loop indices 68 67 INTEGER :: idtime, istatus 69 INTEGER , DIMENSION( 9):: iareasum, iareamin, iareamax70 INTEGER , DIMENSION(3, 4):: iloc ! min/max loc indices68 INTEGER , DIMENSION(jptst) :: iareasum, iareamin, iareamax 69 INTEGER , DIMENSION(3,jptst) :: iloc ! min/max loc indices 71 70 REAL(wp) :: zzz, zminsal, zmaxsal ! local real 72 REAL(wp), DIMENSION(9) :: zmax, zmaxlocal 71 REAL(wp), DIMENSION(jpvar+1) :: zmax 72 REAL(wp), DIMENSION(jptst) :: zmaxlocal 73 73 LOGICAL :: ll_wrtstp, ll_colruns, ll_wrtruns, ll_0oce 74 74 LOGICAL, DIMENSION(jpi,jpj,jpk) :: llmsk … … 78 78 ! 79 79 ll_wrtstp = ( MOD( kt-nit000, sn_cfctl%ptimincr ) == 0 ) .OR. ( kt == nitend ) 80 ll_colruns = ll_wrtstp .AND. sn_cfctl%l_runstat .AND. jpnij > 1 80 ll_colruns = ll_wrtstp .AND. sn_cfctl%l_runstat .AND. jpnij > 1 81 81 ll_wrtruns = ( ll_colruns .OR. jpnij == 1 ) .AND. lwm 82 82 ! … … 111 111 istatus = NF90_ENDDEF(nrunid) 112 112 ENDIF 113 ! 113 ! 114 114 ENDIF 115 115 ! … … 155 155 zmax(5:8) = 0._wp 156 156 ENDIF 157 zmax( 9) = REAL( nstop, wp )! stop indicator157 zmax(jpvar+1) = REAL( nstop, wp ) ! stop indicator 158 158 ! 159 159 ! !== get global extrema ==! 160 160 ! !== done by all processes if writting run.stat ==! 161 161 IF( ll_colruns ) THEN 162 zmaxlocal(:) = zmax( :)162 zmaxlocal(:) = zmax(1:jptst) 163 163 CALL mpp_max( "stpctl", zmax ) ! max over the global domain: ok even of ll_0oce = .true. 164 nstop = NINT( zmax( 9) )! update nstop indicator (now sheared among all local domains)164 nstop = NINT( zmax(jpvar+1) ) ! update nstop indicator (now sheared among all local domains) 165 165 ELSE 166 166 ! if no ocean point: MAXVAL returns -HUGE => we must overwrite this value to avoid error handling bellow. 167 IF( ll_0oce ) zmax(1:4) = (/ 0._wp, 0._wp, -1._wp, 1._wp /) ! default "valid" values... 168 ENDIF 169 ! 170 zmax(3) = -zmax(3) ! move back from max(-zz) to min(zz) : easier to manage! 171 zmax(5) = -zmax(5) ! move back from max(-zz) to min(zz) : easier to manage! 172 IF( ll_colruns ) THEN 173 zmaxlocal(3) = -zmaxlocal(3) ! move back from max(-zz) to min(zz) : easier to manage! 174 zmaxlocal(5) = -zmaxlocal(5) ! move back from max(-zz) to min(zz) : easier to manage! 175 ENDIF 167 IF( ll_0oce ) zmax(1:jptst) = (/ 0._wp, 0._wp, -1._wp, 1._wp /) ! default "valid" values... 168 ENDIF 169 ! 170 zmax(3) = -zmax(3) ! move back from max(-zz) to min(zz) : easier to manage! 171 zmax(5) = -zmax(5) ! move back from max(-zz) to min(zz) : easier to manage! 172 IF( ll_colruns ) zmaxlocal(3) = -zmaxlocal(3) ! move back from max(-zz) to min(zz) : easier to manage! 176 173 ! 177 174 ! !== write "run.stat" files ==! 178 175 ! !== done only by 1st subdomain at writting timestep ==! 179 176 IF( ll_wrtruns ) THEN 180 WRITE(numrun,9500) kt, zmax(1 ), zmax(2), zmax(3), zmax(4)181 DO ji = 1, 6 + 2 * COUNT((/ln_zad_Aimp/) )177 WRITE(numrun,9500) kt, zmax(1:jptst) 178 DO ji = 1, jpvar - 2 * COUNT( .NOT. (/ln_zad_Aimp/) ) 182 179 istatus = NF90_PUT_VAR( nrunid, nvarid(ji), (/zmax(ji)/), (/kt/), (/1/) ) 183 180 END DO … … 188 185 ! 189 186 IF ( ln_SEOS.AND.(rn_b0==0._wp) ) THEN ! Discard checks on salinity 190 zmaxsal = +1.e38! if not used in eos191 zminsal = - 1.e38187 zmaxsal = HUGE(1._wp) ! if not used in eos 188 zminsal = -HUGE(1._wp) 192 189 ELSE 193 190 zmaxsal = 100._wp … … 195 192 ENDIF 196 193 ! 197 IF( zmax(1) > 20._wp .OR. & ! too large sea surface height ( > 20 m )198 & zmax(2) > 10._wp .OR. & ! too large velocity ( > 10 m/s)199 & zmax(3) <= zminsal .OR. & ! negative or zero sea surface salinity200 & zmax(4) >= zmaxsal .OR. & ! too large sea surface salinity ( > 100 )201 & zmax(4) < zminsal .OR. & ! too large sea surface salinity (keep this line for sea-ice)202 & ISNAN( zmax(1) + zmax(2) + zmax(3) ) .OR. & ! NaN encounter in the tests203 & ABS( zmax(1) + zmax(2) + zmax(3) ) > HUGE(1._wp) ) THEN ! Infinity encounter in the tests194 IF( zmax(1) > 20._wp .OR. & ! too large sea surface height ( > 20 m ) 195 & zmax(2) > 10._wp .OR. & ! too large velocity ( > 10 m/s) 196 & zmax(3) <= zminsal .OR. & ! negative or zero sea surface salinity 197 & zmax(4) >= zmaxsal .OR. & ! too large sea surface salinity ( > 100 ) 198 & zmax(4) < zminsal .OR. & ! too large sea surface salinity (keep this line for sea-ice) 199 & ISNAN( SUM(zmax(1:jptst)) ) .OR. & ! NaN encounter in the tests 200 & ABS( SUM(zmax(1:jptst)) ) > HUGE(1._wp) ) THEN ! Infinity encounter in the tests 204 201 ! 205 202 iloc(:,:) = 0 … … 217 214 ! find which subdomain has the max. 218 215 iareamin(:) = jpnij+1 ; iareamax(:) = 0 ; iareasum(:) = 0 219 DO ji = 1, 9216 DO ji = 1, jptst 220 217 IF( zmaxlocal(ji) == zmax(ji) ) THEN 221 218 iareamin(ji) = narea ; iareamax(ji) = narea ; iareasum(ji) = 1 … … 234 231 iloc(1:3,3) = MINLOC( ts(:,:,:,jp_sal,Kmm) , mask = llmsk(:,:,:) ) 235 232 iloc(1:3,4) = MAXLOC( ts(:,:,:,jp_sal,Kmm) , mask = llmsk(:,:,:) ) 236 DO ji = 1, 4! local domain indices ==> global domain indices, excluding halos233 DO ji = 1, jptst ! local domain indices ==> global domain indices, excluding halos 237 234 iloc(1:2,ji) = (/ mig0(iloc(1,ji)), mjg0(iloc(2,ji)) /) 238 235 END DO … … 253 250 CALL dia_wri_state( Kmm, 'output.abort' ) ! create an output.abort file 254 251 ! 255 IF( ll_colruns . or. jpnij == 1 ) THEN ! all processes synchronized -> use lwp to print in opened ocean.output files252 IF( ll_colruns .OR. jpnij == 1 ) THEN ! all processes synchronized -> use lwp to print in opened ocean.output files 256 253 IF(lwp) THEN ; CALL ctl_stop( ctmp1, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ' ', ctmp6 ) 257 254 ELSE ; nstop = MAX(1, nstop) ! make sure nstop > 0 (automatically done when calling ctl_stop) … … 271 268 ! 272 269 END SUBROUTINE stp_ctl 273 274 275 SUBROUTINE stp_ctl_SWE( kt, Kmm )276 !!----------------------------------------------------------------------277 !! *** ROUTINE stp_ctl_SWE ***278 !!279 !! ** Purpose : Control the run280 !!281 !! ** Method : - Save the time step in numstp282 !! - Print it each 50 time steps283 !! - Stop the run IF problem encountered by setting nstop > 0284 !! Problems checked: e3t0+ssh minimum smaller that 0285 !! |U| maximum larger than 10 m/s286 !! ( not for SWE : negative sea surface salinity )287 !!288 !! ** Actions : "time.step" file = last ocean time-step289 !! "run.stat" file = run statistics290 !! nstop indicator sheared among all local domain291 !!----------------------------------------------------------------------292 INTEGER, INTENT(in ) :: kt ! ocean time-step index293 INTEGER, INTENT(in ) :: Kmm ! ocean time level index294 !!295 INTEGER :: ji ! dummy loop indices296 INTEGER :: idtime, istatus297 INTEGER , DIMENSION(3) :: iareasum, iareamin, iareamax298 INTEGER , DIMENSION(3,4) :: iloc ! min/max loc indices299 REAL(wp) :: zzz ! local real300 REAL(wp), DIMENSION(3) :: zmax, zmaxlocal301 LOGICAL :: ll_wrtstp, ll_colruns, ll_wrtruns, ll_0oce302 LOGICAL, DIMENSION(jpi,jpj,jpk) :: llmsk303 CHARACTER(len=20) :: clname304 !!----------------------------------------------------------------------305 !306 IF( nstop > 0 .AND. ngrdstop > -1 ) RETURN ! stpctl was already called by a child grid307 !308 ll_wrtstp = ( MOD( kt-nit000, sn_cfctl%ptimincr ) == 0 ) .OR. ( kt == nitend )309 ll_colruns = ll_wrtstp .AND. sn_cfctl%l_runstat .AND. jpnij > 1310 ll_wrtruns = ( ll_colruns .OR. jpnij == 1 ) .AND. lwm311 !312 IF( kt == nit000 ) THEN313 !314 IF( lwp ) THEN315 WRITE(numout,*)316 WRITE(numout,*) 'stp_ctl_SWE : time-stepping control'317 WRITE(numout,*) '~~~~~~~~~~~'318 ENDIF319 ! ! open time.step ascii file, done only by 1st subdomain320 IF( lwm ) CALL ctl_opn( numstp, 'time.step', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea )321 !322 IF( ll_wrtruns ) THEN323 ! ! open run.stat ascii file, done only by 1st subdomain324 CALL ctl_opn( numrun, 'run.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea )325 ! ! open run.stat.nc netcdf file, done only by 1st subdomain326 clname = 'run.stat.nc'327 IF( .NOT. Agrif_Root() ) clname = TRIM(Agrif_CFixed())//"_"//TRIM(clname)328 istatus = NF90_CREATE( TRIM(clname), NF90_CLOBBER, nrunid )329 istatus = NF90_DEF_DIM( nrunid, 'time', NF90_UNLIMITED, idtime )330 istatus = NF90_DEF_VAR( nrunid, 'abs_ssh_max', NF90_DOUBLE, (/ idtime /), nvarid_SWE(1) )331 istatus = NF90_DEF_VAR( nrunid, 'abs_u_max', NF90_DOUBLE, (/ idtime /), nvarid_SWE(2) )332 istatus = NF90_ENDDEF(nrunid)333 ENDIF334 !335 ENDIF336 !337 ! !== write current time step ==!338 ! !== done only by 1st subdomain at writting timestep ==!339 IF( lwm .AND. ll_wrtstp ) THEN340 WRITE ( numstp, '(1x, i8)' ) kt341 REWIND( numstp )342 ENDIF343 ! !== test of local extrema ==!344 ! !== done by all processes at every time step ==!345 !346 llmsk( 1:Nis1,:,:) = .FALSE. ! exclude halos from the checked region347 llmsk(Nie1: jpi,:,:) = .FALSE.348 llmsk(:, 1:Njs1,:) = .FALSE.349 llmsk(:,Nje1: jpj,:) = .FALSE.350 !351 llmsk(Nis0:Nie0,Njs0:Nje0,1) = ssmask(Nis0:Nie0,Njs0:Nje0) == 1._wp ! define only the inner domain352 !353 ll_0oce = .NOT. ANY( llmsk(:,:,1) ) ! no ocean point in the inner domain?354 !355 zmax(1) = MINVAL( -e3t_0(:,:,1)-ssh(:,:,Kmm) , mask = llmsk(:,:,1) ) ! e3t_Kmm min356 !357 llmsk(Nis0:Nie0,Njs0:Nje0,:) = umask(Nis0:Nie0,Njs0:Nje0,:) == 1._wp ! define only the inner domain358 zmax(2) = MAXVAL( ABS( uu(:,:,:,Kmm) ) , mask = llmsk(:,:,:) ) ! velocity max (zonal only)359 zmax(3) = REAL( nstop , wp ) ! stop indicator360 361 ! !== get global extrema ==!362 ! !== done by all processes if writting run.stat ==!363 IF( ll_colruns ) THEN364 zmaxlocal(:) = zmax(:)365 CALL mpp_max( "stpctl", zmax ) ! max over the global domain366 nstop = NINT( zmax(3) ) ! update nstop indicator (now sheared among all local domains)367 ELSE368 ! if no ocean point: MAXVAL returns -HUGE => we must overwrite this value to avoid error handling bellow.369 IF( ll_0oce ) zmax(1:4) = (/ 0._wp, 0._wp, -1._wp, 1._wp /) ! default "valid" values...370 ENDIF371 !372 zmax(1) = -zmax(1) ! move back from max(-zz) to min(zz) : easier to manage!373 !374 ! !== write "run.stat" files ==!375 ! !== done only by 1st subdomain at writting timestep ==!376 IF( ll_wrtruns ) THEN377 WRITE(numrun,9500) kt, zmax(1), zmax(2)378 istatus = NF90_PUT_VAR( nrunid, nvarid_SWE(1), (/ zmax(1)/), (/kt/), (/1/) )379 istatus = NF90_PUT_VAR( nrunid, nvarid_SWE(2), (/ zmax(2)/), (/kt/), (/1/) )380 IF( kt == nitend ) istatus = NF90_CLOSE(nrunid)381 ENDIF382 ! !== error handling ==!383 ! !== done by all processes at every time step ==!384 !385 !!SWE specific : start386 IF( zmax(1) <= 0._wp .OR. & ! negative e3t_Kmm387 & zmax(2) > 10._wp .OR. & ! too large velocity ( > 10 m/s)388 & ISNAN( zmax(1) + zmax(2) ) .OR. & ! NaN encounter in the tests389 & ABS( zmax(1) + zmax(2) ) > HUGE(1._wp) ) THEN ! Infinity encounter in the tests390 !391 iloc(:,:) = 0392 IF( ll_colruns ) THEN ! zmax is global, so it is the same on all subdomains -> no dead lock with mpp_maxloc393 ! first: close the netcdf file, so we can read it394 IF( lwm .AND. kt /= nitend ) istatus = NF90_CLOSE(nrunid)395 ! get global loc on the min/max396 llmsk(Nis0:Nie0,Njs0:Nje0,1) = ssmask(Nis0:Nie0,Njs0:Nje0 ) == 1._wp ! define only the inner domain397 CALL mpp_minloc( 'stpctl', e3t_0(:,:,1) + ssh(:,:,Kmm), llmsk(:,:,1), zzz, iloc(1:2,1) ) ! mpp_maxloc ok if mask = F398 llmsk(Nis0:Nie0,Njs0:Nje0,:) = tmask(Nis0:Nie0,Njs0:Nje0,:) == 1._wp ! define only the inner domain399 CALL mpp_maxloc( 'stpctl', ABS( uu(:,:,:,Kmm)) , llmsk(:,:,:), zzz, iloc(1:3,2) )400 ! find which subdomain has the max.401 iareamin(:) = jpnij+1 ; iareamax(:) = 0 ; iareasum(:) = 0402 DO ji = 1, 3403 IF( zmaxlocal(ji) == zmax(ji) ) THEN404 iareamin(ji) = narea ; iareamax(ji) = narea ; iareasum(ji) = 1405 ENDIF406 END DO407 CALL mpp_min( "stpctl", iareamin ) ! min over the global domain408 CALL mpp_max( "stpctl", iareamax ) ! max over the global domain409 CALL mpp_sum( "stpctl", iareasum ) ! sum over the global domain410 ELSE ! find local min and max locations:411 ! if we are here, this means that the subdomain contains some oce points -> no need to test the mask used in maxloc412 llmsk(Nis0:Nie0,Njs0:Nje0,1) = ssmask(Nis0:Nie0,Njs0:Nje0 ) == 1._wp ! define only the inner domain413 iloc(1:2,1) = MINLOC( e3t_0(:,:,1) + ssh(:,:,Kmm), mask = llmsk(:,:,1) )414 !415 llmsk(Nis0:Nie0,Njs0:Nje0,:) = umask(Nis0:Nie0,Njs0:Nje0,:) == 1._wp ! define only the inner domain416 iloc(1:3,2) = MAXLOC( ABS( uu(:,:,:, Kmm)), mask = llmsk(:,:,:) )417 iareamin(:) = narea ; iareamax(:) = narea ; iareasum(:) = 1 ! this is local information418 ENDIF419 !420 WRITE(ctmp1,*) ' stp_ctl_SWE: e3t0+ssh < 0 m or |U| > 10 m/s or NaN encounter in the tests'421 CALL wrt_line( ctmp2, kt, 'e3t0+ssh min', zmax(1), iloc(:,1), iareasum(1), iareamin(1), iareamax(1) )422 CALL wrt_line( ctmp3, kt, '|U| max' , zmax(2), iloc(:,2), iareasum(2), iareamin(2), iareamax(2) )423 IF( Agrif_Root() ) THEN424 WRITE(ctmp6,*) ' ===> output of last computed fields in output.abort* files'425 ELSE426 WRITE(ctmp6,*) ' ===> output of last computed fields in '//TRIM(Agrif_CFixed())//'_output.abort* files'427 ENDIF428 !429 CALL dia_wri_state( Kmm, 'output.abort' ) ! create an output.abort file430 !431 IF( ll_colruns .or. jpnij == 1 ) THEN ! all processes synchronized -> use lwp to print in opened ocean.output files432 IF(lwp) THEN ; CALL ctl_stop( ctmp1, ' ', ctmp2, ctmp3, ' ', ctmp6 )433 ELSE ; nstop = MAX(1, nstop) ! make sure nstop > 0 (automatically done when calling ctl_stop)434 ENDIF435 ELSE ! only mpi subdomains with errors are here -> STOP now436 CALL ctl_stop( 'STOP', ctmp1, ' ', ctmp2, ctmp3, ' ', ctmp6 )437 ENDIF438 !439 ENDIF440 !!SWE specific : end441 !442 IF( nstop > 0 ) THEN ! an error was detected and we did not abort yet...443 ngrdstop = Agrif_Fixed() ! store which grid got this error444 IF( .NOT. ll_colruns .AND. jpnij > 1 ) CALL ctl_stop( 'STOP' ) ! we must abort here to avoid MPI deadlock445 ENDIF446 !447 9500 FORMAT(' it :', i8, ' e3t_min: ', D23.16, ' |U|_max: ', D23.16)448 !449 END SUBROUTINE stp_ctl_SWE450 270 451 271 -
NEMO/trunk/src/SAS/stpctl.F90
r13616 r14318 34 34 PUBLIC stp_ctl ! routine called by step.F90 35 35 36 INTEGER :: nrunid ! netcdf file id 37 INTEGER, DIMENSION(3) :: nvarid ! netcdf variable id 36 INTEGER, PARAMETER :: jpvar = 3 37 INTEGER :: nrunid ! netcdf file id 38 INTEGER, DIMENSION(jpvar) :: nvarid ! netcdf variable id 38 39 !!---------------------------------------------------------------------- 39 40 !! NEMO/SAS 4.0 , NEMO Consortium (2018) … … 46 47 !!---------------------------------------------------------------------- 47 48 !! *** ROUTINE stp_ctl *** 48 !! 49 !! 49 50 !! ** Purpose : Control the run 50 51 !! … … 62 63 INTEGER, INTENT(in ) :: Kmm ! ocean time level index 63 64 !! 65 INTEGER, PARAMETER :: jptst = 3 64 66 INTEGER :: ji ! dummy loop indices 65 67 INTEGER :: idtime, istatus 66 INTEGER , DIMENSION( 4):: iareasum, iareamin, iareamax67 INTEGER , DIMENSION(3, 3):: iloc ! min/max loc indices68 INTEGER , DIMENSION(jptst) :: iareasum, iareamin, iareamax 69 INTEGER , DIMENSION(3,jptst) :: iloc ! min/max loc indices 68 70 REAL(wp) :: zzz ! local real 69 REAL(wp), DIMENSION(4) :: zmax, zmaxlocal 71 REAL(wp), DIMENSION(jpvar+1) :: zmax 72 REAL(wp), DIMENSION(jptst) :: zmaxlocal 70 73 LOGICAL :: ll_wrtstp, ll_colruns, ll_wrtruns, ll_0oce 71 74 LOGICAL, DIMENSION(jpi,jpj) :: llmsk … … 75 78 ! 76 79 ll_wrtstp = ( MOD( kt-nit000, sn_cfctl%ptimincr ) == 0 ) .OR. ( kt == nitend ) 77 ll_colruns = ll_wrtstp .AND. sn_cfctl%l_runstat .AND. jpnij > 1 80 ll_colruns = ll_wrtstp .AND. sn_cfctl%l_runstat .AND. jpnij > 1 78 81 ll_wrtruns = ( ll_colruns .OR. jpnij == 1 ) .AND. lwm 79 82 ! … … 107 110 istatus = NF90_ENDDEF(nrunid) 108 111 ENDIF 109 ! 112 ! 110 113 ENDIF 111 114 ! … … 131 134 zmax(2) = MAXVAL( ABS( u_ice(:,:) ) , mask = llmsk ) ! max ice velocity (zonal only) 132 135 zmax(3) = MAXVAL( -tm_i (:,:) + rt0, mask = llmsk ) ! min ice temperature (in degC) 133 zmax( 4) = REAL( nstop, wp )! stop indicator136 zmax(jpvar+1) = REAL( nstop, wp ) ! stop indicator 134 137 ! 135 138 ! !== get global extrema ==! 136 139 ! !== done by all processes if writting run.stat ==! 137 140 IF( ll_colruns ) THEN 138 zmaxlocal(:) = zmax( :)141 zmaxlocal(:) = zmax(1:jptst) 139 142 CALL mpp_max( "stpctl", zmax ) ! max over the global domain: ok even of ll_0oce = .true. 140 nstop = NINT( zmax( 4) )! update nstop indicator (now sheared among all local domains)143 nstop = NINT( zmax(jpvar+1) ) ! update nstop indicator (now sheared among all local domains) 141 144 ELSE 142 145 ! if no ocean point: MAXVAL returns -HUGE => we must overwrite this value to avoid error handling bellow. 143 IF( ll_0oce ) zmax(1: 3) = 0._wp! default "valid" values...146 IF( ll_0oce ) zmax(1:jptst) = 0._wp ! default "valid" values... 144 147 ENDIF 145 148 ! … … 150 153 ! !== done only by 1st subdomain at writting timestep ==! 151 154 IF( ll_wrtruns ) THEN 152 WRITE(numrun,9500) kt, zmax(1 ), zmax(2), zmax(3)153 DO ji = 1, 3155 WRITE(numrun,9500) kt, zmax(1:jptst) 156 DO ji = 1, jpvar 154 157 istatus = NF90_PUT_VAR( nrunid, nvarid(ji), (/zmax(ji)/), (/kt/), (/1/) ) 155 158 END DO … … 159 162 ! !== done by all processes at every time step ==! 160 163 ! 161 IF( zmax(1) > 100._wp .OR. & ! too large ice thickness maximum ( > 100 m)162 & zmax(2) > 10._wp .OR. & ! too large ice velocity ( > 10 m/s)163 & zmax(3) < -101._wp .OR. & ! too cold ice temperature ( < -100 degC)164 & ISNAN( zmax(1) + zmax(2) + zmax(3) ) .OR. & ! NaN encounter in the tests165 & ABS( zmax(1) + zmax(2) + zmax(3) ) > HUGE(1._wp) ) THEN ! Infinity encounter in the tests164 IF( zmax(1) > 100._wp .OR. & ! too large ice thickness maximum ( > 100 m) 165 & zmax(2) > 10._wp .OR. & ! too large ice velocity ( > 10 m/s) 166 & zmax(3) < -101._wp .OR. & ! too cold ice temperature ( < -100 degC) 167 & ISNAN( SUM(zmax(1:jptst)) ) .OR. & ! NaN encounter in the tests 168 & ABS( SUM(zmax(1:jptst)) ) > HUGE(1._wp) ) THEN ! Infinity encounter in the tests 166 169 ! 167 170 iloc(:,:) = 0 … … 175 178 ! find which subdomain has the max. 176 179 iareamin(:) = jpnij+1 ; iareamax(:) = 0 ; iareasum(:) = 0 177 DO ji = 1, 4180 DO ji = 1, jptst 178 181 IF( zmaxlocal(ji) == zmax(ji) ) THEN 179 182 iareamin(ji) = narea ; iareamax(ji) = narea ; iareasum(ji) = 1 … … 188 191 iloc(1:2,2) = MAXLOC( ABS( u_ice(:,:) ) , mask = llmsk ) 189 192 iloc(1:2,3) = MINLOC( tm_i(:,:) - rt0, mask = llmsk ) 190 DO ji = 1, 3! local domain indices ==> global domain indices, excluding halos193 DO ji = 1, jptst ! local domain indices ==> global domain indices, excluding halos 191 194 iloc(1:2,ji) = (/ mig0(iloc(1,ji)), mjg0(iloc(2,ji)) /) 192 195 END DO … … 206 209 CALL dia_wri_state( Kmm, 'output.abort' ) ! create an output.abort file 207 210 ! 208 IF( ll_colruns . or. jpnij == 1 ) THEN ! all processes synchronized -> use lwp to print in opened ocean.output files211 IF( ll_colruns .OR. jpnij == 1 ) THEN ! all processes synchronized -> use lwp to print in opened ocean.output files 209 212 IF(lwp) THEN ; CALL ctl_stop( ctmp1, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ' ', ctmp6 ) 210 213 ELSE ; nstop = MAX(1, nstop) ! make sure nstop > 0 (automatically done when calling ctl_stop) … … 247 250 !!---------------------------------------------------------------------- 248 251 WRITE(clkt , '(i9)') kt 249 252 250 253 WRITE(clfmt, '(i1)') INT(LOG10(REAL(jpnij ,wp))) + 1 ! how many digits to we need to write ? (we decide max = 9) 251 254 !!! WRITE(clsum, '(i'//clfmt//')') ksum ! this is creating a compilation error with AGRIF -
NEMO/trunk/src/SWE/stp_oce.F90
r14239 r14318 93 93 ! (dyn_asm_inc routine) 94 94 USE asmbkg ! writing out state trajectory 95 USE stpctl ! time stepping control (stp_ctl _SWEroutine)95 USE stpctl ! time stepping control (stp_ctl routine) 96 96 USE restart ! ocean restart (rst_wri routine) 97 97 USE prtctl ! Print control (prt_ctl routine) -
NEMO/trunk/src/SWE/stpmlf.F90
r14239 r14318 222 222 ! Control 223 223 !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 224 CALL stp_ctl _SWE( kstp, Nnn )224 CALL stp_ctl ( kstp, Nnn ) 225 225 226 226 IF( kstp == nit000 ) THEN ! 1st time step only -
NEMO/trunk/src/SWE/stprk3.F90
r14239 r14318 319 319 ! Control 320 320 !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 321 CALL stp_ctl _SWE( kstp , Nbb )321 CALL stp_ctl ( kstp , Nbb ) 322 322 323 323 IF( kstp == nit000 ) THEN ! 1st time step only -
NEMO/trunk/tests/STATION_ASF/MY_SRC/stpctl.F90
r14072 r14318 31 31 PUBLIC stp_ctl ! routine called by step.F90 32 32 33 INTEGER :: nrunid ! netcdf file id 34 INTEGER, DIMENSION(3) :: nvarid ! netcdf variable id 33 INTEGER, PARAMETER :: jpvar = 3 34 INTEGER :: nrunid ! netcdf file id 35 INTEGER, DIMENSION(jpvar) :: nvarid ! netcdf variable id 35 36 !!---------------------------------------------------------------------- 36 37 !! NEMO/SAS 4.0 , NEMO Consortium (2018) … … 59 60 INTEGER, INTENT(in ) :: Kmm ! ocean time level index 60 61 !! 62 INTEGER, PARAMETER :: jptst = 3 61 63 INTEGER :: ji ! dummy loop indices 62 64 INTEGER :: idtime, istatus 63 INTEGER , DIMENSION(4) :: iareasum, iareamin, iareamax 64 INTEGER , DIMENSION(3,3) :: iloc ! min/max loc indices 65 REAL(wp) :: zzz ! local real 66 REAL(wp), DIMENSION(4) :: zmax, zmaxlocal 65 INTEGER , DIMENSION(jptst) :: iareasum, iareamin, iareamax 66 INTEGER , DIMENSION(3,jptst) :: iloc ! min/max loc indices 67 REAL(wp) :: zzz ! local real 68 REAL(wp), DIMENSION(jpvar+1) :: zmax 69 REAL(wp), DIMENSION(jptst) :: zmaxlocal 67 70 LOGICAL :: ll_wrtstp, ll_colruns, ll_wrtruns, ll_0oce 68 71 LOGICAL, DIMENSION(jpi,jpj) :: llmsk … … 122 125 zmax(2) = MAXVAL( ABS( qns(:,:) ), mask = llmsk ) ! max non-solar heat flux 123 126 zmax(3) = MAXVAL( ABS( emp(:,:) ), mask = llmsk ) ! max E-P 124 zmax( 4) = REAL( nstop, wp )! stop indicator127 zmax(jpvar+1) = REAL( nstop, wp ) ! stop indicator 125 128 ! 126 129 ! !== get global extrema ==! 127 130 ! !== done by all processes if writting run.stat ==! 128 131 IF( ll_colruns ) THEN 129 zmaxlocal(:) = zmax( :)130 CALL mpp_max( "stpctl", zmax ) ! max over the global domain 131 nstop = NINT( zmax( 4) )! update nstop indicator (now sheared among all local domains)132 zmaxlocal(:) = zmax(1:jptst) 133 CALL mpp_max( "stpctl", zmax ) ! max over the global domain: ok even of ll_0oce = .true. 134 nstop = NINT( zmax(jpvar+1) ) ! update nstop indicator (now sheared among all local domains) 132 135 ELSE 133 136 ! if no ocean point: MAXVAL returns -HUGE => we must overwrite this value to avoid error handling bellow. 134 IF( ll_0oce ) zmax(1:3) = 0._wp ! default "valid" values... 135 ENDIF 136 ! !== error handling ==! 137 IF( ll_0oce ) zmax(1:jptst) = 0._wp ! default "valid" values... 138 ENDIF 137 139 ! !== write "run.stat" files ==! 138 140 ! !== done only by 1st subdomain at writting timestep ==! 139 141 IF( ll_wrtruns ) THEN 140 WRITE(numrun,9500) kt, zmax(1 ), zmax(2), zmax(3)141 DO ji = 1, 3142 WRITE(numrun,9500) kt, zmax(1:jptst) 143 DO ji = 1, jpvar 142 144 istatus = NF90_PUT_VAR( nrunid, nvarid(ji), (/zmax(ji)/), (/kt/), (/1/) ) 143 145 END DO 144 IF( kt == nitend ) istatus = NF90_CLOSE(nrunid)146 IF( kt == nitend ) istatus = NF90_CLOSE(nrunid) 145 147 END IF 146 148 ! !== error handling ==! 147 149 ! !== done by all processes at every time step ==! 148 150 ! 149 IF( zmax(1) > 5._wp .OR. & ! too large wind stress ( > 5 N/m^2 )150 & zmax(2) > 2000._wp .OR. & ! too large non-solar heat flux ( > 2000 W/m^2 )151 & zmax(3) > 1.E-3_wp .OR. & ! too large net freshwater flux ( > 1.E-3 kg/m^2/s )152 & ISNAN( zmax(1) + zmax(2) + zmax(3) ) .OR. & ! NaN encounter in the tests153 & ABS( zmax(1) + zmax(2) + zmax(3) ) > HUGE(1._wp) ) THEN ! Infinity encounter in the tests151 IF( zmax(1) > 5._wp .OR. & ! too large wind stress ( > 5 N/m^2 ) 152 & zmax(2) > 2000._wp .OR. & ! too large non-solar heat flux ( > 2000 W/m^2 ) 153 & zmax(3) > 1.E-3_wp .OR. & ! too large net freshwater flux ( > 1.E-3 kg/m^2/s ) 154 & ISNAN( SUM(zmax(1:jptst)) ) .OR. & ! NaN encounter in the tests 155 & ABS( SUM(zmax(1:jptst)) ) > HUGE(1._wp) ) THEN ! Infinity encounter in the tests 154 156 ! 155 157 iloc(:,:) = 0 … … 163 165 ! find which subdomain has the max. 164 166 iareamin(:) = jpnij+1 ; iareamax(:) = 0 ; iareasum(:) = 0 165 DO ji = 1, 4167 DO ji = 1, jptst 166 168 IF( zmaxlocal(ji) == zmax(ji) ) THEN 167 169 iareamin(ji) = narea ; iareamax(ji) = narea ; iareasum(ji) = 1 … … 176 178 iloc(1:2,2) = MAXLOC( ABS( qns(:,:) ), mask = llmsk ) 177 179 iloc(1:2,3) = MINLOC( ABS( emp(:,:) ), mask = llmsk ) 178 DO ji = 1, 3! local domain indices ==> global domain indices, excluding halos180 DO ji = 1, jptst ! local domain indices ==> global domain indices, excluding halos 179 181 iloc(1:2,ji) = (/ mig0(iloc(1,ji)), mjg0(iloc(2,ji)) /) 180 182 END DO … … 195 197 ! 196 198 IF( ll_colruns .OR. jpnij == 1 ) THEN ! all processes synchronized -> use lwp to print in opened ocean.output files 197 IF(lwp) THEN 198 CALL ctl_stop( ctmp1, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ' ', ctmp6 ) 199 ELSE 200 nstop = MAX(1, nstop) ! make sure nstop > 0 (automatically done when calling ctl_stop) 199 IF(lwp) THEN ; CALL ctl_stop( ctmp1, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ' ', ctmp6 ) 200 ELSE ; nstop = MAX(1, nstop) ! make sure nstop > 0 (automatically done when calling ctl_stop) 201 201 ENDIF 202 202 ELSE ! only mpi subdomains with errors are here -> STOP now … … 239 239 240 240 WRITE(clfmt, '(i1)') INT(LOG10(REAL(jpnij ,wp))) + 1 ! how many digits to we need to write ? (we decide max = 9) 241 !!! WRITE(clsum, '(i'//clfmt//')') ksum ! this is creating a compilation error with AGRIF241 !!! WRITE(clsum, '(i'//clfmt//')') ksum ! this is creating a compilation error with AGRIF 242 242 cl4 = '(i'//clfmt//')' ; WRITE(clsum, cl4) ksum 243 243 WRITE(clfmt, '(i1)') INT(LOG10(REAL(MAX(1,jpnij-1),wp))) + 1 ! how many digits to we need to write ? (we decide max = 9) 244 244 cl4 = '(i'//clfmt//')' ; WRITE(clmin, cl4) kmin-1 245 WRITE(clmax, cl4) kmax-1245 WRITE(clmax, cl4) kmax-1 246 246 ! 247 247 WRITE(clfmt, '(i1)') INT(LOG10(REAL(jpiglo,wp))) + 1 ! how many digits to we need to write jpiglo? (we decide max = 9) … … 259 259 ELSE 260 260 WRITE(clfmt, '(i1)') INT(LOG10(REAL(jpk,wp))) + 1 ! how many digits to we need to write jpk? (we decide max = 9) 261 !!! WRITE(clk, '(i'//clfmt//')') kloc(3) ! this is creating a compilation error with AGRIF261 !!! WRITE(clk, '(i'//clfmt//')') kloc(3) ! this is creating a compilation error with AGRIF 262 262 cl4 = '(i'//clfmt//')' ; WRITE(clk, cl4) kloc(3) ! this is ok with AGRIF 263 263 WRITE(cdline,9400) TRIM(ADJUSTL(clkt)), TRIM(ADJUSTL(cdprefix)), pval, TRIM(cli), TRIM(clj), TRIM(clk), TRIM(clsuff)
Note: See TracChangeset
for help on using the changeset viewer.