debian-3.91.2: Modules for working with the Debian package system

Safe HaskellNone
LanguageHaskell98

Debian.Control.Text

Contents

Synopsis

Types

newtype Control' a Source #

Constructors

Control 

Fields

Instances

Eq a => Eq (Control' a) Source # 

Methods

(==) :: Control' a -> Control' a -> Bool #

(/=) :: Control' a -> Control' a -> Bool #

Ord a => Ord (Control' a) Source # 

Methods

compare :: Control' a -> Control' a -> Ordering #

(<) :: Control' a -> Control' a -> Bool #

(<=) :: Control' a -> Control' a -> Bool #

(>) :: Control' a -> Control' a -> Bool #

(>=) :: Control' a -> Control' a -> Bool #

max :: Control' a -> Control' a -> Control' a #

min :: Control' a -> Control' a -> Control' a #

Read a => Read (Control' a) Source # 
Show a => Show (Control' a) Source # 

Methods

showsPrec :: Int -> Control' a -> ShowS #

show :: Control' a -> String #

showList :: [Control' a] -> ShowS #

(ControlFunctions a, Pretty (PP a)) => Pretty (Control' a) Source #

This may have bad performance issues (dsf: Whoever wrote this comment should have explained why.)

data Field' a Source #

NOTE: we do not strip the leading or trailing whitespace in the name or value

Constructors

Field (a, a) 
Comment a

Lines beginning with #

Instances

Eq a => Eq (Field' a) Source # 

Methods

(==) :: Field' a -> Field' a -> Bool #

(/=) :: Field' a -> Field' a -> Bool #

Ord a => Ord (Field' a) Source # 

Methods

compare :: Field' a -> Field' a -> Ordering #

(<) :: Field' a -> Field' a -> Bool #

(<=) :: Field' a -> Field' a -> Bool #

(>) :: Field' a -> Field' a -> Bool #

(>=) :: Field' a -> Field' a -> Bool #

max :: Field' a -> Field' a -> Field' a #

min :: Field' a -> Field' a -> Field' a #

Read a => Read (Field' a) Source # 
Show a => Show (Field' a) Source # 

Methods

showsPrec :: Int -> Field' a -> ShowS #

show :: Field' a -> String #

showList :: [Field' a] -> ShowS #

(ControlFunctions a, Pretty (PP a)) => Pretty (Field' a) Source # 

type Field = Field' Text Source #

parseFromFile p filePath runs a string parser p on the input read from filePath using readFile. Returns either a ParseError (Left) or a value of type a (Right).

 main    = do{ result <- parseFromFile numbers "digits.txt"
             ; case result of
                 Left err  -> print err
                 Right xs  -> print (sum xs)
             }

class ControlFunctions a where Source #

Methods

parseControlFromFile :: FilePath -> IO (Either ParseError (Control' a)) Source #

parseControlFromFile filepath is a simple wrapper function that parses filepath using pControl

parseControlFromHandle :: String -> Handle -> IO (Either ParseError (Control' a)) Source #

parseControlFromHandle sourceName handle - sourceName is only used for error reporting

parseControl :: String -> a -> Either ParseError (Control' a) Source #

parseControlFromString sourceName text - sourceName is only used for error reporting

lookupP :: String -> Paragraph' a -> Maybe (Field' a) Source #

lookupP fieldName paragraph looks up a Field in a Paragraph. N.B. trailing and leading whitespace is not stripped.

stripWS :: a -> a Source #

Strip the trailing and leading space and tab characters from a string. Folded whitespace is not unfolded. This should probably be moved to someplace more general purpose.

protectFieldText :: a -> a Source #

Protect field value text so the parser doesn't split it into multiple fields or paragraphs. This must modify all field text to enforce two conditions: (1) All lines other than the initial one must begin with a space or a tab, and (2) the trailing white space must not contain newlines. This is called before pretty printing to prevent the parser from misinterpreting field text as multiple fields or paragraphs.

asString :: a -> String Source #

Control File Parser

Helper Functions

renameField :: Eq a => a -> a -> Paragraph' a -> Paragraph' a Source #

modifyField :: Eq a => a -> (a -> a) -> Paragraph' a -> Paragraph' a Source #

raiseFields :: Eq a => (a -> Bool) -> Paragraph' a -> Paragraph' a Source #

Move selected fields to the beginning of a paragraph.

Orphan instances