SlideShare a Scribd company logo
1 of 48
Haste
Same Language, Multiple latforms
Tagless Final Style
Same Syntax, Multiple nterpretations
Nathan Sorenson
@takeoutweight
i
p
haste-lang.org
A Haskell-to-Javascript Compiler
created by Anton Ekblad
+ 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
- No Template Haskell
- No GHCi
- No forkIO
- No Weak Pointers
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
Browser-Friendly GHC-Compatible
Elm
PureScript
Fay GHCJSHaste
ghc-7.4.2.9: The GHC API
parseModule :: GhcMonad m => ModSummary → m ParsedModule
typeCheckModule :: GhcMonad m => ParsedModule → m TypecheckedModu
desugarModule :: GhcMonad m => TypecheckedModule → m DesugaredModule
coreToStg :: DynFlags → CoreProgram → IO [ StgBinding ]
+---------+
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
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)
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)
https://ghc.haskell.org/trac/ghc/ticket/3693
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
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
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
./libraries/haste-lib
module Haste.DOM
addChild :: MonadIO m => Elem → Elem → m ()
elemById :: MonadIO m => ElemID → m (Maybe Elem)
module Haste.JSON
encodeJSON :: JSON → JSString
decodeJSON :: JSString → Either String JSON
module Haste.Graphics.Canvas
setFillColor :: Color → Picture ()
line :: Point → Point → Shape ()
module Haste.Concurrent.Monad
forkIO :: CIO () → CIO ()
putMVar :: MVar a → a → CIO ()
FFI
// javascript.js
function 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 Int
f a b = ffi “(function (a,b) {window.tst = a; return 3;})” a b
-- expose to JS, via Haste[“myInc”] or Haste.myInc
export :: FFI a => JSString → a → IO ()
export “myInc” ((x -> return (x + 1)) :: Int → IO Int)
// javascript.js
Haste.myInc(3) // 4
facebook.github.io/react
<div id=“mydiv”>
<button>clickme</button>
</div>
React.DOM.div({idName:“mydiv”},
[React.DOM.button({},
[“clickme”])])
React.DOM.div({idName:“mydiv”},
[React.DOM.button({},
[“clickme”])])
<div id=“mydiv”>
<button>click{{me}}</button>
</div>
function(me) {
return React.DOM.div({idName:“mydiv”},
[React.DOM.button({},
[“click”+me])]);
}
<div id=“mydiv”>
<button>click{{me}}</button>
</div>
div :: [Attr] → [JSPtr] → JSPtr
button :: [Attr] → [JSPtr] → JSPtr
text :: String → JSPtr
EDSL
div :: [Attr] → [JSPtr] → JSPtr
button :: [Attr] → [JSPtr] → JSPtr
text :: String → JSPtr
EDSS
Embedded Domain Specific Syntax
Tagless Final Style
Tagless Final Style
Discovered by Oleg Kiselyov
Tagless Final Style
Discovered by Oleg Kiselyov
But don’t be scared.
Initial Style
data Html = Div [Attr] [Html]
| Button [Attr] [Html]
| Text String
client :: Html → JSPtr
client (Div attrs children) = …
client (Button attrs children) = …
client (Text str) = …
server :: Html → String
server (Div attrs children) = …
server (Button attrs children) = …
server (Text str) = …
i
i
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
Initial Style
data Html =
Div [Attr] [Html]
| Button [Attr] [Html]
| Text String
class Html i where
div :: [Attr] → [ i ] → i
button :: [Attr] → [ i ] → i
text :: String → i
Final Style
Final Style
class Html i where
div :: [Attr] → [i] → i
button :: [Attr] → [i] → i
text :: String → i
-- Initial Style
data Html =
Div [Attr] [Html]
| Button [Attr] [Html]
| Text String
Final Style
class 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
Final Style
class 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
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
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
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
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
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
-- Initial Style
i :: Html
i = Div [] [(Button [] [Text “clickMe”])]
iOut :: String
iOut = server i
-- Final Style
f :: (Html i) => i
f = div [] [(button [] [text “clickMe”])]
fOut = f :: String
class Math (i :: * ) where
lit :: Int → i
(+) :: i → i → i
(>) :: i → i → i
instance Math Int where …
instance Math String where …
i
i
class Math (i :: *→*) where
lit :: Int → i Int
(+) :: i Int → i Int → i Int
(>) :: i Int → i Int → i Bool
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 -- False
p = pp a -- “(1 > (2 + 3))”
i
i
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
f :: (Html i, SafariHtml i) => i
f = div [] [(webkitElt [] [text “clickMe”])]
fOut = f :: String
Language Extensibility
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 ButtonAttr
newtype DivAttr
i
i
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 → a
class 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
type src form
<img>
instance
SrcA ImgAttr
<input>
instance
TypeA InputAttr
instance
SrcA InputAttr
instance
FormA InputAttr
<button
>
instance
TypeA ButtonAttr
instance
FormA ButtonAttr
<label>
instance
FormA LabelAttr
i
i
i
i i
i
i
Typed Tagless Final Course Notes
okmij.org/ftp/tagless-final/course/lecture.pdf
haste-lang.org
“Haskell in the Browser With Haste” Lars Kuhtz
alephcloud.github.io/bayhac2014/slides
facebook.github.io/react
github.com/takeoutweight @takeoutweight

