Skip to content

Commit

Permalink
you can remove values from sets in gool
Browse files Browse the repository at this point in the history
  • Loading branch information
NoahCardoso committed Aug 23, 2024
1 parent bc00b71 commit 652da88
Show file tree
Hide file tree
Showing 11 changed files with 63 additions and 27 deletions.
1 change: 1 addition & 0 deletions code/drasil-gool/lib/Drasil/GOOL/CodeInfoOO.hs
Original file line number Diff line number Diff line change
Expand Up @@ -256,6 +256,7 @@ instance List CodeInfoOO where
instance Set CodeInfoOO where
contains = execute2
setAdd = execute2
setRemove = execute2

instance InternalList CodeInfoOO where
listSlice' b e s _ vl = zoom lensMStoVS $ do
Expand Down
1 change: 1 addition & 0 deletions code/drasil-gool/lib/Drasil/GOOL/CodeInfoProc.hs
Original file line number Diff line number Diff line change
Expand Up @@ -209,6 +209,7 @@ instance List CodeInfoProc where
instance Set CodeInfoProc where
contains = execute2
setAdd = execute2
setRemove = execute2

instance InternalList CodeInfoProc where
listSlice' b e s _ vl = zoom lensMStoVS $ do
Expand Down
6 changes: 6 additions & 0 deletions code/drasil-gool/lib/Drasil/GOOL/InterfaceCommon.hs
Original file line number Diff line number Diff line change
Expand Up @@ -288,6 +288,12 @@ class (ValueSym r) => Set r where
-- | Inserts a value into a set
-- Arguments are: Set, Value
setAdd :: SValue r -> SValue r -> SValue r
-- | Removes a value from a set
-- Arguments are: Set, Value
setRemove :: SValue r -> SValue r -> SValue r
-- | Removes a value from a set
-- Arguments are: Set, Set
--setUnion :: SValue r -> SValue r -> SValue r

class (ValueSym r) => InternalList r where
listSlice' :: Maybe (SValue r) -> Maybe (SValue r) -> Maybe (SValue r)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -66,7 +66,7 @@ import qualified Drasil.GOOL.LanguageRenderer.LanguagePolymorphic as G (
minusOp, multOp, divideOp, moduloOp, var, staticVar, objVar, arrayElem,
litChar, litDouble, litInt, litString, valueOf, arg, argsList, objAccess,
objMethodCall, call, funcAppMixedArgs, selfFuncAppMixedArgs, newObjMixedArgs,
lambda, func, get, set, setAddFunc, setAdd, listAdd, listAppend, listAccess, listSet, getFunc,
lambda, func, get, set, setMethodFunc, setAdd, setRemove, listAdd, listAppend, listAccess, listSet, getFunc,
setFunc, listAppendFunc, stmt, loopStmt, emptyStmt, assign, subAssign,
increment, objDecNew, print, closeFile, returnStmt, valStmt,
comment, throw, ifCond, tryCatch, construct, param, method, getMethod,
Expand Down Expand Up @@ -447,6 +447,7 @@ instance List CSharpCode where
instance Set CSharpCode where
contains = CP.contains csContains
setAdd = G.setAdd
setRemove = G.setRemove

instance InternalList CSharpCode where
listSlice' = M.listSlice
Expand All @@ -463,7 +464,8 @@ instance InternalListFunc CSharpCode where
listSetFunc = CP.listSetFunc R.listSetFunc

instance InternalSetFunc CSharpCode where
setAddFunc _ = G.setAddFunc csListAppend
setAddFunc _ = G.setMethodFunc csListAppend
setRemoveFunc _ = G.setMethodFunc csListRemove

instance ThunkSym CSharpCode where
type Thunk CSharpCode = CommonThunk VS
Expand Down Expand Up @@ -779,7 +781,7 @@ csLambdaSep = text "=>"

