/[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.3 - (show annotations) (download)
Fri Mar 25 00:29:17 2005 UTC (19 years, 2 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint57t_post, checkpoint57o_post, checkpoint57f_post, checkpoint57s_post, checkpoint57k_post, checkpoint57g_post, checkpoint57i_post, checkpoint57m_post, checkpoint57g_pre, checkpoint57h_post, checkpoint57f_pre, checkpoint57r_post, checkpoint57h_done, checkpoint57n_post, checkpoint57p_post, checkpoint57q_post, checkpoint57j_post, checkpoint57h_pre, checkpoint57l_post
Changes since 1.2: +3 -1 lines
added storing of kappaRTr, kappaRk

1 C $Header: /u/gcmpack/MITgcm/pkg/ptracers/ptracers_implicit.F,v 1.2 2004/12/16 23:20:48 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 bi, bj, myTime, myIter, myThid )
13
14 C !DESCRIPTION:
15 C Calls the implicit vertical advection/diffusion routine
16 C for each passive tracer.
17
18 C !USES: ===============================================================
19 IMPLICIT NONE
20 #include "SIZE.h"
21 #include "EEPARAMS.h"
22 #include "PTRACERS_SIZE.h"
23 #include "PTRACERS.h"
24 #include "PARAMS.h"
25 #include "GRID.h"
26 #include "GAD.h"
27 #include "DYNVARS.h"
28 #ifdef ALLOW_AUTODIFF_TAMC
29 # include "tamc.h"
30 # include "tamc_keys.h"
31 #endif
32
33 C !INPUT PARAMETERS: ===================================================
34 C bi,bj :: tile indices
35 C myTime :: time in simulation
36 C myIter :: iteration number in simulation
37 C myThid :: thread number
38 INTEGER bi,bj
39 _RL myTime
40 INTEGER myIter
41 INTEGER myThid
42
43 C !OUTPUT PARAMETERS: ==================================================
44 C KappaRk :: vertical diffusion coefficient
45 _RL kappaRk(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
46
47 #ifdef ALLOW_PTRACERS
48
49 C !LOCAL VARIABLES: ====================================================
50 C iTracer :: tracer index
51 INTEGER iTracer
52 INTEGER iMin,iMax,jMin,jMax
53 INTEGER GAD_TR
54 CEOP
55
56 iMin=0
57 iMax=sNx+1
58 jMin=0
59 jMax=sNy+1
60
61 C Loop over tracers
62 DO iTracer=1,PTRACERS_numInUse
63
64 #ifdef ALLOW_AUTODIFF_TAMC
65 act0 = iTracer - 1
66 max0 = PTRACERS_num
67 act1 = bi - myBxLo(myThid)
68 max1 = myBxHi(myThid) - myBxLo(myThid) + 1
69 act2 = bj - myByLo(myThid)
70 max2 = myByHi(myThid) - myByLo(myThid) + 1
71 act3 = myThid - 1
72 max3 = nTx*nTy
73 act4 = ikey_dynamics - 1
74 iptrkey = (act0 + 1)
75 & + act1*max0
76 & + act2*max0*max1
77 & + act3*max0*max1*max2
78 & + act4*max0*max1*max2*max3
79 #endif /* ALLOW_AUTODIFF_TAMC */
80
81 GAD_TR = GAD_TR1 + iTracer - 1
82 IF ( implicitDiffusion ) THEN
83 CALL CALC_3D_DIFFUSIVITY(
84 I bi,bj,iMin,iMax,jMin,jMax,
85 I GAD_TR,
86 I PTRACERS_useGMRedi(iTracer),PTRACERS_useKPP(iTracer),
87 O kappaRk,
88 I myThid)
89 ENDIF
90
91 #ifdef ALLOW_AUTODIFF_TAMC
92 CADJ STORE kappaRk(:,:,:) = comlev1_bibj_ptracers,
93 CADJ & key=iptrkey, byte=isbyte
94 CADJ STORE gPtr(:,:,:,bi,bj,iTracer) = comlev1_bibj_ptracers,
95 CADJ & key=iptrkey, byte=isbyte
96 #endif /* ALLOW_AUTODIFF_TAMC */
97
98 #ifdef INCLUDE_IMPLVERTADV_CODE
99 IF ( PTRACERS_ImplVertAdv(iTracer) ) THEN
100
101 CALL GAD_IMPLICIT_R(
102 I PTRACERS_ImplVertAdv(iTracer),
103 I PTRACERS_advScheme(iTracer), GAD_TR,
104 I kappaRk, wVel, pTracer(1-Olx,1-Oly,1,1,1,iTracer),
105 U gPtr(1-Olx,1-Oly,1,1,1,iTracer),
106 I bi, bj, myTime, myIter, myThid )
107
108 ELSEIF ( implicitDiffusion ) THEN
109 #else /* INCLUDE_IMPLVERTADV_CODE */
110 IF ( implicitDiffusion ) THEN
111 #endif /* INCLUDE_IMPLVERTADV_CODE */
112
113 CALL IMPLDIFF(
114 I bi, bj, iMin, iMax, jMin, jMax,
115 I GAD_TR, kappaRk, recip_HFacC,
116 U gPtr(1-Olx,1-Oly,1,1,1,iTracer),
117 I myThid )
118
119 ENDIF
120 C End of tracer loop
121 ENDDO
122
123 #endif /* ALLOW_PTRACERS */
124
125 RETURN
126 END

  ViewVC Help
Powered by ViewVC 1.1.22