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

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

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


Revision 1.2 - (show annotations) (download)
Tue Aug 22 20:25:52 2006 UTC (18 years, 11 months ago) by jscott
Branch: MAIN
Changes since 1.1: +1 -1 lines
changed AGRID.COM -> AGRID.h

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

  ViewVC Help
Powered by ViewVC 1.1.22