module Irc.Internal where
import Data.String ( IsString(..) )
import Data.Default ( Default(..) )
import Control.Applicative (Applicative)
import Control.Monad.Trans.State as State
        ( State
        , modify
        , execState )
import Control.Exception
import Control.Monad.Reader
import Data.List ( find
                 , isPrefixOf)
import Network ( PortID(PortNumber)
               , connectTo)
import System.IO ( Handle
                 , hClose
                 , hSetBuffering
                 , BufferMode(..)
                 , hFlush
                 , stdout
                 , hGetLine
                 )
import Text.Printf( hPrintf
                  , printf)
type Irc = ReaderT Bot IO
data Bot = Bot { rules :: [Rule]
               , config :: Config
               , socket :: Handle}
data Config = Config { server :: String
                     , port :: Integer
                     , chan :: String
                     , nick :: String}
mainWithConfigAndBehavior :: Config -> Behavior -> IO ()
mainWithConfigAndBehavior conf bev = bracket (connect conf bev) disconnect loop
  where
    disconnect = hClose . socket
    loop       = runReaderT run
connect :: Config -> Behavior -> IO Bot
connect conf bev = notify $ do
    h <- connectTo (server conf) (PortNumber (fromIntegral (port conf)))
    hSetBuffering h NoBuffering
    return (Bot (runBevhavior bev) conf h)
  where
    notify = bracket_
        (printf "Connecting to %s ... " (server conf) >> hFlush stdout)
        (putStrLn "done.")
run :: Irc ()
run = do
    conf <- asks config
    write "NICK" $ nick conf
    write "USER" $ nick conf ++ " 0 * :bot"
    write "JOIN" $ chan conf
    asks socket >>= listen
listen :: Handle -> Irc ()
listen h = forever $ do
    s <- init `fmap` io (hGetLine h)
    io (putStrLn s)
    if ping s then pong s else eval (clean s)
  where
    clean     = drop 1 . dropWhile (/= ':') . drop 1
    ping x    = "PING :" `isPrefixOf` x
    pong x    = write "PONG" (':' : drop 6 x)
eval :: String -> Irc ()
eval s = do
    r <- asks rules
    liftAction (findAction s r) s
findAction :: String -> [Rule] -> Action
findAction s l = maybe doNothing action $ find (\x -> pattern x `isPrefixOf` s) l
                 where doNothing _ = return ""
privmsg :: String -> Irc ()
privmsg s = do
  conf <- asks config
  write "PRIVMSG" (chan conf ++ " :" ++ s)
write :: String -> String -> Irc ()
write s t = do
    h <- asks socket
    io $ hPrintf h "%s %s\r\n" s t
    io $ printf    "> %s %s\n" s t
io :: IO a -> Irc a
io = liftIO
type Pattern = String
type Action = String -> IO String
data Rule = Rule {
      pattern :: Pattern
    , action :: Action
}
instance Default Rule where
  def = Rule
          { pattern = ""
          , action  = def
          }
instance IsString Rule where
  fromString x = def { pattern = x}
liftAction :: Action -> String -> Irc ()
liftAction a s = do
    h <- asks socket
    conf <- asks config
    r <- io (a s)
    p r h (chan conf)
        where
          p [] _ _ = return ()
          p r h c = io $ hPrintf h "PRIVMSG %s\r\n" (c ++ " :" ++ r)
newtype BehaviorM a = BehaviorM {unBehaviorM :: State [Rule] a}
    deriving (Functor
             , Applicative
             , Monad)
type Behavior = BehaviorM ()
instance IsString Behavior where
  fromString = addRule . fromString
instance Show Behavior where
    show = show . map pattern . runBevhavior
runBevhavior :: Behavior -> [Rule]
runBevhavior bev = execState (unBehaviorM bev) []
addRule :: Rule -> Behavior
addRule r = BehaviorM $ modify (r :)
modHeadRule :: Behavior -> (Rule -> Rule) -> Behavior
modHeadRule bev f = do
  let rs = runBevhavior bev
  BehaviorM $ case rs of
                x:_ -> modify (reverse.(f x:).reverse)
                []  -> modify id
ruleAddAction :: Action -> Rule -> Rule
ruleAddAction f r = r {action = f}
infixl 8 |!
(|!) :: Behavior -> (String -> IO String) -> Behavior
bev |! f = modHeadRule bev $ ruleAddAction f