d10-1.0.1.2: Digits 0-9
Safe HaskellSafe
LanguageHaskell2010

D10.Num

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 0 and fromInteger 9.

This module provides many functions for constructing D10 values, including:

There are also several ways to safely write D10 literals using Template Haskell:

  • With the QuasiQuotes GHC extension enabled, you can write use the quasi-quoters d10 and d10list.
  • With the TemplateHaskell GHC extension enabled, you can splice expressions produced by d10Exp and d10ListExp.
Synopsis

Related modules

Additional functions related to this D10 type may be found in:

The contents of the following modules are re-exported here:

The unsafe constructor for D10 can be found in:

The following modules define D10 types in different ways but are otherwise very similar to this one:

Type

data D10 a Source #

A value of some numeric type a between fromInteger 0 and fromInteger 9.

Instances

Instances details
Num a => Bounded (D10 a) Source # 
Instance details

Defined in D10.Num.Unsafe

Methods

minBound :: D10 a #

maxBound :: D10 a #

Integral a => Enum (D10 a) Source # 
Instance details

Defined in D10.Num.Unsafe

Methods

succ :: D10 a -> D10 a #

pred :: D10 a -> D10 a #

toEnum :: Int -> D10 a #

fromEnum :: D10 a -> Int #

enumFrom :: D10 a -> [D10 a] #

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

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

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

Eq a => Eq (D10 a) Source # 
Instance details

Defined in D10.Num.Unsafe

Methods

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

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

Ord a => Ord (D10 a) Source # 
Instance details

Defined in D10.Num.Unsafe

Methods

compare :: D10 a -> D10 a -> Ordering #

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

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

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

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

max :: D10 a -> D10 a -> D10 a #

min :: D10 a -> D10 a -> D10 a #

Integral a => Show (D10 a) Source # 
Instance details

Defined in D10.Num.Unsafe

Methods

showsPrec :: Int -> D10 a -> ShowS #

show :: D10 a -> String #

showList :: [D10 a] -> ShowS #

Hashable a => Hashable (D10 a) Source # 
Instance details

Defined in D10.Num.Unsafe

Methods

hashWithSalt :: Int -> D10 a -> Int

hash :: D10 a -> Int

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|]

Show

show shows base-10 digits using the quasiquoters defined in this module. A single digit is displayed using d10. A list of digits is displayed using d10list.

Quasi-quoters

d10 :: 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
...

This quasi-quoter can also be used as a pattern.

>>> :{
      case (charD10Maybe '5') of
        Just [d10|4|] -> "A"
        Just [d10|5|] -> "B"
        _             -> "C"
>>> :}
"B"
>>> :{
      case (charD10Maybe '5') of
        Just [d10|x|] -> "A"
        Just [d10|5|] -> "B"
        _             -> "C"
>>> :}
...
... d10 must be between 0 and 9
...

d10list :: 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
...

This quasi-quoter can also be used as a pattern.

>>> :{
      case [d10list|56|] of
        [d10list|41|] -> "A"
        [d10list|56|] -> "B"
        _             -> "C"
>>> :}
"B"
>>> :{
      case [d10list|56|] of
        [d10list|4x|] -> "A"
        [d10list|56|] -> "B"
        _             -> "C"
>>> :}
...
... d10 must be between 0 and 9
...

Splices

Expressions

d10Exp :: Integer -> Q Exp Source #

Produces an expression of type D10 a that can be used in a Template Haskell splice.

>>> d10Nat $(d10Exp 5)
5
>>> d10Nat $(d10Exp 12)
...
... d10 must be between 0 and 9
...

You may also be interested in d10, a quasi-quoter which does something similar.

d10ListExp :: String -> Q Exp Source #

Produces an expression of type [D10 a] that can be used in a Template Haskell splice.

>>> d10Nat <$> $(d10ListExp "")
[]
>>> d10Nat <$> $(d10ListExp "5")
[5]
>>> d10Nat <$> $(d10ListExp "58")
[5,8]
>>> d10Nat <$> $(d10ListExp "a")
...
... d10 must be between 0 and 9
...

You may also be interested in d10list, a quasi-quoter which does something similar.

Patterns

d10Pat :: Integer -> Q Pat Source #

Produces a pattern that can be used in a splice to match a particular D10 a value.

>>> :{
      case (charD10Maybe '5') of
        Just $(d10Pat 4) -> "A"
        Just $(d10Pat 5) -> "B"
        _                -> "C"
>>> :}
"B"

You may wish to use the d10 quasi-quoter instead.

d10ListPat :: String -> Q Pat Source #

Produces a pattern that can be used in a splice to match a particular list of D10 a values.

>>> :{
      case (strD10ListMaybe "56") of
        Just $(d10ListPat "42") -> "A"
        Just $(d10ListPat "56") -> "B"
        _                       -> "C"
>>> :}
"B"

You may wish to use the d10list quasi-quoter instead.

Conversions

D10 / Char

d10Char :: Integral a => D10 a -> Char Source #

Convert a D10 to its underlying Char representation.

>>> d10Char [d10|7|]
'7'

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

charD10Either :: Num a => Char -> Either String (D10 a) 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 [d10|5|]
>>> charD10Either 'a'
Left "d10 must be between 0 and 9"

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

d10Str :: Integral a => D10 a -> String Source #

Convert a D10 to a String.

d10Str x = [d10Char x]
>>> d10Str [d10|7|]
"7"

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|]

strD10ListEither :: Num a => String -> Either String [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 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|]

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

d10Nat :: Integral a => D10 a -> Natural Source #

Convert a D10 to a Natural.

d10Num is a more general version of this function.

>>> d10Nat [d10|7|]
7

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

natD10Either :: Num a => Natural -> Either String (D10 a) Source #

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"

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

d10Integer :: Integral a => D10 a -> Integer Source #

Convert a D10 to an Integer.

d10Num is a more general version of this function.

>>> d10Integer [d10|7|]
7

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

integerD10Either :: Num a => Integer -> Either String (D10 a) 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 [d10|5|]
>>> integerD10Either 12
Left "d10 must be between 0 and 9"
>>> integerD10Either (-5)
Left "d10 must be between 0 and 9"

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

d10Int :: Integral a => D10 a -> Int Source #

Convert a D10 to an Int.

d10Num is a more general version of this function.

>>> d10Int [d10|7|]
7

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

intD10Either :: Num a => Int -> Either String (D10 a) 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 [d10|5|]
>>> intD10Either 12
Left "d10 must be between 0 and 9"
>>> intD10Either (-5)
Left "d10 must be between 0 and 9"

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|]