[Haskell-cafe] Question related to Multi Param Type Classes

2008-05-05 Thread Sai Hemanth K
Hi,

I declared a multi param type class as below:
*class MyString m c  where
  zIndex  :: m - Int - c
  zLength :: m - Int
  zPack   :: [c] - m
  zEquals :: c -c - Bool
  zWrap   :: [c] - (m,AnExistingDataType)*

In the end I did not needed it for my program, but for those few minutes I
played with the idea, I came across a zillion questions.
Can some body help me here please?
When I defined a function like below,
\begin{code}
compareStr::(MyString m c) = (m,Int) -(m,Int)-Int-Int
compareStr (s1,pos1) (s2,pos2) soFar
   | (pos1  zLength  s1)   (pos2  zLength s2) =  let
  c1 =
zIndex s1 pos1
  c2 =
zIndex s2 pos2
in
  if(zEquals
c1 c2)then
  compareStr (s1,(pos1 + 1)) (s2, (pos2
+ 1)) (soFar + 1)
  else soFar

   | otherwise= soFar
\end{code}

when I loaded it on ghci ( invoked with -XMultiParamTypeClasses ), I got an
essay in greek (or is it latin?), which started something like below:
Could not deduce (MyString m c) from the context (MyString m c4)
  arising from a use of `zLength' at GenericZAlgo.lhs:42:21-31
Possible fix:
  add (MyString m c) to the context of
the type signature for `compareStr'
In the second argument of `()', namely `zLength s1'
In the first argument of `()', namely `(pos1  zLength s1)'
In a pattern guard for
   the definition of `compareStr':
  (pos1  zLength s1)  (pos2  zLength s2)

And if I let the type inference run the show, the type it shows is :
compareStr :: (MyString t c2,
   MyString m c2,
   Num a,
   MyString t1 c2,
   MyString t c,
   MyString t1 c1) =
  (t, Int) - (t1, Int) - a - a

And puzzlingly, if I try the same thing myself and reload it on the ghci,I
still get similar error.  I can go on about other 'puzzles'.

Can some one please tell me whats going on here?

Apologies, if it is something that's been documented left to right, top to
bottom, but I could not get  anywhere readily. Any pointers to the right
documentation will be much appreciated.
On the surface it looks like something that n00bs like yours truly better
stay away. But  I have a feeling that this one may throw some more light on
type inference.

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


Re: [Haskell-cafe] Question related to Multi Param Type Classes

2008-05-05 Thread Bulat Ziganshin
Hello Sai,

Monday, May 5, 2008, 7:52:29 PM, you wrote:

 class MyString m c  where

it should be

class MyString m c | m-c where

so ghc will realize that same m means the same c. read about
functional dependencies in ghc user manual

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Question related to Multi Param Type Classes

2008-05-05 Thread Ryan Ingram
On 5/5/08, Brandon S. Allbery KF8NH [EMAIL PROTECTED] wrote:
 The functional dependency MyString m c | m - c tells GHC that any
 specific m determines a specific c.  It doesn't matter what the type is
 here, since it's not used in the definition of compareStr; but it must be
 possible to know that the same c is being used in both arguments.  Given
 this, it can fix MyString m c knowing only m and as a result the
 function typechecks.

Although this still makes it impossible to call zEquals for the same
reason; you need a dependency in both directions for it to make sense.

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


Re: multi param type classes

1998-07-09 Thread Fergus Henderson

On 08-Jul-1998, Johannes Waldmann [EMAIL PROTECTED] wrote:
...
 how would you resolve ambiguities?
 probably by requiring an explicit type signature
 at the point of usage.
 
 fine, but then i'd like to have this in other cases as well,
 finally arriving at Ada-style overloading
 (a name may have several meanings
 as long as they can be distinguished by their type)
 
 then i could write  size :: [a] - Int; size :: Tree a - Int,
 and the two things are completely unrelated.

FYI, the logic/functional language Mercury supports exactly that
kind of overloading.  I found the Haskell requirement that
every data constructor have a different name quite annoying:
I wound up including the type name in the data constructor names
to ensure uniqueness.  This is a pain, because you then end up
effectively type-qualifying *every* occurrence of the data constructors,
rather than only type-qualifying the ones that would otherwise be ambiguous.

-- 
Fergus Henderson [EMAIL PROTECTED]  |  "I have always known that the pursuit
WWW: http://www.cs.mu.oz.au/~fjh  |  of excellence is a lethal habit"
PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.





Re: multi param type classes

1998-07-09 Thread Fergus Henderson

On 08-Jul-1998, Mariano Suarez Alvarez [EMAIL PROTECTED] wrote:
 On Wed, 8 Jul 1998 [EMAIL PROTECTED] wrote:
 
  Each expression then has a set of possible types, and the ambiguity is   
  resolved by an explicit type signature.
  
  At present it is quite frustrating in Haskell that when a name is used in   
  one place it is then lost for use in any other context -- the example of   
  an overloaded size function strikes me as very sound.
 
 I don't see why something like
 
   class HasSize a where
 size :: a - Int
 
 doesn't solve this...

Well, for one thing, that only helps with functions, not with data
constructors.  Also, not every occurrence of `size' need have type
`a - Int', and even if they do, the `class' declaration doesn't help
unless you modify the existing uses of the name `size', which you may
not be able to do.  The point is that you often have *unrelated*
occurrences of the same name.  This is especially true if you use
unqualified imports; two modules may use the same name for entirely
different purposes.  In that situation, Haskell forces you to resolve
the issue at module import time, even if the different uses of that
name could be disambiguated by the context, and in fact even if you
don't even make use of the overloaded name at all.

-- 
Fergus Henderson [EMAIL PROTECTED]  |  "I have always known that the pursuit
WWW: http://www.cs.mu.oz.au/~fjh  |  of excellence is a lethal habit"
PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.





Re: multi param type classes

1998-07-08 Thread Johannes Waldmann

Ralf, 

you want to lift this restriction:

 The type of each class operation 
 must mention all of the class type variables.

how would you resolve ambiguities?
probably by requiring an explicit type signature
at the point of usage.

fine, but then i'd like to have this in other cases as well,
finally arriving at Ada-style overloading
(a name may have several meanings
as long as they can be distinguished by their type)

then i could write  size :: [a] - Int; size :: Tree a - Int,
and the two things are completely unrelated.
at the moment, i could make [] and Tree an instance
of a class that has `size' as a method (feels clumsy)
or write sizeList and sizeTree (feels bad as well:
what is part of the name here is really a type signature).

