Skip to content
Snippets Groups Projects
Commit c39bb903 authored by Cheng Shao's avatar Cheng Shao
Browse files

testsuite: add regression test T25473

This commit adds regression test T25473 marked as broken due to #25473.
It will be fixed in the subsequent commit.

(cherry picked from commit ed2ed6c5)
(cherry picked from commit fb470cb6)
parent e5b66003
No related branches found
No related tags found
No related merge requests found
module T25473A where
import GHC.Wasm.Prim
type BinOp a = a -> a -> a
foreign import javascript "wrapper"
mkJSBinOp :: BinOp Int -> IO JSVal
{-# LANGUAGE TemplateHaskell #-}
module T25473B where
import Language.Haskell.TH
import T25473A
$(runIO $ do
_ <- mkJSBinOp (+)
pure [])
setTestOpts([
unless(arch('wasm32'), skip)
])
test('T25473', [expect_broken(25473)], multimod_compile, ['T25473B', '-v0'])
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment