Finally add a test, it still pukes out some rubbish but it works

This commit is contained in:
Mark Eibes 2020-03-29 00:14:15 +01:00
parent 15d51528b6
commit 6d7f609db0
33 changed files with 15433 additions and 349 deletions

Binary file not shown.

Binary file not shown.

14895
components/package-lock.json generated Normal file

File diff suppressed because it is too large Load Diff

View File

@ -38,11 +38,12 @@
"devDependencies": {
"@babel/core": "^7.6.0",
"@storybook/react": "^5.2.0",
"@testing-library/react": "^9.1.4",
"@testing-library/react": "^9.5.0",
"@testing-library/user-event": "^10.0.1",
"babel-loader": "^8.0.6",
"css-loader": "^3.2.0",
"deep-equal": "^1.1.0",
"jsdom": "^15.1.1",
"jsdom": "^16.2.1",
"jsdom-global": "^3.0.2",
"monaco-editor": "^0.20.0",
"monaco-editor-webpack-plugin": "^1.8.2",
@ -51,8 +52,8 @@
"purescript-psa": "^0.7.3",
"purs-loader": "^3.6.0",
"purty": "^4.5.1",
"react": "^16.9.0",
"react-dom": "^16.9.0",
"react": "^16.13.1",
"react-dom": "^16.13.1",
"react-hot-loader": "^4.12.15",
"react-monaco-editor": "^0.33.0",
"react-svg-loader": "^3.0.3",

View File

@ -19,6 +19,7 @@ You can edit this file as you like.
, "react-basic-hooks"
, "react-testing-library"
, "record-extra"
, "refs"
, "spec-discovery"
, "string-parsers"
, "web-html"

View File

@ -0,0 +1,37 @@
module React.Basic.Extra.Hooks where
import Prelude
import Data.Foldable (for_)
import Data.Maybe (Maybe(..))
import Data.Newtype (class Newtype)
import Data.Tuple (Tuple)
import Effect (Effect)
import Effect.Aff (Aff)
import Effect.Class (liftEffect)
import React.Basic.Hooks (Hook, UseState, coerceHook, useState, (/\))
import React.Basic.Hooks as React
import React.Basic.Hooks.Aff (UseAff, useAff)
newtype UseAffReducer state action hooks
= UseAffReducer
( UseAff (Maybe action) Unit
( UseState (Maybe action)
(UseState state hooks)
)
)
derive instance ntUseAffReducer ∷ Newtype (UseAffReducer state action hooks) _
useAffReducer ∷ ∀ state action. Eq action => state -> (state -> action -> Aff state) -> Hook (UseAffReducer state action) (Tuple state (action -> Effect Unit))
useAffReducer initialState reducer =
coerceHook React.do
state /\ modifyState <- useState initialState
maybeAction /\ modifyAction <- useState Nothing
let
dispatch = modifyAction <<< const <<< Just
useAff maybeAction
$ for_ maybeAction \action -> do
newState <- reducer state action
liftEffect do
modifyState (const newState)
modifyAction (const Nothing)
pure (state /\ dispatch)

View File

@ -6,19 +6,20 @@ 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)
spec :: Spec Unit
spec Spec Unit
spec =
describeComponent Box.makeComponent
describeComponent (withDarkTheme Box.makeComponent)
"The Box Component" do
it "renders without problems" \stack -> do
_ <-
renderComponent stack
( justifill
{ kids:
[ R.h1_ [ R.text "Living in a Box" ]
, R.h2_ [ R.text "Living in a Card, Board, Box" ]
]
[ R.h1_ [ R.text "Living in a Box" ]
, R.h2_ [ R.text "Living in a Card, Board, Box" ]
]
, padding: "12rem"
}
)

View File

