Re: ANNOUNCE: GHC 7.8.1 Release Candidate 1

2014-02-05 Thread Arie Peterson
On Wednesday 05 February 2014 15:53:41 Karel Gardas wrote:

> Tried, on my ubuntu 12.04.02, but it fails miserably. Modern GHC
> requires alex 3.1 and cabal alex fails with (due to QuickCheck template
> haskell dependency):
> 
> […]
> 
> So, well, Catch-22?

You can avoid this by installing QuickCheck without template haskell parts:

$ cabal install -f -templateHaskell QuickCheck

(syntax could be off).


Regards,

Arie

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


Re: ANNOUNCE: GHC 7.8.1 Release Candidate 1

2014-02-05 Thread Arie Peterson
On Monday 03 February 2014 16:35:14 Austin Seipp wrote:
> We are pleased to announce the first release candidate for GHC 7.8.1:
> […]
> This includes the source tarball and bindists for Windows, Linux, OS
> X, FreeBSD, and Solaris, on x86 and x86_64. […]

Has anyone by chance built it for arm, yet? If I understand correctly, with 
this new version, it should be possible to compile programs with a dependency 
on vector, on arm.


Regards,

Arie

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


Re: ghc stackfaults

2007-05-20 Thread Arie Peterson
John Meacham wrote:

| ghc 6.6 and 6.6.1 both go into infinite loops and eventually die with a
| stackfault when trying to compile the attached file with optimizations
| turned on.
|
| [...]
|
| > -- A term, can have values
| > newtype T v = V (T v)
| > deriving(Eq,Show,Ord)

This seems strange. Shouldn't it be 'newtype T v = T (V v)'?

I can imagine ghc running in circles trying to derive instances for T.


Regards,

Arie

-- 

Just follow the magic footprints.


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


Re: Template Haskell crashes unexpectedly...

2006-08-21 Thread Arie Peterson
Hello Brian,


> [snip]
> getInfo :: Q Info
> getInfo = reify (mkName "Car")
> [snip]
> -- Crashes if I try to print out the info
> -- info <- runQ getInfo
> -- putStrLn (pprint info)
> [snip]
>
> The example from the paper works fine with the few minor adjustements ie
> Expr --> ExpQ, lift --> stringE. However if I try and obtain the Info it
> compiles but then crashes at runtime (using ghc 6.4.2 on Windows).
>
> Any ideas? (Perhaps because the type doesn't exist - yet the first call to
> runQ (printf...) *does* work at runtime)

I seem to remember that 'reify' cannot be run in the IO monad. IIRC ghci
gives a nice error message saying this, so perhaps you can try to execute
'main' from within ghci to corroborate my suspicion.

> Also, I'm puzzled by the type of reify, because the name "Car" above
> should
> surely be both a TyConI and a DataConI so how does this function decide
> which to return the info about? I expected an extra parameter to determine
> what namespace to look the name up in.

The preferred way to refer to names that are in scope is by using the
quotation mechanism:

  'getNameis the name of the function 'getName'
  ''Objectis the name of the type 'Object'

This also makes the distinction you rightly wanted.


Greetings,

Arie

-- 

Mr. Pelican Shit may be Willy.

  ^
 /e\
 ---


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


partially applied type synonyms

2006-07-27 Thread Arie Peterson
Dear list,


Is there a good reason that partially applied type synonyms cannot be made
instances of classes?

