Add support for Implicit Params
I don't know what I'm doing, but it type checks Closes #246pull/247/head
parent
988d5b4353
commit
a79b5e1a4b
|
@ -140,3 +140,19 @@ foo = #bar
|
|||
#test applied and composed label
|
||||
{-# LANGUAGE OverloadedLabels #-}
|
||||
foo = #bar . #baz $ fmap #foo xs
|
||||
|
||||
###############################################################################
|
||||
## ImplicitParams
|
||||
|
||||
#test IP usage
|
||||
{-# LANGUAGE ImplicitParams #-}
|
||||
foo = ?bar
|
||||
|
||||
#test IP binding
|
||||
{-# LANGUAGE ImplicitParams #-}
|
||||
foo = let ?bar = Foo in value
|
||||
|
||||
#test IP type signature
|
||||
{-# LANGUAGE ImplicitParams #-}
|
||||
foo :: (?bar::Bool) => ()
|
||||
foo = ()
|
|
@ -32,6 +32,7 @@ import GHC ( runGhc
|
|||
, AnnKeywordId(..)
|
||||
)
|
||||
import SrcLoc ( SrcSpan, noSrcSpan, Located , getLoc, unLoc )
|
||||
import qualified FastString
|
||||
import HsSyn
|
||||
#if MIN_VERSION_ghc(8,6,0)
|
||||
import HsExtension (NoExt (..))
|
||||
|
@ -231,6 +232,23 @@ layoutBind lbind@(L _ bind) = case bind of
|
|||
hasComments
|
||||
_ -> Right <$> unknownNodeError "" lbind
|
||||
|
||||
layoutIPBind :: ToBriDoc IPBind
|
||||
layoutIPBind lipbind@(L _ bind) = case bind of
|
||||
#if MIN_VERSION_ghc(8,6,0) /* ghc-8.6 */
|
||||
XIPBind{} -> unknownNodeError "XIPBind" lipbind
|
||||
IPBind _ (Right _) _ -> error "unreachable"
|
||||
IPBind _ (Left (L _ (HsIPName name))) expr -> do
|
||||
#else
|
||||
IPBind (Right _) _ -> error "unreachable"
|
||||
IPBind (Left (L _ (HsIPName name))) expr -> do
|
||||
#endif
|
||||
ipName <- docLit $ Text.pack $ '?' : FastString.unpackFS name
|
||||
binderDoc <- docLit $ Text.pack "="
|
||||
exprDoc <- layoutExpr expr
|
||||
hasComments <- hasAnyCommentsBelow lipbind
|
||||
layoutPatternBindFinal Nothing binderDoc (Just ipName) [([], exprDoc, expr)] Nothing hasComments
|
||||
|
||||
|
||||
data BagBindOrSig = BagBind (LHsBindLR GhcPs GhcPs)
|
||||
| BagSig (LSig GhcPs)
|
||||
|
||||
|
@ -268,8 +286,14 @@ layoutLocalBinds lbinds@(L _ binds) = case binds of
|
|||
Just . (: []) <$> unknownNodeError "HsValBinds ValBindsOut{}"
|
||||
(L noSrcSpan x)
|
||||
#endif
|
||||
x@(HsIPBinds{}) ->
|
||||
Just . (: []) <$> unknownNodeError "HsIPBinds" (L noSrcSpan x)
|
||||
#if MIN_VERSION_ghc(8,6,0) /* ghc-8.6 */
|
||||
x@(HsIPBinds _ XHsIPBinds{}) ->
|
||||
Just . (: []) <$> unknownNodeError "XHsIPBinds" (L noSrcSpan x)
|
||||
HsIPBinds _ (IPBinds _ bb) ->
|
||||
#else
|
||||
HsIPBinds (IPBinds bb _) ->
|
||||
#endif
|
||||
Just <$> mapM layoutIPBind bb
|
||||
EmptyLocalBinds{} -> return $ Nothing
|
||||
|
||||
-- TODO: we don't need the `LHsExpr GhcPs` anymore, now that there is
|
||||
|
|
|
@ -64,9 +64,13 @@ layoutExpr lexpr@(L _ expr) = do
|
|||
#endif
|
||||
let label = FastString.unpackFS name
|
||||
in docLit . Text.pack $ '#' : label
|
||||
HsIPVar{} -> do
|
||||
-- TODO
|
||||
briDocByExactInlineOnly "HsOverLabel{}" lexpr
|
||||
#if MIN_VERSION_ghc(8,6,0) /* ghc-8.6 */
|
||||
HsIPVar _ext (HsIPName name) ->
|
||||
#else
|
||||
HsIPVar (HsIPName name) ->
|
||||
#endif
|
||||
let label = FastString.unpackFS name
|
||||
in docLit . Text.pack $ '?' : label
|
||||
#if MIN_VERSION_ghc(8,6,0) /* ghc-8.6 */
|
||||
HsOverLit _ olit -> do
|
||||
#else
|
||||
|
|
Loading…
Reference in New Issue