htssets-0.1.0.0: Heterogenous Sets

Copyright(c) Zoltan Kelemen 2017
LicenseBSD-style
Maintainerkelemzol@elte.hu
Safe HaskellNone
LanguageHaskell2010

Data.HtsCSet

Description

HtsCSet is a Heterogenous Set wich can provide storing values with different and constrained type.

These modules are intended to be imported qualified, to avoid name clashes with Prelude functions, e.g.

 import qualified Data.HtsCSet as HCSet
  • ---------------------------------------------------------------------------
Synopsis

Documentation

empty :: HtsCSet c Source #

The empty HtsCSet

emptyP :: proxy c -> HtsCSet c Source #

The empty HtsCSet with proxy

singleton :: forall c a. (Typeable a, c a) => a -> HtsCSet c Source #

A HtsCSet with an element

singletonP :: forall proxy c a. (Typeable a, c a) => proxy c -> a -> HtsCSet c Source #

A HtsCSet with an element with proxy

null :: HtsCSet c -> Bool Source #

Is the HtsCSet is empty? > null empty == True > null (singleton "a") == False

size :: HtsCSet c -> Int Source #

The number of elements in the HtsSet > size empty == 0 > size (singleton "a") == 1

member :: forall proxy c a. Typeable a => proxy a -> HtsCSet c -> Bool Source #

The HtsCSet is contain a same type of element? > member (Proxy :: Proxy String) empty == False > member (Proxy :: Proxy String) (singleton "a") == True

notMember :: forall proxy c a. Typeable a => proxy a -> HtsCSet c -> Bool Source #

The HtsCSet is not contain a same type of element?

insert :: forall c a. (Typeable a, c a) => a -> HtsCSet c -> HtsCSet c Source #

Insert a new value in the HtsCSet. If the a elem is already present in the HtsCSet with type, the associated value is replaced with the supplied value > insert "a" $ insert (2 :: Int) $ insert c $ empty

lookup :: forall c a. (Typeable a, c a) => HtsCSet c -> Maybe a Source #

Lookup a value from in the HtsCSet > let hs = insert "a" $ insert (2 :: Int) $ insert c $ empty > lookup hs == Just "a" > lookup hs == Just (2 :: Int) > but > lookup hs == Just 2 -- is False! Because the type of 2 is Num t => t not Int

lookupWithDefault :: forall c a. (Typeable a, c a) => a -> HtsCSet c -> a Source #

Lookup a value from in the HtsCSet with a default value

update :: forall c a. (Typeable a, c a) => (a -> a) -> HtsCSet c -> HtsCSet c Source #

Update a value in HtsCSet > let hs = insert "a" $ insert (2 :: Int) $ insert c $ empty > let hs' = update (++"b") hs > lookup hs' == Just "ab"

existTypeOf :: forall c a. (Typeable a, c a) => a -> HtsCSet c -> Bool Source #

The HtsCSet is contain a same type of element? > let hs = insert "a" $ insert (2 :: Int) $ insert c $ empty > existTypeOf "string" hs == True

existTypeOfP :: forall proxy c a. (Typeable a, c a) => proxy a -> HtsCSet c -> Bool Source #

The HtsCSet is contain a same type of element? (by proxy)

data a :+ b infixr 5 Source #

Helper heterogeneous list for comfortable HtsSet building (with append and fill) > let hs = fill ("a" :+ c :+ True :+ ()) > lookup (hs :: HtsCSet Show) == Just c > use () to close the list > lookup (hs :: HtsCSet Show) == Just () -- is False! > let hs' = fill ("a" :+ c :+ True :+ () :+ ()) > lookup (hs' :: HtsCSet Show) == Just () -- is Ok

Constructors

a :+ b infixr 5 
Instances
(Typeable a, c a, Append c b) => Append c (a :+ b) Source # 
Instance details

Defined in Data.HtsCSet

Methods

append :: (a :+ b) -> HtsCSet c -> HtsCSet c Source #

class Append c a where Source #

Methods

append :: a -> HtsCSet c -> HtsCSet c Source #

Instances
Append c () Source # 
Instance details

Defined in Data.HtsCSet

Methods

append :: () -> HtsCSet c -> HtsCSet c Source #

(Typeable a, c a, Append c b) => Append c (a :+ b) Source # 
Instance details

Defined in Data.HtsCSet

Methods

append :: (a :+ b) -> HtsCSet c -> HtsCSet c Source #

fill :: Append c a => a -> HtsCSet c Source #