Shpadoinkle-0.0.0.1: A programming model for declarative, high performance, user interface.

Safe HaskellNone
LanguageHaskell2010

Shpadoinkle

Description

I think I know precisely what I mean.

A frontend abstraction motivated by simplicity, performance, and egonomics. This module provides core abstractions and types with almost no implimentation details. IE no batteries included. You may use this model a la carte, build ontop of it, or include more Backend packages for additional batteries.

Backend is focused on letting you build your frontend the way you want to. And so is as unopinionated as possible, beyond providing a concrete programming model.

Synopsis

Documentation

data Html :: (Type -> Type) -> Type -> Type where Source #

This is the core type in Backend. The (Html m) Functor is used to describe Html documents. Please note, this is NOT a the Virtual Dom used by Backend this type backs a DSL that is then interpreted into Virual Dom by the backend of your choosing. Html comments are not supported.

Constructors

Node :: Text -> [(Text, Prop m o)] -> [Html m o] -> Html m o

A standard node in the dom tree

Potato :: JSM RawNode -> Html m o

If you can bake an element into a RawNode you can embed it as a baked potato. Backend does not provide any state management or abstraction to deal with custom embeded content. It's own you to decide how and when this RawNode will be updated. For example, if you wanted to embed a google map as a baked potato, and you are driving your Backend view with a TVar, you would need to build the RawNode for this map outside of your Backend view, and pass it in as an argument. The RawNode is a reference you control.

TextNode :: Text -> Html m o

The humble text node

Instances
Functor m => Functor (Html m) Source #

(Html m) is not a Monad, and not even Applicative, by design.

Instance details

Defined in Shpadoinkle

Methods

fmap :: (a -> b) -> Html m a -> Html m b #

(<$) :: a -> Html m b -> Html m a #

IsString (Html m o) Source #

Strings are overload to html text nodes "hiya" = TextNode "hiya"

Instance details

Defined in Shpadoinkle

Methods

fromString :: String -> Html m o #

data Prop m o where Source #

Properties of a Dom node, Backend does not use attributes directly, but rather is focued on the more capable properties that may be set on a dom node in JavaScript. If you wish to add attributes, you may do so by setting its corrosponding property.

Constructors

PText :: Text -> Prop m o

A text property

PListener :: (RawNode -> RawEvent -> m o) -> Prop m o

Event listeners are provided with the RawNode target, and the RawEvent, and may perform a Monadic action such as a side effect. This is the one and only place where you may introduce a custom Monadic action.

PFlag :: Bool -> Prop m o

A boolean property, works as a flag for example ("disabled", PFlag False) has no effect while ("disabled", PFlag True) will add the disabled attribute

Instances
Functor m => Functor (Prop m) Source #

Props are also merely Functors not Monads and not Applicative by design.

Instance details

Defined in Shpadoinkle

Methods

fmap :: (a -> b) -> Prop m a -> Prop m b #

(<$) :: a -> Prop m b -> Prop m a #

IsString [(Text, Prop m o)] Source #

Strings are overload as the class property "active" = ("className", PText "active")

Instance details

Defined in Shpadoinkle

Methods

fromString :: String -> [(Text, Prop m o)] #

IsString (Prop m o) Source #

Strings are overload as text props ("id", "foo") = ("id", PText "foo")

Instance details

Defined in Shpadoinkle

Methods

fromString :: String -> Prop m o #

type Props m o = [(Text, Prop m o)] Source #

Type alias for convenience. Typing out the nested brackets is tiresome.

mapHtml :: Functor m => (m ~> n) -> Html m o -> Html n o Source #

If you can provide a Natural Transformation from one Monad to another you may change the action of Html

mapProp :: (m ~> n) -> Prop m o -> Prop n o Source #

If you can provide a Natural Transformation from one Monad to another you may change the action of Prop

mapProps :: ([(Text, Prop m o)] -> [(Text, Prop m o)]) -> Html m o -> Html m o Source #

Transform the properites of some Node. This has no effect on TextNodes or Potatos

mapChildren :: ([Html m a] -> [Html m a]) -> Html m a -> Html m a Source #

Transform the children of some Node. This has no effect on TextNodes or Potatos

class Backend b m a | b m -> a where Source #

patch raw Nothing >=> patch raw Nothing = patch raw Nothing

The Backend class describes a backend that can render Html. Backends are generally Monad Transformers b over some Monad m.

Associated Types

type VNode b m Source #

VNode type family allows backends to have their own Virtual Dom. As such we can change out the rendering of our Backend view with new backends without updating our view logic.

Methods

interpret Source #

Arguments

:: (m ~> JSM)

Natural transformation for some m to JSM. This is how Backend get access to JSM to perform the rendering side effect

-> Html (b m) a

Html to interpret

-> b m (VNode b m)

Effect producing the Virtual Dom representation

A backend must be able to interpret Html into its own internal Virtual Dom

patch Source #

Arguments

:: RawNode

The container for rendering the Backend view.

-> Maybe (VNode b m)

Perhaps there is a previous Virtual Dom for use to diff. Will be Nothing on the first run.

