Everything is now Data.Text instead of String

This commit is contained in:
vegowotenks 2025-02-21 18:17:46 +01:00
parent 753f429ec8
commit cbfd729795
18 changed files with 178 additions and 137 deletions

View file

@ -1,5 +1,6 @@
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE OverloadedStrings #-}
module Ubc.Parse.Syntax.Import
( parse
, Import(..)
@ -18,8 +19,10 @@ import Data.Functor ((<&>))
import Data.List.NonEmpty (NonEmpty)
import qualified Data.List as List
import qualified Data.Set as Set
import qualified Data.List.NonEmpty as NonEmpty
import qualified Data.Set as Set
import qualified Data.Text as Text
import qualified Data.Text.IO as Text.IO
import qualified System.Directory as IO
@ -28,7 +31,7 @@ import qualified Text.Parsec as Parsec
import Path as Path ( Path, File, parseRelFile, Rel, parseRelDir, Dir, Abs, (</>), fromAbsFile, fromRelFile )
import Ubc.Parse.Syntax (Transformer)
import Ubc.Parse.Syntax (Transformer, Token)
import Ubc.Parse.Syntax.Config (Config)
import qualified Ubc.Parse.Syntax.Config as Config
import qualified Ubc.Parse.Syntax.File as File
@ -36,22 +39,22 @@ import qualified Ubc.Parse.Syntax.Language as UbcLanguage
data Import = Import
{ file :: File.File
, alias :: Maybe String
, list :: [String]
, alias :: Maybe Token
, list :: [Token]
}
deriving stock (Show)
importPath :: Monad m => ParsecT String u m (NonEmpty String)
importPath :: Monad m => ParsecT Token u m (NonEmpty Token)
importPath = UbcLanguage.angles (many importChar `sepBy1` char '/')
<&> NonEmpty.fromList
<&> NonEmpty.fromList . List.map Text.pack
importChar :: (Monad m) => ParsecT String u m Char
importChar :: (Monad m) => ParsecT Token u m Char
importChar = choice
[ char '\\' >> oneOf ">/\\"
, notFollowedBy (oneOf ">/") >> anyChar
]
parse :: ParsecT String u Transformer Import
parse :: ParsecT Token u Transformer Import
parse = do
UbcLanguage.reserved "import"
fragments <- importPath
@ -68,9 +71,9 @@ parse = do
-- fail or parse
importedFile <- case existingFiles of
[] -> fail $ notFoundMessage relFile possiblePaths
[] -> fail . Text.unpack $ notFoundMessage relFile possiblePaths
[path] -> parseFile path
fs@_ -> fail $ multipleFoundMessage relFile fs
fs@_ -> fail . Text.unpack $ multipleFoundMessage relFile fs
importAs <- Parsec.optionMaybe importAlias
@ -78,24 +81,24 @@ parse = do
return $ Import importedFile importAs importList
importAlias :: Monad m => ParsecT String u m String
importAlias :: Monad m => ParsecT Token u m Token
importAlias = UbcLanguage.reserved "as"
*> UbcLanguage.identifier
multipleFoundMessage :: Path Rel File -> [Path Abs File] -> String
multipleFoundMessage relFile foundFiles = "Could not identify imported file " <> Path.fromRelFile relFile <> "\n"
multipleFoundMessage :: Path Rel File -> [Path Abs File] -> Token
multipleFoundMessage relFile foundFiles = "Could not identify imported file " <> Text.pack (Path.fromRelFile relFile) <> "\n"
<> "Found multiple files in the search path:"
<> (unlines . List.map (Path.fromAbsFile >>> ('\t':)) $ foundFiles)
<> (Text.unlines . List.map (Path.fromAbsFile >>> ('\t':) >>> Text.pack) $ foundFiles)
notFoundMessage :: Path Rel File -> [Path Abs File] -> String
notFoundMessage relFile searchedLocations = "Could not locate import file <" <> Path.fromRelFile relFile <> ">\n"
notFoundMessage :: Path Rel File -> [Path Abs File] -> Token
notFoundMessage relFile searchedLocations = "Could not locate import file <" <> Text.pack (Path.fromRelFile relFile) <> ">\n"
<> "Searched locations were:\n"
<> (unlines . List.map (('\t':) . Path.fromAbsFile) $ searchedLocations)
<> (Text.unlines . List.map (Path.fromAbsFile >>> ('\t':) >>> Text.pack) $ searchedLocations)
parseFile :: Path Abs File -> ParsecT String u Transformer File.File
parseFile :: Path Abs File -> ParsecT Token u Transformer File.File
parseFile path = do
let stringPath = Path.fromAbsFile path
contents <- liftIO . readFile $ stringPath
contents <- liftIO . Text.IO.readFile $ stringPath
-- save old state
oldInput <- Parsec.getInput
@ -123,10 +126,10 @@ parseFile path = do
pure importedFile
parseRelPath :: MonadThrow m => NonEmpty FilePath -> m (Path Rel File)
parseRelPath :: MonadThrow m => NonEmpty Token -> m (Path Rel File)
parseRelPath fragments = do
name <- Path.parseRelFile $ NonEmpty.last fragments
dirPath <- mapM Path.parseRelDir . NonEmpty.init $ fragments
name <- Path.parseRelFile . Text.unpack $ NonEmpty.last fragments
dirPath <- mapM (Path.parseRelDir . Text.unpack) . NonEmpty.init $ fragments
pure $ constructRelative name dirPath
constructRelative :: Path Rel t -> [Path Rel Dir] -> Path Rel t