[Haskell-cafe] I seem to constantly abuse TypeFamilies; what do i really want?
Niklas Haas
haskell at nand.wakku.to
Sat Mar 15 00:44:26 UTC 2014
On Fri, 14 Mar 2014 22:19:40 +0100, Eric Walkingshaw <walkiner at eecs.oregonstate.edu> wrote:
> I'm not sure if this answers your questions, but I think this particular
> problem has a cleaner solution with GADTs:
>
> {-# LANGUAGE GADTs #-}
>
> data Cmd s t where
> Push :: a -> Cmd s (a,s)
> F1 :: (a -> b) -> Cmd (a,s) (b,s)
> F2 :: (a -> b -> c) -> Cmd (a,(b,s)) (c,s)
>
> data Prog s t where
> (:.) :: Cmd s t -> Prog t u -> Prog s u
> End :: Prog s s
>
> infixr 5 :.
>
> cmd :: Cmd s t -> s -> t
> cmd (Push a) s = (a, s)
> cmd (F1 f) (a,s) = (f a, s)
> cmd (F2 f) (a,(b,s)) = (f a b, s)
>
> prog :: Prog s t -> s -> t
> prog (c :. p) s = prog p (cmd c s)
> prog End s = s
>
> run :: Prog () t -> t
> run p = prog p ()
>
> Then from GHCi:
>
> > run (Push 3 :. Push 4 :. F2 (+) :. F1 show :. End)
> ("7",())
>
> Maybe you really want GADTs? :)
>
> -Eric
Of course, there's also:
> start :: (() -> r) -> r
> start f = f ()
>
> end :: (a, s) -> a
> end = fst
>
> push :: s -> a -> ((a, s) -> r) -> r
> push s a f = f (a, s)
>
> op2 :: (a -> b -> c) -> (a, (b, s)) -> ((c, s) -> r) -> r
> op2 o (a, (b, s)) f = f (a `o` b, s)
>
> add, mul :: Num a => (a, (a, s)) -> ((a, s) -> r) -> r
> add = op2 (+)
> mul = op2 (*)
>
> example :: Integer
> example = -- 35
> start
> push 2
> push 3
> add
> push 7
> mul
> end
More information about the Haskell-Cafe
mailing list