-> VNode b m

New Virtual Dom to render.

-> b m (VNode b m)

Effect producing and updated virtual dom. This is not needed by all backends. Some JavaScript based backends need to do this for the next tick. Regardless whatever VNode the effect produces will be passed as the previous Virtual Dom on the next render.

A backend must be able to patch the RawNode containing the view, with a new view if the Virtual Dom changed.

setup :: JSM () -> b m () Source #

A backend may perform some inperative setup steps

shpadoinkle Source #

Arguments

:: Backend b m a 
=> Territory t 
=> Eq a 
=> (m ~> JSM)

how to be get to JSM?

-> (t a -> b m ~> m)

What backend are we running?

-> a

what is the initial state?

-> t a

how can we know when to update?

-> (a -> Html (b m) a)

how should the html look?

-> b m RawNode

where do we render?

-> JSM () 

The core view instantiation function. This combines a backend, a territory, and a model and renders the Backend view to the page.

fullPage Source #

Arguments

:: Backend b m a 
=> Territory t 
=> Eq a 
=> (m ~> JSM)

how do we get to JSM?

-> (t a -> b m ~> m)

What backend are we running?

-> a

what is the initial state?

-> (a -> Html (b m) a)

how should the html look?

-> b m RawNode

where do we render?

-> JSM () 

Wrapper around shpadoinkle for full page apps that do not need outside control of the territory

fullPageJSM Source #

Arguments

:: Backend b JSM a 
=> Territory t 
=> Eq a 
=> (t a -> b JSM ~> JSM)

What backend are we running?

-> a

what is the initial state?

-> (a -> Html (b JSM) a)

how should the html look?

-> b JSM RawNode

where do we render?

-> JSM () 

Wrapper around shpadoinkle for full page apps that do not need outside control of the territory where actions are performed directly in JSM.

This set of assumptions is extremely common when starting a new project.

class Territory s where Source #

Shpadoinkling requires a Territory, such as Colorado Territory. This class provides for the state container. As such you may use any type you wish where this semantic can be implimented.

Methods

writeUpdate :: s a -> (a -> JSM a) -> JSM () Source #

How do we update the state?

shouldUpdate :: Eq a => (b -> a -> JSM b) -> b -> s a -> JSM () Source #

When should consider a state updated? This is akin to React's component should update thing. The idea is to provide a semantic for when we consider the model to have changed.

createTerritory :: a -> JSM (s a) Source #

Create a new territory

Instances
Territory TVar Source #

Cannoncal default implimentation of Territory is just a TVar. However there is nothing stopping your from writing your own alternative for a Dynamic t from Reflex Dom, or some JavaScript based container.

Instance details

Defined in Shpadoinkle

Methods

writeUpdate :: TVar a -> (a -> JSM a) -> JSM () Source #

shouldUpdate :: Eq a => (b -> a -> JSM b) -> b -> TVar a -> JSM () Source #

createTerritory :: a -> JSM (TVar a) Source #

type (~>) m n = forall a. m a -> n a Source #

Natural Transformation

type Html' a = forall m. Applicative m => Html m a Source #

A type alias to support scenarios where the view code event listeners are pure.

newtype RawNode Source #

A dom node reference. Useful for building baked potatoes, and binding a Backend view to the page

Constructors

RawNode 

Fields

newtype RawEvent Source #

A raw event object reference

Constructors

RawEvent 

Fields

h :: Text -> [(Text, Prop m o)] -> [Html m o] -> Html m o Source #

JSX style h constructor

text :: Text -> Html m o Source #

Construct a TextNode

flag :: Bool -> Prop m o Source #

Construct a PFlag

listener :: m o -> Prop m o Source #

Construct a simple PListener that will perform an action.

listen :: Text -> m o -> (Text, Prop m o) Source #

Construct a PListener from it's Text name and a Monad action.

listenRaw :: Text -> (RawNode -> RawEvent -> m o) -> (Text, Prop m o) Source #

Construct a PListener from it's Text name a raw listener.

listen' :: Applicative m => Text -> o -> (Text, Prop m o) Source #

Construct a PListener from it's Text name and an ouput value.

baked :: JSM RawNode -> Html m o Source #

Construct a Potato from a JSM action producing a RawNode

props :: Applicative f => ([(Text, Prop m a)] -> f [(Text, Prop m a)]) -> Html m a -> f (Html m a) Source #

Lens to props

children :: Applicative f => ([Html m a] -> f [Html m a]) -> Html m a -> f (Html m a) Source #

Lens to children

name :: Applicative f => (Text -> f Text) -> Html m a -> f (Html m a) Source #

Lens to tag name

textContent :: Applicative f => (Text -> f Text) -> Html m a -> f (Html m a) Source #

Lens to content of TextNodes

injectProps :: [(Text, Prop m o)] -> Html m o -> Html m o Source #

Inject props into an existing Node

class (Applicative m, MonadIO m) => MonadJSM (m :: Type -> Type) #

The MonadJSM is to JSM what MonadIO is to IO. When using GHCJS it is MonadIO.

