File: FilePath.hs

package info (click to toggle)
haskell-foundation 0.0.30-3
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 932 kB
  • sloc: haskell: 9,124; ansic: 570; makefile: 7
file content (257 lines) | stat: -rw-r--r-- 8,136 bytes parent folder | download | duplicates (2)
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
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
-- |
-- Module      : Foundation.VFS.FilePath
-- License     : BSD-style
-- Maintainer  : foundation
-- Stability   : experimental
-- Portability : portable
--
-- # Opaque implementation for FilePath
--
-- The underlying type of a FilePath is a `Foundation.ByteArray`. It is indeed like
-- this because for some systems (Unix systems) a `FilePath` is a null
-- terminated array of bytes.
--
-- # FilePath and FileName for type checking validation
--
-- In order to add some constraint at compile time, it is not possible to
-- append (`</>`) a `FilePath` to another `FilePath`.
-- You can only append (`</>`) a `FileName` to a given `FilePath`.
--

{-# LANGUAGE CPP #-}

module Foundation.VFS.FilePath
    ( FilePath
    , Relativity(..)
    , FileName
      -- * conversion
    , filePathToString
    , filePathToLString

      -- ** unsafe
    , unsafeFilePath
    , unsafeFileName
    , extension
    ) where

import Basement.Compat.Base
import Basement.Compat.Semigroup
import Foundation.Collection
import Foundation.Array
import Foundation.String (Encoding(..), ValidationFailure, toBytes, fromBytes, String)
import Foundation.VFS.Path(Path(..))

import qualified Data.List
-- ------------------------------------------------------------------------- --
--                           System related helpers                          --
-- ------------------------------------------------------------------------- --

#ifdef mingw32_HOST_OS
pathSeparatorWINC :: Char
pathSeparatorWINC = '\\'

-- | define the Path separator for Windows systems : '\\'
pathSeparatorWIN :: String
pathSeparatorWIN = fromString [pathSeparatorWINC]
#else
pathSeparatorPOSIXC :: Char
pathSeparatorPOSIXC = '/'

-- | define the Path separator for POSIX systems : '/'
pathSeparatorPOSIX :: String
pathSeparatorPOSIX = fromString [pathSeparatorPOSIXC]
#endif

pathSeparatorC :: Char
pathSeparator :: String
#ifdef mingw32_HOST_OS
pathSeparatorC = pathSeparatorWINC
pathSeparator = pathSeparatorWIN
#else
pathSeparatorC = pathSeparatorPOSIXC
pathSeparator = pathSeparatorPOSIX
#endif

-- ------------------------------------------------------------------------- --
--                              FilePath                                     --
-- ------------------------------------------------------------------------- --

-- | information about type of FilePath
--
-- A file path being only `Relative` or `Absolute`.
data Relativity = Absolute | Relative
  deriving (Eq, Show)

-- | FilePath is a collection of FileName
--
-- TODO: Eq and Ord are implemented using Show
--       This is not very efficient and would need to be improved
--       Also, it is possible the ordering is not necessary what we want
--       in this case.
--
-- A FilePath is one of the following:
--
-- * An Absolute:
--   * starts with one of the follwing "/"
-- * A relative:
--   * don't start with a "/"
--
-- * authorised:
--   * "/"
--   * "/file/path"
--   * "."
--   * ".."
--   * "work/haskell/hs-foundation"
--
-- * unauthorised
--   * "path//"
data FilePath = FilePath Relativity [FileName]

instance Show FilePath where
    show = filePathToLString
instance Eq FilePath where
  (==) a b = (==) (show a) (show b)
instance Ord FilePath where
  compare a b = compare (show a) (show b)

-- | error associated to filepath manipulation
data FilePath_Invalid
      = ContiguousPathSeparator
          -- ^ this mean there were 2 contiguous path separators.
          --
          -- This is not valid in Foundation's FilePath specifications
    deriving (Typeable, Show)
instance Exception FilePath_Invalid

instance IsString FilePath where
    fromString [] = FilePath Absolute mempty
    fromString s@(x:xs)
        | hasContigueSeparators s = throw ContiguousPathSeparator
        | otherwise = FilePath relativity $ case relativity of
            Absolute -> fromString <$> splitOn isSeparator xs
            Relative -> fromString <$> splitOn isSeparator s
      where
        relativity :: Relativity
        relativity = if isSeparator x then Absolute else Relative

-- | A filename (or path entity) in the FilePath
--
-- * Authorised
--   * ""
--   * "."
--   * ".."
--   * "foundation"
-- * Unauthorised
--   * "/"
--   * "file/"
--   * "/file"
--   * "file/path"
--
data FileName = FileName (UArray Word8)
  deriving (Eq)
-- | errors related to FileName manipulation
data FileName_Invalid
    = ContainsNullByte
        -- ^ this means a null byte was found in the FileName
    | ContainsSeparator
        -- ^ this means a path separator was found in the FileName
    | EncodingError ValidationFailure
        -- ^ encoding error
    | UnknownTrailingBytes (UArray Word8)
        -- ^ some unknown trainling bytes found
  deriving (Typeable, Show)
instance Exception FileName_Invalid

instance Show FileName where
    show = fileNameToLString
instance IsString FileName where
  fromString [] = FileName mempty
  fromString xs | hasNullByte  xs = throw ContainsNullByte
                | hasSeparator xs = throw ContainsSeparator
                | otherwise       = FileName $ toBytes UTF8 $ fromString xs

hasNullByte :: [Char] -> Bool
hasNullByte = Data.List.elem '\0'

hasSeparator :: [Char] -> Bool
hasSeparator = Data.List.elem pathSeparatorC

isSeparator :: Char -> Bool
isSeparator = (==) pathSeparatorC

hasContigueSeparators :: [Char] -> Bool
hasContigueSeparators [] = False
hasContigueSeparators [_] = False
hasContigueSeparators (x1:x2:xs) =
    (isSeparator x1 && x1 == x2) || hasContigueSeparators xs

instance Semigroup FileName where
    (<>) (FileName a) (FileName b) = FileName $ a `mappend` b
instance Monoid FileName where
    mempty = FileName mempty

instance Path FilePath where
    type PathEnt FilePath = FileName
    type PathPrefix FilePath = Relativity
    type PathSuffix FilePath = ()
    (</>) = join
    splitPath (FilePath r xs) = (r, xs, ())
    buildPath (r, xs , _) = FilePath r xs

-- compare to the original </>, this type disallow to be able to append an absolute filepath to a filepath
join :: FilePath -> FileName -> FilePath
join p              (FileName x) | null x = p
join (FilePath r xs) x          = FilePath r $ snoc xs x

filePathToString :: FilePath -> String
filePathToString (FilePath Absolute []) = fromString [pathSeparatorC]
filePathToString (FilePath Relative []) = fromString "."
filePathToString (FilePath Absolute fns) = cons pathSeparatorC $ filenameIntercalate fns
filePathToString (FilePath Relative fns) = filenameIntercalate fns

filenameIntercalate :: [FileName] -> String
filenameIntercalate = mconcat . Data.List.intersperse pathSeparator . fmap fileNameToString

-- | convert a FileName into a String
--
-- This function may throw an exception associated to the encoding
fileNameToString :: FileName -> String
fileNameToString (FileName fp) =
    -- FIXME probably incorrect considering windows.
    -- this is just to get going to be able to be able to reuse System.IO functions which
    -- works on [Char]
    case fromBytes UTF8 fp of
        (s, Nothing, bs)
            | null bs -> s
            | otherwise -> throw $ UnknownTrailingBytes bs
        (_, Just err, _) -> throw $ EncodingError err

-- | conversion of FileName into a list of Char
--
-- this function may throw exceptions
fileNameToLString :: FileName -> [Char]
fileNameToLString = toList . fileNameToString

-- | conversion of a FilePath into a list of Char
--
-- this function may throw exceptions
filePathToLString :: FilePath -> [Char]
filePathToLString = toList . filePathToString

-- | build a file path from a given list of filename
--
-- this is unsafe and is mainly needed for testing purpose
unsafeFilePath :: Relativity -> [FileName] -> FilePath
unsafeFilePath = FilePath

-- | build a file name from a given ByteArray
--
-- this is unsafe and is mainly needed for testing purpose
unsafeFileName :: UArray Word8 -> FileName
unsafeFileName = FileName

extension :: FileName -> Maybe FileName
extension (FileName fn) = case splitOn (\c -> c == 0x2E) fn of
                            []  -> Nothing
                            [_] -> Nothing
                            xs  -> Just $ FileName $ last $ nonEmpty_ xs