haskell-debugger
Safe HaskellNone
LanguageHaskell2010

GHC.Debugger.Logger

Description

Simple Logger API using co-log style loggers

Synopsis

The core Logger type

data Recorder msg Source #

Instances

Instances details
Contravariant Recorder Source # 
Instance details

Defined in GHC.Debugger.Logger

Methods

contramap :: (a' -> a) -> Recorder a -> Recorder a' #

(>$) :: b -> Recorder b -> Recorder a #

Monoid (Recorder msg) Source # 
Instance details

Defined in GHC.Debugger.Logger

Methods

mempty :: Recorder msg #

mappend :: Recorder msg -> Recorder msg -> Recorder msg #

mconcat :: [Recorder msg] -> Recorder msg #

Semigroup (Recorder msg) Source # 
Instance details

Defined in GHC.Debugger.Logger

Methods

(<>) :: Recorder msg -> Recorder msg -> Recorder msg #

sconcat :: NonEmpty (Recorder msg) -> Recorder msg #

stimes :: Integral b => b -> Recorder msg -> Recorder msg #

logWith :: (HasCallStack, MonadIO m) => Recorder (WithSeverity msg) -> Severity -> msg -> m () Source #

Log messages

class Pretty a where #

Overloaded conversion to Doc.

Laws:

  1. output should be pretty. :-)

Minimal complete definition

pretty

Methods

pretty :: a -> Doc ann #

>>> pretty 1 <+> pretty "hello" <+> pretty 1.234
1 hello 1.234

default pretty :: Show a => a -> Doc ann #

prettyList :: [a] -> Doc ann #

prettyList is only used to define the instance Pretty a => Pretty [a]. In normal circumstances only the pretty function is used.

>>> prettyList [1, 23, 456]
[1, 23, 456]

Instances

Instances details
Pretty Void #

Finding a good example for printing something that does not exist is hard, so here is an example of printing a list full of nothing.

>>> pretty ([] :: [Void])
[]
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Void -> Doc ann #

prettyList :: [Void] -> Doc ann #

Pretty Int16 # 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Int16 -> Doc ann #

prettyList :: [Int16] -> Doc ann #

Pretty Int32 # 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Int32 -> Doc ann #

prettyList :: [Int32] -> Doc ann #

Pretty Int64 # 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Int64 -> Doc ann #

prettyList :: [Int64] -> Doc ann #

Pretty Int8 # 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Int8 -> Doc ann #

prettyList :: [Int8] -> Doc ann #

Pretty Word16 # 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Word16 -> Doc ann #

prettyList :: [Word16] -> Doc ann #

Pretty Word32 # 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Word32 -> Doc ann #

prettyList :: [Word32] -> Doc ann #

Pretty Word64 # 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Word64 -> Doc ann #

prettyList :: [Word64] -> Doc ann #

Pretty Word8 # 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Word8 -> Doc ann #

prettyList :: [Word8] -> Doc ann #

Pretty DebuggerLog Source # 
Instance details

Defined in GHC.Debugger

Methods

pretty :: DebuggerLog -> Doc ann #

prettyList :: [DebuggerLog] -> Doc ann #

Pretty EvalLog Source # 
Instance details

Defined in GHC.Debugger.Evaluation

Methods

pretty :: EvalLog -> Doc ann #

prettyList :: [EvalLog] -> Doc ann #

Pretty Log # 
Instance details

Defined in HIE.Bios.Ghc.Check

Methods

pretty :: Log -> Doc ann #

prettyList :: [Log] -> Doc ann #

Pretty Log # 
Instance details

Defined in HIE.Bios.Ghc.Load

Methods

pretty :: Log -> Doc ann #

prettyList :: [Log] -> Doc ann #

Pretty Log # 
Instance details

Defined in HIE.Bios.Types

Methods

pretty :: Log -> Doc ann #

prettyList :: [Log] -> Doc ann #

Pretty Text #

Automatically converts all newlines to line.

