{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}

-- | Types and functions to represent interfaces between Nix code and Haskell
--     code.
module Hercules.CNix.Expr.Schema
  ( -- * Core
    PSObject (..),
    MonadEval,

    -- * Error handling
    Provenance (..),
    NixException (..),
    appendProvenance,

    -- * Alternatives

    --
    -- Runtime type matching. Use of @|@ comes from the implicit sum types that
    -- constitute Nix values.
    type (|.),
    (|!),

    -- * Functions
    type (->.),
    (.$),
    (>>$.),
    type (->?),
    ($?),
    (>>$?),

    -- * Simple types
    type StringWithoutContext,

    -- * Attribute sets
    basicAttrsWithProvenance,
    --
    -- Common type that can represent both simultaneously.
    type Attrs',

    -- * Attribute sets as records
    type Attrs,
    type (::.),
    type (.),
    (#.),
    (>>.),
    type (::?),
    type (::??),
    type (?),
    (#?),
    (>>?),
    (#?!),

    -- * Attribute sets as used as dictionaries
    type Dictionary,
    dictionaryToMap,
    lookupDict,
    lookupDictBS,
    requireDict,
    requireDictBS,

    -- * Serialization
    toPSObject,
    FromPSObject (..),
    check,
    getText_,
    getByteString_,

    -- * Parsing Nix
    exprWithBasePath,
    exprWithBasePathBS,

    -- * Utilities
    uncheckedCast,
    englishOr,
    traverseArray,
    (#??),
  )
where

import Data.Coerce (coerce)
import qualified Data.Map as M
import qualified Data.Text as T
import qualified GHC.TypeLits as TL
import Hercules.CNix.Expr (CheckType, EvalState, HasRawValueType, NixAttrs, NixFunction, NixList, NixPath, NixString, RawValue, ToRawValue (..), ToValue (..), Value (rtValue), apply, checkType, getAttr, getRawValueType, getStringIgnoreContext, hasContext, rawValueType, toRawValue, valueFromExpressionString)
import qualified Hercules.CNix.Expr as Expr
import Hercules.CNix.Expr.Raw (RawValueType, canonicalRawType)
import Protolude hiding (TypeError, check, evalState)

-- TODO add Pos fields
data Provenance
  = File FilePath
  | Other Text
  | Data
  | Attribute Provenance Text
  | ListItem Provenance Int
  | Application Provenance Provenance
  deriving (Int -> Provenance -> ShowS
[Provenance] -> ShowS
Provenance -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [Provenance] -> ShowS
$cshowList :: [Provenance] -> ShowS
show :: Provenance -> [Char]
$cshow :: Provenance -> [Char]
showsPrec :: Int -> Provenance -> ShowS
$cshowsPrec :: Int -> Provenance -> ShowS
Show, Provenance -> Provenance -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Provenance -> Provenance -> Bool
$c/= :: Provenance -> Provenance -> Bool
== :: Provenance -> Provenance -> Bool
$c== :: Provenance -> Provenance -> Bool
Eq, Eq Provenance
Provenance -> Provenance -> Bool
Provenance -> Provenance -> Ordering
Provenance -> Provenance -> Provenance
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Provenance -> Provenance -> Provenance
$cmin :: Provenance -> Provenance -> Provenance
max :: Provenance -> Provenance -> Provenance
$cmax :: Provenance -> Provenance -> Provenance
>= :: Provenance -> Provenance -> Bool
$c>= :: Provenance -> Provenance -> Bool
> :: Provenance -> Provenance -> Bool
$c> :: Provenance -> Provenance -> Bool
<= :: Provenance -> Provenance -> Bool
$c<= :: Provenance -> Provenance -> Bool
< :: Provenance -> Provenance -> Bool
$c< :: Provenance -> Provenance -> Bool
compare :: Provenance -> Provenance -> Ordering
$ccompare :: Provenance -> Provenance -> Ordering
Ord)

data NixException
  = MissingAttribute Provenance Text
  | TypeError
      Provenance
      RawValueType
      -- ^ actual
      [RawValueType]
      -- ^ expected
  | InvalidText Provenance UnicodeException
  | StringContextNotAllowed Provenance
  | InvalidValue Provenance Text
  deriving (Int -> NixException -> ShowS
[NixException] -> ShowS
NixException -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [NixException] -> ShowS
$cshowList :: [NixException] -> ShowS
show :: NixException -> [Char]
$cshow :: NixException -> [Char]
showsPrec :: Int -> NixException -> ShowS
$cshowsPrec :: Int -> NixException -> ShowS
Show, NixException -> NixException -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NixException -> NixException -> Bool
$c/= :: NixException -> NixException -> Bool
== :: NixException -> NixException -> Bool
$c== :: NixException -> NixException -> Bool
Eq)

instance Exception NixException where
  displayException :: NixException -> [Char]
displayException (MissingAttribute Provenance
p Text
name) = [Char]
"Missing attribute " forall a. Semigroup a => a -> a -> a
<> forall a b. (Show a, StringConv [Char] b) => a -> b
show Text
name forall a. Semigroup a => a -> a -> a
<> Provenance -> [Char]
appendProvenance Provenance
p
  displayException (TypeError Provenance
p RawValueType
actual [RawValueType]
expected) = [Char]
"Expecting a value of type " forall a. Semigroup a => a -> a -> a
<> forall a b. ConvertText a b => a -> b
toS ([Text] -> Text
englishOr (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
map forall a b. (Show a, StringConv [Char] b) => a -> b
show [RawValueType]
expected)) forall a. Semigroup a => a -> a -> a
<> [Char]
", but got type " forall a. Semigroup a => a -> a -> a
<> forall a b. (Show a, StringConv [Char] b) => a -> b
show RawValueType
actual forall a. Semigroup a => a -> a -> a
<> [Char]
"." forall a. Semigroup a => a -> a -> a
<> Provenance -> [Char]
appendProvenance Provenance
p
  displayException (InvalidText Provenance
p UnicodeException
ue) = forall e. Exception e => e -> [Char]
displayException UnicodeException
ue forall a. Semigroup a => a -> a -> a
<> Provenance -> [Char]
appendProvenance Provenance
p
  displayException (StringContextNotAllowed Provenance
p) = [Char]
"This string must not have a context. It must be usable without building store paths." forall a. Semigroup a => a -> a -> a
<> Provenance -> [Char]
appendProvenance Provenance
p
  displayException (InvalidValue Provenance
p Text
msg) = [Char]
"Invalid value. " forall a. Semigroup a => a -> a -> a
<> forall a b. ConvertText a b => a -> b
toS Text
msg forall a. Semigroup a => a -> a -> a
<> Provenance -> [Char]
appendProvenance Provenance
p

appendProvenance :: Provenance -> [Char]
appendProvenance :: Provenance -> [Char]
appendProvenance (Attribute Provenance
p Text
name) = [Char]
"\n  in attribute " forall a. Semigroup a => a -> a -> a
<> forall a b. (Show a, StringConv [Char] b) => a -> b
show Text
name forall a. Semigroup a => a -> a -> a
<> Provenance -> [Char]
appendProvenance Provenance
p
appendProvenance (ListItem Provenance
p Int
index) = [Char]
"\n  in list item " forall a. Semigroup a => a -> a -> a
<> forall a b. (Show a, StringConv [Char] b) => a -> b
show Int
index forall a. Semigroup a => a -> a -> a
<> Provenance -> [Char]
appendProvenance Provenance
p
appendProvenance (Other Text
x) = [Char]
"\n  in " forall a. Semigroup a => a -> a -> a
<> forall a b. ConvertText a b => a -> b
toS Text
x
appendProvenance Provenance
Data = [Char]
""
appendProvenance (Application Provenance
p Provenance
_p) = [Char]
"\n  in function result" forall a. Semigroup a => a -> a -> a
<> Provenance -> [Char]
appendProvenance Provenance
p
appendProvenance (File [Char]
f) = [Char]
"\n  in file " forall a. Semigroup a => a -> a -> a
<> forall a b. (Show a, StringConv [Char] b) => a -> b
show [Char]
f

-- | Alternative schema. The value only needs to satisfy one subschema.
data a |. b

-- | Function schema.
data a ->. b

infixr 1 ->.

-- | Optional function. If the value is not a function, use it as the result.
type a ->? b = (a ->. b) |. b

infixr 1 ->?

-- | A Nix @null@ value has 1 possible value, like Haskell's @()@.
type Null = ()

-- | Attribute set schema with known attributes and wildcard type for remaining attributes.
data Attrs' (as :: [Attr]) w

-- | Attribute set schema with known attributes only
type Attrs as = Attrs' as Void

-- | Attribute set functioning as a "dictionary" from string keys to a certain type.
type Dictionary = Attrs' '[]

-- | A kind for attribute declarations.
data Attr
  = -- | Required attribute. Use '::.'.
    Symbol :. Type
  | -- | Optional attribute. Use ':?.'.
    Symbol :? Type

data StringWithoutContext

infix 0 :.

infix 0 :?

infix 0 ::.

infix 0 ::?

-- | 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 ':? b

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

-- | Required (@_.@) attribute name and type (@::_@)
--
-- Note that the type may still be nullable, but the attribute is expected to exist.
type a ::. b = a ':. b

-- | 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.
data PSObject (a :: Type) = PSObject
  { -- | Tracks the origin of the object, which is useful informaton for error messages.
    forall a. PSObject a -> Provenance
provenance :: Provenance,
    -- | 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'.
    forall a. PSObject a -> RawValue
value :: RawValue
  }

instance ToRawValue (PSObject a) where
  toRawValue :: Ptr EvalState -> PSObject a -> IO RawValue
toRawValue Ptr EvalState
_ = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. PSObject a -> RawValue
value

instance
  ( CheckType (NixTypeForSchema t),
    HasRawValueType (NixTypeForSchema t)
  ) =>
  ToValue (PSObject t)
  where
  type NixTypeFor (PSObject t) = NixTypeForSchema t
  toValue :: Ptr EvalState -> PSObject t -> IO (Value (NixTypeFor (PSObject t)))
toValue Ptr EvalState
es PSObject t
v = forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT (forall schema (m :: * -> *).
(CheckType (NixTypeForSchema schema),
 HasRawValueType (NixTypeForSchema schema), MonadEval m) =>
PSObject schema -> m (Value (NixTypeForSchema schema))
check PSObject t
v) Ptr EvalState
es

(.$) :: (MonadIO m) => PSObject (a ->. b) -> PSObject a -> m (PSObject b)
PSObject (a ->. b)
f .$ :: forall (m :: * -> *) a b.
MonadIO m =>
PSObject (a ->. b) -> PSObject a -> m (PSObject b)
.$ PSObject a
a = do
  RawValue
v <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (forall a. PSObject a -> RawValue
value PSObject (a ->. b)
f RawValue -> RawValue -> IO RawValue
`apply` forall a. PSObject a -> RawValue
value PSObject a
a)
  forall (f :: * -> *) a. Applicative f => a -> f a
pure
    PSObject
      { provenance :: Provenance
provenance = Provenance -> Provenance -> Provenance
Application (forall a. PSObject a -> Provenance
provenance PSObject (a ->. b)
f) (forall a. PSObject a -> Provenance
provenance PSObject a
a),
        value :: RawValue
value = RawValue
v
      }

type as . s = AttrType' as as s

type family AttrType' all as s where
  AttrType' all ((s ':. t) ': as) s = t
  AttrType' all ((s ':? t) ': as) s =
    TL.TypeError
      ( 'TL.Text "The attribute set field named " 'TL.:<>: 'TL.ShowType s 'TL.:<>: 'TL.Text " is optional."
          'TL.:$$: 'TL.Text "  Try the optional variation, e.g. (#?) instead of (#.)"
      )
  AttrType' all (_ ': as) s = AttrType' all as s
  AttrType' all '[] s =
    TL.TypeError
      ( 'TL.Text "Schema for attribute set does not declare a field named " 'TL.:<>: 'TL.ShowType s 'TL.:<>: 'TL.Text "."
          'TL.:$$: 'TL.Text "  Known attributes are " 'TL.:<>: 'TL.ShowType all
      )

type as ? s = OptionalAttrType' as as s

type family OptionalAttrType' all as s where
  OptionalAttrType' all ((s ':? t) ': as) s = t
  OptionalAttrType' all ((s ':. t) ': as) s =
    TL.TypeError
      ( 'TL.Text "The attribute set field named " 'TL.:<>: 'TL.ShowType s 'TL.:<>: 'TL.Text " is required, but you're asking for an optional field."
          'TL.:$$: 'TL.Text "  Try the required variation, e.g. (#.) instead of (#?)"
      )
  OptionalAttrType' all (_ ': as) s = OptionalAttrType' all as s
  OptionalAttrType' all '[] s =
    TL.TypeError
      ( 'TL.Text "Schema for attribute set does not declare a field named " 'TL.:<>: 'TL.ShowType s 'TL.:<>: 'TL.Text "."
          'TL.:$$: 'TL.Text "  Known attributes are " 'TL.:<>: 'TL.ShowType all
      )

