{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE PatternSynonyms #-}
module Development.IDE.GHC.Compat.ExactPrint
( ExactPrint
, exactPrint
, makeDeltaAst
, Retrie.Annotated, pattern Annotated, astA, annsA
) where
#if !MIN_VERSION_ghc(9,2,0)
import Control.Arrow ((&&&))
#else
import Development.IDE.GHC.Compat.Parser
#endif
import Language.Haskell.GHC.ExactPrint as Retrie
import qualified Retrie.ExactPrint as Retrie
#if !MIN_VERSION_ghc(9,2,0)
class ExactPrint ast where
makeDeltaAst :: ast -> ast
makeDeltaAst = ast -> ast
forall a. a -> a
id
instance ExactPrint ast
#endif
#if !MIN_VERSION_ghc(9,2,0)
pattern Annotated :: ast -> Anns -> Retrie.Annotated ast
pattern $mAnnotated :: forall r ast.
Annotated ast -> (ast -> Anns -> r) -> (Void# -> r) -> r
Annotated {Annotated ast -> ast
astA, Annotated ast -> Anns
annsA} <- (Retrie.astA &&& Retrie.annsA -> (astA, annsA))
#else
pattern Annotated :: ast -> ApiAnns -> Retrie.Annotated ast
pattern Annotated {astA, annsA} <- ((,()) . Retrie.astA -> (astA, annsA))
#endif