{-# language Trustworthy #-}

module D10.Num.Conversions
    (
    -- * D10 / Char
      d10Char, charD10Maybe, charD10Either, charD10Fail
    -- * D10 / String
    , d10Str, strD10Maybe, strD10Either, strD10Fail
    -- * [D10] / String
    , strD10ListMaybe, strD10ListEither, strD10ListFail
    -- * D10 / Natural
    , d10Nat, natD10Maybe, natD10Either, natD10Fail
    , natMod10
    -- * D10 / Integer
    , d10Integer, integerD10Maybe, integerD10Either
    , integerD10Fail, integerMod10
    -- * D10 / Int
    , d10Int, intD10Maybe, intD10Either, intD10Fail
    , intMod10
    -- * D10 / general numeric types
    , d10Num, integralD10Maybe, integralD10Either
    , integralD10Fail, integralMod10
    ) where

import D10.Num.Unsafe (D10(..))
import D10.Predicate (isD10Char, isD10Int, isD10Integer, isD10Nat)

-- base
import Control.Monad.Fail (MonadFail (fail))
import Data.Char          (chr, ord)
import Numeric.Natural    (Natural)
import Prelude            hiding (fail)

import qualified Prelude as P

-- | Convert a 'D10' to its underlying 'Char' representation.
--
-- >>> d10Char [d10|7|]
-- '7'

d10Char :: Integral a => D10 a -> Char
d10Char :: D10 a -> Char
d10Char (D10_Unsafe a
x) = Int -> Char
chr (Char -> Int
ord Char
'0' Int -> Int -> Int
forall a. Num a => a -> a -> a
P.+ a -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
x)

-- | Convert a 'D10' to a 'String'.
--
-- @'d10Str' x = ['d10Char' x]@
--
-- >>> d10Str [d10|7|]
-- "7"

d10Str :: Integral a => D10 a -> String
d10Str :: D10 a -> String
d10Str D10 a
x = [D10 a -> Char
forall a. Integral a => D10 a -> Char
d10Char D10 a
x]

-- | Convert a 'D10' to a 'Natural'.
--
-- 'd10Num' is a more general version of this function.
--
-- >>> d10Nat [d10|7|]
-- 7

d10Nat :: Integral a => D10 a -> Natural
d10Nat :: D10 a -> Natural
d10Nat = D10 a -> Natural
forall b a. (Integral b, Num a) => D10 b -> a
d10Num

-- | Convert a 'D10' to an 'Integer'.
--
-- 'd10Num' is a more general version of this function.
--
-- >>> d10Integer [d10|7|]
-- 7

d10Integer :: Integral a => D10 a -> Integer
d10Integer :: D10 a -> Integer
d10Integer = D10 a -> Integer
forall b a. (Integral b, Num a) => D10 b -> a
d10Num

-- | Convert a 'D10' to an 'Int'.
--
-- 'd10Num' is a more general version of this function.
--
-- >>> d10Int [d10|7|]
-- 7

d10Int :: Integral a => D10 a -> Int
d10Int :: D10 a -> Int
d10Int = D10 a -> Int
forall b a. (Integral b, Num a) => D10 b -> a
d10Num

-- | Convert a 'D10' to any kind of number with a 'Num' instance.
--
-- Specialized versions of this function include 'd10Nat',
-- 'd10Integer', and 'd10Int'.
--
-- >>> d10Num [d10|7|] :: Integer
-- 7

d10Num :: (Integral b, Num a) => D10 b -> a
d10Num :: D10 b -> a
d10Num (D10_Unsafe b
x) = b -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral b
x

---------------------------------------------------

-- | The 'D10' which is uniquely congruent modulo 10 to the given 'Natural'.
--
-- 'integralMod10' is a more general version of this function.
--
-- >>> natMod10 56 :: D10 Int
-- [d10|6|]

natMod10 :: Num a => Natural -> D10 a
natMod10 :: Natural -> D10 a
natMod10 = Natural -> D10 a
forall b a. (Num b, Integral a) => a -> D10 b
integralMod10

-- | The 'D10' which is uniquely congruent modulo 10 to the given 'Integer'.
--
-- 'integralMod10' is a more general version of this function.
--
-- >>> integerMod10 56 :: D10 Int
-- [d10|6|]
--
-- >>> integerMod10 (-56) :: D10 Int
-- [d10|4|]

integerMod10 :: Num a => Integer -> D10 a
integerMod10 :: Integer -> D10 a
integerMod10 = Integer -> D10 a
forall b a. (Num b, Integral a) => a -> D10 b
integralMod10

-- | The 'D10' which is uniquely congruent modulo 10 to the given 'Int'.
--
-- 'integralMod10' is a more general version of this function.
--
-- >>> intMod10 56 :: D10 Int
-- [d10|6|]
--
-- >>> intMod10 (-56) :: D10 Int
-- [d10|4|]

intMod10 :: Num a => Int -> D10 a
intMod10 :: Int -> D10 a
intMod10 = Int -> D10 a
forall b a. (Num b, Integral a) => a -> D10 b
integralMod10

-- | The 'D10' which is uniquely congruent modulo 10 to the given number
-- (whose type must have an instance of the 'Integral' class).
--
-- Specialized versions of this function include 'natMod10',
-- 'integerMod10', and 'intMod10'.
--
-- >>> integralMod10 (56 :: Integer) :: D10 Int
-- [d10|6|]
--
-- >>> integralMod10 ((-56) :: Integer) :: D10 Int
-- [d10|4|]

integralMod10 :: (Num b, Integral a) => a -> D10 b
integralMod10 :: a -> D10 b
integralMod10 a
x = b -> D10 b
forall a. a -> D10 a
D10_Unsafe (a -> b
forall a b. (Integral a, Num b) => a -> b
fromIntegral (a
x a -> a -> a
forall a. Integral a => a -> a -> a
`mod` a
10))

---------------------------------------------------

-- | Convert a 'Char' to a 'D10' if it is within the range
-- @'0'@ to @'9'@, or produce 'Nothing' otherwise.
--
-- @'D10.Predicate.isD10Char' x = 'Data.Maybe.isJust' ('charD10Maybe' x)@
--
-- 'charD10Fail' is a more general version of this function.
--
-- >>> charD10Maybe '5'
-- Just [d10|5|]
--
-- >>> charD10Maybe 'a'
-- Nothing

charD10Maybe :: Num a => Char -> Maybe (D10 a)
charD10Maybe :: Char -> Maybe (D10 a)
charD10Maybe Char
x
        | Char -> Bool
isD10Char Char
x  =  D10 a -> Maybe (D10 a)
forall a. a -> Maybe a
Just (a -> D10 a
forall a. a -> D10 a
D10_Unsafe (Int -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Char -> Int
ord Char
x Int -> Int -> Int
forall a. Num a => a -> a -> a
P.- Char -> Int
ord Char
'0')))
        | Bool
