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

source: branches/DEV_r2006_merge_TRA_TRC/NEMO/TOP_SRC/CFC/trcini_cfc.F90 @ 2038

Last change on this file since 2038 was 2038, checked in by cetlod, 14 years ago

Apply the merge to passive tracers, see ticket:693

  • Property svn:keywords set to Id
File size: 5.9 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   USE in_out_manager  ! I/O manager
19
20   IMPLICIT NONE
21   PRIVATE
22
23   PUBLIC   trc_ini_cfc   ! called by trcini.F90 module
24
25   INTEGER  ::   inum                   ! unit number
26   REAL(wp) ::   ylats = -10.           ! 10 degrees south
27   REAL(wp) ::   ylatn =  10.           ! 10 degrees north
28
29   !!----------------------------------------------------------------------
30   !! NEMO/TOP 2.0 , LOCEAN-IPSL (2007)
31   !! $Id$
32   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
33   !!----------------------------------------------------------------------
34
35CONTAINS
36
37   SUBROUTINE trc_ini_cfc
38      !!----------------------------------------------------------------------
39      !!                     ***  trc_ini_cfc  *** 
40      !!
41      !! ** Purpose :   initialization for cfc model
42      !!
43      !! ** Method  : - Read the namcfc namelist and check the parameter values
44      !!----------------------------------------------------------------------
45      INTEGER  ::   ji, jj, jn, jl, jm, js
46      REAL(wp) ::   zyy  ,  zyd
47      !!----------------------------------------------------------------------
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
55      ! Initialization of boundaries conditions
56      ! ---------------------------------------
57      xphem (:,:)    = 0.e0
58      DO jl = 1, jp_cfc
59         jn = jp_cfc0 + jl - 1
60         DO jm = 1, jphem
61            DO js = 1, jpyear
62               p_cfc(js,jm,jn) = 0.0
63            END DO
64         END DO
65      END DO
66     
67     
68      ! Initialization of qint in case of  no restart
69      !----------------------------------------------
70      qtr_cfc(:,:,:) = 0.e0
71      IF( .NOT. ln_rsttr ) THEN   
72         IF(lwp) THEN
73            WRITE(numout,*)
74            WRITE(numout,*) 'Initialization de qint ; No restart : qint equal zero '
75         ENDIF
76         DO jl = 1, jp_cfc
77            jn = jp_cfc0 + jl - 1
78            trn     (:,:,:,jn) = 0.e0
79            qint_cfc(:,:  ,jn) = 0.e0
80         END DO
81      ENDIF
82
83
84      !   READ CFC partial pressure atmospheric value :
85      !     p11(year,nt) = PCFC11  in northern (1) and southern (2) hemisphere
86      !     p12(year,nt) = PCFC12  in northern (1) and southern (2) hemisphere
87      !--------------------------------------------------------------------
88
89      IF(lwp) WRITE(numout,*) 'read of formatted file cfc1112atm'
90     
91      CALL ctl_opn( inum, 'cfc1112.atm', 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
92      REWIND(inum)
93     
94      DO jm = 1, 6        ! Skip over 1st six descriptor lines
95         READ(inum,'(1x)')
96      END DO
97   
98      ! file starts in 1931 do jn represent the year in the century.jhh
99      ! Read file till the end
100      jn = 31
101      DO WHILE ( 1 /= 2 )
102         READ(inum,*,END=100) zyy, p_cfc(jn,1,1), p_cfc(jn,1,2), p_cfc(jn,2,1), p_cfc(jn,2,2)
103         IF ( lwp) THEN
104           WRITE(numout,'(f7.2, 4f8.2)' ) &
105            &         zyy, p_cfc(jn,1,1), p_cfc(jn,1,2), p_cfc(jn,2,1), p_cfc(jn,2,2)
106         ENDIF
107         jn = jn + 1
108      END DO
109 100  npyear = jn - 1
110      IF ( lwp) WRITE(numout,*) '    ', npyear ,' years read'
111
112      p_cfc(32,1:2,1) = 5.e-4      ! modify the values of the first years
113      p_cfc(33,1:2,1) = 8.e-4
114      p_cfc(34,1:2,1) = 1.e-6
115      p_cfc(35,1:2,1) = 2.e-3
116      p_cfc(36,1:2,1) = 4.e-3
117      p_cfc(37,1:2,1) = 6.e-3
118      p_cfc(38,1:2,1) = 8.e-3
119      p_cfc(39,1:2,1) = 1.e-2
120     
121      IF(lwp) THEN        ! Control print
122         WRITE(numout,*)
123         WRITE(numout,*) ' Year   p11HN    p11HS    p12HN    p12HS '
124         DO jn = 30, 100
125            WRITE(numout, '( 1I4, 4F9.2)')   &
126               &         jn, p_cfc(jn,1,1), p_cfc(jn,2,1), p_cfc(jn,1,2), p_cfc(jn,2,2)
127         END DO
128      ENDIF
129
130
131      ! Interpolation factor of atmospheric partial pressure
132      ! Linear interpolation between 2 hemispheric function of latitud between ylats and ylatn
133      !---------------------------------------------------------------------------------------
134      zyd = ylatn - ylats     
135      DO jj = 1 , jpj
136         DO ji = 1 , jpi
137            IF(     gphit(ji,jj) >= ylatn ) THEN   ;   xphem(ji,jj) = 1.e0
138            ELSEIF( gphit(ji,jj) <= ylats ) THEN   ;   xphem(ji,jj) = 0.e0
139            ELSE                                   ;   xphem(ji,jj) = ( gphit(ji,jj) - ylats) / zyd
140            ENDIF
141         END DO
142      END DO
143      !
144
145      IF(lwp) WRITE(numout,*) 'Initialization of CFC tracers done'
146      IF(lwp) WRITE(numout,*) ' '
147
148   END SUBROUTINE trc_ini_cfc
149 
150#else
151   !!----------------------------------------------------------------------
152   !!   Dummy module                                         No CFC tracers
153   !!----------------------------------------------------------------------
154CONTAINS
155   SUBROUTINE trc_ini_cfc             ! Empty routine
156   END SUBROUTINE trc_ini_cfc
157#endif
158
159   !!======================================================================
160END MODULE trcini_cfc
Note: See TracBrowser for help on using the repository browser.