Updated documentation

This commit is contained in:
Gabriel Gonzalez 2016-12-04 14:18:51 -08:00
parent 878eccd65e
commit 2b97dab9c1
4 changed files with 25 additions and 3 deletions

View File

@ -1282,6 +1282,9 @@ normalize e = case e of
text = "normalize (" <> Data.Text.pack (show e'') <> ")"
{-| Utility function used to throw internal errors that should never happen
(in theory) but that are not enforced by the type system
-}
internalError :: Data.Text.Text -> forall b . b
internalError text = error (Data.Text.unpack [NeatInterpolation.text|
Error: Compiler bug

View File

@ -194,6 +194,7 @@ instance Show e => Show (Imported e) where
-- Canonicalize all paths
paths' = zip [0..] (drop 1 (reverse (canonicalizeAll paths)))
-- | Newtype used to wrap `HttpException`s with a prettier `Show` instance
newtype PrettyHttpException = PrettyHttpException HttpException
deriving (Typeable)
@ -216,6 +217,7 @@ instance Show PrettyHttpException where
e' -> "\n"
<> show e'
-- | Exception thrown when an imported file is missing
data MissingFile = MissingFile
deriving (Typeable)
@ -369,10 +371,11 @@ exprFromFile path = do
where
parser = unParser (do
Text.Parser.Token.whiteSpace
r <- Dhall.Parser.exprA
r <- Dhall.Parser.expr
Text.Parser.Combinators.eof
return r )
-- | Parse an expression from a URL hosting a Dhall program
exprFromURL :: Manager -> Text -> IO (Expr Src Path)
exprFromURL m url = do
request <- HTTP.parseUrlThrow (Text.unpack url)
@ -418,7 +421,7 @@ exprFromURL m url = do
where
parser = unParser (do
Text.Parser.Token.whiteSpace
r <- Dhall.Parser.exprA
r <- Dhall.Parser.expr
Text.Parser.Combinators.eof
return r )

View File

@ -2,12 +2,14 @@
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings #-}
-- | This module contains Dhall's parsing logic
module Dhall.Parser (
-- * Utilities
exprFromText
-- * Parsers
, exprA
, expr
-- * Types
, Src(..)
@ -62,6 +64,7 @@ import qualified Text.Trifecta
import qualified Text.Trifecta.Combinators
import qualified Text.Trifecta.Delta
-- | Source code extract
data Src = Src Delta Delta ByteString deriving (Show)
instance Buildable Src where
@ -75,6 +78,10 @@ instance Buildable Src where
text = Data.Text.Lazy.strip (Data.Text.Lazy.Encoding.decodeUtf8 bytes')
{-| A `Parser` that is almost identical to
@"Text.Trifecta".`Text.Trifecta.Parser`@ except treating Haskell-style
comments as whitespace
-}
newtype Parser a = Parser { unParser :: Text.Trifecta.Parser a }
deriving
( Functor
@ -195,6 +202,10 @@ combine = symbol "/\\" <|> symbol "∧"
label :: Parser Text
label = Text.Parser.Token.ident identifierStyle <?> "label"
-- | Parser for a top-level Dhall expression
expr :: Parser (Expr Src Path)
expr = exprA
exprA :: Parser (Expr Src Path)
exprA = do
a <- exprB

View File

@ -5,6 +5,8 @@
{-# LANGUAGE RecordWildCards #-}
{-# OPTIONS_GHC -Wall #-}
-- | This module contains the logic for type checking Dhall code
module Dhall.TypeCheck (
-- * Type-checking
typeWith
@ -2842,6 +2844,9 @@ instance Buildable s => Buildable (TypeError s) where
Note s _ -> build s
_ -> mempty
{-| Newtype used to wrap error messages so that they render with a more
detailed explanation of what went wrong
-}
newtype DetailedTypeError s = DetailedTypeError (TypeError s)
deriving (Typeable)