{- 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
import           System.IO.Unsafe (unsafePerformIO)
import           System.Process

{- | 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
/= :: DebVersion -> DebVersion -> Bool
$c/= :: DebVersion -> DebVersion -> Bool
== :: DebVersion -> DebVersion -> Bool
$c== :: DebVersion -> DebVersion -> Bool
Eq)
instance Ord DebVersion where
    compare :: DebVersion -> DebVersion -> Ordering
compare (DebVersion String
v1) (DebVersion String
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
$ String -> String -> IO Ordering
compareDebVersion String
v1 String
v2

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

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