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

Poker

Description

Datatypes and supporting infrastructure for poker computation.

Synopsis

Usage

>>> import Poker
>>> Just h = mkHole (Card Ace Club) (Card Two Diamond)
>>> holeToShortTxt h
"Ac2d"

Cards

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

Hole cards

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

Game

newtype Position Source #

A player's Position in a game of poker.

Positions are ordered by table order (clockwise). The smallest Position, Position 0, is the first player to act preflop. The largest Position is always the big blind.

>>> allPositions SixPlayers
[Position 0,Position 1,Position 2,Position 3,Position 4,Position 5]
>>> positionToTxt SixPlayers <$> allPositions SixPlayers
["LJ","HJ","CO","BU","SB","BB"]
>>> positionToTxt NinePlayers <$> allPositions NinePlayers
["UTG","UTG1","UTG2","LJ","HJ","CO","BU","SB","BB"]

The API for Position is unstable. We are open to better ideas :)

Constructors

Position Word8 

Instances

Instances details
Bounded Position Source # 
Instance details

Defined in Poker.Game

Enum Position Source # 
Instance details

Defined in Poker.Game

Eq Position Source # 
Instance details

Defined in Poker.Game

Data Position Source # 
Instance details

Defined in Poker.Game

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Position -> c Position #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Position #

toConstr :: Position -> Constr #

dataTypeOf :: Position -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Position) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Position) #

gmapT :: (forall b. Data b => b -> b) -> Position -> Position #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Position -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Position -> r #

gmapQ :: (forall d. Data d => d -> u) -> Position -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Position -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Position -> m Position #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Position -> m Position #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Position -> m Position #

Ord Position Source # 
Instance details

Defined in Poker.Game

Read Position Source # 
Instance details

Defined in Poker.Game

Show Position Source # 
Instance details

Defined in Poker.Game

Pretty Position Source # 
Instance details

Defined in Poker.Game

Methods

pretty :: Position -> Doc ann #

prettyList :: [Position] -> Doc ann #

data NumPlayers Source #

Number of active players at a poker table. Players sitting out do not count, as they do not contribute to the number of Positions.

mkNumPlayers :: Integral a => a -> Maybe NumPlayers Source #

WARNING: The incoming Integral is downcast to a Word8

allPositions :: NumPlayers -> [Position] Source #

>>> allPositions SixPlayers
[Position 0,Position 1,Position 2,Position 3,Position 4,Position 5]

positionToTxt :: NumPlayers -> Position -> Text Source #

>>> positionToTxt TwoPlayers <$> allPositions TwoPlayers
["BU","BB"]
>>> positionToTxt SixPlayers <$> allPositions SixPlayers
["LJ","HJ","CO","BU","SB","BB"]
>>> positionToTxt NinePlayers <$> allPositions NinePlayers
["UTG","UTG1","UTG2","LJ","HJ","CO","BU","SB","BB"]

getPreflopOrder :: NumPlayers -> [Position] Source #

>>> positionToTxt TwoPlayers <$> getPreflopOrder TwoPlayers
["BU","BB"]
>>> positionToTxt SixPlayers <$> getPreflopOrder SixPlayers
["LJ","HJ","CO","BU","SB","BB"]
>>> positionToTxt NinePlayers <$> getPreflopOrder NinePlayers
["UTG","UTG1","UTG2","LJ","HJ","CO","BU","SB","BB"]

buttonPosition :: NumPlayers -> Position Source #

>>> buttonPosition TwoPlayers
Position 0
>>> (\numPlayers -> positionToTxt numPlayers $ buttonPosition numPlayers) <$> enumFromTo TwoPlayers NinePlayers
["BU","BU","BU","BU","BU","BU","BU","BU"]

bigBlindPosition :: NumPlayers -> Position Source #

>>> bigBlindPosition TwoPlayers
Position 1
>>> (\numPlayers -> positionToTxt numPlayers $ bigBlindPosition numPlayers) <$> enumFromTo TwoPlayers NinePlayers
["BB","BB","BB","BB","BB","BB","BB","BB"]

getPostFlopOrder :: NumPlayers -> [Position] Source #

>>> positionToTxt TwoPlayers <$> getPostFlopOrder TwoPlayers
["BB","BU"]
>>> positionToTxt ThreePlayers <$> getPostFlopOrder ThreePlayers
["SB","BB","BU"]
>>> positionToTxt SixPlayers <$> getPostFlopOrder SixPlayers
["SB","BB","LJ","HJ","CO","BU"]
>>> positionToTxt NinePlayers <$> getPostFlopOrder NinePlayers
["SB","BB","UTG","UTG1","UTG2","LJ","HJ","CO","BU"]

