newtype-zoo-1.2.0.0: Newtype Wrapper Zoo

Safe HaskellNone
LanguageHaskell2010

NewtypeZoo.Allocated

Description

Indicate that something is Allocated.

Synopsis

Documentation

newtype Allocated a Source #

A wrapper for something that is Allocated.

Constructors

Allocated a 
Instances
Monad Allocated Source # 
Instance details

Defined in NewtypeZoo.Allocated

Methods

(>>=) :: Allocated a -> (a -> Allocated b) -> Allocated b #

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

return :: a -> Allocated a #

fail :: String -> Allocated a #

Functor Allocated Source # 
Instance details

Defined in NewtypeZoo.Allocated

Methods

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

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

MonadFix Allocated Source # 
Instance details

Defined in NewtypeZoo.Allocated

Methods

mfix :: (a -> Allocated a) -> Allocated a #

Applicative Allocated Source # 
Instance details

Defined in NewtypeZoo.Allocated

Methods

pure :: a -> Allocated a #

(<*>) :: Allocated (a -> b) -> Allocated a -> Allocated b #

liftA2 :: (a -> b -> c) -> Allocated a -> Allocated b -> Allocated c #

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

(<*) :: Allocated a -> Allocated b -> Allocated a #

Foldable Allocated Source # 
Instance details

Defined in NewtypeZoo.Allocated

Methods

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

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

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

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

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

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

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

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

toList :: Allocated a -> [a] #

null :: Allocated a -> Bool #

length :: Allocated a -> Int #

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

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

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

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

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

Traversable Allocated Source # 
Instance details

Defined in NewtypeZoo.Allocated

Methods

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

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

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

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

Eq1 Allocated Source # 
Instance details

Defined in NewtypeZoo.Allocated

Methods

liftEq :: (a -> b -> Bool) -> Allocated a -> Allocated b -> Bool #

Ord1 Allocated Source # 
Instance details

Defined in NewtypeZoo.Allocated

Methods

liftCompare :: (a -> b -> Ordering) -> Allocated a -> Allocated b -> Ordering #

Read1 Allocated Source # 
Instance details

Defined in NewtypeZoo.Allocated

Show1 Allocated Source # 
Instance details

Defined in NewtypeZoo.Allocated

Methods

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

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

MonadZip Allocated Source # 
Instance details

Defined in NewtypeZoo.Allocated

Methods

mzip :: Allocated a -> Allocated b -> Allocated (a, b) #

mzipWith :: (a -> b -> c) -> Allocated a -> Allocated b -> Allocated c #

munzip :: Allocated (a, b) -> (Allocated a, Allocated b) #

Comonad Allocated Source # 
Instance details

Defined in NewtypeZoo.Allocated

Methods

extract :: Allocated a -> a #

duplicate :: Allocated a -> Allocated (Allocated a) #

extend :: (Allocated a -> b) -> Allocated a -> Allocated b #

Pointed Allocated Source # 
Instance details

Defined in NewtypeZoo.Allocated

Methods

point :: a -> Allocated a #

Copointed Allocated Source # 
Instance details

Defined in NewtypeZoo.Allocated

Methods

copoint :: Allocated a -> a #

Bounded a => Bounded (Allocated a) Source # 
Instance details

Defined in NewtypeZoo.Allocated

Enum a => Enum (Allocated a) Source # 
Instance details

Defined in NewtypeZoo.Allocated

Eq a => Eq (Allocated a) Source # 
Instance details

Defined in NewtypeZoo.Allocated

Methods

(==) :: Allocated a -> Allocated a -> Bool #

(/=) :: Allocated a -> Allocated a -> Bool #

Floating a => Floating (Allocated a) Source # 
Instance details

Defined in NewtypeZoo.Allocated

Fractional a => Fractional (Allocated a) Source # 
Instance details

Defined in NewtypeZoo.Allocated

Integral a => Integral (Allocated a) Source # 
Instance details

Defined in NewtypeZoo.Allocated

Num a => Num (Allocated a) Source # 
Instance details

Defined in NewtypeZoo.Allocated

Ord a => Ord (Allocated a) Source # 
Instance details

Defined in NewtypeZoo.Allocated

