hercules-ci-cnix-expr-0.3.5.1: Bindings for the Nix evaluator
Safe HaskellSafe-Inferred
LanguageHaskell2010

Hercules.CNix.Expr

Contents

Synopsis

Documentation

init :: 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

withEvalState :: Store -> (Ptr EvalState -> IO a) -> IO a 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.

mkNullableRawValue :: Ptr Value' -> IO (Maybe RawValue) Source #

Converts nullPtr to Nothing; actual values to Just (a :: RawValue)

getDrvFile :: MonadIO m => Ptr EvalState -> RawValue -> m StorePath 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.

class ToRawValue a where Source #

Minimal complete definition

Nothing

Instances

Instances details
ToRawValue Value Source # 
Instance details

Defined in Hercules.CNix.Expr

ToRawValue CBool Source # 
Instance details

Defined in Hercules.CNix.Expr

ToRawValue CDouble Source # 
Instance details

Defined in Hercules.CNix.Expr

ToRawValue Int64 Source #

The native Nix integer type

Instance details

Defined in Hercules.CNix.Expr

ToRawValue ByteString Source #

Nix String

Instance details

Defined in Hercules.CNix.Expr

ToRawValue RawValue Source #

Identity

Instance details

Defined in Hercules.CNix.Expr

ToRawValue Text Source #

UTF-8

Instance details

Defined in Hercules.CNix.Expr

ToRawValue Bool Source # 
Instance details

Defined in Hercules.CNix.Expr

ToRawValue Double Source # 
Instance details

Defined in Hercules.CNix.Expr

ToRawValue Int Source # 
Instance details

Defined in Hercules.CNix.Expr

ToJSON a => ToRawValue (ViaJSON a) Source # 
Instance details

Defined in Hercules.CNix.Expr

ToRawValue (PSObject a) Source # 
Instance details

Defined in Hercules.CNix.Expr.Schema

ToRawValue (Value a) Source #

Upcast

Instance details

Defined in Hercules.CNix.Expr

ToRawValue a => ToRawValue (Vector a) Source # 
Instance details

Defined in Hercules.CNix.Expr

ToRawValue a => ToRawValue [a] Source # 
Instance details

Defined in Hercules.CNix.Expr

Methods

toRawValue :: Ptr EvalState -> [a] -> IO RawValue Source #

ToRawValue a => ToRawValue (Map ByteString a) Source # 
Instance details

Defined in Hercules.CNix.Expr

ToRawValue a => ToRawValue (Map Text a) Source # 
Instance details

Defined in Hercules.CNix.Expr

ToRawValue a => ToRawValue (HashMap Text a) Source # 
Instance details

Defined in Hercules.CNix.Expr

class ToRawValue a => ToValue a where Source #

Associated Types

type NixTypeFor a :: Type Source #

Methods

toValue :: Ptr EvalState -> a -> IO (Value (NixTypeFor a)) Source #

Instances

Instances details
ToValue CBool Source # 
Instance details

Defined in Hercules.CNix.Expr

Associated Types

type NixTypeFor CBool Source #

ToValue CDouble Source # 
Instance details

Defined in Hercules.CNix.Expr

Associated Types

type NixTypeFor CDouble Source #

ToValue Int64 Source #

The native Nix integer type

Instance details

Defined in Hercules.CNix.Expr

Associated Types

type NixTypeFor Int64 Source #

ToValue ByteString Source #

Nix String

Instance details

Defined in Hercules.CNix.Expr

Associated Types

type NixTypeFor ByteString Source #

ToValue Text Source #

UTF-8

Instance details

Defined in Hercules.CNix.Expr

Associated Types

type NixTypeFor Text Source #

ToValue Bool Source # 
Instance details

Defined in Hercules.CNix.Expr

Associated Types

type NixTypeFor Bool Source #

ToValue Double Source # 
Instance details

Defined in Hercules.CNix.Expr

