{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE LambdaCase #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  Miso.FFI.SSE
-- Copyright   :  (C) 2016-2018 David M. Johnson
-- License     :  BSD3-style (see the file LICENSE)
-- Maintainer  :  David M. Johnson <djohnson.m@gmail.com>
-- Stability   :  experimental
-- Portability :  non-portable
----------------------------------------------------------------------------
module Miso.FFI.SSE
  ( EventSource(..)
  , data'
  , new
  , addEventListener
  ) where

import           GHCJS.Types

import           Miso.FFI (JSM)
import qualified Miso.FFI as FFI
import           Miso.String

import qualified Language.Javascript.JSaddle as JSaddle
import           Language.Javascript.JSaddle hiding (new)

newtype EventSource = EventSource JSVal

data' :: JSVal -> JSM JSVal
data' :: JSVal -> JSM JSVal
data' JSVal
v = JSVal
v JSVal -> JSString -> JSM JSVal
forall this name.
(MakeObject this, ToJSString name) =>
this -> name -> JSM JSVal
! (JSString
"data" :: JSString)

new :: MisoString -> JSM EventSource
new :: MisoString -> JSM EventSource
new MisoString
url = JSVal -> EventSource
EventSource (JSVal -> EventSource) -> JSM JSVal -> JSM EventSource
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSM JSVal -> [MisoString] -> JSM JSVal
forall constructor args.
(MakeObject constructor, MakeArgs args) =>
constructor -> args -> JSM JSVal
JSaddle.new (JSString -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg (JSString
"EventSource" :: JSString)) [MisoString
url]

addEventListener :: EventSource -> MisoString -> (JSVal -> JSM ()) -> JSM ()
addEventListener :: EventSource -> MisoString -> (JSVal -> JSM ()) -> JSM ()
addEventListener (EventSource JSVal
s) = JSVal -> MisoString -> (JSVal -> JSM ()) -> JSM ()
FFI.addEventListener JSVal
s