{-# LANGUAGE DeriveTraversable, FlexibleInstances, PatternSynonyms, Safe #-}

{-|
Module      : Data.Char.Domino
Description : A module that defines domino values, and their unicode equivalent.
Maintainer  : hapytexeu+gh@gmail.com
Stability   : experimental
Portability : POSIX

A module that defines values for domino pieces, and converts these to unicode characters of the <https://www.unicode.org/charts/PDF/U1F030.pdf 1F030 unicode block>.
-}

module Data.Char.Domino (
    -- * Data types to represent domino values
    Domino(Domino, Back, leftTop, rightBottom), pattern (:|)
  , OrientedDomino, SimpleDomino, ComplexDomino
    -- * Render domino values
  , dominoH, dominoH'
  , dominoV, dominoV'
  , domino , domino'
    -- * Convert from 'Char'acters
  , fromDomino, fromDomino'
  ) where

import Control.Monad((>=>))

import Data.Char(chr, ord)
import Data.Char.Core(UnicodeCharacter(toUnicodeChar, fromUnicodeChar, fromUnicodeChar'), UnicodeText, Orientation(Horizontal, Vertical), Oriented(Oriented))
import Data.Char.Dice(DieValue)
import Data.Function(on)

import Test.QuickCheck.Arbitrary(Arbitrary(arbitrary), Arbitrary1(liftArbitrary), arbitrary1)
import Test.QuickCheck.Gen(frequency)

-- | A domino piece, which has two items. Depending on the orientation, the
-- items are located at the /top/ and /bottom/; or /left/ and /right/.
data Domino a
  = Domino  -- ^ The front side of the domino piece.
  {
    Domino a -> a
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/.
  , Domino a -> a
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.
  deriving (Domino a -> Domino a -> Bool
(Domino a -> Domino a -> Bool)
-> (Domino a -> Domino a -> Bool) -> Eq (Domino a)
forall a. Eq a => Domino a -> Domino a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Domino a -> Domino a -> Bool
$c/= :: forall a. Eq a => Domino a -> Domino a -> Bool
== :: Domino a -> Domino a -> Bool
$c== :: forall a. Eq a => Domino a -> Domino a -> Bool
Eq, Domino a -> Bool
(a -> m) -> Domino a -> m
(a -> b -> b) -> b -> Domino a -> b
(forall m. Monoid m => Domino m -> m)
-> (forall m a. Monoid m => (a -> m) -> Domino a -> m)
-> (forall m a. Monoid m => (a -> m) -> Domino a -> m)
-> (forall a b. (a -> b -> b) -> b -> Domino a -> b)
-> (forall a b. (a -> b -> b) -> b -> Domino a -> b)
-> (forall b a. (b -> a -> b) -> b -> Domino a -> b)
-> (forall b a. (b -> a -> b) -> b -> Domino a -> b)
-> (forall a. (a -> a -> a) -> Domino a -> a)
-> (forall a. (a -> a -> a) -> Domino a -> a)
-> (forall a. Domino a -> [a])
-> (forall a. Domino a -> Bool)
-> (forall a. Domino a -> Int)
-> (forall a. Eq a => a -> Domino a -> Bool)
-> (forall a. Ord a => Domino a -> a)
-> (forall a. Ord a => Domino a -> a)
-> (forall a. Num a => Domino a -> a)
-> (forall a. Num a => Domino a -> a)
-> Foldable Domino
forall a. Eq a => a -> Domino a -> Bool
forall a. Num a => Domino a -> a
forall a. Ord a => Domino a -> a
forall m. Monoid m => Domino m -> m
forall a. Domino a -> Bool
forall a. Domino a -> Int
forall a. Domino a -> [a]
forall a. (a -> a -> a) -> Domino a -> a
forall m a. Monoid m => (a -> m) -> Domino a -> m
forall b a. (b -> a -> b) -> b -> Domino a -> b
forall a b. (a -> b -> b) -> b -> Domino a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: Domino a -> a
$cproduct :: forall a. Num a => Domino a -> a
sum :: Domino a -> a
$csum :: forall a. Num a => Domino a -> a
minimum :: Domino a -> a
$cminimum :: forall a. Ord a => Domino a -> a
maximum :: Domino a -> a
$cmaximum :: forall a. Ord a => Domino a -> a
elem :: a -> Domino a -> Bool
$celem :: forall a. Eq a => a -> Domino a -> Bool
length :: Domino a -> Int
$clength :: forall a. Domino a -> Int
null :: Domino a -> Bool
$cnull :: forall a. Domino a -> Bool
toList :: Domino a -> [a]
$ctoList :: forall a. Domino a -> [a]
foldl1 :: (a -> a -> a) -> Domino a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> Domino a -> a
foldr1 :: (a -> a -> a) -> Domino a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> Domino a -> a
foldl' :: (b -> a -> b) -> b -> Domino a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> Domino a -> b
foldl :: (b -> a -> b) -> b -> Domino a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> Domino a -> b
foldr' :: (a -> b -> b) -> b -> Domino a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> Domino a -> b
foldr :: (a -> b -> b) -> b -> Domino a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> Domino a -> b
foldMap' :: (a -> m) -> Domino a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> Domino a -> m
foldMap :: (a -> m) -> Domino a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> Domino a -> m
fold :: Domino m -> m
$cfold :: forall m. Monoid m => Domino m -> m
Foldable, a -> Domino b -> Domino a
(a -> b) -> Domino a -> Domino b
(forall a b. (a -> b) -> Domino a -> Domino b)
-> (forall a b. a -> Domino b -> Domino a) -> Functor Domino
forall a b. a -> Domino b -> Domino a
forall a b. (a -> b) -> Domino a -> Domino b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> Domino b -> Domino a
$c<$ :: forall a b. a -> Domino b -> Domino a
fmap :: (a -> b) -> Domino a -> Domino b
$cfmap :: forall a b. (a -> b) -> Domino a -> Domino b
Functor, Eq (Domino a)
Eq (Domino a)
-> (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)
-> (Domino a -> Domino a -> Domino a)
-> (Domino a -> Domino a -> Domino a)
-> Ord (Domino a)
Domino a -> Domino a -> Bool
Domino a -> Domino a -> Ordering
Domino a -> Domino a -> Domino a
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall a. Ord a => Eq (Domino a)
forall a. Ord a => Domino a -> Domino a -> Bool
forall a. Ord a => Domino a -> Domino a -> Ordering
forall a. Ord a => Domino a -> Domino a -> Domino a
min :: Domino a -> Domino a -> Domino a
$cmin :: forall a. Ord a => Domino a -> Domino a -> Domino a
max :: Domino a -> Domino a -> Domino a
$cmax :: forall a. Ord a => Domino a -> Domino a -> Domino a
>= :: Domino a -> Domino a -> Bool
$c>= :: forall a. Ord a => Domino a -> Domino a -> Bool
> :: Domino a -> Domino a -> Bool
$c> :: forall a. Ord a => Domino a -> Domino a -> Bool
<= :: Domino a -> Domino a -> Bool
$c<= :: forall a. Ord a => Domino a -> Domino a -> Bool
< :: Domino a -> Domino a -> Bool
$c< :: forall a. Ord a => Domino a -> Domino a -> Bool
compare :: Domino a -> Domino a -> Ordering
$ccompare :: forall a. Ord a => Domino a -> Domino a -> Ordering
$cp1Ord :: forall a. Ord a => Eq (Domino a)
Ord, ReadPrec [Domino a]
ReadPrec (Domino a)
Int -> ReadS (Domino a)
ReadS [Domino a]
(Int -> ReadS (Domino a))
-> ReadS [Domino a]
-> ReadPrec (Domino a)
-> ReadPrec [Domino a]
-> Read (Domino a)
forall a. Read a => ReadPrec [Domino a]
forall a. Read a => ReadPrec (Domino a)
forall a. Read a => Int -> ReadS (Domino a)
forall a. Read a => ReadS [Domino a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Domino a]
$creadListPrec :: forall a. Read a => ReadPrec [Domino a]
readPrec :: ReadPrec (Domino a)
$creadPrec :: forall a. Read a => ReadPrec (Domino a)
readList :: ReadS [Domino a]
$creadList :: forall a. Read a => ReadS [Domino a]
readsPrec :: Int -> ReadS (Domino a)
$creadsPrec :: forall a. Read a => Int -> ReadS (Domino a)
Read, Int -> Domino a -> ShowS
[Domino a] -> ShowS
Domino a -> String
(Int -> Domino a -> ShowS)
-> (Domino a -> String) -> ([Domino a] -> ShowS) -> Show (Domino a)
forall a. Show a => Int -> Domino a -> ShowS
forall a. Show a => [Domino a] -> ShowS
forall a. Show a => Domino a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Domino a] -> ShowS
$cshowList :: forall a. Show a => [Domino a] -> ShowS
show :: Domino a -> String
$cshow :: forall a. Show a => Domino a -> String
showsPrec :: Int -> Domino a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Domino a -> ShowS
Show, Functor Domino
Foldable Domino
Functor Domino
-> Foldable Domino
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> Domino a -> f (Domino b))
-> (forall (f :: * -> *) a.
    Applicative f =>
    Domino (f a) -> f (Domino a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> Domino a -> m (Domino b))
-> (forall (m :: * -> *) a.
    Monad m =>
    Domino (m a) -> m (Domino a))
-> Traversable Domino
(a -> f b) -> Domino a -> f (Domino b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => Domino (m a) -> m (Domino a)
forall (f :: * -> *) a.
Applicative f =>
Domino (f a) -> f (Domino a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Domino a -> m (Domino b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Domino a -> f (Domino b)
sequence :: Domino (m a) -> m (Domino a)
$csequence :: forall (m :: * -> *) a. Monad m => Domino (m a) -> m (Domino a)
mapM :: (a -> m b) -> Domino a -> m (Domino b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Domino a -> m (Domino b)
sequenceA :: Domino (f a) -> f (Domino a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
Domino (f a) -> f (Domino a)
traverse :: (a -> f b) -> Domino a -> f (Domino b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Domino a -> f (Domino b)
$cp2Traversable :: Foldable Domino
$cp1Traversable :: Functor Domino
Traversable)

-- | A pattern synonym that makes it more convenient to write expressions that
-- look like domino's like for example @II :| IV@.
pattern (:|)
  :: 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.
pattern $b:| :: a -> a -> Domino a
$m:| :: forall r a. Domino a -> (a -> a -> r) -> (Void# -> r) -> r
(:|) x y = Domino x y

-- | A type alias that specifies that 'OrientedDomino' is an 'Oriented' type
-- that wraps a 'Domino' item.
type OrientedDomino a = Oriented (Domino a)

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

-- | A 'ComplexDomino' is a 'Domino' that contains 'Maybe' values wrapping a
-- 'DieValue'. In case of a 'Nothing', that side is considered /empty/.
type ComplexDomino = Domino (Maybe DieValue)

instance Applicative Domino where
    pure :: a -> Domino a
pure a
x = a -> a -> Domino a
forall a. a -> a -> Domino a
Domino a
x a
x
    Domino a -> b
fa a -> b
fb <*> :: Domino (a -> b) -> Domino a -> Domino b
<*> Domino a
a a
b = b -> b -> Domino b
forall a. a -> a -> Domino a
Domino (a -> b
fa a
a) (a -> b
fb a
b)
    Domino (a -> b)
_ <*> Domino a
_ = Domino b
forall a. Domino a
Back

instance Arbitrary a => Arbitrary (Domino a) where
    arbitrary :: Gen (Domino a)
arbitrary = Gen (Domino a)
forall (f :: * -> *) a. (Arbitrary1 f, Arbitrary a) => Gen (f a)
arbitrary1

instance Arbitrary1 Domino where
    liftArbitrary :: Gen a -> Gen (Domino a)
liftArbitrary Gen a
arb = [(Int, Gen (Domino a))] -> Gen (Domino a)
forall a. [(Int, Gen a)] -> Gen a
frequency [(Int
1, Domino a -> Gen (Domino a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Domino a
forall a. Domino a
Back), (Int
3, a -> a -> Domino a
forall a. a -> a -> Domino a
Domino (a -> a -> Domino a) -> Gen a -> Gen (a -> Domino a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen a
arb Gen (a -> Domino a) -> Gen a -> Gen (Domino a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen a
arb)]

instance Bounded a => Bounded (Domino a) where
    minBound :: Domino a
minBound = a -> a -> Domino a
forall a. a -> a -> Domino a
Domino a
forall a. Bounded a => a
minBound a
forall a. Bounded a => a
minBound
    maxBound :: Domino a
maxBound = Domino a
forall a. Domino a
Back

_offsetDominoHorizontal :: Int
_offsetDominoHorizontal :: Int
_offsetDominoHorizontal = Int
0x1f030

_offsetDominoVertical :: Int
_offsetDominoVertical :: Int
_offsetDominoVertical = Int
0x1f062

_domino :: Int -> ComplexDomino -> Char
_domino :: Int -> ComplexDomino -> Char
_domino Int
n = ComplexDomino -> Char
forall a. Enum a => Domino (Maybe a) -> Char
go
    where go :: Domino (Maybe a) -> Char
go Domino (Maybe a)
Back = Int -> Char
chr Int
n
          go (Domino Maybe a
a Maybe a
b) = Int -> Char
chr (Int
7 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Maybe a -> Int
forall a. Enum a => Maybe a -> Int
_val Maybe a
a Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Maybe a -> Int
forall a. Enum a => Maybe a -> Int
_val Maybe a
b Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
          _val :: Maybe a -> Int
_val Maybe a
Nothing = Int
0
          _val (Just a
x) = Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ a -> Int
forall a. Enum a => a -> Int
fromEnum a
x

_fromDomino :: Int -> ComplexDomino
_fromDomino :: Int -> ComplexDomino
_fromDomino (-1) = ComplexDomino
forall a. Domino a
Back
_fromDomino Int
n = (Maybe DieValue -> Maybe DieValue -> ComplexDomino)
-> (Int -> Maybe DieValue) -> Int -> Int -> ComplexDomino
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
on Maybe DieValue -> Maybe DieValue -> ComplexDomino
forall a. a -> a -> Domino a
Domino Int -> Maybe DieValue
forall a. Enum a => Int -> Maybe a
go Int
a Int
b
    where (Int
a, Int
b) = Int -> Int -> (Int, Int)
forall a. Integral a => a -> a -> (a, a)
quotRem Int
n Int
7
          go :: Int -> Maybe a
go Int
0 = Maybe a
forall a. Maybe a
Nothing
          go Int
k = a -> Maybe a
forall a. a -> Maybe a
Just (Int -> a
forall a. Enum a => Int -> a
toEnum (Int
kInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1))

-- | Convert the given 'Char'acter to an 'Oriented' 'ComplexDomino' object. If
-- the given 'Char'acter is not a valid domino character, the result is
-- unspecified.
fromDomino'
  :: Char  -- ^ The given 'Char'acter to convert to an 'Oriented' 'ComplexDomino' object.
  -> Oriented ComplexDomino  -- ^ The equivalent 'Oriented' 'ComplexDomino' object for the given 'Char'acter.
fromDomino' :: Char -> Oriented ComplexDomino
fromDomino' = Int -> Oriented ComplexDomino
go (Int -> Oriented ComplexDomino)
-> (Char -> Int) -> Char -> Oriented ComplexDomino
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Int
ord
    where go :: Int -> Oriented ComplexDomino
go Int
n | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
_offsetDominoVertical = Int -> Int -> Orientation -> Oriented ComplexDomino
go' Int
_offsetDominoVertical Int
n Orientation
Vertical
               | Bool
otherwise = Int -> Int -> Orientation -> Oriented ComplexDomino
go' Int
_offsetDominoHorizontal Int
n Orientation
Horizontal
          go' :: Int -> Int -> Orientation -> Oriented ComplexDomino
go' Int
k = ComplexDomino -> Orientation -> Oriented ComplexDomino
forall a. a -> Orientation -> Oriented a
Oriented (ComplexDomino -> Orientation -> Oriented ComplexDomino)
-> (Int -> ComplexDomino)
-> Int
-> Orientation
-> Oriented ComplexDomino
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> ComplexDomino
_fromDomino (Int -> ComplexDomino) -> (Int -> Int) -> Int -> ComplexDomino
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int
forall a. Enum a => a -> a
pred (Int -> Int) -> (Int -> Int) -> Int -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int -> Int
forall a. Num a => a -> a -> a
subtract Int
k

-- | Convert the given 'Char'acter to an 'Oriented' 'ComplexDomino' object. If
-- the given 'Char'acter wrapped in a 'Just' data constructor if the 'Char'acter
-- is a valid domino character; otherwise 'Nothing'.
fromDomino
  :: Char  -- ^ The given 'Char'acter to convert to an 'Oriented' 'ComplexDomino' object.
  -> Maybe (Oriented ComplexDomino)  -- ^ The equivalent 'Oriented' 'ComplexDomino' object for the given 'Char'acter wrapped in a 'Just'; 'Nothing' if the character is not a domino character.
fromDomino :: Char -> Maybe (Oriented ComplexDomino)
fromDomino Char
c
    | Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
< Char
'\x1f030' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
> Char
'\x1f093' = Maybe (Oriented ComplexDomino)
forall a. Maybe a
Nothing
    | Bool
otherwise = Oriented ComplexDomino -> Maybe (Oriented ComplexDomino)
forall a. a -> Maybe a
Just (Char -> Oriented ComplexDomino
fromDomino' Char
c)

toSimple :: Domino (Maybe a) -> Maybe (Domino a)
toSimple :: Domino (Maybe a) -> Maybe (Domino a)
toSimple Domino (Maybe a)
Back = Domino a -> Maybe (Domino a)
forall a. a -> Maybe a
Just Domino a
forall a. Domino a
Back
toSimple (Domino (Just a
a) (Just a
b)) = Domino a -> Maybe (Domino a)
forall a. a -> Maybe a
Just (a -> a -> Domino a
forall a. a -> a -> Domino a
Domino a
a a
b)
toSimple Domino (Maybe a)
_ = Maybe (Domino a)
forall a. Maybe a
Nothing

-- | Convert a 'ComplexDomino' value to a unicode character rendering the domino
-- value /horizontally/.
dominoH
  :: ComplexDomino  -- ^ The 'ComplexDomino' object to render horizontally.
  -> Char  -- ^ The unicode character that represents the given 'ComplexDomino' value in a horizontal manner.
dominoH :: ComplexDomino -> Char
dominoH = Int -> ComplexDomino -> Char
_domino Int
_offsetDominoHorizontal

-- | Convert a 'SimpleDomino' value to a unicode character rendering the domino
-- value /horizontally/.
dominoH'
  :: SimpleDomino  -- ^ The 'SimpleDomino' object to render horizontally.
  -> Char  -- ^ The unicode character that represents the given 'SimpleDomino' value in a horizontal manner.
dominoH' :: SimpleDomino -> Char
dominoH' = ComplexDomino -> Char
dominoH (ComplexDomino -> Char)
-> (SimpleDomino -> ComplexDomino) -> SimpleDomino -> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (DieValue -> Maybe DieValue) -> SimpleDomino -> ComplexDomino
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap DieValue -> Maybe DieValue
forall a. a -> Maybe a
Just

-- | Convert a 'ComplexDomino' value to a unicode character rendering the domino
-- value /vertically/.
dominoV
  :: ComplexDomino  -- ^ The 'ComplexDomino' object to render vertically.
  -> Char  -- ^ The unicode character that represents the given 'ComplexDomino' value in a vertical manner.
dominoV :: ComplexDomino -> Char
dominoV = Int -> ComplexDomino -> Char
_domino Int
_offsetDominoVertical

-- | Convert a 'SimpleDomino' value to a unicode character rendering the domino
-- value /vertically/.
dominoV'
  :: SimpleDomino  -- ^ The 'SimpleDomino' object to render vertically.
  -> Char  -- ^ The unicode character that represents the given 'SimpleDomino' value in vertical manner.
dominoV' :: SimpleDomino -> Char
dominoV' = ComplexDomino -> Char
dominoV (ComplexDomino -> Char)
-> (SimpleDomino -> ComplexDomino) -> SimpleDomino -> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (DieValue -> Maybe DieValue) -> SimpleDomino -> ComplexDomino
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap DieValue -> Maybe DieValue
forall a. a -> Maybe a
Just

-- | Convert an 'OrientedDomino' to its unicode equivalent, where the sides of
-- the domino can be empty.
domino
  :: OrientedDomino (Maybe DieValue)  -- ^ The 'OrientedDomino' to render.
  -> Char  -- ^ The unicode characters that represents the 'OrientedDomino' value.
domino :: Oriented ComplexDomino -> Char
domino (Oriented ComplexDomino
d Orientation
Horizontal) = ComplexDomino -> Char
dominoH ComplexDomino
d
domino (Oriented ComplexDomino
d Orientation
Vertical) = ComplexDomino -> Char
dominoV ComplexDomino
d

-- | Convert an 'OrientedDomino' to its unicode equivalent, where the sides of
-- the domino can /not/ be empty.
domino'
  :: OrientedDomino DieValue  -- ^ The 'OrientedDomino' to render.
  -> Char  -- ^ The unicode characters that represents the 'OrientedDomino' value.
domino' :: OrientedDomino DieValue -> Char
domino' = Oriented ComplexDomino -> Char
domino (Oriented ComplexDomino -> Char)
-> (OrientedDomino DieValue -> Oriented ComplexDomino)
-> OrientedDomino DieValue
-> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SimpleDomino -> ComplexDomino)
-> OrientedDomino DieValue -> Oriented ComplexDomino
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((DieValue -> Maybe DieValue) -> SimpleDomino -> ComplexDomino
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap DieValue -> Maybe DieValue
forall a. a -> Maybe a
Just)

instance UnicodeCharacter (Oriented (Domino (Maybe DieValue))) where
    toUnicodeChar :: Oriented ComplexDomino -> Char
toUnicodeChar = Oriented ComplexDomino -> Char
domino
    fromUnicodeChar :: Char -> Maybe (Oriented ComplexDomino)
fromUnicodeChar = Char -> Maybe (Oriented ComplexDomino)
fromDomino
    fromUnicodeChar' :: Char -> Oriented ComplexDomino
fromUnicodeChar' = Char -> Oriented ComplexDomino
fromDomino'

instance UnicodeCharacter (Oriented (Domino DieValue)) where
    toUnicodeChar :: OrientedDomino DieValue -> Char
toUnicodeChar = OrientedDomino DieValue -> Char
domino'
    fromUnicodeChar :: Char -> Maybe (OrientedDomino DieValue)
fromUnicodeChar = Char -> Maybe (Oriented ComplexDomino)
fromDomino (Char -> Maybe (Oriented ComplexDomino))
-> (Oriented ComplexDomino -> Maybe (OrientedDomino DieValue))
-> Char
-> Maybe (OrientedDomino DieValue)
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ComplexDomino -> Maybe SimpleDomino)
-> Oriented ComplexDomino -> Maybe (OrientedDomino DieValue)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse ComplexDomino -> Maybe SimpleDomino
forall a. Domino (Maybe a) -> Maybe (Domino a)
toSimple

instance UnicodeText (Oriented (Domino (Maybe DieValue)))
instance UnicodeText (Oriented (Domino DieValue))