{-# LANGUAGE DeriveDataTypeable #-}

module GHCJS.Concurrent ( OnBlocked(..)
                        , WouldBlockException(..)
                        ) where

import           GHCJS.Prim

import           Data.Data

{- |
     The runtime tries to run synchronous threads to completion. Sometimes it's
     not possible to continue running a thread, for example when the thread
     tries to take an empty 'MVar'. The runtime can then either throw a
     'WouldBlockException', aborting the blocking action, or continue the
     thread asynchronously.
 -}

data OnBlocked = ContinueAsync -- ^ continue the thread asynchronously if blocked
               | ThrowWouldBlock -- ^ throw 'WouldBlockException' if blocked
               deriving (Typeable OnBlocked
OnBlocked -> DataType
OnBlocked -> Constr
(forall b. Data b => b -> b) -> OnBlocked -> OnBlocked
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> OnBlocked -> u
forall u. (forall d. Data d => d -> u) -> OnBlocked -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OnBlocked -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OnBlocked -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> OnBlocked -> m OnBlocked
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OnBlocked -> m OnBlocked
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OnBlocked
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OnBlocked -> c OnBlocked
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OnBlocked)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OnBlocked)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OnBlocked -> m OnBlocked
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OnBlocked -> m OnBlocked
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OnBlocked -> m OnBlocked
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OnBlocked -> m OnBlocked
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> OnBlocked -> m OnBlocked
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> OnBlocked -> m OnBlocked
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> OnBlocked -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> OnBlocked -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> OnBlocked -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> OnBlocked -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OnBlocked -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OnBlocked -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OnBlocked -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OnBlocked -> r
gmapT :: (forall b. Data b => b -> b) -> OnBlocked -> OnBlocked
$cgmapT :: (forall b. Data b => b -> b) -> OnBlocked -> OnBlocked
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OnBlocked)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OnBlocked)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OnBlocked)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OnBlocked)
dataTypeOf :: OnBlocked -> DataType
$cdataTypeOf :: OnBlocked -> DataType
toConstr :: OnBlocked -> Constr
$ctoConstr :: OnBlocked -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OnBlocked
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OnBlocked
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OnBlocked -> c OnBlocked
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OnBlocked -> c OnBlocked
Data, Typeable, Int -> OnBlocked
OnBlocked -> Int
OnBlocked -> [OnBlocked]
OnBlocked -> OnBlocked
OnBlocked -> OnBlocked -> [OnBlocked]
OnBlocked -> OnBlocked -> OnBlocked -> [OnBlocked]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: OnBlocked -> OnBlocked -> OnBlocked -> [OnBlocked]
$cenumFromThenTo :: OnBlocked -> OnBlocked -> OnBlocked -> [OnBlocked]
enumFromTo :: OnBlocked -> OnBlocked -> [OnBlocked]
$cenumFromTo :: OnBlocked -> OnBlocked -> [OnBlocked]
enumFromThen :: OnBlocked -> OnBlocked -> [OnBlocked]
$cenumFromThen :: OnBlocked -> OnBlocked -> [OnBlocked]
enumFrom :: OnBlocked -> [OnBlocked]
$cenumFrom :: OnBlocked -> [OnBlocked]
fromEnum :: OnBlocked -> Int
$cfromEnum :: OnBlocked -> Int
toEnum :: Int -> OnBlocked
$ctoEnum :: Int -> OnBlocked
pred :: OnBlocked -> OnBlocked
$cpred :: OnBlocked -> OnBlocked
succ :: OnBlocked -> OnBlocked
$csucc :: OnBlocked -> OnBlocked
Enum, Int -> OnBlocked -> ShowS
[OnBlocked] -> ShowS
OnBlocked -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OnBlocked] -> ShowS
$cshowList :: [OnBlocked] -> ShowS
show :: OnBlocked -> String
$cshow :: OnBlocked -> String
showsPrec :: Int -> OnBlocked -> ShowS
$cshowsPrec :: Int -> OnBlocked -> ShowS
Show, OnBlocked -> OnBlocked -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OnBlocked -> OnBlocked -> Bool
$c/= :: OnBlocked -> OnBlocked -> Bool
== :: OnBlocked -> OnBlocked -> Bool
$c== :: OnBlocked -> OnBlocked -> Bool
Eq, Eq OnBlocked
OnBlocked -> OnBlocked -> Bool
OnBlocked -> OnBlocked -> Ordering
OnBlocked -> OnBlocked -> OnBlocked
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: OnBlocked -> OnBlocked -> OnBlocked
$cmin :: OnBlocked -> OnBlocked -> OnBlocked
max :: OnBlocked -> OnBlocked -> OnBlocked
$cmax :: OnBlocked -> OnBlocked -> OnBlocked
>= :: OnBlocked -> OnBlocked -> Bool
$c>= :: OnBlocked -> OnBlocked -> Bool
> :: OnBlocked -> OnBlocked -> Bool
$c> :: OnBlocked -> OnBlocked -> Bool
<= :: OnBlocked -> OnBlocked -> Bool
$c<= :: OnBlocked -> OnBlocked -> Bool
< :: OnBlocked -> OnBlocked -> Bool
$c< :: OnBlocked -> OnBlocked -> Bool
compare :: OnBlocked -> OnBlocked -> Ordering
$ccompare :: OnBlocked -> OnBlocked -> Ordering
Ord)