2019-05-30 01:02:37 +00:00
|
|
|
-- | Miscellaneous general functions
|
2010-01-17 01:22:05 +00:00
|
|
|
|
2011-07-05 14:37:01 +00:00
|
|
|
{-# LANGUAGE FlexibleInstances, UndecidableInstances, StandaloneDeriving #-}
|
2013-01-20 22:08:20 +00:00
|
|
|
{-# LANGUAGE CPP #-}
|
2010-01-17 01:22:05 +00:00
|
|
|
|
2010-06-21 15:06:20 +00:00
|
|
|
module Database.MongoDB.Internal.Util where
|
2010-01-17 01:22:05 +00:00
|
|
|
|
2015-05-15 13:23:40 +00:00
|
|
|
#if !MIN_VERSION_base(4,8,0)
|
2013-12-27 11:39:22 +00:00
|
|
|
import Control.Applicative ((<$>))
|
2015-05-15 13:23:40 +00:00
|
|
|
#endif
|
2015-03-05 19:20:02 +00:00
|
|
|
import Control.Exception (handle, throwIO, Exception)
|
2012-06-10 19:47:14 +00:00
|
|
|
import Control.Monad (liftM, liftM2)
|
2010-06-15 03:14:40 +00:00
|
|
|
import Data.Bits (Bits, (.|.))
|
2012-06-10 19:47:14 +00:00
|
|
|
import Data.Word (Word8)
|
|
|
|
import Numeric (showHex)
|
|
|
|
import System.Random (newStdGen)
|
|
|
|
import System.Random.Shuffle (shuffle')
|
|
|
|
|
|
|
|
import qualified Data.ByteString as S
|
|
|
|
|
2019-05-29 23:57:51 +00:00
|
|
|
import Control.Monad.Except (MonadError(..))
|
2012-06-10 19:47:14 +00:00
|
|
|
import Control.Monad.Trans (MonadIO, liftIO)
|
|
|
|
import Data.Bson
|
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
|
2010-06-15 03:14:40 +00:00
|
|
|
|
2012-02-12 04:34:07 +00:00
|
|
|
-- | A monadic sort implementation derived from the non-monadic one in ghc's Prelude
|
|
|
|
mergesortM :: Monad m => (a -> a -> m Ordering) -> [a] -> m [a]
|
|
|
|
mergesortM cmp = mergesortM' cmp . map wrap
|
|
|
|
|
|
|
|
mergesortM' :: Monad m => (a -> a -> m Ordering) -> [[a]] -> m [a]
|
|
|
|
mergesortM' _ [] = return []
|
|
|
|
mergesortM' _ [xs] = return xs
|
|
|
|
mergesortM' cmp xss = mergesortM' cmp =<< (merge_pairsM cmp xss)
|
|
|
|
|
|
|
|
merge_pairsM :: Monad m => (a -> a -> m Ordering) -> [[a]] -> m [[a]]
|
|
|
|
merge_pairsM _ [] = return []
|
|
|
|
merge_pairsM _ [xs] = return [xs]
|
|
|
|
merge_pairsM cmp (xs:ys:xss) = liftM2 (:) (mergeM cmp xs ys) (merge_pairsM cmp xss)
|
|
|
|
|
|
|
|
mergeM :: Monad m => (a -> a -> m Ordering) -> [a] -> [a] -> m [a]
|
|
|
|
mergeM _ [] ys = return ys
|
|
|
|
mergeM _ xs [] = return xs
|
|
|
|
mergeM cmp (x:xs) (y:ys)
|
|
|
|
= do
|
|
|
|
c <- x `cmp` y
|
|
|
|
case c of
|
|
|
|
GT -> liftM (y:) (mergeM cmp (x:xs) ys)
|
|
|
|
_ -> liftM (x:) (mergeM cmp xs (y:ys))
|
|
|
|
|
|
|
|
wrap :: a -> [a]
|
|
|
|
wrap x = [x]
|
|
|
|
|
2011-07-05 14:37:01 +00:00
|
|
|
shuffle :: [a] -> IO [a]
|
|
|
|
-- ^ Randomly shuffle items in list
|
2012-06-10 19:47:14 +00:00
|
|
|
shuffle list = shuffle' list (length list) <$> newStdGen
|
2011-07-05 14:37:01 +00:00
|
|
|
|
2017-05-09 05:47:47 +00:00
|
|
|
loop :: Monad m => m (Maybe a) -> m [a]
|
2011-07-05 14:37:01 +00:00
|
|
|
-- ^ Repeatedy execute action, collecting results, until it returns Nothing
|
2017-05-09 05:47:47 +00:00
|
|
|
loop act = act >>= maybe (return []) (\a -> (a :) `liftM` loop act)
|
2011-07-05 14:37:01 +00:00
|
|
|
|
2019-05-29 23:57:51 +00:00
|
|
|
untilSuccess :: (MonadError e m) => (a -> m b) -> [a] -> m b
|
2011-07-05 14:37:01 +00:00
|
|
|
-- ^ Apply action to elements one at a time until one succeeds. Throw last error if all fail. Throw 'strMsg' error if list is empty.
|
2019-05-29 23:57:51 +00:00
|
|
|
untilSuccess = untilSuccess' (error "empty untilSuccess")
|
|
|
|
-- Use 'error' copying behavior in removed 'Control.Monad.Error.Error' instance:
|
|
|
|
-- instance Error Failure where strMsg = error
|
|
|
|
-- 'fail' is treated the same as a programming 'error'. In other words, don't use it.
|
2011-07-05 14:37:01 +00:00
|
|
|
|
|
|
|
untilSuccess' :: (MonadError e m) => e -> (a -> m b) -> [a] -> m b
|
|
|
|
-- ^ Apply action to elements one at a time until one succeeds. Throw last error if all fail. Throw given error if list is empty
|
|
|
|
untilSuccess' e _ [] = throwError e
|
|
|
|
untilSuccess' _ f (x : xs) = catchError (f x) (\e -> untilSuccess' e f xs)
|
|
|
|
|
|
|
|
whenJust :: (Monad m) => Maybe a -> (a -> m ()) -> m ()
|
|
|
|
whenJust mVal act = maybe (return ()) act mVal
|
|
|
|
|
2013-12-26 15:23:02 +00:00
|
|
|
liftIOE :: (MonadIO m, Exception e, Exception e') => (e -> e') -> IO a -> m a
|
2011-07-05 14:37:01 +00:00
|
|
|
-- ^ lift IOE monad to ErrorT monad over some MonadIO m
|
2013-12-26 15:23:02 +00:00
|
|
|
liftIOE f = liftIO . handle (throwIO . f)
|
2011-07-05 14:37:01 +00:00
|
|
|
|
|
|
|
updateAssocs :: (Eq k) => k -> v -> [(k, v)] -> [(k, v)]
|
|
|
|
-- ^ Change or insert value of key in association list
|
|
|
|
updateAssocs key valu assocs = case back of [] -> (key, valu) : front; _ : back' -> front ++ (key, valu) : back'
|
2013-12-26 14:57:33 +00:00
|
|
|
where (front, back) = break ((key ==) . fst) assocs
|
2011-07-05 14:37:01 +00:00
|
|
|
|
2012-09-10 17:25:45 +00:00
|
|
|
bitOr :: (Num a, Bits a) => [a] -> a
|
2010-06-15 03:14:40 +00:00
|
|
|
-- ^ bit-or all numbers together
|
|
|
|
bitOr = foldl (.|.) 0
|
|
|
|
|
2012-05-08 15:13:25 +00:00
|
|
|
(<.>) :: Text -> Text -> Text
|
2010-06-15 03:14:40 +00:00
|
|
|
-- ^ Concat first and second together with period in between. Eg. @\"hello\" \<.\> \"world\" = \"hello.world\"@
|
2012-05-08 15:13:25 +00:00
|
|
|
a <.> b = T.append a (T.cons '.' b)
|
2010-06-15 03:14:40 +00:00
|
|
|
|
|
|
|
true1 :: Label -> Document -> Bool
|
|
|
|
-- ^ Is field's value a 1 or True (MongoDB use both Int and Bools for truth values). Error if field not in document or field not a Num or Bool.
|
|
|
|
true1 k doc = case valueAt k doc of
|
2013-12-26 14:57:33 +00:00
|
|
|
Bool b -> b
|
|
|
|
Float n -> n == 1
|
|
|
|
Int32 n -> n == 1
|
|
|
|
Int64 n -> n == 1
|
|
|
|
_ -> error $ "expected " ++ show k ++ " to be Num or Bool in " ++ show doc
|
2010-12-20 02:08:53 +00:00
|
|
|
|
2012-06-10 19:47:14 +00:00
|
|
|
byteStringHex :: S.ByteString -> String
|
2011-07-05 14:37:01 +00:00
|
|
|
-- ^ Hexadecimal string representation of a byte string. Each byte yields two hexadecimal characters.
|
2012-06-10 19:47:14 +00:00
|
|
|
byteStringHex = concatMap byteHex . S.unpack
|
2011-07-05 14:37:01 +00:00
|
|
|
|
|
|
|
byteHex :: Word8 -> String
|
|
|
|
-- ^ Two char hexadecimal representation of byte
|
|
|
|
byteHex b = (if b < 16 then ('0' :) else id) (showHex b "")
|