[Haskell-cafe] Re: haskell compiler never comes back

Greg Meredith lgreg.meredith at biosimilarity.com
Mon Dec 15 17:49:55 EST 2008


Daniel,

Thanks. i'm using

GHCi, version 6.8.2: http://www.haskell.org/ghc/  :? for help
Loading package base ... linking ... done.
Prelude> :l monoidal.hs
[1 of 1] Compiling Monoidal         ( monoidal.hs, interpreted )
  C-c C-cInterrupted.
> :q

Best wishes,

--greg

On Mon, Dec 15, 2008 at 2:50 PM, Daniel Fischer <daniel.is.fischer at web.de>wrote:

> Am Montag, 15. Dezember 2008 23:16 schrieb Greg Meredith:
> > Haskellians,
> >
> > An even simpler version <http://paste.pocoo.org/show/95518/> that
> reveals
> > the issue. i'm astounded that the compiler literally just hangs.
> >
> > Best wishes,
> >
> > --greg
> >
> > On Mon, Dec 15, 2008 at 12:23 PM, Greg Meredith <
> >
> > lgreg.meredith at biosimilarity.com> wrote:
> > > Haskellians,
> > >
> > > The simple-minded and smallish code sample at this
> > > link<http://paste.pocoo.org/show/95503/>causes the compiler to go off
> > > into never-never land. Any clues would be greatly appreciated.
> > >
> > > Best wishes,
> > >
> > > --greg
>
> I can't confirm it, with 6.8.3:
>
> $ ghc -O2 --make Monoidal.hs
> [1 of 1] Compiling Monoidal         ( Monoidal.hs, Monoidal.o )
>
> Monoidal.hs:110:11:
>    Couldn't match expected type `i1'
>           against inferred type `Isomorpism (HFTensorExpr a i) a'
>      `i1' is a rigid type variable bound by
>           the instance declaration at Monoidal.hs:103:42
>    In the expression: (PutIn (\ a -> (HFTLVal a)))
>    In the third argument of `HFTExpr', namely
>        `[(PutIn (\ a -> (HFTLVal a)))]'
>    In the expression:
>        (HFTExpr
>           (HFTLVal a)
>           (HFTRVal b)
>           [(PutIn (\ a -> (HFTLVal a)))]
>           [(PutIn (\ b -> (HFTRVal b)))])
> $
>
> and the earlier version:
>
> $ ghc -O2 --make Monoidal2.hs
> [1 of 1] Compiling Monoidal2        ( Monoidal2.hs, Monoidal2.o )
>
> Monoidal2.hs:105:18:
>    Couldn't match expected type `HFTensorExpr a i'
>           against inferred type `[i1] -> [i1] -> HFTensorExpr a i1'
>    In the expression: HFTExpr (HFTLVal a) (HFTRVal b)
>    In the definition of `tMult':
>        a tMult b = HFTExpr (HFTLVal a) (HFTRVal b)
>    In the definition for method `tMult'
>
> Monoidal2.hs:122:10:
>    Couldn't match expected type `[]' against inferred type `++ msa'
>      Expected type: [i]
>      Inferred type: ++ msa msb
>    In the third argument of `HFTExpr', namely
>        `((Shuffle
>             (\ (HFTExpr (HFTExpr u v msu msv) w msuv msw)
>                  -> (tAssoc (HFTExpr (HFTExpr u v msu msv) w msuv msw))))
> ::
>            msa ++ msb)'
>    In the expression:
>        (HFTExpr
>           (HFTExpr a b msa msb)
>           c
>           ((Shuffle
>               (\ (HFTExpr (HFTExpr u v msu msv) w msuv msw)
>                    -> (tAssoc (HFTExpr (HFTExpr u v msu msv) w msuv msw))))
> ::
>              msa ++ msb)
>           msc)
>
> Monoidal2.hs:139:10:
>    Couldn't match expected type `[]' against inferred type `++ msl'
>      Expected type: [i]
>      Inferred type: ++ msl msr
>    In the third argument of `HFTExpr', namely
>        `((Shuffle
>             (\ (HFTExpr (HFTExpr a b msa msb) c msab msc)
>                  -> (tAssoc (HFTExpr (HFTExpr a b msa msb) c msab msc))))
> ::
>            msl ++ msr)'
>    In the expression:
>        (HFTExpr
>           (HFTExpr l r msl msr)
>           (HFTRVal b)
>           ((Shuffle
>               (\ (HFTExpr (HFTExpr a b msa msb) c msab msc)
>                    -> (tAssoc (HFTExpr (HFTExpr a b msa msb) c msab msc))))
> ::
>              msl ++ msr)
>           [(PutIn (\ b -> (HFTRVal b)))])
>
> Monoidal2.hs:150:11:
>    Couldn't match expected type `i1'
>           against inferred type `Isomorpism (HFTensorExpr a i) a'
>      `i1' is a rigid type variable bound by
>           the instance declaration at Monoidal2.hs:103:42
>    In the expression: (PutIn (\ a -> (HFTRVal a)))
>    In the third argument of `HFTExpr', namely
>        `[(PutIn (\ a -> (HFTRVal a)))]'
>    In the expression:
>        (HFTExpr
>           (HFTLVal a)
>           (HFTRVal b)
>           [(PutIn (\ a -> (HFTRVal a)))]
>           [(PutIn (\ b -> (HFTRVal b)))])
> $
>
> No hang, which compiler version did you use?
>



-- 
L.G. Meredith
Managing Partner
Biosimilarity LLC
806 55th St NE
Seattle, WA 98105

+1 206.650.3740

http://biosimilarity.blogspot.com
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20081215/07fa512a/attachment.htm


More information about the Haskell-Cafe mailing list