Improve readability
This commit is contained in:
parent
ae68414db3
commit
e3d47d4d9d
@ -12,7 +12,9 @@ Portability : POSIX
|
|||||||
|
|
||||||
Imports from firefox. Firefox needs to be closed when doing the import
|
Imports from firefox. Firefox needs to be closed when doing the import
|
||||||
-}
|
-}
|
||||||
module Operations.Import.Firefox where
|
module Operations.Import.Firefox
|
||||||
|
( importFirefox )
|
||||||
|
where
|
||||||
|
|
||||||
import Data.Monoid
|
import Data.Monoid
|
||||||
(Endo(..))
|
(Endo(..))
|
||||||
@ -45,7 +47,19 @@ import System.Environment
|
|||||||
import GHC.Stack
|
import GHC.Stack
|
||||||
|
|
||||||
import Control.Lens
|
import Control.Lens
|
||||||
(foldMapOf, folded, has, ix, makeLenses, to, (%~), (&), (<>~), (^.))
|
( Lens'
|
||||||
|
, foldMapOf
|
||||||
|
, folded
|
||||||
|
, has
|
||||||
|
, ix
|
||||||
|
, lens
|
||||||
|
, makeLenses
|
||||||
|
, to
|
||||||
|
, (%~)
|
||||||
|
, (&)
|
||||||
|
, (<>~)
|
||||||
|
, (^.)
|
||||||
|
)
|
||||||
|
|
||||||
import qualified Database.SQLite.Simple as SQL
|
import qualified Database.SQLite.Simple as SQL
|
||||||
|
|
||||||
@ -70,7 +84,8 @@ data Firefox
|
|||||||
}
|
}
|
||||||
deriving stock (Show, Eq)
|
deriving stock (Show, Eq)
|
||||||
|
|
||||||
makeLenses ''Firefox
|
url :: Lens' Firefox Text
|
||||||
|
url = lens _url (\f u -> f{_url = u})
|
||||||
|
|
||||||
stores
|
stores
|
||||||
:: MonadResource m
|
:: MonadResource m
|
||||||
@ -101,11 +116,17 @@ makeLenses ''Update
|
|||||||
|
|
||||||
importFirefox :: BuukaM ()
|
importFirefox :: BuukaM ()
|
||||||
importFirefox = do
|
importFirefox = do
|
||||||
|
-- Collect all the imported bookmarks
|
||||||
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)))
|
||||||
|
-- Insert to the buuka store iff, the urls don't already exist in the store
|
||||||
|
-- The fold keeps track of a set of already seen entries. Every iteration
|
||||||
|
-- adds the current url to the known set of urls. Only if the url doesn't
|
||||||
|
-- exist in the set, will it be inserted to the store
|
||||||
buukaU $ modify $ \oldState -> F.foldl' update (initialState oldState) fs ^. buuka
|
buukaU $ modify $ \oldState -> F.foldl' update (initialState oldState) fs ^. buuka
|
||||||
where
|
where
|
||||||
toEntry Firefox{..} = B.BuukaEntry{ B._url = B.URL _url, B._title = Just _title }
|
toEntry Firefox{..} = B.BuukaEntry{ B._url = B.URL _url, B._title = Just _title }
|
||||||
update acc f = acc
|
update acc f = acc
|
||||||
& seen <>~ (f ^. url . to S.singleton)
|
& seen <>~ (f ^. url . to S.singleton)
|
||||||
& if has (seen . ix (f ^. url)) acc then id else buuka %~ (B.insert (toEntry f))
|
& 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 (initialUrls oldState)
|
||||||
|
initialUrls = foldMapOf (B._Buuka . folded . B.url . B._URL) S.singleton
|
||||||
|
Loading…
Reference in New Issue
Block a user