{- arch-tag: Debian Package utilities main file
Copyright (c) 2004-2011 John Goerzen <jgoerzen@complete.org>

All rights reserved.

For license and copyright information, see the file LICENSE
-}

{- |
   Module     : System.Debian
   Copyright  : Copyright (C) 2004-2011 John Goerzen
   SPDX-License-Identifier: BSD-3-Clause

   Stability  : stable
   Portability: portable

This module provides various helpful utilities for dealing with Debian
files and programs.

Written by John Goerzen, jgoerzen\@complete.org
-}

module System.Debian (-- * Control or Similar File Utilities
                        ControlFile,
                        -- * Version Number Utilities
                        DebVersion, compareDebVersion, checkDebVersion
                       )
    where

import System.Exit ( ExitCode(ExitFailure, ExitSuccess) )
import System.IO.Unsafe (unsafePerformIO)
import System.Process ( rawSystem )

{- | The type representing the contents of a Debian control file,
or any control-like file (such as the output from apt-cache show, etc.) -}
type ControlFile = [(String, String)]

----------------------------------------------------------------------
-- VERSION NUMBERS
----------------------------------------------------------------------

{- | The type representing a Debian version number.  This type is an instance
of 'Prelude.Ord', but you can also use 'compareDebVersion' if you prefer.

__WARNING__: calls out to @dpkg@ and will throw exceptions if @dpkg@ is missing
-}
data DebVersion = DebVersion String
                deriving (DebVersion -> DebVersion -> Bool
(DebVersion -> DebVersion -> Bool)
-> (DebVersion -> DebVersion -> Bool) -> Eq DebVersion
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DebVersion -> DebVersion -> Bool
== :: DebVersion -> DebVersion -> Bool
$c/= :: DebVersion -> DebVersion -> Bool
/= :: DebVersion -> DebVersion -> Bool
Eq)
instance Ord DebVersion where
    compare :: DebVersion -> DebVersion -> Ordering
compare (DebVersion [Char]
v1) (DebVersion [Char]
v2) =
        {- This is OK since compareDebVersion should always be the same. -}
        IO Ordering -> Ordering
forall a. IO a -> a
unsafePerformIO (IO Ordering -> Ordering) -> IO Ordering -> Ordering
forall a b. (a -> b) -> a -> b
$ [Char] -> [Char] -> IO Ordering
compareDebVersion [Char]
v1 [Char]
v2

{- | Compare the versions of two packages. -}
compareDebVersion :: String -> String -> IO Ordering
compareDebVersion :: [Char] -> [Char] -> IO Ordering
compareDebVersion [Char]
v1 [Char]
v2 =
    let runit :: [Char] -> IO Bool
runit [Char]
op = [Char] -> [Char] -> [Char] -> IO Bool
checkDebVersion [Char]
v1 [Char]
op [Char]
v2
        in do islt <- [Char] -> IO Bool
runit [Char]
"lt"
              if islt
                 then return LT
                 else do isgt <- runit "gt"
                         if isgt
                            then return GT
                            else return EQ

checkDebVersion :: String       -- ^ Version 1
                -> String       -- ^ Operator
                -> String       -- ^ Version 2
                -> IO Bool
checkDebVersion :: [Char] -> [Char] -> [Char] -> IO Bool
checkDebVersion [Char]
v1 [Char]
op [Char]
v2 =
    do ec <- [Char] -> [[Char]] -> IO ExitCode
rawSystem [Char]
"dpkg" [[Char]
"--compare-versions", [Char]
v1, [Char]
op, [Char]
v2]
       case ec of
               ExitCode
ExitSuccess   -> Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
               ExitFailure Int
_ -> Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False