/[MITgcm]/MITgcm/pkg/offline/offline_readparms.F
ViewVC logotype

Annotation of /MITgcm/pkg/offline/offline_readparms.F

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


Revision 1.9 - (hide annotations) (download)
Sun Apr 4 14:16:32 2010 UTC (14 years, 1 month ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64i, checkpoint64h, checkpoint64j, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint64, checkpoint63, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x
Changes since 1.8: +10 -9 lines
move namelists after local variable declarations (some compilers, like open64,
 ignore declaration of var. which appears BEFORE in a namelist)

1 jmc 1.9 C $Header: /u/gcmpack/MITgcm/pkg/offline/offline_readparms.F,v 1.8 2010/04/03 22:34:26 jmc Exp $
2 jmc 1.5 C $Name: $
3 stephd 1.1
4     #include "OFFLINE_OPTIONS.h"
5    
6     SUBROUTINE OFFLINE_READPARMS( myThid )
7 jmc 1.8 C *==========================================================*
8     C | SUBROUTINE OFFLINE_READPARMS
9     C | o Routine to initialize OFFLINE variables and constants.
10     C *==========================================================*
11     C | Initialize OFFLINE parameters, read in data.off
12     C *==========================================================*
13 stephd 1.1 IMPLICIT NONE
14    
15     C === Global variables ===
16     #include "SIZE.h"
17     #include "EEPARAMS.h"
18     #include "PARAMS.h"
19     #ifdef ALLOW_OFFLINE
20     #include "OFFLINE.h"
21     #endif
22    
23     C === Routine arguments ===
24     INTEGER myThid
25    
26 jmc 1.8 #ifdef ALLOW_OFFLINE
27 jmc 1.9 C === Local variables ===
28     C msgBuf :: Informational/error message buffer
29     C iUnit :: Work variable for IO unit number
30     CHARACTER*(MAX_LEN_MBUF) msgBuf
31     INTEGER iUnit
32     C Retired main data.offline file parameters
33     CHARACTER*(MAX_LEN_FNAM) KPP_ghatFile
34    
35 stephd 1.1 C-- Bulk Formula parameter
36     NAMELIST /OFFLINE_PARM01/
37     & UvelFile, VvelFile, WvelFile, ThetFile,
38     & SaltFile, ConvFile, GMwxFile, GMwyFile,
39 jmc 1.8 & GMwzFile, HfluxFile, SfluxFile,
40     & KPP_DiffSFile, KPP_ghatKFile, ICEFile,
41     & KPP_ghatFile
42 stephd 1.1
43     NAMELIST /OFFLINE_PARM02/
44 stephd 1.4 & offlineIter0, offlineOffsetIter,
45 jmc 1.8 & deltaToffline, offlineForcingPeriod,
46 dfer 1.7 & offlineForcingCycle, offlineLoadPrec
47 stephd 1.1
48 jmc 1.9 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
49 stephd 1.1
50     _BEGIN_MASTER(myThid)
51    
52     WRITE(msgBuf,'(A)') ' OFFLINE_READPARMS: opening data.off'
53     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
54 jmc 1.8 & SQUEEZE_RIGHT, myThid )
55    
56 stephd 1.1
57     CALL OPEN_COPY_DATA_FILE(
58     I 'data.off', 'OFFLINE_READPARMS',
59     O iUnit,
60     I myThid )
61    
62 jmc 1.8 C-- Default values for params in OFFLINE_PARM01 :
63 stephd 1.1 UvelFile=' '
64     VvelFile=' '
65     WvelFile=' '
66     ThetFile=' '
67     SaltFile=' '
68     ConvFile=' '
69     GMwxFile=' '
70     GMwyFile=' '
71 jmc 1.8 GMwzFile=' '
72 stephd 1.2 HFluxFile=' '
73     SFluxFile=' '
74 stephd 1.3 KPP_DiffSFile=' '
75 jmc 1.8 KPP_ghatKFile=' '
76     KPP_ghatFile='KPP_ghatFile has been replaced by KPP_ghatKFile'
77 stephd 1.6 ICEFile=' '
78 stephd 1.1
79     C-- Read parameters from open data file
80     READ(UNIT=iUnit,NML=OFFLINE_PARM01)
81    
82 jmc 1.8 IF ( KPP_ghatFile .NE.
83     & 'KPP_ghatFile has been replaced by KPP_ghatKFile' ) THEN
84     c nRetired = nRetired+1
85     WRITE(msgBuf,'(A,A)') 'S/R OFFLINE_READPARMS: "KPP_ghatFile"',
86     & ' is no longer allowed in file "data.off"'
87     CALL PRINT_ERROR( msgBuf, myThid )
88     WRITE(msgBuf,'(A,A)') 'S/R OFFLINE_READPARMS: read instead ',
89     & 'the product ghat*diffKz from file "KPP_ghatKFile"'
90     CALL PRINT_ERROR( msgBuf, myThid )
91     STOP 'ABNORMAL END: S/R OFFLINE_READPARMS'
92     ENDIF
93    
94     C-- Default values for params in OFFLINE_PARM02 :
95 stephd 1.1 deltaToffline=deltaTclock
96 dfer 1.7 offlineIter0=nIter0 !initial offline field timestep
97 stephd 1.4 offlineOffsetIter=0 !offset
98 stephd 1.1 offlineForcingPeriod=2592000.
99     offlineForcingCycle=31104000.
100 dfer 1.7 offlineLoadPrec=readBinaryPrec
101 jmc 1.8
102 stephd 1.1 C-- Read parameters from open data file
103     READ(UNIT=iUnit,NML=OFFLINE_PARM02)
104    
105     WRITE(msgBuf,'(A)')
106     & ' OFFLINE_READPARMS: finished reading data.off'
107     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
108 jmc 1.8 & SQUEEZE_RIGHT, myThid )
109 stephd 1.1
110     C-- Close the open data file
111     CLOSE(iUnit)
112     _END_MASTER(myThid)
113    
114     C-- Everyone else must wait for the parameters to be loaded
115     _BARRIER
116    
117     #endif /* ALLOW_OFFLINE */
118    
119 jmc 1.5 RETURN
120     END

  ViewVC Help
Powered by ViewVC 1.1.22