Removed complicated validation, Basic Expression parsing

This commit is contained in:
vegowotenks 2025-01-17 21:13:00 +01:00
parent 1c1e25a881
commit 839e278e43
7 changed files with 36 additions and 37 deletions

View file

@ -5,7 +5,7 @@ module Ubc.Parse.Struct
where
import Data.Functor ( (<&>) )
import Control.Arrow ( Arrow(second) )
import Control.Arrow ( (>>>) )
import Text.Parsec
( char,
@ -15,13 +15,11 @@ import Text.Parsec
many,
modifyState,
try,
unexpected,
ParsecT )
import Ubc.Parse.ParserState (ParserState)
import Ubc.Parse.Scope.StructScope (StructScope(..))
import Ubc.Parse.Scope (Scope(..))
import Ubc.Parse.Types (checkTypeValidity)
import Ubc.Parse.Data.Struct (Struct(..))
import qualified Ubc.Parse.Language as UbcLanguage
@ -30,7 +28,6 @@ import qualified Ubc.Parse.ParserState as ParserState
import qualified Ubc.Parse.Scope as Scope
import qualified Ubc.Parse.VariableType as VariableType
import qualified Data.Map as Map
parseStruct :: Monad m => ParsecT String ParserState m Struct
parseStruct = do
@ -39,7 +36,7 @@ parseStruct = do
structIdentifier <- UbcLanguage.identifier
let structScope = StructScope
{ structName = structIdentifier
, variables = Map.empty
, variables = []
}
modifyState (ParserState.pushScope . ScopeStruct $ structScope)
@ -66,24 +63,9 @@ structVariableOrFunction = do
parseVariable :: Monad m => String -> String -> ParsecT String ParserState m ()
parseVariable variableType variableName = do
_ <- UbcLanguage.semicolon
-- TODO: Validate type
(_, structScope) <- getState <&> second Scope.expectScopeStruct . ParserState.popScope
-- check variable name
if (/= Nothing) . Map.lookup variableName . StructScope.variables $ structScope
then do
unexpected $ "variable name: \"" ++ variableName ++ "\", this name is already defined"
else do
return ()
-- check type
isKnownType <- checkTypeValidity variableType
if not isKnownType
then do
unexpected $ "variable type: \"" ++ variableType ++ "\", this type is not defined"
else do
return ()
let structScope' = StructScope.modifyVariables (Map.insert variableName (VariableType.fromString variableType)) structScope
modifyState (ParserState.pushScope $ ScopeStruct structScope')
modifyState (ParserState.modifyScope (Scope.expectScopeStruct
>>> StructScope.modifyVariables ((variableName, VariableType.fromString variableType):)
>>> Scope.ScopeStruct
)
)