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

Annotation of /MITgcm/pkg/matrix/matrix_write_tendency.F

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


Revision 1.3 - (hide annotations) (download)
Mon Nov 5 18:58:00 2007 UTC (16 years, 6 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63a, checkpoint60, checkpoint61, checkpoint62, checkpoint63, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59k, checkpoint59j, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x, checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint61a, checkpoint61n, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61q, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.2: +24 -24 lines
split PTRACERS.h in 2 header files: PTRACERS_FIELDS.h & PTRACERS_PARAMS
 declare Namelist in matrix_readparms.F (was previously in MATRIX.h)

1 jmc 1.3 C $Header: /u/gcmpack/MITgcm/pkg/matrix/matrix_write_tendency.F,v 1.2 2005/04/19 18:44:50 edhill Exp $
2 edhill 1.2 C $Name: $
3 spk 1.1
4     #include "PACKAGES_CONFIG.h"
5     #include "CPP_OPTIONS.h"
6    
7     C !ROUTINE MATRIX_WRITE_TENDENCY.F
8 jmc 1.3 C This routine writes both the explicit and implicit matrices
9 spk 1.1 C to file.
10    
11     SUBROUTINE MATRIX_WRITE_TENDENCY( myTime, myIter, myThid )
12 jmc 1.3
13 spk 1.1 IMPLICIT NONE
14 jmc 1.3 #include "SIZE.h"
15 spk 1.1 #include "EEPARAMS.h"
16 jmc 1.3 #include "PARAMS.h"
17 spk 1.1 #include "PTRACERS_SIZE.h"
18 jmc 1.3 #include "PTRACERS_PARAMS.h"
19     c#include "PTRACERS_FIELDS.h"
20     #include "MATRIX.h"
21    
22 spk 1.1 _RL myTime
23     INTEGER myIter
24     INTEGER myThid
25    
26     #ifdef ALLOW_MATRIX
27    
28     INTEGER bi,bj,i,j,k,iTracer,iRec
29     CHARACTER*(MAX_LEN_MBUF) suff
30     _RL recipImpMatrixCounter, recipExpDeltaTtracer
31    
32     DATA expMatrixWriteCount /0/
33     DATA impMatrixWriteCount /0/
34    
35 edhill 1.2 IF ( (mod(myTime-startTime,expMatrixWriteTime)
36     & .EQ. (0.0 _d 0))) THEN
37 jmc 1.3 recipExpDeltaTtracer =
38 edhill 1.2 & (1. _d 0)/(expMatrixCounter*dTtracerLev(1))
39 spk 1.1 IF (expMatrixWriteCount.EQ.0) expMatrixWriteCount=1
40     iRec=expMatrixWriteCount
41     DO iTracer=1,PTRACERS_numInUse
42     DO bj=myByLo(myThid), myByHi (myThid)
43 jmc 1.3 DO bi=myBxLo (myThid), myBxHi (myThid)
44 spk 1.1 DO k=1,Nr
45     DO j=1-Oly, sNy+Oly
46     DO i=1-Olx, sNx+Olx
47     MATRIX(i,j,k,bi,bj,iTracer,1) =
48 edhill 1.2 & MATRIX(i,j,k,bi,bj,iTracer,1)
49     & *recipExpDeltaTtracer
50 spk 1.1 ENDDO
51     ENDDO
52     ENDDO
53     ENDDO
54     ENDDO
55     WRITE(suff,'(A9,I2.2)') 'MATRIXEXP',iTracer
56 jmc 1.3 write(*,*)'Writing explicit matrix :',iTracer,
57 edhill 1.2 & expMatrixWriteCount, expMatrixCounter
58 spk 1.1 CALL WRITE_REC_XYZ_RL(suff,
59     & MATRIX(1-Olx,1-Oly,1,1,1,iTracer,1),iRec,myIter,myThid)
60     ENDDO
61     expMatrixCounter=0
62     expMatrixWriteCount=expMatrixWriteCount+1
63     C Reset explicit matrix
64     DO iTracer=1,PTRACERS_numInUse
65     DO bj=myByLo(myThid), myByHi (myThid)
66 jmc 1.3 DO bi=myBxLo (myThid), myBxHi (myThid)
67 spk 1.1 DO k=1,Nr
68     DO j=1-Oly, sNy+Oly
69     DO i=1-Olx, sNx+Olx
70     MATRIX(i,j,k,bi,bj,iTracer,1)= 0. _d 0
71     ENDDO
72     ENDDO
73     ENDDO
74 jmc 1.3 ENDDO
75 spk 1.1 ENDDO
76     ENDDO
77     ENDIF
78 jmc 1.3
79 edhill 1.2 IF ( (mod(myTime-startTime,impMatrixWriteTime)
80     & .EQ.(0.0 _d 0)) ) THEN
81 spk 1.1 recipImpMatrixCounter = (1. _d 0)/dble(impMatrixCounter)
82     IF (impMatrixWriteCount.EQ.0) impMatrixWriteCount=1
83     iRec=impMatrixWriteCount
84     DO iTracer=1,PTRACERS_numInUse
85     DO bj=myByLo(myThid), myByHi (myThid)
86 jmc 1.3 DO bi=myBxLo (myThid), myBxHi (myThid)
87 spk 1.1 DO k=1,Nr
88     DO j=1-Oly, sNy+Oly
89     DO i=1-Olx, sNx+Olx
90     MATRIX(i,j,k,bi,bj,iTracer,2) =
91 edhill 1.2 & MATRIX(i,j,k,bi,bj,iTracer,2)
92     & *recipImpMatrixCounter
93 spk 1.1 ENDDO
94     ENDDO
95     ENDDO
96     ENDDO
97     ENDDO
98     WRITE(suff,'(A9,I2.2)') 'MATRIXIMP',iTracer
99 jmc 1.3 write(*,*)'Writing implicit matrix :',iTracer,
100 edhill 1.2 & impMatrixWriteCount, impMatrixCounter
101 spk 1.1 CALL WRITE_REC_XYZ_RL(suff,
102     & MATRIX(1-Olx,1-Oly,1,1,1,iTracer,2),iRec,myIter,myThid)
103 jmc 1.3 ENDDO
104 spk 1.1 impMatrixCounter=0
105     impMatrixWriteCount=impMatrixWriteCount+1
106 jmc 1.3 C Reset implicit matrix
107 spk 1.1 DO iTracer=1,PTRACERS_numInUse
108     DO bj=myByLo(myThid), myByHi (myThid)
109 jmc 1.3 DO bi=myBxLo (myThid), myBxHi (myThid)
110 spk 1.1 DO k=1,Nr
111     DO j=1-Oly, sNy+Oly
112     DO i=1-Olx, sNx+Olx
113     MATRIX(i,j,k,bi,bj,iTracer,2)= 0. _d 0
114     ENDDO
115     ENDDO
116     ENDDO
117 jmc 1.3 ENDDO
118 spk 1.1 ENDDO
119 jmc 1.3 ENDDO
120 spk 1.1 ENDIF
121 jmc 1.3
122 spk 1.1 #endif /* ALLOW_MATRIX */
123 jmc 1.3 RETURN
124 spk 1.1 END

  ViewVC Help
Powered by ViewVC 1.1.22