clash-prelude
Copyright(C) 2018 Google Inc.
2022 LUMI GUIDE FIETSDETECTIE B.V.
LicenseBSD2 (see the file LICENSE)
MaintainerChristiaan Baaij <christiaan.baaij@gmail.com>
Safe HaskellSafe-Inferred
LanguageHaskell2010

Clash.Annotations.BitRepresentation.Internal

Description

 
Synopsis

Documentation

buildCustomReprs :: [DataRepr'] -> CustomReprs Source #

Create indices based on names of constructors and data types

getConstrRepr :: Text -> CustomReprs -> Maybe ConstrRepr' Source #

Lookup constructor representation based on name

uncheckedGetConstrRepr :: HasCallStack => Text -> CustomReprs -> ConstrRepr' Source #

Unchecked version of getConstrRepr

getDataRepr :: Type' -> CustomReprs -> Maybe DataRepr' Source #

Lookup data type representation based on name

thTypeToType' :: Type -> Type' Source #

Convert template haskell type to simple representation of type

data ConstrRepr' Source #

Internal version of ConstrRepr

Constructors

ConstrRepr' 

Fields

Instances

Instances details
Generic ConstrRepr' Source # 
Instance details

Defined in Clash.Annotations.BitRepresentation.Internal

Associated Types

type Rep ConstrRepr' :: Type -> Type #

Show ConstrRepr' Source # 
Instance details

Defined in Clash.Annotations.BitRepresentation.Internal

NFData ConstrRepr' Source # 
Instance details

Defined in Clash.Annotations.BitRepresentation.Internal

Methods

rnf :: ConstrRepr' -> () #

Eq ConstrRepr' Source # 
Instance details

Defined in Clash.Annotations.BitRepresentation.Internal

Ord ConstrRepr' Source # 
Instance details

Defined in Clash.Annotations.BitRepresentation.Internal

Hashable ConstrRepr' Source # 
Instance details

Defined in Clash.Annotations.BitRepresentation.Internal

type Rep ConstrRepr' Source # 
Instance details

Defined in Clash.Annotations.BitRepresentation.Internal

type Rep ConstrRepr' = D1 ('MetaData "ConstrRepr'" "Clash.Annotations.BitRepresentation.Internal" "clash-prelude-1.9.0-inplace" 'False) (C1 ('MetaCons "ConstrRepr'" 'PrefixI 'True) ((S1 ('MetaSel ('Just "crName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "crPosition") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "crMask") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BitMask) :*: (S1 ('MetaSel ('Just "crValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Value) :*: S1 ('MetaSel ('Just "crFieldAnns") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FieldAnn])))))

data DataRepr' Source #

Internal version of DataRepr

Constructors

DataRepr' 

Fields

Instances

Instances details
Generic DataRepr' Source # 
Instance details

Defined in Clash.Annotations.BitRepresentation.Internal

Associated Types

type Rep DataRepr' :: Type -> Type #

Show DataRepr' Source # 
Instance details

Defined in Clash.Annotations.BitRepresentation.Internal

NFData DataRepr' Source # 
Instance details

Defined in Clash.Annotations.BitRepresentation.Internal

Methods

rnf :: DataRepr' -> () #

Eq DataRepr' Source # 
Instance details

Defined in Clash.Annotations.BitRepresentation.Internal

Ord DataRepr' Source # 
Instance details

Defined in Clash.Annotations.BitRepresentation.Internal

Hashable DataRepr' Source # 
Instance details

Defined in Clash.Annotations.BitRepresentation.Internal

type Rep DataRepr' Source # 
Instance details

Defined in Clash.Annotations.BitRepresentation.Internal

type Rep DataRepr' = D1 ('MetaData "DataRepr'" "Clash.Annotations.BitRepresentation.Internal" "clash-prelude-1.9.0-inplace" 'False) (C1 ('MetaCons "DataRepr'" 'PrefixI 'True) (S1 ('MetaSel ('Just "drType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type') :*: (S1 ('MetaSel ('Just "drSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Size) :*: S1 ('MetaSel ('Just "drConstrs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ConstrRepr']))))

data Type' Source #

Simple version of template haskell type. Used internally to match on.

Constructors

AppTy' Type' Type'

Type application

ConstTy' Text

Qualified name of type

LitTy' Integer

Numeral literal (used in BitVector 10, for example)

SymLitTy' Text

Symbol literal (used in for example (Signal System Int))

Instances

Instances details
Generic Type' Source # 
Instance details

Defined in Clash.Annotations.BitRepresentation.Internal

Associated Types

type Rep Type' :: Type -> Type #

Methods

from :: Type' -> Rep Type' x #

to :: Rep Type' x -> Type' #

Show Type' Source # 
Instance details

Defined in Clash.Annotations.BitRepresentation.Internal

Methods

showsPrec :: Int -> Type' -> ShowS #

show :: Type' -> String #

showList :: [Type'] -> ShowS #

NFData Type' Source # 
Instance details

Defined in Clash.Annotations.BitRepresentation.Internal

Methods

rnf :: Type' -> () #

Eq Type' Source # 
Instance details

Defined in Clash.Annotations.BitRepresentation.Internal

Methods

(==) :: Type' -> Type' -> Bool #

(/=) :: Type' -> Type' -> Bool #

Ord Type' Source # 
Instance details

Defined in Clash.Annotations.BitRepresentation.Internal

Methods

compare :: Type' -> Type' -> Ordering #

(<) :: Type' -> Type' -> Bool #

(<=) :: Type' -> Type' -> Bool #

(>) :: Type' -> Type' -> Bool #

(>=) :: Type' -> Type' -> Bool #

max :: Type' -> Type' -> Type' #

min :: Type' -> Type' -> Type' #

Hashable Type' Source # 
Instance details

Defined in Clash.Annotations.BitRepresentation.Internal

Methods

hashWithSalt :: Int -> Type' -> Int #

hash :: Type' -> Int #

type Rep Type' Source # 
Instance details

Defined in Clash.Annotations.BitRepresentation.Internal

type CustomReprs = (Map Type' DataRepr', Map Text ConstrRepr') Source #

Convenience type for index built by buildCustomReprs