+build:
+ stack build
+
+repl:
+ stack repl
+
graylog:
docker run -t -p 9000:9000 -p 12201:12201 -p 12201:12201/udp graylog2/allinone
toJSON Notice = Number 5
toJSON Informational = Number 6
toJSON Debug = Number 7
+
+--
+
+simpleGelf
+ :: Text -- ^ Hostname
+ -> Text -- ^ Short message
+ -> GELF
+simpleGelf host short =
+ GELF Version1x1 host short Nothing Nothing Nothing Nothing Nothing
+{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE RecordWildCards #-}
module Graylog.Types
, closeGraylog
) where
+import Data.List
import Data.Text (Text)
import qualified Data.Text as T
import Network.BSD
defaultChunkSize :: ChunkSize
defaultChunkSize = 8192
-openGraylog :: HostName -> ServiceName -> ChunkSize -> IO (Either String Graylog)
-openGraylog host port chksize = do
- infos <- getAddrInfo Nothing (Just host) (Just port)
- case infos of
- [] -> return $ Left "No address info found."
- [info] -> do
- sock <- socket (addrFamily info) Datagram defaultProtocol
- connect sock (addrAddress info)
- hostname <- getHostName
- return $ Right $ Graylog host port info sock (T.pack hostname) chksize
- _ -> return $ Left "Too many address infos found."
+openGraylog
+ :: HostName -> ServiceName -> ChunkSize -> IO (Either String Graylog)
+openGraylog h p cksize = getAddrInfo Nothing (Just h) (Just p) >>= \case
+ [] -> return $ Left "No address info found."
+ infos ->
+ case find (\i -> addrSocketType i == Datagram) infos of
+ Nothing -> return $ Left "No datagram info found for address."
+ Just i -> do
+ sock <- socket (addrFamily i) Datagram defaultProtocol
+ connect sock (addrAddress i)
+ hostname <- getHostName
+ return $ Right $ Graylog h p i sock (T.pack hostname) cksize
closeGraylog :: Graylog -> IO ()
closeGraylog Graylog{..} = close _graylogSocket
-
-
) where
import Data.Aeson
-import qualified Data.ByteString.Lazy as LBS
-import Data.Word
+{-import Data.ByteString.Builder-}
+{-import qualified Data.ByteString.Lazy as LBS-}
+{-import Data.Word-}
import Network.Socket.ByteString.Lazy
-import System.Random
+{-import System.Random-}
import Graylog.Gelf as Export
import Graylog.Types as Export
sendLog :: Graylog -> GELF -> IO ()
-sendLog glog msg = mapM_ (send $ _graylogSocket glog) cks
+sendLog glog msg = do
+ _ <- send (_graylogSocket glog) raw
+ print raw
+ return ()
where
raw = encode msg
- cks = chunky glog raw
-chunky :: Graylog -> LBS.ByteString -> IO [LBS.ByteString]
-chunky glog raw = do
- groupId <- randomIO
- splitAt gsize
- where
- magic = undefined
- seq = undefined
- total = undefined
- hlen = 12
- gsize = (fromIntegral (_graylogChunkSize glog)) - hlen
+{-sendLog :: Graylog -> GELF -> IO ()-}
+{-sendLog glog msg = do-}
+ {-cks <- chunky glog raw-}
+ {-mapM_ (send $ _graylogSocket glog) cks-}
+ {-where-}
+ {-raw = encode msg-}
+
+{-chunky :: Graylog -> LBS.ByteString -> IO [LBS.ByteString]-}
+{-chunky glog raw = do-}
+ {-groupId <- randomIO-}
+ {-splitAt gsize-}
+ {-where-}
+ {-magic = word8 0x1e <> word8 0x0f-}
+ {-seqNum = undefined-}
+ {-(count, excess) = quotRem (LBS.length raw) gzie-}
+ {-hlen = 12-}
+ {-gsize = (fromIntegral (_graylogChunkSize glog)) - hlen-}
+{-# LANGUAGE OverloadedStrings #-}
+
module Test.Graylog.UDP where
import Test.Tasty
import Test.Tasty.HUnit
+import Graylog.UDP
+
tests :: TestTree
tests = testGroup "Test.Graylog.UDP"
- [ testCase "Validation: Something" case_validateSomething
+ {-[ testCase "Send: Sample" case_validateSomething-}
+ [ testCase "Send sample message." case_sendSample
]
-case_validateSomething :: IO ()
-case_validateSomething = return ()
-
+case_sendSample :: IO ()
+case_sendSample = do
+ eglog <- openGraylog "192.168.99.100" "12201" defaultChunkSize
+ case eglog of
+ Left e -> assertFailure e
+ Right g -> sendLog g sample
+ where
+ sample = simpleGelf "localhost" "hello world!"