[GHC] #13689: Data.Either doesn't export INLINABLE short functions like "rights"

#13689: Data.Either doesn't export INLINABLE short functions like "rights" -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Core | Version: 8.0.2 Libraries | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Incorrect API Unknown/Multiple | annotation Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Currently if I use Data.Either's simple functions like "rights", "isLeft", etc. In Core/Cmm with -O2 I see that they are called like external functions and not inlined. This is because they are not marked as INLINABLE in the library itself. It'll be great if such functions in base are marked as INLINABLE so optimizator/inliner to generate more efficient code. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13689 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13689: Data.Either doesn't export INLINABLE short functions like "rights" -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect API | Unknown/Multiple annotation | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by rwbarton): * status: new => infoneeded Comment: No, that isn't how inlining works. You do not need an INLINABLE pragma on a function for its unfolding to be included in an interface file and used at a call site. (Otherwise virtually nothing would get inlined ever!) Can you provide a reproducer where you are not seeing inlining that you expect to happen? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13689#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13689: Data.Either doesn't export INLINABLE short functions like "rights" -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect API | Unknown/Multiple annotation | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by varosi): {{{ {-# LANGUAGE BangPatterns, ScopedTypeVariables, NoMonomorphismRestriction #-} import Control.Monad import qualified Data.ByteString as B import Data.Csv.Incremental import Data.Either (rights) import System.Exit import System.IO import System.Environment (getArgs) import qualified Data.List as DL main :: IO () main = do [input] <- getArgs withFile input ReadMode $ \ csvFile -> do let loop !acc (Many rs k) = loop (acc + countFields rs) =<< feed k loop !acc (Done rs) = print (countFields rs + acc) loop !_ (Fail _ errMsg) = putStrLn errMsg >> exitFailure feed k = k <$> B.hGetSome csvFile (16*1024) loop 0 (decode NoHeader :: Parser [()]) where countFields = sum . map length . rights }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13689#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13689: Data.Either doesn't export INLINABLE short functions like "rights"
-------------------------------------+-------------------------------------
Reporter: varosi | Owner: (none)
Type: bug | Status: infoneeded
Priority: normal | Milestone:
Component: Core Libraries | Version: 8.0.2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Incorrect API | Unknown/Multiple
annotation | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by bgamari):
I have confirmed that these two indeed don't have an unfolding in 8.0.2,
{{{#!hs
2155eed1475edba07fc3c0eac3a8a1c2
rights :: [Either a b] -> [b]
{- Arity: 1, HasNoCafRefs, Strictness: ,
Unfolding: (\ @ a @ b (x :: [Either a b]) -> rights1 @ a @ b x) -}
39075b0896f5b6036d022994b88a19f9
rights1 :: [Either a b] -> [b]
{- Arity: 1, HasNoCafRefs, Strictness: -}
}}}
Moreover, this,
{{{#!hs
import Data.Either
main = print $ sum $ rights [ Right i | i <- [1..500] ]
}}}
exhibits a call to `rights1`. It seems we really do need an explicit
`INLINABLE` here.
Thanks for pointing this out, varosi.
--
Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13689#comment:3
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

