{-# LANGUAGE ApplicativeDo #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
module Dhall
(
input
, inputWithSettings
, inputFile
, inputFileWithSettings
, inputExpr
, inputExprWithSettings
, interpretExpr
, interpretExprWithSettings
, fromExpr
, fromExprWithSettings
, rootDirectory
, sourceName
, startingContext
, substitutions
, normalizer
, newManager
, defaultInputSettings
, InputSettings
, defaultEvaluateSettings
, EvaluateSettings
, HasEvaluateSettings(..)
, detailed
, module Dhall.Marshal.Decode
, module Dhall.Marshal.Encode
, parseWithSettings
, resolveWithSettings
, resolveAndStatusWithSettings
, typecheckWithSettings
, checkWithSettings
, expectWithSettings
, normalizeWithSettings
, rawInput
) where
import Control.Applicative (Alternative, empty)
import Control.Monad.Catch (MonadThrow, throwM)
import Data.Either.Validation (Validation (..))
import Data.Void (Void)
import Dhall.Import (Imported (..), Status)
import Dhall.Parser (Src (..))
import Dhall.Syntax (Expr (..), Import)
import Dhall.TypeCheck (DetailedTypeError (..), TypeError)
import GHC.Generics
import Lens.Family (LensLike', view)
import Prelude hiding (maybe, sequence)
import System.FilePath (takeDirectory)
import qualified Control.Exception
import qualified Control.Monad.Trans.State.Strict as State
import qualified Data.Text.IO
import qualified Dhall.Context
import qualified Dhall.Core as Core
import qualified Dhall.Import
import qualified Dhall.Parser
import qualified Dhall.Pretty.Internal
import qualified Dhall.Substitution
import qualified Dhall.TypeCheck
import qualified Lens.Family
import Dhall.Marshal.Decode
import Dhall.Marshal.Encode
data InputSettings = InputSettings
{ InputSettings -> FilePath
_rootDirectory :: FilePath
, InputSettings -> FilePath
_sourceName :: FilePath
, InputSettings -> EvaluateSettings
_evaluateSettings :: EvaluateSettings
}
defaultInputSettings :: InputSettings
defaultInputSettings :: InputSettings
defaultInputSettings = InputSettings
{ _rootDirectory :: FilePath
_rootDirectory = FilePath
"."
, _sourceName :: FilePath
_sourceName = FilePath
"(input)"
, _evaluateSettings :: EvaluateSettings
_evaluateSettings = EvaluateSettings
defaultEvaluateSettings
}
rootDirectory
:: (Functor f)
=> LensLike' f InputSettings FilePath
rootDirectory :: forall (f :: * -> *).
Functor f =>
LensLike' f InputSettings FilePath
rootDirectory FilePath -> f FilePath
k InputSettings
s =
(FilePath -> InputSettings) -> f FilePath -> f InputSettings
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\FilePath
x -> InputSettings
s { _rootDirectory = x }) (FilePath -> f FilePath
k (InputSettings -> FilePath
_rootDirectory InputSettings
s))
sourceName
:: (Functor f)
=> LensLike' f InputSettings FilePath
sourceName :: forall (f :: * -> *).
Functor f =>
LensLike' f InputSettings FilePath
sourceName FilePath -> f FilePath
k InputSettings
s =
(FilePath -> InputSettings) -> f FilePath -> f InputSettings
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\FilePath
x -> InputSettings
s { _sourceName = x}) (FilePath -> f FilePath
k (InputSettings -> FilePath
_sourceName InputSettings
s))
data EvaluateSettings = EvaluateSettings
{ EvaluateSettings -> Substitutions Src Void
_substitutions :: Dhall.Substitution.Substitutions Src Void
, EvaluateSettings -> Context (Expr Src Void)
_startingContext :: Dhall.Context.Context (Expr Src Void)
, EvaluateSettings -> Maybe (ReifiedNormalizer Void)
_normalizer :: Maybe (Core.ReifiedNormalizer Void)
, EvaluateSettings -> IO Manager
_newManager :: IO Dhall.Import.Manager
}
defaultEvaluateSettings :: EvaluateSettings
defaultEvaluateSettings :: EvaluateSettings
defaultEvaluateSettings = EvaluateSettings
{ _substitutions :: Substitutions Src Void
_substitutions = Substitutions Src Void
forall s a. Substitutions s a
Dhall.Substitution.empty
, _startingContext :: Context (Expr Src Void)
_startingContext = Context (Expr Src Void)
forall a. Context a
Dhall.Context.empty
, _normalizer :: Maybe (ReifiedNormalizer Void)
_normalizer = Maybe (ReifiedNormalizer Void)
forall a. Maybe a
Nothing
, _newManager :: IO Manager
_newManager = IO Manager
Dhall.Import.defaultNewManager
}
startingContext
:: (Functor f, HasEvaluateSettings s)
=> LensLike' f s (Dhall.Context.Context (Expr Src Void))
startingContext :: forall (f :: * -> *) s.
(Functor f, HasEvaluateSettings s) =>
LensLike' f s (Context (Expr Src Void))
startingContext = LensLike' f s EvaluateSettings
forall s (f :: * -> *).
(HasEvaluateSettings s, Functor f) =>
LensLike' f s EvaluateSettings
forall (f :: * -> *). Functor f => LensLike' f s EvaluateSettings
evaluateSettings LensLike' f s EvaluateSettings
-> ((Context (Expr Src Void) -> f (Context (Expr Src Void)))
-> EvaluateSettings -> f EvaluateSettings)
-> (Context (Expr Src Void) -> f (Context (Expr Src Void)))
-> s
-> f s
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Context (Expr Src Void) -> f (Context (Expr Src Void)))
-> EvaluateSettings -> f EvaluateSettings
forall (f :: * -> *).
Functor f =>
LensLike' f EvaluateSettings (Context (Expr Src Void))
l
where
l :: (Functor f)
=> LensLike' f EvaluateSettings (Dhall.Context.Context (Expr Src Void))
l :: forall (f :: * -> *).
Functor f =>
LensLike' f EvaluateSettings (Context (Expr Src Void))
l Context (Expr Src Void) -> f (Context (Expr Src Void))
k EvaluateSettings
s = (Context (Expr Src Void) -> EvaluateSettings)
-> f (Context (Expr Src Void)) -> f EvaluateSettings
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Context (Expr Src Void)
x -> EvaluateSettings
s { _startingContext = x}) (Context (Expr Src Void) -> f (Context (Expr Src Void))
k (EvaluateSettings -> Context (Expr Src Void)
_startingContext EvaluateSettings
s))
substitutions
:: (Functor f, HasEvaluateSettings s)
=> LensLike' f s (Dhall.Substitution.Substitutions Src Void)
substitutions :: forall (f :: * -> *) s.
(Functor f, HasEvaluateSettings s) =>
LensLike' f s (Substitutions Src Void)
substitutions = LensLike' f s EvaluateSettings
forall s (f :: * -> *).
(HasEvaluateSettings s, Functor f) =>
LensLike' f s EvaluateSettings
forall (f :: * -> *). Functor f => LensLike' f s EvaluateSettings
evaluateSettings LensLike' f s EvaluateSettings
-> ((Substitutions Src Void -> f (Substitutions Src Void))
-> EvaluateSettings -> f EvaluateSettings)
-> (Substitutions Src Void -> f (Substitutions Src Void))
-> s
-> f s
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Substitutions Src Void -> f (Substitutions Src Void))
-> EvaluateSettings -> f EvaluateSettings
forall (f :: * -> *).
Functor f =>
LensLike' f EvaluateSettings (Substitutions Src Void)
l
where
l :: (Functor f)
=> LensLike' f EvaluateSettings (Dhall.Substitution.Substitutions Src Void)
l :: forall (f :: * -> *).
Functor f =>
LensLike' f EvaluateSettings (Substitutions Src Void)
l Substitutions Src Void -> f (Substitutions Src Void)
k EvaluateSettings
s = (Substitutions Src Void -> EvaluateSettings)
-> f (Substitutions Src Void) -> f EvaluateSettings
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Substitutions Src Void
x -> EvaluateSettings
s { _substitutions = x }) (Substitutions Src Void -> f (Substitutions Src Void)
k (EvaluateSettings -> Substitutions Src Void
_substitutions EvaluateSettings
s))
normalizer
:: (Functor f, HasEvaluateSettings s)
=> LensLike' f s (Maybe (Core.ReifiedNormalizer Void))
normalizer :: forall (f :: * -> *) s.
(Functor f, HasEvaluateSettings s) =>
LensLike' f s (Maybe (ReifiedNormalizer Void))
normalizer = LensLike' f s EvaluateSettings
forall s (f :: * -> *).
(HasEvaluateSettings s, Functor f) =>
LensLike' f s EvaluateSettings
forall (f :: * -> *). Functor f => LensLike' f s EvaluateSettings
evaluateSettings LensLike' f s EvaluateSettings
-> ((Maybe (ReifiedNormalizer Void)
-> f (Maybe (ReifiedNormalizer Void)))
-> EvaluateSettings -> f EvaluateSettings)
-> (Maybe (ReifiedNormalizer Void)
-> f (Maybe (ReifiedNormalizer Void)))
-> s
-> f s
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe (ReifiedNormalizer Void)
-> f (Maybe (ReifiedNormalizer Void)))
-> EvaluateSettings -> f EvaluateSettings
forall (f :: * -> *).
Functor f =>
LensLike' f EvaluateSettings (Maybe (ReifiedNormalizer Void))
l
where
l :: (Functor f)
=> LensLike' f EvaluateSettings (Maybe (Core.ReifiedNormalizer Void))
l :: forall (f :: * -> *).
Functor f =>
LensLike' f EvaluateSettings (Maybe (ReifiedNormalizer Void))
l Maybe (ReifiedNormalizer Void)
-> f (Maybe (ReifiedNormalizer Void))
k EvaluateSettings
s = (Maybe (ReifiedNormalizer Void) -> EvaluateSettings)
-> f (Maybe (ReifiedNormalizer Void)) -> f EvaluateSettings
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Maybe (ReifiedNormalizer Void)
x -> EvaluateSettings
s { _normalizer = x }) (Maybe (ReifiedNormalizer Void)
-> f (Maybe (ReifiedNormalizer Void))
k (EvaluateSettings -> Maybe (ReifiedNormalizer Void)
_normalizer EvaluateSettings
s))
newManager
:: (Functor f, HasEvaluateSettings s)
=> LensLike' f s (IO Dhall.Import.Manager)
newManager :: forall (f :: * -> *) s.
(Functor f, HasEvaluateSettings s) =>
LensLike' f s (IO Manager)
newManager = LensLike' f s EvaluateSettings
forall s (f :: * -> *).
(HasEvaluateSettings s, Functor f) =>
LensLike' f s EvaluateSettings
forall (f :: * -> *). Functor f => LensLike' f s EvaluateSettings
evaluateSettings LensLike' f s EvaluateSettings
-> ((IO Manager -> f (IO Manager))
-> EvaluateSettings -> f EvaluateSettings)
-> (IO Manager -> f (IO Manager))
-> s
-> f s
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (IO Manager -> f (IO Manager))
-> EvaluateSettings -> f EvaluateSettings
forall (f :: * -> *).
Functor f =>
LensLike' f EvaluateSettings (IO Manager)
l
where
l :: (Functor f)
=> LensLike' f EvaluateSettings (IO Dhall.Import.Manager)
l :: forall (f :: * -> *).
Functor f =>
LensLike' f EvaluateSettings (IO Manager)
l IO Manager -> f (IO Manager)
k EvaluateSettings
s = (IO Manager -> EvaluateSettings)
-> f (IO Manager) -> f EvaluateSettings
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\IO Manager
x -> EvaluateSettings
s { _newManager = x }) (IO Manager -> f (IO Manager)
k (EvaluateSettings -> IO Manager
_newManager EvaluateSettings
s))
class HasEvaluateSettings s where
evaluateSettings
:: (Functor f)
=> LensLike' f s EvaluateSettings
instance HasEvaluateSettings InputSettings where
evaluateSettings :: forall (f :: * -> *).
Functor f =>
LensLike' f InputSettings EvaluateSettings
evaluateSettings EvaluateSettings -> f EvaluateSettings
k InputSettings
s =
(EvaluateSettings -> InputSettings)
-> f EvaluateSettings -> f InputSettings
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\EvaluateSettings
x -> InputSettings
s { _evaluateSettings = x }) (EvaluateSettings -> f EvaluateSettings
k (InputSettings -> EvaluateSettings
_evaluateSettings InputSettings
s))
instance HasEvaluateSettings EvaluateSettings where
evaluateSettings :: forall (f :: * -> *).
Functor f =>
LensLike' f EvaluateSettings EvaluateSettings
evaluateSettings = (EvaluateSettings -> f EvaluateSettings)
-> EvaluateSettings -> f EvaluateSettings
forall a. a -> a
id
parseWithSettings :: MonadThrow m => InputSettings -> Text -> m (Expr Src Import)
parseWithSettings :: forall (m :: * -> *).
MonadThrow m =>
InputSettings -> Text -> m (Expr Src Import)
parseWithSettings InputSettings
settings Text
text =
(ParseError -> m (Expr Src Import))
-> (Expr Src Import -> m (Expr Src Import))
-> Either ParseError (Expr Src Import)
-> m (Expr Src Import)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either ParseError -> m (Expr Src Import)
forall e a. (HasCallStack, Exception e) => e -> m a
forall (m :: * -> *) e a.
(MonadThrow m, HasCallStack, Exception e) =>
e -> m a
throwM Expr Src Import -> m (Expr Src Import)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath -> Text -> Either ParseError (Expr Src Import)
Dhall.Parser.exprFromText (FoldLike FilePath InputSettings InputSettings FilePath FilePath
-> InputSettings -> FilePath
forall a s t b. FoldLike a s t a b -> s -> a
view FoldLike FilePath InputSettings InputSettings FilePath FilePath
forall (f :: * -> *).
Functor f =>
LensLike' f InputSettings FilePath
sourceName InputSettings
settings) Text
text)
typecheckWithSettings :: MonadThrow m => InputSettings -> Expr Src Void -> m ()
typecheckWithSettings :: forall (m :: * -> *).
MonadThrow m =>
InputSettings -> Expr Src Void -> m ()
typecheckWithSettings InputSettings
settings Expr Src Void
expression =
(TypeError Src Void -> m ())
-> (Expr Src Void -> m ())
-> Either (TypeError Src Void) (Expr Src Void)
-> m ()
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either TypeError Src Void -> m ()
forall e a. (HasCallStack, Exception e) => e -> m a
forall (m :: * -> *) e a.
(MonadThrow m, HasCallStack, Exception e) =>
e -> m a
throwM (() -> m ()
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (() -> m ()) -> (Expr Src Void -> ()) -> Expr Src Void -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. () -> Expr Src Void -> ()
forall a b. a -> b -> a
const ()) (Context (Expr Src Void)
-> Expr Src Void -> Either (TypeError Src Void) (Expr Src Void)
forall s.
Context (Expr s Void)
-> Expr s Void -> Either (TypeError s Void) (Expr s Void)
Dhall.TypeCheck.typeWith (FoldLike
(Context (Expr Src Void))
InputSettings
InputSettings
(Context (Expr Src Void))
(Context (Expr Src Void))
-> InputSettings -> Context (Expr Src Void)
forall a s t b. FoldLike a s t a b -> s -> a
view FoldLike
(Context (Expr Src Void))
InputSettings
InputSettings
(Context (Expr Src Void))
(Context (Expr Src Void))
forall (f :: * -> *) s.
(Functor f, HasEvaluateSettings s) =>
LensLike' f s (Context (Expr Src Void))
startingContext InputSettings
settings) Expr Src Void
expression)
checkWithSettings ::
MonadThrow m =>
InputSettings ->
Expr Src Void ->
Expr Src Void ->
m ()
checkWithSettings :: forall (m :: * -> *).
MonadThrow m =>
InputSettings -> Expr Src Void -> Expr Src Void -> m ()
checkWithSettings InputSettings
settings Expr Src Void
type_ Expr Src Void
expression = do
let suffix :: Text
suffix = Expr Src Void -> Text
forall a. Pretty a => a -> Text
Dhall.Pretty.Internal.prettyToStrictText Expr Src Void
type_
let annotated :: Expr Src Void
annotated = case Expr Src Void
expression of
Note (Src SourcePos
begin SourcePos
end Text
bytes) Expr Src Void
_ ->
Src -> Expr Src Void -> Expr Src Void
forall s a. s -> Expr s a -> Expr s a
Note (SourcePos -> SourcePos -> Text -> Src
Src SourcePos
begin SourcePos
end Text
bytes') (Expr Src Void -> Expr Src Void -> Expr Src Void
forall s a. Expr s a -> Expr s a -> Expr s a
Annot Expr Src Void
expression Expr Src Void
type_)
where
bytes' :: Text
bytes' = Text
bytes Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" : " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
suffix
Expr Src Void
_ ->
Expr Src Void -> Expr Src Void -> Expr Src Void
forall s a. Expr s a -> Expr s a -> Expr s a
Annot Expr Src Void
expression Expr Src Void
type_
InputSettings -> Expr Src Void -> m ()
forall (m :: * -> *).
MonadThrow m =>
InputSettings -> Expr Src Void -> m ()
typecheckWithSettings InputSettings
settings Expr Src Void
annotated
expectWithSettings :: MonadThrow m => InputSettings -> Decoder a -> Expr Src Void -> m ()
expectWithSettings :: forall (m :: * -> *) a.
MonadThrow m =>
InputSettings -> Decoder a -> Expr Src Void -> m ()
expectWithSettings InputSettings
settings Decoder{Expector (Expr Src Void)
Expr Src Void -> Extractor Src Void a
expected :: forall a. Decoder a -> Expector (Expr Src Void)
extract :: Expr Src Void -> Extractor Src Void a
expected :: Expector (Expr Src Void)
extract :: forall a. Decoder a -> Expr Src Void -> Extractor Src Void a
..} Expr Src Void
expression = do
Expr Src Void
expected' <- case Expector (Expr Src Void)
expected of
Success Expr Src Void
x -> Expr Src Void -> m (Expr Src Void)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Expr Src Void
x
Failure ExpectedTypeErrors
e -> ExpectedTypeErrors -> m (Expr Src Void)
forall e a. (HasCallStack, Exception e) => e -> m a
forall (m :: * -> *) e a.
(MonadThrow m, HasCallStack, Exception e) =>
e -> m a
throwM ExpectedTypeErrors
e
InputSettings -> Expr Src Void -> Expr Src Void -> m ()
forall (m :: * -> *).
MonadThrow m =>
InputSettings -> Expr Src Void -> Expr Src Void -> m ()
checkWithSettings InputSettings
settings Expr Src Void
expected' Expr Src Void
expression
resolveWithSettings :: InputSettings -> Expr Src Import -> IO (Expr Src Void)
resolveWithSettings :: InputSettings -> Expr Src Import -> IO (Expr Src Void)
resolveWithSettings InputSettings
settings Expr Src Import
expression =
(Expr Src Void, Status) -> Expr Src Void
forall a b. (a, b) -> a
fst ((Expr Src Void, Status) -> Expr Src Void)
-> IO (Expr Src Void, Status) -> IO (Expr Src Void)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> InputSettings -> Expr Src Import -> IO (Expr Src Void, Status)
resolveAndStatusWithSettings InputSettings
settings Expr Src Import
expression
resolveAndStatusWithSettings
:: InputSettings
-> Expr Src Import
-> IO (Expr Src Void, Status)
resolveAndStatusWithSettings :: InputSettings -> Expr Src Import -> IO (Expr Src Void, Status)
resolveAndStatusWithSettings InputSettings
settings Expr Src Import
expression = do
let InputSettings{FilePath
EvaluateSettings
_rootDirectory :: InputSettings -> FilePath
_sourceName :: InputSettings -> FilePath
_evaluateSettings :: InputSettings -> EvaluateSettings
_rootDirectory :: FilePath
_sourceName :: FilePath
_evaluateSettings :: EvaluateSettings
..} = InputSettings
settings
let EvaluateSettings{Maybe (ReifiedNormalizer Void)
IO Manager
Context (Expr Src Void)
Substitutions Src Void
_substitutions :: EvaluateSettings -> Substitutions Src Void
_startingContext :: EvaluateSettings -> Context (Expr Src Void)
_normalizer :: EvaluateSettings -> Maybe (ReifiedNormalizer Void)
_newManager :: EvaluateSettings -> IO Manager
_substitutions :: Substitutions Src Void
_startingContext :: Context (Expr Src Void)
_normalizer :: Maybe (ReifiedNormalizer Void)
_newManager :: IO Manager
..} = EvaluateSettings
_evaluateSettings
let transform :: Status -> Status
transform =
ASetter
Status Status (Substitutions Src Void) (Substitutions Src Void)
-> Substitutions Src Void -> Status -> Status
forall s t a b. ASetter s t a b -> b -> s -> t
Lens.Family.set ASetter
Status Status (Substitutions Src Void) (Substitutions Src Void)
forall (f :: * -> *).
Functor f =>
LensLike' f Status (Substitutions Src Void)
Dhall.Import.substitutions Substitutions Src Void
_substitutions
(Status -> Status) -> (Status -> Status) -> Status -> Status
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ASetter
Status
Status
(Maybe (ReifiedNormalizer Void))
(Maybe (ReifiedNormalizer Void))
-> Maybe (ReifiedNormalizer Void) -> Status -> Status
forall s t a b. ASetter s t a b -> b -> s -> t
Lens.Family.set ASetter
Status
Status
(Maybe (ReifiedNormalizer Void))
(Maybe (ReifiedNormalizer Void))
forall (f :: * -> *).
Functor f =>
LensLike' f Status (Maybe (ReifiedNormalizer Void))
Dhall.Import.normalizer Maybe (ReifiedNormalizer Void)
_normalizer
(Status -> Status) -> (Status -> Status) -> Status -> Status
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ASetter
Status Status (Context (Expr Src Void)) (Context (Expr Src Void))
-> Context (Expr Src Void) -> Status -> Status
forall s t a b. ASetter s t a b -> b -> s -> t
Lens.Family.set ASetter
Status Status (Context (Expr Src Void)) (Context (Expr Src Void))
forall (f :: * -> *).
Functor f =>
LensLike' f Status (Context (Expr Src Void))
Dhall.Import.startingContext Context (Expr Src Void)
_startingContext
let status :: Status
status = Status -> Status
transform (IO Manager -> FilePath -> Status
Dhall.Import.emptyStatusWithManager IO Manager
_newManager FilePath
_rootDirectory)
(Expr Src Void
resolved, Status
status') <- StateT Status IO (Expr Src Void)
-> Status -> IO (Expr Src Void, Status)
forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
State.runStateT (Expr Src Import -> StateT Status IO (Expr Src Void)
Dhall.Import.loadWith Expr Src Import
expression) Status
status
let substituted :: Expr Src Void
substituted = Expr Src Void -> Substitutions Src Void -> Expr Src Void
forall s a. Expr s a -> Substitutions s a -> Expr s a
Dhall.Substitution.substitute Expr Src Void
resolved (FoldLike
(Substitutions Src Void)
InputSettings
InputSettings
(Substitutions Src Void)
(Substitutions Src Void)
-> InputSettings -> Substitutions Src Void
forall a s t b. FoldLike a s t a b -> s -> a
view FoldLike
(Substitutions Src Void)
InputSettings
InputSettings
(Substitutions Src Void)
(Substitutions Src Void)
forall (f :: * -> *) s.
(Functor f, HasEvaluateSettings s) =>
LensLike' f s (Substitutions Src Void)
substitutions InputSettings
settings)
(Expr Src Void, Status) -> IO (Expr Src Void, Status)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Expr Src Void
substituted, Status
status')
normalizeWithSettings :: InputSettings -> Expr Src Void -> Expr Src Void
normalizeWithSettings :: InputSettings -> Expr Src Void -> Expr Src Void
normalizeWithSettings InputSettings
settings =
Maybe (ReifiedNormalizer Void) -> Expr Src Void -> Expr Src Void
forall a s t.
Eq a =>
Maybe (ReifiedNormalizer a) -> Expr s a -> Expr t a
Core.normalizeWith (FoldLike
(Maybe (ReifiedNormalizer Void))
InputSettings
InputSettings
(Maybe (ReifiedNormalizer Void))
(Maybe (ReifiedNormalizer Void))
-> InputSettings -> Maybe (ReifiedNormalizer Void)
forall a s t b. FoldLike a s t a b -> s -> a
view FoldLike
(Maybe (ReifiedNormalizer Void))
InputSettings
InputSettings
(Maybe (ReifiedNormalizer Void))
(Maybe (ReifiedNormalizer Void))
forall (f :: * -> *) s.
(Functor f, HasEvaluateSettings s) =>
LensLike' f s (Maybe (ReifiedNormalizer Void))
normalizer InputSettings
settings)
input
:: Decoder a
-> Text
-> IO a
input :: forall a. Decoder a -> Text -> IO a
input =
InputSettings -> Decoder a -> Text -> IO a
forall a. InputSettings -> Decoder a -> Text -> IO a
inputWithSettings InputSettings
defaultInputSettings
inputWithSettings
:: InputSettings
-> Decoder a
-> Text
-> IO a
inputWithSettings :: forall a. InputSettings -> Decoder a -> Text -> IO a
inputWithSettings InputSettings
settings decoder :: Decoder a
decoder@Decoder{Expector (Expr Src Void)
Expr Src Void -> Extractor Src Void a
expected :: forall a. Decoder a -> Expector (Expr Src Void)
extract :: forall a. Decoder a -> Expr Src Void -> Extractor Src Void a
extract :: Expr Src Void -> Extractor Src Void a
expected :: Expector (Expr Src Void)
..} Text
text = do
Expr Src Import
parsed <- InputSettings -> Text -> IO (Expr Src Import)
forall (m :: * -> *).
MonadThrow m =>
InputSettings -> Text -> m (Expr Src Import)
parseWithSettings InputSettings
settings Text
text
Expr Src Void
resolved <- InputSettings -> Expr Src Import -> IO (Expr Src Void)
resolveWithSettings InputSettings
settings Expr Src Import
parsed
InputSettings -> Decoder a -> Expr Src Void -> IO ()
forall (m :: * -> *) a.
MonadThrow m =>
InputSettings -> Decoder a -> Expr Src Void -> m ()
expectWithSettings InputSettings
settings Decoder a
decoder Expr Src Void
resolved
let normalized :: Expr Src Void
normalized = InputSettings -> Expr Src Void -> Expr Src Void
normalizeWithSettings InputSettings
settings Expr Src Void
resolved
case Expr Src Void -> Extractor Src Void a
extract Expr Src Void
normalized of
Success a
x -> a -> IO a
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return a
x
Failure ExtractErrors Src Void
e -> ExtractErrors Src Void -> IO a
forall e a. Exception e => e -> IO a
Control.Exception.throwIO ExtractErrors Src Void
e
inputFile
:: Decoder a
-> FilePath
-> IO a
inputFile :: forall a. Decoder a -> FilePath -> IO a
inputFile =
EvaluateSettings -> Decoder a -> FilePath -> IO a
forall a. EvaluateSettings -> Decoder a -> FilePath -> IO a
inputFileWithSettings EvaluateSettings
defaultEvaluateSettings
inputFileWithSettings
:: EvaluateSettings
-> Decoder a
-> FilePath
-> IO a
inputFileWithSettings :: forall a. EvaluateSettings -> Decoder a -> FilePath -> IO a
inputFileWithSettings EvaluateSettings
settings Decoder a
ty FilePath
path = do
Text
text <- FilePath -> IO Text
Data.Text.IO.readFile FilePath
path
let inputSettings :: InputSettings
inputSettings = InputSettings
{ _rootDirectory :: FilePath
_rootDirectory = FilePath -> FilePath
takeDirectory FilePath
path
, _sourceName :: FilePath
_sourceName = FilePath
path
, _evaluateSettings :: EvaluateSettings
_evaluateSettings = EvaluateSettings
settings
}
InputSettings -> Decoder a -> Text -> IO a
forall a. InputSettings -> Decoder a -> Text -> IO a
inputWithSettings InputSettings
inputSettings Decoder a
ty Text
text
inputExpr
:: Text
-> IO (Expr Src Void)
inputExpr :: Text -> IO (Expr Src Void)
inputExpr =
InputSettings -> Text -> IO (Expr Src Void)
inputExprWithSettings InputSettings
defaultInputSettings
inputExprWithSettings
:: InputSettings
-> Text
-> IO (Expr Src Void)
inputExprWithSettings :: InputSettings -> Text -> IO (Expr Src Void)
inputExprWithSettings InputSettings
settings Text
text = do
Expr Src Import
parsed <- InputSettings -> Text -> IO (Expr Src Import)
forall (m :: * -> *).
MonadThrow m =>
InputSettings -> Text -> m (Expr Src Import)
parseWithSettings InputSettings
settings Text
text
Expr Src Void
resolved <- InputSettings -> Expr Src Import -> IO (Expr Src Void)
resolveWithSettings InputSettings
settings Expr Src Import
parsed
()
_ <- InputSettings -> Expr Src Void -> IO ()
forall (m :: * -> *).
MonadThrow m =>
InputSettings -> Expr Src Void -> m ()
typecheckWithSettings InputSettings
settings Expr Src Void
resolved
pure (Maybe (ReifiedNormalizer Void) -> Expr Src Void -> Expr Src Void
forall a s t.
Eq a =>
Maybe (ReifiedNormalizer a) -> Expr s a -> Expr t a
Core.normalizeWith (FoldLike
(Maybe (ReifiedNormalizer Void))
InputSettings
InputSettings
(Maybe (ReifiedNormalizer Void))
(Maybe (ReifiedNormalizer Void))
-> InputSettings -> Maybe (ReifiedNormalizer Void)
forall a s t b. FoldLike a s t a b -> s -> a
view FoldLike
(Maybe (ReifiedNormalizer Void))
InputSettings
InputSettings
(Maybe (ReifiedNormalizer Void))
(Maybe (ReifiedNormalizer Void))
forall (f :: * -> *) s.
(Functor f, HasEvaluateSettings s) =>
LensLike' f s (Maybe (ReifiedNormalizer Void))
normalizer InputSettings
settings) Expr Src Void
resolved)
interpretExpr :: Expr Src Import -> IO (Expr Src Void)
interpretExpr :: Expr Src Import -> IO (Expr Src Void)
interpretExpr = InputSettings -> Expr Src Import -> IO (Expr Src Void)
interpretExprWithSettings InputSettings
defaultInputSettings
interpretExprWithSettings
:: InputSettings -> Expr Src Import -> IO (Expr Src Void)
interpretExprWithSettings :: InputSettings -> Expr Src Import -> IO (Expr Src Void)
interpretExprWithSettings InputSettings
settings Expr Src Import
parsed = do
Expr Src Void
resolved <- InputSettings -> Expr Src Import -> IO (Expr Src Void)
resolveWithSettings InputSettings
settings Expr Src Import
parsed
InputSettings -> Expr Src Void -> IO ()
forall (m :: * -> *).
MonadThrow m =>
InputSettings -> Expr Src Void -> m ()
typecheckWithSettings InputSettings
settings Expr Src Void
resolved
pure (Maybe (ReifiedNormalizer Void) -> Expr Src Void -> Expr Src Void
forall a s t.
Eq a =>
Maybe (ReifiedNormalizer a) -> Expr s a -> Expr t a
Core.normalizeWith (FoldLike
(Maybe (ReifiedNormalizer Void))
InputSettings
InputSettings
(Maybe (ReifiedNormalizer Void))
(Maybe (ReifiedNormalizer Void))
-> InputSettings -> Maybe (ReifiedNormalizer Void)
forall a s t b. FoldLike a s t a b -> s -> a
view FoldLike
(Maybe (ReifiedNormalizer Void))
InputSettings
InputSettings
(Maybe (ReifiedNormalizer Void))
(Maybe (ReifiedNormalizer Void))
forall (f :: * -> *) s.
(Functor f, HasEvaluateSettings s) =>
LensLike' f s (Maybe (ReifiedNormalizer Void))
normalizer InputSettings
settings) Expr Src Void
resolved)
fromExpr :: Decoder a -> Expr Src Import -> IO a
fromExpr :: forall a. Decoder a -> Expr Src Import -> IO a
fromExpr = InputSettings -> Decoder a -> Expr Src Import -> IO a
forall a. InputSettings -> Decoder a -> Expr Src Import -> IO a
fromExprWithSettings InputSettings
defaultInputSettings
fromExprWithSettings :: InputSettings -> Decoder a -> Expr Src Import -> IO a
fromExprWithSettings :: forall a. InputSettings -> Decoder a -> Expr Src Import -> IO a
fromExprWithSettings InputSettings
settings decoder :: Decoder a
decoder@Decoder{Expector (Expr Src Void)
Expr Src Void -> Extractor Src Void a
expected :: forall a. Decoder a -> Expector (Expr Src Void)
extract :: forall a. Decoder a -> Expr Src Void -> Extractor Src Void a
extract :: Expr Src Void -> Extractor Src Void a
expected :: Expector (Expr Src Void)
..} Expr Src Import
expression = do
Expr Src Void
resolved <- InputSettings -> Expr Src Import -> IO (Expr Src Void)
resolveWithSettings InputSettings
settings Expr Src Import
expression
InputSettings -> Decoder a -> Expr Src Void -> IO ()
forall (m :: * -> *) a.
MonadThrow m =>
InputSettings -> Decoder a -> Expr Src Void -> m ()
expectWithSettings InputSettings
settings Decoder a
decoder Expr Src Void
resolved
let normalized :: Expr Src Void
normalized = Maybe (ReifiedNormalizer Void) -> Expr Src Void -> Expr Src Void
forall a s t.
Eq a =>
Maybe (ReifiedNormalizer a) -> Expr s a -> Expr t a
Core.normalizeWith (FoldLike
(Maybe (ReifiedNormalizer Void))
InputSettings
InputSettings
(Maybe (ReifiedNormalizer Void))
(Maybe (ReifiedNormalizer Void))
-> InputSettings -> Maybe (ReifiedNormalizer Void)
forall a s t b. FoldLike a s t a b -> s -> a
view FoldLike
(Maybe (ReifiedNormalizer Void))
InputSettings
InputSettings
(Maybe (ReifiedNormalizer Void))
(Maybe (ReifiedNormalizer Void))
forall (f :: * -> *) s.
(Functor f, HasEvaluateSettings s) =>
LensLike' f s (Maybe (ReifiedNormalizer Void))
normalizer InputSettings
settings) Expr Src Void
resolved
case Expr Src Void -> Extractor Src Void a
extract Expr Src Void
normalized of
Success a
x -> a -> IO a
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return a
x
Failure ExtractErrors Src Void
e -> ExtractErrors Src Void -> IO a
forall e a. Exception e => e -> IO a
Control.Exception.throwIO ExtractErrors Src Void
e
rawInput
:: Alternative f
=> Decoder a
-> Expr s Void
-> f a
rawInput :: forall (f :: * -> *) a s.
Alternative f =>
Decoder a -> Expr s Void -> f a
rawInput (Decoder {Expector (Expr Src Void)
Expr Src Void -> Extractor Src Void a
expected :: forall a. Decoder a -> Expector (Expr Src Void)
extract :: forall a. Decoder a -> Expr Src Void -> Extractor Src Void a
extract :: Expr Src Void -> Extractor Src Void a
expected :: Expector (Expr Src Void)
..}) Expr s Void
expr =
case Expr Src Void -> Extractor Src Void a
extract (Expr s Void -> Expr Src Void
forall a s t. Eq a => Expr s a -> Expr t a
Core.normalize Expr s Void
expr) of
Success a
x -> a -> f a
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
x
Failure ExtractErrors Src Void
_e -> f a
forall a. f a
forall (f :: * -> *) a. Alternative f => f a
empty
detailed :: IO a -> IO a
detailed :: forall a. IO a -> IO a
detailed =
(TypeError Src Void -> IO a) -> IO a -> IO a
forall e a. Exception e => (e -> IO a) -> IO a -> IO a
Control.Exception.handle TypeError Src Void -> IO a
forall a. TypeError Src Void -> IO a
handler1 (IO a -> IO a) -> (IO a -> IO a) -> IO a -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Imported (TypeError Src Void) -> IO a) -> IO a -> IO a
forall e a. Exception e => (e -> IO a) -> IO a -> IO a
Control.Exception.handle Imported (TypeError Src Void) -> IO a
forall a. Imported (TypeError Src Void) -> IO a
handler0
where
handler0 :: Imported (TypeError Src Void) -> IO a
handler0 :: forall a. Imported (TypeError Src Void) -> IO a
handler0 (Imported NonEmpty Chained
ps TypeError Src Void
e) =
Imported (DetailedTypeError Src Void) -> IO a
forall e a. Exception e => e -> IO a
Control.Exception.throwIO (NonEmpty Chained
-> DetailedTypeError Src Void
-> Imported (DetailedTypeError Src Void)
forall e. NonEmpty Chained -> e -> Imported e
Imported NonEmpty Chained
ps (TypeError Src Void -> DetailedTypeError Src Void
forall s a. TypeError s a -> DetailedTypeError s a
DetailedTypeError TypeError Src Void
e))
handler1 :: TypeError Src Void -> IO a
handler1 :: forall a. TypeError Src Void -> IO a
handler1 TypeError Src Void
e = DetailedTypeError Src Void -> IO a
forall e a. Exception e => e -> IO a
Control.Exception.throwIO (TypeError Src Void -> DetailedTypeError Src Void
forall s a. TypeError s a -> DetailedTypeError s a
DetailedTypeError TypeError Src Void
e)