@@ -24,6 +24,10 @@ module Dhall
2424 , inputFileWithSettings
2525 , inputExpr
2626 , inputExprWithSettings
27+ , interpretExpr
28+ , interpretExprWithSettings
29+ , fromExpr
30+ , fromExprWithSettings
2731 , rootDirectory
2832 , sourceName
2933 , startingContext
@@ -43,6 +47,13 @@ module Dhall
4347 -- * Encoders
4448 , module Dhall.Marshal.Encode
4549
50+ -- * Individual phases
51+ , parseWithSettings
52+ , resolveWithSettings
53+ , typecheckWithSettings
54+ , expectWithSettings
55+ , normalizeWithSettings
56+
4657 -- * Miscellaneous
4758 , rawInput
4859 ) where
@@ -52,7 +63,7 @@ import Data.Either.Validation (Validation (..))
5263import Data.Void (Void )
5364import Dhall.Import (Imported (.. ))
5465import Dhall.Parser (Src (.. ))
55- import Dhall.Syntax (Expr (.. ))
66+ import Dhall.Syntax (Expr (.. ), Import )
5667import Dhall.TypeCheck (DetailedTypeError (.. ), TypeError )
5768import GHC.Generics
5869import Lens.Family (LensLike' , view )
@@ -195,6 +206,68 @@ instance HasEvaluateSettings InputSettings where
195206instance HasEvaluateSettings EvaluateSettings where
196207 evaluateSettings = id
197208
209+ -- | Parse an expression, using the supplied `InputSettings`
210+ parseWithSettings :: InputSettings -> Text -> IO (Expr Src Import )
211+ parseWithSettings settings text = do
212+ Core. throws (Dhall.Parser. exprFromText (view sourceName settings) text)
213+
214+ -- | Type-check an expression, using the supplied `InputSettings`
215+ typecheckWithSettings :: InputSettings -> Expr Src Void -> IO ()
216+ typecheckWithSettings settings expression = do
217+ _ <- Core. throws (Dhall.TypeCheck. typeWith (view startingContext settings) expression)
218+
219+ return ()
220+
221+ {-| Type-check an expression against a `Decoder`'s expected type, using the
222+ supplied `InputSettings`
223+ -}
224+ expectWithSettings :: InputSettings -> Decoder a -> Expr Src Void -> IO ()
225+ expectWithSettings settings Decoder {.. } expression = do
226+ expected' <- case expected of
227+ Success x -> return x
228+ Failure e -> Control.Exception. throwIO e
229+
230+ let suffix = Dhall.Pretty.Internal. prettyToStrictText expected'
231+
232+ let annotated = case expression of
233+ Note (Src begin end bytes) _ ->
234+ Note (Src begin end bytes') (Annot expression expected')
235+ where
236+ bytes' = bytes <> " : " <> suffix
237+ _ ->
238+ Annot expression expected'
239+
240+ typecheckWithSettings settings annotated
241+
242+ return ()
243+
244+ {-| Resolve an expression, using the supplied `InputSettings`
245+
246+ Note that this also applies any substitutions specified in the
247+ `InputSettings`
248+ -}
249+ resolveWithSettings :: InputSettings -> Expr Src Import -> IO (Expr Src Void )
250+ resolveWithSettings settings expression = do
251+ let InputSettings {.. } = settings
252+
253+ let EvaluateSettings {.. } = _evaluateSettings
254+
255+ let transform =
256+ Lens.Family. set Dhall.Import. substitutions _substitutions
257+ . Lens.Family. set Dhall.Import. normalizer _normalizer
258+ . Lens.Family. set Dhall.Import. startingContext _startingContext
259+
260+ let status = transform (Dhall.Import. emptyStatusWithManager _newManager _rootDirectory)
261+
262+ resolved <- State. evalStateT (Dhall.Import. loadWith expression) status
263+
264+ pure (Dhall.Substitution. substitute resolved (view substitutions settings))
265+
266+ -- | Normalize an expression, using the supplied `InputSettings`
267+ normalizeWithSettings :: InputSettings -> Expr Src Void -> Expr Src Void
268+ normalizeWithSettings settings =
269+ Core. normalizeWith (view normalizer settings)
270+
198271{-| Type-check and evaluate a Dhall program, decoding the result into Haskell
199272
200273 The first argument determines the type of value that you decode:
@@ -236,24 +309,17 @@ inputWithSettings
236309 -- ^ The Dhall program
237310 -> IO a
238311 -- ^ The decoded value in Haskell
239- inputWithSettings settings (Decoder {.. }) txt = do
240- expected' <- case expected of
241- Success x -> return x
242- Failure e -> Control.Exception. throwIO e
312+ inputWithSettings settings decoder@ Decoder {.. } text = do
313+ parsed <- parseWithSettings settings text
243314
244- let suffix = Dhall.Pretty.Internal. prettyToStrictText expected'
245- let annotate substituted = case substituted of
246- Note (Src begin end bytes) _ ->
247- Note (Src begin end bytes') (Annot substituted expected')
248- where
249- bytes' = bytes <> " : " <> suffix
250- _ ->
251- Annot substituted expected'
315+ resolved <- resolveWithSettings settings parsed
252316
253- normExpr <- inputHelper annotate settings txt
317+ expectWithSettings settings decoder resolved
254318
255- case extract normExpr of
256- Success x -> return x
319+ let normalized = normalizeWithSettings settings resolved
320+
321+ case extract normalized of
322+ Success x -> return x
257323 Failure e -> Control.Exception. throwIO e
258324
259325{-| Type-check and evaluate a Dhall program that is read from the
@@ -320,39 +386,51 @@ inputExprWithSettings
320386 -- ^ The Dhall program
321387 -> IO (Expr Src Void )
322388 -- ^ The fully normalized AST
323- inputExprWithSettings = inputHelper id
389+ inputExprWithSettings settings text = do
390+ parsed <- parseWithSettings settings text
391+
392+ resolved <- resolveWithSettings settings parsed
393+
394+ _ <- typecheckWithSettings settings resolved
395+
396+ pure (Core. normalizeWith (view normalizer settings) resolved)
324397
325- {-| Helper function for the input* function family
398+ {-| Interpret a Dhall Expression
326399
327- @since 1.30
400+ This takes care of import resolution, type-checking, and normalization
328401-}
329- inputHelper
330- :: (Expr Src Void -> Expr Src Void )
331- -> InputSettings
332- -> Text
333- -- ^ The Dhall program
334- -> IO (Expr Src Void )
335- -- ^ The fully normalized AST
336- inputHelper annotate settings txt = do
337- expr <- Core. throws (Dhall.Parser. exprFromText (view sourceName settings) txt)
402+ interpretExpr :: Expr Src Import -> IO (Expr Src Void )
403+ interpretExpr = interpretExprWithSettings defaultInputSettings
338404
339- let InputSettings {.. } = settings
405+ -- | Like `interpretExpr`, but customizable using `InputSettings`
406+ interpretExprWithSettings
407+ :: InputSettings -> Expr Src Import -> IO (Expr Src Void )
408+ interpretExprWithSettings settings parsed = do
409+ resolved <- resolveWithSettings settings parsed
340410
341- let EvaluateSettings { .. } = _evaluateSettings
411+ typecheckWithSettings settings resolved
342412
343- let transform =
344- Lens.Family. set Dhall.Import. substitutions _substitutions
345- . Lens.Family. set Dhall.Import. normalizer _normalizer
346- . Lens.Family. set Dhall.Import. startingContext _startingContext
413+ pure (Core. normalizeWith (view normalizer settings) resolved)
347414
348- let status = transform (Dhall.Import. emptyStatusWithManager _newManager _rootDirectory)
415+ {- | Decode a Dhall expression
416+
417+ This takes care of import resolution, type-checking and normalization
418+ -}
419+ fromExpr :: Decoder a -> Expr Src Import -> IO a
420+ fromExpr = fromExprWithSettings defaultInputSettings
421+
422+ -- | Like `fromExpr`, but customizable using `InputSettings`
423+ fromExprWithSettings :: InputSettings -> Decoder a -> Expr Src Import -> IO a
424+ fromExprWithSettings settings decoder@ Decoder {.. } expression = do
425+ resolved <- resolveWithSettings settings expression
349426
350- expr' <- State. evalStateT ( Dhall.Import. loadWith expr) status
427+ expectWithSettings settings decoder resolved
351428
352- let substituted = Dhall.Substitution. substitute expr' $ view substitutions settings
353- let annot = annotate substituted
354- _ <- Core. throws (Dhall.TypeCheck. typeWith (view startingContext settings) annot)
355- pure (Core. normalizeWith (view normalizer settings) substituted)
429+ let normalized = Core. normalizeWith (view normalizer settings) resolved
430+
431+ case extract normalized of
432+ Success x -> return x
433+ Failure e -> Control.Exception. throwIO e
356434
357435-- | Use this function to extract Haskell values directly from Dhall AST.
358436-- The intended use case is to allow easy extraction of Dhall values for
0 commit comments