Last active
December 18, 2018 14:18
-
-
Save i-am-tom/9664f03f75ad69616c237f2e084a636c to your computer and use it in GitHub Desktop.
Sigmaltons
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE DataKinds #-} | |
{-# LANGUAGE GADTs #-} | |
{-# LANGUAGE PolyKinds #-} | |
{-# LANGUAGE TypeFamilyDependencies #-} | |
module Sigma where | |
import Data.Kind (Type) | |
type family Sing (i :: k) = (o :: Type) | o -> i | |
--- | |
data Nat = Z | S Nat | |
data SNat (n :: Nat) where | |
SZ :: SNat 'Z | |
SS :: SNat n -> SNat ('S n) | |
type instance Sing (x :: Nat) = SNat x | |
--- | |
data Vector (a :: Type) (length :: Nat) where | |
VNil :: Vector a 'Z | |
(:>) :: x -> Vector x n -> Vector x ('S n) | |
infixr 4 :> | |
data Sigma (f :: k -> Type) where | |
Sigma :: Sing x -> f x -> Sigma f | |
test :: [Sigma (Vector Int)] | |
test | |
= [ Sigma SZ VNil | |
, Sigma ( SS SZ ) ( 2 :> VNil) | |
, Sigma (SS (SS SZ)) (1 :> 2 :> VNil) | |
] |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment