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

Hercules.CNix.Expr.Raw

Synopsis

Documentation

newtype 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".

Constructors

RawValue (Ptr Value') 

Instances

Instances details
ToRawValue RawValue Source #

Identity

Instance details

Defined in Hercules.CNix.Expr

mkRawValue :: Ptr Value' -> IO RawValue Source #

Takes ownership of the value.

data RawValueType Source #

Similar to Nix's Value->type but conflates the List variations

Instances

Instances details
Generic RawValueType Source # 
Instance details

Defined in Hercules.CNix.Expr.Raw

Associated Types

type Rep RawValueType :: Type -> Type #

Show RawValueType Source # 
Instance details

Defined in Hercules.CNix.Expr.Raw

Eq RawValueType Source # 
Instance details

Defined in Hercules.CNix.Expr.Raw

Ord RawValueType Source # 
Instance details

Defined in Hercules.CNix.Expr.Raw

type Rep RawValueType Source # 
Instance details

Defined in Hercules.CNix.Expr.Raw

type Rep RawValueType = D1 ('MetaData "RawValueType" "Hercules.CNix.Expr.Raw" "hercules-ci-cnix-expr-0.3.3.0-inplace" 'False) ((((C1 ('MetaCons "Int" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Bool" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "String" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Path" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Null" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Attrs" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "List" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Thunk" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "App" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Lambda" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Blackhole" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PrimOp" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "PrimOpApp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "External" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Float" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Other" 'PrefixI 'False) (U1 :: Type -> Type)))))

rawValueType :: RawValue -> IO RawValueType Source #

You may need to forceValue first.

canonicalRawType :: RawValueType -> RawValueType Source #

Brings RawValueType closer to the 2.4 ValueType.

This function won't be necessary when support for 2.3 is dropped and we switch entirely to the Haskell equivalent of C++ ValueType.