| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Debian.Control.Common
Contents
Synopsis
- newtype Control' a = Control {- unControl :: [Paragraph' a]
 
- newtype Paragraph' a = Paragraph [Field' a]
- data Field' 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
- protectFieldText :: 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
- parseControlFromCmd :: ControlFunctions a => String -> IO (Either String (Control' a))
- md5sumField :: ControlFunctions a => Paragraph' a -> Maybe a
- protectFieldText' :: forall a. (StringLike a, ListLike a Char) => ControlFunctions a => a -> a
Types
Constructors
| Control | |
| Fields 
 | |
Instances
| (ControlFunctions a, Pretty (PP a)) => Pretty (Control' a) Source # | This may have bad performance issues (dsf: Whoever wrote this comment should have explained why.) | 
| Defined in Debian.Control.Common | |
| Read a => Read (Control' a) Source # | |
| Show a => Show (Control' a) Source # | |
| Eq a => Eq (Control' a) Source # | |
| Ord a => Ord (Control' a) Source # | |
| Defined in Debian.Control.Common | |
newtype Paragraph' a Source #
Instances
NOTE: we do not strip the leading or trailing whitespace in the name or value
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.
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.
Instances
mergeControls :: [Control' a] -> Control' a Source #
fieldValue :: ControlFunctions a => String -> Paragraph' a -> Maybe a Source #
removeField :: Eq a => a -> Paragraph' a -> Paragraph' a Source #
prependFields :: [Field' a] -> Paragraph' a -> Paragraph' a Source #
appendFields :: [Field' a] -> Paragraph' a -> Paragraph' a Source #
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.
parseControlFromCmd :: ControlFunctions a => String -> IO (Either String (Control' a)) Source #
Run a command and parse its output as a control file.
md5sumField :: ControlFunctions a => Paragraph' a -> Maybe a Source #
look up the md5sum file in a paragraph Tries several different variations: MD5Sum: Md5Sum: MD5sum:
protectFieldText' :: forall a. (StringLike a, ListLike a Char) => ControlFunctions a => a -> a Source #
This can usually be used as the implementation of protectFieldText