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.h90 in trunk/NEMO/TOP_SRC/SMS – NEMO

source: trunk/NEMO/TOP_SRC/SMS/trcini.cfc.h90 @ 719

Last change on this file since 719 was 719, checked in by ctlod, 17 years ago

get back to the nemo_v2_3 version for trunk

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 4.4 KB
Line 
1   !!----------------------------------------------------------------------
2   !!                    ***  trcini.cfc.h90 ***
3   !!----------------------------------------------------------------------
4   !! * Module variables
5   INTEGER  ::  &
6      inum                   ! unit number
7   CHARACTER (len=34) :: &
8      clname = 'cfc1112.atm' ! ???
9   REAL(wp) ::  &
10      ylats = -10.,    &     ! 10 degrees south
11      ylatn =  10.           ! 10 degrees north
12
13CONTAINS
14
15   SUBROUTINE trc_ini
16      !!---------------------------------------------------------------------
17      !!                     ***  trcini.cfc.h90  *** 
18      !!
19      !!   Purpose : special initialization for cfc model
20      !!  ---------
21      !!
22      !!
23      !! History :
24      !!   8.2  !  04-06  (JC. Dutay)  original code
25      !!   8.5  !  05-03  (O. Aumont and A. El Moussaoui F90
26      !!   9.0  !  05-10  (C. Ethe) Modularity
27      !!---------------------------------------------------------------------
28      !!  TOP 1.0 , LOCEAN-IPSL (2005)
29   !! $Header$
30   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
31      !!---------------------------------------------------------------------
32      !! Local declarations
33      INTEGER  :: ji, jj, jn, jl, jm
34      REAL(wp) :: zyy,  zyd
35
36   
37      !
38      ! Initialization of boundaries conditions
39      ! ---------------------------------------
40
41      pp_cfc(:,:,:) = 0.0
42      qtr  (:,:,:) = 0.0
43      xphem(:,:  ) = 0.0
44
45 
46      DO jn = 1, jptra
47         DO jm = 1, jphem
48            DO jl = 1, jpyear
49               p_cfc(jl,jm,jn) = 0.0
50            END DO
51         END DO
52      ENDDO
53     
54     
55      ! Initialization of qint in case of  no restart
56      !----------------------------------------------
57      IF( .NOT. lrsttr ) THEN   
58         IF(lwp) THEN
59            WRITE(numout,*)
60            WRITE(numout,*) 'Initialization de qint ; No restart : qint equal zero '
61         ENDIF
62         DO jn = 1, jptra
63            DO jj = 1, jpj
64               DO ji = 1, jpi
65                  qint(ji,jj,jn) = 0.
66               END DO
67            END DO
68         ENDDO
69      ENDIF
70
71
72      !
73      !   READ CFC partial pressure atmospheric value :
74      !     p11(year,nt) = PCFC11  in northern (1) and southern (2) hemisphere
75      !     p12(year,nt) = PCFC12  in northern (1) and southern (2) hemisphere
76      !--------------------------------------------------------------------
77
78      IF(lwp) WRITE(numout,*) 'read of formatted file cfc1112atm'
79     
80      CALL ctlopn( inum, clname, 'OLD', 'FORMATTED', 'SEQUENTIAL',   &
81         &           1, numout, .FALSE., 1 )
82      REWIND(inum)
83     
84
85      ! Skip over 1st six descriptor lines
86      !-----------------------------------
87      DO jm = 1, 6
88         READ(inum,'(1x)')
89      END DO
90   
91   
92      !   Read file
93      ! ---------
94      DO jn = 31, 98
95         READ(inum,*) zyy, p_cfc(jn,1,jp11), p_cfc(jn,1,jp12), &
96            &              p_cfc(jn,2,jp11), p_cfc(jn,2,jp12)
97         WRITE(numout,'(f7.2, 4f8.2)' ) &
98            &         zyy, p_cfc(jn,1,jp11), p_cfc(jn,1,jp12), &
99            &              p_cfc(jn,2,jp11), p_cfc(jn,2,jp12)
100      END DO
101
102      p_cfc(32,1:2,jp11) = 5.e-4
103      p_cfc(33,1:2,jp11) = 8.e-4
104      p_cfc(34,1:2,jp11) = 1.e-6
105      p_cfc(35,1:2,jp11) = 2.e-3
106      p_cfc(36,1:2,jp11) = 4.e-3
107      p_cfc(37,1:2,jp11) = 6.e-3
108      p_cfc(38,1:2,jp11) = 8.e-3
109      p_cfc(39,1:2,jp11) = 1.e-2
110     
111     
112      IF(lwp) THEN
113         WRITE(numout,*)
114         WRITE(numout,*) ' Year   p11HN    p11HS    p12HN    p12HS '
115         DO jn = 30, 100
116            WRITE(numout, '( 1I4, 4F9.2)')   &
117               &         jn, p_cfc(jn,1,jp11), p_cfc(jn,2,jp11), &
118               &             p_cfc(jn,1,jp12), p_cfc(jn,2,jp12)
119         END DO
120      ENDIF
121
122
123      ! Interpolation factor of atmospheric partial pressure
124      ! Linear interpolation between 2 hemispheric function of latitud between ylats and ylatn
125      !---------------------------------------------------------------------------------------
126      zyd = ylatn - ylats     
127      DO jj = 1 , jpj
128         DO ji = 1 , jpi
129            IF( gphit(ji,jj) .GE. ylatn ) THEN
130               xphem(ji,jj) = 1.
131            ELSE IF (gphit(ji,jj) .LE. ylats) THEN
132               xphem(ji,jj) = 0.
133            ELSE
134               xphem(ji,jj) = ( gphit(ji,jj) - ylats) / zyd
135            ENDIF
136         END DO
137      END DO
138
139   END SUBROUTINE trc_ini
Note: See TracBrowser for help on using the repository browser.