
Hello, I'm working on a small EDSL, and I think I've finally managed to get GHC to compile it to good core. Basically, it allows for the creation of expressions like:
g = 0.5*x + 0.1*y
which is then compiled to a tuple (related work: CCA, stream fusion)
exists s. (s, s -> Double -> (s,Double))
I also have a function 'mapAccumL :: (V.Unbox a, V.Unbox b) => (s -> a -> (s,b)) -> s -> V.Vector a -> V.Vector b'. Basic usage would be similar to:
import qualified Data.Vector.Unboxed as V
main = do let (gs, gf) = $(compile [] g) ys = mapAccumL gf gs $ V.enumFromTo (1::Double) 5 print ys
For 'g' as above, I currently get 's :: (((), ()), Double)', which is
expected. GHC produces the following core for the inner loop, which
looks pretty good to me:
letrec {
$s$wa_s2OL [Occ=LoopBreaker]
:: ()
-> ()
-> GHC.Prim.Double#
-> GHC.Prim.Int#
-> GHC.Prim.State# (Control.Monad.Primitive.R:PrimStateST s_a1Y9)
-> (# GHC.Prim.State# s_a1Y9, () #)
[LclId, Arity=5, Str=DmdType LLLLL]
$s$wa_s2OL =
\ _
_
(sc2_s2Oq :: GHC.Prim.Double#)
(sc3_s2Or :: GHC.Prim.Int#)
(sc4_s2Os
:: GHC.Prim.State#
(Control.Monad.Primitive.R:PrimStateST s_a1Y9)) ->
case GHC.Prim.<# sc3_s2Or rb1_a2EV of _ {
GHC.Types.False -> (# sc4_s2Os, GHC.Unit.() #);
GHC.Types.True ->
let {
x#_a2aI [Dmd=Just L] :: GHC.Prim.Double#
[LclId, Str=DmdType]
x#_a2aI =
GHC.Prim.+##
(GHC.Prim.*##
(GHC.Prim.indexDoubleArray#
rb2_a2EW (GHC.Prim.+# rb_a2EU sc3_s2Or))
0.5)
(GHC.Prim.*## sc2_s2Oq 0.1) } in
$s$wa_s2OL
GHC.Unit.()
GHC.Unit.()
x#_a2aI
(GHC.Prim.+# sc3_s2Or 1)
((GHC.Prim.writeDoubleArray#
@ (Control.Monad.Primitive.PrimState (GHC.ST.ST s_a1Y9))
arr#_a29n
sc3_s2Or
x#_a2aI
(sc4_s2Os
`cast` (GHC.Prim.State#
(Sym
(Control.Monad.Primitive.TFCo:R:PrimStateST