/[MITgcm]/MITgcm/pkg/matrix/matrix_store_tendency.F
ViewVC logotype

Contents of /MITgcm/pkg/matrix/matrix_store_tendency.F

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


Revision 1.6 - (show annotations) (download)
Mon Aug 11 20:29:06 2014 UTC (9 years, 9 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, HEAD
Changes since 1.5: +13 -16 lines
pass updated tracer field as argument to S/R MATRIX_STORE_TENDENCY_EXP

1 C $Header: /u/gcmpack/MITgcm/pkg/matrix/matrix_store_tendency.F,v 1.5 2013/12/27 15:53:36 jmc Exp $
2 C $Name: $
3
4 #include "MATRIX_OPTIONS.h"
5
6 C-- File matrix_store_tendency.F:
7 C Contents
8 C o MATRIX_STORE_TENDENCY_EXP
9 C o MATRIX_STORE_TENDENCY_IMP
10
11 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
12 CBOP
13 C !ROUTINE: MATRIX_STORE_TENDENCY_EXP
14
15 C !INTERFACE: ==========================================================
16 SUBROUTINE MATRIX_STORE_TENDENCY_EXP(
17 I iTracer, bi, bj,
18 U tracNew,
19 I myTime, myIter, myThid )
20
21 C !DESCRIPTION:
22 C This routine accumalates the explicit tendency matrix. Note that
23 C on entry gPtr is the tracer field after explicit advection-
24 C diffusion. On exit, gPtr is set to the initial tracer field for
25 C the next step (implicit matrix calculation).
26
27 C !USES: ===============================================================
28 IMPLICIT NONE
29 #include "SIZE.h"
30 #include "EEPARAMS.h"
31 #include "PARAMS.h"
32 #include "PTRACERS_SIZE.h"
33 #include "PTRACERS_PARAMS.h"
34 #include "MATRIX.h"
35
36 C !INPUT/OUTPUT PARAMETERS: ============================================
37 C tracNew :: updated tracer field (after adding explicit contributions)
38 INTEGER iTracer
39 INTEGER bi, bj
40 _RL myTime
41 _RL tracNew(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
42 INTEGER myIter
43 INTEGER myThid
44
45 #ifdef ALLOW_MATRIX
46 C !LOCAL VARIABLES: ====================================================
47 INTEGER i,j,k
48 CEOP
49
50 DO k=1,Nr
51 DO j=1-OLy, sNy+OLy
52 DO i=1-OLx, sNx+OLx
53 MATRIX(i,j,k,bi,bj,iTracer,1) = MATRIX(i,j,k,bi,bj,iTracer,1)
54 & + ( tracNew(i,j,k) - PTRACERS_initial(i,j,k,bi,bj,iTracer) )
55 tracNew(i,j,k) = PTRACERS_initial(i,j,k,bi,bj,iTracer)
56 ENDDO
57 ENDDO
58 ENDDO
59
60 C- Increment counter when processing the last pTracer
61 IF ( iTracer.EQ.PTRACERS_numInUse ) THEN
62 expMatrixCounter(bi,bj) = expMatrixCounter(bi,bj) + 1
63 ENDIF
64
65 #endif /* ALLOW_MATRIX */
66 RETURN
67 END
68
69 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
70 CBOP
71 C !ROUTINE: MATRIX_STORE_TENDENCY_IMP
72
73 C !INTERFACE: ==========================================================
74 SUBROUTINE MATRIX_STORE_TENDENCY_IMP(
75 I bi, bj, myTime, myIter, myThid )
76
77 C !DESCRIPTION:
78 C This routine accumalates the implicit update matrix. Note that on
79 C entry PTR is the tracer field after implicit advection-
80 C diffusion. On exit, PTR is set to the initial tracer field.
81
82 C !USES: ===============================================================
83 IMPLICIT NONE
84 #include "SIZE.h"
85 #include "EEPARAMS.h"
86 #include "PARAMS.h"
87 #include "PTRACERS_SIZE.h"
88 #include "PTRACERS_PARAMS.h"
89 #include "PTRACERS_FIELDS.h"
90 #include "MATRIX.h"
91
92 C !INPUT/OUTPUT PARAMETERS: ============================================
93 INTEGER bi, bj
94 _RL myTime
95 INTEGER myIter
96 INTEGER myThid
97
98 #ifdef ALLOW_MATRIX
99 C !LOCAL VARIABLES: ====================================================
100 INTEGER iTracer
101 INTEGER i,j,k
102 CEOP
103
104 DO iTracer=1,PTRACERS_numInUse
105 DO k=1,Nr
106 DO j=1-OLy, sNy+OLy
107 DO i=1-OLx, sNx+OLx
108 MATRIX(i,j,k,bi,bj,iTracer,2) =
109 & MATRIX(i,j,k,bi,bj,iTracer,2)
110 & + pTracer(i,j,k,bi,bj,iTracer)
111 pTracer(i,j,k,bi,bj,iTracer)=
112 & PTRACERS_initial(i,j,k,bi,bj,iTracer)
113 ENDDO
114 ENDDO
115 ENDDO
116 ENDDO
117 impMatrixCounter(bi,bj) = impMatrixCounter(bi,bj) + 1
118
119 #endif /* ALLOW_MATRIX */
120 RETURN
121 END

  ViewVC Help
Powered by ViewVC 1.1.22