!**********************************************************************! ! ! File: afire.f90 (21-Jun-2001) ! (21-Jun-2005) ! ! Hilfsprogramm zur Waldbrand-Simulation (Gittermodell) ! ! Lesen der Ergebnisse einer Simulation von Binaerfile und Ausgabe der ! Wahrscheinlichkeitsdichte der verbrannten Areale in ASCII-File ! "afire.dat" ! !**********************************************************************! program afire !**********************************************************************! implicit none integer,parameter::iin=1,iout=2 character(len=100)::fname integer::i,istat,istep,ns,nx,ny integer,dimension(:),allocatable::ihist real::fact write(unit=*,fmt="("" fname="")",advance="no") read(unit=*,fmt="(a)") fname open(unit=iin,file=fname,status="old",action="read", & form="unformatted") read(unit=iin) nx,istep,ns!,iran ny=nx allocate(ihist(1:nx*ny),stat=istat) if(istat/=0) then close(unit=iin) write(unit=*,fmt="("" afire: can't allocate"")") stop end if read(unit=iin) !lattice read(unit=iin) ihist close(unit=iin) write(unit=*,fmt="("" nx=ny="",i10)") nx write(unit=*,fmt="("" 1/f_m="",i10)") ns write(unit=*,fmt="("" steps="",i10)") istep ! Wahrscheinlichkeitsdichte und komplementaere kumulative ! Wahrscheinlichkeitsverteilung auf File schreiben open(unit=iout,file="afire.dat",status="replace",action="write", & form="formatted") fact=1.0/sum(ihist) do i=1,nx*ny if(ihist(i)/=0) then write(unit=iout,fmt="(tr1,i10,2(tr1,es14.7))") & i,fact*ihist(i),fact*sum(ihist(i:nx*ny)) end if end do close(unit=iout) end program afire !**********************************************************************!