hpp-0.5.2: A Haskell pre-processor

Safe HaskellSafe
LanguageHaskell2010

Hpp.StringSig

Synopsis

Documentation

data CharOrSub s Source #

Constructors

CharMatch !s !s 
SubMatch !s !s 
NoMatch 

class (IsString s, Monoid s) => Stringy s where Source #

A collection of operations relating to sequences of characters.

Methods

stringify :: s -> s Source #

Stringification puts double quotes around a string and backslashes before existing double quote characters and backslash characters.

unquote :: s -> s Source #

Remove double quote characters from the ends of a string.

trimSpaces :: s -> s Source #

Trim trailing spaces from a String

breakOn :: [(s, t)] -> s -> Maybe (t, s, s) Source #

Similar to the function of the same name in the text package.

breakOn needles haystack finds the first instance of an element of needles in haystack. The first component of the result is the needle tag, the second component is the prefix of haystack before the matched needle, the third component is the remainder of the haystack after the needle..

breakCharOrSub :: Char -> s -> s -> CharOrSub s Source #

A special case of breakOn in which we are looking for either a special character or a particular substring.

cons :: Char -> s -> s Source #

uncons :: s -> Maybe (Char, s) Source #

snoc :: s -> Char -> s Source #

unsnoc :: s -> Maybe (s, Char) Source #

sdrop :: Int -> s -> s Source #

sbreak :: (Char -> Maybe t) -> s -> Maybe (t, s, s) Source #

sall :: (Char -> Bool) -> s -> Bool Source #

sIsPrefixOf :: s -> s -> Bool Source #

isEmpty :: s -> Bool Source #

readLines :: FilePath -> IO [s] Source #

putStringy :: Handle -> s -> IO () Source #

toChars :: s -> [Char] Source #

copy :: s -> s Source #

An opportunity to copy a string to its own storage to help with GC

Instances

Stringy String Source # 
Stringy ByteString Source # 

predicateJust :: (a -> Bool) -> a -> Maybe a Source #

sdropWhile :: Stringy s => (Char -> Bool) -> s -> s Source #

pattern (:.) :: Stringy s => Char -> s -> s infixr 5 Source #

pattern Nil :: Stringy s => s Source #