/[MITgcm]/MITgcm_contrib/jscott/igsm/src/daily_new.F
ViewVC logotype

Annotation of /MITgcm_contrib/jscott/igsm/src/daily_new.F

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


Revision 1.4 - (hide annotations) (download)
Tue Sep 1 22:03:56 2009 UTC (15 years, 10 months ago) by jscott
Branch: MAIN
CVS Tags: HEAD
Changes since 1.3: +5 -1 lines
add changes for stochastic precip

1 jscott 1.4 C $Header$
2     C $Name$
3    
4 jscott 1.1 #include "ctrparam.h"
5    
6     ! ==========================================================
7     !
8     ! MD2G04.F: Lots of utility functions.
9     !
10     ! ----------------------------------------------------------
11     !
12     ! Revision History:
13     !
14     ! When Who What
15     ! ---- ---------- -------
16     ! 073100 Chien Wang repack based on CliChem3 & M24x11,
17     ! and add cpp.
18     !
19     ! ==========================================================
20    
21    
22     SUBROUTINE DAILY_NEW 1001.
23     C**** 1002.
24     C**** THIS SUBROUTINE PERFORMS THOSE FUNCTIONS OF THE PROGRAM WHICH 1003.
25     C**** TAKE PLACE AT THE BEGINNING OF A NEW DAY. 1004.
26     C**** 1005.
27    
28     #include "BD2G04.COM" 1006.
29    
30     COMMON/SPEC2/KM,KINC,COEK,C3LAND(IO0,JM0),C3OICE(IO0,JM0) 1006.1
31     * ,C3LICE(IO0,JM0),WMGE(IO0,JM0),TSSFC(IM0,JM0,4) 1006.2
32     COMMON U,V,T,P,Q 1007.
33     COMMON/WORK2/Z1OOLD(IO0,JM0),XO(IO0,JM0,3),XZO(IO0,JM0) 1008.
34     COMMON/OLDZO/ZMLOLD(IO0,JM0)
35     DIMENSION AMONTH(12),JDOFM(13) 1009.
36     CHARACTER*4 AMONTH 1009.1
37     DIMENSION XA(1,JM0),XB(1,JM0),OI(IO0,JM0),XOI(IO0,JM0) 1009.5
38     dimension sst1(JM0,3),sst2(JM0,3),dsst(JM0,3),intem(3),
39     & sstmin(12,2)
40     & ,miceo(JM0)
41     common/qfl/QFLUX(JM0,0:13),ZOAV(JM0),QFLUXT(JM0)
42 jscott 1.3 ! common/TSUR/TSURFC(JM0,0:13),TSURFT(JM0),TSURFD(JM0),DTSURF(JM0)
43     #include "TSRF.COM"
44 jscott 1.1 common/fixcld/cldssm(JM0,LM0,0:13),cldmcm(JM0,LM0,0:13),
45     & CLDSST(JM0,LM0),
46     & CLDMCT(JM0,LM0)
47     common/surps/srps(JM0+3),nsrps
48     #if ( defined OCEAN_3D || defined ML_2D)
49 jscott 1.2 #include "AGRID.h"
50 jscott 1.1 #endif
51 jscott 1.3 #if ( defined CLM )
52     #include "CLM.h"
53     #endif
54 jscott 1.1 LOGICAL HPRNT
55     common/conprn/HPRNT,JPR,LPR
56     data ifirst /1/
57     data intem /1,4,5/
58     data sstmin /-1.56,-1.56,-0.75,6*0.0,2*-0.75,-1.56,
59     * 3*0.0,2*-0.75,3*-1.56,-0.75,3*0.0/
60     DATA AMONTH/'JAN','FEB','MAR','APR','MAY','JUNE','JULY','AUG', 1010.
61     * 'SEP','OCT','NOV','DEC'/ 1011.
62     DATA JDOFM/0,31,59,90,120,151,181,212,243,273,304,334,365/ 1012.
63     DATA JDPERY/365/,JMPERY/12/,EDPERY/365./,Z1I/.1/,RHOI/916.6/ 1013.
64     C**** ORBITAL PARAMETERS FOR EARTH FOR YEAR 2000 A.D. 1014.
65     DATA SOLS/173./,APHEL/186./,OBLIQ/23.44/,ECCN/.0167/ 1015.
66     DATA OMEGT/282.9/
67     C**** 1016.
68     C**** THE GLOBAL MEAN PRESSURE IS KEPT CONSTANT AT PSF MILLIBARS 1017.
69     C**** 1018.
70     C**** CALCULATE THE CURRENT GLOBAL MEAN PRESSURE 1019.
71     100 SMASS=0. 1020.
72     c print *,' from Daily KOCEAN=',KOCEAN
73     nsrps=nsrps+1
74     DO 120 J=1,JM 1021.
75     SPRESS=0. 1022.
76     DO 110 I=1,IM 1023.
77     110 SPRESS=SPRESS+P(I,J) 1024.
78     srps(J)=srps(J)+P(1,J)
79     SMASS=SMASS+SPRESS*DXYP(J) 1025.
80     if(J.EQ.JM/2)PBARSH=SMASS
81     120 continue
82     PBAR=SMASS/AREAG+PTOP 1026.
83     PBARNH=2.*(SMASS-PBARSH)/AREAG
84     PBARSH=2.*PBARSH/AREAG
85     srps(JM+1)=srps(JM+1)+PBARSH
86     srps(JM+2)=srps(JM+2)+PBARNH
87     srps(JM+3)=srps(JM+3)+PBAR-PTOP
88     #if ( defined OCEAN_3D)
89     Cjrs do j=1,jm
90     Cjrs surfpr(j)=surfpr(j)+P(1,J)
91     Cjrs enddo
92     #endif
93     C**** CORRECT PRESSURE FIELD FOR ANY LOSS OF MASS BY TRUNCATION ERROR 1027.
94     130 DELTAP=PSF-PBAR 1028.
95     if(DELTAP.gt.1.)then
96     print *,' from Daily DELTAP=',DELTAP
97     print *,' PBAR=',PBAR,' PBARNH=',PBARNH,' PBARSH=',PBARSH
98     endif
99     c GO TO 1140
100     DO 140 J=1,JM 1029.
101     DO 140 I=1,IM 1030.
102     140 P(I,J)=P(I,J)+DELTAP 1031.
103     DOPK=1. 1032.
104     1140 continue
105     C WRITE (6,901) DELTAP 1033.
106     C**** 1034.
107     C**** CALCULATE THE DAILY CALENDAR 1035.
108     C**** 1036.
109     200 JYEAR=IYEAR+(IDAY-1)/JDPERY 1037.
110     JDAY=IDAY-(JYEAR-IYEAR)*JDPERY 1038.
111     DO 210 MONTH=1,JMPERY 1039.
112     IF(JDAY.LE.JDOFM(MONTH+1)) GO TO 220 1040.
113     210 CONTINUE 1041.
114     220 JDATE=JDAY-JDOFM(MONTH) 1042.
115     JMONTH=AMONTH(MONTH) 1043.
116     C**** CALCULATE SOLAR ANGLES AND ORBIT POSITION 1044.
117     if(ifirst.eq.1.or.HPRNT)then
118     print *,' DAILY_ATM IDAY=',IDAY,' IYEAR=',IYEAR
119     print *,' JYEAR=',JYEAR,' JDAY=',JDAY
120     print *,' JDATE=',JDATE,' JMONTH=',JMONTH
121     print *,'OBLIQ=',OBLIQ
122     ifirst=0
123     endif
124     JDSAVE=JDAY 1044.5
125     JDATES=JDATE 1044.51
126     MONSAV=MONTH 1044.52
127     c JDAY=197 1044.53
128     c JDATE=16 1044.54
129     c MONTH=7 1044.55
130     ! RSDIST=(1.+ECCN*COS(TWOPI*(JDAY-APHEL)/EDPERY))**2 1045.
131     ! DEC=COS(TWOPI*(JDAY-SOLS)/EDPERY)*OBLIQ*TWOPI/360. 1046.
132     ! SIND=SIN(DEC) 1047.
133     ! COSD=COS(DEC) 1048.
134     ! 03/03/06
135     ! Fixed calculation of incoming solar radiation
136     CALL ORBIT (OBLIQ,ECCN,OMEGT,JDAY-0.5,RSDIST,SIND,COSD,LAMBDA)
137     if(JDATE.le.16)then
138     do 7231 j=1,JM
139     do 7231 L=1,LM
140     CLDSST(j,L)=((16-JDATE)*cldssm(j,L,MONTH-1)+
141     * (JDATE+15)*cldssm(j,L,MONTH))/31.
142     CLDMCT(j,L)=((16-JDATE)*cldmcm(j,L,MONTH-1)+
143     * (JDATE+15)*cldmcm(j,L,MONTH))/31.
144     7231 continue
145     else
146     do 7241 j=1,JM
147     do 7241 L=1,LM
148     CLDSST(j,L)=((JDATE-16)*cldssm(j,L,MONTH+1)+
149     * (31-JDATE+16)*cldssm(j,L,MONTH))/31.
150     CLDMCT(j,L)=((JDATE-16)*cldmcm(j,L,MONTH+1)+
151     * (31-JDATE+16)*cldmcm(j,L,MONTH))/31.
152     7241 continue
153     endif
154     #if (defined OCEAN_3D || defined ML_2D)
155     if(JDATE.le.16)then
156     do 723 j=1,JM
157     TSURFT(j)=((16-JDATE)*TSURFC(j,MONTH-1)+
158     * (JDATE+15)*TSURFC(j,MONTH))/31.
159 jscott 1.3 TLANDT(j)=((16-JDATE)*TLANDC(j,MONTH-1)+
160     * (JDATE+15)*TLANDC(j,MONTH))/31.
161 jscott 1.1 723 continue
162     else
163     do 724 j=1,JM
164     TSURFT(j)=((JDATE-16)*TSURFC(j,MONTH+1)+
165     * (31-JDATE+16)*TSURFC(j,MONTH))/31.
166 jscott 1.3 TLANDT(j)=((JDATE-16)*TLANDC(j,MONTH+1)+
167     * (31-JDATE+16)*TLANDC(j,MONTH))/31.
168 jscott 1.1 724 continue
169     endif
170 jscott 1.3 ! print *,'From daily_new TSURFD'
171     ! print *,TSURFD
172     ! print *,'TSURFT'
173     ! print *,TSURFT
174     ! print *,'From daily_new TLANDD'
175     ! print *,TLANDD
176     ! print *,'TLANDT'
177     ! print *,TLANDT
178     do 725 j=1,JM
179     DT2MGL(j)=TSURFD(j)-TSURFT(j)
180     DT2MLD(j)=TLANDD(j)-TLANDT(j)
181     TSURFD(j)=0.
182     TLANDD(j)=0.
183     725 continue
184     #if ( defined CLM )
185     DT2MLAND=0.
186 jscott 1.4 if(PRTREND) then
187 jscott 1.3 AREAL=0.
188     do j=1,jm
189     DT2MLAND=DT2MLAND+DT2MLD(J)*DXYP(j)*FDATA(1,j,2)
190     AREAL=AREAL+DXYP(j)*FDATA(1,j,2)
191     end do !j
192     DT2MLAND=DT2MLAND/AREAL
193     ! print *,'DT2MLD'
194     ! print *,DT2MLD
195     if(JDATE.eq.1)then
196     print *,'JDATE=',JDATE,' DT2MLAND=',DT2MLAND
197     endif
198 jscott 1.4 endif
199 jscott 1.3 ! print *,'AREAL=',AREAL
200     #endif
201    
202 jscott 1.1 #endif
203    
204     RETURN 1108.5
205     C**** 1109.
206     ENTRY DAILY_NEW0 1110.
207     c IF(TAU.GT.TAUI+DT/7200.) GO TO 200 1111.
208     c GO TO 100 1112.
209     go to 200
210     C***** 1113.
211     901 FORMAT ('0PRESSURE ADDED IN GMP IS',F10.6/) 1114.
212     902 FORMAT ('0MEAN SURFACE PRESSURE OF THE ATMOSPHERE IS',F10.4) 1115.
213     910 FORMAT('1',33A4/) 1116.
214     915 FORMAT (47X,'DAY',I5,', HR',I3,' (',I2,A5,I5,')',F8.1) 1117.
215     920 FORMAT('1') 1118.
216     END 1119.
217     SUBROUTINE ORBIT (OBLIQ,ECCN,OMEGT,DAY,SDIST,SIND,COSD,LAMBDA) 8201.
218     C**** 8202.
219     C**** ORBIT receives the orbital parameters and time of year, and 8203.
220     C**** returns the distance from the sun and its declination angle. 8204.
221     C**** The reference for the following caculations is: V.M.Blanco 8205.
222     C**** and S.W.McCuskey, 1961, "Basic Physics of the Solar System", 8206.
223     C**** pages 135 - 151. 8207.
224     C**** 8208.
225     C**** Program authors: Gary L. Russell and Robert J. Suozzo, 12/13/85 8209.
226     C**** 8210.
227     C**** All computations are in double-precision; 8211.
228     C**** but the arguments are single-precision. 8212.
229     C**** Input: OBLIQ = latitude of tropics in degrees 8213.
230     C**** ECCEN = eccentricity of the orbital ellipse 8214.
231     C**** OMEGT = angle from vernal equinox to perihelion in degrees 8215.
232     C**** DAY = day of the year in days; 0 = Jan 1, hour 0 8216.
233     C**** 8217.
234     C**** Constants: EDAYPY = Earth days per year = 365 8218.
235     C**** VERQNX = occurence of vernal equinox = day 79 = Mar 21 8219.
236     C**** 8220.
237     C**** Intermediate quantities: 8221.
238     C**** PERIHE = perihelion during the year in temporal radians 8222.
239     C**** MA = mean anomaly in temporal radians = 2J DAY/365 - PERIHE8223.
240     C**** EA = eccentric anomaly in radians 8224.
241     C**** TA = true anomaly in radians 8225.
242     C**** BSEMI = semi minor axis in units of the semi major axis 8226.
243     C**** GREENW = longitude of Greenwich in the Earth's reference frame 8227.
244     C**** 8228.
245     C**** Output: DIST = distance to the sun in units of the semi major axis8229.
246     C**** SDIST = square of DIST 8229.5
247     C**** SIND = sine of the declination angle 8230.
248     C**** COSD = cosine of the declination angle 8231.
249     C**** LAMBDA = sun longitude in Earth's rotating reference frame 8232.
250     C**** 8233.
251     IMPLICIT REAL*8 (A-H,O-Z) 8234.
252     REAL*8 MA 8235.
253     C REAL*4 SIND,COSD,SDIST,LAMBDA,OBLIQ,ECCN,OMEGT,DAY 8236.
254     C**** 8237.
255     PI = 3.14159265358979D0 8238.
256     EDAYPY = 365. 8239.
257     VERQNX = 79. 8240.
258     OMEGA=OMEGT*(PI/180.D0) 8241.
259     DOBLIQ=OBLIQ*(PI/180.D0) 8242.
260     ECCEN=ECCN 8243.
261     C**** 8244.
262     C**** Determine time of perihelion using Kepler's equation: 8245.
263     C**** PERIHE-VERQNX = OMEGA - ECCEN sin(OMEGA) 8246.
264     C**** 8247.
265     PERIHE = OMEGA-ECCEN*SIN(OMEGA)+VERQNX*2.*PI/365. 8248.
266     C PERIHE = DMOD(PERIHE,2.*PI) 8249.
267     MA = 2.*PI*DAY/365.-PERIHE 8250.
268     MA = DMOD(MA,2.*PI) 8251.
269     C**** 8252.
270     C**** Numerically solve Kepler's equation: MA = EA - ECCEN sin(EA) 8253.
271     C**** 8254.
272     EA = MA+ECCEN*(SIN(MA)+ECCEN*SIN(2.*MA)/2.) 8255.
273     110 DEA = (MA-EA+ECCEN*SIN(MA))/(1.-ECCEN*COS(EA)) 8256.
274     EA = EA+DEA 8257.
275     IF (DABS(DEA).GT.1.D-8) GO TO 110 8258.
276     C**** 8259.
277     C**** Calculate the distance to the sun and the true anomaly 8260.
278     C**** 8261.
279     BSEMI = DSQRT(1.-ECCEN*ECCEN) 8262.
280     COSEA = COS(EA) 8263.
281     SINEA = SIN(EA) 8264.
282     SDIST = (1.-ECCEN*COSEA)*(1.-ECCEN*COSEA) 8265.
283     TA = DATAN2(SINEA*BSEMI,COSEA-ECCEN) 8266.
284     C**** 8267.
285     C**** Change the reference frame to be the Earth's equatorial plane 8268.
286     C**** with the Earth at the center and the positive x axis parallel to 8269.
287     C**** the ray from the sun to the Earth were it at vernal equinox. 8270.
288     C**** The distance from the current Earth to that ray (or x axis) is: 8271.
289     C**** DIST sin(TA+OMEGA). The sun is located at: 8272.
290     C**** 8273.
291     C**** SUN = (-DIST cos(TA+OMEGA), 8274.
292     C**** -DIST sin(TA+OMEGA) cos(OBLIQ), 8275.
293     C**** DIST sin(TA+OMEGA) sin(OBLIQ)) 8276.
294     C**** SIND = sin(TA+OMEGA) sin(OBLIQ) 8277.
295     C**** COSD = sqrt(1-SIND**2) 8278.
296     C**** LAMBDA = atan[tan(TA+OMEGA) cos(OBLIQ)] - GREENW 8279.
297     C**** GREENW = 2*3.14159 DAY (EDAYPY-1)/EDAYPY 8280.
298     C**** 8281.
299     SINDD = SIN(TA+OMEGA)*SIN(DOBLIQ) 8282.
300     COSD = DSQRT(1.-SINDD*SINDD) 8283.
301     SIND = SINDD 8284.
302     C GREENW = 2.*PI*(DAY-VERQNX)*(EDAYPY+1.)/EDAYPY 8285.
303     C SUNX = -COS(TA+OMEGA) 8286.
304     C SUNY = -SIN(TA+OMEGA)*COS(DOBLIQ) 8287.
305     C LAMBDA = DATAN2(SUNY,SUNX)-GREENW 8288.
306     C LAMBDA = DMOD(LAMBDA,2.*PI) 8289.
307     C**** 8290.
308     RETURN 8291.
309     END 8292.

  ViewVC Help
Powered by ViewVC 1.1.22