[Haskell-cafe] ANN: unordered-containers - a new, faster hashing-based containers library

Max Bolingbroke batterseapower at hotmail.com
Wed Feb 23 22:55:36 CET 2011


On 23 February 2011 21:27, Gwern Branwen <gwern0 at gmail.com> wrote:
> On Wed, Feb 23, 2011 at 1:18 PM, Johan Tibell <johan.tibell at gmail.com> wrote:
>>
>> Could you manually look at some of them to see if you find something
>> interesting. In particular `Set.size s == 0` (a common use of size in
>> imperative languages) could be replaced by `Set.null s`.
>
> You could look at them yourself; I attached the files. I see 6 uses
> out of ~100 which involve an == 0

Thanks for bringing some data to the table. There are definitely some
common patterns in what you sent me:

1) For defining Binary instances, you need to write set size before
you write the elements: ~7 occurrences
2) Tests against small constants (typically <= 0 or 1, but also 2 and
3!): ~15 occurrences
3) A surprise to me: generating fresh names! People keep a set of all
names generated so far, and then just take size+1 as their fresh name.
Nice trick. ~17 occurrences
4) Turning sizes into strings for human consumption: ~19 occurrences
5) Just reexporting the functions somehow. Uninformative. ~8 occurrences

There were ~38 occurrences over ~13 repos where it appeared to be
somehow fundamental to an algorithm (I didn't look into most of these
in detail). I've put those after my message.

Frankly I am surprised how much "size" gets used. It seems that making
it fast is more important than I thought.

Cheers,
Max

===

Fundamental-looking occurrences:

bin/folkung/folkung/Clausify.hs:  siz (And ps)            = S.size ps
bin/folkung/folkung/Paradox/Flatten.hs:    | S.size cl >= 1 + S.size bs
bin/folkung/folkung/Paradox/Flatten.hs:       || S.size cl >= S.size
cl' = largestClique cl gr'
bin/folkung/folkung/Paradox/Flatten.hs:                          -- &&
S.size (free xs) <= 1
bin/folkung/folkung/Paradox/Flatten.hs:    n   = S.size (free ls)
bin/folkung/folkung/Paradox/Flatten.hs:      , S.size ws < n-1
bin/folkung/folkung/Paradox/Flatten.hs:        (S.size s1,tpsize
v2,inter s2) `compare` (S.size s2,tpsize v1,inter s1)
bin/folkung/folkung/Paradox/Flatten.hs:        sum [ S.size (s
`S.intersection` vs) | (v,vs) <- cons, v `S.member` s  ]
bin/folkung/folkung/Paradox/Flatten.hs:        , S.size ws' < S.size freeRight-1
bin/folkung/folkung/Paradox/Solve.hs:  degree x = S.size . free $ x
bin/gf/src/compiler/GF/Compile/GeneratePMCFG.hs:          | product
(map Set.size ys) == count
bin/gf/src/compiler/GF/Speech/CFGToFA.hs:            indeg (c,_) =
maybe 0 Set.size $ Map.lookup c ub
bin/gf/src/compiler/GF/Speech/CFGToFA.hs:  where (fa', ns) = newStates
(replicate (Set.size cs) ()) fa
bin/gf/src/GF/Compile/GeneratePMCFG.hs:          | product (map
Set.size ys) == count =
bin/gf/src/GF/Compile/GeneratePMCFGOld.hs:          | product (map
Set.size ys) == count =
bin/gf/src/GF/Data/MultiMap.hs:size = sum . Prelude.map Set.size . Map.elems
bin/gf/src/GF/Speech/CFGToFA.hs:            indeg (c,_) = maybe 0
Set.size $ Map.lookup c ub
bin/gf/src/GF/Speech/CFGToFA.hs:  where (fa', ns) = newStates
(replicate (Set.size cs) ()) fa
bin/halfs/Halfs/FSRoot.hs:                                     $
Set.size $ fsRootAllInodeNums fsroot
bin/halfs/Halfs.hs:    when (Set.size freeSet /= length freeList) (
bin/hcorpus/hcorpus.hs:           let rank = 1 `fidiv` Set.size wrds,
bin/hoogle/src/Hoogle/DataBase/TypeSearch/Binding.hs:                g
(l, vs) = Just $ [restrict|isJust l] ++ replicate (max 0 $ Set.size vs
- 1) var
bin/htab/src/Formula.hs:countNominals f = Set.size $ extractNominals f
bin/hylores-2.5/src/HyLoRes/Clause/BasicClause.hs:    size          =
Set.size . toFormulaSet
bin/hylores-2.5/src/HyLoRes/Subsumption/ClausesByFormulaIndex.hs:
                            let sortedCandidates = sortBy
(compareUsing Set.size) subsCandidates
bin/hylores-diego/src/HyLoRes/Clause/BasicClause.hs:    size
= Set.size . toFormulaSet
bin/hylores-diego/src/HyLoRes/Subsumption/ClausesByFormulaIndex.hs:
                              let sortedCandidates = sortBy
(compareUsing Set.size) subsCandidates
bin/ipclib/Language/Pepa/Compile/States.hs:        Just limit ->
((stateSpaceSize seen) + (Set.size stack)) > limit
bin/jhc/src/Grin/SSimplify.hs:        v n | n `IS.member` s = v (1 + n
+ IS.size s)
bin/jhc/src/Ho/Build.hs:    maxModules <- Set.size `fmap` countNodes cn
bin/jhc/src/Ho/Build.hs:    maxModules <- Set.size `fmap` countNodes cn
bin/lhc/src/Grin/Optimize/CallPattern.hs:          nPatterns =
Set.size callPatterns
bin/proteinvis/Graphics/Visualization/Tree/Geometry.hs:    where theta
= ((fromIntegral index - (fromIntegral (S.size . fst . S.split (Name
name) $ missingLeaves))) * 2 * 3.14157) / (num_leaves - fromIntegral
(S.size missingLeaves))
bin/proteinvis/ProgramState.hs:          c = S.size go
bin/proteinvis/Protein.hs:         , term_count = S.size terms
bin/proteinvis/Protein.hs:
  , term_count = S.size terms
bin/protocol-buffers/hprotoc/Text/ProtocolBuffers/ProtoCompile/Resolve.hs:
 when (Set.size numbers /= Seq.length (D.DescriptorProto.field dp)) $
bin/protocol-buffers/hprotoc/Text/ProtocolBuffers/ProtoCompile/Resolve.hs:
 when (Set.size (Set.fromList values) /= Seq.length vs) $
bin/xmobar/Plugins/Mail.hs:        changeLoop (mapM (fmap S.size .
readTVar) vs) $ \ns -> do



More information about the Haskell-Cafe mailing list