Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Types and functions to represent interfaces between Nix code and Haskell code.
Synopsis
- data PSObject (a :: Type) = PSObject {}
- type MonadEval m = (MonadIO m, MonadReader (Ptr EvalState) m)
- data Provenance
- data NixException
- appendProvenance :: Provenance -> [Char]
- data a |. b
- (|!) :: forall a b c m. (CheckType (NixTypeForSchema a), MonadEval m, PossibleTypesForSchema a, PossibleTypesForSchema b) => (PSObject a -> m c) -> (PSObject b -> m c) -> PSObject (a |. b) -> m c
- data a ->. b
- (.$) :: MonadIO m => PSObject (a ->. b) -> PSObject a -> m (PSObject b)
- (>>$.) :: MonadEval m => m (PSObject (a ->. b)) -> m (PSObject a) -> m (PSObject b)
- type (->?) a b = (a ->. b) |. b
- ($?) :: (MonadEval m, PossibleTypesForSchema b) => PSObject (a ->? b) -> PSObject a -> m (PSObject b)
- (>>$?) :: (MonadEval m, PossibleTypesForSchema b) => m (PSObject (a ->? b)) -> m (PSObject a) -> m (PSObject b)
- data StringWithoutContext
- basicAttrsWithProvenance :: Value NixAttrs -> Provenance -> PSObject (Attrs '[])
- data Attrs' (as :: [Attr]) w
- type Attrs as = Attrs' as Void
- type (::.) a b = a ':. b
- type (.) as s = AttrType' as as s
- (#.) :: (KnownSymbol s, MonadEval m) => PSObject (Attrs' as w) -> AttrLabel s -> m (PSObject (as . s))
- (>>.) :: (KnownSymbol s, MonadEval m) => m (PSObject (Attrs' as w)) -> AttrLabel s -> m (PSObject (as . s))
- type (::?) a b = a ':? b
- type (::??) a b = a ':? (Null |. b)
- type (?) as s = OptionalAttrType' as as s
- (#?) :: (KnownSymbol s, MonadEval m) => PSObject (Attrs' as w) -> AttrLabel s -> m (Maybe (PSObject (as ? s)))
- (>>?) :: (KnownSymbol s, MonadEval m) => m (PSObject (Attrs' as w)) -> AttrLabel s -> m (Maybe (PSObject (as ? s)))
- (#?!) :: (KnownSymbol s, MonadEval m) => PSObject (Attrs' as w) -> AttrLabel s -> m (PSObject (as ? s))
- type Dictionary = Attrs' '[]
- dictionaryToMap :: MonadEval m => PSObject (Dictionary w) -> m (Map ByteString (PSObject w))
- lookupDict :: MonadEval m => Text -> PSObject (Attrs' as w) -> m (Maybe (PSObject w))
- lookupDictBS :: MonadEval m => ByteString -> PSObject (Attrs' as w) -> m (Maybe (PSObject w))
- requireDict :: MonadEval m => Text -> PSObject (Attrs' as w) -> m (PSObject w)
- requireDictBS :: MonadEval m => ByteString -> PSObject (Attrs' as w) -> m (PSObject w)
- toPSObject :: (MonadEval m, ToRawValue a) => a -> m (PSObject (NixTypeFor a))
- class FromPSObject schema a where
- fromPSObject :: MonadEval m => PSObject schema -> m a
- check :: forall schema m. (CheckType (NixTypeForSchema schema), HasRawValueType (NixTypeForSchema schema), MonadEval m) => PSObject schema -> m (Value (NixTypeForSchema schema))
- getText_ :: MonadEval m => PSObject NixString -> m Text
- getByteString_ :: MonadEval m => PSObject NixString -> m ByteString
- exprWithBasePath :: forall schema m. MonadEval m => Text -> FilePath -> Proxy schema -> m (PSObject schema)
- exprWithBasePathBS :: forall schema m. MonadEval m => ByteString -> FilePath -> Proxy schema -> m (PSObject schema)
- uncheckedCast :: forall (a :: Type) (b :: Type). PSObject a -> PSObject b
- englishOr :: [Text] -> Text
- traverseArray :: MonadEval m => (PSObject a -> m b) -> PSObject [a] -> m [b]
- (#??) :: (KnownSymbol s, (as ? s) ~ (Null |. b), PossibleTypesForSchema b, MonadEval m) => PSObject (Attrs' as w) -> AttrLabel s -> m (Maybe (PSObject b))
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.
PSObject | |
|
Instances
ToRawValue (PSObject a) Source # | |
Defined in Hercules.CNix.Expr.Schema | |
(CheckType (NixTypeForSchema t), HasRawValueType (NixTypeForSchema t)) => ToValue (PSObject t) Source # | |
Defined in Hercules.CNix.Expr.Schema type NixTypeFor (PSObject t) Source # | |
type NixTypeFor (PSObject t) Source # | |
Defined in Hercules.CNix.Expr.Schema |
Error handling
data Provenance Source #
File FilePath | |
Other Text | |
Data | |
Attribute Provenance Text | |
ListItem Provenance Int | |
Application Provenance Provenance |
Instances
Show Provenance Source # | |
Defined in Hercules.CNix.Expr.Schema showsPrec :: Int -> Provenance -> ShowS # show :: Provenance -> String # showList :: [Provenance] -> ShowS # | |
Eq Provenance Source # | |
Defined in Hercules.CNix.Expr.Schema (==) :: Provenance -> Provenance -> Bool # (/=) :: Provenance -> Provenance -> Bool # | |
Ord Provenance Source # | |
Defined in Hercules.CNix.Expr.Schema compare :: Provenance -> Provenance -> Ordering # (<) :: Provenance -> Provenance -> Bool # (<=) :: Provenance -> Provenance -> Bool # (>) :: Provenance -> Provenance -> Bool # (>=) :: Provenance -> Provenance -> Bool # max :: Provenance -> Provenance -> Provenance # min :: Provenance -> Provenance -> Provenance # |
data NixException Source #
MissingAttribute Provenance Text | |
TypeError | |
| |
InvalidText Provenance UnicodeException | |
StringContextNotAllowed Provenance | |
InvalidValue Provenance Text |
Instances
Exception NixException Source # | |
Defined in Hercules.CNix.Expr.Schema | |
Show NixException Source # | |
Defined in Hercules.CNix.Expr.Schema showsPrec :: Int -> NixException -> ShowS # show :: NixException -> String # showList :: [NixException] -> ShowS # | |
Eq NixException Source # | |
Defined in Hercules.CNix.Expr.Schema (==) :: NixException -> NixException -> Bool # (/=) :: NixException -> NixException -> Bool # |
appendProvenance :: Provenance -> [Char] Source #
Alternatives
(|!) :: forall a b c m. (CheckType (NixTypeForSchema a), 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
(>>$.) :: MonadEval m => 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 b) => PSObject (a ->? b) -> PSObject a -> m (PSObject b) Source #
Optional application.
(>>$?) :: (MonadEval m, 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
data StringWithoutContext Source #
Instances
FromPSObject StringWithoutContext ByteString Source # | |
Defined in Hercules.CNix.Expr.Schema fromPSObject :: MonadEval m => PSObject StringWithoutContext -> m ByteString Source # | |
FromPSObject StringWithoutContext Text Source # | |
Defined in Hercules.CNix.Expr.Schema fromPSObject :: MonadEval m => PSObject StringWithoutContext -> m Text Source # | |
FromPSObject StringWithoutContext [Char] Source # | |
Defined in Hercules.CNix.Expr.Schema fromPSObject :: MonadEval m => PSObject StringWithoutContext -> m [Char] Source # |
Attribute sets
basicAttrsWithProvenance :: Value NixAttrs -> Provenance -> PSObject (Attrs '[]) Source #
data Attrs' (as :: [Attr]) w Source #
Attribute set schema with known attributes and wildcard type for remaining attributes.
Attribute sets as records
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.
(#.) :: (KnownSymbol s, MonadEval m) => PSObject (Attrs' as w) -> AttrLabel s -> m (PSObject (as . s)) 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, MonadEval m) => m (PSObject (Attrs' as w)) -> AttrLabel s -> m (PSObject (as . s)) infixl 9 Source #
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
.
(#?) :: (KnownSymbol s, MonadEval m) => PSObject (Attrs' as w) -> AttrLabel s -> m (Maybe (PSObject (as ? s))) 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, MonadEval m) => m (PSObject (Attrs' as w)) -> AttrLabel s -> m (Maybe (PSObject (as ? s))) Source #
(#?!) :: (KnownSymbol s, MonadEval m) => PSObject (Attrs' as w) -> AttrLabel s -> m (PSObject (as ? s)) Source #
Attribute sets as used as dictionaries
type Dictionary = Attrs' '[] Source #
Attribute set functioning as a "dictionary" from string keys to a certain type.
dictionaryToMap :: MonadEval m => PSObject (Dictionary w) -> m (Map ByteString (PSObject w)) Source #
lookupDictBS :: MonadEval m => ByteString -> PSObject (Attrs' as w) -> m (Maybe (PSObject w)) Source #
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
toPSObject :: (MonadEval m, ToRawValue a) => a -> m (PSObject (NixTypeFor a)) Source #
class FromPSObject schema a where Source #
Schema-based parsing type class that constrains neither types nor schemas.
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
.
Instances
FromPSObject Int64 Int64 Source # | |
Defined in Hercules.CNix.Expr.Schema | |
FromPSObject StringWithoutContext ByteString Source # | |
Defined in Hercules.CNix.Expr.Schema fromPSObject :: MonadEval m => PSObject StringWithoutContext -> m ByteString Source # | |
FromPSObject StringWithoutContext Text Source # | |
Defined in Hercules.CNix.Expr.Schema fromPSObject :: MonadEval m => PSObject StringWithoutContext -> m Text Source # | |
FromPSObject Bool Bool Source # | |
Defined in Hercules.CNix.Expr.Schema | |
FromPSObject StringWithoutContext [Char] Source # | |
Defined in Hercules.CNix.Expr.Schema fromPSObject :: MonadEval m => PSObject StringWithoutContext -> m [Char] Source # | |
FromPSObject a b => FromPSObject [a] [b] Source # | |
Defined in Hercules.CNix.Expr.Schema fromPSObject :: MonadEval m => PSObject [a] -> m [b] Source # |
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.
getByteString_ :: MonadEval m => PSObject NixString -> m ByteString Source #
Ignores string context.
Parsing Nix
:: 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
:: 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
(#??) :: (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.