data-fix-cse-0.0.3: Common subexpression elimination for the fixploint types.

Safe HaskellSafe
LanguageHaskell2010

Data.Fix.Cse

Contents

Description

Implements common subexpression elimination (CSE) with hashconsig algorithm as described in the paper 'Implementing Explicit and Finding Implicit Sharing in EDSLs' by Oleg Kiselyov. You can define your datatype as a fixpoint type. Then the only thing you need to perform CSE is to define an instance of the class Traversable for your datatype.

Synopsis

Documentation

type Dag f = IntMap (f VarName) Source #

Directed acyclic graphs.

fromDag :: Dag f -> [(VarName, f VarName)] Source #

If plain lists are enough for your case.

Implicit sharing

cse :: (Eq (f Int), Ord (f Int), Traversable f) => Fix f -> Dag f Source #

Performs common subexpression elimination with implicit sharing.

Explicit sharing

letCse :: (Eq (f Int), Ord (f Int), Traversable f) => Fix (Let f) -> Dag f Source #

Performs common subexpression elimination with explicit sharing. To make sharing explicit you can use the datatype Let.

data Let f a Source #

With explicit sharing you provide user with the special function that encodes let-bindings for your EDSL (LetBind). You should not use LetLift case. It's reserverd for the CSE algorithm.

Constructors

LetExp (f a) 
LetBind a (a -> a) 
LetLift VarName 

letFoldFix :: (Functor f, Traversable f) => (f a -> a) -> Fix (Let f) -> a Source #

Catamorphism for fixpoint types wrapped in the type Let.

letFoldFixM :: (Applicative m, Monad m, Traversable f) => (f a -> m a) -> Fix (Let f) -> m a Source #

Monadic catamorphism for fixpoint types wrapped in the type Let.

letWrapper :: (Fix (Let f) -> a) -> (a -> Fix (Let f)) -> a -> (a -> a) -> a Source #

Helper function to make explicit let-bindings. For exampe:

newtype T = T { unT :: Fix (Let f) }

let_ :: T -> (T -> T) -> T
let_ = letWrapper T unT

Framed sharing

If your EDSL contains imperative if-the-else blocks we need to use special version of the CSE. It allocates frames per each if- or else block. So that variables from different if-the-else branches don't get messed up. We need to allocate a new frame for each branch. We can do it with special structure FrameInfo.

data FrameInfo Source #

Marker type for creation frames of variables. Start new frame when if-block starts, create next frame when you go into the next branch of the same block (with else ir elif), stop frame when leaving the if-then-else block. Use no frame for all other expressions.

Instances
Eq FrameInfo Source # 
Instance details

Defined in Data.Fix.Cse

Ord FrameInfo Source # 
Instance details

Defined in Data.Fix.Cse

Show FrameInfo Source # 
Instance details

Defined in Data.Fix.Cse

cseFramed :: (Eq (f Int), Ord (f Int), Traversable f) => (f Int -> FrameInfo) -> Fix f -> Dag f Source #

Performs common subexpression elimination with implicit sharing using information of frames. It doesn't share the variables in different branches of imperative if-then-else block.

Deprecated functions

letCata :: (Functor f, Traversable f) => (f a -> a) -> Fix (Let f) -> a Source #

Deprecated: Use letFoldFix

Catamorphism for fixpoint types wrapped in the type Let.

letCataM :: (Applicative m, Monad m, Traversable f) => (f a -> m a) -> Fix (Let f) -> m a Source #

Deprecated: Use letFoldFixM