of course this would break the general Haskell idea
that every expression has a unique type 
that can be reconstructed by the compiler.
but this is broken anyway (you need type annotations here and there),
and is it a good design goal?

why would you want it? for easier compilation?
for easier programming? an Haskell where i'd have to declare
the type for some, or even each, let-bound variable
doesn't feel that horrendous to me. plenty of other languages
require typed declarations.

best regards,
-- 
Dr Johannes Waldmann  Institut fur InformatikUniversitat Leipzig   
[EMAIL PROTECTED] http://www.informatik.uni-leipzig.de/~joe/
PF 920,  D-04009  Leipzig,  Germany   Tel/Fax (+49) 341 97 32204 / 32209






Re: multi param type classes

1998-07-08 Thread Ralf Hinze

 you want to lift this restriction:
 
  The type of each class operation 
  must mention all of the class type variables.
 
 how would you resolve ambiguities?
 probably by requiring an explicit type signature
 at the point of usage.

No longer ;-). I find SPJ's summary on

http://www.dcs.gla.ac.uk/~simonpj/multi-param.html

convincing. The point is that you simply _cannot_ resolve the ambiguity
at the point of usage. Furthermore, an alternative is at hand (for the
motivating example I gave).

Ralf





Re: multi param type classes

1998-07-08 Thread S. Alexander Jacobson

I think Simon or Alastair promised this in 2.0 (though it doesn't appear
on the list for 2.0...)

-Alex-

