{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
module Debian.Deb where

import Control.Monad

import Debian.Control.Common
import System.Directory (canonicalizePath, withCurrentDirectory)
import System.Exit (ExitCode(..))
import System.Process (readProcessWithExitCode)
import System.IO.Temp (withSystemTempDirectory)

fields :: (ControlFunctions a) => FilePath -> IO (Control' a)
fields :: forall a. ControlFunctions a => FilePath -> IO (Control' a)
fields FilePath
debFP =
    forall (m :: * -> *) a.
(MonadIO m, MonadMask m) =>
FilePath -> (FilePath -> m a) -> m a
withSystemTempDirectory (FilePath
"fields.XXXXXX") forall a b. (a -> b) -> a -> b
$ \FilePath
tmpdir ->
      do FilePath
debFP <- FilePath -> IO FilePath
canonicalizePath FilePath
debFP
         forall a. FilePath -> IO a -> IO a
withCurrentDirectory FilePath
tmpdir forall a b. (a -> b) -> a -> b
$
           do (ExitCode
res, FilePath
out, FilePath
err) <- FilePath
-> [FilePath] -> FilePath -> IO (ExitCode, FilePath, FilePath)
readProcessWithExitCode FilePath
"ar" [FilePath
"x",FilePath
debFP,FilePath
"control.tar.gz"] FilePath
""
              forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (ExitCode
res forall a. Eq a => a -> a -> Bool
/= ExitCode
ExitSuccess) (forall a. HasCallStack => FilePath -> a
error forall a b. (a -> b) -> a -> b
$ FilePath
"Dpkg.fields: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> FilePath
show FilePath
out forall a. [a] -> [a] -> [a]
++ FilePath
"\n" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> FilePath
show FilePath
err forall a. [a] -> [a] -> [a]
++ FilePath
"\n" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> FilePath
show ExitCode
res)
              (ExitCode
res, FilePath
out, FilePath
err) <- FilePath
-> [FilePath] -> FilePath -> IO (ExitCode, FilePath, FilePath)
readProcessWithExitCode FilePath
"tar" [FilePath
"xzf", FilePath
"control.tar.gz", FilePath
"./control"] FilePath
""
              forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (ExitCode
res forall a. Eq a => a -> a -> Bool
/= ExitCode
ExitSuccess) (forall a. HasCallStack => FilePath -> a
error forall a b. (a -> b) -> a -> b
$ FilePath
"Dpkg.fields: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> FilePath
show FilePath
out forall a. [a] -> [a] -> [a]
++ FilePath
"\n" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> FilePath
show FilePath
err forall a. [a] -> [a] -> [a]
++ FilePath
"\n" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> FilePath
show ExitCode
res)
              Either ParseError (Control' a)
c <- forall a.
ControlFunctions a =>
FilePath -> IO (Either ParseError (Control' a))
parseControlFromFile FilePath
"control"
              case Either ParseError (Control' a)
c of
                Left ParseError
e -> forall a. HasCallStack => FilePath -> a
error (forall a. Show a => a -> FilePath
show ParseError
e)
                (Right Control' a
c) -> forall (m :: * -> *) a. Monad m => a -> m a
return Control' a
c -- I don't think we need seq because parsec will force everything from the file