-- | A data type with ten nullary constructors and combinators.
module Data.Digit
(
-- * Data type
  Digit
-- * Constructors
, d0
, d1
, d2
, d3
, d4
, d5
, d6
, d7
, d8
, d9
-- * Deconstructors
, foldDigit
, if0
, if1
, if2
, if3
, if4
, if5
, if6
, if7
, if8
, if9
, ifEven
, ifOdd
) where

-- | A data type with ten nullary constructors.
data Digit =
  D0
  | D1
  | D2
  | D3
  | D4
  | D5
  | D6
  | D7
  | D8
  | D9
  deriving (Eq, Ord, Enum, Bounded)

instance Show Digit where
  show = show . fromEnum

instance Read Digit where
  readsPrec _ ('0':t) =
    [(d0, t)]
  readsPrec _ ('1':t) =
    [(d1, t)]
  readsPrec _ ('2':t) =
    [(d2, t)]
  readsPrec _ ('3':t) =
    [(d3, t)]
  readsPrec _ ('4':t) =
    [(d4, t)]
  readsPrec _ ('5':t) =
    [(d5, t)]
  readsPrec _ ('6':t) =
    [(d6, t)]
  readsPrec _ ('7':t) =
    [(d7, t)]
  readsPrec _ ('8':t) =
    [(d8, t)]
  readsPrec _ ('9':t) =
    [(d9, t)]
  readsPrec _ _       =
    []

-- | Zero.
d0 ::
  Digit
d0 =
  D0

-- | One.
d1 ::
  Digit
d1 =
  D1

-- | Two.
d2 ::
  Digit
d2 =
  D2

-- | Three.
d3 ::
  Digit
d3 =
  D3

-- | Four.
d4 ::
  Digit
d4 =
  D4

-- | Five.
d5 ::
  Digit
d5 =
  D5

-- | Six.
d6 ::
  Digit
d6 =
  D6

-- | Seven.
d7 ::
  Digit
d7 =
  D7

-- | Eight
d8 ::
  Digit
d8 =
  D8

-- | Nine.
d9 ::
  Digit
d9 =
  D9

-- | Catamorphism for @Digit@.
foldDigit ::
  a -- ^ Zero.
  -> a -- ^ One.
  -> a -- ^ Two.
  -> a -- ^ Three.
  -> a -- ^ Four.
  -> a -- ^ Five.
  -> a -- ^ Six.
  -> a -- ^ Seven.
  -> a -- ^ Eight.
  -> a -- ^ Nine.
  -> Digit -- ^ The digit to fold.
  -> a
foldDigit d0 _  _  _  _  _  _  _  _  _  D0 =
  d0
foldDigit _  d1 _  _  _  _  _  _  _  _  D1 =
  d1
foldDigit _  _  d2 _  _  _  _  _  _  _  D2 =
  d2
foldDigit _  _  _  d3 _  _  _  _  _  _  D3 =
  d3
foldDigit _  _  _  _  d4 _  _  _  _  _  D4 =
  d4
foldDigit _  _  _  _  _  d5 _  _  _  _  D5 =
  d5
foldDigit _  _  _  _  _  _  d6 _  _  _  D6 =
  d6
foldDigit _  _  _  _  _  _  _  d7 _  _  D7 =
  d7
foldDigit _  _  _  _  _  _  _  _  d8 _  D8 =
  d8
foldDigit _  _  _  _  _  _  _  _  _  d9 D9 =
  d9

-- | Return the first argument if zero, otherwise the second argument.
if0 ::
  x
  -> x
  -> Digit
  -> x
if0 t _ D0 =
  t
if0 _ f _ =
  f

-- | Return the first argument if one, otherwise the second argument.
if1 ::
  x
  -> x
  -> Digit
  -> x
if1 t _ D1 =
  t
if1 _ f _ =
  f

-- | Return the first argument if two, otherwise the second argument.
if2 ::
  x
  -> x
  -> Digit
  -> x
if2 t _ D2 =
  t
if2 _ f _ =
  f

-- | Return the first argument if three, otherwise the second argument.
if3 ::
  x
  -> x
  -> Digit
  -> x
if3 t _ D3 =
  t
if3 _ f _ =
  f

-- | Return the first argument if four, otherwise the second argument.
if4 ::
  x
  -> x
  -> Digit
  -> x
if4 t _ D4 =
  t
if4 _ f _ =
  f

-- | Return the first argument if five, otherwise the second argument.
if5 ::
  x
  -> x
  -> Digit
  -> x
if5 t _ D5 =
  t
if5 _ f _ =
  f

-- | Return the first argument if six, otherwise the second argument.
if6 ::
  x
  -> x
  -> Digit
  -> x
if6 t _ D6 =
  t
if6 _ f _ =
  f

-- | Return the first argument if seven, otherwise the second argument.
if7::
  x
  -> x
  -> Digit
  -> x
if7 t _ D7 =
  t
if7 _ f _ =
  f

-- | Return the first argument if eight, otherwise the second argument.
if8 ::
  x
  -> x
  -> Digit
  -> x
if8 t _ D8 =
  t
if8 _ f _ =
  f

-- | Return the first argument if nine, otherwise the second argument.
if9 ::
  x
  -> x
  -> Digit
  -> x
if9 t _ D9 =
  t
if9 _ f _ =
  f

-- | Return the first argument if even, otherwise the second argument.
ifEven ::
  x
  -> x
  -> Digit
  -> x
ifEven t f =
  foldDigit t f t f t f t f t f

-- | Return the first argument if odd, otherwise the second argument.
ifOdd ::
  x
  -> x
  -> Digit
  -> x
ifOdd =
  flip ifEven