flocc-pffb

Stabilityexperimental
Maintainerdeveloper@flocc.net
Safe HaskellNone

Compiler.Front.Common

Description

For more information please see http://www.flocc.net/

Synopsis

Documentation

putStrE :: String -> IO ()

class ShowP a where

Methods

showP :: a -> String

Instances

ShowP Char 
ShowP Int 
ShowP Expr 
ShowP Val 
ShowP IdxTree 
ShowP IdTree 
ShowP ExpLbl 
ShowP TyToken 
ShowP CastCandidate 
(ShowP a, Show a) => ShowP [a]

isString s. Returns true if this value is a string. isString :: (Typeable a) => a -> Bool isString n = typeOf n == typeOf abc

ShowP a => ShowP (Maybe a) 
ShowP a => ShowP (IntMap a) 
ShowP t => ShowP (FunctionToken t) 
ShowP t => ShowP (Constr t) 
ShowP t => ShowP (Subst t) 
(ShowP a, ShowP b) => ShowP (Either a b) 
(ShowP a, ShowP b) => ShowP (a, b) 
(ShowP k, ShowP v) => ShowP (Map k v) 
(ShowP l, ShowP t) => ShowP (SchemeEx l t) 
(ShowP t, ShowP l) => ShowP (Scheme l t)

Display a term scheme

Display a term scheme

(ShowP l, ShowP t) => ShowP (Term l t)

Implementation of show for terms

(ShowP a, ShowP b, ShowP c) => ShowP (a, b, c) 

class FunctorM f where

Methods

fmapM :: Monad m => (a -> m b) -> f a -> m (f b)

Instances

class Mappable a where

Class for types that can be mapped over using a |monadic transformation function.

Methods

monadicMap :: Monad m => (a -> m a) -> a -> m a

Instances

Mappable (Term l t) 

class Counted a where

Class for types that carry a count.

Methods

getCount :: a -> Int

setCount :: Int -> a -> a

incCount :: Counted a => a -> a

Increments the count of a counted value by 1.

catchRetry :: MonadCatch m => m a -> Int -> m (Either a SomeException)

catchRetry2 :: MonadCatch m => m a -> Int -> m a

catchRetryIO :: IO a -> Int -> IO a

catchRead :: (Show a, Read a) => String -> String -> a

readMaybe :: (Show a, Read a) => String -> Maybe a

liftPair :: (a -> b) -> (a, a) -> (b, b)

Lifts a function to work on a pair

droplast :: Int -> [a] -> [a]

Returns all but the last n elements of a list

prepad :: [a] -> a -> Int -> Int -> [a]

Pads the list with copies of the second argument until it is at least the length |given by the fourth argument. The third argument should be the length |of the input list.

indent :: a -> Int -> [a] -> [a]

toUpperFst :: String -> String

toUpperFst makes first character of string upper case and rest lower case

underscoresToUppers :: String -> String

underscoresToUppers takes a string with underscores and removes them |making the next character uppercase.

lr :: Either (b -> a) (b -> a) -> Either b b -> Either a a

Takes either a left or a right function, and either a left |or a right value, and applies the function to the value, |returning the result in the left if both the function, |and the value were left, and right otherwise.

lr0 :: (b -> a) -> Either b b -> Either a a

Takes a function and either a left or a right term |and returns the result of applying that function to |the term still wrapped in the appropriate left or right |of its parent

eids :: Int

Idx numbers

initIdxSet :: Num t => t -> [t]

evalIdxState :: Int -> State IdxSet a -> a

Runs an idx state computation

evalIdxStateT :: Monad m => Int -> StateT IdxSet m a -> m a

runIdxStateT :: Monad m => Int -> StateT IdxSet m a -> m (a, IdxSet)

showList :: Show a => [a] -> String

showLookupTable :: Show a => Show b => Int -> [(a, b)] -> String

Shows a lookup table, nicely padded

funLParen :: [Char]

Left and right parentheses for function types

findAndModify :: (a -> Bool) -> (a -> a) -> [a] -> Maybe [a]

Searches the list for an item satisfying the predicate, and modifie |the first occurance using the function.

findAndModifyAll :: (a -> Bool) -> (a -> a) -> [a] -> [a]

Searches the list for an item satisfying the predicate, and modifie |all occurances using the function.

findAndReplace :: (a -> Bool) -> a -> [a] -> Maybe [a]

Searches the list for an item satisfying the predicate, and replaces the |first occurance with the value given in the second argument.

findAndReplaceAll :: (a -> Bool) -> a -> [a] -> [a]

Searches the list for an item satisfying the predicate, and replaces the |first occurance with the value given in the second argument.

