Copyright | (C) 2017-2019 Myrtle Software 2022 QBayLogic B.V. |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | QBayLogic B.V. <[email protected]> |
Safe Haskell | Safe |
Language | Haskell2010 |
Extensions |
|
Clash.Annotations.Primitive
Description
Instruct the Clash compiler to look for primitive HDL templates provided inline or in a specified directory. For distribution of new packages with primitive HDL templates. Primitive guards can be added to warn on instantiating primitives.
Synopsis
- dontTranslate :: PrimitiveGuard ()
- hasBlackBox :: PrimitiveGuard ()
- warnNonSynthesizable :: String -> PrimitiveGuard ()
- warnAlways :: String -> PrimitiveGuard ()
- data Primitive
- = Primitive [HDL] FilePath
- | InlinePrimitive [HDL] String
- | InlineYamlPrimitive [HDL] String
- data HDL
- = SystemVerilog
- | Verilog
- | VHDL
- data PrimitiveGuard a
- data PrimitiveWarning
- extractPrim :: PrimitiveGuard a -> Maybe a
- extractWarnings :: PrimitiveGuard a -> [PrimitiveWarning]
Documentation
dontTranslate :: PrimitiveGuard () Source #
Marks value as not translatable. Clash will error if it finds a blackbox
definition for it, or when it is forced to translate it. You can annotate a
variable or function f
like:
{-# ANN f dontTranslate #-}
hasBlackBox :: PrimitiveGuard () Source #
Marks a value as having a blackbox. Clash will error if it hasn't found
a blackbox. You can annotate a variable or function f
like:
{-# ANN f hasBlackBox #-}
warnNonSynthesizable :: String -> PrimitiveGuard () Source #
Marks value as non-synthesizable. This will trigger a warning if
instantiated in a non-testbench context. You can annotate a variable or
function f
like:
{-# ANN f (warnNonSynthesizable "Tread carefully, user!") #-}
Implies hasBlackBox
.
warnAlways :: String -> PrimitiveGuard () Source #
Always emit warning upon primitive instantiation. You can annotate a
variable or function f
like:
{-# ANN f (warnAlways "Tread carefully, user!") #-}
Implies hasBlackBox
.
The Primitive
constructor instructs the clash compiler to look for primitive
HDL templates in the indicated directory. InlinePrimitive
is equivalent but
provides the HDL template inline. They are intended for the distribution of
new packages with primitive HDL templates.
Example of Primitive
You have some existing IP written in one of HDLs supported by Clash, and you want to distribute some bindings so that the IP can be easily instantiated from Clash.
You create a package which has a myfancyip.cabal
file with the following stanza:
data-files: path/to/MyFancyIP.primitives cpp-options: -DCABAL
and a MyFancyIP.hs
module with the simulation definition and primitive.
module MyFancyIP where import Clash.Prelude myFancyIP :: ... myFancyIP = ... {-# NOINLINE myFancyIP #-}
The NOINLINE
pragma is needed so that GHC will never inline the definition.
Now you need to add the following imports and ANN
pragma:
#ifdef CABAL import Clash.Annotations.Primitive import System.FilePath import qualified Paths_myfancyip import System.IO.Unsafe {-# ANN module (Primitive [VHDL] (unsafePerformIO Paths_myfancyip.getDataDir </> "path" </> "to")) #-} #endif
Add more files to the data-files
stanza in your .cabal
files and more
ANN
pragma's if you want to add more primitive templates for other HDLs
Example of InlineYamlPrimitive
The following example shows off an inline HDL primitive template. It uses the string-interpolate package for nicer multiline strings.
{-# LANGUAGE QuasiQuotes #-} module InlinePrimitive where import Clash.Annotations.Primitive import Clash.Prelude import Data.String.Interpolate (__i) {-# ANN example (InlineYamlPrimitive [VHDL] [__i| BlackBox: kind: Declaration name: InlinePrimitive.example template: |- -- begin InlinePrimitive example: ~GENSYM[example][0] : block ~RESULT <= 1 + ~ARG[0]; end block; -- end InlinePrimitive example |]) #-} {-# NOINLINE example #-} example :: Signal System (BitVector 2) -> Signal System (BitVector 2) example = fmap succ
Constructors
Primitive [HDL] FilePath | Description of a primitive for a given |
InlinePrimitive [HDL] String | Description of a primitive for a given |
InlineYamlPrimitive [HDL] String | Description of a primitive for a given |
Instances
A compilation target HDL.
Constructors
SystemVerilog | |
Verilog | |
VHDL |
Instances
NFData HDL Source # | |||||
Defined in Clash.Annotations.Primitive | |||||
Data HDL Source # | |||||
Defined in Clash.Annotations.Primitive Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HDL -> c HDL # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HDL # dataTypeOf :: HDL -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HDL) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HDL) # gmapT :: (forall b. Data b => b -> b) -> HDL -> HDL # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HDL -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HDL -> r # gmapQ :: (forall d. Data d => d -> u) -> HDL -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HDL -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HDL -> m HDL # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HDL -> m HDL # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HDL -> m HDL # | |||||
Bounded HDL Source # | |||||
Enum HDL Source # | |||||
Generic HDL Source # | |||||
Defined in Clash.Annotations.Primitive Associated Types
| |||||
Read HDL Source # | |||||
Show HDL Source # | |||||
Eq HDL Source # | |||||
Hashable HDL Source # | |||||
Defined in Clash.Annotations.Primitive | |||||
type Rep HDL Source # | |||||
Defined in Clash.Annotations.Primitive type Rep HDL = D1 ('MetaData "HDL" "Clash.Annotations.Primitive" "clash-prelude-1.8.2-7pMHbdmnekg3H4aLWh5GUP" 'False) (C1 ('MetaCons "SystemVerilog" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Verilog" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "VHDL" 'PrefixI 'False) (U1 :: Type -> Type))) |
data PrimitiveGuard a Source #
Primitive guard to mark a value as either not translatable or as having a blackbox with an optional extra warning. Helps Clash generate better error messages.
For use, see dontTranslate
, hasBlackBox
, warnNonSynthesizable
and
warnAlways
.
Constructors
DontTranslate | Marks value as not translatable. Clash will error if it finds a blackbox definition for it, or when it is forced to translate it. |
HasBlackBox [PrimitiveWarning] a | Marks a value as having a blackbox. Clash will error if it hasn't found a blackbox. |
Instances
Functor PrimitiveGuard Source # | |||||
Defined in Clash.Annotations.Primitive Methods fmap :: (a -> b) -> PrimitiveGuard a -> PrimitiveGuard b # (<$) :: a -> PrimitiveGuard b -> PrimitiveGuard a # | |||||
Foldable PrimitiveGuard Source # | |||||
Defined in Clash.Annotations.Primitive Methods fold :: Monoid m => PrimitiveGuard m -> m # foldMap :: Monoid m => (a -> m) -> PrimitiveGuard a -> m # foldMap' :: Monoid m => (a -> m) -> PrimitiveGuard a -> m # foldr :: (a -> b -> b) -> b -> PrimitiveGuard a -> b # foldr' :: (a -> b -> b) -> b -> PrimitiveGuard a -> b # foldl :: (b -> a -> b) -> b -> PrimitiveGuard a -> b # foldl' :: (b -> a -> b) -> b -> PrimitiveGuard a -> b # foldr1 :: (a -> a -> a) -> PrimitiveGuard a -> a # foldl1 :: (a -> a -> a) -> PrimitiveGuard a -> a # toList :: PrimitiveGuard a -> [a] # null :: PrimitiveGuard a -> Bool # length :: PrimitiveGuard a -> Int # elem :: Eq a => a -> PrimitiveGuard a -> Bool # maximum :: Ord a => PrimitiveGuard a -> a # minimum :: Ord a => PrimitiveGuard a -> a # sum :: Num a => PrimitiveGuard a -> a # product :: Num a => PrimitiveGuard a -> a # | |||||
Traversable PrimitiveGuard Source # | |||||
Defined in Clash.Annotations.Primitive Methods traverse :: Applicative f => (a -> f b) -> PrimitiveGuard a -> f (PrimitiveGuard b) # sequenceA :: Applicative f => PrimitiveGuard (f a) -> f (PrimitiveGuard a) # mapM :: Monad m => (a -> m b) -> PrimitiveGuard a -> m (PrimitiveGuard b) # sequence :: Monad m => PrimitiveGuard (m a) -> m (PrimitiveGuard a) # | |||||
Binary a => Binary (PrimitiveGuard a) Source # | |||||
Defined in Clash.Annotations.Primitive Methods put :: PrimitiveGuard a -> Put # get :: Get (PrimitiveGuard a) # putList :: [PrimitiveGuard a] -> Put # | |||||
NFData a => NFData (PrimitiveGuard a) Source # | |||||
Defined in Clash.Annotations.Primitive Methods rnf :: PrimitiveGuard a -> () # | |||||
Data a => Data (PrimitiveGuard a) Source # | |||||
Defined in Clash.Annotations.Primitive Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PrimitiveGuard a -> c (PrimitiveGuard a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (PrimitiveGuard a) # toConstr :: PrimitiveGuard a -> Constr # dataTypeOf :: PrimitiveGuard a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (PrimitiveGuard a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (PrimitiveGuard a)) # gmapT :: (forall b. Data b => b -> b) -> PrimitiveGuard a -> PrimitiveGuard a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PrimitiveGuard a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PrimitiveGuard a -> r # gmapQ :: (forall d. Data d => d -> u) -> PrimitiveGuard a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PrimitiveGuard a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PrimitiveGuard a -> m (PrimitiveGuard a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PrimitiveGuard a -> m (PrimitiveGuard a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PrimitiveGuard a -> m (PrimitiveGuard a) # | |||||
Generic (PrimitiveGuard a) Source # | |||||
Defined in Clash.Annotations.Primitive Associated Types
Methods from :: PrimitiveGuard a -> Rep (PrimitiveGuard a) x # to :: Rep (PrimitiveGuard a) x -> PrimitiveGuard a # | |||||
Read a => Read (PrimitiveGuard a) Source # | |||||
Defined in Clash.Annotations.Primitive Methods readsPrec :: Int -> ReadS (PrimitiveGuard a) # readList :: ReadS [PrimitiveGuard a] # readPrec :: ReadPrec (PrimitiveGuard a) # readListPrec :: ReadPrec [PrimitiveGuard a] # | |||||
Show a => Show (PrimitiveGuard a) Source # | |||||
Defined in Clash.Annotations.Primitive Methods showsPrec :: Int -> PrimitiveGuard a -> ShowS # show :: PrimitiveGuard a -> String # showList :: [PrimitiveGuard a] -> ShowS # | |||||
Eq a => Eq (PrimitiveGuard a) Source # | |||||
Defined in Clash.Annotations.Primitive Methods (==) :: PrimitiveGuard a -> PrimitiveGuard a -> Bool # (/=) :: PrimitiveGuard a -> PrimitiveGuard a -> Bool # | |||||
Hashable a => Hashable (PrimitiveGuard a) Source # | |||||
Defined in Clash.Annotations.Primitive | |||||
type Rep (PrimitiveGuard a) Source # | |||||
Defined in Clash.Annotations.Primitive type Rep (PrimitiveGuard a) = D1 ('MetaData "PrimitiveGuard" "Clash.Annotations.Primitive" "clash-prelude-1.8.2-7pMHbdmnekg3H4aLWh5GUP" 'False) (C1 ('MetaCons "DontTranslate" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HasBlackBox" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PrimitiveWarning]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))) |
data PrimitiveWarning Source #
Warning that will be emitted on instantiating a guarded value.
Constructors
WarnNonSynthesizable String | Marks value as non-synthesizable. This will trigger a warning if instantiated in a non-testbench context. |
WarnAlways String | Always emit warning upon primitive instantiation. |
Instances
Binary PrimitiveWarning Source # | |||||
Defined in Clash.Annotations.Primitive Methods put :: PrimitiveWarning -> Put # get :: Get PrimitiveWarning # putList :: [PrimitiveWarning] -> Put # | |||||
NFData PrimitiveWarning Source # | |||||
Defined in Clash.Annotations.Primitive Methods rnf :: PrimitiveWarning -> () # | |||||
Data PrimitiveWarning Source # | |||||
Defined in Clash.Annotations.Primitive Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PrimitiveWarning -> c PrimitiveWarning # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PrimitiveWarning # toConstr :: PrimitiveWarning -> Constr # dataTypeOf :: PrimitiveWarning -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PrimitiveWarning) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PrimitiveWarning) # gmapT :: (forall b. Data b => b -> b) -> PrimitiveWarning -> PrimitiveWarning # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PrimitiveWarning -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PrimitiveWarning -> r # gmapQ :: (forall d. Data d => d -> u) -> PrimitiveWarning -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PrimitiveWarning -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PrimitiveWarning -> m PrimitiveWarning # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PrimitiveWarning -> m PrimitiveWarning # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PrimitiveWarning -> m PrimitiveWarning # | |||||
Generic PrimitiveWarning Source # | |||||
Defined in Clash.Annotations.Primitive Associated Types
Methods from :: PrimitiveWarning -> Rep PrimitiveWarning x # to :: Rep PrimitiveWarning x -> PrimitiveWarning # | |||||
Read PrimitiveWarning Source # | |||||
Defined in Clash.Annotations.Primitive Methods readsPrec :: Int -> ReadS PrimitiveWarning # readList :: ReadS [PrimitiveWarning] # | |||||
Show PrimitiveWarning Source # | |||||
Defined in Clash.Annotations.Primitive Methods showsPrec :: Int -> PrimitiveWarning -> ShowS # show :: PrimitiveWarning -> String # showList :: [PrimitiveWarning] -> ShowS # | |||||
Eq PrimitiveWarning Source # | |||||
Defined in Clash.Annotations.Primitive Methods (==) :: PrimitiveWarning -> PrimitiveWarning -> Bool # (/=) :: PrimitiveWarning -> PrimitiveWarning -> Bool # | |||||
Hashable PrimitiveWarning Source # | |||||
Defined in Clash.Annotations.Primitive | |||||
type Rep PrimitiveWarning Source # | |||||
Defined in Clash.Annotations.Primitive type Rep PrimitiveWarning = D1 ('MetaData "PrimitiveWarning" "Clash.Annotations.Primitive" "clash-prelude-1.8.2-7pMHbdmnekg3H4aLWh5GUP" 'False) (C1 ('MetaCons "WarnNonSynthesizable" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "WarnAlways" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) |
extractPrim :: PrimitiveGuard a -> Maybe a Source #
Extract primitive definition from a PrimitiveGuard. Will yield Nothing
for guards of value DontTranslate
.
extractWarnings :: PrimitiveGuard a -> [PrimitiveWarning] Source #
Extract primitive warnings from a PrimitiveGuard. Will yield an empty list
for guards of value DontTranslate
.