summaryrefslogtreecommitdiffstats
path: root/src/Reaktor/Internal.hs
blob: 74db9c342d041ae45ac6a968c72e936822101f70 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
module Reaktor.Internal where

import Prelude.Extended
import Blessings
import Data.Aeson
import Network.Socket as Exports (HostName,ServiceName)
import qualified Data.ByteString.Char8.Extended as BS
import System.IO


data Actions = Actions
    { aIsSecure :: Bool

    , aSend :: Message -> IO ()
    , aSendQuiet :: Message -> IO ()

    , aLog :: Blessings ByteString -> IO ()
    , aLogMsg :: Message -> IO ()

    , aSetNick :: ByteString -> IO ()
    , aGetNick :: IO ByteString
    }


data Config = Config
    { cUseTLS :: Bool
    , cHostName :: HostName
    , cServiceName :: ServiceName
    , cNick :: Maybe ByteString
    , cLogHandle :: Handle
    , cLogTime :: Bool
    }

instance Default Config where
  def = Config False "irc.r" "6667" Nothing stderr True

instance FromJSON Config where
  parseJSON = \case
      Object v -> do
        cServiceName <- v .:? "port" .!= cServiceName def
        cUseTLS <- v .:? "useTLS" .!= (cServiceName == tlsPort)
        cHostName <- v .:? "hostname" .!= cHostName def
        cNick <- v .:? "nick"
        cLogHandle <- pure (cLogHandle def)
        cLogTime <- v .:? "logTime" .!= cLogTime def
        pure Config{..}
      _ -> undefined
    where
      tlsPort :: ServiceName
      tlsPort = "6697"


data Message = Message (Maybe ByteString) ByteString [ByteString] | Start
  deriving Show

formatMessage :: Message -> ByteString
formatMessage = \case
    Message mb_prefix cmd params ->
      maybe "" ((":"<>) . (<>" ")) mb_prefix
          <> cmd
          <> BS.concat (map (" "<>) (init params))
          <> if null params then "" else " :" <> last params
          <> "\r\n"
    x -> error ("cannot format " <> show x)