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 trunk/NEMO/TOP_SRC/CFC – NEMO

source: trunk/NEMO/TOP_SRC/CFC/trcini_cfc.F90 @ 933

Last change on this file since 933 was 933, checked in by cetlod, 16 years ago

adding modules the CFC model, see ticket 140

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