ANN: package Boolean: Generalized booleans

I just uploaded a new package [1] for generalized booleans, which provides type classes with generalizations of boolean values & operations, if-then-else, Eq and Ord. These values & types come up for me with every new deep DSEL, and I think they do for others as well. The design space has some tricky trade-offs, and I'm not positive I've found the optimum yet. Users & comments are very welcome. Please direct discussion to the haskell-cafe list (rather than haskell list). [1]: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/Boolean - Conal

On Jun 30, 2009, at 2:44 AM, Conal Elliott wrote:
I just uploaded a new package [1] for generalized booleans, which provides type classes with generalizations of boolean values & operations, if-then-else, Eq and Ord. These values & types come up for me with every new deep DSEL, and I think they do for others as well. The design space has some tricky trade-offs, and I'm not positive I've found the optimum yet. Users & comments are very welcome. Please direct discussion to the haskell-cafe list (rather than haskell list).
class Bool f r | f -> r where bool :: r -> r -> f -> r false :: f true :: f
class Maybe f a r | f -> a, f -> r where maybe :: r -> (a -> r) -> f a -> r nothing :: f a just :: a -> f a
class Either f a b r | f -> a, f -> b, f -> r where either :: (a -> r) -> (b -> r) -> f a b -> r left :: a -> f a b right :: b -> f a b Currently we have a very limited and somewhat messy code base on github[1] which shows how to instantiate these types to get back the original Haskell functionality and how to produce JavaScript code that runs in a browser. The the JavaScript instance is very much the same as I used in my FRP to JS EDSL[4]. Next target will, off course, be Objective C. :-) Our code is not yet release worthy and probably never will be in this
Conal, Good work! Together with Tom Lokhorst I've been working on something very similar. We've been using a rather consistent way of eliminating data structures that scales well to other data types. Although we are also using functional dependencies I think we might want to change them to type families. Examples: form. But is would be very nice to see some kind of generalized prelude evolving.
[1]: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/ Boolean
- Conal
-- Sebastiaan Visser [1] http://github.com/tomlokhorst/AwesomePrelude/tree/master [2] http://github.com/sebastiaanvisser/frp-js

Hi Sebastiaan,
I like your extensions of generalized booleans to other common Haskell
types!
I also prefer using type families to fundeps. In this case I didn't because
of some awkwardness with vector operations, but I'm going to try again.
I'm confused about your particular fundep choice. For instance,
class Bool f r | f -> r where
bool :: r -> r -> f -> r
false :: f
true :: f
Do you *really* mean that the boolean type f determines the value type r?
Regards, - Conal
On Tue, Jun 30, 2009 at 1:34 AM, Sebastiaan Visser
On Jun 30, 2009, at 2:44 AM, Conal Elliott wrote:
I just uploaded a new package [1] for generalized booleans, which provides type classes with generalizations of boolean values & operations, if-then-else, Eq and Ord. These values & types come up for me with every new deep DSEL, and I think they do for others as well. The design space has some tricky trade-offs, and I'm not positive I've found the optimum yet. Users & comments are very welcome. Please direct discussion to the haskell-cafe list (rather than haskell list).
Conal,
Good work!
Together with Tom Lokhorst I've been working on something very similar. We've been using a rather consistent way of eliminating data structures that scales well to other data types. Although we are also using functional dependencies I think we might want to change them to type families.
Examples:
class Bool f r | f -> r where bool :: r -> r -> f -> r false :: f true :: f
class Maybe f a r | f -> a, f -> r where maybe :: r -> (a -> r) -> f a -> r nothing :: f a just :: a -> f a
class Either f a b r | f -> a, f -> b, f -> r where either :: (a -> r) -> (b -> r) -> f a b -> r left :: a -> f a b right :: b -> f a b
Currently we have a very limited and somewhat messy code base on github[1] which shows how to instantiate these types to get back the original Haskell functionality and how to produce JavaScript code that runs in a browser. The the JavaScript instance is very much the same as I used in my FRP to JS EDSL[4]. Next target will, off course, be Objective C. :-) Our code is not yet release worthy and probably never will be in this form. But is would be very nice to see some kind of generalized prelude evolving.
[1]: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/Boolean
- Conal
-- Sebastiaan Visser
[1] http://github.com/tomlokhorst/AwesomePrelude/tree/master [2] http://github.com/sebastiaanvisser/frp-js

