/[MITgcm]/MITgcm/verification/hs94.1x64x5/code_ad/ini_theta.F
ViewVC logotype

Annotation of /MITgcm/verification/hs94.1x64x5/code_ad/ini_theta.F

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


Revision 1.2 - (hide annotations) (download)
Fri Apr 15 22:10:13 2005 UTC (19 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58l_post, checkpoint57t_post, checkpoint57o_post, checkpoint58e_post, checkpoint57v_post, checkpoint58u_post, checkpoint58w_post, checkpoint57m_post, checkpoint57s_post, checkpoint57k_post, checkpoint60, checkpoint61, checkpoint58r_post, checkpoint57i_post, checkpoint57y_post, checkpoint58n_post, checkpoint58x_post, checkpoint58t_post, checkpoint58h_post, checkpoint57y_pre, checkpoint58q_post, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint58j_post, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59i, checkpoint59h, checkpoint59k, checkpoint59j, checkpoint57r_post, checkpoint59, checkpoint58, checkpoint57h_done, checkpoint58f_post, checkpoint57x_post, checkpoint58d_post, checkpoint58c_post, checkpoint57w_post, checkpoint57p_post, checkpint57u_post, checkpoint58a_post, checkpoint58i_post, checkpoint57q_post, checkpoint58g_post, checkpoint58o_post, checkpoint57z_post, checkpoint58y_post, checkpoint58k_post, checkpoint58v_post, checkpoint58s_post, checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint58p_post, checkpoint61a, checkpoint61l, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i, checkpoint57j_post, checkpoint58b_post, checkpoint57h_pre, checkpoint58m_post, checkpoint57l_post, checkpoint57h_post
Changes since 1.1: +66 -41 lines
bring local version closer to model/src version

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

  ViewVC Help
Powered by ViewVC 1.1.22