-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | A Haskell interpreter built on top of the GHC API -- -- 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, essentially, a huge subset of the GHC API wrapped in a -- simpler API. @package hint @version 0.9.0.7 -- | In this module we intend to export some internal functions. -- -- Important note: the authors of this library imply no assurance -- whatsoever of the stability or functionality of the API exposed here, -- and compatibility may break even by minor version changes. Rely on -- these at your own risk. -- -- The reason for showing them here is to aid discoverability of already -- written code and prevent having to reinvent the wheel from scratch if -- said wheel is already invented. -- -- In case you find something here especially useful, please submit an -- issue or a pull request at https://github.com/haskell-hint/hint -- so we can discuss making it part of the official public API. -- -- Some further context can be found here: -- https://github.com/haskell-hint/hint/pull/48#issuecomment-358722638 module Hint.Internal onCompilationError :: MonadInterpreter m => ([GhcError] -> m a) -> InterpreterError -> m a module Language.Haskell.Interpreter class (MonadIO m, MonadMask 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. In hint-0.7.0 and earlier, the underlying ghc was accidentally -- overwriting certain signal handlers (SIGINT, SIGHUP, SIGTERM, SIGQUIT -- on Posix systems, Ctrl-C handler on Windows). runInterpreter :: (MonadIO m, MonadMask 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] -- | 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 MonomorphismRestriction :: Extension FunctionalDependencies :: Extension Rank2Types :: Extension RankNTypes :: Extension PolymorphicComponents :: Extension ExistentialQuantification :: Extension ScopedTypeVariables :: Extension PatternSignatures :: 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 ImplicitPrelude :: Extension NamedFieldPuns :: Extension PatternGuards :: Extension GeneralizedNewtypeDeriving :: Extension ExtensibleRecords :: Extension RestrictedTypeSynonyms :: Extension HereDocuments :: Extension MagicHash :: Extension TypeFamilies :: Extension StandaloneDeriving :: Extension UnicodeSyntax :: Extension UnliftedFFITypes :: Extension InterruptibleFFI :: Extension CApiFFI :: Extension LiberalTypeSynonyms :: Extension TypeOperators :: Extension RecordWildCards :: Extension RecordPuns :: Extension DisambiguateRecordFields :: Extension TraditionalRecordSyntax :: Extension OverloadedStrings :: Extension GADTs :: Extension GADTSyntax :: Extension MonoPatBinds :: Extension RelaxedPolyRec :: Extension ExtendedDefaultRules :: Extension UnboxedTuples :: Extension DeriveDataTypeable :: Extension DeriveGeneric :: Extension DefaultSignatures :: Extension InstanceSigs :: Extension ConstrainedClassMethods :: Extension PackageImports :: Extension ImpredicativeTypes :: Extension NewQualifiedOperators :: Extension PostfixOperators :: Extension QuasiQuotes :: Extension TransformListComp :: Extension MonadComprehensions :: Extension ViewPatterns :: Extension XmlSyntax :: Extension RegularPatterns :: Extension TupleSections :: Extension GHCForeignImportPrim :: Extension NPlusKPatterns :: Extension DoAndIfThenElse :: Extension MultiWayIf :: Extension LambdaCase :: Extension RebindableSyntax :: Extension ExplicitForAll :: Extension DatatypeContexts :: Extension MonoLocalBinds :: Extension DeriveFunctor :: Extension DeriveTraversable :: Extension DeriveFoldable :: Extension NondecreasingIndentation :: Extension SafeImports :: Extension Safe :: Extension Trustworthy :: Extension Unsafe :: Extension ConstraintKinds :: Extension PolyKinds :: Extension DataKinds :: Extension ParallelArrays :: Extension RoleAnnotations :: Extension OverloadedLists :: Extension EmptyCase :: Extension AutoDeriveTypeable :: Extension NegativeLiterals :: Extension BinaryLiterals :: Extension NumDecimals :: Extension NullaryTypeClasses :: Extension ExplicitNamespaces :: Extension AllowAmbiguousTypes :: Extension JavaScriptFFI :: Extension PatternSynonyms :: Extension PartialTypeSignatures :: Extension NamedWildCards :: Extension DeriveAnyClass :: Extension DeriveLift :: Extension StaticPointers :: Extension StrictData :: Extension Strict :: Extension ApplicativeDo :: Extension DuplicateRecordFields :: Extension TypeApplications :: Extension TypeInType :: Extension UndecidableSuperClasses :: Extension MonadFailDesugaring :: Extension TemplateHaskellQuotes :: Extension OverloadedLabels :: Extension TypeFamilyDependencies :: Extension NoOverlappingInstances :: Extension NoUndecidableInstances :: Extension NoIncoherentInstances :: Extension NoDoRec :: Extension NoRecursiveDo :: Extension NoParallelListComp :: Extension NoMultiParamTypeClasses :: Extension NoMonomorphismRestriction :: Extension NoFunctionalDependencies :: Extension NoRank2Types :: Extension NoRankNTypes :: Extension NoPolymorphicComponents :: Extension NoExistentialQuantification :: Extension NoScopedTypeVariables :: Extension NoPatternSignatures :: Extension NoImplicitParams :: Extension NoFlexibleContexts :: Extension NoFlexibleInstances :: Extension NoEmptyDataDecls :: Extension NoCPP :: Extension NoKindSignatures :: Extension NoBangPatterns :: Extension NoTypeSynonymInstances :: Extension NoTemplateHaskell :: Extension NoForeignFunctionInterface :: Extension NoArrows :: Extension NoGenerics :: Extension NoImplicitPrelude :: Extension NoNamedFieldPuns :: Extension NoPatternGuards :: Extension NoGeneralizedNewtypeDeriving :: Extension NoExtensibleRecords :: Extension NoRestrictedTypeSynonyms :: Extension NoHereDocuments :: Extension NoMagicHash :: Extension NoTypeFamilies :: Extension NoStandaloneDeriving :: Extension NoUnicodeSyntax :: Extension NoUnliftedFFITypes :: Extension NoInterruptibleFFI :: Extension NoCApiFFI :: Extension NoLiberalTypeSynonyms :: Extension NoTypeOperators :: Extension NoRecordWildCards :: Extension NoRecordPuns :: Extension NoDisambiguateRecordFields :: Extension NoTraditionalRecordSyntax :: Extension NoOverloadedStrings :: Extension NoGADTs :: Extension NoGADTSyntax :: Extension NoMonoPatBinds :: Extension NoRelaxedPolyRec :: Extension NoExtendedDefaultRules :: Extension NoUnboxedTuples :: Extension NoDeriveDataTypeable :: Extension NoDeriveGeneric :: Extension NoDefaultSignatures :: Extension NoInstanceSigs :: Extension NoConstrainedClassMethods :: Extension NoPackageImports :: Extension NoImpredicativeTypes :: Extension NoNewQualifiedOperators :: Extension NoPostfixOperators :: Extension NoQuasiQuotes :: Extension NoTransformListComp :: Extension NoMonadComprehensions :: Extension NoViewPatterns :: Extension NoXmlSyntax :: Extension NoRegularPatterns :: Extension NoTupleSections :: Extension NoGHCForeignImportPrim :: Extension NoNPlusKPatterns :: Extension NoDoAndIfThenElse :: Extension NoMultiWayIf :: Extension NoLambdaCase :: Extension NoRebindableSyntax :: Extension NoExplicitForAll :: Extension NoDatatypeContexts :: Extension NoMonoLocalBinds :: Extension NoDeriveFunctor :: Extension NoDeriveTraversable :: Extension NoDeriveFoldable :: Extension NoNondecreasingIndentation :: Extension NoSafeImports :: Extension NoSafe :: Extension NoTrustworthy :: Extension NoUnsafe :: Extension NoConstraintKinds :: Extension NoPolyKinds :: Extension NoDataKinds :: Extension NoParallelArrays :: Extension NoRoleAnnotations :: Extension NoOverloadedLists :: Extension NoEmptyCase :: Extension NoAutoDeriveTypeable :: Extension NoNegativeLiterals :: Extension NoBinaryLiterals :: Extension NoNumDecimals :: Extension NoNullaryTypeClasses :: Extension NoExplicitNamespaces :: Extension NoAllowAmbiguousTypes :: Extension NoJavaScriptFFI :: Extension NoPatternSynonyms :: Extension NoPartialTypeSignatures :: Extension NoNamedWildCards :: Extension NoDeriveAnyClass :: Extension NoDeriveLift :: Extension NoStaticPointers :: Extension NoStrictData :: Extension NoStrict :: Extension NoApplicativeDo :: Extension NoDuplicateRecordFields :: Extension NoTypeApplications :: Extension NoTypeInType :: Extension NoUndecidableSuperClasses :: Extension NoMonadFailDesugaring :: Extension NoTemplateHaskellQuotes :: Extension NoOverloadedLabels :: Extension NoTypeFamilyDependencies :: 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] -- | Module names are _not_ filepaths. type ModuleName = String -- | Returns True if the module was interpreted. isModuleInterpreted :: MonadInterpreter m => ModuleName -> m Bool -- | Represent module import statement. See setImportsF data ModuleImport ModuleImport :: String -> ModuleQualification -> ImportList -> ModuleImport [modName] :: ModuleImport -> String [modQual] :: ModuleImport -> ModuleQualification [modImp] :: ModuleImport -> ImportList data ModuleQualification NotQualified :: ModuleQualification ImportAs :: String -> ModuleQualification QualifiedAs :: Maybe String -> ModuleQualification data ImportList NoImportList :: ImportList ImportList :: [String] -> ImportList HidingList :: [String] -> ImportList -- | 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. Note that in order to use code from -- that module, you also need to call setImports (to use the -- exported types and definitions) or setTopLevelModules (to also -- use the private types and definitions). -- -- The interpreter is reset both before loading the modules and in -- the event of an error. -- -- IMPORTANT: Like in a ghci session, this will also load (and -- interpret) any dependency that is not available via an installed -- package. Make sure that you are not loading any module that is also -- being used to compile your application. In particular, you need to -- avoid modules that define types that will later occur in an expression -- that you will want to interpret. -- -- The problem in doing this is that those types will have two -- incompatible representations at runtime: 1) the one in the compiled -- code and 2) the one in the interpreted code. When interpreting such an -- expression (bringing it to program-code) you will likely get a -- segmentation fault, since the latter representation will be used where -- the program assumes the former. -- -- The rule of thumb is: never make the interpreter run on the directory -- with the source code of your program! If you want your interpreted -- code to use some type that is defined in your program, then put the -- defining module on a library and make your program depend on that -- package. 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. These can be -- modules previously loaded with loadModules, or modules from -- packages which hint is aware of. This includes package databases -- specified to unsafeRunInterpreterWithArgs by the -- -package-db=... parameter, and packages specified by a ghc -- environment file created by cabal build -- --write-ghc-environment-files=always. -- -- Warning: setImports, setImportsQ, and setImportsF -- 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 () -- | A variant of setImports where modules them may be qualified. -- e.g.: -- -- setImportsQ [(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 () -- | A variant of setImportsQ where modules may have an explicit -- import list. e.g.: -- --
--   setImportsF [ModuleImport Prelude NotQualified NoImportList, ModuleImport Data.Text (QualifiedAs $ Just Text) (HidingList ["pack"])]
--   
setImportsF :: MonadInterpreter m => [ModuleImport] -> 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] getModuleAnnotations :: (Data a, MonadInterpreter m) => a -> String -> m [a] getValAnnotations :: (Data a, MonadInterpreter m) => a -> String -> m [a] -- | Similar to typeChecks, but gives more information, e.g. the -- type errors. typeChecksWithDetails :: MonadInterpreter m => String -> m (Either [GhcError] String) -- | Returns a string representation of the type of the expression. typeOf :: MonadInterpreter m => String -> m String -- | Tests if the expression type checks. -- -- NB. Be careful if unsafeSetGhcOption "-fdefer-type-errors" is -- used. Perhaps unsurprisingly, that can falsely make -- typeChecks and typeChecksWithDetails return -- True and Right _ respectively. typeChecks :: MonadInterpreter m => String -> m Bool -- | Returns a string representation of the kind of the type expression. kindOf :: MonadInterpreter m => String -> m String -- | Returns a string representation of the normalized type expression. -- This is what the :kind! GHCi command prints after =. normalizeType :: 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 -- | Evaluate a statement in the IO monad, possibly binding new -- names. -- -- Example: -- --
--   runStmt "x <- return 42"
--   runStmt "print x"
--   
runStmt :: MonadInterpreter m => String -> m () 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 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 MonomorphismRestriction :: Extension FunctionalDependencies :: Extension Rank2Types :: Extension RankNTypes :: Extension PolymorphicComponents :: Extension ExistentialQuantification :: Extension ScopedTypeVariables :: Extension PatternSignatures :: 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 ImplicitPrelude :: Extension NamedFieldPuns :: Extension PatternGuards :: Extension GeneralizedNewtypeDeriving :: Extension ExtensibleRecords :: Extension RestrictedTypeSynonyms :: Extension HereDocuments :: Extension MagicHash :: Extension TypeFamilies :: Extension StandaloneDeriving :: Extension UnicodeSyntax :: Extension UnliftedFFITypes :: Extension InterruptibleFFI :: Extension CApiFFI :: Extension LiberalTypeSynonyms :: Extension TypeOperators :: Extension RecordWildCards :: Extension RecordPuns :: Extension DisambiguateRecordFields :: Extension TraditionalRecordSyntax :: Extension OverloadedStrings :: Extension GADTs :: Extension GADTSyntax :: Extension MonoPatBinds :: Extension RelaxedPolyRec :: Extension ExtendedDefaultRules :: Extension UnboxedTuples :: Extension DeriveDataTypeable :: Extension DeriveGeneric :: Extension DefaultSignatures :: Extension InstanceSigs :: Extension ConstrainedClassMethods :: Extension PackageImports :: Extension ImpredicativeTypes :: Extension NewQualifiedOperators :: Extension PostfixOperators :: Extension QuasiQuotes :: Extension TransformListComp :: Extension MonadComprehensions :: Extension ViewPatterns :: Extension XmlSyntax :: Extension RegularPatterns :: Extension TupleSections :: Extension GHCForeignImportPrim :: Extension NPlusKPatterns :: Extension DoAndIfThenElse :: Extension MultiWayIf :: Extension LambdaCase :: Extension RebindableSyntax :: Extension ExplicitForAll :: Extension DatatypeContexts :: Extension MonoLocalBinds :: Extension DeriveFunctor :: Extension DeriveTraversable :: Extension DeriveFoldable :: Extension NondecreasingIndentation :: Extension SafeImports :: Extension Safe :: Extension Trustworthy :: Extension Unsafe :: Extension ConstraintKinds :: Extension PolyKinds :: Extension DataKinds :: Extension ParallelArrays :: Extension RoleAnnotations :: Extension OverloadedLists :: Extension EmptyCase :: Extension AutoDeriveTypeable :: Extension NegativeLiterals :: Extension BinaryLiterals :: Extension NumDecimals :: Extension NullaryTypeClasses :: Extension ExplicitNamespaces :: Extension AllowAmbiguousTypes :: Extension JavaScriptFFI :: Extension PatternSynonyms :: Extension PartialTypeSignatures :: Extension NamedWildCards :: Extension DeriveAnyClass :: Extension DeriveLift :: Extension StaticPointers :: Extension StrictData :: Extension Strict :: Extension ApplicativeDo :: Extension DuplicateRecordFields :: Extension TypeApplications :: Extension TypeInType :: Extension UndecidableSuperClasses :: Extension MonadFailDesugaring :: Extension TemplateHaskellQuotes :: Extension OverloadedLabels :: Extension TypeFamilyDependencies :: Extension NoOverlappingInstances :: Extension NoUndecidableInstances :: Extension NoIncoherentInstances :: Extension NoDoRec :: Extension NoRecursiveDo :: Extension NoParallelListComp :: Extension NoMultiParamTypeClasses :: Extension NoMonomorphismRestriction :: Extension NoFunctionalDependencies :: Extension NoRank2Types :: Extension NoRankNTypes :: Extension NoPolymorphicComponents :: Extension NoExistentialQuantification :: Extension NoScopedTypeVariables :: Extension NoPatternSignatures :: Extension NoImplicitParams :: Extension NoFlexibleContexts :: Extension NoFlexibleInstances :: Extension NoEmptyDataDecls :: Extension NoCPP :: Extension NoKindSignatures :: Extension NoBangPatterns :: Extension NoTypeSynonymInstances :: Extension NoTemplateHaskell :: Extension NoForeignFunctionInterface :: Extension NoArrows :: Extension NoGenerics :: Extension NoImplicitPrelude :: Extension NoNamedFieldPuns :: Extension NoPatternGuards :: Extension NoGeneralizedNewtypeDeriving :: Extension NoExtensibleRecords :: Extension NoRestrictedTypeSynonyms :: Extension NoHereDocuments :: Extension NoMagicHash :: Extension NoTypeFamilies :: Extension NoStandaloneDeriving :: Extension NoUnicodeSyntax :: Extension NoUnliftedFFITypes :: Extension NoInterruptibleFFI :: Extension NoCApiFFI :: Extension NoLiberalTypeSynonyms :: Extension NoTypeOperators :: Extension NoRecordWildCards :: Extension NoRecordPuns :: Extension NoDisambiguateRecordFields :: Extension NoTraditionalRecordSyntax :: Extension NoOverloadedStrings :: Extension NoGADTs :: Extension NoGADTSyntax :: Extension NoMonoPatBinds :: Extension NoRelaxedPolyRec :: Extension NoExtendedDefaultRules :: Extension NoUnboxedTuples :: Extension NoDeriveDataTypeable :: Extension NoDeriveGeneric :: Extension NoDefaultSignatures :: Extension NoInstanceSigs :: Extension NoConstrainedClassMethods :: Extension NoPackageImports :: Extension NoImpredicativeTypes :: Extension NoNewQualifiedOperators :: Extension NoPostfixOperators :: Extension NoQuasiQuotes :: Extension NoTransformListComp :: Extension NoMonadComprehensions :: Extension NoViewPatterns :: Extension NoXmlSyntax :: Extension NoRegularPatterns :: Extension NoTupleSections :: Extension NoGHCForeignImportPrim :: Extension NoNPlusKPatterns :: Extension NoDoAndIfThenElse :: Extension NoMultiWayIf :: Extension NoLambdaCase :: Extension NoRebindableSyntax :: Extension NoExplicitForAll :: Extension NoDatatypeContexts :: Extension NoMonoLocalBinds :: Extension NoDeriveFunctor :: Extension NoDeriveTraversable :: Extension NoDeriveFoldable :: Extension NoNondecreasingIndentation :: Extension NoSafeImports :: Extension NoSafe :: Extension NoTrustworthy :: Extension NoUnsafe :: Extension NoConstraintKinds :: Extension NoPolyKinds :: Extension NoDataKinds :: Extension NoParallelArrays :: Extension NoRoleAnnotations :: Extension NoOverloadedLists :: Extension NoEmptyCase :: Extension NoAutoDeriveTypeable :: Extension NoNegativeLiterals :: Extension NoBinaryLiterals :: Extension NoNumDecimals :: Extension NoNullaryTypeClasses :: Extension NoExplicitNamespaces :: Extension NoAllowAmbiguousTypes :: Extension NoJavaScriptFFI :: Extension NoPatternSynonyms :: Extension NoPartialTypeSignatures :: Extension NoNamedWildCards :: Extension NoDeriveAnyClass :: Extension NoDeriveLift :: Extension NoStaticPointers :: Extension NoStrictData :: Extension NoStrict :: Extension NoApplicativeDo :: Extension NoDuplicateRecordFields :: Extension NoTypeApplications :: Extension NoTypeInType :: Extension NoUndecidableSuperClasses :: Extension NoMonadFailDesugaring :: Extension NoTemplateHaskellQuotes :: Extension NoOverloadedLabels :: Extension NoTypeFamilyDependencies :: Extension UnknownExtension :: String -> Extension supportedExtensions :: [String] -- | 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 :: (MonadMask m, MonadIO m) => [String] -> InterpreterT m a -> m (Either InterpreterError a) -- | A variant of unsafeRunInterpreterWithArgs which also lets you -- specify the folder in which the GHC bootstrap libraries (base, -- containers, etc.) can be found. This allows you to run hint on a -- machine in which GHC is not installed. -- -- A typical libdir value could be -- usrlibghc-8.0.1ghc-8.0.1. unsafeRunInterpreterWithArgsLibdir :: (MonadIO m, MonadMask m) => [String] -> String -> InterpreterT m a -> m (Either InterpreterError a) unsafeInterpret :: MonadInterpreter m => String -> String -> m a