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

Commit

Permalink
feat: function equality
Browse files Browse the repository at this point in the history
  • Loading branch information
prescientmoon committed Jul 20, 2020
1 parent fc1779b commit 3836013
Show file tree
Hide file tree
Showing 3 changed files with 62 additions and 7 deletions.
8 changes: 7 additions & 1 deletion src/Component/Tutorial.purs
Original file line number Diff line number Diff line change
Expand Up @@ -23,6 +23,7 @@ import Lunarbox.Component.Editor as Editor
import Lunarbox.Component.Error (error)
import Lunarbox.Component.Loading (loading)
import Lunarbox.Component.Modal as Modal
import Lunarbox.Component.Tooltip as Tooltip
import Lunarbox.Component.Utils (className, maybeElement)
import Lunarbox.Config (Config)
import Lunarbox.Data.Editor.State as EditorState
Expand Down Expand Up @@ -165,7 +166,12 @@ component =
[ className "tutorial__hint-button"
, onClick $ const $ Just OpenCurrent
]
[ HH.text "?"
[ Tooltip.tooltip
"See tutorial help"
Tooltip.Left
HH.span
[]
[ HH.text "?" ]
]
]
<> slides
Expand Down
48 changes: 45 additions & 3 deletions src/Data/Dataflow/Runtime.purs
Original file line number Diff line number Diff line change
Expand Up @@ -7,19 +7,24 @@ module Lunarbox.Data.Dataflow.Runtime
, toString
, toArray
, strictEval
, checkEquality
, _Number
, _String
, _Function
) where

import Prelude
import Control.Lazy (class Lazy)
import Control.Lazy (class Lazy, defer)
import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, encodeJson, jsonEmptyObject, (.:), (:=), (~>))
import Data.Either (Either(..))
import Data.Generic.Rep (class Generic)
import Data.Lens (Prism', prism')
import Data.List as List
import Data.Maybe (Maybe(..))
import Data.String (joinWith)
import Effect.Unsafe (unsafePerformEffect)
import Test.QuickCheck (class Arbitrary, class Coarbitrary, Result(..), checkResults, coarbitrary, quickCheckPure, quickCheckPure', randomSeed, (===))
import Test.QuickCheck.Arbitrary (genericArbitrary)

-- Representations of all possible runtime values
data RuntimeValue
Expand Down Expand Up @@ -74,15 +79,34 @@ instance showRuntimeValue :: Show RuntimeValue where
Function _ -> "Function"
RLazy exec -> "Lazy"

-- RLazy exec -> show $ exec unit
-- RLazy exec -> show $ exec unit
instance coarbitraryRuntimeValue :: Coarbitrary RuntimeValue where
coarbitrary (Number a) = coarbitrary a
coarbitrary (String a) = coarbitrary a
coarbitrary (Bool a) = coarbitrary a
coarbitrary (NArray arr) = coarbitrary arr
coarbitrary Null = coarbitrary unit
coarbitrary (RLazy a) = coarbitrary $ a unit
coarbitrary (Function a) = coarbitrary a

instance arbitraryRuntimeValue :: Arbitrary RuntimeValue where
arbitrary = defer \_ -> genericArbitrary

instance eqRuntimeValue :: Eq RuntimeValue where
eq (Number n) (Number n') = n == n'
eq (String s) (String s') = s == s'
eq (Bool v) (Bool v') = v == v'
eq (NArray array) (NArray array') = array == array'
eq Null Null = true
eq (RLazy a) (RLazy b) = a unit == b unit
eq (Function a) (Function b) = not $ List.any go (quickCheckPure seed 50 prop)
where
prop val = a val === b val

go (Failed _) = true

go Success = false

seed = unsafePerformEffect randomSeed
eq _ _ = false

instance ordRuntimeValue :: Ord RuntimeValue where
Expand Down Expand Up @@ -131,6 +155,24 @@ strictEval (RLazy exec) = strictEval $ exec unit

strictEval a = a

-- | Basically the same as == but works for functions as well
checkEquality :: RuntimeValue -> RuntimeValue -> { messages :: List.List String, result :: Boolean }
checkEquality (Function a) (Function b) =
{ result: List.null checkResult.failures
, messages: _.message <$> checkResult.failures
}
where
checkResult = checkResults $ quickCheckPure' seed 100 prop

prop val = a val === b val

seed = unsafePerformEffect randomSeed

checkEquality a b =
{ result: a == b
, messages: List.Nil
}

-- Lenses
_Number :: Prism' RuntimeValue Number
_Number =
Expand Down
13 changes: 10 additions & 3 deletions src/Data/Dataflow/Runtime/Class/Runnable.purs
Original file line number Diff line number Diff line change
@@ -1,11 +1,13 @@
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(..), maybe)
import Data.Maybe (Maybe(..), fromMaybe, maybe)
import Data.Number (isNaN)
import Data.Traversable (traverse)
import Lunarbox.Data.Dataflow.Runtime (RuntimeValue(..))
import Math (floor)

class Runnable a where
toRuntime :: a -> RuntimeValue
Expand All @@ -23,7 +25,9 @@ instance coRunnableInt :: Corunnable Int where
instance runnableNumber :: Runnable Number where
toRuntime a
| isNaN a = Null
| otherwise = Number a
| otherwise = Number $ floorAt 1000.0 a
where
floorAt at x = floor (x * at) / at

instance corunnableNumber :: Corunnable Number where
fromRuntime (Number inner) = Just inner
Expand All @@ -49,9 +53,12 @@ instance runnableArrow :: (Corunnable a, Runnable b) => Runnable (a -> b) where
Just inner -> toRuntime $ f inner
Nothing -> Null

instance coRunnableArrow :: (Runnable a, Corunnable b) => Corunnable (a -> Maybe 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
fromRuntime _ = Nothing

instance runnableString :: Runnable String where
toRuntime = String
Expand Down

0 comments on commit 3836013

Please sign in to comment.