| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Poker.Cards
Description
Card types and operators.
Synopsis
- data Rank
- allRanks :: [Rank]
- data Suit
- allSuits :: [Suit]
- suitToUnicode :: Suit -> Char
- suitFromUnicode :: Char -> Maybe Suit
- data Card = Card {}
- allCards :: [Card]
- data Hole = UnsafeHole !Card !Card
- mkHole :: Card -> Card -> Maybe Hole
- allHoles :: [Hole]
- data ShapedHole
- = Pair !Rank
- | UnsafeOffsuit !Rank !Rank
- | UnsafeSuited !Rank !Rank
- mkPair :: Rank -> ShapedHole
- mkOffsuit :: Rank -> Rank -> Maybe ShapedHole
- mkSuited :: Rank -> Rank -> Maybe ShapedHole
- allShapedHoles :: [ShapedHole]
- holeToShapedHole :: Hole -> ShapedHole
- data Deck
- freshDeck :: Deck
- unsafeDeck :: [Card] -> Deck
- shapedHoleToHoles :: ShapedHole -> [Hole]
- rankToChr :: Rank -> Char
- chrToRank :: Char -> Maybe Rank
- suitToChr :: Suit -> Char
- chrToSuit :: Char -> Maybe Suit
- cardToShortTxt :: Card -> Text
- cardFromShortTxt :: Text -> Maybe Card
- shapedHoleToShortTxt :: ShapedHole -> Text
- holeToShortTxt :: Hole -> Text
- unsafeOffsuit :: Rank -> Rank -> ShapedHole
- unsafeSuited :: Rank -> Rank -> ShapedHole
- unsafeHole :: Card -> Card -> Hole
- holeFromShortTxt :: Text -> Maybe Hole
Documentation
Instances
>>>allRanks[Two,Three,Four,Five,Six,Seven,Eight,Nine,Ten,Jack,Queen,King,Ace]
Instances
| Bounded Suit Source # | |
| Enum Suit Source # | |
| Eq Suit Source # | |
| Ord Suit Source # | |
| Read Suit Source # | |
| Show Suit Source # | |
| Generic Suit Source # | |
| Arbitrary Suit Source # | |
| Pretty Suit Source # |
|
Defined in Poker.Cards | |
| type Rep Suit Source # | |
Defined in Poker.Cards type Rep Suit = D1 ('MetaData "Suit" "Poker.Cards" "poker-base-0.1.0.0-CHz5byiVovtI4WerZQqrDU" 'False) ((C1 ('MetaCons "Club" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Diamond" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Heart" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Spade" 'PrefixI 'False) (U1 :: Type -> Type))) | |
suitToUnicode :: Suit -> Char Source #
>>>suitToUnicode <$> [Club, Diamond, Heart, Spade]"\9827\9830\9829\9824">>>suitFromUnicode . suitToUnicode <$> [Club, Diamond, Heart, Spade][Just Club,Just Diamond,Just Heart,Just Spade]
suitFromUnicode :: Char -> Maybe Suit Source #
>>>suitFromUnicode <$> ['♣', '♦', '♥', '♠'][Just Club,Just Diamond,Just Heart,Just Spade]
\s -> suitFromUnicode (suitToUnicode s) == Just s
Representation of a playing card.
Instances
| Eq Card Source # | |
| Ord Card Source # | |
| Read Card Source # | |
| Show Card Source # | |
| IsString Card Source # | |
Defined in Poker.Cards Methods fromString :: String -> Card # | |
| Generic Card Source # | |
| Arbitrary Card Source # | |
| Pretty Card Source # |
|
Defined in Poker.Cards | |
| type Rep Card Source # | |
Defined in Poker.Cards type Rep Card = D1 ('MetaData "Card" "Poker.Cards" "poker-base-0.1.0.0-CHz5byiVovtI4WerZQqrDU" 'False) (C1 ('MetaCons "Card" 'PrefixI 'True) (S1 ('MetaSel ('Just "rank") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Rank) :*: S1 ('MetaSel ('Just "suit") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Suit))) | |
Hole represents a player's hole cards in a game of Texas Hold'Em
Constructors
| UnsafeHole !Card !Card |
Instances
| Eq Hole Source # | |
| Ord Hole Source # | |
| Read Hole Source # | |
| Show Hole Source # | |
| IsString Hole Source # |
|
Defined in Poker.Cards Methods fromString :: String -> Hole # | |
| Generic Hole Source # | |
| Arbitrary Hole Source # | The |
| Pretty Hole Source # |
|
Defined in Poker.Cards | |
| type Rep Hole Source # | |
Defined in Poker.Cards type Rep Hole = D1 ('MetaData "Hole" "Poker.Cards" "poker-base-0.1.0.0-CHz5byiVovtI4WerZQqrDU" 'False) (C1 ('MetaCons "UnsafeHole" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Card) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Card))) | |
data ShapedHole Source #
A ShapedHole is the Suit-normalised representation of a
poker Hole. For example, the Hole "King of Diamonds, 5 of Hearts" is often referred
to as "King-5 offsuit".
To construct a ShapedHole, see mkPair, mkOffsuit, and mkSuited'.
>>>"22p" :: ShapedHolePair Two>>>"A4o" :: ShapedHoleUnsafeOffsuit Ace Four>>>"KJs" :: ShapedHoleUnsafeSuited King Jack
Constructors
| Pair !Rank | |
| UnsafeOffsuit !Rank !Rank | |
| UnsafeSuited !Rank !Rank |
Instances
mkPair :: Rank -> ShapedHole Source #
Build a pair ShapedHole from the given Rank
mkOffsuit :: Rank -> Rank -> Maybe ShapedHole Source #
Returns an offsuit ShapedHole if the incoming Ranks are unique, else Nothing.
Note that the internal representation of ShapedHole is normalised:
\r1 r2 -> mkOffsuit r1 r2 == mkOffsuit r2 r1
mkSuited :: Rank -> Rank -> Maybe ShapedHole Source #
Returns a suited ShapedHole if the incoming Ranks are unique, else Nothing.
Note that mkSuited normalises the order of the incoming Ranks.
\r1 r2 -> mkSuited r1 r2 == mkSuited r2 r1
allShapedHoles :: [ShapedHole] Source #
>>>length allShapedHoles169>>>Data.List.nub allShapedHoles == allShapedHolesTrue>>>pretty $ take 15 allShapedHoles[AAp, AKs, AQs, AJs, ATs, A9s, A8s, A7s, A6s, A5s, A4s, A3s, A2s, AKo, KKp]
holeToShapedHole :: Hole -> ShapedHole Source #
>>>holeToShapedHole "AcKd"UnsafeOffsuit Ace King>>>holeToShapedHole "AcKc"UnsafeSuited Ace King>>>holeToShapedHole "AcAs"Pair Ace
shapedHoleToHoles :: ShapedHole -> [Hole] Source #
>>>fmap holeToShortTxt . shapedHoleToHoles $ "55p"["5d5c","5h5c","5s5c","5h5d","5s5d","5s5h"]>>>fmap holeToShortTxt . shapedHoleToHoles $ "97o"["9c7d","9c7h","9c7s","9d7c","9d7h","9d7s","9h7c","9h7d","9h7s","9s7c","9s7d","9s7h"]>>>fmap holeToShortTxt . shapedHoleToHoles $ "QTs"["QcTc","QdTd","QhTh","QsTs"]
chrToRank :: Char -> Maybe Rank Source #
>>>map (fromJust . chrToRank) "23456789TJQKA"[Two,Three,Four,Five,Six,Seven,Eight,Nine,Ten,Jack,Queen,King,Ace]>>>chrToRank 'x'Nothing
\r -> chrToRank (rankToChr r) == Just r
chrToSuit :: Char -> Maybe Suit Source #
>>>map (fromJust . chrToSuit) "cdhs"[Club,Diamond,Heart,Spade]>>>chrToSuit 'x'Nothing
\s -> chrToSuit (suitToChr s) == Just s
cardToShortTxt :: Card -> Text Source #
>>>cardToShortTxt "Ac""Ac"
cardFromShortTxt :: Text -> Maybe Card Source #
>>>cardFromShortTxt "Ac"Just (Card {rank = Ace, suit = Club})
\c -> cardFromShortTxt (cardToShortTxt c) == Just c
shapedHoleToShortTxt :: ShapedHole -> Text Source #
>>>shapedHoleToShortTxt (mkPair Ace)"AAp">>>shapedHoleToShortTxt <$> (mkOffsuit Ace King)Just "AKo">>>shapedHoleToShortTxt <$> (mkSuited Ace King)Just "AKs"
holeToShortTxt :: Hole -> Text Source #
>>>holeToShortTxt "AcKd""AcKd"
unsafeOffsuit :: Rank -> Rank -> ShapedHole Source #
unsafeSuited :: Rank -> Rank -> ShapedHole Source #