- A simple example would be making the identity type 'Id' ("type Id x =
x") instance of 'Monad'. This would eliminate the need for some silly
occurrences of 'runIdentity', and perhaps narrow the gap between monads
and monad transformers.

- The reason I complain about this now is a more involved example, where
introducing a newtype to work around the restriction is not an option.
Well, not as far as I can see now, anyway.

Partially applied type synonyms are, in a sense, the anonymous functions
at the type level, and one might argue that they deserve the same
'first-class member status' as the lambda at the value level.


Kind regards,

Arie Peterson

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


Concurrency problems with Handle

2003-12-20 Thread Arie Peterson
Hello,

After many hours of vain debugging, I suspect that GHC might not do what I 
think it should do.

I made a module 'Telnet', exporting one function 'telnet', which takes a 
handle (an established connection) and returns an input channel, an output 
channel and a function to close the connection and clean up.
The 'telnet' function creates two channels (input and output), one MVar and 
two threads:
  * One thread takes chars from the output channel and writes them into 
the handle.
  * The other thread reads chars from the handle and puts them in the 
input channel.
  * The MVar regulates writing access to the handle: the reader thread 
sometimes has to respond to telnet commands, but those responses must not 
be interspersed with ordinary data.

Now, if I let one side of the connection send some characters:
  sequence_ $ take 10 $ repeat $ (writeChan outputChan 's')
and I let the other side consume them:
  sequence_ $ take 10 $ repeat $ (putChar =<< readChan inputChan)
then the characters are sent and received correctly, but the receiving side 
shows the characters only after the connection is closed.

If I let both sides send and consume characters in turn, like this:
  sequence_ $ take 10 $ repeat $ threadDelay 250 >> (writeChan outputChan 
's') >> (putChar =<< readChan inputChan)
and
  sequence_ $ take 10 $ repeat $ (putChar =<< readChan inputChan) >> 
threadDelay 250 >> (writeChan outputChan 'c')
, one character is sent, and the other end waits indefinitely before 
sending his character.

Maybe some buffering mechanism is holding my characters?
I already tried hFlush and setting buffering to NoBuffering on all handles.
Could it have anything to with this?
"One final note: the   example may not work too well on GHC (see 
Scheduling, above), due to the locking on a Handle. Only one thread may 
hold the lock on a Handle at any one time, so if a reschedule happens while 
a thread is holding the lock, the other thread won't be able to run. The 
upshot is that the switch from  to b happens infrequently. It can 
be improved by lowering the reschedule tick period. We also have a patch 
that causes a reschedule whenever a thread waiting on a lock is woken up, 
but haven't found it to be useful for anything other than this example :-)" 
(http://haskell.org/ghc/docs/latest/html/libraries/base/Control.Concurrent.html#11)

I tried all this both in compiled and interactive mode with GHC 6.0 and 6.2 
on Windows 2000.

Thanks for your time.

Arie Peterson

Telnet.hs, with many superfluous debugging output:
###
module Telnet (telnet) where
import Control.Concurrent (forkIO,killThread)
import Control.Concurrent.Chan (Chan,newChan,readChan,writeChan)
import Control.Concurrent.MVar (MVar,newMVar,takeMVar,putMVar)
import System.IO (Handle,hGetChar,hPutChar)
telnet :: Handle -> IO (Chan Char,Chan Char,IO ())
telnet handle = do
  inputChan <- newChan
  outputChan <- newChan
  writing <- newMVar ()
  readerId <- forkIO $ reader handle inputChan  writing
  writerId <- forkIO $ writer handle outputChan writing
  return
(
  inputChan,
  outputChan,
  do -- function to close connection
takeMVar writing
hPutChar handle '\255' -- IAC
hPutChar handle '\244' -- IP (Interrupt Process)
killThread readerId
killThread writerId
)
reader :: Handle -> Chan Char -> MVar () -> IO ()
reader handle inputChan writing = sequence_ . repeat $ do
  putStrLn "Telnet.reader: waiting for char in handle"
  c <- hGetChar handle
  putStrLn ("Telnet.reader: received " ++ show c)
  case c of
'\255' -> hGetChar handle >>= \c -> putStrLn ("Telnet.reader: received 
" ++ show c) >> case c of
  '\255' -> writeChan inputChan '\255' -- escaped IAC
  '\254' -> respond '\253'  -- received DONT, send WONT
  '\253' -> respond '\254'  -- received WONT, send DONT
  '\252' -> respond '\253'  -- received DO, send WONT
  '\251' -> respond '\254'  -- received WILL, send DONT
  _  -> return ()   -- received unknown command, ignore
c  -> writeChan inputChan c
   where
respond c = do
  d <- hGetChar handle
  putStrLn ("Telnet.reader: received " ++ show d ++ ", responding")
  takeMVar writing
  hPutChar handle '\255'
  hPutChar handle c
  hPutChar handle d
  putMVar writing ()

writer :: Handle -> Chan Char -> MVar () -> IO ()
writer handle outputChan writing = sequence_ . repeat $ do
  putStrLn "Telnet.writer: waiting for character in chan"
  c <- readChan outputChan
  putStrLn 

Re: overlapping instances

2003-10-15 Thread Arie Peterson

What would have GHC do for the "convert :: String -> String" case?
(You'd like "convert = id" here but it's not clear to me what the
general rule should be.)
mike
The general rule should be that convert :: a -> a = id, no matter what 
other instances are available.
Is there any way to tell GHC so? It would be nice to be able to define 
'precedences'.

Arie

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


overlapping instances

2003-10-15 Thread Arie Peterson
Hi all,

In an attempt to design a elegant way to serialise things to any serialised 
form, I came up with the following exotic solution:

###
{-# OPTIONS -fallow-undecidable-instances -fallow-overlapping-instances #-}
module Convertable where
class Convertable a b where
  convert :: a -> b
instance Convertable a a where
  convert = id
instance (Convertable a b,Convertable b c) => Convertable a c where
  convert = (convert :: b -> c) . (convert :: a -> b)
class (Convertable a b,Convertable b a) => Equivalent a b
###
Happily surprised to see GHC swallow this, I continued by adding

###
{-# OPTIONS -fallow-undecidable-instances -fallow-overlapping-instances #-}
module Serialise where
import Convertable
import Data.PackedString (PackedString,packString,unpackPS)
instance Convertable String PackedString where
  convert = packString
instance Convertable PackedString String where
  convert = unpackPS
instance (Show a) => Convertable a String where
  convert = show
instance (Read a) => Convertable String a where
  convert = read
###
But now GHC complains about overlapping instances:
"Overlapping instance declarations:
Serialise.hs:16: Convertable String a
Convertable.hs:7: Convertable a a"
Why can't GHC decide that the "Convertable String a" instance is more specific?
Apparently, there is no problem with the combination of "Convertable a a" 
and "Convertable a String": if I leave out "read", all is well. What is the 
difference with the above?

In the manual one can find:
"GHC is also conservative about committing to an overlapping instance. For 
example:
  class C a where { op :: a -> a }
  instance C [Int] where ...  instance C a => C [a] where ...
  f :: C b => [b] -> [b]  f x = op x
From the RHS of f we get the constraint C [b]. But GHC does not commit to 
the second instance declaration, because in a paricular call of f, b might 
be instantiate to Int, so the first instance declaration would be 
appropriate. So GHC rejects the program. If you add 
-fallow-incoherent-instances GHC will instead silently pick the second 
instance, without complaining about the problem of subsequent instantiations."
I do not understand why GHC can't choose between C [Int] (whenever f is 
parametrised with Int) or C [a] (whenever f is parametrised with anything 
else). (While checking the type of f, it is clear that the constraint C [b] 
is always met.) (Adding -fallow-incoherent-instances did not change anything.)

Thanks a lot for putting up with my English and my dubious type 
constructions :-).

Regards,

Arie Peterson

BTW: I would like to use this opportunity to express my content: I think 
haskell is a wonderful language (never, ever anymore javascript :s) and GHC 
is a, uhm, glorious compiler :-).

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users