diff --git a/Format.hs b/Format.hs index 52592df..c7d191e 100644 --- a/Format.hs +++ b/Format.hs @@ -53,9 +53,6 @@ rotate n xs = take lxs . drop ((fromIntegral n) `mod` lxs) . cycle $ xs rotateBox :: BoxQueue -> BoxQueue rotateBox (Bq x) = Bq $ rotate 1 x -changes :: Eq a => [a] -> [a] -> [a] -changes x y = filter (\n -> not $ n `elem` y) x - strictApplyN :: Integer -> (a -> a) -> a -> a strictApplyN 0 _ x = x strictApplyN n f x = strictApplyN (n - 1) f $! (f x) diff --git a/Main b/Main index f2b0f65..b2ed0f1 100755 Binary files a/Main and b/Main differ diff --git a/Main.hs b/Main.hs index f57bfca..d74fcb6 100644 --- a/Main.hs +++ b/Main.hs @@ -7,20 +7,15 @@ import Packs import State import Format import Timestamp +import Preview main :: IO () main = do t <- getCurrentTime >>= return . toGregorian . utctDay - mapM_ putStrLn $ showState (currentFormat $ toTS t) + let ts = toTS t + let state = currentFormat ts + let out = (printLegal state) ++ [""] ++ (printPreview $ getPreview ts) + mapM_ putStrLn $ out toTS :: (Integer, Int, Int) -> Timestamp toTS (y,m,d) = Ts (fromIntegral d) (fromIntegral m) y - -showState :: State -> [String] -showState ((i, o), (Bq b), _) = - [ - "Legal Packs:\n" ++ concat (map (\(Ir n) -> " " ++ show n ++ "\n") i) - , "Legal Boxes:\n" ++ concat (map (\x -> " " ++ show x ++ "\n") (catMaybes $ tail b)) - , "Rotated Packs:\n" ++ concat (map (\(Or n _) -> " " ++ show n ++ "\n") o) - , "Rotated Boxes:\n" ++ concat (map (\x -> " " ++ show x ++ "\n") (catMaybes $ [head b])) - ] diff --git a/Preview.hs b/Preview.hs index 367436f..221cddf 100644 --- a/Preview.hs +++ b/Preview.hs @@ -1,30 +1,50 @@ -type Preview = ([DataPack], [DataPack], BigBox, BigBox) +module Preview where -getPreview :: Timestamp -> State -> Maybe Preview -getPreview n (l, p, b, r) +import Data.List +import Data.Maybe +import Packs +import State +import Timestamp +import Format + +type Preview = ([DataPack], [DataPack], Maybe BigBox, Maybe BigBox) + +changes :: Eq a => [a] -> [a] -> [a] +changes x y = filter (\n -> not $ n `elem` y) x + +diffRot :: [InRot] -> [InRot] -> ([DataPack], [DataPack]) +diffRot c f = (packIn, packOut) + where + packIn = map clean $ changes f c + packOut = map clean $ changes c f + clean = (\(Ir n) -> n) + +getPreview :: Timestamp -> Maybe Preview +getPreview n | isPreviewSeason n = Just $ (fst packsChange, snd packsChange, head (rotate 1 b), head b) | otherwise = Nothing where - packsChange = diffRot nl l - (nl, _, _, _) = newRotation (l, p, b, r) + ((i,o), (Bq b), r) = currentFormat n + packsChange = diffRot i ni + ((ni,_),_,_) = nextFormat ((i,o),(Bq b),r) printLegal :: State -> [String] -printLegal (l, p, b, r) = [ - "Evergreen: Revised Core Set x3" - , "Deluxes : " ++ (intercalate ", " $ sort $ catMaybes (tail $ map (\(Bb x) -> x) b)) - , "Datapacks: " ++ (intercalate ", " $ sort $ map (\(Dp n _) -> n) l) +printLegal ((i,o),(Bq b),_) = [ + "===Evergreen:\nRevised Core Set x3" + , "===Deluxes :\n" ++ (intercalate "\n" $ sort $ map show $ catMaybes (tail b)) + , "===Datapacks:\n" ++ (intercalate "\n" $ sort $ map show $ map (\(Ir n) -> n) i) ] printPreview :: Maybe Preview -> [String] -printPreview (Just (i, o, (Bb bi), (Bb bo))) = [ - "Upcoming Changes:" - , ("In : " ++ (intercalate ", " $ (cleanDP i) ++ cbi)) - , ("Out: " ++ (intercalate ", " $ (cleanDP o) ++ cbo)) +printPreview (Just (i, o, bi, bo)) = [ + "===Upcoming Changes:" + , ("===In :\n" ++ (intercalate "\n" $ (map show i) ++ (map show cbi))) + , ("===Out:\n" ++ (intercalate "\n" $ (map show o) ++ (map show cbo))) ] where rmEmp = filter (/="") cbi = catMaybes [bi] cbo = catMaybes [bo] - cleanDP = map (\(Dp n _) -> n) + cleanDP = map (\(Or n _) -> n) printPreview Nothing = [] diff --git a/State.hs b/State.hs index 11b2157..09b3d3e 100644 --- a/State.hs +++ b/State.hs @@ -5,7 +5,7 @@ import Packs type State = (Pool, BoxQueue, StdGen) -data InRot = Ir DataPack deriving Show +data InRot = Ir DataPack deriving (Show, Eq) data OutRot = Or DataPack Integer instance Eq OutRot where