@@ -51,6 +51,7 @@ module Dhall
5151 , parseWithSettings
5252 , resolveWithSettings
5353 , typecheckWithSettings
54+ , checkWithSettings
5455 , expectWithSettings
5556 , normalizeWithSettings
5657
@@ -59,6 +60,7 @@ module Dhall
5960 ) where
6061
6162import Control.Applicative (Alternative , empty )
63+ import Control.Monad.Catch (MonadThrow , throwM )
6264import Data.Either.Validation (Validation (.. ))
6365import Data.Void (Void )
6466import Dhall.Import (Imported (.. ))
@@ -207,39 +209,52 @@ instance HasEvaluateSettings EvaluateSettings where
207209 evaluateSettings = id
208210
209211-- | 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)
212+ parseWithSettings :: MonadThrow m => InputSettings -> Text -> m (Expr Src Import )
213+ parseWithSettings settings text =
214+ either throwM return (Dhall.Parser. exprFromText (view sourceName settings) text)
213215
214216-- | 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)
217+ typecheckWithSettings :: MonadThrow m => InputSettings -> Expr Src Void -> m ()
218+ typecheckWithSettings settings expression =
219+ either throwM ( return . const () ) (Dhall.TypeCheck. typeWith (view startingContext settings) expression)
218220
219- return ()
220-
221- {-| Type-check an expression against a `Decoder`'s expected type, using the
222- supplied `InputSettings`
221+ {-| Type-check an expression against a type provided as a Dhall expreession,
222+ using the supplied `InputSettings`
223223-}
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'
224+ checkWithSettings ::
225+ MonadThrow m =>
226+ -- | The input settings
227+ InputSettings ->
228+ -- | The expected type of the expression
229+ Expr Src Void ->
230+ -- | The expression to check
231+ Expr Src Void ->
232+ m ()
233+ checkWithSettings settings type_ expression = do
234+ let suffix = Dhall.Pretty.Internal. prettyToStrictText type_
231235
232236 let annotated = case expression of
233237 Note (Src begin end bytes) _ ->
234- Note (Src begin end bytes') (Annot expression expected' )
238+ Note (Src begin end bytes') (Annot expression type_ )
235239 where
236240 bytes' = bytes <> " : " <> suffix
237241 _ ->
238- Annot expression expected'
242+ Annot expression type_
239243
240244 typecheckWithSettings settings annotated
241245
242- return ()
246+ {-| Type-check an expression against a `Decoder`'s expected type, using the
247+ supplied `InputSettings`.
248+ This is equivalent of using the 'expected' type of a @Decoder@ as the second
249+ argument to 'checkWithSettings'.
250+ -}
251+ expectWithSettings :: MonadThrow m => InputSettings -> Decoder a -> Expr Src Void -> m ()
252+ expectWithSettings settings Decoder {.. } expression = do
253+ expected' <- case expected of
254+ Success x -> return x
255+ Failure e -> throwM e
256+
257+ checkWithSettings settings expected' expression
243258
244259{-| Resolve an expression, using the supplied `InputSettings`
245260
0 commit comments