New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
trcini_c14b.F90 in trunk/NEMO/TOP_SRC/C14b – NEMO

source: trunk/NEMO/TOP_SRC/C14b/trcini_c14b.F90 @ 1573

Last change on this file since 1573 was 1542, checked in by cetlod, 15 years ago

rename namelist variable lrsttr to ln_rsttr, see ticket:493

File size: 6.5 KB
Line 
1MODULE trcini_c14b
2   !!======================================================================
3   !!                         ***  MODULE trcini_c14b  ***
4   !! TOP :   initialisation of the C14 bomb tracer
5   !!======================================================================
6   !! History : Original ! 2005-10  (Z. Lachkar)
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
20   IMPLICIT NONE
21   PRIVATE
22
23   PUBLIC   trc_ini_c14b   ! called by trcini.F90 module
24
25   INTEGER  ::   &     ! With respect to data file !!
26     jpybeg = 1765 , & !: starting year for C14
27     jpyend = 2002     !: ending year for C14
28
29   INTEGER  ::   &   
30      nrec   ,  & ! number of year in CO2 Concentrations file
31      nmaxrec 
32
33   CHARACTER (len=34) :: &
34     clname_co2 = 'splco2.dat'  , & ! CO2 atmospheric concentrations file
35     clname_c14 = 'atmc14.dat'     ! C-14 atmospheric concentrations file
36
37   INTEGER  ::   inum1, inum2               ! unit number
38
39   REAL(wp) ::     &
40     ys40 = -40. ,    &             ! 40 degrees south
41     ys20 = -20. ,    &             ! 20 degrees south
42     yn20 =  20. ,    &             ! 20 degrees north
43     yn40 =  40.                    ! 40 degrees north
44
45   !!---------------------------------------------------------------------
46   !! NEMO/TOP 2.0 , LOCEAN-IPSL (2007)
47   !! $Id: trcini_cfc.F90 1146 2008-06-25 11:42:56Z rblod $
48   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
49   !!----------------------------------------------------------------------
50
51CONTAINS
52
53   SUBROUTINE trc_ini_c14b
54      !!-------------------------------------------------------------------
55      !!                     ***  trc_ini_c14b  *** 
56      !!
57      !! ** Purpose :   initialization for C14 model
58      !!
59      !!----------------------------------------------------------------------
60      INTEGER  ::   ji, jj, jl, jm
61      REAL(wp) ::   zyear
62      !!----------------------------------------------------------------------
63
64      IF(lwp) WRITE(numout,*)
65      IF(lwp) WRITE(numout,*) ' trc_ini_cfc: initialisation of CFC chemical model'
66      IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~'
67
68
69      ! Initialization of boundaries conditions
70      ! ---------------------------------------
71      qtr_c14(:,:) = 0.e0
72     
73      ! Initialization of qint in case of  no restart
74      !----------------------------------------------
75      IF( .NOT. ln_rsttr ) THEN   
76         IF(lwp) THEN
77            WRITE(numout,*)
78            WRITE(numout,*) 'Initialization de qint ; No restart : qint equal zero '
79         ENDIF
80         trn     (:,:,:,jpc14) = 0.e0
81         qint_c14(:,:        ) = 0.e0
82      ENDIF
83
84
85      ! Read CO2 atmospheric concentrations file...
86      ! read CO2 data from year jpybeg to year jpyend
87      !------------------------------------------------
88
89      nrec    = ( jpyend - jpybeg + 1 )     ! number of year in CO2 Concentrations file
90      nmaxrec = 2 * nrec
91
92      IF(lwp) WRITE(numout,*) 'Read CO2 atmospheric concentrations file '
93 
94      CALL ctlopn( inum1, clname_co2, 'OLD', 'FORMATTED', 'SEQUENTIAL',1, numout, .FALSE., 1 )
95      REWIND(inum1)
96     
97      DO jm = 1, 5        ! Skip over 1st six descriptor lines
98         READ(inum1,'(1x)')
99      END DO
100
101      ! get  CO2 data
102      DO jm = 1, nmaxrec
103         READ(inum1, *)  zyear, spco2(jm)
104         IF (lwp) WRITE(numout, '(f7.1,f9.4)')  zyear, spco2(jm)
105      END DO
106      WRITE(numout,*)
107      CLOSE(inum1)
108
109      IF (lwp) WRITE(numout,*) 'Read C-14 atmospheric concentrations file '
110
111      CALL ctlopn( inum2, clname_c14, 'OLD', 'FORMATTED', 'SEQUENTIAL', 1, numout, .FALSE., 1 )
112      REWIND(inum2)
113
114      ! Skip over 1st descriptor line
115      READ(inum2, '(1x)')
116
117      ! READ FILE
118      DO jm = 1, nrec
119         READ(inum2,*) zyear, bomb(jm,1), bomb(jm,2), bomb(jm,3)
120         IF (lwp) WRITE(numout, '(f7.1, 3f9.4)') zyear, bomb(jm,1), bomb(jm,2), bomb(jm,3)
121      END DO
122      CLOSE(inum2)
123
124      ! Conversion unit : Now atm units are in real C-14 [per mil]
125      ! C-14(Orr) = C-14(per mil)/10.0
126       DO jm = 1, nrec
127         bomb(jm,1) = ( bomb(jm,1 ) + 17.40 ) * 0.1
128         bomb(jm,2) = ( bomb(jm,2 ) + 10.40 ) * 0.1
129         bomb(jm,3) = ( bomb(jm,3 ) + 14.65 ) * 0.1
130       END DO
131
132       ! Linear  interpolation of the C-14 source fonction
133       ! in linear latitude band  (20N,40N) and (20S,40S)
134       !------------------------------------------------------
135       DO jj = 1 , jpj
136          DO ji = 1 , jpi
137            IF( gphit(ji,jj) >= yn40 ) THEN
138                 fareaz(ji,jj,1) = 0.
139                 fareaz(ji,jj,2) = 0.
140                 fareaz(ji,jj,3) = 1.
141            ELSE IF( gphit(ji,jj ) <= ys40) THEN
142                 fareaz(ji,jj,1) = 1.
143                 fareaz(ji,jj,2) = 0.
144                 fareaz(ji,jj,3) = 0.
145            ELSE IF( gphit(ji,jj) >= yn20 ) THEN
146                 fareaz(ji,jj,1) = 0.
147                 fareaz(ji,jj,2) = 2. * ( 1. - gphit(ji,jj) / yn40 )
148                 fareaz(ji,jj,3) = 2. * gphit(ji,jj) / yn40 - 1.
149            ELSE IF( gphit(ji,jj) <= ys20 ) THEN
150                 fareaz(ji,jj,1) = 2. * gphit(ji,jj) / ys40 - 1.
151                 fareaz(ji,jj,2) = 2. * ( 1. - gphit(ji,jj) / ys40 )
152                 fareaz(ji,jj,3) = 0.
153            ELSE
154                 fareaz(ji,jj,1) = 0.
155                 fareaz(ji,jj,2) = 1.
156                 fareaz(ji,jj,3) = 0.
157            ENDIF
158          END DO
159        END DO
160
161      !
162      IF(lwp) WRITE(numout,*) 'Initialization of C14 bomb tracer done'
163      IF(lwp) WRITE(numout,*) ' '
164
165   END SUBROUTINE trc_ini_c14b
166   
167#else
168   !!----------------------------------------------------------------------
169   !!   Dummy module                                    No C14 bomb tracer
170   !!----------------------------------------------------------------------
171CONTAINS
172   SUBROUTINE trc_ini_c14b             ! Empty routine
173   END SUBROUTINE trc_ini_c14b
174#endif
175
176   !!======================================================================
177END MODULE trcini_c14b
Note: See TracBrowser for help on using the repository browser.