What GHC optimization is responsible for duplicating case expressions? - haskell

Given the following code:
{-# OPTIONS_GHC -funbox-strict-fields #-}
module Test where
data X = X !Int !Int
test (X a b) (X c d) = X (max a c) (max b d)
GHC generates this core when compiling with optimizations (renamed to make reading easier):
test
test =
\ u v ->
case u of x { X y z ->
case v of c { X d e ->
case tagToEnum# (<=# y d) of _ {
False ->
case tagToEnum# (<=# z e) of _ {
False -> x;
True -> X y e
};
True ->
case tagToEnum# (<=# z e) of _ {
False -> X d z;
True -> c
}
}
}
}
Note how GHC has generated in total 4 different code paths. In general, the number of code paths grows exponentially with the number of conditions.
What GHC optimization leads to that behavior? Is there a flag to control this optimization? In my case, this generates huge code bloat, and makes core dumps very hard to read because of deeply nested case expressions.

After some research, I've found that the optimization responsible for this is the so called "case-of-case" transformation, that GHC does presumably in the simplifier, so it cannot be deactivated (since it is necessary for a lot of what GHC does and the simplifier is an integral part of GHC's optimization pipeline).
The following link explains how case of case leads to the duplication: http://lambda.jstolarek.com/2013/01/taking-magic-out-of-ghc-or-tracing-compilation-by-transformation/
In particular, case-of-case turns this:
case (
case C of
B1 -> F1
B2 -> F2
) of
A1 -> E1
A2 -> E2
into the following:
case C of
B1 -> case F1 of
A1 -> E1
A2 -> E2
B2 -> case F2 of
A1 -> E1
A2 -> E2
where the outer case has been duplicated and pushed into the branches.

Related

Are these 2 nested functions (that bodies depend on top function arg) equivalent from the compiler's point of view?

