
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)

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
Try again without missing out the list... Peter Padawitz wrote: 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

Jules Bean wrote:
Try again without missing out the list...
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
Peter Padawitz wrote: 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.

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

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!

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

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.

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
participants (3)
-
Bertram Felgenhauer
-
Jules Bean
-
Peter Padawitz