haskhol-core-1.0.0: The core logical system of HaskHOL, an EDSL for HOL theorem proving.

Portabilityunknown
Stabilityunstable
Maintainerecaustin@ittc.ku.edu
Safe HaskellNone

HaskHOL.Core.Lib

Contents

Description

This module defines or re-exports common utility functions, type classes, and auxilliary data types used in HaskHOL. The following conventions hold true: * Where possible, we favor re-exporting common functions rather than redefining them. * We favor re-exporting individual functions rather entire modules to reduce the number of items in our utility library. * We default to the names of functions commonly used by Haskell libraries, however, if there's a different name for a function in HOL systems we include an alias for it. For example, iComb and id.

Note that none of the functions in this module depend on data types introduced by HaskHOL. Utility functions that do have such a dependence are found in the HaskHOL.Core.Basics module.

Synopsis

Function Combinators

iComb :: a -> aSource

The I combinator. An alias for id.

kComb :: a -> b -> aSource

The K combinator. An alias for const.

cComb :: (a -> b -> c) -> b -> a -> cSource

The C combinator. An alias for flip.

wComb :: (a -> a -> b) -> a -> bSource

The W combinator. Takes a function of arity 2 and applies a single argument to it twice.

ffComb :: (a -> c) -> (b -> d) -> (a, b) -> (c, d)Source

The FF combinator. An alias for the arrow combinator ***.

ffCombM :: Monad m => (a -> m c) -> (b -> m d) -> (a, b) -> m (c, d)Source

The monadic version of the FF combinator. An alias for the arrow combinator *** lifted for Kleisli arrows.

liftM1 :: Monad m => (a -> b -> m c) -> m a -> b -> m cSource

Promotes a function to a monad, but only for its first argument, i.e.

 liftM1 f a b === flip f b =<< a

Basic Operations on Pairs

swap :: (a, b) -> (b, a)Source

Swaps the order of a pair. A re-export of swap.

pairMap :: (a -> b) -> (a, a) -> (b, b)Source

Applies a function to both elements of a pair using the *** operator.

pairMapM :: Monad m => (a -> m b) -> (a, a) -> m (b, b)Source

The monadic version of pairMap.

first :: (a -> c) -> (a, b) -> (c, b)Source

Applies a function only to the first element of a pair. A re-export of first.

firstM :: Monad m => (a -> m c) -> (a, b) -> m (c, b)Source

A monadic version of first lifted for Kleisli arrows.

second :: (b -> c) -> (a, b) -> (a, c)Source

Applies a function only to the second element of a pair. A re-export of second.

secondM :: Monad m => (b -> m c) -> (a, b) -> m (a, c)Source

A monadic version of second lifted for Kleisli arrows.

Basic Operations on Lists

tryHead :: [a] -> Maybe aSource

A safe version of head. Fails with Nothing when trying to take the head of an empty list.

tryTail :: [a] -> Maybe [a]Source

A safe version of tail. Fails with Nothing when trying to take the tail of an empty list.

tryInit :: [a] -> Maybe [a]Source

A safe version of init. Fails with Nothing when trying to drop the last element of an empty list.

butLast :: [a] -> Maybe [a]Source

An alias to tryInit for HOL users more familiar with this name.

tryLast :: [a] -> Maybe aSource

A safe version of last. Fails with Nothing when trying to take the last element of an empty list.

tryIndex :: [a] -> Int -> Maybe aSource

A safe version of index. Fails with Nothing if the selected index does not exist.

el :: Int -> [a] -> Maybe aSource

An alias to tryIndex for HOL users more familiar with this name. Note that the order of the arguments is flipped.

rev :: [a] -> [a]Source

An alias to reverse for HOL users more familiar with this name.

Basic Operations on Association Lists

assoc :: Eq a => a -> [(a, b)] -> Maybe bSource

An alias to lookup for HOL users more familiar with this name.

revLookup :: Eq a => a -> [(b, a)] -> Maybe bSource

A version of lookup where the search is performed against the second element of the pair instead of the first. Still fails with Nothing if the desired value is not found.