otherwise    =  Maybe (D10 a)
forall a. Maybe a
Nothing

-- | Convert a 'String' to a 'D10' if it consists of exactly one
-- character and that character is within the range @'0'@ to @'9'@,
-- or produce 'Nothing' otherwise.
--
-- @'D10.Predicate.isD10Str' x = 'Data.Maybe.isJust' ('strD10Maybe' x)@
--
-- 'strD10Fail' is a more general version of this function.
--
-- >>> strD10Maybe "5"
-- Just [d10|5|]
--
-- >>> strD10Maybe "a"
-- Nothing
--
-- >>> strD10Maybe "58"
-- Nothing

strD10Maybe :: Num a => String -> Maybe (D10 a)
strD10Maybe :: String -> Maybe (D10 a)
strD10Maybe [Char
x] = Char -> Maybe (D10 a)
forall a. Num a => Char -> Maybe (D10 a)
charD10Maybe Char
x
strD10Maybe String
_   = Maybe (D10 a)
forall a. Maybe a
Nothing

-- | Convert a 'String' to a list of 'D10' if all of the characters
-- in the string are within the range @'0'@ to @'9'@, or produce
-- 'Nothing' otherwise.
--
-- @'D10.Predicate.isD10ListStr' x = 'Data.Maybe.isJust' ('strD10ListMaybe' x)@
--
-- 'strD10ListFail' is a more general version of this function.
--
-- >>> strD10ListMaybe "5"
-- Just [d10list|5|]
--
-- >>> strD10ListMaybe "a"
-- Nothing
--
-- >>> strD10ListMaybe "58"
-- Just [d10list|58|]

strD10ListMaybe :: Num a => String -> Maybe [D10 a]
strD10ListMaybe :: String -> Maybe [D10 a]
strD10ListMaybe = (Char -> Maybe (D10 a)) -> String -> Maybe [D10 a]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Char -> Maybe (D10 a)
forall a. Num a => Char -> Maybe (D10 a)
charD10Maybe

