In the example below, I'm trying to make foo return its "expected" polymorphic output type. The idea is that foo returns a polymorphic value and an existential type, and then bar specifies the type of the tuple to be the hidden type. (Of course this only works if the type in bar is also existential, which is true in my case.) The following example compiles:
{-# LANGUAGE GADTs, ScopedTypeVariables #-}
module Foo where
import Data.Proxy
import Data.Typeable
data HiddenType where
Hidden :: (Typeable a) => Proxy a -> HiddenType
foo :: (i,HiddenType)
foo = (undefined, Hidden (Proxy::Proxy Int))
data Foo where
Foo :: i -> Foo
bar :: Foo
bar =
let (x,h) = foo
in case h of
(Hidden (p::Proxy i)) -> Foo (x :: i)
I really need a Typeable constraint on foo:
foo :: (Typeable i) => (i,HiddenType)
When I add that constraint (no other changes), I get these errors:
Foo.hs:20:15:
No instance for (Typeable t0) arising from a use of ‘foo’
The type variable ‘t0’ is ambiguous
Relevant bindings include x :: t0 (bound at Foo.hs:20:8)
Note: there are several potential instances:
instance [overlap ok] Typeable ()
-- Defined in ‘Data.Typeable.Internal’
instance [overlap ok] Typeable Bool
-- Defined in ‘Data.Typeable.Internal’
instance [overlap ok] Typeable Char
-- Defined in ‘Data.Typeable.Internal’
...plus 14 others
In the expression: foo
In a pattern binding: (x, h) = foo
In the expression:
let (x, h) = foo
in case h of { (Hidden (p :: Proxy i)) -> Foo (x :: i) }
Foo.hs:22:35:
Couldn't match expected type ‘a’ with actual type ‘t0’
because type variable ‘a’ would escape its scope
This (rigid, skolem) type variable is bound by
a pattern with constructor
Hidden :: forall a. Typeable a => Proxy a -> HiddenType,
in a case alternative
at Foo.hs:22:6-24
Relevant bindings include
p :: Proxy a (bound at Foo.hs:22:14)
x :: t0 (bound at Foo.hs:20:8)
In the first argument of ‘Foo’, namely ‘(x :: i)’
In the expression: Foo (x :: i)
Failed, modules loaded: none.
I understand that constraints turn into arguments in core, so it seems to me that the issue here is that GHC can't handle pattern bindings for GADTs. If it could, I could use a recursive let to say something like:
bar :: Foo
bar =
let (x :: i,h) = foo
(Hidden (p::Proxy i)) = h
in Foo x
That should make the constraint in scope, providing the extra argument to foo. My intent here is that h contains some (hidden) concrete type i, which should be used as the concrete type for the polymorphic function
GHC complains:
Foo.hs:19:8:
You cannot bind scoped type variable ‘i’
in a pattern binding signature
In the pattern: x :: i
In the pattern: (x :: i, h)
In a pattern binding:
(x :: i, h) = foo
Foo.hs:20:8:
My brain just exploded
I can't handle pattern bindings for existential or GADT data constructors.
Instead, use a case-expression, or do-notation, to unpack the constructor.
In the pattern: Hidden (p :: Proxy i)
In a pattern binding: (Hidden (p :: Proxy i)) = h
In the expression:
let
(x :: i, h) = foo
(Hidden (p :: Proxy i)) = h
in Foo x
The assumptions for my use case are that
1. foo computes i and the HiddenType simultaneously
2. The value of the hidden type involves (at least partial) computation of the first tuple element. This means I do not want to call foo twice in bar (once to get the HiddenType, and once to use that type to bind the first tuple element).
Is there some way to make the definition of bar possible in the presence of a constraint on foo?
I suppose the problem is that foos return value isn't actually polymorphic. foo itself is polymorphic but the returned value must exist at a specific type. Unfortunately, the type you want to use isn't available yet and cannot be brought into scope at foos call site because of the circular reference. If we write out the definition of foo in pseudo-core, the problem is clear:
foo (# iType) _ = (undefined # iType, HiddenType...)
Here # iType is a type argument. We need to do foo's type application first (and the dictionary application, which is unused) before getting the HiddenType, so there's no way to make this work as-is.
Fortunately, there is a way to convince ghc that foo should return an actual polymorphic value:
{-# LANGUAGE GADTs, ScopedTypeVariables #-}
{-# LANGUAGE ImpredicativeTypes #-}
module Foo where
import Data.Proxy
import Data.Typeable
data HiddenType where
Hidden :: (Typeable a) => Proxy a -> HiddenType
foo :: (forall i. Typeable i => i,HiddenType)
foo = (undefined, Hidden (Proxy::Proxy Int))
data Foo where
Foo :: i -> Foo
bar =
let (x,h) = foo
in case h of
Hidden p -> Foo (x `asProxyTypeOf` p)
If you're familiar with higher-rank types (e.g. the RankNTypes extension), you can think of ImpredicativeTypes as something similar, except for data structures instead of functions. For example, without ImpredicativeTypes you can write:
list1 :: forall t. Typeable t => [t]
which is the type of a list that contains all values of type t, for some t with a Typeable constraint. Even though it's polymorphic, every element of the list will be of the same type! If instead you wish to move the forall inside the list, so that every element may be a different type t, ImpredicativeTypes will allow this:
list2 :: [forall t. Typeable t => t]
It's not a commonly-enabled extension, but it is occasionally useful.
The core for the impredicative version of foo is a bit different as well:
foo = (\(# iType) _ -> undefined # iType, HiddenType...)
You can see that this allows for x to be polymorphic as desired if you add an annotation to the let:
bar :: Foo
bar =
let (x :: forall i. Typeable i => i,h) = foo
in case h of
Hidden p -> Foo (x `asProxyTypeOf` p)
This allows you to delay the instantiation of x at the hidden type until later, when it's available. You still need to box it up inside Foo or another Hidden though, as ghc won't allow the type to escape from under the first Hidden pattern match.
Related
Why doesn't using an associated type synonym in a signature imply the corresponding constraint?
E.g. why doesn't the following compile:
{-# LANGUAGE TypeApplications, ScopedTypeVariables, TypeFamilies, AllowAmbiguousTypes #-}
class MyClass a where
type AssociatedType a
bar :: Int
foo :: forall a. AssociatedType a -> Int
foo _ = bar #a
ghc 8.6.5 gives the following error:
error:
* No instance for (MyClass a) arising from a use of `bar'
Possible fix:
add (MyClass a) to the context of
the type signature for:
foo :: forall a. AssociatedType a -> Int
* In the expression: bar #a
In an equation for `foo': foo _ = bar #a
|
8 | foo _ = bar #a
| ^^^^^^
GHC documentation doesn't seem to mention this aspect.
If it implied the constraint, then anybody using values of the associated value in any way whatsoever would need to have the constraint in scope. For example,
sort :: Ord a => [a] -> [a]
obviously knows nothing about MyClass, yet it should be possible to use it as sort :: [AssociatedType a] -> [AssociatedType a] provided that you have Ord (AssociatedType a) in the calling scope.
To get behaviour like the one you seem to be looking for, you want a wrapped constraint rather than an associated type. That can't be done with -XTypeFamilies, but it can be done with -XGADTs:
{-# LANGUAGE GADTs #-}
class MyClass a where
bar :: Int
data MyClassWitness a where
MyClassWitness :: MyClass a => MyClassWitness a
foo :: ∀ a. MyClassWitness a -> Int
foo MyClassWitness = bar #a
Instead of a self-rolled wrapper you can also use the one from the constraints library:
import Data.Constraint
foo :: ∀ a . Dict (MyClass a) -> Int
foo Dict = bar #a
Important in both cases is that you actually pattern-match on the GADT constructor, as only that actually brings the constraint into scope. This would not work:
foo :: ∀ a . Dict (MyClass a) -> Int
foo _ = bar #a
Because just using the type does not require the type constraint. For instance, this compiles:
foo :: forall a. AssociatedType a -> Int
foo _ = 42
At runtime, there is no need to pass a typeclass dictionary to this function, which is coherent with the lack of the constraint during type checking.
In your code, the constraint is needed because you are using bar, not because you are using the type.
I have some classes and their instances. The example shows some nonsensical classes. Their exact nature is not important.
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE FlexibleInstances #-}
class Foo a where
foo :: a -> Int
class Bar a where
bar :: a -> String
instance Foo Int where
foo x = x
instance Foo String where
foo x = length x
instance Bar Int where
bar x = show x
instance Bar String where
bar x = x
OK, now I want to create some existential types that hide these classes behind some datatype façade, so I don't have to deal with constraints. (I know existential types are considered an anti-pattern, please don't explain this to me).
data TFoo = forall a. Foo a => TFoo a
instance Foo TFoo where
foo (TFoo x) = foo x
data TBar = forall a. Bar a => TBar a
instance Bar TBar where
bar (TBar x) = bar x
Obviously there's some boilerplate in there. I want to abstract it away.
{-# LANGUAGE ConstraintKinds #-}
data Obj cls = forall o. (cls o) => Obj o
So instead of several existential types I have just one, parametrised by a typeclass. So far so good.
Now how do I perform operations on Obj a? The obvious attempt
op f (Obj a) = f a
fails because the type variable could escape.
existential.hs:31:18: error:
• Couldn't match expected type ‘o -> p1’ with actual type ‘p’
because type variable ‘o’ would escape its scope
This (rigid, skolem) type variable is bound by
a pattern with constructor:
Obj :: forall (cls :: * -> Constraint) o. cls o => o -> Obj cls,
in an equation for ‘call’
at existential.hs:31:9-13
• In the expression: f k
In an equation for ‘call’: call f (Obj k) = f k
• Relevant bindings include
k :: o (bound at existential.hs:31:13)
f :: p (bound at existential.hs:31:6)
call :: p -> Obj cls -> p1 (bound at existential.hs:31:1)
|
31 | call f (Obj k) = f k
| ^^^
Failed, no modules loaded.
I kinda understand why this happens. But with real invocations like call foo and call bar the type variable wouldn't escape. Can I convince the compiler of it? Perhaps I somehow can express the type u -> v where v does not mention u (which really should be the type of f)? If not, what other ways to deal with the situation are there? I guess I could generate something with TemplateHaskell but I still cannot wrap my head around it.
Your code works fine; the compiler just needs some help with its type.
Obj hides the type of its contents, which means that op's argument f must be polymorphic (that is, it can't scrutinise its argument). Turn on RankNTypes:
op :: (forall a. cls a => a -> r) -> Obj cls -> r
op f (Obj x) = f x
You have to give the type signature in full because GHC can't infer higher-rank types.
Existentially quantifying over a class like this is usually not the best way to design a given program.
In the following snippet (I have abstracted all other trivial parts)
data T s = T (s -> s)
foo :: T s -> s -> s
foo (T f) x = bar x where
bar :: s -> s
bar a = f a
I got following error
Couldn't match expected type `s1' with actual type `s'
`s1' is a rigid type variable bound by
the type signature for bar :: s1 -> s1 at /tmp/test.hs:5:12
`s' is a rigid type variable bound by
the type signature for foo :: T s -> s -> s at /tmp/test.hs:3:8
In the return type of a call of `f'
In the expression: f a
In an equation for `bar': bar a = f a
my guess was that the type variables in bar's signature don't share the namespace with foo, so the compiler can't infer that the two s actually mean the same type.
Then I found this page Scoped type variables, which suggests that I can use {-# LANGUAGE ScopedTypeVariables #-}, which didn't help. I got the same error.
Are type variables in “where” clauses in the same namespace with their parents?
No*. This gets a little bit easier if you think of foo :: s -> s in terms of foo :: forall s. s -> s. After all, a type variable indicates that the function works for any type s. Let's add explicit quantifications to your code:
{-# LANGUAGE ExplicitForAll #-}
data T s = T (s -> s)
foo :: forall s. T s -> s -> s
foo (T f) x = bar x where
bar :: forall s. s -> s
bar a = f a
As you can see, there are two forall s. there. But the one in bar is wrong. After all, you cannot choose any s there, but the one already used in s. This can be done by enabling ScopedTypeVariables:
{-# LANGUAGE ScopedTypeVariables #-}
data T s = T (s -> s)
-- vvvvvvvv explicit here
foo :: forall s. T s -> s -> s
foo (T f) x = bar x where
-- vvvvvv same as above here
bar :: s -> s
bar a = f a
However, there are some tricks to get rid of ScopedTypeVariables. For example the following in this case:
data T s = T (s -> s)
foo :: T s -> s -> s
foo (T f) x = (bar `asTypeOf` idType x) x where
bar a = f a
idType :: a -> a -> a
idType a _ = a
-- For completion, definition and type of 'asTypeOf'
-- asTypeOf :: a -> a -> a
-- asTypeOf x _ = x
For any x :: s the term idType x has type s -> s, and asTypeOf enforces both to have the same type.
Depending on your actual code, something like this might be more or less feasible.
* Well, in this case, since it's possible to use ScopedTypeVariables, see later part of the answer.
ScopedTypeVariables are indeed the solution, but there's an extra requirement to use them: You must put explicit foralls in the type signatures declaring the variables you want to scope, like this:
foo :: forall s. T s -> s -> s
This is so that the meaning of signatures in code doesn't depend on whether the extension is enabled or not.
Is there a Haskell language extension for the type class method to "use the only potential instance available"?
I want to compile the following
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
class Foo a r where
foo :: a -> r
instance Foo a (Bool -> a) where
foo x _ = x
-- This compiles
-- bar :: Int -> Bool
-- This does not
bar :: a -> Bool
bar _ = True
use :: Bool
use = bar $ foo _5 True
where
_5 :: Int
_5 = 5
Now I get the following error:
No instance for (Foo Int (Bool -> r0))
(maybe you haven't applied enough arguments to a function?)
arising from a use of ‘foo’
The type variable ‘r0’ is ambiguous
Note: there is a potential instance available:
instance Foo a (Bool -> a) -- Defined at tests/pos/Fixme.hs:9:10
But since there is only one potential instance available, is there a way to force ghc to use that instance? Or is there a way to declare some instance as a default instance when types are ambiguous?
The standard trick is to make your instance more polymorphic, thus:
instance (a ~ b, bool ~ Bool) => Foo a (bool -> b) where
foo x _ = x
This precludes you from writing other function instances, but makes it clear what types to use when a function instance is wanted. You will need to turn on the TypeFamilies extension to do this. In your specific case you may be able to get away with just instance a ~ b => Foo a (Bool -> b), which would allow further function instances with other argument types, at the cost of more frequent ambiguity errors.
See a previous answer of mine for some more explanation of this trick.
I'm using a typed tagless final encoding in an interpreter. Unfortunately, I'm having issues with the typechecking phase. The minimal testcase is as follows:
{-# LANGUAGE RankNTypes, ExistentialQuantification, NoMonomorphismRestriction #-}
class Program repr where
...
intro1 :: repr a (a, ())
...
data DynTerm repr = forall x y. (Typeable x, Typeable y) => DynTerm (repr x y)
ghci> DynTerm intro1
This produces the following error:
Could not deduce (Typeable x0) arising from a use of `DynTerm'
from the context (Program repr)
bound by the inferred type of it :: Program repr => DynTerm repr
at <interactive>:3:1-14
The type variable `x0' is ambiguous
Possible fix: add a type signature that fixes these type variable(s)
Note: there are several potential instances:
instance Typeable Void -- Defined in `Data.Void'
instance [overlap ok] Typeable ()
-- Defined in `Data.Typeable.Internal'
instance [overlap ok] Typeable Bool
-- Defined in `Data.Typeable.Internal'
...plus 25 others
In the expression: DynTerm intro1
In an equation for `it': it = DynTerm intro1
I expected the compiler to reason as follows:
Attempt to unify a with x.
Add Typeable a to the list of constraints (I can manually add this through a type annotation, which makes no difference).
Succeed.
Attempt to unify (a, ()) with y.
Note that since we're assuming Typeable a, Typeable (a, ()) also holds.
Succeed.
However, it seems to be failing on unifying x.
When constructing a value of type DynTerm using the DynTerm constructor, GHC has to know the concrete types x and y in order to decide which Typeable dictionaries should be packed in. In your test expression, you are not providing sufficient type information to determine concrete types, therefore you get an error that certain type variables are ambiguous. It works if you specifically pick a concrete Typeable type.
Example (with ScopedTypeVariables):
test :: forall repr. Program repr => DynTerm repr
test = DynTerm (intro1 :: repr Int (Int, ()))
As kosmikus noted, ExistentialQuantification means that you will abstract over the type variable, but the implementer of your data type must pick a single, monomorphic type:
When a value of this type is constructed, s will be instantiated to some concrete type. When such a value is analysed, s is abstract.
Consider the following:
data D = forall a . Show a => D (a -> String)
-- test0 = D show -- Invalid!
test1 = D (show :: () -> String)
data E = E (forall a . Show a => a -> String)
test2 = E show -- Invalid!
-- test3 = E (show :: () -> String)
So perhaps you want
data DynTerm repr = DynTerm (forall x y. (Typeable x, Typeable y) => repr x y)
But this still won't work with intro1 - it is not sufficiently polymorphic ((a,()) is more specific than x). If you had intro2 :: Program repr => repr x y you could write DynTerm intro2.