sortPostflop :: NumPlayers -> [Position] -> [Position] Source #

Sort a list of positions acccording to postflop ordering

>>> positionToTxt TwoPlayers <$> sortPostflop TwoPlayers (allPositions TwoPlayers)
["BB","BU"]
>>> positionToTxt ThreePlayers <$> sortPostflop ThreePlayers (allPositions ThreePlayers)
["SB","BB","BU"]
>>> positionToTxt SixPlayers <$> sortPostflop SixPlayers (allPositions SixPlayers)
["SB","BB","LJ","HJ","CO","BU"]
>>> positionToTxt NinePlayers <$> sortPostflop NinePlayers (allPositions NinePlayers)
["SB","BB","UTG","UTG1","UTG2","LJ","HJ","CO","BU"]

newtype Seat Source #

A player's seat number at a poker table.

Constructors

Seat 

Fields

Instances

Instances details
Eq Seat Source # 
Instance details

Defined in Poker.Game

Methods

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

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

Num Seat Source # 
Instance details

Defined in Poker.Game

Methods

(+) :: Seat -> Seat -> Seat #

(-) :: Seat -> Seat -> Seat #

(*) :: Seat -> Seat -> Seat #

negate :: Seat -> Seat #

abs :: Seat -> Seat #

signum :: Seat -> Seat #

fromInteger :: Integer -> Seat #

Ord Seat Source # 
Instance details

Defined in Poker.Game

Methods

compare :: Seat -> Seat -> Ordering #

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

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

(>) :: Seat -> Seat -> Bool #

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

max :: Seat -> Seat -> Seat #

min :: Seat -> Seat -> Seat #

Read Seat Source # 
Instance details

Defined in Poker.Game

Show Seat Source # 
Instance details

Defined in Poker.Game

Methods

showsPrec :: Int -> Seat -> ShowS #

show :: Seat -> String #

showList :: [Seat] -> ShowS #

newtype Pot b Source #

Total amount of money in the Pot.

Constructors

Pot 

Fields

Instances

Instances details
Functor Pot Source # 
Instance details

Defined in Poker.Game

Methods

fmap :: (a -> b) -> Pot a -> Pot b #

(<$) :: a -> Pot b -> Pot a #

Eq b => Eq (Pot b) Source # 
Instance details

Defined in Poker.Game

Methods

(==) :: Pot b -> Pot b -> Bool #

(/=) :: Pot b -> Pot b -> Bool #

Num b => Num (Pot b) Source # 
Instance details

Defined in Poker.Game

Methods

(+) :: Pot b -> Pot b -> Pot b #

(-) :: Pot b -> Pot b -> Pot b #

(*) :: Pot b -> Pot b -> Pot b #

negate :: Pot b -> Pot b #

abs :: Pot b -> Pot b #

signum :: Pot b -> Pot b #

fromInteger :: Integer -> Pot b #

Ord b => Ord (Pot b) Source # 
Instance details

Defined in Poker.Game

Methods

compare :: Pot b -> Pot b -> Ordering #

(<) :: Pot b -> Pot b -> Bool #

(<=) :: Pot b -> Pot b -> Bool #

(>) :: Pot b -> Pot b -> Bool #

(>=) :: Pot b -> Pot b -> Bool #

max :: Pot b -> Pot b -> Pot b #

min :: Pot b -> Pot b -> Pot b #

Show b => Show (Pot b) Source # 
Instance details

Defined in Poker.Game

Methods

showsPrec :: Int -> Pot b -> ShowS #

show :: Pot b -> String #

showList :: [Pot b] -> ShowS #

Semigroup b => Semigroup (Pot b) Source # 
Instance details

Defined in Poker.Game

Methods

(<>) :: Pot b -> Pot b -> Pot b #

sconcat :: NonEmpty (Pot b) -> Pot b #

stimes :: Integral b0 => b0 -> Pot b -> Pot b #

Monoid b => Monoid (Pot b) Source # 
Instance details

Defined in Poker.Game

Methods

mempty :: Pot b #

mappend :: Pot b -> Pot b -> Pot b #

mconcat :: [Pot b] -> Pot b #

Pretty b => Pretty (Pot b) Source # 
Instance details

Defined in Poker.Game

Methods

pretty :: Pot b -> Doc ann #

prettyList :: [Pot b] -> Doc ann #

newtype Stack b Source #

Amount of money in a player's stack (not having been bet).

