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