blob: eb6c0332f47701cad7d703cadaff884bf4f10b90 (
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
 | {-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE QuantifiedConstraints #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
module Data where
import Lemmas (Append)
data SList f l where
  SNil :: SList f '[]
  SCons :: f a -> SList f l -> SList f (a : l)
deriving instance (forall a. Show (f a)) => Show (SList f l)
infixr `SCons`
slistMap :: (forall t. f t -> g t) -> SList f list -> SList g list
slistMap _ SNil = SNil
slistMap f (SCons x list) = SCons (f x) (slistMap f list)
sappend :: SList f l1 -> SList f l2 -> SList f (Append l1 l2)
sappend SNil l = l
sappend (SCons x xs) l = SCons x (sappend xs l)
type family Replicate n x where
  Replicate Z x = '[]
  Replicate (S n) x = x : Replicate n x
sreplicate :: SNat n -> f t -> SList f (Replicate n t)
sreplicate SZ _ = SNil
sreplicate (SS n) x = x `SCons` sreplicate n x
data Nat = Z | S Nat
  deriving (Show, Eq, Ord)
data SNat n where
  SZ :: SNat Z
  SS :: SNat n -> SNat (S n)
deriving instance Show (SNat n)
fromSNat :: SNat n -> Int
fromSNat SZ = 0
fromSNat (SS n) = succ (fromSNat n)
class KnownNat n where knownNat :: SNat n
instance KnownNat Z where knownNat = SZ
instance KnownNat n => KnownNat (S n) where knownNat = SS knownNat
data Vec n t where
  VNil :: Vec Z t
  (:<) :: t -> Vec n t -> Vec (S n) t
deriving instance Show t => Show (Vec n t)
deriving instance Functor (Vec n)
deriving instance Foldable (Vec n)
deriving instance Traversable (Vec n)
vecLength :: Vec n t -> SNat n
vecLength VNil = SZ
vecLength (_ :< v) = SS (vecLength v)
vecGenerate :: SNat n -> (forall i. SNat i -> t) -> Vec n t
vecGenerate = \n f -> go n f SZ
  where
    go :: SNat n -> (forall i. SNat i -> t) -> SNat i' -> Vec n t
    go SZ _ _ = VNil
    go (SS n) f i = f i :< go n f (SS i)
 |