/[MITgcm]/MITgcm/verification/hs94.cs-32x32x5/code/ini_theta.F
ViewVC logotype

Diff of /MITgcm/verification/hs94.cs-32x32x5/code/ini_theta.F

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

revision 1.3 by adcroft, Wed Jun 6 19:46:43 2001 UTC revision 1.8 by jmc, Sun Sep 27 23:49:28 2009 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 ==  C     == Functions ==
44        Real*8  PORT_RAND  c     real*8  PORT_RAND
45    c     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        INTEGER I, J, K, localWarnings
53        _RL     term1,term2,thetaLim,thetaEq        _RL     term1,term2,thetaLim,thetaEq
54        _RL     thKappa        CHARACTER*(MAX_LEN_MBUF) msgBuf
55    CEOP
       _BARRIER  
56    
57        J = 99+myBxLo(myThid)+nPx*myByLo(myThid)        J = 99+myBxLo(myThid)+nPx*myByLo(myThid)
58  c     CALL SRAND( J )  c     CALL SRAND( J )
59    c     seed = j
60    
61        IF ( hydrogThetaFile .EQ. ' ' ) THEN        IF ( hydrogThetaFile .EQ. ' ' ) THEN
62  C--    Initialise temperature field to Held & Saurez equilibrium theta  C--    Initialise temperature field to Held & Saurez equilibrium theta
63         DO bj = myByLo(myThid), myByHi(myThid)         DO bj = myByLo(myThid), myByHi(myThid)
64          DO bi = myBxLo(myThid), myBxHi(myThid)          DO bi = myBxLo(myThid), myBxHi(myThid)
65           DO K=1,Nr           DO K=1,Nr
66            Ro_SeaLevel=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)/Ro_SeaLevel)**thKappa)  
67            DO J=1,sNy            DO J=1,sNy
68             DO I=1,sNx             DO I=1,sNx
69             term1=60. _d 0*(sin(yC(I,J,bi,bj)*deg2rad)**2)              term1=60. _d 0*(sin(yC(I,J,bi,bj)*deg2rad)**2)
70             term2=10. _d 0*log((rC(K)/Ro_SeaLevel))              term2=10. _d 0*log((rC(K)/atm_po))
71       &              *(cos(yC(I,J,bi,bj)*deg2rad)**2)       &              *(cos(yC(I,J,bi,bj)*deg2rad)**2)
72             thetaEq=315. _d 0-term1-term2              thetaEq=315. _d 0-term1-term2
73              theta(I,J,K,bi,bj) = MAX( thetaLim, thetaEq )              theta(I,J,K,bi,bj) = MAX( thetaLim, thetaEq )
74  c    &                          + 0.01*(RAND()-0.5)  c    &                          + 0.01*(RAND()-0.5)
75  c    &                          + 0.01*(PORT_RAND()-0.5)  c    &                          + 0.01*(PORT_RAND(seed)-0.5)
76  c           theta(I,J,K,bi,bj) = tRef(K)  c           theta(I,J,K,bi,bj) = tRef(K)
77             ENDDO             ENDDO
78            ENDDO            ENDDO
79           ENDDO           ENDDO
         ENDDO  
        ENDDO  
        DO bj = myByLo(myThid), myByHi(myThid)  
         DO bi = myBxLo(myThid), myBxHi(myThid)  
          DO K=1,Nr  
           DO J=1,sNy  
80  #ifdef ALLOW_ZONAL_FILT  #ifdef ALLOW_ZONAL_FILT
81  C--   Zonal FFT filter initial conditions  C--   Zonal FFT filter initial conditions
82             CALL ZONAL_FILTER(           IF (useZONAL_FILT) THEN
83       U      theta, hFacC,            CALL ZONAL_FILTER(
84       I      1, sNy, k, k, bi, bj, 1, myThid)       U                       theta(1-OLx,1-OLy,1,bi,bj),
85  #endif /* INCLUDE_LAT_CIRC_FFT_FILTER_CODE */       I                       hFacC(1-OLx,1-OLy,1,bi,bj),
86            ENDDO       I                       1, sNy, Nr, bi, bj, 1, myThid )
87           ENDDO           ENDIF
88    #endif /* ALLOW_ZONAL_FILT */
89          ENDDO          ENDDO
90         ENDDO         ENDDO
91        ELSE        ELSE
        _BEGIN_MASTER( myThid )  
92         CALL READ_FLD_XYZ_RL( hydrogThetaFile, ' ', theta, 0, myThid )         CALL READ_FLD_XYZ_RL( hydrogThetaFile, ' ', theta, 0, myThid )
        _END_MASTER(myThid)  
93        ENDIF        ENDIF
94  C     Set initial tendency terms  C--   Apply mask and test consistency
95          localWarnings=0
96        DO bj = myByLo(myThid), myByHi(myThid)        DO bj = myByLo(myThid), myByHi(myThid)
97         DO bi = myBxLo(myThid), myBxHi(myThid)         DO bi = myBxLo(myThid), myBxHi(myThid)
98          DO K=1,Nr          DO K=1,Nr
99           DO J=1,sNy           DO J=1-Oly,sNy+Oly
100            DO I=1,sNx            DO I=1-Olx,sNx+Olx
101             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.  
102            ENDDO            ENDDO
103           ENDDO           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          ENDDO
115         ENDDO         ENDDO
116        ENDDO        ENDDO
117  C        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_R8(theta , myThid )        _EXCH_XYZ_RL(theta , myThid )
       _EXCH_XYZ_R8(gt , myThid )  
       _EXCH_XYZ_R8(gtNM1 , myThid )  
126    
127        CALL PLOT_FIELD_XYZRL( theta, 'Initial Temperature' ,        IF (debugMode) THEN
128       &                       Nr, 1, myThid )          CALL PLOT_FIELD_XYZRL( theta, 'Initial Temperature' ,
129         &                         Nr, 1, myThid )
130          ENDIF
131    
132        RETURN        RETURN
133        END        END

Legend:
Removed from v.1.3  
changed lines
  Added in v.1.8

  ViewVC Help
Powered by ViewVC 1.1.22