clash-lib-0.99.2: CAES Language for Synchronous Hardware - As a Library

Copyright(C) 2012-2016 University of Twente
2016-2017 Myrtle Software Ltd
2017 Google Inc.
LicenseBSD2 (see the file LICENSE)
MaintainerChristiaan Baaij <christiaan.baaij@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Clash.Normalize.Transformations

Description

Transformations of the Normalization process

Synopsis

Documentation

appProp :: NormRewrite Source #

Propagate arguments of application inwards; except for Lam where the argument becomes let-bound.

caseLet :: NormRewrite Source #

Lift the let-bindings out of the subject of a Case-decomposition

caseCon :: NormRewrite Source #

Specialize a Case-decomposition (replace by the RHS of an alternative) if the subject is (an application of) a DataCon; or if there is only a single alternative that doesn't reference variables bound by the pattern.

caseCase :: NormRewrite Source #

Move a Case-decomposition from the subject of a Case-decomposition to the alternatives

inlineNonRep :: NormRewrite Source #

Inline function with a non-representable result if it's the subject of a Case-decomposition

typeSpec :: NormRewrite Source #

Specialize functions on their type

nonRepSpec :: NormRewrite Source #

Specialize functions on their non-representable argument

etaExpansionTL :: NormRewrite Source #

Eta-expand top-level lambda's (DON'T use in a traversal!)

nonRepANF :: NormRewrite Source #

Bring an application of a DataCon or Primitive in ANF, when the argument is is considered non-representable

bindConstantVar :: NormRewrite Source #

Inline let-bindings when the RHS is either a local variable reference or is constant (except clock or reset generators)

constantSpec :: NormRewrite Source #

Specialise functions on arguments which are constant, except when they are clock or reset generators

makeANF :: NormRewrite Source #

Turn an expression into a modified ANF-form. As opposed to standard ANF, constants do not become let-bound.

deadCode :: NormRewrite Source #

Remove unused let-bindings

topLet :: NormRewrite Source #

Ensure that top-level lambda's eventually bind a let-expression of which the body is a variable-reference.

recToLetRec :: NormRewrite Source #

Turn a normalized recursive function, where the recursive calls only pass along the unchanged original arguments, into let-recursive function. This means that all recursive calls are replaced by the same variable reference as found in the body of the top-level let-expression.

inlineWorkFree :: NormRewrite Source #

Inline work-free functions, i.e. fully applied functions that evaluate to a constant

inlineHO :: NormRewrite Source #

Inline a function with functional arguments

inlineSmall :: NormRewrite Source #

Inline small functions

simpleCSE :: NormRewrite Source #

Simplified CSE, only works on let-bindings, works from top to bottom

reduceNonRepPrim :: NormRewrite Source #

Replace primitives by their "definition" if they would lead to let-bindings with a non-representable type when a function is in ANF. This happens for example when Clash.Size.Vector.map consumes or produces a vector of non-representable elements.

Basically what this transformation does is replace a primitive the completely unrolled recursive definition that it represents. e.g.

zipWith ($) (xs :: Vec 2 (Int -> Int)) (ys :: Vec 2 Int)

is replaced by:

let (x0  :: (Int -> Int))       = case xs  of (:>) _ x xr -> x
    (xr0 :: Vec 1 (Int -> Int)) = case xs  of (:>) _ x xr -> xr
    (x1  :: (Int -> Int)(       = case xr0 of (:>) _ x xr -> x
    (y0  :: Int)                = case ys  of (:>) _ y yr -> y
    (yr0 :: Vec 1 Int)          = case ys  of (:>) _ y yr -> xr
    (y1  :: Int                 = case yr0 of (:>) _ y yr -> y
in  (($) x0 y0 :> ($) x1 y1 :> Nil)

Currently, it only handles the following functions:

  • Clash.Sized.Vector.map
  • Clash.Sized.Vector.zipWith
  • Clash.Sized.Vector.traverse#
  • Clash.Sized.Vector.foldr
  • Clash.Sized.Vector.fold
  • Clash.Sized.Vector.dfold
  • Clash.Sized.Vector.(++)
  • Clash.Sized.Vector.head
  • Clash.Sized.Vector.tail
  • Clash.Sized.Vector.unconcat
  • Clash.Sized.Vector.transpose
  • Clash.Sized.Vector.replicate
  • Clash.Sized.Vector.dtfold

caseFlat :: NormRewrite Source #

Flatten ridiculous case-statements generated by GHC

For case-statements in haskell of the form:

f :: Unsigned 4 -> Unsigned 4
f x = case x of
  0 -> 3
  1 -> 2
  2 -> 1
  3 -> 0

GHC generates Core that looks like:

f = (x :: Unsigned 4) -> case x == fromInteger 3 of
                            False -> case x == fromInteger 2 of
                              False -> case x == fromInteger 1 of
                                False -> case x == fromInteger 0 of
                                  False -> error "incomplete case"
                                  True  -> fromInteger 3
                                True -> fromInteger 2
                              True -> fromInteger 1
                            True -> fromInteger 0

Which would result in a priority decoder circuit where a normal decoder circuit was desired.

This transformation transforms the above Core to the saner:

f = (x :: Unsigned 4) -> case x of
       _ -> error "incomplete case"
       0 -> fromInteger 3
       1 -> fromInteger 2
       2 -> fromInteger 1
       3 -> fromInteger 0

disjointExpressionConsolidation :: NormRewrite Source #

This transformation lifts applications of global binders out of alternatives of case-statements.

e.g. It converts:

case x of
  A -> f 3 y
  B -> f x x
  C -> h x

into:

let f_arg0 = case x of {A -> 3; B -> x}
    f_arg1 = case x of {A -> y; B -> x}
    f_out  = f f_arg0 f_arg1
in  case x of
      A -> f_out
      B -> f_out
      C -> h x

inlineCleanup :: NormRewrite Source #

Given a function in the desired normal form, inline all the following let-bindings:

Let-bindings with an internal name that is only used once, where it binds: * a primitive that will be translated to an HDL expression (as opposed to a HDL declaration) * a projection case-expression (1 alternative) * a data constructor

flattenLet :: NormRewrite Source #

Flatten's letrecs after inlineCleanup

inlineCleanup sometimes exposes additional possibilities for caseCon, which then introduces let-bindings in what should be ANF. This transformation flattens those nested let-bindings again.

NB: must only be called in the cleaning up phase.

splitCastWork :: NormRewrite Source #

Make a cast work-free by splitting the work of to a separate binding

let x = cast (f a b)
==>
let x  = cast x'
    x' = f a b

inlineCast :: NormRewrite Source #

Only inline casts that just contain a Var, because these are guaranteed work-free. These are the result of the splitCastWork transformation.

caseCast :: NormRewrite Source #

Push a cast over a case into it's alternatives.

letCast :: NormRewrite Source #

Push a cast over a Letrec into it's body

eliminateCastCast :: NormRewrite Source #

Eliminate two back to back casts where the type going in and coming out are the same

  (cast :: b -> a) $ (cast :: a -> b) x   ==> x

argCastSpec :: NormRewrite Source #

Push cast over an argument to a funtion into that function

This is done by specializing on the casted argument. Example: y = f (cast a) where f x = g x transforms to: y = f' a where f' x' = (x -> g x) (cast x')