functor-monad-0.1.1.0: FFunctor: functors on (the usual) Functors
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Functor.Flip1

Synopsis

Documentation

newtype Flip1 t a b c Source #

Swaps the order of parameters. Flip1 is like Flip but has an additional parameter.

newtype Flip1 t a b c = Flip1 {unFlip1 :: t b a c}

Constructors

Flip1 

Fields

Instances

Instances details
(Functor h, MonadFree h (t g f)) => MonadFree h (Flip1 t f g) Source # 
Instance details

Defined in Data.Functor.Flip1

Methods

wrap :: h (Flip1 t f g a) -> Flip1 t f g a #

Functor g => FFunctor (Flip1 ApT g) Source # 
Instance details

Defined in FFunctor

Methods

ffmap :: forall (g0 :: Type -> Type) (h :: Type -> Type) x. (Functor g0, Functor h) => (g0 ~> h) -> Flip1 ApT g g0 x -> Flip1 ApT g h x Source #

Applicative g => FMonad (Flip1 ApT g) Source # 
Instance details

Defined in FMonad

Methods

fpure :: forall (g0 :: Type -> Type). Functor g0 => g0 ~> Flip1 ApT g g0 Source #

fbind :: forall (g0 :: Type -> Type) (h :: Type -> Type) a. (Functor g0, Functor h) => (g0 ~> Flip1 ApT g h) -> Flip1 ApT g g0 a -> Flip1 ApT g h a Source #

MonadFail (t b a) => MonadFail (Flip1 t a b) Source # 
Instance details

Defined in Data.Functor.Flip1

Methods

fail :: String -> Flip1 t a b a0 #

Foldable (t b a) => Foldable (Flip1 t a b) Source # 
Instance details

Defined in Data.Functor.Flip1

Methods

fold :: Monoid m => Flip1 t a b m -> m #

foldMap :: Monoid m => (a0 -> m) -> Flip1 t a b a0 -> m #

foldMap' :: Monoid m => (a0 -> m) -> Flip1 t a b a0 -> m #

foldr :: (a0 -> b0 -> b0) -> b0 -> Flip1 t a b a0 -> b0 #

foldr' :: (a0 -> b0 -> b0) -> b0 -> Flip1 t a b a0 -> b0 #

foldl :: (b0 -> a0 -> b0) -> b0 -> Flip1 t a b a0 -> b0 #

foldl' :: (b0 -> a0 -> b0) -> b0 -> Flip1 t a b a0 -> b0 #

foldr1 :: (a0 -> a0 -> a0) -> Flip1 t a b a0 -> a0 #

foldl1 :: (a0 -> a0 -> a0) -> Flip1 t a b a0 -> a0 #

toList :: Flip1 t a b a0 -> [a0] #

null :: Flip1 t a b a0 -> Bool #

length :: Flip1 t a b a0 -> Int #

elem :: Eq a0 => a0 -> Flip1 t a b a0 -> Bool #

maximum :: Ord a0 => Flip1 t a b a0 -> a0 #

minimum :: Ord a0 => Flip1 t a b a0 -> a0 #

sum :: Num a0 => Flip1 t a b a0 -> a0 #

product :: Num a0 => Flip1 t a b a0 -> a0 #

Eq1 (t b a) => Eq1 (Flip1 t a b) Source # 
Instance details

Defined in Data.Functor.Flip1

Methods

liftEq :: (a0 -> b0 -> Bool) -> Flip1 t a b a0 -> Flip1 t a b b0 -> Bool #

Ord1 (t b a) => Ord1 (Flip1 t a b) Source # 
Instance details

Defined in Data.Functor.Flip1

Methods

liftCompare :: (a0 -> b0 -> Ordering) -> Flip1 t a b a0 -> Flip1 t a b b0 -> Ordering #

(forall c. Read c => Read (t b a c), forall x y. Coercible x y => Coercible (t b a x) (t b a y)) => Read1 (Flip1 t a b) Source # 
Instance details

Defined in Data.Functor.Flip1

Methods

liftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (Flip1 t a b a0) #

liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [Flip1 t a b a0] #

liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (Flip1 t a b a0) #

liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [Flip1 t a b a0] #

(forall c. Show c => Show (t b a c), forall x y. Coercible x y => Coercible (t b a x) (t b a y)) => Show1 (Flip1 t a b) Source # 
Instance details

Defined in Data.Functor.Flip1

Methods

liftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> Flip1 t a b a0 -> ShowS #

liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [Flip1 t a b a0] -> ShowS #