On Jun 30, 2009, at 5:24 PM, Conal Elliott wrote:
Hi Sebastiaan,
I like your extensions of generalized booleans to other common Haskell types!
I also prefer using type families to fundeps. In this case I didn't because of some awkwardness with vector operations, but I'm going to try again.
I'm confused about your particular fundep choice. For instance,
class Bool f r | f -> r where bool :: r -> r -> f -> r false :: f true :: f
Do you *really* mean that the boolean type f determines the value type r?
Yes, that is really what I mean. This can be used to enforce that the return value of elimination can be restricted by the boolean type. This is especially useful when using GADTs to encode your domain language. For example, take this simple JavaScript language: data Js a where Prim :: String -> Js a -- Primitive embedding. App :: Js (a -> b) -> Js a -> Js b -- Function application. data JsBool Now the functional dependencies can be used to enforce that eliminating booleans in the Js domain always returns a value in the Js domain: instance Bool (Js JsBool) (Js r) where bool f t c = Prim "(function ifthenelse (f, t, c) c ? t : f)" `App` f `App` t `App` c true = Prim "true" false = Prim "false" Getting rid of this fundep and using type families will probably be a lot more intuitive. Any suggestions on how to enforce elimination to be able to go from `Js JsBool -> Js r' using other techniques?
Regards, - Conal
...
-- Sebastiaan Visser

Does this code compile? I'd expect that
instance Bool (Js JsBool) (Js r) where
violates the fundep, since it applies for *all* values of r, not just to
one.
- Conal
On Tue, Jun 30, 2009 at 8:53 AM, Sebastiaan Visser
On Jun 30, 2009, at 5:24 PM, Conal Elliott wrote:
Hi Sebastiaan,
I like your extensions of generalized booleans to other common Haskell types!
I also prefer using type families to fundeps. In this case I didn't because of some awkwardness with vector operations, but I'm going to try again.
I'm confused about your particular fundep choice. For instance,
class Bool f r | f -> r where bool :: r -> r -> f -> r false :: f true :: f
Do you *really* mean that the boolean type f determines the value type r?
Yes, that is really what I mean. This can be used to enforce that the return value of elimination can be restricted by the boolean type. This is especially useful when using GADTs to encode your domain language.
For example, take this simple JavaScript language: data Js a where Prim :: String -> Js a -- Primitive embedding. App :: Js (a -> b) -> Js a -> Js b -- Function application.
data JsBool
Now the functional dependencies can be used to enforce that eliminating booleans in the Js domain always returns a value in the Js domain: instance Bool (Js JsBool) (Js r) where bool f t c = Prim "(function ifthenelse (f, t, c) c ? t : f)" `App` f `App` t `App` c true = Prim "true" false = Prim "false" Getting rid of this fundep and using type families will probably be a lot more intuitive.
Any suggestions on how to enforce elimination to be able to go from `Js JsBool -> Js r' using other techniques?
Regards, - Conal
...
-- Sebastiaan Visser
[]

It compiles fine :-)
If you want, you can take a look at this [1] version of the code (or
the tarball [2]).
Load Main.hs in GHCi and run `test`, it will evaluate to `True`.
Then, in the source code, switch the type of `test` from `P.Bool` to
`Js JsBool` (in the comments) and run `test` again, now it will
evaluate to a JavaScript expression.
The code is still very immature (basically only that one example
works), but it demonstrates our intend.
- Tom
[1]: http://github.com/tomlokhorst/AwesomePrelude/tree/master
[2]: http://github.com/tomlokhorst/AwesomePrelude/tarball/master
On Tue, Jun 30, 2009 at 8:21 PM, Conal Elliott
Does this code compile? I'd expect that
instance Bool (Js JsBool) (Js r) where
violates the fundep, since it applies for *all* values of r, not just to one.
- Conal
On Tue, Jun 30, 2009 at 8:53 AM, Sebastiaan Visser
wrote: On Jun 30, 2009, at 5:24 PM, Conal Elliott wrote:
Hi Sebastiaan,
I like your extensions of generalized booleans to other common Haskell types!
I also prefer using type families to fundeps. In this case I didn't because of some awkwardness with vector operations, but I'm going to try again.
I'm confused about your particular fundep choice. For instance,
class Bool f r | f -> r where bool :: r -> r -> f -> r false :: f true :: f
Do you *really* mean that the boolean type f determines the value type r?
Yes, that is really what I mean. This can be used to enforce that the return value of elimination can be restricted by the boolean type. This is especially useful when using GADTs to encode your domain language.
For example, take this simple JavaScript language: data Js a where Prim :: String -> Js a -- Primitive embedding. App :: Js (a -> b) -> Js a -> Js b -- Function application.
data JsBool
Now the functional dependencies can be used to enforce that eliminating booleans in the Js domain always returns a value in the Js domain: instance Bool (Js JsBool) (Js r) where bool f t c = Prim "(function ifthenelse (f, t, c) c ? t : f)" `App` f `App` t `App` c true = Prim "true" false = Prim "false" Getting rid of this fundep and using type families will probably be a lot more intuitive.
Any suggestions on how to enforce elimination to be able to go from `Js JsBool -> Js r' using other techniques?
Regards, - Conal
...
-- Sebastiaan Visser
[] _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (3)
-
Conal Elliott
-
Sebastiaan Visser
-
Tom Lokhorst