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

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

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


Revision 1.9 - (show annotations) (download)
Sat Jan 2 23:42:51 2010 UTC (14 years, 5 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint63, 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
Changes since 1.8: +5 -4 lines
avoid unused variables

1 C $Header: /u/gcmpack/MITgcm/pkg/ptracers/ptracers_init_varia.F,v 1.8 2009/08/25 21:33:28 jmc Exp $
2 C $Name: $
3
4 #include "PTRACERS_OPTIONS.h"
5 #include "GAD_OPTIONS.h"
6
7 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
8 CBOP
9 C !ROUTINE: PTRACERS_INIT_VARIA
10
11 C !INTERFACE:
12 SUBROUTINE PTRACERS_INIT_VARIA( myThid )
13
14 C !DESCRIPTION:
15 C Initialize PTRACERS data structures
16
17 C !USES:
18 #include "PTRACERS_MOD.h"
19 IMPLICIT NONE
20 #include "SIZE.h"
21 #include "EEPARAMS.h"
22 #include "PARAMS.h"
23 #include "GRID.h"
24 #include "GAD.h"
25 #include "PTRACERS_SIZE.h"
26 #include "PTRACERS_PARAMS.h"
27 #include "PTRACERS_FIELDS.h"
28
29 C !INPUT PARAMETERS:
30 C myThid :: thread number
31 INTEGER myThid
32
33 #ifdef ALLOW_PTRACERS
34
35 C !LOCAL VARIABLES:
36 C i,j,k,bi,bj,iTracer :: loop indices
37 INTEGER i,j,k,bi,bj,iTracer
38 #ifdef PTRACERS_ALLOW_DYN_STATE
39 INTEGER n
40 #endif
41 CEOP
42
43 C Loop over tracers
44 DO iTracer = 1, PTRACERS_num
45
46 C Loop over tiles
47 DO bj = myByLo(myThid), myByHi(myThid)
48 DO bi = myBxLo(myThid), myBxHi(myThid)
49
50 C Initialize arrays in common blocks :
51 DO k=1,Nr
52 DO j=1-OLy,sNy+OLy
53 DO i=1-OLx,sNx+OLx
54 pTracer(i,j,k,bi,bj,iTracer) = PTRACERS_ref(k,iTracer)
55 gPtr(i,j,k,bi,bj,iTracer) = 0. _d 0
56 gpTrNm1(i,j,k,bi,bj,iTracer) = 0. _d 0
57 ENDDO
58 ENDDO
59 ENDDO
60 DO j=1-OLy,sNy+OLy
61 DO i=1-OLx,sNx+OLx
62 surfaceForcingPTr(i,j,bi,bj,iTracer) = 0. _d 0
63 ENDDO
64 ENDDO
65
66 #ifdef PTRACERS_ALLOW_DYN_STATE
67 C Initialize SOM array :
68 IF ( PTRACERS_SOM_Advection(iTracer) ) THEN
69 DO n = 1,nSOM
70 DO k=1,Nr
71 DO j=1-OLy,sNy+OLy
72 DO i=1-OLx,sNx+OLx
73 _Ptracers_som(i,j,k,bi,bj,n,iTracer) = 0. _d 0
74 ENDDO
75 ENDDO
76 ENDDO
77 ENDDO
78 ENDIF
79 #endif /* PTRACERS_ALLOW_DYN_STATE */
80
81 C end bi,bj loops
82 ENDDO
83 ENDDO
84
85 C end of Tracer loop
86 ENDDO
87
88 C Now read initial conditions and always exchange
89 IF (nIter0.EQ.PTRACERS_Iter0) THEN
90 DO iTracer = 1, PTRACERS_numInUse
91 IF ( PTRACERS_initialFile(iTracer) .NE. ' ' ) THEN
92 CALL READ_FLD_XYZ_RL(PTRACERS_initialFile(iTracer),' ',
93 & pTracer(1-Olx,1-Oly,1,1,1,iTracer),0,myThid)
94 _EXCH_XYZ_RL(pTracer(1-Olx,1-Oly,1,1,1,iTracer),myThid)
95 ENDIF
96 ENDDO
97 ENDIF
98
99 C Apply mask
100 DO iTracer = 1, PTRACERS_numInUse
101 DO bj = myByLo(myThid), myByHi(myThid)
102 DO bi = myBxLo(myThid), myBxHi(myThid)
103 DO k=1,Nr
104 DO j=1-OLy,sNy+OLy
105 DO i=1-OLx,sNx+OLx
106 IF (maskC(i,j,k,bi,bj).EQ.0.)
107 & pTracer(i,j,k,bi,bj,iTracer)=0. _d 0
108 ENDDO
109 ENDDO
110 ENDDO
111 ENDDO
112 ENDDO
113 ENDDO
114
115 C Read from a pickup file if needed
116 IF ( nIter0.GT.PTRACERS_Iter0 .OR.
117 & (nIter0.EQ.PTRACERS_Iter0 .AND. pickupSuff.NE.' ')
118 & ) THEN
119
120 CALL PTRACERS_READ_PICKUP( nIter0, myThid )
121 ENDIF
122
123 #endif /* ALLOW_PTRACERS */
124
125 RETURN
126 END

  ViewVC Help
Powered by ViewVC 1.1.22