Re: [Haskell-cafe] ANNOUNCE: set-monad

2012-06-17 Thread Tillmann Rendel

Hi,

David Menendez wrote:

As you noticed, you can get somewhat better performance by using the
combinators that convert to S.Set internally, because they eliminate
redundant computations later on.


Somewhat better? My example was three times faster, and I guess that 
the fast variant is O(n) and the slow variant is O(n²). So I expect that 
for some applications, the Set interface is more than fast enough and 
the MonadPlus-interface is much too slow.



(Why is unioned faster then numbers? Is union doing some rebalancing? Can I
trigger that effect directly?)


It's because mplus a b= f turns into mplus (a= f) (b= f),
whereas unioned takes the union before calling f.


Here, you compare mplused to unioned, but in the parentheses, I asked 
about numbers and unioned (from my last email).


  Tillmann

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


Re: [Haskell-cafe] Haskell is rapidly approaching the top 20

2012-06-17 Thread Stephen Tetley
Ah, enjoy it while it lasts. In April, Kuzcek PLT Institut, Kazakhstan
[*] and the Club of Rome  declared 2012 as the year of Peak FP. It's
downhill from here on…

[*] aka @plt_borat on Twitter - whose views are probably no more
unreliable than Tiobe.

On 16 June 2012 22:58, Henk-Jan van Tuyl hjgt...@chello.nl wrote:

 -✂
 TIOBE [snip]

 [Snip] what language could become the
 next big new programming language. We suggested several candidates such as
 Scala, Erlang and Clojure. Clearly, the new thing was expected to come from
 the functional programming field. ...

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


Re: [Haskell-cafe] [Haskell] JustHub 'Sherkin' Release

2012-06-17 Thread Peter Simons
Hi Chris,

  How much time, approximately, did you spend working with Nix?
  1 hour? 10 hours? 10 days? 10 months?
 
  You know that it is not 10 months.

actually, no. I don't know that, which is why I asked. I find it hard to
get an answer from you, though. It seems strange that you keep such
trivial information to yourself like some super personal secret. The
point of this discussion is to compare the respective properties of Nix
and Hub. In that context, it seems natural that I might be curious how
much actual working experience you have with Nix.


  JustHub [and Nix] have some similarities -- mostly around the idea of
  allowing multiple tool chains to co-exist; the way they go about it
  is very different.

I'm not sure what differences you are referring to. Could you please be
a little bit more specific? How exactly do Nix and Hub differ in the way
they install multiple tool-chains?


  I also know that I have been adding things that a generic package
  manager is most unlikely to be covering [...].

What you mean is: you really don't know, but you are speculating.


  To take just one example, I provide a mechanism that allows
  developers to archive the configuration of their Haskell development
  environment and check it into a source management system. The
  developer can check it out on a another system and if the build
  process invokes the recovery mechanism it will automatically rebuild
  the environment on the first run [...].

Yes, is Nix we solve that problem as follows. Configurations are lazily
evaluated functions. The function that builds Hub, for example, looks
like this:

 | { cabal, fgl, filepath, hexpat, regexCompat, utf8String }:
 |
 | cabal.mkDerivation (self: {
 |   pname = hub;
 |   version = 1.1.0;
 |   sha256 = 0vwn1v32l1pm38qqms9ydjl650ryic37xbl35md7k6v8vim2q8k3;
 |   isLibrary = false;
 |   isExecutable = true;
 |   buildDepends = [ fgl filepath hexpat regexCompat utf8String ];
 |   meta = {
 | homepage = https://justhub.org;;
 | description = For multiplexing GHC installations and providing 
development sandboxes;
 | license = self.stdenv.lib.licenses.bsd3;
 | platforms = self.ghc.meta.platforms;
 |   };
 | })

When Nix runs that build, it's executed in a temporary environment that
contains exactly those package that have been declared as build inputs,
but nothing else. Since all built-time dependencies of this package are
arguments of the function, it's possible to instantiate that build with
any version of GHC, Cabal, fgl, filepath, etc. If I pass GHC 6.12.3, Hub
will be built with GHC 6.12.3. If I pass GHC 7.4.2, Hub will be built
with GHC 7.4.2 instead.

