Skip to content

Commit dd4ee45

Browse files
committed
Improve documentation
1 parent 5fc9acc commit dd4ee45

File tree

8 files changed

+89
-33
lines changed

8 files changed

+89
-33
lines changed

Codec/Archive/Tar/Check/Internal.hs

Lines changed: 6 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -76,7 +76,8 @@ checkSecurity
7676
-> GenEntries FilePath FilePath (Either (Either e DecodeLongNamesError) FileNameError)
7777
checkSecurity = checkEntries checkEntrySecurity . decodeLongNames
7878

79-
-- |
79+
-- | Worker of 'checkSecurity'.
80+
--
8081
-- @since 0.6.0.0
8182
checkEntrySecurity :: GenEntry FilePath FilePath -> Maybe FileNameError
8283
checkEntrySecurity e =
@@ -162,7 +163,8 @@ checkTarbomb expectedTopDir
162163
= checkEntries (checkEntryTarbomb expectedTopDir)
163164
. decodeLongNames
164165

165-
-- |
166+
-- | Worker of 'checkTarbomb'.
167+
--
166168
-- @since 0.6.0.0
167169
checkEntryTarbomb :: FilePath -> GenEntry FilePath linkTarget -> Maybe TarBombError
168170
checkEntryTarbomb expectedTopDir entry = do
@@ -221,7 +223,8 @@ checkPortability
221223
-> GenEntries FilePath FilePath (Either (Either e DecodeLongNamesError) PortabilityError)
222224
checkPortability = checkEntries checkEntryPortability . decodeLongNames
223225

224-
-- |
226+
-- | Worker of 'checkPortability'.
227+
--
225228
-- @since 0.6.0.0
226229
checkEntryPortability :: GenEntry FilePath linkTarget -> Maybe PortabilityError
227230
checkEntryPortability entry

Codec/Archive/Tar/Index.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -76,7 +76,7 @@ import Codec.Archive.Tar.Index.Internal
7676
-- in an accumulator style using the 'IndexBuilder' and operations.
7777
--
7878
-- Start with 'empty' and use 'addNextEntry' (or 'skipNextEntry') for
79-
-- each 'Entry' in the tar file in order. Every entry must added or skipped in
79+
-- each 'Codec.Archive.Tar.Entry.Entry' in the tar file in order. Every entry must added or skipped in
8080
-- order, otherwise the resulting 'TarIndex' will report the wrong
8181
-- 'TarEntryOffset's. At the end use 'finalise' to get the 'TarIndex'.
8282
--

Codec/Archive/Tar/LongNames.hs

Lines changed: 15 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -11,14 +11,23 @@ import Control.Exception
1111
import qualified Data.ByteString.Char8 as B
1212
import qualified Data.ByteString.Lazy.Char8 as BL
1313

14+
-- | Errors raised by 'decodeLongNames'.
1415
data DecodeLongNamesError
1516
= TwoTypeKEntries
17+
-- ^ Two adjacent 'OtherEntryType' @\'K\'@ nodes.
1618
| TwoTypeLEntries
19+
-- ^ Two adjacent 'OtherEntryType' @\'L\'@ nodes.
1720
| NoLinkEntryAfterTypeKEntry
21+
-- ^ 'OtherEntryType' @\'K\'@ node is not followed by a 'SymbolicLink' / 'HardLink'.
1822
deriving (Eq, Ord, Show)
1923

2024
instance Exception DecodeLongNamesError
2125

26+
-- | Translate high-level entries with POSIX 'FilePath's for files and symlinks
27+
-- into entries suitable for serialization by emitting additional
28+
-- 'OtherEntryType' @\'K\'@ and 'OtherEntryType' @\'L\'@ nodes.
29+
--
30+
-- Input 'FilePath's must be POSIX file names, not native ones.
2231
encodeLongNames
2332
:: GenEntry FilePath FilePath
2433
-> [Entry]
@@ -63,7 +72,12 @@ encodeLinkPath lnk = case toTarPath' lnk of
6372
FileNameTooLong (TarPath name _) ->
6473
(Just $ longSymLinkEntry lnk, LinkTarget name)
6574

