sparrow-0.0.2.0: Unified streaming dependency management for web apps

Safe HaskellNone
LanguageHaskell2010

Web.Dependencies.Sparrow.Types

Contents

Synopsis

Conceptual

Server

data ServerArgs m deltaOut Source #

Constructors

ServerArgs 

Fields

data ServerReturn m f initOut deltaIn deltaOut Source #

Constructors

ServerReturn 

Fields

data ServerContinue m f initOut deltaIn deltaOut Source #

Constructors

ServerContinue 

Fields

type Server m f initIn initOut deltaIn deltaOut = initIn -> m (Maybe (ServerContinue m f initOut deltaIn deltaOut)) Source #

staticServer Source #

Arguments

:: MonadIO m 
=> Alternative f 
=> (initIn -> m (Maybe initOut))

Produce an initOut

-> Server m f initIn initOut JSONVoid JSONVoid 

Client

data ClientReturn m initOut deltaIn Source #

Constructors

ClientReturn 

Fields

data ClientArgs m initIn initOut deltaIn deltaOut Source #

Constructors

ClientArgs 

Fields

type Client m initIn initOut deltaIn deltaOut = (ClientArgs m initIn initOut deltaIn deltaOut -> m (Maybe (ClientReturn m initOut deltaIn))) -> m () Source #

staticClient Source #

Arguments

:: Monad m 
=> ((initIn -> m (Maybe initOut)) -> m ())

Obtain an initOut

-> Client m initIn initOut JSONVoid JSONVoid 

Topic

newtype Topic Source #

Constructors

Topic 

Fields

Instances

Eq Topic Source # 

Methods

(==) :: Topic -> Topic -> Bool #

(/=) :: Topic -> Topic -> Bool #

Ord Topic Source # 

Methods

compare :: Topic -> Topic -> Ordering #

(<) :: Topic -> Topic -> Bool #

(<=) :: Topic -> Topic -> Bool #

(>) :: Topic -> Topic -> Bool #

(>=) :: Topic -> Topic -> Bool #

max :: Topic -> Topic -> Topic #

min :: Topic -> Topic -> Topic #

Show Topic Source # 

Methods

showsPrec :: Int -> Topic -> ShowS #

show :: Topic -> String #

showList :: [Topic] -> ShowS #

Generic Topic Source # 

Associated Types

type Rep Topic :: * -> * #

Methods

from :: Topic -> Rep Topic x #

to :: Rep Topic x -> Topic #

ToJSON Topic Source # 
FromJSON Topic Source # 
NFData Topic Source # 

Methods

rnf :: Topic -> () #

Hashable Topic Source # 

Methods

hashWithSalt :: Int -> Topic -> Int #

hash :: Topic -> Int #

type Rep Topic Source # 
type Rep Topic = D1 * (MetaData "Topic" "Web.Dependencies.Sparrow.Types" "sparrow-0.0.2.0-D7ZuxEzWFiGJDCRXDtTnOR" True) (C1 * (MetaCons "Topic" PrefixI True) (S1 * (MetaSel (Just Symbol "getTopic") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Text])))

Broadcast

type Broadcast m = Topic -> m (Maybe (Value -> Maybe (m ()))) Source #

JSON Encodings

data WithSessionID a Source #

Instances

Eq a => Eq (WithSessionID a) Source # 
Show a => Show (WithSessionID a) Source # 
Generic (WithSessionID a) Source # 

Associated Types

type Rep (WithSessionID a) :: * -> * #

ToJSON a => ToJSON (WithSessionID a) Source # 
FromJSON a => FromJSON (WithSessionID a) Source # 
NFData a => NFData (WithSessionID a) Source # 

Methods

rnf :: WithSessionID a -> () #

type Rep (WithSessionID a) Source # 
type Rep (WithSessionID a) = D1 * (MetaData "WithSessionID" "Web.Dependencies.Sparrow.Types" "sparrow-0.0.2.0-D7ZuxEzWFiGJDCRXDtTnOR" False) (C1 * (MetaCons "WithSessionID" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "withSessionIDSessionID") SourceUnpack SourceStrict DecidedStrict) (Rec0 * SessionID)) (S1 * (MetaSel (Just Symbol "withSessionIDContent") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a))))

data WithTopic a Source #

Constructors

WithTopic 

Instances

Eq a => Eq (WithTopic a) Source # 

Methods

(==) :: WithTopic a -> WithTopic a -> Bool #

(/=) :: WithTopic a -> WithTopic a -> Bool #

Show a => Show (WithTopic a) Source # 
Generic (WithTopic a) Source # 

