/[MITgcm]/MITgcm/pkg/shelfice/shelfice_readparms.F
ViewVC logotype

Annotation of /MITgcm/pkg/shelfice/shelfice_readparms.F

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


Revision 1.1 - (hide annotations) (download)
Tue Feb 7 11:45:21 2006 UTC (18 years, 3 months ago) by mlosch
Branch: MAIN
o add new package shelfice

1 mlosch 1.1 C $Header: $
2     C $Name: $
3    
4     #include "SHELFICE_OPTIONS.h"
5    
6     CBOP
7     C !ROUTINE: SHELFICE_READPARMS
8    
9     C !INTERFACE: ==========================================================
10     SUBROUTINE SHELFICE_READPARMS( myThid )
11    
12     C !DESCRIPTION:
13     C Initialize SHELFICE parameters, read in data.shelfice
14    
15     C !USES: ===============================================================
16     IMPLICIT NONE
17     #include "SIZE.h"
18     #include "EEPARAMS.h"
19     #include "SHELFICE.h"
20     #include "PARAMS.h"
21     #ifdef ALLOW_MNC
22     # include "MNC_PARAMS.h"
23     #endif
24    
25     C !INPUT PARAMETERS: ===================================================
26     C myThid :: thread number
27     INTEGER myThid
28    
29     C !OUTPUT PARAMETERS: ==================================================
30     C none
31    
32     #ifdef ALLOW_SHELFICE
33    
34     C !LOCAL VARIABLES: ====================================================
35     C iUnit :: unit number for I/O
36     C msgBuf :: message buffer
37     INTEGER iUnit
38     CHARACTER*(MAX_LEN_MBUF) msgBuf
39     CEOP
40    
41     NAMELIST /SHELFICE_PARM01/
42     & SHELFICEexchangeVelocity,
43     & SHELFICElatentHeat,
44     & SHELFICEDragLinear, SHELFICEDragQuadratic,
45     & useISOMIPTD, no_slip_shelfice,
46     & SHELFICEwriteState,
47     & SHELFICE_dumpFreq,
48     & SHELFICE_taveFreq,
49     & SHELFICE_tave_mnc,
50     & SHELFICE_dump_mnc
51    
52     C This routine has been called by the main model so we set our
53     C internal flag to indicate we are in business
54     SHELFICEisON=.TRUE.
55    
56     C Set defaults values for parameters in SHELFICE.h
57     useISOMIPTD = .TRUE.
58     SHELFICElatentHeat = 334.0 _d 3
59     recip_SHELFICElatentHeat = 0. _d 0
60     SHELFICEexchangeVelocity = 0. _d 0
61     no_slip_shelfice = no_slip_bottom
62     SHELFICEDragLinear = bottomDragLinear
63     SHELFICEDragQuadratic = bottomDragQuadratic
64     SHELFICEwriteState = .FALSE.
65     SHELFICE_dumpFreq = dumpFreq
66     SHELFICE_taveFreq = taveFreq
67     #ifdef ALLOW_MNC
68     SHELFICE_tave_mnc = timeave_mnc
69     SHELFICE_dump_mnc = snapshot_mnc
70     #else
71     SHELFICE_tave_mnc = .FALSE.
72     SHELFICE_dump_mnc = .FALSE.
73     #endif
74     CMLC Eingabe der Konstanten
75     CMLC gat = turbul. heat exchange coeff. [m/s]
76     CMLC gas = turbul. salt exchange coeff. [m/s]
77     CMLC HeMW=Heliumgehalt des Schmelzwassers
78     CMLC OoFW=Isotopeneintrag beim Frieren
79     CMLC OoMW=Isotopeneintrag beim Schmelzen
80     CMLc aqui
81     CML a = -0.0575 !
82     CML b = 0.0901 !Freezing point constants
83     CML c = 7.61e-4 !
84     CML
85     CML pn = 13.8 !Prandtl number
86     CML sn = 2432. !Schmidt number
87     CMLc appa_t = 1.34e-07 !molecular thermal diffusivity
88     CMLc appa_s = 7.40e-10 !molecular salt diffusivity
89     CML un = 1.95e-6
90     CMLc pn = un/appa_t
91     CMLc sn = un/appa_s
92     CML pn1 = pn**(2./3.)
93     CML sn1 = sn**(2./3.)
94     CML cd = 2.50e-3
95     CML srcd = sqrt(cd)
96     CML
97     CMLc arma = 0.4 ! Karman constant
98     CMLc z0_i = 0.00005 ! roughness length
99     CMLc srcd = arma/log(1/z0_i)
100     CML
101     CML lhf = 3.33e+5
102     CML cpi = 152.5+7.122*(atk+tob) !Paterson:"The Physics of Glaciers"
103     CML
104     CML rhoi=917.
105     CML rho0=1000.
106     CML
107     CML hemw= 4.02*14.
108     CML oomw=-30.
109     CML oofw=-2.5
110     CML SHELFICEnRi = 2
111     CML SHELFICEviscMin = 0. _d 0
112     CML SHELFICEdiffMin = 0. _d 0
113     CML SHELFICEviscMax = 1. _d 0
114     CML SHELFICEnu0 = 1. _d -02
115     CML SHELFICEalpha = 5. _d 0
116     CML RiLimit = UNSET_RL
117     CML SHELFICEdumpFreq = dumpFreq
118     CML SHELFICEtaveFreq = taveFreq
119     CML SHELFICEMixingMaps = .FALSE.
120     CML SHELFICEwriteState = .FALSE.
121    
122     C Open and read the data.shelfice file
123     _BEGIN_MASTER(myThid)
124     WRITE(msgBuf,'(A)') ' SHELFICE_READPARMS: opening data.shelfice'
125     CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
126     & SQUEEZE_RIGHT , 1)
127     CALL OPEN_COPY_DATA_FILE(
128     I 'data.shelfice', 'SHELFICE_READPARMS',
129     O iUnit,
130     I myThid )
131     READ(UNIT=iUnit,NML=SHELFICE_PARM01)
132     WRITE(msgBuf,'(A)')
133     & ' SHELFICE_READPARMS: finished reading data.shelfice'
134     CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
135     & SQUEEZE_RIGHT , 1)
136    
137     C Close the open data file
138     CLOSE(iUnit)
139     _END_MASTER(myThid)
140    
141     C Everyone else must wait for the parameters to be loaded
142     _BARRIER
143    
144     C Now set-up any remaining parameters that result from the input parameters
145     IF ( SHELFICElatentHeat .NE. 0. _d 0 )
146     & recip_SHELFICElatentHeat = 1. _d 0/SHELFICElatentHeat
147    
148     C- Set Output type flags :
149     SHELFICE_tave_mdsio = .TRUE.
150     SHELFICE_dump_mdsio = .TRUE.
151     #ifdef ALLOW_MNC
152     IF (useMNC) THEN
153     IF ( .NOT.outputTypesInclusive
154     & .AND. SHELFICE_tave_mnc ) SHELFICE_tave_mdsio = .FALSE.
155     IF ( .NOT.outputTypesInclusive
156     & .AND. SHELFICE_dump_mnc ) SHELFICE_dump_mdsio = .FALSE.
157     ENDIF
158     #endif
159    
160     #ifdef ALLOW_MNC
161     C Initialize MNC variable information for SHELFICE
162     IF ( useMNC .AND. (shelfice_tave_mnc.OR.shelfice_dump_mnc)
163     & ) THEN
164     CALL SHELFICE_MNC_INIT( myThid )
165     ENDIF
166     #endif /* ALLOW_MNC */
167    
168     #endif /* ALLOW_SHELFICE */
169    
170     RETURN
171     END

  ViewVC Help
Powered by ViewVC 1.1.22