How to make this example of pseudo-ducktyping type unambiguously without annotations - haskell

I wanted to demonstrate the idea of statically verifiable duck typing in Haskell using MultiParamTypeClasses, but I am having trouble avoiding type ambiguity.
Here is the code:
{-# LANGUAGE MultiParamTypeClasses #-}
class HasBar a b where
bar :: b -> a
data Foo = Foo { barBool :: Bool } deriving (Show)
instance HasBar Bool Foo where
bar = barBool
data Bazz = Bazz { barInt :: Int } deriving (Show)
instance HasBar Int Bazz where
bar = barInt
When I load it into GHCi and try to do bar (Foo True) or bar (Bazz 5) I get a Non type-variable argument error and it suggests FlexibleContexts, which just changes the error to an ambiguity error. Now doing something like False || bar (Foo True) works fine. But that doesn't seem like it should be needed as Foo is only a member of the typeclass that returns a Bool.
It seems like the issue is something to do with the possibility of something like:
instance HasBar Int Foo where
bar = const 5
Which would necessitate the types being ambiguous. But if there is just one instance I don't see why there are any issues preventing Haskell from finding out the type (do I need some sort of extension). If I can't do it that way then is there an alternative to MultiParamTypeClasses that only allows one instance and would allow for this pseudo-ducktyping type of thing to work?

the problem is that it's not only looking for what it sees but what it can know - and there is the possibility for you to make an instance that will be HasBar Int Foo as well so it complains
You can get rid of this with either FunctionalDependencies or TypeFamilies
using functional dependencies
the first extension is probably the way to go here (you don't have to change much of your code). You can basically tell GHCi, that the type b in your class/constraint will be enough to decide the type a.
if you change it to:
{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-}
class HasBar a b | b -> a where
bar :: b -> a
it'll work (you need the FlexibleContexts only in GHCi
λ> :set -XFlexibleContexts
λ> bar (Foo True)
True
using type families
In case you are interested here is the same thing with type-families and associated types:
{-# LANGUAGE TypeFamilies #-}
class HasBar a where
type Bar a :: *
bar :: a -> Bar a
data Foo = Foo { barBool :: Bool } deriving (Show)
instance HasBar Foo where
type Bar Foo = Bool
bar = barBool
data Bazz = Bazz { barInt :: Int } deriving (Show)
instance HasBar Bazz where
type Bar Bazz = Int
bar = barInt
note that you don't need the MultiParamTypeClasses any more

Related

Haskell: interaction between ConstraintKinds, and TypeSynonymInstances

I'm getting an unexpected error when trying to compile a small Haskell file with GHC 8.6.1 when using ConstraintKinds and TypeSynonymInstances.
I'd like to make a class that takes a class as a parameter, and I'd like to use an alias when writing an instance. Here's the code:
{-# LANGUAGE ConstraintKinds, KindSignatures, TypeSynonymInstances #-}
module TypeAlias where
import Data.Kind
class Foo a
class Bar a
class Baz (c :: * -> Constraint)
instance Baz Foo -- compiles
instance Baz Bar -- compiles
type FooBar a = (Foo a, Bar a) -- compiles
instance Baz FooBar -- fails!
-- TypeAlias.hs:17:10-19: error:
-- • The type synonym ‘FooBar’ should have 1 argument, but has been given none
-- • In the instance declaration for ‘Baz FooBar’
-- |
-- 17 | instance Baz FooBar
-- | ^^^^^^^^^^
The error is surprising because, as far as I can tell, FooBar has the expected kind, namely * -> Constraint, but the compiler says it should be fed an argument.
Is it even possible to use a constraint alias in an instance declaration as I am trying here? If so, how do I make sense of the seemingly contradictory error message?
(I know I can simply declare FooBar as a class instead of an alias, but I really don't want to because I'd also want an instance and at that point I'd have to pull in UndecidableInstances.)
Turns out, Ed Kmett answered my question a year ago. I can't do it with type aliases, but using UndecidableInstances should be benign for this particular situation:
https://www.reddit.com/r/haskell/comments/5zjwym/when_is_undecidableinstances_okay_to_use/
Here's how Kmett might suggest fixing the above example:
{-# LANGUAGE ConstraintKinds, FlexibleInstances,
KindSignatures, UndecidableInstances #-}
module NotTypeAlias where
import Data.Kind
class Foo a
class Bar a
class Baz (c :: * -> Constraint)
instance Baz Foo -- compiles
instance Baz Bar -- compiles
class (Foo a, Bar a) => FooBar a
instance (Foo a, Bar a) => FooBar a -- compiles
instance Baz FooBar -- compiles
Kmett argues that if the instance of FooBar we provide is the sole instance ever in scope, then the type checker won't fall into an infinite loop from our use of UndecidableInstances. I'm satisfied to take him at his word.

Why is this type variable ambiguous, although it should be in scope?

Consider the following code:
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ScopedTypeVariables #-}
class Foo a where
type Bar a
class Foo a => Foo2 a where
bar :: Bar a
It gives the following error message in GHC 8.2:
error:
• Couldn't match expected type ‘Bar a’ with actual type ‘Bar a0’
NB: ‘Bar’ is a type function, and may not be injective
The type variable ‘a0’ is ambiguous
• In the ambiguity check for ‘bar’
To defer the ambiguity check to use sites, enable AllowAmbiguousTypes
When checking the class method: bar :: forall a. Foo2 a => Bar a
In the class declaration for ‘Foo2’
|
7 | bar :: Bar a
| ^^^^^^^^^^^^
What's the problem? Why does it universally quantify over a? If I change the last line to
bar :: a
the problem vanishes. Why doesn't it have the type variable a in scope otherwise?
(I looked through all "ambiguous type variable" questions now, but nothing seems to help.)
Imagine you make two Foo instances with the same associated type, and then defined
..
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE TypeApplications #-}
..
instance Foo Int where type Bar Int = Bool
instance Foo Float where type Bar Float = Bool
instance Foo2 Int where
bar :: Bool
bar = False
instance Foo2 Float where
bar :: Bool
bar = True
This means that the type of bar is not enough to decide between the Foo2 Int and Foo2 Float instances.
bar :: Foo2 a => Bar a
GHC will attempt to infer the type a for you but if you ask for
bar :: Bool
it has no way to pick between Int / Float or any other instance that may come later. You must explicitly specify the type with -XTypeApplications
>>> :set -XTypeApplications
>>
>> bar #Int
False
>> bar #Float
True
Edit: If every instance of Foo is a different type (Foo is injective) you can specify that the result determines the instance type with this syntax .. = res | res -> a
..
{-# Language TypeFamilyDependencies #-}
class Foo a where
type Bar a = res | res -> a
You can't define Bar Int and Bar Float both equal to Bool. If we only define Foo Int and Foo2 Int then bar :: Bool is enough to let GHC know you're looking for bar #Int = False.

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.

Inclusion of typeclasses with default implementation in Haskell

Consider the following definitions:
class Foo a where
foo :: a -> Int
class Bar a where
bar :: a -> [Int]
Now, how do I say "every Foo is also a Bar, with bar defined by default as bar x = [foo x]" in Haskell?
(Whatever I try, the compiler gives me "Illegal instance declaration" or "Constraint is no smaller than the instance head")
Btw, I can define my Foo and Bar classes in some other way, if this would help.
class Foo a where
foo :: a -> Int
-- 'a' belongs to 'Bar' only if it belongs to 'Foo' also
class Foo a => Bar a where
bar :: a -> [Int]
bar x = [foo x] -- yes, you can specify default implementation
instance Foo Char where
foo _ = 0
-- instance with default 'bar' implementation
instance Bar Char
As the automatic definition of a Bar instance through a Foo instance can lead to undecidable cases for the compiler - i.e. one explicit instance and one through Foo conflicting with each other - , we need some special options to allow the desired behaviour. The rest through is quite straigtforward.
{-# LANGUAGE FlexibleInstances, UndecidableInstances #-}
class Foo a where
foo :: a -> Int
class Bar a where
bar :: a -> [Int]
instance (Foo a) => Bar a where
bar x = [foo x]
Generally speaking you don't model things with type classes this way[*] - i.e. an instance of a type class should always be some concrete type, though that type itself can be parameteric - e.g. the Show instance for pair has this signature:
instance (Show a, Show b) => Show (a,b) where
Some of the approaches to "Generics" allow you to model a general base case and then have type specific exceptional cases. SYB3 allowed this - perhaps unfortunately SYB3 isn't the common practice Generics library it is Data.Data / Data.Generics which I think is SYB1.
[*] In the wild the story is a little more complicated - as Dario says UndecidableInstances can enable it.

Constraining the return type to a Context

Here are my attempts so far:
module Main where
data FooT = One | Two deriving (Show, Read)
{-
That is what I want
foo :: (Show a, Read a) => a
foo = One
-}
--class Footable (Show a, Read a) => a where
class Footable a where
--foo2 :: (Show a, Read a) => a
foo2 :: a
instance Footable FooT where
foo2 = One
-- test = print foo2
I want test to compile. I don't think the problem revolves around universal quantification. ghc says that a is a 'strict type-variable' edit (rigid type variable) but I don't really comprehend what this is. The question seems to be related to this
Edit
As I wrote in my comment #sepp2k it's probably about the existential type but I have stumbled over a curious behaviour:
This does compile:
{-# LANGUAGE OverlappingInstances, FlexibleInstances, OverlappingInstances,
UndecidableInstances, MonomorphismRestriction, PolymorphicComponents #-}
{-# OPTIONS_GHC -fno-monomorphism-restriction #-}
module Main where
class (Num a) => Numable a where
foo2 :: a
instance (Num a) => Numable a where
foo2 = 1
instance Numable Int where
foo2 = 2
instance Numable Integer where
foo2 = 3
--test = foo2 + foo2 -- This does NOT compile (ambiguous a)
test = (foo2::Integer) + foo2 --this works
but this does not (`a' is a rigid type variable message)
{-# LANGUAGE OverlappingInstances, FlexibleInstances, OverlappingInstances,
UndecidableInstances, MonomorphismRestriction, PolymorphicComponents #-}
{-# OPTIONS_GHC -fno-monomorphism-restriction #-}
module Main where
data FooT = One | Two deriving (Show, Read)
data BarT = Ten deriving (Show, Read)
class (Show a, Read a) => Footable a where
foo2 :: a
instance (Show a, Read a) => Footable a where
foo2 = Ten
instance Footable FooT where
foo2 = One
main = print foo2
that's so because 1 :: (Num t) => t. Can I define something (typeconstructor, consts dunno) like that?
When I uncomment the definition of test and try to compile your code, I get "ambiguous type variable". Nothing about strictness. To understand why this is ambiguous consider this:
module Main where
data FooT = One | Two deriving (Show, Read)
data BarT = Three | Four deriving Show
class Footable a where
foo2 :: a
instance Footable FooT where
foo2 = One
instance Footable BarT where
foo2 = Three
main = print foo2 -- Should this print One or Three?
Of course in your code there is only one instance of Footable, so haskell could in theory infer that you want to use the foo2 defined for FooT because that's the only instance in scope. However if it did that, the code would break as soon as you import a module that happens to define another instance of Footable, so haskell doesn't do that.
To fix your problem you need to annotate foo2 with its type like so:
module Main where
data FooT = One | Two deriving (Show, Read)
class Footable a where
foo2 :: a
instance Footable FooT where
foo2 = One
main = print (foo2 :: FooT)
To require that all Footables be instances of Show and Read simply do:
class (Show a, Read a) => Footable a where
foo2 :: a
Like you did in your comments, but without specifying the constraint again in the signature of foo2.
As sepp2k said, Ghc can't guess the return type of foo2. Do constraint it (which is the title of your question) add an inline type signature.
test = print (foo2 :: FooT)

Resources