On Thu, 9 Jul 1998, Fergus Henderson wrote:

 On 08-Jul-1998, Johannes Waldmann [EMAIL PROTECTED] wrote:
 ...
  how would you resolve ambiguities?
  probably by requiring an explicit type signature
  at the point of usage.
  
  fine, but then i'd like to have this in other cases as well,
  finally arriving at Ada-style overloading
  (a name may have several meanings
  as long as they can be distinguished by their type)
  
  then i could write  size :: [a] - Int; size :: Tree a - Int,
  and the two things are completely unrelated.
 
 FYI, the logic/functional language Mercury supports exactly that
 kind of overloading.  I found the Haskell requirement that
 every data constructor have a different name quite annoying:
 I wound up including the type name in the data constructor names
 to ensure uniqueness.  This is a pain, because you then end up
 effectively type-qualifying *every* occurrence of the data constructors,
 rather than only type-qualifying the ones that would otherwise be ambiguous.
 
 -- 
 Fergus Henderson [EMAIL PROTECTED]  |  "I have always known that the pursuit
 WWW: http://www.cs.mu.oz.au/~fjh  |  of excellence is a lethal habit"
 PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.
 

___
S. Alexander Jacobson   i2x Media  
1-212-697-0184 voice1-212-697-1427 fax






Query on multi-param type classes

1998-01-30 Thread Jon Mountjoy


Hello,

I decided to try and get my old multi-param. parser to work,
and got told-off by Haskell's parser:

Please tell me what I am doing wrong.  The following program:

 module A where
  
 class (Monad m, Monad (t m)) = AMonadT t m where
   lift :: m a - t m a

Gives me:

(lambda o) ghc -fglasgow-exts A.hs  
A.hs:3:23: parse error on input: "("

Thanks,
Jon
--

The Glorious Glasgow Haskell Compilation System, version 3.00, patchlevel 0

Effective command line: -fglasgow-exts -v

Ineffective C pre-processor:
echo '{-# LINE 1 "A.hs" -}'  /tmp/ghc19403.cpp  cat A.hs  
/tmp/ghc19403.cpp

real0.0
user0.0
sys 0.0
ghc:compile:Output file A.o doesn't exist
ghc:recompile:Input file A.hs newer than A.o

Haskell compiler:
/home/jon/FunctionalLanguages/GHC-3.00//lib/hsc ,-N ,-W ,/tmp/ghc19403.cpp  
-fglasgow-exts -fignore-interface-pragmas -fomit-interface-pragmas -fsimplify [  
-ffloat-lets-exposing-whnf -ffloat-primops-ok -fcase-of-case -fdo-case-elim 
-freuse-con -fpedantic-bottoms -fsimpl-uf-use-threshold3 -fmax-simplifier-iterations4  
]   -fwarn-overlapping-patterns -fwarn-missing-methods -fwarn-duplicate-exports 
-himap=.%.hi:/home/jon/FunctionalLanguages/GHC-3.00//lib/imports%.hi   -v 
-hifile=/tmp/ghc19403.hi -S=/tmp/ghc19403.s +RTS -H600 -K100
Glasgow Haskell Compiler, version 3.00, for Haskell 1.4
A.hs:3:23: parse error on input: "("

real0.1
user0.0
sys 0.1
deleting... /tmp/ghc19403.cpp /tmp/ghc19403.hi /tmp/ghc19403.s

rm -f /tmp/ghc19403*



Re: Query on multi-param type classes

1998-01-30 Thread Ralf Hinze

Dear Jon, dear Simon,

   class (Monad m, Monad (t m)) = AMonadT t m where
 lift :: m a - t m a

 I'm frankly unsure of the consequences of lifting the 
 restriction.  Can you give a compact summary of why you want
 to?  Our multi-parameter type-class paper gives none, and if
 you've got one I'd like to add it.

I would suspect that the context `only' lists an invariant which
should hold and that one can do with `class (Monad m) =' alone.
Give it a try (it worked for me all (most?) of the time).

Cheers, Ralf



