Expand haddock coverage (#277)

This commit is contained in:
Gabriel Gonzalez 2018-02-18 08:44:12 -08:00 committed by GitHub
parent dc75b72553
commit 4a02a219d2
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
6 changed files with 42 additions and 4 deletions

View File

@ -46,6 +46,7 @@ module Dhall
, string
, pair
, GenericInterpret(..)
, GenericInject(..)
, Inject(..)
, inject

View File

@ -135,6 +135,7 @@ instance Buildable PathType where
-- | How to interpret the path's contents (i.e. as Dhall code or raw text)
data PathMode = Code | RawText deriving (Eq, Ord, Show)
-- | A `PathType` extended with an optional hash for semantic integrity checks
data PathHashed = PathHashed
{ hash :: Maybe Data.ByteString.ByteString
, pathType :: PathType
@ -467,6 +468,7 @@ instance Bifunctor Expr where
instance IsString (Expr s a) where
fromString str = Var (fromString str)
-- | The body of an interpolated @Text@ literal
data Chunks s a = Chunks [(Builder, Expr s a)] Builder
deriving (Functor, Foldable, Traversable, Show, Eq)

View File

@ -107,6 +107,8 @@ module Dhall.Import (
, loadWithContext
, hashExpression
, hashExpressionToCode
, Status(..)
, emptyStatus
, Cycle(..)
, ReferentiallyOpaque(..)
, Imported(..)
@ -328,12 +330,19 @@ instance Show MissingEnvironmentVariable where
<> "\n"
<> "" <> Text.unpack name
-- | State threaded throughout the import process
data Status = Status
{ _stack :: [Path]
-- ^ Stack of `Path`s that we've imported along the way to get to the
-- current point
, _cache :: Map Path (Expr Src X)
-- ^ Cache of imported expressions in order to avoid importing the same
-- expression twice with different values
, _manager :: Maybe Manager
-- ^ Cache for the `Manager` so that we only acquire it once
}
-- | Default starting `Status`
emptyStatus :: Status
emptyStatus = Status [] Map.empty Nothing

View File

@ -1,3 +1,6 @@
{-| This module contains logic for pretty-printing expressions, including
support for syntax highlighting
-}
module Dhall.Pretty ( Ann(..), annToAnsiStyle, prettyExpr ) where
import Dhall.Pretty.Internal

View File

@ -2,6 +2,10 @@
{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_GHC -Wall #-}
{-| This module provides internal pretty-printing utilities which are used by
other modules but are not part of the public facing API
-}
module Dhall.Pretty.Internal (
Ann(..)
, annToAnsiStyle
@ -44,6 +48,9 @@ import qualified Data.Text.Prettyprint.Doc as Pretty
import qualified Data.Text.Prettyprint.Doc.Render.Text as Pretty
import qualified Data.Vector
{-| Annotation type used to tag elements in a pretty-printed document for
syntax highlighting purposes
-}
data Ann
= Keyword -- ^ Used for syntactic keywords
| Syntax -- ^ Syntax punctuation such as commas, parenthesis, and braces
@ -51,6 +58,9 @@ data Ann
| Literal -- ^ Literals such as integers and strings
| Builtin -- ^ Builtin types and values
{-| Convert annotations to their corresponding color for syntax highlighting
purposes
-}
annToAnsiStyle :: Ann -> Terminal.AnsiStyle
annToAnsiStyle Keyword = Terminal.bold
annToAnsiStyle Syntax = mempty
@ -58,6 +68,7 @@ annToAnsiStyle Label = Terminal.color Terminal.Green
annToAnsiStyle Literal = Terminal.color Terminal.Magenta
annToAnsiStyle Builtin = Terminal.color Terminal.Red
-- | Pretty print an expression
prettyExpr :: Pretty a => Expr s a -> Doc Ann
prettyExpr = prettyExprA
@ -781,9 +792,10 @@ escapeSingleQuotedText inputBuilder = outputBuilder
substitute before after = Text.intercalate after . Text.splitOn before
-- | Escape a `Builder` literal using Dhall's escaping rules
--
-- Note that the result does not include surrounding quotes
{-| Escape a `Builder` literal using Dhall's escaping rules
Note that the result does not include surrounding quotes
-}
escapeText :: Builder -> Builder
escapeText a = Builder.fromLazyText (Text.concatMap adapt text)
where

View File

@ -136,9 +136,20 @@ typeWith ctx expr = do
checkContext ctx
typeWithA absurd ctx expr
{-| Function that converts the value inside an `Embed` constructor into a new
expression
-}
type Typer a = forall s. a -> Expr s a
typeWithA :: Eq a => Typer a -> Context (Expr s a) -> Expr s a -> Either (TypeError s a) (Expr s a)
{-| Generalization of `typeWith` that allows type-checking the `Embed`
constructor with custom logic
-}
typeWithA
:: Eq a
=> Typer a
-> Context (Expr s a)
-> Expr s a
-> Either (TypeError s a) (Expr s a)
typeWithA tpa = loop
where
loop _ (Const c ) = do