[GHC] #11393: Ability to define INLINE pragma for all instances of a given typeclass

#11393: Ability to define INLINE pragma for all instances of a given typeclass -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 8.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Hello! I would like to request a feature that would allow me to define the `INLINE` pragma for all instances of a given type class. Currently when we are creating high-performance libraries, that strongly depend on type- level computations we are using a lot of typeclasses that we want to be cut-out during the compilation time. We can use the `INLINE` pragma to be sure that after type-class resolution the code will be inlined and hopefully strongly optimized, but we have to put the pragme in every single type class instance, which makes the code look ugly and is just impractival. So I would like to transform code like (this is just example, not a real-world problem solving code): {{{ class Foo a b where foo :: a -> b instance Foo Int String where foo = show {-# INLINE foo #-} instance Foo Int Int where foo = id {-# INLINE foo #-} instance Foo Int Float where foo = fromIntegral {-# INLINE foo #-} }}} into: {{{ class Foo a b where foo :: a -> b {-# INLINE foo #-} instance Foo Int String where foo = show instance Foo Int Int where foo = id instance Foo Int Float where foo = fromIntegral }}} I think it would be pretty easy to support such syntax and a lot of libraries would benefit from the design. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11393 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11393: Ability to define INLINE pragma for all instances of a given typeclass -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by danilo2: Old description:
Hello! I would like to request a feature that would allow me to define the `INLINE` pragma for all instances of a given type class. Currently when we are creating high-performance libraries, that strongly depend on type-level computations we are using a lot of typeclasses that we want to be cut-out during the compilation time. We can use the `INLINE` pragma to be sure that after type-class resolution the code will be inlined and hopefully strongly optimized, but we have to put the pragme in every single type class instance, which makes the code look ugly and is just impractival. So I would like to transform code like (this is just example, not a real-world problem solving code):
{{{
class Foo a b where foo :: a -> b
instance Foo Int String where foo = show {-# INLINE foo #-} instance Foo Int Int where foo = id {-# INLINE foo #-} instance Foo Int Float where foo = fromIntegral {-# INLINE foo #-}
}}}
into:
{{{
class Foo a b where foo :: a -> b {-# INLINE foo #-}
instance Foo Int String where foo = show instance Foo Int Int where foo = id instance Foo Int Float where foo = fromIntegral
}}}
I think it would be pretty easy to support such syntax and a lot of libraries would benefit from the design.
New description: Hello! I would like to request a feature that would allow me to define the `INLINE` pragma for all instances of a given type class. Currently when we are creating high-performance libraries, that strongly depend on type- level computations we are using a lot of typeclasses that we want to be cut-out during the compilation time. We can use the `INLINE` pragma to be sure that after type-class resolution the code will be inlined and hopefully strongly optimized, but we have to put the pragme in every single type class instance, which makes the code look ugly and is just impractival. So I would like to transform code like (this is just example, not a real-world problem solving code): {{{ class Foo a b where foo :: a -> b instance Foo Int String where foo = show {-# INLINE foo #-} instance Foo Int Int where foo = id {-# INLINE foo #-} instance Foo Int Float where foo = fromIntegral {-# INLINE foo #-} }}} into: {{{ class Foo a b where foo :: a -> b {-# INLINE foo #-} instance Foo Int String where foo = show instance Foo Int Int where foo = id instance Foo Int Float where foo = fromIntegral }}} I think it would be pretty easy to support such syntax and a lot of libraries would benefit from the design. Edit: As a small note - I've seen another way of dealing with the problem, namely mixing the pragmas with semicolons like that: {{{ class Foo a b where foo :: a -> b instance Foo Int String where foo = show ;{-# INLINE foo #-} instance Foo Int Int where foo = id ;{-# INLINE foo #-} instance Foo Int Float where foo = fromIntegral ;{-# INLINE foo #-} }}} But this is just another ugly work-around, not a nice solution. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11393#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11393: Ability to define INLINE pragma for all instances of a given typeclass -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by danilo2: Old description:
Hello! I would like to request a feature that would allow me to define the `INLINE` pragma for all instances of a given type class. Currently when we are creating high-performance libraries, that strongly depend on type-level computations we are using a lot of typeclasses that we want to be cut-out during the compilation time. We can use the `INLINE` pragma to be sure that after type-class resolution the code will be inlined and hopefully strongly optimized, but we have to put the pragme in every single type class instance, which makes the code look ugly and is just impractival. So I would like to transform code like (this is just example, not a real-world problem solving code):
{{{
class Foo a b where foo :: a -> b
instance Foo Int String where foo = show {-# INLINE foo #-} instance Foo Int Int where foo = id {-# INLINE foo #-} instance Foo Int Float where foo = fromIntegral {-# INLINE foo #-}
}}}
into:
{{{
class Foo a b where foo :: a -> b {-# INLINE foo #-}
instance Foo Int String where foo = show instance Foo Int Int where foo = id instance Foo Int Float where foo = fromIntegral
}}}
I think it would be pretty easy to support such syntax and a lot of libraries would benefit from the design.
Edit: As a small note - I've seen another way of dealing with the problem, namely mixing the pragmas with semicolons like that:
{{{
class Foo a b where foo :: a -> b
instance Foo Int String where foo = show ;{-# INLINE foo #-} instance Foo Int Int where foo = id ;{-# INLINE foo #-} instance Foo Int Float where foo = fromIntegral ;{-# INLINE foo #-}
}}}
But this is just another ugly work-around, not a nice solution.
New description: Hello! I would like to request a feature that would allow me to define the `INLINE` pragma for all instances of a given type class. Currently when we are creating high-performance libraries, that strongly depend on type- level computations we are using a lot of typeclasses that we want to be cut-out during the compilation time. We can use the `INLINE` pragma to be sure that after type-class resolution the code will be inlined and hopefully strongly optimized, but we have to put the pragme in every single type class instance, which makes the code look ugly and is just impractival. So I would like to transform code like (this is just example, not a real-world problem solving code): {{{ class Foo a b where foo :: a -> b instance Foo Int String where foo = show {-# INLINE foo #-} instance Foo Int Int where foo = id {-# INLINE foo #-} instance Foo Int Float where foo = fromIntegral {-# INLINE foo #-} }}} into: {{{ class Foo a b where foo :: a -> b {-# INLINE foo #-} instance Foo Int String where foo = show instance Foo Int Int where foo = id instance Foo Int Float where foo = fromIntegral }}} I think it would be pretty easy to support such syntax and a lot of libraries would benefit from the design. Unfortunatelly the proposed design does not nicely mix with default methods in classes, where we can use the pragma to denote that the default implementation should be inlined. But if there is no default method implementation GHC rejects the above example, so I think we can find a nice solution for the problem. Edit: As a small note - I've seen another way of dealing with the problem, namely mixing the pragmas with semicolons like that: {{{ class Foo a b where foo :: a -> b instance Foo Int String where foo = show ;{-# INLINE foo #-} instance Foo Int Int where foo = id ;{-# INLINE foo #-} instance Foo Int Float where foo = fromIntegral ;{-# INLINE foo #-} }}} But this is just another ugly work-around, not a nice solution. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11393#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11393: Ability to define INLINE pragma for all instances of a given typeclass -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I'm not sure this is a good plan. * What if someone writes a bug instance declaration? Having an `{-# INLINE #=}` pragma written somewhere else entirely might be highly unexpected. * The `{-# INLINE #-}` pragma in a class decl applies to the default method declaration in that class decl. We'd need a way to get the current behaviour (i.e. inline the default method, but no effect on instances that define their own method for `foo`). Seems doubtful to me. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11393#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC