Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- init :: IO ()
- setTalkative :: IO ()
- setDebug :: IO ()
- setGlobalOption :: Text -> Text -> IO ()
- setOption :: Text -> Text -> IO ()
- setExtraStackOverflowHandlerToSleep :: IO ()
- initThread :: IO ()
- allowThreads :: IO ()
- runGcRegisteredThread :: IO a -> IO a
- logInfo :: Text -> IO ()
- withEvalState :: Store -> (Ptr EvalState -> IO a) -> IO a
- withEvalStateConduit :: MonadResource m => Store -> (Ptr EvalState -> ConduitT i o m r) -> ConduitT i o m r
- addAllowedPath :: Ptr EvalState -> ByteString -> IO ()
- addInternalAllowedPaths :: Ptr EvalState -> IO ()
- evalFile :: Ptr EvalState -> FilePath -> IO RawValue
- newStrings :: IO (Ptr Strings)
- appendString :: Ptr Strings -> ByteString -> IO ()
- evalArgs :: Ptr EvalState -> [ByteString] -> IO (Value NixAttrs)
- autoCallFunction :: Ptr EvalState -> RawValue -> Value NixAttrs -> IO RawValue
- isDerivation :: Ptr EvalState -> RawValue -> IO Bool
- isFunctor :: Ptr EvalState -> RawValue -> IO Bool
- getRecurseForDerivations :: Ptr EvalState -> Value NixAttrs -> IO Bool
- getAttr :: Ptr EvalState -> Value NixAttrs -> ByteString -> IO (Maybe RawValue)
- mkNullableRawValue :: Ptr Value' -> IO (Maybe RawValue)
- getAttrs :: Ptr EvalState -> Value NixAttrs -> IO (Map ByteString RawValue)
- getDrvFile :: MonadIO m => Ptr EvalState -> RawValue -> m StorePath
- getAttrBool :: Ptr EvalState -> Value NixAttrs -> ByteString -> IO (Either SomeException (Maybe Bool))
- getList :: Value NixList -> IO [RawValue]
- getAttrList :: Ptr EvalState -> Value NixAttrs -> ByteString -> IO (Either SomeException (Maybe [RawValue]))
- valueFromExpressionString :: Ptr EvalState -> ByteString -> ByteString -> IO RawValue
- callFunction :: Ptr EvalState -> RawValue -> RawValue -> IO RawValue
- apply :: RawValue -> RawValue -> IO RawValue
- mkPath :: Ptr EvalState -> ByteString -> IO (Value NixPath)
- getFlakeFromFlakeRef :: Ptr EvalState -> ByteString -> IO RawValue
- getLocalFlake :: Ptr EvalState -> Text -> IO RawValue
- getFlakeFromGit :: Ptr EvalState -> Text -> Text -> Text -> IO RawValue
- getFlakeFromArchiveUrl :: Ptr EvalState -> Text -> IO RawValue
- class ToRawValue a where
- toRawValue :: Ptr EvalState -> a -> IO RawValue
- class ToRawValue a => ToValue a where
- type NixTypeFor a :: Type
- toValue :: Ptr EvalState -> a -> IO (Value (NixTypeFor a))
- class FromValue n a | a -> n where
- newtype ViaJSON a = ViaJSON {
- fromViaJSON :: a
- data RawValue
- rawValueType :: RawValue -> IO RawValueType
- module Hercules.CNix.Expr.Typed
- data EvalState
Documentation
setTalkative :: IO () Source #
setExtraStackOverflowHandlerToSleep :: IO () Source #
Configure the stack overflow handler to sleep before returning, allowing other threads to continue for a bit.
No-op before Nix 2.12
initThread :: IO () Source #
Initialize the current (main) thread for stack overflow detection.
allowThreads :: IO () Source #
Configure the garbage collector to support threads.
This is not needed when all evaluation happens on the main thread.
runGcRegisteredThread :: IO a -> IO a Source #
Run in a thread from which GC may be triggered safely.
This also installs the stack overflow handler.
NOTE: Before using this, you must call allowThreads
once.
withEvalStateConduit :: MonadResource m => Store -> (Ptr EvalState -> ConduitT i o m r) -> ConduitT i o m r Source #
addAllowedPath :: Ptr EvalState -> ByteString -> IO () Source #
Insert an allowed path. Only has an effect when in restricted or pure mode.
appendString :: Ptr Strings -> ByteString -> IO () Source #
getAttrBool :: Ptr EvalState -> Value NixAttrs -> ByteString -> IO (Either SomeException (Maybe Bool)) Source #
getAttrList :: Ptr EvalState -> Value NixAttrs -> ByteString -> IO (Either SomeException (Maybe [RawValue])) Source #
valueFromExpressionString Source #
:: Ptr EvalState | |
-> ByteString | The string to parse |
-> ByteString | Base path for path exprs |
-> IO RawValue |
Parse a string and eval it.
getFlakeFromFlakeRef :: Ptr EvalState -> ByteString -> IO RawValue Source #
class ToRawValue a where Source #
Nothing
Instances
class ToRawValue a => ToValue a where Source #
type NixTypeFor a :: Type Source #
Instances
class FromValue n a | a -> n where Source #
Marshall values from Nix into Haskell. Instances must satisfy the requirements that:
- Only a single Nix value type is acceptable for the Haskell type.
- Marshalling does not fail, as the Nix runtime type has already been checked.
For deriving-via of ToRawValue
using ToJSON
.
ViaJSON | |
|
Re-exports
A heap object.
Nix doesn't store all its objects on the heap, but we do.
Also, Nix calls them Value
s but it includes thunks, which are not values
and some may never produce values, such as throw "msg"
.
rawValueType :: RawValue -> IO RawValueType Source #
You may need to forceValue
first.
module Hercules.CNix.Expr.Typed