/[MITgcm]/MITgcm/pkg/flt/flt_traj.F
ViewVC logotype

Annotation of /MITgcm/pkg/flt/flt_traj.F

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


Revision 1.10 - (hide annotations) (download)
Wed Dec 22 21:24:58 2010 UTC (13 years, 5 months ago) by jahn
Branch: MAIN
Changes since 1.9: +14 -1 lines
add exch2 support (1 facet only so far)

1 jahn 1.10 C $Header: /u/gcmpack/MITgcm/pkg/flt/flt_traj.F,v 1.9 2009/09/01 19:32:27 jmc Exp $
2 jmc 1.2 C $Name: $
3 adcroft 1.1
4 jmc 1.2 #include "FLT_OPTIONS.h"
5 adcroft 1.1
6    
7 jmc 1.2 SUBROUTINE FLT_TRAJ (
8 jmc 1.3 I myTime, myIter, myThid )
9 adcroft 1.1
10 jmc 1.2 C ==================================================================
11     C SUBROUTINE FLT_TRAJ
12     C ==================================================================
13     C o This routine samples the model state at float position every
14     C flt_int_traj time steps and writes output.
15     C ==================================================================
16 jmc 1.4
17     C !USES:
18     IMPLICIT NONE
19 adcroft 1.1
20 jmc 1.2 C == global variables ==
21     #include "SIZE.h"
22 adcroft 1.1 #include "EEPARAMS.h"
23 jmc 1.2 #include "PARAMS.h"
24 adcroft 1.1 #include "DYNVARS.h"
25     #include "FLT.h"
26 jahn 1.10 #ifdef ALLOW_EXCH2
27     #include "W2_EXCH2_SIZE.h"
28     #include "W2_EXCH2_TOPOLOGY.h"
29     #endif
30 adcroft 1.1
31 jmc 1.2 C == routine arguments ==
32 jmc 1.3 _RL myTime
33 jmc 1.2 INTEGER myIter, myThid
34 jmc 1.3
35 jmc 1.4 C === Functions ==
36     INTEGER ILNBLNK
37 jmc 1.6 _RL FLT_MAP_K2R
38     EXTERNAL ILNBLNK
39     EXTERNAL FLT_MAP_K2R
40 jmc 1.4
41 jmc 1.3 C == local variables ==
42 adcroft 1.1 INTEGER bi, bj, imax
43 jmc 1.6 PARAMETER (imax=13)
44 jmc 1.2 INTEGER ip, kp, ii
45 jmc 1.7 _RL ix, jy, i0x, j0y, xx, yy, zz
46 jmc 1.6 _RL uu, vv, tt, ss, pp
47 jmc 1.2
48 jmc 1.5 INTEGER ioUnit, irecord
49 adcroft 1.1 _RL tmp(imax)
50     _RL npart_read,npart_times
51 jmc 1.9 _RS dummyRS(1)
52 adcroft 1.1 CHARACTER*(MAX_LEN_FNAM) fn
53 jmc 1.2 CHARACTER*(MAX_LEN_MBUF) msgBuf
54     CHARACTER*(80) dataFName
55     INTEGER iG,jG,IL
56 jahn 1.10 #ifdef ALLOW_EXCH2
57     INTEGER nT
58     #endif
59 jmc 1.2 LOGICAL exst
60     LOGICAL globalFile
61 adcroft 1.1
62 jmc 1.2 C == end of interface ==
63 adcroft 1.1
64     fn = 'float_trajectories'
65    
66     DO bj=myByLo(myThid),myByHi(myThid)
67 jmc 1.4 DO bi=myBxLo(myThid),myBxHi(myThid)
68 adcroft 1.1
69 jmc 1.2 C (1) read actual number floats from file (if exists)
70 adcroft 1.1 IL=ILNBLNK( fn )
71     iG=bi+(myXGlobalLo-1)/sNx ! Kludge until unstructered tiles
72     jG=bj+(myYGlobalLo-1)/sNy ! Kludge until unstructered tiles
73 jmc 1.2 WRITE(dataFname(1:80),'(2a,i3.3,a,i3.3,a)')
74 adcroft 1.1 & fn(1:IL),'.',iG,'.',jG,'.data'
75 jmc 1.2 INQUIRE( file=dataFname, exist=exst )
76     IF (exst) THEN
77 jmc 1.5 CALL FLT_MDSREADVECTOR(fn,globalFile,precFloat64,'RL',
78 jmc 1.2 & imax,tmp,bi,bj,1,myThid)
79 adcroft 1.1 npart_read = tmp(1)
80     npart_times = tmp(5)
81 jmc 1.2 ELSE
82 adcroft 1.1 npart_read = 0.
83     npart_times = 0.
84 jmc 1.2 tmp(2) = myTime
85     ENDIF
86 adcroft 1.1
87 jmc 1.5 C the standard routine mds_writevec_loc can be used here
88 jmc 1.2 C (2) WRITE new actual number floats and time axis into file
89     C
90     C total number of records in this file
91 adcroft 1.1 tmp(1) = DBLE(npart_tile(bi,bj))+npart_read
92 jmc 1.2 C first time of writing floats (do not change when written)
93 adcroft 1.1 c tmp(2) = tmp(2)
94 jmc 1.2 C current time
95     tmp(3) = myTime
96     C timestep
97 adcroft 1.1 tmp(4) = flt_int_traj
98 jmc 1.2 C total number of timesteps
99 adcroft 1.1 tmp(5) = npart_times + 1.
100 jmc 1.2 C total number of floats
101 adcroft 1.1 tmp(6) = max_npart
102 jmc 1.6 DO ii=7,imax
103     tmp(ii) = 0.
104 jmc 1.2 ENDDO
105 adcroft 1.1
106 jmc 1.5 ioUnit = -1
107     CALL MDS_WRITEVEC_LOC( fn, precFloat64, ioUnit,
108 jmc 1.9 & 'RL', imax, tmp, dummyRS,
109 jmc 1.5 & bi,bj,-1, myIter, myThid )
110 adcroft 1.1
111 jahn 1.10 #ifdef ALLOW_EXCH2
112     nT = W2_myTileList(bi,bj)
113     i0x = DFLOAT( exch2_txGlobalo(nT) - 1 )
114     j0y = DFLOAT( exch2_tyGlobalo(nT) - 1 )
115     #else
116 jmc 1.6 i0x = DFLOAT( myXGlobalLo-1 + (bi-1)*sNx )
117     j0y = DFLOAT( myYGlobalLo-1 + (bj-1)*sNy )
118 jahn 1.10 #endif
119 jmc 1.2 DO ip=1,npart_tile(bi,bj)
120 adcroft 1.1
121 jmc 1.7 ix = ipart(ip,bi,bj)
122     jy = jpart(ip,bi,bj)
123     CALL FLT_MAP_IJLOCAL2XY( xx, yy,
124     I ix, jy, bi,bj, myThid )
125     zz = FLT_MAP_K2R( kpart(ip,bi,bj),bi,bj,myThid )
126 jmc 1.4 kp = NINT(kpart(ip,bi,bj))
127 adcroft 1.1 tmp(1) = npart(ip,bi,bj)
128 jmc 1.2 tmp(2) = myTime
129 jmc 1.7 tmp(3) = xx
130     tmp(4) = yy
131 jmc 1.6 tmp(5) = zz
132     tmp(6) = ix + i0x
133     tmp(7) = jy + j0y
134     tmp(8) = kpart(ip,bi,bj)
135 adcroft 1.1
136 jmc 1.4 IF ( ( myTime.GE.tstart(ip,bi,bj)) .AND.
137 jmc 1.2 & ( tend(ip,bi,bj).EQ.-1. .OR. myTime.LE.tend(ip,bi,bj))
138     & ) THEN
139    
140     IF ( kp.LT.1 .OR. kp.GT.Nr ) THEN
141     WRITE(msgBuf,'(2A,I8)') '** WARNING ** FLT_TRAJ: ',
142     & ' illegal value for kp=',kp
143     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
144     & SQUEEZE_RIGHT, myThid )
145     WRITE(msgBuf,'(A,1P5E20.13)')
146     & ' FLT_TRAJ: ', (tmp(ii),ii=1,5)
147     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
148     & SQUEEZE_RIGHT, myThid )
149     c CALL PRINT_ERROR( msgBuf, myThid )
150     c STOP 'ABNORMAL END: S/R FLT_TRAJ'
151 jmc 1.4 C-- jmc: not sure if this is right but added to avoid Pb in FLT_BILINEAR:
152     kp = MIN( MAX(kp,1), Nr)
153 jmc 1.2 ENDIF
154    
155 jmc 1.6 CALL FLT_BILINEAR (ix,jy,uu,uVel, kp,1,bi,bj,myThid)
156     CALL FLT_BILINEAR (ix,jy,vv,vVel, kp,2,bi,bj,myThid)
157     CALL FLT_BILINEAR2D(ix,jy,pp,etaN, 0,bi,bj,myThid)
158     CALL FLT_BILINEAR (ix,jy,tt,theta, kp,0,bi,bj,myThid)
159     CALL FLT_BILINEAR (ix,jy,ss,salt, kp,0,bi,bj,myThid)
160    
161     tmp( 9) = pp
162     tmp(10) = uu
163     tmp(11) = vv
164     tmp(12) = tt
165     tmp(13) = ss
166 jmc 1.2 ELSE
167 jmc 1.6 tmp( 9) = flt_nan
168     tmp(10) = flt_nan
169     tmp(11) = flt_nan
170     tmp(12) = flt_nan
171     tmp(13) = flt_nan
172 jmc 1.2 ENDIF
173    
174     C (3) WRITE float positions into file
175 jmc 1.5 irecord = npart_read+ip+1
176     IF ( ip.NE.npart_tile(bi,bj) ) irecord = -irecord
177     CALL MDS_WRITEVEC_LOC( fn, precFloat64, ioUnit,
178 jmc 1.9 & 'RL', imax, tmp, dummyRS,
179 jmc 1.5 & bi,bj,irecord, myIter, myThid )
180 adcroft 1.1
181 jmc 1.2 ENDDO
182 jmc 1.5 CLOSE( ioUnit )
183 adcroft 1.1
184     ENDDO
185 jmc 1.4 ENDDO
186 adcroft 1.1
187 jmc 1.2 RETURN
188     END

  ViewVC Help
Powered by ViewVC 1.1.22