Read a => Read (Allocated a) Source # 
Instance details

Defined in NewtypeZoo.Allocated

Real a => Real (Allocated a) Source # 
Instance details

Defined in NewtypeZoo.Allocated

RealFloat a => RealFloat (Allocated a) Source # 
Instance details

Defined in NewtypeZoo.Allocated

RealFrac a => RealFrac (Allocated a) Source # 
Instance details

Defined in NewtypeZoo.Allocated

Methods

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

truncate :: Integral b => Allocated a -> b #

round :: Integral b => Allocated a -> b #

ceiling :: Integral b => Allocated a -> b #

floor :: Integral b => Allocated a -> b #

Show a => Show (Allocated a) Source # 
Instance details

Defined in NewtypeZoo.Allocated

Ix a => Ix (Allocated a) Source # 
Instance details

Defined in NewtypeZoo.Allocated

IsString a => IsString (Allocated a) Source # 
Instance details

Defined in NewtypeZoo.Allocated

Methods

fromString :: String -> Allocated a #

Generic (Allocated a) Source # 
Instance details

Defined in NewtypeZoo.Allocated

Associated Types

type Rep (Allocated a) :: Type -> Type #

Methods

from :: Allocated a -> Rep (Allocated a) x #

to :: Rep (Allocated a) x -> Allocated a #

Semigroup a => Semigroup (Allocated a) Source # 
Instance details

Defined in NewtypeZoo.Allocated

Methods

(<>) :: Allocated a -> Allocated a -> Allocated a #

sconcat :: NonEmpty (Allocated a) -> Allocated a #

stimes :: Integral b => b -> Allocated a -> Allocated a #

Monoid a => Monoid (Allocated a) Source # 
Instance details

Defined in NewtypeZoo.Allocated

Arbitrary a => Arbitrary (Allocated a) Source # 
Instance details

Defined in NewtypeZoo.Allocated

Methods

arbitrary :: Gen (Allocated a) #

shrink :: Allocated a -> [Allocated a] #

Bits a => Bits (Allocated a) Source # 
Instance details

Defined in NewtypeZoo.Allocated

FiniteBits a => FiniteBits (Allocated a) Source # 
Instance details

Defined in NewtypeZoo.Allocated

Default a => Default (Allocated a) Source # 
Instance details

Defined in NewtypeZoo.Allocated

Methods

def :: Allocated a #

NFData a => NFData (Allocated a) Source # 
Instance details

Defined in NewtypeZoo.Allocated

Methods

rnf :: Allocated a -> () #

Random a => Random (Allocated a) Source # 
Instance details

Defined in NewtypeZoo.Allocated

Methods

randomR :: RandomGen g => (Allocated a, Allocated a) -> g -> (Allocated a, g) #

random :: RandomGen g => g -> (Allocated a, g) #

randomRs :: RandomGen g => (Allocated a, Allocated a) -> g -> [Allocated a] #

randoms :: RandomGen g => g -> [Allocated a] #

randomRIO :: (Allocated a, Allocated a) -> IO (Allocated a) #

randomIO :: IO (Allocated a) #

Generic1 Allocated Source # 
Instance details

Defined in NewtypeZoo.Allocated

Associated Types

type Rep1 Allocated :: k -> Type #

type Rep (Allocated a) Source # 
Instance details

Defined in NewtypeZoo.Allocated

type Rep (Allocated a) = D1 (MetaData "Allocated" "NewtypeZoo.Allocated" "newtype-zoo-1.2.0.0-2H9swzmDOHJ3G5x4fWrwAi" True) (C1 (MetaCons "Allocated" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 Allocated Source # 
Instance details

Defined in NewtypeZoo.Allocated

type Rep1 Allocated = D1 (MetaData "Allocated" "NewtypeZoo.Allocated" "newtype-zoo-1.2.0.0-2H9swzmDOHJ3G5x4fWrwAi" True) (C1 (MetaCons "Allocated" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))

_theAllocated :: Allocated x -> x Source #

An accessor function for something Allocated.

theAllocated :: forall a b p f. (Profunctor p, Functor f) => p a (f b) -> p (Allocated a) (f (Allocated b)) Source #

A lens for something Allocated.