Compare commits

...

2 commits

4 changed files with 18 additions and 5 deletions

View file

@ -1,4 +1,7 @@
module Ubc.Parse.Syntax.Expression module Ubc.Parse.Syntax.Expression
( Expression(..)
, expressionParser
)
where where
import Text.Parsec (ParsecT) import Text.Parsec (ParsecT)

View file

@ -13,11 +13,15 @@ import Data.Functor ((<&>))
import Text.Parsec (choice, ParsecT, many) import Text.Parsec (choice, ParsecT, many)
import Ubc.Parse.Syntax (Transformer)
import {-# SOURCE #-} Ubc.Parse.Syntax.Import (Import)
import Ubc.Parse.Syntax.Struct (Struct) import Ubc.Parse.Syntax.Struct (Struct)
import Ubc.Parse.Syntax.Function (Function) import Ubc.Parse.Syntax.Function (Function)
import Ubc.Parse.Syntax.Statement (Statement) import Ubc.Parse.Syntax.Statement (Statement)
import Ubc.Parse.Syntax.Enumeration (Enumeration) import Ubc.Parse.Syntax.Enumeration (Enumeration)
import {-# SOURCE #-} qualified Ubc.Parse.Syntax.Import as Import
import qualified Ubc.Parse.Syntax.Struct as Struct import qualified Ubc.Parse.Syntax.Struct as Struct
import qualified Ubc.Parse.Syntax.Function as Function import qualified Ubc.Parse.Syntax.Function as Function
import qualified Ubc.Parse.Syntax.Statement as Statement import qualified Ubc.Parse.Syntax.Statement as Statement
@ -30,7 +34,8 @@ data File = File
deriving (Show) deriving (Show)
data FileBody = FileBody data FileBody = FileBody
{ structs :: [Struct] { imports :: [Import]
, structs :: [Struct]
, functions :: [Function] , functions :: [Function]
, statements :: [Statement] , statements :: [Statement]
, enumerations :: [Enumeration] , enumerations :: [Enumeration]
@ -39,12 +44,13 @@ data FileBody = FileBody
deriving (Semigroup, Monoid) via Generically FileBody deriving (Semigroup, Monoid) via Generically FileBody
-- dont use `deriving ... via FileBody` because that leads to a loop, somehow -- dont use `deriving ... via FileBody` because that leads to a loop, somehow
parse :: Monad m => String -> ParsecT String u m File parse :: String -> ParsecT String u Transformer File
parse source = File source <$!> mconcat <$!> many fileMember parse source = File source <$!> mconcat <$!> many fileMember
fileMember :: Monad m => ParsecT String u m FileBody fileMember :: ParsecT String u Transformer FileBody
fileMember = choice fileMember = choice
[ Struct.parse <&> \s -> mempty { structs = [s] } [ Struct.parse <&> \s -> mempty { structs = [s] }
, Import.parse <&> \i -> mempty { imports = [i] }
, Function.parse <&> \f -> mempty { functions = [f] } , Function.parse <&> \f -> mempty { functions = [f] }
, Statement.parse <&> \s -> mempty { statements = [s] } , Statement.parse <&> \s -> mempty { statements = [s] }
, Enumeration.parse <&> \e -> mempty { enumerations = [e] } , Enumeration.parse <&> \e -> mempty { enumerations = [e] }

View file

@ -1,4 +1,5 @@
{-# LANGUAGE LambdaCase #-} {-# LANGUAGE LambdaCase #-}
{-# LANGUAGE DerivingStrategies #-}
module Ubc.Parse.Syntax.Import module Ubc.Parse.Syntax.Import
( parse ( parse
, Import(..) , Import(..)
@ -37,6 +38,7 @@ data Import = Import
{ file :: File.File { file :: File.File
, alias :: String , alias :: String
} }
deriving stock (Show)
importPath :: Monad m => ParsecT String u m (NonEmpty String) importPath :: Monad m => ParsecT String u m (NonEmpty String)
importPath = UbcLanguage.angles (many importChar `sepBy1` char '/') importPath = UbcLanguage.angles (many importChar `sepBy1` char '/')
@ -84,7 +86,7 @@ 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 :: Path Abs File -> String -> ParsecT String u Transformer Import
parseFile path importAs = do parseFile path importAs = do
let stringPath = Path.fromAbsFile path let stringPath = Path.fromAbsFile path
contents <- liftIO . readFile $ stringPath contents <- liftIO . readFile $ stringPath

View file

@ -1,4 +1,6 @@
module Ubc.Parse.Syntax.Statement module Ubc.Parse.Syntax.Statement
( Statement
)
where where
data Statement data Statement