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

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

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


Revision 1.4 - (hide annotations) (download)
Mon Nov 5 18:48:04 2007 UTC (16 years, 7 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint59q, checkpoint59p, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59k, checkpoint59j
Changes since 1.3: +11 -17 lines
split PTRACERS.h in 2 header files: PTRACERS_FIELDS.h & PTRACERS_PARAMS.h

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

  ViewVC Help
Powered by ViewVC 1.1.22