Re: Type signature inside an instance declaration

2008-12-16 Thread Kwanghoon Choi
Many thanks for your helps.

Kwanghoon

On Tue, Dec 16, 2008 at 11:22 PM, Thomas Schilling
nomin...@googlemail.comwrote:

 {-# LANGUAGE ScopedTypeVariables #-}

 2008/12/16 Neil Mitchell ndmitch...@gmail.com:
   Hi
 
  You want to use `asTypeOf`, with a lazy pattern to name a value of type
 'a'.
 
 pr xs = [ ++ pr (undefined `asTypeOf` x) ++ ]
 where (x:_) = xs
 
  I prefer:
 
  pr xs = [ ++ pr (undefined `asTypeOf` head x) ++ ]
 
  Or even more simply:
 
  pr xs = [ ++ pr (head x) ++ ]
 
  I do believe there is some GHC extension that can be turned on to
  refer to variables like you did, but its not standard Haskell.
 
  Thanks
 
  Neil
  ___
  Glasgow-haskell-users mailing list
  Glasgow-haskell-users@haskell.org
  http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
 



 --
 Push the envelope.  Watch it bend.
  ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Type signature inside an instance declaration

2008-12-16 Thread Thomas Schilling
{-# LANGUAGE ScopedTypeVariables #-}

2008/12/16 Neil Mitchell ndmitch...@gmail.com:
 Hi

 You want to use `asTypeOf`, with a lazy pattern to name a value of type 'a'.

pr xs = [ ++ pr (undefined `asTypeOf` x) ++ ]
where (x:_) = xs

 I prefer:

 pr xs = [ ++ pr (undefined `asTypeOf` head x) ++ ]

 Or even more simply:

 pr xs = [ ++ pr (head x) ++ ]

 I do believe there is some GHC extension that can be turned on to
 refer to variables like you did, but its not standard Haskell.

 Thanks

 Neil
 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users




-- 
Push the envelope.  Watch it bend.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Type signature inside an instance declaration

2008-12-16 Thread Malcolm Wallace
Kwanghoon Choi lazysw...@gmail.com wrote:

 =
 instance Arg a = Arg [a] where
   pr _ = [ ++ pr (undefined :: a) ++ ]
 =

You want to use `asTypeOf`, with a lazy pattern to name a value of type 'a'.

pr xs = [ ++ pr (undefined `asTypeOf` x) ++ ]
where (x:_) = xs

or
pr ~(x:_) = [ ++ pr (undefined `asTypeOf` x) ++ ]

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: length of module name affecting performance??

2008-12-16 Thread Simon Marlow

Daniel GorĂ­n wrote:

On Dec 15, 2008, at 10:43 PM, Don Stewart wrote:


dons:

Running time as a function of module name length,

   http://galois.com/~dons/images/results.png

10 is the magic threshold, where indirections start creeping in.

Codegen cost heuristic fail?


Given this, could you open a bug ticket for it, with all the info we
have,

   http://hackage.haskell.org/trac/ghc/newticket?type=bug

E.g. the graph, the code, the asm diff.

Cheers,
 Don


done! http://hackage.haskell.org/trac/ghc/ticket/2884


I followed up on the ticket.  Basically the problem is to do with inlining 
of record selectors: when the module name is too long, none of the record 
selectors get inlined.


Cheers,
Simon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Type signature inside an instance declaration

2008-12-16 Thread Kwanghoon Choi
===
module Test where
class Arg a where
  pr :: a - String
instance Arg Int where
  pr _ = i
instance Arg Char where
  pr _ = c
instance Arg a = Arg [a] where
  pr _ = [ ++ pr (undefined :: a) ++ ]  -- the type variable 'a' is
interpreted as an unbound one.
  -- (1) pr :: [a] - String
  -- (2) pr (_ :: [a]) = [ ++ pr (undefined :: a) ++ ]
===

Dear All,

I got some problem when I try to compile the above program.

The problem is due to the presence of a type variable 'a' in the body of the
last instance declaration.
How could I refer to the type variable of Arg [a] in the instance
declaration?

I tried these options
   1) by giving an explicit declaration for pr
   2) by giving a type signature to the argument of pr with
-XPatternsSignatures

The first option gives me back an error :
Misplaced type signature: pr :: [a] - String
The type signature must be given where `pr' is declared

The second option gives me an error:
Test.hs:21:12: Not in scope: type variable `a'

Would anybody help me to understand this problem?

Thanks in advance.

Kwanghoon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Type signature inside an instance declaration

2008-12-16 Thread Neil Mitchell
Hi

 You want to use `asTypeOf`, with a lazy pattern to name a value of type 'a'.

pr xs = [ ++ pr (undefined `asTypeOf` x) ++ ]
where (x:_) = xs

I prefer:

pr xs = [ ++ pr (undefined `asTypeOf` head x) ++ ]

Or even more simply:

pr xs = [ ++ pr (head x) ++ ]

I do believe there is some GHC extension that can be turned on to
refer to variables like you did, but its not standard Haskell.

Thanks

Neil
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: length of module name affecting performance??

2008-12-16 Thread Chris Kuklewicz
I suddenly wonder if renaming Text.ParserCombinators.Parsec.Combinator would 
be a performance hack


--
C
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Can't compile GHC 6.8.2

2008-12-16 Thread Uwe Hollerbach
Hello Barney  all, I've been following your messages with some
interest, as I too have been trying to build a more-modern ghc on my
G3 iMac running 10.3.9. I started with an existing 6.6.1 build, and
tried to build 6.8.3; I'm finally at the point where I have something
to report, although I'm not sure if it's a success or a failure
report... :-/

I applied your patch to package.conf.in (approximately; the relevant
section wasn't quite identical), edited rts/Linker.c to add #define
LC_SEGMENT_64 LC_SEGMENT, and hacked up a wrapper script around ar to
always ranlib the library being processed; you had mentioned patching
cabal, but I decided the wrapper around ar was easier... a hack, but
what the hell.

After that, configure  make ran to completion without errors
(although it took a couple of days, since I had all the extralibs).

Success! ... or is it?

I installed the new compiler into /usr/local, then tested it by trying
ghc -v. Alas, no joy! It died with some dynamic-link error which
I've approximately reproduced here:

lupus:~/ghc-6.8.3% ghc-6.8.3 -v
dyld: relocation error (external relocation for symbol _pthread_mutex_unlock
in ghc-6.8.3 relocation entry 0 displacement too large)Trace/BPT trap

Failure! ... or is it?

I thought, how can this be?!? It built itself through stage2, it has
to be good! But clearly it isn't... So I tried one last thing: I tried
to use the stage1 compiler directly to compile the scheme interpreter
I wrote nearly a year ago. That initially failed, too, but for a
simple reason, and one I could work around: no readline in ghc 6.8.3.
Once I changed the scheme interpreter to not use readline, it
compiled, linked, and runs.

So... success or failure? I'm really not quite sure... I guess I could
try installing the stage1 compiler instead of the stage2 compiler, it
seems that it might work. But it would appear that there is still
something not entirely right in there.

regards,
Uwe
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users