[jhc] Re: jhc-0.7.1 and parsec-2.1.0.1

Chris Eidhof chris at eidhof.nl
Wed Nov 18 19:05:20 EST 2009


I've narrowed down the case. I came up with a minimal program that  
still fails:

> {-# LANGUAGE ExistentialQuantification #-}
> module Test where
>
> data T a = forall a . T a
>
> x (T _) = ()

I've changed tidyHeads to have an additional case:

> tidyHeads b ps = mapM f ps where
>     f ([],fe) = error $ "tidyHeads: " ++ show (map fst ps, b)
>     ....

Now when we try to compile the program, we'll get the following error:

> tidyHeads: ([[]],EVar (x4::EVar (Test.v12::ESort *)))

-chris

On 19 nov 2009, at 00:34, Chris Eidhof wrote:

> Hey everyone,
>
> I'm trying to compile parsec-2.1.0.1 as well, but there's a  
> different error. I get an "irrefutable failed for pattern (p:ps)"  
> the following snippet of code.
>
>> tidyHeads ::
>>    Monad m
>>    => E
>>    -> [([HsPat],E->E)]  -- [(pats,else -> value)]
>>    -> Ce m [(HsPat,[HsPat],E->E)]  -- pulls the head off of each  
>> pattern, tidying it up perhaps
>> tidyHeads b ps = mapM f ps where
>>    f (~(p:ps),fe) = do
>>        (p',fe') <- tidyPat p b
>>        return (p',ps,fe' . fe)
>
> I'm not sure what this code does, so I don't know what would be a  
> good implementation for f ([],fe)... any help would be appreciated.
>
> Thanks,
>
> -chris
>
> On 1 sep 2009, at 20:00, John Meacham wrote:
>
>> On Tue, Sep 01, 2009 at 10:28:48AM +0200, Christian Maeder wrote:
>>> John Meacham wrote:
>>>> On Fri, Aug 28, 2009 at 02:07:17PM +0200, Christian Maeder wrote:
>>>>> Hi,
>>>>>
>>>>> I've tried to compile (part of) parsec-2.1.0.1 with jhc-0.7.1
>>>>>
>>>>> and Parsec.Combinator had several problems with do-expression as  
>>>>> infix
>>>>> arguments, which should be simple to fix for you. I.e.
>>>>>
>>>>> do{ p; return ()} <|> return ()
>>>>>
>>>>> needed explicit parenthesis:
>>>>>
>>>>> (do{ p; return ()}) <|> return ()
>>>>>
>>>>> (also if layout is used instead of curly braces)
>>>>
>>>> Hmm.. okay. this may be related to
>>>> http://repetae.net/computer/jhc/bug/issue-35cc6ddc1a577e163e9830b96f89151f0562c029.html
>>>> I'll look into it. thanks for the report!
>>>
>>> No, it's the infix analysis. The "where"-Problem has to do with your
>>> different offside (by one).
>>
>> Ah. I see what is happening. I am desugaring before re-fixitying the
>> source code. Thanks! I see the issue now. I was thinking it was a
>> parsing problem.
>>
>>       John
>>
>> -- 
>> John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
>> _______________________________________________
>> jhc mailing list
>> jhc at haskell.org
>> http://www.haskell.org/mailman/listinfo/jhc
>
> _______________________________________________
> jhc mailing list
> jhc at haskell.org
> http://www.haskell.org/mailman/listinfo/jhc



More information about the jhc mailing list