Skip to content

GitLab

  • Projects
  • Groups
  • Snippets
  • Help
    • Loading...
  • Help
    • Help
    • Support
    • Community forum
    • Submit feedback
  • Sign in / Register
GHC
GHC
  • Project overview
    • Project overview
    • Details
    • Activity
    • Releases
  • Repository
    • Repository
    • Files
    • Commits
    • Branches
    • Tags
    • Contributors
    • Graph
    • Compare
    • Locked Files
  • Issues 4,251
    • Issues 4,251
    • List
    • Boards
    • Labels
    • Service Desk
    • Milestones
    • Iterations
  • Merge Requests 391
    • Merge Requests 391
  • Requirements
    • Requirements
    • List
  • CI / CD
    • CI / CD
    • Pipelines
    • Jobs
    • Schedules
  • Security & Compliance
    • Security & Compliance
    • Dependency List
    • License Compliance
  • Operations
    • Operations
    • Incidents
    • Environments
  • Analytics
    • Analytics
    • CI / CD
    • Code Review
    • Insights
    • Issue
    • Repository
    • Value Stream
  • Wiki
    • Wiki
  • Snippets
    • Snippets
  • Members
    • Members
  • Collapse sidebar
  • Activity
  • Graph
  • Create a new issue
  • Jobs
  • Commits
  • Issue Boards
  • Glasgow Haskell Compiler
  • GHCGHC
  • Issues
  • #6048

Closed
Open
Opened Apr 26, 2012 by Simon Peyton Jones@simonpjDeveloper

Exponential inlining code blowup

(Transferring a new thread from #5539 (closed) to a new ticket, since it's really a separate problem.) kosmikus helpfully provided this program

module TestCase where

import Control.Applicative

data X = X
  (Maybe String)
  (Maybe String)
  (Maybe String)
  (Maybe String)
  (Maybe String)
  (Maybe String)
  (Maybe String)
  (Maybe String)
  (Maybe String)

mb :: (String -> Maybe a) -> String -> Maybe (Maybe a)
mb _ ""  = Just Nothing
mb _ "-" = Just Nothing
mb p xs  = Just <$> p xs

run :: [String] -> Maybe X
run
  [ x1
  , x2
  , x3
  , x4
  , x5
  , x6
  , x7
  , x8
  , x9
  ] = X
  <$> mb pure x1
  <*> mb pure x2
  <*> mb pure x3
  <*> mb pure x4
  <*> mb pure x5
  <*> mb pure x6
  <*> mb pure x7
  <*> mb pure x8
  <*> mb pure x9

Unless mb is marked as NOINLINE, it gets expanded in the body of run a number of times that seems to grow exponentially with the size of the list (9 in the example).

Trac metadata
Trac field Value
Version 7.4.1
Type Bug
TypeOfFailure OtherFailure
Priority normal
Resolution Unresolved
Component Compiler
Test case
Differential revisions
BlockedBy
Related
Blocking
CC
Operating system
Architecture
Assignee
Assign to
None
Milestone
None
Assign milestone
Time tracking
None
Due date
None
Reference: ghc/ghc#6048