instance declarations

2001-12-07 Thread David Feuer

I am curious about a couple things regarding instance declarations.

1.  Why can't they be hidden in module imports/exports?  Is this an
implementation issue (I guess I could see it as a problem with the
dictionary-passing approach...)?  It seems kind of bad that instances are
not allowed to overlap, but can't be hidden.

2.  Why can't you simultaneously declare a type to be an instance of
multiple classes?  i.e, why can't you write the following?

class C1 t where
a::t->t
class C1 t => C2 t where
b::t->t

instance C1 t, C2 t where
a=...
b=...


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



RE: instance declarations

2001-12-07 Thread Mark P Jones

Hi David,

| 1.  Why can't they be hidden in module imports/exports?  Is this an
| implementation issue (I guess I could see it as a problem with the
| dictionary-passing approach...)?  It seems kind of bad that instances are
| not allowed to overlap, but can't be hidden.

There's no solid technical reason for this, but Haskell doesn't allow
it at the moment because there isn't an easy way to name an instance
declaration.  And if you can't name it, then you can't put it in an
import/export list.  Also, I don't think people thought it was worth
the hassle of introducing a syntax for naming instances when the only
thing it could be used for was controlling imports and exports.
Recently, however, there has been some interest in using named instance
declarations in other ways, so perhaps we will see features like this
creeping into future versions of the language.

[Of course, there is a way of naming instance declarations with the
current Haskell syntax, although it is a little verbose, and would
require more work on the implementers part than simple matching of
strings.  The syntax I'm thinking of would look something like the
following:

  module M(C(..), instance C Int, instance C a => C [a]) where ...

Other variations, either more or less verbose, are possible.
Personally, I think it would be nice to be able to document class
instances explicitly like this as part of module interfaces.]

| 2.  Why can't you simultaneously declare a type to be an instance of
| multiple classes?  i.e., why can't you write the following?
| 
| class C1 t where
|   a::t->t
| class C1 t => C2 t where
|   b::t->t
| 
| instance C1 t, C2 t where
|   a=...
|   b=...

Again, there's no problem with this in theory, but it has the potential
to be messy in practice.  What would the syntax for this look like in
the general case?  What if you wanted to include contexts on the instance
declarations?  A nicely worked out proposal that answers questions like
these in the general case, without seeming ad hoc or arbitrary, might
attract some interest from implementers.  As things stand, however, I'm
guessing that most people don't find they need this feature often enough
to justify extra complexity in the language definition.

All the best,
Mark


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: instance declarations

2001-12-07 Thread David Feuer

(sorry to mess up mail threading, but I couldn't properly reply to the
message the way I'm using email right now--broken mail clients)

>Recently, however, there has been some interest in using named instance
>declarations in other ways, so perhaps we will see features like this
>creeping into future versions of the language.

In what kinds of ways?  Sounds interesting.


>[Of course, there is a way of naming instance declarations with the
>current Haskell syntax, although it is a little verbose, and would
>require more work on the implementers part than simple matching of
>strings.  The syntax I'm thinking of would look something like the
>following:
>
>  module M(C(..), instance C Int, instance C a => C [a]) where ...

This is the sort of thing I was thinking too.  But I would probably want
to extend that to classes and types.  For instance

module M (class Eq a=>C a (...), type A, instance C A, instance C a => C
[a])
where ...

If I am not mistaken, this would allow separation of the type namespace
from the typeclass namespace, and would make it obvious whether the thing
being exported is a type or a class.  It could also potentially allow the
context(s) for class and instance declarations to be more restrictive in
the header or in imports than in the module body.  The latter could
perhaps allow resolution of overlapping instances at import time, by
restricting the instances to the point of non-overlap.  I'm not sure that
the former would actually be useful.

Hmmm speaking of overlapping instances...  Would there be a
practical way to add negation (of classes and possibly even types) to the
context syntax?  This would let you say

instance (Integral a) => C (T a) where ...
instance (not Integral a, Real a) => C (T a) where ...
instance (not Num a) => C (T a) where ...


It would also seem nice to be able to say

instance (Integral a, not a Int) => C a where 
and 
instance C Int where .

but this seems even more questionable.


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: instance declarations

2001-12-09 Thread Marcin 'Qrczak' Kowalczyk

Fri, 7 Dec 2001 11:38:14 -0800, Mark P Jones <[EMAIL PROTECTED]> pisze:

> There's no solid technical reason for this, but Haskell doesn't allow
> it at the moment because there isn't an easy way to name an instance
> declaration.

There is another problem: even if we created a syntax to name them,
if they would not be exported by default then current programs would
have to be changed.

An instance is usually meant to be exported, so even not considering
compatibility it would be tedious to list all those instances in
the export list (unless you want to export every named thing as well
and omit the export list). It's easy to overlook some and the point
when somebody tries to use a particular instance might be far in the
future. Each instance is often a "small" part of an interface.

I agree that the ability to selectively export instances would be good.
Only it's hard to combine with the current policy of exporting all
instances by default.

Perhaps in the future it will be possible to specify the interface
of a Haskell module more formally, with types of exported values
for example. Then we should remember about instances and solve both
problems simultaneously.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^
QRCZAK


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: instance declarations

2001-12-09 Thread David Feuer

Marcin 'Qrczak' Kowalczyk wrote:

> There is another problem: even if we created a syntax to name them,
> if they would not be exported by default then current programs would
> have to be changed.

Well, the default could be to export, unless explicitly hidden.  If it
_is_ exported, you could have the option to write it explicitly, or just
have it go by default.
> 
> Perhaps in the future it will be possible to specify the interface
> of a Haskell module more formally, with types of exported values
> for example. Then we should remember about instances and solve both
> problems simultaneously.

I guess that may be true...  It could be really useful to have a tool to
take a source file and automagically make an approximate header for
it...

-- 
/Times-Bold 40 selectfont/n{moveto}def/m{gsave true charpath clip 72
400 n 300 -4 1{dup 160 300 3 -1 roll 0 360 arc 300 div 1 1 sethsbcolor
fill}for grestore 0 -60 rmoveto}def 72 500 n(This message has been)m
(brought to you by the)m(letter alpha and the number pi.)m(David Feuer)
m([EMAIL PROTECTED])m showpage

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



RE: instance declarations

2001-12-10 Thread Mark P Jones

Hi David,

| >Recently, however, there has been some interest in using named instance
| >declarations in other ways, so perhaps we will see features like this
| >creeping into future versions of the language.
| 
| In what kinds of ways?  Sounds interesting.

I was thinking of a couple of papers from the most recent Haskell
workshop.  See http://www.cs.uu.nl/people/ralf/hw2001.html for some
pointers (the second session).


| >  module M(C(..), instance C Int, instance C a => C [a]) where ...
| 
| This is the sort of thing I was thinking too.  But I would probably want
| to extend that to classes and types.  For instance
| 
| module M (class Eq a=>C a (...), type A, instance C A, instance C a => C
| [a])
| where ...

Yes, that's also what I had in mind at the more verbose end of the
spectrum (which is not to say that I think it would be a bad thing).
A richer, more explicit syntax for export lists might provide some
useful documentation and be easier to read than a syntax that leaves
you guessing whether C(..) refers to a type or a class.  On the other
hand, if things start to get too wordy, you might instead want to add
a separate notation for describing interfaces.  The following is an
throwaway syntax, intended only to hint at the basic idea:

  interface I where
class C a where f :: a -> a
instance C Int
instance C a => C [a]

  module M implements I where ...
...

Start allowing parameterization and other interesting features and
this begins to look somewhat like ML style modules (and related
systems).

All the best,
Mark


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



RE: instance declarations

2001-12-10 Thread Mark P Jones

Hi Marcin,

| > There's no solid technical reason for this, but Haskell doesn't allow
| > it at the moment because there isn't an easy way to name an instance
| > declaration.
| 
| There is another problem: even if we created a syntax to name them,
| if they would not be exported by default then current programs would
| have to be changed.

You're right of course, although I consider this a pragmatic issue
rather than a technical problem:  I'm thinking of future languages
that are inspired by current Haskell standards but not constrained
by details of the current definition or existing codebase.

All the best,
Mark


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: instance declarations

2001-12-10 Thread Ketil Z Malde

David Feuer <[EMAIL PROTECTED]> writes:

> 1.  Why can't [instances] be hidden in module imports/exports?

The way I see it, an instance declaration is an assertion that a
certain data type supports a certain set of operations.  Thus, if the
data type and the operations on it are in scope, it makes sense for
the class instance to be, too.

(This leads to the question of why we need to have instance
declarations at all :-)  (My guesses would be: compiler
implementation issues, code clarity, error detection, partially
implemented classes))

Problems arise when a data type needs to be instantiated twice in the
same class, but with different operator implementations.  (I.e. you
have a data type which prints differently according to which module
you're in)

This would, I think, be a problem in most languages, think of deriving
a C++ class twice from the same base class while providing different
overrides for the functions.

I'm not entirely convinced it's an issue that needs a better
resolution than the language provides today.  (There's a diminishing
returns effect when adding language features, and at some point, the
increased complexity of the language doesn't make it worth it, IMHO.)

> 2.  Why can't you simultaneously declare a type to be an instance of
> multiple classes?

Why does it matter?

> class C1 t where a::t->t
> class C1 t => C2 t where b::t->t
> instance C1 T, C2 T where
>   a=...
>   b=...

To me, it'd make more sense to provide

class C1 t where a :: t -> t
class (C1 t) => C2 t where b :: t -> t

instance C2 T where
a = ...  -- implicitly instantiating C1
b = ...

and avoid long instantiation chains.  But that too is IMHO a minor issue.

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: tricky instance declarations

2002-05-03 Thread Ashley Yakeley

At 2002-05-03 03:53, Warrick Gray wrote:

>instance Monad (IO (Either ConnError a)) where

You do of course mean

 instance Monad (/\a => IO (Either ConnError a)) where
   ...

...but you just can't do type-lambdas in Haskell.

-- 
Ashley Yakeley, Seattle WA

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



[Haskell-cafe] Explaining instance declarations

2012-07-29 Thread Patrick Browne
{- I am trying to understand and provide a *simplified* explanation of instance contexts and their relationship with class hierarchies. I use the example from [1]. Are the following two sentences and annotated code a reasonable explanation? " When instantiating an instance I of C, its context must be at the same level or lower than the context of any instance of any super-class of C.  The purpose of this rule is to guarantee that the required super-class methods exist." [1] 4.3.2  Instance Declarations http://www.haskell.org/onlinereport/haskell2010/haskellch4.htmlClass hierarchy 
Eq1   Show1       Foo   
     \ /                |
     \   /                  |
    Num1               Bar
       |
       |
    Num2-}class Foo a whereclass Show1 a whereclass Foo a => Bar a whereclass Eq1 a where-- Eq1 and Show1 are super-classes of Num1 and Num2.class (Eq1 a, Show1 a) => Num1 aclass Num1 a => Num2 a -- We must make an instance of Foo [a], before we can have instance Bar [a]instance (Num1 a) => Foo [a] where -- But that instance of Foo [a] depends on a being a member of Num1-- Hence Bar[a] can only be defined if their exists Num1 a-- But Eq1 & Show1 are super classes of Num1-- The following context causes an *error*, because the context is weaker than required-- instance (Eq1 a, Show1 a) => Bar [a] where-- But this is OKinstance (Num1 a) => Bar [a] where-- Also, this would be OK-- instance (Num2 a) => Bar [a] where
 Tá an teachtaireacht seo scanta ó thaobh ábhar agus víreas ag Seirbhís Scanta Ríomhphost de chuid Seirbhísí Faisnéise, ITBÁC agus meastar í a bheith slán.  http://www.dit.ie
This message has been scanned for content and viruses by the DIT Information Services E-Mail Scanning Service, and is believed to be clean.  http://www.dit.ie



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] duplicate instance declarations. Why?

2008-10-24 Thread Alberto G. Corona
with:

>{-# OPTIONS -fglasgow-exts  -fallow-undecidable-instances  #-}

>class A a
>class R a

>class S a

>instance  R a => A a
>instance S a => A a
--

GHC gives

*Duplicate instance declarations*
*  instance  R a => A a *
*  instance S a => A a *
**
*Why?*
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] duplicate instance declarations. Why?

2008-10-24 Thread Bulat Ziganshin
Hello Alberto,

Friday, October 24, 2008, 12:20:39 PM, you wrote:

 >>instance  R a => A a
 >>instance S a => A a 
>   
>  Duplicate instance declarations
>  Why?

because you may write in other module

instance R Int
instance S Int

if class A includes functions, it may be problematic to determine
which implementation (via R or via S) to use


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] duplicate instance declarations. Why?

2008-10-24 Thread Ryan Ingram
Instance instantiation is *not* search, and *not* similar to
subclassing in OO languages.

Both your instance declarations simply add constraints to functions that use it.

Here's a more concrete example:

class A a where
doA :: a -> String
class R a where
doR :: a -> String

instance R Int where doR = show
instance R a => A a where
doA = doR

question x = doA x

The question is, what is the type of "question"?  Here are two valid
choices with this program:
question :: (A a) => a -> String
question :: (R a) => a -> String

The instance R a => A a says that every type "a" is an instance of
"A"; if an instance for A is needed, the compiler says "OK, I know how
to make one of those.  But I now add a new constraint, R a."

Adding another instance S a => A a makes the choice of what constraint
to add ambiguous.  In particular the following code does *not* work:

class S a where
doS :: a -> String
instance S String where
doS = id
instance S a => A a where
doA = doS

question2 = question (2::Int)
question3 = question "3"

In my experience, if you are turning undecidable instances on and you
don't know exactly why it's safe to do so, there is probably a mistake
in your design.

   -- ryan

2008/10/24 Alberto G. Corona <[EMAIL PROTECTED]>:
> with:
>
>>{-# OPTIONS -fglasgow-exts  -fallow-undecidable-instances  #-}
>
>>class A a
>>class R a
>
>>class S a
>
>>instance  R a => A a
>
>>instance S a => A a
> --
>
> GHC gives
>
> Duplicate instance declarations
>   instance  R a => A a
>   instance S a => A a
>
> Why?
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] duplicate instance declarations. Why?

2008-10-25 Thread Brent Yorgey
On Fri, Oct 24, 2008 at 10:20:39AM +0200, Alberto G. Corona  wrote:
> with:
> 
> >{-# OPTIONS -fglasgow-exts  -fallow-undecidable-instances  #-}
> 
> >class A a
> >class R a
> 
> >class S a
>
> >instance  R a => A a
> >instance S a => A a
> --

This point commonly trips people up (it used to trip me up). In
addition to what others have said, I hope I can provide a bit more
intuition.

If you have 

> instance  R a => A a

it *seems* like it should mean, "Any a which is an instance of R is
also an instance of A".  However, that's *not* what it means!  It
actually means "Any type which matches 'a' (that is, any type at all)
can be an instance of A; and if some type is used as an instance of A,
then it must also be an instance of R as well."

GHC picks which instance to use by looking *only* at stuff to the
right of => in instance declarations.  Only after an instance has been
chosen is the stuff to the left of the => considered.

Hopefully now it is clear why the code above is a duplicate instance
declaration; there's no way to distinguish the instances by looking
only at stuff to the right of => .

-Brent
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] yi-editor: Duplicate instance declarations

2009-09-27 Thread Marcelo Sousa
Hey guys,

I'm trying to install yi using cabal but I got this error. Any ideas
how to solve it?!
I'm using ghc-6.10.1 and cabal-install version 0.6.2 using version
1.6.0.2 of the Cabal library.

Thanks,

Marcelo

-- Code --

$ cabal install yi
Resolving dependencies...
Configuring yi-0.6.1...
Preprocessing library yi-0.6.1...
Preprocessing executables for yi-0.6.1...
Building yi-0.6.1...
[  1 of 120] Compiling System.FriendlyPath ( System/FriendlyPath.hs,
dist/build/System/FriendlyPath.o )
[  2 of 120] Compiling Shim.ProjectContent ( Shim/ProjectContent.hs,
dist/build/Shim/ProjectContent.o )
[  3 of 120] Compiling Parser.Incremental ( Parser/Incremental.hs,
dist/build/Parser/Incremental.o )
[  4 of 120] Compiling Data.Trie( Data/Trie.hs, dist/build/Data/Trie.o )
[  5 of 120] Compiling Data.DelayList   ( Data/DelayList.hs,
dist/build/Data/DelayList.o )
[  6 of 120] Compiling Data.Rope( Data/Rope.hs, dist/build/Data/Rope.o )
[  7 of 120] Compiling Data.Prototype   ( Data/Prototype.hs,
dist/build/Data/Prototype.o )
[  8 of 120] Compiling HConf.Utils  ( HConf/Utils.hs,
dist/build/HConf/Utils.o )
[  9 of 120] Compiling HConf.Paths  ( HConf/Paths.hs,
dist/build/HConf/Paths.o )
[ 10 of 120] Compiling Paths_yi (
dist/build/autogen/Paths_yi.hs, dist/build/Paths_yi.o )
[ 11 of 120] Compiling HConf( HConf.hs, dist/build/HConf.o )
[ 12 of 120] Compiling Yi.Char.Unicode  ( Yi/Char/Unicode.hs,
dist/build/Yi/Char/Unicode.o )
[ 13 of 120] Compiling Yi.UI.Common[boot] ( Yi/UI/Common.hs-boot,
dist/build/Yi/UI/Common.o-boot )
[ 14 of 120] Compiling Yi.String( Yi/String.hs, dist/build/Yi/String.o )
[ 15 of 120] Compiling Yi.Monad ( Yi/Monad.hs, dist/build/Yi/Monad.o )
[ 16 of 120] Compiling Yi.Keymap.Completion ( Yi/Keymap/Completion.hs,
dist/build/Yi/Keymap/Completion.o )
[ 17 of 120] Compiling Yi.Editor[boot]  ( Yi/Editor.hs-boot,
dist/build/Yi/Editor.o-boot )
[ 18 of 120] Compiling Yi.Debug ( Yi/Debug.hs, dist/build/Yi/Debug.o )
[ 19 of 120] Compiling Yi.Prelude   ( Yi/Prelude.hs,
dist/build/Yi/Prelude.o )

Yi/Prelude.hs:182:9:
Duplicate instance declarations:
  instance Category Accessor.T -- Defined at Yi/Prelude.hs:182:9-38
  instance Category Accessor.T
-- Defined in data-accessor-0.2.1:Data.Accessor.Private
cabal: Error: some packages failed to install:
yi-0.6.1 failed during the building phase. The exception was:
exit: ExitFailure 1
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] "Functional dependencies conflict between instance declarations"

