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/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/CFC – NEMO

source: branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/CFC/trcini_cfc.F90 @ 7041

Last change on this file since 7041 was 7041, checked in by cetlod, 8 years ago

ROBUST5_CNRS : implementation of part I of new TOP interface - 1st step -, see ticket #1782

  • Property svn:keywords set to Id
File size: 6.3 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)
7   !!----------------------------------------------------------------------
8   !!----------------------------------------------------------------------
9   !! trc_ini_cfc      : CFC model initialisation
10   !!----------------------------------------------------------------------
11   USE oce_trc         ! Ocean variables
12   USE par_trc         ! TOP parameters
13   USE trc             ! TOP variables
14   USE trcsms_cfc      ! CFC sms trends
15
16   IMPLICIT NONE
17   PRIVATE
18
19   PUBLIC   trc_ini_cfc   ! called by trcini.F90 module
20
21   CHARACTER (len=34) ::   clname = 'cfc1112.atm'   ! ???
22
23   INTEGER  ::   inum                   ! unit number
24   REAL(wp) ::   ylats = -10.           ! 10 degrees south
25   REAL(wp) ::   ylatn =  10.           ! 10 degrees north
26
27   !!----------------------------------------------------------------------
28   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
29   !! $Id$
30   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
31   !!----------------------------------------------------------------------
32CONTAINS
33
34   SUBROUTINE trc_ini_cfc
35      !!----------------------------------------------------------------------
36      !!                     ***  trc_ini_cfc  *** 
37      !!
38      !! ** Purpose :   initialization for cfc model
39      !!
40      !! ** Method  : - Read the namcfc namelist and check the parameter values
41      !!----------------------------------------------------------------------
42      INTEGER  ::  ji, jj, jn, jl, jm, js, io, ierr
43      INTEGER  ::  iskip = 6   ! number of 1st descriptor lines
44      REAL(wp) ::  zyy, zyd
45      CHARACTER(len = 20)  ::  cltra
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     
53      ! assign an index in trc arrays for each CFC prognostic variables
54      jp_cfc = 1 
55      IF( ln_cfc11 .AND. ln_cfc12 )  jp_cfc = 2
56
57      ! assign an index in trc arrays for each prognostic variables
58      DO jn = 1, jptra
59        cltra = ctrcnm(jn) 
60        IF( cltra == 'CFC11'  .OR. cltra == 'cfc11' )   jpc11 = jn 
61        IF( cltra == 'CFC12'  .OR. cltra == 'cfc12' )   jpc12 = jn 
62      ENDDO
63   
64      IF( jp_cfc == 1 ) THEN
65        IF( ln_cfc11 )  jp_cfc0  = jpc11
66        IF( ln_cfc12 )  jp_cfc0  = jpc12
67      ELSE
68        jp_cfc0 = MIN( jpc11, jpc12 ) 
69      ENDIF
70      jp_cfc1 = jp_cfc0 + jp_cfc - 1
71
72      IF( lwp ) THEN
73        WRITE(numout,*) ''
74        WRITE(numout,*) ' First index of CFC tracer in the passive tracer array   jp_cfc0 = ', jp_cfc0
75        WRITE(numout,*) ' Last  index of CFC tracer in the passive tracer array   jp_cfc1 = ', jp_cfc1
76        WRITE(numout,*) 
77      ENDIF
78
79      IF(lwp) WRITE(numout,*) 'read of formatted file cfc1112atm'
80     
81      CALL ctl_opn( inum, clname, 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
82      REWIND(inum)
83     
84      ! compute the number of year in the file
85      ! file starts in 1931 do jn represent the year in the century
86      jn = 31 
87      DO
88        READ(inum,'(1x)',END=100) 
89        jn = jn + 1
90      END DO
91 100  jpyear = jn - 1 - iskip
92      IF ( lwp) WRITE(numout,*) '    ', jpyear ,' years read'
93      !                                ! Allocate CFC arrays
94
95      ALLOCATE( p_cfc(jpyear,jphem,2), STAT=ierr )
96      IF( ierr > 0 ) THEN
97         CALL ctl_stop( 'trc_ini_cfc: unable to allocate p_cfc array' )   ;   RETURN
98      ENDIF
99      IF( trc_sms_cfc_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'trc_ini_cfc: unable to allocate CFC arrays' )
100
101
102      ! Initialization of boundaries conditions
103      ! ---------------------------------------
104      xphem (:,:)    = 0._wp
105      p_cfc(:,:,:)   = 0._wp
106     
107      ! Initialization of qint in case of  no restart
108      !----------------------------------------------
109      qtr_cfc(:,:,:) = 0._wp
110      IF( .NOT. ln_rsttr ) THEN   
111         IF(lwp) THEN
112            WRITE(numout,*)
113            WRITE(numout,*) 'Initialization de qint ; No restart : qint equal zero '
114         ENDIF
115         qint_cfc(:,:,:) = 0._wp
116         DO jl = 1, jp_cfc
117            jn = jp_cfc0 + jl - 1
118            trn(:,:,:,jn) = 0._wp
119         END DO
120      ENDIF
121
122      REWIND(inum)
123     
124      DO jm = 1, iskip        ! Skip over 1st six descriptor lines
125         READ(inum,'(1x)')
126      END DO
127      ! file starts in 1931 do jn represent the year in the century.jhh
128      ! Read file till the end
129      jn = 31
130      DO
131        READ(inum,*, IOSTAT=io) zyy, p_cfc(jn,1,1), p_cfc(jn,1,2), p_cfc(jn,2,1), p_cfc(jn,2,2)
132        IF( io < 0 ) exit
133        jn = jn + 1
134      END DO
135
136      p_cfc(32,1:2,1) = 5.e-4      ! modify the values of the first years
137      p_cfc(33,1:2,1) = 8.e-4
138      p_cfc(34,1:2,1) = 1.e-6
139      p_cfc(35,1:2,1) = 2.e-3
140      p_cfc(36,1:2,1) = 4.e-3
141      p_cfc(37,1:2,1) = 6.e-3
142      p_cfc(38,1:2,1) = 8.e-3
143      p_cfc(39,1:2,1) = 1.e-2
144     
145      IF(lwp) THEN        ! Control print
146         WRITE(numout,*)
147         WRITE(numout,*) ' Year   p11HN    p11HS    p12HN    p12HS '
148         DO jn = 30, jpyear
149            WRITE(numout, '( 1I4, 4F9.2)') jn, p_cfc(jn,1,1), p_cfc(jn,2,1), p_cfc(jn,1,2), p_cfc(jn,2,2)
150         END DO
151      ENDIF
152
153
154      ! Interpolation factor of atmospheric partial pressure
155      ! Linear interpolation between 2 hemispheric function of latitud between ylats and ylatn
156      !---------------------------------------------------------------------------------------
157      zyd = ylatn - ylats     
158      DO jj = 1 , jpj
159         DO ji = 1 , jpi
160            IF(     gphit(ji,jj) >= ylatn ) THEN   ;   xphem(ji,jj) = 1.e0
161            ELSEIF( gphit(ji,jj) <= ylats ) THEN   ;   xphem(ji,jj) = 0.e0
162            ELSE                                   ;   xphem(ji,jj) = ( gphit(ji,jj) - ylats) / zyd
163            ENDIF
164         END DO
165      END DO
166      !
167      IF(lwp) WRITE(numout,*) 'Initialization of CFC tracers done'
168      IF(lwp) WRITE(numout,*) ' '
169      !
170   END SUBROUTINE trc_ini_cfc
171   
172   !!======================================================================
173END MODULE trcini_cfc
Note: See TracBrowser for help on using the repository browser.