{-# LANGUAGE DataKinds #-} {-# LANGUAGE DeriveTraversable #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE QuantifiedConstraints #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE StandaloneDeriving #-} {-# 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) 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)