uhc-util-0.1.6.7: UHC utilities

Safe HaskellSafe
LanguageHaskell98

UHC.Util.Utils

Contents

Synopsis

Set

unionMapSet :: Ord b => (a -> Set b) -> Set a -> Set b Source #

Union a set where each element itself is mapped to a set

Map

inverseMap :: (Ord k, Ord v') => (k -> v -> (v', k')) -> Map k v -> Map v' k' Source #

Inverse of a map

showStringMapKeys :: Map String x -> String -> String Source #

Show keys of map using a separator

mapLookup2' :: (Ord k1, Ord k2) => (v1 -> Map k2 v2) -> k1 -> k2 -> Map k1 v1 -> Maybe (Map k2 v2, v2) Source #

double lookup, with transformer for 2nd map

mapLookup2 :: (Ord k1, Ord k2) => k1 -> k2 -> Map k1 (Map k2 v2) -> Maybe v2 Source #

double lookup

List

hdAndTl' :: a -> [a] -> (a, [a]) Source #

Get head and tail, with default if empty list

hdAndTl :: [a] -> (a, [a]) Source #

Get head and tail, with panic/error if empty list

maybeNull :: r -> ([a] -> r) -> [a] -> r Source #

maybeHd :: r -> (a -> r) -> [a] -> r Source #

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

Split up in words by predicate

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

Possibly last element and init

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

Possibly last and preceding element and init

last' :: a -> [a] -> a Source #

variation on last which returns empty value instead of

firstNotEmpty :: [[x]] -> [x] Source #

First non empty list of list of lists

listSaturate :: (Enum a, Ord a) => a -> a -> (x -> a) -> (a -> x) -> [x] -> [x] Source #

Saturate a list, that is: for all indices i between min and max, if there is no listelement x for which get x returns i, add an element mk i to the list

listSaturateWith :: (Enum a, Ord a) => a -> a -> (x -> a) -> [(a, x)] -> [x] -> [x] Source #

Saturate a list with values from assoc list, that is: for all indices i between min and max, if there is no listelement x for which get x returns i, add a candidate from the associationlist (which must be present) to the list

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

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

variant on filter, where predicate also yields a result

splitPlaces Source #

Arguments

:: [Int]

places

-> [e] 
-> [[e]] 

Split at index places (inspired by/from split package). Places should be increasing, starting with an index >= 0. The number of sublists returned is one higher than the number of places.

Examples: >>> splitPlaces [2,3] [1,2,3,4,5,6,7] [[1,2],[3],[4,5,6,7]]

>>> splitPlaces [6,7] [1,2,3,4,5,6,7]
[[1,2,3,4,5,6],[7],[]]
>>> splitPlaces [0,7] [1,2,3,4,5,6,7]
[[],[1,2,3,4,5,6,7],[]]
>>> splitPlaces [0,1,2,3,4,5,6,7] [1,2,3,4,5,6,7]
[[],[1],[2],[3],[4],[5],[6],[7],[]]

combineToDistinguishedEltsBy :: (e -> e -> Bool) -> [[e]] -> [[e]] Source #

Combine [[x1..xn],..,[y1..ym]] to [[x1..y1],[x2..y1],..,[xn..ym]]. Each element [xi..yi] is distinct based on the the key k in xi==(k,_)

partitionOnSplit :: (a -> (x, y)) -> (x -> x') -> (x -> Bool) -> [a] -> ([(x', y)], [y]) Source #

Partition on part of something, yielding a something else in the partitioning

Tuple

tup123to1 :: (t2, t1, t) -> t2 Source #

tup123to2 :: (t1, t2, t) -> t2 Source #

tup123to12 :: (t2, t1, t) -> (t2, t1) Source #

tup123to23 :: (t, t2, t1) -> (t2, t1) Source #

tup12to123 :: t2 -> (t1, t) -> (t1, t, t2) Source #

fst3 :: (t2, t1, t) -> t2 Source #

snd3 :: (t1, t2, t) -> t2 Source #

thd3 :: (t1, t, t2) -> t2 Source #

thd :: (t1, t, t2) -> t2 Source #

tup1234to1 :: (t3, t2, t1, t) -> t3 Source #

tup1234to2 :: (t2, t3, t1, t) -> t3 Source #

tup1234to3 :: (t2, t1, t3, t) -> t3 Source #

tup1234to4 :: (t2, t1, t, t3) -> t3 Source #

tup1234to12 :: (t3, t2, t1, t) -> (t3, t2) Source #

tup1234to13 :: (t3, t1, t2, t) -> (t3, t2) Source #

tup1234to14 :: (t3, t1, t, t2) -> (t3, t2) Source #