Traversable (t b a) => Traversable (Flip1 t a b) Source # 
Instance details

Defined in Data.Functor.Flip1

Methods

traverse :: Applicative f => (a0 -> f b0) -> Flip1 t a b a0 -> f (Flip1 t a b b0) #

sequenceA :: Applicative f => Flip1 t a b (f a0) -> f (Flip1 t a b a0) #

mapM :: Monad m => (a0 -> m b0) -> Flip1 t a b a0 -> m (Flip1 t a b b0) #

sequence :: Monad m => Flip1 t a b (m a0) -> m (Flip1 t a b a0) #

Alternative (t b a) => Alternative (Flip1 t a b) Source # 
Instance details

Defined in Data.Functor.Flip1

Methods

empty :: Flip1 t a b a0 #

(<|>) :: Flip1 t a b a0 -> Flip1 t a b a0 -> Flip1 t a b a0 #

some :: Flip1 t a b a0 -> Flip1 t a b [a0] #

many :: Flip1 t a b a0 -> Flip1 t a b [a0] #

Applicative (t b a) => Applicative (Flip1 t a b) Source # 
Instance details

Defined in Data.Functor.Flip1

Methods

pure :: a0 -> Flip1 t a b a0 #

(<*>) :: Flip1 t a b (a0 -> b0) -> Flip1 t a b a0 -> Flip1 t a b b0 #

liftA2 :: (a0 -> b0 -> c) -> Flip1 t a b a0 -> Flip1 t a b b0 -> Flip1 t a b c #

(*>) :: Flip1 t a b a0 -> Flip1 t a b b0 -> Flip1 t a b b0 #

(<*) :: Flip1 t a b a0 -> Flip1 t a b b0 -> Flip1 t a b a0 #

Functor (t b a) => Functor (Flip1 t a b) Source # 
Instance details

Defined in Data.Functor.Flip1

Methods

fmap :: (a0 -> b0) -> Flip1 t a b a0 -> Flip1 t a b b0 #

(<$) :: a0 -> Flip1 t a b b0 -> Flip1 t a b a0 #

Monad (t b a) => Monad (Flip1 t a b) Source # 
Instance details

Defined in Data.Functor.Flip1

Methods

(>>=) :: Flip1 t a b a0 -> (a0 -> Flip1 t a b b0) -> Flip1 t a b b0 #

(>>) :: Flip1 t a b a0 -> Flip1 t a b b0 -> Flip1 t a b b0 #

return :: a0 -> Flip1 t a b a0 #

MonadPlus (t b a) => MonadPlus (Flip1 t a b) Source # 
Instance details

Defined in Data.Functor.Flip1

Methods

mzero :: Flip1 t a b a0 #

mplus :: Flip1 t a b a0 -> Flip1 t a b a0 -> Flip1 t a b a0 #

Read (t b a c) => Read (Flip1 t a b c) Source # 
Instance details

Defined in Data.Functor.Flip1

Methods

readsPrec :: Int -> ReadS (Flip1 t a b c) #

readList :: ReadS [Flip1 t a b c] #

readPrec :: ReadPrec (Flip1 t a b c) #

readListPrec :: ReadPrec [Flip1 t a b c] #

Show (t b a c) => Show (Flip1 t a b c) Source # 
Instance details

Defined in Data.Functor.Flip1

Methods

showsPrec :: Int -> Flip1 t a b c -> ShowS #

show :: Flip1 t a b c -> String #

showList :: [Flip1 t a b c] -> ShowS #

Eq (t b a c) => Eq (Flip1 t a b c) Source # 
Instance details

Defined in Data.Functor.Flip1

Methods

(==) :: Flip1 t a b c -> Flip1 t a b c -> Bool #

(/=) :: Flip1 t a b c -> Flip1 t a b c -> Bool #

Ord (t b a c) => Ord (Flip1 t a b c) Source # 
Instance details

Defined in Data.Functor.Flip1

Methods

compare :: Flip1 t a b c -> Flip1 t a b c -> Ordering #

(<) :: Flip1 t a b c -> Flip1 t a b c -> Bool #

(<=) :: Flip1 t a b c -> Flip1 t a b c -> Bool #

(>) :: Flip1 t a b c -> Flip1 t a b c -> Bool #

(>=) :: Flip1 t a b c -> Flip1 t a b c -> Bool #

max :: Flip1 t a b c -> Flip1 t a b c -> Flip1 t a b c #

min :: Flip1 t a b c -> Flip1 t a b c -> Flip1 t a b c #