| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
BNFC.Utils
Synopsis
- type ModuleName = String
- when :: Monoid m => Bool -> m -> m
- unless :: Monoid m => Bool -> m -> m
- unlessNull :: Monoid m => [a] -> ([a] -> m) -> m
- unlessNull' :: Monoid m => [a] -> (a -> [a] -> m) -> m
- applyWhen :: Bool -> (a -> a) -> a -> a
- applyUnless :: Bool -> (a -> a) -> a -> a
- for :: [a] -> (a -> b) -> [b]
- whenJust :: Monoid m => Maybe a -> (a -> m) -> m
- caseMaybe :: Maybe a -> b -> (a -> b) -> b
- (>.>) :: (a -> b) -> (b -> c) -> a -> c
- curry3 :: ((a, b, c) -> d) -> a -> b -> c -> d
- uncurry3 :: (a -> b -> c -> d) -> (a, b, c) -> d
- singleton :: a -> [a]
- headWithDefault :: a -> [a] -> a
- mapHead :: (a -> a) -> [a] -> [a]
- spanEnd :: (a -> Bool) -> [a] -> ([a], [a])
- duplicatesOn :: (Foldable t, Ord b) => (a -> b) -> t a -> [List1 a]
- groupOn :: Eq b => (a -> b) -> [a] -> [List1 a]
- uniqOn :: Eq b => (a -> b) -> [a] -> [a]
- hasNumericSuffix :: String -> Maybe (String, Integer)
- (+++) :: String -> String -> String
- (++++) :: String -> String -> String
- (+-+) :: String -> String -> String
- (+.+) :: String -> String -> String
- parensIf :: Bool -> String -> String
- pad :: Int -> String -> String
- table :: String -> [[String]] -> [String]
- mkName :: [String] -> NameStyle -> String -> String
- mkNames :: [String] -> NameStyle -> [String] -> [String]
- data NameStyle
- capitalize :: String -> String
- lowerCase :: String -> Doc
- upperCase :: String -> Doc
- mixedCase :: String -> Doc
- camelCase :: String -> Doc
- camelCase_ :: String -> String
- snakeCase :: String -> Doc
- snakeCase_ :: String -> String
- replace :: Eq a => a -> a -> [a] -> [a]
- writeFileRep :: FilePath -> String -> IO ()
- cstring :: String -> Doc
- getZonedTimeTruncatedToSeconds :: IO ZonedTime
- symbolToName :: String -> Maybe String
Documentation
unlessNull :: Monoid m => [a] -> ([a] -> m) -> m Source #
Invoke continuation for non-empty list.
unlessNull' :: Monoid m => [a] -> (a -> [a] -> m) -> m Source #
Invoke continuation for non-empty list.
applyUnless :: Bool -> (a -> a) -> a -> a Source #
unless for the monoid of endofunctions 'a -> a'.
curry3 :: ((a, b, c) -> d) -> a -> b -> c -> d Source #
Converts an uncurried function to a curried function.
uncurry3 :: (a -> b -> c -> d) -> (a, b, c) -> d Source #
Converts a curried function to a function on a triple.
headWithDefault :: a -> [a] -> a Source #
Get the first element of a list, fallback for empty list.
spanEnd :: (a -> Bool) -> [a] -> ([a], [a]) Source #
spanEnd p l == reverse (span p (reverse l)).
Invariant: l == front ++ end where (end, front) = spanEnd p l
(From package ghc, module Util.)
duplicatesOn :: (Foldable t, Ord b) => (a -> b) -> t a -> [List1 a] Source #
Returns lists of elements whose normal form appears more than once.
>>>duplicatesOn id [5,1,2,5,1][1 :| [1],5 :| [5]]>>>duplicatesOn abs [5,-5,1][5 :| [-5]]
groupOn :: Eq b => (a -> b) -> [a] -> [List1 a] Source #
Group consecutive elements that have the same normalform.
uniqOn :: Eq b => (a -> b) -> [a] -> [a] Source #
Keep only the first of consecutive elements that have the same normalform.
hasNumericSuffix :: String -> Maybe (String, Integer) Source #
Get a numeric suffix if it exists.
>>>hasNumericSuffix "hello world"Nothing>>>hasNumericSuffix "a1b2"Just ("a1b",2)>>>hasNumericSuffix "1234"Just ("",1234)
pad :: Int -> String -> String Source #
Pad a string on the right by spaces to reach the desired length.
table :: String -> [[String]] -> [String] Source #
Make a list of rows with left-aligned columns from a matrix.
mkName :: [String] -> NameStyle -> String -> String Source #
Generate a name in the given case style taking into account the reserved word of the language. Note that despite the fact that those name are mainly to be used in code rendering (type Doc), we return a String here to allow further manipulation of the name (like disambiguation) which is not possible in the Doc type.
Examples:
>>>mkName [] LowerCase "FooBAR""foobar"
>>>mkName [] UpperCase "FooBAR""FOOBAR"
>>>mkName [] SnakeCase "FooBAR""foo_bar"
>>>mkName [] CamelCase "FooBAR""FooBAR"
>>>mkName [] CamelCase "Foo_bar""FooBar"
>>>mkName [] MixedCase "FooBAR""fooBAR"
>>>mkName ["foobar"] LowerCase "FooBAR""foobar_"
>>>mkName ["foobar", "foobar_"] LowerCase "FooBAR""foobar__"
mkNames :: [String] -> NameStyle -> [String] -> [String] Source #
Same as above but accept a list as argument and make sure that the names generated are uniques.
>>>mkNames ["c"] LowerCase ["A", "b_", "a_", "c"]["a1","b","a2","c_"]
Different case style
capitalize :: String -> String Source #
Make first letter uppercase.
camelCase_ :: String -> String Source #
snakeCase_ :: String -> String Source #
Arguments
| :: Eq a | |
| => a | Value to replace | 
| -> a | Value to replace it with | 
| -> [a] | |
| -> [a] | 
Replace all occurences of a value by another value
writeFileRep :: FilePath -> String -> IO () Source #
Write a file, after making a backup of an existing file with the same name. If an old version of the file exist and the new version is the same, keep the old file and don't create a .bak file. / New version by TH, 2010-09-23
cstring :: String -> Doc Source #
A function that renders a c-like string with escaped characters. Note that although it's called cstring, this can be used with most (all) backend as they seem to mostly share escaping conventions. The c in the name is barely an homage for C being the oldest language in the lot.
>>>cstring "foobar""foobar"
>>>cstring "foobar\"""foobar\""