If you use Hugs -- and possibly GHC -- you might be able to use the
"Either" constructor for subtyping. I first saw this pattern in
"Modular Monadic Interpreters" (or something like that) by Jones,
Liang and Hudak. [Apologies if I didn't get the attribution right.]
data Expr a = Int Integer
| Cte String
| Var String
| App a [Expr a]
type ArithFn = Either Sum (Either Pro Pow)
data Sum = Sum
data Pro = Pro
data Pow = Pow
You may find these handy:
class SubType a b where
inj :: a -> b
prj :: b -> Maybe a
instance SubType a (Either a b) where
inj a = Left a
prj (Left a) = a
prj (_) = Nothing
instance SubType Pow (Either Pro Pow)
inj a = Right a
prj (Right Pow) = Pow
type TrigFun = Either Sin (Either Cos (Either Tan FirstFun)
data Sin = Sin
...
I don't remember if you can do
type TrigFn a = Either Sin (Either Cos (Either Tan a))
type Fun = TrigFn ArithFn
Next, define classes for the
class Application a where
app :: a -> Expr -> M Value
instance (Application a, Application b) => Application (Either a b) where
app (Left a) e = app a e
app (Right b) e = app b e
IIRC, you also need to do this for the "inner" value
instance Application (Either Pro Pow) where
app (Left a) e = app a e
app (Right b) e = app b e
instance Application Sum where
app Sum [] = return bottom -- ?
app Sum (x:xs) = do
v1 <- (eval x)
v2 <- (Sum xs)
return (v1+v2)
...
eval :: Expr a -> M Value
eval (App fn e) = app fn e
eval Cte "pi" = pi
eval Var s = get s
...
Note that a user of the libraries can pick components at will;
type MyFn = Either Sin (Either Pro Pow)
type MyExpr = Expr MyFn
I haven't run the above through the type checker, so it may not work.
Hugs extended type system is very useful. You'll need to run hugs
with +o -98 to enable it.
Regards,
John Hornkvist
--
ToastedMarshmallow, the perfect Cocoa companion
http://www.toastedmarshmallow.com