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

Commit

Permalink
feat: something way too simple I spent way too much time on
Browse files Browse the repository at this point in the history
  • Loading branch information
prescientmoon committed Jul 14, 2020
1 parent bc8cd56 commit 08da6f9
Show file tree
Hide file tree
Showing 4 changed files with 42 additions and 86 deletions.
22 changes: 13 additions & 9 deletions src/Data/Dataflow/Native/ControlFlow.purs
Original file line number Diff line number Diff line change
Expand Up @@ -2,14 +2,17 @@ module Lunarbox.Data.Dataflow.Native.ControlFlow
( controlFlowNodes
) where

import Data.Symbol (SProxy(..))
import Lunarbox.Data.Dataflow.Expression (NativeExpression(..))
import Lunarbox.Data.Dataflow.Native.NativeConfig (NativeConfig(..))
import Lunarbox.Data.Dataflow.Runtime (RuntimeValue(..), binaryFunction)
import Lunarbox.Data.Dataflow.Runtime.Class.Describable (DProxy(..), toNativeExpression)
import Lunarbox.Data.Dataflow.Runtime.Class.Runnable (class Runnable)
import Lunarbox.Data.Dataflow.Scheme (Scheme(..))
import Lunarbox.Data.Dataflow.Type (TVarName(..), Type(..), typeBool, typeFunction)
import Lunarbox.Data.Editor.FunctionData (internal)
import Lunarbox.Data.Editor.FunctionName (FunctionName(..))
import Prelude (const, flip, ($))
import Prelude (const, flip, identity, ($))

-- All the native control flow nodes
controlFlowNodes :: Array (NativeConfig)
Expand All @@ -22,18 +25,11 @@ typeIf = Forall [ return ] $ typeFunction typeBool $ typeFunction typeReturn $ t

typeReturn = TVariable true return

evalIf :: RuntimeValue -> RuntimeValue
evalIf (Bool true) = binaryFunction const

evalIf (Bool false) = binaryFunction $ flip const

evalIf _ = Null

if' :: NativeConfig
if' =
NativeConfig
{ name: FunctionName "if"
, expression: (NativeExpression typeIf $ Function evalIf)
, expression: toNativeExpression proxyIf
, functionData:
internal
[ { name: "condition", description: "A boolean which decides what branch to evaluate to" }
Expand All @@ -48,3 +44,11 @@ if' =
, description: "Evaluates to the 'then' argument if the condition is true, else this evaludates to the 'else' argument"
}
}
where
proxyIf :: DProxy (Boolean -> SProxy "a" -> SProxy "a" -> SProxy "a") _
proxyIf = DProxy evalIf

evalIf :: Boolean -> RuntimeValue -> _
evalIf true = const

evalIf false = flip const
50 changes: 4 additions & 46 deletions src/Data/Dataflow/Native/Literal.purs
Original file line number Diff line number Diff line change
Expand Up @@ -5,77 +5,35 @@ module Lunarbox.Data.Dataflow.Native.Literal
, string
) where

import Prelude
import Lunarbox.Data.Dataflow.Expression (NativeExpression(..))
import Lunarbox.Data.Dataflow.Native.NativeConfig (NativeConfig(..))
import Lunarbox.Data.Dataflow.Runtime (RuntimeValue(..))
import Lunarbox.Data.Dataflow.Scheme (Scheme(..))
import Lunarbox.Data.Dataflow.Type (typeBool, typeNumber, typeString)
import Lunarbox.Data.Dataflow.Runtime.Class.Describable (toNativeExpression)
import Lunarbox.Data.Editor.FunctionData (internal)
import Lunarbox.Data.Editor.FunctionName (FunctionName(..))

-- All the native literal nodes
literalNodes :: Array (NativeConfig)
literalNodes = [ boolean, number, string ]

-- booleaUi ::
-- FunctionUi a s m
-- booleaUi { value } { setValue } =
-- SE.foreignObject
-- [ SA.height switchHeight
-- , SA.width switchWidth
-- , SA.x $ switchWidth / -2.0
-- ]
-- [ switch { checked: toBoolean value, round: true } (setValue <<< Bool)
-- ]
boolean :: NativeConfig
boolean =
NativeConfig
{ name: FunctionName "boolean"
, expression: (NativeExpression (Forall [] typeBool) $ Bool false)
, expression: toNativeExpression false
, functionData: internal [] { name: "Boolean", description: "A boolean which has the same value as the visual switch" }
}

-- numberUi :: FunctionUi a s m
-- numberUi { value } { setValue } =
-- SE.foreignObject
-- [ SA.height switchHeight
-- , SA.width inputWIdth
-- , SA.x $ inputWIdth / -2.0
-- ]
-- [ HH.input
-- [ HP.value $ show $ toNumber value
-- , HP.type_ HP.InputNumber
-- , className "number node-input"
-- , onValueInput $ setValue <=< map Number <<< fromString
-- ]
-- ]
number :: NativeConfig
number =
NativeConfig
{ name: FunctionName "number"
, expression: (NativeExpression (Forall [] typeNumber) $ Number 0.0)
, expression: toNativeExpression 0
, functionData: internal [] { name: "Number", description: "A number which has the same value as the input box" }
}

-- stringUI :: FunctionUi a s m
-- stringUI { value } { setValue } =
-- SE.foreignObject
-- [ SA.height switchHeight
-- , SA.width inputWIdth
-- , SA.x $ inputWIdth / -2.0
-- ]
-- [ HH.input
-- [ HP.value $ toString value
-- , HP.type_ HP.InputText
-- , className "string node-input"
-- , onValueInput $ setValue <<< String
-- ]
-- ]
string :: NativeConfig
string =
NativeConfig
{ name: FunctionName "string"
, expression: (NativeExpression (Forall [] typeString) $ String "lunarbox")
, expression: toNativeExpression "lunarbox"
, functionData: internal [] { name: "String", description: "A string which has the same value as the input textbox" }
}
34 changes: 5 additions & 29 deletions src/Data/Dataflow/Native/String.purs
Original file line number Diff line number Diff line change
Expand Up @@ -4,50 +4,29 @@ module Lunarbox.Data.Dataflow.Native.String

import Prelude
import Data.Array as Array
import Data.Int (toNumber)
import Data.String as String
import Lunarbox.Data.Dataflow.Expression (NativeExpression(..))
import Lunarbox.Data.Dataflow.Native.NativeConfig (NativeConfig(..))
import Lunarbox.Data.Dataflow.Runtime (RuntimeValue(..), binaryFunction)
import Lunarbox.Data.Dataflow.Scheme (Scheme(..))
import Lunarbox.Data.Dataflow.Type (typeFunction, typeNumber, typeString)
import Lunarbox.Data.Dataflow.Runtime.Class.Describable (toNativeExpression)
import Lunarbox.Data.Editor.FunctionData (internal)
import Lunarbox.Data.Editor.FunctionName (FunctionName(..))

-- List of all the string native nodes
stringNodes :: Array (NativeConfig)
stringNodes = [ stringLength, concatStrings, reverseString, trimString ]

-- Helper for unary functions operating on strnigs
stringUnary :: (String -> String) -> RuntimeValue
stringUnary unary =
Function case _ of
String string -> String $ unary string
_ -> Null

evalLength :: RuntimeValue -> RuntimeValue
evalLength (String string) = Number $ toNumber $ String.length string

evalLength _ = Null

stringLength :: NativeConfig
stringLength =
NativeConfig
{ name: FunctionName "length"
, expression: NativeExpression (Forall [] $ typeFunction typeString typeNumber) $ Function evalLength
, expression: toNativeExpression String.length
, functionData: internal [ { name: "string", description: "Any string" } ] { name: "length", description: "The number of characters in the given string" }
}

evalConcat :: RuntimeValue -> RuntimeValue -> RuntimeValue
evalConcat (String first) (String second) = String $ first <> second

evalConcat _ _ = Null

concatStrings :: NativeConfig
concatStrings =
NativeConfig
{ name: FunctionName "concat strings"
, expression: NativeExpression (Forall [] $ typeFunction typeString $ typeFunction typeString typeString) $ binaryFunction evalConcat
, expression: toNativeExpression ((<>) :: String -> _)
, functionData:
internal
[ { name: "first string", description: "Any string" }
Expand All @@ -56,22 +35,19 @@ concatStrings =
{ name: "a ++ b", description: "The result of 'glueing' the strings together" }
}

evalReverse :: RuntimeValue
evalReverse = stringUnary $ String.fromCodePointArray <<< Array.reverse <<< String.toCodePointArray

reverseString :: NativeConfig
reverseString =
NativeConfig
{ name: FunctionName "reverse"
, expression: NativeExpression (Forall [] $ typeFunction typeString typeString) evalReverse
, expression: toNativeExpression $ String.fromCodePointArray <<< Array.reverse <<< String.toCodePointArray
, functionData: internal [ { name: "string", description: "Any string" } ] { name: "reversed string", description: "The given string in reverse" }
}

trimString :: NativeConfig
trimString =
NativeConfig
{ name: FunctionName "trim"
, expression: NativeExpression (Forall [] $ typeFunction typeString typeString) $ stringUnary String.trim
, expression: toNativeExpression String.trim
, functionData:
internal [ { name: "string", description: "Any string" } ]
{ name: "trimmed string", description: "The given string but without spaces at the end and at the start"
Expand Down
22 changes: 20 additions & 2 deletions src/Data/Dataflow/Runtime/Class/Describable.purs
Original file line number Diff line number Diff line change
Expand Up @@ -4,11 +4,29 @@ import Prelude
import Data.Array as Array
import Lunarbox.Data.Dataflow.Class.Substituable (ftv)
import Lunarbox.Data.Dataflow.Expression (NativeExpression(..))
import Lunarbox.Data.Dataflow.Runtime.Class.Runnable (class Runnable, toRuntime)
import Lunarbox.Data.Dataflow.Runtime.Class.Typeable (class Typeable, getType)
import Lunarbox.Data.Dataflow.Runtime.Class.Runnable (class Corunnable, class Runnable, fromRuntime, toRuntime)
import Lunarbox.Data.Dataflow.Runtime.Class.Typeable (class Typeable, getType, typeof)
import Lunarbox.Data.Dataflow.Scheme (Scheme(..))
import Lunarbox.Data.Dataflow.Type (Type)
import Type.Proxy (Proxy(..))

-- | Proxy for giving purs extra info about
-- | how we want to transform someting into
-- | lunarboxes type system.
-- | The first argument is a proof all ts are as
newtype DProxy t a
= DProxy a

instance runnableDProxy :: Runnable a => Runnable (DProxy t a) where
toRuntime (DProxy a) = toRuntime a

instance typeableDProxy :: Typeable t => Typeable (DProxy t a) where
typeof _ = typeof (Proxy :: Proxy t)

instance corunnableDProxy :: Corunnable a => Corunnable (DProxy t a) where
fromRuntime a = DProxy <$> fromRuntime a

-- | Typecalss for stuff which is both Typeable and Runnable
class (Runnable a, Typeable a) <= Describable a

instance describableA :: (Runnable a, Typeable a) => Describable a
Expand Down

0 comments on commit 08da6f9

Please sign in to comment.