On Jun 17, 2009, at 1:00 PM, Niklas Broberg wrote:

Thanks a lot, very useful! I'll add that to the darcs repository if
you don't mind. :-)

feel free!

Here is a cleaned-up and updated version that can also read from stdin:

#! /usr/bin/env runhaskell

> import Language.Haskell.Exts
>
> import System            ( getArgs )
> import System.IO         ( hGetContents, stdin )
> import Prelude hiding    ( catch )
> import Control.Exception ( catch, SomeException )
>
> main :: IO ()
> main = do args  <- getArgs
>           input <- hGetContents stdin
>           mapM_ parse (args ++ lines input)
>  where parse file = catch (parseFile file >>= check) $
> \e -> putStrLn $ file ++ ": " ++ show (e::SomeException)
>
> check :: ParseResult a -> IO ()
> check (ParseOk _)           = return ()
> check (ParseFailed loc msg) = putStrLn err
>  where err = srcFilename loc ++ ": " ++ msg ++ " at " ++
>              show (srcLine loc) ++ ":" ++
>              show (srcColumn loc)


--
Underestimating the novelty of the future is a time-honored tradition.
(D.G.)



Attachment: PGP.sig
Description: This is a digitally signed message part

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to