Compare commits

...

18 Commits

Author SHA1 Message Date
Michele Guerini Rocco 61d91f1e07
cabal: increase version number 2022-01-11 01:22:39 +01:00
Michele Guerini Rocco cca7577aa9
default.nix: update static compiler 2022-01-11 01:22:39 +01:00
Michele Guerini Rocco 1b39e2b060
update copyright year 2022-01-11 01:22:39 +01:00
Michele Guerini Rocco 492be78d5a
ignore cabal2nix generated file 2022-01-11 01:22:39 +01:00
Michele Guerini Rocco dbeabf939f
ignore Nix result link 2022-01-11 01:22:39 +01:00
Michele Guerini Rocco 2ddb95ac0d
ignore cabal v2 build directory 2022-01-11 01:22:39 +01:00
Michele Guerini Rocco 9ae6058851
turn on GHC optimisations 2022-01-11 01:22:39 +01:00
Michele Guerini Rocco 6f371de3aa
fix some warnings 2022-01-11 01:22:39 +01:00
Michele Guerini Rocco 05e930a0a5
add option to bypass locks 2022-01-11 01:02:09 +01:00
Michele Guerini Rocco 41feee9b37
warn about failed actions 2021-09-07 15:00:55 +02:00
Michele Guerini Rocco a0c17c434a
add --version option 2021-09-07 15:00:55 +02:00
Michele Guerini Rocco 3b6ad40a02
doc: add manual pages 2021-09-07 15:00:55 +02:00
Michele Guerini Rocco d131fc510e
cabal: increase version number 2021-09-07 11:25:12 +02:00
Michele Guerini Rocco e16a6e42d6
improve release setup
- use a build flag to turn on static system libraries
- generate shell completion scripts
- externalise the generate cabal2nix function
2021-09-07 11:24:56 +02:00
Michele Guerini Rocco 2fcb4eae1e
README: mention the new options 2021-09-07 01:55:26 +02:00
Michele Guerini Rocco 6c3e5a5c4e
change verb when dry-running 2021-09-07 01:55:26 +02:00
Michele Guerini Rocco cfe3ac83eb
cabal: build with -Wall 2021-09-07 01:55:26 +02:00
Michele Guerini Rocco 5de13cdc3d
add config and dry-run options 2021-09-07 01:55:26 +02:00
8 changed files with 409 additions and 128 deletions

0
.ghc/ghci_history Normal file
View File

3
.gitignore vendored
View File

@ -1 +1,4 @@
dist dist
dist-newstyle
result
bisc.nix

302
Main.hs
View File

