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

Johan Tibell johan.tibell at gmail.com
Wed Feb 23 23:40:15 CET 2011


Attached are all the uses of S.size and Set.size from a semi-recent
snapshot of Hackage.

Johan
-------------- next part --------------
Combinatorrent/0.3.2/Combinatorrent-0.3.2/src/Process/Peer.hs:    let sz = S.size q
Combinatorrent/0.3.2/Combinatorrent-0.3.2/src/Process/PieceMgr.hs:        ipHave = S.size . ipHaveBlocks
Combinatorrent/0.3.2/Combinatorrent-0.3.2/src/Process/PieceMgr.hs:        when ( (S.size $ ipHaveBlocks ipp) >= ipDone ipp)
cpsa/2.2.1/cpsa-2.2.1/src/CPSA/Graph/Tree.hs:          if S.size new == S.size old then
darcswatch/0.4.3/darcswatch-0.4.3/src/HTML.hs:	show (S.size (r2p d !!!! r)) +++ 
EdisonCore/1.2.1.3/EdisonCore-1.2.1.3/src/Data/Edison/Coll/UnbalancedSet.hs:unsafeFromOrdSeq xs = fst (ins xs (S.size xs))
EdisonCore/1.2.1.3/EdisonCore-1.2.1.3/src/Data/Edison/Seq/RevSeq.hs:fromSeq xs = N (S.size xs - 1) xs
EdisonCore/1.2.1.3/EdisonCore-1.2.1.3/src/Data/Edison/Seq/RevSeq.hs:        k = S.size ys
EdisonCore/1.2.1.3/EdisonCore-1.2.1.3/src/Data/Edison/Seq/RevSeq.hs:        k = S.size ys
EdisonCore/1.2.1.3/EdisonCore-1.2.1.3/src/Data/Edison/Seq/RevSeq.hs:structuralInvariant (N i s) = i == ((S.size s) - 1)
EdisonCore/1.2.1.3/EdisonCore-1.2.1.3/src/Data/Edison/Seq/SizedSeq.hs:fromSeq xs = N (S.size xs) xs
EdisonCore/1.2.1.3/EdisonCore-1.2.1.3/src/Data/Edison/Seq/SizedSeq.hs:        m = S.size ys
EdisonCore/1.2.1.3/EdisonCore-1.2.1.3/src/Data/Edison/Seq/SizedSeq.hs:        m = S.size ys
EdisonCore/1.2.1.3/EdisonCore-1.2.1.3/src/Data/Edison/Seq/SizedSeq.hs:structuralInvariant (N i s) = i == S.size s
fountain/0.0.1/fountain-0.0.1/Codec/Fountain.hs:    | S.size s == degree = (s, g)
fountain/0.0.1/fountain-0.0.1/Codec/Fountain.hs:  | S.size indices == 0 = decode' decoder newDroplets
fountain/0.0.1/fountain-0.0.1/Codec/Fountain.hs:  | S.size indices == 1 = decode' (Decoder messageLength extraSymbols (M.insert (head $ S.toList indices) symbol symbols) old) (new ++ newDroplets)
hashmap/1.1.0/hashmap-1.1.0/Data/HashSet.hs:        some_size (More t) = S.size t
hashmap/1.1.0/hashmap-1.1.0/Data/HashSet.hs:some_norm s = case S.size s of 0 -> Nothing
hashmap/1.1.0/hashmap-1.1.0/Data/HashSet.hs:some_norm' s = case S.size s of 1 -> Only $ S.findMin s
HaskellForMaths/0.3.1/HaskellForMaths-0.3.1/Math/Algebra/Group/PermutationGroup.hs:order gs = S.size $ eltsS gs -- length $ elts gs
HaskellForMaths/0.3.1/HaskellForMaths-0.3.1/Math/Combinatorics/LatinSquares.hs:isOneOfEach xs = length xs == S.size (S.fromList xs)
HaskellTorrent/0.1.1/HaskellTorrent-0.1.1/src/Process/Peer.hs:            let sz = S.size q
HaskellTorrent/0.1.1/HaskellTorrent-0.1.1/src/Process/PieceMgr.hs:        ipHave = S.size . ipHaveBlocks
HaskellTorrent/0.1.1/HaskellTorrent-0.1.1/src/Process/PieceMgr.hs:        when ( (S.size $ ipHaveBlocks ipp) >= ipDone ipp)
hburg/1.1.2/hburg-1.1.2/src/Csa/Csa.hs:                          "' - expected type"++ (if (S.size p > 1) then "s" else "") ++
hgom/0.6/hgom-0.6/Gom/Checker.hs:        f s = S.size s > 1
Holumbus-MapReduce/0.1.1/Holumbus-MapReduce-0.1.1/Examples/MapReduce/Crawler/Crawl.hs:       runX (traceMsg 1 ("          Status: already processed: " ++ show (S.size $ cs_wereProcessed cs) ++ 
Holumbus-MapReduce/0.1.1/Holumbus-MapReduce-0.1.1/Examples/MapReduce/Crawler/Crawl.hs:                         ", to be processed: "   ++ show (S.size $ cs_toBeProcessed cs)))
hoopl/3.8.6.0/hoopl-3.8.6.0/Compiler/Hoopl/Unique.hs:  setSize (US s) = S.size s
hs2bf/0.6.2/hs2bf-0.6.2/SAM.hs:    when (S.size rs/=length args) $ report "duplicate arguments"
ideas/0.7/ideas-0.7/src/Domain/Math/Polynomial/RationalExercises.hs:      S.size (varSet expr) > 1
ideas/0.7/ideas-0.7/src/Domain/Math/Polynomial/RationalExercises.hs:       manyVars = S.size (varSet a `S.union` varSet b) > 1
mahoro/0.1.2/mahoro-0.1.2/DB.hs:    delJID (n, jids) = if S.size jids == 1
minesweeper/0.9/minesweeper-0.9/Data/ChangeSet.hs:size        = S.size . toSet
minesweeper/0.9/minesweeper-0.9/State/Functions.hs:    = mines (configuration st) - S.size (marked $ game st)
minesweeper/0.9/minesweeper-0.9/Table.hs:    =  S.size (marked g) + M.size (revealResults g) == msize c
minesweeper/0.9/minesweeper-0.9/Table.hs:    = mines c - S.size (marked g)
panda/2009.4.1/panda-2009.4.1/src/Panda/Model/Tag.hs:sorted xs    = xs.sortBy(compare_by (resources > S.size)).reverse
phybin/0.1.2/phybin-0.1.2/Bio/Phylogeny/PhyBin/Main.hs:    putStrLn$ "\nTotal unique taxa ("++ show (S.size taxa) ++"):  "++ 
regex-tdfa/1.1.7/regex-tdfa-1.1.7/Data/IntSet/EnumSet2.hs:size (EnumSet s) = S.size s
relacion/0.1/relacion-0.1/Data/Relacion.hs:size r  =   M.fold ((+) . S.size) 0 (dominio r)
repa/1.1.0.0/repa-1.1.0.0/Data/Array/Repa.hs:			$! U.enumFromTo (0 :: Int) (S.size sh - 1)
repa/1.1.0.0/repa-1.1.0.0/Data/Array/Repa.hs:	| U.length uarr /= S.size sh
repa/1.1.0.0/repa-1.1.0.0/Data/Array/Repa.hs:		, "        size of shape = " ++ (show $ S.size sh) 	++ "\n"
repa/1.1.0.0/repa-1.1.0.0/Data/Array/Repa.hs:		$ (flip reshape) (Z :. (S.size $ extent arr1)) 
repa/1.1.0.0/repa-1.1.0.0/Data/Array/Repa.hs:	| not $ S.size newExtent == S.size (extent arr)
repa/1.1.0.0/repa-1.1.0.0/Data/Array/Repa.hs:		((S.size $ extent arr) - 1)
repa/1.1.0.0/repa-1.1.0.0/Data/Array/Repa.hs:		((S.size $ extent arr) - 1)
repa/1.1.0.0/repa-1.1.0.0/Data/Array/Repa.hs:	xx	<- arbitraryListOfLength (S.size sh)
repa/1.1.0.0/repa-1.1.0.0/Data/Array/Repa.hs:	forAll (arbitraryListOfLength (S.size sh))	$ \(xx :: [Int]) ->
repa/1.1.0.0/repa-1.1.0.0/Data/Array/Repa.hs:   in	(S.size $ extent arr) == S.size (extent (reshape arr sh'))
repa/1.1.0.0/repa-1.1.0.0/Data/Array/Repa.hs:	forAll (arbitraryListOfLength (S.size sh))	$ \(xx :: [Int]) -> 
SizeCompare/0.1/SizeCompare-0.1/src/Data/SizeCompare.hs:    cSize = Just . S.size
syb-with-class/0.6.1.1/syb-with-class-0.6.1.1/Data/Generics/SYB/WithClass/Instances.hs:  toConstr _ m | S.size m == 0 = emptySetConstr
urlcheck/0.1.1/urlcheck-0.1.1/Check.hs:               (S.size (cache stats))
xmobar/0.12/xmobar-0.12/src/Plugins/Mail.hs:        changeLoop (mapM (fmap S.size . readTVar) vs) $ \ns ->
Agda/2.2.8/Agda-2.2.8/src/full/Agda/Utils/Graph.hs:  where n = Set.size $ nodes g
Agda/2.2.8/Agda-2.2.8/src/full/Agda/Utils/Size.hs:  size = fromIntegral . Set.size
bamboo/2010.2.25/bamboo-2010.2.25/src/Bamboo/Model/Tag.hs:    .sortBy(compare_by (\x -> (x.resources.Set.size, x.name)))
bamboo-theme-blueprint/2010.2.25.1/bamboo-theme-blueprint-2010.2.25.1/src/Bamboo/Theme/Blueprint/Widget/Sidebar.hs:      +++ ( " (" ++ x.Tag.resources.Set.size.show ++ ")" )
bamboo-theme-mini-html5/2009.11.27/bamboo-theme-mini-html5-2009.11.27/src/Bamboo/Theme/MiniHTML5/Widget/Sidebar.hs:      str - " (" ++ x.Tag.resources.Set.size.show ++ ")"
binary/0.5.0.2/binary-0.5.0.2/src/Data/Binary.hs:    put s = put (Set.size s) >> mapM_ put (Set.toAscList s)
cassandra-thrift/0.6.6/cassandra-thrift-0.6.6/Database/Cassandra/Thrift/Cassandra.hs:    (let {f [] = return (); f (_viter362:t) = do {writeString oprot _viter362;f t}} in do {writeSetBegin oprot (T_STRING,Set.size _v); f (Set.toList _v);writeSetEnd oprot})
chp/2.2.0/chp-2.2.0/Control/Concurrent/CHP/Base.hs:               in actWhenLast act (Map.fromList $ map (snd *** Set.size) es)
chp/2.2.0/chp-2.2.0/Control/Concurrent/CHP/Traces.hs:        indivEventsWithAllParticipants = Map.map fst $ Map.filter (\(s, n) -> Set.size s == n) (Map.intersectionWith (,) m ps)
collections/0.3.1/collections-0.3.1/Data/Collections.hs:    size = Set.size
collections-base-instances/1.0.0.0/collections-base-instances-1.0.0.0/Data/Collections/BaseInstances.hs:    size = Set.size
CSPM-Interpreter/0.4.0.2/CSPM-Interpreter-0.4.0.2/src/CSPM/Interpreter/Eval.hs:      return $ VInt $ fromIntegral $ Set.size s
free-theorems/0.3.1.3/free-theorems-0.3.1.3/src/FrontendTypeExpressionsTests.hs:  countTypeAbs t + Set.size set == countTypeAbs (closureFor set t)
free-theorems/0.3.1.3/free-theorems-0.3.1.3/src/Language/Haskell/FreeTheorems/Frontend/CheckGlobal.hs:         in if Set.size ds == Set.size ds'
funsat/0.6.1/funsat-0.6.1/src/Funsat/Circuit.hs:                          , numClauses = Set.size cnf
gbu/0.1/gbu-0.1/Data/Graph/Embedding.hs:            in Set.size outN == 2 &&
gbu/0.1/gbu-0.1/Data/Graph/Embedding.hs:       in if Set.size neiNodesInP  == 1
gf/3.2/gf-3.2/src/compiler/GF/Compile/GeneratePMCFG.hs:          | product (map Set.size ys) == count
gf/3.2/gf-3.2/src/compiler/GF/Speech/CFGToFA.hs:            indeg (c,_) = maybe 0 Set.size $ Map.lookup c ub
gf/3.2/gf-3.2/src/compiler/GF/Speech/CFGToFA.hs:  where (fa', ns) = newStates (replicate (Set.size cs) ()) fa
gf/3.2/gf-3.2/src/compiler/GF/Speech/SRG.hs:          ++ ", External categories: " ++ show (Set.size (cfgExternalCats g))
gf/3.2/gf-3.2/src/runtime/haskell/Data/Binary.hs:    put s = put (Set.size s) >> mapM_ put (Set.toAscList s)
halfs/0.2/halfs-0.2/Halfs/FSRoot.hs:                                     $ Set.size $ fsRootAllInodeNums fsroot
halfs/0.2/halfs-0.2/Halfs/TheBlockMap.hs:    = assert (queueLength free == Set.size freeSet) $
halfs/0.2/halfs-0.2/Halfs.hs:  putStr $ "There are a total of: " ++ (show $ Set.size allInodeNums) ++ " inodes"
halfs/0.2/halfs-0.2/Halfs.hs:    when (Set.size freeSet /= length freeList) (
HAppS-IxSet/0.9.3/HAppS-IxSet-0.9.3/src/HAppS/Data/IxSet.hs:size x = Set.size $ toSet x
HAppS-IxSet/0.9.3/HAppS-IxSet-0.9.3/src/HAppS/Data/IxSet.hs:    num = Set.size set
happstack-ixset/0.5.0.3/happstack-ixset-0.5.0.3/src/Happstack/Data/IxSet.hs:size = Set.size . toSet
happstack-ixset/0.5.0.3/happstack-ixset-0.5.0.3/src/Happstack/Data/IxSet.hs:      no_values = sum [sum [Set.size s | s <- Map.elems m] | Ix m <- indices]
haskell-cnc/0.1.3.1/haskell-cnc-0.1.3.1/Intel/CncPure.hs:		    putStrLn ("    Tag col "++ show key ++" size "++ show (Set.size m)))
Holumbus-MapReduce/0.1.1/Holumbus-MapReduce-0.1.1/source/Holumbus/Distribution/Master/MasterData.hs:  ls2 = map (\(wid,s) -> (Set.size s, wid)) (MMap.toList wtm)
Holumbus-Storage/0.1.0/Holumbus-Storage-0.1.0/source/Holumbus/FileSystem/Controller/ControllerData.hs:    setSelector (_,s) = Set.size s < copyingLimit
hoogle/4.1.2/hoogle-4.1.2/src/Hoogle/DataBase/TypeSearch/Binding.hs:                g (l, vs) = Just $ [restrict|isJust l] ++ replicate (max 0 $ Set.size vs - 1) var
hprotoc/1.8.1/hprotoc-1.8.1/Text/ProtocolBuffers/ProtoCompile/Resolve.hs:  when (Set.size numbers /= Seq.length (D.DescriptorProto.field dp)) $
hprotoc/1.8.1/hprotoc-1.8.1/Text/ProtocolBuffers/ProtoCompile/Resolve.hs:  when (Set.size (Set.fromList values) /= Seq.length vs) $
HTab/1.5.4/HTab-1.5.4/src/HTab/Formula.hs: | Set.size xs == 1 = Set.findMin xs
HTab/1.5.4/HTab-1.5.4/src/HTab/Rules.hs:            | Set.size disjuncts == 1 -> Just (DisjRule df ( prefix ur newDeps disjuncts ), df)
hylolib/1.3.1/hylolib-1.3.1/src/HyLo/Model/Herbrand.hs:    coarbitrary (H es ps rs s) = coarbitrary (Set.size es) .
hylolib/1.3.1/hylolib-1.3.1/src/HyLo/Model/Herbrand.hs:                                 coarbitrary (Set.size ps) .
hylolib/1.3.1/hylolib-1.3.1/src/HyLo/Model/Herbrand.hs:                                 coarbitrary (Set.size rs) .
hylolib/1.3.1/hylolib-1.3.1/src/HyLo/Model.hs:  Set.size (worlds m) > 1 ==> forAll (worldOf m) $ \w ->
lhc/0.10/lhc-0.10/src/Grin/HPT/Interface.hs:--    | Set.size h1 `seq` Set.size h2 `seq` False = undefined
manatee/0.1.7/manatee-0.1.7/Manatee/UI/Window.hs:    -- Set size request for window child.
manatee/0.1.7/manatee-0.1.7/Manatee/UI/WindowNode.hs:  -- Set size request.
manatee-core/0.0.7/manatee-core-0.0.7/Manatee/Toolkit/Widget/PopupWindow.hs:-- | Set size and position.
morfette/0.3.2/morfette-0.3.2/src/GramLab/Morfette/Utils.hs:      uniquePOS  = fromIntegral $ Set.size $ Set.fromList $ map tokenPOS gold
panda/2009.4.1/panda-2009.4.1/src/Panda/View/Widget/Sidebar.hs:tag_link x = ( hotlink (G.root / x.Tag.uid) << x.Tag.name ) +++ ( " (" ++ x.Tag.resources.Set.size.show ++ ")" )
priority-sync/0.2.1.0/priority-sync-0.2.1.0/PrioritySync/Internal/RoomConstraint.hs:        do s <- liftM (Set.size . Set.insert (claimedThread c)) $ inUse $ claimedRoom c
priority-sync/0.2.1.0/priority-sync-0.2.1.0/PrioritySync/Internal/TaskPool.hs:                                                  (flip when retry . (>= n) . Set.size =<< inUse m) >> 
Pugs/6.2.13.16/Pugs-6.2.13.16/src/Pugs/Prim/List.hs:    rand <- io $ randomRIO (0 :: Int, (Set.size set) - 1)
Pugs/6.2.13.16/Pugs-6.2.13.16/src/Pugs/Prim/List.hs:    if (Set.size $ set) == 1 then return $ head $ Set.elems set
Pugs/6.2.13.16/Pugs-6.2.13.16/src/Pugs/Prim/List.hs:    if (Set.size $ set) == 1 && (Set.size $ dups) == 0
Pugs/6.2.13.16/Pugs-6.2.13.16/src/Pugs/Val/Code.hs:    | (Set.size . s_requiredNames) x /= (Set.size . s_requiredNames) y
ruler-core/1.0/ruler-core-1.0/dist/build/ruler-core/ruler-core-tmp/Transform.hs:                   Set.size _clausesIgathClauseNames
ruler-core/1.0/ruler-core-1.0/dist/build/ruler-core/ruler-core-tmp/Transform.hs:                   Set.size _clausesIgathClauseNames
smartGroup/0.2.1/smartGroup-0.2.1/SmartGroup.hs:mkAssoc m = Heap.singleton . Splittable . Map.mapKeys (\k-> StringL k (Set.size (m Map.! k))) $ m
uuagc/0.9.36/uuagc-0.9.36/src-derived/Transform.hs:                    in if Set.size nts' > Set.size nts
vision/0.0.4.0/vision-0.0.4.0/src/Properties/View.hs:            size2 <- Set.size <$> readIORef selected
wxdirect/0.12.1.3/wxdirect-0.12.1.3/src/MultiSet.hs:-- | /O(1)/. Returns the number of distinct elements in the multi set, ie. (@distinctSize mset == Set.size ('toSet' mset)@).


More information about the Haskell-Cafe mailing list