/[MITgcm]/MITgcm/pkg/opps/opps_interface.F
ViewVC logotype

Annotation of /MITgcm/pkg/opps/opps_interface.F

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


Revision 1.2 - (hide annotations) (download)
Wed Apr 6 18:44:50 2005 UTC (19 years, 3 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint57g_post, checkpoint57g_pre, checkpoint57f_post
Changes since 1.1: +1 -4 lines
use baseTime as time origin ; DIFF_BASE_MULTIPLE replaces DIFFERENT_MULTIPLE

1 jmc 1.2 C $Header: /u/gcmpack/MITgcm/pkg/opps/opps_interface.F,v 1.1 2004/09/16 11:28:16 mlosch Exp $
2 mlosch 1.1 C $Name: $
3    
4     #include "PACKAGES_CONFIG.h"
5     #include "CPP_OPTIONS.h"
6    
7     CBOP
8     C !ROUTINE: OPPS_INTERFACE
9     C !INTERFACE:
10     SUBROUTINE OPPS_INTERFACE(
11     I bi, bj, iMin, iMax, jMin, jMax,
12     I myTime, myIter, myThid )
13     C !DESCRIPTION: \bv
14     C *================================================================*
15     C | SUBROUTINE OPPS_INTERFACE |
16     C | o Driver for OPPS mixing scheme that can be called |
17     C | instead of convective_adjustment. |
18     C | Reference: Paluszkiewicz+Romea, Dynamics of Atmospheres and |
19     C | Oceans (1997) 26, pp. 95-130 |
20     C | o Support for passive tracers by joint treatment of |
21     C | active (theta, salt) and passive tracers. The array |
22     C | tracerLoc(Nr,2+PTRACERS_num) contains |
23     C | theta = tracerLoc(:,1), |
24     C | salt = tracerLoc(:,2), and |
25     C | ptracers = tracerLoc(:,3:PTRACERS_num+2). For this to |
26     C | work, the routine opps_calc had to be modified |
27     C | considerably. opps_calc is based on nlopps.F but there is |
28     C | is little left of the original (see opps_calc.F) |
29     C *================================================================*
30     C \ev
31    
32     C !USES:
33     IMPLICIT NONE
34     C == Global data ==
35     #include "SIZE.h"
36     #include "EEPARAMS.h"
37     #include "PARAMS.h"
38     #include "DYNVARS.h"
39     #include "GRID.h"
40     #include "OPPS.h"
41     #ifdef ALLOW_PTRACERS
42     #include "PTRACERS_SIZE.h"
43     #include "PTRACERS.h"
44     #endif
45     #ifdef ALLOW_TIMEAVE
46     #include "TIMEAVE_STATV.h"
47     #endif
48    
49     C !INPUT/OUTPUT PARAMETERS:
50     C == Routine arguments ==
51     C bi,bj,iMin,iMax,jMin,jMax,K - Loop counters
52     C myTime - Current time in simulation
53     C myIter - Current iteration in simulation
54     C myThid - Thread number of this instance of S/R CONVECT
55     INTEGER bi,bj,iMin,iMax,jMin,jMax
56     _RL myTime
57     INTEGER myIter
58     INTEGER myThid
59    
60     #ifdef ALLOW_OPPS
61    
62     C !LOCAL VARIABLES:
63     C == Local variables ==
64     C msgBuf - Informational/error meesage buffer
65     INTEGER nTracer
66     #ifdef ALLOW_PTRACERS
67     PARAMETER( nTracer = 2+PTRACERS_num )
68     #else /* not ALLOW_PTRACERS */
69     PARAMETER( nTracer = 2 )
70     #endif /* ALLOW_PTRACERS */
71     INTEGER i, j, K, kSurface, kMax, ktr, nTracerInUse
72     _RL tMin, tMax, sMin, sMax
73     _RL tMinNew, tMaxNew, sMinNew, sMaxNew
74     _RL thetaLoc(Nr), saltLoc(Nr), wVelLoc(Nr)
75     _RL tracerLoc(Nr,nTracer)
76     CHARACTER*(MAX_LEN_MBUF) msgBuf
77     CEOP
78    
79     C initialization
80     #ifdef ALLOW_PTRACERS
81     nTracerInUse = 2+PTRACERS_numInUse
82     #else
83     nTracerInUse = 2
84     #endif /* ALLOW_PTRACERS */
85     tMax = -1. _d 23
86     tMin = 1. _d 23
87     sMax = -1. _d 23
88     sMin = 1. _d 23
89     tMaxNew = -1. _d 23
90     tMinNew = 1. _d 23
91     sMaxNew = -1. _d 23
92     sMinNew = 1. _d 23
93     tMinNew = 1. _d 23
94     IF ( buoyancyRelation .eq. 'OCEANIC' ) THEN
95     kSurface = 1
96     ELSEIF ( buoyancyRelation .eq. 'OCEANICP' ) THEN
97     kSurface = Nr
98     ELSEIF ( buoyancyRelation .eq. 'ATMOSPHERIC' ) THEN
99     kSurface = Nr
100     ELSE
101     STOP 'OPPS_INTERFACE: We should never reach this point'
102     ENDIF
103     C re-initialize convection counter
104     DO k=1,Nr
105     DO J=1-Oly,sNy+Oly
106     DO I=1-Olx,sNx+Olx
107     OPPSconvectCount(I,J,K,bi,bj) = 0. _d 0
108     ENDDO
109     ENDDO
110     ENDDO
111    
112     C
113     DO J=jMin,jMax
114     DO I=iMin,iMax
115     IF ( hFacC(I,J,kSurface,bi,bj) .gt. 0. _d 0 ) THEN
116     IF ( useGCMwVel ) THEN
117     DO K=1,Nr
118     tracerLoc(K,1) = theta(I,J,K,bi,bj)
119     tracerLoc(K,2) = salt(I,J,K,bi,bj)
120     wVelLoc(K) = wVel(I,J,K,bi,bj)
121     ENDDO
122     ELSE
123     DO K=1,Nr
124     tracerLoc(K,1) = theta(I,J,K,bi,bj)
125     tracerLoc(K,2) = salt(I,J,K,bi,bj)
126     wVelLoc(K) = - VERTICAL_VELOCITY
127     ENDDO
128     ENDIF
129     #ifdef ALLOW_PTRACERS
130     DO ktr = 3, nTracerInUse
131     DO K=1,Nr
132     tracerLoc(K,ktr) = ptracer(I,J,K,bi,bj,ktr-2)
133     ENDDO
134     ENDDO
135     #endif /* ALLOW_PTRACERS */
136     #ifdef ALLOW_OPPS_DEBUG
137     IF ( OPPSdebugLevel .GE. debLevA ) THEN
138     C determine range of temperature and salinity
139     tMax = -1. d 23
140     tMin = 1. d 23
141     sMax = -1. d 23
142     sMin = 1. d 23
143     DO K=1,Nr
144     tMax = MAX(tracerLoc(K,1),tMax)
145     tMin = MAX(tracerLoc(K,1),tMin)
146     sMax = MAX(tracerLoc(K,2),sMax)
147     sMin = MAX(tracerLoc(K,2),sMin)
148     ENDDO
149     ENDIF
150     #endif /* ALLOW_OPPS_DEBUG */
151     kMax = kLowC(I,J,bi,bj)
152     CALL OPPS_CALC(
153     U tracerLoc,
154     I wVelLoc,kMax,nTracer,nTracerInUse,
155     I I,J,bi,bj,myTime,myIter,myThid)
156     #ifdef ALLOW_OPPS_DEBUG
157     IF ( OPPSdebugLevel .GE. debLevA ) THEN
158     C determine range of temperature and salinity
159     tMaxNew = -1. d 23
160     tMinNew = 1. d 23
161     sMaxNew = -1. d 23
162     sMinNew = 1. d 23
163     DO K=1,Nr
164     tMaxNew = MAX(tracerLoc(K,1),tMaxNew)
165     tMinNew = MAX(tracerLoc(K,1),tMinNew)
166     sMaxNew = MAX(tracerLoc(K,2),sMaxNew)
167     sMinNew = MAX(tracerLoc(K,2),sMinNew)
168     ENDDO
169     IF ( tMaxNew.GT.tMax .OR. tMinNew.LT.tMin .OR.
170     & sMaxNew.GT.sMax .OR. sMinNew.LT.sMIN ) THEN
171     WRITE(msgBuf,'(A,A)') 'OPPS_INTERFACE: theta or S-range is',
172     & ' larger than before mixing'
173     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
174     & SQUEEZE_RIGHT , 1)
175     WRITE(msgBuf,'(A,2I5)') ' for (i,j) = ', I,J
176     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
177     & SQUEEZE_RIGHT , 1)
178     ENDIF
179     ENDIF
180     #endif /* ALLOW_OPPS_DEBUG */
181     DO K=1,Nr
182     theta(I,J,K,bi,bj) = tracerLoc(K,1)
183     salt(I,J,K,bi,bj) = tracerLoc(K,2)
184     ENDDO
185     #ifdef ALLOW_PTRACERS
186     DO ktr = 3, nTracerInUse
187     DO K=1,Nr
188     ptracer(I,J,K,bi,bj,ktr-2) = tracerLoc(K,ktr)
189     ENDDO
190     ENDDO
191     #endif /* ALLOW_PTRACERS */
192     ENDIF
193     ENDDO
194     ENDDO
195     #endif /* ALLOW_OPPS */
196    
197     RETURN
198     END

  ViewVC Help
Powered by ViewVC 1.1.22