Using the Additive Class from the Numeric Prelude leads to Overlapping Instances - haskell

While trying to define some mathematical objects using the Numeric prelude I've run into a problem. The Additive typeclass defines an instance
instance Additive.C v => Additive.C [v]
Which I read "if v is Additive, [v] is too" (apparently I was wrong here). It's implemented something like
(+) x y = map (\(a,b) -> a + b) $ zip x y
So that [1,2,3] + [4,5,6] = [5,7,9] which is useless for what I want to do. I assumed I wouldn't have a problem as my v type isn't Additive. Unfortunately I still got an overlapping instances error which I found very confusing. I've did a little reading and I now understand that for some reason, Haskell ignores everything before the "=>" bit so I should have read the default instance as "any list is potentially additive in the sense of the default instance". I've tried using OverlappingInstances despite the fact that this extension has the reputation of being "dangerous", but even that doesn't seem to help.
Here is my testcase.
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE MultiParamTypeClasses,FlexibleInstances #-}
{-# LANGUAGE OverlappingInstances #-} --This doesn't seem to help
import NumericPrelude
import qualified Algebra.Additive as Additive
data Test = Red | Green | Blue deriving Show
instance Additive.C [Test] where
zero = undefined
(+) = undefined
negate = undefined
test = [Red] + [Green] + [Blue]
Produces the error (Update: this appears to only happen in older versions of GHC. version 7.2.2 seems to accept it):
Overlapping instances for Additive.C [Test]
arising from a use of `+'
Matching instances:
instance Additive.C v => Additive.C [v]
-- Defined in Algebra.Additive
instance [overlap ok] Additive.C [Test]
-- Defined at Testcase.hs:10:10-26
In the first argument of `(+)', namely `[Red] + [Green]'
In the expression: [Red] + [Green] + [Blue]
In an equation for `test': test = [Red] + [Green] + [Blue]
Does this mean I can't use lists because I don't want to default instance of Additive? What I really want to do is tell ghc to just forget that default instance, it that possible? If not, I'm not sure where to go from here other than dropping lists.

Edit: As #kosmikus mentioned, your example works well for me, too. I am using ghc 7.4.1.
You cannot make the compiler forget the instance as it is imported as soon as you import the module, the instance is defined in. Note that OverlappingInstances does not tell the compiler to forget an instance but to take the most specify instance that is available.
In order to prevent overlapping instances you can use a type wrapper that is used to distinguish arbitrary lists from the lists you are using. For example, you can define
data TestList = TestList [Test]
Then, you can define a custom instance of the type class for TestList. In most cases, people use record syntax to define an accessor for the list as you have to wrap and unwrap the lists.
data TestList = TestList { list :: [Test] }
In order to reduce the cost of the additional constructor you can use a newtype instead of a data.
newtype TestList = TestList { list :: [Test] }
A newtype may only have a single argument and the compiler basically handles it as if it wasn't there but uses the type information, which the constructor provides, to distinguish your lists from arbitrary lists when choosing the correct instance.

Related

Haskell: Define Show function for a user defined type, which is defined by "type" key word

Let's say I have the type StrInt defined as below
type StrInt = (String, Int)
toStrInt:: Str -> Int -> StrInt
toStrInt str int = (str, int)
I want the Show function to work as below:
Input: show (toStrInt "Hello", 123)
Output: "Hello123"
I have tried to define show as below:
instance Show StrInt where
show (str, int) = (show str) ++ (show int)
But that gives me error:
Illegal instance declaration for ‘Show StrInt’
(All instance types must be of the form (T t1 ... tn)
where T is not a synonym.
Use TypeSynonymInstances if you want to disable this.)
In the instance declaration for ‘Show StrInt’
Any ideas on how to solve this issue?
Appreciate your help!
What you're trying to do is 1. not a good idea to start with, 2. conflicts with the already-existing Show instance and is therefore not possible without OverlappingInstances hackery (which is almost never a good idea), and 3. the error message you're getting is not related to these problems; other class-instances with the same message may be perfectly fine but of course require the extension that GHC asks about.
The Show class is not for generating arbitrary string output in whatever format you feel looks nice right now. That's the purpose of pretty-printing. Show instead is supposed to yield syntactically valid Haskell, like the standard instance does:
Prelude> putStrLn $ show (("Hello,"++" World!", 7+3) :: (String,Int))
("Hello, World!",10)
Prelude> ("Hello, World!",10) -- pasted back the previous output
("Hello, World!",10)
If you write any Show instance yourself, it should also have this property.
Again because (String, Int) already has a Show instance, albeit just one arising from more generic instances namely
instance (Show a, Show b) => Show (a,b)
instance Show a => Show [a]
instance Show Int
declaring a new instance for the same type results in a conflict. Technically speaking this could be circumvented by using an {-# OVERLAPPING #-} pragma, but I would strongly advise against this because doing that kind of thing can lead to very confusing behaviour down the line when instance resolution inexplicably changes based on how the types are presented.
Instead, when you really have a good reason to give two different instances to a type containing given data, the right thing to do is generally to make it a separate type (so it's clear that there will be different behaviour) which just happens to have the same components.
data StrInt' = StrInt String Int
instance Show StrInt' where
...
That actually compiles without any further issues or need for extensions. (Alternatively you can also use newtype StrInt = StrInt (String, Int), but that doesn't really buy you anything and just means you can't bring in record labels.)
Instances of the form instance ClassName TypeSynonym are possible too, and can sometimes make sense, but as GHC already informed you they require the TypeSynonymInstances extension or one that supersedes it. In fact TypeSynonymInstances is not enough if the synonym points to a composite type like a tuple, in that case you need FlexibleInstances (which includes TypeSynonymInstances), an extension I enable all of the time.
{-# LANGUAGE FlexibleInstances #-}
class C
type StrInt = (String, Int)
instance C StrInt

How can I make my type an instance of Arbitrary?

I have the following data and function
data Foo = A | B deriving (Show)
foolist :: Maybe Foo -> [Foo]
foolist Nothing = [A]
foolist (Just x) = [x]
prop_foolist x = (length (foolist x)) == 1
when running quickCheck prop_foolist, ghc tells me that Foo needs to be an instance of Arbitrary.
No instance for (Arbitrary Foo) arising from a use of ‘quickCheck’
In the expression: quickCheck prop_foolist
In an equation for ‘it’: it = quickCheck prop_foolist
I tried data Foo = A | B deriving (Show, Arbitrary), but this results in
Can't make a derived instance of ‘Arbitrary Foo’:
‘Arbitrary’ is not a derivable class
Try enabling DeriveAnyClass
In the data declaration for ‘Foo’
However, I can't figure out how to enble DeriveAnyClass. I just wanted to use quickcheck with my simple function! The possible values of x is Nothing, Just A and Just B. Surely this should be possible to test?
There are two reasonable approaches:
Reuse an existing instance
If there's another instance that looks similar, you can use it. The Gen type is an instance of Functor, Applicative, and even Monad, so you can easily build generators from other ones. This is probably the most important general technique for writing Arbitrary instances. Most complex instances will be built up from one or more simpler ones.
boolToFoo :: Bool -> Foo
boolToFoo False = A
boolToFoo True = B
instance Arbitrary Foo where
arbitrary = boolToFoo <$> arbitrary
In this case, Foo can't be "shrunk" to subparts in any meaningful way, so the default trivial implementation of shrink will work fine. If it were a more interesting type, you could have used some analogue of
shrink = map boolToFoo . shrink . fooToBool
Use the pieces available in Test.QuickCheck.Arbitrary and/or Test.QuickCheck.Gen
In this case, it's pretty easy to just put together the pieces:
import Test.QuickCheck.Arbitrary
data Foo = A | B
deriving (Show,Enum,Bounded)
instance Arbitrary Foo where
arbitrary = arbitraryBoundedEnum
As mentioned, the default shrink implementation would be fine in this case. In the case of a recursive type, you'd likely want to add
{-# LANGUAGE DeriveGeneric #-}
import GHC.Generics (Generic)
and then derive Generic for your type and use
instance Arbitrary ... where
...
shrink = genericShrink
As the documentation warns, genericShrink does not respect any internal validity conditions you may wish to impose, so some care may be required in some cases.
You asked about DeriveAnyClass. If you wanted that, you'd add
{-# LANGUAGE DeriveAnyClass #-}
to the top of your file. But you don't want that. You certainly don't want it here, anyway. It only works for classes that have a full complement of defaults based on Generics, typically using the DefaultSignatures extension. In this case, there is no default arbitrary :: Generic a => Gen a line in the Arbitrary class definition, and arbitrary is mandatory. So an instance of Arbitrary produced by DeriveAnyClass will produce a runtime error as soon as QuickCheck tries to call its arbitrary method.

Overload built in function in Haskell

In Haskell, how can one overload a built in function such as !!?
I originally was trying to figure out how to overload the built in function !! to support by own data types. Specifically, !! is of the type:
[a] -> Int -> a
and I want to preserve it's existing functionality, but also be able to call it where its type signature looks more like
MyType1 -> MyType2 -> MyType3
I originally wanted to do this because MyType1 is like a list, and I wanted to use the !! operator because my operation is very similar to selecting an item from a list.
If I was overloading something like + I could just add an instance of my function to the applicable type class, but I don't think that is an option here.
I'm not convinced I actually even want to overload this function anymore, but I am still interested in how it would be done. Actually, comments on if overloading an operator such as !! is even a good idea would be appreciated as well.
In Haskell, nearly all operators are library-defined. Many of the ones you use the most are defined in the 'standard library' of the Prelude module that is imported by default. Gabriel's answer shows how to avoid importing some of those definitions so you can make your own.
That's not overloading though, because the operator still just means one thing; the new meaning you define for it. The primary method that Haskell provides for overloading, i.e. using an operator in such a way that it has different implementations for different types, is the type class mechanism.
A type class identifies a group of types that support some common functions. When you use those functions with a type, Haskell figures out the correct instance of the type class that applies to your usage and makes sure the correct implementation of the functions is used. Most type classes have just a few functions, some just one or two, that need to be implemented to make a new instance. Many of them offer a lot of secondary functions implemented in terms of the core ones as well, and you can use all of them with a type you make an instance of the class.
It so happens that others have made types that behave quite a bit like lists, and so there's already a type class called ListLike. I'm not sure exactly how close your type is to a list, so it may not be a perfect fit for ListLike, but you should look at it as it will give you a lot of capability if you can make your type a ListLike instance.
You can't actually overload an existing non-typeclass function in Haskell.
What you can do is define a new function in a new type class, which is general enough to encompass both the original function and the new definition you want as an overload. You can give it the same name as the standard function, and avoid importing the standard one. That means in your module you can use the name !! to get both the functionality of your new definition, and the original definition (the resolution will be directed by the types).
Example:
{-# LANGUAGE TypeFamilies #-}
import Prelude hiding ((!!))
import qualified Prelude
class Indexable a where
type Index a
type Elem a
(!!) :: a -> Index a -> Elem a
instance Indexable [a] where
type Index [a] = Int
type Elem [a] = a
(!!) = (Prelude.!!)
newtype MyType1 = MyType1 String
deriving Show
newtype MyType2 = MyType2 Int
deriving Show
newtype MyType3 = MyType3 Char
deriving Show
instance Indexable MyType1 where
type Index MyType1 = MyType2
type Elem MyType1 = MyType3
MyType1 cs !! MyType2 i = MyType3 $ cs !! i
(I've used type families to imply that for a given type that can be indexed, the type of the indices and the type of the elements automatically follows; this could of course be done differently, but going into that in more detail is getting side-tracked from the overload question)
Then:
*Main> :t (!!)
(!!) :: Indexable a => a -> Index a -> Elem a
*Main> :t ([] !!)
([] !!) :: Int -> a
*Main> :t (MyType1 "" !!)
(MyType1 "" !!) :: MyType2 -> MyType3
*Main> [0, 1, 2, 3, 4] !! 2
2
*Main> MyType1 "abcdefg" !! MyType2 3
MyType3 'd'
It should be emphasised that this has done absolutely nothing to the existing !! function defined in the prelude, nor to any other module that uses it. The !! defined here is a new and entirely unrelated function, which just happens to have the same name and to delegate to Prelude.!! in one particular instance. No existing code will be able to start using !! on MyType1 without modification (though other modules you can change can of course import your new !! to get this functionality). Any code that imports this module will either have to module-qualify all uses of !! or else use the same import Prelude hiding ((!!)) line to hide the original one.
Hide the Prelude's (!!) operator and you can define your own (!!) operator:
import Prelude hiding ((!!))
(!!) :: MyType1 -> MyType2 -> MyType3
x !! i = ... -- Go wild!
You can even make a type class for your new (!!) operator if you prefer.

Haskell Ambiguous type error

I have the following definitions
{-# LANGUAGE MultiParamTypeClasses,
FunctionalDependencies,
FlexibleInstances,
FlexibleContexts #-}
import qualified Data.Map as M
class Graph g n e | g -> n e where
empty :: g -- returns an empty graph
type Matrix a = [[a]]
data MxGraph a b = MxGraph { nodeMap :: M.Map a Int, edgeMatrix :: Matrix (Maybe b) } deriving Show
instance (Ord n) => Graph (MxGraph n e) n e where
empty = MxGraph M.empty [[]]
When I try to call empty I get an ambiguous type error
*Main> empty
Ambiguous type variables `g0', `n0', `e0' in the constraint: ...
Why do I get this error? How can I fix it?
You are seeing this type error because Haskell is not provided with sufficient information to know the type of empty.
Any attempt to evaluate an expression though requires the type. The type is not defined yet because the instance cannot be selected yet. That is, as the functional dependency says, the instance can only be selected if type parameter g is known. Simply, it is not known because you do not specify it in any way (such as with a type annotation).
The type-class system makes an open world assumption. This means that there could be many instances for the type class in question and hence the type system is conservative in selecting an instance (even if currently there is only one instance that makes sense to you, but there could be more some other day and the system doesn't want to change its mind just because some other instances get into scope).

Defining an algebra module using constructive-algebra package

The package constructive-algebra allows you to define instances of algebraic modules (like vectorial spaces but using a ring where a field was required)
This is my try at defining a module:
{-# LANGUAGE MultiParamTypeClasses, TypeSynonymInstances #-}
module A where
import Algebra.Structures.Module
import Algebra.Structures.CommutativeRing
import Algebra.Structures.Group
newtype A = A [(Integer,String)]
instance Group A where
(A a) <+> (A b) = A $ a ++ b
zero = A []
neg (A a) = A $ [((-k),c) | (k,c) <- a]
instance Module Integer A where
r *> (A as) = A [(r <*> k,c) | (k,c) <- as]
It fails by:
A.hs:15:10:
Overlapping instances for Group A
arising from the superclasses of an instance declaration
Matching instances:
instance Ring a => Group a -- Defined in Algebra.Structures.Group
instance Group A -- Defined at A.hs:9:10-16
In the instance declaration for `Module Integer A'
A.hs:15:10:
No instance for (Ring A)
arising from the superclasses of an instance declaration
Possible fix: add an instance declaration for (Ring A)
In the instance declaration for `Module Integer A'
Failed, modules loaded: none.
If I comment the Group instance out, then:
A.hs:16:10:
No instance for (Ring A)
arising from the superclasses of an instance declaration
Possible fix: add an instance declaration for (Ring A)
In the instance declaration for `Module Integer A'
Failed, modules loaded: none.
I read this as requiring an instance of Ring A to have Module Integer A which doesn't make sense and is not required in the class definition:
class (CommutativeRing r, AbelianGroup m) => Module r m where
-- | Scalar multiplication.
(*>) :: r -> m -> m
Could you explain this?
The package contains an
instance Ring a => Group a where ...
The instance head a matches every type expression, so any instance with any other type expression will overlap. That overlap only causes an error if such an instance is actually used somewhere. In your module, you use the instance in
instance Module Integer A where
r *> (A as) = A [(r <*> k,c) | (k,c) <- as]
The Module class has an AbelianGroup constraint on the m parameter¹. That implies a Group constraint. So for this instance, the Group instance of A must be looked up. The compiler finds two matching instances.
That is the first reported error.
The next is because the compiler tries to find an AbelianGroup instance for A. The only instance the compiler knows about at that point is
instance (Group a, Ring a) => AbelianGroup a
so it tries to find the instance Ring A where ..., but of course there isn't one.
Instead of commenting out the instance Group A where ..., you should add an
instance AbelianGroup a
(even if it's a lie, we just want to make it compile at the moment) and also add OverlappingInstances to the
{-# LANGUAGE #-} pragma.
With OverlappingInstances, the most specific matching instance is chosen, so it does what you want here.
¹ By the way, your A isn't an instance of AbelianGroup and rightfully can't be unless order is irrelevant in the [(Integer,String)] list.
This type checks without obnoxious language extensions.
{-# LANGUAGE MultiParamTypeClasses, TypeSynonymInstances #-}
module A where
import Algebra.Structures.Module
import Algebra.Structures.CommutativeRing
import Algebra.Structures.Group
newtype A = A [(Integer,String)]
instance Ring A where
A xs <+> A ys = A (xs ++ ys)
neg (A a) = A $ [((-k),c) | (k,c) <- a]
A x <*> A y = A [b | a <- x, b <- y ]
one = A []
zero = A []
instance Module Integer A where
r *> (A as) = A [(r <*> k,c) | (k,c) <- as]
It is a little confusing that <+> <*> and neg are defined independently in Ring and Group; they are completely separate symbols, but then they are brought together in the general instance that makes all Rings Groups, so if Ring is defined, Group mustn't be defined, since it's already spoken for. I'm not sure this is forced on the author by the way the type class system works. Module requires Ring or rather CommutativeRing. CommutativeRing is just basically renaming Ring; nothing further is to be defined. It is supposed to commit you to what is in Haskell an uncheckable assertion of commutativity. So you are supposed to "prove the CommutativeRing laws", so to speak, outside the module before making the Module instance. Note however that these laws are expressed in quickcheck propositions, so you are supposed to run quickcheck on propMulComm and propCommutativeRing specialized to this type.
Don't know what to do about one and zero, but you can get past the point about order by using a suitable structure, maybe:
import qualified Data.Set as S
newtype B = B {getBs :: S.Set (Integer,String) }
But having newtyped you can also, e.g., redefine Eq on A's to make sense of it, I suppose. In fact you have to to run the quickcheck propositions.
Edit: Here is a version with added material needed for QuickCheck http://hpaste.org/68351 together with "Failed" and "OK" quickcheck-statements for different Eq instances. This package is seeming pretty reasonable to me; I think you should redefine Module if you don't want the Ring and CommutativeRing business, since he says he "Consider[s] only the commutative case, it would be possible to implement left and right modules instead." Otherwise you won't be able to use quickcheck, which is clearly the principal point of the package, now that I see what's up, and which he has made it incredibly easy to do. As it is A is exactly the kind of thing he is trying to rule out with the all-pervasive use of quickcheck, which it would surely be very hard to trick in this sort of case.

Resources