/[MITgcm]/MITgcm/pkg/ecco/ecco_readparms.F
ViewVC logotype

Diff of /MITgcm/pkg/ecco/ecco_readparms.F

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

revision 1.2 by heimbach, Fri Jul 13 13:42:16 2001 UTC revision 1.31 by heimbach, Thu Sep 20 18:23:34 2007 UTC
# Line 1  Line 1 
1  C $Header$  C $Header$
2    
3  #include "CPP_OPTIONS.h"  #include "COST_CPPOPTIONS.h"
4    
5          subroutine ecco_readparms( mythid )
       subroutine ecco_readparms(  
      I                      mythid  
      &                    )  
6    
7  c     ==================================================================  c     ==================================================================
8  c     SUBROUTINE ecco_readparms  c     SUBROUTINE ecco_readparms
9  c     ==================================================================  c     ==================================================================
10  c  c
11  c     o Initialize the ECCO release of the MITgcmUV.  c     o This routine initialises the package cost.
12  c  c     started: Ralf Giering 18-Jan-2001
 c     started: Christian Eckert eckert@mit.edu 29-Feb-1999  
 c  
 c              - Introduced to create a package for the MITgcmUV.  
 c  
 c     changed: Christian Eckert eckert@mit.edu  
13  c  c
14  c     ==================================================================  c     ==================================================================
15  c     SUBROUTINE ecco_readparms  c     SUBROUTINE ecco_readparms
# Line 27  c     ================================== Line 19  c     ==================================
19    
20  c     == global variables ==  c     == global variables ==
21    
 #include "SIZE.h"  
22  #include "EEPARAMS.h"  #include "EEPARAMS.h"
23    #include "SIZE.h"
24    #include "GRID.h"
25  #include "PARAMS.h"  #include "PARAMS.h"
26  #include "ecco.h"  
27    #include "ecco_cost.h"
28    
29  c     == routine arguments ==  c     == routine arguments ==
30    
31        integer mythid        integer mythid
32    
33  c     == local variables ==  c     == local variables ==
34    C     msgBuf      - Informational/error meesage buffer
35        integer errio  C     iUnit       - Work variable for IO unit number
36        integer il        CHARACTER*(MAX_LEN_MBUF) msgBuf
37          INTEGER k, iUnit, num_file, num_var
       character*(max_len_prec) record  
   
 c     == external ==  
   
       integer  ilnblnk  
       external ilnblnk  
