{-# LANGUAGE DeriveDataTypeable, DeriveGeneric, Safe #-}

{-|
Module      : Data.Char.Dice
Description : Support for dice characters in unicode.
Maintainer  : hapytexeu+gh@gmail.com
Stability   : experimental
Portability : POSIX

Unicode has a <https://www.unicode.org/charts/PDF/U2600.pdf block> named /Miscellaneous Symbols/ that includes unicode characters for dice, this module aims to make it more convenient to render
die characters.
-}

module Data.Char.Dice(
    -- * Represent die values
    DieValue(I, II, III, IV, V, VI)
    -- * Convert to a die value
  , toDieValue
    -- * Render a die
  , die
  ) where

import Control.DeepSeq(NFData)

import Data.Bits((.|.))
import Data.Char(chr)
import Data.Char.Core(UnicodeCharacter(toUnicodeChar, fromUnicodeChar, fromUnicodeChar'), UnicodeText, mapFromEnum, mapToEnum, mapToEnumSafe)
import Data.Data(Data)
import Data.Hashable(Hashable)

import GHC.Generics(Generic)

import Test.QuickCheck.Arbitrary(Arbitrary(arbitrary), arbitraryBoundedEnum)

_dieOffset :: Int
_dieOffset :: Int
_dieOffset = Int
0x2680

-- | A data type to store the values of a die.
data DieValue
  = I  -- ^ A die with value /one/, represented with ⚀.
  | II  -- ^ A die with value /two/, represented with ⚁.
  | III  -- ^ A die with value /three/, represented with ⚂.
  | IV  -- ^ A die with value /four/, represented with ⚃.
  | V  -- ^ A die with value /five/, represented with ⚄.
  | VI  -- ^ A die with value /six/, represented with ⚅.
  deriving (DieValue
DieValue -> DieValue -> Bounded DieValue
forall a. a -> a -> Bounded a
maxBound :: DieValue
$cmaxBound :: DieValue
minBound :: DieValue
$cminBound :: DieValue
Bounded, Typeable DieValue
DataType
Constr
Typeable DieValue
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> DieValue -> c DieValue)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c DieValue)
-> (DieValue -> Constr)
-> (DieValue -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c DieValue))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DieValue))
-> ((forall b. Data b => b -> b) -> DieValue -> DieValue)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> DieValue -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> DieValue -> r)
-> (forall u. (forall d. Data d => d -> u) -> DieValue -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> DieValue -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> DieValue -> m DieValue)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> DieValue -> m DieValue)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> DieValue -> m DieValue)
-> Data DieValue
DieValue -> DataType
DieValue -> Constr
(forall b. Data b => b -> b) -> DieValue -> DieValue
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DieValue -> c DieValue
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DieValue
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> DieValue -> u
forall u. (forall d. Data d => d -> u) -> DieValue -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DieValue -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DieValue -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> DieValue -> m DieValue
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DieValue -> m DieValue
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DieValue
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DieValue -> c DieValue
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c DieValue)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DieValue)
$cVI :: Constr
$cV :: Constr
$cIV :: Constr
$cIII :: Constr
$cII :: Constr
$cI :: Constr
$tDieValue :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> DieValue -> m DieValue
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DieValue -> m DieValue
gmapMp :: (forall d. Data d => d -> m d) -> DieValue -> m DieValue
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DieValue -> m DieValue
gmapM :: (forall d. Data d => d -> m d) -> DieValue -> m DieValue
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> DieValue -> m DieValue
gmapQi :: Int -> (forall d. Data d => d -> u) -> DieValue -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> DieValue -> u
gmapQ :: (forall d. Data d => d -> u) -> DieValue -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> DieValue -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DieValue -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DieValue -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DieValue -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DieValue -> r
gmapT :: (forall b. Data b => b -> b) -> DieValue -> DieValue
$cgmapT :: (forall b. Data b => b -> b) -> DieValue -> DieValue
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DieValue)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DieValue)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c DieValue)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c DieValue)
dataTypeOf :: DieValue -> DataType
$cdataTypeOf :: DieValue -> DataType
toConstr :: DieValue -> Constr
$ctoConstr :: DieValue -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DieValue
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DieValue
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DieValue -> c DieValue
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DieValue -> c DieValue
$cp1Data :: Typeable DieValue
Data, Int -> DieValue
DieValue -> Int
DieValue -> [DieValue]
DieValue -> DieValue
DieValue -> DieValue -> [DieValue]
DieValue -> DieValue -> DieValue -> [DieValue]
(DieValue -> DieValue)
-> (DieValue -> DieValue)
-> (Int -> DieValue)
-> (DieValue -> Int)
-> (DieValue -> [DieValue])
-> (DieValue -> DieValue -> [DieValue])
-> (DieValue -> DieValue -> [DieValue])
-> (DieValue -> DieValue -> DieValue -> [DieValue])
-> Enum DieValue
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: DieValue -> DieValue -> DieValue -> [DieValue]
$cenumFromThenTo :: DieValue -> DieValue -> DieValue -> [DieValue]
enumFromTo :: DieValue -> DieValue -> [DieValue]
$cenumFromTo :: DieValue -> DieValue -> [DieValue]
enumFromThen :: DieValue -> DieValue -> [DieValue]
$cenumFromThen :: DieValue -> DieValue -> [DieValue]
enumFrom :: DieValue -> [DieValue]
$cenumFrom :: DieValue -> [DieValue]
fromEnum :: DieValue -> Int
$cfromEnum :: DieValue -> Int
toEnum :: Int -> DieValue
$ctoEnum :: Int -> DieValue
pred :: DieValue -> DieValue
$cpred :: DieValue -> DieValue
succ :: DieValue -> DieValue
$csucc :: DieValue -> DieValue
Enum, DieValue -> DieValue -> Bool
(DieValue -> DieValue -> Bool)
-> (DieValue -> DieValue -> Bool) -> Eq DieValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DieValue -> DieValue -> Bool
$c/= :: DieValue -> DieValue -> Bool
== :: DieValue -> DieValue -> Bool
$c== :: DieValue -> DieValue -> Bool
Eq, (forall x. DieValue -> Rep DieValue x)
-> (forall x. Rep DieValue x -> DieValue) -> Generic DieValue
forall x. Rep DieValue x -> DieValue
forall x. DieValue -> Rep DieValue x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DieValue x -> DieValue
$cfrom :: forall x. DieValue -> Rep DieValue x
Generic, Eq DieValue
Eq DieValue
-> (DieValue -> DieValue -> Ordering)
-> (DieValue -> DieValue -> Bool)
-> (DieValue -> DieValue -> Bool)
-> (DieValue -> DieValue -> Bool)
-> (DieValue -> DieValue -> Bool)
-> (DieValue -> DieValue -> DieValue)
-> (DieValue -> DieValue -> DieValue)
-> Ord DieValue
DieValue -> DieValue -> Bool
DieValue -> DieValue -> Ordering
DieValue -> DieValue -> DieValue
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
min :: DieValue -> DieValue -> DieValue
$cmin :: DieValue -> DieValue -> DieValue
max :: DieValue -> DieValue -> DieValue
$cmax :: DieValue -> DieValue -> DieValue
>= :: DieValue -> DieValue -> Bool
$c>= :: DieValue -> DieValue -> Bool
> :: DieValue -> DieValue -> Bool
$c> :: DieValue -> DieValue -> Bool
<= :: DieValue -> DieValue -> Bool
$c<= :: DieValue -> DieValue -> Bool
< :: DieValue -> DieValue -> Bool
$c< :: DieValue -> DieValue -> Bool
compare :: DieValue -> DieValue -> Ordering
$ccompare :: DieValue -> DieValue -> Ordering
$cp1Ord :: Eq DieValue
Ord, ReadPrec [DieValue]
ReadPrec DieValue
Int -> ReadS DieValue
ReadS [DieValue]
(Int -> ReadS DieValue)
-> ReadS [DieValue]
-> ReadPrec DieValue
-> ReadPrec [DieValue]
-> Read DieValue
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DieValue]
$creadListPrec :: ReadPrec [DieValue]
readPrec :: ReadPrec DieValue
$creadPrec :: ReadPrec DieValue
readList :: ReadS [DieValue]
$creadList :: ReadS [DieValue]
readsPrec :: Int -> ReadS DieValue
$creadsPrec :: Int -> ReadS DieValue
Read, Int -> DieValue -> ShowS
[DieValue] -> ShowS
DieValue -> String
(Int -> DieValue -> ShowS)
-> (DieValue -> String) -> ([DieValue] -> ShowS) -> Show DieValue
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DieValue] -> ShowS
$cshowList :: [DieValue] -> ShowS
show :: DieValue -> String
$cshow :: DieValue -> String
showsPrec :: Int -> DieValue -> ShowS
$cshowsPrec :: Int -> DieValue -> ShowS
Show)

