{-# LANGUAGE OverloadedStrings #-}
module System.Log.Raven.Interfaces
    ( 
      
      message
      
    , exception
      
    , http, HttpArgs(..)
      
    , user
      
    , query
      
    , interface
    , fields, (.=:), fromMaybe, fromAssoc
    ) where
import Data.Aeson (ToJSON(toJSON), Value, object, (.=))
import qualified Data.HashMap.Strict as HM
import System.Log.Raven.Types
message :: String       
        -> [Value]      
        -> SentryRecord 
        -> SentryRecord
message msg args = interface "sentry.interfaces.Message" info
    where
        info = object [ "message" .= take 1000 msg
                      , "params" .= args
                      ]
exception :: String       
          -> Maybe String 
          -> Maybe String 
          -> SentryRecord 
          -> SentryRecord
exception v t m = interface "sentry.interfaces.Exception" info
    where
        info = fields [ "value" .=: v
                      , fromMaybe "type" t
                      , fromMaybe "module" m
                      ]
data HttpArgs = EmptyArgs
              | RawArgs String
              | QueryArgs [(String, String)]
              deriving (Eq, Show)
http :: String             
     -> String             
     -> HttpArgs           
     -> Maybe String       
     -> Maybe String       
     -> [(String, String)] 
     -> [(String, String)] 
     -> SentryRecord       
     -> SentryRecord
http url m args q c hs env = interface "sentry.interfaces.Http" info
    where
        info = fields [ "url" .=: url
                      , "method" .=: m
                      , fromHttpArgs args
                      , fromMaybe "query_string" q
                      , fromMaybe "cookies" c
                      , fromAssoc "headers" hs
                      , fromAssoc "env" env
                      ]
        fromHttpArgs EmptyArgs = []
        fromHttpArgs (RawArgs s) = "data" .=: s
        fromHttpArgs (QueryArgs kvs) = "data" .=: HM.fromList kvs
user :: String             
     -> [(String, String)] 
     -> SentryRecord       
     -> SentryRecord
user uid kwargs = interface "sentry.interfaces.User" info
    where
        info = HM.fromList $ ("id", uid) : kwargs
query :: Maybe String 
      -> String       
      -> SentryRecord 
      -> SentryRecord
query d q = interface "sentry.interfaces.Query" info
    where
        info = fields [ "query" .=: q
                      , fromMaybe "engine" d
                      ]
interface :: (ToJSON v) => String -> v -> SentryRecord -> SentryRecord
interface k v rec =
    rec { srInterfaces = HM.insert k (toJSON v) $ srInterfaces rec }
fields :: [[(String, Value)]] -> HM.HashMap String Value
fields = HM.fromList . concat
(.=:) :: (ToJSON v) => String -> v -> [(String, Value)]
k .=: v = [(k, toJSON v)]
fromMaybe :: (ToJSON v) => String -> Maybe v -> [(String, Value)]
fromMaybe k = maybe [] (\v -> [ (k, toJSON v) ])
fromAssoc :: String -> [(String, String)] -> [(String, Value)]
fromAssoc _ [] = []
fromAssoc k vs = [(k, toJSON . HM.fromList $ vs)]