d10-0.1.0.1: Digits 0-9

Safe HaskellNone
LanguageHaskell2010

Data.D10.Safe

Contents

Description

Defines a D10 type as D0 | D1 | D2 | D3 | D4 | D5 | D6 | D7 | D8 | D9.

This module is called "safe" because, in contrast with the alternative representations of a digit defined in Data.D10.Char and Data.D10.Num, this D10 type does not include any possibility of representing an invalid non-digit value.

Synopsis

Type

data D10 Source #

A whole number between 0 and 9.

Constructors

D0

Zero

D1

One

D2

Two

D3

Three

D4

Four

D5

Five

D6

Six

D7

Seven

D8

Eight

D9

Nine

Instances
Bounded D10 Source # 
Instance details

Defined in Data.D10.Safe

Methods

minBound :: D10 #

maxBound :: D10 #

Enum D10 Source # 
Instance details

Defined in Data.D10.Safe

Methods

succ :: D10 -> D10 #

pred :: D10 -> D10 #

toEnum :: Int -> D10 #

fromEnum :: D10 -> Int #

enumFrom :: D10 -> [D10] #

enumFromThen :: D10 -> D10 -> [D10] #

enumFromTo :: D10 -> D10 -> [D10] #

enumFromThenTo :: D10 -> D10 -> D10 -> [D10] #

Eq D10 Source # 
Instance details

Defined in Data.D10.Safe

Methods

(==) :: D10 -> D10 -> Bool #

(/=) :: D10 -> D10 -> Bool #

Ord D10 Source # 
Instance details

Defined in Data.D10.Safe

Methods

compare :: D10 -> D10 -> Ordering #

(<) :: D10 -> D10 -> Bool #

(<=) :: D10 -> D10 -> Bool #

(>) :: D10 -> D10 -> Bool #

(>=) :: D10 -> D10 -> Bool #

max :: D10 -> D10 -> D10 #

min :: D10 -> D10 -> D10 #

Show D10 Source # 
Instance details

Defined in Data.D10.Safe

Methods

showsPrec :: Int -> D10 -> ShowS #

show :: D10 -> String #

showList :: [D10] -> ShowS #

Lift D10 Source # 
Instance details

Defined in Data.D10.Safe

Methods

lift :: D10 -> Q Exp #

Bounded

>>> minBound :: D10
D0
>>> maxBound :: D10
D9

Enum

>>> [ D5 .. ]
[D5,D6,D7,D8,D9]
>>> [ D4 .. D7 ]
[D4,D5,D6,D7]
>>> [ D5, D4 .. ]
[D5,D4,D3,D2,D1,D0]
>>> [ D1, D3 .. ]
[D1,D3,D5,D7,D9]
>>> [ minBound .. maxBound ] :: [D10]
[D0,D1,D2,D3,D4,D5,D6,D7,D8,D9]

Quasi-quoters

d10 :: QuasiQuoter Source #

A single base-10 digit.

This quasi-quoter, when used as an expression, produces a value of type D10.

>>> [d10|5|]
D5
>>> [d10|a|]
...
... d10 must be between 0 and 9
...
>>> [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].

>>> [d10list||]
[]
>>> [d10list|5|]
[D5]
>>> [d10list|58|]
[D5,D8]
>>> [d10list|a|]
...
... d10 must be between 0 and 9
...

Converting between D10 and Char

d10Char :: D10 -> Char Source #

Convert a D10 to its underlying Char representation.

>>> d10Char D7
'7'

charD10Maybe :: Char -> Maybe D10 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 D5
>>> charD10Maybe 'a'
Nothing

charD10Either :: Char -> Either String D10 Source #

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 D5
>>> charD10Either 'a'
Left "d10 must be between 0 and 9"

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
D5
>>> charD10Fail 'a' :: IO D10
*** Exception: user error (d10 must be between 0 and 9)

Converting between D10 and String

d10Str :: D10 -> String Source #

Convert a D10 to a String.

d10Str x = [d10Char x]
>>> d10Str D7
"7"

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.

isD10Str x = isJust (strD10Maybe x)

strD10Fail is a more general version of this function.

>>> strD10Maybe "5"
Just D5
>>> 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 D5
>>> 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
D5
>>> 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)

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.

isD10Str x = isJust (strD10ListMaybe x)

strD10ListFail is a more general version of this function.

>>> strD10ListMaybe "5"
Just [D5]
>>> strD10ListMaybe "a"
Nothing
>>> strD10ListMaybe "58"
Just [D5,D8]

strD10ListEither :: String -> Either String [D10] Source #

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 [D5]
>>> strD10ListEither "a"
Left "d10 must be between 0 and 9"
>>> strD10ListEither "58"
Right [D5,D8]

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]
[D5]
>>> strD10ListFail "a" :: IO [D10]
*** Exception: user error (d10 must be between 0 and 9)
>>> strD10ListFail "58" :: IO [D10]
[D5,D8]

Converting between D10 and Natural

d10Nat :: D10 -> Natural Source #

Convert a D10 to a Natural.

d10Num is a more general version of this function.

>>> d10Nat D7
7

natD10Maybe :: Natural -> Maybe D10 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 D5
>>> natD10Maybe 12
Nothing

natD10Either :: Natural -> Either String D10 Source #

Convert a Natural to a D10 if it is less than 10, or Left with an error message otherwise.

>>> natD10Either 5
Right D5
>>> natD10Either 12
Left "d10 must be less than 10"

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
D5
>>> 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
D6

Converting between D10 and Integer

d10Integer :: D10 -> Integer Source #

Convert a D10 to an Integer.

d10Num is a more general version of this function.

>>> d10Integer D7
7

integerD10Maybe :: Integer -> Maybe D10 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 D5
>>> integerD10Maybe 12
Nothing
>>> integerD10Maybe (-5)
Nothing

integerD10Either :: Integer -> Either String D10 Source #

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 D5
>>> integerD10Either 12
Left "d10 must be between 0 and 9"
>>> integerD10Either (-5)
Left "d10 must be between 0 and 9"

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
D5
>>> 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
D6
>>> integerMod10 (-56)
D4

Converting between D10 and Int

d10Int :: D10 -> Int Source #

Convert a D10 to an Int.

d10Num is a more general version of this function.

>>> d10Int D7
7

intD10Maybe :: Int -> Maybe D10 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 D5
>>> intD10Maybe 12
Nothing
>>> intD10Maybe (-5)
Nothing

intD10Either :: Int -> Either String D10 Source #

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 D5
>>> intD10Either 12
Left "d10 must be between 0 and 9"
>>> intD10Either (-5)
Left "d10 must be between 0 and 9"

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
D5
>>> 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
D6
>>> intMod10 (-56)
D4

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 D7 :: Integer
7

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.

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 D5
>>> 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 D5
>>> 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
D5
>>> 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)
D6
>>> integralMod10 ((-56) :: Integer)
D4