| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Data.D10.Num
Contents
Description
Defines a D10 type as a newtype for any type with an
 instance of the Num class, where the values are restricted
 to numbers between fromInteger 0fromInteger 9
Synopsis
- newtype D10 a = D10_Unsafe a
- d10 :: forall a. (Lift a, Num a) => QuasiQuoter
- d10list :: forall a. (Lift a, Num a) => QuasiQuoter
- d10Char :: Integral a => D10 a -> Char
- charD10Maybe :: Num a => Char -> Maybe (D10 a)
- charD10Either :: Num a => Char -> Either String (D10 a)
- charD10Fail :: (Num a, MonadFail m) => Char -> m (D10 a)
- d10Str :: Integral a => D10 a -> String
- strD10Maybe :: Num a => String -> Maybe (D10 a)
- strD10Either :: Num a => String -> Either String (D10 a)
- strD10Fail :: (Num a, MonadFail m) => String -> m (D10 a)
- isD10Str :: String -> Bool
- strD10ListMaybe :: Num a => String -> Maybe [D10 a]
- strD10ListEither :: Num a => String -> Either String [D10 a]
- strD10ListFail :: (Num a, MonadFail m) => String -> m [D10 a]
- d10Nat :: Integral a => D10 a -> Natural
- natD10Maybe :: Num a => Natural -> Maybe (D10 a)
- natD10Either :: Num a => Natural -> Either String (D10 a)
- natD10Fail :: (Num a, MonadFail m) => Natural -> m (D10 a)
- natMod10 :: Num a => Natural -> D10 a
- d10Integer :: Integral a => D10 a -> Integer
- integerD10Maybe :: Num a => Integer -> Maybe (D10 a)
- integerD10Either :: Num a => Integer -> Either String (D10 a)
- integerD10Fail :: (Num a, MonadFail m) => Integer -> m (D10 a)
- integerMod10 :: Num a => Integer -> D10 a
- d10Int :: Integral a => D10 a -> Int
- intD10Maybe :: Num a => Int -> Maybe (D10 a)
- intD10Either :: Num a => Int -> Either String (D10 a)
- intD10Fail :: (Num a, MonadFail m) => Int -> m (D10 a)
- intMod10 :: Num a => Int -> D10 a
- d10Num :: (Integral b, Num a) => D10 b -> a
- integralD10Maybe :: (Num b, Integral a) => a -> Maybe (D10 b)
- integralD10Either :: (Num b, Integral a) => a -> Either String (D10 b)
- integralD10Fail :: (Num b, Integral a, MonadFail m) => a -> m (D10 b)
- integralMod10 :: (Num b, Integral a) => a -> D10 b
Type
A value of some numeric type a between
 fromInteger 0fromInteger 9
The Data.D10.Num module provides many functions for
 constructing D10 values, including:
- integerD10Maybe::- Integer->- Maybe- D10
- integerMod10::- Integer->- D10
With the QuasiQuotes GHC extension enabled, you can write
 D10 literals using the quasi-quoters d10 and d10list.
Constructors
| D10_Unsafe a | The constructor's name include the word "unsafe" as a reminder
   that you should generally avoid using it directly, because it
   allows constructing invalid  | 
Instances
| Num a => Bounded (D10 a) Source # | |
| Integral a => Enum (D10 a) Source # | |
| Eq a => Eq (D10 a) Source # | |
| Ord a => Ord (D10 a) Source # | |
| Integral a => Show (D10 a) Source # | Shows base-10 digits using the quasiquoters defined in
 Data.D10.Char. A single digit is displayed using  | 
| Lift a => Lift (D10 a) Source # | |
Bounded
>>>minBound :: D10 Integer[d10|0|]
>>>maxBound :: D10 Integer[d10|9|]
Enum
>>>[ [d10|5|] .. ][d10list|56789|]
>>>[ [d10|4|] .. [d10|7|] ][d10list|4567|]
>>>[ [d10|5|], [d10|4|] .. ][d10list|543210|]
>>>[ [d10|1|], [d10|3|] .. ][d10list|13579|]
>>>[ minBound .. maxBound ] :: [D10 Integer][d10list|0123456789|]
Quasi-quoters
d10 :: forall a. (Lift a, Num a) => QuasiQuoter Source #
A single base-10 digit.
This quasi-quoter, when used as an expression, produces a
 value of type D10 a
>>>d10Nat [d10|5|]5
>>>d10Nat [d10|a|]... ... d10 must be between 0 and 9 ...
>>>d10Nat [d10|58|]... ... d10 must be a single character ...
d10list :: forall a. (Lift a, Num a) => QuasiQuoter Source #
A list of base-10 digits.
This quasi-quoter, when used as an expression, produces a
 value of type [.D10 a]
