| Safe Haskell | None |
|---|
Language.Sunroof.TH
Description
Provides template Haskell code to generate instances for JavaScript object wrappers (https://github.com/ku-fpg/sunroof-compiler/wiki/JSObject-Wrapper-Types).
- deriveJSTuple :: Q [Dec] -> Q [Dec]
Documentation
deriveJSTuple :: Q [Dec] -> Q [Dec]Source
derive derives an incomplete instance for JSTuple,
as well as completing other classes.
you write the newtype explictly, and derive does the rest.
newtype JSX o = JSX JSObject
and then the start of the JSTuple instance, and the rest gets filled in
derive [d| instance (SunroofArgument o) => JSTuple (JSX o) where
type Internals (JSX o) = (JSString,JSNumber)
|]
generates
instance (SunroofArgument o) => Show (JSX o) where
show (JSX o) = show o
instance (SunroofArgument o) => Sunroof (JSX o) where
unbox (JSX o) = unbox o
box o = JSX (box o)
instance (SunroofArgument o) => IfB (JSX o) where
ifB = jsIfB
type instance BooleanOf (JSX o) = JSBool
instance (SunroofArgument o) => JSTuple (JSX o) where
type instance Internals (JSX o) = (JSString, JSNumber)
match o = (o ! attr "f1", o ! attr "f2")
tuple (v1,v2) = do
o <- new "Object" ()
o # attr "f1" := v1
o # attr "f2" := v2
return (JSX o)