Navigation Menu

Skip to content

Instantly share code, notes, and snippets.

@TerrorJack
Created October 19, 2022 13:29
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save TerrorJack/6f6b54a2e7a373b1e011142168f6e5f0 to your computer and use it in GitHub Desktop.
Save TerrorJack/6f6b54a2e7a373b1e011142168f6e5f0 to your computer and use it in GitHub Desktop.
{-# LANGUAGE RecordWildCards #-}
import qualified Data.ByteString as BS
import Data.Foldable
import Data.Functor
import Data.Maybe
import Data.Set (Set)
import qualified Data.Set as S
import GHC.SysTools.Ar
import System.Environment.Blank
import System.FilePath
freshFileName :: Set FilePath -> FilePath -> FilePath
freshFileName fs f =
fromJust $
find
(not . (`S.member` fs))
(f : [(b <.> show i) <.> e | i <- [1 :: Int ..]])
where
(b, e) = splitExtension f
main :: IO ()
main = do
[ar_path] <- getArgs
Archive objs <- loadAr ar_path
void $
foldlM
( \fs ArchiveEntry {..} -> do
let f = freshFileName fs filename
BS.writeFile f filedata
pure $ f `S.insert` fs
)
S.empty
objs
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment