diff --git a/README.md b/README.md index ad16e50..2794bba 100644 --- a/README.md +++ b/README.md @@ -15,7 +15,7 @@ If we prefer this API over the existing react-basic API, we may eventually repla ## Example ```purs -mkCounter :: CreateComponent {} +mkCounter :: Effect (ReactComponent {}) mkCounter = do component "Counter" \props -> React.do counter /\ setCounter <- useState 0 diff --git a/examples/aff/src/AffEx.purs b/examples/aff/src/AffEx.purs index 445ad28..fc95b68 100644 --- a/examples/aff/src/AffEx.purs +++ b/examples/aff/src/AffEx.purs @@ -3,14 +3,15 @@ module AffEx where import Prelude import Data.Either (either) import Data.Maybe (Maybe(..), maybe) +import Effect (Effect) import Effect.Aff (Aff, Milliseconds(..), delay, error, message, throwError) import React.Basic.DOM as R import React.Basic.Events (handler_) -import React.Basic.Hooks (type (/\), CreateComponent, Hook, JSX, component, element, fragment, useState, (/\)) +import React.Basic.Hooks (type (/\), ReactComponent, Hook, JSX, component, element, fragment, useState, (/\)) import React.Basic.Hooks as React import React.Basic.Hooks.Aff (useAff) -mkAffEx :: CreateComponent {} +mkAffEx :: Effect (ReactComponent {}) mkAffEx = do -- A component for fetching and rendering a Cat entity. catDetails <- mkCatDetails @@ -68,7 +69,7 @@ mkAffEx = do -- Hooks can't be used conditionally but components can! -- Not needing to deal with a `Maybe` key simplifies this -- compoennt a bit. - mkCatDetails :: CreateComponent { catKey :: Key Cat } + mkCatDetails :: Effect (ReactComponent { catKey :: Key Cat }) mkCatDetails = do component "CatDetails" \{ catKey } -> React.do cat <- useAff catKey $ fetch catKey diff --git a/examples/component/src/Container.purs b/examples/component/src/Container.purs index fbcbb88..4a82c5d 100644 --- a/examples/component/src/Container.purs +++ b/examples/component/src/Container.purs @@ -1,19 +1,19 @@ module Container where import Prelude - -import React.Basic.Hooks(CreateComponent, component, element) +import Effect (Effect) import React.Basic.DOM as R +import React.Basic.Hooks (ReactComponent, component, element) import ToggleButton (mkToggleButton) -mkToggleButtonContainer :: CreateComponent {} +mkToggleButtonContainer :: Effect (ReactComponent {}) mkToggleButtonContainer = do toggleButton <- mkToggleButton - component "Container" \_ -> - pure $ R.div - { children: - [ element toggleButton { label: "A" } - , element toggleButton { label: "B" } - ] - } + pure + $ R.div + { children: + [ element toggleButton { label: "A" } + , element toggleButton { label: "B" } + ] + } diff --git a/examples/component/src/ToggleButton.purs b/examples/component/src/ToggleButton.purs index 616c633..8e4f119 100644 --- a/examples/component/src/ToggleButton.purs +++ b/examples/component/src/ToggleButton.purs @@ -1,26 +1,25 @@ module ToggleButton where import Prelude - +import Effect (Effect) import Effect.Console (log) import React.Basic.DOM as R import React.Basic.Events (handler_) -import React.Basic.Hooks (CreateComponent, component, useEffect, useState, (/\)) +import React.Basic.Hooks (ReactComponent, component, useEffect, useState, (/\)) import React.Basic.Hooks as React -mkToggleButton :: CreateComponent { label :: String } +mkToggleButton :: Effect (ReactComponent { label :: String }) mkToggleButton = do component "ToggleButton" \{ label } -> React.do on /\ setOn <- useState false - useEffect on do log $ "State: " <> if on then "On" else "Off" pure (pure unit) - - pure $ R.button - { onClick: handler_ $ setOn not - , children: - [ R.text label - , R.text if on then " On" else " Off" - ] - } + pure + $ R.button + { onClick: handler_ $ setOn not + , children: + [ R.text label + , R.text if on then " On" else " Off" + ] + } diff --git a/examples/context/src/Context.purs b/examples/context/src/Context.purs index 954afc5..cbfd448 100644 --- a/examples/context/src/Context.purs +++ b/examples/context/src/Context.purs @@ -4,10 +4,10 @@ import Prelude import Effect (Effect) import React.Basic.DOM as R import React.Basic.Events (handler_) -import React.Basic.Hooks (type (/\), CreateComponent, JSX, ReactContext, component, createContext, element, provider, useContext, useState, (/\)) +import React.Basic.Hooks (type (/\), ReactComponent, JSX, ReactContext, component, createContext, element, provider, useContext, useState, (/\)) import React.Basic.Hooks as React -mkContext :: CreateComponent {} +mkContext :: Effect (ReactComponent {}) mkContext = do counterContext <- createContext (0 /\ pure unit) store <- mkStore counterContext @@ -24,7 +24,7 @@ mkContext = do mkStore :: ReactContext (Int /\ (Effect Unit)) -> - CreateComponent { children :: Array JSX } + Effect (ReactComponent { children :: Array JSX }) mkStore context = do component "Store" \{ children } -> React.do counter /\ setCounter <- useState 0 @@ -37,7 +37,7 @@ mkStore context = do mkCounter :: ReactContext (Int /\ (Effect Unit)) -> - CreateComponent {} + Effect (ReactComponent {}) mkCounter counterContext = do component "Counter" \props -> React.do counter /\ increment <- useContext counterContext diff --git a/examples/controlled-input/src/ControlledInput.purs b/examples/controlled-input/src/ControlledInput.purs index c4adf4b..53ddec7 100644 --- a/examples/controlled-input/src/ControlledInput.purs +++ b/examples/controlled-input/src/ControlledInput.purs @@ -1,50 +1,50 @@ module ControlledInput where import Prelude - import Data.Maybe (Maybe(..), fromMaybe, maybe) +import Effect (Effect) import React.Basic.DOM as R import React.Basic.DOM.Events (preventDefault, stopPropagation, targetValue, timeStamp) import React.Basic.Events (EventHandler, handler, merge) -import React.Basic.Hooks (CreateComponent, UseState, Hook, component, fragment, useState, (/\)) +import React.Basic.Hooks (ReactComponent, UseState, Hook, component, fragment, useState, (/\)) import React.Basic.Hooks as React -mkControlledInput :: CreateComponent {} +mkControlledInput :: Effect (ReactComponent {}) mkControlledInput = do component "ControlledInput" \props -> React.do firstName <- useInput "hello" lastName <- useInput "world" - - pure $ R.form_ - [ renderInput firstName - , renderInput lastName - ] + pure + $ R.form_ + [ renderInput firstName + , renderInput lastName + ] where - renderInput input = - fragment - [ R.input { onChange: input.onChange, value: input.value } - , R.p_ [ R.text ("Current value = " <> show input.value) ] - , R.p_ [ R.text ("Changed at = " <> maybe "never" show input.lastChanged) ] - ] + renderInput input = + fragment + [ R.input { onChange: input.onChange, value: input.value } + , R.p_ [ R.text ("Current value = " <> show input.value) ] + , R.p_ [ R.text ("Changed at = " <> maybe "never" show input.lastChanged) ] + ] -useInput - :: String - -> Hook - (UseState { value :: String, lastChanged :: Maybe Number }) - { onChange :: EventHandler - , value :: String - , lastChanged :: Maybe Number - } +useInput :: + String -> + Hook + (UseState { value :: String, lastChanged :: Maybe Number }) + { onChange :: EventHandler + , value :: String + , lastChanged :: Maybe Number + } useInput initialValue = React.do { value, lastChanged } /\ replaceState <- useState { value: initialValue, lastChanged: Nothing } pure - { onChange: handler - (preventDefault >>> stopPropagation >>> merge { targetValue, timeStamp }) - \{ timeStamp, targetValue } -> do - replaceState \_ -> - { value: fromMaybe "" targetValue - , lastChanged: Just timeStamp - } + { onChange: + handler + (preventDefault >>> stopPropagation >>> merge { targetValue, timeStamp }) \{ timeStamp, targetValue } -> do + replaceState \_ -> + { value: fromMaybe "" targetValue + , lastChanged: Just timeStamp + } , value , lastChanged } diff --git a/examples/counter/src/Counter.purs b/examples/counter/src/Counter.purs index 80439a0..bbed475 100644 --- a/examples/counter/src/Counter.purs +++ b/examples/counter/src/Counter.purs @@ -1,27 +1,25 @@ module Counter where import Prelude - import Effect (Effect) import React.Basic.DOM as R import React.Basic.Events (handler_) -import React.Basic.Hooks (CreateComponent, component, fragment, useEffect, useState, (/\)) +import React.Basic.Hooks (ReactComponent, component, fragment, useEffect, useState, (/\)) import React.Basic.Hooks as React -mkCounter :: CreateComponent {} +mkCounter :: Effect (ReactComponent {}) mkCounter = do component "Counter" \props -> React.do counter /\ setCounter <- useState 0 - useEffect counter do setDocumentTitle $ "Count: " <> show counter pure mempty - - pure $ fragment - [ R.button - { onClick: handler_ $ setCounter (_ + 1) - , children: [ R.text $ "Increment: " <> show counter ] - } - ] + pure + $ fragment + [ R.button + { onClick: handler_ $ setCounter (_ + 1) + , children: [ R.text $ "Increment: " <> show counter ] + } + ] foreign import setDocumentTitle :: String -> Effect Unit diff --git a/examples/memo-callback/src/MemoCallback.purs b/examples/memo-callback/src/MemoCallback.purs index b6ac555..a8f6667 100644 --- a/examples/memo-callback/src/MemoCallback.purs +++ b/examples/memo-callback/src/MemoCallback.purs @@ -1,27 +1,27 @@ module MemoCallback where import Prelude - +import Effect (Effect) import Effect.Console (log) import React.Basic.DOM as R import React.Basic.Events (handler_) -import React.Basic.Hooks (CreateComponent, UnsafeReference(..), component, fragment, useCallback, useEffect, useState, (/\)) +import React.Basic.Hooks (ReactComponent, UnsafeReference(..), component, fragment, useCallback, useEffect, useState, (/\)) import React.Basic.Hooks as React -mkMemoCallback :: CreateComponent {} +mkMemoCallback :: Effect (ReactComponent {}) mkMemoCallback = do component "MemoCallback" \props -> React.do counter /\ setCounter <- useState 0 - increment <- useCallback (UnsafeReference setCounter) $ - setCounter (_ + 1) - + increment <- + useCallback (UnsafeReference setCounter) + $ setCounter (_ + 1) useEffect (UnsafeReference increment) do log "increment updated" pure mempty - - pure $ fragment - [ R.button - { onClick: handler_ increment - , children: [ R.text $ "Increment: " <> show counter ] - } - ] + pure + $ fragment + [ R.button + { onClick: handler_ increment + , children: [ R.text $ "Increment: " <> show counter ] + } + ] diff --git a/examples/reducer/src/Reducer.purs b/examples/reducer/src/Reducer.purs index bd67b8c..ccc7738 100644 --- a/examples/reducer/src/Reducer.purs +++ b/examples/reducer/src/Reducer.purs @@ -1,35 +1,34 @@ module Reducer where import Prelude - +import Effect (Effect) import React.Basic.DOM as R import React.Basic.Events (handler_) -import React.Basic.Hooks (CreateComponent, component, fragment, useReducer, (/\)) +import React.Basic.Hooks (ReactComponent, component, fragment, useReducer, (/\)) import React.Basic.Hooks as React data Action = Increment | Decrement -mkReducer :: CreateComponent {} +mkReducer :: Effect (ReactComponent {}) mkReducer = do component "Reducer" \props -> React.do - state /\ dispatch <- useReducer { counter: 0 } \state -> case _ of Increment -> state { counter = state.counter + 1 } Decrement -> state { counter = state.counter - 1 } - - pure $ fragment - [ R.button - { onClick: handler_ $ dispatch Decrement - , children: [ R.text $ "Decrement" ] - } - , R.button - { onClick: handler_ $ dispatch Increment - , children: [ R.text $ "Increment" ] - } - , R.div_ - [ R.text $ show state.counter + pure + $ fragment + [ R.button + { onClick: handler_ $ dispatch Decrement + , children: [ R.text $ "Decrement" ] + } + , R.button + { onClick: handler_ $ dispatch Increment + , children: [ R.text $ "Increment" ] + } + , R.div_ + [ R.text $ show state.counter + ] ] - ] diff --git a/examples/refs/src/Refs.purs b/examples/refs/src/Refs.purs index 77abcce..d138acf 100644 --- a/examples/refs/src/Refs.purs +++ b/examples/refs/src/Refs.purs @@ -1,13 +1,14 @@ module Refs where import Prelude - import Data.Int (round) import Data.Maybe (Maybe(..)) +import Data.Newtype (class Newtype) import Data.Nullable (Nullable, null) +import Effect (Effect) import Math (pow, sqrt) import React.Basic.DOM as R -import React.Basic.Hooks (CreateComponent, Ref, UseEffect, UseRef, UseState, Hook, type (/\), component, element, fragment, readRefMaybe, useEffect, useRef, useState, (/\)) +import React.Basic.Hooks (type (/\), Hook, ReactComponent, Ref, UseEffect, UseRef, UseState, component, element, fragment, coerceHook, readRefMaybe, useEffect, useRef, useState, (/\)) import React.Basic.Hooks as React import Unsafe.Coerce (unsafeCoerce) import Web.DOM (Node) @@ -18,68 +19,78 @@ import Web.HTML.HTMLElement (getBoundingClientRect) import Web.HTML.HTMLElement as HTMLElement import Web.HTML.Window as Window -mkRefs :: CreateComponent {} +mkRefs :: Effect (ReactComponent {}) mkRefs = do component "Refs" \props -> React.do - mouseDistance1 /\ buttonRef1 <- useNodeDistanceFromMouse mouseDistance2 /\ buttonRef2 <- useNodeDistanceFromMouse mouseDistance3 /\ buttonRef3 <- useNodeDistanceFromMouse + pure + $ fragment + [ element (R.unsafeCreateDOMComponent "button") + { ref: buttonRef1 + , children: [ R.text $ show mouseDistance1 <> "px" ] + , style: R.css { width: "100px", position: "absolute", top: "20px", left: "200px" } + } + , element (R.unsafeCreateDOMComponent "button") + { ref: buttonRef2 + , children: [ R.text $ show mouseDistance2 <> "px" ] + , style: R.css { width: "100px", position: "absolute", top: "60px", left: "40px" } + } + , element (R.unsafeCreateDOMComponent "button") + { ref: buttonRef3 + , children: [ R.text $ show mouseDistance3 <> "px" ] + , style: R.css { width: "100px", position: "absolute", top: "120px", left: "90px" } + } + ] - pure $ fragment - [ element (R.unsafeCreateDOMComponent "button") - { ref: buttonRef1 - , children: [ R.text $ show mouseDistance1 <> "px" ] - , style: R.css { width: "100px", position: "absolute", top: "20px", left: "200px" } - } - , element (R.unsafeCreateDOMComponent "button") - { ref: buttonRef2 - , children: [ R.text $ show mouseDistance2 <> "px" ] - , style: R.css { width: "100px", position: "absolute", top: "60px", left: "40px" } - } - , element (R.unsafeCreateDOMComponent "button") - { ref: buttonRef3 - , children: [ R.text $ show mouseDistance3 <> "px" ] - , style: R.css { width: "100px", position: "absolute", top: "120px", left: "90px" } - } - ] +newtype UseNodeDistance hooks + = UseNodeDistance (UseEffect Unit (UseState Int (UseRef (Nullable Node) hooks))) -type UseNodeDistance hooks = UseEffect Unit (UseState Int (UseRef (Nullable Node) hooks)) +derive instance ntUseNodeDistance :: Newtype (UseNodeDistance hooks) _ useNodeDistanceFromMouse :: Hook UseNodeDistance (Int /\ (Ref (Nullable Node))) -useNodeDistanceFromMouse = React.do - elementRef <- useRef null - mouseDistance /\ setMouseDistance <- useState 0 +useNodeDistanceFromMouse = + coerceHook React.do + elementRef <- useRef null + mouseDistance /\ setMouseDistance <- useState 0 + useEffect unit do + maybeElement <- map (HTMLElement.fromNode =<< _) (readRefMaybe elementRef) + case maybeElement of + Nothing -> pure (pure unit) + Just element -> do + mouseMoveListener <- + eventListener \e -> do + { top, bottom, left, right } <- getBoundingClientRect element + let + mouseX = (unsafeCoerce e).clientX - useEffect unit do - maybeElement <- map (HTMLElement.fromNode =<< _) (readRefMaybe elementRef) - case maybeElement of - Nothing -> pure (pure unit) - Just element -> do - mouseMoveListener <- eventListener \e -> do - { top, bottom, left, right } <- getBoundingClientRect element - let - mouseX = (unsafeCoerce e).clientX - mouseY = (unsafeCoerce e).clientY - distanceX = - if mouseX # between left right - then 0.0 - else if mouseX < left - then left - mouseX - else mouseX - right - distanceY = - if mouseY # between top bottom - then 0.0 - else if mouseY < top - then top - mouseY - else mouseY - bottom - distance = sqrt ((distanceX `pow` 2.0) + (distanceY `pow` 2.0)) - setMouseDistance \_ -> round distance + mouseY = (unsafeCoerce e).clientY - let mouseMoveEventType = EventType "mousemove" - windowEventTarget <- map Window.toEventTarget window - addEventListener mouseMoveEventType mouseMoveListener false windowEventTarget - pure do - removeEventListener mouseMoveEventType mouseMoveListener false windowEventTarget + distanceX = + if mouseX # between left right then + 0.0 + else + if mouseX < left then + left - mouseX + else + mouseX - right - pure (mouseDistance /\ elementRef) + distanceY = + if mouseY # between top bottom then + 0.0 + else + if mouseY < top then + top - mouseY + else + mouseY - bottom + + distance = sqrt ((distanceX `pow` 2.0) + (distanceY `pow` 2.0)) + setMouseDistance \_ -> round distance + let + mouseMoveEventType = EventType "mousemove" + windowEventTarget <- map Window.toEventTarget window + addEventListener mouseMoveEventType mouseMoveListener false windowEventTarget + pure do + removeEventListener mouseMoveEventType mouseMoveListener false windowEventTarget + pure (mouseDistance /\ elementRef) diff --git a/examples/todo-app/src/TodoApp.purs b/examples/todo-app/src/TodoApp.purs index cff333b..d4027c5 100644 --- a/examples/todo-app/src/TodoApp.purs +++ b/examples/todo-app/src/TodoApp.purs @@ -10,7 +10,7 @@ import React.Basic.DOM as R import React.Basic.DOM.Events (preventDefault, stopPropagation, targetValue) import React.Basic.Events (handler, handler_) import React.Basic.Events as Events -import React.Basic.Hooks (CreateComponent, component, element, elementKeyed, empty, memo, useReducer, useState, (/\)) +import React.Basic.Hooks (ReactComponent, component, element, elementKeyed, empty, memo, useReducer, useState, (/\)) import React.Basic.Hooks as React data Action @@ -47,7 +47,7 @@ reducer state = case _ of Nothing -> state SetFilter filter -> state { filter = filter } -mkTodoApp :: CreateComponent {} +mkTodoApp :: Effect (ReactComponent {}) mkTodoApp = do let initialState = { todos: [], filter: All } @@ -82,7 +82,7 @@ mkTodoApp = do where todoAppEl = RB.element $ R.unsafeCreateDOMComponent "todo-app" -mkTodoInput :: CreateComponent { dispatch :: Action -> Effect Unit } +mkTodoInput :: Effect (ReactComponent { dispatch :: Action -> Effect Unit }) mkTodoInput = do component "TodoInput" \props -> React.do value /\ setValue <- useState "" @@ -105,7 +105,7 @@ mkTodoInput = do , style: R.css { marginBottom: "16px", width: "100%" } } -mkTodoRow :: CreateComponent { id :: Int, todo :: Todo, dispatch :: Action -> Effect Unit } +mkTodoRow :: Effect (ReactComponent { id :: Int, todo :: Todo, dispatch :: Action -> Effect Unit }) mkTodoRow = component "Todo" \props -> React.do pure @@ -137,7 +137,7 @@ mkTodoRow = } } -mkTodoFilters :: CreateComponent { filter :: TodoFilter, dispatch :: Action -> Effect Unit } +mkTodoFilters :: Effect (ReactComponent { filter :: TodoFilter, dispatch :: Action -> Effect Unit }) mkTodoFilters = component "TodoFilters" \props -> React.do let diff --git a/src/React/Basic/Hooks.purs b/src/React/Basic/Hooks.purs index 3621f3a..b5a949d 100644 --- a/src/React/Basic/Hooks.purs +++ b/src/React/Basic/Hooks.purs @@ -12,8 +12,7 @@ -- | *A note on Refs:* The `Ref` type is useful for passing to DOM nodes, but while this module remains a small extension to the existing react-basic library it won't be possible to pass a `ref` prop to the native DOM components. -- | In the meantime, use `element (unsafeCreateDOMComponent "div") { ref: elementRef }`. module React.Basic.Hooks - ( CreateComponent - , component + ( component , memo , UseState , useState @@ -39,22 +38,14 @@ module React.Basic.Hooks , UseEqCache , useEqCache , UnsafeReference(..) - , Render - , Pure - , Hook - , bind - , discard , displayName + , module React.Basic.Hooks.Internal , module React.Basic , module Data.Tuple.Nested ) where import Prelude hiding (bind, discard) -import Control.Applicative.Indexed (class IxApplicative) -import Control.Apply.Indexed (class IxApply) -import Control.Bind.Indexed (class IxBind, ibind) import Data.Function.Uncurried (Fn2, mkFn2) -import Data.Functor.Indexed (class IxFunctor) import Data.Maybe (Maybe) import Data.Newtype (class Newtype) import Data.Nullable (Nullable, toMaybe) @@ -65,14 +56,10 @@ import Effect.Uncurried (EffectFn1, EffectFn2, EffectFn3, mkEffectFn1, runEffect import Prelude (bind) as Prelude import Prim.Row (class Lacks) import React.Basic (JSX, ReactComponent, ReactContext, Ref, consumer, contextConsumer, contextProvider, createContext, element, elementKeyed, empty, keyed, fragment, provider) -import Type.Equality (class TypeEquals) +import React.Basic.Hooks.Internal (Hook, Pure, Render, bind, discard, coerceHook, unsafeHook, unsafeRenderEffect) import Unsafe.Coerce (unsafeCoerce) import Unsafe.Reference (unsafeRefEq) --- | Alias for convenience. -type CreateComponent props - = Effect (ReactComponent props) - -- | Create a React component given a display name and render function. -- | Creating components is effectful because React uses the function -- | instance as the component's "identity" or "type". Components should @@ -84,20 +71,29 @@ component :: Lacks "ref" props => String -> ({ | props } -> Render Unit hooks JSX) -> - CreateComponent { | props } + Effect (ReactComponent { | props }) component name renderFn = let - c = unsafeReactFunctionComponent (mkEffectFn1 (\props -> case renderFn props of Render a -> a)) + c = + unsafeReactFunctionComponent + ( mkEffectFn1 + ( \props -> + unsafeDiscardRenderEffects (renderFn props) + ) + ) in runEffectFn2 unsafeSetDisplayName name c +unsafeDiscardRenderEffects :: forall x y a. Render x y a -> Effect a +unsafeDiscardRenderEffects = unsafeCoerce + unsafeReactFunctionComponent :: forall props. EffectFn1 props JSX -> ReactComponent props unsafeReactFunctionComponent = unsafeCoerce memo :: forall props. - CreateComponent props -> - CreateComponent props + Effect (ReactComponent props) -> + Effect (ReactComponent props) memo = flip Prelude.bind (runEffectFn1 memo_) foreign import data UseState :: Type -> Type -> Type @@ -107,7 +103,7 @@ useState :: state -> Hook (UseState state) (state /\ ((state -> state) -> Effect Unit)) useState initialState = - Render do + unsafeHook do runEffectFn2 useState_ (mkFn2 Tuple) initialState foreign import data UseEffect :: Type -> Type -> Type @@ -120,7 +116,7 @@ useEffect :: key -> Effect (Effect Unit) -> Hook (UseEffect key) Unit -useEffect key effect = Render (runEffectFn3 useEffect_ (mkFn2 eq) key effect) +useEffect key effect = unsafeHook (runEffectFn3 useEffect_ (mkFn2 eq) key effect) foreign import data UseLayoutEffect :: Type -> Type -> Type @@ -130,7 +126,7 @@ useLayoutEffect :: key -> Effect (Effect Unit) -> Hook (UseLayoutEffect key) Unit -useLayoutEffect keys effect = Render (runEffectFn3 useLayoutEffect_ (mkFn2 eq) keys effect) +useLayoutEffect keys effect = unsafeHook (runEffectFn3 useLayoutEffect_ (mkFn2 eq) keys effect) foreign import data UseReducer :: Type -> Type -> Type -> Type @@ -140,7 +136,7 @@ useReducer :: (state -> action -> state) -> Hook (UseReducer state action) (state /\ (action -> Effect Unit)) useReducer initialState reducer = - Render do + unsafeHook do runEffectFn3 useReducer_ (mkFn2 Tuple) (mkFn2 reducer) @@ -150,7 +146,7 @@ foreign import data UseRef :: Type -> Type -> Type useRef :: forall a. a -> Hook (UseRef a) (Ref a) useRef initialValue = - Render do + unsafeHook do runEffectFn1 useRef_ initialValue readRef :: forall a. Ref a -> Effect a @@ -163,15 +159,15 @@ writeRef :: forall a. Ref a -> a -> Effect Unit writeRef = runEffectFn2 writeRef_ renderRef :: forall a. Ref a -> Pure a -renderRef ref = Render (readRef ref) +renderRef ref = unsafeRenderEffect (readRef ref) renderRefMaybe :: forall a. Ref (Nullable a) -> Pure (Maybe a) -renderRefMaybe a = Render (readRefMaybe a) +renderRefMaybe a = unsafeRenderEffect (readRefMaybe a) foreign import data UseContext :: Type -> Type -> Type useContext :: forall a. ReactContext a -> Hook (UseContext a) a -useContext context = Render (runEffectFn1 useContext_ context) +useContext context = unsafeHook (runEffectFn1 useContext_ context) foreign import data UseMemo :: Type -> Type -> Type -> Type @@ -181,7 +177,7 @@ useMemo :: key -> (Unit -> a) -> Hook (UseMemo key a) a -useMemo key computeA = Render (runEffectFn3 useMemo_ (mkFn2 eq) key computeA) +useMemo key computeA = unsafeHook (runEffectFn3 useMemo_ (mkFn2 eq) key computeA) foreign import data UseCallback :: Type -> Type -> Type -> Type @@ -191,7 +187,7 @@ useCallback :: key -> a -> Hook (UseCallback key a) a -useCallback key computeA = Render (runEffectFn3 useCallback_ (mkFn2 eq) key computeA) +useCallback key computeA = unsafeHook (runEffectFn3 useCallback_ (mkFn2 eq) key computeA) foreign import data UseEqCache :: Type -> Type -> Type @@ -200,7 +196,7 @@ useEqCache :: Eq a => a -> Hook (UseCallback a a) a -useEqCache a = Render (runEffectFn2 useEqCache_ (mkFn2 eq) a) +useEqCache a = unsafeHook (runEffectFn2 useEqCache_ (mkFn2 eq) a) newtype UnsafeReference a = UnsafeReference a @@ -210,57 +206,6 @@ derive instance newtypeUnsafeReference :: Newtype (UnsafeReference a) _ instance eqUnsafeReference :: Eq (UnsafeReference a) where eq = unsafeRefEq --- | Render represents the effects allowed within a React component's --- | body, i.e. during "render". This includes hooks and ends with --- | returning JSX (see `pure`), but does not allow arbitrary side --- | effects. -newtype Render x y a - = Render (Effect a) - -type Pure a - = forall hooks. Render hooks hooks a - -type Hook (newHook :: Type -> Type) a - = forall hooks. Render hooks (newHook hooks) a - -instance ixFunctorRender :: IxFunctor Render where - imap f (Render a) = Render (map f a) - -instance ixApplyRender :: IxApply Render where - iapply (Render f) (Render a) = Render (apply f a) - -instance ixApplicativeRender :: IxApplicative Render where - ipure a = Render (pure a) - -instance ixBindRender :: IxBind Render where - ibind (Render m) f = Render (Prelude.bind m \a -> case f a of Render b -> b) - --- | Exported for use with qualified-do syntax -bind :: forall a b x y z m. IxBind m => m x y a -> (a -> m y z b) -> m x z b -bind = ibind - --- | Exported for use with qualified-do syntax -discard :: forall a b x y z m. IxBind m => m x y a -> (a -> m y z b) -> m x z b -discard = ibind - -instance functorRender :: Functor (Render x y) where - map f (Render a) = Render (map f a) - -instance applyRender :: TypeEquals x y => Apply (Render x y) where - apply (Render f) (Render a) = Render (apply f a) - -instance applicativeRender :: TypeEquals x y => Applicative (Render x y) where - pure a = Render (pure a) - -instance bindRender :: TypeEquals x y => Bind (Render x y) where - bind (Render m) f = Render (Prelude.bind m \a -> case f a of Render b -> b) - -instance semigroupRender :: (TypeEquals x y, Semigroup a) => Semigroup (Render x y a) where - append (Render a) (Render b) = Render (append a b) - -instance monoidRender :: (TypeEquals x y, Monoid a) => Monoid (Render x y a) where - mempty = Render mempty - -- | Retrieve the Display Name from a `ReactComponent`. Useful for debugging and improving -- | error messages in logs. -- | diff --git a/src/React/Basic/Hooks/Aff.purs b/src/React/Basic/Hooks/Aff.purs index 231e34e..63e81eb 100644 --- a/src/React/Basic/Hooks/Aff.purs +++ b/src/React/Basic/Hooks/Aff.purs @@ -1,31 +1,35 @@ module React.Basic.Hooks.Aff where import Prelude - import Data.Either (Either) import Data.Maybe (Maybe(..)) +import Data.Newtype (class Newtype) import Effect.Aff (Aff, error, killFiber, launchAff_, runAff) import Effect.Exception (Error) -import React.Basic.Hooks (Hook, UseEffect, UseState, useEffect, useState, (/\)) +import React.Basic.Hooks (Hook, UseEffect, UseState, coerceHook, useEffect, useState, (/\)) import React.Basic.Hooks as React -type UseAff key a hooks = - UseEffect key (UseState (Result a) hooks) +newtype UseAff key a hooks + = UseAff (UseEffect key (UseState (Result a) hooks)) + +derive instance ntUseAff :: Newtype (UseAff key a hooks) _ -type Result a = Maybe (Either Error a) +type Result a + = Maybe (Either Error a) -useAff - :: forall key a - . Eq key - => key - -> Aff a - -> Hook (UseAff key a) (Result a) -useAff key aff = React.do - result /\ setResult <- useState Nothing - useEffect key do - setResult (const Nothing) - fiber <- runAff (setResult <<< const <<< Just) aff - pure do - launchAff_ do - killFiber (error "Effect hook discarded.") fiber - pure result \ No newline at end of file +useAff :: + forall key a. + Eq key => + key -> + Aff a -> + Hook (UseAff key a) (Result a) +useAff key aff = + coerceHook React.do + result /\ setResult <- useState Nothing + useEffect key do + setResult (const Nothing) + fiber <- runAff (setResult <<< const <<< Just) aff + pure do + launchAff_ do + killFiber (error "Effect hook discarded.") fiber + pure result diff --git a/src/React/Basic/Hooks/Internal.purs b/src/React/Basic/Hooks/Internal.purs new file mode 100644 index 0000000..fd60883 --- /dev/null +++ b/src/React/Basic/Hooks/Internal.purs @@ -0,0 +1,127 @@ +module React.Basic.Hooks.Internal + ( Render + , coerceHook + , unsafeHook + , unsafeRenderEffect + , Pure + , Hook + , bind + , discard + ) where + +import Prelude hiding (bind) +import Control.Applicative.Indexed (class IxApplicative) +import Control.Apply.Indexed (class IxApply) +import Control.Bind.Indexed (class IxBind, ibind) +import Data.Functor.Indexed (class IxFunctor) +import Data.Newtype (class Newtype) +import Effect (Effect) +import Prelude (bind) as Prelude +import Type.Equality (class TypeEquals) + +-- | Render represents the effects allowed within a React component's +-- | body, i.e. during "render". This includes hooks and ends with +-- | returning JSX (see `pure`), but does not allow arbitrary side +-- | effects. +newtype Render x y a + = Render (Effect a) + +-- | Alias a chain of hooks. Useful for exposing a single "clean" +-- | type when creating a hook to improve error messages +-- | and hide implementation details. +-- | +-- | For example, the following alias is technically correct but +-- | when inspecting types or error messages the alias is expanded +-- | to the full original type: +-- | +-- | ```purs +-- | type UseNodeDistance hooks = UseEffect Unit (UseState Int (UseRef (Nullable Node) hooks)) +-- | +-- | useNodeDistanceFromMouse :: Hook UseNodeDistance (Int /\ (Ref (Nullable Node))) +-- | ``` +-- | +-- | `aliasHook` allows TODO! +-- | when inspecting types or error messages the alias is expanded +-- | to the full original type: +-- | +-- | ```purs +-- | type UseNodeDistance hooks = UseEffect Unit (UseState Int (UseRef (Nullable Node) hooks)) +-- | +-- | useNodeDistanceFromMouse :: Hook UseNodeDistance (Int /\ (Ref (Nullable Node))) +-- | ``` +-- | +-- | +-- | +coerceHook :: + forall hooks oldHook newHook a. + Newtype newHook oldHook => + Render hooks oldHook a -> + Render hooks newHook a +coerceHook (Render a) = Render a + +-- | Promote an arbitrary Effect to a Hook. +-- | +-- | This is unsafe because it allows arbitrary +-- | effects to be performed during a render, which +-- | may cause them to be run many times by React. +-- | This function is primarily for constructing +-- | new hooks using the FFI. If you just want to +-- | alias a safe hook's effects, prefer `coerceHook`. +unsafeHook :: + forall newHook a. + Effect a -> Hook newHook a +unsafeHook = Render + +-- | Promote an arbitrary Effect to a Pure render effect. +-- | +-- | This is unsafe because it allows arbitrary +-- | effects to be performed during a render, which +-- | may cause them to be run many times by React. +-- | You should almost always prefer `useEffect`! +unsafeRenderEffect :: forall a. Effect a -> Pure a +unsafeRenderEffect = Render + +-- | Discards +type Pure a + = forall hooks. Render hooks hooks a + +type Hook (newHook :: Type -> Type) a + = forall hooks. Render hooks (newHook hooks) a + +instance ixFunctorRender :: IxFunctor Render where + imap f (Render a) = Render (map f a) + +instance ixApplyRender :: IxApply Render where + iapply (Render f) (Render a) = Render (apply f a) + +instance ixApplicativeRender :: IxApplicative Render where + ipure a = Render (pure a) + +instance ixBindRender :: IxBind Render where + ibind (Render m) f = Render (Prelude.bind m \a -> case f a of Render b -> b) + +-- | Exported for use with qualified-do syntax +bind :: forall a b x y z m. IxBind m => m x y a -> (a -> m y z b) -> m x z b +bind = ibind + +-- | Exported for use with qualified-do syntax +discard :: forall a b x y z m. IxBind m => m x y a -> (a -> m y z b) -> m x z b +discard = ibind + +instance functorRender :: Functor (Render x y) where + map f (Render a) = Render (map f a) + +instance applyRender :: TypeEquals x y => Apply (Render x y) where + apply (Render f) (Render a) = Render (apply f a) + +instance applicativeRender :: TypeEquals x y => Applicative (Render x y) where + pure a = Render (pure a) + +instance bindRender :: TypeEquals x y => Bind (Render x y) where + bind (Render m) f = Render (Prelude.bind m \a -> case f a of Render b -> b) + +instance semigroupRender :: (TypeEquals x y, Semigroup a) => Semigroup (Render x y a) where + append (Render a) (Render b) = Render (append a b) + +instance monoidRender :: (TypeEquals x y, Monoid a) => Monoid (Render x y a) where + mempty = Render mempty