purview-0.2.0.2: A simple, fun way to build websites
Safe HaskellSafe-Inferred
LanguageHaskell2010

Purview

Description

Purview follows the usual pattern of action -> state -> state, with events flowing up from event producers to handlers where they are captured. State is passed from handler to the continuation.

Here's a quick example with a counter:

module Main where
import Prelude hiding (div)
import Purview
import Purview.Server (serve, defaultConfiguration)

incrementButton = onClick "increment" $ button [ text "+" ]
decrementButton = onClick "decrement" $ button [ text "-" ]

view count = div
  [ p [ text ("count: " <> show count) ]
  , incrementButton
  , decrementButton
  ]

countHandler :: (Integer -> Purview String m) -> Purview () m
countHandler = handler' [] (0 :: Integer) reducer

reducer event state = case event of
  "increment" -> (state + 1, [])
  "decrement" -> (state - 1, [])

component' _ = countHandler view

main = serve defaultConfiguration { devMode=True } component'

Note the "devMode=True": this tells Purview to send the whole tree over again when the websocket reconnects. This is handy if you're re-running the server in ghci, although I recommend using ghcid so you can do:

ghcid --command 'stack ghci yourProject/Main.hs' --test :main

Which will automatically restart the server on code changes. It's fast!

For more in depth reading check out the readme and the examples folder.

Synopsis

Handlers

These are how you can catch events sent from things like onClick and change state, or in the case of effectHandler, make API requests or call functions from your project.

In addition they can send events to themself, to a parent, call a function in the browser, or all three.

Note because of the typeable constraints Haskell will yell at you until it knows the types of the event and state.

handler Source #

Arguments

:: (Typeable event, Show state, Eq state, Typeable state) 
=> [DirectedEvent parentEvent event]

Initial events to fire

-> state

The initial state

-> (event -> state -> (state -> state, [DirectedEvent parentEvent event]))

The reducer, or how the state should change for an event

-> (state -> Purview event m)

The continuation / component to connect to

-> Purview parentEvent m 

This is the pure handler, for when you don't need access to IO. Events are still handled within a green thread so it's possible to overwrite state, just something to be aware of.

Example:

Let's say you want to make a button that switches between saying "up" or "down":

view direction = onClick "toggle" $ button [ text direction ]

toggleHandler = handler [] "up" reducer
  where reducer "toggle" state =
          let newState = if state == "up" then "down" else "up"
          in (const newState, [])

component = toggleHandler view

Or typed out in longer form:

type State = String
type Event = String

reducer :: Event -> State -> (State -> State, [DirectedEvent parentEvent Event])
reducer event state = case event of
  "up"   -> (const "down", [])
  "down" -> (const "up", [])

toggleHandler :: (State -> Purview Event m) -> Purview parentEvent m
toggleHandler = handler [] "up" reducer

component :: Purview parentEvent m
component = toggleHandler view

Note that parentEvent is left unspecified as this handler doesn't send any events to a parent, so it can be plugged in anywhere. If you did want to send events, the reducer looks like this:

reducer :: String -> String -> (String -> String, [DirectedEvent String String])
reducer event state = case event of
  "up"   -> (const "down", [Self "down"])
  "down" -> (const "up", [Parent "clickedDown"])

Which is about all there is to sending more events.

effectHandler Source #

Arguments

:: (Typeable event, Show state, Eq state, Typeable state) 
=> [DirectedEvent parentEvent event]

Initial events to fire

-> state

initial state

-> (event -> state -> m (state -> state, [DirectedEvent parentEvent event]))

reducer (note the m!)

-> (state -> Purview event m)

continuation

-> Purview parentEvent m 

This handler gives you access to whichever monad you're running Purview with.

Example:

If you wanted to print something on the server every time someone clicked a button:

view _ = onClick "sayHello" $ button [ text "Say hello on the server" ]

handler = effectHandler [] () reduce
  where reduce "sayHello" state = do
          print "Someone on the browser says hello!"
          pure (const (), [])

component = handler view

handler' Source #

Arguments

:: (Typeable event, Show state, Eq state, Typeable state) 
=> [DirectedEvent parentEvent event]

Initial events to fire

-> state

The initial state

-> (event -> state -> (state, [DirectedEvent parentEvent event]))

The reducer, or how the state should change for an event

-> (state -> Purview event m)

The continuation / component to connect to

-> Purview parentEvent m 

This provides a shorthand for when you know you want to overwrite the state on each event.

Example:

@ view direction = onClick "toggle" $ button [ text direction ]

toggleHandler = handler' [] "up" reducer where reducer "toggle" state = let newState = if state == "up" then "down" else "up" -- note it's just newState, not const newState in (newState, [])

component = toggleHandler view

effectHandler' Source #

Arguments

:: (Typeable event, Show state, Eq state, Typeable state, Functor m) 
=> [DirectedEvent parentEvent event]

Initial events to fire

-> state

initial state

