clash-lib-1.7.0: Clash: a functional hardware description language - As a library
Copyright(C) 2019 Myrtle Software Ltd
2021 QBayLogic B.V.
2022 Google Inc.
LicenseBSD2 (see the file LICENSE)
MaintainerQBayLogic B.V. <devops@qbaylogic.com>
Safe HaskellNone
LanguageHaskell2010

Clash.Core.TermLiteral

Description

Tools to convert a Term into its "real" representation

Synopsis

Documentation

class TermLiteral a Source #

Tools to deal with literals encoded as a Term.

Minimal complete definition

termToData

Instances

Instances details
TermLiteral Bool Source # 
Instance details

Defined in Clash.Core.TermLiteral

TermLiteral Char Source # 
Instance details

Defined in Clash.Core.TermLiteral

TermLiteral Int Source # 
Instance details

Defined in Clash.Core.TermLiteral

TermLiteral Integer Source # 
Instance details

Defined in Clash.Core.TermLiteral

TermLiteral Natural Source # 
Instance details

Defined in Clash.Core.TermLiteral

TermLiteral Word Source # 
Instance details

Defined in Clash.Core.TermLiteral

TermLiteral String Source # 
Instance details

Defined in Clash.Core.TermLiteral

TermLiteral Text Source # 
Instance details

Defined in Clash.Core.TermLiteral

TermLiteral Term Source # 
Instance details

Defined in Clash.Core.TermLiteral

TermLiteral RenderAs Source # 
Instance details

Defined in Clash.Core.TermLiteral

Methods

termToData :: Term -> Either Term RenderAs Source #

showsTypePrec :: Int -> Proxy RenderAs -> ShowS Source #

TermLiteral a => TermLiteral (Maybe a) Source # 
Instance details

Defined in Clash.Core.TermLiteral

KnownNat n => TermLiteral (Index n) Source # 
Instance details

Defined in Clash.Core.TermLiteral

Methods

termToData :: Term -> Either Term (Index n) Source #

showsTypePrec :: Int -> Proxy (Index n) -> ShowS Source #

TermLiteral (SNat n) Source #

Unsafe warning: If you use this instance in a monomorphic context (e.g., TermLiteral (SNat 5)), you need to make very sure that the term corresponds to the literal. If you don't, there will be a mismatch between type level variables and the proof carried in SNats KnownNat. Typical usage of this instance will therefore leave the n polymorphic.

Instance details

Defined in Clash.Core.TermLiteral

Methods

termToData :: Term -> Either Term (SNat n) Source #

showsTypePrec :: Int -> Proxy (SNat n) -> ShowS Source #

TermLiteral a => TermLiteral (Attr a) Source # 
Instance details

Defined in Clash.Core.TermLiteral

Methods

termToData :: Term -> Either Term (Attr a) Source #

showsTypePrec :: Int -> Proxy (Attr a) -> ShowS Source #

TermLiteral a => TermLiteral (Assertion' a) Source # 
Instance details

Defined in Clash.Core.TermLiteral

Methods

termToData :: Term -> Either Term (Assertion' a) Source #

showsTypePrec :: Int -> Proxy (Assertion' a) -> ShowS Source #

TermLiteral a => TermLiteral (Property' a) Source # 
Instance details

Defined in Clash.Core.TermLiteral

Methods

termToData :: Term -> Either Term (Property' a) Source #

showsTypePrec :: Int -> Proxy (Property' a) -> ShowS Source #

(TermLiteral a, TermLiteral b) => TermLiteral (Either a b) Source # 
Instance details

Defined in Clash.Core.TermLiteral

(TermLiteral a, TermLiteral b) => TermLiteral (a, b) Source # 
Instance details

Defined in Clash.Core.TermLiteral

Methods

termToData :: Term -> Either Term (a, b) Source #

showsTypePrec :: Int -> Proxy (a, b) -> ShowS Source #

(TermLiteral a, KnownNat n) => TermLiteral (Vec n a) Source # 
Instance details

Defined in Clash.Core.TermLiteral

Methods

termToData :: Term -> Either Term (Vec n a) Source #

showsTypePrec :: Int -> Proxy (Vec n a) -> ShowS Source #

showsTypePrec Source #

Arguments

:: TermLiteral a 
=> Int

The operator precedence of the enclosing context (a number from 0 to 11). Function application has precedence 10. Used to determine whether the result should be wrapped in parentheses.

-> Proxy a

Proxy for a term whose type needs to be pretty printed

-> ShowS 

Pretty print the type of a term (for error messages). Its default implementation uses Typeable to print the type. Note that this method is there to allow an instance for SNat to exist (and other GADTs imposing KnownNat). Without it, GHC would ask for a KnownNat constraint on the instance, which would defeat the purpose of it.

showType :: TermLiteral a => Proxy a -> String Source #

Pretty print type a

termToData Source #

Arguments

:: (TermLiteral a, HasCallStack) 
=> Term

Term to convert

-> Either Term a

Left indicates a failure, containing the (sub)term that failed to translate. Right indicates a success.

Convert Term to the constant it represents. Will return an error if (one of the subterms) fail to translate.

termToDataError :: forall a. TermLiteral a => Term -> Either String a Source #

Same as termToData, but returns printable error message if it couldn't translate a term.

deriveTermLiteral :: Name -> Q [Dec] Source #

Derive a TermLiteral instance for given type