-- | Convert a 'Natural' to a 'D10' if it is less than 10,
-- or produce 'Nothing' otherwise.
--
-- @'D10.Predicate.isD10Nat' x = 'Data.Maybe.isJust' ('natD10Maybe' x)@
--
-- 'integralD10Maybe', 'natD10Fail', and 'integralD10Fail'
-- are more general versions of this function.
--
-- >>> natD10Maybe 5
-- Just [d10|5|]
--
-- >>> natD10Maybe 12
-- Nothing

natD10Maybe :: Num a => Natural -> Maybe (D10 a)
natD10Maybe :: Natural -> Maybe (D10 a)
natD10Maybe Natural
x
        | Natural -> Bool
isD10Nat Natural
x  =  D10 a -> Maybe (D10 a)
forall a. a -> Maybe a
Just (a -> D10 a
forall a. a -> D10 a
D10_Unsafe (Natural -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral Natural
x))
        | Bool
otherwise   =  Maybe (D10 a)
forall a. Maybe a
Nothing

-- | Convert an 'Integer' to a 'D10' if it is within the range 0 to 9,
-- or produce 'Nothing' otherwise.
--
-- @'D10.Predicate.isD10Integer' x = 'Data.Maybe.isJust' ('integerD10Maybe' x)@
--
-- 'integralD10Maybe', 'integerD10Fail', and 'integralD10Fail'
-- are more general versions of this function.
--
-- >>> integerD10Maybe 5
-- Just [d10|5|]
--
-- >>> integerD10Maybe 12
-- Nothing
--
-- >>> integerD10Maybe (-5)
-- Nothing

integerD10Maybe :: Num a => Integer -> Maybe (D10 a)
integerD10Maybe :: Integer -> Maybe (D10 a)
integerD10Maybe Integer
x
        | Integer -> Bool
isD10Integer Integer
x  =  D10 a -> Maybe (D10 a)
forall a. a -> Maybe a
Just (a -> D10 a
forall a. a -> D10 a
D10_Unsafe (Integer -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
x))
        | Bool
otherwise       =  Maybe (D10 a)
forall a. Maybe a
Nothing

-- | Convert an 'Int' to a 'D10' if it is within the range 0 to 9,
-- or produce 'Nothing' otherwise.
--
-- @'D10.Predicate.isD10Int' x = 'Data.Maybe.isJust' ('intD10Maybe' x)@
--
-- 'integralD10Maybe', 'intD10Fail', and 'integralD10Fail'
-- are more general versions of this function.
--
-- >>> intD10Maybe 5
-- Just [d10|5|]
--
-- >>> intD10Maybe 12
-- Nothing
--
-- >>> intD10Maybe (-5)
-- Nothing

intD10Maybe :: Num a => Int -> Maybe (D10 a)
intD10Maybe :: Int -> Maybe (D10 a)
intD10Maybe Int
x
        | Int -> Bool
isD10Int Int
x  =  D10 a -> Maybe (D10 a)
forall a. a -> Maybe a
Just (a -> D10 a
forall a. a -> D10 a
D10_Unsafe (Int -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
x))
        | Bool
otherwise   =  Maybe (D10 a)
forall a. Maybe a
Nothing

-- | Construct a 'D10' from any kind of number with an 'Integral'
-- instance, or produce 'Nothing' if the number falls outside the
-- range 0 to 9.
--
-- @'D10.Predicate.isD10Integral' x = 'Data.Maybe.isJust' ('integralD10Maybe' x)@
--
-- Specialized versions of this function include 'natD10Maybe',
-- 'integerD10Maybe', and 'intD10Maybe'.
--
-- 'integralD10Fail' is a more general version of this function.
--
-- >>> integralD10Maybe (5 :: Integer)
-- Just [d10|5|]
--
-- >>> integralD10Maybe (12 :: Integer)
-- Nothing
--
-- >>> integralD10Maybe ((-5) :: Integer)
-- Nothing

integralD10Maybe :: (Num b, Integral a) => a -> Maybe (D10 b)
integralD10Maybe :: a -> Maybe (D10 b)
integralD10Maybe a
x = Integer -> Maybe (D10 b)
forall a. Num a => Integer -> Maybe (D10 a)
integerD10Maybe (a -> Integer
forall a. Integral a => a -> Integer
toInteger a
x)

---------------------------------------------------

-- | Convert a 'Char' to a 'D10' if it is within the range
-- @'0'@ to @'9'@, or 'Left' with an error message otherwise.
--
-- >>> charD10Either '5'
-- Right [d10|5|]
--
-- >>> charD10Either 'a'
-- Left "d10 must be between 0 and 9"

