Re: ANNOUNCE: GHC 7.0.1 Release Candidate 2

2010-10-29 Thread Isaac Dupree

On 10/29/10 20:19, Bas van Dijk wrote:

I'm not sure this is in rc2 since I'm using the latest ghc-HEAD (7.1.20101029).

In ghc<  7 you needed to import symbols like fromInteger, (>>=) and
fail when you used them indirectly. For example when using integer
literals or do-notation.

I noticed that in my ghc-HEAD this isn't needed anymore:

{-# OPTIONS_GHC -Wall #-}
{-# LANGUAGE NoImplicitPrelude #-}


Yes, in HEAD only, NoImplicitPrelude no longer implies RebindableSyntax.

http://darcs.haskell.org/cgi-bin/darcsweb.cgi?r=ghc;a=darcs_commitdiff;h=20101022143400-1287e-746a83b4269744bb54177753c8ff67bec542b46c.gz


import Control.Monad ( return )
import System.IO ( IO )
import Data.Int

-- Only needed for ghc<  7.
-- In fact, the following gives a redundancy warning in ghc-7:
import Control.Monad ( (>>=), fail )
import Prelude   ( fromInteger )


However, a redundancy warning sounds wrong (or at least confusing).  An 
"unused import" warning seems more appropriate to me, although it's a 
bit of a grey area.  If you remove LANGUAGE NoImplicitPrelude from the 
module, what warning do you get? (maybe test that in HEAD as well as 
6.12 or so)


-Isaac
___
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-10-29 Thread Bas van Dijk
I'm not sure this is in rc2 since I'm using the latest ghc-HEAD (7.1.20101029).

In ghc < 7 you needed to import symbols like fromInteger, (>>=) and
fail when you used them indirectly. For example when using integer
literals or do-notation.

I noticed that in my ghc-HEAD this isn't needed anymore:

{-# OPTIONS_GHC -Wall #-}
{-# LANGUAGE NoImplicitPrelude #-}

import Control.Monad ( return )
import System.IO ( IO )
import Data.Int

-- Only needed for ghc < 7.
-- In fact, the following gives a redundancy warning in ghc-7:
import Control.Monad ( (>>=), fail )
import Prelude   ( fromInteger )

main :: IO ()
main = do _ <- return (1 :: Int)
  return ()

Is this intentional?

Regards,

Bas
___
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-10-29 Thread Bas van Dijk
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,

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


ANNOUNCE: GHC 7.0.1 Release Candidate 2

2010-10-29 Thread 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/

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


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

2010-10-29 Thread Bas van Dijk
Hello,

I'm updating my usb-safe package for GHC-7:

darcs get http://code.haskell.org/~basvandijk/code/usb-safe

It depends on the HEAD version of regions:
darcs get http://code.haskell.org/~basvandijk/code/regions

I think I'm suffering from the new implied MonoLocalBinds extension
(I'm using GADTs) as described in:

http://hackage.haskell.org/trac/ghc/blog/LetGeneralisationInGhc7

However, I'm not sure this is the problem because I'm not using local
bindings and use explicit type signatures everywhere.

I try to make a small isolated example when I have time but for now
let's use the actual definitions:

The following function type-checked fine in GHC-6.12.3 but fails in
GHC-7.1.20101027:

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

The error I get is:

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'

These are the types and definitions of the other functions involved:

useWhich ∷
  ∀ k desc e (m ∷ * → *) α
  . (GetDescriptor e desc, MonadIO m)
  ⇒ [e]
  → (e → k → m α)
  → (desc → Bool)
  → k
  → m α
useWhich ds w p f = case find (p ∘ getDesc) ds of
  Nothing → throw USB.NotFoundException
  Just d  → w d f

withDevice ∷
MonadCatchIO pr
  ⇒ USB.Device
  → (∀ s. RegionalDeviceHandle (RegionT s pr) → RegionT s pr α)
  → pr α
withDevice dev f = runRegionT $ openDevice dev >>= f

Note that when I inline the definition of useWhich it type-checks fine:

withDeviceWhich ctx p f = do
  devs ← liftIO $ USB.getDevices ctx
  case find (p ∘ getDesc) devs of
Nothing → throw USB.NotFoundException
Just d  → withDevice d f

Since I'm not using local bindings and use explicit type signatures
everywhere, I'm not sure MonoLocalBinds is the problem.

Note that other applications of useWhich which also use RankNTypes
type-check just fine in both GHC-6.12.3 and GHC-7.1.20101027:

---

setConfigWhich ∷
  ∀ pr cr α
  . (pr `AncestorRegion` cr, MonadCatchIO cr)
  ⇒ RegionalDeviceHandle pr
  → (USB.ConfigDesc → Bool)
  → (∀ sCfg. ConfigHandle sCfg → cr α)
  → cr α
setConfigWhich h = useWhich (getConfigs h) setConfig

getConfigs ∷ RegionalDeviceHandle r → [Config r]

setConfig ∷
  ∀ pr cr α
  . (pr `AncestorRegion` cr, MonadCatchIO cr)
  ⇒ Config pr
  → (∀ sCfg. ConfigHandle sCfg → cr α)
  → cr α

---

withInterfaceWhich ∷
  ∀ pr sCfg α
  . MonadCatchIO pr
  ⇒ ConfigHandle sCfg
  → (USB.Interface → Bool)
  → (∀ s. RegionalInterfaceHandle sCfg (RegionT s pr) → RegionT s pr α)
  → pr α
withInterfaceWhich h = useWhich (getInterfaces h) withInterface

getInterfaces ∷ ConfigHandle sCfg → [Interface sCfg]

withInterface ∷
  ∀ pr sCfg α
  . MonadCatchIO pr
  ⇒ Interface sCfg
  → (∀ s. RegionalInterfaceHandle sCfg (RegionT s pr) → RegionT s pr α)
  → pr α


---

setAlternateWhich ∷
  ∀ pr cr sCfg α
  . (pr `AncestorRegion` cr, MonadCatchIO cr)
  ⇒ RegionalInterfaceHandle sCfg pr
  → (USB.InterfaceDesc → Bool)
  → (∀ sAlt. AlternateHandle sAlt pr → cr α)
  → cr α
setAlternateWhich h = useWhich (getAlternates h) setAlternate

getAlternates ∷ RegionalInterfaceHandle sCfg r → [Alternate sCfg r]

setAlternate ∷
  ∀ pr cr sCfg α
  . (pr `AncestorRegion` cr, MonadCatchIO cr)
  ⇒ Alternate sCfg pr
  → (∀ sAlt. AlternateHandle sAlt pr → cr α)
  → cr α


---

I'm happy to provide more info when needed.

Regards,

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