express-0.1.16: Dynamically-typed expressions involving function application and variables.
Copyright(c) 2019-2021 Rudy Matela
License3-Clause BSD (see the file LICENSE)
MaintainerRudy Matela <rudy@matela.com.br>
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Express.Instances

Description

Defines utilities do deal with instances of typeclasses

Functions provided by this module store the set of instances as a simple Haskell list. When storing only a few instances this should be fine in terms of performance.

If you plan to store hundreds or thousands of instances, we recommend implementing different versions that use a more efficient Set/Map storage.

Synopsis

Documentation

reifyEq :: (Typeable a, Eq a) => a -> [Expr] Source #

O(1). Reifies an Eq instance into a list of Exprs. The list will contain == and /= for the given type. (cf. mkEq, mkEquation)

> reifyEq (undefined :: Int)
[ (==) :: Int -> Int -> Bool
, (/=) :: Int -> Int -> Bool ]
> reifyEq (undefined :: Bool)
[ (==) :: Bool -> Bool -> Bool
, (/=) :: Bool -> Bool -> Bool ]
> reifyEq (undefined :: String)
[ (==) :: [Char] -> [Char] -> Bool
, (/=) :: [Char] -> [Char] -> Bool ]

reifyOrd :: (Typeable a, Ord a) => a -> [Expr] Source #

O(1). Reifies an Ord instance into a list of Exprs. The list will contain compare, <= and < for the given type. (cf. mkOrd, mkOrdLessEqual, mkComparisonLE, mkComparisonLT)

> reifyOrd (undefined :: Int)
[ (<=) :: Int -> Int -> Bool
, (<) :: Int -> Int -> Bool ]
> reifyOrd (undefined :: Bool)
[ (<=) :: Bool -> Bool -> Bool
, (<) :: Bool -> Bool -> Bool ]
> reifyOrd (undefined :: [Bool])
[ (<=) :: [Bool] -> [Bool] -> Bool
, (<) :: [Bool] -> [Bool] -> Bool ]

reifyEqOrd :: (Typeable a, Ord a) => a -> [Expr] Source #

O(1). Reifies Eq and Ord instances into a list of Expr.

reifyName :: (Typeable a, Name a) => a -> [Expr] Source #

O(1). Reifies a Name instance into a list of Exprs. The list will contain name for the given type. (cf. mkName, lookupName, lookupNames)

> reifyName (undefined :: Int)
[name :: Int -> [Char]]
> reifyName (undefined :: Bool)
[name :: Bool -> [Char]]

mkEq :: Typeable a => (a -> a -> Bool) -> [Expr] Source #

O(1). Builds a reified Eq instance from the given == function. (cf. reifyEq)

> mkEq ((==) :: Int -> Int -> Bool)
[ (==) :: Int -> Int -> Bool
, (/=) :: Int -> Int -> Bool ]

mkOrd :: Typeable a => (a -> a -> Ordering) -> [Expr] Source #

O(1). Builds a reified Ord instance from the given compare function. (cf. reifyOrd, mkOrdLessEqual)

mkOrdLessEqual :: Typeable a => (a -> a -> Bool) -> [Expr] Source #

O(1). Builds a reified Ord instance from the given <= function. (cf. reifyOrd, mkOrd)

mkName :: Typeable a => (a -> String) -> [Expr] Source #

O(1). Builds a reified Name instance from the given name function. (cf. reifyName, mkNameWith)

mkNameWith :: Typeable a => String -> a -> [Expr] Source #

O(1). Builds a reified Name instance from the given String and type. (cf. reifyName, mkName)

isEq :: [Expr] -> Expr -> Bool Source #

O(n+m). Returns whether an Eq instance exists in the given instances list for the given Expr.

> isEq (reifyEqOrd (undefined :: Int)) (val (0::Int))
True
> isEq (reifyEqOrd (undefined :: Int)) (val ([[[0::Int]]]))
False

Given that the instances list has length m and that the given Expr has size n, this function is O(n+m).

