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

Hercules.CNix.Expr.Schema

Description

Types and functions to represent interfaces between Nix code and Haskell code.

Synopsis

Core

data PSObject (a :: Type) Source #

An object (thunk or value) with its Provenance and an expected schema type attached as a phantom type.

The phantom specifies the expactation, not a checked type.

Constructors

PSObject 

Fields

  • provenance :: Provenance

    Tracks the origin of the object, which is useful informaton for error messages.

  • value :: RawValue

    The Nix object, which may be a thunk (producing errors, non-termination, etc) or a Value of any type.

    Use check and/or |. to evaluate it (whnf) and narrow down its runtime type to a specific Value.

Instances

Instances details
ToRawValue (PSObject a) Source # 
Instance details

Defined in Hercules.CNix.Expr.Schema

(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 #

type NixTypeFor (PSObject t) Source # 
Instance details

Defined in Hercules.CNix.Expr.Schema

Error handling

Alternatives

data a |. b Source #

Alternative schema. The value only needs to satisfy one subschema.

(|!) :: forall a b c m. (CheckType (NixTypeForSchema a), MonadIO m, MonadEval m, PossibleTypesForSchema a, PossibleTypesForSchema b) => (PSObject a -> m c) -> (PSObject b -> m c) -> PSObject (a |. b) -> m c Source #

Force and check type, then continue without backtracking

Functions

data a ->. b infixr 1 Source #

Function schema.

(.$) :: MonadIO m => PSObject (a ->. b) -> PSObject a -> m (PSObject b) Source #

(>>$.) :: (MonadEval m, PossibleTypesForSchema a, PossibleTypesForSchema b) => m (PSObject (a ->. b)) -> m (PSObject a) -> m (PSObject b) Source #

Application. Like $. but takes care of monadic binding as a convenience.

type (->?) a b = (a ->. b) |. b infixr 1 Source #

Optional function. If the value is not a function, use it as the result.

($?) :: (MonadEval m, PossibleTypesForSchema a, PossibleTypesForSchema b) => PSObject (a ->? b) -> PSObject a -> m (PSObject b) Source #

Optional application.

(>>$?) :: (MonadEval m, PossibleTypesForSchema a, PossibleTypesForSchema b) => m (PSObject (a ->? b)) -> m (PSObject a) -> m (PSObject b) Source #

Optional application. Like $? but takes care of monadic binding as a convenience.

Simple types

Attribute sets

data Attrs' (as :: [Attr]) w Source #

Attribute set schema with known attributes and wildcard type for remaining attributes.

Attribute sets as records

type Attrs as = Attrs' as Void Source #

Attribute set schema with known attributes only

type (::.) a b = a :. b infix 0 Source #

Required (_.) attribute name and type (::_)

Note that the type may still be nullable, but the attribute is expected to exist.

type (.) as s = AttrType' as as s Source #

(#.) :: (KnownSymbol s, (as . s) ~ b, MonadEval m) => PSObject (Attrs' as w) -> AttrLabel s -> m (PSObject b) infixl 9 Source #

Attribute selector. a #. #b is a.b in Nix. Operates on attributes that are required (_.) in the schema, throwing an error if necessary.

(>>.) :: (KnownSymbol s, (as . s) ~ b, MonadEval m) => m (PSObject (Attrs' as w)) -> AttrLabel s -> m (PSObject b) infixl 9 Source #

A combination of >>= and #..

type (::?) a b = a :? b infix 0 Source #

Optional (_?) attribute name and type (::_)

This indicates that the attribute may be omitted in its entirety, which is distinct from an attribute that may be null.

type (::??) a b = a :? (Null |. b) Source #

Optional (_?) attribute name and type (::_)

This indicates that the attribute may be omitted in its entirety, which is distinct from an attribute that may be null.

type (?) as s = OptionalAttrType' as as s Source #

(#?) :: (KnownSymbol s, (as ? s) ~ b, MonadEval m) => PSObject (Attrs' as w) -> AttrLabel s -> m (Maybe (PSObject b)) Source #

Attribute selector. a #? #b is a.b in Nix, but handles the missing case without exception. Operates on attributes that are optional (_?) in the schema, throwing an error if necessary.

(>>?) :: (KnownSymbol s, (as ? s) ~ b, MonadEval m) => m (PSObject (Attrs' as w)) -> AttrLabel s -> m (Maybe (PSObject b)) Source #

A combination of >>= and #?.

(#?!) :: (KnownSymbol s, (as ? s) ~ b, MonadEval m) => PSObject (Attrs' as w) -> AttrLabel s -> m (PSObject b) Source #

Retrieve an optional attribute but throw if it's missing.

It provides a decent error message with attrset provenance, but can't provide extra context like you can when manually handling the a #? b Nothing case.

Attribute sets as used as dictionaries

type Dictionary = Attrs' '[] Source #

Attribute set functioning as a "dictionary" from string keys to a certain type.

requireDict :: MonadEval m => Text -> PSObject (Attrs' as w) -> m (PSObject w) Source #

Like #?!. Throws an acceptable but not great error message.

requireDictBS :: MonadEval m => ByteString -> PSObject (Attrs' as w) -> m (PSObject w) Source #

Like #?!. Throws an acceptable but not great error message.

Serialization

class FromPSObject schema a where Source #

Schema-based parsing type class that constrains neither types nor schemas.

Methods

fromPSObject :: MonadEval m => PSObject schema -> m a Source #

Parse an object assumed to be in schema schema into a value of type a or throw a NixException.

check :: forall schema m. (CheckType (NixTypeForSchema schema), HasRawValueType (NixTypeForSchema schema), MonadEval m) => PSObject schema -> m (Value (NixTypeForSchema schema)) Source #

Force a value and check against schema.

getText_ :: MonadEval m => PSObject NixString -> m Text Source #

Ignores string context.

getByteString_ :: MonadEval m => PSObject NixString -> m ByteString Source #

Ignores string context.

Parsing Nix

exprWithBasePath Source #

Arguments

:: forall schema m. MonadEval m 
=> Text

Expression text in the Nix language.

-> FilePath

Base path for relative path references in the expression text.

-> Proxy schema

A schema that the expression should satisfy.

-> m (PSObject schema) 

Parses an expression from string

exprWithBasePathBS Source #

Arguments

:: forall schema m. MonadEval m 
=> ByteString

Expression text in the Nix language.

-> FilePath

Base path for relative path references in the expression text.

-> Proxy schema

A schema that the expression should satisfy.

-> m (PSObject schema) 

Parses an expression from string

Utilities

uncheckedCast :: forall (a :: Type) (b :: Type). PSObject a -> PSObject b Source #

traverseArray :: MonadEval m => (PSObject a -> m b) -> PSObject [a] -> m [b] Source #

(#??) :: (KnownSymbol s, (as ? s) ~ (Null |. b), PossibleTypesForSchema b, MonadEval m) => PSObject (Attrs' as w) -> AttrLabel s -> m (Maybe (PSObject b)) Source #

Attribute selector. a #? #b is a.b in Nix, but handles the missing case and the null case without exception. Operates on attributes that are optional (_?) and nullable (Null |., () |.) in the schema.