2007-09-10 Thread Peter Verswyvelen
The Haskell mailing list seems to be filled with people requesting 
information about this error, so I cannot resist to include myself in it ;-)


I've read the information about funcdeps in the GHC user guide, and I 
think I understand how it works, but I get the error a lot, without 
having a clue why. Sometimes I get the error even when all the types of 
all the type parameters are completely different, so even when all 
parameters would be one-to-one dependent, I still don't get why I would 
get a conflict error.


Does a wiki exists with possible reasons why this error occured and how 
to fix it?


Thanks,
Peter

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] yi-editor: Duplicate instance declarations

2009-09-27 Thread Nicolas Pouillard
Excerpts from Marcelo Sousa's message of Sun Sep 27 14:13:43 +0200 2009:
> Hey guys,
> 
> I'm trying to install yi using cabal but I got this error. Any ideas
> how to solve it?!
> I'm using ghc-6.10.1 and cabal-install version 0.6.2 using version
> 1.6.0.2 of the Cabal library.

This means that you either have to downgrade data-accessor, or trash out the
Category instance in Yi/Prelude.hs line 182.

> $ cabal install yi
> Resolving dependencies...
> Configuring yi-0.6.1...
> Preprocessing library yi-0.6.1...
> Preprocessing executables for yi-0.6.1...
> Building yi-0.6.1...
> [  1 of 120] Compiling System.FriendlyPath ( System/FriendlyPath.hs,
> dist/build/System/FriendlyPath.o )
> [  2 of 120] Compiling Shim.ProjectContent ( Shim/ProjectContent.hs,
> dist/build/Shim/ProjectContent.o )
> [  3 of 120] Compiling Parser.Incremental ( Parser/Incremental.hs,
> dist/build/Parser/Incremental.o )
> [  4 of 120] Compiling Data.Trie( Data/Trie.hs, 
> dist/build/Data/Trie.o )
> [  5 of 120] Compiling Data.DelayList   ( Data/DelayList.hs,
> dist/build/Data/DelayList.o )
> [  6 of 120] Compiling Data.Rope( Data/Rope.hs, 
> dist/build/Data/Rope.o )
> [  7 of 120] Compiling Data.Prototype   ( Data/Prototype.hs,
> dist/build/Data/Prototype.o )
> [  8 of 120] Compiling HConf.Utils  ( HConf/Utils.hs,
> dist/build/HConf/Utils.o )
> [  9 of 120] Compiling HConf.Paths  ( HConf/Paths.hs,
> dist/build/HConf/Paths.o )
> [ 10 of 120] Compiling Paths_yi (
> dist/build/autogen/Paths_yi.hs, dist/build/Paths_yi.o )
> [ 11 of 120] Compiling HConf( HConf.hs, dist/build/HConf.o )
> [ 12 of 120] Compiling Yi.Char.Unicode  ( Yi/Char/Unicode.hs,
> dist/build/Yi/Char/Unicode.o )
> [ 13 of 120] Compiling Yi.UI.Common[boot] ( Yi/UI/Common.hs-boot,
> dist/build/Yi/UI/Common.o-boot )
> [ 14 of 120] Compiling Yi.String( Yi/String.hs, 
> dist/build/Yi/String.o )
> [ 15 of 120] Compiling Yi.Monad ( Yi/Monad.hs, dist/build/Yi/Monad.o )
> [ 16 of 120] Compiling Yi.Keymap.Completion ( Yi/Keymap/Completion.hs,
> dist/build/Yi/Keymap/Completion.o )
> [ 17 of 120] Compiling Yi.Editor[boot]  ( Yi/Editor.hs-boot,
> dist/build/Yi/Editor.o-boot )
> [ 18 of 120] Compiling Yi.Debug ( Yi/Debug.hs, dist/build/Yi/Debug.o )
> [ 19 of 120] Compiling Yi.Prelude   ( Yi/Prelude.hs,
> dist/build/Yi/Prelude.o )
> 
> Yi/Prelude.hs:182:9:
> Duplicate instance declarations:
>   instance Category Accessor.T -- Defined at Yi/Prelude.hs:182:9-38
>   instance Category Accessor.T
> -- Defined in data-accessor-0.2.1:Data.Accessor.Private
> cabal: Error: some packages failed to install:
> yi-0.6.1 failed during the building phase. The exception was:
> exit: ExitFailure 1

-- 
Nicolas Pouillard
http://nicolaspouillard.fr
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] yi-editor: Duplicate instance declarations

2009-09-27 Thread Jochem Berndsen
Nicolas Pouillard wrote:
> Excerpts from Marcelo Sousa's message of Sun Sep 27 14:13:43 +0200 2009:
>> Hey guys,
>>
>> I'm trying to install yi using cabal but I got this error. Any ideas
>> how to solve it?!
>> I'm using ghc-6.10.1 and cabal-install version 0.6.2 using version
>> 1.6.0.2 of the Cabal library.
> 
> This means that you either have to downgrade data-accessor, or trash out the
> Category instance in Yi/Prelude.hs line 182.
> 