Constructors

Stack 

Fields

Instances

Instances details
Functor Stack Source # 
Instance details

Defined in Poker.Game

Methods

fmap :: (a -> b) -> Stack a -> Stack b #

(<$) :: a -> Stack b -> Stack a #

Eq b => Eq (Stack b) Source # 
Instance details

Defined in Poker.Game

Methods

(==) :: Stack b -> Stack b -> Bool #

(/=) :: Stack b -> Stack b -> Bool #

Num b => Num (Stack b) Source # 
Instance details

Defined in Poker.Game

Methods

(+) :: Stack b -> Stack b -> Stack b #

(-) :: Stack b -> Stack b -> Stack b #

(*) :: Stack b -> Stack b -> Stack b #

negate :: Stack b -> Stack b #

abs :: Stack b -> Stack b #

signum :: Stack b -> Stack b #

fromInteger :: Integer -> Stack b #

Ord b => Ord (Stack b) Source # 
Instance details

Defined in Poker.Game

Methods

compare :: Stack b -> Stack b -> Ordering #

(<) :: Stack b -> Stack b -> Bool #

(<=) :: Stack b -> Stack b -> Bool #

(>) :: Stack b -> Stack b -> Bool #

(>=) :: Stack b -> Stack b -> Bool #

max :: Stack b -> Stack b -> Stack b #

min :: Stack b -> Stack b -> Stack b #

Show b => Show (Stack b) Source # 
Instance details

Defined in Poker.Game

Methods

showsPrec :: Int -> Stack b -> ShowS #

show :: Stack b -> String #

showList :: [Stack b] -> ShowS #

Semigroup b => Semigroup (Stack b) Source # 
Instance details

Defined in Poker.Game

Methods

(<>) :: Stack b -> Stack b -> Stack b #

sconcat :: NonEmpty (Stack b) -> Stack b #

stimes :: Integral b0 => b0 -> Stack b -> Stack b #

Pretty b => Pretty (Stack b) Source # 
Instance details

Defined in Poker.Game

Methods

pretty :: Stack b -> Doc ann #

prettyList :: [Stack b] -> Doc ann #

newtype Stake b Source #

Amount of money needed to join a game.

Constructors

Stake 

Fields

Instances

Instances details
Functor Stake Source # 
Instance details

Defined in Poker.Game

Methods

fmap :: (a -> b) -> Stake a -> Stake b #

(<$) :: a -> Stake b -> Stake a #

Eq b => Eq (Stake b) Source # 
Instance details

Defined in Poker.Game

Methods

(==) :: Stake b -> Stake b -> Bool #

(/=) :: Stake b -> Stake b -> Bool #

Ord b => Ord (Stake b) Source # 
Instance details

Defined in Poker.Game

Methods

compare :: Stake b -> Stake b -> Ordering #

(<) :: Stake b -> Stake b -> Bool #

(<=) :: Stake b -> Stake b -> Bool #

(>) :: Stake b -> Stake b -> Bool #

(>=) :: Stake b -> Stake b -> Bool #

max :: Stake b -> Stake b -> Stake b #

min :: Stake b -> Stake b -> Stake b #

Read b => Read (Stake b) Source # 
Instance details

Defined in Poker.Game

Show b => Show (Stake b) Source # 
Instance details

Defined in Poker.Game

Methods

showsPrec :: Int -> Stake b -> ShowS #

show :: Stake b -> String #

showList :: [Stake b] -> ShowS #

Pretty b => Pretty (Stake b) Source # 
Instance details

Defined in Poker.Game

Methods

pretty :: Stake b -> Doc ann #

prettyList :: [Stake b] -> Doc ann #

Amount

data Amount (b :: Symbol) Source #

Amount is the type used to represent amounts of money during a game of poker. The internal representation of Amount is a Discrete' from the safe-money package. The exposed constructors for Amount ensure that no Amount can have a negative value.

The use of the safe-money package allows for lossless conversion between currencies with well-maintained support for type safety, serialisation, and currency conversions.

