Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
HIE.Bios.Types
Synopsis
- hie_bios_output :: String
- hie_bios_ghc :: String
- hie_bios_ghc_args :: String
- hie_bios_arg :: String
- hie_bios_deps :: String
- data Cradle a = Cradle {}
- data ActionName a
- data Log
- data LoadStyle
- data CradleAction a = CradleAction {
- actionName :: ActionName a
- runCradle :: FilePath -> LoadStyle -> IO (CradleLoadResult ComponentOptions)
- runGhcCmd :: [String] -> IO (CradleLoadResult String)
- data CradleLoadResult r
- cradleLoadResult :: c -> (CradleError -> c) -> (r -> c) -> CradleLoadResult r -> c
- newtype CradleLoadResultT m a = CradleLoadResultT {
- runCradleResultT :: m (CradleLoadResult a)
- modCradleError :: Monad m => CradleLoadResultT m a -> (CradleError -> m CradleError) -> CradleLoadResultT m a
- throwCE :: Monad m => CradleError -> CradleLoadResultT m a
- data CradleError = CradleError {}
- data ComponentOptions = ComponentOptions {}
- prettyCmdSpec :: CmdSpec -> String
- prettyProcessEnv :: CreateProcess -> [String]
Documentation
hie_bios_output :: String Source #
Environment variable containing the filepath to which cradle actions write their results to. If the filepath does not exist, cradle actions must create them.
hie_bios_ghc :: String Source #
Environment variable pointing to the GHC location used by cabal's and stack's GHC wrapper.
If not set, will default to sensible defaults.
hie_bios_ghc_args :: String Source #
Environment variable with extra arguments passed to the GHC location in cabal's and stack's GHC wrapper.
If not set, assume no extra arguments.
hie_bios_arg :: String Source #
Environment variable pointing to the source file location that caused the cradle action to be executed.
hie_bios_deps :: String Source #
Environment variable pointing to a filepath to which dependencies of a cradle can be written to by the cradle action.
The environment of a single Cradle
.
A Cradle
is a unit for the respective build-system.
It contains the root directory of the Cradle
, the name of
the Cradle
(for debugging purposes), and knows how to set up
a GHC session that is able to compile files that are part of this Cradle
.
A Cradle
may be a single unit in the "cabal-install" context, or
the whole package, comparable to how "stack" works.
Constructors
Cradle | |
Fields
|
data ActionName a Source #
Instances
Functor ActionName Source # | |
Defined in HIE.Bios.Types Methods fmap :: (a -> b) -> ActionName a -> ActionName b # (<$) :: a -> ActionName b -> ActionName a # | |
Show a => Show (ActionName a) Source # | |
Defined in HIE.Bios.Types Methods showsPrec :: Int -> ActionName a -> ShowS # show :: ActionName a -> String # showList :: [ActionName a] -> ShowS # | |
Eq a => Eq (ActionName a) Source # | |
Defined in HIE.Bios.Types | |
Ord a => Ord (ActionName a) Source # | |
Defined in HIE.Bios.Types Methods compare :: ActionName a -> ActionName a -> Ordering # (<) :: ActionName a -> ActionName a -> Bool # (<=) :: ActionName a -> ActionName a -> Bool # (>) :: ActionName a -> ActionName a -> Bool # (>=) :: ActionName a -> ActionName a -> Bool # max :: ActionName a -> ActionName a -> ActionName a # min :: ActionName a -> ActionName a -> ActionName a # |
The LoadStyle
instructs a cradle on how to load a given file target.
Constructors
LoadFile | Instruct the cradle to load the given file target. What this entails depends on the cradle. For example, the |
LoadWithContext [FilePath] | Give a cradle additional context for loading a file target. The context instructs the cradle to load the file target, while also loading the given filepaths. This is useful for cradles that support loading multiple code units at once, e.g. cabal cradles can use the 'multi-repl' feature to set up a multiple home unit session in GHC. |
Instances
Show LoadStyle Source # | |
Eq LoadStyle Source # | |
Ord LoadStyle Source # | |
data CradleAction a Source #
Constructors
CradleAction | |
Fields
|
Instances
Functor CradleAction Source # | |
Defined in HIE.Bios.Types Methods fmap :: (a -> b) -> CradleAction a -> CradleAction b # (<$) :: a -> CradleAction b -> CradleAction a # | |
Show a => Show (CradleAction a) Source # | |
Defined in HIE.Bios.Types Methods showsPrec :: Int -> CradleAction a -> ShowS # show :: CradleAction a -> String # showList :: [CradleAction a] -> ShowS # |
data CradleLoadResult r Source #
Result of an attempt to set up a GHC session for a Cradle
.
This is the go-to error handling mechanism. When possible, this
should be preferred over throwing exceptions.
Constructors
CradleSuccess r | The cradle succeeded and returned these options. |
CradleFail CradleError | We tried to load the cradle and it failed. |
CradleNone | No attempt was made to load the cradle. |
Instances
cradleLoadResult :: c -> (CradleError -> c) -> (r -> c) -> CradleLoadResult r -> c Source #
newtype CradleLoadResultT m a Source #
Constructors
CradleLoadResultT | |
Fields
|
Instances
modCradleError :: Monad m => CradleLoadResultT m a -> (CradleError -> m CradleError) -> CradleLoadResultT m a Source #
throwCE :: Monad m => CradleError -> CradleLoadResultT m a Source #
data CradleError Source #
Constructors
CradleError | |
Fields
|
Instances
Exception CradleError Source # | |
Defined in HIE.Bios.Types Methods toException :: CradleError -> SomeException # fromException :: SomeException -> Maybe CradleError # displayException :: CradleError -> String # | |
Show CradleError Source # | |
Defined in HIE.Bios.Types Methods showsPrec :: Int -> CradleError -> ShowS # show :: CradleError -> String # showList :: [CradleError] -> ShowS # | |
Eq CradleError Source # | |
Defined in HIE.Bios.Types |
data ComponentOptions Source #
Option information for GHC
Constructors
ComponentOptions | |
Fields
|
Instances
Show ComponentOptions Source # | |
Defined in HIE.Bios.Types Methods showsPrec :: Int -> ComponentOptions -> ShowS # show :: ComponentOptions -> String # showList :: [ComponentOptions] -> ShowS # | |
Eq ComponentOptions Source # | |
Defined in HIE.Bios.Types Methods (==) :: ComponentOptions -> ComponentOptions -> Bool # (/=) :: ComponentOptions -> ComponentOptions -> Bool # | |
Ord ComponentOptions Source # | |
Defined in HIE.Bios.Types Methods compare :: ComponentOptions -> ComponentOptions -> Ordering # (<) :: ComponentOptions -> ComponentOptions -> Bool # (<=) :: ComponentOptions -> ComponentOptions -> Bool # (>) :: ComponentOptions -> ComponentOptions -> Bool # (>=) :: ComponentOptions -> ComponentOptions -> Bool # max :: ComponentOptions -> ComponentOptions -> ComponentOptions # min :: ComponentOptions -> ComponentOptions -> ComponentOptions # |
prettyProcessEnv :: CreateProcess -> [String] Source #
Pretty print hie-bios's relevant environment variables.