Using a default implementation of typeclass method to omit an argument - haskell

I want to be able to define a (mulit-parameter-) typeclass instance whose implementation of the class's method ignores one of its arguments. This can be easily done as follows.
instance MyType MyData () where
specific _ a = f a
As I'm using this pattern in several places, I tried to generalize it by adding a specialized class method and adequate default implementations. I came up with the following.
{-# LANGUAGE MultiParamTypeClasses, AllowAmbiguousTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
class MyType a b where
specific :: b -> a -> a
specific = const dontCare
dontCare :: a -> a
dontCare = specific (undefined :: b)
{-# MINIMAL specific | dontCare #-}
This however yields the error Could not deduce (MyType a b0) arising from a use of ‘dontCare’ [..] The type variable ‘b0’ is ambiguous. I don't see why the latter should be the case with the type variable b being scoped from the class signature to the method declaration. Can you help me understand the exact problem that arises here?
Is there another reasonable way to achieve what I intended, namely to allow such trimmed instances in a generic way?

The problem is in the default definition of specific. Let's zoom out for a second and see what types your methods are actually given, based on your type signatures.
specific :: forall a b. MyType a b => b -> a -> a
dontCare :: forall a b. MyType a b => a -> a
In the default definition of specific, you use dontCare at type a -> a. So GHC infers that the first type argument to dontCare is a. But nothing constrains its second type argument, so GHC has no way to select the correct instance dictionary to use for it. This is why you ended up needing AllowAmbiguousTypes to get GHC to accept your type signature for dontCare. The reason these "ambiguous" types are useful in modern GHC is that we have TypeApplications to allow us to fix them. This definition works just fine:
class MyType a b where
specific :: b -> a -> a
specific = const (dontCare #_ #b)
dontCare :: a -> a
dontCare = specific (undefined :: b)
{-# MINIMAL specific | dontCare #-}
The type application specifies that the second argument is b. You could fill in a for the first argument, but GHC can actually figure that one out just fine.

Related

Deriving Via: Cannot derive well-kinded instance

I am encountering this error when I try to derive an instance.
Cannot derive well-kinded instance of form ‘HFunctor (ControlFlowCMD ...)’
Class ‘HFunctor’ expects an argument of kind ‘(* -> *, *)
-> * -> *’
• In the newtype declaration for ‘ControlFlowCMD’
I am trying to do this:
newtype ControlFlowCMD fs a = ControlFlowCMD (ControlCMD fs a)
deriving HFunctor via (ControlCMD fs a)
You can see the data type and instance I am basing my type on and trying to derive here, on line 278. I am not that used to using deriving via - could anyone explain what this error means and how I would fix it?
The problem was that (* -> *, *) or, equivalently, (Type -> Type, Type) is a kind-level tuple, and one must enable the DataKinds and PolyKinds extensions in order to handle it. (I'm not completely sure why PolyKinds is needed though; maybe it's to allow more general kind inference.)
With datatypes having complex kinds, it's often a good idea to enable StandaloneKindSignatures and give the kind signature explicitly:
import Data.Kind
type ControlFlowCMD :: (Type -> Type, Type) -> Type -> Type
newtype ControlFlowCMD fs a = ...

Haskell - GADTs pattern match with class constraints

Consider the following example
{-# LANGUAGE DataKinds, GADTs #-}
data Phantom = A | B
data Foo (a :: Phantom) where
FooA :: Foo 'A
FooB :: Foo 'B
class PhantomConstraint (a :: Phantom)
instance PhantomConstraint 'A -- Note: No instance for 'B
someFunc :: PhantomConstraint a => Foo a -> ()
someFunc FooA = ()
If I do something like this GHC complains that the pattern matches are inexhaustive for someFunc, however, if I do try and include the case for FooB (which I don't want to do for domain specific reasons) it complains that it can't deduce the instance of PhantomConstraint for Foo 'B
Is there any way to make GADT pattern matching aware of typeclass constraints such that it eliminates required arms of pattern matching?
EDIT: More details around what I want to do. I have a bucket of types that are all somewhat related but have different properties. In the OO world this is what people use subtyping and inheritance for. However in the FP community, the consensus seems to be that there is no real good way to do subtyping, so in this case I need to hack around it. As such I have a GADT that unifies all of the types, but with different parameters on that type. I then proceed to write different typeclasses and typeclass instances on the type parameters (enabled by datakinds, no term representation). I want to be able to express that some of these types from the datakinds have a property that others don't, but they all do share certain common properties so I don't really want to break up the type. The only other option I can foresee is to create a taxonomy on the type part, but then the DataKinds types get messed up.
I can't reproduce the issue. This loads without warnings or errors in GHCi 8.4.3.
{-# LANGUAGE GADTs, DataKinds, KindSignatures #-}
{-# OPTIONS -Wall #-}
module GADTwarning2 where
data Phantom = A | B
data Foo (a :: Phantom) where
FooA :: Foo 'A
FooB :: Foo 'B
class PhantomConstraint (a :: Phantom)
instance PhantomConstraint 'A -- Note: No instance for 'B
someFunc :: PhantomConstraint a => Foo a -> ()
someFunc FooA = ()
someFunc FooB = ()
As luqui explained in a comment, we can't avoid the FooB case, since type classes are open, and another instance could be added later on by another module, making the pattern match non exhaustive.
If you are absolutely sure you don't need any other instances except the one for A, you can try to use
class a ~ 'A => PhantomConstraint (a :: Phantom)
Or, if the index a can be 'A or 'B, but never a third constructor 'C, then we can try to reify this fact:
class PhantomConstraint (a :: Phantom) where
aIsAOrB :: Either (a :~: 'A) (a :~: 'B)
and then exploit this member later on.

Is this use of GADTs fully equivalent to existential types?

Existentially quantified data constructors like
data Foo = forall a. MkFoo a (a -> Bool)
| Nil
can be easily translated to GADTs:
data Foo where
MkFoo :: a -> (a -> Bool) -> Foo
Nil :: Foo
Are there any differences between them: code which compiles with one but not another, or gives different results?
They are nearly equivalent, albeit not completely so, depending on which extensions you turn on.
First of all, note that you don't need to enable the GADTs extension to use the data .. where syntax for existential types. It suffices to enable the following lesser extensions.
{-# LANGUAGE GADTSyntax #-}
{-# LANGUAGE ExistentialQuantification #-}
With these extensions, you can compile
data U where
U :: a -> (a -> String) -> U
foo :: U -> String
foo (U x f) = f x
g x = let h y = const y x
in (h True, h 'a')
The above code also compiles if we replace the extensions and the type definition with
{-# LANGUAGE ExistentialQuantification #-}
data U = forall a . U a (a -> String)
The above code, however, does not compile with the GADTs extension turned on! This is because GADTs also turns on the MonoLocalBinds extension, which prevents the above definition of g to compile. This is because the latter extension prevents h to receive a polymorphic type.
From the documentation:
Notice that GADT-style syntax generalises existential types (Existentially quantified data constructors). For example, these two declarations are equivalent:
data Foo = forall a. MkFoo a (a -> Bool)
data Foo' where { MKFoo :: a -> (a->Bool) -> Foo' }
(emphasis on the word equivalent)
The latter isn't actually a GADT - it's an existentially quantified data type declared with GADT syntax. As such, it is identical to the former.
The reason it's not a GADT is that there is no type variable that gets refined based on the choice of constructor. That's the key new functionality added by GADTs. If you have a GADT like this:
data Foo a where
StringFoo :: String -> Foo String
IntFoo :: Int -> Foo Int
Then pattern-matching on each constructor reveals additional information that can be used inside the matching clause. For instance:
deconstructFoo :: Foo a -> a
deconstructFoo (StringFoo s) = "Hello! " ++ s ++ " is a String!"
deconstructFoo (IntFoo i) = i * 3 + 1
Notice that something very interesting is happening there, from the point of view of the type system. deconstructFoo promises it will work for any choice of a, as long as it's passed a value of type Foo a. But then the first equation returns a String, and the second equation returns an Int.
This is what you cannot do with a regular data type, and the new thing GADTs provide. In the first equation, the pattern match adds the constraint (a ~ String) to its context. In the second equation, the pattern match adds (a ~ Int).
If you haven't created a type where pattern-matching can cause type refinement, you don't have a GADT. You just have a type declared with GADT syntax. Which is fine - in a lot of ways, it's a better syntax than the basic data type syntax. It's just more verbose for the easiest cases.

Why do Haskell's scoped type variables not allow binding of type variables in pattern bindings?

I noticed that GHC's ScopedTypeVariables is able to bind type variables in function patterns but not let patterns.
As a minimal example, consider the type
data Foo where Foo :: Typeable a => a -> Foo
If I want to gain access to the type inside a Foo, the following function does not compile:
fooType :: Foo -> TypeRep
fooType (Foo x) =
let (_ :: a) = x
in typeRep (Proxy::Proxy a)
But using this trick to move the type variable binding to a function call, it works without issue:
fooType (Foo x) =
let helper (_ :: a) = typeRep (Proxy::Proxy a)
in helper x
Since let bindings are actually function bindings in disguise, why aren't the above two code snippets equivalent?
(In this example, other solutions would be to create the TypeRep with typeOf x, or bind the variable directly as x :: a in the top-level function. Neither of those options are available in my real code, and using them doesn't answer the question.)
The big thing is, functions are case expressions in disguise, not let expressions. case matching and let matching have different semantics. This is also why you can't match a GADT constructor that does type refinement in a let expression.
The difference is that case matches evaluate the scrutinee before continuing, whereas let matches throw a thunk onto the heap that says "do this evaluation when the result is demanded". GHC doesn't know how to preserve locally-scoped types (like a in your example) across all the potential ways laziness may interact with them, so it just doesn't try. If locally-scoped types are involved, use a case expression such that laziness can't become a problem.
As for your code, ScopedTypeVariables actually provides you a far more succinct option:
{-# Language ScopedTypeVariables, GADTs #-}
import Data.Typeable
import Data.Proxy
data Foo where
Foo :: Typeable a => a -> Foo
fooType :: Foo -> TypeRep
fooType (Foo (x :: a)) = typeRep (Proxy :: Proxy a)

What is the difference between `DeriveAnyClass` and an empty instance?

Using the cassava package, the following compiles:
{-# LANGUAGE DeriveGeneric #-}
import Data.Csv
import GHC.Generics
data Foo = Foo { foo :: Int } deriving (Generic)
instance ToNamedRecord Foo
However, the following does not:
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveAnyClass #-}
import Data.Csv
import GHC.Generics
data Foo = Foo { foo :: Int } deriving (Generic, ToNamedRecord)
The compiler reports:
test.hs:7:50:
No instance for (ToNamedRecord Int)
arising from the first field of ‘Foo’ (type ‘Int’)
Possible fix:
use a standalone 'deriving instance' declaration,
so you can specify the instance context yourself
When deriving the instance for (ToNamedRecord Foo)
This leaves me with two questions: Why isn't the second version identical to the first? And why is the compiler hoping to find an instance for ToNamedRecord Int?
NB: As pointed out by David in the comments, GHC has been updated since I wrote this. The code as written in the question compiles and works correctly. So just imagine everything below is written in the past tense.
The GHC docs say:
The instance context will be generated according to the same rules
used when deriving Eq (if the kind of the type is *), or the rules for
Functor (if the kind of the type is (* -> *)). For example
instance C a => C (a,b) where ...
data T a b = MkT a (a,b) deriving( C )
The deriving clause will
generate
instance C a => C (T a b) where {}
The constraints C a and C (a,b) are generated from the data constructor arguments, but the
latter simplifies to C a.
So, according to the Eq rules, your deriving clause generates...
instance ToNamedRecord Int => ToNamedRecord Foo where
... which is not the same as...
instance ToNamedRecord Foo where
... in that the former is only valid if there's an instance ToNamedRecord Int in scope (which is appears there isn't in your case).
But I find the spec to be somewhat ambiguous. Should the example really generate that code, or should it generate instance (C a, C (a, b)) => instance C (T a b) and let the solver discharge the second constraint? It appears, in your example, that it's generating such constraints even for fields with fully-concrete types.
I hesitate to call this a bug, because it's how Eq works, but given that DeriveAnyClass is intended to make it quicker to write empty instances it does seem unintuitive.

Resources