66-
-- | Resolved 'FilePath's are still POSIX file names, not native ones.
75+
-- | Translate low-level entries (usually freshly deserialized) into
76+
-- high-level entries with POSIX 'FilePath's for files and symlinks
77+
-- by parsing and eliminating
78+
-- 'OtherEntryType' @\'K\'@ and 'OtherEntryType' @\'L\'@ nodes.
79+
--
80+
-- Resolved 'FilePath's are still POSIX file names, not native ones.
6781
decodeLongNames
6882
:: Entries e
6983
-> GenEntries FilePath FilePath (Either e DecodeLongNamesError)

Codec/Archive/Tar/Pack.hs

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -71,8 +71,10 @@ pack
7171
-> IO [Entry]
7272
pack = packAndCheck (const Nothing)
7373

74-
-- | Like 'pack', but allows to specify any sanity/security checks on the input
75-
-- filenames.
74+
-- | Like 'pack', but allows to specify additional sanity/security
75+
-- checks on the input filenames. This is useful if you know which
76+
-- check will be used on client side
77+
-- in 'Codec.Tar.Check.unpack' / 'Codec.Tar.Check.unpackAndCheck'.
7678
--
7779
-- @since 0.6.0.0
7880
packAndCheck

Codec/Archive/Tar/PackAscii.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,7 @@ import qualified Data.ByteString.Char8 as BS.Char8
66
import Data.Char
77
import GHC.Stack
88

9-
-- | We should really migrate to 'OsPath' from 'filepath',
9+
-- | We should really migrate to @OsPath@ from @filepath@ package,
1010
-- but for now let's not corrupt data silently.
1111
packAscii :: HasCallStack => FilePath -> BS.Char8.ByteString
1212
packAscii xs

Codec/Archive/Tar/Types.hs

Lines changed: 45 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -100,13 +100,14 @@ type DevMinor = Int
100100
type TypeCode = Char
101101
type Permissions = FileMode
102102

