Copyright | (c) Edward Kmett 2010-2011 |
---|---|
License | BSD3 |
Maintainer | ekmett@gmail.com |
Stability | experimental |
Portability | portable |
Safe Haskell | Trustworthy |
Language | Haskell98 |
Fast set membership tests for Char
values
Stored as a (possibly negated) IntMap and a fast set used for the head byte.
The set of valid (possibly negated) head bytes is stored unboxed as a 32-byte bytestring-based lookup table.
Designed to be imported qualified:
import Data.CharSet (CharSet) import qualified Data.CharSet as CharSet
Synopsis
- data CharSet = CharSet !Bool !ByteSet !IntSet
- (\\) :: CharSet -> CharSet -> CharSet
- null :: CharSet -> Bool
- size :: CharSet -> Int
- member :: Char -> CharSet -> Bool
- notMember :: Char -> CharSet -> Bool
- overlaps :: CharSet -> CharSet -> Bool
- isSubsetOf :: CharSet -> CharSet -> Bool
- isComplemented :: CharSet -> Bool
- build :: (Char -> Bool) -> CharSet
- empty :: CharSet
- singleton :: Char -> CharSet
- full :: CharSet
- insert :: Char -> CharSet -> CharSet
- delete :: Char -> CharSet -> CharSet
- complement :: CharSet -> CharSet
- range :: Char -> Char -> CharSet
- union :: CharSet -> CharSet -> CharSet
- intersection :: CharSet -> CharSet -> CharSet
- difference :: CharSet -> CharSet -> CharSet
- filter :: (Char -> Bool) -> CharSet -> CharSet
- partition :: (Char -> Bool) -> CharSet -> (CharSet, CharSet)
- map :: (Char -> Char) -> CharSet -> CharSet
- fold :: (Char -> b -> b) -> b -> CharSet -> b
- toList :: CharSet -> String
- fromList :: String -> CharSet
- toAscList :: CharSet -> String
- fromAscList :: String -> CharSet
- fromDistinctAscList :: String -> CharSet
- fromCharSet :: CharSet -> (Bool, IntSet)
- toCharSet :: IntSet -> CharSet
- toArray :: CharSet -> UArray Char Bool
Set type
Instances
Bounded CharSet Source # | |
Eq CharSet Source # | |
Data CharSet Source # | |
Defined in Data.CharSet gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CharSet -> c CharSet # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CharSet # toConstr :: CharSet -> Constr # dataTypeOf :: CharSet -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CharSet) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CharSet) # gmapT :: (forall b. Data b => b -> b) -> CharSet -> CharSet # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CharSet -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CharSet -> r # gmapQ :: (forall d. Data d => d -> u) -> CharSet -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CharSet -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CharSet -> m CharSet # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CharSet -> m CharSet # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CharSet -> m CharSet # | |
Ord CharSet Source # | |
Read CharSet Source # | |
Show CharSet Source # | |
Semigroup CharSet Source # | |
Monoid CharSet Source # | |
Operators
Query
isComplemented :: CharSet -> Bool Source #
Construction
complement :: CharSet -> CharSet Source #
Combine
Filter
Map
Fold
Conversion
List
Ordered list
fromAscList :: String -> CharSet Source #
fromDistinctAscList :: String -> CharSet Source #