separated-0.3.2.1: A data type with elements separated by values

Safe HaskellNone
LanguageHaskell2010

Data.Separated.Between

Contents

Synopsis

Datatypes

data Between s t a Source #

An a with an s on the left and a t on the right

Constructors

Between s a t 

Instances

Functor (Between s t) Source # 

Methods

fmap :: (a -> b) -> Between s t a -> Between s t b #

(<$) :: a -> Between s t b -> Between s t a #

Foldable (Between s t) Source # 

Methods

fold :: Monoid m => Between s t m -> m #

foldMap :: Monoid m => (a -> m) -> Between s t a -> m #

foldr :: (a -> b -> b) -> b -> Between s t a -> b #

foldr' :: (a -> b -> b) -> b -> Between s t a -> b #

foldl :: (b -> a -> b) -> b -> Between s t a -> b #

foldl' :: (b -> a -> b) -> b -> Between s t a -> b #

foldr1 :: (a -> a -> a) -> Between s t a -> a #

foldl1 :: (a -> a -> a) -> Between s t a -> a #

toList :: Between s t a -> [a] #

null :: Between s t a -> Bool #

length :: Between s t a -> Int #

elem :: Eq a => a -> Between s t a -> Bool #

maximum :: Ord a => Between s t a -> a #

minimum :: Ord a => Between s t a -> a #

sum :: Num a => Between s t a -> a #

product :: Num a => Between s t a -> a #

Traversable (Between s t) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Between s t a -> f (Between s t b) #

sequenceA :: Applicative f => Between s t (f a) -> f (Between s t a) #

mapM :: Monad m => (a -> m b) -> Between s t a -> m (Between s t b) #

sequence :: Monad m => Between s t (m a) -> m (Between s t a) #

Generic1 (Between s t) Source # 

Associated Types

type Rep1 (Between s t :: * -> *) :: * -> * #

Methods

from1 :: Between s t a -> Rep1 (Between s t) a #

to1 :: Rep1 (Between s t) a -> Between s t a #

(Eq s0, Eq t0) => Eq1 (Between s0 t0) Source # 

Methods

liftEq :: (a -> b -> Bool) -> Between s0 t0 a -> Between s0 t0 b -> Bool #

(Ord s0, Ord t0) => Ord1 (Between s0 t0) Source # 

Methods

liftCompare :: (a -> b -> Ordering) -> Between s0 t0 a -> Between s0 t0 b -> Ordering #

(Show s0, Show t0) => Show1 (Between s0 t0) Source # 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Between s0 t0 a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Between s0 t0 a] -> ShowS #

(Eq t, Eq a, Eq s) => Eq (Between s t a) Source # 

Methods

(==) :: Between s t a -> Between s t a -> Bool #

(/=) :: Between s t a -> Between s t a -> Bool #

(Ord t, Ord a, Ord s) => Ord (Between s t a) Source # 

Methods

compare :: Between s t a -> Between s t a -> Ordering #

(<) :: Between s t a -> Between s t a -> Bool #

(<=) :: Between s t a -> Between s t a -> Bool #

(>) :: Between s t a -> Between s t a -> Bool #

(>=) :: Between s t a -> Between s t a -> Bool #

max :: Between s t a -> Between s t a -> Between s t a #

min :: Between s t a -> Between s t a -> Between s t a #

(Show t, Show a, Show s) => Show (Between s t a) Source # 

Methods

showsPrec :: Int -> Between s t a -> ShowS #

show :: Between s t a -> String #

showList :: [Between s t a] -> ShowS #

Generic (Between s t a) Source # 

Associated Types

type Rep (Between s t a) :: * -> * #

Methods

from :: Between s t a -> Rep (Between s t a) x #

to :: Rep (Between s t a) x -> Between s t a #

type Rep1 (Between s t) Source # 
type Rep (Between s t a) Source # 

data Between' s a Source #

An a with an s on each side

Constructors

Between' s a s 

Instances

Bifunctor Between' Source # 

Methods

bimap :: (a -> b) -> (c -> d) -> Between' a c -> Between' b d #

first :: (a -> b) -> Between' a c -> Between' b c #

second :: (b -> c) -> Between' a b -> Between' a c #

