@@ -38,7 +38,6 @@ module Data.Path.Pathy
38
38
, pathName
39
39
, identicalPath
40
40
, parentDir
41
- , parentDir'
42
41
, peel
43
42
, posixEscaper
44
43
, parsePath
@@ -81,7 +80,7 @@ import Data.String as S
81
80
import Data.String.NonEmpty (NonEmptyString , appendString )
82
81
import Data.String.NonEmpty (fromString , toString ) as NEString
83
82
import Data.Traversable (traverse )
84
- import Data.Tuple (Tuple (..), fst , snd )
83
+ import Data.Tuple (Tuple (..), snd )
85
84
import Partial.Unsafe (unsafeCrashWith )
86
85
import Unsafe.Coerce (unsafeCoerce )
87
86
@@ -130,14 +129,14 @@ runName (Name name) = NEString.toString name
130
129
-- |
131
130
-- | This ADT allows invalid paths (e.g. paths inside files), but there is no
132
131
-- | possible way for such paths to be constructed by user-land code. The only
133
- -- | "invalid path" that may be constructed is using the `parentDir' ` function, e.g.
134
- -- | `parentDir' rootDir`, or by parsing an equivalent string such as `/../`,
132
+ -- | "invalid path" that may be constructed is using the `parentDir` function, e.g.
133
+ -- | `parentDir rootDir`, or by parsing an equivalent string such as `/../`,
135
134
-- | but such paths are marked as unsandboxed, and may not be rendered to strings
136
135
-- | until they are first sandboxed to some directory.
137
136
data Path (a :: RelOrAbs ) (b :: DirOrFile ) (s :: SandboxedOrNot )
138
137
= Current
139
138
| Root
140
- | ParentIn (Path a b s )
139
+ | ParentIn (Path a Dir s )
141
140
| In (Path a Dir s ) (Name b )
142
141
143
142
-- | A type describing a file whose location is given relative to some other,
@@ -277,18 +276,18 @@ pathName :: forall b s. AnyPath b s -> Either (Maybe (Name Dir)) (Name File)
277
276
pathName = bimap dirName fileName
278
277
279
278
-- | Given a directory path, appends either a file or directory to the path.
280
- appendPath :: forall a b s . Path a Dir s -> Path Rel b s -> Path a b s
279
+ appendPath :: forall a b s . SplitDirOrFile b => Path a Dir s -> Path Rel b s -> Path a b s
280
+ appendPath _ Root = unsafeCrashWith " Imposible"
281
281
appendPath Current Current = Current
282
282
appendPath Root Current = Root
283
- appendPath (ParentIn p1) Current = ParentIn (p1 </> Current )
284
- appendPath (In p1 f1) Current = In (p1 </> Current ) (unsafeCoerce $ f1)
283
+ -- TODO this shold be correct?
284
+ -- appendPath (ParentIn p) c@Current = ParentIn (p </> c)
285
+ appendPath (ParentIn p) Current = ParentIn (p </> Current )
286
+ appendPath (In p1 (Name f1)) c@Current = case dirOrFile c of
287
+ Left dir -> In (p1 </> dir) (Name f1)
288
+ Right _ -> unsafeCrashWith " Imposible"
285
289
appendPath p1 (ParentIn p2) = ParentIn (p1 </> p2)
286
290
appendPath p1 (In p2 f2) = In (p1 </> p2) f2
287
- -- following cases don't make sense but cannot exist
288
- appendPath Current Root = Current
289
- appendPath Root Root = Root
290
- appendPath (ParentIn p1) Root = ParentIn (p1 </> Current )
291
- appendPath (In p1 f1) Root = In (p1 </> Current ) (unsafeCoerce $ f1)
292
291
293
292
infixl 6 appendPath as </>
294
293
@@ -307,10 +306,11 @@ infixl 6 setExtension as <.>
307
306
-- | its previous sandbox.
308
307
parentAppend
309
308
:: forall a b s s'
310
- . Path a Dir s
309
+ . SplitDirOrFile b
310
+ => Path a Dir s
311
311
-> Path Rel b s'
312
312
-> Path a b Unsandboxed
313
- parentAppend d p = parentDir' d </> unsandbox p
313
+ parentAppend d p = parentDir d </> unsandbox p
314
314
315
315
infixl 6 parentAppend as <..>
316
316
@@ -337,12 +337,6 @@ depth Root = 0
337
337
depth (ParentIn p) = depth p - 1
338
338
depth (In p _) = depth p + 1
339
339
340
- -- | Attempts to extract out the parent directory of the specified path. If the
341
- -- | function would have to use a relative path in the return value, the function will
342
- -- | instead return `Nothing`.
343
- parentDir :: forall a b s . Path a b s -> Maybe (Path a Dir s )
344
- parentDir p = fst <$> peel p
345
-
346
340
-- | Unsandboxes any path (whether sandboxed or not).
347
341
unsandbox :: forall a b s . Path a b s -> Path a b Unsandboxed
348
342
unsandbox Current = Current
@@ -352,8 +346,8 @@ unsandbox (In p n) = In (unsandbox p) n
352
346
353
347
-- | Creates a path that points to the parent directory of the specified path.
354
348
-- | This function always unsandboxes the path.
355
- parentDir' :: forall a b s . Path a b s -> Path a Dir Unsandboxed
356
- parentDir' = ParentIn <<< unsafeCoerceType <<< unsandbox
349
+ parentDir :: forall a b s . Path a Dir s -> Path a Dir Unsandboxed
350
+ parentDir = ParentIn <<< unsandbox
357
351
358
352
unsafeCoerceType :: forall a b b' s . Path a b s -> Path a b' s
359
353
unsafeCoerceType = unsafeCoerce
@@ -388,7 +382,7 @@ canonicalize = snd <<< canonicalize'
388
382
canonicalize' :: forall a b s . Path a b s -> Tuple Boolean (Path a b s )
389
383
canonicalize' Current = Tuple false Current
390
384
canonicalize' Root = Tuple false Root
391
- canonicalize' (ParentIn (In p f)) = Tuple true (unsafeCoerceType $ snd $ canonicalize' p)
385
+ canonicalize' (ParentIn (In p f)) = Tuple true (unsafeCoerceType $ snd $ canonicalize' p)
392
386
canonicalize' (ParentIn p) = case canonicalize' p of
393
387
Tuple changed p' ->
394
388
let p'' = ParentIn p'
@@ -511,12 +505,12 @@ parsePath rd ad rf af err p =
511
505
false , true -> segsRaw
512
506
false , false -> dropEnd 1 segsRaw
513
507
last = length segsDropped - 1
514
- folder :: forall a b s . Int -> Path a b s -> NonEmptyString -> Path a b s
508
+ folder :: forall a b s . SplitDirOrFile b => Int -> Path a b s -> NonEmptyString -> Path a b s
515
509
folder idx base seg =
516
510
if NEString .toString seg == " ." then
517
511
base
518
512
else if NEString .toString seg == " .." then
519
- ParentIn base
513
+ ParentIn $ unsafeCoerceType base
520
514
else In (unsafeCoerceType base) (Name seg)
521
515
in
522
516
case traverse NEString .fromString segsDropped of
@@ -546,7 +540,7 @@ parseAbsDir = parsePath (const Nothing) Just (const Nothing) (const Nothing) (co
546
540
instance showPath :: SplitDirOrFile b => Show (Path a b s ) where
547
541
show Current = " currentDir"
548
542
show Root = " rootDir"
549
- show (ParentIn p) = " (parentDir' " <> show p <> " )"
543
+ show (ParentIn p) = " (parentDir " <> show p <> " )"
550
544
show (In p n ) = case dirOrFileName n of
551
545
Left dirN ->
552
546
" (" <> show p <> " </> dir " <> show dirN <> " )"
0 commit comments