module System.Debian (
ControlFile,
DebVersion, compareDebVersion, checkDebVersion
)
where
import System.Exit ( ExitCode(ExitFailure, ExitSuccess) )
import System.IO.Unsafe (unsafePerformIO)
import System.Process ( rawSystem )
type ControlFile = [(String, String)]
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) =
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
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
-> String
-> String
-> 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