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

Poker.Amount

Description

Representation of money, and bet quantities.

Synopsis

Documentation

data Amount (b :: Symbol) where 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

Constructors

UnsafeAmount 

Fields

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

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.

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