Draggable Spells

This commit is contained in:
Mark Eibes 2020-05-04 23:44:11 +02:00
parent 4321e4cc2d
commit 4669fb5dc7
23 changed files with 379 additions and 81 deletions

Binary file not shown.

View File

@ -1,6 +1,7 @@
module React.Basic.Helpers where
import Data.Maybe (Maybe, fromMaybe, fromMaybe')
import Prelude
import Data.Maybe (Maybe, fromMaybe')
import Data.Symbol (SProxy(..))
import Justifill.Fillable (class Fillable, class FillableFields, fill)
import Justifill.Justifiable (class Justifiable, justify)
@ -8,6 +9,7 @@ import Literals.Undefined (undefined)
import Prim.Row (class Lacks, class Nub)
import Prim.RowList (class RowToList)
import React.Basic (JSX)
import React.Basic.DOM as R
import React.Basic.Hooks (ReactComponent, element)
import Record (disjointUnion, insert)
import Unsafe.Coerce (unsafeCoerce)
@ -57,13 +59,18 @@ jsx x partialProps kids = element x propsWithKids
where
propsWithKids ∷ Record (Kids to)
propsWithKids = disjointUnion { kids } props
fill' ∷ { | thru } -> { | to }
fill' = fill
justify' ∷ { | from } -> { | thru }
justify' = justify
props ∷ Record to
props =
( (fill ∷ { | thru } -> { | to })
( (justify ∷ { | from } -> { | thru })
partialProps
)
)
props = fill' (justify' partialProps)
orUndefined ∷ ∀ a. Maybe a -> a
orUndefined = fromMaybe' \_ -> unsafeCoerce undefined
classSpan ∷ String -> Array JSX -> JSX
classSpan className children = R.span { className, children }
classDiv ∷ String -> Array JSX -> JSX
classDiv className children = R.div { className, children }

View File

@ -5,6 +5,11 @@ exports.useSpringImpl = function (mkStyles) { return function () {
var result = react_spring_1.useSpring(mkStyles);
return { style: result[0], set: result[1], stop: result[2] };
}; };
exports.useSpringsImpl = function (n) { return function (fn) { return function () {
var result = react_spring_1.useSprings(n, fn);
console.log("REEEEEEEEESLUT", result);
return { styles: result[0], set: result[1], stop: result[2] };
}; }; };
exports.useTransitionImpl = react_spring_1.useTransition;
exports.animatedComponentImpl = function (name) { return react_spring_1.animated[name]; };
exports.animatedImpl = react_spring_1.animated;

View File

@ -6,14 +6,12 @@ import Data.Nullable (Nullable, toNullable)
import Data.Nullable as Nullable
import Effect (Effect)
import Effect.Uncurried (EffectFn1, EffectFn3, runEffectFn1, runEffectFn3)
import Foreign (Foreign)
import Prim.Row (class Union)
import React.Basic (JSX, ReactComponent, Ref, element)
import React.Basic (JSX, ReactComponent, element)
import React.Basic.DOM (CSS, Props_div, Props_span)
import React.Basic.DOM.SVG (Props_svg, Props_path)
import React.Basic.Hooks (Hook, unsafeHook)
import React.Basic.Hooks as React
import Simple.JSON (class WriteForeign)
foreign import data UseSpring ∷ Type -> Type -> Type
@ -33,6 +31,28 @@ useSpring f = React.do
res <- unsafeHook (useSpringImpl f)
pure $ res { set = runEffectFn1 res.set }
foreign import data UseSprings ∷ Type -> Type -> Type
foreign import useSpringsImpl ∷
∀ r s.
Int ->
(Int -> { | r }) ->
Effect { styles ∷ Array { | r }, set ∷ SetSpringsImpl s, stop ∷ StopSpring }
type SetSpringsImpl r
= EffectFn1 (Int -> { | r }) Unit
type SetSprings r
= (Int -> { | r }) -> Effect Unit
useSprings ∷
∀ r s.
Int ->
(Int -> { | r }) -> Hook (UseSprings { | r }) { styles ∷ Array { | r }, set ∷ SetSprings s, stop ∷ StopSpring }
useSprings n f = React.do
res <- unsafeHook (useSpringsImpl n f)
pure $ res { set = runEffectFn1 res.set }
foreign import data UseTransition ∷ Type -> Type -> Type
foreign import useTransitionImpl ∷ ∀ a. EffectFn3 (Array a) (Nullable (a -> String)) CSS (Array { item ∷ Nullable a, key ∷ Nullable String, props ∷ CSS })

View File

@ -1,10 +1,24 @@
import { useChain, useSpring, useTransition, animated } from "react-spring";
import {
useChain,
useSpring,
useSprings,
useTransition,
interpolate,
animated,
} from "react-spring";
exports.interpolateImpl = interpolate;
exports.useSpringImpl = (mkStyles) => () => {
const result = useSpring(mkStyles);
return { style: result[0], set: result[1], stop: result[2] };
};
exports.useSpringsImpl = (n: number) => (fn) => () => {
const result = useSprings(n, fn);
return { styles: result[0], set: result[1], stop: result[2] };
};
exports.useTransitionImpl = useTransition;
exports.animatedComponentImpl = (name: string) => animated[name];

View File

@ -7,6 +7,7 @@ import Data.Monoid (guard)
import Data.Tuple.Nested ((/\))
import Effect (Effect)
import JSS (jssClasses)
import Justifill (justifill)
import React.Basic.DOM (css)
import React.Basic.DOM as R
import React.Basic.Events (handler_)
@ -129,8 +130,8 @@ mkDragAnimated = do
component "Draggable Example" \{} -> React.do
{ style, set } <- useSpring $ const { x: 0.0, y: 0.0, config: { mass: 1, tension: 210, friction: 20 } }
classes <- useStyles {}
mkDragProps <-
useDrag \{ down, movement: mx /\ my } ->
bindDragProps <-
useDrag (justifill {}) \{ down, movement: mx /\ my } ->
set { x: if down then mx else 0.0, y: if down then my else 0.0 }
pure
$ animatedDiv
@ -140,4 +141,4 @@ mkDragAnimated = do
]
}
`withDragProps`
mkDragProps
(bindDragProps unit)