-> (event -> state -> m (state, [DirectedEvent parentEvent event]))

reducer (note the m!)

-> (state -> Purview event m)

continuation

-> Purview parentEvent m 

To mirror handler', a shorthand for when you know you want to overwrite state.

Styling

style :: QuasiQuoter Source #

Components styled with this QuasiQuoter will have a class added to them and the CSS added to the stylesheet. Basic support is provided for easily styling nested components and for pseudo selectors.

Examples:

Styling a button:

blue = [style|
  background-color: blue;
|]

blueButton = blue $ button []

Styling a list with a pseudo selector to get the right cursor on hover:

listStyle = [style|
  width: 250px;
  li {
    padding: 25px;
    &:hover {
      cursor: pointer;
    }
  }
|]

list = listStyle $ ul [ li [ text "an item" ] ]

istyle :: String -> Purview event m -> Purview event m Source #

For adding inline styles. Good for dynamic parts of styling, as the style QuasiQuoter does not support variables.

Example:

Varying a color based on input:

submitButton valid =
  let
    borderColor = if valid then "green" else "red"
    borderStyle = "border-color: " <> borderColor <> ";"
  in
    istyle borderStyle $ button [ text Submit ]

HTML

These are some of the more common HTML nodes and some attributes to get you started, but you'll want to create your own as well. Here's how:

Examples:

If you wanted to create a code node:

import Purview ( Purview( Html ), text )

code :: [Purview event m] -> Purview event m
code = Html "code"

helloCode :: Purview event m
helloCode = code [ text "it's some code" ]
-- renders as codeit's some code/code

If you wanted to create a new attribute for adding test-ids to nodes:

import Purview ( Purview( Attribute ), Attributes( Generic ), button, text )

testId :: String -> Purview event m -> Purview event m
testId = Attribute . Generic "test-id"

testableButton :: Purview event m
testableButton = testId "cool-button" $ button [ text "testable!" ]
-- renders as test-id="cool-button"testable!/button

div :: [Purview event m] -> Purview event m Source #

span :: [Purview event m] -> Purview event m Source #

p :: [Purview event m] -> Purview event m Source #

h1 :: [Purview event m] -> Purview event m Source #

h2 :: [Purview event m] -> Purview event m Source #

h3 :: [Purview event m] -> Purview event m Source #

h4 :: [Purview event m] -> Purview event m Source #

text :: String -> Purview event m Source #

button :: [Purview event m] -> Purview event m Source #

a :: [Purview event m] -> Purview event m Source #

ul :: [Purview event m] -> Purview event m Source #

li :: [Purview event m] -> Purview event m Source #

form :: [Purview event m] -> Purview event m Source #

input :: [Purview event m] -> Purview event m Source #

href :: String -> Purview event m -> Purview event m Source #

id' :: String -> Purview event m -> Purview event m Source #

For adding an "id" to HTML

class' :: String -> Purview event m -> Purview event m Source #

For adding a "class" to HTML

Events

Event creators work similar to attributes in that they are bound to the eventual concrete HTML. When triggered they create an event that flows up to a handler. They can have a value, in which case you'll need to provide a function to transform that value into an event your handler can handle.

To create your own:

Examples:

To add an event creator for keydown:

import Purview ( Purview( Attribute ), Attributes( On ) )
import Data.Typeable

onKeyDown
  :: ( Typeable event
     , Eq event
     , Show event
     )
  => (Maybe String -> event) -> Purview event m -> Purview event m
onKeyDown = Attribute . On "keydown" Nothing

In addition to this, you'll need to add "keydown" to the list of events listened for in the configuration at the top like so:

import Purview.Server (defaultConfiguration, serve, Configuration( eventsToListenTo ))

newConfig =
  let events = eventsToListenTo defaultConfiguration
  in defaultConfiguration { eventsToListenTo="keydown":events }

main = serve newConfig $ const $ div []

This is hopefully short-lived and going away in a coming version.

onClick :: (Typeable event, Eq event, Show event) => event -> Purview event m -> Purview event m Source #

This will send the event to the handler above it whenever "click" is triggered on the frontend. It will be bound to whichever concrete HTML is beneath it.

Example:

To send a string based event:

toggleButton :: Purview String m
toggleButton = onClick "toggle" $ button []

To send a better typed event:

data Toggle = Toggle
  deriving (Show, Eq)

toggleButton :: Purview Toggle m
toggleButton = onClick Toggle $ button []

Note how the type changed to show which kind of event is produced.

onSubmit :: (Typeable event, Eq event, Show event) => (Maybe String -> event) -> Purview event m -> Purview event m Source #

This will send the event to the handler above it whenever "submit" is triggered on the frontend. It takes a function to transform the value received into an event for handlers, this can be a good spot to debug trace and see what is being received from the browser.

The form produces JSON so the handling function can also be used to parse the form, or you can throw it up as a string for the handler to parse.

Example:

nameAttr = Attribute . Generic "name"

