Skip to content

Instantly share code, notes, and snippets.

@coot
Last active July 21, 2017 07:48
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save coot/861707a21cf15b3581666532d7bc8366 to your computer and use it in GitHub Desktop.
Save coot/861707a21cf15b3581666532d7bc8366 to your computer and use it in GitHub Desktop.
React.RecSpec
module React.RecSpec where
import Control.Monad.Eff (Eff, kind Effect)
import Data.Maybe (Maybe(..), fromMaybe)
import Data.Record as R
import Prelude (Unit, bind, pure, show, unit, ($))
import React (Disallowed, ReactElement, ReactProps, ReactRefs, ReactState, ReadOnly, ReadWrite)
import React.DOM as D
import Type.Data.Symbol (class IsSymbol, SProxy(..))
import Type.Row (class RowLacks)
newtype This props state (r :: # Type) = This (Record r)
set
:: forall l a b p s r r1 r2 eff
. IsSymbol l
=> RowCons l a r r1
=> RowCons l b r r2
=> SProxy l
-> b
-> This p s r1
-> Eff eff (This p s r2)
set l b (This r) = pure (This (R.set l b r))
insert
:: forall r1 r2 l a p s eff
. IsSymbol l
=> RowLacks l r1
=> RowCons l a r1 r2
=> SProxy l
-> a
-> This p s r1
-> Eff eff (This p s r2)
insert l a (This r) = pure (This (R.insert l a r))
get
:: forall r r' l a p s eff
. IsSymbol l
=> RowCons l a r' r
=> SProxy l
-> This p s r
-> Eff eff a
get l (This r) = pure $ R.get l r
delete
:: forall r1 r2 l a p s eff
. IsSymbol l
=> RowLacks l r1
=> RowCons l a r1 r2
=> SProxy l
-> This p s r2
-> Eff eff (This p s r1)
delete l (This r) = pure (This (R.delete l r))
-- | A render function.
type Render props state r eff =
This props state r ->
Eff
( props :: ReactProps
, refs :: ReactRefs Disallowed
, state :: ReactState ReadOnly
| eff
) ReactElement
-- | A get initial state function.
type GetInitialState props state r eff =
This props state r ->
Eff
( props :: ReactProps
, state :: ReactState Disallowed
, refs :: ReactRefs Disallowed
| eff
) state
-- | A component will mount function.
type ComponentWillMount props state r eff =
This props state () ->
Eff
( props :: ReactProps
, state :: ReactState ReadWrite
, refs :: ReactRefs Disallowed
| eff
) (This props state r)
-- | A component did mount function.
type ComponentDidMount props state r eff =
This props state r ->
Eff
( props :: ReactProps
, state :: ReactState ReadWrite
, refs :: ReactRefs ReadOnly
| eff
) Unit
-- | A component will receive props function.
type ComponentWillReceiveProps props state r eff =
This props state r ->
props ->
Eff
( props :: ReactProps
, state :: ReactState ReadWrite
, refs :: ReactRefs ReadOnly
| eff
) Unit
-- | A should component update function.
type ShouldComponentUpdate props state r eff =
This props state r ->
props ->
state ->
Eff
( props :: ReactProps
, state :: ReactState ReadWrite
, refs :: ReactRefs ReadOnly
| eff
) Boolean
-- | A component will update function.
type ComponentWillUpdate props state r eff =
This props state r ->
props ->
state ->
Eff
( props :: ReactProps
, state :: ReactState ReadWrite
, refs :: ReactRefs ReadOnly
| eff
) Unit
-- | A component did update function.
type ComponentDidUpdate props state r eff =
This props state r ->
props ->
state ->
Eff
( props :: ReactProps
, state :: ReactState ReadOnly
, refs :: ReactRefs ReadOnly
| eff
) Unit
-- | A component will unmount function.
type ComponentWillUnmount props state r1 eff =
-- Subrow r2 r1 =>
This props state r1 ->
Eff
( props :: ReactProps
, state :: ReactState ReadOnly
, refs :: ReactRefs ReadOnly
| eff
) (This props state ())
type Spec p s (r :: # Type) (eff :: # Effect) =
{ render :: Render p s r eff
, displayName :: String
, getInitialState :: GetInitialState p s r eff
, componentWillMount :: ComponentWillMount p s r eff
, componentDidMount :: ComponentDidMount p s r eff
, componentWillReceiveProps :: ComponentWillReceiveProps p s r eff
, shouldComponentUpdate :: ShouldComponentUpdate p s r eff
, componentWillUpdate :: ComponentWillUpdate p s r eff
, componentDidUpdate :: ComponentDidUpdate p s r eff
, componentWillUnmount :: ComponentWillUnmount p s r eff
}
spec'
:: forall p s r eff
. GetInitialState p s r eff
-> ComponentWillMount p s r eff
-> ComponentWillUnmount p s r eff
-> Render p s r eff
-> Spec p s r eff
spec' getInitialState componentWillMount componentWillUnmount renderFn =
{ render: renderFn
, displayName: ""
, getInitialState: getInitialState
, componentWillMount: componentWillMount
, componentDidMount: \_ -> pure unit
, componentWillReceiveProps: \_ _ -> pure unit
, shouldComponentUpdate: \_ _ _ -> pure true
, componentWillUpdate: \_ _ _ -> pure unit
, componentDidUpdate: \_ _ _ -> pure unit
, componentWillUnmount: componentWillUnmount
}
spec
:: forall p s eff
. s
-> Render p s () eff
-> Spec p s () eff
spec s r = spec' (\_ -> pure s) pure pure r
-- test
cSpec :: forall eff. Spec Unit Unit (count :: Maybe Int) eff
cSpec = (spec' (\_ -> pure unit) componentWillMount componentWillUnmount render)
{ componentWillMount = componentWillMount
}
where
componentWillMount this = do
insert (SProxy :: SProxy "count") (Just 0) this
componentWillUnmount this = do
delete (SProxy :: SProxy "count") this
render this = do
c <- get (SProxy :: SProxy "count") this
pure $ D.div' [ D.text (show (fromMaybe 0 c)) ]
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment