/[MITgcm]/MITgcm_contrib/jscott/pkg_atm2d/fixed_flux_add.F
ViewVC logotype

Annotation of /MITgcm_contrib/jscott/pkg_atm2d/fixed_flux_add.F

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


Revision 1.4 - (hide annotations) (download)
Tue Aug 21 16:06:21 2007 UTC (17 years, 11 months ago) by jscott
Branch: MAIN
CVS Tags: HEAD
Changes since 1.3: +0 -0 lines
FILE REMOVED
remove old atm2d pkg repository

1 jscott 1.1 #include "ctrparam.h"
2     #include "ATM2D_OPTIONS.h"
3    
4     C !INTERFACE:
5     SUBROUTINE FIXED_FLUX_ADD( wght0, wght1,
6     & intime0, intime1, iftime, myIter, myThid)
7     C *==========================================================*
8 jscott 1.3 C | Add fixed flux files to the surface forcing fields. These|
9     c | can be OBS fields or derived fields for anomaly coupling.|
10 jscott 1.1 C *==========================================================*
11     IMPLICIT NONE
12    
13     C === Global Atmos/Ocean/Seaice Interface Variables ===
14     #include "ATMSIZE.h"
15     #include "SIZE.h"
16     #include "EEPARAMS.h"
17     #include "THSICE_VARS.h"
18     #include "ATM2D_VARS.h"
19    
20     C !INPUT/OUTPUT PARAMETERS:
21     C === Routine arguments ===
22 jscott 1.3 C wght0, wght1 - weight of first and second month, respectively
23     C intime0,intime1- month id # for first and second months
24     C iftime - true -> prompts a reloading of data from disk
25 jscott 1.1 C myIter - Ocean iteration number
26     C myThid - Thread no. that called this routine.
27     _RL wght0
28     _RL wght1
29     INTEGER intime0
30     INTEGER intime1
31     LOGICAL iftime
32     INTEGER myIter
33     INTEGER myThid
34    
35     C LOCAL VARIABLES:
36 jscott 1.3 INTEGER i,j ! loop counters
37     C save below in common block so continual reloading isn't necessary
38 jscott 1.1 COMMON /OCEANMEAN/
39     & tau0, tau1, tav0, tav1,
40     & wind0, wind1, qnet0, qnet1,
41     & evap0, evap1,
42     & precip0, precip1,
43     & runoff0, runoff1
44    
45     _RS tau0(1-Olx:sNx+Olx,1-Oly:sNy+Oly,1,1)
46     _RS tau1(1-Olx:sNx+Olx,1-Oly:sNy+Oly,1,1)
47     _RS tav0(1-Olx:sNx+Olx,1-Oly:sNy+Oly,1,1)
48     _RS tav1(1-Olx:sNx+Olx,1-Oly:sNy+Oly,1,1)
49     _RS wind0(1-Olx:sNx+Olx,1-Oly:sNy+Oly,1,1)
50     _RS wind1(1-Olx:sNx+Olx,1-Oly:sNy+Oly,1,1)
51     _RS qnet0(1-Olx:sNx+Olx,1-Oly:sNy+Oly,1,1)
52     _RS qnet1(1-Olx:sNx+Olx,1-Oly:sNy+Oly,1,1)
53     _RS evap0(1-Olx:sNx+Olx,1-Oly:sNy+Oly,1,1)
54     _RS evap1(1-Olx:sNx+Olx,1-Oly:sNy+Oly,1,1)
55     _RS precip0(1-Olx:sNx+Olx,1-Oly:sNy+Oly,1,1)
56     _RS precip1(1-Olx:sNx+Olx,1-Oly:sNy+Oly,1,1)
57     _RS runoff0(1-Olx:sNx+Olx,1-Oly:sNy+Oly,1,1)
58     _RS runoff1(1-Olx:sNx+Olx,1-Oly:sNy+Oly,1,1)
59    
60     IF (ifTime) THEN
61    
62     C If the above condition is met then we need to read in
63     C data for the period ahead and the period behind current time.
64    
65     WRITE(*,*) 'S/R FIXED_FLUX_ADD: Reading new data'
66     IF ( tauuFile .NE. ' ' ) THEN
67     CALL READ_REC_XY_RS( tauuFile,tau0,intime0,
68     & myIter,myThid )
69     CALL READ_REC_XY_RS( tauuFile,tau1,intime1,
70     & myIter,myThid )
71     ENDIF
72     IF ( tauvFile .NE. ' ' ) THEN
73     CALL READ_REC_XY_RS( tauvFile,tav0,intime0,
74     & myIter,myThid )
75     CALL READ_REC_XY_RS( tauvFile,tav1,intime1,
76     & myIter,myThid )
77     ENDIF
78     IF ( windFile .NE. ' ' ) THEN
79     CALL READ_REC_XY_RS( windFile,wind0,intime0,
80     & myIter,myThid )
81     CALL READ_REC_XY_RS( windFile,wind1,intime1,
82     & myIter,myThid )
83     ENDIF
84     IF ( qnetFile .NE. ' ' ) THEN
85     CALL READ_REC_XY_RS( qnetFile,qnet0,intime0,
86     & myIter,myThid )
87     CALL READ_REC_XY_RS( qnetFile,qnet1,intime1,
88     & myIter,myThid )
89     ENDIF
90     IF ( evapFile .NE. ' ' ) THEN
91     CALL READ_REC_XY_RS( evapFile,evap0,intime0,
92     & myIter,myThid )
93     CALL READ_REC_XY_RS( evapFile,evap1,intime1,
94     & myIter,myThid )
95     ENDIF
96     IF ( precipFile .NE. ' ' ) THEN
97     CALL READ_REC_XY_RS( precipFile,precip0,intime0,
98     & myIter,myThid )
99     CALL READ_REC_XY_RS( precipFile,precip1,intime1,
100     & myIter,myThid )
101     ENDIF
102     IF ( runoffFile .NE. ' ' ) THEN
103     CALL READ_REC_XY_RS( runoffFile,runoff0,intime0,
104     & myIter,myThid )
105     CALL READ_REC_XY_RS( runoffFile,runoff1,intime1,
106     & myIter,myThid )
107     ENDIF
108    
109     ENDIF
110    
111    
112     C-- Interpolate and add to anomaly
113     DO j=1,sNy
114     DO i=1,sNx
115    
116     fu_2D(i,j)= fu_2D(i,j) +
117     & (wght0*tau0(i,j,1,1) + wght1*tau1(i,j,1,1))
118     fv_2D(i,j)= fv_2D(i,j) +
119     & (wght0*tav0(i,j,1,1) + wght1*tav1(i,j,1,1))
120     wspeed_2D(i,j)= wspeed_2D(i,j) +
121     & (wght0*wind0(i,j,1,1) + wght1*wind1(i,j,1,1))
122     qneto_2D(i,j)= qneto_2D(i,j) +
123     & (wght0*qnet0(i,j,1,1) + wght1*qnet1(i,j,1,1))
124    
125     c note below is different from older code...
126 jscott 1.2 IF (iceMask(i,j,1,1) .NE. 0. _d 0)
127 jscott 1.1 & qneti_2D(i,j)= qneti_2D(i,j) +
128     & (wght0*qnet0(i,j,1,1) + wght1*qnet1(i,j,1,1))
129    
130     IF (useObsEmP) THEN
131     evapo_2D(i,j)= (wght0*evap0(i,j,1,1) + wght1*evap1(i,j,1,1))
132     precipo_2D(i,j)= (wght0*precip0(i,j,1,1) + wght1*precip1(i,j,1,1))
133 jscott 1.2 IF (iceMask(i,j,1,1) .NE. 0. _d 0) THEN
134 jscott 1.1 evapi_2D(i,j)= (wght0*evap0(i,j,1,1) + wght1*evap1(i,j,1,1))
135     precipi_2D(i,j)= (wght0*precip0(i,j,1,1) +
136     & wght1*precip1(i,j,1,1))
137     ENDIF
138     ELSE
139     evapo_2D(i,j)= evapo_2D(i,j) +
140     & (wght0*evap0(i,j,1,1) + wght1*evap1(i,j,1,1))
141     precipo_2D(i,j)= precipo_2D(i,j) +
142     & (wght0*precip0(i,j,1,1) + wght1*precip1(i,j,1,1))
143 jscott 1.2 IF (iceMask(i,j,1,1) .NE. 0. _d 0) THEN
144 jscott 1.1 evapi_2D(i,j)= evapi_2D(i,j) +
145     & (wght0*evap0(i,j,1,1) + wght1*evap1(i,j,1,1))
146     precipi_2D(i,j)= precipi_2D(i,j) +
147     & (wght0*precip0(i,j,1,1) + wght1*precip1(i,j,1,1))
148     ENDIF
149     ENDIF
150    
151     IF (useObsRunoff) THEN
152     runoff_2D(i,j)= (wght0*runoff0(i,j,1,1) + wght1*runoff1(i,j,1,1))
153     ELSE
154     runoff_2D(i,j)= runoff_2D(i,j) +
155     & (wght0*runoff0(i,j,1,1) + wght1*runoff1(i,j,1,1))
156     ENDIF
157     ENDDO
158     ENDDO
159    
160     RETURN
161     END
162    

  ViewVC Help
Powered by ViewVC 1.1.22