/[MITgcm]/MITgcm/model/src/ini_theta.F
ViewVC logotype

Contents of /MITgcm/model/src/ini_theta.F

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


Revision 1.29 - (show annotations) (download)
Wed Jun 8 01:27:59 2011 UTC (13 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint65b, checkpoint65a, checkpoint62z, checkpoint63g, checkpoint64, checkpoint65, checkpoint63, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f
Changes since 1.28: +3 -2 lines
test debugLevel (instead of debugMode) to print maps (using PLOT_FIELDS call)

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

  ViewVC Help
Powered by ViewVC 1.1.22