HaskellForMaths-0.4.9: Combinatorics, group theory, commutative algebra, non-commutative algebra

Safe HaskellSafe
LanguageHaskell98

Math.Core.Utils

Description

A module of simple utility functions which are used throughout the rest of the library

Synopsis

Documentation

toSet :: Ord a => [a] -> [a] Source #

sortDesc :: Ord a => [a] -> [a] Source #

insertDesc :: Ord a => a -> [a] -> [a] Source #

setUnionAsc :: Ord a => [a] -> [a] -> [a] Source #

The set union of two ascending lists. If both inputs are strictly increasing, then the output is their union and is strictly increasing. The code does not check that the lists are strictly increasing.

setUnionDesc :: Ord a => [a] -> [a] -> [a] Source #

intersectAsc :: Ord a => [a] -> [a] -> [a] Source #

The (multi-)set intersection of two ascending lists. If both inputs are strictly increasing, then the output is the set intersection and is strictly increasing. If both inputs are weakly increasing, then the output is the multiset intersection (with multiplicity), and is weakly increasing.

multisetSumAsc :: Ord a => [a] -> [a] -> [a] Source #

The multiset sum of two ascending lists. If xs and ys are ascending, then multisetSumAsc xs ys == sort (xs++ys). The code does not check that the lists are ascending.

multisetSumDesc :: Ord a => [a] -> [a] -> [a] Source #

The multiset sum of two descending lists. If xs and ys are descending, then multisetSumDesc xs ys == sortDesc (xs++ys). The code does not check that the lists are descending.

diffAsc :: Ord a => [a] -> [a] -> [a] Source #

The multiset or set difference between two ascending lists. If xs and ys are ascending, then diffAsc xs ys == xs \ ys, and diffAsc is more efficient. If xs and ys are sets (that is, have no repetitions), then diffAsc xs ys is the set difference. The code does not check that the lists are ascending.

diffDesc :: Ord a => [a] -> [a] -> [a] Source #

The multiset or set difference between two descending lists. If xs and ys are descending, then diffDesc xs ys == xs \ ys, and diffDesc is more efficient. If xs and ys are sets (that is, have no repetitions), then diffDesc xs ys is the set difference. The code does not check that the lists are descending.

isSubsetAsc :: Ord a => [a] -> [a] -> Bool Source #

isSubMultisetAsc :: Ord a => [a] -> [a] -> Bool Source #

elemAsc :: Ord a => a -> [a] -> Bool Source #

Is the element in the ascending list?

With infinite lists, this can fail to terminate. For example, elemAsc 1 [12,34,7/8..] would fail to terminate. However, with a list of Integer, this will always terminate.

notElemAsc :: Ord a => a -> [a] -> Bool Source #

Is the element not in the ascending list? (With infinite lists, this can fail to terminate.)

picks :: [a] -> [(a, [a])] Source #

Return all the ways to "pick one and leave the others" from a list

pairs :: [t] -> [(t, t)] Source #

ordpair :: Ord b => b -> b -> (b, b) Source #

foldcmpl :: (b -> b -> Bool) -> [b] -> Bool Source #

cmpfst :: Ord a => (a, b1) -> (a, b2) -> Ordering Source #

eqfst :: Eq a => (a, b1) -> (a, b2) -> Bool Source #

fromBase :: (Foldable t, Num a) => a -> t a -> a Source #

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

Given a set xs, represented as an ordered list, powersetdfs xs returns the list of all subsets of xs, in lex order

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

Given a set xs, represented as an ordered list, powersetbfs xs returns the list of all subsets of xs, in shortlex order

combinationsOf :: Int -> [a] -> [[a]] Source #

Given a positive integer k, and a set xs, represented as a list, combinationsOf k xs returns all k-element subsets of xs. The result will be in lex order, relative to the order of the xs.

choose :: Integral a => a -> a -> a Source #

choose n k is the number of ways of choosing k distinct elements from an n-set

class FinSet x where Source #

The class of finite sets

Methods

elts :: [x] Source #

Instances
FinSet F25 Source # 
Instance details

Defined in Math.Core.Field

Methods

elts :: [F25] Source #

FinSet F16 Source # 
Instance details

Defined in Math.Core.Field

Methods

elts :: [F16] Source #

FinSet F9 Source # 
Instance details

Defined in Math.Core.Field

Methods

elts :: [F9] Source #

FinSet F8 Source # 
Instance details

Defined in Math.Core.Field

Methods

elts :: [F8] Source #

FinSet F4 Source # 
Instance details

Defined in Math.Core.Field

Methods

elts :: [F4] Source #

FinSet F23 Source # 
Instance details

Defined in Math.Core.Field

Methods

elts :: [F23] Source #

FinSet F19 Source # 
Instance details

Defined in Math.Core.Field

Methods

elts :: [F19] Source #

FinSet F17 Source # 
Instance details

Defined in Math.Core.Field

Methods

elts :: [F17] Source #

FinSet F13 Source # 
Instance details

Defined in Math.Core.Field

Methods

elts :: [F13] Source #

FinSet F11 Source # 
Instance details

Defined in Math.Core.Field

Methods

elts :: [F11] Source #

FinSet F7 Source # 
Instance details

Defined in Math.Core.Field

Methods

elts :: [F7] Source #

FinSet F5 Source # 
Instance details

Defined in Math.Core.Field

Methods

elts :: [F5] Source #

FinSet F3 Source # 
Instance details

Defined in Math.Core.Field

Methods

elts :: [F3] Source #

FinSet F2 Source # 
Instance details

Defined in Math.Core.Field

Methods

elts :: [F2] Source #

IntegerAsType p => FinSet (Fp p) Source # 
Instance details

Defined in Math.Algebra.Field.Base

Methods

elts :: [Fp p] Source #

(FinSet fp, Eq fp, Num fp, PolynomialAsType fp poly) => FinSet (ExtensionField fp poly) Source # 
Instance details

Defined in Math.Algebra.Field.Extension

Methods

elts :: [ExtensionField fp poly] Source #

class HasInverses a where Source #

A class representing algebraic structures having an inverse operation. Note that in some cases not every element has an inverse.

Methods

inverse :: a -> a Source #

Instances
HasInverses SSymF Source # 
Instance details

Defined in Math.Combinatorics.CombinatorialHopfAlgebra

Methods

inverse :: SSymF -> SSymF Source #

Ord a => HasInverses (Permutation a) Source #

The HasInverses instance is what enables us to write g^-1 for the inverse of a group element.

Instance details

Defined in Math.Algebra.Group.PermutationGroup

HasInverses (GroupAlgebra Q) Source #

Note that the inverse of a group algebra element can only be efficiently calculated if the group generated by the non-zero terms is very small (eg <100 elements).

Instance details

Defined in Math.Algebras.GroupAlgebra

(Eq k, Fractional k, Ord a, Show a) => HasInverses (Vect k (Interval a)) Source # 
Instance details

Defined in Math.Combinatorics.IncidenceAlgebra

Methods

inverse :: Vect k (Interval a) -> Vect k (Interval a) Source #

(^-) :: (Num a, HasInverses a, Integral b) => a -> b -> a infix 8 Source #

A trick: x^-1 returns the inverse of x