module TerraHS.Algebras.Temporal.DateTime where import TerraHS import System.Time import TerraHS.Algebras.Temporal.TimeFunctions import TerraHS.Algebras.DB.Databases import TerraHS.Algebras.DB.Model import TerraHS.Algebras.Base.Category ----------------------------------------------- -- Modulo Temporal ----------------------------------------------- --- definições de tipos ------------------------------------------------ --- tipos Temporais (Instant,Duration,Date,Time ,Interval) data Date= Date (Int,Int,Int) deriving (Eq,Ord) instance Show Date where show (Date (d, m ,a) ) = (show d) ++ "/" ++ (show m) ++ "/" ++ (show a) data Time = Time (Int,Int,Int) deriving (Eq,Ord) instance Show Time where show (Time (h, m ,s) ) = (show h) ++ ":" ++ (show m) ++ ":" ++ (show s) data Duration = Duration (Int,Int,Int,Int) deriving (Eq,Ord,Show) data Instant=Instant(Date,Time) deriving (Eq,Ord) instance Show Instant where show (Instant (d, t ) ) = (show d) ++ " " ++ (show t) data Interval = Interval(Instant,Instant,Bool,Bool) deriving (Eq,Ord,Show) ----------------------------------------------- --- definições de funcoes ------------------------------------------------ --- funcoes Temporais 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}) diffInstant::Instant->Instant->Integer diffInstant i f = (timeDiffToSecs (diffClockTimes (toClockTime (instanttoCalendarTime f) ) (toClockTime (instanttoCalendarTime i)))) insidei::Interval->Interval->Bool insidei i1 i2 = containsi i2 i1 containsi::Interval->Interval->Bool containsi (Interval(ib1,ie1,lc1,rc1 )) (Interval(ib2,ie2,lc2,rc2 )) | ((ib1 < ib2) && (ie1 > ie2) && (lc1 == False)) =True | ((ie1 > ie2) && (lc2 == True)) =True | ((ib1 < ib2) && (rc2 == True)) =True |otherwise = False before::Interval->Interval->Bool before (Interval(ib1,ie1,lc1,lr1 )) (Interval(ib2,ie2,lc2,lr2 )) =((ie1 <= ib2) && (lc1 == False)) --after::Interval->Interval->Bool --after (Interval(ib1,ie1,lc1,lr1 )) (Interval(ib2,ie2,lc2,lr2 )) =((ib1 >= ie2) && (lc2 == False)) r_disjoint::Interval->Interval->Bool r_disjoint (Interval(ib1,ie1,lc1,rc1 )) (Interval(ib2,ie2,lc2,rc2 ))= ((ie2 < ib1) && (not(lc2 && rc1))) disjointi::Interval->Interval->Bool disjointi i1 i2 = ((r_disjoint i1 i2) || (r_disjoint i2 i1)) intercepti::Interval->Interval->Bool intercepti i1 i2 = (not (disjointi i1 i2)) --r_adjacenti::Interval->Interval->Bool --r_adjacenti i1 i2 = ((after i1 i2) && (not (disjointi i1 i2) )) --adjacenti::Interval->Interval->Bool --adjacenti i1 i2 = ((r_adjacenti i1 i2) || (r_adjacenti i2 i1))