Compare commits

..

No commits in common. "6242b2f1eb3232022277f973d3ecdf806703ea8a" and "82cdfdac4028b39774ba2b7b4326f4246fff6820" have entirely different histories.

2 changed files with 17 additions and 28 deletions

View file

@ -11,7 +11,7 @@ import Control.Monad (filterM)
import Control.Monad.Catch ( MonadThrow, ) import Control.Monad.Catch ( MonadThrow, )
import Control.Monad.Trans (lift, MonadIO (liftIO)) import Control.Monad.Trans (lift, MonadIO (liftIO))
import Control.Monad.Trans.Except () import Control.Monad.Trans.Except ()
import Control.Monad.Trans.Reader (asks, ReaderT) import Control.Monad.Trans.Reader (asks)
import Data.Functor ((<&>)) import Data.Functor ((<&>))
@ -22,20 +22,18 @@ import qualified Data.List.NonEmpty as NonEmpty
import qualified System.Directory as IO import qualified System.Directory as IO
import Text.Parsec (sepBy1, ParsecT, anyChar, many, char, choice, notFollowedBy, oneOf, option) import Text.Parsec (sepBy1, ParsecT, anyChar, many, char, choice, notFollowedBy, oneOf)
import qualified Text.Parsec as Parsec import qualified Text.Parsec as Parsec
import Path as Path ( Path, File, parseRelFile, Rel, parseRelDir, Dir, Abs, (</>), fromAbsFile, fromRelFile ) import Path as Path ( Path, File, parseRelFile, Rel, parseRelDir, Dir, Abs, (</>), fromAbsFile, fromRelFile )
import Ubc.Parse.Syntax (Transformer) import Ubc.Parse.Syntax (Transformer)
import Ubc.Parse.Syntax.Config (Config)
import qualified Ubc.Parse.Syntax.Config as Config import qualified Ubc.Parse.Syntax.Config as Config
import qualified Ubc.Parse.Syntax.File as File import qualified Ubc.Parse.Syntax.File as File
import qualified Ubc.Parse.Syntax.Language as UbcLanguage import qualified Ubc.Parse.Syntax.Language as UbcLanguage
data Import = Import data Import = Import
{ file :: File.File { file :: File.File
, alias :: String
} }
importPath :: Monad m => ParsecT String u m (NonEmpty String) importPath :: Monad m => ParsecT String u m (NonEmpty String)
@ -52,27 +50,19 @@ parse :: ParsecT String u Transformer Import
parse = do parse = do
UbcLanguage.reserved "import" UbcLanguage.reserved "import"
fragments <- importPath fragments <- importPath
importAs <- option (NonEmpty.last fragments) importAlias
-- concatenate directory and file parts, also utf-decoding case parseRelPath fragments of
relFile <- case parseRelPath fragments of Left err -> fail $ "Failed to decode path:\n" <> show err
Left err -> fail $ "Failed to decode path:\n" <> show err Right relFile -> do
Right relFile -> pure relFile possiblePaths <- lift $ constructPaths relFile
existingFiles <- liftIO $ filterInexistent possiblePaths
tryImport relFile possiblePaths existingFiles
-- appended to all search directories tryImport :: Path Rel File -> [Path Abs File] -> [Path Abs File] -> ParsecT String u Transformer Import
possiblePaths <- lift $ constructPaths relFile tryImport targetFile searchedPaths = \case
-- only existing files [] -> fail $ notFoundMessage targetFile searchedPaths
existingFiles <- liftIO $ filterInexistent possiblePaths [path] -> parseFile path
fs@_ -> fail $ multipleFoundMessage targetFile fs
-- fail if there are multiple files
case existingFiles of
[] -> fail $ notFoundMessage relFile possiblePaths
[path] -> parseFile path importAs
fs@_ -> fail $ multipleFoundMessage relFile fs
importAlias :: Monad m => ParsecT String u m String
importAlias = UbcLanguage.reserved "as"
*> UbcLanguage.identifier
multipleFoundMessage :: Path Rel File -> [Path Abs File] -> String multipleFoundMessage :: Path Rel File -> [Path Abs File] -> String
multipleFoundMessage relFile foundFiles = "Could not identify imported file " <> Path.fromRelFile relFile <> "\n" multipleFoundMessage relFile foundFiles = "Could not identify imported file " <> Path.fromRelFile relFile <> "\n"
@ -84,8 +74,8 @@ notFoundMessage relFile searchedLocations = "Could not locate import file path"
<> "Searched locations were:" <> "Searched locations were:"
<> (unlines . List.map (('\t':) . Path.fromAbsFile) $ searchedLocations) <> (unlines . List.map (('\t':) . Path.fromAbsFile) $ searchedLocations)
parseFile :: MonadIO m => Path Abs File -> String -> ParsecT String u m Import parseFile :: MonadIO m => Path Abs File -> ParsecT String u m Import
parseFile path importAs = do parseFile path = do
let stringPath = Path.fromAbsFile path let stringPath = Path.fromAbsFile path
contents <- liftIO . readFile $ stringPath contents <- liftIO . readFile $ stringPath
@ -108,7 +98,7 @@ parseFile path importAs = do
Parsec.setInput oldInput Parsec.setInput oldInput
Parsec.setPosition oldPosition Parsec.setPosition oldPosition
pure $ Import importedFile importAs pure $ Import importedFile
parseRelPath :: MonadThrow m => NonEmpty FilePath -> m (Path Rel File) parseRelPath :: MonadThrow m => NonEmpty FilePath -> m (Path Rel File)
parseRelPath fragments = do parseRelPath fragments = do
@ -122,7 +112,7 @@ constructRelative = foldr (</>)
filterInexistent :: [Path Abs File] -> IO [Path Abs File] filterInexistent :: [Path Abs File] -> IO [Path Abs File]
filterInexistent paths = filterM (IO.doesFileExist . Path.fromAbsFile) paths filterInexistent paths = filterM (IO.doesFileExist . Path.fromAbsFile) paths
constructPaths :: Monad m => Path Rel t -> ReaderT Config m [Path Abs t] constructPaths :: Path Rel File -> Transformer [Path Abs File]
constructPaths suffix = do constructPaths suffix = do
paths <- asks Config.includePaths paths <- asks Config.includePaths
Set.toList Set.toList

View file

@ -67,7 +67,6 @@ languageDef = LanguageDef {
, "while" , "while"
, "until" , "until"
, "type" , "type"
, "import"
] ]
, reservedOpNames = [ "+" , reservedOpNames = [ "+"
, "-" , "-"