debian-3.47: Modules for working with the Debian package systemSource codeContentsIndex
Debian.Control.ByteString
Contents
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' ByteString
type Paragraph = Paragraph' ByteString
type Field = Field' ByteString
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
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
Documentation
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' ByteStringSource
type Paragraph = Paragraph' ByteStringSource
type Field = Field' ByteStringSource
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
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.6.1