buuka/src/Operations/Import/Firefox.hs

48 lines
1.1 KiB
Haskell

{-|
Module : Operations.Import.Firefox
Description : Imports from firefox
Copyright : (c) Mats Rauhala, 2020
License : BSD-3-Clause
Maintainer : mats.rauhala@iki.fi
Stability : experimental
Portability : POSIX
Imports from firefox. Firefox needs to be closed when doing the import
-}
module Operations.Import.Firefox where
import Conduit
import qualified Data.Conduit.Combinators as C
import System.FilePath
(takeFileName, (</>))
import Control.Exception
(Exception)
import System.Environment
(lookupEnv)
import GHC.Stack
-- select p.title, p.url from moz_bookmarks b join moz_places p on b.fk = p.id
--
-- select keyword from moz_keywords where place_id = ?
newtype ImportException
= HomeNotFound CallStack
deriving stock (Show)
deriving anyclass (Exception)
stores
:: MonadResource m
=> MonadThrow m
=> MonadIO m
=> HasCallStack
=> ConduitT i FilePath m ()
stores = liftIO (lookupEnv "HOME") >>= maybe (throwM (HomeNotFound callStack)) listStores
where
listStores home =
sourceDirectoryDeep False (home </> ".mozilla/firefox")
.| C.filter (\p -> takeFileName p == "places.sqlite")