module Data.Nat (
    
    Nat(..),
    toNatural,
    fromNatural,
    cata,
    
    explicitShow,
    explicitShowsPrec,
    
    zero, one, two, three, four, five,
    ) where
import Control.DeepSeq (NFData (..))
import Data.Data       (Data)
import Data.Hashable   (Hashable (..))
import Data.Typeable   (Typeable)
import GHC.Exception   (ArithException (..), throw)
import Numeric.Natural (Natural)
data Nat = Z | S Nat deriving (Eq, Ord, Typeable, Data)
instance Show Nat where
    showsPrec d = showsPrec d . toNatural
instance Num Nat where
    fromInteger = fromNatural . fromInteger
    Z   + m = m
    S n + m = S (n + m)
    Z   * _ = Z
    S n * m = (n * m) + m
    abs = id
    signum Z     = Z
    signum (S _) = S Z
    negate _ = error "negate @Nat"
instance Real Nat where
    toRational = toRational . toInteger
instance Integral Nat where
    toInteger = cata 0 succ
    quotRem _ Z = throw DivideByZero
    quotRem _ _ = error "un-implemented"
instance Enum Nat where
    toEnum n
        | n < 0     = throw Underflow
        | otherwise = iterate S Z !! n
    fromEnum = cata 0 succ
    succ       = S
    pred Z     = throw Underflow
    pred (S n) = n
instance NFData Nat where
    rnf Z     = ()
    rnf (S n) = rnf n
instance Hashable Nat where
    hashWithSalt salt = hashWithSalt salt . toInteger
explicitShow :: Nat -> String
explicitShow n = explicitShowsPrec 0 n ""
explicitShowsPrec :: Int -> Nat -> ShowS
explicitShowsPrec _ Z     = showString "Z"
explicitShowsPrec d (S n) = showParen (d > 10)
    $ showString "S "
    . explicitShowsPrec 11 n
cata :: a -> (a -> a) -> Nat -> a
cata z f = go where
    go Z     = z
    go (S n) = f (go n)
toNatural :: Nat -> Natural
toNatural Z = 0
toNatural (S n) = succ (toNatural n)
fromNatural :: Natural -> Nat
fromNatural 0 = Z
fromNatural n = S (fromNatural (pred n))
zero, one, two, three, four, five :: Nat
zero  = Z
one   = S zero
two   = S one
three = S two
four  = S four
five  = S five