{-# LANGUAGE PatternSynonyms, ForeignFunctionInterface, JavaScriptFFI #-} module GHCJS.DOM.JSFFI.Generated.XSLTProcessor (js_newXSLTProcessor, newXSLTProcessor, js_importStylesheet, importStylesheet, js_transformToFragment, transformToFragment, js_transformToDocument, transformToDocument, js_setParameter, setParameter, js_getParameter, getParameter, js_removeParameter, removeParameter, js_clearParameters, clearParameters, js_reset, reset, XSLTProcessor, castToXSLTProcessor, gTypeXSLTProcessor) where import Prelude ((.), (==), (>>=), return, IO, Int, Float, Double, Bool(..), Maybe, maybe, fromIntegral, round, fmap, Show, Read, Eq, Ord) import Data.Typeable (Typeable) import GHCJS.Types (JSRef(..), JSString, castRef) import GHCJS.Foreign (jsNull) import GHCJS.Foreign.Callback (syncCallback, asyncCallback, syncCallback1, asyncCallback1, syncCallback2, asyncCallback2, OnBlocked(..)) import GHCJS.Marshal (ToJSRef(..), FromJSRef(..)) import GHCJS.Marshal.Pure (PToJSRef(..), PFromJSRef(..)) import Control.Monad.IO.Class (MonadIO(..)) import Data.Int (Int64) import Data.Word (Word, Word64) import GHCJS.DOM.Types import Control.Applicative ((<$>)) import GHCJS.DOM.EventTargetClosures (EventName, unsafeEventName) import GHCJS.DOM.Enums foreign import javascript unsafe "new window[\"XSLTProcessor\"]()" js_newXSLTProcessor :: IO (JSRef XSLTProcessor) -- | newXSLTProcessor :: (MonadIO m) => m XSLTProcessor newXSLTProcessor = liftIO (js_newXSLTProcessor >>= fromJSRefUnchecked) foreign import javascript unsafe "$1[\"importStylesheet\"]($2)" js_importStylesheet :: JSRef XSLTProcessor -> JSRef Node -> IO () -- | importStylesheet :: (MonadIO m, IsNode stylesheet) => XSLTProcessor -> Maybe stylesheet -> m () importStylesheet self stylesheet = liftIO (js_importStylesheet (unXSLTProcessor self) (maybe jsNull (unNode . toNode) stylesheet)) foreign import javascript unsafe "$1[\"transformToFragment\"]($2,\n$3)" js_transformToFragment :: JSRef XSLTProcessor -> JSRef Node -> JSRef Document -> IO (JSRef DocumentFragment) -- | transformToFragment :: (MonadIO m, IsNode source, IsDocument docVal) => XSLTProcessor -> Maybe source -> Maybe docVal -> m (Maybe DocumentFragment) transformToFragment self source docVal = liftIO ((js_transformToFragment (unXSLTProcessor self) (maybe jsNull (unNode . toNode) source) (maybe jsNull (unDocument . toDocument) docVal)) >>= fromJSRef) foreign import javascript unsafe "$1[\"transformToDocument\"]($2)" js_transformToDocument :: JSRef XSLTProcessor -> JSRef Node -> IO (JSRef Document) -- | transformToDocument :: (MonadIO m, IsNode source) => XSLTProcessor -> Maybe source -> m (Maybe Document) transformToDocument self source = liftIO ((js_transformToDocument (unXSLTProcessor self) (maybe jsNull (unNode . toNode) source)) >>= fromJSRef) foreign import javascript unsafe "$1[\"setParameter\"]($2, $3, $4)" js_setParameter :: JSRef XSLTProcessor -> JSString -> JSString -> JSString -> IO () -- | setParameter :: (MonadIO m, ToJSString namespaceURI, ToJSString localName, ToJSString value) => XSLTProcessor -> namespaceURI -> localName -> value -> m () setParameter self namespaceURI localName value = liftIO (js_setParameter (unXSLTProcessor self) (toJSString namespaceURI) (toJSString localName) (toJSString value)) foreign import javascript unsafe "$1[\"getParameter\"]($2, $3)" js_getParameter :: JSRef XSLTProcessor -> JSString -> JSString -> IO (JSRef (Maybe JSString)) -- | getParameter :: (MonadIO m, ToJSString namespaceURI, ToJSString localName, FromJSString result) => XSLTProcessor -> namespaceURI -> localName -> m (Maybe result) getParameter self namespaceURI localName = liftIO (fromMaybeJSString <$> (js_getParameter (unXSLTProcessor self) (toJSString namespaceURI) (toJSString localName))) foreign import javascript unsafe "$1[\"removeParameter\"]($2, $3)" js_removeParameter :: JSRef XSLTProcessor -> JSString -> JSString -> IO () -- | removeParameter :: (MonadIO m, ToJSString namespaceURI, ToJSString localName) => XSLTProcessor -> namespaceURI -> localName -> m () removeParameter self namespaceURI localName = liftIO (js_removeParameter (unXSLTProcessor self) (toJSString namespaceURI) (toJSString localName)) foreign import javascript unsafe "$1[\"clearParameters\"]()" js_clearParameters :: JSRef XSLTProcessor -> IO () -- | clearParameters :: (MonadIO m) => XSLTProcessor -> m () clearParameters self = liftIO (js_clearParameters (unXSLTProcessor self)) foreign import javascript unsafe "$1[\"reset\"]()" js_reset :: JSRef XSLTProcessor -> IO () -- | reset :: (MonadIO m) => XSLTProcessor -> m () reset self = liftIO (js_reset (unXSLTProcessor self))