{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ViewPatterns #-}
module GHC.Util (
module GHC.Util.View
, module GHC.Util.FreeVars
, module GHC.Util.ApiAnnotation
, module GHC.Util.HsDecl
, module GHC.Util.HsExpr
, module GHC.Util.SrcLoc
, module GHC.Util.DynFlags
, module GHC.Util.Scope
, module GHC.Util.Unify
, parsePragmasIntoDynFlags
, fileToModule
, pattern SrcSpan, srcSpanFilename, srcSpanStartLine', srcSpanStartColumn, srcSpanEndLine', srcSpanEndColumn
, pattern SrcLoc, srcFilename, srcLine, srcColumn
, showSrcSpan,
) where
import GHC.Util.View
import GHC.Util.FreeVars
import GHC.Util.ApiAnnotation
import GHC.Util.HsExpr
import GHC.Util.HsDecl
import GHC.Util.SrcLoc
import GHC.Util.DynFlags
import GHC.Util.Scope
import GHC.Util.Unify
import Language.Haskell.GhclibParserEx.GHC.Parser (parseFile)
import Language.Haskell.GhclibParserEx.GHC.Driver.Session (parsePragmasIntoDynFlags)
import Language.Haskell.GhclibParserEx.GHC.Utils.Outputable
import GHC.Hs
import GHC.Parser.Lexer
import GHC.Types.SrcLoc
import GHC.Driver.Session
import GHC.Data.FastString
import System.FilePath
import Language.Preprocessor.Unlit
fileToModule :: FilePath -> String -> DynFlags -> ParseResult (Located (HsModule GhcPs))
fileToModule :: String
-> String -> DynFlags -> ParseResult (Located (HsModule GhcPs))
fileToModule String
filename String
str DynFlags
flags =
String
-> DynFlags -> String -> ParseResult (Located (HsModule GhcPs))
parseFile String
filename DynFlags
flags
(if String -> String
takeExtension String
filename String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= String
".lhs" then String
str else String -> String -> String
unlit String
filename String
str)
{-# COMPLETE SrcSpan #-}
pattern SrcSpan :: String -> Int -> Int -> Int -> Int -> SrcSpan
pattern $mSrcSpan :: forall {r}.
SrcSpan
-> (String -> Int -> Int -> Int -> Int -> r) -> ((# #) -> r) -> r
SrcSpan
{ SrcSpan -> String
srcSpanFilename
, SrcSpan -> Int
srcSpanStartLine'
, SrcSpan -> Int
srcSpanStartColumn
, SrcSpan -> Int
srcSpanEndLine'
, SrcSpan -> Int
srcSpanEndColumn
}
<-
(toOldeSpan ->
( srcSpanFilename
, srcSpanStartLine'
, srcSpanStartColumn
, srcSpanEndLine'
, srcSpanEndColumn
))
toOldeSpan :: SrcSpan -> (String, Int, Int, Int, Int)
toOldeSpan :: SrcSpan -> (String, Int, Int, Int, Int)
toOldeSpan (RealSrcSpan RealSrcSpan
span Maybe BufSpan
_) =
( FastString -> String
unpackFS (FastString -> String) -> FastString -> String
forall a b. (a -> b) -> a -> b
$ RealSrcSpan -> FastString
srcSpanFile RealSrcSpan
span
, RealSrcSpan -> Int
srcSpanStartLine RealSrcSpan
span
, RealSrcSpan -> Int
srcSpanStartCol RealSrcSpan
span
, RealSrcSpan -> Int
srcSpanEndLine RealSrcSpan
span
, RealSrcSpan -> Int
srcSpanEndCol RealSrcSpan
span
)
toOldeSpan (UnhelpfulSpan UnhelpfulSpanReason
_) =
( String
"no-span"
, -Int
1
, -Int
1
, -Int
1
, -Int
1
)
{-# COMPLETE SrcLoc #-}
pattern SrcLoc :: String -> Int -> Int -> SrcLoc
pattern $mSrcLoc :: forall {r}.
SrcLoc -> (String -> Int -> Int -> r) -> ((# #) -> r) -> r
SrcLoc
{ SrcLoc -> String
srcFilename
, SrcLoc -> Int
srcLine
, SrcLoc -> Int
srcColumn
}
<-
(toOldeLoc ->
( srcFilename
, srcLine
, srcColumn
))
toOldeLoc :: SrcLoc -> (String, Int, Int)
toOldeLoc :: SrcLoc -> (String, Int, Int)
toOldeLoc (RealSrcLoc RealSrcLoc
loc Maybe BufPos
_) =
( FastString -> String
unpackFS (FastString -> String) -> FastString -> String
forall a b. (a -> b) -> a -> b
$ RealSrcLoc -> FastString
srcLocFile RealSrcLoc
loc
, RealSrcLoc -> Int
srcLocLine RealSrcLoc
loc
, RealSrcLoc -> Int
srcLocCol RealSrcLoc
loc
)
toOldeLoc (UnhelpfulLoc FastString
_) =
( String
"no-loc"
, -Int
1
, -Int
1
)
showSrcSpan :: SrcSpan -> String
showSrcSpan :: SrcSpan -> String
showSrcSpan = SrcSpan -> String
forall a. Outputable a => a -> String
unsafePrettyPrint