| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Hercules.CNix.Expr
Contents
Synopsis
- init :: IO ()
- setTalkative :: IO ()
- setDebug :: IO ()
- setGlobalOption :: Text -> Text -> IO ()
- setOption :: Text -> Text -> IO ()
- 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 :: 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 :: 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 #
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 #
Arguments
| :: 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 #
Minimal complete definition
Nothing
Methods
Instances
class ToRawValue a => ToValue a where Source #
Associated Types
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.
Constructors
| ViaJSON | |
Fields
| |
Instances
| Read a => Read (ViaJSON a) Source # | |
| Show a => Show (ViaJSON a) Source # | |
| Eq a => Eq (ViaJSON a) Source # | |
| Ord a => Ord (ViaJSON a) Source # | |
| ToJSON a => ToRawValue (ViaJSON a) Source # | |
Defined in Hercules.CNix.Expr | |
Re-exports
A heap object.
Nix doesn't store all its objects on the heap, but we do.
Also, Nix calls them Values but it includes thunks, which are not values
and some may never produce values, such as throw "msg".
Instances
| ToRawValue RawValue Source # | Identity |
Defined in Hercules.CNix.Expr | |
rawValueType :: RawValue -> IO RawValueType Source #
You may need to forceValue first.
module Hercules.CNix.Expr.Typed