
What is wrong here? ghci tries (and fails) to deduce certain types for the comp functions that I did not expect. |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 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 c c') = cond (compBoolE be) (compCommand c) (compCommand c') compCommand (Loop be c) = loop (compBoolE be) (compCommand c)-} 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) |

On Dec 3, 2007 7:43 AM, Peter Padawitz
What is wrong here? ghci tries (and fails) to deduce certain types for the comp functions that I did not expect.
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 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 c c') = cond (compBoolE be) (compCommand c) (compCommand c') compCommand (Loop be c) = loop (compBoolE be) (compCommand c)-}
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)
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? -Brent

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

On Dec 5, 2007 10:38 PM, Ben Franksen
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.

On 12/5/07, Ben Franksen
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

Ryan Ingram wrote:
On 12/5/07, Ben Franksen
wrote: 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.
Sounds reasonable, and in fact that was what I tried first. However data Command = Skip class Java block command | command -> block where block_ :: [command] -> block compBlock :: [Command] -> block compBlock = block_ . map compCommand compCommand :: Command -> command still gives 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) which is /exactly/ the same error as I get w/o the fundep. Cheers Ben

Ben Franksen wrote:
Ryan Ingram wrote:
On 12/5/07, Ben Franksen
wrote: 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. Sounds reasonable, and in fact that was what I tried first. However
data Command = Skip
class Java block command | command -> block where block_ :: [command] -> block
compBlock :: [Command] -> block compBlock = block_ . map compCommand
compCommand :: Command -> command
still gives
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)
which is /exactly/ the same error as I get w/o the fundep.
Yes, because command determines block but block doesn't determine command. So in a usage of 'compBlock' it has no way of deciding which 'command' to use, although it can choose the block from the return type. You could have command -> block, block -> command, if that is indeed true. Jule

Functional dependencies don't work in my case. Actually, I don't see why they should. What seems to be needed here is a type class construct with a kind of record parameter so that instance conflicts cannot occur. Jules Bean wrote:
Ben Franksen wrote:
Ryan Ingram wrote:
On 12/5/07, Ben Franksen
wrote: 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. Sounds reasonable, and in fact that was what I tried first. However
data Command = Skip
class Java block command | command -> block where block_ :: [command] -> block
compBlock :: [Command] -> block compBlock = block_ . map compCommand
compCommand :: Command -> command
still gives
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)
which is /exactly/ the same error as I get w/o the fundep.
Yes, because command determines block but block doesn't determine command.
So in a usage of 'compBlock' it has no way of deciding which 'command' to use, although it can choose the block from the return type.
You could have command -> block, block -> command, if that is indeed true.
Jule _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Prof. Dr. Peter Padawitz Informatik 1 University of Dortmund D-44221 Dortmund Germany phone +49-231-755-5108 fax +49-231-755-6555 secretary +49-231-755-6223 email peter.padawitz@udo.edu internet http://funlog.padawitz.de

Peter Padawitz wrote:
Functional dependencies don't work in my case. Actually, I don't see why they should.
Ah well, it's cruel to say that without explaining to us why! I'm not sure why a complete cyclic dep a -> b -> c -> d -> a isn't what you want.
What seems to be needed here is a type class construct with a kind of record parameter so that instance conflicts cannot occur.
I'm not entirely sure what you intend to mean by this, but if you mean what I guess you mean: class Java (a,b,c,d) where .... then I think that would appear to be the same thing as a complete cyclic fundep to me... Jules

Jules Bean wrote:
Peter Padawitz wrote:
Functional dependencies don't work in my case. Actually, I don't see why they should.
Ah well, it's cruel to say that without explaining to us why!
Cause I don't see why the instantiation conflicts pointed out by others would vanish then.
I'm not sure why a complete cyclic dep a -> b -> c -> d -> a isn't what you want.
What seems to be needed here is a type class construct with a kind of record parameter so that instance conflicts cannot occur.
I'm not entirely sure what you intend to mean by this, but if you mean what I guess you mean:
class Java (a,b,c,d) where ....
Yeah... but ghc accepts only type variables here, not arbitrary polymorphic types.

Peter Padawitz wrote:
Jules Bean wrote:
Peter Padawitz wrote:
Functional dependencies don't work in my case. Actually, I don't see why they should.
Ah well, it's cruel to say that without explaining to us why!
Cause I don't see why the instantiation conflicts pointed out by others would vanish then.
They would. If it's really true that there is only one possible choice of b,c,d for any particular a, then there are no conflicts, so you'd get no errors. So the fundep would solve the problem.
class Java (a,b,c,d) where ....
Yeah... but ghc accepts only type variables here, not arbitrary polymorphic types.
Indeed, but there is a workaround: class Java all a b c d | all -> a, all -> b, all -> c, all -> d, a,b,c,d -> all instance Java (a,b,c,d) a b c d where... but I'm not sure you need this. Jules

