unboxed-containers-0.0.2.4: Self-optimizing unboxed sets using view patterns and data families

Copyright(c) Edward Kmett 2009 (c) Daan Leijen 2002
LicenseBSD3
Maintainerekmett@gmail.com
Stabilityexperimental
Portabilitynon-portable (type families, view patterns, unboxed tuples)
Safe HaskellSafe
LanguageHaskell98

Data.Set.Unboxed

Contents

Description

An efficient implementation of sets.

Since many function names (but not the type name) clash with Prelude names, this module is usually imported qualified, e.g.

 import Data.Set.Unboxed (USet)
 import qualified Data.Set.Unboxed as USet

The implementation of USet is based on size balanced binary trees (or trees of bounded balance) as described by:

  • Stephen Adams, "Efficient sets: a balancing act", Journal of Functional Programming 3(4):553-562, October 1993, http://www.swiss.ai.mit.edu/~adams/BB/.
  • J. Nievergelt and E.M. Reingold, "Binary search trees of bounded balance", SIAM journal of computing 2(1), March 1973.

Note that the implementation is left-biased -- the elements of a first argument are always preferred to the second, for example in union or insert. Of course, left-biasing can only be observed when equality is an equivalence relation instead of structural equality.

Modified from Data.Set to use type families for automatic unboxing

Synopsis

Set type

class US a where Source #

Minimal complete definition

view, tip, bin

Associated Types

data USet a Source #

Methods

size :: USet a -> Size Source #

O(1). The number of elements in the set.

null :: USet a -> Bool Source #

O(1). Is this the empty set?

Instances

US Char Source # 

Associated Types

data USet Char :: * Source #

US Double Source # 
US Float Source # 
US Int Source # 

Associated Types

data USet Int :: * Source #

Methods

view :: USet Int -> Set Int

viewk :: b -> (Size -> Int -> USet Int -> USet Int -> b) -> USet Int -> b

viewBin :: USet Int -> (#LiftedRep, LiftedRep, LiftedRep, Int, USet Int, USet Int#)

size :: USet Int -> Size Source #

null :: USet Int -> Bool Source #

tip :: USet Int

bin :: Size -> Int -> USet Int -> USet Int -> USet Int

balance :: Int -> USet Int -> USet Int -> USet Int

US Int8 Source # 

Associated Types

data USet Int8 :: * Source #

US Int16 Source # 
US Int32 Source # 
US Int64 Source # 
US Integer Source # 
US Word8 Source # 
US Word16 Source # 
US Word32 Source # 
US Word64 Source # 
US (Boxed a) Source # 

Associated Types

data USet (Boxed a) :: * Source #

Methods

view :: USet (Boxed a) -> Set (Boxed a)

viewk :: b -> (Size -> Boxed a -> USet (Boxed a) -> USet (Boxed a) -> b) -> USet (Boxed a) -> b

viewBin :: USet (Boxed a) -> (#LiftedRep, LiftedRep, LiftedRep, Boxed a, USet (Boxed a), USet (Boxed a)#)

size :: USet (Boxed a) -> Size Source #

null :: USet (Boxed a) -> Bool Source #

tip :: USet (Boxed a)

bin :: Size -> Boxed a -> USet (Boxed a) -> USet (Boxed a) -> USet (Boxed a)

balance :: Boxed a -> USet (Boxed a) -> USet (Boxed a) -> USet (Boxed a)

US (Char, Char) Source # 

Associated Types

data USet (Char, Char) :: * Source #

Methods

view :: USet (Char, Char) -> Set (Char, Char)

viewk :: b -> (Size -> (Char, Char) -> USet (Char, Char) -> USet (Char, Char) -> b) -> USet (Char, Char) -> b

viewBin :: USet (Char, Char) -> (#LiftedRep, LiftedRep, LiftedRep, (Char, Char), USet (Char, Char), USet (Char, Char)#)

size :: USet (Char, Char) -> Size Source #

null :: USet (Char, Char) -> Bool Source #

tip :: USet (Char, Char)

bin :: Size -> (Char, Char) -> USet (Char, Char) -> USet (Char, Char) -> USet (Char, Char)

balance :: (Char, Char) -> USet (Char, Char) -> USet (Char, Char) -> USet (Char, Char)

US (Double, Double) Source # 
US (Float, Float) Source # 

Associated Types

data USet (Float, Float) :: * Source #

US (Int, Int) Source # 

Associated Types

data USet (Int, Int) :: * Source #

Methods

view :: USet (Int, Int) -> Set (Int, Int)

viewk :: b -> (Size -> (Int, Int) -> USet (Int, Int) -> USet (Int, Int) -> b) -> USet (Int, Int) -> b

viewBin :: USet (Int, Int) -> (#LiftedRep, LiftedRep, LiftedRep, (Int, Int), USet (Int, Int), USet (Int, Int)#)

size :: USet (Int, Int) -> Size Source #

null :: USet (Int, Int) -> Bool Source #

tip :: USet (Int, Int)

bin :: Size -> (Int, Int) -> USet (Int, Int) -> USet (Int, Int) -> USet (Int, Int)

balance :: (Int, Int) -> USet (Int, Int) -> USet (Int, Int) -> USet (Int, Int)

US (Int8, Int8) Source # 

Associated Types

data USet (Int8, Int8) :: * Source #

Methods

view :: USet (Int8, Int8) -> Set (Int8, Int8)

viewk :: b -> (Size -> (Int8, Int8) -> USet (Int8, Int8) -> USet (Int8, Int8) -> b) -> USet (Int8, Int8) -> b

viewBin :: USet (Int8, Int8) -> (#LiftedRep, LiftedRep, LiftedRep, (Int8, Int8), USet (Int8, Int8), USet (Int8, Int8)#)

size :: USet (Int8, Int8) -> Size Source #

null :: USet (Int8, Int8) -> Bool Source #

tip :: USet (Int8, Int8)

bin :: Size -> (Int8, Int8) -> USet (Int8, Int8) -> USet (Int8, Int8) -> USet (Int8, Int8)

balance :: (Int8, Int8) -> USet (Int8, Int8) -> USet (Int8, Int8) -> USet (Int8, Int8)

US (Int16, Int16) Source # 

Associated Types

data USet (Int16, Int16) :: * Source #

US (Int32, Int32) Source # 

Associated Types

data USet (Int32, Int32) :: * Source #

US (Int64, Int64) Source # 

Associated Types

data USet (Int64, Int64) :: * Source #

US (Integer, Integer) Source # 
US (Word8, Word8) Source # 

Associated Types

data USet (Word8, Word8) :: * Source #

US (Word16, Word16) Source # 
US (Word32, Word32) Source # 
US (Word64, Word64) Source # 
US (Boxed a, Boxed b) Source # 

Associated Types

data USet (Boxed a, Boxed b) :: * Source #

Methods

view :: USet (Boxed a, Boxed b) -> Set (Boxed a, Boxed b)

viewk :: b -> (Size -> (Boxed a, Boxed b) -> USet (Boxed a, Boxed b) -> USet (Boxed a, Boxed b) -> b) -> USet (Boxed a, Boxed b) -> b

viewBin :: USet (Boxed a, Boxed b) -> (#LiftedRep, LiftedRep, LiftedRep, (Boxed a, Boxed b), USet (Boxed a, Boxed b), USet (Boxed a, Boxed b)#)

size :: USet (Boxed a, Boxed b) -> Size Source #

null :: USet (Boxed a, Boxed b) -> Bool Source #

tip :: USet (Boxed a, Boxed b)

bin :: Size -> (Boxed a, Boxed b) -> USet (Boxed a, Boxed b) -> USet (Boxed a, Boxed b) -> USet (Boxed a, Boxed b)

balance :: (Boxed a, Boxed b) -> USet (Boxed a, Boxed b) -> USet (Boxed a, Boxed b) -> USet (Boxed a, Boxed b)

US (Char, Char, Char) Source # 

Associated Types

data USet (Char, Char, Char) :: * Source #

Methods

view :: USet (Char, Char, Char) -> Set (Char, Char, Char)

viewk :: b -> (Size -> (Char, Char, Char) -> USet (Char, Char, Char) -> USet (Char, Char, Char) -> b) -> USet (Char, Char, Char) -> b

viewBin :: USet (Char, Char, Char) -> (#LiftedRep, LiftedRep, LiftedRep, (Char, Char, Char), USet (Char, Char, Char), USet (Char, Char, Char)#)

size :: USet (Char, Char, Char) -> Size Source #

null :: USet (Char, Char, Char) -> Bool Source #

tip :: USet (Char, Char, Char)

bin :: Size -> (Char, Char, Char) -> USet (Char, Char, Char) -> USet (Char, Char, Char) -> USet (Char, Char, Char)

balance :: (Char, Char, Char) -> USet (Char, Char, Char) -> USet (Char, Char, Char) -> USet (Char, Char, Char)

US (Double, Double, Double) Source # 
US (Float, Float, Float) Source # 
US (Int, Int, Int) Source # 

Associated Types

data USet (Int, Int, Int) :: * Source #

Methods

view :: USet (Int, Int, Int) -> Set (Int, Int, Int)

viewk :: b -> (Size -> (Int, Int, Int) -> USet (Int, Int, Int) -> USet (Int, Int, Int) -> b) -> USet (Int, Int, Int) -> b

viewBin :: USet (Int, Int, Int) -> (#LiftedRep, LiftedRep, LiftedRep, (Int, Int, Int), USet (Int, Int, Int), USet (Int, Int, Int)#)

size :: USet (Int, Int, Int) -> Size Source #

null :: USet (Int, Int, Int) -> Bool Source #

tip :: USet (Int, Int, Int)

bin :: Size -> (Int, Int, Int) -> USet (Int, Int, Int) -> USet (Int, Int, Int) -> USet (Int, Int, Int)

balance :: (Int, Int, Int) -> USet (Int, Int, Int) -> USet (Int, Int, Int) -> USet (Int, Int, Int)

US (Int8, Int8, Int8) Source # 

Associated Types

data USet (Int8, Int8, Int8) :: * Source #

Methods

view :: USet (Int8, Int8, Int8) -> Set (Int8, Int8, Int8)

viewk :: b -> (Size -> (Int8, Int8, Int8) -> USet (Int8, Int8, Int8) -> USet (Int8, Int8, Int8) -> b) -> USet (Int8, Int8, Int8) -> b

viewBin :: USet (Int8, Int8, Int8) -> (#LiftedRep, LiftedRep, LiftedRep, (Int8, Int8, Int8), USet (Int8, Int8, Int8), USet (Int8, Int8, Int8)#)

size :: USet (Int8, Int8, Int8) -> Size Source #

null :: USet (Int8, Int8, Int8) -> Bool Source #

tip :: USet (Int8, Int8, Int8)

bin :: Size -> (Int8, Int8, Int8) -> USet (Int8, Int8, Int8) -> USet (Int8, Int8, Int8) -> USet (Int8, Int8, Int8)

balance :: (Int8, Int8, Int8) -> USet (Int8, Int8, Int8) -> USet (Int8, Int8, Int8) -> USet (Int8, Int8, Int8)

US (Int16, Int16, Int16) Source # 
US (Int32, Int32, Int32) Source # 
US (Int64, Int64, Int64) Source # 
US (Integer, Integer, Integer) Source # 
US (Word8, Word8, Word8) Source # 
US (Word16, Word16, Word16) Source # 
US (Word32, Word32, Word32) Source # 
US (Word64, Word64, Word64) Source # 
US (Boxed a, Boxed b, Boxed c) Source # 

Associated Types

data USet (Boxed a, Boxed b, Boxed c) :: * Source #

Methods

view :: USet (Boxed a, Boxed b, Boxed c) -> Set (Boxed a, Boxed b, Boxed c)

viewk :: b -> (Size -> (Boxed a, Boxed b, Boxed c) -> USet (Boxed a, Boxed b, Boxed c) -> USet (Boxed a, Boxed b, Boxed c) -> b) -> USet (Boxed a, Boxed b, Boxed c) -> b

viewBin :: USet (Boxed a, Boxed b, Boxed c) -> (#LiftedRep, LiftedRep, LiftedRep, (Boxed a, Boxed b, Boxed c), USet (Boxed a, Boxed b, Boxed c), USet (Boxed a, Boxed b, Boxed c)#)

size :: USet (Boxed a, Boxed b, Boxed c) -> Size Source #

null :: USet (Boxed a, Boxed b, Boxed c) -> Bool Source #

tip :: USet (Boxed a, Boxed b, Boxed c)

bin :: Size -> (Boxed a, Boxed b, Boxed c) -> USet (Boxed a, Boxed b, Boxed c) -> USet (Boxed a, Boxed b, Boxed c) -> USet (Boxed a, Boxed b, Boxed c)

balance :: (Boxed a, Boxed b, Boxed c) -> USet (Boxed a, Boxed b, Boxed c) -> USet (Boxed a, Boxed b, Boxed c) -> USet (Boxed a, Boxed b, Boxed c)

US (Char, Char, Char, Char) Source # 

Associated Types

data USet (Char, Char, Char, Char) :: * Source #

US (Double, Double, Double, Double) Source # 
US (Float, Float, Float, Float) Source # 
US (Int, Int, Int, Int) Source # 

Associated Types

data USet (Int, Int, Int, Int) :: * Source #

Methods

view :: USet (Int, Int, Int, Int) -> Set (Int, Int, Int, Int)

viewk :: b -> (Size -> (Int, Int, Int, Int) -> USet (Int, Int, Int, Int) -> USet (Int, Int, Int, Int) -> b) -> USet (Int, Int, Int, Int) -> b

viewBin :: USet (Int, Int, Int, Int) -> (#LiftedRep, LiftedRep, LiftedRep, (Int, Int, Int, Int), USet (Int, Int, Int, Int), USet (Int, Int, Int, Int)#)

size :: USet (Int, Int, Int, Int) -> Size Source #

null :: USet (Int, Int, Int, Int) -> Bool Source #

tip :: USet (Int, Int, Int, Int)

bin :: Size -> (Int, Int, Int, Int) -> USet (Int, Int, Int, Int) -> USet (Int, Int, Int, Int) -> USet (Int, Int, Int, Int)

balance :: (Int, Int, Int, Int) -> USet (Int, Int, Int, Int) -> USet (Int, Int, Int, Int) -> USet (Int, Int, Int, Int)

US (Int8, Int8, Int8, Int8) Source # 

Associated Types

data USet (Int8, Int8, Int8, Int8) :: * Source #

US (Int16, Int16, Int16, Int16) Source # 
US (Int32, Int32, Int32, Int32) Source # 
US (Int64, Int64, Int64, Int64) Source # 
US (Integer, Integer, Integer, Integer) Source # 
US (Word8, Word8, Word8, Word8) Source # 
US (Word16, Word16, Word16, Word16) Source # 
US (Word32, Word32, Word32, Word32) Source # 
US (Word64, Word64, Word64, Word64) Source # 
US (Boxed a, Boxed b, Boxed c, Boxed d) Source # 

Associated Types

data USet (Boxed a, Boxed b, Boxed c, Boxed d) :: * Source #

Methods

view :: USet (Boxed a, Boxed b, Boxed c, Boxed d) -> Set (Boxed a, Boxed b, Boxed c, Boxed d)

viewk :: b -> (Size -> (Boxed a, Boxed b, Boxed c, Boxed d) -> USet (Boxed a, Boxed b, Boxed c, Boxed d) -> USet (Boxed a, Boxed b, Boxed c, Boxed d) -> b) -> USet (Boxed a, Boxed b, Boxed c, Boxed d) -> b

viewBin :: USet (Boxed a, Boxed b, Boxed c, Boxed d) -> (#LiftedRep, LiftedRep, LiftedRep, (Boxed a, Boxed b, Boxed c, Boxed d), USet (Boxed a, Boxed b, Boxed c, Boxed d), USet (Boxed a, Boxed b, Boxed c, Boxed d)#)

size :: USet (Boxed a, Boxed b, Boxed c, Boxed d) -> Size Source #

null :: USet (Boxed a, Boxed b, Boxed c, Boxed d) -> Bool Source #

tip :: USet (Boxed a, Boxed b, Boxed c, Boxed d)

bin :: Size -> (Boxed a, Boxed b, Boxed c, Boxed d) -> USet (Boxed a, Boxed b, Boxed c, Boxed d) -> USet (Boxed a, Boxed b, Boxed c, Boxed d) -> USet (Boxed a, Boxed b, Boxed c, Boxed d)

balance :: (Boxed a, Boxed b, Boxed c, Boxed d) -> USet (Boxed a, Boxed b, Boxed c, Boxed d) -> USet (Boxed a, Boxed b, Boxed c, Boxed d) -> USet (Boxed a, Boxed b, Boxed c, Boxed d)

US (Char, Char, Char, Char, Char) Source # 
US (Double, Double, Double, Double, Double) Source # 
US (Float, Float, Float, Float, Float) Source # 
US (Int, Int, Int, Int, Int) Source # 

Associated Types

data USet (Int, Int, Int, Int, Int) :: * Source #

Methods

view :: USet (Int, Int, Int, Int, Int) -> Set (Int, Int, Int, Int, Int)

viewk :: b -> (Size -> (Int, Int, Int, Int, Int) -> USet (Int, Int, Int, Int, Int) -> USet (Int, Int, Int, Int, Int) -> b) -> USet (Int, Int, Int, Int, Int) -> b

viewBin :: USet (Int, Int, Int, Int, Int) -> (#LiftedRep, LiftedRep, LiftedRep, (Int, Int, Int, Int, Int), USet (Int, Int, Int, Int, Int), USet (Int, Int, Int, Int, Int)#)

size :: USet (Int, Int, Int, Int, Int) -> Size Source #

null :: USet (Int, Int, Int, Int, Int) -> Bool Source #

tip :: USet (Int, Int, Int, Int, Int)

bin :: Size -> (Int, Int, Int, Int, Int) -> USet (Int, Int, Int, Int, Int) -> USet (Int, Int, Int, Int, Int) -> USet (Int, Int, Int, Int, Int)

balance :: (Int, Int, Int, Int, Int) -> USet (Int, Int, Int, Int, Int) -> USet (Int, Int, Int, Int, Int) -> USet (Int, Int, Int, Int, Int)

US (Int8, Int8, Int8, Int8, Int8) Source # 
US (Int16, Int16, Int16, Int16, Int16) Source # 
US (Int32, Int32, Int32, Int32, Int32) Source # 
US (Int64, Int64, Int64, Int64, Int64) Source # 
US (Integer, Integer, Integer, Integer, Integer) Source # 
US (Word8, Word8, Word8, Word8, Word8) Source # 
US (Word16, Word16, Word16, Word16, Word16) Source # 
US (Word32, Word32, Word32, Word32, Word32) Source # 
US (Word64, Word64, Word64, Word64, Word64) Source # 
US (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e) Source # 

Associated Types

data USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e) :: * Source #

Methods

view :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e) -> Set (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e)

viewk :: b -> (Size -> (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e) -> b) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e) -> b

viewBin :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e) -> (#LiftedRep, LiftedRep, LiftedRep, (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e), USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e), USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e)#)

size :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e) -> Size Source #

null :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e) -> Bool Source #

tip :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e)

bin :: Size -> (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e)

balance :: (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e)

US (Char, Char, Char, Char, Char, Char) Source # 
US (Double, Double, Double, Double, Double, Double) Source # 
US (Float, Float, Float, Float, Float, Float) Source # 
US (Int, Int, Int, Int, Int, Int) Source # 

Associated Types

data USet (Int, Int, Int, Int, Int, Int) :: * Source #

Methods

view :: USet (Int, Int, Int, Int, Int, Int) -> Set (Int, Int, Int, Int, Int, Int)

viewk :: b -> (Size -> (Int, Int, Int, Int, Int, Int) -> USet (Int, Int, Int, Int, Int, Int) -> USet (Int, Int, Int, Int, Int, Int) -> b) -> USet (Int, Int, Int, Int, Int, Int) -> b

viewBin :: USet (Int, Int, Int, Int, Int, Int) -> (#LiftedRep, LiftedRep, LiftedRep, (Int, Int, Int, Int, Int, Int), USet (Int, Int, Int, Int, Int, Int), USet (Int, Int, Int, Int, Int, Int)#)

size :: USet (Int, Int, Int, Int, Int, Int) -> Size Source #

null :: USet (Int, Int, Int, Int, Int, Int) -> Bool Source #

tip :: USet (Int, Int, Int, Int, Int, Int)

bin :: Size -> (Int, Int, Int, Int, Int, Int) -> USet (Int, Int, Int, Int, Int, Int) -> USet (Int, Int, Int, Int, Int, Int) -> USet (Int, Int, Int, Int, Int, Int)

balance :: (Int, Int, Int, Int, Int, Int) -> USet (Int, Int, Int, Int, Int, Int) -> USet (Int, Int, Int, Int, Int, Int) -> USet (Int, Int, Int, Int, Int, Int)

US (Int8, Int8, Int8, Int8, Int8, Int8) Source # 
US (Int16, Int16, Int16, Int16, Int16, Int16) Source # 
US (Int32, Int32, Int32, Int32, Int32, Int32) Source # 
US (Int64, Int64, Int64, Int64, Int64, Int64) Source # 
US (Integer, Integer, Integer, Integer, Integer, Integer) Source # 

Associated Types

data USet (Integer, Integer, Integer, Integer, Integer, Integer) :: * Source #

US (Word8, Word8, Word8, Word8, Word8, Word8) Source # 
US (Word16, Word16, Word16, Word16, Word16, Word16) Source # 
US (Word32, Word32, Word32, Word32, Word32, Word32) Source # 
US (Word64, Word64, Word64, Word64, Word64, Word64) Source # 
US (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f) Source # 

Associated Types

data USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f) :: * Source #

Methods

view :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f) -> Set (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f)

viewk :: b -> (Size -> (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f) -> b) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f) -> b

viewBin :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f) -> (#LiftedRep, LiftedRep, LiftedRep, (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f), USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f), USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f)#)

size :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f) -> Size Source #

null :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f) -> Bool Source #

tip :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f)

bin :: Size -> (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f)

balance :: (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f)

US (Char, Char, Char, Char, Char, Char, Char) Source # 
US (Double, Double, Double, Double, Double, Double, Double) Source # 

Associated Types

data USet (Double, Double, Double, Double, Double, Double, Double) :: * Source #

US (Float, Float, Float, Float, Float, Float, Float) Source # 
US (Int, Int, Int, Int, Int, Int, Int) Source # 

Associated Types

data USet (Int, Int, Int, Int, Int, Int, Int) :: * Source #

Methods

view :: USet (Int, Int, Int, Int, Int, Int, Int) -> Set (Int, Int, Int, Int, Int, Int, Int)

viewk :: b -> (Size -> (Int, Int, Int, Int, Int, Int, Int) -> USet (Int, Int, Int, Int, Int, Int, Int) -> USet (Int, Int, Int, Int, Int, Int, Int) -> b) -> USet (Int, Int, Int, Int, Int, Int, Int) -> b

viewBin :: USet (Int, Int, Int, Int, Int, Int, Int) -> (#LiftedRep, LiftedRep, LiftedRep, (Int, Int, Int, Int, Int, Int, Int), USet (Int, Int, Int, Int, Int, Int, Int), USet (Int, Int, Int, Int, Int, Int, Int)#)

size :: USet (Int, Int, Int, Int, Int, Int, Int) -> Size Source #

null :: USet (Int, Int, Int, Int, Int, Int, Int) -> Bool Source #

tip :: USet (Int, Int, Int, Int, Int, Int, Int)

bin :: Size -> (Int, Int, Int, Int, Int, Int, Int) -> USet (Int, Int, Int, Int, Int, Int, Int) -> USet (Int, Int, Int, Int, Int, Int, Int) -> USet (Int, Int, Int, Int, Int, Int, Int)

balance :: (Int, Int, Int, Int, Int, Int, Int) -> USet (Int, Int, Int, Int, Int, Int, Int) -> USet (Int, Int, Int, Int, Int, Int, Int) -> USet (Int, Int, Int, Int, Int, Int, Int)

US (Int8, Int8, Int8, Int8, Int8, Int8, Int8) Source # 
US (Int16, Int16, Int16, Int16, Int16, Int16, Int16) Source # 
US (Int32, Int32, Int32, Int32, Int32, Int32, Int32) Source # 
US (Int64, Int64, Int64, Int64, Int64, Int64, Int64) Source # 
US (Integer, Integer, Integer, Integer, Integer, Integer, Integer) Source # 

Associated Types

data USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer) :: * Source #

Methods

view :: USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer) -> Set (Integer, Integer, Integer, Integer, Integer, Integer, Integer)

viewk :: b -> (Size -> (Integer, Integer, Integer, Integer, Integer, Integer, Integer) -> USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer) -> USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer) -> b) -> USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer) -> b

