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

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

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

revision 1.1 by heimbach, Sun Oct 26 01:58:09 2003 UTC revision 1.2 by jmc, Fri Apr 15 22:10:13 2005 UTC
# Line 1  Line 1 
1  C $Header$  C $Header$
2  C $Name$  C $Name$
3    
4    #include "PACKAGES_CONFIG.h"
5  #include "CPP_OPTIONS.h"  #include "CPP_OPTIONS.h"
6    
7  CStartOfInterface  CBOP
8    C     !ROUTINE: INI_THETA
9    C     !INTERFACE:
10        SUBROUTINE INI_THETA( myThid )        SUBROUTINE INI_THETA( myThid )
11  C     /==========================================================\  C     !DESCRIPTION: \bv
12  C     | SUBROUTINE INI_THETA                                     |  C     *==========================================================*
13  C     | o Set model initial temperature field.                   |  C     | SUBROUTINE INI_THETA                                      
14  C     |==========================================================|  C     | o Set model initial temperature field.                    
15  C     | There are several options for setting the initial        |  C     *==========================================================*
16  C     | temperature file                                         |  C     | There are several options for setting the initial        
17  C     |  1. Inline code                                          |  C     | temperature file                                          
18  C     |  2. Vertical profile ( uniform T in X and Y )            |  C     |  1. Inline code                                          
19  C     |  3. Three-dimensional data from a file. For example from |  C     |  2. Vertical profile ( uniform T in X and Y )            
20  C     |     Levitus or from a checkpoint file from a previous    |  C     |  3. Three-dimensional data from a file. For example from  
21  C     |     integration.                                         |  C     |     Levitus or from a checkpoint file from a previous    
22  C     | In addition to setting the temperature field we also     |  C     |     integration.                                          
23  C     | set the initial temperature tendency term here.          |  C     | In addition to setting the temperature field we also      
24  C     \==========================================================/  C     | set the initial temperature tendency term here.          
25    C     *==========================================================*
26    C     \ev
27    
28    C     !USES:
29        IMPLICIT NONE        IMPLICIT NONE
30    
31  C     === Global variables ===  C     === Global variables ===
# Line 28  C     === Global variables === Line 35  C     === Global variables ===
35  #include "GRID.h"  #include "GRID.h"
36  #include "DYNVARS.h"  #include "DYNVARS.h"
37    
38    C     !INPUT/OUTPUT PARAMETERS:
39  C     == Routine arguments ==  C     == Routine arguments ==
40  C     myThid -  Number of this instance of INI_THETA  C     myThid -  Number of this instance of INI_THETA
41        INTEGER myThid        INTEGER myThid
 CEndOfInterface  
42    
43    C     == Functions ==
44          real*8  PORT_RAND
45          real*8  seed
46    
47    C     !LOCAL VARIABLES:
48  C     == Local variables ==  C     == Local variables ==
49  C     bi,bj  - Loop counters  C     bi,bj  - Loop counters
50  C     I,J,K  C     I,J,K
51        INTEGER bi, bj        INTEGER bi, bj
52        INTEGER I, J, K, localWarnings        INTEGER I, J, K, localWarnings
53        _RL     term1,term2,thetaLim,thetaEq        _RL     term1,term2,thetaLim,thetaEq
       _RL     thKappa,rSurf  
54        CHARACTER*(MAX_LEN_MBUF) msgBuf        CHARACTER*(MAX_LEN_MBUF) msgBuf
55    CEOP
56    
57        _BARRIER        _BARRIER
58    
59          J = 99+myBxLo(myThid)+nPx*myByLo(myThid)
60    c     CALL SRAND( J )
61    c     seed = j
62    
63        IF ( hydrogThetaFile .EQ. ' ' ) THEN        IF ( hydrogThetaFile .EQ. ' ' ) THEN
64  C--    Initialise temperature field to Held & Saurez equilibrium theta  C--    Initialise temperature field to Held & Saurez equilibrium theta
65         DO bj = myByLo(myThid), myByHi(myThid)         DO bj = myByLo(myThid), myByHi(myThid)
66          DO bi = myBxLo(myThid), myBxHi(myThid)          DO bi = myBxLo(myThid), myBxHi(myThid)
67           DO K=1,Nr           DO K=1,Nr
68            rSurf=1. _d 5            thetaLim = 200. _d 0/((rC(K)/atm_po)**atm_kappa)
           thKappa = 2. _d 0/7. _d 0  
           thetaLim = 200. _d 0 / ((rC(K)/rSurf)**thKappa)  
 C         thetaLim = 170. _d 0 / ((rC(K)/rSurf)**thKappa)  