revAssoc :: Eq a => a -> [(b, a)] -> Maybe bSource

An alias to revLookup for HOL users who are more familiar with this name.

assocd :: Eq a => a -> [(a, b)] -> b -> bSource

An alias to lookupd for HOL users who are more familiar with this name.

lookupd :: Eq a => a -> [(a, b)] -> b -> bSource

A version of lookup that defaults to a provided value rather than fail.

revLookupd :: Eq a => a -> [(b, a)] -> b -> bSource

A version of revLookup that defaults to a provided value rather than fail.

revAssocd :: Eq a => a -> [(b, a)] -> b -> bSource

An alias to revLookupd for HOL users who are more familiar with this name.

Methods for Error Handling

can :: (Alternative m, Monad m) => (a -> m b) -> a -> m BoolSource

Returns a boolean value indicating whether a monadic computation succeeds or fails. The <|> operator is used for branching.

canNot :: (Alternative m, Monad m) => (a -> m b) -> a -> m BoolSource

The opposite of can. Functionally equivalent to

 \ f -> liftM not . can f

check :: (a -> Bool) -> a -> Maybe aSource

Checks if a predicate succeeds for a provided value, returning that value guarded by a Maybe type if so.

note :: a -> Maybe b -> Either a bSource

Takes a default error value to convert a Maybe type to an Either type.

hush :: Either a b -> Maybe bSource

Suppresses the error value of an Either type to convert it to a Maybe type.

fromRight :: Either err a -> aSource

An analogue of fromJust for the Either type. Fails with error when provided a Left value, so take care only to use it in cases where you know you are working with a Right value or are catching exceptions.

fromRightM :: MonadPlus m => Either err a -> m aSource

A version of fromRight that maps Left values to mzero rather than failing.

fromJustM :: MonadPlus m => Maybe a -> m aSource

A version of fromJust that maps Nothing values to mzero rather than failing.

class Monad m => LiftOption l m whereSource

The LiftOption class provides an infix operator to more cleanly apply the fromJustM and fromRightM methods to a value that will be passed to a monadic computation.

Methods

liftO :: l a -> m aSource

Used to lift an option value, i.e. Maybe or Either, so that it can be passed as an argument to a monadic computation.

