File: Path.hs

package info (click to toggle)
haskell-wai-app-file-cgi 3.1.10-3
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 200 kB
  • sloc: haskell: 995; sh: 18; makefile: 3
file content (137 lines) | stat: -rw-r--r-- 2,898 bytes parent folder | download | duplicates (4)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
{-# LANGUAGE OverloadedStrings, BangPatterns #-}

module Network.Wai.Application.Classic.Path (
    Path
  , pathString
  , fromString
  , (</>), (<\>), (<.>)
  , breakAtSeparator, hasLeadingPathSeparator, hasTrailingPathSeparator
  , isSuffixOf
  ) where

import Data.ByteString (ByteString)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Char8 as B8
import Data.String
import Data.Word

----------------------------------------------------------------

-- | File path.
type Path = ByteString

pathString :: Path -> String
pathString = B8.unpack
{-# INLINE pathString #-}

----------------------------------------------------------------

-- pathDot :: Word8
-- pathDot = 46

pathDotBS :: ByteString
pathDotBS = "."

pathSep :: Word8
pathSep = 47

pathSepBS :: ByteString
pathSepBS = "/"

{-|
  Checking if the path ends with the path separator.

>>> hasLeadingPathSeparator "/foo/bar"
True
>>> hasLeadingPathSeparator "foo/bar"
False
-}
hasLeadingPathSeparator :: Path -> Bool
hasLeadingPathSeparator bs
  | BS.null bs            = False
  | BS.head bs == pathSep = True
  | otherwise             = False
{-# INLINE hasLeadingPathSeparator #-}

{-|
  Checking if the path ends with the path separator.

>>> hasTrailingPathSeparator "/foo/bar/"
True
>>> hasTrailingPathSeparator "/foo/bar"
False
-}
hasTrailingPathSeparator :: Path -> Bool
hasTrailingPathSeparator bs
  | BS.null bs            = False
  | BS.last bs == pathSep = True
  | otherwise             = False
{-# INLINE hasTrailingPathSeparator #-}

{-|
  Appending with the file separator.

>>> "/foo" </> "bar"
"/foo/bar"
>>> "/foo/" </> "bar"
"/foo/bar"
>>> "/foo" </> "/bar"
"/foo/bar"
>>> "/foo/" </> "/bar"
"/foo/bar"
-}

(</>) :: Path -> Path -> Path
p1 </> p2 = p
  where
    !has1 = hasTrailingPathSeparator p1
    !has2 = hasLeadingPathSeparator p2
    !p | has1 && not has2 = p1 `BS.append` p2
       | not has1 && has2 = p1 `BS.append` p2
       | has1             = p1 `BS.append` BS.tail p2
       | otherwise        = BS.concat [p1,pathSepBS,p2]
{-# INLINE (</>) #-}

{-|
  Removing prefix. The prefix of the second argument is removed
  from the first argument.

>>> "foobar" <\> "foo"
"bar"
>>> "foo" <\> "foobar"
""
>>> "foobar" <\> "baz"
"bar"
-}
(<\>) :: Path -> Path -> Path
p1 <\> p2 = p
  where
    !p = BS.drop (BS.length p2) p1
{-# INLINE (<\>) #-}

{-|
  Adding suffix.
-}
(<.>) :: Path -> Path -> Path
p1 <.> p2 = p
  where
    !p = BS.concat [p1,pathDotBS,p2]
{-# INLINE (<.>) #-}

{-|
  Breaking at the first path separator.

>>> breakAtSeparator "/foo/bar/baz"
("","/foo/bar/baz")
>>> breakAtSeparator "foo/bar/baz"
("foo","/bar/baz")
>>> breakAtSeparator "foo"
("foo","")
-}
breakAtSeparator :: Path -> (Path,Path)
breakAtSeparator p = BS.break (== pathSep) p
{-# INLINE breakAtSeparator #-}

isSuffixOf :: Path -> Path -> Bool
isSuffixOf = BS.isSuffixOf
{-# INLINE isSuffixOf #-}