viewBin :: USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer) -> (#LiftedRep, LiftedRep, LiftedRep, (Integer, Integer, Integer, Integer, Integer, Integer, Integer), USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer), USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer)#)

size :: USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer) -> Size Source #

null :: USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer) -> Bool Source #

tip :: USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer)

bin :: Size -> (Integer, Integer, Integer, Integer, Integer, Integer, Integer) -> USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer) -> USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer) -> USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer)

balance :: (Integer, Integer, Integer, Integer, Integer, Integer, Integer) -> USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer) -> USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer) -> USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer)

US (Word8, Word8, Word8, Word8, Word8, Word8, Word8) Source # 
US (Word16, Word16, Word16, Word16, Word16, Word16, Word16) Source # 

Associated Types

data USet (Word16, Word16, Word16, Word16, Word16, Word16, Word16) :: * Source #

US (Word32, Word32, Word32, Word32, Word32, Word32, Word32) Source # 

Associated Types

data USet (Word32, Word32, Word32, Word32, Word32, Word32, Word32) :: * Source #

US (Word64, Word64, Word64, Word64, Word64, Word64, Word64) Source # 

Associated Types

data USet (Word64, Word64, Word64, Word64, Word64, Word64, Word64) :: * Source #

US (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g) Source # 

Associated Types

data USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g) :: * Source #

Methods

view :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g) -> Set (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g)

viewk :: b -> (Size -> (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g) -> b) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g) -> b

viewBin :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g) -> (#LiftedRep, LiftedRep, LiftedRep, (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g), USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g), USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g)#)

size :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g) -> Size Source #

null :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g) -> Bool Source #

tip :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g)

bin :: Size -> (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g)

balance :: (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g)

US (Char, Char, Char, Char, Char, Char, Char, Char) Source # 
US (Double, Double, Double, Double, Double, Double, Double, Double) Source # 

Associated Types

data USet (Double, Double, Double, Double, Double, Double, Double, Double) :: * Source #

Methods

view :: USet (Double, Double, Double, Double, Double, Double, Double, Double) -> Set (Double, Double, Double, Double, Double, Double, Double, Double)

viewk :: b -> (Size -> (Double, Double, Double, Double, Double, Double, Double, Double) -> USet (Double, Double, Double, Double, Double, Double, Double, Double) -> USet (Double, Double, Double, Double, Double, Double, Double, Double) -> b) -> USet (Double, Double, Double, Double, Double, Double, Double, Double) -> b

viewBin :: USet (Double, Double, Double, Double, Double, Double, Double, Double) -> (#LiftedRep, LiftedRep, LiftedRep, (Double, Double, Double, Double, Double, Double, Double, Double), USet (Double, Double, Double, Double, Double, Double, Double, Double), USet (Double, Double, Double, Double, Double, Double, Double, Double)#)

size :: USet (Double, Double, Double, Double, Double, Double, Double, Double) -> Size Source #

null :: USet (Double, Double, Double, Double, Double, Double, Double, Double) -> Bool Source #

tip :: USet (Double, Double, Double, Double, Double, Double, Double, Double)

bin :: Size -> (Double, Double, Double, Double, Double, Double, Double, Double) -> USet (Double, Double, Double, Double, Double, Double, Double, Double) -> USet (Double, Double, Double, Double, Double, Double, Double, Double) -> USet (Double, Double, Double, Double, Double, Double, Double, Double)

balance :: (Double, Double, Double, Double, Double, Double, Double, Double) -> USet (Double, Double, Double, Double, Double, Double, Double, Double) -> USet (Double, Double, Double, Double, Double, Double, Double, Double) -> USet (Double, Double, Double, Double, Double, Double, Double, Double)

US (Float, Float, Float, Float, Float, Float, Float, Float) Source # 

Associated Types

data USet (Float, Float, Float, Float, Float, Float, Float, Float) :: * Source #

US (Int, Int, Int, Int, Int, Int, Int, Int) Source # 

Associated Types

data USet (Int, Int, Int, Int, Int, Int, Int, Int) :: * Source #

Methods

view :: USet (Int, Int, Int, Int, Int, Int, Int, Int) -> Set (Int, Int, Int, Int, Int, Int, Int, Int)

viewk :: b -> (Size -> (Int, Int, Int, Int, Int, Int, Int, Int) -> USet (Int, Int, Int, Int, Int, Int, Int, Int) -> USet (Int, Int, Int, Int, Int, Int, Int, Int) -> b) -> USet (Int, Int, Int, Int, Int, Int, Int, Int) -> b

viewBin :: USet (Int, Int, Int, Int, Int, Int, Int, Int) -> (#LiftedRep, LiftedRep, LiftedRep, (Int, Int, Int, Int, Int, Int, Int, Int), USet (Int, Int, Int, Int, Int, Int, Int, Int), USet (Int, Int, Int, Int, Int, Int, Int, Int)#)

size :: USet (Int, Int, Int, Int, Int, Int, Int, Int) -> Size Source #

null :: USet (Int, Int, Int, Int, Int, Int, Int, Int) -> Bool Source #

tip :: USet (Int, Int, Int, Int, Int, Int, Int, Int)

bin :: Size -> (Int, Int, Int, Int, Int, Int, Int, Int) -> USet (Int, Int, Int, Int, Int, Int, Int, Int) -> USet (Int, Int, Int, Int, Int, Int, Int, Int) -> USet (Int, Int, Int, Int, Int, Int, Int, Int)

balance :: (Int, Int, Int, Int, Int, Int, Int, Int) -> USet (Int, Int, Int, Int, Int, Int, Int, Int) -> USet (Int, Int, Int, Int, Int, Int, Int, Int) -> USet (Int, Int, Int, Int, Int, Int, Int, Int)

US (Int8, Int8, Int8, Int8, Int8, Int8, Int8, Int8) Source # 
US (Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16) Source # 

Associated Types

data USet (Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16) :: * Source #

US (Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32) Source # 

Associated Types

data USet (Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32) :: * Source #

US (Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64) Source # 

Associated Types

data USet (Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64) :: * Source #

US (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer) Source # 

Methods

view :: USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer) -> Set (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer)

viewk :: b -> (Size -> (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer) -> USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer) -> USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer) -> b) -> USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer) -> b

viewBin :: USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer) -> (#LiftedRep, LiftedRep, LiftedRep, (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer), USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer), USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer)#)

size :: USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer) -> Size Source #

null :: USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer) -> Bool Source #

tip :: USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer)

bin :: Size -> (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer) -> USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer) -> USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer) -> USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer)

balance :: (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer) -> USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer) -> USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer) -> USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer)

US (Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8) Source # 

Associated Types

data USet (Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8) :: * Source #

US (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16) Source # 

Associated Types

data USet (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16) :: * Source #

Methods

view :: USet (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16) -> Set (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16)

viewk :: b -> (Size -> (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16) -> USet (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16) -> USet (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16) -> b) -> USet (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16) -> b

viewBin :: USet (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16) -> (#LiftedRep, LiftedRep, LiftedRep, (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16), USet (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16), USet (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16)#)

size :: USet (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16) -> Size Source #

null :: USet (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16) -> Bool Source #

tip :: USet (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16)

bin :: Size -> (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16) -> USet (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16) -> USet (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16) -> USet (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16)

balance :: (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16) -> USet (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16) -> USet (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16) -> USet (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16)

US (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32) Source # 

Associated Types

data USet (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32) :: * Source #

Methods

view :: USet (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32) -> Set (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32)

viewk :: b -> (Size -> (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32) -> USet (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32) -> USet (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32) -> b) -> USet (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32) -> b

viewBin :: USet (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32) -> (#LiftedRep, LiftedRep, LiftedRep, (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32), USet (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32), USet (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32)#)

size :: USet (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32) -> Size Source #

null :: USet (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32) -> Bool Source #

tip :: USet (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32)

bin :: Size -> (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32) -> USet (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32) -> USet (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32) -> USet (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32)

balance :: (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32) -> USet (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32) -> USet (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32) -> USet (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32)

US (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64) Source # 

Associated Types

data USet (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64) :: * Source #

Methods

view :: USet (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64) -> Set (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64)

viewk :: b -> (Size -> (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64) -> USet (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64) -> USet (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64) -> b) -> USet (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64) -> b

viewBin :: USet (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64) -> (#LiftedRep, LiftedRep, LiftedRep, (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64), USet (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64), USet (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64)#)

size :: USet (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64) -> Size Source #

null :: USet (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64) -> Bool Source #

tip :: USet (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64)

bin :: Size -> (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64) -> USet (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64) -> USet (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64) -> USet (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64)

balance :: (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64) -> USet (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64) -> USet (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64) -> USet (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64)

US (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h) Source # 

Associated Types

data USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h) :: * Source #

Methods

view :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h) -> Set (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h)

viewk :: b -> (Size -> (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h) -> b) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h) -> b

viewBin :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h) -> (#LiftedRep, LiftedRep, LiftedRep, (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h), USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h), USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h)#)

size :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h) -> Size Source #

null :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h) -> Bool Source #

tip :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h)

bin :: Size -> (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h)

balance :: (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h)

US (Char, Char, Char, Char, Char, Char, Char, Char, Char) Source # 

Associated Types

data USet (Char, Char, Char, Char, Char, Char, Char, Char, Char) :: * Source #

US (Double, Double, Double, Double, Double, Double, Double, Double, Double) Source # 

Associated Types

data USet (Double, Double, Double, Double, Double, Double, Double, Double, Double) :: * Source #

Methods

view :: USet (Double, Double, Double, Double, Double, Double, Double, Double, Double) -> Set (Double, Double, Double, Double, Double, Double, Double, Double, Double)

viewk :: b -> (Size -> (Double, Double, Double, Double, Double, Double, Double, Double, Double) -> USet (Double, Double, Double, Double, Double, Double, Double, Double, Double) -> USet (Double, Double, Double, Double, Double, Double, Double, Double, Double) -> b) -> USet (Double, Double, Double, Double, Double, Double, Double, Double, Double) -> b

