Skip to content

Commit

Permalink
Sort booster packs
Browse files Browse the repository at this point in the history
Booster packs no longer come as jumbled mess instead they are sorted
by booster pack generation rules or set specific rules
  • Loading branch information
skykanin committed May 8, 2021
1 parent 6ebbecc commit e438f1a
Show file tree
Hide file tree
Showing 2 changed files with 23 additions and 18 deletions.
11 changes: 5 additions & 6 deletions src/DraftGen/Encode.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,8 +13,7 @@ module Encode (encodeCard, encodePacks) where

import Control.Applicative ((<|>))
import Control.Lens
import Data.HashSet (HashSet)
import qualified Data.HashSet as S
import Data.Foldable (toList)
import Data.Maybe (fromMaybe)
import qualified Data.Sequence as Seq
import Types
Expand All @@ -28,9 +27,9 @@ encodeCard card =
& nickname ?~ card ^. name

-- | Map position data and set of cards into a GameObj representing a single pack
encodePack :: TransformObj -> HashSet CardObj -> GameObj
encodePack :: Foldable f => TransformObj -> f CardObj -> GameObj
encodePack transformObj cardSet =
go (mkEmptyPack transformObj) 100 $ S.toList cardSet
go (mkEmptyPack transformObj) 100 $ toList cardSet
where
go :: GameObj -> Int -> [CardObj] -> GameObj
go packObj _ [] = packObj
Expand All @@ -44,10 +43,10 @@ encodePack transformObj cardSet =
& containedObjects %~ (Seq.|> mkTTSCardObj cardId cardObj)

-- | Encode list of packs into a single TTSObj
encodePacks :: [HashSet CardObj] -> TTSObj
encodePacks :: Foldable f => [f CardObj] -> TTSObj
encodePacks = go defaultTTSObj 1 (0, 0)
where
go :: TTSObj -> Int -> (Int, Int) -> [HashSet CardObj] -> TTSObj
go :: Foldable f => TTSObj -> Int -> (Int, Int) -> [f CardObj] -> TTSObj
go ttsObj _ _ [] = ttsObj
go ttsObj counter (x, z) (pack : packs) =
go newTTSObj (checkCounter counter) (checkX x, checkZ z) packs
Expand Down
30 changes: 18 additions & 12 deletions src/DraftGen/Generate.hs
Original file line number Diff line number Diff line change
Expand Up @@ -28,6 +28,9 @@ import Data.Char (toLower)
import Data.HashSet (HashSet)
import qualified Data.HashSet as S
import Data.List (find, intersect, isInfixOf, isPrefixOf, isSuffixOf)
import Data.Maybe (fromMaybe)
import Data.Sequence (Seq)
import qualified Data.Sequence as Sq
import System.Random
import Types

Expand Down Expand Up @@ -135,7 +138,7 @@ commonWithMaybeFoil (Ratio numerator denominator) n commonSet foilSet = do
pure $ commonCards `S.union` foilCard

-- | Plural of genPack
genPacks :: PackConfig -> [CardObj] -> IO [HashSet CardObj]
genPacks :: PackConfig -> [CardObj] -> IO [Seq CardObj]
genPacks config cards = replicateM (config ^. amount) (genPack config cards)

-- | Return basic lands belonging to the data set
Expand All @@ -147,7 +150,7 @@ genTokens :: PackConfig -> [CardObj] -> [HashSet CardObj]
genTokens config = pure . filterBySet ('t' : config ^. set) . S.fromList

-- | Generate a random pack based on the pack configuration
genPack :: PackConfig -> [CardObj] -> IO (HashSet CardObj)
genPack :: PackConfig -> [CardObj] -> IO (Seq CardObj)
genPack config cards =
if config ^. set == "stx"
then genStrixhavenPack config cards
Expand All @@ -162,10 +165,13 @@ genPack config cards =
uncommonCards <- gen (config ^. uncommons) (fbr Uncommon)
pick <- pickRareOrMythic (config ^. mythicChance)
rareOrMythicCards <- gen (config ^. rareOrMythics) (fbr pick)
pure $ S.unions [commonWithMaybeFoilCards, uncommonCards, rareOrMythicCards]
pure $ fromSets [commonWithMaybeFoilCards, uncommonCards, rareOrMythicCards]

fromSets :: [HashSet a] -> Seq a
fromSets = foldr ((Sq.><) . Sq.fromList . S.toList) Sq.empty

-- | Generate a strixhaven pack (has special rules)
genStrixhavenPack :: PackConfig -> [CardObj] -> IO (HashSet CardObj)
genStrixhavenPack :: PackConfig -> [CardObj] -> IO (Seq CardObj)
genStrixhavenPack config cards = do
let stxCards = english . filterBySet (config ^. set) . S.fromList . filterDesired $ cards
baseNoLesson = filterLesson Out . filterBasicLands Out $ stxCards
Expand All @@ -180,14 +186,14 @@ genStrixhavenPack config cards = do
uncommonCards <- gen (config ^. uncommons) (fbr Uncommon)
pick <- pickRareOrMythic (config ^. mythicChance)
rareOrMythicCards <- gen (config ^. rareOrMythics) (fbr pick)
lesson <- genByRarity 1 [Common, Rare, Mythic] lessons
mysticalArchive <- genByRarity 1 [Uncommon .. Mythic] staCards
pure $ S.unions [commonWithMaybeFoilCards, uncommonCards, rareOrMythicCards, lesson, mysticalArchive]

-- | Generate set of cards filtered by rarity
genByRarity :: Int -> [Rarity] -> HashSet CardObj -> IO (HashSet CardObj)
genByRarity n rarityList cardSet = do
rarity <- pickRarity rarityList
lesson <- genByType 1 Lesson lessons
mysticalArchive <- genByType 1 Archive staCards
pure $ fromSets [commonWithMaybeFoilCards, uncommonCards, rareOrMythicCards, lesson, mysticalArchive]

-- | Generate set of cards filtered by card type
genByType :: Int -> StxCardType -> HashSet CardObj -> IO (HashSet CardObj)
genByType n cardType cardSet = do
rarity <- pickStxRarity cardType
gen n (filterByRarity rarity cardSet)

-- | Generate set of n cards from set
Expand Down

0 comments on commit e438f1a

Please sign in to comment.