clingo-0.2.0.0: Haskell bindings to the Clingo ASP solver

Safe HaskellNone
LanguageHaskell2010

Clingo.Inspection.Theory

Documentation

data AspifLiteral s Source #

Instances

Eq (AspifLiteral s) Source # 
Ord (AspifLiteral s) Source # 
Show (AspifLiteral s) Source # 
Generic (AspifLiteral s) Source # 

Associated Types

type Rep (AspifLiteral s) :: * -> * #

Methods

from :: AspifLiteral s -> Rep (AspifLiteral s) x #

to :: Rep (AspifLiteral s) x -> AspifLiteral s #

NFData (AspifLiteral s) Source # 

Methods

rnf :: AspifLiteral s -> () #

Hashable (AspifLiteral s) Source # 
Signed (AspifLiteral s) Source # 
type Rep (AspifLiteral s) Source # 
type Rep (AspifLiteral s) = D1 (MetaData "AspifLiteral" "Clingo.Internal.Types" "clingo-0.2.0.0-DzJnCg9nABaE1yAGw8EIsO" True) (C1 (MetaCons "AspifLiteral" PrefixI True) (S1 (MetaSel (Just Symbol "rawAspifLiteral") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Literal)))

data Guard s Source #

Constructors

Guard Text (GroundTheoryTerm s) 

Instances

Generic (Guard s) Source # 

Associated Types

type Rep (Guard s) :: * -> * #

Methods

from :: Guard s -> Rep (Guard s) x #

to :: Rep (Guard s) x -> Guard s #

NFData (Guard s) Source # 

Methods

rnf :: Guard s -> () #

type Rep (Guard s) Source # 
type Rep (Guard s) = D1 (MetaData "Guard" "Clingo.Inspection.Theory" "clingo-0.2.0.0-DzJnCg9nABaE1yAGw8EIsO" False) (C1 (MetaCons "Guard" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (GroundTheoryTerm s)))))

data Element s Source #

Instances

Generic (Element s) Source # 

Associated Types

type Rep (Element s) :: * -> * #

Methods

from :: Element s -> Rep (Element s) x #

to :: Rep (Element s) x -> Element s #

NFData (Element s) Source # 

Methods

rnf :: Element s -> () #

type Rep (Element s) Source # 
type Rep (Element s) = D1 (MetaData "Element" "Clingo.Inspection.Theory" "clingo-0.2.0.0-DzJnCg9nABaE1yAGw8EIsO" False) (C1 (MetaCons "Element" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "elementTuple") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [GroundTheoryTerm s])) (S1 (MetaSel (Just Symbol "elementCondition") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [AspifLiteral s]))) ((:*:) (S1 (MetaSel (Just Symbol "elementConditionId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AspifLiteral s))) (S1 (MetaSel (Just Symbol "renderElement") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))))

data GroundTheoryTerm s Source #

Instances

Generic (GroundTheoryTerm s) Source # 

Associated Types

type Rep (GroundTheoryTerm s) :: * -> * #

NFData (GroundTheoryTerm s) Source # 

Methods

rnf :: GroundTheoryTerm s -> () #

type Rep (GroundTheoryTerm s) Source # 
type Rep (GroundTheoryTerm s) = D1 (MetaData "GroundTheoryTerm" "Clingo.Inspection.Theory" "clingo-0.2.0.0-DzJnCg9nABaE1yAGw8EIsO" False) ((:+:) ((:+:) (C1 (MetaCons "SymbolTerm" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))) ((:+:) (C1 (MetaCons "FunctionTerm" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [GroundTheoryTerm s]))))) (C1 (MetaCons "NumberTerm" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer)))))) ((:+:) (C1 (MetaCons "TupleTerm" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Element s])))) ((:+:) (C1 (MetaCons "ListTerm" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Element s])))) (C1 (MetaCons "SetTerm" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Element s])))))))