Different mana types implemented with a Mana type class

This commit is contained in:
Correl Roush 2012-01-04 01:04:54 -05:00
parent 0571b86640
commit 00ceb48e2f
2 changed files with 61 additions and 31 deletions

View file

@ -17,7 +17,8 @@ data Rarity = Land
data Card = Card Rarity String Cost data Card = Card Rarity String Cost
deriving (Show, Eq) deriving (Show, Eq)
instance ManaCost Card where instance Mana Card where
colors (Card _ _ cost) = colors cost
converted (Card _ _ cost) = converted cost converted (Card _ _ cost) = converted cost
data Deck = Deck [Card] data Deck = Deck [Card]
@ -27,5 +28,8 @@ curve (Deck cards) = do
let largest = maximum (map converted cards) let largest = maximum (map converted cards)
map (\x -> (x, length (filter (\(Card rarity _ cost) -> rarity /= Land && converted cost == x) cards))) [0..largest] map (\x -> (x, length (filter (\(Card rarity _ cost) -> rarity /= Land && converted cost == x) cards))) [0..largest]
deck = Deck ((replicate 13 (Card Land "Swamp" (Cost []))) ++ (replicate 13 (Card Land "Plains" (Cost []))) cards = concat $ [ replicate 13 (Card Land "Swamp" (Cost [] [] []))
++ replicate 4 (Card Mythic "Jace Beleren" (Cost [Mana 1 Colorless, Mana 2 Blue]))) , replicate 13 (Card Land "Plains" (Cost [] [] []))
, replicate 4 (Card Mythic "Jace Beleren" (Cost [Standard 1 Colorless, Standard 2 Blue] [] []))
]
deck = Deck cards

82
Mana.hs
View file

@ -1,5 +1,8 @@
module Mana where module Mana where
import Data.Char
import Data.List
data Color = Colorless data Color = Colorless
| Black | Black
| White | White
@ -8,35 +11,58 @@ data Color = Colorless
| Green | Green
deriving (Show, Eq) deriving (Show, Eq)
data Mana = Mana { amount :: Int class Mana a where
, color :: Color colors :: a -> [Color]
} deriving (Show, Eq)
data Cost = Cost [Mana]
deriving (Eq)
instance Show Cost where
show c = pretty c
class ManaCost a where
converted :: a -> Int converted :: a -> Int
instance ManaCost Cost where data Standard = Standard Int Color
converted (Cost []) = 0 deriving (Eq)
converted (Cost cost) = (foldl (\t (Mana x _) -> t + x) 0) cost
pretty :: Cost -> String instance Mana Standard where
pretty c = do colors (Standard _ x) = [x]
let filtered c (Cost cost) = converted $ Cost $ filter (\x -> color x == c) cost converted (Standard x _) = x
let colored = concat [ replicate (filtered Black c) 'B'
, replicate (filtered White c) 'W'
, replicate (filtered Red c) 'R'
, replicate (filtered Blue c) 'U'
, replicate (filtered Green c) 'G'
]
let colorless = filtered Colorless c
if length colored > 0 && colorless == 0 then
colored
else
(show colorless) ++ colored
instance Show Standard where
show (Standard n c)
| c == Black = replicate n 'B'
| c == White = replicate n 'W'
| c == Red = replicate n 'R'
| c == Blue = replicate n 'U'
| c == Green = replicate n 'G'
| otherwise = show n
data Hybrid = Hybrid Standard Standard
deriving (Eq)
instance Mana Hybrid where
colors (Hybrid x y) = concat [colors x, colors y]
converted (Hybrid x y) = min (converted x) (converted y)
instance Show Hybrid where
show (Hybrid x y) = map toLower $ "(" ++ (show x) ++ "/" ++ (show y) ++ ")"
data Phyrexian = Phyrexian Standard
deriving (Eq)
instance Mana Phyrexian where
colors (Phyrexian x) = colors x
converted (Phyrexian x) = converted x
instance Show Phyrexian where
show (Phyrexian x) = "(" ++ (map toLower $ show x) ++ "/p)"
data Cost = Cost [Standard] [Hybrid] [Phyrexian]
deriving (Eq)
instance Mana Cost where
colors (Cost s h p) = nub $ concat $ [(concat $ map colors s), (concat $ map colors h), (concat $ map colors p)]
converted (Cost s h p) = (sum $ map converted s) + (sum $ map converted h) + (sum $ map converted p)
instance Show Cost where
show (Cost s h p) = do
let colorless = filter (\x -> colors x == [Colorless]) s
let colored = filter (\x -> colors x /= [Colorless]) s
concat [show $ sum $ map converted colorless
, concat $ map show p
, concat $ map show h
, concat $ map show colored]