On Mon, Dec 8, 2008 at 4:43 AM, Tobias Bexelius
<[EMAIL PROTECTED]> wrote:
> {-# LANGUAGE OverlappingInstances #-}
>
> With this extension, the most specific instance will be used, i.e.
> "instance TShow Engine" for Engine's, no matter if it is an instance of
> Show.
Of course, down this way madne
.
"instance TShow Engine" for Enginge's, no matter if it is an instance of
Show.
/Tobias
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of John Ky
Sent: den 8 december 2008 13:32
To: Haskell Cafe
Subject: [Haskell-cafe] Overlapping instances
Hi,
I've got the following code which tries to implement a TShow class, which is
equivalent to Show, except it is supposed to work on TVar types as well.
import GHC.Conc
createEngine :: String -> Int -> Int -> IO Engine
createEngine name major minor = do
tUsers <- newTVarIO []
return $ Eng
Marc Weber wrote:
> class (HList c) => HListAppendArbitrary a b c | a b -> c where
> hAppendArbitrary :: a -> b -> c
>
> -- instance HList + HList (1)
> instance (HList a, HList b, HAppend a b c, HList c)
> => HListAppendArbitrary a b c where
> hAppendArbitrary a b = hAppend a b
>
>
I want to write a class introducing a function which should append a b
resulting in a HList containing a and b (order doesn't matter)
So I came up with:
= code ===
class (HList c) => HListAppendArbitrary a b c | a b -> c where
hAppend
I would like to state that a class Sup is exhaustively broken down in two
subclasses Sub1 and Sub2 (meaning, for every instance of Sub1 and every
instance of Sub2, the methods in Sup apply).
I try to code this as:
instance Sub1 x => Sup x
instance Sub2 x => Sup x
And get the (expected) error
This is still an ad-hoc solution, cause you lose
the `most-specific' instance property. You really have to
impose a `fixed' ordering in which instance-improvement rules
fire.
Recap:
The combination of overlapping instances
and type improvement leads to a `non-confluent' system, i.e.
there're to
Daniel Brown wrote:
>class Baz a b | a -> b
>instance Baz (a -> b) (a -> [b])
>instance Baz a a
> ...but Baz fails with this error...
>
> When confronted with overlapping instances, the compiler chooses the
> most specific one (if it is unique), e.g. `Baz (a -> b) (a -> [b])` is
> mor
Simon's dead right, too :) The issue raised here is of general nature and
doesn't depend on the particular (syntactic) formalism used to specify
type dependencies (let it be FDs, ATs,...). The consequence is that
instances and type dependencies are closer linked to each other
then one might think
Martin's dead right. GHC uses a less sophisticated mechanism to do
matching when it's thinking about functional dependencies than when it's
doing straight instance matching. Maybe something cleverer for fundeps
would make sense, as you point out. I hadn't thought of that before;
it's a good poin
Hi,
I wouldn't call this a bug, overlapping instances
and in particular the combination with functional dependencies
are something which is not well studied yet.
Hence, GHC is very conservative here.
I feel like you, this program should work.
As you correctly point out, there's a conflict among
I have the following three programs:
class Foo a b
instance Foo (a -> b) (a -> [b])
instance Foo a a
class Bar a b | a -> b
instance Bar (a -> b) (a -> b)
instance Bar a a
class Baz a b | a -> b
instance Baz (a -> b) (a -> [b])
instance Baz a a
When compiled in ghc 6.4 (with
12 matches
Mail list logo