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/2015/nemo_v3_6_STABLE/NEMOGCM/NEMO/TOP_SRC/CFC – NEMO

source: branches/2015/nemo_v3_6_STABLE/NEMOGCM/NEMO/TOP_SRC/CFC/trcini_cfc.F90 @ 8353

Last change on this file since 8353 was 8353, checked in by lovato, 7 years ago

3.6 stable: update TOP modules and shared configuraton files for CMIP6 (#1925)

  • Property svn:keywords set to Id
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)
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   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 3.3 , NEMO Consortium (2010)
30   !! $Id$
31   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
32   !!----------------------------------------------------------------------
33CONTAINS
34
35   SUBROUTINE trc_ini_cfc
36      !!----------------------------------------------------------------------
37      !!                     ***  trc_ini_cfc  *** 
38      !!
39      !! ** Purpose :   initialization for cfc model
40      !!
41      !! ** Method  : - Read the namcfc namelist and check the parameter values
42      !!----------------------------------------------------------------------
43      INTEGER  ::  ji, jj, jn, jl, jm, js, io, ierr
44      INTEGER  ::  iskip = 6   ! number of 1st descriptor lines
45      REAL(wp) ::  zyy, zyd
46      CHARACTER(len = 20)  ::  cltra
47      !!----------------------------------------------------------------------
48
49      IF(lwp) WRITE(numout,*)
50      IF(lwp) WRITE(numout,*) ' trc_ini_cfc: initialisation of CFC chemical model'
51      IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~'
52      !
53      IF(lwp) WRITE(numout,*) 'Read annual atmospheric concentrations from formatted file : ' // TRIM(clnamecfc)
54     
55      CALL ctl_opn( inum, clnamecfc, 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
56      REWIND(inum)
57     
58      ! compute the number of year in the file
59      ! file starts in 1931 do jn represent the year in the century
60      jn = 31 
61      DO
62        READ(inum,'(1x)',END=100) 
63        jn = jn + 1
64      END DO
65 100  jpyear = jn - 1 - iskip
66      IF ( lwp) WRITE(numout,*) '   --->  ', jpyear ,' years read'
67      !                                ! Allocate CFC arrays
68
69      ALLOCATE( p_cfc(jpyear,jphem,3), STAT=ierr )
70      IF( ierr > 0 ) THEN
71         CALL ctl_stop( 'trc_ini_cfc: unable to allocate p_cfc array' )   ;   RETURN
72      ENDIF
73      IF( trc_sms_cfc_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'trc_ini_cfc: unable to allocate CFC arrays' )
74
75
76      ! Initialization of boundaries conditions
77      ! ---------------------------------------
78      xphem (:,:)    = 0._wp
79      p_cfc(:,:,:)   = 0._wp
80     
81      ! Initialization of qint in case of  no restart
82      !----------------------------------------------
83      qtr_cfc(:,:,:) = 0._wp
84      IF( .NOT. ln_rsttr ) THEN   
85         IF(lwp) THEN
86            WRITE(numout,*)
87            WRITE(numout,*) 'Initialisation of qint ; No restart : qint equal zero '
88         ENDIF
89         qint_cfc(:,:,:) = 0._wp
90         DO jl = 1, jp_cfc
91            jn = jp_cfc0 + jl - 1
92            trn(:,:,:,jn) = 0._wp
93         END DO
94      ENDIF
95
96      REWIND(inum)
97     
98      DO jm = 1, iskip        ! Skip over 1st six descriptor lines
99         READ(inum,'(1x)')
100      END DO
101      ! file starts in 1931 do jn represent the year in the century.jhh
102      ! Read file till the end
103      jn = 31
104      DO
105        READ(inum,*, IOSTAT=io) zyy, p_cfc(jn,1:2,1), p_cfc(jn,1:2,2), p_cfc(jn,1:2,3)
106        IF( io < 0 ) exit
107        jn = jn + 1
108      END DO
109
110      IF(lwp) THEN        ! Control print
111         WRITE(numout,*)
112         WRITE(numout,*) ' Year   c11NH     c11SH     c12NH     c12SH     SF6NH     SF6SH'
113         DO jn = 30, jpyear
114            WRITE(numout, '( 1I4, 6F10.4)') jn, p_cfc(jn,1:2,1), p_cfc(jn,1:2,2), p_cfc(jn,1:2,3)
115         END DO
116      ENDIF
117
118
119      ! Interpolation factor of atmospheric partial pressure
120      ! Linear interpolation between 2 hemispheric function of latitud between ylats and ylatn
121      !---------------------------------------------------------------------------------------
122      zyd = ylatn - ylats     
123      DO jj = 1 , jpj
124         DO ji = 1 , jpi
125            IF(     gphit(ji,jj) >= ylatn ) THEN   ;   xphem(ji,jj) = 1.e0
126            ELSEIF( gphit(ji,jj) <= ylats ) THEN   ;   xphem(ji,jj) = 0.e0
127            ELSE                                   ;   xphem(ji,jj) = ( gphit(ji,jj) - ylats) / zyd
128            ENDIF
129         END DO
130      END DO
131      !
132      IF(lwp) WRITE(numout,*) 'Initialization of CFC tracers done'
133      IF(lwp) WRITE(numout,*) ' '
134      !
135   END SUBROUTINE trc_ini_cfc
136   
137#else
138   !!----------------------------------------------------------------------
139   !!   Dummy module                                         No CFC tracers
140   !!----------------------------------------------------------------------
141CONTAINS
142   SUBROUTINE trc_ini_cfc             ! Empty routine
143   END SUBROUTINE trc_ini_cfc
144#endif
145
146   !!======================================================================
147END MODULE trcini_cfc
Note: See TracBrowser for help on using the repository browser.