More Related Content

Viewers also liked

ダウンサイジング時代のプロセス改善モデル(OHP)
ダウンサイジング時代のプロセス改善モデル(OHP)ダウンサイジング時代のプロセス改善モデル(OHP)
ダウンサイジング時代のプロセス改善モデル(OHP)Makoto SAKAI
 
Key isi guerrilla handler on akhtar abdul rehman
Key isi guerrilla handler on akhtar abdul rehmanKey isi guerrilla handler on akhtar abdul rehman
Key isi guerrilla handler on akhtar abdul rehmanAgha A
 
Taller expedición de datos OPEN DATA - DANE - Sharecollab - Work&Go
Taller expedición de datos  OPEN DATA - DANE -  Sharecollab - Work&GoTaller expedición de datos  OPEN DATA - DANE -  Sharecollab - Work&Go
Taller expedición de datos OPEN DATA - DANE - Sharecollab - Work&GoSharecollab
 
TripDesign.Us presents Eat Play Chill ; #Meghalaya
TripDesign.Us presents Eat Play Chill ; #MeghalayaTripDesign.Us presents Eat Play Chill ; #Meghalaya
TripDesign.Us presents Eat Play Chill ; #MeghalayaRakesh Debur
 
Dove Science Academy Audit - a Gulen operated charter school
Dove Science Academy Audit - a Gulen operated charter schoolDove Science Academy Audit - a Gulen operated charter school
Dove Science Academy Audit - a Gulen operated charter schoolGulen Cemaat
 
Boletín 17/03/2017
Boletín 17/03/2017Boletín 17/03/2017
Boletín 17/03/2017Openbank
 

Viewers also liked (7)

ダウンサイジング時代のプロセス改善モデル(OHP)
ダウンサイジング時代のプロセス改善モデル(OHP)ダウンサイジング時代のプロセス改善モデル(OHP)
ダウンサイジング時代のプロセス改善モデル(OHP)
 
Key isi guerrilla handler on akhtar abdul rehman
Key isi guerrilla handler on akhtar abdul rehmanKey isi guerrilla handler on akhtar abdul rehman
Key isi guerrilla handler on akhtar abdul rehman
 
Taller expedición de datos OPEN DATA - DANE - Sharecollab - Work&Go
Taller expedición de datos  OPEN DATA - DANE -  Sharecollab - Work&GoTaller expedición de datos  OPEN DATA - DANE -  Sharecollab - Work&Go
Taller expedición de datos OPEN DATA - DANE - Sharecollab - Work&Go
 
Ajax 応用
Ajax 応用Ajax 応用
Ajax 応用
 
TripDesign.Us presents Eat Play Chill ; #Meghalaya
TripDesign.Us presents Eat Play Chill ; #MeghalayaTripDesign.Us presents Eat Play Chill ; #Meghalaya
TripDesign.Us presents Eat Play Chill ; #Meghalaya
 
Dove Science Academy Audit - a Gulen operated charter school
Dove Science Academy Audit - a Gulen operated charter schoolDove Science Academy Audit - a Gulen operated charter school
Dove Science Academy Audit - a Gulen operated charter school
 
Boletín 17/03/2017
Boletín 17/03/2017Boletín 17/03/2017
Boletín 17/03/2017
 

Similar to Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations)

Pick up the low-hanging concurrency fruit
Pick up the low-hanging concurrency fruitPick up the low-hanging concurrency fruit
Pick up the low-hanging concurrency fruitVaclav Pech
 
Refactoring to Macros with Clojure
Refactoring to Macros with ClojureRefactoring to Macros with Clojure
Refactoring to Macros with ClojureDmitry Buzdin
 
Groovy for java developers
Groovy for java developersGroovy for java developers
Groovy for java developersPuneet Behl
 
The Ring programming language version 1.5.4 book - Part 40 of 185
The Ring programming language version 1.5.4 book - Part 40 of 185The Ring programming language version 1.5.4 book - Part 40 of 185
The Ring programming language version 1.5.4 book - Part 40 of 185Mahmoud Samir Fayed
 
Is HTML5 Ready? (workshop)
Is HTML5 Ready? (workshop)Is HTML5 Ready? (workshop)
Is HTML5 Ready? (workshop)Remy Sharp
 
Is html5-ready-workshop-110727181512-phpapp02
Is html5-ready-workshop-110727181512-phpapp02Is html5-ready-workshop-110727181512-phpapp02
Is html5-ready-workshop-110727181512-phpapp02PL dream
 
4Developers: Michał Szczepanik- Kotlin - Let’s ketchup it
4Developers: Michał Szczepanik- Kotlin - Let’s ketchup it4Developers: Michał Szczepanik- Kotlin - Let’s ketchup it
4Developers: Michał Szczepanik- Kotlin - Let’s ketchup itPROIDEA
 
Python Peculiarities
Python PeculiaritiesPython Peculiarities
Python Peculiaritiesnoamt
 
Desarrollando aplicaciones web en minutos
Desarrollando aplicaciones web en minutosDesarrollando aplicaciones web en minutos
Desarrollando aplicaciones web en minutosEdgar Suarez
 
JavaScript Advanced - Useful methods to power up your code
JavaScript Advanced - Useful methods to power up your codeJavaScript Advanced - Useful methods to power up your code
JavaScript Advanced - Useful methods to power up your codeLaurence Svekis ✔
 
Building a friendly .NET SDK to connect to Space
Building a friendly .NET SDK to connect to SpaceBuilding a friendly .NET SDK to connect to Space
Building a friendly .NET SDK to connect to SpaceMaarten Balliauw
 
Acceptance Testing with Webrat
Acceptance Testing with WebratAcceptance Testing with Webrat
Acceptance Testing with WebratLuismi Cavallé
 
Unobtrusive javascript with jQuery
Unobtrusive javascript with jQueryUnobtrusive javascript with jQuery
Unobtrusive javascript with jQueryAngel Ruiz
 

Similar to Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Syntax, Multiple Interpretations) (20)

Pick up the low-hanging concurrency fruit
Pick up the low-hanging concurrency fruitPick up the low-hanging concurrency fruit
Pick up the low-hanging concurrency fruit
 
Unfiltered Unveiled
Unfiltered UnveiledUnfiltered Unveiled
Unfiltered Unveiled
 
Refactoring to Macros with Clojure
Refactoring to Macros with ClojureRefactoring to Macros with Clojure
Refactoring to Macros with Clojure
 
Elm: give it a try
Elm: give it a tryElm: give it a try
Elm: give it a try
 
PureScript & Pux
PureScript & PuxPureScript & Pux
PureScript & Pux
 
Introduction to Groovy
Introduction to GroovyIntroduction to Groovy
Introduction to Groovy
 
Groovy for java developers
Groovy for java developersGroovy for java developers
Groovy for java developers
 
JQuery Flot
JQuery FlotJQuery Flot
JQuery Flot
 
The Ring programming language version 1.5.4 book - Part 40 of 185
The Ring programming language version 1.5.4 book - Part 40 of 185The Ring programming language version 1.5.4 book - Part 40 of 185
The Ring programming language version 1.5.4 book - Part 40 of 185
 
Is HTML5 Ready? (workshop)
Is HTML5 Ready? (workshop)Is HTML5 Ready? (workshop)
Is HTML5 Ready? (workshop)
 
Is html5-ready-workshop-110727181512-phpapp02
Is html5-ready-workshop-110727181512-phpapp02Is html5-ready-workshop-110727181512-phpapp02
Is html5-ready-workshop-110727181512-phpapp02
 
4Developers: Michał Szczepanik- Kotlin - Let’s ketchup it
4Developers: Michał Szczepanik- Kotlin - Let’s ketchup it4Developers: Michał Szczepanik- Kotlin - Let’s ketchup it
4Developers: Michał Szczepanik- Kotlin - Let’s ketchup it
 
Python Peculiarities
Python PeculiaritiesPython Peculiarities
Python Peculiarities
 
Desarrollando aplicaciones web en minutos
Desarrollando aplicaciones web en minutosDesarrollando aplicaciones web en minutos
Desarrollando aplicaciones web en minutos
 
JavaScript Advanced - Useful methods to power up your code
JavaScript Advanced - Useful methods to power up your codeJavaScript Advanced - Useful methods to power up your code
JavaScript Advanced - Useful methods to power up your code
 
Building a friendly .NET SDK to connect to Space
Building a friendly .NET SDK to connect to SpaceBuilding a friendly .NET SDK to connect to Space
Building a friendly .NET SDK to connect to Space
 
Acceptance Testing with Webrat
Acceptance Testing with WebratAcceptance Testing with Webrat
Acceptance Testing with Webrat
 
Beware sharp tools
Beware sharp toolsBeware sharp tools
Beware sharp tools
 
Unobtrusive javascript with jQuery
Unobtrusive javascript with jQueryUnobtrusive javascript with jQuery
Unobtrusive javascript with jQuery
 
Groovy kind of test
Groovy kind of testGroovy kind of test
Groovy kind of test
 

Recently uploaded

Odoo 14 - eLearning Module In Odoo 14 Enterprise
Odoo 14 - eLearning Module In Odoo 14 EnterpriseOdoo 14 - eLearning Module In Odoo 14 Enterprise
Odoo 14 - eLearning Module In Odoo 14 Enterprisepreethippts
 
Cyber security and its impact on E commerce
Cyber security and its impact on E commerceCyber security and its impact on E commerce
Cyber security and its impact on E commercemanigoyal112
 
Precise and Complete Requirements? An Elusive Goal
Precise and Complete Requirements? An Elusive GoalPrecise and Complete Requirements? An Elusive Goal
Precise and Complete Requirements? An Elusive GoalLionel Briand
 
Automate your Kamailio Test Calls - Kamailio World 2024
Automate your Kamailio Test Calls - Kamailio World 2024Automate your Kamailio Test Calls - Kamailio World 2024
Automate your Kamailio Test Calls - Kamailio World 2024Andreas Granig
 
Implementing Zero Trust strategy with Azure
Implementing Zero Trust strategy with AzureImplementing Zero Trust strategy with Azure
Implementing Zero Trust strategy with AzureDinusha Kumarasiri
 
Open Source Summit NA 2024: Open Source Cloud Costs - OpenCost's Impact on En...
Open Source Summit NA 2024: Open Source Cloud Costs - OpenCost's Impact on En...Open Source Summit NA 2024: Open Source Cloud Costs - OpenCost's Impact on En...
Open Source Summit NA 2024: Open Source Cloud Costs - OpenCost's Impact on En...Matt Ray
 
Folding Cheat Sheet #4 - fourth in a series
Folding Cheat Sheet #4 - fourth in a seriesFolding Cheat Sheet #4 - fourth in a series
Folding Cheat Sheet #4 - fourth in a seriesPhilip Schwarz
 
Machine Learning Software Engineering Patterns and Their Engineering
Machine Learning Software Engineering Patterns and Their EngineeringMachine Learning Software Engineering Patterns and Their Engineering
Machine Learning Software Engineering Patterns and Their EngineeringHironori Washizaki
 
GOING AOT WITH GRAALVM – DEVOXX GREECE.pdf
GOING AOT WITH GRAALVM – DEVOXX GREECE.pdfGOING AOT WITH GRAALVM – DEVOXX GREECE.pdf
GOING AOT WITH GRAALVM – DEVOXX GREECE.pdfAlina Yurenko
 
