オリジナルのプログラムにあった若干のバグを修正しています。
注意:このプログラムは入力データとして、
大気の比湿(g/kg)
短波放射
長波放射
海流の流速(m/s)
波高(m)
が必要です。
比湿のデータが無い場合、相対湿度、気温、大気圧から比湿を計算してやる必要があります。
短波放射と長波放射のデータが無い場合は、0を与えます。パラメータiwarm, icoldも1から0にしておく必要があるかもしれません(未確認)。
海流の流速データが無い場合、0を与えます。
波高のデータが無い場合は、0を与えます。
Program heat_flux_toga_coare_3_0
!toga coare bulk flux model version 3.0
!***************************************
!uses following subroutines:
! cor30a.F90
! psiu_30.F90
! psit_30.F90
! qsee.F90
! grv.F90
!***************************************
!*********** basic specifications *****
! zu= height of wind measurement
! zt= height of air temperature measurement
! zq= height of air humidity measurement
! ts_depth depth of water temperature measurement
! jwarm= 0=no warm layer calc, 1 =do warm layer calc
! jcool= 0=no cool skin calc, 1=do cool skin calc
! jwave= 0= Charnock, 1=Oost et al, 2=Taylor and Yelland
!*********** input data **************
! YYYYMMHHMMSS= date in toga coare format, Y2K version
! u= wind speed (m/s) measured at height zu
! us= ocean surface current (m/s)
! msp (ts) = bulk surface sea temp (degC)
! t= air temp (degC) measured at height zt
! qs= sea surface sat specific humidity (g/kg)
! q= air specific humidity (g/kg) measuered height zq
! Rs= downward solar flux (w/m^2)
! Rl= downward IR flux (w/m^2)
! zi= inversion height (m)
! P= air pressure (mb)
! rain=rain rate (mm/hr)
! lon= longitude (deg E=+)
! lat= latitude (deg N=+)
!********** output data ***************
! hsb= sensible heat flux (w/m^2)
! hlb= latent heat flux (w/m^2)
! RF= rain heat flux(w/m^2)
! wbar= webb mean w (m/s)
! tau= stress (nt/m^2)
! zo= velocity roughness length (m)
! zot temperature roughness length (m)
! zoq= moisture roughness length (m)
! L= Monin_Obukhov stability length
! usr= turbulent friction velocity (m/s), including gustiness
! tsr temperature scaling parameter (K)
! qsr humidity scaling parameter (g/g)
! dter= cool skin temperature depression (K)
! dqer= cool skin humidity depression (g/g)
! tkt= cool skin thickness (m)
! Cd= velocity drag coefficient at zu, referenced to u
! Ch= heat transfer coefficient at zt
! Ce= moisture transfer coefficient at zq
! Cdn_10= 10-m velocity drag coeeficient, including gustiness
! Chn_10= 10-m heat transfer coeeficient, including gustiness
! Cen_10= 10-m humidity transfer coeeficient, including gustiness
!
IMPLICIT NONE
character(len=500)::infle,ofle
integer ndat,nhead
integer,allocatable :: indx(:)
real,allocatable ::arnl(:), Hrain(:), hnet(:), hs(:), hl(:), tau(:)
real,allocatable::arrout(:,:), qsx(:),locx(:)
integer xin, ibg, jdx(30)
real tsx(30), dt(30), hwave
real :: x(19), y(30), hl_webb(30)
real :: u,tsnk,ta,qa,rs,rl,org,lat,lon,msp
real :: jcool, jwave
real :: a,al,b,be,cd,cdn_10,ce,cen_10,ch,chktime,chn_10,cpa,cpv,cpw,ctd1,ctd2
real :: didread,dqer,dsea,dt_wrm,dter,dtime,fxp,grav,hl_old,hlb,hs_old,hsb
integer :: i,icount,iday,ihr,imin,isec,iyr,jamset,jump,jwarm,l,le,mon
real :: loc,lonx,newtime,p,q,q_pwp,qcol_ac,qjoule,qr_out,qs,qsr,rain,rf,rf_old,rgas
!real :: loc,locx,lonx,newtime,p,q,q_pwp,qcol_ac,qjoule,qr_out,qs,qsr,rain,rf,rf_old,rgas
real :: rhoa,rhow,rich,rnl,rns,t,tau_ac,tau_old,taub,tcw,tdk,time,intime,jtime,tk_pwp,tkt,ts,ts_depth,tsea
real :: tsr,twave,us,usr,visa,visw,wbar,wg,zi,zo,zoq,zot,zq,zt,zu
double precision :: jdy,st
real, external :: grv, qsee
!real :: jdy,st
xin = 20
didread=0
! jdy=x(xin,1) !time in the form YYYYMMDDHHSS.SS
! U=x(xin,2) !true wind speed, m/s etl sonic anemometer
! tsnk=x(xin,3) !sea snake temperature, C (0.05 m depth)
! ta=x(xin,4) !air temperature, C (z=14.5 m)
! qa=x(xin,5) !air specific humidity, g/kg (z=14.5 m)
! rs=x(xin,6) !downward solar flux, W/m^2 (ETL units)
! rl=x(xin,7) !downward IR flux, W/m^2 (ETL units)
! org=x(xin,8) !rainrate, mm/hr (ETL STI optical rain gauge, uncorrected)
! lat=x(xin,9) !latitude, deg (SCS pcode)
! lon=x(xin,10) !longitude, deg (SCS pcode)
! msp=x(xin,11) !6-m deotg T from MSP, C
namelist /para/infle,ofle,nhead,ndat,zu,zt,zq,ts_depth,jcool,jwarm,jwave,icount
read(*,nml=para)
write(*,'(A,f6.1,A)')'zu=',zu,' (m)'
write(*,'(A,f6.1,A)')'zt=',zt,' (m)'
write(*,'(A,f6.1,A)')'zq=',zq,' (m)'
write(*,'(A,f6.1,A)')'ts_depth=',ts_depth,' (m)'
write(*,'(A,i3)')'jcool=',jcool
write(*,'(A,i3)')'jwarm=',jwarm
write(*,'(A,i3)')'icount=',icount
write(*,'(A,A)')'Input: ',trim(infle)
write(*,'(A,A)')'Output: ',trim(ofle)
write(*,'(A,i6)')'nhead= ',nhead
write(*,'(A,i6)')'ndat= ',ndat
allocate(indx(ndat))
allocate(arnl(ndat), Hrain(ndat), hnet(ndat), hs(ndat), hl(ndat), tau(ndat))
allocate(arrout(ndat,13), qsx(ndat),locx(ndat))
! ************* open the output file
open(unit=12,file=ofle)
7 format(i6,i9,5i2.2,3f9.2,2f10.5,6f9.2)
!********************* housekeep variables ********
qcol_ac=0
tau_ac=0
jtime=0
jamset=0
tau_old=.06
hs_old=10
hl_old=100
RF_old=0
dsea=0
dt_wrm=0
tk_pwp=19
fxp=.5
q_pwp=0
jump=1
!******************* set constants ****************
tdk=273.16
grav=grv(30.0) !(-2.) !9.72
Rgas=287.1
cpa=1004.67
be=0.026
cpw=4000
rhow=1022
visw=1e-6
tcw=0.6
dter=0.3
!*********** set variables not in data base ********
P=1008 !air pressure [hPa]
us=0 !surface current [m/s]
zi=600 !inversion ht [m]
!****************** setup read data loop **********
open(unit=3,file=infle,action="read")
do i=1,nhead
read(3,*) !Skip header lines
enddo !i
do ibg = 1,ndat !major read loop
! read(3,*)
! tsnk=msp !Just in case (assuming skin temp.=bulk SST)
! !I believe tsnk is not used in the following flux calculation.
read(3,8) jdy, u, tsnk, ta, qa, rs, rl, org, lat, lon, msp
8 format(f17.2,f7.2,f9.2,2f8.2,f9.2,f8.2,f6.2,f9.2,f9.2,f7.2)
!******* decode date ************
st=(jdy)
print '(f17.0)',st
iyr=floor(st/1e10)
mon=floor(st/1e8)-iyr*100
iday=floor((st/1e6) -iyr*1e4 - mon*100)
ihr=floor((st/1e4)-iyr*1e6-mon*1e4-iday*100 )
imin=floor((st/100)- iyr*1e8-mon*1e6-iday*1e4-ihr*100)
isec=0
print *,iyr, mon, iday, ihr, imin, isec
!******** decode bulk met data ****
if(ibg .eq. 1) ts=msp
tsea=msp !bulk sea surface temp
t=ta !air temp
qs=qsee(tsea, P) !bulk sea surface humidity
q=qa !air humidity
Rs=rs !downward solar flux
Rl=rl !doward IR flux
rain=org !rain rate
grav=grv(lat) !9.72
lonx=lon !longitude
!***** variables for warm layer ***
! time=(float(ihr*3600)+float(imin*60))/24./3600.
time=((float(ihr*3600)+float(imin*60))/24.) /3600.
intime=time
loc=(lonx+7.5)/15
locx(ibg)=loc
Rnl=.97*(5.67e-8*(ts-dter*jcool+273.16)**4-Rl) !oceanic broadband emissivity=0.97
arnl(ibg)=Rnl
Rns=.945*Rs !oceanic albedo=0.055 daily average
!********* set condition dependent stuff ******
Le=(2.501-.00237*tsea)*1e6
cpv=cpa*(1+0.84*q/1000)
rhoa=P*100/(Rgas*(t+tdk)*(1+0.61*q/1000))
visa=1.326e-5*(1+6.542e-3*t+8.301e-6*t*t-4.84e-9*t*t*t)
Al=2.1e-5*(tsea+3.2)**0.79
!************** apply warm layer ***********
if (jwarm .EQ. 1) then !do warm layer
chktime=loc+(intime*24.0)
! chktime=loc+intime*24
newtime=(chktime-24*floor(chktime/24))*3600
if (icount .GT. 1) then !not first time thru
if ((newtime .GT. 21600) .AND. (jump .EQ. 1)) then
else
jump=0
if (newtime .LT. jtime) then !re-zero at midnight
jamset=0
fxp=.5
tk_pwp=19
tau_ac=0
qcol_ac=0
dt_wrm=0
jump=0 !goto 16
else
!*************** set warm layer constants **************
rich=.65 !crit rich
ctd1=sqrt(2*rich*cpw/(Al*grav*rhow))
ctd2=sqrt(2*Al*grav/(rich*rhow))/(cpw**1.5)
!************************************************
dtime=newtime-jtime !delta time for integrals
qr_out=Rnl+hs_old+hl_old+RF_old !total cooling at surface
q_pwp=fxp*Rns-qr_out !tot heat abs in warm layer
if (q_pwp .LT. 50 .AND. jamset .EQ. 0) then !check for threshold
!goto 16
else
jamset=1 !indicates threshold crossed
tau_ac=tau_ac+max(.002,tau_old)*dtime !momentum integral
if ((qcol_ac+q_pwp*dtime) .GT. 0) then !check threshold for warm layer existence
do i=1,5 !loop 5 times for fxp
fxp=1-(0.28*0.014*(1-exp(-tk_pwp/0.014))+0.27*0.357*(1-exp(-tk_pwp/0.357))+0.45*12.82*(1-exp(-tk_pwp/12.82)))/tk_pwp
!fg=fpaul(tk_pwp) fxp=fg(1)
qjoule=(fxp*Rns-qr_out)*dtime
if (qcol_ac+qjoule .GT. 0) then
tk_pwp=min(19.,ctd1*tau_ac/sqrt(qcol_ac+qjoule))
endif
enddo ! end i loop
else !warm layer wiped out
fxp=0.75
tk_pwp=19
qjoule=(fxp*Rns-qr_out)*dtime
endif ! end sign check on qcol_ac
qcol_ac=qcol_ac+qjoule !heat integral
!*********** compute dt_warm **************
if (qcol_ac .GT. 0) then
dt_wrm=ctd2*(qcol_ac)**1.5/tau_ac
else
dt_wrm=0
endif
endif ! end threshold check
endif ! end midnight reset
if (tk_pwp .LT. ts_depth) then
dsea=dt_wrm
else
dsea=dt_wrm*ts_depth/tk_pwp
endif
endif ! end 6am start first time thru
endif ! end first time thru check
jtime=newtime
endif ! end jwarm, end warm layer model appl check
ts=tsea+dsea
qs=qsee(ts, P)
qsx(ibg)=qs
tsx(20)= 1. !ts
a=.018
b=.729
twave=b*u
hwave=a*u**2.*(1+.015*u)
x=(/u, us, ts, t, qs, q, Rs, Rl, rain, zi, P, zu, zt, zq, lat, jcool, jwave, twave, hwave/)!set data for basic flux alogithm
!******** call modified LKB routine *******
call cor30a(x,y)
!****************** output from routine *****************************
hsb=y(1) !sensible heat flux W/m/m
hlb=y(2) !latent
taub=y(3) !stress
zo=y(4) !vel roughness
zot=y(5) !temp "
zoq=y(6) !hum "
L=y(7) !Ob Length
usr=y(8) !ustar
tsr=y(9) !tstar
qsr=y(10) !qstar [g/g]
dter=y(11) !cool skin delta T
dqer=y(12) ! " " " q
tkt=y(13) !thickness of cool skin
RF=y(14) !rain heat flux
wbar=y(15) !webb mean w
Cd=y(16) !drag @ zu
Ch=y(17) !
Ce=y(18) !Dalton
Cdn_10=y(19) !neutral drag @ 10 [includes gustiness]
Chn_10=y(20) !
Cen_10=y(21) !
Wg=y(22)
! zax(1)=jd !julian day
! zax(2:10)=x(1:9) !
! zax(4)=tsea !Tsea [no cool skin]
! zax(11:32)=y(1:22) !
! zax(33:35)=(/dt_wrm, tk_pwp, ts/) !warm layer deltaT, thickness, corrected Tsea
!******* previous values from cwf hp basic code *****
Hrain(ibg)=RF
!********** new values from this code
hnet(ibg)=Rns-Rnl-hsb-hlb-Hrain(ibg) !total heat input to ocean
hs(ibg)=hsb
hl(ibg)=hlb
tau(ibg)=taub
hl_webb=rhoa*Le*wbar*qa/1000
!******************** save various parts of data **********************************
!************* create Bradley type out file
indx(ibg)=ibg
arrout(ibg,1)=ibg
arrout(ibg,2)=jdy !output old results
arrout(ibg,3)=hsb
arrout(ibg,4)=hlb
arrout(ibg,5)=ts-dter*jcool
arrout(ibg,6)=taub
arrout(ibg,7)=wbar
arrout(ibg,8)=RF
arrout(ibg,9)=dter
arrout(ibg,10)=dt_wrm
arrout(ibg,11)=tk_pwp
arrout(ibg,12)=tkt*1e3
arrout(ibg,13)=Wg
hs_old=hsb
hl_old=hlb
RF_old=RF
tau_old=taub
icount=icount+1
! print *, arrout(ibg,:)
write(12,7)ibg,iyr, mon, iday, ihr, imin, isec ,arrout(ibg,3:13)
enddo ! data line loop
!***************** write output file ******
close(unit=3)
close(unit=15)
print *,"Done!"
end PROGRAM !cor3_0af.F90
subroutine cor30a(x,y)
!version with shortened iteration modified Rt and Rq
!uses wave information wave period in s and wave ht in m
!no wave, standard coare 2.6 charnock: jwave=0
!Oost et al. zo=50/2/pi L (u*/c)**4.5 if jwave=1
!taylor and yelland zo=1200 h*(L/h)**4.5 jwave=2
!
IMPLICIT NONE
real x(19), y(22)
real u,us,ts,t,Qs,Q,Rs,Rl,rain,zi,P,zu,zt,zq,lat,jcool,twave,hwave
real Beta,von,fdg,tdk,grav,Rgas,Le,cpa,cpv,rhoa,visa,Al,be,cpw,rhow,visw,tcw,bigc,wetc
real lwave,cwave,Rns,Rnl,du,dt,dq,qout,dels,qcol,alq,xlamx,alfac,bf,cc,cd10,ch10,charn,ct,ct10,dtmp,dwat,hl_webb
real jwave,l10,nits,pi,ribcu,ribu,rr,ta,u10,ut,zet,zetu,zo10,zot10
real hsb, hlb, tau, zo, zot, zoq, L, usr, tsr, qsr, dter, dqer, tkt, RF, wbar, Cd, Ch, Ce, Cdn_10, Chn_10, Cen_10, ug
real p30, ztL10
real, external :: psit_30, psiuo, grv
integer i
u=x(1) !wind speed (m/s) at height zu (m)
us=x(2) !surface current speed in the wind direction (m/s)
ts=x(3) !bulk water temperature (C) if jcool=1, interface water T if jcool=0
t=x(4) !bulk air temperature (C), height zt
Qs=x(5)/1000 !bulk water spec hum (g/kg) if jcool=1, ...
Q=x(6)/1000 !bulk air spec hum (g/kg), height zq
Rs=x(7) !downward solar flux (W/m**2)
Rl=x(8) !downard IR flux (W/m**2)
rain=x(9) !rain rate (mm/hr)
zi=x(10) !PBL depth (m)
P=x(11) !Atmos surface pressure (mb)
zu=x(12) !wind speed measurement height (m)
zt=x(13) !air T measurement height (m)
zq=x(14) !air q measurement height (m)
lat=x(15) !latitude (deg, N=+)
jcool=x(16) !implement cool calculation skin switch, 0=no, 1=yes
jwave=x(17) !implement wave dependent roughness model
twave=x(18) !wave period (s)
hwave=x(19) !wave height (m)
!***************** set constants *************
Beta=1.2
von=0.4
fdg=1.00
tdk=273.16
pi = 3.141593
grav=grv(lat) !9.82
!************* air constants ************
Rgas=287.1
Le=(2.501-.00237*ts)*1e6
cpa=1004.67
cpv=cpa*(1+0.84*Q)
rhoa=P*100/(Rgas*(t+tdk)*(1+0.61*Q))
visa=1.326e-5*(1+6.542e-3*t+8.301e-6*t*t-4.84e-9*t*t*t)
!************ cool skin constants *******
Al=2.1e-5*(ts+3.2)**0.79
be=0.026
cpw=4000
rhow=1022
visw=1e-6
tcw=0.6
bigc=16*grav*cpw*(rhow*visw)**3/(tcw*tcw*rhoa*rhoa)
wetc=0.622*Le*Qs/(Rgas*(ts+tdk)**2)
!*************** wave parameters *********
lwave=grav/2/pi*twave**2
cwave=grav/2/pi*twave
!************** compute aux stuff *******
Rns=Rs*.945
Rnl=0.97*(5.67e-8*(ts-0.3*jcool+tdk)**4-Rl)
!*************** Begin bulk loop *******
!*************** first guess ************
du=u-us
dt=ts-t-.0098*zt
dq=Qs-Q
ta=t+tdk
ug=.5
dter=0.3
dqer=wetc*dter
ut=sqrt(du*du+ug*ug)
u10=ut*log(10/1e-4)/log(zu/1e-4)
usr=.035*u10
zo10=0.011*usr*usr/grav+0.11*visa/usr
Cd10=(von/log(10/zo10))**2
Ch10=0.00115
Ct10=Ch10/sqrt(Cd10)
zot10=10/exp(von/Ct10)
Cd=(von/log(zu/zo10))**2
Ct=von/log(zt/zot10)
CC=von*Ct/Cd
Ribcu=-zu/zi/.004/Beta**3
Ribu=-grav*zu/ta*((dt-dter*jcool)+.61*ta*dq)/ut**2
nits=3
if (Ribu .LT. 0) then
zetu=CC*Ribu/(1+Ribu/Ribcu)
else
zetu=CC*Ribu*(1+27/9*Ribu/CC)
endif
L10=zu/zetu
if (zetu .GT. 50) then
nits=1
endif
usr=ut*von/(log(zu/zo10)-psiuo(zu/L10))
tsr=-(dt-dter*jcool)*von*fdg/(log(zt/zot10)-psit_30(zt/L10))
qsr=-(dq-wetc*dter*jcool)*von*fdg/(log(zq/zot10)-psit_30(zq/L10))
tkt=.001
charn=0.011
if (ut .GT. 10) then
charn=0.011+(ut-10)/(18-10)*(0.018-0.011)
endif
if (ut .GT. 18) then
charn=0.018
endif
!*************** bulk loop ************
do i=1, nits
zet=von*grav*zu/ta*(tsr*(1+0.61*Q)+.61*ta*qsr)/(usr*usr)/(1+0.61*Q)
!disp(usr)
!disp(zet)
if (jwave .EQ. 0) zo=charn*usr*usr/grav+0.11*visa/usr
if (jwave .EQ. 1) zo=50/2/pi*lwave*(usr/cwave)**4.5+0.11*visa/usr !Oost et al
if (jwave .EQ. 2) zo=1200*hwave*(hwave/lwave)**4.5+0.11*visa/usr !Taylor and Yelland
rr=zo*usr/visa
L=zu/zet
zoq=min(1.15e-4,5.5e-5/rr**.6)
zot=zoq
usr=ut*von/(log(zu/zo)-psiuo(zu/L))
tsr=-(dt-dter*jcool)*von*fdg/(log(zt/zot)-psit_30(zt/L))
qsr=-(dq-wetc*dter*jcool)*von*fdg/(log(zq/zoq)-psit_30(zq/L))
Bf=-grav/ta*usr*(tsr+.61*ta*qsr)
if (Bf .GT. 0) then
ug=Beta*(Bf*zi)**.333
else
ug=.2
endif
ut=sqrt(du*du+ug*ug)
Rnl=0.97*(5.67e-8*(ts-dter*jcool+tdk)**4-Rl)
hsb=-rhoa*cpa*usr*tsr
hlb=-rhoa*Le*usr*qsr
qout=Rnl+hsb+hlb
dels=Rns*(.065+11*tkt-6.6e-5/tkt*(1-exp(-tkt/8.0e-4))) ! Eq.16 Shortwave
qcol=qout-dels
alq=Al*qcol+be*hlb*cpw/Le ! Eq. 7 Buoy flux water
if (alq .GT. 0) then
xlamx=6/(1+(bigc*alq/usr**4)**.75)**.333 ! Eq 13 Saunders
tkt=xlamx*visw/(sqrt(rhoa/rhow)*usr) !Eq.11 Sub. thk
else
xlamx=6.0
tkt=min(.01,xlamx*visw/(sqrt(rhoa/rhow)*usr)) !Eq.11 Sub. thk
endif
dter=qcol*tkt/tcw ! Eq.12 Cool skin
dqer=wetc*dter
! print *,' third guesses=',usr,tsr,qsr,ug,ut
enddo !bulk iter loop
tau=rhoa*usr*usr*du/ut !stress
hsb=-rhoa*cpa*usr*tsr
hlb=-rhoa*Le*usr*qsr
!**************** rain heat flux ********
dwat=2.11e-5*((t+tdk)/tdk)**1.94 !! water vapour diffusivity
dtmp=(1.+3.309e-3*t-1.44e-6*t*t)*0.02411/(rhoa*cpa) !!heat diffusivity
alfac= 1/(1+(wetc*Le*dwat)/(cpa*dtmp)) !! wet bulb factor
RF= rain*alfac*cpw*((ts-t-dter*jcool)+(Qs-Q-dqer*jcool)*Le/cpa)/3600
!**************** Webb et al. correection ************
wbar=1.61*hlb/Le/(1+1.61*Q)/rhoa+hsb/rhoa/cpa/ta !formulation in hlb already includes webb
!wbar=1.61*hlb/Le/rhoa+(1+1.61*Q)*hsb/rhoa/cpa/ta
hl_webb=rhoa*wbar*Q*Le
!************** compute transfer coeffs relative to ut @meas. ht **********
Cd=tau/rhoa/ut/max(.1,du)
Ch=-usr*tsr/ut/(dt-dter*jcool)
Ce=-usr*qsr/(dq-dqer*jcool)/ut
!************ 10-m neutral coeff realtive to ut ********
Cdn_10=von*von/log(10/zo)/log(10/zo)
Chn_10=von*von*fdg/log(10/zo)/log(10/zot)
Cen_10=von*von*fdg/log(10/zo)/log(10/zoq)
!**************** the Y array going back tom the main program ****************
y=(/hsb, hlb, tau, zo, zot, zoq, L, usr, tsr, qsr, dter, dqer, tkt, RF, wbar, Cd, Ch, Ce, Cdn_10, Chn_10, Cen_10, ug /)
! 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22
end subroutine
function psiuo(zet)
x=(1.-15.*zet)**.25
psik=2.*log((1.+x)/2.)+log((1.+x*x)/2.)-2.*atan(x)+2.*atan(1.)
x=(1.-10.15*zet)**.3333
psic=1.5*log((1.+x+x*x)/3.)-sqrt(3.)*atan((1.+2.*x)/sqrt(3.))+4.*atan(1.)/sqrt(3.)
f=zet*zet/(1+zet*zet)
psiuo=(1-f)*psik+f*psic
if(zet>0)then
c=min(50.,.35*zet)
psiuo=-((1+1.0*zet)**1.0+.667*(zet-14.28)/exp(c)+8.525)
endif
END FUNCTION psiuo
function psit_30(zet)
x=(1.-(15*zet))**.5
psik=2*log((1+x)/2)
x=(1.-(34.15*zet))**.3333
psic=1.5*log((1.+x+x*x)/3.)-sqrt(3.)*atan((1.+2.*x)/sqrt(3.))+4.*atan(1.)/sqrt(3.)
f=zet*zet/(1+zet*zet)
psit_30=(1-f)*psik+f*psic
if(zet>0)then
c=min(50.,.35*zet)
psit_30=-((1.+2./3.*zet)**1.5+.6667*(zet-14.28)/exp(c)+8.525)
endif
end FUNCTION psit_30
function qsee(ts,Pa)
real :: ts,Pa
x=ts
p=Pa
es=6.112*exp(17.502*x/(x+240.97))*.98*(1.0007+3.46e-6*p)
qsee=es*621.97/(p-.378*es)
end function
function grv(lat)
real lat
gamma=9.7803267715
c1=0.0052790414
c2=0.0000232718
c3=0.0000001262
c4=0.0000000007
pi=3.141593
phi=lat*pi/180
x=sin(phi)
grv=gamma*(1+(c1*x**2)+(c2*x**4)+(c3*x**6)+(c4*x**8))
!print *,'grav=',grv,lat
end function grv
#j 参考文献
#j makefile の書き方
#j http://www.eis.osakafu-u.ac.jp/~yabu/soft/makefile.html
#j Makefile小技と新バージョンのDelFEM(FEMとUIの日記@New York)
#j http://d.hatena.ne.jp/etopirika5/20091207/1260207955
#
#-----------------------------------------
#j マクロの定義
#-----------------------------------------
#j コンパイラの指定
FC=ifort
#FC=gfortran
#FC=g77
#FC=f77
#j OBJDIR (オブジェクトファイルをおくディレクトリ)
OBJDIR=./obj
#-----------------------------------------
#j コンパイルオプション(ifort)
#-----------------------------------------
#j デバッグ用オプション(はじめて実行するときには必ずこのオプションをつけてコンパイルする)
FDFLAGS= -CB -traceback -fpe0
#j コンパイルオプション
FFLAGS=-module ${OBJDIR}
#j -module : モジュールファイル(.mod)を置く場所を指定する
#j 最適化用(他にも何種類かある. ifort -helpかマニュアルを見て調べる)
#FFLAGS = -O3 -module ${OBJDIR}
#j 倍精度
#FFLAGS = -r8 -module ${OBJDIR}
#j 入力データのバイト・スワップ(大型計算機のバイナリデータを読む時などにつかう)
#FFLAGS = #-convert big_endian -module ${OBJDIR}
#-----------------------------------------
#j リンク用のオプション
#-----------------------------------------
LDFLAGS=-module ${OBJDIR}
#j ターゲット名(最終的に作りたい実行ファイル名)
TARGET1=heat.flux.toga.coare.3.0
TARGET2=
TARGETS=$(TARGET1) $(TARGET2)
#j MOD (Fortran90以降のモジュールファイル)
MOD=
#j SRC7 (Fortran77のソースファイル)
SRC7=
#j SRC9 (Fortran90のソースファイル)
SRC9=heat.flux.toga.coare.3.0.f90 \
cor30a.f90 \
psiu_30.f90 \
psit_30.f90 \
qsee.f90 \
grv.f90
#j OBJ1 (ターゲットを作るのに必要なオブジェクトファイル名)
OBJM=$(MOD:.f90=.o)
OBJ7=$(SRC7:.f=.o)
OBJ9=$(SRC9:.f90=.o)
OBJTMP=$(OBJM) $(OBJ7) $(OBJ9)
OBJ1=$(OBJTMP:%=${OBJDIR}/%)
MOD2=
#j SRC7 (Fortran77のソースファイル)
SRC72=
#j SRC9 (Fortran90のソースファイル)
SRC92=
#j OBJ (ターゲットを作るのに必要なオブジェクトファイル名)
OBJM2=$(MOD2:.f90=.o)
OBJ72=$(SRC72:.f=.o)
OBJ92=$(SRC92:.f90=.o)
OBJTMP2=$(OBJM2) $(OBJ72) $(OBJ92)
OBJ2=$(OBJTMP2:%=${OBJDIR}/%)
OBJ=$(OBJ1) $(OBJ2)
#-----------------------------------------
#j ここからコンパイルのルールの記述
#-----------------------------------------
all: mkobjd $(TARGETS)
$(TARGET1): $(OBJ1)
$(FC) -o $@ $(OBJ1) ${LDFLAGS}
$(TARGET2): $(OBJ2)
$(FC) -o $@ $(OBJ2) ${LDFLAGS}
#j 暗黙のサフィックスルールを無効にする
.SUFFIXES:
#j サフィックスの追加
.SUFFIXES: .o .f .f90
#j f77のソースファイルのコンパイル(.f用のサフィックスルール)
${OBJDIR}/%.o : %.f
$(FC) -c ${FDFLAGS} ${FFLAGS} -c -o $@ $<
#j f90のソースファイルのコンパイル(.f90用のサフィックスルール)
${OBJDIR}/%.o : %.f90
$(FC) -c ${FDFLAGS} ${FFLAGS} -c -o $@ $<
#j オブジェクトファイルを削除
clean:
rm -rf $(OBJ) ${OBJDIR}/*.mod
#j オブジェクトファイルと実行ファイルを削除
distclean:
rm -rf $(OBJ) ${OBJDIR}/*.mod $(TARGETS) \
rm -rf ${OBJDIR}
#j オブジェクトファイルを置くディレクトリを作成
mkobjd:
if [ ! -d ${OBJDIR} ]; then \
mkdir -p ${OBJDIR} ; \
fi
run:
cd .. ; \
./run.sh 2>&1 > log.txt ; \
cd src
#j tarファイルを作る
tar:
tar cvf $(TARGET1).tar ./*.f90 ./*.f ./*.c ./*.h ./*.txt makefile
#!/bin/sh
exe=heat.flux.toga.coare.3.0
infle=test3_0.txt #MandA2012Leg3.meteo.txt
ofle=test3_0_ah_out.CHECK.3.dat #MandA2012Leg3.flux.coare.3.0.txt
namelist=${exe}.namelist.txt
cat << EOF > $namelist
¶
infle="${infle}"
ofle="${ofle}"
nhead=0 !Number of header lines in input file (infle)
ndat=116 !Number of data lines in input file (infle)
zu=15.0 !anemometer hight (m)
zt=15.0 !air T height (m)
zq=15.0 !humidity height (m)
ts_depth=6.0 !bulk water temperature sensor depth (m)
jcool=1 !0=no cool skin calc, 1=do cool skin calc
jwarm=1 !0=no warm layer calc, 1 =do warm layer calc
jwave=0 !0= Charnock, 1=Oost et al, 2=Taylor and Yelland
icount=1 !
&end
EOF
$exe < $namelist
19921125132100.00 4.70 29.00 27.70 17.60 0.00 428.00 0.00 -1.73 156.07 29.15
19921125141200.00 4.10 29.00 27.70 17.70 0.00 429.00 0.00 -1.73 156.06 29.15
19921125150300.00 4.30 29.00 27.80 17.80 0.00 422.00 0.00 -1.73 156.06 29.15
19921125155500.00 4.70 29.00 27.80 17.60 0.00 412.00 0.00 -1.73 156.05 29.15
19921125164600.00 3.70 29.00 27.70 17.30 0.00 413.00 0.00 -1.73 156.04 29.16
19921125173800.00 5.10 29.00 27.30 17.60 0.00 419.00 0.00 -1.73 156.02 29.16
19921125182900.00 2.50 29.00 27.50 17.90 0.00 425.00 0.00 -1.73 156.01 29.16
19921125192000.00 3.80 29.00 27.90 17.70 50.00 427.00 0.00 -1.73 156.00 29.15
19921125201200.00 4.80 29.00 28.00 17.60 249.00 428.00 0.00 -1.73 156.00 29.14
19921125210500.00 3.90 29.00 27.80 18.30 386.00 422.00 0.00 -1.73 155.99 29.13
19921125221900.00 4.60 29.10 27.90 17.60 633.00 413.00 0.00 -1.73 155.99 29.14
19921125232700.00 5.20 29.20 28.00 18.00 881.00 409.00 0.00 -1.73 155.99 29.14
19921126001900.00 4.40 29.30 28.10 18.10 883.00 414.00 0.00 -1.73 155.98 29.20
19921126011000.00 4.00 29.30 28.10 18.60 853.00 420.00 0.00 -1.73 155.97 29.27
19921126022200.00 4.80 29.50 28.50 17.90 842.00 417.00 0.00 -1.73 155.97 29.26
19921126031300.00 4.80 29.50 28.40 18.10 779.00 411.00 0.00 -1.72 155.97 29.42
19921126041600.00 4.30 29.60 28.50 18.40 513.00 423.00 0.00 -1.72 155.96 29.59
19921126050700.00 4.40 29.50 28.60 18.90 362.00 422.00 0.00 -1.72 155.96 29.59
19921126055900.00 4.40 29.30 28.50 18.80 171.00 415.00 0.00 -1.72 155.96 29.50
19921126065500.00 4.10 29.30 28.50 17.90 26.00 410.00 0.00 -1.72 155.96 29.37
19921126074700.00 3.90 29.20 28.50 17.60 0.00 410.00 0.00 -1.72 155.95 29.37
19921126083800.00 3.20 29.30 28.50 17.80 0.00 410.00 0.00 -1.72 155.95 29.35
19921126093000.00 2.20 29.30 28.60 18.00 0.00 426.00 0.00 -1.72 155.95 29.39
19921126102100.00 1.90 29.30 28.50 18.00 0.00 414.00 0.00 -1.72 155.94 29.45
19921126111200.00 1.90 29.30 28.40 18.00 0.00 425.00 0.00 -1.72 155.94 29.42
19921126120800.00 2.50 29.20 28.40 18.00 0.00 417.00 0.00 -1.72 155.94 29.42
19921126130000.00 3.00 29.30 28.30 18.10 0.00 408.00 0.00 -1.72 155.94 29.35
19921126145300.00 2.70 29.20 28.00 18.70 0.00 412.00 0.00 -1.71 156.00 29.41
19921126154500.00 3.00 29.20 27.90 18.60 0.00 409.00 0.00 -1.72 156.02 29.31
19921126163600.00 3.10 29.20 27.90 18.50 0.00 413.00 0.00 -1.72 156.05 29.29
19921126172700.00 2.50 29.10 28.00 18.30 0.00 414.00 0.00 -1.72 156.07 29.27
19921126181900.00 1.90 29.10 28.00 18.20 0.00 409.00 0.00 -1.72 156.06 29.26
19921126191000.00 1.10 29.20 27.90 18.20 25.00 411.00 0.00 -1.72 156.06 29.27
19921126200100.00 0.80 29.20 28.00 18.40 110.00 414.00 0.00 -1.72 156.04 29.27
19921126213400.00 0.70 29.30 28.10 18.20 123.00 436.00 0.00 -1.72 156.02 29.29
19921126222600.00 2.10 29.20 27.30 18.40 116.00 445.00 0.00 -1.72 156.01 29.38
19921126231700.00 7.90 29.20 25.40 18.20 247.00 436.00 4.80 -1.72 156.00 29.31
19921127000900.00 6.60 29.30 25.90 17.70 635.00 418.00 0.00 -1.73 156.02 29.33
19921127010000.00 5.80 29.30 26.70 17.40 486.00 422.00 0.00 -1.73 156.06 29.33
19921127015100.00 4.80 29.30 26.90 17.50 356.00 429.00 0.00 -1.72 156.06 29.33
19921127024300.00 4.50 29.20 27.00 17.50 421.00 422.00 0.00 -1.72 156.05 29.36
19921127033400.00 5.20 29.20 26.80 17.90 191.00 434.00 0.00 -1.72 156.04 29.25
19921127042500.00 6.90 29.10 25.30 18.20 50.00 437.00 9.40 -1.72 156.04 29.23
19921127051700.00 5.70 29.10 25.10 17.50 72.00 434.00 1.60 -1.72 156.03 29.23
19921127060800.00 9.90 29.10 24.70 17.70 18.00 432.00 1.50 -1.72 156.01 29.24
19921127070000.00 5.20 29.10 25.00 17.60 6.00 429.00 0.00 -1.72 156.01 29.22
19921127075100.00 4.30 29.10 26.10 16.90 0.00 415.00 0.00 -1.72 155.99 29.22
19921127084200.00 3.70 29.10 26.70 16.30 0.00 414.00 0.00 -1.72 155.98 29.16
19921127093400.00 3.30 29.10 27.20 16.10 0.00 410.00 0.00 -1.72 155.98 29.15
19921127102500.00 3.90 29.00 27.50 16.20 0.00 410.00 0.00 -1.72 155.97 29.14
19921127113200.00 5.00 29.00 27.50 16.90 0.00 414.00 0.00 -1.72 155.96 29.14
19921127122600.00 5.90 29.00 27.60 17.30 0.00 415.00 0.00 -1.72 155.95 29.12
19921127134800.00 4.90 29.00 27.50 18.20 0.00 405.00 0.00 -1.72 155.95 29.11
19921127143900.00 5.20 29.00 27.60 18.30 0.00 406.00 0.00 -1.72 155.97 29.10
19921127160400.00 5.40 29.00 27.70 17.70 0.00 413.00 0.00 -1.72 156.01 29.13
19921127170000.00 4.40 29.00 27.70 17.70 0.00 416.00 0.00 -1.72 156.00 29.14
19921127175200.00 3.80 29.00 27.70 17.70 0.00 413.00 0.00 -1.73 156.00 29.12
19921127184300.00 3.10 29.00 27.70 17.60 2.00 406.00 0.00 -1.73 155.98 29.12
19921127193500.00 2.90 29.00 27.90 17.70 88.00 410.00 0.00 -1.72 156.00 29.12
19921127202600.00 2.10 29.00 27.90 17.80 276.00 410.00 0.00 -1.72 156.00 29.12
19921127211700.00 1.90 29.10 27.80 17.80 487.00 406.00 0.00 -1.72 155.99 29.12
19921127220900.00 1.60 29.20 27.70 17.70 670.00 407.00 0.00 -1.73 155.98 29.13
19921127230000.00 1.40 29.50 27.40 17.90 810.00 416.00 0.00 -1.74 155.98 29.14
19921127235200.00 1.10 30.10 27.40 17.80 917.00 410.00 0.00 -1.72 156.01 29.16
19921128004300.00 1.10 30.60 27.40 17.80 960.00 412.00 0.00 -1.72 156.00 29.14
19921128022100.00 1.50 30.80 27.70 17.90 939.00 413.00 0.00 -1.72 155.99 29.17
19921128042600.00 1.20 31.00 28.40 17.80 665.00 411.00 0.00 -1.72 156.00 29.27
19921128043600.00 1.30 31.00 28.70 17.50 493.00 410.00 0.00 -1.72 156.00 29.47
19921128052800.00 0.80 30.70 28.90 17.50 301.00 410.00 0.00 -1.72 155.99 29.23
19921128061900.00 0.60 30.60 28.90 17.60 125.00 411.00 0.00 -1.73 155.99 29.44
19921128075200.00 1.20 30.20 28.70 17.90 0.00 416.00 0.00 -1.72 156.00 29.27
19921128084300.00 1.00 30.10 28.70 17.90 0.00 417.00 0.00 -1.72 155.99 29.30
19921128093500.00 2.60 29.80 28.40 18.20 0.00 413.00 0.00 -1.72 155.99 29.30
19921128102600.00 1.80 29.50 28.50 17.50 0.00 420.00 0.00 -1.72 155.99 29.35
19921128111800.00 1.00 29.60 28.60 17.40 0.00 417.00 0.00 -1.72 155.99 29.24
19921128120900.00 2.80 29.30 28.00 18.80 0.00 411.00 0.00 -1.72 155.99 29.30
19921128130100.00 2.20 29.50 28.00 18.50 0.00 409.00 0.00 -1.72 155.98 29.56
19921128135200.00 1.60 29.40 28.10 18.10 0.00 407.00 0.00 -1.72 155.98 29.56
19921128144400.00 1.40 29.40 28.10 18.00 0.00 407.00 0.00 -1.72 155.97 29.29
19921128153500.00 1.90 29.20 28.10 17.80 0.00 407.00 0.00 -1.72 155.96 29.26
19921128162600.00 2.20 29.10 28.00 17.70 0.00 407.00 0.00 -1.72 155.95 29.26
19921128171800.00 2.30 29.10 28.00 18.00 0.00 406.00 0.00 -1.72 155.94 29.19
19921128180900.00 1.90 29.00 28.00 18.00 0.00 410.00 0.00 -1.72 155.94 29.13
19921128190100.00 2.30 29.10 28.00 17.80 14.00 407.00 0.00 -1.72 155.94 29.18
19921128195200.00 2.20 29.10 28.10 17.90 80.00 408.00 0.00 -1.72 155.97 29.17
19921128204400.00 1.60 29.20 28.10 17.50 109.00 414.00 0.00 -1.72 155.99 29.17
19921128213500.00 1.90 29.40 28.10 17.60 278.00 430.00 0.00 -1.71 156.02 29.40
19921128222600.00 1.20 29.60 27.20 18.50 614.00 425.00 0.00 -1.71 156.04 29.52
19921128231800.00 1.10 29.90 27.30 18.60 719.00 426.00 0.00 -1.71 156.05 29.52
19921129000900.00 0.50 30.40 27.10 18.40 930.00 415.00 0.00 -1.71 156.04 29.58
19921129010100.00 2.60 30.50 27.80 18.30 629.00 435.00 0.00 -1.71 156.04 29.49
19921129015200.00 2.50 30.10 27.70 17.90 838.00 418.00 0.00 -1.71 156.03 29.41
19921129024400.00 1.70 30.50 28.20 18.00 522.00 432.00 0.00 -1.71 156.03 29.41
19921129033500.00 2.10 30.30 28.50 17.70 745.00 413.00 0.00 -1.71 156.02 29.37
19921129042600.00 2.40 30.30 28.80 17.60 565.00 411.00 0.00 -1.71 156.01 29.23
19921129051800.00 2.10 30.10 28.80 17.80 209.00 430.00 0.00 -1.71 156.00 29.23
19921129060900.00 1.60 29.90 28.10 18.30 24.00 448.00 0.00 -1.72 155.98 29.32
19921129070100.00 3.70 30.00 26.60 17.90 1.00 445.00 6.50 -1.72 155.97 29.26
19921129075200.00 2.10 29.50 25.60 17.10 0.00 441.00 6.60 -1.72 155.97 29.46
19921129091700.00 2.20 29.80 27.30 17.10 0.00 410.00 0.00 -1.72 155.95 29.34
19921129100800.00 3.60 29.70 28.10 18.10 0.00 408.00 0.00 -1.72 155.95 29.33
19921129110000.00 3.20 29.40 28.20 18.40 0.00 409.00 0.00 -1.72 155.94 29.23
19921129115500.00 2.50 29.30 28.20 18.30 0.00 409.00 0.00 -1.72 155.95 29.23
19921129124700.00 2.60 29.20 28.10 18.30 0.00 407.00 0.00 -1.72 155.97 29.18
19921129133800.00 2.10 29.30 28.00 18.20 0.00 406.00 0.00 -1.72 156.00 29.40
19921129142900.00 2.10 29.50 28.00 18.20 0.00 405.00 0.00 -1.72 156.02 29.40
19921129153100.00 2.40 29.70 28.00 18.20 0.00 407.00 0.00 -1.72 156.05 29.63
19921129163800.00 3.00 29.60 28.00 18.00 0.00 411.00 0.00 -1.71 156.07 29.57
19921129173000.00 3.40 29.50 27.90 18.20 0.00 414.00 0.00 -1.72 156.06 29.49
19921129182100.00 3.10 29.40 28.00 18.00 0.00 417.00 0.00 -1.72 156.05 29.42
19921129191300.00 2.90 29.30 28.00 18.00 44.00 415.00 0.00 -1.72 156.04 29.42
19921129200400.00 3.20 29.30 27.80 18.10 213.00 418.00 0.00 -1.72 156.03 29.35
19921129205500.00 2.90 29.30 28.10 17.90 340.00 407.00 0.00 -1.72 156.02 29.35
19921129214700.00 2.40 29.40 28.00 17.90 597.00 405.00 0.00 -1.72 156.01 29.35
19921129223800.00 2.40 29.60 27.90 17.90 766.00 407.00 0.00 -1.72 156.00 29.37
19921129233000.00 2.40 29.80 27.80 17.80 900.00 411.00 0.00 -1.72 156.00 29.31
1 1992112513**00 7.18 118.59 28.86 0.02898 0.00009 0.00 0.29 0.00 19.00 1.05 0.78
2 1992112514**00 6.48 106.01 28.85 0.02215 0.00008 0.00 0.30 0.00 19.00 1.17 0.75
3 1992112515**00 5.96 107.07 28.85 0.02414 0.00008 0.00 0.30 0.00 19.00 1.13 0.74
4 1992112515**00 6.26 117.20 28.83 0.02881 0.00008 0.00 0.32 0.00 19.00 1.05 0.76
5 1992112516**00 5.79 103.25 28.81 0.01823 0.00007 0.00 0.35 0.00 19.00 1.25 0.73
6 1992112517**00 10.81 128.05 28.85 0.03473 0.00010 0.00 0.31 0.00 19.00 0.97 0.84
7 1992112518**00 5.39 71.99 28.84 0.00905 0.00006 0.00 0.32 0.00 19.00 1.59 0.68
8 1992112519**00 4.82 98.73 28.85 0.01894 0.00007 0.00 0.30 0.00 19.00 1.25 0.71
9 1992112520**00 5.10 118.70 28.86 0.02982 0.00008 0.00 0.28 0.00 19.00 1.04 0.74
10 1992112521**00 5.60 92.07 28.86 0.01990 0.00007 0.00 0.27 0.00 19.00 1.23 0.72
11 1992112522**00 5.60 115.48 28.85 0.02750 0.00008 0.00 0.29 0.00 19.00 1.07 0.75
12 1992112523**00 5.50 118.59 28.88 0.03499 0.00008 0.00 0.26 0.00 19.00 0.97 0.75
13 1992112600**00 4.61 104.60 28.94 0.02493 0.00007 0.00 0.26 0.00 19.00 1.13 0.71
14 1992112601**00 4.85 92.14 29.03 0.02071 0.00007 0.00 0.24 0.00 19.00 1.22 0.70
15 1992112602**00 2.48 114.26 29.00 0.02922 0.00007 0.00 0.26 0.00 19.00 1.05 0.69
16 1992112603**00 4.21 115.99 29.14 0.02958 0.00008 0.00 0.28 0.00 19.00 1.04 0.72
17 1992112604**00 4.61 107.84 29.35 0.02388 0.00007 0.00 0.28 0.04 6.21 1.14 0.72
18 1992112605**00 3.94 100.21 29.35 0.02472 0.00007 0.00 0.27 0.04 8.75 1.13 0.70
19 1992112605**00 3.75 98.60 29.22 0.02468 0.00007 0.00 0.29 0.02 13.92 1.12 0.69
20 1992112606**00 2.46 103.12 29.04 0.02143 0.00006 0.00 0.33 0.00 19.00 1.18 0.67
21 1992112607**00 2.29 103.40 29.03 0.01949 0.00006 0.00 0.34 0.00 19.00 1.22 0.67
22 1992112608**00 1.82 85.18 29.00 0.01336 0.00005 0.00 0.35 0.00 19.00 1.40 0.62
23 1992112609**00 1.26 63.87 29.07 0.00685 0.00004 0.00 0.32 0.00 19.00 1.72 0.56
24 1992112610**00 1.61 59.04 29.10 0.00541 0.00004 0.00 0.35 0.00 19.00 1.78 0.56
25 1992112611**00 1.97 59.56 29.09 0.00546 0.00004 0.00 0.33 0.00 19.00 1.80 0.57
26 1992112612**00 2.30 71.18 29.08 0.00868 0.00005 0.00 0.34 0.00 19.00 1.60 0.61
27 1992112613**00 2.73 78.53 29.00 0.01199 0.00005 0.00 0.35 0.00 19.00 1.45 0.63
28 1992112614**00 4.31 68.77 29.07 0.01011 0.00005 0.00 0.34 0.00 19.00 1.53 0.65
29 1992112615**00 4.65 73.65 28.97 0.01220 0.00005 0.00 0.34 0.00 19.00 1.45 0.67
30 1992112616**00 4.71 76.51 28.96 0.01295 0.00006 0.00 0.33 0.00 19.00 1.42 0.67
31 1992112617**00 3.44 66.78 28.93 0.00878 0.00005 0.00 0.34 0.00 19.00 1.60 0.63
32 1992112618**00 2.76 56.09 28.91 0.00551 0.00004 0.00 0.35 0.00 19.00 1.77 0.59
33 1992112619**00 2.37 41.60 28.93 0.00235 0.00003 0.00 0.34 0.00 19.00 2.02 0.54
34 1992112620**00 1.85 34.43 28.96 0.00146 0.00002 0.00 0.31 0.00 19.00 2.15 0.51
35 1992112621**00 1.73 34.44 29.04 0.00122 0.00002 0.00 0.25 0.00 19.00 2.30 0.50
36 1992112622**00 6.92 65.04 29.11 0.00691 0.00006 0.00 0.27 0.00 19.00 1.75 0.70
37 1992112623**00 39.80 180.55 29.05 0.09219 0.00021 21.13 0.26 0.00 19.00 0.62 1.16
38 1992112700**00 29.30 167.15 29.04 0.06222 0.00018 0.00 0.29 0.00 19.00 0.74 1.07
39 1992112701**00 19.02 154.73 29.03 0.04653 0.00014 0.00 0.30 0.00 19.00 0.85 0.96
40 1992112701**00 14.99 132.48 29.03 0.03152 0.00012 0.00 0.30 0.00 19.00 1.01 0.90
41 1992112702**00 13.70 126.83 29.05 0.02768 0.00011 0.00 0.31 0.00 19.00 1.06 0.88
42 1992112703**00 16.14 130.43 28.97 0.03692 0.00012 0.00 0.28 0.00 19.00 0.94 0.91
43 1992112704**00 36.00 159.60 28.96 0.06906 0.00019 40.87 0.27 0.00 19.00 0.71 1.12
44 1992112705**00 33.04 154.14 28.92 0.04687 0.00018 7.57 0.31 0.00 19.00 0.84 1.09
45 1992112706**00 57.13 233.04 28.97 0.15337 0.00029 7.16 0.27 0.00 19.00 0.48 1.29
46 1992112707**00 31.72 142.23 28.89 0.03905 0.00017 0.00 0.33 0.00 19.00 0.91 1.07
47 1992112707**00 18.80 132.48 28.85 0.02611 0.00013 0.00 0.37 0.00 19.00 1.08 0.94
48 1992112708**00 12.26 124.32 28.77 0.01922 0.00010 0.00 0.39 0.00 19.00 1.21 0.86
49 1992112709**00 8.02 113.72 28.75 0.01523 0.00009 0.00 0.40 0.00 19.00 1.32 0.78
50 1992112710**00 7.08 125.50 28.76 0.02049 0.00009 0.00 0.38 0.00 19.00 1.19 0.78
51 1992112711**00 8.76 137.13 28.81 0.03321 0.00010 0.00 0.33 0.00 19.00 0.98 0.82
52 1992112712**00 9.08 145.97 28.82 0.04636 0.00011 0.00 0.30 0.00 19.00 0.85 0.84
53 1992112713**00 8.47 110.27 28.80 0.03154 0.00009 0.00 0.31 0.00 19.00 1.01 0.79
54 1992112714**00 8.06 112.69 28.80 0.03540 0.00009 0.00 0.30 0.00 19.00 0.96 0.78
55 1992112716**00 7.73 128.24 28.83 0.03832 0.00009 0.00 0.30 0.00 19.00 0.93 0.80
56 1992112717**00 6.62 110.50 28.82 0.02537 0.00008 0.00 0.32 0.00 19.00 1.11 0.76
57 1992112717**00 5.72 98.33 28.79 0.01907 0.00007 0.00 0.33 0.00 19.00 1.24 0.73
58 1992112718**00 4.75 84.91 28.76 0.01305 0.00006 0.00 0.36 0.00 19.00 1.41 0.69
59 1992112719**00 3.57 78.82 28.78 0.01143 0.00005 0.00 0.34 0.00 19.00 1.48 0.65
60 1992112720**00 2.92 62.31 28.80 0.00653 0.00004 0.00 0.32 0.00 19.00 1.74 0.61
61 1992112721**00 3.61 61.09 28.91 0.00562 0.00004 0.00 0.31 0.11 1.41 1.80 0.62
62 1992112722**00 4.41 60.03 29.12 0.00436 0.00005 0.00 0.30 0.29 1.55 1.90 0.64
63 1992112723**00 6.35 60.49 29.43 0.00368 0.00005 0.00 0.27 0.56 1.53 1.99 0.68
64 1992112723**00 6.83 59.77 29.77 0.00264 0.00005 0.00 0.28 0.89 1.50 2.05 0.69
65 1992112800**00 8.10 65.43 30.11 0.00271 0.00006 0.00 0.29 1.26 1.45 2.01 0.72
66 1992112802**00 10.67 84.93 30.69 0.00437 0.00008 0.00 0.35 1.87 1.46 1.80 0.79
67 1992112804**00 1.28 45.33 29.02 0.00259 0.00003 0.00 0.25 0.00 19.00 2.16 0.52
68 1992112804**00 1.09 51.70 29.23 0.00294 0.00003 0.00 0.30 0.06 0.32 2.03 0.53
69 1992112805**00 -0.13 35.41 28.98 0.00132 0.00002 0.00 0.29 0.04 1.27 2.21 0.42
70 1992112806**00 0.16 32.64 29.13 0.00090 0.00002 0.00 0.31 0.02 19.00 2.18 0.43
71 1992112807**00 0.24 41.88 28.94 0.00249 0.00002 0.00 0.33 0.00 19.00 2.03 0.46
72 1992112808**00 0.31 38.39 28.98 0.00189 0.00002 0.00 0.32 0.00 19.00 2.09 0.45
73 1992112809**00 1.82 68.14 28.96 0.00918 0.00004 0.00 0.34 0.00 19.00 1.58 0.59
74 1992112810**00 1.24 60.00 29.01 0.00495 0.00004 0.00 0.34 0.00 19.00 1.82 0.55
75 1992112811**00 0.39 41.34 28.91 0.00192 0.00002 0.00 0.33 0.00 19.00 2.08 0.47
76 1992112812**00 3.90 66.99 28.97 0.01069 0.00005 0.00 0.33 0.00 19.00 1.51 0.64
77 1992112813**00 4.31 64.42 29.20 0.00719 0.00005 0.00 0.36 0.00 19.00 1.66 0.64
78 1992112813**00 3.14 55.68 29.18 0.00425 0.00004 0.00 0.38 0.00 19.00 1.83 0.60
79 1992112814**00 2.05 48.11 28.93 0.00336 0.00003 0.00 0.36 0.00 19.00 1.92 0.55
80 1992112815**00 2.35 59.23 28.89 0.00550 0.00004 0.00 0.37 0.00 19.00 1.76 0.58
81 1992112816**00 3.00 66.78 28.89 0.00708 0.00005 0.00 0.37 0.00 19.00 1.67 0.62
82 1992112817**00 2.81 64.22 28.83 0.00757 0.00004 0.00 0.36 0.00 19.00 1.65 0.61
83 1992112818**00 2.28 55.68 28.78 0.00546 0.00004 0.00 0.35 0.00 19.00 1.78 0.57
84 1992112819**00 2.77 66.20 28.82 0.00758 0.00004 0.00 0.36 0.00 19.00 1.65 0.61
85 1992112819**00 2.28 62.66 28.82 0.00697 0.00004 0.00 0.35 0.00 19.00 1.69 0.59
86 1992112820**00 1.91 54.80 28.83 0.00414 0.00004 0.00 0.34 0.00 19.00 1.89 0.56
87 1992112821**00 3.20 65.34 29.11 0.00561 0.00005 0.00 0.29 0.00 19.00 1.82 0.62
88 1992112822**00 5.97 49.35 29.28 0.00290 0.00004 0.00 0.24 0.00 19.00 2.11 0.66
89 1992112823**00 5.47 46.56 29.31 0.00253 0.00004 0.00 0.21 0.00 19.00 2.21 0.64
90 1992112900**00 4.91 38.05 29.40 0.00090 0.00004 0.00 0.18 0.00 19.00 2.50 0.61
91 1992112901**00 6.08 76.62 29.24 0.00973 0.00006 0.00 0.25 0.00 19.00 1.60 0.70
92 1992112901**00 6.02 77.95 29.16 0.00912 0.00006 0.00 0.27 0.04 13.64 1.62 0.70
93 1992112902**00 2.98 58.52 29.21 0.00466 0.00004 0.00 0.24 0.08 11.72 1.96 0.60
94 1992112903**00 1.74 65.98 29.10 0.00641 0.00004 0.00 0.27 0.00 19.00 1.79 0.58
95 1992112904**00 0.62 71.27 29.10 0.00788 0.00004 0.00 0.30 0.16 1.22 1.68 0.56
96 1992112905**00 0.27 61.47 29.02 0.00620 0.00004 0.00 0.28 0.07 2.78 1.80 0.52
97 1992112906**00 2.75 52.15 29.08 0.00420 0.00004 0.00 0.26 0.01 5.90 1.98 0.58
98 1992112907**00 14.13 104.08 28.96 0.01925 0.00010 27.39 0.30 0.00 19.00 1.23 0.86
99 1992112907**00 15.49 86.56 29.10 0.00756 0.00009 32.84 0.36 0.00 19.00 1.62 0.86
100 1992112909**00 6.45 78.26 28.95 0.00748 0.00006 0.00 0.39 0.00 19.00 1.62 0.71
101 1992112910**00 4.26 91.23 28.99 0.01699 0.00006 0.00 0.34 0.00 19.00 1.29 0.69
102 1992112911**00 2.84 76.36 28.90 0.01342 0.00005 0.00 0.33 0.00 19.00 1.41 0.63
103 1992112911**00 2.32 64.65 28.89 0.00862 0.00004 0.00 0.34 0.00 19.00 1.61 0.59
104 1992112912**00 2.60 65.89 28.84 0.00926 0.00004 0.00 0.34 0.00 19.00 1.57 0.61
105 1992112913**00 3.48 62.35 29.03 0.00658 0.00004 0.00 0.37 0.00 19.00 1.69 0.62
106 1992112914**00 3.47 62.30 29.03 0.00658 0.00004 0.00 0.37 0.00 19.00 1.69 0.62
107 1992112915**00 4.85 72.94 29.25 0.00840 0.00005 0.00 0.38 0.00 19.00 1.59 0.67
108 1992112916**00 5.43 86.81 29.21 0.01241 0.00006 0.00 0.36 0.00 19.00 1.42 0.70
109 1992112917**00 6.19 91.29 29.15 0.01559 0.00007 0.00 0.34 0.00 19.00 1.33 0.73
110 1992112918**00 4.85 85.68 29.08 0.01306 0.00006 0.00 0.34 0.00 19.00 1.41 0.69
111 1992112919**00 4.60 81.54 29.08 0.01158 0.00006 0.00 0.34 0.00 19.00 1.47 0.68
112 1992112920**00 5.83 86.28 29.03 0.01393 0.00006 0.00 0.32 0.00 19.00 1.39 0.71
113 1992112920**00 3.78 80.79 29.02 0.01146 0.00006 0.00 0.33 0.00 19.00 1.48 0.66
114 1992112921**00 3.85 71.62 29.04 0.00828 0.00005 0.00 0.31 0.00 19.00 1.64 0.65
115 1992112922**00 4.50 72.99 29.08 0.00835 0.00005 0.00 0.29 0.00 19.00 1.65 0.66
116 1992112923**00 4.80 73.86 29.04 0.00839 0.00005 0.00 0.27 0.00 19.00 1.66 0.67