Ja ja ja, was ist los, was ist das?

This commit is contained in:
Mark Eibes 2020-05-03 13:38:52 +02:00
parent c2baa78104
commit 4321e4cc2d
52 changed files with 11716 additions and 250 deletions

1
.gitignore vendored
View File

@ -35,6 +35,7 @@ playground/.spago
playground/src/Main.purs
blog/output
blog/.psc-ide-port
playgrounds/**
!playgrounds/.gitkeep

1
blog/.gitignore vendored
View File

@ -70,3 +70,4 @@ yarn-error.log
# Purescript
.spago/
.psc-ide-port

View File

@ -1 +0,0 @@
15877

View File

@ -2,42 +2,36 @@ module PSLayout where
import Prelude
import Control.Monad.State (evalStateT, get, put, runStateT)
import Control.Monad.State as State
import Control.Monad.Trans.Class (lift)
import Data.Array (foldMap)
import Data.Array (foldMap, intercalate)
import Data.Array as Array
import Data.Array.NonEmpty as NEA
import Data.Either (Either(..))
import Data.Foldable (fold)
import Data.Function.Uncurried (mkFn2)
import Data.Maybe (Maybe(..), fromMaybe, isJust)
import Data.Monoid (guard)
import Data.Monoid.Additive (Additive(..))
import Data.Newtype (ala)
import Data.Newtype as NT
import Data.Nullable (Nullable)
import Data.Nullable as Nullable
import Data.String as String
import Data.Traversable (Accum, mapAccumL)
import Data.Traversable (mapAccumL)
import Data.Tuple.Nested ((/\))
import Debug.Trace (spy)
import Effect (Effect)
import Effect.Aff (launchAff_)
import Effect.Class (liftEffect)
import Effect.Class.Console (log)
import JSS (jss, jssClasses)
import JSS (jssClasses)
import Justifill (justifill)
import Milkis.Impl (FetchImpl)
import React.Basic (JSX, ReactComponent, fragment)
import React.Basic.DOM (unsafeCreateDOMComponent)
import React.Basic.DOM as R
import React.Basic.Helpers (jsx)
import React.Basic.Hooks (ReactChildren, component, componentWithChildren, element, memo, reactChildrenToArray, readRef, useEffect, useReducer, useRef, useState, writeRef)
import React.Basic.Hooks (ReactChildren, component, componentWithChildren, element, memo, reactChildrenToArray, useReducer, useState)
import React.Basic.Hooks as React
import Shared.Models.Body (CompileResult)
import Unsafe.Coerce (unsafeCoerce)
import Yoga.Box.Component as Box
import Yoga.ClickAway.Component as ClickAway
import Yoga.CloseIcon.Component as CloseIcon
import Yoga.CompileEditor.Component (mkCompileEditor)
import Yoga.Compiler.Api (apiCompiler)
import Yoga.Compiler.Types (Compiler)
@ -113,9 +107,10 @@ mkLayout fetchImpl = do
, element modal (justifill modalProps)
]
, element mdxProviderComponent
{ children: spy "children" children
{ children
, siteInfo
, showModal: dispatch <<< ShowModal
, hideModal: dispatch HideModal
}
]
]
@ -136,6 +131,7 @@ mkMdxProviderComponent ∷
{ children ∷ ReactChildren JSX
, siteInfo ∷ SiteQueryResult
, showModal ∷ Modal.Props -> Effect Unit
, hideModal :: Effect Unit
}
)
mkMdxProviderComponent compiler = do
@ -148,6 +144,7 @@ mkMdxProviderComponent compiler = do
quiz <- memo $ mkQuiz compiler
h <- memo mkH
p <- memo mkP
closeIcon <- CloseIcon.makeComponent
useStyles <-
makeStylesJSS
$ jssClasses \(theme ∷ CSSTheme) ->
@ -160,22 +157,32 @@ mkMdxProviderComponent compiler = do
, borderRadius: "3px"
}
}
componentWithChildren "MDXProviderComponent" \{ children, siteInfo, showModal } -> React.do
componentWithChildren "MDXProviderComponent" \{ children, siteInfo, showModal, hideModal } -> React.do
classes <- useStyles {}
visibleUntil /\ updateVisible <- useState 1
let
onFailure = showModal (justifill { title: "Failed", kids: [ R.text "Try again" ] } ∷ Modal.Props)
onFailure title kids =
showModal
( justifill
{ title
, icon: element closeIcon { onClick: hideModal, style: Nothing }
, kids
} ∷ Modal.Props
)
onSuccess = updateVisible (_ + one)
mapVisible i kid =
{ accum: i + if isQuiz kid then one else zero
, value: guard (i < visibleUntil) (pure kid)
}
visibleKids :: Array JSX
visibleKids = reactChildrenToArray children
# mapAccumL mapVisible zero
# _.value
# Array.catMaybes
visibleKids ∷ Array JSX
visibleKids =
reactChildrenToArray children
# mapAccumL mapVisible zero
# _.value
# Array.catMaybes
siteInfoJSX =
R.div
@ -205,10 +212,11 @@ mkMdxProviderComponent compiler = do
, inlineCode:
\props -> do
R.span { className: classes.code, children: props.children }
, pre: mkFn2
\(props ∷ PreProps) other -> do
, pre:
mkFn2 \(props ∷ PreProps) other -> do
let
_ = spy "other" other
childrenQ = Nullable.toMaybe props.children
propsQ = (_.props >>> Nullable.toMaybe) =<< childrenQ
@ -255,9 +263,9 @@ mkQuiz ∷ _ -> Effect (ReactComponent _)
mkQuiz compiler = do
fillInTheGaps <- FillInTheGaps.makeComponent
box <- Box.makeComponent
component "Quiz" \({ initialSegments, onFailure, onSuccess } ∷ { initialSegments ∷ _, onFailure ∷ _, onSuccess :: _}) -> React.do
component "Quiz" \({ initialSegments, onFailure, onSuccess } ∷ { initialSegments ∷ _, onFailure ∷ _, onSuccess ∷ _ }) -> React.do
segments /\ updateSegments <- useState initialSegments
solved /\ updateSolved <- useState false
solvedWith /\ updateSolvedWith <- useState Nothing
pure
$ jsx box {}
[ element fillInTheGaps
@ -270,9 +278,11 @@ mkQuiz compiler = do
liftEffect case result of
Right r
| String.stripSuffix (String.Pattern "\n") r.stdout == (findResult $ join segments) -> do
updateSolved (const true)
updateSolvedWith (const $ String.stripSuffix (String.Pattern "\n") r.stdout)
onSuccess
_ -> onFailure
Right r | r.stdout /= "\n" -> onFailure "Oh shit!" [R.text r.stdout]
Right r -> onFailure "Oh shit!" [R.text r.stderr]
Left (cr :: CompileResult) -> onFailure "Oh shit!" [R.text (intercalate ", " (cr.result <#> _.message))]
, updateSegments:
\update -> do
let
@ -281,7 +291,7 @@ mkQuiz compiler = do
old, new
| new == old -> mempty
_, _ -> updateSegments (const updated)
, readOnly: Just solved
, solvedWith
}
]

67
blog/src/pages/cast.mdx Normal file
View File

@ -0,0 +1,67 @@
import { Link } from 'gatsby'
import SEO from '../components/seo'
<SEO title="Home" keywords={['gatsby', 'application', 'react']} />
# The beginning
## Hocus
```purescript
--result pocus
module Main where
import Grimoire
incantation :: Effect Unit
incantation =
--start here
cast "pocus"
--end here
```
## Ala
```purescript
--result kazam
module Main where
import Grimoire
incantation :: Effect Unit
incantation =
--start here
{-cast-} "kazam"
--end here
```
## Abra
```purescript
--result cadabra
module Main where
import Grimoire
incantation :: Effect Unit
incantation =
--start here
{-cast-} "{-cadabra-}"
--end here
```
## Abra cadabra
```purescript
--result abra\ncadabra
module Main where
import Grimoire
import Prelude (discard)
incantation :: Effect Unit
incantation =
--start here
do
{-cast-} "{-abra-}"
{-cast-} "{-cadabra-}"
--end here
```
<Link to="/take/"><b>Take</b> the book and venture on</Link>

View File

@ -4,22 +4,9 @@ import SEO from '../components/seo'
<SEO title="Home" keywords={['gatsby', 'application', 'react']} />
# Welcome to baby's first tutorial!
# The beginning
Try some PureScript here.
Welcome to your magical journey
```purescript
module Main where
import Batteries
main :: Effect Unit
main = log $ "Hello!" <> show heinz
heinz = 7
```
This is some `inline code`.
Now go build something great.
<Link to="/optional/">Go to the first exercise</Link>
<Link to="/cast/">Learn to <emph>cast</emph> some spells</Link>

View File

@ -1,43 +0,0 @@
import Layout from '../components/layout'
import SEO from '../components/seo'
import { Link } from 'gatsby'
<SEO title="Home" keywords={['gatsby', 'application', 'react']} />
# Optional
```purescript
--result Hello World
module Main where
import Grimoire
incantation :: Effect Unit
--start here
incantation = cast $
"{-Hello-}" <> " " <> "{-World-}"
--end here
```
---
```purescript
--result Hello World
module Main where
import Grimoire
incantation :: Effect Unit
--start here
incantation = cast $
"{-Hello World-}"
--end here
```
---
## Hans Hölzel
---
Guter Mann
<Link to="/optional/">Go to the first exercise</Link>

111
blog/src/pages/take.mdx Normal file
View File

@ -0,0 +1,111 @@
import { Link } from 'gatsby'
import SEO from '../components/seo'
<SEO title="Home" keywords={['gatsby', 'application', 'react']} />
# Take
## Hocu
```purescript
--result pocu
module Main where
import Grimoire
import Data.String (take)
incantation :: Effect Unit
incantation =
--start here
cast (take 4 "pocus")
--end here
```
## Hoc
```purescript
--result poc
module Main where
import Grimoire
import Data.String (take)
incantation :: Effect Unit
incantation =
--start here
{-cast-} (take 3 "pocus")
--end here
```
## H
```purescript
--result p
module Main where
import Grimoire
import Data.String (take)
incantation :: Effect Unit
incantation =
--start here
cast (take {-1-} "pocus")
--end here
```
## Hocus
```purescript
--result pocus
module Main where
import Grimoire
import Data.String (take)
incantation :: Effect Unit
incantation =
--start here
{-cast-} ({-take-} 200 "pocus")
--end here
```
## Ab
```purescript
--result cadab
module Main where
import Grimoire
import Data.String (take)
incantation :: Effect Unit
incantation =
--start here
{-cast-} ({-take-} 5 "cadabra")
--end here
```
## Echo
```purescript
--result echo
module Main where
import Grimoire
import Data.String (take)
incantation :: Effect Unit
incantation =
--start here
cast (take {-4-} "echo")
--end here
```
## Silence
```purescript
--result
module Main where
import Grimoire
import Data.String (take)
incantation :: Effect Unit
incantation =
--start here
cast (take {-0-} "noise")
--end here
```
<Link to="/optional/">That's it for now</Link>

2761
components/dist/bundle.js vendored Normal file

File diff suppressed because one or more lines are too long

496
components/dist/editor.worker.js vendored Normal file

File diff suppressed because one or more lines are too long

808
components/dist/json.worker.js vendored Normal file

File diff suppressed because one or more lines are too long

2761
components/dist/test-bundle.js vendored Normal file

File diff suppressed because one or more lines are too long

496
components/editor.worker.js Normal file

File diff suppressed because one or more lines are too long

808
components/json.worker.js Normal file

File diff suppressed because one or more lines are too long

View File

@ -3,11 +3,9 @@ module React.Basic.Extra.Hooks.UseKeyUp where
import Prelude
import Data.Maybe (Maybe(..))
import Data.Newtype (class Newtype)
import Debug.Trace (spy)
import Effect (Effect)
import React.Basic.Hooks (Hook, UseEffect, UseState, coerceHook, useEffect, useState, (/\))
import React.Basic.Hooks as React
import Unsafe.Coerce (unsafeCoerce)
import Web.Event.Event (Event, EventType(..))
import Web.Event.EventTarget (addEventListener, eventListener, removeEventListener)
import Web.HTML (window)
@ -18,14 +16,13 @@ newtype UseKeyUp hooks
(UseEffect Unit (UseState Boolean hooks))
derive instance ntUseKeyUp ∷ Newtype (UseKeyUp hooks) _
-- useScrollYPosition ∷ Hook UseScrollYPosition Number
useKeyUp ∷ Int -> Effect Unit -> Hook UseKeyUp Unit
useKeyUp ∷ KeyCode -> Effect Unit -> Hook UseKeyUp Unit
useKeyUp targetKey doWhat = do
coerceHook React.do
keyPressed /\ modifyKeyPressed <- useState false
useEffect unit do
listener <-
eventListener \event -> when (getKeyCode event == Just targetKey) doWhat
eventListener \event -> when (getKeyCode event == Just (keyCodeToInt targetKey)) doWhat
win <- window
addEventListener eventTypeKeyUp listener false (Win.toEventTarget win)
pure (removeEventListener eventTypeKeyUp listener false (Win.toEventTarget win))
@ -37,3 +34,11 @@ foreign import getKeyImpl ∷ ∀ a. (a -> Maybe a) -> Maybe a -> Event -> Maybe
getKeyCode ∷ Event -> Maybe Int
getKeyCode = getKeyImpl Just Nothing
data KeyCode
= Escape
| Return
keyCodeToInt = case _ of
Escape -> 27
Return -> 13

View File

@ -28,11 +28,10 @@ element_ x partialProps = element x props
where
props ∷ Record to
props =
( (fill ∷ { | thru } -> { | to })
( (justify ∷ { | from } -> { | thru })
partialProps
)
)
(fill ∷ { | thru } -> { | to })
( (justify ∷ { | from } -> { | thru })
partialProps
)
type Kids r
= ( kids ∷ Array JSX | r )

View File

@ -1,14 +1,11 @@
module React.Basic.Hooks.Spring.Stories where
import Prelude hiding (add)
import Data.Function.Uncurried (mkFn2)
import Data.Int (pow)
import Data.Maybe (Maybe(..), isJust)
import Data.Monoid (guard)
import Data.Tuple.Nested ((/\))
import Debug.Trace (spy)
import Effect (Effect)
import Effect.Unsafe (unsafePerformEffect)
import JSS (jssClasses)
import React.Basic.DOM (css)
import React.Basic.DOM as R
@ -24,8 +21,7 @@ import Yoga.Button.Component (mkButton)
import Yoga.Card.Component (mkCard)
import Yoga.Centre.Component as Centre
import Yoga.Cluster.Component as Cluster
import Yoga.Helpers ((?||))
import Yoga.Spec.Helpers (withDarkTheme)
import Yoga.Spec.Helpers (withSpecTheme)
import Yoga.Stack.Component as Stack
import Yoga.Theme.Styles (makeStylesJSS)
import Yoga.Theme.Types (CSSTheme)
@ -33,11 +29,11 @@ import Yoga.Theme.Types (CSSTheme)
stories ∷ Effect Storybook
stories = do
storiesOf "Spring" do
add "The Spring" (withDarkTheme mkAnimated)
add "The Spring" (withSpecTheme mkAnimated)
[ {} ]
add "The Transition" (withDarkTheme mkTransition)
add "The Transition" (withSpecTheme mkTransition)
[ {} ]
add "The Drag" (withDarkTheme mkDragAnimated)
add "The Drag" (withSpecTheme mkDragAnimated)
[ {} ]
mkAnimated ∷ Effect (ReactComponent {})

View File

@ -18,6 +18,7 @@ import Web.Storage.Storage (getItem, setItem)
import Yoga.Theme (fromTheme)
import Yoga.Theme.CSSBaseline (mkCssBaseline)
import Yoga.Theme.Default (darkTheme, lightTheme)
import Yoga.Theme.Default as Default
import Yoga.Theme.Provider (mkThemeProvider)
import Yoga.Theme.Styles (makeStylesJSS)
import Yoga.Theme.Types (CSSTheme)
@ -63,7 +64,7 @@ mkThemeSwitcher ∷
)
mkThemeSwitcher = do
themeProvider <- mkThemeProvider
baseline <- mkCssBaseline
baseline <- mkCssBaseline Default.fontFaces
useStyles <-
makeStylesJSS
$ jssClasses \_ ->

View File

@ -6,11 +6,11 @@ import React.Basic.DOM as R
import React.TestingLibrary (describeComponent, renderComponent)
import Test.Spec (Spec, it)
import Yoga.Box.Component as Box
import Yoga.Spec.Helpers (withDarkTheme)
import Yoga.Spec.Helpers (withSpecTheme)
spec ∷ Spec Unit
spec =
describeComponent (withDarkTheme Box.makeComponent)
describeComponent (withSpecTheme Box.makeComponent)
"The Box Component" do
it "renders without problems" \stack -> do
_ <-

View File

@ -6,15 +6,18 @@ import CSS as Color
import Data.Array.NonEmpty as NEA
import Data.Foldable (intercalate)
import Data.Interpolate (i)
import Data.Maybe (Maybe)
import Data.Maybe (Maybe(..))
import Data.Monoid (guard)
import Effect (Effect)
import JSS (JSSClasses, JSSElem, jssClasses)
import Prim.Row (class Nub, class Union)
import React.Basic (JSX)
import React.Basic.DOM (Props_button)
import React.Basic.DOM as R
import React.Basic.Events (EventHandler)
import React.Basic.Hooks (ReactComponent, component)
import React.Basic.Hooks as React
import Record as Record
import Yoga.Helpers ((?||))
import Yoga.Theme (withAlpha)
import Yoga.Theme.Styles (makeStylesJSS)
@ -195,39 +198,59 @@ styles =
}
}
type Props
type MyProps
= ( children ∷ Array JSX, className ∷ String, disabled ∷ Boolean, onClick ∷ EventHandler )
type Props r
= { kids ∷ Array JSX
, buttonType ∷ Maybe ButtonType
, onClick ∷ EventHandler
, className ∷ Maybe String
, buttonProps ∷ Maybe { | r }
}
mkButton ∷ Effect (ReactComponent Props)
mkButton = do
mkButton ∷ Effect (ReactComponent (Props ()))
mkButton = mkButtonWithProps
type WithProps r
= Effect (ReactComponent (Props r))
mkButtonWithProps ∷
∀ extra given missing.
Union extra MyProps given =>
Nub given given =>
Union given missing Props_button =>
Effect (ReactComponent (Props extra))
mkButtonWithProps = do
useBaseStyles <- makeStylesJSS styles
useHighlightStyles <- makeStylesJSS highlightStyles
component "Button" \props@{ kids, onClick } -> React.do
component "Button" \(props@{ kids, onClick } ∷ Props extra) -> React.do
classes <- useBaseStyles {}
{ highlightedButton } <- useHighlightStyles {}
let
buttonType = props.buttonType ?|| PlainButton
className = props.className ?|| ""
buttonProps ∷ { | MyProps }
buttonProps =
{ className:
intercalate " "
[ classes.btn
, guard (buttonType == HighlightedButton) highlightedButton
, className
]
, disabled: buttonType == DisabledButton
, onClick
, children: kids
}
pure
$ R.div
{ className: classes.container <> " " <> if buttonType == DisabledButton then classes.disabled else ""
, children:
[ R.button
$ { className:
intercalate " "
[ classes.btn
, guard (buttonType == HighlightedButton) highlightedButton
, className
]
, disabled: buttonType == DisabledButton
, onClick
, children: kids
}
[ case props.buttonProps of
Just bps -> R.button $ Record.merge bps buttonProps
Nothing -> R.button buttonProps
]
}

View File

@ -43,7 +43,7 @@ stories =
button <- Button.mkButton
component "ExampleButton" \{ text, buttonType, onClick } -> React.do
pure
$ jsx (button ∷ _ Button.Props)
$ jsx button
{ onClick
, buttonType
}

View File

@ -1,21 +1,20 @@
module Yoga.Card.Component where
import Prelude
import CSS (BackgroundImage, angular, deg, linearGradient, pct)
import Color (cssStringRGBA)
import Color as Color
import Data.Foldable (fold)
import Data.Interpolate (i)
import Data.Maybe (Maybe)
import Data.Tuple.Nested ((/\))
import Effect (Effect)
import JSS (JSSClasses, JSSElem, jssClasses)
import React.Basic (JSX)
import React.Basic.Helpers (jsx)
import React.Basic.DOM as R
import React.Basic.Hooks (ReactComponent, component)
import React.Basic.Hooks as React
import Record.Extra (pick)
import Yoga.Box.Component as Box
import Yoga.Helpers (ifJustTrue, (?||))
import Yoga.Helpers (ifJustTrue)
import Yoga.Theme (withAlpha)
import Yoga.Theme.Styles (makeStylesJSS)
import Yoga.Theme.Types (CSSTheme, YogaTheme)
@ -29,6 +28,7 @@ styles =
{ card:
\props ->
{ borderRadius: "var(--s-2)"
, overflow: "hidden"
, boxShadow:
i -- bottom right
"var(--s-5) var(--s-3) var(--s-3) "
@ -61,7 +61,7 @@ mkCard = do
component "Card" \props@{ kids, className } -> React.do
classes <- useStyles (pick props)
pure
$ jsx box
{ className: classes.card <> " " <> (className ?|| "")
$ R.div
{ className: classes.card <> " " <> fold className
, children: kids
}
kids

View File

@ -24,8 +24,9 @@ stories = do
component "ExampleCard" \{} -> React.do
pure
$ jsx box {}
[ jsx card {}
[ R.text "hi there!" ]
$ pure
$ jsx card {}
[ jsx box {} [ R.text "hi there!" ]
]
loremIpsum ∷ String

View File

@ -6,7 +6,7 @@ import Data.Tuple.Nested ((/\))
import Effect (Effect)
import React.Basic.DOM (CSS)
import React.Basic.Events (handler_)
import React.Basic.Extra.Hooks.UseKeyUp (useKeyUp)
import React.Basic.Extra.Hooks.UseKeyUp (KeyCode(..), useKeyUp)
import React.Basic.Helpers (jsx, orUndefined)
import React.Basic.Hooks (ReactComponent, component, useState)
import React.Basic.Hooks as React
@ -32,7 +32,7 @@ makeComponent = do
useStyles <- makeStylesJSS Style.styles
component "ClickAway" \props -> React.do
cs <- useStyles (pick props)
useKeyUp 27 $ ifJustTrue props.allowEscape props.onClick
useKeyUp Escape $ ifJustTrue props.allowEscape props.onClick
animationDone /\ modifyAnimationDone <- useState false
pure
$ jsx imposter

View File

@ -6,11 +6,11 @@ import Justifill (justifill)
import React.TestingLibrary (describeComponent, renderComponent)
import Test.Spec (Spec, it)
import Yoga.ClickAway.Component as ClickAway
import Yoga.Spec.Helpers (withDarkTheme)
import Yoga.Spec.Helpers (withSpecTheme)
spec ∷ Spec Unit
spec =
describeComponent (withDarkTheme ClickAway.makeComponent)
describeComponent (withSpecTheme ClickAway.makeComponent)
"The ClickAway Component" do
it "renders without problems" \clickaway -> do
_ <-

View File

@ -9,11 +9,11 @@ import React.TestingLibrary (describeComponent, fireEventClick, renderComponent)
import Test.Spec (Spec, it)
import Test.Spec.Assertions (shouldEqual)
import Yoga.CloseIcon.Component as CloseIcon
import Yoga.Spec.Helpers (withDarkTheme)
import Yoga.Spec.Helpers (withSpecTheme)
spec ∷ Spec Unit
spec =
describeComponent (withDarkTheme CloseIcon.makeComponent)
describeComponent (withSpecTheme CloseIcon.makeComponent)
"The CloseIcon Component" do
it "renders without problems" \closeicon -> do
_ <-

View File

@ -13,9 +13,9 @@ import React.Basic.Hooks as React
import Unsafe.Coerce (unsafeCoerce)
import Web.DOM (Node)
import Web.DOM.Element (clientHeight)
import Web.HTML (window)
import Web.HTML (HTMLElement, window)
import Web.HTML.HTMLDocument as Document
import Web.HTML.HTMLElement (DOMRect, getBoundingClientRect)
import Web.HTML.HTMLElement (DOMRect, focus, getBoundingClientRect)
import Web.HTML.HTMLElement as HTMLElement
import Web.HTML.Window (document)
@ -28,7 +28,6 @@ newtype UseBoundingBox hooks
)
derive instance ntUseBoundingBox ∷ Newtype (UseBoundingBox hooks) _
useBoundingBox ∷ Hook UseBoundingBox (Maybe DOMRect /\ Ref (Nullable Node))
useBoundingBox =
coerceHook React.do
@ -48,7 +47,6 @@ newtype UseViewportHeight hooks
= UseViewportHeight (UseLayoutEffect Unit (UseState (Maybe Number) hooks))
derive instance ntUseViewportHeight ∷ Newtype (UseViewportHeight hooks) _
useViewportHeight ∷ Hook UseViewportHeight (Maybe Number)
useViewportHeight =
coerceHook React.do
@ -64,3 +62,20 @@ useViewportHeight =
modifyViewportHeight (const $ Just ch)
pure (pure unit)
pure viewportHeight
newtype UseFocus hooks
= UseFocus (UseLayoutEffect Unit (UseRef (Nullable Node) (UseState Boolean hooks)))
derive instance ntUseFocus ∷ Newtype (UseFocus hooks) _
useFocus ∷ Hook UseFocus (Ref (Nullable Node))
useFocus =
coerceHook React.do
focussed /\ updateFocussed <- useState false
ref <- useRef Nullable.null
useLayoutEffect unit
$ mempty -- No callback
<* unless focussed do
maybeNode <- readRefMaybe ref
for_ (maybeNode >>= HTMLElement.fromNode) focus
updateFocussed (const true)
pure ref

View File

@ -2,25 +2,39 @@ module Yoga.FillInTheGaps.Component where
import Prelude
import Data.Array as A
import Data.Maybe (Maybe(..))
import Data.Monoid (guard)
import Data.Maybe (Maybe(..), isJust)
import Data.Newtype as NT
import Data.Nullable (Nullable)
import Data.Time.Duration (Milliseconds(..))
import Effect (Effect)
import Effect.Aff (delay, launchAff_)
import Effect.Class (liftEffect)
import Justifill (justifill)
import Literals.Undefined (undefined)
import React.Basic (JSX, ReactComponent, element)
import React.Basic.DOM as R
import React.Basic.Events (handler_)
import React.Basic.DOM.Events (preventDefault)
import React.Basic.Events (handler, handler_)
import React.Basic.Helpers (jsx)
import React.Basic.Hooks (component)
import React.Basic.Hooks (Ref, component)
import React.Basic.Hooks as React
import React.Basic.SyntaxHighlighter.Component (HighlighterTheme, syntaxHighlighterImpl)
import Yoga.Button.Component (ButtonType(..), mkButton)
import Record.Extra (pick)
import Unsafe.Coerce (unsafeCoerce)
import Web.DOM (Node)
import Yoga.Box.Component as Box
import Yoga.Button.Component (ButtonType(..), mkButtonWithProps)
import Yoga.Button.Component as Button
import Yoga.Cluster.Component as Cluster
import Yoga.FillInTheGaps.Logic (Segment(..), complete, updateSegments)
import Yoga.Helpers (ifJustTrue, (?||))
import Yoga.DOM.Hook (useFocus)
import Yoga.FillInTheGaps.Logic (Segment(..), complete, findFirstHoleIndex, holeToFiller, updateSegments)
import Yoga.FillInTheGaps.Styles (styles)
import Yoga.Helpers ((?||))
import Yoga.InlineCode.Component as InlineCode
import Yoga.Stack.Component as Stack
import Yoga.Theme.Styles (useTheme)
import Yoga.Theme.Styles (makeStylesJSS, useTheme)
import Yoga.Theme.Syntax (mkHighlighterTheme)
import Yoga.Theme.Types (CSSTheme)
visibleRange ∷ Array (Array Segment) -> { end ∷ Int, start ∷ Int }
visibleRange arr = { start, end }
@ -28,54 +42,87 @@ visibleRange arr = { start, end }
start = A.findIndex (_ == [ Start ]) arr ?|| 0
end = A.findIndex (_ == [ End ]) arr ?|| A.length arr
renderSegments ∷ Maybe Boolean -> HighlighterTheme -> ReactComponent InlineCode.Props -> ((Array (Array Segment) -> Array (Array Segment)) -> Effect Unit) -> Array (Array Segment) -> JSX
renderSegments readOnly highlighterTheme ic update arrs = R.div_ (A.mapWithIndex renderLine arrs)
renderSegments ∷ Milliseconds -> HighlighterTheme -> ReactComponent InlineCode.Props -> ((Array (Array Segment) -> Array (Array Segment)) -> Effect Unit) -> Array (Array Segment) -> JSX
renderSegments debounceBy highlighterTheme ic update arrs = R.div_ (A.mapWithIndex renderLine arrs)
where
firstHoleIndex = findFirstHoleIndex arrs
{ start, end } = visibleRange arrs
renderLine i l = R.div_ (A.mapWithIndex (renderSegment i) l)
renderSegment i j s =
if between start end i then case s of
Filler s' -> element syntaxHighlighterImpl { style: highlighterTheme, language: "purescript", children: s' }
Hole width text ->
element ic
$ justifill
{ width
, update: update <<< updateSegments i j
, text
, readOnly
}
_ -> mempty
else
mempty
renderSegment i j s = case s, between start end i of
Filler s', true ->
element
syntaxHighlighterImpl
{ style: highlighterTheme, language: "purescript", children: s' }
Hole width text, true ->
element ic
$ justifill
{ width
, update: update <<< updateSegments i j
, text
, focusOnFirstRender: firstHoleIndex <#> \fh -> fh.i == i && fh.j == j
}
_, _ -> mempty
type Props
= { segments ∷ Array (Array Segment)
, updateSegments ∷ (Array (Array Segment) -> Array (Array Segment)) -> Effect Unit
, incantate ∷ Effect Unit
, readOnly ∷ Maybe Boolean
, solvedWith ∷ Maybe String
}
makeComponent ∷ Effect (ReactComponent Props)
makeComponent = do
ic <- InlineCode.makeComponent
btn <- mkButton
btn <- mkButtonWithProps ∷ Button.WithProps ( ref ∷ Ref (Nullable Node) )
stack <- Stack.makeComponent
box <- Box.makeComponent
cluster <- Cluster.makeComponent
component "FillInTheGaps" \({ updateSegments, segments, incantate, readOnly } ∷ Props) -> React.do
highlighterTheme <- useTheme <#> mkHighlighterTheme
useStyles <- makeStylesJSS styles
component "FillInTheGaps" \(props@{ updateSegments, segments, incantate, solvedWith } ∷ Props) -> React.do
{ codeContainer, solutionContainer } <- useStyles (pick props)
theme ∷ CSSTheme <- useTheme
ref <- useFocus
let
highlighterTheme = mkHighlighterTheme theme
debounceBy = 16.6666667 # Milliseconds
onSubmitHandler _ =
launchAff_ do
delay (NT.over2 Milliseconds (+) debounceBy (5.0 # Milliseconds))
incantate # liftEffect
pure
$ jsx stack {}
[ renderSegments readOnly highlighterTheme ic updateSegments segments
, if Just true == readOnly then
mempty
else
jsx cluster {}
[ R.div_
[ jsx btn
{ onClick: handler_ incantate
, buttonType: if complete segments then HighlightedButton else DisabledButton
}
[ R.text "Incantate" ]
]
]
]
$ R.form
{ onSubmit: handler preventDefault onSubmitHandler
, children:
[ R.div
{ className: codeContainer
, children:
[ jsx box { className: codeContainer }
[ jsx stack {}
[ case solvedWith of
Nothing -> renderSegments debounceBy highlighterTheme ic updateSegments segments
Just _ -> renderSegments debounceBy highlighterTheme ic updateSegments (segments <#> map holeToFiller)
, case solvedWith of
Just solution ->
R.pre
{ className: solutionContainer
, children: [ R.text solution ]
}
Nothing ->
jsx cluster {}
[ R.div_
[ jsx btn
{ onClick: handler_ mempty
, buttonType: if complete segments then HighlightedButton else DisabledButton
, buttonProps: { ref: if isJust (findFirstHoleIndex segments) then unsafeCoerce undefined else ref }
}
[ R.text "Incantate" ]
]
]
]
]
]
}
]
}

View File

@ -34,14 +34,31 @@ data Segment
derive instance eqSegment ∷ Eq Segment
derive instance ordSegment ∷ Ord Segment
isHole ∷ Segment -> Boolean
isHole = case _ of
Hole _ _ -> true
_ -> false
holeToFiller ∷ Segment -> Segment
holeToFiller = case _ of
Hole _ text -> Filler text
other -> other
getResult ∷ Segment -> Maybe String
getResult = case _ of
ExpectedResult r -> Just r
ExpectedResult r -> Just $ S.replaceAll (S.Pattern ("\\n")) (S.Replacement "\n") r
_ -> Nothing
findResult ∷ Array Segment -> Maybe String
findResult = A.findMap getResult
findFirstHoleIndex ∷ Array (Array Segment) -> Maybe { i ∷ Int, j ∷ Int }
findFirstHoleIndex lines = do
i <- A.findIndex (map isHole >>> A.elem true) lines
line <- lines A.!! i
j <- A.findIndex isHole line
pure { i, j }
toCode ∷ Array (Array Segment) -> String
toCode lines = intercalate "\n" mapped
where

View File

@ -33,7 +33,7 @@ makeWrapper = do
{ segments
, updateSegments
, incantate: mempty
, readOnly: Just false
, solvedWith: Nothing
}
codeWithHoles =

View File

@ -1,6 +1,8 @@
module Yoga.FillInTheGaps.Styles where
import Prelude hiding (top)
import CSS (backgroundColor, borderRadius, color, fontSize, fontStyle)
import CSS.FontStyle (italic)
import JSS (JSSClasses, JSSElem, jssClasses)
import Yoga.Theme.Types (YogaTheme)
@ -11,13 +13,20 @@ type Props
= Record PropsR
type Classes a
= ( blue ∷ a
, green ∷ a
= ( codeContainer ∷ a
, solutionContainer ∷ a
)
styles ∷ JSSClasses YogaTheme Props (Classes (JSSElem Props))
styles =
jssClasses \theme ->
{ blue: { color: theme.blue }
, green: { color: theme.green }
jssClasses \theme@{ s0 } ->
{ codeContainer:
do
borderRadius s0 s0 s0 s0
backgroundColor theme.backgroundColourDarker
, solutionContainer:
do
fontStyle italic
fontSize theme.s1
color theme.highlightColour
}

View File

@ -0,0 +1,33 @@
module Yoga.Grid.Component where
import Prelude
import Data.Foldable (fold, intercalate)
import Data.Maybe (Maybe)
import Effect (Effect)
import React.Basic (JSX, ReactComponent)
import React.Basic.DOM as R
import React.Basic.Hooks (component)
import React.Basic.Hooks as React
import Record.Extra (pick)
import Yoga.Grid.Styles (styles)
import Yoga.Grid.Styles as Style
import Yoga.Theme.Styles (makeStylesJSS, useTheme)
import Yoga.Theme.Types (CSSTheme)
type Props
= { kids ∷ Array JSX
, className ∷ Maybe String
| Style.PropsR
}
makeComponent ∷ Effect (ReactComponent Props)
makeComponent = do
useStyles <- makeStylesJSS styles
component "Grid" \(props@{ kids, className } ∷ Props) -> React.do
{ grid } <- useStyles (pick props)
theme ∷ CSSTheme <- useTheme
pure
$ R.div
{ className: grid
, children: kids
}

View File

@ -0,0 +1,20 @@
module Yoga.Grid.Spec where
import Prelude
import Justifill (justifill)
import React.Basic.DOM as R
import React.TestingLibrary (describeComponent, renderComponent)
import Test.Spec (Spec, it)
import Yoga.Grid.Component as Grid
import Yoga.Spec.Helpers (withSpecTheme)
spec ∷ Spec Unit
spec =
describeComponent (withSpecTheme Grid.makeComponent)
"The Grid Component" do
it "renders without problems" \grid -> do
_ <-
renderComponent grid
$ justifill
{}
pure unit

View File

@ -0,0 +1,59 @@
module Yoga.Grid.Stories where
import Prelude hiding (add)
import Data.Array (mapWithIndex, replicate, (..))
import Effect (Effect)
import Effect.Unsafe (unsafePerformEffect)
import Justifill (justifill)
import React.Basic.DOM (css)
import React.Basic.DOM as R
import React.Basic.Helpers (jsx)
import React.Basic.Hooks (component, element)
import Storybook.Decorator.FullScreen (fullScreenDecorator)
import Storybook.React (Storybook, add, addDecorator, storiesOf)
import Yoga.Box.Component as Box
import Yoga.Card.Component (mkCard)
import Yoga.Centre.Component as Centre
import Yoga.Grid.Component as Grid
import Yoga.Stack.Component as Stack
stories ∷ Effect Storybook
stories = do
storiesOf "Grid" do
addDecorator fullScreenDecorator
add "The Grid" mkExample
[ justifill
{ kids:
(1 .. 11)
<#> \i ->
R.div
{ style:
css
{ background: "url(" <> src i <> ")"
, width: "100%"
, height: "200px"
, backgroundSize: "cover"
}
}
, minWidth: "200px"
}
]
where
mkExample = do
box <- Box.makeComponent
grid <- Grid.makeComponent
centre <- Centre.makeComponent
card <- mkCard
component "ExampleGrid" \(props ∷ Grid.Props) -> React.do
let
kids = props.kids <#> \kid -> jsx card {} [ kid ]
pure
$ R.div
{ style:
css { width: "100vw" }
, children:
[ jsx box {} [ element grid (props { kids = kids }) ]
]
}
src seed = "https://picsum.photos/200?random=" <> show seed

View File

@ -0,0 +1,30 @@
module Yoga.Grid.Styles where
import Prelude hiding (top)
import Data.Interpolate (i)
import Data.Maybe (Maybe)
import JSS (JSSClasses, JSSElem, jssClasses)
import Yoga.Helpers ((?||))
import Yoga.Theme.Types (YogaTheme)
type PropsR
= ( minWidth ∷ Maybe String
)
type Props
= Record PropsR
type Classes a
= ( grid ∷ a
)
styles ∷ JSSClasses YogaTheme Props (Classes (JSSElem Props))
styles =
jssClasses \theme@{ s0 } ->
{ grid:
\{ minWidth } ->
{ display: "grid"
, gridGap: "1rem"
, gridTemplateColumns: i "repeat(auto-fit, minmax(min(" (minWidth ?|| "250px") ", 100%), 1fr))" ∷ String
}
}

View File

@ -0,0 +1,25 @@
module Yoga.Grimoire.Component where
import Prelude
import Effect (Effect)
import React.Basic (ReactComponent)
import React.Basic.DOM as R
import React.Basic.Hooks (component)
import React.Basic.Hooks as React
import Record.Extra (pick)
import Yoga.Grimoire.Styles (styles)
import Yoga.Theme.Styles (makeStylesJSS, useTheme)
import Yoga.Theme.Types (CSSTheme)
type Props
= {
}
makeComponent ∷ Effect (ReactComponent Props)
makeComponent = do
useStyles <- makeStylesJSS styles
component "Grimoire" \(props@{} ∷ Props) -> React.do
{} <- useStyles (pick props)
theme ∷ CSSTheme <- useTheme
pure
$ R.div_ [ R.text "WriteMe" ]

View File

@ -0,0 +1,18 @@
module Yoga.Grimoire.Stories where
import Prelude hiding (add)
import Effect (Effect)
import Justifill (justifill)
import React.Basic.DOM as R
import Storybook.Decorator.FullScreen (fullScreenDecorator)
import Storybook.React (Storybook, add, addDecorator, storiesOf)
import Yoga.Grimoire.Component as Grimoire
stories ∷ Effect Storybook
stories = do
storiesOf "Grimoire" do
addDecorator fullScreenDecorator
add "The Grimoire" Grimoire.makeComponent
[ justifill
{}
]

View File

@ -0,0 +1,25 @@
module Yoga.Grimoire.Styles where
import Prelude hiding (top)
import CSS (backgroundColor, borderRadius)
import JSS (JSSClasses, JSSElem, jssClasses)
import Yoga.Theme.Types (YogaTheme)
type PropsR
= ()
type Props
= Record PropsR
type Classes a
= ( container ∷ a
)
styles ∷ JSSClasses YogaTheme Props (Classes (JSSElem Props))
styles =
jssClasses \theme@{ s0 } ->
{ container:
do
borderRadius s0 s0 s0 s0
backgroundColor theme.backgroundColourDarker
}

View File

@ -2,15 +2,14 @@ module Yoga.InlineCode.Component where
import Prelude
import Data.Foldable (fold, intercalate)
import Data.Maybe (Maybe)
import Data.Nullable (toNullable)
import Data.Nullable as Nullable
import Data.Maybe (Maybe(..))
import Data.Time.Duration (Milliseconds(..))
import Data.Tuple.Nested ((/\))
import Effect (Effect)
import Effect.Aff (delay)
import Effect.Class (liftEffect)
import Foreign.Object as Obj
import Literals.Undefined (undefined)
import React.Basic.DOM as R
import React.Basic.DOM.Events (targetValue)
import React.Basic.Events (handler)
@ -19,6 +18,7 @@ import React.Basic.Hooks as React
import React.Basic.Hooks.Aff (useAff)
import Record.Extra (pick)
import Unsafe.Coerce (unsafeCoerce)
import Yoga.DOM.Hook (useFocus)
import Yoga.Helpers ((?||))
import Yoga.InlineCode.Styles (styles)
import Yoga.InlineCode.Styles as Styles
@ -35,28 +35,32 @@ type OptionalProps r
, text ∷ Maybe String
, className ∷ Maybe String
, readOnly ∷ Maybe Boolean
, debounceBy ∷ Maybe Milliseconds
, focusOnFirstRender ∷ Maybe Boolean
| r
)
makeComponent ∷ Effect (ReactComponent Props)
makeComponent = do
useStyles <- makeStylesJSS styles
component "InlineCode" \props@{ className, text, update, readOnly } -> React.do
component "InlineCode" \props@{ text, update } -> React.do
value /\ modifyValue <- useState (text ?|| "")
classes <- useStyles $ pick props
ref <- useFocus
useAff value do
delay (200.0 # Milliseconds)
delay $ props.debounceBy ?|| (16.667 # Milliseconds)
update value # liftEffect
pure
$ R.div
{ className: classes.form
{ className: classes.container
, children:
[ R.input
{ className: intercalate " " [ classes.inlinecode, fold className ]
{ className: intercalate " " [ classes.inlinecode, fold props.className ]
, maxLength: props.width ?|| 10
, value
, readOnly: readOnly ?|| false
, disabled: readOnly ?|| false
, ref: if props.focusOnFirstRender == Just true then ref else unsafeCoerce undefined
, readOnly: props.readOnly ?|| false
, disabled: props.readOnly ?|| false
, spellCheck: false
, autoComplete: unsafeCoerce "false"
, autoCorrect: "off"

View File

@ -4,7 +4,7 @@ import Prelude
import Data.Maybe (Maybe(..))
import Data.Tuple.Nested ((/\))
import Effect (Effect)
import Effect.Aff (Aff)
import Effect.Aff (Aff, Milliseconds(..))
import Effect.Class (liftEffect)
import Effect.Ref (Ref)
import Effect.Ref as Ref
@ -12,13 +12,11 @@ import Justifill (justifill)
import React.Basic.Extra.Hooks.UseAffReducer (useAffReducer)
import React.Basic.Hooks (ReactComponent, component, element, useEffect)
import React.Basic.Hooks as React
import React.TestingLibrary (describeComponent, fireEventSubmit, renderComponent, typeText)
import React.TestingLibrary (describeComponent, renderComponent)
import Test.Spec (Spec, it)
import Test.Spec.Assertions (shouldEqual)
import Web.Event.Internal.Types (Event)
import Web.HTML.HTMLElement (focus)
import Yoga.InlineCode.Component as InlineCode
import Yoga.Spec.Helpers (withDarkTheme)
import Yoga.Spec.Helpers (withSpecTheme)
foreign import newInputEvent ∷ String -> Event
@ -26,21 +24,21 @@ foreign import newChangeEvent ∷ Event
spec ∷ Spec Unit
spec =
describeComponent (withDarkTheme mkWrapper)
describeComponent (withSpecTheme mkWrapper)
"The InlineCode Component" do
it "renders without problems" \wrapper -> do
strRef <- Ref.new "" # liftEffect
void $ renderComponent wrapper { strRef }
it "performs actions" \wrapper -> do
strRef <- Ref.new "" # liftEffect
{ findByTestId } <- renderComponent wrapper { strRef }
input <- findByTestId "inline-code"
focus input # liftEffect
typeText "Heinzelmän" input
fireEventSubmit input
refContent <- Ref.read strRef # liftEffect
refContent `shouldEqual` "Heinzelmän"
-- it "performs actions" \wrapper -> do
-- strRef <- Ref.new "" # liftEffect
-- { findByTestId } <- renderComponent wrapper { strRef }
-- input <- findByTestId "inline-code"
-- focus input # liftEffect
-- typeText "Heinzelmän" input
-- fireEventSubmit input
-- refContent <- Ref.read strRef # liftEffect
-- refContent `shouldEqual` "Heinzelmän"
data Action
= InlineCodeAction String
@ -61,5 +59,6 @@ mkWrapper = do
$ element inlineCode
( justifill
{ update: dispatch <<< InlineCodeAction
, debounceBy: 0.0 # Milliseconds
}
)

View File

@ -1,10 +1,10 @@
module Yoga.InlineCode.Styles where
import Prelude
import CSS (GenericFontFamily(..), Selector, TimingFunction(..), animation, background, border, borderBottom, borderBox, borderRadius, boxSizing, color, darken, display, element, focus, fontFamily, fontSize, fromString, inlineBlock, iterationCount, keyframes, lighten, lineHeight, nil, padding, sec, solid, transform, transition, unitless, width, (!*), (!+), (&), (?))
import CSS (GenericFontFamily(..), Selector, TimingFunction(..), animation, background, border, borderBox, borderRadius, boxSizing, color, display, element, focus, fontFamily, fontSize, fromString, inlineBlock, iterationCount, keyframes, lineHeight, nil, padding, sec, solid, transform, unitless, width, (!*), (!+), (&), (?))
import CSS.Animation (forwards, normalAnimationDirection)
import CSS.Common (baseline, middle)
import CSS.Overflow (hidden, overflow, visible)
import CSS.Common (baseline)
import CSS.Overflow (overflow, visible)
import CSS.Size (ch)
import CSS.Transform (scale3d)
import CSS.VerticalAlign (verticalAlign)
@ -30,13 +30,13 @@ type Props
styles ∷
JSSClasses YogaTheme Props
( inlinecode ∷ JSSElem Props
, form ∷ JSSElem Props
, container ∷ JSSElem Props
, "@keyframes plop" ∷ JSSElem Props
)
styles = jssClasses go
where
go (theme@{ s0, s1, s_1, s_2, s_3, s_4, s_5 } ∷ CSSTheme) =
{ form:
{ container:
do
display inlineBlock
, "@keyframes plop":
@ -62,7 +62,7 @@ styles = jssClasses go
(NonEmpty (GenericFontFamily $ fromString "monospace") [])
fontSize (s0)
lineHeight (s0)
width $ (props.width ?|| 10 # toNumber # ch) !+ (unitless 4.2 !* s_5)
width $ (props.width ?|| 10 # toNumber # ch) !+ (unitless 4.3 !* s_5)
padding nil s_5 nil s_5
color theme.textColour
this & focus

View File

@ -6,11 +6,11 @@ import React.Basic.DOM as R
import React.TestingLibrary (describeComponent, renderComponent)
import Test.Spec (Spec, it)
import Yoga.Modal.Component as Modal
import Yoga.Spec.Helpers (withDarkTheme)
import Yoga.Spec.Helpers (withSpecTheme)
spec ∷ Spec Unit
spec =
describeComponent (withDarkTheme Modal.makeComponent)
describeComponent (withSpecTheme Modal.makeComponent)
"The Modal Component" do
it "renders without problems" \modal -> do
_ <-

View File

@ -1,14 +1,17 @@
module Yoga.Spec.Helpers where
import Prelude
import CSS (rem)
import Color as Color
import Effect (Effect)
import JSS (jss)
import Prim.Row (class Lacks)
import React.Basic.Hooks (ReactComponent, component, element)
import Yoga.Font (FontFamily)
import Yoga.Theme (fromTheme)
import Yoga.Theme.CSSBaseline (mkCssBaseline)
import Yoga.Theme.Default (darkTheme, lightTheme)
import Yoga.Theme.Provider (mkThemeProvider)
import Yoga.Theme.Types (CSSTheme)
import Yoga.Theme.Types (CSSTheme, Theme)
withTheme ∷
∀ props.
@ -20,7 +23,7 @@ withTheme ∷
Effect (ReactComponent { | props })
withTheme theme mkComp = do
themeProvider <- mkThemeProvider
baseline <- mkCssBaseline
baseline <- mkCssBaseline (jss ([] ∷ _ FontFamily))
comp <- mkComp
component "ThemeWrapper" \(props ∷ { | props }) -> React.do
pure
@ -29,20 +32,35 @@ withTheme theme mkComp = do
, children: [ element baseline { kids: [ element comp props ] } ]
}
withDarkTheme ∷
∀ props.
Lacks "children" props =>
Lacks "ref" props =>
Lacks "key" props =>
Effect (ReactComponent (Record props)) ->
Effect (ReactComponent (Record props))
withDarkTheme = withTheme (fromTheme darkTheme)
-- Remove fonts because they require webpack to load
specTheme ∷ Theme
specTheme =
{ backgroundColour: Color.hsl 238.0 0.18 0.20
, textColour: Color.hsl 225.0 0.28 0.90
, interfaceColour: Color.hsl 225.0 0.48 0.12
, highlightColour: Color.hsl 285.0 0.88 0.72
, altHighlightColour: Color.hsl 84.0 0.617 0.631
, textFontFamily: pure "sans-serif"
, headingFontFamily: pure "sans-serif"
, codeFontFamily: pure "monospace"
, yellow: Color.hsl 36.0 0.82 0.76
, green: Color.hsl 84.0 0.617 0.631
, purple: Color.hsl 276.0 0.677 0.745
, red: Color.rgb 255 88 116
, blue: Color.rgb 130 170 255
, grey: Color.rgb 150 150 150
, white: Color.rgb 250 250 250
, measure: "60ch"
, borderThin: "0.125rem"
, ratio: 1.5
, s0: 1.0 # rem
}
withLightTheme ∷
withSpecTheme ∷
∀ props.
Lacks "children" props =>
Lacks "ref" props =>
Lacks "key" props =>
Effect (ReactComponent (Record props)) ->
Effect (ReactComponent (Record props))
withLightTheme = withTheme (fromTheme lightTheme)
withSpecTheme = withTheme (fromTheme specTheme)

View File

@ -0,0 +1,27 @@
module Yoga.Template.Component where
import Prelude
import Effect (Effect)
import React.Basic (ReactComponent)
import React.Basic.DOM as R
import React.Basic.Hooks (component)
import React.Basic.Hooks as React
import Record.Extra (pick)
import Yoga.Template.Styles (styles)
import Yoga.Template.Styles as Style
import Yoga.Theme.Styles (makeStylesJSS, useTheme)
import Yoga.Theme.Types (CSSTheme)
type Props
= {
| Style.PropsR
}
makeComponent ∷ Effect (ReactComponent Props)
makeComponent = do
useStyles <- makeStylesJSS styles
component "Template" \(props@{} ∷ Props) -> React.do
{} <- useStyles (pick props)
theme ∷ CSSTheme <- useTheme
pure
$ R.div_ [ R.text "WriteMe" ]

View File

@ -0,0 +1,20 @@
module Yoga.Template.Spec where
import Prelude
import Justifill (justifill)
import React.Basic.DOM as R
import React.TestingLibrary (describeComponent, renderComponent)
import Test.Spec (Spec, it)
import Yoga.Template.Component as Template
import Yoga.Spec.Helpers (withSpecTheme)
spec ∷ Spec Unit
spec =
describeComponent (withSpecTheme Template.makeComponent)
"The Template Component" do
it "renders without problems" \template -> do
_ <-
renderComponent template
$ justifill
{}
pure unit

View File

@ -0,0 +1,18 @@
module Yoga.Template.Stories where
import Prelude hiding (add)
import Effect (Effect)
import Justifill (justifill)
import React.Basic.DOM as R
import Storybook.Decorator.FullScreen (fullScreenDecorator)
import Storybook.React (Storybook, add, addDecorator, storiesOf)
import Yoga.Template.Component as Template
stories ∷ Effect Storybook
stories = do
storiesOf "Template" do
addDecorator fullScreenDecorator
add "The Template" Template.makeComponent
[ justifill
{}
]

View File

@ -0,0 +1,25 @@
module Yoga.Template.Styles where
import Prelude hiding (top)
import CSS (backgroundColor, borderRadius)
import JSS (JSSClasses, JSSElem, jssClasses)
import Yoga.Theme.Types (YogaTheme)
type PropsR
= ()
type Props
= Record PropsR
type Classes a
= ( container ∷ a
)
styles ∷ JSSClasses YogaTheme Props (Classes (JSSElem Props))
styles =
jssClasses \theme@{ s0 } ->
{ container:
do
borderRadius s0 s0 s0 s0
backgroundColor theme.backgroundColourDarker
}

View File

@ -9,15 +9,14 @@ import JSS (JSSClasses, JSSElem, jss, jssClasses)
import React.Basic (ReactComponent)
import React.Basic.Hooks (JSX, component, fragment)
import React.Basic.Hooks as React
import Yoga.Font.Rubik as Rubik
import Yoga.Font.VictorMono as VictorMono
import Yoga.Theme.Styles (makeStylesJSS)
import Yoga.Theme.Types (YogaTheme, CSSTheme)
mkCssBaseline ∷
JSSElem {} ->
Effect (ReactComponent { kids ∷ Array JSX })
mkCssBaseline = do
useStyles <- makeStylesJSS styles
mkCssBaseline fontFaces = do
useStyles <- makeStylesJSS (styles fontFaces)
component "CSSBaseline" \{ kids } -> React.do
classes <- useStyles {}
pure
@ -48,13 +47,13 @@ root theme =
declare theme.s4Var
declare theme.s5Var
styles ∷ JSSClasses YogaTheme {} ( "@global" ∷ JSSElem {} )
styles =
styles ∷ JSSElem {} -> JSSClasses YogaTheme {} ( "@global" ∷ JSSElem {} )
styles fontFaces =
jssClasses \theme ->
{ "@global":
jss
{ html
, "@font-face": jss (Rubik.fontFamilies <> VictorMono.fontFamilies)
, "@font-face": fontFaces
, ":root": root theme
, "*":
{ maxWidth: theme.measure

View File

@ -5,7 +5,10 @@ import CSS (rem)
import Color as Color
import Data.Array.NonEmpty (cons')
import Data.Maybe (fromMaybe')
import JSS (JSSElem, jss)
import Partial.Unsafe (unsafeCrashWith)
import Yoga.Font.Rubik as Rubik
import Yoga.Font.VictorMono as VictorMono
import Yoga.Theme.Types (Theme)
systemFontStack ∷ Array String
@ -14,6 +17,9 @@ systemFontStack = [ "-apple-system", "BlinkMacSystemFont", "Helvetica", "Arial",
hex ∷ String -> Color.Color
hex c = c # Color.fromHexString # fromMaybe' \_ -> unsafeCrashWith $ "Invalid hex string " <> c
fontFaces ∷ JSSElem {}
fontFaces = jss (Rubik.fontFamilies <> VictorMono.fontFamilies)
darkTheme ∷ Theme
darkTheme =
{ backgroundColour: Color.hsl 238.0 0.18 0.20

View File

@ -2,6 +2,9 @@
var reactJss = require("react-jss");
exports.makeStylesWithPropsImpl = styles => () => props => () =>
reactJss.createUseStyles(styles)(props);
exports.makeStylesWithPropsImpl = (styles) => () => {
const useStyles = reactJss.createUseStyles(styles);
// For injection order this needs to be run now!
return (props) => () => useStyles(props);
};
exports.useThemeImpl = reactJss.useTheme;

View File

@ -7,8 +7,8 @@ import Test.Spec.Discovery (discover)
import Test.Spec.Reporter (consoleReporter)
import Test.Spec.Runner (runSpec)
main :: Effect Unit
main =
main Effect Unit
main = do
launchAff_ do
specs <- discover ".*Spec"
runSpec [ consoleReporter ] specs

File diff suppressed because one or more lines are too long