Re: [Haskell-cafe] Idiomatic usage of the fixpoint library

2011-09-05 Thread Sean Leather
On Sun, Sep 4, 2011 at 13:03, Roman Cheplyaka wrote:

 * Sean Leather [2011-09-04 12:48:38+0200]
  On Sun, Sep 4, 2011 at 12:31, Roman Cheplyaka wrote:
 
   I'm looking for an example of idiomatic usage of the fixpoint
 library[1].
  
   [1]: http://hackage.haskell.org/package/fixpoint-0.1.1
 
 
  I'm not sure if this counts for idiomatic usage, but you can check out
  our approach to incrementalization.
 
  http://people.cs.uu.nl/andres/Incrementalization/

 Yeah, it has more or less the same problems as my code above.

 You essentially defined your tree twice (Tree and F (Tree)).
 For such a simple type it's fine, but if it was an AST with a few
 dozens of constructors, such approach would be unacceptable.


True. Technically, one doesn't need Expr or Tree, right? But if you prefer
to define your datatype that way, that's usually where I turn to code
generation, possibly using Template Haskell, Data.Derive, or something else.

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


Re: [Haskell-cafe] Idiomatic usage of the fixpoint library

2011-09-05 Thread Roman Leshchinskiy
Roman Cheplyaka wrote:

 {-# LANGUAGE TypeFamilies, FlexibleContexts, UndecidableInstances,
 FlexibleInstances #-}
 import Data.Fixpoint

 newtype Expr = Expr { unExpr :: Pre Expr Expr }

 instance Functor (Pre Expr) = Fixpoint Expr where
 data Pre Expr a
 = Add a a
 | Const Int
 project = unExpr
 inject = Expr

 instance Functor (Pre Expr) where
 fmap f (Const x) = Const x
 fmap f (Add x1 x2) = Add (f x1) (f x2)

 eval = cata eval' where
 eval' (Const x) = x
 eval' (Add x1 x2) = x1 + x2

 There are some issues with this code, compared to simply using

 newtype Fix f = In { out :: f (Fix f) }

 to build an Expr.

 1. Since 'Pre' is a data (not type) family, we cannot simply make use of
a functor defined elsewhere. We need to define the functor inside the
instance declaration (or at least wrap an existing functor).

Yes, it would be nicer if it was a type family. There is a single reason
why this isn't the case but I find that reason pretty compelling: you
couldn't type hylo if it was.

 2. I wasn't able to derive the Functor instance, getting an error

 Derived instance `Functor (Pre Expr)'
   requires illegal partial application of data type family Pre
 In the data type instance declaration for `Pre'

That's really a GHC problem. There is no reason why it shouldn't be able
to do this.

 3. Having to use UndecidableInstances makes me feel a bit uncomfortable.

You don't need UndecidableInstances. Just get rid of the Functor (Pre
Expr) constraint on the Fixpoint Expr instance, it's doesn't do anything
anyway.

Roman




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


[Haskell-cafe] Idiomatic usage of the fixpoint library

2011-09-04 Thread Roman Cheplyaka
Hi,

I'm looking for an example of idiomatic usage of the fixpoint library[1].

[1]: http://hackage.haskell.org/package/fixpoint-0.1.1

Here's what I managed to get:

{-# LANGUAGE TypeFamilies, FlexibleContexts, UndecidableInstances, 
FlexibleInstances #-}
import Data.Fixpoint

newtype Expr = Expr { unExpr :: Pre Expr Expr }

instance Functor (Pre Expr) = Fixpoint Expr where
data Pre Expr a
= Add a a
| Const Int
project = unExpr
inject = Expr

instance Functor (Pre Expr) where
fmap f (Const x) = Const x
fmap f (Add x1 x2) = Add (f x1) (f x2)

eval = cata eval' where
eval' (Const x) = x
eval' (Add x1 x2) = x1 + x2

There are some issues with this code, compared to simply using

newtype Fix f = In { out :: f (Fix f) }

to build an Expr.

1. Since 'Pre' is a data (not type) family, we cannot simply make use of
   a functor defined elsewhere. We need to define the functor inside the
   instance declaration (or at least wrap an existing functor).

2. I wasn't able to derive the Functor instance, getting an error

Derived instance `Functor (Pre Expr)'
  requires illegal partial application of data type family Pre
In the data type instance declaration for `Pre'

3. Having to use UndecidableInstances makes me feel a bit uncomfortable.

This makes me think that the intended usage is somewhat different.
So, could someone give an example?

-- 
Roman I. Cheplyaka :: http://ro-che.info/

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


Re: [Haskell-cafe] Idiomatic usage of the fixpoint library

2011-09-04 Thread Sean Leather
On Sun, Sep 4, 2011 at 12:31, Roman Cheplyaka wrote:

 I'm looking for an example of idiomatic usage of the fixpoint library[1].

 [1]: http://hackage.haskell.org/package/fixpoint-0.1.1


I'm not sure if this counts for idiomatic usage, but you can check out
our approach to incrementalization.

http://people.cs.uu.nl/andres/Incrementalization/

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


Re: [Haskell-cafe] Idiomatic usage of the fixpoint library

2011-09-04 Thread Roman Cheplyaka
* Sean Leather leat...@cs.uu.nl [2011-09-04 12:48:38+0200]
 On Sun, Sep 4, 2011 at 12:31, Roman Cheplyaka wrote:
 
  I'm looking for an example of idiomatic usage of the fixpoint library[1].
 
  [1]: http://hackage.haskell.org/package/fixpoint-0.1.1
 
 
 I'm not sure if this counts for idiomatic usage, but you can check out
 our approach to incrementalization.
 
 http://people.cs.uu.nl/andres/Incrementalization/

Yeah, it has more or less the same problems as my code above.

You essentially defined your tree twice (Tree and F (Tree)).
For such a simple type it's fine, but if it was an AST with a few
dozens of constructors, such approach would be unacceptable.

-- 
Roman I. Cheplyaka :: http://ro-che.info/

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