Compare commits

..

No commits in common. "4e8e5b9e8432f33dd9dcecba1a9e543ea9cc4173" and "01fafec1c0f43b30a8b8cef0a9cd48fd7c9cc6a3" have entirely different histories.

8 changed files with 46 additions and 67 deletions

View file

@ -6,4 +6,4 @@ main :: IO ()
main = do main = do
text <- getContents text <- getContents
print $ Parsec.parse (File.parse <* Parsec.eof) "<stdin>" text print $ Parsec.parse File.parse "<stdin>" text

View file

@ -0,0 +1,23 @@
module Ubc.Parse.Syntax.Data.Struct
( Struct(..)
, addVariable
, addFunction)
where
import Ubc.Parse.Syntax.VariableType (VariableType)
import Ubc.Parse.Syntax.Function (Function)
type VariableName = String
data Struct = Struct
{ name :: String
, variables :: [(VariableName, VariableType)]
, functions :: [Function]
}
deriving (Show)
addVariable :: Struct -> VariableName -> VariableType -> Struct
addVariable (Struct sn vs fs) n t = Struct sn ((n, t): vs) fs
addFunction :: Struct -> Function -> Struct
addFunction (Struct sn vs fs) f = Struct sn vs (f:fs)

View file

@ -1,23 +0,0 @@
module Ubc.Parse.Syntax.Enumeration
( Enumeration(..)
, parse
)
where
import qualified Ubc.Parse.Syntax.Language as UbcLanguage
import Text.Parsec (ParsecT, many, (<?>))
type EnumerationMember = String
data Enumeration = Enumeration
{ name :: String
, members :: [EnumerationMember]
}
deriving (Show)
parse :: Monad m => ParsecT String u m Enumeration
parse = do
UbcLanguage.reserved "enum"
identifier <- UbcLanguage.identifier <?> "enum identifier"
values <- UbcLanguage.braces $ many UbcLanguage.identifier
return $ Enumeration identifier values

View file

@ -8,45 +8,38 @@ import Control.Monad ((<$!>))
import Text.Parsec (choice, ParsecT, many) import Text.Parsec (choice, ParsecT, many)
import Ubc.Parse.Syntax.Struct ( Struct ) import Ubc.Parse.Syntax.Data.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 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
import qualified Ubc.Parse.Syntax.Enumeration as Enumeration
data File = File data File = File
{ name :: String { name :: String
, structs :: [Struct] , structs :: [Struct]
, functions :: [Function] , functions :: [Function]
, statements :: [Statement] , statements :: [Statement]
, enumerations :: [Enumeration]
} }
deriving (Show) deriving (Show)
data FileMember = FileFunction Function data FileMember = FileFunction Function
| FileStruct Struct | FileStruct Struct
| FileEnumeration Enumeration
| FileStatement Statement | FileStatement Statement
accumulateFile :: File -> FileMember -> File accumulateFile :: File -> FileMember -> File
accumulateFile (File name_ sss fs sts es) (FileStruct s) = File name_ (s:sss) fs sts es accumulateFile (File name_ struct_ functions_ statements_) (FileFunction f) = File name_ struct_ (f:functions_) statements_
accumulateFile (File name_ sss fs sts es) (FileFunction f) = File name_ sss (f:fs) sts es accumulateFile (File name_ struct_ functions_ statements_) (FileStatement s) = File name_ struct_ functions_ (s:statements_)
accumulateFile (File name_ sss fs sts es) (FileStatement s) = File name_ sss fs (s:sts) es accumulateFile (File name_ struct_ functions_ statements_) (FileStruct s) = File name_ (s:struct_) functions_ statements_
accumulateFile (File name_ sss fs sts es) (FileEnumeration e) = File name_ sss fs sts (e:es)
parse :: Monad m => ParsecT String u m File parse :: Monad m => ParsecT String u m File
parse = foldr (flip accumulateFile) (File "" [] [] [] []) <$!> many fileMember parse = foldl accumulateFile (File "" [] [] []) <$!> many fileMember
fileMember :: Monad m => ParsecT String u m FileMember fileMember :: Monad m => ParsecT String u m FileMember
fileMember = choice fileMember = choice
[ FileStruct <$!> Struct.parse [ FileStruct <$!> Struct.parse
, FileFunction <$!> Function.parse , FileFunction <$!> Function.parse
, FileStatement <$!> Statement.parse , FileStatement <$!> Statement.parse
, FileEnumeration <$!> Enumeration.parse
] ]

View file

