| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Data.D10.Char
Contents
Description
Synopsis
- newtype D10 = D10_Unsafe Char
- d10 :: QuasiQuoter
- d10list :: QuasiQuoter
- d10Exp :: Integral a => a -> Q Exp
- d10ListExp :: String -> Q Exp
- d10Char :: D10 -> Char
- charD10Maybe :: Char -> Maybe D10
- charD10Either :: Char -> Either String D10
- charD10Fail :: MonadFail m => Char -> m D10
- d10Str :: D10 -> String
- strD10Maybe :: String -> Maybe D10
- strD10Either :: String -> Either String D10
- strD10Fail :: MonadFail m => String -> m D10
- isD10Str :: String -> Bool
- strD10ListMaybe :: String -> Maybe [D10]
- strD10ListEither :: String -> Either String [D10]
- strD10ListFail :: MonadFail m => String -> m [D10]
- d10Nat :: D10 -> Natural
- natD10Maybe :: Natural -> Maybe D10
- natD10Either :: Natural -> Either String D10
- natD10Fail :: MonadFail m => Natural -> m D10
- natMod10 :: Natural -> D10
- d10Integer :: D10 -> Integer
- integerD10Maybe :: Integer -> Maybe D10
- integerD10Either :: Integer -> Either String D10
- integerD10Fail :: MonadFail m => Integer -> m D10
- integerMod10 :: Integer -> D10
- d10Int :: D10 -> Int
- intD10Maybe :: Int -> Maybe D10
- intD10Either :: Int -> Either String D10
- intD10Fail :: MonadFail m => Int -> m D10
- intMod10 :: Int -> D10
- d10Num :: Num a => D10 -> a
- integralD10Maybe :: Integral a => a -> Maybe D10
- integralD10Either :: Integral a => a -> Either String D10
- integralD10Fail :: (Integral a, MonadFail m) => a -> m D10
- integralMod10 :: Integral a => a -> D10
Type
A Char value between '0' and '9'.
The Data.D10.Char module provides many functions for
constructing D10 values, including:
integerD10Maybe::Integer->MaybeD10integerMod10::Integer->D10
With the QuasiQuotes GHC extension enabled, you can write
D10 literals using the quasi-quoters d10 and d10list.
Constructors
| D10_Unsafe Char | The constructor's name include the word "unsafe" as a reminder
that you should generally avoid using it directly, because it
allows constructing invalid |
Bounded
>>>minBound :: D10[d10|0|]
>>>maxBound :: D10[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][d10list|0123456789|]
Quasi-quoters
d10 :: QuasiQuoter Source #
A single base-10 digit.
This quasi-quoter, when used as an expression, produces a
value of type D10.
>>>d10Nat [d10|5|]5
>>>d10Nat [d10|a|]... ... d10 must be between 0 and 9 ...
>>>d10Nat [d10|58|]... ... d10 must be a single character ...
d10list :: QuasiQuoter Source #
A list of base-10 digits.
This quasi-quoter, when used as an expression, produces a
value of type [.D10]
>>>d10Nat <$> [d10list||][]
>>>d10Nat <$> [d10list|5|][5]
>>>d10Nat <$> [d10list|58|][5,8]
>>>d10Nat <$> [d10list|a|]... ... d10 must be between 0 and 9 ...
Splice expressions
d10Exp :: Integral a => a -> Q Exp Source #
A single base-10 digit.
Produces an expression of type D10 that can be used
in a Template Haskell splice.
>>>d10Nat $(d10Exp 5)5
>>>d10Nat $(d10Exp 12)... ... d10 must be between 0 and 9 ...
d10ListExp :: String -> Q Exp Source #
A list of base-10 digits.
Produces an expression of type [ that can be used
in a Template Haskell splice.D10]
>>>d10Nat <$> $(d10ListExp "")[]
>>>d10Nat <$> $(d10ListExp "5")[5]
>>>d10Nat <$> $(d10ListExp "58")[5,8]
>>>d10Nat <$> $(d10ListExp "a")... ... d10 must be between 0 and 9 ...
Converting between D10 and Char
charD10Maybe :: Char -> Maybe D10 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 :: MonadFail m => Char -> m D10 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[d10|5|]
>>>charD10Fail 'a' :: IO D10*** Exception: user error (d10 must be between 0 and 9)
Converting between D10 and String
strD10Maybe :: String -> Maybe D10 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 :: String -> Either String D10 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 :: MonadFail m => String -> m D10 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[d10|5|]
>>>strD10Fail "a" :: IO D10*** Exception: user error (d10 must be between 0 and 9)
>>>strD10Fail "58" :: IO D10*** 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 :: String -> Maybe [D10] 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 :: MonadFail m => String -> m [D10] 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][d10list|5|]
>>>strD10ListFail "a" :: IO [D10]*** Exception: user error (d10 must be between 0 and 9)
>>>strD10ListFail "58" :: IO [D10][d10list|58|]
Converting between D10 and Natural
natD10Maybe :: Natural -> Maybe D10 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 :: MonadFail m => Natural -> m D10 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[d10|5|]
>>>natD10Fail 12 :: IO D10*** Exception: user error (d10 must be less than 10)
natMod10 :: Natural -> D10 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|6|]
Converting between D10 and Integer
d10Integer :: D10 -> Integer Source #
integerD10Maybe :: Integer -> Maybe D10 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 :: MonadFail m => Integer -> m D10 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[d10|5|]
>>>integerD10Fail 12 :: IO D10*** Exception: user error (d10 must be between 0 and 9)
>>>integerD10Fail (-5) :: IO D10*** Exception: user error (d10 must be between 0 and 9)
integerMod10 :: Integer -> D10 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|6|]
>>>integerMod10 (-56)[d10|4|]
Converting between D10 and Int
intD10Maybe :: Int -> Maybe D10 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 :: MonadFail m => Int -> m D10 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[d10|5|]
>>>intD10Fail 12 :: IO D10*** Exception: user error (d10 must be between 0 and 9)
>>>intD10Fail (-5) :: IO D10*** Exception: user error (d10 must be between 0 and 9)
intMod10 :: Int -> D10 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|6|]
>>>intMod10 (-56)[d10|4|]
Converting between D10 and general numeric types
d10Num :: Num a => D10 -> 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 :: Integral a => a -> Maybe D10 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 :: Integral a => a -> Either String D10 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 :: (Integral a, MonadFail m) => a -> m D10 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[d10|5|]
>>>integralD10Fail (12 :: Integer) :: IO D10*** Exception: user error (d10 must be between 0 and 9)
>>>integralD10Fail ((-5) :: Integer) :: IO D10*** Exception: user error (d10 must be between 0 and 9)
integralMod10 :: Integral a => a -> D10 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|6|]
>>>integralMod10 ((-56) :: Integer)[d10|4|]