debian-1.2: A set of modules for working with debian control files and packagesContentsIndex
Linspire.Debian.Control.String
Contents
Types
Control File Parser
Helper Functions
Synopsis
newtype Control' a = Control {
unControl :: [Paragraph' a]
}
newtype Paragraph' a = Paragraph [Field' a]
data Field' a
= Field (a, a)
| Comment a
type Control = Control' String
type Paragraph = Paragraph' String
type Field = Field' String
type ControlParser a = CharParser () a
class ControlFunctions a where
parseControlFromFile :: FilePath -> IO (Either ParseError (Control' a))
parseControlFromHandle :: String -> Handle -> IO (Either ParseError (Control' a))
lookupP :: String -> Paragraph' a -> Maybe (Field' a)
stripWS :: a -> a
pControl :: ControlParser Control
mergeControls :: [Control' a] -> Control' a
fieldValue :: ControlFunctions a => String -> Paragraph' a -> Maybe a
removeField :: Eq a => a -> Paragraph' a -> Paragraph' a
prependFields :: [Field' a] -> Paragraph' a -> Paragraph' a
appendFields :: [Field' a] -> Paragraph' a -> Paragraph' a
renameField :: Eq a => a -> a -> Paragraph' a -> Paragraph' a
modifyField :: Eq a => a -> (a -> a) -> Paragraph' a -> Paragraph' a
raiseFields :: Eq a => (a -> Bool) -> Paragraph' a -> Paragraph' a
Types
newtype Control' a
Constructors
Control
unControl :: [Paragraph' a]
show/hide Instances
newtype Paragraph' a
Constructors
Paragraph [Field' a]
show/hide Instances
data Field' a
NOTE: we do not strip the leading or trailing whitespace in the name or value
Constructors
Field (a, a)
Comment a
show/hide Instances
(Eq a, ??? a) => Eq (Field' a)
Show (Field' String)
type Control = Control' String
type Paragraph = Paragraph' String
type Field = Field' String
type ControlParser a = CharParser () a
class ControlFunctions a where
Methods
parseControlFromFile :: FilePath -> IO (Either ParseError (Control' a))
parseControlFromFile filepath is a simple wrapper function that parses filepath using pControl
parseControlFromHandle :: String -> Handle -> IO (Either ParseError (Control' a))
parseControlFromHandle sourceName handle - sourceName is only used for error reporting
lookupP :: String -> Paragraph' a -> Maybe (Field' a)
lookupP fieldName paragraph looks up a Field in a Paragraph. N.B. trailing and leading whitespace is not stripped.
stripWS :: a -> a
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.
show/hide Instances
Control File Parser
pControl :: ControlParser Control
A parser for debian control file. This parser handles control files that end without a newline as well as ones that have several blank lines at the end. It is very liberal and does not attempt validate the fields in any way. All trailing, leading, and folded whitespace is preserved in the field values. See stripWS.
Helper Functions
mergeControls :: [Control' a] -> Control' a
fieldValue :: ControlFunctions a => String -> Paragraph' a -> Maybe a
removeField :: Eq a => a -> Paragraph' a -> Paragraph' a
prependFields :: [Field' a] -> Paragraph' a -> Paragraph' a
appendFields :: [Field' a] -> Paragraph' a -> Paragraph' a
renameField :: Eq a => a -> a -> Paragraph' a -> Paragraph' a
modifyField :: Eq a => a -> (a -> a) -> Paragraph' a -> Paragraph' a
raiseFields :: Eq a => (a -> Bool) -> Paragraph' a -> Paragraph' a
Move selected fields to the beginning of a paragraph.
Produced by Haddock version 0.8