Efficent lens operation for Data.Map et al.
Johan Tibell
johan.tibell at gmail.com
Wed Jan 18 22:40:17 CET 2012
On Wed, Jan 18, 2012 at 1:35 PM, <roconnor at theorem.ca> wrote:
> On Wed, 18 Jan 2012, Johan Tibell wrote:
>
>> IIRC you just replace the current functions with yours and run make in
>> the benchmarks/ directory to compile the benchmark binaries (which use
>> Criterion). Then simply run them.
>
>
> I got an error trying to build the benchmarks:
>
> $ ghc --version
> The Glorious Glasgow Haskell Compilation System, version 6.12.3
>
> $ make
> ghc -DTESTING -cpp -O2 -fregs-graph -rtsopts --make -fforce-recomp -i.. -o
> bench-Map Map.hs
> [1 of 7] Compiling Data.StrictPair ( ../Data/StrictPair.hs,
> ../Data/StrictPair.o )
> [2 of 7] Compiling Data.Set ( ../Data/Set.hs, ../Data/Set.o )
> [3 of 7] Compiling Data.Map.Base ( ../Data/Map/Base.hs,
> ../Data/Map/Base.o )
> [4 of 7] Compiling Data.Map.Lazy ( ../Data/Map/Lazy.hs,
> ../Data/Map/Lazy.o )
> [5 of 7] Compiling Data.Map.Strict ( ../Data/Map/Strict.hs,
> ../Data/Map/Strict.o )
> [6 of 7] Compiling Data.Map ( ../Data/Map.hs, ../Data/Map.o )
> [7 of 7] Compiling Main ( Map.hs, Map.o )
> Linking bench-Map ...
> ghc -DTESTING -cpp -O2 -fregs-graph -rtsopts --make -fforce-recomp -i.. -o
> bench-Set Set.hs
> [1 of 2] Compiling Data.Set ( ../Data/Set.hs, ../Data/Set.o )
> [2 of 2] Compiling Main ( Set.hs, Set.o )
> Linking bench-Set ...
> ghc -DTESTING -cpp -O2 -fregs-graph -rtsopts --make -fforce-recomp -i.. -o
> bench-IntMap IntMap.hs
>
> ../Data/IntMap/Base.hs:195:44: parse error on input `#'
> make: *** [bench-IntMap] Error 1
>
>
> Any tips on how to proceed?
You've hit a bug in GHC 6.12.3; it doesn't handle conditional language
pragmas well. In the beginning of Data/IntMap/Base.hs we have:
{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__
{-# LANGUAGE MagicHash, DeriveDataTypeable, StandaloneDeriving #-}
#endif
and 6.12.3 does the wrong thing here. Should work in 7.0.
-- Johan
More information about the Libraries
mailing list