Re: [Haskell-cafe] Weird interaction between literate haskell, ghci and OverloadedStrings

2011-12-03 Thread Joachim Breitner
Hi,

Am Samstag, den 03.12.2011, 16:18 +1100 schrieb Erik de Castro Lopo:
 I'm working on a literate haskell document (actually TeX, but the
 example below is just test) and I'm using ByteStrings in the code.
 I know I can do:
 
 ghci -XOverloadedStrings file.lhs
 
 or, after ghci is running I can do:
 
 Main :set -XOverloadedStrings
 
 but I'd like to embed a directive in the file so that when loaded
 in GHCi, I will automatically get OverloadedStrings. This is mainly
 so that it JustWorks(tm) when I pass the file on to someone else.
 
 Is there a way to do this?
 
 There is a short example file below. I'm using ghc-7.0.4 from Debian
 testing.

it does not seem to be related to literate haskell, if I copy the code
from your file into a .hs without the  , ghci still does not activate
the OverloadedStrings extension when loading the file.

I’d consider this a bug until the developers explain why this should or
cannot be different, and suggest you file it as such.

Greetings,
Joachim

-- 
Joachim nomeata Breitner
  m...@joachim-breitner.de  |  nome...@debian.org  |  GPG: 0x4743206C
  xmpp: nome...@joachim-breitner.de | http://www.joachim-breitner.de/



signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: monad-control-0.3

2011-12-03 Thread Herbert Valerio Riedel
On Sat, 2011-12-03 at 01:35 +0100, Bas van Dijk wrote:
 Here are some benchmark results that compare the original monad-peel,
 the previous monad-control-0.2.0.3 and the new monad-control-0.3:
 
 http://basvandijk.github.com/monad-control.html
 
 Note that the benchmarks use Bryan O'Sullivan's excellent new
 criterion-0.6 package.

btw, how did you manage to get measurements from 2 different versions of
the same library (monad-control 0.3 and 0.2.0.3) into a single report?


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Weird interaction between literate haskell, ghci and OverloadedStrings

2011-12-03 Thread Erik de Castro Lopo
Joachim Breitner wrote:

 it does not seem to be related to literate haskell, if I copy the code
 from your file into a .hs without the  , ghci still does not activate
 the OverloadedStrings extension when loading the file.

I hadn't noticed that.
 
 I’d consider this a bug until the developers explain why this should or
 cannot be different, and suggest you file it as such.

I agree. I've lodged a bug report here:

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

Erik
-- 
--
Erik de Castro Lopo
http://www.mega-nerd.com/

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: monad-control-0.3

2011-12-03 Thread Bas van Dijk
On 3 December 2011 10:18, Herbert Valerio Riedel h...@gnu.org wrote:
 btw, how did you manage to get measurements from 2 different versions of
 the same library (monad-control 0.3 and 0.2.0.3) into a single report?

By renaming the old package to monad-control2 and using the
PackageImports extension.

I do wonder why it's not possible to use two different versions of the
same package at the same time.

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: monad-control-0.3

