Update examples

This commit is contained in:
Don Stewart
2005-09-03 04:45:14 +00:00
parent 5321754614
commit dff0363224
421 changed files with 19 additions and 9 deletions

View File

@ -0,0 +1,3 @@
module A where
a = "a"

View File

@ -0,0 +1,3 @@
module B where
b = "b"

View File

@ -0,0 +1,3 @@
module C where
c = "c"

View File

@ -0,0 +1,3 @@
TEST= make/makeall001
TOP=../../..
include ../../build.mk

View File

@ -0,0 +1,13 @@
module Tiny ( resource ) where
import API
import A
import B
import C
resource = tiny {
field = a ++ b ++ c
}

View File

@ -0,0 +1,13 @@
{-# OPTIONS -fglasgow-exts #-}
-- ^ needed to derive Typeable
module API where
import Data.Dynamic
data Tiny = Tiny { field :: String }
deriving (Typeable, Show)
tiny :: Tiny
tiny = Tiny { field = "default value" }

View File

@ -0,0 +1,18 @@
-- little more complex. use the path to the obj file we get back from
-- 'make'. load() uses this to find the .hi file
import System.Plugins
import API
main = do
status <- makeAll "../Tiny.hs" ["-i../api"]
o <- case status of
MakeSuccess _ o -> return o
MakeFailure e -> mapM_ putStrLn e >> error "failed"
m_v <- load o [".."] [] "resource"
v <- case m_v of
LoadSuccess _ v -> return v
_ -> error "load failed"
putStrLn $ field v

View File

@ -0,0 +1 @@
abc

View File

@ -0,0 +1,4 @@
TEST= make/null
TOP=../../..
include ../../build.mk

View File

@ -0,0 +1,11 @@
module Null ( resource, resource_dyn ) where
import API
import Data.Dynamic
import Prelude hiding (null)
resource = null
-- ! this has to be special: it can't be overridden by the user.
resource_dyn :: Dynamic
resource_dyn = toDyn resource

View File

@ -0,0 +1,12 @@
{-# OPTIONS -fglasgow-exts #-}
module API where
import Data.Dynamic
data Null = Null { a, b :: Int }
deriving (Typeable, Show)
null :: Null
null = Null { a = 42 , b = 1 }

View File

@ -0,0 +1,13 @@
-- an example where we want to compile and load a file
import System.Plugins
import API
main = do
make "../Null.hs" ["-i../api"]
m_v <- load "../Null.o" ["../api"] [] "resource"
v <- case m_v of
LoadSuccess _ v -> return v
_ -> error "load failed"
putStrLn ( show (a v) )

View File

@ -0,0 +1 @@
42

View File

@ -0,0 +1,3 @@
TEST=make/o
TOP =../../..
include ../../build.mk

View File

@ -0,0 +1,7 @@
module Plugin ( resource ) where
import API
resource = plugin {
field = "hello out there"
}

View File

@ -0,0 +1,8 @@
module API where
data Interface = Interface {
field :: String
}
plugin :: Interface
plugin = Interface { field = undefined }

View File

@ -0,0 +1,28 @@
import System.Plugins
import API
import System.Directory
-- note: the name of the original *source* module is used to find
-- symbols in the *object* file. load works out what the source file
-- name was by looking at the object file name, i.e. it assumes they
-- have the same name. so, if you are going to store objects in a
-- tmpdir, you should make a tmp directory, and store them inside that,
-- rather than mkstemp'ing the name of the object file yourself.
--
-- this should go away once we can read .hi files.
main = do
#if __GLASGOW_HASKELL__ >= 604
tmpDir <- getTemporaryDirectory
#else
let tmpDir = "/tmp"
#endif
make "../Plugin.hs" [ "-i../api", "-o", (tmpDir ++ "/Plugin.o") ]
m_v <- load (tmpDir ++ "/Plugin.o") ["../api"] [] "resource"
v <- case m_v of
LoadSuccess _ v -> return v
_ -> error "load failed"
putStrLn $ field v
mapM_ removeFile [ (tmpDir ++ "/Plugin.hi"), (tmpDir ++ "/Plugin.o") ]

View File

@ -0,0 +1 @@
hello out there

View File

@ -0,0 +1,3 @@
TEST= make/odir
TOP=../../..
include ../../build.mk

View File

@ -0,0 +1,7 @@
module Plugin ( resource ) where
import API
resource = plugin {
field = "hello out there"
}

View File

@ -0,0 +1,8 @@
module API where
data Interface = Interface {
field :: String
}
plugin :: Interface
plugin = Interface { field = undefined }

View File

@ -0,0 +1,21 @@
import System.Plugins
import API
import System.Directory
main = do
#if __GLASGOW_HASKELL__ >= 604
tmpDir <- getTemporaryDirectory
#else
let tmpDir = "/tmp"
#endif
status <- make "../Plugin.hs" [ "-i../api", "-odir", tmpDir ]
o <- case status of
MakeSuccess _ o -> return o
MakeFailure e -> mapM_ putStrLn e >> error "didn't compile"
m_v <- load o ["../api"] [] "resource"
v <- case m_v of
LoadSuccess _ v -> return v
_ -> error "load failed"
putStrLn $ field v
mapM_ removeFile [(tmpDir ++ "/Plugin.hi"), (tmpDir ++ "/Plugin.o") ]

View File

@ -0,0 +1 @@
hello out there

View File

@ -0,0 +1,3 @@
module Bar where
bar = undefined

View File

@ -0,0 +1,3 @@
module Foo where
foo = undefined

View File

@ -0,0 +1,36 @@
--
-- expected output:
-- $ ./a.out
-- True
-- False
-- True
-- False
--
import System.Plugins
import System.Directory
main = do
status <- make "Foo.hs" [] -- should make
print status
status <- make "Foo.hs" [] -- shouldn't make
print status
status <- merge "Foo.hs" "Bar.hs"
case status of
MergeFailure e -> error $ show e
MergeSuccess _ _ fp -> do {
;status <- make fp [] -- should make
;() <- case status of
MakeSuccess c _ -> print c
MakeFailure e -> error $ show e
;status <- make fp [] -- shouldn't make
;case status of
MakeSuccess c _ -> print c
MakeFailure e -> error $ show e
;removeFile "Foo.o"
}

View File

@ -0,0 +1,4 @@
TEST= merge/remake001
TOP=../../..
include ../../eval.mk

View File

@ -0,0 +1,4 @@
MakeSuccess ReComp "Foo.o"
MakeSuccess NotReq "Foo.o"
ReComp
NotReq

View File

@ -0,0 +1,3 @@
module Bar where
bar = undef {- error -}

View File

@ -0,0 +1,3 @@
module Foo where
foo = undefined

View File

@ -0,0 +1,31 @@
import System.Plugins
import System.Directory
main = do
status <- make "Foo.hs" [] -- should make
print status
status <- make "Foo.hs" [] -- shouldn't make
print status
status <- merge "Foo.hs" "Bar.hs"
case status of
MergeFailure e -> error $ show e
MergeSuccess _ _ fp -> do {
;status <- make fp [] -- should make
;() <- case status of
MakeSuccess c _ -> print c
MakeFailure _ -> print "make failure"
;status <- make fp [] -- shouldn't make
;case status of
MakeSuccess c _ -> print c
MakeFailure _ -> print "make failure"
;removeFile "Foo.o" -- make test deterministic
}

View File

@ -0,0 +1,4 @@
TEST= make/remake001_should_fail
TOP=../../..
include ../../eval.mk

View File

@ -0,0 +1,4 @@
MakeSuccess ReComp "Foo.o"
MakeSuccess NotReq "Foo.o"
"make failure"
"make failure"

View File

@ -0,0 +1,3 @@
TEST= make/simple
TOP=../../..
include ../../build.mk

View File

@ -0,0 +1,14 @@
module Tiny ( resource, resource_dyn ) where
import API
import Data.Dynamic
resource = tiny {
field = "hello strange world"
}
resource_dyn :: Dynamic
resource_dyn = toDyn resource

View File

@ -0,0 +1,13 @@
{-# OPTIONS -fglasgow-exts #-}
-- ^ needed to derive Typeable
module API where
import Data.Dynamic
data Tiny = Tiny { field :: String }
deriving (Typeable, Show)
tiny :: Tiny
tiny = Tiny { field = "default value" }

View File

@ -0,0 +1,19 @@
-- little more complex. use the path to the obj file we get back from
-- 'make'. load() uses this to find the .hi file
import System.Plugins
import API
main = do
status <- make "../Tiny.hs" ["-i../api"]
o <- case status of
MakeSuccess _ o -> return o
MakeFailure e -> mapM_ putStrLn e >> error "failed"
m_v <- load o ["../api"] [] "resource"
v <- case m_v of
LoadSuccess _ v -> return v
_ -> error "load failed"
putStrLn $ field v

View File

@ -0,0 +1 @@
hello strange world