instance Hashable DieValue

instance NFData DieValue

-- | Convert the given integral value to a 'DieValue' that represents the given
-- number. If the number is less than one, or greater than six, 'Nothing' is
-- returned.
toDieValue :: Integral i
  => i  -- ^ The given integral value to convert to a 'DieValue'.
  -> Maybe DieValue  -- ^ A 'DieValue' wrapped in a 'Just' if the given integral value is greater than zero, and less than seven, otherwise 'Nothing'.
toDieValue :: i -> Maybe DieValue
toDieValue i
i
    | i
i i -> i -> Bool
forall a. Ord a => a -> a -> Bool
> i
0 Bool -> Bool -> Bool
&& i
i i -> i -> Bool
forall a. Ord a => a -> a -> Bool
<= i
6 = DieValue -> Maybe DieValue
forall a. a -> Maybe a
Just (Int -> DieValue
forall a. Enum a => Int -> a
toEnum (i -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral i
iInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1))
    | Bool
otherwise = Maybe DieValue
forall a. Maybe a
Nothing

instance Arbitrary DieValue where
    arbitrary :: Gen DieValue
arbitrary = Gen DieValue
forall a. (Bounded a, Enum a) => Gen a
arbitraryBoundedEnum

-- | Convert the given 'DieValue' to a unicode character that represents a /die/
-- with that value.
die
  :: DieValue  -- ^ The die value to convert.
  -> Char  -- ^ A unicode character that represents a die with the given 'DieValue'.
die :: DieValue -> Char
die = Int -> Char
chr (Int -> Char) -> (DieValue -> Int) -> DieValue -> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int
_dieOffset Int -> Int -> Int
forall a. Bits a => a -> a -> a
.|.) (Int -> Int) -> (DieValue -> Int) -> DieValue -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DieValue -> Int
forall a. Enum a => a -> Int
fromEnum

instance UnicodeCharacter DieValue where
    toUnicodeChar :: DieValue -> Char
toUnicodeChar = Int -> DieValue -> Char
forall a. Enum a => Int -> a -> Char
mapFromEnum Int
_dieOffset
    fromUnicodeChar :: Char -> Maybe DieValue
fromUnicodeChar = Int -> Char -> Maybe DieValue
forall a. (Bounded a, Enum a) => Int -> Char -> Maybe a
mapToEnumSafe Int
_dieOffset
    fromUnicodeChar' :: Char -> DieValue
fromUnicodeChar' = Int -> Char -> DieValue
forall a. Enum a => Int -> Char -> a
mapToEnum Int
_dieOffset

instance UnicodeText DieValue