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

Commit

Permalink
feat: pairs & runtime defaulting system
Browse files Browse the repository at this point in the history
  • Loading branch information
prescientmoon committed Jan 14, 2021
1 parent 7eb149c commit c57802a
Show file tree
Hide file tree
Showing 6 changed files with 115 additions and 88 deletions.
1 change: 1 addition & 0 deletions .gitignore
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,7 @@ yarn-error.log
output
dce-output
dist
generated-docs
public/index.js

.env.*
117 changes: 64 additions & 53 deletions src/Data/Dataflow/Runtime.purs
Original file line number Diff line number Diff line change
Expand Up @@ -12,14 +12,16 @@ module Lunarbox.Data.Dataflow.Runtime
) where

import Prelude

import Control.Monad.Gen (oneOf)
import Data.NonEmpty ((:|))
import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, jsonEmptyObject, (.:), (:=), (~>))
import Data.Either (Either(..))
import Data.Generic.Rep (class Generic)
import Data.Lens (Prism', prism')
import Data.Maybe (Maybe(..))
import Data.NonEmpty ((:|))
import Data.String (joinWith)
import Data.Tuple (Tuple(..))
import Test.QuickCheck (class Arbitrary, class Coarbitrary, arbitrary, coarbitrary)

-- Representations of all possible runtime values
Expand All @@ -28,16 +30,69 @@ data RuntimeValue
| String String
| Bool Boolean
| NArray (Array RuntimeValue)
| Pair RuntimeValue RuntimeValue
| Null
| Function (RuntimeValue -> RuntimeValue)

---------- Helpers
-- helper to ease the creation of binary functions
binaryFunction :: (RuntimeValue -> RuntimeValue -> RuntimeValue) -> RuntimeValue
binaryFunction f = Function $ Function <<< f

-- Same as binaryFunction but with 3 arguments
ternaryFunction :: (RuntimeValue -> RuntimeValue -> RuntimeValue -> RuntimeValue) -> RuntimeValue
ternaryFunction f = Function $ binaryFunction <<< f

-- Turns any runtime value to a boolean
toBoolean :: RuntimeValue -> Boolean
toBoolean value
| value == Bool true = true
| otherwise = false

-- Extracts the array out of a runtime value. Returns [] if the vaule isn't an array
toArray :: RuntimeValue -> Array RuntimeValue
toArray (NArray inner) = inner

toArray _ = []

-- Extract a number from a runtime value, defaulting to 0
toNumber :: RuntimeValue -> Number
toNumber (Number inner) = inner
toNumber _ = 0.0

-- Similar to show except it doesn't put quotes around strings
toString :: RuntimeValue -> String
toString (String inner) = inner
toString other = show other

-- Lenses
_Number :: Prism' RuntimeValue Number
_Number =
prism' Number case _ of
Number c -> Just c
_ -> Nothing

_String :: Prism' RuntimeValue String
_String =
prism' String case _ of
String c -> Just c
_ -> Nothing

_Function :: Prism' RuntimeValue (RuntimeValue -> RuntimeValue)
_Function =
prism' Function case _ of
Function c -> Just c
_ -> Nothing

---------- Typeclass instances
derive instance genericRuntimeValue :: Generic RuntimeValue _

instance encodeJsonRuntimeValue :: EncodeJson RuntimeValue where
encodeJson (Number inner) = "type" := "number" ~> "value" := inner ~> jsonEmptyObject
encodeJson (String inner) = "type" := "string" ~> "value" := inner ~> jsonEmptyObject
encodeJson (Bool inner) = "type" := "boolean" ~> "value" := inner ~> jsonEmptyObject
encodeJson (NArray inner) = "type" := "array" ~> "value" := inner ~> jsonEmptyObject
encodeJson (Pair fst snd) = "type" := "pair" ~> "value" := (Tuple fst snd) ~> jsonEmptyObject
encodeJson _ = "type" := "null" ~> jsonEmptyObject

