haste (same language, multiple platforms) and tagless final style (same syntax, multiple...

48
Haste Same Language, Multiple latforms Tagless Final Style Same Syntax, Multiple nterpretations Nathan Sorenson @takeoutweight i p

Upload: takeoutweight

Post on 10-Sep-2014

3.076 views

Category:

Software


4 download

DESCRIPTION

I discuss Haste, which compiles Haskell code to Javascript to be run on the browser. I then cover Tagless Final Style, which is a technique for creating flexible and extensible DSLs.

TRANSCRIPT

Page 1: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

HasteSame Language, Multiple latforms

Tagless Final StyleSame Syntax, Multiple nterpretations

Nathan Sorenson@takeoutweight

i

p

Page 2: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

haste-lang.org

A Haskell-to-Javascript Compilercreated by Anton Ekblad

Page 3: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

+ Full Haskell 2010 Support (Proper Numbers, Lazy, Pure, Type Classes, …)

+ Nearly all GHC extensions+ Supports large amount of Hackage+ Cabal-style build+ Compact output (~2k hello world)

+ Fast+ Javascript FFI+ Browser API

Page 4: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

- No Template Haskell- No GHCi- No forkIO- No Weak Pointers

Page 5: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

Elm Haskell-inspired. Strict. Structural typing and FRP.

Purescript Haskell-inspired. Strict. Structural typing and Effect typing.

Fay Haskell subset. Lazy. Small & Fast code. No type classes.

GHCJS Full GHC. Big runtime with GC, Thread scheduler, etc

Page 6: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

Browser-Friendly GHC-Compatible

ElmPureScript

Fay GHCJSHaste

Page 7: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

ghc-7.4.2.9: The GHC API

parseModule :: GhcMonad m => ModSummary → m ParsedModuletypeCheckModule :: GhcMonad m => ParsedModule → m TypecheckedModuledesugarModule :: GhcMonad m => TypecheckedModule → m DesugaredModulecoreToStg :: DynFlags → CoreProgram → IO [ StgBinding ]

Page 8: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

+---------+ LLVM backend /--->| LLVM IR |--\ | +---------+ | LLVM | v +------------+ Desugar +------+ STGify +-----+ CodeGen +-----+ | NCG +----------+ | Parse tree |--------->| Core |-------->| STG |--------->| C-- |----+-------->| Assembly | +------------+ +------+ +-----+ +-----+ | +----------+ | ^ | +---+ | GCC C backend \---->| C |--/ +---+

https://ghc.haskell.org/trac/ghc/wiki/Commentary/Compiler/GeneratedCode

ghc-7.4.2.9: The GHC API

Page 9: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

module StgSyn where

data GenStgExpr bndr occ Source = StgApp occ [GenStgArg occ] | StgLit Literal | StgConApp DataCon [GenStgArg occ] | StgOpApp StgOp [GenStgArg occ] Type | StgLam Type [bndr] StgExpr | StgCase (GenStgExpr bndr occ) (GenStgLiveVars occ) … | StgLet (GenStgBinding bndr occ) (GenStgExpr bndr occ) | StgLetNoEscape (GenStgLiveVars occ) (GenStgLiveVars … | StgSCC CostCentre !Bool !Bool (GenStgExpr bndr occ) | StgTick Module Int (GenStgExpr bndr occ)

Page 10: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

module Data.JSTarget.AST where

-- | Expressions. Completely predictable.data Exp where Var :: Var → Exp Lit :: Lit → Exp Not :: Exp → Exp BinOp :: BinOp → Exp → Exp → Exp Fun :: Maybe Name → [Var] → Stm → Exp Call :: Arity → Call → Exp → [Exp] → Exp Index :: Exp → Exp → Exp Arr :: [Exp] → Exp AssignEx :: Exp → Exp → Exp IfEx :: Exp → Exp → Exp → Exp deriving (Eq, Show)

Page 11: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

https://ghc.haskell.org/trac/ghc/ticket/3693

Page 12: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)
Page 13: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

Installing

$ cabal install haste-compiler $ haste-boot

# Or from source$ git clone https://github.com/valderman/haste-compiler.git$ cd haste-compiler$ cabal sandbox init$ cabal install$ haste-boot --local

Page 14: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

Building a Haste Project

$ hastec Main.hs # → Main.js

$ hastec --start=asap Main.hs # node Main.js

# Or with via cabal-install$ haste-inst configure $ haste-inst build

# installing dependencies (if lucky)$ haste-inst install contravariant mtl semigroups

Page 15: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

Remove Haste Unfriendly Things

use Cabal build-type: Simple, not Custom

remove use of Template Haskell

remove use of ‘vector’ package

# installing dependencies (if unlucky)$ cabal unpack time# … remove Haste Unfriendly Things …$ haste-inst configure$ haste-inst build --install-jsmods --ghc-options=-UHLINT$ haste-install-his time-1.4.2 dist/build $ haste-copy-pkg time-1.4.2 --package-db=dist/package.conf.inplace

Page 16: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

./libraries/haste-libmodule Haste.DOMaddChild :: MonadIO m => Elem → Elem → m ()elemById :: MonadIO m => ElemID → m (Maybe Elem)

module Haste.JSONencodeJSON :: JSON → JSStringdecodeJSON :: JSString → Either String JSON

module Haste.Graphics.CanvassetFillColor :: Color → Picture ()line :: Point → Point → Shape ()

module Haste.Concurrent.MonadforkIO :: CIO () → CIO ()putMVar :: MVar a → a → CIO ()

Page 17: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

FFI// javascript.jsfunction jsGetAttr(elem, prop) { return elem.getAttribute(prop).toString();}

-- haskell.hs (compile-time ffi)foreign import ccall jsGetAttr :: Elem → JSString → IO JSString

-- (in-line javascript, run-time ffi)f :: String → String → IO Intf a b = ffi “(function (a,b) {window.tst = a; return 3;})” a b

-- expose to JS, via Haste[“myInc”] or Haste.myIncexport :: FFI a => JSString → a → IO ()export “myInc” ((\x -> return (x + 1)) :: Int → IO Int)

// javascript.jsHaste.myInc(3) // 4

Page 18: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

facebook.github.io/react

Page 19: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

<div id=“mydiv”> <button>clickme</button></div>

React.DOM.div({idName:“mydiv”}, [React.DOM.button({}, [“clickme”])])

Page 20: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

React.DOM.div({idName:“mydiv”}, [React.DOM.button({}, [“clickme”])])

<div id=“mydiv”> <button>click{{me}}</button></div>

Page 21: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

function(me) { return React.DOM.div({idName:“mydiv”}, [React.DOM.button({}, [“click”+me])]);}

<div id=“mydiv”> <button>click{{me}}</button></div>

Page 22: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

div :: [Attr] → [JSPtr] → JSPtrbutton :: [Attr] → [JSPtr] → JSPtrtext :: String → JSPtr

EDSL

Page 23: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

div :: [Attr] → [JSPtr] → JSPtrbutton :: [Attr] → [JSPtr] → JSPtrtext :: String → JSPtr

EDSSEmbedded Domain Specific Syntax

Page 24: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

Tagless Final Style

Page 25: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

Tagless Final Style

Discovered by Oleg Kiselyov

Page 26: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

Tagless Final Style

Discovered by Oleg Kiselyov

But don’t be scared.

Page 27: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

Initial Styledata Html = Div [Attr] [Html] | Button [Attr] [Html] | Text String

client :: Html → JSPtrclient (Div attrs children) = …client (Button attrs children) = …client (Text str) = …

server :: Html → Stringserver (Div attrs children) = …server (Button attrs children) = …server (Text str) = …

i

i

Page 28: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

server :: Html → String

server (Div attrs children) = “<div” ++ show attrs ++ “>” ++ concatMap server children ++ “</div>”

server (Button attrs children) = “<button” ++ show attrs ++ “>” ++ concatMap server children ++ “</button>”

server (Text str) = str

Page 29: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

Initial Styledata Html = Div [Attr] [Html] | Button [Attr] [Html] | Text String

Page 30: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

class Html i where div :: [Attr] → [ i ] → i button :: [Attr] → [ i ] → i text :: String → i

Final Style

Page 31: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

Final Styleclass Html i where div :: [Attr] → [i] → i button :: [Attr] → [i] → i text :: String → i

-- Initial Styledata Html = Div [Attr] [Html] | Button [Attr] [Html] | Text String

Page 32: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

Final Styleclass Html i where div :: [Attr] → [i] → i button :: [Attr] → [i] → i text :: String → i

-- Initial Style (GADT)data Html where Div :: [Attr] → [Html] → Html Button :: [Attr] → [Html] → Html Text :: String → Html

Page 33: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

Final Styleclass Html i where div :: [Attr] → [i] → i button :: [Attr] → [i] → i text :: String → i

instance Html String where div attrs children = … button attrs children = … text str = …

instance Html JSPtr where div attrs children = … button attrs children = … text str = …

i

i

Page 34: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

srv :: Html→String

srv (Div attrs children) = “<div” ++ show attrs ++ “>” ++ concatMap srv children ++ “</div>”

srv (Button attrs children) = “<button” ++ show attrs ++ “>” ++ concatMap srv children ++ “</button>”

srv (Text str) = str

Page 35: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

instance Html String where

div attrs children = “<div” ++ show attrs ++ “>” ++ concatMap srv children ++ “</div>”

button attrs children = “<button” ++ show attrs ++ “>” ++ concatMap srv children ++ “</button>”

text str = str

Page 36: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

instance Html String where-- div :: [Attr] → [i] → i div attrs children = “<div” ++ show attrs ++ “>” ++ concatMap ??? children ++ “</div>”-- button :: [Attr] → [i] → i button attrs children = “<button” ++ show attrs ++ “>” ++ concatMap ??? children ++ “</button>”-- text:: String → i text str = str

Page 37: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

instance Html String where-- div :: [Attr] → [i] → i div attrs children = “<div” ++ show attrs ++ “>” ++ concatMap id children ++ “</div>”-- button :: [Attr] → [i] → i button attrs children = “<button” ++ show attrs ++ “>” ++ concatMap id children ++ “</button>”-- text:: String → i text str = str

Page 38: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

instance Html String where-- div :: [Attr] → [i] → i div attrs children = “<div” ++ show attrs ++ “>” ++ concat children ++ “</div>”-- button :: [Attr] → [i] → i button attrs children = “<button” ++ show attrs ++ “>” ++ concat children ++ “</button>”-- text:: String → i text str = str

Page 39: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

-- Initial Stylei :: Htmli = Div [] [(Button [] [Text “clickMe”])]

iOut :: StringiOut = server i

-- Final Style

f :: (Html i) => if = div [] [(button [] [text “clickMe”])]

fOut = f :: String

Page 40: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

class Math (i :: * ) where lit :: Int → i (+) :: i → i → i (>) :: i → i → i

instance Math Int where …instance Math String where …

i

i

Page 41: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

class Math (i :: *→*) where lit :: Int → i Int (+) :: i Int → i Int → i Int (>) :: i Int → i Int → i Bool

Page 42: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

class Math (i :: *→*) where lit :: Int → i Int (+) :: i Int → i Int → i Int (>) :: i Int → i Int → i Bool

newtype Eval a = Eval {eval :: a}instance Math Eval where …

newtype Pretty a = Pretty {pp :: String}instance Math Pretty where …

a = (lit 1) > ((lit 2) + (lit 3))e = eval a -- Falsep = pp a -- “(1 > (2 + 3))”

i

i

Page 43: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

class Html i where div :: [Attr] → [i] → i button :: [Attr] → [i] → i text :: String → i

instance SafariHtml String where webkitElt attrs children) = …

