sbcrnf.F90 35 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624
  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 eosbn2 ! Equation Of State
  21. USE closea, ONLY: l_clo_rnf, clo_rnf ! closed seas
  22. !
  23. USE in_out_manager ! I/O manager
  24. USE fldread ! read input field at current time step
  25. USE iom ! I/O module
  26. USE lib_mpp ! MPP library
  27. IMPLICIT NONE
  28. PRIVATE
  29. PUBLIC sbc_rnf ! called in sbcmod module
  30. PUBLIC sbc_rnf_div ! called in divhor module
  31. PUBLIC sbc_rnf_alloc ! called in sbcmod module
  32. PUBLIC sbc_rnf_init ! called in sbcmod module
  33. ! !!* namsbc_rnf namelist *
  34. CHARACTER(len=100) :: cn_dir !: Root directory for location of rnf files
  35. LOGICAL , PUBLIC :: ln_rnf_depth !: depth river runoffs attribute specified in a file
  36. LOGICAL :: ln_rnf_depth_ini !: depth river runoffs computed at the initialisation
  37. REAL(wp) :: rn_rnf_max !: maximum value of the runoff climatologie (ln_rnf_depth_ini =T)
  38. REAL(wp) :: rn_dep_max !: depth over which runoffs is spread (ln_rnf_depth_ini =T)
  39. INTEGER :: nn_rnf_depth_file !: create (=1) a runoff depth file or not (=0)
  40. LOGICAL , PUBLIC :: ln_rnf_icb !: iceberg flux is specified in a file
  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_i_rnf !: information about the iceberg flux file to be read
  46. TYPE(FLD_N) :: sn_s_rnf !: information about the salinities of runoff file to be read
  47. TYPE(FLD_N) :: sn_t_rnf !: information about the temperatures of runoff file to be read
  48. TYPE(FLD_N) :: sn_dep_rnf !: information about the depth which river inflow affects
  49. LOGICAL , PUBLIC :: ln_rnf_mouth !: specific treatment in mouths vicinity
  50. REAL(wp) :: rn_hrnf !: runoffs, depth over which enhanced vertical mixing is used
  51. REAL(wp) , PUBLIC :: rn_avt_rnf !: runoffs, value of the additional vertical mixing coef. [m2/s]
  52. REAL(wp) , PUBLIC :: rn_rfact !: multiplicative factor for runoff
  53. LOGICAL , PUBLIC :: l_rnfcpl = .false. !: runoffs recieved from oasis
  54. INTEGER , PUBLIC :: nkrnf = 0 !: nb of levels over which Kz is increased at river mouths
  55. REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: rnfmsk !: river mouth mask (hori.)
  56. REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) :: rnfmsk_z !: river mouth mask (vert.)
  57. REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: h_rnf !: depth of runoff in m
  58. INTEGER, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: nk_rnf !: depth of runoff in model levels
  59. REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: rnf_tsc_b, rnf_tsc !: before and now T & S runoff contents [K.m/s & PSU.m/s]
  60. TYPE(FLD), ALLOCATABLE, DIMENSION(:) :: sf_rnf ! structure: river runoff (file information, fields read)
  61. TYPE(FLD), ALLOCATABLE, DIMENSION(:) :: sf_i_rnf ! structure: iceberg flux (file information, fields read)
  62. TYPE(FLD), ALLOCATABLE, DIMENSION(:) :: sf_s_rnf ! structure: river runoff salinity (file information, fields read)
  63. TYPE(FLD), ALLOCATABLE, DIMENSION(:) :: sf_t_rnf ! structure: river runoff temperature (file information, fields read)
  64. #if defined key_drakkar
  65. INTEGER :: nn_rnf_freq !: number of runoff data set
  66. TYPE(FLD_N), DIMENSION(5) :: sn_rnf2 !: information about the extra runoff file to be read
  67. TYPE(FLD_N), DIMENSION(6) :: slf_rnf !: information about all the runoff in namelist
  68. #endif
  69. !! * Substitutions
  70. # include "do_loop_substitute.h90"
  71. # include "domzgr_substitute.h90"
  72. !!----------------------------------------------------------------------
  73. !! NEMO/OCE 4.0 , NEMO Consortium (2018)
  74. !! $Id: sbcrnf.F90 15190 2021-08-13 12:52:50Z gsamson $
  75. !! Software governed by the CeCILL license (see ./LICENSE)
  76. !!----------------------------------------------------------------------
  77. CONTAINS
  78. INTEGER FUNCTION sbc_rnf_alloc()
  79. !!----------------------------------------------------------------------
  80. !! *** ROUTINE sbc_rnf_alloc ***
  81. !!----------------------------------------------------------------------
  82. ALLOCATE( rnfmsk(jpi,jpj) , rnfmsk_z(jpk) , &
  83. & h_rnf (jpi,jpj) , nk_rnf (jpi,jpj) , &
  84. & rnf_tsc_b(jpi,jpj,jpts) , rnf_tsc (jpi,jpj,jpts) , STAT=sbc_rnf_alloc )
  85. !
  86. CALL mpp_sum ( 'sbcrnf', sbc_rnf_alloc )
  87. IF( sbc_rnf_alloc > 0 ) CALL ctl_warn('sbc_rnf_alloc: allocation of arrays failed')
  88. END FUNCTION sbc_rnf_alloc
  89. SUBROUTINE sbc_rnf( kt )
  90. !!----------------------------------------------------------------------
  91. !! *** ROUTINE sbc_rnf ***
  92. !!
  93. !! ** Purpose : Introduce a climatological run off forcing
  94. !!
  95. !! ** Method : Set each river mouth with a monthly climatology
  96. !! provided from different data.
  97. !! CAUTION : upward water flux, runoff forced to be < 0
  98. !!
  99. !! ** Action : runoff updated runoff field at time-step kt
  100. !!----------------------------------------------------------------------
  101. INTEGER, INTENT(in) :: kt ! ocean time step
  102. !
  103. INTEGER :: ji, jj ! dummy loop indices
  104. INTEGER :: z_err = 0 ! dummy integer for error handling
  105. !!----------------------------------------------------------------------
  106. REAL(wp), DIMENSION(jpi,jpj) :: ztfrz ! freezing point used for temperature correction
  107. !
  108. !
  109. ! !-------------------!
  110. ! ! Update runoff !
  111. ! !-------------------!
  112. !
  113. !
  114. IF( .NOT. l_rnfcpl ) THEN
  115. CALL fld_read ( kt, nn_fsbc, sf_rnf ) ! Read Runoffs data and provide it at kt ( runoffs + iceberg )
  116. IF( ln_rnf_icb ) CALL fld_read ( kt, nn_fsbc, sf_i_rnf ) ! idem for iceberg flux if required
  117. ENDIF
  118. IF( ln_rnf_tem ) CALL fld_read ( kt, nn_fsbc, sf_t_rnf ) ! idem for runoffs temperature if required
  119. IF( ln_rnf_sal ) CALL fld_read ( kt, nn_fsbc, sf_s_rnf ) ! idem for runoffs salinity if required
  120. !
  121. IF( MOD( kt - 1, nn_fsbc ) == 0 ) THEN
  122. !
  123. IF( .NOT. l_rnfcpl ) THEN
  124. #if defined key_drakkar
  125. rnf(:,:) = 0._wp
  126. DO ji = 1, nn_rnf_freq
  127. rnf(:,:) = rnf(:,:) + sf_rnf(ji)%fnow(:,:,1) !
  128. ENDDO
  129. rnf(:,:) = rn_rfact * rnf(:,:) * tmask(:,:,1) ! updated runoff value at time step kt
  130. #else
  131. rnf(:,:) = rn_rfact * ( sf_rnf(1)%fnow(:,:,1) ) * tmask(:,:,1) ! updated runoff value at time step kt
  132. #endif
  133. IF( ln_rnf_icb ) THEN
  134. ! ELIC change
  135. ! - the iceberg melt flux is associated with a loss of heat by the ocean
  136. ! - to avoid cooling the ocean below its freezing point, we block the iceberg
  137. ! melt flux when the surface of the ocean is already close to its freezing
  138. ! point
  139. !
  140. CALL eos_fzp( sss_m(:,:), ztfrz(:,:) )
  141. WHERE( sst_m(:,:) > ztfrz(:,:) + 0.15_wp )
  142. fwficb(:,:) = rn_rfact * ( sf_i_rnf(1)%fnow(:,:,1) ) * tmask(:,:,1) ! updated runoff value at time step kt
  143. ELSE WHERE
  144. fwficb(:,:) = 0._wp
  145. END WHERE
  146. ! end ELIC CHANGE
  147. rnf(:,:) = rnf(:,:) + fwficb(:,:)
  148. qns(:,:) = qns(:,:) - fwficb(:,:) * rLfus
  149. !!qns_tot(:,:) = qns_tot(:,:) - fwficb(:,:) * rLfus
  150. !!qns_oce(:,:) = qns_oce(:,:) - fwficb(:,:) * rLfus
  151. CALL iom_put( 'iceberg_cea' , fwficb(:,:) ) ! output iceberg flux
  152. CALL iom_put( 'hflx_icb_cea' , -fwficb(:,:) * rLfus ) ! output Heat Flux into Sea Water due to Iceberg Thermodynamics -->
  153. ENDIF
  154. ENDIF
  155. !
  156. ! ! set temperature & salinity content of runoffs
  157. IF( ln_rnf_tem ) THEN ! use runoffs temperature data
  158. rnf_tsc(:,:,jp_tem) = ( sf_t_rnf(1)%fnow(:,:,1) ) * rnf(:,:) * r1_rho0
  159. CALL eos_fzp( sss_m(:,:), ztfrz(:,:) )
  160. WHERE( sf_t_rnf(1)%fnow(:,:,1) == -999._wp ) ! if missing data value use SST as runoffs temperature
  161. rnf_tsc(:,:,jp_tem) = sst_m(:,:) * rnf(:,:) * r1_rho0
  162. END WHERE
  163. ELSE ! use SST as runoffs temperature
  164. !CEOD River is fresh water so must at least be 0 unless we consider ice
  165. rnf_tsc(:,:,jp_tem) = MAX( sst_m(:,:), 0.0_wp ) * rnf(:,:) * r1_rho0
  166. ENDIF
  167. ! ! use runoffs salinity data
  168. IF( ln_rnf_sal ) rnf_tsc(:,:,jp_sal) = ( sf_s_rnf(1)%fnow(:,:,1) ) * rnf(:,:) * r1_rho0
  169. ! ! else use S=0 for runoffs (done one for all in the init)
  170. CALL iom_put( 'runoffs' , rnf(:,:) ) ! output runoff mass flux
  171. IF( iom_use('hflx_rnf_cea') ) CALL iom_put( 'hflx_rnf_cea', rnf_tsc(:,:,jp_tem) * rho0 * rcp ) ! output runoff sensible heat (W/m2)
  172. IF( iom_use('sflx_rnf_cea') ) CALL iom_put( 'sflx_rnf_cea', rnf_tsc(:,:,jp_sal) * rho0 ) ! output runoff salt flux (g/m2/s)
  173. ENDIF
  174. !
  175. ! ! ---------------------------------------- !
  176. IF( kt == nit000 ) THEN ! set the forcing field at nit000 - 1 !
  177. ! ! ---------------------------------------- !
  178. IF( ln_rstart .AND. .NOT.l_1st_euler ) THEN !* Restart: read in restart file
  179. IF(lwp) WRITE(numout,*) ' nit000-1 runoff forcing fields red in the restart file', lrxios
  180. CALL iom_get( numror, jpdom_auto, 'rnf_b' , rnf_b ) ! before runoff
  181. CALL iom_get( numror, jpdom_auto, 'rnf_hc_b', rnf_tsc_b(:,:,jp_tem) ) ! before heat content of runoff
  182. CALL iom_get( numror, jpdom_auto, 'rnf_sc_b', rnf_tsc_b(:,:,jp_sal) ) ! before salinity content of runoff
  183. ELSE !* no restart: set from nit000 values
  184. IF(lwp) WRITE(numout,*) ' nit000-1 runoff forcing fields set to nit000'
  185. rnf_b (:,: ) = rnf (:,: )
  186. rnf_tsc_b(:,:,:) = rnf_tsc(:,:,:)
  187. ENDIF
  188. ENDIF
  189. ! ! ---------------------------------------- !
  190. IF( lrst_oce ) THEN ! Write in the ocean restart file !
  191. ! ! ---------------------------------------- !
  192. IF(lwp) WRITE(numout,*)
  193. IF(lwp) WRITE(numout,*) 'sbcrnf : runoff forcing fields written in ocean restart file ', &
  194. & 'at it= ', kt,' date= ', ndastp
  195. IF(lwp) WRITE(numout,*) '~~~~'
  196. CALL iom_rstput( kt, nitrst, numrow, 'rnf_b' , rnf )
  197. CALL iom_rstput( kt, nitrst, numrow, 'rnf_hc_b', rnf_tsc(:,:,jp_tem) )
  198. CALL iom_rstput( kt, nitrst, numrow, 'rnf_sc_b', rnf_tsc(:,:,jp_sal) )
  199. ENDIF
  200. !
  201. END SUBROUTINE sbc_rnf
  202. SUBROUTINE sbc_rnf_div( phdivn, Kmm )
  203. !!----------------------------------------------------------------------
  204. !! *** ROUTINE sbc_rnf ***
  205. !!
  206. !! ** Purpose : update the horizontal divergence with the runoff inflow
  207. !!
  208. !! ** Method :
  209. !! CAUTION : rnf is positive (inflow) decreasing the
  210. !! divergence and expressed in m/s
  211. !!
  212. !! ** Action : phdivn decreased by the runoff inflow
  213. !!----------------------------------------------------------------------
  214. INTEGER , INTENT(in ) :: Kmm ! ocean time level index
  215. REAL(wp), DIMENSION(:,:,:), INTENT(inout) :: phdivn ! horizontal divergence
  216. !!
  217. INTEGER :: ji, jj, jk ! dummy loop indices
  218. REAL(wp) :: zfact ! local scalar
  219. !!----------------------------------------------------------------------
  220. !
  221. zfact = 0.5_wp
  222. !
  223. IF( ln_rnf_depth .OR. ln_rnf_depth_ini ) THEN !== runoff distributed over several levels ==!
  224. IF( ln_linssh ) THEN !* constant volume case : just apply the runoff input flow
  225. DO_2D_OVR( nn_hls-1, nn_hls, nn_hls-1, nn_hls )
  226. DO jk = 1, nk_rnf(ji,jj)
  227. phdivn(ji,jj,jk) = phdivn(ji,jj,jk) - ( rnf(ji,jj) + rnf_b(ji,jj) ) * zfact * r1_rho0 / h_rnf(ji,jj)
  228. END DO
  229. END_2D
  230. ELSE !* variable volume case
  231. DO_2D_OVR( nn_hls, nn_hls, nn_hls, nn_hls ) ! update the depth over which runoffs are distributed
  232. h_rnf(ji,jj) = 0._wp
  233. DO jk = 1, nk_rnf(ji,jj) ! recalculates h_rnf to be the depth in metres
  234. h_rnf(ji,jj) = h_rnf(ji,jj) + e3t(ji,jj,jk,Kmm) ! to the bottom of the relevant grid box
  235. END DO
  236. END_2D
  237. DO_2D_OVR( nn_hls-1, nn_hls, nn_hls-1, nn_hls ) ! apply the runoff input flow
  238. DO jk = 1, nk_rnf(ji,jj)
  239. phdivn(ji,jj,jk) = phdivn(ji,jj,jk) - ( rnf(ji,jj) + rnf_b(ji,jj) ) * zfact * r1_rho0 / h_rnf(ji,jj)
  240. END DO
  241. END_2D
  242. ENDIF
  243. ELSE !== runoff put only at the surface ==!
  244. DO_2D_OVR( nn_hls, nn_hls, nn_hls, nn_hls )
  245. h_rnf (ji,jj) = e3t(ji,jj,1,Kmm) ! update h_rnf to be depth of top box
  246. END_2D
  247. DO_2D_OVR( nn_hls-1, nn_hls, nn_hls-1, nn_hls )
  248. phdivn(ji,jj,1) = phdivn(ji,jj,1) - ( rnf(ji,jj) + rnf_b(ji,jj) ) * zfact * r1_rho0 / e3t(ji,jj,1,Kmm)
  249. END_2D
  250. ENDIF
  251. !
  252. END SUBROUTINE sbc_rnf_div
  253. SUBROUTINE sbc_rnf_init( Kmm )
  254. !!----------------------------------------------------------------------
  255. !! *** ROUTINE sbc_rnf_init ***
  256. !!
  257. !! ** Purpose : Initialisation of the runoffs if (ln_rnf=T)
  258. !!
  259. !! ** Method : - read the runoff namsbc_rnf namelist
  260. !!
  261. !! ** Action : - read parameters
  262. !!----------------------------------------------------------------------
  263. INTEGER, INTENT(in) :: Kmm ! ocean time level index
  264. CHARACTER(len=32) :: rn_dep_file ! runoff file name
  265. INTEGER :: ji, jj, jk, jm ! dummy loop indices
  266. INTEGER :: ierror, inum ! temporary integer
  267. INTEGER :: ios ! Local integer output status for namelist read
  268. INTEGER :: nbrec ! temporary integer
  269. REAL(wp) :: zacoef
  270. REAL(wp), DIMENSION(jpi,jpj,2) :: zrnfcl
  271. !!
  272. NAMELIST/namsbc_rnf/ cn_dir , ln_rnf_depth, ln_rnf_tem, ln_rnf_sal, ln_rnf_icb, &
  273. & sn_rnf, sn_cnf , sn_i_rnf, sn_s_rnf , sn_t_rnf , sn_dep_rnf, &
  274. & ln_rnf_mouth , rn_hrnf , rn_avt_rnf, rn_rfact, &
  275. & ln_rnf_depth_ini , rn_dep_max , rn_rnf_max, nn_rnf_depth_file
  276. #if defined key_drakkar
  277. INTEGER :: ierror2
  278. NAMELIST/namsbc_rnf_drk/ nn_rnf_freq, sn_rnf2
  279. #endif
  280. !!----------------------------------------------------------------------
  281. !
  282. ! !== allocate runoff arrays
  283. IF( sbc_rnf_alloc() /= 0 ) CALL ctl_stop( 'STOP', 'sbc_rnf_alloc : unable to allocate arrays' )
  284. !
  285. IF( .NOT. ln_rnf ) THEN ! no specific treatment in vicinity of river mouths
  286. ln_rnf_mouth = .FALSE. ! default definition needed for example by sbc_ssr or by tra_adv_muscl
  287. nkrnf = 0
  288. rnf (:,:) = 0.0_wp
  289. rnf_b (:,:) = 0.0_wp
  290. rnfmsk (:,:) = 0.0_wp
  291. rnfmsk_z(:) = 0.0_wp
  292. RETURN
  293. ENDIF
  294. !
  295. ! ! ============
  296. ! ! Namelist
  297. ! ! ============
  298. !
  299. READ ( numnam_ref, namsbc_rnf, IOSTAT = ios, ERR = 901)
  300. 901 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_rnf in reference namelist' )
  301. READ ( numnam_cfg, namsbc_rnf, IOSTAT = ios, ERR = 902 )
  302. 902 IF( ios > 0 ) CALL ctl_nam ( ios , 'namsbc_rnf in configuration namelist' )
  303. IF(lwm) WRITE ( numond, namsbc_rnf )
  304. #if defined key_drakkar
  305. READ ( numnam_ref, namsbc_rnf_drk, IOSTAT = ios, ERR = 903)
  306. 903 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_rnf_drk in reference namelist' )
  307. READ ( numnam_cfg, namsbc_rnf_drk, IOSTAT = ios, ERR = 904 )
  308. 904 IF( ios > 0 ) CALL ctl_nam ( ios , 'namsbc_rnf_drk in configuration namelist' )
  309. IF(lwm) WRITE ( numond, namsbc_rnf_drk )
  310. #endif
  311. !
  312. ! ! Control print
  313. IF(lwp) THEN
  314. WRITE(numout,*)
  315. WRITE(numout,*) 'sbc_rnf_init : runoff '
  316. WRITE(numout,*) '~~~~~~~~~~~~ '
  317. WRITE(numout,*) ' Namelist namsbc_rnf'
  318. WRITE(numout,*) ' specific river mouths treatment ln_rnf_mouth = ', ln_rnf_mouth
  319. WRITE(numout,*) ' river mouth additional Kz rn_avt_rnf = ', rn_avt_rnf
  320. WRITE(numout,*) ' depth of river mouth additional mixing rn_hrnf = ', rn_hrnf
  321. WRITE(numout,*) ' multiplicative factor for runoff rn_rfact = ', rn_rfact
  322. ENDIF
  323. ! ! ==================
  324. ! ! Type of runoff
  325. ! ! ==================
  326. !
  327. IF( .NOT. l_rnfcpl ) THEN
  328. #if defined key_drakkar
  329. IF(lwp) WRITE(numout,*)
  330. IF(lwp) WRITE(numout,*) ' ==>>> runoffs inflow read in ',nn_rnf_freq,' file(s)'
  331. ALLOCATE( sf_rnf(nn_rnf_freq), STAT=ierror ) ! Create sf_rnf structure (runoff inflow)
  332. DO ji = 1, nn_rnf_freq
  333. ALLOCATE ( sf_rnf(ji)%fnow(jpi,jpj,1) , STAT=ierror2) ; ierror = ierror + ierror2
  334. ALLOCATE ( sf_rnf(ji)%fdta(jpi,jpj,1,2), STAT=ierror2) ; ierror = ierror + ierror2
  335. ENDDO
  336. IF( ierror > 0 ) THEN
  337. CALL ctl_stop( 'sbc_rnf_init: unable to allocate sf_rnf structure' ) ; RETURN
  338. ENDIF
  339. slf_rnf(1) = sn_rnf
  340. DO ji = 2, nn_rnf_freq
  341. slf_rnf(ji) = sn_rnf2(ji-1)
  342. ENDDO
  343. CALL fld_fill( sf_rnf, slf_rnf(1:nn_rnf_freq), cn_dir, 'sbc_rnf_init', 'read runoffs data', 'namsbc_rnf', no_print )
  344. #else
  345. ALLOCATE( sf_rnf(1), STAT=ierror ) ! Create sf_rnf structure (runoff inflow)
  346. IF(lwp) WRITE(numout,*)
  347. IF(lwp) WRITE(numout,*) ' ==>>> runoffs inflow read in a file'
  348. IF( ierror > 0 ) THEN
  349. CALL ctl_stop( 'sbc_rnf_init: unable to allocate sf_rnf structure' ) ; RETURN
  350. ENDIF
  351. ALLOCATE( sf_rnf(1)%fnow(jpi,jpj,1) )
  352. IF( sn_rnf%ln_tint ) ALLOCATE( sf_rnf(1)%fdta(jpi,jpj,1,2) )
  353. CALL fld_fill( sf_rnf, (/ sn_rnf /), cn_dir, 'sbc_rnf_init', 'read runoffs data', 'namsbc_rnf', no_print )
  354. #endif
  355. !
  356. IF( ln_rnf_icb ) THEN ! Create (if required) sf_i_rnf structure
  357. IF(lwp) WRITE(numout,*)
  358. IF(lwp) WRITE(numout,*) ' iceberg flux read in a file'
  359. ALLOCATE( sf_i_rnf(1), STAT=ierror )
  360. IF( ierror > 0 ) THEN
  361. CALL ctl_stop( 'sbc_rnf_init: unable to allocate sf_i_rnf structure' ) ; RETURN
  362. ENDIF
  363. ALLOCATE( sf_i_rnf(1)%fnow(jpi,jpj,1) )
  364. IF( sn_i_rnf%ln_tint ) ALLOCATE( sf_i_rnf(1)%fdta(jpi,jpj,1,2) )
  365. CALL fld_fill (sf_i_rnf, (/ sn_i_rnf /), cn_dir, 'sbc_rnf_init', 'read iceberg flux data', 'namsbc_rnf' )
  366. ELSE
  367. fwficb(:,:) = 0._wp
  368. ENDIF
  369. ENDIF
  370. !
  371. IF( ln_rnf_tem ) THEN ! Create (if required) sf_t_rnf structure
  372. IF(lwp) WRITE(numout,*)
  373. IF(lwp) WRITE(numout,*) ' ==>>> runoffs temperatures read in a file'
  374. ALLOCATE( sf_t_rnf(1), STAT=ierror )
  375. IF( ierror > 0 ) THEN
  376. CALL ctl_stop( 'sbc_rnf_init: unable to allocate sf_t_rnf structure' ) ; RETURN
  377. ENDIF
  378. ALLOCATE( sf_t_rnf(1)%fnow(jpi,jpj,1) )
  379. IF( sn_t_rnf%ln_tint ) ALLOCATE( sf_t_rnf(1)%fdta(jpi,jpj,1,2) )
  380. CALL fld_fill (sf_t_rnf, (/ sn_t_rnf /), cn_dir, 'sbc_rnf_init', 'read runoff temperature data', 'namsbc_rnf', no_print )
  381. ENDIF
  382. !
  383. IF( ln_rnf_sal ) THEN ! Create (if required) sf_s_rnf and sf_t_rnf structures
  384. IF(lwp) WRITE(numout,*)
  385. IF(lwp) WRITE(numout,*) ' ==>>> runoffs salinities read in a file'
  386. ALLOCATE( sf_s_rnf(1), STAT=ierror )
  387. IF( ierror > 0 ) THEN
  388. CALL ctl_stop( 'sbc_rnf_init: unable to allocate sf_s_rnf structure' ) ; RETURN
  389. ENDIF
  390. ALLOCATE( sf_s_rnf(1)%fnow(jpi,jpj,1) )
  391. IF( sn_s_rnf%ln_tint ) ALLOCATE( sf_s_rnf(1)%fdta(jpi,jpj,1,2) )
  392. CALL fld_fill (sf_s_rnf, (/ sn_s_rnf /), cn_dir, 'sbc_rnf_init', 'read runoff salinity data', 'namsbc_rnf', no_print )
  393. ENDIF
  394. !
  395. IF( ln_rnf_depth ) THEN ! depth of runoffs set from a file
  396. IF(lwp) WRITE(numout,*)
  397. IF(lwp) WRITE(numout,*) ' ==>>> runoffs depth read in a file'
  398. rn_dep_file = TRIM( cn_dir )//TRIM( sn_dep_rnf%clname )
  399. IF( .NOT. sn_dep_rnf%ln_clim ) THEN ; WRITE(rn_dep_file, '(a,"_y",i4)' ) TRIM( rn_dep_file ), nyear ! add year
  400. IF( sn_dep_rnf%clftyp == 'monthly' ) WRITE(rn_dep_file, '(a,"m",i2)' ) TRIM( rn_dep_file ), nmonth ! add month
  401. ENDIF
  402. CALL iom_open ( rn_dep_file, inum ) ! open file
  403. CALL iom_get ( inum, jpdom_global, sn_dep_rnf%clvar, h_rnf, kfill = jpfillcopy ) ! read the river mouth. no 0 on halos!
  404. CALL iom_close( inum ) ! close file
  405. !
  406. nk_rnf(:,:) = 0 ! set the number of level over which river runoffs are applied
  407. DO_2D( nn_hls, nn_hls, nn_hls, nn_hls )
  408. IF( h_rnf(ji,jj) > 0._wp ) THEN
  409. jk = 2
  410. DO WHILE ( jk < mbkt(ji,jj) .AND. gdept_0(ji,jj,jk) < h_rnf(ji,jj) ) ; jk = jk + 1
  411. END DO
  412. nk_rnf(ji,jj) = jk
  413. ELSEIF( h_rnf(ji,jj) == -1._wp ) THEN ; nk_rnf(ji,jj) = 1
  414. ELSEIF( h_rnf(ji,jj) == -999._wp ) THEN ; nk_rnf(ji,jj) = mbkt(ji,jj)
  415. ELSE
  416. CALL ctl_stop( 'sbc_rnf_init: runoff depth not positive, and not -999 or -1, rnf value in file fort.999' )
  417. WRITE(999,*) 'ji, jj, h_rnf(ji,jj) :', ji, jj, h_rnf(ji,jj)
  418. ENDIF
  419. END_2D
  420. DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) ! set the associated depth
  421. h_rnf(ji,jj) = 0._wp
  422. DO jk = 1, nk_rnf(ji,jj)
  423. h_rnf(ji,jj) = h_rnf(ji,jj) + e3t(ji,jj,jk,Kmm)
  424. END DO
  425. END_2D
  426. !
  427. ELSE IF( ln_rnf_depth_ini ) THEN ! runoffs applied at the surface
  428. !
  429. IF(lwp) WRITE(numout,*)
  430. IF(lwp) WRITE(numout,*) ' ==>>> depth of runoff computed once from max value of runoff'
  431. IF(lwp) WRITE(numout,*) ' max value of the runoff climatologie (over global domain) rn_rnf_max = ', rn_rnf_max
  432. IF(lwp) WRITE(numout,*) ' depth over which runoffs is spread rn_dep_max = ', rn_dep_max
  433. IF(lwp) WRITE(numout,*) ' create (=1) a runoff depth file or not (=0) nn_rnf_depth_file = ', nn_rnf_depth_file
  434. CALL iom_open( TRIM( sn_rnf%clname ), inum ) ! open runoff file
  435. nbrec = iom_getszuld( inum )
  436. zrnfcl(:,:,1) = 0._wp ! init the max to 0. in 1
  437. DO jm = 1, nbrec
  438. CALL iom_get( inum, jpdom_global, TRIM( sn_rnf%clvar ), zrnfcl(:,:,2), jm ) ! read the value in 2
  439. zrnfcl(:,:,1) = MAXVAL( zrnfcl(:,:,:), DIM=3 ) ! store the maximum value in time in 1
  440. END DO
  441. CALL iom_close( inum )
  442. !
  443. ! ELIC change
  444. ! - the iceberg flux should be taken into account to compute the depth up
  445. ! to which the runoff must be distributed vertically
  446. ! - the implementation below is not perfect: it selects the maximum runoff
  447. ! or iceberg flux (over the records) instead of selecting the maximum
  448. ! (over the records) of the sum of the runoff and the iceberg flux
  449. ! - since the runoff and the iceberg flux are often not colocated, this is
  450. ! not a severe problem
  451. ! - in addition, since the runoff and iceberg flux could have different
  452. ! number of records, this would be difficult to improve
  453. !
  454. IF( ln_rnf_icb ) THEN
  455. CALL iom_open( TRIM( sn_i_rnf%clname ), inum ) ! open iceberg flux file
  456. nbrec = iom_getszuld( inum )
  457. DO jm = 1, nbrec
  458. CALL iom_get( inum, jpdom_global, TRIM( sn_i_rnf%clvar ), zrnfcl(:,:,2), jm ) ! read the value in 2
  459. zrnfcl(:,:,1) = MAXVAL( zrnfcl(:,:,:), DIM=3 ) ! store the maximum value in time in 1
  460. END DO
  461. CALL iom_close( inum )
  462. ENDIF
  463. ! end ELIC change
  464. !
  465. h_rnf(:,:) = 1.
  466. !
  467. zacoef = rn_dep_max / rn_rnf_max ! coef of linear relation between runoff and its depth (150m for max of runoff)
  468. !
  469. WHERE( zrnfcl(:,:,1) > 0._wp ) h_rnf(:,:) = zacoef * zrnfcl(:,:,1) ! compute depth for all runoffs
  470. !
  471. DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) ! take in account min depth of ocean rn_hmin
  472. IF( zrnfcl(ji,jj,1) > 0._wp ) THEN
  473. jk = mbkt(ji,jj)
  474. h_rnf(ji,jj) = MIN( h_rnf(ji,jj), gdept_0(ji,jj,jk ) )
  475. ENDIF
  476. END_2D
  477. !
  478. nk_rnf(:,:) = 0 ! number of levels on which runoffs are distributed
  479. DO_2D( nn_hls, nn_hls, nn_hls, nn_hls )
  480. IF( zrnfcl(ji,jj,1) > 0._wp ) THEN
  481. jk = 2
  482. DO WHILE ( jk < mbkt(ji,jj) .AND. gdept_0(ji,jj,jk) < h_rnf(ji,jj) ) ; jk = jk + 1
  483. END DO
  484. nk_rnf(ji,jj) = jk
  485. ELSE
  486. nk_rnf(ji,jj) = 1
  487. ENDIF
  488. END_2D
  489. !
  490. DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) ! set the associated depth
  491. h_rnf(ji,jj) = 0._wp
  492. DO jk = 1, nk_rnf(ji,jj)
  493. h_rnf(ji,jj) = h_rnf(ji,jj) + e3t(ji,jj,jk,Kmm)
  494. END DO
  495. END_2D
  496. !
  497. IF( nn_rnf_depth_file == 1 ) THEN ! save output nb levels for runoff
  498. IF(lwp) WRITE(numout,*) ' ==>>> create runoff depht file'
  499. CALL iom_open ( TRIM( sn_dep_rnf%clname ), inum, ldwrt = .TRUE. )
  500. CALL iom_rstput( 0, 0, inum, 'rodepth', h_rnf )
  501. CALL iom_close ( inum )
  502. ENDIF
  503. ELSE ! runoffs applied at the surface
  504. nk_rnf(:,:) = 1
  505. h_rnf (:,:) = e3t(:,:,1,Kmm)
  506. ENDIF
  507. !
  508. rnf(:,:) = 0._wp ! runoff initialisation
  509. rnf_tsc(:,:,:) = 0._wp ! runoffs temperature & salinty contents initilisation
  510. !
  511. ! ! ========================
  512. ! ! River mouth vicinity
  513. ! ! ========================
  514. !
  515. IF( ln_rnf_mouth ) THEN ! Specific treatment in vicinity of river mouths :
  516. ! ! - Increase Kz in surface layers ( rn_hrnf > 0 )
  517. ! ! - set to zero SSS damping (ln_ssr=T)
  518. ! ! - mixed upstream-centered (ln_traadv_cen2=T)
  519. !
  520. IF( ln_rnf_depth ) CALL ctl_warn( 'sbc_rnf_init: increased mixing turned on but effects may already', &
  521. & 'be spread through depth by ln_rnf_depth' )
  522. !
  523. nkrnf = 0 ! Number of level over which Kz increase
  524. IF( rn_hrnf > 0._wp ) THEN
  525. nkrnf = 2
  526. DO WHILE( nkrnf /= jpkm1 .AND. gdepw_1d(nkrnf+1) < rn_hrnf ) ; nkrnf = nkrnf + 1
  527. END DO
  528. IF( ln_sco ) CALL ctl_warn( 'sbc_rnf_init: number of levels over which Kz is increased is computed for zco...' )
  529. ENDIF
  530. IF(lwp) WRITE(numout,*)
  531. IF(lwp) WRITE(numout,*) ' ==>>> Specific treatment used in vicinity of river mouths :'
  532. IF(lwp) WRITE(numout,*) ' - Increase Kz in surface layers (if rn_hrnf > 0 )'
  533. IF(lwp) WRITE(numout,*) ' by ', rn_avt_rnf,' m2/s over ', nkrnf, ' w-levels'
  534. IF(lwp) WRITE(numout,*) ' - set to zero SSS damping (if ln_ssr=T)'
  535. IF(lwp) WRITE(numout,*) ' - mixed upstream-centered (if ln_traadv_cen2=T)'
  536. !
  537. CALL rnf_mouth ! set river mouth mask
  538. !
  539. ELSE ! No treatment at river mouths
  540. IF(lwp) WRITE(numout,*)
  541. IF(lwp) WRITE(numout,*) ' ==>>> No specific treatment at river mouths'
  542. rnfmsk (:,:) = 0._wp
  543. #if defined key_drakkar
  544. ! rnf_msk is read from socoefr even if ln_rnf_mouth = F
  545. ! because it is used in SSS restoring
  546. CALL rnf_mouth ! set river mouth mask
  547. #endif
  548. rnfmsk_z(:) = 0._wp
  549. nkrnf = 0
  550. ENDIF
  551. !
  552. END SUBROUTINE sbc_rnf_init
  553. SUBROUTINE rnf_mouth
  554. !!----------------------------------------------------------------------
  555. !! *** ROUTINE rnf_mouth ***
  556. !!
  557. !! ** Purpose : define the river mouths mask
  558. !!
  559. !! ** Method : read the river mouth mask (=0/1) in the river runoff
  560. !! climatological file. Defined a given vertical structure.
  561. !! CAUTION, the vertical structure is hard coded on the
  562. !! first 5 levels.
  563. !! This fields can be used to:
  564. !! - set an upstream advection scheme
  565. !! (ln_rnf_mouth=T and ln_traadv_cen2=T)
  566. !! - increase vertical on the top nn_krnf vertical levels
  567. !! at river runoff input grid point (nn_krnf>=2, see step.F90)
  568. !! - set to zero SSS restoring flux at river mouth grid points
  569. !!
  570. !! ** Action : rnfmsk set to 1 at river runoff input, 0 elsewhere
  571. !! rnfmsk_z vertical structure
  572. !!----------------------------------------------------------------------
  573. INTEGER :: inum ! temporary integers
  574. CHARACTER(len=140) :: cl_rnfile ! runoff file name
  575. !!----------------------------------------------------------------------
  576. !
  577. IF(lwp) WRITE(numout,*)
  578. IF(lwp) WRITE(numout,*) ' rnf_mouth : river mouth mask'
  579. IF(lwp) WRITE(numout,*) ' ~~~~~~~~~ '
  580. !
  581. cl_rnfile = TRIM( cn_dir )//TRIM( sn_cnf%clname )
  582. IF( .NOT. sn_cnf%ln_clim ) THEN ; WRITE(cl_rnfile, '(a,"_y",i4.4)' ) TRIM( cl_rnfile ), nyear ! add year
  583. IF( sn_cnf%clftyp == 'monthly' ) WRITE(cl_rnfile, '(a,"m" ,i2.2)' ) TRIM( cl_rnfile ), nmonth ! add month
  584. ENDIF
  585. !
  586. ! horizontal mask (read in NetCDF file)
  587. CALL iom_open ( cl_rnfile, inum ) ! open file
  588. CALL iom_get ( inum, jpdom_global, sn_cnf%clvar, rnfmsk ) ! read the river mouth array
  589. CALL iom_close( inum ) ! close file
  590. !
  591. IF( l_clo_rnf ) CALL clo_rnf( rnfmsk ) ! closed sea inflow set as river mouth
  592. !
  593. rnfmsk_z(:) = 0._wp ! vertical structure
  594. rnfmsk_z(1) = 1.0
  595. rnfmsk_z(2) = 1.0 ! **********
  596. rnfmsk_z(3) = 0.5 ! HARD CODED on the 5 first levels
  597. rnfmsk_z(4) = 0.25 ! **********
  598. rnfmsk_z(5) = 0.125
  599. !
  600. END SUBROUTINE rnf_mouth
  601. !!======================================================================
  602. END MODULE sbcrnf