instance decodeJsonRuntimeValue :: DecodeJson RuntimeValue where
Expand All @@ -56,7 +111,10 @@ instance decodeJsonRuntimeValue :: DecodeJson RuntimeValue where
pure $ Bool value
"array" -> do
value <- obj .: "value"
pure value
pure $ NArray value
"pair" -> do
(Tuple a b) <- obj .: "value"
pure $ Pair a b
"null" -> pure $ Null
_ -> Left $ "Cannot parse runtime value of type " <> type'

Expand All @@ -68,6 +126,7 @@ instance showRuntimeValue :: Show RuntimeValue where
String value -> show value
NArray inner -> "[" <> joinWith ", " (show <$> inner) <> "]"
Function _ -> "Function"
Pair fst snd -> "(" <> show fst <> ", " <> show snd <> ")"

instance coarbitraryRuntimeValue :: Coarbitrary RuntimeValue where
coarbitrary (Number a) = coarbitrary a
Expand All @@ -76,6 +135,7 @@ instance coarbitraryRuntimeValue :: Coarbitrary RuntimeValue where
coarbitrary (NArray arr) = coarbitrary arr
coarbitrary Null = coarbitrary unit
coarbitrary (Function a) = coarbitrary a
coarbitrary (Pair fst snd) = coarbitrary (Tuple fst snd)

