GADT Strangeness

2008-12-21 Thread Dominic Steinitz
If I remove -XScopedTypeVariables from this http://hpaste.org/13230 then
I get the following error message:

 Asn1cTestNew.hs:55:27:
 GADT pattern match in non-rigid context for `INTEGER'
   Solution: add a type signature
 In the pattern: INTEGER
 In the definition of `referenceTypeAndValAux2':
 referenceTypeAndValAux2 ns INTEGER x
   = lhs ns  text  =   text (show x)  
 semi
 Failed, modules loaded: Language.ASN1, ASNTYPE.

At the very least the message is unhelpful. It was only by accident I
decided to put in -XScopedTypeVariables.

Can anyone offer an explanation as to what is happening?

Dominic.


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


Graham Hutton's calculator example for win32

2008-12-21 Thread Ahn, Ki Yung
In Graham Hutton's Programming in Haskell there is an interactive
calculator example using ANSI code to implement the UI on the terminal.
This example doesn't work on MS Windows XP or other MS OSes based on NT
kernel, since their command line does not support ANSI very well.

But, thanks to ansi-terminal on Hackage, I was able to extract minimal
code from the package to make a win32 version of the calculator example
in Hutton's book.

calculatorWin32.lhs and Win32ANSI.hs is an implementation for win32.
I extracted the win32 console API bindings for setting cursor positions
from ansi-terminal project and put them in Win32ANSI.hs. I had to put
this in a separate file because I had an issue with ghci.  To run this,
I had to compile the console API bindings with ghc first and then run
ghci as follows

 C:\ ghc -c Win32ANSI.hs
 C:\ ghci calculatorWin32.lhs

Without compiling the object code, ghci cannot find the proper link for
win32 console API FFI bindings.

 C:\ ghci calculatorWin32.lhs
GHCi, version 6.10.1: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer ... linking ... done.
Loading package base ... linking ... done.
[1 of 3] Compiling Parsing  ( Parsing.lhs, interpreted )
[2 of 3] Compiling Win32ANSI( Win32ANSI.hs, interpreted )

During interactive linking, GHCi couldn't find the following symbol:
  getconsolescreenbufferi...@8
This may be due to you not asking GHCi to load extra object files,
archives or DLLs needed by your current session.  Restart GHCi, specifying
the missing library using the -L/path/to/object/dir and -lmissinglibname
flags, or simply by naming the relevant files on the GHCi command line.
Alternatively, this link failure might indicate a bug in GHCi.
If you suspect the latter, please send a bug report to:
  glasgow-haskell-b...@haskell.org


Is this a bug or a natural behavior of ghci? This is strange to me
since ghci finds the proper link for the functions in the other C
libraries such as getch in conio.h.


In addition, I am attaching a patched calculator.lhs which works
for Unix/Linux on both GHC 6.8.x and GHC 6.10.1. The one currently
on the book homepage only works for GHC 6.8.x but not GHC 6.10.1.
This is due to the bug fix of hSetBuffering in GHC 6.10.1.

To run these calculator example you will also need Parsing.lhs from
the book hompage.http://www.cs.nott.ac.uk/~gmh/Parsing.lhs

--
  Ahn, Ki Yung
Calculator example from section 9.6 of Programming in Haskell,
Graham Hutton, Cambridge University Press, 2007.

Note: the definition for getCh in this example works with the
Glasgow Haskell Compiler, but may not work with some Haskell
systems, such as Hugs.  Moreover, the use of control characters
may not work on some systems, such as WinHugs.