charD10Either :: Num a => Char -> Either String (D10 a)
charD10Either :: Char -> Either String (D10 a)
charD10Either Char
x
        | Char -> Bool
isD10Char Char
x  =  D10 a -> Either String (D10 a)
forall a b. b -> Either a b
Right (a -> D10 a
forall a. a -> D10 a
D10_Unsafe (Int -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Char -> Int
ord Char
x Int -> Int -> Int
forall a. Num a => a -> a -> a
P.- Char -> Int
ord Char
'0')))
        | Bool
otherwise    =  String -> Either String (D10 a)
forall a b. a -> Either a b
Left String
"d10 must be between 0 and 9"

-- | Convert a 'String' to a 'D10' if it consists of a single
-- character and that character is within the range @'0'@ to
-- @'9'@, or 'Left' with an error message otherwise.
--
-- >>> strD10Either "5"
-- Right [d10|5|]
--
-- >>> strD10Either "a"
-- Left "d10 must be between 0 and 9"
--
-- >>> strD10Either "58"
-- Left "d10 must be a single character"

strD10Either :: Num a => String -> Either String (D10 a)
strD10Either :: String -> Either String (D10 a)
strD10Either [Char
x]         =  Char -> Either String (D10 a)
forall a. Num a => Char -> Either String (D10 a)
charD10Either Char
x
strD10Either String
_           =  String -> Either String (D10 a)
forall a b. a -> Either a b
Left String
"d10 must be a single character"

-- | Convert a 'String' to a 'D10' if all of the characters in
-- the string fall within the range @'0'@ to @'9'@, or 'Left'
-- with an error message otherwise.
--
-- >>> strD10ListEither "5"
-- Right [d10list|5|]
--
-- >>> strD10ListEither "a"
-- Left "d10 must be between 0 and 9"
--
-- >>> strD10ListEither "58"
-- Right [d10list|58|]

strD10ListEither :: Num a => String -> Either String [D10 a]
strD10ListEither :: String -> Either String [D10 a]
strD10ListEither = (Char -> Either String (D10 a)) -> String -> Either String [D10 a]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Char -> Either String (D10 a)
forall a. Num a => Char -> Either String (D10 a)
charD10Either

-- | Convert a 'Natural' to a 'D10' if it is less than 10,
-- or 'Left' with an error message otherwise.
--
-- >>> natD10Either 5
-- Right [d10|5|]
--
-- >>> natD10Either 12
-- Left "d10 must be less than 10"

natD10Either :: Num a => Natural -> Either String (D10 a)
natD10Either :: Natural -> Either String (D10 a)
natD10Either Natural
x =
    case (Natural -> Maybe (D10 a)
forall a. Num a => Natural -> Maybe (D10 a)
natD10Maybe Natural
x) of
        Just D10 a
y  -> D10 a -> Either String (D10 a)
forall a b. b -> Either a b
Right D10 a
y
        Maybe (D10 a)
Nothing -> String -> Either String (D10 a)
forall a b. a -> Either a b
Left String
"d10 must be less than 10"

-- | Convert an 'Integer' to a 'D10' if it is within the
-- range 0 to 9, or 'Left' with an error message otherwise.
--
-- >>> integerD10Either 5
-- Right [d10|5|]
--
-- >>> integerD10Either 12
-- Left "d10 must be between 0 and 9"
--
-- >>> integerD10Either (-5)
-- Left "d10 must be between 0 and 9"

integerD10Either :: Num a => Integer -> Either String (D10 a)
integerD10Either :: Integer -> Either String (D10 a)
integerD10Either Integer
x =
    case (Integer -> Maybe (D10 a)
forall a. Num a => Integer -> Maybe (D10 a)
integerD10Maybe Integer
x) of
        Just D10 a
y  -> D10 a -> Either String (D10 a)
forall a b. b -> Either a b
Right D10 a
y
        Maybe (D10 a)
Nothing -> String -> Either String (D10 a)
forall a b. a -> Either a b
Left String
"d10 must be between 0 and 9"

-- | Convert an 'Int' to a 'D10' if it is within the range
-- 0 to 9, or 'Left' with an error message otherwise.
--
-- >>> intD10Either 5
-- Right [d10|5|]
--
-- >>> intD10Either 12
-- Left "d10 must be between 0 and 9"
--
-- >>> intD10Either (-5)
-- Left "d10 must be between 0 and 9"