Instances
MonadJSM JSM 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> JSM a #

MonadJSM m => MonadJSM (MaybeT m) 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> MaybeT m a #

MonadJSM m => MonadJSM (ListT m) 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> ListT m a #

MonadJSM m => MonadJSM (IdentityT m) 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> IdentityT m a #

MonadJSM m => MonadJSM (ExceptT e m) 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> ExceptT e m a #

(Error e, MonadJSM m) => MonadJSM (ErrorT e m) 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> ErrorT e m a #

MonadJSM m => MonadJSM (StateT s m) 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> StateT s m a #

MonadJSM m => MonadJSM (ReaderT r m) 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> ReaderT r m a #

MonadJSM m => MonadJSM (StateT s m) 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> StateT s m a #

(Monoid w, MonadJSM m) => MonadJSM (WriterT w m) 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> WriterT w m a #

(Monoid w, MonadJSM m) => MonadJSM (WriterT w m) 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> WriterT w m a #

MonadJSM m => MonadJSM (ContT r m) 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> ContT r m a #

(Monoid w, MonadJSM m) => MonadJSM (RWST r w s m) 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> RWST r w s m a #

(Monoid w, MonadJSM m) => MonadJSM (RWST r w s m) 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> RWST r w s m a #

data JSM a #

The JSM monad keeps track of the JavaScript execution context.

When using GHCJS it is IO.

Given a JSM function and a JSContextRef you can run the function like this...

runJSM jsmFunction javaScriptContext
Instances
Monad JSM 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

(>>=) :: JSM a -> (a -> JSM b) -> JSM b #

(>>) :: JSM a -> JSM b -> JSM b #

return :: a -> JSM a #

fail :: String -> JSM a #

Functor JSM 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

fmap :: (a -> b) -> JSM a -> JSM b #

(<$) :: a -> JSM b -> JSM a #

MonadFix JSM 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

mfix :: (a -> JSM a) -> JSM a #

MonadFail JSM 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

fail :: String -> JSM a #

Applicative JSM 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

pure :: a -> JSM a #

(<*>) :: JSM (a -> b) -> JSM a -> JSM b #

liftA2 :: (a -> b -> c) -> JSM a -> JSM b -> JSM c #

(*>) :: JSM a -> JSM b -> JSM b #

(<*) :: JSM a -> JSM b -> JSM a #

MonadIO JSM 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftIO :: IO a -> JSM a #

MonadThrow JSM 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

throwM :: Exception e => e -> JSM a #

MonadCatch JSM 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

catch :: Exception e => JSM a -> (e -> JSM a) -> JSM a #

MonadMask JSM 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

mask :: ((forall a. JSM a -> JSM a) -> JSM b) -> JSM b #

uninterruptibleMask :: ((forall a. JSM a -> JSM a) -> JSM b) -> JSM b #

generalBracket :: JSM a -> (a -> ExitCase b -> JSM c) -> (a -> JSM b) -> JSM (b, c) #

MonadJSM JSM 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> JSM a #

MonadRef JSM 
Instance details

Defined in Language.Javascript.JSaddle.Types

Associated Types

type Ref JSM :: Type -> Type #

Methods

newRef :: a -> JSM (Ref JSM a) #

readRef :: Ref JSM a -> JSM a #

writeRef :: Ref JSM a -> a -> JSM () #

modifyRef :: Ref JSM a -> (a -> a) -> JSM () #

modifyRef' :: Ref JSM a -> (a -> a) -> JSM () #

MonadAtomicRef JSM 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

atomicModifyRef :: Ref JSM a -> (a -> (a, b)) -> JSM b #

atomicModifyRef' :: Ref JSM a -> (a -> (a, b)) -> JSM b #

MonadUnliftIO JSM 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

askUnliftIO :: JSM (UnliftIO JSM) #

withRunInIO :: ((forall a. JSM a -> IO a) -> IO b) -> JSM b #

MakeArgs arg => MakeArgs (JSM arg) 
Instance details

Defined in Language.Javascript.JSaddle.Classes.Internal

Methods

makeArgs :: JSM arg -> JSM [JSVal] #

type Ref JSM 
Instance details

Defined in Language.Javascript.JSaddle.Types

type Ref JSM = Ref IO

liftJSM :: MonadJSM m => JSM a -> m a #

The liftJSM is to JSM what liftIO is to IO. When using GHCJS it is liftIO.

newTVarIO :: MonadIO m => a -> m (TVar a) #

Lifted version of newTVarIO

Since: unliftio-0.2.1.0

readTVarIO :: MonadIO m => TVar a -> m a #

Lifted version of readTVarIO

Since: unliftio-0.2.1.0

runJSorWarp :: Int -> JSM () -> IO () Source #

Start the program!

For GHC or GHCjs. I saved your from using CPP directly. Your welcome.

runJSM :: MonadIO m => JSM a -> JSContextRef -> m a #

Runs a JSM JavaScript function in a given JavaScript context.

askJSM :: MonadJSM m => m JSContextRef #

Gets the JavaScript context from the monad