foundKey :: Eq k => k -> (k, v) -> Bool

Simple boolean predicate for finding a key in a key value list

modifyValue :: (v -> v) -> (k, v) -> (k, v)

Simple function that modifies the second element in a pair using a function

tracer :: Show a => a -> a

Debug function for tracing

tracerEx :: Show a => String -> a -> a

Debug function for tracing, that can be curried with a label string

tracerEx2 :: String -> (a -> String) -> a -> a

Debug function for tracing, that takes a label string and a custom show function

tracerEx3 :: String -> (a -> String) -> a -> b -> b

Debug function for tracing, that takes a label string, show function, and object to |display

flipAssocList :: [(a, b)] -> [(b, a)]

Flips an associative list so that the keys become value's and |visa versa.

xor :: Bool -> Bool -> Bool

Implementation or exclusive or

isLeft :: Either a b -> Bool

maybeError :: String -> Maybe a -> a

maybeError takes a string message and a maybe value |returning the enclosed value when its a Just |or returning an error with the message otherwise

maybeList :: Maybe a -> [a]

maybeList takes a maybe value and returns |either a singleton, or empty list depending on the value

fromMaybePair :: (Maybe a, Maybe b) -> Maybe (a, b)

fromMaybePair takes a pair of maybe values and if |both are Just return a single maybe holding the pair

fromIntMap :: IntMap t -> Map Int t

fromIntMap im. Returns a Data.Map.Strict map from an |IntMap.

toIntMap :: Map Int t -> IntMap t

toIntMap m. Returns a Data.IntMap.Strict map from a |Data.Map.Strict.

lookupOrValue :: Ord k => k -> Map k v -> v -> v

lookupOrValue takes a key, map, and value and looks |that key up in the map, returning the associated value if it exists |or the value given otherwise.

lookupIntOrValue :: Int -> IntMap v -> v -> v

lookupIntOrValue takes a key, map, and value and looks |that key up in the map, returning the associated value if it exists |or the value given otherwise.

lookupOrError :: (Show k, Ord k) => String -> k -> Map k v -> v

lookupOrError takes an error message string, key and a map, |and tries to lookup from the map, returning the element if |it exists, or throwing an error with the message otherwise

lookupIntOrError :: String -> Int -> IntMap v -> v

lookupIntOrError takes an error message string, key and an intmap, |and tries to lookup from the map, returning the element if |it exists, or throwing an error with the message otherwise

lookupAssocOrValue :: (Eq k, Show k) => a -> k -> [(k, a)] -> a

replaceAssocVal :: Eq a => String -> a -> v -> [(a, v)] -> [(a, v)]

replaceAssocVal takes an error message string, key value and assoc |array and returns the list with the first occurence of the key replaced |with the value, or throws an error if that key does not exist in the list.

unionsCheckDisjoint :: (Ord a, Show a) => String -> [Set a] -> Set a

unionsCheckDisjoint takes a list of sets and throws the error message |if they are not disjoint, or returns the unions set otherwise.

mapUnionCheckDisjoint :: (Ord k, Show k, Show v) => String -> Map k v -> Map k v -> Map k v

mapUnionCheckDisjoint checks thats is operands are disjoint before performing their union

imapUnionCheckDisjoint :: Show v => String -> IntMap v -> IntMap v -> IntMap v

mapUnionCheckDisjoint checks thats is operands are disjoint before performing their union

deleteIfExists :: Ord x => x -> Set x -> Set x

deleteIfExists deletes from the set if it contains it, or nothing afterwards

assocToListMap :: Ord k => [(k, v)] -> Map k [v]

assocToListMap takes an associative array (which may contain duplicates) and returns |a Map of lists.

takeOrError :: Show a => String -> Int -> [a] -> [a]

takeOrError throws an error if the input array isn't the exact length |given by the integer argument, or returns it otherwise

updateListItem :: [a] -> (a -> a) -> Int -> [a]

updateList updates an element in a list.

listIdx :: Show a => [a] -> Int -> a

listItem list idx. Returns list item at idx, or error if idx is out of range.

listGet :: Show a => String -> [a] -> Int -> a

listItem list idx. Returns list item at idx, or error if idx is out of range.

intersects :: Eq a => [[a]] -> [a]

pairUp :: (a -> a -> b) -> [a] -> [b]

pairUp f l. Returns a new list formed by applying f to |all adjacent pairs in l. e.g. pairUp (+) [1,2,3] = [3,5]

hasCycle :: Ord a => Set a -> [(a, [a])] -> Bool

hasCycle seenVars edges. Returns True iff the directed graph has a cycle (i.e. |contains a back edge that points to a vertex that is the input vertex for |an edge that has already been visited.)