List installed packages from a repository
All checks were successful
Build / audit (push) Successful in 9s
Build / test (push) Successful in 16m24s

This commit is contained in:
Eugen Wissner 2024-11-25 17:08:28 +01:00
parent b5e6e3a2d6
commit 468852410e
Signed by: belka
GPG Key ID: A27FDC1E8EE902C0
7 changed files with 103 additions and 38 deletions

View File

@ -7,6 +7,7 @@ module SlackBuilder.Info
( PackageInfo(..) ( PackageInfo(..)
, generate , generate
, parseInfoFile , parseInfoFile
, readInfoFile
) where ) where
import Control.Applicative (Alternative(..)) import Control.Applicative (Alternative(..))
@ -26,7 +27,7 @@ import Crypto.Hash (Digest, MD5, digestFromByteString)
import Data.Void (Void) import Data.Void (Void)
import Data.Word (Word8) import Data.Word (Word8)
import Numeric (readHex, showHex) import Numeric (readHex, showHex)
import Text.Megaparsec (Parsec, count, eof, takeWhile1P) import Text.Megaparsec (Parsec, count, eof, parse, takeWhile1P)
import Text.Megaparsec.Byte (space, string, hexDigitChar) import Text.Megaparsec.Byte (space, string, hexDigitChar)
import Text.URI import Text.URI
( URI(..) ( URI(..)
@ -34,6 +35,14 @@ import Text.URI
, render , render
) )
import qualified Data.Word8 as Word8 import qualified Data.Word8 as Word8
import SlackBuilder.Trans
( SlackBuilderT(..)
, SlackBuilderException(..)
, relativeToRepository
)
import System.FilePath ((</>), (<.>))
import Control.Monad.IO.Class (MonadIO(..))
import Conduit (MonadThrow(throwM))
type GenParser = Parsec Void ByteString type GenParser = Parsec Void ByteString
@ -110,6 +119,17 @@ parseInfoFile = PackageInfo . Char8.unpack
*> packageName *> packageName
<* "\"\n" <* "\"\n"
readInfoFile :: Text -> Text -> SlackBuilderT PackageInfo
readInfoFile category packageName' = do
let packageName'' = Text.unpack packageName'
infoPath <- relativeToRepository
$ Text.unpack category </> packageName'' </> packageName'' <.> "info"
infoContents <- liftIO $ ByteString.readFile infoPath
either (throwM . MalformedInfoFile) pure
$ parse parseInfoFile infoPath infoContents
generate :: PackageInfo -> Text generate :: PackageInfo -> Text
generate pkg = Lazy.Text.toStrict $ Text.Builder.toLazyText builder generate pkg = Lazy.Text.toStrict $ Text.Builder.toLazyText builder
where where

View File

@ -5,7 +5,8 @@
-- | Contains data describing packages, methods to update them and to request -- | Contains data describing packages, methods to update them and to request
-- information about them. -- information about them.
module SlackBuilder.Package module SlackBuilder.Package
( Download(..) ( DataBaseEntry(..)
, Download(..)
, DownloadTemplate(..) , DownloadTemplate(..)
, PackageDescription(..) , PackageDescription(..)
, PackageUpdateData(..) , PackageUpdateData(..)
@ -66,3 +67,15 @@ data Updater = Updater
, is64 :: Bool , is64 :: Bool
, getVersion :: Text -> Text -> SlackBuilderT Download , getVersion :: Text -> Text -> SlackBuilderT Download
} }
data DataBaseEntry = DataBaseEntry
{ name :: Text
, version :: Text
, arch :: Text
, build :: Text
} deriving Eq
instance Show DataBaseEntry
where
show DataBaseEntry{..} = Text.unpack
$ Text.intercalate "-" [name, version, arch, build]

View File

