[Haskell-cafe] Strictness problems with Control.Event?
Brian Troutwine
goofyheadedpunk at gmail.com
Wed Nov 5 14:45:24 EST 2008
I'm attempting to use Control.Event to limit HTTP requests made by a
dippy little scraper I'm constructing to once per second but I think,
maybe, that the Events are not being evaluated. First, some imports.
> import qualified Data.ByteString as B
> import qualified Data.ByteString.Char8 as C
> import Network.Curl.Download
> import Network.Curl.Opts
> import System.Exit
> import System.Environment
> import System.Time
> import Control.Event
> import Control.Monad
> import Data.Char
The Event function of this program is append. It takes a local path
and a URL, retrieves the contents pointed to by the URL and appends
them to the local path. The function download, below, performs the
retrieval.
> append :: FilePath -> C.ByteString -> IO ()
> append f u =
> B.appendFile f . addNew . C.filter (not . isAscii) =<< download u
> where addNew = C.append (C.pack "\n")
> download :: B.ByteString -> IO B.ByteString
> download url = do
> res <- openURIWithOpts [CurlEncoding "gzip", CurlUserAgent "aule-0.0.2"] $ C.unpack url
> case res of
> Left _ -> exitFailure
> Right cont -> B.putStrLn cont >> return cont
The function sched adds a list of Events to the evtSys system, a fixed
time delay between each.
> sched :: EventSystem -> ClockTime -> Integer -> Integer -> (t -> IO ()) -> [t] -> IO ()
> sched _ _ _ _ _ [] = return ()
> sched evtSys (TOD sec _) delay mul action (x:xs) = do
> addEvent evtSys (TOD (sec + (delay*mul)) 0) (action x)
> sched evtSys (TOD sec 0) delay (mul + 1) action xs
main is, as usual, pretty boring. The program compiles and runs, but
no output file is made. This being one of my first appreciable Haskell
programs, I rather imagine I've run into a strictness problem, maybe.
Would someone be so kind as to steer me in the right direction?
> main :: IO ()
> main = do
> [i, o] <- getArgs
> eS <- initEventSystem
> t <- getClockTime
> inp <- B.readFile i
> sched eS t 1 1 (append o) (C.lines inp)
Thanks,
Brian
More information about the Haskell-Cafe
mailing list