poker-base-0.1.0.0: A library for core poker types
Safe HaskellNone
LanguageHaskell2010

Poker.Cards

Description

Card types and operators.

Synopsis

Documentation

data Rank Source #

The Rank of a playing Card

Constructors

Two 
Three 
Four 
Five 
Six 
Seven 
Eight 
Nine 
Ten 
Jack 
Queen 
King 
Ace 

Instances

Instances details
Bounded Rank Source # 
Instance details

Defined in Poker.Cards

Enum Rank Source # 
Instance details

Defined in Poker.Cards

Methods

succ :: Rank -> Rank #

pred :: Rank -> Rank #

toEnum :: Int -> Rank #

fromEnum :: Rank -> Int #

enumFrom :: Rank -> [Rank] #

enumFromThen :: Rank -> Rank -> [Rank] #

enumFromTo :: Rank -> Rank -> [Rank] #

enumFromThenTo :: Rank -> Rank -> Rank -> [Rank] #

Eq Rank Source # 
Instance details

Defined in Poker.Cards

Methods

(==) :: Rank -> Rank -> Bool #

(/=) :: Rank -> Rank -> Bool #

Ord Rank Source # 
Instance details

Defined in Poker.Cards

Methods

compare :: Rank -> Rank -> Ordering #

(<) :: Rank -> Rank -> Bool #

(<=) :: Rank -> Rank -> Bool #

(>) :: Rank -> Rank -> Bool #

(>=) :: Rank -> Rank -> Bool #

max :: Rank -> Rank -> Rank #

min :: Rank -> Rank -> Rank #

Read Rank Source # 
Instance details

Defined in Poker.Cards

Show Rank Source # 
Instance details

Defined in Poker.Cards

Methods

showsPrec :: Int -> Rank -> ShowS #

show :: Rank -> String #

showList :: [Rank] -> ShowS #

Generic Rank Source # 
Instance details

Defined in Poker.Cards

Associated Types

type Rep Rank :: Type -> Type #

Methods

from :: Rank -> Rep Rank x #

to :: Rep Rank x -> Rank #

Arbitrary Rank Source # 
Instance details

Defined in Poker.Cards

Methods

arbitrary :: Gen Rank #

shrink :: Rank -> [Rank] #

Pretty Rank Source #
>>> pretty <$> allRanks
[2,3,4,5,6,7,8,9,T,J,Q,K,A]
Instance details

Defined in Poker.Cards

Methods

pretty :: Rank -> Doc ann #

prettyList :: [Rank] -> Doc ann #

type Rep Rank Source # 
Instance details

Defined in Poker.Cards

