On Jun 17, 2009, at 12:43 AM, Niklas Broberg wrote:

Testing it is
really easy, four simple steps:

cabal install haskell-src-exts
[...]
ghci
[...]
Prelude> :m Language.Haskell.Exts
Prelude Language.Haskell.Exts> parseFile "YourFileHere.(l)hs"

This script may even simplify testing of large code bases:

-------
#! /usr/bin/env runhaskell

> import System
> import System.IO
> import Data.Char
> import Language.Haskell.Exts
>
> import Prelude hiding ( catch )
> import Control.Exception ( catch, SomeException )
>
> main = getArgs >>= mapM_ parse
>  where parse file = do hSetBuffering stdout NoBuffering
>                        putStr $ file ++ ": "
>                        catch (parseFile file >>= putStr . check) $
>                         \e -> print (e :: SomeException)
> where check (ParseOk _) = replicate (2+length file) '\b'
>               check (ParseFailed loc msg) = unlines [err]
>                where err = msg ++ " at " ++
>                            show (srcLine loc) ++ ":" ++
>                            show (srcColumn loc)
-------

After making it executable you can run it as shell script and pass names of Haskell files -- (something like) this will check all Haskell files (literate or not) in your home directory:

   find ~ -name "*hs" | xargs parse-haskell.lhs

Cheers,
Sebastian

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



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

Reply via email to