isOrd :: [Expr] -> Expr -> Bool Source #

O(n+m). Returns whether an Ord instance exists in the given instances list for the given Expr.

> isOrd (reifyEqOrd (undefined :: Int)) (val (0::Int))
True
> isOrd (reifyEqOrd (undefined :: Int)) (val ([[[0::Int]]]))
False

Given that the instances list has length m and that the given Expr has size n, this function is O(n+m).

isEqOrd :: [Expr] -> Expr -> Bool Source #

O(n+m). Returns whether both Eq and Ord instance exist in the given list for the given Expr.

Given that the instances list has length m and that the given Expr has size n, this function is O(n+m).

isEqT :: [Expr] -> TypeRep -> Bool Source #

O(n). Returns whether an Eq instance exists in the given instances list for the given TypeRep.

> isEqT (reifyEqOrd (undefined :: Int)) (typeOf (undefined :: Int))
True
> isEqT (reifyEqOrd (undefined :: Int)) (typeOf (undefined :: [[[Int]]]))
False

Given that the instances list has length n, this function is O(n).

isOrdT :: [Expr] -> TypeRep -> Bool Source #

O(n). Returns whether an Ord instance exists in the given instances list for the given TypeRep.

> isOrdT (reifyEqOrd (undefined :: Int)) (typeOf (undefined :: Int))
True
> isOrdT (reifyEqOrd (undefined :: Int)) (typeOf (undefined :: [[[Int]]]))
False

Given that the instances list has length n, this function is O(n).

isEqOrdT :: [Expr] -> TypeRep -> Bool Source #

O(n). Returns whether both Eq and Ord instance exist in the given list for the given TypeRep.

Given that the instances list has length n, this function is O(n).

mkEquation :: [Expr] -> Expr -> Expr -> Expr Source #

O(n+m). Returns an equation between two expressions given that it is possible to do so from == operators given in the argument instances list.

When not possible, this function returns False encoded as an Expr.

mkComparisonLE :: [Expr] -> Expr -> Expr -> Expr Source #

O(n+m). Returns a less-than-or-equal-to inequation between two expressions given that it is possible to do so from <= operators given in the argument instances list.

When not possible, this function returns False encoded as an Expr.

mkComparisonLT :: [Expr] -> Expr -> Expr -> Expr Source #

O(n+m). Returns a less-than inequation between two expressions given that it is possible to do so from < operators given in the argument instances list.

When not possible, this function returns False encoded as an Expr.

mkComparison :: String -> [Expr] -> Expr -> Expr -> Expr Source #

O(n+m). Like mkEquation, mkComparisonLE and mkComparisonLT but allows providing the binary operator name.

When not possible, this function returns False encoded as an Expr.

lookupComparison :: String -> TypeRep -> [Expr] -> Maybe Expr Source #

O(n). Lookups for a comparison function (:: a -> a -> Bool) with the given name and argument type.

listVarsWith :: [Expr] -> Expr -> [Expr] Source #

O(n+m). Like lookupNames but returns a list of variables encoded as Exprs.

lookupName :: [Expr] -> Expr -> String Source #

O(n+m). Like name but lifted over an instance list and an Expr.

> lookupName preludeNameInstances (val False)
"p"
> lookupName preludeNameInstances (val (0::Int))
"x"

This function defaults to "x" when no appropriate name is found.

> lookupName [] (val False)
"x"

lookupNames :: [Expr] -> Expr -> [String] Source #

O(n+m). A mix between lookupName and names: this returns an infinite list of names based on an instances list and an Expr.

validApps :: [Expr] -> Expr -> [Expr] Source #

Given a list of functional expressions and another expression, returns a list of valid applications.

findValidApp :: [Expr] -> Expr -> Maybe Expr Source #

Like validApps but returns a Maybe value.

preludeNameInstances :: [Expr] Source #

A list of reified Name instances for an arbitrary selection of types from the Haskell Prelude.