type Rep Rank = D1 ('MetaData "Rank" "Poker.Cards" "poker-base-0.1.0.0-CHz5byiVovtI4WerZQqrDU" 'False) (((C1 ('MetaCons "Two" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Three" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Four" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Five" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Six" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Seven" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Eight" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Nine" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Ten" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Jack" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Queen" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "King" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Ace" 'PrefixI 'False) (U1 :: Type -> Type)))))

allRanks :: [Rank] Source #

>>> allRanks
[Two,Three,Four,Five,Six,Seven,Eight,Nine,Ten,Jack,Queen,King,Ace]

data Suit Source #

The Suit of a playing Card

Constructors

Club 
Diamond 
Heart 
Spade 

Instances

Instances details
Bounded Suit Source # 
Instance details

Defined in Poker.Cards

Enum Suit Source # 
Instance details

Defined in Poker.Cards

Methods

succ :: Suit -> Suit #

pred :: Suit -> Suit #

toEnum :: Int -> Suit #

fromEnum :: Suit -> Int #

enumFrom :: Suit -> [Suit] #

enumFromThen :: Suit -> Suit -> [Suit] #

enumFromTo :: Suit -> Suit -> [Suit] #

enumFromThenTo :: Suit -> Suit -> Suit -> [Suit] #

Eq Suit Source # 
Instance details

Defined in Poker.Cards

Methods

(==) :: Suit -> Suit -> Bool #

(/=) :: Suit -> Suit -> Bool #

Ord Suit Source # 
Instance details

Defined in Poker.Cards

Methods

compare :: Suit -> Suit -> Ordering #

(<) :: Suit -> Suit -> Bool #

(<=) :: Suit -> Suit -> Bool #

(>) :: Suit -> Suit -> Bool #

(>=) :: Suit -> Suit -> Bool #

max :: Suit -> Suit -> Suit #

min :: Suit -> Suit -> Suit #

Read Suit Source # 
Instance details

Defined in Poker.Cards

Show Suit Source # 
Instance details

Defined in Poker.Cards

Methods

showsPrec :: Int -> Suit -> ShowS #

show :: Suit -> String #

showList :: [Suit] -> ShowS #

Generic Suit Source # 
Instance details

Defined in Poker.Cards

Associated Types

type Rep Suit :: Type -> Type #

Methods

from :: Suit -> Rep Suit x #

to :: Rep Suit x -> Suit #

Arbitrary Suit Source # 
Instance details

Defined in Poker.Cards

Methods

arbitrary :: Gen Suit #

shrink :: Suit -> [Suit] #

Pretty Suit Source #
>>> pretty allSuits
[c, d, h, s]
Instance details

Defined in Poker.Cards

Methods

pretty :: Suit -> Doc ann #

prettyList :: [Suit] -> Doc ann #

type Rep Suit Source # 
Instance details

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)))

allSuits :: [Suit] Source #

>>> allSuits
[Club,Diamond,Heart,Spade]

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

data Card Source #

Representation of a playing card.

Constructors

Card 

Fields

Instances

Instances details
Eq Card Source # 
Instance details

Defined in Poker.Cards

Methods

(==) :: Card -> Card -> Bool #

(/=) :: Card -> Card -> Bool #

Ord Card Source # 
Instance details

Defined in Poker.Cards

Methods

compare :: Card -> Card -> Ordering #

(<) :: Card -> Card -> Bool #

(<=) :: Card -> Card -> Bool #

(>) :: Card -> Card -> Bool #

(>=) :: Card -> Card -> Bool #

max :: Card -> Card -> Card #

min :: Card -> Card -> Card #

Read Card Source # 
Instance details

Defined in Poker.Cards

Show Card Source # 
Instance details

Defined in Poker.Cards

Methods

showsPrec :: Int -> Card -> ShowS #

show :: Card -> String #

showList :: [Card] -> ShowS #

IsString Card Source # 
Instance details

Defined in Poker.Cards

Methods

fromString :: String -> Card #

Generic Card Source # 
Instance details

Defined in Poker.Cards

Associated Types

type Rep Card :: Type -> Type #

Methods

from :: Card -> Rep Card x #

to :: Rep Card x -> Card #

Arbitrary Card Source # 
Instance details

Defined in Poker.Cards

Methods

arbitrary :: Gen Card #

shrink :: Card -> [Card] #

Pretty Card Source #
>>> pretty ("Ac" :: Card)
Ac
Instance details

Defined in Poker.Cards

Methods

pretty :: Card -> Doc ann #

prettyList :: [Card] -> Doc ann #

type Rep Card Source # 
Instance details

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)))

allCards :: [Card] Source #

All cards in a Deck

>>> length allCards
52

data Hole Source #

Hole represents a player's hole cards in a game of Texas Hold'Em

Constructors

UnsafeHole !Card !Card

First Card is expected to be > the second

Instances

Instances details
Eq Hole Source # 
Instance details

Defined in Poker.Cards

Methods

(==) :: Hole -> Hole -> Bool #

(/=) :: Hole -> Hole -> Bool #

Ord Hole Source # 
Instance details

Defined in Poker.Cards

Methods

compare :: Hole -> Hole -> Ordering #

(<) :: Hole -> Hole -> Bool #

(<=) :: Hole -> Hole -> Bool #

(>) :: Hole -> Hole -> Bool #

(>=) :: Hole -> Hole -> Bool #

max :: Hole -> Hole -> Hole #

min :: Hole -> Hole -> Hole #

Read Hole Source # 
Instance details

Defined in Poker.Cards

Show Hole Source # 
Instance details

Defined in Poker.Cards

Methods

showsPrec :: Int -> Hole -> ShowS #

show :: Hole -> String #

showList :: [Hole] -> ShowS #

IsString Hole Source #
>>> "AcKd" :: Hole
UnsafeHole (Card {rank = Ace, suit = Club}) (Card {rank = King, suit = Diamond})
Instance details

Defined in Poker.Cards

Methods

fromString :: String -> Hole #

Generic Hole Source # 
Instance details

Defined in Poker.Cards

Associated Types

type Rep Hole :: Type -> Type #

Methods

from :: Hole -> Rep Hole x #

to :: Rep Hole x -> Hole #

Arbitrary Hole Source #

The Arbitrary instance for Hole generates values whose Card members are already normalised.

Instance details

Defined in Poker.Cards

Methods

arbitrary :: Gen Hole #

shrink :: Hole -> [Hole] #

Pretty Hole Source #
>>> pretty <$> mkHole (Card Ace Heart) (Card King Spade)
Just AhKs
Instance details

