Import hs-plugins cvs

This commit is contained in:
Don Stewart
2005-04-24 08:51:33 +00:00
commit 887fa59389
494 changed files with 23721 additions and 0 deletions

View File

@ -0,0 +1,5 @@
TEST=makewith/global_pragma
TOP=../../..
include ../../build.mk

View File

@ -0,0 +1,17 @@
{-# GLOBALOPTIONS -package posix #-}
module M ( resource ) where
import System.IO.Unsafe
import API
import System.Process
import System.IO
resource = tiny { field = date }
date :: String
date = unsafePerformIO $ do
(_,outh,_,proc) <- runInteractiveProcess "echo" ["hello"] Nothing Nothing
waitForProcess proc
s <- hGetContents outh
return s

View File

@ -0,0 +1,8 @@
module API where
data Tiny = Tiny { field :: String }
tiny :: Tiny
tiny = Tiny { field = "default value" }

View File

@ -0,0 +1,19 @@
import Plugins
import API
conf = "../Plugin.hs"
apipath = "../api"
main = do
status <- makeWith conf conf ["-i"++apipath]
o <- case status of
MakeFailure e -> mapM_ putStrLn e >> error "compile failed"
MakeSuccess _ o -> return o
m_v <- load o [apipath] [] "resource"
v <- case m_v of
LoadSuccess _ v -> return v
LoadFailure ers -> mapM_ putStrLn ers >> error "load failed"
putStr $ field v
makeCleaner o

View File

@ -0,0 +1 @@
hello

View File

@ -0,0 +1,4 @@
TEST=makewith/io
TOP=../../..
include ../../build.mk

View File

@ -0,0 +1,2 @@
An example using IO monad fields in the .conf file.

View File

@ -0,0 +1,76 @@
{-# OPTIONS -cpp #-}
--
-- Copyright (c) 2004 Don Stewart - http://www.cse.unsw.edu.au/~dons
-- LGPL version 2.1 or later (see http://www.gnu.org/copyleft/lesser.html)
--
import System.IO
import System.Posix.Types ( ProcessID, Fd )
import System.Posix.Process ( forkProcess, executeFile, getProcessID )
import System.Posix.IO ( createPipe, stdInput,
stdOutput, fdToHandle, closeFd, dupTo )
resource = testio { field = date }
--
-- call a shell command , returning it's output
--
date :: IO String
date = do (hdl,_,_) <- catch (popen "/bin/date") (\_->error "popen failed")
hGetLine hdl
------------------------------------------------------------------------
--
-- my implementation of $val = `cmd`; (if this was perl)
--
-- provide similar functionality to popen(3),
-- along with bidirectional ipc via pipes
-- return's the pid of the child process
--
-- there are two different forkProcess functions. the pre-620 was a
-- unix-fork style function, and the modern function has semantics more
-- like the Awkward-Squad paper. We provide implementations of popen
-- using both versions, depending on which GHC the user wants to try.
--
popen :: FilePath -> IO (Handle, Handle, ProcessID)
popen cmd = do
(pr, pw) <- createPipe
(cr, cw) <- createPipe
-- parent --
let parent = do closeFd cw
closeFd pr
-- child --
let child = do closeFd pw
closeFd cr
exec cmd (pr,cw)
error "exec cmd failed!" -- typing only
-- if the parser front end understood cpp, this would work
-- #if __GLASGOW_HASKELL__ >= 601
pid <- forkProcess child -- fork child
parent -- and run parent code
-- #else
-- p <- forkProcess
-- pid <- case p of
-- Just pid -> parent >> return pid
-- Nothing -> child
-- #endif
hcr <- fdToHandle cr
hpw <- fdToHandle pw
return (hcr,hpw,pid)
--
-- execve cmd in the child process, dup'ing the file descriptors passed
-- as arguments to become the child's stdin and stdout.
--
exec :: FilePath -> (Fd,Fd) -> IO ()
exec cmd (pr,cw) = do
dupTo pr stdInput
dupTo cw stdOutput
executeFile cmd False [] Nothing
------------------------------------------------------------------------

View File

@ -0,0 +1,10 @@
module TestIO ( resource, resource_dyn ) where
import API
import Data.Dynamic
resource = testio
resource_dyn :: Dynamic
resource_dyn = toDyn resource

View File

@ -0,0 +1,16 @@
{-# OPTIONS -fglasgow-exts #-}
module API where
import Data.Dynamic
data TestIO = TestIO {
field :: IO String
}
deriving (Typeable, Show)
instance Show (IO String) where
show _ = "<<io action>>"
testio :: TestIO
testio = TestIO { field = return "default value" }

View File

@ -0,0 +1,21 @@
import Plugins
import API
conf = "../TestIO.conf"
stub = "../TestIO.stub"
apipath = "../api"
main = do
status <- makeWith conf stub ["-i"++apipath]
o <- case status of
MakeFailure e -> mapM_ putStrLn e >> error "failed"
MakeSuccess _ o -> return o
m_v <- load o [apipath] [] "resource"
v <- case m_v of
LoadSuccess _ v -> return v
_ -> error "load failed"
s <- field v
makeCleaner o
if null s then print False else print True

View File

@ -0,0 +1 @@
True

View File

@ -0,0 +1,3 @@
module Bar where
resource :: Int

View File

@ -0,0 +1,4 @@
module Foo where
resource :: Integer
resource = 0xBAD

View File

@ -0,0 +1,38 @@
import Plugins
import System.Directory
a = "Foo.hs" -- uesr code
b = "Bar.hs" -- trusted code. Result is "Bar.o"
main = do
status <- merge a b
f <- case status of
MergeFailure e -> error "merge failure"
MergeSuccess _ _ f -> return f
status <- merge a b
f' <- case status of
MergeFailure e -> error "merge failure"
MergeSuccess ReComp _ f -> error "unnec. merge"
MergeSuccess NotReq _ f -> return f
print ( f == f' )
status <- make f' []
o <- case status of
MakeFailure e -> error "make failed"
MakeSuccess _ o -> return o
m_v <- load o [] [] "resource"
v <- case m_v of
LoadSuccess _ v -> return v
_ -> error "load failed"
putStrLn $ show $ (v :: Int)
removeFile o
return ()
makeCleaner f

View File

@ -0,0 +1,4 @@
TEST=makewith/merge00
TOP=../../..
include ../../eval.mk

View File

@ -0,0 +1,2 @@
True
2989

View File

@ -0,0 +1,3 @@
module Bar where
resource :: Int

View File

@ -0,0 +1,4 @@
module Foo where
resource :: Integer
resource = 0xBAD

View File

@ -0,0 +1,37 @@
import Plugins
import System.Directory
a = "Foo.hs" -- uesr code
b = "Bar.hs" -- trusted code. Result is "Bar.o"
c = "Out.hs"
main = do
status <- mergeTo a b c
f <- case status of
MergeFailure e -> error "mergeto failure"
MergeSuccess _ _ f -> return f
print $ f == c
status <- mergeTo a b c
f' <- case status of
MergeFailure e -> error "mergeto failure"
MergeSuccess ReComp _ f -> error "unnec. mergeto"
MergeSuccess NotReq _ f -> return f -- good, not req
print $ f == f' && f == c
status <- make f' []
o <- case status of
MakeFailure e -> error "make failed"
MakeSuccess _ o -> return o
m_v <- load o [] [] "resource"
v <- case m_v of
LoadSuccess _ v -> return v
_ -> error "load failed"
putStrLn $ show $ (v :: Int)
makeCleaner c

View File

@ -0,0 +1,4 @@
TEST=makewith/mergeto0
TOP=../../..
include ../../eval.mk

View File

@ -0,0 +1,3 @@
True
True
2989

View File

@ -0,0 +1,3 @@
module Bar where
resource :: Int

View File

@ -0,0 +1,4 @@
module Foo where
resource :: Integer
resource = 1

View File

@ -0,0 +1,33 @@
import Plugins
import System.Directory
a = "Foo.hs" -- uesr code
b = "Bar.hs" -- trusted code. Result is "Bar.o"
main = do
status <- makeWith a b []
s <- case status of
MakeFailure e -> mapM_ putStrLn e >> error "failed"
MakeSuccess n s -> print n >> return s
status <- makeWith a b []
s' <- case status of
MakeFailure e -> mapM_ putStrLn e >> error "failed"
MakeSuccess n s -> print n >> return s
status <- makeWith a b []
s'' <- case status of
MakeFailure e -> mapM_ putStrLn e >> error "failed"
MakeSuccess n s -> print n >> return s
print $ (s == s') && (s' == s'')
m_v <- load s [] [] "resource"
v <- case m_v of
LoadSuccess _ v -> return v
_ -> error "load failed"
putStrLn $ show $ (v :: Int)
makeCleaner s''

View File

@ -0,0 +1,4 @@
TEST=makewith/module_name
TOP=../../..
include ../../eval.mk

View File

@ -0,0 +1,5 @@
ReComp
NotReq
NotReq
True
1

View File

@ -0,0 +1,4 @@
module Bar where
resource :: Int
resource = 2

View File

@ -0,0 +1,4 @@
module Foo where
resource :: Integer
resource = 1

View File

@ -0,0 +1,37 @@
import Plugins
import System.Directory
a = "Foo.hs" -- user code
b = "Bar.hs" -- more user code
z = "Stub.hs" -- and a stub
main = do
status <- makeWith a z []
s <- case status of
MakeFailure e -> mapM_ putStrLn e >> error "failed"
MakeSuccess n s -> print n >> return s
status <- makeWith b z []
s' <- case status of
MakeFailure e -> mapM_ putStrLn e >> error "failed"
MakeSuccess n s -> print n >> return s
-- shouldn't need to remerge (a,z)
status <- makeWith a z []
t <- case status of
MakeFailure e -> mapM_ putStrLn e >> error "failed"
MakeSuccess n s -> print n >> return s
-- shouldn't need to remerge (b,z)
status <- makeWith b z []
t' <- case status of
MakeFailure e -> mapM_ putStrLn e >> error "failed"
MakeSuccess n s -> print n >> return s
print $ s /= s' -- test we got unique modules
print $ t /= t' -- test we got unique modules
mapM_ makeCleaner [s,s']

View File

@ -0,0 +1,4 @@
TEST=makewith/multi_make
TOP=../../..
include ../../eval.mk

View File

@ -0,0 +1,4 @@
module Stub where
resource :: Int

View File

@ -0,0 +1,6 @@
ReComp
ReComp
NotReq
NotReq
True
True

View File

@ -0,0 +1,4 @@
TEST=makewith/should_fail_0
TOP=../../..
include ../../build.mk

View File

@ -0,0 +1,3 @@
module Plugin where
resource = 0xBAD :: Int

View File

@ -0,0 +1,6 @@
module Plugin ( resource ) where
import API
resource :: Interface
resource = plugin

View File

@ -0,0 +1,10 @@
module API where
data Interface = Interface {
function :: String
}
plugin :: Interface
plugin = Interface { function = "goodbye" }

View File

@ -0,0 +1,19 @@
import Plugins
import API
conf = "../Plugin.in"
stub = "../Plugin.stub"
main = do
status <- makeWith conf stub ["-i../api"]
case status of
MakeFailure e -> putStrLn "make failed"
MakeSuccess _ o -> do
m_v <- load o ["../api"] [] "resource"
v <- case m_v of
LoadSuccess _ v -> return v
_ -> error "load failed"
putStrLn $ (function v)
makeCleaner o

View File

@ -0,0 +1 @@
make failed

View File

@ -0,0 +1,5 @@
TEST=makewith/tiny
TOP=../../..
include ../../build.mk

View File

@ -0,0 +1,8 @@
resource = tiny {
field = "hello strange world"
}

View File

@ -0,0 +1,31 @@
module Tiny ( resource, resource_dyn ) where
import API
import Data.Dynamic
resource = tiny
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,21 @@
import Plugins
import API
import Data.Either
conf = "../Tiny.conf"
stub = "../Tiny.stub"
apipath = "../api"
main = do
status <- makeWith conf stub ["-i"++apipath]
o <- case status of
MakeFailure e -> mapM_ putStrLn e >> error "failed"
MakeSuccess _ o -> return o
m_v <- load o [apipath] [] "resource"
v <- case m_v of
LoadSuccess _ v -> return v
_ -> error "load failed"
putStrLn $ field v
makeCleaner o

View File

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

View File

@ -0,0 +1,5 @@
TEST=makewith/unsafeio
TOP=../../..
include ../../build.mk

View File

@ -0,0 +1,3 @@
hmm. on 6.3 we need to add 'mtl' to a package dependency, other
HSlang complains of a missing symbol. Is this a bug in the
package.conf for HSlang?

View File

@ -0,0 +1,17 @@
{-# GLOBALOPTIONS -package posix #-}
-- illustrates the use of static options in pragmas
import System.IO.Unsafe
import System.IO
import System.Process
resource = unsafe { field = date }
-- illustrates the use of the devil's work
date :: String
date = unsafePerformIO $ do
(_,outh,_,proc) <- runInteractiveProcess "date" [] Nothing Nothing
waitForProcess proc
s <- hGetContents outh
return s

View File

@ -0,0 +1,13 @@
module Unsafe ( resource, resource_dyn ) where
import API
import Data.Dynamic
resource = unsafe
--
-- special
--
resource_dyn :: Dynamic
resource_dyn = toDyn resource

View File

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

View File

@ -0,0 +1,20 @@
import Plugins
import API
import Data.Either
conf = "../Unsafe.conf"
stub = "../Unsafe.stub"
apipath = "../api"
main = do
status <- makeWith conf stub ["-i"++apipath]
o <- case status of
MakeFailure e -> mapM_ putStrLn e >> error "failed"
MakeSuccess _ o -> return o
m_v <- load o [apipath] [] "resource"
v <- case m_v of
LoadSuccess _ v -> return v
_ -> error "load failed"
let s = field v
makeCleaner o
if null s then print False else print True

View File

@ -0,0 +1,8 @@
this is an example of an application that uses the HSConf library to
dynamically load compiled conf files.
We use the .conf file in the parent directory, and communicate with
the plugin via the API in the api_package/ directory.
The plugin is a .o file
The api is a GHC package archive

View File

@ -0,0 +1 @@
True