Copyright | (C) 2015-2016 University of Twente 2016 Myrtle Software Ltd |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | Christiaan Baaij <christiaan.baaij@gmail.com> |
Safe Haskell | None |
Language | Haskell2010 |
Reductions of primitives
Currently, it contains reductions for:
- 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.unconcatBitVector#
- Clash.Sized.Vector.replicate
- Clash.Sized.Vector.imap
- Clash.Sized.Vector.dtfold
- Clash.Sized.RTree.tfold
- Clash.Sized.Vector.reverse
- Clash.Sized.Vector.unconcat
Partially handles:
- Clash.Sized.Vector.transpose
Synopsis
- typeNatAdd :: TyConName
- typeNatMul :: TyConName
- typeNatSub :: TyConName
- vecHeadPrim :: TyConName -> Term
- vecLastPrim :: TyConName -> Term
- vecHeadTy :: TyConName -> Type
- vecTailPrim :: TyConName -> Term
- vecInitPrim :: TyConName -> Term
- vecTailTy :: TyConName -> Type
- extractHeadTail :: DataCon -> Type -> Integer -> Term -> (Term, Term)
- extractHead :: DataCon -> Type -> Integer -> Term -> Term
- extractTail :: DataCon -> Type -> Integer -> Term -> Term
- mkVecCons :: HasCallStack => DataCon -> Type -> Integer -> Term -> Term -> Term
- mkVecNil :: DataCon -> Type -> Term
- reduceReverse :: InScopeSet -> Integer -> Type -> Term -> NormalizeSession Term
- reduceZipWith :: TransformContext -> PrimInfo -> Integer -> Type -> Type -> Type -> Term -> Term -> Term -> NormalizeSession Term
- reduceMap :: TransformContext -> PrimInfo -> Integer -> Type -> Type -> Term -> Term -> NormalizeSession Term
- reduceImap :: TransformContext -> Integer -> Type -> Type -> Term -> Term -> NormalizeSession Term
- reduceIterateI :: TransformContext -> Integer -> Type -> Type -> Term -> Term -> RewriteMonad NormalizeState Term
- reduceTraverse :: TransformContext -> Integer -> Type -> Type -> Type -> Term -> Term -> Term -> NormalizeSession Term
- mkTravVec :: TyConName -> DataCon -> DataCon -> Term -> Term -> Term -> Type -> Integer -> [Term] -> Term
- reduceFoldr :: TransformContext -> PrimInfo -> Integer -> Type -> Term -> Term -> Term -> NormalizeSession Term
- reduceFold :: TransformContext -> Integer -> Type -> Term -> Term -> NormalizeSession Term
- reduceDFold :: InScopeSet -> Integer -> Type -> Term -> Term -> Term -> NormalizeSession Term
- reduceHead :: InScopeSet -> Integer -> Type -> Term -> NormalizeSession Term
- reduceTail :: InScopeSet -> Integer -> Type -> Term -> NormalizeSession Term
- reduceLast :: InScopeSet -> Integer -> Type -> Term -> NormalizeSession Term
- reduceInit :: InScopeSet -> PrimInfo -> Integer -> Type -> Term -> NormalizeSession Term
- reduceAppend :: InScopeSet -> Integer -> Integer -> Type -> Term -> Term -> NormalizeSession Term
- reduceUnconcat :: InScopeSet -> PrimInfo -> Integer -> Integer -> Type -> Term -> Term -> NormalizeSession Term
- reduceTranspose :: Integer -> Integer -> Type -> Term -> NormalizeSession Term
- reduceReplicate :: Integer -> Type -> Type -> Term -> NormalizeSession Term
- reduceReplace_int :: InScopeSet -> Integer -> Type -> Type -> Term -> Term -> Term -> NormalizeSession Term
- reduceIndex_int :: InScopeSet -> Integer -> Type -> Term -> Term -> NormalizeSession Term
- reduceDTFold :: InScopeSet -> Integer -> Type -> Term -> Term -> Term -> NormalizeSession Term
- reduceTFold :: InScopeSet -> Integer -> Type -> Term -> Term -> Term -> NormalizeSession Term
- reduceTReplicate :: Integer -> Type -> Type -> Term -> NormalizeSession Term
- buildSNat :: DataCon -> Integer -> Term
Documentation
:: DataCon | The Cons (:>) constructor |
-> Type | Element type |
-> Integer | Length of the vector |
-> Term | Vector to extract head from |
-> (Term, Term) | (head of vector, tail of vector) |
Makes two case statements: the first one extract the _head_ from the given vector, the latter the tail.
:: HasCallStack | |
=> DataCon | The Cons (:>) constructor |
-> Type | Element type |
-> Integer | Length of the vector |
-> Term | head of the vector |
-> Term | tail of the vector |
-> Term |
Create a vector of supplied elements
:: InScopeSet | |
-> Integer | Length of the vector |
-> Type | Element of type of the vector |
-> Term | The vector to reverse |
-> NormalizeSession Term |
Replace an application of the Clash.Sized.Vector.reverse
primitive on
vectors of a known length n
, by the fully unrolled recursive "definition"
of Clash.Sized.Vector.reverse
:: TransformContext | |
-> PrimInfo | zipWith primitive info |
-> Integer | Length of the vector(s) |
-> Type | Element type of the lhs of the function |
-> Type | Element type of the rhs of the function |
-> Type | Element type of the result of the function |
-> Term | The zipWith'd functions |
-> Term | The 1st vector argument |
-> Term | The 2nd vector argument |
-> NormalizeSession Term |
Replace an application of the Clash.Sized.Vector.zipWith
primitive on
vectors of a known length n
, by the fully unrolled recursive "definition"
of Clash.Sized.Vector.zipWith
:: TransformContext | |
-> PrimInfo | map primitive info |
-> Integer | Length of the vector |
-> Type | Argument type of the function |
-> Type | Result type of the function |
-> Term | The map'd function |
-> Term | The map'd over vector |
-> NormalizeSession Term |
Replace an application of the Clash.Sized.Vector.map
primitive on vectors
of a known length n
, by the fully unrolled recursive "definition" of
Clash.Sized.Vector.map
:: TransformContext | |
-> Integer | Length of the vector |
-> Type | Argument type of the function |
-> Type | Result type of the function |
-> Term | The imap'd function |
-> Term | The imap'd over vector |
-> NormalizeSession Term |
Replace an application of the Clash.Sized.Vector.imap
primitive on vectors
of a known length n
, by the fully unrolled recursive "definition" of
Clash.Sized.Vector.imap
:: TransformContext | |
-> Integer | Length of vector |
-> Type | Vector's element type |
-> Type | Vector's type |
-> Term | iterateI's HO-function argument |
-> Term | iterateI's start value |
-> RewriteMonad NormalizeState Term | Fully unrolled definition |
Replace an application of the Clash.Sized.Vector.iterateI
primitive on
vectors of a known length n
, by the fully unrolled recursive "definition"
of Clash.Sized.Vector.iterateI
:: TransformContext | |
-> Integer | Length of the vector |
-> Type | Element type of the argument vector |
-> Type | The type of the applicative |
-> Type | Element type of the result vector |
-> Term | The |
-> Term | The function to traverse with |
-> Term | The argument vector |
-> NormalizeSession Term |
Replace an application of the Clash.Sized.Vector.traverse#
primitive on
vectors of a known length n
, by the fully unrolled recursive "definition"
of Clash.Sized.Vector.traverse#
:: TyConName | Vec tcon |
-> DataCon | Nil con |
-> DataCon | Cons con |
-> Term |
|
-> Term |
|
-> Term |
|
-> Type |
|
-> Integer | Length of the vector |
-> [Term] | Elements of the vector |
-> Term |
Create the traversable vector
e.g. for a length '2' input vector, we get
(:>) <$> x0 <*> ((:>) <$> x1 <*> pure Nil)
:: TransformContext | |
-> PrimInfo | Primitive info for foldr blackbox |
-> Integer | Length of the vector |
-> Type | Element type of the argument vector |
-> Term | The function to fold with |
-> Term | The starting value |
-> Term | The argument vector |
-> NormalizeSession Term |
Replace an application of the Clash.Sized.Vector.foldr
primitive on
vectors of a known length n
, by the fully unrolled recursive "definition"
of Clash.Sized.Vector.foldr
:: TransformContext | |
-> Integer | Length of the vector |
-> Type | Element type of the argument vector |
-> Term | The function to fold with |
-> Term | The argument vector |
-> NormalizeSession Term |
Replace an application of the Clash.Sized.Vector.fold
primitive on
vectors of a known length n
, by the fully unrolled recursive "definition"
of Clash.Sized.Vector.fold
:: InScopeSet | |
-> Integer | Length of the vector |
-> Type | Element type of the argument vector |
-> Term | Function to fold with |
-> Term | Starting value |
-> Term | The vector to fold |
-> NormalizeSession Term |
Replace an application of the Clash.Sized.Vector.dfold
primitive on
vectors of a known length n
, by the fully unrolled recursive "definition"
of Clash.Sized.Vector.dfold
:: InScopeSet | |
-> Integer | Length of the vector |
-> Type | Element type of the vector |
-> Term | The argument vector |
-> NormalizeSession Term |
Replace an application of the Clash.Sized.Vector.head
primitive on
vectors of a known length n
, by a projection of the first element of a
vector.
:: InScopeSet | |
-> Integer | Length of the vector |
-> Type | Element type of the vector |
-> Term | The argument vector |
-> NormalizeSession Term |
Replace an application of the Clash.Sized.Vector.tail
primitive on
vectors of a known length n
, by a projection of the tail of a
vector.
:: InScopeSet | |
-> Integer | Length of the vector |
-> Type | Element type of the vector |
-> Term | The argument vector |
-> NormalizeSession Term |
Replace an application of the Clash.Sized.Vector.last
primitive on
vectors of a known length n
, by a projection of the last element of a
vector.
:: InScopeSet | |
-> PrimInfo | Primitive info for |
-> Integer | Length of the vector |
-> Type | Element type of the vector |
-> Term | The argument vector |
-> NormalizeSession Term |
Replace an application of the Clash.Sized.Vector.init
primitive on
vectors of a known length n
, by a projection of the init of a
vector.
:: InScopeSet | |
-> Integer | Length of the LHS arg |
-> Integer | Lenght of the RHS arg |
-> Type | Element type of the vectors |
-> Term | The LHS argument |
-> Term | The RHS argument |
-> NormalizeSession Term |
Replace an application of the Clash.Sized.Vector.(++)
primitive on
vectors of a known length n
, by the fully unrolled recursive "definition"
of Clash.Sized.Vector.(++)
:: InScopeSet | |
-> PrimInfo | Unconcat primitive info |
-> Integer | Length of the result vector |
-> Integer | Length of the elements of the result vector |
-> Type | Element type |
-> Term | SNat "Length of the elements of the result vector" |
-> Term | Argument vector |
-> NormalizeSession Term |
Replace an application of the Clash.Sized.Vector.unconcat
primitive on
vectors of a known length n
, by the fully unrolled recursive "definition"
of Clash.Sized.Vector.unconcat
:: Integer | Length of the result vector |
-> Integer | Length of the elements of the result vector |
-> Type | Element type |
-> Term | Argument vector |
-> NormalizeSession Term |
Replace an application of the Clash.Sized.Vector.transpose
primitive on
vectors of a known length n
, by the fully unrolled recursive "definition"
of Clash.Sized.Vector.transpose
reduceReplicate :: Integer -> Type -> Type -> Term -> NormalizeSession Term Source #
:: InScopeSet | |
-> Integer | Size of vector |
-> Type | Type of vector element |
-> Type | Type of vector |
-> Term | Vector |
-> Term | Index |
-> Term | Element |
-> NormalizeSession Term |
:: InScopeSet | |
-> Integer | Size of vector |
-> Type | Type of vector element |
-> Term | Vector |
-> Term | Index |
-> NormalizeSession Term |
:: InScopeSet | |
-> Integer | Length of the vector |
-> Type | Element type of the argument vector |
-> Term | Function to convert elements with |
-> Term | Function to combine branches with |
-> Term | The vector to fold |
-> NormalizeSession Term |
Replace an application of the Clash.Sized.Vector.dtfold
primitive on
vectors of a known length n
, by the fully unrolled recursive "definition"
of Clash.Sized.Vector.dtfold
:: InScopeSet | |
-> Integer | Depth of the tree |
-> Type | Element type of the argument tree |
-> Term | Function to convert elements with |
-> Term | Function to combine branches with |
-> Term | The tree to fold |
-> NormalizeSession Term |
Replace an application of the Clash.Sized.RTree.tdfold
primitive on
trees of a known depth n
, by the fully unrolled recursive "definition"
of Clash.Sized.RTree.tdfold