-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Runtime Haskell interpreter (GHC API wrapper) -- -- This library defines an Interpreter monad. It allows to load -- Haskell modules, browse them, type-check and evaluate strings with -- Haskell expressions and even coerce them into values. The library is -- thread-safe and type-safe (even the coercion of expressions to -- values). It is, esentially, a huge subset of the GHC API wrapped in a -- simpler API. Works with GHC 6.10.x and 6.8.x (this version was not -- tested with GHC 6.6). @package hint @version 0.3.3.5 module Language.Haskell.Interpreter.Extension -- | This represents language extensions beyond Haskell 98 that are -- supported by GHC (it was taken from Cabal's -- Language.Haskell.Extension) data Extension OverlappingInstances :: Extension UndecidableInstances :: Extension IncoherentInstances :: Extension DoRec :: Extension RecursiveDo :: Extension ParallelListComp :: Extension MultiParamTypeClasses :: Extension NoMonomorphismRestriction :: Extension FunctionalDependencies :: Extension Rank2Types :: Extension RankNTypes :: Extension PolymorphicComponents :: Extension ExistentialQuantification :: Extension ScopedTypeVariables :: Extension ImplicitParams :: Extension FlexibleContexts :: Extension FlexibleInstances :: Extension EmptyDataDecls :: Extension CPP :: Extension KindSignatures :: Extension BangPatterns :: Extension TypeSynonymInstances :: Extension TemplateHaskell :: Extension ForeignFunctionInterface :: Extension Arrows :: Extension Generics :: Extension NoImplicitPrelude :: Extension NamedFieldPuns :: Extension PatternGuards :: Extension GeneralizedNewtypeDeriving :: Extension ExtensibleRecords :: Extension RestrictedTypeSynonyms :: Extension HereDocuments :: Extension MagicHash :: Extension TypeFamilies :: Extension StandaloneDeriving :: Extension UnicodeSyntax :: Extension PatternSignatures :: Extension UnliftedFFITypes :: Extension LiberalTypeSynonyms :: Extension TypeOperators :: Extension RecordWildCards :: Extension RecordPuns :: Extension DisambiguateRecordFields :: Extension OverloadedStrings :: Extension GADTs :: Extension NoMonoPatBinds :: Extension RelaxedPolyRec :: Extension ExtendedDefaultRules :: Extension UnboxedTuples :: Extension DeriveDataTypeable :: Extension ConstrainedClassMethods :: Extension PackageImports :: Extension ImpredicativeTypes :: Extension NewQualifiedOperators :: Extension PostfixOperators :: Extension QuasiQuotes :: Extension TransformListComp :: Extension ViewPatterns :: Extension XmlSyntax :: Extension RegularPatterns :: Extension TupleSections :: Extension GHCForeignImportPrim :: Extension NPlusKPatterns :: Extension DoAndIfThenElse :: Extension RebindableSyntax :: Extension ExplicitForAll :: Extension DatatypeContexts :: Extension MonoLocalBinds :: Extension DeriveFunctor :: Extension DeriveTraversable :: Extension DeriveFoldable :: Extension UnknownExtension :: String -> Extension knownExtensions :: [Extension] -- | List of the extensions known by the interpreter. availableExtensions :: [Extension] asExtension :: String -> Extension module Language.Haskell.Interpreter.Unsafe -- | Set a GHC option for the current session, eg. unsafeSetGhcOption -- "-XNoMonomorphismRestriction". -- -- Warning: Some options may interact badly with the Interpreter. unsafeSetGhcOption :: MonadInterpreter m => String -> m () -- | Executes the interpreter, setting the args as though they were -- command-line args. In particular, this means args that have no effect -- with :set in ghci might function properly from this context. -- -- Warning: Some options may interact badly with the Interpreter. unsafeRunInterpreterWithArgs :: (MonadCatchIO m, Functor m) => [String] -> InterpreterT m a -> m (Either InterpreterError a) -- | DEPRECATED: use Language.Haskell.Interpreter.Unsafe instead. -- | Deprecated: Import Language.Haskell.Interpreter.Unsafe instead. module Language.Haskell.Interpreter.GHC.Unsafe -- | A Haskell interpreter built on top of the GHC API module Language.Haskell.Interpreter class (MonadCatchIO m, MonadError InterpreterError m) => MonadInterpreter m fromSession :: MonadInterpreter m => FromSession m a modifySessionRef :: MonadInterpreter m => ModifySessionRef m a runGhc :: MonadInterpreter m => RunGhc m a data InterpreterT m a type Interpreter = InterpreterT IO -- | Executes the interpreter. Returns Left InterpreterError in -- case of error. -- -- NB. The underlying ghc will overwrite certain signal handlers (SIGINT, -- SIGHUP, SIGTERM, SIGQUIT on Posix systems, Ctrl-C handler on Windows). -- In future versions of hint, this might be controlled by the user. runInterpreter :: (MonadCatchIO m, Functor m) => InterpreterT m a -> m (Either InterpreterError a) -- | Available options are: -- -- data Option m a data OptionVal m (:=) :: (Option m a) -> a -> OptionVal m -- | Retrieves the value of an option. get :: MonadInterpreter m => Option m a -> m a -- | Use this function to set or modify the value of any option. It is -- invoked like this: -- --
--   set [opt1 := val1, opt2 := val2,... optk := valk]
--   
set :: MonadInterpreter m => [OptionVal m] -> m () -- | Language extensions in use by the interpreter. -- -- Default is: [] (i.e. none, pure Haskell 98) languageExtensions :: MonadInterpreter m => Option m [Extension] -- | List of the extensions known by the interpreter. availableExtensions :: [Extension] -- | List of extensions turned on when the -fglasgow-exts flag is -- used glasgowExtensions :: [Extension] -- | This represents language extensions beyond Haskell 98 that are -- supported by GHC (it was taken from Cabal's -- Language.Haskell.Extension) data Extension OverlappingInstances :: Extension UndecidableInstances :: Extension IncoherentInstances :: Extension DoRec :: Extension RecursiveDo :: Extension ParallelListComp :: Extension MultiParamTypeClasses :: Extension NoMonomorphismRestriction :: Extension FunctionalDependencies :: Extension Rank2Types :: Extension RankNTypes :: Extension PolymorphicComponents :: Extension ExistentialQuantification :: Extension ScopedTypeVariables :: Extension ImplicitParams :: Extension FlexibleContexts :: Extension FlexibleInstances :: Extension EmptyDataDecls :: Extension CPP :: Extension KindSignatures :: Extension BangPatterns :: Extension TypeSynonymInstances :: Extension TemplateHaskell :: Extension ForeignFunctionInterface :: Extension Arrows :: Extension Generics :: Extension NoImplicitPrelude :: Extension NamedFieldPuns :: Extension PatternGuards :: Extension GeneralizedNewtypeDeriving :: Extension ExtensibleRecords :: Extension RestrictedTypeSynonyms :: Extension HereDocuments :: Extension MagicHash :: Extension TypeFamilies :: Extension StandaloneDeriving :: Extension UnicodeSyntax :: Extension PatternSignatures :: Extension UnliftedFFITypes :: Extension LiberalTypeSynonyms :: Extension TypeOperators :: Extension RecordWildCards :: Extension RecordPuns :: Extension DisambiguateRecordFields :: Extension OverloadedStrings :: Extension GADTs :: Extension NoMonoPatBinds :: Extension RelaxedPolyRec :: Extension ExtendedDefaultRules :: Extension UnboxedTuples :: Extension DeriveDataTypeable :: Extension ConstrainedClassMethods :: Extension PackageImports :: Extension ImpredicativeTypes :: Extension NewQualifiedOperators :: Extension PostfixOperators :: Extension QuasiQuotes :: Extension TransformListComp :: Extension ViewPatterns :: Extension XmlSyntax :: Extension RegularPatterns :: Extension TupleSections :: Extension GHCForeignImportPrim :: Extension NPlusKPatterns :: Extension DoAndIfThenElse :: Extension RebindableSyntax :: Extension ExplicitForAll :: Extension DatatypeContexts :: Extension MonoLocalBinds :: Extension DeriveFunctor :: Extension DeriveTraversable :: Extension DeriveFoldable :: Extension UnknownExtension :: String -> Extension -- | When set to True, every module in every available package is -- implicitly imported qualified. This is very convenient for interactive -- evaluation, but can be a problem in sandboxed environments (e.g. -- unsafePerformIO is in scope). -- -- Default value is True. -- -- Observe that due to limitations in the GHC-API, when set to -- False, the private symbols in interpreted modules will not be -- in scope. installedModulesInScope :: MonadInterpreter m => Option m Bool -- | The search path for source files. Observe that every time it is set, -- it overrides the previous search path. The default is ["."]. -- -- Keep in mind that by a limitation in ghc, "." is always in -- scope. searchPath :: MonadInterpreter m => Option m [FilePath] setUseLanguageExtensions :: MonadInterpreter m => Bool -> m () setInstalledModsAreInScopeQualified :: MonadInterpreter m => Bool -> m () -- | Module names are _not_ filepaths. type ModuleName = String -- | Returns True if the module was interpreted. isModuleInterpreted :: MonadInterpreter m => ModuleName -> m Bool -- | Tries to load all the requested modules from their source file. -- Modules my be indicated by their ModuleName (e.g. "My.Module") or by -- the full path to its source file. -- -- The interpreter is reset both before loading the modules and in -- the event of an error. loadModules :: MonadInterpreter m => [String] -> m () -- | Returns the list of modules loaded with loadModules. getLoadedModules :: MonadInterpreter m => m [ModuleName] -- | Sets the modules whose context is used during evaluation. All bindings -- of these modules are in scope, not only those exported. -- -- Modules must be interpreted to use this function. setTopLevelModules :: MonadInterpreter m => [ModuleName] -> m () -- | Sets the modules whose exports must be in context. -- -- Warning: setImports and setImportsQ are mutually -- exclusive. If you have a list of modules to be used qualified and -- another list unqualified, then you need to do something like -- --
--   setImportsQ ((zip unqualified $ repeat Nothing) ++ qualifieds)
--   
setImports :: MonadInterpreter m => [ModuleName] -> m () -- | Sets the modules whose exports must be in context; some of them may be -- qualified. E.g.: -- -- setImports [(Prelude, Nothing), (Data.Map, Just -- M)]. -- -- Here, map will refer to Prelude.map and M.map to -- Data.Map.map. setImportsQ :: MonadInterpreter m => [(ModuleName, Maybe String)] -> m () -- | All imported modules are cleared from the context, and loaded modules -- are unloaded. It is similar to a :load in GHCi, but observe -- that not even the Prelude will be in context after a reset. reset :: MonadInterpreter m => m () data ModuleElem Fun :: Id -> ModuleElem Class :: Id -> [Id] -> ModuleElem Data :: Id -> [Id] -> ModuleElem -- | An Id for a class, a type constructor, a data constructor, a binding, -- etc type Id = String name :: ModuleElem -> Id children :: ModuleElem -> [Id] -- | Gets an abstract representation of all the entities exported by the -- module. It is similar to the :browse command in GHCi. getModuleExports :: MonadInterpreter m => ModuleName -> m [ModuleElem] -- | Get the annotations associated with a particular module. -- -- For example, given: -- --
--   RBRACE-# ANN module (1 :: Int) #-LBRACE
--   module SomeModule(g, h) where
--   ...
--   
-- -- Then after using loadModule to load SomeModule into scope: -- --
--   x <- getModuleAnnotations (as :: Int) SomeModule
--   liftIO $ print x
--   -- result is [1]
--   
getModuleAnnotations :: (Data a, MonadInterpreter m) => a -> String -> m [a] -- | Get the annotations associated with a particular function -- -- For example, given: -- --
--      module SomeModule(g, h) where
--   
--   LBRACE-# ANN g (Just 1 :: Maybe Int) #-RBRACE
--      g = f [f]
--   
--   LBRACE-# ANN h (Just 2 :: Maybe Int) #-RBRACE
--      h = f
--   
-- -- Then after using loadModule to bring SomeModule into scope: -- --
--   x <- liftM concat $ mapM (getValAnnotations (as :: Maybe Int)) ["g","h"]
--   liftIO $ print x
--   -- result is [Just 2, Just 1]
--   
-- -- This can also work on data constructors and types with annotations. getValAnnotations :: (Data a, MonadInterpreter m) => a -> String -> m [a] -- | Returns a string representation of the type of the expression. typeOf :: MonadInterpreter m => String -> m String -- | Tests if the expression type checks. typeChecks :: MonadInterpreter m => String -> m Bool -- | Returns a string representation of the kind of the type expression. kindOf :: MonadInterpreter m => String -> m String -- | Evaluates an expression, given a witness for its monomorphic type. interpret :: (MonadInterpreter m, Typeable a) => String -> a -> m a -- | Convenience functions to be used with interpret to provide -- witnesses. Example: -- -- as :: Typeable a => a -- | Convenience functions to be used with interpret to provide -- witnesses. Example: -- -- infer :: Typeable a => a -- | eval expr will evaluate show expr. It will succeed -- only if expr has type t and there is a Show instance -- for t. eval :: MonadInterpreter m => String -> m String data InterpreterError UnknownError :: String -> InterpreterError WontCompile :: [GhcError] -> InterpreterError NotAllowed :: String -> InterpreterError -- | GhcExceptions from the underlying GHC API are caught and rethrown as -- this. GhcException :: String -> InterpreterError newtype GhcError GhcError :: String -> GhcError errMsg :: GhcError -> String -- | The installed version of ghc is not thread-safe. This exception is -- thrown whenever you try to execute runInterpreter while -- another instance is already running. data MultipleInstancesNotAllowed MultipleInstancesNotAllowed :: MultipleInstancesNotAllowed -- | Version of the underlying ghc api. Values are: -- -- ghcVersion :: Int -- | Conceptually, parens s = "(" ++ s ++ ")", where s is any -- valid haskell expression. In practice, it is harder than this. Observe -- that if s ends with a trailing comment, then parens -- s would be a malformed expression. The straightforward solution -- for this is to put the closing parenthesis in a different line. -- However, now we are messing with the layout rules and we don't know -- where s is going to be used! Solution: parens s = "(let -- {foo =n" ++ s ++ "\n ;} in foo)" where foo does not -- occur in s parens :: String -> String -- | DEPRECATED: use Language.Haskell.Interpreter.Unsafe instead. -- | Deprecated: Import Language.Haskell.Interpreter instead. module Language.Haskell.Interpreter.GHC