Bitraversable Between' Source #
bitraverse f g (Between' s a s') = Between' <$> f s <*> g a <*> f s'

Methods

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

Bifoldable Between' Source #
bifoldMap f g (Between' s a s') = f s <> g a <> f s'

Methods

bifold :: Monoid m => Between' m m -> m #

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

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Between' a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Between' a b -> c #

Functor (Between' s) Source # 

Methods

fmap :: (a -> b) -> Between' s a -> Between' s b #

(<$) :: a -> Between' s b -> Between' s a #

Foldable (Between' s) Source # 

Methods

fold :: Monoid m => Between' s m -> m #

foldMap :: Monoid m => (a -> m) -> Between' s a -> m #

foldr :: (a -> b -> b) -> b -> Between' s a -> b #

foldr' :: (a -> b -> b) -> b -> Between' s a -> b #

foldl :: (b -> a -> b) -> b -> Between' s a -> b #

foldl' :: (b -> a -> b) -> b -> Between' s a -> b #

foldr1 :: (a -> a -> a) -> Between' s a -> a #

foldl1 :: (a -> a -> a) -> Between' s a -> a #

toList :: Between' s a -> [a] #

null :: Between' s a -> Bool #

length :: Between' s a -> Int #

elem :: Eq a => a -> Between' s a -> Bool #

maximum :: Ord a => Between' s a -> a #

minimum :: Ord a => Between' s a -> a #

sum :: Num a => Between' s a -> a #

product :: Num a => Between' s a -> a #

Traversable (Between' s) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Between' s a -> f (Between' s b) #

sequenceA :: Applicative f => Between' s (f a) -> f (Between' s a) #

mapM :: Monad m => (a -> m b) -> Between' s a -> m (Between' s b) #

sequence :: Monad m => Between' s (m a) -> m (Between' s a) #

Generic1 (Between' s) Source # 

Associated Types

type Rep1 (Between' s :: * -> *) :: * -> * #

Methods

from1 :: Between' s a -> Rep1 (Between' s) a #

to1 :: Rep1 (Between' s) a -> Between' s a #

Eq s0 => Eq1 (Between' s0) Source # 

Methods

liftEq :: (a -> b -> Bool) -> Between' s0 a -> Between' s0 b -> Bool #

Ord s0 => Ord1 (Between' s0) Source # 

Methods

liftCompare :: (a -> b -> Ordering) -> Between' s0 a -> Between' s0 b -> Ordering #

Show s0 => Show1 (Between' s0) Source # 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Between' s0 a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Between' s0 a] -> ShowS #

(Eq a, Eq s) => Eq (Between' s a) Source # 

Methods

(==) :: Between' s a -> Between' s a -> Bool #

(/=) :: Between' s a -> Between' s a -> Bool #

(Ord a, Ord s) => Ord (Between' s a) Source # 

Methods

compare :: Between' s a -> Between' s a -> Ordering #

(<) :: Between' s a -> Between' s a -> Bool #

(<=) :: Between' s a -> Between' s a -> Bool #

(>) :: Between' s a -> Between' s a -> Bool #

(>=) :: Between' s a -> Between' s a -> Bool #

max :: Between' s a -> Between' s a -> Between' s a #

min :: Between' s a -> Between' s a -> Between' s a #

(Show a, Show s) => Show (Between' s a) Source # 

Methods

showsPrec :: Int -> Between' s a -> ShowS #

show :: Between' s a -> String #

showList :: [Between' s a] -> ShowS #

Generic (Between' s a) Source # 

Associated Types

type Rep (Between' s a) :: * -> * #

Methods

from :: Between' s a -> Rep (Between' s a) x #

to :: Rep (Between' s a) x -> Between' s a #

type Rep1 (Between' s) Source # 
type Rep (Between' s a) Source # 

Isos

between :: Iso (s, a, s') (t, b, t') (Between s s' a) (Between t t' b) Source #

Between s t a is isomorphic to (s, a, t)

between' :: Iso (s, a, s) (t, b, t) (Between' s a) (Between' t b) Source #

Between' s a is isomorphic to (s, a, s)

betweens :: Iso (Between s s a) (Between t t b) (Between' s a) (Between' t b) Source #

Between' s a is isomorphic to Between s s a