Skip to content

Commit

Permalink
Merge pull request #28 from lyncmi07/1_native_aliases
Browse files Browse the repository at this point in the history
1 native aliases
  • Loading branch information
lyncmi07 authored Aug 31, 2019
2 parents 59c562a + 466b031 commit c258b49
Show file tree
Hide file tree
Showing 17 changed files with 130 additions and 18 deletions.
1 change: 1 addition & 0 deletions .gitignore
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,7 @@ test/*
!test/*.hs
!test/*.ns
!test/*.ns.fail
!test/*.ns.disable
documents/*.pdf
documents/*.html
*.aux
Expand Down
25 changes: 25 additions & 0 deletions src/Com/NoSyn/Ast/If/AliasDefinition.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,25 @@
module Com.NoSyn.Ast.If.AliasDefinition where

import Com.NoSyn.Ast.Traits.TargetCodeGeneratable
import Com.NoSyn.Ast.Traits.EnvironmentUpdater
import Com.NoSyn.Environment.ProgramEnvironment
import Com.NoSyn.Data.Types
import Com.NoSyn.Error.CompilerStatus
import Data.Map.Ordered

data AliasDefinition =
ADNative Ident String
| ADNoSyn Ident Ident
deriving Show

instance TargetCodeGeneratable AliasDefinition where
generateD _ (ADNative _ _) = return "";
generateD _ (ADNoSyn _ _) = return "";

instance EnvironmentUpdater AliasDefinition where
updateEnvironment programEnvironment@(PE { aliases = aliasEnvironment }) a@(ADNative _ _) =
Error "Native aliases have not been implemented yet" (show a)
updateEnvironment programEnvironment@(PE { aliases = aliasEnvironment }) (ADNoSyn aliasName aliasType) = do
_ <- lookupDType aliasType aliasEnvironment
let updatedAliasEnvironment = (aliasName, aliasType) |< aliasEnvironment in
return (programEnvironment { aliases = updatedAliasEnvironment })
3 changes: 3 additions & 0 deletions src/Com/NoSyn/Ast/If/IfElement.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@ module Com.NoSyn.Ast.If.IfElement where

import Com.NoSyn.Ast.If.Constant
import Com.NoSyn.Ast.If.Expression
import Com.NoSyn.Ast.If.AliasDefinition
import Com.NoSyn.Ast.If.FunctionDefinition
import Com.NoSyn.Ast.If.Parameter
import Com.NoSyn.Ast.If.Program
Expand All @@ -14,6 +15,7 @@ import Com.NoSyn.Ast.Traits.TargetCodeGeneratable
data IfElement =
IfConstant Constant
| IfExpression Expression
| IfAliasDefinition AliasDefinition
| IfFunctionDefinition FunctionDefinition
| IfParameter Parameter
| IfProgram Program
Expand All @@ -30,6 +32,7 @@ data IfElement =
instance TargetCodeGeneratable IfElement where
generateD a (IfConstant b) = generateD a b
generateD a (IfExpression b) = generateD a b
generateD a (IfAliasDefinition b) = generateD a b
generateD a (IfFunctionDefinition b) = generateD a b
generateD a (IfParameter b) = generateD a b
generateD a (IfProgram b) = generateD a b
Expand Down
2 changes: 1 addition & 1 deletion src/Com/NoSyn/Ast/If/Parameter.hs
Original file line number Diff line number Diff line change
Expand Up @@ -42,7 +42,7 @@ instance TargetCodeGeneratable Parameter where
return $ parameterDType ++ "* " ++ paramName
generateD programEnvironment parameter@(PVariadic paramType paramName) = do
parameterDType <- getRealType programEnvironment parameter
return $ parameterDType ++ "... " ++ paramName
return $ parameterDType ++ "[] " ++ paramName ++ " ..."

instance Typeable Parameter where
getTypeNoCheck (PConst paramType _) = paramType
Expand Down
11 changes: 5 additions & 6 deletions src/Com/NoSyn/Ast/If/Program.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,26 +5,25 @@ import Com.NoSyn.Ast.Traits.EnvironmentUpdater
import Com.NoSyn.Ast.If.FunctionDefinition
import Com.NoSyn.Ast.If.VariableDeclaration
import Com.NoSyn.Ast.If.Block
import Com.NoSyn.Ast.If.AliasDefinition
import Com.NoSyn.Data.Types
import Data.Map.Ordered
import Com.NoSyn.Environment.ProgramEnvironment

type Program = Block ProgramStmt
data ProgramStmt =
PSAliasDef Ident Ident
PSAliasDef AliasDefinition
| PSFuncDef FunctionDefinition
| PSVarDec VariableDeclaration
deriving Show

instance TargetCodeGeneratable ProgramStmt where
generateD _ (PSAliasDef _ _) = return "";
generateD _ (PSAliasDef _) = return "";
generateD programEnvironment (PSFuncDef functionDefinition) = generateD programEnvironment functionDefinition
generateD programEnvironment (PSVarDec variableDeclaration) = generateD programEnvironment variableDeclaration

instance EnvironmentUpdater ProgramStmt where
updateEnvironment programEnvironment@(PE { aliases = aliasEnvironment }) (PSAliasDef aliasName aliasType) = do
_ <- lookupDType aliasType aliasEnvironment
let updatedAliasEnvironment = (aliasName, aliasType) |< aliasEnvironment in
return (programEnvironment { aliases = updatedAliasEnvironment })
updateEnvironment programEnvironment (PSAliasDef aliasDefinition) =
updateEnvironment programEnvironment aliasDefinition
instance Blockable ProgramStmt where
blockSeparator _ = ";\n"
17 changes: 17 additions & 0 deletions src/Com/NoSyn/Ast/Ifm1/AliasDefinition.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,17 @@
module Com.NoSyn.Ast.Ifm1.AliasDefinition where

import Com.NoSyn.Ast.Traits.IfElementGeneratable
import Com.NoSyn.Data.Types
import qualified Com.NoSyn.Ast.If.AliasDefinition as IfAliasDefinition
import qualified Com.NoSyn.Ast.If.IfElement as IfElement

data AliasDefinition =
ADNative Ident String
| ADNoSyn Ident Ident
deriving Show

instance IfElementGeneratable AliasDefinition where
generateIfElement programEnvironment (ADNative aliasName aliasType) =
return $ IfElement.IfAliasDefinition (IfAliasDefinition.ADNative aliasName aliasType)
generateIfElement programEnvironment (ADNoSyn aliasName aliasType) =
return $ IfElement.IfAliasDefinition (IfAliasDefinition.ADNoSyn aliasName aliasType)
8 changes: 5 additions & 3 deletions src/Com/NoSyn/Ast/Ifm1/Program.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,21 +6,23 @@ import qualified Com.NoSyn.Ast.If.Program as IfProgram
import Com.NoSyn.Data.Types
import Com.NoSyn.Ast.Traits.IfElementGeneratable
import Com.NoSyn.Ast.Ifm1.VariableDeclaration
import Com.NoSyn.Ast.Ifm1.AliasDefinition
import Com.NoSyn.Ast.Ifm1.FunctionDefinition
import Com.NoSyn.Error.CompilerStatus
import Com.NoSyn.Ast.If.Block
import Com.NoSyn.Ast.Traits.Listable

type Program = Block ProgramStmt
data ProgramStmt =
PSAliasDef Ident Ident
PSAliasDef AliasDefinition
| PSFuncDef FunctionDefinition
| PSVarDec VariableDeclaration
deriving Show

instance IfElementGeneratable ProgramStmt where
generateIfElement programEnvironment (PSAliasDef a b) =
return $ IfElement.IfProgramStmt (IfProgram.PSAliasDef a b)
generateIfElement programEnvironment (PSAliasDef a) = do
~(IfElement.IfAliasDefinition b) <- generateIfElement programEnvironment a
return $ IfElement.IfProgramStmt (IfProgram.PSAliasDef b)
generateIfElement programEnvironment (PSVarDec a) = do
~(IfElement.IfVariableDeclaration b) <- generateIfElement programEnvironment a
return $ IfElement.IfProgramStmt (IfProgram.PSVarDec b)
Expand Down
6 changes: 4 additions & 2 deletions src/Com/NoSyn/Environment/ProgramEnvironment.hs
Original file line number Diff line number Diff line change
Expand Up @@ -63,7 +63,8 @@ lookupDType noSynType aliasEnvironment
lookupDType' noSynType aliasEnvironment
| noSynType `OrderMap.member` aliasEnvironment = do
nextAlias <- compilerStatusFromMaybe ("COMPILER ERROR: imported library incorrect") (OrderMap.lookup noSynType aliasEnvironment)
lookupDType' nextAlias aliasEnvironment
if nextAlias == noSynType then return nextAlias -- If the aliases are the same then the break out of the loop because `nextAlias` is actually refering to a type in D
else lookupDType' nextAlias aliasEnvironment
| otherwise = return noSynType

lookupAtomicNoSynType::Ident->AliasEnvironment->CompilerStatus Ident
Expand All @@ -82,7 +83,8 @@ lookupAtomicNoSynType noSynType aliasEnvironment
lookupAtomicNoSynType' previousType noSynType aliasEnvironment
| noSynType `OrderMap.member` aliasEnvironment = do
nextAlias <- compilerStatusFromMaybe ("COMPILER ERROR: imported library incorrect") (OrderMap.lookup noSynType aliasEnvironment)
lookupAtomicNoSynType' noSynType nextAlias aliasEnvironment
if noSynType == nextAlias then return noSynType -- If the aliases are the same then the break out of the loop because `nextAlias` is actually refering to a type in D
else lookupAtomicNoSynType' noSynType nextAlias aliasEnvironment
| otherwise = return previousType


Expand Down
13 changes: 11 additions & 2 deletions src/Com/NoSyn/Evaluation/Program/Internal/AliasEvaluation.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
module Com.NoSyn.Evaluation.Program.Internal.AliasEvaluation (programAliasEvaluate) where

import Com.NoSyn.Ast.If.Program
import Com.NoSyn.Ast.If.AliasDefinition
import Com.NoSyn.Ast.Traits.Listable as Listable
import Com.NoSyn.Error.CompilerStatus
import Data.Map.Ordered
Expand All @@ -10,12 +11,20 @@ import Com.NoSyn.Data.Types

programAliasEvaluate::AliasEnvironment -> Program -> CompilerStatus AliasEnvironment
programAliasEvaluate defaultEnvironment program =
let environmentWithNativeAliases = addNativeAliases (Listable.toList program) defaultEnvironment in
let noSynLookupTable = createNoSynTypeLookupTable (Listable.toList program) in
createRealTypeLookupTable noSynLookupTable defaultEnvironment
createRealTypeLookupTable noSynLookupTable environmentWithNativeAliases

addNativeAliases::[ProgramStmt] -> AliasEnvironment -> AliasEnvironment
addNativeAliases [] aliasEnvironment = aliasEnvironment
addNativeAliases ((PSAliasDef (ADNative aliasName aliasType)):xs) aliasEnvironment =
let updatedAliasEnvironment = (aliasName, aliasType) |< aliasEnvironment in
addNativeAliases xs updatedAliasEnvironment
addNativeAliases (_:xs) aliasEnvironment = addNativeAliases xs aliasEnvironment

createNoSynTypeLookupTable::[ProgramStmt] -> OMap Ident Ident
createNoSynTypeLookupTable [] = Data.Map.Ordered.empty
createNoSynTypeLookupTable ((PSAliasDef aliasName aliasType):xs) =
createNoSynTypeLookupTable ((PSAliasDef (ADNoSyn aliasName aliasType)):xs) =
(aliasName, aliasType) |< (createNoSynTypeLookupTable xs)
createNoSynTypeLookupTable (_:xs) = createNoSynTypeLookupTable xs

Expand Down
13 changes: 9 additions & 4 deletions src/Com/NoSyn/Parser/ConcreteSyntaxConverter.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@ import Com.NoSyn.Ast.If.Block
import Com.NoSyn.Ast.If.Constant as IfConstant
import Com.NoSyn.Ast.Ifm1.Constant as Ifm1Constant
import Com.NoSyn.Ast.Ifm1.Expression
import Com.NoSyn.Ast.Ifm1.AliasDefinition
import Com.NoSyn.Ast.Ifm1.FunctionDefinition
import Com.NoSyn.Ast.If.Parameter as IfParameter
import Com.NoSyn.Ast.Ifm1.Parameter as Ifm1Parameter
Expand Down Expand Up @@ -154,10 +155,13 @@ convertFunctionDefinition (CBracketOpOverloadDef a b c d) = do
m <- convertBlockStatement d
return $ FDBracketOverload b a n m

convertAliasDefinition :: CAliasDefinition -> CompilerStatus ProgramStmt
convertAliasDefinition :: CAliasDefinition -> CompilerStatus AliasDefinition
convertAliasDefinition (CAliasDef o a b)
| o == "=" = return $ PSAliasDef a b
| otherwise = Error "alias statement must assign using '=' symbol" (show (CAliasDef o a b))
| o == "=" = return $ ADNoSyn a b
| otherwise = Error "alias statement must assign using '=' symbol" (show (CAliasDef o a b))
convertAliasDefinition (CNativeAliasDef o a b)
| o == "=" = return $ ADNative a b
| otherwise = Error "alias statement must assign using '=' symbol" (show (CNativeAliasDef o a b))

convertProgramStatement :: CProgramStatement -> CompilerStatus ProgramStmt
convertProgramStatement (CPSVarDec a) = do
Expand All @@ -167,7 +171,8 @@ convertProgramStatement (CPSFuncDef a) = do
n <- convertFunctionDefinition a
return $ PSFuncDef n
convertProgramStatement (CPSAliasDef a) = do
convertAliasDefinition a
n <- convertAliasDefinition a
return $ PSAliasDef n
convertProgramStatement (CPSImportStatement a) =
Error "COMPILER ERROR: Import statements should not be present in this context" (show (CPSImportStatement a))

Expand Down
1 change: 1 addition & 0 deletions src/Com/NoSyn/Parser/ConcreteSyntaxTree.hs
Original file line number Diff line number Diff line change
Expand Up @@ -72,6 +72,7 @@ data CFunctionDefinition =


data CAliasDefinition = CAliasDef String String String
| CNativeAliasDef String String String
deriving Show

data CProgramStatement =
Expand Down
7 changes: 7 additions & 0 deletions src/Com/NoSyn/Parser/Lexer.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,6 +15,7 @@ lexer (x:xs)
| x `elem` digits = lexNum (x:xs)
| x `elem` operatorChars = lexOperator (x:xs)
lexer ('"':xs) = lexString xs
lexer ('`':xs) = lexNativeCode xs
lexer (x:xs)
| x `elem` ['(', '[', '{'] = let (tokens, rest) = lexBracket x xs in
tokens ++ lexer rest
Expand Down Expand Up @@ -44,6 +45,12 @@ lexString' :: String -> String -> (Token, String)
lexString' ('"':xs) finalString = (TokenString finalString, xs)
lexString' (x:xs) currentString = lexString' xs (currentString ++ [x])

lexNativeCode x = let (nativeCodeToken, rest) = lexNativeCode' x "" in nativeCodeToken : lexer rest
lexNativeCode' :: String -> String -> (Token, String)
lexNativeCode' ('`':xs) finalNativeCode = (TokenNativeCode finalNativeCode, xs)
lexNativeCode' (x:xs) currentNativeCode = lexNativeCode' xs (currentNativeCode ++ [x])


lexNum x = let (numToken, rest) = lexNum' x "" in numToken : lexer rest
lexNum' :: String -> String -> (Token, String)
lexNum' ('.':xs) currentInt = lexDouble xs (currentInt ++ ".")
Expand Down
3 changes: 3 additions & 0 deletions src/Com/NoSyn/Parser/NoSynParser.y
Original file line number Diff line number Diff line change
Expand Up @@ -13,6 +13,7 @@ import Com.NoSyn.Parser.Token

%token
string { TokenString $$ }
nativecode { TokenNativeCode $$ }
integer { TokenInt $$ }
double { TokenDouble $$ }
char { TokenChar $$ }
Expand Down Expand Up @@ -99,6 +100,7 @@ BracketType : '(' empty ')' { Parentheses }
| '{' empty '}' { Curly }

AliasDefinition : alias ident operator ident { CAliasDef $3 $2 $4 }
| native alias ident operator nativecode {CNativeAliasDef $4 $3 $5 }

ProgramStatement : VariableDeclaration { CPSVarDec $1 }
| FunctionDefinition { CPSFuncDef $1 }
Expand All @@ -115,3 +117,4 @@ ModuleName : ident { CModuleIdent $1 }
parseError :: [Token] -> a
parseError (x:_) = error $ "Parser Error at " ++ (show x)
}

1 change: 1 addition & 0 deletions src/Com/NoSyn/Parser/Token.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@ module Com.NoSyn.Parser.Token where

data Token =
TokenString String
| TokenNativeCode String
| TokenInt Int
| TokenDouble Double
| TokenChar Char
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -33,6 +33,7 @@ serializeNamedFunction' (functionName, (x:xs)) serializedFunctions =
parameterVariables = Prelude.map (\(_, y) -> y) parameterList
variableSerializer (VConst typ name) = typ ++ ";" ++ name
variableSerializer (VPointer typ name) = typ ++ "*;" ++ name
variableSerializer (VVariadic typ name) = typ ++ "...;" ++ name
serializedParameters = concat $ intersperse "," $ Prelude.map variableSerializer parameterVariables

deserializeFunction :: String -> CompilerStatus (Ident, FunctionOverload)
Expand Down Expand Up @@ -67,4 +68,6 @@ deserializeParameters serializedParameters = do
let paramType:paramName:empty = splitOn ";" serializedParameter in
if (empty /= []) then Error ("Invalid serialization: " ++ serializedParameter) (serializedParameters)
else if (backTake 1 paramType) == "*" then return $ VPointer (backDrop 1 paramType) paramName
else if (backTake 3 paramType) == "..." then return $ VVariadic (backDrop 3 paramType) paramName
else return $ VConst paramType paramName

17 changes: 17 additions & 0 deletions test/aliases.ns.disable
Original file line number Diff line number Diff line change
@@ -0,0 +1,17 @@
%%SOURCE%%

alias AnotherInt = Int;

native Nothing assignment(Int* a, Int b);

Nothing infix_:=_(Int* a, AnotherInt b) {
assignment(b, b);
}

Nothing infix_+_(Int* a, AnotherInt b) {
a := add(a, b);
}

Int add(Int a, Int b) {
a;
}
17 changes: 17 additions & 0 deletions test/native_aliases.ns
Original file line number Diff line number Diff line change
@@ -0,0 +1,17 @@
%%SOURCE%%

native alias AnotherInt = `long`;

native Nothing assignment(AnotherInt* a, AnotherInt b);

Nothing infix_:=_(Int* a, AnotherInt b) {
assignment(b, b);
}

Nothing infix_+_(Int* a, AnotherInt b) {
a := add(a, b);
}

AnotherInt add(Int a, AnotherInt b) {
b;
}

0 comments on commit c258b49

Please sign in to comment.