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.F90 in branches/dev_001_GM/NEMO/TOP_SRC/CFC – NEMO

source: branches/dev_001_GM/NEMO/TOP_SRC/CFC/trcini_cfc.F90 @ 766

Last change on this file since 766 was 766, checked in by gm, 16 years ago

dev_001_GM - create 1 trcini_ module by trc model (CFC, LOBSTER, PISCES..) - never compiled

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 5.6 KB
Line 
1MODULE 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) from trcini.cfc.h90
7   !!----------------------------------------------------------------------
8#if defined key_cfc
9   !!----------------------------------------------------------------------
10   !!   'key_cfc'                                               CFC tracers
11   !!----------------------------------------------------------------------
12   !! trc_ini_cfc      : CFC model initialisation
13   !!----------------------------------------------------------------------
14   USE par_trc         ! TOP parameters
15   USE trccfc          ! CFC sms trends
16
17   IMPLICIT NONE
18   PRIVATE
19
20   PUBLIC   trc_ini_cfc   ! called by trcini.F90 module
21
22   CHARACTER (len=34) ::   clname = 'cfc1112.atm'   ! ???
23
24   INTEGER  ::   inum                   ! unit number
25   REAL(wp) ::   ylats = -10.           ! 10 degrees south
26   REAL(wp) ::   ylatn =  10.           ! 10 degrees north
27
28   !!----------------------------------------------------------------------
29   !! NEMO/TOP 2.0 , LOCEAN-IPSL (2007)
30   !! $Id:$
31   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
32   !!----------------------------------------------------------------------
33
34CONTAINS
35
36   SUBROUTINE trc_ini_cfc
37      !!----------------------------------------------------------------------
38      !!                     ***  trc_ini_cfc  *** 
39      !!
40      !! ** Purpose :   initialization for cfc model
41      !!
42      !! ** Method  : - Read the namcfc namelist and check the parameter values
43      !!----------------------------------------------------------------------
44      INTEGER  ::   ji, jj, jn, jl, jm
45      REAL(wp) ::   zyy  ,  zyd
46      !!----------------------------------------------------------------------
47
48      IF(lwp) WRITE(numout,*)
49      IF(lwp) WRITE(numout,*) ' trc_ini_cfc: initialisation of CFC chemical model'
50      IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~'
51
52      ! Initialization of boundaries conditions
53      ! ---------------------------------------
54      pp_cfc(:,:,:) = 0.e0
55      qtr   (:,:,:) = 0.e0
56      xphem (:,:)   = 0.e0
57      DO jn = 1, jptra
58         DO jm = 1, jphem
59            DO jl = 1, jpyear
60               p_cfc(jl,jm,jn) = 0.0
61            END DO
62         END DO
63      END DO
64     
65     
66      ! Initialization of qint in case of  no restart
67      !----------------------------------------------
68      IF( .NOT. lrsttr ) THEN   
69         IF(lwp) THEN
70            WRITE(numout,*)
71            WRITE(numout,*) 'Initialization de qint ; No restart : qint equal zero '
72         ENDIF
73         DO jn = 1, jptra
74            qint(:,:,jn) = 0.e0
75         END DO
76      ENDIF
77
78
79      !   READ CFC partial pressure atmospheric value :
80      !     p11(year,nt) = PCFC11  in northern (1) and southern (2) hemisphere
81      !     p12(year,nt) = PCFC12  in northern (1) and southern (2) hemisphere
82      !--------------------------------------------------------------------
83
84      IF(lwp) WRITE(numout,*) 'read of formatted file cfc1112atm'
85     
86      CALL ctlopn( inum, clname, 'OLD', 'FORMATTED', 'SEQUENTIAL',   &
87         &           1, numout, .FALSE., 1 )
88      REWIND(inum)
89     
90
91      ! Skip over 1st six descriptor lines
92      !-----------------------------------
93      DO jm = 1, 6
94         READ(inum,'(1x)')
95      END DO
96   
97   
98      !   Read file
99      ! ---------
100      DO jn = 31, 98
101         READ(inum,*) zyy, p_cfc(jn,1,jp11), p_cfc(jn,1,jp12), &
102            &              p_cfc(jn,2,jp11), p_cfc(jn,2,jp12)
103         WRITE(numout,'(f7.2, 4f8.2)' ) &
104            &         zyy, p_cfc(jn,1,jp11), p_cfc(jn,1,jp12), &
105            &              p_cfc(jn,2,jp11), p_cfc(jn,2,jp12)
106      END DO
107
108      p_cfc(32,1:2,jp11) = 5.e-4
109      p_cfc(33,1:2,jp11) = 8.e-4
110      p_cfc(34,1:2,jp11) = 1.e-6
111      p_cfc(35,1:2,jp11) = 2.e-3
112      p_cfc(36,1:2,jp11) = 4.e-3
113      p_cfc(37,1:2,jp11) = 6.e-3
114      p_cfc(38,1:2,jp11) = 8.e-3
115      p_cfc(39,1:2,jp11) = 1.e-2
116     
117     
118      IF(lwp) THEN
119         WRITE(numout,*)
120         WRITE(numout,*) ' Year   p11HN    p11HS    p12HN    p12HS '
121         DO jn = 30, 100
122            WRITE(numout, '( 1I4, 4F9.2)')   &
123               &         jn, p_cfc(jn,1,jp11), p_cfc(jn,2,jp11), &
124               &             p_cfc(jn,1,jp12), p_cfc(jn,2,jp12)
125         END DO
126      ENDIF
127
128
129      ! Interpolation factor of atmospheric partial pressure
130      ! Linear interpolation between 2 hemispheric function of latitud between ylats and ylatn
131      !---------------------------------------------------------------------------------------
132      zyd = ylatn - ylats     
133      DO jj = 1 , jpj
134         DO ji = 1 , jpi
135            IF(     gphit(ji,jj) >= ylatn ) THEN   ;   xphem(ji,jj) = 1.e0
136            ELSEIF( gphit(ji,jj) <= ylats ) THEN   ;   xphem(ji,jj) = 0.e0
137            ELSE                                   ;   xphem(ji,jj) = ( gphit(ji,jj) - ylats) / zyd
138            ENDIF
139         END DO
140      END DO
141      !
142   END SUBROUTINE trc_ini_cfc
143   
144#else
145   !!----------------------------------------------------------------------
146   !!   Dummy module                                         No CFC tracers
147   !!----------------------------------------------------------------------
148CONTAINS
149   SUBROUTINE trc_ini_cfc             ! Empty routine
150   END SUBROUTINE trc_ini_cfc
151#endif
152
153   !!======================================================================
154END MODULE trcini_cfc
Note: See TracBrowser for help on using the repository browser.