Intelligent Home Wi-Fi Solutions | ThinkPalm
Intelligent Home Wi-Fi Solutions | ThinkPalmIntelligent Home Wi-Fi Solutions | ThinkPalm
Intelligent Home Wi-Fi Solutions | ThinkPalmSujith Sukumaran
 
cpct NetworkING BASICS AND NETWORK TOOL.ppt
cpct NetworkING BASICS AND NETWORK TOOL.pptcpct NetworkING BASICS AND NETWORK TOOL.ppt
cpct NetworkING BASICS AND NETWORK TOOL.pptrcbcrtm
 
Taming Distributed Systems: Key Insights from Wix's Large-Scale Experience - ...
Taming Distributed Systems: Key Insights from Wix's Large-Scale Experience - ...Taming Distributed Systems: Key Insights from Wix's Large-Scale Experience - ...
Taming Distributed Systems: Key Insights from Wix's Large-Scale Experience - ...Natan Silnitsky
 
MYjobs Presentation Django-based project
MYjobs Presentation Django-based projectMYjobs Presentation Django-based project
MYjobs Presentation Django-based projectAnoyGreter
 
VK Business Profile - provides IT solutions and Web Development
VK Business Profile - provides IT solutions and Web DevelopmentVK Business Profile - provides IT solutions and Web Development
VK Business Profile - provides IT solutions and Web Developmentvyaparkranti
 
How to submit a standout Adobe Champion Application
How to submit a standout Adobe Champion ApplicationHow to submit a standout Adobe Champion Application
How to submit a standout Adobe Champion ApplicationBradBedford3
 
Software Project Health Check: Best Practices and Techniques for Your Product...
Software Project Health Check: Best Practices and Techniques for Your Product...Software Project Health Check: Best Practices and Techniques for Your Product...
Software Project Health Check: Best Practices and Techniques for Your Product...Velvetech LLC
 
Balasore Best It Company|| Top 10 IT Company || Balasore Software company Odisha
Balasore Best It Company|| Top 10 IT Company || Balasore Software company OdishaBalasore Best It Company|| Top 10 IT Company || Balasore Software company Odisha
Balasore Best It Company|| Top 10 IT Company || Balasore Software company Odishasmiwainfosol
 
Unveiling the Future: Sylius 2.0 New Features
Unveiling the Future: Sylius 2.0 New FeaturesUnveiling the Future: Sylius 2.0 New Features
Unveiling the Future: Sylius 2.0 New FeaturesŁukasz Chruściel
 
Software Coding for software engineering
Software Coding for software engineeringSoftware Coding for software engineering
Software Coding for software engineeringssuserb3a23b
 
KnowAPIs-UnknownPerf-jaxMainz-2024 (1).pptx
KnowAPIs-UnknownPerf-jaxMainz-2024 (1).pptxKnowAPIs-UnknownPerf-jaxMainz-2024 (1).pptx
KnowAPIs-UnknownPerf-jaxMainz-2024 (1).pptxTier1 app
 

Recently uploaded (20)

Odoo 14 - eLearning Module In Odoo 14 Enterprise
Odoo 14 - eLearning Module In Odoo 14 EnterpriseOdoo 14 - eLearning Module In Odoo 14 Enterprise
Odoo 14 - eLearning Module In Odoo 14 Enterprise
 
Cyber security and its impact on E commerce
Cyber security and its impact on E commerceCyber security and its impact on E commerce
Cyber security and its impact on E commerce
 
Precise and Complete Requirements? An Elusive Goal
Precise and Complete Requirements? An Elusive GoalPrecise and Complete Requirements? An Elusive Goal
Precise and Complete Requirements? An Elusive Goal
 
Automate your Kamailio Test Calls - Kamailio World 2024
Automate your Kamailio Test Calls - Kamailio World 2024Automate your Kamailio Test Calls - Kamailio World 2024
Automate your Kamailio Test Calls - Kamailio World 2024
 
Implementing Zero Trust strategy with Azure
Implementing Zero Trust strategy with AzureImplementing Zero Trust strategy with Azure
Implementing Zero Trust strategy with Azure
 
