/[MITgcm]/MITgcm/verification/advect_xz/code/ini_theta.F
ViewVC logotype

Diff of /MITgcm/verification/advect_xz/code/ini_theta.F

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

revision 1.1 by adcroft, Fri Sep 28 02:28:10 2001 UTC revision 1.2 by jmc, Fri Apr 15 22:10:13 2005 UTC
# Line 3  C $Name$ Line 3  C $Name$
3    
4  #include "CPP_OPTIONS.h"  #include "CPP_OPTIONS.h"
5    
6  CStartOfInterface  CBOP
7    C     !ROUTINE: INI_THETA
8    C     !INTERFACE:
9        SUBROUTINE INI_THETA( myThid )        SUBROUTINE INI_THETA( myThid )
10  C     /==========================================================\  C     !DESCRIPTION: \bv
11  C     | SUBROUTINE INI_THETA                                     |  C     *==========================================================*
12  C     | o Set model initial temperature field.                   |  C     | SUBROUTINE INI_THETA                                      
13  C     |==========================================================|  C     | o Set model initial temperature field.                    
14  C     | There are several options for setting the initial        |  C     *==========================================================*
15  C     | temperature file                                         |  C     | There are several options for setting the initial        
16  C     |  1. Inline code                                          |  C     | temperature file                                          
17  C     |  2. Vertical profile ( uniform T in X and Y )            |  C     |  1. Inline code                                          
18  C     |  3. Three-dimensional data from a file. For example from |  C     |  2. Vertical profile ( uniform T in X and Y )            
19  C     |     Levitus or from a checkpoint file from a previous    |  C     |  3. Three-dimensional data from a file. For example from  
20  C     |     integration.                                         |  C     |     Levitus or from a checkpoint file from a previous    
21  C     | In addition to setting the temperature field we also     |  C     |     integration.                                          
22  C     | set the initial temperature tendency term here.          |  C     | In addition to setting the temperature field we also      
23  C     \==========================================================/  C     | set the initial temperature tendency term here.          
24        IMPLICIT NONE  C     *==========================================================*
25    C     \ev
26    
27    C     !USES:
28          IMPLICIT NONE
29  C     === Global variables ===  C     === Global variables ===
30  #include "SIZE.h"  #include "SIZE.h"
31  #include "EEPARAMS.h"  #include "EEPARAMS.h"
# Line 28  C     === Global variables === Line 33  C     === Global variables ===
33  #include "GRID.h"  #include "GRID.h"
34  #include "DYNVARS.h"  #include "DYNVARS.h"
35    
36    C     !INPUT/OUTPUT PARAMETERS:
37  C     == Routine arguments ==  C     == Routine arguments ==
38  C     myThid -  Number of this instance of INI_THETA  C     myThid -  Number of this instance of INI_THETA
39        INTEGER myThid        INTEGER myThid
 CEndOfInterface  
40    
41    C     !LOCAL VARIABLES:
42  C     == Local variables ==  C     == Local variables ==
 C     iC, jC - Center of domain  
 C     iD, jD - Disitance from domain center.  
 C     rad    - Radius of initial patch  
 C     rD     - Radial displacement of point I,J  
 C     iG, jG - Global coordinate index  
43  C     bi,bj  - Loop counters  C     bi,bj  - Loop counters
44  C     I,J,K  C     I,J,K
45        INTEGER iC, jC, iD, jD  C     rD     - Radial displacement of point I,J
       INTEGER iG, jG  
46        INTEGER bi, bj        INTEGER bi, bj
47        INTEGER I, J, K, localWarnings        INTEGER I, J, K, localWarnings
48        _RL     rad, rD        _RL     Tfreezing
49          _RL     rD
50        CHARACTER*(MAX_LEN_MBUF) msgBuf        CHARACTER*(MAX_LEN_MBUF) msgBuf
51    CEOP
52    
53        _BARRIER  C--   Initialise temperature field to the vertical reference profile
54          DO bj = myByLo(myThid), myByHi(myThid)
55        IF ( hydrogThetaFile .EQ. ' ' ) THEN         DO bi = myBxLo(myThid), myBxHi(myThid)
56  C--    Example 1          DO K=1,Nr
57             DO J=1-Oly,sNy+Oly
58              DO I=1-Olx,sNx+Olx
59               theta(I,J,K,bi,bj) = tRef(K)
60              ENDDO
61             ENDDO
62  C--    Initialise temperature field to a circular patch.  C--    Initialise temperature field to a circular patch.
63         iC  = Nx/2           DO J=1,sNy
64         jC  = Ny/2            DO I=1,sNx
        rad = MIN(Ny/8,Nx/8)  
        DO bj = myByLo(myThid), myByHi(myThid)  
         DO bi = myBxLo(myThid), myBxHi(myThid)  
          DO K=1,Nr  
           DO J=1,sNy  
            DO I=1,sNx  
