[Haskell-cafe] Bool as type class to serve EDSLs.
Lennart Augustsson
lennart at augustsson.net
Thu May 28 03:57:09 EDT 2009
Here's what I usually use. As Simon points out, ambiguity is lurking
as soon as you use conditional. You can avoid it a fundep, but that's
not necessarily what you want either.
-- | Generalization of the 'Bool' type. Used by the generalized 'Eq' and 'Ord'.
class Boolean bool where
(&&) :: bool -> bool -> bool -- ^Logical conjunction.
(||) :: bool -> bool -> bool -- ^Logical disjunction.
not :: bool -> bool -- ^Locical negation.
false :: bool -- ^Truth.
true :: bool -- ^Falsity.
fromBool :: Bool -> bool -- ^Convert a 'Bool' to the
generalized Boolean type.
fromBool b = if b then true else false
-- | Generalization of the @if@ construct.
class (Boolean bool) => Conditional bool a where
conditional :: bool -> a -> a -> a -- ^Pick the first argument if
the 'Boolean' value is true, otherwise the second argument.
class (Boolean bool) => Eq a bool {- x | a -> bool -} where
(==) :: a -> a -> bool
(/=) :: a -> a -> bool
x /= y = not (x == y)
x == y = not (x /= y)
On Thu, May 28, 2009 at 8:14 AM, Simon Peyton-Jones
<simonpj at microsoft.com> wrote:
> You are absolutely right about the tantalising opportunity. I know that Lennart has thought quite a bit about this very point when designing his Paradise system. Likewise Conal for Pan.
>
> One difficulty is, I think, that it's easy to get ambiguity. Eg
> ifthenelse (a > b) e1 e2
> The (a>b) produces a boolean-thing, and ifthenelse consumes it; but which type of boolean? The Expr type? Real Bools? Or what?
>
> If there was a nice design, then GHC's existing -fno-implicit-prelude flag could be extended (again) to desugar if-then-else to the new thing. But the design is unclear, to me anyway.
>
> Simon
>
> | -----Original Message-----
> | From: haskell-cafe-bounces at haskell.org [mailto:haskell-cafe-bounces at haskell.org] On
> | Behalf Of Sebastiaan Visser
> | Sent: 27 May 2009 13:32
> | To: Haskell Cafe
> | Subject: [Haskell-cafe] Bool as type class to serve EDSLs.
> |
> | Hello,
> |
> | While playing with embedded domain specific languages in Haskell I
> | discovered the Num type class is a really neat tool. Take this simple
> | example embedded language that can embed primitives from the output
> | language and can do function application.
> |
> | >data Expr :: * -> * where
> | > Prim :: String -> Expr a
> | > App :: Expr (a -> b) -> Expr a -> Expr b
> |
> | Take these two dummy types to represent things in the output language.
> |
> | >data MyNum
> | >data MyBool
> |
> | Now it is very easy to create an Num instance for this language:
> |
> | >primPlus :: Expr (MyNum -> MyNum -> MyNum)
> | >primPlus = Prim "prim+"
> |
> | >instance Num (Epxr MyNum) where
> | > a + b = primPlus `App` a `App` b
> | > fromInteger = Prim . show
> | > ...
> |
> | Which allows you to create very beautiful expression for your language
> | embedded inside Haskell. The Haskell expression `10 * 5 + 2' produces
> | a nice and well typed expression in your embedded domain.
> |
> | But unfortunately, not everyone in the Prelude is as tolerant as the
> | Num instance. Take the Eq and the Ord type classes for example, they
> | require you to deliver real Haskell `Bool's. This makes it impossible
> | make your DSL an instance of these two, because there are no `Bool's
> | only `Expr Bool's.
> |
> | Which brings me to the point that, for the sake of embedding other
> | languages, Haskell's Prelude (or an alternative) can greatly benefit
> | from (at least) a Boolean type class like this:
> |
> | class Boolean a where
> | ifthenelse :: a -> b -> b -> b -- Not sure about this
> | representation.
> | ...
> |
> | And one instance:
> |
> | >instance Boolean (Expr MyBool) where
> | > ifthenelse c a b = Prim "if-then-else" `App` c `App` a `App` b
> |
> | Now we can change (for example) the Eq type class to this:
> |
> | >class Eq a where
> | > (==) :: Boolean b => a -> a -> b
> | > (/=) :: Boolean b => a -> a -> b
> |
> | For which we can give an implementation for our domain:
> |
> | >primEq :: Epxr (a -> a -> MyBool)
> | >primEq = Prim "=="
> |
> | >instance Eq (Expr a) where
> | > a == b = primEq `App` a `App` b
> |
> | And now we get all functionality from the Prelude that is based on Eq
> | (like not, &&, ||, etc) for free in our domain specific language! Off
> | course there are many, many more examples of things from the standard
> | libraries that can be generalised in order to serve reuse in EDSLs.
> |
> | Anyone already working on such a generalized Prelude? I can imagine
> | much more domains can benefit from this than my example above. Any
> | interesting thoughts or pointers related to this subject?
> |
> | Gr,
> |
> | --
> | Sebastiaan Visser
> |
> | _______________________________________________
> | Haskell-Cafe mailing list
> | Haskell-Cafe at haskell.org
> | http://www.haskell.org/mailman/listinfo/haskell-cafe
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
More information about the Haskell-Cafe
mailing list