Open Source Summit NA 2024: Open Source Cloud Costs - OpenCost's Impact on En...
Open Source Summit NA 2024: Open Source Cloud Costs - OpenCost's Impact on En...Open Source Summit NA 2024: Open Source Cloud Costs - OpenCost's Impact on En...
Open Source Summit NA 2024: Open Source Cloud Costs - OpenCost's Impact on En...
 
Folding Cheat Sheet #4 - fourth in a series
Folding Cheat Sheet #4 - fourth in a seriesFolding Cheat Sheet #4 - fourth in a series
Folding Cheat Sheet #4 - fourth in a series
 
Machine Learning Software Engineering Patterns and Their Engineering
Machine Learning Software Engineering Patterns and Their EngineeringMachine Learning Software Engineering Patterns and Their Engineering
Machine Learning Software Engineering Patterns and Their Engineering
 
GOING AOT WITH GRAALVM – DEVOXX GREECE.pdf
GOING AOT WITH GRAALVM – DEVOXX GREECE.pdfGOING AOT WITH GRAALVM – DEVOXX GREECE.pdf
GOING AOT WITH GRAALVM – DEVOXX GREECE.pdf
 
Intelligent Home Wi-Fi Solutions | ThinkPalm
Intelligent Home Wi-Fi Solutions | ThinkPalmIntelligent Home Wi-Fi Solutions | ThinkPalm
Intelligent Home Wi-Fi Solutions | ThinkPalm
 
cpct NetworkING BASICS AND NETWORK TOOL.ppt
cpct NetworkING BASICS AND NETWORK TOOL.pptcpct NetworkING BASICS AND NETWORK TOOL.ppt
cpct NetworkING BASICS AND NETWORK TOOL.ppt
 
Taming Distributed Systems: Key Insights from Wix's Large-Scale Experience - ...
Taming Distributed Systems: Key Insights from Wix's Large-Scale Experience - ...Taming Distributed Systems: Key Insights from Wix's Large-Scale Experience - ...
Taming Distributed Systems: Key Insights from Wix's Large-Scale Experience - ...
 
MYjobs Presentation Django-based project
MYjobs Presentation Django-based projectMYjobs Presentation Django-based project
MYjobs Presentation Django-based project
 
VK Business Profile - provides IT solutions and Web Development
VK Business Profile - provides IT solutions and Web DevelopmentVK Business Profile - provides IT solutions and Web Development
VK Business Profile - provides IT solutions and Web Development
 
How to submit a standout Adobe Champion Application
How to submit a standout Adobe Champion ApplicationHow to submit a standout Adobe Champion Application
How to submit a standout Adobe Champion Application
 
Software Project Health Check: Best Practices and Techniques for Your Product...
Software Project Health Check: Best Practices and Techniques for Your Product...Software Project Health Check: Best Practices and Techniques for Your Product...
Software Project Health Check: Best Practices and Techniques for Your Product...
 
Balasore Best It Company|| Top 10 IT Company || Balasore Software company Odisha
Balasore Best It Company|| Top 10 IT Company || Balasore Software company OdishaBalasore Best It Company|| Top 10 IT Company || Balasore Software company Odisha
Balasore Best It Company|| Top 10 IT Company || Balasore Software company Odisha
 
Unveiling the Future: Sylius 2.0 New Features
Unveiling the Future: Sylius 2.0 New FeaturesUnveiling the Future: Sylius 2.0 New Features
Unveiling the Future: Sylius 2.0 New Features
 
Software Coding for software engineering
Software Coding for software engineeringSoftware Coding for software engineering
Software Coding for software engineering
 
