/[MITgcm]/MITgcm_contrib/snarayan/activefiles/verification/hs94.1x64x5/code_oad/ini_theta.F
ViewVC logotype

Annotation of /MITgcm_contrib/snarayan/activefiles/verification/hs94.1x64x5/code_oad/ini_theta.F

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


Revision 1.1 - (hide annotations) (download)
Mon Dec 1 16:46:01 2014 UTC (10 years, 8 months ago) by snarayan
Branch: MAIN
CVS Tags: HEAD
A test version for active files

1 snarayan 1.1 C $Header: /u/gcmpack/MITgcm/verification/hs94.1x64x5/code_oad/ini_theta.F,v 1.1 2013/06/21 17:36:32 heimbach 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    
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    
38     C !INPUT/OUTPUT PARAMETERS:
39     C == Routine arguments ==
40     C myThid - Number of this instance of INI_THETA
41     INTEGER myThid
42    
43     C == Functions ==
44     c real*8 PORT_RAND
45     c real*8 seed
46    
47     C !LOCAL VARIABLES:
48     C == Local variables ==
49     C bi,bj - Loop counters
50     C I,J,K
51     INTEGER bi, bj
52     INTEGER I, J, K, localWarnings
53     _RL term1,term2,thetaLim,thetaEq
54     CHARACTER*(MAX_LEN_MBUF) msgBuf
55     CEOP
56    
57     J = 99+myBxLo(myThid)+nPx*myByLo(myThid)
58     c CALL SRAND( J )
59     c seed = j
60    
61     IF ( hydrogThetaFile .EQ. ' ' ) THEN
62     C-- Initialise temperature field to Held & Saurez equilibrium theta
63     DO bj = myByLo(myThid), myByHi(myThid)
64     DO bi = myBxLo(myThid), myBxHi(myThid)
65     DO K=1,Nr
66     thetaLim = 200. _d 0/((rC(K)/atm_po)**atm_kappa)
67     DO J=1,sNy
68     DO I=1,sNx
69     term1=60. _d 0*(sin(yC(I,J,bi,bj)*deg2rad)**2)
70     term2=10. _d 0*log((rC(K)/atm_po))
71     & *(cos(yC(I,J,bi,bj)*deg2rad)**2)
72     thetaEq=315. _d 0-term1-term2
73     theta(I,J,K,bi,bj) = MAX( thetaLim, thetaEq )
74     c & + 0.01*(RAND()-0.5)
75     c & + 0.01*(PORT_RAND(seed)-0.5)
76     c theta(I,J,K,bi,bj) = tRef(K)
77     ENDDO
78     ENDDO
79     ENDDO
80     #ifdef ALLOW_ZONAL_FILT
81     C-- Zonal FFT filter initial conditions
82     IF (useZONAL_FILT) THEN
83     CALL ZONAL_FILTER(
84     U theta(1-OLx,1-OLy,1,bi,bj),
85     I hFacC(1-OLx,1-OLy,1,bi,bj),
86     I 1, sNy, Nr, bi, bj, 1, myThid )
87     ENDIF
88     #endif /* ALLOW_ZONAL_FILT */
89     ENDDO
90     ENDDO
91     ELSE
92     CALL READ_FLD_XYZ_RL( hydrogThetaFile, ' ', theta, 0, myThid )
93     ENDIF
94     C-- Apply mask and test consistency
95     localWarnings=0
96     DO bj = myByLo(myThid), myByHi(myThid)
97     DO bi = myBxLo(myThid), myBxHi(myThid)
98     DO K=1,Nr
99     DO J=1-Oly,sNy+Oly
100     DO I=1-Olx,sNx+Olx
101     IF (maskC(I,J,K,bi,bj).EQ.0.) theta(I,J,K,bi,bj) = 0.
102     ENDDO
103     ENDDO
104     IF ( tRef(k).NE.0. ) THEN
105     DO J=1,sNy
106     DO I=1,sNx
107     IF ( maskC(I,J,K,bi,bj).NE.0.
108     & .AND. theta(I,J,K,bi,bj).EQ.0. ) THEN
109     localWarnings=localWarnings+1
110     ENDIF
111     ENDDO
112     ENDDO
113     ENDIF
114     ENDDO
115     ENDDO
116     ENDDO
117     IF (localWarnings.NE.0) THEN
118     WRITE(msgBuf,'(A,A)')
119     & 'S/R INI_THETA: theta = 0 identically. If this is intentional',
120     & 'you will need to edit ini_theta.F to avoid this safety check'
121     CALL PRINT_ERROR( msgBuf , myThid)
122     STOP 'ABNORMAL END: S/R INI_THETA'
123     ENDIF
124    
125     _EXCH_XYZ_RL(theta , myThid )
126    
127     IF (debugMode) THEN
128     CALL PLOT_FIELD_XYZRL( theta, 'Initial Temperature' ,
129     & Nr, 1, myThid )
130     ENDIF
131    
132     RETURN
133     END

  ViewVC Help
Powered by ViewVC 1.1.22