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, Eq a, c a) => a -> HtsCSet c -> Bool
- notMember :: forall proxy c a. (Typeable a, Eq a, c a) => a -> HtsCSet c -> Bool
- 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
- existTypeOfP' :: forall c a. (Typeable a, c a) => Proxy a -> HtsCSet c -> Bool
- appl :: forall a b c. (Typeable a, c a) => b -> (a -> b) -> HtsCSet c -> b
- compliance :: forall a c. (Typeable a, c a) => Bool -> (a -> Bool) -> 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
- deleteByType :: forall a c. (Typeable a, c a) => a -> HtsCSet c -> HtsCSet c
- deleteByTypeP :: forall proxy c a. (Typeable a, c a) => proxy a -> HtsCSet c -> HtsCSet c
- deleteByTypeP' :: forall a c. (Typeable a, c a) => Proxy a -> HtsCSet c -> HtsCSet c
- deleteWhen :: forall a c. (Typeable a, c a) => (a -> Bool) -> HtsCSet c -> HtsCSet c
- data a :+ b = a :+ b
- class Append c a where
- fill :: Append c a => a -> HtsCSet c
- data Proxy (t :: k) :: forall k. k -> Type = Proxy
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, Eq a, c a) => a -> HtsCSet c -> Bool Source #
The HtsSet is contain an element?
member (Proxy :: Proxy String) empty == False member (Proxy :: Proxy String) (singleton "a") == True
notMember :: forall proxy c a. (Typeable a, Eq a, c a) => a -> HtsCSet c -> Bool Source #
The HtsSet is not contain an element?
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)
existTypeOfP' :: forall c a. (Typeable a, c a) => Proxy a -> HtsCSet c -> Bool Source #
The HtsCSet is contain a same type of element? (by fixed proxy)
appl :: forall a b c. (Typeable a, c a) => b -> (a -> b) -> HtsCSet c -> b Source #
Apply a function to an element with a default value
appl "no ABC" (:"BC") $ singleton 'A' == "ABC" appl "no ABC" (:"BC") $ singleton "s" == "no ABC"
compliance :: forall a c. (Typeable a, c a) => Bool -> (a -> Bool) -> HtsCSet c -> Bool Source #
appl specialization
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"
deleteByType :: forall a c. (Typeable a, c a) => a -> HtsCSet c -> HtsCSet c Source #
Delete an element by type
(member 'c' $ deleteByType 'b' $ singleton 'c') == False
deleteByTypeP :: forall proxy c a. (Typeable a, c a) => proxy a -> HtsCSet c -> HtsCSet c Source #
Delete an element by type (by proxy)
(member 'c' $ deleteByTypeP (Proxy :: Proxy Char) $ singleton 'c') == False
deleteByTypeP' :: forall a c. (Typeable a, c a) => Proxy a -> HtsCSet c -> HtsCSet c Source #
Delete an element by type (by fixed proxy)
deleteWhen :: forall a c. (Typeable a, c a) => (a -> Bool) -> HtsCSet c -> HtsCSet c Source #
Delete an element by condition
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 |
data Proxy (t :: k) :: forall k. k -> Type #
Proxy
is a type that holds no data, but has a phantom parameter of
arbitrary type (or even kind). Its use is to provide type information, even
though there is no value available of that type (or it may be too costly to
create one).
Historically,
is a safer alternative to the
Proxy
:: Proxy
a'undefined :: a'
idiom.
>>>
Proxy :: Proxy (Void, Int -> Int)
Proxy
Proxy can even hold types of higher kinds,
>>>
Proxy :: Proxy Either
Proxy
>>>
Proxy :: Proxy Functor
Proxy
>>>
Proxy :: Proxy complicatedStructure
Proxy
Instances
Monad (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Functor (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Applicative (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Foldable (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Defined in Data.Foldable fold :: Monoid m => Proxy m -> m # foldMap :: Monoid m => (a -> m) -> Proxy a -> m # foldr :: (a -> b -> b) -> b -> Proxy a -> b # foldr' :: (a -> b -> b) -> b -> Proxy a -> b # foldl :: (b -> a -> b) -> b -> Proxy a -> b # foldl' :: (b -> a -> b) -> b -> Proxy a -> b # foldr1 :: (a -> a -> a) -> Proxy a -> a # foldl1 :: (a -> a -> a) -> Proxy a -> a # elem :: Eq a => a -> Proxy a -> Bool # maximum :: Ord a => Proxy a -> a # minimum :: Ord a => Proxy a -> a # | |
Traversable (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Alternative (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
MonadPlus (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Bounded (Proxy t) | Since: base-4.7.0.0 |
Enum (Proxy s) | Since: base-4.7.0.0 |
Eq (Proxy s) | Since: base-4.7.0.0 |
Ord (Proxy s) | Since: base-4.7.0.0 |
Read (Proxy t) | Since: base-4.7.0.0 |
Show (Proxy s) | Since: base-4.7.0.0 |
Ix (Proxy s) | Since: base-4.7.0.0 |
Semigroup (Proxy s) | Since: base-4.9.0.0 |
Monoid (Proxy s) | Since: base-4.7.0.0 |