{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# OPTIONS_HADDOCK show-extensions #-}
module Yi.IReader where
import Control.Exception (SomeException, catch)
import Control.Monad (join, void)
import Data.Binary (Binary, decode, encodeFile)
import qualified Data.ByteString.Char8 as B (ByteString, pack, readFile, unpack)
import qualified Data.ByteString.Lazy.Char8 as BL (fromChunks)
import Data.Default (Default, def)
import Data.Sequence as S (Seq, ViewL (EmptyL, (:<)),
ViewR ((:>)), empty, length,
null, splitAt, viewl, viewr,
(<|), (><), (|>))
import Data.Typeable (Typeable)
import Yi.Buffer.HighLevel (replaceBufferContent, topB)
import Yi.Buffer.Misc (elemsB, getBufferDyn, putBufferDyn)
import Yi.Editor (withCurrentBuffer)
import Yi.Keymap (YiM)
import Yi.Paths (getConfigPath)
import qualified Yi.Rope as R (fromString, toString)
import Yi.Types (YiVariable)
import Yi.Utils (io)
type Article = B.ByteString
newtype ArticleDB = ADB { unADB :: Seq Article }
deriving (Typeable, Binary)
instance Default ArticleDB where
def = ADB S.empty
instance YiVariable ArticleDB
split :: ArticleDB -> (Article, ArticleDB)
split (ADB adb) = case viewl adb of
EmptyL -> (B.pack "", def)
(a :< b) -> (a, ADB b)
getLatestArticle :: ArticleDB -> Article
getLatestArticle = fst . split
removeSetLast :: ArticleDB -> Article -> ArticleDB
removeSetLast adb old = ADB (unADB (snd (split adb)) S.|> old)
shift :: Int -> ArticleDB -> ArticleDB
shift n adb = if n < 2 || lst < 2 then adb else ADB $ (r S.|> lastentry) >< s'
where lst = S.length (unADB adb) - 1
(r,s) = S.splitAt (lst `div` n) (unADB adb)
(s' :> lastentry) = S.viewr s
insertArticle :: ArticleDB -> Article -> ArticleDB
insertArticle (ADB adb) new = ADB (new S.<| adb)
writeDB :: ArticleDB -> YiM ()
writeDB adb = void $ io . join . fmap (`encodeFile` adb) $ getArticleDbFilename
readDB :: YiM ArticleDB
readDB = io $ (getArticleDbFilename >>= r) `catch` returnDefault
where r = fmap (decode . BL.fromChunks . return) . B.readFile
returnDefault (_ :: SomeException) = return def
getArticleDbFilename :: IO FilePath
getArticleDbFilename = getConfigPath "articles.db"
oldDbNewArticle :: YiM (ArticleDB, Article)
oldDbNewArticle = do
saveddb <- withCurrentBuffer getBufferDyn
newarticle <- B.pack . R.toString <$> withCurrentBuffer elemsB
if not $ S.null (unADB saveddb)
then return (saveddb, newarticle)
else readDB >>= \olddb -> return (olddb, newarticle)
setDisplayedArticle :: ArticleDB -> YiM ()
setDisplayedArticle newdb = do
let next = getLatestArticle newdb
withCurrentBuffer $ do
replaceBufferContent $ R.fromString (B.unpack next)
topB
putBufferDyn newdb
nextArticle :: YiM ()
nextArticle = do
(oldb,_) <- oldDbNewArticle
let newdb = removeSetLast oldb (getLatestArticle oldb)
writeDB newdb
setDisplayedArticle newdb
deleteAndNextArticle :: YiM ()
deleteAndNextArticle = do
(oldb,_) <- oldDbNewArticle
let ndb = ADB $ case viewl (unADB oldb) of
EmptyL -> empty
(_ :< b) -> b
writeDB ndb
setDisplayedArticle ndb
saveAndNextArticle :: Int -> YiM ()
saveAndNextArticle n = do
(oldb,newa) <- oldDbNewArticle
let newdb = shift n $ removeSetLast oldb newa
writeDB newdb
setDisplayedArticle newdb
saveAsNewArticle :: YiM ()
saveAsNewArticle = do
oldb <- readDB
(_,newa) <- oldDbNewArticle
let newdb = insertArticle oldb newa
writeDB newdb