fixfile-0.4.0.0: File-backed recursive data structures.

Copyright(C) 2016 Rev. Johnny Healey
LicenseLGPL-3
MaintainerRev. Johnny Healey <rev.null@gmail.com>
Stabilityexperimental
Portabilityunknown
Safe HaskellNone
LanguageHaskell2010

Data.FixFile.Set

Description

This is a data type that can be used with a FixFile to store a set of Ordered items as an unbalanced binary tree. This file is not recommended for use, but exists for educational purposes. It has a simple implementation that is easier to read than some of the more advanced balanced data types.

Synopsis

Documentation

data Set i a Source #

Warning: Set is unbalanced and not recommended.

A Fixed (Set i) is a set of items represented as a binary tree.

Instances

Functor (Set i) Source # 

Methods

fmap :: (a -> b) -> Set i a -> Set i b #

(<$) :: a -> Set i b -> Set i a #

Foldable (Set i) Source # 

Methods

fold :: Monoid m => Set i m -> m #

foldMap :: Monoid m => (a -> m) -> Set i a -> m #

foldr :: (a -> b -> b) -> b -> Set i a -> b #

foldr' :: (a -> b -> b) -> b -> Set i a -> b #

foldl :: (b -> a -> b) -> b -> Set i a -> b #

foldl' :: (b -> a -> b) -> b -> Set i a -> b #

foldr1 :: (a -> a -> a) -> Set i a -> a #

foldl1 :: (a -> a -> a) -> Set i a -> a #

toList :: Set i a -> [a] #

null :: Set i a -> Bool #

length :: Set i a -> Int #

elem :: Eq a => a -> Set i a -> Bool #

maximum :: Ord a => Set i a -> a #

minimum :: Ord a => Set i a -> a #

sum :: Num a => Set i a -> a #

product :: Num a => Set i a -> a #

Traversable (Set i) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Set i a -> f (Set i b) #

sequenceA :: Applicative f => Set i (f a) -> f (Set i a) #

mapM :: Monad m => (a -> m b) -> Set i a -> m (Set i b) #

sequence :: Monad m => Set i (m a) -> m (Set i a) #

FixedFoldable (Set i) Source # 

Methods

foldMapF :: (Fixed g, Monoid m, (* ~ a) (Alg (Set i))) => (a -> m) -> g (Set i) -> m Source #

FixedAlg (Set i) Source # 

Associated Types

type Alg (Set i :: * -> *) :: * Source #

(Read i, Read a) => Read (Set i a) Source # 

Methods

readsPrec :: Int -> ReadS (Set i a) #

readList :: ReadS [Set i a] #

readPrec :: ReadPrec (Set i a) #

readListPrec :: ReadPrec [Set i a] #

(Show i, Show a) => Show (Set i a) Source # 

Methods

showsPrec :: Int -> Set i a -> ShowS #

show :: Set i a -> String #

showList :: [Set i a] -> ShowS #

Generic (Set i a) Source # 

Associated Types

type Rep (Set i a) :: * -> * #

Methods

from :: Set i a -> Rep (Set i a) x #

to :: Rep (Set i a) x -> Set i a #

(Binary i, Binary a) => Binary (Set i a) Source # 

Methods

put :: Set i a -> Put #

get :: Get (Set i a) #

putList :: [Set i a] -> Put #

type Alg (Set i) Source # 
type Alg (Set i) = i
type Rep (Set i a) Source # 

createSetFile :: (Binary i, Typeable i) => FilePath -> IO (FixFile (Ref (Set i))) Source #

Create a FixFile (Set i).

openSetFile :: (Binary i, Typeable i) => FilePath -> IO (FixFile (Ref (Set i))) Source #

Open a FixFile (Set i).

empty :: Fixed g => g (Set i) Source #

An empty Set.

insertSet :: (Ord i, Fixed g) => i -> g (Set i) -> g (Set i) Source #

Insert an item i into a Fixed recursive Set i.

insertSetT :: (Ord i, Binary i) => i -> Transaction (Ref (Set i)) s () Source #

deleteSet :: (Ord i, Fixed g) => i -> g (Set i) -> g (Set i) Source #

Delete an item i into a Fixed recursive Set i.

deleteSetT :: (Ord i, Binary i) => i -> Transaction (Ref (Set i)) s () Source #

lookupSet :: (Ord i, Fixed g) => i -> g (Set i) -> Bool Source #

Predicate to lookup an item from a Set i.

lookupSetT :: (Ord i, Binary i) => i -> Transaction (Ref (Set i)) s Bool Source #

FTransaction version of lookupSet.

toListSet :: Fixed g => g (Set i) -> [i] Source #

Turn a Fixed recurive structure of Set i into a list.