! linfiles.f90 ! module procedure written by Tim Mitchell in April 2001 ! contains all routines for loading data from .lin files ! LoadLin, LoadLinAuto, SaveLin module LinFiles use FileNames implicit none contains !******************************************************************************* subroutine LoadLin (CallFile, YearAD, Names, Data) integer, pointer, dimension (:) :: YearAD ! years AD of full job character (len=80), pointer, dimension (:) :: Names ! names of individual lines real, pointer, dimension (:,:) :: Data ! datum: line, year real, allocatable, dimension (:,:) :: FileTimes real, parameter :: MissVal = -999.0 real :: TimMin, TimMax real :: TotalMiss, PerCentMiss character (len=80) :: GivenFile, LinFilePath, LinTitle, CallFile, CallTitle character (len=10) :: LinFormat integer :: TimeN,YearN,LineN integer :: XLine, XTime integer :: AllocStat ! status of allocation statement integer :: ReadStatus ! status of user input integer :: XLineTime, XLineStart integer :: XOutTime, XOutStart !*************************************** LinFilePath = LoadPath (CallFile,".lin") open (2, file=LinFilePath, status="old", access="sequential", form="formatted", & action="read") read (2, fmt="(A80)"), LinTitle read (2, fmt="(A10)"), LinFormat read (2, fmt="(2I6)"), LineN, TimeN allocate (Names (LineN), & YearAD (TimeN), & FileTimes (LineN, TimeN), & Data (LineN, TimeN), stat=AllocStat) if (AllocStat.NE.0) print*, " > ##### ERROR: LoadLin: Allocation failure #####" YearAD = MissVal do XLine = 1, LineN read (2, fmt="(a80)"), Names (XLine) end do do XLine = 1, LineN do XTime = 1, TimeN read (2, fmt=LinFormat), FileTimes (XLine, XTime) if (FileTimes(XLine,XTime).NE.MissVal.AND.YearAD(XTime).EQ.MissVal) & YearAD(XTime) = nint(FileTimes(XLine,XTime)) end do end do do XLine = 1, LineN do XTime = 1, TimeN read (2, fmt=LinFormat), Data (XLine, XTime) end do end do close (2) end subroutine LoadLin !******************************************************************************* subroutine LoadLinAuto (YearAD, Names, Data) integer, pointer, dimension (:) :: YearAD ! years AD of full job character (len=80), pointer, dimension (:) :: Names ! names of individual lines real, pointer, dimension (:,:) :: Data ! datum: line, year real, parameter :: MissVal = -999.0 real :: RealDatum character (len=80) :: GivenFile, FilePath, Title character (len=10) :: Format integer :: YearN, ColN ! no. time steps in file integer :: XCol, XYear integer :: AllocStat ! status of allocation statement integer :: ReadStatus ! status of user input print*, " > Enter the filepath of the .lin file to load: " do do read (*,*,iostat=ReadStatus), GivenFile if (ReadStatus.LE.0) exit end do inquire (file=GivenFile, name=FilePath) open (1, file=FilePath, status="old", iostat=ReadStatus) if (ReadStatus .EQ. 0) close (1) if (ReadStatus .EQ. 0) exit end do open (2, file=FilePath, status="old", access="sequential", form="formatted", & action="read") read (2, fmt="(A80)"), Title print*, adjustl(trim(Title)) read (2, fmt="(A10)"), Format read (2, fmt="(2I6)"), ColN, YearN allocate (Names (ColN), & YearAD (YearN), & Data (ColN, YearN), stat=AllocStat) if (AllocStat.NE.0) print*, " > ##### ERROR: LoadLinAuto: Allocation failure #####" Names = "" ; YearAD = MissVal ; Data = MissVal do XCol = 1, ColN read (2, fmt="(a80)"), Names (XCol) end do do XCol = 1, ColN do XYear = 1, YearN read (2, fmt=Format), RealDatum if (YearAD(XYear).EQ.MissVal) YearAD(XYear) = nint (RealDatum) end do end do do XCol = 1, ColN do XYear = 1, YearN read (2, fmt=Format), Data (XCol, XYear) end do end do close (2) end subroutine LoadLinAuto !******************************************************************************* subroutine SaveLin (CallFile, CallTitle, Names, YearAD, Data) character (len=80), pointer, dimension (:) :: Names ! names of individual lines integer, pointer, dimension (:) :: YearAD ! year AD of each time step real, pointer, dimension (:,:) :: Data ! datum: line, year real, parameter :: MissVal = -999.0 character (len=80) :: GivenFile, LinFilePath, LinTitle, CallFile, CallTitle character (len=10) :: LinFormat integer :: XLine, XTime, LineN, YearN integer :: AllocStat ! status of allocation statement integer :: ReadStatus ! status of user input !*************************************** YearN = size(YearAD) ; LineN = size(Names) LinFilePath = SavePath (CallFile,".lin") if (CallTitle.EQ."") then print*, " > Enter the .lin file title: " do read (*,*,iostat=ReadStatus), LinTitle if (ReadStatus.LE.0.AND.LinTitle.NE."") exit end do else LinTitle = CallTitle end if LinFormat = "(E12.4)" open (2, file=LinFilePath, status="replace", access="sequential", form="formatted", & action="write") write (2, fmt="(A80)"), LinTitle write (2, fmt="(A10)"), LinFormat write (2, fmt="(2I6)"), LineN, YearN do XLine = 1, LineN write (2, fmt="(a80)"), Names (XLine) end do do XLine = 1, LineN do XTime = 1, YearN write (2, fmt=LinFormat), real (YearAD (XTime)) end do end do do XLine = 1, LineN do XTime = 1, YearN write (2, fmt=LinFormat), Data (XLine, XTime) end do end do close (2) end subroutine SaveLin !******************************************************************************* end module LinFiles