hermit-0.2.0.0: Haskell Equational Reasoning Model-to-Implementation Tunnel

Safe HaskellNone

Language.HERMIT.Primitive.Local.Case

Contents

Synopsis

Rewrites on Case Expressions

externals :: [External]Source

Externals relating to Case expressions.

caseElim :: Rewrite c HermitM CoreExprSource

case s of w; C vs -> e ==> e if w and vs are not free in e

caseFloatApp :: (ExtendPath c Crumb, AddBindings c, ReadBindings c) => Rewrite c HermitM CoreExprSource

(case s of alt1 -> e1; alt2 -> e2) v ==> case s of alt1 -> e1 v; alt2 -> e2 v

caseFloatArg :: (ExtendPath c Crumb, AddBindings c, ReadBindings c) => Rewrite c HermitM CoreExprSource

f (case s of alt1 -> e1; alt2 -> e2) ==> case s of alt1 -> f e1; alt2 -> f e2 Only safe if f is strict.

caseFloatCase :: (ExtendPath c Crumb, AddBindings c, ReadBindings c) => Rewrite c HermitM CoreExprSource

case (case s1 of alt11 -> e11; alt12 -> e12) of alt21 -> e21; alt22 -> e22 ==> case s1 of alt11 -> case e11 of alt21 -> e21; alt22 -> e22 alt12 -> case e12 of alt21 -> e21; alt22 -> e22

caseFloatCast :: MonadCatch m => Rewrite c m CoreExprSource

cast (case s of p -> e) co ==> case s of p -> cast e co

caseFloatLet :: (ExtendPath c Crumb, AddBindings c, ReadBindings c) => Rewrite c HermitM CoreExprSource

let v = case s of alt1 -> e1 in e ==> case s of alt1 -> let v = e1 in e

caseFloat :: (ExtendPath c Crumb, AddBindings c, ReadBindings c) => Rewrite c HermitM CoreExprSource

Float a Case whatever the context.

caseUnfloat :: (ExtendPath c Crumb, AddBindings c, MonadCatch m) => Rewrite c m CoreExprSource

Unfloat a Case whatever the context.

caseUnfloatApp :: Monad m => Rewrite c m CoreExprSource

Unimplemented!

caseReduceDatacon :: forall c. (ExtendPath c Crumb, AddBindings c, ReadBindings c) => Rewrite c HermitM CoreExprSource

Case-of-known-constructor rewrite.

caseSplit :: Name -> Rewrite c HermitM CoreExprSource

Case split a free variable in an expression:

Assume expression e which mentions x :: [a]

e ==> case x of x [] -> e (a:b) -> e

caseSplitInline :: (ExtendPath c Crumb, AddBindings c, ReadBindings c) => Name -> Rewrite c HermitM CoreSource

Like caseSplit, but additionally inlines the constructor applications for each occurance of the named variable.

 caseSplitInline nm = caseSplit nm >>> anybuR (inlineName nm)