viewBin :: USet (Double, Double, Double, Double, Double, Double, Double, Double, Double) -> (#LiftedRep, LiftedRep, LiftedRep, (Double, Double, Double, Double, Double, Double, Double, Double, Double), USet (Double, Double, Double, Double, Double, Double, Double, Double, Double), USet (Double, Double, Double, Double, Double, Double, Double, Double, Double)#)

size :: USet (Double, Double, Double, Double, Double, Double, Double, Double, Double) -> Size Source #

null :: USet (Double, Double, Double, Double, Double, Double, Double, Double, Double) -> Bool Source #

tip :: USet (Double, Double, Double, Double, Double, Double, Double, Double, Double)

bin :: Size -> (Double, Double, Double, Double, Double, Double, Double, Double, Double) -> USet (Double, Double, Double, Double, Double, Double, Double, Double, Double) -> USet (Double, Double, Double, Double, Double, Double, Double, Double, Double) -> USet (Double, Double, Double, Double, Double, Double, Double, Double, Double)

balance :: (Double, Double, Double, Double, Double, Double, Double, Double, Double) -> USet (Double, Double, Double, Double, Double, Double, Double, Double, Double) -> USet (Double, Double, Double, Double, Double, Double, Double, Double, Double) -> USet (Double, Double, Double, Double, Double, Double, Double, Double, Double)

US (Float, Float, Float, Float, Float, Float, Float, Float, Float) Source # 

Associated Types

data USet (Float, Float, Float, Float, Float, Float, Float, Float, Float) :: * Source #

Methods

view :: USet (Float, Float, Float, Float, Float, Float, Float, Float, Float) -> Set (Float, Float, Float, Float, Float, Float, Float, Float, Float)

viewk :: b -> (Size -> (Float, Float, Float, Float, Float, Float, Float, Float, Float) -> USet (Float, Float, Float, Float, Float, Float, Float, Float, Float) -> USet (Float, Float, Float, Float, Float, Float, Float, Float, Float) -> b) -> USet (Float, Float, Float, Float, Float, Float, Float, Float, Float) -> b

viewBin :: USet (Float, Float, Float, Float, Float, Float, Float, Float, Float) -> (#LiftedRep, LiftedRep, LiftedRep, (Float, Float, Float, Float, Float, Float, Float, Float, Float), USet (Float, Float, Float, Float, Float, Float, Float, Float, Float), USet (Float, Float, Float, Float, Float, Float, Float, Float, Float)#)

size :: USet (Float, Float, Float, Float, Float, Float, Float, Float, Float) -> Size Source #

null :: USet (Float, Float, Float, Float, Float, Float, Float, Float, Float) -> Bool Source #

tip :: USet (Float, Float, Float, Float, Float, Float, Float, Float, Float)

bin :: Size -> (Float, Float, Float, Float, Float, Float, Float, Float, Float) -> USet (Float, Float, Float, Float, Float, Float, Float, Float, Float) -> USet (Float, Float, Float, Float, Float, Float, Float, Float, Float) -> USet (Float, Float, Float, Float, Float, Float, Float, Float, Float)

balance :: (Float, Float, Float, Float, Float, Float, Float, Float, Float) -> USet (Float, Float, Float, Float, Float, Float, Float, Float, Float) -> USet (Float, Float, Float, Float, Float, Float, Float, Float, Float) -> USet (Float, Float, Float, Float, Float, Float, Float, Float, Float)

US (Int, Int, Int, Int, Int, Int, Int, Int, Int) Source # 

Associated Types

data USet (Int, Int, Int, Int, Int, Int, Int, Int, Int) :: * Source #

Methods

view :: USet (Int, Int, Int, Int, Int, Int, Int, Int, Int) -> Set (Int, Int, Int, Int, Int, Int, Int, Int, Int)

viewk :: b -> (Size -> (Int, Int, Int, Int, Int, Int, Int, Int, Int) -> USet (Int, Int, Int, Int, Int, Int, Int, Int, Int) -> USet (Int, Int, Int, Int, Int, Int, Int, Int, Int) -> b) -> USet (Int, Int, Int, Int, Int, Int, Int, Int, Int) -> b

viewBin :: USet (Int, Int, Int, Int, Int, Int, Int, Int, Int) -> (#LiftedRep, LiftedRep, LiftedRep, (Int, Int, Int, Int, Int, Int, Int, Int, Int), USet (Int, Int, Int, Int, Int, Int, Int, Int, Int), USet (Int, Int, Int, Int, Int, Int, Int, Int, Int)#)

size :: USet (Int, Int, Int, Int, Int, Int, Int, Int, Int) -> Size Source #

null :: USet (Int, Int, Int, Int, Int, Int, Int, Int, Int) -> Bool Source #

tip :: USet (Int, Int, Int, Int, Int, Int, Int, Int, Int)

bin :: Size -> (Int, Int, Int, Int, Int, Int, Int, Int, Int) -> USet (Int, Int, Int, Int, Int, Int, Int, Int, Int) -> USet (Int, Int, Int, Int, Int, Int, Int, Int, Int) -> USet (Int, Int, Int, Int, Int, Int, Int, Int, Int)

balance :: (Int, Int, Int, Int, Int, Int, Int, Int, Int) -> USet (Int, Int, Int, Int, Int, Int, Int, Int, Int) -> USet (Int, Int, Int, Int, Int, Int, Int, Int, Int) -> USet (Int, Int, Int, Int, Int, Int, Int, Int, Int)

US (Int8, Int8, Int8, Int8, Int8, Int8, Int8, Int8, Int8) Source # 

Associated Types

data USet (Int8, Int8, Int8, Int8, Int8, Int8, Int8, Int8, Int8) :: * Source #

US (Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16) Source # 

Associated Types

data USet (Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16) :: * Source #

Methods

view :: USet (Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16) -> Set (Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16)

viewk :: b -> (Size -> (Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16) -> USet (Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16) -> USet (Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16) -> b) -> USet (Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16) -> b

viewBin :: USet (Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16) -> (#LiftedRep, LiftedRep, LiftedRep, (Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16), USet (Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16), USet (Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16)#)

size :: USet (Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16) -> Size Source #

null :: USet (Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16) -> Bool Source #

tip :: USet (Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16)

bin :: Size -> (Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16) -> USet (Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16) -> USet (Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16) -> USet (Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16)

balance :: (Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16) -> USet (Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16) -> USet (Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16) -> USet (Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16, Int16)

US (Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32) Source # 

Associated Types

data USet (Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32) :: * Source #

Methods

view :: USet (Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32) -> Set (Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32)

viewk :: b -> (Size -> (Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32) -> USet (Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32) -> USet (Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32) -> b) -> USet (Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32) -> b

viewBin :: USet (Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32) -> (#LiftedRep, LiftedRep, LiftedRep, (Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32), USet (Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32), USet (Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32)#)

size :: USet (Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32) -> Size Source #

null :: USet (Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32) -> Bool Source #

tip :: USet (Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32)

bin :: Size -> (Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32) -> USet (Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32) -> USet (Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32) -> USet (Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32)

balance :: (Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32) -> USet (Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32) -> USet (Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32) -> USet (Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32, Int32)

US (Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64) Source # 

Associated Types

data USet (Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64) :: * Source #

Methods

view :: USet (Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64) -> Set (Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64)

viewk :: b -> (Size -> (Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64) -> USet (Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64) -> USet (Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64) -> b) -> USet (Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64) -> b

viewBin :: USet (Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64) -> (#LiftedRep, LiftedRep, LiftedRep, (Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64), USet (Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64), USet (Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64)#)

size :: USet (Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64) -> Size Source #

null :: USet (Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64) -> Bool Source #

tip :: USet (Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64)

bin :: Size -> (Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64) -> USet (Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64) -> USet (Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64) -> USet (Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64)

balance :: (Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64) -> USet (Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64) -> USet (Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64) -> USet (Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64, Int64)

US (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer) Source # 

Methods

view :: USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer) -> Set (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer)

viewk :: b -> (Size -> (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer) -> USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer) -> USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer) -> b) -> USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer) -> b

viewBin :: USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer) -> (#LiftedRep, LiftedRep, LiftedRep, (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer), USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer), USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer)#)

size :: USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer) -> Size Source #

null :: USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer) -> Bool Source #

tip :: USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer)

bin :: Size -> (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer) -> USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer) -> USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer) -> USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer)

balance :: (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer) -> USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer) -> USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer) -> USet (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer, Integer)

US (Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8) Source # 

Associated Types

data USet (Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8) :: * Source #

Methods

view :: USet (Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8) -> Set (Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8)

viewk :: b -> (Size -> (Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8) -> USet (Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8) -> USet (Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8) -> b) -> USet (Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8) -> b

viewBin :: USet (Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8) -> (#LiftedRep, LiftedRep, LiftedRep, (Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8), USet (Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8), USet (Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8)#)

size :: USet (Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8) -> Size Source #

null :: USet (Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8) -> Bool Source #

tip :: USet (Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8)

bin :: Size -> (Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8) -> USet (Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8) -> USet (Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8) -> USet (Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8)

balance :: (Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8) -> USet (Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8) -> USet (Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8) -> USet (Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8)

US (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16) Source # 

Associated Types

data USet (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16) :: * Source #

Methods

view :: USet (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16) -> Set (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16)

viewk :: b -> (Size -> (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16) -> USet (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16) -> USet (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16) -> b) -> USet (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16) -> b

viewBin :: USet (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16) -> (#LiftedRep, LiftedRep, LiftedRep, (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16), USet (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16), USet (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16)#)

size :: USet (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16) -> Size Source #

null :: USet (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16) -> Bool Source #

tip :: USet (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16)

bin :: Size -> (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16) -> USet (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16) -> USet (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16) -> USet (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16)

balance :: (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16) -> USet (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16) -> USet (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16) -> USet (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16)

US (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32) Source # 

Associated Types

data USet (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32) :: * Source #

Methods

view :: USet (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32) -> Set (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32)

viewk :: b -> (Size -> (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32) -> USet (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32) -> USet (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32) -> b) -> USet (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32) -> b

viewBin :: USet (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32) -> (#LiftedRep, LiftedRep, LiftedRep, (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32), USet (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32), USet (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32)#)

size :: USet (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32) -> Size Source #

null :: USet (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32) -> Bool Source #

tip :: USet (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32)

bin :: Size -> (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32) -> USet (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32) -> USet (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32) -> USet (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32)

balance :: (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32) -> USet (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32) -> USet (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32) -> USet (Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32, Word32)

US (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64) Source # 

Associated Types

data USet (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64) :: * Source #

Methods

view :: USet (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64) -> Set (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64)

viewk :: b -> (Size -> (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64) -> USet (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64) -> USet (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64) -> b) -> USet (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64) -> b

viewBin :: USet (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64) -> (#LiftedRep, LiftedRep, LiftedRep, (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64), USet (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64), USet (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64)#)

size :: USet (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64) -> Size Source #

null :: USet (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64) -> Bool Source #

tip :: USet (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64)

bin :: Size -> (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64) -> USet (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64) -> USet (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64) -> USet (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64)

balance :: (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64) -> USet (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64) -> USet (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64) -> USet (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64)

US (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i) Source # 

Associated Types

data USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i) :: * Source #

Methods

view :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i) -> Set (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i)

viewk :: b -> (Size -> (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i) -> b) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i) -> b

viewBin :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i) -> (#LiftedRep, LiftedRep, LiftedRep, (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i), USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i), USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i)#)

size :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i) -> Size Source #

null :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i) -> Bool Source #

tip :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i)

bin :: Size -> (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i)

balance :: (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i)

newtype Boxed a Source #

Constructors

Boxed 

Fields

Instances

Bounded a => Bounded (Boxed a) Source # 

Methods

minBound :: Boxed a #

maxBound :: Boxed a #

Eq a => Eq (Boxed a) Source # 

