File: More.hs

package info (click to toggle)
lambdabot 4.2.3.2-4
  • links: PTS, VCS
  • area: main
  • in suites: wheezy
  • size: 5,584 kB
  • sloc: haskell: 10,102; ansic: 76; makefile: 7
file content (37 lines) | stat: -rw-r--r-- 1,458 bytes parent folder | download
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
{-# LANGUAGE TemplateHaskell, MultiParamTypeClasses, TypeSynonymInstances, FlexibleInstances #-}
-- | Support for more(1) buffering
module Plugin.More (theModule) where

import Plugin

import Message( Nick )

$(plugin "More")

type MoreState = GlobalPrivate () [String]

-- the @more state is handled centrally
instance Module MoreModule MoreState where
    moduleHelp _ _              = "@more. Return more output from the bot buffer."
    moduleCmds   _              = ["more"]
    moduleDefState _            = return $ mkGlobalPrivate 20 ()
    moduleInit   _              = bindModule2 moreFilter >>=
                                      ircInstallOutputFilter
    process      _ _ target _ _ = do
        morestate <- readPS target
        case morestate of
            Nothing -> return []
            Just ls -> do mapM_ (lift . ircPrivmsg' target) =<< moreFilter target ls
                          return []       -- special

moreFilter :: Nick -> [String] -> ModuleLB MoreState
moreFilter target msglines = do
    let (morelines, thislines) = case drop (maxLines+2) msglines of
          [] -> ([],msglines)
          _  -> (drop maxLines msglines, take maxLines msglines)
    writePS target $ if null morelines then Nothing else Just morelines
    return $ thislines ++ if null morelines
                          then []
                          else ['[':shows (length morelines) " @more lines]"]

    where maxLines = 5 -- arbitrary, really