Maintainer | hapytexeu+gh@gmail.com |
---|---|
Stability | experimental |
Portability | POSIX |
Safe Haskell | Safe |
Language | Haskell2010 |
A module that defines values for domino pieces, and converts these to unicode characters of the 1F030 unicode block.
Synopsis
- data Domino a
- = Domino {
- leftTop :: a
- rightBottom :: a
- | Back
- = Domino {
- pattern (:|) :: a -> a -> Domino a
- type OrientedDomino a = Oriented (Domino a)
- type SimpleDomino = Domino DieValue
- type ComplexDomino = Domino (Maybe DieValue)
- dominoH :: ComplexDomino -> Char
- dominoH' :: SimpleDomino -> Char
- dominoV :: ComplexDomino -> Char
- dominoV' :: SimpleDomino -> Char
- domino :: OrientedDomino (Maybe DieValue) -> Char
- domino' :: OrientedDomino DieValue -> Char
Data types to represent domino values
A domino piece, which has two items. Depending on the orientation, the items are located at the top and bottom; or left and right.
Domino | The front side of the domino piece. |
| |
Back | The back side of the domino piece. |
Instances
Functor Domino Source # | |
Applicative Domino Source # | |
Foldable Domino Source # | |
Defined in Data.Char.Domino 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 # elem :: Eq a => a -> Domino a -> Bool # maximum :: Ord a => Domino a -> a # minimum :: Ord a => Domino a -> a # | |
Traversable Domino Source # | |
Arbitrary1 Domino Source # | |
Defined in Data.Char.Domino liftArbitrary :: Gen a -> Gen (Domino a) # liftShrink :: (a -> [a]) -> Domino a -> [Domino a] # | |
Eq a => Eq (Domino a) Source # | |
Ord a => Ord (Domino a) Source # | |
Defined in Data.Char.Domino | |
Read a => Read (Domino a) Source # | |
Show a => Show (Domino a) Source # | |
Arbitrary a => Arbitrary (Domino a) Source # | |
:: 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
:: ComplexDomino | The |
-> Char | The unicode character that represents the given |
Convert a ComplexDomino
value to a unicode character rendering the domino
value horizontally.
:: SimpleDomino | The |
-> Char | The unicode character that represents the given |
Convert a SimpleDomino
value to a unicode character rendering the domino
value horizontally.
:: ComplexDomino | The |
-> Char | The unicode character that represents the given |
Convert a ComplexDomino
value to a unicode character rendering the domino
value vertically.
:: SimpleDomino | The |
-> Char | The unicode character that represents the given |
Convert a SimpleDomino
value to a unicode character rendering the domino
value vertically.
:: OrientedDomino (Maybe DieValue) | The |
-> Char | The unicode characters that represents the |
Convert an OrientedDomino
to its unicode equivalent, where the sides of
the domino can be empty.
:: OrientedDomino DieValue | The |
-> Char | The unicode characters that represents the |
Convert an OrientedDomino
to its unicode equivalent, where the sides of
the domino can not be empty.