Skip to content

Instantly share code, notes, and snippets.

@RyanGlScott
Last active November 16, 2017 21:26
Show Gist options
  • Select an option

  • Save RyanGlScott/0ffa086b0c574f81977f9b35185285ad to your computer and use it in GitHub Desktop.

Select an option

Save RyanGlScott/0ffa086b0c574f81977f9b35185285ad to your computer and use it in GitHub Desktop.
Sigma types in Haskell
{-# LANGUAGE GADTs #-}
{-# LANGUAGE PackageImports #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeInType #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -Wall #-}
{-# OPTIONS_GHC -Wno-unticked-promoted-constructors #-}
module SigmaExample where
import Data.Kind
import "singleton-nats" Data.Nat
import "singletons" Data.Singletons.Prelude
import "singletons" Data.Singletons.TH
data Sigma (s :: Type) :: (s ~> Type) -> Type where
(:&:) :: forall s t fst. Sing (fst :: s) -> t @@ fst -> Sigma s t
infixr 4 :&:
data Vec :: Type -> Nat -> Type where
VNil :: Vec a Z
(:>) :: a -> Vec a n -> Vec a (S n)
infixr 5 :>
$(singletons
[d| len :: [a] -> Nat
len [] = Z
len (_:xs) = S (len xs) |])
slistToVec :: forall (a :: Type) (z :: [a]). SingKind a
=> SList z -> Vec (Demote a) (Len z)
slistToVec SNil = VNil
slistToVec (x `SCons` xs) = fromSing x :> slistToVec xs
listToVec :: SingKind a => [Demote a] -> Sigma Nat (TyCon1 (Vec (Demote a)))
listToVec x = withSomeSing x $ \sX -> sLen sX :&: slistToVec sX
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment