stpctl.F90 9.5 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223
  1. MODULE stpctl
  2. !!======================================================================
  3. !! *** MODULE stpctl ***
  4. !! Ocean run control : gross check of the ocean time stepping
  5. !!======================================================================
  6. !! History : OPA ! 1991-03 (G. Madec) Original code
  7. !! 6.0 ! 1992-06 (M. Imbard)
  8. !! 8.0 ! 1997-06 (A.M. Treguier)
  9. !! NEMO 1.0 ! 2002-06 (G. Madec) F90: Free form and module
  10. !! 2.0 ! 2009-07 (G. Madec) Add statistic for time-spliting
  11. !!----------------------------------------------------------------------
  12. !!----------------------------------------------------------------------
  13. !! stp_ctl : Control the run
  14. !!----------------------------------------------------------------------
  15. USE oce ! ocean dynamics and tracers variables
  16. USE dom_oce ! ocean space and time domain variables
  17. USE sol_oce ! ocean space and time domain variables
  18. USE sbc_oce ! surface boundary conditions variables
  19. USE in_out_manager ! I/O manager
  20. USE lbclnk ! ocean lateral boundary conditions (or mpp link)
  21. USE lib_mpp ! distributed memory computing
  22. USE lib_fortran ! Fortran routines library
  23. USE dynspg_oce ! pressure gradient schemes
  24. USE c1d ! 1D vertical configuration
  25. IMPLICIT NONE
  26. PRIVATE
  27. PUBLIC stp_ctl ! routine called by step.F90
  28. !!----------------------------------------------------------------------
  29. !! NEMO/OPA 3.3 , NEMO Consortium (2010)
  30. !! $Id: stpctl.F90 7847 2017-03-30 13:30:29Z cetlod $
  31. !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
  32. !!----------------------------------------------------------------------
  33. CONTAINS
  34. SUBROUTINE stp_ctl( kt, kindic )
  35. !!----------------------------------------------------------------------
  36. !! *** ROUTINE stp_ctl ***
  37. !!
  38. !! ** Purpose : Control the run
  39. !!
  40. !! ** Method : - Save the time step in numstp
  41. !! - Print it each 50 time steps
  42. !! - Print solver statistics in numsol
  43. !! - Stop the run IF problem for the solver ( indec < 0 )
  44. !!
  45. !! ** Actions : 'time.step' file containing the last ocean time-step
  46. !!
  47. !!----------------------------------------------------------------------
  48. INTEGER, INTENT( in ) :: kt ! ocean time-step index
  49. INTEGER, INTENT( inout ) :: kindic ! indicator of solver convergence
  50. !!
  51. CHARACTER(len = 32) :: clfname ! time stepping output file name
  52. INTEGER :: ji, jj, jk ! dummy loop indices
  53. INTEGER :: ii, ij, ik ! temporary integers
  54. REAL(wp) :: zumax, zsmin, zssh2, zsshmax ! temporary scalars
  55. INTEGER, DIMENSION(3) :: ilocu !
  56. INTEGER, DIMENSION(2) :: ilocs !
  57. !!----------------------------------------------------------------------
  58. IF( kt == nit000 .AND. lwp ) THEN
  59. WRITE(numout,*)
  60. WRITE(numout,*) 'stp_ctl : time-stepping control'
  61. WRITE(numout,*) '~~~~~~~'
  62. ! open time.step file with special treatment for SAS
  63. IF ( nn_components == jp_iam_sas ) THEN
  64. clfname = 'time.step.sas'
  65. ELSE
  66. clfname = 'time.step'
  67. ENDIF
  68. CALL ctl_opn( numstp, TRIM(clfname), 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea )
  69. ENDIF
  70. IF(lwp) WRITE ( numstp, '(1x, i8)' ) kt !* save the current time step in numstp
  71. IF(lwp) REWIND( numstp ) ! --------------------------
  72. ! !* Test maximum of velocity (zonal only)
  73. ! ! ------------------------
  74. !! zumax = MAXVAL( ABS( un(:,:,:) ) ) ! slower than the following loop on NEC SX5
  75. zumax = 0.e0
  76. DO jk = 1, jpk
  77. DO jj = 1, jpj
  78. DO ji = 1, jpi
  79. zumax = MAX(zumax,ABS(un(ji,jj,jk)))
  80. END DO
  81. END DO
  82. END DO
  83. IF( lk_mpp ) CALL mpp_max( zumax ) ! max over the global domain
  84. !
  85. IF( MOD( kt, nwrite ) == 1 .AND. lwp ) WRITE(numout,*) ' ==>> time-step= ',kt,' abs(U) max: ', zumax
  86. !
  87. IF( zumax > 20.e0 ) THEN
  88. IF( lk_mpp ) THEN
  89. CALL mpp_maxloc(ABS(un),umask,zumax,ii,ij,ik)
  90. ELSE
  91. ilocu = MAXLOC( ABS( un(:,:,:) ) )
  92. ii = ilocu(1) + nimpp - 1
  93. ij = ilocu(2) + njmpp - 1
  94. ik = ilocu(3)
  95. ENDIF
  96. IF(lwp) THEN
  97. WRITE(numout,cform_err)
  98. WRITE(numout,*) ' stpctl: the zonal velocity is larger than 20 m/s'
  99. WRITE(numout,*) ' ====== '
  100. WRITE(numout,9400) kt, zumax, ii, ij, ik
  101. WRITE(numout,*)
  102. WRITE(numout,*) ' output of last fields in numwso'
  103. ENDIF
  104. kindic = -3
  105. ENDIF
  106. 9400 FORMAT (' kt=',i6,' max abs(U): ',1pg11.4,', i j k: ',3i5)
  107. ! !* Test minimum of salinity
  108. ! ! ------------------------
  109. !! zsmin = MINVAL( tsn(:,:,1,jp_sal), mask = tmask(:,:,1) == 1.e0 ) slower than the following loop on NEC SX5
  110. zsmin = 100.e0
  111. DO jj = 2, jpjm1
  112. DO ji = 1, jpi
  113. IF( tmask(ji,jj,1) == 1) zsmin = MIN(zsmin,tsn(ji,jj,1,jp_sal))
  114. END DO
  115. END DO
  116. IF( lk_mpp ) CALL mpp_min( zsmin ) ! min over the global domain
  117. !
  118. IF( MOD( kt, nwrite ) == 1 .AND. lwp ) WRITE(numout,*) ' ==>> time-step= ',kt,' SSS min:', zsmin
  119. !
  120. IF( zsmin < 0.) THEN
  121. IF (lk_mpp) THEN
  122. CALL mpp_minloc ( tsn(:,:,1,jp_sal),tmask(:,:,1), zsmin, ii,ij )
  123. ELSE
  124. ilocs = MINLOC( tsn(:,:,1,jp_sal), mask = tmask(:,:,1) == 1.e0 )
  125. ii = ilocs(1) + nimpp - 1
  126. ij = ilocs(2) + njmpp - 1
  127. ENDIF
  128. !
  129. IF(lwp) THEN
  130. WRITE(numout,cform_err)
  131. WRITE(numout,*) 'stp_ctl : NEGATIVE sea surface salinity'
  132. WRITE(numout,*) '======= '
  133. WRITE(numout,9500) kt, zsmin, ii, ij
  134. WRITE(numout,*)
  135. WRITE(numout,*) ' output of last fields in numwso'
  136. ENDIF
  137. kindic = -3
  138. ENDIF
  139. 9500 FORMAT (' kt=',i6,' min SSS: ',1pg11.4,', i j: ',2i5)
  140. IF( lk_c1d ) RETURN ! No log file in case of 1D vertical configuration
  141. ! log file (solver or ssh statistics)
  142. ! --------
  143. IF( lk_dynspg_flt ) THEN ! elliptic solver statistics (if required)
  144. !
  145. IF(lwp) WRITE(numsol,9200) kt, niter, res, SQRT(epsr)/eps ! Solver
  146. !
  147. IF( kindic < 0 .AND. zsmin > 0.e0 .AND. zumax <= 20.e0 ) THEN ! create a abort file if problem found
  148. IF(lwp) THEN
  149. WRITE(numout,*) ' stpctl: the elliptic solver DO not converge or explode'
  150. WRITE(numout,*) ' ====== '
  151. WRITE(numout,9200) kt, niter, res, sqrt(epsr)/eps
  152. WRITE(numout,*)
  153. WRITE(numout,*) ' stpctl: output of last fields'
  154. WRITE(numout,*) ' ====== '
  155. ENDIF
  156. ENDIF
  157. !
  158. ELSE !* ssh statistics (and others...)
  159. IF( kt == nit000 .AND. lwp ) THEN ! open ssh statistics file (put in solver.stat file)
  160. CALL ctl_opn( numsol, 'solver.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea )
  161. ENDIF
  162. !
  163. zsshmax = 0.e0
  164. DO jj = 1, jpj
  165. DO ji = 1, jpi
  166. IF( tmask(ji,jj,1) == 1) zsshmax = MAX( zsshmax, ABS(sshn(ji,jj)) )
  167. END DO
  168. END DO
  169. IF( lk_mpp ) CALL mpp_max( zsshmax ) ! min over the global domain
  170. !
  171. IF( MOD( kt, nwrite ) == 1 .AND. lwp ) WRITE(numout,*) ' ==>> time-step= ',kt,' ssh max:', zsshmax
  172. !
  173. IF( zsshmax > 10.e0 ) THEN
  174. IF (lk_mpp) THEN
  175. CALL mpp_maxloc( ABS(sshn(:,:)),tmask(:,:,1),zsshmax,ii,ij)
  176. ELSE
  177. ilocs = MAXLOC( ABS(sshn(:,:)) )
  178. ii = ilocs(1) + nimpp - 1
  179. ij = ilocs(2) + njmpp - 1
  180. ENDIF
  181. !
  182. IF(lwp) THEN
  183. WRITE(numout,cform_err)
  184. WRITE(numout,*) 'stp_ctl : the ssh is larger than 10m'
  185. WRITE(numout,*) '======= '
  186. WRITE(numout,9600) kt, zsshmax, ii, ij
  187. WRITE(numout,*)
  188. WRITE(numout,*) ' output of last fields in numwso'
  189. ENDIF
  190. kindic = -3
  191. ENDIF
  192. 9600 FORMAT (' kt=',i6,' max ssh: ',1pg11.4,', i j: ',2i5)
  193. !
  194. zssh2 = glob_sum( sshn(:,:) * sshn(:,:) )
  195. !
  196. IF(lwp) WRITE(numsol,9300) kt, zssh2, zumax, zsmin ! ssh statistics
  197. !
  198. IF( isnan( zssh2 ) .OR. isnan( zsmin ) .OR. isnan( zumax ) ) THEN
  199. kindic = -3
  200. IF(lwp) WRITE(numout,*) " ssh too big. output.abort "
  201. ENDIF
  202. !
  203. ENDIF
  204. 9200 FORMAT('it:', i8, ' iter:', i4, ' r: ',d23.16, ' b: ',d23.16 )
  205. 9300 FORMAT(' it :', i8, ' ssh2: ', d23.16, ' Umax: ',d23.16,' Smin: ',d23.16)
  206. !
  207. END SUBROUTINE stp_ctl
  208. !!======================================================================
  209. END MODULE stpctl