intD10Either :: Num a => Int -> Either String (D10 a)
intD10Either :: Int -> Either String (D10 a)
intD10Either Int
x =
    case (Int -> Maybe (D10 a)
forall a. Num a => Int -> Maybe (D10 a)
intD10Maybe Int
x) of
        Just D10 a
y  ->  D10 a -> Either String (D10 a)
forall a b. b -> Either a b
Right D10 a
y
        Maybe (D10 a)
Nothing ->  String -> Either String (D10 a)
forall a b. a -> Either a b
Left String
"d10 must be between 0 and 9"

-- | Convert a number of a type that has an 'Integral' instance
-- to a 'D10' if it falls within the range 0 to 9, or 'Left'
-- with an error message otherwise.
--
-- >>> integralD10Either (5 :: Integer)
-- Right [d10|5|]
--
-- >>> integralD10Either (12 :: Integer)
-- Left "d10 must be between 0 and 9"
--
-- >>> integralD10Either ((-5) :: Integer)
-- Left "d10 must be between 0 and 9"

integralD10Either :: (Num b, Integral a) => a -> Either String (D10 b)
integralD10Either :: a -> Either String (D10 b)
integralD10Either a
x = Integer -> Either String (D10 b)
forall a. Num a => Integer -> Either String (D10 a)
integerD10Either (a -> Integer
forall a. Integral a => a -> Integer
toInteger a
x)

---------------------------------------------------

-- | Convert a 'Char' to a 'D10' if it is within the range
-- @'0'@ to @'9'@, or 'fail' with an error message otherwise.
--
-- 'charD10Maybe' is a specialized version of this function.
--
-- >>> charD10Fail '5' :: IO (D10 Int)
-- [d10|5|]
--
-- >>> charD10Fail 'a' :: IO (D10 Int)
-- *** Exception: user error (d10 must be between 0 and 9)

charD10Fail :: (Num a, MonadFail m) => Char -> m (D10 a)
charD10Fail :: Char -> m (D10 a)
charD10Fail Char
x
        | Char -> Bool
isD10Char Char
x  =  D10 a -> m (D10 a)
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> D10 a
forall a. a -> D10 a
D10_Unsafe (Int -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Char -> Int
ord Char
x Int -> Int -> Int
forall a. Num a => a -> a -> a
P.- Char -> Int
ord Char
'0')))
        | Bool
otherwise    =  String -> m (D10 a)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"d10 must be between 0 and 9"

-- | Convert a 'String' to a 'D10' if it consists of a single
-- character and that character is within the range @'0'@ to
-- @'9'@, or 'fail' with an error message otherwise.
--
-- 'strD10Maybe' is a specialized version of this function.
--
-- >>> strD10Fail "5" :: IO (D10 Int)
-- [d10|5|]
--
-- >>> strD10Fail "a" :: IO (D10 Int)
-- *** Exception: user error (d10 must be between 0 and 9)
--
-- >>> strD10Fail "58" :: IO (D10 Int)
-- *** Exception: user error (d10 must be a single character)

strD10Fail :: (Num a, MonadFail m) => String -> m (D10 a)
strD10Fail :: String -> m (D10 a)
strD10Fail [Char
x]         =  Char -> m (D10 a)
forall a (m :: * -> *). (Num a, MonadFail m) => Char -> m (D10 a)
charD10Fail Char
x
strD10Fail String
_           =  String -> m (D10 a)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"d10 must be a single character"

-- | Convert a 'String' to a 'D10' if all of the characters in
-- the string fall within the range @'0'@ to @'9'@, or 'fail'
-- with an error message otherwise.
--
-- 'strD10ListMaybe' is a specialized version of this function.
--
-- >>> strD10ListFail "5" :: IO [D10 Int]
-- [d10list|5|]
--
-- >>> strD10ListFail "a" :: IO [D10 Int]
-- *** Exception: user error (d10 must be between 0 and 9)
--
-- >>> strD10ListFail "58" :: IO [D10 Int]
-- [d10list|58|]

strD10ListFail :: (Num a, MonadFail m) => String -> m [D10 a]
strD10ListFail :: String -> m [D10 a]
strD10ListFail = (Char -> m (D10 a)) -> String -> m [D10 a]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Char -> m (D10 a)
forall a (m :: * -> *). (Num a, MonadFail m) => Char -> m (D10 a)
charD10Fail

