2018-06-24 19:47:53 -04:00
|
|
|
module Preview where
|
2018-06-24 17:26:43 -04:00
|
|
|
|
2018-06-24 19:47:53 -04:00
|
|
|
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
|
2018-06-24 17:26:43 -04:00
|
|
|
| isPreviewSeason n = Just $ (fst packsChange, snd packsChange, head (rotate 1 b), head b)
|
|
|
|
| otherwise = Nothing
|
|
|
|
where
|
2018-06-24 19:47:53 -04:00
|
|
|
((i,o), (Bq b), r) = currentFormat n
|
|
|
|
packsChange = diffRot i ni
|
|
|
|
((ni,_),_,_) = nextFormat ((i,o),(Bq b),r)
|
2018-06-24 17:26:43 -04:00
|
|
|
|
|
|
|
printLegal :: State -> [String]
|
2018-06-24 19:47:53 -04:00
|
|
|
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)
|
2018-06-24 17:26:43 -04:00
|
|
|
]
|
|
|
|
|
|
|
|
printPreview :: Maybe Preview -> [String]
|
2018-06-24 19:47:53 -04:00
|
|
|
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)))
|
2018-06-24 17:26:43 -04:00
|
|
|
]
|
|
|
|
where
|
|
|
|
rmEmp = filter (/="")
|
|
|
|
cbi = catMaybes [bi]
|
|
|
|
cbo = catMaybes [bo]
|
2018-06-24 19:47:53 -04:00
|
|
|
cleanDP = map (\(Or n _) -> n)
|
2018-06-24 17:26:43 -04:00
|
|
|
printPreview Nothing = []
|
|
|
|
|