module Debian.Control.Common
(
Control'(..)
, Paragraph'(..)
, Field'(..)
, ControlFunctions(..)
, mergeControls
, fieldValue
, removeField
, prependFields
, appendFields
, renameField
, modifyField
, raiseFields
, parseControlFromCmd
, md5sumField
, protectFieldText'
)
where
import Control.Monad (msum)
import Data.Char (isSpace)
import Data.List as List (dropWhileEnd, partition, intersperse)
import Data.ListLike as LL (ListLike, cons, dropWhileEnd, empty, find, null, singleton)
import Data.ListLike.String as LL (StringLike, lines, unlines)
import Data.Monoid ((<>))
import Debian.Pretty (PP(..))
import System.Exit (ExitCode(ExitSuccess, ExitFailure))
import System.IO (Handle)
import System.Process (runInteractiveCommand, waitForProcess)
import Text.ParserCombinators.Parsec (ParseError)
import Text.PrettyPrint (Doc, text, hcat)
import Text.PrettyPrint.HughesPJClass (Pretty(pPrint))
newtype Control' a
= Control { unControl :: [Paragraph' a] } deriving (Eq, Ord, Read, Show)
newtype Paragraph' a
= Paragraph [Field' a]
deriving (Eq, Ord, Read, Show)
data Field' a
= Field (a, a)
| Comment a
deriving (Eq, Ord, Read, Show)
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
protectFieldText' :: forall a. (StringLike a, ListLike a Char) => ControlFunctions a => a -> a
protectFieldText' s =
let trimmedLines :: [a]
trimmedLines = map (LL.dropWhileEnd isSpace :: a -> a) $ (LL.lines s :: [a])
strippedLines :: [a]
strippedLines = List.dropWhileEnd LL.null trimmedLines in
case strippedLines of
[] -> empty
(l : ls) ->
let
l' = l
ls' = case all indented ls of
True -> map (\ x -> if LL.null x then (LL.cons ' ' $ singleton '.') else x) ls
False -> map (LL.cons ' ') $ map (\ x -> if LL.null x then (singleton '.') else x) ls in
LL.dropWhileEnd isSpace (LL.unlines (l' : ls'))
where
indented l = maybe True isSpace (LL.find (const True) l)
instance (ControlFunctions a, Pretty (PP a)) => Pretty (Control' a) where
pPrint = ppControl
instance (ControlFunctions a, Pretty (PP a)) => Pretty (Paragraph' a) where
pPrint = ppParagraph
instance (ControlFunctions a, Pretty (PP a)) => Pretty (Field' a) where
pPrint = ppField
ppControl :: (ControlFunctions a, Pretty (PP a)) => Control' a -> Doc
ppControl (Control paragraph) =
hcat (intersperse (text "\n") (map ppParagraph paragraph))
ppParagraph :: (ControlFunctions a, Pretty (PP a)) => Paragraph' a -> Doc
ppParagraph (Paragraph fields) =
hcat (map (\ x -> ppField x <> text "\n") fields)
ppField :: (ControlFunctions a, Pretty (PP a)) => Field' a -> Doc
ppField (Field (n,v)) = pPrint (PP n) <> text ":" <> pPrint (PP (protectFieldText v))
ppField (Comment c) = pPrint (PP c)
mergeControls :: [Control' a] -> Control' a
mergeControls controls =
Control (concatMap unControl controls)
fieldValue :: (ControlFunctions a) => String -> Paragraph' a -> Maybe a
fieldValue fieldName paragraph =
case lookupP fieldName paragraph of
Just (Field (_, val)) -> Just $ stripWS val
_ -> Nothing
removeField :: (Eq a) => a -> Paragraph' a -> Paragraph' a
removeField toRemove (Paragraph fields) =
Paragraph (filter remove fields)
where
remove (Field (name,_)) = name == toRemove
remove (Comment _) = False
prependFields :: [Field' a] -> Paragraph' a -> Paragraph' a
prependFields newfields (Paragraph fields) = Paragraph (newfields ++ fields)
appendFields :: [Field' a] -> Paragraph' a -> Paragraph' a
appendFields newfields (Paragraph fields) = Paragraph (fields ++ newfields)
renameField :: (Eq a) => a -> a -> Paragraph' a -> Paragraph' a
renameField oldname newname (Paragraph fields) =
Paragraph (map rename fields)
where
rename (Field (name, value)) | name == oldname = Field (newname, value)
rename field = field
modifyField :: (Eq a) => a -> (a -> a) -> Paragraph' a -> Paragraph' a
modifyField name f (Paragraph fields) =
Paragraph (map modify fields)
where
modify (Field (name', value)) | name' == name = Field (name, f value)
modify field = field
raiseFields :: (Eq a) => (a -> Bool) -> Paragraph' a -> Paragraph' a
raiseFields f (Paragraph fields) =
let (a, b) = partition f' fields in Paragraph (a ++ b)
where f' (Field (name, _)) = f name
f' (Comment _) = False
parseControlFromCmd :: ControlFunctions a => String -> IO (Either String (Control' a))
parseControlFromCmd cmd =
do
(_, outh, _, handle) <- runInteractiveCommand cmd
result <- parseControlFromHandle cmd outh
either (return . Left . show) (finish handle) result
where
finish handle control =
do
exitCode <- waitForProcess handle
case exitCode of
ExitSuccess -> return $ Right control
ExitFailure n -> return $ Left ("Failure: " ++ cmd ++ " -> " ++ show n)
md5sumField :: (ControlFunctions a) => Paragraph' a -> Maybe a
md5sumField p = msum [fieldValue "MD5Sum" p, fieldValue "Md5Sum" p, fieldValue "MD5sum" p]