module Resource.Compressed.Zstd where import RIO import RIO.FilePath (takeExtension) import RIO.ByteString qualified as ByteString import Codec.Compression.Zstd qualified as Zstd data CompressedError = EmptyFile FilePath | ZstdError Text deriving (Eq, Show) instance Exception CompressedError fromFileWith :: MonadIO m => (ByteString -> m b) -> (FilePath -> m b) -> FilePath -> m b fromFileWith withBS withFilePath filePath | elem (takeExtension filePath) compressedExts = loadCompressed withBS filePath | otherwise = withFilePath filePath loadCompressed :: MonadIO m => (ByteString -> m b) -> FilePath -> m b loadCompressed withBS filePath = do yeet'd <- ByteString.readFile filePath case Zstd.decompress yeet'd of Zstd.Skip -> throwIO $ EmptyFile filePath Zstd.Error str -> throwIO $ ZstdError (fromString str) Zstd.Decompress buf -> withBS buf compressedExts :: [FilePath] compressedExts = [ ".zst" , ".zstd" ]