Re: Pin a package?

2013-01-12 Thread wagnerdm

Quoting Stephen Paul Weber singpol...@singpolyma.net:

Is there a way to tell cabal to refuse to upgrade a package?  I'd  
like to pin my `bytestring` to the version that shipped with my GHC.


cabal install --constraint bytestring installed

~d

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


Re: Pin a package?

2013-01-12 Thread wagnerdm

Quoting Shachaf Ben-Kiki shac...@gmail.com:


You can put constraint: bytestring == version in ~/.cabal/config.
Alternatively you can run one `cabal install --constraint bytestring
== version` command.


Keep in mind the following subtle difference between this constraint  
and the installed constraint: this fixes a version, but doesn't fix  
a set of flags or dependencies' versions. So cabal may still rebuild  
bytestring if it discovers that changing either of these will make an  
otherwise failing constraint set succeed, whereas the installed  
constraint will force the package not to be rebuilt. On the other  
hand, if there are many versions of bytestring installed, the  
installed constraint does not fix any one of them as the exact  
version.


It can make sense to use both == version constraints and installed  
constraints at once.


~d

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


Re: Unexpected ambiguity in a seemingly valid Haskell 2010 program

2012-11-09 Thread wagnerdm

It's possible that the below blog post is related.
~d

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

Quoting Roman Cheplyaka r...@ro-che.info:


For this module

module Test where

import System.Random

data RPS = Rock | Paper | Scissors deriving (Show, Enum)

instance Random RPS where
  random g =