@ -4,41 +4,100 @@
{-# LANGUAGE OverloadedLabels #-} {-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE MultiWayIf #-}
import Data.List (nub, foldl') -- Databases
import Data.Maybe (mapMaybe) import Database.Selda (Text, liftIO, (!))
import Data.Function ((&)) import Database.Selda.SQLite (withSQLite)
import Data.Default (def) import Control.Monad.Trans.Resource (ResourceT)
import Data.Text.Encoding (decodeUtf8)
import Control.Monad (mapM_, when, (>=>))
import Control.Monad.Reader (ReaderT, runReaderT, asks)
import Control.Monad.Except (ExceptT, runExceptT, throwError)
import System.FilePath (joinPath, takeBaseName, (</>))
import Database.Selda (Text, liftIO, (.||), (!))
import Database.Selda.SQLite (withSQLite)
import qualified Database.Selda as S import qualified Database.Selda as S
import qualified Database.LevelDB as L import qualified Database.LevelDB as L
import qualified Database.LevelDB.Streaming as LS import qualified Database.LevelDB.Streaming as LS
import Control.Exception as BE -- Error handling
import Control.Monad.Catch as CE import Control.Exception as BE
import Control.Monad.Catch as CE
import qualified System.Exit as E
import qualified System.Directory as D -- Configuration
import qualified Data.Configurator as C import qualified Options.Applicative as O
import qualified System.Directory as D
import qualified Data.Configurator as C
-- Text converion
import Data.Text.Encoding (decodeUtf8)
import qualified Data.Text as T import qualified Data.Text as T
import qualified Data.Text.IO as T import qualified Data.Text.IO as T
import qualified Data.ByteString as B import qualified Data.ByteString as B
import Debug.Trace -- Version information
import qualified Paths_bisc as Bisc
import Data.Version (showVersion)
-- | Bisc settings -- File locking bypass
import qualified System.Posix.Files as Posix
-- Misc
import Data.List (nub, isInfixOf)
import Data.Maybe (mapMaybe)
import Data.Function ((&))
import Data.Default (def)
import Control.Monad (when)
import Control.Monad.Reader (ReaderT, runReaderT, asks)
import Control.Monad.Except (ExceptT, runExceptT, throwError)
import System.FilePath (joinPath, takeBaseName, (</>))
-- Options
-- | Configuration file settings
data Settings = Settings data Settings = Settings
{ whitelistPath :: FilePath -- ^ whitelist file { webenginePath :: FilePath -- ^ webengine data directory
, webenginePath :: FilePath -- ^ webengine data directory
, whitelist :: [Text] -- ^ whitelisted domains , whitelist :: [Text] -- ^ whitelisted domains
, options :: Options -- ^ cli options
} }
-- | Command line options
data Options = Options
{ version :: Bool -- ^ print version number
, dryRun :: Bool -- ^ don't delete anything
, unsafe :: Bool -- ^ ignore locks
, configPath :: FilePath -- ^ config file path
}
-- | Command line parser
cliParser :: FilePath -> O.ParserInfo Options
cliParser defConfig = O.info (O.helper <*> parser) infos
where
parser = Options
<$> O.switch
( O.long "version"
<> O.short 'v'
<> O.help "Print the version number and exit"
)
<*> O.switch
( O.long "dry-run"
<> O.short 'n'
<> O.help ("Don't actually remove anything, "<>
"just show what would be done")
)
<*> O.switch
( O.long "unsafe"
<> O.short 'u'
<> O.help ("Ignore database locks. " <>
"This will probably corrupt the databases, but " <>
"works while the browser is running.")
)
<*> O.strOption
( O.long "config"
<> O.short 'c'
<> O.value defConfig
<> O.help "Specify a configuration file"
)
infos =
O.fullDesc <>
O.progDesc "A small tool that clears cookies (and more)"
-- SQL records -- SQL records
@ -68,6 +127,7 @@ cookies = S.table "cookies" []
quotaOrigins :: S.Table QuotaOrigin quotaOrigins :: S.Table QuotaOrigin
quotaOrigins = S.table "OriginInfoTable" [] quotaOrigins = S.table "OriginInfoTable" []
-- | Main monad stack -- | Main monad stack
-- --
-- * 'ReaderT' for accessing settings -- * 'ReaderT' for accessing settings
@ -83,49 +143,79 @@ type Result = (Int, [Text])
-- | Clears all means of permanent storage -- | Clears all means of permanent storage
main :: IO () main :: IO ()
main = do main = do
config <- D.getXdgDirectory D.XdgConfig ("bisc" </> "bisc.conf") defConfig <- D.getXdgDirectory D.XdgConfig ("bisc" </> "bisc.conf")
run <- runAction <$> loadSettings config opts <- O.execParser (cliParser defConfig)
run "Cookies" deleteCookies
run "QuotaManager" deleteQuotaOrigins when (version opts) $ do
run "IndexedDB" deleteIndexedDB putStrLn ("bisc " <> showVersion Bisc.version)
run "LocalStorage" deleteLocalStorage E.exitSuccess
run "SessionStorage" deleteSessionStorage
run <- runAction <$> loadSettings opts
numFailures <- sum <$> mapM (uncurry run) actions
if numFailures == 0
then E.exitSuccess
else do
putStrLn ("\nwarning: " <> show numFailures <> " actions have failed")
E.exitWith (E.ExitFailure numFailures)
-- | Runs an 'Action' and pretty-prints the results -- | Runs an 'Action' and pretty-prints the results
runAction :: Settings -> Text -> Action Result -> IO () runAction :: Settings -> Text -> Action Result -> IO Int
runAction settings name x = do runAction settings name x = do
a <- BE.try $ runExceptT (runReaderT x settings) a <- BE.try $ runExceptT (runReaderT x settings)
case a of case a of
Right (Right res) -> printResult res Right (Right res) -> printResult res >> return 0
Right (Left msg) -> printFailed msg Right (Left msg) -> printFailed msg >> return 1
Left (err :: BE.IOException) -> printFailed (T.pack $ BE.displayException err) Left (err :: BE.IOException) ->
printFailed (T.pack $ BE.displayException err) >> return 1
where where
printFailed msg = T.putStrLn ("- " <> name <> " cleaning failed:\n " <> msg) printFailed msg =
T.putStrLn ("- " <> name <> " cleaning failed:\n " <> msg)
printResult (n, bad) printResult (n, bad)
| n > 0 = do | n > 0 = do
T.putStrLn ("- " <> name <> ": deleted " <> T.pack (show n) <> " entries for:") T.putStrLn ("- " <> name <> ": " <> verb <>
" " <> T.pack (show n) <> " entries for:")
T.putStrLn (T.unlines $ map (" * " <>) bad) T.putStrLn (T.unlines $ map (" * " <>) bad)
| otherwise = T.putStrLn ("- " <> name <> ": nothing to delete") | otherwise = T.putStrLn ("- " <> name <> ": nothing to delete")
verb = if (dryRun . options $ settings)
then "would delete"
else "deleted"
-- * Cleaning actions -- * Cleaning actions
-- | List of actions and their names
actions :: [(Text, Action Result)]
actions =
[ ("Cookies", deleteCookies)
, ("QuotaManager", deleteQuotaOrigins)
, ("IndexedDB", deleteIndexedDB)
, ("LocalStorage", deleteLocalStorage)
, ("SessionStorage", deleteSessionStorage)
]
-- | Deletes records in the Cookies database -- | Deletes records in the Cookies database
deleteCookies :: Action Result deleteCookies :: Action Result
deleteCookies = do deleteCookies = do
database <- (</> "Cookies") <$> asks webenginePath dir <- asks webenginePath
exists <- liftIO $ D.doesFileExist database dry <- asks (dryRun . options)
-- check for database
exists <- liftIO $ D.doesFileExist (dir </> "Cookies")
when (not exists) (throwError "database is missing") when (not exists) (throwError "database is missing")
whitelist <- map S.text <$> asks whitelist whitelist <- map S.text <$> asks whitelist
CE.handle dbErrors $ withSQLite database $ do withoutLocks "Cookies" $ \database -> do
bad <- S.query $ do CE.handle dbErrors $ withSQLite database $ do
cookie <- S.select cookies bad <- S.query $ do
S.restrict (by whitelist cookie) cookie <- S.select cookies
return (cookie ! #host_key) S.restrict (by whitelist cookie)
n <- S.deleteFrom cookies (by whitelist) return (cookie ! #host_key)
return (n, nub bad) when (not dry) $
S.deleteFrom_ cookies (by whitelist)
return (length bad, nub bad)
where where
by set x = S.not_ (x ! #host_key `S.isIn` set) by set x = S.not_ (x ! #host_key `S.isIn` set)
@ -133,18 +223,23 @@ deleteCookies = do
-- | Deletes records in the QuotaManager API database -- | Deletes records in the QuotaManager API database
deleteQuotaOrigins :: Action Result deleteQuotaOrigins :: Action Result
deleteQuotaOrigins = do deleteQuotaOrigins = do
database <- (</> "QuotaManager") <$> asks webenginePath dir <- asks webenginePath
exists <- liftIO $ D.doesFileExist database dry <- asks (dryRun . options)
-- check for database
exists <- liftIO $ D.doesFileExist (dir </> "QuotaManager")
when (not exists) (throwError "database is missing") when (not exists) (throwError "database is missing")
whitelist <- map pattern <$> asks whitelist whitelist <- map mkPattern <$> asks whitelist
CE.handle dbErrors $ withSQLite database $ do withoutLocks "QuotaManager" $ \database -> do
bad <- S.query $ do CE.handle dbErrors $ withSQLite database $ do
quota <- S.select quotaOrigins bad <- S.query $ do
S.restrict (by whitelist quota) quota <- S.select quotaOrigins
return (quota ! #origin) S.restrict (by whitelist quota)
n <- S.deleteFrom quotaOrigins (by whitelist) return (quota ! #origin)
return (n, nub bad) when (not dry) $
S.deleteFrom_ quotaOrigins (by whitelist)
return (length bad, nub bad)
where where
-- check if quota is not whitelisted -- check if quota is not whitelisted
by whitelist quota = S.not_ (S.true `S.isIn` matches) by whitelist quota = S.not_ (S.true `S.isIn` matches)
@ -155,8 +250,7 @@ deleteQuotaOrigins = do
S.restrict (url `S.like` S.the pattern) S.restrict (url `S.like` S.the pattern)
return S.true return S.true
-- turns domains into patterns to match a url -- turns domains into patterns to match a url
pattern domain = "http%://%" <> domain <> "/" mkPattern domain = "http%://%" <> domain <> "/"
-- | Deletes per-domain files under the IndexedDB directory -- | Deletes per-domain files under the IndexedDB directory
@ -169,15 +263,17 @@ deleteQuotaOrigins = do
deleteIndexedDB :: Action Result deleteIndexedDB :: Action Result
deleteIndexedDB = do deleteIndexedDB = do
webengine <- asks webenginePath webengine <- asks webenginePath
dry <- asks (dryRun . options)
exists <- liftIO $ D.doesDirectoryExist (webengine </> "IndexedDB") exists <- liftIO $ D.doesDirectoryExist (webengine </> "IndexedDB")
when (not exists) $ throwError "directory is missing" when (not exists) $ throwError "directory is missing"
entries <- listDirectoryAbs (webengine </> "IndexedDB") entries <- listDirectoryAbs (webengine </> "IndexedDB")
unlisted <- (\domains -> not . (`elem` domains)) <$> asks whitelist unlisted <- (\domains -> not . (`elem` domains)) <$> asks whitelist
let let
badFiles = filterMaybe (fmap unlisted . domain) entries badFiles = filterMaybe (fmap unlisted . domain) entries
badDomains = mapMaybe domain badFiles badDomains = mapMaybe domain badFiles
liftIO $ mapM_ D.removePathForcibly badFiles when (not dry) $
liftIO $ mapM_ D.removePathForcibly badFiles
return (length badFiles, nub badDomains) return (length badFiles, nub badDomains)
where where
listDirectoryAbs :: FilePath -> Action [FilePath] listDirectoryAbs :: FilePath -> Action [FilePath]
@ -193,8 +289,8 @@ deleteIndexedDB = do
domain :: FilePath -> Maybe Text domain :: FilePath -> Maybe Text
domain = extract . url where domain = extract . url where
extract [] = Nothing extract [] = Nothing
extract (x:[]) = Nothing extract (_:[]) = Nothing
extract (x:xs) = Just $ T.unwords (init xs) extract (_:xs) = Just $ T.unwords (init xs)
url = T.splitOn "_" . T.pack . takeBaseName url = T.splitOn "_" . T.pack . takeBaseName
@ -213,18 +309,29 @@ deleteLocalStorage = do
whitelist <- asks whitelist whitelist <- asks whitelist
let path = webengine </> "Local Storage" </> "leveldb" let path = webengine </> "Local Storage" </> "leveldb"
dry <- asks (dryRun . options)
unsafe <- asks (unsafe . options)
when (not dry && unsafe) $ liftIO $ do
-- delete and recreate the lock file to bypass POSIX locks
D.removeFile (path </> "LOCK")
T.writeFile (path </> "LOCK") ""
dbIsOk <- liftIO $ D.doesFileExist (path </> "LOCK") dbIsOk <- liftIO $ D.doesFileExist (path </> "LOCK")
when (not dbIsOk) (throwError "database is missing or corrupted") when (not dbIsOk) (throwError "database is missing or corrupted")
version <- withRetryDB path (\db -> L.get db def "VERSION") version <- withRetryDB path (\db -> L.get db def "VERSION")
when (version /= Just "1") (throwError "database is empty or the schema unsupported") when (version /= Just "1") (throwError "database is empty or the schema unsupported")
-- when dry running replace the delete function with a nop
let delete = if dry then (\_ _ _ -> pure ()) else L.delete
withDB path $ \db -> do withDB path $ \db -> do
badDomains <- L.withIterator db def $ \i -> badDomains <- L.withIterator db def $ \i ->
LS.keySlice i LS.AllKeys LS.Asc LS.keySlice i LS.AllKeys LS.Asc
& LS.filter (\k -> "META:" `B.isPrefixOf ` k & LS.filter (\k -> "META:" `B.isPrefixOf ` k
&& (metaDomain k) `notElem` whitelist) && (metaDomain k) `notElem` whitelist)
& LS.mapM (\k -> L.delete db def k >> return (metaDomain k)) & LS.mapM (\k -> delete db def k >> return (metaDomain k))
& LS.toList & LS.toList
n <- L.withIterator db def $ \i -> n <- L.withIterator db def $ \i ->
@ -232,7 +339,7 @@ deleteLocalStorage = do
& LS.filter (\k -> "_" `B.isPrefixOf` k & LS.filter (\k -> "_" `B.isPrefixOf` k
&& "\NUL\SOH" `B.isInfixOf` k && "\NUL\SOH" `B.isInfixOf` k
&& (recDomain k) `notElem` whitelist) && (recDomain k) `notElem` whitelist)
& LS.mapM (L.delete db def) & LS.mapM (delete db def)
& LS.length & LS.length
return (n, badDomains) return (n, badDomains)
@ -258,12 +365,23 @@ deleteSessionStorage = do
whitelist <- asks whitelist whitelist <- asks whitelist
let path = webengine </> "Session Storage" let path = webengine </> "Session Storage"
dry <- asks (dryRun . options)
unsafe <- asks (unsafe . options)
when (not dry && unsafe) $ liftIO $ do
-- delete and recreate the lock file to bypass POSIX locks
D.removeFile (path </> "LOCK")
T.writeFile (path </> "LOCK") ""
dbIsOk <- liftIO $ D.doesFileExist (path </> "LOCK") dbIsOk <- liftIO $ D.doesFileExist (path </> "LOCK")
when (not dbIsOk) (throwError "database is missing or corrupted") when (not dbIsOk) (throwError "database is missing or corrupted")
version <- withRetryDB path (\db -> L.get db def "version") version <- withRetryDB path (\db -> L.get db def "version")
when (version /= Just "1") (throwError "database is empty or the schema unsupported") when (version /= Just "1") (throwError "database is empty or the schema unsupported")
-- when dry running replace the delete function with a nop
let delete = if dry then (\_ _ _ -> pure ()) else L.delete
withDB path $ \db -> do withDB path $ \db -> do
-- map of id -> isBad -- map of id -> isBad
badMap <- L.withIterator db def $ \i -> badMap <- L.withIterator db def $ \i ->
@ -277,7 +395,7 @@ deleteSessionStorage = do
LS.keySlice i LS.AllKeys LS.Asc LS.keySlice i LS.AllKeys LS.Asc
& LS.filter (B.isPrefixOf "namespace") & LS.filter (B.isPrefixOf "namespace")
& LS.filter (isBad whitelist) & LS.filter (isBad whitelist)
& LS.mapM (\k -> L.delete db def k >> return (domain k)) & LS.mapM (\k -> delete db def k >> return (domain k))
& LS.toList & LS.toList
-- and their records -- and their records
@ -286,7 +404,7 @@ deleteSessionStorage = do
& LS.filter (B.isPrefixOf "map-") & LS.filter (B.isPrefixOf "map-")
& LS.mapM (\k -> & LS.mapM (\k ->
case lookup (originId k) badMap of case lookup (originId k) badMap of
Just True -> L.delete db def k >> return 1 Just True -> delete db def k >> return 1
_ -> return 0) _ -> return 0)
& LS.sum & LS.sum
return (n, nub badDomains) return (n, nub badDomains)
@ -302,40 +420,72 @@ deleteSessionStorage = do
-- * Helper functions -- * Helper functions
-- | Loads a leveldb database and runs a resourceT action -- | Loads a leveldb database and runs a resourceT action
-- withDB :: FilePath -> (L.DB -> ResourceT IO a) -> Action a
-- withDB :: FilePath -> (L.DB -> ResourceT IO a) -> Action a
withDB path f = liftIO $ L.runResourceT (L.open path def >>= f) withDB path f = liftIO $ L.runResourceT (L.open path def >>= f)
-- | Like 'withDB' but retry the action after repairing the db -- | Like 'withDB' but retry the action after repairing the db
-- withRetryDB :: FilePath -> (L.DB -> ResourceT IO a) -> Action a
-- withRetryDB :: FilePath -> (L.DB -> ResourceT IO a) -> Action a
withRetryDB path action = do withRetryDB path action = do
res <- CE.try (withDB path action) res <- CE.try (withDB path action)
case res of case res of
Right b -> return b Right b -> return b
Left (e :: BE.IOException) -> Left (e :: BE.IOException) ->
if not ("Corruption" `T.isInfixOf` msg) if | "Corruption" `T.isInfixOf` msg -> do
then throwError ("error opening the database:\n " <> msg) -- try repairing before giving up
else liftIO $ L.repair path def >> withDB path action liftIO $ L.repair path def
withDB path action
| "unavailable" `T.isInfixOf` msg ->
throwError "database is locked (in use by another process)"
| otherwise ->
throwError ("error opening the database:\n " <> msg)
where msg = T.pack (BE.displayException e) where msg = T.pack (BE.displayException e)
-- | Loads the config from a file
loadSettings :: FilePath -> IO Settings -- | Bypass SQLite locking mechanism
loadSettings path = do --
-- SQLite manages concurrent access via POSIX locks: these are tied to a
-- specific file and pid. They can be bypassed by simply creating a hard
-- link (pointing to the same inode), editing the link and then removing it.
withoutLocks :: String -> (FilePath -> Action a) -> Action a
withoutLocks dbName cont = do
dir <- asks webenginePath
unsafe <- asks (unsafe . options)
let
real = dir </> dbName
link = real <> "-bypass"
-- bypass the SQLite POSIX locks with hard links
when unsafe $ liftIO (Posix.createLink real link)
res <- cont (if unsafe then link else real)
-- remove the hard links
when unsafe $ liftIO (Posix.removeLink link)
return res
-- | Loads the config file/cli options
loadSettings :: Options -> IO Settings
loadSettings opts = do
configdir <- D.getXdgDirectory D.XdgConfig "qutebrowser" configdir <- D.getXdgDirectory D.XdgConfig "qutebrowser"
datadir <- D.getXdgDirectory D.XdgData "qutebrowser" datadir <- D.getXdgDirectory D.XdgData "qutebrowser"
let let
defaultWhitelist = joinPath [configdir, "whitelists", "cookies"] defaultWhitelist = joinPath [configdir, "whitelists", "cookies"]
defaultWebengine = joinPath [datadir, "webengine"] defaultWebengine = joinPath [datadir, "webengine"]
config <- C.load [C.Optional path] config <- C.load [C.Optional (configPath opts)]
whitelist <- C.lookupDefault defaultWhitelist config "whitelist-path" whitelist <- C.lookupDefault defaultWhitelist config "whitelist-path"
webengine <- C.lookupDefault defaultWebengine config "webengine-path" webengine <- C.lookupDefault defaultWebengine config "webengine-path"
domains <- T.lines <$> T.readFile whitelist domains <- T.lines <$> T.readFile whitelist
return (Settings whitelist webengine domains) return (Settings webengine domains opts)
-- | Catches any Selda error -- | Catches any Selda error
dbErrors :: S.SeldaError -> Action a dbErrors :: S.SeldaError -> Action a
dbErrors e = throwError $ dbErrors (S.DbError msg) = throwError $ "error opening database: " <> T.pack msg
"database operation failed: " <> T.pack (BE.displayException e) dbErrors e =
if "ErrorBusy" `isInfixOf` msg
then throwError "database is locked (in use by another process)"
else throwError $ "database operation failed: " <> T.pack msg
where msg = BE.displayException e

View File

@ -2,29 +2,28 @@
### A small tool that clears cookies (and more) ### A small tool that clears cookies (and more)
Websites can store unwanted data using all sorts of methods: besides Websites can store unwanted data using all sorts of methods: besides the usual
the usual cookies, there are also the local and session storage, the cookies, there are also the local and session storage, the IndexedDB API and
IndexedDB API and more caches as well. more caches as well.
bisc will try to go through each of them and remove all information from bisc will try to go through each of them and remove all information from
websites that are not explicitly allowed (ie. a whitelist of domains). websites that are not explicitly allowed (ie. a whitelist of domains).
It was created for qutebrowser, but it actually supports the storage It was created for qutebrowser, but it actually supports the storage format
format used by Chromium-based browsers, which (sadly) means almost used by Chromium-based browsers, which (sadly) means almost every one nowadays.
every one nowadays.
## Installation ## Installation
bisc is a Haskell program available on [Hackage][hackage] and can bisc is a Haskell program available on [Hackage][hackage] and can be installed
be installed with one of the Haskell package managers. For with one of the Haskell package managers. For example, with
example, with [cabal-install][cabal] you would do [cabal-install][cabal] you would do
``` ```
cabal install bisc cabal install bisc
``` ```
and similarly for [stack][stack]. and similarly for [stack][stack].
Alternatively, if you are using Nix or NixOS, bisc is available Alternatively, if you are using Nix or NixOS, bisc is available under the
under the attribute `haskellPackages.bisc`. It should also be in attribute `haskellPackages.bisc`. It should also be in the Nix binary cache so
the Nix binary cache so you don't have to build from source. you don't have to build from source.
Finally, statically compiled binaries can be found in the Finally, statically compiled binaries can be found in the
[releases](/git/rnhmjoj/bisc/releases). [releases](/git/rnhmjoj/bisc/releases).
@ -35,26 +34,29 @@ Finally, statically compiled binaries can be found in the
## Configuration ## Configuration
The bisc configuration file is `$XDG_CONFIG_HOME/bisc/bisc.conf`. The bisc configuration file is `$XDG_CONFIG_HOME/bisc/bisc.conf`. It allows to
It allows to change the paths of the QtWebEngine/Chromium change the paths of the QtWebEngine/Chromium directory and the whitelist file.
directory and the whitelist file.
The default settings are: The default settings are:
``` ```
whitelist-path = "$(XDG_CONFIG_HOME)/qutebrowser/whitelists/cookies" whitelist-path = "$(XDG_CONFIG_HOME)/qutebrowser/whitelists/cookies"
webengine-path = "$(XDG_DATA_HOME)/qutebrowser/webengine" webengine-path = "$(XDG_DATA_HOME)/qutebrowser/webengine"
``` ```
If you want a different location for the configuration file, you can change it
using the `--config` command line option.
## Usage ## Usage
Create an empty whitelist file and write the domains of the - Create an empty whitelist file and write the domains of the allowed cookies,
allowed cookies, one per line. one per line.
Eg. Eg.
``` ```
.example.com .example.com
example.com example.com
``` ```
Run `bisc` to delete all non-whitelisted data from qutebrowser. - Run `bisc --dry-run` to see what would be deleted without actually doing it.
- Run `bisc` to delete all non-whitelisted data from qutebrowser.
Note that running bisc while the browser is open is not safe: this means it Note that running bisc while the browser is open is not safe: this means it
could possibly **corrupt** the databases. Hoever, corruption in the sqllite could possibly **corrupt** the databases. Hoever, corruption in the sqllite
@ -64,7 +66,7 @@ corrupt more often, are automatically repaired by bisc.
## License ## License
Copyright (C) 2021 Michele Guerini Rocco Copyright (C) 2022 Michele Guerini Rocco
This program is free software: you can redistribute it and/or modify This program is free software: you can redistribute it and/or modify
it under the terms of the GNU General Public License as published by it under the terms of the GNU General Public License as published by

View File

@ -1,5 +1,5 @@
name: bisc name: bisc
version: 0.3.1.0 version: 0.4.1.0
synopsis: A small tool that clears cookies (and more). synopsis: A small tool that clears cookies (and more).
description: description:
@ -19,23 +19,30 @@ license: GPL-3
license-file: LICENSE license-file: LICENSE
author: Michele Guerini Rocco author: Michele Guerini Rocco
maintainer: rnhmjoj@inventati.org maintainer: rnhmjoj@inventati.org
copyright: Copyright (C) 2021 Michele Guerini Rocco copyright: Copyright (C) 2022 Michele Guerini Rocco
category: Utility category: Utility
build-type: Simple build-type: Simple
extra-source-files: README.md extra-source-files: README.md, man/bisc.1 man/bisc.conf.5
cabal-version: >=1.10 cabal-version: >=1.10
source-repository head source-repository head
type: git type: git
location: https://maxwell.ydns.eu/git/rnhmjoj/bisc location: https://maxwell.ydns.eu/git/rnhmjoj/bisc
flag static
default: False
description: Create a statically-linked binary
executable bisc executable bisc
main-is: Main.hs main-is: Main.hs
build-depends: base ==4.* , selda ==0.*, build-depends: base ==4.* , selda ==0.*,
selda-sqlite ==0.*, selda-sqlite ==0.*,
leveldb-haskell ==0.*, leveldb-haskell ==0.*, resourcet,
filepath, directory, text, filepath, directory, text, unix,
mtl, configurator, exceptions, mtl, configurator, exceptions,
data-default, bytestring data-default, bytestring,
optparse-applicative
default-language: Haskell2010 default-language: Haskell2010
extra-libraries: snappy stdc++ ghc-options: -Wall -Wno-name-shadowing -O2
if flag(static)
extra-libraries: snappy stdc++

View File

@ -10,37 +10,32 @@ let
basepkgs = import nixpkgs { inherit system; }; basepkgs = import nixpkgs { inherit system; };
pkgs = if static then basepkgs.pkgsStatic else basepkgs.pkgs; pkgs = if static then basepkgs.pkgsStatic else basepkgs.pkgs;
f = { mkDerivation, base, bytestring, configurator, data-default ghc = if static then pkgs.haskell.packages.integer-simple.ghc901
, directory, exceptions, filepath, leveldb-haskell, mtl, selda
, selda-sqlite , lib, text
}:
mkDerivation {
pname = "bisc";
version = "0.3.0.0";
src = ./.;
isLibrary = false;
isExecutable = true;
executableHaskellDepends = [
base bytestring configurator data-default directory exceptions
filepath leveldb-haskell mtl selda selda-sqlite text
];
executableSystemDepends = [ pkgs.snappy ];
buildFlags = lib.optionals static [
"--ld-option=-lstdc++"
"--ld-option=-lsnappy"
];
homepage = "https://maxwell.ydns.eu/git/rnhmjoj/bisc";
description = "A small tool that clears cookies (and more)";
license = lib.licenses.gpl3;
};
ghc = if static then pkgs.haskell.packages.integer-simple.ghc8104
else if compiler == "default" then pkgs.haskellPackages else if compiler == "default" then pkgs.haskellPackages
else pkgs.haskell.packages.${compiler}; else pkgs.haskell.packages.${compiler};
variant = if doBenchmark then pkgs.haskell.lib.doBenchmark else pkgs.lib.id; variant = if doBenchmark then pkgs.haskell.lib.doBenchmark else pkgs.lib.id;
drv = variant (ghc.callPackage f {}); drv = variant (override (ghc.callPackage ./bisc.nix {}));
override = drv: pkgs.haskell.lib.overrideCabal drv (old: with pkgs.lib; {
buildTools = [ pkgs.installShellFiles ];
configureFlags = optional static "-f static";
buildFlags = optionals static [
"--ld-option=-lstdc++"
"--ld-option=-lsnappy"
];
postInstall = ''
# generate completion
$out/bin/bisc --bash-completion-script "$out/bin/bisc" > bisc.bash
$out/bin/bisc --fish-completion-script "$out/bin/bisc" > bisc.fish
$out/bin/bisc --zsh-completion-script "$out/bin/bisc" > bisc.zsh
installShellCompletion bisc.{bash,fish,zsh}
installManPage man/*.[0-9]
'';
postFixup = optionalString static "rm -r $out/nix-support";
});
in in

75
man/bisc.1 Normal file
View File

@ -0,0 +1,75 @@
.TH bisc 1 "January 11, 2022" "bisc 0.4.1" "User Commands"
.SH NAME
bisc - a small tool that clears cookies (and more)
.SH SYNOPSIS
.B bisc
.RI [ option ]
.SH DESCRIPTION
.PP
Websites can store unwanted data using all sorts of methods: besides the usual
cookies, there are also the local and session storage, the IndexedDB API and
more caches as well.
.PP
Bisc will try to go through each of them and remove all information from
websites that are not explicitly allowed (ie. a whitelist of domains).
It was created for qutebrowser, but it actually supports the storage format
used by Chromium-based browsers, which (sadly) means almost every one nowadays.
.SH USAGE
.IP \(bu 2
Create an empty whitelist file (see the FILES section) and write the domains of
the allowed cookies, one per line. For example:
.IP
.nf
\fC
\&.example.com
example.com
\fR
.fi
.IP \(bu 2
Run \fCbisc --dry-run\fR to see what would be deleted without actually
doing it.
.IP \(bu 2
Run \fCbisc\fR to delete all non-whitelisted data from qutebrowser.
.SH OPTIONS
.TP
.BR -c ","\ --config\ FILE
Use FILE as the configuration file.
.TP
.BR -n ","\ --dry-run
Don't actually remove anything, just show what would be done.
.TP
.BR -u ","\ --unsafe
Ignore database locks.
This will probably corrupt the databases, but works while the browser is
running.
.TP
.BR -h ","\ --help
Show the program information and help screen.
.SH FILES
.TP
.I $XDG_CONFIG_HOME/bisc/bisc.conf
Bisc configuration
.TP
.I $XDG_CONFIG_HOME/qutebrowser/whitelists/cookies
Domain whitelist
.TP
.I $XDG_DATA_HOME/qutebrowser/webengine
Chromium/QtWebEngine state directory
.PP
Note: when the variable $XDG_CONFIG_HOME or $XDG_DATA_HOME is not set,
$HOME/.config and $HOME/.local/share respectively, will be used instead.
.SH SEE ALSO
\fBbisc.conf\fR(5) for the bisc configuration file
.SH AUTHORS
Copyright © 2022 Michele Guerini Rocco.
.TP 0
Released under the GPL, version 3 or greater.
This software carries no warranty of any kind.

49
man/bisc.conf.5 Normal file
View File

@ -0,0 +1,49 @@
.TH bisc.conf 5 "January 11, 2022" "bisc 0.4.1"
.SH NAME
bisc.conf - bisc configuration file
.SH SYNOPSIS
The bisc configuration file, found at the following locations, unless specified
via the \fC-c\fR command line option:
.IP \(bu 3
$XDG_CONFIG_HOME/bisc/bisc.conf,
.IP \(bu 3
$HOME/.config/bisc/bisc.conf (when $XDG_CONFIG_HOME is not set)
.SH DESCRIPTION
.PP
The bisc.conf file allows to change the default location of a couple of files
used by bisc.
.SH OPTIONS
.TP 4
.BR "webengine-path" " (default " "$(XDG_DATA_HOME)/qutebrowser/webengine")
The location of the Chromium/QtWebEngine state directory.
.TP 4
.BR "whitelist-path" " (default " "$(XDG_CONFIG_HOME)/qutebrowser/whitelists/cookies")
The location of the domain whitelist.
.SH EXAMPLE
This is an example configuration:
.IP
.nf
\fC
# This is a comment
whitelist-path = "/home/alice/docs/cookie-whitelist"
# You can also access environment variables:
webengine-path = "$(HOME)/.local/qutebrowser/webengine"
\fR
.fi
.SH SEE ALSO
\fBbisc\fR(1) for the bisc command
.SH AUTHORS
Copyright © 2022 Michele Guerini Rocco.
.TP 0
Released under the GPL, version 3 or greater.
This software carries no warranty of any kind.