Methods

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

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

Ord a => Ord (Boxed a) Source # 

Methods

compare :: Boxed a -> Boxed a -> Ordering #

(<) :: Boxed a -> Boxed a -> Bool #

(<=) :: Boxed a -> Boxed a -> Bool #

(>) :: Boxed a -> Boxed a -> Bool #

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

max :: Boxed a -> Boxed a -> Boxed a #

min :: Boxed a -> Boxed a -> Boxed a #

Read a => Read (Boxed a) Source # 
Show a => Show (Boxed a) Source # 

Methods

showsPrec :: Int -> Boxed a -> ShowS #

show :: Boxed a -> String #

showList :: [Boxed a] -> ShowS #

US (Boxed a) Source # 

Associated Types

data USet (Boxed a) :: * Source #

Methods

view :: USet (Boxed a) -> Set (Boxed a)

viewk :: b -> (Size -> Boxed a -> USet (Boxed a) -> USet (Boxed a) -> b) -> USet (Boxed a) -> b

viewBin :: USet (Boxed a) -> (#LiftedRep, LiftedRep, LiftedRep, Boxed a, USet (Boxed a), USet (Boxed a)#)

size :: USet (Boxed a) -> Size Source #

null :: USet (Boxed a) -> Bool Source #

tip :: USet (Boxed a)

bin :: Size -> Boxed a -> USet (Boxed a) -> USet (Boxed a) -> USet (Boxed a)

balance :: Boxed a -> USet (Boxed a) -> USet (Boxed a) -> USet (Boxed a)

US (Boxed a, Boxed b) Source # 

Associated Types

data USet (Boxed a, Boxed b) :: * Source #

Methods

view :: USet (Boxed a, Boxed b) -> Set (Boxed a, Boxed b)

viewk :: b -> (Size -> (Boxed a, Boxed b) -> USet (Boxed a, Boxed b) -> USet (Boxed a, Boxed b) -> b) -> USet (Boxed a, Boxed b) -> b

viewBin :: USet (Boxed a, Boxed b) -> (#LiftedRep, LiftedRep, LiftedRep, (Boxed a, Boxed b), USet (Boxed a, Boxed b), USet (Boxed a, Boxed b)#)

size :: USet (Boxed a, Boxed b) -> Size Source #

null :: USet (Boxed a, Boxed b) -> Bool Source #

tip :: USet (Boxed a, Boxed b)

bin :: Size -> (Boxed a, Boxed b) -> USet (Boxed a, Boxed b) -> USet (Boxed a, Boxed b) -> USet (Boxed a, Boxed b)

balance :: (Boxed a, Boxed b) -> USet (Boxed a, Boxed b) -> USet (Boxed a, Boxed b) -> USet (Boxed a, Boxed b)

US (Boxed a, Boxed b, Boxed c) Source # 

Associated Types

data USet (Boxed a, Boxed b, Boxed c) :: * Source #

Methods

view :: USet (Boxed a, Boxed b, Boxed c) -> Set (Boxed a, Boxed b, Boxed c)

viewk :: b -> (Size -> (Boxed a, Boxed b, Boxed c) -> USet (Boxed a, Boxed b, Boxed c) -> USet (Boxed a, Boxed b, Boxed c) -> b) -> USet (Boxed a, Boxed b, Boxed c) -> b

viewBin :: USet (Boxed a, Boxed b, Boxed c) -> (#LiftedRep, LiftedRep, LiftedRep, (Boxed a, Boxed b, Boxed c), USet (Boxed a, Boxed b, Boxed c), USet (Boxed a, Boxed b, Boxed c)#)

size :: USet (Boxed a, Boxed b, Boxed c) -> Size Source #

null :: USet (Boxed a, Boxed b, Boxed c) -> Bool Source #

tip :: USet (Boxed a, Boxed b, Boxed c)

bin :: Size -> (Boxed a, Boxed b, Boxed c) -> USet (Boxed a, Boxed b, Boxed c) -> USet (Boxed a, Boxed b, Boxed c) -> USet (Boxed a, Boxed b, Boxed c)

balance :: (Boxed a, Boxed b, Boxed c) -> USet (Boxed a, Boxed b, Boxed c) -> USet (Boxed a, Boxed b, Boxed c) -> USet (Boxed a, Boxed b, Boxed c)

US (Boxed a, Boxed b, Boxed c, Boxed d) Source # 

Associated Types

data USet (Boxed a, Boxed b, Boxed c, Boxed d) :: * Source #

Methods

view :: USet (Boxed a, Boxed b, Boxed c, Boxed d) -> Set (Boxed a, Boxed b, Boxed c, Boxed d)

viewk :: b -> (Size -> (Boxed a, Boxed b, Boxed c, Boxed d) -> USet (Boxed a, Boxed b, Boxed c, Boxed d) -> USet (Boxed a, Boxed b, Boxed c, Boxed d) -> b) -> USet (Boxed a, Boxed b, Boxed c, Boxed d) -> b

viewBin :: USet (Boxed a, Boxed b, Boxed c, Boxed d) -> (#LiftedRep, LiftedRep, LiftedRep, (Boxed a, Boxed b, Boxed c, Boxed d), USet (Boxed a, Boxed b, Boxed c, Boxed d), USet (Boxed a, Boxed b, Boxed c, Boxed d)#)

size :: USet (Boxed a, Boxed b, Boxed c, Boxed d) -> Size Source #

null :: USet (Boxed a, Boxed b, Boxed c, Boxed d) -> Bool Source #

tip :: USet (Boxed a, Boxed b, Boxed c, Boxed d)

bin :: Size -> (Boxed a, Boxed b, Boxed c, Boxed d) -> USet (Boxed a, Boxed b, Boxed c, Boxed d) -> USet (Boxed a, Boxed b, Boxed c, Boxed d) -> USet (Boxed a, Boxed b, Boxed c, Boxed d)

balance :: (Boxed a, Boxed b, Boxed c, Boxed d) -> USet (Boxed a, Boxed b, Boxed c, Boxed d) -> USet (Boxed a, Boxed b, Boxed c, Boxed d) -> USet (Boxed a, Boxed b, Boxed c, Boxed d)

US (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e) Source # 

Associated Types

data USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e) :: * Source #

Methods

view :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e) -> Set (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e)

viewk :: b -> (Size -> (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e) -> b) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e) -> b

viewBin :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e) -> (#LiftedRep, LiftedRep, LiftedRep, (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e), USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e), USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e)#)

size :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e) -> Size Source #

null :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e) -> Bool Source #

tip :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e)

bin :: Size -> (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e)

balance :: (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e)

US (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f) Source # 

Associated Types

data USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f) :: * Source #

Methods

view :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f) -> Set (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f)

viewk :: b -> (Size -> (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f) -> b) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f) -> b

viewBin :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f) -> (#LiftedRep, LiftedRep, LiftedRep, (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f), USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f), USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f)#)

size :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f) -> Size Source #

null :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f) -> Bool Source #

tip :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f)

bin :: Size -> (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f)

balance :: (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f)

US (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g) Source # 

Associated Types

data USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g) :: * Source #

Methods

view :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g) -> Set (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g)

viewk :: b -> (Size -> (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g) -> b) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g) -> b

viewBin :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g) -> (#LiftedRep, LiftedRep, LiftedRep, (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g), USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g), USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g)#)

size :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g) -> Size Source #

null :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g) -> Bool Source #

tip :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g)

bin :: Size -> (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g)

balance :: (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g)

US (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h) Source # 

Associated Types

data USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h) :: * Source #

Methods

view :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h) -> Set (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h)

viewk :: b -> (Size -> (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h) -> b) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h) -> b

viewBin :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h) -> (#LiftedRep, LiftedRep, LiftedRep, (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h), USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h), USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h)#)

size :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h) -> Size Source #

null :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h) -> Bool Source #

