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

Poker.Game

Description

Representation of a game of holdem, including table structure, positioning, pot and betting state.

Synopsis

Documentation

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 #