Re: [Haskell-cafe] Why isn't hsc2hs functionality provided by ghc?

2013-06-05 Thread John Lato
I agree that preprocessing code shouldn't be hsc2hs specific.  I prefer
c2hs myself.  But hsc2hs is distributed with ghc, which makes it as
official as a good many other parts of "modern Haskell".

I also agree that making cabal-ghci work nicely would be ideal, but I don't
think it can be done without either adding hooks into ghci or wrapping
stdin.  As Roman points out, if you use :r in ghci, cabal-ghci wouldn't
pick up changes in the source file.  Using ghc's support for custom
preprocessors seems like a very straightforward solution: it already
exists, can be used today, and isn't tied to hsc2hs.

Not that this should stop anyone from working on cabal-ghci of course.


On Thu, Jun 6, 2013 at 11:43 AM, Jeremy Shaw  wrote:

> While hsc2hs is a popular FFI preprocessor, it is not the only one.
> There is also greencard and a few others.
>
> While hsc2hs can usually get the job done -- it's not clear that it is
> really the best choice. I think the Haskell FFI got to the point that
> it was 'just good enough' and then people lost interest in doing
> anything more. Let's face it -- working on the FFI is just not that
> exciting :)
>
> So, basically, we are stuck with stuff that is 'good enough' but no so
> great that we want to make it official.
>
> We can bind to C fairly easily, but for C++, Python, Ruby, Javascript,
> Java, etc, we have never really made much headway.
>
> I think the efforts to make cabal-ghci work nicely could really be the
> best solution for now. That is more extensible, and makes it easy to
> solve the problem you actually care about (being able to easily
> load/compile .hs files) with out giving priority to any particular FFI
> system.
>
> - jeremy
>
> On Tue, Jun 4, 2013 at 9:02 PM, silly  wrote:
> > I was wondering today, why hasn't hsc2hs been merged with ghc so that
> > it would be possible to add a
> >
> > {-# LANGUAGE ForeignFunctionInterface #-}
> >
> > at the top of a source file and then load it with ghci or compile it,
> > without the intermediate step of calling hsc2hs? This would be exactly
> > like the CPP extension. I don't have to call cpp manually. All I have
> > to do is to add {-# LANGUAGE CPP #-} and then ghc will take care of
> > the rest. This would also mean that there would be no need to have a
> > separate file extension. Surely I must not be the first person to have
> > that thought, so there must be a good reason why this hasn't happen
> > yet, but what is it?
> >
> > ___
> > 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
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] FRP memory leaks

2013-06-05 Thread John Lato
Which FRP frameworks have you been looking at?

In my experience, the most publicized leaks have been time leaks, which are
a particular type of memory leak related to switching.  However, the
presence of time leaks mostly arises in terms of the FRP implementation.
 Arrowized FRP (e.g. Yampa, netwire) do not typically suffer from this for
example.  Some libraries that implement the semantics of Conal Elliott's
"Push-pull functional reactive programming" (or similar semantics) have
been susceptible to this, however recent implementations are not.  Sodium,
elerea, and reactive-banana for example have generally overcome the worst
issues present in earlier systems.  Leaks can still be present in current
systems of course, but now they're generally due to the programmer
unintentionally retaining data in a case that's much simpler to reason
about.  That is, the situation today is more similar to forgetting to use
deepseq or similar, rather than the prior leaks that were very difficult to
reason about.

I think the most common current issue is that a very natural way of
accumulating reactive events across time can leak.  Suppose you have a
library of reactive widgets, where each widget has an associated stream of
IO actions that you want to run.  E.g. clicking a button prints it, sliding
a scale prints the value, etc.

> class Actionable a where
>   actions :: a -> Event (IO ())

suppose you have a collection that allows you to add/remove Actionable
things to it (e.g. a button panel).  This panel has an action stream that's
simply the concatenation of those of its components.  One possible
implementation looks like this:

> data ButtonPanel = ButtonPanel (Event (IO ())

> emptyPanel = ButtonPanel mempty

> addActionable :: Actionable a => ButtonPanel -> a -> ButtonPanel
> addActionable (ButtonPanel e) a = ButtonPanel (e <> actions a)

I've omitted all the parts for wiring up the gui, but suppose they're
handled also, and removing a button from the panel just removes it from the
gui and destroys the widget.  After that, the button's event stream is
empty, so you can just leave the ButtonPanel's event stream unchanged,
because the destroyed button will never fire.

This is a memory leak.  The destroyed Button's event stream is still
referenced in the ButtonPanel event stream, so data related to it never
gets freed.  Over time your FRP network will grow, and eventually you'll
hit scaling problems.

The proper solution in this instance is to keep a list of each button's
event stream within the button panel.  It's ok to keep a cached aggregate
stream, but that cache needs to be re-built when a button is removed.  This
is usually fairly natural to do with FRP, but your ButtonPanel may look
like this instead:

> data ButtonPanel = ButtonPanel  (Map Key (Event (IO ()))

> addActionable :: Actionable a => ButtonPanel-> Key -> a -> ButtonPanel
> removeActionable :: ButtonPanel -> Key -> ButtonPanel

and now you need to manage some sort of Key for collection elements.

This style isn't entirely idiomatic FRP.  Instead of these functions, you
could have all your modifications handled via the FRP framework.  For
example,

> data ButtonPanel = ButtonPanel (Behavior (Map Key (Event (IO ()
> buttonPanel :: Actionable a => Event (Key,a) -> Event Key -> ButtonPanel

but you still need to be aware that objects can reference older objects.
 Behaviors are frequently created via accumulators over events (e.g.
accumB), and if the accumulation is doing something like 'mappend', a
memory leak is likely.

Basically, the issue is that when you're accumulating reactive stuff over
time, you need to be sure that your accumulator doesn't reference data that
is otherwise expired.  This example uses a push-pull style pseudocode
because that's what I'm most familiar with.  I'm not entirely show how (or
if) this translates to arrowized FRP, although it wouldn't surprise me if
there's a similar pattern.


On Thu, Jun 6, 2013 at 2:50 AM, Łukasz Dąbek  wrote:

> Hello, Cafe!
>
> I've heard that one of the problems of FRP (Functional Reactive
> Programming) is that it's easy to create memory leaks. However I cannot
> find any natural examples of such leaks. Could anybody post some
> (pseudo)code demonstrating this phenomenon? Preferably something that
> arises when one is writing bigger applications in FRP style.
>
> Thanks in advance!
>
> --
> Łukasz Dąbek
>
> ___
> 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] Why isn't hsc2hs functionality provided by ghc?

2013-06-05 Thread Jeremy Shaw
While hsc2hs is a popular FFI preprocessor, it is not the only one.
There is also greencard and a few others.

While hsc2hs can usually get the job done -- it's not clear that it is
really the best choice. I think the Haskell FFI got to the point that
it was 'just good enough' and then people lost interest in doing
anything more. Let's face it -- working on the FFI is just not that
exciting :)

So, basically, we are stuck with stuff that is 'good enough' but no so
great that we want to make it official.

We can bind to C fairly easily, but for C++, Python, Ruby, Javascript,
Java, etc, we have never really made much headway.

I think the efforts to make cabal-ghci work nicely could really be the
best solution for now. That is more extensible, and makes it easy to
solve the problem you actually care about (being able to easily
load/compile .hs files) with out giving priority to any particular FFI
system.

- jeremy

On Tue, Jun 4, 2013 at 9:02 PM, silly  wrote:
> I was wondering today, why hasn't hsc2hs been merged with ghc so that
> it would be possible to add a
>
> {-# LANGUAGE ForeignFunctionInterface #-}
>
> at the top of a source file and then load it with ghci or compile it,
> without the intermediate step of calling hsc2hs? This would be exactly
> like the CPP extension. I don't have to call cpp manually. All I have
> to do is to add {-# LANGUAGE CPP #-} and then ghc will take care of
> the rest. This would also mean that there would be no need to have a
> separate file extension. Surely I must not be the first person to have
> that thought, so there must be a good reason why this hasn't happen
> yet, but what is it?
>
> ___
> 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] Why isn't hsc2hs functionality provided by ghc?

2013-06-05 Thread John Lato
On Wed, Jun 5, 2013 at 3:56 PM, Roman Cheplyaka  wrote:

> * Ivan Lazar Miljenovic  [2013-06-05
> 17:47:40+1000]
> > On 5 June 2013 17:34, Roman Cheplyaka  wrote:
> > > * Jason Dagit  [2013-06-04 21:00:25-0700]
> > >> > My preferred solution would be to have ghc/ghci automatically run
> hsc2hs
> > >> > (support c2hs also?) when necessary.  But so long as it's handled
> > >> > automatically, I wouldn't be particularly bothered by the
> implementation.
> > >>
> > >> How about having a `ghci` command for cabal? Or does the automatic
> > >> requirement really need to be part of ghc to work the way you want?
> > >>
> > >> (BTW, cabal-dev does have a `ghci` command, but I haven't tested to
> > >> see if it does the hsc -> hs conversion.)
> > >
> > > I don't think cabal can provide that. Let's say you're inside a 'cabal
> > > ghci' session. If you modify the hsc file and reload it in ghci, you'd
> > > expect to load the updated version — yet cabal hasn't even been called
> > > since 'cabal ghci', and have had no chance to re-generate the hs file.
> > >
> > > To answer the subject question — hsc2hs is not a single preprocessor
> > > available. There are also c2hs and greencard, and maybe something else.
> > > It is (or, at least, was) not clear which one should be generally
> > > preferred. Perhaps by now hsc2hs is a clear winner — I don't know.
> > >
> > > Another option is to add a generic preprocessor option to GHC,
> something
> > > like -pgmX cmd. Then, for hsc2hs one would write something like
> > >
> > >   {-# OPTIONS_GHC -pgmX hsc2hs #-}
> >
> > Isn't this what -pgmF is
> > for?
> http://www.haskell.org/ghc/docs/7.6.1/html/users_guide/options-phases.html#replacing-phases
> >
> > {-# OPTIONS_GHC -F -pgmF hsc2hs #-}
>
> Indeed! I should've read the whole section.
>
> Problem solved, then?


Pretty close.  For anyone who wants to use hsc2hs in this way, the first
step is to create a wrapper script to handle the arguments appropriately
(otherwise the output doesn't go to the proper location)

> file ghc_hsc2hs.sh
>   #!/bin/sh
>   hsc2hs $2 -o $3

Put the wrapper in your path, and add
{-# OPTIONS_GHC -F -pgmF ghc_hsc2hs.sh #-}

to the top of the source file.  The source file must have a .hs extension
for ghci to load it, but hsc2hs will ignore that and process it anyway.

With this you can load the file in ghci, and if you modify the file
reloading in ghci will pick up the changes, so it works pretty nicely.

There are a couple drawbacks though.  First, this isn't good for
distribution because other people won't have your wrapper script.  Second,
this preprocessor stage comes after CPP, which might impose some
difficulties in certain cases.

I can see this working well for internal projects etc.  If hsc2hs (and
other preprocessors) were distributed in a fashion suitable for use with
-F, either directly or by providing a wrapper, I think this could become
the preferred workflow.  I'm not entirely pleased that a non-Haskell file
gets a .hs extension, but c'est la vie.

I think it would generally be useful if ghc's -F phase were to support
non-Haskell files, but that's probably a bit more work than just
distributing a pgmF-friendly hsc2hs.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Haskell Weekly News: Issue 269

2013-06-05 Thread Daniel Santa Cruz
Welcome to issue 269 of the HWN, an issue covering crowd-sourced bits
of information about Haskell from around the web. This issue covers the
week of May 26 to June 1, 2013.

Quotes of the Week

   * neutrino: i've been teaching people about functional programming
 etc (when I came in there was exactly 0 knowledge about this, after
 I joined that changed, but not sure in which direction)

Top Reddit Stories

   * Haskell Platform 2013.2.0.0 is out
 Domain: haskell.org, Score: 103, Comments: 19
 On Reddit: [1] http://goo.gl/Iabii
 Original: [2] http://goo.gl/DniAP

   * Elm & Prezi: I'm now working on Elm full-time!
 Domain: elm-lang.org, Score: 96, Comments: 18
 On Reddit: [3] http://goo.gl/03Aab
 Original: [4] http://goo.gl/4o1Xh

   * ANN: Idris 0.9.8 released
 Domain: idris-lang.org, Score: 54, Comments: 58
 On Reddit: [5] http://goo.gl/PGrXi
 Original: [6] http://goo.gl/birp8

   * Type-Safe Runtime Code Generation with (Typed) Template Haskell
 Domain: gmainland.blogspot.co.uk, Score: 54, Comments: 17
 On Reddit: [7] http://goo.gl/rMEFc
 Original: [8] http://goo.gl/MBOJn

   * Elm 0.8 released! Type annotations and aliases, better HTML/JS
integration, and lots more
 Domain: elm-lang.org, Score: 50, Comments: 10
 On Reddit: [9] http://goo.gl/B9AIa
 Original: [10] http://goo.gl/tM3Qq

   * Why did the Haskeller need to replace his keyboard regularly?
 Domain: self.haskell, Score: 48, Comments: 9
 On Reddit: [11] http://goo.gl/FHiCn
 Original: [12] http://goo.gl/FHiCn

   * Towards a better Haskell package
 Domain: fvisser.nl, Score: 40, Comments: 26
 On Reddit: [13] http://goo.gl/XNFGM
 Original: [14] http://goo.gl/jbW4Q

   * What does the Haskell runtime look like?
 Domain: self.haskell, Score: 37, Comments: 17
 On Reddit: [15] http://goo.gl/n8bqD
 Original: [16] http://goo.gl/n8bqD

   * The AST Typing Problem
 Domain: blog.ezyang.com, Score: 33, Comments: 14
 On Reddit: [17] http://goo.gl/nYMNg
 Original: [18] http://goo.gl/FYpD2

   * [haskell.org Google Summer of Code 2013] Approved Projects
 Domain: haskell.org, Score: 28, Comments: 10
 On Reddit: [19] http://goo.gl/hnSnz
 Original: [20] http://goo.gl/IUE0U

Top StackOverflow Questions

   * What's the best way to exit a Haskell program?
 votes: 25, answers: 1
 Read on SO: [21] http://goo.gl/3AQdw

   * Haskell Conduit: One processing conduit, 2 IO sources of the same type
 votes: 23, answers: 0
 Read on SO: [22] http://goo.gl/12dwP

   * Why is length of “Níðhöggr” 9?
 votes: 22, answers: 2
 Read on SO: [23] http://goo.gl/emGGm

   * What is a solid example of something that can be done with list
comprehensions that is tricky with high order functions?
 votes: 11, answers: 5
 Read on SO: [24] http://goo.gl/fJMcg

   * Fibonacci Seq. strange output forms (Haskell)
 votes: 10, answers: 2
 Read on SO: [25] http://goo.gl/9OQYW

   * Gnuplot in Haskell: don't enter gnuplot terminal
 votes: 10, answers: 0
 Read on SO: [26] http://goo.gl/Fwb66

   * Haskell: YesNo type class. Why Integer?
 votes: 10, answers: 3
 Read on SO: [27] http://goo.gl/jnLLH

   * Is it possible to use extended precision (80-bit) floating point
arithmetic in GHC/Haskell?
 votes: 9, answers: 1
 Read on SO: [28] http://goo.gl/HUUoL

   * Having trouble understanding list comprehensions
 votes: 9, answers: 2
 Read on SO: [29] http://goo.gl/JkNL3

   * What is the rule of the order of multiple type variables in haskell?
 votes: 9, answers: 1
 Read on SO: [30] http://goo.gl/1whHM

Until next time,
+Daniel Santa Cruz

References

   1. http://www.haskell.org/platform/
   2.
http://www.reddit.com/r/haskell/comments/1f6l2a/haskell_platform_2013200_is_out/
   3. http://elm-lang.org/blog/announce/Elm-and-Prezi.elm
   4.
http://www.reddit.com/r/haskell/comments/1f9yd8/elm_prezi_im_now_working_on_elm_fulltime/
   5. http://idris-lang.org/archives/272
   6.
http://www.reddit.com/r/haskell/comments/1f75ge/ann_idris_098_released/
   7.
http://gmainland.blogspot.co.uk/2013/05/type-safe-runtime-code-generation-with.html
   8.
http://www.reddit.com/r/haskell/comments/1feqhn/typesafe_runtime_code_generation_with_typed/
   9. http://elm-lang.org/blog/announce/version-0.8.elm
  10.
http://www.reddit.com/r/haskell/comments/1f77h0/elm_08_released_type_annotations_and_aliases/
  11.
http://www.reddit.com/r/haskell/comments/1f6gjs/why_did_the_haskeller_need_to_replace_his/
  12.
http://www.reddit.com/r/haskell/comments/1f6gjs/why_did_the_haskeller_need_to_replace_his/
  13.
http://fvisser.nl/post/2013/may/28/towards-a-better-haskell-package.html
  14.
http://www.reddit.com/r/haskell/comments/1f70wi/towards_a_better_haskell_package/
  15.
http://www.reddit.com/r/haskell/comments/1f48dc/what_does_the_haskell_runtime_look_like/
  16.
http://www.reddit.com/r/haskell/comments/1f48dc/what_does_the_haskel

Re: [Haskell-cafe] voting sytem DSL

2013-06-05 Thread Jeremy Shaw
Hello,

The closest thing I know of is, https://github.com/whatgoodisaroad/surveyor

- jeremy


On Wed, Jun 5, 2013 at 4:22 PM, Corentin Dupont
 wrote:
> Hi haskellers!
> I am trying to make a DSL able to describe a voting system. That DSL should
> be able to describe many different voting procedures:
> unanimity or majority, open or secret ballot, one or two turns... It should
> also work for referendums (yes/no question) or elections (electing one or
> several people)...
> Are you aware of any such DSL? In Haskell I haven't see it, maybe in another
> language?
>
> Cheers,
> Corentin
>
> ___
> 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] Typeable typeclass and type-level naturals

2013-06-05 Thread TP
José Pedro Magalhães wrote:

>> Oh, it should probably be simply
>>
>>   deriving instance Typeable 'Zero
>>   deriving instance Typeable 'Succ
>>
> 
> Yes, that's how it should be. Please let me know if that
> doesn't work.

Thanks, it works perfectly like that.
I don't understand exactly why the previous syntax did not work, but maybe 
it will be clearer when I finish the paper "Scrap your boilerplate: a 
practical design pattern for generic programming" (anyway, this paper seems 
very interesting).
Output of the code:

-
$ runghc-head test_typeable.hs 
Box test_typeable.hs: Prelude.undefined
-

Maybe the "Box " in front of the line is strange, but it is OK: "one" is 
undefined, not "Box one".

This is the full tested code, for sake of reference:

---
{-# LANGUAGE GADTs #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE StandaloneDeriving #-}

import Data.Typeable

data Nat = Zero | Succ Nat
deriving ( Show, Eq, Ord )

deriving instance Typeable 'Zero
deriving instance Typeable 'Succ

data Box where
Box :: (Typeable s, Show s, Eq s) => s -> Box
deriving Typeable

data Proxy a = P deriving (Typeable, Show, Eq)

deriving instance Show Box
instance Eq Box where

(Box s1) == (Box s2) = Just s1 == cast s2

main = do

let one = undefined :: Main.Proxy ('Succ 'Zero)
let foo = Box one
print foo
--

Thanks a lot,

TP


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


Re: [Haskell-cafe] voting sytem DSL

2013-06-05 Thread AlanKim Zimmerman
Have you looked at http://frictionfreedemocracy.org/

They are using https://github.com/agocorona/Workflow amongst other things
to define election work flows.

Alan
On Jun 5, 2013 11:25 PM, "Corentin Dupont" 
wrote:

> Hi haskellers!
> I am trying to make a DSL able to describe a voting system. That DSL
> should be able to describe many different voting procedures:
> unanimity or majority, open or secret ballot, one or two turns... It
> should also work for referendums (yes/no question) or elections (electing
> one or several people)...
> Are you aware of any such DSL? In Haskell I haven't see it, maybe in
> another language?
>
> Cheers,
> Corentin
>
> ___
> 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


[Haskell-cafe] voting sytem DSL

2013-06-05 Thread Corentin Dupont
Hi haskellers!
I am trying to make a DSL able to describe a voting system. That DSL should
be able to describe many different voting procedures:
unanimity or majority, open or secret ballot, one or two turns... It should
also work for referendums (yes/no question) or elections (electing one or
several people)...
Are you aware of any such DSL? In Haskell I haven't see it, maybe in
another language?

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


[Haskell-cafe] FRP memory leaks

2013-06-05 Thread Łukasz Dąbek
Hello, Cafe!

I've heard that one of the problems of FRP (Functional Reactive
Programming) is that it's easy to create memory leaks. However I cannot
find any natural examples of such leaks. Could anybody post some
(pseudo)code demonstrating this phenomenon? Preferably something that
arises when one is writing bigger applications in FRP style.

Thanks in advance!

--
Łukasz Dąbek
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why isn't hsc2hs functionality provided by ghc?

2013-06-05 Thread Tillmann Rendel

Hi,

Roman Cheplyaka wrote:

My preferred solution would be to have ghc/ghci automatically run hsc2hs
[...] when necessary.


How about having a `ghci` command for cabal?


I don't think cabal can provide that. Let's say you're inside a 'cabal
ghci' session. If you modify the hsc file and reload it in ghci, you'd
expect to load the updated version — yet cabal hasn't even been called
since 'cabal ghci', and have had no chance to re-generate the hs file.


Maybe ghci could be changed to call some kind of hook everytime a file 
is called, and cabal could then provide an implementation for this hook 
that regenerates the files if necessary?


Maybe this is even possible today using:

  :def r somethingCleverHere

A quick test shows some minor problems, like

  :def r (const (return ":r"))
  :r

looping. But maybe this could be figured out.

  Tillmann

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


Re: [Haskell-cafe] Array, Vector, Bytestring

2013-06-05 Thread Bas van Dijk
On 5 June 2013 11:50, Peter Simons  wrote:
> I meant to say that there is redundancy in *both*. The libraries
> mentioned in this thread re-implement the same type internally and
> expose APIs to the user that are largely identical.

I agree. I hope that ByteStrings will be replaced by a Storable.Vector
of Word8 at some point in the future.

To make the transition easier I have an experimental library which
defines a ByteString as a type synonym of a Storable.Vector of Word8
and provides the same interface as the bytestring package:

https://github.com/basvandijk/vector-bytestring

It includes a comprehensive benchmark suite which compares it to
bytestring. IIRC some functions are way faster in vector than their
bytestring equivalents and they have the potential to fuse. However
some functions are still way slower so more work has to be done in
vector to beat bytestring completely.

Bas

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


Re: [Haskell-cafe] Array, Vector, Bytestring

2013-06-05 Thread Peter Simons
Hi Tom,

thank you for the explanation.

 > I believe you are suggesting that there is redundancy in the
 > implementation details of these libraries, not in the APIs they
 > expose.

I meant to say that there is redundancy in *both*. The libraries
mentioned in this thread re-implement the same type internally and
expose APIs to the user that are largely identical.

Take care,
Peter


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


Re: [Haskell-cafe] [haskell.org Google Summer of Code 2013] Approved Projects

2013-06-05 Thread Dominic Steinitz
I will certainly volunteer (to mentor) next year if I feel I can add value.

Dominic Steinitz
domi...@steinitz.org
http://idontgetoutmuch.wordpress.com

On 2 Jun 2013, at 17:23, Edward Kmett  wrote:

> Public good is a nebulous concept, but it is something that each of the folks 
> who sign up as mentors judges independently when they are rating the projects 
> and talking about them.
> 
> Most of the folks who are offering to mentor have been involved in the 
> community for quite some time and have a pretty good overview of what is 
> going on, and what are currently active pain points.
> 
> With 25 mentors we get a pretty good cross section of the community. We 
> aren't really able to canvas outside of the mentor group during the approval 
> process by google's guidelines, since we shouldn't leak information about 
> unaccepted projects. 
> 
> Something like that uservoice site might be used to gauge public opinion of 
> general ideas before the proposals start coming in, but in the end students 
> write the proposals we get, so the things we would have polled about are 
> inevitably not quite what we're rating anyways. We rarely get something that 
> is just cut and pasted from the ideas list. Consequently a generic rating 
> that doesn't take into consideration the actual proposal isn't worth a whole 
> lot, beyond giving students an idea of what might be a successful proposal. 
> There is a lot of variability in the ratings for projects based simply on 
> what we know about the student, how clear the proposal is, and how achievable 
> his or her particular goals are.
> 
> In practice, we've been able to make sure that a couple of slots go to 
> separable tasks in projects like cabal, haddock, and ghc that benefit 
> everyone and that exceptional one-off projects don't get shut out completely 
> just by asking each mentor to rate all of the projects, even the ones they 
> aren't interested in mentoring, and from the discussions between the mentors 
> and between the mentors and students that ensue within melange.
> 
> My main advice is that if you want to get involved in the process, the 
> easiest way to peel back the curtain is to volunteer to mentor! We're 
> generally quite open to adding new voices to the discussion.
> 
> -Edward
> 
> 
> 
> 
> On Sun, Jun 2, 2013 at 10:14 AM, Dominic Steinitz  
> wrote:
> Hi Edward,
> 
> Thanks for this comprehensive answer (and also thanks to participants in the 
> follow-up dissuasion).
> 
> How is the "public good" determined? (sounds rather Benthamite). I would have 
> been disappointed if "charts using diagrams" had not been selected yet I 
> don't recall being canvassed.
> 
> Sorry to sound picky. I think from what you say that in this particular year 
> it was obvious which projects should be selected; in future it may not be. I 
> think an acceptable reason would be "there was only one user who wanted it". 
> Maybe we should use something like: https://www.uservoice.com. Sadly it seems 
> this requires payment but there may be a free equivalent
> 
> Dominic Steinitz
> domi...@steinitz.org
> http://idontgetoutmuch.wordpress.com
> 
> On 28 May 2013, at 16:11, Edward Kmett  wrote:
> 
>> Hi Dominic,
>> 
>> The proposal is admittedly rather unfortunately opaque.
>> 
>> The parts I can shed light on:
>> 
>> Students come up with proposals with the help of the community and then 
>> submit them to google-melange.com.
>> 
>> A bunch of folks from the haskell community sign up as potential mentors, 
>> vote on and discuss the proposals. (We had ~25 candidate mentors and ~20 
>> proposals this year).
>> 
>> The student application template contains a number of desirable criteria for 
>> a successful summer of code application, which is shown on the 
>> google-melange website under our organization -- an old version is available 
>> http://hackage.haskell.org/trac/summer-of-code/wiki/StudApply2012 contains 
>> 
>> Once we have the proposals in hand, and some initial ranking, we ask google 
>> for slots. Allocation is based on past performance, arcane community 
>> parameters that only they know, mentor ratio, etc. This should be our 
>> largest year in the program, despite the fact that in general organizations 
>> have been getting fewer slots as more organizations join, so we're 
>> apparently doing rather well.
>> 
>> In general we do try to select projects that maximize the public good. Most 
>> of the time this can almost be done by just straight cut off based on the 
>> average score. There is some special casing for duplicate applications 
>> between different students and where students have submitted multiple 
>> applications we can have some flexibility in how to apply them.
>> 
>> This year we also received an extra couple of special-purpose darcs slots 
>> from Google in exchange for continuing to act as an umbrella organization 
>> over darcs at the request of the administrator of the program at Google. In 
>> previous years I had requested an extra sl

Re: [Haskell-cafe] Why isn't hsc2hs functionality provided by ghc?

2013-06-05 Thread Roman Cheplyaka
* Ivan Lazar Miljenovic  [2013-06-05 17:47:40+1000]
> On 5 June 2013 17:34, Roman Cheplyaka  wrote:
> > * Jason Dagit  [2013-06-04 21:00:25-0700]
> >> > My preferred solution would be to have ghc/ghci automatically run hsc2hs
> >> > (support c2hs also?) when necessary.  But so long as it's handled
> >> > automatically, I wouldn't be particularly bothered by the implementation.
> >>
> >> How about having a `ghci` command for cabal? Or does the automatic
> >> requirement really need to be part of ghc to work the way you want?
> >>
> >> (BTW, cabal-dev does have a `ghci` command, but I haven't tested to
> >> see if it does the hsc -> hs conversion.)
> >
> > I don't think cabal can provide that. Let's say you're inside a 'cabal
> > ghci' session. If you modify the hsc file and reload it in ghci, you'd
> > expect to load the updated version — yet cabal hasn't even been called
> > since 'cabal ghci', and have had no chance to re-generate the hs file.
> >
> > To answer the subject question — hsc2hs is not a single preprocessor
> > available. There are also c2hs and greencard, and maybe something else.
> > It is (or, at least, was) not clear which one should be generally
> > preferred. Perhaps by now hsc2hs is a clear winner — I don't know.
> >
> > Another option is to add a generic preprocessor option to GHC, something
> > like -pgmX cmd. Then, for hsc2hs one would write something like
> >
> >   {-# OPTIONS_GHC -pgmX hsc2hs #-}
> 
> Isn't this what -pgmF is
> for?http://www.haskell.org/ghc/docs/7.6.1/html/users_guide/options-phases.html#replacing-phases
> 
> {-# OPTIONS_GHC -F -pgmF hsc2hs #-}

Indeed! I should've read the whole section.

Problem solved, then?

Roman

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


Re: [Haskell-cafe] Typeable typeclass and type-level naturals

2013-06-05 Thread José Pedro Magalhães
On Wed, Jun 5, 2013 at 8:46 AM, Roman Cheplyaka  wrote:

> * TP  [2013-06-05 00:37:36+0200]
> > Roman Cheplyaka wrote:
> >
> > > Try adding
> > >
> > >   deriving instance Typeable 'Zero
> > >   deriving instance Typeable a => Typeable ('Succ a)
> > >
> > > to your module.
> > >
> > > (I haven't tested it -- you might need to tweak it a bit.)
> >
> > Thanks Roman.
> > Unfortunately, I already tried that (without the constraint "Typeable a
> =>",
> > what a fool), but it did not work. The error is the same with the
> > constraint:
> >
> > Derived typeable instance must be of form (Typeable 'Succ)
> > In the stand-alone deriving instance for
> >   'Typeable a => Typeable (Succ a)'
> >
> > What is the problem?
>
> Oh, it should probably be simply
>
>   deriving instance Typeable 'Zero
>   deriving instance Typeable 'Succ
>

Yes, that's how it should be. Please let me know if that
doesn't work.

(Sorry for taking so long to reply to this...)


Cheers,
Pedro


>
> Roman
>
> ___
> 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] Why isn't hsc2hs functionality provided by ghc?

2013-06-05 Thread Ivan Lazar Miljenovic
On 5 June 2013 17:34, Roman Cheplyaka  wrote:
> * Jason Dagit  [2013-06-04 21:00:25-0700]
>> > My preferred solution would be to have ghc/ghci automatically run hsc2hs
>> > (support c2hs also?) when necessary.  But so long as it's handled
>> > automatically, I wouldn't be particularly bothered by the implementation.
>>
>> How about having a `ghci` command for cabal? Or does the automatic
>> requirement really need to be part of ghc to work the way you want?
>>
>> (BTW, cabal-dev does have a `ghci` command, but I haven't tested to
>> see if it does the hsc -> hs conversion.)
>
> I don't think cabal can provide that. Let's say you're inside a 'cabal
> ghci' session. If you modify the hsc file and reload it in ghci, you'd
> expect to load the updated version — yet cabal hasn't even been called
> since 'cabal ghci', and have had no chance to re-generate the hs file.
>
> To answer the subject question — hsc2hs is not a single preprocessor
> available. There are also c2hs and greencard, and maybe something else.
> It is (or, at least, was) not clear which one should be generally
> preferred. Perhaps by now hsc2hs is a clear winner — I don't know.
>
> Another option is to add a generic preprocessor option to GHC, something
> like -pgmX cmd. Then, for hsc2hs one would write something like
>
>   {-# OPTIONS_GHC -pgmX hsc2hs #-}

Isn't this what -pgmF is
for?http://www.haskell.org/ghc/docs/7.6.1/html/users_guide/options-phases.html#replacing-phases

{-# OPTIONS_GHC -F -pgmF hsc2hs #-}

>
> This is a better option, IMO.
>
> Roman



-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
http://IvanMiljenovic.wordpress.com

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


Re: [Haskell-cafe] Typeable typeclass and type-level naturals

2013-06-05 Thread Roman Cheplyaka
* TP  [2013-06-05 00:37:36+0200]
> Roman Cheplyaka wrote:
> 
> > Try adding
> > 
> >   deriving instance Typeable 'Zero
> >   deriving instance Typeable a => Typeable ('Succ a)
> > 
> > to your module.
> > 
> > (I haven't tested it — you might need to tweak it a bit.)
> 
> Thanks Roman.
> Unfortunately, I already tried that (without the constraint "Typeable a =>", 
> what a fool), but it did not work. The error is the same with the 
> constraint:
> 
> Derived typeable instance must be of form (Typeable 'Succ)
> In the stand-alone deriving instance for
>   ‛Typeable a => Typeable (Succ a)’
> 
> What is the problem?

Oh, it should probably be simply

  deriving instance Typeable 'Zero
  deriving instance Typeable 'Succ

Roman

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


Re: [Haskell-cafe] Why isn't hsc2hs functionality provided by ghc?

2013-06-05 Thread Roman Cheplyaka
* Jason Dagit  [2013-06-04 21:00:25-0700]
> > My preferred solution would be to have ghc/ghci automatically run hsc2hs
> > (support c2hs also?) when necessary.  But so long as it's handled
> > automatically, I wouldn't be particularly bothered by the implementation.
> 
> How about having a `ghci` command for cabal? Or does the automatic
> requirement really need to be part of ghc to work the way you want?
> 
> (BTW, cabal-dev does have a `ghci` command, but I haven't tested to
> see if it does the hsc -> hs conversion.)

I don't think cabal can provide that. Let's say you're inside a 'cabal
ghci' session. If you modify the hsc file and reload it in ghci, you'd
expect to load the updated version — yet cabal hasn't even been called
since 'cabal ghci', and have had no chance to re-generate the hs file.

To answer the subject question — hsc2hs is not a single preprocessor
available. There are also c2hs and greencard, and maybe something else.
It is (or, at least, was) not clear which one should be generally
preferred. Perhaps by now hsc2hs is a clear winner — I don't know.

Another option is to add a generic preprocessor option to GHC, something
like -pgmX cmd. Then, for hsc2hs one would write something like

  {-# OPTIONS_GHC -pgmX hsc2hs #-}

This is a better option, IMO.

Roman

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