1 |
program hadley3 |
2 |
|
3 |
c*** This subroutine calculates analysis errors using greg`s |
4 |
c*** ensemble square root filter, or the traditional ensemble |
5 |
c*** kalman filter. |
6 |
c*** |
7 |
c*** Written by: Sai Ravela |
8 |
c*** Last modified: Feb 2, 2003 |
9 |
|
10 |
implicit none |
11 |
|
12 |
integer i, j, k, ijuli, isteps |
13 |
integer nens ! ensemble size |
14 |
integer iters ! number of iterations |
15 |
integer n ! state size, calculated from |
16 |
integer nx, ny, nz ! physical dimension sizes, and |
17 |
integer nf ! number of observed variables |
18 |
integer mobs, isai |
19 |
integer ii, jj, zob, xob, yob |
20 |
#include "hadley3.h" |
21 |
integer iobsloc(mobs) ! obs locations, in terms of |
22 |
! dimensions in the state vector. |
23 |
! Indicated with the matrix H in KF |
24 |
! literature. |
25 |
! In practical terms, the numbers |
26 |
! the locations of the words in the |
27 |
! pickup file |
28 |
integer indxa |
29 |
real*8 ytrue(n) ! state vector |
30 |
real*8 yobs(mobs) ! current observations of state |
31 |
real*8 ytmp(n) ! tmp state vector |
32 |
real*8 pert(n), R(mobs), yobsfull(n), ave(n), var(n) |
33 |
real*8 xens(n,nens) |
34 |
real*8 var_obs, eps, dt, x |
35 |
real*8 obserr, analerr, distsub, distobs |
36 |
integer iret, system |
37 |
real*4 mask(ny,nx) |
38 |
|
39 |
c*** open some output files |
40 |
open(unit=2,file='test.dat',status='unknown') |
41 |
c open(unit=3,file='fields.dat',status='unknown') |
42 |
|
43 |
c*** initialisations |
44 |
eps=0.0005 ! obs error variance - 1/2 mm/s |
45 |
! only good for u and v |
46 |
! need to vary this for |
47 |
! different variables |
48 |
|
49 |
c*** Here is where you read iobsloc and set the corresponding |
50 |
c variances. |
51 |
call ReadObsLoc(3,mobs,iobsloc) |
52 |
write (*,*) 'iobsloc set',mobs, iobsloc(mobs), nens |
53 |
var_obs=eps**2 |
54 |
do i=1,mobs |
55 |
c why the if/then? |
56 |
if (iobsloc(i) < nx*ny*nz*3) then |
57 |
R(i)=var_obs |
58 |
else |
59 |
R(i) = 0.1 ! 0.9 deg other |
60 |
end if |
61 |
enddo |
62 |
|
63 |
c*** get initial observations -- assumes that model has |
64 |
c already spun up (how long?) |
65 |
|
66 |
write (*,*) 'getting Truth' |
67 |
call ReadPickup(0,n,nx,ny,nz,ytrue) |
68 |
write (*,*) 'got Truth' |
69 |
|
70 |
c*** fantasy observations |
71 |
write (*,*) 'generating observations' |
72 |
call random2(pert,n) |
73 |
yobsfull = ytrue+eps*pert |
74 |
c*** apply observation mask |
75 |
do i = 1,mobs |
76 |
indxa = iobsloc(i) |
77 |
yobs(i) = yobsfull(indxa) |
78 |
end do |
79 |
|
80 |
write (*,*) 'generating ensemble' |
81 |
do i=1,nens |
82 |
call random2(pert,n) |
83 |
do j=1,n |
84 |
xens(j,i)=yobsfull(j)+eps*pert(j) |
85 |
ytmp(j)=xens(j,i) |
86 |
enddo |
87 |
call WritePickUp(i,n,nx,ny,nz,ytmp) |
88 |
enddo |
89 |
|
90 |
c*** main iteration loop |
91 |
do i=1,iters |
92 |
|
93 |
c*** step truth forward |
94 |
write (*,*) 'Stepping Truth' |
95 |
call Model(0) |
96 |
c call ReadPickup(0,n,nx,ny,nz,ytmp) |
97 |
c call WritePickUp(0,n,nx,ny,nz,ytmp) |
98 |
write (*,*) 'Stepped Truth' |
99 |
|
100 |
write (*,*) 'getting Truth' |
101 |
call ReadPickup(0,n,nx,ny,nz,ytrue) |
102 |
write (*,*) 'got Truth' |
103 |
|
104 |
c*** fantasy observations |
105 |
write (*,*) 'generating observations' |
106 |
call random2(pert,n) |
107 |
yobsfull = ytrue+eps*pert |
108 |
c*** apply observation mask |
109 |
do j = 1,mobs |
110 |
indxa = iobsloc(j) |
111 |
yobs(j) = yobsfull(indxa) |
112 |
end do |
113 |
|
114 |
c*** step ensemble forward |
115 |
write (*,*) 'Stepping Ensemble' |
116 |
do j=1,nens |
117 |
call Model(j) |
118 |
call ReadPickUp(j,n,nx,ny,nz,ytmp) |
119 |
do k=1,n |
120 |
xens(k,j)=ytmp(k) |
121 |
enddo |
122 |
enddo |
123 |
write (*,*) 'Stepped Ensemble' |
124 |
|
125 |
|
126 |
call EnSRF3d(xens,yobs,iobsloc,n,mobs,R,nens,nx,ny,nz,mask) |
127 |
|
128 |
do j=0,nens |
129 |
do k=1,n |
130 |
ytmp(k)=xens(k,j) |
131 |
enddo |
132 |
call WritePickUp(j,n,nx,ny,nz,ytmp) |
133 |
enddo |
134 |
|
135 |
|
136 |
c*** get ensemble mean and variance |
137 |
call ranmean2(xens,ave,n,nens) |
138 |
call ranvar(xens,ave,n,nens,var) |
139 |
|
140 |
c*** calculate obs and anal err |
141 |
obserr=distsub(yobs,yobsfull,n) |
142 |
analerr=distsub(yobs,ave,n) |
143 |
write(6,*) "\tOBSERR\t", "\tANALERR" |
144 |
write(6,*) obserr, analerr |
145 |
write(2,*) iters, obserr, analerr |
146 |
write(3,'(250f18.10)') (ave(i), i=1,n) |
147 |
|
148 |
call flush() |
149 |
|
150 |
enddo |
151 |
|
152 |
return |
153 |
end |
154 |
|