/[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.12 - (show annotations) (download)
Fri Aug 15 19:18:12 2014 UTC (9 years, 10 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, checkpoint65c, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, HEAD
Changes since 1.11: +1 -2 lines
remove gPtr from common block

1 C $Header: /u/gcmpack/MITgcm/pkg/ptracers/ptracers_init_varia.F,v 1.11 2013/03/21 18:07:59 jahn 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_START.h"
28 #include "PTRACERS_FIELDS.h"
29
30 C !INPUT PARAMETERS:
31 C myThid :: thread number
32 INTEGER myThid
33
34 #ifdef ALLOW_PTRACERS
35
36 C !LOCAL VARIABLES:
37 C i,j,k,bi,bj,iTracer :: loop indices
38 INTEGER i,j,k,bi,bj,iTracer
39 #ifdef PTRACERS_ALLOW_DYN_STATE
40 INTEGER n
41 #endif
42 CHARACTER*(MAX_LEN_FNAM) tmpInitialFile
43 CEOP
44
45 C Initialise internal parameter in common block:
46 _BEGIN_MASTER( myThid )
47 DO iTracer = 1, PTRACERS_num
48 PTRACERS_StepFwd(iTracer) = .TRUE.
49 PTRACERS_startAB(iTracer) = nIter0 - PTRACERS_Iter0
50 ENDDO
51 _END_MASTER( myThid )
52 _BARRIER
53
54 C Loop over tracers
55 DO iTracer = 1, PTRACERS_num
56
57 C Loop over tiles
58 DO bj = myByLo(myThid), myByHi(myThid)
59 DO bi = myBxLo(myThid), myBxHi(myThid)
60
61 C Initialize arrays in common blocks :
62 DO k=1,Nr
63 DO j=1-OLy,sNy+OLy
64 DO i=1-OLx,sNx+OLx
65 pTracer(i,j,k,bi,bj,iTracer) = PTRACERS_ref(k,iTracer)
66 gpTrNm1(i,j,k,bi,bj,iTracer) = 0. _d 0
67 ENDDO
68 ENDDO
69 ENDDO
70 DO j=1-OLy,sNy+OLy
71 DO i=1-OLx,sNx+OLx
72 surfaceForcingPTr(i,j,bi,bj,iTracer) = 0. _d 0
73 ENDDO
74 ENDDO
75
76 #ifdef PTRACERS_ALLOW_DYN_STATE
77 C Initialize SOM array :
78 IF ( PTRACERS_SOM_Advection(iTracer) ) THEN
79 DO n = 1,nSOM
80 DO k=1,Nr
81 DO j=1-OLy,sNy+OLy
82 DO i=1-OLx,sNx+OLx
83 _Ptracers_som(i,j,k,bi,bj,n,iTracer) = 0. _d 0
84 ENDDO
85 ENDDO
86 ENDDO
87 ENDDO
88 ENDIF
89 #endif /* PTRACERS_ALLOW_DYN_STATE */
90
91 C end bi,bj loops
92 ENDDO
93 ENDDO
94
95 C end of Tracer loop
96 ENDDO
97
98 C Now read initial conditions and always exchange
99 IF (nIter0.EQ.PTRACERS_Iter0) THEN
100 DO iTracer = 1, PTRACERS_numInUse
101 tmpInitialFile = PTRACERS_initialFile(iTracer)
102 IF ( tmpInitialFile .NE. ' ' ) THEN
103 CALL READ_FLD_XYZ_RL(tmpInitialFile,' ',
104 & pTracer(1-OLx,1-OLy,1,1,1,iTracer),0,myThid)
105 _EXCH_XYZ_RL(pTracer(1-OLx,1-OLy,1,1,1,iTracer),myThid)
106 ENDIF
107 ENDDO
108 ENDIF
109
110 C Apply mask
111 DO iTracer = 1, PTRACERS_numInUse
112 DO bj = myByLo(myThid), myByHi(myThid)
113 DO bi = myBxLo(myThid), myBxHi(myThid)
114 DO k=1,Nr
115 DO j=1-OLy,sNy+OLy
116 DO i=1-OLx,sNx+OLx
117 IF (maskC(i,j,k,bi,bj).EQ.0.)
118 & pTracer(i,j,k,bi,bj,iTracer)=0. _d 0
119 ENDDO
120 ENDDO
121 ENDDO
122 ENDDO
123 ENDDO
124 ENDDO
125
126 C Read from a pickup file if needed
127 IF ( nIter0.GT.PTRACERS_Iter0 .OR.
128 & (nIter0.EQ.PTRACERS_Iter0 .AND. pickupSuff.NE.' ')
129 & ) THEN
130
131 CALL PTRACERS_READ_PICKUP( nIter0, myThid )
132 ENDIF
133
134 #endif /* ALLOW_PTRACERS */
135
136 RETURN
137 END

  ViewVC Help
Powered by ViewVC 1.1.22