Re: Unicode windows console output.

2010-11-01 Thread David Sankel
On Mon, Nov 1, 2010 at 10:20 PM, David Sankel  wrote:

> Hello all,
>
> I'm attempting to output some Unicode on the windows console. I set my
> windows console code page to utf-8 using "chcp 65001".
>
> The program:
>
> -- Test.hs
> main = putStr "λ.x→x"
>
>
> The output of `runghc Test.hs`:
>
> λ.x→
>
>
> From within ghci, typing `main`:
>
> λ*** Exception: : hPutChar: permission denied (Permission denied)
>
>
> I suspect both of these outputs are evidence of bugs. Might I be doing
> something wrong? (aside from using windows ;))
>
>
I forgot to mention that I'm using Windows XP with ghc 6.12.3.


-- 
David Sankel
Sankel Software
www.sankelsoftware.com
585 617 4748 (Office)
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Unicode windows console output.

2010-11-01 Thread David Sankel
Hello all,

I'm attempting to output some Unicode on the windows console. I set my
windows console code page to utf-8 using "chcp 65001".

The program:

-- Test.hs
main = putStr "λ.x→x"


The output of `runghc Test.hs`:

λ.x→


>From within ghci, typing `main`:

λ*** Exception: : hPutChar: permission denied (Permission denied)


I suspect both of these outputs are evidence of bugs. Might I be doing
something wrong? (aside from using windows ;))

TIA,

David

-- 
David Sankel
Sankel Software
www.sankelsoftware.com
585 617 4748 (Office)
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: ANNOUNCE: GHC 7.0.1 Release Candidate 2

2010-11-01 Thread Christian Maeder
Am 29.10.2010 20:38, schrieb Ian Lynagh:
> 
> We are pleased to announce the second release candidate for GHC 7.0.1:
> 
> http://new-www.haskell.org/ghc/dist/7.0.1-rc2/

