add firefox bookmark import (Resolves #15)

This commit is contained in:
Jon Schoning 2020-06-14 03:04:11 -05:00 committed by Yann Esposito (Yogsototh)
parent 6fa8edbd5e
commit b0d230edbb
Signed by untrusted user who does not match committer: yogsototh
GPG key ID: 7B19A4C650D59646
3 changed files with 119 additions and 14 deletions

View file

@ -43,12 +43,18 @@ see https://github.com/jonschoning/espial-docker
stack exec migration -- createuser --conn espial.sqlite3 --userName myusername --userPassword myuserpassword stack exec migration -- createuser --conn espial.sqlite3 --userName myusername --userPassword myuserpassword
``` ```
5. Import a bookmark file for a user (optional) 5a. Import a pinboard bookmark file for a user (optional)
``` ```
stack exec migration -- importbookmarks --conn espial.sqlite3 --userName myusername --bookmarkFile sample-bookmarks.json stack exec migration -- importbookmarks --conn espial.sqlite3 --userName myusername --bookmarkFile sample-bookmarks.json
``` ```
5b. Import a firefox bookmark file for a user (optional)
```
stack exec migration -- importfirefoxbookmarks --conn espial.sqlite3 --userName myusername --bookmarkFile firefox-bookmarks.json
```
6. Start a production server: 6. Start a production server:
``` ```
@ -78,7 +84,7 @@ ssl: use reverse proxy
- See `purs/` folder - See `purs/` folder
## Import Bookmark file format ## Import Bookmark file format (pinboard compatible format)
see `sample-bookmarks.json`, which contains a JSON array, each line containing a `FileBookmark` object. see `sample-bookmarks.json`, which contains a JSON array, each line containing a `FileBookmark` object.

View file

@ -26,6 +26,9 @@ data MigrationOpts
| ImportBookmarks { conn :: Text | ImportBookmarks { conn :: Text
, userName :: Text , userName :: Text
, bookmarkFile :: FilePath } , bookmarkFile :: FilePath }
| ImportFirefoxBookmarks { conn :: Text
, userName :: Text
, bookmarkFile :: FilePath }
| ExportBookmarks { conn :: Text | ExportBookmarks { conn :: Text
, userName :: Text , userName :: Text
, bookmarkFile :: FilePath } , bookmarkFile :: FilePath }
@ -72,13 +75,6 @@ main = do
P.deleteCascade uid P.deleteCascade uid
pure () :: DB () pure () :: DB ()
ImportBookmarks {..} ->
P.runSqlite conn $ do
muser <- P.getBy (UniqueUserName userName)
case muser of
Just (P.Entity uid _) -> insertFileBookmarks uid bookmarkFile
Nothing -> liftIO (print (userName ++ "not found"))
ExportBookmarks {..} -> ExportBookmarks {..} ->
P.runSqlite conn $ do P.runSqlite conn $ do
muser <- P.getBy (UniqueUserName userName) muser <- P.getBy (UniqueUserName userName)
@ -86,9 +82,36 @@ main = do
Just (P.Entity uid _) -> exportFileBookmarks uid bookmarkFile Just (P.Entity uid _) -> exportFileBookmarks uid bookmarkFile
Nothing -> liftIO (print (userName ++ "not found")) Nothing -> liftIO (print (userName ++ "not found"))
ImportBookmarks {..} ->
P.runSqlite conn $ do
muser <- P.getBy (UniqueUserName userName)
case muser of
Just (P.Entity uid _) -> do
result <- insertFileBookmarks uid bookmarkFile
case result of
Left e -> liftIO (print e)
Right n -> liftIO (print (show n ++ " bookmarks imported."))
Nothing -> liftIO (print (userName ++ "not found"))
ImportFirefoxBookmarks {..} ->
P.runSqlite conn $ do
muser <- P.getBy (UniqueUserName userName)
case muser of
Just (P.Entity uid _) -> do
result <- insertFFBookmarks uid bookmarkFile
case result of
Left e -> liftIO (print e)
Right n -> liftIO (print (show n ++ " bookmarks imported."))
Nothing -> liftIO (print (userName ++ "not found"))
ImportNotes {..} -> ImportNotes {..} ->
P.runSqlite conn $ do P.runSqlite conn $ do
muser <- P.getBy (UniqueUserName userName) muser <- P.getBy (UniqueUserName userName)
case muser of case muser of
Just (P.Entity uid _) -> insertDirFileNotes uid noteDirectory Just (P.Entity uid _) -> do
result <- insertDirFileNotes uid noteDirectory
case result of
Left e -> liftIO (print e)
Right n -> liftIO (print (show n ++ " notes imported."))
Nothing -> liftIO (print (userName ++ "not found")) Nothing -> liftIO (print (userName ++ "not found"))

View file

@ -10,6 +10,7 @@ import qualified Data.Attoparsec.Text as P
import qualified Control.Monad.Combinators as PC import qualified Control.Monad.Combinators as PC
import qualified Data.List.NonEmpty as NE import qualified Data.List.NonEmpty as NE
import qualified Data.Time.ISO8601 as TI import qualified Data.Time.ISO8601 as TI
import qualified Data.Time.Clock.POSIX as TI
import qualified Database.Esqueleto as E import qualified Database.Esqueleto as E
import Database.Esqueleto.Internal.Sql as E import Database.Esqueleto.Internal.Sql as E
import qualified Data.Time as TI import qualified Data.Time as TI
@ -349,12 +350,69 @@ bookmarkTofileBookmark (Bookmark {..}) tags =
bookmarkArchiveHref bookmarkArchiveHref
tags tags
data FFBookmarkNode = FFBookmarkNode
{ firefoxBookmarkChildren :: Maybe [FFBookmarkNode]
, firefoxBookmarkDateAdded :: !TI.POSIXTime
, firefoxBookmarkGuid :: !Text
, firefoxBookmarkIconUri :: !(Maybe Text)
, firefoxBookmarkId :: !Int
, firefoxBookmarkIndex :: !Int
, firefoxBookmarkLastModified :: !TI.POSIXTime
, firefoxBookmarkRoot :: !(Maybe Text)
, firefoxBookmarkTitle :: !Text
, firefoxBookmarkType :: !Text
, firefoxBookmarkTypeCode :: !Int
, firefoxBookmarkUri :: !(Maybe Text)
} deriving (Show, Eq, Typeable, Ord)
instance FromJSON FFBookmarkNode where
parseJSON (Object o) =
FFBookmarkNode <$>
(o A..:? "children") <*>
(o .: "dateAdded") <*>
o .: "guid" <*>
(o A..:? "iconUri") <*>
o .: "id" <*>
o .: "index" <*>
(o .: "lastModified") <*>
(o A..:? "root") <*>
(o .: "title") <*>
(o .: "type") <*>
(o .: "typeCode") <*>
(o A..:? "uri")
parseJSON _ = A.parseFail "bad parse"
insertFileBookmarks :: Key User -> FilePath -> DB () firefoxBookmarkNodeToBookmark :: UserId -> FFBookmarkNode -> IO [Bookmark]
firefoxBookmarkNodeToBookmark user (FFBookmarkNode {..}) = do
case firefoxBookmarkTypeCode of
1 -> do
slug <- mkBmSlug
pure $
[ Bookmark
user
slug
(fromMaybe "" firefoxBookmarkUri)
firefoxBookmarkTitle
""
(TI.posixSecondsToUTCTime (firefoxBookmarkDateAdded / 1000000))
True
False
False
Nothing
]
2 ->
join <$>
mapM
(firefoxBookmarkNodeToBookmark user)
(fromMaybe [] firefoxBookmarkChildren)
_ -> pure []
insertFileBookmarks :: Key User -> FilePath -> DB (Either String Int)
insertFileBookmarks userId bookmarkFile = do insertFileBookmarks userId bookmarkFile = do
mfmarks <- liftIO $ readFileBookmarks bookmarkFile mfmarks <- liftIO $ readFileBookmarks bookmarkFile
case mfmarks of case mfmarks of
Left e -> print e Left e -> pure $ Left e
Right fmarks -> do Right fmarks -> do
bmarks <- liftIO $ mapM (fileBookmarkToBookmark userId) fmarks bmarks <- liftIO $ mapM (fileBookmarkToBookmark userId) fmarks
mbids <- mapM insertUnique bmarks mbids <- mapM insertUnique bmarks
@ -366,13 +424,30 @@ insertFileBookmarks userId bookmarkFile = do
(\mbid tags -> ((, tags) <$> mbid)) (\mbid tags -> ((, tags) <$> mbid))
mbids mbids
(extractTags <$> fmarks) (extractTags <$> fmarks)
pure $ Right (length bmarks)
where where
extractTags = words . fileBookmarkTags extractTags = words . fileBookmarkTags
insertFFBookmarks :: Key User -> FilePath -> DB (Either String Int)
insertFFBookmarks userId bookmarkFile = do
mfmarks <- liftIO $ readFFBookmarks bookmarkFile
case mfmarks of
Left e -> pure $ Left e
Right fmarks -> do
bmarks <- liftIO $ firefoxBookmarkNodeToBookmark userId fmarks
_ <- mapM insertUnique bmarks
pure $ Right (length bmarks)
readFileBookmarks :: MonadIO m => FilePath -> m (Either String [FileBookmark]) readFileBookmarks :: MonadIO m => FilePath -> m (Either String [FileBookmark])
readFileBookmarks fpath = readFileBookmarks fpath =
pure . A.eitherDecode' . fromStrict =<< readFile fpath pure . A.eitherDecode' . fromStrict =<< readFile fpath
readFFBookmarks :: MonadIO m => FilePath -> m (Either String FFBookmarkNode)
readFFBookmarks fpath =
pure . A.eitherDecode' . fromStrict =<< readFile fpath
exportFileBookmarks :: Key User -> FilePath -> DB () exportFileBookmarks :: Key User -> FilePath -> DB ()
exportFileBookmarks user fpath = do exportFileBookmarks user fpath = do
liftIO . A.encodeFile fpath =<< getFileBookmarks user liftIO . A.encodeFile fpath =<< getFileBookmarks user
@ -519,14 +594,15 @@ fileNoteToNote user (FileNote {..} ) = do
fileNoteCreatedAt fileNoteCreatedAt
fileNoteUpdatedAt fileNoteUpdatedAt
insertDirFileNotes :: Key User -> FilePath -> DB () insertDirFileNotes :: Key User -> FilePath -> DB (Either String Int)
insertDirFileNotes userId noteDirectory = do insertDirFileNotes userId noteDirectory = do
mfnotes <- liftIO $ readFileNotes noteDirectory mfnotes <- liftIO $ readFileNotes noteDirectory
case mfnotes of case mfnotes of
Left e -> print e Left e -> pure $ Left e
Right fnotes -> do Right fnotes -> do
notes <- liftIO $ mapM (fileNoteToNote userId) fnotes notes <- liftIO $ mapM (fileNoteToNote userId) fnotes
void $ mapM insertUnique notes void $ mapM insertUnique notes
pure $ Right (length notes)
where where
readFileNotes :: MonadIO m => FilePath -> m (Either String [FileNote]) readFileNotes :: MonadIO m => FilePath -> m (Either String [FileNote])
readFileNotes fdir = do readFileNotes fdir = do