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

2007-12-07 Thread Jules Bean

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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2007-12-07 Thread Peter Padawitz
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 [EMAIL PROTECTED] 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   [EMAIL PROTECTED]
internethttp://funlog.padawitz.de

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


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

2007-12-07 Thread Jules Bean

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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2007-12-07 Thread Benja Fallenstein
On Dec 7, 2007 6:57 PM, Peter Padawitz [EMAIL PROTECTED] wrote:
 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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2007-12-07 Thread Jules Bean

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)

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


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

2007-12-07 Thread Luke Palmer
On Dec 7, 2007 5:57 PM, Peter Padawitz [EMAIL PROTECTED] wrote:
 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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2007-12-07 Thread Peter Padawitz

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)

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


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

2007-12-07 Thread Peter Padawitz

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.


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


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

2007-12-06 Thread Ben Franksen
Ryan Ingram wrote:
 On 12/5/07, Ben Franksen [EMAIL PROTECTED] 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

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


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

2007-12-06 Thread Jules Bean

Ben Franksen wrote:

Ryan Ingram wrote:

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