Commit 1699fa41 authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski Committed by James Laver

Purescript bump to 0.13.5 and fixes to warnings

parent 72a5e8ad
......@@ -109,10 +109,10 @@ let additions =
-}
let mkPackage =
https://raw.githubusercontent.com/purescript/package-sets/psc-0.13.0-20190614/src/mkPackage.dhall sha256:0b197efa1d397ace6eb46b243ff2d73a3da5638d8d0ac8473e8e4a8fc528cf57
https://raw.githubusercontent.com/purescript/package-sets/psc-0.13.5-20191127/src/mkPackage.dhall sha256:0b197efa1d397ace6eb46b243ff2d73a3da5638d8d0ac8473e8e4a8fc528cf57
let upstream =
https://raw.githubusercontent.com/purescript/package-sets/psc-0.12.5-20190419/src/packages.dhall sha256:aee7258b1bf1b81ed5e22d1247e812a80ec2e879758562f33334512ed086c5ae
https://raw.githubusercontent.com/purescript/package-sets/psc-0.13.5-20191127/src/packages.dhall sha256:654e8427ff1f9830542f491623cd5d89b1648774a765520554f98f41d3d1b3b3
let overrides =
{ contravariant =
......@@ -120,24 +120,6 @@ let overrides =
[ "newtype", "either", "prelude", "tuples" ]
"https://github.com/purescript/purescript-contravariant"
"v4.0.1"
-- spec =
-- mkPackage
-- [ "aff"
-- , "ansi"
-- , "avar"
-- , "console"
-- , "exceptions"
-- , "foldable-traversable"
-- , "fork"
-- , "generics-rep"
-- , "now"
-- , "pipes"
-- , "prelude"
-- , "strings"
-- , "transformers"
-- ]
-- "https://github.com/purescript-spec/purescript-spec.git"
-- "v3.1.0"
, ordered-collections =
mkPackage
[ "arrays"
......@@ -155,7 +137,7 @@ let overrides =
]
"https://github.com/purescript/purescript-ordered-collections.git"
"v1.6.1"
}
}
let additions =
{ dom-simple =
......
module Reactix.DOM.HTML where
import Prelude ((<<<), ($), (<>), map, identity)
import Prelude (identity, ($), (<<<), (<>))
import Data.Maybe (maybe)
import Data.Foldable (foldl)
import Data.String (toUpper)
import Effect.Uncurried (mkEffectFn1)
import FFI.Simple.Objects ((.?), (.=), (!-), (..), keys)
import Reactix.React (Element, createDOMElement)
......@@ -11,7 +10,7 @@ import Reactix.Utils (ucFirst)
import Unsafe.Coerce (unsafeCoerce)
createDOM :: forall props. String -> Record props -> Array Element -> Element
createDOM e p = createDOMElement e (magicProps p)
createDOM e props = createDOMElement e (magicProps props)
magicProps :: forall props. props -> props
magicProps = xformAriaProps <<< xformDataProps <<< xformEventProps
......@@ -20,8 +19,8 @@ magicProps = xformAriaProps <<< xformDataProps <<< xformEventProps
xformDataProps = magicPrefixProp "data" "data-"
magicPrefixProp :: forall props. String -> String -> props -> props
magicPrefixProp prop pre props = maybe props help (props .? prop)
where help val = prefixCopyAll pre props val !- prop
magicPrefixProp prop pre' props = maybe props help (props .? prop)
where help val = prefixCopyAll pre' props val !- prop
xformEventProps :: forall props. props -> props
xformEventProps props = maybe props help (props .? "on")
......@@ -30,14 +29,14 @@ xformEventProps props = maybe props help (props .? "on")
eventPropName other = "on" <> ucFirst other
prefixCopyAll :: forall p q. String -> p -> q -> p
prefixCopyAll pre = mapCopyAll (pre <> _) identity
prefixCopyAll pre' = mapCopyAll (pre' <> _) identity
mapCopyAll :: forall a b p q. (String -> String) -> (a -> b) -> p -> q -> p
mapCopyAll xf yf dest src = foldl f dest (keys src)
where f dest k = (dest .= xf k) (yf $ src .. k)
where f dest' k = (dest' .= xf k) (yf $ src .. k)
createLeafDOM :: forall props. String -> Record props -> Element
createLeafDOM e p = createDOM e p []
createLeafDOM e props = createDOM e props []
-- A factory function for a DOM element with no children
type LeafFactory = forall props. Record props -> Element
......
......@@ -31,19 +31,14 @@ module Reactix.Hooks
)
where
import Prelude hiding (div)
import Data.Function.Uncurried (Fn2, mkFn2, runFn2)
import Data.Tuple (Tuple(..))
import Prelude (Unit, const, identity, pure, unit, ($), (*>), (<<<))
import Data.Function.Uncurried (mkFn2)
import Data.Tuple (Tuple)
import Effect (Effect)
import Effect.Uncurried
( EffectFn1, runEffectFn1, mkEffectFn1
, EffectFn2, runEffectFn2, EffectFn3, runEffectFn3
, EffectFn4, runEffectFn4, EffectFn5, runEffectFn5, EffectFn6, runEffectFn6 )
import FFI.Simple ((...), (..), delay, args2, args3, args4, args5, setProperty)
import FFI.Simple (args2, args3, args4, args5, delay, (...))
import FFI.Simple.PseudoArray as Array
import DOM.Simple.Console
import Reactix.Utils (tuple, currySecond, hook, splay1, splay2, splay3, splay4, splay5)
import Reactix.React (Context, Ref, Hooks, react, unsafeHooksEffect)
import Reactix.React (Context, Hooks, Ref, react)
--- useState
......
......@@ -24,18 +24,13 @@ module Reactix.React
import Prelude
import Data.Function.Uncurried (mkFn2)
import Data.Maybe (Maybe, maybe)
import Data.Maybe (Maybe)
import Data.Nullable (Nullable, toMaybe)
import Effect (Effect)
import Effect.Class (class MonadEffect, liftEffect)
import Effect.Uncurried (EffectFn1, mkEffectFn1, EffectFn2)
import Unsafe.Coerce (unsafeCoerce)
import Prim.Row (class Lacks)
import Effect.Uncurried (EffectFn1, mkEffectFn1)
import DOM.Simple as DOM
import FFI.Simple.PseudoArray as PA
import FFI.Simple
( (..), (...), (.=), args2, args3, delay, setProperty, defineProperty )
import FFI.Simple.Undef (nullUndef)
import FFI.Simple (args2, defineProperty, delay, (..), (...), (.=))
foreign import data React :: Type
foreign import data ReactDOM :: Type
......
......@@ -3,12 +3,8 @@ module Reactix.SyntheticEvent where
import Prelude
import DOM.Simple as DOM
import DOM.Simple.Event as E
import DOM.Simple.Event
( class IsEvent, class IsMouseEvent, class HasModifierKeys
, KeyboardEvent, MouseEvent, MouseButtonEvent, TouchEvent )
import DOM.Simple.Event (class HasModifierKeys, class IsEvent, class IsMouseEvent, KeyboardEvent, MouseButtonEvent)
import Effect ( Effect )
import Effect.Uncurried ( EffectFn1, runEffectFn1 )
import FFI.Simple ( (..), (...), delay )
foreign import data SyntheticEvent :: Type -> Type
......@@ -34,7 +30,7 @@ timestamp e = e .. "timeStamp"
type' :: forall e. IsEvent e => SyntheticEvent e -> String
type' e = e .. "type"
target :: forall e t. IsEvent e => SyntheticEvent e -> DOM.Element
target :: forall e. IsEvent e => SyntheticEvent e -> DOM.Element
target e = e .. "target"
currentTarget :: forall e. IsEvent e => SyntheticEvent e -> DOM.Element
......
......@@ -6,14 +6,12 @@ module Reactix.Test
, cleanup
) where
import Prelude
import Prelude (Unit, pure, unit, ($))
import Effect ( Effect )
import Effect.Uncurried ( EffectFn1, runEffectFn1, EffectFn2, runEffectFn2 )
import Data.Function.Uncurried ( Fn2, runFn2 )
import Effect.Uncurried (runEffectFn1)
import DOM.Simple as DOM
import Reactix.React ( react, Element )
import Reactix.React (Element)
import FFI.Simple ( (..), (...), delay )
import DOM.Simple.Console
foreign import data TestUtils :: Type
......
......@@ -3,33 +3,23 @@ module Reactix.React.Spec where
import Prelude
import Data.Array as A
import Data.Array ( (!!) )
import Data.EuclideanRing (mod)
import Data.Maybe ( Maybe(..) )
import Data.Nullable (null)
import Data.Traversable ( traverse, traverse_, sequence_ )
import Data.Tuple ( Tuple(..) )
import Data.Traversable (sequence_, traverse_)
import Data.Tuple.Nested ( (/\) )
import Data.Unfoldable (fromMaybe)
import Effect ( Effect )
import Effect.Aff ( Aff, launchAff )
import Effect.Aff (Aff)
import Effect.Class ( liftEffect )
import Effect.Ref as Ref
import Effect.Uncurried ( EffectFn1, mkEffectFn1, runEffectFn1 )
-- import Effect.Aff (launchAff_)
import Test.Spec ( Spec, describe, it )
import Test.Spec.Assertions ( shouldEqual )
-- import Test.Spec.QuickCheck (quickCheck')
import DOM.Simple as DOM
import DOM.Simple.Document as Document
import DOM.Simple.Element as Element
import DOM.Simple.Node as Node
import DOM.Simple.Event as Event
import DOM.Simple.Types (Element)
import FFI.Simple (delay)
import Reactix as R
import Reactix.Test as RT
import Reactix.DOM.HTML ( button, div, i, text )
import DOM.Simple.Console
import Reactix.DOM.HTML as H
staticTest :: Spec Unit
staticTest =
......@@ -59,9 +49,9 @@ staticTest =
(Element.name <$> children) `shouldEqual` ["I", "I"]
(Element.innerHTML <$> children) `shouldEqual` ["hello","world"]
where
simple = i {} [ text "hello world" ]
magic = div {aria: {label: "example"}, "data": {sample: "example"}} []
frag = i {} [ text "hello" ] <> i {} [ text "world" ]
simple = H.i {} [ H.text "hello world" ]
magic = H.div {aria: {label: "example"}, "data": {sample: "example"}} []
frag = H.i {} [ H.text "hello" ] <> H.i {} [ H.text "world" ]
getAttr :: String -> Element -> Maybe String
getAttr = flip Element.attr
......@@ -73,9 +63,9 @@ counterCpt = R.hooksComponent "Counter" cpt
where
cpt {count} _ = do
y /\ setY <- R.useState' count
pure $ div { className: "counter" }
[ button { type: "button", on: { click: \_ -> setY (_ + 1) } } [ text "++" ]
, div {} [ text (show y) ] ]
pure $ H.div { className: "counter" }
[ H.button { type: "button", on: { click: \_ -> setY (_ + 1) } } [ H.text "++" ]
, H.div {} [ H.text (show y) ] ]
counterTest :: Spec Unit
counterTest =
......@@ -114,10 +104,10 @@ bicounterCpt = R.hooksComponent "Bicounter" cpt
where
cpt {count} _ = do
y /\ reduceY <- R.useReducer' reduce count
pure $ div { className: "counter" }
[ button { type: "button", on: { click: \_ -> reduceY Inc } } [ text "++" ]
, button { type: "button", on: { click: \_ -> reduceY Dec } } [ text "--" ]
, div {} [ text (show y) ] ]
pure $ H.div { className: "counter" }
[ H.button { type: "button", on: { click: \_ -> reduceY Inc } } [ H.text "++" ]
, H.button { type: "button", on: { click: \_ -> reduceY Dec } } [ H.text "--" ]
, H.div {} [ H.text (show y) ] ]
reduce count Inc = count + 1
reduce count Dec = count - 1
......@@ -171,7 +161,7 @@ effectorCpt = R.hooksComponent "Effector" cpt
R.useEffect $ do
Ref.write Initialised stateRef
pure $ Ref.write Done stateRef
pure $ div {} []
pure $ H.div {} []
-- TODO: test it's firing at the right time
effectorTest :: Spec Unit
......@@ -199,7 +189,7 @@ layoutEffectorCpt = R.hooksComponent "LayoutEffector" cpt
R.useLayoutEffect $ do
Ref.write Initialised stateRef
pure $ delay unit $ \_ -> Ref.write Done stateRef
pure $ div {} []
pure $ H.div {} []
-- TODO: test it's firing at the right time
layoutEffectorTest :: Spec Unit
......@@ -236,7 +226,7 @@ themedCpt = R.hooksComponent "Themed" cpt
where
cpt {theme} _ = do
theme' <- R.useContext theme
pure $ div {} [ text (showTheme theme') ]
pure $ H.div {} [ H.text (showTheme theme') ]
themeChooserCpt :: R.Component ThemeChooserProps
themeChooserCpt = R.hooksComponent "ThemeChooser" cpt
......@@ -246,16 +236,16 @@ themeChooserCpt = R.hooksComponent "ThemeChooser" cpt
ref <- R.useRef $ R.createContext Nothing
let context = R.readRef ref
pure $
div {}
[ button
H.div {}
[ H.button
{ type: "button", on: {click: \_ -> setTheme (const Nothing) } }
[ text "None" ]
, button
[ H.text "None" ]
, H.button
{ type: "button", on: {click: \_ -> setTheme (const $ Just Dark) } }
[ text "Dark" ]
, button
[ H.text "Dark" ]
, H.button
{ type: "button", on: {click: \_ -> setTheme (const $ Just Light) } }
[ text "Light" ]
[ H.text "Light" ]
, R.provideContext context theme [ R.createElement themedCpt { theme: context } [] ] ]
themeChooserTest :: Spec Unit
......
This diff is collapsed.
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment