module Myxine.Direct
(
PageLocation, pagePort, PagePort, pagePath, PagePath
, Update(..), EventList(..), PageEvent(..), Target, tag, attribute
, PageContent, pageBody, pageTitle, pageContentBody, pageContentTitle
, update, events
, JavaScript(..), evaluateJs, JsException(..)
, ProtocolException(..)
, Some(..)
, module Myxine.Event
) where
import Data.Maybe
import Control.Monad
import Data.Monoid
import Data.String
import Data.List (foldl')
import Data.List.NonEmpty (NonEmpty(..))
import Control.Monad.IO.Class
import Control.Exception
import Data.Constraint
import Data.Some.Newtype (Some(..))
import qualified Data.ByteString.Char8
import qualified Data.ByteString.Lazy.Char8 as ByteString
import Data.ByteString.Lazy.Char8 (ByteString)
import Data.Text (Text)
import Data.IORef
import qualified Data.Text as Text
import qualified Data.Text.Encoding as Text
import qualified Data.Aeson as JSON
import qualified Network.HTTP.Req as Req
import qualified Text.URI as URI
import qualified Salve
import Data.Version (showVersion)
import Myxine.Internal.Event
import Myxine.Event
import Myxine.Target
import Paths_myxine_client (version)
data PageContent
= PageContent
{ _pageContentBody :: Text
, _pageContentTitle :: Last Text
} deriving (Eq, Ord, Show)
instance Semigroup PageContent where
PageContent body title <> PageContent body' title' =
PageContent (body <> body') (title <> title')
instance Monoid PageContent where
mempty = PageContent mempty mempty
pageBody :: Text -> PageContent
pageBody body = mempty { _pageContentBody = body }
pageTitle :: Text -> PageContent
pageTitle title = mempty { _pageContentTitle = Last (Just title) }
pageContentBody :: PageContent -> Text
pageContentBody = _pageContentBody
pageContentTitle :: PageContent -> Maybe Text
pageContentTitle = getLast . _pageContentTitle
data Update
= Dynamic
PageContent
| Static
ByteString
ByteString
deriving (Eq, Ord, Show)
host :: Text
host = "localhost"
pageUrl :: PagePath -> Req.Url 'Req.Http
pageUrl (PagePath p) =
foldl' (Req./:) (Req.http host) (Text.split ('/' ==) p)
newtype PagePort
= PagePort Int
deriving newtype (Num, Eq, Ord, Show)
newtype PagePath
= PagePath Text
deriving newtype (IsString, Eq, Ord, Show)
data PageLocation
= PageLocation
{ pageLocationPort :: Last PagePort
, pageLocationPath :: Last PagePath
} deriving (Eq, Ord, Show)
pagePath :: PagePath -> PageLocation
pagePath p = mempty { pageLocationPath = Last (Just p) }
pagePort :: PagePort -> PageLocation
pagePort p = mempty { pageLocationPort = Last (Just p) }
defaultPort :: Int
defaultPort = 1123
instance Semigroup PageLocation where
PageLocation port1 path1 <> PageLocation port2 path2 =
PageLocation (port1 <> port2) (path1 <> path2)
instance Monoid PageLocation where
mempty = PageLocation
{ pageLocationPort = mempty
, pageLocationPath = mempty }
data PageEvent where
PageEvent :: { event :: EventType props
, properties :: props
, targets :: [Target]
} -> PageEvent
instance Show PageEvent where
showsPrec d PageEvent{event, properties, targets} =
case eventPropertiesDict event of
Dict -> showParen (d > 10) $
showString "PageEvent {event = " .
showsPrec 0 event .
showString ", properties = " .
showsPrec 0 properties .
showString ", targets = " .
showsPrec 0 targets .
showString "}"
instance JSON.FromJSON PageEvent where
parseJSON = JSON.withObject "PageEvent" \o ->
do eventName <- o JSON..: "event"
Some event <-
flip maybe pure
(fail ("Unrecognized event: " <> Text.unpack eventName))
(decodeSomeEventType eventName)
Dict <- pure (eventPropertiesDict event)
properties <- o JSON..: "properties"
targets <- o JSON..: "targets"
pure (PageEvent{event, properties, targets})
data EventList
= AllEvents
| SomeEvents (NonEmpty (Some EventType))
deriving (Eq, Ord, Show)
update ::
PageLocation
->
Update
->
IO ()
update PageLocation{pageLocationPort = Last maybePort,
pageLocationPath = Last maybePath} updateContent =
wrapCaughtReqException $
do response <- Req.runReq Req.defaultHttpConfig $
Req.req Req.POST url body Req.ignoreResponse options
checkServerVersion response
pure ()
where
url = pageUrl (fromMaybe "" maybePath)
options =
Req.port (maybe defaultPort (\(PagePort p) -> p) maybePort) <>
Req.responseTimeout maxBound <>
updateOptions
body :: Req.ReqBodyLbs
updateOptions :: Req.Option 'Req.Http
(body, updateOptions) = case updateContent of
Dynamic (PageContent{_pageContentTitle = Last maybeTitle,
_pageContentBody = text}) ->
( Req.ReqBodyLbs (ByteString.fromStrict (Text.encodeUtf8 text))
, foldMap ("title" Req.=:) maybeTitle )
Static contentType content ->
( Req.ReqBodyLbs content
, Req.header "Content-Type" (ByteString.toStrict contentType)
<> Req.queryFlag "static" )
data JavaScript
= JsExpression Text
| JsBlock Text
deriving (Eq, Ord, Show)
newtype JsException =
JsException String
deriving newtype (Eq, Ord, Show)
deriving anyclass (Exception)
evaluateJs ::
JSON.FromJSON a =>
PageLocation ->
JavaScript ->
IO a
evaluateJs PageLocation{pageLocationPort = Last maybePort,
pageLocationPath = Last maybePath} js =
wrapCaughtReqException $
do response <- Req.runReq
Req.defaultHttpConfig { Req.httpConfigCheckResponse = \_ _ _ -> Nothing } $
Req.req Req.POST url body Req.lbsResponse options
checkServerVersion response
if Req.responseStatusCode response == 200
then either (throwIO . JsException) pure $
JSON.eitherDecode (Req.responseBody response)
else throwIO (JsException (ByteString.unpack (Req.responseBody response)))
where
url = pageUrl (fromMaybe "" maybePath)
options =
Req.port (maybe defaultPort (\(PagePort p) -> p) maybePort) <>
Req.responseTimeout maxBound <>
exprOption
body :: Req.ReqBodyLbs
exprOption :: Req.Option 'Req.Http
(body, exprOption) = case js of
JsExpression expr ->
(Req.ReqBodyLbs "", "evaluate" Req.=: expr)
JsBlock block ->
(Req.ReqBodyLbs (ByteString.fromStrict (Text.encodeUtf8 block)),
Req.queryFlag "evaluate")
events ::
PageLocation
->
IO (EventList -> IO PageEvent)
events PageLocation{pageLocationPort = Last maybePort,
pageLocationPath = Last maybePath} =
do moment <- newIORef Nothing
pure (\eventList -> wrapCaughtReqException $
Req.runReq Req.defaultHttpConfig (go moment eventList))
where
go :: IORef (Maybe Text) -> EventList -> Req.Req PageEvent
go moment eventList =
do currentMoment <- liftIO (readIORef moment)
(url, options) <-
maybe (liftIO . throwIO . MyxineProtocolException $
"Invalid Content-Location:" <> show currentMoment)
pure
(urlAndOptions currentMoment eventList)
response <- Req.req Req.GET url Req.NoReqBody Req.jsonResponse options
liftIO $ checkServerVersion response
let nextMoment =
Text.decodeUtf8 <$>
Req.responseHeader response "Content-Location"
liftIO $ catch @SomeException
(do writeIORef moment nextMoment
pure (Req.responseBody response))
(\e -> do
writeIORef moment currentMoment
throwIO e)
urlAndOptions ::
Maybe Text ->
EventList ->
Maybe (Req.Url 'Req.Http, Req.Option 'Req.Http)
urlAndOptions maybeMoment eventList =
case maybeMoment of
Nothing ->
pure (pageUrl (fromMaybe "" maybePath), fixedOptions)
Just moment ->
do URI.URI { uriScheme,
uriAuthority,
uriPath,
uriQuery,
uriFragment } <- URI.mkURI moment
let uriScheme' = Just $
maybe (fromJust (URI.mkScheme "http")) id uriScheme
uriAuthority' = Right $
either (const $
URI.Authority { authUserInfo = Nothing
, authHost = fromJust (URI.mkHost host)
, authPort = Nothing })
id
uriAuthority
uri = URI.URI { uriScheme = uriScheme'
, uriAuthority = uriAuthority'
, uriPath
, uriQuery
, uriFragment }
(url, momentOption) <- Req.useHttpURI uri
pure (url, fixedOptions <> momentOption)
where
fixedOptions :: Req.Option 'Req.Http
fixedOptions =
portOption <> eventParams <> Req.queryFlag "next"
<> Req.responseTimeout maxBound
portOption :: Req.Option 'Req.Http
portOption = Req.port (maybe defaultPort (\(PagePort p) -> p) maybePort)
eventParams :: Req.Option 'Req.Http
eventParams = case eventList of
AllEvents -> Req.queryFlag "events"
SomeEvents es -> flip foldMap es
\(Some e) -> "event" Req.=: ByteString.unpack (encodeEventType e)
wrapCaughtReqException :: IO a -> IO a
wrapCaughtReqException action =
catch @Req.HttpException action $
\case
Req.VanillaHttpException e -> throwIO e
Req.JsonHttpException message -> throwIO (MyxineProtocolException message)
data ProtocolException
= MyxineProtocolException String
| MyxineServerVersionClashException Salve.Version
| MyxineUnknownServerException
deriving stock (Eq, Ord)
deriving anyclass (Exception)
supportedServers :: Salve.Constraint
supportedServers = Salve.unsafeParseConstraint ">=0.2.0 <0.3.0"
checkServerVersion :: Req.HttpResponse response => response -> IO ()
checkServerVersion response =
case Data.ByteString.Char8.split '/' <$> Req.responseHeader response "server" of
Nothing -> throwIO MyxineUnknownServerException
Just ["myxine", versionString] ->
case Salve.parseVersion (Data.ByteString.Char8.unpack (versionString <> ".0")) of
Nothing -> throwIO MyxineUnknownServerException
Just serverVersion ->
when (not (Salve.satisfiesConstraint supportedServers serverVersion)) $
throwIO (MyxineServerVersionClashException serverVersion)
_ -> throwIO MyxineUnknownServerException
instance Show ProtocolException where
show MyxineUnknownServerException =
"*** Refusing to connect to a server that doesn't self-identify as a Myxine server.\n"
<> "Ensure that the address and port are correct and try again."
show (MyxineServerVersionClashException serverVersion) =
"*** Myxine client/server version mismatch: myxine-client library " <> showVersion version
<> " is incompatible with myxine server version " <> Salve.renderVersion serverVersion <> ".\n"
<> "Either connect to a server in the compatible range of " <> Salve.renderConstraint supportedServers <> ","
<> " or update this application to use a compatible client library version."
show (MyxineProtocolException details) =
"*** Myxine client panic: Failed to process event!\n"
<> "This likely means there is a bug in the Myxine server or client library.\n"
<> "Please file a bug report at: " <> bugReportURL <> ".\n"
<> "Please include the version of this library (" <> showVersion version <> "), "
<> "and the following error message: \n" <> details
where
bugReportURL :: String
bugReportURL = "https://github.com/kwf/myxine/issues/new"