[GHC] #11301: Using GHC's parser and rendering the results is unreasonably difficult
GHC
ghc-devs at haskell.org
Mon Dec 28 05:02:24 UTC 2015
#11301: Using GHC's parser and rendering the results is unreasonably difficult
-------------------------------------+-------------------------------------
Reporter: bitemyapp | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: GHC API | Version: 7.10.2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Description changed by bitemyapp:
Old description:
> After a couple hours, 30-some browser tabs, and attempting to use ghc-
> simple to paper over some annoyances with GHC's API (dynFlags/session-
> stuff, particularly), I gave up.
>
> I then opened up haskell-src-exts and found the function I wanted in a
> minute or two.
>
> {{{#!hs
>
> import qualified Language.Haskell.Exts.Parser as P
>
> parsePls' :: String -> IO ()
> parsePls' s = print $ P.parseExp s
> }}}
>
> This is where I got stuck:
>
> {{{
> Prelude> parsePls "1 + 1"
> Too late for parseStaticFlags: call it before runGhc or runGhcT
> }}}
>
> This is the code I was working with before I gave up on GHC:
>
> {{{#!hs
> module ParsePls where
>
> import DynFlags
> import FastString
> import qualified GHC
> import qualified GhcMonad as GM
> import HsSyn
> import Lexer
> import Outputable
> import Parser
> import RdrName
> import SrcLoc
> import StaticFlags
> import StringBuffer
>
> import qualified Language.Haskell.GHC.Simple as S
> import qualified Language.Haskell.GHC.Simple.Types as ST
>
> import System.Environment
>
> main :: IO ()
> main = do
> [expr] <- getArgs
> parsePls expr
>
> parsePls :: String -> IO ()
> parsePls s = do
> initStaticOpts
> let sbuf = stringToStringBuffer s
> srcloc = mkRealSrcLoc (mkFastString s) 1 1
> (dynflags, _) <- S.getDynFlagsForConfig ST.defaultConfig
> -- dynflags <- undefined -- GHC.getSessionDynFlags
> -- unP :: P a -> PState -> ParseResult a
>
> -- mkPState :: DynFlags -> StringBuffer -> RealSrcLoc -> PState
> -- parseExpression :: P (LHsExpr RdrName)
> -- type LHsExpr id = Located (HsExpr id) -- Defined in ‘HsExpr’
>
> let parseResult = unP parseExpression
> (mkPState dynflags sbuf srcloc)
> case parseResult of
> POk _ (L _ mdl) -> print $ showPpr dynflags mdl
> PFailed ss _ -> do
> putStrLn "Error occurred!"
> print ss
> }}}
>
> Is there a reason it has to be this difficult?
New description:
After a couple hours, 30-some browser tabs, and attempting to use ghc-
simple to paper over some annoyances with GHC's API (dynFlags/session-
stuff, particularly), I gave up.
I then opened up haskell-src-exts and found the function I wanted in a
minute or two.
{{{#!hs
import qualified Language.Haskell.Exts.Parser as P
parsePls' :: String -> IO ()
parsePls' s = print $ P.parseExp s
}}}
This is where I got stuck:
{{{
Prelude> parsePls "1 + 1"
Too late for parseStaticFlags: call it before runGhc or runGhcT
}}}
This is the code I was working with before I gave up on GHC:
{{{#!hs
module ParsePls where
import DynFlags
import FastString
import qualified GHC
import qualified GhcMonad as GM
import HsSyn
import Lexer
import Outputable
import Parser
import RdrName
import SrcLoc
import StaticFlags
import StringBuffer
import qualified Language.Haskell.GHC.Simple as S
import qualified Language.Haskell.GHC.Simple.Types as ST
import System.Environment
main :: IO ()
main = do
[expr] <- getArgs
parsePls expr
parsePls :: String -> IO ()
parsePls s = do
initStaticOpts
let sbuf = stringToStringBuffer s
srcloc = mkRealSrcLoc (mkFastString s) 1 1
(dynflags, _) <- S.getDynFlagsForConfig ST.defaultConfig
-- dynflags <- undefined -- GHC.getSessionDynFlags
-- unP :: P a -> PState -> ParseResult a
-- mkPState :: DynFlags -> StringBuffer -> RealSrcLoc -> PState
-- parseExpression :: P (LHsExpr RdrName)
-- type LHsExpr id = Located (HsExpr id) -- Defined in ‘HsExpr’
let parseResult = unP parseExpression
(mkPState dynflags sbuf srcloc)
case parseResult of
POk _ (L _ mdl) -> print $ showPpr dynflags mdl
PFailed ss _ -> do
putStrLn "Error occurred!"
print ss
}}}
Whereas with haskell-src-exts I got:
{{{
Prelude> parsePls' "1 + 1"
ParseOk (InfixApp (Lit (Int 1)) (QVarOp (UnQual (Symbol "+"))) (Lit (Int
1)))
}}}
Which was perfectly satisfactory.
Is there a reason it has to be this difficult?
--
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11301#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list