Distribution.Types.Condition
data Condition c Source #
A boolean expression parameterized over the variable type used.
Constructors
Defined in Distribution.Types.Condition
Methods
(>>=) :: Condition a -> (a -> Condition b) -> Condition b Source #
(>>) :: Condition a -> Condition b -> Condition b Source #
return :: a -> Condition a Source #
fmap :: (a -> b) -> Condition a -> Condition b Source #
(<$) :: a -> Condition b -> Condition a Source #
pure :: a -> Condition a Source #
(<*>) :: Condition (a -> b) -> Condition a -> Condition b Source #
liftA2 :: (a -> b -> c) -> Condition a -> Condition b -> Condition c Source #
(*>) :: Condition a -> Condition b -> Condition b Source #
(<*) :: Condition a -> Condition b -> Condition a Source #
fold :: Monoid m => Condition m -> m Source #
foldMap :: Monoid m => (a -> m) -> Condition a -> m Source #
foldMap' :: Monoid m => (a -> m) -> Condition a -> m Source #
foldr :: (a -> b -> b) -> b -> Condition a -> b Source #
foldr' :: (a -> b -> b) -> b -> Condition a -> b Source #
foldl :: (b -> a -> b) -> b -> Condition a -> b Source #
foldl' :: (b -> a -> b) -> b -> Condition a -> b Source #
foldr1 :: (a -> a -> a) -> Condition a -> a Source #
foldl1 :: (a -> a -> a) -> Condition a -> a Source #
toList :: Condition a -> [a] Source #
null :: Condition a -> Bool Source #
length :: Condition a -> Int Source #
elem :: Eq a => a -> Condition a -> Bool Source #
maximum :: Ord a => Condition a -> a Source #
minimum :: Ord a => Condition a -> a Source #
sum :: Num a => Condition a -> a Source #
product :: Num a => Condition a -> a Source #
traverse :: Applicative f => (a -> f b) -> Condition a -> f (Condition b) Source #
sequenceA :: Applicative f => Condition (f a) -> f (Condition a) Source #
mapM :: Monad m => (a -> m b) -> Condition a -> m (Condition b) Source #
sequence :: Monad m => Condition (m a) -> m (Condition a) Source #
empty :: Condition a Source #
(<|>) :: Condition a -> Condition a -> Condition a Source #
some :: Condition a -> Condition [a] Source #
many :: Condition a -> Condition [a] Source #
mzero :: Condition a Source #
mplus :: Condition a -> Condition a -> Condition a Source #
(==) :: Condition c -> Condition c -> Bool #
(/=) :: Condition c -> Condition c -> Bool #
gfoldl :: (forall d b. Data d => c0 (d -> b) -> d -> c0 b) -> (forall g. g -> c0 g) -> Condition c -> c0 (Condition c) Source #
gunfold :: (forall b r. Data b => c0 (b -> r) -> c0 r) -> (forall r. r -> c0 r) -> Constr -> c0 (Condition c) Source #
toConstr :: Condition c -> Constr Source #
dataTypeOf :: Condition c -> DataType Source #
dataCast1 :: Typeable t => (forall d. Data d => c0 (t d)) -> Maybe (c0 (Condition c)) Source #
dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c0 (t d e)) -> Maybe (c0 (Condition c)) Source #
gmapT :: (forall b. Data b => b -> b) -> Condition c -> Condition c Source #
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Condition c -> r Source #
gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Condition c -> r Source #
gmapQ :: (forall d. Data d => d -> u) -> Condition c -> [u] Source #
gmapQi :: Int -> (forall d. Data d => d -> u) -> Condition c -> u Source #
gmapM :: Monad m => (forall d. Data d => d -> m d) -> Condition c -> m (Condition c) Source #
gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Condition c -> m (Condition c) Source #
gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Condition c -> m (Condition c) Source #
showsPrec :: Int -> Condition c -> ShowS Source #
show :: Condition c -> String Source #
showList :: [Condition c] -> ShowS Source #
Associated Types
type Rep (Condition c) :: Type -> Type Source #
from :: Condition c -> Rep (Condition c) x Source #
to :: Rep (Condition c) x -> Condition c Source #
(<>) :: Condition a -> Condition a -> Condition a Source #
sconcat :: NonEmpty (Condition a) -> Condition a Source #
stimes :: Integral b => b -> Condition a -> Condition a Source #
mempty :: Condition a Source #
mappend :: Condition a -> Condition a -> Condition a Source #
mconcat :: [Condition a] -> Condition a Source #
put :: Condition c -> Put Source #
get :: Get (Condition c) Source #
putList :: [Condition c] -> Put Source #
rnf :: Condition c -> () Source #
structure :: Proxy (Condition c) -> Structure Source #
structureHash' :: Tagged (Condition c) MD5
cNot :: Condition a -> Condition a Source #
Boolean negation of a Condition value.
Condition
cAnd :: Condition a -> Condition a -> Condition a Source #
Boolean AND of two Condtion values.
Condtion
cOr :: Eq v => Condition v -> Condition v -> Condition v Source #
Boolean OR of two Condition values.
simplifyCondition Source #
Arguments
(partial) variable assignment
Simplify the condition and return its free variables.