Skip to content

Commit

Permalink
Added use of GHC API for compiling to a file
Browse files Browse the repository at this point in the history
* Invoke using 'compileToFile' function
  • Loading branch information
blambo committed Nov 14, 2011
1 parent e8656f3 commit 1fc4fa8
Show file tree
Hide file tree
Showing 2 changed files with 43 additions and 5 deletions.
44 changes: 40 additions & 4 deletions Data/Array/Accelerate/Repa.hs
Expand Up @@ -11,6 +11,7 @@
module Data.Array.Accelerate.Repa
( Arrays
, run
, compileToFile
)
where

Expand All @@ -22,23 +23,50 @@ import Data.Array.Accelerate.Repa.Stencil (stencilDoc)

import Text.PrettyPrint

-- | Used to compile and run an embedded array program using the Repa backend
--run :: Arrays a => Smart.Acc a -> String
--run = evalAcc . Smart.convertAcc
import GHC -- For compiling and running using GHC API
import GHC.Paths (libdir) -- simplifies use of GHC API
import System.IO -- For writing source to a file

-- | Used to compile and run an embedded array program using the Repa backend
run :: Arrays a => Smart.Acc a -> String
run acc = show $
headS $$ (nest 1 (evalAcc $ Smart.convertAcc acc))
$$ tailS
$+$ text " "
$$ stencilDoc

compileToFile :: Arrays a => Maybe String -> Smart.Acc a -> IO ()
compileToFile targetFile acc = do
let f = case targetFile of
Just s -> s
Nothing -> defaultFile
-- writes source to file as currently can't compile from String
writeFile f $ run acc
-- using GHC API from here
r <- loadAndCompile f
case r of
Just err -> error err
Nothing -> return ()

loadAndCompile :: String -> IO (Maybe String)
loadAndCompile targetFile = runGhc (Just libdir) $ do
dflags <- getSessionDynFlags
setSessionDynFlags (dflags{
optLevel = 2
})
target <- guessTarget targetFile Nothing
addTarget target
r <- load LoadAllTargets
return $ case r of
Failed -> Just "Error in module loading"
Succeeded -> Nothing

headS :: Doc
{-# INLINE headS #-}
headS =
text "{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, TypeOperators #-}" $+$
text "{-# LANGUAGE FlexibleContexts #-}" $+$
text "module AccRepa where" $+$
text "module" <+> text modName <+> text "where" $+$
text "import Data.Array.Repa as Repa" $+$
text "import Data.Bits -- required for Prim ops" $+$
text "import Data.Char -- required for Prim ops" $+$
Expand All @@ -51,3 +79,11 @@ headS =
tailS :: Doc
{-# INLINE tailS #-}
tailS = empty

modName :: String
{-# INLINE modName #-}
modName = "Main"

defaultFile :: String
{-# INLINE defaultFile #-}
defaultFile = "AccRepa.hs"
4 changes: 3 additions & 1 deletion accelerate-repa.cabal
Expand Up @@ -18,7 +18,9 @@ Library
Build-depends: repa == 2.*,
accelerate == 0.9.*,
base,
pretty == 1.1.*
pretty == 1.1.*,
ghc-paths == 0.1.*,
ghc == 7.2.*

Exposed-modules: Data.Array.Accelerate.Repa
Other-modules: Data.Array.Accelerate.Repa.Evaluations
Expand Down

0 comments on commit 1fc4fa8

Please sign in to comment.