Safe Haskell | Trustworthy |
---|---|
Language | Haskell2010 |
Synopsis
- 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)
- 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
D10 / 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.
isD10Char
x =isJust
(charD10Maybe
x)
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)
D10 / 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.
isD10Str
x =isJust
(strD10Maybe
x)
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)
[D10] / 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.
isD10ListStr
x =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|]
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|]
D10 / 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.
isD10Nat
x =isJust
(natD10Maybe
x)
integralD10Maybe
, natD10Fail
, and integralD10Fail
are more general versions of this function.
>>>
natD10Maybe 5
Just [d10|5|]
>>>
natD10Maybe 12
Nothing
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|]
D10 / 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.
isD10Integer
x =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
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|]
D10 / 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.
isD10Int
x =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
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|]
D10 / 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|] :: Integer
7
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.
isD10Integral
x =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
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|]