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.cfc.h90 in trunk/NEMO/TOP_SRC/SMS – NEMO

source: trunk/NEMO/TOP_SRC/SMS/trcini.cfc.h90 @ 338

Last change on this file since 338 was 338, checked in by opalod, 18 years ago

nemo_v1_update_026 : CE + RB + CT : add CFC tracer

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 4.2 KB
Line 
1   !!----------------------------------------------------------------------
2   !!                    ***  trcini.cfc.h90 ***
3   !!----------------------------------------------------------------------
4   !! * Module variables
5   INTEGER  ::  &
6      inum = 16     ! unit number
7   CHARACTER (len=34) :: &
8      clname = 'cfc1112.atm' ! ???
9   REAL(wp) ::  &
10      ylats = -10.,    &     ! 10 degrees south
11      ylatn =  10.           ! 10 degrees north
12
13CONTAINS
14
15   SUBROUTINE trc_ini
16      !!---------------------------------------------------------------------
17      !!                     ***  trcini.cfc.h90  *** 
18      !!
19      !!   Purpose : special initialization for cfc model
20      !!  ---------
21      !!
22      !!
23      !! History :
24      !!   8.2  !  04-06  (JC. Dutay)  original code
25      !!   8.5  !  05-03  (O. Aumont and A. El Moussaoui F90
26      !!   9.0  !  05-10  (C. Ethe) Modularity
27      !!---------------------------------------------------------------------
28      !!  TOP 1.0,  LOCEAN-IPSL (2005)
29      !!----------------------------------------------------------------
30      !! Local declarations
31      INTEGER  :: ji, jj, jn, jl, jm
32      REAL(wp) :: zyy,  zyd
33
34   
35      !
36      ! Initialization of boundaries conditions
37      ! ---------------------------------------
38
39      pp_cfc(:,:,:) = 0.0
40      qtr  (:,:,:) = 0.0
41      xphem(:,:  ) = 0.0
42
43 
44      DO jn = 1, jptra
45         DO jm = 1, jphem
46            DO jl = 1, jpyear
47               p_cfc(jl,jm,jn) = 0.0
48            END DO
49         END DO
50      ENDDO
51     
52     
53      ! Initialization of qint in case of  no restart
54      !----------------------------------------------
55      IF( .NOT. lrsttr ) THEN   
56         IF(lwp) THEN
57            WRITE(numout,*)
58            WRITE(numout,*) 'Initialization de qint ; No restart : qint equal zero '
59         ENDIF
60         DO jn = 1, jptra
61            DO jj = 1, jpj
62               DO ji = 1, jpi
63                  qint(ji,jj,jn) = 0.
64               END DO
65            END DO
66         ENDDO
67      ENDIF
68
69
70      !
71      !   READ CFC partial pressure atmospheric value :
72      !     p11(year,nt) = PCFC11  in northern (1) and southern (2) hemisphere
73      !     p12(year,nt) = PCFC12  in northern (1) and southern (2) hemisphere
74      !--------------------------------------------------------------------
75
76      IF(lwp) WRITE(numout,*) 'read of formatted file cfc1112atm'
77     
78      OPEN( UNIT = inum, FORM = 'FORMATTED',FILE = clname, STATUS = 'OLD')
79      REWIND(inum)
80     
81
82      ! Skip over 1st six descriptor lines
83      !-----------------------------------
84      DO jm = 1, 6
85         READ(inum,'(1x)')
86      END DO
87   
88   
89      !   Read file
90      ! ---------
91      DO jn = 31, 98
92         READ(inum,*) zyy, p_cfc(jn,1,jp11), p_cfc(jn,1,jp12), &
93            &              p_cfc(jn,2,jp11), p_cfc(jn,2,jp12)
94         WRITE(numout,'(f7.2, 4f8.2)' ) &
95            &         zyy, p_cfc(jn,1,jp11), p_cfc(jn,1,jp12), &
96            &              p_cfc(jn,2,jp11), p_cfc(jn,2,jp12)
97      END DO
98
99      p_cfc(32,1:2,jp11) = 5.e-4
100      p_cfc(33,1:2,jp11) = 8.e-4
101      p_cfc(34,1:2,jp11) = 1.e-6
102      p_cfc(35,1:2,jp11) = 2.e-3
103      p_cfc(36,1:2,jp11) = 4.e-3
104      p_cfc(37,1:2,jp11) = 6.e-3
105      p_cfc(38,1:2,jp11) = 8.e-3
106      p_cfc(39,1:2,jp11) = 1.e-2
107     
108     
109      IF(lwp) THEN
110         WRITE(numout,*)
111         WRITE(numout,*) ' Year   p11HN    p11HS    p12HN    p12HS '
112         DO jn = 30, 100
113            WRITE(numout, '( 1I4, 4F9.2)')   &
114               &         jn, p_cfc(jn,1,jp11), p_cfc(jn,2,jp11), &
115               &             p_cfc(jn,1,jp12), p_cfc(jn,2,jp12)
116         END DO
117      ENDIF
118
119
120      ! Interpolation factor of atmospheric partial pressure
121      ! Linear interpolation between 2 hemispheric function of latitud between ylats and ylatn
122      !---------------------------------------------------------------------------------------
123      zyd = ylatn - ylats     
124      DO jj = 1 , jpj
125         DO ji = 1 , jpi
126            IF( gphit(ji,jj) .GE. ylatn ) THEN
127               xphem(ji,jj) = 1.
128            ELSE IF (gphit(ji,jj) .LE. ylats) THEN
129               xphem(ji,jj) = 0.
130            ELSE
131               xphem(ji,jj) = ( gphit(ji,jj) - ylats) / zyd
132            ENDIF
133         END DO
134      END DO
135
136   END SUBROUTINE trc_ini
Note: See TracBrowser for help on using the repository browser.