KnowAPIs-UnknownPerf-jaxMainz-2024 (1).pptx
KnowAPIs-UnknownPerf-jaxMainz-2024 (1).pptxKnowAPIs-UnknownPerf-jaxMainz-2024 (1).pptx
KnowAPIs-UnknownPerf-jaxMainz-2024 (1).pptx
 

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

  • 1. Haste Same Language, Multiple latforms Tagless Final Style Same Syntax, Multiple nterpretations Nathan Sorenson @takeoutweight i p
  • 3. + 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
  • 4. - No Template Haskell - No GHCi - No forkIO - No Weak Pointers
  • 5. 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
  • 7. ghc-7.4.2.9: The GHC API parseModule :: GhcMonad m => ModSummary → m ParsedModule typeCheckModule :: GhcMonad m => ParsedModule → m TypecheckedModu desugarModule :: GhcMonad m => TypecheckedModule → m DesugaredModule coreToStg :: DynFlags → CoreProgram → IO [ StgBinding ]
  • 8. +---------+ 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
  • 9. 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)
  • 10. 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)
  • 12.
  • 13. 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
  • 14. 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
  • 15. 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
  • 16. ./libraries/haste-lib module Haste.DOM addChild :: MonadIO m => Elem → Elem → m () elemById :: MonadIO m => ElemID → m (Maybe Elem) module Haste.JSON encodeJSON :: JSON → JSString decodeJSON :: JSString → Either String JSON module Haste.Graphics.Canvas setFillColor :: Color → Picture () line :: Point → Point → Shape () module Haste.Concurrent.Monad forkIO :: CIO () → CIO () putMVar :: MVar a → a → CIO ()
  • 17. FFI // javascript.js function 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 Int f a b = ffi “(function (a,b) {window.tst = a; return 3;})” a b -- expose to JS, via Haste[“myInc”] or Haste.myInc export :: FFI a => JSString → a → IO () export “myInc” ((x -> return (x + 1)) :: Int → IO Int) // javascript.js Haste.myInc(3) // 4
  • 22. div :: [Attr] → [JSPtr] → JSPtr button :: [Attr] → [JSPtr] → JSPtr text :: String → JSPtr EDSL
  • 23. div :: [Attr] → [JSPtr] → JSPtr button :: [Attr] → [JSPtr] → JSPtr text :: String → JSPtr EDSS Embedded Domain Specific Syntax
  • 25. Tagless Final Style Discovered by Oleg Kiselyov
  • 26. Tagless Final Style Discovered by Oleg Kiselyov But don’t be scared.
  • 27. Initial Style data Html = Div [Attr] [Html] | Button [Attr] [Html] | Text String client :: Html → JSPtr client (Div attrs children) = … client (Button attrs children) = … client (Text str) = … server :: Html → String server (Div attrs children) = … server (Button attrs children) = … server (Text str) = … i i
  • 28. 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
  • 29. Initial Style data Html = Div [Attr] [Html] | Button [Attr] [Html] | Text String
  • 30. class Html i where div :: [Attr] → [ i ] → i button :: [Attr] → [ i ] → i text :: String → i Final Style
  • 31. Final Style class Html i where div :: [Attr] → [i] → i button :: [Attr] → [i] → i text :: String → i -- Initial Style data Html = Div [Attr] [Html] | Button [Attr] [Html] | Text String
  • 32. Final Style class 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
  • 33. Final Style class 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
  • 34. 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
  • 35. 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
  • 36. 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
  • 37. 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
  • 38. 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
  • 39. -- Initial Style i :: Html i = Div [] [(Button [] [Text “clickMe”])] iOut :: String iOut = server i -- Final Style f :: (Html i) => i f = div [] [(button [] [text “clickMe”])] fOut = f :: String
  • 40. class Math (i :: * ) where lit :: Int → i (+) :: i → i → i (>) :: i → i → i instance Math Int where … instance Math String where … i i
  • 41. class Math (i :: *→*) where lit :: Int → i Int (+) :: i Int → i Int → i Int (>) :: i Int → i Int → i Bool
  • 42. 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 -- False p = pp a -- “(1 > (2 + 3))” i i
  • 43. 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
  • 44. f :: (Html i, SafariHtml i) => i f = div [] [(webkitElt [] [text “clickMe”])] fOut = f :: String Language Extensibility
  • 45. 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 ButtonAttr newtype DivAttr i i
  • 46. 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 → a class 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
  • 47. type src form <img> instance SrcA ImgAttr <input> instance TypeA InputAttr instance SrcA InputAttr instance FormA InputAttr <button > instance TypeA ButtonAttr instance FormA ButtonAttr <label> instance FormA LabelAttr i i i i i i i
  • 48. Typed Tagless Final Course Notes okmij.org/ftp/tagless-final/course/lecture.pdf haste-lang.org “Haskell in the Browser With Haste” Lars Kuhtz alephcloud.github.io/bayhac2014/slides facebook.github.io/react github.com/takeoutweight @takeoutweight