Associated Types

type Rep (WithTopic a) :: * -> * #

Methods

from :: WithTopic a -> Rep (WithTopic a) x #

to :: Rep (WithTopic a) x -> WithTopic a #

ToJSON a => ToJSON (WithTopic a) Source # 
FromJSON a => FromJSON (WithTopic a) Source # 

Methods

parseJSON :: Value -> Parser (WithTopic a) #

NFData a => NFData (WithTopic a) Source # 

Methods

rnf :: WithTopic a -> () #

type Rep (WithTopic a) Source # 
type Rep (WithTopic a) = D1 * (MetaData "WithTopic" "Web.Dependencies.Sparrow.Types" "sparrow-0.0.2.0-D7ZuxEzWFiGJDCRXDtTnOR" False) (C1 * (MetaCons "WithTopic" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "withTopicTopic") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Topic)) (S1 * (MetaSel (Just Symbol "withTopicContent") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a))))

data InitResponse a Source #

Instances

Eq a => Eq (InitResponse a) Source # 
Show a => Show (InitResponse a) Source # 
Generic (InitResponse a) Source # 

Associated Types

type Rep (InitResponse a) :: * -> * #

Methods

from :: InitResponse a -> Rep (InitResponse a) x #

to :: Rep (InitResponse a) x -> InitResponse a #

ToJSON a => ToJSON (InitResponse a) Source # 
FromJSON a => FromJSON (InitResponse a) Source # 
NFData a => NFData (InitResponse a) Source # 

Methods

rnf :: InitResponse a -> () #

type Rep (InitResponse a) Source # 
type Rep (InitResponse a) = D1 * (MetaData "InitResponse" "Web.Dependencies.Sparrow.Types" "sparrow-0.0.2.0-D7ZuxEzWFiGJDCRXDtTnOR" False) ((:+:) * ((:+:) * (C1 * (MetaCons "InitBadEncoding" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ByteString))) (C1 * (MetaCons "InitDecodingError" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * String)))) ((:+:) * (C1 * (MetaCons "InitRejected" PrefixI False) (U1 *)) (C1 * (MetaCons "InitResponse" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)))))

data WSIncoming a Source #

Constructors

WSUnsubscribe 
WSIncoming a 

Instances

Eq a => Eq (WSIncoming a) Source # 

Methods

(==) :: WSIncoming a -> WSIncoming a -> Bool #

(/=) :: WSIncoming a -> WSIncoming a -> Bool #

Show a => Show (WSIncoming a) Source # 
Generic (WSIncoming a) Source # 

Associated Types

type Rep (WSIncoming a) :: * -> * #

Methods

from :: WSIncoming a -> Rep (WSIncoming a) x #

to :: Rep (WSIncoming a) x -> WSIncoming a #

ToJSON a => ToJSON (WSIncoming a) Source # 
FromJSON a => FromJSON (WSIncoming a) Source # 

Methods

parseJSON :: Value -> Parser (WSIncoming a) #

NFData a => NFData (WSIncoming a) Source # 

Methods

rnf :: WSIncoming a -> () #

type Rep (WSIncoming a) Source # 
type Rep (WSIncoming a) = D1 * (MetaData "WSIncoming" "Web.Dependencies.Sparrow.Types" "sparrow-0.0.2.0-D7ZuxEzWFiGJDCRXDtTnOR" False) ((:+:) * (C1 * (MetaCons "WSUnsubscribe" PrefixI True) (S1 * (MetaSel (Just Symbol "wsUnsubscribeTopic") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Topic))) (C1 * (MetaCons "WSIncoming" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a))))

data WSOutgoing a Source #

Instances

Eq a => Eq (WSOutgoing a) Source # 

Methods

(==) :: WSOutgoing a -> WSOutgoing a -> Bool #

(/=) :: WSOutgoing a -> WSOutgoing a -> Bool #

Show a => Show (WSOutgoing a) Source # 
Generic (WSOutgoing a) Source # 

Associated Types

type Rep (WSOutgoing a) :: * -> * #

Methods

from :: WSOutgoing a -> Rep (WSOutgoing a) x #

to :: Rep (WSOutgoing a) x -> WSOutgoing a #

ToJSON a => ToJSON (WSOutgoing a) Source # 
FromJSON a => FromJSON (WSOutgoing a) Source # 

Methods

parseJSON :: Value -> Parser (WSOutgoing a) #

NFData a => NFData (WSOutgoing a) Source # 

Methods

rnf :: WSOutgoing a -> () #

type Rep (WSOutgoing a) Source #