Now, in my home directory there is a file ~/.nixpkgs/config.nix that
works like the 'main' function in a Haskell program insofar as that it
ties all those individual functions together into an user configuration:

 | let
 |   haskellEnv = pkgs: pkgs.ghcWithPackages (self: with pkgs; [
 | # Haskell Platform
 | haskellPlatform
 | # other packages
 | cmdlib dimensional funcmp hackageDb hledger hledgerLib hlint hoogle
 | HStringTemplate monadPar pandoc smallcheck tar uulib permutation
 | criterion graphviz async
 |   ]);
 | in
 | {
 |   packageOverrides = pkgs:
 |   {
 | ghc704Env = haskellEnv pkgs.haskellPackages_ghc704;
 | ghc741Env = haskellEnv pkgs.haskellPackages_ghc741;
 | ghc742Env = haskellEnv pkgs.haskellPackages_ghc742;
 |   };
 | }

I can copy that file to every other machine, regardless of whether it's
a Linux host, a Mac, or a BSD Unix, and run

  nix-env -iA ghc704Env

to have Nix build my GHC 7.0.4 development environment with exactly
those extra libraries that I configured.

How would I do something like that in Hub?


  Maybe Nix provides such a mechanism -- I don't know.

It does. :-)

Take care,
Peter


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


Re: [Haskell-cafe] event handler

2012-06-17 Thread Corentin Dupont
OK, so here's my last attempt. What do you think?
The Event class is optional (it works without because of EventData is
enforcing the use of the right types) however, I find it more clear because
it clearly specifies which types are events.
*
data NewPlayer = NewPlayer deriving (Typeable, Eq)
data NewRule = NewRule deriving (Typeable, Eq)

class (Eq e, Typeable e) = Event e
instance Event NewPlayer
instance Event NewRule

data family EventData e
data instance EventData NewPlayer = P Int
data instance EventData NewRule = R Int
instance Typeable1 EventData where
typeOf1 _ = mkTyConApp (mkTyCon EventData) []

data EventHandler = forall e . (Event e) = EH e (EventData e - IO ())

addEvent :: (Event e) = e - (EventData e - IO ()) - [EventHandler] -
[EventHandler]
addEvent e h ehs = (EH e h):ehs


triggerEvent :: (Event e) = e - (EventData e) - [EventHandler] - IO ()
triggerEvent e d ehs = do
let r = find (\(EH myEvent _) - cast e == Just myEvent) ehs
case r of
   Nothing - return ()
   Just (EH _ h) - case cast h of
Just castedH - castedH d
Nothing - return ()

-- TESTS
h1 :: EventData NewPlayer - IO ()
h1 (P a) = putStrLn $ Welcome Player  ++ (show a) ++ !
h2 :: EventData NewRule - IO ()
h2 (R a) = putStrLn $ New Rule  ++ (show a)
eventList1 = addEvent NewPlayer h1 []
eventList2 = addEvent NewRule h2 eventList1

trigger1 = triggerEvent NewPlayer (P 1) eventList2 --Yelds Welcome Player
1!
trigger2 = triggerEvent NewRule (R 2) eventList2 --Yelds New Rule 2 *


Thanks again!!
Corentin

