{-# LANGUAGE ConstrainedClassMethods #-}
{-# LANGUAGE CPP                     #-}
{-# LANGUAGE DefaultSignatures       #-}
{-# LANGUAGE DerivingStrategies      #-}
{-# LANGUAGE FlexibleContexts        #-}
{-# LANGUAGE FlexibleInstances       #-}
{-# LANGUAGE GADTs                   #-}
{-# LANGUAGE TypeFamilies            #-}
{-# LANGUAGE TypeOperators           #-}
{-# LANGUAGE UndecidableInstances    #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
-- | Type classes mirroring standard typeclasses, but working with monomorphic containers.
--
-- The motivation is that some commonly used data types (i.e., 'ByteString' and
-- 'Text') do not allow for instances of typeclasses like 'Functor' and
-- 'Foldable', since they are monomorphic structures. This module allows both
-- monomorphic and polymorphic data types to be instances of the same
-- typeclasses.
--
-- All of the laws for the polymorphic typeclasses apply to their monomorphic
-- cousins. Thus, even though a 'MonoFunctor' instance for 'Set' could
-- theoretically be defined, it is omitted since it could violate the functor
-- law of @'omap' f . 'omap' g = 'omap' (f . g)@.
--
-- Note that all typeclasses have been prefixed with @Mono@, and functions have
-- been prefixed with @o@. The mnemonic for @o@ is "only one", or alternatively
-- \"it's mono, but m is overused in Haskell, so we'll use the second letter
-- instead.\" (Agreed, it's not a great mangling scheme, input is welcome!)
module Data.MonoTraversable where

import           Control.Applicative
import           Control.Category
import           Control.Monad        (Monad (..))
import qualified Data.ByteString      as S
import qualified Data.ByteString.Lazy as L
import qualified Data.Foldable        as F
import           Data.Functor
import           Data.Maybe           (fromMaybe)
import           Data.Monoid (Monoid (..), Any (..), All (..))
import           Data.Proxy
import qualified Data.Text            as T
import qualified Data.Text.Lazy       as TL
import           Data.Traversable
import           Data.Word            (Word8)
import Data.Int (Int, Int64)
import           GHC.Exts             (build)
import           GHC.Generics         ((:.:), (:*:), (:+:)(..), K1(..), M1(..), Par1(..), Rec1(..), U1(..), V1)
import           Prelude              (Bool (..), const, Char, flip, IO, Maybe (..), Either (..),
                                       (+), Integral, Ordering (..), compare, fromIntegral, Num, (>=),
                                       (==), seq, otherwise, Eq, Ord, (-), (*))
import qualified Prelude
import qualified Data.ByteString.Internal as Unsafe
import qualified Foreign.ForeignPtr.Unsafe as Unsafe
import Foreign.Ptr (plusPtr)
import Foreign.ForeignPtr (touchForeignPtr)
import Foreign.Storable (peek)
import Control.Arrow (Arrow)
import Data.Tree (Tree (..))
import Data.Sequence (Seq, ViewL (..), ViewR (..))
import qualified Data.Sequence as Seq
import Data.IntMap (IntMap)
import Data.IntSet (IntSet)
import qualified Data.List as List
import Data.List.NonEmpty (NonEmpty)
import Data.Functor.Identity (Identity)
import Data.Map (Map)
import qualified Data.Map.Strict as Map
import Data.HashMap.Strict (HashMap)
import Data.Vector (Vector)
import Control.Monad.Trans.Maybe (MaybeT (..))
#if !MIN_VERSION_transformers(0,6,0)
import Control.Monad.Trans.List (ListT)
#endif
import Control.Monad.Trans.Writer (WriterT)
import qualified Control.Monad.Trans.Writer.Strict as Strict (WriterT)
import Control.Monad.Trans.State (StateT(..))
import qualified Control.Monad.Trans.State.Strict as Strict (StateT(..))
import Control.Monad.Trans.RWS (RWST(..))
import qualified Control.Monad.Trans.RWS.Strict as Strict (RWST(..))
import Control.Monad.Trans.Reader (ReaderT)
import Control.Monad.Trans.Cont (ContT)
import Data.Functor.Compose (Compose)
import Data.Functor.Product (Product)
import Data.Set (Set)
import qualified Data.Set as Set
import Data.HashSet (HashSet)
import qualified Data.HashSet as HashSet
import Data.Hashable (Hashable)
import qualified Data.Vector as V
import qualified Data.Vector.Unboxed as U
import qualified Data.Vector.Storable as VS
import qualified Data.IntSet as IntSet
import Data.Semigroup
  ( Semigroup
-- Option has been removed in base-4.16 (GHC 9.2)
#if !MIN_VERSION_base(4,16,0)
  , Option (..)
#endif
  , Arg
  )
import qualified Data.ByteString.Unsafe as SU
import Control.Monad.Trans.Identity (IdentityT)

-- | Type family for getting the type of the elements
-- of a monomorphic container.
type family Element mono
type instance Element S.ByteString = Word8
type instance Element L.ByteString = Word8
type instance Element T.Text = Char
type instance Element TL.Text = Char
type instance Element [a] = a
type instance Element (IO a) = a
type instance Element (ZipList a) = a
type instance Element (Maybe a) = a
type instance Element (Tree a) = a
type instance Element (Seq a) = a
type instance Element (ViewL a) = a
type instance Element (ViewR a) = a
type instance Element (IntMap a) = a
type instance Element IntSet = Int
#if !MIN_VERSION_base(4,16,0)
type instance Element (Option a) = a
#endif
type instance Element (NonEmpty a) = a
type instance Element (Identity a) = a
type instance Element (r -> a) = a
type instance Element (Either a b) = b
type instance Element (a, b) = b
type instance Element (Const m a) = a
type instance Element (WrappedMonad m a) = a
type instance Element (Map k v) = v
type instance Element (HashMap k v) = v
type instance Element (Set e) = e
type instance Element (HashSet e) = e
type instance Element (Vector a) = a
type instance Element (WrappedArrow a b c) = c
type instance Element (MaybeT m a) = a
#if !MIN_VERSION_transformers(0,6,0)
type instance Element (ListT m a) = a
#endif
type instance Element (IdentityT m a) = a
type instance Element (WriterT w m a) = a
type instance Element (Strict.WriterT w m a) = a
type instance Element (StateT s m a) = a
type instance Element (Strict.StateT s m a) = a
type instance Element (RWST r w s m a) = a
type instance Element (Strict.RWST r w s m a) = a
type instance Element (ReaderT r m a) = a
type instance Element (ContT r m a) = a
type instance Element (Compose f g a) = a
type instance Element (Product f g a) = a
type instance Element (U.Vector a) = a
type instance Element (VS.Vector a) = a
type instance Element (Arg a b) = b
type instance Element ((f :.: g) a) = a
type instance Element ((f :*: g) a) = a
type instance Element ((f :+: g) a) = a
type instance Element (K1 i c a)    = a
type instance Element (M1 i c f a)  = a
type instance Element (Rec1 f a)    = a
type instance Element (Par1 a)      = a
type instance Element (U1 a)        = a
type instance Element (V1 a)        = a
type instance Element (Proxy a)     = a

-- | Monomorphic containers that can be mapped over.
class MonoFunctor mono where
    -- | Map over a monomorphic container
    omap :: (Element mono -> Element mono) -> mono -> mono
    default omap :: (Functor f, Element (f a) ~ a, f a ~ mono)
                 => (Element mono -> Element mono) -> mono -> mono
    omap = (Element mono -> Element mono) -> mono -> mono
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap
    {-# INLINE omap #-}

instance MonoFunctor S.ByteString where
    omap :: (Element ByteString -> Element ByteString)
-> ByteString -> ByteString
omap = (Word8 -> Word8) -> ByteString -> ByteString
(Element ByteString -> Element ByteString)
-> ByteString -> ByteString
S.map
    {-# INLINE omap #-}
instance MonoFunctor L.ByteString where
    omap :: (Element ByteString -> Element ByteString)
-> ByteString -> ByteString
omap = (Word8 -> Word8) -> ByteString -> ByteString
(Element ByteString -> Element ByteString)
-> ByteString -> ByteString
L.map
    {-# INLINE omap #-}
instance MonoFunctor T.Text where
    omap :: (Element Text -> Element Text) -> Text -> Text
omap = (Char -> Char) -> Text -> Text
(Element Text -> Element Text) -> Text -> Text
T.map
    {-# INLINE omap #-}
instance MonoFunctor TL.Text where
    omap :: (Element Text -> Element Text) -> Text -> Text
omap = (Char -> Char) -> Text -> Text
(Element Text -> Element Text) -> Text -> Text
TL.map
    {-# INLINE omap #-}
instance MonoFunctor [a]
instance MonoFunctor (IO a)
instance MonoFunctor (ZipList a)
instance MonoFunctor (Maybe a)
instance MonoFunctor (Tree a)
instance MonoFunctor (Seq a)
instance MonoFunctor (ViewL a)
instance MonoFunctor (ViewR a)
instance MonoFunctor (IntMap a)
#if !MIN_VERSION_base(4,16,0)
instance MonoFunctor (Option a)
#endif
instance MonoFunctor (NonEmpty a)
instance MonoFunctor (Identity a)
instance MonoFunctor (r -> a)
instance MonoFunctor (Either a b)
instance MonoFunctor (a, b)
instance MonoFunctor (Const m a)
instance Monad m => MonoFunctor (WrappedMonad m a)
instance MonoFunctor (Map k v)
instance MonoFunctor (HashMap k v)
instance MonoFunctor (Vector a)
instance MonoFunctor (Arg a b)
instance Arrow a => MonoFunctor (WrappedArrow a b c)
instance Functor m => MonoFunctor (MaybeT m a)
#if !MIN_VERSION_transformers(0,6,0)
instance Functor m => MonoFunctor (ListT m a)
#endif
instance Functor m => MonoFunctor (IdentityT m a)
instance Functor m => MonoFunctor (WriterT w m a)
instance Functor m => MonoFunctor (Strict.WriterT w m a)
instance Functor m => MonoFunctor (StateT s m a)
instance Functor m => MonoFunctor (Strict.StateT s m a)
instance Functor m => MonoFunctor (RWST r w s m a)
instance Functor m => MonoFunctor (Strict.RWST r w s m a)
instance Functor m => MonoFunctor (ReaderT r m a)
instance Functor m => MonoFunctor (ContT r m a)
instance (Functor f, Functor g) => MonoFunctor (Compose f g a)
instance (Functor f, Functor g) => MonoFunctor (Product f g a)
-- | @since 1.0.11.0
instance (Functor f, Functor g) => MonoFunctor ((f :.: g) a)
-- | @since 1.0.11.0
instance (Functor f, Functor g) => MonoFunctor ((f :*: g) a)
-- | @since 1.0.11.0
instance (Functor f, Functor g) => MonoFunctor ((f :+: g) a)
-- | @since 1.0.11.0
instance MonoFunctor (K1 i c a)
-- | @since 1.0.11.0
instance Functor f => MonoFunctor (M1 i c f a)
-- | @since 1.0.11.0
instance Functor f => MonoFunctor (Rec1 f a)
-- | @since 1.0.11.0
instance MonoFunctor (Par1 a)
-- | @since 1.0.11.0
instance MonoFunctor (U1 a)
-- | @since 1.0.11.0
instance MonoFunctor (V1 a)
-- | @since 1.0.11.0
instance MonoFunctor (Proxy a)
instance U.Unbox a => MonoFunctor (U.Vector a) where
    omap :: (Element (Vector a) -> Element (Vector a)) -> Vector a -> Vector a
omap = (Element (Vector a) -> Element (Vector a)) -> Vector a -> Vector a
forall a b. (Unbox a, Unbox b) => (a -> b) -> Vector a -> Vector b
U.map
    {-# INLINE omap #-}
instance VS.Storable a => MonoFunctor (VS.Vector a) where
    omap :: (Element (Vector a) -> Element (Vector a)) -> Vector a -> Vector a
omap = (Element (Vector a) -> Element (Vector a)) -> Vector a -> Vector a
forall a b.
(Storable a, Storable b) =>
(a -> b) -> Vector a -> Vector b
VS.map
    {-# INLINE omap #-}

-- | @'replaceElem' old new@ replaces all @old@ elements with @new@.
--
-- @since 1.0.1
replaceElem :: (MonoFunctor mono, Eq (Element mono)) => Element mono -> Element mono -> mono -> mono
replaceElem :: Element mono -> Element mono -> mono -> mono
replaceElem Element mono
old Element mono
new = (Element mono -> Element mono) -> mono -> mono
forall mono.
MonoFunctor mono =>
(Element mono -> Element mono) -> mono -> mono
omap (\Element mono
x -> if Element mono
x Element mono -> Element mono -> Bool
forall a. Eq a => a -> a -> Bool
== Element mono
old then Element mono
new else Element mono
x)

{-# INLINE [0] replaceElem #-}
{-# RULES "strict Text replaceElem" replaceElem = replaceElemStrictText #-}
replaceElemStrictText :: Char -> Char -> T.Text -> T.Text
replaceElemStrictText :: Char -> Char -> Text -> Text
replaceElemStrictText Char
old Char
new = Text -> Text -> Text -> Text
T.replace (Char -> Text
T.singleton Char
old) (Char -> Text
T.singleton Char
new)
{-# RULES "lazy Text replaceElem" replaceElem = replaceElemLazyText #-}
replaceElemLazyText :: Char -> Char -> TL.Text -> TL.Text
replaceElemLazyText :: Char -> Char -> Text -> Text
replaceElemLazyText Char
old Char
new = Text -> Text -> Text -> Text
TL.replace (Char -> Text
TL.singleton Char
old) (Char -> Text
TL.singleton Char
new)


-- | Monomorphic containers that can be folded.
class MonoFoldable mono where
    -- | Map each element of a monomorphic container to a 'Monoid'
    -- and combine the results.
    ofoldMap :: Monoid m => (Element mono -> m) -> mono -> m
    default ofoldMap :: (t a ~ mono, a ~ Element (t a), F.Foldable t, Monoid m) => (Element mono -> m) -> mono -> m
    ofoldMap = (Element mono -> m) -> mono -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
F.foldMap
    {-# INLINE ofoldMap #-}

    -- | Right-associative fold of a monomorphic container.
    ofoldr :: (Element mono -> b -> b) -> b -> mono -> b
    default ofoldr :: (t a ~ mono, a ~ Element (t a), F.Foldable t) => (Element mono -> b -> b) -> b -> mono -> b
    ofoldr = (Element mono -> b -> b) -> b -> mono -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
F.foldr
    {-# INLINE ofoldr #-}

    -- | Strict left-associative fold of a monomorphic container.
    ofoldl' :: (a -> Element mono -> a) -> a -> mono -> a
    default ofoldl' :: (t b ~ mono, b ~ Element (t b), F.Foldable t) => (a -> Element mono -> a) -> a -> mono -> a
    ofoldl' = (a -> Element mono -> a) -> a -> mono -> a
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
F.foldl'
    {-# INLINE ofoldl' #-}

    -- | Convert a monomorphic container to a list.
    otoList :: mono -> [Element mono]
    otoList mono
t = (forall b. (Element mono -> b -> b) -> b -> b) -> [Element mono]
forall a. (forall b. (a -> b -> b) -> b -> b) -> [a]
build (\ Element mono -> b -> b
mono b
n -> (Element mono -> b -> b) -> b -> mono -> b
forall mono b.
MonoFoldable mono =>
(Element mono -> b -> b) -> b -> mono -> b
ofoldr Element mono -> b -> b
mono b
n mono
t)
    {-# INLINE otoList #-}

    -- | Are __all__ of the elements in a monomorphic container
    -- converted to booleans 'True'?
    oall :: (Element mono -> Bool) -> mono -> Bool
    oall Element mono -> Bool
f = All -> Bool
getAll (All -> Bool) -> (mono -> All) -> mono -> Bool
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (Element mono -> All) -> mono -> All
forall mono m.
(MonoFoldable mono, Monoid m) =>
(Element mono -> m) -> mono -> m
ofoldMap (Bool -> All
All (Bool -> All) -> (Element mono -> Bool) -> Element mono -> All
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Element mono -> Bool
f)
    {-# INLINE oall #-}

    -- | Are __any__ of the elements in a monomorphic container
    -- converted to booleans 'True'?
    oany :: (Element mono -> Bool) -> mono -> Bool
    oany Element mono -> Bool
f = Any -> Bool
getAny (Any -> Bool) -> (mono -> Any) -> mono -> Bool
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (Element mono -> Any) -> mono -> Any
forall mono m.
(MonoFoldable mono, Monoid m) =>
(Element mono -> m) -> mono -> m
ofoldMap (Bool -> Any
Any (Bool -> Any) -> (Element mono -> Bool) -> Element mono -> Any
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Element mono -> Bool
f)
    {-# INLINE oany #-}

    -- | Is the monomorphic container empty?
    onull :: mono -> Bool
    onull = (Element mono -> Bool) -> mono -> Bool
forall mono.
MonoFoldable mono =>
(Element mono -> Bool) -> mono -> Bool
oall (Bool -> Element mono -> Bool
forall a b. a -> b -> a
const Bool
False)
    {-# INLINE onull #-}

    -- | Length of a monomorphic container, returns a 'Int'.
    olength :: mono -> Int
    olength = (Int -> Element mono -> Int) -> Int -> mono -> Int
forall mono a.
MonoFoldable mono =>
(a -> Element mono -> a) -> a -> mono -> a
ofoldl' (\Int
i Element mono
_ -> Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Int
0
    {-# INLINE olength #-}

    -- | Length of a monomorphic container, returns a 'Int64'.
    olength64 :: mono -> Int64
    olength64 = (Int64 -> Element mono -> Int64) -> Int64 -> mono -> Int64
forall mono a.
MonoFoldable mono =>
(a -> Element mono -> a) -> a -> mono -> a
ofoldl' (\Int64
i Element mono
_ -> Int64
i Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+ Int64
1) Int64
0
    {-# INLINE olength64 #-}

    -- | Compare the length of a monomorphic container and a given number.
    ocompareLength :: Integral i => mono -> i -> Ordering
    -- Basic implementation using length for most instance. See the list
    -- instance below for support for infinite structures. Arguably, that
    -- should be the default instead of this.
    ocompareLength mono
c0 i
i0 = mono -> Int
forall mono. MonoFoldable mono => mono -> Int
olength mono
c0 Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` i -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral i
i0
    {-# INLINE ocompareLength #-}

    -- | Map each element of a monomorphic container to an action,
    -- evaluate these actions from left to right, and ignore the results.
    otraverse_ :: Applicative f => (Element mono -> f b) -> mono -> f ()
    otraverse_ Element mono -> f b
f = (Element mono -> f () -> f ()) -> f () -> mono -> f ()
forall mono b.
MonoFoldable mono =>
(Element mono -> b -> b) -> b -> mono -> b
ofoldr (f b -> f () -> f ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
(*>) (f b -> f () -> f ())
-> (Element mono -> f b) -> Element mono -> f () -> f ()
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Element mono -> f b
f) (() -> f ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
    {-# INLINE otraverse_ #-}

    -- | 'ofor_' is 'otraverse_' with its arguments flipped.
    ofor_ :: Applicative f => mono -> (Element mono -> f b) -> f ()
    ofor_ = ((Element mono -> f b) -> mono -> f ())
-> mono -> (Element mono -> f b) -> f ()
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Element mono -> f b) -> mono -> f ()
forall mono (f :: * -> *) b.
(MonoFoldable mono, Applicative f) =>
(Element mono -> f b) -> mono -> f ()
otraverse_
    {-# INLINE ofor_ #-}

    -- | Map each element of a monomorphic container to a monadic action,
    -- evaluate these actions from left to right, and ignore the results.
    omapM_ :: Applicative m => (Element mono -> m ()) -> mono -> m ()
    omapM_ = (Element mono -> m ()) -> mono -> m ()
forall mono (f :: * -> *) b.
(MonoFoldable mono, Applicative f) =>
(Element mono -> f b) -> mono -> f ()
otraverse_
    {-# INLINE omapM_ #-}

    -- | 'oforM_' is 'omapM_' with its arguments flipped.
    oforM_ :: Applicative m => mono -> (Element mono -> m ()) -> m ()
    oforM_ = ((Element mono -> m ()) -> mono -> m ())
-> mono -> (Element mono -> m ()) -> m ()
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Element mono -> m ()) -> mono -> m ()
forall mono (m :: * -> *).
(MonoFoldable mono, Applicative m) =>
(Element mono -> m ()) -> mono -> m ()
omapM_
    {-# INLINE oforM_ #-}

    -- | Monadic fold over the elements of a monomorphic container, associating to the left.
    ofoldlM :: Monad m => (a -> Element mono -> m a) -> a -> mono -> m a
    ofoldlM a -> Element mono -> m a
f a
z0 mono
xs = (Element mono -> (a -> m a) -> a -> m a)
-> (a -> m a) -> mono -> a -> m a
forall mono b.
MonoFoldable mono =>
(Element mono -> b -> b) -> b -> mono -> b
ofoldr Element mono -> (a -> m a) -> a -> m a
f' a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return mono
xs a
z0
      where f' :: Element mono -> (a -> m a) -> a -> m a
f' Element mono
x a -> m a
k a
z = a -> Element mono -> m a
f a
z Element mono
x m a -> (a -> m a) -> m a
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= a -> m a
k
    {-# INLINE ofoldlM #-}

    -- | Map each element of a monomorphic container to a semigroup,
    -- and combine the results.
    --
    -- Note: this is a partial function. On an empty 'MonoFoldable', it will
    -- throw an exception.
    --
    -- /See 'Data.NonNull.ofoldMap1' from "Data.NonNull" for a total version of this function./
    ofoldMap1Ex :: Semigroup m => (Element mono -> m) -> mono -> m
    ofoldMap1Ex Element mono -> m
f = m -> Maybe m -> m
forall a. a -> Maybe a -> a
fromMaybe ([Char] -> m
forall a. HasCallStack => [Char] -> a
Prelude.error [Char]
"Data.MonoTraversable.ofoldMap1Ex")
                       (Maybe m -> m) -> (mono -> Maybe m) -> mono -> m
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (Element mono -> Maybe m) -> mono -> Maybe m
forall mono m.
(MonoFoldable mono, Monoid m) =>
(Element mono -> m) -> mono -> m
ofoldMap (m -> Maybe m
forall a. a -> Maybe a
Just (m -> Maybe m) -> (Element mono -> m) -> Element mono -> Maybe m
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Element mono -> m
f)

    -- | Right-associative fold of a monomorphic container with no base element.
    --
    -- Note: this is a partial function. On an empty 'MonoFoldable', it will
    -- throw an exception.
    --
    -- /See 'Data.NonNull.ofoldr1' from "Data.NonNull" for a total version of this function./
    ofoldr1Ex :: (Element mono -> Element mono -> Element mono) -> mono -> Element mono
    default ofoldr1Ex :: (t a ~ mono, a ~ Element (t a), F.Foldable t)
                      => (Element mono -> Element mono -> Element mono) -> mono -> Element mono
    ofoldr1Ex = (Element mono -> Element mono -> Element mono)
-> mono -> Element mono
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
F.foldr1
    {-# INLINE ofoldr1Ex #-}

    -- | Strict left-associative fold of a monomorphic container with no base
    -- element.
    --
    -- Note: this is a partial function. On an empty 'MonoFoldable', it will
    -- throw an exception.
    --
    -- /See 'Data.NonNull.ofoldl1'' from "Data.NonNull" for a total version of this function./
    ofoldl1Ex' :: (Element mono -> Element mono -> Element mono) -> mono -> Element mono
    default ofoldl1Ex' :: (t a ~ mono, a ~ Element (t a), F.Foldable t)
                       => (Element mono -> Element mono -> Element mono) -> mono -> Element mono
    ofoldl1Ex' = (Element mono -> Element mono -> Element mono)
-> mono -> Element mono
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
F.foldl1
    {-# INLINE ofoldl1Ex' #-}

    -- | Get the first element of a monomorphic container.
    --
    -- Note: this is a partial function. On an empty 'MonoFoldable', it will
    -- throw an exception.
    --
    -- /See 'Data.NonNull.head' from "Data.NonNull" for a total version of this function./
    headEx :: mono -> Element mono
    headEx = (Element mono -> Element mono -> Element mono)
-> Element mono -> mono -> Element mono
forall mono b.
MonoFoldable mono =>
(Element mono -> b -> b) -> b -> mono -> b
ofoldr Element mono -> Element mono -> Element mono
forall a b. a -> b -> a
const ([Char] -> Element mono
forall a. HasCallStack => [Char] -> a
Prelude.error [Char]
"Data.MonoTraversable.headEx: empty")
    {-# INLINE headEx #-}

    -- | Get the last element of a monomorphic container.
    --
    -- Note: this is a partial function. On an empty 'MonoFoldable', it will
    -- throw an exception.
    --
    -- /See 'Data.NonNull.last' from "Data.NonNull" for a total version of this function./
    lastEx :: mono -> Element mono
    lastEx = (Element mono -> Element mono -> Element mono)
-> mono -> Element mono
forall mono.
MonoFoldable mono =>
(Element mono -> Element mono -> Element mono)
-> mono -> Element mono
ofoldl1Ex' ((Element mono -> Element mono -> Element mono)
-> Element mono -> Element mono -> Element mono
forall a b c. (a -> b -> c) -> b -> a -> c
flip Element mono -> Element mono -> Element mono
forall a b. a -> b -> a
const)
    {-# INLINE lastEx #-}

    -- | Equivalent to 'headEx'.
    unsafeHead :: mono -> Element mono
    unsafeHead = mono -> Element mono
forall mono. MonoFoldable mono => mono -> Element mono
headEx
    {-# INLINE unsafeHead #-}

    -- | Equivalent to 'lastEx'.
    unsafeLast :: mono -> Element mono
    unsafeLast = mono -> Element mono
forall mono. MonoFoldable mono => mono -> Element mono
lastEx
    {-# INLINE unsafeLast #-}

    -- | Get the maximum element of a monomorphic container,
    -- using a supplied element ordering function.
    --
    -- Note: this is a partial function. On an empty 'MonoFoldable', it will
    -- throw an exception.
    --
    -- /See 'Data.NonNull.maximiumBy' from "Data.NonNull" for a total version of this function./
    maximumByEx :: (Element mono -> Element mono -> Ordering) -> mono -> Element mono
    maximumByEx Element mono -> Element mono -> Ordering
f =
        (Element mono -> Element mono -> Element mono)
-> mono -> Element mono
forall mono.
MonoFoldable mono =>
(Element mono -> Element mono -> Element mono)
-> mono -> Element mono
ofoldl1Ex' Element mono -> Element mono -> Element mono
go
      where
        go :: Element mono -> Element mono -> Element mono
go Element mono
x Element mono
y =
            case Element mono -> Element mono -> Ordering
f Element mono
x Element mono
y of
                Ordering
LT -> Element mono
y
                Ordering
_  -> Element mono
x
    {-# INLINE maximumByEx #-}

    -- | Get the minimum element of a monomorphic container,
    -- using a supplied element ordering function.
    --
    -- Note: this is a partial function. On an empty 'MonoFoldable', it will
    -- throw an exception.
    --
    -- /See 'Data.NonNull.minimumBy' from "Data.NonNull" for a total version of this function./
    minimumByEx :: (Element mono -> Element mono -> Ordering) -> mono -> Element mono
    minimumByEx Element mono -> Element mono -> Ordering
f =
        (Element mono -> Element mono -> Element mono)
-> mono -> Element mono
forall mono.
MonoFoldable mono =>
(Element mono -> Element mono -> Element mono)
-> mono -> Element mono
ofoldl1Ex' Element mono -> Element mono -> Element mono
go
      where
        go :: Element mono -> Element mono -> Element mono
go Element mono
x Element mono
y =
            case Element mono -> Element mono -> Ordering
f Element mono
x Element mono
y of
                Ordering
GT -> Element mono
y
                Ordering
_  -> Element mono
x
    {-# INLINE minimumByEx #-}

    -- | Checks if the monomorphic container includes the supplied element.
    oelem :: Eq (Element mono) => Element mono -> mono -> Bool
    oelem Element mono
e = Element mono -> [Element mono] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
List.elem Element mono
e ([Element mono] -> Bool)
-> (mono -> [Element mono]) -> mono -> Bool
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. mono -> [Element mono]
forall mono. MonoFoldable mono => mono -> [Element mono]
otoList
    {-# INLINE [0] oelem #-}

    -- | Checks if the monomorphic container does not include the supplied element.
    onotElem :: Eq (Element mono) => Element mono -> mono -> Bool
    onotElem Element mono
e = Element mono -> [Element mono] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
List.notElem Element mono
e ([Element mono] -> Bool)
-> (mono -> [Element mono]) -> mono -> Bool
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. mono -> [Element mono]
forall mono. MonoFoldable mono => mono -> [Element mono]
otoList
    {-# INLINE [0] onotElem #-}

instance MonoFoldable S.ByteString where
    ofoldMap :: (Element ByteString -> m) -> ByteString -> m
ofoldMap Element ByteString -> m
f = (Element ByteString -> m -> m) -> m -> ByteString -> m
forall mono b.
MonoFoldable mono =>
(Element mono -> b -> b) -> b -> mono -> b
ofoldr (m -> m -> m
forall a. Monoid a => a -> a -> a
mappend (m -> m -> m) -> (Word8 -> m) -> Word8 -> m -> m
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Word8 -> m
Element ByteString -> m
f) m
forall a. Monoid a => a
mempty
    ofoldr :: (Element ByteString -> b -> b) -> b -> ByteString -> b
ofoldr = (Element ByteString -> b -> b) -> b -> ByteString -> b
forall a. (Word8 -> a -> a) -> a -> ByteString -> a
S.foldr
    ofoldl' :: (a -> Element ByteString -> a) -> a -> ByteString -> a
ofoldl' = (a -> Element ByteString -> a) -> a -> ByteString -> a
forall a. (a -> Word8 -> a) -> a -> ByteString -> a
S.foldl'
    otoList :: ByteString -> [Element ByteString]
otoList = ByteString -> [Word8]
ByteString -> [Element ByteString]
S.unpack
    oall :: (Element ByteString -> Bool) -> ByteString -> Bool
oall = (Word8 -> Bool) -> ByteString -> Bool
(Element ByteString -> Bool) -> ByteString -> Bool
S.all
    oany :: (Element ByteString -> Bool) -> ByteString -> Bool
oany = (Word8 -> Bool) -> ByteString -> Bool
(Element ByteString -> Bool) -> ByteString -> Bool
S.any
    onull :: ByteString -> Bool
onull = ByteString -> Bool
S.null
    olength :: ByteString -> Int
olength = ByteString -> Int
S.length
    oelem :: Element ByteString -> ByteString -> Bool
oelem = Word8 -> ByteString -> Bool
Element ByteString -> ByteString -> Bool
S.elem
    onotElem :: Element ByteString -> ByteString -> Bool
onotElem = Word8 -> ByteString -> Bool
Element ByteString -> ByteString -> Bool
S.notElem

    omapM_ :: (Element ByteString -> m ()) -> ByteString -> m ()
omapM_ Element ByteString -> m ()
f (Unsafe.PS ForeignPtr Word8
fptr Int
offset Int
len) = do
        let start :: Ptr Word8
start = ForeignPtr Word8 -> Ptr Word8
forall a. ForeignPtr a -> Ptr a
Unsafe.unsafeForeignPtrToPtr ForeignPtr Word8
fptr Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
offset
            end :: Ptr Word8
end = Ptr Word8
start Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
len
            loop :: Ptr Word8 -> m ()
loop Ptr Word8
ptr
                | Ptr Word8
ptr Ptr Word8 -> Ptr Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= Ptr Word8
end = IO () -> ()
forall a. IO a -> a
evil (ForeignPtr Word8 -> IO ()
forall a. ForeignPtr a -> IO ()
touchForeignPtr ForeignPtr Word8
fptr) () -> m () -> m ()
`seq`
                    () -> m ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
                | Bool
otherwise =
                    Element ByteString -> m ()
f (IO Word8 -> Word8
forall a. IO a -> a
evil (Ptr Word8 -> IO Word8
forall a. Storable a => Ptr a -> IO a
peek Ptr Word8
ptr)) m () -> m () -> m ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
                    Ptr Word8 -> m ()
loop (Ptr Word8
ptr Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
1)
        Ptr Word8 -> m ()
loop Ptr Word8
start
      where
#if MIN_VERSION_bytestring(0,10,6)
        evil :: IO a -> a
evil = IO a -> a
forall a. IO a -> a
Unsafe.accursedUnutterablePerformIO
#else
        evil = Unsafe.inlinePerformIO
#endif
        {-# INLINE evil #-}
    ofoldr1Ex :: (Element ByteString -> Element ByteString -> Element ByteString)
-> ByteString -> Element ByteString
ofoldr1Ex = (Word8 -> Word8 -> Word8) -> ByteString -> Word8
(Element ByteString -> Element ByteString -> Element ByteString)
-> ByteString -> Element ByteString
S.foldr1
    ofoldl1Ex' :: (Element ByteString -> Element ByteString -> Element ByteString)
-> ByteString -> Element ByteString
ofoldl1Ex' = (Word8 -> Word8 -> Word8) -> ByteString -> Word8
(Element ByteString -> Element ByteString -> Element ByteString)
-> ByteString -> Element ByteString
S.foldl1'
    headEx :: ByteString -> Element ByteString
headEx = ByteString -> Word8
ByteString -> Element ByteString
S.head
    lastEx :: ByteString -> Element ByteString
lastEx = ByteString -> Word8
ByteString -> Element ByteString
S.last
    unsafeHead :: ByteString -> Element ByteString
unsafeHead = ByteString -> Word8
ByteString -> Element ByteString
SU.unsafeHead
    {-# INLINE ofoldMap #-}
    {-# INLINE ofoldr #-}
    {-# INLINE ofoldl' #-}
    {-# INLINE otoList #-}
    {-# INLINE oall #-}
    {-# INLINE oany #-}
    {-# INLINE onull #-}
    {-# INLINE olength #-}
    {-# INLINE omapM_ #-}
    {-# INLINE ofoldr1Ex #-}
    {-# INLINE ofoldl1Ex' #-}
    {-# INLINE headEx #-}
    {-# INLINE lastEx #-}
    {-# INLINE unsafeHead #-}
    {-# INLINE oelem #-}
    {-# INLINE onotElem #-}
{-# RULES "strict ByteString: ofoldMap = concatMap" ofoldMap = S.concatMap #-}

instance MonoFoldable L.ByteString where
    ofoldMap :: (Element ByteString -> m) -> ByteString -> m
ofoldMap Element ByteString -> m
f = (Element ByteString -> m -> m) -> m -> ByteString -> m
forall mono b.
MonoFoldable mono =>
(Element mono -> b -> b) -> b -> mono -> b
ofoldr (m -> m -> m
forall a. Monoid a => a -> a -> a
mappend (m -> m -> m) -> (Word8 -> m) -> Word8 -> m -> m
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Word8 -> m
Element ByteString -> m
f) m
forall a. Monoid a => a
mempty
    ofoldr :: (Element ByteString -> b -> b) -> b -> ByteString -> b
ofoldr = (Element ByteString -> b -> b) -> b -> ByteString -> b
forall a. (Word8 -> a -> a) -> a -> ByteString -> a
L.foldr
    ofoldl' :: (a -> Element ByteString -> a) -> a -> ByteString -> a
ofoldl' = (a -> Element ByteString -> a) -> a -> ByteString -> a
forall a. (a -> Word8 -> a) -> a -> ByteString -> a
L.foldl'
    otoList :: ByteString -> [Element ByteString]
otoList = ByteString -> [Word8]
ByteString -> [Element ByteString]
L.unpack
    oall :: (Element ByteString -> Bool) -> ByteString -> Bool
oall = (Word8 -> Bool) -> ByteString -> Bool
(Element ByteString -> Bool) -> ByteString -> Bool
L.all
    oany :: (Element ByteString -> Bool) -> ByteString -> Bool
oany = (Word8 -> Bool) -> ByteString -> Bool
(Element ByteString -> Bool) -> ByteString -> Bool
L.any
    onull :: ByteString -> Bool
onull = ByteString -> Bool
L.null
    olength64 :: ByteString -> Int64
olength64 = ByteString -> Int64
L.length
    omapM_ :: (Element ByteString -> m ()) -> ByteString -> m ()
omapM_ Element ByteString -> m ()
f = (Element [ByteString] -> m ()) -> [ByteString] -> m ()
forall mono (m :: * -> *).
(MonoFoldable mono, Applicative m) =>
(Element mono -> m ()) -> mono -> m ()
omapM_ ((Element ByteString -> m ()) -> ByteString -> m ()
forall mono (m :: * -> *).
(MonoFoldable mono, Applicative m) =>
(Element mono -> m ()) -> mono -> m ()
omapM_ Element ByteString -> m ()
Element ByteString -> m ()
f) ([ByteString] -> m ())
-> (ByteString -> [ByteString]) -> ByteString -> m ()
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteString -> [ByteString]
L.toChunks
    ofoldr1Ex :: (Element ByteString -> Element ByteString -> Element ByteString)
-> ByteString -> Element ByteString
ofoldr1Ex = (Word8 -> Word8 -> Word8) -> ByteString -> Word8
(Element ByteString -> Element ByteString -> Element ByteString)
-> ByteString -> Element ByteString
L.foldr1
    ofoldl1Ex' :: (Element ByteString -> Element ByteString -> Element ByteString)
-> ByteString -> Element ByteString
ofoldl1Ex' = (Word8 -> Word8 -> Word8) -> ByteString -> Word8
(Element ByteString -> Element ByteString -> Element ByteString)
-> ByteString -> Element ByteString
L.foldl1'
    headEx :: ByteString -> Element ByteString
headEx = ByteString -> Word8
ByteString -> Element ByteString
L.head
    lastEx :: ByteString -> Element ByteString
lastEx = ByteString -> Word8
ByteString -> Element ByteString
L.last
    oelem :: Element ByteString -> ByteString -> Bool
oelem = Word8 -> ByteString -> Bool
Element ByteString -> ByteString -> Bool
L.elem
    onotElem :: Element ByteString -> ByteString -> Bool
onotElem = Word8 -> ByteString -> Bool
Element ByteString -> ByteString -> Bool
L.notElem

    {-# INLINE ofoldMap #-}
    {-# INLINE ofoldr #-}
    {-# INLINE ofoldl' #-}
    {-# INLINE otoList #-}
    {-# INLINE oall #-}
    {-# INLINE oany #-}
    {-# INLINE onull #-}
    {-# INLINE olength64 #-}
    {-# INLINE omapM_ #-}
    {-# INLINE ofoldr1Ex #-}
    {-# INLINE ofoldl1Ex' #-}
    {-# INLINE headEx #-}
    {-# INLINE lastEx #-}
    {-# INLINE oelem #-}
    {-# INLINE onotElem #-}
{-# RULES "lazy ByteString: ofoldMap = concatMap" ofoldMap = L.concatMap #-}

instance MonoFoldable T.Text where
    ofoldMap :: (Element Text -> m) -> Text -> m
ofoldMap Element Text -> m
f = (Element Text -> m -> m) -> m -> Text -> m
forall mono b.
MonoFoldable mono =>
(Element mono -> b -> b) -> b -> mono -> b
ofoldr (m -> m -> m
forall a. Monoid a => a -> a -> a
mappend (m -> m -> m) -> (Char -> m) -> Char -> m -> m
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Char -> m
Element Text -> m
f) m
forall a. Monoid a => a
mempty
    ofoldr :: (Element Text -> b -> b) -> b -> Text -> b
ofoldr = (Element Text -> b -> b) -> b -> Text -> b
forall a. (Char -> a -> a) -> a -> Text -> a
T.foldr
    ofoldl' :: (a -> Element Text -> a) -> a -> Text -> a
ofoldl' = (a -> Element Text -> a) -> a -> Text -> a
forall a. (a -> Char -> a) -> a -> Text -> a
T.foldl'
    otoList :: Text -> [Element Text]
otoList = Text -> [Char]
Text -> [Element Text]
T.unpack
    oall :: (Element Text -> Bool) -> Text -> Bool
oall = (Char -> Bool) -> Text -> Bool
(Element Text -> Bool) -> Text -> Bool
T.all
    oany :: (Element Text -> Bool) -> Text -> Bool
oany = (Char -> Bool) -> Text -> Bool
(Element Text -> Bool) -> Text -> Bool
T.any
    onull :: Text -> Bool
onull = Text -> Bool
T.null
    olength :: Text -> Int
olength = Text -> Int
T.length
    ofoldr1Ex :: (Element Text -> Element Text -> Element Text)
-> Text -> Element Text
ofoldr1Ex = (Char -> Char -> Char) -> Text -> Char
(Element Text -> Element Text -> Element Text)
-> Text -> Element Text
T.foldr1
    ofoldl1Ex' :: (Element Text -> Element Text -> Element Text)
-> Text -> Element Text
ofoldl1Ex' = (Char -> Char -> Char) -> Text -> Char
(Element Text -> Element Text -> Element Text)
-> Text -> Element Text
T.foldl1'
    headEx :: Text -> Element Text
headEx = Text -> Char
Text -> Element Text
T.head
    lastEx :: Text -> Element Text
lastEx = Text -> Char
Text -> Element Text
T.last
    {-# INLINE ofoldMap #-}
    {-# INLINE ofoldr #-}
    {-# INLINE ofoldl' #-}
    {-# INLINE otoList #-}
    {-# INLINE oall #-}
    {-# INLINE oany #-}
    {-# INLINE onull #-}
    {-# INLINE olength #-}
    {-# INLINE ofoldr1Ex #-}
    {-# INLINE ofoldl1Ex' #-}
    {-# INLINE headEx #-}
    {-# INLINE lastEx #-}
{-# RULES "strict Text: ofoldMap = concatMap" ofoldMap = T.concatMap #-}

instance MonoFoldable TL.Text where
    ofoldMap :: (Element Text -> m) -> Text -> m
ofoldMap Element Text -> m
f = (Element Text -> m -> m) -> m -> Text -> m
forall mono b.
MonoFoldable mono =>
(Element mono -> b -> b) -> b -> mono -> b
ofoldr (m -> m -> m
forall a. Monoid a => a -> a -> a
mappend (m -> m -> m) -> (Char -> m) -> Char -> m -> m
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Char -> m
Element Text -> m
f) m
forall a. Monoid a => a
mempty
    ofoldr :: (Element Text -> b -> b) -> b -> Text -> b
ofoldr = (Element Text -> b -> b) -> b -> Text -> b
forall a. (Char -> a -> a) -> a -> Text -> a
TL.foldr
    ofoldl' :: (a -> Element Text -> a) -> a -> Text -> a
ofoldl' = (a -> Element Text -> a) -> a -> Text -> a
forall a. (a -> Char -> a) -> a -> Text -> a
TL.foldl'
    otoList :: Text -> [Element Text]
otoList = Text -> [Char]
Text -> [Element Text]
TL.unpack
    oall :: (Element Text -> Bool) -> Text -> Bool
oall = (Char -> Bool) -> Text -> Bool
(Element Text -> Bool) -> Text -> Bool
TL.all
    oany :: (Element Text -> Bool) -> Text -> Bool
oany = (Char -> Bool) -> Text -> Bool
(Element Text -> Bool) -> Text -> Bool
TL.any
    onull :: Text -> Bool
onull = Text -> Bool
TL.null
    olength64 :: Text -> Int64
olength64 = Text -> Int64
TL.length
    ofoldr1Ex :: (Element Text -> Element Text -> Element Text)
-> Text -> Element Text
ofoldr1Ex = (Char -> Char -> Char) -> Text -> Char
(Element Text -> Element Text -> Element Text)
-> Text -> Element Text
TL.foldr1
    ofoldl1Ex' :: (Element Text -> Element Text -> Element Text)
-> Text -> Element Text
ofoldl1Ex' = (Char -> Char -> Char) -> Text -> Char
(Element Text -> Element Text -> Element Text)
-> Text -> Element Text
TL.foldl1'
    headEx :: Text -> Element Text
headEx = Text -> Char
Text -> Element Text
TL.head
    lastEx :: Text -> Element Text
lastEx = Text -> Char
Text -> Element Text
TL.last
    {-# INLINE ofoldMap #-}
    {-# INLINE ofoldr #-}
    {-# INLINE ofoldl' #-}
    {-# INLINE otoList #-}
    {-# INLINE oall #-}
    {-# INLINE oany #-}
    {-# INLINE onull #-}
    {-# INLINE ofoldr1Ex #-}
    {-# INLINE ofoldl1Ex' #-}
    {-# INLINE headEx #-}
    {-# INLINE lastEx #-}
{-# RULES "lazy Text: ofoldMap = concatMap" ofoldMap = TL.concatMap #-}

instance MonoFoldable IntSet where
    ofoldMap :: (Element IntSet -> m) -> IntSet -> m
ofoldMap Element IntSet -> m
f = (Element IntSet -> m -> m) -> m -> IntSet -> m
forall mono b.
MonoFoldable mono =>
(Element mono -> b -> b) -> b -> mono -> b
ofoldr (m -> m -> m
forall a. Monoid a => a -> a -> a
mappend (m -> m -> m) -> (Int -> m) -> Int -> m -> m
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int -> m
Element IntSet -> m
f) m
forall a. Monoid a => a
mempty
    ofoldr :: (Element IntSet -> b -> b) -> b -> IntSet -> b
ofoldr = (Element IntSet -> b -> b) -> b -> IntSet -> b
forall b. (Int -> b -> b) -> b -> IntSet -> b
IntSet.foldr
    ofoldl' :: (a -> Element IntSet -> a) -> a -> IntSet -> a
ofoldl' = (a -> Element IntSet -> a) -> a -> IntSet -> a
forall a. (a -> Int -> a) -> a -> IntSet -> a
IntSet.foldl'
    otoList :: IntSet -> [Element IntSet]
otoList = IntSet -> [Int]
IntSet -> [Element IntSet]
IntSet.toList
    onull :: IntSet -> Bool
onull = IntSet -> Bool
IntSet.null
    olength :: IntSet -> Int
olength = IntSet -> Int
IntSet.size
    ofoldr1Ex :: (Element IntSet -> Element IntSet -> Element IntSet)
-> IntSet -> Element IntSet
ofoldr1Ex Element IntSet -> Element IntSet -> Element IntSet
f = (Element [Int] -> Element [Int] -> Element [Int])
-> [Int] -> Element [Int]
forall mono.
MonoFoldable mono =>
(Element mono -> Element mono -> Element mono)
-> mono -> Element mono
ofoldr1Ex Element [Int] -> Element [Int] -> Element [Int]
Element IntSet -> Element IntSet -> Element IntSet
f ([Int] -> Int) -> (IntSet -> [Int]) -> IntSet -> Int
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. IntSet -> [Int]
IntSet.toList
    ofoldl1Ex' :: (Element IntSet -> Element IntSet -> Element IntSet)
-> IntSet -> Element IntSet
ofoldl1Ex' Element IntSet -> Element IntSet -> Element IntSet
f = (Element [Int] -> Element [Int] -> Element [Int])
-> [Int] -> Element [Int]
forall mono.
MonoFoldable mono =>
(Element mono -> Element mono -> Element mono)
-> mono -> Element mono
ofoldl1Ex' Element [Int] -> Element [Int] -> Element [Int]
Element IntSet -> Element IntSet -> Element IntSet
f ([Int] -> Int) -> (IntSet -> [Int]) -> IntSet -> Int
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. IntSet -> [Int]
IntSet.toList
    {-# INLINE ofoldMap #-}
    {-# INLINE ofoldr #-}
    {-# INLINE ofoldl' #-}
    {-# INLINE otoList #-}
    {-# INLINE onull #-}
    {-# INLINE olength #-}
    {-# INLINE ofoldr1Ex #-}
    {-# INLINE ofoldl1Ex' #-}
instance MonoFoldable [a] where
    otoList :: [a] -> [Element [a]]
otoList = [a] -> [Element [a]]
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
    {-# INLINE otoList #-}

    ocompareLength :: [a] -> i -> Ordering
ocompareLength [] i
i = i
0 i -> i -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` i
i
    ocompareLength (a
_:[a]
xs) i
i
        | i
i i -> i -> Bool
forall a. Ord a => a -> a -> Bool
Prelude.<= i
0 = Ordering
GT
        | Bool
otherwise = [a] -> i -> Ordering
forall mono i.
(MonoFoldable mono, Integral i) =>
mono -> i -> Ordering
ocompareLength [a]
xs (i
i i -> i -> i
forall a. Num a => a -> a -> a
- i
1)
instance MonoFoldable (Maybe a) where
    omapM_ :: (Element (Maybe a) -> m ()) -> Maybe a -> m ()
omapM_ Element (Maybe a) -> m ()
_ Maybe a
Nothing = () -> m ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
    omapM_ Element (Maybe a) -> m ()
f (Just a
x) = Element (Maybe a) -> m ()
f a
Element (Maybe a)
x
    {-# INLINE omapM_ #-}
instance MonoFoldable (Tree a)
instance MonoFoldable (Seq a) where
    headEx :: Seq a -> Element (Seq a)
headEx = (Seq a -> Int -> a) -> Int -> Seq a -> a
forall a b c. (a -> b -> c) -> b -> a -> c
flip Seq a -> Int -> a
forall a. Seq a -> Int -> a
Seq.index Int
0
    lastEx :: Seq a -> Element (Seq a)
lastEx Seq a
xs = Seq a -> Int -> a
forall a. Seq a -> Int -> a
Seq.index Seq a
xs (Seq a -> Int
forall a. Seq a -> Int
Seq.length Seq a
xs Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
    {-# INLINE headEx #-}
    {-# INLINE lastEx #-}
instance MonoFoldable (ViewL a)
instance MonoFoldable (ViewR a)
instance MonoFoldable (IntMap a)
#if !MIN_VERSION_base(4,16,0)
instance MonoFoldable (Option a)
#endif
instance MonoFoldable (NonEmpty a)
instance MonoFoldable (Identity a)
instance MonoFoldable (Map k v) where
    olength :: Map k v -> Int
olength = Map k v -> Int
forall k v. Map k v -> Int
Map.size
    {-# INLINE olength #-}
instance MonoFoldable (HashMap k v)
instance MonoFoldable (Vector a) where
    ofoldr :: (Element (Vector a) -> b -> b) -> b -> Vector a -> b
ofoldr = (Element (Vector a) -> b -> b) -> b -> Vector a -> b
forall a b. (a -> b -> b) -> b -> Vector a -> b
V.foldr
    ofoldl' :: (a -> Element (Vector a) -> a) -> a -> Vector a -> a
ofoldl' = (a -> Element (Vector a) -> a) -> a -> Vector a -> a
forall a b. (a -> b -> a) -> a -> Vector b -> a
V.foldl'
    otoList :: Vector a -> [Element (Vector a)]
otoList = Vector a -> [Element (Vector a)]
forall a. Vector a -> [a]
V.toList
    oall :: (Element (Vector a) -> Bool) -> Vector a -> Bool
oall = (Element (Vector a) -> Bool) -> Vector a -> Bool
forall a. (a -> Bool) -> Vector a -> Bool
V.all
    oany :: (Element (Vector a) -> Bool) -> Vector a -> Bool
oany = (Element (Vector a) -> Bool) -> Vector a -> Bool
forall a. (a -> Bool) -> Vector a -> Bool
V.any
    onull :: Vector a -> Bool
onull = Vector a -> Bool
forall a. Vector a -> Bool
V.null
    olength :: Vector a -> Int
olength = Vector a -> Int
forall a. Vector a -> Int
V.length
    ofoldr1Ex :: (Element (Vector a) -> Element (Vector a) -> Element (Vector a))
-> Vector a -> Element (Vector a)
ofoldr1Ex = (Element (Vector a) -> Element (Vector a) -> Element (Vector a))
-> Vector a -> Element (Vector a)
forall a. (a -> a -> a) -> Vector a -> a
V.foldr1
    ofoldl1Ex' :: (Element (Vector a) -> Element (Vector a) -> Element (Vector a))
-> Vector a -> Element (Vector a)
ofoldl1Ex' = (Element (Vector a) -> Element (Vector a) -> Element (Vector a))
-> Vector a -> Element (Vector a)
forall a. (a -> a -> a) -> Vector a -> a
V.foldl1'
    headEx :: Vector a -> Element (Vector a)
headEx = Vector a -> Element (Vector a)
forall a. Vector a -> a
V.head
    lastEx :: Vector a -> Element (Vector a)
lastEx = Vector a -> Element (Vector a)
forall a. Vector a -> a
V.last
    unsafeHead :: Vector a -> Element (Vector a)
unsafeHead = Vector a -> Element (Vector a)
forall a. Vector a -> a
V.unsafeHead
    unsafeLast :: Vector a -> Element (Vector a)
unsafeLast = Vector a -> Element (Vector a)
forall a. Vector a -> a
V.unsafeLast
    maximumByEx :: (Element (Vector a) -> Element (Vector a) -> Ordering)
-> Vector a -> Element (Vector a)
maximumByEx = (Element (Vector a) -> Element (Vector a) -> Ordering)
-> Vector a -> Element (Vector a)
forall a. (a -> a -> Ordering) -> Vector a -> a
V.maximumBy
    minimumByEx :: (Element (Vector a) -> Element (Vector a) -> Ordering)
-> Vector a -> Element (Vector a)
minimumByEx = (Element (Vector a) -> Element (Vector a) -> Ordering)
-> Vector a -> Element (Vector a)
forall a. (a -> a -> Ordering) -> Vector a -> a
V.minimumBy
    {-# INLINE ofoldr #-}
    {-# INLINE ofoldl' #-}
    {-# INLINE otoList #-}
    {-# INLINE oall #-}
    {-# INLINE oany #-}
    {-# INLINE onull #-}
    {-# INLINE olength #-}
    {-# INLINE ofoldr1Ex #-}
    {-# INLINE ofoldl1Ex' #-}
    {-# INLINE headEx #-}
    {-# INLINE lastEx #-}
    {-# INLINE unsafeHead #-}
    {-# INLINE maximumByEx #-}
    {-# INLINE minimumByEx #-}
instance Ord e => MonoFoldable (Set e) where
    olength :: Set e -> Int
olength = Set e -> Int
forall a. Set a -> Int
Set.size
    oelem :: Element (Set e) -> Set e -> Bool
oelem = Element (Set e) -> Set e -> Bool
forall a. Ord a => a -> Set a -> Bool
Set.member
    onotElem :: Element (Set e) -> Set e -> Bool
onotElem = Element (Set e) -> Set e -> Bool
forall a. Ord a => a -> Set a -> Bool
Set.notMember
    {-# INLINE olength #-}
    {-# INLINE oelem #-}
    {-# INLINE onotElem #-}
instance MonoFoldable (HashSet e)

instance U.Unbox a => MonoFoldable (U.Vector a) where
    ofoldMap :: (Element (Vector a) -> m) -> Vector a -> m
ofoldMap Element (Vector a) -> m
f = (Element (Vector a) -> m -> m) -> m -> Vector a -> m
forall mono b.
MonoFoldable mono =>
(Element mono -> b -> b) -> b -> mono -> b
ofoldr (m -> m -> m
forall a. Monoid a => a -> a -> a
mappend (m -> m -> m) -> (a -> m) -> a -> m -> m
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. a -> m
Element (Vector a) -> m
f) m
forall a. Monoid a => a
mempty
    ofoldr :: (Element (Vector a) -> b -> b) -> b -> Vector a -> b
ofoldr = (Element (Vector a) -> b -> b) -> b -> Vector a -> b
forall a b. Unbox a => (a -> b -> b) -> b -> Vector a -> b
U.foldr
    ofoldl' :: (a -> Element (Vector a) -> a) -> a -> Vector a -> a
ofoldl' = (a -> Element (Vector a) -> a) -> a -> Vector a -> a
forall b a. Unbox b => (a -> b -> a) -> a -> Vector b -> a
U.foldl'
    otoList :: Vector a -> [Element (Vector a)]
otoList = Vector a -> [Element (Vector a)]
forall a. Unbox a => Vector a -> [a]
U.toList
    oall :: (Element (Vector a) -> Bool) -> Vector a -> Bool
oall = (Element (Vector a) -> Bool) -> Vector a -> Bool
forall a. Unbox a => (a -> Bool) -> Vector a -> Bool
U.all
    oany :: (Element (Vector a) -> Bool) -> Vector a -> Bool
oany = (Element (Vector a) -> Bool) -> Vector a -> Bool
forall a. Unbox a => (a -> Bool) -> Vector a -> Bool
U.any
    onull :: Vector a -> Bool
onull = Vector a -> Bool
forall a. Unbox a => Vector a -> Bool
U.null
    olength :: Vector a -> Int
olength = Vector a -> Int
forall a. Unbox a => Vector a -> Int
U.length
    ofoldr1Ex :: (Element (Vector a) -> Element (Vector a) -> Element (Vector a))
-> Vector a -> Element (Vector a)
ofoldr1Ex = (Element (Vector a) -> Element (Vector a) -> Element (Vector a))
-> Vector a -> Element (Vector a)
forall a. Unbox a => (a -> a -> a) -> Vector a -> a
U.foldr1
    ofoldl1Ex' :: (Element (Vector a) -> Element (Vector a) -> Element (Vector a))
-> Vector a -> Element (Vector a)
ofoldl1Ex' = (Element (Vector a) -> Element (Vector a) -> Element (Vector a))
-> Vector a -> Element (Vector a)
forall a. Unbox a => (a -> a -> a) -> Vector a -> a
U.foldl1'
    headEx :: Vector a -> Element (Vector a)
headEx = Vector a -> Element (Vector a)
forall a. Unbox a => Vector a -> a
U.head
    lastEx :: Vector a -> Element (Vector a)
lastEx = Vector a -> Element (Vector a)
forall a. Unbox a => Vector a -> a
U.last
    unsafeHead :: Vector a -> Element (Vector a)
unsafeHead = Vector a -> Element (Vector a)
forall a. Unbox a => Vector a -> a
U.unsafeHead
    unsafeLast :: Vector a -> Element (Vector a)
unsafeLast = Vector a -> Element (Vector a)
forall a. Unbox a => Vector a -> a
U.unsafeLast
    maximumByEx :: (Element (Vector a) -> Element (Vector a) -> Ordering)
-> Vector a -> Element (Vector a)
maximumByEx = (Element (Vector a) -> Element (Vector a) -> Ordering)
-> Vector a -> Element (Vector a)
forall a. Unbox a => (a -> a -> Ordering) -> Vector a -> a
U.maximumBy
    minimumByEx :: (Element (Vector a) -> Element (Vector a) -> Ordering)
-> Vector a -> Element (Vector a)
minimumByEx = (Element (Vector a) -> Element (Vector a) -> Ordering)
-> Vector a -> Element (Vector a)
forall a. Unbox a => (a -> a -> Ordering) -> Vector a -> a
U.minimumBy
    {-# INLINE ofoldMap #-}
    {-# INLINE ofoldr #-}
    {-# INLINE ofoldl' #-}
    {-# INLINE otoList #-}
    {-# INLINE oall #-}
    {-# INLINE oany #-}
    {-# INLINE onull #-}
    {-# INLINE olength #-}
    {-# INLINE ofoldr1Ex #-}
    {-# INLINE ofoldl1Ex' #-}
    {-# INLINE headEx #-}
    {-# INLINE lastEx #-}
    {-# INLINE unsafeHead #-}
    {-# INLINE maximumByEx #-}
    {-# INLINE minimumByEx #-}
instance VS.Storable a => MonoFoldable (VS.Vector a) where
    ofoldMap :: (Element (Vector a) -> m) -> Vector a -> m
ofoldMap Element (Vector a) -> m
f = (Element (Vector a) -> m -> m) -> m -> Vector a -> m
forall mono b.
MonoFoldable mono =>
(Element mono -> b -> b) -> b -> mono -> b
ofoldr (m -> m -> m
forall a. Monoid a => a -> a -> a
mappend (m -> m -> m) -> (a -> m) -> a -> m -> m
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. a -> m
Element (Vector a) -> m
f) m
forall a. Monoid a => a
mempty
    ofoldr :: (Element (Vector a) -> b -> b) -> b -> Vector a -> b
ofoldr = (Element (Vector a) -> b -> b) -> b -> Vector a -> b
forall a b. Storable a => (a -> b -> b) -> b -> Vector a -> b
VS.foldr
    ofoldl' :: (a -> Element (Vector a) -> a) -> a -> Vector a -> a
ofoldl' = (a -> Element (Vector a) -> a) -> a -> Vector a -> a
forall b a. Storable b => (a -> b -> a) -> a -> Vector b -> a
VS.foldl'
    otoList :: Vector a -> [Element (Vector a)]
otoList = Vector a -> [Element (Vector a)]
forall a. Storable a => Vector a -> [a]
VS.toList
    oall :: (Element (Vector a) -> Bool) -> Vector a -> Bool
oall = (Element (Vector a) -> Bool) -> Vector a -> Bool
forall a. Storable a => (a -> Bool) -> Vector a -> Bool
VS.all
    oany :: (Element (Vector a) -> Bool) -> Vector a -> Bool
oany = (Element (Vector a) -> Bool) -> Vector a -> Bool
forall a. Storable a => (a -> Bool) -> Vector a -> Bool
VS.any
    onull :: Vector a -> Bool
onull = Vector a -> Bool
forall a. Storable a => Vector a -> Bool
VS.null
    olength :: Vector a -> Int
olength = Vector a -> Int
forall a. Storable a => Vector a -> Int
VS.length
    ofoldr1Ex :: (Element (Vector a) -> Element (Vector a) -> Element (Vector a))
-> Vector a -> Element (Vector a)
ofoldr1Ex = (Element (Vector a) -> Element (Vector a) -> Element (Vector a))
-> Vector a -> Element (Vector a)
forall a. Storable a => (a -> a -> a) -> Vector a -> a
VS.foldr1
    ofoldl1Ex' :: (Element (Vector a) -> Element (Vector a) -> Element (Vector a))
-> Vector a -> Element (Vector a)
ofoldl1Ex' = (Element (Vector a) -> Element (Vector a) -> Element (Vector a))
-> Vector a -> Element (Vector a)
forall a. Storable a => (a -> a -> a) -> Vector a -> a
VS.foldl1'
    headEx :: Vector a -> Element (Vector a)
headEx = Vector a -> Element (Vector a)
forall a. Storable a => Vector a -> a
VS.head
    lastEx :: Vector a -> Element (Vector a)
lastEx = Vector a -> Element (Vector a)
forall a. Storable a => Vector a -> a
VS.last
    unsafeHead :: Vector a -> Element (Vector a)
unsafeHead = Vector a -> Element (Vector a)
forall a. Storable a => Vector a -> a
VS.unsafeHead
    unsafeLast :: Vector a -> Element (Vector a)
unsafeLast = Vector a -> Element (Vector a)
forall a. Storable a => Vector a -> a
VS.unsafeLast
    maximumByEx :: (Element (Vector a) -> Element (Vector a) -> Ordering)
-> Vector a -> Element (Vector a)
maximumByEx = (Element (Vector a) -> Element (Vector a) -> Ordering)
-> Vector a -> Element (Vector a)
forall a. Storable a => (a -> a -> Ordering) -> Vector a -> a
VS.maximumBy
    minimumByEx :: (Element (Vector a) -> Element (Vector a) -> Ordering)
-> Vector a -> Element (Vector a)
minimumByEx = (Element (Vector a) -> Element (Vector a) -> Ordering)
-> Vector a -> Element (Vector a)
forall a. Storable a => (a -> a -> Ordering) -> Vector a -> a
VS.minimumBy
    {-# INLINE ofoldMap #-}
    {-# INLINE ofoldr #-}
    {-# INLINE ofoldl' #-}
    {-# INLINE otoList #-}
    {-# INLINE oall #-}
    {-# INLINE oany #-}
    {-# INLINE onull #-}
    {-# INLINE olength #-}
    {-# INLINE ofoldr1Ex #-}
    {-# INLINE ofoldl1Ex' #-}
    {-# INLINE headEx #-}
    {-# INLINE lastEx #-}
    {-# INLINE unsafeHead #-}
    {-# INLINE maximumByEx #-}
    {-# INLINE minimumByEx #-}
instance MonoFoldable (Either a b) where
    ofoldMap :: (Element (Either a b) -> m) -> Either a b -> m
ofoldMap Element (Either a b) -> m
f = (Element (Either a b) -> m -> m) -> m -> Either a b -> m
forall mono b.
MonoFoldable mono =>
(Element mono -> b -> b) -> b -> mono -> b
ofoldr (m -> m -> m
forall a. Monoid a => a -> a -> a
mappend (m -> m -> m) -> (b -> m) -> b -> m -> m
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. b -> m
Element (Either a b) -> m
f) m
forall a. Monoid a => a
mempty
    ofoldr :: (Element (Either a b) -> b -> b) -> b -> Either a b -> b
ofoldr Element (Either a b) -> b -> b
f b
b (Right b
a) = Element (Either a b) -> b -> b
f b
Element (Either a b)
a b
b
    ofoldr Element (Either a b) -> b -> b
_ b
b (Left a
_) = b
b
    ofoldl' :: (a -> Element (Either a b) -> a) -> a -> Either a b -> a
ofoldl' a -> Element (Either a b) -> a
f a
a (Right b
b) = a -> Element (Either a b) -> a
f a
a b
Element (Either a b)
b
    ofoldl' a -> Element (Either a b) -> a
_ a
a (Left a
_) = a
a
    otoList :: Either a b -> [Element (Either a b)]
otoList (Left a
_) = []
    otoList (Right b
b) = [b
Element (Either a b)
b]
    oall :: (Element (Either a b) -> Bool) -> Either a b -> Bool
oall Element (Either a b) -> Bool
_ (Left a
_) = Bool
True
    oall Element (Either a b) -> Bool
f (Right b
b) = Element (Either a b) -> Bool
f b
Element (Either a b)
b
    oany :: (Element (Either a b) -> Bool) -> Either a b -> Bool
oany Element (Either a b) -> Bool
_ (Left a
_) = Bool
False
    oany Element (Either a b) -> Bool
f (Right b
b) = Element (Either a b) -> Bool
f b
Element (Either a b)
b
    onull :: Either a b -> Bool
onull (Left a
_) = Bool
True
    onull (Right b
_) = Bool
False
    olength :: Either a b -> Int
olength (Left a
_) = Int
0
    olength (Right b
_) = Int
1
    ofoldr1Ex :: (Element (Either a b)
 -> Element (Either a b) -> Element (Either a b))
-> Either a b -> Element (Either a b)
ofoldr1Ex Element (Either a b)
-> Element (Either a b) -> Element (Either a b)
_ (Left a
_) = [Char] -> b
forall a. HasCallStack => [Char] -> a
Prelude.error [Char]
"ofoldr1Ex on Either"
    ofoldr1Ex Element (Either a b)
-> Element (Either a b) -> Element (Either a b)
_ (Right b
x) = b
Element (Either a b)
x
    ofoldl1Ex' :: (Element (Either a b)
 -> Element (Either a b) -> Element (Either a b))
-> Either a b -> Element (Either a b)
ofoldl1Ex' Element (Either a b)
-> Element (Either a b) -> Element (Either a b)
_ (Left a
_) = [Char] -> b
forall a. HasCallStack => [Char] -> a
Prelude.error [Char]
"ofoldl1Ex' on Either"
    ofoldl1Ex' Element (Either a b)
-> Element (Either a b) -> Element (Either a b)
_ (Right b
x) = b
Element (Either a b)
x
    omapM_ :: (Element (Either a b) -> m ()) -> Either a b -> m ()
omapM_ Element (Either a b) -> m ()
_ (Left a
_) = () -> m ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
    omapM_ Element (Either a b) -> m ()
f (Right b
x) = Element (Either a b) -> m ()
f b
Element (Either a b)
x
    {-# INLINE ofoldMap #-}
    {-# INLINE ofoldr #-}
    {-# INLINE ofoldl' #-}
    {-# INLINE otoList #-}
    {-# INLINE oall #-}
    {-# INLINE oany #-}
    {-# INLINE onull #-}
    {-# INLINE olength #-}
    {-# INLINE omapM_ #-}
    {-# INLINE ofoldr1Ex #-}
    {-# INLINE ofoldl1Ex' #-}
instance MonoFoldable (a, b)
instance MonoFoldable (Const m a)
instance F.Foldable f => MonoFoldable (MaybeT f a)
#if !MIN_VERSION_transformers(0,6,0)
instance F.Foldable f => MonoFoldable (ListT f a)
#endif
instance F.Foldable f => MonoFoldable (IdentityT f a)
instance F.Foldable f => MonoFoldable (WriterT w f a)
instance F.Foldable f => MonoFoldable (Strict.WriterT w f a)
instance (F.Foldable f, F.Foldable g) => MonoFoldable (Compose f g a)
instance (F.Foldable f, F.Foldable g) => MonoFoldable (Product f g a)
-- | @since 1.0.11.0
instance (F.Foldable f, F.Foldable g) => MonoFoldable ((f :.: g) a)
-- | @since 1.0.11.0
instance (F.Foldable f, F.Foldable g) => MonoFoldable ((f :*: g) a)
-- | @since 1.0.11.0
instance (F.Foldable f, F.Foldable g) => MonoFoldable ((f :+: g) a)
-- | @since 1.0.11.0
instance MonoFoldable (K1 i c a)
-- | @since 1.0.11.0
instance F.Foldable f => MonoFoldable (M1 i c f a)
-- | @since 1.0.11.0
instance F.Foldable f => MonoFoldable (Rec1 f a)
-- | @since 1.0.11.0
instance MonoFoldable (Par1 a)
-- | @since 1.0.11.0
instance MonoFoldable (U1 a)
-- | @since 1.0.11.0
instance MonoFoldable (V1 a)
-- | @since 1.0.11.0
instance MonoFoldable (Proxy a)

-- | Safe version of 'headEx'.
--
-- Returns 'Nothing' instead of throwing an exception when encountering
-- an empty monomorphic container.
headMay :: MonoFoldable mono => mono -> Maybe (Element mono)
headMay :: mono -> Maybe (Element mono)
headMay mono
mono
    | mono -> Bool
forall mono. MonoFoldable mono => mono -> Bool
onull mono
mono = Maybe (Element mono)
forall a. Maybe a
Nothing
    | Bool
otherwise = Element mono -> Maybe (Element mono)
forall a. a -> Maybe a
Just (mono -> Element mono
forall mono. MonoFoldable mono => mono -> Element mono
headEx mono
mono)
{-# INLINE headMay #-}

-- | Safe version of 'lastEx'.
--
-- Returns 'Nothing' instead of throwing an exception when encountering
-- an empty monomorphic container.
lastMay :: MonoFoldable mono => mono -> Maybe (Element mono)
lastMay :: mono -> Maybe (Element mono)
lastMay mono
mono
    | mono -> Bool
forall mono. MonoFoldable mono => mono -> Bool
onull mono
mono = Maybe (Element mono)
forall a. Maybe a
Nothing
    | Bool
otherwise = Element mono -> Maybe (Element mono)
forall a. a -> Maybe a
Just (mono -> Element mono
forall mono. MonoFoldable mono => mono -> Element mono
lastEx mono
mono)
{-# INLINE lastMay #-}

-- | 'osum' computes the sum of the numbers of a monomorphic container.
osum :: (MonoFoldable mono, Num (Element mono)) => mono -> Element mono
osum :: mono -> Element mono
osum = (Element mono -> Element mono -> Element mono)
-> Element mono -> mono -> Element mono
forall mono a.
MonoFoldable mono =>
(a -> Element mono -> a) -> a -> mono -> a
ofoldl' Element mono -> Element mono -> Element mono
forall a. Num a => a -> a -> a
(+) Element mono
0
{-# INLINE osum #-}

-- | 'oproduct' computes the product of the numbers of a monomorphic container.
oproduct :: (MonoFoldable mono, Num (Element mono)) => mono -> Element mono
oproduct :: mono -> Element mono
oproduct = (Element mono -> Element mono -> Element mono)
-> Element mono -> mono -> Element mono
forall mono a.
MonoFoldable mono =>
(a -> Element mono -> a) -> a -> mono -> a
ofoldl' Element mono -> Element mono -> Element mono
forall a. Num a => a -> a -> a
(*) Element mono
1
{-# INLINE oproduct #-}

-- | Are __all__ of the elements 'True'?
--
-- @since 0.6.0
oand :: (Element mono ~ Bool, MonoFoldable mono) => mono -> Bool
oand :: mono -> Bool
oand = (Element mono -> Bool) -> mono -> Bool
forall mono.
MonoFoldable mono =>
(Element mono -> Bool) -> mono -> Bool
oall Element mono -> Bool
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
{-# INLINE oand #-}

-- | Are __any__ of the elements 'True'?
--
-- @since 0.6.0
oor :: (Element mono ~ Bool, MonoFoldable mono) => mono -> Bool
oor :: mono -> Bool
oor = (Element mono -> Bool) -> mono -> Bool
forall mono.
MonoFoldable mono =>
(Element mono -> Bool) -> mono -> Bool
oany Element mono -> Bool
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
{-# INLINE oor #-}

-- | Synonym for 'ofoldMap'
--
-- @since 1.0.0
oconcatMap :: (MonoFoldable mono, Monoid m) => (Element mono -> m) -> mono -> m
oconcatMap :: (Element mono -> m) -> mono -> m
oconcatMap = (Element mono -> m) -> mono -> m
forall mono m.
(MonoFoldable mono, Monoid m) =>
(Element mono -> m) -> mono -> m
ofoldMap

-- | Monoidally combine all values in the container
--
-- @since 1.0.0
ofold :: (MonoFoldable mono, Monoid (Element mono)) => mono -> Element mono
ofold :: mono -> Element mono
ofold = (Element mono -> Element mono) -> mono -> Element mono
forall mono m.
(MonoFoldable mono, Monoid m) =>
(Element mono -> m) -> mono -> m
ofoldMap Element mono -> Element mono
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
{-# INLINE ofold #-}

-- | Synonym for 'ofold'
--
-- @since 1.0.0
oconcat :: (MonoFoldable mono, Monoid (Element mono)) => mono -> Element mono
oconcat :: mono -> Element mono
oconcat = mono -> Element mono
forall mono.
(MonoFoldable mono, Monoid (Element mono)) =>
mono -> Element mono
ofold
{-# INLINE oconcat #-}

-- | Synonym for 'ofoldlM'
--
-- @since 1.0.0
ofoldM :: (MonoFoldable mono, Monad m) => (a -> Element mono -> m a) -> a -> mono -> m a
ofoldM :: (a -> Element mono -> m a) -> a -> mono -> m a
ofoldM = (a -> Element mono -> m a) -> a -> mono -> m a
forall mono (m :: * -> *) a.
(MonoFoldable mono, Monad m) =>
(a -> Element mono -> m a) -> a -> mono -> m a
ofoldlM
{-# INLINE ofoldM #-}

-- | Perform all actions in the given container
--
-- @since 1.0.0
osequence_ :: (Applicative m, MonoFoldable mono, Element mono ~ (m ())) => mono -> m ()
osequence_ :: mono -> m ()
osequence_ = (Element mono -> m ()) -> mono -> m ()
forall mono (m :: * -> *).
(MonoFoldable mono, Applicative m) =>
(Element mono -> m ()) -> mono -> m ()
omapM_ Element mono -> m ()
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
{-# INLINE osequence_ #-}

-- | Get the minimum element of a monomorphic container.
--
-- Note: this is a partial function. On an empty 'MonoFoldable', it will
-- throw an exception.
--
-- /See 'Data.NonNull.maximum' from "Data.NonNull" for a total version of this function./
maximumEx :: (MonoFoldable mono, Ord (Element mono)) => mono -> Element mono
maximumEx :: mono -> Element mono
maximumEx = (Element mono -> Element mono -> Ordering) -> mono -> Element mono
forall mono.
MonoFoldable mono =>
(Element mono -> Element mono -> Ordering) -> mono -> Element mono
maximumByEx Element mono -> Element mono -> Ordering
forall a. Ord a => a -> a -> Ordering
compare
{-# INLINE [0] maximumEx #-}

-- | Get the maximum element of a monomorphic container.
--
-- Note: this is a partial function. On an empty 'MonoFoldable', it will
-- throw an exception.
--
-- /See 'Data.NonNull.minimum' from "Data.NonNull" for a total version of this function./
minimumEx :: (MonoFoldable mono, Ord (Element mono)) => mono -> Element mono
minimumEx :: mono -> Element mono
minimumEx = (Element mono -> Element mono -> Ordering) -> mono -> Element mono
forall mono.
MonoFoldable mono =>
(Element mono -> Element mono -> Ordering) -> mono -> Element mono
minimumByEx Element mono -> Element mono -> Ordering
forall a. Ord a => a -> a -> Ordering
compare
{-# INLINE [0] minimumEx #-}

{-# RULES "strict ByteString maximumEx" maximumEx = S.maximum #-}
{-# RULES "strict ByteString minimumEx" minimumEx = S.minimum #-}

{-# RULES "lazy ByteString maximumEx" maximumEx = L.maximum #-}
{-# RULES "lazy ByteString minimumEx" minimumEx = L.minimum #-}

{-# RULES "strict Text maximumEx" maximumEx = T.maximum #-}
{-# RULES "strict Text minimumEx" minimumEx = T.minimum #-}

{-# RULES "lazy Text maximumEx" maximumEx = TL.maximum #-}
{-# RULES "lazy Text minimumEx" minimumEx = TL.minimum #-}

{-# RULES "boxed Vector maximumEx" maximumEx = V.maximum #-}
{-# RULES "boxed Vector minimumEx" minimumEx = V.minimum #-}

{-# RULES "unboxed Vector maximumEx" forall (u :: U.Unbox a => U.Vector a). maximumEx u = U.maximum u #-}
{-# RULES "unboxed Vector minimumEx" forall (u :: U.Unbox a => U.Vector a). minimumEx u = U.minimum u #-}

{-# RULES "storable Vector maximumEx" forall (v :: VS.Storable a => VS.Vector a). maximumEx v = VS.maximum v #-}
{-# RULES "storable Vector minimumEx" forall (v :: VS.Storable a => VS.Vector a). minimumEx v = VS.minimum v #-}

-- | Safe version of 'maximumEx'.
--
-- Returns 'Nothing' instead of throwing an exception when
-- encountering an empty monomorphic container.
maximumMay :: (MonoFoldable mono, Ord (Element mono)) => mono -> Maybe (Element mono)
maximumMay :: mono -> Maybe (Element mono)
maximumMay mono
mono
    | mono -> Bool
forall mono. MonoFoldable mono => mono -> Bool
onull mono
mono = Maybe (Element mono)
forall a. Maybe a
Nothing
    | Bool
otherwise = Element mono -> Maybe (Element mono)
forall a. a -> Maybe a
Just (mono -> Element mono
forall mono.
(MonoFoldable mono, Ord (Element mono)) =>
mono -> Element mono
maximumEx mono
mono)
{-# INLINE maximumMay #-}

-- | Safe version of 'maximumByEx'.
--
-- Returns 'Nothing' instead of throwing an exception when
-- encountering an empty monomorphic container.
maximumByMay :: MonoFoldable mono
             => (Element mono -> Element mono -> Ordering)
             -> mono
             -> Maybe (Element mono)
maximumByMay :: (Element mono -> Element mono -> Ordering)
-> mono -> Maybe (Element mono)
maximumByMay Element mono -> Element mono -> Ordering
f mono
mono
    | mono -> Bool
forall mono. MonoFoldable mono => mono -> Bool
onull mono
mono = Maybe (Element mono)
forall a. Maybe a
Nothing
    | Bool
otherwise = Element mono -> Maybe (Element mono)
forall a. a -> Maybe a
Just ((Element mono -> Element mono -> Ordering) -> mono -> Element mono
forall mono.
MonoFoldable mono =>
(Element mono -> Element mono -> Ordering) -> mono -> Element mono
maximumByEx Element mono -> Element mono -> Ordering
f mono
mono)
{-# INLINE maximumByMay #-}

-- | Safe version of 'minimumEx'.
--
-- Returns 'Nothing' instead of throwing an exception when
-- encountering an empty monomorphic container.
minimumMay :: (MonoFoldable mono, Ord (Element mono)) => mono -> Maybe (Element mono)
minimumMay :: mono -> Maybe (Element mono)
minimumMay mono
mono
    | mono -> Bool
forall mono. MonoFoldable mono => mono -> Bool
onull mono
mono = Maybe (Element mono)
forall a. Maybe a
Nothing
    | Bool
otherwise = Element mono -> Maybe (Element mono)
forall a. a -> Maybe a
Just (mono -> Element mono
forall mono.
(MonoFoldable mono, Ord (Element mono)) =>
mono -> Element mono
minimumEx mono
mono)
{-# INLINE minimumMay #-}

-- | Safe version of 'minimumByEx'.
--
-- Returns 'Nothing' instead of throwing an exception when
-- encountering an empty monomorphic container.
minimumByMay :: MonoFoldable mono
             => (Element mono -> Element mono -> Ordering)
             -> mono
             -> Maybe (Element mono)
minimumByMay :: (Element mono -> Element mono -> Ordering)
-> mono -> Maybe (Element mono)
minimumByMay Element mono -> Element mono -> Ordering
f mono
mono
    | mono -> Bool
forall mono. MonoFoldable mono => mono -> Bool
onull mono
mono = Maybe (Element mono)
forall a. Maybe a
Nothing
    | Bool
otherwise = Element mono -> Maybe (Element mono)
forall a. a -> Maybe a
Just ((Element mono -> Element mono -> Ordering) -> mono -> Element mono
forall mono.
MonoFoldable mono =>
(Element mono -> Element mono -> Ordering) -> mono -> Element mono
minimumByEx Element mono -> Element mono -> Ordering
f mono
mono)
{-# INLINE minimumByMay #-}

-- | Monomorphic containers that can be traversed from left to right.
--
-- NOTE: Due to limitations with the role system, GHC is yet unable to provide newtype-derivation of
-- 'MonoTraversable'. See <https://stackoverflow.com/questions/49776924/newtype-deriving-issequence>.
class (MonoFunctor mono, MonoFoldable mono) => MonoTraversable mono where
    -- | Map each element of a monomorphic container to an action,
    -- evaluate these actions from left to right, and
    -- collect the results.
    otraverse :: Applicative f => (Element mono -> f (Element mono)) -> mono -> f mono
    default otraverse :: (Traversable t, mono ~ t a, a ~ Element mono, Applicative f) => (Element mono -> f (Element mono)) -> mono -> f mono
    otraverse = (Element mono -> f (Element mono)) -> mono -> f mono
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse

    -- | Map each element of a monomorphic container to a monadic action,
    -- evaluate these actions from left to right, and
    -- collect the results.
    omapM :: Applicative m => (Element mono -> m (Element mono)) -> mono -> m mono
    omapM = (Element mono -> m (Element mono)) -> mono -> m mono
forall mono (f :: * -> *).
(MonoTraversable mono, Applicative f) =>
(Element mono -> f (Element mono)) -> mono -> f mono
otraverse
    {-# INLINE otraverse #-}
    {-# INLINE omapM #-}

instance MonoTraversable S.ByteString where
    otraverse :: (Element ByteString -> f (Element ByteString))
-> ByteString -> f ByteString
otraverse Element ByteString -> f (Element ByteString)
f = ([Word8] -> ByteString) -> f [Word8] -> f ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Word8] -> ByteString
S.pack (f [Word8] -> f ByteString)
-> (ByteString -> f [Word8]) -> ByteString -> f ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (Word8 -> f Word8) -> [Word8] -> f [Word8]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Word8 -> f Word8
Element ByteString -> f (Element ByteString)
f ([Word8] -> f [Word8])
-> (ByteString -> [Word8]) -> ByteString -> f [Word8]
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteString -> [Word8]
S.unpack
    {-# INLINE otraverse #-}
instance MonoTraversable L.ByteString where
    otraverse :: (Element ByteString -> f (Element ByteString))
-> ByteString -> f ByteString
otraverse Element ByteString -> f (Element ByteString)
f = ([Word8] -> ByteString) -> f [Word8] -> f ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Word8] -> ByteString
L.pack (f [Word8] -> f ByteString)
-> (ByteString -> f [Word8]) -> ByteString -> f ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (Word8 -> f Word8) -> [Word8] -> f [Word8]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Word8 -> f Word8
Element ByteString -> f (Element ByteString)
f ([Word8] -> f [Word8])
-> (ByteString -> [Word8]) -> ByteString -> f [Word8]
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteString -> [Word8]
L.unpack
    {-# INLINE otraverse #-}
instance MonoTraversable T.Text where
    otraverse :: (Element Text -> f (Element Text)) -> Text -> f Text
otraverse Element Text -> f (Element Text)
f = ([Char] -> Text) -> f [Char] -> f Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Char] -> Text
T.pack (f [Char] -> f Text) -> (Text -> f [Char]) -> Text -> f Text
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (Char -> f Char) -> [Char] -> f [Char]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Char -> f Char
Element Text -> f (Element Text)
f ([Char] -> f [Char]) -> (Text -> [Char]) -> Text -> f [Char]
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Text -> [Char]
T.unpack
    {-# INLINE otraverse #-}
instance MonoTraversable TL.Text where
    otraverse :: (Element Text -> f (Element Text)) -> Text -> f Text
otraverse Element Text -> f (Element Text)
f = ([Char] -> Text) -> f [Char] -> f Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Char] -> Text
TL.pack (f [Char] -> f Text) -> (Text -> f [Char]) -> Text -> f Text
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (Char -> f Char) -> [Char] -> f [Char]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Char -> f Char
Element Text -> f (Element Text)
f ([Char] -> f [Char]) -> (Text -> [Char]) -> Text -> f [Char]
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Text -> [Char]
TL.unpack
    {-# INLINE otraverse #-}
instance MonoTraversable [a]
instance MonoTraversable (Maybe a)
instance MonoTraversable (Tree a)
instance MonoTraversable (Seq a)
instance MonoTraversable (ViewL a)
instance MonoTraversable (ViewR a)
instance MonoTraversable (IntMap a)
#if !MIN_VERSION_base(4,16,0)
instance MonoTraversable (Option a)
#endif
instance MonoTraversable (NonEmpty a)
instance MonoTraversable (Identity a)
instance MonoTraversable (Map k v)
instance MonoTraversable (HashMap k v)
instance MonoTraversable (Vector a)
instance U.Unbox a => MonoTraversable (U.Vector a) where
    -- FIXME do something more efficient
    otraverse :: (Element (Vector a) -> f (Element (Vector a)))
-> Vector a -> f (Vector a)
otraverse Element (Vector a) -> f (Element (Vector a))
f = ([a] -> Vector a) -> f [a] -> f (Vector a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [a] -> Vector a
forall a. Unbox a => [a] -> Vector a
U.fromList (f [a] -> f (Vector a))
-> (Vector a -> f [a]) -> Vector a -> f (Vector a)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (a -> f a) -> [a] -> f [a]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse a -> f a
Element (Vector a) -> f (Element (Vector a))
f ([a] -> f [a]) -> (Vector a -> [a]) -> Vector a -> f [a]
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Vector a -> [a]
forall a. Unbox a => Vector a -> [a]
U.toList
    omapM :: (Element (Vector a) -> m (Element (Vector a)))
-> Vector a -> m (Vector a)
omapM = (Element (Vector a) -> m (Element (Vector a)))
-> Vector a -> m (Vector a)
forall mono (f :: * -> *).
(MonoTraversable mono, Applicative f) =>
(Element mono -> f (Element mono)) -> mono -> f mono
otraverse
    {-# INLINE otraverse #-}
    {-# INLINE omapM #-}
instance VS.Storable a => MonoTraversable (VS.Vector a) where
    -- FIXME do something more efficient
    otraverse :: (Element (Vector a) -> f (Element (Vector a)))
-> Vector a -> f (Vector a)
otraverse Element (Vector a) -> f (Element (Vector a))
f = ([a] -> Vector a) -> f [a] -> f (Vector a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [a] -> Vector a
forall a. Storable a => [a] -> Vector a
VS.fromList (f [a] -> f (Vector a))
-> (Vector a -> f [a]) -> Vector a -> f (Vector a)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (a -> f a) -> [a] -> f [a]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse a -> f a
Element (Vector a) -> f (Element (Vector a))
f ([a] -> f [a]) -> (Vector a -> [a]) -> Vector a -> f [a]
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Vector a -> [a]
forall a. Storable a => Vector a -> [a]
VS.toList
    omapM :: (Element (Vector a) -> m (Element (Vector a)))
-> Vector a -> m (Vector a)
omapM = (Element (Vector a) -> m (Element (Vector a)))
-> Vector a -> m (Vector a)
forall mono (f :: * -> *).
(MonoTraversable mono, Applicative f) =>
(Element mono -> f (Element mono)) -> mono -> f mono
otraverse
    {-# INLINE otraverse #-}
    {-# INLINE omapM #-}
instance MonoTraversable (Either a b) where
    otraverse :: (Element (Either a b) -> f (Element (Either a b)))
-> Either a b -> f (Either a b)
otraverse Element (Either a b) -> f (Element (Either a b))
_ (Left a
a) = Either a b -> f (Either a b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a -> Either a b
forall a b. a -> Either a b
Left a
a)
    otraverse Element (Either a b) -> f (Element (Either a b))
f (Right b
b) = (b -> Either a b) -> f b -> f (Either a b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap b -> Either a b
forall a b. b -> Either a b
Right (Element (Either a b) -> f (Element (Either a b))
f b
Element (Either a b)
b)
    omapM :: (Element (Either a b) -> m (Element (Either a b)))
-> Either a b -> m (Either a b)
omapM Element (Either a b) -> m (Element (Either a b))
_ (Left a
a) = Either a b -> m (Either a b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a -> Either a b
forall a b. a -> Either a b
Left a
a)
    omapM Element (Either a b) -> m (Element (Either a b))
f (Right b
b) = (b -> Either a b) -> m b -> m (Either a b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap b -> Either a b
forall a b. b -> Either a b
Right (Element (Either a b) -> m (Element (Either a b))
f b
Element (Either a b)
b)
    {-# INLINE otraverse #-}
    {-# INLINE omapM #-}
instance MonoTraversable (a, b)
instance MonoTraversable (Const m a)
instance Traversable f => MonoTraversable (MaybeT f a)
#if !MIN_VERSION_transformers(0,6,0)
instance Traversable f => MonoTraversable (ListT f a)
#endif
instance Traversable f => MonoTraversable (IdentityT f a)
instance Traversable f => MonoTraversable (WriterT w f a)
instance Traversable f => MonoTraversable (Strict.WriterT w f a)
instance (Traversable f, Traversable g) => MonoTraversable (Compose f g a)
instance (Traversable f, Traversable g) => MonoTraversable (Product f g a)
-- | @since 1.0.11.0
instance (Traversable f, Traversable g) => MonoTraversable ((f :.: g) a)
-- | @since 1.0.11.0
instance (Traversable f, Traversable g) => MonoTraversable ((f :*: g) a)
-- | @since 1.0.11.0
instance (Traversable f, Traversable g) => MonoTraversable ((f :+: g) a)
-- | @since 1.0.11.0
instance MonoTraversable (K1 i c a)
-- | @since 1.0.11.0
instance Traversable f => MonoTraversable (M1 i c f a)
-- | @since 1.0.11.0
instance Traversable f => MonoTraversable (Rec1 f a)
-- | @since 1.0.11.0
instance MonoTraversable (Par1 a)
-- | @since 1.0.11.0
instance MonoTraversable (U1 a)
-- | @since 1.0.11.0
instance MonoTraversable (V1 a)
-- | @since 1.0.11.0
instance MonoTraversable (Proxy a)

-- | 'ofor' is 'otraverse' with its arguments flipped.
ofor :: (MonoTraversable mono, Applicative f) => mono -> (Element mono -> f (Element mono)) -> f mono
ofor :: mono -> (Element mono -> f (Element mono)) -> f mono
ofor = ((Element mono -> f (Element mono)) -> mono -> f mono)
-> mono -> (Element mono -> f (Element mono)) -> f mono
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Element mono -> f (Element mono)) -> mono -> f mono
forall mono (f :: * -> *).
(MonoTraversable mono, Applicative f) =>
(Element mono -> f (Element mono)) -> mono -> f mono
otraverse
{-# INLINE ofor #-}

-- | 'oforM' is 'omapM' with its arguments flipped.
oforM :: (MonoTraversable mono, Applicative f) => mono -> (Element mono -> f (Element mono)) -> f mono
oforM :: mono -> (Element mono -> f (Element mono)) -> f mono
oforM = ((Element mono -> f (Element mono)) -> mono -> f mono)
-> mono -> (Element mono -> f (Element mono)) -> f mono
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Element mono -> f (Element mono)) -> mono -> f mono
forall mono (f :: * -> *).
(MonoTraversable mono, Applicative f) =>
(Element mono -> f (Element mono)) -> mono -> f mono
omapM
{-# INLINE oforM #-}

-- | A strict left fold, together with an unwrap function.
--
-- This is convenient when the accumulator value is not the same as the final
-- expected type. It is provided mainly for integration with the @foldl@
-- package, to be used in conjunction with @purely@.
--
-- @since 0.3.1
ofoldlUnwrap :: MonoFoldable mono
             => (x -> Element mono -> x) -> x -> (x -> b) -> mono -> b
ofoldlUnwrap :: (x -> Element mono -> x) -> x -> (x -> b) -> mono -> b
ofoldlUnwrap x -> Element mono -> x
f x
x x -> b
unwrap mono
mono = x -> b
unwrap ((x -> Element mono -> x) -> x -> mono -> x
forall mono a.
MonoFoldable mono =>
(a -> Element mono -> a) -> a -> mono -> a
ofoldl' x -> Element mono -> x
f x
x mono
mono)

-- | A monadic strict left fold, together with an unwrap function.
--
-- Similar to 'foldlUnwrap', but allows monadic actions. To be used with
-- @impurely@ from @foldl@.
--
-- @since 0.3.1
ofoldMUnwrap :: (Monad m, MonoFoldable mono)
             => (x -> Element mono -> m x) -> m x -> (x -> m b) -> mono -> m b
ofoldMUnwrap :: (x -> Element mono -> m x) -> m x -> (x -> m b) -> mono -> m b
ofoldMUnwrap x -> Element mono -> m x
f m x
mx x -> m b
unwrap mono
mono = do
    x
x <- m x
mx
    x
x' <- (x -> Element mono -> m x) -> x -> mono -> m x
forall mono (m :: * -> *) a.
(MonoFoldable mono, Monad m) =>
(a -> Element mono -> m a) -> a -> mono -> m a
ofoldlM x -> Element mono -> m x
f x
x mono
mono
    x -> m b
unwrap x
x'

-- | Typeclass for monomorphic containers that an element can be
-- lifted into.
--
-- For any 'MonoFunctor', the following law holds:
--
-- @
-- 'omap' f . 'opoint' = 'opoint' . f
-- @
class MonoPointed mono where
    -- | Lift an element into a monomorphic container.
    --
    -- 'opoint' is the same as 'Control.Applicative.pure' for an 'Applicative'
    opoint :: Element mono -> mono
    default opoint :: (Applicative f, (f a) ~ mono, Element (f a) ~ a)
                   => Element mono -> mono
    opoint = Element mono -> mono
forall (f :: * -> *) a. Applicative f => a -> f a
pure
    {-# INLINE opoint #-}

-- monomorphic
instance MonoPointed S.ByteString where
    opoint :: Element ByteString -> ByteString
opoint = Word8 -> ByteString
Element ByteString -> ByteString
S.singleton
    {-# INLINE opoint #-}
instance MonoPointed L.ByteString where
    opoint :: Element ByteString -> ByteString
opoint = Word8 -> ByteString
Element ByteString -> ByteString
L.singleton
    {-# INLINE opoint #-}
instance MonoPointed T.Text where
    opoint :: Element Text -> Text
opoint = Char -> Text
Element Text -> Text
T.singleton
    {-# INLINE opoint #-}
instance MonoPointed TL.Text where
    opoint :: Element Text -> Text
opoint = Char -> Text
Element Text -> Text
TL.singleton
    {-# INLINE opoint #-}

-- Applicative
instance MonoPointed [a]
instance MonoPointed (Maybe a)
#if !MIN_VERSION_base(4,16,0)
instance MonoPointed (Option a)
#endif
instance MonoPointed (NonEmpty a)
instance MonoPointed (Identity a)
instance MonoPointed (Vector a)
instance MonoPointed (IO a)
instance MonoPointed (ZipList a)
instance MonoPointed (r -> a)
instance Monoid a => MonoPointed (a, b)
instance Monoid m => MonoPointed (Const m a)
instance Monad m => MonoPointed (WrappedMonad m a)
#if !MIN_VERSION_transformers(0,6,0)
instance Applicative m => MonoPointed (ListT m a)
#endif
instance Applicative m => MonoPointed (IdentityT m a)
instance Arrow a => MonoPointed (WrappedArrow a b c)
instance (Monoid w, Applicative m) => MonoPointed (WriterT w m a)
instance (Monoid w, Applicative m) => MonoPointed (Strict.WriterT w m a)
instance Applicative m => MonoPointed (ReaderT r m a)
instance MonoPointed (ContT r m a)
instance (Applicative f, Applicative g) => MonoPointed (Compose f g a)
instance (Applicative f, Applicative g) => MonoPointed (Product f g a)
-- | @since 1.0.11.0
instance (Applicative f, Applicative g) => MonoPointed ((f :.: g) a)
-- | @since 1.0.11.0
instance (Applicative f, Applicative g) => MonoPointed ((f :*: g) a)
-- | @since 1.0.11.0
instance Applicative f => MonoPointed (M1 i c f a)
-- | @since 1.0.11.0
instance Applicative f => MonoPointed (Rec1 f a)
-- | @since 1.0.11.0
instance MonoPointed (Par1 a)
-- | @since 1.0.11.0
instance MonoPointed (U1 a)
-- | @since 1.0.11.0
instance MonoPointed (Proxy a)

-- Not Applicative
instance MonoPointed (Seq a) where
    opoint :: Element (Seq a) -> Seq a
opoint = Element (Seq a) -> Seq a
forall a. a -> Seq a
Seq.singleton
    {-# INLINE opoint #-}
instance U.Unbox a => MonoPointed (U.Vector a) where
    opoint :: Element (Vector a) -> Vector a
opoint = Element (Vector a) -> Vector a
forall a. Unbox a => a -> Vector a
U.singleton
    {-# INLINE opoint #-}
instance VS.Storable a => MonoPointed (VS.Vector a) where
    opoint :: Element (Vector a) -> Vector a
opoint = Element (Vector a) -> Vector a
forall a. Storable a => a -> Vector a
VS.singleton
    {-# INLINE opoint #-}
instance MonoPointed (Either a b) where
    opoint :: Element (Either a b) -> Either a b
opoint = Element (Either a b) -> Either a b
forall a b. b -> Either a b
Right
    {-# INLINE opoint #-}
instance MonoPointed IntSet.IntSet where
    opoint :: Element IntSet -> IntSet
opoint = Int -> IntSet
Element IntSet -> IntSet
IntSet.singleton
    {-# INLINE opoint #-}
instance MonoPointed (Set a) where
    opoint :: Element (Set a) -> Set a
opoint = Element (Set a) -> Set a
forall a. a -> Set a
Set.singleton
    {-# INLINE opoint #-}
instance Hashable a => MonoPointed (HashSet a) where
    opoint :: Element (HashSet a) -> HashSet a
opoint = Element (HashSet a) -> HashSet a
forall a. Hashable a => a -> HashSet a
HashSet.singleton
    {-# INLINE opoint #-}
instance Applicative f => MonoPointed (MaybeT f a) where
    opoint :: Element (MaybeT f a) -> MaybeT f a
opoint = f (Maybe a) -> MaybeT f a
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (f (Maybe a) -> MaybeT f a)
-> (a -> f (Maybe a)) -> a -> MaybeT f a
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (a -> Maybe a) -> f a -> f (Maybe a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> Maybe a
forall a. a -> Maybe a
Just (f a -> f (Maybe a)) -> (a -> f a) -> a -> f (Maybe a)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
    {-# INLINE opoint #-}
instance (Monoid w, Applicative m) => MonoPointed (RWST r w s m a) where
    opoint :: Element (RWST r w s m a) -> RWST r w s m a
opoint Element (RWST r w s m a)
a = (r -> s -> m (a, s, w)) -> RWST r w s m a
forall r w s (m :: * -> *) a.
(r -> s -> m (a, s, w)) -> RWST r w s m a
RWST (\r
_ s
s -> (a, s, w) -> m (a, s, w)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a
Element (RWST r w s m a)
a, s
s, w
forall a. Monoid a => a
mempty))
    {-# INLINE opoint #-}
instance (Monoid w, Applicative m) => MonoPointed (Strict.RWST r w s m a) where
    opoint :: Element (RWST r w s m a) -> RWST r w s m a
opoint Element (RWST r w s m a)
a = (r -> s -> m (a, s, w)) -> RWST r w s m a
forall r w s (m :: * -> *) a.
(r -> s -> m (a, s, w)) -> RWST r w s m a
Strict.RWST (\r
_ s
s -> (a, s, w) -> m (a, s, w)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a
Element (RWST r w s m a)
a, s
s, w
forall a. Monoid a => a
mempty))
    {-# INLINE opoint #-}
instance Applicative m => MonoPointed (StateT s m a) where
    opoint :: Element (StateT s m a) -> StateT s m a
opoint Element (StateT s m a)
a = (s -> m (a, s)) -> StateT s m a
forall s (m :: * -> *) a. (s -> m (a, s)) -> StateT s m a
StateT (\s
s -> (a, s) -> m (a, s)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a
Element (StateT s m a)
a, s
s))
    {-# INLINE opoint #-}
instance Applicative m => MonoPointed (Strict.StateT s m a) where
    opoint :: Element (StateT s m a) -> StateT s m a
opoint Element (StateT s m a)
a = (s -> m (a, s)) -> StateT s m a
forall s (m :: * -> *) a. (s -> m (a, s)) -> StateT s m a
Strict.StateT (\s
s -> (a, s) -> m (a, s)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a
Element (StateT s m a)
a, s
s))
    {-# INLINE opoint #-}
instance MonoPointed (ViewL a) where
    opoint :: Element (ViewL a) -> ViewL a
opoint Element (ViewL a)
a = a
Element (ViewL a)
a a -> Seq a -> ViewL a
forall a. a -> Seq a -> ViewL a
:< Seq a
forall a. Seq a
Seq.empty
    {-# INLINE opoint #-}
instance MonoPointed (ViewR a) where
    opoint :: Element (ViewR a) -> ViewR a
opoint Element (ViewR a)
a = Seq a
forall a. Seq a
Seq.empty Seq a -> a -> ViewR a
forall a. Seq a -> a -> ViewR a
:> a
Element (ViewR a)
a
    {-# INLINE opoint #-}
instance MonoPointed (Tree a) where
    opoint :: Element (Tree a) -> Tree a
opoint Element (Tree a)
a = a -> Forest a -> Tree a
forall a. a -> Forest a -> Tree a
Node a
Element (Tree a)
a []
    {-# INLINE opoint #-}
-- | @since 1.0.11.0
instance (Applicative f, Applicative g) => MonoPointed ((f :+: g) a) where
    opoint :: Element ((:+:) f g a) -> (:+:) f g a
opoint = g a -> (:+:) f g a
forall k (f :: k -> *) (g :: k -> *) (p :: k). g p -> (:+:) f g p
R1 (g a -> (:+:) f g a) -> (a -> g a) -> a -> (:+:) f g a
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. a -> g a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
    {-# INLINE opoint #-}


-- | Typeclass for monomorphic containers where it is always okay to
-- "extract" a value from with 'oextract', and where you can extrapolate
-- any "extracting" function to be a function on the whole part with
-- 'oextend'.
--
-- 'oextend' and 'oextract' should work together following the laws:
--
-- @
-- 'oextend' 'oextract'      = 'id'
-- 'oextract' . 'oextend' f  = f
-- 'oextend' f . 'oextend' g = 'oextend' (f . 'oextend' g)
-- @
--
-- As an intuition, @'oextend' f@ uses @f@ to "build up" a new @mono@ with
-- pieces from the old one received by @f@.
--
class MonoFunctor mono => MonoComonad mono where
    -- | Extract an element from @mono@.  Can be thought of as a dual
    -- concept to @opoint@.
    oextract :: mono -> Element mono
    -- | "Extend" a @mono -> 'Element' mono@ function to be a @mono ->
    -- mono@; that is, builds a new @mono@ from the old one by using pieces
    -- glimpsed from the given function.
    oextend :: (mono -> Element mono) -> mono -> mono

-- Not Comonad
instance MonoComonad (ViewL a) where
    oextract :: ViewL a -> Element (ViewL a)
oextract ~(a
x :< Seq a
_) = a
Element (ViewL a)
x
    {-# INLINE oextract #-}
    oextend :: (ViewL a -> Element (ViewL a)) -> ViewL a -> ViewL a
oextend ViewL a -> Element (ViewL a)
f w :: ViewL a
w@(~(a
_ :< Seq a
xxs)) =
        ViewL a -> Element (ViewL a)
f ViewL a
w a -> Seq a -> ViewL a
forall a. a -> Seq a -> ViewL a
:< case Seq a -> ViewL a
forall a. Seq a -> ViewL a
Seq.viewl Seq a
xxs of
                 ViewL a
EmptyL -> Seq a
forall a. Seq a
Seq.empty
                 ViewL a
xs     -> case (ViewL a -> Element (ViewL a)) -> ViewL a -> ViewL a
forall mono.
MonoComonad mono =>
(mono -> Element mono) -> mono -> mono
oextend ViewL a -> Element (ViewL a)
f ViewL a
xs of
                             ViewL a
EmptyL  -> Seq a
forall a. Seq a
Seq.empty
                             a
y :< Seq a
ys -> a
y a -> Seq a -> Seq a
forall a. a -> Seq a -> Seq a
Seq.<| Seq a
ys

instance MonoComonad (ViewR a) where
    oextract :: ViewR a -> Element (ViewR a)
oextract ~(Seq a
_ :> a
x) = a
Element (ViewR a)
x
    {-# INLINE oextract #-}
    oextend :: (ViewR a -> Element (ViewR a)) -> ViewR a -> ViewR a
oextend ViewR a -> Element (ViewR a)
f w :: ViewR a
w@(~(Seq a
xxs :> a
_)) =
        (case Seq a -> ViewR a
forall a. Seq a -> ViewR a
Seq.viewr Seq a
xxs of
           ViewR a
EmptyR -> Seq a
forall a. Seq a
Seq.empty
           ViewR a
xs     -> case (ViewR a -> Element (ViewR a)) -> ViewR a -> ViewR a
forall mono.
MonoComonad mono =>
(mono -> Element mono) -> mono -> mono
oextend ViewR a -> Element (ViewR a)
f ViewR a
xs of
                       ViewR a
EmptyR  -> Seq a
forall a. Seq a
Seq.empty
                       Seq a
ys :> a
y -> Seq a
ys Seq a -> a -> Seq a
forall a. Seq a -> a -> Seq a
Seq.|> a
y
        ) Seq a -> a -> ViewR a
forall a. Seq a -> a -> ViewR a
:> ViewR a -> Element (ViewR a)
f ViewR a
w

-- | Containers which, when two values are combined, the combined length is no
-- less than the larger of the two inputs. In code:
--
-- @
-- olength (x <> y) >= max (olength x) (olength y)
-- @
--
-- This class has no methods, and is simply used to assert that this law holds,
-- in order to provide guarantees of correctness (see, for instance,
-- "Data.NonNull").
--
-- This should have a @Semigroup@ superclass constraint, however, due to
-- @Semigroup@ only recently moving to base, some packages do not provide
-- instances.
class MonoFoldable mono => GrowingAppend mono

instance GrowingAppend (Seq.Seq a)
instance GrowingAppend [a]
instance GrowingAppend (V.Vector a)
instance U.Unbox a => GrowingAppend (U.Vector a)
instance VS.Storable a => GrowingAppend (VS.Vector a)
instance GrowingAppend S.ByteString
instance GrowingAppend L.ByteString
instance GrowingAppend T.Text
instance GrowingAppend TL.Text
instance GrowingAppend (NonEmpty a)
instance Ord k => GrowingAppend (Map k v)
instance (Eq k, Hashable k) => GrowingAppend (HashMap k v)
instance Ord v => GrowingAppend (Set.Set v)
instance (Eq v, Hashable v) => GrowingAppend (HashSet.HashSet v)
instance GrowingAppend IntSet.IntSet
instance GrowingAppend (IntMap v)

-- | 'intercalate' @seq seqs@ inserts @seq@ in between @seqs@ and
-- concatenates the result.
--
-- @since 1.0.0
ointercalate :: (MonoFoldable mono, Monoid (Element mono))
             => Element mono
             -> mono
             -> Element mono
ointercalate :: Element mono -> mono -> Element mono
ointercalate Element mono
x = [Element mono] -> Element mono
forall a. Monoid a => [a] -> a
mconcat ([Element mono] -> Element mono)
-> (mono -> [Element mono]) -> mono -> Element mono
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Element mono -> [Element mono] -> [Element mono]
forall a. a -> [a] -> [a]
List.intersperse Element mono
x ([Element mono] -> [Element mono])
-> (mono -> [Element mono]) -> mono -> [Element mono]
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. mono -> [Element mono]
forall mono. MonoFoldable mono => mono -> [Element mono]
otoList
{-# INLINE [0] ointercalate #-}
{-# RULES "ointercalate list" forall x.
        ointercalate x = List.intercalate x . otoList #-}
{-# RULES "intercalate ByteString" forall x.
        ointercalate x = S.intercalate x . otoList #-}
{-# RULES "intercalate LByteString" forall x.
        ointercalate x = L.intercalate x . otoList #-}
{-# RULES "intercalate Text" forall x.
        ointercalate x = T.intercalate x . otoList #-}
{-# RULES "intercalate LText" forall x.
        ointercalate x = TL.intercalate x . otoList #-}

-- | Provides a `MonoFoldable`, `MonoFunctor` or `MonoPointed` for an arbitrary
-- `F.Foldable`, `Functor` or `Applicative`.
--
-- Useful for, e.g., passing a `F.Foldable` type you don't own into a
-- function that expects a `MonoFoldable`.
--
-- > // package A
-- > data MyList a = MyList [a] deriving Foldable
-- >
-- > // package B
-- > process :: MonoFoldable mono => mono -> IO ()
-- >
-- > // package C
-- > process (WrappedPoly (MyList []))
--
-- @since 1.0.13.0
newtype WrappedPoly f a = WrappedPoly { WrappedPoly f a -> f a
unwrapPoly :: f a }
    deriving newtype (a -> WrappedPoly f a -> Bool
WrappedPoly f m -> m
WrappedPoly f a -> [a]
WrappedPoly f a -> Bool
WrappedPoly f a -> Int
WrappedPoly f a -> a
WrappedPoly f a -> a
WrappedPoly f a -> a
WrappedPoly f a -> a
(a -> m) -> WrappedPoly f a -> m
(a -> m) -> WrappedPoly f a -> m
(a -> b -> b) -> b -> WrappedPoly f a -> b
(a -> b -> b) -> b -> WrappedPoly f a -> b
(b -> a -> b) -> b -> WrappedPoly f a -> b
(b -> a -> b) -> b -> WrappedPoly f a -> b
(a -> a -> a) -> WrappedPoly f a -> a
(a -> a -> a) -> WrappedPoly f a -> a
(forall m. Monoid m => WrappedPoly f m -> m)
-> (forall m a. Monoid m => (a -> m) -> WrappedPoly f a -> m)
-> (forall m a. Monoid m => (a -> m) -> WrappedPoly f a -> m)
-> (forall a b. (a -> b -> b) -> b -> WrappedPoly f a -> b)
-> (forall a b. (a -> b -> b) -> b -> WrappedPoly f a -> b)
-> (forall b a. (b -> a -> b) -> b -> WrappedPoly f a -> b)
-> (forall b a. (b -> a -> b) -> b -> WrappedPoly f a -> b)
-> (forall a. (a -> a -> a) -> WrappedPoly f a -> a)
-> (forall a. (a -> a -> a) -> WrappedPoly f a -> a)
-> (forall a. WrappedPoly f a -> [a])
-> (forall a. WrappedPoly f a -> Bool)
-> (forall a. WrappedPoly f a -> Int)
-> (forall a. Eq a => a -> WrappedPoly f a -> Bool)
-> (forall a. Ord a => WrappedPoly f a -> a)
-> (forall a. Ord a => WrappedPoly f a -> a)
-> (forall a. Num a => WrappedPoly f a -> a)
-> (forall a. Num a => WrappedPoly f a -> a)
-> Foldable (WrappedPoly f)
forall a. Eq a => a -> WrappedPoly f a -> Bool
forall a. Num a => WrappedPoly f a -> a
forall a. Ord a => WrappedPoly f a -> a
forall m. Monoid m => WrappedPoly f m -> m
forall a. WrappedPoly f a -> Bool
forall a. WrappedPoly f a -> Int
forall a. WrappedPoly f a -> [a]
forall a. (a -> a -> a) -> WrappedPoly f a -> a
forall m a. Monoid m => (a -> m) -> WrappedPoly f a -> m
forall b a. (b -> a -> b) -> b -> WrappedPoly f a -> b
forall a b. (a -> b -> b) -> b -> WrappedPoly f a -> b
forall (f :: * -> *) a.
(Foldable f, Eq a) =>
a -> WrappedPoly f a -> Bool
forall (f :: * -> *) a. (Foldable f, Num a) => WrappedPoly f a -> a
forall (f :: * -> *) a. (Foldable f, Ord a) => WrappedPoly f a -> a
forall (f :: * -> *) m.
(Foldable f, Monoid m) =>
WrappedPoly f m -> m
forall (f :: * -> *) a. Foldable f => WrappedPoly f a -> Bool
forall (f :: * -> *) a. Foldable f => WrappedPoly f a -> Int
forall (f :: * -> *) a. Foldable f => WrappedPoly f a -> [a]
forall (f :: * -> *) a.
Foldable f =>
(a -> a -> a) -> WrappedPoly f a -> a
forall (f :: * -> *) m a.
(Foldable f, Monoid m) =>
(a -> m) -> WrappedPoly f a -> m
forall (f :: * -> *) b a.
Foldable f =>
(b -> a -> b) -> b -> WrappedPoly f a -> b
forall (f :: * -> *) a b.
Foldable f =>
(a -> b -> b) -> b -> WrappedPoly f a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: WrappedPoly f a -> a
$cproduct :: forall (f :: * -> *) a. (Foldable f, Num a) => WrappedPoly f a -> a
sum :: WrappedPoly f a -> a
$csum :: forall (f :: * -> *) a. (Foldable f, Num a) => WrappedPoly f a -> a
minimum :: WrappedPoly f a -> a
$cminimum :: forall (f :: * -> *) a. (Foldable f, Ord a) => WrappedPoly f a -> a
maximum :: WrappedPoly f a -> a
$cmaximum :: forall (f :: * -> *) a. (Foldable f, Ord a) => WrappedPoly f a -> a
elem :: a -> WrappedPoly f a -> Bool
$celem :: forall (f :: * -> *) a.
(Foldable f, Eq a) =>
a -> WrappedPoly f a -> Bool
length :: WrappedPoly f a -> Int
$clength :: forall (f :: * -> *) a. Foldable f => WrappedPoly f a -> Int
null :: WrappedPoly f a -> Bool
$cnull :: forall (f :: * -> *) a. Foldable f => WrappedPoly f a -> Bool
toList :: WrappedPoly f a -> [a]
$ctoList :: forall (f :: * -> *) a. Foldable f => WrappedPoly f a -> [a]
foldl1 :: (a -> a -> a) -> WrappedPoly f a -> a
$cfoldl1 :: forall (f :: * -> *) a.
Foldable f =>
(a -> a -> a) -> WrappedPoly f a -> a
foldr1 :: (a -> a -> a) -> WrappedPoly f a -> a
$cfoldr1 :: forall (f :: * -> *) a.
Foldable f =>
(a -> a -> a) -> WrappedPoly f a -> a
foldl' :: (b -> a -> b) -> b -> WrappedPoly f a -> b
$cfoldl' :: forall (f :: * -> *) b a.
Foldable f =>
(b -> a -> b) -> b -> WrappedPoly f a -> b
foldl :: (b -> a -> b) -> b -> WrappedPoly f a -> b
$cfoldl :: forall (f :: * -> *) b a.
Foldable f =>
(b -> a -> b) -> b -> WrappedPoly f a -> b
foldr' :: (a -> b -> b) -> b -> WrappedPoly f a -> b
$cfoldr' :: forall (f :: * -> *) a b.
Foldable f =>
(a -> b -> b) -> b -> WrappedPoly f a -> b
foldr :: (a -> b -> b) -> b -> WrappedPoly f a -> b
$cfoldr :: forall (f :: * -> *) a b.
Foldable f =>
(a -> b -> b) -> b -> WrappedPoly f a -> b
foldMap' :: (a -> m) -> WrappedPoly f a -> m
$cfoldMap' :: forall (f :: * -> *) m a.
(Foldable f, Monoid m) =>
(a -> m) -> WrappedPoly f a -> m
foldMap :: (a -> m) -> WrappedPoly f a -> m
$cfoldMap :: forall (f :: * -> *) m a.
(Foldable f, Monoid m) =>
(a -> m) -> WrappedPoly f a -> m
fold :: WrappedPoly f m -> m
$cfold :: forall (f :: * -> *) m.
(Foldable f, Monoid m) =>
WrappedPoly f m -> m
F.Foldable, a -> WrappedPoly f b -> WrappedPoly f a
(a -> b) -> WrappedPoly f a -> WrappedPoly f b
(forall a b. (a -> b) -> WrappedPoly f a -> WrappedPoly f b)
-> (forall a b. a -> WrappedPoly f b -> WrappedPoly f a)
-> Functor (WrappedPoly f)
forall a b. a -> WrappedPoly f b -> WrappedPoly f a
forall a b. (a -> b) -> WrappedPoly f a -> WrappedPoly f b
forall (f :: * -> *) a b.
Functor f =>
a -> WrappedPoly f b -> WrappedPoly f a
forall (f :: * -> *) a b.
Functor f =>
(a -> b) -> WrappedPoly f a -> WrappedPoly f b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> WrappedPoly f b -> WrappedPoly f a
$c<$ :: forall (f :: * -> *) a b.
Functor f =>
a -> WrappedPoly f b -> WrappedPoly f a
fmap :: (a -> b) -> WrappedPoly f a -> WrappedPoly f b
$cfmap :: forall (f :: * -> *) a b.
Functor f =>
(a -> b) -> WrappedPoly f a -> WrappedPoly f b
Functor, Functor (WrappedPoly f)
a -> WrappedPoly f a
Functor (WrappedPoly f)
-> (forall a. a -> WrappedPoly f a)
-> (forall a b.
    WrappedPoly f (a -> b) -> WrappedPoly f a -> WrappedPoly f b)
-> (forall a b c.
    (a -> b -> c)
    -> WrappedPoly f a -> WrappedPoly f b -> WrappedPoly f c)
-> (forall a b.
    WrappedPoly f a -> WrappedPoly f b -> WrappedPoly f b)
-> (forall a b.
    WrappedPoly f a -> WrappedPoly f b -> WrappedPoly f a)
-> Applicative (WrappedPoly f)
WrappedPoly f a -> WrappedPoly f b -> WrappedPoly f b
WrappedPoly f a -> WrappedPoly f b -> WrappedPoly f a
WrappedPoly f (a -> b) -> WrappedPoly f a -> WrappedPoly f b
(a -> b -> c)
-> WrappedPoly f a -> WrappedPoly f b -> WrappedPoly f c
forall a. a -> WrappedPoly f a
forall a b. WrappedPoly f a -> WrappedPoly f b -> WrappedPoly f a
forall a b. WrappedPoly f a -> WrappedPoly f b -> WrappedPoly f b
forall a b.
WrappedPoly f (a -> b) -> WrappedPoly f a -> WrappedPoly f b
forall a b c.
(a -> b -> c)
-> WrappedPoly f a -> WrappedPoly f b -> WrappedPoly f c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
forall (f :: * -> *). Applicative f => Functor (WrappedPoly f)
forall (f :: * -> *) a. Applicative f => a -> WrappedPoly f a
forall (f :: * -> *) a b.
Applicative f =>
WrappedPoly f a -> WrappedPoly f b -> WrappedPoly f a
forall (f :: * -> *) a b.
Applicative f =>
WrappedPoly f a -> WrappedPoly f b -> WrappedPoly f b
forall (f :: * -> *) a b.
Applicative f =>
WrappedPoly f (a -> b) -> WrappedPoly f a -> WrappedPoly f b
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c)
-> WrappedPoly f a -> WrappedPoly f b -> WrappedPoly f c
<* :: WrappedPoly f a -> WrappedPoly f b -> WrappedPoly f a
$c<* :: forall (f :: * -> *) a b.
Applicative f =>
WrappedPoly f a -> WrappedPoly f b -> WrappedPoly f a
*> :: WrappedPoly f a -> WrappedPoly f b -> WrappedPoly f b
$c*> :: forall (f :: * -> *) a b.
Applicative f =>
WrappedPoly f a -> WrappedPoly f b -> WrappedPoly f b
liftA2 :: (a -> b -> c)
-> WrappedPoly f a -> WrappedPoly f b -> WrappedPoly f c
$cliftA2 :: forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c)
-> WrappedPoly f a -> WrappedPoly f b -> WrappedPoly f c
<*> :: WrappedPoly f (a -> b) -> WrappedPoly f a -> WrappedPoly f b
$c<*> :: forall (f :: * -> *) a b.
Applicative f =>
WrappedPoly f (a -> b) -> WrappedPoly f a -> WrappedPoly f b
pure :: a -> WrappedPoly f a
$cpure :: forall (f :: * -> *) a. Applicative f => a -> WrappedPoly f a
$cp1Applicative :: forall (f :: * -> *). Applicative f => Functor (WrappedPoly f)
Applicative, Applicative (WrappedPoly f)
a -> WrappedPoly f a
Applicative (WrappedPoly f)
-> (forall a b.
    WrappedPoly f a -> (a -> WrappedPoly f b) -> WrappedPoly f b)
-> (forall a b.
    WrappedPoly f a -> WrappedPoly f b -> WrappedPoly f b)
-> (forall a. a -> WrappedPoly f a)
-> Monad (WrappedPoly f)
WrappedPoly f a -> (a -> WrappedPoly f b) -> WrappedPoly f b
WrappedPoly f a -> WrappedPoly f b -> WrappedPoly f b
forall a. a -> WrappedPoly f a
forall a b. WrappedPoly f a -> WrappedPoly f b -> WrappedPoly f b
forall a b.
WrappedPoly f a -> (a -> WrappedPoly f b) -> WrappedPoly f b
forall (f :: * -> *). Monad f => Applicative (WrappedPoly f)
forall (f :: * -> *) a. Monad f => a -> WrappedPoly f a
forall (f :: * -> *) a b.
Monad f =>
WrappedPoly f a -> WrappedPoly f b -> WrappedPoly f b
forall (f :: * -> *) a b.
Monad f =>
WrappedPoly f a -> (a -> WrappedPoly f b) -> WrappedPoly f b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: a -> WrappedPoly f a
$creturn :: forall (f :: * -> *) a. Monad f => a -> WrappedPoly f a
>> :: WrappedPoly f a -> WrappedPoly f b -> WrappedPoly f b
$c>> :: forall (f :: * -> *) a b.
Monad f =>
WrappedPoly f a -> WrappedPoly f b -> WrappedPoly f b
>>= :: WrappedPoly f a -> (a -> WrappedPoly f b) -> WrappedPoly f b
$c>>= :: forall (f :: * -> *) a b.
Monad f =>
WrappedPoly f a -> (a -> WrappedPoly f b) -> WrappedPoly f b
$cp1Monad :: forall (f :: * -> *). Monad f => Applicative (WrappedPoly f)
Monad)

type instance Element (WrappedPoly f a) = a
instance F.Foldable f  => MonoFoldable (WrappedPoly f a)
instance Functor f     => MonoFunctor (WrappedPoly f a)
instance Applicative f => MonoPointed (WrappedPoly f a)


-- | Provides a `F.Foldable` for an arbitrary `MonoFoldable`.
--
-- @since 1.0.14.0
data WrappedMono mono a where
    WrappedMono :: Element mono ~ a => mono -> WrappedMono mono a

-- | Unwraps a `WrappedMono`.
--
-- @since 1.0.14.0
unwrapMono :: WrappedMono mono a -> mono
unwrapMono :: WrappedMono mono a -> mono
unwrapMono (WrappedMono mono
mono) = mono
mono
{-# INLINE unwrapMono #-}

type instance Element (WrappedMono mono a) = Element mono

instance MonoFoldable mono => MonoFoldable (WrappedMono mono a) where
    ofoldMap :: (Element (WrappedMono mono a) -> m) -> WrappedMono mono a -> m
ofoldMap Element (WrappedMono mono a) -> m
f = (Element mono -> m) -> mono -> m
forall mono m.
(MonoFoldable mono, Monoid m) =>
(Element mono -> m) -> mono -> m
ofoldMap Element mono -> m
Element (WrappedMono mono a) -> m
f (mono -> m)
-> (WrappedMono mono a -> mono) -> WrappedMono mono a -> m
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. WrappedMono mono a -> mono
forall mono a. WrappedMono mono a -> mono
unwrapMono
    {-# INLINE ofoldMap #-}
    ofoldr :: (Element (WrappedMono mono a) -> b -> b)
-> b -> WrappedMono mono a -> b
ofoldr Element (WrappedMono mono a) -> b -> b
f b
z = (Element mono -> b -> b) -> b -> mono -> b
forall mono b.
MonoFoldable mono =>
(Element mono -> b -> b) -> b -> mono -> b
ofoldr Element mono -> b -> b
Element (WrappedMono mono a) -> b -> b
f b
z (mono -> b)
-> (WrappedMono mono a -> mono) -> WrappedMono mono a -> b
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. WrappedMono mono a -> mono
forall mono a. WrappedMono mono a -> mono
unwrapMono
    {-# INLINE ofoldr #-}
    ofoldl' :: (a -> Element (WrappedMono mono a) -> a)
-> a -> WrappedMono mono a -> a
ofoldl' a -> Element (WrappedMono mono a) -> a
f a
z = (a -> Element mono -> a) -> a -> mono -> a
forall mono a.
MonoFoldable mono =>
(a -> Element mono -> a) -> a -> mono -> a
ofoldl' a -> Element mono -> a
a -> Element (WrappedMono mono a) -> a
f a
z (mono -> a)
-> (WrappedMono mono a -> mono) -> WrappedMono mono a -> a
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. WrappedMono mono a -> mono
forall mono a. WrappedMono mono a -> mono
unwrapMono
    {-# INLINE ofoldl' #-}
    otoList :: WrappedMono mono a -> [Element (WrappedMono mono a)]
otoList = mono -> [Element mono]
forall mono. MonoFoldable mono => mono -> [Element mono]
otoList (mono -> [Element mono])
-> (WrappedMono mono a -> mono)
-> WrappedMono mono a
-> [Element mono]
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. WrappedMono mono a -> mono
forall mono a. WrappedMono mono a -> mono
unwrapMono
    {-# INLINE otoList #-}
    oall :: (Element (WrappedMono mono a) -> Bool)
-> WrappedMono mono a -> Bool
oall Element (WrappedMono mono a) -> Bool
f = (Element mono -> Bool) -> mono -> Bool
forall mono.
MonoFoldable mono =>
(Element mono -> Bool) -> mono -> Bool
oall Element mono -> Bool
Element (WrappedMono mono a) -> Bool
f (mono -> Bool)
-> (WrappedMono mono a -> mono) -> WrappedMono mono a -> Bool
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. WrappedMono mono a -> mono
forall mono a. WrappedMono mono a -> mono
unwrapMono
    {-# INLINE oall #-}
    oany :: (Element (WrappedMono mono a) -> Bool)
-> WrappedMono mono a -> Bool
oany Element (WrappedMono mono a) -> Bool
f = (Element mono -> Bool) -> mono -> Bool
forall mono.
MonoFoldable mono =>
(Element mono -> Bool) -> mono -> Bool
oany Element mono -> Bool
Element (WrappedMono mono a) -> Bool
f (mono -> Bool)
-> (WrappedMono mono a -> mono) -> WrappedMono mono a -> Bool
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. WrappedMono mono a -> mono
forall mono a. WrappedMono mono a -> mono
unwrapMono
    {-# INLINE oany #-}
    onull :: WrappedMono mono a -> Bool
onull = mono -> Bool
forall mono. MonoFoldable mono => mono -> Bool
onull (mono -> Bool)
-> (WrappedMono mono a -> mono) -> WrappedMono mono a -> Bool
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. WrappedMono mono a -> mono
forall mono a. WrappedMono mono a -> mono
unwrapMono
    {-# INLINE onull #-}
    olength :: WrappedMono mono a -> Int
olength = mono -> Int
forall mono. MonoFoldable mono => mono -> Int
olength (mono -> Int)
-> (WrappedMono mono a -> mono) -> WrappedMono mono a -> Int
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. WrappedMono mono a -> mono
forall mono a. WrappedMono mono a -> mono
unwrapMono
    {-# INLINE olength #-}
    olength64 :: WrappedMono mono a -> Int64
olength64 = mono -> Int64
forall mono. MonoFoldable mono => mono -> Int64
olength64 (mono -> Int64)
-> (WrappedMono mono a -> mono) -> WrappedMono mono a -> Int64
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. WrappedMono mono a -> mono
forall mono a. WrappedMono mono a -> mono
unwrapMono
    {-# INLINE olength64 #-}
    ocompareLength :: WrappedMono mono a -> i -> Ordering
ocompareLength WrappedMono mono a
mono i
i = mono -> i -> Ordering
forall mono i.
(MonoFoldable mono, Integral i) =>
mono -> i -> Ordering
ocompareLength (WrappedMono mono a -> mono
forall mono a. WrappedMono mono a -> mono
unwrapMono WrappedMono mono a
mono) i
i
    {-# INLINE ocompareLength #-}
    otraverse_ :: (Element (WrappedMono mono a) -> f b) -> WrappedMono mono a -> f ()
otraverse_ Element (WrappedMono mono a) -> f b
f = (Element mono -> f b) -> mono -> f ()
forall mono (f :: * -> *) b.
(MonoFoldable mono, Applicative f) =>
(Element mono -> f b) -> mono -> f ()
otraverse_ Element mono -> f b
Element (WrappedMono mono a) -> f b
f (mono -> f ())
-> (WrappedMono mono a -> mono) -> WrappedMono mono a -> f ()
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. WrappedMono mono a -> mono
forall mono a. WrappedMono mono a -> mono
unwrapMono
    {-# INLINE otraverse_ #-}
    ofor_ :: WrappedMono mono a -> (Element (WrappedMono mono a) -> f b) -> f ()
ofor_ WrappedMono mono a
mono Element (WrappedMono mono a) -> f b
f = mono -> (Element mono -> f b) -> f ()
forall mono (f :: * -> *) b.
(MonoFoldable mono, Applicative f) =>
mono -> (Element mono -> f b) -> f ()
ofor_ (WrappedMono mono a -> mono
forall mono a. WrappedMono mono a -> mono
unwrapMono WrappedMono mono a
mono) Element mono -> f b
Element (WrappedMono mono a) -> f b
f
    {-# INLINE ofor_ #-}
    omapM_ :: (Element (WrappedMono mono a) -> m ())
-> WrappedMono mono a -> m ()
omapM_ Element (WrappedMono mono a) -> m ()
f = (Element mono -> m ()) -> mono -> m ()
forall mono (m :: * -> *).
(MonoFoldable mono, Applicative m) =>
(Element mono -> m ()) -> mono -> m ()
omapM_ Element mono -> m ()
Element (WrappedMono mono a) -> m ()
f (mono -> m ())
-> (WrappedMono mono a -> mono) -> WrappedMono mono a -> m ()
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. WrappedMono mono a -> mono
forall mono a. WrappedMono mono a -> mono
unwrapMono
    {-# INLINE omapM_ #-}
    oforM_ :: WrappedMono mono a
-> (Element (WrappedMono mono a) -> m ()) -> m ()
oforM_ WrappedMono mono a
mono Element (WrappedMono mono a) -> m ()
f = mono -> (Element mono -> m ()) -> m ()
forall mono (m :: * -> *).
(MonoFoldable mono, Applicative m) =>
mono -> (Element mono -> m ()) -> m ()
oforM_ (WrappedMono mono a -> mono
forall mono a. WrappedMono mono a -> mono
unwrapMono WrappedMono mono a
mono) Element mono -> m ()
Element (WrappedMono mono a) -> m ()
f
    {-# INLINE oforM_ #-}
    ofoldlM :: (a -> Element (WrappedMono mono a) -> m a)
-> a -> WrappedMono mono a -> m a
ofoldlM a -> Element (WrappedMono mono a) -> m a
f a
z = (a -> Element mono -> m a) -> a -> mono -> m a
forall mono (m :: * -> *) a.
(MonoFoldable mono, Monad m) =>
(a -> Element mono -> m a) -> a -> mono -> m a
ofoldlM a -> Element mono -> m a
a -> Element (WrappedMono mono a) -> m a
f a
z (mono -> m a)
-> (WrappedMono mono a -> mono) -> WrappedMono mono a -> m a
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. WrappedMono mono a -> mono
forall mono a. WrappedMono mono a -> mono
unwrapMono
    {-# INLINE ofoldlM #-}
    ofoldMap1Ex :: (Element (WrappedMono mono a) -> m) -> WrappedMono mono a -> m
ofoldMap1Ex Element (WrappedMono mono a) -> m
f = (Element mono -> m) -> mono -> m
forall mono m.
(MonoFoldable mono, Semigroup m) =>
(Element mono -> m) -> mono -> m
ofoldMap1Ex Element mono -> m
Element (WrappedMono mono a) -> m
f (mono -> m)
-> (WrappedMono mono a -> mono) -> WrappedMono mono a -> m
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. WrappedMono mono a -> mono
forall mono a. WrappedMono mono a -> mono
unwrapMono
    {-# INLINE ofoldMap1Ex #-}
    ofoldr1Ex :: (Element (WrappedMono mono a)
 -> Element (WrappedMono mono a) -> Element (WrappedMono mono a))
-> WrappedMono mono a -> Element (WrappedMono mono a)
ofoldr1Ex Element (WrappedMono mono a)
-> Element (WrappedMono mono a) -> Element (WrappedMono mono a)
f = (Element mono -> Element mono -> Element mono)
-> mono -> Element mono
forall mono.
MonoFoldable mono =>
(Element mono -> Element mono -> Element mono)
-> mono -> Element mono
ofoldr1Ex Element mono -> Element mono -> Element mono
Element (WrappedMono mono a)
-> Element (WrappedMono mono a) -> Element (WrappedMono mono a)
f (mono -> Element mono)
-> (WrappedMono mono a -> mono)
-> WrappedMono mono a
-> Element mono
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. WrappedMono mono a -> mono
forall mono a. WrappedMono mono a -> mono
unwrapMono
    {-# INLINE ofoldr1Ex #-}
    ofoldl1Ex' :: (Element (WrappedMono mono a)
 -> Element (WrappedMono mono a) -> Element (WrappedMono mono a))
-> WrappedMono mono a -> Element (WrappedMono mono a)
ofoldl1Ex' Element (WrappedMono mono a)
-> Element (WrappedMono mono a) -> Element (WrappedMono mono a)
f = (Element mono -> Element mono -> Element mono)
-> mono -> Element mono
forall mono.
MonoFoldable mono =>
(Element mono -> Element mono -> Element mono)
-> mono -> Element mono
ofoldl1Ex' Element mono -> Element mono -> Element mono
Element (WrappedMono mono a)
-> Element (WrappedMono mono a) -> Element (WrappedMono mono a)
f (mono -> Element mono)
-> (WrappedMono mono a -> mono)
-> WrappedMono mono a
-> Element mono
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. WrappedMono mono a -> mono
forall mono a. WrappedMono mono a -> mono
unwrapMono
    {-# INLINE ofoldl1Ex' #-}
    headEx :: WrappedMono mono a -> Element (WrappedMono mono a)
headEx = mono -> Element mono
forall mono. MonoFoldable mono => mono -> Element mono
headEx (mono -> Element mono)
-> (WrappedMono mono a -> mono)
-> WrappedMono mono a
-> Element mono
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. WrappedMono mono a -> mono
forall mono a. WrappedMono mono a -> mono
unwrapMono
    {-# INLINE headEx #-}
    lastEx :: WrappedMono mono a -> Element (WrappedMono mono a)
lastEx = mono -> Element mono
forall mono. MonoFoldable mono => mono -> Element mono
lastEx (mono -> Element mono)
-> (WrappedMono mono a -> mono)
-> WrappedMono mono a
-> Element mono
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. WrappedMono mono a -> mono
forall mono a. WrappedMono mono a -> mono
unwrapMono
    {-# INLINE lastEx #-}
    unsafeHead :: WrappedMono mono a -> Element (WrappedMono mono a)
unsafeHead = mono -> Element mono
forall mono. MonoFoldable mono => mono -> Element mono
unsafeHead (mono -> Element mono)
-> (WrappedMono mono a -> mono)
-> WrappedMono mono a
-> Element mono
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. WrappedMono mono a -> mono
forall mono a. WrappedMono mono a -> mono
unwrapMono
    {-# INLINE unsafeHead #-}
    unsafeLast :: WrappedMono mono a -> Element (WrappedMono mono a)
unsafeLast = mono -> Element mono
forall mono. MonoFoldable mono => mono -> Element mono
unsafeLast (mono -> Element mono)
-> (WrappedMono mono a -> mono)
-> WrappedMono mono a
-> Element mono
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. WrappedMono mono a -> mono
forall mono a. WrappedMono mono a -> mono
unwrapMono
    {-# INLINE unsafeLast #-}
    maximumByEx :: (Element (WrappedMono mono a)
 -> Element (WrappedMono mono a) -> Ordering)
-> WrappedMono mono a -> Element (WrappedMono mono a)
maximumByEx Element (WrappedMono mono a)
-> Element (WrappedMono mono a) -> Ordering
f = (Element mono -> Element mono -> Ordering) -> mono -> Element mono
forall mono.
MonoFoldable mono =>
(Element mono -> Element mono -> Ordering) -> mono -> Element mono
maximumByEx Element mono -> Element mono -> Ordering
Element (WrappedMono mono a)
-> Element (WrappedMono mono a) -> Ordering
f (mono -> Element mono)
-> (WrappedMono mono a -> mono)
-> WrappedMono mono a
-> Element mono
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. WrappedMono mono a -> mono
forall mono a. WrappedMono mono a -> mono
unwrapMono
    {-# INLINE maximumByEx #-}
    minimumByEx :: (Element (WrappedMono mono a)
 -> Element (WrappedMono mono a) -> Ordering)
-> WrappedMono mono a -> Element (WrappedMono mono a)
minimumByEx Element (WrappedMono mono a)
-> Element (WrappedMono mono a) -> Ordering
f = (Element mono -> Element mono -> Ordering) -> mono -> Element mono
forall mono.
MonoFoldable mono =>
(Element mono -> Element mono -> Ordering) -> mono -> Element mono
minimumByEx Element mono -> Element mono -> Ordering
Element (WrappedMono mono a)
-> Element (WrappedMono mono a) -> Ordering
f (mono -> Element mono)
-> (WrappedMono mono a -> mono)
-> WrappedMono mono a
-> Element mono
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. WrappedMono mono a -> mono
forall mono a. WrappedMono mono a -> mono
unwrapMono
    {-# INLINE minimumByEx #-}
    oelem :: Element (WrappedMono mono a) -> WrappedMono mono a -> Bool
oelem Element (WrappedMono mono a)
a = Element mono -> mono -> Bool
forall mono.
(MonoFoldable mono, Eq (Element mono)) =>
Element mono -> mono -> Bool
oelem Element mono
Element (WrappedMono mono a)
a (mono -> Bool)
-> (WrappedMono mono a -> mono) -> WrappedMono mono a -> Bool
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. WrappedMono mono a -> mono
forall mono a. WrappedMono mono a -> mono
unwrapMono
    {-# INLINE oelem #-}
    onotElem :: Element (WrappedMono mono a) -> WrappedMono mono a -> Bool
onotElem Element (WrappedMono mono a)
a = Element mono -> mono -> Bool
forall mono.
(MonoFoldable mono, Eq (Element mono)) =>
Element mono -> mono -> Bool
onotElem Element mono
Element (WrappedMono mono a)
a (mono -> Bool)
-> (WrappedMono mono a -> mono) -> WrappedMono mono a -> Bool
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. WrappedMono mono a -> mono
forall mono a. WrappedMono mono a -> mono
unwrapMono
    {-# INLINE onotElem #-}

instance MonoFunctor mono => MonoFunctor (WrappedMono mono a) where
    omap :: (Element (WrappedMono mono a) -> Element (WrappedMono mono a))
-> WrappedMono mono a -> WrappedMono mono a
omap Element (WrappedMono mono a) -> Element (WrappedMono mono a)
f (WrappedMono mono
mono) = mono -> WrappedMono mono a
forall mono a. (Element mono ~ a) => mono -> WrappedMono mono a
WrappedMono ((Element mono -> Element mono) -> mono -> mono
forall mono.
MonoFunctor mono =>
(Element mono -> Element mono) -> mono -> mono
omap Element mono -> Element mono
Element (WrappedMono mono a) -> Element (WrappedMono mono a)
f mono
mono)
    {-# INLINE omap #-}

instance (MonoPointed mono, Element mono ~ a) => MonoPointed (WrappedMono mono a) where
    opoint :: Element (WrappedMono mono a) -> WrappedMono mono a
opoint Element (WrappedMono mono a)
a = mono -> WrappedMono mono a
forall mono a. (Element mono ~ a) => mono -> WrappedMono mono a
WrappedMono (Element mono -> mono
forall mono. MonoPointed mono => Element mono -> mono
opoint Element mono
Element (WrappedMono mono a)
a)
    {-# INLINE opoint #-}

instance MonoFoldable mono => F.Foldable (WrappedMono mono) where
    foldr :: (a -> b -> b) -> b -> WrappedMono mono a -> b
foldr a -> b -> b
f b
zero (WrappedMono mono
mono) = (Element mono -> b -> b) -> b -> mono -> b
forall mono b.
MonoFoldable mono =>
(Element mono -> b -> b) -> b -> mono -> b
ofoldr a -> b -> b
Element mono -> b -> b
f b
zero mono
mono
    {-# INLINE foldr #-}
    foldMap :: (a -> m) -> WrappedMono mono a -> m
foldMap a -> m
f (WrappedMono mono
mono) = (Element mono -> m) -> mono -> m
forall mono m.
(MonoFoldable mono, Monoid m) =>
(Element mono -> m) -> mono -> m
ofoldMap a -> m
Element mono -> m
f mono
mono
    {-# INLINE foldMap #-}
    foldl' :: (b -> a -> b) -> b -> WrappedMono mono a -> b
foldl' b -> a -> b
f b
z (WrappedMono mono
mono) = (b -> Element mono -> b) -> b -> mono -> b
forall mono a.
MonoFoldable mono =>
(a -> Element mono -> a) -> a -> mono -> a
ofoldl' b -> a -> b
b -> Element mono -> b
f b
z mono
mono
    {-# INLINE foldl' #-}
    foldl1 :: (a -> a -> a) -> WrappedMono mono a -> a
foldl1 a -> a -> a
f (WrappedMono mono
mono) = (Element mono -> Element mono -> Element mono)
-> mono -> Element mono
forall mono.
MonoFoldable mono =>
(Element mono -> Element mono -> Element mono)
-> mono -> Element mono
ofoldl1Ex' a -> a -> a
Element mono -> Element mono -> Element mono
f mono
mono
    {-# INLINE foldl1 #-}
    toList :: WrappedMono mono a -> [a]
toList (WrappedMono mono
mono) = mono -> [Element mono]
forall mono. MonoFoldable mono => mono -> [Element mono]
otoList mono
mono
    {-# INLINE toList #-}
    null :: WrappedMono mono a -> Bool
null (WrappedMono mono
mono) = mono -> Bool
forall mono. MonoFoldable mono => mono -> Bool
onull mono
mono
    {-# INLINE null #-}
    length :: WrappedMono mono a -> Int
length (WrappedMono mono
mono) = mono -> Int
forall mono. MonoFoldable mono => mono -> Int
olength mono
mono
    {-# INLINE length #-}
    elem :: a -> WrappedMono mono a -> Bool
elem a
a (WrappedMono mono
mono) = Element mono -> mono -> Bool
forall mono.
(MonoFoldable mono, Eq (Element mono)) =>
Element mono -> mono -> Bool
oelem a
Element mono
a mono
mono
    {-# INLINE elem #-}
    maximum :: WrappedMono mono a -> a
maximum (WrappedMono mono
mono) = mono -> Element mono
forall mono.
(MonoFoldable mono, Ord (Element mono)) =>
mono -> Element mono
maximumEx mono
mono
    {-# INLINE maximum #-}
    minimum :: WrappedMono mono a -> a
minimum (WrappedMono mono
mono) = mono -> Element mono
forall mono.
(MonoFoldable mono, Ord (Element mono)) =>
mono -> Element mono
minimumEx mono
mono
    {-# INLINE minimum #-}