38    
39  c     == end of interface ==  c     == end of interface ==
40    
41  c--   ECCO parameters.  c--   Read the namelist input.
42        namelist /ECCO_PARMS/        namelist /ecco_cost_nml/
43       &                      expId       &                   data_errfile,
44             &                   tbarfile, sbarfile, psbarfile,
45         &                   ubarfile, vbarfile, wbarfile,
46         &                   tauxbarfile, tauybarfile,
47         &                   hfluxbarfile, sfluxbarfile,
48         &                   costTranspDataFile,
49         &                   using_topex,
50         &                   topexstartdate1, topexstartdate2,
51         &                   topexperiod, topexfile, topexmeanfile,
52         &                   topexintercept, topexslope,
53         &                   using_ers,
54         &                   ersstartdate1, ersstartdate2,
55         &                   ersperiod, ersfile,
56         &                   ersintercept, ersslope,
57         &                   using_gfo,
58         &                   gfostartdate1, gfostartdate2,
59         &                   gfoperiod, gfofile,
60         &                   gfointercept, gfoslope,
61         &                   scatstartdate1, scatstartdate2,
62         &                   scatperiod, scatxdatfile, scatydatfile,
63         &                   scatx_errfile, scaty_errfile,
64         &                   ssh_errfile,
65         &                   tp_errfile, ers_errfile, gfo_errfile,
66         &                   tmistartdate1, tmistartdate2, tmidatfile,
67         &                   sststartdate1, sststartdate2, sstdatfile,
68         &                   sssstartdate1, sssstartdate2, sssdatfile,
69         &                   tdatfile, sdatfile,
70         &                   ctdtfile, ctdsfile,
71         &                   ctdtclimfile, ctdsclimfile,
72         &                   xbtfile,
73         &                   argotstartdate1, argotstartdate2, argotfile,
74         &                   argosstartdate1, argosstartdate2, argosfile,
75         &                   udriftfile, vdriftfile,
76         &                   udrifterrfile, vdrifterrfile,
77         &                   curmtrufile,curmtrvfile,
78         &                   salterrfile, temperrfile, velerrfile,
79         &                   salt0errfile, temp0errfile, vel0errfile,
80         &                   hflux_errfile, sflux_errfile,
81         &                   tauu_errfile, tauv_errfile,
82         &                   atemp_errfile, aqh_errfile,
83         &                   precip_errfile, swflux_errfile, swdown_errfile,
84         &                   lwflux_errfile, lwdown_errfile, evap_errfile,
85         &                   snowprecip_errfile, apressure_errfile,
86         &                   uwind_errfile, vwind_errfile,
87         &                   geoid_errfile, geoid_covariancefile,
88         &                   bottomdrag_errfile,edtau_errfile,
89         &                   kapgm_errfile,diffkr_errfile,
90         &                   gencost_datafile, gencost_errfile,
91         &                   mult_hflux, mult_sflux, mult_tauu, mult_tauv,
92         &                   mult_hfluxmm, mult_sfluxmm,
93         &                   mult_atemp, mult_aqh,
94         &                   mult_precip, mult_swflux, mult_swdown,
95         &                   mult_lwflux, mult_lwdown, mult_evap,
96         &                   mult_snowprecip, mult_apressure,
97         &                   mult_uwind, mult_vwind,
98         &                   mult_hmean, mult_h,
99         &                   mult_tp, mult_ers, mult_gfo,
100         &                   mult_temp, mult_salt,
101         &                   mult_tmi, mult_sst, mult_sss,
102         &                   mult_ctdt, mult_ctds,
103         &                   mult_ctdtclim, mult_ctdsclim,
104         &                   mult_xbt, mult_drift,
105         &                   mult_argot, mult_argos,
106         &                   mult_scatx, mult_scaty,
107         &                   mult_sdrift, mult_tdrift, mult_wdrift,
108         &                   mult_temp0, mult_salt0,
109         &                   mult_obcsn, mult_obcss,
110         &                   mult_obcsw, mult_obcse, mult_obcsvol,
111         &                   mult_curmtr, mult_ageos,
112         &                   mult_kapgm, mult_diffkr,
113         &                   mult_edtau, mult_bottomdrag,
114         &                   mult_gencost,
115         &                   mult_smooth_ic, mult_smooth_bc,
116         &                   whflux0, wsflux0, wtau0,
117         &                   wbottomdrag0,
118         &                   watemp0, waqh0,
119         &                   wprecip0, wswflux0, wswdown0, wwind0,
120         &                   wsnowprecip0, wlwflux0, wlwdown0, wevap0,
121         &                   wapressure0, wdiffkr0, wkapgm0, wedtau0,
122         &                   wmean_hflux, wmean_sflux, wmean_tau,
123         &                   wmean_atemp, wmean_aqh, wmean_precip,
124         &                   wmean_swflux, wmean_swdown, wmean_wind,
125         &                   wmean_lwflux, wmean_lwdown, wmean_evap,
126         &                   wmean_snowprecip, wmean_apressure,
127         &                   cost_iprec, cost_yftype
128    
129        _BEGIN_MASTER( myThid )        _BEGIN_MASTER( myThid )
         open( unit=scrunit1, status='scratch' )  
