Copyright | (c) Zoltan Kelemen 2017 |
---|---|
License | BSD-style |
Maintainer | kelemzol@elte.hu |
Safe Haskell | Safe |
Language | Haskell2010 |
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
- data HtsSet
- empty :: HtsSet
- singleton :: forall a. Typeable a => a -> HtsSet
- null :: HtsSet -> Bool
- size :: HtsSet -> Int
- member :: forall proxy a. Typeable a => proxy a -> HtsSet -> Bool
- notMember :: forall proxy a. Typeable a => proxy a -> HtsSet -> Bool
- insert :: forall a. Typeable a => a -> HtsSet -> HtsSet
- lookup :: forall a. Typeable a => HtsSet -> Maybe a
- lookupWithDefault :: forall a. Typeable a => a -> HtsSet -> a
- update :: forall a. Typeable a => (a -> a) -> HtsSet -> HtsSet
- existTypeOf :: forall a. Typeable a => a -> HtsSet -> Bool
- existTypeOfP :: forall proxy a. Typeable a => proxy a -> HtsSet -> Bool
- data a :+ b = a :+ b
- class Append a where
- fill :: Append a => a -> HtsSet
Documentation
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)
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
a :+ b infixr 5 |