/[MITgcm]/MITgcm/pkg/gmredi/gmredi_readparms.F
ViewVC logotype

Annotation of /MITgcm/pkg/gmredi/gmredi_readparms.F

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


Revision 1.5 - (hide annotations) (download)
Sun Dec 16 18:54:49 2001 UTC (22 years, 6 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint44e_post, checkpoint44f_post, checkpoint43a-release1mods, chkpt44d_post, checkpoint44e_pre, release1-branch_tutorials, chkpt44a_post, chkpt44c_pre, checkpoint44g_post, release1-branch-end, release1_final_v1, checkpoint44b_post, chkpt44a_pre, checkpoint44b_pre, checkpoint44, chkpt44c_post, checkpoint44f_pre, release1-branch_branchpoint
Branch point for: release1_final, release1-branch
Changes since 1.4: +50 -11 lines
Modification to the GMREDI package :
 change units of tensor-K arrays, scale now like diffusivity
 initialise all common block arrays in S/R gmredi_init
 add option to use different isopycnal(Redi) & GM diffusivity
 add option to use the advective GM form or the skew-flux form (=default)
 bug in non_unity_diagonal part fixed.

1 jmc 1.5 C $Header: /u/gcmpack/models/MITgcmUV/pkg/gmredi/gmredi_readparms.F,v 1.4 2001/02/04 14:38:49 cnh Exp $
2     C $Name: $
3 heimbach 1.1
4     #include "GMREDI_OPTIONS.h"
5    
6     SUBROUTINE GMREDI_READPARMS( myThid )
7     C /==========================================================\
8     C | SUBROUTINE GMREDI_READPARMS |
9     C | o Routine to initialize GM/Redi variables and constants. |
10     C |==========================================================|
11     C | Initialize GM/Redi parameters, read in data.gmredi |
12     C \==========================================================/
13     IMPLICIT NONE
14    
15     C === Global variables ===
16     #include "SIZE.h"
17     #include "EEPARAMS.h"
18     #include "PARAMS.h"
19     #include "GRID.h"
20     #include "GMREDI.h"
21     #include "GMREDI_DIAGS.h"
22    
23     C === Routine arguments ===
24     INTEGER myThid
25    
26     #ifdef ALLOW_GMREDI
27    
28     C-- GM/Redi parameter
29     NAMELIST /GM_PARM01/
30 jmc 1.5 & GM_AdvForm,
31     & GM_isopycK,
32     & GM_background_K,
33 heimbach 1.1 & GM_taper_scheme,
34     & GM_maxSlope,
35 jmc 1.5 & GM_Kmin_horiz,
36 heimbach 1.1 & GM_Visbeck_alpha,
37     & GM_Visbeck_length,
38     & GM_Visbeck_depth,
39     & GM_Visbeck_maxval_K,
40     & GM_Scrit,
41     & GM_Sd
42     c & GM_dumpFreq,
43     c & GM_taveFreq
44    
45     C === Local variables ===
46     C msgBuf - Informational/error meesage buffer
47     C iUnit - Work variable for IO unit number
48     CHARACTER*(MAX_LEN_MBUF) msgBuf
49     INTEGER iUnit
50    
51     C-- GMREDI_READPARMS has been called so we know that
52     C the package is active.
53     GMRediIsOn=.TRUE.
54    
55    
56     _BEGIN_MASTER(myThid)
57    
58 adcroft 1.3 WRITE(msgBuf,'(A)') ' GM_READPARMS: opening data.gmredi'
59 heimbach 1.1 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
60     & SQUEEZE_RIGHT , 1)
61    
62    
63     CALL OPEN_COPY_DATA_FILE(
64 adcroft 1.3 I 'data.gmredi', 'GM_READPARMS',
65 heimbach 1.1 O iUnit,
66     I myThid )
67    
68     C-- Default values GM/Redi
69 jmc 1.5 GM_AdvForm = .FALSE.
70     GM_isopycK = -999.
71 heimbach 1.1 GM_background_K = 0.
72     GM_maxslope = 1.0D-2
73 jmc 1.5 GM_Kmin_horiz = 0.
74 heimbach 1.1 GM_taper_scheme = ' '
75     GM_Scrit = 0.004
76     GM_Sd = 0.001
77    
78     C-- Default values GM/Redi I/O control
79     c GM_dumpFreq = -1.
80     c GM_taveFreq = -1.
81    
82     C-- Default values Visbeck
83     GM_Visbeck_alpha = 0.
84     GM_Visbeck_length = 200.D3
85     GM_Visbeck_depth = 1000.D0
86     GM_Visbeck_maxval_K = 2500.D0
87    
88     C-- Read parameters from open data file
89     READ(UNIT=iUnit,NML=GM_PARM01)
90    
91 jmc 1.5 C Default value for GM_isopycK is equal to GM_background_K :
92     IF (GM_isopycK.EQ.-999.) GM_isopycK = GM_background_K
93    
94 heimbach 1.1 C Some constants
95     GM_rMaxSlope=0.
96     if (GM_maxSlope.ne.0.) GM_rMaxSlope=1. / GM_maxSlope
97    
98 jmc 1.5 IF (GM_AdvForm) THEN
99     GM_skewflx = 0.
100     GM_advect = 1.
101     GM_ExtraDiag = GM_Visbeck_alpha.NE.0. .OR. GM_isopycK.NE.0.
102     ELSE
103     GM_skewflx = 1.
104     GM_advect = 0.
105     GM_ExtraDiag = GM_isopycK.NE.GM_background_K
106     ENDIF
107    
108 heimbach 1.1 C Unspecified I/O control parameters default to model pars
109     c if (GM_dumpFreq.EQ.-1.) GM_dumpFreq=dumpFreq
110     c if (GM_taveFreq.EQ.-1.) GM_taveFreq=taveFreq
111    
112     #ifndef GM_VISBECK_VARIABLE_K
113     C Make sure we are not trying to use something that is unavailable
114     IF (GM_Visbeck_alpha .NE. 0.) THEN
115     WRITE(msgBuf,'(A)')
116 adcroft 1.3 & ' GM_READPARMS: Visbeck variables used in data.gmredi'
117 heimbach 1.1 CALL PRINT_ERROR( msgBuf, 1 )
118     WRITE(msgBuf,'(A)')
119 adcroft 1.3 & ' GM_READPARMS: without #define GM_VISBECK_VARIABLE_K'
120 heimbach 1.1 CALL PRINT_ERROR( msgBuf, 1 )
121 adcroft 1.3 STOP 'ABNORMAL END: S/R GM_READPARMS'
122 heimbach 1.1 ENDIF
123     #endif
124    
125 jmc 1.5 #ifndef GM_BOLUS_ADVEC
126     C Make sure we are not trying to use some arrays that are unavailable
127     IF (GM_AdvForm) THEN
128     WRITE(msgBuf,'(A)')
129     & ' GM_READPARMS: GM Advection form used in data.gmredi'
130     CALL PRINT_ERROR( msgBuf, 1 )
131     WRITE(msgBuf,'(A)')
132     & ' GM_READPARMS: without #define GM_BOLUS_ADVEC'
133     CALL PRINT_ERROR( msgBuf, 1 )
134     STOP 'ABNORMAL END: S/R GM_READPARMS'
135     ENDIF
136     #endif
137    
138     #ifndef GM_EXTRA_DIAGONAL
139     C Make sure we are not trying to use some arrays that are unavailable
140     IF (GM_ExtraDiag) THEN
141     WRITE(msgBuf,'(A)')
142     & ' GM_READPARMS: GM_skew_Flux_K & GM_isopycK not equal'
143     CALL PRINT_ERROR( msgBuf, 1 )
144     WRITE(msgBuf,'(A)')
145     & ' GM_READPARMS: without #define GM_EXTRA_DIAGONAL'
146     CALL PRINT_ERROR( msgBuf, 1 )
147     STOP 'ABNORMAL END: S/R GM_READPARMS'
148     ENDIF
149     #endif
150    
151 adcroft 1.3 WRITE(msgBuf,'(A)') ' GM_READPARMS: finished reading data.gmredi'
152 heimbach 1.1 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
153     & SQUEEZE_RIGHT , 1)
154    
155     C-- Close the open data file
156     CLOSE(iUnit)
157     _END_MASTER(myThid)
158    
159     C-- Everyone else must wait for the parameters to be loaded
160     _BARRIER
161    
162     #endif /* ALLOW_GMREDI */
163    
164 jmc 1.5 RETURN
165     END

  ViewVC Help
Powered by ViewVC 1.1.22