uni-util-2.3.0.3: Utilities for the uniform workbench
Safe HaskellNone
LanguageHaskell2010

Util.ExtendedPrelude

Description

Basic string-manipulation and other functions they forgot to put in the standard prelude.

Synopsis

Trimming spaces from Strings and putting them back again.

trimTrailing :: String -> String Source #

Remove trailing spaces (We try to avoid reconstructing the string, on the assumption that there aren't often spaces)

trimLeading :: String -> String Source #

Remove leading spaces

trimSpaces :: String -> String Source #

Remove trailing and leading spaces

padToLength :: Int -> String -> String Source #

Pad a string if necessary to the given length with leading spaces.

Miscellaneous functions

monadDot :: Monad m => (b -> m c) -> (a -> m b) -> a -> m c Source #

The "." operator lifted to monads. So like ., the arguments are given in the reverse order to that in which they should be executed.

simpleSplit :: (a -> Bool) -> [a] -> [[a]] Source #

findJust :: (a -> Maybe b) -> [a] -> Maybe b Source #

insertOrdLt :: Ord a => a -> [a] -> [a] Source #

insertOrdGt :: Ord a => a -> [a] -> [a] Source #

insertOrd :: (a -> a -> Bool) -> a -> [a] -> [a] Source #

insertOrdAlternate :: (a -> a -> Ordering) -> a -> (a -> a) -> [a] -> [a] Source #

insertOrdAlternate is similar to insertOrd except (1) it takes an Ordering argument; (2) if it finds an argument that matches, it applies the given function to generate a new element, rather than inserting another. The new generated element should be EQ to the old one.

readCheck :: Read a => String -> Maybe a Source #

returns Just a if we can read a, and the rest is just spaces.

chop :: Int -> [a] -> Maybe [a] Source #

pairList :: a -> [b] -> [(a, b)] Source #

lastOpt :: [a] -> Maybe a Source #

isPrefix :: Eq a => [a] -> [a] -> Maybe [a] Source #

returns remainder if the first list is a prefix of the second one.

class HasCoMapIO option where Source #

Methods

coMapIO :: (a -> IO b) -> option b -> option a Source #

class HasMapIO option where Source #

Methods

mapIO :: (a -> IO b) -> option a -> option b Source #

Instances

Instances details
HasMapIO SimpleSource Source # 
Instance details

Defined in Util.Sources

Methods

mapIO :: (a -> IO b) -> SimpleSource a -> SimpleSource b Source #

class HasMapMonadic h where Source #

Methods

mapMonadic :: Monad m => (a -> m b) -> h a -> m (h b) Source #

Instances

Instances details
HasMapMonadic [] Source # 
Instance details

Defined in Util.ExtendedPrelude

Methods

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

mapPartialM :: Monad m => (a -> m (Maybe b)) -> [a] -> m [b] Source #

Miscellaneous string and list operations

splitToChar :: Char -> String -> Maybe (String, String) Source #

We split at the first occurrence of the character, returning the string before and after.

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

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

deleteFirst :: (a -> Bool) -> [a] -> [a] Source #

deleteFirstOpt :: (a -> Bool) -> [a] -> [a] Source #

deleteAndFindFirst :: (a -> Bool) -> [a] -> (a, [a]) Source #

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

divideList :: (a -> Either b c) -> [a] -> ([b], [c]) Source #

Folding on trees

treeFold :: (ancestorInfo -> state -> node -> (ancestorInfo, state, [node])) -> ancestorInfo -> state -> node -> state Source #

node is the tree's node type. state is folded through every node of the tree (and is the result). We search the tree in depth-first order, applying visitNode at each node to update the state. The ancestorInfo information comes from the ancestors of the node. EG if we are visiting node N1 which came from N2 the ancestorInfo given to visitNode for N1 will be that computed from visitNode for N2. For the root node, it will be initialAncestor

treeFoldM :: Monad m => (ancestorInfo -> state -> node -> m (ancestorInfo, state, [node])) -> ancestorInfo -> state -> node -> m state Source #

Like treeFold, but using monads.

mapEq :: Eq a => (b -> a) -> b -> b -> Bool Source #

Produce an equality function for b

mapOrd :: Ord a => (b -> a) -> b -> b -> Ordering Source #

Produce a compare function for b

Exception-driven error mechanism.

type BreakFn = forall other. String -> other Source #

A function indicating we want to escape from the current computation.

addFallOut :: (BreakFn -> IO a) -> IO (Either String a) Source #

Intended use, EG addFallOut ( break -> do -- blah blah (normal IO a stuff) -- when (break condition) (break "You can't do that there ere") -- more blah blah, not executed if there's an break -- return (value of type a) )

addFallOutWE :: (BreakFn -> IO a) -> IO (WithError a) Source #

Like addFallOut, but returns a WithError object instead.

data GeneralBreakFn a Source #

Constructors

GeneralBreakFn (forall b. a -> b) 

data GeneralCatchFn a Source #

Constructors

GeneralCatchFn (forall c. IO c -> IO (Either a c)) 

Other miscellaneous functions

class EqIO v where Source #

Methods

eqIO :: v -> v -> IO Bool Source #

Instances

Instances details
EqIO ICStringLen Source # 
Instance details

Defined in Util.ICStringLen

class EqIO v => OrdIO v where Source #

Methods

compareIO :: v -> v -> IO Ordering Source #

Instances

Instances details
OrdIO ICStringLen Source # 
Instance details

Defined in Util.ICStringLen

newtype Full a Source #

indicates that an Ord or Eq instance really does need to take everything into account.

Constructors

Full a 

uniqOrd :: Ord a => [a] -> [a] Source #

Remove duplicate elements from a list.

uniqOrdOrder :: Ord a => [a] -> [a] Source #

Like uniqOrd, except that we specify the output order of the list. The resulting list is that obtained by deleting all duplicate elements in the list, except the first, for example [1,2,3,2,1,4] will go to [1,2,3,4].

uniqOrdByKey :: Ord b => (a -> b) -> [a] -> [a] Source #

Remove duplicate elements from a list where the key function is supplied.

uniqOrdByKeyOrder :: Ord b => (a -> b) -> [a] -> [a] Source #

Remove duplicate elements from a list where the key function is supplied. The list order is preserved and of the duplicates, it is the first in the list which is not deleted.

allSame :: (a -> Bool) -> [a] -> Maybe Bool Source #

Return Just True if all the elements give True, Just False if all False, Nothing otherwise (or list is empty).

allEq :: Eq a => [a] -> Bool Source #

If all the elements are equal, return True

findDuplicate :: Ord a => (b -> a) -> [b] -> Maybe b Source #

If there are two elements of the list with the same (a), return one, otherwise Nothing.

generalisedMerge Source #

Arguments

:: Monad m 
=> [a]

input list

-> [b]

list to combine with input list

-> (a -> b -> Ordering)

comparison function. a and b should be already sorted consistently with this comparison function, and it is assumed that each list is EQ to at most one of the other.

-> (Maybe a -> Maybe b -> m (Maybe a, Maybe c))

Merge function applied to each element of a and b, where we pair EQ elements together.

-> m ([a], [c])

Output of merge function concatenated.

A merge function for combining an input list with some new data, where both are pre-sorted.