Added Generics to functions and structs
This commit is contained in:
parent
ac0e697622
commit
21bec764db
5 changed files with 37 additions and 8 deletions
|
@ -12,12 +12,15 @@ import Text.Parsec (lookAhead, try, ParsecT)
|
|||
import Ubc.Parse.Syntax.VariableType (VariableType)
|
||||
import {-# SOURCE #-} Ubc.Parse.Syntax.Expression (Expression, expressionParser)
|
||||
|
||||
import Ubc.Parse.Syntax.Generic (Generic)
|
||||
import qualified Ubc.Parse.Syntax.Language as UbcLanguage
|
||||
import qualified Ubc.Parse.Syntax.VariableType as VariableType
|
||||
import qualified Ubc.Parse.Syntax.Generic as Generic
|
||||
|
||||
data Function = Function
|
||||
{ identifier :: String
|
||||
, returnType :: VariableType
|
||||
{ returnType :: VariableType
|
||||
, identifier :: String
|
||||
, generics :: [Generic]
|
||||
, body :: Expression
|
||||
, arguments :: [(VariableType, String)]
|
||||
}
|
||||
|
@ -25,11 +28,13 @@ data Function = Function
|
|||
|
||||
parsePrefixed :: Monad m => VariableType -> String -> ParsecT String u m Function
|
||||
parsePrefixed ftype fname = do
|
||||
genericList <- UbcLanguage.angles $ UbcLanguage.commaSeparated1 Generic.parse
|
||||
|
||||
argumentList <- UbcLanguage.parens (UbcLanguage.commaSeparated argumentDefinition)
|
||||
|
||||
expressionBody <- expressionParser
|
||||
|
||||
return $ Function fname ftype expressionBody argumentList
|
||||
return $ Function ftype fname genericList expressionBody argumentList
|
||||
|
||||
parse :: Monad m => ParsecT String u m Function
|
||||
parse = do
|
||||
|
|
17
src/Ubc/Parse/Syntax/Generic.hs
Normal file
17
src/Ubc/Parse/Syntax/Generic.hs
Normal file
|
@ -0,0 +1,17 @@
|
|||
{-# LANGUAGE DerivingStrategies #-}
|
||||
module Ubc.Parse.Syntax.Generic
|
||||
( Generic(..)
|
||||
, parse)
|
||||
where
|
||||
|
||||
import qualified Ubc.Parse.Syntax.Language as Language
|
||||
import Control.Monad ((<$!>))
|
||||
import Text.Parsec (ParsecT)
|
||||
|
||||
data Generic = Generic
|
||||
{ name :: String
|
||||
}
|
||||
deriving stock (Show)
|
||||
|
||||
parse :: Monad m => ParsecT String u m Generic
|
||||
parse = Generic <$!> Language.identifier
|
|
@ -23,7 +23,7 @@ import qualified Data.List.NonEmpty as NonEmpty
|
|||
|
||||
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 Path as Path ( Path, File, parseRelFile, Rel, parseRelDir, Dir, Abs, (</>), fromAbsFile, fromRelFile )
|
||||
|
@ -36,7 +36,8 @@ import qualified Ubc.Parse.Syntax.Language as UbcLanguage
|
|||
|
||||
data Import = Import
|
||||
{ file :: File.File
|
||||
, alias :: String
|
||||
, alias :: Maybe String
|
||||
, list :: [String]
|
||||
}
|
||||
deriving stock (Show)
|
||||
|
||||
|
@ -71,9 +72,11 @@ parse = do
|
|||
[path] -> parseFile path
|
||||
fs@_ -> fail $ multipleFoundMessage relFile fs
|
||||
|
||||
importAs <- Parsec.parserTraced "alias" $ option (NonEmpty.last fragments) importAlias
|
||||
importAs <- Parsec.optionMaybe importAlias
|
||||
|
||||
return $ Import importedFile importAs
|
||||
importList <- UbcLanguage.parens $ UbcLanguage.commaSeparated UbcLanguage.identifier
|
||||
|
||||
return $ Import importedFile importAs importList
|
||||
|
||||
importAlias :: Monad m => ParsecT String u m String
|
||||
importAlias = UbcLanguage.reserved "as"
|
||||
|
|
|
@ -25,11 +25,13 @@ import Ubc.Parse.Syntax.Function (Function)
|
|||
import qualified Ubc.Parse.Syntax.Language as UbcLanguage
|
||||
import qualified Ubc.Parse.Syntax.VariableType as VariableType
|
||||
import qualified Ubc.Parse.Syntax.Function as Function
|
||||
import qualified Ubc.Parse.Syntax.Generic as Syntax.Generic
|
||||
|
||||
type VariableName = String
|
||||
|
||||
data Struct = Struct
|
||||
{ name :: String
|
||||
, generics :: [Syntax.Generic.Generic]
|
||||
, body :: StructBody
|
||||
}
|
||||
deriving (Show)
|
||||
|
@ -45,9 +47,10 @@ parse :: Monad m => ParsecT String u m Struct
|
|||
parse = do
|
||||
_ <- UbcLanguage.reserved "struct"
|
||||
structIdentifier <- UbcLanguage.identifier
|
||||
structGenerics <- UbcLanguage.angles $ UbcLanguage.commaSeparated1 Syntax.Generic.parse
|
||||
structBody <- mconcat <$!> UbcLanguage.braces (many structMember)
|
||||
|
||||
pure $ Struct structIdentifier structBody
|
||||
pure $ Struct structIdentifier structGenerics structBody
|
||||
|
||||
structMember :: Monad m => ParsecT String u m StructBody
|
||||
structMember = choice [ structVariableOrFunction ]
|
||||
|
|
|
@ -31,6 +31,7 @@ library
|
|||
Ubc.Parse.Syntax.Expression
|
||||
Ubc.Parse.Syntax.File
|
||||
Ubc.Parse.Syntax.Function
|
||||
Ubc.Parse.Syntax.Generic
|
||||
Ubc.Parse.Syntax.Import
|
||||
Ubc.Parse.Syntax.Language
|
||||
Ubc.Parse.Syntax.Operators
|
||||
|
|
Loading…
Reference in a new issue