View File

@ -2,40 +2,61 @@ module React.Basic.Hooks.UseGesture where
import Prelude
import Data.Array ((!!))
import Data.Foldable (fold)
import Data.Monoid.Additive (Additive(..))
import Data.Newtype (ala)
import Data.Maybe (Maybe, fromMaybe')
import Data.Nullable (Nullable)
import Data.Tuple.Nested ((/\), type (/\))
import Debug.Trace (spy)
import Effect (Effect)
import Effect.Uncurried (EffectFn1, runEffectFn1)
import Effect.Aff.Compat (runEffectFn2)
import Effect.Uncurried (EffectFn2)
import Effect.Unsafe (unsafePerformEffect)
import Partial.Unsafe (unsafeCrashWith)
import Prim.Row (class Lacks, class Nub)
import React.Basic.Events (EventHandler)
import React.Basic.Hooks (Hook, unsafeHook)
import React.Basic.Helpers (orUndefined)
import React.Basic.Hooks (Hook, Ref, unsafeHook)
import Record (disjointUnion)
import Web.DOM (Node)
import Yoga.Helpers ((?||))
foreign import data UseDrag ∷ Type -> Type -> Type
type DragHandler
= { down ∷ Boolean, movement ∷ Number /\ Number } -> Effect Unit
type DragHandler a
= { arg ∷ a, down ∷ Boolean, movement ∷ Number /\ Number } -> Effect Unit
type DragHandlerImpl
= { down ∷ Boolean, movement ∷ Array Number } -> Unit
type DragHandlerImpl a
= { args ∷ Array a, down ∷ Boolean, movement ∷ Array Number } -> Unit
type DragProps
= { onMouseDown ∷ EventHandler, onTouchStart ∷ EventHandler }
foreign import useDragImpl ∷ EffectFn1 DragHandlerImpl (Effect DragProps)
type GenericOptionsImpl r
= { domTarget ∷ Ref (Nullable Node) | r }
useDrag ∷ DragHandler -> Hook (UseDrag Unit) (Effect DragProps)
useDrag dragHandler = unsafeHook (runEffectFn1 useDragImpl f)
type GenericOptions r
= { domTarget ∷ Maybe (Ref (Nullable Node)) | r }
type DragOptions
= GenericOptions ()
type DragOptionsImpl
= GenericOptionsImpl ()
dragOptionsToImpl ∷ DragOptions -> DragOptionsImpl
dragOptionsToImpl { domTarget } = { domTarget: domTarget # orUndefined }
foreign import useDragImpl ∷ ∀ a. EffectFn2 (DragHandlerImpl a) DragOptionsImpl (a -> DragProps)
useDrag ∷ ∀ a. DragOptions -> DragHandler a -> Hook (UseDrag Unit) (a -> DragProps)
useDrag dragOptions dragHandler = unsafeHook (runEffectFn2 useDragImpl dragHandlerImpl (dragOptionsToImpl dragOptions))
where
f x =
dragHandlerImpl ∷ DragHandlerImpl a
dragHandlerImpl x =
(unsafePerformEffect <<< dragHandler)
{ down: x.down, movement: mx /\ my
{ arg, down: x.down, movement: mx /\ my
}
where
arg = x.args !! 0 # fromMaybe' (\_ -> unsafeCrashWith "Bollox")
mx = x.movement !! 0 ?|| 0.0
my = x.movement !! 1 ?|| 0.0
@ -47,6 +68,6 @@ withDragProps ∷
( onMouseDown ∷ EventHandler, onTouchStart ∷ EventHandler | attrs )
( onMouseDown ∷ EventHandler, onTouchStart ∷ EventHandler | attrs ) =>
{ | attrs } ->
Effect DragProps ->
DragProps ->
{ onMouseDown ∷ EventHandler, onTouchStart ∷ EventHandler | attrs }
withDragProps x (y ∷ Effect DragProps) = disjointUnion (unsafePerformEffect y) x
withDragProps x (y ∷ DragProps) = disjointUnion y x

View File

@ -112,5 +112,14 @@ mkThemeSwitcher = do
pure
$ element themeProvider
{ theme
, children: [ element baseline { kids: [ R.div_ [ themeSelect, child ] ] } ]
, children:
[ element baseline
{ kids:
[ R.div
{ style: css { width: "100%" }
, children: [ themeSelect, child ]
}
]
}
]
}

View File

@ -6,13 +6,16 @@ import Color as Color
import Data.Foldable (fold)
import Data.Interpolate (i)
import Data.Maybe (Maybe)
import Data.Nullable (Nullable)
import Effect (Effect)
import JSS (JSSClasses, JSSElem, jssClasses)
import React.Basic (JSX)
import React.Basic.DOM as R
import React.Basic.Hooks (ReactComponent, component)
import React.Basic.Helpers (orUndefined)
import React.Basic.Hooks (ReactComponent, Ref, component)
import React.Basic.Hooks as React
import Record.Extra (pick)
import Web.DOM (Node)
import Yoga.Box.Component as Box
import Yoga.Helpers (ifJustTrue)
import Yoga.Theme (withAlpha)
@ -44,24 +47,25 @@ styles =
}
}
type Props r
type PropsR r
= ( kids ∷ Array JSX
, className ∷ Maybe String
, divRef ∷ Maybe (Ref (Nullable Node))
| r
)
mkCard ∷
Effect
( ReactComponent
{ | Props (StyleProps) }
)
type Props
= { | PropsR (StyleProps) }
mkCard ∷ Effect (ReactComponent Props)
mkCard = do
useStyles <- makeStylesJSS styles
box <- Box.makeComponent
component "Card" \props@{ kids, className } -> React.do
component "Card" \(props@{ kids, className } ∷ Props) -> React.do
classes <- useStyles (pick props)
pure
$ R.div
{ className: classes.card <> " " <> fold className
{ ref: props.divRef # orUndefined
, className: classes.card <> " " <> fold className
, children: kids
}

View File

@ -2,15 +2,14 @@ module Yoga.Cover.Component where
import Prelude
import Data.Array (foldMap)
import Data.Array as Array
import Data.Maybe (Maybe)
import Effect (Effect)
import Yoga.Cover.Styles as Cover
import Prim.Row (class Nub, class Union)
import React.Basic (JSX)
import React.Basic.DOM as R
import React.Basic.Hooks (ReactComponent, component)
import React.Basic.Hooks as React
import Record (disjointUnion)
import Yoga.Cover.Styles as Cover
import Yoga.Theme.Styles (makeStylesJSS)
type Props
@ -20,33 +19,24 @@ type PropsR
= OptionalProps ()
type OptionalProps r
= ( header ∷ JSX
, footer ∷ JSX
, principal ∷ JSX
= ( header ∷ Maybe JSX
, footer ∷ Maybe JSX
, kids ∷ Array JSX
, className ∷ Maybe String
| r
)
withDefaults ∷
∀ r missing props.
Union r missing props =>
Nub props props =>
Monoid { | missing } =>
{ | r } ->
{ | props }
withDefaults x = disjointUnion x mempty
makeComponent ∷ Effect (ReactComponent Props)
makeComponent = do
useStyles <- makeStylesJSS Cover.styles
component "Cover" \{ header, footer, principal, className } -> React.do
component "Cover" \{ header, footer, kids, className } -> React.do
classes <- useStyles {}
pure
$ R.div
{ className: classes.cover <> foldMap (" " <> _) className
, children:
[ R.div { className: classes.header, children: pure header }
, R.div { className: classes.principal, children: pure principal }
, R.div { className: classes.footer, children: pure footer }
[ R.div { className: classes.header, children: Array.fromFoldable header }
, R.div { className: classes.principal, children: kids }
, R.div { className: classes.footer, children: Array.fromFoldable footer }
]
}

View File

@ -1,14 +1,16 @@
module Yoga.Cover.Spec where
import Prelude
import Yoga.Cover.Component as Cover
import Justifill (justifill)
import React.Basic.DOM as R
import React.TestingLibrary (describeComponent, renderComponent)
import Test.Spec (Spec, it)
import Yoga.Cover.Component as Cover
spec :: Spec Unit
spec Spec Unit
spec =
describeComponent Cover.makeComponent
"The Cover Component" do
it "renders without problems" \panel -> do
_ <- renderComponent panel (Cover.withDefaults {})
it "renders without problems" \cover -> do
_ <- renderComponent cover (justifill { kids: [ R.text "hi" ] })
pure unit

View File

@ -1,30 +1,34 @@
module Yoga.Cover.Stories where
import Prelude hiding (add)
import Storybook.Decorator.FullScreen (fullScreenDecorator)
import Effect (Effect)
import Yoga.Cover.Component as Cover
import Justifill (justifill)
import React.Basic (JSX)
import React.Basic.DOM as R
import Storybook.Decorator.FullScreen (fullScreenDecorator)
import Storybook.React (Storybook, add, addDecorator, storiesOf)
import Yoga.Cover.Component as Cover
stories ∷ Effect Storybook
stories = do
storiesOf "Cover" do
addDecorator fullScreenDecorator
add "The Cover" Cover.makeComponent
[ Cover.withDefaults
{ principal: R.h1_ [ R.text "Main thing" ]
[ justifill
{ kids: [ R.h1_ [ R.text "Main thing" ] ]
, header: R.text "Header"
, footer: R.text "Footer"
}
, Cover.withDefaults
{ principal: R.h1_ [ R.text "Only main" ]
, justifill
{ kids: [ R.h1_ [ R.text "Only main" ] ]
}
, Cover.withDefaults
, justifill
{ header: R.h1_ [ R.text "Only header" ]
, kids: [] ∷ Array JSX
}
, Cover.withDefaults
, justifill
{ header: R.h1_ [ R.text "Header" ]
, footer: R.h1_ [ R.text "Footer" ]
, kids: [] ∷ Array JSX
}
]

View File

@ -3,6 +3,7 @@ module Yoga.Grid.Spec where
import Prelude
import Justifill (justifill)
import React.Basic.DOM as R
import React.Basic.Hooks (JSX)
import React.TestingLibrary (describeComponent, renderComponent)
import Test.Spec (Spec, it)
import Yoga.Grid.Component as Grid
@ -16,5 +17,5 @@ spec =
_ <-
renderComponent grid
$ justifill
{}
{ kids: [] ∷ _ JSX }
pure unit

View File

@ -1,9 +1,8 @@
module Yoga.Grid.Stories where
import Prelude hiding (add)
import Data.Array (mapWithIndex, replicate, (..))
import Data.Array ((..))
import Effect (Effect)
import Effect.Unsafe (unsafePerformEffect)
import Justifill (justifill)
import React.Basic.DOM (css)
import React.Basic.DOM as R
@ -15,7 +14,6 @@ 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

View File

@ -0,0 +1,4 @@
exports.unsafeArraySetAt = function (i) { return function (v) { return function (arr) {
arr[i] = v;
return arr;
}; }; };

View File

@ -1,25 +1,72 @@
module Yoga.Grimoire.Component where
import Prelude
import Data.Array (mapWithIndex, zip)
import Data.Array as Array
import Data.Maybe (Maybe(..))
import Data.Nullable (Nullable)
import Data.Tuple.Nested ((/\))
import Debug.Trace (spy)
import Effect (Effect)
import Justifill (justifill)
import React.Basic (ReactComponent)
import React.Basic.DOM as R
import React.Basic.Hooks (component)
import React.Basic.DOM (css)
import React.Basic.Helpers (jsx)
import React.Basic.Hooks (Ref, component, element)
import React.Basic.Hooks as React
import React.Basic.Hooks.Spring (animatedDiv, useSprings)
import React.Basic.Hooks.UseGesture (useDrag, withDragProps)
import Record.Extra (pick)
import Unsafe.Coerce (unsafeCoerce)
import Web.DOM (Node)
import Yoga.Grid.Component as Grid
import Yoga.Grimoire.Spell.Component as GrimoireSpell
import Yoga.Grimoire.Styles (styles)
import Yoga.Spell.Types (Spell)
import Yoga.Theme.Styles (makeStylesJSS, useTheme)
import Yoga.Theme.Types (CSSTheme)
type Props
= {
= { spells ∷ Array Spell
}
makeComponent ∷ Effect (ReactComponent Props)
makeComponent = do
grid <- Grid.makeComponent
spellComponent <- GrimoireSpell.makeComponent
useStyles <- makeStylesJSS styles
component "Grimoire" \(props@{} ∷ Props) -> React.do
component "Grimoire" \(props ∷ Props) -> React.do
{} <- useStyles (pick props)
springs <- useSprings (Array.length props.spells) \_ -> { x: 0.0, y: 0.0, zIndex: 0, immediate: false, transform: "scale3d(1.0,1.0,1.0)" }
let
_ = spy "springs" springs
theme ∷ CSSTheme <- useTheme
bindDragProps <-
useDrag (justifill {}) \{ arg, down, movement: mx /\ my } -> do
springs.set \i ->
if i == arg && down then
{ x: mx, y: my, zIndex: 1, transform: "scale3d(1.1, 1.1, 1.1)", immediate: \n -> n == "x" || n == "y" || n == "zIndex" }
else
{ x: 0.0, y: 0.0, zIndex: 0, transform: "scale3d(1.0, 1.0, 1.0)", immediate: const false }
let
renderSpells =
mapWithIndex \i (spell /\ style) ->
animatedDiv
$ { style: css style
, children:
[ element
spellComponent
{ spell
, cardRef: Nothing
}
]
}
`withDragProps`
bindDragProps i
pure
$ R.div_ [ R.text "WriteMe" ]
$ jsx grid {} (renderSpells (props.spells `zip` springs.styles))
foreign import unsafeArraySetAt ∷ ∀ a. Int -> a -> Array a -> Array a
unsafeUpdateRefs ∷ Ref (Array (Nullable Node)) -> Int -> Nullable Node -> Array (Nullable Node)
unsafeUpdateRefs refsRef i el = unsafeArraySetAt i el ((unsafeCoerce refsRef).current)

View File

@ -0,0 +1,4 @@
exports.unsafeArraySetAt = <A>(i: number) => (v: A) => (arr: Array<A>) => {
arr[i] = v;
return arr;
};

View File

@ -0,0 +1,66 @@
module Yoga.Grimoire.Spell.Component where
import Prelude
import CSS (AlignItemsValue, JustifyContentValue, spaceBetween)
import CSS.Common (baseline)
import Data.Maybe (Maybe)
import Data.Nullable (Nullable)
import Effect (Effect)
import React.Basic (ReactComponent)
import React.Basic.DOM as R
import React.Basic.Helpers (classSpan, jsx)
import React.Basic.Hooks (Ref, component)
import React.Basic.Hooks as React
import Record.Extra (pick)
import Web.DOM (Node)
import Yoga.Box.Component as Box
import Yoga.Card.Component (mkCard)
import Yoga.Centre.Component as Centre
import Yoga.Cluster.Component as Cluster
import Yoga.Cover.Component as Cover
import Yoga.Grimoire.Spell.Styles (styles)
import Yoga.Grimoire.Spell.Styles as Style
import Yoga.Spell.Types (Spell)
import Yoga.Stack.Component as Stack
import Yoga.Theme.Styles (makeStylesJSS, useTheme)
import Yoga.Theme.Types (CSSTheme)
type Props
= { spell ∷ Spell
, cardRef ∷ Maybe (Ref (Nullable Node))
| Style.PropsR
}
makeComponent ∷ Effect (ReactComponent Props)
makeComponent = do
box <- Box.makeComponent
centre <- Centre.makeComponent
stack <- Stack.makeComponent
cluster <- Cluster.makeComponent
card <- mkCard
cover <- Cover.makeComponent
useStyles <- makeStylesJSS styles
component "Spell" \(props@{ spell } ∷ Props) -> React.do
style <- useStyles (pick props)
theme ∷ CSSTheme <- useTheme
let
headerCluster =
jsx cluster
{ space: "var(--s-5)"
, align: baseline ∷ AlignItemsValue
, justify: spaceBetween ∷ JustifyContentValue
}
[ R.div_
[ classSpan style.name [ R.text spell.name ]
, classSpan style.signature [ R.text spell.signature ]
]
]
pure
$ jsx card { divRef: props.cardRef }
[ jsx box { className: style.container, padding: "var(--s-1)" }
[ jsx stack { space: "var(--s-3)" }
[ headerCluster
, classSpan style.description [ R.text spell.description ]
]
]
]

View File

@ -0,0 +1,19 @@
module Yoga.Grimoire.Spell.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.Grimoire.Spell.Component as Spell
import Yoga.Spec.Helpers (withSpecTheme)
spec ∷ Spec Unit
spec =
describeComponent (withSpecTheme Spell.makeComponent)
"The Spell Component" do
it "renders without problems" \spell -> do
_ <-
renderComponent spell
$ justifill { spell: { description: "bla", name: "Heinz", signature: "Any -> Unit" } }
pure unit

View File

@ -0,0 +1,20 @@
module Yoga.Grimoire.Spell.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.Spell.Component as Spell
stories ∷ Effect Storybook
stories = do
storiesOf "Spell" do
addDecorator fullScreenDecorator
add "The Spell" Spell.makeComponent
[ justifill
{ spell:
{ name: "append", signature: "a -> a -> a", description: "Takes two values and produces one" }
}
]

View File

@ -0,0 +1,49 @@
module Yoga.Grimoire.Spell.Styles where
import Prelude hiding (top)
import CSS (ColorSpace(..), backgroundColor, border, borderRadius, color, fontFamily, fontSize, fontStyle, height, mix, pct, sansSerif, solid, width)
import CSS.FontStyle (italic)
import CSS.TextAlign (rightTextAlign, textAlign)
import Data.Array (fromFoldable)
import Data.NonEmpty (NonEmpty(..))
import Data.NonEmpty as NonEmpty
import JSS (JSSClasses, JSSElem, jss, jssClasses)
import Yoga.Theme.Types (YogaTheme)
type PropsR
= ()
type Props
= Record PropsR
type Classes a
= ( container ∷ a
, signature ∷ a
, description ∷ a
, name ∷ a
)
styles ∷ JSSClasses YogaTheme Props (Classes (JSSElem Props))
styles =
jssClasses \theme@{ s0, s1, s4, s5, s_5 } ->
{ container:
jss { userSelect: "none" }
<> jss do
backgroundColor theme.backgroundColourLighter
height (100.0 # pct)
, signature:
do
color theme.textColour
textAlign rightTextAlign
fontFamily (fromFoldable theme.codeFontFamily) (NonEmpty.singleton sansSerif)
fontStyle italic
, name:
do
color theme.highlightColour
fontFamily (fromFoldable theme.codeFontFamily) (NonEmpty.singleton sansSerif)
fontSize s1
, description:
do
color theme.grey
fontStyle italic
}

View File

@ -14,5 +14,11 @@ stories = do
addDecorator fullScreenDecorator
add "The Grimoire" Grimoire.makeComponent
[ justifill
{}
{ spells }
]
spells =
[ { name: "cast", signature: "String -> Effect Unit", description: "Casts an incantation" }
, { name: "take", signature: "Int -> String -> String", description: "Takes the first characters of a string" }
, { name: "append", signature: "a -> a -> a", description: "Takes two values and produces one" }
]

View File

@ -0,0 +1,7 @@
module Yoga.Spell.Types where
type Spell
= { name ∷ String
, signature ∷ String
, description ∷ String
}