getting derivations out of typeclass resolution - haskell

We can get a value level proof that [Int] has a Show instance using a Dict
{-# LANGUAGE ConstraintKinds, GADTs #-}
data Dict (p :: Constraint) where
Dict :: p => Dict p
and
proof = Dict :: Dict (Show [Int])
Is there a way to get a value level derivation, that is, the entire proof tree ?
derivation = Apply#Int(Lam a.(Show a) :=> Show [a])) (Apply(() :=> Show Int)())

There isn't a way to get the derivation of an arbitrary constraint as a Haskell value.
The closest thing I can think of, if you want to check whether the derivation is what you think it is, is to look at the desugarer output.
ghc -ddump-ds -ddump-to-file A.hs
The relevant part looks like this:
-- RHS size: {terms: 2, types: 1, coercions: 0, joins: 0/0}
irred :: Show [Int]
[LclId]
irred = GHC.Show.$fShow[] # Int GHC.Show.$fShowInt
-- RHS size: {terms: 2, types: 3, coercions: 0, joins: 0/0}
proof :: Dict (Show [Int])
[LclIdX]
proof = Cns.Dict # (Show [Int]) irred
Another one is to write custom typeclasses instrumented to reflect the derivation, either in types or in values, but of course this doesn't apply to preexisting type classes.
{-# LANGUAGE AllowAmbiguousTypes, ConstraintKinds, GADTs, DataKinds,
FlexibleInstances, KindSignatures, MultiParamTypeClasses, RankNTypes,
ScopedTypeVariables, TypeApplications, TypeOperators,
UndecidableInstances #-}
import Data.Typeable
import Data.Kind
data (c :: [Type]) :=> (d :: Type -> Constraint)
class MyShow a d where
myshow :: a -> String
instance (d ~ ('[] :=> MyShow Int)) => MyShow Int d where
instance (MyShow a da, d ~ ('[da] :=> MyShow [a])) => MyShow [a] d where
myshowInstance :: forall a d. (Typeable d, MyShow a d) => TypeRep
myshowInstance = typeRep #_ #d Proxy
main = print (myshowInstance #[Int])
The output could be made to look better, e.g., via a singleton with a proper rendering method instead of TypeRep, but I hope you get the main idea.
:=> (': * (:=> ('[] *) (MyShow Int)) ('[] *)) (MyShow [Int])

This may be what you're after, or at least enough to give you a general idea. I can't think of a way to have GHC provide this automatically, but you can manually construct the chain of entailments that proves the constraint using the constraints package.
For whatever reason, there is no instance () :=> Show Int, so I've used Char instead. This is likely an oversight, I've opened a pull request to add the missing instances.
{-# LANGUAGE ConstraintKinds #-}
import Data.Constraints
derivation :: () :- Show [Char]
derivation = trans showList showChar
where showList :: Show a :- Show [a]
showList = ins
showChar :: () :- Show Char
showChar = ins
Unfortunately printing this value doesn't show the inner derivations, just "Sub Dict".
A fun exercise could be to try to write derivation with explicit TypeApplications using Data.Constraint.Forall. You'll need a couple extra steps to prove Show a :- Forall Show and ForallF Show [] :- Show [a].

Related

Problems writing type class instances for types determined by a closed type family

I tried to model my own enumeration type with type literals, closed type families and a bunch of different stuff. (I know GHC.Generics would be probably a better approach, but now I want to know, what is going on.)
Through trial and error (I have to admit that) I finally arrived at this piece of program, which compiles and some things are working (the base case) but the recursion is not:
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilyDependencies #-}
module Wft2 where
import GHC.TypeLits
import GHC.Exts
data Label (l :: Symbol) = Value deriving Eq
instance (KnownSymbol l) => Show (Label (l :: Symbol)) where show = symbolVal
type family Enumerate (a :: [Symbol]) = b | b -> a where
Enumerate '[] = ()
Enumerate '[a] = Label a
Enumerate (a ': b) = Either (Label a) (Enumerate b)
type family CheckEmbedImpl (a :: [Symbol]) (orig :: [Symbol]) (b :: Symbol) where
CheckEmbedImpl '[] orig b = TypeError (ShowType b :<>: Text " not contained in " :<>: ShowType orig)
CheckEmbedImpl (b : rest) orig b = (() :: Constraint)
CheckEmbedImpl (b : rest) orig c = CheckEmbedImpl rest orig c
type family CheckEmbed (a :: [Symbol]) (b :: Symbol) where
CheckEmbed a b = CheckEmbedImpl a a b
class Embed (l :: [Symbol]) (s :: Symbol) where
embed :: (CheckEmbed l s) => Label s -> Enumerate l
instance {-# OVERLAPS #-} (Enumerate '[t] ~ Label t) => Embed '[t] t where embed _ = Value
instance {-# OVERLAPS #-} Embed '[t] s where embed = undefined
instance {-# OVERLAPS #-} (Either (Label a) (Enumerate b) ~ Enumerate (a ': b)) =>
Embed (a ': b) a where embed _ = Left Value
instance {-# OVERLAPS #-} (Either (Label a) (Enumerate b) ~ Enumerate (a ': b),
Embed b t,
CheckEmbed b t) =>
Embed (a ': b) t where embed l = Right (embed l)
doing stuff like embed (Value :: Label "abc") :: Enumerate '["abc"]) and
embed (Value :: Label "abc") :: Enumerate '["abcd"]) works as expected, but embed (Value :: Label "abc") :: Enumerate '["abc", abc2"] gives me errors like
*Wft2> embed (Value :: Label "abc") :: Enumerate '["abc", "abcd" ]
<interactive>:13:1: error:
• Couldn't match type ‘Enumerate l0’
with ‘Either (Label "abc") (Label "abcd")’
Expected type: Enumerate '["abc", "abcd"]
Actual type: Enumerate l0
The type variable ‘l0’ is ambiguous
• In the expression:
embed (Value :: Label "abc") :: Enumerate '["abc", "abcd"]
In an equation for ‘it’:
it = embed (Value :: Label "abc") :: Enumerate '["abc", "abcd"]
I thought the type equality constrain on my third Embed instance should handle this. Why isn't GHC able to deduce l0 ~ '["abc", "abcd"] and thus
Enumerate l0 ~ Either (Label "abc") (Label "abcd")?
Bonus points: If you know about some tutorial, which tries to do stuff like that and has some example, please provide pointers.
Beware it is an injective type family, so it is not to blame on type families being not injective.
Injective type families are fairly new, not very evolved, and fairly buggy.
Note that in the following patterns:
Enumerate '[a] = ...
Enumerate (a ': b) = ...
if b ~ '[] then these patterns both match and the choice between the two is ambiguous. (Also note that while it is obvious to a human that b is not '[] in Enumerate '["abc", "abcd" ], the compiler doesn't know this a priori - this is precisely what it is trying to prove using injectivity).
This type family still passes the injectivity check because the typechecker knows it is a closed type family and knows that b cannot be '[] or the previous pattern would have matched. But the actual evaluation semantics of type families don't care at all whether the type family is open or closed. Injectivity doesn't affect evaluation of type families at all; it just allows the typechecker to reduce a constraint like Enumerate l ~ Label "x" to l ~ "x".
The solution is to change the last pattern to
Enumerate (a ': (b ': c)) = Either (Label a) (Enumerate (b ': c))
which makes it 'obvious' that this cannot overlap with the previous one.

How can I constrain Vinyl / Composite Records?

I have an extensible Vinyl / Composite record (similar to HList, Frames...), and I would like to generate the tuples of keys/values, such as
tuplify '[String :-> Whatevs, ...] :: [(String, String)]
This is surprisingly hard. original gist.
Solution Gist, thanks to Alec below
type FA = "a" :-> String
type FB = "b" :-> Int
type AB = '[FA, FB]
ab :: Rec Identity AB
ab = "A" :*: 1 :*: RNil
tuplify :: (Show a) => Rec Identity '[a] -> [(String, String)]
tuplify = recordToList . rmap undefined -- ??????
-- tuplify ab = [("a", "A"), ("b", "1")]
If you care to try out what I've done so far, check out that gist, and it has well-thought-out examples and the errors I see:
Here is the hardware for refying in Composite (reifyDicts):
And the same for Vinyl (reifyConstraints):
AFAICT, the problem is that in something like rmap:
rmap :: (forall x. f x -> g x) -> Rec f rs -> Rec g rs
The mapped fn is defined forall x, but my tuplify is constrained, and I think the reification should move the constraint into the type (that's what Dicts are for), but, alas, no luck so far.
I can't get composite related stuff to install on my global Stack setup but the following should still work (I just copy-pasted relevant definitions). That said, I think a simple type-class based dispatch based on type is simpler here (since the constraints are non-trivial). With all of the right extensions enabled [1], you just need:
class Tuplify a where
tuplify :: a -> [(String, String)]
instance Tuplify (Rec Identity '[]) where
tuplify RNil = []
instance (Show t, KnownSymbol s, Tuplify (Rec Identity rs)) =>
Tuplify (Rec Identity (s :-> t ': rs)) where
tuplify (v :*: rs) = (symbolVal (Proxy :: Proxy s), show v) : tuplify rs
Then, in GHCi:
ghci> tuplify ab
[("a","\"A\""),("b","1")]
If you really want to try the reifying constraint approach, you'll have to start by declaring a type class and instance for the particular constraint you want:
class ShowField a where
showField :: a -> (String, String)
instance (KnownSymbol s, Show a) => ShowField (Identity (s :-> a)) where
showField (Identity (Val v)) = (symbolVal (Proxy :: Proxy s), show v)
Then it becomes more straightforward to use reifyConstraints and rmap:
tuplify' :: RecAll Identity rs ShowField => Rec Identity rs -> [(String, String)]
tuplify' xs = recordToList
. rmap (\(Vinyl.Compose (Dict x)) -> Vinyl.Const $ showField x)
$ reifyConstraint (Proxy :: Proxy ShowField) xs
I imagine something similar is possible with reifyDicts, although I wish there was a variant of it defined using ValuesAllHave instead of just AllHave (then we could bypass declaring a ShowField typeclass and do everything in just a function).
[1] extensions needed for first example
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}

How to use an arbitrary makeFields lens argument with different types in the same function?

I am using makeFields from lens to generate fields overloaded for various structures. I would like to use these fields at one with multiple structures while having to state which field I want to use only once. It would look like this:
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE FlexibleInstances #-}
import Control.Lens
data A = A
{ _aX :: String
, _aY :: String
}
makeFields ''A
data B = B
{ _bX :: String -> Char
, _bY :: String -> Bool
}
makeFields ''B
-- x can get _aX from an A and _bX from a B
a :: A
a = undefined
b :: B
b = undefined
q :: (Getter A String) AND (Getter B (String -> a)) -> a
q lens = (b^.lens) (a^.lens)
Which type should I give q? I tried letting GHC infer the types, but that failed.
To decide what is to be done, we need to know what the types of your (makeField-generated) fields are:
GHCi> :t x
x :: (HasX s a, Functor f) => (a -> f a) -> s -> f s
So the abstraction covering all your x-bearing types (the abstraction I was whining about before noticing you were using makeFields) is a multi-parameter type class HasX, and similarly for the other fields. That gives us enough to use x with different types in a single implementation:
-- Additional extension required: FlexibleContexts
-- Note that GHC is able to infer this type.
qx :: (HasX t (a -> b), HasX s a) => t -> s -> b
qx t s = (t ^. x) (s ^. x)
GHCi> import Data.Maybe
GHCi> let testA = A "foo" "bar"
GHCi> let testB = B (fromMaybe 'ø' . listToMaybe) null
GHCi> qx testB testA
'f'
That, however, is not quite what you asked for. You wanted something like:
q xOrY b a = (b^.xOrY) (a^.xOrY)
Achieving that, however, requires abstracting over the classes HasX, HasY, etc. Doing so is, in fact, somewhat feasible thanks to the ConstraintKinds extension, as demonstrated in Could we abstract over type classes? Here it goes:
-- Additional extensions required: ConstraintKinds, ScopedTypeVariables
-- Additional import required: Data.Proxy
-- GHC cannot infer this type.
q :: forall h s t a b. (h t (a -> b), h s a) => Proxy a -> Proxy h
-> (forall u c. h u c => Getting c u c) -> t -> s -> b
q _ _ l t s =
(t ^. (l :: Getting (a -> b) t (a -> b))) (s ^. (l :: Getting a s a))
GHCi> q (Proxy :: Proxy String) (Proxy :: Proxy HasX) x testB testA
'f'
The first proxy, which determines the intermediate type, is necessary unless you give up this bit of generality and replace a by String. Additionally, you have to specify the field twice, both by passing the getter as an argument and through the second proxy. I am not at all convinced that this second solution is worth the trouble -- the extra boilerplate of having to define qx, qy, etc. looks quite a bit less painful than all the circuitousness involved here. Still, if any of you who are reading this would like to suggest an improvement, I'm all ears.

Typeable instance for Constraint tupling

I'm trying to derive a Typeable instance for tupled constraints. See the following code:
{-# LANGUAGE ConstraintKinds, GADTs #-}
{-# LANGUAGE DataKinds, PolyKinds, AutoDeriveTypeable #-}
{-# LANGUAGE StandaloneDeriving, DeriveDataTypeable #-}
import Data.Proxy
import Data.Typeable
data Foo (p :: (*, *))
data Dict ctx where
Dict :: ctx => Dict ctx
deriving (Typeable)
deriving instance Typeable '(,)
deriving instance Typeable Typeable
deriving instance Typeable Show
works :: IO ()
works = print (typeRep (Proxy :: Proxy (Foo '(Bool, Char))))
alsoWorks :: IO ()
alsoWorks = print (typeRep (Dict :: Dict (Show Bool)))
fails :: IO ()
fails = print (typeRep (Dict :: Dict (Show Bool, Typeable Bool)))
main :: IO ()
main = works >> alsoWorks >> fails
If you compile this with -fprint-explicit-kinds, the following error is given:
No instance for (Typeable
(Constraint -> Constraint -> Constraint) (,))
Is there a way to derive such an instance? Everything I try refuses to disambiguate from the ★ -> ★ -> ★ constructor.
GHC can not currently make a Typeable instance, or any other instance, for (,) :: Constraint -> Constraint -> Constraint. The type constructor (,) only has kind * -> * -> *. There is no type constructor for products of the kind Constraint -> Constraint -> Constraint. The constructor (,) is overloaded to construct both tuples and products of Constraints, but has no corresponding type constructor when used to make a product of Constraints.
If we did have a type constructor for products of Constraints we should be able to define an instance as follows. For this, we'll pretend (,) is also a type constructor with kind (,) :: Constraint -> Constraint -> Constraint. To define an instance for it, we'd use KindSignatures and import GHC.Exts.Constraint to be able to talk about the kind of constraints explicitly
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE KindSignatures #-}
import GHC.Exts (Constraint)
import Data.Typeable
deriving instance Typeable ((,) :: Constraint -> Constraint -> Constraint)
If we do this now, it results in the following error, due to the kind of the (,) type constructor.
The signature specified kind `Constraint
-> Constraint -> Constraint',
but `(,)' has kind `* -> * -> *'
In the stand-alone deriving instance for
`Typeable ((,) :: Constraint -> Constraint -> Constraint)'
The constraints package also works with products of constraints, and includes the following note.
due to the hack for the kind of (,) in the current version of GHC we can't actually make instances for (,) :: Constraint -> Constraint -> Constraint
I presume the hack Edward Kmett is referring to is the overloading of the (,) constructor for Constraints without a corresponding type constructor.
It seems that it is not currently possible. There's a revealing comment in the latest version of constraint:
due to the hack for the kind of (,) in the current version of GHC we can't actually make instances for (,) :: Constraint -> Constraint -> Constraint

Haskell Overlapping/Incoherent Instances

I know this is code is a bit silly, but can someone explain why this isList [42] returns True whereas isList2 [42] prints False, and how to prevent this? I'd like to get better understanding of some of the more obscure GHC type extensions, and I thought this would be an interesting example to figure out.
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverlappingInstances #-}
{-# LANGUAGE IncoherentInstances #-}
class IsList a where
isList :: a -> Bool
instance IsList a where
isList x = False
instance IsList [a] where
isList x = True
isList2 = isList
main =
print (isList 42) >>
print (isList2 42) >>
print (isList [42]) >>
print (isList2 [42])
It's really quite simple. Let's ask GHCi what the type of isList2 is:
∀x. x ⊢ :t isList2
isList2 :: a -> Bool
This doesn't match the [a] instance (even though it could, via unification), but it does match the a instance immediately. Therefore, GHC selects the a instance, so isList2 returns False.
This behavior is precisely what IncoherentInstances means. Actually, this is a rather nice demonstration of it.
Hilariously, if you simply disable IncoherentInstances, we get exactly the opposite effect, and GHCi now says this:
∀x. x ⊢ :t isList2
isList2 :: [Integer] -> Bool
This happens because isList2 is a top-level binding not defined using function syntax, and thus subject to the Dreaded Monomorphism Restriction. So it gets specialized to the instance it's actually used with.
Adding NoMonomorphismRestriction as well as disabling IncoherentInstances, we get this instead:
∀x. x ⊢ :t isList2
isList2 :: IsList a => a -> Bool
∀x. x ⊢ isList2 'a'
False
∀x. x ⊢ isList2 "a"
True
∀x. x ⊢ isList2 undefined
<interactive>:19:1:
Overlapping instances for IsList a0 arising from a use of `isList2'
Which is the expected overlapping behavior, with the instance chosen based on use and complaints if the choice is ambiguous.
Regarding the edit to the question, I don't believe the desired result is possible without type annotations.
The first option is to give isList2 a type signature, which prevents IncoherentInstances from selecting an instance too early.
isList2 :: (IsList a) => a -> Bool
isList2 = isList
You'll probably need to do the same anywhere else isList is mentioned (even indirectly) without being applied to an argument.
The second option is to disambiguate the numeric literals and disable IncoherentInstances.
main =
print (isList (42 :: Integer)) >>
print (isList2 (42 :: Integer)) >>
print (isList [42]) >>
print (isList2 [42])
In this case, there's enough information to pick a most-specific instance, so OverlappingInstances does its thing.
The following code does the trick without requiring IncoherentInstances:
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverlappingInstances #-}
class IsList a where
isList :: a -> Bool
instance IsList a where
isList x = False
instance IsList [a] where
isList x = True
isList2 :: (IsList a) => a -> Bool
isList2 = isList
main = do
print (isList (42 :: Int))
print (isList [42 :: Int])
print (isList2 (42 :: Int))
print (isList2 [42 :: Int])
I'd recommend not using IncoherentInstances, it seems to cause a lot of trouble, as you can silently call different overloads depending on context quite easily.

Resources