Fix forall type signature layouting

pull/35/head
Lennart Spitzner 2017-05-18 14:18:10 +02:00
parent 296629b96c
commit 8b7b1334e2
2 changed files with 38 additions and 6 deletions

View File

@ -209,9 +209,32 @@ test052 :: lkasdlkjalsdjlakjsdlkjasldkjalskdjlkajsd
#test forall oneliner #test forall oneliner
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
--this comment is necessary for whatever reason..
func :: forall (a :: *) b . a -> b func :: forall (a :: *) b . a -> b
#test forall context multiline
{-# LANGUAGE ScopedTypeVariables #-}
func
:: forall m
. Foo
=> ColMap2
-> ColInfo
-> ColInfo
-> ColInfo
-> ColInfo
-> m ()
#test forall no-context multiline
{-# LANGUAGE ScopedTypeVariables #-}
func
:: forall m
. ColMap2
-> ColInfo
-> ColInfo
-> ColInfo
-> ColInfo
-> ColInfo
-> m ()
#test language pragma issue #test language pragma issue
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
func :: forall (a :: *) b . a -> b func :: forall (a :: *) b . a -> b

View File

@ -105,7 +105,7 @@ layoutType ltype@(L _ typ) = docWrapNode ltype $ case typ of
in docSeq ([open]++tyVarDocLineList++[close]) in docSeq ([open]++tyVarDocLineList++[close])
, docForceSingleline contextDoc , docForceSingleline contextDoc
, docLit $ Text.pack " => " , docLit $ Text.pack " => "
, typeDoc , docForceSingleline typeDoc
] ]
-- :: forall a b c -- :: forall a b c
-- . (Foo a b c) -- . (Foo a b c)
@ -117,7 +117,7 @@ layoutType ltype@(L _ typ) = docWrapNode ltype $ case typ of
[ docCols ColTyOpPrefix [ docCols ColTyOpPrefix
[ docWrapNodeRest ltype $ docLit $ Text.pack " . " [ docWrapNodeRest ltype $ docLit $ Text.pack " . "
, docAddBaseY (BrIndentSpecial 3) , docAddBaseY (BrIndentSpecial 3)
$ docForceSingleline contextDoc $ contextDoc
] ]
, docCols ColTyOpPrefix , docCols ColTyOpPrefix
[ docLit $ Text.pack "=> " [ docLit $ Text.pack "=> "
@ -133,6 +133,9 @@ layoutType ltype@(L _ typ) = docWrapNode ltype $ case typ of
(L _ (KindedTyVar lrdrName kind)) -> do (L _ (KindedTyVar lrdrName kind)) -> do
d <- layoutType kind d <- layoutType kind
return $ (lrdrNameToText lrdrName, Just $ return d) return $ (lrdrNameToText lrdrName, Just $ return d)
let maybeForceML = case typ2 of
(L _ HsFunTy{}) -> docForceMultiline
_ -> id
let let
tyVarDocLineList = tyVarDocs >>= \case tyVarDocLineList = tyVarDocs >>= \case
(tname, Nothing) -> [docLit $ Text.pack " " <> tname] (tname, Nothing) -> [docLit $ Text.pack " " <> tname]
@ -143,6 +146,7 @@ layoutType ltype@(L _ typ) = docWrapNode ltype $ case typ of
, docLit $ Text.pack ")" , docLit $ Text.pack ")"
] ]
docAlt docAlt
-- forall x . x
[ docSeq [ docSeq
[ if null bndrs [ if null bndrs
then docEmpty then docEmpty
@ -150,15 +154,20 @@ layoutType ltype@(L _ typ) = docWrapNode ltype $ case typ of
open = docLit $ Text.pack "forall" open = docLit $ Text.pack "forall"
close = docLit $ Text.pack " . " close = docLit $ Text.pack " . "
in docSeq ([open]++tyVarDocLineList++[close]) in docSeq ([open]++tyVarDocLineList++[close])
, return typeDoc , docForceSingleline $ return $ typeDoc
] ]
-- :: forall x
-- . x
, docPar , docPar
(docSeq $ docLit (Text.pack "forall") : tyVarDocLineList) (docSeq $ docLit (Text.pack "forall") : tyVarDocLineList)
( docCols ColTyOpPrefix ( docCols ColTyOpPrefix
[ docWrapNodeRest ltype $ docLit $ Text.pack ". " [ docWrapNodeRest ltype $ docLit $ Text.pack ". "
, return typeDoc , maybeForceML $ return typeDoc
] ]
) )
-- :: forall
-- (x :: *)
-- . x
, docPar , docPar
(docLit (Text.pack "forall")) (docLit (Text.pack "forall"))
(docLines (docLines
@ -179,7 +188,7 @@ layoutType ltype@(L _ typ) = docWrapNode ltype $ case typ of
) )
++[ docCols ColTyOpPrefix ++[ docCols ColTyOpPrefix
[ docWrapNodeRest ltype $ docLit $ Text.pack ". " [ docWrapNodeRest ltype $ docLit $ Text.pack ". "
, return typeDoc , maybeForceML $ return typeDoc
] ]
] ]
) )