Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module can automatically generate TopEntity definitions from Clash.NamedTypes annotations. Annotations involving data/type families must be inspected for correctness. Not all cases can be handled with automatic generation due to the difficulty of type manipulation in template Haskell. In particular annotations inside the following is unlikely to work:
- Data/type family referencing other data/type families.
- Annotations inside recursive data types
- Clock constraints other than a single HiddenClockResetEnable. (You can still use arbitrary explicit clock/reset/enables!)
See Clash.Tests.TopEntityGeneration for more examples.
import Clash.Annotations.TH data Named = Named { name1 :: "named1" ::: BitVector 3 , name2 :: "named2" ::: BitVector 5 } topEntity :: "tup1" ::: Signal System (Int, Bool) -> "tup2" ::: (Signal System Int, Signal System Bool) -> "tup3" ::: Signal System ("int":::Int, "bool":::Bool) -> "tup4" ::: ("int":::Signal System Int, "bool":::Signal System Bool) -> "custom" ::: Signal System Named -> "outTup" ::: Signal System ("outint":::Int, "outbool":::Bool) topEntity = undefined makeTopEntity 'topEntity -- ===> --
Synopsis
- makeTopEntity :: Name -> DecsQ
- makeTopEntityWithName :: Name -> String -> DecsQ
- makeTopEntityWithName' :: Name -> Maybe String -> DecQ
- buildTopEntity :: Maybe String -> (Name, Type) -> TExpQ TopEntity
- maybeBuildTopEntity :: Maybe String -> Name -> Q (TExp (Maybe TopEntity))
- getNameBinding :: Name -> Q (Name, Type)
To create a Synthesize annotation pragma
makeTopEntity :: Name -> DecsQ Source #
Automatically create a
for a given TopEntity
. The name of the
generated RTL entity will be the name of the function that has been
specified; e.g. Name
will generate a makeTopEntity
'foobarfoobar
module.
The function arguments and return values of the function specified by the
given
must be annotated with Name
. This annotation provides the
given name of the port.(:::)
makeTopEntityWithName' :: Name -> Maybe String -> DecQ Source #
Wrap a TopEntity
expression in an annotation pragma
To create a TopEntity value
Orphan instances
Recursive Type Source # | |
project :: Type -> Base Type Type # cata :: (Base Type a -> a) -> Type -> a # para :: (Base Type (Type, a) -> a) -> Type -> a # gpara :: (Corecursive Type, Comonad w) => (forall b. Base Type (w b) -> w (Base Type b)) -> (Base Type (EnvT Type w a) -> a) -> Type -> a # prepro :: Corecursive Type => (forall b. Base Type b -> Base Type b) -> (Base Type a -> a) -> Type -> a # gprepro :: (Corecursive Type, Comonad w) => (forall b. Base Type (w b) -> w (Base Type b)) -> (forall c. Base Type c -> Base Type c) -> (Base Type (w a) -> a) -> Type -> a # | |
Corecursive Type Source # | |
embed :: Base Type Type -> Type # ana :: (a -> Base Type a) -> a -> Type # apo :: (a -> Base Type (Either Type a)) -> a -> Type # postpro :: Recursive Type => (forall b. Base Type b -> Base Type b) -> (a -> Base Type a) -> a -> Type # gpostpro :: (Recursive Type, Monad m) => (forall b. m (Base Type b) -> Base Type (m b)) -> (forall c. Base Type c -> Base Type c) -> (a -> Base Type (m a)) -> a -> Type # |