FYI: I had the same problem this morning. Using data-accessor 0.2.0.2
worked.

Regards, Jochem

-- 
Jochem Berndsen | joc...@functor.nl | joc...@牛在田里.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Why distinct tyvars in instance declarations?

2005-06-25 Thread Josh Hoyt
Hello,

I'm a new Haskeller, and I'm running into a problem attempting to
declare certain types as instances. I was attempting something that's
effectively equivalent to:

> class Foo a
> 
> instance Foo (Either b b)

but GHC complains:

> Illegal instance declaration for `Foo (Either b b)'
> (The instance type must be of form (T a b c)
>  where T is not a synonym, and a,b,c are distinct type variables)
> In the instance declaration for `Foo (Either b b)'

and so I looked in the report
(http://www.haskell.org/onlinereport/decls.html#sect4.3.2) and found:

> The general form of the corresponding instance declaration is:
> 
> instance cx' => C (T u1 ... uk) where { d }
> 
> where k>=0. The type (T u1 ... uk) must take the form of a type constructor T 
> applied to simple type variables u1, ... uk; furthermore, T must not be a 
> type synonym, and *the ui must all be distinct*. (emphasis mine)

My question is, why this restriction that the types must be distinct?

In particular, I'd like to declare a very specific type (Either String
String) as an instance. What techniques can I use to accomplish this?

Josh Hoyt
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] "Functional dependencies conflict between instance declarations"

2007-09-10 Thread Peter Verswyvelen

Never mind, that GHC compiler was again more clever than me, sigh.

That's really frustrating about Haskell: the compiler captures so many 
errors at compile time, that newbies hardly get anything done, it's a 
constant battle against the errors. But once it compiles, it usually 
works at runtime :-)


Happy hacking,
Peter





___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] "Functional dependencies conflict between instance declarations"

2007-09-10 Thread Andrew Coppin

Peter Verswyvelen wrote:

Never mind, that GHC compiler was again more clever than me, sigh.

That's really frustrating about Haskell: the compiler captures so many 
errors at compile time, that newbies hardly get anything done, it's a 
constant battle against the errors. But once it compiles, it usually 
works at runtime :-)


This is what I love about Haskell: If it typechecks, it probably does 
the thing you meant it to. I've never seen any other language like it. 
It's amazing!


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: "Functional dependencies conflict between instance declarations"

2007-09-12 Thread Stefan Monnier
>> Never mind, that GHC compiler was again more clever than me, sigh.
>> That's really frustrating about Haskell: the compiler captures so many
>> errors at compile time, that newbies hardly get anything done, it's
>> a constant battle against the errors. But once it compiles, it usually
>> works at runtime :-)
> This is what I love about Haskell: If it typechecks, it probably does the
> thing you meant it to.  I've never seen any other language like
> it.  It's amazing!

Next stop: Coq, where the fight with the type checker is so much more
difficult that when the code finally type checks you don't even need to
run it at all.


Stefan

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Deferred instance declarations (context without type variables)

2006-09-16 Thread Misha Aizatulin
hello,

  I have a question about context in type signature. I would like to
write a function, say (f :: T -> T) which also relies on an instance of
class C being defined for T. The problem is, I don't want this instance
defined at the same time f is defined, instead I would like to defer
this definition until f is called (in some other module). Naively the
code would look like this:
=
module DefineF where

class C a where
  fC :: a -> a

data T = T

f :: (C T) => T -> T
f T = fC T
=
module CallF where

instance C T where
  fC = id

call = f T
=
  The definition of f in DefineF won't compile because "All of the type
variables .. are already in scope". Could you recommend any other way to
achieve what I am trying to do?

  An interesting thing is that I can easily make the code compile with
the same meaning by changing the 
declaration of T to include a dummy type variable:
> data T a = T
  it's just a pity that I have to trick the compiler in such an ugly
way.

Cheers,
  Misha
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why distinct tyvars in instance declarations?

2005-06-26 Thread Daniel Fischer
Am Samstag, 25. Juni 2005 21:22 schrieb Josh Hoyt:
> Hello,
>
> I'm a new Haskeller, and I'm running into a problem attempting to
> declare certain types as instances. I was attempting something that's
>
> effectively equivalent to:
> > class Foo a
> >
> > instance Foo (Either b b)
>
> but GHC complains:
> > Illegal instance declaration for `Foo (Either b b)'
> > (The instance type must be of form (T a b c)
> >  where T is not a synonym, and a,b,c are distinct type variables)
> > In the instance declaration for `Foo (Either b b)'
>
> and so I looked in the report
>
> (http://www.haskell.org/onlinereport/decls.html#sect4.3.2) and found:
> > The general form of the corresponding instance declaration is:
> >
> > instance cx' => C (T u1 ... uk) where { d }
> >
> > where k>=0. The type (T u1 ... uk) must take the form of a type
> > constructor T applied to simple type variables u1, ... uk; furthermore, T
> > must not be a type synonym, and *the ui must all be distinct*. (emphasis
> > mine)
>
> My question is, why this restriction that the types must be distinct?
>
> In particular, I'd like to declare a very specific type (Either String
> String) as an instance. What techniques can I use to accomplish this?
>
> Josh Hoyt

I don't know, why the tyvars must be distinct in Haskell 98, but if you use 
extensions (hugs -98; -fglasgow-exts for ghc(i)), you can declare

instance Foo (Either b b) where ...

or

instance Foo (Either String String) where ...

without problems.

HTH,
Daniel
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why distinct tyvars in instance declarations?

2005-06-26 Thread Henning Thielemann

On Sun, 26 Jun 2005, Daniel Fischer wrote:

> Am Samstag, 25. Juni 2005 21:22 schrieb Josh Hoyt:
> > Hello,
> >
> > I'm a new Haskeller, and I'm running into a problem attempting to
> > declare certain types as instances. I was attempting something that's
> >
> > effectively equivalent to:
> > > class Foo a
> > >
> > > instance Foo (Either b b)
> >
> > My question is, why this restriction that the types must be distinct?
> >
> > In particular, I'd like to declare a very specific type (Either String
> > String) as an instance. What techniques can I use to accomplish this?
> >
> > Josh Hoyt
>
> I don't know, why the tyvars must be distinct in Haskell 98,

This is certainly to prevent from overlapping instances. An implementation
for general (Either a b) could also be invoked when (Either String String)
is requested.

If it is really necessary to make the Either type an instance of something
better use a data or a newtype definition.

newtype EitherString = EitherString (Either String String)

and declare an instance for EitherString.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why distinct tyvars in instance declarations?

2005-06-27 Thread Frank-Andre Riess
Hi there,

> but GHC complains:
> >     Illegal instance declaration for `Foo (Either b b)'
> >         (The instance type must be of form (T a b c)
> >          where T is not a synonym, and a,b,c are distinct type variables)
> >     In the instance declaration for `Foo (Either b b)'

unless I'm totally mistaken, your problem isn't the distinction thingy, but 
rather an error like supplying an Int for where you need (Int -> Int -> Int). 
That is, you're trying make (Either String String) an instance of Foo, 
(Either String String) already being a fully constructed type; Foo, on the 
other hand, seems to require a type constructor that is yet to parameterize 
over three more types (e.g. StateT).

Greets,
Frank-Andre Riess
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why distinct tyvars in instance declarations?

2005-06-27 Thread robert dockins

but GHC complains:


   Illegal instance declaration for `Foo (Either b b)'
   (The instance type must be of form (T a b c)
where T is not a synonym, and a,b,c are distinct type variables)
   In the instance declaration for `Foo (Either b b)'



unless I'm totally mistaken, your problem isn't the distinction thingy, but 
rather an error like supplying an Int for where you need (Int -> Int -> Int). 
That is, you're trying make (Either String String) an instance of Foo, 
(Either String String) already being a fully constructed type; Foo, on the 
other hand, seems to require a type constructor that is yet to parameterize 
over three more types (e.g. StateT).


