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 tags/nemo_v3_2/nemo_v3_2/NEMO/TOP_SRC/C14b – NEMO

source: tags/nemo_v3_2/nemo_v3_2/NEMO/TOP_SRC/C14b/trcini_c14b.F90 @ 1878

Last change on this file since 1878 was 1878, checked in by flavoni, 14 years ago

initial test for nemogcm

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