69            DO J=1,sNy            DO J=1,sNy
            term1=60. _d 0*(sin(yC(1,J,bi,bj)*deg2rad)**2)  
            term2=10. _d 0*log((rC(K)/rSurf))  
      &              *(cos(yC(1,J,bi,bj)*deg2rad)**2)  
            thetaEq=315. _d 0-term1-term2  
70             DO I=1,sNx             DO I=1,sNx
71                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              theta(I,J,K,bi,bj) = MAX( thetaLim, thetaEq )              theta(I,J,K,bi,bj) = MAX( thetaLim, thetaEq )
76  C           theta(I,J,K,bi,bj) = tRef(K)  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             ENDDO             ENDDO
80            ENDDO            ENDDO
81           ENDDO           ENDDO
82    #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          ENDDO          ENDDO
91         ENDDO         ENDDO
92        ELSE        ELSE
# Line 71  C           theta(I,J,K,bi,bj) = tRef(K) Line 94  C           theta(I,J,K,bi,bj) = tRef(K)
94         CALL READ_FLD_XYZ_RL( hydrogThetaFile, ' ', theta, 0, myThid )         CALL READ_FLD_XYZ_RL( hydrogThetaFile, ' ', theta, 0, myThid )
95         _END_MASTER(myThid)         _END_MASTER(myThid)
96        ENDIF        ENDIF
97  C     Set initial tendency terms  C--   Apply mask and test consistency
98        localWarnings=0        localWarnings=0
99        DO bj = myByLo(myThid), myByHi(myThid)        DO bj = myByLo(myThid), myByHi(myThid)
100         DO bi = myBxLo(myThid), myBxHi(myThid)         DO bi = myBxLo(myThid), myBxHi(myThid)
101          DO K=1,Nr          DO K=1,Nr
102           DO J=1,sNy           DO J=1-Oly,sNy+Oly
103            DO I=1,sNx            DO I=1-Olx,sNx+Olx
104             gt   (I,J,K,bi,bj) = 0. _d 0             IF (maskC(I,J,K,bi,bj).EQ.0.) theta(I,J,K,bi,bj) = 0.
            gtNM1(I,J,K,bi,bj) = 0. _d 0  
            IF (hFacC(I,J,K,bi,bj).EQ.0) theta(I,J,K,bi,bj) = 0.  
            IF (hFacC(I,J,K,bi,bj).NE.0.AND.theta(I,J,K,bi,bj).EQ.0.)  
      &      THEN  
              localWarnings=localWarnings+1  
             ENDIF  
105            ENDDO            ENDDO
106           ENDDO           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                ENDIF
114               ENDDO
115              ENDDO
116             ENDIF
117          ENDDO          ENDDO
118         ENDDO         ENDDO
119        ENDDO        ENDDO
# Line 97  C     Set initial tendency terms Line 124  C     Set initial tendency terms
124         CALL PRINT_ERROR( msgBuf , myThid)         CALL PRINT_ERROR( msgBuf , myThid)
125         STOP 'ABNORMAL END: S/R INI_THETA'         STOP 'ABNORMAL END: S/R INI_THETA'
126        ENDIF        ENDIF
127  C  
128        _EXCH_XYZ_R8(theta , myThid )        _EXCH_XYZ_R8(theta , myThid )
       _EXCH_XYZ_R8(gt , myThid )  
       _EXCH_XYZ_R8(gtNM1 , myThid )  
129    
130        CALL PLOT_FIELD_XYZRL( theta, 'Initial Temperature' ,        CALL PLOT_FIELD_XYZRL( theta, 'Initial Temperature' ,
131       &                       Nr, 1, myThid )       &                       Nr, 1, myThid )
132    
133        RETURN        RETURN

Legend:
Removed from v.1.1  
changed lines
  Added in v.1.2

  ViewVC Help
Powered by ViewVC 1.1.22