-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Interface for JavaScript that works with GHCJS and GHC -- -- This package provides an EDSL for calling JavaScript that can be used -- both from GHCJS and GHC. When using GHC the application is run using -- Warp and WebSockets to drive a small JavaScipt helper. @package jsaddle @version 0.8.3.0 module Language.Javascript.JSaddle.Run.Files indexHtml :: ByteString jsaddleJs :: ByteString initState :: ByteString runBatch :: (ByteString -> ByteString) -> ByteString ghcjsHelpers :: ByteString module JavaScript.TypedArray.Immutable module GHCJS.Prim.Internal newtype JSVal JSVal :: JSValueRef -> JSVal type JSValueRef = Int64 data JSException JSException :: JSVal -> String -> JSException -- | If a synchronous thread tries to do something that can only be done -- asynchronously, and the thread is set up to not continue -- asynchronously, it receives this exception. data WouldBlockException WouldBlockException :: WouldBlockException mkJSException :: JSVal -> IO JSException jsNull :: JSVal instance Data.Aeson.Types.FromJSON.FromJSON GHCJS.Prim.Internal.JSVal instance Data.Aeson.Types.ToJSON.ToJSON GHCJS.Prim.Internal.JSVal instance GHC.Show.Show GHCJS.Prim.Internal.JSVal instance Control.DeepSeq.NFData GHCJS.Prim.Internal.JSVal instance GHC.Exception.Exception GHCJS.Prim.Internal.JSException instance GHC.Show.Show GHCJS.Prim.Internal.JSException instance GHC.Show.Show GHCJS.Prim.Internal.WouldBlockException instance GHC.Exception.Exception GHCJS.Prim.Internal.WouldBlockException module Language.Javascript.JSaddle.Exception newtype JSException JSException :: JSVal -> JSException instance GHC.Show.Show Language.Javascript.JSaddle.Exception.JSException instance GHC.Exception.Exception Language.Javascript.JSaddle.Exception.JSException module Data.JSString.Internal.Type -- | A wrapper around a JavaScript string newtype JSString JSString :: Text -> JSString -- | O(1) The empty JSString. empty :: JSString -- | A non-inlined version of empty. empty_ :: JSString safe :: Char -> Char -- | Apply a function to the first element of an optional pair. firstf :: (a -> c) -> Maybe (a, b) -> Maybe (c, b) instance Data.Aeson.Types.FromJSON.FromJSON Data.JSString.Internal.Type.JSString instance Data.Aeson.Types.ToJSON.ToJSON Data.JSString.Internal.Type.JSString instance Data.Data.Data Data.JSString.Internal.Type.JSString instance GHC.Classes.Eq Data.JSString.Internal.Type.JSString instance GHC.Classes.Ord Data.JSString.Internal.Type.JSString instance GHC.Base.Monoid Data.JSString.Internal.Type.JSString instance Data.String.IsString Data.JSString.Internal.Type.JSString instance GHC.Read.Read Data.JSString.Internal.Type.JSString instance GHC.Show.Show Data.JSString.Internal.Type.JSString instance Control.DeepSeq.NFData Data.JSString.Internal.Type.JSString module Language.Javascript.JSaddle.Types -- | Identifies a JavaScript execution context. When using GHCJS this is -- just '()' since their is only one context. When using GHC it includes -- the functions JSaddle needs to communicate with the JavaScript -- context. data JSContextRef JSContextRef :: UTCTime -> (Command -> IO Result) -> (AsyncCommand -> IO ()) -> (Object -> JSCallAsFunction -> IO ()) -> (Object -> IO ()) -> TVar JSValueRef -> (Bool -> IO ()) -> JSContextRef [startTime] :: JSContextRef -> UTCTime [doSendCommand] :: JSContextRef -> Command -> IO Result [doSendAsyncCommand] :: JSContextRef -> AsyncCommand -> IO () [addCallback] :: JSContextRef -> Object -> JSCallAsFunction -> IO () [freeCallback] :: JSContextRef -> Object -> IO () [nextRef] :: JSContextRef -> TVar JSValueRef [doEnableLogging] :: JSContextRef -> Bool -> IO () -- | The JSM monad keeps track of the JavaScript execution context. -- -- When using GHCJS it is IO. -- -- Given a JSM function and a JSContextRef you can run the -- function like this... -- --
--   runJSM jsmFunction javaScriptContext
--   
newtype JSM a JSM :: ReaderT JSContextRef IO a -> JSM a [unJSM] :: JSM a -> ReaderT JSContextRef IO a -- | The MonadJSM is to JSM what MonadIO is to -- IO. When using GHCJS it is MonadIO. class (Applicative m, MonadIO m) => MonadJSM m liftJSM' :: MonadJSM m => JSM a -> m a -- | The liftJSM is to JSM what liftIO is to -- IO. When using GHCJS it is liftIO. liftJSM :: MonadJSM m => JSM a -> m a -- | Type we can give to functions that are pure when using ghcjs, but live -- in JSM when using jsaddle. -- -- Some functions that can be pure in GHCJS cannot be implemented in a -- pure way in JSaddle (because we need to know the JSContextRef). -- Instead we implement versions of these functions in that return -- `GHCJSPure a` instead of a. To call them in a way that will -- work when compiling with GHCJS use ghcjsPure. newtype GHCJSPure a GHCJSPure :: (JSM a) -> GHCJSPure a -- | Used when you want to call a functions that is pure in GHCJS, but -- lives in the JSM in jsaddle. ghcjsPure :: GHCJSPure a -> JSM a ghcjsPureMap :: (a -> b) -> GHCJSPure a -> GHCJSPure b ghcjsPureId :: a -> GHCJSPure a newtype JSVal JSVal :: JSValueRef -> JSVal class IsJSVal a where jsval_ = GHCJSPure . return . coerce jsval_ :: IsJSVal a => a -> GHCJSPure JSVal jsval_ :: (IsJSVal a, Coercible a JSVal) => a -> GHCJSPure JSVal jsval :: IsJSVal a => a -> GHCJSPure JSVal newtype SomeJSArray (m :: MutabilityType s) SomeJSArray :: JSVal -> SomeJSArray -- | See JSArray type JSArray = SomeJSArray Immutable -- | See MutableJSArray type MutableJSArray = SomeJSArray Mutable -- | See STJSArray type STJSArray s = SomeJSArray (STMutable s) -- | See Object newtype Object Object :: JSVal -> Object -- | A wrapper around a JavaScript string newtype JSString JSString :: Text -> JSString -- | See Nullable newtype Nullable a Nullable :: a -> Nullable a -- | Type used for Haskell functions called from JavaScript. type JSCallAsFunction = JSVal Function object -> JSVal this -> [JSVal] Function arguments -> JSM () Only () (aka 'JSUndefined') can be returned because the function may need to be executed in a different thread. If you need to get a value out pass in a continuation function as an argument and invoke it from haskell. -- | Like HasCallStack, but only when jsaddle cabal flag check-unchecked is -- set type JSadddleHasCallStack = (() :: Constraint) data MutabilityType s Mutable_ :: s -> MutabilityType s Immutable_ :: s -> MutabilityType s STMutable :: s -> MutabilityType s type Mutable = Mutable_ () type Immutable = Immutable_ () data IsItMutable IsImmutable :: IsItMutable IsMutable :: IsItMutable -- | Wrapper used when receiving a JSVal from the JavaScript context newtype JSValueReceived JSValueReceived :: JSValueRef -> JSValueReceived -- | Wrapper used when sending a JSVal to the JavaScript context newtype JSValueForSend JSValueForSend :: JSValueRef -> JSValueForSend -- | Wrapper used when receiving a JSString from the JavaScript -- context newtype JSStringReceived JSStringReceived :: Text -> JSStringReceived -- | Wrapper used when sending a JString to the JavaScript context newtype JSStringForSend JSStringForSend :: Text -> JSStringForSend -- | Wrapper used when sending a Object to the JavaScript context newtype JSObjectForSend JSObjectForSend :: JSValueForSend -> JSObjectForSend -- | Command sent to a JavaScript context for execution asynchronously data AsyncCommand FreeRef :: JSValueForSend -> AsyncCommand SetPropertyByName :: JSObjectForSend -> JSStringForSend -> JSValueForSend -> AsyncCommand SetPropertyAtIndex :: JSObjectForSend -> Int -> JSValueForSend -> AsyncCommand StringToValue :: JSStringForSend -> JSValueForSend -> AsyncCommand NumberToValue :: Double -> JSValueForSend -> AsyncCommand JSONValueToValue :: Value -> JSValueForSend -> AsyncCommand GetPropertyByName :: JSObjectForSend -> JSStringForSend -> JSValueForSend -> AsyncCommand GetPropertyAtIndex :: JSObjectForSend -> Int -> JSValueForSend -> AsyncCommand CallAsFunction :: JSObjectForSend -> JSObjectForSend -> [JSValueForSend] -> JSValueForSend -> AsyncCommand CallAsConstructor :: JSObjectForSend -> [JSValueForSend] -> JSValueForSend -> AsyncCommand NewEmptyObject :: JSValueForSend -> AsyncCommand NewCallback :: JSValueForSend -> AsyncCommand NewArray :: [JSValueForSend] -> JSValueForSend -> AsyncCommand EvaluateScript :: JSStringForSend -> JSValueForSend -> AsyncCommand SyncWithAnimationFrame :: JSValueForSend -> AsyncCommand -- | Command sent to a JavaScript context for execution synchronously data Command DeRefVal :: JSValueForSend -> Command ValueToBool :: JSValueForSend -> Command ValueToNumber :: JSValueForSend -> Command ValueToString :: JSValueForSend -> Command ValueToJSON :: JSValueForSend -> Command ValueToJSONValue :: JSValueForSend -> Command IsNull :: JSValueForSend -> Command IsUndefined :: JSValueForSend -> Command StrictEqual :: JSValueForSend -> JSValueForSend -> Command InstanceOf :: JSValueForSend -> JSObjectForSend -> Command PropertyNames :: JSObjectForSend -> Command Sync :: Command -- | Batch of commands that can be sent together to the JavaScript context data Batch Batch :: [Either AsyncCommand Command] -> Bool -> Batch -- | Result of a Command returned from the JavaScript context data Result DeRefValResult :: JSValueRef -> Text -> Result ValueToBoolResult :: Bool -> Result ValueToNumberResult :: Double -> Result ValueToStringResult :: JSStringReceived -> Result ValueToJSONResult :: JSStringReceived -> Result ValueToJSONValueResult :: Value -> Result IsNullResult :: Bool -> Result IsUndefinedResult :: Bool -> Result StrictEqualResult :: Bool -> Result InstanceOfResult :: Bool -> Result PropertyNamesResult :: [JSStringReceived] -> Result ThrowJSValue :: JSValueReceived -> Result SyncResult :: Result data Results Success :: [Result] -> Results Failure :: [Result] -> JSValueReceived -> Results Callback :: JSValueReceived -> JSValueReceived -> [JSValueReceived] -> Results ProtocolError :: Text -> Results instance GHC.Generics.Generic Language.Javascript.JSaddle.Types.Results instance GHC.Show.Show Language.Javascript.JSaddle.Types.Results instance Control.Monad.Fix.MonadFix Language.Javascript.JSaddle.Types.JSM instance Control.Monad.IO.Class.MonadIO Language.Javascript.JSaddle.Types.JSM instance GHC.Base.Monad Language.Javascript.JSaddle.Types.JSM instance GHC.Base.Applicative Language.Javascript.JSaddle.Types.JSM instance GHC.Base.Functor Language.Javascript.JSaddle.Types.JSM instance GHC.Generics.Generic Language.Javascript.JSaddle.Types.Result instance GHC.Show.Show Language.Javascript.JSaddle.Types.Result instance GHC.Generics.Generic Language.Javascript.JSaddle.Types.Batch instance GHC.Show.Show Language.Javascript.JSaddle.Types.Batch instance GHC.Generics.Generic Language.Javascript.JSaddle.Types.Command instance GHC.Show.Show Language.Javascript.JSaddle.Types.Command instance GHC.Generics.Generic Language.Javascript.JSaddle.Types.AsyncCommand instance GHC.Show.Show Language.Javascript.JSaddle.Types.AsyncCommand instance GHC.Generics.Generic Language.Javascript.JSaddle.Types.JSStringForSend instance Data.Aeson.Types.FromJSON.FromJSON Language.Javascript.JSaddle.Types.JSStringForSend instance Data.Aeson.Types.ToJSON.ToJSON Language.Javascript.JSaddle.Types.JSStringForSend instance GHC.Show.Show Language.Javascript.JSaddle.Types.JSStringForSend instance Data.Aeson.Types.FromJSON.FromJSON Language.Javascript.JSaddle.Types.JSStringReceived instance Data.Aeson.Types.ToJSON.ToJSON Language.Javascript.JSaddle.Types.JSStringReceived instance GHC.Show.Show Language.Javascript.JSaddle.Types.JSStringReceived instance GHC.Generics.Generic Language.Javascript.JSaddle.Types.JSObjectForSend instance Data.Aeson.Types.FromJSON.FromJSON Language.Javascript.JSaddle.Types.JSObjectForSend instance Data.Aeson.Types.ToJSON.ToJSON Language.Javascript.JSaddle.Types.JSObjectForSend instance GHC.Show.Show Language.Javascript.JSaddle.Types.JSObjectForSend instance GHC.Generics.Generic Language.Javascript.JSaddle.Types.JSValueForSend instance Data.Aeson.Types.FromJSON.FromJSON Language.Javascript.JSaddle.Types.JSValueForSend instance Data.Aeson.Types.ToJSON.ToJSON Language.Javascript.JSaddle.Types.JSValueForSend instance GHC.Show.Show Language.Javascript.JSaddle.Types.JSValueForSend instance Data.Aeson.Types.FromJSON.FromJSON Language.Javascript.JSaddle.Types.JSValueReceived instance Data.Aeson.Types.ToJSON.ToJSON Language.Javascript.JSaddle.Types.JSValueReceived instance GHC.Show.Show Language.Javascript.JSaddle.Types.JSValueReceived instance Data.Aeson.Types.FromJSON.FromJSON Language.Javascript.JSaddle.Types.Object instance Data.Aeson.Types.ToJSON.ToJSON Language.Javascript.JSaddle.Types.Object instance GHC.Show.Show Language.Javascript.JSaddle.Types.Object instance Language.Javascript.JSaddle.Types.MonadJSM Language.Javascript.JSaddle.Types.JSM instance Language.Javascript.JSaddle.Types.MonadJSM m => Language.Javascript.JSaddle.Types.MonadJSM (Control.Monad.Trans.Reader.ReaderT e m) instance Language.Javascript.JSaddle.Types.MonadJSM m => Language.Javascript.JSaddle.Types.MonadJSM (Control.Monad.Trans.State.Lazy.StateT r m) instance Language.Javascript.JSaddle.Types.MonadJSM m => Language.Javascript.JSaddle.Types.MonadJSM (Control.Monad.Trans.State.Strict.StateT r m) instance Control.Monad.Ref.MonadRef Language.Javascript.JSaddle.Types.JSM instance Control.Monad.Ref.MonadAtomicRef Language.Javascript.JSaddle.Types.JSM instance forall s (m :: Language.Javascript.JSaddle.Types.MutabilityType s). Language.Javascript.JSaddle.Types.IsJSVal (Language.Javascript.JSaddle.Types.SomeJSArray m) instance Control.DeepSeq.NFData Language.Javascript.JSaddle.Types.JSValueForSend instance Control.DeepSeq.NFData Language.Javascript.JSaddle.Types.JSObjectForSend instance Control.DeepSeq.NFData Language.Javascript.JSaddle.Types.JSStringForSend instance Data.Aeson.Types.ToJSON.ToJSON Language.Javascript.JSaddle.Types.AsyncCommand instance Data.Aeson.Types.FromJSON.FromJSON Language.Javascript.JSaddle.Types.AsyncCommand instance Control.DeepSeq.NFData Language.Javascript.JSaddle.Types.AsyncCommand instance Data.Aeson.Types.ToJSON.ToJSON Language.Javascript.JSaddle.Types.Command instance Data.Aeson.Types.FromJSON.FromJSON Language.Javascript.JSaddle.Types.Command instance Control.DeepSeq.NFData Language.Javascript.JSaddle.Types.Command instance Data.Aeson.Types.ToJSON.ToJSON Language.Javascript.JSaddle.Types.Batch instance Data.Aeson.Types.FromJSON.FromJSON Language.Javascript.JSaddle.Types.Batch instance Control.DeepSeq.NFData Language.Javascript.JSaddle.Types.Batch instance Data.Aeson.Types.ToJSON.ToJSON Language.Javascript.JSaddle.Types.Result instance Data.Aeson.Types.FromJSON.FromJSON Language.Javascript.JSaddle.Types.Result instance Data.Aeson.Types.ToJSON.ToJSON Language.Javascript.JSaddle.Types.Results instance Data.Aeson.Types.FromJSON.FromJSON Language.Javascript.JSaddle.Types.Results -- | These classes are used to make various JavaScript types out of -- whatever we have. Functions in jsaddle take these as inputs. This -- alows implicit casting and eager evaluation. module Language.Javascript.JSaddle.Classes.Internal -- | Anything that can be used to make a JavaScript object reference class MakeObject this makeObject :: MakeObject this => this -> JSM Object -- | Anything that can be used to make a list of JavaScript value -- references for use as function arguments class MakeArgs this makeArgs :: MakeArgs this => this -> JSM [JSVal] instance Language.Javascript.JSaddle.Classes.Internal.MakeObject Language.Javascript.JSaddle.Types.Object instance Language.Javascript.JSaddle.Classes.Internal.MakeArgs arg => Language.Javascript.JSaddle.Classes.Internal.MakeArgs (Language.Javascript.JSaddle.Types.JSM arg) module Language.Javascript.JSaddle.Run -- | Forces execution of pending asyncronous code syncPoint :: JSM () -- | Forces execution of pending asyncronous code after performing -- f syncAfter :: JSM a -> JSM a -- | On GHCJS this is waitForAnimationFrame. On GHC it will delay -- the execution of the current batch of asynchronous command when they -- are sent to JavaScript. It will not delay the Haskell code execution. -- The time returned will be based on the Haskell clock (not the -- JavaScript clock). waitForAnimationFrame :: JSM Double -- | Tries to executes the given code in the next animation frame callback. -- Avoid synchronous opperations where possible. nextAnimationFrame :: (Double -> JSM a) -> JSM a -- | Enable (or disable) JSaddle logging enableLogging :: Bool -> JSM () runJavaScript :: (Batch -> IO ()) -> JSM () -> IO (Results -> IO (), IO ()) -- | Command sent to a JavaScript context for execution asynchronously data AsyncCommand FreeRef :: JSValueForSend -> AsyncCommand SetPropertyByName :: JSObjectForSend -> JSStringForSend -> JSValueForSend -> AsyncCommand SetPropertyAtIndex :: JSObjectForSend -> Int -> JSValueForSend -> AsyncCommand StringToValue :: JSStringForSend -> JSValueForSend -> AsyncCommand NumberToValue :: Double -> JSValueForSend -> AsyncCommand JSONValueToValue :: Value -> JSValueForSend -> AsyncCommand GetPropertyByName :: JSObjectForSend -> JSStringForSend -> JSValueForSend -> AsyncCommand GetPropertyAtIndex :: JSObjectForSend -> Int -> JSValueForSend -> AsyncCommand CallAsFunction :: JSObjectForSend -> JSObjectForSend -> [JSValueForSend] -> JSValueForSend -> AsyncCommand CallAsConstructor :: JSObjectForSend -> [JSValueForSend] -> JSValueForSend -> AsyncCommand NewEmptyObject :: JSValueForSend -> AsyncCommand NewCallback :: JSValueForSend -> AsyncCommand NewArray :: [JSValueForSend] -> JSValueForSend -> AsyncCommand EvaluateScript :: JSStringForSend -> JSValueForSend -> AsyncCommand SyncWithAnimationFrame :: JSValueForSend -> AsyncCommand -- | Command sent to a JavaScript context for execution synchronously data Command DeRefVal :: JSValueForSend -> Command ValueToBool :: JSValueForSend -> Command ValueToNumber :: JSValueForSend -> Command ValueToString :: JSValueForSend -> Command ValueToJSON :: JSValueForSend -> Command ValueToJSONValue :: JSValueForSend -> Command IsNull :: JSValueForSend -> Command IsUndefined :: JSValueForSend -> Command StrictEqual :: JSValueForSend -> JSValueForSend -> Command InstanceOf :: JSValueForSend -> JSObjectForSend -> Command PropertyNames :: JSObjectForSend -> Command Sync :: Command -- | Result of a Command returned from the JavaScript context data Result DeRefValResult :: JSValueRef -> Text -> Result ValueToBoolResult :: Bool -> Result ValueToNumberResult :: Double -> Result ValueToStringResult :: JSStringReceived -> Result ValueToJSONResult :: JSStringReceived -> Result ValueToJSONValueResult :: Value -> Result IsNullResult :: Bool -> Result IsUndefinedResult :: Bool -> Result StrictEqualResult :: Bool -> Result InstanceOfResult :: Bool -> Result PropertyNamesResult :: [JSStringReceived] -> Result ThrowJSValue :: JSValueReceived -> Result SyncResult :: Result sendCommand :: Command -> JSM Result sendLazyCommand :: (JSValueForSend -> AsyncCommand) -> JSM JSVal sendAsyncCommand :: AsyncCommand -> JSM () wrapJSVal :: JSValueReceived -> JSM JSVal -- | JSM monad keeps track of the JavaScript context module Language.Javascript.JSaddle.Monad -- | The JSM monad keeps track of the JavaScript execution context. -- -- When using GHCJS it is IO. -- -- Given a JSM function and a JSContextRef you can run the -- function like this... -- --
--   runJSM jsmFunction javaScriptContext
--   
newtype JSM a JSM :: ReaderT JSContextRef IO a -> JSM a [unJSM] :: JSM a -> ReaderT JSContextRef IO a -- | Identifies a JavaScript execution context. When using GHCJS this is -- just '()' since their is only one context. When using GHC it includes -- the functions JSaddle needs to communicate with the JavaScript -- context. data JSContextRef -- | The MonadJSM is to JSM what MonadIO is to -- IO. When using GHCJS it is MonadIO. class (Applicative m, MonadIO m) => MonadJSM m -- | The liftJSM is to JSM what liftIO is to -- IO. When using GHCJS it is liftIO. liftJSM :: MonadJSM m => JSM a -> m a -- | Gets the JavaScript context from the monad askJSM :: MonadJSM m => m JSContextRef -- | Runs a JSM JavaScript function in a given JavaScript context. runJSM :: MonadIO m => JSM a -> JSContextRef -> m a -- | Alternative version of runJSM runJSaddle :: MonadIO m => JSContextRef -> JSM a -> m a -- | Forces execution of pending asyncronous code syncPoint :: JSM () -- | Forces execution of pending asyncronous code after performing -- f syncAfter :: JSM a -> JSM a -- | On GHCJS this is waitForAnimationFrame. On GHC it will delay -- the execution of the current batch of asynchronous command when they -- are sent to JavaScript. It will not delay the Haskell code execution. -- The time returned will be based on the Haskell clock (not the -- JavaScript clock). waitForAnimationFrame :: JSM Double -- | Tries to executes the given code in the next animation frame callback. -- Avoid synchronous opperations where possible. nextAnimationFrame :: (Double -> JSM a) -> JSM a -- | Wrapped version of catch that runs in a MonadIO that works a -- bit better with JSM catch :: Exception e => JSM b -> (e -> JSM b) -> JSM b -- | Wrapped version of bracket that runs in a MonadIO that works a -- bit better with JSM bracket :: JSM a -> (a -> JSM b) -> (a -> JSM c) -> JSM c module Language.Javascript.JSaddle.Native.Internal wrapJSVal :: JSValueReceived -> JSM JSVal wrapJSString :: MonadIO m => JSStringReceived -> m JSString withJSVal :: MonadIO m => JSVal -> (JSValueForSend -> m a) -> m a withJSVals :: MonadIO m => [JSVal] -> ([JSValueForSend] -> m a) -> m a withObject :: MonadIO m => Object -> (JSObjectForSend -> m a) -> m a withJSString :: MonadIO m => JSString -> (JSStringForSend -> m a) -> m a setPropertyByName :: JSString -> JSVal -> Object -> JSM () setPropertyAtIndex :: Int -> JSVal -> Object -> JSM () stringToValue :: JSString -> JSM JSVal numberToValue :: Double -> JSM JSVal jsonValueToValue :: Value -> JSM JSVal getPropertyByName :: JSString -> Object -> JSM JSVal getPropertyAtIndex :: Int -> Object -> JSM JSVal callAsFunction :: Object -> Object -> [JSVal] -> JSM JSVal callAsConstructor :: Object -> [JSVal] -> JSM JSVal newEmptyObject :: JSM Object newCallback :: JSCallAsFunction -> JSM Object newArray :: [JSVal] -> JSM JSVal evaluateScript :: JSString -> JSM JSVal deRefVal :: JSVal -> JSM Result valueToBool :: JSVal -> JSM Bool valueToNumber :: JSVal -> JSM Double valueToString :: JSVal -> JSM JSString valueToJSON :: JSVal -> JSM JSString valueToJSONValue :: JSVal -> JSM Value isNull :: JSVal -> JSM Bool isUndefined :: JSVal -> JSM Bool strictEqual :: JSVal -> JSVal -> JSM Bool instanceOf :: JSVal -> Object -> JSM Bool propertyNames :: Object -> JSM [JSString] -- | Conversion between Text and JSString module Data.JSString.Text textToJSString :: Text -> JSString textFromJSString :: JSString -> Text lazyTextToJSString :: Text -> JSString lazyTextFromJSString :: JSString -> Text -- | returns the empty Text if not a string textFromJSVal :: JSVal -> GHCJSPure Text -- | returns the empty Text if not a string lazyTextFromJSVal :: JSVal -> GHCJSPure Text module GHCJS.Internal.Types class IsJSVal a where jsval_ = GHCJSPure . return . coerce jsval_ :: IsJSVal a => a -> GHCJSPure JSVal jsval_ :: (IsJSVal a, Coercible a JSVal) => a -> GHCJSPure JSVal jsval :: IsJSVal a => a -> GHCJSPure JSVal data MutabilityType s Mutable_ :: s -> MutabilityType s Immutable_ :: s -> MutabilityType s STMutable :: s -> MutabilityType s type Mutable = Mutable_ () type Immutable = Immutable_ () data IsItMutable IsImmutable :: IsItMutable IsMutable :: IsItMutable instance Language.Javascript.JSaddle.Types.IsJSVal Data.JSString.Internal.Type.JSString module GHCJS.Prim -- | Low-level conversion utilities for packages that cannot depend on -- ghcjs-base fromJSString :: JSVal -> GHCJSPure String toJSString :: String -> GHCJSPure JSVal isNull :: JSVal -> GHCJSPure Bool isUndefined :: JSVal -> GHCJSPure Bool module GHCJS.Foreign.Internal jsTrue :: JSVal jsFalse :: JSVal jsNull :: JSVal toJSBool :: Bool -> JSVal jsUndefined :: JSVal isTruthy :: JSVal -> GHCJSPure Bool isNull :: JSVal -> GHCJSPure Bool isUndefined :: JSVal -> GHCJSPure Bool data JSType Undefined :: JSType Object :: JSType Boolean :: JSType Number :: JSType String :: JSType Symbol :: JSType Function :: JSType -- | implementation dependent Other :: JSType instance GHC.Enum.Enum GHCJS.Foreign.Internal.JSType instance GHC.Classes.Ord GHCJS.Foreign.Internal.JSType instance GHC.Classes.Eq GHCJS.Foreign.Internal.JSType instance GHC.Show.Show GHCJS.Foreign.Internal.JSType module GHCJS.Types data JSVal -- | If a synchronous thread tries to do something that can only be done -- asynchronously, and the thread is set up to not continue -- asynchronously, it receives this exception. data WouldBlockException WouldBlockException :: WouldBlockException data JSException JSException :: JSVal -> String -> JSException class IsJSVal a where jsval_ = GHCJSPure . return . coerce jsval :: IsJSVal a => a -> GHCJSPure JSVal isNull :: JSVal -> GHCJSPure Bool isUndefined :: JSVal -> GHCJSPure Bool nullRef :: JSVal -- | A wrapper around a JavaScript string data JSString mkRef :: Ref# -> JSVal type Ref# = Int64 -- | This is a deprecated copmatibility wrapper for the old JSRef type. -- -- See https://github.com/ghcjs/ghcjs/issues/421 -- | Deprecated: Use JSVal instead, or a more specific newtype wrapper -- of JSVal type JSRef a = JSVal module GHCJS.Buffer.Types newtype SomeBuffer (a :: MutabilityType s) SomeBuffer :: JSVal -> SomeBuffer type Buffer = SomeBuffer Immutable type MutableBuffer = SomeBuffer Mutable module JavaScript.TypedArray.ArrayBuffer.Type module JavaScript.Array.Internal newtype SomeJSArray (m :: MutabilityType s) SomeJSArray :: JSVal -> SomeJSArray -- | See JSArray type JSArray = SomeJSArray Immutable -- | See MutableJSArray type MutableJSArray = SomeJSArray Mutable -- | See STJSArray type STJSArray s = SomeJSArray (STMutable s) create :: JSM MutableJSArray fromList :: [JSVal] -> GHCJSPure (SomeJSArray m) fromListIO :: [JSVal] -> JSM (SomeJSArray m) toList :: SomeJSArray m -> GHCJSPure [JSVal] toListIO :: SomeJSArray m -> JSM [JSVal] index :: Int -> SomeJSArray m -> GHCJSPure JSVal read :: Int -> SomeJSArray m -> JSM JSVal push :: JSVal -> MutableJSArray -> JSM () module JavaScript.Object.Internal -- | See Object newtype Object Object :: JSVal -> Object -- | create an empty object create :: JSM Object listProps :: Object -> JSM [JSString] -- | get a property from an object. If accessing the property results in an -- exception, the exception is converted to a JSException. Since -- exception handling code prevents some optimizations in some JS -- engines, you may want to use unsafeGetProp instead getProp :: JSString -> Object -> JSM JSVal unsafeGetProp :: JSString -> Object -> JSM JSVal setProp :: JSString -> JSVal -> Object -> JSM () unsafeSetProp :: JSString -> JSVal -> Object -> JSM () module JavaScript.Object -- | See Object data Object -- | create an empty object create :: JSM Object -- | get a property from an object. If accessing the property results in an -- exception, the exception is converted to a JSException. Since -- exception handling code prevents some optimizations in some JS -- engines, you may want to use unsafeGetProp instead getProp :: JSString -> Object -> JSM JSVal unsafeGetProp :: JSString -> Object -> JSM JSVal setProp :: JSString -> JSVal -> Object -> JSM () unsafeSetProp :: JSString -> JSVal -> Object -> JSM () listProps :: Object -> JSM [JSString] -- | JavaScript string conversion functions module Language.Javascript.JSaddle.String -- | A wrapper around a JavaScript string data JSString textFromJSString :: JSString -> Text textToJSString :: Text -> JSString -- | Convert a JavaScript string to a Haskell Text strToText :: JSString -> Text -- | Convert a Haskell Text to a JavaScript string textToStr :: Text -> JSString module GHCJS.Marshal.Internal class FromJSVal a where fromJSValUnchecked = fmap fromJust . fromJSVal fromJSValListOf = fmap sequence . (mapM fromJSVal <=< toListIO . coerce) fromJSValUncheckedListOf = mapM fromJSValUnchecked <=< toListIO . coerce fromJSVal = fromJSVal_generic id fromJSVal :: FromJSVal a => JSVal -> JSM (Maybe a) fromJSValUnchecked :: FromJSVal a => JSVal -> JSM a fromJSValListOf :: FromJSVal a => JSVal -> JSM (Maybe [a]) fromJSValUncheckedListOf :: FromJSVal a => JSVal -> JSM [a] fromJSVal :: (FromJSVal a, Generic a, GFromJSVal (Rep a ())) => JSVal -> JSM (Maybe a) class ToJSVal a where toJSValListOf = fmap coerce . fromListIO <=< mapM toJSVal toJSVal = toJSVal_generic id toJSVal :: ToJSVal a => a -> JSM JSVal toJSValListOf :: ToJSVal a => [a] -> JSM JSVal toJSVal :: (ToJSVal a, Generic a, GToJSVal (Rep a ())) => a -> JSM JSVal class PToJSVal a pToJSVal :: PToJSVal a => a -> JSVal class PFromJSVal a pFromJSVal :: PFromJSVal a => JSVal -> a data Purity -- | conversion is pure even if the original value is shared PureShared :: Purity -- | conversion is pure if the we only convert once PureExclusive :: Purity toJSVal_generic :: forall a. (Generic a, GToJSVal (Rep a ())) => (String -> String) -> a -> JSM JSVal fromJSVal_generic :: forall a. (Generic a, GFromJSVal (Rep a ())) => (String -> String) -> JSVal -> JSM (Maybe a) toJSVal_pure :: PToJSVal a => a -> JSM JSVal fromJSVal_pure :: PFromJSVal a => JSVal -> JSM (Maybe a) fromJSValUnchecked_pure :: PFromJSVal a => JSVal -> JSM a instance Data.Data.Data GHCJS.Marshal.Internal.Purity instance GHC.Classes.Ord GHCJS.Marshal.Internal.Purity instance GHC.Classes.Eq GHCJS.Marshal.Internal.Purity instance GHCJS.Marshal.Internal.ToJSVal b => GHCJS.Marshal.Internal.GToJSVal (GHC.Generics.K1 a b c) instance GHCJS.Marshal.Internal.GToJSVal p => GHCJS.Marshal.Internal.GToJSVal (GHC.Generics.Par1 p) instance GHCJS.Marshal.Internal.GToJSVal (f p) => GHCJS.Marshal.Internal.GToJSVal (GHC.Generics.Rec1 f p) instance (GHCJS.Marshal.Internal.GToJSVal (a p), GHCJS.Marshal.Internal.GToJSVal (b p)) => GHCJS.Marshal.Internal.GToJSVal ((GHC.Generics.:+:) a b p) instance (GHC.Generics.Datatype c, GHCJS.Marshal.Internal.GToJSVal (a p)) => GHCJS.Marshal.Internal.GToJSVal (GHC.Generics.M1 GHC.Generics.D c a p) instance (GHC.Generics.Constructor c, GHCJS.Marshal.Internal.GToJSVal (a p)) => GHCJS.Marshal.Internal.GToJSVal (GHC.Generics.M1 GHC.Generics.C c a p) instance (GHCJS.Marshal.Internal.GToJSArr (a p), GHCJS.Marshal.Internal.GToJSArr (b p), GHCJS.Marshal.Internal.GToJSProp (a p), GHCJS.Marshal.Internal.GToJSProp (b p)) => GHCJS.Marshal.Internal.GToJSVal ((GHC.Generics.:*:) a b p) instance GHCJS.Marshal.Internal.GToJSVal (a p) => GHCJS.Marshal.Internal.GToJSVal (GHC.Generics.M1 GHC.Generics.S c a p) instance (GHCJS.Marshal.Internal.GToJSProp (a p), GHCJS.Marshal.Internal.GToJSProp (b p)) => GHCJS.Marshal.Internal.GToJSProp ((GHC.Generics.:*:) a b p) instance (GHC.Generics.Selector c, GHCJS.Marshal.Internal.GToJSVal (a p)) => GHCJS.Marshal.Internal.GToJSProp (GHC.Generics.M1 GHC.Generics.S c a p) instance (GHCJS.Marshal.Internal.GToJSArr (a p), GHCJS.Marshal.Internal.GToJSArr (b p)) => GHCJS.Marshal.Internal.GToJSArr ((GHC.Generics.:*:) a b p) instance GHCJS.Marshal.Internal.GToJSVal (a p) => GHCJS.Marshal.Internal.GToJSArr (GHC.Generics.M1 GHC.Generics.S c a p) instance GHCJS.Marshal.Internal.GToJSVal (GHC.Generics.V1 p) instance GHCJS.Marshal.Internal.GToJSVal (GHC.Generics.U1 p) instance GHCJS.Marshal.Internal.FromJSVal b => GHCJS.Marshal.Internal.GFromJSVal (GHC.Generics.K1 a b c) instance GHCJS.Marshal.Internal.GFromJSVal p => GHCJS.Marshal.Internal.GFromJSVal (GHC.Generics.Par1 p) instance GHCJS.Marshal.Internal.GFromJSVal (f p) => GHCJS.Marshal.Internal.GFromJSVal (GHC.Generics.Rec1 f p) instance (GHCJS.Marshal.Internal.GFromJSVal (a p), GHCJS.Marshal.Internal.GFromJSVal (b p)) => GHCJS.Marshal.Internal.GFromJSVal ((GHC.Generics.:+:) a b p) instance (GHC.Generics.Datatype c, GHCJS.Marshal.Internal.GFromJSVal (a p)) => GHCJS.Marshal.Internal.GFromJSVal (GHC.Generics.M1 GHC.Generics.D c a p) instance (GHC.Generics.Constructor c, GHCJS.Marshal.Internal.GFromJSVal (a p)) => GHCJS.Marshal.Internal.GFromJSVal (GHC.Generics.M1 GHC.Generics.C c a p) instance (GHCJS.Marshal.Internal.GFromJSArr (a p), GHCJS.Marshal.Internal.GFromJSArr (b p), GHCJS.Marshal.Internal.GFromJSProp (a p), GHCJS.Marshal.Internal.GFromJSProp (b p)) => GHCJS.Marshal.Internal.GFromJSVal ((GHC.Generics.:*:) a b p) instance GHCJS.Marshal.Internal.GFromJSVal (a p) => GHCJS.Marshal.Internal.GFromJSVal (GHC.Generics.M1 GHC.Generics.S c a p) instance (GHCJS.Marshal.Internal.GFromJSProp (a p), GHCJS.Marshal.Internal.GFromJSProp (b p)) => GHCJS.Marshal.Internal.GFromJSProp ((GHC.Generics.:*:) a b p) instance (GHC.Generics.Selector c, GHCJS.Marshal.Internal.GFromJSVal (a p)) => GHCJS.Marshal.Internal.GFromJSProp (GHC.Generics.M1 GHC.Generics.S c a p) instance (GHCJS.Marshal.Internal.GFromJSArr (a p), GHCJS.Marshal.Internal.GFromJSArr (b p)) => GHCJS.Marshal.Internal.GFromJSArr ((GHC.Generics.:*:) a b p) instance GHCJS.Marshal.Internal.GFromJSVal (a p) => GHCJS.Marshal.Internal.GFromJSArr (GHC.Generics.M1 GHC.Generics.S c a p) instance GHCJS.Marshal.Internal.GFromJSVal (GHC.Generics.V1 p) instance GHCJS.Marshal.Internal.GFromJSVal (GHC.Generics.U1 p) module GHCJS.Marshal.Pure class PFromJSVal a pFromJSVal :: PFromJSVal a => JSVal -> a class PToJSVal a pToJSVal :: PToJSVal a => a -> JSVal instance GHCJS.Marshal.Internal.PFromJSVal GHCJS.Prim.Internal.JSVal instance GHCJS.Marshal.Internal.PFromJSVal () instance GHCJS.Marshal.Internal.PToJSVal GHCJS.Prim.Internal.JSVal instance GHCJS.Marshal.Internal.PToJSVal GHC.Types.Bool module JavaScript.TypedArray.ArrayBuffer.Internal newtype SomeArrayBuffer (a :: MutabilityType s) SomeArrayBuffer :: JSVal -> SomeArrayBuffer type ArrayBuffer = SomeArrayBuffer Immutable type MutableArrayBuffer = SomeArrayBuffer Mutable type STArrayBuffer s = SomeArrayBuffer (STMutable s) instance forall s (m :: Language.Javascript.JSaddle.Types.MutabilityType s). Language.Javascript.JSaddle.Types.IsJSVal (JavaScript.TypedArray.ArrayBuffer.Internal.SomeArrayBuffer m) instance GHCJS.Marshal.Internal.PToJSVal JavaScript.TypedArray.ArrayBuffer.Internal.MutableArrayBuffer instance GHCJS.Marshal.Internal.PFromJSVal JavaScript.TypedArray.ArrayBuffer.Internal.MutableArrayBuffer module JavaScript.TypedArray.DataView.Internal newtype SomeDataView (a :: MutabilityType s) SomeDataView :: JSVal -> SomeDataView type DataView = SomeDataView Immutable type MutableDataView = SomeDataView Mutable type STDataView s = SomeDataView (STMutable s) module Language.Javascript.JSaddle.Helper -- | Helper function needed because there is no FromJSVal instance for -- MutableArrayBuffer mutableArrayBufferFromJSVal :: JSVal -> JSM MutableArrayBuffer -- | Helper function needed because there is no ToJSVal instance for -- MutableArrayBuffer mutableArrayBufferToJSVal :: MutableArrayBuffer -> JSM JSVal -- | JSStrings in JSaddle (when compiled with GHC) is not a -- JSVal instead it is implemented with a Text. module Language.Javascript.JSaddle.Marshal.String -- | Anything that can be used to make a JavaScript string class ToJSVal a => ToJSString a toJSString :: ToJSString a => a -> JSString -- | Anything that can be constructed from a JavaScript string class FromJSVal a => FromJSString a fromJSString :: FromJSString a => JSString -> a -- | These classes are used to make various JavaScript types out of -- whatever we have. Functions in jsaddle take these as inputs. This -- alows implicit casting and eager evaluation. module Language.Javascript.JSaddle.Classes class PToJSVal a pToJSVal :: PToJSVal a => a -> JSVal class PFromJSVal a pFromJSVal :: PFromJSVal a => JSVal -> a class ToJSVal a where toJSValListOf = fmap coerce . fromListIO <=< mapM toJSVal toJSVal = toJSVal_generic id toJSVal :: ToJSVal a => a -> JSM JSVal toJSValListOf :: ToJSVal a => [a] -> JSM JSVal toJSVal :: (ToJSVal a, Generic a, GToJSVal (Rep a ())) => a -> JSM JSVal class FromJSVal a where fromJSValUnchecked = fmap fromJust . fromJSVal fromJSValListOf = fmap sequence . (mapM fromJSVal <=< toListIO . coerce) fromJSValUncheckedListOf = mapM fromJSValUnchecked <=< toListIO . coerce fromJSVal = fromJSVal_generic id fromJSVal :: FromJSVal a => JSVal -> JSM (Maybe a) fromJSValUnchecked :: FromJSVal a => JSVal -> JSM a fromJSValListOf :: FromJSVal a => JSVal -> JSM (Maybe [a]) fromJSValUncheckedListOf :: FromJSVal a => JSVal -> JSM [a] fromJSVal :: (FromJSVal a, Generic a, GFromJSVal (Rep a ())) => JSVal -> JSM (Maybe a) -- | Anything that can be used to make a JavaScript string class ToJSVal a => ToJSString a toJSString :: ToJSString a => a -> JSString -- | Anything that can be constructed from a JavaScript string class FromJSVal a => FromJSString a fromJSString :: FromJSString a => JSString -> a -- | Anything that can be used to make a JavaScript object reference class MakeObject this makeObject :: MakeObject this => this -> JSM Object -- | Anything that can be used to make a list of JavaScript value -- references for use as function arguments class MakeArgs this makeArgs :: MakeArgs this => this -> JSM [JSVal] module Language.Javascript.JSaddle.Arguments -- | Anything that can be used to make a list of JavaScript value -- references for use as function arguments class MakeArgs this makeArgs :: MakeArgs this => this -> JSM [JSVal] instance GHCJS.Marshal.Internal.ToJSVal arg => Language.Javascript.JSaddle.Classes.Internal.MakeArgs [arg] instance (GHCJS.Marshal.Internal.ToJSVal arg1, GHCJS.Marshal.Internal.ToJSVal arg2) => Language.Javascript.JSaddle.Classes.Internal.MakeArgs (arg1, arg2) instance (GHCJS.Marshal.Internal.ToJSVal arg1, GHCJS.Marshal.Internal.ToJSVal arg2, GHCJS.Marshal.Internal.ToJSVal arg3) => Language.Javascript.JSaddle.Classes.Internal.MakeArgs (arg1, arg2, arg3) instance (GHCJS.Marshal.Internal.ToJSVal arg1, GHCJS.Marshal.Internal.ToJSVal arg2, GHCJS.Marshal.Internal.ToJSVal arg3, GHCJS.Marshal.Internal.ToJSVal arg4) => Language.Javascript.JSaddle.Classes.Internal.MakeArgs (arg1, arg2, arg3, arg4) instance (GHCJS.Marshal.Internal.ToJSVal arg1, GHCJS.Marshal.Internal.ToJSVal arg2, GHCJS.Marshal.Internal.ToJSVal arg3, GHCJS.Marshal.Internal.ToJSVal arg4, GHCJS.Marshal.Internal.ToJSVal arg5) => Language.Javascript.JSaddle.Classes.Internal.MakeArgs (arg1, arg2, arg3, arg4, arg5) instance (GHCJS.Marshal.Internal.ToJSVal arg1, GHCJS.Marshal.Internal.ToJSVal arg2, GHCJS.Marshal.Internal.ToJSVal arg3, GHCJS.Marshal.Internal.ToJSVal arg4, GHCJS.Marshal.Internal.ToJSVal arg5, GHCJS.Marshal.Internal.ToJSVal arg6) => Language.Javascript.JSaddle.Classes.Internal.MakeArgs (arg1, arg2, arg3, arg4, arg5, arg6) -- | If you just want to run some JavaScript that you have as a string this -- is you can use eval or evaluateScript. module Language.Javascript.JSaddle.Evaluate -- | Evaluates a script (like eval in java script) -- --
--   >>> testJSaddle $ eval "1+1"
--   2
--   
eval :: (ToJSString script) => script -> JSM JSVal module Language.Javascript.JSaddle.Native withToJSVal :: ToJSVal val => val -> (JSValueForSend -> JSM a) -> JSM a -- | Low level JavaScript object property access. In most cases you should -- use Language.Javascript.JSaddle.Object instead. -- -- This module is mostly here to implement functions needed to use -- JSPropRef. module Language.Javascript.JSaddle.Properties -- | get a property from an object. If accessing the property results in an -- exception, the exception is converted to a JSException. Since -- exception handling code prevents some optimizations in some JS -- engines, you may want to use unsafeGetProp instead getProp :: JSString -> Object -> JSM JSVal unsafeGetProp :: JSString -> Object -> JSM JSVal -- | Get a property value given the object and the name of the property. objGetPropertyByName :: ToJSString name => Object -> name -> JSM JSVal -- | Get a property value given the object and the index of the property. objGetPropertyAtIndex :: Object -> Int -> JSM JSVal setProp :: JSString -> JSVal -> Object -> JSM () unsafeSetProp :: JSString -> JSVal -> Object -> JSM () -- | Set a property value given the object and the name of the property. objSetPropertyByName :: (ToJSString name, ToJSVal val) => Object -> name -> val -> JSM () -- | Set a property value given the object and the index of the property. objSetPropertyAtIndex :: (ToJSVal val) => Object -> Int -> val -> JSM () -- | Deals with JavaScript values. These can be -- -- module Language.Javascript.JSaddle.Value data JSVal class ToJSVal a where toJSValListOf = fmap coerce . fromListIO <=< mapM toJSVal toJSVal = toJSVal_generic id toJSVal :: ToJSVal a => a -> JSM JSVal toJSValListOf :: ToJSVal a => [a] -> JSM JSVal toJSVal :: (ToJSVal a, Generic a, GToJSVal (Rep a ())) => a -> JSM JSVal data JSNull -- | Type that represents a value that can only be null. Haskell of course -- has no null so we are adding this type. JSNull :: JSNull type JSUndefined = () A type that can only be undefined in JavaScript. Using () because functions in JavaScript that have no return, impicitly return undefined. type JSBool = Bool -- ^ JavaScript boolean values map the 'Bool' haskell type. type JSNumber = Double -- ^ A number in JavaScript maps nicely to 'Double'. type JSString = Text -- ^ JavaScript strings can be represented with the Haskell 'Text' type. -- | A wrapper around a JavaScript string data JSString -- | An algebraic data type that can represent a JavaScript value. Any -- JavaScriptCore JSVal can be converted into this type. data JSValue -- | null ValNull :: JSValue -- | undefined ValUndefined :: JSValue -- | true or false ValBool :: Bool -> JSValue -- | a number ValNumber :: Double -> JSValue -- | a string ValString :: Text -> JSValue -- | an object ValObject :: Object -> JSValue -- | Show a JSValue but just say "object" if the value is a JavaScript -- object. showJSValue :: JSValue -> String isTruthy :: JSVal -> GHCJSPure Bool -- | Given a JavaScript value get its boolean value. All values in -- JavaScript convert to bool. -- --
--   >>> testJSaddle $ valToBool JSNull
--   false
--   
--   >>> testJSaddle $ valToBool ()
--   false
--   
--   >>> testJSaddle $ valToBool True
--   true
--   
--   >>> testJSaddle $ valToBool False
--   false
--   
--   >>> testJSaddle $ valToBool (1.0 :: Double)
--   true
--   
--   >>> testJSaddle $ valToBool (0.0 :: Double)
--   false
--   
--   >>> testJSaddle $ valToBool ""
--   false
--   
--   >>> testJSaddle $ valToBool "1"
--   true
--   
valToBool :: ToJSVal value => value -> JSM Bool -- | Given a JavaScript value get its numeric value. May throw JSException. -- --
--   >>> testJSaddle $ show <$> valToNumber JSNull
--   0.0
--   
--   >>> testJSaddle $ show <$> valToNumber ()
--   NaN
--   
--   >>> testJSaddle $ show <$> valToNumber True
--   1.0
--   
--   >>> testJSaddle $ show <$> valToNumber False
--   0.0
--   
--   >>> testJSaddle $ show <$> valToNumber (1.0 :: Double)
--   1.0
--   
--   >>> testJSaddle $ show <$> valToNumber (0.0 :: Double)
--   0.0
--   
--   >>> testJSaddle $ show <$> valToNumber ""
--   0.0
--   
--   >>> testJSaddle $ show <$> valToNumber "1"
--   1.0
--   
valToNumber :: ToJSVal value => value -> JSM Double -- | Given a JavaScript value get its string value (as a JavaScript -- string). May throw JSException. -- --
--   >>> testJSaddle $ strToText <$> valToStr JSNull
--   null
--   
--   >>> testJSaddle $ strToText <$> valToStr ()
--   undefined
--   
--   >>> testJSaddle $ strToText <$> valToStr True
--   true
--   
--   >>> testJSaddle $ strToText <$> valToStr False
--   false
--   
--   >>> testJSaddle $ strToText <$> valToStr (1.0 :: Double)
--   1
--   
--   >>> testJSaddle $ strToText <$> valToStr (0.0 :: Double)
--   0
--   
--   >>> testJSaddle $ strToText <$> valToStr ""
--   
--   
--   >>> testJSaddle $ strToText <$> valToStr "1"
--   1
--   
valToStr :: ToJSVal value => value -> JSM JSString -- | Given a JavaScript value get its object value. May throw JSException. -- --
--   >>> testJSaddle $ (valToObject JSNull >>= valToText) `catch` \ (JSException e) -> valToText e
--   null
--   
--   >>> testJSaddle $ (valToObject () >>= valToText) `catch` \ (JSException e) -> valToText e
--   undefined
--   
--   >>> testJSaddle $ valToObject True
--   true
--   
--   >>> testJSaddle $ valToObject False
--   false
--   
--   >>> testJSaddle $ valToObject (1.0 :: Double)
--   1
--   
--   >>> testJSaddle $ valToObject (0.0 :: Double)
--   0
--   
--   >>> testJSaddle $ valToObject ""
--   
--   
--   >>> testJSaddle $ valToObject "1"
--   1
--   
valToObject :: ToJSVal value => value -> JSM Object -- | Given a JavaScript value get its string value (as a Haskell -- Text). May throw JSException. -- --
--   >>> testJSaddle $ show <$> valToText JSNull
--   "null"
--   
--   >>> testJSaddle $ show <$> valToText ()
--   "undefined"
--   
--   >>> testJSaddle $ show <$> valToText True
--   "true"
--   
--   >>> testJSaddle $ show <$> valToText False
--   "false"
--   
--   >>> testJSaddle $ show <$> valToText (1.0 :: Double)
--   "1"
--   
--   >>> testJSaddle $ show <$> valToText (0.0 :: Double)
--   "0"
--   
--   >>> testJSaddle $ show <$> valToText ""
--   ""
--   
--   >>> testJSaddle $ show <$> valToText "1"
--   "1"
--   
valToText :: ToJSVal value => value -> JSM Text -- | Given a JavaScript value get a JSON string value. May throw -- JSException. -- --
--   >>> testJSaddle $ strToText <$> valToJSON JSNull
--   null
--   
--   >>> testJSaddle $ strToText <$> valToJSON ()
--   
--   
--   >>> testJSaddle $ strToText <$> valToJSON True
--   true
--   
--   >>> testJSaddle $ strToText <$> valToJSON False
--   false
--   
--   >>> testJSaddle $ strToText <$> valToJSON (1.0 :: Double)
--   1
--   
--   >>> testJSaddle $ strToText <$> valToJSON (0.0 :: Double)
--   0
--   
--   >>> testJSaddle $ strToText <$> valToJSON ""
--   ""
--   
--   >>> testJSaddle $ strToText <$> valToJSON "1"
--   "1"
--   
--   >>> testJSaddle $ strToText <$> (obj >>= valToJSON)
--   {}
--   
valToJSON :: ToJSVal value => value -> JSM JSString -- | Convert to a JavaScript value (just an alias for toJSVal) val :: ToJSVal value => value -> JSM JSVal jsNull :: JSVal -- | A null JavaScript value valNull :: JSVal isNull :: JSVal -> GHCJSPure Bool -- | Test a JavaScript value to see if it is null valIsNull :: ToJSVal value => value -> JSM Bool jsUndefined :: JSVal -- | An undefined JavaScript value valUndefined :: JSVal isUndefined :: JSVal -> GHCJSPure Bool -- | Test a JavaScript value to see if it is undefined valIsUndefined :: ToJSVal value => value -> JSM Bool -- | Convert a JSVal to a Maybe JSVal (converting null and undefined to -- Nothing) maybeNullOrUndefined :: ToJSVal value => value -> JSM (Maybe JSVal) maybeNullOrUndefined' :: ToJSVal value => (JSVal -> JSM a) -> value -> JSM (Maybe a) toJSBool :: Bool -> JSVal jsTrue :: JSVal jsFalse :: JSVal -- | A JavaScript boolean value valBool :: Bool -> JSVal -- | Make a JavaScript number valMakeNumber :: Double -> JSM JSVal -- | Make a JavaScript string from JSString valMakeString :: JSString -> JSM JSVal -- | Make a JavaScript string from Text valMakeText :: Text -> JSM JSVal -- | Make a JavaScript string from AESON Value valMakeJSON :: Value -> JSM JSVal -- | Derefernce a value reference. -- --
--   >>> testJSaddle $ showJSValue <$> deRefVal JSNull
--   null
--   
--   >>> testJSaddle $ showJSValue <$> deRefVal ()
--   undefined
--   
--   >>> testJSaddle $ showJSValue <$> deRefVal True
--   true
--   
--   >>> testJSaddle $ showJSValue <$> deRefVal False
--   false
--   
--   >>> testJSaddle $ showJSValue <$> deRefVal (1.0 :: Double)
--   1.0
--   
--   >>> testJSaddle $ showJSValue <$> deRefVal (0.0 :: Double)
--   0.0
--   
--   >>> testJSaddle $ showJSValue <$> deRefVal ""
--   ""
--   
--   >>> testJSaddle $ showJSValue <$> deRefVal "1"
--   "1"
--   
--   >>> testJSaddle $ showJSValue <$> (valToObject True >>= deRefVal)
--   true
--   
--   >>> testJSaddle $ showJSValue <$> (obj >>= deRefVal)
--   object
--   
deRefVal :: ToJSVal value => value -> JSM JSValue -- | Make a JavaScript value out of a JSValue ADT. -- --
--   >>> testJSaddle $ valMakeRef ValNull
--   null
--   
--   >>> testJSaddle $ valMakeRef ValUndefined
--   undefined
--   
--   >>> testJSaddle $ valMakeRef (ValBool True)
--   true
--   
--   >>> testJSaddle $ valMakeRef (ValNumber 1)
--   1
--   
--   >>> testJSaddle $ valMakeRef (ValString $ T.pack "Hello")
--   Hello
--   
valMakeRef :: JSValue -> JSM JSVal -- | Determine if two values are equal (JavaScripts ===) >>> -- testJSaddle $ strictEqual True False false >>> testJSaddle $ -- strictEqual True True true >>> testJSaddle $ strictEqual -- Hello () false >>> testJSaddle $ strictEqual -- Hello Hello true strictEqual :: (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool -- | Determine if two values are equal (JavaScripts ===) >>> -- testJSaddle $ instanceOf obj (Object $ jsg Object) true instanceOf :: (ToJSVal value, MakeObject constructor) => value -> constructor -> JSM Bool instance Language.Javascript.JSaddle.Classes.Internal.MakeObject GHCJS.Prim.Internal.JSVal instance GHCJS.Marshal.Internal.ToJSVal Language.Javascript.JSaddle.Types.Object instance GHCJS.Marshal.Internal.ToJSVal GHCJS.Prim.Internal.JSVal instance Language.Javascript.JSaddle.Classes.Internal.MakeArgs GHCJS.Prim.Internal.JSVal instance GHCJS.Marshal.Internal.ToJSVal v => GHCJS.Marshal.Internal.ToJSVal (Language.Javascript.JSaddle.Types.JSM v) instance GHCJS.Marshal.Internal.ToJSVal Language.Javascript.JSaddle.Value.JSNull instance Language.Javascript.JSaddle.Classes.Internal.MakeArgs Language.Javascript.JSaddle.Value.JSNull instance GHCJS.Marshal.Internal.ToJSVal a => GHCJS.Marshal.Internal.ToJSVal (GHC.Base.Maybe a) instance GHCJS.Marshal.Internal.FromJSVal a => GHCJS.Marshal.Internal.FromJSVal (GHC.Base.Maybe a) instance GHCJS.Marshal.Internal.ToJSVal a => GHCJS.Marshal.Internal.ToJSVal [a] instance GHCJS.Marshal.Internal.FromJSVal a => GHCJS.Marshal.Internal.FromJSVal [a] instance GHCJS.Marshal.Internal.ToJSVal Language.Javascript.JSaddle.Value.JSUndefined instance Language.Javascript.JSaddle.Classes.Internal.MakeArgs () instance GHCJS.Marshal.Internal.ToJSVal GHC.Types.Bool instance Language.Javascript.JSaddle.Classes.Internal.MakeArgs GHC.Types.Bool instance GHCJS.Marshal.Internal.ToJSVal GHC.Types.Double instance GHCJS.Marshal.Internal.ToJSVal GHC.Types.Float instance GHCJS.Marshal.Internal.ToJSVal GHC.Types.Word instance GHCJS.Marshal.Internal.ToJSVal GHC.Word.Word8 instance GHCJS.Marshal.Internal.ToJSVal GHC.Word.Word16 instance GHCJS.Marshal.Internal.ToJSVal GHC.Word.Word32 instance GHCJS.Marshal.Internal.ToJSVal GHC.Types.Int instance GHCJS.Marshal.Internal.ToJSVal GHC.Int.Int8 instance GHCJS.Marshal.Internal.ToJSVal GHC.Int.Int16 instance GHCJS.Marshal.Internal.ToJSVal GHC.Int.Int32 instance Language.Javascript.JSaddle.Classes.Internal.MakeArgs GHC.Types.Double instance GHCJS.Marshal.Internal.ToJSVal Data.Text.Internal.Text instance GHCJS.Marshal.Internal.FromJSVal Data.Text.Internal.Text instance Language.Javascript.JSaddle.Classes.Internal.MakeArgs Data.Text.Internal.Text instance GHCJS.Marshal.Internal.ToJSVal Data.JSString.Internal.Type.JSString instance GHCJS.Marshal.Internal.FromJSVal Data.JSString.Internal.Type.JSString instance Language.Javascript.JSaddle.Marshal.String.ToJSString Data.JSString.Internal.Type.JSString instance Language.Javascript.JSaddle.Marshal.String.ToJSString Data.Text.Internal.Text instance Language.Javascript.JSaddle.Marshal.String.ToJSString GHC.Base.String instance Language.Javascript.JSaddle.Marshal.String.FromJSString Data.Text.Internal.Text instance Language.Javascript.JSaddle.Marshal.String.FromJSString GHC.Base.String instance Language.Javascript.JSaddle.Marshal.String.FromJSString Data.JSString.Internal.Type.JSString instance GHCJS.Marshal.Internal.ToJSVal GHC.Types.Char instance GHCJS.Marshal.Internal.FromJSVal GHC.Types.Char instance GHCJS.Marshal.Internal.ToJSVal Data.Aeson.Types.Internal.Value instance Language.Javascript.JSaddle.Classes.Internal.MakeArgs Data.Aeson.Types.Internal.Value instance GHCJS.Marshal.Internal.ToJSVal Language.Javascript.JSaddle.Value.JSValue instance Language.Javascript.JSaddle.Classes.Internal.MakeArgs Language.Javascript.JSaddle.Value.JSValue -- | Interface to JavaScript object module Language.Javascript.JSaddle.Object -- | See Object newtype Object Object :: JSVal -> Object -- | Anything that can be used to make a JavaScript object reference class MakeObject this makeObject :: MakeObject this => this -> JSM Object -- | Lookup a property based on its name. -- --
--   >>> testJSaddle $ eval "'Hello World'.length"
--   11
--   
--   >>> testJSaddle $ val "Hello World" ! "length"
--   11
--   
(!) :: (MakeObject this, ToJSString name) => this -> name -> JSM JSVal -- | Lookup a property based on its index. -- --
--   >>> testJSaddle $ eval "'Hello World'[6]"
--   W
--   
--   >>> testJSaddle $ val "Hello World" !! 6
--   W
--   
(!!) :: (MakeObject this) => this -> Int -> JSM JSVal -- | Makes a getter for a particular property name. -- --
--   js name = to (!name)
--   
-- --
--   >>> testJSaddle $ eval "'Hello World'.length"
--   11
--   
--   >>> testJSaddle $ val "Hello World" ^. js "length"
--   11
--   
js :: (MakeObject s, ToJSString name) => name -> IndexPreservingGetter s (JSM JSVal) -- | Makes a setter for a particular property name. -- --
--   jss name = to (<#name)
--   
-- --
--   >>> testJSaddle $ eval "'Hello World'.length = 12"
--   12
--   
--   >>> testJSaddle $ val "Hello World" ^. jss "length" 12
--   undefined
--   
jss :: (ToJSString name, ToJSVal val) => name -> val -> forall o. MakeObject o => IndexPreservingGetter o (JSM ()) -- | Java script function applications have this type type JSF = forall o. MakeObject o => IndexPreservingGetter o (JSM JSVal) -- | Handy way to call a function -- --
--   jsf name = to (\o -> o # name $ args)
--   
-- --
--   >>> testJSaddle $ val "Hello World" ^. jsf "indexOf" ["World"]
--   6
--   
jsf :: (ToJSString name, MakeArgs args) => name -> args -> JSF -- | Handy way to call a function that expects no arguments -- --
--   js0 name = jsf name ()
--   
-- --
--   >>> testJSaddle $ val "Hello World" ^. js0 "toLowerCase"
--   hello world
--   
js0 :: (ToJSString name) => name -> JSF -- | Handy way to call a function that expects one argument -- --
--   js1 name a0 = jsf name [a0]
--   
-- --
--   >>> testJSaddle $ val "Hello World" ^. js1 "indexOf" "World"
--   6
--   
js1 :: (ToJSString name, ToJSVal a0) => name -> a0 -> JSF -- | Handy way to call a function that expects two arguments js2 :: (ToJSString name, ToJSVal a0, ToJSVal a1) => name -> a0 -> a1 -> JSF -- | Handy way to call a function that expects three arguments js3 :: (ToJSString name, ToJSVal a0, ToJSVal a1, ToJSVal a2) => name -> a0 -> a1 -> a2 -> JSF -- | Handy way to call a function that expects four arguments js4 :: (ToJSString name, ToJSVal a0, ToJSVal a1, ToJSVal a2, ToJSVal a3) => name -> a0 -> a1 -> a2 -> a3 -> JSF -- | Handy way to call a function that expects five arguments js5 :: (ToJSString name, ToJSVal a0, ToJSVal a1, ToJSVal a2, ToJSVal a3, ToJSVal a4) => name -> a0 -> a1 -> a2 -> a3 -> a4 -> JSF -- | Handy way to get and hold onto a reference top level javascript -- --
--   >>> testJSaddle $ eval "w = console; w.log('Hello World')"
--   undefined
--   
--   >>> testJSaddle $ do w <- jsg "console"; w ^. js1 "log" "Hello World"
--   undefined
--   
jsg :: ToJSString a => a -> JSM JSVal -- | Handy way to call a function -- --
--   jsgf name = jsg name . to (# args)
--   
-- --
--   >>> testJSaddle $ eval "globalFunc = function (x) {return x.length;}"
--   function (x) {return x.length;}
--   
--   >>> testJSaddle $ jsgf "globalFunc" ["World"]
--   5
--   
jsgf :: (ToJSString name, MakeArgs args) => name -> args -> JSM JSVal -- | Handy way to call a function that expects no arguments -- --
--   jsg0 name = jsgf name ()
--   
-- --
--   >>> testJSaddle $ jsg0 "globalFunc" >>= valToText
--   A JavaScript exception was thrown! (may not reach Haskell code)
--   TypeError:...undefine...
--   
jsg0 :: (ToJSString name) => name -> JSM JSVal -- | Handy way to call a function that expects one argument -- --
--   jsg1 name a0 = jsgf name [a0]
--   
-- --
--   >>> testJSaddle $ jsg1 "globalFunc" "World"
--   5
--   
jsg1 :: (ToJSString name, ToJSVal a0) => name -> a0 -> JSM JSVal -- | Handy way to call a function that expects two arguments jsg2 :: (ToJSString name, ToJSVal a0, ToJSVal a1) => name -> a0 -> a1 -> JSM JSVal -- | Handy way to call a function that expects three arguments jsg3 :: (ToJSString name, ToJSVal a0, ToJSVal a1, ToJSVal a2) => name -> a0 -> a1 -> a2 -> JSM JSVal -- | Handy way to call a function that expects four arguments jsg4 :: (ToJSString name, ToJSVal a0, ToJSVal a1, ToJSVal a2, ToJSVal a3) => name -> a0 -> a1 -> a2 -> a3 -> JSM JSVal -- | Handy way to call a function that expects five arguments jsg5 :: (ToJSString name, ToJSVal a0, ToJSVal a1, ToJSVal a2, ToJSVal a3, ToJSVal a4) => name -> a0 -> a1 -> a2 -> a3 -> a4 -> JSM JSVal -- | Set a JavaScript property -- --
--   >>> testJSaddle $ eval "var j = {}; j.x = 1; j.x"
--   1
--   
--   >>> testJSaddle $ do {j <- obj; (j <# "x") 1; j!"x"}
--   1
--   
(<#) :: (MakeObject this, ToJSString name, ToJSVal val) => this -> name -> val -> JSM () infixr 1 <# -- | Set a JavaScript property -- --
--   >>> testJSaddle $ eval "var j = {}; j[6] = 1; j[6]"
--   1
--   
--   >>> testJSaddle $ do {j <- obj; (j <## 6) 1; j!!6}
--   1
--   
(<##) :: (MakeObject this, ToJSVal val) => this -> Int -> val -> JSM () infixr 1 <## -- | Call a JavaScript function -- --
--   >>> testJSaddle $ eval "'Hello World'.indexOf('World')"
--   6
--   
--   >>> testJSaddle $ val "Hello World" # "indexOf" $ ["World"]
--   6
--   
(#) :: (MakeObject this, ToJSString name, MakeArgs args) => this -> name -> args -> JSM JSVal infixr 2 # -- | Call a JavaScript function -- --
--   >>> testJSaddle $ eval "something = {}; something[6]=function (x) {return x.length;}; something[6]('World')"
--   5
--   
--   >>> testJSaddle $ jsg "something" ## 6 $ ["World"]
--   5
--   
(##) :: (MakeObject this, MakeArgs args) => this -> Int -> args -> JSM JSVal infixr 2 ## -- | Use this to create a new JavaScript object -- -- If you pass more than 7 arguments to a constructor for a built in -- JavaScript type (like Date) then this function will fail. -- --
--   >>> testJSaddle $ new (jsg "Date") (2013, 1, 1)
--   Fri Feb 01 2013 00:00:00 GMT+... (...)
--   
new :: (MakeObject constructor, MakeArgs args) => constructor -> args -> JSM JSVal -- | Call function with a given this. In most cases you should use -- #. -- --
--   >>> testJSaddle $ eval "(function(){return this;}).apply('Hello', [])"
--   Hello
--   
--   >>> testJSaddle $ do { test <- eval "(function(){return this;})"; call test (val "Hello") () }
--   Hello
--   
call :: (MakeObject f, MakeObject this, MakeArgs args) => f -> this -> args -> JSM JSVal -- | Make an empty object using the default constuctor -- --
--   >>> testJSaddle $ eval "var a = {}; a.x = 'Hello'; a.x"
--   Hello
--   
--   >>> testJSaddle $ do { a <- obj; (a <# "x") "Hello"; a ^. js "x" }
--   Hello
--   
obj :: JSM Object -- | create an empty object create :: JSM Object -- | get a property from an object. If accessing the property results in an -- exception, the exception is converted to a JSException. Since -- exception handling code prevents some optimizations in some JS -- engines, you may want to use unsafeGetProp instead getProp :: JSString -> Object -> JSM JSVal unsafeGetProp :: JSString -> Object -> JSM JSVal setProp :: JSString -> JSVal -> Object -> JSM () unsafeSetProp :: JSString -> JSVal -> Object -> JSM () -- | Make a JavaScript function object that wraps a Haskell function. newtype Function Function :: Object -> Function [functionObject] :: Function -> Object function :: JSCallAsFunction -> JSM Function freeFunction :: Function -> JSM () -- | Short hand ::JSCallAsFunction so a haskell function can be -- passed to a to a JavaScipt one. -- --
--   >>> testJSaddle $ eval "(function(f) {f('Hello');})(function (a) {console.log(a)})"
--   undefined
--   
--   >>> :{
--    testJSaddle $ do
--      result <- liftIO newEmptyMVar
--      deRefVal $ call (eval "(function(f) {f('Hello');})") global [fun $ \ _ _ [arg1] -> do
--           valToText arg1 >>= (liftIO . putMVar result)
--           ]
--      liftIO $ takeMVar result
--   :}
--   Hello
--   
fun :: JSCallAsFunction -> JSCallAsFunction -- | Type used for Haskell functions called from JavaScript. type JSCallAsFunction = JSVal Function object -> JSVal this -> [JSVal] Function arguments -> JSM () Only () (aka 'JSUndefined') can be returned because the function may need to be executed in a different thread. If you need to get a value out pass in a continuation function as an argument and invoke it from haskell. fromListIO :: [JSVal] -> JSM (SomeJSArray m) -- | Make an JavaScript array from a list of values -- --
--   >>> testJSaddle $ eval "['Hello', 'World'][1]"
--   World
--   
--   >>> testJSaddle $ array ["Hello", "World"] !! 1
--   World
--   
--   >>> testJSaddle $ eval "['Hello', null, undefined, true, 1]"
--   Hello,,,true,1
--   
--   >>> testJSaddle $ array ("Hello", JSNull, (), True, 1.0::Double)
--   Hello,,,true,1
--   
array :: MakeArgs args => args -> JSM Object -- | JavaScript's global object global :: Object listProps :: Object -> JSM [JSString] -- | Get a list containing the property names present on a given object -- >>> testJSaddle $ show . map strToText $ propertyNames -- obj [] >>> testJSaddle $ show . map strToText $ -- propertyNames (eval "({x:1, y:2})") ["x","y"] propertyNames :: MakeObject this => this -> JSM [JSString] -- | Get a list containing references to all the properties present on a -- given object properties :: MakeObject this => this -> JSM [JSVal] -- | Call a JavaScript object as function. Consider using #. objCallAsFunction :: MakeArgs args => Object -> Object -> args -> JSM JSVal -- | Call a JavaScript object as a constructor. Consider using new. -- -- If you pass more than 7 arguments to a constructor for a built in -- JavaScript type (like Date) then this function will fail. objCallAsConstructor :: MakeArgs args => Object -> args -> JSM JSVal nullObject :: Object instance Language.Javascript.JSaddle.Classes.Internal.MakeObject v => Language.Javascript.JSaddle.Classes.Internal.MakeObject (Language.Javascript.JSaddle.Types.JSM v) instance GHCJS.Marshal.Internal.ToJSVal Language.Javascript.JSaddle.Object.Function instance GHCJS.Marshal.Internal.ToJSVal Language.Javascript.JSaddle.Types.JSCallAsFunction instance Language.Javascript.JSaddle.Classes.Internal.MakeArgs Language.Javascript.JSaddle.Types.JSCallAsFunction -- | Interface to JavaScript array module JavaScript.Array newtype SomeJSArray (m :: MutabilityType s) SomeJSArray :: JSVal -> SomeJSArray -- | See JSArray type JSArray = SomeJSArray Immutable -- | See MutableJSArray type MutableJSArray = SomeJSArray Mutable create :: JSM MutableJSArray length :: SomeJSArray m -> GHCJSPure Int lengthIO :: SomeJSArray m -> JSM Int null :: SomeJSArray m -> GHCJSPure Bool fromList :: [JSVal] -> GHCJSPure (SomeJSArray m) fromListIO :: [JSVal] -> JSM (SomeJSArray m) toList :: SomeJSArray m -> GHCJSPure [JSVal] toListIO :: SomeJSArray m -> JSM [JSVal] index :: Int -> SomeJSArray m -> GHCJSPure JSVal (!) :: JSArray -> Int -> GHCJSPure JSVal read :: Int -> SomeJSArray m -> JSM JSVal write :: Int -> JSVal -> MutableJSArray -> JSM () append :: SomeJSArray m -> SomeJSArray m -> JSM (SomeJSArray m1) push :: JSVal -> MutableJSArray -> JSM () pop :: MutableJSArray -> JSM JSVal unshift :: JSVal -> MutableJSArray -> JSM () shift :: MutableJSArray -> JSM JSVal reverse :: MutableJSArray -> JSM () take :: Int -> SomeJSArray m -> GHCJSPure (SomeJSArray m1) takeIO :: Int -> SomeJSArray m -> JSM (SomeJSArray m1) drop :: Int -> SomeJSArray m -> GHCJSPure (SomeJSArray m1) dropIO :: Int -> SomeJSArray m -> JSM (SomeJSArray m1) slice :: Int -> Int -> JSArray -> GHCJSPure (SomeJSArray m1) sliceIO :: Int -> Int -> JSArray -> JSM (SomeJSArray m1) freeze :: MutableJSArray -> JSM JSArray unsafeFreeze :: MutableJSArray -> JSM JSArray thaw :: JSArray -> JSM MutableJSArray unsafeThaw :: JSArray -> JSM MutableJSArray module GHCJS.Marshal class FromJSVal a where fromJSValUnchecked = fmap fromJust . fromJSVal fromJSValListOf = fmap sequence . (mapM fromJSVal <=< toListIO . coerce) fromJSValUncheckedListOf = mapM fromJSValUnchecked <=< toListIO . coerce fromJSVal = fromJSVal_generic id fromJSVal :: FromJSVal a => JSVal -> JSM (Maybe a) fromJSValUnchecked :: FromJSVal a => JSVal -> JSM a fromJSValListOf :: FromJSVal a => JSVal -> JSM (Maybe [a]) fromJSValUncheckedListOf :: FromJSVal a => JSVal -> JSM [a] fromJSVal :: (FromJSVal a, Generic a, GFromJSVal (Rep a ())) => JSVal -> JSM (Maybe a) class ToJSVal a where toJSValListOf = fmap coerce . fromListIO <=< mapM toJSVal toJSVal = toJSVal_generic id toJSVal :: ToJSVal a => a -> JSM JSVal toJSValListOf :: ToJSVal a => [a] -> JSM JSVal toJSVal :: (ToJSVal a, Generic a, GToJSVal (Rep a ())) => a -> JSM JSVal toJSVal_aeson :: ToJSON a => a -> JSM JSVal toJSVal_pure :: PToJSVal a => a -> JSM JSVal instance GHCJS.Marshal.Internal.FromJSVal GHCJS.Prim.Internal.JSVal instance GHCJS.Marshal.Internal.FromJSVal () instance GHCJS.Marshal.Internal.FromJSVal GHC.Types.Bool instance GHCJS.Marshal.Internal.FromJSVal GHC.Types.Int instance GHCJS.Marshal.Internal.FromJSVal GHC.Int.Int8 instance GHCJS.Marshal.Internal.FromJSVal GHC.Int.Int16 instance GHCJS.Marshal.Internal.FromJSVal GHC.Int.Int32 instance GHCJS.Marshal.Internal.FromJSVal GHC.Types.Word instance GHCJS.Marshal.Internal.FromJSVal GHC.Word.Word8 instance GHCJS.Marshal.Internal.FromJSVal GHC.Word.Word16 instance GHCJS.Marshal.Internal.FromJSVal GHC.Word.Word32 instance GHCJS.Marshal.Internal.FromJSVal GHC.Types.Float instance GHCJS.Marshal.Internal.FromJSVal GHC.Types.Double instance GHCJS.Marshal.Internal.FromJSVal Data.Aeson.Types.Internal.Value instance (GHCJS.Marshal.Internal.FromJSVal a, GHCJS.Marshal.Internal.FromJSVal b) => GHCJS.Marshal.Internal.FromJSVal (a, b) instance (GHCJS.Marshal.Internal.FromJSVal a, GHCJS.Marshal.Internal.FromJSVal b, GHCJS.Marshal.Internal.FromJSVal c) => GHCJS.Marshal.Internal.FromJSVal (a, b, c) instance (GHCJS.Marshal.Internal.FromJSVal a, GHCJS.Marshal.Internal.FromJSVal b, GHCJS.Marshal.Internal.FromJSVal c, GHCJS.Marshal.Internal.FromJSVal d) => GHCJS.Marshal.Internal.FromJSVal (a, b, c, d) instance (GHCJS.Marshal.Internal.FromJSVal a, GHCJS.Marshal.Internal.FromJSVal b, GHCJS.Marshal.Internal.FromJSVal c, GHCJS.Marshal.Internal.FromJSVal d, GHCJS.Marshal.Internal.FromJSVal e) => GHCJS.Marshal.Internal.FromJSVal (a, b, c, d, e) instance (GHCJS.Marshal.Internal.FromJSVal a, GHCJS.Marshal.Internal.FromJSVal b, GHCJS.Marshal.Internal.FromJSVal c, GHCJS.Marshal.Internal.FromJSVal d, GHCJS.Marshal.Internal.FromJSVal e, GHCJS.Marshal.Internal.FromJSVal f) => GHCJS.Marshal.Internal.FromJSVal (a, b, c, d, e, f) instance (GHCJS.Marshal.Internal.FromJSVal a, GHCJS.Marshal.Internal.FromJSVal b, GHCJS.Marshal.Internal.FromJSVal c, GHCJS.Marshal.Internal.FromJSVal d, GHCJS.Marshal.Internal.FromJSVal e, GHCJS.Marshal.Internal.FromJSVal f, GHCJS.Marshal.Internal.FromJSVal g) => GHCJS.Marshal.Internal.FromJSVal (a, b, c, d, e, f, g) instance (GHCJS.Marshal.Internal.FromJSVal a, GHCJS.Marshal.Internal.FromJSVal b, GHCJS.Marshal.Internal.FromJSVal c, GHCJS.Marshal.Internal.FromJSVal d, GHCJS.Marshal.Internal.FromJSVal e, GHCJS.Marshal.Internal.FromJSVal f, GHCJS.Marshal.Internal.FromJSVal g, GHCJS.Marshal.Internal.FromJSVal h) => GHCJS.Marshal.Internal.FromJSVal (a, b, c, d, e, f, g, h) instance (GHCJS.Marshal.Internal.ToJSVal a, GHCJS.Marshal.Internal.ToJSVal b) => GHCJS.Marshal.Internal.ToJSVal (a, b) instance (GHCJS.Marshal.Internal.ToJSVal a, GHCJS.Marshal.Internal.ToJSVal b, GHCJS.Marshal.Internal.ToJSVal c) => GHCJS.Marshal.Internal.ToJSVal (a, b, c) instance (GHCJS.Marshal.Internal.ToJSVal a, GHCJS.Marshal.Internal.ToJSVal b, GHCJS.Marshal.Internal.ToJSVal c, GHCJS.Marshal.Internal.ToJSVal d) => GHCJS.Marshal.Internal.ToJSVal (a, b, c, d) instance (GHCJS.Marshal.Internal.ToJSVal a, GHCJS.Marshal.Internal.ToJSVal b, GHCJS.Marshal.Internal.ToJSVal c, GHCJS.Marshal.Internal.ToJSVal d, GHCJS.Marshal.Internal.ToJSVal e) => GHCJS.Marshal.Internal.ToJSVal (a, b, c, d, e) instance (GHCJS.Marshal.Internal.ToJSVal a, GHCJS.Marshal.Internal.ToJSVal b, GHCJS.Marshal.Internal.ToJSVal c, GHCJS.Marshal.Internal.ToJSVal d, GHCJS.Marshal.Internal.ToJSVal e, GHCJS.Marshal.Internal.ToJSVal f) => GHCJS.Marshal.Internal.ToJSVal (a, b, c, d, e, f) instance (GHCJS.Marshal.Internal.ToJSVal a, GHCJS.Marshal.Internal.ToJSVal b, GHCJS.Marshal.Internal.ToJSVal c, GHCJS.Marshal.Internal.ToJSVal d, GHCJS.Marshal.Internal.ToJSVal e, GHCJS.Marshal.Internal.ToJSVal f, GHCJS.Marshal.Internal.ToJSVal g) => GHCJS.Marshal.Internal.ToJSVal (a, b, c, d, e, f, g) module GHCJS.Foreign jsTrue :: JSVal jsFalse :: JSVal jsNull :: JSVal toJSBool :: Bool -> JSVal jsUndefined :: JSVal isTruthy :: JSVal -> GHCJSPure Bool isNull :: JSVal -> GHCJSPure Bool isUndefined :: JSVal -> GHCJSPure Bool isObject :: JSVal -> GHCJSPure Bool isFunction :: JSVal -> GHCJSPure Bool isString :: JSVal -> GHCJSPure Bool isBoolean :: JSVal -> GHCJSPure Bool isSymbol :: JSVal -> GHCJSPure Bool isNumber :: JSVal -> GHCJSPure Bool data JSType Undefined :: JSType Object :: JSType Boolean :: JSType Number :: JSType String :: JSType Symbol :: JSType Function :: JSType -- | implementation dependent Other :: JSType jsTypeOf :: JSVal -> GHCJSPure JSType module JavaScript.TypedArray.ArrayBuffer type ArrayBuffer = SomeArrayBuffer Immutable type MutableArrayBuffer = SomeArrayBuffer Mutable -- | Create an immutable ArrayBuffer by copying a -- MutableArrayBuffer freeze :: MutableArrayBuffer -> JSM ArrayBuffer -- | Create an immutable ArrayBuffer from a -- MutableArrayBuffer without copying. The result shares the -- buffer with the argument, not modify the data in the -- MutableArrayBuffer after freezing unsafeFreeze :: MutableArrayBuffer -> JSM ArrayBuffer -- | Create a MutableArrayBuffer by copying an immutable -- ArrayBuffer thaw :: ArrayBuffer -> JSM MutableArrayBuffer unsafeThaw :: ArrayBuffer -> JSM MutableArrayBuffer byteLengthIO :: SomeArrayBuffer any -> JSM Int -- | This package provides an EDSL for calling JavaScript that can be used -- both from GHCJS and GHC. When using GHC the application is run using -- Warp and WebSockets to drive a small JavaScipt helper. module Language.Javascript.JSaddle module JavaScript.TypedArray.Internal.Types newtype SomeTypedArray (e :: TypedArrayElem) (m :: MutabilityType s) SomeTypedArray :: JSVal -> SomeTypedArray type SomeSTTypedArray s (e :: TypedArrayElem) = SomeTypedArray e (STMutable s) data TypedArrayElem Int8Elem :: TypedArrayElem Int16Elem :: TypedArrayElem Int32Elem :: TypedArrayElem Uint8Elem :: TypedArrayElem Uint16Elem :: TypedArrayElem Uint32Elem :: TypedArrayElem Uint8ClampedElem :: TypedArrayElem Float32Elem :: TypedArrayElem Float64Elem :: TypedArrayElem type SomeInt8Array = SomeTypedArray Int8Elem type SomeInt16Array = SomeTypedArray Int16Elem type SomeInt32Array = SomeTypedArray Int32Elem type SomeUint8Array = SomeTypedArray Uint8Elem type SomeUint16Array = SomeTypedArray Uint16Elem type SomeUint32Array = SomeTypedArray Uint32Elem type SomeFloat32Array = SomeTypedArray Float32Elem type SomeFloat64Array = SomeTypedArray Float64Elem type SomeUint8ClampedArray = SomeTypedArray Uint8ClampedElem type Int8Array = SomeInt8Array Immutable type Int16Array = SomeInt16Array Immutable type Int32Array = SomeInt32Array Immutable type Uint8Array = SomeUint8Array Immutable type Uint16Array = SomeUint16Array Immutable type Uint32Array = SomeUint32Array Immutable type Uint8ClampedArray = SomeUint8ClampedArray Immutable type Float32Array = SomeFloat32Array Immutable type Float64Array = SomeFloat64Array Immutable type IOInt8Array = SomeInt8Array Mutable type IOInt16Array = SomeInt16Array Mutable type IOInt32Array = SomeInt32Array Mutable type IOUint8Array = SomeUint8Array Mutable type IOUint16Array = SomeUint16Array Mutable type IOUint32Array = SomeUint32Array Mutable type IOUint8ClampedArray = SomeUint8ClampedArray Mutable type IOFloat32Array = SomeFloat32Array Mutable type IOFloat64Array = SomeFloat64Array Mutable type STInt8Array s = SomeSTTypedArray s Int8Elem type STInt16Array s = SomeSTTypedArray s Int16Elem type STInt32Array s = SomeSTTypedArray s Int32Elem type STUint8Array s = SomeSTTypedArray s Uint8Elem type STUint16Array s = SomeSTTypedArray s Uint16Elem type STUint32Array s = SomeSTTypedArray s Uint32Elem type STFloat32Array s = SomeSTTypedArray s Float32Elem type STFloat64Array s = SomeSTTypedArray s Float64Elem type STUint8ClampedArray s = SomeSTTypedArray s Uint8ClampedElem instance forall s (e :: JavaScript.TypedArray.Internal.Types.TypedArrayElem) (m :: Language.Javascript.JSaddle.Types.MutabilityType s). Language.Javascript.JSaddle.Types.IsJSVal (JavaScript.TypedArray.Internal.Types.SomeTypedArray e m) module GHCJS.Buffer type Buffer = SomeBuffer Immutable type MutableBuffer = SomeBuffer Mutable create :: Int -> JSM MutableBuffer createFromArrayBuffer :: SomeArrayBuffer any -> GHCJSPure (SomeBuffer any) thaw :: Buffer -> JSM MutableBuffer freeze :: MutableBuffer -> JSM Buffer clone :: MutableBuffer -> JSM (SomeBuffer any2) byteLength :: SomeBuffer any -> GHCJSPure Int getArrayBuffer :: SomeBuffer any -> GHCJSPure (SomeArrayBuffer any) getUint8Array :: SomeBuffer any -> GHCJSPure (SomeUint8Array any) getUint16Array :: SomeBuffer any -> GHCJSPure (SomeUint16Array any) getInt32Array :: SomeBuffer any -> GHCJSPure (SomeInt32Array any) getDataView :: SomeBuffer any -> GHCJSPure (SomeDataView any) getFloat32Array :: SomeBuffer any -> GHCJSPure (SomeFloat32Array any) getFloat64Array :: SomeBuffer any -> GHCJSPure (SomeFloat64Array any) -- | Wrap a Buffer into a ByteString using the given offset -- and length. toByteString :: Int -> Maybe Int -> Buffer -> GHCJSPure ByteString fromByteString :: ByteString -> GHCJSPure (Buffer, Int, Int) module JavaScript.TypedArray.Internal elemSize :: SomeTypedArray e m -> GHCJSPure Int class TypedArray a unsafeIndex :: TypedArray a => Int -> a -> JSM (Elem a) index :: TypedArray a => Int -> a -> JSM (Elem a) unsafeSetIndex :: TypedArray a => Int -> Elem a -> a -> JSM () setIndex :: TypedArray a => Int -> Elem a -> a -> JSM () create :: TypedArray a => Int -> JSM a fromArray :: TypedArray a => SomeJSArray m -> JSM a fromArrayBuffer :: TypedArray a => MutableArrayBuffer -> Int -> Maybe Int -> JSM a indexOf :: TypedArray a => Int -> Elem a -> a -> JSM Int lastIndexOf :: TypedArray a => Int -> Elem a -> a -> JSM Int indexI :: Int -> SomeTypedArray e m -> JSM Int indexI16 :: Int -> SomeTypedArray e m -> JSM Int16 indexI8 :: Int -> SomeTypedArray e m -> JSM Int8 indexW :: Int -> SomeTypedArray e m -> JSM Word indexW16 :: Int -> SomeTypedArray e m -> JSM Word16 indexW8 :: Int -> SomeTypedArray e m -> JSM Word8 indexD :: Int -> SomeTypedArray e m -> JSM Double unsafeIndexI :: Int -> SomeTypedArray e m -> JSM Int unsafeIndexI16 :: Int -> SomeTypedArray e m -> JSM Int16 unsafeIndexI8 :: Int -> SomeTypedArray e m -> JSM Int8 unsafeIndexW :: Int -> SomeTypedArray e m -> JSM Word unsafeIndexW16 :: Int -> SomeTypedArray e m -> JSM Word16 unsafeIndexW8 :: Int -> SomeTypedArray e m -> JSM Word8 unsafeIndexD :: Int -> SomeTypedArray e m -> JSM Double int8ArrayFrom :: SomeJSArray m0 -> JSM (SomeInt8Array m1) int16ArrayFrom :: SomeJSArray m0 -> JSM (SomeInt16Array m1) int32ArrayFrom :: SomeJSArray m0 -> JSM (SomeInt32Array m1) uint8ArrayFrom :: SomeJSArray m0 -> JSM (SomeUint8Array m1) uint8ClampedArrayFrom :: SomeJSArray m0 -> JSM (SomeUint8ClampedArray m1) uint16ArrayFrom :: SomeJSArray m0 -> JSM (SomeUint16Array m1) uint32ArrayFrom :: SomeJSArray m0 -> JSM (SomeUint32Array m1) float32ArrayFrom :: SomeJSArray m0 -> JSM (SomeFloat32Array m1) float64ArrayFrom :: SomeJSArray m0 -> JSM (SomeFloat64Array m1) setIndexI :: Mutability m ~ IsMutable => Int -> Int -> SomeTypedArray e m -> JSM () unsafeSetIndexI :: Mutability m ~ IsMutable => Int -> Int -> SomeTypedArray e m -> JSM () setIndexW :: Mutability m ~ IsMutable => Int -> Word -> SomeTypedArray e m -> JSM () unsafeSetIndexW :: Mutability m ~ IsMutable => Int -> Word -> SomeTypedArray e m -> JSM () setIndexD :: Mutability m ~ IsMutable => Int -> Double -> SomeTypedArray e m -> JSM () unsafeSetIndexD :: Mutability m ~ IsMutable => Int -> Double -> SomeTypedArray e m -> JSM () indexOfI :: Mutability m ~ IsMutable => Int -> Int -> SomeTypedArray e m -> JSM Int indexOfW :: Int -> Word -> SomeTypedArray e m -> JSM Int indexOfD :: Int -> Double -> SomeTypedArray e m -> JSM Int lastIndexOfI :: Int -> Int -> SomeTypedArray e m -> JSM Int lastIndexOfW :: Int -> Word -> SomeTypedArray e m -> JSM Int lastIndexOfD :: Int -> Double -> SomeTypedArray e m -> JSM Int -- | length of the typed array in elements length :: SomeTypedArray e m -> GHCJSPure Int -- | length of the array in bytes byteLength :: SomeTypedArray e m -> GHCJSPure Int -- | offset of the array in the buffer byteOffset :: SomeTypedArray e m -> GHCJSPure Int -- | the underlying buffer of the array buffer :: SomeTypedArray e m -> GHCJSPure (SomeArrayBuffer m) -- | create a view of the existing array subarray :: Int -> Int -> SomeTypedArray e m -> GHCJSPure (SomeTypedArray e m) -- | copy the elements of one typed array to another set :: Int -> SomeTypedArray e m -> SomeTypedArray e1 Mutable -> GHCJSPure () unsafeSet :: Int -> SomeTypedArray e m -> SomeTypedArray e1 Mutable -> GHCJSPure () instance JavaScript.TypedArray.Internal.TypedArray JavaScript.TypedArray.Internal.Types.IOInt8Array instance JavaScript.TypedArray.Internal.TypedArray JavaScript.TypedArray.Internal.Types.IOInt16Array instance JavaScript.TypedArray.Internal.TypedArray JavaScript.TypedArray.Internal.Types.IOInt32Array instance JavaScript.TypedArray.Internal.TypedArray JavaScript.TypedArray.Internal.Types.IOUint8ClampedArray instance JavaScript.TypedArray.Internal.TypedArray JavaScript.TypedArray.Internal.Types.IOUint8Array instance JavaScript.TypedArray.Internal.TypedArray JavaScript.TypedArray.Internal.Types.IOUint16Array instance JavaScript.TypedArray.Internal.TypedArray JavaScript.TypedArray.Internal.Types.IOUint32Array instance JavaScript.TypedArray.Internal.TypedArray JavaScript.TypedArray.Internal.Types.IOFloat32Array instance JavaScript.TypedArray.Internal.TypedArray JavaScript.TypedArray.Internal.Types.IOFloat64Array module JavaScript.TypedArray class TypedArray a unsafeIndex :: TypedArray a => Int -> a -> JSM (Elem a) index :: TypedArray a => Int -> a -> JSM (Elem a) unsafeSetIndex :: TypedArray a => Int -> Elem a -> a -> JSM () setIndex :: TypedArray a => Int -> Elem a -> a -> JSM () create :: TypedArray a => Int -> JSM a fromArray :: TypedArray a => SomeJSArray m -> JSM a fromArrayBuffer :: TypedArray a => MutableArrayBuffer -> Int -> Maybe Int -> JSM a indexOf :: TypedArray a => Int -> Elem a -> a -> JSM Int lastIndexOf :: TypedArray a => Int -> Elem a -> a -> JSM Int type Int8Array = SomeInt8Array Immutable type Int16Array = SomeInt16Array Immutable type Int32Array = SomeInt32Array Immutable type Uint8Array = SomeUint8Array Immutable type Uint16Array = SomeUint16Array Immutable type Uint32Array = SomeUint32Array Immutable type Uint8ClampedArray = SomeUint8ClampedArray Immutable type Float32Array = SomeFloat32Array Immutable type Float64Array = SomeFloat64Array Immutable -- | length of the typed array in elements length :: SomeTypedArray e m -> GHCJSPure Int -- | length of the array in bytes byteLength :: SomeTypedArray e m -> GHCJSPure Int -- | offset of the array in the buffer byteOffset :: SomeTypedArray e m -> GHCJSPure Int -- | the underlying buffer of the array buffer :: SomeTypedArray e m -> GHCJSPure (SomeArrayBuffer m) -- | create a view of the existing array subarray :: Int -> Int -> SomeTypedArray e m -> GHCJSPure (SomeTypedArray e m) -- | copy the elements of one typed array to another set :: Int -> SomeTypedArray e m -> SomeTypedArray e1 Mutable -> GHCJSPure () unsafeSet :: Int -> SomeTypedArray e m -> SomeTypedArray e1 Mutable -> GHCJSPure () module Data.JSString.Internal.Search indices :: JSString -> JSString -> [Int] -- | Warning: this is an internal module, and does not have a stable -- API or name. Functions in this module may not check or enforce -- preconditions expected by public modules. Use at your own risk! -- -- Core stream fusion functionality for text. module Data.JSString.Internal.Fusion.Types -- | Specialised tuple for case conversion. data CC s :: * -> * CC :: ~s -> {-# UNPACK #-} ~Char -> {-# UNPACK #-} ~Char -> CC s -- | Strict pair. data PairS a b :: * -> * -> * (:*:) :: ~a -> ~b -> PairS a b -- | Restreaming state. data RS s :: * -> * RS0 :: ~s -> RS s RS1 :: ~s -> {-# UNPACK #-} ~Word8 -> RS s RS2 :: ~s -> {-# UNPACK #-} ~Word8 -> {-# UNPACK #-} ~Word8 -> RS s RS3 :: ~s -> {-# UNPACK #-} ~Word8 -> {-# UNPACK #-} ~Word8 -> {-# UNPACK #-} ~Word8 -> RS s -- | Intermediate result in a processing pipeline. data Step s a :: * -> * -> * Done :: Step s a Skip :: ~s -> Step s a Yield :: ~a -> ~s -> Step s a data Stream a :: * -> * [Stream] :: Stream a -- | The empty stream. empty :: Stream a module Data.JSString.Internal.Fusion.Common singleton :: Char -> Stream Char streamList :: [a] -> Stream a unstreamList :: Stream a -> [a] -- | Stream the UTF-8-like packed encoding used by GHC to represent -- constant strings in generated code. -- -- This encoding uses the byte sequence "xc0x80" to represent NUL, and -- the string is NUL-terminated. streamCString# :: Addr# -> Stream Char -- | O(n) Adds a character to the front of a Stream Char. cons :: Char -> Stream Char -> Stream Char -- | O(n) Adds a character to the end of a stream. snoc :: Stream Char -> Char -> Stream Char -- | O(n) Appends one Stream to the other. append :: Stream Char -> Stream Char -> Stream Char -- | O(1) Returns the first character of a Text, which must be -- non-empty. Subject to array fusion. head :: Stream Char -> Char -- | O(1) Returns the first character and remainder of a 'Stream -- Char', or Nothing if empty. Subject to array fusion. uncons :: Stream Char -> Maybe (Char, Stream Char) -- | O(n) Returns the last character of a 'Stream Char', which must -- be non-empty. last :: Stream Char -> Char -- | O(1) Returns all characters after the head of a Stream Char, -- which must be non-empty. tail :: Stream Char -> Stream Char -- | O(1) Returns all but the last character of a Stream Char, which -- must be non-empty. init :: Stream Char -> Stream Char -- | O(1) Tests whether a Stream Char is empty or not. null :: Stream Char -> Bool -- | O(n) Returns the number of characters in a string. lengthI :: Integral a => Stream Char -> a -- | O(n) Compares the count of characters in a string to a number. -- Subject to fusion. -- -- This function gives the same answer as comparing against the result of -- lengthI, but can short circuit if the count of characters is -- greater than the number or if the stream can't possibly be as long as -- the number supplied, and hence be more efficient. compareLengthI :: Integral a => Stream Char -> a -> Ordering -- | O(n) Indicate whether a string contains exactly one element. isSingleton :: Stream Char -> Bool -- | O(n) map f xs is the Stream Char obtained by -- applying f to each element of xs. map :: (Char -> Char) -> Stream Char -> Stream Char intercalate :: Stream Char -> [Stream Char] -> Stream Char -- | O(n) Take a character and place it between each of the -- characters of a 'Stream Char'. intersperse :: Char -> Stream Char -> Stream Char -- | O(n) Convert a string to folded case. This function is mainly -- useful for performing caseless (or case insensitive) string -- comparisons. -- -- A string x is a caseless match for a string y if and -- only if: -- --
--   toCaseFold x == toCaseFold y
--   
-- -- The result string may be longer than the input string, and may differ -- from applying toLower to the input string. For instance, the -- Armenian small ligature men now (U+FB13) is case folded to the bigram -- men now (U+0574 U+0576), while the micro sign (U+00B5) is case folded -- to the Greek small letter letter mu (U+03BC) instead of itself. toCaseFold :: Stream Char -> Stream Char -- | O(n) Convert a string to lower case, using simple case -- conversion. The result string may be longer than the input string. For -- instance, the Latin capital letter I with dot above (U+0130) maps to -- the sequence Latin small letter i (U+0069) followed by combining dot -- above (U+0307). toLower :: Stream Char -> Stream Char -- | O(n) Convert a string to title case, using simple case -- conversion. -- -- The first letter of the input is converted to title case, as is every -- subsequent letter that immediately follows a non-letter. Every letter -- that immediately follows another letter is converted to lower case. -- -- The result string may be longer than the input string. For example, -- the Latin small ligature fl (U+FB02) is converted to the sequence Latin -- capital letter F (U+0046) followed by Latin small letter l (U+006C). -- -- Note: this function does not take language or culture specific -- rules into account. For instance, in English, different style guides -- disagree on whether the book name "The Hill of the Red Fox" is -- correctly title cased—but this function will capitalize every -- word. toTitle :: Stream Char -> Stream Char -- | O(n) Convert a string to upper case, using simple case -- conversion. The result string may be longer than the input string. For -- instance, the German eszett (U+00DF) maps to the two-letter sequence -- SS. toUpper :: Stream Char -> Stream Char justifyLeftI :: Integral a => a -> Char -> Stream Char -> Stream Char -- | foldl, applied to a binary operator, a starting value (typically the -- left-identity of the operator), and a Stream, reduces the Stream using -- the binary operator, from left to right. foldl :: (b -> Char -> b) -> b -> Stream Char -> b -- | A strict version of foldl. foldl' :: (b -> Char -> b) -> b -> Stream Char -> b -- | foldl1 is a variant of foldl that has no starting value argument, and -- thus must be applied to non-empty Streams. foldl1 :: (Char -> Char -> Char) -> Stream Char -> Char -- | A strict version of foldl1. foldl1' :: (Char -> Char -> Char) -> Stream Char -> Char -- | foldr, applied to a binary operator, a starting value -- (typically the right-identity of the operator), and a stream, reduces -- the stream using the binary operator, from right to left. foldr :: (Char -> b -> b) -> b -> Stream Char -> b -- | foldr1 is a variant of foldr that has no starting value -- argument, and thus must be applied to non-empty streams. Subject to -- array fusion. foldr1 :: (Char -> Char -> Char) -> Stream Char -> Char -- | O(n) Concatenate a list of streams. Subject to array fusion. concat :: [Stream Char] -> Stream Char -- | Map a function over a stream that results in a stream and concatenate -- the results. concatMap :: (Char -> Stream Char) -> Stream Char -> Stream Char -- | O(n) any p xs determines if any character in the -- stream xs satisfies the predicate p. any :: (Char -> Bool) -> Stream Char -> Bool -- | O(n) all p xs determines if all characters in the -- Text xs satisfy the predicate p. all :: (Char -> Bool) -> Stream Char -> Bool -- | O(n) maximum returns the maximum value from a stream, which -- must be non-empty. maximum :: Stream Char -> Char -- | O(n) minimum returns the minimum value from a Text, -- which must be non-empty. minimum :: Stream Char -> Char scanl :: (Char -> Char -> Char) -> Char -> Stream Char -> Stream Char replicateCharI :: Integral a => a -> Char -> Stream Char replicateI :: Int64 -> Stream Char -> Stream Char -- | O(n), where n is the length of the result. The unfoldr -- function is analogous to the List unfoldr. unfoldr builds a -- stream from a seed value. The function takes the element and returns -- Nothing if it is done producing the stream or returns Just (a,b), in -- which case, a is the next Char in the string, and b is the seed value -- for further production. unfoldr :: (a -> Maybe (Char, a)) -> a -> Stream Char -- | O(n) Like unfoldr, unfoldrNI builds a stream from -- a seed value. However, the length of the result is limited by the -- first argument to unfoldrNI. This function is more efficient -- than unfoldr when the length of the result is known. unfoldrNI :: Integral a => a -> (b -> Maybe (Char, b)) -> b -> Stream Char -- | O(n) take n, applied to a stream, returns the prefix of the -- stream of length n, or the stream itself if n is -- greater than the length of the stream. take :: Integral a => a -> Stream Char -> Stream Char -- | O(n) drop n, applied to a stream, returns the suffix of the -- stream after the first n characters, or the empty stream if -- n is greater than the length of the stream. drop :: Integral a => a -> Stream Char -> Stream Char -- | takeWhile, applied to a predicate p and a stream, returns the -- longest prefix (possibly empty) of elements that satisfy p. takeWhile :: (Char -> Bool) -> Stream Char -> Stream Char -- | dropWhile p xs returns the suffix remaining after takeWhile -- p xs. dropWhile :: (Char -> Bool) -> Stream Char -> Stream Char -- | O(n) The isPrefixOf function takes two Streams -- and returns True iff the first is a prefix of the second. isPrefixOf :: Eq a => Stream a -> Stream a -> Bool -- | O(n) elem is the stream membership predicate. elem :: Char -> Stream Char -> Bool -- | O(n) filter, applied to a predicate and a stream, -- returns a stream containing those characters that satisfy the -- predicate. filter :: (Char -> Bool) -> Stream Char -> Stream Char -- | O(n) The findBy function takes a predicate and a stream, -- and returns the first element in matching the predicate, or -- Nothing if there is no such element. findBy :: (Char -> Bool) -> Stream Char -> Maybe Char -- | O(n) Stream index (subscript) operator, starting from 0. indexI :: Integral a => Stream Char -> a -> Char -- | The findIndexI function takes a predicate and a stream and -- returns the index of the first element in the stream satisfying the -- predicate. findIndexI :: Integral a => (Char -> Bool) -> Stream Char -> Maybe a -- | O(n) The countCharI function returns the number of times -- the query element appears in the given stream. countCharI :: Integral a => Char -> Stream Char -> a -- | zipWith generalises zip by zipping with the function given as -- the first argument, instead of a tupling function. zipWith :: (a -> a -> b) -> Stream a -> Stream a -> Stream b module Data.JSString.Internal.Fusion.CaseMapping upperMapping :: forall s. Char -> s -> Step (CC s) Char lowerMapping :: forall s. Char -> s -> Step (CC s) Char titleMapping :: forall s. Char -> s -> Step (CC s) Char foldMapping :: forall s. Char -> s -> Step (CC s) Char module Data.JSString.Internal.Fusion data Stream a :: * -> * [Stream] :: Stream a -- | Intermediate result in a processing pipeline. data Step s a :: * -> * -> * Done :: Step s a Skip :: ~s -> Step s a Yield :: ~a -> ~s -> Step s a -- | O(n) Convert a JSString into a 'Stream Char'. stream :: JSString -> Stream Char -- | O(n) Convert a 'Stream Char' into a JSString. unstream :: Stream Char -> JSString -- | O(n) Convert a JSString into a 'Stream Char', but -- iterate backwards. reverseStream :: JSString -> Stream Char length :: Stream Char -> Int -- | O(n) Reverse the characters of a string. reverse :: Stream Char -> JSString -- | O(n) Perform the equivalent of scanr over a list, only -- with the input and result reversed. reverseScanr :: (Char -> Char -> Char) -> Char -> Stream Char -> Stream Char -- | O(n) Like a combination of map and foldl'. -- Applies a function to each element of a Text, passing an -- accumulating parameter from left to right, and returns a final -- JSString. mapAccumL :: (a -> Char -> (a, Char)) -> a -> Stream Char -> (a, JSString) -- | O(n) Like unfoldr, unfoldrN builds a stream -- from a seed value. However, the length of the result is limited by the -- first argument to unfoldrN. This function is more efficient -- than unfoldr when the length of the result is known. unfoldrN :: Int -> (a -> Maybe (Char, a)) -> a -> Stream Char -- | O(n) stream index (subscript) operator, starting from 0. index :: Stream Char -> Int -> Char -- | The findIndex function takes a predicate and a stream and -- returns the index of the first element in the stream satisfying the -- predicate. findIndex :: (Char -> Bool) -> Stream Char -> Maybe Int -- | O(n) The count function returns the number of times -- the query element appears in the given stream. countChar :: Char -> Stream Char -> Int module Data.JSString.Internal -- | Manipulation of JavaScript strings, API and fusion implementation -- based on Data.Text by Tom Harper, Duncan Coutts, Bryan O'Sullivan e.a. module Data.JSString -- | A wrapper around a JavaScript string data JSString -- | O(n) Convert a String into a JSString. Subject to -- fusion. pack :: String -> JSString -- | O(n) Convert a JSString into a String. Subject to -- fusion. unpack :: JSString -> String unpack' :: JSString -> String -- | O(1) Convert a character into a JSString. Subject to -- fusion. Performs replacement on invalid scalar values. singleton :: Char -> JSString -- | O(1) The empty JSString. empty :: JSString -- | O(n) Adds a character to the front of a JSString. This -- function is more costly than its List counterpart because it -- requires copying a new array. Subject to fusion. Performs replacement -- on invalid scalar values. cons :: Char -> JSString -> JSString infixr 5 `cons` -- | O(n) Adds a character to the end of a JSString. This -- copies the entire array in the process, unless fused. Subject to -- fusion. Performs replacement on invalid scalar values. snoc :: JSString -> Char -> JSString -- | O(n) Appends one JSString to the other by copying both -- of them into a new JSString. Subject to fusion. append :: JSString -> JSString -> JSString -- | O(1) Returns the first character and rest of a JSString, -- or Nothing if empty. Subject to fusion. uncons :: JSString -> Maybe (Char, JSString) -- | O(1) Returns the first character of a JSString, which -- must be non-empty. Subject to fusion. head :: JSString -> Char -- | O(1) Returns the last character of a JSString, which -- must be non-empty. Subject to fusion. last :: JSString -> Char -- | O(1) Returns all characters after the head of a -- JSString, which must be non-empty. Subject to fusion. tail :: JSString -> JSString -- | O(1) Returns all but the last character of a JSString, -- which must be non-empty. Subject to fusion. init :: JSString -> JSString -- | O(1) Tests whether a JSString is empty or not. Subject -- to fusion. null :: JSString -> Bool -- | O(n) Returns the number of characters in a JSString. -- Subject to fusion. length :: JSString -> Int -- | O(n) Compare the count of characters in a JSString to a -- number. Subject to fusion. -- -- This function gives the same answer as comparing against the result of -- length, but can short circuit if the count of characters is -- greater than the number, and hence be more efficient. compareLength :: JSString -> Int -> Ordering -- | O(n) map f t is the JSString -- obtained by applying f to each element of t. Subject -- to fusion. Performs replacement on invalid scalar values. map :: (Char -> Char) -> JSString -> JSString -- | O(n) The intercalate function takes a JSString -- and a list of JSStrings and concatenates the list after -- interspersing the first argument between each element of the list. intercalate :: JSString -> [JSString] -> JSString -- | O(n) The intersperse function takes a character and -- places it between the characters of a JSString. Subject to -- fusion. Performs replacement on invalid scalar values. intersperse :: Char -> JSString -> JSString -- | O(n) The transpose function transposes the rows and -- columns of its JSString argument. Note that this function uses -- pack, unpack, and the list version of transpose, and is -- thus not very efficient. transpose :: [JSString] -> [JSString] -- | O(n) Reverse the characters of a string. Subject to fusion. reverse :: JSString -> JSString -- | O(m+n) Replace every non-overlapping occurrence of -- needle in haystack with replacement. -- -- This function behaves as though it was defined as follows: -- --
--   replace needle replacement haystack =
--     intercalate replacement (splitOn needle haystack)
--   
-- -- As this suggests, each occurrence is replaced exactly once. So if -- needle occurs in replacement, that occurrence will -- not itself be replaced recursively: -- --
--   replace "oo" "foo" "oo" == "foo"
--   
-- -- In cases where several instances of needle overlap, only the -- first one will be replaced: -- --
--   replace "ofo" "bar" "ofofo" == "barfo"
--   
-- -- In (unlikely) bad cases, this function's time complexity degrades -- towards O(n*m). replace :: JSString -> JSString -> JSString -> JSString -- | O(n) Convert a string to folded case. Subject to fusion. -- -- This function is mainly useful for performing caseless (also known as -- case insensitive) string comparisons. -- -- A string x is a caseless match for a string y if and -- only if: -- --
--   toCaseFold x == toCaseFold y
--   
-- -- The result string may be longer than the input string, and may differ -- from applying toLower to the input string. For instance, the -- Armenian small ligature "ﬓ" (men now, U+FB13) is case folded to the -- sequence "մ" (men, U+0574) followed by "ն" (now, U+0576), while the -- Greek "µ" (micro sign, U+00B5) is case folded to "μ" (small letter mu, -- U+03BC) instead of itself. toCaseFold :: JSString -> JSString -- | O(n) Convert a string to lower case, using simple case -- conversion. Subject to fusion. -- -- The result string may be longer than the input string. For instance, -- "İ" (Latin capital letter I with dot above, U+0130) maps to the -- sequence "i" (Latin small letter i, U+0069) followed by " ̇" -- (combining dot above, U+0307). toLower :: JSString -> JSString -- | O(n) Convert a string to upper case, using simple case -- conversion. Subject to fusion. -- -- The result string may be longer than the input string. For instance, -- the German "ß" (eszett, U+00DF) maps to the two-letter sequence "SS". toUpper :: JSString -> JSString -- | O(n) Convert a string to title case, using simple case -- conversion. Subject to fusion. -- -- The first letter of the input is converted to title case, as is every -- subsequent letter that immediately follows a non-letter. Every letter -- that immediately follows another letter is converted to lower case. -- -- The result string may be longer than the input string. For example, -- the Latin small ligature fl (U+FB02) is converted to the sequence Latin -- capital letter F (U+0046) followed by Latin small letter l (U+006C). -- -- Note: this function does not take language or culture specific -- rules into account. For instance, in English, different style guides -- disagree on whether the book name "The Hill of the Red Fox" is -- correctly title cased—but this function will capitalize every -- word. toTitle :: JSString -> JSString -- | O(n) Left-justify a string to the given length, using the -- specified fill character on the right. Subject to fusion. Performs -- replacement on invalid scalar values. -- -- Examples: -- --
--   justifyLeft 7 'x' "foo"    == "fooxxxx"
--   justifyLeft 3 'x' "foobar" == "foobar"
--   
justifyLeft :: Int -> Char -> JSString -> JSString -- | O(n) Right-justify a string to the given length, using the -- specified fill character on the left. Performs replacement on invalid -- scalar values. -- -- Examples: -- --
--   justifyRight 7 'x' "bar"    == "xxxxbar"
--   justifyRight 3 'x' "foobar" == "foobar"
--   
justifyRight :: Int -> Char -> JSString -> JSString -- | O(n) Center a string to the given length, using the specified -- fill character on either side. Performs replacement on invalid scalar -- values. -- -- Examples: -- --
--   center 8 'x' "HS" = "xxxHSxxx"
--   
center :: Int -> Char -> JSString -> JSString -- | O(n) foldl, applied to a binary operator, a starting -- value (typically the left-identity of the operator), and a -- JSString, reduces the JSString using the binary -- operator, from left to right. Subject to fusion. foldl :: (a -> Char -> a) -> a -> JSString -> a -- | O(n) A strict version of foldl. Subject to fusion. foldl' :: (a -> Char -> a) -> a -> JSString -> a -- | O(n) A variant of foldl that has no starting value -- argument, and thus must be applied to a non-empty JSString. -- Subject to fusion. foldl1 :: (Char -> Char -> Char) -> JSString -> Char -- | O(n) A strict version of foldl1. Subject to fusion. foldl1' :: (Char -> Char -> Char) -> JSString -> Char -- | O(n) foldr, applied to a binary operator, a starting -- value (typically the right-identity of the operator), and a -- JSString, reduces the JSString using the binary -- operator, from right to left. Subject to fusion. foldr :: (Char -> a -> a) -> a -> JSString -> a -- | O(n) A variant of foldr that has no starting value -- argument, and thus must be applied to a non-empty JSString. -- Subject to fusion. foldr1 :: (Char -> Char -> Char) -> JSString -> Char -- | O(n) Concatenate a list of JSStrings. concat :: [JSString] -> JSString -- | O(n) Map a function over a JSString that results in a -- JSString, and concatenate the results. concatMap :: (Char -> JSString) -> JSString -> JSString -- | O(n) any p t determines whether any -- character in the JSString t satisifes the predicate -- p. Subject to fusion. any :: (Char -> Bool) -> JSString -> Bool -- | O(n) all p t determines whether all -- characters in the JSString t satisify the predicate -- p. Subject to fusion. all :: (Char -> Bool) -> JSString -> Bool -- | O(n) maximum returns the maximum value from a -- JSString, which must be non-empty. Subject to fusion. maximum :: JSString -> Char -- | O(n) minimum returns the minimum value from a -- JSString, which must be non-empty. Subject to fusion. minimum :: JSString -> Char -- | O(n) scanl is similar to foldl, but returns a -- list of successive reduced values from the left. Subject to fusion. -- Performs replacement on invalid scalar values. -- --
--   scanl f z [x1, x2, ...] == [z, z `f` x1, (z `f` x1) `f` x2, ...]
--   
-- -- Note that -- --
--   last (scanl f z xs) == foldl f z xs.
--   
scanl :: (Char -> Char -> Char) -> Char -> JSString -> JSString -- | O(n) scanl1 is a variant of scanl that has no -- starting value argument. Subject to fusion. Performs replacement on -- invalid scalar values. -- --
--   scanl1 f [x1, x2, ...] == [x1, x1 `f` x2, ...]
--   
scanl1 :: (Char -> Char -> Char) -> JSString -> JSString -- | O(n) scanr is the right-to-left dual of scanl. -- Performs replacement on invalid scalar values. -- --
--   scanr f v == reverse . scanl (flip f) v . reverse
--   
scanr :: (Char -> Char -> Char) -> Char -> JSString -> JSString -- | O(n) scanr1 is a variant of scanr that has no -- starting value argument. Subject to fusion. Performs replacement on -- invalid scalar values. scanr1 :: (Char -> Char -> Char) -> JSString -> JSString -- | O(n) Like a combination of map and foldl'. -- Applies a function to each element of a JSString, passing an -- accumulating parameter from left to right, and returns a final -- JSString. Performs replacement on invalid scalar values. mapAccumL :: (a -> Char -> (a, Char)) -> a -> JSString -> (a, JSString) -- | The mapAccumR function behaves like a combination of map -- and a strict foldr; it applies a function to each element of a -- JSString, passing an accumulating parameter from right to left, -- and returning a final value of this accumulator together with the new -- JSString. Performs replacement on invalid scalar values. mapAccumR :: (a -> Char -> (a, Char)) -> a -> JSString -> (a, JSString) -- | O(n*m) replicate n t is a -- JSString consisting of the input t repeated n -- times. replicate :: Int -> JSString -> JSString -- | O(n), where n is the length of the result. The -- unfoldr function is analogous to the List unfoldr. -- unfoldr builds a JSString from a seed value. The -- function takes the element and returns Nothing if it is done -- producing the JSString, otherwise Just (a,b). -- In this case, a is the next Char in the string, and -- b is the seed value for further production. Subject to -- fusion. Performs replacement on invalid scalar values. unfoldr :: (a -> Maybe (Char, a)) -> a -> JSString -- | O(n) Like unfoldr, unfoldrN builds a -- JSString from a seed value. However, the length of the result -- should be limited by the first argument to unfoldrN. This -- function is more efficient than unfoldr when the maximum length -- of the result is known and correct, otherwise its performance is -- similar to unfoldr. Subject to fusion. Performs replacement on -- invalid scalar values. unfoldrN :: Int -> (a -> Maybe (Char, a)) -> a -> JSString -- | O(n) take n, applied to a JSString, -- returns the prefix of the JSString of length n, or the -- JSString itself if n is greater than the length of the -- JSString. Subject to fusion. take :: Int -> JSString -> JSString -- | O(n) takeEnd n t returns the suffix -- remaining after taking n characters from the end of -- t. -- -- Examples: -- --
--   takeEnd 3 "foobar" == "bar"
--   
takeEnd :: Int -> JSString -> JSString -- | O(n) drop n, applied to a JSString, -- returns the suffix of the JSString after the first n -- characters, or the empty JSString if n is greater than -- the length of the JSString. Subject to fusion. drop :: Int -> JSString -> JSString -- | O(n) dropEnd n t returns the prefix -- remaining after dropping n characters from the end of -- t. -- -- Examples: -- --
--   dropEnd 3 "foobar" == "foo"
--   
dropEnd :: Int -> JSString -> JSString -- | O(n) takeWhile, applied to a predicate p and a -- JSString, returns the longest prefix (possibly empty) of -- elements that satisfy p. Subject to fusion. takeWhile :: (Char -> Bool) -> JSString -> JSString -- | O(n) dropWhile p t returns the suffix -- remaining after takeWhile p t. Subject to -- fusion. dropWhile :: (Char -> Bool) -> JSString -> JSString -- | O(n) dropWhileEnd p t returns the -- prefix remaining after dropping characters that fail the predicate -- p from the end of t. Subject to fusion. Examples: -- --
--   dropWhileEnd (=='.') "foo..." == "foo"
--   
dropWhileEnd :: (Char -> Bool) -> JSString -> JSString -- | O(n) dropAround p t returns the -- substring remaining after dropping characters that fail the predicate -- p from both the beginning and end of t. Subject to -- fusion. dropAround :: (Char -> Bool) -> JSString -> JSString -- | O(n) Remove leading and trailing white space from a string. -- Equivalent to: -- --
--   dropAround isSpace
--   
strip :: JSString -> JSString -- | O(n) Remove leading white space from a string. Equivalent to: -- --
--   dropWhile isSpace
--   
stripStart :: JSString -> JSString -- | O(n) Remove trailing white space from a string. Equivalent to: -- --
--   dropWhileEnd isSpace
--   
stripEnd :: JSString -> JSString -- | O(n) splitAt n t returns a pair whose first -- element is a prefix of t of length n, and whose -- second is the remainder of the string. It is equivalent to -- (take n t, drop n t). splitAt :: Int -> JSString -> (JSString, JSString) -- | O(n+m) Find the first instance of needle (which must -- be non-null) in haystack. The first element of the -- returned tuple is the prefix of haystack before -- needle is matched. The second is the remainder of -- haystack, starting with the match. -- -- Examples: -- --
--   breakOn "::" "a::b::c" ==> ("a", "::b::c")
--   breakOn "/" "foobar"   ==> ("foobar", "")
--   
-- -- Laws: -- --
--   append prefix match == haystack
--     where (prefix, match) = breakOn needle haystack
--   
-- -- If you need to break a string by a substring repeatedly (e.g. you want -- to break on every instance of a substring), use breakOnAll -- instead, as it has lower startup overhead. -- -- In (unlikely) bad cases, this function's time complexity degrades -- towards O(n*m). breakOn :: JSString -> JSString -> (JSString, JSString) -- | O(n+m) Similar to breakOn, but searches from the end of -- the string. -- -- The first element of the returned tuple is the prefix of -- haystack up to and including the last match of -- needle. The second is the remainder of haystack, -- following the match. -- --
--   breakOnEnd "::" "a::b::c" ==> ("a::b::", "c")
--   
breakOnEnd :: JSString -> JSString -> (JSString, JSString) -- | O(n) break is like span, but the prefix returned -- is over elements that fail the predicate p. break :: (Char -> Bool) -> JSString -> (JSString, JSString) -- | O(n) span, applied to a predicate p and text -- t, returns a pair whose first element is the longest prefix -- (possibly empty) of t of elements that satisfy p, -- and whose second is the remainder of the list. span :: (Char -> Bool) -> JSString -> (JSString, JSString) -- | O(n) Group characters in a string by equality. group :: JSString -> [JSString] group' :: JSString -> [JSString] -- | O(n) Group characters in a string according to a predicate. groupBy :: (Char -> Char -> Bool) -> JSString -> [JSString] -- | O(n^2) Return all initial segments of the given -- JSString, shortest first. inits :: JSString -> [JSString] -- | O(n^2) Return all final segments of the given JSString, -- longest first. tails :: JSString -> [JSString] -- | O(m+n) Break a JSString into pieces separated by the -- first JSString argument (which cannot be empty), consuming the -- delimiter. An empty delimiter is invalid, and will cause an error to -- be raised. -- -- Examples: -- --
--   splitOn "\r\n" "a\r\nb\r\nd\r\ne" == ["a","b","d","e"]
--   splitOn "aaa"  "aaaXaaaXaaaXaaa"  == ["","X","X","X",""]
--   splitOn "x"    "x"                == ["",""]
--   
-- -- and -- --
--   intercalate s . splitOn s         == id
--   splitOn (singleton c)             == split (==c)
--   
-- -- (Note: the string s to split on above cannot be empty.) -- -- In (unlikely) bad cases, this function's time complexity degrades -- towards O(n*m). splitOn :: JSString -> JSString -> [JSString] splitOn' :: JSString -> JSString -> [JSString] -- | O(n) Splits a JSString into components delimited by -- separators, where the predicate returns True for a separator element. -- The resulting components do not contain the separators. Two adjacent -- separators result in an empty component in the output. eg. -- --
--   split (=='a') "aabbaca" == ["","","bb","c",""]
--   split (=='a') ""        == [""]
--   
split :: (Char -> Bool) -> JSString -> [JSString] -- | O(n) Splits a JSString into components of length -- k. The last element may be shorter than the other chunks, -- depending on the length of the input. Examples: -- --
--   chunksOf 3 "foobarbaz"   == ["foo","bar","baz"]
--   chunksOf 4 "haskell.org" == ["hask","ell.","org"]
--   
chunksOf :: Int -> JSString -> [JSString] -- | O(n) Splits a JSString into components of length -- k. The last element may be shorter than the other chunks, -- depending on the length of the input. Examples: -- --
--   chunksOf 3 "foobarbaz"   == ["foo","bar","baz"]
--   chunksOf 4 "haskell.org" == ["hask","ell.","org"]
--   
chunksOf' :: Int -> JSString -> [JSString] -- | O(n) Breaks a JSString up into a list of -- JSStrings at newline Chars. The resulting strings do not -- contain newlines. lines :: JSString -> [JSString] lines' :: JSString -> [JSString] -- | O(n) Breaks a JSString up into a list of words, -- delimited by Chars representing white space. words :: JSString -> [JSString] words' :: JSString -> [JSString] -- | O(n) Joins lines, after appending a terminating newline to -- each. unlines :: [JSString] -> JSString -- | O(n) Joins words using single space characters. unwords :: [JSString] -> JSString -- | O(n) The isPrefixOf function takes two JSStrings -- and returns True iff the first is a prefix of the second. -- Subject to fusion. isPrefixOf :: JSString -> JSString -> Bool -- | O(n) The isSuffixOf function takes two JSStrings -- and returns True iff the first is a suffix of the second. isSuffixOf :: JSString -> JSString -> Bool -- | The isInfixOf function takes two JSStrings and returns -- True iff the first is contained, wholly and intact, anywhere -- within the second. -- -- Complexity depends on how the JavaScript engine implements -- String.prototype.find. isInfixOf :: JSString -> JSString -> Bool -- | O(n) Return the suffix of the second string if its prefix -- matches the entire first string. -- -- Examples: -- --
--   stripPrefix "foo" "foobar" == Just "bar"
--   stripPrefix ""    "baz"    == Just "baz"
--   stripPrefix "foo" "quux"   == Nothing
--   
-- -- This is particularly useful with the ViewPatterns extension -- to GHC, as follows: -- --
--   {-# LANGUAGE ViewPatterns #-}
--   import Data.Text as T
--   
--   fnordLength :: JSString -> Int
--   fnordLength (stripPrefix "fnord" -> Just suf) = T.length suf
--   fnordLength _                                 = -1
--   
stripPrefix :: JSString -> JSString -> Maybe JSString -- | O(n) Return the prefix of the second string if its suffix -- matches the entire first string. -- -- Examples: -- --
--   stripSuffix "bar" "foobar" == Just "foo"
--   stripSuffix ""    "baz"    == Just "baz"
--   stripSuffix "foo" "quux"   == Nothing
--   
-- -- This is particularly useful with the ViewPatterns extension -- to GHC, as follows: -- --
--   {-# LANGUAGE ViewPatterns #-}
--   import Data.Text as T
--   
--   quuxLength :: Text -> Int
--   quuxLength (stripSuffix "quux" -> Just pre) = T.length pre
--   quuxLength _                                = -1
--   
stripSuffix :: JSString -> JSString -> Maybe JSString -- | O(n) Find the longest non-empty common prefix of two strings -- and return it, along with the suffixes of each string at which they no -- longer match. -- -- If the strings do not have a common prefix or either one is empty, -- this function returns Nothing. -- -- Examples: -- --
--   commonPrefixes "foobar" "fooquux" == Just ("foo","bar","quux")
--   commonPrefixes "veeble" "fetzer"  == Nothing
--   commonPrefixes "" "baz"           == Nothing
--   
commonPrefixes :: JSString -> JSString -> Maybe (JSString, JSString, JSString) -- | O(n) filter, applied to a predicate and a -- JSString, returns a JSString containing those characters -- that satisfy the predicate. filter :: (Char -> Bool) -> JSString -> JSString -- | O(n+m) Find all non-overlapping instances of needle in -- haystack. Each element of the returned list consists of a -- pair: -- -- -- -- Examples: -- --
--   breakOnAll "::" ""
--   ==> []
--   breakOnAll "/" "a/b/c/"
--   ==> [("a", "/b/c/"), ("a/b", "/c/"), ("a/b/c", "/")]
--   
-- -- In (unlikely) bad cases, this function's time complexity degrades -- towards O(n*m). -- -- The needle parameter may not be empty. breakOnAll :: JSString -> JSString -> [(JSString, JSString)] breakOnAll' :: JSString -> JSString -> [(JSString, JSString)] -- | O(n) The find function takes a predicate and a -- JSString, and returns the first element matching the predicate, -- or Nothing if there is no such element. find :: (Char -> Bool) -> JSString -> Maybe Char -- | O(n) The partition function takes a predicate and a -- JSString, and returns the pair of JSStrings with -- elements which do and do not satisfy the predicate, respectively; i.e. -- --
--   partition p t == (filter p t, filter (not . p) t)
--   
partition :: (Char -> Bool) -> JSString -> (JSString, JSString) -- | O(n) JSString index (subscript) operator, starting from -- 0. index :: JSString -> Int -> Char -- | O(n) The findIndex function takes a predicate and a -- JSString and returns the index of the first element in the -- JSString satisfying the predicate. Subject to fusion. findIndex :: (Char -> Bool) -> JSString -> Maybe Int -- | O(n+m) The count function returns the number of times -- the query string appears in the given JSString. An empty query -- string is invalid, and will cause an error to be raised. -- -- In (unlikely) bad cases, this function's time complexity degrades -- towards O(n*m). count :: JSString -> JSString -> Int -- | O(n) zip takes two JSStrings and returns a list -- of corresponding pairs of bytes. If one input JSString is -- short, excess elements of the longer JSString are discarded. -- This is equivalent to a pair of unpack operations. zip :: JSString -> JSString -> [(Char, Char)] -- | O(n) zipWith generalises zip by zipping with the -- function given as the first argument, instead of a tupling function. -- Performs replacement on invalid scalar values. zipWith :: (Char -> Char -> Char) -> JSString -> JSString -> JSString instance GHC.Exts.IsList Data.JSString.Internal.Type.JSString