Query bookmarks from firefox
N+1 queries :/
This commit is contained in:
parent
25ecac21fa
commit
b1f3760e06
@ -1,3 +1,5 @@
|
|||||||
|
{-# LANGUAGE RecordWildCards #-}
|
||||||
|
{-# LANGUAGE TemplateHaskell #-}
|
||||||
{-|
|
{-|
|
||||||
Module : Operations.Import.Firefox
|
Module : Operations.Import.Firefox
|
||||||
Description : Imports from firefox
|
Description : Imports from firefox
|
||||||
@ -14,6 +16,9 @@ module Operations.Import.Firefox where
|
|||||||
import Conduit
|
import Conduit
|
||||||
import qualified Data.Conduit.Combinators as C
|
import qualified Data.Conduit.Combinators as C
|
||||||
|
|
||||||
|
import Data.Text
|
||||||
|
(Text)
|
||||||
|
|
||||||
import System.FilePath
|
import System.FilePath
|
||||||
(takeFileName, (</>))
|
(takeFileName, (</>))
|
||||||
|
|
||||||
@ -25,6 +30,14 @@ import System.Environment
|
|||||||
|
|
||||||
import GHC.Stack
|
import GHC.Stack
|
||||||
|
|
||||||
|
import Control.Lens
|
||||||
|
(makeLenses)
|
||||||
|
|
||||||
|
import qualified Database.SQLite.Simple as SQL
|
||||||
|
|
||||||
|
import Data.Traversable
|
||||||
|
(for)
|
||||||
|
|
||||||
-- select p.title, p.url from moz_bookmarks b join moz_places p on b.fk = p.id
|
-- 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 = ?
|
-- select keyword from moz_keywords where place_id = ?
|
||||||
@ -34,6 +47,15 @@ newtype ImportException
|
|||||||
deriving stock (Show)
|
deriving stock (Show)
|
||||||
deriving anyclass (Exception)
|
deriving anyclass (Exception)
|
||||||
|
|
||||||
|
data Firefox
|
||||||
|
= Firefox { _url :: Text
|
||||||
|
, _title :: Text
|
||||||
|
, _keywords :: [Text]
|
||||||
|
}
|
||||||
|
deriving stock (Show, Eq)
|
||||||
|
|
||||||
|
makeLenses ''Firefox
|
||||||
|
|
||||||
stores
|
stores
|
||||||
:: MonadResource m
|
:: MonadResource m
|
||||||
=> MonadThrow m
|
=> MonadThrow m
|
||||||
@ -45,3 +67,10 @@ stores = liftIO (lookupEnv "HOME") >>= maybe (throwM (HomeNotFound callStack)) l
|
|||||||
listStores home =
|
listStores home =
|
||||||
sourceDirectoryDeep False (home </> ".mozilla/firefox")
|
sourceDirectoryDeep False (home </> ".mozilla/firefox")
|
||||||
.| C.filter (\p -> takeFileName p == "places.sqlite")
|
.| C.filter (\p -> takeFileName p == "places.sqlite")
|
||||||
|
|
||||||
|
bookmarks :: MonadIO m => FilePath -> m [Firefox]
|
||||||
|
bookmarks path = liftIO $ SQL.withConnection path $ \conn -> do
|
||||||
|
elems <- SQL.query_ conn "select p.id, p.title, p.url from moz_bookmarks b join moz_places p on b.fk = p.id"
|
||||||
|
for elems $ \(_id, _title, _url) -> do
|
||||||
|
_keywords <- fmap SQL.fromOnly <$> SQL.query conn "select keyword from moz_keywords where place_id = ?" (SQL.Only @Int _id)
|
||||||
|
pure Firefox{..}
|
||||||
|
Loading…
Reference in New Issue
Block a user