strict-0.4: Strict data types and String IO.

Safe HaskellSafe
LanguageHaskell2010

Data.Strict.Tuple

Description

The strict variant of the standard Haskell pairs and the corresponding variants of the functions from Data.Tuple.

Note that unlike regular Haskell pairs, (x :*: _|_) = (_|_ :*: y) = _|_

Synopsis

Documentation

data Pair a b Source #

The type of strict pairs.

Constructors

!a :!: !b infix 2 
Instances
Bifunctor Pair Source # 
Instance details

Defined in Data.Strict.Tuple

Methods

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

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

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

Swap Pair Source # 
Instance details

Defined in Data.Strict.Tuple

Methods

swap :: Pair a b -> Pair b a #

Assoc Pair Source # 
Instance details

Defined in Data.Strict.Tuple

Methods

assoc :: Pair (Pair a b) c -> Pair a (Pair b c) #

unassoc :: Pair a (Pair b c) -> Pair (Pair a b) c #

Bitraversable Pair Source # 
Instance details

Defined in Data.Strict.Tuple

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Pair a b -> f (Pair c d) #

Bifoldable Pair Source # 
Instance details

Defined in Data.Strict.Tuple

Methods

bifold :: Monoid m => Pair m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Pair a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Pair a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Pair a b -> c #

Eq2 Pair Source # 
Instance details

Defined in Data.Strict.Tuple

Methods

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

Ord2 Pair Source # 
Instance details

Defined in Data.Strict.Tuple

Methods

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

Read2 Pair Source #
>>> readsPrec2 0 "'a' :!: ('b' :!: 'c')" :: [(Pair Char (Pair Char Char), String)]
[('a' :!: ('b' :!: 'c'),"")]
>>> readsPrec2 0 "('a' :!: 'b') :!: 'c'" :: [(Pair (Pair Char Char) Char, String)]
[(('a' :!: 'b') :!: 'c',"")]
Instance details

Defined in Data.Strict.Tuple

Methods

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

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

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

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

Show2 Pair Source # 
Instance details

Defined in Data.Strict.Tuple

Methods

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

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

NFData2 Pair Source # 
Instance details

Defined in Data.Strict.Tuple

Methods

liftRnf2 :: (a -> ()) -> (b -> ()) -> Pair a b -> () #

Hashable2 Pair Source # 
Instance details

Defined in Data.Strict.Tuple

Methods

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

Functor (Pair e) Source # 
Instance details

Defined in Data.Strict.Tuple

Methods

fmap :: (a -> b) -> Pair e a -> Pair e b #

(<$) :: a -> Pair e b -> Pair e a #

Foldable (Pair e) Source # 
Instance details

Defined in Data.Strict.Tuple

Methods

fold :: Monoid m => Pair e m -> m #

foldMap :: Monoid m => (a -> m) -> Pair e a -> m #

foldr :: (a -> b -> b) -> b -> Pair e a -> b #

foldr' :: (a -> b -> b) -> b -> Pair e a -> b #

foldl :: (b -> a -> b) -> b -> Pair e a -> b #

foldl' :: (b -> a -> b) -> b -> Pair e a -> b #

foldr1 :: (a -> a -> a) -> Pair e a -> a #

foldl1 :: (a -> a -> a) -> Pair e a -> a #

toList :: Pair e a -> [a] #

null :: Pair e a -> Bool #

length :: Pair e a -> Int #

elem :: Eq a => a -> Pair e a -> Bool #

maximum :: Ord a => Pair e a -> a #

minimum :: Ord a => Pair e a -> a #

sum :: Num a => Pair e a -> a #

product :: Num a => Pair e a -> a #

Traversable (Pair e) Source # 
Instance details

Defined in Data.Strict.Tuple

Methods

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

sequenceA :: Applicative f => Pair e (f a) -> f (Pair e a) #

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

sequence :: Monad m => Pair e (m a) -> m (Pair e a) #

Eq a => Eq1 (Pair a) Source # 
Instance details

Defined in Data.Strict.Tuple

Methods

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

Ord a => Ord1 (Pair a) Source # 
Instance details

Defined in Data.Strict.Tuple

Methods

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

Read a => Read1 (Pair a) Source # 
Instance details

Defined in Data.Strict.Tuple

Methods

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

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

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

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

Show a => Show1 (Pair a) Source # 
Instance details

Defined in Data.Strict.Tuple

Methods

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

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

NFData a => NFData1 (Pair a) Source # 
Instance details

Defined in Data.Strict.Tuple

Methods

liftRnf :: (a0 -> ()) -> Pair a a0 -> () #

Hashable a => Hashable1 (Pair a) Source # 
Instance details

Defined in Data.Strict.Tuple

Methods

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

Generic1 (Pair a :: Type -> Type) Source # 
Instance details

Defined in Data.Strict.Tuple

Associated Types

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

