trcini_c14b.F90 7.8 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215
  1. MODULE trcini_c14b
  2. !!======================================================================
  3. !! *** MODULE trcini_c14b ***
  4. !! TOP : initialisation of the C14 bomb tracer
  5. !!======================================================================
  6. !! History : 1.0 ! 2005-10 (Z. Lachkar) Original code
  7. !! 2.0 ! 2007-12 (C. Ethe)
  8. !!----------------------------------------------------------------------
  9. #if defined key_c14b
  10. !!----------------------------------------------------------------------
  11. !! 'key_c14b' C14 bomb tracer
  12. !!----------------------------------------------------------------------
  13. !! trc_ini_c14b : C14 model initialisation
  14. !!----------------------------------------------------------------------
  15. USE oce_trc ! Ocean variables
  16. USE par_trc ! TOP parameters
  17. USE trc ! TOP variables
  18. USE trcsms_c14b ! C14 sms trends
  19. IMPLICIT NONE
  20. PRIVATE
  21. PUBLIC trc_ini_c14b ! called by trcini.F90 module
  22. ! ! With respect to data file !!
  23. INTEGER :: jpybeg = 1765 ! starting year for C14
  24. INTEGER :: jpyend = 2002 ! ending year for C14
  25. INTEGER :: nrec ! number of year in CO2 Concentrations file
  26. INTEGER :: nmaxrec
  27. INTEGER :: inum1, inum2 ! unit number
  28. REAL(wp) :: ys40 = -40. ! 40 degrees south
  29. REAL(wp) :: ys20 = -20. ! 20 degrees south
  30. REAL(wp) :: yn20 = 20. ! 20 degrees north
  31. REAL(wp) :: yn40 = 40. ! 40 degrees north
  32. !!----------------------------------------------------------------------
  33. !! NEMO/TOP 3.3 , NEMO Consortium (2010)
  34. !! $Id: trcini_c14b.F90 3294 2012-01-28 16:44:18Z rblod $
  35. !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
  36. !!----------------------------------------------------------------------
  37. CONTAINS
  38. SUBROUTINE trc_ini_c14b
  39. !!-------------------------------------------------------------------
  40. !! *** trc_ini_c14b ***
  41. !!
  42. !! ** Purpose : initialization for C14 model
  43. !!
  44. !!----------------------------------------------------------------------
  45. INTEGER :: ji, jj, jl, jm
  46. REAL(wp) :: zyear
  47. !!----------------------------------------------------------------------
  48. ! ! Allocate C14b arrays
  49. IF( trc_sms_c14b_alloc() /= 0 ) CALL ctl_stop( 'STOP', 'trc_ini_c14b : unable to allocate C14b arrays' )
  50. CALL trc_ctl_c14b ! Control consitency
  51. IF(lwp) WRITE(numout,*) ''
  52. IF(lwp) WRITE(numout,*) ' trc_ini_c14b: initialisation of Bomb C14 chemical model'
  53. IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~'
  54. ! Initialization of boundaries conditions
  55. ! ---------------------------------------
  56. qtr_c14(:,:) = 0._wp
  57. ! Initialization of qint in case of no restart
  58. !----------------------------------------------
  59. IF( .NOT. ln_rsttr ) THEN
  60. IF(lwp) THEN
  61. WRITE(numout,*)
  62. WRITE(numout,*) 'Initialization de qint ; No restart : qint equal zero '
  63. ENDIF
  64. trn (:,:,:,jpc14) = 0._wp
  65. qint_c14(:,: ) = 0._wp
  66. ENDIF
  67. ! Read CO2 atmospheric concentrations file...
  68. ! read CO2 data from year jpybeg to year jpyend
  69. !------------------------------------------------
  70. nrec = ( jpyend - jpybeg + 1 ) ! number of year in CO2 Concentrations file
  71. nmaxrec = 2 * nrec
  72. IF(lwp) WRITE(numout,*) 'Read CO2 atmospheric concentrations file '
  73. CALL ctl_opn( inum1, 'splco2.dat', 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
  74. REWIND(inum1)
  75. DO jm = 1, 5 ! Skip over 1st six descriptor lines
  76. READ(inum1,'(1x)')
  77. END DO
  78. ! get CO2 data
  79. DO jm = 1, nmaxrec
  80. READ(inum1, *) zyear, spco2(jm)
  81. IF (lwp) WRITE(numout, '(f7.1,f9.4)') zyear, spco2(jm)
  82. END DO
  83. WRITE(numout,*)
  84. CLOSE(inum1)
  85. IF (lwp) WRITE(numout,*) 'Read C-14 atmospheric concentrations file '
  86. CALL ctl_opn( inum2, 'atmc14.dat', 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
  87. REWIND(inum2)
  88. ! Skip over 1st descriptor line
  89. READ(inum2, '(1x)')
  90. ! READ FILE
  91. DO jm = 1, nrec
  92. READ(inum2,*) zyear, bomb(jm,1), bomb(jm,2), bomb(jm,3)
  93. IF (lwp) WRITE(numout, '(f7.1, 3f9.4)') zyear, bomb(jm,1), bomb(jm,2), bomb(jm,3)
  94. END DO
  95. CLOSE(inum2)
  96. ! Conversion unit : Now atm units are in real C-14 [per mil]
  97. ! C-14(Orr) = C-14(per mil)/10.0
  98. DO jm = 1, nrec
  99. bomb(jm,1) = ( bomb(jm,1 ) + 17.40 ) * 0.1
  100. bomb(jm,2) = ( bomb(jm,2 ) + 10.40 ) * 0.1
  101. bomb(jm,3) = ( bomb(jm,3 ) + 14.65 ) * 0.1
  102. END DO
  103. ! Linear interpolation of the C-14 source fonction
  104. ! in linear latitude band (20N,40N) and (20S,40S)
  105. !------------------------------------------------------
  106. DO jj = 1 , jpj
  107. DO ji = 1 , jpi
  108. IF( gphit(ji,jj) >= yn40 ) THEN
  109. fareaz(ji,jj,1) = 0.
  110. fareaz(ji,jj,2) = 0.
  111. fareaz(ji,jj,3) = 1.
  112. ELSE IF( gphit(ji,jj ) <= ys40) THEN
  113. fareaz(ji,jj,1) = 1.
  114. fareaz(ji,jj,2) = 0.
  115. fareaz(ji,jj,3) = 0.
  116. ELSE IF( gphit(ji,jj) >= yn20 ) THEN
  117. fareaz(ji,jj,1) = 0.
  118. fareaz(ji,jj,2) = 2. * ( 1. - gphit(ji,jj) / yn40 )
  119. fareaz(ji,jj,3) = 2. * gphit(ji,jj) / yn40 - 1.
  120. ELSE IF( gphit(ji,jj) <= ys20 ) THEN
  121. fareaz(ji,jj,1) = 2. * gphit(ji,jj) / ys40 - 1.
  122. fareaz(ji,jj,2) = 2. * ( 1. - gphit(ji,jj) / ys40 )
  123. fareaz(ji,jj,3) = 0.
  124. ELSE
  125. fareaz(ji,jj,1) = 0.
  126. fareaz(ji,jj,2) = 1.
  127. fareaz(ji,jj,3) = 0.
  128. ENDIF
  129. END DO
  130. END DO
  131. !
  132. IF(lwp) WRITE(numout,*) 'Initialization of C14 bomb tracer done'
  133. IF(lwp) WRITE(numout,*) ' '
  134. !
  135. END SUBROUTINE trc_ini_c14b
  136. SUBROUTINE trc_ctl_c14b
  137. !!----------------------------------------------------------------------
  138. !! *** ROUTINE trc_ctl_c14b ***
  139. !!
  140. !! ** Purpose : control the cpp options, namelist and files
  141. !!----------------------------------------------------------------------
  142. IF(lwp) THEN
  143. WRITE(numout,*) ' C14 bomb Model '
  144. WRITE(numout,*) ' '
  145. ENDIF
  146. ! Check number of tracers
  147. ! -----------------------
  148. IF( jp_c14b > 1) CALL ctl_stop( ' Change jp_c14b to be equal 1 in par_c14b.F90' )
  149. ! Check tracer names
  150. ! ------------------
  151. IF( ctrcnm(jpc14) /= 'C14B' ) THEN
  152. ctrcnm(jpc14) = 'C14B'
  153. ctrcln(jpc14) = 'Bomb C14 concentration'
  154. ENDIF
  155. IF(lwp) THEN
  156. CALL ctl_warn( ' we force tracer names' )
  157. WRITE(numout,*) ' tracer nb: ',jpc14,' name = ',ctrcnm(jpc14), ctrcln(jpc14)
  158. WRITE(numout,*) ' '
  159. ENDIF
  160. ! Check tracer units
  161. ! ------------------
  162. IF( ctrcun(jpc14) /= 'ration' ) THEN
  163. ctrcun(jpc14) = 'ration'
  164. IF(lwp) THEN
  165. CALL ctl_warn( ' we force tracer unit' )
  166. WRITE(numout,*) ' tracer ',ctrcnm(jpc14), 'UNIT= ',ctrcun(jpc14)
  167. WRITE(numout,*) ' '
  168. ENDIF
  169. ENDIF
  170. !
  171. END SUBROUTINE trc_ctl_c14b
  172. #else
  173. !!----------------------------------------------------------------------
  174. !! Dummy module No C14 bomb tracer
  175. !!----------------------------------------------------------------------
  176. CONTAINS
  177. SUBROUTINE trc_ini_c14b ! Empty routine
  178. END SUBROUTINE trc_ini_c14b
  179. #endif
  180. !!======================================================================
  181. END MODULE trcini_c14b