instance SafariHtml JSPtr where webkitElt attrs children) = …

class SafariHtml i where webkitElt :: [Attr] → [i] → i

Language Extensibility

i

i

Page 44: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

f :: (Html i, SafariHtml i) => if = div [] [(webkitElt [] [text “clickMe”])]

fOut = f :: String

Language Extensibility

Page 45: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

div :: (Attr a, Html i) => [a] → [i] → i-- div [idName “mydiv”] []

button :: (Attr a, Html i) => [a] → [i] → i-- button [idName “mybtn”, disabled True] []

class Attr a where idName :: String → a disabled :: Bool → a

instance Attr DivAttr where idName s = … disabled b = … instance Attr ButtonAttr where

idName s = … disabled b = …

newtype ButtonAttrnewtype DivAttr i

i

Page 46: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

div :: (Html i) => [DivAttr] → [i] → i-- div [idName “mydiv”] []

button :: (Html i) => [ButtonAttr] → [i] → i-- button [idName “mybtn”, disabled True] []

class IdA a where idName :: String → aclass DisabledA a where disabled :: Bool → a

instance IdA ButtonAttr where idName s = …

instance DisabledA ButtonAttr where disabled b = …

newtype ButtonAttrinstance IdA DivAttr where idName s = …

newtype DivAttr i

i

i

Page 47: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

type src form<img>

instance SrcA ImgAttr

<input>instance

TypeA InputAttrinstance

SrcA InputAttrinstance

FormA InputAttr

<button>instance

TypeA ButtonAttrinstance

FormA ButtonAttr

<label>instance

FormA LabelAttr

i

i

i

i i

i

i

Page 48: Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

Typed Tagless Final Course Notesokmij.org/ftp/tagless-final/course/lecture.pdf

haste-lang.org

“Haskell in the Browser With Haste” Lars Kuhtzalephcloud.github.io/bayhac2014/slides

facebook.github.io/react

github.com/takeoutweight @takeoutweight