module Network.Metric.Internal (
Handle(..)
, Host
, Group
, Bucket
, Metric(..)
, AnyMeasurable(..)
, AnySink(..)
, Measurable(..)
, Encodable(..)
, Sink(..)
, key
, fOpen
, hOpen
, hClose
, hPush
, HostName
, PortNumber(..)
) where
import Control.Monad (liftM, unless)
import Data.Typeable (Typeable)
import Network.Socket hiding (send)
import Network.Socket.ByteString.Lazy (send)
import Text.Printf (printf)
import qualified Data.ByteString.Char8 as BS
import qualified Data.ByteString.Lazy.Char8 as BL
data Handle = Handle Socket SockAddr deriving (Show)
type Host = BS.ByteString
type Group = BS.ByteString
type Bucket = BS.ByteString
data Metric
= Counter Group Bucket Integer
| Timer Group Bucket Double
| Gauge Group Bucket Double
deriving (Show)
class Measurable a where
measure :: a -> [Metric]
class (Show a, Typeable a) => Encodable a where
encode :: a -> BS.ByteString
class Sink a where
push :: Measurable b => a -> b -> IO ()
close :: a -> IO ()
data AnyMeasurable = forall a. Measurable a => AnyMeasurable a
data AnySink = forall a. Sink a => AnySink a
instance Measurable AnyMeasurable where
measure (AnyMeasurable m) = measure m
instance Measurable Metric where
measure = flip (:) [] . id
instance Encodable Int where
encode = BS.pack . show
instance Encodable Integer where
encode = BS.pack . show
instance Encodable Double where
encode = BS.pack . printf "%.8f"
instance Encodable String where
encode = BS.pack
instance Sink AnySink where
push (AnySink s) = push s
close (AnySink s) = close s
key :: Host -> Group -> Bucket -> BS.ByteString
key h g b = BS.intercalate "." [h, g, b]
fOpen :: Sink a
=> (Handle -> a)
-> SocketType
-> HostName
-> PortNumber
-> IO AnySink
fOpen ctor typ host port = liftM (AnySink . ctor) (hOpen typ host port)
hOpen :: SocketType -> HostName -> PortNumber -> IO Handle
hOpen typ host (PortNum port) = do
(addr:_) <- getAddrInfo Nothing (Just host) (Just $ show port)
sock <- socket (addrFamily addr) typ defaultProtocol
return $ Handle sock (addrAddress addr)
hClose :: Handle -> IO ()
hClose (Handle sock _) = sClose sock
hPush :: Handle -> BL.ByteString -> IO ()
hPush (Handle sock addr) bstr | BL.null bstr = return ()
| otherwise = do
sIsConnected sock >>= \b -> unless b $ connect sock addr
_ <- send sock bstr
return ()