react-flux-1.2.3: A binding to React based on the Flux application architecture for GHCJS

Safe HaskellNone
LanguageHaskell2010

React.Flux.Ajax

Description

Make calls to the backend from within your stores. This module is low-level in that it mostly directly exposes the XMLHttpRequest access. If you are using servant, react-flux-servant for a higher-level interface.

Synopsis

Documentation

initAjax :: IO () Source #

If you are going to use ajax or jsonAjax, you must call initAjax once from your main function. The call should appear before the call to reactRender.

data RequestTimeout Source #

An optional timeout to use for XMLHttpRequest.timeout. When a request times out, a status code of 504 is set in respStatus and the response handler executes.

jsonAjax Source #

Arguments

:: (ToJSON body, FromJSON response) 
=> RequestTimeout 
-> Text

the method

-> Text

the URI

-> [(Text, Text)]

the headers. In addition to these headers, jsonAjax adds two headers: Content-Type: application/json and Accept: application/json.

-> body

the body

-> (Either (Int, Text) response -> IO [SomeStoreAction])

Once XMLHttpRequest changes the readyState to done this handler will be executed and the resulting actions dispatched to the stores.

  • If the response status is 200, the body will be parsed as JSON and a Right value will be passed to this handler. If there is an error parsing the JSON response, a Left value with 500 and the error message from aeson is given to the handler.
  • If the response status is anything besides 200, a Left value with a pair of the response status and response text is passed to the handler.
-> IO () 

Use XMLHttpRequest to send a request with a JSON body, parse the response body as JSON, and then dispatch some actions with the response. This should be used from within the transform function of your store. For example,

data Target = AlienShip | AlienPlanet
  deriving (Show, Typeable, Generic, ToJSON, FromJSON)

data Trajectory = Trajectory
    { x :: Double, y :: Double, z :: Double, vx :: Double, vy :: Double, vz :: Double }
  deriving (Show, Typeable, Generic, ToJSON, FromJSON)

data UpdatePending = NoUpdatePending | UpdatePending Text | PreviousUpdateHadError Text

data MyStore = MyStore { currentTrajectory :: Maybe Trajectory, launchUpdate :: UpdatePending }

data MyStoreAction = LaunchTheMissiles Target
                   | MissilesLaunched Trajectory
                   | UnableToLaunchMissiles Text
  deriving (Typeable, Generic, NFData)

instance StoreData MyStore where
    type StoreAction MyStore = MyStoreAction

    transform (LaunchTheMissiles t) s = do
        jsonAjax NoTimeout "PUT" "/launch-the-missiles" [] t $ \case
            Left (_, msg) -> return [SomeStoreAction myStore $ UnableToLaunchMissiles msg]
            Right traj -> return [SomeStoreAction myStore $ MissilesLaunched traj]
        return s { launchUpdate = UpdatePending ("Requesting missle launch against " ++ T.pack (show t)) }

    transform (MissilesLaunched traj) s =
        return s { currentTrajectory = Just traj, launchUpdate = NoUpdatePending }

    transform (UnableToLaunchMissiles err) s =
        return s { launchUpdate = PreviousUpdateHadError err }

myStore :: ReactStore MyStore
myStore = mkStore $ MyStore Nothing NoUpdatePending

And then in your view, you can render this using something like:

myView :: ReactView ()
myView = defineControllerView "launch the missles" myStore $ \s () -> do
    case launchUpdate s of
        NoUpdatePending -> return ()
        UpdatePending msg -> span_ $ faIcon_ "rocket" <> elemText msg
        PreviousUpdateHadErroer err -> span_ $ faIcon_ "exclamation" <> elemText err
    clbutton_ ["pure-button button-success"] ([SomeStoreAction myStore $ LaunchTheMissiles AlienShip]) $ do
        faIcon_ "rocket"
        "Launch the missles against the alien ship!"
    p_ $ elemString $ "Current trajectory " ++ show (currentTrajectory s)

data AjaxRequest Source #

The input to an AJAX request built using XMLHttpRequest.

Instances

data AjaxResponse Source #

The response after XMLHttpRequest indicates that the readyState is done.

Constructors

AjaxResponse 

Fields

ajax :: AjaxRequest -> (AjaxResponse -> IO [SomeStoreAction]) -> IO () Source #

Use XMLHttpRequest to send a request to the backend. Once the response arrives and the readyState is done, the response will be passed to the given handler and the resulting actions will be executed. Note that ajax returns immedietly and does not wait for the request to finish.