@ -1,7 +1,7 @@
module Yoga.Button.Component where
import Prelude
import CSS (Color, ColorSpace(..), mix, toHexString)
import CSS (Color, cssStringRGBA, desaturate)
import CSS as Color
import Data.Foldable (intercalate)
import Data.Interpolate (i)
@ -15,7 +15,7 @@ import React.Basic.Events (EventHandler)
import React.Basic.Hooks (ReactComponent, component)
import React.Basic.Hooks as React
import Yoga.Helpers ((?||))
import Yoga.Theme (increaseContrast, unsafeWithAlpha)
import Yoga.Theme (withAlpha)
import Yoga.Theme.Styles (makeStylesJSS)
import Yoga.Theme.Types (CSSTheme, YogaTheme)
@ -38,29 +38,15 @@ highlightStyles =
{ highlightedButton:
{ background:
linearGradient
( if theme.isLight then
"180deg"
else
"0deg"
)
[ do
let
col = theme.highlightColourRotatedBackwards
{ r, g, b, a } = Color.toRGBA (Color.saturate (10.0) col)
Color.rgba r g b 0.5
, do
let
col = theme.highlightColourRotatedForwards
{ r, g, b, a } = Color.toRGBA (Color.saturate (10.0) col)
Color.rgba r g b 0.5
"135deg"
[ withAlpha (if theme.isLight then 0.15 else 0.07) theme.backgroundColourDarker
, withAlpha (if theme.isLight then 0.15 else 0.07) theme.backgroundColourLighter
]
, "&:active":
{ background:
linearGradient "145deg" [ theme.highlightColourDark, theme.highlightColour ]
}
, color: Color.white
, color: theme.backgroundColour
}
}
@ -69,99 +55,103 @@ styles ∷
( "@keyframes gradientBG" ∷ JSSElem StyleProps
, btn ∷ JSSElem StyleProps
, buttonContainer ∷ JSSElem StyleProps
, disabled ∷ JSSElem StyleProps
)
styles =
jssClasses
$ \(theme ∷ CSSTheme) ->
{ buttonContainer:
{ padding: "var(--s-4)"
, background:
linearGradient "135deg"
[ theme.highlightColourRotatedBackwards
, theme.highlightColourRotatedForwards
]
, borderRadius: "var(--s1)"
, height: "calc(var(--s1) - var(--s1-3))"
, minWidth: "var(--s2)"
, boxSizing: "border-box"
, boxShadow:
( unsafeWithAlpha 0.15 "#000000"
)
<> " 0px 1px 2px 2px"
}
, "@keyframes gradientBG":
{ "0%": { backgroundPosition: "0% 50%" }
, "50%": { backgroundPosition: "100% 50%" }
, "100%": { backgroundPosition: "0% 50%" }
}
, btn:
{ width: "100%"
, background:
linearGradient "180deg"
[ Color.darken 0.05 theme.backgroundColour
, Color.darken 0.10 theme.backgroundColour
]
, color:
let
c = theme.highlightColour
in
if Color.isLight c then Color.rotateHue (-10.0) c else Color.lighten 0.2 c
, borderRadius: "var(--s1)"
, border: "0"
, height: "calc(var(--s2) + var(--s-4) - 2px)"
, fontSize: "calc(var(--s-1))"
, fontFamily: "Rubik Regular"
, fontWeight: "600"
, padding: "0 var(--s0) 0 var(--s0)"
, letterSpacing: "var(--s-5)"
, textTransform: "uppercase"
, outline: "none"
, "&:focus":
{ background:
linearGradient
"145deg"
[ theme.interfaceColourDarker
, theme.highlightColourDark
, theme.highlightColour
let
darken x = Color.darken x
lighten x = Color.lighten x
more amount x = if Color.isLight x then lighten amount x else darken amount x
less amount x = if Color.isLight x then darken amount x else lighten amount x
in
{ buttonContainer:
{ padding: "var(--s-4)"
, background:
linearGradient "225deg"
[ theme.highlightColourRotatedBackwards
, theme.highlightColourRotatedForwards
]
, borderRadius: "var(--s1)"
, height: "calc(var(--s1) - var(--s1-3))"
, minWidth: "var(--s2)"
, boxSizing: "border-box"
, boxShadow:
( cssStringRGBA (Color.rgba 0 0 0 0.15)
)
<> " 0 var(--s-5) var(--s-5) var(--s-5)"
}
, "@keyframes gradientBG":
{ "0%": { backgroundPosition: "0% 50%" }
, "50%": { backgroundPosition: "100% 50%" }
, "100%": { backgroundPosition: "0% 50%" }
}
, btn:
{ width: "calc(100%)"
, background:
linearGradient "80deg"
[ less 0.03 theme.backgroundColour
, less 0.05 theme.backgroundColour
]
, color:
do
let
hlc = theme.highlightColour
hlcd = theme.highlightColourDark
bg = if theme.isLight then hlc else mix HSL hlc hlcd 0.5
tc = theme.textColour
increaseContrast bg tc
, backgroundSize: "200% 400%, 100% 100%"
, animation: "$gradientBG 3s ease infinite"
let
c = theme.highlightColour
in
if Color.isLight c then Color.rotateHue (-10.0) c else Color.lighten 0.2 c
, borderRadius: "var(--s1)"
, border: "0"
, height: "calc(var(--s2))"
, fontSize: "calc(var(--s-1))"
, fontFamily: theme.textFontFamily
, fontWeight: "600"
, padding: "0 var(--s0) 0 var(--s0)"
, letterSpacing: "var(--s-5)"
, textTransform: "uppercase"
, outline: "none"
, "&:focus":
{ boxShadow:
( i "var(--s-4) 0 var(--s-2)"
(cssStringRGBA theme.highlightColourRotatedForwards)
", calc(-1 * var(--s-4)) 0 var(--s-2)"
(cssStringRGBA theme.highlightColourRotatedForwards)
", 0 calc(-1 * var(--s-4)) var(--s-2)"
(cssStringRGBA theme.highlightColourRotatedBackwards)
", 0 var(--s-4) var(--s-2)"
(cssStringRGBA theme.highlightColourRotatedBackwards)
) ∷
String
}
, "&:active":
{ boxShadow:
( i "inset var(--s-3) var(--s-3) var(--s-3) "
(cssStringRGBA $ darken 0.3 theme.backgroundColourDarker)
", inset calc(-1 * var(--s-3)) calc(-1 * -var(--s-3)) var(--s-3) "
(cssStringRGBA theme.backgroundColourDarkest)
) ∷
String
, background:
linearGradient
"145deg"
[ theme.backgroundColourDarker
, theme.backgroundColourDarkest
]
}
, "&:disabled":
{ boxShadow: "0 0 0 black"
, background: less 0.1 theme.backgroundColour
, color: less 0.2 theme.backgroundColour
}
}
, "&:active":
{ boxShadow:
( i "inset 6px 6px 6px "
(toHexString theme.backgroundColourDarkest)
", inset -6px -6px 6px "
(toHexString theme.backgroundColourLightest)
) ∷
String
, background:
linearGradient
"145deg"
[ theme.backgroundColourDarker
, theme.backgroundColourLighter
]
}
, "&:disabled":
{ boxShadow: "0 0 0 black"
, background: theme.grey
, border: "1px dotted " <> toHexString theme.interfaceColourLightest
, textDecoration: "line-through"
, textDecorationColor: theme.red
, "disabled":
{ background:
(cssStringRGBA $ less 0.1 theme.backgroundColour)
<> " !important"
}
}
}
type Props
= { kids ∷ Array JSX
@ -183,7 +173,7 @@ mkButton = do
className = props.className ?|| ""
pure
$ R.div
{ className: classes.buttonContainer
{ className: classes.buttonContainer <> " " <> if buttonType == DisabledButton then classes.disabled else ""
, children:
[ R.button
$ { className:
@ -200,4 +190,4 @@ mkButton = do
}
linearGradient ∷ String -> Array Color -> String
linearGradient direction elems = "linear-gradient(" <> direction <> "," <> intercalate "," (map toHexString elems) <> ")"
linearGradient direction elems = "linear-gradient(" <> direction <> "," <> intercalate "," (map cssStringRGBA elems) <> ")"

View File

@ -1,14 +1,19 @@
module Yoga.Card.Component where
import Prelude
import Color (toHexString)
import Color (cssStringRGBA, toHexString)
import Color as Color
import Data.Interpolate (i)
import Data.Maybe (Maybe)
import Effect (Effect)
import JSS (JSSClasses, JSSElem, jssClasses)
import React.Basic (JSX)
import React.Basic.DOM as R
import React.Basic.Helpers (jsx)
import React.Basic.Hooks (ReactComponent, component)
import React.Basic.Hooks as React
import Yoga.Box.Component as Box
import Yoga.Helpers ((?||))
import Yoga.Theme.Styles (makeStylesJSS)
import Yoga.Theme.Types (CSSTheme, YogaTheme)
@ -18,113 +23,45 @@ type StyleProps
styles ∷ JSSClasses YogaTheme StyleProps ( card ∷ JSSElem StyleProps )
styles =
jssClasses \(theme ∷ CSSTheme) ->
{ card:
{ background: (i "linear-gradient(145deg," (toHexString theme.backgroundColourDarker) ", " (toHexString theme.backgroundColourLighter) ")") ∷ String
, color: theme.textColour # toHexString
, fontFamily: theme.textFontFamily
, margin: "20px"
, boxShadow:
(i "30px 30px 60px " (toHexString theme.backgroundColourDarker) ", -30px -30px 60px " (toHexString theme.backgroundColourLighter) ";") ∷ String
, borderRadius: "15px"
, padding: "36px 40px 32px 40px"
let
lighten x = Color.lighten if theme.isLight then (0.5 * x) else 1.7 * x
darken x = Color.darken if theme.isLight then 1.0 * x else (1.2 * x)
in
{ card:
{ borderRadius: "var(--s1)"
, boxShadow:
( i -- bottom right
"var(--s1) var(--s1) var(--s2) "
(cssStringRGBA $ darken 0.04 theme.backgroundColour)
--bottom left
", calc(-1 * var(--s1)) var(--s1) var(--s2) "
(cssStringRGBA $ darken 0.01 theme.backgroundColour)
--top left
", calc(-1 * var(--s1)) calc(-1 * var(--s1)) var(--s2) "
(cssStringRGBA $ lighten 0.05 theme.backgroundColour)
--top right
", var(--s1) calc(-1 * var(--s1)) var(--s2) "
(cssStringRGBA $ darken 0.02 theme.backgroundColour)
) ∷
String
-- background: (i "linear-gradient(145deg," (toHexString theme.backgroundColourDarker) ", " (toHexString theme.backgroundColourLighter) ")") ∷ String
}
}
}
mkCard ∷
Effect
( ReactComponent
{ kids ∷ Array JSX
, className ∷ String
, className ∷ Maybe String
}
)
mkCard = do
useStyles <- makeStylesJSS styles
box <- Box.makeComponent
component "Card" \{ kids, className } -> React.do
classes <- useStyles {}
pure
$ R.div
{ className: classes.card <> " " <> className
, children: kids
}
mkCardTitle ∷
Effect
( ReactComponent
{ kids ∷ Array JSX
}
)
mkCardTitle = do
useStyles <-
makeStylesJSS
$ jssClasses \(theme ∷ CSSTheme) ->
{ cardtitle:
{ color: theme.textColourLightest # toHexString
, fontSize: "1.2em"
, fontWeight: "400"
, fontFamily: theme.headingFontFamily
, padding: "4px 8px toHexString"
}
}
component "CardTitle" \{ kids } -> React.do
classNames <- useStyles {}
pure
$ R.div
{ className: classNames.cardtitle
, children: kids
}
mkCardSubtitle ∷
Effect
( ReactComponent
{ kids ∷ Array JSX
}
)
mkCardSubtitle = do
useStyles <-
makeStylesJSS
$ jssClasses \(theme ∷ CSSTheme) ->
{ cardtitle:
{ color: theme.textColourDarker # toHexString
, opacity: "0.8"
, fontSize: "1.0em"
, fontWeight: "500"
, fontFamily: theme.headingFontFamily
, padding: "4px 8px 22px 8px"
}
}
component "CardSubtitle" \{ kids } -> React.do
classNames <- useStyles {}
pure
$ R.div
{ className: classNames.cardtitle
, children: kids
}
mkCardContent ∷
Effect
( ReactComponent
{ kids ∷ Array JSX
}
)
mkCardContent = do
useStyles <-
makeStylesJSS
$ jssClasses \(theme ∷ CSSTheme) ->
{ cardContent:
{ fontFamily: theme.textFontFamily
, color: theme.textColourDarker # toHexString
, fontSize: "0.8em"
, fontWeight: "300"
, "WebkitFontSmoothing": "subpixel-antialiased"
, textAlign: "justify"
, hyphens: "auto"
, padding: "4px 8px 22px 8px"
}
}
component "CardContent" \{ kids } -> React.do
classNames <- useStyles {}
pure
$ R.div
{ className: classNames.cardContent
, children: kids
}
$ jsx box
{ className: classes.card <> " " <> (className ?|| "") }
kids

View File

@ -1,12 +1,14 @@
module Yoga.Card.Stories where
import Prelude hiding (add)
import Yoga.Card.Component (mkCard, mkCardContent, mkCardSubtitle, mkCardTitle)
import Storybook.Decorator.FullScreen (fullScreenDecorator)
import Effect (Effect)
import React.Basic.DOM as R
import React.Basic.Hooks (component, element)
import React.Basic.Helpers (jsx)
import React.Basic.Hooks (component)
import Storybook.Decorator.FullScreen (fullScreenDecorator)
import Storybook.React (Storybook, add, addDecorator, storiesOf)
import Yoga.Box.Component as Box
import Yoga.Card.Component (mkCard)
stories ∷ Effect Storybook
stories = do
@ -20,24 +22,14 @@ stories = do
]
where
mkExample = do
box <- Box.makeComponent
card <- mkCard
cardTitle <- mkCardTitle
cardSubtitle <- mkCardSubtitle
cardContent <- mkCardContent
component "ExampleCard" \{ title, subtitle, content } -> React.do
pure
$ R.div
{ children:
pure
$ element card
{ kids:
[ element cardTitle { kids: [ R.text title ] }
, element cardSubtitle { kids: [ R.text subtitle ] }
, element cardContent { kids: [ content ] }
]
, className: ""
}
}
$ jsx box {}
[ jsx card {}
[ R.text "hi there!" ]
]
loremIpsum ∷ String
loremIpsum =

View File

@ -113,10 +113,10 @@ mkCompileEditor fetch = do
]
]
]
, element card
{ kids: [ R.text (compileResultToString compileResult) ]
, className: classes.card <> " " <> compileResultToClass compileResult
, jsx card
{ className: classes.card <> " " <> compileResultToClass compileResult
}
[ R.text (compileResultToString compileResult) ]
]
compileAndRun ∷ M.Fetch -> Body.CompileRequest -> Aff (Either Body.CompileResult Body.RunResult)

View File

@ -23,9 +23,9 @@ fontFamilies =
, fontWeight: "normal"
, fontStyle: "italic"
}
, { fontFamily: "Rubik Medium"
, { fontFamily: "Rubik"
, src: "url(" <> unsafeCoerce rubikMediumwoff2 <> """) format("woff2")"""
, fontWeight: "400"
, fontWeight: "600"
, fontStyle: "normal"
}
, { fontFamily: "Rubik"
@ -36,19 +36,19 @@ fontFamilies =
, { fontFamily: "Rubik"
, src: "url(" <> unsafeCoerce rubikItalicwoff2 <> """) format("woff2")"""
, fontWeight: "400"
, fontStyle: "normal"
, fontStyle: "italic"
}
, { fontFamily: "Rubik Light"
, { fontFamily: "Rubik"
, src: "url(" <> unsafeCoerce rubikLightwoff2 <> """) format("woff2")"""
, fontWeight: "400"
, fontWeight: "200"
, fontStyle: "normal"
}
, { fontFamily: "Rubik Light"
, { fontFamily: "Rubik"
, src: "url(" <> unsafeCoerce rubikLightItalicwoff2 <> """) format("woff2")"""
, fontWeight: "400"
, fontStyle: "italic"
}
, { fontFamily: "Rubik Regular"
, { fontFamily: "Rubik"
, src: "url(" <> unsafeCoerce rubikRegularwoff2 <> """) format("woff2")"""
, fontWeight: "normal"
, fontStyle: "normal"

View File

@ -1,4 +1,4 @@
exports.victorMonoMediumWoff2 = require("../../../assets/fonts/VictorMonoPureScript-Medium.woff2");
exports.victorMonoMediumWoff2 = require("../../../assets/fonts/VictorMonoPureScript-SemiBold.woff2");
exports.victorMonoBoldWoff2 = require("../../../assets/fonts/VictorMonoPureScript-Bold.woff2");
exports.victorMonoMediumItalicWoff2 = require("../../../assets/fonts/VictorMonoPureScript-MediumItalic.woff2");
exports.victorMonoBoldItalicWoff2 = require("../../../assets/fonts/VictorMonoPureScript-BoldItalic.woff2");
exports.victorMonoBoldItalicWoff2 = require("../../../assets/fonts/VictorMonoPureScript-SemiBoldItalic.woff2");

View File

@ -0,0 +1,60 @@
module Yoga.InlineCode.Component where
import Prelude
import Data.Foldable (fold, intercalate)
import Data.Maybe (Maybe)
import Data.Tuple.Nested ((/\))
import Effect (Effect)
import Effect.Class.Console (log)
import Foreign.Object as Obj
import React.Basic.DOM as R
import React.Basic.DOM.Events (preventDefault, targetValue)
import React.Basic.Events (handler)
import React.Basic.Hooks (ReactComponent, component, useState)
import React.Basic.Hooks as React
import Record.Extra (pick)
import Yoga.Helpers ((?||))
import Yoga.InlineCode.Styles (styles)
import Yoga.InlineCode.Styles as Styles
import Yoga.Theme.Styles (makeStylesJSS)
type Props
= Record PropsR
type PropsR
= OptionalProps (Styles.PropsR)
data Action
= CompileAndRunCode String
derive instance eqAction ∷ Eq Action
type OptionalProps r
= ( dispatch ∷ Action -> Effect Unit
, className ∷ Maybe String
| r
)
makeComponent ∷ Effect (ReactComponent Props)
makeComponent = do
useStyles <- makeStylesJSS styles
component "InlineCode" \props@{ className, dispatch } -> React.do
value /\ modifyValue <- useState ""
classes <- useStyles $ pick props
pure
$ R.form
{ children:
[ R.input
{ className: intercalate " " [ classes.inlinecode, fold className ]
, "type": "text"
, value
, onChange:
handler targetValue
( \v -> modifyValue $ const (v ?|| "")
)
, _data: Obj.singleton "testid" "inline-code"
}
]
, onSubmit:
handler preventDefault
(const (log ("dispatching " <> value) *> dispatch (CompileAndRunCode value)))
}

View File

@ -0,0 +1,5 @@
exports.newInputEvent = s => {
return new Event("input", { data: s, bubbles: true });
};
exports.newChangeEvent = new Event("change");

View File

@ -0,0 +1,64 @@
module Yoga.InlineCode.Spec where
import Prelude
import Data.Maybe (Maybe(..))
import Data.Tuple.Nested ((/\))
import Effect (Effect)
import Effect.Aff (Aff)
import Effect.Class (liftEffect)
import Effect.Class.Console (logShow)
import Effect.Ref (Ref)
import Effect.Ref as Ref
import React.Basic.Extra.Hooks (useAffReducer)
import React.Basic.Hooks (ReactComponent, component, element, useEffect)
import React.Basic.Hooks as React
import React.TestingLibrary (describeComponent, fireEventSubmit, renderComponent, typeText)
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
foreign import newInputEvent ∷ String -> Event
foreign import newChangeEvent ∷ Event
spec ∷ Spec Unit
spec =
describeComponent 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"
data Action
= InlineCodeAction InlineCode.Action
derive instance eqAction ∷ Eq Action
mkReducer ∷ Ref String -> Maybe String -> Action -> Aff (Maybe String)
mkReducer ref state = case _ of
InlineCodeAction (InlineCode.CompileAndRunCode s) -> do
Ref.write s ref # liftEffect
pure state
mkWrapper ∷ Effect (ReactComponent { strRef ∷ Ref String })
mkWrapper = do
inlineCode <- InlineCode.makeComponent
component "Wrapper" \{ strRef } -> React.do
state /\ dispatch <- useAffReducer Nothing (mkReducer strRef)
useEffect state (logShow state $> mempty)
pure
$ element inlineCode
( { dispatch: dispatch <<< InlineCodeAction
, className: Nothing
}
)

View File

@ -0,0 +1,20 @@
module Yoga.InlineCode.Stories where
import Prelude hiding (add)
import Data.Maybe (Maybe(..))
import Effect (Effect)
import Effect.Class.Console (log)
import React.Basic.DOM as R
import Storybook.Decorator.FullScreen (fullScreenDecorator)
import Storybook.React (Storybook, add, addDecorator, storiesOf)
import Yoga.InlineCode.Component as InlineCode
stories ∷ Effect Storybook
stories = do
storiesOf "InlineCode" do
addDecorator fullScreenDecorator
add "The InlineCode" InlineCode.makeComponent
[ { dispatch: const $ log "hi"
, className: Nothing
}
]

View File

@ -0,0 +1,23 @@
module Yoga.InlineCode.Styles where
import Prelude
import JSS (JSSClasses, JSSElem, jssClasses)
import Yoga.Theme.Types (YogaTheme)
type PropsR
= (
)
type Props
= Record PropsR
styles ∷
JSSClasses YogaTheme Props
( inlinecode ∷ JSSElem Props
)
styles =
jssClasses \theme ->
{ inlinecode:
\props ->
{}
}

View File

@ -2,7 +2,10 @@ module Yoga.Modal.Component where
import Prelude
import CSS (JustifyContentValue(..), spaceBetween)
import Data.Foldable (foldMap)
import Data.Maybe (Maybe)
import Effect (Effect)
import Foreign.Object as Obj
import React.Basic (JSX)
import React.Basic.DOM as R
import React.Basic.DOM.Events (stopPropagation)
@ -14,6 +17,7 @@ import React.Basic.Hooks as React
import Record.Extra (pick)
import Yoga.Box.Component as Box
import Yoga.Cluster.Component as Cluster
import Yoga.Helpers ((?||))
import Yoga.Imposter.Component as Imposter
import Yoga.Modal.Styles as Style
import Yoga.Stack.Component as Stack
@ -25,7 +29,7 @@ type Props
type PropsR
= ( title ∷ String
, content ∷ JSX
, onClose ∷ Effect Unit
, onClose ∷ Maybe (Effect Unit)
| Style.PropsR
)
@ -41,34 +45,34 @@ makeComponent = do
let
darkOverlay =
jsx imposter
{ className: cs.darkOverlay <> " animated fadeIn"
{ className: cs.darkOverlay <> " " <> cs.fadeIn
, fixed: true
, breakout: false
, onClick: handler_ props.onClose
, onClick: props.onClose ?|| mempty # handler_
}
dialogImposter =
jsx imposter
{ className: cs.dialog ∷ String
, onClick: handler stopPropagation (\_ -> pure unit)
{ className: cs.dialog
, onClick: handler stopPropagation mempty
, fixed: true
}
dialogBox =
jsx box
{ className: cs.box <> " animated lightSpeedIn"
, invert: true
} -- [TODO]: reconsider
{ className: cs.box <> " " <> cs.zoomIn
}
dialogBoxStack =
jsx stack
{ className: cs.dialogBoxStack ∷ String
{ className: cs.dialogBoxStack
}
titleCluster =
jsx cluster
{ className: cs.titleCluster ∷ String
{ className: cs.titleCluster
, justify: JustifyContentValue spaceBetween
, space: "0"
}
title =
@ -77,7 +81,7 @@ makeComponent = do
, R.div
{ className: cs.closeIcon
, children:
[ closeIcon (handler_ props.onClose) cs
[ props.onClose # foldMap (closeIcon cs <<< handler_)
]
}
]
@ -93,15 +97,16 @@ makeComponent = do
]
]
closeIcon ∷ ∀ a. EventHandler -> { closeIcon ∷ String | a } -> JSX
closeIcon onClick classes =
closeIcon ∷ ∀ a. { closeIcon ∷ String | a } -> EventHandler -> JSX
closeIcon classes onClick =
SVG.svg
{ xmlns: "http://www.w3.org/2000/svg"
, viewBox: "19 19 85 85"
, viewBox: "5 0 100 105"
, fillRule: "evenodd"
, clipRule: "evenodd"
, strokeLinejoin: "round"
, strokeMiterlimit: "2"
, _data: Obj.singleton "testid" "close-icon-svg"
, onClick
, className: classes.closeIcon
, children:

View File

@ -2,19 +2,21 @@ module Yoga.Modal.Spec where
import Prelude
import Effect (Effect)
import Effect.Class (liftEffect)
import Effect.Ref as Ref
import Justifill (justifill)
import React.Basic.DOM as R
import React.TestingLibrary (renderComponent)
import Test.Spec (Spec, describe, itOnly)
import React.TestingLibrary (describeComponent, fireEventClick, renderComponent)
import Test.Spec (Spec, it)
import Test.Spec.Assertions (shouldEqual)
import Yoga.Modal.Component as Modal
import Yoga.Spec.Helpers (withDarkTheme)
spec ∷ Spec Unit
spec =
describe
describeComponent (withDarkTheme Modal.makeComponent)
"The Modal Component" do
itOnly "renders without problems" do
modal <- withDarkTheme Modal.makeComponent
it "renders without problems" \modal -> do
_ <-
renderComponent modal
$ justifill
@ -23,8 +25,16 @@ spec =
, onClose: (pure unit) ∷ Effect Unit
}
pure unit
{- it "calls the onClose handler when clicking away" \panel -> do
-- [TODO]
_ <- renderComponent panel (justifill { kids: [], onClose: pure unit })
pure unit
-}
it "calls the onClose handler when clicking on the svg close" \modal -> do
ref <- Ref.new false # liftEffect
{ findByTestId } <-
renderComponent modal
$ justifill
{ title: "Hey"
, onClose: Ref.write true ref
, content: R.text "content"
}
closeBtn <- findByTestId "close-icon-svg"
fireEventClick closeBtn
clicked <- Ref.read ref # liftEffect
clicked `shouldEqual` true

View File

@ -1,6 +1,7 @@
module Yoga.Modal.Stories where
import Prelude hiding (add)
import Data.Maybe (Maybe(..))
import Data.Monoid (guard)
import Data.Tuple.Nested ((/\))
import Effect (Effect)
@ -25,7 +26,6 @@ stories = do
[ justifill
{ content: R.text "I'm a Modal"
, title: "Something important has happened this is excessively, if not prohibitively long title text to see what will happen"
, onClose: log "On close"
}
]
add "Interactive Modal Example" mkExample
@ -38,7 +38,7 @@ mkExample = do
centre <- Centre.makeComponent
button <- mkButton
component "ModalStory" \{} -> React.do
state /\ modState <- useState { open: false }
state /\ modState <- useState { open: true }
pure
$ fragment
[ jsx centre {}
@ -53,6 +53,6 @@ mkExample = do
{ title: "Warning"
, content:
R.text "This is more interactive"
, onClose: modState (_ { open = false })
, onClose: Just $ modState (_ { open = false })
}
]

View File

@ -1,7 +1,8 @@
module Yoga.Modal.Styles where
import Prelude hiding (top)
import CSS (backgroundColor, black, borderRadius, boxShadow, nil, rem, toHexString)
import CSS (backgroundColor, borderRadius, boxShadow, nil, rem, toHexString)
import CSS as Color
import JSS (JSSClasses, JSSElem, jssClasses)
import Yoga.Theme.Types (YogaTheme)
@ -20,6 +21,10 @@ type Classes a
, dialogBoxStack ∷ a
, title ∷ a
, titleCluster ∷ a
, "@keyframes zoomIn" ∷ a
, "@keyframes fadeIn" ∷ a
, zoomIn ∷ a
, fadeIn ∷ a
)
styles ∷ JSSClasses YogaTheme Props (Classes (JSSElem Props))
@ -36,15 +41,14 @@ styles =
, box:
do
backgroundColor theme.interfaceColour
boxShadow nil nil (3.5 # rem) black
boxShadow nil nil (3.5 # rem) (Color.rgba 0 0 0 0.5)
borderRadius boxBorderRadius boxBorderRadius boxBorderRadius boxBorderRadius
, closeIcon:
{ fill: toHexString theme.backgroundColour
, width: "calc(0.67 * var(--s1))"
, height: "calc(0.67 * var(--s1))"
, width: "calc(0.8em * var(--ratio))"
, height: "calc(0.8em * var(--ratio))"
, margin: 0
, padding: 0
, marginTop: "var(--s-4)"
}
, titleCluster:
{ "& > * ":
@ -68,4 +72,32 @@ styles =
, maxHeight:
"10.0 vh !important"
}
, "@keyframes zoomIn":
{ "from":
{ opacity: 0
, transform: "scale3d(0.1, 0.1, 0.1) translate3d(0, 100vh, 0)"
, "animation-timing-function": "cubic-bezier(0.55, 0.055, 0.675, 0.19)"
}
, "60%":
{ opacity: 1
, transform: "scale3d(0.475, 0.475, 0.475) translate3d(0, -20vh, 0)"
, "animation-timing-function": "cubic-bezier(0.175, 0.885, 0.32, 1)"
}
}
, zoomIn:
{ animation: "$zoomIn 0.90s ease-in"
, animationFillMode: "both"
}
, "@keyframes fadeIn":
{ from:
{ opacity: 0
}
, to:
{ opacity: 1
}
}
, fadeIn:
{ animation: "$fadeIn 0.70s"
, animationFillMode: "both"
}
}

View File

@ -78,7 +78,7 @@ exports.setMonarchTokensProviderImpl = function (monacoInstance) {
};
};
};
exports.vsCodeTheme = {
exports.vsCodeTheme = function (bg) { return ({
base: "vs",
inherit: true,
rules: [
@ -165,14 +165,14 @@ exports.vsCodeTheme = {
],
colors: {
"editor.foreground": "#000000",
"editor.background": "#DDE0EE",
"editor.background": bg,
"editor.selectionBackground": "#B5D5FF",
"editor.lineHighlightBackground": "#00000012",
"editorCursor.foreground": "#000000",
"editorWhitespace.foreground": "#BFBFBF"
}
};
exports.nightOwlTheme = {
}); };
exports.nightOwlTheme = function (bg) { return ({
base: "vs-dark",
inherit: true,
rules: [
@ -840,7 +840,7 @@ exports.nightOwlTheme = {
colors: {
"editor.foreground": "#d6deeb",
// "editor.background": "#011627",
"editor.background": "#131D2F",
"editor.background": bg,
"editor.selectionBackground": "#5f7e9779",
"editor.lineHighlightBackground": "#010E17",
"editorCursor.foreground": "#80a4c2",
@ -848,7 +848,7 @@ exports.nightOwlTheme = {
"editorIndentGuide.background": "#5e81ce52",
"editor.selectionHighlightBorder": "#122d42"
}
};
}); };
exports.purescriptSyntax = {
displayName: "Purescript",
name: "purescript",

View File

@ -1,10 +1,11 @@
module Yoga.Editor where
import Prelude
import CSS (backgroundColor, borderBox, boxSizing, margin, pct, unitless, width)
import CSS (backgroundColor, borderBox, boxSizing, margin, pct, toHexString, unitless, width)
import CSS.Overflow (hidden, overflowY)
import Control.Promise (Promise)
import Control.Promise as Promise
import Data.Foldable (for_)
import Data.Maybe (Maybe(..), maybe)
import Data.Nullable (Nullable)
import Data.Tuple.Nested ((/\))
@ -18,7 +19,7 @@ import JSS (jssClasses)
import Prim.Row (class Union)
import React.Basic (JSX, ReactComponent, Ref, element, fragment)
import React.Basic.DOM as R
import React.Basic.Hooks (component, useState)
import React.Basic.Hooks (component, useEffect, useState)
import React.Basic.Hooks as React
import React.Basic.Hooks.Aff (useAff)
import Web.DOM (Node)
@ -46,9 +47,9 @@ foreign import defineThemeImpl ∷ Monaco -> String -> MonacoTheme -> Effect Uni
foreign import setThemeImpl ∷ Monaco -> String -> Effect Unit
foreign import nightOwlTheme ∷ MonacoTheme
foreign import nightOwlTheme ∷ String -> MonacoTheme
foreign import vsCodeTheme ∷ MonacoTheme
foreign import vsCodeTheme ∷ String -> MonacoTheme
foreign import getValue ∷ Editor -> Effect String
@ -79,10 +80,10 @@ foreign import registerLanguageImpl ∷ Monaco -> String -> Effect Unit
foreign import setMonarchTokensProviderImpl ∷ Monaco -> String -> MonarchLanguage -> Effect Unit
initEditor ∷ Monaco -> Effect Unit
initEditor monaco = do
defineThemeImpl monaco darkThemeName nightOwlTheme
defineThemeImpl monaco lightThemeName vsCodeTheme
initEditor ∷ CSSTheme -> Monaco -> Effect Unit
initEditor theme monaco = do
defineThemeImpl monaco darkThemeName (nightOwlTheme (toHexString theme.backgroundColour))
defineThemeImpl monaco lightThemeName (vsCodeTheme (toHexString theme.backgroundColour))
registerLanguageImpl monaco "purescript"
setMonarchTokensProviderImpl monaco "purescript" purescriptSyntax
@ -108,10 +109,14 @@ mkEditor = do
component "Editor" \{ onLoad, height, language } -> React.do
classes <- useStyles {}
maybeEditor /\ modifyEditor <- useState Nothing
maybeMonaco /\ modifyMonaco <- useState Nothing
useAff unit do
eddy <- monacoEditor
liftEffect $ modifyEditor (const (Just eddy))
theme <- useTheme
useEffect theme do
for_ maybeMonaco (initEditor theme)
pure mempty
let
themeName = if theme.isLight then lightThemeName else darkThemeName
pure
@ -140,7 +145,10 @@ mkEditor = do
, language
-- https://microsoft.github.io/monaco-editor/playground.html#extending-language-services-custom-languages
, editorDidMount: mkEffectFn2 \e _ -> onLoad e
, editorWillMount: mkEffectFn1 initEditor
, editorWillMount:
mkEffectFn1 \m -> do
modifyMonaco (const $ Just m)
(initEditor theme m)
}
]
}

View File

@ -45,7 +45,7 @@ exports.setMonarchTokensProviderImpl = function(monacoInstance) {
};
};
exports.vsCodeTheme = {
exports.vsCodeTheme = bg => ({
base: "vs",
inherit: true,
rules: [
@ -132,15 +132,15 @@ exports.vsCodeTheme = {
],
colors: {
"editor.foreground": "#000000",
"editor.background": "#DDE0EE",
"editor.background": bg,
"editor.selectionBackground": "#B5D5FF",
"editor.lineHighlightBackground": "#00000012",
"editorCursor.foreground": "#000000",
"editorWhitespace.foreground": "#BFBFBF"
}
};
});
exports.nightOwlTheme = {
exports.nightOwlTheme = bg => ({
base: "vs-dark",
inherit: true,
rules: [
@ -809,7 +809,7 @@ exports.nightOwlTheme = {
colors: {
"editor.foreground": "#d6deeb",
// "editor.background": "#011627",
"editor.background": "#131D2F",
"editor.background": bg,
"editor.selectionBackground": "#5f7e9779",
"editor.lineHighlightBackground": "#010E17",
"editorCursor.foreground": "#80a4c2",
@ -817,7 +817,7 @@ exports.nightOwlTheme = {
"editorIndentGuide.background": "#5e81ce52",
"editor.selectionHighlightBorder": "#122d42"
}
};
});
exports.purescriptSyntax = {
displayName: "Purescript",

View File

@ -14,7 +14,6 @@ newtype UseScrollYPosition hooks
= UseScrollYPosition (UseLayoutEffect Unit (UseState Number hooks))
derive instance ntUseScrollYPosition ∷ Newtype (UseScrollYPosition hooks) _
useScrollYPosition ∷ Hook UseScrollYPosition Number
useScrollYPosition =
coerceHook React.do
@ -31,6 +30,4 @@ makeListener setPosition = do
eventListener
$ const do
win <- window
let
yPos = (unsafeCoerce win).scrollY
setPosition yPos
setPosition (unsafeCoerce win).scrollY

View File

@ -2,8 +2,6 @@ module Yoga.Spec.Helpers where
import Prelude
import Effect (Effect)
import Effect.Aff (Aff)
import Effect.Class (liftEffect)
import Prim.Row (class Lacks)
import React.Basic.Hooks (ReactComponent, component, element)
import Yoga.Theme (fromTheme)
@ -18,17 +16,16 @@ withTheme ∷
Lacks "key" props =>
CSSTheme ->
Effect (ReactComponent { | props }) ->
Aff (ReactComponent { | props })
withTheme theme mkComp =
liftEffect do
themeProvider <- mkThemeProvider
comp <- mkComp
component "ThemeWrapper" \(props ∷ { | props }) -> React.do
pure
$ element themeProvider
{ theme
, children: [ element comp props ]
}
Effect (ReactComponent { | props })
withTheme theme mkComp = do
themeProvider <- mkThemeProvider
comp <- mkComp
component "ThemeWrapper" \(props ∷ { | props }) -> React.do
pure
$ element themeProvider
{ theme
, children: [ element comp props ]
}
withDarkTheme ∷
∀ props.
@ -36,7 +33,7 @@ withDarkTheme ∷
Lacks "ref" props =>
Lacks "key" props =>
Effect (ReactComponent (Record props)) ->
Aff (ReactComponent (Record props))
Effect (ReactComponent (Record props))
withDarkTheme = withTheme (fromTheme darkTheme)
withLightTheme ∷
@ -45,5 +42,5 @@ withLightTheme ∷
Lacks "ref" props =>
Lacks "key" props =>
Effect (ReactComponent (Record props)) ->
Aff (ReactComponent (Record props))
Effect (ReactComponent (Record props))
withLightTheme = withTheme (fromTheme lightTheme)

View File

@ -20,6 +20,11 @@ increaseContrast contrastWith = go 0
else
go (i + 1) (modify 0.1 col)
withAlpha ∷ Number -> Color -> Color
withAlpha alpha c1 = Color.rgba' r g b alpha
where
{ r, g, b } = Color.toRGBA' c1
unsafeWithAlpha ∷ Number -> String -> String
unsafeWithAlpha alpha s1 =
fromMaybe "yellow" do

View File

@ -91,9 +91,12 @@ styles =
}
, "h3, .h3":
{ "font-size": "var(--s2)"
, "hyphens": "auto"
, "text-transform": "uppercase"
}
, "h4, .h4":
{ "font-size": "var(--s1)"
, "text-transform": "uppercase"
}
}
}

View File

@ -15,10 +15,11 @@ hex c = c # Color.fromHexString # fromMaybe' \_ -> unsafeCrashWith $ "Invalid he
darkTheme ∷ Theme
darkTheme =
{ backgroundColour: Color.hsl 220.0 0.42 0.13
{ backgroundColour: Color.hsl 228.0 0.12 0.20
, textColour: Color.hsl 225.0 0.28 0.90
, interfaceColour: Color.hsl 225.0 0.48 0.12
, highlightColour: Color.rgb 209 51 225
, highlightColour: Color.hsl 350.0 0.50 0.67
-- , highlightColour: Color.hsl 33.0 0.37 0.8
, altHighlightColour: Color.hsl 84.0 0.617 0.631
, textFontFamily: cons' "Rubik" systemFontStack
, headingFontFamily: cons' "Rubik" systemFontStack
@ -41,7 +42,7 @@ lightTheme =
darkTheme
{ textColour = Color.hsl 225.0 0.18 0.25
-- , backgroundColour = Color.hsl 210.0 0.08 0.87
, backgroundColour = hex "#F6F9FC"
, backgroundColour = Color.hsl 30.0 0.50 0.96
, interfaceColour = Color.hsl 210.0 0.10 0.89
-- , highlightColour = Color.hsl 209.0 0.95 0.69
, highlightColour = Color.hsl 350.0 0.90 0.70

View File

@ -29,8 +29,8 @@ stories = do
$ R.div
{ style:
css
{ color: cssTheme.textColour
, backgroundColor: cssTheme.backgroundColour
{ color: toHexString cssTheme.textColour
, backgroundColor: toHexString cssTheme.backgroundColour
}
, children:
[ R.div

View File

@ -27,39 +27,39 @@ mkH = do
makeStylesJSS
$ jssClasses \(theme ∷ CSSTheme) ->
{ common:
{ color: theme.textColour # toHexString
, fontFamily: theme.headingFontFamily
}
{ color: theme.textColour # toHexString
, fontFamily: theme.headingFontFamily
}
, h1:
{ textTransform: "uppercase"
, fontSize: "3.6em"
, letterSpacing: "0.07em"
, margin: 0
, padding: 0
}
{ textTransform: "uppercase"
-- , fontSize: "3.6em"
, letterSpacing: "0.07em"
, margin: 0
, padding: 0
}
, h2:
{ textTransform: "uppercase"
, fontSize: "3em"
, letterSpacing: "0.05em"
, margin: 0
, padding: 0
}
{ textTransform: "uppercase"
-- , fontSize: "3em"
, letterSpacing: "0.05em"
, margin: 0
, padding: 0
}
, h3:
{ fontSize: "2.2em"
, margin: 0
, padding: 0
}
{ -- fontSize: "2.2em"
margin: 0
, padding: 0
}
, h4:
{ fontSize: "1.5em"
, margin: 0
, padding: 0
}
{ fontSize: "1.5em"
, margin: 0
, padding: 0
}
, h5:
{ fontSize: "1.0em"
, margin: 0
, padding: 0
, color: theme.textColourLighter # toHexString
}
{ fontSize: "1.0em"
, margin: 0
, padding: 0
, color: theme.textColourLighter # toHexString
}
}
component "Heading" \{ level, text, className } -> React.do
classes <- useStyles {}

View File

@ -154,7 +154,7 @@ let additions =
]
, repo =
"https://github.com/i-am-the-slime/purescript-react-testing-library.git"
, version = "5a10027deeeee12de3ccfeecfdb033d1e53f8d05"
, version = "4120c0ab605bc71ca03836f761bc687fc1cdd377"
}
, pseudo-random =
{ dependencies =