plugins-1.5.1.1: Dynamic linking for Haskell and C objects

System.Eval.Haskell

Description

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.

Synopsis

Documentation

eval :: Typeable a => String -> [Import] -> IO (Maybe a)Source

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_Source

Arguments

:: Typeable a 
=> String

code to compile

-> [Import]

any imports

-> [String]

extra make flags

-> [FilePath]

(package.confs) for load

-> [FilePath]

include paths load is to search in

-> IO (Either [String] (Maybe a))

either errors, or maybe a well typed value

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.

unsafeEval :: String -> [Import] -> IO (Maybe a)Source

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_Source

Arguments

:: String

code to compile

-> [Import]

any imports

-> [String]

make flags

-> [FilePath]

(package.confs) for load

-> [FilePath]

include paths load is to search in

-> IO (Either [String] 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.

typeOf :: String -> [Import] -> IO StringSource

Return a compiled value's type, by using Dynamic to get a representation of the inferred type.

mkHsValues :: Show a => Map String a -> StringSource

mkHsValues is a helper function for converting Data.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).