>>>d10Nat <$> [d10list||][]
>>>d10Nat <$> [d10list|5|][5]
>>>d10Nat <$> [d10list|58|][5,8]
>>>d10Nat <$> [d10list|a|]... ... d10 must be between 0 and 9 ...
Converting between D10 and Char
charD10Maybe :: Num a => Char -> Maybe (D10 a) Source #
Convert a Char to a D10 if it is within the range
 '0' to '9', or produce Nothing otherwise.
isD10Charx =isJust(charD10Maybex)
charD10Fail is a more general version of this function.
>>>charD10Maybe '5'Just [d10|5|]
>>>charD10Maybe 'a'Nothing
charD10Fail :: (Num a, MonadFail m) => Char -> m (D10 a) Source #
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)
Converting between D10 and String
strD10Maybe :: Num a => String -> Maybe (D10 a) Source #
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.
isD10Strx =isJust(strD10Maybex)
strD10Fail is a more general version of this function.
>>>strD10Maybe "5"Just [d10|5|]
>>>strD10Maybe "a"Nothing
>>>strD10Maybe "58"Nothing
strD10Either :: Num a => String -> Either String (D10 a) Source #
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"
strD10Fail :: (Num a, MonadFail m) => String -> m (D10 a) Source #
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)
isD10Str :: String -> Bool Source #
Determines whether a String consists of a single character
 and that character is within the range '0' to '9'.
Converting between [D10] and String
strD10ListMaybe :: Num a => String -> Maybe [D10 a] Source #
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.
isD10Strx =isJust(strD10ListMaybex)
strD10ListFail is a more general version of this function.
>>>strD10ListMaybe "5"Just [d10list|5|]
>>>strD10ListMaybe "a"Nothing
>>>strD10ListMaybe "58"Just [d10list|58|]
strD10ListFail :: (Num a, MonadFail m) => String -> m [D10 a] Source #
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|]
Converting between D10 and Natural
natD10Maybe :: Num a => Natural -> Maybe (D10 a) Source #
Convert a Natural to a D10 if it is less than 10,
 or produce Nothing otherwise.
isD10Natx =isJust(natD10Maybex)
integralD10Maybe, natD10Fail, and integralD10Fail
 are more general versions of this function.
>>>natD10Maybe 5Just [d10|5|]
>>>natD10Maybe 12Nothing
natD10Fail :: (Num a, MonadFail m) => Natural -> m (D10 a) Source #
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)
natMod10 :: Num a => Natural -> D10 a Source #
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|]
Converting between D10 and Integer
integerD10Maybe :: Num a => Integer -> Maybe (D10 a) Source #
Convert an Integer to a D10 if it is within the range 0 to 9,
 or produce Nothing otherwise.
isD10Integerx =isJust(integerD10Maybex)
integralD10Maybe, integerD10Fail, and integralD10Fail
 are more general versions of this function.
>>>integerD10Maybe 5Just [d10|5|]
>>>integerD10Maybe 12Nothing
>>>integerD10Maybe (-5)Nothing
integerD10Fail :: (Num a, MonadFail m) => Integer -> m (D10 a) Source #
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)
integerMod10 :: Num a => Integer -> D10 a Source #
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|]
Converting between D10 and Int
intD10Maybe :: Num a => Int -> Maybe (D10 a) Source #
Convert an Int to a D10 if it is within the range 0 to 9,
 or produce Nothing otherwise.
isD10Intx =isJust(intD10Maybex)
integralD10Maybe, intD10Fail, and integralD10Fail
 are more general versions of this function.
>>>intD10Maybe 5Just [d10|5|]
>>>intD10Maybe 12Nothing
>>>intD10Maybe (-5)Nothing
intD10Fail :: (Num a, MonadFail m) => Int -> m (D10 a) Source #
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)
intMod10 :: Num a => Int -> D10 a Source #
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|]
Converting between D10 and general numeric types
d10Num :: (Integral b, Num a) => D10 b -> a Source #
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|] :: Integer7
integralD10Maybe :: (Num b, Integral a) => a -> Maybe (D10 b) Source #
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.
isD10Integralx =isJust(integralD10Maybex)
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
integralD10Either :: (Num b, Integral a) => a -> Either String (D10 b) Source #
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"
integralD10Fail :: (Num b, Integral a, MonadFail m) => a -> m (D10 b) Source #
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)
integralMod10 :: (Num b, Integral a) => a -> D10 b Source #
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|]