Changeset 12859
- Timestamp:
- 2020-05-03T11:33:32+02:00 (5 years ago)
- Location:
- NEMO/releases/r4.0/r4.0-HEAD
- Files:
-
- 11 edited
Legend:
- Unmodified
- Added
- Removed
-
NEMO/releases/r4.0/r4.0-HEAD/src/OCE/C1D/step_c1d.F90
r10068 r12859 54 54 ! 55 55 INTEGER :: jk ! dummy loop indice 56 INTEGER :: indic ! error indicator if < 057 56 !! --------------------------------------------------------------------- 58 59 indic = 0 ! reset to no error condition60 57 IF( kstp == nit000 ) CALL iom_init( "nemo") ! iom_put initialization (must be done after nemo_init for AGRIF+XIOS+OASIS) 61 58 IF( kstp /= nit000 ) CALL day( kstp ) ! Calendar (day was already called at nit000 in day_init) … … 131 128 ! Control and restarts 132 129 !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 133 CALL stp_ctl( kstp , indic)130 CALL stp_ctl( kstp ) 134 131 IF( kstp == nit000 ) CALL iom_close( numror ) ! close input ocean restart file 135 132 IF( lrst_oce ) CALL rst_write( kstp ) ! write output ocean restart file 136 133 ! 137 134 #if defined key_iomput 138 IF( kstp == nitend .OR. indic <0 ) CALL xios_context_finalize() ! needed for XIOS135 IF( kstp == nitend .OR. nstop > 0 ) CALL xios_context_finalize() ! needed for XIOS 139 136 ! 140 137 #endif -
NEMO/releases/r4.0/r4.0-HEAD/src/OCE/DOM/dom_oce.F90
r12737 r12859 233 233 Agrif_CFixed = '0' 234 234 END FUNCTION Agrif_CFixed 235 236 INTEGER FUNCTION Agrif_Fixed() 237 Agrif_Fixed = 0 238 END FUNCTION Agrif_Fixed 235 239 #endif 236 240 -
NEMO/releases/r4.0/r4.0-HEAD/src/OCE/IOM/in_out_manager.F90
r11536 r12859 159 159 INTEGER :: no_print = 0 !: optional argument of fld_fill (if present, suppress some control print) 160 160 INTEGER :: nstop = 0 !: error flag (=number of reason for a premature stop run) 161 !$AGRIF_DO_NOT_TREAT 162 INTEGER :: ngrdstop = -1 !: grid number having nstop > 1 163 !$AGRIF_END_DO_NOT_TREAT 161 164 INTEGER :: nwarn = 0 !: warning flag (=number of warning found during the run) 162 165 CHARACTER(lc) :: ctmp1, ctmp2, ctmp3 !: temporary characters 1 to 3 -
NEMO/releases/r4.0/r4.0-HEAD/src/OCE/IOM/iom.F90
r12598 r12859 2460 2460 #else 2461 2461 IF( .FALSE. ) WRITE(numout,*) cdname, pmiss_val ! useless test to avoid compilation warnings 2462 IF( .FALSE. ) pmiss_val = 0._wp ! useless assignment to avoid compilation warnings 2462 2463 #endif 2463 2464 END SUBROUTINE iom_miss_val -
NEMO/releases/r4.0/r4.0-HEAD/src/OCE/LBC/lib_mpp.F90
r12518 r12859 1084 1084 CHARACTER(len=*), INTENT(in ), OPTIONAL :: cd2, cd3, cd4, cd5 1085 1085 CHARACTER(len=*), INTENT(in ), OPTIONAL :: cd6, cd7, cd8, cd9, cd10 1086 ! 1087 INTEGER :: inum 1086 1088 !!---------------------------------------------------------------------- 1087 1089 ! 1088 1090 nstop = nstop + 1 1089 1091 ! 1090 ! force to open ocean.output file if not already opened 1091 IF( numout == 6 ) CALL ctl_opn( numout, 'ocean.output', 'APPEND', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE. ) 1092 IF( numout == 6 ) THEN ! force to open ocean.output file if not already opened 1093 CALL ctl_opn( numout, 'ocean.output', 'APPEND', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE. ) 1094 ELSE 1095 IF( narea > 1 .AND. cd1 == 'STOP' ) THEN ! add an error message in ocean.output 1096 CALL ctl_opn( inum,'ocean.output', 'APPEND', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE. ) 1097 WRITE(inum,*) 1098 WRITE(inum,'(a,i4.4)') ' ===>>> : see E R R O R in ocean.output_', narea - 1 1099 ENDIF 1100 ENDIF 1092 1101 ! 1093 1102 WRITE(numout,*) … … 1117 1126 WRITE(numout,*) 'huge E-R-R-O-R : immediate stop' 1118 1127 WRITE(numout,*) 1128 CALL FLUSH(numout) 1129 CALL SLEEP(60) ! make sure that all output and abort files are written by all cores. 60s should be enough... 1119 1130 CALL mppstop( ld_abort = .true. ) 1120 1131 ENDIF … … 1206 1217 & OPEN(UNIT=knum,FILE='NUL', FORM=cdform, ACCESS=cdacce, STATUS=cdstat , ERR=100, IOSTAT=iost ) 1207 1218 IF( iost == 0 ) THEN 1208 IF(ldwp ) THEN1219 IF(ldwp .AND. kout > 0) THEN 1209 1220 WRITE(kout,*) ' file : ', TRIM(clfile),' open ok' 1210 1221 WRITE(kout,*) ' unit = ', knum -
NEMO/releases/r4.0/r4.0-HEAD/src/OCE/LBC/mpp_loc_generic.h90
r10716 r12859 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 … … 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 ! … … 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/releases/r4.0/r4.0-HEAD/src/OCE/nemogcm.F90
r12640 r12859 179 179 END DO 180 180 ! 181 IF( .NOT. Agrif_Root() ) THEN182 CALL Agrif_ParentGrid_To_ChildGrid()183 IF( ln_diaobs ) CALL dia_obs_wri184 IF( ln_timing ) CALL timing_finalize185 CALL Agrif_ChildGrid_To_ParentGrid()186 ENDIF187 !188 181 # else 189 182 ! … … 230 223 IF( nstop /= 0 .AND. lwp ) THEN ! error print 231 224 WRITE(ctmp1,*) ' ==>>> nemo_gcm: a total of ', nstop, ' errors have been found' 232 CALL ctl_stop( ctmp1 ) 225 IF( ngrdstop > 0 ) THEN 226 WRITE(ctmp9,'(i2)') ngrdstop 227 WRITE(ctmp2,*) ' ==>>> Error detected in Agrif grid '//TRIM(ctmp9) 228 WRITE(ctmp3,*) ' ==>>> look for error messages in '//TRIM(ctmp9)//'_ocean_output* files' 229 CALL ctl_stop( ctmp1, ctmp2, ctmp3 ) 230 ELSE 231 CALL ctl_stop( ctmp1 ) 232 ENDIF 233 233 ENDIF 234 234 ! -
NEMO/releases/r4.0/r4.0-HEAD/src/OCE/step.F90
r12651 r12859 76 76 !!---------------------------------------------------------------------- 77 77 INTEGER :: ji, jj, jk ! dummy loop indice 78 INTEGER :: indic ! error indicator if < 079 78 !!gm kcall can be removed, I guess 80 79 INTEGER :: kcall ! optional integer argument (dom_vvl_sf_nxt) 81 80 !! --------------------------------------------------------------------- 82 81 #if defined key_agrif 83 IF( nstop > 0 ) return ! avoid to go further if an error was detected during previous time step82 IF( nstop > 0 ) RETURN ! avoid to go further if an error was detected during previous time step (child grid) 84 83 kstp = nit000 + Agrif_Nb_Step() 85 84 IF( lk_agrif_debug ) THEN … … 98 97 ! update I/O and calendar 99 98 !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 100 indic = 0 ! reset to no error condition101 102 99 IF( kstp == nit000 ) THEN ! initialize IOM context (must be done after nemo_init for AGRIF+XIOS+OASIS) 103 100 CALL iom_init( cxios_context ) ! for model grid (including passible AGRIF zoom) … … 288 285 ! Control 289 286 !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 290 CALL stp_ctl ( kstp , indic)287 CALL stp_ctl ( kstp ) 291 288 292 289 #if defined key_agrif … … 294 291 ! AGRIF update 295 292 !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 296 IF( Agrif_NbStepint() == 0 .AND. nstop == 0 ) CALL Agrif_update_all( ) ! Update all components 293 IF( Agrif_NbStepint() == 0 .AND. nstop == 0 ) THEN 294 CALL Agrif_update_all( ) ! Update all components 295 ENDIF 297 296 #endif 298 297 … … 312 311 !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 313 312 !!gm why lk_oasis and not lk_cpl ???? 314 IF( lk_oasis 313 IF( lk_oasis .AND. nstop == 0 ) CALL sbc_cpl_snd( kstp ) ! coupled mode : field exchanges 315 314 ! 316 315 #if defined key_iomput … … 318 317 ! Finalize contextes if end of simulation or error detected 319 318 !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 320 IF( kstp == nitend .OR. indic <0 ) THEN321 CALL iom_context_finalize( cxios_context) ! needed for XIOS+AGRIF319 IF( kstp == nitend .OR. nstop > 0 ) THEN 320 CALL iom_context_finalize( cxios_context ) ! needed for XIOS+AGRIF 322 321 IF( lrxios ) CALL iom_context_finalize( crxios_context ) 323 322 IF( ln_crs ) CALL iom_context_finalize( trim(cxios_context)//"_crs" ) ! … … 328 327 ! 329 328 END SUBROUTINE stp 330 329 ! 331 330 !!====================================================================== 332 331 END MODULE step -
NEMO/releases/r4.0/r4.0-HEAD/src/OCE/stpctl.F90
r11407 r12859 34 34 35 35 INTEGER :: idrun, idtime, idssh, idu, ids1, ids2, idt1, idt2, idc1, idw1, istatus 36 LOGICAL :: lsomeoce37 36 !!---------------------------------------------------------------------- 38 37 !! NEMO/OCE 4.0 , NEMO Consortium (2018) … … 42 41 CONTAINS 43 42 44 SUBROUTINE stp_ctl( kt , kindic)43 SUBROUTINE stp_ctl( kt ) 45 44 !!---------------------------------------------------------------------- 46 45 !! *** ROUTINE stp_ctl *** … … 50 49 !! ** Method : - Save the time step in numstp 51 50 !! - Print it each 50 time steps 52 !! - Stop the run IF problem encountered by setting indic=-351 !! - Stop the run IF problem encountered by setting nstop > 0 53 52 !! Problems checked: |ssh| maximum larger than 10 m 54 53 !! |U| maximum larger than 10 m/s … … 57 56 !! ** Actions : "time.step" file = last ocean time-step 58 57 !! "run.stat" file = run statistics 59 !! nstop indicator sheared among all local domain (lk_mpp=T)58 !! nstop indicator sheared among all local domain 60 59 !!---------------------------------------------------------------------- 61 60 INTEGER, INTENT(in ) :: kt ! ocean time-step index 62 INTEGER, INTENT(inout) :: kindic ! error indicator63 61 !! 64 62 INTEGER :: ji, jj, jk ! dummy loop indices 65 INTEGER, DIMENSION(2) :: ih! min/max loc indices66 INTEGER, DIMENSION(3) :: iu, is1, is2 ! min/max loc indices63 INTEGER, DIMENSION(3) :: ih, iu, is1, is2 ! min/max loc indices 64 INTEGER, DIMENSION(9) :: iareasum, iareamin, iareamax 67 65 REAL(wp) :: zzz ! local real 68 REAL(wp), DIMENSION(9) :: zmax 66 REAL(wp), DIMENSION(9) :: zmax, zmaxlocal 69 67 LOGICAL :: ll_wrtstp, ll_colruns, ll_wrtruns 70 68 CHARACTER(len=20) :: clname 71 69 !!---------------------------------------------------------------------- 72 ! 73 ll_wrtstp = ( MOD( kt, sn_cfctl%ptimincr ) == 0 ) .OR. ( kt == nitend ) 74 ll_colruns = ll_wrtstp .AND. ( ln_ctl .OR. sn_cfctl%l_runstat ) 75 ll_wrtruns = ll_colruns .AND. lwm 76 IF( kt == nit000 .AND. lwp ) THEN 77 WRITE(numout,*) 78 WRITE(numout,*) 'stp_ctl : time-stepping control' 79 WRITE(numout,*) '~~~~~~~' 70 IF( nstop > 0 .AND. ngrdstop > -1 ) RETURN ! stpctl was already called by a child grid 71 ! 72 ll_wrtstp = ( MOD( kt-nit000, sn_cfctl%ptimincr ) == 0 ) .OR. ( kt == nitend ) 73 ll_colruns = ll_wrtstp .AND. sn_cfctl%l_runstat .AND. jpnij > 1 74 ll_wrtruns = ( ll_colruns .OR. jpnij == 1 ) .AND. lwm 75 ! 76 IF( kt == nit000 ) THEN 77 ! 78 IF( lwp ) THEN 79 WRITE(numout,*) 80 WRITE(numout,*) 'stp_ctl : time-stepping control' 81 WRITE(numout,*) '~~~~~~~' 82 ENDIF 80 83 ! ! open time.step file 81 84 IF( lwm ) CALL ctl_opn( numstp, 'time.step', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 82 85 ! ! open run.stat file(s) at start whatever 83 86 ! ! the value of sn_cfctl%ptimincr 84 IF( l wm .AND. ( ln_ctl .OR. sn_cfctl%l_runstat )) THEN87 IF( ll_wrtruns ) THEN 85 88 CALL ctl_opn( numrun, 'run.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 86 89 clname = 'run.stat.nc' … … 99 102 ENDIF 100 103 istatus = NF90_ENDDEF(idrun) 101 zmax(8:9) = 0._wp ! initialise to zero in case ln_zad_Aimp option is not in use 102 ENDIF 103 ENDIF 104 IF( kt == nit000 ) lsomeoce = COUNT( ssmask(:,:) == 1._wp ) > 0 104 ENDIF 105 ENDIF 105 106 ! 106 107 IF(lwm .AND. ll_wrtstp) THEN !== current time step ==! ("time.step" file) … … 118 119 zmax(3) = MAXVAL( -tsn(:,:,:,jp_sal) , mask = tmask(:,:,:) == 1._wp ) ! minus salinity max 119 120 zmax(4) = MAXVAL( tsn(:,:,:,jp_sal) , mask = tmask(:,:,:) == 1._wp ) ! salinity max 120 zmax(5) = MAXVAL( -tsn(:,:,:,jp_tem) , mask = tmask(:,:,:) == 1._wp ) ! minus temperature max 121 zmax(6) = MAXVAL( tsn(:,:,:,jp_tem) , mask = tmask(:,:,:) == 1._wp ) ! temperature max 121 IF( ll_colruns ) THEN ! following variables are used only in the netcdf file 122 zmax(5) = MAXVAL( -tsn(:,:,:,jp_tem) , mask = tmask(:,:,:) == 1._wp ) ! minus temperature max 123 zmax(6) = MAXVAL( tsn(:,:,:,jp_tem) , mask = tmask(:,:,:) == 1._wp ) ! temperature max 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 ELSE 128 zmax(8:9) = 0._wp 129 ENDIF 130 ELSE 131 zmax(5:9) = 0._wp 132 ENDIF 122 133 zmax(7) = REAL( nstop , wp ) ! stop indicator 123 IF( ln_zad_Aimp ) THEN124 zmax(8) = MAXVAL( ABS( wi(:,:,:) ) , mask = wmask(:,:,:) == 1._wp ) ! implicit vertical vel. max125 zmax(9) = MAXVAL( Cu_adv(:,:,:) , mask = tmask(:,:,:) == 1._wp ) ! partitioning coeff. max126 ENDIF127 134 ! 128 135 IF( ll_colruns ) THEN 136 zmaxlocal(:) = zmax(:) 129 137 CALL mpp_max( "stpctl", zmax ) ! max over the global domain 130 138 nstop = NINT( zmax(7) ) ! nstop indicator sheared among all local domains … … 143 151 istatus = NF90_PUT_VAR( idrun, idc1, (/ zmax(9)/), (/kt/), (/1/) ) 144 152 ENDIF 145 IF( MOD( kt , 100 ) == 0 ) istatus = NF90_SYNC(idrun) 146 IF( kt == nitend ) istatus = NF90_CLOSE(idrun) 153 IF( kt == nitend ) istatus = NF90_CLOSE(idrun) 147 154 END IF 148 155 ! !== error handling ==! 149 IF( ( ln_ctl .OR. lsomeoce ) .AND. ( & ! have use mpp_max (because ln_ctl=.T.) or contains some ocean points 150 & zmax(1) > 20._wp .OR. & ! too large sea surface height ( > 20 m ) 156 IF( zmax(1) > 20._wp .OR. & ! too large sea surface height ( > 20 m ) 151 157 & zmax(2) > 10._wp .OR. & ! too large velocity ( > 10 m/s) 152 158 & zmax(3) >= 0._wp .OR. & ! negative or zero sea surface salinity 153 159 & zmax(4) >= 100._wp .OR. & ! too large sea surface salinity ( > 100 ) 154 160 & zmax(4) < 0._wp .OR. & ! too large sea surface salinity (keep this line for sea-ice) 155 & ISNAN( zmax(1) + zmax(2) + zmax(3) ) ) ) THEN ! NaN encounter in the tests 156 IF( lk_mpp .AND. ln_ctl ) THEN 157 CALL mpp_maxloc( 'stpctl', ABS(sshn) , ssmask(:,:) , zzz, ih ) 161 & ISNAN( zmax(1) + zmax(2) + zmax(3) ) .OR. & ! NaN encounter in the tests 162 & ABS( zmax(1) + zmax(2) + zmax(3) ) > HUGE(1._wp) ) THEN ! Infinity encounter in the tests 163 IF( ll_colruns ) THEN 164 ! first: close the netcdf file, so we can read it 165 IF( lwm .AND. kt /= nitend ) istatus = NF90_CLOSE(idrun) 166 CALL mpp_maxloc( 'stpctl', ABS(sshn) , ssmask(:,:) , zzz, ih(1:2) ) ; ih(3) = 0 158 167 CALL mpp_maxloc( 'stpctl', ABS(un) , umask (:,:,:), zzz, iu ) 159 168 CALL mpp_minloc( 'stpctl', tsn(:,:,:,jp_sal), tmask (:,:,:), zzz, is1 ) 160 169 CALL mpp_maxloc( 'stpctl', tsn(:,:,:,jp_sal), tmask (:,:,:), zzz, is2 ) 170 ! find which subdomain has the max. 171 iareamin(:) = jpnij+1 ; iareamax(:) = 0 ; iareasum(:) = 0 172 DO ji = 1, 9 173 IF( zmaxlocal(ji) == zmax(ji) ) THEN 174 iareamin(ji) = narea ; iareamax(ji) = narea ; iareasum(ji) = 1 175 ENDIF 176 END DO 177 CALL mpp_min( "stpctl", iareamin ) ! min over the global domain 178 CALL mpp_max( "stpctl", iareamax ) ! max over the global domain 179 CALL mpp_sum( "stpctl", iareasum ) ! sum over the global domain 161 180 ELSE 162 ih( :) = MAXLOC( ABS( sshn(:,:) ) ) + (/ nimpp - 1, njmpp - 1 /)181 ih(1:2)= MAXLOC( ABS( sshn(:,:) ) ) + (/ nimpp - 1, njmpp - 1 /) ; ih(3) = 0 163 182 iu(:) = MAXLOC( ABS( un (:,:,:) ) ) + (/ nimpp - 1, njmpp - 1, 0 /) 164 183 is1(:) = MINLOC( tsn(:,:,:,jp_sal), mask = tmask(:,:,:) == 1._wp ) + (/ nimpp - 1, njmpp - 1, 0 /) 165 184 is2(:) = MAXLOC( tsn(:,:,:,jp_sal), mask = tmask(:,:,:) == 1._wp ) + (/ nimpp - 1, njmpp - 1, 0 /) 166 ENDIF 167 185 iareamin(:) = narea ; iareamax(:) = narea ; iareasum(:) = 1 ! this is local information 186 ENDIF 187 ! 168 188 WRITE(ctmp1,*) ' stp_ctl: |ssh| > 20 m or |U| > 10 m/s or S <= 0 or S >= 100 or NaN encounter in the tests' 169 WRITE(ctmp2,9100) kt, zmax(1), ih(1) , ih(2) 170 WRITE(ctmp3,9200) kt, zmax(2), iu(1) , iu(2) , iu(3) 171 WRITE(ctmp4,9300) kt, - zmax(3), is1(1), is1(2), is1(3) 172 WRITE(ctmp5,9400) kt, zmax(4), is2(1), is2(2), is2(3) 173 WRITE(ctmp6,*) ' ===> output of last computed fields in output.abort.nc file' 174 175 CALL dia_wri_state( 'output.abort' ) ! create an output.abort file 176 177 IF( .NOT. ln_ctl ) THEN 178 WRITE(ctmp8,*) 'E R R O R message from sub-domain: ', narea 179 CALL ctl_stop( 'STOP', ctmp1, ' ', ctmp8, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ctmp6 ) 189 CALL wrt_line(ctmp2, kt, ' |ssh| max ', zmax(1), ih , iareasum(1), iareamin(1), iareamax(1) ) 190 CALL wrt_line(ctmp3, kt, ' |U| max ', zmax(2), iu , iareasum(2), iareamin(2), iareamax(2) ) 191 CALL wrt_line(ctmp4, kt, ' Sal min ', - zmax(3), is1, iareasum(3), iareamin(3), iareamax(3) ) 192 CALL wrt_line(ctmp5, kt, ' Sal max ', zmax(4), is2, iareasum(4), iareamin(4), iareamax(4) ) 193 IF( Agrif_Root() ) THEN 194 WRITE(ctmp6,*) ' ===> output of last computed fields in output.abort* files' 180 195 ELSE 181 CALL ctl_stop( ctmp1, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ' ', ctmp6, ' ' ) 182 ENDIF 183 184 kindic = -3 185 ! 186 ENDIF 187 ! 188 9100 FORMAT (' kt=',i8,' |ssh| max: ',1pg11.4,', at i j : ',2i5) 189 9200 FORMAT (' kt=',i8,' |U| max: ',1pg11.4,', at i j k: ',3i5) 190 9300 FORMAT (' kt=',i8,' S min: ',1pg11.4,', at i j k: ',3i5) 191 9400 FORMAT (' kt=',i8,' S max: ',1pg11.4,', at i j k: ',3i5) 196 WRITE(ctmp6,*) ' ===> output of last computed fields in '//TRIM(Agrif_CFixed())//'_output.abort* files' 197 ENDIF 198 ! 199 CALL dia_wri_state( 'output.abort' ) ! create an output.abort file 200 ! 201 IF( ll_colruns .or. jpnij == 1 ) THEN ! all processes synchronized -> use lwp to print in opened ocean.output files 202 IF(lwp) CALL ctl_stop( ctmp1, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ' ', ctmp6 ) 203 ELSE ! only mpi subdomains with errors are here -> STOP now 204 CALL ctl_stop( 'STOP', ctmp1, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ' ', ctmp6 ) 205 ENDIF 206 ! 207 IF( nstop == 0 ) nstop = 1 208 ngrdstop = Agrif_Fixed() 209 ! 210 ENDIF 211 ! 192 212 9500 FORMAT(' it :', i8, ' |ssh|_max: ', D23.16, ' |U|_max: ', D23.16,' S_min: ', D23.16,' S_max: ', D23.16) 193 213 ! 194 214 END SUBROUTINE stp_ctl 215 216 217 SUBROUTINE wrt_line( cdline, kt, cdprefix, pval, kloc, ksum, kmin, kmax ) 218 !!---------------------------------------------------------------------- 219 !! *** ROUTINE wrt_line *** 220 !! 221 !! ** Purpose : write information line 222 !! 223 !!---------------------------------------------------------------------- 224 CHARACTER(len=*), INTENT( out) :: cdline 225 CHARACTER(len=*), INTENT(in ) :: cdprefix 226 REAL(wp), INTENT(in ) :: pval 227 INTEGER, DIMENSION(3), INTENT(in ) :: kloc 228 INTEGER, INTENT(in ) :: kt, ksum, kmin, kmax 229 ! 230 CHARACTER(len=80) :: clsuff 231 CHARACTER(len=9 ) :: clkt, clsum, clmin, clmax 232 CHARACTER(len=9 ) :: cli, clj, clk 233 CHARACTER(len=1 ) :: clfmt 234 CHARACTER(len=4 ) :: cl4 ! needed to be able to compile with Agrif, I don't know why 235 INTEGER :: ifmtk 236 !!---------------------------------------------------------------------- 237 WRITE(clkt , '(i9)') kt 238 239 WRITE(clfmt, '(i1)') INT(LOG10(REAL(jpnij ,wp))) + 1 ! how many digits to we need to write ? (we decide max = 9) 240 !!! WRITE(clsum, '(i'//clfmt//')') ksum ! this is creating a compilation error with AGRIF 241 cl4 = '(i'//clfmt//')' ; WRITE(clsum, cl4) ksum 242 WRITE(clfmt, '(i1)') INT(LOG10(REAL(jpnij-1,wp))) + 1 ! how many digits to we need to write ? (we decide max = 9) 243 cl4 = '(i'//clfmt//')' ; WRITE(clmin, cl4) kmin-1 244 WRITE(clmax, cl4) kmax-1 245 ! 246 WRITE(clfmt, '(i1)') INT(LOG10(REAL(jpiglo,wp))) + 1 ! how many digits to we need to write jpiglo? (we decide max = 9) 247 cl4 = '(i'//clfmt//')' ; WRITE(cli, cl4) kloc(1) ! this is ok with AGRIF 248 WRITE(clfmt, '(i1)') INT(LOG10(REAL(jpjglo,wp))) + 1 ! how many digits to we need to write jpjglo? (we decide max = 9) 249 cl4 = '(i'//clfmt//')' ; WRITE(clj, cl4) kloc(2) ! this is ok with AGRIF 250 ! 251 IF( ksum == 1 ) THEN ; WRITE(clsuff,9100) TRIM(clmin) 252 ELSE ; WRITE(clsuff,9200) TRIM(clsum), TRIM(clmin), TRIM(clmax) 253 ENDIF 254 IF(kloc(3) == 0) THEN 255 ifmtk = INT(LOG10(REAL(jpk,wp))) + 1 ! how many digits to we need to write jpk? (we decide max = 9) 256 clk = REPEAT(' ', ifmtk) ! create the equivalent in blank string 257 WRITE(cdline,9300) TRIM(ADJUSTL(clkt)), TRIM(ADJUSTL(cdprefix)), pval, TRIM(cli), TRIM(clj), clk(1:ifmtk), TRIM(clsuff) 258 ELSE 259 WRITE(clfmt, '(i1)') INT(LOG10(REAL(jpk,wp))) + 1 ! how many digits to we need to write jpk? (we decide max = 9) 260 !!! WRITE(clk, '(i'//clfmt//')') kloc(3) ! this is creating a compilation error with AGRIF 261 cl4 = '(i'//clfmt//')' ; WRITE(clk, cl4) kloc(3) ! this is ok with AGRIF 262 WRITE(cdline,9400) TRIM(ADJUSTL(clkt)), TRIM(ADJUSTL(cdprefix)), pval, TRIM(cli), TRIM(clj), TRIM(clk), TRIM(clsuff) 263 ENDIF 264 ! 265 9100 FORMAT('MPI rank ', a) 266 9200 FORMAT('found in ', a, ' MPI tasks, spread out among ranks ', a, ' to ', a) 267 9300 FORMAT('kt ', a, ' ', a, ' ', 1pg11.4, ' at i j ', a, ' ', a, ' ', a, ' ', a) 268 9400 FORMAT('kt ', a, ' ', a, ' ', 1pg11.4, ' at i j k ', a, ' ', a, ' ', a, ' ', a) 269 ! 270 END SUBROUTINE wrt_line 271 195 272 196 273 !!====================================================================== -
NEMO/releases/r4.0/r4.0-HEAD/src/SAS/stpctl.F90
r10603 r12859 32 32 33 33 INTEGER :: idrun, idtime, idssh, idu, ids, istatus 34 LOGICAL :: lsomeoce35 34 !!---------------------------------------------------------------------- 36 35 !! NEMO/SAS 4.0 , NEMO Consortium (2018) … … 62 61 !!---------------------------------------------------------------------- 63 62 ! 64 ll_wrtstp = ( MOD( kt, sn_cfctl%ptimincr ) == 0 ) .OR. ( kt == nitend ) 65 ll_colruns = ll_wrtstp .AND. ( ln_ctl .OR. sn_cfctl%l_runstat ) 66 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,*) '~~~~~~~' 63 ll_wrtstp = ( MOD( kt-nit000, sn_cfctl%ptimincr ) == 0 ) .OR. ( kt == nitend ) 64 ll_colruns = ll_wrtstp .AND. sn_cfctl%l_runstat .AND. jpnij > 1 65 ll_wrtruns = ( ll_colruns .OR. jpnij == 1 ) .AND. lwm 66 ! 67 IF( kt == nit000 ) THEN 68 ! 69 IF( lwp ) THEN 70 WRITE(numout,*) 71 WRITE(numout,*) 'stp_ctl : time-stepping control' 72 WRITE(numout,*) '~~~~~~~' 73 ENDIF 71 74 ! ! open time.step file 72 75 IF( lwm ) CALL ctl_opn( numstp, 'time.step', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 73 76 ! ! open run.stat file(s) at start whatever 74 77 ! ! the value of sn_cfctl%ptimincr 75 IF( l wm .AND. ( ln_ctl .OR. sn_cfctl%l_runstat )) THEN78 IF( ll_wrtruns ) THEN 76 79 CALL ctl_opn( numrun, 'run.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 77 80 clname = 'run.stat.nc' … … 85 88 ENDIF 86 89 ENDIF 87 IF( kt == nit000 ) lsomeoce = COUNT( ssmask(:,:) == 1._wp ) > 088 90 ! 89 91 IF(lwm .AND. ll_wrtstp) THEN !== current time step ==! ("time.step" file) … … 92 94 ENDIF 93 95 ! !== test of extrema ==! 94 IF( ll_colruns ) THEN96 IF( ll_colruns .OR. jpnij == 1 ) THEN 95 97 zmax(1) = MAXVAL( vt_i (:,:) ) ! max ice thickness 96 98 zmax(2) = MAXVAL( ABS( u_ice(:,:) ) ) ! max ice velocity (zonal only) 97 99 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 domain100 IF( ll_colruns ) CALL mpp_max( "stpctl", zmax ) ! max over the global domain 99 101 END IF 100 102 ! !== run statistics ==! ("run.stat" file) -
NEMO/releases/r4.0/r4.0-HEAD/tests/CANAL/MY_SRC/stpctl.F90
r10572 r12859 34 34 35 35 INTEGER :: idrun, idtime, idssh, idu, ids1, ids2, idt1, idt2, idc1, idw1, istatus 36 LOGICAL :: lsomeoce37 36 !!---------------------------------------------------------------------- 38 37 !! NEMO/OCE 4.0 , NEMO Consortium (2018) … … 42 41 CONTAINS 43 42 44 SUBROUTINE stp_ctl( kt , kindic)43 SUBROUTINE stp_ctl( kt ) 45 44 !!---------------------------------------------------------------------- 46 45 !! *** ROUTINE stp_ctl *** … … 50 49 !! ** Method : - Save the time step in numstp 51 50 !! - Print it each 50 time steps 52 !! - Stop the run IF problem encountered by setting indic=-351 !! - Stop the run IF problem encountered by setting nstop > 0 53 52 !! Problems checked: |ssh| maximum larger than 10 m 54 53 !! |U| maximum larger than 10 m/s … … 57 56 !! ** Actions : "time.step" file = last ocean time-step 58 57 !! "run.stat" file = run statistics 59 !! nstop indicator sheared among all local domain (lk_mpp=T)58 !! nstop indicator sheared among all local domain 60 59 !!---------------------------------------------------------------------- 61 60 INTEGER, INTENT(in ) :: kt ! ocean time-step index 62 INTEGER, INTENT(inout) :: kindic ! error indicator63 61 !! 64 62 INTEGER :: ji, jj, jk ! dummy loop indices 65 INTEGER, DIMENSION(2) :: ih! min/max loc indices66 INTEGER, DIMENSION(3) :: iu, is1, is2 ! min/max loc indices63 INTEGER, DIMENSION(3) :: ih, iu, is1, is2 ! min/max loc indices 64 INTEGER, DIMENSION(9) :: iareasum, iareamin, iareamax 67 65 REAL(wp) :: zzz ! local real 68 REAL(wp), DIMENSION(9) :: zmax 66 REAL(wp), DIMENSION(9) :: zmax, zmaxlocal 69 67 LOGICAL :: ll_wrtstp, ll_colruns, ll_wrtruns 70 68 CHARACTER(len=20) :: clname 71 69 !!---------------------------------------------------------------------- 72 ! 73 ll_wrtstp = ( MOD( kt, sn_cfctl%ptimincr ) == 0 ) .OR. ( kt == nitend ) 74 ll_colruns = ll_wrtstp .AND. ( ln_ctl .OR. sn_cfctl%l_runstat ) 75 ll_wrtruns = ll_colruns .AND. lwm 76 IF( kt == nit000 .AND. lwp ) THEN 77 WRITE(numout,*) 78 WRITE(numout,*) 'stp_ctl : time-stepping control' 79 WRITE(numout,*) '~~~~~~~' 70 IF( nstop > 0 .AND. ngrdstop > -1 ) RETURN ! stpctl was already called by a child grid 71 ! 72 ll_wrtstp = ( MOD( kt-nit000, sn_cfctl%ptimincr ) == 0 ) .OR. ( kt == nitend ) 73 ll_colruns = ll_wrtstp .AND. sn_cfctl%l_runstat .AND. jpnij > 1 74 ll_wrtruns = ( ll_colruns .OR. jpnij == 1 ) .AND. lwm 75 ! 76 IF( kt == nit000 ) THEN 77 ! 78 IF( lwp ) THEN 79 WRITE(numout,*) 80 WRITE(numout,*) 'stp_ctl : time-stepping control' 81 WRITE(numout,*) '~~~~~~~' 82 ENDIF 80 83 ! ! open time.step file 81 84 IF( lwm ) CALL ctl_opn( numstp, 'time.step', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 82 85 ! ! open run.stat file(s) at start whatever 83 86 ! ! the value of sn_cfctl%ptimincr 84 IF( l wm .AND. ( ln_ctl .OR. sn_cfctl%l_runstat )) THEN87 IF( ll_wrtruns ) THEN 85 88 CALL ctl_opn( numrun, 'run.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 86 89 clname = 'run.stat.nc' … … 96 99 IF( ln_zad_Aimp ) THEN 97 100 istatus = NF90_DEF_VAR( idrun, 'abs_wi_max', NF90_DOUBLE, (/ idtime /), idw1 ) 98 istatus = NF90_DEF_VAR( idrun, 'C u_max', NF90_DOUBLE, (/ idtime /), idc1 )101 istatus = NF90_DEF_VAR( idrun, 'Cf_max', NF90_DOUBLE, (/ idtime /), idc1 ) 99 102 ENDIF 100 103 istatus = NF90_ENDDEF(idrun) 101 zmax(8:9) = 0._wp ! initialise to zero in case ln_zad_Aimp option is not in use 102 ENDIF 103 ENDIF 104 IF( kt == nit000 ) lsomeoce = COUNT( ssmask(:,:) == 1._wp ) > 0 104 ENDIF 105 ENDIF 105 106 ! 106 107 IF(lwm .AND. ll_wrtstp) THEN !== current time step ==! ("time.step" file) … … 118 119 zmax(3) = MAXVAL( -tsn(:,:,:,jp_sal) , mask = tmask(:,:,:) == 1._wp ) ! minus salinity max 119 120 zmax(4) = MAXVAL( tsn(:,:,:,jp_sal) , mask = tmask(:,:,:) == 1._wp ) ! salinity max 120 zmax(5) = MAXVAL( -tsn(:,:,:,jp_tem) , mask = tmask(:,:,:) == 1._wp ) ! minus temperature max 121 zmax(6) = MAXVAL( tsn(:,:,:,jp_tem) , mask = tmask(:,:,:) == 1._wp ) ! temperature max 121 IF( ll_colruns ) THEN ! following variables are used only in the netcdf file 122 zmax(5) = MAXVAL( -tsn(:,:,:,jp_tem) , mask = tmask(:,:,:) == 1._wp ) ! minus temperature max 123 zmax(6) = MAXVAL( tsn(:,:,:,jp_tem) , mask = tmask(:,:,:) == 1._wp ) ! temperature max 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 ELSE 128 zmax(8:9) = 0._wp 129 ENDIF 130 ELSE 131 zmax(5:9) = 0._wp 132 ENDIF 122 133 zmax(7) = REAL( nstop , wp ) ! stop indicator 123 IF( ln_zad_Aimp ) THEN124 zmax(8) = MAXVAL( ABS( wi(:,:,:) ) , mask = wmask(:,:,:) == 1._wp ) ! implicit vertical vel. max125 zmax(9) = MAXVAL( Cu_adv(:,:,:) , mask = tmask(:,:,:) == 1._wp ) ! cell Courant no. max126 ENDIF127 134 ! 128 135 IF( ll_colruns ) THEN 136 zmaxlocal(:) = zmax(:) 129 137 CALL mpp_max( "stpctl", zmax ) ! max over the global domain 130 138 nstop = NINT( zmax(7) ) ! nstop indicator sheared among all local domains … … 143 151 istatus = NF90_PUT_VAR( idrun, idc1, (/ zmax(9)/), (/kt/), (/1/) ) 144 152 ENDIF 145 IF( MOD( kt , 100 ) == 0 ) istatus = NF90_SYNC(idrun) 146 IF( kt == nitend ) istatus = NF90_CLOSE(idrun) 153 IF( kt == nitend ) istatus = NF90_CLOSE(idrun) 147 154 END IF 148 155 ! !== error handling ==! 149 IF( ( ln_ctl .OR. lsomeoce ) .AND. ( & ! have use mpp_max (because ln_ctl=.T.) or contains some ocean points 150 & zmax(1) > 50._wp .OR. & ! too large sea surface height ( > 50 m ) 151 & zmax(2) > 20._wp .OR. & ! too large velocity ( > 20 m/s) 156 IF( zmax(1) > 20._wp .OR. & ! too large sea surface height ( > 20 m ) 157 & zmax(2) > 10._wp .OR. & ! too large velocity ( > 10 m/s) 152 158 !!$ & zmax(3) >= 0._wp .OR. & ! negative or zero sea surface salinity 153 159 !!$ & zmax(4) >= 100._wp .OR. & ! too large sea surface salinity ( > 100 ) 154 160 !!$ & zmax(4) < 0._wp .OR. & ! too large sea surface salinity (keep this line for sea-ice) 155 & ISNAN( zmax(1) + zmax(2) + zmax(3) ) ) ) THEN ! NaN encounter in the tests 156 IF( lk_mpp .AND. ln_ctl ) THEN 157 CALL mpp_maxloc( 'stpctl', ABS(sshn) , ssmask(:,:) , zzz, ih ) 161 & ISNAN( zmax(1) + zmax(2) + zmax(3) ) .OR. & ! NaN encounter in the tests 162 & ABS( zmax(1) + zmax(2) + zmax(3) ) > HUGE(1._wp) ) THEN ! Infinity encounter in the tests 163 IF( ll_colruns ) THEN 164 ! first: close the netcdf file, so we can read it 165 IF( lwm .AND. kt /= nitend ) istatus = NF90_CLOSE(idrun) 166 CALL mpp_maxloc( 'stpctl', ABS(sshn) , ssmask(:,:) , zzz, ih(1:2) ) ; ih(3) = 0 158 167 CALL mpp_maxloc( 'stpctl', ABS(un) , umask (:,:,:), zzz, iu ) 159 168 CALL mpp_minloc( 'stpctl', tsn(:,:,:,jp_sal), tmask (:,:,:), zzz, is1 ) 160 169 CALL mpp_maxloc( 'stpctl', tsn(:,:,:,jp_sal), tmask (:,:,:), zzz, is2 ) 170 ! find which subdomain has the max. 171 iareamin(:) = jpnij+1 ; iareamax(:) = 0 ; iareasum(:) = 0 172 DO ji = 1, 9 173 IF( zmaxlocal(ji) == zmax(ji) ) THEN 174 iareamin(ji) = narea ; iareamax(ji) = narea ; iareasum(ji) = 1 175 ENDIF 176 END DO 177 CALL mpp_min( "stpctl", iareamin ) ! min over the global domain 178 CALL mpp_max( "stpctl", iareamax ) ! max over the global domain 179 CALL mpp_sum( "stpctl", iareasum ) ! sum over the global domain 161 180 ELSE 162 ih( :) = MAXLOC( ABS( sshn(:,:) ) ) + (/ nimpp - 1, njmpp - 1 /)181 ih(1:2)= MAXLOC( ABS( sshn(:,:) ) ) + (/ nimpp - 1, njmpp - 1 /) ; ih(3) = 0 163 182 iu(:) = MAXLOC( ABS( un (:,:,:) ) ) + (/ nimpp - 1, njmpp - 1, 0 /) 164 183 is1(:) = MINLOC( tsn(:,:,:,jp_sal), mask = tmask(:,:,:) == 1._wp ) + (/ nimpp - 1, njmpp - 1, 0 /) 165 184 is2(:) = MAXLOC( tsn(:,:,:,jp_sal), mask = tmask(:,:,:) == 1._wp ) + (/ nimpp - 1, njmpp - 1, 0 /) 166 ENDIF 167 168 WRITE(ctmp1,*) ' stp_ctl: |ssh| > 50 m or |U| > 20 m/s or NaN encounter in the tests' 169 WRITE(ctmp2,9100) kt, zmax(1), ih(1) , ih(2) 170 WRITE(ctmp3,9200) kt, zmax(2), iu(1) , iu(2) , iu(3) 171 WRITE(ctmp4,9300) kt, - zmax(3), is1(1), is1(2), is1(3) 172 WRITE(ctmp5,9400) kt, zmax(4), is2(1), is2(2), is2(3) 173 WRITE(ctmp6,*) ' ===> output of last computed fields in output.abort.nc file' 174 175 CALL dia_wri_state( 'output.abort' ) ! create an output.abort file 176 177 IF( .NOT. ln_ctl ) THEN 178 WRITE(ctmp8,*) 'E R R O R message from sub-domain: ', narea 179 CALL ctl_stop( 'STOP', ctmp1, ' ', ctmp8, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ctmp6 ) 185 iareamin(:) = narea ; iareamax(:) = narea ; iareasum(:) = 1 ! this is local information 186 ENDIF 187 ! 188 WRITE(ctmp1,*) ' stp_ctl: |ssh| > 20 m or |U| > 10 m/s or S <= 0 or S >= 100 or NaN encounter in the tests' 189 CALL wrt_line(ctmp2, kt, ' |ssh| max ', zmax(1), ih , iareasum(1), iareamin(1), iareamax(1) ) 190 CALL wrt_line(ctmp3, kt, ' |U| max ', zmax(2), iu , iareasum(2), iareamin(2), iareamax(2) ) 191 CALL wrt_line(ctmp4, kt, ' Sal min ', - zmax(3), is1, iareasum(3), iareamin(3), iareamax(3) ) 192 CALL wrt_line(ctmp5, kt, ' Sal max ', zmax(4), is2, iareasum(4), iareamin(4), iareamax(4) ) 193 IF( Agrif_Root() ) THEN 194 WRITE(ctmp6,*) ' ===> output of last computed fields in output.abort* files' 180 195 ELSE 181 CALL ctl_stop( ctmp1, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ' ', ctmp6, ' ' ) 182 ENDIF 183 184 kindic = -3 185 ! 186 ENDIF 187 ! 188 9100 FORMAT (' kt=',i8,' |ssh| max: ',1pg11.4,', at i j : ',2i5) 189 9200 FORMAT (' kt=',i8,' |U| max: ',1pg11.4,', at i j k: ',3i5) 190 9300 FORMAT (' kt=',i8,' S min: ',1pg11.4,', at i j k: ',3i5) 191 9400 FORMAT (' kt=',i8,' S max: ',1pg11.4,', at i j k: ',3i5) 196 WRITE(ctmp6,*) ' ===> output of last computed fields in '//TRIM(Agrif_CFixed())//'_output.abort* files' 197 ENDIF 198 ! 199 CALL dia_wri_state( 'output.abort' ) ! create an output.abort file 200 ! 201 IF( ll_colruns .or. jpnij == 1 ) THEN ! all processes synchronized -> use lwp to print in opened ocean.output files 202 IF(lwp) CALL ctl_stop( ctmp1, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ' ', ctmp6 ) 203 ELSE ! only mpi subdomains with errors are here -> STOP now 204 CALL ctl_stop( 'STOP', ctmp1, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ' ', ctmp6 ) 205 ENDIF 206 ! 207 IF( nstop == 0 ) nstop = 1 208 ngrdstop = Agrif_Fixed() 209 ! 210 ENDIF 211 ! 192 212 9500 FORMAT(' it :', i8, ' |ssh|_max: ', D23.16, ' |U|_max: ', D23.16,' S_min: ', D23.16,' S_max: ', D23.16) 193 213 ! 194 214 END SUBROUTINE stp_ctl 215 216 217 SUBROUTINE wrt_line( cdline, kt, cdprefix, pval, kloc, ksum, kmin, kmax ) 218 !!---------------------------------------------------------------------- 219 !! *** ROUTINE wrt_line *** 220 !! 221 !! ** Purpose : write information line 222 !! 223 !!---------------------------------------------------------------------- 224 CHARACTER(len=*), INTENT( out) :: cdline 225 CHARACTER(len=*), INTENT(in ) :: cdprefix 226 REAL(wp), INTENT(in ) :: pval 227 INTEGER, DIMENSION(3), INTENT(in ) :: kloc 228 INTEGER, INTENT(in ) :: kt, ksum, kmin, kmax 229 ! 230 CHARACTER(len=80) :: clsuff 231 CHARACTER(len=9 ) :: clkt, clsum, clmin, clmax 232 CHARACTER(len=9 ) :: cli, clj, clk 233 CHARACTER(len=1 ) :: clfmt 234 CHARACTER(len=4 ) :: cl4 ! needed to be able to compile with Agrif, I don't know why 235 INTEGER :: ifmtk 236 !!---------------------------------------------------------------------- 237 WRITE(clkt , '(i9)') kt 238 239 WRITE(clfmt, '(i1)') INT(LOG10(REAL(jpnij ,wp))) + 1 ! how many digits to we need to write ? (we decide max = 9) 240 !!! WRITE(clsum, '(i'//clfmt//')') ksum ! this is creating a compilation error with AGRIF 241 cl4 = '(i'//clfmt//')' ; WRITE(clsum, cl4) ksum 242 WRITE(clfmt, '(i1)') INT(LOG10(REAL(jpnij-1,wp))) + 1 ! how many digits to we need to write ? (we decide max = 9) 243 cl4 = '(i'//clfmt//')' ; WRITE(clmin, cl4) kmin-1 244 WRITE(clmax, cl4) kmax-1 245 ! 246 WRITE(clfmt, '(i1)') INT(LOG10(REAL(jpiglo,wp))) + 1 ! how many digits to we need to write jpiglo? (we decide max = 9) 247 cl4 = '(i'//clfmt//')' ; WRITE(cli, cl4) kloc(1) ! this is ok with AGRIF 248 WRITE(clfmt, '(i1)') INT(LOG10(REAL(jpjglo,wp))) + 1 ! how many digits to we need to write jpjglo? (we decide max = 9) 249 cl4 = '(i'//clfmt//')' ; WRITE(clj, cl4) kloc(2) ! this is ok with AGRIF 250 ! 251 IF( ksum == 1 ) THEN ; WRITE(clsuff,9100) TRIM(clmin) 252 ELSE ; WRITE(clsuff,9200) TRIM(clsum), TRIM(clmin), TRIM(clmax) 253 ENDIF 254 IF(kloc(3) == 0) THEN 255 ifmtk = INT(LOG10(REAL(jpk,wp))) + 1 ! how many digits to we need to write jpk? (we decide max = 9) 256 clk = REPEAT(' ', ifmtk) ! create the equivalent in blank string 257 WRITE(cdline,9300) TRIM(ADJUSTL(clkt)), TRIM(ADJUSTL(cdprefix)), pval, TRIM(cli), TRIM(clj), clk(1:ifmtk), TRIM(clsuff) 258 ELSE 259 WRITE(clfmt, '(i1)') INT(LOG10(REAL(jpk,wp))) + 1 ! how many digits to we need to write jpk? (we decide max = 9) 260 !!! WRITE(clk, '(i'//clfmt//')') kloc(3) ! this is creating a compilation error with AGRIF 261 cl4 = '(i'//clfmt//')' ; WRITE(clk, cl4) kloc(3) ! this is ok with AGRIF 262 WRITE(cdline,9400) TRIM(ADJUSTL(clkt)), TRIM(ADJUSTL(cdprefix)), pval, TRIM(cli), TRIM(clj), TRIM(clk), TRIM(clsuff) 263 ENDIF 264 ! 265 9100 FORMAT('MPI rank ', a) 266 9200 FORMAT('found in ', a, ' MPI tasks, spread out among ranks ', a, ' to ', a) 267 9300 FORMAT('kt ', a, ' ', a, ' ', 1pg11.4, ' at i j ', a, ' ', a, ' ', a, ' ', a) 268 9400 FORMAT('kt ', a, ' ', a, ' ', 1pg11.4, ' at i j k ', a, ' ', a, ' ', a, ' ', a) 269 ! 270 END SUBROUTINE wrt_line 271 195 272 196 273 !!======================================================================
Note: See TracChangeset
for help on using the changeset viewer.