Type families for dummies - haskell

Could someone give a super simple (few line) example to get a basic understanding about what type families can be used for and what are they ?
The 2+2 kind of example of type families ?

Here's an example:
{-# Language TypeFamilies, DataKinds, KindSignatures, GADTs, UndecidableInstances #-}
data Nat = Z | S Nat
type family Plus (x :: Nat) (y :: Nat) :: Nat where
Plus 'Z y = y
Plus ('S x) y = 'S (Plus x y)
data Vec :: Nat -> * -> * where
Nil :: Vec 'Z a
Cons :: a -> Vec n a -> Vec ('S n) a
append :: Vec m a -> Vec n a -> Vec (Plus m n) a
append Nil ys = ys
append (Cons x xs) ys = Cons x (append xs ys)
Note that many/most interesting applications of type families require UndecidableInstances. You should not be scared of this extension.
Another useful sort of type family is one associated with a class. For a really contrived example,
class Box b where
type Elem b :: *
elem :: b -> Elem b
An instance of Box is a type that something can be pulled out of. For instance,
instance Box (Identity x) where
type Elem (Identity x) = x
elem = runIdentity
instance Box Char where
type Elem Char = String
elem c = [c]
Now elem (Identity 3) = 3 and elem 'x' = "x".
You can also use type families to make weird skolem variables. This is best done in the as-yet-unreleased GHC 8.0.1, where it will look like
type family Any :: k where {}
Any is a peculiar type. It's uninhabited, it can't be (specifically) an instance of a class, and it's poly-kinded. This turns out to be really useful for certain purposes. This particular type is advertised as a safe target for unsafeCoerce, but Data.Constraint.Forall uses similar type families for more interesting purposes.

Related

Coq: Strong specification of haskell's Replicate function

I'm having a bit of trouble understanding the difference between strong and weak specification in Coq. For instance, if I wanted to write the replicate function (given a number n and a value x, it creates a list of length n, with all elements equal to x) using the strong specification way, how would I be able to do that? Apparently I have to write an Inductive "version" of the function but how?
Definition in Haskell:
myReplicate :: Int -> a -> [a]
myReplicate 0 _ = []
myReplicate n x | n > 0 = x:myReplicate (n-1) x
| otherwise = []
Definition of weak specification:
To define these functions with a weak specification and then add companion lemmas.
For instance, we define a function f : A->B and we prove a statement of the form ∀ x:A, Rx (fx), where R is a relation coding the intended input/output behaviour of the function.
Definition of strong specification:
To give a strong specification of the function: the type of this function directly states that the input is a value x of type A and that the output is the combination of a value v of type B and a proof that v satisfies Rxv.
This kind of specification usually relies on dependent types.
EDIT: I heard back from my teacher and apparently I have to do something similar to this, but for the replicate case:
"For example, if we want to extract a function that computes the length of a list from its specification, we can define a relation RelLength which establishes a relation between the expected input and output and then prove it. Like this:
Inductive RelLength (A:Type) : nat -> list A -> Prop :=
| len_nil : RelLength 0 nil
| len_cons : forall l x n, RelLength n l -> RelLength (S n) (x::l) .
Theorem len_corr : forall (A:Type) (l:list A), {n | RelLength n l}.
Proof.
…
Qed.
Recursive Extraction len_corr.
The function used to prove must use the list “recursor” directly (that’s why fixpoint won’t show up - it’s hidden in list_rect).
So you don’t need to write the function itself, only the relation, because the function will be defined by the proof."
Knowing this, how can I apply it to the replicate function case?
Just for fun, here's what it would look like in Haskell, where everything dependent-ish is much more annoying. This code uses some very new GHC features, mostly to make the types more explicit, but it could be modified quite easily to work with older GHC versions.
{-# language GADTs, TypeFamilies, PolyKinds, DataKinds, ScopedTypeVariables,
TypeOperators, TypeApplications, StandaloneKindSignatures #-}
{-# OPTIONS_GHC -Wincomplete-patterns #-}
module RelRepl where
import Data.Kind (Type)
import Data.Type.Equality ((:~:)(..))
-- | Singletons (borrowed from the `singletons` package).
type Sing :: forall (k :: Type). k -> Type
type family Sing
type instance Sing #Nat = SNat
type instance Sing #[a] = SList #a
-- The version of Sing in the singletons package has many more instances;
-- in any case, more can be added anywhere as needed.
-- Natural numbers, used at the type level
data Nat = Z | S Nat
-- Singleton representations of natural numbers, used
-- at the term level.
data SNat :: Nat -> Type where
SZ :: SNat 'Z
SS :: SNat n -> SNat ('S n)
-- Singleton lists
data SList :: forall (a :: Type). [a] -> Type where
SNil :: SList '[]
SCons :: Sing a -> SList as -> SList (a ': as)
-- The relation representing the `replicate` function.
data RelRepl :: forall (a :: Type). Nat -> a -> [a] -> Type where
Repl_Z :: forall x. RelRepl 'Z x '[]
Repl_S :: forall n x l. RelRepl n x l -> RelRepl ('S n) x (x ': l)
-- Dependent pairs, because those aren't natively supported.
data DPair :: forall (a :: Type). (a -> Type) -> Type where
MkDPair :: forall {a :: Type} (x :: a) (p :: a -> Type).
Sing x -> p x -> DPair #a p
-- Proof that every natural number and value produce a list
-- satisfying the relation.
repl_corr :: forall {a :: Type} (n :: Nat) (x :: a).
SNat n -> Sing x -> DPair #[a] (RelRepl n x)
repl_corr SZ _x = MkDPair SNil Repl_Z
repl_corr (SS n) x
| MkDPair l pf <- repl_corr n x
= MkDPair (SCons x l) (Repl_S pf)
-- Here's a proof that the relation indeed specifies
-- a *unique* function.
replUnique :: forall {a :: Type} (n :: Nat) (x :: a) (xs :: [a]) (ys :: [a]).
RelRepl n x xs -> RelRepl n x ys -> xs :~: ys
replUnique Repl_Z Repl_Z = Refl
replUnique (Repl_S pf1) (Repl_S pf2)
| Refl <- replUnique pf1 pf2
= Refl
A possible specification would look like this :
Inductive RelReplicate (A : Type) (a : A) : nat -> (list A) -> Prop :=
| rep0 : RelReplicate A a 0 nil
| repS : …
I did the zero case, leaving you the successor case. Its conclusion should be something like RelReplicate A a (S n) (a :: l).
As in your example, you can then try and prove something like
Theorem replicate_corr : forall (A:Type) (a : A) (n : nat), {l | ReplicateRel A a n l}.
which should be easy by induction on n.
If you want to check that your function replicate_corr corresponds to what you had in mind, you can try it on a few examples, with
Eval compute in (proj1_sig (rep_corr nat 0 3)).
which evaluates the first argument (the one corresponding to the "real function" and not the proof) of rep_corr. To be able to do that, you should end your Theorem with Defined rather than Qed so that Coq can evaluate it.

Is there any practical difference between these two definitions of type-level Peano Natural number summation?

I'm new to type level programming, and I am facing inability to reason about even very simple type level programs.
I have this code:
data Nat = Zero | Succ Nat
type family n + m where
Zero + m = m -- This is the base case of my type level recursive function.
Now, I have two variants of going about recursive case, and only one of them typechecks without UndecidableInstances:
Succ n + m = n + Succ m -- Typechecks with UndecidableInstances.
Succ n + m = Succ (n + m) -- Typechecks without UndecidableInstances.
I understand that UndecidableInstances allow me to use general recursion on type level, rather than structural recursion alone, which would guarantee typechecker termination. But in actuality both definitions seem to compile equally well, and give sane types when verified with :kind! in repl, for small numbers.
Can I be certain that these two definitions are equivalent in all regards, or are there corner cases? Should I test these implementations of + against each other, or use some theory?
As others have noted, the two definitions are not equivalent. Neither is particularly more general than the other, and it would be a stretch to argue that one or the other was clearly superior.
As #Benjamin Hodgson notes, the choice of definition affects the ease with which you can write code, but I'd add that typically each choice will make some code easier and other code harder.
Here's a concrete example. Suppose you have a vector type:
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
data Nat = Zero | Succ Nat
-- A vector type
data Vec n a where
V0 :: Vec Zero a
(:>) :: a -> Vec n a -> Vec (Succ n) a
infixr 5 :>
and let's start by working with the "nice" version of (+), the one that doesn't require undecidable instances. Note that I've switched the order of m and n because I get confused otherwise:
type family m + n where
Zero + m = m
Succ m + n = Succ (m + n)
If we try to implement a (++) for vectors, we find it's straightforward:
vappend :: Vec m a -> Vec n a -> Vec (m + n) a
vappend V0 ys = ys
vappend (x :> xs) ys = x :> vappend xs ys
On the other hand, consider the following list function:
rev :: [a] -> [a] -> [a]
rev ys [] = ys
rev ys (x:xs) = rev (x:ys) xs
which might be used to define a version of reverse:
reverse' = rev []
If we try to implement vrev, we run into trouble:
vrev :: Vec m a -> Vec n a -> Vec (n + m) a
vrev ys V0 = ys
vrev ys (x :> xs) = vrev (x :> ys) xs
The first case type-checks okay, but the second fails with the complaint that GHC can't deduce:
(n1 + 'Succ m) ~ 'Succ (n1 + m)
even though this statement is "obviously" true.
Replacing n + m with m + n in the signature makes things worse -- neither case will type-check.
On the other hand, if you replace the + definition with the undecidable version:
Succ m + n = m + Succ n
you'll find that vrev type-checks fine while vappend doesn't!
So, what's the solution? Well, typically people choose a definition that seems the most convenient in the most number of cases and then use various techniques to handle the "hard" cases. If you choose the:
Succ m + n = Succ (m + n)
definition, you'll be in good company. That's the one used in the Hasochism paper and the singletons-nats package, for example.
Suppose
foo :: T (Succ n) -> Bool
bar :: T n -> T m -> T (n + m)
Then,
baz :: T (Succ a) -> String
baz x | foo (bar x x) = "A"
| otherwise = "B"
will only type-check if + was defined using
Succ n + m = Succ (n + m)
If instead we used
Succ n + m = n + Succ m
then, during the type-checking of baz, we would discover that bar x x :: a + Succ (Succ a), but that is not of the right form to be an argument of foo.
Summing up: it not enough to think about "ground" Nat types. During type checking we also meet with type expressions with free type variables (i.e., non ground) like Succ a + Succ a, which will be simplified according to the equational rules. We need rules that work on such cases, too.

List of showables OOP-style in Haskell?

I want to build a list of different things which have one property in common, namely, they could be turned into string. The object-oriented approach is straightforward: define interface Showable and make classes of interest implement it. Second point can in principle be a problem when you can't alter the classes, but let's pretend this is not the case. Then you create a list of Showables and fill it with objects of these classes without any additional noise (e.g. upcasting is usually done implicitly). Proof of concept in Java is given here.
My question is what options for this do I have in Haskell? Below I discuss approaches that I've tried and which don't really satisfy me.
Approach 1: existensials. Works but ugly.
{-# LANGUAGE ExistentialQuantification #-}
data Showable = forall a. Show a => Sh a
aList :: [Showable]
aList = [Sh (1 :: Int), Sh "abc"]
The main drawback for me here is the necessity for Sh when filling the list. This closely resembles upcast operations which are implicitly done in OO-languages.
More generally, the dummy wrapper Showable for the thing which is already in the language — Show type class — adds extra noise in my code. No good.
Approach 2: impredicatives. Desired but does not work.
The most straightforward type for such a list for me and what I really desire would be:
{-# LANGUAGE ImpredicativeTypes #-}
aList :: [forall a. Show a => a]
aList = [(1 :: Int), "abc"]
Besides that (as I heard)ImpredicativeTypes is “fragile at best and broken at worst”
it does not compile:
Couldn't match expected type ‘a’ with actual type ‘Int’
‘a’ is a rigid type variable bound by
a type expected by the context: Show a => a
and the same error for "abc". (Note type signature for 1: without it I receive even more weird message: Could not deduce (Num a) arising from the literal ‘1’).
Approach 3: Rank-N types together with some sort of functional lists (difference lists?).
Instead of problematic ImpredicativeTypes one would probably prefer more stable and wide-accepted RankNTypes. This basically means: move
desired forall a. Show a => a out of type constructor (i.e. []) to plain function types. Consequently we need some representation of lists as plain functions. As I barely heard there are such representations. The one I heard of is difference lists. But in Dlist package the main type is good old data so we return to impredicatives. I didn't investigate this line any further as I suspect that it could yield more verbose code than in approach 1. But if you think it won't, please give me an example.
Bottom line: how would you attack such a task in Haskell? Could you give more succinct solution than in OO-language (especially in place of filling a list — see comment for code in approach 1)? Can you comment on how relevant are the approaches listed above?
UPD (based on first comments): the question is of course simplified for the purpose of readability. The real problem is more about how to store things which share the same type class, i.e. can be processed later on in a number of ways (Show has only one method, but other classes can have more than one). This factors out solutions which suggest apply show method right when filling a list.
Since evaluation is lazy in Haskell, how about just creating a list of the actual strings?
showables = [ show 1, show "blah", show 3.14 ]
The HList-style solutions would work, but it is possible to reduce the complexity if you only need to work with lists of constrained existentials and you don't need the other HList machinery.
Here's how I handle this in my existentialist package:
{-# LANGUAGE ConstraintKinds, ExistentialQuantification, RankNTypes #-}
data ConstrList c = forall a. c a => a :> ConstrList c
| Nil
infixr :>
constrMap :: (forall a. c a => a -> b) -> ConstrList c -> [b]
constrMap f (x :> xs) = f x : constrMap f xs
constrMap f Nil = []
This can then be used like this:
example :: [String]
example
= constrMap show
(( 'a'
:> True
:> ()
:> Nil) :: ConstrList Show)
It could be useful if you have a large list or possibly if you have to do lots of manipulations to a list of constrained existentials.
Using this approach, you also don't need to encode the length of the list in the type (or the original types of the elements). This could be a good thing or a bad thing depending on the situation. If you want to preserve the all of original type information, an HList is probably the way to go.
Also, if (as is the case of Show) there is only one class method, the approach I would recommend would be applying that method to each item in the list directly as in ErikR's answer or the first technique in phadej's answer.
It sounds like the actual problem is more complex than just a list of Show-able values, so it is hard to give a definite recommendation of which of these specifically is the most appropriate without more concrete information.
One of these methods would probably work out well though (unless the architecture of the code itself could be simplified so that it doesn't run into the problem in the first place).
Generalizing to existentials contained in higher-kinded types
This can be generalized to higher kinds like this:
data AnyList c f = forall a. c a => f a :| (AnyList c f)
| Nil
infixr :|
anyMap :: (forall a. c a => f a -> b) -> AnyList c f -> [b]
anyMap g (x :| xs) = g x : anyMap g xs
anyMap g Nil = []
Using this, we can (for example) create a list of functions that have Show-able result types.
example2 :: Int -> [String]
example2 x = anyMap (\m -> show (m x))
(( f
:| g
:| h
:| Nil) :: AnyList Show ((->) Int))
where
f :: Int -> String
f = show
g :: Int -> Bool
g = (< 3)
h :: Int -> ()
h _ = ()
We can see that this is a true generalization by defining:
type ConstrList c = AnyList c Identity
(>:) :: forall c a. c a => a -> AnyList c Identity -> AnyList c Identity
x >: xs = Identity x :| xs
infixr >:
constrMap :: (forall a. c a => a -> b) -> AnyList c Identity -> [b]
constrMap f (Identity x :| xs) = f x : constrMap f xs
constrMap f Nil = []
This allows the original example from the first part of this to work using this new, more general, formulation with no changes to the existing example code except changing :> to >: (even this small change might be able to be avoided with pattern synonyms. I'm not totally sure though since I haven't tried and sometimes pattern synonyms interact with existential quantification in ways that I don't fully understand).
If you really, really want, you can use a heterogeneous list. This approach really isn't useful for Show, because it has a single method and all you can do is apply it, but if your class has multiple methods this could be useful.
{-# LANGUAGE PolyKinds, KindSignatures, GADTs, TypeFamilies
, TypeOperators, DataKinds, ConstraintKinds, RankNTypes, PatternSynonyms #-}
import Data.List (intercalate)
import GHC.Prim (Constraint)
infixr 5 :&
data HList xs where
None :: HList '[]
(:&) :: a -> HList bs -> HList (a ': bs)
-- | Constraint All c xs holds if c holds for all x in xs
type family All (c :: k -> Constraint) xs :: Constraint where
All c '[] = ()
All c (x ': xs) = (c x, All c xs)
-- | The list whose element types are unknown, but known to satisfy
-- a class predicate.
data CList c where CL :: All c xs => HList xs -> CList c
cons :: c a => a -> CList c -> CList c
cons a (CL xs) = CL (a :& xs)
empty :: CList c
empty = CL None
uncons :: (forall a . c a => a -> CList c -> r) -> r -> CList c -> r
uncons _ n (CL None) = n
uncons c n (CL (x :& xs)) = c x (CL xs)
foldrC :: (forall a . c a => a -> r -> r) -> r -> CList c -> r
foldrC f z = go where go = uncons (\x -> f x . go) z
showAll :: CList Show -> String
showAll l = "[" ++ intercalate "," (foldrC (\x xs -> show x : xs) [] l) ++ "]"
test = putStrLn $ showAll $ CL $
1 :&
'a' :&
"foo" :&
[2.3, 2.5 .. 3] :&
None
You can create your own operator to reduce syntax noise:
infixr 5 <:
(<:) :: Show a => a -> [String] -> [String]
x <: l = show x : l
So you can do:
λ > (1 :: Int) <: True <: "abs" <: []
["1","True","\"abs\""]
This is not [1 :: Int, True, "abs"] but not much longer.
Unfortunately you cannot rebind [...] syntax with RebindableSyntax.
Another approach is to use HList and preserve all type information, i.e. no downcasts, no upcasts:
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
import GHC.Exts (Constraint)
infixr 5 :::
type family All (c :: k -> Constraint) (xs :: [k]) :: Constraint where
All c '[] = ()
All c (x ': xs) = (c x, All c xs)
data HList as where
HNil :: HList '[]
(:::) :: a -> HList as -> HList (a ': as)
instance All Show as => Show (HList as) where
showsPrec d HNil = showString "HNil"
showsPrec d (x ::: xs) = showParen (d > 5) (showsPrec 5 x)
. showString " ::: "
. showParen (d > 5) (showsPrec 5 xs)
And after all that:
λ *Main > (1 :: Int) ::: True ::: "foo" ::: HNil
1 ::: True ::: "foo" ::: HNil
λ *Main > :t (1 :: Int) ::: True ::: "foo" ::: HNil
(1 :: Int) ::: True ::: "foo" ::: HNil
:: HList '[Int, Bool, [Char]]
There are various ways to encode heterogenous list, in HList is one, there is also generics-sop with NP I xs. It depends on what you are trying to achieve in the larger context, if this is this preserve-all-the-types approach is what you need.
I would do something like this:
newtype Strings = Strings { getStrings :: [String] }
newtype DiffList a = DiffList { getDiffList :: [a] -> [a] }
instance Monoid (DiffList a) where
mempty = DiffList id
DiffList f `mappend` DiffList g = DiffList (f . g)
class ShowList a where
showList' :: DiffList String -> a
instance ShowList Strings where
showList' (DiffList xs) = Strings (xs [])
instance (Show a, ShowList b) => ShowList (a -> b) where
showList' xs x = showList' $ xs `mappend` DiffList (show x :)
showList = showList' mempty
Now, you can create a ShowList as follows:
myShowList = showList 1 "blah" 3.14
You can get back a list of strings using getStrings as follows:
myStrings = getStrings myShowList
Here's what's happening:
A value of the type ShowList a => a could be:
Either a list of strings wrapped in a Strings newtype wrapper.
Or a function from an instance of Show to an instance of ShowList.
This means that the function showList is a variadic argument function which takes an arbitrary number of printable values and eventually returns a list of strings wrapped in a Strings newtype wrapper.
You can eventually call getStrings on a value of the type ShowList a => a to get the final result. In addition, you don't need to do any explicit type coercion yourself.
Advantages:
You can add new elements to your list whenever you want.
The syntax is succinct. You don't have to manually add show in front of every element.
It doesn't make use of any language extensions. Hence, it works in Haskell 98 too.
You get the best of both worlds, type safety and a great syntax.
Using difference lists, you can construct the result in linear time.
For more information on functions with variadic arguments, read the answer to the following question:
How does Haskell printf work?
My answer is fundamentally the same as ErikR's: the type that best embodies your requirements is [String]. But I'll go a bit more into the logic that I believe justifies this answer. The key is in this quote from the question:
[...] things which have one property in common, namely, they could be turned into string.
Let's call this type Stringable. But now the key observation is this:
Stringable is isomorphic to String!
That is, if your statement above is the whole specification of the Stringable type, then there is a pair functions with these signatures:
toString :: Stringable -> String
toStringable :: String -> Stringable
...such that the two functions are inverses. When two types are isomorphic, any program that uses either of the types can be rewritten in terms of the other without any change to its semantics. So Stringable doesn't let you do anything that String doesn't let you do already!
In more concrete terms, the point is that this refactoring is guaranteed to work no matter what:
At every point in your program where you turn an object into a Stringable and stick that into a [Stringable], turn the object into a String and stick that into a [String].
At every point in your program that you consume a Stringable by applying toString to it, you can now eliminate the call to toString.
Note that this argument generalizes to types more complex than Stringable, with many "methods". So for example, the type of "things that you can turn into either a String or an Int" is isomorphic to (String, Int). The type of "things that you can either turn into a String or combine them with a Foo to produce a Bar" is isomorphic to (String, Foo -> Bar). And so on. Basically, this logic leads to the "record of methods" encoding that other answers have brought up.
I think the lesson to draw from this is the following: you need a specification richer than just "can be turned into a string" in order to justify using any of the mechanisms you brought up. So for example, if we add the requirement that Stringable values can be downcast to the original type, an existential type now perhaps becomes justifiable:
{-# LANGUAGE GADTs #-}
import Data.Typeable
data Showable = Showable
Showable :: (Show a, Typeable a) => a -> Stringable
downcast :: Typeable a => Showable -> Maybe a
downcast (Showable a) = cast a
This Showable type is not isomorphic to String, because the Typeable constraint allows us to implement the downcast function that allows us to distinguish between different Showables that produce the same string. A richer version of this idea can be seen in this "shape example" Gist.
You can store partially applied functions in the list.
Suppose we are building a ray-tracer with different shape that you can intersect.
data Sphere = ...
data Triangle = ...
data Ray = ...
data IntersectionResult = ...
class Intersect t where
intersect :: t -> Ray -> Maybe IntersectionResult
instance Intersect Sphere where ...
instance Intersect Triangle where ...
Now, we can partially apply the intersect to get a list of Ray -> Maybe IntersectionResult such as:
myList :: [(Ray -> Maybe IntersectionResult)]
myList = [intersect sphere, intersect triangle, ...]
Now, if you want to get all the intersections, you can write:
map ($ ray) myList -- or map (\f -> f ray) myList
This can be extended a bit to handle an interface with multiples functions, for example, if you want to be able to get something of a shape :
class ShapeWithSomething t where
getSomething :: t -> OtherParam -> Float
data ShapeIntersectAndSomething = ShapeIntersectAndSomething {
intersect :: Ray -> Maybe IntersectionResult,
getSomething :: OtherParam -> Float}
Something I don't know is the overhead of this approach. We need to store the pointer to the function and the pointer to the shape and this for each function of the interface, which is a lot compared to the shared vtable usually used in OO language. I don't have any idea if GHC is able to optimize this.
The core of the problem is : you want to dispatch (read select which function to call) at runtime, depending on what the "type" of the object is. In Haskell this can be achieved by wrapping the data into a sum data type (which is called here ShowableInterface):
data ShowableInterface = ShowInt Int | ShowApple Apple | ShowBusiness Business
instance Show ShowableInterface where
show (ShowInt i) = show i
show (ShowApple a) = show a
show (ShowBusiness b) = show b
list=[ShowInt 2, ShowApple CrunchyGold, ShowBusiness MoulinRouge]
show list
would correspond to something like this in Java :
class Int implements ShowableInterface
{
public show {return Integer.asString(i)};
}
class Apple implements ShowableInterface
{
public show {return this.name};
}
class ShowBusiness implements ShowableInterface
{
public show {return this.fancyName};
}
List list = new ArrayList (new Apple("CrunchyGold"),
new ShowBusiness("MoulingRouge"), new Integer(2));
so in Haskell you need to explicitly wrap stuff into the ShowableInterface, in Java this wrapping is done implicitly on object creation.
credit goes to #haskell IRC for explaining this to me a year ago, or so.

Unsafe entailment with Haskell constraints

I'm playing around with the constraints package (for GHC Haskell). I have a type family for determining if a type-level list contains an element:
type family HasElem (x :: k) (xs :: [k]) where
HasElem x '[] = False
HasElem x (x ': xs) = True
HasElem x (y ': xs) = HasElem x xs
This works, but one thing it doesn't give me is the knowledge that
HasElem x xs entails HasElem x (y ': xs)
since the type family isn't an inductive definition of the "is element of" statement (like you would have in agda). I'm pretty sure that, until GADTs are promotable to the type level, there is no way to express list membership with a data type.
So, I've used the constraints package to write this:
containerEntailsLarger :: Proxy x -> Proxy xs -> Proxy b -> (HasElem x xs ~ True) :- (HasElem x (b ': xs) ~ True)
containerEntailsLarger _ _ _ = unsafeCoerceConstraint
Spooky, but it works. I can pattern match on the entailment to get what I need. What I'm wondering is if it can ever cause a program to crash. It seems like it couldn't, since unsafeCoerceConstraint is defined as:
unsafeCoerceConstraint = unsafeCoerce refl
And in GHC, the type level is elided at runtime. I thought I'd check though, just to make sure that doing this is ok.
--- EDIT ---
Since no one has given an explanation yet, I thought I would expand the question a little. In the unsafe entailment I'm creating, I only expect a type family. If I did something that involved typeclass dictionaries instead like this:
badEntailment :: Proxy a -> (Show a) :- (Ord a)
badEntailment _ = unsafeCoerceConstraint
I assume that this would almost certainly be capable of causing a segfault. Is this true? and if so, what makes it different from the original?
--- EDIT 2 ---
I just wanted to provide a little background for why I am interested in this. One of my interests is making a usable encoding of relational algebra in Haskell. I think that no matter how you define functions to work on type-level lists, there will be obvious things that aren't proved correctly. For example, a constraint (for semijoin) that I've had before looked like this (this is from memory, so it might not be exact):
semijoin :: ( GetOverlap as bs ~ Overlap inAs inBoth inBs
, HasElem x as, HasElem x (inAs ++ inBoth ++ inBs)) => ...
So, it should be obvious (to a person) that if I take union of two sets, that it contains an element x that was in as, but I'm not sure that it's possible the legitimately convince the constraint solver of this. So, that's my motivation for doing this trick. I create entailments to cheat the constraint solver, but I don't know if it's actually safe.
I don't know if this will suit your other needs, but it accomplishes this particular purpose. I'm not too good with type families myself, so it's not clear to me what your type family can actually be used for.
{-# LANGUAGE ...., UndecidableInstances #-}
type family Or (x :: Bool) (y :: Bool) :: Bool where
Or 'True x = 'True
Or x 'True = 'True
Or x y = 'False
type family Is (x :: k) (y :: k) where
Is x x = 'True
Is x y = 'False
type family HasElem (x :: k) (xs :: [k]) :: Bool where
HasElem x '[] = 'False
HasElem x (y ': z) = Or (Is x y) (HasElem x z)
containerEntailsLarger :: proxy1 x -> proxy2 xs -> proxy3 b ->
(HasElem x xs ~ 'True) :- (HasElem x (b ': xs) ~ 'True)
containerEntailsLarger _p1 _p2 _p3 = Sub Dict
An approach using GADTs
I've been having trouble letting go of this problem. Here's a way to use a GADT to get good evidence while using type families and classes to get a good interface.
-- Lots of extensions; I don't think I use ScopedTypeVariables,
-- but I include it as a matter of principle to avoid getting
-- confused.
{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, UndecidableInstances #-}
{-# LANGUAGE TypeFamilies, TypeOperators #-}
{-# LANGUAGE DataKinds, PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE GADTs #-}
-- Some natural numbers
data Nat = Z | S Nat deriving (Eq, Ord, Show)
-- Evidence that a type is in a list of types
data ElemG :: k -> [k] -> * where
Here :: ElemG x (x ': xs)
There :: ElemG x xs -> ElemG x (y ': xs)
deriving instance Show (ElemG x xs)
-- Take `ElemG` to the class level.
class ElemGC (x :: k) (xs :: [k]) where
elemG :: proxy1 x -> proxy2 xs -> ElemG x xs
-- There doesn't seem to be a way to instantiate ElemGC
-- directly without overlap, but we can do it via another class.
instance ElemGC' n x xs => ElemGC x xs where
elemG = elemG'
type family First (x :: k) (xs :: [k]) :: Nat where
First x (x ': xs) = 'Z
First x (y ': ys) = 'S (First x ys)
class First x xs ~ n => ElemGC' (n :: Nat) (x :: k) (xs :: [k]) where
elemG' :: proxy1 x -> proxy2 xs -> ElemG x xs
instance ElemGC' 'Z x (x ': xs) where
elemG' _p1 _p2 = Here
instance (ElemGC' n x ys, First x (y ': ys) ~ 'S n) => ElemGC' ('S n) x (y ': ys) where
elemG' p1 _p2 = There (elemG' p1 Proxy)
This actually seems to work, at least in simple cases:
*Hello> elemG (Proxy :: Proxy Int) (Proxy :: Proxy '[Int, Char])
Here
*Hello> elemG (Proxy :: Proxy Int) (Proxy :: Proxy '[Char, Int, Int])
There Here
*Hello> elemG (Proxy :: Proxy Int) (Proxy :: Proxy '[Char, Integer, Int])
There (There Here)
This doesn't support the precise entailment you desire, but I believe the ElemGC' recursive case is probably the closest you can get with such an informative constraint, at least in GHC 7.10.

Binding name in type signature using DataKind

So, I finally found a task where I could make use of the new DataKinds extension (using ghc 7.4.1). Here's the Vec I'm using:
data Nat = Z | S Nat deriving (Eq, Show)
data Vec :: Nat -> * -> * where
Nil :: Vec Z a
Cons :: a -> Vec n a -> Vec (S n) a
Now, for convenience I wanted to implement fromList. Basically no problem with simple recursion/fold -- but I can't figure out how to give it the correct type. For reference, this is the Agda version:
fromList : ∀ {a} {A : Set a} → (xs : List A) → Vec A (List.length xs)
My Haskell approach, using the syntax I saw here:
fromList :: (ls :: [a]) -> Vec (length ls) a
fromList [] = Nil
fromList (x:xs) = Cons x (fromList xs)
This gives me a parse error on input 'a'. Is the syntax I found even correct, or have they changed it? I also added some more extensions which are in the code in the link, which didn't help either (currently I have GADTs, DataKinds, KindSignatures, TypeOperators, TypeFamilies, UndecidableInstances).
My other suspicion was that I just can't bind polymorphic types, but my test for this:
bla :: (n :: Nat) -> a -> Vec (S n) a
bla = undefined
failed, too, with Kind mis-match Expected kind 'ArgKind', but 'n' has kind 'Nat' (don't really know what that means).
Could anyone help me with a working version of fromList and also clarify the other issues? Unfortunately, DataKinds isn't documented very well yet and seems to assume that everybody using it has profound type theory knowledge.
Haskell, unlike Agda, does not have dependent types, so there is no way to do exactly what you want. Types cannot be parameterized by value, since Haskell enforces a phase distinction between runtime and compile time. The way DataKinds works conceptually is actually really simple: data types are promoted to kinds (types of types) and data constructors are promoted to types.
fromList :: (ls :: [a]) -> Vec (length ls) a
has a couple of problems: (ls :: [a]) does not really make sense (at least when you are only faking dependent types with promotion), and length is a type variable instead of a type function. What you want to say is
fromList :: [a] -> Vec ??? a
where ??? is the length of the list. The problem is that you have no way of getting the length of the list at compile time... so we might try
fromList :: [a] -> Vec len a
but this is wrong, since it says that fromList can return a list of any length. Instead what we want to say is
fromList :: exists len. [a] -> Vec len a
but Haskell does not support this. Instead
data VecAnyLength a where
VecAnyLength :: Vec len a -> VecAnyLength a
cons a (VecAnyLength v) = VecAnyLength (Cons a v)
fromList :: [a] -> VecAnyLength a
fromList [] = VecAnyLength Nil
fromList (x:xs) = cons x (fromList xs)
you can actually use a VecAnyLength by pattern matching, and thus getting a (locally) psuedo-dependently typed value.
similarly,
bla :: (n :: Nat) -> a -> Vec (S n) a
does not work because Haskell functions can only take arguments of kind *. Instead you might try
data HNat :: Nat -> * where
Zero :: HNat Z
Succ :: HNat n -> HNat (S n)
bla :: HNat n -> a -> Ven (S n) a
which is even definable
bla Zero a = Cons a Nil
bla (Succ n) a = Cons a (bla n a)
You can use some typeclass magic here (see HList for more):
{-# LANGUAGE GADTs, KindSignatures, DataKinds, FlexibleInstances
, NoMonomorphismRestriction, FlexibleContexts #-}
data Nat = Z | S Nat deriving (Eq, Show)
data Vec :: Nat -> * -> * where
Nil :: Vec Z a
Cons :: a -> Vec n a -> Vec (S n) a
instance Show (Vec Z a) where
show Nil = "."
instance (Show a, Show (Vec m a)) => Show (Vec (S m) a) where
show (Cons x xs) = show x ++ " " ++ show xs
class FromList m where
fromList :: [a] -> Vec m a
instance FromList Z where
fromList [] = Nil
instance FromList n => FromList (S n) where
fromList (x:xs) = Cons x $ fromList xs
t5 = fromList [1, 2, 3, 4, 5]
but this not realy solve the problem:
> :t t5
t5 :: (Num a, FromList m) => Vec m a
Lists are formed at runtime, their length is not known at compile time, so the compiler can't infer the type for t5, it must be specified explicitly:
*Main> t5
<interactive>:99:1:
Ambiguous type variable `m0' in the constraint:
(FromList m0) arising from a use of `t5'
Probable fix: add a type signature that fixes these type variable(s)
In the expression: t5
In an equation for `it': it = t5
*Main> t5 :: Vec 'Z Int
*** Exception: /tmp/d.hs:20:3-19: Non-exhaustive patterns in function fromList
*Main> t5 :: Vec ('S ('S ('S 'Z))) Int
1 2 3 *** Exception: /tmp/d.hs:20:3-19: Non-exhaustive patterns in function fromList
*Main> t5 :: Vec ('S ('S ('S ('S ('S 'Z))))) Int
1 2 3 4 5 .
*Main> t5 :: Vec ('S ('S ('S ('S ('S ('S ('S 'Z))))))) Int
1 2 3 4 5 *** Exception: /tmp/d.hs:23:3-40: Non-exhaustive patterns in function fromList
Languages ​​with dependent types have maps from terms to types, types can be formed dynamically at runtime too, so this problem does not exist.
On top of the previous answers :
value level, from [a] to exist n. Vec n a
value to typed value, from [a] to Vec 5 a, where you have to provide a specific n.
A variant of the 1st transform, goes like
reify :: [a] -> (forall (n::Nat). Proxy n -> Vec n a -> w) -> w
reify [] k = k (Proxy # 'Z) Nil
reify (x:xs) k = reify xs (\(_ :: Proxy n) v -> k (Proxy # ('S n)) (Cons x v))
It still goes from a value [a] to a typed value Vec n a in which n is (statically) quantified. This is similar to the VecAnyLength approach, without introducing an actual datatype to perform quantification.
The proxy here is to explicit the n as a Nat. it can be removed from the code and n left silent, appearing only in the type Vec n a, and not provided to the values constructed, as it is in Proxy # ('S n).

Resources