module Imp.Extra.HsModule where import qualified GHC.Hs as Hs overDecls :: (Functor f) => ([Hs.LHsDecl Hs.GhcPs] -> f [Hs.LHsDecl Hs.GhcPs]) -> Hs.HsModule Hs.GhcPs -> f (Hs.HsModule Hs.GhcPs) overDecls :: forall (f :: * -> *). Functor f => ([LHsDecl GhcPs] -> f [LHsDecl GhcPs]) -> HsModule GhcPs -> f (HsModule GhcPs) overDecls [LHsDecl GhcPs] -> f [LHsDecl GhcPs] f HsModule GhcPs x = (\[GenLocated SrcSpanAnnA (HsDecl GhcPs)] y -> HsModule GhcPs x {Hs.hsmodDecls = y}) ([GenLocated SrcSpanAnnA (HsDecl GhcPs)] -> HsModule GhcPs) -> f [GenLocated SrcSpanAnnA (HsDecl GhcPs)] -> f (HsModule GhcPs) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> [LHsDecl GhcPs] -> f [LHsDecl GhcPs] f (HsModule GhcPs -> [LHsDecl GhcPs] forall p. HsModule p -> [LHsDecl p] Hs.hsmodDecls HsModule GhcPs x) overImports :: ([Hs.LImportDecl Hs.GhcPs] -> [Hs.LImportDecl Hs.GhcPs]) -> Hs.HsModule Hs.GhcPs -> Hs.HsModule Hs.GhcPs overImports :: ([LImportDecl GhcPs] -> [LImportDecl GhcPs]) -> HsModule GhcPs -> HsModule GhcPs overImports [LImportDecl GhcPs] -> [LImportDecl GhcPs] f HsModule GhcPs x = HsModule GhcPs x {Hs.hsmodImports = f $ Hs.hsmodImports x}