Implement support for inline signatures

This commit is contained in:
mrkkrp 2019-06-09 13:40:12 +02:00 committed by Mark Karpov
parent a8235f7164
commit 046f14e7e5
8 changed files with 102 additions and 1 deletions

View File

@ -0,0 +1,11 @@
foo :: Int -> Int
foo = id
{-# INLINE foo #-}
{-# INLINE [2] bar #-}
bar :: Int -> Int
bar = id
baz :: Int -> Int
baz = id
{-# INLINE [~2] baz #-}

View File

@ -0,0 +1,13 @@
foo :: Int -> Int
foo = id
{-# INLINE foo #-}
{-# INLINE [2] bar #-}
bar :: Int -> Int
bar = id
baz :: Int -> Int
baz = id
{-# INLINE [~2] baz #-}

View File

@ -0,0 +1,11 @@
foo :: Int -> Int
foo = id
{-# INLINEABLE foo #-}
{-# INLINEABLE [2] bar #-}
bar :: Int -> Int
bar = id
baz :: Int -> Int
baz = id
{-# INLINEABLE [~2] baz #-}

View File

@ -0,0 +1,13 @@
foo :: Int -> Int
foo = id
{-# INLINEABLE foo #-}
{-# INLINEABLE [2] bar #-}
bar :: Int -> Int
bar = id
baz :: Int -> Int
baz = id
{-# INLINEABLE [~2] baz #-}

View File

@ -0,0 +1,11 @@
foo :: Int -> Int
foo = id
{-# NOINLINE foo #-}
{-# NOINLINE [2] bar #-}
bar :: Int -> Int
bar = id
baz :: Int -> Int
baz = id
{-# NOINLINE [~2] baz #-}

View File

@ -0,0 +1,13 @@
foo :: Int -> Int
foo = id
{-# NOINLINE foo #-}
{-# NOINLINE [2] bar #-}
bar :: Int -> Int
bar = id
baz :: Int -> Int
baz = id
{-# NOINLINE [~2] baz #-}

View File

@ -10,7 +10,7 @@ module Ormolu.Printer.Meat.Declaration.Signature
)
where
import BasicTypes (Fixity (..))
import BasicTypes
import Control.Monad
import GHC
import Ormolu.Printer.Combinators
@ -26,6 +26,7 @@ p_sigDecl' = \case
TypeSig NoExt names hswc -> p_typeSig names hswc
ClassOpSig NoExt def names hsib -> p_classOpSig def names hsib
FixSig NoExt sig -> p_fixSig sig
InlineSig NoExt name inlinePragma -> p_inlineSig name inlinePragma
_ -> notImplemented "certain types of signature declarations"
p_typeSig
@ -63,3 +64,27 @@ p_fixSig = \case
space
sequence_ (withSep comma p_rdrName names)
XFixitySig NoExt -> notImplemented "XFixitySig"
p_inlineSig
:: Located RdrName -- ^ Name
-> InlinePragma -- ^ Inline pragma specification
-> R ()
p_inlineSig name InlinePragma {..} = do
txt "{-# "
txt $ case inl_inline of
Inline -> "INLINE"
Inlinable -> "INLINEABLE"
NoInline -> "NOINLINE"
NoUserInline -> notImplemented "NoUserInline"
space
case inl_act of
NeverActive -> return ()
AlwaysActive -> return ()
ActiveBefore _ n -> do
brackets (txt "~" >> atom n)
space
ActiveAfter _ n -> do
brackets (atom n)
space
p_rdrName name
txt " #-}"

View File

@ -66,4 +66,8 @@ separatedDecls
-> Bool
separatedDecls (SigD NoExt (TypeSig NoExt (n:_) _)) (ValD NoExt (FunBind NoExt n' _ _ _)) =
unL n /= unL n'
separatedDecls (ValD NoExt (FunBind NoExt n _ _ _)) (SigD NoExt (InlineSig NoExt n' _)) =
unL n /= unL n'
separatedDecls (SigD NoExt (InlineSig NoExt n _)) (SigD NoExt (TypeSig NoExt (n':_) _)) =
unL n /= unL n'
separatedDecls _ _ = True