| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Poker
Description
Datatypes and supporting infrastructure for poker computation.
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
- newtype Position = Position Word8
- data NumPlayers
- numPlayersToWord8 :: NumPlayers -> Word8
- numPlayersFromWord8 :: Word8 -> Maybe NumPlayers
- mkNumPlayers :: Integral a => a -> Maybe NumPlayers
- allPositions :: NumPlayers -> [Position]
- positionToTxt :: NumPlayers -> Position -> Text
- getPreflopOrder :: NumPlayers -> [Position]
- buttonPosition :: NumPlayers -> Position
- bigBlindPosition :: NumPlayers -> Position
- getPostFlopOrder :: NumPlayers -> [Position]
- sortPostflop :: NumPlayers -> [Position] -> [Position]
- newtype Seat = Seat {}
- newtype Pot b = Pot {
- _pot :: b
- newtype Stack b = Stack {
- _stack :: b
- newtype Stake b = Stake {
- _stake :: b
- data Amount (b :: Symbol)
- unsafeAmount :: (GoodScale (CurrencyScale b), KnownSymbol b) => Discrete' b (CurrencyScale b) -> Amount b
- class (Monoid b, Show b, Ord b) => IsBet b where
- smallestAmount :: b
- minus :: b -> b -> Maybe b
- add :: b -> b -> b
- mkAmount :: (GoodScale (CurrencyScale b), KnownSymbol b) => Discrete' b (CurrencyScale b) -> Maybe (Amount b)
- newtype BigBlind = BigBlind {
- unBigBlind :: Amount "BB"
- bigBlindToDense :: BigBlind -> Dense "BB"
- data Freq = Freq !Int !Int
- newtype Range a b = Range {}
- getDecisionFreqRange :: Foldable f => (b -> Bool) -> Range a (f b) -> Range a Freq
- holdingRangeToShapedRange :: Monoid v => Range Hole v -> Range ShapedHole v
- addHoleToShapedRange :: Num a => a -> Hole -> Range ShapedHole a -> Range ShapedHole a
Usage
>>>import Poker>>>Just h = mkHole (Card Ace Club) (Card Two Diamond)>>>holeToShortTxt h"Ac2d"
Cards
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 cards
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 #
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
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 :)
Instances
| Bounded Position Source # | |
| Enum Position Source # | |
| Eq Position Source # | |
| Data Position Source # | |
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 # | |
Defined in Poker.Game | |
| Read Position Source # | |
| Show Position Source # | |
| Pretty Position Source # | |
Defined in Poker.Game | |
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.
Constructors
| TwoPlayers | |
| ThreePlayers | |
| FourPlayers | |
| FivePlayers | |
| SixPlayers | |
| SevenPlayers | |
| EightPlayers | |
| NinePlayers |
Instances
| Enum NumPlayers Source # | |
Defined in Poker.Game Methods succ :: NumPlayers -> NumPlayers # pred :: NumPlayers -> NumPlayers # toEnum :: Int -> NumPlayers # fromEnum :: NumPlayers -> Int # enumFrom :: NumPlayers -> [NumPlayers] # enumFromThen :: NumPlayers -> NumPlayers -> [NumPlayers] # enumFromTo :: NumPlayers -> NumPlayers -> [NumPlayers] # enumFromThenTo :: NumPlayers -> NumPlayers -> NumPlayers -> [NumPlayers] # | |
| Eq NumPlayers Source # | |
Defined in Poker.Game | |
| Ord NumPlayers Source # | |
Defined in Poker.Game Methods compare :: NumPlayers -> NumPlayers -> Ordering # (<) :: NumPlayers -> NumPlayers -> Bool # (<=) :: NumPlayers -> NumPlayers -> Bool # (>) :: NumPlayers -> NumPlayers -> Bool # (>=) :: NumPlayers -> NumPlayers -> Bool # max :: NumPlayers -> NumPlayers -> NumPlayers # min :: NumPlayers -> NumPlayers -> NumPlayers # | |
numPlayersToWord8 :: NumPlayers -> Word8 Source #
Convert a NumPlayers to a Word8.
numPlayersFromWord8 :: Word8 -> Maybe NumPlayers Source #
Convert a Word8 to a NumPlayers.
mkNumPlayers :: Integral a => a -> Maybe NumPlayers Source #
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 TwoPlayersPosition 0>>>(\numPlayers -> positionToTxt numPlayers $ buttonPosition numPlayers) <$> enumFromTo TwoPlayers NinePlayers["BU","BU","BU","BU","BU","BU","BU","BU"]
bigBlindPosition :: NumPlayers -> Position Source #
>>>bigBlindPosition TwoPlayersPosition 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"]
A player's seat number at a poker table.
Total amount of money in the Pot.
Amount of money in a player's stack (not having been bet).
Amount of money needed to join a game.
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
| Eq (Amount b) Source # | |
| Ord (Amount b) Source # | |
Defined in Poker.Amount | |
| Show (Amount b) Source # | |
| (GoodScale (CurrencyScale b), KnownSymbol b) => Semigroup (Amount b) Source # | |
| (GoodScale (CurrencyScale b), KnownSymbol b) => Monoid (Amount b) Source # | |
| Pretty (Amount b) Source # | |
Defined in Poker.Amount | |
| (GoodScale (CurrencyScale b), KnownSymbol b) => IsBet (Amount b) Source # | |
unsafeAmount :: (GoodScale (CurrencyScale b), KnownSymbol b) => Discrete' b (CurrencyScale b) -> Amount b Source #
class (Monoid b, Show b, Ord b) => IsBet b where Source #
A type b satisfies IsBet if we know:
- A
Monoidinstance forb. This allows us to construct a zero amount ofband toaddtwo amounts ofbtogether. - the smallest non-zero currency unit for
b(smallestAmount). For example, for USD the minimum currency amount is $0.01. - how to
addtwobs. By default, this is theMonoidinstance's append forb. - how to
minustwobs, which may fail (returningNothing), if the resultingAmountis 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
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" 0Just (UnsafeAmount {unAmount = Discrete "USD" 100%1 0})>>>mkAmount @"USD" (-1)Nothing
BigBlind is the type describing poker chip amounts that are measured in big blinds.
The internal representation of BigBlind is . This module introduces
a new instance of Amount BBCurrencyScale (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
| |
bigBlindToDense :: BigBlind -> Dense "BB" Source #
Range
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.
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).
Instances
| (Eq a, Eq b) => Eq (Range a b) Source # | |
| (Ord a, Read a, Read b) => Read (Range a b) Source # | |
| (Show a, Show b) => Show (Range a b) Source # | |
| (Ord a, Monoid b) => Semigroup (Range a b) Source # |
|
| (Ord a, Monoid b) => Monoid (Range a b) Source # |
|
| (Pretty a, Pretty b) => Pretty (Range a b) Source # | |
Defined in Poker.Range | |
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.