htssets-0.1.0.0: Heterogenous Sets

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

Data.HtsSet

Description

HtsSet is a Heterogenous Set wich can provide storing values with different type.

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

 import qualified Data.HtsSet as HSet
  • ---------------------------------------------------------------------------
Synopsis

Documentation

empty :: HtsSet Source #

The empty HtsSet

singleton :: forall a. Typeable a => a -> HtsSet Source #

A HtsSet with an element

null :: HtsSet -> Bool Source #

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

size :: HtsSet -> Int Source #

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

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

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

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

The HtsSet is not contain a same type of element?

insert :: forall a. Typeable a => a -> HtsSet -> HtsSet Source #

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

lookup :: forall a. Typeable a => HtsSet -> Maybe a Source #

Lookup a value from in the HtsSet > 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 a. Typeable a => a -> HtsSet -> a Source #

Lookup a value from in the HtsSet with a default value

update :: forall a. Typeable a => (a -> a) -> HtsSet -> HtsSet Source #

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

existTypeOf :: forall a. Typeable a => a -> HtsSet -> Bool Source #

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

existTypeOfP :: forall proxy a. Typeable a => proxy a -> HtsSet -> Bool Source #

The HtsSet 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 == Just c > use () to close the list > lookup hs == Just () -- is False! > let hs' = fill ("a" :+ c :+ True :+ () :+ ()) > lookup hs' == Just () -- is Ok

Constructors

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

Defined in Data.HtsSet

Methods

append :: (a :+ b) -> HtsSet -> HtsSet Source #

class Append a where Source #

Methods

append :: a -> HtsSet -> HtsSet Source #

Instances
Append () Source # 
Instance details

Defined in Data.HtsSet

Methods

append :: () -> HtsSet -> HtsSet Source #

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

Defined in Data.HtsSet

Methods

append :: (a :+ b) -> HtsSet -> HtsSet Source #

fill :: Append a => a -> HtsSet Source #