Hello.

Today I wrote a small program to experiment with the Applicative
class. The program is supposed to use an "applicative reader", similar
to a "monad reader", to evaluate arithmetic expressions.

But when compiling the program with ghc-7.6.1, I get the following message:

  $ ghc --make applicative-eval
  [1 of 1] Compiling Main             ( applicative-eval.hs, applicative-eval.o 
)
  ghc: panic! (the 'impossible' happened)
    (GHC version 7.6.1 for x86_64-unknown-linux):
    expectJust cpeBody:collect_args

  Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug

If the line

  eval (Let s a b) = \m -> eval b ((s,eval a m):m)

is commented out, the program compiles without problems.

Is this a known issue with the compiler?

The source code is attached.

Romildo
module Main where

import Control.Applicative (pure,(<*>),(<$>),(<$),(<*),(*>))
import Text.Parsec
import System.IO (stdout,hSetBuffering,BufferMode(NoBuffering))

data Exp = Cte Integer
         | Var String
         | Sum Exp Exp
         | Sub Exp Exp
         | Mul Exp Exp
         | Div Exp Exp
         | Let String Exp Exp
         deriving (Show)

type Memory = [(String,Integer)]

eval :: Exp -> (->) Memory Integer
eval (Cte i) = pure i
eval (Var s) = \m -> case lookup s m of
                       Just v -> v
                       Nothing -> 0
eval (Sum a b) = (+) <$> eval a <*> eval b
eval (Sub a b) = (-) <$> eval a <*> eval b
eval (Mul a b) = (*) <$> eval a <*> eval b
eval (Div a b) = (div) <$> eval a <*> eval b
eval (Let s a b) = \m -> eval b ((s,eval a m):m)

pExp, pTerm, pFactor :: Parsec String () Exp
pExp = chainl1 pTerm (lexeme (Sum <$ char '+' <|> Sub <$ char '-'))
pTerm = chainl1 pFactor (lexeme (Mul <$ char '*' <|> Div <$ char '/'))
pFactor = Cte <$> lexeme pInteger <|>
          Var <$> lexeme pVariable <|>
          lexeme (char '(') *> pExp <* lexeme (char ')')
pInteger = read <$> many1 digit
pVariable = (:) <$> letter <*> many (alphaNum <|> char '-')

lexeme p = p <* spaces



main = do hSetBuffering stdout NoBuffering
          calc 1

calc n = do putStr ("[" ++ show n ++ "] ")
            input <- getLine
            case parse pExp "-" input of
              Left err -> putStrLn (show err)
              Right exp -> do putStrLn (show exp)
                              putStrLn (show (eval exp []))
            calc (n+1)
_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to