let (x, g') = randomR (0, 2) g
in (toEnum x, g')
  randomR = undefined

ghc (7.4.1 and 7.6.1) reports an error:

rand.hs:9:9:
No instance for (Random t0) arising from the ambiguity check for g'
The type variable `t0' is ambiguous
Possible fix: add a type signature that fixes these type variable(s)
Note: there are several potential instances:
  instance Random RPS -- Defined at rand.hs:7:10
  instance Random Bool -- Defined in `System.Random'
  instance Random Foreign.C.Types.CChar -- Defined in `System.Random'
  ...plus 34 others
When checking that g' has the inferred type `g'
Probable cause: the inferred type is ambiguous
In the expression: let (x, g') = randomR (0, 2) g in (toEnum x, g')
In an equation for `random':
random g = let (x, g') = randomR ... g in (toEnum x, g')
Failed, modules loaded: none.

There should be no ambiguity since 'toEnum' determines the type of x
(Int), and that in turn fixes types of 0 and 2. Interestingly,
annotating 0 or 2 with the type makes the problem go away.

jhc 0.8.0 compiles this module fine.

Roman

___
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: Call to arms: lambda-case is stuck and needs your help

2012-07-07 Thread wagnerdm

Quoting Jonas Almström Duregård jonas.dureg...@chalmers.se:


Couldn't we use \\ for multi-case lambdas with layout?


Actually, \\ is a valid (infix) function name... and the base library  
includes one in Data.List. That name is copied in several other  
container interfaces, as well.


~d

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


Re: Call to arms: lambda-case is stuck and needs your help

2012-07-05 Thread wagnerdm

Quoting Mikhail Vorozhtsov mikhail.vorozht...@gmail.com:

After 21 months of occasional arguing the lambda-case proposal(s) is  
in danger of being buried under its own trac ticket comments. We  
need fresh blood to finally reach an agreement on the syntax. Read  
the wiki page[1], take a look at the ticket[2], vote and comment on  
the proposals!


P.S. I'm CC-ing Cafe to attract more people, but please keep the  
discussion to the GHC Users list.


[1] http://hackage.haskell.org/trac/ghc/wiki/LambdasVsPatternMatching
[2] http://hackage.haskell.org/trac/ghc/ticket/4359


Well, for what it's worth, my vote goes for a multi-argument \case. I  
find the comment on the wiki page about mistyping \case Just x  
instead of \case (Just x) a lot a bit disingenuous, since you  
already need these parens with today's lambda. The complaint that  
multi-argument cases are unorthodox doesn't really hold a lot of  
weight with me -- much more serious things than syntax have changed in  
GHC compared to the Report!


Is there a more formal way to cast votes...?
~d

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


Re: Call to arms: lambda-case is stuck and needs your help

2012-07-05 Thread wagnerdm

Quoting wagne...@seas.upenn.edu:


Well, for what it's worth, my vote goes for a multi-argument \case. I


Just saw a proposal for \of on the reddit post about this. That's even  
better, since:


1. it doesn't change the list of block heralds
2. it doesn't mention case, and therefore multi-arg \of is perhaps a  
bit less objectionable to those who expect case to be single-argument

3. 40% less typing!

Can I change my vote? =)
~d

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


Re: Kindness of strangers (or strangeness of Kinds)

2012-06-07 Thread wagnerdm

Quoting AntC anthony_clay...@clear.net.nz:


GHC 7.2.1 :k (-) :: ?? - ? - *

GHC 7.4.1 :k (-) :: * - * - *

At first sight (-) is becoming less polyKinded. Is the eventual aim to be:

GHC 7.6+ :k (-) :: AnyKind1 - AnyKind2 - *


I sort of doubt it. After all, the prototypical thing to do with a  
function is to apply it to something, and Haskell expressions are  
categorized by types of OpenKind -- the new kinds you create with the  
new extension don't classify inhabited types.


It looks to me like a - b and (-) a b are just different  
syntactic classes now, not interconvertible with each other:


Prelude GHC.Exts :set -XMagicHash
Prelude GHC.Exts :k Int# - Int#
Int# - Int# :: *
Prelude GHC.Exts :k (-) Int# Int#

interactive:1:6:
Expecting a lifted type, but `Int#' is unlifted
In a type in a GHCi command: (-) Int# Int#

Perhaps this is a side-effect of the introduction of PolyKinds; from  
the release notes:


There is a new feature kind polymorphism (-XPolyKinds): Section  
7.8.1, ?Kind polymorphism?. A side-effect of this is that, when the  
extension is not enabled, in certain circumstances kinds are now  
defaulted to * rather than being inferred.


Though I must say it's not 100% clear to me exactly what's changed, or  
whether it was intentional.

~d

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


Re: Kindness of strangers (or strangeness of Kinds)

2012-06-06 Thread wagnerdm

Quoting AntC anthony_clay...@clear.net.nz:


{-# OPTIONS_GHC -XDataKinds -XPolyKinds -XKindSignatures#-}

data MyNat = Z | S Nat

class NatToIntN (n :: MyNat)
where natToIntN :: (n :: MyNat) - Int
instance NatToIntN Z
where natToIntN _ = 0
instance (NatToIntN n) = NatToIntN (S n)
where natToIntN _ = 1 + natToInt (undefined :: n)

But GHC rejects the class declaration (method's type):
Kind mis-match
 Expected kind `ArgKind', but `n' has kind `MyNat'
(Taking the Kind signature out of the method's type gives same message.)


At a guess, (-) :: * - * - *, but n :: MyNat, not n :: *, so (-) n  
is badly kinded. In comparison:



data Proxy a = Proxy

class NatToInt (n :: MyNat)
where natToInt :: Proxy (n :: MyNat) - Int
instance NatToInt Z
where natToInt _ = 0
instance (NatToInt n) = NatToInt (S n)
where natToInt _ = 1 + natToInt (Proxy :: Proxy n)


Here Proxy n :: *, even if n :: MyNat, so Proxy n is a fine argument  
to hand to (-).


~d

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


Re: Help me grok addFinalizer

2012-02-16 Thread wagnerdm

Quoting Antoine Latter aslat...@gmail.com:


On Thu, Feb 16, 2012 at 2:04 PM, Michael Craig mks...@gmail.com wrote:

When I read the docs for System.Mem.Weak, it all seems to make sense. But
then this code doesn't run as I expect it to when I turn on
-threaded: http://hpaste.org/63832 (Expected/actual output are listed in the
paste.)

I've tried this on 7.4.1 and 7.0.4 with the same results. Can someone
enlighten me?


First off, I'm pretty sure finalizers won't run until the data they
were associated with has been GCd, and GHC doesn't do GCs unless there
is allocation - threadDelay doesn't allocate much, I imagine.


This seems to be an explanation of why a finalizer might run later  
than expected (or not run at all). But his paste shows that it runs  
*earlier* than what he expected.


~d

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


Re: Is it true that an exception is always terminates the thread?

2012-01-23 Thread wagnerdm

Quoting Heka Treep zena.tr...@gmail.com:


actor mbox = do
  empty - atomically $ isEmptyTChan mbox
  if empty
then actor mbox
else do
  val - atomically $ readTChan mbox
  putStrLn val
  actor mbox


This looks a bit silly. Why not just this?

actor mbox = forever $ atomically (readTChan mbox) = putStrLn

~d

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


RE: Unit unboxed tuples

2011-12-28 Thread wagnerdm

Quoting Simon Peyton-Jones simo...@microsoft.com:

for example.  Singleton unboxed tuples are a perfectly valid data  
type; it's just that we don't (now) have a name for their constructor.


Well, Haskell *does* have a mechanism for giving two different  
implementations to a particular name...


class UnboxedUnit a where (# #) :: a
instance UnboxedUnit (##)
instance UnboxedUnit (a - (# a #))

That only leaves solving the equivalent problem for the type-level name (# #).

~d

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


Re: ConstraintKinds and default associated empty constraints

2011-12-21 Thread wagnerdm

Quoting Bas van Dijk v.dijk@gmail.com:


I'm playing a bit with the new ConstraintKinds feature in GHC
7.4.1-rc1. I'm trying to give the Functor class an associated
constraint so that we can make Set an instance of Functor. The
following code works but I wonder if the trick with: class Empty a;
instance Empty a, is the recommended way to do this:


Maybe something like this?

class Functor f where
type C f a :: Constraint
type C f a = ()

instance Functor Set where
type C Set a = Ord a

~d

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


Re: Why not allow empty record updates?

2011-11-15 Thread wagnerdm

Quoting Yitzchak Gale g...@sefer.org:


Yes. The translation of record updates given in the Report
makes perfect sense for {}. It is only forbidden by
n = 1, but no reason is given for that restriction.


It doesn't make sense to me. The translation explodes a value into a  
case statement over its constructors; what constructors do you use  
when you don't know the type of the value?


When n = 1, you know the type of the value by looking where the field  
came from, and hence which constructors to use in the case statement.


~d

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


Re: Should GHC default to -O1 ?

2011-11-08 Thread wagnerdm

Quoting Conrad Parker con...@metadecks.org:


I don't think compile time is an issue for new users when building
HelloWorld.hs and getting the hang of basic algorithms and data
structures. Anyone could explicitly set -O0 if they are worried about
compile times for a larger project.


I don't agree that GHC's user interface should be optimized for  
newcomers to Haskell. GHC is an industrial-strength compiler with some  
very advanced features; the majority of its target audience is  
professional programmers. Let its interface reflect that fact.


As Simon explained, GHC's current defaults are a very nice point in  
the programming space for people who are actively building and  
changing their programs.


~d

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


Re: problems with impredicativity

2011-11-04 Thread wagnerdm

Quoting Wolfgang Jeltsch g9ks1...@acme.softbase.org:


this code is accepted by GHC 7.0.4:
snip
However, this one isn?t:


{-# LANGUAGE ImpredicativeTypes #-}

polyId :: (forall a. Maybe a) - Maybe a
polyId x = x

polyIdMap :: [forall a. Maybe a] - [forall a. Maybe a]
polyIdMap xs = fmap polyId xs


Is there a way to make it accepted?


Yep, fix the type signature. There is no type you can substitute for  
a in Maybe a that results in forall a. Maybe a. But GHC accepts  
the same code with the following type signature, which should make  
clear what I mean:


polyIdMap :: [forall a. Maybe a] - [Maybe (forall a. a)]

~d

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


Re: problems with impredicativity

2011-11-04 Thread wagnerdm

Quoting wagne...@seas.upenn.edu:


Quoting Wolfgang Jeltsch g9ks1...@acme.softbase.org:


this code is accepted by GHC 7.0.4:
snip
However, this one isn?t:


{-# LANGUAGE ImpredicativeTypes #-}

polyId :: (forall a. Maybe a) - Maybe a
polyId x = x

polyIdMap :: [forall a. Maybe a] - [forall a. Maybe a]
polyIdMap xs = fmap polyId xs


Is there a way to make it accepted?


Yep, fix the type signature. There is no type you can substitute for  
a in Maybe a that results in forall a. Maybe a. But GHC  
accepts the same code with the following type signature, which  
should make clear what I mean:


polyIdMap :: [forall a. Maybe a] - [Maybe (forall a. a)]


It occurred to me that you may have been attempting to do something  
else, so perhaps I fired off my first reply too quickly. Another  
interpretation is that the type of polyIdMap is correct, but the type  
of polyId isn't.


The first thing to observe is that, ideally, the following two types  
would mean slightly different things:


polyId :: forall b. (forall a. Maybe a) - Maybe b
polyId :: (forall a. Maybe a) - (forall b. Maybe b)

The first means: first, choose a monomorphic type, then specialize the  
first argument to that monomorphic type. The second means: take a  
polymorphic value, then return it, delaying the choice of a  
monomorphic type until later. (And, again ideally, any unbound  
variables would implicitly put their forall at the top level, as in  
the first signature above.) If this distinction existed, then your  
polyIdMap would be fully compatible with a polyId having the second  
type signature.


Unfortunately, in GHC, these two types do not mean different things:  
foralls on the result side of an arrow are silently floated to the  
top level, even if you explicitly choose to put them later in your  
type annotation. The only way I know of to prevent this is to make a  
newtype barrier. For example, the following works:


newtype PolyMaybe = PolyMaybe (forall a. Maybe a)

polyId :: PolyMaybe - PolyMaybe
polyId x = x

polyIdMap :: [PolyMaybe] - [PolyMaybe]
polyIdMap xs = fmap polyId xs

Then, later, you can unwrap the PolyMaybe -- but only when you're  
ready to turn it into a monomorphic Maybe! (Note that none of these  
things is using ImpredicativeTypes, which is what made me jump to my  
first, probably mistaken impression of what you were trying to do.  
Rank2Types is enough for the above to compile.)


~d

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


Re: Is this a concurrency bug in base?

2011-10-09 Thread wagnerdm

Quoting Jean-Marie Gaillourdet j...@gaillourdet.net:

That sounds plausible. Do you see any workaround? Perhaps repeatedly  
evaluating typeOf?


If there's a concurrency bug, surely the workaround is to protect  
calls to the non-thread-safe function with a lock.


typeOfWorkaround lock v = do
() - takeMVar lock
x - evaluate (typeOf v)
putMVar lock ()
return x

~d

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


RE: Evaluating type expressions in GHCi

2011-09-20 Thread wagnerdm
Would it be possible to have no command at all? Types are  
distinguished by upper-case letters, so it should be possible to tell  
whether a given expression is a value-level or a type-level expression.


I guess that's not strictly true, since the expression could be _only_  
type variables -- but then I think it would be forgivable to just use  
the value-level evaluator for those ambiguous ones.


~d

Quoting Simon Peyton-Jones simo...@microsoft.com:


Sean

Yes, this has been asked for before, and it wouldn't be hard to implement.


What should the GHCi command be *called*?

We already have :kind, which displays the kind of a type.  Maybe  
:kind! should evaluate the type as well?  Or perhaps :kind should  
evaluate anyway (although that would be a bit  inconsistent with  
:type which does not evaluate the expression)


Or :normtype?   short for normalise type

Simon

From: glasgow-haskell-users-boun...@haskell.org  
[mailto:glasgow-haskell-users-boun...@haskell.org] On Behalf Of Sean  
Leather

Sent: 20 September 2011 11:34
To: GHC Users List
Subject: Evaluating type expressions in GHCi

I would like to ask GHCi for the type that a type expression will  
evaluate to, once all definitions of type synonyms and (when  
possible) type families have been inlined.


It appears that I can do some part of this for type T by using :t  
undefined :: T:


type family F a
type instance F Int = Bool
type instance F Bool = Int
type instance F (a, b) = (F a, F b)

ghci :t undefined :: F (Int, Bool)
undefined :: F (Int, Bool) :: (Bool, Int)

I also get what I expect here:

ghci :t undefined :: F (a, Bool)
undefined :: F (a, Bool) :: (F a, Int)

Of course, this doesn't work on types of kinds other than *.

Is it possible and worth having another GHCi command to perform this  
operation for any types? It could be the type analogue to :t such  
that it evaluates the type and gives its kind.


Regards,
Sean





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


Re: INLINE pragma changes in 7.2.1

2011-08-13 Thread wagnerdm
The behavior of the compilation part didn't change, GHC just started  
complaining about nonsense. See  
http://hackage.haskell.org/trac/ghc/ticket/5084 for more information.


~d

Quoting Antoine Latter aslat...@gmail.com:


Hi GHC,

Did the behavior of the INLINE prgama change in version 7.2.1? I
didn't see anything in the release notes.

Previously (7.0.3) I could attach an inline pragma to a class member like so:

class MyClass a with
  foo :: a - Int
  {-# INLINE foo #-}

Now I get the error message:

The INLINE pragma for default method `foo' lacks an accompanying binding

Is this change on purpose?

Thanks,
Antoine

___
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


System.Process.system in Windows

2011-08-03 Thread wagnerdm

Hello all,

I had a bit of fun recently tracking down quoting issues with the  
system command in Windows. For the examples below, I'll consistently  
use Windows  as the beginning of some text sent to the Windows  
command prompt cmd.exe, and use GHC  as the beginning of some text  
sent to a ghci session running in cmd.exe with System.Cmd imported.


The situation is this: I want to hand off a command line which has  
both a possibly-quoted command name and a (definitely) quoted  
argument. For concreteness, let's use more as the command and  
foo.txt as the argument, so that you can follow along at home on  
your favorite Windows system.


Windows echo foo  foo.txt
Windows more foo.txt
foo

All good so far. But:

GHC system \more\ \foo.txt\
'more foo.txt' is not recognized as an internal or external command,
operable program or batch file.
ExitFailure 1

After some digging, I discovered that system is shipping out to cmd  
/c, and indeed:


Windows cmd /c more foo.txt
'more foo.txt' is not recognized as an internal or external command,
operable program or batch file.

I don't know what the *right* fix is. However, after a bit of playing  
around, I discovered the following:


Windows cmd /c more foo.txt
foo
GHC system \\more\ \foo.txt\\
foo
ExitSuccess

Wrapping commands with an extra pair of double-quotes this way seemed  
to give behavior matching the bare cmd.exe for all the examples I  
could think of, even ones I thought it would break. For example:


GHC system \more foo.txt\
foo
ExitSuccess

If this turns out to be the right thing to do, it's pretty easy to  
implement. In the commandToProcess function, at  
libraries/process/System/Process/Internals.hs:455, the change is just


-   return (cmd, translate cmd ++ /c  ++ string)
+   return (cmd, translate cmd ++ /c \ ++ string ++ \)

(And in any case, the examples above should answer this amusing  
comment, immediately following those lines:


-- We don't want to put the cmd into a single
-- argument, because cmd.exe will not try to split it up.  Instead,
-- we just tack the command on the end of the cmd.exe command line,
-- which partly works.  There seem to be some quoting issues, but
-- I don't have the energy to find+fix them right now (ToDo). --SDM
-- (later) Now I don't know what the above comment means.  sigh.

=)

~d

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