Import hs-plugins cvs
This commit is contained in:
5
examples/pdynload/badint/Makefile
Normal file
5
examples/pdynload/badint/Makefile
Normal file
@ -0,0 +1,5 @@
|
||||
|
||||
TEST=pdynload/badint
|
||||
|
||||
TOP=../../..
|
||||
include ../../build.mk
|
4
examples/pdynload/badint/Plugin.hs
Normal file
4
examples/pdynload/badint/Plugin.hs
Normal file
@ -0,0 +1,4 @@
|
||||
module Plugin where
|
||||
|
||||
resource :: Num t => t
|
||||
resource = 0xBAD
|
9
examples/pdynload/badint/api/API.hs
Normal file
9
examples/pdynload/badint/api/API.hs
Normal file
@ -0,0 +1,9 @@
|
||||
module API where
|
||||
|
||||
data Interface = Interface {
|
||||
transform :: String -> String
|
||||
}
|
||||
|
||||
rsrc :: Interface
|
||||
rsrc = Interface { transform = id }
|
||||
|
18
examples/pdynload/badint/prog/Main.hs
Normal file
18
examples/pdynload/badint/prog/Main.hs
Normal file
@ -0,0 +1,18 @@
|
||||
|
||||
import Plugins
|
||||
import API
|
||||
|
||||
src = "../Plugin.hs"
|
||||
wrap = "../Wrapper.hs"
|
||||
apipath = "../api"
|
||||
|
||||
main = do status <- make src ["-i"++apipath]
|
||||
case status of
|
||||
MakeSuccess _ _ -> f
|
||||
MakeFailure e-> mapM_ putStrLn e
|
||||
|
||||
where f = do v <- pdynload "../Plugin.o" ["../api"] [] "API.Interface" "resource"
|
||||
case v of
|
||||
LoadSuccess _ a -> putStrLn $ (transform a) "foo"
|
||||
_ -> putStrLn "wrong types"
|
||||
|
1
examples/pdynload/badint/prog/expected
Normal file
1
examples/pdynload/badint/prog/expected
Normal file
@ -0,0 +1 @@
|
||||
wrong types
|
4
examples/pdynload/null/Makefile
Normal file
4
examples/pdynload/null/Makefile
Normal file
@ -0,0 +1,4 @@
|
||||
|
||||
TEST= pdynload/null
|
||||
TOP=../../..
|
||||
include ../../build.mk
|
5
examples/pdynload/null/Plugin.hs
Normal file
5
examples/pdynload/null/Plugin.hs
Normal file
@ -0,0 +1,5 @@
|
||||
module Plugin where
|
||||
|
||||
import API
|
||||
|
||||
resource = D 1
|
5
examples/pdynload/null/api/API.hs
Normal file
5
examples/pdynload/null/api/API.hs
Normal file
@ -0,0 +1,5 @@
|
||||
|
||||
module API where
|
||||
|
||||
data Num t => Interface t = D t
|
||||
|
19
examples/pdynload/null/prog/Main.hs
Normal file
19
examples/pdynload/null/prog/Main.hs
Normal file
@ -0,0 +1,19 @@
|
||||
|
||||
import Plugins
|
||||
import Plugins.Utils
|
||||
import API
|
||||
|
||||
src = "../Plugin.hs"
|
||||
wrap = "../Wrapper.hs"
|
||||
apipath = "../api"
|
||||
|
||||
main = do status <- make src ["-i"++apipath]
|
||||
case status of
|
||||
MakeSuccess _ _ -> f
|
||||
MakeFailure e-> mapM_ putStrLn e
|
||||
|
||||
where f = do v <- load "../Plugin.o" ["../api"] [] "resource"
|
||||
-- (i,_) <- exec "ghc" ["--numeric-version"]
|
||||
-- mapM_ putStrLn i
|
||||
putStrLn "done."
|
||||
|
1
examples/pdynload/null/prog/expected
Normal file
1
examples/pdynload/null/prog/expected
Normal file
@ -0,0 +1 @@
|
||||
done.
|
4
examples/pdynload/numclass/Makefile
Normal file
4
examples/pdynload/numclass/Makefile
Normal file
@ -0,0 +1,4 @@
|
||||
|
||||
TEST= pdynload/numclass
|
||||
TOP=../../..
|
||||
include ../../build.mk
|
5
examples/pdynload/numclass/Plugin.hs
Normal file
5
examples/pdynload/numclass/Plugin.hs
Normal file
@ -0,0 +1,5 @@
|
||||
module Plugin where
|
||||
|
||||
-- import API
|
||||
|
||||
resource = "error"
|
5
examples/pdynload/numclass/api/API.hs
Normal file
5
examples/pdynload/numclass/api/API.hs
Normal file
@ -0,0 +1,5 @@
|
||||
|
||||
module API where
|
||||
|
||||
data Num t => Interface t = D t
|
||||
|
19
examples/pdynload/numclass/prog/Main.hs
Normal file
19
examples/pdynload/numclass/prog/Main.hs
Normal file
@ -0,0 +1,19 @@
|
||||
|
||||
import Plugins
|
||||
import API
|
||||
|
||||
src = "../Plugin.hs"
|
||||
wrap = "../Wrapper.hs"
|
||||
apipath = "../api"
|
||||
|
||||
main = do status <- make src ["-i"++apipath]
|
||||
case status of
|
||||
MakeFailure _ -> putStrLn "make failed"
|
||||
MakeSuccess _ _ -> do {
|
||||
|
||||
;v <- pdynload "../Plugin.o" ["../api"] [] "API.Interface Integer" "resource"
|
||||
;case v of
|
||||
LoadSuccess _ a -> let D i = snd a in putStrLn $ show i
|
||||
_ -> putStrLn "wrong types"
|
||||
|
||||
}
|
1
examples/pdynload/numclass/prog/expected
Normal file
1
examples/pdynload/numclass/prog/expected
Normal file
@ -0,0 +1 @@
|
||||
wrong types
|
5
examples/pdynload/poly/Makefile
Normal file
5
examples/pdynload/poly/Makefile
Normal file
@ -0,0 +1,5 @@
|
||||
|
||||
TEST=pdynload/poly
|
||||
|
||||
TOP=../../..
|
||||
include ../../build.mk
|
9
examples/pdynload/poly/Plugin.hs
Normal file
9
examples/pdynload/poly/Plugin.hs
Normal file
@ -0,0 +1,9 @@
|
||||
module Plugin where
|
||||
|
||||
import Data.Generics.Schemes
|
||||
|
||||
import API
|
||||
|
||||
resource = rsrc {
|
||||
field = id listify
|
||||
}
|
12
examples/pdynload/poly/api/API.hs
Normal file
12
examples/pdynload/poly/api/API.hs
Normal file
@ -0,0 +1,12 @@
|
||||
{-# OPTIONS -fglasgow-exts #-}
|
||||
-- a really nasty type:
|
||||
|
||||
module API where
|
||||
|
||||
import Data.Generics
|
||||
|
||||
data Interface = Interface { field :: Typeable r => (r -> Bool) -> GenericQ [r] }
|
||||
|
||||
rsrc :: Interface
|
||||
rsrc = Interface { field = listify }
|
||||
|
17
examples/pdynload/poly/prog/Main.hs
Normal file
17
examples/pdynload/poly/prog/Main.hs
Normal file
@ -0,0 +1,17 @@
|
||||
|
||||
import Plugins
|
||||
import API
|
||||
|
||||
src = "../Plugin.hs"
|
||||
wrap = "../Wrapper.hs"
|
||||
apipath = "../api"
|
||||
|
||||
main = do status <- make src ["-i"++apipath]
|
||||
case status of
|
||||
MakeSuccess _ _ -> f
|
||||
MakeFailure e -> mapM_ putStrLn e
|
||||
|
||||
where f = do v <- pdynload "../Plugin.o" ["../api"] [] "API.Interface" "resource"
|
||||
case v of
|
||||
LoadSuccess _ a -> putStrLn "loaded .. yay!"
|
||||
_ -> putStrLn "wrong types"
|
1
examples/pdynload/poly/prog/expected
Normal file
1
examples/pdynload/poly/prog/expected
Normal file
@ -0,0 +1 @@
|
||||
loaded .. yay!
|
4
examples/pdynload/poly1/Makefile
Normal file
4
examples/pdynload/poly1/Makefile
Normal file
@ -0,0 +1,4 @@
|
||||
TEST= pdynload/poly1
|
||||
EXTRA_OBJS=Plugin.o
|
||||
TOP=../../..
|
||||
include ../../build.mk
|
5
examples/pdynload/poly1/Plugin.hs
Normal file
5
examples/pdynload/poly1/Plugin.hs
Normal file
@ -0,0 +1,5 @@
|
||||
module Plugin where
|
||||
|
||||
import API
|
||||
|
||||
resource = plugin { function = (+) }
|
9
examples/pdynload/poly1/api/API.hs
Normal file
9
examples/pdynload/poly1/api/API.hs
Normal file
@ -0,0 +1,9 @@
|
||||
module API where
|
||||
|
||||
data Interface = Interface {
|
||||
function :: (Num a) => a -> a -> a
|
||||
}
|
||||
|
||||
plugin :: Interface
|
||||
plugin = Interface { function = error "no function defined" }
|
||||
|
18
examples/pdynload/poly1/prog/Main.hs
Normal file
18
examples/pdynload/poly1/prog/Main.hs
Normal file
@ -0,0 +1,18 @@
|
||||
|
||||
import Plugins
|
||||
import API
|
||||
|
||||
src = "../Plugin.hs"
|
||||
wrap = "../Wrapper.hs"
|
||||
apipath = "../api"
|
||||
|
||||
main = do status <- make src ["-i"++apipath]
|
||||
case status of
|
||||
MakeSuccess _ _ -> f
|
||||
MakeFailure e -> mapM_ putStrLn e
|
||||
|
||||
where f = do v <- pdynload "../Plugin.o" ["../api"] [] "API.Interface" "resource"
|
||||
case v of
|
||||
LoadSuccess _ a -> let fn = function a in putStrLn $ show $ 1 `fn` 2
|
||||
_ -> putStrLn "wrong types"
|
||||
|
1
examples/pdynload/poly1/prog/expected
Normal file
1
examples/pdynload/poly1/prog/expected
Normal file
@ -0,0 +1 @@
|
||||
3
|
4
examples/pdynload/should_fail0/Makefile
Normal file
4
examples/pdynload/should_fail0/Makefile
Normal file
@ -0,0 +1,4 @@
|
||||
TEST= pdynload/should_fail0
|
||||
EXTRA_OBJS=Plugin.o
|
||||
TOP=../../..
|
||||
include ../../build.mk
|
9
examples/pdynload/should_fail0/Plugin.hs
Normal file
9
examples/pdynload/should_fail0/Plugin.hs
Normal file
@ -0,0 +1,9 @@
|
||||
module Plugin where
|
||||
|
||||
import API
|
||||
|
||||
resource = 0xBAD :: Int
|
||||
|
||||
-- resource = tiny {
|
||||
-- field = "hello strange world"
|
||||
-- }
|
13
examples/pdynload/should_fail0/api/API.hs
Normal file
13
examples/pdynload/should_fail0/api/API.hs
Normal file
@ -0,0 +1,13 @@
|
||||
{-# OPTIONS -fglasgow-exts #-}
|
||||
-- ^ needed to derive Typeable
|
||||
|
||||
module API where
|
||||
|
||||
import Data.Dynamic
|
||||
|
||||
data Interface = Interface { field :: String }
|
||||
deriving (Show)
|
||||
|
||||
rsrc :: Interface
|
||||
rsrc = Interface { field = "default value" }
|
||||
|
18
examples/pdynload/should_fail0/prog/Main.hs
Normal file
18
examples/pdynload/should_fail0/prog/Main.hs
Normal file
@ -0,0 +1,18 @@
|
||||
|
||||
import Plugins
|
||||
import API
|
||||
|
||||
src = "../Plugin.hs"
|
||||
wrap = "../Wrapper.hs"
|
||||
apipath = "../api"
|
||||
|
||||
main = do status <- make src ["-i"++apipath]
|
||||
case status of
|
||||
MakeSuccess _ _ -> f
|
||||
MakeFailure e -> mapM_ putStrLn e
|
||||
where
|
||||
f = do v <- pdynload "../Plugin.o" ["../api"] [] "API.Interface" "resource"
|
||||
case v of
|
||||
LoadSuccess _ a -> putStrLn "loaded .. yay!"
|
||||
_ -> putStrLn "wrong types"
|
||||
|
1
examples/pdynload/should_fail0/prog/expected
Normal file
1
examples/pdynload/should_fail0/prog/expected
Normal file
@ -0,0 +1 @@
|
||||
wrong types
|
5
examples/pdynload/should_fail1/Makefile
Normal file
5
examples/pdynload/should_fail1/Makefile
Normal file
@ -0,0 +1,5 @@
|
||||
# Missing class constraint... can't do that in Clean
|
||||
|
||||
TEST= pdynload/should_fail1
|
||||
TOP=../../..
|
||||
include ../../build.mk
|
5
examples/pdynload/should_fail1/Plugin.hs
Normal file
5
examples/pdynload/should_fail1/Plugin.hs
Normal file
@ -0,0 +1,5 @@
|
||||
module Plugin where
|
||||
|
||||
data I = I Int
|
||||
|
||||
resource = I 1
|
8
examples/pdynload/should_fail1/api/API.hs
Normal file
8
examples/pdynload/should_fail1/api/API.hs
Normal file
@ -0,0 +1,8 @@
|
||||
|
||||
module API where
|
||||
|
||||
newtype Interface = I Int
|
||||
|
||||
rsrc :: Interface
|
||||
rsrc = I 1
|
||||
|
17
examples/pdynload/should_fail1/prog/Main.hs
Normal file
17
examples/pdynload/should_fail1/prog/Main.hs
Normal file
@ -0,0 +1,17 @@
|
||||
|
||||
import Plugins
|
||||
import API
|
||||
|
||||
src = "../Plugin.hs"
|
||||
wrap = "../Wrapper.hs"
|
||||
apipath = "../api"
|
||||
|
||||
main = do status <- make src ["-i"++apipath]
|
||||
case status of
|
||||
MakeSuccess _ _ -> f
|
||||
MakeFailure e -> mapM_ putStrLn e
|
||||
|
||||
where f = do v <- pdynload "../Plugin.o" ["../api"] [] "API.Interface" "resource"
|
||||
case v of
|
||||
LoadSuccess _ a -> putStrLn "loaded .. yay!"
|
||||
_ -> putStrLn "wrong types"
|
1
examples/pdynload/should_fail1/prog/expected
Normal file
1
examples/pdynload/should_fail1/prog/expected
Normal file
@ -0,0 +1 @@
|
||||
wrong types
|
4
examples/pdynload/small/Makefile
Normal file
4
examples/pdynload/small/Makefile
Normal file
@ -0,0 +1,4 @@
|
||||
TEST= pdynload/small
|
||||
EXTRA_OBJS=Plugin.o
|
||||
TOP=../../..
|
||||
include ../../build.mk
|
5
examples/pdynload/small/Plugin.hs
Normal file
5
examples/pdynload/small/Plugin.hs
Normal file
@ -0,0 +1,5 @@
|
||||
module Plugin where
|
||||
|
||||
import API
|
||||
|
||||
resource = plugin { function = "good" }
|
9
examples/pdynload/small/api/API.hs
Normal file
9
examples/pdynload/small/api/API.hs
Normal file
@ -0,0 +1,9 @@
|
||||
module API where
|
||||
|
||||
data Interface = Interface {
|
||||
function :: String
|
||||
}
|
||||
|
||||
plugin :: Interface
|
||||
plugin = Interface { function = "goodbye" }
|
||||
|
18
examples/pdynload/small/prog/Main.hs
Normal file
18
examples/pdynload/small/prog/Main.hs
Normal file
@ -0,0 +1,18 @@
|
||||
|
||||
import Plugins
|
||||
import API
|
||||
|
||||
src = "../Plugin.hs"
|
||||
wrap = "../Wrapper.hs"
|
||||
apipath = "../api"
|
||||
|
||||
main = do status <- make src ["-i"++apipath]
|
||||
case status of
|
||||
MakeSuccess _ _ -> f
|
||||
MakeFailure e -> mapM_ putStrLn e
|
||||
|
||||
where f = do v <- pdynload "../Plugin.o" ["../api"] [] "API.Interface" "resource"
|
||||
case v of
|
||||
LoadSuccess _ a -> putStrLn "loaded .. yay!"
|
||||
_ -> putStrLn "wrong types"
|
||||
|
1
examples/pdynload/small/prog/expected
Normal file
1
examples/pdynload/small/prog/expected
Normal file
@ -0,0 +1 @@
|
||||
loaded .. yay!
|
5
examples/pdynload/spj1/Makefile
Normal file
5
examples/pdynload/spj1/Makefile
Normal file
@ -0,0 +1,5 @@
|
||||
|
||||
TEST=pdynload/spj1
|
||||
|
||||
TOP=../../..
|
||||
include ../../build.mk
|
17
examples/pdynload/spj1/Plugin.hs
Normal file
17
examples/pdynload/spj1/Plugin.hs
Normal file
@ -0,0 +1,17 @@
|
||||
module Plugin where
|
||||
|
||||
-- user doesn't import the API
|
||||
-- and provides a polymorphic value
|
||||
|
||||
-- import API
|
||||
-- resource :: Interface
|
||||
|
||||
--
|
||||
-- should pass type check, and dump core
|
||||
--
|
||||
-- resource :: Num a => a
|
||||
|
||||
-- import API
|
||||
|
||||
resource :: Num a => a
|
||||
resource = 7
|
9
examples/pdynload/spj1/api/API.hs
Normal file
9
examples/pdynload/spj1/api/API.hs
Normal file
@ -0,0 +1,9 @@
|
||||
|
||||
module API where
|
||||
|
||||
-- data Interface = Interface { field :: Int }
|
||||
|
||||
-- newtype Interface = Interface Int
|
||||
|
||||
type Interface = Int
|
||||
|
0
examples/pdynload/spj1/dont_test
Normal file
0
examples/pdynload/spj1/dont_test
Normal file
17
examples/pdynload/spj1/prog/Main.hs
Normal file
17
examples/pdynload/spj1/prog/Main.hs
Normal file
@ -0,0 +1,17 @@
|
||||
|
||||
import Plugins
|
||||
import API
|
||||
|
||||
src = "../Plugin.hs"
|
||||
wrap = "../Wrapper.hs"
|
||||
apipath = "../api"
|
||||
|
||||
main = do status <- make src ["-i"++apipath]
|
||||
case status of
|
||||
MakeSuccess _ _ -> f
|
||||
MakeFailure e -> mapM_ putStrLn e
|
||||
|
||||
where f = do v <- pdynload "../Plugin.o" ["../api"] [] "API.Interface" "resource"
|
||||
case v of
|
||||
LoadSuccess _ (a :: Interface) -> print $ a -- will crash
|
||||
LoadFailure es -> putStrLn $ show es
|
0
examples/pdynload/spj1/prog/expected
Normal file
0
examples/pdynload/spj1/prog/expected
Normal file
5
examples/pdynload/spj2/Makefile
Normal file
5
examples/pdynload/spj2/Makefile
Normal file
@ -0,0 +1,5 @@
|
||||
|
||||
TEST=pdynload/spj1
|
||||
|
||||
TOP=../../..
|
||||
include ../../build.mk
|
13
examples/pdynload/spj2/Plugin.hs
Normal file
13
examples/pdynload/spj2/Plugin.hs
Normal file
@ -0,0 +1,13 @@
|
||||
module Plugin where
|
||||
|
||||
-- user doesn't import the API
|
||||
-- and provides a polymorphic value
|
||||
|
||||
import API
|
||||
resource :: Interface
|
||||
|
||||
--
|
||||
-- should pass type check, and dump core
|
||||
--
|
||||
-- resource :: Num a => a
|
||||
resource = 7
|
6
examples/pdynload/spj2/api/API.hs
Normal file
6
examples/pdynload/spj2/api/API.hs
Normal file
@ -0,0 +1,6 @@
|
||||
|
||||
module API where
|
||||
|
||||
-- simple type
|
||||
type Interface = Int
|
||||
|
17
examples/pdynload/spj2/prog/Main.hs
Normal file
17
examples/pdynload/spj2/prog/Main.hs
Normal file
@ -0,0 +1,17 @@
|
||||
|
||||
import Plugins
|
||||
import API
|
||||
|
||||
src = "../Plugin.hs"
|
||||
wrap = "../Wrapper.hs"
|
||||
apipath = "../api"
|
||||
|
||||
main = do status <- make src ["-i"++apipath]
|
||||
case status of
|
||||
MakeSuccess _ _ -> f
|
||||
MakeFailure e -> mapM_ putStrLn e
|
||||
|
||||
where f = do v <- pdynload "../Plugin.o" ["../api"] [] "API.Interface" "resource"
|
||||
case v of
|
||||
LoadSuccess _ (a :: Interface) -> putStrLn $ show a -- will crash
|
||||
LoadFailure es -> putStrLn $ show es
|
1
examples/pdynload/spj2/prog/expected
Normal file
1
examples/pdynload/spj2/prog/expected
Normal file
@ -0,0 +1 @@
|
||||
7
|
3
examples/pdynload/spj3/Makefile
Normal file
3
examples/pdynload/spj3/Makefile
Normal file
@ -0,0 +1,3 @@
|
||||
TEST= pdynload/spj3
|
||||
TOP=../../..
|
||||
include ../../build.mk
|
5
examples/pdynload/spj3/Plugin.hs
Normal file
5
examples/pdynload/spj3/Plugin.hs
Normal file
@ -0,0 +1,5 @@
|
||||
module Plugin where
|
||||
|
||||
import API
|
||||
|
||||
resource = plugin { function = (+) :: Int -> Int -> Int }
|
9
examples/pdynload/spj3/api/API.hs
Normal file
9
examples/pdynload/spj3/api/API.hs
Normal file
@ -0,0 +1,9 @@
|
||||
module API where
|
||||
|
||||
data Interface = Interface {
|
||||
function :: (Num a) => a -> a -> a
|
||||
}
|
||||
|
||||
plugin :: Interface
|
||||
plugin = Interface { function = error "no function defined" }
|
||||
|
18
examples/pdynload/spj3/prog/Main.hs
Normal file
18
examples/pdynload/spj3/prog/Main.hs
Normal file
@ -0,0 +1,18 @@
|
||||
|
||||
import Plugins
|
||||
import API
|
||||
|
||||
src = "../Plugin.hs"
|
||||
wrap = "../Wrapper.hs"
|
||||
apipath = "../api"
|
||||
|
||||
main = do status <- make src ["-i"++apipath]
|
||||
case status of
|
||||
MakeSuccess _ _ -> f
|
||||
MakeFailure e -> mapM_ putStrLn e
|
||||
|
||||
where f = do v <- pdynload "../Plugin.o" ["../api"] [] "API.Interface" "resource"
|
||||
case v of
|
||||
LoadSuccess _ a -> let fn = function a in putStrLn $ show $ 1 `fn` 2
|
||||
_ -> putStrLn "wrong types"
|
||||
|
8
examples/pdynload/spj3/prog/expected
Normal file
8
examples/pdynload/spj3/prog/expected
Normal file
@ -0,0 +1,8 @@
|
||||
|
||||
../Plugin.hs:5:
|
||||
Cannot unify the type-signature variable `a' with the type `Int'
|
||||
Expected type: a -> a -> a
|
||||
Inferred type: Int -> Int -> Int
|
||||
When checking the type signature of the expression:
|
||||
(+) :: Int -> Int -> Int
|
||||
In the `function' field of a record
|
9
examples/pdynload/spj3/prog/expected.604
Normal file
9
examples/pdynload/spj3/prog/expected.604
Normal file
@ -0,0 +1,9 @@
|
||||
|
||||
../Plugin.hs:5:31:
|
||||
Couldn't match the rigid variable `a' against `Int'
|
||||
`a' is bound by the polymorphic type `forall a. (Num a) => a -> a -> a'
|
||||
at ../Plugin.hs:5:11-56
|
||||
Expected type: a -> a -> a
|
||||
Inferred type: Int -> Int -> Int
|
||||
In the expression: (+) :: Int -> Int -> Int
|
||||
In the `function' field of a record
|
5
examples/pdynload/spj4/Makefile
Normal file
5
examples/pdynload/spj4/Makefile
Normal file
@ -0,0 +1,5 @@
|
||||
|
||||
TEST=pdynload/spj4
|
||||
|
||||
TOP=../../..
|
||||
include ../../build.mk
|
16
examples/pdynload/spj4/Plugin.hs
Normal file
16
examples/pdynload/spj4/Plugin.hs
Normal file
@ -0,0 +1,16 @@
|
||||
module Plugin where
|
||||
|
||||
-- user doesn't import the API
|
||||
-- and provides a polymorphic value
|
||||
|
||||
-- import API
|
||||
-- resource :: Interface
|
||||
|
||||
--
|
||||
-- should pass type check, and dump core
|
||||
--
|
||||
-- resource :: Num a => a
|
||||
|
||||
import API
|
||||
|
||||
resource = Interface { field = 7 :: Num a => a }
|
5
examples/pdynload/spj4/api/API.hs
Normal file
5
examples/pdynload/spj4/api/API.hs
Normal file
@ -0,0 +1,5 @@
|
||||
|
||||
module API where
|
||||
|
||||
newtype Interface = Interface { field :: Int }
|
||||
|
17
examples/pdynload/spj4/prog/Main.hs
Normal file
17
examples/pdynload/spj4/prog/Main.hs
Normal file
@ -0,0 +1,17 @@
|
||||
|
||||
import Plugins
|
||||
import API
|
||||
|
||||
src = "../Plugin.hs"
|
||||
wrap = "../Wrapper.hs"
|
||||
apipath = "../api"
|
||||
|
||||
main = do status <- make src ["-i"++apipath]
|
||||
case status of
|
||||
MakeSuccess _ _ -> f
|
||||
MakeFailure e -> error "there was a type error"
|
||||
|
||||
where f = do v <- pdynload "../Plugin.o" ["../api"] [] "API.Interface" "resource"
|
||||
case v of
|
||||
LoadSuccess _ (a :: Interface) -> print $ field a -- will crash
|
||||
LoadFailure es -> mapM_ putStrLn es
|
1
examples/pdynload/spj4/prog/expected
Normal file
1
examples/pdynload/spj4/prog/expected
Normal file
@ -0,0 +1 @@
|
||||
7
|
5
examples/pdynload/typealias/Makefile
Normal file
5
examples/pdynload/typealias/Makefile
Normal file
@ -0,0 +1,5 @@
|
||||
# Missing class constraint... can't do that in Clean
|
||||
|
||||
TEST= pdynload/typealias
|
||||
TOP=../../..
|
||||
include ../../build.mk
|
3
examples/pdynload/typealias/Plugin.hs
Normal file
3
examples/pdynload/typealias/Plugin.hs
Normal file
@ -0,0 +1,3 @@
|
||||
module Plugin where
|
||||
|
||||
resource = 1 :: Int
|
8
examples/pdynload/typealias/api/API.hs
Normal file
8
examples/pdynload/typealias/api/API.hs
Normal file
@ -0,0 +1,8 @@
|
||||
|
||||
module API where
|
||||
|
||||
type Interface = Int
|
||||
|
||||
rsrc :: Interface
|
||||
rsrc = 1
|
||||
|
19
examples/pdynload/typealias/prog/Main.hs
Normal file
19
examples/pdynload/typealias/prog/Main.hs
Normal file
@ -0,0 +1,19 @@
|
||||
|
||||
import Plugins
|
||||
import API
|
||||
|
||||
src = "../Plugin.hs"
|
||||
wrap = "../Wrapper.hs"
|
||||
apipath = "../api"
|
||||
|
||||
main = do status <- make src ["-i"++apipath]
|
||||
case status of
|
||||
MakeSuccess _ _ -> f
|
||||
MakeFailure e -> mapM_ putStrLn e
|
||||
|
||||
where f = do v <- pdynload "../Plugin.o" ["../api"] [] "API.Interface" "resource"
|
||||
case v of
|
||||
LoadSuccess _ a -> putStrLn "loaded .. yay!"
|
||||
_ -> putStrLn "wrong types"
|
||||
|
||||
|
1
examples/pdynload/typealias/prog/expected
Normal file
1
examples/pdynload/typealias/prog/expected
Normal file
@ -0,0 +1 @@
|
||||
loaded .. yay!
|
4
examples/pdynload/univquant/Makefile
Normal file
4
examples/pdynload/univquant/Makefile
Normal file
@ -0,0 +1,4 @@
|
||||
TEST= pdynload/univquant
|
||||
EXTRA_OBJS=Plugin.o
|
||||
TOP=../../..
|
||||
include ../../build.mk
|
8
examples/pdynload/univquant/Plugin.hs
Normal file
8
examples/pdynload/univquant/Plugin.hs
Normal file
@ -0,0 +1,8 @@
|
||||
module Plugin where
|
||||
|
||||
import API
|
||||
|
||||
resource = plugin { function = my_id }
|
||||
|
||||
my_id :: forall a. a -> a
|
||||
my_id x = x
|
9
examples/pdynload/univquant/api/API.hs
Normal file
9
examples/pdynload/univquant/api/API.hs
Normal file
@ -0,0 +1,9 @@
|
||||
module API where
|
||||
|
||||
data Interface = Interface {
|
||||
function :: forall a. a -> a
|
||||
}
|
||||
|
||||
plugin :: Interface
|
||||
plugin = Interface { function = id }
|
||||
|
17
examples/pdynload/univquant/prog/Main.hs
Normal file
17
examples/pdynload/univquant/prog/Main.hs
Normal file
@ -0,0 +1,17 @@
|
||||
|
||||
import Plugins
|
||||
import API
|
||||
|
||||
src = "../Plugin.hs"
|
||||
wrap = "../Wrapper.hs"
|
||||
apipath = "../api"
|
||||
|
||||
main = do status <- make src ["-i"++apipath]
|
||||
case status of
|
||||
MakeSuccess _ _ -> f
|
||||
MakeFailure e -> mapM_ putStrLn e
|
||||
|
||||
where f = do v <- pdynload "../Plugin.o" ["../api"] [] "API.Interface" "resource"
|
||||
case v of
|
||||
LoadSuccess _ a -> putStrLn "loaded .. yay!"
|
||||
_ -> putStrLn "wrong types"
|
1
examples/pdynload/univquant/prog/expected
Normal file
1
examples/pdynload/univquant/prog/expected
Normal file
@ -0,0 +1 @@
|
||||
loaded .. yay!
|
Reference in New Issue
Block a user