femwind_wrfout calling femwind #4
[wrf-fire-matlab.git] / detection / sfire_simple.f90
blob14edafcc52db5e379629462f1199a6b98321724d
1 program sfire_simple
2 implicit none
3 double precision, allocatable,dimension(:,:)::t0,t1,mask,r11,r12,r13,r21,r23,r31,r32,r33
4 integer::m,n,i,j,k,nsteps,changed,masked
5 double precision::diff,a
6 open(1,file='r.dat',form='unformatted',status='old')
7 read(1)m,n
8 allocate(t0(m,n))
9 allocate(t1(m,n))
10 allocate(mask(m,n))
11 allocate(r11(m,n))
12 allocate(r12(m,n))
13 allocate(r13(m,n))
14 allocate(r21(m,n))
15 allocate(r23(m,n))
16 allocate(r31(m,n))
17 allocate(r32(m,n))
18 allocate(r33(m,n))
19 read(1)r11
20 read(1)r12
21 read(1)r13
22 read(1)r21
23 read(1)r23
24 read(1)r31
25 read(1)r32
26 read(1)r33
27 close(1)
28 open(1,file='in.dat',form='unformatted',status='old')
29 read(1)nsteps
30 read(1)t0
31 read(1)mask
32 close(1)
34 t1=t0; ! keep old where not updated
35 do k=1,nsteps
36 diff=0.
37 changed=0
38 masked=0
39 do j=2,n-1
40 do i=2,m-1
41 if(mask(i,j)>0.)then
42 t1(i,j)=min(t0(i-1,j)+r32(i-1,j), &
43 t0(i+1,j)+r12(i+1,j), &
44 t0(i,j-1)+r23(i,j-1), &
45 t0(i,j+1)+r21(i,j+1), &
46 t0(i-1,j-1)+r33(i-1,j-1), &
47 t0(i+1,j-1)+r13(i+1,j-1), &
48 t0(i-1,j+1)+r31(i-1,j+1), &
49 t0(i+1,j+1)+r11(i+1,j+1))
50 a=abs(t1(i,j)-t0(i,j))
51 if(a>0.)then
52 changed=changed+1
53 diff=max(diff,a)
54 endif
55 else
56 masked=masked+1
57 endif
58 enddo
59 enddo
60 t0=t1
61 print *,'iter ',k,' diff ',diff,' changed ',changed,' masked ',masked
62 enddo
63 open(1,file='out.dat',form='unformatted',status='unknown')
64 write(1)t1
65 close(1)
66 end program sfire_simple