1
1
mirror of https://github.com/google/ormolu.git synced 2024-11-23 22:27:16 +03:00

Implement signature declarations

This implements not everything, but the most common case: simple top-level
declarations for functions.
This commit is contained in:
mrkkrp 2019-05-16 16:29:34 +02:00 committed by Mark Karpov
parent 4e087ff0c3
commit 3553fc35d0
17 changed files with 146 additions and 4 deletions

View File

@ -4,9 +4,7 @@
data Foo a where
-- | 'Foo' is wonderful.
Foo
:: forall a b. ( Show a
, Eq b -- foo
)
:: forall a b. (Show a, Eq b) -- foo
=> -- bar
a
-> b

View File

@ -0,0 +1,14 @@
{-# LANGUAGE RankNTypes #-}
functionName
:: (C1, C2, C3, C4, C5)
=> a
-> b
-> ( forall a. (C6, C7)
=> LongDataTypeName
-> a
-> AnotherLongDataTypeName
-> b
-> c
)
-> (c -> d)
-> (a, b, c, d)

View File

@ -0,0 +1,16 @@
{-# LANGUAGE RankNTypes #-}
functionName
:: (C1, C2, C3, C4, C5)
=> a
-> b
-> (forall a.
(C6, C7)
=> LongDataTypeName
-> a
-> AnotherLongDataTypeName
-> b
-> c
)
-> (c -> d)
-> (a, b, c, d)

View File

@ -0,0 +1,10 @@
functionName
:: ( C1
, C2
, C3
)
=> a
-> b
-> c
-> d
-> (a, b, c, d)

View File

@ -0,0 +1,10 @@
functionName
:: ( C1
, C2
, C3
)
=> a
-> b
-> c
-> d
-> (a, b, c, d)

View File

@ -0,0 +1,7 @@
functionName
:: (C1, C2, C3)
=> a
-> b
-> c
-> d
-> (a, b, c, d)

View File

@ -0,0 +1,7 @@
functionName
:: (C1, C2, C3)
=> a
-> b
-> c
-> d
-> (a, b, c, d)

View File

@ -0,0 +1,3 @@
fun1 :: Def ('[Ref s (Stored Uint32), IBool] T.:-> IBool)
fun2 :: Def ('[Ref s (Stored Uint32), IBool] :-> IBool)

View File

@ -0,0 +1,2 @@
fun1 :: Def ('[ Ref s (Stored Uint32), IBool] 'T.:-> IBool)
fun2 :: Def ('[ Ref s (Stored Uint32), IBool] ':-> IBool)

View File

@ -0,0 +1,6 @@
longFunctionName
:: a
-> b
-> c
-> d
-> (a, b, c, d)

View File

@ -0,0 +1,6 @@
longFunctionName
:: a
-> b
-> c
-> d
-> (a, b, c, d)

View File

@ -0,0 +1,15 @@
functionName
:: (C1, C2, C3, C4, C5)
=> a
-> b
-> ( LongDataTypeName
AnotherLongDataTypeName
AnotherLongDataTypeName2
AnotherLongDataTypeName3
-> a
-> AnotherLongDataTypeName4
-> b
-> c
)
-> (c -> d)
-> (a, b, c, d)

View File

@ -0,0 +1,15 @@
functionName
:: (C1, C2, C3, C4, C5)
=> a
-> b
-> ( LongDataTypeName
AnotherLongDataTypeName
AnotherLongDataTypeName2
AnotherLongDataTypeName3
-> a
-> AnotherLongDataTypeName4
-> b
-> c
)
-> (c -> d)
-> (a, b, c, d)

View File

@ -60,6 +60,7 @@ library
, Ormolu.Printer.Meat.Common
, Ormolu.Printer.Meat.Declaration
, Ormolu.Printer.Meat.Declaration.Data
, Ormolu.Printer.Meat.Declaration.Signature
, Ormolu.Printer.Meat.Declaration.Type
, Ormolu.Printer.Meat.Declaration.TypeFamily
, Ormolu.Printer.Meat.ImportExport

View File

@ -11,12 +11,14 @@ where
import GHC
import Ormolu.Printer.Combinators
import Ormolu.Printer.Meat.Declaration.Data
import Ormolu.Printer.Meat.Declaration.Signature
import Ormolu.Printer.Meat.Declaration.Type
import Ormolu.Printer.Meat.Declaration.TypeFamily
p_hsDecl :: HsDecl GhcPs -> R ()
p_hsDecl = \case
TyClD x -> p_tyClDecl x
SigD x -> p_sigDecl x
_ -> error "this is not yet supported"
p_tyClDecl :: TyClDecl GhcPs -> R ()

View File

@ -0,0 +1,30 @@
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
-- | Type signature declarations.
module Ormolu.Printer.Meat.Declaration.Signature
( p_sigDecl )
where
import GHC
import Ormolu.Printer.Combinators
import Ormolu.Printer.Meat.Common
import Ormolu.Printer.Meat.Type
p_sigDecl :: Sig GhcPs -> R ()
p_sigDecl = \case
TypeSig names hswc -> line (p_typeSig names hswc)
_ -> error "Ormolu.Printer.Meat.Declaration.Signature: unimplemented signatures"
p_typeSig
:: [Located RdrName]
-> LHsSigWcType GhcPs
-> R ()
p_typeSig names HsWC {..} = do
spaceSep (located' p_rdrName) names
breakpoint
inci $ do
txt ":: "
relaxComments $ located (hsib_body hswc_body) p_hsType

View File

@ -24,7 +24,7 @@ p_hsType = \case
txt ". "
locatedVia Nothing t p_hsType
HsQualTy qs t -> do
locatedVia Nothing qs p_hsContext
located qs p_hsContext
breakpoint
txt "=> "
locatedVia Nothing t p_hsType