trcdta.F90 14 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284
  1. MODULE trcdta
  2. !!======================================================================
  3. !! *** MODULE trcdta ***
  4. !! TOP : reads passive tracer data
  5. !!=====================================================================
  6. !! History : 1.0 ! 2002-04 (O. Aumont) original code
  7. !! - ! 2004-03 (C. Ethe) module
  8. !! - ! 2005-03 (O. Aumont, A. El Moussaoui) F90
  9. !! 3.4 ! 2010-11 (C. Ethe, G. Madec) use of fldread + dynamical allocation
  10. !! 3.5 ! 2013-08 (M. Vichi) generalization for other BGC models
  11. !!----------------------------------------------------------------------
  12. #if defined key_top
  13. !!----------------------------------------------------------------------
  14. !! 'key_top' TOP model
  15. !!----------------------------------------------------------------------
  16. !! trc_dta : read and time interpolated passive tracer data
  17. !!----------------------------------------------------------------------
  18. USE par_trc ! passive tracers parameters
  19. USE oce_trc ! shared variables between ocean and passive tracers
  20. USE trc ! passive tracers common variables
  21. USE iom ! I/O manager
  22. USE lib_mpp ! MPP library
  23. USE fldread ! read input fields
  24. IMPLICIT NONE
  25. PRIVATE
  26. PUBLIC trc_dta ! called in trcini.F90 and trcdmp.F90
  27. PUBLIC trc_dta_init ! called in trcini.F90
  28. INTEGER , SAVE, PUBLIC :: nb_trcdta ! number of tracers to be initialised with data
  29. INTEGER , SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:) :: n_trc_index ! indice of tracer which is initialised with data
  30. INTEGER , SAVE, PUBLIC :: ntra ! MAX( 1, nb_trcdta ) to avoid compilation error with bounds checking
  31. REAL(wp) , SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:) :: rf_trfac ! multiplicative factor for tracer values
  32. !$AGRIF_DO_NOT_TREAT
  33. TYPE(FLD), SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:) :: sf_trcdta ! structure of input SST (file informations, fields read)
  34. !$AGRIF_END_DO_NOT_TREAT
  35. !! * Substitutions
  36. # include "domzgr_substitute.h90"
  37. !!----------------------------------------------------------------------
  38. !! NEMO/OPA 3.3 , NEMO Consortium (2010)
  39. !! $Id: trcdta.F90 4624 2014-04-28 12:09:03Z acc $
  40. !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
  41. !!----------------------------------------------------------------------
  42. CONTAINS
  43. SUBROUTINE trc_dta_init(ntrc)
  44. !!----------------------------------------------------------------------
  45. !! *** ROUTINE trc_dta_init ***
  46. !!
  47. !! ** Purpose : initialisation of passive tracer input data
  48. !!
  49. !! ** Method : - Read namtsd namelist
  50. !! - allocates passive tracer data structure
  51. !!----------------------------------------------------------------------
  52. !
  53. INTEGER,INTENT(IN) :: ntrc ! number of tracers
  54. INTEGER :: jl, jn ! dummy loop indices
  55. INTEGER :: ierr0, ierr1, ierr2, ierr3 ! temporary integers
  56. INTEGER :: ios ! Local integer output status for namelist read
  57. CHARACTER(len=100) :: clndta, clntrc
  58. REAL(wp) :: zfact
  59. !
  60. CHARACTER(len=100) :: cn_dir
  61. TYPE(FLD_N), ALLOCATABLE, DIMENSION(:) :: slf_i ! array of namelist informations on the fields to read
  62. TYPE(FLD_N), DIMENSION(jpmaxtrc) :: sn_trcdta
  63. REAL(wp) , DIMENSION(jpmaxtrc) :: rn_trfac ! multiplicative factor for tracer values
  64. !!
  65. NAMELIST/namtrc_dta/ sn_trcdta, cn_dir, rn_trfac
  66. !!----------------------------------------------------------------------
  67. !
  68. IF( nn_timing == 1 ) CALL timing_start('trc_dta_init')
  69. !
  70. ! Initialisation
  71. ierr0 = 0 ; ierr1 = 0 ; ierr2 = 0 ; ierr3 = 0
  72. ! Compute the number of tracers to be initialised with data
  73. ALLOCATE( n_trc_index(ntrc), slf_i(ntrc), STAT=ierr0 )
  74. IF( ierr0 > 0 ) THEN
  75. CALL ctl_stop( 'trc_dta_init: unable to allocate n_trc_index' ) ; RETURN
  76. ENDIF
  77. nb_trcdta = 0
  78. n_trc_index(:) = 0
  79. DO jn = 1, ntrc
  80. IF( ln_trc_ini(jn) ) THEN
  81. nb_trcdta = nb_trcdta + 1
  82. n_trc_index(jn) = nb_trcdta
  83. ENDIF
  84. ENDDO
  85. !
  86. ntra = MAX( 1, nb_trcdta ) ! To avoid compilation error with bounds checking
  87. IF(lwp) THEN
  88. WRITE(numout,*) ' '
  89. WRITE(numout,*) 'trc_dta_init : Passive tracers Initial Conditions '
  90. WRITE(numout,*) '~~~~~~~~~~~~~~ '
  91. WRITE(numout,*) ' number of passive tracers to be initialize by data :', ntra
  92. WRITE(numout,*) ' '
  93. ENDIF
  94. !
  95. REWIND( numnat_ref ) ! Namelist namtrc_dta in reference namelist : Passive tracer input data
  96. READ ( numnat_ref, namtrc_dta, IOSTAT = ios, ERR = 901)
  97. 901 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dta in reference namelist', lwp )
  98. REWIND( numnat_cfg ) ! Namelist namtrc_dta in configuration namelist : Passive tracer input data
  99. READ ( numnat_cfg, namtrc_dta, IOSTAT = ios, ERR = 902 )
  100. 902 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dta in configuration namelist', lwp )
  101. IF(lwm) WRITE ( numont, namtrc_dta )
  102. IF( lwp ) THEN
  103. DO jn = 1, ntrc
  104. IF( ln_trc_ini(jn) ) THEN ! open input file only if ln_trc_ini(jn) is true
  105. clndta = TRIM( sn_trcdta(jn)%clvar )
  106. if (jn > jptra) then
  107. clntrc='Dummy' ! By pass weird formats in ocean.output if ntrc > jptra
  108. else
  109. clntrc = TRIM( ctrcnm (jn) )
  110. endif
  111. zfact = rn_trfac(jn)
  112. IF( clndta /= clntrc ) THEN
  113. CALL ctl_warn( 'trc_dta_init: passive tracer data initialisation ', &
  114. & 'Input name of data file : '//TRIM(clndta)// &
  115. & ' differs from that of tracer : '//TRIM(clntrc)//' ')
  116. ENDIF
  117. WRITE(numout,'(a, i4,3a,e11.3)') ' Read IC file for tracer number :', &
  118. & jn, ', name : ', TRIM(clndta), ', Multiplicative Scaling factor : ', zfact
  119. ENDIF
  120. END DO
  121. ENDIF
  122. !
  123. IF( nb_trcdta > 0 ) THEN ! allocate only if the number of tracer to initialise is greater than zero
  124. ALLOCATE( sf_trcdta(nb_trcdta), rf_trfac(nb_trcdta), STAT=ierr1 )
  125. IF( ierr1 > 0 ) THEN
  126. CALL ctl_stop( 'trc_dta_init: unable to allocate sf_trcdta structure' ) ; RETURN
  127. ENDIF
  128. !
  129. DO jn = 1, ntrc
  130. IF( ln_trc_ini(jn) ) THEN ! update passive tracers arrays with input data read from file
  131. jl = n_trc_index(jn)
  132. slf_i(jl) = sn_trcdta(jn)
  133. rf_trfac(jl) = rn_trfac(jn)
  134. ALLOCATE( sf_trcdta(jl)%fnow(jpi,jpj,jpk) , STAT=ierr2 )
  135. IF( sn_trcdta(jn)%ln_tint ) ALLOCATE( sf_trcdta(jl)%fdta(jpi,jpj,jpk,2) , STAT=ierr3 )
  136. IF( ierr2 + ierr3 > 0 ) THEN
  137. CALL ctl_stop( 'trc_dta_init : unable to allocate passive tracer data arrays' ) ; RETURN
  138. ENDIF
  139. ENDIF
  140. !
  141. ENDDO
  142. ! ! fill sf_trcdta with slf_i and control print
  143. CALL fld_fill( sf_trcdta, slf_i, cn_dir, 'trc_dta_init', 'Passive tracer data', 'namtrc' )
  144. !
  145. ENDIF
  146. !
  147. DEALLOCATE( slf_i ) ! deallocate local field structure
  148. IF( nn_timing == 1 ) CALL timing_stop('trc_dta_init')
  149. !
  150. END SUBROUTINE trc_dta_init
  151. SUBROUTINE trc_dta( kt, sf_dta, ptrfac, ptrc)
  152. !!----------------------------------------------------------------------
  153. !! *** ROUTINE trc_dta ***
  154. !!
  155. !! ** Purpose : provides passive tracer data at kt
  156. !!
  157. !! ** Method : - call fldread routine
  158. !! - s- or mixed z-s coordinate: vertical interpolation on model mesh
  159. !! - ln_trcdmp=F: deallocates the data structure as they are not used
  160. !!
  161. !! ** Action : sf_dta passive tracer data on medl mesh and interpolated at time-step kt
  162. !!----------------------------------------------------------------------
  163. INTEGER , INTENT(in ) :: kt ! ocean time-step
  164. TYPE(FLD), DIMENSION(1) , INTENT(inout) :: sf_dta ! array of information on the field to read
  165. REAL(wp) , INTENT(in ) :: ptrfac ! multiplication factor
  166. REAL(wp), DIMENSION(jpi,jpj,jpk), OPTIONAL , INTENT(out ) :: ptrc
  167. !
  168. INTEGER :: ji, jj, jk, jl, jkk, ik ! dummy loop indices
  169. REAL(wp):: zl, zi
  170. REAL(wp), DIMENSION(jpk) :: ztp ! 1D workspace
  171. REAL(wp), POINTER, DIMENSION(:,:,:) :: ztrcdta ! 3D workspace
  172. CHARACTER(len=100) :: clndta
  173. !!----------------------------------------------------------------------
  174. !
  175. IF( nn_timing == 1 ) CALL timing_start('trc_dta')
  176. !
  177. IF( nb_trcdta > 0 ) THEN
  178. !
  179. CALL wrk_alloc( jpi, jpj, jpk, ztrcdta ) ! Memory allocation
  180. !
  181. CALL fld_read( kt, 1, sf_dta ) !== read data at kt time step ==!
  182. ztrcdta(:,:,:) = sf_dta(1)%fnow(:,:,:) * tmask(:,:,:) ! Mask
  183. !
  184. IF( ln_sco ) THEN !== s- or mixed s-zps-coordinate ==!
  185. !
  186. IF( kt == nit000 .AND. lwp )THEN
  187. WRITE(numout,*)
  188. WRITE(numout,*) 'trc_dta: interpolates passive tracer data onto the s- or mixed s-z-coordinate mesh'
  189. ENDIF
  190. !
  191. DO jj = 1, jpj ! vertical interpolation of T & S
  192. DO ji = 1, jpi
  193. DO jk = 1, jpk ! determines the intepolated T-S profiles at each (i,j) points
  194. zl = gdept_0(ji,jj,jk)
  195. IF( zl < gdept_1d(1 ) ) THEN ! above the first level of data
  196. ztp(jk) = ztrcdta(ji,jj,1)
  197. ELSEIF( zl > gdept_1d(jpk) ) THEN ! below the last level of data
  198. ztp(jk) = ztrcdta(ji,jj,jpkm1)
  199. ELSE ! inbetween : vertical interpolation between jkk & jkk+1
  200. DO jkk = 1, jpkm1 ! when gdept(jkk) < zl < gdept(jkk+1)
  201. IF( (zl-gdept_1d(jkk)) * (zl-gdept_1d(jkk+1)) <= 0._wp ) THEN
  202. zi = ( zl - gdept_1d(jkk) ) / (gdept_1d(jkk+1)-gdept_1d(jkk))
  203. ztp(jk) = ztrcdta(ji,jj,jkk) + ( ztrcdta(ji,jj,jkk+1) - &
  204. ztrcdta(ji,jj,jkk) ) * zi
  205. ENDIF
  206. END DO
  207. ENDIF
  208. END DO
  209. DO jk = 1, jpkm1
  210. ztrcdta(ji,jj,jk) = ztp(jk) * tmask(ji,jj,jk) ! mask required for mixed zps-s-coord
  211. END DO
  212. ztrcdta(ji,jj,jpk) = 0._wp
  213. END DO
  214. END DO
  215. !
  216. ELSE !== z- or zps- coordinate ==!
  217. !
  218. IF( ln_zps ) THEN ! zps-coordinate (partial steps) interpolation at the last ocean level
  219. DO jj = 1, jpj
  220. DO ji = 1, jpi
  221. ik = mbkt(ji,jj)
  222. IF( ik > 1 ) THEN
  223. zl = ( gdept_1d(ik) - gdept_0(ji,jj,ik) ) / ( gdept_1d(ik) - gdept_1d(ik-1) )
  224. ztrcdta(ji,jj,ik) = (1.-zl) * ztrcdta(ji,jj,ik) + zl * ztrcdta(ji,jj,ik-1)
  225. ENDIF
  226. ik = mikt(ji,jj)
  227. IF( ik > 1 ) THEN
  228. zl = ( gdept_0(ji,jj,ik) - gdept_1d(ik) ) / ( gdept_1d(ik+1) - gdept_1d(ik) )
  229. ztrcdta(ji,jj,ik) = (1.-zl) * ztrcdta(ji,jj,ik) + zl * ztrcdta(ji,jj,ik+1)
  230. ENDIF
  231. END DO
  232. END DO
  233. ENDIF
  234. !
  235. ENDIF
  236. !
  237. ! Add multiplicative factor
  238. ztrcdta(:,:,:) = ztrcdta(:,:,:) * ptrfac
  239. !
  240. ! Data structure for trc_ini (and BFMv5.1 coupling)
  241. IF( .NOT. PRESENT(ptrc) ) sf_dta(1)%fnow(:,:,:) = ztrcdta(:,:,:)
  242. !
  243. ! Data structure for trc_dmp
  244. IF( PRESENT(ptrc) ) ptrc(:,:,:) = ztrcdta(:,:,:)
  245. !
  246. IF( lwp .AND. kt == nit000 ) THEN
  247. clndta = TRIM( sf_dta(1)%clvar )
  248. WRITE(numout,*) ''//clndta//' data '
  249. WRITE(numout,*)
  250. WRITE(numout,*)' level = 1'
  251. CALL prihre( ztrcdta(:,:,1), jpi, jpj, 1, jpi, 20, 1, jpj, 20, 1., numout )
  252. WRITE(numout,*)' level = ', jpk/2
  253. CALL prihre( ztrcdta(:,:,jpk/2), jpi, jpj, 1, jpi, 20, 1, jpj, 20, 1., numout )
  254. WRITE(numout,*)' level = ', jpkm1
  255. CALL prihre( ztrcdta(:,:,jpkm1), jpi, jpj, 1, jpi, 20, 1, jpj, 20, 1., numout )
  256. WRITE(numout,*)
  257. ENDIF
  258. !
  259. CALL wrk_dealloc( jpi, jpj, jpk, ztrcdta )
  260. !
  261. ENDIF
  262. !
  263. IF( nn_timing == 1 ) CALL timing_stop('trc_dta')
  264. !
  265. END SUBROUTINE trc_dta
  266. #else
  267. !!----------------------------------------------------------------------
  268. !! Dummy module NO 3D passive tracer data
  269. !!----------------------------------------------------------------------
  270. CONTAINS
  271. SUBROUTINE trc_dta( kt, sf_dta, ptrfac, ptrc) ! Empty routine
  272. WRITE(*,*) 'trc_dta: You should not have seen this print! error?', kt
  273. END SUBROUTINE trc_dta
  274. #endif
  275. !!======================================================================
  276. END MODULE trcdta