130    
131  c--     Next, read the ECCO data file.  c--     Set default values.
132          open( unit   = modeldataunit,          data_errfile          =    ' '
133       &        file   = 'data.ecco',          tbarfile              =    'tbar'
134       &        status = 'old',          sbarfile              =    'sbar'
135       &        iostat = errio)          psbarfile             =    'psbar'
136            ubarfile              =    'ubar'
137          if ( errio .lt. 0 ) then          vbarfile              =    'vbar'
138            stop ' stopped in ecco_readparms.'          wbarfile              =    'wbar'
139          endif          tauxbarfile           =    'tauxbar'
140            tauybarfile           =    'tauybar'
141          do while ( .true. )          hfluxbarfile          =    'hfluxbar'
142            read(modeldataunit, fmt='(a)', end=1001) record          sfluxbarfile          =    'sfluxbar'
143            il = max(ilnblnk(record),1)          costTranspDataFile    =    ' '
144            if ( record(1:1) .ne. commentcharacter )          using_topex           = .false.
145       &        write(unit=scrunit1, fmt='(a)') record(:il)          topexstartdate1       =      0
146            topexstartdate2       =      0
147            topexperiod           =      0. _d 0
148            topexintercept        =      0. _d 0
149            topexslope            =      0. _d 0
150            topexfile             =    ' '
151            topexmeanfile         =    ' '
152            using_ers             = .false.
153            ersstartdate1         =      0
154            ersstartdate2         =      0
155            ersperiod             =      0. _d 0
156            ersintercept          =      0. _d 0
157            ersslope              =      0. _d 0
158            ersfile               =    ' '
159            using_gfo             = .false.
160            gfostartdate1         =      0
161            gfostartdate2         =      0
162            gfoperiod             =      0. _d 0
163            gfointercept          =      0. _d 0
164            gfoslope              =      0. _d 0
165            gfofile               =    ' '
166            scatstartdate1        =      0
167            scatstartdate2        =      0
168            scatperiod            =      0. _d 0
169            scatxdatfile          =    ' '
170            scatydatfile          =    ' '
171            ssh_errfile           =    ' '
172            tp_errfile            =    ' '
173            ers_errfile           =    ' '
174            gfo_errfile           =    ' '
175            scatx_errfile         =    ' '
176            scaty_errfile         =    ' '
177            tmistartdate1         =      0
178            tmistartdate2         =      0
179            tmidatfile            =    ' '
180            sststartdate1         =      0
181            sststartdate2         =      0
182            sstdatfile            =    ' '
183            sssstartdate1         =      0
184            sssstartdate2         =      0
185            sssdatfile            =    ' '
186            tdatfile              =    ' '
187            sdatfile              =    ' '
188            ctdtfile              =    ' '
189            ctdsfile              =    ' '
190            ctdtclimfile          =    ' '
191            ctdsclimfile          =    ' '
192            curmtrufile           =    ' '
193            curmtrvfile           =    ' '
194            xbtfile               =    ' '
195            argotstartdate1       =      0
196            argotstartdate2       =      0
197            argotfile             =    ' '
198            argosstartdate1       =      0
199            argosstartdate2       =      0
200            argosfile             =    ' '
201            udriftfile            =    ' '
202            vdriftfile            =    ' '
203            udrifterrfile         =    ' '
204            vdrifterrfile         =    ' '
205            salterrfile           =    ' '
206            temperrfile           =    ' '
207            velerrfile            =    ' '
208            salt0errfile          =    ' '
209            temp0errfile          =    ' '
210            vel0errfile           =    ' '
211            hflux_errfile         =    ' '
212            sflux_errfile         =    ' '
213            tauu_errfile          =    ' '
214            tauv_errfile          =    ' '
215            atemp_errfile         =    ' '
216            aqh_errfile           =    ' '
217            precip_errfile        =    ' '
218            swflux_errfile        =    ' '
219            swdown_errfile        =    ' '
220            lwflux_errfile        =    ' '
221            lwdown_errfile        =    ' '
222            evap_errfile          =    ' '
223            snowprecip_errfile    =    ' '
224            apressure_errfile     =    ' '
225            uwind_errfile         =    ' '
226            vwind_errfile         =    ' '
227            geoid_errfile         =    ' '
228            geoid_covariancefile  =    ' '
229            bottomdrag_errfile    =    ' '
230            edtau_errfile         =    ' '
231            kapgm_errfile         =    ' '
232            diffkr_errfile        =    ' '
233            do k=1,NGENCOST
234            gencost_datafile(k)    =    ' '
235            gencost_errfile(k)    =    ' '
236          enddo          enddo
237   1001   continue          mult_hflux            =      0. _d 0
238          close( modeldataunit )          mult_sflux            =      0. _d 0
239            mult_hfluxmm          =      0. _d 0
240          rewind( scrunit1 )          mult_sfluxmm          =      0. _d 0
241          read  ( unit = scrunit1, nml = ecco_parms)          mult_tauu             =      0. _d 0
242          close ( scrunit1 )          mult_tauv             =      0. _d 0
243            mult_atemp            =      0. _d 0
244  c-------------------------------- ECCO --------------------------------          mult_aqh              =      0. _d 0
245            mult_precip           =      0. _d 0
246  #ifdef INCLUDE_ECCO_PACKAGE          mult_swflux           =      0. _d 0
247  C--   Initialise the ECCO State Estimation package.          mult_swdown           =      0. _d 0
248            mult_lwflux           =      0. _d 0
249  #ifdef ALLOW_CALENDAR          mult_lwdown           =      0. _d 0
250  C--   Initialise the calendar package.          mult_evap             =      0. _d 0
251  #ifdef ALLOW_CAL_NENDITER          mult_snowprecip       =      0. _d 0
252        call cal_init(          mult_apressure        =      0. _d 0
253       I               startTime,          mult_uwind            =      0. _d 0
254       I               endTime,          mult_vwind            =      0. _d 0
255       I               deltaTclock,          mult_hmean            =      0. _d 0
256       I               nIter0,          mult_h                =      1. _d 0
257       I               nEndIter,          mult_tp               =      0. _d 0
258       I               nTimeSteps,          mult_ers              =      0. _d 0
259       I               myThid          mult_gfo              =      0. _d 0
260       &             )          mult_temp             =      0. _d 0
261  #else          mult_salt             =      0. _d 0
262        call cal_init(          mult_temp0            =      0. _d 0
263       I               startTime,          mult_salt0            =      0. _d 0
264       I               endTime,          mult_tmi              =      0. _d 0
265       I               deltaTclock,          mult_sst              =      0. _d 0
266       I               nIter0,          mult_sss              =      0. _d 0
267       I               nTimeSteps,          mult_ctdt             =      0. _d 0
268       I               myThid          mult_ctds             =      0. _d 0
269       &             )          mult_ctdtclim         =      0. _d 0
270  #endif          mult_ctdsclim         =      0. _d 0
271        _BARRIER          mult_xbt              =      0. _d 0
272  #endif          mult_argot            =      0. _d 0
273            mult_argos            =      0. _d 0
274  C--   Custom routine to set forcing fields.          mult_drift            =      0. _d 0
275  #ifdef INCLUDE_EXTERNAL_FORCING_PACKAGE          mult_tdrift           =      0. _d 0
276        call exf_readparms  ( mythid )          mult_sdrift           =      0. _d 0
277        call exf_init( mythid )          mult_wdrift           =      0. _d 0
278  #endif /* INCLUDE_EXTERNAL_FORCING_PACKAGE */          mult_scatx            =      0. _d 0
279            mult_scaty            =      0. _d 0
280  #ifdef ALLOW_ECCO_OPTIMIZATION          mult_obcsn            =      0. _d 0
281  c--   Initialise the optimization-related parts of the ECCO State          mult_obcss            =      0. _d 0
282  c--   Estimation package.          mult_obcsw            =      0. _d 0
283        call optim_init( myThid )          mult_obcse            =      0. _d 0
284        _BARRIER          mult_obcsvol          =      0. _d 0
285  #else          mult_ageos            =      0. _d 0
286  c--   Optimization not enabled.          mult_curmtr           =      0. _d 0
287  #endif          mult_kapgm            =      0. _d 0
288            mult_diffkr           =      0. _d 0
289  #ifndef ALLOW_ECCO_FORWARD_RUN          mult_edtau            =      0. _d 0
290  C--   Initialise the cost function.          mult_bottomdrag       =      0. _d 0
291        call cost_readparms( mythid )          do k=1,NGENCOST
292        call cost_init( myThid )          mult_gencost(k)       =      0. _d 0
293        _BARRIER          enddo
294            mult_smooth_ic        =      0. _d 0
295  C--   Initialise the control vector.          mult_smooth_bc        =      0. _d 0
296        call ctrl_init( myThid )          watemp0               =      0. _d 0
297        _BARRIER          waqh0                 =      0. _d 0
298  #else          wprecip0              =      0. _d 0
299  c     not needed for forward run only          wswflux0              =      0. _d 0
300  #endif          wswdown0              =      0. _d 0
301            wlwflux0              =      0. _d 0
302  #ifdef ALLOW_ECCO_DIAGNOSTICS_RUN          wlwdown0              =      0. _d 0
303  c--   Initialise the ECCO diagnostics package.          wevap0                =      0. _d 0
304        call diagnos_init( myThid )          wsnowprecip0          =      0. _d 0
305        _BARRIER          wapressure0           =      0. _d 0
306  #else          wwind0                =      0. _d 0
307  c--   Diagnostics not enabled.          wdiffkr0              =      1. _d 0
308            wkapgm0               =      1. _d 0
309            wedtau0               =      1. _d 0
310            whflux0               =      0. _d 0
311            wsflux0               =      0. _d 0
312            wtau0                 =      0. _d 0
313            wbottomdrag0          =      1. _d 0
314            wmean_atemp           =      0. _d 0
315            wmean_aqh             =      0. _d 0
316            wmean_precip          =      0. _d 0
317            wmean_swflux          =      0. _d 0
318            wmean_swdown          =      0. _d 0
319            wmean_lwflux          =      0. _d 0
320            wmean_lwdown          =      0. _d 0
321            wmean_evap            =      0. _d 0
322            wmean_snowprecip      =      0. _d 0
323            wmean_apressure       =      0. _d 0
324            wmean_wind            =      0. _d 0
325            wmean_hflux           =      0. _d 0
326            wmean_sflux           =      0. _d 0
327            wmean_tau             =      0. _d 0
328    
329    c--     Next, read the cost data file.
330            WRITE(msgBuf,'(A)') 'ECCO_READPARMS: opening data.ecco'
331            CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
332         &                    SQUEEZE_RIGHT , 1)
333    
334            CALL OPEN_COPY_DATA_FILE(
335         I                          'data.ecco', 'ECCO_READPARMS',
336         O                          iUnit,
337         I                          myThid )
338    
339            READ(  iUnit, nml = ecco_cost_nml )
340    
341            WRITE(msgBuf,'(A)') 'ECCO_READPARMS: finished reading data.ecco'
342            CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
343         &                  SQUEEZE_RIGHT , 1)
344    
345            CLOSE( iUnit )
346    
347    #ifdef ALLOW_CAL
348    c--     Get the complete dates of the ...
349    c--     ... SST data.
350            WRITE(msgBuf,'(A)') 'ECCO_READPARMS: start assigning cost dates'
351            CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
352         &                  SQUEEZE_RIGHT , 1)
353    
354            call cal_FullDate( sststartdate1,   sststartdate2,
355         &                     sststartdate,    mythid )
356    c--     ... TMI data.
357            call cal_FullDate( tmistartdate1,   tmistartdate2,
358         &                     tmistartdate,    mythid )
359    c--     ... SSS data.
360            call cal_FullDate( sssstartdate1,   sssstartdate2,
361         &                     sssstartdate,    mythid )    
362    c--     ... T/P data.
363            call cal_FullDate( topexstartdate1, topexstartdate2,
364         &                     topexstartdate,  mythid )
365    c--     ... ERS data.
366            call cal_FullDate( ersstartdate1,   ersstartdate2,
367         &                     ersstartdate,    mythid )
368    c--     ... GFO data.
369            call cal_FullDate( gfostartdate1,   gfostartdate2,
370         &                     gfostartdate,    mythid )
371    c--     ... SCAT data.
372            call cal_FullDate( scatstartdate1,   scatstartdate2,
373         &                     scatxstartdate,    mythid )
374            call cal_FullDate( scatstartdate1,   scatstartdate2,  
375         &                     scatystartdate,    mythid )
376    
377            WRITE(msgBuf,'(A)') 'ECCO_READPARMS: end assigning cost dates'
378            CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
379         &                  SQUEEZE_RIGHT , 1)
380  #endif  #endif
381    
 #endif /* INCLUDE_ECCO_PACKAGE */  
   
 c-------------------------------- ECCO --------------------------------  
   
 c--     Summarize the setup of the ECCO release.  
 c        call ecco_summary( mythid )  
382        _END_MASTER( mythid )        _END_MASTER( mythid )
383    
 c--   Everyone else must wait for the parameters to be loaded and  
 c--   the setup to be completed.  
384        _BARRIER        _BARRIER
385    
386        end        end

Legend:
Removed from v.1.2  
changed lines
  Added in v.1.31

  ViewVC Help
Powered by ViewVC 1.1.22