-- | Convert a 'Natural' to a 'D10' if it is less than 10,
-- or 'fail' with an error message otherwise.
--
-- 'natD10Maybe' is a specialized version of this function.
--
-- 'integralD10Fail' is a more general version of this function.
--
-- >>> natD10Fail 5 :: IO (D10 Int)
-- [d10|5|]
--
-- >>> natD10Fail 12 :: IO (D10 Int)
-- *** Exception: user error (d10 must be less than 10)

natD10Fail :: (Num a, MonadFail m) => Natural -> m (D10 a)
natD10Fail :: Natural -> m (D10 a)
natD10Fail Natural
x =
    case (Natural -> Maybe (D10 a)
forall a. Num a => Natural -> Maybe (D10 a)
natD10Maybe Natural
x) of
        Just D10 a
y  -> D10 a -> m (D10 a)
forall (m :: * -> *) a. Monad m => a -> m a
return D10 a
y
        Maybe (D10 a)
Nothing -> String -> m (D10 a)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"d10 must be less than 10"

-- | Convert an 'Integer' to a 'D10' if it is within the
-- range 0 to 9, or 'fail' with an error message otherwise.
--
-- 'integerD10Maybe' is a specialized version of this function.
--
-- 'integralD10Fail' is a more general version of this function.
--
-- >>> integerD10Fail 5 :: IO (D10 Int)
-- [d10|5|]
--
-- >>> integerD10Fail 12 :: IO (D10 Int)
-- *** Exception: user error (d10 must be between 0 and 9)
--
-- >>> integerD10Fail (-5) :: IO (D10 Int)
-- *** Exception: user error (d10 must be between 0 and 9)

integerD10Fail :: (Num a, MonadFail m) => Integer -> m (D10 a)
integerD10Fail :: Integer -> m (D10 a)
integerD10Fail Integer
x =
    case (Integer -> Maybe (D10 a)
forall a. Num a => Integer -> Maybe (D10 a)
integerD10Maybe Integer
x) of
        Just D10 a
y  -> D10 a -> m (D10 a)
forall (m :: * -> *) a. Monad m => a -> m a
return D10 a
y
        Maybe (D10 a)
Nothing -> String -> m (D10 a)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"d10 must be between 0 and 9"

-- | Convert an 'Int' to a 'D10' if it is within the range
-- 0 to 9, or 'fail' with an error message otherwise.
--
-- 'intD10Maybe' is a specialized version of this function.
--
-- 'integralD10Fail' is a more general version of this function.
--
-- >>> intD10Fail 5 :: IO (D10 Int)
-- [d10|5|]
--
-- >>> intD10Fail 12 :: IO (D10 Int)
-- *** Exception: user error (d10 must be between 0 and 9)
--
-- >>> intD10Fail (-5) :: IO (D10 Int)
-- *** Exception: user error (d10 must be between 0 and 9)

intD10Fail :: (Num a, MonadFail m) => Int -> m (D10 a)
intD10Fail :: Int -> m (D10 a)
intD10Fail Int
x =
    case (Int -> Maybe (D10 a)
forall a. Num a => Int -> Maybe (D10 a)
intD10Maybe Int
x) of
        Just D10 a
y  ->  D10 a -> m (D10 a)
forall (m :: * -> *) a. Monad m => a -> m a
return D10 a
y
        Maybe (D10 a)
Nothing ->  String -> m (D10 a)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"d10 must be between 0 and 9"

-- | Convert a number of a type that has an 'Integral' instance
-- to a 'D10' if it falls within the range 0 to 9, or 'fail'
-- with an error message otherwise.
--
-- 'natD10Maybe', 'integerD10Maybe', 'intD10Maybe',
-- 'integralD10Maybe', 'natD10Fail', 'integerD10Fail', and
-- 'intD10Fail' are all specialized versions of this function.
--
-- >>> integralD10Fail (5 :: Integer) :: IO (D10 Int)
-- [d10|5|]
--
-- >>> integralD10Fail (12 :: Integer) :: IO (D10 Int)
-- *** Exception: user error (d10 must be between 0 and 9)
--
-- >>> integralD10Fail ((-5) :: Integer) :: IO (D10 Int)
-- *** Exception: user error (d10 must be between 0 and 9)

integralD10Fail :: (Num b, Integral a, MonadFail m) => a -> m (D10 b)
integralD10Fail :: a -> m (D10 b)
integralD10Fail a
x = Integer -> m (D10 b)
forall a (m :: * -> *).
(Num a, MonadFail m) =>
Integer -> m (D10 a)
integerD10Fail (a -> Integer
forall a. Integral a => a -> Integer
toInteger a
x)