hgeometry-combinatorial-0.12.0.3: Data structures, and Data types.
Copyright(C) Frank Staals
Licensesee the LICENSE file
MaintainerFrank Staals
Safe HaskellNone
LanguageHaskell2010

Data.Util

Description

Some basic types, mostly strict triples and pairs.

Synopsis

Strict Triples

data STR a b c Source #

strict triple

Constructors

STR !a !b !c 

Instances

Instances details
Functor (STR a b) Source # 
Instance details

Defined in Data.Util

Methods

fmap :: (a0 -> b0) -> STR a b a0 -> STR a b b0 #

(<$) :: a0 -> STR a b b0 -> STR a b a0 #

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

Defined in Data.Util

Methods

(==) :: STR a b c -> STR a b c -> Bool #

(/=) :: STR a b c -> STR a b c -> Bool #

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

Defined in Data.Util

Methods

compare :: STR a b c -> STR a b c -> Ordering #

(<) :: STR a b c -> STR a b c -> Bool #

(<=) :: STR a b c -> STR a b c -> Bool #

(>) :: STR a b c -> STR a b c -> Bool #

(>=) :: STR a b c -> STR a b c -> Bool #

max :: STR a b c -> STR a b c -> STR a b c #

min :: STR a b c -> STR a b c -> STR a b c #

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

Defined in Data.Util

Methods

showsPrec :: Int -> STR a b c -> ShowS #

show :: STR a b c -> String #

showList :: [STR a b c] -> ShowS #

Generic (STR a b c) Source # 
Instance details

Defined in Data.Util

Associated Types

type Rep (STR a b c) :: Type -> Type #

Methods

from :: STR a b c -> Rep (STR a b c) x #

to :: Rep (STR a b c) x -> STR a b c #

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

Defined in Data.Util

Methods

(<>) :: STR a b c -> STR a b c -> STR a b c #

sconcat :: NonEmpty (STR a b c) -> STR a b c #

stimes :: Integral b0 => b0 -> STR a b c -> STR a b c #

(Semigroup a, Semigroup b, Semigroup c, Monoid a, Monoid b, Monoid c) => Monoid (STR a b c) Source # 
Instance details

Defined in Data.Util

Methods

mempty :: STR a b c #

mappend :: STR a b c -> STR a b c -> STR a b c #

mconcat :: [STR a b c] -> STR a b c #

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

Defined in Data.Util

Methods

rnf :: STR a b c -> () #

Field1 (STR a b c) (STR d b c) a d Source # 
Instance details

Defined in Data.Util

Methods

_1 :: Lens (STR a b c) (STR d b c) a d #

Field2 (STR a b c) (STR a d c) b d Source # 
Instance details

Defined in Data.Util

Methods

_2 :: Lens (STR a b c) (STR a d c) b d #

Field3 (STR a b c) (STR a b d) c d Source # 
Instance details

Defined in Data.Util

Methods

_3 :: Lens (STR a b c) (STR a b d) c d #

type Rep (STR a b c) Source # 
Instance details

Defined in Data.Util

type Rep (STR a b c) = D1 ('MetaData "STR" "Data.Util" "hgeometry-combinatorial-0.12.0.3-9KgRsdeXKv96i7LJf3Ilw2" 'False) (C1 ('MetaCons "STR" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 c))))

type Three = V3 Source #

Strict Triple with all items the same

pattern Three :: a -> a -> a -> Three a Source #

Pattern synonym for strict triples.

uniqueTriplets :: [a] -> [Three a] Source #

Generate All unique unordered triplets.

Strict Pairs

data SP a b Source #

Strict pair

Constructors

SP !a !b 

Instances

Instances details
Bifunctor SP Source # 
Instance details

Defined in Data.Util

Methods

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

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

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

Functor (SP a) Source # 
Instance details

Defined in Data.Util

Methods

fmap :: (a0 -> b) -> SP a a0 -> SP a b #

(<$) :: a0 -> SP a b -> SP a a0 #

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

Defined in Data.Util

Methods

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

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

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

Defined in Data.Util

Methods

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

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

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

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

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

max :: SP a b -> SP a b -> SP a b #

min :: SP a b -> SP a b -> SP a b #

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

Defined in Data.Util

Methods

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

show :: SP a b -> String #

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

Generic (SP a b) Source # 
Instance details

Defined in Data.Util

Associated Types

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

Methods

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

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

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

Defined in Data.Util

Methods

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

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

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

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

Defined in Data.Util

Methods

mempty :: SP a b #

mappend :: SP a b -> SP a b -> SP a b #

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

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

Defined in Data.Util

Methods

rnf :: SP a b -> () #

Field1 (SP a b) (SP c b) a c Source # 
Instance details

Defined in Data.Util

Methods

_1 :: Lens (SP a b) (SP c b) a c #

Field2 (SP a b) (SP a c) b c Source # 
Instance details

Defined in Data.Util

Methods

_2 :: Lens (SP a b) (SP a c) b c #

type Rep (SP a b) Source # 
Instance details

Defined in Data.Util

type Rep (SP a b) = D1 ('MetaData "SP" "Data.Util" "hgeometry-combinatorial-0.12.0.3-9KgRsdeXKv96i7LJf3Ilw2" 'False) (C1 ('MetaCons "SP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b)))

type Two = V2 Source #

  • Strict pair whose elements are of the same type.

Strict pair with both items the same

pattern Two :: a -> a -> Two a Source #

Pattern synonym for strict pairs.

uniquePairs :: [a] -> [Two a] Source #

Given a list xs, generate all unique (unordered) pairs.

nonEmptyTails :: [a] -> [[a]] Source #

A version of List.tails in which we remove the emptylist