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 NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/CFC – NEMO

source: NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/CFC/trcini_cfc.F90 @ 10975

Last change on this file since 10975 was 10975, checked in by acc, 5 years ago

2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps : Finish converting all TOP routines and knock-on effects of these conversions. Fully SETTE tested (SETTE tests 1-6 and 9). This completes the first stage conversion of TRA and TOP but need to revisit and pass ts and tr arrays through the argument lists where appropriate.

  • 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   !!----------------------------------------------------------------------
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 trcnam_cfc      ! CFC SMS namelist
15   USE trcsms_cfc      ! CFC sms trends
16
17   IMPLICIT NONE
18   PRIVATE
19
20   PUBLIC   trc_ini_cfc   ! called by trcini.F90 module
21
22   INTEGER  ::   inum                   ! unit number
23   REAL(wp) ::   ylats = -10.           ! 10 degrees south
24   REAL(wp) ::   ylatn =  10.           ! 10 degrees north
25
26   !!----------------------------------------------------------------------
27   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
28   !! $Id$
29   !! Software governed by the CeCILL license (see ./LICENSE)
30   !!----------------------------------------------------------------------
31CONTAINS
32
33   SUBROUTINE trc_ini_cfc( Kmm )
34      !!----------------------------------------------------------------------
35      !!                     ***  trc_ini_cfc  *** 
36      !!
37      !! ** Purpose :   initialization for cfc model
38      !!
39      !! ** Method  : - Read the namcfc namelist and check the parameter values
40      !!----------------------------------------------------------------------
41      INTEGER, INTENT(in)  ::  Kmm  ! time level indices
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      CALL trc_nam_cfc
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      IF(lwp) WRITE(numout,*) 'Read annual atmospheric concentratioins from formatted file : ' // TRIM(clname)
55     
56      CALL ctl_opn( inum, clname, 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
57      REWIND(inum)
58     
59      ! compute the number of year in the file
60      ! file starts in 1931 do jn represent the year in the century
61      jn = 31 
62      DO
63        READ(inum,'(1x)',END=100) 
64        jn = jn + 1
65      END DO
66 100  jpyear = jn - 1 - iskip
67      IF ( lwp) WRITE(numout,*) '   --->  ', jpyear ,' years read'
68      !                                ! Allocate CFC arrays
69
70      ALLOCATE( p_cfc(jpyear,jphem,3), STAT=ierr )
71      IF( ierr > 0 ) THEN
72         CALL ctl_stop( 'trc_ini_cfc: unable to allocate p_cfc array' )   ;   RETURN
73      ENDIF
74      IF( trc_sms_cfc_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'trc_ini_cfc: unable to allocate CFC arrays' )
75
76
77      ! Initialization of boundaries conditions
78      ! ---------------------------------------
79      xphem (:,:)    = 0._wp
80      p_cfc(:,:,:)   = 0._wp
81     
82      ! Initialization of qint in case of  no restart
83      !----------------------------------------------
84      qtr_cfc(:,:,:) = 0._wp
85      IF( .NOT. ln_rsttr ) THEN   
86         IF(lwp) THEN
87            WRITE(numout,*)
88            WRITE(numout,*) 'Initialisation of qint ; No restart : qint equal zero '
89         ENDIF
90         qint_cfc(:,:,:) = 0._wp
91         DO jl = 1, jp_cfc
92            jn = jp_cfc0 + jl - 1
93            tr(:,:,:,jn,Kmm) = 0._wp
94         END DO
95      ENDIF
96
97      REWIND(inum)
98     
99      DO jm = 1, iskip        ! Skip over 1st six descriptor lines
100         READ(inum,'(1x)')
101      END DO
102      ! file starts in 1931 do jn represent the year in the century.jhh
103      ! Read file till the end
104      jn = 31
105      DO
106        READ(inum,*, IOSTAT=io) zyy, p_cfc(jn,1:2,1), p_cfc(jn,1:2,2), p_cfc(jn,1:2,3)
107        IF( io < 0 ) exit
108        jn = jn + 1
109      END DO
110
111      !p_cfc(32,1:2,1) = 5.e-4      ! modify the values of the first years
112      !p_cfc(33,1:2,1) = 8.e-4
113      !p_cfc(34,1:2,1) = 1.e-6
114      !p_cfc(35,1:2,1) = 2.e-3
115      !p_cfc(36,1:2,1) = 4.e-3
116      !p_cfc(37,1:2,1) = 6.e-3
117      !p_cfc(38,1:2,1) = 8.e-3
118      !p_cfc(39,1:2,1) = 1.e-2
119      IF(lwp) THEN        ! Control print
120         WRITE(numout,*)
121         WRITE(numout,*) ' Year   c11NH     c11SH     c12NH     c12SH     SF6NH     SF6SH'
122         DO jn = 30, jpyear
123            WRITE(numout, '( 1I4, 6F10.4)') jn, p_cfc(jn,1:2,1), p_cfc(jn,1:2,2), p_cfc(jn,1:2,3)
124         END DO
125      ENDIF
126
127
128      ! Interpolation factor of atmospheric partial pressure
129      ! Linear interpolation between 2 hemispheric function of latitud between ylats and ylatn
130      !---------------------------------------------------------------------------------------
131      zyd = ylatn - ylats     
132      DO jj = 1 , jpj
133         DO ji = 1 , jpi
134            IF(     gphit(ji,jj) >= ylatn ) THEN   ;   xphem(ji,jj) = 1.e0
135            ELSEIF( gphit(ji,jj) <= ylats ) THEN   ;   xphem(ji,jj) = 0.e0
136            ELSE                                   ;   xphem(ji,jj) = ( gphit(ji,jj) - ylats) / zyd
137            ENDIF
138         END DO
139      END DO
140      !
141      IF(lwp) WRITE(numout,*) 'Initialization of CFC tracers done'
142      IF(lwp) WRITE(numout,*) ' '
143      !
144   END SUBROUTINE trc_ini_cfc
145
146   !!======================================================================
147END MODULE trcini_cfc
Note: See TracBrowser for help on using the repository browser.