> The only problem I see with that is that error message locations will be
> a bit off, since the file being compiled is different from the file
> submitted. But since we're in the hacks territory anyway, this could be
> fixed up with a simple regex :-)

... or line pragmas :-)

I'm currently investigating another route though. I wrote a simple
program which parses some Haskell files with "haskell-src-exts" (we
actually even need "hse-cpp"), builds a graph with all known
dependencies, uses "topSort" from "Data.Graph" to come up with a proper
ordering and prints the source files in that order. That approach feels
a lot safer to me. It can be used like:

  ghc -c $(cabal exec topoSort "${files[@]}")

(Never mind the obvious unsafe file name handling.)

The downside is that parse errors won't be reported by GHC, but by our
preprocessing tool.

(I've attached the tool, but keep in mind it's just a quick proof of
concept.)

Cheers
Lars
import Control.Applicative
import Data.Graph
import Data.Traversable (traverse)
import Language.Haskell.Exts.Annotated
import Language.Haskell.Exts.Annotated.CPP
import System.Environment

moduleData :: (Module SrcSpanInfo, [Comment]) -> (FilePath, String, [String])
moduleData ((Module srcInfo (Just (ModuleHead _ name _ _)) _ imports _), _) = (srcSpanFilename $ srcInfoSpan srcInfo, getModuleName name, map (getModuleName . importModule) imports)
moduleData _ = error "parse error or unsupported module"

getFilePath (path, _, _) = path
getModuleName (ModuleName _ name) = name

cppOptions =
  defaultCpphsOptions {
    defines = ("Testing", "") : defines defaultCpphsOptions
  }

main = do
  args <- getArgs
  parsed <- sequence <$> traverse (parseFileWithCommentsAndCPP cppOptions defaultParseMode) args
  let mData = map moduleData $ fromParseResult parsed
  let (graph, dest) = graphFromEdges' mData
  putStr $ unwords $ map (getFilePath . dest) $ topSort $ transposeG graph
_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to