Added duck spawning capabilities, ready to be shot!
This commit is contained in:
parent
a8c0c85787
commit
b3d04f9a06
2 changed files with 33 additions and 9 deletions
|
@ -4,26 +4,32 @@ module Hsbot.Plugin.Duck
|
||||||
, theDuck
|
, theDuck
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Control.Concurrent.Chan ()
|
import Control.Concurrent
|
||||||
import qualified Data.List as L
|
import qualified Data.List as L
|
||||||
import Control.Monad.Reader
|
import Control.Monad.Reader
|
||||||
import qualified Network.IRC as IRC
|
import qualified Network.IRC as IRC
|
||||||
import Prelude hiding (catch)
|
import Prelude hiding (catch)
|
||||||
|
import System.Random
|
||||||
|
|
||||||
import Hsbot.Message
|
import Hsbot.Message
|
||||||
import Hsbot.Types
|
import Hsbot.Types
|
||||||
|
import Hsbot.Utils
|
||||||
|
|
||||||
-- | The duck plugin identity
|
-- | The duck plugin identity
|
||||||
duck :: PluginId
|
duck :: PluginId
|
||||||
duck = PluginId
|
duck = PluginId
|
||||||
{ pluginName = "duck"
|
{ pluginName = "duck"
|
||||||
, pluginEp = theDuck }
|
, pluginEp = theDuck "" 11 }
|
||||||
|
|
||||||
-- | An IRC plugin that generates and kills ducks
|
-- | An IRC plugin that generates and kills ducks
|
||||||
theDuck :: Plugin (Env IO) ()
|
theDuck :: String -> Int -> Plugin (Env IO) ()
|
||||||
theDuck = forever $ do
|
theDuck channel seconds = do
|
||||||
msg <- readMsg
|
env <- lift ask
|
||||||
eval msg
|
pEnv <- ask
|
||||||
|
secondsMVar <- liftIO $ newMVar seconds
|
||||||
|
killMVar <- liftIO newEmptyMVar
|
||||||
|
(liftIO . forkIO $ runReaderT (runReaderT (duckSpawner channel secondsMVar killMVar) pEnv) env) >>= lift . addThreadIdToQuitMVar
|
||||||
|
forever $ readMsg >>= eval
|
||||||
where
|
where
|
||||||
eval :: Message -> Plugin (Env IO) ()
|
eval :: Message -> Plugin (Env IO) ()
|
||||||
eval (IncomingMsg msg)
|
eval (IncomingMsg msg)
|
||||||
|
@ -31,17 +37,34 @@ theDuck = forever $ do
|
||||||
| otherwise = return ()
|
| otherwise = return ()
|
||||||
eval _ = return ()
|
eval _ = return ()
|
||||||
|
|
||||||
|
-- | Regularly spawns ducks on a channel, just waiting to be shot
|
||||||
|
duckSpawner :: String -> MVar Int -> MVar Int -> Plugin (Env IO) ()
|
||||||
|
duckSpawner channel secondsMVar killMVar = forever $ do
|
||||||
|
nbDucks <- liftIO . getStdRandom $ randomR (1,4)
|
||||||
|
liftIO $ putMVar killMVar nbDucks
|
||||||
|
thoseDucks <- liftIO $ someRandomDucks nbDucks ""
|
||||||
|
writeMsg . OutgoingMsg $ IRC.Message Nothing "PRIVMSG" [channel, thoseDucks]
|
||||||
|
secs <- liftIO $ readMVar secondsMVar
|
||||||
|
liftIO $ threadDelay (3000000 * secs)
|
||||||
|
|
||||||
-- | Shoot as many times are there are ducks in the initial string
|
-- | Shoot as many times are there are ducks in the initial string
|
||||||
isThereADuckToKillInThere :: String -> String
|
isThereADuckToKillInThere :: String -> String
|
||||||
isThereADuckToKillInThere = concat . concatMap (\y -> map (\x -> if x `L.isInfixOf` y then "PAN! " else "") ducks) . words
|
isThereADuckToKillInThere = concat . concatMap (\y -> map (\x -> if x `L.isInfixOf` y then "PAN! " else "") ducks) . words
|
||||||
|
|
||||||
|
someRandomDucks :: Int -> String -> IO String
|
||||||
|
someRandomDucks 0 theDucks = return theDucks
|
||||||
|
someRandomDucks nbDucks theDucks = do
|
||||||
|
whatDuck <- getStdRandom $ randomR (1,length ducks)
|
||||||
|
let thisDuck = ducks !! whatDuck
|
||||||
|
someRandomDucks (nbDucks -1 ) $ concat [thisDuck, " ", theDucks]
|
||||||
|
|
||||||
-- | There are many ways to hide as a duck, this function tries to cover most of them
|
-- | There are many ways to hide as a duck, this function tries to cover most of them
|
||||||
ducks :: [String]
|
ducks :: [String]
|
||||||
ducks = [ x : y : z | x <- nose, y <- face, z <- ["__/", "_/", "/"] ]
|
ducks = [ x : y : z | x <- nose, y <- face, z <- ["__/", "_/", "/"] ]
|
||||||
++ [ L.reverse $ x : y : z | x <- nose, y <- face, z <- ["__\\", "_\\", "\\"] ]
|
++ [ L.reverse $ x : y : z | x <- nose, y <- face, z <- ["__\\", "_\\", "\\"] ]
|
||||||
where
|
where
|
||||||
nose :: [Char]
|
nose :: String
|
||||||
nose = "<>="
|
nose = "<>="
|
||||||
face :: [Char]
|
face :: String
|
||||||
face = "oO°@©®ð*òôóø"
|
face = "oO°@©®ð*òôóø"
|
||||||
|
|
||||||
|
|
|
@ -1,5 +1,5 @@
|
||||||
Name: hsbot
|
Name: hsbot
|
||||||
Version: 0.4.9
|
Version: 0.4.10
|
||||||
Cabal-version: >=1.2
|
Cabal-version: >=1.2
|
||||||
Synopsis: A multipurposes IRC bot
|
Synopsis: A multipurposes IRC bot
|
||||||
Description:
|
Description:
|
||||||
|
@ -39,6 +39,7 @@ Library
|
||||||
irc,
|
irc,
|
||||||
mtl,
|
mtl,
|
||||||
network,
|
network,
|
||||||
|
random,
|
||||||
tls >= 0.6.1,
|
tls >= 0.6.1,
|
||||||
tls-extra >= 0.2.0
|
tls-extra >= 0.2.0
|
||||||
|
|
||||||
|
|
Reference in a new issue