Copyright | (C) 2020 QBayLogic B.V. |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | QBayLogic B.V. <devops@qbaylogic.com> |
Safe Haskell | None |
Language | Haskell2010 |
Transform/format a Netlist Identifier so that it is acceptable as a HDL identifier
Synopsis
- data IdentifierSet
- class Monad m => IdentifierSetMonad m where
- identifierSetM :: (IdentifierSet -> IdentifierSet) -> m IdentifierSet
- class HasIdentifierSet s where
- emptyIdentifierSet :: Bool -> PreserveCase -> HDL -> IdentifierSet
- makeSet :: Bool -> PreserveCase -> HDL -> HashSet Identifier -> IdentifierSet
- clearSet :: IdentifierSet -> IdentifierSet
- data Identifier
- data IdentifierType
- unsafeMake :: HasCallStack => Text -> Identifier
- toText :: Identifier -> Text
- toLazyText :: Identifier -> Text
- toList :: IdentifierSet -> [Identifier]
- union :: HasCallStack => IdentifierSet -> IdentifierSet -> IdentifierSet
- make :: (HasCallStack, IdentifierSetMonad m) => Text -> m Identifier
- makeBasic :: (HasCallStack, IdentifierSetMonad m) => Text -> m Identifier
- makeBasicOr :: (HasCallStack, IdentifierSetMonad m) => Text -> Text -> m Identifier
- makeAs :: (HasCallStack, IdentifierSetMonad m) => IdentifierType -> Text -> m Identifier
- add :: HasCallStack => IdentifierSetMonad m => Identifier -> m ()
- addMultiple :: (HasCallStack, IdentifierSetMonad m, Foldable t) => t Identifier -> m ()
- addRaw :: (HasCallStack, IdentifierSetMonad m) => Text -> m Identifier
- deepen :: (HasCallStack, IdentifierSetMonad m) => Identifier -> m Identifier
- deepenN :: (HasCallStack, IdentifierSetMonad m) => Int -> Identifier -> m [Identifier]
- next :: (HasCallStack, IdentifierSetMonad m) => Identifier -> m Identifier
- nextN :: (HasCallStack, IdentifierSetMonad m) => Int -> Identifier -> m [Identifier]
- prefix :: (HasCallStack, IdentifierSetMonad m) => Identifier -> Text -> m Identifier
- suffix :: (HasCallStack, IdentifierSetMonad m) => Identifier -> Text -> m Identifier
- fromCoreId :: (HasCallStack, IdentifierSetMonad m) => Id -> m Identifier
- stripDollarPrefixes :: Text -> Text
- toBasicId# :: HDL -> PreserveCase -> Text -> Text
- isBasic# :: HDL -> Text -> Bool
- isExtended# :: HDL -> Text -> Bool
Utilities to use IdentifierSet
data IdentifierSet Source #
A collection of unique identifiers. Allows for fast fresh identifier generation.
NB: use the functions in Clash.Netlist.Id. Don't use the constructor directly.
Instances
class Monad m => IdentifierSetMonad m where Source #
An IdentifierSetMonad supports unique name generation for Clash Netlist
identifierSetM :: (IdentifierSet -> IdentifierSet) -> m IdentifierSet Source #
Instances
IdentifierSetMonad NetlistMonad Source # | |
Defined in Clash.Netlist.Types | |
HasIdentifierSet s => IdentifierSetMonad (State s) Source # | |
Defined in Clash.Netlist.Types identifierSetM :: (IdentifierSet -> IdentifierSet) -> State s IdentifierSet Source # | |
HasIdentifierSet s => IdentifierSetMonad (State s) Source # | |
Defined in Clash.Netlist.Types identifierSetM :: (IdentifierSet -> IdentifierSet) -> State s IdentifierSet Source # | |
IdentifierSetMonad m => IdentifierSetMonad (Ap m) Source # | |
Defined in Clash.Netlist.Types identifierSetM :: (IdentifierSet -> IdentifierSet) -> Ap m IdentifierSet Source # |
class HasIdentifierSet s where Source #
Structures that hold an IdentifierSet
Instances
HasIdentifierSet IdentifierSet Source # | |
Defined in Clash.Netlist.Types | |
HasIdentifierSet VerilogState Source # | |
Defined in Clash.Backend.Verilog | |
HasIdentifierSet VHDLState Source # | |
Defined in Clash.Backend.VHDL | |
HasIdentifierSet SystemVerilogState Source # | |
Backend backend => HasIdentifierSet (BlockState backend) Source # | |
Defined in Clash.Primitives.DSL identifierSet :: Lens' (BlockState backend) IdentifierSet Source # |
:: Bool | Allow escaped identifiers? |
-> PreserveCase | Should all basic identifiers be lower case? |
-> HDL | HDL to generate names for |
-> IdentifierSet |
Identifier set without identifiers
:: Bool | Allow escaped identifiers? |
-> PreserveCase | Should all basic identifiers be lower case? |
-> HDL | HDL to generate names for |
-> HashSet Identifier | Identifiers to add to set |
-> IdentifierSet |
Make a identifier set filled with given identifiers
clearSet :: IdentifierSet -> IdentifierSet Source #
Remove all identifiers from a set
Unsafe creation and extracting identifiers
data Identifier Source #
HDL identifier. Consists of a base name and a number of extensions. An identifier with a base name of "foo" and a list of extensions [1, 2] will be rendered as "foo_1_2".
Note: The Eq instance of Identifier is case insensitive! E.g., two
identifiers with base names fooBar
and FoObAR
are considered the same.
However, identifiers are stored case preserving. This means Clash won't
generate two identifiers with differing case, but it will try to keep
capitalization.
The goal of this data structure is to greatly simplify how Clash deals with identifiers internally. Any Identifier should be trivially printable to any HDL.
NB: use the functions in Clash.Netlist.Id. Don't use these constructors directly.
Instances
data IdentifierType Source #
Basic | A basic identifier: does not have to be escaped in order to be a valid identifier in HDL. |
Extended | An extended identifier: has to be escaped, wrapped, or otherwise postprocessed before writhing it to HDL. |
Instances
Eq IdentifierType Source # | |
Defined in Clash.Netlist.Types (==) :: IdentifierType -> IdentifierType -> Bool # (/=) :: IdentifierType -> IdentifierType -> Bool # | |
Show IdentifierType Source # | |
Defined in Clash.Netlist.Types showsPrec :: Int -> IdentifierType -> ShowS # show :: IdentifierType -> String # showList :: [IdentifierType] -> ShowS # | |
Generic IdentifierType Source # | |
Defined in Clash.Netlist.Types type Rep IdentifierType :: Type -> Type # from :: IdentifierType -> Rep IdentifierType x # to :: Rep IdentifierType x -> IdentifierType # | |
NFData IdentifierType Source # | |
Defined in Clash.Netlist.Types rnf :: IdentifierType -> () # | |
type Rep IdentifierType Source # | |
unsafeMake :: HasCallStack => Text -> Identifier Source #
Like addRaw
, unsafeMake
creates an identifier that will be spliced
at verbatim in the HDL. As opposed to addRaw
, the resulting Identifier
might be generated at a later point as it is NOT added to an IdentifierSet.
toText :: Identifier -> Text Source #
Convert an identifier to string. Use unmake
if you need the
IdentifierType too.
toLazyText :: Identifier -> Text Source #
Convert an identifier to string. Use unmake
if you need the
IdentifierType too.
toList :: IdentifierSet -> [Identifier] Source #
union :: HasCallStack => IdentifierSet -> IdentifierSet -> IdentifierSet Source #
Union of two identifier sets. Errors if given sets have been made with different options enabled.
Creating and extending identifiers
make :: (HasCallStack, IdentifierSetMonad m) => Text -> m Identifier Source #
Make unique identifier based on given string
makeBasic :: (HasCallStack, IdentifierSetMonad m) => Text -> m Identifier Source #
Make unique basic identifier based on given string
:: (HasCallStack, IdentifierSetMonad m) | |
=> Text | Name hint |
-> Text | If name hint can't be converted to a sensible basic id, use this instead |
-> m Identifier |
Make unique basic identifier based on given string. If given string can't be converted to a basic identifier (i.e., it would yield an empty string) the alternative name is used.
makeAs :: (HasCallStack, IdentifierSetMonad m) => IdentifierType -> Text -> m Identifier Source #
add :: HasCallStack => IdentifierSetMonad m => Identifier -> m () Source #
Add an identifier to an IdentifierSet
addMultiple :: (HasCallStack, IdentifierSetMonad m, Foldable t) => t Identifier -> m () Source #
Add identifiers to an IdentifierSet
addRaw :: (HasCallStack, IdentifierSetMonad m) => Text -> m Identifier Source #
Add a string as is to an IdentifierSet. Should only be used for identifiers that should be spliced at verbatim in HDL, such as port names. It's sanitized version will still be added to the identifier set, to prevent freshly generated variables clashing with the raw one.
deepen :: (HasCallStack, IdentifierSetMonad m) => Identifier -> m Identifier Source #
Given identifier "foo_1_2" return "foo_1_2_0". If "foo_1_2_0" is already a member of the given set, return "foo_1_2_1" instead, etc. Identifier returned is guaranteed to be unique.
deepenN :: (HasCallStack, IdentifierSetMonad m) => Int -> Identifier -> m [Identifier] Source #
Same as deepenM
, but returns N fresh identifiers. For example, given
"foo_23" is would return "foo_23_0", "foo_23_1", ...
next :: (HasCallStack, IdentifierSetMonad m) => Identifier -> m Identifier Source #
Given identifier "foo_1_2" return "foo_1_3". If "foo_1_3" is already a member of the given set, return "foo_1_4" instead, etc. Identifier returned is guaranteed to be unique.
nextN :: (HasCallStack, IdentifierSetMonad m) => Int -> Identifier -> m [Identifier] Source #
Same as nextM
, but returns N fresh identifiers
prefix :: (HasCallStack, IdentifierSetMonad m) => Identifier -> Text -> m Identifier Source #
Given identifier "foo_1_2" and a prefix "bar", return an identifier called
"bar_foo". Identifier returned is guaranteed to be unique according to the
rules of nextIdentifier
.
suffix :: (HasCallStack, IdentifierSetMonad m) => Identifier -> Text -> m Identifier Source #
Given identifier "foo_1_2" and a suffix "bar", return an identifier called
"foo_bar". Identifier returned is guaranteed to be unique according to the
rules of nextIdentifier
.
fromCoreId :: (HasCallStack, IdentifierSetMonad m) => Id -> m Identifier Source #
Convert a Clash Core Id to an identifier. Makes sure returned identifier is unique.
Misc. and internals
stripDollarPrefixes :: Text -> Text Source #
toBasicId# :: HDL -> PreserveCase -> Text -> Text Source #
isExtended# :: HDL -> Text -> Bool Source #
Is given string a valid extended identifier in given HDL?