Works fine for me. I need a higher -fcontext-stack of 31 (instead of 20)
and the compile time without optimization increased from 9 to 15 minutes
(which isn't bad).

Cheers C.

> 
> This includes the source tarball, installers for OS X and Windows, and
> bindists for amd64/Linux, i386/Linux, amd64/FreeBSD and i386/FreeBSD.
> 
> Amongst the changes since RC 1 are:
> 
> * -fglasgow-exts now gives a deprecated warning, and no longer enables
>   GADTs or TypeFamilies.
> 
> * The haskell98 packge is no longer automatically linked, although this
>   often won't make a difference as --make is now enabled by default.
> 
> Please test as much as possible; bugs are much cheaper if we find them
> before the release!
> 
> 
> Thanks
> Ian, on behalf of the GHC team
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC.Types consturctors with #

2010-11-01 Thread Daniel Fischer
On Monday 01 November 2010 18:40:00, Larry Evans wrote:
> http://www.haskell.org/ghc/docs/6.10.2/html/libraries/ghc-prim/GHC-Types
>.html
>
> contains:
>
> data Int = I# Int#
>
> What does I# Int# mean?  I've tried a simple interpretation:
>
>   Prelude GHC.Types> I# 5#
>
>   :1:5: parse error (possibly incorrect indentation)
>   Prelude GHC.Types>
>
> but obviously that failed :(

Needs

ghci> :set -XMagicHash

then it will print 5.

GHC uses the magic hash to denote unboxed raw types and data constructors 
using those.

The point is, I think, making them stand out and avoiding accidental use 
(most of the time you're fine using the regular boxed things and letting 
GHC unbox them, but for when that's not good enough, you can use the low-
level stuff directly).

>
> TIA.
>
> -Larry

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


Re: GHC.Types consturctors with #

2010-11-01 Thread David Peixotto
Hi Larry,

GHC allows you to work with unboxed types. Int# is the type of unboxed ints. I# 
is a normal data constructor. So we can see that GHC represents a (boxed) Int 
as a normal algebraic data type

data Int = I# Int#

which says that an Int is a type with a single constructor (I#) that wraps a 
machine integer (Int#). By convention, unboxed types use a # in their name.

You can find more info about unboxed types here: 
http://www.haskell.org/ghc/docs/6.12.2/html/users_guide/primitives.html#glasgow-unboxed

To work with unboxed types in your code (or ghci) you need the MagicHash 
extension: 
http://www.haskell.org/ghc/docs/6.12.2/html/users_guide/syntax-extns.html#magic-hash

$ ghci -XMagicHash
GHCi, version 6.12.3: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Loading package ffi-1.0 ... linking ... done.
Prelude> import GHC.Types
Prelude GHC.Types> I# 5#
5
Prelude GHC.Types> 

-David


On Nov 1, 2010, at 12:40 PM, Larry Evans wrote:

> http://www.haskell.org/ghc/docs/6.10.2/html/libraries/ghc-prim/GHC-Types.html
> 
> contains:
> 
> data Int = I# Int#
> 
> What does I# Int# mean?  I've tried a simple interpretation:
> 
>  Prelude GHC.Types> I# 5#
> 
>  :1:5: parse error (possibly incorrect indentation)
>  Prelude GHC.Types>
> 
> but obviously that failed :(
> 
> TIA.
> 
> -Larry
> 
> ___
> 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


GHC.Types consturctors with #

2010-11-01 Thread Larry Evans
http://www.haskell.org/ghc/docs/6.10.2/html/libraries/ghc-prim/GHC-Types.html

contains:

data Int = I# Int#

What does I# Int# mean?  I've tried a simple interpretation:

  Prelude GHC.Types> I# 5#

  :1:5: parse error (possibly incorrect indentation)
  Prelude GHC.Types>

but obviously that failed :(

TIA.

-Larry

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


Re: Wadler space leak

2010-11-01 Thread Jan Christiansen


On 01.11.2010, at 10:38, Simon Marlow wrote:


On 28/10/2010 14:21, Bertram Felgenhauer wrote:



Right. The optimization works by producing special thunks for tuple
selectors which the garbage collector can recognize and evaluate
during GC.

However the implementation in GHC is quite brittle. See

http://hackage.haskell.org/trac/ghc/ticket/2607

I suspect your program is another instance of this behaviour.


Yes, that's exactly what happens.


Thanks very much for the explanation.

It seems to me that this bug is not considered as high priority. Is  
this correct? So it is not likely that this will be fixed in one of  
the next ghc releases, is it?


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


Re: Forall and type synonyms in GHC 7.0

2010-11-01 Thread Mario Blažević



I had the exact same problem in my regional-pointers package in the
withArray function:

withArray ∷ (Storable α, MonadCatchIO pr)
   ⇒ [α]
   → (∀ s. RegionalPtr α (RegionT s pr) → RegionT s pr β)
   → pr β

  I had to replace the original:

withArray vals = withArrayLen vals ∘ const

with:

withArray vals f = withArrayLen vals $ \_ → f

where:

withArrayLen ∷ (Storable α, MonadCatchIO pr)
 ⇒ [α]
 → (∀ s. Int → RegionalPtr α (RegionT s pr) → RegionT s pr β)
 → pr β

So unfortunately you gave to inline the function composition:

pair2 combinator = pair1 $ \b ->  combinator (chooseBinder b)



	This worked for me, thank you! I was worried I'd have to make a 
sweeping change to the module interfaces. I find this solution rather 
surprising, but as long as it's localized I don't mind.




Note that in the other thread I'm describing a similar problem in my
usb-safe package. Where in essence the problem is that the following
won't type check:

foo :: (forall s. ST s a) ->  a
foo st = ($) runST st

but the following will:

foo :: (forall s. ST s a) ->  a
foo st = runST st

and surprisingly the following will also type check:

foo :: (forall s. ST s a) ->  a
foo st = runST $ st



	Yes, I hadn't seen that thread until this morning. The same issue with 
impredicative types appears to cause my problem and both problems you've 
encountered. I wonder what percentage of Hackage libraries will be 
affected by the change.

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


Re: new-www

2010-11-01 Thread Brent Yorgey
On Sat, Oct 30, 2010 at 01:08:50PM +0400, Serge D. Mechveliani wrote:
> People,
> what is, in short, the relation between  www.haskell.org   and  
> new-www.haskell.org ?
> Which one do I need to use for looking for the Haskell materials, 
> for GHC materials?

As far as I can tell, new-www is just a sample mock-up of a potential
new design for www.haskell.org.  If you look carefully you will note
that all the events listed at new-www are old.  www.haskell.org is
and will continue to be the place to go.

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


haskell98 package not linked by default in 7.0.1 (was: Re: making 7.01-pre)

2010-11-01 Thread Simon Marlow

On 30/10/2010 16:52, David Fox wrote:

On Sat, Oct 30, 2010 at 4:43 AM, Serge D. Mechveliani  wrote:

Dear GHC developers,

I am testing this fresh  ghc-7.0.0.20101028
on  Debian Linux, i386-family.
Making it from source by  ghc-6.12.3  is all right.
Then, making it from source by itself reports
(here I abbreviate the messages by inserting `...')

-
+ test -f mk/config.mk.old
+ cp -p mk/config.mk mk/config.mk.old
...
...
"inplace/bin/mkdirhier" utils/ghc-cabal/dist/build/tmp//.
"inplace/bin/mkdirhier" bootstrapping/.
"/home/mechvel/ghc/7.01pre/inst1/bin/ghc" -H32m -O --make
  utils/ghc-cabal/ghc-cabal.hs -o utils/ghc-cabal/dist/build/tmp/ghc-cabal
...
...
"rm" -f compiler/stage1/ghc_boot_platform.h
Creating compiler/stage1/ghc_boot_platform.h...
Done.
"/usr/bin/gcc"  -fno-stack-protector  -DTABLES_NEXT_TO_CODE -Iincludes
  -Irts  -DGEN_HASKELL  -c includes/mkDerivedConstants.c -o
includes/dist-ghcconstants/build/mkDerivedConstants.o
...
...
...
utils/genprimopcode/dist/build/Lexer.o: In function `s2yT_info':
(.text+0x1e1d): undefined reference to
  `__stginit_arrayzm0zi3zi0zi2_DataziArray_'
...
...
utils/genprimopcode/dist/build/Parser.o: In function `s4pK_info':
(.text+0x5691): undefined reference to
`__stginit_arrayzm0zi3zi0zi2_DataziArray_'
collect2: ld returned 1 exit status
make[1]: *** [utils/genprimopcode/dist/build/tmp/genprimopcode] Error 1
make: *** [all] Error 2
-

Why cannot it make itself?


genprimopcode now needs -package array to build.  We'll fix this in the 
build system but it raises an interesting point that we probably haven't 
publicised much.


Previously we linked the haskell98 package by default, which also caused 
its dependencies (include array) to also be linked, but in 7.0.1 we 
don't link haskell98 by default, only base.


If you're using --make (which is now the default in 7.0.1), you won't 
notice any difference, because all package dependencies are 
automatically linked, so this only makes a differences in "one-shot" 
mode where you compile each module to .o files first and then link by 
saying


  ghc Main.o Foo.o Bar.o -o prog

So if you're doing this, and the program has dependencies on modules not 
in base, then you need to list them explicitly, e.g.


  ghc -package haskell98 Main.o Foo.o Bar.o -o prog

This is part of moving from Haskell 98 to Haskell 2010 as our default 
base language.


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


Re: Wadler space leak

2010-11-01 Thread Simon Marlow

On 28/10/2010 14:21, Bertram Felgenhauer wrote:

Hi,


   let (first,rest) = break (const False) input
   in
   print (length (first ++ rest))

When I compile this program using -O2 and use a large text file as
input the code runs in constant space. If I understand correctly,
the program runs in constant space because ghc uses an optimization
similar to the one proposed by Wadler/Sparud.


Right. The optimization works by producing special thunks for tuple
selectors which the garbage collector can recognize and evaluate
during GC.

However the implementation in GHC is quite brittle. See

 http://hackage.haskell.org/trac/ghc/ticket/2607

I suspect your program is another instance of this behaviour.


If I define the following function which is based on break

   splitBy :: (a ->  Bool) ->  [a] ->  [[a]]
   splitBy _ []  = []
   splitBy p xs  =
 l : case ys of
  []   ->  []
  _:zs ->  splitBy' p zs
 where
   (l,ys) = break p xs


I haven't looked in detail; what follows is a guess of what
ghc may be doing. It could be verified by looking at the
generated core.

The where-binding desugars to something like

 let q = break p xs
 ys = case q of (_, ys) ->  ys
 l = case q of (l, _) ->  l
 in  ...

ys can be inlined into splitBy, producing

 l : case (case q of (l, ys) ->  ys) of
  []   ->  []
  _:zs ->  splitBy' p zs

 l : case q of (l, ys) ->  case ys of
  []   ->  []
  _:zs ->  splitBy' p zs

and now the tuple selector is no longer recognizable.


Yes, that's exactly what happens.

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


RE: Type error in GHC-7 but not in GHC-6.12.3

2010-11-01 Thread Simon Peyton-Jones
OK now I see.  

You are using impredicative polymorphism.  As I mentioned in my last message 
I've simplified the treatment of impredicativity to follow (more or less) QML: 
http://research.microsoft.com/en-us/um/people/crusso/qml/


In the call to useWhich

useWhich devs withDevice p f

you can see that 
withDevice ∷ Monad pr
   ⇒ Device
   → (∀ s. RegionalDeviceHandle (RegionT s pr) → RegionT s pr α)
   → pr α

useWhich ∷ ∀ k desc e (m ∷ * → *) α
 . (GetDescriptor e desc)
 ⇒ [e]
 → (e → k → m α)
 → (desc → Bool)
 → k
 → m α

So it follows that you must instantiate 
k = (∀ s. RegionalDeviceHandle (RegionT s pr) → RegionT s pr α)
Arguably GHC should complain at this point unless you use 
-XImpredicativePolymorphism, but it doesn't.
   
Now, the arguemnnt 'f' in the call, is apparently compatible with this type 
*except* that f's type is instantiated.  What you want is a way to say "don't 
instantiate f here".  QML provides a way to do that, via a "rigid" type 
signature, but GHC currently does not.  (Pressure of time, plus impredicativity 
is a somewhat obscure feature.)

So I guess I should implement rigid type signatures.  As ever the problem is 
syntax.

To work around this, use a newtype to the forall in the last argument of 
useWhich.

Simon


| -Original Message-
| From: Bas van Dijk [mailto:v.dijk@gmail.com]
| Sent: 30 October 2010 00:58
| To: glasgow-haskell-users@haskell.org
| Cc: Simon Peyton-Jones
| Subject: Re: Type error in GHC-7 but not in GHC-6.12.3
| 
| On Fri, Oct 29, 2010 at 5:42 PM, Simon Peyton-Jones
|  wrote:
| > That looks odd.
| >
| > Can you isolate it for us?  The easiest thing is usually to start with the
| offending code:
| > withDeviceWhich ∷
| >  ∀ pr α
| >  . MonadCatchIO pr
| >  ⇒ USB.Ctx
| >  → (USB.DeviceDesc → Bool)
| >  → (∀ s. RegionalDeviceHandle (RegionT s pr) → RegionT s pr α)
| >  → pr α
| > withDeviceWhich ctx p f = do
| >  devs ← liftIO $ USB.getDevices ctx
| >  useWhich devs withDevice p f
| >
| > Now add local definitions for each of the functions mentioned, with 
definition foo
| = undefined.
| >
| > useWhich ∷
| >  ∀ k desc e (m ∷ * → *) α
| >  . (GetDescriptor e desc, MonadIO m)
| >  ⇒ [e]
| >  → (e → k → m α)
| >  → (desc → Bool)
| >  → k
| >  → m α
| > useWhich = undefined.
| >
| > Now all you need is the types involved, and you can probably define them as
| >
| > data RegionT s pr a
| >
| > etc
| >
| > That should give a standalone test case.
| >
| > Thanks!
| >
| > SImon
| >
| 
| Ok, Here's the more isolated program which still gives the same error
| as the full usb-safe (on the latest ghc-HEAD (7.1.20101029)):
| 
| 
| USBSafeTest.hs:39:57:
| Couldn't match expected type `forall s.
|   RegionalDeviceHandle (RegionT s pr)
| -> RegionT s pr α'
| with actual type `RegionalDeviceHandle (RegionT s pr)
|   -> RegionT s pr α'
| In the fourth argument of `useWhich', namely `f'
| In the expression: useWhich devs withDevice p f
| In the expression:
|   do { devs <- return [Device];
|useWhich devs withDevice p f }
| 
| 
| {-# LANGUAGE UnicodeSyntax
|, KindSignatures
|, RankNTypes
|, MultiParamTypeClasses
|, FunctionalDependencies
|   #-}
| 
| import Data.List (find)
| 
| data Ctx = Ctx
| data Device = Device
| data DeviceDesc = DeviceDesc
| data RegionalDeviceHandle (r ∷ * → *) = RegionalDeviceHandle
| data RegionT s (pr ∷ * → *) α = RegionT
| 
| instance Monad pr ⇒ Monad (RegionT s pr) where
| return = undefined
| (>>=)  = undefined
| 
| runRegionT ∷ (∀ s. RegionT s pr α) → pr α
| runRegionT = undefined
| 
| openDevice ∷ Device → RegionT s pr (RegionalDeviceHandle (RegionT s pr))
| openDevice = undefined
| 
| withDevice ∷ Monad pr
|⇒ Device
|→ (∀ s. RegionalDeviceHandle (RegionT s pr) → RegionT s pr α)
|→ pr α
| withDevice dev f = runRegionT $ openDevice dev >>= f
| 
| withDeviceWhich ∷ ∀ pr α
| . Monad pr
| ⇒ Ctx
| → (DeviceDesc → Bool)
| → (∀ s. RegionalDeviceHandle (RegionT s pr) → RegionT s pr α)
| → pr α
| withDeviceWhich ctx p f = do devs ← return [Device]
|  useWhich devs withDevice p f
| 
| useWhich ∷ ∀ k desc e (m ∷ * → *) α
|  . (GetDescriptor e desc)
|  ⇒ [e]
|  → (e → k → m α)
|  → (desc → Bool)
|  → k
|  → m α
| useWhich ds w p f = case find (p . getDesc) ds of
|   Nothing → error "not found"
|   Just d  → w d f
| 
| class GetDescriptor α desc | α → desc, desc → α where
| getDesc ∷ α → desc
| 
| instance GetDescriptor Device DeviceDesc where
| getDesc = undefined
| 
| 
| I could isolate it a bit more if you want.
| 
| Thanks,

RE: Type error in GHC-7 but not in GHC-6.12.3

2010-11-01 Thread Simon Peyton-Jones
| foo :: (forall s. ST s a) -> a
| foo st = ($) runST st

This is a motivating example for type inference that can deal with 
impredicative types.  Consider the type of ($):
($) :: forall p q.  (p->q) -> p -> q
In the example we need to instantiate 'p' with (forall s. ST s a), and that's 
what impredicative polymorphism means: instantiating a type variable with a 
polymorphic type.

Sadly, I know of no system of reasonable complexity that can typecheck 'foo' 
unaided.  There are plenty of complicated systems, and I have been a co-author 
on papers on at least two, but they are all Too Jolly Complicated to live in 
GHC.  We did have an implementation of boxy types, but I took it out when 
implementing the new typechecker.  Nobody understood it.

However, people so often write
runST $ do ...
that in GHC 7 I implemented a special typing rule, just for infix uses of ($).  
Just think of
(f $ x) as a new syntactic form, with the obvious typing rule, and away you go.

It's very ad hoc, because it's absolutely specific to ($), and I'll take it out 
if you all hate it, but it's in GHC 7 for now.

Anyway, that's why you encountered the puzzling behaviour you describe below.

Simon

| -Original Message-
| From: Bas van Dijk [mailto:v.dijk@gmail.com]
| Sent: 30 October 2010 21:14
| To: glasgow-haskell-users@haskell.org
| Cc: Simon Peyton-Jones
| Subject: Re: Type error in GHC-7 but not in GHC-6.12.3
| 
| On Sat, Oct 30, 2010 at 1:57 AM, Bas van Dijk  wrote:
| > I could isolate it a bit more if you want.
| 
| And so I did. The following is another instance of the problem I'm
| having but set in a more familiar setting:
| 
| {-# LANGUAGE RankNTypes #-}
| 
| import Control.Monad.ST
| 
| foo :: (forall s. ST s a) -> a
| foo st = ($) runST st
| 
| Couldn't match expected type `forall s. ST s a'
| with actual type `ST s a'
| In the second argument of `($)', namely `st'
| 
| Note that: 'foo st = runST st' type checks as expected.
| 
| Surprisingly 'foo st = runST $ st' also type checks!
| 
| I find the latter surprising because according to the report[1]: e1 op
| e2 = (op) e1 e2. So either both should type check or both should fail.
| 
| I guess that a RULE somewhere eliminates the ($) before the
| type-checker kicks in. I do find that a little strange because I
| thought RULES where applied after type checking.
| 
| Regards,
| 
| Bas
| 
| [1] http://www.haskell.org/onlinereport/exps.html#operators

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