/[MITgcm]/MITgcm/pkg/exf/exf_clim_readparms.F
ViewVC logotype

Annotation of /MITgcm/pkg/exf/exf_clim_readparms.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.12 - (hide annotations) (download)
Mon May 23 19:28:45 2005 UTC (18 years, 11 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint57t_post, checkpoint58l_post, checkpoint57m_post, checkpoint58e_post, checkpoint57v_post, checkpoint57s_post, checkpoint57j_post, checkpoint58b_post, checkpoint58m_post, checkpoint58r_post, checkpoint57y_post, checkpoint58g_post, checkpoint57x_post, checkpoint58n_post, checkpoint58x_post, checkpoint58h_post, checkpoint58w_post, checkpoint58j_post, checkpoint57y_pre, checkpoint57o_post, checkpoint57r_post, checkpoint57k_post, checkpoint57i_post, checkpoint58, checkpoint58f_post, checkpoint57n_post, checkpoint58d_post, checkpoint57w_post, checkpoint57p_post, checkpint57u_post, checkpoint58a_post, checkpoint58i_post, checkpoint57q_post, checkpoint58o_post, checkpoint57z_post, checkpoint58c_post, checkpoint58k_post, checkpoint58u_post, checkpoint58y_post, checkpoint58v_post, checkpoint58s_post, checkpoint58p_post, checkpoint58t_post, checkpoint58q_post, checkpoint57l_post
Changes since 1.11: +21 -7 lines
Replace call to nml_filter by open_copy_data_file
(dont know why it hasnt always been that way in the first place).

1 heimbach 1.12 c $Header: /u/gcmpack/MITgcm/pkg/exf/exf_clim_readparms.F,v 1.11 2005/01/04 04:18:36 dimitri Exp $
2 heimbach 1.1
3 edhill 1.4 #include "EXF_OPTIONS.h"
4 heimbach 1.1
5    
6     subroutine exf_clim_readparms(
7     I mythid
8     & )
9    
10     c ==================================================================
11     c SUBROUTINE exf_clim_readparms
12     c ==================================================================
13     c
14     c o This routine initialises the climatologic forcing
15     c
16     c started: Ralf.Giering@FastOpt.de 25-Mai-20000
17     c
18     c ==================================================================
19     c SUBROUTINE exf_clim_readparms
20     c ==================================================================
21    
22     implicit none
23    
24     c == global variables ==
25    
26     #include "EEPARAMS.h"
27     #include "SIZE.h"
28 dimitri 1.8 #include "PARAMS.h"
29 heimbach 1.1 #include "cal.h"
30     #include "exf.h"
31 dimitri 1.3 #include "exf_param.h"
32 heimbach 1.1 #include "exf_clim_param.h"
33    
34     c == routine arguments ==
35    
36     integer mythid
37    
38     c == local variables ==
39    
40     integer i
41 dimitri 1.5 integer date_array(4), difftime(4)
42 heimbach 1.12 integer iUnit
43    
44     character*(max_len_mbuf) msgbuf
45 heimbach 1.1
46     c == end of interface ==
47    
48     c Surface flux data.
49     namelist /exf_clim_nml/
50 mlosch 1.6 & climtempfreeze,
51 heimbach 1.1 & climtempstartdate1, climtempstartdate2, climtempperiod,
52     & climsaltstartdate1, climsaltstartdate2, climsaltperiod,
53 heimbach 1.2 & climsststartdate1, climsststartdate2, climsstperiod,
54     & climsssstartdate1, climsssstartdate2, climsssperiod,
55     & climtempfile, climsaltfile, climsstfile,
56     & climsssfile, climsstconst, climsssconst,
57 heimbach 1.1 & exf_clim_iprec, exf_clim_yftype
58 dimitri 1.3 #ifdef USE_EXF_INTERPOLATION
59     & ,climsst_lon0, climsst_lon_inc,
60     & climsst_lat0, climsst_lat_inc,
61     & climsst_nlon, climsst_nlat,
62     & climsss_lon0, climsss_lon_inc,
63     & climsss_lat0, climsss_lat_inc,
64     & climsss_nlon, climsss_nlat
65     #endif
66 heimbach 1.1
67     _BEGIN_MASTER(mythid)
68    
69     c Set default values.
70    
71     c Calendar data.
72     climtempstartdate1 = 0
73     climtempstartdate2 = 0
74     climtempperiod = 0
75    
76     climsaltstartdate1 = 0
77     climsaltstartdate2 = 0
78     climsaltperiod = 0
79    
80     climsststartdate1 = 0
81     climsststartdate2 = 0
82     climsstperiod = 0
83    
84     climsssstartdate1 = 0
85     climsssstartdate2 = 0
86     climsssperiod = 0
87    
88     c Data files.
89     climtempfile = ' '
90     climsaltfile = ' '
91     climsstfile = ' '
92     climsssfile = ' '
93    
94 dimitri 1.5 c Start dates.
95 dimitri 1.10 climtempstartdate = 0.
96     climsaltstartdate = 0.
97     climsststartdate = 0.
98     climsssstartdate = 0.
99 heimbach 1.2
100     c Initialise constant values for relax. to constant SST, SSS
101     climsstconst = 0. _d 0
102     climsssconst = 0. _d 0
103 mlosch 1.6
104     c Initialise freezing temperature of sea water
105     climtempfreeze = -1.9 _d 0
106 heimbach 1.1
107     c Initialise file type and field precision
108     exf_clim_iprec = 32
109     exf_clim_yftype = 'RL'
110    
111 dimitri 1.8 #ifdef USE_EXF_INTERPOLATION
112     climsst_lon0 = thetaMin + delX(1) / 2
113     climsss_lon0 = thetaMin + delX(1) / 2
114     climsst_lat0 = phimin + delY(1) / 2
115     climsss_lat0 = phimin + delY(1) / 2
116     climsst_nlon = Nx
117     climsst_nlat = Ny
118     climsss_nlon = Nx
119     climsss_nlat = Ny
120     climsst_lon_inc = delX(1)
121     climsss_lon_inc = delX(1)
122     DO i=1,MAX_LAT_INC
123     IF (i.LT.Ny) THEN
124     climsst_lat_inc(i) = (delY(i) + delY(i)) / 2.
125     climsss_lat_inc(i) = (delY(i) + delY(i)) / 2.
126     ELSE
127     climsst_lat_inc(i) = 0.
128     climsss_lat_inc(i) = 0.
129     ENDIF
130     ENDDO
131     #endif /* USE_EXF_INTERPOLATION */
132    
133 heimbach 1.1 c Check for the availability of the right calendar version.
134     if ( calendarversion .ne. usescalendarversion ) then
135     print*,' exf_Init: You are not using the appropriate'
136     print*,' version of the calendar package.'
137     print*
138     print*,' Please use Calendar version: ',
139     & usescalendarversion
140     stop ' stopped in exf_Init.'
141     endif
142    
143     c Next, read the forcing data file.
144 heimbach 1.12 WRITE(msgBuf,'(A)') 'EXF_CLIM_READPARMS: opening data.exf_clim'
145     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
146     & SQUEEZE_RIGHT , 1)
147    
148     CALL OPEN_COPY_DATA_FILE(
149     I 'data.exf_clim', 'EXF_CLIM_READPARMS',
150     O iUnit,
151     I myThid )
152    
153     READ( iUnit, nml = exf_clim_nml )
154    
155     WRITE(msgBuf,'(A)')
156     & 'EXF_CLIM_READPARMS: finished reading data.exf_clim'
157     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
158     & SQUEEZE_RIGHT , 1)
159    
160     CLOSE( iUnit )
161 heimbach 1.1
162     c Complete the start date specifications for the forcing
163     c fields to get a complete calendar date array.
164    
165     c check for consistency
166    
167     if (.NOT. (exf_clim_iprec .EQ. 32
168     & .OR. exf_clim_iprec .EQ. 64)) then
169     stop 'stopped in exf_clim_readparms: value of iprec not allowed'
170     else if
171     & (.NOT. (exf_clim_yftype .EQ. 'RS'
172     & .OR. exf_clim_yftype .EQ. 'RL'))
173     & then
174     stop 'stopped in exf_clim_readparms: value of yftype not allowed'
175     end if
176    
177 dimitri 1.9 #ifdef USE_EXF_INTERPOLATION
178     if ( climsst_nlat .GT. MAX_LAT_INC )
179     & stop 'stopped in exf_clim_readparms: climsst_nlat > MAX_LAT_INC'
180     if ( climsss_nlat .GT. MAX_LAT_INC )
181     & stop 'stopped in exf_clim_readparms: climsss_nlat > MAX_LAT_INC'
182     #endif
183    
184    
185 heimbach 1.1 #ifdef ALLOW_CLIMTEMP_RELAXATION
186 dimitri 1.11 if ( climtempfile .NE. ' ' .AND. climtempperiod .NE. 0. ) then
187 heimbach 1.7 call cal_FullDate( climtempstartdate1, climtempstartdate2,
188     & date_array, mythid )
189     call cal_TimePassed(modelstartdate,date_array,difftime,mythid)
190     call cal_ToSeconds (difftime, climtempstartdate ,mythid)
191     climtempstartdate=modelstart+climtempstartdate
192     endif
193 heimbach 1.1 #endif
194    
195     #ifdef ALLOW_CLIMSALT_RELAXATION
196 dimitri 1.11 if ( climsaltfile .NE. ' ' .AND. climsaltperiod .NE. 0. ) then
197 heimbach 1.1 call cal_FullDate( climsaltstartdate1, climsaltstartdate2,
198 dimitri 1.5 & date_array, mythid )
199     call cal_TimePassed(modelstartdate,date_array,difftime,mythid)
200     call cal_ToSeconds (difftime, climsaltstartdate ,mythid)
201     climsaltstartdate=modelstart+climsaltstartdate
202 heimbach 1.7 endif
203 heimbach 1.1 #endif
204    
205     #ifdef ALLOW_CLIMSST_RELAXATION
206 dimitri 1.11 if ( climsstfile .NE. ' ' .AND. climsstperiod .NE. 0. ) then
207 heimbach 1.7 call cal_FullDate( climsststartdate1, climsststartdate2,
208     & date_array, mythid )
209     call cal_TimePassed(modelstartdate,date_array,difftime,mythid)
210     call cal_ToSeconds (difftime, climsststartdate ,mythid)
211     climsststartdate=modelstart+climsststartdate
212     endif
213 heimbach 1.1 #endif
214    
215     #ifdef ALLOW_CLIMSSS_RELAXATION
216 dimitri 1.11 if ( climsssfile .NE. ' ' .AND. climsssperiod .NE. 0. ) then
217 heimbach 1.7 call cal_FullDate( climsssstartdate1, climsssstartdate2,
218     & date_array, mythid )
219     call cal_TimePassed(modelstartdate,date_array,difftime,mythid)
220     call cal_ToSeconds (difftime, climsssstartdate ,mythid)
221     climsssstartdate=modelstart+climsssstartdate
222     endif
223 heimbach 1.1 #endif
224    
225     _END_MASTER( mythid )
226    
227     _BARRIER
228    
229     end

  ViewVC Help
Powered by ViewVC 1.1.22