{-# LANGUAGE PackageImports, ScopedTypeVariables, TupleSections #-} {-# OPTIONS -fno-warn-name-shadowing #-} module Debian.Repo.Package.ToSourcePackage ( toSourcePackage ) where import Data.List as List (intercalate, map, partition) import Data.Maybe (catMaybes) import qualified Data.Text as T (Text, unpack) import Debian.Control (formatParagraph) import qualified Debian.Control.Text as B (fieldValue, Paragraph) import Debian.Repo.Package.Internal.ParseSourceParagraph (parseSourceParagraph) import Debian.Repo.Types.PackageIndex (makeSourcePackageID, PackageIndex, SourceFileSpec(SourceFileSpec), SourcePackage(..)) import Debian.Version (parseDebianVersion) toSourcePackage :: PackageIndex -> B.Paragraph -> SourcePackage toSourcePackage index package = case (B.fieldValue "Directory" package, B.fieldValue "Files" package, B.fieldValue "Package" package, maybe Nothing (Just . parseDebianVersion . T.unpack) (B.fieldValue "Version" package)) of (Just directory, Just files, Just name, Just version) -> case (parseSourcesFileList files, parseSourceParagraph package) of (Right files', Right para) -> SourcePackage { sourcePackageID = makeSourcePackageID (T.unpack name) version , sourceParagraph = package , sourceControl = para , sourceDirectory = T.unpack directory , sourcePackageFiles = files' } (Left messages, _) -> error $ "Invalid file list: " ++ show messages (_, Left messages) -> error $ "Error in source paragraph\n package=" ++ show package ++ "\n index=" ++ show index ++ "\n messages:\n " ++ intercalate "\n " messages x -> error $ "Missing info in source package control information in " ++ show index ++ " -> " ++ show x ++ " :\n" ++ T.unpack (formatParagraph package) where -- Parse the list of files in a paragraph of a Sources index. parseSourcesFileList :: T.Text -> Either [String] [SourceFileSpec] parseSourcesFileList text = merge . catMaybes . List.map parseSourcesFiles . lines . T.unpack $ text parseSourcesFiles line = case words line of [md5sum, size, name] -> Just (Right (SourceFileSpec md5sum (read size) name)) [] -> Nothing _ -> Just (Left ("Invalid line in Files list: '" ++ show line ++ "'")) merge x = case partition (either (const True) (const False)) x of (a, []) -> Left . catMaybes . List.map (either Just (const Nothing )) $ a (_, a) -> Right . catMaybes . List.map (either (const Nothing) Just) $ a