Shpadoinkle-widgets-0.1.0.0: A collection of common reusable types and components.

Safe HaskellNone
LanguageHaskell2010

Shpadoinkle.Widgets.Types.Remote

Documentation

data Remote e a Source #

Constructors

Success a 
Failure e 
Loading 
NotAsked 
Instances
Monad (Remote e) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Remote

Methods

(>>=) :: Remote e a -> (a -> Remote e b) -> Remote e b #

(>>) :: Remote e a -> Remote e b -> Remote e b #

return :: a -> Remote e a #

fail :: String -> Remote e a #

Functor (Remote e) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Remote

Methods

fmap :: (a -> b) -> Remote e a -> Remote e b #

(<$) :: a -> Remote e b -> Remote e a #

Applicative (Remote e) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Remote

Methods

pure :: a -> Remote e a #

(<*>) :: Remote e (a -> b) -> Remote e a -> Remote e b #

liftA2 :: (a -> b -> c) -> Remote e a -> Remote e b -> Remote e c #

(*>) :: Remote e a -> Remote e b -> Remote e b #

(<*) :: Remote e a -> Remote e b -> Remote e a #

Foldable (Remote e) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Remote

Methods

fold :: Monoid m => Remote e m -> m #

foldMap :: Monoid m => (a -> m) -> Remote e a -> m #

foldr :: (a -> b -> b) -> b -> Remote e a -> b #

foldr' :: (a -> b -> b) -> b -> Remote e a -> b #

foldl :: (b -> a -> b) -> b -> Remote e a -> b #

foldl' :: (b -> a -> b) -> b -> Remote e a -> b #

foldr1 :: (a -> a -> a) -> Remote e a -> a #

foldl1 :: (a -> a -> a) -> Remote e a -> a #

toList :: Remote e a -> [a] #

null :: Remote e a -> Bool #

length :: Remote e a -> Int #

elem :: Eq a => a -> Remote e a -> Bool #

maximum :: Ord a => Remote e a -> a #

minimum :: Ord a => Remote e a -> a #

sum :: Num a => Remote e a -> a #

product :: Num a => Remote e a -> a #

Traversable (Remote e) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Remote

Methods

traverse :: Applicative f => (a -> f b) -> Remote e a -> f (Remote e b) #

sequenceA :: Applicative f => Remote e (f a) -> f (Remote e a) #

mapM :: Monad m => (a -> m b) -> Remote e a -> m (Remote e b) #

sequence :: Monad m => Remote e (m a) -> m (Remote e a) #

Alternative (Remote e) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Remote

Methods

empty :: Remote e a #

(<|>) :: Remote e a -> Remote e a -> Remote e a #

some :: Remote e a -> Remote e [a] #

many :: Remote e a -> Remote e [a] #

(Eq a, Eq e) => Eq (Remote e a) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Remote

Methods

(==) :: Remote e a -> Remote e a -> Bool #

(/=) :: Remote e a -> Remote e a -> Bool #

(Ord a, Ord e) => Ord (Remote e a) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Remote

Methods

compare :: Remote e a -> Remote e a -> Ordering #

(<) :: Remote e a -> Remote e a -> Bool #

(<=) :: Remote e a -> Remote e a -> Bool #

(>) :: Remote e a -> Remote e a -> Bool #

(>=) :: Remote e a -> Remote e a -> Bool #

max :: Remote e a -> Remote e a -> Remote e a #

min :: Remote e a -> Remote e a -> Remote e a #

(Read a, Read e) => Read (Remote e a) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Remote

(Show a, Show e) => Show (Remote e a) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Remote

Methods

showsPrec :: Int -> Remote e a -> ShowS #

show :: Remote e a -> String #

showList :: [Remote e a] -> ShowS #

Generic (Remote e a) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Remote

Associated Types

type Rep (Remote e a) :: Type -> Type #

Methods

from :: Remote e a -> Rep (Remote e a) x #

to :: Rep (Remote e a) x -> Remote e a #

Semigroup a => Semigroup (Remote e a) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Remote

Methods

(<>) :: Remote e a -> Remote e a -> Remote e a #

sconcat :: NonEmpty (Remote e a) -> Remote e a #

stimes :: Integral b => b -> Remote e a -> Remote e a #

Semigroup a => Monoid (Remote e a) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Remote

Methods

mempty :: Remote e a #

mappend :: Remote e a -> Remote e a -> Remote e a #

mconcat :: [Remote e a] -> Remote e a #

(ToJSON a, ToJSON e) => ToJSON (Remote e a) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Remote

Methods

toJSON :: Remote e a -> Value #

toEncoding :: Remote e a -> Encoding #

toJSONList :: [Remote e a] -> Value #

toEncodingList :: [Remote e a] -> Encoding #

(FromJSON e, FromJSON a) => FromJSON (Remote e a) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Remote

Methods

parseJSON :: Value -> Parser (Remote e a) #

parseJSONList :: Value -> Parser [Remote e a] #

type Rep (Remote e a) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Remote

type Rep (Remote e a) = D1 (MetaData "Remote" "Shpadoinkle.Widgets.Types.Remote" "Shpadoinkle-widgets-0.1.0.0-inplace" False) ((C1 (MetaCons "Success" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) :+: C1 (MetaCons "Failure" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 e))) :+: (C1 (MetaCons "Loading" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NotAsked" PrefixI False) (U1 :: Type -> Type)))