2012-03-13 05:31:13 +01:00
|
|
|
|
module BlogDB where
|
|
|
|
|
|
2015-11-21 02:59:03 +01:00
|
|
|
|
import Control.Monad.Reader (ask)
|
|
|
|
|
import Control.Monad.State (get, put)
|
|
|
|
|
import Data.Acid
|
|
|
|
|
import Data.Acid.Advanced
|
|
|
|
|
import Data.Acid.Remote
|
|
|
|
|
import Data.ByteString (ByteString)
|
|
|
|
|
import Data.Data (Data, Typeable)
|
2015-11-21 03:18:08 +01:00
|
|
|
|
import Data.IxSet (Indexable (..), IxSet, Proxy (..), getOne, ixFun, ixSet, (@=))
|
|
|
|
|
import Data.SafeCopy (base, deriveSafeCopy)
|
2015-11-21 02:59:03 +01:00
|
|
|
|
import Data.Text (Text, pack)
|
|
|
|
|
import Data.Time
|
|
|
|
|
import Network (PortID (..))
|
|
|
|
|
import System.Environment (getEnv)
|
2013-04-28 14:30:00 +02:00
|
|
|
|
|
|
|
|
|
import qualified Crypto.Hash.SHA512 as SHA (hash)
|
2012-03-13 05:31:13 +01:00
|
|
|
|
import qualified Data.ByteString.Base64 as B64 (encode)
|
2013-04-28 14:30:00 +02:00
|
|
|
|
import qualified Data.ByteString.Char8 as B
|
|
|
|
|
import qualified Data.IxSet as IxSet
|
2012-03-13 05:31:13 +01:00
|
|
|
|
|
|
|
|
|
newtype EntryId = EntryId { unEntryId :: Integer }
|
2014-05-08 15:57:10 +02:00
|
|
|
|
deriving (Eq, Ord, Data, Enum, Typeable)
|
|
|
|
|
|
2014-08-22 15:56:03 +02:00
|
|
|
|
$(deriveSafeCopy 2 'base ''EntryId)
|
2012-03-13 05:31:13 +01:00
|
|
|
|
|
|
|
|
|
instance Show EntryId where
|
|
|
|
|
show = show . unEntryId
|
|
|
|
|
|
2013-04-28 14:30:00 +02:00
|
|
|
|
data BlogLang = EN | DE
|
2012-03-13 05:31:13 +01:00
|
|
|
|
deriving (Eq, Ord, Data, Typeable)
|
|
|
|
|
|
|
|
|
|
instance Show BlogLang where
|
|
|
|
|
show DE = "de"
|
|
|
|
|
show EN = "en"
|
|
|
|
|
|
|
|
|
|
$(deriveSafeCopy 0 'base ''BlogLang)
|
|
|
|
|
|
|
|
|
|
data Entry = Entry {
|
2015-11-21 02:59:03 +01:00
|
|
|
|
entryId :: EntryId,
|
|
|
|
|
lang :: BlogLang,
|
|
|
|
|
author :: Text,
|
|
|
|
|
title :: Text,
|
|
|
|
|
btext :: Text,
|
|
|
|
|
mtext :: Text,
|
|
|
|
|
edate :: UTCTime
|
2012-03-13 05:31:13 +01:00
|
|
|
|
} deriving (Eq, Ord, Show, Data, Typeable)
|
|
|
|
|
|
2014-08-22 15:56:03 +02:00
|
|
|
|
$(deriveSafeCopy 2 'base ''Entry)
|
2012-03-13 05:31:13 +01:00
|
|
|
|
|
|
|
|
|
-- ixSet requires different datatypes for field indexes, so let's define some
|
2014-05-08 15:57:10 +02:00
|
|
|
|
newtype Author = Author Text deriving (Eq, Ord, Data, Typeable)
|
|
|
|
|
newtype Title = Title Text deriving (Eq, Ord, Data, Typeable)
|
|
|
|
|
newtype BText = BText Text deriving (Eq, Ord, Data, Typeable) -- standard text
|
|
|
|
|
newtype MText = MText Text deriving (Eq, Ord, Data, Typeable) -- "read more" text
|
|
|
|
|
newtype Tag = Tag Text deriving (Eq, Ord, Data, Typeable)
|
|
|
|
|
newtype EDate = EDate UTCTime deriving (Eq, Ord, Data, Typeable)
|
|
|
|
|
newtype SDate = SDate UTCTime deriving (Eq, Ord, Data, Typeable)
|
|
|
|
|
newtype Username = Username Text deriving (Eq, Ord, Data, Typeable)
|
|
|
|
|
newtype SessionID = SessionID Text deriving (Eq, Ord, Data, Typeable)
|
|
|
|
|
|
2014-08-22 15:56:03 +02:00
|
|
|
|
$(deriveSafeCopy 2 'base ''Author)
|
|
|
|
|
$(deriveSafeCopy 2 'base ''Title)
|
|
|
|
|
$(deriveSafeCopy 2 'base ''BText)
|
|
|
|
|
$(deriveSafeCopy 2 'base ''MText)
|
|
|
|
|
$(deriveSafeCopy 2 'base ''Tag)
|
|
|
|
|
$(deriveSafeCopy 2 'base ''EDate)
|
|
|
|
|
$(deriveSafeCopy 2 'base ''SDate)
|
|
|
|
|
$(deriveSafeCopy 2 'base ''Username)
|
|
|
|
|
$(deriveSafeCopy 2 'base ''SessionID)
|
2012-03-13 05:31:13 +01:00
|
|
|
|
|
2013-04-28 14:30:00 +02:00
|
|
|
|
instance Indexable Entry where
|
2012-03-13 05:31:13 +01:00
|
|
|
|
empty = ixSet [ ixFun $ \e -> [ entryId e]
|
|
|
|
|
, ixFun $ (:[]) . lang
|
|
|
|
|
, ixFun $ \e -> [ Author $ author e ]
|
|
|
|
|
, ixFun $ \e -> [ Title $ title e]
|
|
|
|
|
, ixFun $ \e -> [ BText $ btext e]
|
|
|
|
|
, ixFun $ \e -> [ MText $ mtext e]
|
|
|
|
|
, ixFun $ \e -> [ EDate $ edate e]
|
|
|
|
|
]
|
|
|
|
|
|
|
|
|
|
data User = User {
|
|
|
|
|
username :: Text,
|
|
|
|
|
password :: ByteString
|
|
|
|
|
} deriving (Eq, Ord, Data, Typeable)
|
|
|
|
|
|
|
|
|
|
$(deriveSafeCopy 0 'base ''User)
|
|
|
|
|
|
|
|
|
|
data Session = Session {
|
|
|
|
|
sessionID :: Text,
|
|
|
|
|
user :: User,
|
|
|
|
|
sdate :: UTCTime
|
|
|
|
|
} deriving (Eq, Ord, Data, Typeable)
|
|
|
|
|
|
|
|
|
|
$(deriveSafeCopy 0 'base ''Session)
|
|
|
|
|
|
|
|
|
|
instance Indexable User where
|
|
|
|
|
empty = ixSet [ ixFun $ \u -> [Username $ username u]
|
2013-04-28 14:30:00 +02:00
|
|
|
|
, ixFun $ (:[]) . password
|
2012-03-13 05:31:13 +01:00
|
|
|
|
]
|
|
|
|
|
|
|
|
|
|
instance Indexable Session where
|
|
|
|
|
empty = ixSet [ ixFun $ \s -> [SessionID $ sessionID s]
|
|
|
|
|
, ixFun $ (:[]) . user
|
|
|
|
|
, ixFun $ \s -> [SDate $ sdate s]
|
|
|
|
|
]
|
|
|
|
|
|
|
|
|
|
data Blog = Blog {
|
|
|
|
|
blogSessions :: IxSet Session,
|
|
|
|
|
blogUsers :: IxSet User,
|
|
|
|
|
blogEntries :: IxSet Entry
|
|
|
|
|
} deriving (Data, Typeable)
|
|
|
|
|
|
|
|
|
|
$(deriveSafeCopy 0 'base ''Blog)
|
|
|
|
|
|
2013-04-28 14:30:00 +02:00
|
|
|
|
initialBlogState :: Blog
|
|
|
|
|
initialBlogState =
|
2012-03-13 05:31:13 +01:00
|
|
|
|
Blog { blogSessions = empty
|
|
|
|
|
, blogUsers = empty
|
|
|
|
|
, blogEntries = empty }
|
|
|
|
|
|
|
|
|
|
-- acid-state database functions (purity is necessary!)
|
|
|
|
|
|
|
|
|
|
insertEntry :: Entry -> Update Blog Entry
|
2013-04-28 14:30:00 +02:00
|
|
|
|
insertEntry e =
|
2012-03-13 05:31:13 +01:00
|
|
|
|
do b@Blog{..} <- get
|
|
|
|
|
put $ b { blogEntries = IxSet.insert e blogEntries }
|
|
|
|
|
return e
|
|
|
|
|
|
|
|
|
|
updateEntry :: Entry -> Update Blog Entry
|
2013-04-28 14:30:00 +02:00
|
|
|
|
updateEntry e =
|
2012-03-13 05:31:13 +01:00
|
|
|
|
do b@Blog{..} <- get
|
2015-11-24 14:07:31 +01:00
|
|
|
|
put $ b { blogEntries = IxSet.updateIx (entryId e) e blogEntries }
|
2012-03-13 05:31:13 +01:00
|
|
|
|
return e
|
|
|
|
|
|
2015-11-24 14:07:31 +01:00
|
|
|
|
deleteEntry :: EntryId -> Update Blog EntryId
|
|
|
|
|
deleteEntry entry =
|
|
|
|
|
do b@Blog{..} <- get
|
|
|
|
|
put $ b { blogEntries = IxSet.deleteIx entry blogEntries }
|
|
|
|
|
return entry
|
|
|
|
|
|
2012-03-13 05:31:13 +01:00
|
|
|
|
getEntry :: EntryId -> Query Blog (Maybe Entry)
|
|
|
|
|
getEntry eId =
|
2015-11-21 03:18:08 +01:00
|
|
|
|
do Blog{..} <- ask
|
2012-03-13 05:31:13 +01:00
|
|
|
|
return $ getOne $ blogEntries @= eId
|
|
|
|
|
|
|
|
|
|
latestEntries :: BlogLang -> Query Blog [Entry]
|
|
|
|
|
latestEntries lang =
|
2015-11-21 03:18:08 +01:00
|
|
|
|
do Blog{..} <- ask
|
2012-03-13 05:31:13 +01:00
|
|
|
|
return $ IxSet.toDescList (Proxy :: Proxy EDate) $ blogEntries @= lang
|
|
|
|
|
|
2012-03-13 06:35:56 +01:00
|
|
|
|
addSession :: Session -> Update Blog Session
|
|
|
|
|
addSession nSession =
|
2012-03-13 05:31:13 +01:00
|
|
|
|
do b@Blog{..} <- get
|
2012-03-13 06:35:56 +01:00
|
|
|
|
put $ b { blogSessions = IxSet.insert nSession blogSessions}
|
|
|
|
|
return nSession
|
2012-03-13 05:31:13 +01:00
|
|
|
|
|
|
|
|
|
getSession :: SessionID -> Query Blog (Maybe Session)
|
|
|
|
|
getSession sId =
|
2015-11-21 03:18:08 +01:00
|
|
|
|
do Blog{..} <- ask
|
2012-03-13 05:31:13 +01:00
|
|
|
|
return $ getOne $ blogSessions @= sId
|
|
|
|
|
|
2012-03-13 21:29:06 +01:00
|
|
|
|
clearSessions :: Update Blog [Session]
|
|
|
|
|
clearSessions =
|
|
|
|
|
do b@Blog{..} <- get
|
|
|
|
|
put $ b { blogSessions = empty }
|
|
|
|
|
return []
|
|
|
|
|
|
2012-03-13 05:31:13 +01:00
|
|
|
|
addUser :: Text -> String -> Update Blog User
|
|
|
|
|
addUser un pw =
|
|
|
|
|
do b@Blog{..} <- get
|
|
|
|
|
let u = User un $ hashString pw
|
|
|
|
|
put $ b { blogUsers = IxSet.insert u blogUsers}
|
|
|
|
|
return u
|
|
|
|
|
|
|
|
|
|
getUser :: Username -> Query Blog (Maybe User)
|
|
|
|
|
getUser uN =
|
2015-11-21 03:18:08 +01:00
|
|
|
|
do Blog{..} <- ask
|
2012-03-13 05:31:13 +01:00
|
|
|
|
return $ getOne $ blogUsers @= uN
|
|
|
|
|
|
2013-04-28 14:44:14 +02:00
|
|
|
|
checkUser :: Username -> String -> Query Blog Bool
|
2012-03-13 05:31:13 +01:00
|
|
|
|
checkUser uN pw =
|
2015-11-21 03:18:08 +01:00
|
|
|
|
do Blog{..} <- ask
|
2012-03-13 05:31:13 +01:00
|
|
|
|
let user = getOne $ blogUsers @= uN
|
|
|
|
|
case user of
|
|
|
|
|
Nothing -> return False
|
2013-04-28 14:44:14 +02:00
|
|
|
|
(Just u) -> return $ password u == hashString pw
|
2012-03-13 05:31:13 +01:00
|
|
|
|
|
|
|
|
|
-- various functions
|
|
|
|
|
hashString :: String -> ByteString
|
|
|
|
|
hashString = B64.encode . SHA.hash . B.pack
|
|
|
|
|
|
|
|
|
|
$(makeAcidic ''Blog
|
|
|
|
|
[ 'insertEntry
|
|
|
|
|
, 'updateEntry
|
2015-11-24 14:07:31 +01:00
|
|
|
|
, 'deleteEntry
|
2012-03-13 05:31:13 +01:00
|
|
|
|
, 'getEntry
|
|
|
|
|
, 'latestEntries
|
|
|
|
|
, 'addSession
|
|
|
|
|
, 'getSession
|
|
|
|
|
, 'addUser
|
|
|
|
|
, 'getUser
|
|
|
|
|
, 'checkUser
|
2012-03-13 21:29:06 +01:00
|
|
|
|
, 'clearSessions
|
2012-03-13 05:31:13 +01:00
|
|
|
|
])
|
|
|
|
|
|
2015-11-21 02:59:03 +01:00
|
|
|
|
interactiveUserAdd :: String -> IO ()
|
|
|
|
|
interactiveUserAdd dbHost = do
|
|
|
|
|
acid <- openRemoteState skipAuthenticationPerform dbHost (PortNumber 8070)
|
2012-03-13 06:35:56 +01:00
|
|
|
|
putStrLn "Username:"
|
|
|
|
|
un <- getLine
|
|
|
|
|
putStrLn "Password:"
|
|
|
|
|
pw <- getLine
|
|
|
|
|
update' acid (AddUser (pack un) pw)
|
2012-03-14 00:37:00 +01:00
|
|
|
|
closeAcidState acid
|
2012-03-13 21:29:06 +01:00
|
|
|
|
|
|
|
|
|
flushSessions :: IO ()
|
|
|
|
|
flushSessions = do
|
|
|
|
|
tbDir <- getEnv "TAZBLOG"
|
|
|
|
|
acid <- openLocalStateFrom (tbDir ++ "/BlogState") initialBlogState
|
2013-04-28 14:44:14 +02:00
|
|
|
|
update' acid ClearSessions
|
2012-03-14 00:37:00 +01:00
|
|
|
|
closeAcidState acid
|
|
|
|
|
|
|
|
|
|
archiveState :: IO ()
|
|
|
|
|
archiveState = do
|
|
|
|
|
tbDir <- getEnv "TAZBLOG"
|
|
|
|
|
acid <- openLocalStateFrom (tbDir ++ "/BlogState") initialBlogState
|
|
|
|
|
createArchive acid
|
|
|
|
|
closeAcidState acid
|