clash-lib-1.4.3: Clash: a functional hardware description language - As a library
Copyright(C) 2020 QBayLogic B.V.
LicenseBSD2 (see the file LICENSE)
MaintainerQBayLogic B.V. <devops@qbaylogic.com>
Safe HaskellNone
LanguageHaskell2010

Clash.Netlist.Id

Description

Transform/format a Netlist Identifier so that it is acceptable as a HDL identifier

Synopsis

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

Instances details
Show IdentifierSet Source # 
Instance details

Defined in Clash.Netlist.Types

Generic IdentifierSet Source # 
Instance details

Defined in Clash.Netlist.Types

Associated Types

type Rep IdentifierSet :: Type -> Type #

NFData IdentifierSet Source # 
Instance details

Defined in Clash.Netlist.Types

Methods

rnf :: IdentifierSet -> () #

HasIdentifierSet IdentifierSet Source # 
Instance details

Defined in Clash.Netlist.Types

type Rep IdentifierSet Source # 
Instance details

Defined in Clash.Netlist.Types

type Rep IdentifierSet = D1 ('MetaData "IdentifierSet" "Clash.Netlist.Types" "clash-lib-1.4.3-inplace" 'False) (C1 ('MetaCons "IdentifierSet" 'PrefixI 'True) ((S1 ('MetaSel ('Just "is_allowEscaped") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "is_lowerCaseBasicIds") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PreserveCase)) :*: (S1 ('MetaSel ('Just "is_hdl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HDL) :*: (S1 ('MetaSel ('Just "is_freshCache") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 FreshCache) :*: S1 ('MetaSel ('Just "is_store") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HashSet Identifier))))))

emptyIdentifierSet Source #

Arguments

:: Bool

Allow escaped identifiers?

-> PreserveCase

Should all basic identifiers be lower case?

-> HDL

HDL to generate names for

-> IdentifierSet 

Identifier set without identifiers

makeSet Source #

Arguments

:: 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

Instances details
Eq Identifier Source # 
Instance details

Defined in Clash.Netlist.Types

Ord Identifier Source # 
Instance details

Defined in Clash.Netlist.Types

Show Identifier Source # 
Instance details

Defined in Clash.Netlist.Types

Generic Identifier Source # 
Instance details

Defined in Clash.Netlist.Types

Associated Types

type Rep Identifier :: Type -> Type #

Hashable Identifier Source # 
Instance details

Defined in Clash.Netlist.Types

NFData Identifier Source # 
Instance details

Defined in Clash.Netlist.Types

Methods

rnf :: Identifier -> () #

Pretty Identifier Source # 
Instance details

Defined in Clash.Netlist.Id.Internal

Methods

pretty :: Identifier -> Doc ann #

prettyList :: [Identifier] -> Doc ann #

type Rep Identifier Source # 
Instance details

Defined in Clash.Netlist.Types

data IdentifierType Source #

Constructors

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

Instances details
Eq IdentifierType Source # 
Instance details

Defined in Clash.Netlist.Types

Show IdentifierType Source # 
Instance details

Defined in Clash.Netlist.Types

Generic IdentifierType Source # 
Instance details

Defined in Clash.Netlist.Types

Associated Types

type Rep IdentifierType :: Type -> Type #

NFData IdentifierType Source # 
Instance details

Defined in Clash.Netlist.Types

Methods

rnf :: IdentifierType -> () #

type Rep IdentifierType Source # 
Instance details

Defined in Clash.Netlist.Types

type Rep IdentifierType = D1 ('MetaData "IdentifierType" "Clash.Netlist.Types" "clash-lib-1.4.3-inplace" 'False) (C1 ('MetaCons "Basic" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Extended" 'PrefixI 'False) (U1 :: Type -> Type))

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.

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

makeBasicOr Source #

Arguments

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

Make unique identifier. Uses makeBasic if first argument is Basic

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

isBasic# :: HDL -> Text -> Bool Source #

Is given string a valid basic identifier in given HDL?

isExtended# :: HDL -> Text -> Bool Source #

Is given string a valid extended identifier in given HDL?