{-# OPTIONS -fglasgow-exts #-} module Types where import Data.Typeable import Data.Map as Map import Data.Set import Data.ByteString type Title = String type Summary = String type Description = String type Reason = String type Hash = ByteString type TicketId = Int type TorrentId = Int type SeriesId = Int type SerieName = String type SeasonId = Int type EpisodeId = Int type Year = Int type Month = Int type Day = Int type EpisodeIndex = (SeriesId, LocalEpisodeIndex) data LocalEpisodeIndex = EpIdx SeasonId EpisodeId | DateIdx Year Month Day deriving (Eq, Typeable) instance Show LocalEpisodeIndex where show (EpIdx s e) = show (s,e) show (DateIdx y m d) = show (y,m,d) instance Read LocalEpisodeIndex where readsPrec n str = do ((a,b),c) <- readsPrec n str return (EpIdx a b,c) ++ do ((a,b,c),d) <- readsPrec n str return (DateIdx a b c,d) instance Ord LocalEpisodeIndex where compare (EpIdx s1 e1) (EpIdx s2 e2) = compare (s1,e1) (s2,e2) compare (DateIdx y1 m1 d1) (DateIdx y2 m2 d2) = compare (y1,m1,d1) (y2,m2,d2) compare (EpIdx _ _) (DateIdx _ _ _) = LT compare (DateIdx _ _ _) (EpIdx _ _) = GT data TorrentTag = HR | HDTV | Proper | Repack | NoTag {- | OtherTag String -} deriving (Show, Enum, Bounded,Typeable,Ord,Eq)