Skip to content

Instantly share code, notes, and snippets.

@Pranz
Last active August 29, 2015 13:56
Show Gist options
  • Save Pranz/9040556 to your computer and use it in GitHub Desktop.
Save Pranz/9040556 to your computer and use it in GitHub Desktop.
List indexed by constraint
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE FlexibleInstances #-}
data ConstraintList c where
Nil :: ConstraintList c
Cons :: (c a) => a -> ConstraintList c -> ConstraintList c
instance Show (ConstraintList Show) where
show Nil = "[]"
show (Cons x xs) = show x ++ " : " ++ show xs
conls :: ConstraintList Show
conls = Cons 1 $ Cons "Hello, World!" $ Cons True Nil
main = print conls
@Twey
Copy link

Twey commented Feb 16, 2014

{-# LANGUAGE UnicodeSyntax, ExistentialQuantification,
             ConstraintKinds, FlexibleInstances #-}

module Exists where

data Exists c = ∀ a. c a ⇒ Exists a

stuff ∷ [Exists Show]
stuff = [Exists 3, Exists 3.0, Exists "three"]

instance Show (Exists Show) where
    showsPrec n (Exists a) = showsPrec n a

main = mapM_ print stuff

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment