/[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.7 - (hide annotations) (download)
Thu Nov 14 22:43:49 2002 UTC (21 years, 6 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint47e_post, checkpoint47c_post, checkpoint47d_pre, checkpoint47a_post, checkpoint47d_post, checkpoint47g_post, branch-exfmods-tag, checkpoint47b_post, checkpoint47f_post, checkpoint47, checkpoint47h_post
Branch point for: branch-exfmods-curt
Changes since 1.6: +2 -2 lines
o * "clean" adjoint code (in terms of extensive recomputations)
    can now be obtained for all GMREDI options (i.e. for
    - GM_VISBECK_VARIABLE_K
    - GM_NON_UNITY_DIAGONAL
    - GM_EXTRA_DIAGONAL
    - GM_BOLUS_ADVEC )
  * However, wrong gradient check problem remains unsolved.
  * New CPP options have been introduced for different
    tapering schemes

1 heimbach 1.7 C $Header: /u/gcmpack/MITgcm/pkg/gmredi/gmredi_readparms.F,v 1.6 2002/03/06 01:56:27 jmc Exp $
2     C $Name: checkpoint46 $
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.6 & GM_AdvForm, GM_AdvSeparate,
31 jmc 1.5 & 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 jmc 1.6 GM_AdvSeparate = .FALSE.
71 jmc 1.5 GM_isopycK = -999.
72 heimbach 1.1 GM_background_K = 0.
73     GM_maxslope = 1.0D-2
74 jmc 1.5 GM_Kmin_horiz = 0.
75 heimbach 1.1 GM_taper_scheme = ' '
76     GM_Scrit = 0.004
77     GM_Sd = 0.001
78    
79     C-- Default values GM/Redi I/O control
80     c GM_dumpFreq = -1.
81     c GM_taveFreq = -1.
82    
83     C-- Default values Visbeck
84     GM_Visbeck_alpha = 0.
85     GM_Visbeck_length = 200.D3
86     GM_Visbeck_depth = 1000.D0
87     GM_Visbeck_maxval_K = 2500.D0
88    
89     C-- Read parameters from open data file
90     READ(UNIT=iUnit,NML=GM_PARM01)
91    
92 jmc 1.5 C Default value for GM_isopycK is equal to GM_background_K :
93     IF (GM_isopycK.EQ.-999.) GM_isopycK = GM_background_K
94    
95 heimbach 1.1 C Some constants
96     GM_rMaxSlope=0.
97     if (GM_maxSlope.ne.0.) GM_rMaxSlope=1. / GM_maxSlope
98    
99 jmc 1.5 IF (GM_AdvForm) THEN
100     GM_skewflx = 0.
101     GM_advect = 1.
102     GM_ExtraDiag = GM_Visbeck_alpha.NE.0. .OR. GM_isopycK.NE.0.
103     ELSE
104     GM_skewflx = 1.
105     GM_advect = 0.
106     GM_ExtraDiag = GM_isopycK.NE.GM_background_K
107     ENDIF
108    
109 heimbach 1.1 C Unspecified I/O control parameters default to model pars
110     c if (GM_dumpFreq.EQ.-1.) GM_dumpFreq=dumpFreq
111     c if (GM_taveFreq.EQ.-1.) GM_taveFreq=taveFreq
112    
113     #ifndef GM_VISBECK_VARIABLE_K
114     C Make sure we are not trying to use something that is unavailable
115     IF (GM_Visbeck_alpha .NE. 0.) THEN
116     WRITE(msgBuf,'(A)')
117 adcroft 1.3 & ' GM_READPARMS: Visbeck variables used in data.gmredi'
118 heimbach 1.1 CALL PRINT_ERROR( msgBuf, 1 )
119     WRITE(msgBuf,'(A)')
120 adcroft 1.3 & ' GM_READPARMS: without #define GM_VISBECK_VARIABLE_K'
121 heimbach 1.1 CALL PRINT_ERROR( msgBuf, 1 )
122 adcroft 1.3 STOP 'ABNORMAL END: S/R GM_READPARMS'
123 heimbach 1.1 ENDIF
124     #endif
125    
126 jmc 1.5 #ifndef GM_BOLUS_ADVEC
127     C Make sure we are not trying to use some arrays that are unavailable
128     IF (GM_AdvForm) THEN
129     WRITE(msgBuf,'(A)')
130     & ' GM_READPARMS: GM Advection form used in data.gmredi'
131     CALL PRINT_ERROR( msgBuf, 1 )
132     WRITE(msgBuf,'(A)')
133     & ' GM_READPARMS: without #define GM_BOLUS_ADVEC'
134     CALL PRINT_ERROR( msgBuf, 1 )
135     STOP 'ABNORMAL END: S/R GM_READPARMS'
136     ENDIF
137     #endif
138    
139     #ifndef GM_EXTRA_DIAGONAL
140     C Make sure we are not trying to use some arrays that are unavailable
141     IF (GM_ExtraDiag) THEN
142     WRITE(msgBuf,'(A)')
143     & ' GM_READPARMS: GM_skew_Flux_K & GM_isopycK not equal'
144     CALL PRINT_ERROR( msgBuf, 1 )
145     WRITE(msgBuf,'(A)')
146     & ' GM_READPARMS: without #define GM_EXTRA_DIAGONAL'
147     CALL PRINT_ERROR( msgBuf, 1 )
148     STOP 'ABNORMAL END: S/R GM_READPARMS'
149     ENDIF
150     #endif
151    
152 adcroft 1.3 WRITE(msgBuf,'(A)') ' GM_READPARMS: finished reading data.gmredi'
153 heimbach 1.1 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
154     & SQUEEZE_RIGHT , 1)
155    
156     C-- Close the open data file
157     CLOSE(iUnit)
158     _END_MASTER(myThid)
159    
160     C-- Everyone else must wait for the parameters to be loaded
161     _BARRIER
162    
163     #endif /* ALLOW_GMREDI */
164    
165 jmc 1.5 RETURN
166     END

  ViewVC Help
Powered by ViewVC 1.1.22