{-# Language TypeApplications #-}

case unsafeAmount @"USD" (discrete 100) of
  UnsafeAmount x -> x     -- x == discrete 100

Instances

Instances details
Eq (Amount b) Source # 
Instance details

Defined in Poker.Amount

Methods

(==) :: Amount b -> Amount b -> Bool #

(/=) :: Amount b -> Amount b -> Bool #

Ord (Amount b) Source # 
Instance details

Defined in Poker.Amount

Methods

compare :: Amount b -> Amount b -> Ordering #

(<) :: Amount b -> Amount b -> Bool #

(<=) :: Amount b -> Amount b -> Bool #

(>) :: Amount b -> Amount b -> Bool #

(>=) :: Amount b -> Amount b -> Bool #

max :: Amount b -> Amount b -> Amount b #

min :: Amount b -> Amount b -> Amount b #

Show (Amount b) Source # 
Instance details

Defined in Poker.Amount

Methods

showsPrec :: Int -> Amount b -> ShowS #

show :: Amount b -> String #

showList :: [Amount b] -> ShowS #

(GoodScale (CurrencyScale b), KnownSymbol b) => Semigroup (Amount b) Source # 
Instance details

Defined in Poker.Amount

Methods

(<>) :: Amount b -> Amount b -> Amount b #

sconcat :: NonEmpty (Amount b) -> Amount b #

stimes :: Integral b0 => b0 -> Amount b -> Amount b #

(GoodScale (CurrencyScale b), KnownSymbol b) => Monoid (Amount b) Source # 
Instance details

Defined in Poker.Amount

Methods

mempty :: Amount b #

mappend :: Amount b -> Amount b -> Amount b #

mconcat :: [Amount b] -> Amount b #

Pretty (Amount b) Source # 
Instance details

Defined in Poker.Amount

Methods

pretty :: Amount b -> Doc ann #

prettyList :: [Amount b] -> Doc ann #

(GoodScale (CurrencyScale b), KnownSymbol b) => IsBet (Amount b) Source # 
Instance details

Defined in Poker.Amount

unsafeAmount :: (GoodScale (CurrencyScale b), KnownSymbol b) => Discrete' b (CurrencyScale b) -> Amount b Source #

Make an Amount from a Discrete'. Only use when you are certain that your Discrete' value is positive, since most usages of Amount will break for negative quantities.

class (Monoid b, Show b, Ord b) => IsBet b where Source #

A type b satisfies IsBet if we know:

  • A Monoid instance for b. This allows us to construct a zero amount of b and to add two amounts of b together.
  • the smallest non-zero currency unit for b (smallestAmount). For example, for USD the minimum currency amount is $0.01.
  • how to add two bs. By default, this is the Monoid instance's append for b.
  • how to minus two bs, which may fail (returning Nothing), if the resulting Amount is negative.

Types that satisfy IsBet are expected to have both Ord and Show instances, so that packages such as poker-game can handle arbitrary new user bet types.

For an example instance of the IsBet class, see Poker.BigBlind.

Minimal complete definition

smallestAmount, minus

Methods

smallestAmount :: b Source #

minus :: b -> b -> Maybe b Source #

add :: b -> b -> b Source #

Instances

Instances details
IsBet BigBlind Source # 
Instance details

Defined in Poker.Amount

(GoodScale (CurrencyScale b), KnownSymbol b) => IsBet (Amount b) Source # 
Instance details

Defined in Poker.Amount

mkAmount :: (GoodScale (CurrencyScale b), KnownSymbol b) => Discrete' b (CurrencyScale b) -> Maybe (Amount b) Source #

Returns an Amount from a Discrete' so long as the given Discrete' is non-negative.

>>> mkAmount @"USD" 0
Just (UnsafeAmount {unAmount = Discrete "USD" 100%1 0})
>>> mkAmount @"USD" (-1)
Nothing

newtype BigBlind Source #

BigBlind is the type describing poker chip amounts that are measured in big blinds.

The internal representation of BigBlind is Amount BB. This module introduces a new instance of CurrencyScale (from the safe-money package), which allows translation from BigBlind to any valid currency in a lossless manner.

The small unit of a "BB" is a "bb", with 100 "bb"s in a "BB".

TODO include an API for translating from BigBlind to any safe-money currency, given a Stake.

Calculations in the safe-money package are done with Discrete and Dense types. Discrete values are used to describe a regular BigBlind value, such as 1.30bb. Dense values are used when calculating some complex (non-discrete) value such as one third of a big blind. When using the BigBlind type, it is best to do all calculation with Dense BB values and then convert back to a Discrete BB "bb" after all calculation has been completed:

Constructors

BigBlind 

Fields

Instances

Instances details
Eq BigBlind Source # 
Instance details

Defined in Poker.Amount

Ord BigBlind Source # 
Instance details

Defined in Poker.Amount

Show BigBlind Source # 
Instance details

Defined in Poker.Amount

Generic BigBlind Source # 
Instance details

Defined in Poker.Amount

Associated Types

type Rep BigBlind :: Type -> Type #

Methods

from :: BigBlind -> Rep BigBlind x #

to :: Rep BigBlind x -> BigBlind #

Semigroup BigBlind Source # 
Instance details

Defined in Poker.Amount

Monoid BigBlind Source # 
Instance details

Defined in Poker.Amount

IsBet BigBlind Source # 
Instance details

Defined in Poker.Amount

type Rep BigBlind Source # 
Instance details

Defined in Poker.Amount

type Rep BigBlind = D1 ('MetaData "BigBlind" "Poker.Amount" "poker-base-0.1.0.0-CHz5byiVovtI4WerZQqrDU" 'True) (C1 ('MetaCons "BigBlind" 'PrefixI 'True) (S1 ('MetaSel ('Just "unBigBlind") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Amount "BB"))))

bigBlindToDense :: BigBlind -> Dense "BB" Source #

When working with a BigBlind you might want to (cautiously) retain losslessness when using functions such as % calculations or division. A Dense allows you to do so.

Range

data Freq Source #

A frequency is an unevaluated ratio that indicates how often a decision was made. For example, the value Freq (12, 34) indicates that out of the 34 people who faced this decision, 12 chose to make this decision.

Constructors

Freq !Int !Int 

Instances

Instances details
Eq Freq Source # 
Instance details

Defined in Poker.Range

Methods

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

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

Show Freq Source # 
Instance details

Defined in Poker.Range

Methods

showsPrec :: Int -> Freq -> ShowS #

show :: Freq -> String #

showList :: [Freq] -> ShowS #

Semigroup Freq Source # 
Instance details

Defined in Poker.Range

Methods

(<>) :: Freq -> Freq -> Freq #

sconcat :: NonEmpty Freq -> Freq #

stimes :: Integral b => b -> Freq -> Freq #

Monoid Freq Source # 
Instance details

Defined in Poker.Range

Methods

mempty :: Freq #

mappend :: Freq -> Freq -> Freq #

mconcat :: [Freq] -> Freq #

newtype Range a b Source #

A simple wrapper around a Map that uses different instances for Semigroup. Range's Semigroup instance combines values at the same keys with <> (unlike the Map Semigroup instance from containers).

Note that the Range's internal Map is strict.

Constructors

Range 

Fields

Instances

Instances details
(Eq a, Eq b) => Eq (Range a b) Source # 
Instance details

Defined in Poker.Range

Methods

(==) :: Range a b -> Range a b -> Bool #

(/=) :: Range a b -> Range a b -> Bool #

(Ord a, Read a, Read b) => Read (Range a b) Source # 
Instance details

Defined in Poker.Range

(Show a, Show b) => Show (Range a b) Source # 
Instance details

Defined in Poker.Range

Methods

showsPrec :: Int -> Range a b -> ShowS #

show :: Range a b -> String #

showList :: [Range a b] -> ShowS #

(Ord a, Monoid b) => Semigroup (Range a b) Source #
>>> let left = rangeFromList [("55p" :: ShapedHole, Freq 1 3)]
>>> let right = rangeFromList [("55p", Freq 10 32)]
>>> left <> right
Range {_range = fromList [(Pair Five,Freq 11 35)]}
Instance details

Defined in Poker.Range

Methods

(<>) :: Range a b -> Range a b -> Range a b #

sconcat :: NonEmpty (Range a b) -> Range a b #

stimes :: Integral b0 => b0 -> Range a b -> Range a b #

(Ord a, Monoid b) => Monoid (Range a b) Source #
>>> mempty @(Range Hole Freq)
Range {_range = fromList []}
Instance details

Defined in Poker.Range

Methods

mempty :: Range a b #

mappend :: Range a b -> Range a b -> Range a b #

mconcat :: [Range a b] -> Range a b #

(Pretty a, Pretty b) => Pretty (Range a b) Source # 
Instance details

Defined in Poker.Range

Methods

pretty :: Range a b -> Doc ann #

prettyList :: [Range a b] -> Doc ann #

getDecisionFreqRange :: Foldable f => (b -> Bool) -> Range a (f b) -> Range a Freq Source #

Converts a Range from key to action, to a Range from key to decision frequency, given a predicate that returns True if the action matched the decision.

holdingRangeToShapedRange :: Monoid v => Range Hole v -> Range ShapedHole v Source #

Convert from a Range of hole cards to a Range of ShapedHole.

addHoleToShapedRange :: Num a => a -> Hole -> Range ShapedHole a -> Range ShapedHole a Source #

Add a singleton Hole hand to a Range of ShapedHole.