Skip to content
This repository has been archived by the owner on Mar 4, 2024. It is now read-only.

Commit

Permalink
fix: fixed bugs in the runtime
Browse files Browse the repository at this point in the history
  • Loading branch information
prescientmoon committed Apr 27, 2020
1 parent 3c5baab commit 54fc101
Show file tree
Hide file tree
Showing 6 changed files with 21 additions and 14 deletions.
2 changes: 1 addition & 1 deletion src/Component/Editor/Node.purs
Original file line number Diff line number Diff line change
Expand Up @@ -168,7 +168,7 @@ renderNode { nodeData: nodeData
}
_ -> mempty

maxRadius = nodeRadius + (toNumber $ List.length inputArcs - 1) * inputLayerOffset
maxRadius = nodeRadius + (toNumber $ List.length inputArcs - 1) * inputLayerOffset + arcWidth * 2.0

valueSvg =
maybe mempty
Expand Down
3 changes: 1 addition & 2 deletions src/Component/Editor/Node/Overlays.purs
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,6 @@ import Prelude
import Data.Array (mapWithIndex)
import Data.Int (toNumber)
import Halogen.HTML (HTML)
import Lunarbox.Data.Editor.Constants (nodeRadius)
import Svg.Attributes as SA
import Svg.Elements as SE

Expand All @@ -20,7 +19,7 @@ overlays radius =
<<< mapWithIndex \index elem ->
SE.g
[ SA.transform
[ SA.Translate 0.0 $ -nodeRadius + (toNumber $ (index + 1) * -20)
[ SA.Translate 0.0 $ -radius + (toNumber $ (index + 1) * -20)
]
]
[ elem ]
18 changes: 9 additions & 9 deletions src/Control/Monad/Dataflow/Interpreter/Interpret.purs
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,6 @@ import Lunarbox.Data.Dataflow.Expression (Expression(..), Literal(..), NativeExp
import Lunarbox.Data.Dataflow.Runtime (RuntimeValue(..))
import Lunarbox.Data.Dataflow.Runtime.TermEnvironment as TermEnvironment
import Lunarbox.Data.Dataflow.Runtime.ValueMap (ValueMap(..))
import Lunarbox.Data.Lens (newtypeIso)

-- Gets a value from the current environment
getVariable :: forall l. Ord l => String -> Interpreter l RuntimeValue
Expand All @@ -27,7 +26,7 @@ getVariable name = do

-- Perform an action in an environment with an extra variable
withTerm :: forall l. Ord l => String -> RuntimeValue -> Interpreter l ~> Interpreter l
withTerm name value = local $ over (_termEnv <<< newtypeIso) $ Map.insert (show name) value
withTerm name value = local $ over _termEnv $ TermEnvironment.insert name value

-- Interpret an expression into a runtimeValue
interpret :: forall l. Ord l => Expression l -> Interpreter l RuntimeValue
Expand All @@ -53,14 +52,15 @@ interpret expression = do
Nothing -> pure Null
Let _ _ name value body -> do
runtimeValue <- interpret value
local (over (_termEnv <<< newtypeIso) $ Map.insert (show name) runtimeValue) $ interpret body
withTerm (show name) runtimeValue $ interpret body
FixPoint _ function -> interpret $ FunctionCall location function $ FixPoint location function
Native _ (NativeExpression _ call) -> pure call
FunctionCall _ argument function -> do
Native _ (NativeExpression _ inner) -> pure inner
FunctionCall _ function argument -> do
runtimeArgument <- interpret argument
runtimeFunction <- interpret function
case runtimeFunction of
Function call -> pure $ call runtimeArgument
_ -> pure Null
runtimeFunction <-
interpret function
pure case runtimeFunction of
Function call -> call runtimeArgument
_ -> Null
tell $ ValueMap $ Map.singleton location value
pure value
3 changes: 2 additions & 1 deletion src/Data/Dataflow/Expression.purs
Original file line number Diff line number Diff line change
Expand Up @@ -39,7 +39,8 @@ derive instance eqVarName :: Eq VarName

derive instance ordVarName :: Ord VarName

derive newtype instance showVarName :: Show VarName
instance showVarName :: Show VarName where
show = unwrap

derive instance newtypeVarName :: Newtype VarName _

Expand Down
4 changes: 3 additions & 1 deletion src/Data/Dataflow/Native/ControlFlow.purs
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,9 @@ typeIf = Forall [ return ] $ TArrow typeBool $ TArrow typeReturn $ TArrow typeRe
evalIf :: RuntimeValue -> RuntimeValue
evalIf (Bool true) = binaryFunction const

evalIf _ = binaryFunction $ flip const
evalIf (Bool false) = binaryFunction $ flip const

evalIf _ = Null

if' :: NativeConfig
if' =
Expand Down
5 changes: 5 additions & 0 deletions src/Data/Dataflow/Runtime/TermEnvironment.purs
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
module Lunarbox.Data.Dataflow.Runtime.TermEnvironment
( TermEnvironment(..)
, lookup
, insert
) where

import Prelude
Expand All @@ -24,3 +25,7 @@ derive newtype instance monoidTermEnvironment :: Monoid TermEnvironment
-- Same as Map.lookup but returns Null in case the value cannot be found
lookup :: String -> TermEnvironment -> RuntimeValue
lookup key = fromMaybe Null <<< Map.lookup key <<< unwrap

-- Wrapper around Map.insert
insert :: String -> RuntimeValue -> TermEnvironment -> TermEnvironment
insert key value (TermEnvironment env) = TermEnvironment $ Map.insert key value env

0 comments on commit 54fc101

Please sign in to comment.