Defined in Poker.Cards

Methods

pretty :: Hole -> Doc ann #

prettyList :: [Hole] -> Doc ann #

type Rep Hole Source # 
Instance details

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)))

mkHole :: Card -> Card -> Maybe Hole Source #

Returns a Hole if the incoming Cards are unique, else Nothing. Note that mkHole automatically normalises the order of the given Cards. See Hole for details.

\c1 c2 -> mkHole c1 c2 == mkHole c2 c1
\c1 c2 -> (c1 /= c2) ==> isJust (mkHole c1 c2)

allHoles :: [Hole] Source #

All possible valid Holes (the Holes are already normalised).

>>> length allCards * length allCards
2704
>>> length allHoles
1326
>>> Data.List.nub allHoles == allHoles
True
>>> pretty $ take 10 allHoles
[AsAh, AsAd, AhAd, AsAc, AhAc, AdAc, AsKs, AhKs, AdKs, AcKs]

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" :: ShapedHole
Pair Two
>>> "A4o" :: ShapedHole
UnsafeOffsuit Ace Four
>>> "KJs" :: ShapedHole
UnsafeSuited King Jack

Constructors

Pair !Rank 
UnsafeOffsuit !Rank !Rank

First Rank should be > the second

UnsafeSuited !Rank !Rank

First Rank should be > the second

Instances

Instances details
Eq ShapedHole Source # 
Instance details

Defined in Poker.Cards

Ord ShapedHole Source # 
Instance details

Defined in Poker.Cards

Read ShapedHole Source # 
Instance details

Defined in Poker.Cards

Show ShapedHole Source # 
Instance details

Defined in Poker.Cards

IsString ShapedHole Source #
>>> "AKs" :: ShapedHole
UnsafeSuited Ace King
>>> "AKo" :: ShapedHole
UnsafeOffsuit Ace King
>>> "AAp" :: ShapedHole
Pair Ace
>>> "KAs" == ("AKs" :: ShapedHole)
True
Instance details

Defined in Poker.Cards

Generic ShapedHole Source # 
Instance details

Defined in Poker.Cards

Associated Types

type Rep ShapedHole :: Type -> Type #

Arbitrary ShapedHole Source #

The Arbitrary instance for ShapedHole generates values whose Rank members are already normalised.

Instance details

Defined in Poker.Cards

Pretty ShapedHole Source #
>>> pretty $ take 10 allShapedHoles
[AAp, AKs, AQs, AJs, ATs, A9s, A8s, A7s, A6s, A5s]
Instance details

Defined in Poker.Cards

Methods

pretty :: ShapedHole -> Doc ann #

prettyList :: [ShapedHole] -> Doc ann #

type Rep ShapedHole Source # 
Instance details

Defined in Poker.Cards

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 allShapedHoles
169
>>> Data.List.nub allShapedHoles == allShapedHoles
True
>>> 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

data Deck Source #

A Deck of Cards

Instances

Instances details
Eq Deck Source # 
Instance details

Defined in Poker.Cards

Methods

(==) :: Deck -> Deck -> Bool #

(/=) :: Deck -> Deck -> Bool #

Read Deck Source # 
Instance details

Defined in Poker.Cards

Show Deck Source # 
Instance details

Defined in Poker.Cards

Methods

showsPrec :: Int -> Deck -> ShowS #

show :: Deck -> String #

showList :: [Deck] -> ShowS #

freshDeck :: Deck Source #

A unshuffled Deck with all Cards

>>> freshDeck == unsafeDeck allCards
True

unsafeDeck :: [Card] -> Deck Source #

The input Cards are not checked in any way.

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"]

rankToChr :: Rank -> Char Source #

>>> rankToChr <$> allRanks
"23456789TJQKA"

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

suitToChr :: Suit -> Char Source #

>>> suitToChr <$> allSuits
"cdhs"

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 #

First Rank should > than second Rank

unsafeSuited :: Rank -> Rank -> ShapedHole Source #

First Rank should be > than second Rank

unsafeHole :: Card -> Card -> Hole Source #

Unsafely create a new Hole. The first Card should be > than the second. See mkHole for a safe way to create a Hole.

holeFromShortTxt :: Text -> Maybe Hole Source #

>>> holeFromShortTxt "AcKd"
Just (UnsafeHole (Card {rank = Ace, suit = Club}) (Card {rank = King, suit = Diamond}))
>>> ("KdAc" :: Hole) == "AcKd"
True
\h -> holeFromShortTxt (holeToShortTxt h) == Just h