/[MITgcm]/MITgcm/model/src/the_correction_step.F
ViewVC logotype

Annotation of /MITgcm/model/src/the_correction_step.F

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


Revision 1.6 - (hide annotations) (download)
Thu Mar 8 20:32:35 2001 UTC (23 years, 3 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint37
Branch point for: pre38
Changes since 1.5: +9 -9 lines
calc_grad_phi_surf (replace calc_grad_eta_surf) to get directly gradient of Phi_Surf

1 jmc 1.6 C $Header: /u/gcmpack/models/MITgcmUV/model/src/the_correction_step.F,v 1.5 2001/03/06 17:15:28 jmc Exp $
2 jmc 1.5 C Tag $Name: $
3 adcroft 1.2
4     #include "CPP_OPTIONS.h"
5    
6     SUBROUTINE THE_CORRECTION_STEP(myTime, myIter, myThid)
7     C /==========================================================\
8     C | SUBROUTINE THE_CORRECTION_STEP |
9     C |==========================================================|
10     C | |
11     C | U*,V* (contained in gUnm1,gVnm1) have the surface |
12     C | pressure gradient term added and the result stored in |
13     C | U,V (contained in uVel, vVel) |
14     C | |
15     C | T* (contained in gTnm1) is copied to T (theta) |
16     C | |
17     C | S* (contained in gSnm1) is copied to S (salt) |
18     C | |
19     C \==========================================================/
20     IMPLICIT NONE
21    
22     C == Global variables ===
23     #include "SIZE.h"
24     #include "EEPARAMS.h"
25     #include "PARAMS.h"
26     #include "DYNVARS.h"
27    
28     C == Routine arguments ==
29     C myTime - Current time in simulation
30     C myIter - Current iteration number in simulation
31     C myThid - Thread number for this instance of the routine.
32     _RL myTime
33     INTEGER myIter
34     INTEGER myThid
35    
36     C == Local variables
37 jmc 1.6 _RL phiSurfX(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
38     _RL phiSurfY(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
39 adcroft 1.2 INTEGER iMin,iMax
40     INTEGER jMin,jMax
41     INTEGER bi,bj
42     INTEGER k,i,j
43    
44     DO bj=myByLo(myThid),myByHi(myThid)
45     DO bi=myBxLo(myThid),myBxHi(myThid)
46    
47     C-- Set up work arrays that need valid initial values
48     DO j=1-OLy,sNy+OLy
49     DO i=1-OLx,sNx+OLx
50 jmc 1.6 phiSurfX(i,j)=0.
51     phiSurfY(i,j)=0.
52 adcroft 1.2 ENDDO
53     ENDDO
54    
55     C The arrays used for time stepping are cycled.
56     C
57     C Tracers:
58     C T(n) = Gt(n-1)
59     C Gt(n-1) = Gt(n)
60     C Momentum:
61     C V(n) = Gv(n-1) - dt * grad Eta
62     C Gv(n-1) = Gv(n)
63     C
64     C Static stability is calculated and the tracers are
65     C convective adjusted where statically unstable.
66    
67     C Loop range: Gradients of Eta are evaluated so valid
68     C range is all but first row and column in overlaps.
69     iMin = 1-OLx+1
70     iMax = sNx+OLx
71     jMin = 1-OLy+1
72     jMax = sNy+OLy
73    
74 jmc 1.6 C- Calculate gradient of surface Potentiel
75     CALL CALC_GRAD_PHI_SURF(
76 adcroft 1.2 I bi,bj,iMin,iMax,jMin,jMax,
77 jmc 1.5 I etaN,
78 jmc 1.6 O phiSurfX,phiSurfY,
79 adcroft 1.2 I myThid )
80    
81     C-- Loop over all layers, top to bottom
82     DO K=1,Nr
83    
84     C- Update velocity fields: V(n) = V** - dt * grad Eta
85 adcroft 1.3 IF (momStepping)
86     & CALL CORRECTION_STEP(
87 adcroft 1.2 I bi,bj,iMin,iMax,jMin,jMax,K,
88 jmc 1.6 I phiSurfX,phiSurfY,myTime,myThid )
89 adcroft 1.2
90     C- Update tracer fields: T(n) = T**, Gt(n-1) = Gt(n)
91     IF (tempStepping)
92     & CALL CYCLE_TRACER(
93     I bi,bj,iMin,iMax,jMin,jMax,K,
94     U theta,gT,gTNm1,
95     I myTime,myThid )
96     IF (saltStepping)
97     & CALL CYCLE_TRACER(
98     I bi,bj,iMin,iMax,jMin,jMax,K,
99     U salt,gS,gSNm1,
100     I myTime,myThid )
101    
102     #ifdef ALLOW_OBCS
103     #ifdef ALLOW_AUTODIFF_TAMC
104     CADJ STORE uvel (:,:,k,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte
105     CADJ STORE vvel (:,:,k,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte
106     CADJ STORE theta(:,:,k,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte
107     CADJ STORE salt (:,:,k,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte
108     #endif /* ALLOW_AUTODIFF_TAMC */
109     IF (useOBCS) THEN
110     CALL OBCS_APPLY_UV(bi,bj,K,uVel,vVel,myThid)
111     ENDIF
112     #endif /* ALLOW_OBCS */
113    
114     C-- End DO K=1,Nr
115     ENDDO
116    
117     C-- Convectively adjust new fields to be statically stable
118     CALL CONVECTIVE_ADJUSTMENT(
119     I bi, bj, iMin, iMax, jMin, jMax,
120     I myTime, myIter, myThid )
121 jmc 1.4
122 jmc 1.5 #ifdef ALLOW_TIMEAVE
123 jmc 1.4 IF (taveFreq.GT.0.) THEN
124 jmc 1.5 CALL TIMEAVE_STATVARS(myTime, myIter, bi, bj, myThid)
125 jmc 1.4 ENDIF
126 jmc 1.5 #endif /* ALLOW_TIMEAVE */
127 adcroft 1.2
128     ENDDO
129     ENDDO
130    
131     RETURN
132     END

  ViewVC Help
Powered by ViewVC 1.1.22