Jules Bean wrote:
Peter Padawitz wrote:
Jules Bean wrote:
Peter Padawitz wrote:
Functional dependencies don't work in my case. Actually, I don't see why they should.
Ah well, it's cruel to say that without explaining to us why!
Cause I don't see why the instantiation conflicts pointed out by others would vanish then.
They would.
If it's really true that there is only one possible choice of b,c,d for any particular a, then there are no conflicts, so you'd get no errors.
How can ghci know this even if no instance has been defined?
So the fundep would solve the problem.
But, actually, it doesn't :-(
class Java (a,b,c,d) where ....
Yeah... but ghc accepts only type variables here, not arbitrary polymorphic types.
Indeed, but there is a workaround:
class Java all a b c d | all -> a, all -> b, all -> c, all -> d, a,b,c,d -> all
Same problem. If I omit the comp functions (see below), everything works. If I add them, all proposed solutions fail with error messages of the form Could not deduce (Java block1 ....) from the context (Java block ....) arising from use of `prod' at ... (see also Ben Franksen's comment from yesterday). *************** 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 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)

On Dec 7, 2007 5:57 PM, Peter Padawitz
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 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 kcompIntE es)
compBoolE :: BoolE -> boolE compBoolE (BoolE b) = boolE_ b compBoolE (Greater e e') = greater (compIntE e) (compIntE e') compBoolE (Not be) = not_ (compBoolE be)
I'm not sure what this is worth, since you seem to have your mind set on using this strange four-parameter type class. You can keep most of the design advantages of using this type at the "cost" of being more explicit if you factor it into a data type yourself:
data Java block command intE boolE = Java { block_ :: [command] -> block , skip :: command , assign :: String -> intE -> command , ... , compBlock :: Block -> block , ... }
For your default implementations:
defCompBlock :: Java block command intE boolE -> Block -> block defCompBlock self = block_ self . map (compCommand self)
.. etc
Then to define an example instance:
javaAST :: Java Block Command IntE BoolE javaAST = Java { block_ = Block , ... , compBlock = defCompBlock javaAST , ... }
Your type errors will be resolved because you are saying explicitly which instance to use by passing the instance data structure you want explicitly. Luke

Peter Padawitz wrote:
So the fundep would solve the problem.
But, actually, it doesn't :-(
But actually, it does! 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. Jules {-# 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)

On Dec 7, 2007 6:57 PM, Peter Padawitz
Jules Bean wrote:
Peter Padawitz wrote:
Cause I don't see why the instantiation conflicts pointed out by others would vanish then.
They would.
If it's really true that there is only one possible choice of b,c,d for any particular a, then there are no conflicts, so you'd get no errors.
How can ghci know this even if no instance has been defined?
Because "there is only one possible choice of b,c,d for any particular a" is what the fundep means :-)
If I omit the comp functions (see below), everything works. If I add them, all proposed solutions fail with error messages of the form
Could not deduce (Java block1 ....) from the context (Java block ....) arising from use of `prod' at ...
(see also Ben Franksen's comment from yesterday).
If you add the cyclic functional dependencies to your code, it compiles just fine: 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) Best, - Benja

Yes, the recursive calls of compCommand are supposed to be calls of compBlock. The intention of the program is a generic evaluator comp... of Sigma-terms in arbitrary Sigma-algebras. The signature Sigma is given by the first 4 types (and the corresponding functions in the class declaration), the terms are the objects of the types, and the algebras are the class instances. The problem with my implementation in terms of multiple-parameter classes seems to be - I conclude this from Ryan's comment - that the intended dependency among the parameters is not reflected here. But what are the alternatives? Roughly said, I need a construct that allows me gather several type variables such that an instance is always an instance of all of them.
On Dec 3, 2007 7:43 AM, Peter Padawitz
mailto:peter.padawitz@udo.edu> wrote: What is wrong here? ghci tries (and fails) to deduce certain types for the comp functions that I did not expect.
|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 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 c c') = cond (compBoolE be) (compCommand c)
(compCommand c') compCommand (Loop be c) = loop (compBoolE be) (compCommand c)-}
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) |
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?
-Brent

Peter Padawitz wrote:
Yes, the recursive calls of compCommand are supposed to be calls of compBlock.
The intention of the program is a generic evaluator comp... of Sigma-terms in arbitrary Sigma-algebras. The signature Sigma is given by the first 4 types (and the corresponding functions in the class declaration), the terms are the objects of the types, and the algebras are the class instances.
The problem with my implementation in terms of multiple-parameter classes seems to be - I conclude this from Ryan's comment - that the intended dependency among the parameters is not reflected here. But what are the alternatives? Roughly said, I need a construct that allows me gather several type variables such that an instance is always an instance of all of them.
well, given class Java a b c d where .... if it is true that everything is determined by choice of any one of them, you could write class Java a b c d | a -> b, b -> c, c -> d, d -> a where... otherwise, well you can express whatever dependency network you want... Jules
participants (8)
-
Ben Franksen
-
Benja Fallenstein
-
Brent Yorgey
-
Felipe Lessa
-
Jules Bean
-
Luke Palmer
-
Peter Padawitz
-
Ryan Ingram