/[MITgcm]/MITgcm/pkg/ptracers/ptracers_implicit.F
ViewVC logotype

Contents of /MITgcm/pkg/ptracers/ptracers_implicit.F

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


Revision 1.10 - (show annotations) (download)
Thu Mar 8 17:13:31 2012 UTC (12 years, 3 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64q, checkpoint64p, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63k, checkpoint64
Changes since 1.9: +4 -1 lines
-only step forward tracer if PTRACERS_StepFwd(iTr)=T

1 C $Header: /u/gcmpack/MITgcm/pkg/ptracers/ptracers_implicit.F,v 1.9 2011/12/01 14:27:53 jmc Exp $
2 C $Name: $
3
4 #include "PTRACERS_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: PTRACERS_IMPLICIT
8
9 C !INTERFACE: ==========================================================
10 SUBROUTINE PTRACERS_IMPLICIT(
11 U kappaRk,
12 I recip_hFac,
13 I bi, bj, myTime, myIter, myThid )
14
15 C !DESCRIPTION:
16 C Calls the implicit vertical advection/diffusion routine
17 C for each passive tracer.
18 C And apply open boundary conditions for each passive tracer
19 C Note: would be better to apply OBC in a dedicated S/R ;
20 C can be done here assuming no other contribution modify passive
21 C tracer after implicit vertical diffus/advect is applied.
22
23 C !USES: ===============================================================
24 IMPLICIT NONE
25 #include "SIZE.h"
26 #include "EEPARAMS.h"
27 #ifdef ALLOW_LONGSTEP
28 #include "LONGSTEP_PARAMS.h"
29 #include "LONGSTEP.h"
30 #endif
31 #include "PTRACERS_SIZE.h"
32 #include "PTRACERS_PARAMS.h"
33 #include "PTRACERS_START.h"
34 #include "PTRACERS_FIELDS.h"
35 #include "PARAMS.h"
36 #include "GRID.h"
37 #include "GAD.h"
38 #include "DYNVARS.h"
39 #ifdef ALLOW_AUTODIFF_TAMC
40 # include "tamc.h"
41 # include "tamc_keys.h"
42 #endif
43
44 C !INPUT PARAMETERS: ===================================================
45 C recip_hFac :: Inverse of cell open-depth factor
46 C bi,bj :: tile indices
47 C myTime :: time in simulation
48 C myIter :: iteration number in simulation
49 C myThid :: thread number
50 _RS recip_hFac(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
51 INTEGER bi,bj
52 _RL myTime
53 INTEGER myIter
54 INTEGER myThid
55
56 C !OUTPUT PARAMETERS: ==================================================
57 C KappaRk :: vertical diffusion coefficient
58 _RL kappaRk(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
59
60 #ifdef ALLOW_PTRACERS
61
62 C !LOCAL VARIABLES: ====================================================
63 C iTracer :: tracer index
64 INTEGER iTracer
65 INTEGER iMin,iMax,jMin,jMax
66 INTEGER GAD_TR
67 CEOP
68
69 iMin=0
70 iMax=sNx+1
71 jMin=0
72 jMax=sNy+1
73
74 C Loop over tracers
75 DO iTracer=1,PTRACERS_numInUse
76 IF ( PTRACERS_StepFwd(iTracer) ) THEN
77
78 #ifdef ALLOW_AUTODIFF_TAMC
79 act0 = iTracer - 1
80 max0 = PTRACERS_num
81 act1 = bi - myBxLo(myThid)
82 max1 = myBxHi(myThid) - myBxLo(myThid) + 1
83 act2 = bj - myByLo(myThid)
84 max2 = myByHi(myThid) - myByLo(myThid) + 1
85 act3 = myThid - 1
86 max3 = nTx*nTy
87 act4 = ikey_dynamics - 1
88 iptrkey = (act0 + 1)
89 & + act1*max0
90 & + act2*max0*max1
91 & + act3*max0*max1*max2
92 & + act4*max0*max1*max2*max3
93 #endif /* ALLOW_AUTODIFF_TAMC */
94
95 GAD_TR = GAD_TR1 + iTracer - 1
96 IF ( implicitDiffusion ) THEN
97 CALL CALC_3D_DIFFUSIVITY(
98 I bi,bj,iMin,iMax,jMin,jMax,
99 I GAD_TR,
100 I PTRACERS_useGMRedi(iTracer),PTRACERS_useKPP(iTracer),
101 O kappaRk,
102 I myThid)
103 ENDIF
104
105 #ifdef ALLOW_AUTODIFF_TAMC
106 CADJ STORE kappaRk(:,:,:) = comlev1_bibj_ptracers,
107 CADJ & key=iptrkey, byte=isbyte
108 CADJ STORE gPtr(:,:,:,bi,bj,iTracer) = comlev1_bibj_ptracers,
109 CADJ & key=iptrkey, byte=isbyte
110 #endif /* ALLOW_AUTODIFF_TAMC */
111
112 #ifdef INCLUDE_IMPLVERTADV_CODE
113 IF ( PTRACERS_ImplVertAdv(iTracer) ) THEN
114
115 CALL GAD_IMPLICIT_R(
116 I PTRACERS_ImplVertAdv(iTracer),
117 I PTRACERS_advScheme(iTracer), GAD_TR,
118 I PTRACERS_dTLev, kappaRk, recip_hFac,
119 #ifdef ALLOW_LONGSTEP
120 I LS_wVel,
121 #else
122 I wVel,
123 #endif
124 I pTracer(1-OLx,1-OLy,1,1,1,iTracer),
125 U gPtr(1-OLx,1-OLy,1,1,1,iTracer),
126 I bi, bj, myTime, myIter, myThid )
127
128 ELSEIF ( implicitDiffusion ) THEN
129 #else /* INCLUDE_IMPLVERTADV_CODE */
130 IF ( implicitDiffusion ) THEN
131 #endif /* INCLUDE_IMPLVERTADV_CODE */
132
133 CALL IMPLDIFF(
134 I bi, bj, iMin, iMax, jMin, jMax,
135 I GAD_TR, kappaRk, recip_hFac,
136 U gPtr(1-OLx,1-OLy,1,1,1,iTracer),
137 I myThid )
138 ENDIF
139
140 #ifdef ALLOW_OBCS
141 C-- Apply open boundary conditions
142 IF ( useOBCS ) THEN
143 CALL OBCS_APPLY_PTRACER(
144 I bi, bj, 0, iTracer,
145 U gPtr(1-OLx,1-OLy,1,bi,bj,iTracer),
146 I myThid )
147 ENDIF
148 #endif /* ALLOW_OBCS */
149
150 C End of tracer loop
151 ENDIF
152 ENDDO
153
154 #endif /* ALLOW_PTRACERS */
155
156 RETURN
157 END

  ViewVC Help
Powered by ViewVC 1.1.22