Methods

from1 :: Pair a a0 -> Rep1 (Pair a) a0 #

to1 :: Rep1 (Pair a) a0 -> Pair a a0 #

(Bounded a, Bounded b) => Bounded (Pair a b) Source # 
Instance details

Defined in Data.Strict.Tuple

Methods

minBound :: Pair a b #

maxBound :: Pair a b #

(Eq a, Eq b) => Eq (Pair a b) Source # 
Instance details

Defined in Data.Strict.Tuple

Methods

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

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

(Data a, Data b) => Data (Pair a b) Source # 
Instance details

Defined in Data.Strict.Tuple

Methods

gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Pair a b -> c (Pair a b) #

gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Pair a b) #

toConstr :: Pair a b -> Constr #

dataTypeOf :: Pair a b -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Pair a b)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Pair a b)) #

gmapT :: (forall b0. Data b0 => b0 -> b0) -> Pair a b -> Pair a b #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pair a b -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pair a b -> r #

gmapQ :: (forall d. Data d => d -> u) -> Pair a b -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Pair a b -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Pair a b -> m (Pair a b) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Pair a b -> m (Pair a b) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Pair a b -> m (Pair a b) #

(Ord a, Ord b) => Ord (Pair a b) Source # 
Instance details

Defined in Data.Strict.Tuple

Methods

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

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

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

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

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

max :: Pair a b -> Pair a b -> Pair a b #

min :: Pair a b -> Pair a b -> Pair a b #

(Read a, Read b) => Read (Pair a b) Source # 
Instance details

Defined in Data.Strict.Tuple

Methods

readsPrec :: Int -> ReadS (Pair a b) #

readList :: ReadS [Pair a b] #

readPrec :: ReadPrec (Pair a b) #

readListPrec :: ReadPrec [Pair a b] #

(Show a, Show b) => Show (Pair a b) Source # 
Instance details

Defined in Data.Strict.Tuple

Methods

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

show :: Pair a b -> String #

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

(Ix a, Ix b) => Ix (Pair a b) Source # 
Instance details

Defined in Data.Strict.Tuple

Methods

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

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

unsafeIndex :: (Pair a b, Pair a b) -> Pair a b -> Int

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

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

unsafeRangeSize :: (Pair a b, Pair a b) -> Int

Generic (Pair a b) Source # 
Instance details

Defined in Data.Strict.Tuple

Associated Types

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

Methods

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

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

(Semigroup a, Semigroup b) => Semigroup (Pair a b) Source # 
Instance details

Defined in Data.Strict.Tuple

Methods

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

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

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

(Monoid a, Monoid b) => Monoid (Pair a b) Source # 
Instance details

Defined in Data.Strict.Tuple

Methods

mempty :: Pair a b #

mappend :: Pair a b -> Pair a b -> Pair a b #

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

(Binary a, Binary b) => Binary (Pair a b) Source # 
Instance details

Defined in Data.Strict.Tuple

Methods

put :: Pair a b -> Put #

get :: Get (Pair a b) #

putList :: [Pair a b] -> Put #

(NFData a, NFData b) => NFData (Pair a b) Source # 
Instance details

Defined in Data.Strict.Tuple

Methods

rnf :: Pair a b -> () #

(Hashable a, Hashable b) => Hashable (Pair a b) Source # 
Instance details

Defined in Data.Strict.Tuple

Methods

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

hash :: Pair a b -> Int #

Strict (a, b) (Pair a b) Source # 
Instance details

Defined in Data.Strict.Classes

Methods

toStrict :: (a, b) -> Pair a b Source #

toLazy :: Pair a b -> (a, b) Source #

type Rep1 (Pair a :: Type -> Type) Source # 
Instance details

Defined in Data.Strict.Tuple

type Rep (Pair a b) Source # 
Instance details

Defined in Data.Strict.Tuple

type Rep (Pair a b) = D1 (MetaData "Pair" "Data.Strict.Tuple" "strict-0.4-DcORXBfkCIx3v5lLd1UYRe" False) (C1 (MetaCons ":!:" (InfixI NotAssociative 2) False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 b)))

type (:!:) = Pair infix 2 Source #

fst :: Pair a b -> a Source #

Extract the first component of a strict pair.

snd :: Pair a b -> b Source #

Extract the second component of a strict pair.

curry :: (Pair a b -> c) -> a -> b -> c Source #

Curry a function on strict pairs.

uncurry :: (a -> b -> c) -> Pair a b -> c Source #

Convert a curried function to a function on strict pairs.

swap :: Pair a b -> Pair b a Source #

Analagous to swap from Data.Tuple

zip :: [a] -> [b] -> [Pair a b] Source #

Zip for strict pairs (defined with zipWith).

unzip :: [Pair a b] -> ([a], [b]) Source #

Unzip for stict pairs into a (lazy) pair of lists.