clash-lib-1.4.1: Clash: a functional hardware description language - As a library
Copyright(C) 2012-2016 University of Twente
LicenseBSD2 (see the file LICENSE)
MaintainerChristiaan Baaij <christiaan.baaij@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Clash.Core.Util

Description

Smart constructor and destructor functions for CoreHW

Synopsis

Documentation

mkVec Source #

Arguments

:: DataCon

The Nil constructor

-> DataCon

The Cons (:>) constructor

-> Type

Element type

-> Integer

Length of the vector

-> [Term]

Elements to put in the vector

-> Term 

Create a vector of supplied elements

appendToVec Source #

Arguments

:: DataCon

The Cons (:>) constructor

-> Type

Element type

-> Term

The vector to append the elements to

-> Integer

Length of the vector

-> [Term]

Elements to append

-> Term 

Append elements to the supplied vector

extractElems Source #

Arguments

:: Supply

Unique supply

-> InScopeSet

(Superset of) in scope variables

-> DataCon

The Cons (:>) constructor

-> Type

The element type

-> Char

Char to append to the bound variable names

-> Integer

Length of the vector

-> Term

The vector

-> (Supply, [(Term, [LetBinding])]) 

Create let-bindings with case-statements that select elements out of a vector. Returns both the variables to which element-selections are bound and the let-bindings

extractTElems Source #

Arguments

:: Supply

Unique supply

-> InScopeSet

(Superset of) in scope variables

-> DataCon

The LR constructor

-> DataCon

The BR constructor

-> Type

The element type

-> Char

Char to append to the bound variable names

-> Integer

Depth of the tree

-> Term

The tree

-> (Supply, ([Term], [LetBinding])) 

Create let-bindings with case-statements that select elements out of a tree. Returns both the variables to which element-selections are bound and the let-bindings

mkRTree Source #

Arguments

:: DataCon

The LR constructor

-> DataCon

The BR constructor

-> Type

Element type

-> Integer

Depth of the tree

-> [Term]

Elements to put in the tree

-> Term 

Create a vector of supplied elements

isSignalType :: TyConMap -> Type -> Bool Source #

Determine whether a type is isomorphic to Clash.Signal.Internal.Signal

It is i.e.:

  • Signal clk a
  • (Signal clk a, Signal clk b)
  • Vec n (Signal clk a)
  • data Wrap = W (Signal clk' Int)
  • etc.

This also includes BiSignals, i.e.:

  • BiSignalIn High System Int
  • etc.

isEnable :: TyConMap -> Type -> Bool Source #

Determines whether given type is an (alias of en) Enable line.

isClockOrReset :: TyConMap -> Type -> Bool Source #

Determines whether given type is an (alias of en) Clock or Reset line

dataConInstArgTysE :: HasCallStack => InScopeSet -> TyConMap -> DataCon -> [Type] -> Maybe [Type] Source #

Same as dataConInstArgTys, but it tries to compute existentials too, hence the extra argument TyConMap. WARNING: It will return the types of non-existentials only

dataConInstArgTys :: DataCon -> [Type] -> Maybe [Type] Source #

Given a DataCon and a list of types, the type variables of the DataCon type are substituted for the list of types. The argument types are returned.

The list of types should be equal to the number of type variables, otherwise Nothing is returned.

primCo :: Type -> Term Source #

Make a coercion

undefinedTm :: Type -> Term Source #

Make an undefined term

tyLitShow :: TyConMap -> Type -> Except String String Source #

Try to reduce an arbitrary type to a literal type (Symbol or Nat), and subsequently extract its String representation

data Projections where Source #

Helper existential for shouldSplit, contains a function that:

  1. given a term of a type that should be split,
  2. creates projections of that term for all the constructor arguments

Constructors

Projections :: (forall m. MonadUnique m => InScopeSet -> Term -> m [Term]) -> Projections 

shouldSplit Source #

Arguments

:: TyConMap 
-> Type

Type to examine

-> Maybe ([Term] -> Term, Projections, [Type])

If we want to split values of the given type then we have Just:

  1. The (type-applied) data-constructor which, when applied to values of the types in 3., creates a value of the examined type
  2. Function that give a term of the type we need to split, creates projections of that term for all the types in 3.
  3. The arguments types of the product we are trying to split.

Note that we only split one level at a time (although we check all the way down), e.g. given (Int, (Clock, Bool)) we return:

Just ( (,) @Int @(Clock, Bool)
     , \s -> [case s of (a,b) -> a, case s of (a,b) -> b]
     , [Int, (Clock, Bool)])

An outer loop is required to subsequently split the (Clock, Bool) tuple.

Determine whether we should split away types from a product type, i.e. clocks should always be separate arguments, and not part of a product.

shouldSplit0 :: TyConMap -> TypeView -> Maybe ([Term] -> Term, Projections, [Type]) Source #

Worker of shouldSplit, works on TypeView instead of Type

splitShouldSplit :: TyConMap -> [Type] -> [Type] Source #

Potentially split apart a list of function argument types. e.g. given:

[Int,(Clock,(Reset,Bool)),Char]

we return

[Int,Clock,Reset,Bool,Char]

But we would leave

[Int, (Bool,Int), Char]

unchanged.

stripIP :: Type -> Type Source #

Strip implicit parameter wrappers (IP)

inverseTopSortLetBindings :: HasCallStack => Term -> Term Source #

Do an inverse topological sorting of the let-bindings in a let-expression

sccLetBindings :: HasCallStack => [LetBinding] -> [SCC LetBinding] Source #

Group let-bindings into cyclic groups and acyclic individual bindings

mkSelectorCase Source #

Arguments

:: HasCallStack 
=> MonadUnique m 
=> String

Name of the caller of this function

-> InScopeSet 
-> TyConMap

TyCon cache

-> Term

Subject of the case-composition

-> Int

n'th DataCon

-> Int

n'th field

-> m Term 

Make a case-decomposition that extracts a field out of a (Sum-of-)Product type

mkWildValBinder :: MonadUnique m => InScopeSet -> Type -> m Id Source #

Make a binder that should not be referenced

mkInternalVar Source #

Arguments

:: MonadUnique m 
=> InScopeSet 
-> OccName

Name of the identifier

-> KindOrType 
-> m Id 

Make a new, unique, identifier