File: Path.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 (160 lines) | stat: -rw-r--r-- 3,958 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
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
-- |
-- Module      : Foundation.VFS.Path
-- License     : BSD-style
-- Maintainer  : foundation
-- Stability   : experimental
-- Portability : portable
--

{-# LANGUAGE FlexibleContexts #-}

module Foundation.VFS.Path
    (
      -- * Path class
      Path(..)

    , parent
    , filename
    , prefix
    , suffix
    ) where

import Basement.Compat.Base

-- $setup
-- >>> import Basement.Compat.Base
-- >>> import Foundation.VFS.FilePath
-- >>> import Foundation.VFS.Path

-- | Path type class
--
-- defines the Path associated types and basic functions to implement related
-- to the path manipulation
--
-- # TODO, add missing enhancement:
--
-- @
-- splitExtension :: PathEnt path -> (PathEnt path, PathEnt path)
-- addExtension  :: PathEnt path -> PathEnt path -> PathEnt path
-- (<.>) :: path -> PathEnt path -> path
-- (-<.>) :: path -> PathEnt path -> path
-- @
--
class Path path where
    -- | the associated PathEntity of the given `path`
    -- this type is the minimal element contained in the Path
    -- a Path is not a collection but it is possible to see this
    -- associated type equivalent to the `Foundation.Collection.Element` type family
    type PathEnt path

    -- | the associated prefix of the given `path`
    --
    -- in the case of a `Foundation.VFS.FilePath`, it is a void (i.e. `()`)
    -- in the case of a `Foundation.VFS.URI`, it is the schema, host, port...
    type PathPrefix path

    -- | the associated suffix of the given path
    --
    -- in the case of the `Foundation.VFS.FilePath`, it is a void (i.e. `()`)
    -- in the case of the `Foundation.VFS.URI`, it is a the query, the fragment
    type PathSuffix path

    -- | join a path entity to a given path
    (</>) :: path -> PathEnt path -> path

    -- | split the path into the associated elements
    splitPath :: path -> ( PathPrefix path
                         , [PathEnt path]
                         , PathSuffix path
                         )

    -- | build the path from the associated elements
    buildPath :: ( PathPrefix path
                 , [PathEnt path]
                 , PathSuffix path
                 )
              -> path


-- | parent is only going to drop the filename.
--
-- if you actually want to reference to the parent directory, simply uses:
--
-- @
-- parent "." /= "." </> ".."
-- @
--
-- >>> parent ("foo.hs" :: FilePath)
-- .
--
-- >>> parent ("foo/bar/baz.hs" :: FilePath)
-- foo/bar
parent :: Path path => path -> path
parent path = buildPath (p, init ps, s)
  where
    (p, ps, s) = splitPath path


-- | get the filename of the given path
--
-- If there is no filename, you will receive the 'mempty' of the 'PathEnt'
--
-- >>> filename ("foo.hs" :: FilePath)
-- foo.hs
--
-- >>> filename ("foo/bar/baz.hs" :: FilePath)
-- baz.hs
filename :: (Path path, Monoid (PathEnt path)) => path -> PathEnt path
filename path = case ps of
    [] -> mempty
    _  -> last ps
  where
    (_, ps , _) = splitPath path

-- TODO: this might be better in Sequential ?
init :: [a] -> [a]
init [] = []
init [_] = []
init (x:xs) = x : init xs

-- TODO: this might be better in Sequential ?
last :: [a] -> a
last [] = undefined
last [x] = x
last (_:xs) = last xs


-- | get the path prefix information
--
-- >>> prefix ("/home/tab" :: FilePath)
-- Absolute
--
-- >>> prefix ("home/tab" :: FilePath)
-- Relative
--
-- or for URI (TODO, not yet accurate)
--
-- @
-- prefix "http://github.com/vincenthz/hs-foundation?w=1"
--    == URISchema http Nothing Nothing "github.com" Nothing
-- @
prefix :: Path path => path -> PathPrefix path
prefix p = pre
  where
    (pre, _, _) = splitPath p

-- | get the path suffix information
--
-- >>> suffix ("/home/tab" :: FilePath)
-- ()
--
-- or for URI (TODO, not yet accurate)
--
-- @
-- suffix "http://github.com/vincenthz/hs-foundation?w=1"
--    == URISuffix (["w", "1"], Nothing)
-- @
suffix :: Path path => path -> PathSuffix path
suffix p = suf
  where
    (_, _, suf) = splitPath p