2011-12-03 Thread Bas van Dijk
On 3 December 2011 00:45, Bas van Dijk v.dijk@gmail.com wrote:
 Note that Peter Simons just discovered that these packages don't build
 with GHC-7.0.4 (https://github.com/basvandijk/monad-control/issues/3).
 I just committed some fixes which enable them to be build on GHC =
 6.12.3. Hopefully I can release these fixes this weekend.

I just released the fixes:

http://hackage.haskell.org/package/monad-control-0.3.0.1
http://hackage.haskell.org/package/lifted-base-0.1.0.1

Cheers,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Weird interaction between literate haskell, ghci and OverloadedStrings

2011-12-03 Thread Bas van Dijk
On 3 December 2011 11:19, Erik de Castro Lopo mle...@mega-nerd.com wrote:
 Joachim Breitner wrote:

 it does not seem to be related to literate haskell, if I copy the code
 from your file into a .hs without the  , ghci still does not activate
 the OverloadedStrings extension when loading the file.

 I hadn't noticed that.

 I’d consider this a bug until the developers explain why this should or
 cannot be different, and suggest you file it as such.

 I agree. I've lodged a bug report here:

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

I think it's very dangerous if language extensions leak from modules
by default. For example if someone creates a library and needs to use
some unsafe language extensions like:

{-# LANGUAGE UndecidableInstances, OverlappingInstances, IncoherentInstances #-}
module SomeLib where ...

You surely don't want to silently enable these in some unsuspecting client:

module MyFirstHaskellModule where
import SomeLib
...

I can imagine having a pragma for explicitly exporting language extensions:

{-# EXPORT_LANGUAGE OverloadedStrings #-}

Cheers,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ismzero operator possible without equal constraint

2011-12-03 Thread edgar klerks
Hi list,

I am using MonadSplit (from
http://www.haskell.org/haskellwiki/New_monads/MonadSplit )  for a project
and now I want to make a library out of it. This seems to be
straightforward, but I got stuck when I tried to move miszero out of the
class:

miszero :: m a - Bool

It tests if the provided monad instance is empty. My naive attempt was:

miszero :: (Eq (m a), MonadPlus m) = m a - Bool
miszero =  ( == mzero )

This works, but not correctly. It adds an Eq constraint that is unneeded. I
would prefer to have something like:

miszero :: MonadPlus m = m a - Bool


Because I am not comparing the contents of the monad. I don't even touch
it.  Is this possible to write?

with kind regards,

Edgar
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ismzero operator possible without equal constraint

2011-12-03 Thread Arseniy Alekseyev
Of course it is not possible! Take a simple composition of reader and
Maybe functors for an example:

miszero :: (b - Maybe a) - Bool

I'm pretty sure (b - Maybe a) for a is a MonadPlus, but you can't
implement miszero for it.

Arseniy.

On 3 December 2011 16:55, edgar klerks edgar.kle...@gmail.com wrote:
 Hi list,

 I am using MonadSplit
 (from http://www.haskell.org/haskellwiki/New_monads/MonadSplit )  for a
 project and now I want to make a library out of it. This seems to be
 straightforward, but I got stuck when I tried to move miszero out of the
 class:

 miszero :: m a - Bool

 It tests if the provided monad instance is empty. My naive attempt was:

 miszero :: (Eq (m a), MonadPlus m) = m a - Bool
 miszero =  ( == mzero )

 This works, but not correctly. It adds an Eq constraint that is unneeded. I
 would prefer to have something like:

 miszero :: MonadPlus m = m a - Bool


 Because I am not comparing the contents of the monad. I don't even touch it.
  Is this possible to write?

 with kind regards,

 Edgar

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ismzero operator possible without equal constraint

2011-12-03 Thread edgar klerks
Hi Arseniy,

Yes, I see it now. :) . I had some feeling there should be some structural
equality:

Just _ == Just _ = True
Nothing == Nothing = True
_ == _ = False

But this doesn't work for functions.

Thanks for your answer!

Greets,

Edgar
On Sat, Dec 3, 2011 at 6:23 PM, Arseniy Alekseyev 
arseniy.alekse...@gmail.com wrote:

 Of course it is not possible! Take a simple composition of reader and
 Maybe functors for an example:

 miszero :: (b - Maybe a) - Bool

 I'm pretty sure (b - Maybe a) for a is a MonadPlus, but you can't
 implement miszero for it.

 Arseniy.

 On 3 December 2011 16:55, edgar klerks edgar.kle...@gmail.com wrote:
  Hi list,
 
  I am using MonadSplit
  (from http://www.haskell.org/haskellwiki/New_monads/MonadSplit )  for a
  project and now I want to make a library out of it. This seems to be
  straightforward, but I got stuck when I tried to move miszero out of the
  class:
 
  miszero :: m a - Bool
 
  It tests if the provided monad instance is empty. My naive attempt was:
 
  miszero :: (Eq (m a), MonadPlus m) = m a - Bool
  miszero =  ( == mzero )
 
  This works, but not correctly. It adds an Eq constraint that is
 unneeded. I
  would prefer to have something like:
 
  miszero :: MonadPlus m = m a - Bool
 
 
  Because I am not comparing the contents of the monad. I don't even touch
 it.
   Is this possible to write?
 
  with kind regards,
 
  Edgar
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: monad-control-0.3

2011-12-03 Thread Ertugrul Söylemez
Bas van Dijk v.dijk@gmail.com wrote:

 It provides lifted versions of functions from the base library.
 Currently it exports the following modules:

 * Control.Exception.Lifted
 * Control.Concurrent.Lifted
 * Control.Concurrent.MVar.Lifted
 * System.Timeout.Lifted

 These are just modules which people have needed in the past. If you
 need a lifted version of some function, just ask me to add it or send
 me a patch.

 Note that Peter Simons just discovered that these packages don't build
 with GHC-7.0.4 (https://github.com/basvandijk/monad-control/issues/3).
 I just committed some fixes which enable them to be build on GHC =
 6.12.3. Hopefully I can release these fixes this weekend.

Just in time!  The forkable-monad library seems to fail with base
libraries more recent than mine, and I really need a generalized
forkIO. =)

Thanks for your great work.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife = sex)
http://ertes.de/


signature.asc
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ismzero operator possible without equal constraint

2011-12-03 Thread Antoine Latter
On Sat, Dec 3, 2011 at 10:55 AM, edgar klerks edgar.kle...@gmail.com wrote:
 Hi list,

 I am using MonadSplit
 (from http://www.haskell.org/haskellwiki/New_monads/MonadSplit )  for a
 project and now I want to make a library out of it. This seems to be
 straightforward, but I got stuck when I tried to move miszero out of the
 class:

 miszero :: m a - Bool

 It tests if the provided monad instance is empty. My naive attempt was:


You can write:

miszero :: MonadPlus m = m a - m Bool
miszero m = (m  return False) | return True

but that will invoke any monadic effects as well as determining the
nature of the value, which may not be what you want.

Antoine

 miszero :: (Eq (m a), MonadPlus m) = m a - Bool
 miszero =  ( == mzero )

 This works, but not correctly. It adds an Eq constraint that is unneeded. I
 would prefer to have something like:

 miszero :: MonadPlus m = m a - Bool


 Because I am not comparing the contents of the monad. I don't even touch it.
  Is this possible to write?

 with kind regards,

 Edgar

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ismzero operator possible without equal constraint

2011-12-03 Thread David Menendez
On Sat, Dec 3, 2011 at 3:55 PM, Antoine Latter aslat...@gmail.com wrote:
 On Sat, Dec 3, 2011 at 10:55 AM, edgar klerks edgar.kle...@gmail.com wrote:
 Hi list,

 I am using MonadSplit
 (from http://www.haskell.org/haskellwiki/New_monads/MonadSplit )  for a
 project and now I want to make a library out of it. This seems to be
 straightforward, but I got stuck when I tried to move miszero out of the
 class:

 miszero :: m a - Bool

 It tests if the provided monad instance is empty. My naive attempt was:


 You can write:

 miszero :: MonadPlus m = m a - m Bool
 miszero m = (m  return False) | return True

 but that will invoke any monadic effects as well as determining the
 nature of the value, which may not be what you want.

It's almost certainly not what you want for the list monad.

-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Anonymous, Unique Types, maybe

2011-12-03 Thread Scott Lawrence
(Sorry if this email is rather unclear - I know my desired end result, 
but neither how to acheive nor explain it well. Here goes.)


I'm processing lists, using them sortof as streams. (Whether that's a 
good idea isn't the issue here - but let me know if it isn't!) 
Fundamentally, there are two types of operations (at least, that are 
relevant here) - those that change the length of the list and those that 
don't.


Some operators might take more than one list/stream as an argument, 
combining them in some way or another. Obviously, if the lists were 
different lengths, the operator would fail. I don't want that to happen 
at run time, so I want to check for it statically, presumably via the 
type system. I could do this manually:


type AList = [Event]
type BList = [Event]
type CList = [Event]

myMapish :: AList - AList
mySelect :: AList - (Event - Bool) - BList
myOtherSelect :: BList - CList

but I'd rather not have to manually define a new type for every new list 
length:


myMapish :: List a - List a
mySelect :: List a - List ?

The '?' would be an anonymous, unique type - unless there's a better way 
to accomplish this.


Hope that was clear, and thanks (as always) for the help (and being 
awesome).


--
Scott Lawrence

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to get a file path to the program invoked?

2011-12-03 Thread wren ng thornton

On 12/1/11 11:12 AM, dokondr wrote:

Hi,
When my program starts it needs to know a complete path to the directory
from which it was invoked.
In terms of standard shell (sh) I need the Haskell function that will do
equivalent to:

#!/bin/sh
path=$(dirname $0)


That's not the path to the directory from which the script is invoked 
(aka, $PWD or, more accurately, the results of `pwd`). That's the path 
to the directory containing the script.


The current working directory (the dir from which the program is 
invoked, provided the program haven't moved since invocation) can be 
gotten by System.Directory.getCurrentDirectory in the directory package.


Getting the path to the location of the executable is trickier business.

--
Live well,
~wren

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to get a file path to the program invoked?

2011-12-03 Thread wren ng thornton

On 12/1/11 2:26 PM, dokondr wrote:

How to find this path using GHC libraries?


There was a discussion about this recently over on libraries@, IIRC. The 
short answer is that, at present, there is no function to give you $0. 
We'd like to add such a function, but it's not been done yet.


Part of the problem is that, as Alexey says, the first element of argv 
is just whatever is passed to exec, which is not guaranteed to be a 
complete path, a canonical path, or any other specific thing we'd 
desire. It's not at all straightforward to determine the actual location 
of the executable, especially not in a platform-independent manner. 
argv[0] can't be trusted, scanning through $PATH isn't guaranteed to 
find it (and even if you find something of the right name, it's not 
guaranteed to be the correct executable), etc etc.


--
Live well,
~wren

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: monad-control-0.3

2011-12-03 Thread wren ng thornton

On 12/2/11 7:35 PM, Bas van Dijk wrote:

On 3 December 2011 00:45, Bas van Dijkv.dijk@gmail.com  wrote:

* 60 times faster than the previous release!


Here are some benchmark results that compare the original monad-peel,
the previous monad-control-0.2.0.3 and the new monad-control-0.3:

http://basvandijk.github.com/monad-control.html

Note that the benchmarks use Bryan O'Sullivan's excellent new
criterion-0.6 package.



Those are some beautiful benchmarks. Not only is it much faster, but the 
distribution is much more peaked, which is always a good thing since it 
makes the performance more predictable. Kudos.


--
Live well,
~wren

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Anonymous, Unique Types, maybe

2011-12-03 Thread Stephen Tetley
Umm, an obvious point is that if you really are using lists as streams
they should appear infinite to the processing code, so you shouldn't
encounter operations that fail due to incompatible lengths.

Otherwise I think there might be packages on Hackage for fixed sized
lists, its a common example for the power of GADTs, though personally
I've found size annotated lists unusable at the point where I need
`filter` (which you are calling mySelect?).

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANNOUNCE: Haskell Communities and Activities Report (21st ed., November 2011)

2011-12-03 Thread Janis Voigtländer

On behalf of all the contributors, I am pleased to announce that the

   Haskell Communities and Activities Report
 (21st edition, November 2011)

is now available in PDF and HTML formats:

  http://haskell.org/communities/11-2011/report.pdf
  http://haskell.org/communities/11-2011/html/report.html

Many thanks go to all the people that contributed to this report,
both directly, by sending in descriptions, and indirectly, by doing
all the interesting things that are reported. I hope you will find
it as interesting a read as I did.

If you have not encountered the Haskell Communities and Activities
Reports before, you may like to know that the first of these reports
was published in November 2001. Their goal is to improve the
communication between the increasingly diverse groups, projects, and
individuals working on, with, or inspired by Haskell. The idea behind
these reports is simple:

  Every six months, a call goes out to all of you enjoying Haskell to
  contribute brief summaries of your own area of work. Many of you
  respond (eagerly, unprompted, and sometimes in time for the actual
  deadline to the call. The editor collects all the contributions
  into a single report and feeds that back to the community.

When I try for the next update, six months from now, you might want
to report on your own work, project, research area or group as well.
So, please put the following into your diaries now:

   =
  End of April 2012:
   target deadline for contributions to the
 May 2012 edition of the HCA Report
   =

Unfortunately, many Haskellers working on interesting projects are so
busy with their work that they seem to have lost the time to follow
the Haskell related mailing lists and newsgroups, and have trouble even
finding time to report on their work. If you are a member, user or
friend of a project so burdened, please find someone willing to make
time to report and ask them to register with the editor for a simple
e-mail reminder in April (you could point me to them as well, and I
can then politely ask if they want to contribute, but it might work
better if you do the initial asking). Of course, they will still have to
find the ten to fifteen minutes to draw up their report, but maybe we
can increase our coverage of all that is going on in the community.

Feel free to circulate this announcement further in order to
reach people who might otherwise not see it. Enjoy!

Janis Voigtlaender
hcar at haskell.org

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ismzero operator possible without equal constraint

2011-12-03 Thread edgar klerks
No not for lists, but it is not a bad direction. If I modify it a bit, I
can get an ifmzero function:

ifmzero :: (MonadSplit m) = m a - m b - m b - m b
ifmzero p b f = join $ mhead $ (liftM (const f) p) `mplus` (return b)

mhead :: (MonadSplit m) = m a - m a
mhead = liftM fst . msplit

Which I think works for all MonadSplit monads. I have some loose rationing,
I can show, but am a bit affraid to share :)

I have made a small example with a foldl function.

Thanks for your example.

Greets,

Edgar

 module Control.Monad.MonadSplit where
 import Control.Monad
 import Control.Applicative
 import qualified Data.Sequence as S
 import Test.QuickCheck

 class MonadPlus m = MonadSplit m where
   msplit  :: m a - m (a, m a)


 instance MonadSplit [] where
   msplit [] = mzero
   msplit (x:xs) = return (x,xs)

 instance MonadSplit Maybe where
   msplit Nothing   = mzero
   msplit (Just x)  = return (x, Nothing)

 ifmzero p b f = join $ mhead $ (liftM (const f) p) `mplus` (return b)

 mhead :: (MonadSplit m) = m a - m a
 mhead = liftM fst . msplit

 foldMSl :: (MonadSplit m) = (b - a - m b) - b - m a - m b
 foldMSl m i n = ifmzero n (return i) $ do
(x, xs) - msplit n
i' - m i x
foldMSl m i' xs

 prop_foldMSl_ref = property $ test_foldMSl_ref
where test_foldMSl_ref :: Int - [Int] - Bool
  test_foldMSl_ref x y = (foldMSl (\x y - return $ x - y) x y) ==
(return (foldl (\x y - x - y) x y))



On Sat, Dec 3, 2011 at 11:39 PM, David Menendez d...@zednenem.com wrote:

 On Sat, Dec 3, 2011 at 3:55 PM, Antoine Latter aslat...@gmail.com wrote:
  On Sat, Dec 3, 2011 at 10:55 AM, edgar klerks edgar.kle...@gmail.com
 wrote:
  Hi list,
 
  I am using MonadSplit
  (from http://www.haskell.org/haskellwiki/New_monads/MonadSplit )  for a
  project and now I want to make a library out of it. This seems to be
  straightforward, but I got stuck when I tried to move miszero out of the
  class:
 
  miszero :: m a - Bool
 
  It tests if the provided monad instance is empty. My naive attempt was:
 
 
  You can write:
 
  miszero :: MonadPlus m = m a - m Bool
  miszero m = (m  return False) | return True
 
  but that will invoke any monadic effects as well as determining the
  nature of the value, which may not be what you want.

 It's almost certainly not what you want for the list monad.

 --
 Dave Menendez d...@zednenem.com
 http://www.eyrie.org/~zednenem/

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe