summaryrefslogtreecommitdiff
path: root/src/DPut.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/DPut.hs')
-rw-r--r--src/DPut.hs75
1 files changed, 0 insertions, 75 deletions
diff --git a/src/DPut.hs b/src/DPut.hs
deleted file mode 100644
index 38e532d0..00000000
--- a/src/DPut.hs
+++ /dev/null
@@ -1,75 +0,0 @@
1{-# LANGUAGE ConstraintKinds #-}
2{-# LANGUAGE ScopedTypeVariables #-}
3module DPut where
4
5import Control.Monad.IO.Class
6import qualified Data.Map.Strict as Map
7import Data.Maybe
8import Data.IORef
9import System.IO.Unsafe (unsafePerformIO)
10import System.Log.Logger
11import qualified Data.ByteString.Char8 as B
12import qualified Data.Text as T
13import qualified Data.Text.Encoding as T
14import Debug.Trace
15import Data.Typeable
16import Data.Dynamic
17
18type IsDebugTag t = (Eq t, Ord t, Show t, Read t, Enum t, Bounded t,Typeable t)
19
20appName :: String
21appName = "toxmpp"
22
23(<.>) :: String -> String -> String
24a <.> b = a ++ "." ++ b
25
26dput :: (MonadIO m, IsDebugTag tag) => tag -> String -> m ()
27dput tag msg = liftIO $ debugM (appName <.> show tag) msg
28
29dputB :: (MonadIO m, IsDebugTag tag) => tag -> B.ByteString -> m ()
30dputB tag msg = liftIO $ debugM (appName <.> show tag) (T.unpack . T.decodeUtf8 $ msg)
31
32{-# NOINLINE verbosityMap #-}
33verbosityMap :: IORef (Map.Map TypeRep Dynamic)
34verbosityMap = unsafePerformIO $ newIORef (Map.empty)
35
36-- | Trace version of 'dput' works in arbitrary monad, using unsafePerformIO.
37tput :: (Applicative m, IsDebugTag tag) => tag -> String -> m ()
38tput tag msg =
39 let mp = unsafePerformIO $ readIORef verbosityMap
40 in if maybe True (fromMaybe True . Map.lookup tag . flip fromDyn Map.empty) (Map.lookup (typeOf tag) mp)
41 then trace msg (pure ())
42 else pure ()
43
44-- | like 'trace' but parameterized with 'DebugTag'
45dtrace :: forall a tag. IsDebugTag tag => tag -> String -> a -> a
46dtrace tag msg result = let mp = unsafePerformIO $ readIORef verbosityMap
47 mp' :: Map.Map tag Bool
48 mp' = maybe Map.empty (flip fromDyn Map.empty) (Map.lookup (typeOf tag) mp)
49 in if fromMaybe True (Map.lookup tag mp')
50 then trace msg result
51 else result
52
53setTagLevel :: forall tag. IsDebugTag tag => Priority -> tag -> IO ()
54setTagLevel level tag = do
55 updateGlobalLogger (appName <.> show tag) (setLevel level)
56 modifyIORef verbosityMap $ \mpByType -> do
57 case Map.lookup (typeOf tag) mpByType of
58 Nothing -> Map.insert (typeOf tag) (toDyn $ Map.fromList [(tag,(level <= DEBUG))]) mpByType
59 Just dyn -> let mpByTag :: Map.Map tag Bool
60 mpByTag = fromDyn dyn Map.empty
61 in Map.insert (typeOf tag) (toDyn $ Map.insert tag (level <= DEBUG) mpByTag) mpByType
62
63setQuiet :: forall tag. IsDebugTag tag => tag -> IO ()
64setQuiet = setTagLevel WARNING
65
66setVerbose :: forall tag. IsDebugTag tag => tag -> IO ()
67setVerbose = setTagLevel DEBUG
68
69getVerbose :: forall tag. IsDebugTag tag => tag -> IO Bool
70getVerbose tag = do
71 logger <- getLogger (appName <.> show tag)
72 case getLevel logger of
73 Just p | p <= DEBUG -> return True
74 _ -> return False
75