{-# LANGUAGE CPP #-}
{-# LANGUAGE PatternSynonyms #-}
module HIndent.Pretty.Types
  ( InfixExpr(..)
  , InfixOp(..)
  , PrefixOp(..)
  , InfixApp(..)
  , GRHSsExpr(..)
  , GRHSExpr(..)
  , GRHSProc(..)
  , RecConPat(..)
  , RecConField(..)
  , HsSigType'(..)
  , pattern HsSigTypeInsideInstDecl
  , pattern HsSigTypeInsideVerticalFuncSig
  , pattern HsSigTypeInsideDeclSig
  , HsType'(..)
  , pattern HsTypeInsideVerticalFuncSig
  , pattern HsTypeInsideDeclSig
  , pattern HsTypeInsideInstDecl
  , pattern HsTypeWithVerticalAppTy
  , DataFamInstDecl'(..)
  , pattern DataFamInstDeclTopLevel
  , pattern DataFamInstDeclInsideClassInst
  , FamEqn'(..)
  , pattern FamEqnTopLevel
  , pattern FamEqnInsideClassInst
  , StmtLRInsideVerticalList(..)
  , ParStmtBlockInsideVerticalList(..)
  , TopLevelTyFamInstDecl(..)
  , Context(..)
  , HorizontalContext(..)
  , VerticalContext(..)
  , ModuleNameWithPrefix(..)
  , PatInsidePatDecl(..)
  , LambdaCase(..)
  , ListComprehension(..)
  , DoExpression(..)
  , DoOrMdo(..)
  , QualifiedDo(..)
  , LetIn(..)
  , GRHSExprType(..)
  , GRHSProcType(..)
  , HsTypeFor(..)
  , HsTypeDir(..)
  , CaseOrCases(..)
  , DataFamInstDeclFor(..)
  ) where
import Data.List.NonEmpty
import GHC.Hs
import GHC.Types.Name.Reader
#if !MIN_VERSION_ghc_lib_parser(9,6,1)
import GHC.Unit
#endif
newtype InfixExpr =
  InfixExpr (LHsExpr GhcPs)
newtype InfixOp =
  InfixOp RdrName
newtype PrefixOp =
  PrefixOp RdrName
data InfixApp = InfixApp
  { InfixApp -> LHsExpr GhcPs
lhs :: LHsExpr GhcPs
  , InfixApp -> LHsExpr GhcPs
op :: LHsExpr GhcPs
  , InfixApp -> LHsExpr GhcPs
rhs :: LHsExpr GhcPs
  }
data GRHSsExpr = GRHSsExpr
  { GRHSsExpr -> GRHSExprType
grhssExprType :: GRHSExprType
  , GRHSsExpr -> GRHSs GhcPs (LHsExpr GhcPs)
grhssExpr :: GRHSs GhcPs (LHsExpr GhcPs)
  }
data GRHSExpr = GRHSExpr
  { GRHSExpr -> GRHSExprType
grhsExprType :: GRHSExprType
  , GRHSExpr -> GRHS GhcPs (LHsExpr GhcPs)
grhsExpr :: GRHS GhcPs (LHsExpr GhcPs)
  }
newtype GRHSProc =
  GRHSProc (GRHS GhcPs (LHsCmd GhcPs))
newtype RecConPat =
  RecConPat (HsRecFields GhcPs (LPat GhcPs))
#if MIN_VERSION_ghc_lib_parser(9,4,1)
newtype RecConField =
  RecConField (HsFieldBind (LFieldOcc GhcPs) (LPat GhcPs))
#else
newtype RecConField =
  RecConField (HsRecField' (FieldOcc GhcPs) (LPat GhcPs))
#endif
data HsSigType' = HsSigType'
  { HsSigType' -> HsTypeFor
hsSigTypeFor :: HsTypeFor 
  , HsSigType' -> HsTypeDir
hsSigTypeDir :: HsTypeDir 
                                
  , HsSigType' -> HsSigType GhcPs
hsSigType :: HsSigType GhcPs 
  }
pattern HsSigTypeInsideInstDecl :: HsSigType GhcPs -> HsSigType'
pattern $mHsSigTypeInsideInstDecl :: forall {r}.
HsSigType' -> (HsSigType GhcPs -> r) -> ((# #) -> r) -> r
$bHsSigTypeInsideInstDecl :: HsSigType GhcPs -> HsSigType'
HsSigTypeInsideInstDecl x = HsSigType' HsTypeForInstDecl HsTypeNoDir x
pattern HsSigTypeInsideVerticalFuncSig :: HsSigType GhcPs -> HsSigType'
pattern $mHsSigTypeInsideVerticalFuncSig :: forall {r}.
HsSigType' -> (HsSigType GhcPs -> r) -> ((# #) -> r) -> r
$bHsSigTypeInsideVerticalFuncSig :: HsSigType GhcPs -> HsSigType'
HsSigTypeInsideVerticalFuncSig x = HsSigType' HsTypeForFuncSig HsTypeVertical x
pattern HsSigTypeInsideDeclSig :: HsSigType GhcPs -> HsSigType'
pattern $mHsSigTypeInsideDeclSig :: forall {r}.
HsSigType' -> (HsSigType GhcPs -> r) -> ((# #) -> r) -> r
$bHsSigTypeInsideDeclSig :: HsSigType GhcPs -> HsSigType'
HsSigTypeInsideDeclSig x = HsSigType' HsTypeForDeclSig HsTypeNoDir x
data HsType' = HsType'
  { HsType' -> HsTypeFor
hsTypeFor :: HsTypeFor 
  , HsType' -> HsTypeDir
hsTypeDir :: HsTypeDir 
                           
  , HsType' -> HsType GhcPs
hsType :: HsType GhcPs 
  }
pattern HsTypeInsideVerticalFuncSig :: HsType GhcPs -> HsType'
pattern $mHsTypeInsideVerticalFuncSig :: forall {r}. HsType' -> (HsType GhcPs -> r) -> ((# #) -> r) -> r
$bHsTypeInsideVerticalFuncSig :: HsType GhcPs -> HsType'
HsTypeInsideVerticalFuncSig x = HsType' HsTypeForFuncSig HsTypeVertical x
pattern HsTypeInsideDeclSig :: HsType GhcPs -> HsType'
pattern $mHsTypeInsideDeclSig :: forall {r}. HsType' -> (HsType GhcPs -> r) -> ((# #) -> r) -> r
$bHsTypeInsideDeclSig :: HsType GhcPs -> HsType'
HsTypeInsideDeclSig x = HsType' HsTypeForDeclSig HsTypeNoDir x
pattern HsTypeInsideInstDecl :: HsType GhcPs -> HsType'
pattern $mHsTypeInsideInstDecl :: forall {r}. HsType' -> (HsType GhcPs -> r) -> ((# #) -> r) -> r
$bHsTypeInsideInstDecl :: HsType GhcPs -> HsType'
HsTypeInsideInstDecl x = HsType' HsTypeForInstDecl HsTypeNoDir x
pattern HsTypeWithVerticalAppTy :: HsType GhcPs -> HsType'
pattern $mHsTypeWithVerticalAppTy :: forall {r}. HsType' -> (HsType GhcPs -> r) -> ((# #) -> r) -> r
$bHsTypeWithVerticalAppTy :: HsType GhcPs -> HsType'
HsTypeWithVerticalAppTy x = HsType' HsTypeForVerticalAppTy HsTypeVertical x
data DataFamInstDecl' = DataFamInstDecl'
  { DataFamInstDecl' -> DataFamInstDeclFor
dataFamInstDeclFor :: DataFamInstDeclFor 
  , DataFamInstDecl' -> DataFamInstDecl GhcPs
dataFamInstDecl :: DataFamInstDecl GhcPs 
  }
pattern DataFamInstDeclTopLevel :: DataFamInstDecl GhcPs -> DataFamInstDecl'
pattern $mDataFamInstDeclTopLevel :: forall {r}.
DataFamInstDecl'
-> (DataFamInstDecl GhcPs -> r) -> ((# #) -> r) -> r
$bDataFamInstDeclTopLevel :: DataFamInstDecl GhcPs -> DataFamInstDecl'
DataFamInstDeclTopLevel x = DataFamInstDecl' DataFamInstDeclForTopLevel x
pattern DataFamInstDeclInsideClassInst :: DataFamInstDecl GhcPs -> DataFamInstDecl'
pattern $mDataFamInstDeclInsideClassInst :: forall {r}.
DataFamInstDecl'
-> (DataFamInstDecl GhcPs -> r) -> ((# #) -> r) -> r
$bDataFamInstDeclInsideClassInst :: DataFamInstDecl GhcPs -> DataFamInstDecl'
DataFamInstDeclInsideClassInst x = DataFamInstDecl' DataFamInstDeclForInsideClassInst x
data FamEqn' = FamEqn'
  { FamEqn' -> DataFamInstDeclFor
famEqnFor :: DataFamInstDeclFor 
  , FamEqn' -> FamEqn GhcPs (HsDataDefn GhcPs)
famEqn :: FamEqn GhcPs (HsDataDefn GhcPs)
  }
pattern FamEqnTopLevel :: FamEqn GhcPs (HsDataDefn GhcPs) -> FamEqn'
pattern $mFamEqnTopLevel :: forall {r}.
FamEqn'
-> (FamEqn GhcPs (HsDataDefn GhcPs) -> r) -> ((# #) -> r) -> r
$bFamEqnTopLevel :: FamEqn GhcPs (HsDataDefn GhcPs) -> FamEqn'
FamEqnTopLevel x = FamEqn' DataFamInstDeclForTopLevel x
pattern FamEqnInsideClassInst :: FamEqn GhcPs (HsDataDefn GhcPs) -> FamEqn'
pattern $mFamEqnInsideClassInst :: forall {r}.
FamEqn'
-> (FamEqn GhcPs (HsDataDefn GhcPs) -> r) -> ((# #) -> r) -> r
$bFamEqnInsideClassInst :: FamEqn GhcPs (HsDataDefn GhcPs) -> FamEqn'
FamEqnInsideClassInst x = FamEqn' DataFamInstDeclForInsideClassInst x
newtype StmtLRInsideVerticalList =
  StmtLRInsideVerticalList (StmtLR GhcPs GhcPs (LHsExpr GhcPs))
newtype ParStmtBlockInsideVerticalList =
  ParStmtBlockInsideVerticalList (ParStmtBlock GhcPs GhcPs)
newtype TopLevelTyFamInstDecl =
  TopLevelTyFamInstDecl (TyFamInstDecl GhcPs)
#if MIN_VERSION_ghc_lib_parser(9,4,1)
newtype Context =
  Context (LHsContext GhcPs)
newtype HorizontalContext =
  HorizontalContext (LHsContext GhcPs)
newtype VerticalContext =
  VerticalContext (LHsContext GhcPs)
#else
newtype Context =
  Context (Maybe (LHsContext GhcPs))
newtype HorizontalContext =
  HorizontalContext (Maybe (LHsContext GhcPs))
newtype VerticalContext =
  VerticalContext (Maybe (LHsContext GhcPs))
#endif
newtype ModuleNameWithPrefix =
  ModuleNameWithPrefix ModuleName
newtype PatInsidePatDecl =
  PatInsidePatDecl (Pat GhcPs)
data LambdaCase = LambdaCase
  { LambdaCase -> MatchGroup GhcPs (LHsExpr GhcPs)
lamCaseGroup :: MatchGroup GhcPs (LHsExpr GhcPs)
  , LambdaCase -> CaseOrCases
caseOrCases :: CaseOrCases
  }
data ListComprehension = ListComprehension
  { ListComprehension -> ExprLStmt GhcPs
listCompLhs :: ExprLStmt GhcPs 
  , ListComprehension -> NonEmpty (ExprLStmt GhcPs)
listCompRhs :: NonEmpty (ExprLStmt GhcPs) 
  }
data DoExpression = DoExpression
  { DoExpression -> [ExprLStmt GhcPs]
doStmts :: [ExprLStmt GhcPs]
  , DoExpression -> QualifiedDo
qualifiedDo :: QualifiedDo
  }
data LetIn = LetIn
  { LetIn -> HsLocalBinds GhcPs
letBinds :: HsLocalBinds GhcPs
  , LetIn -> LHsExpr GhcPs
inExpr :: LHsExpr GhcPs
  }
data DoOrMdo
  = Do
  | Mdo
data QualifiedDo =
  QualifiedDo (Maybe ModuleName) DoOrMdo
data GRHSExprType
  = GRHSExprNormal
  | GRHSExprCase
  | GRHSExprMultiWayIf
  | GRHSExprLambda
  deriving (GRHSExprType -> GRHSExprType -> Bool
(GRHSExprType -> GRHSExprType -> Bool)
-> (GRHSExprType -> GRHSExprType -> Bool) -> Eq GRHSExprType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GRHSExprType -> GRHSExprType -> Bool
== :: GRHSExprType -> GRHSExprType -> Bool
$c/= :: GRHSExprType -> GRHSExprType -> Bool
/= :: GRHSExprType -> GRHSExprType -> Bool
Eq)
data GRHSProcType
  = GRHSProcCase
  | GRHSProcLambda
data HsTypeFor
  = HsTypeForNormalDecl
  | HsTypeForInstDecl
  | HsTypeForFuncSig
  | HsTypeForDeclSig
  | HsTypeForVerticalAppTy
data HsTypeDir
  = HsTypeNoDir
  | HsTypeVertical
data CaseOrCases
  = Case
  | Cases
data DataFamInstDeclFor
  = DataFamInstDeclForTopLevel
  | DataFamInstDeclForInsideClassInst