Skip to content

Commit

Permalink
Adds a currently failing (not compiling) test case.
Browse files Browse the repository at this point in the history
Using GHCi via TemplateHaskell bytecode interpretation with Data.Atomics.
Related to rrnewton#10 .
Note:  hello-word-atomic-primops.hs missing.
  • Loading branch information
robstewart57 committed Jul 19, 2013
1 parent 0169990 commit 93c0e2c
Show file tree
Hide file tree
Showing 3 changed files with 55 additions and 0 deletions.
21 changes: 21 additions & 0 deletions AtomicPrimops/testing/TemplateHaskellSplices.hs
@@ -0,0 +1,21 @@
{-# LANGUAGE TemplateHaskell,
RankNTypes #-}

-- | TH splices used in atommic-primops tests.
-- Splices defined in own module for technical reasons.

module TemplateHaskellSplices where

import Language.Haskell.TH
import Control.Monad (replicateM)

tmap :: forall a. (Enum a, Eq a, Num a)
=> a -> Int -> Q Exp
tmap i n = do
f <- newName "f"
as <- replicateM n (newName "a")
lamE [varP f, tupP (map varP as)] $
tupE [ if i == i'
then [| $(varE f) $a |]
else a
| (a,i') <- map varE as `zip` [1..] ]
20 changes: 20 additions & 0 deletions AtomicPrimops/testing/ghci-test.hs
@@ -0,0 +1,20 @@
{-# LANGUAGE TemplateHaskell #-}

-- | Test the invocation of the GHCi bytecode intepreter with atomic-primops.

module Main where

import Data.Atomics -- import needed to test whether ghci linking error occurs
import TemplateHaskellSplices (tmap)
import Test.Framework (defaultMain)
import Test.Framework.Providers.HUnit (testCase)

main :: IO ()
main = defaultMain
[
----------------------------------------
testCase "Template_Haskell_invocation" $ do
putStrLn "Attempting Template Haskell implementation of map operation"
print $ $(tmap 3 4) (+ 1) (1,2,3,4) -- comment out for compilation to succeed
----------------------------------------
]
14 changes: 14 additions & 0 deletions AtomicPrimops/testing/test-atomic-primops.cabal
Expand Up @@ -14,6 +14,10 @@ Flag threaded
Description: Enable GHC threaded RTS.
Default: True

Flag withTH
Description: Build the test suite, including the template-haskell-atomic-primops executable.
Default: False

Test-Suite test-atomic-primops
type: exitcode-stdio-1.0
main-is: Test.hs
Expand All @@ -35,3 +39,13 @@ Test-Suite test-atomic-primops
Executable hello-world-atomic-primops
main-is: hello.hs
build-depends: base >= 4.5, atomic-primops

Executable template-haskell-atomic-primops
main-is: ghci-test.hs
if flag(withTH)
Buildable: True
else
Buildable: False
build-depends: base >= 4.5, atomic-primops >= 0.4, template-haskell,
-- For Testing:
test-framework, test-framework-hunit

0 comments on commit 93c0e2c

Please sign in to comment.