/[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.4 - (hide annotations) (download)
Wed Feb 14 22:51:27 2001 UTC (23 years, 3 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint36
Changes since 1.3: +8 -2 lines
recover (after checkpoint35) time average output

1 jmc 1.4 C $Header: /u/gcmpack/models/MITgcmUV/model/src/the_correction_step.F,v 1.3 2001/02/07 16:47:50 adcroft Exp $
2     C Tag $Name: checkpoint35 $
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     _RL etaSurfX(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
38     _RL etaSurfY(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
39     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     etaSurfX(i,j)=0.
51     etaSurfY(i,j)=0.
52     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     C- Calculate gradient of surface pressure
75     CALL CALC_GRAD_ETA_SURF(
76     I bi,bj,iMin,iMax,jMin,jMax,
77     O etaSurfX,etaSurfY,
78     I myThid )
79    
80     C-- Loop over all layers, top to bottom
81     DO K=1,Nr
82    
83     C- Update velocity fields: V(n) = V** - dt * grad Eta
84 adcroft 1.3 IF (momStepping)
85     & CALL CORRECTION_STEP(
86 adcroft 1.2 I bi,bj,iMin,iMax,jMin,jMax,K,
87     I etaSurfX,etaSurfY,myTime,myThid )
88    
89     C- Update tracer fields: T(n) = T**, Gt(n-1) = Gt(n)
90     IF (tempStepping)
91     & CALL CYCLE_TRACER(
92     I bi,bj,iMin,iMax,jMin,jMax,K,
93     U theta,gT,gTNm1,
94     I myTime,myThid )
95     IF (saltStepping)
96     & CALL CYCLE_TRACER(
97     I bi,bj,iMin,iMax,jMin,jMax,K,
98     U salt,gS,gSNm1,
99     I myTime,myThid )
100    
101     #ifdef ALLOW_OBCS
102     #ifdef ALLOW_AUTODIFF_TAMC
103     CADJ STORE uvel (:,:,k,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte
104     CADJ STORE vvel (:,:,k,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte
105     CADJ STORE theta(:,:,k,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte
106     CADJ STORE salt (:,:,k,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte
107     #endif /* ALLOW_AUTODIFF_TAMC */
108     IF (useOBCS) THEN
109     CALL OBCS_APPLY_UV(bi,bj,K,uVel,vVel,myThid)
110     ENDIF
111     #endif /* ALLOW_OBCS */
112    
113     C-- End DO K=1,Nr
114     ENDDO
115    
116     C-- Convectively adjust new fields to be statically stable
117     CALL CONVECTIVE_ADJUSTMENT(
118     I bi, bj, iMin, iMax, jMin, jMax,
119     I myTime, myIter, myThid )
120 jmc 1.4
121     #ifdef INCLUDE_DIAGNOSTICS_INTERFACE_CODE
122     IF (taveFreq.GT.0.) THEN
123     CALL DO_TIME_AVERAGES(myTime, myIter, bi, bj, myThid)
124     ENDIF
125     #endif /* INCLUDE_DIAGNOSTICS_INTERFACE_CODE */
126 adcroft 1.2
127     ENDDO
128     ENDDO
129    
130     RETURN
131     END

  ViewVC Help
Powered by ViewVC 1.1.22