Associated Types

type NixTypeFor Double Source #

ToValue Int Source # 
Instance details

Defined in Hercules.CNix.Expr

Associated Types

type NixTypeFor Int Source #

(CheckType (NixTypeForSchema t), HasRawValueType (NixTypeForSchema t)) => ToValue (PSObject t) Source # 
Instance details

Defined in Hercules.CNix.Expr.Schema

Associated Types

type NixTypeFor (PSObject t) Source #

ToValue (Value a) Source #

Identity

Instance details

Defined in Hercules.CNix.Expr

Associated Types

type NixTypeFor (Value a) Source #

ToRawValue a => ToValue (Vector a) Source # 
Instance details

Defined in Hercules.CNix.Expr

Associated Types

type NixTypeFor (Vector a) Source #

ToRawValue a => ToValue [a] Source # 
Instance details

Defined in Hercules.CNix.Expr

Associated Types

type NixTypeFor [a] Source #

Methods

toValue :: Ptr EvalState -> [a] -> IO (Value (NixTypeFor [a])) Source #

ToRawValue a => ToValue (Map ByteString a) Source # 
Instance details

Defined in Hercules.CNix.Expr

Associated Types

type NixTypeFor (Map ByteString a) Source #

ToRawValue a => ToValue (Map Text a) Source # 
Instance details

Defined in Hercules.CNix.Expr

Associated Types

type NixTypeFor (Map Text a) Source #

ToRawValue a => ToValue (HashMap Text a) Source # 
Instance details

Defined in Hercules.CNix.Expr

Associated Types

type NixTypeFor (HashMap Text a) Source #

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.

Methods

fromValue :: Value n -> IO a Source #

Instances

Instances details
FromValue NixInt Int64 Source # 
Instance details

Defined in Hercules.CNix.Expr

FromValue Bool Bool Source # 
Instance details

Defined in Hercules.CNix.Expr

FromValue NixList [RawValue] Source # 
Instance details

Defined in Hercules.CNix.Expr

newtype ViaJSON a Source #

For deriving-via of ToRawValue using ToJSON.

Constructors

ViaJSON 

Fields

Instances

Instances details
Read a => Read (ViaJSON a) Source # 
Instance details

Defined in Hercules.CNix.Expr

Show a => Show (ViaJSON a) Source # 
Instance details

Defined in Hercules.CNix.Expr

Methods

showsPrec :: Int -> ViaJSON a -> ShowS #

show :: ViaJSON a -> String #

showList :: [ViaJSON a] -> ShowS #

Eq a => Eq (ViaJSON a) Source # 
Instance details

Defined in Hercules.CNix.Expr

Methods

(==) :: ViaJSON a -> ViaJSON a -> Bool #

(/=) :: ViaJSON a -> ViaJSON a -> Bool #

Ord a => Ord (ViaJSON a) Source # 
Instance details

Defined in Hercules.CNix.Expr

Methods

compare :: ViaJSON a -> ViaJSON a -> Ordering #

(<) :: ViaJSON a -> ViaJSON a -> Bool #

(<=) :: ViaJSON a -> ViaJSON a -> Bool #

(>) :: ViaJSON a -> ViaJSON a -> Bool #

(>=) :: ViaJSON a -> ViaJSON a -> Bool #

max :: ViaJSON a -> ViaJSON a -> ViaJSON a #

min :: ViaJSON a -> ViaJSON a -> ViaJSON a #

ToJSON a => ToRawValue (ViaJSON a) Source # 
Instance details

Defined in Hercules.CNix.Expr

Re-exports

data RawValue Source #

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

Instances details
ToRawValue RawValue Source #

Identity

Instance details

Defined in Hercules.CNix.Expr

FromValue NixList [RawValue] Source # 
Instance details

Defined in Hercules.CNix.Expr

rawValueType :: RawValue -> IO RawValueType Source #

You may need to forceValue first.