@ -10,6 +10,7 @@ module SlackBuilder.Trans
) where ) where
import Control.Monad.Trans.Reader (ReaderT(..), asks) import Control.Monad.Trans.Reader (ReaderT(..), asks)
import Data.ByteString (ByteString)
import Data.Text (Text) import Data.Text (Text)
import qualified Data.Text as Text import qualified Data.Text as Text
import SlackBuilder.Config import SlackBuilder.Config
@ -20,11 +21,14 @@ import System.FilePath ((</>))
import Text.URI (URI) import Text.URI (URI)
import qualified Text.URI as URI import qualified Text.URI as URI
import qualified Codec.Compression.Lzma as Lzma import qualified Codec.Compression.Lzma as Lzma
import Text.Megaparsec (ParseErrorBundle(..), errorBundlePretty)
import Conduit (Void)
data SlackBuilderException data SlackBuilderException
= UpdaterNotFound Text = UpdaterNotFound Text
| UnsupportedUrlType URI | UnsupportedUrlType URI
| LzmaDecompressionFailed Lzma.LzmaRet | LzmaDecompressionFailed Lzma.LzmaRet
| MalformedInfoFile (ParseErrorBundle ByteString Void)
deriving Show deriving Show
instance Exception SlackBuilderException instance Exception SlackBuilderException
@ -55,6 +59,8 @@ instance Exception SlackBuilderException
"No progress is possible" "No progress is possible"
displayException (LzmaDecompressionFailed Lzma.LzmaRetProgError) = displayException (LzmaDecompressionFailed Lzma.LzmaRetProgError) =
"Programming error" "Programming error"
displayException (MalformedInfoFile errorBundle) =
errorBundlePretty errorBundle
newtype SlackBuilderT a = SlackBuilderT newtype SlackBuilderT a = SlackBuilderT
{ runSlackBuilderT :: ReaderT Settings IO a { runSlackBuilderT :: ReaderT Settings IO a

View File

@ -76,7 +76,7 @@ library
hs-source-dirs: lib hs-source-dirs: lib
ghc-options: -Wall ghc-options: -Wall
build-depends: build-depends:
mono-traversable ^>= 1.0.17 mono-traversable ^>= 1.0.17
executable slackbuilder executable slackbuilder
import: dependencies import: dependencies

View File

@ -17,6 +17,7 @@ import SlackBuilder.LatestVersionCheck
import SlackBuilder.Update import SlackBuilder.Update
import qualified Toml import qualified Toml
import Data.Text (Text) import Data.Text (Text)
import qualified Data.Text as Text
import qualified Data.Text.IO as Text import qualified Data.Text.IO as Text
import Control.Monad.Trans.Reader (ReaderT(..), asks) import Control.Monad.Trans.Reader (ReaderT(..), asks)
import SlackBuilder.Package (PackageDescription(..), renderTextWithVersion) import SlackBuilder.Package (PackageDescription(..), renderTextWithVersion)
@ -32,6 +33,9 @@ import System.Console.ANSI
) )
import Data.Maybe (mapMaybe) import Data.Maybe (mapMaybe)
import qualified Text.URI as URI import qualified Text.URI as URI
import System.Directory (listDirectory)
import qualified Data.HashMap.Strict as HashMap
import SlackBuilder.Info (readInfoFile)
autoUpdatable :: [PackageSettings] -> [PackageDescription] autoUpdatable :: [PackageSettings] -> [PackageDescription]
autoUpdatable = mapMaybe go autoUpdatable = mapMaybe go
@ -97,6 +101,31 @@ check = SlackBuilderT (asks (getField @"packages"))
>>= mapM_ checkUpdateAvailability >>= mapM_ checkUpdateAvailability
>> liftIO (putStrLn "") >> liftIO (putStrLn "")
installed :: SlackBuilderT ()
installed = do
listing <- listRepository
database <- foldr createDataBase HashMap.empty . mapMaybe createEntry
<$> liftIO (listDirectory "/var/lib/pkgtools/packages")
traverse_ findInfo $ HashMap.intersectionWith (,) database listing
where
findInfo (installed'@Package.DataBaseEntry{ name }, fromRepository) = do
_ <- readInfoFile fromRepository name
liftIO $ print installed'
createDataBase entry@Package.DataBaseEntry{ name } =
HashMap.insert name entry
createEntry filename = createEntryFromChunks
$ Text.split (== '-')
$ Text.reverse
$ Text.pack filename
createEntryFromChunks (build : arch : version : name) = Just
Package.DataBaseEntry
{ arch = Text.reverse arch
, build = Text.reverse build
, version = Text.reverse version
, name = Text.reverse (Text.intercalate "-" name)
}
createEntryFromChunks _ = Nothing
main :: IO () main :: IO ()
main = execParser slackBuilderParser main = execParser slackBuilderParser
>>= handle handleException . withCommandLine >>= handle handleException . withCommandLine
@ -116,3 +145,4 @@ main = execParser slackBuilderParser
executeCommand = \case executeCommand = \case
CheckCommand -> check CheckCommand -> check
Up2DateCommand packageName -> up2Date packageName Up2DateCommand packageName -> up2Date packageName
InstalledCommand -> installed

View File

@ -25,6 +25,7 @@ import Options.Applicative
data SlackBuilderCommand data SlackBuilderCommand
= CheckCommand = CheckCommand
| Up2DateCommand (Maybe Text) | Up2DateCommand (Maybe Text)
| InstalledCommand
slackBuilderParser :: ParserInfo SlackBuilderCommand slackBuilderParser :: ParserInfo SlackBuilderCommand
slackBuilderParser = info slackBuilderCommand fullDesc slackBuilderParser = info slackBuilderCommand fullDesc
@ -33,7 +34,9 @@ slackBuilderCommand :: Parser SlackBuilderCommand
slackBuilderCommand = subparser slackBuilderCommand = subparser
$ command "check" (info checkCommand mempty) $ command "check" (info checkCommand mempty)
<> command "up2date" (info up2DateCommand mempty) <> command "up2date" (info up2DateCommand mempty)
<> command "installed" (info installedCommand mempty)
where where
checkCommand = pure CheckCommand checkCommand = pure CheckCommand
up2DateCommand = Up2DateCommand up2DateCommand = Up2DateCommand
<$> optional (argument str (metavar "PKGNAM")) <$> optional (argument str (metavar "PKGNAM"))
installedCommand = pure InstalledCommand

View File

@ -8,6 +8,7 @@ module SlackBuilder.Update
, downloadWithTemplate , downloadWithTemplate
, getAndLogLatest , getAndLogLatest
, handleException , handleException
, listRepository
, repackageWithTemplate , repackageWithTemplate
, reuploadWithTemplate , reuploadWithTemplate
, updatePackageIfRequired , updatePackageIfRequired
@ -17,8 +18,9 @@ import Control.Exception (Exception(..), SomeException(..))
import Control.Monad.Catch (MonadCatch(..)) import Control.Monad.Catch (MonadCatch(..))
import Control.Monad.IO.Class (MonadIO(..)) import Control.Monad.IO.Class (MonadIO(..))
import Control.Monad.Trans.Reader (asks) import Control.Monad.Trans.Reader (asks)
import qualified Data.ByteString as ByteString
import Data.Foldable (Foldable(..), find) import Data.Foldable (Foldable(..), find)
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HashMap
import qualified Data.List.NonEmpty as NonEmpty import qualified Data.List.NonEmpty as NonEmpty
import Data.Maybe (fromJust, fromMaybe) import Data.Maybe (fromJust, fromMaybe)
import Data.Text (Text) import Data.Text (Text)
@ -48,7 +50,6 @@ import SlackBuilder.Info
import SlackBuilder.Package (PackageDescription(..), PackageUpdateData(..)) import SlackBuilder.Package (PackageDescription(..), PackageUpdateData(..))
import qualified SlackBuilder.Package as Package import qualified SlackBuilder.Package as Package
import SlackBuilder.Trans import SlackBuilder.Trans
import Text.Megaparsec (parse, errorBundlePretty)
import Text.URI (URI(..)) import Text.URI (URI(..))
import qualified Text.URI as URI import qualified Text.URI as URI
import System.Directory import System.Directory
@ -74,41 +75,32 @@ getAndLogLatest description = do
let PackageDescription{ latest = Package.Updater{ detectLatest }, name } = description let PackageDescription{ latest = Package.Updater{ detectLatest }, name } = description
liftIO (putStrLn $ Text.unpack name <> ": Retreiving the latest version.") liftIO (putStrLn $ Text.unpack name <> ": Retreiving the latest version.")
detectedVersion <- detectLatest detectedVersion <- detectLatest
category <- fmap Text.pack category <- HashMap.lookup name <$> listRepository
<$> findCategory (Text.unpack name)
pure $ PackageUpdateData description pure $ PackageUpdateData description
<$> category <$> category
<*> detectedVersion <*> detectedVersion
checkUpdateAvailability :: PackageUpdateData -> SlackBuilderT (Maybe PackageInfo) checkUpdateAvailability :: PackageUpdateData -> SlackBuilderT (Maybe PackageInfo)
checkUpdateAvailability PackageUpdateData{..} = do checkUpdateAvailability PackageUpdateData{..} = do
let name' = Text.unpack $ getField @"name" description parsedInfoFile <- readInfoFile category $ getField @"name" description
packagePath = Text.unpack category </> name' </> (name' <.> "info")
repository' <- SlackBuilderT $ asks repository
infoContents <- liftIO $ ByteString.readFile $ repository' </> packagePath
case parse parseInfoFile packagePath infoContents of if version == getField @"version" parsedInfoFile
Right parsedInfoFile then liftIO $ do
| version == getField @"version" parsedInfoFile -> setSGR [SetColor Foreground Dull Green]
liftIO $ do Text.IO.putStrLn
setSGR [SetColor Foreground Dull Green] $ getField @"name" description <> " is up to date (Version " <> version <> ")."
Text.IO.putStrLn setSGR [Reset]
$ getField @"name" description <> " is up to date (Version " <> version <> ")." pure Nothing
setSGR [Reset] else liftIO $ do
pure Nothing setSGR [SetColor Foreground Dull Yellow]
| otherwise -> Text.IO.putStr
liftIO $ do $ "A new version of "
setSGR [SetColor Foreground Dull Yellow] <> getField @"name" description
Text.IO.putStr <> " " <> getField @"version" parsedInfoFile
$ "A new version of " <> " is available (" <> version <> ")."
<> getField @"name" description setSGR [Reset]
<> " " <> getField @"version" parsedInfoFile putStrLn ""
<> " is available (" <> version <> ")." pure $ Just parsedInfoFile
setSGR [Reset]
putStrLn ""
pure $ Just parsedInfoFile
Left errorBundle -> liftIO (putStr $ errorBundlePretty errorBundle)
>> pure Nothing
updatePackageIfRequired :: PackageUpdateData -> SlackBuilderT () updatePackageIfRequired :: PackageUpdateData -> SlackBuilderT ()
updatePackageIfRequired updateData updatePackageIfRequired updateData
@ -252,19 +244,20 @@ updatePackage PackageUpdateData{..} info = do
commit packagePath version commit packagePath version
findCategory :: FilePath -> SlackBuilderT (Maybe FilePath) listRepository :: SlackBuilderT (HashMap Text Text)
findCategory packageName = do listRepository = do
repository' <- SlackBuilderT $ asks repository repository' <- SlackBuilderT $ asks repository
go repository' [] "" <&> fmap fst . find ((packageName ==) . snd) listing <- go repository' [] ""
pure $ HashMap.fromList $ bimap Text.pack Text.pack <$> listing
where where
go currentDirectory found accumulatedDirectory = do go currentDirectory found accumulatedDirectory = do
let fullDirectory = currentDirectory </> accumulatedDirectory let fullDirectory = currentDirectory </> accumulatedDirectory
contents <- liftIO $ listDirectory fullDirectory contents <- liftIO $ listDirectory fullDirectory
case find (isSuffixOf ".info") contents of case find (isSuffixOf ".info") contents of
Just _ -> Just _ ->
let result = first dropTrailingPathSeparator let (category, packageName) = first dropTrailingPathSeparator
$ splitFileName accumulatedDirectory $ splitFileName accumulatedDirectory
in pure $ result : found in pure $ (packageName, category) : found
Nothing -> Nothing ->
let accumulatedDirectories = (accumulatedDirectory </>) let accumulatedDirectories = (accumulatedDirectory </>)
<$> filter (not . isPrefixOf ".") contents <$> filter (not . isPrefixOf ".") contents