{-# LANGUAGE CPP, FlexibleContexts, OverloadedStrings, RecordWildCards #-}
module Database.MongoDB.Admin (
CollectionOption(..), createCollection, renameCollection, dropCollection,
validateCollection,
Index(..), IndexName, index, ensureIndex, createIndex, dropIndex,
getIndexes, dropIndexes,
allUsers, addUser, removeUser,
admin, cloneDatabase, copyDatabase, dropDatabase, repairDatabase,
serverBuildInfo, serverVersion,
collectionStats, dataSize, storageSize, totalIndexSize, totalSize,
ProfilingLevel(..), getProfilingLevel, MilliSec, setProfilingLevel,
dbStats, OpNum, currentOp, killOp,
serverStatus
) where
import Prelude hiding (lookup)
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative ((<$>))
#endif
import Control.Concurrent (forkIO, threadDelay)
import Control.Monad (forever, unless, liftM)
import Control.Monad.Fail(MonadFail)
import Data.IORef (IORef, newIORef, readIORef, writeIORef)
import Data.Maybe (maybeToList)
import Data.Set (Set)
import System.IO.Unsafe (unsafePerformIO)
import qualified Data.HashTable.IO as H
import qualified Data.Set as Set
import Control.Monad.Trans (MonadIO, liftIO)
import Data.Bson (Document, Field(..), at, (=:), (=?), exclude, merge)
import Data.Text (Text)
import qualified Data.Text as T
import Database.MongoDB.Connection (Host, showHostPort)
import Database.MongoDB.Internal.Protocol (pwHash, pwKey)
import Database.MongoDB.Internal.Util ((<.>), true1)
import Database.MongoDB.Query (Action, Database, Collection, Username, Password,
Order, Query(..), accessMode, master, runCommand,
useDb, thisDatabase, rest, select, find, findOne,
insert_, save, delete)
data CollectionOption = Capped | MaxByteSize Int | MaxItems Int deriving (Show, Eq)
coptElem :: CollectionOption -> Field
coptElem Capped = "capped" =: True
coptElem (MaxByteSize n) = "size" =: n
coptElem (MaxItems n) = "max" =: n
createCollection :: (MonadIO m) => [CollectionOption] -> Collection -> Action m Document
createCollection opts col = runCommand $ ["create" =: col] ++ map coptElem opts
renameCollection :: (MonadIO m) => Collection -> Collection -> Action m Document
renameCollection from to = do
db <- thisDatabase
useDb admin $ runCommand ["renameCollection" =: db <.> from, "to" =: db <.> to, "dropTarget" =: True]
dropCollection :: (MonadIO m, MonadFail m) => Collection -> Action m Bool
dropCollection coll = do
resetIndexCache
r <- runCommand ["drop" =: coll]
if true1 "ok" r then return True else do
if at "errmsg" r == ("ns not found" :: Text) then return False else
fail $ "dropCollection failed: " ++ show r
validateCollection :: (MonadIO m) => Collection -> Action m Document
validateCollection coll = runCommand ["validate" =: coll]
type IndexName = Text
data Index = Index {
iColl :: Collection,
iKey :: Order,
iName :: IndexName,
iUnique :: Bool,
iDropDups :: Bool,
iExpireAfterSeconds :: Maybe Int
} deriving (Show, Eq)
idxDocument :: Index -> Database -> Document
idxDocument Index{..} db = [
"ns" =: db <.> iColl,
"key" =: iKey,
"name" =: iName,
"unique" =: iUnique,
"dropDups" =: iDropDups ] ++ (maybeToList $ fmap ((=:) "expireAfterSeconds") iExpireAfterSeconds)
index :: Collection -> Order -> Index
index coll keys = Index coll keys (genName keys) False False Nothing
genName :: Order -> IndexName
genName keys = T.intercalate "_" (map f keys) where
f (k := v) = k `T.append` "_" `T.append` T.pack (show v)
ensureIndex :: (MonadIO m) => Index -> Action m ()
ensureIndex idx = let k = (iColl idx, iName idx) in do
icache <- fetchIndexCache
set <- liftIO (readIORef icache)
unless (Set.member k set) $ do
accessMode master (createIndex idx)
liftIO $ writeIORef icache (Set.insert k set)
createIndex :: (MonadIO m) => Index -> Action m ()
createIndex idx = insert_ "system.indexes" . idxDocument idx =<< thisDatabase
dropIndex :: (MonadIO m) => Collection -> IndexName -> Action m Document
dropIndex coll idxName = do
resetIndexCache
runCommand ["deleteIndexes" =: coll, "index" =: idxName]
getIndexes :: MonadIO m => Collection -> Action m [Document]
getIndexes coll = do
db <- thisDatabase
rest =<< find (select ["ns" =: db <.> coll] "system.indexes")
dropIndexes :: (MonadIO m) => Collection -> Action m Document
dropIndexes coll = do
resetIndexCache
runCommand ["deleteIndexes" =: coll, "index" =: ("*" :: Text)]
type DbIndexCache = H.BasicHashTable Database IndexCache
type IndexCache = IORef (Set (Collection, IndexName))
dbIndexCache :: DbIndexCache
dbIndexCache = unsafePerformIO $ do
table <- H.new
_ <- forkIO . forever $ threadDelay 900000000 >> clearDbIndexCache
return table
{-# NOINLINE dbIndexCache #-}
clearDbIndexCache :: IO ()
clearDbIndexCache = do
keys <- map fst <$> H.toList dbIndexCache
mapM_ (H.delete dbIndexCache) keys
fetchIndexCache :: (MonadIO m) => Action m IndexCache
fetchIndexCache = do
db <- thisDatabase
liftIO $ do
mc <- H.lookup dbIndexCache db
maybe (newIdxCache db) return mc
where
newIdxCache db = do
idx <- newIORef Set.empty
H.insert dbIndexCache db idx
return idx
resetIndexCache :: (MonadIO m) => Action m ()
resetIndexCache = do
icache <- fetchIndexCache
liftIO (writeIORef icache Set.empty)
allUsers :: MonadIO m => Action m [Document]
allUsers = map (exclude ["_id"]) `liftM` (rest =<< find
(select [] "system.users") {sort = ["user" =: (1 :: Int)], project = ["user" =: (1 :: Int), "readOnly" =: (1 :: Int)]})
addUser :: (MonadIO m)
=> Bool -> Username -> Password -> Action m ()
addUser readOnly user pass = do
mu <- findOne (select ["user" =: user] "system.users")
let usr = merge ["readOnly" =: readOnly, "pwd" =: pwHash user pass] (maybe ["user" =: user] id mu)
save "system.users" usr
removeUser :: (MonadIO m)
=> Username -> Action m ()
removeUser user = delete (select ["user" =: user] "system.users")
admin :: Database
admin = "admin"
cloneDatabase :: (MonadIO m) => Database -> Host -> Action m Document
cloneDatabase db fromHost = useDb db $ runCommand ["clone" =: showHostPort fromHost]
copyDatabase :: (MonadIO m) => Database -> Host -> Maybe (Username, Password) -> Database -> Action m Document
copyDatabase fromDb fromHost mup toDb = do
let c = ["copydb" =: (1 :: Int), "fromhost" =: showHostPort fromHost, "fromdb" =: fromDb, "todb" =: toDb]
useDb admin $ case mup of
Nothing -> runCommand c
Just (usr, pss) -> do
n <- at "nonce" `liftM` runCommand ["copydbgetnonce" =: (1 :: Int), "fromhost" =: showHostPort fromHost]
runCommand $ c ++ ["username" =: usr, "nonce" =: n, "key" =: pwKey n usr pss]
dropDatabase :: (MonadIO m) => Database -> Action m Document
dropDatabase db = useDb db $ runCommand ["dropDatabase" =: (1 :: Int)]
repairDatabase :: (MonadIO m) => Database -> Action m Document
repairDatabase db = useDb db $ runCommand ["repairDatabase" =: (1 :: Int)]
serverBuildInfo :: (MonadIO m) => Action m Document
serverBuildInfo = useDb admin $ runCommand ["buildinfo" =: (1 :: Int)]
serverVersion :: (MonadIO m) => Action m Text
serverVersion = at "version" `liftM` serverBuildInfo
collectionStats :: (MonadIO m) => Collection -> Action m Document
collectionStats coll = runCommand ["collstats" =: coll]
dataSize :: (MonadIO m) => Collection -> Action m Int
dataSize c = at "size" `liftM` collectionStats c
storageSize :: (MonadIO m) => Collection -> Action m Int
storageSize c = at "storageSize" `liftM` collectionStats c
totalIndexSize :: (MonadIO m) => Collection -> Action m Int
totalIndexSize c = at "totalIndexSize" `liftM` collectionStats c
totalSize :: MonadIO m => Collection -> Action m Int
totalSize coll = do
x <- storageSize coll
xs <- mapM isize =<< getIndexes coll
return (foldl (+) x xs)
where
isize idx = at "storageSize" `liftM` collectionStats (coll `T.append` ".$" `T.append` at "name" idx)
data ProfilingLevel = Off | Slow | All deriving (Show, Enum, Eq)
getProfilingLevel :: (MonadIO m) => Action m ProfilingLevel
getProfilingLevel = (toEnum . at "was") `liftM` runCommand ["profile" =: (-1 :: Int)]
type MilliSec = Int
setProfilingLevel :: (MonadIO m) => ProfilingLevel -> Maybe MilliSec -> Action m ()
setProfilingLevel p mSlowMs =
runCommand (["profile" =: fromEnum p] ++ ("slowms" =? mSlowMs)) >> return ()
dbStats :: (MonadIO m) => Action m Document
dbStats = runCommand ["dbstats" =: (1 :: Int)]
currentOp :: (MonadIO m) => Action m (Maybe Document)
currentOp = findOne (select [] "$cmd.sys.inprog")
type OpNum = Int
killOp :: (MonadIO m) => OpNum -> Action m (Maybe Document)
killOp op = findOne (select ["op" =: op] "$cmd.sys.killop")
serverStatus :: (MonadIO m) => Action m Document
serverStatus = useDb admin $ runCommand ["serverStatus" =: (1 :: Int)]