clash-prelude-1.2.0: CAES Language for Synchronous Hardware - Prelude library

Copyright(C) 2017-2019 Myrtle Software QBayLogic
LicenseBSD2 (see the file LICENSE)
MaintainerChristiaan Baaij <christiaan.baaij@gmail.com>
Safe HaskellSafe
LanguageHaskell2010
Extensions
  • TemplateHaskellQuotes
  • ScopedTypeVariables
  • BangPatterns
  • ViewPatterns
  • DataKinds
  • InstanceSigs
  • StandaloneDeriving
  • DeriveDataTypeable
  • DeriveFunctor
  • DeriveTraversable
  • DeriveFoldable
  • DeriveGeneric
  • DefaultSignatures
  • DeriveAnyClass
  • DeriveLift
  • DerivingStrategies
  • MagicHash
  • KindSignatures
  • TupleSections
  • TypeOperators
  • ExplicitNamespaces
  • ExplicitForAll
  • LambdaCase
  • BinaryLiterals
  • TypeApplications

Clash.Annotations.Primitive

Description

Instruct the clash compiler to look for primitive HDL templates in the indicated directory. For distribution of new packages with primitive HDL templates.

Synopsis

Documentation

data Primitive Source #

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.json
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.

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

Constructors

Primitive [HDL] FilePath

Description of a primitive for a given HDLs in a file at FilePath

InlinePrimitive [HDL] String

Description of a primitive for a given HDLs as an inline String

Instances
Data Primitive Source # 
Instance details

Defined in Clash.Annotations.Primitive

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Primitive -> c Primitive #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Primitive #

toConstr :: Primitive -> Constr #

dataTypeOf :: Primitive -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Primitive) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Primitive) #

gmapT :: (forall b. Data b => b -> b) -> Primitive -> Primitive #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Primitive -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Primitive -> r #

gmapQ :: (forall d. Data d => d -> u) -> Primitive -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Primitive -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Primitive -> m Primitive #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Primitive -> m Primitive #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Primitive -> m Primitive #

Read Primitive Source # 
Instance details

Defined in Clash.Annotations.Primitive

Show Primitive Source # 
Instance details

Defined in Clash.Annotations.Primitive

Generic Primitive Source # 
Instance details

Defined in Clash.Annotations.Primitive

Associated Types

type Rep Primitive :: Type -> Type #

NFData Primitive Source # 
Instance details

Defined in Clash.Annotations.Primitive

Methods

rnf :: Primitive -> () #

Hashable Primitive Source # 
Instance details

Defined in Clash.Annotations.Primitive

type Rep Primitive Source # 
Instance details

Defined in Clash.Annotations.Primitive

data PrimitiveGuard a Source #

Guard primitive functions. This will help Clash generate better error messages. You can annotate a function like:

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 a

Marks a value as having a blackbox. Clash will err if it hasn't found a blackbox

WarnNonSynthesizable String a

Marks value as non-synthesizable. This will trigger a warning if instantiated in a non-testbench context. Implies HasBlackBox.

WarnAlways String a

Always emit warning upon instantiation. Implies HasBlackBox.

Instances
Functor PrimitiveGuard Source # 
Instance details

Defined in Clash.Annotations.Primitive

Methods

fmap :: (a -> b) -> PrimitiveGuard a -> PrimitiveGuard b #

(<$) :: a -> PrimitiveGuard b -> PrimitiveGuard a #

Foldable PrimitiveGuard Source # 
Instance details

Defined in Clash.Annotations.Primitive

Methods

fold :: Monoid m => PrimitiveGuard m -> 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 # 
Instance details

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) #

Data a => Data (PrimitiveGuard a) Source # 
Instance details

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 :: (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) #

Read a => Read (PrimitiveGuard a) Source # 
Instance details

Defined in Clash.Annotations.Primitive

Show a => Show (PrimitiveGuard a) Source # 
Instance details

Defined in Clash.Annotations.Primitive

Generic (PrimitiveGuard a) Source # 
Instance details

Defined in Clash.Annotations.Primitive

Associated Types

type Rep (PrimitiveGuard a) :: Type -> Type #

Binary a => Binary (PrimitiveGuard a) Source # 
Instance details

Defined in Clash.Annotations.Primitive

NFData a => NFData (PrimitiveGuard a) Source # 
Instance details

Defined in Clash.Annotations.Primitive

Methods

rnf :: PrimitiveGuard a -> () #

Hashable a => Hashable (PrimitiveGuard a) Source # 
Instance details

Defined in Clash.Annotations.Primitive

type Rep (PrimitiveGuard a) Source # 
Instance details

Defined in Clash.Annotations.Primitive

data HDL Source #

Constructors

SystemVerilog 
Verilog 
VHDL 
Instances
Bounded HDL Source # 
Instance details

Defined in Clash.Annotations.Primitive

Methods

minBound :: HDL #

maxBound :: HDL #

Enum HDL Source # 
Instance details

Defined in Clash.Annotations.Primitive

Methods

succ :: HDL -> HDL #

pred :: HDL -> HDL #

toEnum :: Int -> HDL #

fromEnum :: HDL -> Int #

enumFrom :: HDL -> [HDL] #

enumFromThen :: HDL -> HDL -> [HDL] #

enumFromTo :: HDL -> HDL -> [HDL] #

enumFromThenTo :: HDL -> HDL -> HDL -> [HDL] #

Eq HDL Source # 
Instance details

Defined in Clash.Annotations.Primitive

Methods

(==) :: HDL -> HDL -> Bool #

(/=) :: HDL -> HDL -> Bool #

Data HDL Source # 
Instance details

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 #

toConstr :: HDL -> Constr #

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 :: (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 # 
Instance details

Defined in Clash.Annotations.Primitive

Show HDL Source # 
Instance details

Defined in Clash.Annotations.Primitive

Methods

showsPrec :: Int -> HDL -> ShowS #

show :: HDL -> String #

showList :: [HDL] -> ShowS #

Generic HDL Source # 
Instance details

Defined in Clash.Annotations.Primitive

Associated Types

type Rep HDL :: Type -> Type #

Methods

from :: HDL -> Rep HDL x #

to :: Rep HDL x -> HDL #

NFData HDL Source # 
Instance details

Defined in Clash.Annotations.Primitive

Methods

rnf :: HDL -> () #

Hashable HDL Source # 
Instance details

Defined in Clash.Annotations.Primitive

Methods

hashWithSalt :: Int -> HDL -> Int #

hash :: HDL -> Int #

type Rep HDL Source # 
Instance details

Defined in Clash.Annotations.Primitive

type Rep HDL = D1 (MetaData "HDL" "Clash.Annotations.Primitive" "clash-prelude-1.2.0-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)))

extractPrim :: PrimitiveGuard a -> Maybe a Source #

Extract primitive definition from a PrimitiveGuard. Will yield Nothing for guards of value DontTranslate.