Blub
This commit is contained in:
parent
8bcdb84efd
commit
a452b44cfe
@ -37,9 +37,11 @@ library
|
|||||||
bytestring,
|
bytestring,
|
||||||
containers,
|
containers,
|
||||||
data-default,
|
data-default,
|
||||||
|
errors,
|
||||||
filepath >= 1.3.0.0,
|
filepath >= 1.3.0.0,
|
||||||
hinotify,
|
hinotify,
|
||||||
hpath,
|
hpath,
|
||||||
|
monad-loops,
|
||||||
mtl >= 2.2,
|
mtl >= 2.2,
|
||||||
old-locale >= 1,
|
old-locale >= 1,
|
||||||
posix-paths,
|
posix-paths,
|
||||||
|
@ -16,6 +16,7 @@ along with this program; if not, write to the Free Software
|
|||||||
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA.
|
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA.
|
||||||
--}
|
--}
|
||||||
|
|
||||||
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
{-# OPTIONS_HADDOCK ignore-exports #-}
|
{-# OPTIONS_HADDOCK ignore-exports #-}
|
||||||
|
|
||||||
module HSFM.Settings.Bookmarks where
|
module HSFM.Settings.Bookmarks where
|
||||||
@ -34,11 +35,11 @@ import Data.ByteString
|
|||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
(
|
(
|
||||||
catMaybes
|
catMaybes
|
||||||
|
, fromJust
|
||||||
)
|
)
|
||||||
import Data.Word8
|
import Data.Word8
|
||||||
(
|
(
|
||||||
_lf
|
_nul
|
||||||
, _nul
|
|
||||||
)
|
)
|
||||||
import qualified HPath as P
|
import qualified HPath as P
|
||||||
import HPath
|
import HPath
|
||||||
@ -50,6 +51,10 @@ import HPath
|
|||||||
import HSFM.FileSystem.FileOperations
|
import HSFM.FileSystem.FileOperations
|
||||||
import HSFM.FileSystem.FileType
|
import HSFM.FileSystem.FileType
|
||||||
import Prelude hiding (readFile, writeFile)
|
import Prelude hiding (readFile, writeFile)
|
||||||
|
import System.Posix.Env.ByteString
|
||||||
|
(
|
||||||
|
getEnv
|
||||||
|
)
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
@ -62,12 +67,12 @@ data Bookmark = MkBookmark {
|
|||||||
|
|
||||||
|
|
||||||
-- |Parses bookmarks from a ByteString that has pairs of
|
-- |Parses bookmarks from a ByteString that has pairs of
|
||||||
-- name and path. Name and path are separated by null character
|
-- name and path. Name and path are separated by one null character
|
||||||
-- and the pairs istelf are separated by newline `_lf` from
|
-- and the pairs itself are separated by two null characters from
|
||||||
-- each other.
|
-- each other.
|
||||||
bkParser :: Parser [Bookmark]
|
bkParser :: Parser [Bookmark]
|
||||||
bkParser =
|
bkParser =
|
||||||
fmap catMaybes $ many' (fmap toBm $ bookmark <* word8 _lf)
|
fmap catMaybes $ many' (fmap toBm $ bookmark <* word8 _nul <* word8 _nul)
|
||||||
where
|
where
|
||||||
toBm :: (ByteString, ByteString) -> Maybe Bookmark
|
toBm :: (ByteString, ByteString) -> Maybe Bookmark
|
||||||
toBm (name, path) = MkBookmark <$> P.parseFn name
|
toBm (name, path) = MkBookmark <$> P.parseFn name
|
||||||
@ -78,20 +83,24 @@ bkParser =
|
|||||||
<$> many1' char
|
<$> many1' char
|
||||||
<* (word8 _nul)
|
<* (word8 _nul)
|
||||||
<*> many1' char
|
<*> many1' char
|
||||||
char = satisfy (`notElem` [_nul, _lf])
|
char = satisfy (`notElem` [_nul])
|
||||||
|
|
||||||
|
|
||||||
-- |Writes bookmarks to a give file.
|
-- |Writes bookmarks to a given file.
|
||||||
writeBookmarksToFile :: Path Abs -> [Bookmark] -> IO ()
|
writeBookmarks :: [Bookmark] -> IO ()
|
||||||
writeBookmarksToFile _ [] = return ()
|
writeBookmarks [] = return ()
|
||||||
writeBookmarksToFile p bs = do
|
writeBookmarks bs = do
|
||||||
let str = foldr1 (\x y -> x `BS.append` BS.singleton _lf
|
bf <- bookmarksFile
|
||||||
|
bfd <- bookmarksDir
|
||||||
|
mkdirP bfd
|
||||||
|
readFile getFileInfo bfd >>= (\x -> createFile x bookmarksFileName)
|
||||||
|
let str = foldr1 (\x y -> x `BS.append` BS.pack [_nul, _nul]
|
||||||
`BS.append`
|
`BS.append`
|
||||||
y `BS.append` BS.singleton _lf)
|
y `BS.append` BS.pack [_nul, _nul])
|
||||||
(fmap toByteString bs)
|
(fmap toByteString bs)
|
||||||
file <- readFile getFileInfo p
|
file <- readFile getFileInfo bf
|
||||||
void $ writeFile file str
|
void $ writeFile file str
|
||||||
where
|
where
|
||||||
toByteString :: Bookmark -> ByteString
|
toByteString :: Bookmark -> ByteString
|
||||||
toByteString b = (P.fromRel $ bkName b)
|
toByteString b = (P.fromRel $ bkName b)
|
||||||
`BS.append` BS.singleton _nul
|
`BS.append` BS.singleton _nul
|
||||||
@ -99,11 +108,32 @@ writeBookmarksToFile p bs = do
|
|||||||
|
|
||||||
|
|
||||||
-- |Reads bookmarks from a given file.
|
-- |Reads bookmarks from a given file.
|
||||||
readBookmarksFromFile :: Path Abs -> IO [Bookmark]
|
readBookmarks :: IO [Bookmark]
|
||||||
readBookmarksFromFile p = do
|
readBookmarks = do
|
||||||
|
p <- bookmarksFile
|
||||||
file <- readFile getFileInfo p
|
file <- readFile getFileInfo p
|
||||||
c <- readFileContents file
|
c <- readFileContents file
|
||||||
case parseOnly bkParser c of
|
case parseOnly bkParser c of
|
||||||
Left _ -> return []
|
Left _ -> return []
|
||||||
Right x -> return x
|
Right x -> return x
|
||||||
|
|
||||||
|
|
||||||
|
bookmarksDir :: IO (Path Abs)
|
||||||
|
bookmarksDir = do
|
||||||
|
mhomedir <- getEnv "HOME"
|
||||||
|
case mhomedir of
|
||||||
|
Nothing -> ioError (userError "No valid homedir?!")
|
||||||
|
Just home -> do
|
||||||
|
phome <- P.parseAbs home
|
||||||
|
reldir <- P.parseRel ".config/hsfm"
|
||||||
|
return $ phome P.</> reldir
|
||||||
|
|
||||||
|
|
||||||
|
bookmarksFile :: IO (Path Abs)
|
||||||
|
bookmarksFile = do
|
||||||
|
path <- bookmarksDir
|
||||||
|
return $ path P.</> bookmarksFileName
|
||||||
|
|
||||||
|
|
||||||
|
bookmarksFileName :: Path Fn
|
||||||
|
bookmarksFileName = fromJust $ P.parseFn "bookmarks"
|
||||||
|
Loading…
Reference in New Issue
Block a user