linear-base-0.1.0: Standard library for linear types.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Functor.Linear

Description

The data functor hierarchy

This module defines the data functor library. Unlike in the case of non-linear, unrestricted, functors, there is a split between data functors, which represent containers, and control functors which represent effects. Please read this blog post. For more details, see Control.Functor.Linear.

  • Linear data functors should be thought of as containers of data.
  • Linear data applicative functors should be thought of as containers that can be zipped.
  • Linear data traversible functors should be thought of as containers which store a finite number of values.
Synopsis

Data Functor Hierarchy

class Functor f where Source #

Linear Data Functors should be thought of as containers holding values of type a over which you are able to apply a linear function of type a %1-> b on each value of type a in the functor and consume a given functor of type f a.

Methods

fmap :: (a %1 -> b) -> f a %1 -> f b Source #

Instances

Instances details
Functor [] Source # 
Instance details

Defined in Data.Functor.Linear.Internal.Functor

Methods

fmap :: (a %1 -> b) -> [a] %1 -> [b] Source #

Functor Maybe Source # 
Instance details

Defined in Data.Functor.Linear.Internal.Functor

Methods

fmap :: (a %1 -> b) -> Maybe a %1 -> Maybe b Source #

Functor Identity Source # 
Instance details

Defined in Data.Functor.Linear.Internal.Functor

Methods

fmap :: (a %1 -> b) -> Identity a %1 -> Identity b Source #

Functor Ur Source # 
Instance details

Defined in Data.Unrestricted.Internal.Instances

Methods

fmap :: (a %1 -> b) -> Ur a %1 -> Ur b Source #

Functor IO Source # 
Instance details

Defined in System.IO.Linear

Methods

fmap :: (a %1 -> b) -> IO a %1 -> IO b Source #

Functor RIO Source # 
Instance details

Defined in System.IO.Resource

Methods

fmap :: (a %1 -> b) -> RIO a %1 -> RIO b Source #

Functor Array Source # 
Instance details

Defined in Data.Array.Polarized.Pull.Internal

Methods

fmap :: (a %1 -> b) -> Array a %1 -> Array b Source #

Functor Array Source # 
Instance details

Defined in Data.Array.Mutable.Linear

Methods

fmap :: (a %1 -> b) -> Array a %1 -> Array b Source #

Functor Vector Source # 
Instance details

Defined in Data.Vector.Mutable.Linear

Methods

fmap :: (a %1 -> b) -> Vector a %1 -> Vector b Source #

Functor Array Source # 
Instance details

Defined in Data.Array.Polarized.Push

Methods

fmap :: (a %1 -> b) -> Array a %1 -> Array b Source #

Functor (Either e) Source # 
Instance details

Defined in Data.Functor.Linear.Internal.Functor

Methods

fmap :: (a %1 -> b) -> Either e a %1 -> Either e b Source #

Functor ((,) a) Source # 
Instance details

Defined in Data.Functor.Linear.Internal.Functor

Methods

fmap :: (a0 %1 -> b) -> (a, a0) %1 -> (a, b) Source #

Functor m => Functor (MaybeT m) Source # 
Instance details

Defined in Data.Functor.Linear.Internal.Functor

Methods

fmap :: (a %1 -> b) -> MaybeT m a %1 -> MaybeT m b Source #

Functor f => Functor (Data f) Source # 
Instance details

Defined in Control.Functor.Linear.Internal.Instances

Methods

fmap :: (a %1 -> b) -> Data f a %1 -> Data f b Source #

Functor (V n) Source # 
Instance details

Defined in Data.V.Linear.Internal.Instances

Methods

fmap :: (a %1 -> b) -> V n a %1 -> V n b Source #

Functor (Of a) Source # 
Instance details

Defined in Streaming.Internal.Type

Methods

fmap :: (a0 %1 -> b) -> Of a a0 %1 -> Of a b Source #

Functor (HashMap k) Source # 
Instance details

Defined in Data.HashMap.Mutable.Linear

Methods

fmap :: (a %1 -> b) -> HashMap k a %1 -> HashMap k b Source #

