! runselectmod.f90 ! module procedure written by Tim Mitchell on 08.12.99 ! last modification on 24.01.00 ! gets the user to select a run ! returns the run details to the calling program module RunSelectMod implicit none contains subroutine RunSelect (GridChosen, JobMonth0, JobMonth1, JobYearN, JobDecN, JobADYear, & RunTitle, DecStyleThis, DecStyleNext, & DecPathThis, DecPathNext, DecYearN, DecGetYear0, DecGetYear1) !******************************************************************************* integer, pointer, dimension (:) :: JobADYear ! year AD for each year wanted integer, pointer, dimension (:) :: DecYearN, DecGetYear0, DecGetYear1 ! details for each raw file integer, pointer, dimension (:) :: DecStyleThis, DecStyleNext ! style (format etc) for each decade (+ next for overlaps) character (len=80), pointer, dimension (:) :: DecPathThis, DecPathNext ! filepath for each decade (+ next for overlaps) integer, intent (in) :: GridChosen, JobYearN, JobDecN, JobMonth0, JobMonth1 ! Grid chosen + job parameters character (len=40), intent(out) :: RunTitle ! the name of the run character (len=80), allocatable, dimension (:) :: RunFilePath, RawFilePath character (len=20), allocatable, dimension (:) :: RunName integer, allocatable, dimension (:) :: RawYearN, RawADYear0, RawADYear1, RawStyle real, parameter :: MissVal = -999.0 character (len=80) :: SetFilePath ! filename of runs integer :: RunN integer :: AllocStat ! status of allocation integer :: ReadStatus ! check on user input integer :: XDec, XRaw, XRun integer :: XADYear, XRawYear, XDecYear integer :: ChosenRun,QReGrid integer :: RawFileN integer :: FirstDecYear0 integer :: MatchFirstRaw !******************************************************************************* ! 1. obs (Hulme) 7. CCSR-NIES" ! 2. ECHam4-OPYC3 8. ECHam3-LSG" ! 3. HadCM2 9. GFDL" ! 4. HadCM3 10. NCAR-CGCM" ! 5. CGCM1 11. NCAR-PCM3" ! 6. CSIRO 12. HalfDegree" if (GridChosen.EQ.3) then print*, " > Use HadCM2 runs (=1) or regridded runs (=2) ?" do read (*,*,iostat=ReadStatus), QReGrid if (ReadStatus.LE.0.AND.QReGrid.GE.1.AND.QReGrid.LE.2) exit end do if (QReGrid.EQ.1) SetFilePath = "/cru/u2/f709762/goglo/ref/hadcm2-runs.ref" if (QReGrid.EQ.2) SetFilePath = "/cru/u2/f709762/goglo/ref/regrid-had2-runs.ref" else if (GridChosen.EQ.4) then SetFilePath = "/cru/u2/f709762/goglo/ref/hadcm3-runs.ref" else if (GridChosen.EQ.12) then SetFilePath = "/cru/u2/f709762/goglo/ref/half-degree-runs.ref" else print*, " > ### No link to runs here (runselectmod.f90) for Grid ###" end if !******************************************************************************* open (4, file=SetFilePath, status="old", access="sequential", action="read") read (4, fmt="(I4)"), RunN allocate (RunFilePath (RunN), RunName (RunN), stat=AllocStat) if (AllocStat.NE.0) print*, " > ##### ERROR: Allocation failure #####" do XRun = 1, RunN read (4, fmt="(A20)"), RunName (XRun) end do do XRun = 1, RunN read (4, fmt="(A80)"), RunFilePath (XRun) end do close (4) !******************************************************************************* print*, " > Select a simulation (0=list): " do read (*,*,iostat=ReadStatus), ChosenRun if (ReadStatus.LE.0 .AND. ChosenRun.EQ.0 ) then do XRun = 1, RunN, 2 if ((XRun+1).LE.RunN) then print "(I4,A2,A20,A3,I4,A2,A20)", XRun, ': ', trim(adjustl(RunName (XRun))), & " ", (XRun+1), ': ', trim(adjustl(RunName (XRun+1))) else print "(I4,A2,A20)", XRun, ': ', trim(adjustl(RunName (XRun))) end if end do end if if (ReadStatus.LE.0 .AND. ChosenRun.GE.1 .AND. ChosenRun.LE.RunN) exit end do print*, RunName (ChosenRun) RunTitle = RunName (ChosenRun) !******************************************************************************* open (5, file=RunFilePath(ChosenRun), status="old", access="sequential", action="read") read (5, fmt="(I4)"), RawFileN allocate (RawYearN (RawFileN), & RawADYear0 (RawFileN), & RawADYear1 (RawFileN), & RawStyle (RawFileN), & RawFilePath (RawFileN), stat=AllocStat) if (AllocStat.NE.0) print*, " > ##### ERROR: Allocation failure #####" do XRaw = 1, RawFileN read (5, fmt="(A80)"), RawFilePath (XRaw) end do do XRaw = 1, RawFileN read (5, fmt="(4(I6))"), RawStyle (XRaw), RawYearN (XRaw), RawADYear0 (XRaw), RawADYear1 (XRaw) if (RawYearN(XRaw).NE.10) print*, " > ##### RunSelectMod: Cannot handle files with other than 10yrs #####" end do close (5) !******************************************************************************* allocate (DecYearN (JobDecN), & DecGetYear0 (JobDecN), & DecGetYear1 (JobDecN), & DecStyleThis (JobDecN), & DecStyleNext (JobDecN), & DecPathThis (JobDecN), & DecPathNext (JobDecN), stat=AllocStat) if (AllocStat.NE.0) print*, " > ##### ERROR: Allocation failure #####" DecYearN = MissVal DecGetYear0 = MissVal DecGetYear1 = MissVal DecPathThis = "blank" DecPathNext = "blank" DecStyleThis = MissVal DecStyleNext = MissVal XDecYear = 1 if (JobADYear(XDecYear).EQ.MissVal) then do XDecYear = XDecYear + 1 if (JobADYear(XDecYear).NE.MissVal) exit end do end if FirstDecYear0 = 10 * floor (real (JobADYear(XDecYear)) / 10.0) XRaw = 1 do if (RawADYear0(XRaw).EQ.FirstDecYear0) exit XRaw = XRaw + 1 end do MatchFirstRaw = XRaw do XDec = 1, JobDecN XRaw = MatchFirstRaw + (XDec - 1) if (XRaw.LE.RawFileN) then DecYearN (XDec) = RawYearN (XRaw) DecPathThis (XDec) = RawFilePath (XRaw) DecStyleThis (XDec) = RawStyle (XRaw) ! DecStyleNext and DecPathNext are filled if there is a file available if (XRaw.LT.RawFileN) then DecPathNext (XDec) = RawFilePath (XRaw+1) DecStyleNext (XDec) = RawStyle (XRaw+1) end if XDecYear = 1 do if (JobADYear ((XDec-1)*10+XDecYear) .NE. MissVal) exit XDecYear = XDecYear + 1 end do DecGetYear0 (XDec) = XDecYear do XDecYear = XDecYear + 1 if (XDecYear .EQ. 11) exit if (JobADYear ((XDec-1)*10+XDecYear) .EQ. MissVal) exit end do DecGetYear1 (XDec) = (XDecYear-1) end if end do !******************************************************************************* deallocate (RawYearN,RawADYear0,RawADYear1,RawFilePath,RawStyle) deallocate (RunFilePath,RunName) !******************************************************************************* end subroutine RunSelect end module RunSelectMod