Note: This code works on GHC versions 6.10.1 on MS Windows command line
  using the code extracted from ansi-termial-0.5.0 package.  You will need
  Win32ANSI.hs in addition to Parsing.hs. To run this code you should invoke
  the compiler first to compile Win32ANSI.o and then the run ghci as follows:
  $ ghc -c Win32ANSI.hs
  $ ghci calculatorWin32.lhs
  ...
  Ahn, Ki Yung

 {-# LANGUAGE ForeignFunctionInterface#-}
 import Parsing
 import Win32ANSI (setCursorPosition)

 import Monad
 import Char

 import System.IO
 import System.Info (os)
 import System.Cmd (system)

 import Foreign.C

Parser for expressions
--

 expr  :: Parser Int
 expr  =  do t - term
 do symbol +
e - expr
return (t + e)
  +++ do symbol -
 e - expr
 return (t - e)
  +++ return t
 
 term  :: Parser Int
 term  =  do f - factor
 do symbol *
t - term
return (f * t)
  +++ do symbol /
 t - term
 return (f `div` t)
  +++ return f

 factor:: Parser Int
 factor=  do symbol (
 e - expr
 symbol )
 return e
   +++ integer

Derived primitives
--

 getCh :: IO Char
 getCh =  liftM (chr . fromEnum) c_getch
 foreign import ccall unsafe conio.h getch c_getch :: IO CInt

 beep  :: IO ()
 beep  =  do putStr \BEL

Re: Can't compile GHC 6.8.2

2008-12-21 Thread Uwe Hollerbach
On 12/19/08, Simon Marlow marlo...@gmail.com wrote:
 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'd guess that the size of the binary has caused some kind of overflow of a
 short relocation field.  Any experts in MacOS linking around?

 You might want to try the testsuite with stage1 and see whether the failure
 shows up anywhere else.

 Cheers,
   Simon

Thanks, I will try that and see what I can find out.

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


Re: unique identifiers as a separate library

2008-12-21 Thread Iavor Diatchki
Hello,
I have made the two changes that Simon suggested and uploaded a new
version of the library.   By the way, GHC seemed to work correctly
even without the extra boolean parameter, perhaps it treats
unsafePerformIO specially somehow?  A somewhat related question:  I
ended up using three calls to unsafeInterleaveIO which seems like a
bit much.  Could I have done it in a different way somehow?  This is
what I did:

gen r = do v - unsafeInterleaveIO (genSym r)
   ls - unsafeInterleaveIO (gen r)
   rs - unsafeInterleaveIO (gen r)
   return (Node v ls rs)

Note that a single unsafeInterleaveIO around the whole do block is not
quite right (this is what the code in the other package does) because
this will increment the name as soon as the generator object is
forced, and we want the name to be increment when the name is forced.

-Iavor




On Fri, Dec 19, 2008 at 1:24 AM, Simon Marlow marlo...@gmail.com wrote:
 Why not depend on this instead?

 http://hackage.haskell.org/cgi-bin/hackage-scripts/package/value-supply

 Looking at the code for this, I'm somewhat suspicious that it actually works
 with GHC:

  -- The extra argument to ``gen'' is passed because without
  -- it Hugs spots that the recursive calls are the same but does
  -- not know that unsafePerformIO is unsafe.
  where gen _ r = Node { supplyValue  = unsafePerformIO (genSym r),
 supplyLeft   = gen False r,
 supplyRight  = gen True r }

 even if that extra Bool argument is enough to fool Hugs, I wouldn't count on
 it being enough to fool GHC -O2!  You probably want to use
 unsafeInterleaveIO like we do in GHC's UniqSupply library.

 Also, I'd replace the MVar with an IORef and use atomicModifyIORef for
 speed.

 Cheers,
Simon

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


Possible Haddock bug affecting GHC docs

2008-12-21 Thread Krzysztof Skrzętnicki
Hello everyone

Please visit these to pages:
http://www.haskell.org/ghc/docs/6.8.3/html/libraries/haskell98/CTypes.html
-- ver 0.9
http://www.haskell.org/ghc/docs/6.10.1/html/libraries/haskell98/CTypes.html
-- ver 2.3.0

They show documentation produced by Haddock.

The problem is: on the second page (for GHC 6.10.1) there is no
information about exported module:

 module CTypes (module Foreign.C.Types) where
 import Foreign.C.Types

It seems it has something to do with bug fixed by 2.3.0 version of
Haddock: (see http://haskell.org/haddock/CHANGES.txt )

 Changed in version 2.3.0:
 (...)
  * Fix a bug that made hidden modules show up in the contents  index pages
 (...)

This is really annoying, especially that documentation on page doesn't
contain links for source code. I think this should be fixed too.
I also checked that information about exported modules appears when
there is more thing to export like in Control.Concurrent.

I didn't file a Haddock bug since I failed to make minimal example
that reproduces the bug.

A.hs:
 module A (module B) where

 import B

B.hs:
 module B (one,two) where

 one :: Int
 one = 1

 two :: Int
 two = 2

Turns out to generate good documentation. Perhaps there is something
more to be done to actually trigger the bug.
I attach my testing suite (A.hs, B.hs, Makefile, results).

All best

Christopher Skrzętnicki


haddock-bug.7z
Description: Binary data
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Type families: module export of instance data constructor

2008-12-21 Thread Wolfgang Jeltsch
Am Montag, 15. Dezember 2008 02:17 schrieb Ben Horsfall:
 I have a type family

 class Lang term where
   data Token term :: *

 with

 instance Lang Term where
   newtype Token Term = T String

 I can't work out how to export the type constructor T from the module,
 unless I make no explict exports from the module at all.


 Ben

Hello Ben,

try

Lang (type Token)

in the export list.

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


Re: Type families: module export of instance data constructor

2008-12-21 Thread Ben Horsfall
Hi Wolfgang,

On Mon, Dec 22, 2008 at 12:23 PM, Wolfgang Jeltsch
g9ks1...@acme.softbase.org wrote:
 Am Montag, 15. Dezember 2008 02:17 schrieb Ben Horsfall:
 I have a type family

 class Lang term where
   data Token term :: *

 with

 instance Lang Term where
   newtype Token Term = T String

 I can't work out how to export the type constructor T from the module,
 unless I make no explict exports from the module at all.


 Ben

 Hello Ben,

 try

Lang (type Token)

 in the export list.

 Best wishes,
 Wolfgang

That exports just the name of the associated type from the type class,
as far as I can see, and syntax like Lang (type Token (..)) is not
allowed. That would improperly mix the classes and instances, for one
thing. But perhaps something similar ought to be permited for
associated type instances, as in my example. Something like:

module Term (Term (Token Term (T)))

is what I'd have in mind.

In the meantime, I can step around the issue by making Token a
top-level type familiy alongside the Lang class:

data family Token term :: *

with instance:

newtype instance Token Term = T String

alongside the instance Lang Term, allowing me to make the module
exports I wanted in the usual style:

module Term (Term (..), Token (T))

But this is a bit curious. The module might have contained more than
one instance of Token, and this syntax mentions the name of the type
family and a constructor for an instance of it, but not the type
instance Token Term itself (although a constructor will always
uniquely determine a type instance).

This reminds me to mention that I've had the class and instance
declarations in separate modules all along. Also, I'm using GHC
6.10.1.


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


Re: Type families: module export of instance data constructor

2008-12-21 Thread Ben Horsfall
I'm afraid I'd got into a muddle, and all of this can be ignored.

In general, top-level and associated type instances get the same
syntactic treatment in module exports, and the problem I had in the
first place was due to another mistake.


Ben

On Mon, Dec 22, 2008 at 4:26 PM, Ben Horsfall ben.horsf...@gmail.com wrote:
 Hi Wolfgang,

 On Mon, Dec 22, 2008 at 12:23 PM, Wolfgang Jeltsch
 g9ks1...@acme.softbase.org wrote:
 Am Montag, 15. Dezember 2008 02:17 schrieb Ben Horsfall:
 I have a type family

 class Lang term where
   data Token term :: *

 with

 instance Lang Term where
   newtype Token Term = T String

 I can't work out how to export the type constructor T from the module,
 unless I make no explict exports from the module at all.


 Ben

 Hello Ben,

 try

Lang (type Token)

 in the export list.

 Best wishes,
 Wolfgang

 That exports just the name of the associated type from the type class,
 as far as I can see, and syntax like Lang (type Token (..)) is not
 allowed. That would improperly mix the classes and instances, for one
 thing. But perhaps something similar ought to be permited for
 associated type instances, as in my example. Something like:

 module Term (Term (Token Term (T)))

 is what I'd have in mind.

 In the meantime, I can step around the issue by making Token a
 top-level type familiy alongside the Lang class:

 data family Token term :: *

 with instance:

 newtype instance Token Term = T String

 alongside the instance Lang Term, allowing me to make the module
 exports I wanted in the usual style:

 module Term (Term (..), Token (T))

 But this is a bit curious. The module might have contained more than
 one instance of Token, and this syntax mentions the name of the type
 family and a constructor for an instance of it, but not the type
 instance Token Term itself (although a constructor will always
 uniquely determine a type instance).

 This reminds me to mention that I've had the class and instance
 declarations in separate modules all along. Also, I'm using GHC
 6.10.1.


 Ben

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