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

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

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


Revision 1.23 - (hide annotations) (download)
Tue Nov 8 23:01:10 2005 UTC (18 years, 7 months ago) by cnh
Branch: MAIN
CVS Tags: checkpoint58b_post, checkpoint57y_post, checkpoint58, checkpoint58f_post, checkpoint58d_post, checkpoint58a_post, checkpoint57z_post, checkpoint58m_post, checkpoint57y_pre, checkpoint58o_post, checkpoint58p_post, checkpoint58q_post, checkpoint58e_post, checkpoint58n_post, checkpoint58k_post, checkpoint58l_post, checkpoint58g_post, checkpoint58h_post, checkpoint58j_post, checkpoint58i_post, checkpoint57x_post, checkpoint58c_post
Changes since 1.22: +3 -3 lines
Removing gratuitous _BEGIN_MASTER statements so that singleCpuIO make work
multi-threaded.

1 cnh 1.23 C $Header: /u/gcmpack/MITgcm/model/src/ini_theta.F,v 1.22 2005/11/07 18:26:02 cnh Exp $
2 adcroft 1.15 C $Name: $
3 cnh 1.1
4 cnh 1.9 #include "CPP_OPTIONS.h"
5 cnh 1.1
6 cnh 1.16 CBOP
7     C !ROUTINE: INI_THETA
8     C !INTERFACE:
9 cnh 1.1 SUBROUTINE INI_THETA( myThid )
10 cnh 1.16 C !DESCRIPTION: \bv
11     C *==========================================================*
12     C | SUBROUTINE INI_THETA
13     C | o Set model initial temperature field.
14     C *==========================================================*
15     C | There are several options for setting the initial
16     C | temperature file
17     C | 1. Inline code
18     C | 2. Vertical profile ( uniform T in X and Y )
19     C | 3. Three-dimensional data from a file. For example from
20     C | Levitus or from a checkpoint file from a previous
21     C | integration.
22     C | In addition to setting the temperature field we also
23     C | set the initial temperature tendency term here.
24     C *==========================================================*
25     C \ev
26    
27     C !USES:
28 adcroft 1.11 IMPLICIT NONE
29 cnh 1.1 C === Global variables ===
30     #include "SIZE.h"
31     #include "EEPARAMS.h"
32     #include "PARAMS.h"
33     #include "GRID.h"
34     #include "DYNVARS.h"
35    
36 cnh 1.16 C !INPUT/OUTPUT PARAMETERS:
37 cnh 1.1 C == Routine arguments ==
38     C myThid - Number of this instance of INI_THETA
39     INTEGER myThid
40    
41 cnh 1.16 C !LOCAL VARIABLES:
42 cnh 1.1 C == Local variables ==
43     C bi,bj - Loop counters
44     C I,J,K
45     INTEGER bi, bj
46 adcroft 1.13 INTEGER I, J, K, localWarnings
47 jmc 1.21 _RL Tfreezing
48 adcroft 1.13 CHARACTER*(MAX_LEN_MBUF) msgBuf
49 cnh 1.16 CEOP
50 cnh 1.1
51 adcroft 1.15 C-- Initialise temperature field to the vertical reference profile
52     DO bj = myByLo(myThid), myByHi(myThid)
53     DO bi = myBxLo(myThid), myBxHi(myThid)
54     DO K=1,Nr
55     DO J=1-Oly,sNy+Oly
56     DO I=1-Olx,sNx+Olx
57     theta(I,J,K,bi,bj) = tRef(K)
58 cnh 1.1 ENDDO
59     ENDDO
60     ENDDO
61     ENDDO
62 adcroft 1.15 ENDDO
63 cnh 1.22 _BARRIER
64 adcroft 1.15
65     IF ( hydrogThetaFile .NE. ' ' ) THEN
66 cnh 1.23 C _BEGIN_MASTER( myThid )
67 cnh 1.4 CALL READ_FLD_XYZ_RL( hydrogThetaFile, ' ', theta, 0, myThid )
68 cnh 1.23 C _END_MASTER(myThid)
69 adcroft 1.15 _EXCH_XYZ_R8(theta,myThid)
70 cnh 1.3 ENDIF
71 adcroft 1.15
72 dimitri 1.19 C-- Apply mask and test consistency
73 adcroft 1.13 localWarnings=0
74 cnh 1.1 DO bj = myByLo(myThid), myByHi(myThid)
75     DO bi = myBxLo(myThid), myBxHi(myThid)
76 cnh 1.7 DO K=1,Nr
77 jmc 1.21 DO J=1-Oly,sNy+Oly
78     DO I=1-Olx,sNx+Olx
79     IF (maskC(I,J,K,bi,bj).EQ.0.) theta(I,J,K,bi,bj) = 0.
80     ENDDO
81     ENDDO
82     IF ( tRef(k).NE.0. ) THEN
83     DO J=1,sNy
84     DO I=1,sNx
85     IF ( maskC(I,J,K,bi,bj).NE.0.
86     & .AND. theta(I,J,K,bi,bj).EQ.0. ) THEN
87     localWarnings=localWarnings+1
88 adcroft 1.13 ENDIF
89 jmc 1.21 ENDDO
90 cnh 1.1 ENDDO
91 jmc 1.21 ENDIF
92 cnh 1.1 ENDDO
93     ENDDO
94     ENDDO
95 adcroft 1.13 IF (localWarnings.NE.0) THEN
96     WRITE(msgBuf,'(A,A)')
97     & 'S/R INI_THETA: theta = 0 identically. If this is intentional',
98     & 'you will need to edit ini_theta.F to avoid this safety check'
99     CALL PRINT_ERROR( msgBuf , myThid)
100     STOP 'ABNORMAL END: S/R INI_THETA'
101 dimitri 1.19 ENDIF
102    
103     C-- Check that there are no values of temperature below freezing point.
104 jmc 1.20 Tfreezing=-1.9 _d 0
105 dimitri 1.19 IF ( allowFreezing ) THEN
106     DO bj = myByLo(myThid), myByHi(myThid)
107     DO bi = myBxLo(myThid), myBxHi(myThid)
108     DO K=1,Nr
109     DO J=1-Oly,sNy+Oly
110     DO I=1-Olx,sNx+Olx
111     IF (theta(I,J,k,bi,bj) .LT. Tfreezing) THEN
112     theta(I,J,K,bi,bj) = Tfreezing
113     ENDIF
114     ENDDO
115     ENDDO
116     ENDDO
117     ENDDO
118     ENDDO
119 adcroft 1.13 ENDIF
120 cnh 1.5
121 jmc 1.21 CALL PLOT_FIELD_XYZRL( theta, 'Initial Temperature' ,
122 cnh 1.8 & Nr, 1, myThid )
123 cnh 1.5
124 cnh 1.1 RETURN
125     END

  ViewVC Help
Powered by ViewVC 1.1.22