data FormEvent = Submitted String
  deriving (Show, Eq)

handleSubmit (Just val) = Submitted val
handleSubmit Nothing    = Submitted ""

component :: Purview FormEvent m
component = onSubmit handleSubmit $
  form
    [ nameAttr "text" $ input []
    ]

onBlur :: (Typeable event, Eq event, Show event) => (Maybe String -> event) -> Purview event m -> Purview event m Source #

This is triggered on focusout instead of blur to work with mobile sites as well. Like onSubmit it takes a value.

Example:

data AddressEvent = LineOneUpdated String
  deriving (Show, Eq)

handleBlur (Just val) = LineOneUpdated val
handleBlur Nothing    = LineOneUpdated ""

addressLineOne = onBlur handleBlur $ input []

onChange :: (Typeable event, Eq event, Show event) => (Maybe String -> event) -> Purview event m -> Purview event m Source #

Triggered on change

Example:

data AddressEvent = LineOneUpdated String
  deriving (Show, Eq)

handleChange (Just val) = LineOneUpdated val
handleChange Nothing    = LineOneUpdated ""

addressLineOne = onChange handleChange $ input []

Interop

While the receiver covers receiving events, here's how you can call javascript functions:

Example:

Here whenever "increment" is received by the handler, it produces a new Browser event. This calls window.addMessage in the browser, with an argument of the "show newState" -- so, a String.

countHandler = handler' [] (0 :: Int) reducer
  where
    reducer "increment" state =
      let newState = state + 1
      -- this being the important bit, you can call any function in javascript
      -- with the Brower fnName value event.
      in (newState, [Browser "addMessage" (show newState)])

jsMessageAdder = [r|
  const addMessage = (value) => {
    const messagesBlock = document.querySelector("#messages");
    messagesBlock.innerHTML = value;
  }
  -- important, otherwise it won't be able to find the function
  window.addMessage = addMessage;
|]

main = serve (defaultConfiguration { javascript=jsMessageAdder }

receiver :: (Show event, Eq event, Typeable event) => String -> (Maybe String -> event) -> (state -> Purview event m) -> state -> Purview event m Source #

For receiving events from Javascript. In addition to the name and an event producer, the receiver takes in a state and child and passes it through for (hopefully) more natural composition with handlers.

Example:

This receives an event from javascript every 1 second and increments the count.

component count = div [ text (show count) ]

countHandler = handler' [] (0 :: Int) reducer
  where
    reducer "increment" state = (state + 1, [])
    reducer "decrement" state = (state - 1, [])

countReceiver = receiver "incrementReceiver" (const "increment")

render = countHandler . countReceiver $ component

jsCounter = [r|
  const startCount = () => {
    window.setInterval(() => {
      -- sendEvent is added to the window by Purview and all that's
      -- needed.  Purview finds the receiver by name.
      sendEvent("incrementReceiver", "increment")
    }, 1000)
  }
  startCount()
|]

main = serve defaultConfiguration { javascript=jsCounter } render

Testing

render :: Purview action m -> String Source #

Takes the tree and turns it into HTML. Attributes are passed down to children until they reach a real HTML tag.

AST

data Attributes event where Source #

Attributes are collected until an HTML constructor is hit, where they are applied during rendering.

Constructors

On 

Fields

Style 

Fields

Generic 

Fields

  • :: String
     
  • -> String
     
  • -> Attributes event

    for creating new Attributes to put on HTML, e.g. Generic "type" "radio" for type="radio".

Instances

Instances details
Show (Attributes event) Source # 
Instance details

Defined in Component

Methods

showsPrec :: Int -> Attributes event -> ShowS #

show :: Attributes event -> String #

showList :: [Attributes event] -> ShowS #

Eq (Attributes event) Source # 
Instance details

Defined in Component

Methods

(==) :: Attributes event -> Attributes event -> Bool #

(/=) :: Attributes event -> Attributes event -> Bool #

data DirectedEvent a b where Source #

This is for creating events that should go to a parent handler, or sent back in to the same handler.

Constructors

Parent :: (Show a, Eq a) => a -> DirectedEvent a b 
Self :: (Show b, Eq b) => b -> DirectedEvent a b 
Browser :: String -> String -> DirectedEvent a b 

data Purview event m where Source #

This is what you end up building using the various helpers. It's hopefully rare that you have to use these directly, but it may be useful to better understand what's happening behind the scenes.

Constructors

Attribute :: Attributes event -> Purview event m -> Purview event m 
Html :: String -> [Purview event m] -> Purview event m 

Instances

Instances details
Show (Purview event m) Source # 
Instance details

Defined in Component

Methods

showsPrec :: Int -> Purview event m -> ShowS #

show :: Purview event m -> String #

showList :: [Purview event m] -> ShowS #

Eq (Purview event m) Source # 
Instance details

Defined in Component

Methods

(==) :: Purview event m -> Purview event m -> Bool #

(/=) :: Purview event m -> Purview event m -> Bool #