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

Language.REST.WQOConstraints.Strict

Description

This module defines an implemenation for representing constraints on a WQO; in this case represented by a set of "extendable" WQOs each satisfying the constraints. For more details see StrictOC

Synopsis

Documentation

strictOC :: Monad m => WQOConstraints StrictOC m Source #

An implementation of StrictOC; for any computational context

strictOC' :: WQOConstraints StrictOC Identity Source #

An implementation of StrictOC in the Identity monad; usable in pure computations.

difference :: (Eq a, Ord a, Hashable a) => StrictOC a -> StrictOC a -> StrictOC a Source #

isUnsatisfiable :: Eq a => StrictOC a -> Bool Source #

Returns true iff strictOC ws does not permit any WQOs; i.e., if ws is empty.

noConstraints :: forall a. (Eq a, Ord a, Hashable a) => StrictOC a Source #

Constraints that permit any WQO. In this case implemented by a singleton set containing an empty WQO.

permits :: (Eq a, Ord a, Hashable a) => StrictOC a -> WQO a -> Bool Source #

StrictOC ws permits a WQO w if there exists a w' in ws that can be extended to equal w

data StrictOC a Source #

StrictOC ws represents constraints on a WQO. Each element of ws is a WQO that satisfies the constraints. StrictOC ws permits a WQO w if there exists a w' in ws such that w' can be extended to yield w.

This implementation is similar to disjunctive normal form representation of logical formulas; except in this case each "conjunction" is a valid WQO, and thus "satisfiable". Therefore StrictOC ws satisfies some WQO iff ws is not empty.

Two potential downsides to this implementation are: 1. The size of ws can grow quickly; an inherent issue of DNF 2. Related, calculating the entire set ws is computationally expensive, and often unnecessary for RESTs use-case, where continuing the path only requires knowing if any WQO is permitted.

Instances

Instances details
Generic (StrictOC a) Source # 
Instance details

Defined in Language.REST.WQOConstraints.Strict

Associated Types

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

Methods

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

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

(Show a, Eq a, Ord a, Hashable a) => Show (StrictOC a) Source # 
Instance details

Defined in Language.REST.WQOConstraints.Strict

Methods

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

show :: StrictOC a -> String #

showList :: [StrictOC a] -> ShowS #

Eq a => Eq (StrictOC a) Source # 
Instance details

Defined in Language.REST.WQOConstraints.Strict

Methods

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

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

Ord a => Ord (StrictOC a) Source # 
Instance details

Defined in Language.REST.WQOConstraints.Strict

Methods

compare :: StrictOC a -> StrictOC a -> Ordering #

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

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

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

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

max :: StrictOC a -> StrictOC a -> StrictOC a #

min :: StrictOC a -> StrictOC a -> StrictOC a #

Hashable a => Hashable (StrictOC a) Source # 
Instance details

Defined in Language.REST.WQOConstraints.Strict

Methods

hashWithSalt :: Int -> StrictOC a -> Int #

hash :: StrictOC a -> Int #

type Rep (StrictOC a) Source # 
Instance details

Defined in Language.REST.WQOConstraints.Strict

type Rep (StrictOC a)