I think that you are mistaken.  The OP listed:

> class Foo a
> instance Foo (Either b b)

Without further information, Haskell compilers will assume that the 
type(s) in a class declaration has/have kind * (Report section 4.6). 
Either b b does have kind *, so that's not the problem.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why distinct tyvars in instance declarations?

2005-06-27 Thread Josh Hoyt
On 6/27/05, robert dockins <[EMAIL PROTECTED]> wrote:
>
> I think that you are mistaken.  The OP listed:
> 
>  > class Foo a
>  > instance Foo (Either b b)
> 
> Without further information, Haskell compilers will assume that the
> type(s) in a class declaration has/have kind * (Report section 4.6).
> Either b b does have kind *, so that's not the problem.
>

Indeed.

> class Foo a
>
> instance Foo (Either b c)

*is* accepted, so this is not a kind error.

Josh Hoyt
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why distinct tyvars in instance declarations?

2005-06-27 Thread Josh Hoyt
On 6/26/05, Henning Thielemann <[EMAIL PROTECTED]> wrote:
> On Sun, 26 Jun 2005, Daniel Fischer wrote:
> > [...]
> > I don't know, why the tyvars must be distinct in Haskell 98,
> 
> This is certainly to prevent from overlapping instances. An implementation
> for general (Either a b) could also be invoked when (Either String String)
> is requested.
> 
> If it is really necessary to make the Either type an instance of something
> better use a data or a newtype definition.
> 
> newtype EitherString = EitherString (Either String String)
> 
> and declare an instance for EitherString.

I see why there is ambiguity between (Either a b) and (Either b b). In
fact, it seems rather obvious now. Thanks for your help.

Just to make sure I understand, and hopefully instructive for others
who run into the same difficulty:

class Foo a where
frob :: a -> String

{- Illegal:

instance Foo (Either String String) where
frob (Right x) = x
frob (Left y) = y

-}

-- Instead:


-- Option a:
-- Generic implementation in terms of other classes

instance (Show a, Show b) => Foo (Either a b) where
frob (Right x) = show x
frob (Left y) = show y


-- Option b:
-- Let the type system know that this is a specific case by defining a type

newtype EitherString = EitherString (Either String String)

instance Foo EitherString where
frob (EitherString (Right x)) = x
frob (EitherString (Left y)) = y
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Re: "Functional dependencies conflict between instance declarations"

2007-09-12 Thread bf3
Are you kidding, or has automatic proving of programs evolved that far?

Anyway, for my sector, videogames, "proving" if something works correctly is
subjective, it's very hard to check if "the gameplay of a game is good
enough" since that involves human fuzzy judgement ;-)  Although this might
just be statistics, so can be proven too! Aaarrrggg, soon we're all out
of job ;-)

Peter

-Original Message-
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Stefan Monnier
Sent: Wednesday, September 12, 2007 7:06 PM
To: haskell-cafe@haskell.org
Subject: [Haskell-cafe] Re: "Functional dependencies conflict between
instance declarations"

>> Never mind, that GHC compiler was again more clever than me, sigh.
>> That's really frustrating about Haskell: the compiler captures so many
>> errors at compile time, that newbies hardly get anything done, it's
>> a constant battle against the errors. But once it compiles, it usually
>> works at runtime :-)
> This is what I love about Haskell: If it typechecks, it probably does the
> thing you meant it to.  I've never seen any other language like
> it.  It's amazing!

Next stop: Coq, where the fight with the type checker is so much more
difficult that when the code finally type checks you don't even need to
run it at all.


Stefan

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: "Functional dependencies conflict between instance declarations"

2007-09-12 Thread Andrew Coppin

[EMAIL PROTECTED] wrote:

Are you kidding, or has automatic proving of programs evolved that far?

Aaarrrggg, soon we're all out of job ;-)
  


"Experts" have been proclaiming this since high-level programming was 
invented many decades ago. We're still waiting. ;-)


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] technique to allow innocuous ambiguity in instance declarations?

2006-07-11 Thread Nicolas Frisby

Brief disclaimer: I'm using GHC 6.4.1 and haven't looked into Hugs; but I
don't suspect there's much difference on this issue. Could easily be
wrong there.

I've hit a bit of a road bump in ambiguity regarding type class
instances and transformer types (in the style of monad transformers).
The interesting point is that, in this case, I believe that the
ambiguity is harmless and that all possible derivations of instances
would be extensionally equivalent. But the typechecker won't let me
get far enough to test that hypothesis.

So, I have a relation C and intuition that the property can be carried
through transformations on either of its related types. I'm seeking
1) a suggested technique for formulating that intuition in such a way
that the type-checker could act on it
2) a suggestion claiming that such a harmless ambiguity is down right
impossible

Below is pseudo-code outlining the shape of my problem. Consider a 2
parameter (both are type constructors) class:


class C f g where
  nest :: f a -> g a


I have instances for base types (analogous to the Identity monad).


class C IdL IdR where
  nest = ...


I also have transformers that I can apply to these base types and
instances that correspond to "lifting" the C type class property
through the transformers.


class C f g => C f (TransR g) where
  nest = ... code that involves the "nest" of the C f g instance ...


or


class C f g => C (TransL f) g where
  nest = ... code that involves the "nest" of the C f g instance ...


The simple version of my issue is that, give the instances so far, the
compiler won't derive an instance for T.


type T = C (TransL IdL) (TransR IdR)


The impasse is the ambiguity in the derivation from C IdL IdR to T.
One could apply first TransL or apply first TransR. The
"-fallow-overlapping-instances" type system extension fails to help
because there is no "most specific" instance.

The order of application of my transformers (i.e. transforming the
left or transforming the right parameter) does not seem to matter--I
have found no intuition that says the derivations ought to be
distinguishable in anyway.

My question: Is there a technique to allow such innocuous ambiguity in
instance declarations?

I experimented with introducing something akin to a trace in a third
parameter to the class which would disambiguate the derivation (by
specifying the order of the transformations; reminded me of "Strongly
typed heterogeneous collections"), but had no luck there (perhaps
someone else would). Because the ambiguity does not matter to me, I'd
be fine implementing a rule such as "always transform the left
parameter first", but I don't know how to/if I can formulate that in
Haskell.

I also tried to reduce the class to a single parameter, which
incorporated the the functors into a single type. The method of the
class needs those functor types available, so that approach sputtered
out.

Another issue is modularity: both of my attempts above would have
bloated the code using the class with the details needed to
disambiguate it. I certainly prefer the context "C f g" to one that
exposes the disambiguation. That is, I would highly prefer a solution
that allows h1 instead of h2.


h1 :: C f g => a type
h1 = ... some code with nest ...



h2 :: (C f g, DisambiguationHelper f g ?) => a type
h2 = ... some code with nest ...


My harrowing suspicion is that I will need to split the property into
two--something I can't readily see how to do.

Thanks for your time,
Nick
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] How to escape from typecheck error: Duplicate instance declarations ?

2013-01-25 Thread s9gf4ult
Hello, haskellers. I am trying to write some generic subtyping issue. Here 
upcast is always safe operation because of subtype is always behaves like the 
parrent type. downcast is not the safe becase of not every parrent type value 
can be converted to children type. Rangeable here is the typeclass of values 
in some range, so downcasting to Rang1 or Range2 or any other type, having 
instance for Rangeable can be done by checking if value is in proper range. 
The same for MultipleTo, downcasting can be done with checking if value is 
multiple to some value.

