{-# LANGUAGE RecordWildCards #-} module HIndent.Ast.Declaration.StandAloneDeriving ( StandAloneDeriving , mkStandAloneDeriving ) where import HIndent.Applicative import HIndent.Ast.Declaration.Data.Deriving.Strategy import HIndent.Ast.NodeComments import HIndent.Ast.WithComments import qualified HIndent.GhcLibParserWrapper.GHC.Hs as GHC import {-# SOURCE #-} HIndent.Pretty import HIndent.Pretty.Combinators import HIndent.Pretty.NodeComments data StandAloneDeriving = StandAloneDeriving { StandAloneDeriving -> Maybe (WithComments DerivingStrategy) strategy :: Maybe (WithComments DerivingStrategy) , StandAloneDeriving -> LHsSigType GhcPs className :: GHC.LHsSigType GHC.GhcPs } instance CommentExtraction StandAloneDeriving where nodeComments :: StandAloneDeriving -> NodeComments nodeComments StandAloneDeriving {} = [LEpaComment] -> [LEpaComment] -> [LEpaComment] -> NodeComments NodeComments [] [] [] instance Pretty StandAloneDeriving where pretty' :: StandAloneDeriving -> Printer () pretty' StandAloneDeriving {strategy :: StandAloneDeriving -> Maybe (WithComments DerivingStrategy) strategy = Just WithComments DerivingStrategy strategy, LHsSigType GhcPs className :: StandAloneDeriving -> LHsSigType GhcPs className :: LHsSigType GhcPs ..} | DerivingStrategy -> Bool isViaStrategy (WithComments DerivingStrategy -> DerivingStrategy forall a. WithComments a -> a getNode WithComments DerivingStrategy strategy) = [Printer ()] -> Printer () spaced [ HasCallStack => String -> Printer () String -> Printer () string String "deriving" , WithComments DerivingStrategy -> Printer () forall a. Pretty a => a -> Printer () pretty WithComments DerivingStrategy strategy , HasCallStack => String -> Printer () String -> Printer () string String "instance" , GenLocated SrcSpanAnnA (HsSigType GhcPs) -> Printer () forall a. Pretty a => a -> Printer () pretty LHsSigType GhcPs GenLocated SrcSpanAnnA (HsSigType GhcPs) className ] pretty' StandAloneDeriving {Maybe (WithComments DerivingStrategy) LHsSigType GhcPs strategy :: StandAloneDeriving -> Maybe (WithComments DerivingStrategy) className :: StandAloneDeriving -> LHsSigType GhcPs strategy :: Maybe (WithComments DerivingStrategy) className :: LHsSigType GhcPs ..} = do HasCallStack => String -> Printer () String -> Printer () string String "deriving " Maybe (WithComments DerivingStrategy) -> (WithComments DerivingStrategy -> Printer ()) -> Printer () forall (m :: * -> *) a. Applicative m => Maybe a -> (a -> m ()) -> m () whenJust Maybe (WithComments DerivingStrategy) strategy ((WithComments DerivingStrategy -> Printer ()) -> Printer ()) -> (WithComments DerivingStrategy -> Printer ()) -> Printer () forall a b. (a -> b) -> a -> b $ \WithComments DerivingStrategy x -> WithComments DerivingStrategy -> Printer () forall a. Pretty a => a -> Printer () pretty WithComments DerivingStrategy x Printer () -> Printer () -> Printer () forall a b. Printer a -> Printer b -> Printer b forall (m :: * -> *) a b. Monad m => m a -> m b -> m b >> Printer () space HasCallStack => String -> Printer () String -> Printer () string String "instance " GenLocated SrcSpanAnnA (HsSigType GhcPs) -> Printer () forall a. Pretty a => a -> Printer () pretty LHsSigType GhcPs GenLocated SrcSpanAnnA (HsSigType GhcPs) className mkStandAloneDeriving :: GHC.DerivDecl GHC.GhcPs -> StandAloneDeriving mkStandAloneDeriving :: DerivDecl GhcPs -> StandAloneDeriving mkStandAloneDeriving GHC.DerivDecl {deriv_type :: forall pass. DerivDecl pass -> LHsSigWcType pass deriv_type = GHC.HsWC {XHsWC GhcPs (LHsSigType GhcPs) LHsSigType GhcPs hswc_ext :: XHsWC GhcPs (LHsSigType GhcPs) hswc_body :: LHsSigType GhcPs hswc_body :: forall pass thing. HsWildCardBndrs pass thing -> thing hswc_ext :: forall pass thing. HsWildCardBndrs pass thing -> XHsWC pass thing ..}, Maybe (XRec GhcPs OverlapMode) Maybe (LDerivStrategy GhcPs) XCDerivDecl GhcPs deriv_ext :: XCDerivDecl GhcPs deriv_strategy :: Maybe (LDerivStrategy GhcPs) deriv_overlap_mode :: Maybe (XRec GhcPs OverlapMode) deriv_overlap_mode :: forall pass. DerivDecl pass -> Maybe (XRec pass OverlapMode) deriv_strategy :: forall pass. DerivDecl pass -> Maybe (LDerivStrategy pass) deriv_ext :: forall pass. DerivDecl pass -> XCDerivDecl pass ..} = StandAloneDeriving {Maybe (WithComments DerivingStrategy) LHsSigType GhcPs GenLocated SrcSpanAnnA (HsSigType GhcPs) strategy :: Maybe (WithComments DerivingStrategy) className :: LHsSigType GhcPs strategy :: Maybe (WithComments DerivingStrategy) className :: GenLocated SrcSpanAnnA (HsSigType GhcPs) ..} where strategy :: Maybe (WithComments DerivingStrategy) strategy = (GenLocated EpAnnCO (DerivStrategy GhcPs) -> WithComments DerivingStrategy) -> Maybe (GenLocated EpAnnCO (DerivStrategy GhcPs)) -> Maybe (WithComments DerivingStrategy) forall a b. (a -> b) -> Maybe a -> Maybe b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap ((DerivStrategy GhcPs -> DerivingStrategy) -> WithComments (DerivStrategy GhcPs) -> WithComments DerivingStrategy forall a b. (a -> b) -> WithComments a -> WithComments b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap DerivStrategy GhcPs -> DerivingStrategy mkDerivingStrategy (WithComments (DerivStrategy GhcPs) -> WithComments DerivingStrategy) -> (GenLocated EpAnnCO (DerivStrategy GhcPs) -> WithComments (DerivStrategy GhcPs)) -> GenLocated EpAnnCO (DerivStrategy GhcPs) -> WithComments DerivingStrategy forall b c a. (b -> c) -> (a -> b) -> a -> c . GenLocated EpAnnCO (DerivStrategy GhcPs) -> WithComments (DerivStrategy GhcPs) forall l a. CommentExtraction l => GenLocated l a -> WithComments a fromGenLocated) Maybe (LDerivStrategy GhcPs) Maybe (GenLocated EpAnnCO (DerivStrategy GhcPs)) deriv_strategy className :: LHsSigType GhcPs className = LHsSigType GhcPs hswc_body