/[MITgcm]/MITgcm_contrib/cam_devel/sigma_testing/code-sigma/ini_theta.F
ViewVC logotype

Annotation of /MITgcm_contrib/cam_devel/sigma_testing/code-sigma/ini_theta.F

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


Revision 1.1 - (hide annotations) (download)
Wed Jan 6 04:31:15 2010 UTC (15 years, 6 months ago) by cnh
Branch: MAIN
CVS Tags: HEAD
start some cam work

1 cnh 1.1 C $Header: /u/gcmpack/MITgcm/model/src/ini_theta.F,v 1.28 2009/10/15 01:06:51 jmc Exp $
2     C $Name: $
3    
4     #include "PACKAGES_CONFIG.h"
5     #include "CPP_OPTIONS.h"
6    
7     CBOP
8     C !ROUTINE: INI_THETA
9     C !INTERFACE:
10     SUBROUTINE INI_THETA( myThid )
11     C !DESCRIPTION: \bv
12     C *==========================================================*
13     C | SUBROUTINE INI_THETA
14     C | o Set model initial temperature field.
15     C *==========================================================*
16     C | There are several options for setting the initial
17     C | temperature file
18     C | 1. Inline code
19     C | 2. Vertical profile ( uniform T in X and Y )
20     C | 3. Three-dimensional data from a file. For example from
21     C | Levitus or from a checkpoint file from a previous
22     C | integration.
23     C | In addition to setting the temperature field we also
24     C | set the initial temperature tendency term here.
25     C *==========================================================*
26     C \ev
27    
28     C !USES:
29     IMPLICIT NONE
30     C === Global variables ===
31     #include "SIZE.h"
32     #include "EEPARAMS.h"
33     #include "PARAMS.h"
34     #include "GRID.h"
35     #include "DYNVARS.h"
36     #ifdef ALLOW_MNC
37     #include "MNC_PARAMS.h"
38     #endif
39    
40     C !INPUT/OUTPUT PARAMETERS:
41     C == Routine arguments ==
42     C myThid :: Number of this instance of INI_THETA
43     INTEGER myThid
44    
45     C !LOCAL VARIABLES:
46     C == Local variables ==
47     C bi,bj :: Tile indices
48     C i,j,k :: Loop counters
49     INTEGER bi, bj
50     INTEGER i, j, k, localWarnings
51     _RL Tfreezing
52     CHARACTER*(MAX_LEN_MBUF) msgBuf
53     CEOP
54    
55     C-- Initialise temperature field to the vertical reference profile
56     DO bj = myByLo(myThid), myByHi(myThid)
57     DO bi = myBxLo(myThid), myBxHi(myThid)
58     DO k=1,Nr
59     DO j=1-Oly,sNy+Oly
60     DO i=1-Olx,sNx+Olx
61     theta(i,j,k,bi,bj) = tRef(k)
62     ENDDO
63     ENDDO
64     ENDDO
65     ENDDO
66     ENDDO
67    
68     IF ( hydrogThetaFile .NE. ' ' ) THEN
69     #ifdef ALLOW_MNC
70     IF ( useMNC.AND.mnc_read_theta ) THEN
71     CALL MNC_FILE_CLOSE_ALL_MATCHING(hydrogThetaFile, myThid)
72     CALL MNC_CW_SET_UDIM(hydrogThetaFile, 1, myThid)
73     CALL MNC_CW_SET_CITER(hydrogThetaFile, 2, -1, -1, -1, myThid)
74     CALL MNC_CW_SET_UDIM(hydrogThetaFile, 1, myThid)
75     CALL MNC_CW_RL_R('D',hydrogThetaFile,0,0,'Temp',theta,myThid)
76     CALL MNC_FILE_CLOSE_ALL_MATCHING(hydrogThetaFile, myThid)
77     ELSE
78     #endif /* ALLOW_MNC */
79     CALL READ_FLD_XYZ_RL( hydrogThetaFile, ' ', theta, 0, myThid )
80     #ifdef ALLOW_MNC
81     ENDIF
82     #endif /* ALLOW_MNC */
83     _EXCH_XYZ_RL(theta,myThid)
84     ENDIF
85    
86     C-- Apply mask and test consistency
87     localWarnings=0
88     DO bj = myByLo(myThid), myByHi(myThid)
89     DO bi = myBxLo(myThid), myBxHi(myThid)
90     DO k=1,Nr
91     IF ( maskIniTemp ) THEN
92     DO j=1-Oly,sNy+Oly
93     DO i=1-Olx,sNx+Olx
94     IF (maskC(i,j,k,bi,bj).EQ.0.) theta(i,j,k,bi,bj) = 0.
95     ENDDO
96     ENDDO
97     ENDIF
98     IF ( tRef(k).NE.0. ) THEN
99     DO j=1,sNy
100     DO i=1,sNx
101     IF ( maskC(i,j,k,bi,bj).NE.0.
102     & .AND. theta(i,j,k,bi,bj).EQ.0. ) THEN
103     localWarnings=localWarnings+1
104     ENDIF
105     ENDDO
106     ENDDO
107     ENDIF
108     ENDDO
109     ENDDO
110     ENDDO
111     IF (localWarnings.NE.0) THEN
112     IF ( checkIniTemp ) THEN
113     WRITE(msgBuf,'(A,I10,A)')
114     & ' INI_THETA: found', localWarnings,
115     & ' wet grid-pts with theta=0 identically.'
116     CALL PRINT_ERROR( msgBuf , myThid)
117     WRITE(msgBuf,'(A,A)')
118     & ' If this is intentional, you need to',
119     & ' set checkIniTemp=.false. in "data", namelist PARM05'
120     CALL PRINT_ERROR( msgBuf , myThid)
121     STOP 'ABNORMAL END: S/R INI_THETA'
122     ELSE
123     WRITE(msgBuf,'(A,I10,A)')
124     & '** WARNINGS ** INI_THETA: found', localWarnings,
125     & ' wet grid-pts with theta=0 identically.'
126     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
127     & SQUEEZE_RIGHT, myThid )
128     ENDIF
129     ENDIF
130    
131     C-- Check that there are no values of temperature below freezing point.
132     Tfreezing=-1.9 _d 0
133     IF ( allowFreezing ) THEN
134     DO bj = myByLo(myThid), myByHi(myThid)
135     DO bi = myBxLo(myThid), myBxHi(myThid)
136     DO k=1,Nr
137     DO j=1-Oly,sNy+Oly
138     DO i=1-Olx,sNx+Olx
139     IF (theta(i,j,k,bi,bj) .LT. Tfreezing) THEN
140     theta(i,j,k,bi,bj) = Tfreezing
141     ENDIF
142     ENDDO
143     ENDDO
144     ENDDO
145     ENDDO
146     ENDDO
147     ENDIF
148    
149     C-- Stick a tracer anomaly at K=Nr
150     DO i=1,100
151     theta(i,1,Nr,1,1) = theta(i,1,Nr,1,1)+
152     & EXP(-(DBLE(I)-50.)**2./400.)*100.
153     ENDDO
154    
155     IF (debugMode) THEN
156     CALL PLOT_FIELD_XYZRL( theta, 'Initial Temperature',
157     & Nr, 1, myThid )
158     ENDIF
159    
160     RETURN
161     END

  ViewVC Help
Powered by ViewVC 1.1.22