Skip to content

Commit bb0e91e

Browse files
committed
Fix more haddock warnings
1 parent 1bb768a commit bb0e91e

File tree

9 files changed

+52
-52
lines changed

9 files changed

+52
-52
lines changed

Codec/Archive/Tar.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -84,7 +84,7 @@ module Codec.Archive.Tar (
8484
-- called a \"directory traversal vulnerability\". Historically, such
8585
-- vulnerabilities have been common in packages handling tar archives.
8686
--
87-
-- The 'extract' and 'unpack' functions check for bad file names. See the
87+
-- The 'extract' and 'Codec.Archive.Tar.unpack' functions check for bad file names. See the
8888
-- 'Codec.Archive.Tar.Check.checkSecurity' function for more details.
8989
-- If you need to do any custom
9090
-- unpacking then you should use this.
@@ -156,7 +156,7 @@ module Codec.Archive.Tar (
156156
-- The style of error handling by returning structured errors. The pure
157157
-- functions in the library do not throw exceptions, they return the errors
158158
-- as data. The IO actions in the library can throw exceptions, in particular
159-
-- the 'unpack' action does this. All the error types used are an instance of
159+
-- the 'Codec.Archive.Tar.unpack' action does this. All the error types used are an instance of
160160
-- the standard 'Exception' class so it is possible to 'throw' and 'catch'
161161
-- them.
162162

Codec/Archive/Tar/Index.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -22,7 +22,7 @@ module Codec.Archive.Tar.Index (
2222
-- within the archive.
2323
--
2424
-- This module provides an index of a @tar@ file. A linear pass of the
25-
-- @tar@ file is needed to 'build' the 'TarIndex', but thereafter you can
25+
-- @tar@ file is needed to 'build' the t'TarIndex', but thereafter you can
2626
-- 'lookup' paths in the @tar@ file, and then use 'hReadEntry' to
2727
-- seek to the right part of the file and read the entry.
2828
--
@@ -73,12 +73,12 @@ import Codec.Archive.Tar.Index.Internal
7373

7474
-- $incremental-construction
7575
-- If you need more control than 'build' then you can construct the index
76-
-- in an accumulator style using the 'IndexBuilder' and operations.
76+
-- in an accumulator style using the t'IndexBuilder' and operations.
7777
--
7878
-- Start with 'empty' and use 'addNextEntry' (or 'skipNextEntry') for
7979
-- each 'Codec.Archive.Tar.Entry.Entry' in the tar file in order. Every entry must added or skipped in
80-
-- order, otherwise the resulting 'TarIndex' will report the wrong
81-
-- 'TarEntryOffset's. At the end use 'finalise' to get the 'TarIndex'.
80+
-- order, otherwise the resulting t'TarIndex' will report the wrong
81+
-- 'TarEntryOffset's. At the end use 'finalise' to get the t'TarIndex'.
8282
--
8383
-- For example, 'build' is simply:
8484
--

Codec/Archive/Tar/Index/IntTrie.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -123,10 +123,10 @@ toList = concatMap (aux []) . (`completionsFrom` 0)
123123
-- Toplevel trie array construction
124124
--
125125

126-
-- So constructing the 'IntTrie' as a whole is just a matter of stringing
126+
-- So constructing the t'IntTrie' as a whole is just a matter of stringing
127127
-- together all the bits
128128

129-
-- | Build an 'IntTrie' from a bunch of (key, value) pairs, where the keys
129+
-- | Build an t'IntTrie' from a bunch of (key, value) pairs, where the keys
130130
-- are sequences.
131131
--
132132
construct :: [([Key], Value)] -> IntTrie

Codec/Archive/Tar/Index/Internal.hs

Lines changed: 19 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -123,7 +123,7 @@ data TarIndex = TarIndex
123123
instance NFData TarIndex where
124124
rnf (TarIndex _ _ _) = () -- fully strict by construction
125125

126-
-- | The result of 'lookup' in a 'TarIndex'. It can either be a file directly,
126+
-- | The result of 'Codec.Archive.Tar.Index.lookup' in a t'TarIndex'. It can either be a file directly,
127127
-- or a directory entry containing further entries (and all subdirectories
128128
-- recursively). Note that the subtrees are constructed lazily, so it's
129129
-- cheaper if you don't look at them.
@@ -144,7 +144,7 @@ newtype PathComponentId = PathComponentId Int
144144
type TarEntryOffset = Word32
145145

146146

147-
-- | Look up a given filepath in the 'TarIndex'. It may return a 'TarFileEntry'
147+
-- | Look up a given filepath in the t'TarIndex'. It may return a 'TarFileEntry'
148148
-- containing the 'TarEntryOffset' of the file within the tar file, or if
149149
-- the filepath identifies a directory then it returns a 'TarDir' containing
150150
-- the list of files within that directory.
@@ -195,7 +195,7 @@ toList (TarIndex pathTable pathTrie _) =
195195
, let path = FilePath.joinPath (map (fromComponentId pathTable . keyToPathComponentId) cids) ]
196196

197197

198-
-- | Build a 'TarIndex' from a sequence of tar 'Entries'. The 'Entries' are
198+
-- | Build a t'TarIndex' from a sequence of tar 'Entries'. The 'Entries' are
199199
-- assumed to start at offset @0@ within a file.
200200
--
201201
build :: Entries e -> Either e TarIndex
@@ -205,7 +205,7 @@ build = go empty
205205
go !builder Done = Right $! finalise builder
206206
go !_ (Fail err) = Left err
207207

208-
-- | The intermediate type used for incremental construction of a 'TarIndex'.
208+
-- | The intermediate type used for incremental construction of a t'TarIndex'.
209209
--
210210
data IndexBuilder
211211
= IndexBuilder !(StringTableBuilder PathComponentId)
@@ -216,12 +216,12 @@ data IndexBuilder
216216
instance NFData IndexBuilder where
217217
rnf IndexBuilder{} = () -- fully strict by construction
218218

219-
-- | The initial empty 'IndexBuilder'.
219+
-- | The initial empty t'IndexBuilder'.
220220
--
221221
empty :: IndexBuilder
222222
empty = IndexBuilder StringTable.empty IntTrie.empty 0
223223

224-
-- | Add the next t'Entry' into the 'IndexBuilder'.
224+
-- | Add the next t'Entry' into the t'IndexBuilder'.
225225
--
226226
addNextEntry :: Entry -> IndexBuilder -> IndexBuilder
227227
addNextEntry entry (IndexBuilder stbl itrie nextOffset) =
@@ -233,13 +233,13 @@ addNextEntry entry (IndexBuilder stbl itrie nextOffset) =
233233
itrie' = IntTrie.insert (map pathComponentIdToKey cids) (IntTrie.Value nextOffset) itrie
234234

235235
-- | Use this function if you want to skip some entries and not add them to the
236-
-- final 'TarIndex'.
236+
-- final t'TarIndex'.
237237
--
238238
skipNextEntry :: Entry -> IndexBuilder -> IndexBuilder
239239
skipNextEntry entry (IndexBuilder stbl itrie nextOffset) =
240240
IndexBuilder stbl itrie (nextEntryOffset entry nextOffset)
241241

242-
-- | Finish accumulating t'Entry' information and build the compact 'TarIndex'
242+
-- | Finish accumulating t'Entry' information and build the compact t'TarIndex'
243243
-- lookup structure.
244244
--
245245
finalise :: IndexBuilder -> TarIndex
@@ -250,8 +250,8 @@ finalise (IndexBuilder stbl itrie finalOffset) =
250250
pathTrie = IntTrie.finalise itrie
251251

252252
-- | This is the offset immediately following the entry most recently added
253-
-- to the 'IndexBuilder'. You might use this if you need to know the offsets
254-
-- but don't want to use the 'TarIndex' lookup structure.
253+
-- to the t'IndexBuilder'. You might use this if you need to know the offsets
254+
-- but don't want to use the t'TarIndex' lookup structure.
255255
-- Use with 'hSeekEntryOffset'. See also 'nextEntryOffset'.
256256
--
257257
indexNextEntryOffset :: IndexBuilder -> TarEntryOffset
@@ -268,7 +268,7 @@ indexEndEntryOffset (TarIndex _ _ off) = off
268268
-- offset of the current entry.
269269
--
270270
-- This is much like using 'skipNextEntry' and 'indexNextEntryOffset', but without
271-
-- using an 'IndexBuilder'.
271+
-- using an t'IndexBuilder'.
272272
--
273273
nextEntryOffset :: Entry -> TarEntryOffset -> TarEntryOffset
274274
nextEntryOffset entry offset =
@@ -302,14 +302,14 @@ splitDirectories bs =
302302

303303
-- | Resume building an existing index
304304
--
305-
-- A 'TarIndex' is optimized for a highly compact and efficient in-memory
305+
-- A t'TarIndex' is optimized for a highly compact and efficient in-memory
306306
-- representation. This, however, makes it read-only. If you have an existing
307-
-- 'TarIndex' for a large file, and want to add to it, you can translate the
308-
-- 'TarIndex' back to an 'IndexBuilder'. Be aware that this is a relatively
309-
-- costly operation (linear in the size of the 'TarIndex'), though still
307+
-- t'TarIndex' for a large file, and want to add to it, you can translate the
308+
-- t'TarIndex' back to an t'IndexBuilder'. Be aware that this is a relatively
309+
-- costly operation (linear in the size of the t'TarIndex'), though still
310310
-- faster than starting again from scratch.
311311
--
312-
-- This is the left inverse to 'finalise' (modulo ordering).
312+
-- This is the left inverse to 'Codec.Archive.Tar.Index.finalise' (modulo ordering).
313313
--
314314
unfinalise :: TarIndex -> IndexBuilder
315315
unfinalise (TarIndex pathTable pathTrie finalOffset) =
@@ -428,7 +428,7 @@ hReadEntryHeaderOrEof hnd blockOff = do
428428
-- | Seek to the end of a tar file, to the position where new entries can
429429
-- be appended, and return that 'TarEntryOffset'.
430430
--
431-
-- If you have a valid 'TarIndex' for this tar file then you should supply it
431+
-- If you have a valid t'TarIndex' for this tar file then you should supply it
432432
-- because it allows seeking directly to the correct location.
433433
--
434434
-- If you do not have an index, then this becomes an expensive linear
@@ -461,7 +461,7 @@ hSeekEndEntryOffset hnd Nothing = do
461461
-- (de)serialisation
462462
--
463463

464-
-- | The 'TarIndex' is compact in memory, and it has a similarly compact
464+
-- | The t'TarIndex' is compact in memory, and it has a similarly compact
465465
-- external representation.
466466
--
467467
serialise :: TarIndex -> BS.ByteString
@@ -487,7 +487,7 @@ serialiseBuilder (TarIndex stringTable intTrie finalOffset) =
487487
<> StringTable.serialise stringTable
488488
<> IntTrie.serialise intTrie
489489

490-
-- | Read the external representation back into a 'TarIndex'.
490+
-- | Read the external representation back into a t'TarIndex'.
491491
--
492492
deserialise :: BS.ByteString -> Maybe (TarIndex, BS.ByteString)
493493
deserialise bs

Codec/Archive/Tar/Index/StringTable.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -91,7 +91,7 @@ index (StringTable bs offsets _ids ixs) =
9191
index' bs offsets . (ixs !) . fromIntegral . fromEnum
9292

9393

94-
-- | Given a list of strings, construct a 'StringTable' mapping those strings
94+
-- | Given a list of strings, construct a t'StringTable' mapping those strings
9595
-- to a dense set of integers. Also return the ids for all the strings used
9696
-- in the construction.
9797
--

Codec/Archive/Tar/Pack.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -62,15 +62,15 @@ import Codec.Archive.Tar.Check.Internal (checkEntrySecurity)
6262
--
6363
-- * This function returns results lazily. Subdirectories are scanned
6464
-- and files are read one by one as the list of entries is consumed.
65-
-- Do not change their contents before the output of 'pack' was consumed in full.
65+
-- Do not change their contents before the output of 'Codec.Archive.Tar.pack' was consumed in full.
6666
--
6767
pack
6868
:: FilePath -- ^ Base directory
6969
-> [FilePath] -- ^ Files and directories to pack, relative to the base dir
7070
-> IO [Entry]
7171
pack = packAndCheck (const Nothing)
7272

73-
-- | Like 'pack', but allows to specify additional sanity/security
73+
-- | Like 'Codec.Archive.Tar.pack', but allows to specify additional sanity/security
7474
-- checks on the input filenames. This is useful if you know which
7575
-- check will be used on client side
7676
-- in 'Codec.Archive.Tar.unpack' / 'Codec.Archive.Tar.unpackAndCheck'.

Codec/Archive/Tar/Types.hs

Lines changed: 20 additions & 20 deletions
Original file line numberDiff line numberDiff line change
@@ -121,7 +121,7 @@ type Permissions = FileMode
121121

122122
-- | Polymorphic tar archive entry. High-level interfaces
123123
-- commonly work with 'GenEntry' 'FilePath' 'FilePath',
124-
-- while low-level ones use 'GenEntry' 'TarPath' 'LinkTarget'.
124+
-- while low-level ones use 'GenEntry' t'TarPath' t'LinkTarget'.
125125
--
126126
-- @since 0.6.0.0
127127
data GenEntry tarPath linkTarget = Entry {
@@ -161,7 +161,7 @@ entryPath = fromTarPath . entryTarPath
161161

162162
-- | Polymorphic content of a tar archive entry. High-level interfaces
163163
-- commonly work with 'GenEntryContent' 'FilePath',
164-
-- while low-level ones use 'GenEntryContent' 'LinkTarget'.
164+
-- while low-level ones use 'GenEntryContent' t'LinkTarget'.
165165
--
166166
-- Portable archives should contain only 'NormalFile' and 'Directory'.
167167
--
@@ -375,7 +375,7 @@ instance NFData TarPath where
375375
instance Show TarPath where
376376
show = show . fromTarPath
377377

378-
-- | Convert a 'TarPath' to a native 'FilePath'.
378+
-- | Convert a t'TarPath' to a native 'FilePath'.
379379
--
380380
-- The native 'FilePath' will use the native directory separator but it is not
381381
-- otherwise checked for validity or sanity. In particular:
@@ -391,23 +391,23 @@ instance Show TarPath where
391391
fromTarPath :: TarPath -> FilePath
392392
fromTarPath = fromPosixString . fromTarPathInternal (PS.unsafeFromChar FilePath.Native.pathSeparator)
393393

394-
-- | Convert a 'TarPath' to a Unix\/Posix 'FilePath'.
394+
-- | Convert a t'TarPath' to a Unix\/Posix 'FilePath'.
395395
--
396396
-- The difference compared to 'fromTarPath' is that it always returns a Unix
397397
-- style path irrespective of the current operating system.
398398
--
399-
-- This is useful to check how a 'TarPath' would be interpreted on a specific
399+
-- This is useful to check how a t'TarPath' would be interpreted on a specific
400400
-- operating system, eg to perform portability checks.
401401
--
402402
fromTarPathToPosixPath :: TarPath -> FilePath
403403
fromTarPathToPosixPath = fromPosixString . fromTarPathInternal (PS.unsafeFromChar FilePath.Posix.pathSeparator)
404404

405-
-- | Convert a 'TarPath' to a Windows 'FilePath'.
405+
-- | Convert a t'TarPath' to a Windows 'FilePath'.
406406
--
407407
-- The only difference compared to 'fromTarPath' is that it always returns a
408408
-- Windows style path irrespective of the current operating system.
409409
--
410-
-- This is useful to check how a 'TarPath' would be interpreted on a specific
410+
-- This is useful to check how a t'TarPath' would be interpreted on a specific
411411
-- operating system, eg to perform portability checks.
412412
--
413413
fromTarPathToWindowsPath :: TarPath -> FilePath
@@ -425,11 +425,11 @@ fromTarPathInternal sep = go
425425
| otherwise = adjustSeps prefix <> PS.cons sep (adjustSeps name)
426426
{-# INLINE fromTarPathInternal #-}
427427

428-
-- | Convert a native 'FilePath' to a 'TarPath'.
428+
-- | Convert a native 'FilePath' to a t'TarPath'.
429429
--
430430
-- The conversion may fail if the 'FilePath' is empty or too long.
431431
toTarPath :: Bool -- ^ Is the path for a directory? This is needed because for
432-
-- directories a 'TarPath' must always use a trailing @\/@.
432+
-- directories a t'TarPath' must always use a trailing @\/@.
433433
-> FilePath
434434
-> Either String TarPath
435435
toTarPath isDir path = case toTarPath' path' of
@@ -441,7 +441,7 @@ toTarPath isDir path = case toTarPath' path' of
441441
then path <> [FilePath.Native.pathSeparator]
442442
else path
443443

444-
-- | Convert a native 'FilePath' to a 'TarPath'.
444+
-- | Convert a native 'FilePath' to a t'TarPath'.
445445
-- Directory paths must always have a trailing @\/@, this is not checked.
446446
--
447447
-- @since 0.6.0.0
@@ -461,11 +461,11 @@ toTarPath'
461461
-- @since 0.6.0.0
462462
data ToTarPathResult
463463
= FileNameEmpty
464-
-- ^ 'FilePath' was empty, but 'TarPath' must be non-empty.
464+
-- ^ 'FilePath' was empty, but t'TarPath' must be non-empty.
465465
| FileNameOK TarPath
466-
-- ^ All good, this is just a normal 'TarPath'.
466+
-- ^ All good, this is just a normal t'TarPath'.
467467
| FileNameTooLong TarPath
468-
-- ^ 'FilePath' was longer than 255 characters, 'TarPath' contains
468+
-- ^ 'FilePath' was longer than 255 characters, t'TarPath' contains
469469
-- a truncated part only. An actual entry must be preceded by
470470
-- 'longLinkEntry'.
471471

@@ -515,7 +515,7 @@ newtype LinkTarget = LinkTarget PosixString
515515
instance NFData LinkTarget where
516516
rnf (LinkTarget bs) = rnf bs
517517

518-
-- | Convert a native 'FilePath' to a tar 'LinkTarget'.
518+
-- | Convert a native 'FilePath' to a tar t'LinkTarget'.
519519
-- string is longer than 100 characters or if it contains non-portable
520520
-- characters.
521521
toLinkTarget :: FilePath -> Maybe LinkTarget
@@ -534,7 +534,7 @@ instance Exception LinkTargetException where
534534
displayException (TooLong _) = "The link target is too long"
535535

536536
-- | Convert a native 'FilePath' to a unix filepath suitable for
537-
-- using as 'LinkTarget'. Does not error if longer than 100 characters.
537+
-- using as t'LinkTarget'. Does not error if longer than 100 characters.
538538
toLinkTarget' :: FilePath -> Maybe FilePath
539539
toLinkTarget' path
540540
| FilePath.Native.isAbsolute path = Nothing
@@ -544,15 +544,15 @@ toLinkTarget' path
544544
= FilePath.Posix.addTrailingPathSeparator
545545
| otherwise = id
546546

547-
-- | Convert a tar 'LinkTarget' to a native 'FilePath'.
547+
-- | Convert a tar t'LinkTarget' to a native 'FilePath'.
548548
fromLinkTarget :: LinkTarget -> FilePath
549549
fromLinkTarget (LinkTarget pathbs) = fromFilePathToNative $ fromPosixString pathbs
550550

551-
-- | Convert a tar 'LinkTarget' to a Unix\/POSIX 'FilePath' (@\'/\'@ path separators).
551+
-- | Convert a tar t'LinkTarget' to a Unix\/POSIX 'FilePath' (@\'/\'@ path separators).
552552
fromLinkTargetToPosixPath :: LinkTarget -> FilePath
553553
fromLinkTargetToPosixPath (LinkTarget pathbs) = fromPosixString pathbs
554554

555-
-- | Convert a tar 'LinkTarget' to a Windows 'FilePath' (@\'\\\\\'@ path separators).
555+
-- | Convert a tar t'LinkTarget' to a Windows 'FilePath' (@\'\\\\\'@ path separators).
556556
fromLinkTargetToWindowsPath :: LinkTarget -> FilePath
557557
fromLinkTargetToWindowsPath (LinkTarget pathbs) =
558558
fromFilePathToWindowsPath $ fromPosixString pathbs
@@ -581,7 +581,7 @@ fromFilePathInternal fromSep toSep = adjustSeps
581581
-- | Polymorphic sequence of archive entries.
582582
-- High-level interfaces
583583
-- commonly work with 'GenEntries' 'FilePath' 'FilePath',
584-
-- while low-level ones use 'GenEntries' 'TarPath' 'LinkTarget'.
584+
-- while low-level ones use 'GenEntries' t'TarPath' t'LinkTarget'.
585585
--
586586
-- The point of this type as opposed to just using a list is that it makes the
587587
-- failure case explicit. We need this because the sequence of entries we get
@@ -647,7 +647,7 @@ unfoldEntriesM interleave f = unfold
647647
Right (Just e) -> Next e <$> interleave unfold
648648

649649
-- | This is like the standard 'Data.List.foldr' function on lists, but for 'Entries'.
650-
-- Compared to 'foldr' it takes an extra function to account for the
650+
-- Compared to 'Data.List.foldr' it takes an extra function to account for the
651651
-- possibility of failure.
652652
--
653653
-- This is used to consume a sequence of entries. For example it could be used

Codec/Archive/Tar/Unpack.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -91,7 +91,7 @@ unpack
9191
-> IO ()
9292
unpack = unpackAndCheck (fmap SomeException . checkEntrySecurity)
9393

94-
-- | Like 'unpack', but run custom sanity/security checks instead of 'checkEntrySecurity'.
94+
-- | Like 'Codec.Archive.Tar.unpack', but run custom sanity/security checks instead of 'checkEntrySecurity'.
9595
-- For example,
9696
--
9797
-- > import Control.Exception (SomeException(..))

test/Codec/Archive/Tar/Index/Tests.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -248,7 +248,7 @@ instance Arbitrary SimpleTarArchive where
248248
, 1022 , 1023 , 1024 , 1025 , 1026
249249
]
250250

251-
-- | 'IndexBuilder' constructed from a 'SimpleIndex'
251+
-- | t'IndexBuilder' constructed from a 'SimpleIndex'
252252
newtype SimpleIndexBuilder = SimpleIndexBuilder IndexBuilder
253253
deriving Show
254254

0 commit comments

Comments
 (0)