Skip to content

Commit b8d0505

Browse files
committed
🔥 pathtype.
1 parent a507b45 commit b8d0505

File tree

30 files changed

+109
-161
lines changed

30 files changed

+109
-161
lines changed

semantic-analysis/semantic-analysis.cabal

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -76,7 +76,6 @@ library
7676
, filepath
7777
, fused-effects ^>= 1.1
7878
, hashable
79-
, pathtype ^>= 0.8.1
8079
, semantic-source ^>= 0.2
8180
, text ^>= 1.2.3.1
8281
, transformers ^>= 0.5

semantic-analysis/src/Analysis/Blob.hs

Lines changed: 11 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -8,13 +8,11 @@ module Analysis.Blob
88
, nullBlob
99
) where
1010

11-
import Analysis.File as A
12-
import Analysis.Reference as A
13-
import Data.Aeson
14-
import Source.Language as Language
15-
import Source.Source as Source
16-
import qualified System.Path as Path
17-
import qualified System.Path.PartClass as Path.PartClass
11+
import Analysis.File as A
12+
import Analysis.Reference as A
13+
import Data.Aeson
14+
import Source.Language as Language
15+
import Source.Source as Source
1816

1917
-- | The source, path information, and language of a file read from disk.
2018
data Blob = Blob
@@ -25,27 +23,27 @@ data Blob = Blob
2523
instance FromJSON Blob where
2624
parseJSON = withObject "Blob" $ \b -> do
2725
src <- b .: "content"
28-
Right pth <- fmap Path.parse (b .: "path")
26+
pth <- b .: "path"
2927
lang <- b .: "language"
3028
let lang' = if knownLanguage lang then lang else Language.forPath pth
31-
pure (fromSource (pth :: Path.AbsRelFile) lang' src)
29+
pure (fromSource pth lang' src)
3230

3331

3432
-- | Create a Blob from a provided path, language, and UTF-8 source.
3533
-- The resulting Blob's span is taken from the 'totalSpan' of the source.
36-
fromSource :: Path.PartClass.AbsRel ar => Path.File ar -> Language -> Source -> Blob
34+
fromSource :: FilePath -> Language -> Source -> Blob
3735
fromSource filepath language source
38-
= Blob source (A.File (A.Reference (Path.toAbsRel filepath) (totalSpan source)) language)
36+
= Blob source (A.File (A.Reference filepath (totalSpan source)) language)
3937

4038
blobLanguage :: Blob -> Language
4139
blobLanguage = A.fileBody . blobFile
4240

43-
blobPath :: Blob -> Path.AbsRelFile
41+
blobPath :: Blob -> FilePath
4442
blobPath = A.refPath . A.fileRef . blobFile
4543

4644
-- | Show FilePath for error or json outputs.
4745
blobFilePath :: Blob -> String
48-
blobFilePath = Path.toString . blobPath
46+
blobFilePath = blobPath
4947

5048
nullBlob :: Blob -> Bool
5149
nullBlob = Source.null . blobSource

semantic-analysis/src/Analysis/File.hs

Lines changed: 2 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -14,8 +14,6 @@ import Data.Maybe (fromJust, listToMaybe)
1414
import GHC.Stack
1515
import Source.Language as Language
1616
import Source.Span
17-
import qualified System.Path as Path
18-
import qualified System.Path.PartClass as Path.PartClass
1917

2018
-- Files
2119

@@ -29,10 +27,10 @@ data File a = File
2927
-- Constructors
3028

3129
fromBody :: HasCallStack => a -> File a
32-
fromBody body = File (A.Reference (Path.absRel (srcLocFile srcLoc)) (spanFromSrcLoc srcLoc)) body where
30+
fromBody body = File (A.Reference (srcLocFile srcLoc) (spanFromSrcLoc srcLoc)) body where
3331
srcLoc = snd (fromJust (listToMaybe (getCallStack callStack)))
3432

35-
fromPath :: Path.PartClass.AbsRel ar => Path.File ar -> File Language
33+
fromPath :: FilePath -> File Language
3634
fromPath p = File (A.fromPath p) (Language.forPath p)
3735

3836

semantic-analysis/src/Analysis/Module.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -13,7 +13,7 @@ import Data.Foldable (foldl')
1313
import qualified Data.Map as Map
1414
import qualified Data.Set as Set
1515
import qualified Data.Text as Text
16-
import qualified System.Path as Path
16+
import System.FilePath as Path
1717

1818
data Module a = Module
1919
{ body :: Map.Map Name a -> a
@@ -50,7 +50,7 @@ instance Monoid (ModuleSet a) where
5050
fromList :: [File (Module a)] -> ModuleSet a
5151
fromList = ModuleSet . Map.fromList . map (\ (File ref mod) -> (refName ref, mod))
5252
where
53-
refName (Reference path _) = name (Text.pack (Path.toString (Path.takeBaseName path)))
53+
refName (Reference path _) = name (Text.pack (Path.takeBaseName path))
5454

5555
link :: ModuleSet a -> Module a -> Module a
5656
link (ModuleSet ms) m = Module body' (imports m Set.\\ Map.keysSet ms) (exports m) unknown' where

semantic-analysis/src/Analysis/Project.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -12,19 +12,19 @@ import Analysis.File
1212
import Data.Text (Text)
1313
import qualified Data.Text as T
1414
import Source.Language
15-
import qualified System.Path as Path
15+
import System.FilePath (takeFileName)
1616

1717
-- | A 'Project' contains all the information that semantic needs
1818
-- to execute an analysis, diffing, or graphing pass.
1919
data Project = Project
20-
{ projectRootDir :: Path.AbsRelDir
20+
{ projectRootDir :: FilePath
2121
, projectBlobs :: [Blob]
2222
, projectLanguage :: Language
23-
, projectExcludeDirs :: [Path.AbsRelDir]
23+
, projectExcludeDirs :: [FilePath]
2424
} deriving (Eq, Show)
2525

2626
projectName :: Project -> Text
27-
projectName = T.pack . maybe "" Path.toString . Path.takeDirName . projectRootDir
27+
projectName = T.pack . takeFileName . projectRootDir
2828

2929
projectExtensions :: Project -> [String]
3030
projectExtensions = extensionsForLanguage . projectLanguage

semantic-analysis/src/Analysis/Reference.hs

Lines changed: 3 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -6,19 +6,17 @@ module Analysis.Reference
66
) where
77

88
import Source.Span
9-
import System.Path as Path
10-
import System.Path.PartClass as Path.PartClass
119

1210
-- Reference
1311

1412
data Reference = Reference
15-
{ refPath :: Path.AbsRelFile
13+
{ refPath :: FilePath
1614
, refSpan :: Span
1715
}
1816
deriving (Eq, Ord, Show)
1917

2018

2119
-- Constructors
2220

23-
fromPath :: Path.PartClass.AbsRel ar => Path.File ar -> Reference
24-
fromPath p = Reference (Path.toAbsRel p) (point (Pos 0 0))
21+
fromPath :: FilePath -> Reference
22+
fromPath p = Reference p (point (Pos 0 0))

semantic-analysis/src/Analysis/Syntax.hs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -55,7 +55,6 @@ import qualified Data.Vector as V
5555
import qualified Source.Source as Source
5656
import Source.Span
5757
import System.FilePath
58-
import qualified System.Path as Path
5958

6059
data Term
6160
= Var Name
@@ -140,7 +139,7 @@ parseFile path = do
140139
case (A.eitherDecodeWith A.json' (A.iparse parseGraph) contents) of
141140
Left (_, err) -> throwError err
142141
Right (_, Nothing) -> throwError "no root node found"
143-
Right (_, Just root) -> pure (sourceContents, File (Reference (Path.absRel sourcePath) span) root)
142+
Right (_, Just root) -> pure (sourceContents, File (Reference sourcePath span) root)
144143
where
145144
decrSpan (Span (Pos sl sc) (Pos el ec)) = Span (Pos (sl - 1) (sc - 1)) (Pos (el - 1) (ec - 1))
146145

semantic-ast/semantic-ast.cabal

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -73,7 +73,6 @@ library
7373
, filepath ^>= 1.4.1
7474
, fused-effects ^>= 1.1
7575
, Glob ^>= 0.10.0
76-
, pathtype ^>= 0.8.1
7776
, semantic-source ^>= 0.2
7877
, tasty ^>= 1.2.3
7978
, tasty-hunit ^>= 0.10.0.2

semantic-ast/src/AST/TestHelpers.hs

Lines changed: 28 additions & 32 deletions
Original file line numberDiff line numberDiff line change
@@ -7,29 +7,28 @@ module AST.TestHelpers
77
, testCorpus
88
) where
99

10-
import Control.Applicative
11-
import Control.Monad
12-
import Data.Attoparsec.ByteString.Char8
13-
import Data.Attoparsec.ByteString.Char8 as Attoparsec
14-
import Data.ByteString (ByteString, readFile)
15-
import Data.ByteString.Char8 (pack, unpack)
16-
import Data.Either
17-
import Data.Functor
18-
import Prelude hiding (takeWhile)
19-
import System.Exit (exitFailure)
20-
import System.Path ((</>))
21-
import qualified System.Path as Path
22-
import qualified System.Path.Directory as Path
23-
import System.FilePath.Glob
24-
import Test.Tasty
25-
import Test.Tasty.HUnit
10+
import Control.Applicative
11+
import Control.Monad
12+
import Data.Attoparsec.ByteString.Char8
13+
import Data.Attoparsec.ByteString.Char8 as Attoparsec
14+
import Data.ByteString (ByteString, readFile)
15+
import Data.ByteString.Char8 (pack, unpack)
16+
import Data.Either
17+
import Data.Functor
18+
import Prelude hiding (takeWhile)
19+
import System.Directory
20+
import System.Exit (exitFailure)
21+
import System.FilePath
22+
import System.FilePath.Glob
23+
import Test.Tasty
24+
import Test.Tasty.HUnit
2625

27-
testCorpus :: (ByteString -> IO (Either String (t a))) -> Path.AbsRelFile -> IO TestTree
26+
testCorpus :: (ByteString -> IO (Either String (t a))) -> FilePath -> IO TestTree
2827
testCorpus parse path = do
2928
xs <- parseCorpusFile path
3029
case xs of
31-
Left e -> print ("Failed to parse corpus: " <> show (Path.toString path) <> " " <> "Error: " <> show e) *> exitFailure
32-
Right xs -> testGroup (Path.toString path) <$> traverse corpusTestCase xs
30+
Left e -> print ("Failed to parse corpus: " <> show path <> " " <> "Error: " <> show e) *> exitFailure
31+
Right xs -> testGroup path <$> traverse corpusTestCase xs
3332
where
3433
corpusTestCase (CorpusExample name code) = testCase name . either (errMsg code) pass <$> parse code
3534
pass = const (pure ())
@@ -38,31 +37,28 @@ testCorpus parse path = do
3837
-- Depending on whether these tests are invoked via cabal run or cabal test,
3938
-- we might be in a project subdirectory or not, so let's make sure we're
4039
-- in project subdirectories as needed.
41-
findCorpus :: Path.RelDir -> IO Path.RelDir
40+
findCorpus :: FilePath -> IO FilePath
4241
findCorpus p = do
43-
cwd <- Path.getCurrentDirectory
44-
if Path.takeDirName cwd == Just (Path.relDir "haskell-tree-sitter")
42+
cwd <- getCurrentDirectory
43+
if takeFileName cwd == "haskell-tree-sitter"
4544
then pure p
46-
else pure (Path.relDir ".." </> p)
45+
else pure (".." </> p)
4746

4847
-- The path is expected to be relative to the language project.
49-
readCorpusFiles :: Path.RelDir -> IO [Path.RelFile]
48+
readCorpusFiles :: FilePath -> IO [FilePath]
5049
readCorpusFiles parent = do
5150
dir <- findCorpus parent
52-
files <- globDir1 (compile "**/*.txt") (Path.toString dir)
53-
pure (Path.relPath <$> files)
51+
globDir1 (compile "**/*.txt") dir
5452

55-
readCorpusFiles' :: Path.AbsRelDir -> IO [Path.AbsRelFile]
56-
readCorpusFiles' dir = do
57-
files <- globDir1 (compile "**/*.txt") (Path.toString dir)
58-
pure (Path.file <$> files)
53+
readCorpusFiles' :: FilePath -> IO [FilePath]
54+
readCorpusFiles' = globDir1 (compile "**/*.txt")
5955

6056
data CorpusExample = CorpusExample { name :: String, code :: ByteString }
6157
deriving (Eq, Show)
6258

63-
parseCorpusFile :: Path.AbsRelFile -> IO (Either String [CorpusExample])
59+
parseCorpusFile :: FilePath -> IO (Either String [CorpusExample])
6460
parseCorpusFile path = do
65-
c <- Data.ByteString.readFile (Path.toString path)
61+
c <- Data.ByteString.readFile path
6662
pure $ parseOnly corpusParser c
6763

6864
corpusParser :: Parser [CorpusExample]

semantic-ast/src/System/Path/Fixture.hs

Lines changed: 8 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -13,9 +13,8 @@ where
1313

1414
import Control.Concurrent
1515
import GHC.Stack
16+
import System.FilePath
1617
import System.IO
17-
import qualified System.Path as Path
18-
import System.Path ((</>))
1918

2019
#if BAZEL_BUILD
2120
import qualified Bazel.Runfiles as Bazel
@@ -29,13 +28,13 @@ type HasFixture =
2928
create :: IO Bazel.Runfiles
3029
create = Bazel.create
3130

32-
root :: HasFixture => Path.AbsRelDir
31+
root :: HasFixture => FilePath
3332
root = Path.absRel (Bazel.rlocation ?runfiles ".")
3433

35-
absRelFile :: (HasFixture) => String -> Path.AbsRelFile
34+
absRelFile :: (HasFixture) => String -> FilePath
3635
absRelFile x = Path.toAbsRel (root </> Path.relDir "semantic" </> ?project </> Path.relFile x)
3736

38-
absRelDir :: HasFixture => String -> Path.AbsRelDir
37+
absRelDir :: HasFixture => String -> FilePath
3938
absRelDir x = Path.toAbsRel (root </> Path.relDir "semantic" </> ?project </> Path.relDir x)
4039

4140
#else
@@ -46,11 +45,11 @@ type HasFixture = HasCallStack
4645
create :: IO ()
4746
create = pure ()
4847

49-
absRelFile :: String -> Path.AbsRelFile
50-
absRelFile x = Path.absRel "semantic" </> Path.relFile x
48+
absRelFile :: String -> FilePath
49+
absRelFile x = "semantic" </> x
5150

52-
absRelDir :: String -> Path.AbsRelDir
53-
absRelDir x = Path.absRel "semantic" </> Path.relDir x
51+
absRelDir :: String -> FilePath
52+
absRelDir x = "semantic" </> x
5453

5554
#endif
5655

0 commit comments

Comments
 (0)