On Sun, Jun 17, 2012 at 12:46 AM, Alexander Solla alex.so...@gmail.comwrote:



 On Sat, Jun 16, 2012 at 3:31 PM, Corentin Dupont 
 corentin.dup...@gmail.com wrote:

 Hi Alexander,
 sorry my initial example was maybe misleading. What I really what to do
 is to associate each event with an arbitrary data type. For example,
 consider the following events:
 NewPlayer
 NewRule
 Message
 User

 I want to associate the following data types with each, to pass to there
 respective handlers:
 NewPlayer --- Player
 NewRule --- Rule
 Message --- String
 User --- String

 Message and User have the same data type associated, that's why we can't
 use this type as a key to index the event...


 In that case, you definitely want FunctionalDependencies or TypeFamilies,
 and will probably want to drop the constraint (Handler e d) on Event e (if
 it doesn't work), and maybe enforce it with explicit exports.

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


[Haskell-cafe] Data.Binary hanging when used with socket - feature?

2012-06-17 Thread Paul Brenman
I'm using the 0.5.1.0 binary package (i.e. Data.Binary/Data.Binary.Get) to
encode/decode a lazy bytestring. Unfortunately, decode/get are hanging,
possibly due to the underlying chunking logic in Data.Binary.Get.

The lazy bytestring is being populated from a socket (via socketTohandle
sock ReadWriteMode . hGetContents). Periodically, encoded data structures
are received from the socket. When the encoded data structure happens to
end exactly on a chunk boundary, and in my specific case the final encoded
item is an Int(64), the Data.Binary.Get.getBytes function wants to force
the next chunk to be read into the lazy bytestring before returning the
decoded item (see comment in file at line 333 that reads forces the next
chunk before this one is returned). Unfortunately, since the socket is not
yet ready to send anything the call to decode/get hangs. The assumption
seems to be that the lazy bytestring isn't populated from a source that can
potentially block.

Is this reading correct?

If so, are there any workarounds?

Appreciate any advice - production code.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Noticed this change about infix decls in GHC 7.4.2

2012-06-17 Thread Christopher Done
So I have some module, in a work project that I'm portnig from GHC
6.12.3 to GHC 7.4.2,

module Data.Monoid.Operator where

import Data.Monoid

(++) :: Monoid a = a - a - a
(++) = mappend
infixr 5 ++

This compiles happily on GHC 6.12.3, but on 7.4.2 says:

src/Data/Monoid/Operator.hs:9:10:
Ambiguous occurrence `++'
It could refer to either `Data.Monoid.Operator.++',
 defined at src/Data/Monoid/Operator.hs:8:1
  or `Prelude.++',
 imported from `Prelude' at
src/Data/Monoid/Operator.hs:3:8-27
 (and originally defined in `GHC.Base')

It seems that it used to assign higher priority to the declared thing
in the current module over the imported one. Is this intentional? I'd
suspect not, given that if I comment the binding out:

-- (++) :: Monoid a = a - a - a
-- (++) = mappend

I get:

src/Data/Monoid/Operator.hs:9:10:
The fixity signature for `++' lacks an accompanying binding
  (The fixity signature must be given where `++' is declared)

Which seems to contradict the previous error message.

Bug?

Ciao!

P.S. Yes, I know I can fix this by not importing Prelude.
P.P.S Yes, I know there's a  or + defined now, but I prefer (++), thanks.

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


Re: [Haskell-cafe] Data.Binary hanging when used with socket - feature?

2012-06-17 Thread Gregory Collins
On Sun, Jun 17, 2012 at 7:40 PM, Paul Brenman paul.bren...@gmail.comwrote:


 Appreciate any advice - production code.


Don't use lazy bytestrings for I/O -- use enumerator/conduit/pipes and hook
it up to an attoparsec parser instead. Porting code from the Get monad to
attoparsec's Parser monad should be trivial.

G
-- 
Gregory Collins g...@gregorycollins.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: set-monad

2012-06-17 Thread David Menendez
On Sun, Jun 17, 2012 at 2:26 AM, Tillmann Rendel
ren...@informatik.uni-marburg.de wrote:
 Hi,


 David Menendez wrote:

 As you noticed, you can get somewhat better performance by using the
 combinators that convert to S.Set internally, because they eliminate
 redundant computations later on.

 Somewhat better? My example was three times faster, and I guess that the
 fast variant is O(n) and the slow variant is O(n²). So I expect that for
 some applications, the Set interface is more than fast enough and the
 MonadPlus-interface is much too slow.

Yes, that should have been significantly better.

 (Why is unioned faster then numbers? Is union doing some rebalancing? Can
 I
 trigger that effect directly?)


 It's because mplus a b= f turns into mplus (a= f) (b= f),
 whereas unioned takes the union before calling f.

 Here, you compare mplused to unioned, but in the parentheses, I asked about
 numbers and unioned (from my last email).

You're right. That may have been caused by the time to compute numbers
itself; I saw that numbers `times` numbers was faster than unioned
`times` unioned the second time I ran it.



Additionally, I haven't done any serious performance testing, but
there also seems to be a speedup when the following lines are added to
run:

run (Bind (Plus (Prim sa) mb) f) = run (Bind (S.union sa (run mb)) f)
run (Bind (Plus ma (Prim sb)) f) = run (Bind (S.union (run ma) sb) f)



-- 
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


Re: [Haskell-cafe] [Haskell] JustHub 'Sherkin' Release

2012-06-17 Thread Chris Dornan
 How would I do something like that [save and restore a Hakell project 
 configuration] in Hub?

Once I have an environment I am happy with, I save its configuration
(here the hub is named 'project'):

hub save project project.har

I would check this file into the source repository and at the start of
the build process
(it could be in a script or makefile) I would load it thus:

hub load project project.har

While the build environment is stable this will just check that
the environment matches the configuration and immediately continue
with the normal build process.

But when I check out and build the source tree on another
system it will locate the tools specified in the configuration
file and rebuild the user package database, complaining if it
can't locate the right tools.

There are more examples at http://justhub.org/overview

Chris

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


Re: [Haskell-cafe] Safe Haskell at the export symbol granularity?

2012-06-17 Thread Gábor Lehel
Thanks for the long answer!

It just occured to me that Data.Typeable is in basically the same
situation. Data.Typeable is a Trustworthy module with a type class,
and with functions built on that class, which are safe if they are
used with types for which the instances of the class are proper.
Using only safe modules and imports, it is not possible to subvert
that safety: instances can only be derived, and derived instances are
guaranteed to be proper. But if someone makes a Trustworthy module
with an improper manual Typeable instance and you import it, suddenly
the functions in Data.Typeable can be unsafe, even though nothing in
that module has changed.

The only difference in my situation is that there's no
guaranteed-to-be-safe deriving mechanism, it all rests on whether the
Trustworthy modules importing my Unsafe module to write their
instances are behaving themselves.

I think one way to resolve this might be to say that Safe Haskell's
mission is to help prevent bad things from happening in a global
sense, but not necessarily to delineate which functions can or cannot
be causing the bad things once unsafeness has crept into the program.
Trustworthy modules are inherently risky: they declare of themselves
that they're trustworthy, but really, they could do anything. The
burden is on the administrator to decide what they actually trust.
What Safe Haskell says is that if the administrator does this properly
and only trusts packages/modules which are actually safe, then
programs will not behave unsafely. But if they make a bad decision and
trust an unsafe module, then whether it does the bad things directly,
or indirectly by breaking the invariants another module depends on,
doesn't make much of a practical difference. You've lost either way.

On Sat, Jun 2, 2012 at 2:28 AM, David Terei dave.te...@gmail.com wrote:
 So this is a good question, sorry for the late reply. It's tricky as
 the way typeclasses are imported and exported in Haskell is confusing.

 Basically, instances are hard to control access to as they aren't part
 of import or export statements. Importing a module that defines an
 instances gives you those instances. This works transitively so you
 have access to all instances defined below you in the dependency
 graph.

 Controlling access to a typeclass function is easy though, it works
 just like a normal function. So in your example, the Safe module
 wouldn't necessarily become unsafe but there is some unsatisfactory
 trickiness.

  - untrusted code still couldn't access the type class as the
 functions for it aren't exported.
  - the derived functions may or may not be safe anymore depending on
 polymorphism:
   - If the derived functions don't have any polymorphism that would
 allow consumers of the functions to choose what underlying typeclass
 is used, then the module is still safe.
   - If they do, then yes untrusted code could choose what types to
 use to cause the unsafe instance to be used, thus making the derived
 functions unsafe. (This assumes the untrusted code has access to the
 unsafe instance but as I said, this is hard to reason about since
 instances are somewhat global).

 there are solutions to this problem but its a tricky situation with
 the solutions really being to be careful... I don't know how we could
 do better. Tracking safety at the symbol level doesn't seem like it
 would change this situation. Basically you want closed type classes or
 a way to control what instances can be used (maybe by simply making
 instances part of import/export lists) both of which are big changes
 to Haskell.

 I wrote some example code and a note about this stuff:

 https://github.com/dterei/SafeHaskellExamples/tree/master/typeclasses

 Cheers,
 David

 On 18 May 2012 06:58, Gábor Lehel illiss...@gmail.com wrote:
 I have a related-seeming question:

 Say I have a type class with methods, and some functions implemented
 on top of it. The class methods are inherently unsafe. Instances of
 the class are supposed to satisfy some conditions, and if those
 conditions are met, the functions built on top are safe.

 So say I put the class in an Unsafe module, and re-export the class
 without its methods along with the derived functions in a Safe module.
 For anything unsafe to happen, the Unsafe module has to be imported
 somewhere. But if someone imports it and implements a bad instance,
 the Safe module *also* becomes potentially unsafe! What's the
 recommended practice here?

 (I can't really tell if this is the same question as originally posed
 by Ryan, but I think it's not.)

 On Thu, May 17, 2012 at 4:53 PM, Ryan Newton rrnew...@gmail.com wrote:
 Good point, Antoine!

 I think that does the trick.


 On Thu, May 17, 2012 at 10:48 AM, Antoine Latter aslat...@gmail.com wrote:

 On Thu, May 17, 2012 at 8:50 AM, Ryan Newton rrnew...@gmail.com wrote:
  Thanks David.
 
  I'm glad to see it was discussed in the wiki.  (Btw, my 2 cents is that
  I
  like the comment pragmas more than new