debian-3.33: Modules for working with the Debian package systemSource codeContentsIndex
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))
parseControl :: String -> a -> Either ParseError (Control' a)
lookupP :: String -> Paragraph' a -> Maybe (Field' a)
stripWS :: a -> a
asString :: a -> String
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 Source
Constructors
Control
unControl :: [Paragraph' a]
show/hide Instances
newtype Paragraph' a Source
Constructors
Paragraph [Field' a]
show/hide Instances
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
show/hide Instances
type Control = Control' StringSource
type Paragraph = Paragraph' StringSource
type Field = Field' StringSource
type ControlParser a = CharParser () aSource
class ControlFunctions a whereSource
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 -> aSource
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.
asString :: a -> StringSource
show/hide Instances
Control File Parser
pControl :: ControlParser ControlSource
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' aSource
fieldValue :: ControlFunctions a => String -> Paragraph' a -> Maybe aSource
removeField :: Eq a => a -> Paragraph' a -> Paragraph' aSource
prependFields :: [Field' a] -> Paragraph' a -> Paragraph' aSource
appendFields :: [Field' a] -> Paragraph' a -> Paragraph' aSource
renameField :: Eq a => a -> a -> Paragraph' a -> Paragraph' aSource
modifyField :: Eq a => a -> (a -> a) -> Paragraph' a -> Paragraph' aSource
raiseFields :: Eq a => (a -> Bool) -> Paragraph' a -> Paragraph' aSource
Move selected fields to the beginning of a paragraph.
Produced by Haddock version 2.4.2