I have some function test which has a signature like:
data D = D | C
test :: D -> ....
test d ... =
And I want to create with let some nested function which body is either body-A or body-B based on case analyze of the d. So, I can do it as:
let nestedFun p =
case d of
C -> case (ft, p) of
(Just SM.FileTypeRegular, Just p1) | Just nm <- takeFileName (cs p1) -> S.member nm itemNames
_ -> False
D -> case (ft, p) of
(Just SM.FileTypeRegular, Just p1) -> S.member (hash $ cs #_ #FilePath p1) itemHashes
_ -> False
or as
let nestedFun p =
case (ft, p) of
(Just SM.FileTypeRegular, Just p1) -> case d of
C | Just nm <- takeFileName (cs p1) ->
S.member nm itemNames
D ->
S.member (hash $ cs #_ #FilePath p1) itemHashes
_ -> False
In short, the difference is that the 1st version looks like Python's:
if isinstance(d, D):
nestedFun = lambda p: ...
else:
nestedFun = lambda p: ...
while the 2nd one is like:
def nestedFun(p):
if isinstance(d, D): ...
else: ...
I will call this nestedFun on the big list of values so the question here is: Is the Haskell compiler/optimizer able to understand that both versions are the same and to reduce the 2nd one to the 1st one, so the case-analyze on d happens just once?
GHC is able to -- the optimizer does consider case-of-case transformations to see if they enable other optimizations -- but not in a way that you can rely on. If you need this, I highly recommend performing that transformation by hand. In fact, for the case you describe here, I would go even farther, and make it clear that the case can happen before p is in scope:
nestedFunDmwit = case d of
C -> \p -> case (ft, p) of ...
D -> \p -> case (ft, p) of ...
The difference here is that nestedFun will re-evaluate the case each time it is applied to an argument, while nestedFunDmwit will evaluate the case just once. So, for example, map (nestedFun x) [a, b, c] would reliably evaluate the case just once; map nestedFun [a, b, c] would evaluate the case three times unless things line up just so for the optimizer; and map nestedFunDmwit [a, b, c] would reliably evaluate the case just once.

Dual default methods

Consider the following classes:
class F t where
f1 :: ...
f2 :: ...
class F t => G t where
g1 :: ...
g2 :: ...
Also I can write the following default functions:
f1 in terms of f2.
f2 in terms of f1.
g1 in terms of g2.
g2 in terms of g1.
f1 in terms of g1, if G t.
f2 in terms of g2, if G t.
Hence, I should be able to do the following:
instance F T1 where
f1 x = (some function of f2)
Or:
instance F T1
instance G T1 where
g1 x = (some function of g2)
But it seems the only way I can achieve this is to have two default definitions of f1 and f2, but I don't think GHC allows this. Is there anyway I can write this so that for both types that are only of class F, and types that are also of class G, only have to implement one function?
If I get the requirements right, they can be straightforwardly satisfied with a couple of extensions:
{-# LANGUAGE FlexibleInstances, UndecidableInstances, OverlappingInstances #-}
class F t where
f1 :: t -> t -> t
f1 _ = f2
f2 :: t -> t
f2 x = f1 x x
class F t => G t where
g1 :: t -> t -> t
g1 x _ = g2 x
g2 :: t -> t
g2 x = g1 x x
instance G t => F t where
f1 = flip g1
f2 = g2
instance F Int where
f1 = (-)
main = mapM_ print ([f1 4 2, f2 4] :: [Int])
*Main> :main
2
0
The instance can be changed to G:
instance G Int where
g1 = subtract
main = mapM_ print ([f1 4 2, f2 4, g1 4 2, g2 4] :: [Int])
*Main> :main
2
0
-2
0
However, I'd consider this solution poor. Could this duality be expressed in some other way? If you provide a concrete example of what F and G are, a more suitable design may be found.
A fairly common idiom for defining subclass methods in terms of the superclass (or is it superclass methods in terms of the subclass? I can never keep it straight) is to expose an explicit *Default method, as in
class F t where
{-# MINIMAL f1 | f2 #-}
f1 = ... f2 ...
f2 = ... f1 ...
f1Default :: G t => ...
f1Default = ... g1 ...
f2Default :: G t => ...
f2Default = ... g2 ...
class G t where
{-# MINIMAL g1 | g2 #-}
g1 = ... g2 ...
g2 = ... g1 ...
This gives the instance-writer control over which default is used.
There are many examples of this pattern in base, including fmapDefault, foldMapDefault, bimapDefault, bifoldMapDefault, and many more, and I expect there are a fair number of examples of this outside base as well.

will the result of `let` and `where` expressions be stored in haskell?

I am rather new to Haskell and after reading this and some performance tips on strictness I am still wondering how this applies to let and where expressions. If I have code like:
f :: Int -> Int -> Int
f a b
|a==b = <simple computation>
|otherwise = e1 + 2 * e1 - e1^2
where e1 = <lengthy computation>
how often will <lengthy computation> be evaluated? I assume that given Haskell's lazy evaluation in e1 will not be evaluated at all if a==b. But if not, is e1 substituted in the otherwise expression and then evaluated every time it is encountered or is it evaluated once it is first encountered and then stored and reused in all subsequent occurrences? Also:
is there a way to control this process "manually"?
does this depend on weather I run code in ghci or compile it with GHC and within GHC compilation does it depend on flags like -o?
This is quite similar to this question but I could not find answers for Haskell.
Explanations are very appreciated.
As a rule, code in the where or let block of a constant applicative form is evaluated only once, and only as deep as necessary (i.e., if it's not used at all it also won't be evaluated at all).
f is not a constant applicative form because it has arguments; it's equivalent to
f' = \a b -> let e1 = <lengthy computation>
in if a==b
then <simple computation>
else e1 + 2 * e1 - e1^2
So, e1 is evaluated once every time you call the function with both arguments. This is likely also what you want, and in fact the best behaviour possible if <lengthy computation> depends on both a and b. If it, say, only depends on a, you can do better:
f₂ a = \b ->
if a==b then <simple computation>
else e1 + 2 * e1 - e1^2
where e1 = <lengthy computation>
This form will be more efficient when you do e.g. map (f 34) [1,3,9,2,9]: in that example, e1 would only be computed once for the entire list. (But <lengthy computation> won't have b in scope, so it can't depend on it.)
OTOH, there can also be scenarios where you don't want e1 to be kept at all. (E.g. if it occupies a lot of memory, but is rather quick to compute). In this case, you can just make it a “nullary function”
f₃ a b
| a==b = <simple computation>
| otherwise = e1() + 2 * e1() - e1()^2
where e1 () = <lengthy computation>
Functions are not memoized by default, so in the above, <lengthy computation> is done zero times if a==b and three times else.
Yet another possibility is to force that e1 is always evaluated exactly once. You can do that with seq:
f₄ a b = e1 `seq` if a==b
then <simple computation>
else e1 + 2 * e1 - e1^2
where e1 = <lengthy computation>
This is the only of the suggestions that actually changes something about the semantics, not just the performance: assume we define always e1 = error "too tough". Then f, f', f₂ and f₃ will all still work provided that a==b; however f₄ will even fail in that case.
As for optimisations (-O or -O2) – these generally won't change anything about the strictness properties of your program (i.e. can't change between the behaviour of f and f₄). Beyond that, the compiler is pretty much free to make any change it considers benefitial to performance. But usually, it will not change anything about what I said above. The main exception, as Taren remarks, is something like f₃: the compiler will readily inline e1 () and then share a reference to the computed value, which prevents the garbage collector from reclaiming the memory. So it's better not to rely on this (anyway somewhat hackish) technique.
You can check actually check out how GHC will optimize your code:
ghc -ddump-simpl -dsuppress-idinfo -dsuppress-coercions -dsuppress-type-applications -dsuppress-uniques -dsuppress-module-prefixes -fforce-recomp .\scratch.hs
This is a bit of a mouthful so you might want to alias it. The results of this very much depend on the optimization level so you might want to try this out with each.
With g i = sum [1..i] as expensive computation and -O2 I get this output:
==================== Tidy Core ====================
Result size of Tidy Core = {terms: 64, types: 23, coercions: 0}
Rec {
-- RHS size: {terms: 16, types: 3, coercions: 0}
$wgo :: Int# -> Int# -> Int#
$wgo =
\ (w :: Int#) (ww :: Int#) ->
case w of wild {
__DEFAULT -> $wgo (+# wild 1#) (+# ww wild);
10000# -> +# ww 10000#
}
end Rec }
-- RHS size: {terms: 15, types: 1, coercions: 0}
f2 :: Int
f2 =
case $wgo 1# 0# of ww { __DEFAULT ->
I# (-# (+# ww (*# 2# ww)) (*# ww ww))
}
-- RHS size: {terms: 2, types: 0, coercions: 0}
f1 :: Int
f1 = I# 42#
-- RHS size: {terms: 17, types: 8, coercions: 0}
f :: Int -> Int -> Int
f =
\ (a :: Int) (b :: Int) ->
case a of _ { I# x ->
case b of _ { I# y ->
case tagToEnum# (==# x y) of _ {
False -> f2;
True -> f1
}
}
}
Which is pretty ugly when compared to your haskell version but with a bit of squinting it isn't much more complicated. $wgo is our expensive function. The interesting part here is that f1 or f2, the possible return values of f, are only computed once when they are required for the first time. For the rest of the program run they are reused.

Is it possible to generalise equations in Haskell?

Apologies for my poor wording of the question. I've tried searching for an answer but not knowing what to search is making it very difficult to find one.
Here is a simple function which calculates the area of a triangle.
triangleArea :: Float -> Float -> Float -> Float
triangleArea a b c
| (a + b) <= c = error "Not a triangle!"
| (a + c) <= b = error "Not a triangle!"
| (b + c) <= a = error "Not a triangle!"
| otherwise = sqrt (s * (s - a) * (s - b) * (s - c))
where s = (a + b + c) / 2
Three lines of the function have been taken up for the purposes of error checking. I was wondering if these three lines could be condensed into one generic line.
I was wondering if something similar to the following would be possible
(arg1 + arg2) == arg3
where Haskell knows to check each possible combination of the three arguments.
I think #behzad.nouri's comment is the best. Sometimes doing a little math is the best way to program. Here's a somewhat overdone expansion on #melpomene's solution, which I thought would be fun to share. Let's write a function similar to permutations but that computes combinations:
import Control.Arrow (first, second)
-- choose n xs returns a list of tuples, the first component of each having
-- n elements and the second component having the rest, in all combinations
-- (ignoring order within the lists). N.B. this would be faster if implemented
-- using a DList.
choose :: Int -> [a] -> [([a],[a])]
choose 0 xs = [([], xs)]
choose _ [] = []
choose n (x:xs) =
map (first (x:)) (choose (n-1) xs) ++
map (second (x:)) (choose n xs)
So..
ghci> choose 2 [1,2,3]
[([1,2],[3]),([1,3],[2]),([2,3],[1])]
Now you can write
triangleArea a b c
| or [ x + y <= z | ([x,y], [z]) <- choose 2 [a,b,c] ] = error ...
This doesn't address the question of how to shorten your error checking code, but you may be able to limit how often you repeat it by defining some new types with invariants. This function needs error checking because you can't trust the user to supply Float triples that make a reasonable triangle, and if you continue to define functions this way then every triangle-related function you write would need similar error checks.
However, if you define a Triangle type, you can check your invariants only once, when a triangle is created, and then all other functions will be guaranteed to receive valid triangles:
module Triangle (Triangle(), mkTriangle, area) where
data Triangle a = Triangle a a a deriving Show
mkTriangle :: (Num a, Ord a) => a -> a -> a -> Either String (Triangle a)
mkTriangle a b c
| a + b <= c = wrong
| a + c <= b = wrong
| b + c <= a = wrong
| otherwise = Right $ Triangle a b c
where wrong = Left "Not a triangle!"
area :: Floating a => Triangle a -> a
area (Triangle a b c) = sqrt (s * (s - a) * (s - b) * (s - c))
where s = (a + b + c) / 2
Here we export the Triangle type, but not its constructor, so that the client must use mkTriangle instead, which can do the required error checking. Then area, and any other triangle functions you write, can omit the checks that they are receiving a valid triangle. This general pattern is called "smart constructors".
Here are two ideas.
Using existing tools, you can generate all the permutations of the arguments and check that they all satisfy a condition. Thus:
import Data.List
triangleArea a b c
| any (\[x, y, z] -> x + y <= z) (permutations [a,b,c])
= error "Not a triangle!"
| otherwise = {- ... -}
This doesn't require writing very much additional code; however, it will search some permutations you don't care about.
Use the usual trick for choosing an element from a list and the left-overs. The zippers function is one I use frequently:
zippers :: [a] -> [([a], a, [a])]
zippers = go [] where
go b [] = []
go b (v:e) = (b, v, e) : go (v:b) e
We can use it to build a function which chooses only appropriate triples of elements:
triples :: [a] -> [(a, a, a)]
triples xs = do
(b1, v1, e1) <- zippers xs
(b2, v2, e2) <- zippers e1
v3 <- b1 ++ b2 ++ e2
return (v1, v2, v3)
Now we can write our guard like in part (1), but it will only consider unique pairings for the addition.
triangleArea a b c
| any (\(x, y, z) -> x + y <= z) (triples [a,b,c])
= error "Not a triangle!"
| otherwise = {- ... -}

How to combine case statement patterns [duplicate]

This question already has answers here:
Haskell syntax for 'or' in case expressions
(5 answers)
Closed 7 years ago.
I'm trying to match on many different constructors in a case statement. For simplicity, assume in half the cases we do the same thing, and in the other half we do something else. Even if I factor out the logic to another function, I still have to write:
case x of
C1 -> foo x
C2 -> foo x
...
C10 -> bar x
C11 -> bar x
...
Is there some way to make case statements behave more like switch statements in C (i.e. with fallthrough), or so that I can match on one of many patterns at once, like:
case x of
C1, C2, C3 -> foo x
C10, C11, C12 -> bar x
Or perhaps another way to clean this up?
These are called disjunctive patterns, and Haskell does not have them. (OCaml and F# do.) There are a few typical workarounds, however. If your type is an enumeration, you can use equality, with for example elem, using a case expression, guards, or MultiWayIf:
exampleCase cond = case cond of
c
| c `elem` [C1, C2, C3] -> foo
| c `elem` [C10, C11, C12] -> bar
| otherwise -> baz
exampleGuards c
| c `elem` [C1, C2, C3] -> foo
| c `elem` [C10, C11, C12] -> bar
| otherwise -> baz
exampleIf c
= additionalProcessing $ if
| c `elem` [C1, C2, C3] -> foo
| c `elem` [C10, C11, C12] -> bar
| otherwise -> baz
And of course, if foo or bar are long expressions, thanks to laziness you can simply factor them into local definitions, so you only have to repeat the name and any pattern variables you need as arguments:
exampleWhere cond = case cond of
C1 x -> foo x
C2 y -> foo y
…
C10 -> bar
C11 -> bar
…
where
foo x = something long (involving x, presumably)
bar = if you please then something else quite long
If you frequently group constructors together in this way, you can use the PatternSynonyms language option, which is especially useful in conjunction with ViewPatterns, to make your own patterns for matching such groups:
{-# Language
LambdaCase,
PatternSynonyms,
ViewPatterns #-}
-- Write one function to match each property.
fooish :: T -> Maybe X
fooish = \ case
C1 x -> Just x
C2 x -> Just x
…
C10 -> Nothing
C11 -> Nothing
…
-- May use a wildcard ‘_’ here; I prefer not to,
-- to require updating cases when a type changes.
barrish :: T -> Bool
barrish = \ case
C1{} -> False
C2{} -> False
…
C10 -> True
C11 -> True
…
-- Create synonyms for matching those properties.
-- (These happen to be unidirectional only.)
pattern Fooish :: T -> Foo
pattern Fooish x <- (fooish -> Just x)
pattern Barrish :: T -> Bar
pattern Barrish <- (barrish -> True)
-- If they cover all cases, tell the compiler so.
-- This helps produce useful warnings with ‘-Wall’.
{-# Complete Fooish, Barrish #-}
-- Use them just like normal patterns.
exampleSynonyms x = case x of
Fooish x -> …
…
Barrish -> …
…

Resources