instance arbitraryRuntimeValue :: Arbitrary RuntimeValue where
arbitrary =
Expand All @@ -90,6 +150,7 @@ instance eqRuntimeValue :: Eq RuntimeValue where
eq (String s) (String s') = s == s'
eq (Bool v) (Bool v') = v == v'
eq (NArray array) (NArray array') = array == array'
eq (Pair a b) (Pair a' b') = a == a' && b == b'
eq Null Null = true
eq _ _ = false

Expand All @@ -98,55 +159,5 @@ instance ordRuntimeValue :: Ord RuntimeValue where
compare (String s) (String s') = compare s s'
compare (Bool v) (Bool v') = compare v v'
compare (NArray array) (NArray array') = compare array array'
compare (Pair a b) (Pair a' b') = compare (Tuple a b) (Tuple a' b')
compare _ _ = EQ

-- helper to ease the creation of binary functions
binaryFunction :: (RuntimeValue -> RuntimeValue -> RuntimeValue) -> RuntimeValue
binaryFunction f = Function $ Function <<< f

-- Same as binaryFunction but with 3 arguments
ternaryFunction :: (RuntimeValue -> RuntimeValue -> RuntimeValue -> RuntimeValue) -> RuntimeValue
ternaryFunction f = Function $ binaryFunction <<< f

-- Turns any runtime value to a boolean
toBoolean :: RuntimeValue -> Boolean
toBoolean value
| value == Bool true = true
| otherwise = false

-- Extracts the array out of a runtime value. Returns [] if the vaule isn't an array
toArray :: RuntimeValue -> Array RuntimeValue
toArray (NArray inner) = inner

toArray _ = []

-- Extract a number from a runtime value, defaulting to 0
toNumber :: RuntimeValue -> Number
toNumber (Number inner) = inner

toNumber _ = 0.0

-- Similar to show except it doesn't put quotes around strings
toString :: RuntimeValue -> String
toString (String inner) = inner

toString other = show other

-- Lenses
_Number :: Prism' RuntimeValue Number
_Number =
prism' Number case _ of
Number c -> Just c
_ -> Nothing

_String :: Prism' RuntimeValue String
_String =
prism' String case _ of
String c -> Just c
_ -> Nothing

_Function :: Prism' RuntimeValue (RuntimeValue -> RuntimeValue)
_Function =
prism' Function case _ of
Function c -> Just c
_ -> Nothing
30 changes: 24 additions & 6 deletions src/Data/Dataflow/Runtime/Class/Runnable.purs
Original file line number Diff line number Diff line change
@@ -1,14 +1,25 @@
module Lunarbox.Data.Dataflow.Runtime.Class.Runnable where

import Prelude
import Data.Default (class Default, def)

import Data.Int (fromNumber, toNumber)
import Data.Maybe (Maybe(..), fromMaybe, maybe)
import Data.Number (isNaN)
import Data.Traversable (traverse)
import Data.Tuple (Tuple(..))
import Lunarbox.Data.Dataflow.Runtime (RuntimeValue(..))
import Math (floor)

--------- Helper classes
class RuntimeDefault a where
runtimeDefault :: a

instance runtimeDefaultRV :: RuntimeDefault RuntimeValue where
runtimeDefault = Null
else instance runtimeDefaultArrow :: RuntimeDefault a => RuntimeDefault (anything -> a) where
runtimeDefault _ = runtimeDefault

---------- Runnable and Corrunable
class Runnable a where
toRuntime :: a -> RuntimeValue

Expand Down Expand Up @@ -56,8 +67,11 @@ instance runnableArrow :: (Corunnable a, Runnable b) => Runnable (a -> b) where
instance corunnableArrow :: (Runnable a, Corunnable b) => Corunnable (a -> Maybe b) where
fromRuntime (Function f) = Just $ fromRuntime <<< f <<< toRuntime
fromRuntime _ = Nothing
else instance corunnableArrow' :: (Runnable a, Corunnable b, Default b) => Corunnable (a -> b) where
fromRuntime (Function f) = Just $ fromMaybe def <<< fromRuntime <<< f <<< toRuntime
else instance corunnableArrow' :: Runnable a => Corunnable (a -> RuntimeValue) where
fromRuntime (Function f) = Just $ fromMaybe Null <<< fromRuntime <<< f <<< toRuntime
fromRuntime _ = Nothing
else instance corunnableArrow'' :: (Runnable a, Corunnable b, RuntimeDefault b) => Corunnable (a -> b) where
fromRuntime (Function f) = Just $ fromMaybe runtimeDefault <<< fromRuntime <<< f <<< toRuntime
fromRuntime _ = Nothing

instance runnableString :: Runnable String where
Expand All @@ -74,9 +88,13 @@ instance corunnableArray :: Corunnable a => Corunnable (Array a) where
fromRuntime (NArray arr) = traverse fromRuntime arr
fromRuntime _ = Nothing

instance runnableMaybe :: Runnable a => Runnable (Maybe a) where
toRuntime = maybe Null toRuntime
instance runnableTuple :: (Runnable a, Runnable b) => Runnable (Tuple a b) where
toRuntime (Tuple a b) = Pair (toRuntime a) (toRuntime b)

instance corunnableTuple :: (Corunnable a, Corunnable b) => Corunnable (Tuple a b) where
fromRuntime (Pair a b) = Tuple <$> fromRuntime a <*> fromRuntime b
fromRuntime _ = Nothing

-- | Run a non runtime function over a runtime value
overRuntimeValue :: forall a b. Runnable b => Corunnable a => (a -> b) -> RuntimeValue -> RuntimeValue
overRuntimeValue func = toRuntime <<< map func <<< fromRuntime
overRuntimeValue func = maybe Null toRuntime <<< map func <<< fromRuntime
13 changes: 12 additions & 1 deletion src/Data/Dataflow/Runtime/Class/Typeable.purs
Original file line number Diff line number Diff line change
@@ -1,8 +1,10 @@
module Lunarbox.Data.Dataflow.Runtime.Class.Typeable where

import Prelude

import Data.Symbol (class IsSymbol, SProxy(..), reflectSymbol)
import Lunarbox.Data.Dataflow.Type (TVarName(..), Type(..), typeArray, typeBool, typeFunction, typeNumber, typeString)
import Data.Tuple (Tuple)
import Lunarbox.Data.Dataflow.Type (TVarName(..), Type(..), typeArray, typeBool, typeFunction, typeNumber, typePair, typeString)
import Type.Proxy (Proxy(..))

class Typeable (a :: Type) where
Expand All @@ -23,6 +25,15 @@ instance typeableBool :: Typeable Boolean where
instance typeableArray :: Typeable a => Typeable (Array a) where
typeof _ = typeArray (typeof (Proxy :: Proxy a))

instance typePair :: (Typeable a, Typeable b) => Typeable (Tuple a b) where
typeof _ = typePair (typeof _a) (typeof _b)
where
_a :: Proxy a
_a = Proxy

_b :: Proxy b
_b = Proxy

instance typeableSymbol :: IsSymbol sym => Typeable (SProxy sym) where
typeof _ = TVariable true $ TVarName $ reflectSymbol (SProxy :: SProxy sym)

Expand Down
9 changes: 5 additions & 4 deletions src/Data/Dataflow/Type.purs
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,7 @@ module Lunarbox.Data.Dataflow.Type
, typeString
, typeArray
, typeFunction
, typePair
, numberOfInputs
, createTypeVariable
, isArrow
Expand Down Expand Up @@ -57,6 +58,9 @@ typeFunction from to = TConstant "Function" [ from, to ]
typeArray :: Type -> Type
typeArray content = TConstant "Array" [ content ]

typePair :: Type -> Type -> Type
typePair a b = TConstant "Pair" [ a, b ]

-- Create a variable and a type for it
createTypeVariable :: String -> Tuple TVarName Type
createTypeVariable name = Tuple varName $ TVariable true varName
Expand Down Expand Up @@ -109,15 +113,12 @@ instance typeShow :: Show Type where

printType :: Boolean -> Type -> String
printType _ (TVariable _ v) = show v

printType _ (TConstant name []) = name

printType _ (TConstant "Array" [ inner ]) = "[" <> printType false inner <> "]"

printType _ (TConstant "Pair" [ a, b ]) = "(" <> printType false a <> ", " <> printType false b <> ")"
printType p (TConstant "Function" [ from, to ]) = if p then "(" <> result <> ")" else result
where
prefix = printType (isArrow from) from

result = prefix <> spaced arrow <> show to

printType _ (TConstant name vars) = name <> " " <> (joinWith " " $ show <$> vars)
33 changes: 9 additions & 24 deletions yarn.lock
Original file line number Diff line number Diff line change
Expand Up @@ -3267,13 +3267,6 @@ create-hmac@^1.1.0, create-hmac@^1.1.4, create-hmac@^1.1.7:
safe-buffer "^5.0.1"
sha.js "^2.4.8"

cross-env@^7.0.2:
version "7.0.2"
resolved "https://registry.yarnpkg.com/cross-env/-/cross-env-7.0.2.tgz#bd5ed31339a93a3418ac4f3ca9ca3403082ae5f9"
integrity sha512-KZP/bMEOJEDCkDQAyRhu3RL2ZO/SUVrxQVI0G3YEQ+OLbRA3c6zgixe8Mq8a/z7+HKlNEjo8oiLUs8iRijY2Rw==
dependencies:
cross-spawn "^7.0.1"

cross-spawn@^5.0.1:
version "5.1.0"
resolved "https://registry.yarnpkg.com/cross-spawn/-/cross-spawn-5.1.0.tgz#e8bd0efee58fcff6f8f94510a0a554bbfa235449"
Expand All @@ -3294,7 +3287,7 @@ cross-spawn@^6.0.0, cross-spawn@^6.0.4:
shebang-command "^1.2.0"
which "^1.2.9"

cross-spawn@^7.0.0, cross-spawn@^7.0.1:
cross-spawn@^7.0.0:
version "7.0.3"
resolved "https://registry.yarnpkg.com/cross-spawn/-/cross-spawn-7.0.3.tgz#f73a85b9d5d41d045551c177e2882d4ac85728a6"
integrity sha512-iRDPJKUPVEND7dHPO8rkbOnPpyDygcDFtWjpeWNCgy8WP2rXcxXL8TskReQl6OrB2G7+UJrags1q15Fudc7G6w==
Expand Down Expand Up @@ -6892,7 +6885,6 @@ npm@^6.10.3:
cmd-shim "^3.0.3"
columnify "~1.5.4"
config-chain "^1.1.12"
debuglog "*"
detect-indent "~5.0.0"
detect-newline "^2.1.0"
dezalgo "~1.0.3"
Expand All @@ -6907,7 +6899,6 @@ npm@^6.10.3:
has-unicode "~2.0.1"
hosted-git-info "^2.8.8"
iferr "^1.0.2"
imurmurhash "*"
infer-owner "^1.0.4"
inflight "~1.0.6"
inherits "^2.0.4"
Expand All @@ -6926,14 +6917,8 @@ npm@^6.10.3:
libnpx "^10.2.4"
lock-verify "^2.1.0"
lockfile "^1.0.4"
lodash._baseindexof "*"
lodash._baseuniq "~4.6.0"
lodash._bindcallback "*"
lodash._cacheindexof "*"
lodash._createcache "*"
lodash._getnative "*"
lodash.clonedeep "~4.5.0"
lodash.restparam "*"
lodash.union "~4.6.0"
lodash.uniq "~4.5.0"
lodash.without "~4.4.0"
Expand Down Expand Up @@ -8701,10 +8686,10 @@ safe-regex@^1.1.0:
resolved "https://registry.yarnpkg.com/safer-buffer/-/safer-buffer-2.1.2.tgz#44fa161b0187b9549dd84bb91802f9bd8385cd6a"
integrity sha512-YZo3K82SD7Riyi0E1EQPojLz7kpepnSQI9IyPbHHg1XXXevb5dJI7tpyN2ADxGcQbHG7vcyRHk0cbwqcQriUtg==

sass@^1.26.7:
version "1.26.7"
resolved "https://registry.yarnpkg.com/sass/-/sass-1.26.7.tgz#d3c9f3dd9771632bfb60af8746c308da3765166d"
integrity sha512-xgNazdkr6yvgHEfNaOjKtZzhDZmKYMCmoRKMPrTDo7YvjaITIzU2DDYsIUuN/atAg7/JOxPeCQHH7TtCo5Tq2g==
sass@^1.26.11:
version "1.32.4"
resolved "https://registry.yarnpkg.com/sass/-/sass-1.32.4.tgz#308bf29dd7f53d44ae4f06580e9a910ad9aa411e"
integrity sha512-N0BT0PI/t3+gD8jKa83zJJUb7ssfQnRRfqN+GIErokW6U4guBpfYl8qYB+OFLEho+QvnV5ZH1R9qhUC/Z2Ch9w==
dependencies:
chokidar ">=2.0.0 <4.0.0"

Expand Down Expand Up @@ -9785,10 +9770,10 @@ typedarray@^0.0.6:
resolved "https://registry.yarnpkg.com/typedarray/-/typedarray-0.0.6.tgz#867ac74e3864187b1d3d47d996a78ec5c8830777"
integrity sha1-hnrHTjhkGHsdPUfZlqeOxciDB3c=

typescript@^3.9.3:
version "3.9.3"
resolved "https://registry.yarnpkg.com/typescript/-/typescript-3.9.3.tgz#d3ac8883a97c26139e42df5e93eeece33d610b8a"
integrity sha512-D/wqnB2xzNFIcoBG9FG8cXRDjiqSTbG2wd8DMZeQyJlP1vfTkIxH4GKveWaEBYySKIg+USu+E+EDIR47SqnaMQ==
typescript@^3.9.7:
version "3.9.7"
resolved "https://registry.yarnpkg.com/typescript/-/typescript-3.9.7.tgz#98d600a5ebdc38f40cb277522f12dc800e9e25fa"
integrity sha512-BLbiRkiBzAwsjut4x/dsibSTB6yWpwT5qWmC2OfuCg3GgVQCSgMs4vEctYPhsaGtd0AeuuHMkjZ2h2WG8MSzRw==

uglify-js@^3.1.4:
version "3.9.4"
Expand Down

0 comments on commit c57802a

Please sign in to comment.