bitwise-enum: Bitwise operations on bounded enumerations

[ bsd3, data, data-structures, foreign, library ] [ Propose Tags ]

Bitwise operations on bounded enumerations.

Data.Enum.Set
Constant-time sets using bit flags.
Data.Enum.Memo
Constant-time lookup memoization for functions on enumerated types.

[Skip to Readme]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

Versions [RSS] 0.1.0.0, 0.1.0.1, 0.1.0.2, 0.1.0.3, 1.0.0, 1.0.0.1, 1.0.0.2, 1.0.0.3, 1.0.1.0, 1.0.1.1, 1.0.1.2 (info)
Change log CHANGES.md
Dependencies aeson (>=0.11 && <2.3), array (>=0.5.1 && <0.6), base (>=4.5 && <5), deepseq (>=1.1 && <1.6), mono-traversable (>=1.0.12 && <1.1), vector (>=0.11 && <0.14) [details]
License BSD-3-Clause
Author Joshua Booth <joshua.n.booth@gmail.com>
Maintainer Joshua Booth <joshua.n.booth@gmail.com>
Category Data, Data Structures, Foreign
Home page https://github.com/jnbooth/bitwise-enum
Bug tracker https://github.com/jnbooth/bitwise-enum/issues
Source repo head: git clone https://github.com/jnbooth/bitwise-enum
Uploaded by jnbooth at 2023-07-30T20:49:39Z
Distributions LTSHaskell:1.0.1.2, NixOS:1.0.1.2, Stackage:1.0.1.2
Reverse Dependencies 1 direct, 0 indirect [details]
Downloads 2452 total (35 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2023-07-30 [all 1 reports]

Readme for bitwise-enum-1.0.1.1

[back to package description]

bitwise-enum

Efficient sets over bounded enumerations, using bitwise operations based on containers and EdisonCore. All operations apart from folds are constant-time. In many cases, the compiler may use constant folding to optimize EnumSets away entirely. For example, in the following code:

import Data.Enum.Set as E

data Foo = A | B | C | D | E | F | G | H deriving (Bounded, Enum, Eq, Ord)

instance E.AsEnumSet Foo

addFoos :: E.EnumSet Foo -> E.EnumSet Foo
addFoos = E.delete A . E.insert B

bar :: E.EnumSet Foo
bar = addFoos $ E.fromFoldable [A, C, E]

barHasA :: Bool
barHasA = E.member A bar

With -O or -O2 , bar will compile to GHC.Types.W# 22## and barHasA will compile to GHC.Types.False.

By default, Words are used as the representation. Other representations may be chosen in the class instance:

{-# LANGUAGE TypeFamilies #-}

import Data.Enum.Set as E
import Data.Word (Word64)

data Foo = A | B | C | D | E | F | G | H deriving (Bounded, Enum, Eq, Ord, Show)

instance E.AsEnumSet Foo where
    type EnumSetRep Foo = Word64