[Haskell-cafe] Small question
Andrew Coppin
andrewcoppin at btinternet.com
Fri Aug 10 13:12:03 EDT 2007
Stefan O'Rear wrote:
> On Fri, Aug 10, 2007 at 07:26:28AM +0100, Andrew Coppin wrote:
>
>> My program needs to make decisions based on a pair of boolean values.
>> Encoding both values as a single algebraic data type means I have to keep
>> "taking it apart" so I can work with it. I'm not sure how much time this
>> wastes...
>>
>
> Good point...
>
I suppose the only sure way to find out is to test. (IIRC, doesn't GHC
have a tendance to "take apart" tuples anyway?)
>>> Probably. I wound up doing something similar with vty, to considerable
>>> gain. (I did however use .&. instead of testBit - probably makes no
>>> difference, but I'm reminded of the (^2) being much slower than join(*)
>>> case...)
>>>
>> Well, perhaps I could define a pair of constants representing the bit
>> masks? (OTOH, won't GHC optimise "testBit <constant>" into something faster
>> anyway?)
>>
>
> Probably not; GHC has few rules for dealing with partial evaluation on
> numeric arguments. Asking GHC itself:
>
> stefan at stefans:/tmp$ ghc -c -ddump-simpl -O2 X.hs
>
> ==================== Tidy Core ====================
> X.moo [NEVER Nothing] :: forall a_a82. GHC.Base.Int -> a_a82 -> a_a82 -> a_a82
> [GlobalId]
> [Arity 3
> NoCafRefs
> Str: DmdType U(L)LL]
> X.moo =
> \ (@ a_a88) (ix_a84 :: GHC.Base.Int) (ift_a85 :: a_a88) (iff_a86 :: a_a88) ->
> case ix_a84 of wild_acF { GHC.Base.I# x#_acH ->
> case Data.Bits.$w$s$dmbit 7 of ww1_acN { __DEFAULT ->
> case GHC.Prim.word2Int#
> (GHC.Prim.and# (GHC.Prim.int2Word# x#_acH) (GHC.Prim.int2Word# ww1_acN))
> of wild1_acO {
> __DEFAULT -> ift_a85; 0 -> iff_a86
> }
> }
> }
>
>
>
>
> ==================== Tidy Core Rules ====================
>
>
> stefan at stefans:/tmp$ cat X.hs
> module X where
>
> import Data.Bits
>
> {-# NOINLINE moo #-}
> -- ghc doesn't optimize functions that are deemed small enough for inlining;
> -- this is a good thing (since when we inline we know more about the context
> -- and can do a better job if we wait until then), but interferes with small
> -- experiments like this
>
> moo :: Int -> a -> a -> a
> moo ix ift iff = if testBit ix 7 then ift else iff
> stefan at stefans:/tmp$
>
>
> The important bit is the (Data.Bits.$w$s$dmbit 7). Since that function
> doesn't do IO (no realworld arguments), it could in theory be evaluated
> at compile time (and judging from context it almost surely evaluates to
> 128#), but it hasn't been.
>
Mmm. See, now, I have *no idea* what GHC is saying. But I would have
expected that if I do something like
x = if testBit 3 q ...
then the definition of testBit would get inlined, and then hopfully the
optimiser would do something. But then, IANAGD. (I am not a GHC developer.)
>> Like that time yesterday, I compiled from program and got a weird message
>> about GHC about "ignored trigraphs" or something... What the heck is a
>> trigraph?
>>
>
> Everyone's favorite obscure feature of the ANSI C99 preprocessor.
> Probably you had something like "this is odd???" in your source code,
> and were using -cpp.
>
> http://www.vmunix.com/~gabor/c/draft.html#5.2.1.1
>
Er... wow. OK, well I have no idea what happened there... (I'm not using
-cpp. I don't even know what it is.) I had presumed GHC was upset
because it got killed on the previous run... (I was running something
else and it locked up the PC.)
>>> Good idea! Maybe it could be fit into the GHC Performance Resource
>>> somehow? (http://www.haskell.org/haskellwiki/Performance/GHC)
>>>
>> OK. But it'll probably contain a lot of guessing to start with... ;-)
>>
>
> Wiki pages can be fixed. Private misunderstandings can't, at least not
> anywhere near as easily.
>
Point taken... ;-)
More information about the Haskell-Cafe
mailing list