BNFC-2.9.4: A compiler front-end generator.
Safe HaskellSafe-Inferred
LanguageHaskell2010

BNFC.Utils

Synopsis

Documentation

type ModuleName = String Source #

The name of a module, e.g. Foo.Abs, Foo.Print etc.

when :: Monoid m => Bool -> m -> m Source #

Generalization of when.

unless :: Monoid m => Bool -> m -> m Source #

Generalization of unless.

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.

applyWhen :: Bool -> (a -> a) -> a -> a Source #

when for the monoid of endofunctions 'a -> a'.

applyUnless :: Bool -> (a -> a) -> a -> a Source #

unless for the monoid of endofunctions 'a -> a'.

for :: [a] -> (a -> b) -> [b] Source #

Non-monadic forM.

whenJust :: Monoid m => Maybe a -> (a -> m) -> m Source #

Generalization of forM to Monoid.

caseMaybe :: Maybe a -> b -> (a -> b) -> b Source #

Rotation of maybe.

(>.>) :: (a -> b) -> (b -> c) -> a -> c infixr 8 Source #

Diagrammatic composition.

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.

singleton :: a -> [a] Source #

Give a telling name to the electric monkey.

headWithDefault :: a -> [a] -> a Source #

Get the first element of a list, fallback for empty list.

mapHead :: (a -> a) -> [a] -> [a] Source #

Apply a function to the head of a 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)

(+++) :: String -> String -> String infixr 5 Source #

Concatenate strings by a space.

(++++) :: String -> String -> String infixr 5 Source #

Concatenate strings by a newline.

(+-+) :: String -> String -> String infixr 5 Source #

Concatenate strings by an underscore.

(+.+) :: String -> String -> String infixr 5 Source #

Concatenate strings by a dot.

parensIf :: Bool -> String -> String Source #

Wrap in parentheses if condition holds.

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_"]

data NameStyle Source #

Different case style

Constructors

LowerCase

e.g. lowercase

UpperCase

e.g. UPPERCASE

SnakeCase

e.g. snake_case

CamelCase

e.g. CamelCase

MixedCase

e.g. mixedCase

OrigCase

Keep original capitalization and form.

Instances

Instances details
Show NameStyle Source # 
Instance details

Defined in BNFC.Utils

Eq NameStyle Source # 
Instance details

Defined in BNFC.Utils

lowerCase :: String -> Doc Source #

Ident to lower case. >>> lowerCase MyIdent myident

upperCase :: String -> Doc Source #

Ident to upper case. >>> upperCase MyIdent MYIDENT

mixedCase :: String -> Doc Source #

To mixed case. >>> mixedCase "my_ident" myIdent

camelCase :: String -> Doc Source #

Ident to camel case. >>> camelCase "my_ident" MyIdent

snakeCase :: String -> Doc Source #

To snake case. >>> snakeCase MyIdent my_ident

replace 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\""

symbolToName :: String -> Maybe String Source #

Print a symbol as typical token name, like "(" as LPAREN.