Functor (Const x :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Linear.Internal.Functor

Methods

fmap :: (a %1 -> b) -> Const x a %1 -> Const x b Source #

Functor m => Functor (StateT s m) Source # 
Instance details

Defined in Data.Functor.Linear.Internal.Functor

Methods

fmap :: (a %1 -> b) -> StateT s m a %1 -> StateT s m b Source #

Functor m => Functor (ReaderT r m) Source # 
Instance details

Defined in Data.Functor.Linear.Internal.Functor

Methods

fmap :: (a %1 -> b) -> ReaderT r m a %1 -> ReaderT r m b Source #

Functor m => Functor (ExceptT e m) Source # 
Instance details

Defined in Data.Functor.Linear.Internal.Functor

Methods

fmap :: (a %1 -> b) -> ExceptT e m a %1 -> ExceptT e m b Source #

Functor m => Functor (StateT s m) Source # 
Instance details

Defined in Control.Functor.Linear.Internal.State

Methods

fmap :: (a %1 -> b) -> StateT s m a %1 -> StateT s m b Source #

Functor m => Functor (ReaderT r m) Source # 
Instance details

Defined in Control.Functor.Linear.Internal.Reader

Methods

fmap :: (a %1 -> b) -> ReaderT r m a %1 -> ReaderT r m b Source #

(Functor m, Functor f) => Functor (Stream f m) Source # 
Instance details

Defined in Streaming.Internal.Type

Methods

fmap :: (a %1 -> b) -> Stream f m a %1 -> Stream f m b Source #

(Functor f, Functor g) => Functor (Sum f g) Source # 
Instance details

Defined in Data.Functor.Linear.Internal.Functor

Methods

fmap :: (a %1 -> b) -> Sum f g a %1 -> Sum f g b Source #

Functor (ContT r m) Source # 
Instance details

Defined in Data.Functor.Linear.Internal.Functor

Methods

fmap :: (a %1 -> b) -> ContT r m a %1 -> ContT r m b Source #

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

Defined in Data.Functor.Linear.Internal.Functor

Methods

fmap :: (a %1 -> b) -> Compose f g a %1 -> Compose f g b Source #

(<$>) :: Functor f => (a %1 -> b) -> f a %1 -> f b Source #

(<$) :: (Functor f, Consumable b) => a -> f b %1 -> f a Source #

Replace all occurances of b with the given a and consume the functor f b.

void :: (Functor f, Consumable a) => f a %1 -> f () Source #

Discard a consumable value stored in a data functor.

class Functor f => Applicative f where Source #

Data Applicative-s can be seen as containers which can be zipped together. A prime example of data Applicative are vectors of known length (ZipLists would be, if it were not for the fact that zipping them together drops values, which we are not allowed to do in a linear container).

In fact, an applicative functor is precisely a functor equipped with (pure and) liftA2 :: (a %1-> b %1-> c) -> f a %1-> f b %1-> f c. In the case where f = [], the signature of liftA2 would specialise to that of zipWith.

Intuitively, the type of liftA2 means that Applicatives can be seen as containers whose "number" of elements is known at compile-time. This includes vectors of known length but excludes Maybe, since this may contain either zero or one value. Similarly, ((->) r) forms a Data Applicative, since this is a (possibly infinitary) container indexed by r, while lists do not, since they may contain any number of elements.

Remarks for the mathematically inclined

An Applicative is, as in the restricted case, a lax monoidal endofunctor of the category of linear types. That is, it is equipped with

  • a (linear) function () %1-> f ()
  • a (linear) natural transformation (f a, f b) %1-> f (a, b)

It is a simple exercise to verify that these are equivalent to the definition of Applicative. Hence that the choice of linearity of the various arrow is indeed natural.

Minimal complete definition

pure, (liftA2 | (<*>))

Methods

pure :: a -> f a Source #

(<*>) :: f (a %1 -> b) %1 -> f a %1 -> f b Source #

liftA2 :: (a %1 -> b %1 -> c) -> f a %1 -> f b %1 -> f c Source #

Instances

Instances details
Applicative Identity Source # 
Instance details

Defined in Data.Functor.Linear.Internal.Applicative

Methods

pure :: a -> Identity a Source #

(<*>) :: Identity (a %1 -> b) %1 -> Identity a %1 -> Identity b Source #

liftA2 :: (a %1 -> b %1 -> c) -> Identity a %1 -> Identity b %1 -> Identity c Source #

Applicative Ur Source # 
Instance details

Defined in Data.Unrestricted.Internal.Instances

Methods

pure :: a -> Ur a Source #

(<*>) :: Ur (a %1 -> b) %1 -> Ur a %1 -> Ur b Source #

liftA2 :: (a %1 -> b %1 -> c) -> Ur a %1 -> Ur b %1 -> Ur c Source #

Applicative IO Source # 
Instance details

Defined in System.IO.Linear

Methods

pure :: a -> IO a Source #

(<*>) :: IO (a %1 -> b) %1 -> IO a %1 -> IO b Source #

liftA2 :: (a %1 -> b %1 -> c) -> IO a %1 -> IO b %1 -> IO c Source #

Applicative RIO Source # 
Instance details

Defined in System.IO.Resource

Methods

pure :: a -> RIO a Source #

(<*>) :: RIO (a %1 -> b) %1 -> RIO a %1 -> RIO b Source #

liftA2 :: (a %1 -> b %1 -> c) -> RIO a %1 -> RIO b %1 -> RIO c Source #

Monoid a => Applicative ((,) a) Source # 
Instance details

Defined in Data.Functor.Linear.Internal.Applicative

Methods

pure :: a0 -> (a, a0) Source #

(<*>) :: (a, a0 %1 -> b) %1 -> (a, a0) %1 -> (a, b) Source #

liftA2 :: (a0 %1 -> b %1 -> c) -> (a, a0) %1 -> (a, b) %1 -> (a, c) Source #

Applicative f => Applicative (Data f) Source # 
Instance details

Defined in Control.Functor.Linear.Internal.Instances

Methods

pure :: a -> Data f a Source #

(<*>) :: Data f (a %1 -> b) %1 -> Data f a %1 -> Data f b Source #

liftA2 :: (a %1 -> b %1 -> c) -> Data f a %1 -> Data f b %1 -> Data f c Source #

KnownNat n => Applicative (V n) Source # 
Instance details

Defined in Data.V.Linear.Internal.Instances

Methods

pure :: a -> V n a Source #

(<*>) :: V n (a %1 -> b) %1 -> V n a %1 -> V n b Source #

liftA2 :: (a %1 -> b %1 -> c) -> V n a %1 -> V n b %1 -> V n c Source #

Monoid x => Applicative (Const x :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Linear.Internal.Applicative

Methods

pure :: a -> Const x a Source #

(<*>) :: Const x (a %1 -> b) %1 -> Const x a %1 -> Const x b Source #

liftA2 :: (a %1 -> b %1 -> c) -> Const x a %1 -> Const x b %1 -> Const x c Source #

Applicative m => Applicative (ReaderT r m) Source # 
Instance details

Defined in Data.Functor.Linear.Internal.Applicative

Methods

pure :: a -> ReaderT r m a Source #

(<*>) :: ReaderT r m (a %1 -> b) %1 -> ReaderT r m a %1 -> ReaderT r m b Source #

liftA2 :: (a %1 -> b %1 -> c) -> ReaderT r m a %1 -> ReaderT r m b %1 -> ReaderT r m c Source #

Monad m => Applicative (StateT s m) Source # 
Instance details

Defined in Control.Functor.Linear.Internal.State

Methods

pure :: a -> StateT s m a Source #

(<*>) :: StateT s m (a %1 -> b) %1 -> StateT s m a %1 -> StateT s m b Source #

liftA2 :: (a %1 -> b %1 -> c) -> StateT s m a %1 -> StateT s m b %1 -> StateT s m c Source #

(Applicative m, Dupable r) => Applicative (ReaderT r m) Source # 
Instance details

Defined in Control.Functor.Linear.Internal.Reader

Methods

pure :: a -> ReaderT r m a Source #

(<*>) :: ReaderT r m (a %1 -> b) %1 -> ReaderT r m a %1 -> ReaderT r m b Source #

liftA2 :: (a %1 -> b %1 -> c) -> ReaderT r m a %1 -> ReaderT r m b %1 -> ReaderT r m c Source #

(Functor m, Functor f) => Applicative (Stream f m) Source # 
Instance details

Defined in Streaming.Internal.Type

Methods

pure :: a -> Stream f m a Source #

(<*>) :: Stream f m (a %1 -> b) %1 -> Stream f m a %1 -> Stream f m b Source #

liftA2 :: (a %1 -> b %1 -> c) -> Stream f m a %1 -> Stream f m b %1 -> Stream f m c Source #

(Applicative f, Applicative g) => Applicative (Compose f g) Source # 
Instance details

Defined in Data.Functor.Linear.Internal.Applicative

Methods

pure :: a -> Compose f g a Source #

(<*>) :: Compose f g (a %1 -> b) %1 -> Compose f g a %1 -> Compose f g b Source #

liftA2 :: (a %1 -> b %1 -> c) -> Compose f g a %1 -> Compose f g b %1 -> Compose f g c Source #

newtype Const a (b :: k) #

The Const functor.

Constructors

Const 

Fields

Instances

Instances details
Strong Either Void (CoKleisli (Const x :: Type -> Type)) Source # 
Instance details

Defined in Data.Profunctor.Kleisli.Linear

Methods

first :: CoKleisli (Const x) a b -> CoKleisli (Const x) (Either a c) (Either b c) Source #

second :: CoKleisli (Const x) b c -> CoKleisli (Const x) (Either a b) (Either a c) Source #

Generic1 (Const a :: k -> Type) 
Instance details

Defined in Data.Functor.Const

Associated Types

type Rep1 (Const a) :: k -> Type #

Methods

from1 :: forall (a0 :: k0). Const a a0 -> Rep1 (Const a) a0 #

to1 :: forall (a0 :: k0). Rep1 (Const a) a0 -> Const a a0 #

Show2 (Const :: Type -> Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> Const a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [Const a b] -> ShowS #

Read2 (Const :: Type -> Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (Const a b) #

liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Const a b] #

liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (Const a b) #

liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [Const a b] #

Ord2 (Const :: Type -> Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> Const a c -> Const b d -> Ordering #

Eq2 (Const :: Type -> Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> Const a c -> Const b d -> Bool #

Bifunctor (Const :: Type -> Type -> Type)

Since: base-4.8.0.0

Instance details

Defined in Data.Bifunctor

Methods

bimap :: (a -> b) -> (c -> d) -> Const a c -> Const b d #

first :: (a -> b) -> Const a c -> Const b c #

second :: (b -> c) -> Const a b -> Const a c #

Hashable2 (Const :: Type -> Type -> Type) 
Instance details

Defined in Data.Hashable.Class

Methods

liftHashWithSalt2 :: (Int -> a -> Int) -> (Int -> b -> Int) -> Int -> Const a b -> Int #

Functor (Const m :: Type -> Type)

Since: base-2.1

Instance details

Defined in Data.Functor.Const

Methods

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

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

Monoid m => Applicative (Const m :: Type -> Type)

Since: base-2.0.1

Instance details

Defined in Data.Functor.Const

Methods

pure :: a -> Const m a #

(<*>) :: Const m (a -> b) -> Const m a -> Const m b #

liftA2 :: (a -> b -> c) -> Const m a -> Const m b -> Const m c #

(*>) :: Const m a -> Const m b -> Const m b #

(<*) :: Const m a -> Const m b -> Const m a #

Foldable (Const m :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Functor.Const

Methods

fold :: Monoid m0 => Const m m0 -> m0 #

foldMap :: Monoid m0 => (a -> m0) -> Const m a -> m0 #

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

foldr :: (a -> b -> b) -> b -> Const m a -> b #

foldr' :: (a -> b -> b) -> b -> Const m a -> b #

foldl :: (b -> a -> b) -> b -> Const m a -> b #

foldl' :: (b -> a -> b) -> b -> Const m a -> b #

foldr1 :: (a -> a -> a) -> Const m a -> a #

foldl1 :: (a -> a -> a) -> Const m a -> a #

toList :: Const m a -> [a] #

null :: Const m a -> Bool #

length :: Const m a -> Int #

elem :: Eq a => a -> Const m a -> Bool #

maximum :: Ord a => Const m a -> a #

minimum :: Ord a => Const m a -> a #

sum :: Num a => Const m a -> a #

product :: Num a => Const m a -> a #

Traversable (Const m :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Traversable

Methods

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

sequenceA :: Applicative f => Const m (f a) -> f (Const m a) #

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

sequence :: Monad m0 => Const m (m0 a) -> m0 (Const m a) #

Show a => Show1 (Const a :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> Const a a0 -> ShowS #

liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [Const a a0] -> ShowS #

Read a => Read1 (Const a :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (Const a a0) #

liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [Const a a0] #

liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (Const a a0) #

liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [Const a a0] #

Ord a => Ord1 (Const a :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare :: (a0 -> b -> Ordering) -> Const a a0 -> Const a b -> Ordering #

Eq a => Eq1 (Const a :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a0 -> b -> Bool) -> Const a a0 -> Const a b -> Bool #

Hashable a => Hashable1 (Const a :: Type -> Type) 
Instance details

Defined in Data.Hashable.Class

Methods

liftHashWithSalt :: (Int -> a0 -> Int) -> Int -> Const a a0 -> Int #

Functor (Const x :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Linear.Internal.Functor

Methods

fmap :: (a %1 -> b) -> Const x a %1 -> Const x b Source #

Monoid x => Applicative (Const x :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Linear.Internal.Applicative

Methods

pure :: a -> Const x a Source #

(<*>) :: Const x (a %1 -> b) %1 -> Const x a %1 -> Const x b Source #

liftA2 :: (a %1 -> b %1 -> c) -> Const x a %1 -> Const x b %1 -> Const x c Source #

Traversable (Const a :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Linear.Internal.Traversable

Methods

traverse :: Applicative f => (a0 %1 -> f b) -> Const a a0 %1 -> f (Const a b) Source #

sequence :: Applicative f => Const a (f a0) %1 -> f (Const a a0) Source #

Bounded a => Bounded (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

minBound :: Const a b #

maxBound :: Const a b #

Enum a => Enum (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

succ :: Const a b -> Const a b #

pred :: Const a b -> Const a b #

toEnum :: Int -> Const a b #

fromEnum :: Const a b -> Int #

enumFrom :: Const a b -> [Const a b] #

enumFromThen :: Const a b -> Const a b -> [Const a b] #

enumFromTo :: Const a b -> Const a b -> [Const a b] #

enumFromThenTo :: Const a b -> Const a b -> Const a b -> [Const a b] #

Eq a => Eq (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

(==) :: Const a b -> Const a b -> Bool #

(/=) :: Const a b -> Const a b -> Bool #

Floating a => Floating (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

pi :: Const a b #

exp :: Const a b -> Const a b #

log :: Const a b -> Const a b #

sqrt :: Const a b -> Const a b #

(**) :: Const a b -> Const a b -> Const a b #

logBase :: Const a b -> Const a b -> Const a b #

sin :: Const a b -> Const a b #

cos :: Const a b -> Const a b #

tan :: Const a b -> Const a b #

asin :: Const a b -> Const a b #

acos :: Const a b -> Const a b #

atan :: Const a b -> Const a b #

sinh :: Const a b -> Const a b #

cosh :: Const a b -> Const a b #

tanh :: Const a b -> Const a b #

asinh :: Const a b -> Const a b #

acosh :: Const a b -> Const a b #

atanh :: Const a b -> Const a b #

log1p :: Const a b -> Const a b #

expm1 :: Const a b -> Const a b #

log1pexp :: Const a b -> Const a b #

log1mexp :: Const a b -> Const a b #

Fractional a => Fractional (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

(/) :: Const a b -> Const a b -> Const a b #

recip :: Const a b -> Const a b #

fromRational :: Rational -> Const a b #

Integral a => Integral (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

quot :: Const a b -> Const a b -> Const a b #

rem :: Const a b -> Const a b -> Const a b #

div :: Const a b -> Const a b -> Const a b #

mod :: Const a b -> Const a b -> Const a b #

quotRem :: Const a b -> Const a b -> (Const a b, Const a b) #

divMod :: Const a b -> Const a b -> (Const a b, Const a b) #

toInteger :: Const a b -> Integer #

Num a => Num (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

(+) :: Const a b -> Const a b -> Const a b #

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

(*) :: Const a b -> Const a b -> Const a b #

negate :: Const a b -> Const a b #

abs :: Const a b -> Const a b #

signum :: Const a b -> Const a b #

fromInteger :: Integer -> Const a b #

Ord a => Ord (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

compare :: Const a b -> Const a b -> Ordering #

(<) :: Const a b -> Const a b -> Bool #

(<=) :: Const a b -> Const a b -> Bool #

(>) :: Const a b -> Const a b -> Bool #

(>=) :: Const a b -> Const a b -> Bool #

max :: Const a b -> Const a b -> Const a b #

min :: Const a b -> Const a b -> Const a b #

Read a => Read (Const a b)

This instance would be equivalent to the derived instances of the Const newtype if the getConst field were removed

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Const

Real a => Real (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

toRational :: Const a b -> Rational #

RealFloat a => RealFloat (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

floatRadix :: Const a b -> Integer #

floatDigits :: Const a b -> Int #

floatRange :: Const a b -> (Int, Int) #

decodeFloat :: Const a b -> (Integer, Int) #

encodeFloat :: Integer -> Int -> Const a b #

exponent :: Const a b -> Int #

significand :: Const a b -> Const a b #

scaleFloat :: Int -> Const a b -> Const a b #

isNaN :: Const a b -> Bool #

isInfinite :: Const a b -> Bool #

isDenormalized :: Const a b -> Bool #

isNegativeZero :: Const a b -> Bool #

isIEEE :: Const a b -> Bool #

atan2 :: Const a b -> Const a b -> Const a b #

RealFrac a => RealFrac (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

properFraction :: Integral b0 => Const a b -> (b0, Const a b) #

truncate :: Integral b0 => Const a b -> b0 #

round :: Integral b0 => Const a b -> b0 #

ceiling :: Integral b0 => Const a b -> b0 #

floor :: Integral b0 => Const a b -> b0 #

Show a => Show (Const a b)

This instance would be equivalent to the derived instances of the Const newtype if the getConst field were removed

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Const

Methods

showsPrec :: Int -> Const a b -> ShowS #

show :: Const a b -> String #

showList :: [Const a b] -> ShowS #

Ix a => Ix (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

range :: (Const a b, Const a b) -> [Const a b] #

index :: (Const a b, Const a b) -> Const a b -> Int #

unsafeIndex :: (Const a b, Const a b) -> Const a b -> Int #

inRange :: (Const a b, Const a b) -> Const a b -> Bool #

rangeSize :: (Const a b, Const a b) -> Int #

unsafeRangeSize :: (Const a b, Const a b) -> Int #

IsString a => IsString (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.String

Methods

fromString :: String -> Const a b #

Generic (Const a b) 
Instance details

Defined in Data.Functor.Const

Associated Types

type Rep (Const a b) :: Type -> Type #

Methods

from :: Const a b -> Rep (Const a b) x #

to :: Rep (Const a b) x -> Const a b #

Semigroup a => Semigroup (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

(<>) :: Const a b -> Const a b -> Const a b #

sconcat :: NonEmpty (Const a b) -> Const a b #

stimes :: Integral b0 => b0 -> Const a b -> Const a b #

Monoid a => Monoid (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

mempty :: Const a b #

mappend :: Const a b -> Const a b -> Const a b #

mconcat :: [Const a b] -> Const a b #

Storable a => Storable (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

sizeOf :: Const a b -> Int #

alignment :: Const a b -> Int #

peekElemOff :: Ptr (Const a b) -> Int -> IO (Const a b) #

pokeElemOff :: Ptr (Const a b) -> Int -> Const a b -> IO () #

peekByteOff :: Ptr b0 -> Int -> IO (Const a b) #

pokeByteOff :: Ptr b0 -> Int -> Const a b -> IO () #

peek :: Ptr (Const a b) -> IO (Const a b) #

poke :: Ptr (Const a b) -> Const a b -> IO () #

FiniteBits a => FiniteBits (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Bits a => Bits (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

(.&.) :: Const a b -> Const a b -> Const a b #

(.|.) :: Const a b -> Const a b -> Const a b #

xor :: Const a b -> Const a b -> Const a b #

complement :: Const a b -> Const a b #

shift :: Const a b -> Int -> Const a b #

rotate :: Const a b -> Int -> Const a b #

zeroBits :: Const a b #

bit :: Int -> Const a b #

setBit :: Const a b -> Int -> Const a b #

clearBit :: Const a b -> Int -> Const a b #

complementBit :: Const a b -> Int -> Const a b #

testBit :: Const a b -> Int -> Bool #

bitSizeMaybe :: Const a b -> Maybe Int #

bitSize :: Const a b -> Int #

isSigned :: Const a b -> Bool #

shiftL :: Const a b -> Int -> Const a b #

unsafeShiftL :: Const a b -> Int -> Const a b #

shiftR :: Const a b -> Int -> Const a b #

unsafeShiftR :: Const a b -> Int -> Const a b #

rotateL :: Const a b -> Int -> Const a b #

rotateR :: Const a b -> Int -> Const a b #

popCount :: Const a b -> Int #

Hashable a => Hashable (Const a b) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Const a b -> Int #

hash :: Const a b -> Int #

type Rep1 (Const a :: k -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

type Rep1 (Const a :: k -> Type) = D1 ('MetaData "Const" "Data.Functor.Const" "base" 'True) (C1 ('MetaCons "Const" 'PrefixI 'True) (S1 ('MetaSel ('Just "getConst") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))
type Rep (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

type Rep (Const a b) = D1 ('MetaData "Const" "Data.Functor.Const" "base" 'True) (C1 ('MetaCons "Const" 'PrefixI 'True) (S1 ('MetaSel ('Just "getConst") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

Linear traversable hierarchy

class Functor t => Traversable t where Source #

A linear data traversible is a functor of type t a where you can apply a linear effectful action of type a %1-> f b on each value of type a and compose this to perform an action on the whole functor, resulting in a value of type f (t b).

To learn more about Traversable, see here:

Minimal complete definition

traverse | sequence

Methods

traverse :: Applicative f => (a %1 -> f b) -> t a %1 -> f (t b) Source #

sequence :: Applicative f => t (f a) %1 -> f (t a) Source #

Instances

Instances details
Traversable [] Source # 
Instance details

Defined in Data.Functor.Linear.Internal.Traversable

Methods

traverse :: Applicative f => (a %1 -> f b) -> [a] %1 -> f [b] Source #

sequence :: Applicative f => [f a] %1 -> f [a] Source #

Traversable Maybe Source # 
Instance details

Defined in Data.Functor.Linear.Internal.Traversable

Methods

traverse :: Applicative f => (a %1 -> f b) -> Maybe a %1 -> f (Maybe b) Source #

sequence :: Applicative f => Maybe (f a) %1 -> f (Maybe a) Source #

Traversable (Either a) Source # 
Instance details

Defined in Data.Functor.Linear.Internal.Traversable

Methods

traverse :: Applicative f => (a0 %1 -> f b) -> Either a a0 %1 -> f (Either a b) Source #

sequence :: Applicative f => Either a (f a0) %1 -> f (Either a a0) Source #

Traversable ((,) a) Source # 
Instance details

Defined in Data.Functor.Linear.Internal.Traversable

Methods

traverse :: Applicative f => (a0 %1 -> f b) -> (a, a0) %1 -> f (a, b) Source #

sequence :: Applicative f => (a, f a0) %1 -> f (a, a0) Source #

KnownNat n => Traversable (V n) Source # 
Instance details

Defined in Data.V.Linear.Internal.Instances

Methods

traverse :: Applicative f => (a %1 -> f b) -> V n a %1 -> f (V n b) Source #

sequence :: Applicative f => V n (f a) %1 -> f (V n a) Source #

Traversable (Const a :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Linear.Internal.Traversable

Methods

traverse :: Applicative f => (a0 %1 -> f b) -> Const a a0 %1 -> f (Const a b) Source #

sequence :: Applicative f => Const a (f a0) %1 -> f (Const a a0) Source #

mapM :: (Traversable t, Monad m) => (a %1 -> m b) -> t a %1 -> m (t b) Source #

sequenceA :: (Traversable t, Applicative f) => t (f a) %1 -> f (t a) Source #

for :: (Traversable t, Applicative f) => t a %1 -> (a %1 -> f b) -> f (t b) Source #

forM :: (Traversable t, Monad m) => t a %1 -> (a %1 -> m b) -> m (t b) Source #

mapAccumL :: Traversable t => (a %1 -> b %1 -> (a, c)) -> a %1 -> t b %1 -> (a, t c) Source #

mapAccumR :: Traversable t => (a %1 -> b %1 -> (a, c)) -> a %1 -> t b %1 -> (a, t c) Source #