grisette-0.11.0.0: Symbolic evaluation as a library
Copyright(c) Sirui Lu 2024
LicenseBSD-3-Clause (see the LICENSE file)
Maintainersiruilu@cs.washington.edu
StabilityExperimental
PortabilityGHC only
Safe HaskellSafe-Inferred
LanguageHaskell2010

Grisette.Internal.Core.Data.Symbol

Description

 
Synopsis

Documentation

data Identifier Source #

Identifier type used for GenSym

The constructor is hidden intentionally. You can construct an identifier by:

  • a raw identifier

The following two expressions will refer to the same identifier (the solver won't distinguish them and would assign the same value to them). The user may need to use unique names to avoid unintentional identifier collision.

>>> identifier "a"
a
>>> "a" :: Identifier -- available when OverloadedStrings is enabled
a
  • bundle the identifier with some user provided metadata

Identifiers created with different name or different additional information will not be the same.

>>> withMetadata "a" (NumberAtom 1)
a:1
  • bundle the calling file location with the identifier to ensure global uniqueness

Identifiers created at different locations will not be the same. The identifiers created at the same location will be the same.

>>> $$(withLocation "a") -- a sample result could be "a:[grisette-file-location <interactive> 18 (4 18)]"
a:[grisette-file-location <interactive>...]

Constructors

Identifier 

Fields

Instances

Instances details
IsString Identifier Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Symbol

Generic Identifier Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Symbol

Associated Types

type Rep Identifier :: Type -> Type #

Show Identifier Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Symbol

Binary Identifier Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Symbol

Serial Identifier Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Symbol

Methods

serialize :: MonadPut m => Identifier -> m () #

deserialize :: MonadGet m => m Identifier #

Serialize Identifier Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Symbol

NFData Identifier Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Symbol

Methods

rnf :: Identifier -> () #

Eq Identifier Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Symbol

Ord Identifier Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Symbol

PPrint Identifier Source # 
Instance details

Defined in Grisette.Internal.Internal.Impl.Core.Data.Class.PPrint

Hashable Identifier Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Symbol

Lift Identifier Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Symbol

Methods

lift :: Quote m => Identifier -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Identifier -> Code m Identifier #

type Rep Identifier Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Symbol

type Rep Identifier = D1 ('MetaData "Identifier" "Grisette.Internal.Core.Data.Symbol" "grisette-0.11.0.0-En6Ko5xIwnQLAUQ39GJ2kN" 'False) (C1 ('MetaCons "Identifier" 'PrefixI 'True) (S1 ('MetaSel ('Just "baseIdent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "metadata") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SExpr)))

identifier :: Text -> Identifier Source #

Simple identifier. The same identifier refers to the same symbolic variable in the whole program.

The user may need to use unique identifiers to avoid unintentional identifier collision.

withMetadata :: Text -> SExpr -> Identifier Source #

Identifier with extra metadata.

The same identifier with the same metadata refers to the same symbolic variable in the whole program.

The user may need to use unique identifiers or additional metadata to avoid unintentional identifier collision.

withLocation :: Text -> SpliceQ Identifier Source #

Identifier with the file location.

mapMetadata :: (SExpr -> SExpr) -> Identifier -> Identifier Source #

Modify the metadata of an identifier.

uniqueIdentifier :: Text -> IO Identifier Source #

Get a globally unique identifier within the IO monad.

data Symbol where Source #

Symbol types for a symbolic variable.

The symbols can be indexed with an integer.

Instances

Instances details
IsString Symbol Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Symbol

Methods

fromString :: String -> Symbol #

Generic Symbol Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Symbol

Associated Types

type Rep Symbol :: Type -> Type #

Methods

from :: Symbol -> Rep Symbol x #

to :: Rep Symbol x -> Symbol #

Show Symbol Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Symbol

Binary Symbol Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Symbol

Methods

put :: Symbol -> Put #

get :: Get Symbol #

putList :: [Symbol] -> Put #

Serial Symbol Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Symbol

Methods

serialize :: MonadPut m => Symbol -> m () #

deserialize :: MonadGet m => m Symbol #

Serialize Symbol Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Symbol

NFData Symbol Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Symbol

Methods

rnf :: Symbol -> () #

Eq Symbol Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Symbol

Methods

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

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

Ord Symbol Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Symbol

PPrint Symbol Source # 
Instance details

Defined in Grisette.Internal.Internal.Impl.Core.Data.Class.PPrint

Methods

pformat :: Symbol -> Doc ann Source #

pformatPrec :: Int -> Symbol -> Doc ann Source #

pformatList :: [Symbol] -> Doc ann Source #

Hashable Symbol Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Symbol

Methods

hashWithSalt :: Int -> Symbol -> Int #

hash :: Symbol -> Int #

Lift Symbol Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Symbol

Methods

lift :: Quote m => Symbol -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Symbol -> Code m Symbol #

type Rep Symbol Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Symbol

type Rep Symbol = D1 ('MetaData "Symbol" "Grisette.Internal.Core.Data.Symbol" "grisette-0.11.0.0-En6Ko5xIwnQLAUQ39GJ2kN" 'False) (C1 ('MetaCons "SimpleSymbol" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Identifier)) :+: C1 ('MetaCons "IndexedSymbol" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Identifier) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

simple :: Identifier -> Symbol Source #

Create a simple symbol.

indexed :: Identifier -> Int -> Symbol Source #

Create an indexed symbol.

symbolIdentifier :: Symbol -> Identifier Source #

Get the identifier of a symbol.

mapIdentifier :: (Identifier -> Identifier) -> Symbol -> Symbol Source #

Modify the identifier of a symbol.