aboutsummaryrefslogtreecommitdiff
path: root/src/Data/Nat.hs
blob: b154f673862c442b814f06dff9eb3bf7b6cbe9f2 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -fplugin GHC.TypeLits.KnownNat.Solver #-}
module Data.Nat where

import Data.Proxy
import Numeric.Natural
import qualified GHC.TypeLits as G


-- | Evidence for the constraint @c a@.
data Dict c a where
  Dict :: c a => Dict c a

-- | A peano natural number. Intended to be used at the type level.
data Nat = Z | S Nat
  deriving (Show)

-- | Singleton for a 'Nat'.
data SNat n where
  SZ :: SNat Z
  SS :: SNat n -> SNat (S n)
deriving instance Show (SNat n)

-- | A singleton 'SNat' corresponding to @n@.
class KnownNat n where knownNat :: SNat n
instance KnownNat Z where knownNat = SZ
instance KnownNat n => KnownNat (S n) where knownNat = SS knownNat

-- | Convert a 'Nat' to a normal number.
unNat :: Nat -> Natural
unNat Z = 0
unNat (S n) = 1 + unNat n

-- | Convert an 'SNat' to a normal number.
unSNat :: SNat n -> Natural
unSNat SZ = 0
unSNat (SS n) = 1 + unSNat n

-- | Convert an 'SNat' to an integer.
unSNat' :: SNat n -> Int
unSNat' = fromIntegral . unSNat

-- | A 'KnownNat' dictionary is just a singleton natural, so we can create
-- evidence of 'KnownNat' given an 'SNat'.
snatKnown :: SNat n -> Dict KnownNat n
snatKnown SZ = Dict
snatKnown (SS n) | Dict <- snatKnown n = Dict

-- | Add two 'Nat's
type family n + m where
  Z + m = m
  S n + m = S (n + m)

-- | Convert a 'Nat' to a "GHC.TypeLits" 'G.Nat'.
type family GNat n where
  GNat Z = 0
  GNat (S n) = 1 G.+ GNat n

-- | If an inductive 'Nat' is known, then the corresponding "GHC.TypeLits"
-- 'G.Nat' is also known.
gknownNat :: KnownNat n => Proxy n -> Dict G.KnownNat (GNat n)
gknownNat (Proxy @n) = go (knownNat @n)
  where
    go :: SNat m -> Dict G.KnownNat (GNat m)
    go SZ = Dict
    go (SS n) | Dict <- go n = Dict

-- * Some type-level naturals

type N0 = Z
type N1 = S N0
type N2 = S N1
type N3 = S N2
type N4 = S N3
type N5 = S N4
type N6 = S N5
type N7 = S N6
type N8 = S N7
type N9 = S N8