/[MITgcm]/MITgcm_contrib/osse/EnKF/hadley3.F
ViewVC logotype

Diff of /MITgcm_contrib/osse/EnKF/hadley3.F

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

revision 1.1 by afe, Tue May 4 18:19:34 2004 UTC revision 1.2 by afe, Thu May 13 23:45:43 2004 UTC
# Line 1  Line 1 
1          program hadley3        program hadley3
2    
3  c***  This subroutine calculates analysis errors using greg's  c***  This subroutine calculates analysis errors using greg`s
4  c***  ensemble square root filter, or the traditional ensemble  c***  ensemble square root filter, or the traditional ensemble
5  c***  kalman filter.  c***  kalman filter.
6  c***  c***
# Line 9  c***  Last modified: Feb 2, 2003 Line 9  c***  Last modified: Feb 2, 2003
9    
10          implicit none          implicit none
11    
12          integer i, j, k, n, ijim, ijuli, isteps, nens, ics          integer i, j, k, ijuli, isteps
13          integer nx, ny, nz, nf, nnx, nny, nnz, mobs, isai          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          integer ii, jj, zob, xob, yob
20  #include "hadley3.h"  #include "hadley3.h"
21          integer iobsloc(mobs), indxa          integer iobsloc(mobs)   ! obs locations, in terms of
22          real*8    ytrue(n),  yobs(mobs), ytmp(n)                                  ! 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)          real*8    pert(n),  R(mobs), yobsfull(n), ave(n), var(n)
33          real*8    xens(n,nens)          real*8    xens(n,nens)
34          real*8    var_obs, eps, dt, x          real*8    var_obs, eps, dt, x
# Line 27  c***  open some output files Line 41  c***  open some output files
41  c        open(unit=3,file='fields.dat',status='unknown')  c        open(unit=3,file='fields.dat',status='unknown')
42    
43  c***  initialisations  c***  initialisations
44          eps=0.005               ! obs error - 1/2 mm/s          eps=0.0005              ! obs error variance - 1/2 mm/s
45          isteps=1        ! number of steps per obs cycle                                  ! only good for u and v
46                                    ! need to vary this for
47  c***    Here is where you read iobsloc and corresponding                                  ! different variables
48  c       variances. You should know  
49  c       mobs in advance...in hadley  c***    Here is where you read iobsloc and set the corresponding
50    c     variances.  
51          call ReadObs(3,mobs,iobsloc)          call ReadObsLoc(3,mobs,iobsloc)
52          write (*,*) 'iobsloc set',mobs, iobsloc(mobs), nens          write (*,*) 'iobsloc set',mobs, iobsloc(mobs), nens
53          var_obs=eps**2          var_obs=eps**2
54          do i=1,mobs          do i=1,mobs
55           if (iobsloc(i) < nx*ny*nz*3) then  c     why the if/then?
56               if (iobsloc(i) < nx*ny*nz*3) then
57              R(i)=var_obs              R(i)=var_obs
58           else           else
59              R(i) = 0.1    ! 0.9 deg other              R(i) = 0.1          ! 0.9 deg other
60           end if           end if
61          enddo        enddo
62    
63    c*** get initial observations -- assumes that model has
64    c    already spun up (how long?)
65    
66  c***  loop over initial conditions          write (*,*) 'getting Truth'        
67          do ijim=1,ics          call ReadPickup(0,n,nx,ny,nz,ytrue)
68                      write (*,*) 'got Truth'
69             call ReadPickup(0,n,nx,ny,nz,ytrue)  
70             write (*,*) 'Picked Truth'  c***  fantasy observations
71             do k = 1,mobs          write (*,*) 'generating observations'      
72                indxa = iobsloc(k)          call random2(pert,n)
73                yobs(k) = ytrue(indxa)          yobsfull = ytrue+eps*pert
74             end do  c*** apply observation mask
75             do isai=1,nens          do i = 1,mobs
76                call ReadPickUp(isai,n,nx,ny,nz,ytmp)             indxa = iobsloc(i)
77                do k=1,n             yobs(i) = yobsfull(indxa)
78                   xens(k,isai)=ytmp(k)          end do
79                enddo  
80             enddo              write (*,*) 'generating ensemble'          
81             write (*,*) 'Picked Ensemble'          do i=1,nens
82            call EnSRF3d(xens,yobs,iobsloc,n,mobs,R,nens,nx,ny,nz,mask)                   call random2(pert,n)          
83  c***    get ensemble mean and variance             do j=1,n
84             call ranmean2(xens,ave,n,nens)                xens(j,i)=yobsfull(j)+eps*pert(j)
85  c***    calculate obs and anal err                ytmp(j)=xens(j,i)
86             analerr=distobs(yobs,ave,iobsloc,mobs,n)             enddo
87             write(6,*) ijim, analerr             call  WritePickUp(i,n,nx,ny,nz,ytmp)
88             write(2,*) ijim, analerr          enddo    
89             analerr=distsub(ytrue,ave,n)  
90             write(6,*) '>',ijim, analerr  c***  main iteration loop
91             write(2,*) '>',ijim, analerr          do i=1,iters
 c       write(3,'(250f18.10)') (ave(i), i=1,n)  
             
92    
93  c***    step truth forward  c***  step truth forward
94               write (*,*) 'Stepping Truth'
95             call Model(0)             call Model(0)
96             call ReadPickup(0,n,nx,ny,nz,ytmp)    c     call ReadPickup(0,n,nx,ny,nz,ytmp)  
97             call  WritePickUp(0,n,nx,ny,nz,ytmp)  c     call  WritePickUp(0,n,nx,ny,nz,ytmp)
98             write (*,*) 'Stepped Truth'             write (*,*) 'Stepped Truth'
99  c***    step ensemble forward  
100             do isai=1,nens             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                do k=1,n
120                   ytmp(k)=xens(k,isai)                   xens(k,j)=ytmp(k)
121                enddo                enddo
               call  WritePickUp(isai,n,nx,ny,nz,ytmp)  
               call Model(isai)  
122             enddo                       enddo          
123             write (*,*) 'Stepped Ensemble'             write (*,*) 'Stepped Ensemble'
124             call flush()  
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          enddo
151                    
152          return          return

Legend:
Removed from v.1.1  
changed lines
  Added in v.1.2

  ViewVC Help
Powered by ViewVC 1.1.22