-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Dynamic linking for Haskell and C objects -- -- Dynamic linking and runtime evaluation of Haskell, and C, including -- dependency chasing and package resolution. -- -- Described in the papers: * Plugging Haskell In * Dynamic -- Applications from the Ground Up * Dynamic Extension of Typed -- Functional Languages. @package plugins @version 1.5.3.0 -- | A Posix.popen compatibility mapping. -- -- If we use this, we should build -threaded module System.Plugins.Process exec :: String -> [String] -> IO ([String], [String]) popen :: FilePath -> [String] -> Maybe String -> IO (String, String, ProcessID) module System.Plugins.Parser -- | parse a file (as a string) as Haskell src parse :: FilePath -> String -> Either String HsModule -- | mergeModules : generate a full Haskell src file, give a .hs config -- file, and a stub to take default syntax and decls from. Mostly we just -- ensure they don't do anything bad, and that the names are correct for -- the module. -- -- Transformations: -- -- . Take src location pragmas from the conf file (1st file) . Use the -- template's (2nd argument) module name . Only use export list from -- template (2nd arg) . Merge top-level decls . need to force the type of -- the plugin to match the stub, overwriting any type they supply. mergeModules :: HsModule -> HsModule -> HsModule -- | pretty print haskell src -- -- doesn't handle operators with '#' at the end. i.e. unsafeCoerce# pretty :: HsModule -> String -- | Parsing option pragmas. -- -- This is not a type checker. If the user supplies bogus options, -- they'll get slightly mystical error messages. Also, we want to -- handle -package options, and other static flags. This is more -- than GHC. -- -- GHC user's guide : -- --
--   OPTIONS pragmas are only looked for at the top of your source
--   files, up to the first (non-literate,non-empty) line not
--   containing OPTIONS. Multiple OPTIONS pragmas are recognised.
--   
-- -- based on getOptionsFromSource(), in main/DriverUtil.hs parsePragmas :: String -> ([String], [String]) -- | A Haskell source module. data HsModule :: * HsModule :: SrcLoc -> Module -> Maybe [HsExportSpec] -> [HsImportDecl] -> [HsDecl] -> HsModule -- | replace Module name with String. replaceModName :: HsModule -> String -> HsModule instance SynEq HsImportDecl instance SynEq HsDecl module System.Plugins.LoadTypes data Key Object :: String -> Key Package :: String -> Key type Symbol = String type Type = String type Errors = [String] type PackageConf = FilePath data Module Module :: !FilePath -> !String -> !ObjType -> ModIface -> Key -> Module path :: Module -> !FilePath mname :: Module -> !String kind :: Module -> !ObjType iface :: Module -> ModIface key :: Module -> Key data ObjType Vanilla :: ObjType Shared :: ObjType instance Eq ObjType instance Eq Module instance Ord Module module System.Plugins.Consts -- | path to *build* dir, used by eval() for testing the examples top :: [Char] -- | what is ghc called? ghc :: [Char] -- | path to standard ghc libraries ghcLibraryPath :: [Char] -- | name of the system package.conf file sysPkgConf :: [Char] -- | This code is from runtime_loader: The extension used by system -- modules. sysPkgSuffix :: [Char] objSuf :: [Char] hiSuf :: [Char] hsSuf :: [Char] dllSuf :: [Char] -- | The prefix used by system modules. This, in conjunction with -- systemModuleExtension, will result in a module filename that -- looks like "HSconcurrent.o" sysPkgPrefix :: [Char] -- | '_' on a.out, and Darwin prefixUnderscore :: [Char] -- | Define tmpDir to where tmp files should be created on your platform tmpDir :: FilePath module System.Plugins.Env env :: (MVar (), IORef (FiniteMap key elt), IORef (FiniteMap key1 elt1), IORef PkgEnvs, IORef (Set [Char]), IORef (FiniteMap key2 elt2)) -- | apply f to the loaded objects Env, apply f to the -- package.conf FM locks up the MVar so you can't recursively call -- a function inside a with any -Env function. Nice and threadsafe withModEnv :: Env -> (ModEnv -> IO a) -> IO a withDepEnv :: Env -> (DepEnv -> IO a) -> IO a withPkgEnvs :: Env -> (PkgEnvs -> IO a) -> IO a withMerged :: Env -> (MergeEnv -> IO a) -> IO a modifyModEnv :: Env -> (ModEnv -> IO ModEnv) -> IO () modifyDepEnv :: Env -> (DepEnv -> IO DepEnv) -> IO () modifyPkgEnv :: Env -> (PkgEnvs -> IO PkgEnvs) -> IO () modifyMerged :: Env -> (MergeEnv -> IO MergeEnv) -> IO () -- | insert a loaded module name into the environment addModule :: String -> Module -> IO () -- | remove a module name from the environment. Returns True if the module -- was actually removed. rmModule :: String -> IO Bool -- | insert a list of module names all in one go addModules :: [(String, Module)] -> IO () -- | is a module/package already loaded? isLoaded :: String -> IO Bool loaded :: String -> IO Bool -- | Set the dependencies of a Module. addModuleDeps :: Module -> [Module] -> IO () -- | Get module dependencies. Nothing if none have been recored. getModuleDeps :: Module -> IO [Module] -- | Unrecord a module from the environment. rmModuleDeps :: Module -> IO () isMerged :: FilePath -> FilePath -> IO Bool lookupMerged :: FilePath -> FilePath -> IO (Maybe FilePath) addMerge :: FilePath -> FilePath -> FilePath -> IO () -- | Insert a single package.conf (containing multiple configs) means: -- create a new FM. insert packages into FM. add FM to end of list of FM -- stored in the environment. addPkgConf :: FilePath -> IO () -- | add a new FM for the package.conf to the list of existing ones; if a -- package occurs multiple times, pick the one with the higher version -- number as the default (e.g., important for base in GHC 6.12) union :: PkgEnvs -> [PackageConfig] -> PkgEnvs addStaticPkg :: PackageName -> IO () isStaticPkg :: PackageName -> IO Bool -- | generate a PkgEnv from the system package.conf The path to the default -- package.conf was determined by configure This imposes a -- constraint that you must build your plugins with the same ghc you use -- to build hs-plugins. This is reasonable, we feel. grabDefaultPkgConf :: IO PkgEnvs readPackageConf :: FilePath -> IO [PackageConfig] lookupPkg :: PackageName -> IO ([FilePath], [FilePath]) module System.Plugins.Utils type Arg = String -- | writeFile for Handles hWrite :: Handle -> String -> IO () -- | Get a new temp file, unique from those in /tmp, and from those modules -- already loaded. Very nice for merge/eval uses. -- -- Will run for a long time if we can't create a temp file, luckily -- mkstemps gives us a pretty big search space mkUnique :: IO FilePath hMkUnique :: IO (FilePath, Handle) mkUniqueIn :: FilePath -> IO FilePath hMkUniqueIn :: FilePath -> IO (FilePath, Handle) findFile :: [String] -> FilePath -> IO (Maybe FilePath) -- | mkstemps. -- -- We use the Haskell version now... it is faster than calling into -- mkstemps(3). -- -- create a new temp file, returning name and handle. bit like the mktemp -- shell utility mkTemp :: IO (String, Handle) mkTempIn :: String -> IO (String, Handle) -- | return the object file, given the .conf file i.e. -- homedonsfoo.rc -> homedonsfoo.o -- -- we depend on the suffix we are given having a lead . replaceSuffix :: FilePath -> String -> FilePath outFilePath :: FilePath -> [Arg] -> (FilePath, FilePath) dropSuffix :: FilePath -> FilePath -- | work out the mod name from a filepath mkModid :: String -> String -- | Changes the extension of a file path. changeFileExt :: FilePath -> String -> FilePath -- | The joinFileExt function is the opposite of -- splitFileExt. It joins a file name and an extension to form a -- complete file path. -- -- The general rule is: -- --
--   filename `joinFileExt` ext == path
--     where
--       (filename,ext) = splitFileExt path
--   
joinFileExt :: String -> String -> FilePath -- | Split the path into file name and extension. If the file doesn't have -- extension, the function will return empty string. The extension -- doesn't include a leading period. -- -- Examples: -- --
--   splitFileExt "foo.ext" == ("foo", "ext")
--   splitFileExt "foo"     == ("foo", "")
--   splitFileExt "."       == (".",   "")
--   splitFileExt ".."      == ("..",  "")
--   splitFileExt "foo.bar."== ("foo.bar.", "")
--   
splitFileExt :: FilePath -> (String, String) isSublistOf :: Eq a => [a] -> [a] -> Bool -- | dirname : return the directory portion of a file path if null, return -- . dirname :: FilePath -> FilePath -- | basename : return the filename portion of a path basename :: FilePath -> FilePath -- | /, . : join two path components () :: FilePath -> FilePath -> FilePath -- | /, . : join two path components (<.>) :: FilePath -> FilePath -> FilePath -- | /, . : join two path components (<+>) :: FilePath -> FilePath -> FilePath -- | /, . : join two path components (<>) :: FilePath -> FilePath -> FilePath -- | is file1 newer than file2? -- -- needs some fixing to work with 6.0.x series. (is this true?) -- -- fileExist still seems to throw exceptions on some platforms: ia64 in -- particular. -- -- invarient : we already assume the first file, a, exists newer :: FilePath -> FilePath -> IO Bool encode :: String -> EncodedString decode :: EncodedString -> String -- | return the Z-Encoding of the string. -- -- Stolen from GHC. Use -package ghc as soon as possible type EncodedString = String -- | useful panic :: String -> IO a -- | An interface to a Haskell compiler, providing the facilities of a -- compilation manager. module System.Plugins.Make -- | The MakeStatus type represents success or failure of -- compilation. Compilation can fail for the usual reasons: syntax -- errors, type errors and the like. The MakeFailure constructor -- returns any error messages produced by the compiler. -- MakeSuccess returns a MakeCode value, and the path -- to the object file produced. data MakeStatus -- | compilation was successful MakeSuccess :: MakeCode -> FilePath -> MakeStatus -- | compilation failed MakeFailure :: Errors -> MakeStatus -- | The MakeCode type is used when compilation is successful, to -- distinguish two cases: * The source file needed recompiling, and this -- was done * The source file was already up to date, recompilation was -- skipped data MakeCode -- | recompilation was performed ReComp :: MakeCode -- | recompilation was not required NotReq :: MakeCode -- | One-shot unconditional compilation of a single Haskell module. -- make behaves like 'ghc -c'. Extra arguments to ghc may -- be passed in the args parameter, they will be appended to the -- argument list. make always recompiles its target, whether or -- not it is out of date. -- -- A side-effect of calling make is to have GHC produce a -- .hi file containing a list of package and objects that the -- source depends on. Subsequent calls to load will use this -- interface file to load module and library dependencies prior to -- loading the object itself. make :: FilePath -> [Arg] -> IO MakeStatus -- | makeAll recursively compiles any dependencies it can find using -- GHC's --make flag. Dependencies will be recompiled only if -- they are visible to ghc -- this may require passing appropriate -- include path flags in the args parameter. makeAll -- takes the top-level file as the first argument. makeAll :: FilePath -> [Arg] -> IO MakeStatus -- | This is a variety of make that first calls merge to -- combine the plugin source with a syntax stub. The result is then -- compiled. This is provided for EDSL authors who wish to add extra -- syntax to a user's source. It is important to note that the module and -- types from the second file argument are used to override any of those -- that appear in the first argument. For example, consider the following -- source files: -- --
--   module A where
--   a :: Integer
--   a = 1
--   
-- -- and -- --
--   module B where
--   a :: Int
--   
-- -- Calling makeWith A B [] will merge the module -- name and types from module B into module A, generating a third file: -- --
--   {-# LINE 1 "A.hs" #-}
--   module MxYz123 where
--   {-# LINE 3 "B.hs" #-}
--   a :: Int
--   {-# LINE 4 "A.hs" #-}
--   a = 1
--   
makeWith :: FilePath -> FilePath -> [Arg] -> IO MakeStatus -- | hasChanged returns True if the module or any of its -- dependencies have older object files than source files. Defaults to -- True if some files couldn't be located. hasChanged :: Module -> IO Bool hasChanged' :: [String] -> Module -> IO Bool -- | recompileAll is like makeAll, but rather than relying on -- ghc --make, we explicitly check a module's dependencies using -- our internal map of module dependencies. Performance is thus better, -- and the result is more accurate. recompileAll :: Module -> [Arg] -> IO MakeStatus recompileAll' :: [String] -> Module -> [Arg] -> IO MakeStatus -- | An equivalent status for the preprocessor phase data MergeStatus -- | the merge was successful MergeSuccess :: MergeCode -> Args -> FilePath -> MergeStatus -- | failure, and any errors returned MergeFailure :: Errors -> MergeStatus -- | Merging may be avoided if the source files are older than an existing -- merged result. The MergeCode type indicates whether merging -- was performed, or whether it was unneccessary. type MergeCode = MakeCode -- | A list of String arguments type Args = [Arg] -- | Convience synonym type Errors = [String] -- | Merge to source files into a temporary file. If we've tried to merge -- these two stub files before, then reuse the module name (helps -- recompilation checking) -- -- The merging operation is extremely useful for providing extra default -- syntax. An EDSL user then need not worry about declaring module names, -- or having required imports. In this way, the stub file can also be -- used to provide syntax declarations that would be inconvenient to -- require of the plugin author. -- -- merge will include any import and export declarations written -- in the stub, as well as any module name, so that plugin author's need -- not worry about this compulsory syntax. Additionally, if a plugin -- requires some non-standard library, which must be provided as a -- -package flag to GHC, they may specify this using the -- non-standard GLOBALOPTIONS pragma. Options specified in the -- source this way will be added to the command line. This is useful for -- users who wish to use GHC flags that cannot be specified using the -- conventional OPTIONS pragma. The merging operation uses the -- parser hs-plugins was configured with, either Haskell or the -- HSX parser, to parse Haskell source files. merge :: FilePath -> FilePath -> IO MergeStatus -- | mergeTo behaves like merge, but we can specify the file -- in which to place output. mergeTo :: FilePath -> FilePath -> FilePath -> IO MergeStatus -- | mergeToDir behaves like merge, but lets you specify a -- target directory. mergeToDir :: FilePath -> FilePath -> FilePath -> IO MergeStatus -- | makeClean : assuming we some element of [f.hs,f.hi,f.o], remove the -- .hi and .o components. Silently ignore any missing components. /Does -- not remove .hs files/. To do that use makeCleaner. This would -- be useful for merged files, for example. makeClean :: FilePath -> IO () makeCleaner :: FilePath -> IO () -- | Lower-level than make. Compile a .hs file to a .o file If the -- plugin needs to import an api (which should be almost everyone) then -- the ghc flags to find the api need to be provided as arguments build :: FilePath -> FilePath -> [String] -> IO [String] instance Eq MakeCode instance Show MakeCode instance Eq MergeStatus instance Show MergeStatus instance Eq MakeStatus instance Show MakeStatus -- | An interface to the GHC runtime's dynamic linker, providing runtime -- loading and linking of Haskell object files, commonly known as -- plugins. module System.Plugins.Load -- | The LoadStatus type encodes the return status of functions -- that perform dynamic loading in a type isomorphic to Either. -- Failure returns a list of error strings, success returns a reference -- to a loaded module, and the Haskell value corresponding to the symbol -- that was indexed. data LoadStatus a LoadSuccess :: Module -> a -> LoadStatus a LoadFailure :: Errors -> LoadStatus a -- | load is the basic interface to the dynamic loader. A call to -- load imports a single object file into the caller's address -- space, returning the value associated with the symbol requested. -- Libraries and modules that the requested module depends upon are -- loaded and linked in turn. -- -- The first argument is the path to the object file to load, the second -- argument is a list of directories to search for dependent modules. The -- third argument is a list of paths to user-defined, but unregistered, -- package.conf files. The Symbol argument is the symbol -- name of the value you with to retrieve. -- -- The value returned must be given an explicit type signature, or -- provided with appropriate type constraints such that Haskell compiler -- can determine the expected type returned by load, as the return -- type is notionally polymorphic. -- -- Example: -- --
--   do mv <- load "Plugin.o" ["api"] [] "resource"
--      case mv of
--          LoadFailure msg -> print msg
--          LoadSuccess _ v -> return v
--   
load :: FilePath -> [FilePath] -> [PackageConf] -> Symbol -> IO (LoadStatus a) -- | Like load, but doesn't want a package.conf arg (they are rarely used) load_ :: FilePath -> [FilePath] -> Symbol -> IO (LoadStatus a) -- | A work-around for Dynamics. The keys used to compare two TypeReps are -- somehow not equal for the same type in hs-plugin's loaded objects. -- Solution: implement our own dynamics... -- -- The problem with dynload is that it requires the plugin to export a -- value that is a Dynamic (in our case a (TypeRep,a) pair). If this is -- not the case, we core dump. Use pdynload if you don't trust the user -- to supply you with a Dynamic dynload :: Typeable a => FilePath -> [FilePath] -> [PackageConf] -> Symbol -> IO (LoadStatus a) -- | The super-replacement for dynload -- -- Use GHC at runtime so we get staged type inference, providing full -- power dynamics, *on module interfaces only*. This is quite suitable -- for plugins, of coures :) -- -- TODO where does the .hc file go in the call to build() ? pdynload :: FilePath -> [FilePath] -> [PackageConf] -> Type -> Symbol -> IO (LoadStatus a) -- | Like pdynload, but you can specify extra arguments to the typechecker. pdynload_ :: FilePath -> [FilePath] -> [PackageConf] -> [Arg] -> Type -> Symbol -> IO (LoadStatus a) -- | unload a module (not its dependencies) we have the dependencies, so -- cascaded unloading is possible -- -- once you unload it, you can't load it again, you have to -- reload it. Cause we don't unload all the dependencies unload :: Module -> IO () -- | unload a module and its dependencies we have the dependencies, so -- cascaded unloading is possible unloadAll :: Module -> IO () -- | this will be nice for panTHeon, needs thinking about the interface -- reload a single object file. don't care about depends, assume they are -- loaded. (should use state to store all this) -- -- assumes you've already done a load -- -- should factor the code reload :: Module -> Symbol -> IO (LoadStatus a) data Module Module :: !FilePath -> !String -> !ObjType -> ModIface -> Key -> Module path :: Module -> !FilePath mname :: Module -> !String kind :: Module -> !ObjType iface :: Module -> ModIface key :: Module -> Key initLinker :: IO () -- | load a single object. no dependencies. You should know what you're -- doing. loadModule :: FilePath -> IO Module -- | Call the initLinker function first, before calling any of the other -- functions in this module - otherwise you'll get unresolved symbols. -- -- Load a function from a module (which must be loaded and resolved -- first). loadFunction :: Module -> String -> IO (Maybe a) loadFunction_ :: String -> String -> IO (Maybe a) -- | Loads a function from a package module, given the package name, module -- name and symbol name. loadPackageFunction :: String -> String -> String -> IO (Maybe a) -- | Load a -package that we might need, implicitly loading the cbits too -- The argument is the name of package (e.g. "concurrent") -- -- How to find a package is determined by the package.conf info we store -- in the environment. It is just a matter of looking it up. -- -- Not printing names of dependent pkgs loadPackage :: String -> IO () -- | Unload a -package, that has already been loaded. Unload the cbits too. -- The argument is the name of the package. -- -- May need to check if it exists. -- -- Note that we currently need to unload everything. grumble grumble. -- -- We need to add the version number to the package name with 6.4 and -- over. yi-0.1 for example. This is a bug really. unloadPackage :: String -> IO () -- | load a package using the given package.conf to help TODO should report -- if it doesn't actually load the package, instead of mapM_ doing -- nothing like above. loadPackageWith :: String -> [PackageConf] -> IO () -- | from ghci/ObjLinker.c -- -- Load a .so type object file. loadShared :: FilePath -> IO Module -- | Resolve (link) the modules loaded by the loadObject function. resolveObjs :: IO a -> IO () -- | Load a generic .o file, good for loading C objects. You should know -- what you're doing.. Returns a fairly meaningless iface value. loadRawObject :: FilePath -> IO Module type Symbol = String -- | Nice interface to .hi parser getImports :: String -> IO [String] module System.Plugins module System.Eval.Utils type Import = String symbol :: Symbol escape :: [Char] -> [Char] getPaths :: IO ([String], [String]) mkUniqueWith :: (String -> String -> [Import] -> String) -> String -> [Import] -> IO FilePath cleanup :: String -> String -> IO () -- | Evaluate Haskell at runtime, using runtime compilation and dynamic -- loading. Arguments are compiled to native code, and dynamically -- loaded, returning a Haskell value representing the compiled argument. -- The underlying implementation treats String arguments as the -- source for plugins to be compiled at runtime. module System.Eval.Haskell -- | eval provides a typesafe (to a limit) form of runtime -- evaluation for Haskell -- a limited form of runtime -- metaprogramming. The String argument to eval is a -- Haskell source fragment to evaluate at rutime. imps are a -- list of module names to use in the context of the compiled value. -- -- The value returned by eval is constrained to be Typeable -- -- meaning we can perform a limited runtime typecheck, using -- the dynload function. One consequence of this is that the code -- must evaluate to a monomorphic value (which will be wrapped in a -- Dynamic). -- -- If the evaluated code typechecks under the Typeable -- constraints, 'Just v' is returned. Nothing indicates -- typechecking failed. Typechecking may fail at two places: when -- compiling the argument, or when typechecking the splice point. -- eval resembles a metaprogramming run operator for -- closed source fragments. -- -- To evaluate polymorphic values you need to wrap them in data -- structures using rank-N types. -- -- Examples: -- --
--   do i <- eval "1 + 6 :: Int" [] :: IO (Maybe Int)
--      when (isJust i) $ putStrLn (show (fromJust i))
--   
eval :: Typeable a => String -> [Import] -> IO (Maybe a) -- | eval_ is a variety of eval with all the internal hooks -- available. You are able to set any extra arguments to the compiler -- (for example, optimisation flags) or dynamic loader, as well as having -- any errors returned in an Either type. eval_ :: Typeable a => String -> [Import] -> [String] -> [FilePath] -> [FilePath] -> IO (Either [String] (Maybe a)) -- | Sometimes when constructing string fragments to evaluate, the -- programmer is able to provide some other constraint on the evaluated -- string, such that the evaluated expression will be typesafe, without -- requiring a Typeable constraint. In such cases, the monomorphic -- restriction is annoying. unsafeEval removes any splice-point -- typecheck, with an accompanying obligation on the programmer to ensure -- that the fragment evaluated will be typesafe at the point it is -- spliced. -- -- An example of how to do this would be to wrap the fragment in a call -- to show. The augmented fragment would then be checked when -- compiled to return a String, and the programmer can rely on -- this, without requiring a splice-point typecheck, and thus no -- Typeable restriction. -- -- Note that if you get the proof wrong, your program will likely -- segfault. -- -- Example: -- --
--   do s <- unsafeEval "map toUpper \"haskell\"" ["Data.Char"]
--      when (isJust s) $ putStrLn (fromJust s)
--   
unsafeEval :: String -> [Import] -> IO (Maybe a) -- | unsafeEval_ is a form of unsafeEval with all internal -- hooks exposed. This is useful for application wishing to return error -- messages to users, to specify particular libraries to link against and -- so on. unsafeEval_ :: String -> [Import] -> [String] -> [FilePath] -> [FilePath] -> IO (Either [String] a) -- | Return a compiled value's type, by using Dynamic to get a -- representation of the inferred type. typeOf :: String -> [Import] -> IO String -- | mkHsValues is a helper function for converting Maps of -- names and values into Haskell code. It relies on the assumption of -- names and values into Haskell code. It relies on the assumption that -- the passed values' Show instances produce valid Haskell literals (this -- is true for all Prelude types). mkHsValues :: Show a => Map String a -> String module System.Eval