{-# LANGUAGE DeriveDataTypeable #-} module DPM.Core.DataTypes where import Data.Time ( UTCTime ) import Data.ByteString ( ByteString ) import Data.Data ( Data ) import Data.Typeable ( Typeable ) newtype PatchID = PatchID { unPatchID :: String } deriving (Eq,Ord,Show,Read,Data,Typeable) data PatchState = PatchStateUNDECIDED | PatchStateAPPLIED | PatchStateDISCARDED ReasonDiscarded deriving (Eq,Ord,Show,Read,Data,Typeable) data ReasonDiscarded = ReasonRejected | ReasonObsolete deriving (Eq,Ord,Show,Read,Data,Typeable) isDiscarded :: PatchState -> Bool isDiscarded (PatchStateDISCARDED _) = True isDiscarded _ = False data PatchTag = TagReviewed deriving (Eq,Ord,Show,Read) data Patch = Patch { p_id :: PatchID , p_date :: UTCTime , p_name :: PatchGroupID , p_author :: String , p_darcsLog :: [String] , p_log :: [LogEntry] , p_inverted :: Bool , p_state :: PatchState , p_tags :: [PatchTag] , p_dependents :: [PatchID] } deriving (Eq,Ord,Show,Read) isReviewed :: Patch -> Bool isReviewed p = TagReviewed `elem` p_tags p data SimplePatch = SimplePatch { sp_id :: PatchID , sp_date :: UTCTime , sp_name :: PatchGroupID , sp_author :: String , sp_darcsLog :: [String] , sp_inverted :: Bool } deriving (Eq,Ord,Show,Read) data LogEntry = LogEntry { log_time :: UTCTime , log_user :: String , log_modelChanged :: Bool , log_message :: String } deriving (Eq,Ord,Show,Read) data PatchData = PatchData { pd_id :: PatchID , pd_content :: ByteString } deriving (Eq,Ord,Show,Read) newtype PatchGroupID = PatchGroupID { unPatchGroupID :: String } deriving (Eq,Ord,Show,Read,Data,Typeable) data PatchGroupState = PatchGroupOpen | PatchGroupClosed deriving (Eq,Ord,Show,Read) data PatchGroup a = PatchGroup { pg_id :: PatchGroupID , pg_state :: PatchGroupState , pg_patches :: [a] , pg_complete :: Bool } deriving (Eq,Ord,Show,Read) data Query = QPrim String | QAnd Query Query | QOr Query Query | QNot Query | QState PatchState | QGroupState PatchGroupState | QPatchID String | QReviewed | QTrue | QFalse deriving (Eq,Show) queryTrue :: Query queryTrue = QTrue queryFalse :: Query queryFalse = QFalse