trcbc.F90 15 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311
  1. MODULE trcbc
  2. !!======================================================================
  3. !! *** MODULE trcdta ***
  4. !! TOP : module for passive tracer boundary conditions
  5. !!=====================================================================
  6. !!----------------------------------------------------------------------
  7. #if defined key_top
  8. !!----------------------------------------------------------------------
  9. !! 'key_top' TOP model
  10. !!----------------------------------------------------------------------
  11. !! trc_dta : read and time interpolated passive tracer data
  12. !!----------------------------------------------------------------------
  13. USE par_trc ! passive tracers parameters
  14. USE oce_trc ! shared variables between ocean and passive tracers
  15. USE trc ! passive tracers common variables
  16. USE iom ! I/O manager
  17. USE lib_mpp ! MPP library
  18. USE fldread ! read input fields
  19. IMPLICIT NONE
  20. PRIVATE
  21. PUBLIC trc_bc_init ! called in trcini.F90
  22. PUBLIC trc_bc_read ! called in trcstp.F90 or within
  23. INTEGER , SAVE, PUBLIC :: nb_trcobc ! number of tracers with open BC
  24. INTEGER , SAVE, PUBLIC :: nb_trcsbc ! number of tracers with surface BC
  25. INTEGER , SAVE, PUBLIC :: nb_trccbc ! number of tracers with coastal BC
  26. INTEGER , SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:) :: n_trc_indobc ! index of tracer with OBC data
  27. INTEGER , SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:) :: n_trc_indsbc ! index of tracer with SBC data
  28. INTEGER , SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:) :: n_trc_indcbc ! index of tracer with CBC data
  29. INTEGER , SAVE, PUBLIC :: ntra_obc ! MAX( 1, nb_trcxxx ) to avoid compilation error with bounds checking
  30. INTEGER , SAVE, PUBLIC :: ntra_sbc ! MAX( 1, nb_trcxxx ) to avoid compilation error with bounds checking
  31. INTEGER , SAVE, PUBLIC :: ntra_cbc ! MAX( 1, nb_trcxxx ) to avoid compilation error with bounds checking
  32. REAL(wp) , SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:) :: rf_trofac ! multiplicative factor for OBCtracer values
  33. TYPE(FLD), SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:) :: sf_trcobc ! structure of data input OBC (file informations, fields read)
  34. REAL(wp) , SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:) :: rf_trsfac ! multiplicative factor for SBC tracer values
  35. TYPE(FLD), SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:) :: sf_trcsbc ! structure of data input SBC (file informations, fields read)
  36. REAL(wp) , SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:) :: rf_trcfac ! multiplicative factor for CBC tracer values
  37. TYPE(FLD), SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:) :: sf_trccbc ! structure of data input CBC (file informations, fields read)
  38. !! * Substitutions
  39. # include "domzgr_substitute.h90"
  40. !!----------------------------------------------------------------------
  41. !! NEMO/OPA 3.3 , NEMO Consortium (2010)
  42. !! $Id: trcbc.F90 4578 2017-09-25 09:34:12Z ufla $
  43. !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
  44. !!----------------------------------------------------------------------
  45. CONTAINS
  46. SUBROUTINE trc_bc_init(ntrc)
  47. !!----------------------------------------------------------------------
  48. !! *** ROUTINE trc_bc_init ***
  49. !!
  50. !! ** Purpose : initialisation of passive tracer BC data
  51. !!
  52. !! ** Method : - Read namtsd namelist
  53. !! - allocates passive tracer BC data structure
  54. !!----------------------------------------------------------------------
  55. !
  56. INTEGER,INTENT(IN) :: ntrc ! number of tracers
  57. INTEGER :: jl, jn ! dummy loop indices
  58. INTEGER :: ierr0, ierr1, ierr2, ierr3 ! temporary integers
  59. INTEGER :: ios ! Local integer output status for namelist read
  60. CHARACTER(len=100) :: clndta, clntrc
  61. !
  62. CHARACTER(len=100) :: cn_dir
  63. TYPE(FLD_N), ALLOCATABLE, DIMENSION(:) :: slf_i ! local array of namelist informations on the fields to read
  64. TYPE(FLD_N), DIMENSION(jpmaxtrc) :: sn_trcobc ! open
  65. TYPE(FLD_N), DIMENSION(jpmaxtrc) :: sn_trcsbc ! surface
  66. TYPE(FLD_N), DIMENSION(jpmaxtrc) :: sn_trccbc ! coastal
  67. REAL(wp) , DIMENSION(jpmaxtrc) :: rn_trofac ! multiplicative factor for tracer values
  68. REAL(wp) , DIMENSION(jpmaxtrc) :: rn_trsfac ! multiplicative factor for tracer values
  69. REAL(wp) , DIMENSION(jpmaxtrc) :: rn_trcfac ! multiplicative factor for tracer values
  70. !!
  71. NAMELIST/namtrc_bc/ cn_dir, sn_trcobc, rn_trofac, sn_trcsbc, rn_trsfac, sn_trccbc, rn_trcfac
  72. !!----------------------------------------------------------------------
  73. IF( nn_timing == 1 ) CALL timing_start('trc_bc_init')
  74. !
  75. ! Initialisation and local array allocation
  76. ierr0 = 0 ; ierr1 = 0 ; ierr2 = 0 ; ierr3 = 0
  77. ALLOCATE( slf_i(ntrc), STAT=ierr0 )
  78. IF( ierr0 > 0 ) THEN
  79. CALL ctl_stop( 'trc_bc_init: unable to allocate local slf_i' ) ; RETURN
  80. ENDIF
  81. ! Compute the number of tracers to be initialised with open, surface and boundary data
  82. ALLOCATE( n_trc_indobc(ntrc), STAT=ierr0 )
  83. IF( ierr0 > 0 ) THEN
  84. CALL ctl_stop( 'trc_bc_init: unable to allocate n_trc_indobc' ) ; RETURN
  85. ENDIF
  86. nb_trcobc = 0
  87. n_trc_indobc(:) = 0
  88. !
  89. ALLOCATE( n_trc_indsbc(ntrc), STAT=ierr0 )
  90. IF( ierr0 > 0 ) THEN
  91. CALL ctl_stop( 'trc_bc_init: unable to allocate n_trc_indsbc' ) ; RETURN
  92. ENDIF
  93. nb_trcsbc = 0
  94. n_trc_indsbc(:) = 0
  95. !
  96. ALLOCATE( n_trc_indcbc(ntrc), STAT=ierr0 )
  97. IF( ierr0 > 0 ) THEN
  98. CALL ctl_stop( 'trc_bc_init: unable to allocate n_trc_indcbc' ) ; RETURN
  99. ENDIF
  100. nb_trccbc = 0
  101. n_trc_indcbc(:) = 0
  102. !
  103. DO jn = 1, ntrc
  104. IF( ln_trc_obc(jn) ) THEN
  105. nb_trcobc = nb_trcobc + 1
  106. n_trc_indobc(jn) = nb_trcobc
  107. ENDIF
  108. IF( ln_trc_sbc(jn) ) THEN
  109. nb_trcsbc = nb_trcsbc + 1
  110. n_trc_indsbc(jn) = nb_trcsbc
  111. ENDIF
  112. IF( ln_trc_cbc(jn) ) THEN
  113. nb_trccbc = nb_trccbc + 1
  114. n_trc_indcbc(jn) = nb_trccbc
  115. ENDIF
  116. ENDDO
  117. ntra_obc = MAX( 1, nb_trcobc ) ! To avoid compilation error with bounds checking
  118. IF( lwp ) WRITE(numout,*) ' '
  119. IF( lwp ) WRITE(numout,*) ' Number of passive tracers to be initialized with open boundary data :', nb_trcobc
  120. IF( lwp ) WRITE(numout,*) ' '
  121. ntra_sbc = MAX( 1, nb_trcsbc ) ! To avoid compilation error with bounds checking
  122. IF( lwp ) WRITE(numout,*) ' '
  123. IF( lwp ) WRITE(numout,*) ' Number of passive tracers to be initialized with surface boundary data :', nb_trcsbc
  124. IF( lwp ) WRITE(numout,*) ' '
  125. ntra_cbc = MAX( 1, nb_trccbc ) ! To avoid compilation error with bounds checking
  126. IF( lwp ) WRITE(numout,*) ' '
  127. IF( lwp ) WRITE(numout,*) ' Number of passive tracers to be initialized with coastal boundary data :', nb_trccbc
  128. IF( lwp ) WRITE(numout,*) ' '
  129. REWIND( numnat_ref ) ! Namelist namtrc_bc in reference namelist : Passive tracer data structure
  130. READ ( numnat_ref, namtrc_bc, IOSTAT = ios, ERR = 901)
  131. 901 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_bc in reference namelist', lwp )
  132. REWIND( numnat_cfg ) ! Namelist namtrc_bc in configuration namelist : Passive tracer data structure
  133. READ ( numnat_cfg, namtrc_bc, IOSTAT = ios, ERR = 902 )
  134. 902 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_bc in configuration namelist', lwp )
  135. IF(lwm) WRITE ( numont, namtrc_bc )
  136. ! print some information for each
  137. IF( lwp ) THEN
  138. DO jn = 1, ntrc
  139. IF( ln_trc_obc(jn) ) THEN
  140. clndta = TRIM( sn_trcobc(jn)%clvar )
  141. IF(lwp) WRITE(numout,*) 'Preparing to read OBC data file for passive tracer number :', jn, ' name : ', clndta, &
  142. & ' multiplicative factor : ', rn_trofac(jn)
  143. ENDIF
  144. IF( ln_trc_sbc(jn) ) THEN
  145. clndta = TRIM( sn_trcsbc(jn)%clvar )
  146. IF(lwp) WRITE(numout,*) 'Preparing to read SBC data file for passive tracer number :', jn, ' name : ', clndta, &
  147. & ' multiplicative factor : ', rn_trsfac(jn)
  148. ENDIF
  149. IF( ln_trc_cbc(jn) ) THEN
  150. clndta = TRIM( sn_trccbc(jn)%clvar )
  151. IF(lwp) WRITE(numout,*) 'Preparing to read CBC data file for passive tracer number :', jn, ' name : ', clndta, &
  152. & ' multiplicative factor : ', rn_trcfac(jn)
  153. ENDIF
  154. END DO
  155. ENDIF
  156. !
  157. ! The following code is written this way to reduce memory usage and repeated for each boundary data
  158. ! MAV: note that this is just a placeholder and the dimensions must be changed according to
  159. ! what will be done with BDY. A new structure will probably need to be included
  160. !
  161. ! OPEN Lateral boundary conditions
  162. IF( nb_trcobc > 0 ) THEN ! allocate only if the number of tracer to initialise is greater than zero
  163. ALLOCATE( sf_trcobc(nb_trcobc), rf_trofac(nb_trcobc), STAT=ierr1 )
  164. IF( ierr1 > 0 ) THEN
  165. CALL ctl_stop( 'trc_bc_init: unable to allocate sf_trcobc structure' ) ; RETURN
  166. ENDIF
  167. !
  168. DO jn = 1, ntrc
  169. IF( ln_trc_obc(jn) ) THEN ! update passive tracers arrays with input data read from file
  170. jl = n_trc_indobc(jn)
  171. slf_i(jl) = sn_trcobc(jn)
  172. rf_trofac(jl) = rn_trofac(jn)
  173. ALLOCATE( sf_trcobc(jl)%fnow(jpi,jpj,jpk) , STAT=ierr2 )
  174. IF( sn_trcobc(jn)%ln_tint ) ALLOCATE( sf_trcobc(jl)%fdta(jpi,jpj,jpk,2) , STAT=ierr3 )
  175. IF( ierr2 + ierr3 > 0 ) THEN
  176. CALL ctl_stop( 'trc_bc_init : unable to allocate passive tracer OBC data arrays' ) ; RETURN
  177. ENDIF
  178. ENDIF
  179. !
  180. ENDDO
  181. ! ! fill sf_trcdta with slf_i and control print
  182. CALL fld_fill( sf_trcobc, slf_i, cn_dir, 'trc_bc_init', 'Passive tracer OBC data', 'namtrc_bc' )
  183. !
  184. ENDIF
  185. !
  186. ! SURFACE Boundary conditions
  187. IF( nb_trcsbc > 0 ) THEN ! allocate only if the number of tracer to initialise is greater than zero
  188. ALLOCATE( sf_trcsbc(nb_trcsbc), rf_trsfac(nb_trcsbc), STAT=ierr1 )
  189. IF( ierr1 > 0 ) THEN
  190. CALL ctl_stop( 'trc_bc_init: unable to allocate sf_trcsbc structure' ) ; RETURN
  191. ENDIF
  192. !
  193. DO jn = 1, ntrc
  194. IF( ln_trc_sbc(jn) ) THEN ! update passive tracers arrays with input data read from file
  195. jl = n_trc_indsbc(jn)
  196. slf_i(jl) = sn_trcsbc(jn)
  197. rf_trsfac(jl) = rn_trsfac(jn)
  198. ALLOCATE( sf_trcsbc(jl)%fnow(jpi,jpj,1) , STAT=ierr2 )
  199. IF( sn_trcsbc(jn)%ln_tint ) ALLOCATE( sf_trcsbc(jl)%fdta(jpi,jpj,1,2) , STAT=ierr3 )
  200. IF( ierr2 + ierr3 > 0 ) THEN
  201. CALL ctl_stop( 'trc_bc_init : unable to allocate passive tracer SBC data arrays' ) ; RETURN
  202. ENDIF
  203. ENDIF
  204. !
  205. ENDDO
  206. ! ! fill sf_trcsbc with slf_i and control print
  207. CALL fld_fill( sf_trcsbc, slf_i, cn_dir, 'trc_bc_init', 'Passive tracer SBC data', 'namtrc_bc' )
  208. !
  209. ENDIF
  210. !
  211. ! COSTAL Boundary conditions
  212. IF( nb_trccbc > 0 ) THEN ! allocate only if the number of tracer to initialise is greater than zero
  213. ALLOCATE( sf_trccbc(nb_trccbc), rf_trcfac(nb_trccbc), STAT=ierr1 )
  214. IF( ierr1 > 0 ) THEN
  215. CALL ctl_stop( 'trc_bc_ini: unable to allocate sf_trccbc structure' ) ; RETURN
  216. ENDIF
  217. !
  218. DO jn = 1, ntrc
  219. IF( ln_trc_cbc(jn) ) THEN ! update passive tracers arrays with input data read from file
  220. jl = n_trc_indcbc(jn)
  221. slf_i(jl) = sn_trccbc(jn)
  222. rf_trcfac(jl) = rn_trcfac(jn)
  223. ALLOCATE( sf_trccbc(jl)%fnow(jpi,jpj,1) , STAT=ierr2 )
  224. IF( sn_trccbc(jn)%ln_tint ) ALLOCATE( sf_trccbc(jl)%fdta(jpi,jpj,1,2) , STAT=ierr3 )
  225. IF( ierr2 + ierr3 > 0 ) THEN
  226. CALL ctl_stop( 'trc_bc_ini : unable to allocate passive tracer CBC data arrays' ) ; RETURN
  227. ENDIF
  228. ENDIF
  229. !
  230. ENDDO
  231. ! ! fill sf_trccbc with slf_i and control print
  232. CALL fld_fill( sf_trccbc, slf_i, cn_dir, 'trc_bc_init', 'Passive tracer CBC data', 'namtrc_bc' )
  233. !
  234. ENDIF
  235. DEALLOCATE( slf_i ) ! deallocate local field structure
  236. IF( nn_timing == 1 ) CALL timing_stop('trc_bc_init')
  237. END SUBROUTINE trc_bc_init
  238. SUBROUTINE trc_bc_read(kt)
  239. !!----------------------------------------------------------------------
  240. !! *** ROUTINE trc_bc_init ***
  241. !!
  242. !! ** Purpose : Read passive tracer Boundary Conditions data
  243. !!
  244. !! ** Method : Read BC inputs and update data structures using fldread
  245. !!
  246. !!----------------------------------------------------------------------
  247. ! NEMO
  248. USE fldread
  249. !! * Arguments
  250. INTEGER, INTENT( in ) :: kt ! ocean time-step index
  251. !!---------------------------------------------------------------------
  252. !
  253. IF( nn_timing == 1 ) CALL timing_start('trc_bc_read')
  254. IF( kt == nit000 ) THEN
  255. IF(lwp) WRITE(numout,*)
  256. IF(lwp) WRITE(numout,*) 'trc_bc_read : Surface boundary conditions for passive tracers.'
  257. IF(lwp) WRITE(numout,*) '~~~~~~~ '
  258. ENDIF
  259. ! OPEN boundary conditions: DOES NOT WORK. Waiting for stable BDY
  260. IF( nb_trcobc > 0 ) THEN
  261. if (lwp) write(numout,'(a,i5,a,i12)') ' reading OBC data for ', nb_trcobc ,' variables at step ', kt
  262. CALL fld_read(kt,1,sf_trcobc)
  263. ! vertical interpolation on s-grid and partial step to be added
  264. ENDIF
  265. ! SURFACE boundary conditions
  266. IF( nb_trcsbc > 0 ) THEN
  267. if (lwp) write(numout,'(a,i5,a,i12)') ' reading SBC data for ', nb_trcsbc ,' variables at step ', kt
  268. CALL fld_read(kt,1,sf_trcsbc)
  269. ENDIF
  270. ! COASTAL boundary conditions
  271. IF( nb_trccbc > 0 ) THEN
  272. if (lwp) write(numout,'(a,i5,a,i12)') ' reading CBC data for ', nb_trccbc ,' variables at step ', kt
  273. CALL fld_read(kt,1,sf_trccbc)
  274. ENDIF
  275. !
  276. IF( nn_timing == 1 ) CALL timing_stop('trc_bc_read')
  277. !
  278. END SUBROUTINE trc_bc_read
  279. #else
  280. !!----------------------------------------------------------------------
  281. !! Dummy module NO 3D passive tracer data
  282. !!----------------------------------------------------------------------
  283. CONTAINS
  284. SUBROUTINE trc_bc_read( kt ) ! Empty routine
  285. WRITE(*,*) 'trc_bc_read: You should not have seen this print! error?', kt
  286. END SUBROUTINE trc_bc_read
  287. #endif
  288. !!======================================================================
  289. END MODULE trcbc