clash-lib-1.2.5: CAES Language for Synchronous Hardware - As a Library
Copyright(C) 2012-2016 University of Twente
2017-2018 Google Inc.
LicenseBSD2 (see the file LICENSE)
MaintainerChristiaan Baaij <christiaan.baaij@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Clash.Core.Var

Description

Variables in CoreHW

Synopsis

Documentation

data Attr' Source #

Interal version of Clash.Annotations.SynthesisAttributes.Attr.

Needed because Clash.Annotations.SynthesisAttributes.Attr uses the Symbol kind for names, which do not have a term-level representation

Instances

Instances details
Eq Attr' Source # 
Instance details

Defined in Clash.Core.Var

Methods

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

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

Ord Attr' Source # 
Instance details

Defined in Clash.Core.Var

Methods

compare :: Attr' -> Attr' -> Ordering #

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

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

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

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

max :: Attr' -> Attr' -> Attr' #

min :: Attr' -> Attr' -> Attr' #

Show Attr' Source # 
Instance details

Defined in Clash.Core.Var

Methods

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

show :: Attr' -> String #

showList :: [Attr'] -> ShowS #

Generic Attr' Source # 
Instance details

Defined in Clash.Core.Var

Associated Types

type Rep Attr' :: Type -> Type #

Methods

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

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

Hashable Attr' Source # 
Instance details

Defined in Clash.Core.Var

Methods

hashWithSalt :: Int -> Attr' -> Int #

hash :: Attr' -> Int #

Binary Attr' Source # 
Instance details

Defined in Clash.Core.Var

Methods

put :: Attr' -> Put #

get :: Get Attr' #

putList :: [Attr'] -> Put #

NFData Attr' Source # 
Instance details

Defined in Clash.Core.Var

Methods

rnf :: Attr' -> () #

type Rep Attr' Source # 
Instance details

Defined in Clash.Core.Var

data Var a Source #

Variables in CoreHW

Constructors

TyVar

Constructor for type variables

Fields

Id

Constructor for term variables

Fields

Instances

Instances details
Eq (Var a) Source # 
Instance details

Defined in Clash.Core.Var

Methods

(==) :: Var a -> Var a -> Bool #

(/=) :: Var a -> Var a -> Bool #

Ord (Var a) Source # 
Instance details

Defined in Clash.Core.Var

Methods

compare :: Var a -> Var a -> Ordering #

(<) :: Var a -> Var a -> Bool #

(<=) :: Var a -> Var a -> Bool #

(>) :: Var a -> Var a -> Bool #

(>=) :: Var a -> Var a -> Bool #

max :: Var a -> Var a -> Var a #

min :: Var a -> Var a -> Var a #

Show (Var a) Source # 
Instance details

Defined in Clash.Core.Var

Methods

showsPrec :: Int -> Var a -> ShowS #

show :: Var a -> String #

showList :: [Var a] -> ShowS #

Generic (Var a) Source # 
Instance details

Defined in Clash.Core.Var

Associated Types

type Rep (Var a) :: Type -> Type #

Methods

from :: Var a -> Rep (Var a) x #

to :: Rep (Var a) x -> Var a #

Hashable (Var a) Source # 
Instance details

Defined in Clash.Core.Var

Methods

hashWithSalt :: Int -> Var a -> Int #

hash :: Var a -> Int #

Binary (Var a) Source # 
Instance details

Defined in Clash.Core.Var

Methods

put :: Var a -> Put #

get :: Get (Var a) #

putList :: [Var a] -> Put #

NFData (Var a) Source # 
Instance details

Defined in Clash.Core.Var

Methods

rnf :: Var a -> () #

ClashPretty (Var a) Source # 
Instance details

Defined in Clash.Core.Pretty

Methods

clashPretty :: Var a -> Doc () Source #

Uniquable (Var a) Source # 
Instance details

Defined in Clash.Core.Var

Methods

getUnique :: Var a -> Unique Source #

setUnique :: Var a -> Unique -> Var a Source #

PrettyPrec (Var a) Source # 
Instance details

Defined in Clash.Core.Pretty

PrettyPrec (Id, Term) Source # 
Instance details

Defined in Clash.Core.Pretty

type Rep (Var a) Source # 
Instance details

Defined in Clash.Core.Var

data IdScope Source #

Constructors

GlobalId 
LocalId 

Instances

Instances details
Eq IdScope Source # 
Instance details

Defined in Clash.Core.Var

Methods

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

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

Ord IdScope Source # 
Instance details

Defined in Clash.Core.Var

Show IdScope Source # 
Instance details

Defined in Clash.Core.Var

Generic IdScope Source # 
Instance details

Defined in Clash.Core.Var

Associated Types

type Rep IdScope :: Type -> Type #

Methods

from :: IdScope -> Rep IdScope x #

to :: Rep IdScope x -> IdScope #

Hashable IdScope Source # 
Instance details

Defined in Clash.Core.Var

Methods

hashWithSalt :: Int -> IdScope -> Int #

hash :: IdScope -> Int #

Binary IdScope Source # 
Instance details

Defined in Clash.Core.Var

Methods

put :: IdScope -> Put #

get :: Get IdScope #

putList :: [IdScope] -> Put #

NFData IdScope Source # 
Instance details

Defined in Clash.Core.Var

Methods

rnf :: IdScope -> () #

type Rep IdScope Source # 
Instance details

Defined in Clash.Core.Var

type Rep IdScope = D1 ('MetaData "IdScope" "Clash.Core.Var" "clash-lib-1.2.5-inplace" 'False) (C1 ('MetaCons "GlobalId" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LocalId" 'PrefixI 'False) (U1 :: Type -> Type))

type Id = Var Term Source #

Term variable

type TyVar = Var Type Source #

Type variable

mkId :: Type -> IdScope -> TmName -> Id Source #

Make a term variable

mkTyVar :: Kind -> TyName -> TyVar Source #

Make a type variable

setVarType :: Var a -> Type -> Var a Source #

modifyVarName :: (Name a -> Name a) -> Var a -> Var a Source #

Change the name of a variable