Re: [Haskell-cafe] Re: type class question

2007-12-10 Thread Bertram Felgenhauer
Peter Padawitz wrote:
> Jules Bean wrote:
>> I don't see why!
>>
>> In the class
>>
>> class Foo a where
>>   f :: a -> Int
>>   g :: b -> Integer
>>   g = fromIntegral . f
>>
>> The equations within the class are defaults, not equations. 
>
> I must admit that I didn't know this... Nevertheless, won't you agree that 
> the default and the actual instance should be semantically equivalent?

It depends on the class, or maybe on your notion of semantical
equivalence. As an example, look at the Show class. Its interface is

> class Show a where
>   showsPrec :: Int -> a -> ShowS
>   show :: a -> String
>   showList :: [a] -> ShowS

showsPrec has a default implementation in terms of show, and show
a default implementation in terms of showsPrec. Instances may refine
showsPrec but should still satisfy  show x = shows x "".

However, the most interesting function here is showList. It comes
with a default implementation that renders a list as "[item1,...]".

showList is used in the Show instance for lists:

> instance Show a => Show [a]  where
> showsPrec _ = showList

By redefining showList for Char, we get a prettier representation
for String values.

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


Re: [Haskell-cafe] Re: type class question

2007-12-10 Thread Peter Padawitz

Jules Bean wrote:


Peter Padawitz wrote:


Jules Bean wrote:


Peter Padawitz wrote:

What is so bad about making compFoo part of the class? It reduces 
the code (constraints can be avoided) and reflects the close 
connection between  a signature Sig (implemented by the class) and 
the evaluation (compFoo) of Sig-terms in Sig-algebras.


making it part of the class allows instances to override the 
implementation.


Which in this case is a strange thing to do.


Sure, but this can only happen because Haskell does not check whether 
the instances satisfy the equations in the class. The type class 
concept would be "cleaner" if all methods (partially or totally) 
defined by equations within the class were not allowed to be 
instantiated!



I don't see why!

In the class

class Foo a where
  f :: a -> Int
  g :: b -> Integer
  g = fromIntegral . f

The equations within the class are defaults, not equations. 


I must admit that I didn't know this... Nevertheless, won't you agree 
that the default and the actual instance should be semantically equivalent?



The equation for 'g' is a default, not a rule.

If you want equations, you do it outside the class. I have written 
that class wrongly, I should actually write g = fromIntegral . f as a 
function outside the class, thus guaranteeing the implementation and 
stopping people breaking that invariant.


The purpose of methods with defaults is to allow the possibility that 
there is an obvious natural way to implement one function in terms of 
others, but there might be more efficient ways.


