-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | A sensible set of defaults for writing custom Preludes. -- -- A sensible set of defaults for writing custom Preludes. @package protolude @version 0.1.10 module Semiring class Monoid m => Semiring m one :: Semiring m => m (<.>) :: Semiring m => m -> m -> m -- | Alias for mempty zero :: Monoid m => m module List head :: (Foldable f) => f a -> Maybe a ordNub :: (Ord a) => [a] -> [a] sortOn :: (Ord o) => (a -> o) -> [a] -> [a] list :: [b] -> (a -> b) -> [a] -> [b] product :: (Foldable f, Num a) => f a -> a sum :: (Foldable f, Num a) => f a -> a module Functor -- | The Functor class is used for types that can be mapped over. -- Instances of Functor should satisfy the following laws: -- --
-- fmap id == id -- fmap (f . g) == fmap f . fmap g ---- -- The instances of Functor for lists, Maybe and IO -- satisfy these laws. class Functor (f :: * -> *) fmap :: Functor f => (a -> b) -> f a -> f b -- | Replace all locations in the input with the same value. The default -- definition is fmap . const, but this may be -- overridden with a more efficient version. (<$) :: Functor f => a -> f b -> f a -- | Flipped version of <$. -- --
-- >>> Nothing $> "foo" -- Nothing -- -- >>> Just 90210 $> "foo" -- Just "foo" ---- -- Replace the contents of an Either Int -- Int with a constant String, resulting in an -- Either Int String: -- --
-- >>> Left 8675309 $> "foo" -- Left 8675309 -- -- >>> Right 8675309 $> "foo" -- Right "foo" ---- -- Replace each element of a list with a constant String: -- --
-- >>> [1,2,3] $> "foo" -- ["foo","foo","foo"] ---- -- Replace the second element of a pair with a constant String: -- --
-- >>> (1,2) $> "foo" -- (1,"foo") --($>) :: Functor f => f a -> b -> f b infixl 4 $> -- | An infix synonym for fmap. -- -- The name of this operator is an allusion to $. Note the -- similarities between their types: -- --
-- ($) :: (a -> b) -> a -> b -- (<$>) :: Functor f => (a -> b) -> f a -> f b ---- -- Whereas $ is function application, <$> is -- function application lifted over a Functor. -- --
-- >>> show <$> Nothing -- Nothing -- -- >>> show <$> Just 3 -- Just "3" ---- -- Convert from an Either Int Int to -- an Either Int String using -- show: -- --
-- >>> show <$> Left 17 -- Left 17 -- -- >>> show <$> Right 17 -- Right "17" ---- -- Double each element of a list: -- --
-- >>> (*2) <$> [1,2,3] -- [2,4,6] ---- -- Apply even to the second element of a pair: -- --
-- >>> even <$> (2,2) -- (2,True) --(<$>) :: Functor f => (a -> b) -> f a -> f b infixl 4 <$> -- | void value discards or ignores the result of -- evaluation, such as the return value of an IO action. -- --
-- >>> void Nothing -- Nothing -- -- >>> void (Just 3) -- Just () ---- -- Replace the contents of an Either Int -- Int with unit, resulting in an Either -- Int '()': -- --
-- >>> void (Left 8675309) -- Left 8675309 -- -- >>> void (Right 8675309) -- Right () ---- -- Replace every element of a list with unit: -- --
-- >>> void [1,2,3] -- [(),(),()] ---- -- Replace the second element of a pair with unit: -- --
-- >>> void (1,2) -- (1,()) ---- -- Discard the result of an IO action: -- --
-- >>> mapM print [1,2] -- 1 -- 2 -- [(),()] -- -- >>> void $ mapM print [1,2] -- 1 -- 2 --void :: Functor f => f a -> f () module Either maybeToLeft :: r -> Maybe l -> Either l r maybeToRight :: l -> Maybe r -> Either l r leftToMaybe :: Either l r -> Maybe l rightToMaybe :: Either l r -> Maybe r maybeToEither :: Monoid b => (a -> b) -> Maybe a -> b module Bool whenM :: Monad m => m Bool -> m () -> m () unlessM :: Monad m => m Bool -> m () -> m () ifM :: Monad m => m Bool -> m a -> m a -> m a guardM :: MonadPlus m => m Bool -> m () bool :: a -> a -> Bool -> a module Bifunctor class Bifunctor p where bimap f g = first f . second g first f = bimap f id second = bimap id bimap :: Bifunctor p => (a -> b) -> (c -> d) -> p a c -> p b d first :: Bifunctor p => (a -> b) -> p a c -> p b c second :: Bifunctor p => (b -> c) -> p a b -> p a c instance Bifunctor.Bifunctor (,) instance Bifunctor.Bifunctor ((,,) x1) instance Bifunctor.Bifunctor ((,,,) x1 x2) instance Bifunctor.Bifunctor ((,,,,) x1 x2 x3) instance Bifunctor.Bifunctor ((,,,,,) x1 x2 x3 x4) instance Bifunctor.Bifunctor ((,,,,,,) x1 x2 x3 x4 x5) instance Bifunctor.Bifunctor Data.Either.Either instance Bifunctor.Bifunctor Data.Functor.Const.Const module Base ($!) :: (a -> b) -> a -> b infixr 0 $! module Conv class StringConv a b strConv :: StringConv a b => Leniency -> a -> b toS :: StringConv a b => a -> b toSL :: StringConv a b => a -> b data Leniency Lenient :: Leniency Strict :: Leniency instance GHC.Enum.Bounded Conv.Leniency instance GHC.Enum.Enum Conv.Leniency instance GHC.Classes.Ord Conv.Leniency instance GHC.Show.Show Conv.Leniency instance GHC.Classes.Eq Conv.Leniency instance Conv.StringConv GHC.Base.String GHC.Base.String instance Conv.StringConv GHC.Base.String Data.ByteString.Internal.ByteString instance Conv.StringConv GHC.Base.String Data.ByteString.Lazy.Internal.ByteString instance Conv.StringConv GHC.Base.String Data.Text.Internal.Text instance Conv.StringConv GHC.Base.String Data.Text.Internal.Lazy.Text instance Conv.StringConv Data.ByteString.Internal.ByteString GHC.Base.String instance Conv.StringConv Data.ByteString.Internal.ByteString Data.ByteString.Internal.ByteString instance Conv.StringConv Data.ByteString.Internal.ByteString Data.ByteString.Lazy.Internal.ByteString instance Conv.StringConv Data.ByteString.Internal.ByteString Data.Text.Internal.Text instance Conv.StringConv Data.ByteString.Internal.ByteString Data.Text.Internal.Lazy.Text instance Conv.StringConv Data.ByteString.Lazy.Internal.ByteString GHC.Base.String instance Conv.StringConv Data.ByteString.Lazy.Internal.ByteString Data.ByteString.Internal.ByteString instance Conv.StringConv Data.ByteString.Lazy.Internal.ByteString Data.ByteString.Lazy.Internal.ByteString instance Conv.StringConv Data.ByteString.Lazy.Internal.ByteString Data.Text.Internal.Text instance Conv.StringConv Data.ByteString.Lazy.Internal.ByteString Data.Text.Internal.Lazy.Text instance Conv.StringConv Data.Text.Internal.Text GHC.Base.String instance Conv.StringConv Data.Text.Internal.Text Data.ByteString.Internal.ByteString instance Conv.StringConv Data.Text.Internal.Text Data.ByteString.Lazy.Internal.ByteString instance Conv.StringConv Data.Text.Internal.Text Data.Text.Internal.Lazy.Text instance Conv.StringConv Data.Text.Internal.Text Data.Text.Internal.Text instance Conv.StringConv Data.Text.Internal.Lazy.Text GHC.Base.String instance Conv.StringConv Data.Text.Internal.Lazy.Text Data.Text.Internal.Text instance Conv.StringConv Data.Text.Internal.Lazy.Text Data.Text.Internal.Lazy.Text instance Conv.StringConv Data.Text.Internal.Lazy.Text Data.ByteString.Lazy.Internal.ByteString instance Conv.StringConv Data.Text.Internal.Lazy.Text Data.ByteString.Internal.ByteString module Exceptions hush :: Alternative m => Either e a -> m a note :: (MonadError e m, Applicative m) => e -> Maybe a -> m a tryIO :: MonadIO m => IO a -> ExceptT IOException m a module Monad -- | The Monad class defines the basic operations over a -- monad, a concept from a branch of mathematics known as -- category theory. From the perspective of a Haskell programmer, -- however, it is best to think of a monad as an abstract datatype -- of actions. Haskell's do expressions provide a convenient -- syntax for writing monadic expressions. -- -- Instances of Monad should satisfy the following laws: -- -- -- -- Furthermore, the Monad and Applicative operations should -- relate as follows: -- -- -- -- The above laws imply: -- -- -- -- and that pure and (<*>) satisfy the applicative -- functor laws. -- -- The instances of Monad for lists, Maybe and IO -- defined in the Prelude satisfy these laws. class Applicative m => Monad (m :: * -> *) -- | Sequentially compose two actions, passing any value produced by the -- first as an argument to the second. (>>=) :: Monad m => m a -> (a -> m b) -> m b -- | Sequentially compose two actions, discarding any value produced by the -- first, like sequencing operators (such as the semicolon) in imperative -- languages. (>>) :: Monad m => m a -> m b -> m b -- | Inject a value into the monadic type. return :: Monad m => a -> m a -- | Monads that also support choice and failure. class (Alternative m, Monad m) => MonadPlus (m :: * -> *) -- | the identity of mplus. It should also satisfy the equations -- --
-- mzero >>= f = mzero -- v >> mzero = mzero --mzero :: MonadPlus m => m a -- | an associative operation mplus :: MonadPlus m => m a -> m a -> m a -- | Same as >>=, but with the arguments interchanged. (=<<) :: Monad m => (a -> m b) -> m a -> m b infixr 1 =<< -- | Left-to-right Kleisli composition of monads. (>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c infixr 1 >=> -- | Right-to-left Kleisli composition of monads. -- (>=>), with the arguments flipped. -- -- Note how this operator resembles function composition -- (.): -- --
-- (.) :: (b -> c) -> (a -> b) -> a -> c -- (<=<) :: Monad m => (b -> m c) -> (a -> m b) -> a -> m c --(<=<) :: Monad m => (b -> m c) -> (a -> m b) -> a -> m c infixr 1 <=< -- | Sequentially compose two actions, discarding any value produced by the -- first, like sequencing operators (such as the semicolon) in imperative -- languages. (>>) :: Monad m => forall a b. m a -> m b -> m b -- | forever act repeats the action infinitely. forever :: Applicative f => f a -> f b -- | The join function is the conventional monad join operator. It -- is used to remove one level of monadic structure, projecting its bound -- argument into the outer level. join :: Monad m => m (m a) -> m a -- | Direct MonadPlus equivalent of filter -- filter = (mfilter:: (a -> Bool) -> [a] -- -> [a] applicable to any MonadPlus, for example -- mfilter odd (Just 1) == Just 1 mfilter odd (Just 2) == -- Nothing mfilter :: MonadPlus m => (a -> Bool) -> m a -> m a -- | This generalizes the list-based filter function. filterM :: Applicative m => (a -> m Bool) -> [a] -> m [a] -- | The mapAndUnzipM function maps its first argument over a list, -- returning the result as a pair of lists. This function is mainly used -- with complicated data structures or a state-transforming monad. mapAndUnzipM :: Applicative m => (a -> m (b, c)) -> [a] -> m ([b], [c]) -- | The zipWithM function generalizes zipWith to arbitrary -- applicative functors. zipWithM :: Applicative m => (a -> b -> m c) -> [a] -> [b] -> m [c] -- | zipWithM_ is the extension of zipWithM which ignores the -- final result. zipWithM_ :: Applicative m => (a -> b -> m c) -> [a] -> [b] -> m () -- | The foldM function is analogous to foldl, except that -- its result is encapsulated in a monad. Note that foldM works -- from left-to-right over the list arguments. This could be an issue -- where (>>) and the `folded function' are not -- commutative. -- --
-- foldM f a1 [x1, x2, ..., xm] ---- -- == -- --
-- do -- a2 <- f a1 x1 -- a3 <- f a2 x2 -- ... -- f am xm ---- -- If right-to-left evaluation is required, the input list should be -- reversed. -- -- Note: foldM is the same as foldlM foldM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b -- | Like foldM, but discards the result. foldM_ :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m () -- | replicateM n act performs the action n times, -- gathering the results. replicateM :: Applicative m => Int -> m a -> m [a] -- | Like replicateM, but discards the result. replicateM_ :: Applicative m => Int -> m a -> m () concatMapM :: Monad m => (a -> m [b]) -> [a] -> m [b] -- | guard b is pure () if b is -- True, and empty if b is False. guard :: Alternative f => Bool -> f () -- | Conditional execution of Applicative expressions. For example, -- --
-- when debug (putStrLn "Debugging") ---- -- will output the string Debugging if the Boolean value -- debug is True, and otherwise do nothing. when :: Applicative f => Bool -> f () -> f () -- | The reverse of when. unless :: Applicative f => Bool -> f () -> f () -- | Promote a function to a monad. liftM :: Monad m => (a1 -> r) -> m a1 -> m r -- | Promote a function to a monad, scanning the monadic arguments from -- left to right. For example, -- --
-- liftM2 (+) [0,1] [0,2] = [0,2,1,3] -- liftM2 (+) (Just 1) Nothing = Nothing --liftM2 :: Monad m => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r -- | Promote a function to a monad, scanning the monadic arguments from -- left to right (cf. liftM2). liftM3 :: Monad m => (a1 -> a2 -> a3 -> r) -> m a1 -> m a2 -> m a3 -> m r -- | Promote a function to a monad, scanning the monadic arguments from -- left to right (cf. liftM2). liftM4 :: Monad m => (a1 -> a2 -> a3 -> a4 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m r -- | Promote a function to a monad, scanning the monadic arguments from -- left to right (cf. liftM2). liftM5 :: Monad m => (a1 -> a2 -> a3 -> a4 -> a5 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m a5 -> m r liftM' :: Monad m => (a -> b) -> m a -> m b liftM2' :: (Monad m) => (a -> b -> c) -> m a -> m b -> m c -- | In many situations, the liftM operations can be replaced by -- uses of ap, which promotes function application. -- --
-- return f `ap` x1 `ap` ... `ap` xn ---- -- is equivalent to -- --
-- liftMn f x1 x2 ... xn --ap :: Monad m => m (a -> b) -> m a -> m b (<$!>) :: Monad m => (a -> b) -> m a -> m b module Panic -- | Uncatchable exceptions thrown and never caught. data FatalError FatalError :: Text -> FatalError [msg] :: FatalError -> Text panic :: Text -> a instance GHC.Show.Show Panic.FatalError instance GHC.Exception.Exception Panic.FatalError module Show class Print a putStr :: (Print a, MonadIO m) => a -> m () putStrLn :: (Print a, MonadIO m) => a -> m () putText :: MonadIO m => Text -> m () putLText :: MonadIO m => Text -> m () instance Show.Print Data.Text.Internal.Text instance Show.Print Data.Text.Internal.Lazy.Text instance Show.Print Data.ByteString.Internal.ByteString instance Show.Print Data.ByteString.Lazy.Internal.ByteString instance Show.Print [GHC.Types.Char] module Debug undefined :: a -- | Warning: error remains in code error :: Text -> a -- | Warning: trace remains in code trace :: Print b => b -> a -> a -- | Warning: traceM remains in code traceM :: (Monad m) => Text -> m () -- | Warning: traceM remains in code traceId :: Text -> Text -- | Warning: traceIO remains in code traceIO :: Print b => b -> a -> IO a -- | Warning: traceShow remains in code traceShow :: Show a => a -> b -> b -- | Warning: traceShowId remains in code traceShowId :: Show a => a -> a -- | Warning: traceShowM remains in code traceShowM :: (Show a, Monad m) => a -> m () notImplemented :: a module Unsafe unsafeHead :: [a] -> a unsafeTail :: [a] -> [a] unsafeInit :: [a] -> [a] unsafeLast :: [a] -> a unsafeFromJust :: Maybe a -> a unsafeIndex :: [a] -> Int -> a unsafeThrow :: Exception e => e -> a module Applicative orAlt :: (Alternative f, Monoid a) => f a -> f a orEmpty :: Alternative f => Bool -> a -> f a eitherA :: (Alternative f) => f a -> f b -> f (Either a b) purer :: (Applicative f, Applicative g) => a -> f (g a) liftAA2 :: (Applicative f, Applicative g) => (a -> b -> c) -> f (g a) -> f (g b) -> f (g c) (<<*>>) :: (Applicative f, Applicative g) => f (g (a -> b)) -> f (g a) -> f (g b) module Protolude identity :: a -> a map :: Functor f => (a -> b) -> f a -> f b (&) :: a -> (a -> b) -> b infixl 1 & uncons :: [a] -> Maybe (a, [a]) unsnoc :: [x] -> Maybe ([x], x) applyN :: Int -> (a -> a) -> a -> a print :: (MonadIO m, Show a) => a -> m () throwIO :: (MonadIO m, Exception e) => e -> m a throwTo :: (MonadIO m, Exception e) => ThreadId -> e -> m () foreach :: Functor f => f a -> (a -> b) -> f b show :: (Show a, StringConv String b) => a -> b pass :: Applicative f => f () guarded :: (Alternative f) => (a -> Bool) -> a -> f a guardedA :: (Functor f, Alternative t) => (a -> f Bool) -> a -> f (t a) type LText = Text type LByteString = ByteString