{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, FunctionalDependencies, 
FlexibleContexts, UndecidableInstances, OverlappingInstances, 
IncoherentInstances #-}

class SubtypeOf a b | a -> b where
  upcast :: a -> b
  downcastSafe :: b -> Maybe a
  downcast :: b -> a
  downcast b = case downcastSafe b of
Nothing -> error $ "can not downcast the value"
Just a -> a

class (Ord a) => Rangable t a | t -> a where
  lowLim :: t -> a
  highLim :: t -> a

class Packable t a | t -> a where
  pack :: a -> t
  unpack :: t -> a

class MultipleTo t a | t -> a where
  multiple :: t -> a
  
instance (Num a, Ord a, Rangable range a, Packable range a) => SubtypeOf range 
a where
  upcast = unpack
  downcastSafe b | b >= (lowLim $ pb) && b <= (highLim $ pb) = Just $ pb
 | otherwise = Nothing
where
  pb = pack b

instance (Integral a, Packable range a, MultipleTo range a) => SubtypeOf range 
a where
  upcast = unpack
  downcastSafe b | b `mod` (multiple pb) == 0 = Just pb
 | otherwise = Nothing
where
  pb = pack b

newtype Range1 a = Range1 {unRange1 :: a}
 deriving Show

instance (Num a, Ord a) => Rangable (Range1 a) a where
  lowLim _ = 0
  highLim _ = 10

instance (Num a, Ord a) => Packable (Range1 a) a where
  pack = Range1
  unpack = unRange1

newtype Range2 a = Range2 {unRange2 :: a}
   deriving Show

instance (Num a, Ord a) => Rangable (Range2 a) a where
  lowLim _ = -10
  highLim _ = 200

instance (Num a, Ord a) => Packable (Range2 a) a where
  pack = Range2
  unpack = unRange2

but there is compilation error:

Duplicate instance declarations:
  instance [incoherent] (Num a, Ord a, Rangable range a,
 Packable range a) =>
SubtypeOf range a
-- Defined at ...:22:10
  instance [incoherent] (Integral a, Packable range a,
 MultipleTo range a) =>
SubtypeOf range a
-- Defined at ...:29:10
Failed, modules loaded: none.

If I remove one of instances of SubtypeOf the program is compiling. How to 
write this instances properly, or to write proper type casting ?

Thanks

PS. My english is not very good, but I hope this is understandable.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] newbie question about "Functional dependencies conflict between instance declarations:".....

2013-07-05 Thread Nicholls, Mark
Hello,

I largely don't know what I'm doing or even trying to do, it is a voyage into 
the unknownbutif I go...