65              rD=sqrt( (XC(i,j,bi,bj)-40.E3)**2              rD=sqrt( (XC(i,j,bi,bj)-40.E3)**2
66       &              +(YC(i,j,bi,bj)-40.E3)**2       &              +(YC(i,j,bi,bj)-40.E3)**2
67       &              +(RC(k)+50.E3)**2 )       &              +(RC(k)+50.E3)**2 )
68              theta(i,j,k,bi,bj)=exp(-0.5*( rD/20.E3 )**2 )              theta(i,j,k,bi,bj)=exp(-0.5*( rD/20.E3 )**2 )
            ENDDO  
69            ENDDO            ENDDO
70           ENDDO           ENDDO
71          ENDDO          ENDDO
72         ENDDO         ENDDO
73        ELSE        ENDDO
74    
75          IF ( hydrogThetaFile .NE. ' ' ) THEN
76         _BEGIN_MASTER( myThid )         _BEGIN_MASTER( myThid )
77         CALL READ_FLD_XYZ_RL( hydrogThetaFile, ' ', theta, 0, myThid )         CALL READ_FLD_XYZ_RL( hydrogThetaFile, ' ', theta, 0, myThid )
78         _END_MASTER(myThid)         _END_MASTER(myThid)
79           _EXCH_XYZ_R8(theta,myThid)
80        ENDIF        ENDIF
81  C     Set initial tendency terms  
82    C--   Apply mask and test consistency
83        localWarnings=0        localWarnings=0
84        DO bj = myByLo(myThid), myByHi(myThid)        DO bj = myByLo(myThid), myByHi(myThid)
85         DO bi = myBxLo(myThid), myBxHi(myThid)         DO bi = myBxLo(myThid), myBxHi(myThid)
86          DO K=1,Nr          DO K=1,Nr
87           DO J=1,sNy           DO J=1-Oly,sNy+Oly
88            DO I=1,sNx            DO I=1-Olx,sNx+Olx
89             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  
90            ENDDO            ENDDO
91           ENDDO           ENDDO
92             IF ( tRef(k).NE.0. ) THEN
93              DO J=1,sNy
94               DO I=1,sNx
95                IF (  maskC(I,J,K,bi,bj).NE.0.
96         &      .AND. theta(I,J,K,bi,bj).EQ.0. ) THEN
97                  localWarnings=localWarnings+1
98                ENDIF
99               ENDDO
100              ENDDO
101             ENDIF
102          ENDDO          ENDDO
103         ENDDO         ENDDO
104        ENDDO        ENDDO
# Line 101  C     Set initial tendency terms Line 109  C     Set initial tendency terms
109         CALL PRINT_ERROR( msgBuf , myThid)         CALL PRINT_ERROR( msgBuf , myThid)
110         STOP 'ABNORMAL END: S/R INI_THETA'         STOP 'ABNORMAL END: S/R INI_THETA'
111        ENDIF        ENDIF
 C  
       _EXCH_XYZ_R8(theta , myThid )  
       _EXCH_XYZ_R8(gt , myThid )  
       _EXCH_XYZ_R8(gtNM1 , myThid )  
112    
113        CALL PLOT_FIELD_XYZRL( theta, 'Initial Temperature' ,  C--   Check that there are no values of temperature below freezing point.
114          Tfreezing=-1.9 _d 0
115          IF ( allowFreezing ) THEN
116           DO bj = myByLo(myThid), myByHi(myThid)
117            DO bi = myBxLo(myThid), myBxHi(myThid)
118             DO K=1,Nr
119              DO J=1-Oly,sNy+Oly
120               DO I=1-Olx,sNx+Olx
121                IF (theta(I,J,k,bi,bj) .LT. Tfreezing) THEN
122                   theta(I,J,K,bi,bj) = Tfreezing
123                ENDIF
124               ENDDO
125              ENDDO
126             ENDDO
127            ENDDO
128           ENDDO
129          ENDIF
130    
131          _EXCH_XYZ_R8(theta,myThid)
132    
133          CALL PLOT_FIELD_XYZRL( theta, 'Initial Temperature' ,
134       &                       Nr, 1, myThid )       &                       Nr, 1, myThid )
135    
136        RETURN        RETURN

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

  ViewVC Help
Powered by ViewVC 1.1.22