module TerraHS.Algebras.Temporal.Interval where import System.Time {-- import TerraHS.Misc import TerraHS.Misc.Generic import TerraHS.Misc.TimeFunctions import TerraHS.Misc.StrFunctions --} --import Generic import TerraHS.Algebras.Temporal.TimeFunctions import TerraHS.Misc.StrFunctions --import Operations data Date= Date Int Int Int deriving (Eq,Ord) data Time = Time Int Int Int deriving (Eq,Ord) data Duration = Duration Int Int Int Int deriving (Eq,Ord,Show) data Instant = Instant Date Time deriving (Eq,Ord) data Interval = Interval Instant Instant Bool Bool deriving (Eq, Show) begin :: Interval -> Instant begin (Interval s _ _ _) = s end :: Interval -> Instant end (Interval _ e _ _) = e instance Show Date where show (Date d m a ) = (show d) ++ "/" ++ (show m) ++ "/" ++ (show a) instance Show Time where show (Time h m s ) = (show h) ++ ":" ++ (show m) ++ ":" ++ (show s) instance Show Instant where show (Instant d t ) = (show d) ++ " " ++ (show t) instance Ord Interval where (<) (Interval ib1 ie1 lc1 lr1) (Interval ib2 ie2 lc2 lr2) = (ib1 < ib2) (>) (Interval ib1 ie1 lc1 lr1) (Interval ib2 ie2 lc2 lr2) = (ib1 > ib2) (<=) (Interval ib1 ie1 lc1 lr1) (Interval ib2 ie2 lc2 lr2) = (ib1 <= ib2) (>=) (Interval ib1 ie1 lc1 lr1) (Interval ib2 ie2 lc2 lr2) = (ib1 >= ib2) r_disjoint::Interval->Interval->Bool r_disjoint (Interval ib1 ie1 lc1 rc1) (Interval ib2 ie2 lc2 rc2 ) = ((ie2 < ib1) && (not(lc2 && rc1))) disjoint::Interval->Interval->Bool disjoint i1 i2 = ((r_disjoint i1 i2) || (r_disjoint i2 i1)) diffInstant :: Instant -> Instant -> Integer diffInstant i f = (timeDiffToSecs (diffClockTimes (toClockTime (instanttoCalendarTime f) ) (toClockTime (instanttoCalendarTime i)))) diffInterval :: Interval -> Interval -> Integer diffInterval ( Interval ib1 ie1 lc1 lr1 ) ( Interval ib2 ie2 lc2 lr2 ) = (diffInstant ib1 ie2) ---------------------------------------------------------- --- fun�es auxiliares ----------------------------------- ---------------------------------------------------------- stringtoDate::String->Date stringtoDate str = (Date d m a ) where d = string2decimal (get_head str '/') m = string2decimal (get_head (get_tail (str) '/') '/') a = string2decimal (get_tail (get_tail (str) '/') '/') stringtoTime::String->Time stringtoTime str = (Time h m s ) where h = string2decimal (get_head str ':') m = string2decimal (get_head (get_tail (str) ':') ':') s = string2decimal (get_tail (get_tail (str) ':') ':') time2sec::Time->Integer time2sec (Time h m s) =fromIntegral((h*3600) + (m*60) + s) sec2time::Integer->Time sec2time sec = (Time h m s) where h= fromInteger (div sec 3600) m= fromInteger (div (mod sec 3600 ) 60) s = fromInteger (mod (mod sec 3600 ) 60) sec2duration::Integer->Duration sec2duration sec = (Duration d h m s) where d= fromInteger (div sec 86400) aux = (mod sec 86400) h= fromInteger (div aux 3600) m= fromInteger (div (mod aux 3600 ) 60) s = fromInteger (mod (mod aux 3600 ) 60) instanttoCalendarTime::Instant->CalendarTime instanttoCalendarTime (Instant (Date d m a) (Time h mm s) ) = (CalendarTime { ctYear = a, ctMonth = (toMonth(m)), ctDay = d, ctHour = h, ctMin = mm, ctSec = s, ctPicosec = 0, ctWDay = Thursday, ctYDay = 0, ctTZName = "UTC", ctTZ = 0, ctIsDST = False}) i1 = Instant (Date 10 02 2004) (Time 10 02 00) i2 = Instant (Date 11 02 2004) (Time 10 02 00) i3 = Instant (Date 12 02 2004) (Time 10 02 00) i4 = Instant (Date 13 02 2004) (Time 10 02 00) i5 = Instant (Date 15 02 2004) (Time 10 02 00) i6 = Instant (Date 18 02 2004) (Time 10 02 00) in1 = Interval i1 i2 False False in2 = Interval i2 i3 False False in3 = Interval i3 i4 False False in4 = Interval i4 i5 False False in5 = Interval i5 i6 False False