#13689: Data.Either doesn't export INLINABLE short functions like "rights" -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect API | Unknown/Multiple annotation | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by varosi): I'm expect "rights" to be inlined in Core. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13689#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13689: Data.Either doesn't export INLINABLE short functions like "rights" -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect API | Unknown/Multiple annotation | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by varosi): Could you elaborate more why this happens? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13689#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13689: Data.Either doesn't export INLINABLE short functions like "rights" -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect API | Unknown/Multiple annotation | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): Should we not ask first why they do not have unfoldings? They seem quite small. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13689#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13689: Data.Either doesn't export INLINABLE short functions like "rights" -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect API | Unknown/Multiple annotation | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): They are defined in terms of list comprehensions, which does result in a rather large desugared core definition, {{{#!hs rights' :: forall t_aQz t_aQx. [Either t_aQz t_aQx] -> [t_aQx] [LclIdX, Str=DmdType] rights' = \ (@ t_aQz) (@ t_aQx) (xs_aPD :: [Either t_aQz t_aQx]) -> GHC.Base.build @ t_aQx (\ (@ a_d1An) (c_d1Ao [OS=OneShot] :: t_aQx -> a_d1An -> a_d1An) (n_d1Ap [OS=OneShot] :: a_d1An) -> GHC.Base.foldr @ (Either t_aQz t_aQx) @ a_d1An (\ (ds_d1Ar :: Either t_aQz t_aQx) (ds_d1Aq [OS=OneShot] :: a_d1An) -> case ds_d1Ar of _ [Occ=Dead] { __DEFAULT -> (\ _ [Occ=Dead, OS=OneShot] -> ds_d1Aq) GHC.Prim.void#; Right x_aPE -> c_d1Ao x_aPE ds_d1Aq }) n_d1Ap xs_aPD) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13689#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13689: Data.Either doesn't export INLINABLE short functions like "rights" -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect API | Unknown/Multiple annotation | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * cc: nomeata (added) Comment: CCing Joachim who has thought a great deal about fusion. I think the simplest option here is to just to do as varosi suggests and add INLINEABLE pragmas. Yes, we could give `lefts` and `rights` the same treatment that we give `filter` and give it a "trivial" definition, alongside some fusible definitions with rules to map one to the other, but I think this is a lot of complexity for little pay-off. In general this does raise the point though of being careful about defining library functions in terms of list comprehensions as they make definitions look much smaller than they in fact are. If we make `lefts` and `rights` `INLINEABLE` then we also ought to look for other functions in `base` defined in terms of comprehensions. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13689#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13689: Data.Either doesn't export INLINABLE short functions like "rights" -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect API | Unknown/Multiple annotation | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): `INLINEABLE` might be reasonable. Isn’t it the case that the unfolding stored in the interface will be the un-optimized one (i.e. not the large thing visible up there?) Or is the large code directly the result of the desugared list comprehension (instead of applying rules to the resulting code)?
Yes, we could give lefts and rights the same treatment that we give filter and give it a "naive" definition, alongside some fusible definitions with rules to map one to the other, but I think this is a lot of complexity for little pay-off.
Probably not worth it. `lefts` and `rights` are already defined in terms of fusable things (list comprehensions) – this is different for `filter`, which has a recursive definition. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13689#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13689: Data.Either doesn't export INLINABLE short functions like "rights" -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect API | Unknown/Multiple annotation | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3576 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * differential: => Phab:D3576 Comment:
INLINEABLE might be reasonable. Isn’t it the case that the unfolding stored in the interface will be the un-optimized one .
Yes.
(i.e. not the large thing visible up there?)
No :) The large thing visible here is the desugared Core (`-ddump-ds`); no simplification has happened. It just so happens that list comprehensions are directly desugared into fusion primitives and consequently produce rather large Core. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13689#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13689: Data.Either doesn't export INLINABLE short functions like "rights" -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect API | Unknown/Multiple annotation | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3576 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari):
Probably not worth it. lefts and rights are already defined in terms of fusable things (list comprehensions) – this is different for filter, which has a recursive definition.
Right; that is my view as well. The only difference would be the size of the interface file and how much work the simplifier needs to do. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13689#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13689: Data.Either doesn't export INLINABLE short functions like "rights" -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect API | Unknown/Multiple annotation | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3576 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: infoneeded => patch -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13689#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13689: Data.Either doesn't export INLINABLE short functions like "rights" -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect API | Unknown/Multiple annotation | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3576 Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata):
It just so happens that list comprehensions are directly desugared into fusion primitives and consequently produce rather large Core.
Oh, annoying. What if the implementation was ``` lefts = concatMap go where go (Left x) = [x] go (Right _) = [] ``` That should result in the same code in terms of `foldr` and `buildr`, but maybe produce a smaller unfolding, and be inlinable by itself. (This is more out of curiosity, it is not too bad to have a large unfolding, I think). Although it would be desirable to use a single library defined definition of `lefts` when no fusion happens, instead of repeating the code at every use-site. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13689#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13689: Data.Either doesn't export INLINABLE short functions like "rights" -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect API | Unknown/Multiple annotation | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3576 Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): I'd rather not give special treatment to `rights` which is not a very special function. It's common to write functions like `rights` for ones own types for example. Instead could we perhaps give a bigger bonus to unfoldings headed by `build`? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13689#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13689: Data.Either doesn't export INLINABLE short functions like "rights" -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect API | Unknown/Multiple annotation | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3576 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari):
Instead could we perhaps give a bigger bonus to unfoldings headed by `build`?
This sounds like a nice avenue to explore but it seems a bit ad-hoc. While `foldr/build` do enjoy some special treatment in the compiler, I suspect end-users may want to have this same bonus (e.g. `vector`'s `stream`). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13689#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13689: Data.Either doesn't export INLINABLE short functions like "rights" -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect API | Unknown/Multiple annotation | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3576 Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): Replying to [comment:8 bgamari]:
In general this does raise the point though of being careful about defining library functions in terms of list comprehensions as they make definitions look much smaller than they in fact are. If we make `lefts` and `rights` `INLINEABLE` then we also ought to look for other functions in `base` defined in terms of comprehensions.
I don't think the unfoldings are any bigger than they need to be, but you're right; we need to think about `INLINABLE` annotations when we might not otherwise. I believe the inliner gives a bonus when it sees things that are mentioned in `RULES`. If we don't do so already, we should surely give a similar bonus when deciding whether to export an unfolding. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13689#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13689: Data.Either doesn't export INLINABLE short functions like "rights" -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect API | Unknown/Multiple annotation | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3576 Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): By the way, way back a few years ago when I was mucking about with list fusion, it always seemed that GHC was a lot better at deciding to inline `foldr` things than at deciding to inline `build` things. I'm not sure why. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13689#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13689: Data.Either doesn't export INLINABLE short functions like "rights" -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect API | Unknown/Multiple annotation | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3576 Wiki Page: | -------------------------------------+------------------------------------- Changes (by dfeuer): * cc: dfeuer (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13689#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13689: Data.Either doesn't export INLINABLE short functions like "rights" -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect API | Unknown/Multiple annotation | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3576 Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): JFTR: The definition {{{ lefts = concatMap go where go (Left x) = [x] go (Right _) = [] }}} results in the same code (GHC HEAD even CSE’s it with the other definition if defined in the same module), and also does not get an unfolding automatically, and with `INLINEABLE` the unfolding is the large one with `foldr` and `build`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13689#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13689: Data.Either doesn't export INLINABLE short functions like "rights" -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect API | Unknown/Multiple annotation | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3576 Wiki Page: | -------------------------------------+------------------------------------- Comment (by varosi): Is there a way to see if this code is part of inner-cycle/fold/map so it's better to be inlined? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13689#comment:20 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13689: Data.Either doesn't export INLINABLE short functions like "rights" -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect API | Unknown/Multiple annotation | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3576 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): varosi, the problem is that GHC considers the definitions of `lefts` and `rights` to be too large to inline and consequently doesn't produce unfoldings for them when compiling `GHC.Eithers`. This means that by the time we get to compiling your code we couldn't inline `lefts` and `rights` even if we wanted to. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13689#comment:21 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13689: Data.Either doesn't export INLINABLE short functions like "rights" -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.2.1 Component: Core Libraries | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect API | Unknown/Multiple annotation | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3576 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: => 8.2.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13689#comment:22 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13689: Data.Either doesn't export INLINABLE short functions like "rights" -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.2.1 Component: Core Libraries | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect API | Unknown/Multiple annotation | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3576 Wiki Page: | -------------------------------------+------------------------------------- Comment (by varosi): hm, strange. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13689#comment:23 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13689: Data.Either doesn't export INLINABLE short functions like "rights"
-------------------------------------+-------------------------------------
Reporter: varosi | Owner: (none)
Type: bug | Status: patch
Priority: normal | Milestone: 8.2.1
Component: Core Libraries | Version: 8.0.2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Incorrect API | Unknown/Multiple
annotation | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D3576
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#13689: Data.Either doesn't export INLINABLE short functions like "rights" -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: ⊥ Component: Core Libraries | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect API | Unknown/Multiple annotation | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3576 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => new * milestone: 8.2.1 => ⊥ Comment: I have merged comment:24 to `ghc-8.2`, but, as has been pointed out above, this is arguably only papering over a symptom. However, we discussed this on the call and it seems that fixing this robustly may be quite tricky. Reopening but milestoning to _|_. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13689#comment:25 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13689: Data.Either doesn't export INLINABLE short functions like "rights" -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: ⊥ Component: Core Libraries | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect API | Unknown/Multiple annotation | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3576 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Merged to `ghc-8.2` as fdcdcd0f8fdb08125932b7f8a3f5a8adc5d50466. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13689#comment:26 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13689: Data.Either doesn't export INLINABLE short functions like "rights" -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: ⊥ Component: Core Libraries | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect API | Unknown/Multiple annotation | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3576 Wiki Page: | -------------------------------------+------------------------------------- Comment (by varosi): Possible discussion for 8.4? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13689#comment:27 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13689: Data.Either doesn't export INLINABLE short functions like "rights" -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: ⊥ Component: Core Libraries | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect API | Unknown/Multiple annotation | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3576 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): We are certainly open to better solutions. However, I'll admit I don't have any great ideas at the moment. Knowing whether inlining is fruitful in general is a hard problem. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13689#comment:28 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC