Defining an algebra module using constructive-algebra package - haskell

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.

Related

Constraint on method depends on instances in scope?

Consider this code:
{-# language FlexibleInstances, UndecidableInstances #-}
module Y where
class C m where
x :: m
instance {-# overlappable #-} Monoid m => C m where
x = mempty
instance C Int where
x = 53
What is the type of x?
λ :type x
x :: C m => m
So far — so good. Now remove the Int instance. What is the type of x?
λ :type x
x :: Monoid m => m
Surprise!
Why is this happening?
This behaviour is explained in the following blog post:
Opaque constraint synonyms
In short: GHC is smart enough to see that you have only one instance of the C typeclass and decided that it's the only possible instance, so every time it sees C m constraint, it replaces it with Monoid m because they are equivalent.
N.B. As #chi further explains in a comment:
When GHC finds a constraint C t, it tries to solve it. If if finds a matching instance (...) => C t where ..., the constraint is replaced with the context (...). This is repeated as much as possible. The final constraint appears in the type (or triggers a "unsolved" type error). This process is justified since there can only be at most one matching instance. Overlapping instances change this, and prevent this context reduction when multiple instances (in scope!) match, roughly. It is a fragile extension, to be used with some care.

Overlapping instance for Show

Suppose we have the following:
{-# LANGUAGE FlexibleInstances #-}
module Sample where
newtype A a =
A a
deriving (Show)
newtype L a =
L [a]
class ListContainer l where
getList :: l a -> [a]
instance ListContainer L where
getList (L l) = l
instance (Show a, ListContainer l) => Show (l a) where
show = const "example"
With this code, ghc complains:
warning: [-Wdeferred-type-errors]
• Overlapping instances for Show (A a)
    arising from a use of ‘GHC.Show.$dmshowList’
  Matching instances:
    instance (Show a, ListContainer l) => Show (l a)
      -- Defined at /.../src/Sample.hs:18:10
    instance Show a => Show (A a)
      -- Defined at /.../src/Sample.hs:7:13
• In the expression: GHC.Show.$dmshowList #(A a)
  In an equation for ‘showList’:
      showList = GHC.Show.$dmshowList #(A a)
  When typechecking the code for ‘showList’
    in a derived instance for ‘Show (A a)’:
    To see the code I am typechecking, use -ddump-deriv
  In the instance declaration for ‘Show (A a)’
warning: [-Wdeferred-type-errors]
• Overlapping instances for Show (A a)
    arising from a use of ‘GHC.Show.$dmshow’
  Matching instances:
    instance (Show a, ListContainer l) => Show (l a)
      -- Defined at /.../src/Sample.hs:18:10
    instance Show a => Show (A a)
      -- Defined at /.../src/Sample.hs:7:13
• In the expression: GHC.Show.$dmshow #(A a)
  In an equation for ‘show’: show = GHC.Show.$dmshow #(A a)
  When typechecking the code for ‘show’
    in a derived instance for ‘Show (A a)’:
    To see the code I am typechecking, use -ddump-deriv
  In the instance declaration for ‘Show (A a)’
I can understand that it thinks type a can either derive Show, or derive ListContainer, which may result in Show.
How do we avoid that?
I understand that there exists a function showList, but its signature is a bit foreign. I do already have a function that I intend to use to display certain lists, which returns String directly.
I can understand that it thinks type a can either derive Show, or derive ListContainer, which may result in Show.
That is not what it thinks.
When Haskell chooses class instance, it doesn't look at instance constraints at all. All it considers when choosing an instance is the instance head (the thing that comes right after class name).
In your Show instance, the instance head is l a. This instance head matches A a (by assuming l = A). It also matches a lot of other things by the way - for example, it matches Maybe a (where l = Maybe), and Either b a (with l = Either b), and Identity a, and IO a - pretty much every type with a type parameter, come to think of it. It doesn't matter that neither A nor Maybe nor IO have an instance of ListContainer, because like I said above, Haskell doesn't look at constraints when choosing instances, only at instance heads.
It is only after finding a matching instance (by matching on its head) that Haskell will check if that instance's constraints are in fact satisfied. And will complain if they aren't. But it will never go back and try to pick another instance instead.
So coming back to your example: since A now has two matching Show instances - its own derived one and the Show (l a) one that you wrote, - the compiler complains that they are overlapping.
In your example you can just remove instance (Show a, ListContainer l) => Show (l a) and add deriving (Show) to L definition.
Alternatively you can remove deriving (Show) from A definition.
If you want you code behave as it is now remove deriving (Show) and implement it explicitly
instance {-# OVERLAPPING #-} Show a => Show (A a)
where
show (A a) = "A " ++ show a

Set specific properties for data in Haskell

Let us say I want to make a ADT as follows in Haskell:
data Properties = Property String [String]
deriving (Show,Eq)
I want to know if it is possible to give the second list a bounded and enumerated property? Basically the first element of the list will be the minBound and the last element will be the maxBound. I am trying,
data Properties a = Property String [a]
deriving (Show, Eq)
instance Bounded (Properties a) where
minBound a = head a
maxBound a = (head . reverse) a
But not having much luck.
Well no, you can't do quite what you're asking, but maybe you'll find inspiration in this other neat trick.
{-# language ScopedTypeVariables, FlexibleContexts, UndecidableInstances #-}
import Data.Reflection -- from the reflection package
import qualified Data.List.NonEmpty as NE
import Data.List.NonEmpty (NonEmpty (..))
import Data.Proxy
-- Just the plain string part
newtype Pstring p = P String deriving Eq
-- Those properties you're interested in. It will
-- only be possible to produce bounds if there's at
-- least one property, so NonEmpty makes more sense
-- than [].
type Props = NonEmpty String
-- This is just to make a Show instance that does
-- what you seem to want easier to write. It's not really
-- necessary.
data Properties = Property String [String] deriving Show
Now we get to the key part, where we use reflection to produce class instances that can depend on run-time values. Roughly speaking, you can think of
Reifies x t => ...
as being a class-level version of
\(x :: t) -> ...
Because it operates at the class level, you can use it to parametrize instances. Since Reifies x t binds a type variable x, rather than a term variable, you need to use reflect to actually get the value back. If you happen to have a value on hand whose type ends in p, then you can just apply reflect to that value. Otherwise, you can always magic up a Proxy :: Proxy p to do the job.
-- If some Props are "in the air" tied to the type p,
-- then we can show them along with the string.
instance Reifies p Props => Show (Pstring p) where
showsPrec k p#(P str) =
showsPrec k $ Property str (NE.toList $ reflect p)
-- If some Props are "in the air" tied to the type p,
-- then we can give Pstring p a Bounded instance.
instance Reifies p Props => Bounded (Pstring p) where
minBound = P $ NE.head (reflect (Proxy :: Proxy p))
maxBound = P $ NE.last (reflect (Proxy :: Proxy p))
Now we need to have a way to actually bind types that can be passed to the type-level lambdas. This is done using the reify function. So let's throw some Props into the air and then let the butterfly nets get them back.
main :: IO ()
main = reify ("Hi" :| ["how", "are", "you"]) $
\(_ :: Proxy p) -> do
print (minBound :: Pstring p)
print (maxBound :: Pstring p)
./dfeuer#squirrel:~/src> ./WeirdBounded
Property "Hi" ["Hi","how","are","you"]
Property "you" ["Hi","how","are","you"]
You can think of reify x $ \(p :: Proxy p) -> ... as binding a type p to the value x; you can then pass the type p where you like by constraining things to have types involving p.
If you're just doing a couple of things, all this machinery is way more than necessary. Where it gets nice is when you're performing lots of operations with values that have phantom types carrying extra information. In many cases, you can avoid most of the explicit applications of reflect and the explicit proxy handling, because type inference just takes care of it all for you. For a good example of this technique in action, see the hyperloglog package. Configuration information for the HyperLogLog data structure is carried in a type parameter; this guarantees, at compile time, that only similarly configured structures are merged with each other.

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).

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

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.

Resources