Insert to buuka
This commit is contained in:
parent
01c591434e
commit
ae68414db3
@ -1,5 +1,6 @@
|
|||||||
{-# LANGUAGE RecordWildCards #-}
|
{-# LANGUAGE RecordWildCards #-}
|
||||||
{-# LANGUAGE TemplateHaskell #-}
|
{-# LANGUAGE TemplateHaskell #-}
|
||||||
|
{-# LANGUAGE TypeApplications #-}
|
||||||
{-|
|
{-|
|
||||||
Module : Operations.Import.Firefox
|
Module : Operations.Import.Firefox
|
||||||
Description : Imports from firefox
|
Description : Imports from firefox
|
||||||
@ -44,7 +45,7 @@ import System.Environment
|
|||||||
import GHC.Stack
|
import GHC.Stack
|
||||||
|
|
||||||
import Control.Lens
|
import Control.Lens
|
||||||
(foldMapOf, folded, makeLenses, to, (&), (<>~), (^.))
|
(foldMapOf, folded, has, ix, makeLenses, to, (%~), (&), (<>~), (^.))
|
||||||
|
|
||||||
import qualified Database.SQLite.Simple as SQL
|
import qualified Database.SQLite.Simple as SQL
|
||||||
|
|
||||||
@ -103,6 +104,8 @@ importFirefox = do
|
|||||||
fs <- (`appEndo` []) <$> runResourceT (runConduit $ stores .| C.mapM bookmarks .| C.foldMap (\f -> Endo (++ f)))
|
fs <- (`appEndo` []) <$> runResourceT (runConduit $ stores .| C.mapM bookmarks .| C.foldMap (\f -> Endo (++ f)))
|
||||||
buukaU $ modify $ \oldState -> F.foldl' update (initialState oldState) fs ^. buuka
|
buukaU $ modify $ \oldState -> F.foldl' update (initialState oldState) fs ^. buuka
|
||||||
where
|
where
|
||||||
-- incomplete update
|
toEntry Firefox{..} = B.BuukaEntry{ B._url = B.URL _url, B._title = Just _title }
|
||||||
update acc f = acc & seen <>~ (f ^. url . to S.singleton)
|
update acc f = acc
|
||||||
|
& seen <>~ (f ^. url . to S.singleton)
|
||||||
|
& if has (seen . ix (f ^. url)) acc then id else buuka %~ (B.insert (toEntry f))
|
||||||
initialState oldState = Update oldState (foldMapOf (B._Buuka . folded . B.url . B._URL) S.singleton oldState)
|
initialState oldState = Update oldState (foldMapOf (B._Buuka . folded . B.url . B._URL) S.singleton oldState)
|
||||||
|
Loading…
Reference in New Issue
Block a user