Lastik-0.6.3: A library for compiling programs in a variety of languages

System.Build.Args

Description

Functions for working with command line arguments and options.

Synopsis

Documentation

quote :: String -> StringSource

Surrounds the given string in double-quotes.

(~~) :: String -> Bool -> StringSource

An empty list if the boolean is False otherwise the given string value with - prepended.

(~:) :: String -> [FilePath] -> StringSource

If the given list of file paths is empty, then returns the empty list. Otherwise prepend - to the string followed by ' ' then the search path separator intercalated in the list of file paths.

 Posix
 "123" ~?? ["abc", "def"] == "-123 \"abc\":\"def\""
 "123" ~?? ["abc", "def", "ghi"] == "-123 \"abc\":\"def\":\"ghi\""

(~?) :: (k -> [a]) -> Maybe k -> [a]Source

If the given value is Nothing return the empty list, otherwise run the given function.

param :: String -> Char -> (k -> String) -> Maybe k -> StringSource

If the given value is Nothing return the empty list, otherwise prepend - to the given string followed by the given character followed by surrounding the result of running the given function in double-quotes.

 param "abc" 'x' id (Just "tuv") == "-abcx\"tuv\""
 param "abc" 'x' id Nothing == ""

many :: String -> [String] -> StringSource

A parameter with many values interspersed by ' '.

 many "abc" ["tuv", "wxy"] == "-abc \"tuv\" -abc \"wxy\""

manys :: (a -> String) -> String -> [a] -> StringSource

A parameter with many values interspersed by ' '.

 manys id "abc" ["tuv", "wxy"] == "-abc \"tuv\" -abc \"wxy\""

(~~~>) :: String -> String -> StringSource

Prepends - followed by the first value then ' ' then the second value surrounded by double-quotes.

 "abc" ~~~> "def" == "-abc \"def\""

(~~>) :: Show k => String -> Maybe k -> StringSource

If the given value is Nothing return the empty list, otherwise prepend - followed by the first value then ' ' followed by surrounding the result of running the given function in double-quotes.

 "abc" ~~> Just "def" == "-abc \"def\""
 "abc" ~~> Nothing == ""

(-~>) :: Show k => String -> Maybe k -> StringSource

If the given value is Nothing return the empty list, otherwise prepend - followed by the first value then : followed by surrounding the result of show in double-quotes.

 "abc" ~~> Just "def" == "-abc:\"def\""
 "abc" ~~> Nothing == ""

(^^^) :: [[a]] -> [a] -> [a]Source

Removes all empty lists from the first argument the intercalates the second argument.

 ["abc", "", "def"] ^^^ "x" == "abcxdef"

space :: [String] -> StringSource

Surrounds each given value in double-quotes then intercalates ' '.

 space ["abc", "def"] == "\"abc\" \"def\""

searchPath :: [String] -> StringSource

Surrounds each given value in double-quotes then intercalates [searchPathSeparator].

 searchPath ["abc", "def"] == "\"abc\":\"def\""

tryEnvs :: [(String, String -> a)] -> IO (Maybe a)Source

Look up the given environment variables. The first one found that exists has its associated function called to produce a value.