-- | Like 'Proxy', but with an 'IsLabel' instance. For use with '(^#)'
data AttrLabel a = AttrLabel

instance (s ~ t) => IsLabel s (AttrLabel t) where
  fromLabel :: AttrLabel t
fromLabel = forall {k} (a :: k). AttrLabel a
AttrLabel

infixl 9 #.

infixl 9 >>.

type MonadEval m = (MonadIO m, MonadReader (Ptr EvalState) m)

-- | A combination of '>>=' and '#.'.
(>>.) :: (KnownSymbol s, as . s ~ b, MonadEval m) => m (PSObject (Attrs' as w)) -> AttrLabel s -> m (PSObject b)
m (PSObject (Attrs' as w))
mas >>. :: forall {k} (s :: Symbol) (as :: [Attr]) b (m :: * -> *) (w :: k).
(KnownSymbol s, (as . s) ~ b, MonadEval m) =>
m (PSObject (Attrs' as w)) -> AttrLabel s -> m (PSObject b)
>>. AttrLabel s
p = m (PSObject (Attrs' as w))
mas forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \PSObject (Attrs' as w)
as -> PSObject (Attrs' as w)
as forall {k} (s :: Symbol) (as :: [Attr]) b (m :: * -> *) (w :: k).
(KnownSymbol s, (as . s) ~ b, MonadEval m) =>
PSObject (Attrs' as w) -> AttrLabel s -> m (PSObject b)
#. AttrLabel s
p

-- | 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) => PSObject (Attrs' as w) -> AttrLabel s -> m (PSObject b)
PSObject (Attrs' as w)
as #. :: forall {k} (s :: Symbol) (as :: [Attr]) b (m :: * -> *) (w :: k).
(KnownSymbol s, (as . s) ~ b, MonadEval m) =>
PSObject (Attrs' as w) -> AttrLabel s -> m (PSObject b)
#. AttrLabel s
p = do
  Ptr EvalState
evalState <- forall r (m :: * -> *). MonadReader r m => m r
ask
  let name :: Text
name = [Char] -> Text
T.pack (forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> [Char]
symbolVal AttrLabel s
p)
  Value NixAttrs
v <- forall schema (m :: * -> *).
(CheckType (NixTypeForSchema schema),
 HasRawValueType (NixTypeForSchema schema), MonadEval m) =>
PSObject schema -> m (Value (NixTypeForSchema schema))
check PSObject (Attrs' as w)
as
  forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (Ptr EvalState
-> Value NixAttrs -> ByteString -> IO (Maybe RawValue)
getAttr Ptr EvalState
evalState Value NixAttrs
v (Text -> ByteString
encodeUtf8 Text
name)) forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
    Maybe RawValue
Nothing -> forall (m :: * -> *) e a. (MonadIO m, Exception e) => e -> m a
throwIO forall a b. (a -> b) -> a -> b
$ Provenance -> Text -> NixException
MissingAttribute (forall a. PSObject a -> Provenance
provenance PSObject (Attrs' as w)
as) Text
name
    Just RawValue
b -> forall (f :: * -> *) a. Applicative f => a -> f a
pure PSObject {value :: RawValue
value = RawValue
b, provenance :: Provenance
provenance = Provenance -> Text -> Provenance
Attribute (forall a. PSObject a -> Provenance
provenance PSObject (Attrs' as w)
as) Text
name}

-- | A combination of '>>=' and '#?'.
(>>?) :: (KnownSymbol s, as ? s ~ b, MonadEval m) => m (PSObject (Attrs' as w)) -> AttrLabel s -> m (Maybe (PSObject b))
m (PSObject (Attrs' as w))
mas >>? :: forall {k} (s :: Symbol) (as :: [Attr]) b (m :: * -> *) (w :: k).
(KnownSymbol s, (as ? s) ~ b, MonadEval m) =>
m (PSObject (Attrs' as w)) -> AttrLabel s -> m (Maybe (PSObject b))
>>? AttrLabel s
p = m (PSObject (Attrs' as w))
mas forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \PSObject (Attrs' as w)
as -> PSObject (Attrs' as w)
as forall {k} (s :: Symbol) (as :: [Attr]) b (m :: * -> *) (w :: k).
(KnownSymbol s, (as ? s) ~ b, MonadEval m) =>
PSObject (Attrs' as w) -> AttrLabel s -> m (Maybe (PSObject b))
#? AttrLabel s
p

-- | 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) => PSObject (Attrs' as w) -> AttrLabel s -> m (Maybe (PSObject b))
PSObject (Attrs' as w)
as #? :: forall {k} (s :: Symbol) (as :: [Attr]) b (m :: * -> *) (w :: k).
(KnownSymbol s, (as ? s) ~ b, MonadEval m) =>
PSObject (Attrs' as w) -> AttrLabel s -> m (Maybe (PSObject b))
#? AttrLabel s
p = do
  Ptr EvalState
evalState <- forall r (m :: * -> *). MonadReader r m => m r
ask
  let name :: Text
name = [Char] -> Text
T.pack (forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> [Char]
symbolVal AttrLabel s
p)
  Value NixAttrs
v <- forall schema (m :: * -> *).
(CheckType (NixTypeForSchema schema),
 HasRawValueType (NixTypeForSchema schema), MonadEval m) =>
PSObject schema -> m (Value (NixTypeForSchema schema))
check PSObject (Attrs' as w)
as
  forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (Ptr EvalState
-> Value NixAttrs -> ByteString -> IO (Maybe RawValue)
getAttr Ptr EvalState
evalState Value NixAttrs
v (Text -> ByteString
encodeUtf8 Text
name))
    forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\RawValue
b -> PSObject {value :: RawValue
value = RawValue
b, provenance :: Provenance
provenance = Provenance -> Text -> Provenance
Attribute (forall a. PSObject a -> Provenance
provenance PSObject (Attrs' as w)
as) Text
name})

-- | 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.
(#??) :: (KnownSymbol s, as ? s ~ (Null |. b), PossibleTypesForSchema b, MonadEval m) => PSObject (Attrs' as w) -> AttrLabel s -> m (Maybe (PSObject b))
PSObject (Attrs' as w)
as #?? :: forall {k} (s :: Symbol) (as :: [Attr]) b (m :: * -> *) (w :: k).
(KnownSymbol s, (as ? s) ~ (() |. b), PossibleTypesForSchema b,
 MonadEval m) =>
PSObject (Attrs' as w) -> AttrLabel s -> m (Maybe (PSObject b))
#?? AttrLabel s
p = do
  Maybe (PSObject (() |. b))
mv <- PSObject (Attrs' as w)
as forall {k} (s :: Symbol) (as :: [Attr]) b (m :: * -> *) (w :: k).
(KnownSymbol s, (as ? s) ~ b, MonadEval m) =>
PSObject (Attrs' as w) -> AttrLabel s -> m (Maybe (PSObject b))
#? AttrLabel s
p
  forall (m :: * -> *) a. Monad m => m (m a) -> m a
join forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
t a -> (a -> f b) -> f (t b)
for Maybe (PSObject (() |. b))
mv (forall a b. a -> b -> a
const (forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Maybe a
Nothing) 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
|! (forall (f :: * -> *) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Maybe a
Just))

-- | 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.
(#?!) :: (KnownSymbol s, as ? s ~ b, MonadEval m) => PSObject (Attrs' as w) -> AttrLabel s -> m (PSObject b)
PSObject (Attrs' as w)
as #?! :: forall {k} (s :: Symbol) (as :: [Attr]) b (m :: * -> *) (w :: k).
(KnownSymbol s, (as ? s) ~ b, MonadEval m) =>
PSObject (Attrs' as w) -> AttrLabel s -> m (PSObject b)
#?! AttrLabel s
p = do
  PSObject (Attrs' as w)
as forall {k} (s :: Symbol) (as :: [Attr]) b (m :: * -> *) (w :: k).
(KnownSymbol s, (as ? s) ~ b, MonadEval m) =>
PSObject (Attrs' as w) -> AttrLabel s -> m (Maybe (PSObject b))
#? AttrLabel s
p forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
    Maybe (PSObject b)
Nothing -> forall (m :: * -> *) e a. (MonadIO m, Exception e) => e -> m a
throwIO forall a b. (a -> b) -> a -> b
$ Provenance -> Text -> NixException
MissingAttribute (forall a. PSObject a -> Provenance
provenance PSObject (Attrs' as w)
as) ([Char] -> Text
T.pack (forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> [Char]
symbolVal AttrLabel s
p))
    Just PSObject b
x -> forall (f :: * -> *) a. Applicative f => a -> f a
pure PSObject b
x

lookupDictBS :: MonadEval m => ByteString -> PSObject (Attrs' as w) -> m (Maybe (PSObject w))
lookupDictBS :: forall (m :: * -> *) (as :: [Attr]) w.
MonadEval m =>
ByteString -> PSObject (Attrs' as w) -> m (Maybe (PSObject w))
lookupDictBS ByteString
name PSObject (Attrs' as w)
as = do
  Ptr EvalState
evalState <- forall r (m :: * -> *). MonadReader r m => m r
ask
  Value NixAttrs
v <- forall schema (m :: * -> *).
(CheckType (NixTypeForSchema schema),
 HasRawValueType (NixTypeForSchema schema), MonadEval m) =>
PSObject schema -> m (Value (NixTypeForSchema schema))
check PSObject (Attrs' as w)
as
  forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (Ptr EvalState
-> Value NixAttrs -> ByteString -> IO (Maybe RawValue)
getAttr Ptr EvalState
evalState Value NixAttrs
v ByteString
name)
    forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\RawValue
b -> PSObject {value :: RawValue
value = RawValue
b, provenance :: Provenance
provenance = Provenance -> Text -> Provenance
Attribute (forall a. PSObject a -> Provenance
provenance PSObject (Attrs' as w)
as) (OnDecodeError -> ByteString -> Text
decodeUtf8With OnDecodeError
lenientDecode ByteString
name)})

lookupDict :: MonadEval m => Text -> PSObject (Attrs' as w) -> m (Maybe (PSObject w))
lookupDict :: forall (m :: * -> *) (as :: [Attr]) w.
MonadEval m =>
Text -> PSObject (Attrs' as w) -> m (Maybe (PSObject w))
lookupDict Text
name PSObject (Attrs' as w)
as = do
  Ptr EvalState
evalState <- forall r (m :: * -> *). MonadReader r m => m r
ask
  Value NixAttrs
v <- forall schema (m :: * -> *).
(CheckType (NixTypeForSchema schema),
 HasRawValueType (NixTypeForSchema schema), MonadEval m) =>
PSObject schema -> m (Value (NixTypeForSchema schema))
check PSObject (Attrs' as w)
as
  forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (Ptr EvalState
-> Value NixAttrs -> ByteString -> IO (Maybe RawValue)
getAttr Ptr EvalState
evalState Value NixAttrs
v (Text -> ByteString
encodeUtf8 Text
name))
    forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\RawValue
b -> PSObject {value :: RawValue
value = RawValue
b, provenance :: Provenance
provenance = Provenance -> Text -> Provenance
Attribute (forall a. PSObject a -> Provenance
provenance PSObject (Attrs' as w)
as) Text
name})

-- | Like '#?!'. Throws an acceptable but not great error message.
requireDictBS :: MonadEval m => ByteString -> PSObject (Attrs' as w) -> m (PSObject w)
requireDictBS :: forall (m :: * -> *) (as :: [Attr]) w.
MonadEval m =>
ByteString -> PSObject (Attrs' as w) -> m (PSObject w)
requireDictBS ByteString
name PSObject (Attrs' as w)
as = do
  forall (m :: * -> *) (as :: [Attr]) w.
MonadEval m =>
ByteString -> PSObject (Attrs' as w) -> m (Maybe (PSObject w))
lookupDictBS ByteString
name PSObject (Attrs' as w)
as forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
    Maybe (PSObject w)
Nothing -> forall (m :: * -> *) e a. (MonadIO m, Exception e) => e -> m a
throwIO forall a b. (a -> b) -> a -> b
$ Provenance -> Text -> NixException
MissingAttribute (forall a. PSObject a -> Provenance
provenance PSObject (Attrs' as w)
as) (OnDecodeError -> ByteString -> Text
decodeUtf8With OnDecodeError
lenientDecode ByteString
name)
    Just PSObject w
r -> forall (f :: * -> *) a. Applicative f => a -> f a
pure PSObject w
r

-- | Like '#?!'. Throws an acceptable but not great error message.
requireDict :: MonadEval m => Text -> PSObject (Attrs' as w) -> m (PSObject w)
requireDict :: forall (m :: * -> *) (as :: [Attr]) w.
MonadEval m =>
Text -> PSObject (Attrs' as w) -> m (PSObject w)
requireDict Text
name PSObject (Attrs' as w)
as = do
  forall (m :: * -> *) (as :: [Attr]) w.
MonadEval m =>
Text -> PSObject (Attrs' as w) -> m (Maybe (PSObject w))
lookupDict Text
name PSObject (Attrs' as w)
as forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
    Maybe (PSObject w)
Nothing -> forall (m :: * -> *) e a. (MonadIO m, Exception e) => e -> m a
throwIO forall a b. (a -> b) -> a -> b
$ Provenance -> Text -> NixException
MissingAttribute (forall a. PSObject a -> Provenance
provenance PSObject (Attrs' as w)
as) Text
name
    Just PSObject w
r -> forall (f :: * -> *) a. Applicative f => a -> f a
pure PSObject w
r

dictionaryToMap :: MonadEval m => PSObject (Dictionary w) -> m (Map ByteString (PSObject w))
dictionaryToMap :: forall (m :: * -> *) w.
MonadEval m =>
PSObject (Dictionary w) -> m (Map ByteString (PSObject w))
dictionaryToMap PSObject (Dictionary w)
dict = do
  Ptr EvalState
es <- forall r (m :: * -> *). MonadReader r m => m r
ask
  (forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr EvalState -> Value NixAttrs -> IO (Map ByteString RawValue)
Expr.getAttrs Ptr EvalState
es forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall schema (m :: * -> *).
(CheckType (NixTypeForSchema schema),
 HasRawValueType (NixTypeForSchema schema), MonadEval m) =>
PSObject schema -> m (Value (NixTypeForSchema schema))
check PSObject (Dictionary w)
dict)
    forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> forall k a b. (k -> a -> b) -> Map k a -> Map k b
M.mapWithKey
      ( \ByteString
name RawValue
b ->
          PSObject {value :: RawValue
value = RawValue
b, provenance :: Provenance
provenance = Provenance -> Text -> Provenance
Attribute (forall a. PSObject a -> Provenance
provenance PSObject (Dictionary w)
dict) (OnDecodeError -> ByteString -> Text
decodeUtf8With OnDecodeError
lenientDecode ByteString
name)}
      )

type family NixTypeForSchema s where
  NixTypeForSchema (Attrs' _ _) = NixAttrs
  NixTypeForSchema (_ ->. _) = NixFunction
  NixTypeForSchema NixString = NixString
  NixTypeForSchema StringWithoutContext = NixString
  NixTypeForSchema NixPath = NixPath
  NixTypeForSchema Bool = Bool
  NixTypeForSchema Int64 = Int64
  NixTypeForSchema [a] = NixList
  NixTypeForSchema () = ()

class PossibleTypesForSchema s where
  typesForSchema :: Proxy s -> [RawValueType]
  default typesForSchema :: HasRawValueType (NixTypeForSchema s) => Proxy s -> [RawValueType]
  typesForSchema Proxy s
_ = [forall s. HasRawValueType s => Proxy s -> RawValueType
getRawValueType (forall {k} (t :: k). Proxy t
Proxy @(NixTypeForSchema s))]

instance PossibleTypesForSchema (Attrs' as w)

instance PossibleTypesForSchema (a ->. b)

instance PossibleTypesForSchema NixString

instance PossibleTypesForSchema NixPath

instance PossibleTypesForSchema Bool

instance PossibleTypesForSchema Int64

instance PossibleTypesForSchema ()

instance PossibleTypesForSchema [a] where
  typesForSchema :: Proxy [a] -> [RawValueType]
typesForSchema Proxy [a]
_ = [forall s. HasRawValueType s => Proxy s -> RawValueType
getRawValueType (forall {k} (t :: k). Proxy t
Proxy @NixList)]

instance
  (PossibleTypesForSchema a, PossibleTypesForSchema b) =>
  PossibleTypesForSchema (a |. b)
  where
  typesForSchema :: Proxy (a |. b) -> [RawValueType]
typesForSchema Proxy (a |. b)
_ = forall s. PossibleTypesForSchema s => Proxy s -> [RawValueType]
typesForSchema (forall {k} (t :: k). Proxy t
Proxy @a) forall a. Semigroup a => a -> a -> a
<> forall s. PossibleTypesForSchema s => Proxy s -> [RawValueType]
typesForSchema (forall {k} (t :: k). Proxy t
Proxy @b)

-- | Force and check type, then continue without backtracking
(|!) ::
  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
PSObject a -> m c
f |! :: 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
|! PSObject b -> m c
g = \PSObject (a |. b)
ab -> do
  Ptr EvalState
evalState <- forall r (m :: * -> *). MonadReader r m => m r
ask
  Maybe (Value (NixTypeForSchema a))
t <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall a.
CheckType a =>
Ptr EvalState -> RawValue -> IO (Maybe (Value a))
checkType @(NixTypeForSchema a) Ptr EvalState
evalState (forall a. PSObject a -> RawValue
value PSObject (a |. b)
ab)
  RawValueType
rawType <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ RawValue -> IO RawValueType
rawValueType (forall a. PSObject a -> RawValue
value PSObject (a |. b)
ab)
  let c :: RawValueType
c = RawValueType -> RawValueType
canonicalRawType RawValueType
rawType
      -- This call makes it O(n*n) because of the nested |! calls, but n is small.
      ts :: [RawValueType]
ts = forall s. PossibleTypesForSchema s => Proxy s -> [RawValueType]
typesForSchema (forall {k} (t :: k). Proxy t
Proxy @(a |. b))
  forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (RawValueType
c forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [RawValueType]
ts) do
    forall (m :: * -> *) e a. (MonadIO m, Exception e) => e -> m a
throwIO forall a b. (a -> b) -> a -> b
$ Provenance -> RawValueType -> [RawValueType] -> NixException
TypeError (forall a. PSObject a -> Provenance
provenance PSObject (a |. b)
ab) RawValueType
c [RawValueType]
ts
  case Maybe (Value (NixTypeForSchema a))
t of
    Just Value (NixTypeForSchema a)
_abChecked -> PSObject a -> m c
f (PSObject (a |. b)
ab {value :: RawValue
value = forall a. PSObject a -> RawValue
value PSObject (a |. b)
ab})
    Maybe (Value (NixTypeForSchema a))
Nothing -> PSObject b -> m c
g (PSObject (a |. b)
ab {value :: RawValue
value = forall a. PSObject a -> RawValue
value PSObject (a |. b)
ab})

englishOr :: [Text] -> Text
englishOr :: [Text] -> Text
englishOr [] = Text
"impossible"
englishOr [Text
a] = Text
a
englishOr [Text
y, Text
z] = Text
y forall a. Semigroup a => a -> a -> a
<> Text
" or " forall a. Semigroup a => a -> a -> a
<> Text
z
englishOr (Text
a : [Text]
as) = Text
a forall a. Semigroup a => a -> a -> a
<> Text
", " forall a. Semigroup a => a -> a -> a
<> [Text] -> Text
englishOr [Text]
as

-- | Optional application.
($?) :: (MonadEval m, PossibleTypesForSchema a, PossibleTypesForSchema b) => PSObject (a ->? b) -> PSObject a -> m (PSObject b)
PSObject (a ->? b)
x $? :: forall (m :: * -> *) a b.
(MonadEval m, PossibleTypesForSchema a,
 PossibleTypesForSchema b) =>
PSObject (a ->? b) -> PSObject a -> m (PSObject b)
$? PSObject a
a =
  forall (f :: * -> *) a. Applicative f => a -> f a
pure PSObject (a ->? b)
x forall (m :: * -> *) a b.
(MonadEval m, PossibleTypesForSchema a,
 PossibleTypesForSchema b) =>
m (PSObject (a ->? b)) -> m (PSObject a) -> m (PSObject b)
>>$? forall (f :: * -> *) a. Applicative f => a -> f a
pure PSObject a
a

-- | Optional application. Like '$?' but takes care of monadic binding as a convenience.
(>>$?) :: (MonadEval m, PossibleTypesForSchema a, PossibleTypesForSchema b) => m (PSObject (a ->? b)) -> m (PSObject a) -> m (PSObject b)
m (PSObject (a ->? b))
x >>$? :: forall (m :: * -> *) a b.
(MonadEval m, PossibleTypesForSchema a,
 PossibleTypesForSchema b) =>
m (PSObject (a ->? b)) -> m (PSObject a) -> m (PSObject b)
>>$? m (PSObject a)
a =
  ( (\PSObject (a ->. b)
f -> m (PSObject a)
a forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (PSObject (a ->. b)
f forall (m :: * -> *) a b.
MonadIO m =>
PSObject (a ->. b) -> PSObject a -> m (PSObject b)
.$))
      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
|! forall (f :: * -> *) a. Applicative f => a -> f a
pure
  )
    forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< m (PSObject (a ->? b))
x

-- | Application. Like '$.' but takes care of monadic binding as a convenience.
(>>$.) :: (MonadEval m, PossibleTypesForSchema a, PossibleTypesForSchema b) => m (PSObject (a ->. b)) -> m (PSObject a) -> m (PSObject b)
m (PSObject (a ->. b))
f >>$. :: forall (m :: * -> *) a b.
(MonadEval m, PossibleTypesForSchema a,
 PossibleTypesForSchema b) =>
m (PSObject (a ->. b)) -> m (PSObject a) -> m (PSObject b)
>>$. m (PSObject a)
a = do
  PSObject (a ->. b)
f' <- m (PSObject (a ->. b))
f
  PSObject a
a' <- m (PSObject a)
a
  PSObject (a ->. b)
f' forall (m :: * -> *) a b.
MonadIO m =>
PSObject (a ->. b) -> PSObject a -> m (PSObject b)
.$ PSObject a
a'

-- | Parses an expression from string
exprWithBasePath ::
  forall schema m.
  (MonadEval m) =>
  -- | Expression text in the Nix language.
  Text ->
  -- | Base path for relative path references in the expression text.
  FilePath ->
  -- | A schema that the expression should satisfy.
  Proxy schema ->
  m (PSObject schema)
exprWithBasePath :: forall schema (m :: * -> *).
MonadEval m =>
Text -> [Char] -> Proxy schema -> m (PSObject schema)
exprWithBasePath Text
expr = forall schema (m :: * -> *).
MonadEval m =>
ByteString -> [Char] -> Proxy schema -> m (PSObject schema)
exprWithBasePathBS (Text -> ByteString
encodeUtf8 Text
expr)

-- | Parses an expression from string
exprWithBasePathBS ::
  forall schema m.
  (MonadEval m) =>
  -- | Expression text in the Nix language.
  ByteString ->
  -- | Base path for relative path references in the expression text.
  FilePath ->
  -- | A schema that the expression should satisfy.
  Proxy schema ->
  m (PSObject schema)
exprWithBasePathBS :: forall schema (m :: * -> *).
MonadEval m =>
ByteString -> [Char] -> Proxy schema -> m (PSObject schema)
exprWithBasePathBS ByteString
expr [Char]
path Proxy schema
_ = do
  Ptr EvalState
evalState <- forall r (m :: * -> *). MonadReader r m => m r
ask
  RawValue
v <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (Ptr EvalState -> ByteString -> ByteString -> IO RawValue
valueFromExpressionString Ptr EvalState
evalState ByteString
expr (Text -> ByteString
encodeUtf8 (forall a b. ConvertText a b => a -> b
toS [Char]
path)))
  forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ PSObject {provenance :: Provenance
provenance = Text -> Provenance
Other Text
"internal expression", value :: RawValue
value = RawValue
v}

-- | Ignores string context.
getByteString_ ::
  (MonadEval m) =>
  PSObject NixString ->
  m ByteString
getByteString_ :: forall (m :: * -> *).
MonadEval m =>
PSObject NixString -> m ByteString
getByteString_ PSObject NixString
s = do
  forall schema (m :: * -> *).
(CheckType (NixTypeForSchema schema),
 HasRawValueType (NixTypeForSchema schema), MonadEval m) =>
PSObject schema -> m (Value (NixTypeForSchema schema))
check PSObject NixString
s forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value NixString -> IO ByteString
Expr.getStringIgnoreContext

-- | Ignores string context.
getText_ ::
  (MonadEval m) =>
  PSObject NixString ->
  m Text
getText_ :: forall (m :: * -> *). MonadEval m => PSObject NixString -> m Text
getText_ = forall (m :: * -> *) s a e b.
MonadIO m =>
(PSObject s -> m a)
-> (a -> Either e b)
-> (Provenance -> e -> NixException)
-> PSObject s
-> m b
validateE forall (m :: * -> *).
MonadEval m =>
PSObject NixString -> m ByteString
getByteString_ ByteString -> Either UnicodeException Text
decodeUtf8' Provenance -> UnicodeException -> NixException
InvalidText

validate :: Monad m => (PSObject s -> m a) -> (Provenance -> a -> m b) -> PSObject s -> m b
validate :: forall (m :: * -> *) s a b.
Monad m =>
(PSObject s -> m a)
-> (Provenance -> a -> m b) -> PSObject s -> m b
validate PSObject s -> m a
basicParse Provenance -> a -> m b
validator PSObject s
o = do
  a
a <- PSObject s -> m a
basicParse PSObject s
o
  Provenance -> a -> m b
validator (forall a. PSObject a -> Provenance
provenance PSObject s
o) a
a

validateE :: MonadIO m => (PSObject s -> m a) -> (a -> Either e b) -> (Provenance -> e -> NixException) -> PSObject s -> m b
validateE :: forall (m :: * -> *) s a e b.
MonadIO m =>
(PSObject s -> m a)
-> (a -> Either e b)
-> (Provenance -> e -> NixException)
-> PSObject s
-> m b
validateE PSObject s -> m a
basicParse a -> Either e b
validator Provenance -> e -> NixException
thrower =
  forall (m :: * -> *) s a b.
Monad m =>
(PSObject s -> m a)
-> (Provenance -> a -> m b) -> PSObject s -> m b
validate PSObject s -> m a
basicParse \Provenance
prov a
a ->
    case a -> Either e b
validator a
a of
      (Left e
e) -> forall (m :: * -> *) e a. (MonadIO m, Exception e) => e -> m a
throwIO (Provenance -> e -> NixException
thrower Provenance
prov e
e)
      (Right b
b) -> forall (f :: * -> *) a. Applicative f => a -> f a
pure b
b

-- | Force a value and check against schema.
check ::
  forall schema m.
  ( CheckType (NixTypeForSchema schema),
    HasRawValueType (NixTypeForSchema schema),
    MonadEval m
  ) =>
  PSObject schema ->
  m (Value (NixTypeForSchema schema))
check :: forall schema (m :: * -> *).
(CheckType (NixTypeForSchema schema),
 HasRawValueType (NixTypeForSchema schema), MonadEval m) =>
PSObject schema -> m (Value (NixTypeForSchema schema))
check PSObject schema
pv = do
  Ptr EvalState
evalState <- forall r (m :: * -> *). MonadReader r m => m r
ask
  forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
    forall a.
CheckType a =>
Ptr EvalState -> RawValue -> IO (Maybe (Value a))
checkType Ptr EvalState
evalState (forall a. PSObject a -> RawValue
value PSObject schema
pv) forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
      Maybe (Value (NixTypeForSchema schema))
Nothing -> do
        RawValueType
t <- RawValue -> IO RawValueType
rawValueType (forall a. PSObject a -> RawValue
value PSObject schema
pv)
        forall (m :: * -> *) e a. (MonadIO m, Exception e) => e -> m a
throwIO forall a b. (a -> b) -> a -> b
$ Provenance -> RawValueType -> [RawValueType] -> NixException
TypeError (forall a. PSObject a -> Provenance
provenance PSObject schema
pv) RawValueType
t [forall s. HasRawValueType s => Proxy s -> RawValueType
getRawValueType (forall {k} (t :: k). Proxy t
Proxy @(NixTypeForSchema schema))]
      Just Value (NixTypeForSchema schema)
x -> forall (f :: * -> *) a. Applicative f => a -> f a
pure Value (NixTypeForSchema schema)
x

-- TODO make this actually schema-based
toPSObject ::
  (MonadEval m, Expr.ToRawValue a) =>
  a ->
  m (PSObject (Expr.NixTypeFor a))
toPSObject :: forall (m :: * -> *) a.
(MonadEval m, ToRawValue a) =>
a -> m (PSObject (NixTypeFor a))
toPSObject a
a = do
  Ptr EvalState
evalState <- forall r (m :: * -> *). MonadReader r m => m r
ask
  RawValue
v <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (forall a. ToRawValue a => Ptr EvalState -> a -> IO RawValue
toRawValue Ptr EvalState
evalState a
a)
  forall (f :: * -> *) a. Applicative f => a -> f a
pure (PSObject {provenance :: Provenance
provenance = Provenance
Data, value :: RawValue
value = RawValue
v})

uncheckedCast :: forall (a :: Type) (b :: Type). PSObject a -> PSObject b
uncheckedCast :: forall a b. PSObject a -> PSObject b
uncheckedCast = coerce :: forall a b. Coercible a b => a -> b
coerce

-- | Schema-based parsing type class that constrains neither types nor schemas.
class FromPSObject schema a where
  -- | Parse an object assumed to be in schema @schema@ into a value of type @a@
  -- or throw a 'NixException'.
  fromPSObject :: MonadEval m => PSObject schema -> m a

instance FromPSObject StringWithoutContext ByteString where
  fromPSObject :: forall (m :: * -> *).
MonadEval m =>
PSObject StringWithoutContext -> m ByteString
fromPSObject PSObject StringWithoutContext
o = do
    Value NixString
v <- forall schema (m :: * -> *).
(CheckType (NixTypeForSchema schema),
 HasRawValueType (NixTypeForSchema schema), MonadEval m) =>
PSObject schema -> m (Value (NixTypeForSchema schema))
check PSObject StringWithoutContext
o
    forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
      Bool
c <- Value NixString -> IO Bool
hasContext Value NixString
v
      forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
c do
        forall (m :: * -> *) e a. (MonadIO m, Exception e) => e -> m a
throwIO forall a b. (a -> b) -> a -> b
$ Provenance -> NixException
StringContextNotAllowed (forall a. PSObject a -> Provenance
provenance PSObject StringWithoutContext
o)
    forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ Value NixString -> IO ByteString
getStringIgnoreContext Value NixString
v

instance FromPSObject StringWithoutContext Text where
  fromPSObject :: forall (m :: * -> *).
MonadEval m =>
PSObject StringWithoutContext -> m Text
fromPSObject = forall (m :: * -> *) s a e b.
MonadIO m =>
(PSObject s -> m a)
-> (a -> Either e b)
-> (Provenance -> e -> NixException)
-> PSObject s
-> m b
validateE forall schema a (m :: * -> *).
(FromPSObject schema a, MonadEval m) =>
PSObject schema -> m a
fromPSObject ByteString -> Either UnicodeException Text
decodeUtf8' Provenance -> UnicodeException -> NixException
InvalidText

instance FromPSObject StringWithoutContext [Char] where
  fromPSObject :: forall (m :: * -> *).
MonadEval m =>
PSObject StringWithoutContext -> m [Char]
fromPSObject = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> [Char]
T.unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall schema a (m :: * -> *).
(FromPSObject schema a, MonadEval m) =>
PSObject schema -> m a
fromPSObject

instance FromPSObject Bool Bool where
  fromPSObject :: forall (m :: * -> *). MonadEval m => PSObject Bool -> m Bool
fromPSObject PSObject Bool
o = do
    Value Bool
v <- forall schema (m :: * -> *).
(CheckType (NixTypeForSchema schema),
 HasRawValueType (NixTypeForSchema schema), MonadEval m) =>
PSObject schema -> m (Value (NixTypeForSchema schema))
check PSObject Bool
o
    forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (Value Bool -> IO Bool
Expr.getBool Value Bool
v)

basicAttrsWithProvenance :: Value NixAttrs -> Provenance -> PSObject (Attrs '[])
basicAttrsWithProvenance :: Value NixAttrs -> Provenance -> PSObject (Attrs '[])
basicAttrsWithProvenance Value NixAttrs
attrs Provenance
p = PSObject {value :: RawValue
value = forall a. Value a -> RawValue
rtValue Value NixAttrs
attrs, provenance :: Provenance
provenance = Provenance
p}

instance FromPSObject Int64 Int64 where
  fromPSObject :: forall (m :: * -> *). MonadEval m => PSObject Int64 -> m Int64
fromPSObject PSObject Int64
o = do
    Value Int64
v <- forall schema (m :: * -> *).
(CheckType (NixTypeForSchema schema),
 HasRawValueType (NixTypeForSchema schema), MonadEval m) =>
PSObject schema -> m (Value (NixTypeForSchema schema))
check PSObject Int64
o
    forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (forall n a. FromValue n a => Value n -> IO a
Expr.fromValue Value Int64
v)

instance forall a b. FromPSObject a b => FromPSObject [a] [b] where
  fromPSObject :: forall (m :: * -> *). MonadEval m => PSObject [a] -> m [b]
fromPSObject PSObject [a]
o = do
    forall (m :: * -> *) a b.
MonadEval m =>
(PSObject a -> m b) -> PSObject [a] -> m [b]
traverseArray forall schema a (m :: * -> *).
(FromPSObject schema a, MonadEval m) =>
PSObject schema -> m a
fromPSObject PSObject [a]
o

traverseArray :: (MonadEval m) => (PSObject a -> m b) -> PSObject [a] -> m [b]
traverseArray :: forall (m :: * -> *) a b.
MonadEval m =>
(PSObject a -> m b) -> PSObject [a] -> m [b]
traverseArray PSObject a -> m b
f PSObject [a]
o = do
  Value NixList
ov <- forall schema (m :: * -> *).
(CheckType (NixTypeForSchema schema),
 HasRawValueType (NixTypeForSchema schema), MonadEval m) =>
PSObject schema -> m (Value (NixTypeForSchema schema))
check PSObject [a]
o
  [RawValue]
l <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (forall n a. FromValue n a => Value n -> IO a
Expr.fromValue Value NixList
ov)
  [RawValue]
l forall a b. a -> (a -> b) -> b
& forall a b. [a] -> [b] -> [(a, b)]
zip [Int
0 ..] forall a b. a -> (a -> b) -> b
& forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse \(Int
i, RawValue
a) ->
    PSObject a -> m b
f (forall a. Provenance -> RawValue -> PSObject a
PSObject (Provenance -> Int -> Provenance
ListItem (forall a. PSObject a -> Provenance
provenance PSObject [a]
o) Int
i) RawValue
a :: PSObject a)