2010-06-15 03:14:40 +00:00
-- | Database administrative functions
2011-12-05 17:23:39 +00:00
{- # LANGUAGE FlexibleContexts, OverloadedStrings, RecordWildCards # -}
2010-06-15 03:14:40 +00:00
module Database.MongoDB.Admin (
-- * Admin
-- ** Collection
2012-06-10 19:47:14 +00:00
CollectionOption ( .. ) , createCollection , renameCollection , dropCollection ,
validateCollection ,
2010-06-15 03:14:40 +00:00
-- ** Index
2012-06-10 19:47:14 +00:00
Index ( .. ) , IndexName , index , ensureIndex , createIndex , dropIndex ,
getIndexes , dropIndexes ,
2010-06-15 03:14:40 +00:00
-- ** User
allUsers , addUser , removeUser ,
-- ** Database
2010-10-27 20:13:23 +00:00
admin , cloneDatabase , copyDatabase , dropDatabase , repairDatabase ,
2010-06-15 03:14:40 +00:00
-- ** Server
serverBuildInfo , serverVersion ,
-- * Diagnotics
-- ** Collection
collectionStats , dataSize , storageSize , totalIndexSize , totalSize ,
-- ** Profiling
2011-09-07 16:03:52 +00:00
ProfilingLevel ( .. ) , getProfilingLevel , MilliSec , setProfilingLevel ,
2010-06-15 03:14:40 +00:00
-- ** Database
dbStats , OpNum , currentOp , killOp ,
-- ** Server
serverStatus
) where
import Prelude hiding ( lookup )
import Control.Applicative ( ( <$> ) )
2012-06-10 19:47:14 +00:00
import Control.Concurrent ( forkIO , threadDelay )
import Control.Monad ( forever , unless )
import Data.IORef ( IORef , newIORef , readIORef , writeIORef )
import Data.Set ( Set )
import System.IO.Unsafe ( unsafePerformIO )
import qualified Data.HashTable as H
import qualified Data.Set as Set
import Control.Monad.Trans ( MonadIO , liftIO )
import Control.Monad.Trans.Control ( MonadBaseControl )
import Data.Bson ( Document , Field ( .. ) , at , ( =: ) , ( =? ) , exclude , merge )
2012-05-08 15:13:25 +00:00
import Data.Text ( Text )
2012-06-10 19:47:14 +00:00
2012-05-08 15:13:25 +00:00
import qualified Data.Text as T
2012-06-10 19:47:14 +00:00
import Database.MongoDB.Connection ( Host , showHostPort )
import Database.MongoDB.Internal.Protocol ( pwHash , pwKey )
2011-07-05 14:37:01 +00:00
import Database.MongoDB.Internal.Util ( MonadIO ' , ( <.> ) , true1 )
2012-06-10 19:47:14 +00:00
import Database.MongoDB.Query ( Action , Database , Collection , Username , Password ,
Order , Query ( .. ) , accessMode , master , runCommand ,
useDb , thisDatabase , rest , select , find , findOne ,
insert_ , save , delete )
2010-06-15 03:14:40 +00:00
-- * Admin
-- ** Collection
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
2011-07-05 14:37:01 +00:00
createCollection :: ( MonadIO' m ) => [ CollectionOption ] -> Collection -> Action m Document
2010-06-15 03:14:40 +00:00
-- ^ Create collection with given options. You only need to call this to set options, otherwise a collection is created automatically on first use with no options.
createCollection opts col = runCommand $ [ " create " =: col ] ++ map coptElem opts
2011-07-05 14:37:01 +00:00
renameCollection :: ( MonadIO' m ) => Collection -> Collection -> Action m Document
2010-06-15 03:14:40 +00:00
-- ^ Rename first collection to second collection
2010-06-21 15:06:20 +00:00
renameCollection from to = do
2011-07-05 14:37:01 +00:00
db <- thisDatabase
useDb admin $ runCommand [ " renameCollection " =: db <.> from , " to " =: db <.> to , " dropTarget " =: True ]
2010-06-15 03:14:40 +00:00
2011-07-05 14:37:01 +00:00
dropCollection :: ( MonadIO' m ) => Collection -> Action m Bool
2010-06-15 03:14:40 +00:00
-- ^ Delete the given collection! Return True if collection existed (and was deleted); return False if collection did not exist (and no action).
dropCollection coll = do
resetIndexCache
r <- runCommand [ " drop " =: coll ]
if true1 " ok " r then return True else do
2012-05-08 15:13:25 +00:00
if at " errmsg " r == ( " ns not found " :: Text ) then return False else
2010-06-15 03:14:40 +00:00
fail $ " dropCollection failed: " ++ show r
2011-07-05 14:37:01 +00:00
validateCollection :: ( MonadIO' m ) => Collection -> Action m Document
2010-06-15 03:14:40 +00:00
-- ^ This operation takes a while
validateCollection coll = runCommand [ " validate " =: coll ]
-- ** Index
2012-05-08 15:13:25 +00:00
type IndexName = Text
2010-06-15 03:14:40 +00:00
data Index = Index {
iColl :: Collection ,
iKey :: Order ,
iName :: IndexName ,
iUnique :: Bool ,
iDropDups :: Bool
} deriving ( Show , Eq )
idxDocument :: Index -> Database -> Document
2011-07-05 14:37:01 +00:00
idxDocument Index { .. } db = [
2010-06-15 03:14:40 +00:00
" ns " =: db <.> iColl ,
" key " =: iKey ,
" name " =: iName ,
" unique " =: iUnique ,
" dropDups " =: iDropDups ]
index :: Collection -> Order -> Index
-- ^ Spec of index of ordered keys on collection. Name is generated from keys. Unique and dropDups are False.
index coll keys = Index coll keys ( genName keys ) False False
genName :: Order -> IndexName
2012-05-08 15:13:25 +00:00
genName keys = T . intercalate " _ " ( map f keys ) where
f ( k := v ) = k ` T . append ` " _ " ` T . append ` T . pack ( show v )
2010-06-15 03:14:40 +00:00
2011-07-05 14:37:01 +00:00
ensureIndex :: ( MonadIO' m ) => Index -> Action m ()
2010-06-15 03:14:40 +00:00
-- ^ Create index if we did not already create one. May be called repeatedly with practically no performance hit, because we remember if we already called this for the same index (although this memory gets wiped out every 15 minutes, in case another client drops the index and we want to create it again).
ensureIndex idx = let k = ( iColl idx , iName idx ) in do
icache <- fetchIndexCache
set <- liftIO ( readIORef icache )
2012-06-10 19:47:14 +00:00
unless ( Set . member k set ) $ do
2011-07-09 02:13:47 +00:00
accessMode master ( createIndex idx )
2012-06-10 19:47:14 +00:00
liftIO $ writeIORef icache ( Set . insert k set )
2010-06-21 15:06:20 +00:00
2011-07-05 14:37:01 +00:00
createIndex :: ( MonadIO' m ) => Index -> Action m ()
2010-06-15 03:14:40 +00:00
-- ^ Create index on the server. This call goes to the server every time.
createIndex idx = insert_ " system.indexes " . idxDocument idx =<< thisDatabase
2011-07-05 14:37:01 +00:00
dropIndex :: ( MonadIO' m ) => Collection -> IndexName -> Action m Document
2010-06-15 03:14:40 +00:00
-- ^ Remove the index
dropIndex coll idxName = do
resetIndexCache
runCommand [ " deleteIndexes " =: coll , " index " =: idxName ]
2011-12-05 17:23:39 +00:00
getIndexes :: ( MonadIO m , MonadBaseControl IO m , Functor m ) => Collection -> Action m [ Document ]
2010-06-15 03:14:40 +00:00
-- ^ Get all indexes on this collection
getIndexes coll = do
2011-07-05 14:37:01 +00:00
db <- thisDatabase
2010-06-21 15:06:20 +00:00
rest =<< find ( select [ " ns " =: db <.> coll ] " system.indexes " )
2010-06-15 03:14:40 +00:00
2011-07-05 14:37:01 +00:00
dropIndexes :: ( MonadIO' m ) => Collection -> Action m Document
2010-06-15 03:14:40 +00:00
-- ^ Drop all indexes on this collection
dropIndexes coll = do
resetIndexCache
2012-05-08 15:13:25 +00:00
runCommand [ " deleteIndexes " =: coll , " index " =: ( " * " :: Text ) ]
2010-06-15 03:14:40 +00:00
-- *** Index cache
2012-05-08 15:13:25 +00:00
type DbIndexCache = H . HashTable Database IndexCache
2010-06-15 03:14:40 +00:00
-- ^ Cache the indexes we create so repeatedly calling ensureIndex only hits database the first time. Clear cache every once in a while so if someone else deletes index we will recreate it on ensureIndex.
2012-06-10 19:47:14 +00:00
type IndexCache = IORef ( Set ( Collection , IndexName ) )
2010-06-15 03:14:40 +00:00
dbIndexCache :: DbIndexCache
-- ^ initialize cache and fork thread that clears it every 15 minutes
dbIndexCache = unsafePerformIO $ do
2012-05-08 15:13:25 +00:00
table <- H . new ( == ) ( H . hashString . T . unpack )
2010-06-15 03:14:40 +00:00
_ <- forkIO . forever $ threadDelay 900000000 >> clearDbIndexCache
return table
{- # NOINLINE dbIndexCache # -}
clearDbIndexCache :: IO ()
clearDbIndexCache = do
2012-05-08 15:13:25 +00:00
keys <- map fst <$> H . toList dbIndexCache
mapM_ ( H . delete dbIndexCache ) keys
2010-06-15 03:14:40 +00:00
2011-07-05 14:37:01 +00:00
fetchIndexCache :: ( MonadIO m ) => Action m IndexCache
2010-06-15 03:14:40 +00:00
-- ^ Get index cache for current database
2010-06-21 15:06:20 +00:00
fetchIndexCache = do
db <- thisDatabase
liftIO $ do
2012-05-08 15:13:25 +00:00
mc <- H . lookup dbIndexCache db
2010-06-21 15:06:20 +00:00
maybe ( newIdxCache db ) return mc
2010-06-15 03:14:40 +00:00
where
newIdxCache db = do
2012-06-10 19:47:14 +00:00
idx <- newIORef Set . empty
2012-05-08 15:13:25 +00:00
H . insert dbIndexCache db idx
2010-06-15 03:14:40 +00:00
return idx
2011-07-05 14:37:01 +00:00
resetIndexCache :: ( MonadIO m ) => Action m ()
2010-06-15 03:14:40 +00:00
-- ^ reset index cache for current database
resetIndexCache = do
icache <- fetchIndexCache
2012-06-10 19:47:14 +00:00
liftIO ( writeIORef icache Set . empty )
2010-06-15 03:14:40 +00:00
-- ** User
2011-12-05 17:23:39 +00:00
allUsers :: ( MonadIO m , MonadBaseControl IO m , Functor m ) => Action m [ Document ]
2010-06-15 03:14:40 +00:00
-- ^ Fetch all users of this database
allUsers = map ( exclude [ " _id " ] ) <$> ( rest =<< find
2010-06-21 15:06:20 +00:00
( select [] " system.users " ) { sort = [ " user " =: ( 1 :: Int ) ] , project = [ " user " =: ( 1 :: Int ) , " readOnly " =: ( 1 :: Int ) ] } )
2010-06-15 03:14:40 +00:00
2011-07-05 14:37:01 +00:00
addUser :: ( MonadIO' m ) => Bool -> Username -> Password -> Action m ()
2010-06-15 03:14:40 +00:00
-- ^ Add user with password with read-only access if bool is True or read-write access if bool is False
addUser readOnly user pass = do
2010-06-21 15:06:20 +00:00
mu <- findOne ( select [ " user " =: user ] " system.users " )
2010-12-27 05:23:02 +00:00
let usr = merge [ " readOnly " =: readOnly , " pwd " =: pwHash user pass ] ( maybe [ " user " =: user ] id mu )
save " system.users " usr
2010-06-15 03:14:40 +00:00
2011-07-05 14:37:01 +00:00
removeUser :: ( MonadIO m ) => Username -> Action m ()
2010-06-21 15:06:20 +00:00
removeUser user = delete ( select [ " user " =: user ] " system.users " )
2010-06-15 03:14:40 +00:00
-- ** Database
2010-10-27 20:46:11 +00:00
admin :: Database
2010-10-27 20:13:23 +00:00
-- ^ \"admin\" database
2011-07-05 14:37:01 +00:00
admin = " admin "
2010-10-27 20:13:23 +00:00
2011-07-05 14:37:01 +00:00
cloneDatabase :: ( MonadIO' m ) => Database -> Host -> Action m Document
2010-07-27 21:18:53 +00:00
-- ^ Copy database from given host to the server I am connected to. Fails and returns @"ok" = 0@ if we don't have permission to read from given server (use copyDatabase in this case).
2011-07-05 14:37:01 +00:00
cloneDatabase db fromHost = useDb db $ runCommand [ " clone " =: showHostPort fromHost ]
2010-06-15 03:14:40 +00:00
2011-07-05 14:37:01 +00:00
copyDatabase :: ( MonadIO' m ) => Database -> Host -> Maybe ( Username , Password ) -> Database -> Action m Document
2010-07-27 21:18:53 +00:00
-- ^ Copy database from given host to the server I am connected to. If username & password is supplied use them to read from given host.
2011-07-05 14:37:01 +00:00
copyDatabase fromDb fromHost mup toDb = do
2010-06-15 03:14:40 +00:00
let c = [ " copydb " =: ( 1 :: Int ) , " fromhost " =: showHostPort fromHost , " fromdb " =: fromDb , " todb " =: toDb ]
2011-07-05 14:37:01 +00:00
useDb admin $ case mup of
2010-06-15 03:14:40 +00:00
Nothing -> runCommand c
2010-12-27 05:23:02 +00:00
Just ( usr , pss ) -> do
2010-06-15 03:14:40 +00:00
n <- at " nonce " <$> runCommand [ " copydbgetnonce " =: ( 1 :: Int ) , " fromhost " =: showHostPort fromHost ]
2010-12-27 05:23:02 +00:00
runCommand $ c ++ [ " username " =: usr , " nonce " =: n , " key " =: pwKey n usr pss ]
2010-06-15 03:14:40 +00:00
2011-07-05 14:37:01 +00:00
dropDatabase :: ( MonadIO' m ) => Database -> Action m Document
2010-06-15 03:14:40 +00:00
-- ^ Delete the given database!
2011-07-05 14:37:01 +00:00
dropDatabase db = useDb db $ runCommand [ " dropDatabase " =: ( 1 :: Int ) ]
2010-06-15 03:14:40 +00:00
2011-07-05 14:37:01 +00:00
repairDatabase :: ( MonadIO' m ) => Database -> Action m Document
2010-06-15 03:14:40 +00:00
-- ^ Attempt to fix any corrupt records. This operation takes a while.
2011-07-05 14:37:01 +00:00
repairDatabase db = useDb db $ runCommand [ " repairDatabase " =: ( 1 :: Int ) ]
2010-06-15 03:14:40 +00:00
-- ** Server
2011-07-05 14:37:01 +00:00
serverBuildInfo :: ( MonadIO' m ) => Action m Document
serverBuildInfo = useDb admin $ runCommand [ " buildinfo " =: ( 1 :: Int ) ]
2010-06-15 03:14:40 +00:00
2012-05-08 15:13:25 +00:00
serverVersion :: ( MonadIO' m ) => Action m Text
2010-06-15 03:14:40 +00:00
serverVersion = at " version " <$> serverBuildInfo
-- * Diagnostics
-- ** Collection
2011-07-05 14:37:01 +00:00
collectionStats :: ( MonadIO' m ) => Collection -> Action m Document
2010-06-15 03:14:40 +00:00
collectionStats coll = runCommand [ " collstats " =: coll ]
2011-07-05 14:37:01 +00:00
dataSize :: ( MonadIO' m ) => Collection -> Action m Int
2010-06-15 03:14:40 +00:00
dataSize c = at " size " <$> collectionStats c
2011-07-05 14:37:01 +00:00
storageSize :: ( MonadIO' m ) => Collection -> Action m Int
2010-06-15 03:14:40 +00:00
storageSize c = at " storageSize " <$> collectionStats c
2011-07-05 14:37:01 +00:00
totalIndexSize :: ( MonadIO' m ) => Collection -> Action m Int
2010-06-15 03:14:40 +00:00
totalIndexSize c = at " totalIndexSize " <$> collectionStats c
2011-12-05 17:23:39 +00:00
totalSize :: ( MonadIO m , MonadBaseControl IO m , MonadIO' m ) => Collection -> Action m Int
2010-06-15 03:14:40 +00:00
totalSize coll = do
x <- storageSize coll
xs <- mapM isize =<< getIndexes coll
return ( foldl ( + ) x xs )
where
2012-05-08 15:13:25 +00:00
isize idx = at " storageSize " <$> collectionStats ( coll ` T . append ` " .$ " ` T . append ` at " name " idx )
2010-06-15 03:14:40 +00:00
-- ** Profiling
data ProfilingLevel = Off | Slow | All deriving ( Show , Enum , Eq )
2011-07-05 14:37:01 +00:00
getProfilingLevel :: ( MonadIO' m ) => Action m ProfilingLevel
2010-06-15 03:14:40 +00:00
getProfilingLevel = toEnum . at " was " <$> runCommand [ " profile " =: ( - 1 :: Int ) ]
type MilliSec = Int
2011-07-05 14:37:01 +00:00
setProfilingLevel :: ( MonadIO' m ) => ProfilingLevel -> Maybe MilliSec -> Action m ()
2010-06-15 03:14:40 +00:00
setProfilingLevel p mSlowMs =
runCommand ( [ " profile " =: fromEnum p ] ++ ( " slowms " =? mSlowMs ) ) >> return ()
-- ** Database
2011-07-05 14:37:01 +00:00
dbStats :: ( MonadIO' m ) => Action m Document
2010-06-15 03:14:40 +00:00
dbStats = runCommand [ " dbstats " =: ( 1 :: Int ) ]
2011-07-05 14:37:01 +00:00
currentOp :: ( MonadIO m ) => Action m ( Maybe Document )
2010-06-15 03:14:40 +00:00
-- ^ See currently running operation on the database, if any
2010-06-21 15:06:20 +00:00
currentOp = findOne ( select [] " $cmd.sys.inprog " )
2010-06-15 03:14:40 +00:00
type OpNum = Int
2011-07-05 14:37:01 +00:00
killOp :: ( MonadIO m ) => OpNum -> Action m ( Maybe Document )
2010-06-21 15:06:20 +00:00
killOp op = findOne ( select [ " op " =: op ] " $cmd.sys.killop " )
2010-06-15 03:14:40 +00:00
-- ** Server
2011-07-05 14:37:01 +00:00
serverStatus :: ( MonadIO' m ) => Action m Document
serverStatus = useDb admin $ runCommand [ " serverStatus " =: ( 1 :: Int ) ]
2010-06-15 03:14:40 +00:00
{- Authors: Tony Hannan <tony@10gen.com>
2011-07-05 14:37:01 +00:00
Copyright 2011 10 gen Inc .
2010-06-15 03:14:40 +00:00
Licensed under the Apache License , Version 2.0 ( the " License " ) ; you may not use this file except in compliance with the License . You may obtain a copy of the License at : http :// www . apache . org / licenses / LICENSE - 2.0 . Unless required by applicable law or agreed to in writing , software distributed under the License is distributed on an " AS IS " BASIS , WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND , either express or implied . See the License for the specific language governing permissions and limitations under the License . - }