For example, the Foldable class should (but doesn't) have a member 
length. This could be defaulted to length . toList, but have a more 
efficient implementation in Sequence, which stores its own length anyway.


Or maybe we are at cross-purposes.


No no, default functions make sense.

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


Re: [Haskell-cafe] Re: type class question

2007-12-10 Thread Jules Bean

Peter Padawitz wrote:

Jules Bean wrote:


Peter Padawitz wrote:

What is so bad about making compFoo part of the class? It reduces the 
code (constraints can be avoided) and reflects the close connection 
between  a signature Sig (implemented by the class) and the 
evaluation (compFoo) of Sig-terms in Sig-algebras.



making it part of the class allows instances to override the 
implementation.


Which in this case is a strange thing to do.


Sure, but this can only happen because Haskell does not check whether 
the instances satisfy the equations in the class. The type class concept 
would be "cleaner" if all methods (partially or totally) defined by 
equations within the class were not allowed to be instantiated!




I don't see why!

In the class

class Foo a where
  f :: a -> Int
  g :: b -> Integer
  g = fromIntegral . f

The equations within the class are defaults, not equations. The equation 
for 'g' is a default, not a rule.


If you want equations, you do it outside the class. I have written that 
class wrongly, I should actually write g = fromIntegral . f as a 
function outside the class, thus guaranteeing the implementation and 
stopping people breaking that invariant.


The purpose of methods with defaults is to allow the possibility that 
there is an obvious natural way to implement one function in terms of 
others, but there might be more efficient ways.


For example, the Foldable class should (but doesn't) have a member 
length. This could be defaulted to length . toList, but have a more 
efficient implementation in Sequence, which stores its own length anyway.


Or maybe we are at cross-purposes.

Jules

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


Re: [Haskell-cafe] Re: type class question

2007-12-10 Thread Peter Padawitz

Jules Bean wrote:


Peter Padawitz wrote:

What is so bad about making compFoo part of the class? It reduces the 
code (constraints can be avoided) and reflects the close connection 
between  a signature Sig (implemented by the class) and the 
evaluation (compFoo) of Sig-terms in Sig-algebras.



making it part of the class allows instances to override the 
implementation.


Which in this case is a strange thing to do.


Sure, but this can only happen because Haskell does not check whether 
the instances satisfy the equations in the class. The type class concept 
would be "cleaner" if all methods (partially or totally) defined by 
equations within the class were not allowed to be instantiated!


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


Re: [Haskell-cafe] Re: type class question

2007-12-10 Thread Jules Bean

Peter Padawitz wrote:
What is so bad about making compFoo part of the class? It reduces the 
code (constraints can be avoided) and reflects the close connection 
between  a signature Sig (implemented by the class) and the evaluation 
(compFoo) of Sig-terms in Sig-algebras.


making it part of the class allows instances to override the implementation.

Which in this case is a strange thing to do.

Class methods are ad-hoc. They can do *anything*.

Functions which happen to have constraints are something a bit more 
parametric. Their "ad-hoc-ness" is bounded by the methods of the class; 
they can only be implemented using methods, so they are guaranteed to be 
 uniform to some extent.


For example:

sort is a function with an Ord constraint. If sort was part of the Ord 
class, then every ordered type would be free to supply its own sort 
routine, possibly faster, possibly broken. Writing sort as a function 
rather than a method makes it generic (parametric) over all members of 
class Ord.


Jules


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


Re: [Haskell-cafe] Re: type class question

2007-12-10 Thread Peter Padawitz

Jules Bean wrote:


Try again without missing out the list...

Peter Padawitz wrote:
> Jules Bean wrote:
>> Incidentally, I question why the "compFoo" are methods. Why not 
just make them polymorphic functions? They don't look like you expect 
instances to change them. The code continues to compile if I make them 
functions and amend their signatures as required.

>
> I put compFoo into the class for the same reason why /= is part of 
the class Eq: both functions are unique as soon as the others have 
been instantiated.


I believe you misunderstand the reason.

/= is part of Eq in case a particular instance has a particularly 
efficient way to implement /=, rather than using not and (==).


"Being unique as soon as the others are implemented" is not a reason 
not to make it a method.


It might not have been the reason, but it is a nice effect that is often 
taken advantage of.


What is so bad about making compFoo part of the class? It reduces the 
code (constraints can be avoided) and reflects the close connection 
between  a signature Sig (implemented by the class) and the evaluation 
(compFoo) of Sig-terms in Sig-algebras.



compBlock :: (Java block command intE boolE) => Block -> block
compBlock = block_ . map compCommand

still retains that property.


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


Re: [Haskell-cafe] Re: type class question

2007-12-10 Thread Jules Bean

Try again without missing out the list...

Peter Padawitz wrote:
> Jules Bean wrote:
>> Incidentally, I question why the "compFoo" are methods. Why not just 
make them polymorphic functions? They don't look like you expect 
instances to change them. The code continues to compile if I make them 
functions and amend their signatures as required.

>
> I put compFoo into the class for the same reason why /= is part of 
the class Eq: both functions are unique as soon as the others have been 
instantiated.


I believe you misunderstand the reason.

/= is part of Eq in case a particular instance has a particularly 
efficient way to implement /=, rather than using not and (==).


"Being unique as soon as the others are implemented" is not a reason not 
to make it a method.



compBlock :: (Java block command intE boolE) => Block -> block
compBlock = block_ . map compCommand

still retains that property.

Jules


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


[Haskell-cafe] Re: type class question

2007-12-10 Thread Peter Padawitz

Jules Bean wrote:


Peter Padawitz wrote:


So the fundep would solve the problem.



But, actually, it doesn't :-(


But actually, it does!


Indeed... Sorry, I think I left intE out of the cycle. This might be the 
reason why it did not work before.


Ben Franksen's answer from yesterday compiles fine for me if I add the 
missing fundep, block -> command.


Your original code compiles without error, given the fundep. Exact 
code I compiled attached at the bottom of this document. You may have 
to repair long lines!


Incidentally, I question why the "compFoo" are methods. Why not just 
make them polymorphic functions? They don't look like you expect 
instances to change them. The code continues to compile if I make them 
functions and amend their signatures as required.


I put compFoo into the class for the same reason why /= is part of the 
class Eq: both functions are unique as soon as the others have been 
instantiated.




{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-}

type Block   = [Command]
data Command = Skip | Assign String IntE | Cond BoolE Block Block | 
Loop BoolE Block
data IntE= IntE Int | Var String | Sub IntE IntE | Sum [IntE] | 
Prod [IntE]

data BoolE   = BoolE Bool | Greater IntE IntE | Not BoolE

class Java block command intE boolE | block -> command, command -> 
intE, intE -> boolE, boolE -> block

  where block_ :: [command] -> block
skip :: command
assign :: String -> intE -> command
cond :: boolE -> block -> block -> command
loop :: boolE -> block -> command
intE_ :: Int -> intE
var :: String -> intE
sub :: intE -> intE -> intE
sum_ :: [intE] -> intE
prod :: [intE] -> intE
boolE_ :: Bool -> boolE
greater :: intE -> intE -> boolE
not_ :: boolE -> boolE
compBlock :: Block -> block
compBlock = block_ . map compCommand
compCommand :: Command -> command
compCommand Skip   = skip
compCommand (Assign x e)   = assign x (compIntE e)
compCommand (Cond be cs cs') = cond (compBoolE be) (compBlock 
cs) (compBlock cs')

compCommand (Loop be cs)= loop (compBoolE be) (compBlock cs)
compIntE :: IntE -> intE
compIntE (IntE i)   = intE_ i
compIntE (Var x)= var x
compIntE (Sub e e') = sub (compIntE e) (compIntE e')
compIntE (Sum es)   = sum_ (map compIntE es)
compIntE (Prod es)  = prod (map compIntE es)
compBoolE :: BoolE -> boolE
compBoolE (BoolE b)  = boolE_ b
compBoolE (Greater e e') = greater (compIntE e) (compIntE e')
compBoolE (Not be)   = not_ (compBoolE be)


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


Re: [Haskell-cafe] Re: type class question

2007-12-05 Thread Ryan Ingram
On 12/5/07, Ben Franksen <[EMAIL PROTECTED]> wrote:
>
> data Command = Skip
>
> class Java block command where
> block_ :: [command] -> block
>
> compBlock :: [Command] -> block
> --compBlock = block_ . map compCommand
>
> compCommand :: Command -> command
>
> This compiles ok. But when I ask ghci for the type of the body of the
> default definition of compBlock I get
>
> *Main> :t block_ . map compCommand
> block_ . map compCommand :: forall block block1 command.
> (Java block command, Java block1 command) =>
> [Command] -> block


Lets look at the type of "compCommand".

compCommand :: Java block command => Command -> command

The block type is not used at all in this declaration, but the block type
can influence which implementation "compCommand" is chosen.  This means that
it's actually almost impossible to ever call this function, as given a type
for  "command" there could be multiple implementations of "Java block
command" for different block types, and there's no way to ever determine
which function to call unless the instance declaration admits any type.

{-# OPTIONS_GHC -fglasgow-exts #-}
module BrokenTypeClass where

class Broken a b where
broken :: String -> b

{-
instance Broken Bool String where
broken = id

instance Broken String String where
broken = reverse
-} -- which instance of "broken" do you choose in "test" below?

instance Broken a String where
broken = id

test :: String
test = broken "hello"
You would have to use functional dependencies or associated types to
eliminate this error.  Alternatively, you can add a dummy argument of type
"block" and pass "undefined :: BlockType" in to help choose the instance
declaration.

Still, I agree with Brent here; whenever I have written code like this I
soon realize that I didn't need a typeclass in the first place, and I would
have been better off not using them; they're not like OO classes.

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


Re: [Haskell-cafe] Re: type class question

2007-12-05 Thread Felipe Lessa
On Dec 5, 2007 10:38 PM, Ben Franksen <[EMAIL PROTECTED]> wrote:
> data Command = Skip
>
> class Java block command where
>   block_ :: [command] -> block
>
>   compBlock :: [Command] -> block
>   --compBlock = block_ . map compCommand
>
>   compCommand :: Command -> command

My guess is that nothing's guaranteeing the calls from block_ and
compCommand to be using the same 'command' type as the class head. For
example, having

> instance Java B C1
> instance Java B C2

you can have both

> compBlock = (block_ :: [C1] -> B) . map (compCommand :: Command -> C1)
> compBlock = (block_ :: [C2] -> B) . map (compCommand :: Command -> C2)

Also, there's another problem: from compCommand you can't know the
type of block (as it's not appearing in the signature). The modified
version below typechecks:

> data Command = Skip
>
> class Java block command | command -> block where
>  block_ :: [command] -> block
>
>  compBlock :: [Command] -> block
>  compBlock = block_ . map (compCommand :: Command -> command)
>
>  compCommand :: Command -> command

(Note that (compCommand :: Command -> command) actually is restricting
to a monomorphic type.)

So, this seems to me to be a problem with multi-parameter type classes
when you prune the types (on compBlock and on compCommand one of the
types of the class head is missing).

I'm not a wizard on this subject, please anybody correct me if I'm mistaken =).

Cheers,

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


[Haskell-cafe] Re: type class question

2007-12-05 Thread Ben Franksen
Brent Yorgey wrote:
> Well, first of all, the definition of compCommand should use calls to
> compBlock, not recursive calls to compCommand.  But that's not the main
> source of your problems.
> 
> What exactly are you trying to accomplish?  And why do you need a type
> class?

Whatever the code is supposed to accomplish, there is something strange
going on with the type checking. I have managed to reduce the code (while
keeping the type error message) thus

data Command = Skip

class Java block command where
  block_ :: [command] -> block

  compBlock :: [Command] -> block
  --compBlock = block_ . map compCommand

  compCommand :: Command -> command

This compiles ok. But when I ask ghci for the type of the body of the
default definition of compBlock I get

*Main> :t block_ . map compCommand
block_ . map compCommand :: forall block block1 command.
(Java block command, Java block1 command) =>
[Command] -> block

and if I remove the comment from the default definition of compBlock I get

Could not deduce (Java block command1)
  from the context (Java block command)
  arising from use of `block_' at Bla.hs:7:14-19
Possible fix:
  add (Java block command1)
  to the class or instance method `compBlock'
In the first argument of `(.)', namely `block_'
In the expression: block_ . (map compCommand)
In the definition of `compBlock':
compBlock = block_ . (map compCommand)

It would be nice if someone could explain (in language that can be
understood by non-type-system-experts) why ghc(i) deduces these
strange 'duplicated' contexts.

Cheers
Ben

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