{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ViewPatterns #-}
module Language.Haskell.Brittany.Internal.Layouters.Pattern
( layoutPat
, colsWrapPat
)
where
#include "prelude.inc"
import Language.Haskell.Brittany.Internal.Types
import Language.Haskell.Brittany.Internal.LayouterBasics
import GHC ( Located
, runGhc
, GenLocated(L)
, moduleNameString
, ol_val
)
import qualified GHC
#if MIN_VERSION_ghc(8,10,1) /* ghc-8.10.1 */
import GHC.Hs
#else
import HsSyn
#endif
import Name
import BasicTypes
import {-# SOURCE #-} Language.Haskell.Brittany.Internal.Layouters.Expr
import Language.Haskell.Brittany.Internal.Layouters.Type
layoutPat :: LPat GhcPs -> ToBriDocM (Seq BriDocNumbered)
layoutPat :: LPat GhcPs -> ToBriDocM (Seq BriDocNumbered)
layoutPat (LPat GhcPs -> Located (SrcSpanLess (Located (Pat GhcPs)))
forall a. HasSrcSpan a => a -> Located (SrcSpanLess a)
ghcDL -> lpat :: Located (SrcSpanLess (Located (Pat GhcPs)))
lpat@(L SrcSpan
_ SrcSpanLess (Located (Pat GhcPs))
pat)) = Located (Pat GhcPs)
-> ToBriDocM (Seq BriDocNumbered) -> ToBriDocM (Seq BriDocNumbered)
forall a ast. (DocWrapable a, Data ast) => Located ast -> a -> a
docWrapNode Located (Pat GhcPs)
Located (SrcSpanLess (Located (Pat GhcPs)))
lpat (ToBriDocM (Seq BriDocNumbered) -> ToBriDocM (Seq BriDocNumbered))
-> ToBriDocM (Seq BriDocNumbered) -> ToBriDocM (Seq BriDocNumbered)
forall a b. (a -> b) -> a -> b
$ case SrcSpanLess (Located (Pat GhcPs))
pat of
WildPat _ -> (BriDocNumbered -> Seq BriDocNumbered)
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> ToBriDocM (Seq BriDocNumbered)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap BriDocNumbered -> Seq BriDocNumbered
forall a. a -> Seq a
Seq.singleton (MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> ToBriDocM (Seq BriDocNumbered))
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> ToBriDocM (Seq BriDocNumbered)
forall a b. (a -> b) -> a -> b
$ Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docLit (Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall a b. (a -> b) -> a -> b
$ String -> Text
Text.pack String
"_"
VarPat _ n ->
(BriDocNumbered -> Seq BriDocNumbered)
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> ToBriDocM (Seq BriDocNumbered)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap BriDocNumbered -> Seq BriDocNumbered
forall a. a -> Seq a
Seq.singleton (MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> ToBriDocM (Seq BriDocNumbered))
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> ToBriDocM (Seq BriDocNumbered)
forall a b. (a -> b) -> a -> b
$ Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docLit (Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall a b. (a -> b) -> a -> b
$ GenLocated SrcSpan RdrName -> Text
forall l. GenLocated l RdrName -> Text
lrdrNameToText Located (IdP GhcPs)
GenLocated SrcSpan RdrName
n
LitPat _ lit ->
(BriDocNumbered -> Seq BriDocNumbered)
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> ToBriDocM (Seq BriDocNumbered)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap BriDocNumbered -> Seq BriDocNumbered
forall a. a -> Seq a
Seq.singleton (MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> ToBriDocM (Seq BriDocNumbered))
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> ToBriDocM (Seq BriDocNumbered)
forall a b. (a -> b) -> a -> b
$ BriDocFInt
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall (m :: * -> *).
MonadMultiState NodeAllocIndex m =>
BriDocFInt -> m BriDocNumbered
allocateNode (BriDocFInt
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> BriDocFInt
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall a b. (a -> b) -> a -> b
$ HsLit GhcPs -> BriDocFInt
litBriDoc HsLit GhcPs
lit
#if MIN_VERSION_ghc(8,8,0) /* ghc-8.8 */
ParPat _ inner -> do
#else
ParPat _ inner -> do
#endif
BriDocNumbered
left <- Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docLit (Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall a b. (a -> b) -> a -> b
$ String -> Text
Text.pack String
"("
BriDocNumbered
right <- Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docLit (Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall a b. (a -> b) -> a -> b
$ String -> Text
Text.pack String
")"
BriDocNumbered
innerDocs <- Seq BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
colsWrapPat (Seq BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> ToBriDocM (Seq BriDocNumbered)
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< LPat GhcPs -> ToBriDocM (Seq BriDocNumbered)
layoutPat LPat GhcPs
inner
Seq BriDocNumbered -> ToBriDocM (Seq BriDocNumbered)
forall (m :: * -> *) a. Monad m => a -> m a
return (Seq BriDocNumbered -> ToBriDocM (Seq BriDocNumbered))
-> Seq BriDocNumbered -> ToBriDocM (Seq BriDocNumbered)
forall a b. (a -> b) -> a -> b
$ Seq BriDocNumbered
forall a. Seq a
Seq.empty Seq BriDocNumbered -> BriDocNumbered -> Seq BriDocNumbered
forall a. Seq a -> a -> Seq a
Seq.|> BriDocNumbered
left Seq BriDocNumbered -> BriDocNumbered -> Seq BriDocNumbered
forall a. Seq a -> a -> Seq a
Seq.|> BriDocNumbered
innerDocs Seq BriDocNumbered -> BriDocNumbered -> Seq BriDocNumbered
forall a. Seq a -> a -> Seq a
Seq.|> BriDocNumbered
right
ConPatIn lname (PrefixCon args) -> do
Text
nameDoc <- GenLocated SrcSpan RdrName
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
Text
forall (m :: * -> *).
(MonadMultiReader Config m, MonadMultiReader Anns m) =>
GenLocated SrcSpan RdrName -> m Text
lrdrNameToTextAnn Located (IdP GhcPs)
GenLocated SrcSpan RdrName
lname
[Seq BriDocNumbered]
argDocs <- LPat GhcPs -> ToBriDocM (Seq BriDocNumbered)
Located (Pat GhcPs) -> ToBriDocM (Seq BriDocNumbered)
layoutPat (Located (Pat GhcPs) -> ToBriDocM (Seq BriDocNumbered))
-> [Located (Pat GhcPs)]
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
[Seq BriDocNumbered]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
`mapM` [LPat GhcPs]
[Located (Pat GhcPs)]
args
if [Seq BriDocNumbered] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Seq BriDocNumbered]
argDocs
then BriDocNumbered -> Seq BriDocNumbered
forall (m :: * -> *) a. Monad m => a -> m a
return (BriDocNumbered -> Seq BriDocNumbered)
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> ToBriDocM (Seq BriDocNumbered)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docLit Text
nameDoc
else do
BriDocNumbered
x1 <- MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
appSep (Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docLit Text
nameDoc)
Seq BriDocNumbered
xR <- ([BriDocNumbered] -> Seq BriDocNumbered)
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
[BriDocNumbered]
-> ToBriDocM (Seq BriDocNumbered)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [BriDocNumbered] -> Seq BriDocNumbered
forall a. [a] -> Seq a
Seq.fromList
(MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
[BriDocNumbered]
-> ToBriDocM (Seq BriDocNumbered))
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
[BriDocNumbered]
-> ToBriDocM (Seq BriDocNumbered)
forall a b. (a -> b) -> a -> b
$ [MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered]
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
[BriDocNumbered]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence
([MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered]
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
[BriDocNumbered])
-> [MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered]
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
[BriDocNumbered]
forall a b. (a -> b) -> a -> b
$ [MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered]
-> [MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered]
spacifyDocs
([MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered]
-> [MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered])
-> [MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered]
-> [MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered]
forall a b. (a -> b) -> a -> b
$ (Seq BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> [Seq BriDocNumbered]
-> [MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Seq BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
colsWrapPat [Seq BriDocNumbered]
argDocs
Seq BriDocNumbered -> ToBriDocM (Seq BriDocNumbered)
forall (m :: * -> *) a. Monad m => a -> m a
return (Seq BriDocNumbered -> ToBriDocM (Seq BriDocNumbered))
-> Seq BriDocNumbered -> ToBriDocM (Seq BriDocNumbered)
forall a b. (a -> b) -> a -> b
$ BriDocNumbered
x1 BriDocNumbered -> Seq BriDocNumbered -> Seq BriDocNumbered
forall a. a -> Seq a -> Seq a
Seq.<| Seq BriDocNumbered
xR
ConPatIn lname (InfixCon left right) -> do
Text
nameDoc <- GenLocated SrcSpan RdrName
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
Text
forall (m :: * -> *).
(MonadMultiReader Config m, MonadMultiReader Anns m) =>
GenLocated SrcSpan RdrName -> m Text
lrdrNameToTextAnn Located (IdP GhcPs)
GenLocated SrcSpan RdrName
lname
BriDocNumbered
leftDoc <- MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
appSep (MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> (Seq BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> Seq BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Seq BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
colsWrapPat (Seq BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> ToBriDocM (Seq BriDocNumbered)
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< LPat GhcPs -> ToBriDocM (Seq BriDocNumbered)
layoutPat LPat GhcPs
left
BriDocNumbered
rightDoc <- Seq BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
colsWrapPat (Seq BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> ToBriDocM (Seq BriDocNumbered)
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< LPat GhcPs -> ToBriDocM (Seq BriDocNumbered)
layoutPat LPat GhcPs
right
BriDocNumbered
middle <- MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
appSep (MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall a b. (a -> b) -> a -> b
$ Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docLit Text
nameDoc
Seq BriDocNumbered -> ToBriDocM (Seq BriDocNumbered)
forall (m :: * -> *) a. Monad m => a -> m a
return (Seq BriDocNumbered -> ToBriDocM (Seq BriDocNumbered))
-> Seq BriDocNumbered -> ToBriDocM (Seq BriDocNumbered)
forall a b. (a -> b) -> a -> b
$ Seq BriDocNumbered
forall a. Seq a
Seq.empty Seq BriDocNumbered -> BriDocNumbered -> Seq BriDocNumbered
forall a. Seq a -> a -> Seq a
Seq.|> BriDocNumbered
leftDoc Seq BriDocNumbered -> BriDocNumbered -> Seq BriDocNumbered
forall a. Seq a -> a -> Seq a
Seq.|> BriDocNumbered
middle Seq BriDocNumbered -> BriDocNumbered -> Seq BriDocNumbered
forall a. Seq a -> a -> Seq a
Seq.|> BriDocNumbered
rightDoc
ConPatIn lname (RecCon (HsRecFields [] Nothing)) -> do
let t :: Text
t = GenLocated SrcSpan RdrName -> Text
forall l. GenLocated l RdrName -> Text
lrdrNameToText Located (IdP GhcPs)
GenLocated SrcSpan RdrName
lname
(BriDocNumbered -> Seq BriDocNumbered)
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> ToBriDocM (Seq BriDocNumbered)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap BriDocNumbered -> Seq BriDocNumbered
forall a. a -> Seq a
Seq.singleton (MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> ToBriDocM (Seq BriDocNumbered))
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> ToBriDocM (Seq BriDocNumbered)
forall a b. (a -> b) -> a -> b
$ Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docLit (Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall a b. (a -> b) -> a -> b
$ Text
t Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
Text.pack String
"{}"
ConPatIn lname (RecCon (HsRecFields fs@(_:_) Nothing)) -> do
let t :: Text
t = GenLocated SrcSpan RdrName -> Text
forall l. GenLocated l RdrName -> Text
lrdrNameToText Located (IdP GhcPs)
GenLocated SrcSpan RdrName
lname
[(Text, Maybe (ToBriDocM (Seq BriDocNumbered)))]
fds <- [LHsRecField GhcPs (LPat GhcPs)]
[GenLocated
SrcSpan (HsRecField' (FieldOcc GhcPs) (Located (Pat GhcPs)))]
fs [GenLocated
SrcSpan (HsRecField' (FieldOcc GhcPs) (Located (Pat GhcPs)))]
-> (GenLocated
SrcSpan (HsRecField' (FieldOcc GhcPs) (Located (Pat GhcPs)))
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
(Text, Maybe (ToBriDocM (Seq BriDocNumbered))))
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
[(Text, Maybe (ToBriDocM (Seq BriDocNumbered)))]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
`forM` \(L SrcSpan
_ (HsRecField (L SrcSpan
_ FieldOcc GhcPs
fieldOcc) Located (Pat GhcPs)
fPat Bool
pun)) -> do
let FieldOcc XCFieldOcc GhcPs
_ GenLocated SrcSpan RdrName
lnameF = FieldOcc GhcPs
fieldOcc
Maybe (ToBriDocM (Seq BriDocNumbered))
fExpDoc <- if Bool
pun
then Maybe (ToBriDocM (Seq BriDocNumbered))
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
(Maybe (ToBriDocM (Seq BriDocNumbered)))
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe (ToBriDocM (Seq BriDocNumbered))
forall a. Maybe a
Nothing
else ToBriDocM (Seq BriDocNumbered)
-> Maybe (ToBriDocM (Seq BriDocNumbered))
forall a. a -> Maybe a
Just (ToBriDocM (Seq BriDocNumbered)
-> Maybe (ToBriDocM (Seq BriDocNumbered)))
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
(ToBriDocM (Seq BriDocNumbered))
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
(Maybe (ToBriDocM (Seq BriDocNumbered)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Located (Pat GhcPs) -> ToBriDocM (Seq BriDocNumbered))
-> Located (Pat GhcPs)
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
(ToBriDocM (Seq BriDocNumbered))
forall (m :: * -> *) x y. Monad m => (x -> m y) -> x -> m (m y)
docSharedWrapper LPat GhcPs -> ToBriDocM (Seq BriDocNumbered)
Located (Pat GhcPs) -> ToBriDocM (Seq BriDocNumbered)
layoutPat Located (Pat GhcPs)
fPat
(Text, Maybe (ToBriDocM (Seq BriDocNumbered)))
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
(Text, Maybe (ToBriDocM (Seq BriDocNumbered)))
forall (m :: * -> *) a. Monad m => a -> m a
return (GenLocated SrcSpan RdrName -> Text
forall l. GenLocated l RdrName -> Text
lrdrNameToText GenLocated SrcSpan RdrName
lnameF, Maybe (ToBriDocM (Seq BriDocNumbered))
fExpDoc)
BriDocNumbered -> Seq BriDocNumbered
forall a. a -> Seq a
Seq.singleton (BriDocNumbered -> Seq BriDocNumbered)
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> ToBriDocM (Seq BriDocNumbered)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered]
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docSeq
[ MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
appSep (MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall a b. (a -> b) -> a -> b
$ Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docLit Text
t
, MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
appSep (MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall a b. (a -> b) -> a -> b
$ Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docLit (Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall a b. (a -> b) -> a -> b
$ String -> Text
Text.pack String
"{"
, [MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered]
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docSeq ([MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered]
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> [MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered]
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall a b. (a -> b) -> a -> b
$ MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> [MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered]
-> [MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered]
forall a. a -> [a] -> [a]
List.intersperse MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docCommaSep
([MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered]
-> [MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered])
-> [MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered]
-> [MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered]
forall a b. (a -> b) -> a -> b
$ [(Text, Maybe (ToBriDocM (Seq BriDocNumbered)))]
fds [(Text, Maybe (ToBriDocM (Seq BriDocNumbered)))]
-> ((Text, Maybe (ToBriDocM (Seq BriDocNumbered)))
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> [MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered]
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \case
(Text
fieldName, Just ToBriDocM (Seq BriDocNumbered)
fieldDoc) -> [MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered]
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docSeq
[ MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
appSep (MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall a b. (a -> b) -> a -> b
$ Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docLit Text
fieldName
, MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
appSep (MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall a b. (a -> b) -> a -> b
$ Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docLit (Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall a b. (a -> b) -> a -> b
$ String -> Text
Text.pack String
"="
, ToBriDocM (Seq BriDocNumbered)
fieldDoc ToBriDocM (Seq BriDocNumbered)
-> (Seq BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Seq BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
colsWrapPat
]
(Text
fieldName, Maybe (ToBriDocM (Seq BriDocNumbered))
Nothing) -> Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docLit Text
fieldName
, MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docSeparator
, Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docLit (Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall a b. (a -> b) -> a -> b
$ String -> Text
Text.pack String
"}"
]
#if MIN_VERSION_ghc(8,10,1) /* ghc-8.10.1 */
ConPatIn lname (RecCon (HsRecFields [] (Just (L _ 0)))) -> do
#else
ConPatIn lname (RecCon (HsRecFields [] (Just 0))) -> do
#endif
let t :: Text
t = GenLocated SrcSpan RdrName -> Text
forall l. GenLocated l RdrName -> Text
lrdrNameToText Located (IdP GhcPs)
GenLocated SrcSpan RdrName
lname
BriDocNumbered -> Seq BriDocNumbered
forall a. a -> Seq a
Seq.singleton (BriDocNumbered -> Seq BriDocNumbered)
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> ToBriDocM (Seq BriDocNumbered)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered]
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docSeq
[ MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
appSep (MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall a b. (a -> b) -> a -> b
$ Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docLit Text
t
, Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docLit (Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall a b. (a -> b) -> a -> b
$ String -> Text
Text.pack String
"{..}"
]
#if MIN_VERSION_ghc(8,10,1) /* ghc-8.10.1 */
ConPatIn lname (RecCon (HsRecFields fs@(_:_) (Just (L _ dotdoti)))) | Int
dotdoti Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== [GenLocated
SrcSpan (HsRecField' (FieldOcc GhcPs) (Located (Pat GhcPs)))]
-> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [LHsRecField GhcPs (LPat GhcPs)]
[GenLocated
SrcSpan (HsRecField' (FieldOcc GhcPs) (Located (Pat GhcPs)))]
fs -> do
#else
ConPatIn lname (RecCon (HsRecFields fs@(_:_) (Just dotdoti))) | dotdoti == length fs -> do
#endif
let t :: Text
t = GenLocated SrcSpan RdrName -> Text
forall l. GenLocated l RdrName -> Text
lrdrNameToText Located (IdP GhcPs)
GenLocated SrcSpan RdrName
lname
[(Text, Maybe (ToBriDocM (Seq BriDocNumbered)))]
fds <- [LHsRecField GhcPs (LPat GhcPs)]
[GenLocated
SrcSpan (HsRecField' (FieldOcc GhcPs) (Located (Pat GhcPs)))]
fs [GenLocated
SrcSpan (HsRecField' (FieldOcc GhcPs) (Located (Pat GhcPs)))]
-> (GenLocated
SrcSpan (HsRecField' (FieldOcc GhcPs) (Located (Pat GhcPs)))
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
(Text, Maybe (ToBriDocM (Seq BriDocNumbered))))
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
[(Text, Maybe (ToBriDocM (Seq BriDocNumbered)))]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
`forM` \(L SrcSpan
_ (HsRecField (L SrcSpan
_ FieldOcc GhcPs
fieldOcc) Located (Pat GhcPs)
fPat Bool
pun)) -> do
let FieldOcc XCFieldOcc GhcPs
_ GenLocated SrcSpan RdrName
lnameF = FieldOcc GhcPs
fieldOcc
Maybe (ToBriDocM (Seq BriDocNumbered))
fExpDoc <- if Bool
pun
then Maybe (ToBriDocM (Seq BriDocNumbered))
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
(Maybe (ToBriDocM (Seq BriDocNumbered)))
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe (ToBriDocM (Seq BriDocNumbered))
forall a. Maybe a
Nothing
else ToBriDocM (Seq BriDocNumbered)
-> Maybe (ToBriDocM (Seq BriDocNumbered))
forall a. a -> Maybe a
Just (ToBriDocM (Seq BriDocNumbered)
-> Maybe (ToBriDocM (Seq BriDocNumbered)))
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
(ToBriDocM (Seq BriDocNumbered))
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
(Maybe (ToBriDocM (Seq BriDocNumbered)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Located (Pat GhcPs) -> ToBriDocM (Seq BriDocNumbered))
-> Located (Pat GhcPs)
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
(ToBriDocM (Seq BriDocNumbered))
forall (m :: * -> *) x y. Monad m => (x -> m y) -> x -> m (m y)
docSharedWrapper LPat GhcPs -> ToBriDocM (Seq BriDocNumbered)
Located (Pat GhcPs) -> ToBriDocM (Seq BriDocNumbered)
layoutPat Located (Pat GhcPs)
fPat
(Text, Maybe (ToBriDocM (Seq BriDocNumbered)))
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
(Text, Maybe (ToBriDocM (Seq BriDocNumbered)))
forall (m :: * -> *) a. Monad m => a -> m a
return (GenLocated SrcSpan RdrName -> Text
forall l. GenLocated l RdrName -> Text
lrdrNameToText GenLocated SrcSpan RdrName
lnameF, Maybe (ToBriDocM (Seq BriDocNumbered))
fExpDoc)
BriDocNumbered -> Seq BriDocNumbered
forall a. a -> Seq a
Seq.singleton (BriDocNumbered -> Seq BriDocNumbered)
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> ToBriDocM (Seq BriDocNumbered)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered]
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docSeq
[ MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
appSep (MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall a b. (a -> b) -> a -> b
$ Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docLit Text
t
, MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
appSep (MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall a b. (a -> b) -> a -> b
$ Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docLit (Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall a b. (a -> b) -> a -> b
$ String -> Text
Text.pack String
"{"
, [MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered]
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docSeq ([MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered]
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> [MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered]
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall a b. (a -> b) -> a -> b
$ [(Text, Maybe (ToBriDocM (Seq BriDocNumbered)))]
fds [(Text, Maybe (ToBriDocM (Seq BriDocNumbered)))]
-> ((Text, Maybe (ToBriDocM (Seq BriDocNumbered)))
-> [MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered])
-> [MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered]
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
(Text
fieldName, Just ToBriDocM (Seq BriDocNumbered)
fieldDoc) ->
[ MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
appSep (MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall a b. (a -> b) -> a -> b
$ Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docLit Text
fieldName
, MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
appSep (MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall a b. (a -> b) -> a -> b
$ Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docLit (Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall a b. (a -> b) -> a -> b
$ String -> Text
Text.pack String
"="
, ToBriDocM (Seq BriDocNumbered)
fieldDoc ToBriDocM (Seq BriDocNumbered)
-> (Seq BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Seq BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
colsWrapPat
, MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docCommaSep
]
(Text
fieldName, Maybe (ToBriDocM (Seq BriDocNumbered))
Nothing) -> [Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docLit Text
fieldName, MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docCommaSep]
, Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docLit (Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall a b. (a -> b) -> a -> b
$ String -> Text
Text.pack String
"..}"
]
TuplePat _ args boxity -> do
case Boxity
boxity of
Boxity
Boxed -> [LPat GhcPs]
-> String
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> ToBriDocM (Seq BriDocNumbered)
wrapPatListy [LPat GhcPs]
args String
"()" MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docParenL MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docParenR
Boxity
Unboxed -> [LPat GhcPs]
-> String
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> ToBriDocM (Seq BriDocNumbered)
wrapPatListy [LPat GhcPs]
args String
"(##)" MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docParenHashLSep MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docParenHashRSep
AsPat _ asName asPat -> do
LPat GhcPs
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> ToBriDocM (Seq BriDocNumbered)
wrapPatPrepend LPat GhcPs
asPat (Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docLit (Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall a b. (a -> b) -> a -> b
$ GenLocated SrcSpan RdrName -> Text
forall l. GenLocated l RdrName -> Text
lrdrNameToText Located (IdP GhcPs)
GenLocated SrcSpan RdrName
asName Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
Text.pack String
"@")
#if MIN_VERSION_ghc(8,8,0) /* ghc-8.8 */
SigPat _ pat1 (HsWC _ (HsIB _ ty1)) -> do
#else
SigPat (HsWC _ (HsIB _ ty1)) pat1 -> do
#endif
Seq BriDocNumbered
patDocs <- LPat GhcPs -> ToBriDocM (Seq BriDocNumbered)
layoutPat LPat GhcPs
pat1
MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
tyDoc <- (Located (HsType GhcPs)
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> Located (HsType GhcPs)
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
(MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
forall (m :: * -> *) x y. Monad m => (x -> m y) -> x -> m (m y)
docSharedWrapper Located (HsType GhcPs)
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
layoutType Located (HsType GhcPs)
LHsType (NoGhcTc GhcPs)
ty1
case Seq BriDocNumbered -> ViewR BriDocNumbered
forall a. Seq a -> ViewR a
Seq.viewr Seq BriDocNumbered
patDocs of
ViewR BriDocNumbered
Seq.EmptyR -> String -> ToBriDocM (Seq BriDocNumbered)
forall a. HasCallStack => String -> a
error String
"cannot happen ljoiuxoasdcoviuasd"
Seq BriDocNumbered
xR Seq.:> BriDocNumbered
xN -> do
BriDocNumbered
xN' <-
BrIndent
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docAddBaseY BrIndent
BrIndentRegular (MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall a b. (a -> b) -> a -> b
$ [MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered]
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docSeq
[ MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
appSep (MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall a b. (a -> b) -> a -> b
$ BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall (m :: * -> *) a. Monad m => a -> m a
return BriDocNumbered
xN
, MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
appSep (MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall a b. (a -> b) -> a -> b
$ Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docLit (Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall a b. (a -> b) -> a -> b
$ String -> Text
Text.pack String
"::"
, MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docForceSingleline MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
tyDoc
]
Seq BriDocNumbered -> ToBriDocM (Seq BriDocNumbered)
forall (m :: * -> *) a. Monad m => a -> m a
return (Seq BriDocNumbered -> ToBriDocM (Seq BriDocNumbered))
-> Seq BriDocNumbered -> ToBriDocM (Seq BriDocNumbered)
forall a b. (a -> b) -> a -> b
$ Seq BriDocNumbered
xR Seq BriDocNumbered -> BriDocNumbered -> Seq BriDocNumbered
forall a. Seq a -> a -> Seq a
Seq.|> BriDocNumbered
xN'
ListPat _ elems ->
[LPat GhcPs]
-> String
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> ToBriDocM (Seq BriDocNumbered)
wrapPatListy [LPat GhcPs]
elems String
"[]" MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docBracketL MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docBracketR
BangPat _ pat1 -> do
LPat GhcPs
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> ToBriDocM (Seq BriDocNumbered)
wrapPatPrepend LPat GhcPs
pat1 (Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docLit (Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall a b. (a -> b) -> a -> b
$ String -> Text
Text.pack String
"!")
LazyPat _ pat1 -> do
LPat GhcPs
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> ToBriDocM (Seq BriDocNumbered)
wrapPatPrepend LPat GhcPs
pat1 (Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docLit (Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall a b. (a -> b) -> a -> b
$ String -> Text
Text.pack String
"~")
NPat _ llit@(L _ ol) mNegative _ -> do
BriDocNumbered
litDoc <- Located (HsOverLit GhcPs)
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall a ast. (DocWrapable a, Data ast) => Located ast -> a -> a
docWrapNode Located (HsOverLit GhcPs)
llit (MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall a b. (a -> b) -> a -> b
$ BriDocFInt
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall (m :: * -> *).
MonadMultiState NodeAllocIndex m =>
BriDocFInt -> m BriDocNumbered
allocateNode (BriDocFInt
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> BriDocFInt
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall a b. (a -> b) -> a -> b
$ OverLitVal -> BriDocFInt
overLitValBriDoc (OverLitVal -> BriDocFInt) -> OverLitVal -> BriDocFInt
forall a b. (a -> b) -> a -> b
$ HsOverLit GhcPs -> OverLitVal
forall p. HsOverLit p -> OverLitVal
GHC.ol_val HsOverLit GhcPs
ol
BriDocNumbered
negDoc <- Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docLit (Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall a b. (a -> b) -> a -> b
$ String -> Text
Text.pack String
"-"
Seq BriDocNumbered -> ToBriDocM (Seq BriDocNumbered)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Seq BriDocNumbered -> ToBriDocM (Seq BriDocNumbered))
-> Seq BriDocNumbered -> ToBriDocM (Seq BriDocNumbered)
forall a b. (a -> b) -> a -> b
$ case Maybe (SyntaxExpr GhcPs)
mNegative of
Just{} -> [BriDocNumbered] -> Seq BriDocNumbered
forall a. [a] -> Seq a
Seq.fromList [BriDocNumbered
negDoc, BriDocNumbered
litDoc]
Maybe (SyntaxExpr GhcPs)
Nothing -> BriDocNumbered -> Seq BriDocNumbered
forall a. a -> Seq a
Seq.singleton BriDocNumbered
litDoc
SrcSpanLess (Located (Pat GhcPs))
_ -> BriDocNumbered -> Seq BriDocNumbered
forall (m :: * -> *) a. Monad m => a -> m a
return (BriDocNumbered -> Seq BriDocNumbered)
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> ToBriDocM (Seq BriDocNumbered)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String
-> Located (Pat GhcPs)
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall ast.
(Annotate ast, Data ast) =>
String
-> Located ast
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
briDocByExactInlineOnly String
"some unknown pattern" (Located (Pat GhcPs) -> Located (SrcSpanLess (Located (Pat GhcPs)))
forall a. HasSrcSpan a => a -> Located (SrcSpanLess a)
ghcDL Located (Pat GhcPs)
Located (SrcSpanLess (Located (Pat GhcPs)))
lpat)
colsWrapPat :: Seq BriDocNumbered -> ToBriDocM BriDocNumbered
colsWrapPat :: Seq BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
colsWrapPat = ColSig
-> [MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered]
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docCols ColSig
ColPatterns ([MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered]
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> (Seq BriDocNumbered
-> [MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered])
-> Seq BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> [BriDocNumbered]
-> [MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall (m :: * -> *) a. Monad m => a -> m a
return ([BriDocNumbered]
-> [MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered])
-> (Seq BriDocNumbered -> [BriDocNumbered])
-> Seq BriDocNumbered
-> [MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Seq BriDocNumbered -> [BriDocNumbered]
forall (t :: * -> *) a. Foldable t => t a -> [a]
Foldable.toList
wrapPatPrepend
:: LPat GhcPs
-> ToBriDocM BriDocNumbered
-> ToBriDocM (Seq BriDocNumbered)
wrapPatPrepend :: LPat GhcPs
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> ToBriDocM (Seq BriDocNumbered)
wrapPatPrepend LPat GhcPs
pat MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
prepElem = do
Seq BriDocNumbered
patDocs <- LPat GhcPs -> ToBriDocM (Seq BriDocNumbered)
layoutPat LPat GhcPs
pat
case Seq BriDocNumbered -> ViewL BriDocNumbered
forall a. Seq a -> ViewL a
Seq.viewl Seq BriDocNumbered
patDocs of
ViewL BriDocNumbered
Seq.EmptyL -> Seq BriDocNumbered -> ToBriDocM (Seq BriDocNumbered)
forall (m :: * -> *) a. Monad m => a -> m a
return Seq BriDocNumbered
forall a. Seq a
Seq.empty
BriDocNumbered
x1 Seq.:< Seq BriDocNumbered
xR -> do
BriDocNumbered
x1' <- [MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered]
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docSeq [MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
prepElem, BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall (m :: * -> *) a. Monad m => a -> m a
return BriDocNumbered
x1]
Seq BriDocNumbered -> ToBriDocM (Seq BriDocNumbered)
forall (m :: * -> *) a. Monad m => a -> m a
return (Seq BriDocNumbered -> ToBriDocM (Seq BriDocNumbered))
-> Seq BriDocNumbered -> ToBriDocM (Seq BriDocNumbered)
forall a b. (a -> b) -> a -> b
$ BriDocNumbered
x1' BriDocNumbered -> Seq BriDocNumbered -> Seq BriDocNumbered
forall a. a -> Seq a -> Seq a
Seq.<| Seq BriDocNumbered
xR
wrapPatListy
:: [LPat GhcPs]
-> String
-> ToBriDocM BriDocNumbered
-> ToBriDocM BriDocNumbered
-> ToBriDocM (Seq BriDocNumbered)
wrapPatListy :: [LPat GhcPs]
-> String
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> ToBriDocM (Seq BriDocNumbered)
wrapPatListy [LPat GhcPs]
elems String
both MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
start MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
end = do
Seq BriDocNumbered
elemDocs <- [Located (Pat GhcPs)] -> Seq (Located (Pat GhcPs))
forall a. [a] -> Seq a
Seq.fromList [LPat GhcPs]
[Located (Pat GhcPs)]
elems Seq (Located (Pat GhcPs))
-> (Located (Pat GhcPs)
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> ToBriDocM (Seq BriDocNumbered)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
`forM` (LPat GhcPs -> ToBriDocM (Seq BriDocNumbered)
Located (Pat GhcPs) -> ToBriDocM (Seq BriDocNumbered)
layoutPat (Located (Pat GhcPs) -> ToBriDocM (Seq BriDocNumbered))
-> (Seq BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> Located (Pat GhcPs)
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> Seq BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
colsWrapPat)
case Seq BriDocNumbered -> ViewL BriDocNumbered
forall a. Seq a -> ViewL a
Seq.viewl Seq BriDocNumbered
elemDocs of
ViewL BriDocNumbered
Seq.EmptyL -> (BriDocNumbered -> Seq BriDocNumbered)
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> ToBriDocM (Seq BriDocNumbered)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap BriDocNumbered -> Seq BriDocNumbered
forall a. a -> Seq a
Seq.singleton (MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> ToBriDocM (Seq BriDocNumbered))
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
-> ToBriDocM (Seq BriDocNumbered)
forall a b. (a -> b) -> a -> b
$ Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docLit (Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> Text
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall a b. (a -> b) -> a -> b
$ String -> Text
Text.pack String
both
BriDocNumbered
x1 Seq.:< Seq BriDocNumbered
rest -> do
BriDocNumbered
sDoc <- MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
start
BriDocNumbered
eDoc <- MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
end
Seq BriDocNumbered
rest' <- Seq BriDocNumbered
rest Seq BriDocNumbered
-> (BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered)
-> ToBriDocM (Seq BriDocNumbered)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
`forM` \BriDocNumbered
bd -> [MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered]
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docSeq
[ MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
docCommaSep
, BriDocNumbered
-> MultiRWST
'[Config, Anns]
'[[BrittanyError], Seq String]
'[NodeAllocIndex]
Identity
BriDocNumbered
forall (m :: * -> *) a. Monad m => a -> m a
return BriDocNumbered
bd
]
Seq BriDocNumbered -> ToBriDocM (Seq BriDocNumbered)
forall (m :: * -> *) a. Monad m => a -> m a
return (Seq BriDocNumbered -> ToBriDocM (Seq BriDocNumbered))
-> Seq BriDocNumbered -> ToBriDocM (Seq BriDocNumbered)
forall a b. (a -> b) -> a -> b
$ (BriDocNumbered
sDoc BriDocNumbered -> Seq BriDocNumbered -> Seq BriDocNumbered
forall a. a -> Seq a -> Seq a
Seq.<| BriDocNumbered
x1 BriDocNumbered -> Seq BriDocNumbered -> Seq BriDocNumbered
forall a. a -> Seq a -> Seq a
Seq.<| Seq BriDocNumbered
rest') Seq BriDocNumbered -> BriDocNumbered -> Seq BriDocNumbered
forall a. Seq a -> a -> Seq a
Seq.|> BriDocNumbered
eDoc