tip :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h)

bin :: Size -> (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h)

balance :: (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h)

US (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i) Source # 

Associated Types

data USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i) :: * Source #

Methods

view :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i) -> Set (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i)

viewk :: b -> (Size -> (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i) -> b) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i) -> b

viewBin :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i) -> (#LiftedRep, LiftedRep, LiftedRep, (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i), USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i), USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i)#)

size :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i) -> Size Source #

null :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i) -> Bool Source #

tip :: USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i)

bin :: Size -> (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i)

balance :: (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i) -> USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i)

data USet (Boxed a) Source # 
data USet (Boxed a)
data USet (Boxed a, Boxed b) Source # 
data USet (Boxed a, Boxed b)
data USet (Boxed a, Boxed b, Boxed c) Source # 
data USet (Boxed a, Boxed b, Boxed c, Boxed d) Source # 
data USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e) Source # 
data USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f) Source # 
data USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g) Source # 
data USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h) Source # 
data USet (Boxed a, Boxed b, Boxed c, Boxed d, Boxed e, Boxed f, Boxed g, Boxed h, Boxed i) Source # 

type Size = Int Source #

Operators

(\\) :: (US a, Ord a) => USet a -> USet a -> USet a infixl 9 Source #

O(n+m). See difference.

Query

null :: US a => USet a -> Bool Source #

O(1). Is this the empty set?

size :: US a => USet a -> Size Source #

O(1). The number of elements in the set.

member :: (US a, Ord a) => a -> USet a -> Bool Source #

O(log n). Is the element in the set?

notMember :: (US a, Ord a) => a -> USet a -> Bool Source #

O(log n). Is the element not in the set?

isSubsetOf :: (US a, Ord a) => USet a -> USet a -> Bool Source #

O(n+m). Is this a subset? (s1 isSubsetOf s2) tells whether s1 is a subset of s2.

isProperSubsetOf :: (US a, Ord a) => USet a -> USet a -> Bool Source #

O(n+m). Is this a proper subset? (ie. a subset but not equal).

Construction

empty :: US a => USet a Source #

O(1). The empty set.

singleton :: US a => a -> USet a Source #

O(1). Create a singleton set.

insert :: (US a, Ord a) => a -> USet a -> USet a Source #

O(log n). Insert an element in a set. If the set already contains an element equal to the given value, it is replaced with the new value.

delete :: (US a, Ord a) => a -> USet a -> USet a Source #

O(log n). Delete an element from a set.

Combine

union :: (US a, Ord a) => USet a -> USet a -> USet a Source #

O(n+m). The union of two sets, preferring the first set when equal elements are encountered. The implementation uses the efficient hedge-union algorithm. Hedge-union is more efficient on (bigset union smallset).

unions :: (US a, Ord a) => [USet a] -> USet a Source #

The union of a list of sets: (unions == foldl union empty).

difference :: (US a, Ord a) => USet a -> USet a -> USet a Source #

O(n+m). Difference of two sets. The implementation uses an efficient hedge algorithm comparable with hedge-union.

intersection :: (US a, Ord a) => USet a -> USet a -> USet a Source #

O(n+m). The intersection of two sets. Elements of the result come from the first set, so for example

import qualified Data.Set as S
data AB = A | B deriving Show
instance Ord AB where compare _ _ = EQ
instance Eq AB where _ == _ = True
main = print (S.singleton A `S.intersection` S.singleton B,
              S.singleton B `S.intersection` S.singleton A)

prints (fromList [A],fromList [B]).

Filter

filter :: (US a, Ord a) => (a -> Bool) -> USet a -> USet a Source #

O(n). Filter all elements that satisfy the predicate.

partition :: (US a, Ord a) => (a -> Bool) -> USet a -> (USet a, USet a) Source #

O(n). Partition the set into two sets, one with all elements that satisfy the predicate and one with all elements that don't satisfy the predicate. See also split.

split :: (US a, Ord a) => a -> USet a -> (USet a, USet a) Source #

O(log n). The expression (split x set) is a pair (set1,set2) where set1 comprises the elements of set less than x and set2 comprises the elements of set greater than x.

splitMember :: (US a, Ord a) => a -> USet a -> (USet a, Bool, USet a) Source #

O(log n). Performs a split but also returns whether the pivot element was found in the original set.

Map

map :: (US a, US b, Ord a, Ord b) => (a -> b) -> USet a -> USet b Source #

O(n*log n). map f s is the set obtained by applying f to each element of s.

It's worth noting that the size of the result may be smaller if, for some (x,y), x /= y && f x == f y

mapMonotonic :: (US a, US b) => (a -> b) -> USet a -> USet b Source #

O(n). The

mapMonotonic f s == map f s, but works only when f is monotonic. The precondition is not checked. Semi-formally, we have:

and [x < y ==> f x < f y | x <- ls, y <- ls] 
                    ==> mapMonotonic f s == map f s
    where ls = toList s

Fold

fold :: US a => (a -> b -> b) -> b -> USet a -> b Source #

O(n). Fold over the elements of a set in an unspecified order.

Min/Max

findMin :: US a => USet a -> a Source #

O(log n). The minimal element of a set.

findMax :: US a => USet a -> a Source #

O(log n). The maximal element of a set.

deleteMin :: US a => USet a -> USet a Source #

O(log n). Delete the minimal element.

deleteMax :: US a => USet a -> USet a Source #

O(log n). Delete the maximal element.

deleteFindMin :: US a => USet a -> (a, USet a) Source #

O(log n). Delete and find the minimal element.

deleteFindMin set = (findMin set, deleteMin set)

deleteFindMax :: US a => USet a -> (a, USet a) Source #

O(log n). Delete and find the maximal element.

deleteFindMax set = (findMax set, deleteMax set)

maxView :: US a => USet a -> Maybe (a, USet a) Source #

O(log n). Retrieves the maximal key of the set, and the set stripped of that element, or Nothing if passed an empty set.

minView :: US a => USet a -> Maybe (a, USet a) Source #

O(log n). Retrieves the minimal key of the set, and the set stripped of that element, or Nothing if passed an empty set.

Conversion

List

elems :: US a => USet a -> [a] Source #

O(n). The elements of a set.

toList :: US a => USet a -> [a] Source #

O(n). Convert the set to a list of elements.

fromList :: (US a, Ord a) => [a] -> USet a Source #

O(n*log n). Create a set from a list of elements.

Ordered list

toAscList :: US a => USet a -> [a] Source #

O(n). Convert the set to an ascending list of elements.

fromAscList :: (US a, Eq a) => [a] -> USet a Source #

O(n). Build a set from an ascending list in linear time. The precondition (input list is ascending) is not checked.

fromDistinctAscList :: US a => [a] -> USet a Source #

O(n). Build a set from an ascending list of distinct elements in linear time. The precondition (input list is strictly ascending) is not checked.

Debugging

showTree :: (US a, Show a) => USet a -> String Source #

O(n). Show the tree that implements the set. The tree is shown in a compressed, hanging format.

showTreeWith :: (US a, Show a) => Bool -> Bool -> USet a -> String Source #

O(n). The expression (showTreeWith hang wide map) shows the tree that implements the set. If hang is True, a hanging tree is shown otherwise a rotated tree is shown. If wide is True, an extra wide version is shown.

Set> putStrLn $ showTreeWith True False $ fromDistinctAscList [1..5]
4
+--2
|  +--1
|  +--3
+--5

Set> putStrLn $ showTreeWith True True $ fromDistinctAscList [1..5]
4
|
+--2
|  |
|  +--1
|  |
|  +--3
|
+--5

Set> putStrLn $ showTreeWith False True $ fromDistinctAscList [1..5]
+--5
|
4
|
|  +--3
|  |
+--2
   |
   +--1

valid :: (US a, Ord a) => USet a -> Bool Source #

O(n). Test if the internal set structure is valid.