{-# LANGUAGE DataKinds #-} -- | This module provides parts of the JQuery API (). module Language.Sunroof.JS.JQuery ( -- * General JQuery API dollar , jQuery, jq -- * DOM , append , html, setHtml , text, setText -- * CSS , css, setCss , addClass, removeClass -- * Attributes , attribute, attr' , setAttr , removeAttr -- * Event Handling , on -- * Manipulation , innerWidth , innerHeight , outerWidth, outerWidth' , outerHeight, outerHeight' , clone, clone' ) where import Language.Sunroof.Classes ( SunroofArgument(..) ) import Language.Sunroof.Types import Language.Sunroof.JS.Object ( JSObject ) import Language.Sunroof.JS.String ( JSString ) import Language.Sunroof.JS.Number ( JSNumber ) import Language.Sunroof.JS.Bool ( JSBool ) -- ----------------------------------------------------------------------- -- JQuery interface -- ----------------------------------------------------------------------- -- | The dollar function. -- See . dollar :: JSFunction JSString JSObject dollar = fun "$" -- | Calls the JQuery dollar function. -- See . jQuery :: JSString -> JS t JSObject jQuery nm = dollar `apply` nm -- | Short-hand for 'jQuery'. jq :: JSString -> JS t JSObject jq = jQuery -- ----------------------------------------------------------------------- -- Manipulation > DOM -- ----------------------------------------------------------------------- -- | See . append :: JSObject -> JSObject -> JS t () append x = invoke "append" x -- | See @.html()@ at . html :: JSObject -> JS t JSObject html = invoke "html" () -- | See @.html(htmlString)@ at . setHtml :: JSString -> JSObject -> JS t JSObject setHtml s = invoke "html" s -- | See @.text()@ at . text :: JSObject -> JS t JSObject text = invoke "text" () -- | See @.text(textString)@ at . setText :: JSString -> JSObject -> JS t JSObject setText s = invoke "text" s -- ------------------------------------------------------------- -- CSS -- ------------------------------------------------------------- -- | See @.css(propertyName)@ at . css :: JSString -> JSObject -> JS t JSString css prop = invoke "css" prop -- | See @.css(propertyName, value)@ at . setCss :: JSString -> JSString -> JSObject -> JS t JSString setCss prop v = invoke "css" (prop, v) -- | See . addClass :: JSString -> JSObject -> JS t () addClass = invoke "addClass" -- | See . removeClass :: JSString -> JSObject -> JS t () removeClass = invoke "removeClass" -- ------------------------------------------------------------- -- Attributes -- ------------------------------------------------------------- -- | See @.attr(attributeName)@ at . -- This binding does not have the original Javascript name, -- because of the 'attr' function. attribute :: JSString -> JSObject -> JS t JSString attribute a = invoke "attr" a -- | See @.attr(attributeName)@ at . -- This binding does not have the original Javascript name, -- because of the 'attr' function. attr' :: JSString -> JSObject -> JS t JSString attr' = attribute -- | See @.attr(attributeName, value)@ at . setAttr :: JSString -> JSString -> JSObject -> JS t JSString setAttr a v = invoke "attr" (a, v) -- | See: removeAttr :: JSString -> JSObject -> JS t JSObject removeAttr attrName = invoke "removeAttr" attrName -- ------------------------------------------------------------- -- Event Handling -- ------------------------------------------------------------- -- | See . on :: (SunroofArgument a) => JSString -> JSString -> (a -> JS B ()) -> JSObject -> JS t () on nm sel f o = do callback <- continuation f o # invoke "on" (nm,sel,callback) -- ------------------------------------------------------------- -- Manipulation > Style Properties -- ------------------------------------------------------------- -- | See . innerWidth :: JSObject -> JS t JSNumber innerWidth = invoke "innerWidth" () -- | See . innerHeight :: JSObject -> JS t JSNumber innerHeight = invoke "innerHeight" () -- | See . outerWidth :: JSObject -> JS t JSNumber outerWidth = invoke "outerWidth" () -- | See . outerWidth' :: JSBool -> JSObject -> JS t JSNumber outerWidth' includeMargin = invoke "outerWidth" includeMargin -- | See . outerHeight :: JSObject -> JS t JSNumber outerHeight = invoke "outerHeight" () -- | See . outerHeight' :: JSBool -> JSObject -> JS t JSNumber outerHeight' includeMargin = invoke "outerHeight" includeMargin -- | See @.clone()@ at . clone :: JSObject -> JS t JSObject clone = invoke "clone" () -- | See @.clone(withDataAndEvents, deepWithDataAndEvents)@ at . clone' :: JSBool -> JSBool -> JSObject -> JS t JSObject clone' withDataAndEvents deepWithDataAndEvents = invoke "clone" (withDataAndEvents, deepWithDataAndEvents)