@ -56,7 +56,6 @@ languageDef = LanguageDef {
, opStart = oneOf "+-*/%" , opStart = oneOf "+-*/%"
, opLetter = oneOf "+-*/%" , opLetter = oneOf "+-*/%"
, reservedNames = [ "struct" , reservedNames = [ "struct"
, "enum"
, "u32" , "u32"
, "i32" , "i32"
, "f32" , "f32"

View file

@ -1,14 +1,9 @@
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE DeriveGeneric #-}
module Ubc.Parse.Syntax.Struct module Ubc.Parse.Syntax.Struct
( Struct(..) ( Struct(..)
, parse , parse
) )
where where
-- yay, explicit dependency on ghc
import GHC.Generics (Generic)
import Control.Monad ((<$!>)) import Control.Monad ((<$!>))
import Text.Parsec import Text.Parsec
@ -18,41 +13,33 @@ import Text.Parsec
ParsecT, ParsecT,
) )
import Ubc.Parse.Syntax.Data.Struct (Struct(..))
import Ubc.Parse.Syntax.VariableType (VariableType) import Ubc.Parse.Syntax.VariableType (VariableType)
import Ubc.Parse.Syntax.Function (Function)
import qualified Ubc.Parse.Syntax.Language as UbcLanguage import qualified Ubc.Parse.Syntax.Language as UbcLanguage
import qualified Ubc.Parse.Syntax.VariableType as VariableType import qualified Ubc.Parse.Syntax.VariableType as VariableType
import qualified Ubc.Parse.Syntax.Data.Struct as Struct
import qualified Ubc.Parse.Syntax.Function as Function import qualified Ubc.Parse.Syntax.Function as Function
type VariableName = String type VariableName = String
data StructStatement = Variable VariableName VariableType
data Struct = Struct | Function Function.Function
{ name :: String
, body :: StructBody
}
deriving (Show)
data StructBody = StructBody
{ variables :: [(VariableName, VariableType)]
, functions :: [Function]
}
deriving stock (Generic, Show)
deriving (Semigroup, Monoid) via StructBody
parse :: Monad m => ParsecT String u m Struct parse :: Monad m => ParsecT String u m Struct
parse = do parse = do
_ <- UbcLanguage.reserved "struct" _ <- UbcLanguage.reserved "struct"
structIdentifier <- UbcLanguage.identifier structIdentifier <- UbcLanguage.identifier
structBody <- mconcat <$!> UbcLanguage.braces (many structMember)
pure $ Struct structIdentifier structBody foldl accumulateStruct (Struct structIdentifier [] []) <$!> UbcLanguage.braces (many structMember)
structMember :: Monad m => ParsecT String u m StructBody accumulateStruct :: Struct -> StructStatement -> Struct
accumulateStruct s (Variable n t) = Struct.addVariable s n t
accumulateStruct s (Function f) = Struct.addFunction s f
structMember :: Monad m => ParsecT String u m StructStatement
structMember = choice [ structVariableOrFunction ] structMember = choice [ structVariableOrFunction ]
structVariableOrFunction :: Monad m => ParsecT String u m StructBody structVariableOrFunction :: Monad m => ParsecT String u m StructStatement
structVariableOrFunction = do structVariableOrFunction = do
(typeName, identifier) <- try $ do (typeName, identifier) <- try $ do
typeName <- UbcLanguage.typeName typeName <- UbcLanguage.typeName
@ -60,10 +47,10 @@ structVariableOrFunction = do
return (VariableType.fromString typeName, objectIdentifier) return (VariableType.fromString typeName, objectIdentifier)
choice choice
[ parseVariable typeName identifier [ parseVariable typeName identifier
, (\ f -> mempty { functions = [f] }) <$!> Function.parsePrefixed typeName identifier , Function <$!> Function.parsePrefixed typeName identifier
] ] -- TODO: Functions on structs
parseVariable :: Monad m => VariableType -> String -> ParsecT String u m StructBody parseVariable :: Monad m => VariableType -> String -> ParsecT String u m StructStatement
parseVariable variableType variableName = do parseVariable variableType variableName = do
_ <- UbcLanguage.semicolon _ <- UbcLanguage.semicolon
return $ mempty { variables = [(variableName, variableType)] } return $ Variable variableName variableType

View file

@ -9,7 +9,7 @@ import Control.Monad ((<$!>))
import Text.Parsec (choice, ParsecT) import Text.Parsec (choice, ParsecT)
import Ubc.Parse.Syntax.VariableType (VariableType) import Ubc.Parse.Syntax.VariableType (VariableType)
import Ubc.Parse.Syntax.Struct (Struct) import Ubc.Parse.Syntax.Data.Struct (Struct)
import qualified Ubc.Parse.Syntax.Language as UbcLanguage import qualified Ubc.Parse.Syntax.Language as UbcLanguage
import qualified Ubc.Parse.Syntax.VariableType as VariableType import qualified Ubc.Parse.Syntax.VariableType as VariableType

View file

@ -26,7 +26,7 @@ source-repository head
library library
exposed-modules: exposed-modules:
Ubc.Parse.Syntax.Config Ubc.Parse.Syntax.Config
Ubc.Parse.Syntax.Enumeration Ubc.Parse.Syntax.Data.Struct
Ubc.Parse.Syntax.Expression Ubc.Parse.Syntax.Expression
Ubc.Parse.Syntax.File Ubc.Parse.Syntax.File
Ubc.Parse.Syntax.Function Ubc.Parse.Syntax.Function