(#<<) :: (a -> m b) -> l a -> m bSource

A version of =<< composed with liftO for the right argument.

(<#<) :: (b -> m c) -> (a -> l b) -> a -> m cSource

A version of <=< composed with liftO for the right argument.

(<#>) :: (a -> b -> m c) -> l a -> b -> m cSource

A version of liftM1 composed with liftO for the right argument.

Instances

class (Alternative m, Monad m) => Note m whereSource

The Note class provides an ad hoc way of tagging an error case with a string.

Methods

(<?>) :: m a -> String -> m aSource

Used to annotate more precise error messages. Replaces the <|> operator in cases such as

 ... <|> fail "..."

failWhen :: m Bool -> String -> m ()Source

Replaces the common pattern

 m >>= \ cond -> if cond then fail "..."

The default case is defined in terms of empty and <?>.

Instances

Note (Either String) 
Note (HOL cls thry) 

Methods for Function Repetition

funpow :: Int -> (a -> a) -> a -> aSource

Repeatedly applies a function to an argument n times. Rather than fail, the original argument is returned when n<=0.

funpowM :: Monad m => Int -> (a -> m a) -> a -> m aSource

The monadic version of funpow.

repeatM :: (Alternative m, Monad m) => (a -> m a) -> a -> m aSource

Repeatedly applies a monadic computation to an argument until there is a failure. The <|> operator is used for branching.

map2 :: (a -> b -> c) -> [a] -> [b] -> Maybe [c]Source

A safe version of a list map for functions of arity 2. Fails with Nothing if the two lists are of different lengths.

map2M :: (Monad m, MonadPlus m) => (a -> b -> m c) -> [a] -> [b] -> m [c]Source

The monadic version of map2. Fails with mzero if the two lists are of different lengths.

doList :: Monad m => (a -> m b) -> [a] -> m ()Source

Map a monadic function over a list, ignoring the results. A re-export of mapM_.

allpairs :: (a -> b -> c) -> [a] -> [b] -> [c]Source

Produces a list containing the results of applying a function to all possible combinations of arguments from two lists. Rather than failing if the lists are of different lengths, iteration is shortcutted to end when the left most list is null.

Methods for List Iteration

itlist :: (a -> b -> b) -> [a] -> b -> bSource

An alias to foldr for HOL users more familiar with this name. Note that the order of the list and base case arguments is flipped.

itlistM :: (Foldable t, Monad m) => (a -> b -> m b) -> t a -> b -> m bSource

The monadic version of itlist.

foldrM :: (Foldable t, Monad m) => (a -> b -> m b) -> b -> t a -> m bSource

The monadic version of foldr. A re-export of foldrM.

revItlist :: (a -> b -> b) -> [a] -> b -> bSource

An alias to foldl for HOL users more familiar with this name. Note that the order of the list and base case arguments is flipped, as is the order of the arguments to the function.

foldlM :: (Foldable t, Monad m) => (a -> b -> m a) -> a -> t b -> m aSource

The monadic version of foldl. A re-export of foldlM.

tryFoldr1 :: (a -> a -> a) -> [a] -> Maybe aSource

A safe version of foldr1. Fails with Nothing if an empty list is provided as an argument.

endItlist :: (a -> a -> a) -> [a] -> Maybe aSource

An alias to tryFoldr1 for HOL users more familiar with this name.

foldr1M :: (Monad m, MonadPlus m) => (a -> a -> m a) -> [a] -> m aSource

The monadic version of foldr1. Fails with mzero if an empty list is provided as an argument.

foldr2 :: (a -> b -> c -> c) -> c -> [a] -> [b] -> Maybe cSource

A safe version of a right, list fold for functions of arity 2. Fails with Nothing if the two lists are of different lengths.

itlist2 :: (a -> b -> c -> c) -> [a] -> [b] -> c -> Maybe cSource

An alias to foldr2 for HOL users more familiar with this name. Note that the order of the two list arguments and the base case argument is flipped.

foldr2M :: (Monad m, MonadPlus m) => (a -> b -> c -> m c) -> c -> [a] -> [b] -> m cSource

The monadic version of foldr2. Fails with mzero if the two lists are of different lengths.

foldl2 :: (c -> a -> b -> c) -> c -> [a] -> [b] -> Maybe cSource

A safe version of a left, list fold for functions of arity 2. Fails with Nothing if the two lists are of different lengths.

revItlist2 :: (a -> b -> c -> c) -> [a] -> [b] -> c -> Maybe cSource

An alias to foldl2 for HOL users more familiar with this name. Note that the order of the two list arguments and base case argument is flipped, as is the order of the arguments to the provided function.

foldl2M :: (Monad m, MonadPlus m) => (c -> a -> b -> m c) -> c -> [a] -> [b] -> m cSource

The monadic version of foldl2. Fails with mzero if the two lists are of different lengths.

Methods for Sorting and Merging Lists

sort :: Eq a => (a -> a -> Bool) -> [a] -> [a]Source

Sorts a list using a partitioning predicate to build an implied ordering. If p is the predicate and x `p` y and not (y `p` x) are true then x will be in front of y in the sorted list.

sortBy :: (a -> a -> Ordering) -> [a] -> [a]Source

A more traditional sort using an Ordering relationship between elements. A re-export of sortBy.

merge :: (a -> a -> Bool) -> [a] -> [a] -> [a]Source

Merges two lists using a partitioning predicate to build an implied ordering. See sort for more information on how the predicate affects the order of the resultant list.

mergesort :: forall a. (a -> a -> Bool) -> [a] -> [a]Source

Sorts a list using a partitioning predicate to build an implied ordering; uses merge internally. See sort for more information on how the predicate affects the order of the resultant list.

Methods for Splitting and Stripping Binary Terms

splitList :: (b -> Maybe (a, b)) -> b -> ([a], b)Source

Repeatedly applies a binary destructor function to a term until failure.

Application is forward, or left-associative, such that for a term of the form x1 `f` x2 `f` b calling this function with a destructor for f will produce the result ([x1, x2], b).

splitListM :: (Alternative m, Monad m) => (b -> m (a, b)) -> b -> m ([a], b)Source

The monadic version of splitList.

revSplitList :: forall a. (a -> Maybe (a, a)) -> a -> (a, [a])Source

Repeatedly applies a binary destructor function to a term until failure.

Application is reverse, or right-associative, such that for a term of the form x1 `f` x2 `f` b calling this function with a destructor for f will produce the result (f, [x1, x2 `f` b]).

revSplitListM :: forall m b. (Alternative m, Monad m) => (b -> m (b, b)) -> b -> m (b, [b])Source

The monadic version of revSplitList.

nsplit :: (a -> Maybe (a, a)) -> [b] -> a -> Maybe ([a], a)Source

Repeatedly applies a binary destructor function to a term for every element in a provided list.

Application is reverse, or right-associative, such that for a term of the form f x1 (f x2 ...(f xn b)) calling this function with a destructor for f and a list l will produce the result ([x1 .. xk], f x(k+1) ...(f xn b)) where k is the length of list l.

nsplitM :: Monad m => (b -> m (b, b)) -> [c] -> b -> m ([b], b)Source

The monadic version of nsplit.

stripList :: forall a. (a -> Maybe (a, a)) -> a -> [a]Source

Repeatedly applies a binary destructor function to a term until failure.

Application is forward, or left-associative, such that for a term of the form x1 `f` x2 `f` x3 calling this function with a destructor for f will produce the result [x1, x2, x3].

stripListM :: forall m a. (Alternative m, Monad m) => (a -> m (a, a)) -> a -> m [a]Source

The monadic version of stripList.

Methods for Searching and Manipulating Lists

forall :: (a -> Bool) -> [a] -> BoolSource

An alias to all for HOL users who are more familiar with this name.

forall2 :: (a -> b -> Bool) -> [a] -> [b] -> Maybe BoolSource

A version of all for predicates of arity 2. Iterates down two lists simultaneously with map2, using and to combine the results.

exists :: (a -> Bool) -> [a] -> BoolSource

An alias to any for HOL users who are more familiar with this name.

partition :: (a -> Bool) -> [a] -> ([a], [a])Source

Separates a list of elements using a predicate. A re-export of partition.

mapFilter :: (a -> Maybe b) -> [a] -> [b]Source

An alias to mapMaybe for HOL users more familiar with this name.

mapFilterM :: (Alternative m, Monad m) => (a -> m b) -> [a] -> m [b]Source

The monadic version of mapFilter. The '(|)' operator is used for branching.

find :: (a -> Bool) -> [a] -> Maybe aSource

A re-export of find.

findM :: (Monad m, MonadPlus m) => (a -> m Bool) -> [a] -> m aSource

The monadic version of find. Fails if the monadic predicate does. Also fails with mzero if an empty list is provided.

tryFind :: (Monad m, MonadPlus m) => (a -> m b) -> [a] -> m bSource

An alternative monadic version of find where the predicate is a monadic computation not necessarily of a boolean return type. Returns the result of the first successful application of the predicate to an element of the list. Fails with mzero if called on an empty list.

Note that mplus is used for branching instead of <|> to minimize the constraint type; for the vast majority of monads these two functions should be identical anyway.

flat :: [[a]] -> [a]Source

An alias to concat for HOL users who are more familiar with this name.

dropWhileEnd :: (a -> Bool) -> [a] -> [a]Source

Drops elements from the end of a list while a predicate is true. A re-export of dropWhileEnd.

remove :: (a -> Bool) -> [a] -> Maybe (a, [a])Source

Separates the first element of a list that satisfies a predicate. Fails with Nothing if no such element is found.

trySplitAt :: Int -> [a] -> Maybe ([a], [a])Source

A safe version of splitAt. Fails with Nothing if a split is attempted at an index that doesn't exist.

chopList :: Int -> [a] -> Maybe ([a], [a])Source

An alias to trySplitAt for HOL users more familiar with this name

elemIndex :: Eq a => a -> [a] -> Maybe IntSource

Returns the first index where an element appears in list. Fails with Nothing if no such element is found. A re-export of elemIndex.

index :: Eq a => a -> [a] -> Maybe IntSource

An alias to elemIndex for HOL users more familiar with this name.

stripPrefix :: Eq a => [a] -> [a] -> Maybe [a]Source

Drops the given prefix from a list. Fails with Nothing if there is no such prefix. A re-export of stripPrefix.

uniq :: Eq a => [a] -> [a]Source

Removes adjacent, equal elements from a list.

shareOut :: [[a]] -> [b] -> Maybe [[b]]Source

Partitions a list into a list of lists matching the structure of the first argument. For example: shareOut [[1, 2], [3], [4, 5]] "abcde" === ["ab", "c", "de"]

Set Operations on Lists

mem :: Eq a => a -> [a] -> BoolSource

An alias to elem for HOL users who are more familiar with this name.

insert :: Eq a => a -> [a] -> [a]Source

Inserts an item into a list if it would be a unique element.

Important note: This insert is unordered, unlike the insert in the Data.List module.

insertMap :: Eq a => a -> b -> [(a, b)] -> [(a, b)]Source

Inserts, or updates, a key value pair in an association list.

Note that this insert is unordered, but uniqueness preserving.

union :: Eq a => [a] -> [a] -> [a]Source

Unions two list maintaining uniqueness of elements.

Important note: This union is unordered, unlike the union in the Data.List module.

unions :: Eq a => [[a]] -> [a]Source

Unions a list of lists using union.

intersect :: Eq a => [a] -> [a] -> [a]Source

Finds the intersection of two lists. A re-export of intersect.

delete :: Eq a => a -> [a] -> [a]Source

Removes an item from a list. A re-export of delete.

(\\) :: Eq a => [a] -> [a] -> [a]Source

Subtracts one list from the other. A re-export of \\.

subset :: Eq a => [a] -> [a] -> BoolSource

Tests if the first list is a subset of the second.

setEq :: Eq a => [a] -> [a] -> BoolSource

A test for set equality using subset.

setify :: Eq a => [a] -> [a]Source

An alias to nub for HOL users more familiar with this name.

nub :: Eq a => [a] -> [a]Source

Converts a list to a set by removing duplicates. A re-export of nub.

Set Operations Parameterized by Predicate

mem' :: (a -> a -> Bool) -> a -> [a] -> BoolSource

A version of mem where the membership test is an explicit predicate, rather than a strict equality test.

insert' :: (a -> a -> Bool) -> a -> [a] -> [a]Source

A version of insert where the uniqueness test is an explicit predicate, rather than a strict equality test.

union' :: (a -> a -> Bool) -> [a] -> [a] -> [a]Source

A version of union where the uniqueness test is an explicit predicate, rather than a strict equality test.

unions' :: (a -> a -> Bool) -> [[a]] -> [a]Source

A version of unions where the uniqueness test is an explicit predicate, rather than a strict equality test.

subtract' :: (a -> a -> Bool) -> [a] -> [a] -> [a]Source

A version of subtract where the uniqueness test is an explicit predicate, rather than a strict equality test.

group' :: (a -> a -> Bool) -> [a] -> [[a]]Source

Groups neighbors in a list together based on a predicate. A re-export of groupBy.

uniq' :: Eq a => (a -> a -> Bool) -> [a] -> [a]Source

A version of uniq that eliminates elements based on a provided predicate.

setify' :: Eq a => (a -> a -> Bool) -> (a -> a -> Bool) -> [a] -> [a]Source

A version of setify that eliminates elements based on a provided predicate.

Operations on "Num" Types

The following are aliases to frequently used values and functions for arbitrary-precision integers. Typically, they are used when converting to and from numbers in the implementation language and the logic language. The aliases clarify the intended use and saves us from having lots of explicit type annotations to force Integer values.

num0 :: IntegerSource

 0 :: Integer

num1 :: IntegerSource

 1 :: Integer

num2 :: IntegerSource

 2 :: Integer

num10 :: IntegerSource

 10 :: Integer

pow2 :: Integer -> IntegerSource

 x ^ (2 :: Integer)

pow10 :: Integer -> IntegerSource

 x ^ (10 :: Integer)

numdom :: Real a => a -> RationalSource

Converts a real number to a rational representation. An alias to toRational for HOL users more familiar with this name.

numerator :: Rational -> IntegerSource

Returns the numerator of a rational number. A re-export of numerator.

denominator :: Rational -> IntegerSource

Returns the denominator of a rational number. A re-export of denominator.

gcdNum :: Integer -> Integer -> IntegerSource

Finds the least common denominator between two numbers. An alias to gcd for HOL users more familiar with this name.

lcmNum :: Integer -> Integer -> IntegerSource

Finds the least common multiplier between two numbers. An alias to lcm for HOL users more familiar with this name.

numOfString :: forall a. (Eq a, Num a) => String -> Maybe aSource

Converts a string representation of a number to an appropriate instance of the Num class. Fails with Nothing if the conversion cannot be performed.

Note: The following prefixes are valid:

  • 0x - number read as a hexidecimal value
  • 0b - number read as a binary value
  • Any other prefix causes the number to be read as a decimal value

Classes for Common "Language" Operations

The following two classes are used as an ad hoc mechanism for sharing "language" operations between different types. For example, both tactics and conversions share a number of the same operations. Rather than having multiple functions, such as thenTac and thenConv, we've found it easier to have a single, polymorphic function to use, _THEN.

The sequencing operations are seperated in their own class, LangSeq, because their tactic instances have a reliance on the boolean logic theory. Rather than unecessarily propogate this prerequisite for all members of the Lang class, we elected to separate them.

class Lang a whereSource

The Lang class defines common language operations and combinators not based on sequencing.

Methods

_FAIL :: String -> aSource

A primitive language operation that always fails. Typically this is written using throw.

_NO :: aSource

An instance of _FAIL with a fixed failure string.

_ALL :: aSource

A primitive language operation that always succeeds.

_ORELSE :: a -> a -> aSource

A language combinator for branching based on failure. The language equivalent of the <|> operator.

_FIRST :: [a] -> aSource

A language combinator that performs the first operation in a list.

_CHANGED :: a -> aSource

A language combinator that fails if the wrapped operation doesn't invoke some change, i.e. a tactic fails to change the goal state.

_TRY :: a -> aSource

A language combinator that prevents the wrapped operation from having an effect if it fails. The language equivalent of the backtracking try operator.

class LangSeq a whereSource

The LangSeq class defines common language operations and combinators based on sequencing. See the note at the top of this section for more details as to why these are separated on their own.

Methods

_THEN :: a -> a -> aSource

A language combinator that sequences operations.

_REPEAT :: a -> aSource

A language combinator that repeatedly applies a language operation until failure.

_EVERY :: [a] -> aSource

A language combinator that performs every operation in a list sequentially.

Miscellaneous Re-exported Libraries

Re-exports deriveLift, deriveLiftMany, and Lift to be used with our extensible state mechanisms.

Re-exports Applicative, Alternative, and the utility functions for use with the HOL monad.

Re-exports the entirety of the library, but currently only NFData is used. Necessary for using the Criterion benchmarking library.

Re-exports the entirety of the library for use with the HOL monad.

module Data.Maybe

Re-exports the entirety of the library. Used primarily to make interacting with primitive rules easier at later points in the system.

Re-exports the entirety of the library. Used primarily to make interacting with primitive rules easier at later points in the system.

Re-exports the Typeable class name for use in deriving clauses.

Re-exports the entirety of the library. Used primarily for its Assoc data type, but also contains a number of primitives used by the parser.