module Web.Lightning.Types.Lightning
(
Lightning
, LightningF(..)
, LightningT(..)
, ValidatablePlot(..)
, runRoute
, sendPlot
, streamPlot
, sendJSON
, receiveRoute
, withBaseURL
, failWith
, liftLightningF
)
where
import Control.Monad.IO.Class
import Control.Monad.Reader
import Control.Monad.Trans.Free
import Data.Aeson
import qualified Data.Text as T
import Network.API.Builder hiding (runRoute)
import Web.Lightning.Routes (stream)
import Web.Lightning.Types.Error
import Web.Lightning.Types.Visualization
import Web.Lightning.Utilities
class ValidatablePlot a where
validatePlot :: a -> Either LightningError a
type Lightning a = LightningT IO a
type BaseUrl = T.Text
data LightningF m a where
FailWith :: APIError LightningError -> LightningF m a
ReceiveRoute :: Receivable b => Route -> (b -> a) -> LightningF m a
RunRoute :: FromJSON b => Route -> (b -> a) -> LightningF m a
SendJSON :: (Receivable b) => Value -> Route -> (b -> a) -> LightningF m a
WithBaseURL :: T.Text -> LightningT m b -> (b -> a) -> LightningF m a
instance Functor (LightningF m) where
fmap _ (FailWith x) = FailWith x
fmap f (ReceiveRoute r x) = ReceiveRoute r (fmap f x)
fmap f (RunRoute r x) = RunRoute r (fmap f x)
fmap f (SendJSON js r x) = SendJSON js r (fmap f x)
fmap f (WithBaseURL u a x) = WithBaseURL u a (fmap f x)
newtype LightningT m a = LightningT (ReaderT BaseUrl (FreeT (LightningF m) m) a)
deriving (Functor, Applicative, Monad, MonadReader T.Text)
instance MonadIO m => MonadIO (LightningT m) where
liftIO = LightningT . liftIO
instance MonadTrans LightningT where
lift = LightningT . lift . lift
liftLightningF :: (Monad m) => FreeT (LightningF m) m a
-> ReaderT T.Text (FreeT (LightningF m) m) a
liftLightningF = lift
runRoute :: (FromJSON a, Monad m) => Route
-> LightningT m a
runRoute r = LightningT $ liftF $ RunRoute r id
sendPlot :: (ToJSON p, ValidatablePlot p, Receivable a, Monad m) => T.Text
-> p
-> Route
-> LightningT m a
sendPlot t p r =
case validatePlot p of
Left err -> failWith (APIError err)
Right p' -> sendJSON (createPayLoad t $ toJSON p') r
streamPlot :: (ToJSON p,
ValidatablePlot p,
Receivable a,
Monad m) => Maybe Visualization
-> T.Text
-> p
-> Route
-> LightningT m a
streamPlot viz t p r =
case validatePlot p of
Left err -> failWith (APIError err)
Right _ -> streamOrCreate viz
where
streamOrCreate (Just viz') = sendJSON (createDataPayLoad $ toJSON p) (stream viz')
streamOrCreate Nothing = sendJSON (createPayLoad t $ toJSON p) r
sendJSON :: (Receivable a, Monad m) => Value
-> Route
-> LightningT m a
sendJSON j r = LightningT $ liftF $ SendJSON j r id
receiveRoute :: (Receivable a, Monad m) => Route
-> LightningT m a
receiveRoute r = LightningT $ liftF $ ReceiveRoute r id
withBaseURL :: Monad m => T.Text
-> LightningT m a
-> LightningT m a
withBaseURL u f = LightningT $ liftF $ WithBaseURL u f id
failWith :: Monad m => APIError LightningError
-> LightningT m a
failWith = LightningT . liftF . FailWith