Skip to content

Commit 9dca2b8

Browse files
authored
Fix ambiguous haddock errors (#2014)
… and fix CI to catch them going forward
1 parent 7810c4f commit 9dca2b8

File tree

27 files changed

+129
-109
lines changed

27 files changed

+129
-109
lines changed

dhall/ghc-src/Dhall/Import/Manager.hs

Lines changed: 8 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,12 @@
1-
{-| Both the GHC and GHCJS implementations of "Dhall.Import.Manager" export a
2-
`Manager` type suitable for use within the "Dhall.Import" module
1+
{-| Both the GHC and GHCJS implementations of 'Dhall.Import.Manager.Manager'
2+
export a `Dhall.Import.Manager.Manager` type suitable for use within the
3+
"Dhall.Import" module
34
4-
For the GHC implementation the `Manager` type is a real `Manager` from the
5-
@http-client@ package. For the GHCJS implementation the `Manager` type is
6-
a synonym for @`Data.Void.Void`@ since GHCJS does not use a `Manager` for
7-
HTTP requests.
5+
For the GHC implementation the `Dhall.Import.Manager` type is a real
6+
`Network.HTTP.Client.Manager` from the @http-client@ package. For the
7+
GHCJS implementation the `Dhall.Import.Manager.Manager` type is
8+
a synonym for @`Data.Void.Void`@ since GHCJS does not use a
9+
`Network.HTTP.Client.Manager` for HTTP requests.
810
-}
911
module Dhall.Import.Manager
1012
( -- * Manager

dhall/ghcjs-src/Dhall/Import/HTTP.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -18,11 +18,11 @@ import qualified Data.Text as Text
1818
import qualified JavaScript.XHR
1919

2020

21-
{-| The GHCJS implementation does not require a `Manager`
21+
{-| The GHCJS implementation does not require a `Network.HTTP.Client.Manager`
2222
2323
The purpose of this synonym is so that "Dhall.Import.Types" can import a
24-
`Manager` type from "Dhall.Import.HTTP" that does the correct thing for
25-
both the GHC and GHCJS implementations
24+
`Dhall.Import.Manager.Manager` type from "Dhall.Import.HTTP" that does the
25+
correct thing for both the GHC and GHCJS implementations
2626
-}
2727
type Manager = Void
2828

Lines changed: 9 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,12 @@
1-
{-| Both the GHC and GHCJS implementations of "Dhall.Import.Manager" export a
2-
`Manager` type suitable for use within the "Dhall.Import" module
1+
{-| Both the GHC and GHCJS implementations of `Dhall.Import.Manager.Manager`
2+
export a `Dhall.Import.Manager.Manager` type suitable for use within the
3+
"Dhall.Import" module
34
4-
For the GHC implementation the `Manager` type is a real `Manager` from the
5-
@http-client@ package. For the GHCJS implementation the `Manager` type is
6-
a synonym for @`Data.Void.Void`@ since GHCJS does not use a `Manager` for
7-
HTTP requests.
5+
For the GHC implementation the `Dhall.Import.Manager.Manager` type is a real
6+
`Network.HTTP.Client.Manager` from the @http-client@ package. For the GHCJS
7+
implementation the `Dhall.Import.Manager.Manager` type is a synonym for
8+
@`Data.Void.Void`@ since GHCJS does not use a
9+
`Network.HTTP.Client.Manager` for HTTP requests.
810
-}
911
module Dhall.Import.Manager
1012
( -- * Manager
@@ -13,5 +15,5 @@ module Dhall.Import.Manager
1315

1416
import Data.Void (Void)
1517

16-
-- | GHCJS does not use a `Manager`
18+
-- | GHCJS does not use a `Network.HTTP.Client.Manager`
1719
type Manager = Void

dhall/src/Dhall.hs

Lines changed: 18 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -41,7 +41,7 @@ module Dhall
4141
, InputSettings
4242
, defaultEvaluateSettings
4343
, EvaluateSettings
44-
, HasEvaluateSettings
44+
, HasEvaluateSettings(..)
4545
, detailed
4646

4747
-- * Decoders
@@ -110,7 +110,7 @@ module Dhall
110110
, union
111111
, constructor
112112
, GenericFromDhall(..)
113-
113+
, GenericFromDhallUnion(..)
114114
, ToDhall(..)
115115
, Inject
116116
, inject
@@ -133,6 +133,7 @@ module Dhall
133133
, rawInput
134134
, (>$<)
135135
, (>*<)
136+
, Result
136137

137138
-- * Re-exports
138139
, Natural
@@ -259,7 +260,7 @@ typeError expected actual = Failure $ case expected of
259260
Failure e -> fmap ExpectedTypeError e
260261
Success expected' -> DhallErrors $ pure $ TypeMismatch $ InvalidDecoder expected' actual
261262

262-
-- | Turn a `Text` message into an extraction failure
263+
-- | Turn a `Data.Text.Text` message into an extraction failure
263264
extractError :: Text -> Extractor s a b
264265
extractError = Failure . DhallErrors . pure . ExtractError
265266

@@ -630,7 +631,7 @@ inputHelper annotate settings txt = do
630631
-- The intended use case is to allow easy extraction of Dhall values for
631632
-- making the function `Core.normalizeWith` easier to use.
632633
--
633-
-- For other use cases, use `input` from `Dhall` module. It will give you
634+
-- For other use cases, use `input` from "Dhall" module. It will give you
634635
-- a much better user experience.
635636
rawInput
636637
:: Alternative f
@@ -785,7 +786,7 @@ data Decoder a = Decoder
785786
}
786787
deriving (Functor)
787788

788-
{-| Decode a `Bool`
789+
{-| Decode a `Prelude.Bool`
789790
790791
>>> input bool "True"
791792
True
@@ -798,7 +799,7 @@ bool = Decoder {..}
798799

799800
expected = pure Bool
800801

801-
{-| Decode a `Natural`
802+
{-| Decode a `Prelude.Natural`
802803
803804
>>> input natural "42"
804805
42
@@ -811,7 +812,7 @@ natural = Decoder {..}
811812

812813
expected = pure Natural
813814

814-
{-| Decode an `Integer`
815+
{-| Decode an `Prelude.Integer`
815816
816817
>>> input integer "+42"
817818
42
@@ -939,7 +940,7 @@ r
939940
scientific :: Decoder Scientific
940941
scientific = fmap Data.Scientific.fromFloatDigits double
941942

942-
{-| Decode a `Double`
943+
{-| Decode a `Prelude.Double`
943944
944945
>>> input double "42.0"
945946
42.0
@@ -952,15 +953,15 @@ double = Decoder {..}
952953

953954
expected = pure Double
954955

955-
{-| Decode lazy `Text`
956+
{-| Decode lazy `Data.Text.Text`
956957
957958
>>> input lazyText "\"Test\""
958959
"Test"
959960
-}
960961
lazyText :: Decoder Data.Text.Lazy.Text
961962
lazyText = fmap Data.Text.Lazy.fromStrict strictText
962963

963-
{-| Decode strict `Text`
964+
{-| Decode strict `Data.Text.Text`
964965
965966
>>> input strictText "\"Test\""
966967
"Test"
@@ -1054,7 +1055,7 @@ functionWith inputNormalizer (Encoder {..}) (Decoder extractIn expectedIn) =
10541055

10551056
expectedOut = Pi "_" declared <$> expectedIn
10561057

1057-
{-| Decode a `Set` from a `List`
1058+
{-| Decode a `Data.Set.Set` from a `List`
10581059
10591060
>>> input (setIgnoringDuplicates natural) "[1, 2, 3]"
10601061
fromList [1,2,3]
@@ -1068,7 +1069,7 @@ fromList [1,3]
10681069
setIgnoringDuplicates :: (Ord a) => Decoder a -> Decoder (Data.Set.Set a)
10691070
setIgnoringDuplicates = fmap Data.Set.fromList . list
10701071

1071-
{-| Decode a `HashSet` from a `List`
1072+
{-| Decode a `Data.HashSet.HashSet` from a `List`
10721073
10731074
>>> input (hashSetIgnoringDuplicates natural) "[1, 2, 3]"
10741075
fromList [1,2,3]
@@ -1084,7 +1085,7 @@ hashSetIgnoringDuplicates :: (Hashable a, Ord a)
10841085
-> Decoder (Data.HashSet.HashSet a)
10851086
hashSetIgnoringDuplicates = fmap Data.HashSet.fromList . list
10861087

1087-
{-| Decode a `Set` from a `List` with distinct elements
1088+
{-| Decode a `Data.Set.Set` from a `List` with distinct elements
10881089
10891090
>>> input (setFromDistinctList natural) "[1, 2, 3]"
10901091
fromList [1,2,3]
@@ -1113,7 +1114,7 @@ An error is thrown if the list contains duplicates.
11131114
setFromDistinctList :: (Ord a, Show a) => Decoder a -> Decoder (Data.Set.Set a)
11141115
setFromDistinctList = setHelper Data.Set.size Data.Set.fromList
11151116

1116-
{-| Decode a `HashSet` from a `List` with distinct elements
1117+
{-| Decode a `Data.HashSet.HashSet` from a `List` with distinct elements
11171118
11181119
>>> input (hashSetFromDistinctList natural) "[1, 2, 3]"
11191120
fromList [1,2,3]
@@ -1683,6 +1684,9 @@ extractUnionConstructor (Field (Union kts) (Core.fieldSelectionLabel -> fld)) =
16831684
extractUnionConstructor _ =
16841685
empty
16851686

1687+
{-| This is the underlying class that powers the `FromDhall` class's support
1688+
for automatically deriving a generic implementation for a union type
1689+
-}
16861690
class GenericFromDhallUnion t f where
16871691
genericUnionAutoWithNormalizer :: Proxy t -> InputNormalizer -> InterpretOptions -> UnionDecoder (f a)
16881692

dhall/src/Dhall/Binary.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -98,7 +98,7 @@ data StandardVersion
9898
-- ^ Version "1.0.0"
9999
deriving (Enum, Bounded)
100100

101-
-- | Render a `StandardVersion` as `Text`
101+
-- | Render a `StandardVersion` as `Data.Text.Text`
102102
renderStandardVersion :: StandardVersion -> Text
103103
renderStandardVersion NoVersion = "none"
104104
renderStandardVersion V_1_0_0 = "1.0.0"
@@ -1206,7 +1206,7 @@ instance Serialise (Expr Void Import) where
12061206
encodeExpression :: Serialise (Expr Void a) => Expr Void a -> ByteString
12071207
encodeExpression = Serialise.serialise
12081208

1209-
-- | Decode a Dhall expression from a CBOR `Term`
1209+
-- | Decode a Dhall expression from a CBOR `Codec.CBOR.Term.Term`
12101210
decodeExpression
12111211
:: Serialise (Expr s a) => ByteString -> Either DecodingFailure (Expr s a)
12121212
decodeExpression bytes =

dhall/src/Dhall/Context.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -15,8 +15,8 @@ module Dhall.Context (
1515
import Data.Text (Text)
1616
import Prelude hiding (lookup)
1717

18-
{-| A @(Context a)@ associates `Text` labels with values of type @a@. Each
19-
`Text` label can correspond to multiple values of type @a@
18+
{-| A @(Context a)@ associates `Data.Text.Text` labels with values of type @a@.
19+
Each `Data.Text.Text` label can correspond to multiple values of type @a@
2020
2121
The `Context` is used for type-checking when @(a = Expr X)@
2222

dhall/src/Dhall/Core.hs

Lines changed: 5 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -99,7 +99,7 @@ pretty :: Pretty a => a -> Text
9999
pretty = pretty_
100100
{-# INLINE pretty #-}
101101

102-
{-| Escape a `Text` literal using Dhall's escaping rules
102+
{-| Escape a `Data.Text.Text` literal using Dhall's escaping rules
103103
104104
Note that the result does not include surrounding quotes
105105
-}
@@ -111,7 +111,7 @@ escapeText = escapeText_
111111
{-| Utility used to implement the @--censor@ flag, by:
112112
113113
* Replacing all `Src` text with spaces
114-
* Replacing all `Text` literals inside type errors with spaces
114+
* Replacing all `Dhall.Syntax.Text` literals inside type errors with spaces
115115
-}
116116
censorExpression :: Expr Src a -> Expr Src a
117117
censorExpression (TextLit chunks) = TextLit (censorChunks chunks)
@@ -125,7 +125,9 @@ censorChunks (Chunks xys z) = Chunks xys' z'
125125

126126
xys' = [ (censorText x, censorExpression y) | (x, y) <- xys ]
127127

128-
-- | Utility used to censor `Text` by replacing all characters with a space
128+
{-| Utility used to censor `Data.Text.Text` by replacing all characters with a
129+
space
130+
-}
129131
censorText :: Text -> Text
130132
censorText = Data.Text.map (\_ -> ' ')
131133

dhall/src/Dhall/Deriving.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -58,7 +58,7 @@ module Dhall.Deriving
5858
, TrainCase
5959

6060
-- * Type-level versions of SingletonConstructors
61-
, ToSingletonConstructors
61+
, ToSingletonConstructors(..)
6262
, Bare
6363
, Wrapped
6464
, Smart
@@ -402,7 +402,7 @@ instance FromDhall Font where
402402
403403
Second, we defined the @Name@ type in Haskell as a newtype over @Text@, with a
404404
@getName@ field for unwrapping. In Dhall, however, @Name@ is a synonym of
405-
'Text', which is why 'input' above was expecting a record.
405+
'Data.Text.Text', which is why 'Dhall.input' above was expecting a record.
406406
The 'Dhall.Bare' option for 'singletonConstructors' is a perfect fit here:
407407
it translates Haskell singleton constructors into the Dhall version of the
408408
nested type, without wrapping it into a record.

dhall/src/Dhall/DirectoryTree.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -137,8 +137,8 @@ toDirectoryTree path expression = case expression of
137137
unexpectedExpression = expression
138138

139139
{- | This error indicates that you supplied an invalid Dhall expression to the
140-
`directoryTree` function. The Dhall expression could not be translated to
141-
a directory tree.
140+
`toDirectoryTree` function. The Dhall expression could not be translated
141+
to a directory tree.
142142
-}
143143
newtype FilesystemError =
144144
FilesystemError { unexpectedExpression :: Expr Void Void }

dhall/src/Dhall/Import.hs

Lines changed: 6 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -130,6 +130,7 @@ module Dhall.Import (
130130
, chainImport
131131
, dependencyToFile
132132
, ImportSemantics
133+
, HTTPHeader
133134
, Cycle(..)
134135
, ReferentiallyOpaque(..)
135136
, Imported(..)
@@ -345,6 +346,7 @@ instance Show MissingImports where
345346
throwMissingImport :: (MonadCatch m, Exception e) => e -> m a
346347
throwMissingImport e = throwM (MissingImports [toException e])
347348

349+
-- | HTTP headers
348350
type HTTPHeader = (CI ByteString, ByteString)
349351

350352
-- | Exception thrown when a HTTP url is imported but dhall was built without
@@ -498,9 +500,9 @@ chainImport (Chained parent) child =
498500
return (Chained (canonicalize (parent <> child)))
499501

500502
-- | Load an import, resulting in a fully resolved, type-checked and normalised
501-
-- expression. @loadImport@ handles the 'hot' cache in @Status@ and defers to
502-
-- `loadImportWithSemanticCache` for imports that aren't in the @Status@ cache
503-
-- already.
503+
-- expression. @loadImport@ handles the \"hot\" cache in @Status@ and defers
504+
-- to @loadImportWithSemanticCache@ for imports that aren't in the @Status@
505+
-- cache already.
504506
loadImport :: Chained -> StateT Status IO ImportSemantics
505507
loadImport import_ = do
506508
Status {..} <- State.get
@@ -513,7 +515,7 @@ loadImport import_ = do
513515
return importSemantics
514516

515517
-- | Load an import from the 'semantic cache'. Defers to
516-
-- `loadImportWithSemisemanticCache` for imports that aren't frozen (and
518+
-- @loadImportWithSemisemanticCache@ for imports that aren't frozen (and
517519
-- therefore not cached semantically), as well as those that aren't cached yet.
518520
loadImportWithSemanticCache :: Chained -> StateT Status IO ImportSemantics
519521
loadImportWithSemanticCache

0 commit comments

Comments
 (0)