! makecruts.f90 ! program to convert raw data files to CRU ts format ! written by Dr. Tim Mitchell (Tyndall Centre) on 05.02.02 ! last modified on 01.05.02 ! f90 -o ./../cruts/makecruts time.f90 filenames.f90 grimfiles.f90 crutsfiles.f90 wmokey.f90 ! ./../cruts/makecruts.f90 program MakeCRUts use Time use FileNames use GrimFiles use CRUtsFiles use WMOkey implicit none real, pointer, dimension (:) :: Lat,Long,Elev real, allocatable, dimension (:) :: RawMulti integer, pointer, dimension (:,:,:) :: Raw integer, pointer, dimension (:,:) :: StnInfo integer, allocatable, dimension (:,:) :: CountYrMon,CountYrStn integer, allocatable, dimension (:) :: RawMissVals,CheckStn,FileLines,LineData integer, pointer, dimension (:) :: YearAD,Code character (len=80), pointer, dimension (:) :: RawFiles,RawVaris character (len=20), pointer, dimension (:) :: NameStn character (len=13), pointer, dimension (:) :: NameCty character (len=09), pointer, dimension (:) :: NameLoc character (len=04), pointer, dimension (:) :: RawSuffices real, parameter :: MissVal = -999.0 integer, parameter :: DataMissVal = -9999 real :: UnusedReal,SaveMulti,LoadMulti integer :: ReadStatus,AllocStat integer :: RawFileN,RawColN,ColN,CheckStnN,LineN,StationN,YearN,MonthN integer :: XRawFile,XRawCol,XCol,XCheckStn,XLine,XStation,XYear,XMonth integer :: RawVariety ! 1=PhilJ-CLIMAT integer :: MonthVariety ! 1=dummy-end 2=12month-line integer :: YearVariety ! 1=file-per-yr 2=file-all integer :: WMOMissVal,LoadMissVal,LoadTraceVal,SaveTraceVal integer :: UnusedInt,SelectCol,WMOCol,YearCol,YearAD0,YearAD1,OpTot,Digits character (len=80) :: Blank = " " character (len=80) :: DataFormat,SaveFormat,SaveVari,SaveFile,LoadFile,GivenFile character (len=80) :: Trash character (len=04) :: SaveSuffix !******************************************************************************* call Intro call SpecifyRaw call SpecifySave call IDStns call LoadRaw call DumpToFile call Close contains !******************************************************************************* subroutine Intro open (99,file="/cru/mikeh1/f709762/scratch/log/log-makecruts.dat",status="replace",action="write") print* print*, " > ***** MakeCRUts: convert raw files to CRU ts files *****" print* end subroutine Intro !******************************************************************************* subroutine SpecifyRaw print*, " > Identify the raw data file variety: " print*, " > 1=PhilJ-CLIMAT 2=GHCNv2" do read (*,*,iostat=ReadStatus), RawVariety if (ReadStatus.LE.0.AND.RawVariety.GE.1.AND.RawVariety.LE.2) exit end do if (RawVariety.EQ.1) then call GetBatch (Blank,RawFiles) print*, " > Enter the first year AD:" do read (*,*,iostat=ReadStatus), YearAD0 if (ReadStatus.LE.0) exit end do RawFileN = size(RawFiles,1) MonthVariety = 1 ; YearVariety = 1 RawColN = 10 YearN = RawFileN ; MonthN = 12 WMOCol = 1 LoadTraceVal = 0 ; SaveTraceVal = 0 ! i.e. no trace values recorded in raw/dump files Digits = 6 DataFormat = "(3i7,i5,i4,i3,i7,i2,2i4)" allocate (RawMissVals(RawColN), & RawMulti (RawColN), & RawSuffices(RawColN), & RawVaris (RawColN), stat=AllocStat) if (AllocStat.NE.0) print*, " > ##### ERROR: SpecifyRaw: Allocation failure #####" RawMissVals = [999999,-32768,-32768,-999,-99,-99,-32768,-9,-99,-99] RawMulti = [1.0,0.1,0.1,0.1,0.1,1.0,1.0,1.0,0.1,0.1] RawSuffices = [' ','.stp','.slp','.tmp','.vap','.wet','.pre','.clq','.ssh','.spc'] do XRawCol = 2, RawColN call CheckVariSuffix (RawSuffices(XRawCol),RawVaris(XRawCol),UnusedReal) end do print*, " > Identify the variable to convert to CRU ts format (0=list): " do read (*,*,iostat=ReadStatus), SelectCol if (SelectCol.EQ.0) then do XRawCol = 2, RawColN print "(a,i2,a1,a)", " > ", XRawCol, " ", trim(RawVaris(XRawCol)) end do end if if (ReadStatus.LE.0.AND.SelectCol.GE.2.AND.SelectCol.LE.RawColN) exit end do LoadMissVal = RawMissVals(SelectCol) LoadMulti = RawMulti(SelectCol) SaveSuffix = RawSuffices(SelectCol) call CheckVariSuffix (SaveSuffix,SaveVari,SaveMulti) else if (RawVariety.EQ.2) then print*, " > Select the GHCNv2 data file: " do read (*,*,iostat=ReadStatus), GivenFile if (ReadStatus.LE.0.AND.GivenFile.NE."") exit end do LoadFile = LoadPath(GivenFile," ") print*, " > Enter the first, last years AD:" do read (*,*,iostat=ReadStatus), YearAD0, YearAD1 if (ReadStatus.LE.0.AND.YearAD1.GE.YearAD0) exit end do RawFileN = 1 ; RawColN = 17 MonthVariety = 2 ; YearVariety = 2 YearN = YearAD1 - YearAD0 + 1 MonthN = 12 WMOCol = 2 ; SelectCol = 6 ; YearCol = 5 Digits = 6 ! @@@@@@@@@@@ check this @@@@@@@@@@@@@@ DataFormat = "(i3,i5,i3,i1,i4,12i5)" allocate (RawMissVals(RawColN), & RawMulti (RawColN), & RawFiles (RawFileN), stat=AllocStat) if (AllocStat.NE.0) print*, " > ##### ERROR: SpecifyRaw: Allocation failure #####" RawMissVals = [-99,-9999,-99,9,-999,-9999,-9999,-9999,-9999,-9999,-9999,-9999,-9999,-9999,-9999,-9999,-9999] RawMulti = 0.1 RawMulti (2) = 10.0 RawFiles = LoadFile print*, " > Enter the variable suffix (.???):" do read (*,*,iostat=ReadStatus), SaveSuffix call CheckVariSuffix (SaveSuffix,SaveVari,SaveMulti) if (ReadStatus.GT.0.OR.SaveMulti.EQ.0) print*, " > Entry unacceptable. Try again." if (ReadStatus.LE.0.AND.SaveMulti.NE.0) exit end do if (SaveSuffix.EQ.".pre") then LoadTraceVal = -8888 ; SaveTraceVal = 1 ! save trace values (-8888) as 0.1mm else LoadTraceVal = 0 ; SaveTraceVal = 0 ! i.e. no trace values recorded in raw/dump files end if LoadMissVal = RawMissVals(SelectCol) LoadMulti = RawMulti(SelectCol) end if end subroutine SpecifyRaw !******************************************************************************* subroutine SpecifySave print "(a,a4)", " > Enter the file to save, with suffix: ", SaveSuffix do read (*,*,iostat=ReadStatus), GivenFile if (ReadStatus.LE.0.AND.GivenFile.NE."") exit end do SaveFile = SavePath(GivenFile,SaveSuffix) SaveFile = trim(SaveFile) // ".cts" end subroutine SpecifySave !******************************************************************************* subroutine IDStns print*, " > Identifying stations in files..." CheckStnN = 1000000 allocate (CheckStn (CheckStnN), & FileLines (RawFileN), & LineData (RawColN), stat=AllocStat) if (AllocStat.NE.0) print*, " > ##### ERROR: GetFileSpecs: Allocation failure: CheckStn #####" CheckStn = 0 ; FileLines = 0 ; StationN = 0 do XRawFile = 1, RawFileN call system ('wc -l ' // trim(RawFiles(XRawFile)) // ' > trashme.txt') open (3,file='trashme.txt',status="old",access="sequential",form="formatted",action="read") read (3,"(i10)"), FileLines(XRawFile) ! get number of lines close (3) call system ('rm trashme.txt') open (3,file=RawFiles(XRawFile),status="old",access="sequential",form="formatted",action="read") do XLine = 1, FileLines(XRawFile) read (3,DataFormat), (LineData(XRawCol),XRawCol=1,RawColN) ! write (99,DataFormat), (LineData(XRawCol),XRawCol=1,RawColN) ! ########################### if (LineData(WMOCol).NE.RawMissVals(WMOCol)) then XStation = nint(real(LineData(WMOCol)) * RawMulti(WMOCol)) CheckStn(XStation) = CheckStn(XStation) + 1 ! store existence of station/month if (CheckStn(XStation).EQ.1) StationN = StationN + 1 end if end do close (3) end do print*, " > WMO stations in files total: ", StationN XStation = 0 do XCheckStn = 1, CheckStnN if (CheckStn(XCheckStn).GT.0) then XStation = XStation + 1 CheckStn(XCheckStn) = XStation end if end do end subroutine IDStns !******************************************************************************* subroutine LoadRaw print*, " > Loading data from files..." allocate (Raw (YearN,MonthN,StationN), & CountYrMon (YearN,MonthN), & CountYrStn (YearN,StationN), stat=AllocStat) if (AllocStat.NE.0) print*, " > ##### ERROR: LoadRaw: Allocation failure: Raw #####" Raw = DataMissVal ; CountYrMon = 0 ; CountYrStn = 0 if (YearVariety.EQ.2) then open (3,file=RawFiles(1),status="old",access="sequential",action="read") LineN = FileLines (1) end if do XRawFile = 1, RawFileN open (3,file=RawFiles(XRawFile),status="old",access="sequential",action="read") LineN = FileLines (XRawFile) if (YearVariety .EQ.1) XYear = XRawFile if (MonthVariety.EQ.1) XMonth = 1 do XLine = 1, LineN read (3,DataFormat), (LineData(XRawCol),XRawCol=1,RawColN) if (LineData(WMOCol).EQ.RawMissVals(WMOCol)) then if (MonthVariety.EQ.1) XMonth = XMonth + 1 else XStation = LineData(WMOCol) * RawMulti(WMOCol) if (MonthVariety.EQ.1.AND.LineData(SelectCol).NE.RawMissVals(SelectCol)) then CountYrMon(XYear,XMonth) = CountYrMon(XYear,XMonth) + 1 CountYrStn(XYear,CheckStn(XStation)) = CountYrStn(XYear,CheckStn(XStation)) + 1 Raw(XYear,XMonth,CheckStn(XStation)) = LineData(SelectCol) else if (MonthVariety.EQ.2) then if (YearVariety.EQ.2) XYear = LineData(YearCol) - YearAD0 + 1 do XMonth = 1, 12 XCol = SelectCol + XMonth - 1 if (LineData(XCol).NE.RawMissVals(SelectCol)) then CountYrMon(XYear,XMonth) = CountYrMon(XYear,XMonth) + 1 CountYrStn(XYear,CheckStn(XStation)) = CountYrStn(XYear,CheckStn(XStation)) + 1 Raw(XYear,XMonth,CheckStn(XStation)) = LineData(XCol) end if end do end if end if end do close (3) end do end subroutine LoadRaw !******************************************************************************* subroutine DumpToFile print*, " > Dumping data to CRU ts file..." allocate (Code (StationN), & YearAD (YearN), & NameLoc(StationN), stat=AllocStat) if (AllocStat.NE.0) print*, " > ##### ERROR: DumpToFile: Allocation failure #####" NameLoc=" nocode" do XYear = 1, YearN YearAD(XYear) = YearAD0 + XYear - 1 end do do XCheckStn = 1, CheckStnN if (CheckStn(XCheckStn).GT.0) then Code(CheckStn(XCheckStn)) = XCheckStn end if end do if (LoadTraceVal.NE.0) then do XYear = 1, YearN do XMonth = 1, MonthN do XStation = 1, StationN if (Raw(XYear,XMonth,XStation).EQ.LoadTraceVal) Raw(XYear,XMonth,XStation) = SaveTraceVal end do end do end do end if if (LoadMulti.NE.SaveMulti) then do XYear = 1, YearN do XMonth = 1, MonthN do XStation = 1, StationN if (Raw(XYear,XMonth,XStation).NE.DataMissVal) Raw(XYear,XMonth,XStation) = & nint(real(Raw(XYear,XMonth,XStation))*LoadMulti/SaveMulti) end do end do end do end if call GetCRUtsInfo (Code,Lat,Long,Elev,NameStn,NameCty,Digits) call MakeStnInfo (StnInfo,Code,Lat,Long,Elev,1,YearAD=YearAD,Data=Raw) call SaveCTS (StnInfo,NameLoc,NameStn,NameCty,Raw,YearAD,SaveFile) end subroutine DumpToFile !******************************************************************************* subroutine Close write (99,"(a)"), "YR Jan Feb Mar Apr May Jun Jul Aug Sep Oct Nov Dec ANY" do XYear = 1, YearN OpTot = 0 do XStation = 1, StationN if (CountYrStn(XYear,XStation).GT.0) OpTot = OpTot + 1 end do write (99,"(i2,13i6)"), XYear, (CountYrMon(XYear,XMonth),XMonth=1,12), OpTot end do print* close (99) end subroutine Close !******************************************************************************* end program MakeCRUts