Re: Query on multi-param type classes

1998-01-30 Thread Keith S. Wansbrough

   A.hs:3:23: parse error on input: "("
 
 I should have said that I've implemented the choices given
 on the Standard Haskell web discussion page.  In particular:
 
 ===
 Choice 7a
 ~
 
 The context in a class declaration (which introduces superclasses)
 must constrain only type variables.  For example, this is legal:
 
 class (Foo a b, Baz b b) = Flob a b where ...
 but not
 class (Foo [a] b, Baz (a,b) b) = Flob a b where ...
 
 It might be possible to relax this restriction (which is the same
 as in current Haskell) without losing decideability, but we're not
 sure.  Choice 7a is conservative, and we don't know of any examples
 that motivate relaxing the restriction.
 ===
 
 I'm frankly unsure of the consequences of lifting the 
 restriction.  Can you give a compact summary of why you want
 to?  Our multi-parameter type-class paper gives none, and if
 you've got one I'd like to add it.
 
 In the short term, you're stuck.  Damn!  First customer too!

I ran into *exactly* the same problem with my own monad transformer
code, but haven't reported it yet because there's a lot of other stuff
I need to do to massage it into GHC-friendly form.

The problem is, the above parens appear in the standard definition of
a monad transformer, the motivating example for MPCs in the first
place!

Consider the state monad transformer:

 type StateT s m v = s - m (v,s)
 
 instance Monad m = Monad (StateT s m) where
   return v = \s - return (v,s)
   m = f  = \s - m s  = \(v,s') - 
(f v) s
 
 instance (Monad m, Monad (StateT s m))   -- here is the problem
   = MonadT (StateT s) m where
   lift m = \s - m = \v -
  return (v,s)
 
 class Monad m = StateMonad s m where
   getS :: m s
   setS :: s - m ()
 
 instance Monad m = StateMonad s (StateT s m) where
   getS   = \s - return (s ,s)
   setS s = \_ - return ((),s)
 
 instance (StateMonad s m, MonadT t m)
   = StateMonad s (t m) where
   getS   = lift getS
   setS s = lift (setS s)

Note we assume here the definition of MonadT:

 class (Monad m, Monad (t m)) = MonadT t m where  -- here again
   liftM :: m a - t m a

You can see the two lines that violate 7a.

 Simon

--KW 8-)
-- 
: Keith Wansbrough, MSc, BSc(Hons) (Auckland) -:
: PhD Student, Computing Science, University of Glasgow, Scotland. :
: Native of Antipodean Auckland, New Zealand: 174d47' E, 36d55' S. :
: http://www.dcs.gla.ac.uk/~keithw/  mailto:[EMAIL PROTECTED]   :
:--:



Re: Query on multi-param type classes

1998-01-30 Thread Simon L Peyton Jones


 I decided to try and get my old multi-param. parser to work,
 and got told-off by Haskell's parser:
 
 Please tell me what I am doing wrong.  The following program:
 
  module A where
   
  class (Monad m, Monad (t m)) = AMonadT t m where
lift :: m a - t m a
 
 Gives me:
 
 (lambda o) ghc -fglasgow-exts A.hs
  A.hs:3:23: parse error on input: "("

I should have said that I've implemented the choices given
on the Standard Haskell web discussion page.  In particular:

===
Choice 7a
~

The context in a class declaration (which introduces superclasses)
must constrain only type variables.  For example, this is legal:

class (Foo a b, Baz b b) = Flob a b where ...
but not
class (Foo [a] b, Baz (a,b) b) = Flob a b where ...

It might be possible to relax this restriction (which is the same
as in current Haskell) without losing decideability, but we're not
sure.  Choice 7a is conservative, and we don't know of any examples
that motivate relaxing the restriction.
===

I'm frankly unsure of the consequences of lifting the 
restriction.  Can you give a compact summary of why you want
to?  Our multi-parameter type-class paper gives none, and if
you've got one I'd like to add it.

In the short term, you're stuck.  Damn!  First customer too!

Simon