> {-# LANGUAGE MultiParamTypeClasses #-}
> {-# LANGUAGE FunctionalDependencies #-}
> {-# LANGUAGE FlexibleInstances #-}
> {-# LANGUAGE UndecidableInstances #-}

> class Foo x y | x -> y, y -> x
> instance Foo Integer Integer

That seems to workand my head seems to say...your created some sort of 
binary relation between 2 types...and made  a member of it...

Something like that anyway

Then I go

> data Bar

> instance Foo Bar x

Error!but I'm think I understand thisI can't claim that  is a 
member of Foo and  is member of Foo and preserve my functional 
dependencies, because  is now a member of Foo..

Bad programmer...


So how I naively go


> class NotAnInteger a

> instance (NotAnInteger x) => Foo Bar x

I haven't declared integer to be "NotAnInteger"so (in a closed 
world)this would seem to exclude the contradiction....but...


Functional dependencies conflict between instance declarations:
  instance Foo Integer Integer -- Defined at liam1.lhs:7:12
  instance NotAnInteger x => Foo Bar x -- Defined at liam1.lhs:13:12

So

i)I clearly don't understand something about the type 
system.

ii)   I don't know how to restrict type variables in instance 
declarationsi.e. how do I use the notion of "Foo" across different 
combinations of types, without them colliding.







CONFIDENTIALITY NOTICE

This e-mail (and any attached files) is confidential and protected by copyright 
(and other intellectual property rights). If you are not the intended recipient 
please e-mail the sender and then delete the email and any attached files 
immediately. Any further use or dissemination is prohibited.

While MTV Networks Europe has taken steps to ensure that this email and any 
attachments are virus free, it is your responsibility to ensure that this 
message and any attachments are virus free and do not affect your systems / 
data.

Communicating by email is not 100% secure and carries risks such as delay, data 
corruption, non-delivery, wrongful interception and unauthorised amendment. If 
you communicate with us by e-mail, you acknowledge and assume these risks, and 
you agree to take appropriate measures to minimise these risks when e-mailing 
us.

MTV Networks International, MTV Networks UK & Ireland, Greenhouse, Nickelodeon 
Viacom Consumer Products, VBSi, Viacom Brand Solutions International, Be 
Viacom, Viacom International Media Networks and VIMN and Comedy Central are all 
trading names of MTV Networks Europe.  MTV Networks Europe is a partnership 
between MTV Networks Europe Inc. and Viacom Networks Europe Inc.  Address for 
service in Great Britain is 17-29 Hawley Crescent, London, NW1 8TT.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: technique to allow innocuous ambiguity in instance declarations?

2006-07-11 Thread oleg

Nicolas Frisby posed a problem about controlling the order of
instance selection rules (or, the application of type improvement rules)

Given the following code

> newtype IdL a = IdL a
> newtype IdR a = IdR a
>
> class C f g where nest :: f a -> g a
>
> instance C IdL IdR where nest (IdL x) = IdR x
>
> newtype TransR f a = TransR (f a)
> newtype TransL f a = TransL (f a)
>
> instance C f g => C (TransL f) g where -- Instance1
> nest (TransL x) = nest x
>
> instance C f g => C f (TransR g) where -- Instance2
> nest x = TransR (nest x)

we can quite happily write

> test1 :: TransL IdL a -> IdR a
> test1 = nest

and ditto

> test2 :: IdL a -> TransR IdR a
> test2 = nest

but we can't write

> testx :: TransL IdL a -> TransR IdR a
> testx = nest

because the typechecker doesn't know which instance to choose: either
to attempt to improve constraints  as
   C (TransL IdL) (TransR IdR) --> C IdL (TransR IdR) -->
C IdL IdR
(choosing the Instance1 first)
or
   C (TransL IdL) (TransR IdR) --> C (TransL IdL) IdR -->
C IdL IdR
choosing Instance2 first.

One can see that the end result is just the same. But the typechecker
doesn't actually know that instances commute, so it reports the
ambiguity and quits. But suppose we do know that these particular
instances commute. How to impart this knowledge to the typechecker?
Or, simply, how to tell the typechecker to remove the ambiguity by
choosing Instance1 first?

It turns out, there is a simple way. It relies again on this quite
useful contraption, TypeCast. The idea is to introduce the most
general instance C f g. The typechecker will choose it if nothing more
specific applies. And then we examine f and g to see what we've got
and how to proceed from that. At that point, it's us who decides what
to improve first. The idea is similar to the one described in

  http://pobox.com/~oleg/ftp/Haskell/types.html#is-function-type

The complete code follows. Now testx typechecks.


> {-# OPTIONS -fglasgow-exts #-}
> {-# OPTIONS -fallow-undecidable-instances #-}
> {-# OPTIONS -fallow-overlapping-instances #-}
>
> module N where
>
> newtype IdL a = IdL a
> newtype IdR a = IdR a
>
> class C f g where nest :: f a -> g a
>
> instance C IdL IdR where nest (IdL x) = IdR x
>
> newtype TransR f a = TransR (f a)
> newtype TransL f a = TransL (f a)
>
> instance (IsTransL f b, C' b f g) => C f g where
> nest = nest' (undefined::b)
>
> class C' b f g where nest' :: b -> f a -> g a
>
> instance C f g => C' HTrue (TransL f) g where
> nest' _ (TransL x) = nest x
>
> instance C f g => C' HFalse f (TransR g) where
> nest' _ x = TransR (nest x)
>
> {- From the first attempt
> instance C f g => C (TransL f) g where
> nest (TransL x) = nest x
>
> instance C f g => C f (TransR g) where
> nest x = TransR (nest x)
> -}
>
> test1 :: TransL IdL a -> IdR a
> test1 = nest
>
> test2 :: IdL a -> TransR IdR a
> test2 = nest
>
>
> testx :: TransL IdL a -> TransR IdR a
> testx = nest
>
> data HTrue
> data HFalse
>
> class IsTransL (a :: * -> * ) b | a -> b
> instance TypeCast f HTrue => IsTransL (TransL y) f
> instance TypeCast f HFalse => IsTransL a f
>
>
> -- Our silver bullet
>
> class TypeCast   a b   | a -> b, b->a   where typeCast   :: a -> b
> class TypeCast'  t a b | t a -> b, t b -> a where typeCast'  :: t->a->b
> class TypeCast'' t a b | t a -> b, t b -> a where typeCast'' :: t->a->b
> instance TypeCast'  () a b => TypeCast a b where typeCast x = typeCast' () x
> instance TypeCast'' t a b => TypeCast' t a b where typeCast' = typeCast''
> instance TypeCast'' () a a where typeCast'' _ x  = x

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to escape from typecheck error: Duplicate instance declarations ?

2013-01-25 Thread Brandon Allbery
On Fri, Jan 25, 2013 at 3:18 PM,  wrote:

> Duplicate instance declarations:
>
> instance [incoherent] (Num a, Ord a, Rangable range a,
>
> Packable range a) =>
>
> SubtypeOf range a
>
> -- Defined at ...:22:10
>
> instance [incoherent] (Integral a, Packable range a,
>
> MultipleTo range a) =>
>
> SubtypeOf range a
>
> -- Defined at ...:29:10
>
>
This would be correct.  Constraints on an instance are applied *after* the
instance is selected, so when Haskell is looking for an instance, these two
are identical.

This has the code smell of trying to use typeclasses for OOP.  That won't
work.  (Yes, really.)

-- 
brandon s allbery kf8nh   sine nomine associates
allber...@gmail.com  ballb...@sinenomine.net
unix, openafs, kerberos, infrastructure, xmonadhttp://sinenomine.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to escape from typecheck error: Duplicate instance declarations ?

2013-01-25 Thread s9gf4ult
> This has the code smell of trying to use typeclasses for OOP.  That won't 
work.  (Yes, really.)

I am not trying to use OOP, I am just writing some typecasting at all. 

> This would be correct.  Constraints on an instance are applied *after* the 
instance is selected, so when Haskell is looking for an instance, these two 
are identical.

I didn't understand why these two instances are identical ? The constraints 
are different and OverlappingInstances should permit overlapping typeclasses 
in constraints and select more specific instance clause.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to escape from typecheck error: Duplicate instance declarations ?

2013-01-25 Thread s9gf4ult
http://ideone.com/v2CrAm

I has posted to ideone to show what is wrong.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to escape from typecheck error: Duplicate instance declarations ?

2013-01-25 Thread Alexander Solla
On Fri, Jan 25, 2013 at 12:39 PM,  wrote:

> **
>
> > This has the code smell of trying to use typeclasses for OOP.  That
> won't work.  (Yes, really.)
>
>
>
> I am not trying to use OOP, I am just writing some typecasting at all.
>
>
>
> > This would be correct.  Constraints on an instance are applied *after*
> the instance is selected, so when Haskell is looking for an instance, these
> two are identical.
>
>
>
> I didn't understand why these two instances are identical ? The
> constraints are different and OverlappingInstances should permit
> overlapping typeclasses in constraints and select more specific instance
> clause.
>

They are identical because constraints don't "count" for deciding that a
type is in a class.   For the purposes of deciding if a type is in a class,

instance Foo (Bar a)
instance Fizz a => Foo (Bar a)
instance Fuzz a => Foo (Bar a)

are exactly the same, and all three are therefore overlapping instances.
 None is more specific, because they all refer to the same type -- (Bar a).

Also, you can just use Typeable instead of that downcasting stuff.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] newbie question about "Functional dependencies conflict between instance declarations:".....

2013-07-05 Thread Erik Hesselink
The constraint on an instance never influences which instance is
selected. So as far as instance selection goes, 'instance Foo x' and
'instance C x => Foo x' are the same. The constraint is only checked
after the instance is selected.

Erik

On Fri, Jul 5, 2013 at 2:43 PM, Nicholls, Mark  wrote:
> Hello,
>
>
>
> I largely don’t know what I’m doing or even trying to do, it is a voyage
> into the unknown….but….if I go…
>
>
>
>> {-# LANGUAGE MultiParamTypeClasses #-}
>
>> {-# LANGUAGE FunctionalDependencies #-}
>
>> {-# LANGUAGE FlexibleInstances #-}
>
>> {-# LANGUAGE UndecidableInstances #-}
>
>
>
>> class Foo x y | x -> y, y -> x
>
>> instance Foo Integer Integer
>
>
>
> That seems to work….and my head seems to say…your created some sort of
> binary relation between 2 types…and made  a member of it…
>
>
>
> Something like that anyway….
>
>
>
> Then I go….
>
>
>
>> data Bar
>
>
>
>> instance Foo Bar x
>
>
>
> Error!but I’m think I understand this….I can’t claim that  is a
> member of Foo and  is member of Foo and preserve my
> functional dependencies, because  is now a member of Foo..
>
>
>
> Bad programmer…….
>
>
>
>
>
> So how I naively go….
>
>
>
>
>
>> class NotAnInteger a
>
>
>
>> instance (NotAnInteger x) => Foo Bar x
>
>
>
> I haven’t declared integer to be “NotAnInteger”….so (in a closed
> world)….this would seem to exclude the contradiction….but…
>
>
>
>
>
> Functional dependencies conflict between instance declarations:
>
>   instance Foo Integer Integer -- Defined at liam1.lhs:7:12
>
>   instance NotAnInteger x => Foo Bar x -- Defined at liam1.lhs:13:12
>
>
>
> So
>
> i)I clearly don’t understand something about the type
> system.
>
> ii)   I don’t know how to restrict type variables in
> instance declarations….i.e. how do I use the notion of “Foo” across
> different combinations of types, without them colliding.
>
>
>
>
>
>
>
>
>
>
>
>
>
>
>
>
>
> CONFIDENTIALITY NOTICE
>
> This e-mail (and any attached files) is confidential and protected by
> copyright (and other intellectual property rights). If you are not the
> intended recipient please e-mail the sender and then delete the email and
> any attached files immediately. Any further use or dissemination is
> prohibited.
>
> While MTV Networks Europe has taken steps to ensure that this email and any
> attachments are virus free, it is your responsibility to ensure that this
> message and any attachments are virus free and do not affect your systems /
> data.
>
> Communicating by email is not 100% secure and carries risks such as delay,
> data corruption, non-delivery, wrongful interception and unauthorised
> amendment. If you communicate with us by e-mail, you acknowledge and assume
> these risks, and you agree to take appropriate measures to minimise these
> risks when e-mailing us.
>
> MTV Networks International, MTV Networks UK & Ireland, Greenhouse,
> Nickelodeon Viacom Consumer Products, VBSi, Viacom Brand Solutions
> International, Be Viacom, Viacom International Media Networks and VIMN and
> Comedy Central are all trading names of MTV Networks Europe.  MTV Networks
> Europe is a partnership between MTV Networks Europe Inc. and Viacom Networks
> Europe Inc.  Address for service in Great Britain is 17-29 Hawley Crescent,
> London, NW1 8TT.
>
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] newbie question about "Functional dependencies conflict between instance declarations:".....

2013-07-05 Thread Tikhon Jelvis
You're running into the "open world"assumption--anybody could come along
and make Integer part of your NotAnInteger class, and there's nothing you
can do to stop them. This is a design tradeoff for typeclasses: typeclass
instances are always global and are exported to all other modules you use.
This means you cannot ensure a type is *not* part of a typeclass. (Or, at
the very least, you can't convince GHC of this fact.)

For more information about this, take a look at the following StackOverflow
question:
http://stackoverflow.com/questions/8728596/explicitly-import-instances
On Jul 5, 2013 8:47 AM, "Nicholls, Mark"  wrote:

>  Hello,
>
> ** **
>
> I largely don’t know what I’m doing or even trying to do, it is a voyage
> into the unknown….but….if I go…
>
> ** **
>
> > {-# LANGUAGE MultiParamTypeClasses #-}
>
> > {-# LANGUAGE FunctionalDependencies #-}
>
> > {-# LANGUAGE FlexibleInstances #-}
>
> > {-# LANGUAGE UndecidableInstances #-}
>
> ** **
>
> > class Foo x y | x -> y, y -> x
>
> > instance Foo Integer Integer
>
> ** **
>
> That seems to work….and my head seems to say…your created some sort of
> binary relation between 2 types…and made  a member of it…
> 
>
> ** **
>
> Something like that anyway….
>
> ** **
>
> Then I go….
>
> ** **
>
> > data Bar
>
> ** **
>
> > instance Foo Bar x
>
> ** **
>
> Error!but I’m think I understand this….I can’t claim that  is a
> member of Foo and  is member of Foo and preserve my
> functional dependencies, because  is now a member of Foo..***
> *
>
> ** **
>
> Bad programmer…….
>
> ** **
>
> ** **
>
> So how I naively go….
>
> ** **
>
> ** **
>
> > class NotAnInteger a
>
> ** **
>
> > instance (NotAnInteger x) => Foo Bar x
>
> ** **
>
> I haven’t declared integer to be “NotAnInteger”….so (in a closed
> world)….this would seem to exclude the contradiction….but…
>
> ** **
>
> ** **
>
> Functional dependencies conflict between instance declarations:
>
>   instance Foo Integer Integer -- Defined at liam1.lhs:7:12
>
>   instance NotAnInteger x => Foo Bar x -- Defined at liam1.lhs:13:12**
> **
>
> ** **
>
> So 
>
> **i)**I clearly don’t understand something about the
> type system.
>
> **ii)   **I don’t know how to restrict type variables in
> instance declarations….i.e. how do I use the notion of “Foo” across
> different combinations of types, without them colliding.
>
> ** **
>
> ** **
>
> ** **
>
> ** **
>
> ** **
>
> ** **
>
> ** **
>
>
>
> CONFIDENTIALITY NOTICE
>
> This e-mail (and any attached files) is confidential and protected by
> copyright (and other intellectual property rights). If you are not the
> intended recipient please e-mail the sender and then delete the email and
> any attached files immediately. Any further use or dissemination is
> prohibited.
>
> While MTV Networks Europe has taken steps to ensure that this email and
> any attachments are virus free, it is your responsibility to ensure that
> this message and any attachments are virus free and do not affect your
> systems / data.
>
> Communicating by email is not 100% secure and carries risks such as delay,
> data corruption, non-delivery, wrongful interception and unauthorised
> amendment. If you communicate with us by e-mail, you acknowledge and assume
> these risks, and you agree to take appropriate measures to minimise these
> risks when e-mailing us.
>
> MTV Networks International, MTV Networks UK & Ireland, Greenhouse,
> Nickelodeon Viacom Consumer Products, VBSi, Viacom Brand Solutions
> International, Be Viacom, Viacom International Media Networks and VIMN and
> Comedy Central are all trading names of MTV Networks Europe.  MTV Networks
> Europe is a partnership between MTV Networks Europe Inc. and Viacom
> Networks Europe Inc.  Address for service in Great Britain is 17-29 Hawley
> Crescent, London, NW1 8TT.
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] newbie question about "Functional dependencies conflict between instance declarations:".....

2013-07-05 Thread Nicholls, Mark
Ah

So it isn't a closed world

So how do I stop my instances clashing?

The "x" in

instance Foo Bar x

is never intended to be Integer.



Mark Nicholls | Lead broadcast & corporate architect, Programmes & Development 
- Viacom International Media Networks
A: 17-29 Hawley Crescent London NW1 8TT | e: 
nicholls.m...@vimn.com<mailto:m...@vimn.com> T: +44 (0)203 580 2223

[Description: cid:image001.png@01CD488D.9204D030]

From: Tikhon Jelvis [mailto:tik...@jelv.is]
Sent: 05 July 2013 2:08 PM
To: Nicholls, Mark
Cc: haskell-cafe
Subject: Re: [Haskell-cafe] newbie question about "Functional dependencies 
conflict between instance declarations:".


You're running into the "open world"assumption--anybody could come along and 
make Integer part of your NotAnInteger class, and there's nothing you can do to 
stop them. This is a design tradeoff for typeclasses: typeclass instances are 
always global and are exported to all other modules you use. This means you 
cannot ensure a type is *not* part of a typeclass. (Or, at the very least, you 
can't convince GHC of this fact.)

For more information about this, take a look at the following StackOverflow 
question: http://stackoverflow.com/questions/8728596/explicitly-import-instances
On Jul 5, 2013 8:47 AM, "Nicholls, Mark" 
mailto:nicholls.m...@vimn.com>> wrote:
Hello,

I largely don't know what I'm doing or even trying to do, it is a voyage into 
the unknownbutif I go...

> {-# LANGUAGE MultiParamTypeClasses #-}
> {-# LANGUAGE FunctionalDependencies #-}
> {-# LANGUAGE FlexibleInstances #-}
> {-# LANGUAGE UndecidableInstances #-}

> class Foo x y | x -> y, y -> x
> instance Foo Integer Integer

That seems to workand my head seems to say...your created some sort of 
binary relation between 2 types...and made  a member of it...

Something like that anyway

Then I go

> data Bar

> instance Foo Bar x

Error!but I'm think I understand thisI can't claim that  is a 
member of Foo and  is member of Foo and preserve my functional 
dependencies, because  is now a member of Foo..

Bad programmer...


So how I naively go


> class NotAnInteger a

> instance (NotAnInteger x) => Foo Bar x

I haven't declared integer to be "NotAnInteger"so (in a closed 
world)this would seem to exclude the contradictionbut...


Functional dependencies conflict between instance declarations:
  instance Foo Integer Integer -- Defined at liam1.lhs:7:12
  instance NotAnInteger x => Foo Bar x -- Defined at liam1.lhs:13:12

So

i)    I clearly don't understand something about the type 
system.

ii)   I don't know how to restrict type variables in instance 
declarationsi.e. how do I use the notion of "Foo" across different 
combinations of types, without them colliding.









CONFIDENTIALITY NOTICE

This e-mail (and any attached files) is confidential and protected by copyright 
(and other intellectual property rights). If you are not the intended recipient 
please e-mail the sender and then delete the email and any attached files 
immediately. Any further use or dissemination is prohibited.

While MTV Networks Europe has taken steps to ensure that this email and any 
attachments are virus free, it is your responsibility to ensure that this 
message and any attachments are virus free and do not affect your systems / 
data.

Communicating by email is not 100% secure and carries risks such as delay, data 
corruption, non-delivery, wrongful interception and unauthorised amendment. If 
you communicate with us by e-mail, you acknowledge and assume these risks, and 
you agree to take appropriate measures to minimise these risks when e-mailing 
us.

MTV Networks International, MTV Networks UK & Ireland, Greenhouse, Nickelodeon 
Viacom Consumer Products, VBSi, Viacom Brand Solutions International, Be 
Viacom, Viacom International Media Networks and VIMN and Comedy Central are all 
trading names of MTV Networks Europe.  MTV Networks Europe is a partnership 
between MTV Networks Europe Inc. and Viacom Networks Europe Inc.  Address for 
service in Great Britain is 17-29 Hawley Crescent, London, NW1 8TT.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org<mailto:Haskell-Cafe@haskell.org>
http://www.haskell.org/mailman/listinfo/haskell-cafe
CONFIDENTIALITY NOTICE

This e-mail (and any attached files) is confidential and protected by copyright 
(and other intellectual property rights). If you are not the intended recipient 
please e-mail the sender and then delete the email and any attached files 
immediately. Any further use or dissemination is prohibited.

While MTV Networks Europe has taken steps to ensure that this email and any 
attachments are virus free, it is your