csSystem, csConsole, csGeneric, csDiagnostics, csIO, csList, csSet, csInt, csFloat, csBool,
csChar, csParse, csReader, csWriter, csReadLine, csWrite, csWriteLine,
csIndex, csContains, csListAdd, csListAppend, csClose, csEOS, csSplit, csMain,
csIndex, csContains, csListAdd, csListAppend, csListRemove, csClose, csEOS, csSplit, csMain,
csFunc :: String
csSystem = "System"
csConsole = "Console"
Expand All @@ -802,6 +804,7 @@ csIndex = "IndexOf"
csContains = "Contains"
csListAdd = "Insert"
csListAppend = "Add"
csListRemove = "Remove"
csClose = "Close"
csEOS = "EndOfStream"
csSplit = "Split"
Expand Down
13 changes: 10 additions & 3 deletions code/drasil-gool/lib/Drasil/GOOL/LanguageRenderer/CppRenderer.hs
Original file line number Diff line number Diff line change
Expand Up @@ -73,7 +73,7 @@ import qualified Drasil.GOOL.LanguageRenderer.LanguagePolymorphic as G (
minusOp, multOp, divideOp, moduloOp, var, staticVar, objVar, arrayElem,
litChar, litDouble, litInt, litString, valueOf, arg, argsList, objAccess,
objMethodCall, funcAppMixedArgs, selfFuncAppMixedArgs, newObjMixedArgs,
lambda, func, get, set, setAdd, setAddFunc, listAdd, listAppend, listAccess, listSet, getFunc,
lambda, func, get, set, setAdd, setRemove, setMethodFunc, listAdd, listAppend, listAccess, listSet, getFunc,
setFunc, listAppendFunc, stmt, loopStmt, emptyStmt, assign, subAssign,
increment, objDecNew, print, closeFile, returnStmt, valStmt, comment, throw,
ifCond, tryCatch, construct, param, method, getMethod, setMethod, function,
Expand Down Expand Up @@ -465,6 +465,7 @@ instance (Pair p) => List (p CppSrcCode CppHdrCode) where
instance (Pair p) => Set (p CppSrcCode CppHdrCode) where
contains = pair2 contains contains
setAdd = pair2 setAdd setAdd
setRemove = pair2 setRemove setRemove

instance (Pair p) => InternalList (p CppSrcCode CppHdrCode) where
listSlice' b e s vr vl = pair2
Expand All @@ -487,6 +488,7 @@ instance (Pair p) => InternalListFunc (p CppSrcCode CppHdrCode) where

instance (Pair p) => InternalSetFunc (p CppSrcCode CppHdrCode) where
setAddFunc = pair2 setAddFunc setAddFunc
setRemoveFunc = pair2 setRemoveFunc setRemoveFunc

instance ThunkSym (p CppSrcCode CppHdrCode) where
type Thunk (p CppSrcCode CppHdrCode) = CommonThunk VS
Expand Down Expand Up @@ -1395,6 +1397,7 @@ instance List CppSrcCode where
instance Set CppSrcCode where
contains = CP.containsInt cppIndex cppIterEnd
setAdd = G.setAdd
setRemove = G.setRemove

instance InternalList CppSrcCode where
listSlice' = M.listSlice
Expand All @@ -1411,7 +1414,8 @@ instance InternalListFunc CppSrcCode where
listSetFunc = CP.listSetFunc cppListSetDoc

instance InternalSetFunc CppSrcCode where
setAddFunc _ = G.setAddFunc cppListAdd
setAddFunc _ = G.setMethodFunc cppListAdd
setRemoveFunc _ = G.setMethodFunc cppListRemove

instance ThunkSym CppSrcCode where
type Thunk CppSrcCode = CommonThunk VS
Expand Down Expand Up @@ -2103,6 +2107,7 @@ instance List CppHdrCode where
instance Set CppHdrCode where
contains _ _ = mkStateVal void empty
setAdd _ _ = mkStateVal void empty
setRemove _ _ = mkStateVal void empty

instance InternalList CppHdrCode where
listSlice' _ _ _ _ _ = toState $ toCode empty
Expand All @@ -2120,6 +2125,7 @@ instance InternalListFunc CppHdrCode where

instance InternalSetFunc CppHdrCode where
setAddFunc _ _ = funcFromData empty void
setRemoveFunc _ _ = funcFromData empty void

instance ThunkSym CppHdrCode where
type Thunk CppHdrCode = CommonThunk VS
Expand Down Expand Up @@ -2512,7 +2518,7 @@ ptrAccess' = text ptrAccess
nmSpc, ptrAccess, cppFor, std, algorithm, cppString, vector, sstream, stringstream,
fstream, iostream, limits, mathh, cassert, cppBool, cppInfile, cppOutfile,
cppIterator, cppOpen, stod, stof, cppIgnore, numLimits, streamsize, max,
endl, cin, cout, cppIndex, cppListAccess, cppListAdd, cppListAppend,
endl, cin, cout, cppIndex, cppListAccess, cppListAdd, cppListRemove, cppListAppend,
cppIterBegin, cppIterEnd, cppR, cppW, cppA, cppGetLine, cppClose, cppClear,
cppStr, mathDefines, cppSet, cppIn, cppConst :: String
nmSpc = "::"
Expand Down Expand Up @@ -2546,6 +2552,7 @@ cout = stdAccess "cout"
cppIndex= "find"
cppListAccess = "at"
cppListAdd = "insert"
cppListRemove = "erase"
cppListAppend = "push_back"
cppIterBegin = "begin"
cppIterEnd = "end"
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -68,7 +68,7 @@ import qualified Drasil.GOOL.LanguageRenderer.LanguagePolymorphic as G (
minusOp, multOp, divideOp, moduloOp, var, staticVar, objVar, arrayElem,
litChar, litDouble, litInt, litString, valueOf, arg, argsList, objAccess,
objMethodCall, funcAppMixedArgs, selfFuncAppMixedArgs, newObjMixedArgs,
lambda, func, get, set, listAdd, setAdd, setAddFunc, listAppend, listAccess, listSet, getFunc,
lambda, func, get, set, listAdd, setAdd, setRemove, setMethodFunc, listAppend, listAccess, listSet, getFunc,
setFunc, listAppendFunc, stmt, loopStmt, emptyStmt, assign, subAssign,
increment, objDecNew, print, closeFile, returnStmt, valStmt, comment, throw,
ifCond, tryCatch, construct, param, method, getMethod, setMethod, function,
Expand Down Expand Up @@ -476,6 +476,7 @@ instance List JavaCode where
instance Set JavaCode where
contains = CP.contains jContains
setAdd = G.setAdd
setRemove = G.setRemove

instance InternalList JavaCode where
listSlice' = M.listSlice
Expand All @@ -492,7 +493,8 @@ instance InternalListFunc JavaCode where
listSetFunc = jListSetFunc

instance InternalSetFunc JavaCode where
setAddFunc _ = G.setAddFunc jListAdd
setAddFunc _ = G.setMethodFunc jListAdd
setRemoveFunc _ = G.setMethodFunc jListRemove

instance ThunkSym JavaCode where
type Thunk JavaCode = CommonThunk VS
Expand Down Expand Up @@ -820,7 +822,7 @@ jLambdaSep = text "->"
arrayList, jBool, jBool', jInteger, jObject, jScanner, jContains,
jPrintWriter, jFile, jFileWriter, jIOExc, jFNFExc, jArrays, jSet, jAsList, jSetOf, jStdIn,
jStdOut, jPrintLn, jEquals, jParseInt, jParseDbl, jParseFloat, jIndex,
jListAdd, jListAccess, jListSet, jClose, jNext, jNextLine, jNextBool,
jListAdd, jListRemove, jListAccess, jListSet, jClose, jNext, jNextLine, jNextBool,
jHasNextLine, jCharAt, jSplit, io, util :: String
arrayList = "ArrayList"
jBool = "boolean"
Expand All @@ -847,6 +849,7 @@ jParseDbl = CP.doubleRender `access` "parseDouble"
jParseFloat = CP.floatRender `access` "parseFloat"
jIndex = "indexOf"
jListAdd = "add"
jListRemove = "remove"
jListAccess = "get"
jListSet = "set"
jClose = "close"
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -30,7 +30,7 @@ import Drasil.GOOL.RendererClassesCommon (CommonRenderSym, ImportSym(..),
ImportElim, RenderBody(..), BodyElim, RenderBlock(..), BlockElim,
RenderType(..), InternalTypeElim, UnaryOpSym(..), BinaryOpSym(..),
OpElim(uOpPrec, bOpPrec), RenderVariable(..), InternalVarElim(variableBind),
RenderValue(..), ValueElim(..), InternalListFunc(..), RenderFunction(..),
RenderValue(..), ValueElim(..), InternalListFunc(..), InternalSetFunc(..), RenderFunction(..),
FunctionElim(functionType), InternalAssignStmt(..), InternalIOStmt(..),
InternalControlStmt(..), RenderStatement(..), StatementElim(statementTerm),
RenderVisibility(..), VisibilityElim, MethodTypeSym(..), RenderParam(..),
Expand Down Expand Up @@ -401,6 +401,7 @@ instance List JuliaCode where
instance Set JuliaCode where
contains = jlIndexOf
setAdd = CP.listAppend
setRemove = CP.listAppend

instance InternalList JuliaCode where
listSlice' b e s vn vo = jlListSlice vn vo b e (fromMaybe (litInt 1) s)
Expand All @@ -418,6 +419,10 @@ instance InternalListFunc JuliaCode where
listAccessFunc = CP.listAccessFunc
listSetFunc = CP.listSetFunc R.listSetFunc

instance InternalSetFunc JuliaCode where
setAddFunc = listAppendFunc
setRemoveFunc = listAppendFunc

instance ThunkSym JuliaCode where
type Thunk JuliaCode = CommonThunk VS

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -10,8 +10,8 @@ module Drasil.GOOL.LanguageRenderer.LanguagePolymorphic (fileFromData,
classVarCheckStatic, arrayElem, local, litChar, litDouble, litInt, litString,
valueOf, arg, argsList, call, funcAppMixedArgs, selfFuncAppMixedArgs,
newObjMixedArgs, lambda, objAccess, objMethodCall, func, get, set, listAdd,
listAppend, setAdd, listAccess, listSet, getFunc, setFunc,
listAppendFunc, setAddFunc, stmt, loopStmt, emptyStmt, assign, subAssign, increment,
listAppend, setAdd, setRemove, listAccess, listSet, getFunc, setFunc,
listAppendFunc, setMethodFunc, stmt, loopStmt, emptyStmt, assign, subAssign, increment,
objDecNew, print, closeFile, returnStmt, valStmt, comment, throw, ifCond,
tryCatch, construct, param, method, getMethod, setMethod, initStmts,
function, docFuncRepr, docFunc, buildClass, implementingClass, docClass,
Expand Down Expand Up @@ -50,7 +50,7 @@ import Drasil.GOOL.RendererClassesCommon (CommonRenderSym, RenderType(..),
BlockCommentSym(..))
import qualified Drasil.GOOL.RendererClassesCommon as S (RenderValue(call),
InternalListFunc (listAddFunc, listAppendFunc, listAccessFunc, listSetFunc),
RenderStatement(stmt), InternalIOStmt(..), InternalSetFunc (setAddFunc))
RenderStatement(stmt), InternalIOStmt(..), InternalSetFunc (setAddFunc, setRemoveFunc))
import qualified Drasil.GOOL.RendererClassesCommon as RC (BodyElim(..),
BlockElim(..), InternalVarElim(variable), ValueElim(value, valueInt),
FunctionElim(..), StatementElim(statement), BlockCommentElim(..))
Expand Down Expand Up @@ -308,9 +308,12 @@ listAdd v i vToAdd = v $. S.listAddFunc v (IC.intToIndex i) vToAdd
listAppend :: (OORenderSym r) => SValue r -> SValue r -> SValue r
listAppend v vToApp = v $. S.listAppendFunc v vToApp

setAdd :: (OORenderSym r, S.InternalSetFunc r) => SValue r -> SValue r -> SValue r
setAdd :: (OORenderSym r) => SValue r -> SValue r -> SValue r
setAdd v vToApp = v $. S.setAddFunc v vToApp

setRemove :: (OORenderSym r) => SValue r -> SValue r -> SValue r
setRemove v vToApp = v $. S.setRemoveFunc v vToApp

listAccess :: (CommonRenderSym r) => SValue r -> SValue r -> SValue r
listAccess v i = do
v' <- v
Expand Down Expand Up @@ -341,8 +344,8 @@ setFunc t v toVal = v >>= (\vr -> IG.func (setterName $ variableName vr) t
listAppendFunc :: (OORenderSym r) => Label -> SValue r -> VSFunction r
listAppendFunc f v = IG.func f (IC.listType $ onStateValue valueType v) [v]

setAddFunc :: (OORenderSym r) => Label -> SValue r -> VSFunction r
setAddFunc f v = IG.func f (IC.setType $ onStateValue valueType v) [v]
setMethodFunc :: (OORenderSym r) => Label -> SValue r -> VSFunction r
setMethodFunc f v = IG.func f (IC.setType $ onStateValue valueType v) [v]

-- Statements --

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -66,11 +66,11 @@ import qualified Drasil.GOOL.LanguageRenderer.LanguagePolymorphic as G (
minusOp, multOp, divideOp, moduloOp, var, staticVar, objVar, arrayElem,
litChar, litDouble, litInt, litString, valueOf, arg, argsList, objAccess,
objMethodCall, call, funcAppMixedArgs, selfFuncAppMixedArgs, newObjMixedArgs,
lambda, func, get, set, listAdd, setAdd, setAddFunc, listAppend, listAccess, listSet, getFunc,
setFunc, listAppendFunc, stmt, loopStmt, emptyStmt, assign, subAssign,
increment, objDecNew, print, closeFile, returnStmt, valStmt, comment, throw,
ifCond, tryCatch, construct, param, method, getMethod, setMethod, function,
buildClass, implementingClass, commentedClass, modFromData, fileDoc,
lambda, func, get, set, listAdd, setAdd, setRemove, setMethodFunc, listAppend,
listAccess, listSet, getFunc, setFunc, listAppendFunc, stmt, loopStmt, emptyStmt,
assign, subAssign, increment, objDecNew, print, closeFile, returnStmt, valStmt,
comment, throw, ifCond, tryCatch, construct, param, method, getMethod, setMethod,
function, buildClass, implementingClass, commentedClass, modFromData, fileDoc,
fileFromData, local)
import qualified Drasil.GOOL.LanguageRenderer.CommonPseudoOO as CP (int,
constructor, doxFunc, doxClass, doxMod, extVar, classVar, objVarSelf,
Expand Down Expand Up @@ -458,6 +458,7 @@ instance List PythonCode where
instance Set PythonCode where
contains a b = typeBinExpr (inPrec pyIn) bool b a
setAdd = G.setAdd
setRemove = G.setRemove

instance InternalList PythonCode where
listSlice' b e s vn vo = pyListSlice vn vo (getVal b) (getVal e) (getVal s)
Expand All @@ -477,7 +478,8 @@ instance InternalListFunc PythonCode where
listSetFunc = CP.listSetFunc R.listSetFunc

instance InternalSetFunc PythonCode where
setAddFunc _ = G.setAddFunc pyAdd
setAddFunc _ = G.setMethodFunc pyAdd
setRemoveFunc _ = G.setMethodFunc pyRemove

instance ThunkSym PythonCode where
type Thunk PythonCode = CommonThunk VS
Expand Down Expand Up @@ -840,7 +842,7 @@ pyInputFunc = text "input()" -- raw_input() for < Python 3.0
pyPrintFunc = text printLabel

pyListSize, pyIndex, pyInsert, pyAppendFunc, pyReadline, pyReadlines, pyClose,
pySplit, pyRange, pyRstrip, pyMath, pyIn, pyAdd :: String
pySplit, pyRange, pyRstrip, pyMath, pyIn, pyAdd, pyRemove :: String
pyListSize = "len"
pyIndex = "index"
pyInsert = "insert"
Expand All @@ -854,6 +856,7 @@ pyRstrip = "rstrip"
pyMath = "math"
pyIn = "in"
pyAdd = "add"
pyRemove = "remove"

pyDef, pyLambdaDec, pyElseIf, pyRaise, pyExcept :: Doc
pyDef = text "def"
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -69,7 +69,7 @@ import qualified Drasil.GOOL.LanguageRenderer.LanguagePolymorphic as G (
minusOp, multOp, divideOp, moduloOp, var, staticVar, objVar, arrayElem,
litChar, litDouble, litInt, litString, valueOf, arg, argsList, objAccess,
objMethodCall, call, funcAppMixedArgs, selfFuncAppMixedArgs, newObjMixedArgs,
lambda, func, get, set, setAdd, setAddFunc, listAdd, listAppend, listAccess, listSet, getFunc,
lambda, func, get, set, setAdd, setRemove, setMethodFunc, listAdd, listAppend, listAccess, listSet, getFunc,
setFunc, listAppendFunc, stmt, loopStmt, emptyStmt, assign, subAssign,
increment, objDecNew, print, returnStmt, valStmt, comment, throw, ifCond,
tryCatch, construct, param, method, getMethod, setMethod, initStmts,
Expand Down Expand Up @@ -463,6 +463,7 @@ instance List SwiftCode where
instance Set SwiftCode where
contains = CP.contains swiftContains
setAdd = G.setAdd
setRemove = G.setRemove

instance InternalList SwiftCode where
listSlice' b e s vn vo = swiftListSlice vn vo b e (fromMaybe (litInt 1) s)
Expand All @@ -481,7 +482,8 @@ instance InternalListFunc SwiftCode where
listSetFunc = CP.listSetFunc R.listSetFunc

instance InternalSetFunc SwiftCode where
setAddFunc _ = G.setAddFunc swiftListAdd
setAddFunc _ = G.setMethodFunc swiftListAdd
setRemoveFunc _ = G.setMethodFunc swiftListRemove

instance ThunkSym SwiftCode where
type Thunk SwiftCode = CommonThunk VS
Expand Down Expand Up @@ -907,7 +909,7 @@ swiftUnwrap' = text swiftUnwrap
swiftMain, swiftFoundation, swiftMath, swiftNil, swiftInt, swiftChar,
swiftURL, swiftFileHdl, swiftRetType, swiftVoid, swiftCommLine,
swiftSearchDir, swiftPathMask, swiftArgs, swiftWrite, swiftIndex,
swiftStride, swiftMap, swiftListAdd, swiftListAppend, swiftReadLine,
swiftStride, swiftMap, swiftListAdd, swiftListRemove, swiftListAppend, swiftReadLine,
swiftSeekEnd, swiftClose, swiftJoined, swiftAppendPath, swiftUrls, swiftSplit,
swiftData, swiftEncoding, swiftOf, swiftFrom, swiftTo, swiftBy, swiftAt,
swiftTerm, swiftFor, swiftIn, swiftContentsOf, swiftWriteTo, swiftSep,
Expand All @@ -931,6 +933,7 @@ swiftIndex = "firstIndex"
swiftStride = "stride"
swiftMap = "map"
swiftListAdd = "insert"
swiftListRemove = "remove"
swiftListAppend = "append"
swiftReadLine = "readLine"
swiftSeekEnd = "seekToEnd"
Expand Down
3 changes: 2 additions & 1 deletion code/drasil-gool/lib/Drasil/GOOL/RendererClassesCommon.hs
Original file line number Diff line number Diff line change
Expand Up @@ -35,7 +35,7 @@ class (AssignStatement r, DeclStatement r, IOStatement r,
r, Argument r, Literal r, MathConstant r, VariableValue r, CommandLineArgs r,
NumericExpression r, BooleanExpression r, Comparison r, List r,
InternalList r, VectorExpression r, TypeElim r, VariableElim r, RenderBlock r,
BlockElim r, RenderBody r, BodyElim r, InternalListFunc r, RenderFunction r,
BlockElim r, RenderBody r, BodyElim r, InternalListFunc r, InternalSetFunc r, RenderFunction r,
FunctionElim r, OpElim r, RenderParam r, ParamElim r, RenderVisibility r,
VisibilityElim r, InternalAssignStmt r, InternalIOStmt r,
InternalControlStmt r, RenderStatement r, StatementElim r, RenderType r,
Expand Down Expand Up @@ -170,6 +170,7 @@ class InternalListFunc r where
class InternalSetFunc r where
-- | Set, Value
setAddFunc :: SValue r -> SValue r -> VSFunction r
setRemoveFunc :: SValue r -> SValue r -> VSFunction r

class RenderFunction r where
funcFromData :: Doc -> VSType r -> VSFunction r
Expand Down

0 comments on commit 652da88

Please sign in to comment.