clash-lib-0.99: CAES Language for Synchronous Hardware - As a Library

Copyright(C) 2012-2016 University of Twente
2016 Myrtle Software Ltd
2017 Google Inc.
LicenseBSD2 (see the file LICENSE)
MaintainerChristiaan Baaij <christiaan.baaij@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Clash.Core.Literal

Description

Term Literal

Synopsis

Documentation

data Literal Source #

Term Literal

Instances

Eq Literal Source # 

Methods

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

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

Ord Literal Source # 
Show Literal Source # 
Generic Literal Source # 

Associated Types

type Rep Literal :: * -> * #

Methods

from :: Literal -> Rep Literal x #

to :: Rep Literal x -> Literal #

Hashable Literal Source # 

Methods

hashWithSalt :: Int -> Literal -> Int #

hash :: Literal -> Int #

NFData Literal Source # 

Methods

rnf :: Literal -> () #

Alpha Literal Source # 
Pretty Literal Source # 

Methods

ppr :: LFresh m => Literal -> m Doc Source #

pprPrec :: LFresh m => Rational -> Literal -> m Doc Source #

Subst a Literal Source # 
type Rep Literal Source # 
type Rep Literal = D1 * (MetaData "Literal" "Clash.Core.Literal" "clash-lib-0.99-CApG5XjEMCZFUVyS8kIjXv" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "IntegerLiteral" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Integer))) (C1 * (MetaCons "IntLiteral" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Integer)))) ((:+:) * (C1 * (MetaCons "WordLiteral" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Integer))) ((:+:) * (C1 * (MetaCons "Int64Literal" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Integer))) (C1 * (MetaCons "Word64Literal" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Integer)))))) ((:+:) * ((:+:) * (C1 * (MetaCons "StringLiteral" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * String))) (C1 * (MetaCons "FloatLiteral" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Rational)))) ((:+:) * (C1 * (MetaCons "DoubleLiteral" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Rational))) ((:+:) * (C1 * (MetaCons "CharLiteral" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Char))) (C1 * (MetaCons "NaturalLiteral" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Integer)))))))

literalType :: Literal -> Type Source #

Determines the Type of a Literal