Changeset 12684
- Timestamp:
- 2020-04-05T18:47:37+02:00 (4 years ago)
- Location:
- NEMO/branches/2020/r12581_ticket2418
- Files:
-
- 10 edited
Legend:
- Unmodified
- Added
- Removed
-
NEMO/branches/2020/r12581_ticket2418/src/OCE/DOM/dom_oce.F90
r12489 r12684 17 17 !!---------------------------------------------------------------------- 18 18 !! Agrif_Root : dummy function used when lk_agrif=F 19 !! Agrif_Fixed : dummy function used when lk_agrif=F 19 20 !! Agrif_CFixed : dummy function used when lk_agrif=F 20 21 !! dom_oce_alloc : dynamical allocation of dom_oce arrays … … 233 234 END FUNCTION Agrif_Root 234 235 236 INTEGER FUNCTION Agrif_Fixed() 237 Agrif_Fixed = 0 238 END FUNCTION Agrif_Fixed 239 235 240 CHARACTER(len=3) FUNCTION Agrif_CFixed() 236 241 Agrif_CFixed = '0' -
NEMO/branches/2020/r12581_ticket2418/src/OCE/IOM/in_out_manager.F90
r12593 r12684 165 165 INTEGER :: no_print = 0 !: optional argument of fld_fill (if present, suppress some control print) 166 166 INTEGER :: nstop = 0 !: error flag (=number of reason for a premature stop run) 167 !$AGRIF_DO_NOT_TREAT 168 INTEGER :: ngrdstop = -1 !: grid number having nstop > 1 169 !$AGRIF_END_DO_NOT_TREAT 167 170 INTEGER :: nwarn = 0 !: warning flag (=number of warning found during the run) 168 171 CHARACTER(lc) :: ctmp1, ctmp2, ctmp3 !: temporary characters 1 to 3 -
NEMO/branches/2020/r12581_ticket2418/src/OCE/LBC/lib_mpp.F90
r12593 r12684 1146 1146 WRITE(numout,*) 1147 1147 CALL FLUSH(numout) 1148 CALL SLEEP(60) 1148 CALL SLEEP(60) ! make sure that all output and abort files are written by all cores. 60s should be enough... 1149 1149 CALL mppstop( ld_abort = .true. ) 1150 1150 ENDIF -
NEMO/branches/2020/r12581_ticket2418/src/OCE/nemogcm.F90
r12655 r12684 186 186 END DO 187 187 ! 188 IF( .NOT. Agrif_Root() ) THEN189 CALL Agrif_ParentGrid_To_ChildGrid()190 IF( ln_diaobs ) CALL dia_obs_wri191 IF( ln_timing ) CALL timing_finalize192 CALL Agrif_ChildGrid_To_ParentGrid()193 ENDIF194 !195 188 # else 196 189 ! … … 237 230 IF( nstop /= 0 .AND. lwp ) THEN ! error print 238 231 WRITE(ctmp1,*) ' ==>>> nemo_gcm: a total of ', nstop, ' errors have been found' 239 CALL ctl_stop( ctmp1 ) 232 IF( ngrdstop > 0 ) THEN 233 WRITE(ctmp9,'(i2)') ngrdstop 234 WRITE(ctmp2,*) ' ==>>> Error detected in Agrif grid '//TRIM(ctmp9) 235 WRITE(ctmp3,*) ' ==>>> look for error messages in '//TRIM(ctmp9)//'_ocean_output* files' 236 CALL ctl_stop( ctmp1, ctmp2, ctmp3 ) 237 ELSE 238 CALL ctl_stop( ctmp1 ) 239 ENDIF 240 240 ENDIF 241 241 ! -
NEMO/branches/2020/r12581_ticket2418/src/OCE/step.F90
r12655 r12684 86 86 !! --------------------------------------------------------------------- 87 87 #if defined key_agrif 88 IF( nstop > 0 ) return ! avoid to go further if an error was detected during previous time step88 IF( nstop > 0 ) RETURN ! avoid to go further if an error was detected during previous time step (child grid) 89 89 kstp = nit000 + Agrif_Nb_Step() 90 90 Kbb_a = Nbb; Kmm_a = Nnn; Krhs_a = Nrhs ! agrif_oce module copies of time level indices … … 327 327 328 328 #endif 329 IF( ln_diaobs ) CALL dia_obs ( kstp, Nnn ) ! obs-minus-model (assimilation) diagnostics (callafter dynamics update)329 IF( ln_diaobs .AND. nstop == 0 ) CALL dia_obs( kstp, Nnn ) ! obs-minus-model (assimilation) diags (after dynamics update) 330 330 331 331 !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> … … 341 341 ! Coupled mode 342 342 !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 343 !!gm why lk_oasis and not lk_cpl ???? 344 IF( lk_oasis ) CALL sbc_cpl_snd( kstp, Nbb, Nnn ) ! coupled mode : field exchanges 343 IF( lk_oasis .AND. nstop == 0 ) CALL sbc_cpl_snd( kstp, Nbb, Nnn ) ! coupled mode : field exchanges 345 344 ! 346 345 #if defined key_iomput -
NEMO/branches/2020/r12581_ticket2418/src/OCE/stpctl.F90
r12593 r12684 71 71 CHARACTER(len=20) :: clname 72 72 !!---------------------------------------------------------------------- 73 IF( nstop > 0 .AND. ngrdstop > -1 ) RETURN ! stpctl was already called by a child grid 73 74 ! 74 75 ll_wrtstp = ( MOD( kt-nit000, sn_cfctl%ptimincr ) == 0 ) .OR. ( kt == nitend ) … … 203 204 WRITE(ctmp4,9200) kt, ' Sal min ', -zmax(3), iloc(1,3), iloc(2,3), iloc(3,3), NINT(zarea(3))-1 204 205 WRITE(ctmp5,9200) kt, ' Sal max ', zmax(4), iloc(1,4), iloc(2,4), iloc(3,4), NINT(zarea(4))-1 205 WRITE(ctmp6,*) ' ===> output of last computed fields in output.abort.nc file' 206 IF( Agrif_Root() ) THEN 207 WRITE(ctmp6,*) ' ===> output of last computed fields in output.abort* files' 208 ELSE 209 WRITE(ctmp6,*) ' ===> output of last computed fields in '//TRIM(Agrif_CFixed())//'_output.abort* files' 210 ENDIF 206 211 ! 207 212 CALL dia_wri_state( Kmm, 'output.abort' ) ! create an output.abort file … … 214 219 ! 215 220 IF( nstop == 0 ) nstop = 1 221 ngrdstop = Agrif_Fixed() 216 222 ! 217 223 ENDIF -
NEMO/branches/2020/r12581_ticket2418/src/SAS/nemogcm.F90
r12655 r12684 126 126 END DO 127 127 ! 128 IF( .NOT. Agrif_Root() ) THEN129 CALL Agrif_ParentGrid_To_ChildGrid()130 IF( ln_timing ) CALL timing_finalize131 CALL Agrif_ChildGrid_To_ParentGrid()132 ENDIF133 !134 128 #else 135 129 ! … … 166 160 IF( nstop /= 0 .AND. lwp ) THEN ! error print 167 161 WRITE(ctmp1,*) ' ==>>> nemo_gcm: a total of ', nstop, ' errors have been found' 168 CALL ctl_stop( ctmp1 ) 162 IF( ngrdstop > 0 ) THEN 163 WRITE(ctmp9,'(i2)') ngrdstop 164 WRITE(ctmp2,*) ' ==>>> Error detected in Agrif grid '//TRIM(ctmp9) 165 WRITE(ctmp3,*) ' ==>>> look for error messages in '//TRIM(ctmp9)//'_ocean_output* files' 166 CALL ctl_stop( ctmp1, ctmp2, ctmp3 ) 167 ELSE 168 CALL ctl_stop( ctmp1 ) 169 ENDIF 169 170 ENDIF 170 171 ! -
NEMO/branches/2020/r12581_ticket2418/src/SAS/step.F90
r12655 r12684 76 76 77 77 #if defined key_agrif 78 IF( nstop > 0 ) return ! avoid to go further if an error was detected during previous time step78 IF( nstop > 0 ) RETURN ! avoid to go further if an error was detected during previous time step (child grid) 79 79 kstp = nit000 + Agrif_Nb_Step() 80 80 Kbb_a = Nbb; Kmm_a = Nnn; Krhs_a = Nrhs ! agrif_oce module copies of time level indices … … 133 133 ! Coupled mode 134 134 !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 135 IF( lk_oasis ) CALL sbc_cpl_snd( kstp, Nbb, Nnn )! coupled mode : field exchanges if OASIS-coupled ice135 IF( lk_oasis .AND. nstop == 0 ) CALL sbc_cpl_snd( kstp, Nbb, Nnn ) ! coupled mode : field exchanges if OASIS-coupled ice 136 136 137 137 #if defined key_iomput … … 145 145 ENDIF 146 146 IF( kstp == nitend .OR. nstop > 0 ) THEN 147 147 CALL iom_context_finalize( cxios_context ) ! needed for XIOS+AGRIF 148 148 ENDIF 149 149 #endif -
NEMO/branches/2020/r12581_ticket2418/src/SAS/stpctl.F90
r12655 r12684 70 70 CHARACTER(len=20) :: clname 71 71 !!---------------------------------------------------------------------- 72 IF( nstop > 0 .AND. ngrdstop > -1 ) RETURN ! stpctl was already called by a child grid 72 73 ! 73 74 ll_wrtstp = ( MOD( kt-nit000, sn_cfctl%ptimincr ) == 0 ) .OR. ( kt == nitend ) … … 163 164 WRITE(ctmp3,9100) kt, ' |ice_vel| max', zmax(2), iloc(1,2), iloc(2,3), NINT(zarea(2))-1 164 165 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 IF( Agrif_Root() ) THEN 167 WRITE(ctmp6,*) ' ===> output of last computed fields in output.abort* files' 168 ELSE 169 WRITE(ctmp6,*) ' ===> output of last computed fields in '//TRIM(Agrif_CFixed())//'_output.abort* files' 170 ENDIF 166 171 ! 167 172 CALL dia_wri_state( Kmm, 'output.abort' ) ! create an output.abort file … … 174 179 ! 175 180 IF( nstop == 0 ) nstop = 1 181 ngrdstop = Agrif_Fixed() 176 182 ! 177 183 ENDIF -
NEMO/branches/2020/r12581_ticket2418/tests/CANAL/MY_SRC/stpctl.F90
r12377 r12684 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 ! 74 ll_wrtstp = ( MOD( kt, sn_cfctl%ptimincr ) == 0 ) .OR. ( kt == nitend ) 75 ll_colruns = ll_wrtstp .AND. ( ln_ctl .OR. sn_cfctl%l_runstat ) 73 IF( nstop > 0 .AND. ngrdstop > -1 ) RETURN ! stpctl was already called by a child grid 74 ! 75 ll_wrtstp = ( MOD( kt-nit000, sn_cfctl%ptimincr ) == 0 ) .OR. ( kt == nitend ) 76 ll_colruns = ll_wrtstp .AND. sn_cfctl%l_runstat 76 77 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. ( ln_ctl .OR. sn_cfctl%l_runstat ) ) THEN 78 ! 79 IF( kt == nit000 ) THEN 80 ! 81 IF( lwp ) THEN 82 WRITE(numout,*) 83 WRITE(numout,*) 'stp_ctl : time-stepping control' 84 WRITE(numout,*) '~~~~~~~' 85 ENDIF 86 ! ! open time.step ascii file, done only by 1st subdomain 87 IF( lwm ) CALL ctl_opn( numstp, 'time.step', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 88 ! 89 IF( ll_wrtruns ) THEN 90 ! ! open run.stat ascii file, done only by 1st subdomain 86 91 CALL ctl_opn( numrun, 'run.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 92 ! ! open run.stat.nc netcdf file, done only by 1st subdomain 87 93 clname = 'run.stat.nc' 88 94 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)95 istatus = NF90_CREATE( TRIM(clname), NF90_CLOBBER, nrunid ) 96 istatus = NF90_DEF_DIM( nrunid, 'time', NF90_UNLIMITED, idtime ) 97 istatus = NF90_DEF_VAR( nrunid, 'abs_ssh_max', NF90_DOUBLE, (/ idtime /), nvarid(1) ) 98 istatus = NF90_DEF_VAR( nrunid, 'abs_u_max', NF90_DOUBLE, (/ idtime /), nvarid(2) ) 99 istatus = NF90_DEF_VAR( nrunid, 's_min', NF90_DOUBLE, (/ idtime /), nvarid(3) ) 100 istatus = NF90_DEF_VAR( nrunid, 's_max', NF90_DOUBLE, (/ idtime /), nvarid(4) ) 101 istatus = NF90_DEF_VAR( nrunid, 't_min', NF90_DOUBLE, (/ idtime /), nvarid(5) ) 102 istatus = NF90_DEF_VAR( nrunid, 't_max', NF90_DOUBLE, (/ idtime /), nvarid(6) ) 97 103 IF( ln_zad_Aimp ) THEN 98 istatus = NF90_DEF_VAR( idrun, 'abs_wi_max', NF90_DOUBLE, (/ idtime /), idw1)99 istatus = NF90_DEF_VAR( idrun, 'Cu_max', NF90_DOUBLE, (/ idtime /), idc1)104 istatus = NF90_DEF_VAR( nrunid, 'Cf_max', NF90_DOUBLE, (/ idtime /), nvarid(7) ) 105 istatus = NF90_DEF_VAR( nrunid,'abs_wi_max',NF90_DOUBLE, (/ idtime /), nvarid(8) ) 100 106 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) 107 istatus = NF90_ENDDEF(nrunid) 108 ENDIF 109 ! 110 ENDIF 111 ! 112 ! !== write current time step ==! 113 ! !== done only by 1st subdomain at writting timestep ==! 114 IF( lwm .AND. ll_wrtstp ) THEN 108 115 WRITE ( numstp, '(1x, i8)' ) kt 109 116 REWIND( numstp ) 110 117 ENDIF 111 ! 112 ! !== test of extrema ==! 118 ! !== test of local extrema ==! 119 ! !== done by all processes at every time step ==! 120 llmsk(:,:,1) = ssmask(:,:) == 1._wp 113 121 IF( ll_wd ) THEN 114 zmax(1) = MAXVAL( ABS( ssh(:,:,Kmm) + ssh_ref*tmask(:,:,1) ) ) ! ssh max122 zmax(1) = MAXVAL( ABS( ssh(:,:,Kmm) + ssh_ref ), mask = llmsk(:,:,1) ) ! ssh max 115 123 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 ) ! cell Courant no. max 127 ENDIF 128 ! 124 zmax(1) = MAXVAL( ABS( ssh(:,:,Kmm) ), mask = llmsk(:,:,1) ) ! ssh max 125 ENDIF 126 llmsk(:,:,:) = umask(:,:,:) == 1._wp 127 zmax(2) = MAXVAL( ABS( uu(:,:,:,Kmm) ), mask = llmsk ) ! velocity max (zonal only) 128 llmsk(:,:,:) = tmask(:,:,:) == 1._wp 129 zmax(3) = MAXVAL( -ts(:,:,:,jp_sal,Kmm), mask = llmsk ) ! minus salinity max 130 zmax(4) = MAXVAL( ts(:,:,:,jp_sal,Kmm), mask = llmsk ) ! salinity max 131 IF( ll_colruns ) THEN ! following variables are used only in the netcdf file 132 zmax(5) = MAXVAL( -ts(:,:,:,jp_tem,Kmm), mask = llmsk ) ! minus temperature max 133 zmax(6) = MAXVAL( ts(:,:,:,jp_tem,Kmm), mask = llmsk ) ! temperature max 134 IF( ln_zad_Aimp ) THEN 135 zmax(7) = MAXVAL( Cu_adv(:,:,:) , mask = llmsk ) ! partitioning coeff. max 136 llmsk(:,:,:) = wmask(:,:,:) == 1._wp 137 zmax(8) = MAXVAL( ABS( wi(:,:,:) ) , mask = llmsk ) ! implicit vertical vel. max 138 ELSE 139 zmax(7:8) = 0._wp 140 ENDIF 141 ELSE 142 zmax(5:8) = 0._wp 143 ENDIF 144 zmax(9) = REAL( nstop, wp ) ! stop indicator 145 ! !== get global extrema ==! 146 ! !== done by all processes if writting run.stat ==! 129 147 IF( ll_colruns ) THEN 148 zmaxlocal(:) = zmax(:) 130 149 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) 150 nstop = NINT( zmax(9) ) ! update nstop indicator (now sheared among all local domains) 151 ENDIF 152 ! !== write "run.stat" files ==! 153 ! !== done only by 1st subdomain at writting timestep ==! 134 154 IF( ll_wrtruns ) THEN 135 155 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/) )156 istatus = NF90_PUT_VAR( nrunid, nvarid(1), (/ zmax(1)/), (/kt/), (/1/) ) 157 istatus = NF90_PUT_VAR( nrunid, nvarid(2), (/ zmax(2)/), (/kt/), (/1/) ) 158 istatus = NF90_PUT_VAR( nrunid, nvarid(3), (/-zmax(3)/), (/kt/), (/1/) ) 159 istatus = NF90_PUT_VAR( nrunid, nvarid(4), (/ zmax(4)/), (/kt/), (/1/) ) 160 istatus = NF90_PUT_VAR( nrunid, nvarid(5), (/-zmax(5)/), (/kt/), (/1/) ) 161 istatus = NF90_PUT_VAR( nrunid, nvarid(6), (/ zmax(6)/), (/kt/), (/1/) ) 142 162 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) 163 istatus = NF90_PUT_VAR( nrunid, nvarid(7), (/ zmax(7)/), (/kt/), (/1/) ) 164 istatus = NF90_PUT_VAR( nrunid, nvarid(8), (/ zmax(8)/), (/kt/), (/1/) ) 165 ENDIF 166 IF( kt == nitend ) istatus = NF90_CLOSE(nrunid) 148 167 END IF 149 ! !== error handling ==! 150 IF( ( ln_ctl .OR. lsomeoce ) .AND. ( & ! have use mpp_max (because ln_ctl=.T.) or contains some ocean points 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. ln_ctl ) THEN 158 CALL mpp_maxloc( 'stpctl', ABS(ssh(:,:,Kmm)) , ssmask(:,:) , zzz, ih ) 159 CALL mpp_maxloc( 'stpctl', ABS(uu(:,:,:,Kmm)) , umask (:,:,:), zzz, iu ) 160 CALL mpp_minloc( 'stpctl', ts(:,:,:,jp_sal,Kmm), tmask (:,:,:), zzz, is1 ) 161 CALL mpp_maxloc( 'stpctl', ts(:,:,:,jp_sal,Kmm), tmask (:,:,:), zzz, is2 ) 168 ! !== error handling ==! 169 ! !== done by all processes at every time step ==! 170 ! 171 IF( zmax(1) > 20._wp .OR. & ! too large sea surface height ( > 20 m ) 172 & zmax(2) > 10._wp .OR. & ! too large velocity ( > 10 m/s) 173 !!$ & zmax(3) >= 0._wp .OR. & ! negative or zero sea surface salinity 174 !!$ & zmax(4) >= 100._wp .OR. & ! too large sea surface salinity ( > 100 ) 175 !!$ & zmax(4) < 0._wp .OR. & ! too large sea surface salinity (keep this line for sea-ice) 176 & ISNAN( zmax(1) + zmax(2) + zmax(3) ) ) THEN ! NaN encounter in the tests 177 ! 178 IF( ll_colruns ) THEN ! zmax is global, so it is the same on all subdomains -> no dead lock with mpp_maxloc 179 ! first: close the netcdf file, so we can read it 180 IF( lwm .AND. kt /= nitend ) istatus = NF90_CLOSE(nrunid) 181 ! get global loc on the min/max 182 CALL mpp_maxloc( 'stpctl', ABS(ssh(:,:, Kmm)), ssmask(:,: ), zzz, iloc(1:2,1) ) ! mpp_maxloc ok if mask = F 183 CALL mpp_maxloc( 'stpctl', ABS( uu(:,:,:, Kmm)), umask(:,:,:), zzz, iloc(1:3,2) ) 184 CALL mpp_minloc( 'stpctl', ts(:,:,:,jp_sal,Kmm) , tmask(:,:,:), zzz, iloc(1:3,3) ) 185 CALL mpp_maxloc( 'stpctl', ts(:,:,:,jp_sal,Kmm) , tmask(:,:,:), zzz, iloc(1:3,4) ) 186 ! find which subdomain has the max. 187 zarea(:) = 0._wp 188 DO ji = 1, 9 189 IF( zmaxlocal(ji) == zmax(ji) ) zarea(ji) = narea 190 END DO 191 CALL mpp_max( "stpctl", zarea ) ! max over the global domain 192 ELSE ! find local min and max locations: 193 ! if we are here, this means that the subdomain contains some oce points -> no need to test the mask used in maxloc 194 iloc(1:2,1) = MAXLOC( ABS( ssh(:,:, Kmm)), mask = ssmask(:,: ) == 1._wp ) + (/ nimpp - 1, njmpp - 1 /) 195 iloc(1:3,2) = MAXLOC( ABS( uu(:,:,:, Kmm)), mask = umask(:,:,:) == 1._wp ) + (/ nimpp - 1, njmpp - 1, 0 /) 196 iloc(1:3,3) = MINLOC( ts(:,:,:,jp_sal,Kmm) , mask = tmask(:,:,:) == 1._wp ) + (/ nimpp - 1, njmpp - 1, 0 /) 197 iloc(1:3,4) = MAXLOC( ts(:,:,:,jp_sal,Kmm) , mask = tmask(:,:,:) == 1._wp ) + (/ nimpp - 1, njmpp - 1, 0 /) 198 zarea(:) = narea ! this is local information 199 ENDIF 200 ! 201 WRITE(ctmp1,*) ' stp_ctl: |ssh| > 20 m or |U| > 10 m/s or S <= 0 or S >= 100 or NaN encounter in the tests' 202 WRITE(ctmp2,9100) kt, ' |ssh| max ', zmax(1), iloc(1,1), iloc(2,1), NINT(zarea(1))-1 203 WRITE(ctmp3,9200) kt, ' |U| max ', zmax(2), iloc(1,2), iloc(2,2), iloc(3,2), NINT(zarea(2))-1 204 WRITE(ctmp4,9200) kt, ' Sal min ', -zmax(3), iloc(1,3), iloc(2,3), iloc(3,3), NINT(zarea(3))-1 205 WRITE(ctmp5,9200) kt, ' Sal max ', zmax(4), iloc(1,4), iloc(2,4), iloc(3,4), NINT(zarea(4))-1 206 IF( Agrif_Root() ) THEN 207 WRITE(ctmp6,*) ' ===> output of last computed fields in output.abort* files' 162 208 ELSE 163 ih(:) = MAXLOC( ABS( ssh(:,:,Kmm) ) ) + (/ nimpp - 1, njmpp - 1 /) 164 iu(:) = MAXLOC( ABS( uu (:,:,:,Kmm) ) ) + (/ nimpp - 1, njmpp - 1, 0 /) 165 is1(:) = MINLOC( ts(:,:,:,jp_sal,Kmm), mask = tmask(:,:,:) == 1._wp ) + (/ nimpp - 1, njmpp - 1, 0 /) 166 is2(:) = MAXLOC( ts(:,:,:,jp_sal,Kmm), mask = tmask(:,:,:) == 1._wp ) + (/ nimpp - 1, njmpp - 1, 0 /) 167 ENDIF 168 169 WRITE(ctmp1,*) ' stp_ctl: |ssh| > 20 m or |U| > 10 m/s or S <= 0 or S >= 100 or NaN encounter in the tests' 170 WRITE(ctmp2,9100) kt, zmax(1), ih(1) , ih(2) 171 WRITE(ctmp3,9200) kt, zmax(2), iu(1) , iu(2) , iu(3) 172 WRITE(ctmp4,9300) kt, - zmax(3), is1(1), is1(2), is1(3) 173 WRITE(ctmp5,9400) kt, zmax(4), is2(1), is2(2), is2(3) 174 WRITE(ctmp6,*) ' ===> output of last computed fields in output.abort.nc file' 175 209 WRITE(ctmp6,*) ' ===> output of last computed fields in '//TRIM(Agrif_CFixed())//'_output.abort* files' 210 ENDIF 211 ! 176 212 CALL dia_wri_state( Kmm, 'output.abort' ) ! create an output.abort file 177 178 IF( .NOT. ln_ctl ) THEN 179 WRITE(ctmp8,*) 'E R R O R message from sub-domain: ', narea 180 CALL ctl_stop( 'STOP', ctmp1, ' ', ctmp8, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ctmp6 ) 181 ELSE 182 CALL ctl_stop( ctmp1, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ' ', ctmp6, ' ' ) 183 ENDIF 184 185 kindic = -3 186 ! 187 ENDIF 188 ! 189 9100 FORMAT (' kt=',i8,' |ssh| max: ',1pg11.4,', at i j : ',2i5) 190 9200 FORMAT (' kt=',i8,' |U| max: ',1pg11.4,', at i j k: ',3i5) 191 9300 FORMAT (' kt=',i8,' S min: ',1pg11.4,', at i j k: ',3i5) 192 9400 FORMAT (' kt=',i8,' S max: ',1pg11.4,', at i j k: ',3i5) 213 ! 214 IF( ll_colruns ) THEN ! all processes are synchronized -> use lwp to do the print in opened ocean.output files 215 IF(lwp) CALL ctl_stop( ctmp1, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ' ', ctmp6 ) 216 ELSE ! only mpi subdomains with errors are here -> STOP now 217 CALL ctl_stop( 'STOP', ctmp1, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ' ', ctmp6 ) 218 ENDIF 219 ! 220 IF( nstop == 0 ) nstop = 1 221 ngrdstop = Agrif_Fixed() 222 ! 223 ENDIF 224 ! 225 9100 FORMAT(' kt ',i8,a,1pg11.4,' at i j ',2i6, 6x,' MPI rank',i6) 226 9200 FORMAT(' kt ',i8,a,1pg11.4,' at i j k',2i6, i6,' MPI rank',i6) 193 227 9500 FORMAT(' it :', i8, ' |ssh|_max: ', D23.16, ' |U|_max: ', D23.16,' S_min: ', D23.16,' S_max: ', D23.16) 194 228 !
Note: See TracChangeset
for help on using the changeset viewer.