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/NERC/dev_r5518_NOC_MEDUSA_Stable/NEMOGCM/NEMO/TOP_SRC/CFC – NEMO

source: branches/NERC/dev_r5518_NOC_MEDUSA_Stable/NEMOGCM/NEMO/TOP_SRC/CFC/trcini_cfc.F90 @ 8121

Last change on this file since 8121 was 8075, checked in by jpalmier, 7 years ago

JPALM -- update CFCs - add SF6 and update gas transfert param

File size: 6.1 KB
RevLine 
[933]1MODULE trcini_cfc
2   !!======================================================================
3   !!                         ***  MODULE trcini_cfc  ***
4   !! TOP :   initialisation of the CFC tracers
5   !!======================================================================
[3294]6   !! History :   2.0  !  2007-12  (C. Ethe, G. Madec)
[8075]7   !!                  !  2017-04  (A. Yool)  Add SF6
[933]8   !!----------------------------------------------------------------------
9#if defined key_cfc
10   !!----------------------------------------------------------------------
11   !!   'key_cfc'                                               CFC tracers
12   !!----------------------------------------------------------------------
13   !! trc_ini_cfc      : CFC model initialisation
14   !!----------------------------------------------------------------------
15   USE oce_trc         ! Ocean variables
16   USE par_trc         ! TOP parameters
17   USE trc             ! TOP variables
[2715]18   USE trcsms_cfc      ! CFC sms trends
[933]19
20   IMPLICIT NONE
21   PRIVATE
22
23   PUBLIC   trc_ini_cfc   ! called by trcini.F90 module
24
[8075]25   CHARACTER (len=34) ::   clname = 'cfc1112sf6.atm'   ! ???
[2047]26
[933]27   INTEGER  ::   inum                   ! unit number
28   REAL(wp) ::   ylats = -10.           ! 10 degrees south
29   REAL(wp) ::   ylatn =  10.           ! 10 degrees north
30
31   !!----------------------------------------------------------------------
[2528]32   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
[5735]33   !! $Id$
[2528]34   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
[933]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      !!----------------------------------------------------------------------
[3294]46      INTEGER  ::  ji, jj, jn, jl, jm, js, io, ierr
[8075]47      INTEGER  ::  iskip = 7   ! number of 1st descriptor lines
[2715]48      REAL(wp) ::  zyy, zyd
[933]49      !!----------------------------------------------------------------------
50
51      IF(lwp) WRITE(numout,*)
52      IF(lwp) WRITE(numout,*) ' trc_ini_cfc: initialisation of CFC chemical model'
53      IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~'
54
[3294]55
[8075]56      IF(lwp) WRITE(numout,*) 'read of formatted file cfc1112sf6.atm'
[3294]57     
58      CALL ctl_opn( inum, clname, 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
59      REWIND(inum)
60     
61      ! compute the number of year in the file
62      ! file starts in 1931 do jn represent the year in the century
63      jn = 31 
64      DO
65        READ(inum,'(1x)',END=100) 
66        jn = jn + 1
67      END DO
68 100  jpyear = jn - 1 - iskip
69      IF ( lwp) WRITE(numout,*) '    ', jpyear ,' years read'
[2715]70      !                                ! Allocate CFC arrays
[3294]71
72      ALLOCATE( p_cfc(jpyear,jphem,2), STAT=ierr )
73      IF( ierr > 0 ) THEN
74         CALL ctl_stop( 'trc_ini_cfc: unable to allocate p_cfc array' )   ;   RETURN
75      ENDIF
[2715]76      IF( trc_sms_cfc_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'trc_ini_cfc: unable to allocate CFC arrays' )
[1004]77
[2715]78
[933]79      ! Initialization of boundaries conditions
80      ! ---------------------------------------
[2715]81      xphem (:,:)    = 0._wp
82      p_cfc(:,:,:)   = 0._wp
[933]83     
84      ! Initialization of qint in case of  no restart
85      !----------------------------------------------
[2715]86      qtr_cfc(:,:,:) = 0._wp
[1542]87      IF( .NOT. ln_rsttr ) THEN   
[933]88         IF(lwp) THEN
89            WRITE(numout,*)
90            WRITE(numout,*) 'Initialization de qint ; No restart : qint equal zero '
91         ENDIF
[2715]92         qint_cfc(:,:,:) = 0._wp
[1255]93         DO jl = 1, jp_cfc
94            jn = jp_cfc0 + jl - 1
[2715]95            trn(:,:,:,jn) = 0._wp
[933]96         END DO
97      ENDIF
98
99      REWIND(inum)
100     
[3294]101      DO jm = 1, iskip        ! Skip over 1st six descriptor lines
[933]102         READ(inum,'(1x)')
103      END DO
[2047]104      ! file starts in 1931 do jn represent the year in the century.jhh
105      ! Read file till the end
106      jn = 31
[3294]107      DO
[8075]108        READ(inum,*, IOSTAT=io) zyy, p_cfc(jn,1,1), p_cfc(jn,1,2), &
109             & p_cfc(jn,1,3), p_cfc(jn,2,1) &
110             & p_cfc(jn,2,2), p_cfc(jn,2,3)
[3294]111        IF( io < 0 ) exit
112        jn = jn + 1
[933]113      END DO
114
[8075]115      ! AXY (25/04/17): do not adjust
116      ! p_cfc(32,1:2,1) = 5.e-4      ! modify the values of the first years
117      ! p_cfc(33,1:2,1) = 8.e-4
118      ! p_cfc(34,1:2,1) = 1.e-6
119      ! p_cfc(35,1:2,1) = 2.e-3
120      ! p_cfc(36,1:2,1) = 4.e-3
121      ! p_cfc(37,1:2,1) = 6.e-3
122      ! p_cfc(38,1:2,1) = 8.e-3
123      ! p_cfc(39,1:2,1) = 1.e-2
[933]124     
125      IF(lwp) THEN        ! Control print
126         WRITE(numout,*)
[8075]127         WRITE(numout,*) ' Year   p11HN    p11HS    p12HN    p12HS    pSF6N    pSF6S '
[3294]128         DO jn = 30, jpyear
[8075]129            WRITE(numout, '( 1I4, 6F9.2)') jn, p_cfc(jn,1,1), p_cfc(jn,2,1), &
130                 & p_cfc(jn,1,2), p_cfc(jn,2,2) &
131                 & p_cfc(jn,1,3), p_cfc(jn,2,3)
[933]132         END DO
133      ENDIF
134
135      ! Interpolation factor of atmospheric partial pressure
136      ! Linear interpolation between 2 hemispheric function of latitud between ylats and ylatn
137      !---------------------------------------------------------------------------------------
138      zyd = ylatn - ylats     
139      DO jj = 1 , jpj
140         DO ji = 1 , jpi
141            IF(     gphit(ji,jj) >= ylatn ) THEN   ;   xphem(ji,jj) = 1.e0
142            ELSEIF( gphit(ji,jj) <= ylats ) THEN   ;   xphem(ji,jj) = 0.e0
143            ELSE                                   ;   xphem(ji,jj) = ( gphit(ji,jj) - ylats) / zyd
144            ENDIF
145         END DO
146      END DO
147      !
[1004]148      IF(lwp) WRITE(numout,*) 'Initialization of CFC tracers done'
149      IF(lwp) WRITE(numout,*) ' '
[2715]150      !
[933]151   END SUBROUTINE trc_ini_cfc
152   
153#else
154   !!----------------------------------------------------------------------
155   !!   Dummy module                                         No CFC tracers
156   !!----------------------------------------------------------------------
157CONTAINS
158   SUBROUTINE trc_ini_cfc             ! Empty routine
159   END SUBROUTINE trc_ini_cfc
160#endif
161
162   !!======================================================================
163END MODULE trcini_cfc
Note: See TracBrowser for help on using the repository browser.