rest-rewrite-0.4.3: Rewriting library with online termination checking
Safe HaskellSafe-Inferred
LanguageHaskell2010

Language.REST.Path

Synopsis

Documentation

data Step rule term a Source #

Step represents an intermediate step in a Path explored by REST

Constructors

Step 

Fields

  • term :: PathTerm rule term

    The "from" term in this path

  • rule :: rule

    The rule generating the next term

  • ordering :: a

    The generated constraints from applying the rule

  • fromPLE :: Bool

    Whether the term was derived from a provably terminating eval function

Instances

Instances details
Generic (Step rule term a) Source # 
Instance details

Defined in Language.REST.Path

Associated Types

type Rep (Step rule term a) :: Type -> Type #

Methods

from :: Step rule term a -> Rep (Step rule term a) x #

to :: Rep (Step rule term a) x -> Step rule term a #

(Eq term, Eq rule, Eq a) => Eq (Step rule term a) Source # 
Instance details

Defined in Language.REST.Path

Methods

(==) :: Step rule term a -> Step rule term a -> Bool #

(/=) :: Step rule term a -> Step rule term a -> Bool #

(Ord term, Ord rule, Ord a) => Ord (Step rule term a) Source # 
Instance details

Defined in Language.REST.Path

Methods

compare :: Step rule term a -> Step rule term a -> Ordering #

(<) :: Step rule term a -> Step rule term a -> Bool #

(<=) :: Step rule term a -> Step rule term a -> Bool #

(>) :: Step rule term a -> Step rule term a -> Bool #

(>=) :: Step rule term a -> Step rule term a -> Bool #

max :: Step rule term a -> Step rule term a -> Step rule term a #

min :: Step rule term a -> Step rule term a -> Step rule term a #

(Hashable term, Hashable rule, Hashable a) => Hashable (Step rule term a) Source # 
Instance details

Defined in Language.REST.Path

Methods

hashWithSalt :: Int -> Step rule term a -> Int #

hash :: Step rule term a -> Int #

type Rep (Step rule term a) Source # 
Instance details

Defined in Language.REST.Path

type Rep (Step rule term a) = D1 ('MetaData "Step" "Language.REST.Path" "rest-rewrite-0.4.3-L4CHsmDzf4PMYNf7CqgfF" 'False) (C1 ('MetaCons "Step" 'PrefixI 'True) ((S1 ('MetaSel ('Just "term") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PathTerm rule term)) :*: S1 ('MetaSel ('Just "rule") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 rule)) :*: (S1 ('MetaSel ('Just "ordering") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "fromPLE") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))))

data PathTerm rule term Source #

PathTerm is the term explored at a path

Constructors

PathTerm 

Fields

  • pathTerm :: term
     
  • rejected :: HashSet (term, rule)

    The orderings FROM pathTerm that were rejected. TODO: This should be removed, as it's really only used in the visualization

Instances

Instances details
Generic (PathTerm rule term) Source # 
Instance details

Defined in Language.REST.Path

Associated Types

type Rep (PathTerm rule term) :: Type -> Type #

Methods

from :: PathTerm rule term -> Rep (PathTerm rule term) x #

to :: Rep (PathTerm rule term) x -> PathTerm rule term #

(Eq term, Eq rule) => Eq (PathTerm rule term) Source # 
Instance details

Defined in Language.REST.Path

Methods

(==) :: PathTerm rule term -> PathTerm rule term -> Bool #

(/=) :: PathTerm rule term -> PathTerm rule term -> Bool #

(Ord term, Ord rule) => Ord (PathTerm rule term) Source # 
Instance details

Defined in Language.REST.Path

Methods

compare :: PathTerm rule term -> PathTerm rule term -> Ordering #

(<) :: PathTerm rule term -> PathTerm rule term -> Bool #

(<=) :: PathTerm rule term -> PathTerm rule term -> Bool #

(>) :: PathTerm rule term -> PathTerm rule term -> Bool #

(>=) :: PathTerm rule term -> PathTerm rule term -> Bool #

max :: PathTerm rule term -> PathTerm rule term -> PathTerm rule term #

min :: PathTerm rule term -> PathTerm rule term -> PathTerm rule term #

(Hashable term, Hashable rule) => Hashable (PathTerm rule term) Source # 
Instance details

Defined in Language.REST.Path

Methods

hashWithSalt :: Int -> PathTerm rule term -> Int #

hash :: PathTerm rule term -> Int #

type Rep (PathTerm rule term) Source # 
Instance details

Defined in Language.REST.Path

type Rep (PathTerm rule term) = D1 ('MetaData "PathTerm" "Language.REST.Path" "rest-rewrite-0.4.3-L4CHsmDzf4PMYNf7CqgfF" 'False) (C1 ('MetaCons "PathTerm" 'PrefixI 'True) (S1 ('MetaSel ('Just "pathTerm") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 term) :*: S1 ('MetaSel ('Just "rejected") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet (term, rule)))))

type Path rule term a = ([Step rule term a], PathTerm rule term) Source #

A path explored by REST. The head of the 1st part of the tuple is the initial term. The 2nd part of the tuple is the last term.

pathTerms :: Path rule term a -> [term] Source #

Extracts the list of terms from the path

runtimeTerm :: Path rule term a -> term Source #

Extracts the last (most recently generated) term