103-
-- | Tar archive entry.
103+
-- | Polymorphic tar archive entry. High-level interfaces
104+
-- commonly work with 'GenEntry' 'FilePath' 'FilePath',
105+
-- while low level uses 'GenEntry' 'TarPath' 'LinkTarget'.
104106
--
105107
-- @since 0.6.0.0
106108
data GenEntry tarPath linkTarget = Entry {
107109

108-
-- | The path of the file or directory within the archive. This is in a
109-
-- tar-specific form. Use 'entryPath' to get a native 'FilePath'.
110+
-- | The path of the file or directory within the archive.
110111
entryTarPath :: !tarPath,
111112

112113
-- | The real content of the entry. For 'NormalFile' this includes the
@@ -127,14 +128,18 @@ data GenEntry tarPath linkTarget = Entry {
127128
}
128129
deriving (Eq, Show)
129130

131+
-- | Monomorphic tar archive entry, ready for serialization / deserialization.
132+
--
130133
type Entry = GenEntry TarPath LinkTarget
131134

132135
-- | Native 'FilePath' of the file or directory within the archive.
133136
--
134-
entryPath :: Entry -> FilePath
137+
entryPath :: GenEntry TarPath linkTarget -> FilePath
135138
entryPath = fromTarPath . entryTarPath
136139

137-
-- | The content of a tar archive entry, which depends on the type of entry.
140+
-- | Polymorphic content of a tar archive entry. High-level interfaces
141+
-- commonly work with 'GenEntryContent' 'FilePath',
142+
-- while low level uses 'GenEntryContent' 'LinkTarget'.
138143
--
139144
-- Portable archives should contain only 'NormalFile' and 'Directory'.
140145
--
@@ -153,6 +158,8 @@ data GenEntryContent linkTarget
153158
{-# UNPACK #-} !FileSize
154159
deriving (Eq, Ord, Show)
155160

161+
-- | Monomorphic content of a tar archive entry,
162+
-- ready for serialization / deserialization.
156163
type EntryContent = GenEntryContent LinkTarget
157164

158165
data Ownership = Ownership {
@@ -183,17 +190,15 @@ data Format =
183190
-- | The \"USTAR\" format is an extension of the classic V7 format. It was
184191
-- later standardised by POSIX. It has some restrictions but is the most
185192
-- portable format.
186-
--
187193
| UstarFormat
188194

189195
-- | The GNU tar implementation also extends the classic V7 format, though
190-
-- in a slightly different way from the USTAR format. In general for new
191-
-- archives the standard USTAR/POSIX should be used.
192-
--
196+
-- in a slightly different way from the USTAR format. This is the only format
197+
-- supporting long file names.
193198
| GnuFormat
194199
deriving (Eq, Ord, Show)
195200

196-
instance NFData (GenEntry a b) where
201+
instance NFData (GenEntry tarPath linkTarget) where
197202
rnf (Entry _ c _ _ _ _) = rnf c
198203

199204
instance NFData (GenEntryContent linkTarget) where
@@ -224,7 +229,7 @@ directoryPermissions :: Permissions
224229
directoryPermissions = 0o0755
225230

226231
-- | An 'Entry' with all default values except for the file name and type. It
227-
-- uses the portable USTAR/POSIX format (see 'UstarHeader').
232+
-- uses the portable USTAR/POSIX format (see 'UstarFormat').
228233
--
229234
-- You can use this as a basis and override specific fields, eg:
230235
--
@@ -352,7 +357,8 @@ instance Show TarPath where
352357
--
353358
-- * The tar path may be an absolute path or may contain @\"..\"@ components.
354359
-- For security reasons this should not usually be allowed, but it is your
355-
-- responsibility to check for these conditions (eg using 'checkEntrySecurity').
360+
-- responsibility to check for these conditions
361+
-- (e.g., using 'Codec.Archive.Tar.Check.checkEntrySecurity').
356362
--
357363
fromTarPath :: TarPath -> FilePath
358364
fromTarPath = BS.Char8.unpack . fromTarPathInternal FilePath.Native.pathSeparator
@@ -543,15 +549,15 @@ fromFilePathToWindowsPath path = adjustDirectory $
543549
-- * Entries type
544550
--
545551

546-
-- | A tar archive is a sequence of entries.
552+
-- | Polymorphic sequence of archive entries.
553+
-- High-level interfaces
554+
-- commonly work with 'GenEntries' 'FilePath' 'FilePath',
555+
-- while low level uses 'GenEntries' 'TarPath' 'LinkTarget'.
547556
--
548557
-- The point of this type as opposed to just using a list is that it makes the
549558
-- failure case explicit. We need this because the sequence of entries we get
550559
-- from reading a tarball can include errors.
551560
--
552-
-- It is a concrete data type so you can manipulate it directly but it is often
553-
-- clearer to use the provided functions for mapping, folding and unfolding.
554-
--
555561
-- Converting from a list can be done with just @foldr Next Done@. Converting
556562
-- back into a list can be done with 'foldEntries' however in that case you
557563
-- must be prepared to handle the 'Fail' case inherent in the 'Entries' type.
@@ -574,16 +580,21 @@ data GenEntries tarPath linkTarget e
574580

575581
infixr 5 `Next`
576582

583+
-- | Monomorphic sequence of archive entries,
584+
-- ready for serialization / deserialization.
577585
type Entries e = GenEntries TarPath LinkTarget e
578586

579-
-- | This is like the standard 'unfoldr' function on lists, but for 'Entries'.
587+
-- | This is like the standard 'Data.List.unfoldr' function on lists, but for 'Entries'.
580588
-- It includes failure as an extra possibility that the stepper function may
581589
-- return.
582590
--
583591
-- It can be used to generate 'Entries' from some other type. For example it is
584592
-- used internally to lazily unfold entries from a 'LBS.ByteString'.
585593
--
586-
unfoldEntries :: (a -> Either e (Maybe (Entry, a))) -> a -> Entries e
594+
unfoldEntries
595+
:: (a -> Either e (Maybe (GenEntry tarPath linkTarget, a)))
596+
-> a
597+
-> GenEntries tarPath linkTarget e
587598
unfoldEntries f = unfold
588599
where
589600
unfold x = case f x of
@@ -598,7 +609,11 @@ unfoldEntries f = unfold
598609
-- This is used to consume a sequence of entries. For example it could be used
599610
-- to scan a tarball for problems or to collect an index of the contents.
600611
--
601-
foldEntries :: (GenEntry tarPath linkTarget -> a -> a) -> a -> (e -> a) -> GenEntries tarPath linkTarget e -> a
612+
foldEntries
613+
:: (GenEntry tarPath linkTarget -> a -> a)
614+
-> a
615+
-> (e -> a)
616+
-> GenEntries tarPath linkTarget e -> a
602617
foldEntries next done fail' = fold
603618
where
604619
fold (Next e es) = next e (fold es)
@@ -609,7 +624,11 @@ foldEntries next done fail' = fold
609624
-- accumulator result, or the failure along with the intermediate accumulator
610625
-- value.
611626
--
612-
foldlEntries :: (a -> Entry -> a) -> a -> Entries e -> Either (e, a) a
627+
foldlEntries
628+
:: (a -> GenEntry tarPath linkTarget -> a)
629+
-> a
630+
-> GenEntries tarPath linkTarget e
631+
-> Either (e, a) a
613632
foldlEntries f = go
614633
where
615634
go !acc (Next e es) = go (f acc e) es
@@ -623,14 +642,19 @@ foldlEntries f = go
623642
-- 'mapEntriesNoFail'
624643
mapEntries
625644
:: (GenEntry tarPath linkTarget -> Either e' (GenEntry tarPath linkTarget))
645+
-- ^ Function to apply to each entry
626646
-> GenEntries tarPath linkTarget e
647+
-- ^ Input sequence
627648
-> GenEntries tarPath linkTarget (Either e e')
628649
mapEntries f =
629650
foldEntries (\entry rest -> either (Fail . Right) (`Next` rest) (f entry)) Done (Fail . Left)
630651

631652
-- | Like 'mapEntries' but the mapping function itself cannot fail.
632653
--
633-
mapEntriesNoFail :: (Entry -> Entry) -> Entries e -> Entries e
654+
mapEntriesNoFail
655+
:: (GenEntry tarPath linkTarget -> GenEntry tarPath linkTarget)
656+
-> GenEntries tarPath linkTarget e
657+
-> GenEntries tarPath linkTarget e
634658
mapEntriesNoFail f =
635659
foldEntries (Next . f) Done Fail
636660

Codec/Archive/Tar/Unpack.hs

Lines changed: 15 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -81,18 +81,30 @@ import Control.Exception as Exception
8181
-- On its own, this function only checks for security (using 'checkEntrySecurity').
8282
-- Use 'unpackAndCheck' if you need more checks.
8383
--
84-
unpack :: Exception e => FilePath -> Entries e -> IO ()
84+
unpack
85+
:: Exception e
86+
=> FilePath
87+
-- ^ Base directory
88+
-> Entries e
89+
-- ^ Entries to upack
90+
-> IO ()
8591
unpack = unpackAndCheck (fmap SomeException . checkEntrySecurity)
8692

87-
-- | Like 'unpack', but does not perform any sanity/security checks on the tar entries.
88-
-- You can do so yourself, e.g.: @unpackRaw@ 'checkEntrySecurity' @dir@ @entries@.
93+
-- | Like 'unpack', but run custom sanity/security checks instead of 'checkEntrySecurity'.
94+
-- For example,
95+
--
96+
-- > unpackAndCheck (\x -> SomeException <$> checkEntryPortability x
97+
-- > <|> SomeException <$> checkEntrySecurity x) dir entries
8998
--
9099
-- @since 0.6.0.0
91100
unpackAndCheck
92101
:: Exception e
93102
=> (GenEntry FilePath FilePath -> Maybe SomeException)
103+
-- ^ Checks to run on each entry before unpacking
94104
-> FilePath
105+
-- ^ Base directory
95106
-> Entries e
107+
-- ^ Entries to upack
96108
-> IO ()
97109
unpackAndCheck secCB baseDir entries = do
98110
let resolvedEntries = decodeLongNames entries

changelog.md

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -18,7 +18,8 @@ See also http://pvp.haskell.org/faq
1818
* Switch to trailer parsing mode only after a full block of `NUL`
1919
* Drop deprecated `emptyIndex` and `finaliseIndex`
2020
* Extend `FileNameError` with `UnsafeLinkTarget` constructor
21-
* Add `packAndCheck`, `unpackAndCheck` and `Entry`-wise checks
21+
* Redesign `Codec.Archive.Tar.Check`
22+
* Add `packAndCheck` and `unpackAndCheck`
2223
* Generalize `Entries`, `Entry` and `EntryContent` to `GenEntries`, `GenEntry` and `GenEntryContent`
2324

2425
0.5.1.1 Herbert Valerio Riedel <[email protected]> August 2019

0 commit comments

Comments
 (0)