>>> pretty ("hello\nworld" :: Text)
hello
world

Note that line can be undone by group:

>>> group (pretty ("hello\nworld" :: Text))
hello world

Manually use hardline if you definitely want newlines.

Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Text -> Doc ann #

prettyList :: [Text] -> Doc ann #

Pretty Text #

(lazy Text instance, identical to the strict version)

Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Text -> Doc ann #

prettyList :: [Text] -> Doc ann #

Pretty Integer #
>>> pretty (2^123 :: Integer)
10633823966279326983230456482242756608
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Integer -> Doc ann #

prettyList :: [Integer] -> Doc ann #

Pretty Natural # 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Natural -> Doc ann #

prettyList :: [Natural] -> Doc ann #

Pretty () #
>>> pretty ()
()

The argument is not used:

>>> pretty (error "Strict?" :: ())
()
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: () -> Doc ann #

prettyList :: [()] -> Doc ann #

Pretty Bool #
>>> pretty True
True
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Bool -> Doc ann #

prettyList :: [Bool] -> Doc ann #

Pretty Char #

Instead of (pretty 'n'), consider using line as a more readable alternative.

>>> pretty 'f' <> pretty 'o' <> pretty 'o'
foo
>>> pretty ("string" :: String)
string
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Char -> Doc ann #

prettyList :: [Char] -> Doc ann #

Pretty Double #
>>> pretty (exp 1 :: Double)
2.71828182845904...
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Double -> Doc ann #

prettyList :: [Double] -> Doc ann #

Pretty Float #
>>> pretty (pi :: Float)
3.1415927
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Float -> Doc ann #

prettyList :: [Float] -> Doc ann #

Pretty Int #
>>> pretty (123 :: Int)
123
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Int -> Doc ann #

prettyList :: [Int] -> Doc ann #

Pretty Word # 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Word -> Doc ann #

prettyList :: [Word] -> Doc ann #

Pretty a => Pretty (NonEmpty a) # 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: NonEmpty a -> Doc ann #

prettyList :: [NonEmpty a] -> Doc ann #

Pretty a => Pretty (Identity a) #
>>> pretty (Identity 1)
1
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Identity a -> Doc ann #

prettyList :: [Identity a] -> Doc ann #

Pretty a => Pretty (Maybe a) #

Ignore Nothings, print Just contents.

>>> pretty (Just True)
True
>>> braces (pretty (Nothing :: Maybe Bool))
{}
>>> pretty [Just 1, Nothing, Just 3, Nothing]
[1, 3]
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Maybe a -> Doc ann #

prettyList :: [Maybe a] -> Doc ann #

Pretty a => Pretty [a] #
>>> pretty [1,2,3]
[1, 2, 3]
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: [a] -> Doc ann #

prettyList :: [[a]] -> Doc ann #

(Pretty a1, Pretty a2) => Pretty (a1, a2) #
>>> pretty (123, "hello")
(123, hello)
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: (a1, a2) -> Doc ann #

prettyList :: [(a1, a2)] -> Doc ann #

Pretty a => Pretty (Const a b) # 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Const a b -> Doc ann #

prettyList :: [Const a b] -> Doc ann #

(Pretty a1, Pretty a2, Pretty a3) => Pretty (a1, a2, a3) #
>>> pretty (123, "hello", False)
(123, hello, False)
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: (a1, a2, a3) -> Doc ann #

prettyList :: [(a1, a2, a3)] -> Doc ann #

For simpler usage

newtype LogAction (m :: Type -> Type) msg #

Polymorphic and very general logging action type.

  • msg type variables is an input for logger. It can be Text or custom logging messsage with different fields that you want to format in future.
  • m type variable is for monadic action inside which logging is happening. It can be either IO or some custom pure monad.

Key design point here is that LogAction is:

Constructors

LogAction 

Fields

Instances

Instances details
Contravariant (LogAction m) # 
Instance details

Defined in Colog.Core.Action

Methods

