unicode-tricks-0.8.0.0: Functions to work with unicode blocks more convenient.

Maintainerhapytexeu+gh@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellSafe
LanguageHaskell2010

Data.Char.Domino

Contents

Description

A module that defines values for domino pieces, and converts these to unicode characters of the 1F030 unicode block.

Synopsis

Data types to represent domino values

data Domino a Source #

A domino piece, which has two items. Depending on the orientation, the items are located at the top and bottom; or left and right.

Constructors

Domino

The front side of the domino piece.

Fields

  • leftTop :: a

    The part that is located at the left side in case the piece is located horizontally, or at the top in case the piece is located vertically.

  • rightBottom :: a

    The part that is located at the right side in case the piece is located horizontally, or at the bottom in case the piece is located vertically.

Back

The back side of the domino piece.

Instances
Functor Domino Source # 
Instance details

Defined in Data.Char.Domino

Methods

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

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

Applicative Domino Source # 
Instance details

Defined in Data.Char.Domino

Methods

pure :: a -> Domino a #

(<*>) :: Domino (a -> b) -> Domino a -> Domino b #

liftA2 :: (a -> b -> c) -> Domino a -> Domino b -> Domino c #

(*>) :: Domino a -> Domino b -> Domino b #

(<*) :: Domino a -> Domino b -> Domino a #

Foldable Domino Source # 
Instance details

Defined in Data.Char.Domino

Methods

fold :: Monoid m => Domino m -> m #

foldMap :: Monoid m => (a -> m) -> Domino a -> m #

foldr :: (a -> b -> b) -> b -> Domino a -> b #

foldr' :: (a -> b -> b) -> b -> Domino a -> b #

foldl :: (b -> a -> b) -> b -> Domino a -> b #

foldl' :: (b -> a -> b) -> b -> Domino a -> b #

foldr1 :: (a -> a -> a) -> Domino a -> a #

foldl1 :: (a -> a -> a) -> Domino a -> a #

toList :: Domino a -> [a] #

null :: Domino a -> Bool #

length :: Domino a -> Int #

elem :: Eq a => a -> Domino a -> Bool #

maximum :: Ord a => Domino a -> a #

minimum :: Ord a => Domino a -> a #

sum :: Num a => Domino a -> a #

product :: Num a => Domino a -> a #

Traversable Domino Source # 
Instance details

Defined in Data.Char.Domino

Methods

traverse :: Applicative f => (a -> f b) -> Domino a -> f (Domino b) #

sequenceA :: Applicative f => Domino (f a) -> f (Domino a) #

mapM :: Monad m => (a -> m b) -> Domino a -> m (Domino b) #

sequence :: Monad m => Domino (m a) -> m (Domino a) #

Arbitrary1 Domino Source # 
Instance details

Defined in Data.Char.Domino

Methods

liftArbitrary :: Gen a -> Gen (Domino a) #

liftShrink :: (a -> [a]) -> Domino a -> [Domino a] #

Eq a => Eq (Domino a) Source # 
Instance details

Defined in Data.Char.Domino

Methods

(==) :: Domino a -> Domino a -> Bool #

(/=) :: Domino a -> Domino a -> Bool #

Ord a => Ord (Domino a) Source # 
Instance details

Defined in Data.Char.Domino

Methods

compare :: Domino a -> Domino a -> Ordering #

(<) :: Domino a -> Domino a -> Bool #

(<=) :: Domino a -> Domino a -> Bool #

(>) :: Domino a -> Domino a -> Bool #

(>=) :: Domino a -> Domino a -> Bool #

max :: Domino a -> Domino a -> Domino a #

min :: Domino a -> Domino a -> Domino a #

Read a => Read (Domino a) Source # 
Instance details

Defined in Data.Char.Domino

Show a => Show (Domino a) Source # 
Instance details

Defined in Data.Char.Domino

Methods

showsPrec :: Int -> Domino a -> ShowS #

show :: Domino a -> String #

showList :: [Domino a] -> ShowS #

Arbitrary a => Arbitrary (Domino a) Source # 
Instance details

Defined in Data.Char.Domino

Methods

arbitrary :: Gen (Domino a) #

shrink :: Domino a -> [Domino a] #

pattern (:|) Source #

Arguments

:: a

The item that is located at the left, or the top.

-> a

The item that is located at the right, or the bottom.

-> Domino a

The domino that is constructed.

A pattern synonym that makes it more convenient to write expressions that look like domino's like for example II :| IV.

type OrientedDomino a = Oriented (Domino a) Source #

A type alias that specifies that OrientedDomino is an Oriented type that wraps a Domino item.

type SimpleDomino = Domino DieValue Source #

A SimpleDomino is a Domino that contains DieValue objects, it thus can not have an "empty" value.

type ComplexDomino = Domino (Maybe DieValue) Source #

A ComplexDomino is a Domino that contains Maybe values wrapping a DieValue. In case of a Nothing, that side is considered empty.

Render domino values

dominoH Source #

Arguments

:: ComplexDomino

The ComplexDomino object to render horizontally.

-> Char

The unicode character that represents the given ComplexDomino value in a horizontal manner.

Convert a ComplexDomino value to a unicode character rendering the domino value horizontally.

dominoH' Source #

Arguments

:: SimpleDomino

The SimpleDomino object to render horizontally.

-> Char

The unicode character that represents the given SimpleDomino value in a horizontal manner.

Convert a SimpleDomino value to a unicode character rendering the domino value horizontally.

dominoV Source #

Arguments

:: ComplexDomino

The ComplexDomino object to render vertically.

-> Char

The unicode character that represents the given ComplexDomino value in a vertical manner.

Convert a ComplexDomino value to a unicode character rendering the domino value vertically.

dominoV' Source #

Arguments

:: SimpleDomino

The SimpleDomino object to render vertically.

-> Char

The unicode character that represents the given SimpleDomino value in vertical manner.

Convert a SimpleDomino value to a unicode character rendering the domino value vertically.

domino Source #

Arguments

:: OrientedDomino (Maybe DieValue)

The OrientedDomino to render.

-> Char

The unicode characters that represents the OrientedDomino value.

Convert an OrientedDomino to its unicode equivalent, where the sides of the domino can be empty.

domino' Source #

Arguments

:: OrientedDomino DieValue

The OrientedDomino to render.

-> Char

The unicode characters that represents the OrientedDomino value.

Convert an OrientedDomino to its unicode equivalent, where the sides of the domino can not be empty.