tup1234to23 :: (t1, t3, t2, t) -> (t3, t2) Source #

tup1234to24 :: (t1, t3, t, t2) -> (t3, t2) Source #

tup1234to34 :: (t1, t, t3, t2) -> (t3, t2) Source #

tup1234to123 :: (t3, t2, t1, t) -> (t3, t2, t1) Source #

tup1234to234 :: (t, t3, t2, t1) -> (t3, t2, t1) Source #

tup1234to124 :: (t3, t2, t, t1) -> (t3, t2, t1) Source #

tup1234to134 :: (t3, t, t2, t1) -> (t3, t2, t1) Source #

tup123to1234 :: t3 -> (t2, t1, t) -> (t2, t1, t, t3) Source #

fst4 :: (t3, t2, t1, t) -> t3 Source #

snd4 :: (t2, t3, t1, t) -> t3 Source #

thd4 :: (t2, t1, t3, t) -> t3 Source #

fth4 :: (t2, t1, t, t3) -> t3 Source #

fth :: (t2, t1, t, t3) -> t3 Source #

String

strWhite :: Int -> String Source #

Blanks

strPad :: String -> Int -> String Source #

Pad upto size with blanks

strCapitalize :: String -> String Source #

Capitalize first letter

strToLower :: String -> String Source #

Lower case

strToInt :: String -> Int Source #

Convert string to Int

splitForQualified :: String -> [String] Source #

Split into fragments based on . convention for qualified Haskell names

Show utils

showUnprefixedWithShowTypeable :: (Show x, Typeable x) => Int -> x -> String Source #

Show, additionally removing type name prefix, assuming constructor names are prefixed with type name, possibly with additional underscore (or something like that)

class DataAndConName x where Source #

Methods

dataAndConName :: x -> (String, String) Source #

Get datatype and constructor name for a datatype

dataAndConName :: (Generic x, GDataAndConName (Rep x)) => x -> (String, String) Source #

Get datatype and constructor name for a datatype

showUnprefixed :: DataAndConName x => Int -> x -> String Source #

Show, additionally removing type name prefix, assuming constructor names are prefixed with type name, possibly with additional underscore (or something like that)

Ordering

orderingLexic :: Ordering -> Ordering -> Ordering Source #

Reduce compare results lexicographically using a continuation ordering

orderingLexicList :: [Ordering] -> Ordering Source #

Reduce compare results lexicographically to one compare result

Misc

panic :: [Char] -> a Source #

Error, with message

isSortedByOn :: (b -> b -> Ordering) -> (a -> b) -> [a] -> Bool Source #

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

A slightly more lazy version of Data.List.sortOn. See also https://github.com/UU-ComputerScience/uhc-util/issues/5 .

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

Sort a list by comparing the results of a key function applied to each element. sortOn f is equivalent to sortBy (comparing f), but has the performance advantage of only evaluating f once for each element in the input list. This is called the decorate-sort-undecorate paradigm, or Schwartzian transform.

Since: 4.8.0.0

sortByOn :: (b -> b -> Ordering) -> (a -> b) -> [a] -> [a] Source #

groupOn :: Eq b => (a -> b) -> [a] -> [[a]] Source #

groupByOn :: (b -> b -> Bool) -> (a -> b) -> [a] -> [[a]] Source #

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

groupSortByOn :: (b -> b -> Ordering) -> (a -> b) -> [a] -> [[a]] Source #

nubOn :: Eq b => (a -> b) -> [a] -> [a] Source #

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

The consecutiveBy function groups like groupBy, but based on a function which says whether 2 elements are consecutive

partitionAndRebuild :: (v -> Bool) -> [v] -> ([v], [v], [v'] -> [v'] -> [v']) Source #

Partition, but also return a function which will rebuild according to the original ordering of list elements

Maybe

($?) :: (a -> Maybe b) -> Maybe a -> Maybe b infixr 0 Source #

orMb :: Maybe a -> Maybe a -> Maybe a Source #

maybeAnd :: x -> (a -> b -> x) -> Maybe a -> Maybe b -> x Source #

maybeOr :: x -> (a -> x) -> (b -> x) -> Maybe a -> Maybe b -> x Source #

Graph

scc :: Ord n => [(n, [n])] -> [[n]] Source #

Monad

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

loop over monads yielding a Maybe from a start value, yielding the first Just or the start (when no Just is returned)

breakM :: Monad m => (a -> Bool) -> [m a] -> m ([a], Maybe (a, [m a])) Source #

Monadic equivalent of break: evaluate monads until a predicate is True, returning what is yes/no evaluated and the split point