Skip to content
Snippets Groups Projects
Commit 0833ad55 authored by Matthew Pickering's avatar Matthew Pickering Committed by Marge Bot
Browse files

Add failing test for #20674

parent 4c434c9e
No related branches found
No related tags found
No related merge requests found
{-# LANGUAGE TemplateHaskell #-}
module Main where
import P
main = $([| return () |])
module P where
foreign export ccall foo :: Int -> IO Int
foo :: Int -> IO Int
foo n = return (length (f n))
f :: Int -> [Int]
f 0 = []
f n = n:(f (n-1))
setTestOpts(req_interp)
# TH should work with -fexternal-interpreter too
if config.have_ext_interp :
setTestOpts(extra_ways(['ext-interp']))
setTestOpts(only_ways(['normal','ghci','ext-interp']))
if llvm_build():
setTestOpts(fragile_for(16087, ['ext-interp']))
test('T20674', [expect_broken(20674), extra_files(['Main.hs', 'P.hs', 'foo.c', 'header.h'])], multimod_compile, ['Main', 'P foo.c'])
#include "header.h"
int q() {
int e = foo(0);
return(0);
}
#include <HsFFI.h>
int foo(int);
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