Copyright | (C) 2017-2019 Myrtle Software QBayLogic |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | Christiaan Baaij <christiaan.baaij@gmail.com> |
Safe Haskell | Safe |
Language | Haskell2010 |
Extensions |
|
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
- 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 InlinePrimitive
The following example shows off an inline HDL primitive template. It uses the interpolate package for nicer multiline strings.
{-# LANGUAGE QuasiQuotes #-} module InlinePrimitive where import Clash.Annotations.Primitive import Clash.Prelude import Data.String.Interpolate (i) import Data.String.Interpolate.Util (unindent) {-# ANN example (InlinePrimitive [VHDL] $ unindent [i| [ { "BlackBox" : { "name" : "InlinePrimitive.example" , "kind": "Declaration" , "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
Primitive [HDL] FilePath | Description of a primitive for a given |
InlinePrimitive [HDL] String | Description of a primitive for a given |
Instances
A compilation target HDL.
Instances
Bounded HDL Source # | |
Enum HDL Source # | |
Eq HDL Source # | |
Data HDL Source # | |
Defined in Clash.Annotations.Primitive 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 # | |
Read HDL Source # | |
Show HDL Source # | |
Generic HDL Source # | |
NFData HDL Source # | |
Defined in Clash.Annotations.Primitive | |
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.4.3-inplace" '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
.
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
data PrimitiveWarning Source #
Warning that will be emitted on instantiating a guarded value.
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
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
.