Support building DataDecl with 8.0.2
parent
9971e3905d
commit
aeaa043e99
|
@ -1,3 +1,4 @@
|
||||||
|
{-# LANGUAGE CPP #-}
|
||||||
{-# LANGUAGE DataKinds #-}
|
{-# LANGUAGE DataKinds #-}
|
||||||
{-# LANGUAGE TypeApplications #-}
|
{-# LANGUAGE TypeApplications #-}
|
||||||
{-# LANGUAGE KindSignatures #-}
|
{-# LANGUAGE KindSignatures #-}
|
||||||
|
@ -171,6 +172,7 @@ createDerivingPar
|
||||||
:: HsDeriving GhcPs -> ToBriDocM BriDocNumbered -> ToBriDocM BriDocNumbered
|
:: HsDeriving GhcPs -> ToBriDocM BriDocNumbered -> ToBriDocM BriDocNumbered
|
||||||
createDerivingPar derivs mainDoc = do
|
createDerivingPar derivs mainDoc = do
|
||||||
case derivs of
|
case derivs of
|
||||||
|
#if MIN_VERSION_ghc(8,2,0) /* ghc-8.2 */
|
||||||
(L _ []) -> docLines [mainDoc]
|
(L _ []) -> docLines [mainDoc]
|
||||||
(L _ types) ->
|
(L _ types) ->
|
||||||
docPar mainDoc
|
docPar mainDoc
|
||||||
|
@ -179,13 +181,26 @@ createDerivingPar derivs mainDoc = do
|
||||||
$ docWrapNode derivs
|
$ docWrapNode derivs
|
||||||
$ derivingClauseDoc
|
$ derivingClauseDoc
|
||||||
<$> types
|
<$> types
|
||||||
|
#else
|
||||||
|
Nothing -> docLines [mainDoc]
|
||||||
|
Just types ->
|
||||||
|
docPar mainDoc
|
||||||
|
$ docEnsureIndent BrIndentRegular
|
||||||
|
$ derivingClauseDoc types
|
||||||
|
#endif
|
||||||
|
|
||||||
|
#if MIN_VERSION_ghc(8,2,0) /* ghc-8.2 */
|
||||||
derivingClauseDoc :: LHsDerivingClause GhcPs -> ToBriDocM BriDocNumbered
|
derivingClauseDoc :: LHsDerivingClause GhcPs -> ToBriDocM BriDocNumbered
|
||||||
|
#else
|
||||||
|
derivingClauseDoc :: Located [LHsSigType GhcPs] -> ToBriDocM BriDocNumbered
|
||||||
|
#endif
|
||||||
#if MIN_VERSION_ghc(8,6,0) /* ghc-8.6 */
|
#if MIN_VERSION_ghc(8,6,0) /* ghc-8.6 */
|
||||||
derivingClauseDoc (L _ (XHsDerivingClause ext)) = absurdExt ext
|
derivingClauseDoc (L _ (XHsDerivingClause ext)) = absurdExt ext
|
||||||
derivingClauseDoc (L _ (HsDerivingClause _ext mStrategy types)) = case types of
|
derivingClauseDoc (L _ (HsDerivingClause _ext mStrategy types)) = case types of
|
||||||
#else
|
#elif MIN_VERSION_ghc(8,2,0) /* ghc-8.2 */
|
||||||
derivingClauseDoc (L _ (HsDerivingClause mStrategy types)) = case types of
|
derivingClauseDoc (L _ (HsDerivingClause mStrategy types)) = case types of
|
||||||
|
#else
|
||||||
|
derivingClauseDoc types = case types of
|
||||||
#endif
|
#endif
|
||||||
(L _ []) -> docSeq []
|
(L _ []) -> docSeq []
|
||||||
(L _ ts) ->
|
(L _ ts) ->
|
||||||
|
@ -193,7 +208,11 @@ derivingClauseDoc (L _ (HsDerivingClause mStrategy types)) = case types of
|
||||||
tsLength = length ts
|
tsLength = length ts
|
||||||
whenMoreThan1Type val =
|
whenMoreThan1Type val =
|
||||||
if tsLength > 1 then docLit (Text.pack val) else docLit (Text.pack "")
|
if tsLength > 1 then docLit (Text.pack val) else docLit (Text.pack "")
|
||||||
|
#if MIN_VERSION_ghc(8,2,0) /* ghc-8.2 */
|
||||||
(lhsStrategy, rhsStrategy) = maybe (docEmpty, docEmpty) strategyLeftRight mStrategy
|
(lhsStrategy, rhsStrategy) = maybe (docEmpty, docEmpty) strategyLeftRight mStrategy
|
||||||
|
#else
|
||||||
|
(lhsStrategy, rhsStrategy) = (docEmpty, docEmpty)
|
||||||
|
#endif
|
||||||
in
|
in
|
||||||
docSeq
|
docSeq
|
||||||
[ docDeriving
|
[ docDeriving
|
||||||
|
@ -207,12 +226,15 @@ derivingClauseDoc (L _ (HsDerivingClause mStrategy types)) = case types of
|
||||||
#if MIN_VERSION_ghc(8,6,0) /* ghc-8.6 */
|
#if MIN_VERSION_ghc(8,6,0) /* ghc-8.6 */
|
||||||
HsIB _ t -> layoutType t
|
HsIB _ t -> layoutType t
|
||||||
XHsImplicitBndrs x -> absurdExt x
|
XHsImplicitBndrs x -> absurdExt x
|
||||||
#else
|
#elif MIN_VERSION_ghc(8,2,0) /* ghc-8.2 */
|
||||||
HsIB _ t _ -> layoutType t
|
HsIB _ t _ -> layoutType t
|
||||||
|
#else
|
||||||
|
HsIB _ t -> layoutType t
|
||||||
#endif
|
#endif
|
||||||
, whenMoreThan1Type ")"
|
, whenMoreThan1Type ")"
|
||||||
, rhsStrategy
|
, rhsStrategy
|
||||||
]
|
]
|
||||||
|
#if MIN_VERSION_ghc(8,2,0) /* ghc-8.6 */
|
||||||
where
|
where
|
||||||
strategyLeftRight = \case
|
strategyLeftRight = \case
|
||||||
(L _ StockStrategy ) -> (docLit $ Text.pack " stock", docEmpty)
|
(L _ StockStrategy ) -> (docLit $ Text.pack " stock", docEmpty)
|
||||||
|
@ -230,6 +252,7 @@ derivingClauseDoc (L _ (HsDerivingClause mStrategy types)) = case types of
|
||||||
XHsImplicitBndrs ext -> absurdExt ext
|
XHsImplicitBndrs ext -> absurdExt ext
|
||||||
)
|
)
|
||||||
#endif
|
#endif
|
||||||
|
#endif
|
||||||
|
|
||||||
docDeriving :: ToBriDocM BriDocNumbered
|
docDeriving :: ToBriDocM BriDocNumbered
|
||||||
docDeriving = docLit $ Text.pack "deriving"
|
docDeriving = docLit $ Text.pack "deriving"
|
||||||
|
|
|
@ -743,8 +743,10 @@ layoutTyCl ltycl@(L _loc tycl) = case tycl of
|
||||||
$ layoutSynDecl isInfix wrapNodeRest name (hsq_explicit vars) typ
|
$ layoutSynDecl isInfix wrapNodeRest name (hsq_explicit vars) typ
|
||||||
#if MIN_VERSION_ghc(8,6,0)
|
#if MIN_VERSION_ghc(8,6,0)
|
||||||
DataDecl _ext name tyVars _ dataDefn ->
|
DataDecl _ext name tyVars _ dataDefn ->
|
||||||
#else
|
#elif MIN_VERSION_ghc(8,2,0)
|
||||||
DataDecl name tyVars _ dataDefn _ _ ->
|
DataDecl name tyVars _ dataDefn _ _ ->
|
||||||
|
#else
|
||||||
|
DataDecl name tyVars dataDefn _ _ ->
|
||||||
#endif
|
#endif
|
||||||
docWrapNodePrior ltycl $
|
docWrapNodePrior ltycl $
|
||||||
layoutDataDecl ltycl name tyVars dataDefn
|
layoutDataDecl ltycl name tyVars dataDefn
|
||||||
|
|
Loading…
Reference in New Issue