Skip to content

Commit

Permalink
Syncing with darcs
Browse files Browse the repository at this point in the history
  • Loading branch information
Jonas Westerlund committed Oct 5, 2010
1 parent 170c435 commit 51d621d
Show file tree
Hide file tree
Showing 4 changed files with 22 additions and 10 deletions.
1 change: 0 additions & 1 deletion IRC.hs
Expand Up @@ -19,7 +19,6 @@ import Parser
import qualified Seen as S
import System.Exit
import System.IO
import Text.ParserCombinators.Parsec hiding (letter)
import Types

import qualified Utils as U
Expand Down
10 changes: 9 additions & 1 deletion L.hs
@@ -1,4 +1,7 @@
{-# LANGUAGE NoMonomorphismRestriction #-}
{-# LANGUAGE NoMonomorphismRestriction,
ScopedTypeVariables,
UnicodeSyntax #-}

module L where

import Control.Arrow
Expand All @@ -17,6 +20,7 @@ import System
import System.IO
import System.Process
import System.Random
import Text.Regex

interleave [] _ = []
interleave (x:xs) ys = x : interleave ys xs
Expand Down Expand Up @@ -75,3 +79,7 @@ muu = "much unlike urself"

trim = trim' . trim'
where trim' = reverse . dropWhile isSpace

-- Omg postfix function application so you can `car drive` instead of `drive car`!
infixl 0 &
x & f = f x
19 changes: 11 additions & 8 deletions Seen.hs
Expand Up @@ -2,8 +2,6 @@

module Seen where

import Control.Monad
import Control.Monad.Trans (liftIO)
import Control.Monad.State
import qualified Data.Bson as B
import Data.List hiding (sort, insert)
Expand Down Expand Up @@ -49,11 +47,14 @@ seen (Message (Just (NickName n _ _)) _ params) = do
case conn of
Left _ -> return "MongoDB is down!"
Right con -> do
Right res <- run con
(findOne (select ["nick" =: Regex (mconcat [u"^", u (escape' nick), "$"]) "i"] "messages")
{ sort = ["date" =: (-1 :: Int)] })
Right res <- run con (findNick nick)
either (const $ return "Everyone died!")
(internet n nick) res
where findNick n = findOne (select
["nick" =: Regex
(mconcat [u"^", u (escape' n), "$"])
"i"]
"messages") { sort = ["date" =: (-1 :: Int)] }

seen (Message _ _ _) = return "nlogax fails at pattern matching."

Expand Down Expand Up @@ -118,9 +119,11 @@ relTime t | t < s = ["now"]
d = h * 24
w = d * 7

concatTime xss@(x:xs) | x == "now" = x
| length xss == 1 = concat xss ++ " ago"
| otherwise = intercalate ", " (init xss) ++ " and " ++ last xss ++ " ago"
concatTime xss@(x:_) | x == "now" = x
| length xss == 1 = concat xss ++ " ago"
| otherwise = intercalate ", " (init xss)
++ " and " ++ last xss ++ " ago"

concatTime [] = []

rollDie :: State StdGen Int
Expand Down
2 changes: 2 additions & 0 deletions TODO
@@ -1,6 +1,8 @@
Fix the cabal files
Never done it, gotta find out how.

Switch to extensible exceptions so GHC shuts up

Add support for multiple channels
The bot now replies to the channel the message originated from.
Need to handle queries and stuff though.
Expand Down

0 comments on commit 51d621d

Please sign in to comment.