sbcrnf.F90 29 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529
  1. MODULE sbcrnf
  2. !!======================================================================
  3. !! *** MODULE sbcrnf ***
  4. !! Ocean forcing: river runoff
  5. !!=====================================================================
  6. !! History : OPA ! 2000-11 (R. Hordoir, E. Durand) NetCDF FORMAT
  7. !! NEMO 1.0 ! 2002-09 (G. Madec) F90: Free form and module
  8. !! 3.0 ! 2006-07 (G. Madec) Surface module
  9. !! 3.2 ! 2009-04 (B. Lemaire) Introduce iom_put
  10. !! 3.3 ! 2010-10 (R. Furner, G. Madec) runoff distributed over ocean levels
  11. !!----------------------------------------------------------------------
  12. !!----------------------------------------------------------------------
  13. !! sbc_rnf : monthly runoffs read in a NetCDF file
  14. !! sbc_rnf_init : runoffs initialisation
  15. !! rnf_mouth : set river mouth mask
  16. !!----------------------------------------------------------------------
  17. USE dom_oce ! ocean space and time domain
  18. USE phycst ! physical constants
  19. USE sbc_oce ! surface boundary condition variables
  20. USE sbcisf ! PM we could remove it I think
  21. USE closea ! closed seas
  22. USE fldread ! read input field at current time step
  23. USE in_out_manager ! I/O manager
  24. USE iom ! I/O module
  25. USE lib_mpp ! MPP library
  26. USE eosbn2
  27. USE wrk_nemo ! Memory allocation
  28. IMPLICIT NONE
  29. PRIVATE
  30. PUBLIC sbc_rnf ! routine call in sbcmod module
  31. PUBLIC sbc_rnf_div ! routine called in divcurl module
  32. PUBLIC sbc_rnf_alloc ! routine call in sbcmod module
  33. PUBLIC sbc_rnf_init ! (PUBLIC for TAM)
  34. ! !!* namsbc_rnf namelist *
  35. CHARACTER(len=100) :: cn_dir !: Root directory for location of rnf files
  36. LOGICAL :: ln_rnf_depth !: depth river runoffs attribute specified in a file
  37. LOGICAL :: ln_rnf_depth_ini !: depth river runoffs computed at the initialisation
  38. REAL(wp) :: rn_rnf_max !: maximum value of the runoff climatologie ( ln_rnf_depth_ini = .true )
  39. REAL(wp) :: rn_dep_max !: depth over which runoffs is spread ( ln_rnf_depth_ini = .true )
  40. INTEGER :: nn_rnf_depth_file !: create (=1) a runoff depth file or not (=0)
  41. LOGICAL :: ln_rnf_tem !: temperature river runoffs attribute specified in a file
  42. LOGICAL , PUBLIC :: ln_rnf_sal !: salinity river runoffs attribute specified in a file
  43. TYPE(FLD_N) , PUBLIC :: sn_rnf !: information about the runoff file to be read
  44. TYPE(FLD_N) :: sn_cnf !: information about the runoff mouth file to be read
  45. TYPE(FLD_N) :: sn_s_rnf !: information about the salinities of runoff file to be read
  46. TYPE(FLD_N) :: sn_t_rnf !: information about the temperatures of runoff file to be read
  47. TYPE(FLD_N) :: sn_dep_rnf !: information about the depth which river inflow affects
  48. LOGICAL , PUBLIC :: ln_rnf_mouth !: specific treatment in mouths vicinity
  49. REAL(wp) :: rn_hrnf !: runoffs, depth over which enhanced vertical mixing is used
  50. REAL(wp) , PUBLIC :: rn_avt_rnf !: runoffs, value of the additional vertical mixing coef. [m2/s]
  51. REAL(wp) , PUBLIC :: rn_rfact !: multiplicative factor for runoff
  52. LOGICAL , PUBLIC :: l_rnfcpl = .false. ! runoffs recieved from oasis
  53. INTEGER , PUBLIC :: nkrnf = 0 !: nb of levels over which Kz is increased at river mouths
  54. REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: rnfmsk !: river mouth mask (hori.)
  55. REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) :: rnfmsk_z !: river mouth mask (vert.)
  56. REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: h_rnf !: depth of runoff in m
  57. INTEGER, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: nk_rnf !: depth of runoff in model levels
  58. REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: rnf_tsc_b, rnf_tsc !: before and now T & S runoff contents [K.m/s & PSU.m/s]
  59. TYPE(FLD), ALLOCATABLE, DIMENSION(:) :: sf_rnf ! structure: river runoff (file information, fields read)
  60. TYPE(FLD), ALLOCATABLE, DIMENSION(:) :: sf_s_rnf ! structure: river runoff salinity (file information, fields read)
  61. TYPE(FLD), ALLOCATABLE, DIMENSION(:) :: sf_t_rnf ! structure: river runoff temperature (file information, fields read)
  62. !! * Substitutions
  63. # include "domzgr_substitute.h90"
  64. !!----------------------------------------------------------------------
  65. !! NEMO/OPA 3.3 , NEMO Consortium (2010)
  66. !! $Id: sbcrnf.F90 5503 2015-06-29 12:31:29Z cetlod $
  67. !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
  68. !!----------------------------------------------------------------------
  69. CONTAINS
  70. INTEGER FUNCTION sbc_rnf_alloc()
  71. !!----------------------------------------------------------------------
  72. !! *** ROUTINE sbc_rnf_alloc ***
  73. !!----------------------------------------------------------------------
  74. ALLOCATE( rnfmsk(jpi,jpj) , rnfmsk_z(jpk) , &
  75. & h_rnf (jpi,jpj) , nk_rnf (jpi,jpj) , &
  76. & rnf_tsc_b(jpi,jpj,jpts) , rnf_tsc (jpi,jpj,jpts) , STAT=sbc_rnf_alloc )
  77. !
  78. IF( lk_mpp ) CALL mpp_sum ( sbc_rnf_alloc )
  79. IF( sbc_rnf_alloc > 0 ) CALL ctl_warn('sbc_rnf_alloc: allocation of arrays failed')
  80. END FUNCTION sbc_rnf_alloc
  81. SUBROUTINE sbc_rnf( kt )
  82. !!----------------------------------------------------------------------
  83. !! *** ROUTINE sbc_rnf ***
  84. !!
  85. !! ** Purpose : Introduce a climatological run off forcing
  86. !!
  87. !! ** Method : Set each river mouth with a monthly climatology
  88. !! provided from different data.
  89. !! CAUTION : upward water flux, runoff forced to be < 0
  90. !!
  91. !! ** Action : runoff updated runoff field at time-step kt
  92. !!----------------------------------------------------------------------
  93. INTEGER, INTENT(in) :: kt ! ocean time step
  94. !
  95. INTEGER :: ji, jj ! dummy loop indices
  96. INTEGER :: z_err = 0 ! dummy integer for error handling
  97. !!----------------------------------------------------------------------
  98. REAL(wp), DIMENSION(:,:), POINTER :: ztfrz ! freezing point used for temperature correction
  99. !
  100. CALL wrk_alloc( jpi,jpj, ztfrz)
  101. !
  102. ! !-------------------!
  103. ! ! Update runoff !
  104. ! !-------------------!
  105. !
  106. IF( .NOT. l_rnfcpl ) CALL fld_read ( kt, nn_fsbc, sf_rnf ) ! Read Runoffs data and provide it at kt
  107. IF( ln_rnf_tem ) CALL fld_read ( kt, nn_fsbc, sf_t_rnf ) ! idem for runoffs temperature if required
  108. IF( ln_rnf_sal ) CALL fld_read ( kt, nn_fsbc, sf_s_rnf ) ! idem for runoffs salinity if required
  109. !
  110. IF( MOD( kt - 1, nn_fsbc ) == 0 ) THEN
  111. !
  112. IF( .NOT. l_rnfcpl ) rnf(:,:) = rn_rfact * ( sf_rnf(1)%fnow(:,:,1) ) ! updated runoff value at time step kt
  113. !
  114. ! ! set temperature & salinity content of runoffs
  115. IF( ln_rnf_tem ) THEN ! use runoffs temperature data
  116. rnf_tsc(:,:,jp_tem) = ( sf_t_rnf(1)%fnow(:,:,1) ) * rnf(:,:) * r1_rau0
  117. WHERE( sf_t_rnf(1)%fnow(:,:,1) == -999._wp ) ! if missing data value use SST as runoffs temperature
  118. rnf_tsc(:,:,jp_tem) = sst_m(:,:) * rnf(:,:) * r1_rau0
  119. END WHERE
  120. WHERE( sf_t_rnf(1)%fnow(:,:,1) == -222._wp ) ! where fwf comes from melting of ice shelves or iceberg
  121. ztfrz(:,:) = -1.9 !tfreez( sss_m(:,:) ) !PM to be discuss (trouble if sensitivity study)
  122. rnf_tsc(:,:,jp_tem) = ztfrz(:,:) * rnf(:,:) * r1_rau0 - rnf(:,:) * lfusisf * r1_rau0_rcp
  123. END WHERE
  124. ELSE ! use SST as runoffs temperature
  125. rnf_tsc(:,:,jp_tem) = sst_m(:,:) * rnf(:,:) * r1_rau0
  126. ENDIF
  127. ! ! use runoffs salinity data
  128. IF( ln_rnf_sal ) rnf_tsc(:,:,jp_sal) = ( sf_s_rnf(1)%fnow(:,:,1) ) * rnf(:,:) * r1_rau0
  129. ! ! else use S=0 for runoffs (done one for all in the init)
  130. IF( iom_use('runoffs') ) CALL iom_put( 'runoffs' , rnf(:,:) ) ! output runoff mass flux
  131. IF( iom_use('hflx_rnf_cea') ) CALL iom_put( 'hflx_rnf_cea', rnf_tsc(:,:,jp_tem) * rau0 * rcp ) ! output runoff sensible heat (W/m2)
  132. ENDIF
  133. !
  134. ! ! ---------------------------------------- !
  135. IF( kt == nit000 ) THEN ! set the forcing field at nit000 - 1 !
  136. ! ! ---------------------------------------- !
  137. IF( ln_rstart .AND. & !* Restart: read in restart file
  138. & iom_varid( numror, 'rnf_b', ldstop = .FALSE. ) > 0 ) THEN
  139. IF(lwp) WRITE(numout,*) ' nit000-1 runoff forcing fields red in the restart file'
  140. CALL iom_get( numror, jpdom_autoglo, 'rnf_b', rnf_b ) ! before runoff
  141. CALL iom_get( numror, jpdom_autoglo, 'rnf_hc_b', rnf_tsc_b(:,:,jp_tem) ) ! before heat content of runoff
  142. CALL iom_get( numror, jpdom_autoglo, 'rnf_sc_b', rnf_tsc_b(:,:,jp_sal) ) ! before salinity content of runoff
  143. ELSE !* no restart: set from nit000 values
  144. IF(lwp) WRITE(numout,*) ' nit000-1 runoff forcing fields set to nit000'
  145. rnf_b (:,: ) = rnf (:,: )
  146. rnf_tsc_b(:,:,:) = rnf_tsc(:,:,:)
  147. ENDIF
  148. ENDIF
  149. ! ! ---------------------------------------- !
  150. IF( lrst_oce ) THEN ! Write in the ocean restart file !
  151. ! ! ---------------------------------------- !
  152. IF(lwp) WRITE(numout,*)
  153. IF(lwp) WRITE(numout,*) 'sbcrnf : runoff forcing fields written in ocean restart file ', &
  154. & 'at it= ', kt,' date= ', ndastp
  155. IF(lwp) WRITE(numout,*) '~~~~'
  156. CALL iom_rstput( kt, nitrst, numrow, 'rnf_b' , rnf )
  157. CALL iom_rstput( kt, nitrst, numrow, 'rnf_hc_b', rnf_tsc(:,:,jp_tem) )
  158. CALL iom_rstput( kt, nitrst, numrow, 'rnf_sc_b', rnf_tsc(:,:,jp_sal) )
  159. ENDIF
  160. !
  161. CALL wrk_dealloc( jpi,jpj, ztfrz)
  162. !
  163. END SUBROUTINE sbc_rnf
  164. SUBROUTINE sbc_rnf_div( phdivn )
  165. !!----------------------------------------------------------------------
  166. !! *** ROUTINE sbc_rnf ***
  167. !!
  168. !! ** Purpose : update the horizontal divergence with the runoff inflow
  169. !!
  170. !! ** Method :
  171. !! CAUTION : rnf is positive (inflow) decreasing the
  172. !! divergence and expressed in m/s
  173. !!
  174. !! ** Action : phdivn decreased by the runoff inflow
  175. !!----------------------------------------------------------------------
  176. REAL(wp), DIMENSION(:,:,:), INTENT(inout) :: phdivn ! horizontal divergence
  177. !!
  178. INTEGER :: ji, jj, jk ! dummy loop indices
  179. REAL(wp) :: zfact ! local scalar
  180. !!----------------------------------------------------------------------
  181. !
  182. zfact = 0.5_wp
  183. !
  184. IF( ln_rnf_depth .OR. ln_rnf_depth_ini ) THEN !== runoff distributed over several levels ==!
  185. IF( lk_vvl ) THEN ! variable volume case
  186. DO jj = 1, jpj ! update the depth over which runoffs are distributed
  187. DO ji = 1, jpi
  188. h_rnf(ji,jj) = 0._wp
  189. DO jk = 1, nk_rnf(ji,jj) ! recalculates h_rnf to be the depth in metres
  190. h_rnf(ji,jj) = h_rnf(ji,jj) + fse3t(ji,jj,jk) ! to the bottom of the relevant grid box
  191. END DO
  192. ! ! apply the runoff input flow
  193. DO jk = 1, nk_rnf(ji,jj)
  194. phdivn(ji,jj,jk) = phdivn(ji,jj,jk) - ( rnf(ji,jj) + rnf_b(ji,jj) ) * zfact * r1_rau0 / h_rnf(ji,jj)
  195. END DO
  196. END DO
  197. END DO
  198. ELSE ! constant volume case : just apply the runoff input flow
  199. DO jj = 1, jpj
  200. DO ji = 1, jpi
  201. DO jk = 1, nk_rnf(ji,jj)
  202. phdivn(ji,jj,jk) = phdivn(ji,jj,jk) - ( rnf(ji,jj) + rnf_b(ji,jj) ) * zfact * r1_rau0 / h_rnf(ji,jj)
  203. END DO
  204. END DO
  205. END DO
  206. ENDIF
  207. ELSE !== runoff put only at the surface ==!
  208. IF( lk_vvl ) THEN ! variable volume case
  209. h_rnf(:,:) = fse3t(:,:,1) ! recalculate h_rnf to be depth of top box
  210. ENDIF
  211. phdivn(:,:,1) = phdivn(:,:,1) - ( rnf(:,:) + rnf_b(:,:) ) * zfact * r1_rau0 / fse3t(:,:,1)
  212. ENDIF
  213. !
  214. END SUBROUTINE sbc_rnf_div
  215. SUBROUTINE sbc_rnf_init
  216. !!----------------------------------------------------------------------
  217. !! *** ROUTINE sbc_rnf_init ***
  218. !!
  219. !! ** Purpose : Initialisation of the runoffs if (ln_rnf=T)
  220. !!
  221. !! ** Method : - read the runoff namsbc_rnf namelist
  222. !!
  223. !! ** Action : - read parameters
  224. !!----------------------------------------------------------------------
  225. CHARACTER(len=32) :: rn_dep_file ! runoff file name
  226. INTEGER :: ji, jj, jk, jm ! dummy loop indices
  227. INTEGER :: ierror, inum ! temporary integer
  228. INTEGER :: ios ! Local integer output status for namelist read
  229. INTEGER :: nbrec ! temporary integer
  230. REAL(wp) :: zacoef
  231. REAL(wp), DIMENSION(12) :: zrec ! times records
  232. REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: zrnfcl
  233. REAL(wp), DIMENSION(:,: ), ALLOCATABLE :: zrnf
  234. !
  235. NAMELIST/namsbc_rnf/ cn_dir , ln_rnf_depth, ln_rnf_tem, ln_rnf_sal, &
  236. & sn_rnf, sn_cnf , sn_s_rnf , sn_t_rnf , sn_dep_rnf, &
  237. & ln_rnf_mouth , rn_hrnf , rn_avt_rnf, rn_rfact, &
  238. & ln_rnf_depth_ini , rn_dep_max , rn_rnf_max, nn_rnf_depth_file
  239. !!----------------------------------------------------------------------
  240. !
  241. ! !== allocate runoff arrays
  242. IF( sbc_rnf_alloc() /= 0 ) CALL ctl_stop( 'STOP', 'sbc_rnf_alloc : unable to allocate arrays' )
  243. !
  244. IF( .NOT. ln_rnf ) THEN ! no specific treatment in vicinity of river mouths
  245. ln_rnf_mouth = .FALSE. ! default definition needed for example by sbc_ssr or by tra_adv_muscl
  246. nkrnf = 0
  247. rnf (:,:) = 0.0_wp
  248. rnf_b (:,:) = 0.0_wp
  249. rnfmsk (:,:) = 0.0_wp
  250. rnfmsk_z(:) = 0.0_wp
  251. RETURN
  252. ENDIF
  253. !
  254. ! ! ============
  255. ! ! Namelist
  256. ! ! ============
  257. !
  258. REWIND( numnam_ref ) ! Namelist namsbc_rnf in reference namelist : Runoffs
  259. READ ( numnam_ref, namsbc_rnf, IOSTAT = ios, ERR = 901)
  260. 901 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_rnf in reference namelist', lwp )
  261. REWIND( numnam_cfg ) ! Namelist namsbc_rnf in configuration namelist : Runoffs
  262. READ ( numnam_cfg, namsbc_rnf, IOSTAT = ios, ERR = 902 )
  263. 902 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_rnf in configuration namelist', lwp )
  264. IF(lwm) WRITE ( numond, namsbc_rnf )
  265. !
  266. ! ! Control print
  267. IF(lwp) THEN
  268. WRITE(numout,*)
  269. WRITE(numout,*) 'sbc_rnf : runoff '
  270. WRITE(numout,*) '~~~~~~~ '
  271. WRITE(numout,*) ' Namelist namsbc_rnf'
  272. WRITE(numout,*) ' specific river mouths treatment ln_rnf_mouth = ', ln_rnf_mouth
  273. WRITE(numout,*) ' river mouth additional Kz rn_avt_rnf = ', rn_avt_rnf
  274. WRITE(numout,*) ' depth of river mouth additional mixing rn_hrnf = ', rn_hrnf
  275. WRITE(numout,*) ' multiplicative factor for runoff rn_rfact = ', rn_rfact
  276. ENDIF
  277. ! ! ==================
  278. ! ! Type of runoff
  279. ! ! ==================
  280. !
  281. IF( .NOT. l_rnfcpl ) THEN
  282. ALLOCATE( sf_rnf(1), STAT=ierror ) ! Create sf_rnf structure (runoff inflow)
  283. IF(lwp) WRITE(numout,*)
  284. IF(lwp) WRITE(numout,*) ' runoffs inflow read in a file'
  285. IF( ierror > 0 ) THEN
  286. CALL ctl_stop( 'sbc_rnf: unable to allocate sf_rnf structure' ) ; RETURN
  287. ENDIF
  288. ALLOCATE( sf_rnf(1)%fnow(jpi,jpj,1) )
  289. IF( sn_rnf%ln_tint ) ALLOCATE( sf_rnf(1)%fdta(jpi,jpj,1,2) )
  290. CALL fld_fill( sf_rnf, (/ sn_rnf /), cn_dir, 'sbc_rnf_init', 'read runoffs data', 'namsbc_rnf' )
  291. ENDIF
  292. !
  293. IF( ln_rnf_tem ) THEN ! Create (if required) sf_t_rnf structure
  294. IF(lwp) WRITE(numout,*)
  295. IF(lwp) WRITE(numout,*) ' runoffs temperatures read in a file'
  296. ALLOCATE( sf_t_rnf(1), STAT=ierror )
  297. IF( ierror > 0 ) THEN
  298. CALL ctl_stop( 'sbc_rnf_init: unable to allocate sf_t_rnf structure' ) ; RETURN
  299. ENDIF
  300. ALLOCATE( sf_t_rnf(1)%fnow(jpi,jpj,1) )
  301. IF( sn_t_rnf%ln_tint ) ALLOCATE( sf_t_rnf(1)%fdta(jpi,jpj,1,2) )
  302. CALL fld_fill (sf_t_rnf, (/ sn_t_rnf /), cn_dir, 'sbc_rnf_init', 'read runoff temperature data', 'namsbc_rnf' )
  303. ENDIF
  304. !
  305. IF( ln_rnf_sal ) THEN ! Create (if required) sf_s_rnf and sf_t_rnf structures
  306. IF(lwp) WRITE(numout,*)
  307. IF(lwp) WRITE(numout,*) ' runoffs salinities read in a file'
  308. ALLOCATE( sf_s_rnf(1), STAT=ierror )
  309. IF( ierror > 0 ) THEN
  310. CALL ctl_stop( 'sbc_rnf_init: unable to allocate sf_s_rnf structure' ) ; RETURN
  311. ENDIF
  312. ALLOCATE( sf_s_rnf(1)%fnow(jpi,jpj,1) )
  313. IF( sn_s_rnf%ln_tint ) ALLOCATE( sf_s_rnf(1)%fdta(jpi,jpj,1,2) )
  314. CALL fld_fill (sf_s_rnf, (/ sn_s_rnf /), cn_dir, 'sbc_rnf_init', 'read runoff salinity data', 'namsbc_rnf' )
  315. ENDIF
  316. !
  317. IF( ln_rnf_depth ) THEN ! depth of runoffs set from a file
  318. IF(lwp) WRITE(numout,*)
  319. IF(lwp) WRITE(numout,*) ' runoffs depth read in a file'
  320. rn_dep_file = TRIM( cn_dir )//TRIM( sn_dep_rnf%clname )
  321. IF( .NOT. sn_dep_rnf%ln_clim ) THEN ; WRITE(rn_dep_file, '(a,"_y",i4)' ) TRIM( rn_dep_file ), nyear ! add year
  322. IF( sn_dep_rnf%cltype == 'monthly' ) WRITE(rn_dep_file, '(a,"m",i2)' ) TRIM( rn_dep_file ), nmonth ! add month
  323. ENDIF
  324. CALL iom_open ( rn_dep_file, inum ) ! open file
  325. CALL iom_get ( inum, jpdom_data, sn_dep_rnf%clvar, h_rnf ) ! read the river mouth array
  326. CALL iom_close( inum ) ! close file
  327. !
  328. nk_rnf(:,:) = 0 ! set the number of level over which river runoffs are applied
  329. DO jj = 1, jpj
  330. DO ji = 1, jpi
  331. IF( h_rnf(ji,jj) > 0._wp ) THEN
  332. jk = 2
  333. DO WHILE ( jk /= mbkt(ji,jj) .AND. gdept_0(ji,jj,jk) < h_rnf(ji,jj) ) ; jk = jk + 1
  334. END DO
  335. nk_rnf(ji,jj) = jk
  336. ELSEIF( h_rnf(ji,jj) == -1._wp ) THEN ; nk_rnf(ji,jj) = 1
  337. ELSEIF( h_rnf(ji,jj) == -999._wp ) THEN ; nk_rnf(ji,jj) = mbkt(ji,jj)
  338. ELSE
  339. CALL ctl_stop( 'sbc_rnf_init: runoff depth not positive, and not -999 or -1, rnf value in file fort.999' )
  340. WRITE(999,*) 'ji, jj, h_rnf(ji,jj) :', ji, jj, h_rnf(ji,jj)
  341. ENDIF
  342. END DO
  343. END DO
  344. DO jj = 1, jpj ! set the associated depth
  345. DO ji = 1, jpi
  346. h_rnf(ji,jj) = 0._wp
  347. DO jk = 1, nk_rnf(ji,jj)
  348. h_rnf(ji,jj) = h_rnf(ji,jj) + fse3t(ji,jj,jk)
  349. END DO
  350. END DO
  351. END DO
  352. !
  353. ELSE IF( ln_rnf_depth_ini ) THEN ! runoffs applied at the surface
  354. !
  355. IF(lwp) WRITE(numout,*)
  356. IF(lwp) WRITE(numout,*) ' depth of runoff computed once from max value of runoff'
  357. IF(lwp) WRITE(numout,*) ' max value of the runoff climatologie (over global domain) rn_rnf_max = ', rn_rnf_max
  358. IF(lwp) WRITE(numout,*) ' depth over which runoffs is spread rn_dep_max = ', rn_dep_max
  359. IF(lwp) WRITE(numout,*) ' create (=1) a runoff depth file or not (=0) nn_rnf_depth_file = ', nn_rnf_depth_file
  360. CALL iom_open( TRIM( sn_rnf%clname ), inum ) ! open runoff file
  361. CALL iom_gettime( inum, zrec, kntime=nbrec)
  362. ALLOCATE( zrnfcl(jpi,jpj,nbrec) ) ; ALLOCATE( zrnf(jpi,jpj) )
  363. DO jm = 1, nbrec
  364. CALL iom_get( inum, jpdom_data, TRIM( sn_rnf%clvar ), zrnfcl(:,:,jm), jm )
  365. END DO
  366. CALL iom_close( inum )
  367. zrnf(:,:) = MAXVAL( zrnfcl(:,:,:), DIM=3 ) ! maximum value in time
  368. DEALLOCATE( zrnfcl )
  369. !
  370. h_rnf(:,:) = 1.
  371. !
  372. zacoef = rn_dep_max / rn_rnf_max ! coef of linear relation between runoff and its depth (150m for max of runoff)
  373. !
  374. WHERE( zrnf(:,:) > 0._wp ) h_rnf(:,:) = zacoef * zrnf(:,:) ! compute depth for all runoffs
  375. !
  376. DO jj = 1, jpj ! take in account min depth of ocean rn_hmin
  377. DO ji = 1, jpi
  378. IF( zrnf(ji,jj) > 0._wp ) THEN
  379. jk = mbkt(ji,jj)
  380. h_rnf(ji,jj) = MIN( h_rnf(ji,jj), gdept_0(ji,jj,jk ) )
  381. ENDIF
  382. END DO
  383. END DO
  384. !
  385. nk_rnf(:,:) = 0 ! number of levels on which runoffs are distributed
  386. DO jj = 1, jpj
  387. DO ji = 1, jpi
  388. IF( zrnf(ji,jj) > 0._wp ) THEN
  389. jk = 2
  390. DO WHILE ( jk /= mbkt(ji,jj) .AND. gdept_0(ji,jj,jk) < h_rnf(ji,jj) ) ; jk = jk + 1
  391. END DO
  392. nk_rnf(ji,jj) = jk
  393. ELSE
  394. nk_rnf(ji,jj) = 1
  395. ENDIF
  396. END DO
  397. END DO
  398. !
  399. DEALLOCATE( zrnf )
  400. !
  401. DO jj = 1, jpj ! set the associated depth
  402. DO ji = 1, jpi
  403. h_rnf(ji,jj) = 0._wp
  404. DO jk = 1, nk_rnf(ji,jj)
  405. h_rnf(ji,jj) = h_rnf(ji,jj) + fse3t(ji,jj,jk)
  406. END DO
  407. END DO
  408. END DO
  409. !
  410. IF( nn_rnf_depth_file == 1 ) THEN ! save output nb levels for runoff
  411. IF(lwp) WRITE(numout,*) ' create runoff depht file'
  412. CALL iom_open ( TRIM( sn_dep_rnf%clname ), inum, ldwrt = .TRUE., kiolib = jprstlib )
  413. CALL iom_rstput( 0, 0, inum, 'rodepth', h_rnf )
  414. CALL iom_close ( inum )
  415. ENDIF
  416. ELSE ! runoffs applied at the surface
  417. nk_rnf(:,:) = 1
  418. h_rnf (:,:) = fse3t(:,:,1)
  419. ENDIF
  420. !
  421. rnf(:,:) = 0._wp ! runoff initialisation
  422. rnf_tsc(:,:,:) = 0._wp ! runoffs temperature & salinty contents initilisation
  423. !
  424. ! ! ========================
  425. ! ! River mouth vicinity
  426. ! ! ========================
  427. !
  428. IF( ln_rnf_mouth ) THEN ! Specific treatment in vicinity of river mouths :
  429. ! ! - Increase Kz in surface layers ( rn_hrnf > 0 )
  430. ! ! - set to zero SSS damping (ln_ssr=T)
  431. ! ! - mixed upstream-centered (ln_traadv_cen2=T)
  432. !
  433. IF ( ln_rnf_depth ) CALL ctl_warn( 'sbc_rnf_init: increased mixing turned on but effects may already', &
  434. & 'be spread through depth by ln_rnf_depth' )
  435. !
  436. nkrnf = 0 ! Number of level over which Kz increase
  437. IF( rn_hrnf > 0._wp ) THEN
  438. nkrnf = 2
  439. DO WHILE( nkrnf /= jpkm1 .AND. gdepw_1d(nkrnf+1) < rn_hrnf ) ; nkrnf = nkrnf + 1
  440. END DO
  441. IF( ln_sco ) CALL ctl_warn( 'sbc_rnf: number of levels over which Kz is increased is computed for zco...' )
  442. ENDIF
  443. IF(lwp) WRITE(numout,*)
  444. IF(lwp) WRITE(numout,*) ' Specific treatment used in vicinity of river mouths :'
  445. IF(lwp) WRITE(numout,*) ' - Increase Kz in surface layers (if rn_hrnf > 0 )'
  446. IF(lwp) WRITE(numout,*) ' by ', rn_avt_rnf,' m2/s over ', nkrnf, ' w-levels'
  447. IF(lwp) WRITE(numout,*) ' - set to zero SSS damping (if ln_ssr=T)'
  448. IF(lwp) WRITE(numout,*) ' - mixed upstream-centered (if ln_traadv_cen2=T)'
  449. !
  450. CALL rnf_mouth ! set river mouth mask
  451. !
  452. ELSE ! No treatment at river mouths
  453. IF(lwp) WRITE(numout,*)
  454. IF(lwp) WRITE(numout,*) ' No specific treatment at river mouths'
  455. rnfmsk (:,:) = 0._wp
  456. rnfmsk_z(:) = 0._wp
  457. nkrnf = 0
  458. ENDIF
  459. !
  460. END SUBROUTINE sbc_rnf_init
  461. SUBROUTINE rnf_mouth
  462. !!----------------------------------------------------------------------
  463. !! *** ROUTINE rnf_mouth ***
  464. !!
  465. !! ** Purpose : define the river mouths mask
  466. !!
  467. !! ** Method : read the river mouth mask (=0/1) in the river runoff
  468. !! climatological file. Defined a given vertical structure.
  469. !! CAUTION, the vertical structure is hard coded on the
  470. !! first 5 levels.
  471. !! This fields can be used to:
  472. !! - set an upstream advection scheme
  473. !! (ln_rnf_mouth=T and ln_traadv_cen2=T)
  474. !! - increase vertical on the top nn_krnf vertical levels
  475. !! at river runoff input grid point (nn_krnf>=2, see step.F90)
  476. !! - set to zero SSS restoring flux at river mouth grid points
  477. !!
  478. !! ** Action : rnfmsk set to 1 at river runoff input, 0 elsewhere
  479. !! rnfmsk_z vertical structure
  480. !!----------------------------------------------------------------------
  481. INTEGER :: inum ! temporary integers
  482. CHARACTER(len=140) :: cl_rnfile ! runoff file name
  483. !!----------------------------------------------------------------------
  484. !
  485. IF(lwp) WRITE(numout,*)
  486. IF(lwp) WRITE(numout,*) 'rnf_mouth : river mouth mask'
  487. IF(lwp) WRITE(numout,*) '~~~~~~~~~ '
  488. !
  489. cl_rnfile = TRIM( cn_dir )//TRIM( sn_cnf%clname )
  490. IF( .NOT. sn_cnf%ln_clim ) THEN ; WRITE(cl_rnfile, '(a,"_y",i4)' ) TRIM( cl_rnfile ), nyear ! add year
  491. IF( sn_cnf%cltype == 'monthly' ) WRITE(cl_rnfile, '(a,"m",i2)' ) TRIM( cl_rnfile ), nmonth ! add month
  492. ENDIF
  493. !
  494. ! horizontal mask (read in NetCDF file)
  495. CALL iom_open ( cl_rnfile, inum ) ! open file
  496. CALL iom_get ( inum, jpdom_data, sn_cnf%clvar, rnfmsk ) ! read the river mouth array
  497. CALL iom_close( inum ) ! close file
  498. !
  499. IF( nn_closea == 1 ) CALL clo_rnf( rnfmsk ) ! closed sea inflow set as ruver mouth
  500. !
  501. rnfmsk_z(:) = 0._wp ! vertical structure
  502. rnfmsk_z(1) = 1.0
  503. rnfmsk_z(2) = 1.0 ! **********
  504. rnfmsk_z(3) = 0.5 ! HARD CODED on the 5 first levels
  505. rnfmsk_z(4) = 0.25 ! **********
  506. rnfmsk_z(5) = 0.125
  507. !
  508. END SUBROUTINE rnf_mouth
  509. !!======================================================================
  510. END MODULE sbcrnf