/[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.4 - (hide annotations) (download)
Sun Feb 1 21:10:51 2009 UTC (15 years, 4 months ago) by jmc
Branch: MAIN
Changes since 1.3: +21 -35 lines
- clean-up & simplify linear interpolation S/R :
  (move flt_bilinear.F -> flt_interp_linear.F ; add arg. myThid ; add
   option for var @ corner position)
- fix some indices (mainly vertical index)
- uses IMPLICIT NONE

1 jmc 1.4 C $Header: /u/gcmpack/MITgcm/pkg/flt/flt_traj.F,v 1.3 2009/01/04 00:58:23 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     #include "GRID.h"
25 adcroft 1.1 #include "DYNVARS.h"
26     #include "FLT.h"
27    
28 jmc 1.2 C == routine arguments ==
29 jmc 1.3 _RL myTime
30 jmc 1.2 INTEGER myIter, myThid
31 jmc 1.3
32 jmc 1.4 C === Functions ==
33     INTEGER ILNBLNK
34     _RL global2local_i
35     _RL global2local_j
36    
37 jmc 1.3 C == local variables ==
38 adcroft 1.1 INTEGER bi, bj, imax
39 jmc 1.2 PARAMETER (imax=10)
40     INTEGER ip, kp, ii
41 jmc 1.3 _RL xx, yy
42     _RL uu,vv,tt,ss, pp
43 jmc 1.2
44     INTEGER irecord
45 adcroft 1.1 _RL tmp(imax)
46     _RL npart_read,npart_times
47     CHARACTER*(MAX_LEN_FNAM) fn
48 jmc 1.2 CHARACTER*(MAX_LEN_MBUF) msgBuf
49     CHARACTER*(80) dataFName
50     INTEGER iG,jG,IL
51     LOGICAL exst
52     LOGICAL globalFile
53 adcroft 1.1
54 jmc 1.2 C == end of interface ==
55 adcroft 1.1
56     fn = 'float_trajectories'
57    
58     DO bj=myByLo(myThid),myByHi(myThid)
59 jmc 1.4 DO bi=myBxLo(myThid),myBxHi(myThid)
60 adcroft 1.1
61 jmc 1.2 C (1) read actual number floats from file (if exists)
62 adcroft 1.1 IL=ILNBLNK( fn )
63     iG=bi+(myXGlobalLo-1)/sNx ! Kludge until unstructered tiles
64     jG=bj+(myYGlobalLo-1)/sNy ! Kludge until unstructered tiles
65 jmc 1.2 WRITE(dataFname(1:80),'(2a,i3.3,a,i3.3,a)')
66 adcroft 1.1 & fn(1:IL),'.',iG,'.',jG,'.data'
67 jmc 1.2 INQUIRE( file=dataFname, exist=exst )
68     IF (exst) THEN
69     CALL FLT_MDSREADVECTOR(fn,globalFile,64,'RL',
70     & imax,tmp,bi,bj,1,myThid)
71 adcroft 1.1 npart_read = tmp(1)
72     npart_times = tmp(5)
73 jmc 1.2 ELSE
74 adcroft 1.1 npart_read = 0.
75     npart_times = 0.
76 jmc 1.2 tmp(2) = myTime
77     ENDIF
78 adcroft 1.1
79 jmc 1.2 C the standard routine mdswritevector can be used here
80     C (2) WRITE new actual number floats and time axis into file
81     C
82     C total number of records in this file
83 adcroft 1.1 tmp(1) = DBLE(npart_tile(bi,bj))+npart_read
84 jmc 1.2 C first time of writing floats (do not change when written)
85 adcroft 1.1 c tmp(2) = tmp(2)
86 jmc 1.2 C current time
87     tmp(3) = myTime
88     C timestep
89 adcroft 1.1 tmp(4) = flt_int_traj
90 jmc 1.2 C total number of timesteps
91 adcroft 1.1 tmp(5) = npart_times + 1.
92 jmc 1.2 C total number of floats
93 adcroft 1.1 tmp(6) = max_npart
94 jmc 1.2 DO ip=7,imax
95 adcroft 1.1 tmp(ip) = 0.
96 jmc 1.2 ENDDO
97 adcroft 1.1
98 jmc 1.2 CALL MDSWRITEVECTOR(fn,64,.false.,'RL',imax,tmp,bi,bj,1,
99     & myIter,myThid)
100 adcroft 1.1
101 jmc 1.2 DO ip=1,npart_tile(bi,bj)
102 adcroft 1.1
103 jmc 1.2 xx=global2local_i(xpart(ip,bi,bj),bi,bj,myThid)
104     yy=global2local_j(ypart(ip,bi,bj),bi,bj,myThid)
105 jmc 1.4 kp = NINT(kpart(ip,bi,bj))
106 adcroft 1.1 tmp(1) = npart(ip,bi,bj)
107 jmc 1.2 tmp(2) = myTime
108     tmp(3) = xpart(ip,bi,bj)
109     tmp(4) = ypart(ip,bi,bj)
110 adcroft 1.1 tmp(5) = kpart(ip,bi,bj)
111    
112 jmc 1.4 IF ( ( myTime.GE.tstart(ip,bi,bj)) .AND.
113 jmc 1.2 & ( tend(ip,bi,bj).EQ.-1. .OR. myTime.LE.tend(ip,bi,bj))
114     & ) THEN
115    
116     IF ( kp.LT.1 .OR. kp.GT.Nr ) THEN
117     WRITE(msgBuf,'(2A,I8)') '** WARNING ** FLT_TRAJ: ',
118     & ' illegal value for kp=',kp
119     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
120     & SQUEEZE_RIGHT, myThid )
121     WRITE(msgBuf,'(A,1P5E20.13)')
122     & ' FLT_TRAJ: ', (tmp(ii),ii=1,5)
123     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
124     & SQUEEZE_RIGHT, myThid )
125     c CALL PRINT_ERROR( msgBuf, myThid )
126     c STOP 'ABNORMAL END: S/R FLT_TRAJ'
127 jmc 1.4 C-- jmc: not sure if this is right but added to avoid Pb in FLT_BILINEAR:
128     kp = MIN( MAX(kp,1), Nr)
129 jmc 1.2 ENDIF
130    
131 jmc 1.4 CALL FLT_BILINEAR (xx,yy,uu,uVel, kp,1,bi,bj,myThid)
132     CALL FLT_BILINEAR (xx,yy,vv,vVel, kp,2,bi,bj,myThid)
133     CALL FLT_BILINEAR2D(xx,yy,pp,etaN, 0,bi,bj,myThid)
134     CALL FLT_BILINEAR (xx,yy,tt,theta, kp,0,bi,bj,myThid)
135     CALL FLT_BILINEAR (xx,yy,ss,salt, kp,0,bi,bj,myThid)
136 jmc 1.2
137     tmp(6) = uu
138     tmp(7) = vv
139     tmp(8) = tt
140     tmp(9) = ss
141     tmp(10) = pp
142     ELSE
143     tmp(6) = flt_nan
144     tmp(7) = flt_nan
145     tmp(8) = flt_nan
146     tmp(9) = flt_nan
147     tmp(10) = flt_nan
148     ENDIF
149    
150     C the standard routine mdswritevector can be used here
151     C (3) WRITE float positions into file
152 adcroft 1.1
153     irecord=npart_read+ip+1
154 jmc 1.4 CALL MDSWRITEVECTOR(fn,64,.FALSE.,'RL',imax,tmp,bi,bj,
155 jmc 1.2 & irecord,myIter,myThid)
156 adcroft 1.1
157 jmc 1.2 ENDDO
158 adcroft 1.1
159     ENDDO
160 jmc 1.4 ENDDO
161 adcroft 1.1
162 jmc 1.2 RETURN
163     END

  ViewVC Help
Powered by ViewVC 1.1.22