1 | MODULE trcini_cfc |
---|
2 | !!====================================================================== |
---|
3 | !! *** MODULE trcini_cfc *** |
---|
4 | !! TOP : initialisation of the CFC tracers |
---|
5 | !!====================================================================== |
---|
6 | !! History : 2.0 ! 2007-12 (C. Ethe, G. Madec) |
---|
7 | !! ! 2017-04 (A. Yool) Add SF6 |
---|
8 | !!---------------------------------------------------------------------- |
---|
9 | #if defined key_cfc |
---|
10 | !!---------------------------------------------------------------------- |
---|
11 | !! 'key_cfc' CFC tracers |
---|
12 | !!---------------------------------------------------------------------- |
---|
13 | !! trc_ini_cfc : CFC model initialisation |
---|
14 | !!---------------------------------------------------------------------- |
---|
15 | USE oce_trc ! Ocean variables |
---|
16 | USE par_trc ! TOP parameters |
---|
17 | USE trc ! TOP variables |
---|
18 | USE trcsms_cfc ! CFC sms trends |
---|
19 | |
---|
20 | IMPLICIT NONE |
---|
21 | PRIVATE |
---|
22 | |
---|
23 | PUBLIC trc_ini_cfc ! called by trcini.F90 module |
---|
24 | |
---|
25 | CHARACTER (len=34) :: clname = 'cfc1112sf6.atm' ! ??? |
---|
26 | |
---|
27 | INTEGER :: inum ! unit number |
---|
28 | REAL(wp) :: ylats = -10. ! 10 degrees south |
---|
29 | REAL(wp) :: ylatn = 10. ! 10 degrees north |
---|
30 | |
---|
31 | !!---------------------------------------------------------------------- |
---|
32 | !! NEMO/TOP 3.3 , NEMO Consortium (2010) |
---|
33 | !! $Id$ |
---|
34 | !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) |
---|
35 | !!---------------------------------------------------------------------- |
---|
36 | CONTAINS |
---|
37 | |
---|
38 | SUBROUTINE trc_ini_cfc |
---|
39 | !!---------------------------------------------------------------------- |
---|
40 | !! *** trc_ini_cfc *** |
---|
41 | !! |
---|
42 | !! ** Purpose : initialization for cfc model |
---|
43 | !! |
---|
44 | !! ** Method : - Read the namcfc namelist and check the parameter values |
---|
45 | !!---------------------------------------------------------------------- |
---|
46 | INTEGER :: ji, jj, jn, jl, jm, js, io, iostatus, ierr |
---|
47 | INTEGER :: iskip = 7 ! number of 1st descriptor lines |
---|
48 | REAL(wp) :: zyy, zyd |
---|
49 | !!---------------------------------------------------------------------- |
---|
50 | |
---|
51 | IF(lwp) WRITE(numout,*) |
---|
52 | IF(lwp) WRITE(numout,*) ' trc_ini_cfc: initialisation of CFC chemical model' |
---|
53 | IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~' |
---|
54 | |
---|
55 | |
---|
56 | IF(lwp) WRITE(numout,*) 'read of formatted file cfc1112sf6.atm' |
---|
57 | |
---|
58 | CALL ctl_opn( inum, clname, 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. ) |
---|
59 | |
---|
60 | ! compute the number of year in the file |
---|
61 | ! file starts in 1931 do jn represent the year in the century |
---|
62 | iostatus = 0 |
---|
63 | jn = 31 |
---|
64 | DO WHILE ( iostatus == 0 ) |
---|
65 | READ(inum,'(1x)', IOSTAT=iostatus, END=100) |
---|
66 | jn = jn + 1 |
---|
67 | ENDDO |
---|
68 | IF( iostatus .NE. 0 ) THEN |
---|
69 | !! Error while reading CFC input file |
---|
70 | CALL ctl_stop('trc_ini_cfc: & |
---|
71 | & Error on the 1st reading of cfc1112sf6.atm') |
---|
72 | RETURN |
---|
73 | ENDIF |
---|
74 | 100 jpyear = jn - 1 - iskip |
---|
75 | IF ( lwp) WRITE(numout,*) ' ', jpyear ,' years read' |
---|
76 | ! ! Allocate CFC arrays |
---|
77 | |
---|
78 | ALLOCATE( p_cfc(jpyear,jphem,3), STAT=ierr ) |
---|
79 | IF( ierr > 0 ) THEN |
---|
80 | CALL ctl_stop( 'trc_ini_cfc: unable to allocate p_cfc array' ) |
---|
81 | RETURN |
---|
82 | ENDIF |
---|
83 | IF( trc_sms_cfc_alloc() /= 0 ) CALL ctl_stop( 'STOP', 'trc_ini_cfc: unable to allocate CFC arrays' ) |
---|
84 | |
---|
85 | |
---|
86 | ! Initialization of boundaries conditions |
---|
87 | ! --------------------------------------- |
---|
88 | xphem (:,:) = 0._wp |
---|
89 | p_cfc(:,:,:) = 0._wp |
---|
90 | |
---|
91 | ! Initialization of qint in case of no restart |
---|
92 | !---------------------------------------------- |
---|
93 | qtr_cfc(:,:,:) = 0._wp |
---|
94 | IF( .NOT. ln_rsttr ) THEN |
---|
95 | IF(lwp) THEN |
---|
96 | WRITE(numout,*) |
---|
97 | WRITE(numout,*) 'Initialization de qint ; No restart : qint equal zero ' |
---|
98 | ENDIF |
---|
99 | qint_cfc(:,:,:) = 0._wp |
---|
100 | trn(:,:,:,jp_cfc0:jp_cfc1) = 0._wp |
---|
101 | ENDIF |
---|
102 | |
---|
103 | REWIND(inum) |
---|
104 | |
---|
105 | DO jm = 1, iskip ! Skip over 1st six descriptor lines |
---|
106 | READ(inum,'(1x)') |
---|
107 | END DO |
---|
108 | ! file starts in 1931 do jn represent the year in the century.jhh |
---|
109 | ! Read file till the end |
---|
110 | DO jn = 31, jpyear |
---|
111 | !!READ(inum, '(F6.1,6F7.2)', IOSTAT=io) zyy, p_cfc(jn,1,1), p_cfc(jn,1,2), & |
---|
112 | READ(inum,*, IOSTAT=io) zyy, p_cfc(jn,1,1), p_cfc(jn,1,2), & |
---|
113 | & p_cfc(jn,1,3), p_cfc(jn,2,1), & |
---|
114 | & p_cfc(jn,2,2), p_cfc(jn,2,3) |
---|
115 | IF( io .NE.0 ) THEN |
---|
116 | !! Error while reading CFC input file |
---|
117 | CALL ctl_stop('trc_ini_cfc: & |
---|
118 | & Error on the 2nd reading of cfc1112sf6.atm') |
---|
119 | RETURN |
---|
120 | ENDIF |
---|
121 | END DO |
---|
122 | |
---|
123 | ! AXY (25/04/17): do not adjust |
---|
124 | ! p_cfc(32,1:2,1) = 5.e-4 ! modify the values of the first years |
---|
125 | ! p_cfc(33,1:2,1) = 8.e-4 |
---|
126 | ! p_cfc(34,1:2,1) = 1.e-6 |
---|
127 | ! p_cfc(35,1:2,1) = 2.e-3 |
---|
128 | ! p_cfc(36,1:2,1) = 4.e-3 |
---|
129 | ! p_cfc(37,1:2,1) = 6.e-3 |
---|
130 | ! p_cfc(38,1:2,1) = 8.e-3 |
---|
131 | ! p_cfc(39,1:2,1) = 1.e-2 |
---|
132 | |
---|
133 | IF(lwp) THEN ! Control print |
---|
134 | WRITE(numout,*) |
---|
135 | WRITE(numout,*) ' Year p11HN p11HS p12HN p12HS pSF6N pSF6S ' |
---|
136 | DO jn = 30, jpyear |
---|
137 | WRITE(numout, '( 1I4, 6F9.2)') jn, p_cfc(jn,1,1), p_cfc(jn,2,1), & |
---|
138 | & p_cfc(jn,1,2), p_cfc(jn,2,2), & |
---|
139 | & p_cfc(jn,1,3), p_cfc(jn,2,3) |
---|
140 | END DO |
---|
141 | ENDIF |
---|
142 | |
---|
143 | ! Interpolation factor of atmospheric partial pressure |
---|
144 | ! Linear interpolation between 2 hemispheric function of latitud between ylats and ylatn |
---|
145 | !--------------------------------------------------------------------------------------- |
---|
146 | zyd = ylatn - ylats |
---|
147 | DO jj = 1 , jpj |
---|
148 | DO ji = 1 , jpi |
---|
149 | IF( gphit(ji,jj) >= ylatn ) THEN ; xphem(ji,jj) = 1.e0 |
---|
150 | ELSEIF( gphit(ji,jj) <= ylats ) THEN ; xphem(ji,jj) = 0.e0 |
---|
151 | ELSE ; xphem(ji,jj) = ( gphit(ji,jj) - ylats) / zyd |
---|
152 | ENDIF |
---|
153 | END DO |
---|
154 | END DO |
---|
155 | ! |
---|
156 | IF(lwp) WRITE(numout,*) 'Initialization of CFC tracers done' |
---|
157 | IF(lwp) WRITE(numout,*) ' ' |
---|
158 | ! |
---|
159 | END SUBROUTINE trc_ini_cfc |
---|
160 | |
---|
161 | #else |
---|
162 | !!---------------------------------------------------------------------- |
---|
163 | !! Dummy module No CFC tracers |
---|
164 | !!---------------------------------------------------------------------- |
---|
165 | CONTAINS |
---|
166 | SUBROUTINE trc_ini_cfc ! Empty routine |
---|
167 | END SUBROUTINE trc_ini_cfc |
---|
168 | #endif |
---|
169 | |
---|
170 | !!====================================================================== |
---|
171 | END MODULE trcini_cfc |
---|