contramap :: (a' -> a) -> LogAction m a -> LogAction m a' #

(>$) :: b -> LogAction m b -> LogAction m a #

UnrepresentableClass => Functor (LogAction m) #

⚠️CAUTION⚠️ This instance is for custom error display only.

LogAction is not supposed to have Functor instance by design.

In case it is used by mistake, the user will see the following:

>>> fmap show logStringStdout
...
... 'LogAction' cannot have a 'Functor' instance by design.
      However, you've attempted to use this instance.
...
      Probably you meant 'Contravariant' class instance with the following methods:
        * contramap :: (a -> b) -> LogAction m b -> LogAction m a
        * (>$) :: b -> LogAction m b -> LogAction m a
...

# 207 "srcCologCore/Action.hs"

Since: co-log-core-0.2.1.0

Instance details

Defined in Colog.Core.Action

Methods

fmap :: (a -> b) -> LogAction m a -> LogAction m b #

(<$) :: a -> LogAction m b -> LogAction m a #

Applicative m => Monoid (LogAction m a) # 
Instance details

Defined in Colog.Core.Action

Methods

mempty :: LogAction m a #

mappend :: LogAction m a -> LogAction m a -> LogAction m a #

mconcat :: [LogAction m a] -> LogAction m a #

Applicative m => Semigroup (LogAction m a) #

This instance allows you to join multiple logging actions into single one.

For example, if you have two actions like these:

logToStdout :: LogAction IO String  -- outputs String to terminal
logToFile   :: LogAction IO String  -- appends String to some file

You can create new LogAction that perform both actions one after another using Semigroup:

logToBoth :: LogAction IO String  -- outputs String to both terminal and some file
logToBoth = logToStdout <> logToFile
Instance details

Defined in Colog.Core.Action

Methods

(<>) :: LogAction m a -> LogAction m a -> LogAction m a #

sconcat :: NonEmpty (LogAction m a) -> LogAction m a #

stimes :: Integral b => b -> LogAction m a -> LogAction m a #

HasLog (LogAction m msg) msg m # 
Instance details

Defined in Colog.Core.Class

Methods

getLogAction :: LogAction m msg -> LogAction m msg #

setLogAction :: LogAction m msg -> LogAction m msg -> LogAction m msg #

overLogAction :: (LogAction m msg -> LogAction m msg) -> LogAction m msg -> LogAction m msg #

logActionL :: Lens' (LogAction m msg) (LogAction m msg) #

toCologAction :: forall (m :: Type -> Type) msg. (MonadIO m, HasCallStack) => Recorder msg -> LogAction m msg Source #

Severity

data Severity #

Severity for the log messages.

Constructors

Debug

Information useful for debug purposes.

E.g. output of the function that is important for the internal development, not for users. Like, the result of SQL query.

Info

Normal operational information.

E.g. describing general steps: starting application, finished downloading.

Warning

General warnings, non-critical failures.

E.g. couldn't download icon from some service to display.

Error

General errors/severe errors.

E.g. exceptional situations: couldn't syncronize accounts.

Instances

Instances details
Eq Severity # 
Instance details

Defined in Colog.Core.Severity

Ord Severity # 
Instance details

Defined in Colog.Core.Severity

Bounded Severity # 
Instance details

Defined in Colog.Core.Severity

Enum Severity # 
Instance details

Defined in Colog.Core.Severity

Ix Severity # 
Instance details

Defined in Colog.Core.Severity

Read Severity # 
Instance details

Defined in Colog.Core.Severity

Show Severity # 
Instance details

Defined in Colog.Core.Severity

data WithSeverity msg #

A message tagged with a Severity.

It is common to want to log various types of messages tagged with a severity. WithSeverity provides a standard way to do so while allowing the messages to be processed independently of the severity.

It is easy to cmap over a 'LogAction m (WithSeverity a)', or to filter based on the severity.

logSomething :: LogAction m (WithSeverity String) -> m ()
logSomething logger = logger <& "hello" `WithSeverity` Info

cmap' :: (b -> a) -> LogAction m (WithSeverity a) -> LogAction m (WithSeverity b)
cmap' f action = cmap (fmap f) action

filterBySeverity' :: (Applicative m) => Severity -> LogAction m (WithSeverity a) -> LogAction m (WithSeverity a)
filterBySeverity' threshold action = filterBySeverity threshold getSeverity action

Since: co-log-core-0.3.1.0

Constructors

WithSeverity 

Fields

Instances

Instances details
Functor WithSeverity # 
Instance details

Defined in Colog.Core.Severity

Methods

fmap :: (a -> b) -> WithSeverity a -> WithSeverity b #

(<$) :: a -> WithSeverity b -> WithSeverity a #

Foldable WithSeverity # 
Instance details

Defined in Colog.Core.Severity

Methods

fold :: Monoid m => WithSeverity m -> m #

foldMap :: Monoid m => (a -> m) -> WithSeverity a -> m #

foldMap' :: Monoid m => (a -> m) -> WithSeverity a -> m #

foldr :: (a -> b -> b) -> b -> WithSeverity a -> b #

foldr' :: (a -> b -> b) -> b -> WithSeverity a -> b #

foldl :: (b -> a -> b) -> b -> WithSeverity a -> b #

foldl' :: (b -> a -> b) -> b -> WithSeverity a -> b #

foldr1 :: (a -> a -> a) -> WithSeverity a -> a #

foldl1 :: (a -> a -> a) -> WithSeverity a -> a #

toList :: WithSeverity a -> [a] #

null :: WithSeverity a -> Bool #

length :: WithSeverity a -> Int #

elem :: Eq a => a -> WithSeverity a -> Bool #

maximum :: Ord a => WithSeverity a -> a #

minimum :: Ord a => WithSeverity a -> a #

sum :: Num a => WithSeverity a -> a #

product :: Num a => WithSeverity a -> a #

Traversable WithSeverity # 
Instance details

Defined in Colog.Core.Severity

Methods

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

sequenceA :: Applicative f => WithSeverity (f a) -> f (WithSeverity a) #

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

sequence :: Monad m => WithSeverity (m a) -> m (WithSeverity a) #

Eq msg => Eq (WithSeverity msg) # 
Instance details

Defined in Colog.Core.Severity

Methods

(==) :: WithSeverity msg -> WithSeverity msg -> Bool #

(/=) :: WithSeverity msg -> WithSeverity msg -> Bool #

Ord msg => Ord (WithSeverity msg) # 
Instance details

Defined in Colog.Core.Severity

Show msg => Show (WithSeverity msg) # 
Instance details

Defined in Colog.Core.Severity

cmap :: (a -> b) -> Recorder b -> Recorder a Source #

cmapIO :: (a -> IO b) -> Recorder b -> Recorder a Source #

Pretty printing of logs

class Contravariant (f :: Type -> Type) where #

The class of contravariant functors.

Whereas in Haskell, one can think of a Functor as containing or producing values, a contravariant functor is a functor that can be thought of as consuming values.

As an example, consider the type of predicate functions a -> Bool. One such predicate might be negative x = x < 0, which classifies integers as to whether they are negative. However, given this predicate, we can re-use it in other situations, providing we have a way to map values to integers. For instance, we can use the negative predicate on a person's bank balance to work out if they are currently overdrawn:

newtype Predicate a = Predicate { getPredicate :: a -> Bool }

instance Contravariant Predicate where
  contramap :: (a' -> a) -> (Predicate a -> Predicate a')
  contramap f (Predicate p) = Predicate (p . f)
                                         |   `- First, map the input...
                                         `----- then apply the predicate.

overdrawn :: Predicate Person
overdrawn = contramap personBankBalance negative

Any instance should be subject to the following laws:

Identity
contramap id = id
Composition
contramap (g . f) = contramap f . contramap g

Note, that the second law follows from the free theorem of the type of contramap and the first law, so you need only check that the former condition holds.

Methods

contramap :: (a' -> a) -> f a -> f a' #

Instances

Instances details
Contravariant ToJSONKeyFunction # 
Instance details

Defined in Data.Aeson.Types.ToJSON

Contravariant Comparison #

A Comparison is a Contravariant Functor, because contramap can apply its function argument to each input of the comparison function.

Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> Comparison a -> Comparison a' #

(>$) :: b -> Comparison b -> Comparison a #

Contravariant Equivalence #

Equivalence relations are Contravariant, because you can apply the contramapped function to each input to the equivalence relation.

Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> Equivalence a -> Equivalence a' #

(>$) :: b -> Equivalence b -> Equivalence a #

Contravariant Predicate #

A Predicate is a Contravariant Functor, because contramap can apply its function argument to the input of the predicate.

Without newtypes contramap f equals precomposing with f (= (. f)).

contramap :: (a' -> a) -> (Predicate a -> Predicate a')
contramap f (Predicate g) = Predicate (g . f)
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> Predicate a -> Predicate a' #

(>$) :: b -> Predicate b -> Predicate a #

Contravariant Recorder Source # 
Instance details

Defined in GHC.Debugger.Logger

Methods

contramap :: (a' -> a) -> Recorder a -> Recorder a' #

(>$) :: b -> Recorder b -> Recorder a #

Contravariant (Op a) # 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a0) -> Op a a0 -> Op a a' #

(>$) :: b -> Op a b -> Op a a0 #

Contravariant (LogAction m) # 
Instance details

Defined in Colog.Core.Action

Methods

contramap :: (a' -> a) -> LogAction m a -> LogAction m a' #

(>$) :: b -> LogAction m b -> LogAction m a #

Contravariant (Proxy :: Type -> Type) # 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> Proxy a -> Proxy a' #

(>$) :: b -> Proxy b -> Proxy a #

Contravariant (U1 :: Type -> Type) # 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> U1 a -> U1 a' #

(>$) :: b -> U1 b -> U1 a #

Contravariant (V1 :: Type -> Type) # 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> V1 a -> V1 a' #

(>$) :: b -> V1 b -> V1 a #

Contravariant m => Contravariant (MaybeT m) # 
Instance details

Defined in Control.Monad.Trans.Maybe

Methods

contramap :: (a' -> a) -> MaybeT m a -> MaybeT m a' #

(>$) :: b -> MaybeT m b -> MaybeT m a #

Contravariant (Const a :: Type -> Type) # 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a0) -> Const a a0 -> Const a a' #

(>$) :: b -> Const a b -> Const a a0 #

Contravariant f => Contravariant (Alt f) # 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> Alt f a -> Alt f a' #

(>$) :: b -> Alt f b -> Alt f a #

Contravariant f => Contravariant (Rec1 f) # 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> Rec1 f a -> Rec1 f a' #

(>$) :: b -> Rec1 f b -> Rec1 f a #

Contravariant f => Contravariant (Backwards f) #

Derived instance.

Instance details

Defined in Control.Applicative.Backwards

Methods

contramap :: (a' -> a) -> Backwards f a -> Backwards f a' #

(>$) :: b -> Backwards f b -> Backwards f a #

Contravariant m => Contravariant (ExceptT e m) # 
Instance details

Defined in Control.Monad.Trans.Except

Methods

contramap :: (a' -> a) -> ExceptT e m a -> ExceptT e m a' #

(>$) :: b -> ExceptT e m b -> ExceptT e m a #

Contravariant f => Contravariant (IdentityT f) # 
Instance details

Defined in Control.Monad.Trans.Identity

Methods

contramap :: (a' -> a) -> IdentityT f a -> IdentityT f a' #

(>$) :: b -> IdentityT f b -> IdentityT f a #

Contravariant m => Contravariant (ReaderT r m) # 
Instance details

Defined in Control.Monad.Trans.Reader

Methods

contramap :: (a' -> a) -> ReaderT r m a -> ReaderT r m a' #

(>$) :: b -> ReaderT r m b -> ReaderT r m a #

Contravariant m => Contravariant (StateT s m) # 
Instance details

Defined in Control.Monad.Trans.State.Lazy

Methods

contramap :: (a' -> a) -> StateT s m a -> StateT s m a' #

(>$) :: b -> StateT s m b -> StateT s m a #

Contravariant m => Contravariant (StateT s m) # 
Instance details

Defined in Control.Monad.Trans.State.Strict

Methods

contramap :: (a' -> a) -> StateT s m a -> StateT s m a' #

(>$) :: b -> StateT s m b -> StateT s m a #

Contravariant m => Contravariant (WriterT w m) # 
Instance details

Defined in Control.Monad.Trans.Writer.Lazy

Methods

contramap :: (a' -> a) -> WriterT w m a -> WriterT w m a' #

(>$) :: b -> WriterT w m b -> WriterT w m a #

Contravariant m => Contravariant (WriterT w m) # 
Instance details

Defined in Control.Monad.Trans.Writer.Strict

Methods

contramap :: (a' -> a) -> WriterT w m a -> WriterT w m a' #

(>$) :: b -> WriterT w m b -> WriterT w m a #

Contravariant (Constant a :: Type -> Type) # 
Instance details

Defined in Data.Functor.Constant

Methods

contramap :: (a' -> a0) -> Constant a a0 -> Constant a a' #

(>$) :: b -> Constant a b -> Constant a a0 #

Contravariant f => Contravariant (Reverse f) #

Derived instance.

Instance details

Defined in Data.Functor.Reverse

Methods

contramap :: (a' -> a) -> Reverse f a -> Reverse f a' #

(>$) :: b -> Reverse f b -> Reverse f a #

(Contravariant f, Contravariant g) => Contravariant (Product f g) # 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> Product f g a -> Product f g a' #

(>$) :: b -> Product f g b -> Product f g a #

(Contravariant f, Contravariant g) => Contravariant (Sum f g) # 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> Sum f g a -> Sum f g a' #

(>$) :: b -> Sum f g b -> Sum f g a #

(Contravariant f, Contravariant g) => Contravariant (f :*: g) # 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> (f :*: g) a -> (f :*: g) a' #

(>$) :: b -> (f :*: g) b -> (f :*: g) a #

(Contravariant f, Contravariant g) => Contravariant (f :+: g) # 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> (f :+: g) a -> (f :+: g) a' #

(>$) :: b -> (f :+: g) b -> (f :+: g) a #

Contravariant (K1 i c :: Type -> Type) # 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> K1 i c a -> K1 i c a' #

(>$) :: b -> K1 i c b -> K1 i c a #

(Functor f, Contravariant g) => Contravariant (Compose f g) # 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> Compose f g a -> Compose f g a' #

(>$) :: b -> Compose f g b -> Compose f g a #

(Functor f, Contravariant g) => Contravariant (f :.: g) # 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> (f :.: g) a -> (f :.: g) a' #

(>$) :: b -> (f :.: g) b -> (f :.: g) a #

Contravariant f => Contravariant (M1 i c f) # 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> M1 i c f a -> M1 i c f a' #

(>$) :: b -> M1 i c f b -> M1 i c f a #

Contravariant m => Contravariant (RWST r w s m) # 
Instance details

Defined in Control.Monad.Trans.RWS.Lazy

Methods

contramap :: (a' -> a) -> RWST r w s m a -> RWST r w s m a' #

(>$) :: b -> RWST r w s m b -> RWST r w s m a #

Contravariant m => Contravariant (RWST r w s m) # 
Instance details

Defined in Control.Monad.Trans.RWS.Strict

Methods

contramap :: (a' -> a) -> RWST r w s m a -> RWST r w s m a' #

(>$) :: b -> RWST r w s m b -> RWST r w s m a #