[Haskell-cafe] Parameterized constraints

2012-07-06 Thread Emil Axelsson

Hi!

The `constraints` package provides ways to manipulate objects of kind 
`Constraint`. I need the same kind of manipulation, except that I need 
to work with objects of kind `* -> Constraint`. I.e. I need 
parameterized constraints that can be applied to different types.


BTW, is there a standard term for things of kind `* -> Constraint`?

I have a type family

  type family Constr (f :: * -> *) :: * -> Constraint

which returns a parameterized constraint with the property that any 
value of type `f a` fulfills the constraint `Constr f a`. Since the 
constraint can be stronger than needed, I need something similar to `:-` 
from `constraints`, except it should operate on parameterized constraints.


I have implemented the stuff I need (see below), but my question is if 
it's possible to do this with the `constraints` package directly (e.g. 
using `Forall`). I'm afraid I can't see how.


Here is what I've come up with so far:

  -- Instead of (c1,c2)
  class(c1 a, c2 a) => (c1 :/\: c2) a
  instance (c1 a, c2 a) => (c1 :/\: c2) a

  -- Instead of (:-)
  type sub :< sup = forall a . Dict (sup a) -> Dict (sub a)

  -- Instead of weaken1
  weak1 :: c1 :< (c1 :/\: c2)
  weak1 Dict = Dict

  weak2 :: c2 :< (c1 :/\: c2)
  weak2 Dict = Dict

Thanks!

--
/ Emil


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


[Haskell-cafe] ANNOUNCE: husk-scheme, release 3.5.6

2012-07-06 Thread Justin Ethier
I would like to announce the release of husk-scheme 3.5.6, a Scheme
extension language and stand-alone interpreter/compiler that I have been
developing. husk implements most of the Scheme R5RS
standardincluding
advanced features such as continuations, hygienic macros, and a
full numeric tower. husk has been an ongoing project for over a year now,
but this is the first announcement on the mailing list so feedback is very
welcome. Hackage: http://hackage.haskell.org/package/husk-scheme
Homepage: http://justinethier.github.com/husk-scheme
Change Log:
https://github.com/justinethier/husk-scheme/blob/master/ChangeLog.markdown
Issues and Enhancement Requests:
https://github.com/justinethier/husk-scheme/issues

Thanks,

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


Re: [Haskell-cafe] Call to arms: lambda-case is stuck and needs your help

2012-07-06 Thread Chris Smith
Whoops, my earlier answer forgot to copy mailing lists... I would love to
see \of, but I really don't think this is important enough to make case
sometimes introduce layout and other times not.  If it's going to obfuscate
the lexical syntax like that, I'd rather just stick with \x->case x of.
On Jul 6, 2012 3:15 PM, "Strake"  wrote:

> On 05/07/2012, Mikhail Vorozhtsov  wrote:
> > Hi.
> >
> > 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!
> >
>
> +1 for "\ of" multi-clause lambdas
>
> It looks like binding "of" to me, which it ain't, but it is nicely brief...
>
> ___
> 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] ANNOUNCE: lens-family-th 0.1.0.0

2012-07-06 Thread Dan Burton
Following the announcement of lens-family, I'm pleased to announce
lens-family-th 0.1.0.0, a Template Haskell library supplying macros to
generate lens-family lenses for fields of data types declared with record
syntax.

Be warned that currently, type signatures are *not* generated alongside the
lens definitions. Type inference should correctly determine the type of the
generated lenses, but I have structured the library code so that in the
future, type signatures can also be generated. Patches welcome!

http://hackage.haskell.org/package/lens-family-th

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


Re: [Haskell-cafe] vector, alignment and SIMD through FFI

2012-07-06 Thread Nicolas Trangez
On Fri, 2012-07-06 at 13:43 -0700, Thomas DuBuisson wrote:
> On Fri, Jul 6, 2012 at 1:06 PM, Nicolas Trangez  wrote:
> > -- This fails:
> > -- Ambiguous type variable `a0' in the constraint:
> > --   (Storable a0) arising from a use of `sizeOf'
> 
> Here you can either tie a type knot using proxy types or you can use
> the scoped type variable language extension.

Guess I'll have to do some reading ;-) Thanks.

> Perhaps I'm missing something specific to your use, but for the
> alignment issue you should be OK just calling allocBytes or one of its
> variants.  I made some noise about this a bit ago and it resulted in
> some extra words in the report under mallocBytes:
> 
> """
> The block of memory is sufficiently aligned for any of the basic
> foreign types that fits into a memory block of the allocated size.
> """
> 
> Which I'm pretty sure GHC did, and still does, follow.

Hmh... as far as I could find, mallocBytes basically does what malloc(3)
does, which is 8-byte alignment if I'm not mistaken on my x86-64 Linux
system. I could use those and the over-allocate-and-offset tricks,
but... that's ugly unless strictly necessary ;-)

Normally posix_memalign or memalign or valloc or _mm_malloc should
provide what I need as-is.

Except, when using those and vector's unsafeFromForeignPtr0, all I get
is a "Vector a", which no longer has any alignment information in the
type, so I can't write a function which only accepts N-aligned vectors.
As a result, I'd need to be very careful only to pass aligned vectors to
it (checking manually), add code to handle pre/post-alignment bytes in
my SIMD functions (slow and stupid), or live with it and let my
application crash at random.

I found some work by Oleg Kiselyov and Chung-chieh Shan at [1] which
might be related, yet as of now I feel like that's too general for my
purpose (e.g. I don't see how to integrate it with vector).

Thanks,

Nicolas

[1] http://okmij.org/ftp/Haskell/types.html#ls-resources


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


Re: [Haskell-cafe] translation between two flavors of lexically-scoped type variables

2012-07-06 Thread Kangyuan Niu
Thanks, I think I understand it now.

Do you know why they switched over in GHC 6.6?

-Kangyuan Niu

On Fri, Jul 6, 2012 at 3:11 AM,  wrote:

>
> Kangyuan Niu wrote:
> > Aren't both Haskell and SML translatable into System F, from which
> > type-lambda is directly taken?
>
> The fact that both Haskell and SML are translatable to System F does
> not imply that Haskell and SML are just as expressive as System
> F. Although SML (and now OCaml) does have what looks like a
> type-lambda, the occurrences of that type lambda are greatly
> restricted. It may only come at the beginning of a polymorphic
> definition (it cannot occur in an argument, for example).
>
> > data Ap = forall a. Ap [a] ([a] -> Int)
> > Why isn't it possible to write something like:
> >
> > fun 'a revap (Ap (xs : 'a list) f) = f ys
> >   where
> > ys :: 'a list
> > ys = reverse xs
> >
> > in SML?
>
> This looks like a polymorphic function: an expression of the form
> /\a. has the type forall a. . However, the Haskell function
>
> > revap :: Ap -> Int
> > revap (Ap (xs :: [a]) f) = f ys
> >   where
> > ys :: [a]
> > ys = reverse xs
>
> you meant to emulate is not polymorphic. Both Ap and Int are concrete
> types. Therefore, your SML code cannot correspond to the Haskell code.
>
> That does not mean we can't use SML-style type variables (which must
> be forall-bound) with existentials. We have to write the
> elimination principle for existentials explicitly
>
> {-# LANGUAGE ExistentialQuantification, RankNTypes #-}
> {-# LANGUAGE ScopedTypeVariables #-}
>
> data Ap = forall a. Ap [a] ([a] -> Int)
>
> -- Elimination principle
> deconAp :: Ap -> (forall a. [a] -> ([a] -> Int) -> w) -> w
> deconAp (Ap xs f) k = k xs f
>
>
> revap :: Ap -> Int
> revap  ap = deconAp ap revap'
>
> revap' :: forall a. [a] -> ([a] -> Int) -> Int
> revap' xs f = f ys
>   where
>   ys :: [a]
>   ys = reverse xs
>
>
> Incidentally, GHC now uses SML-like design for type
> variables. However, there is a special exception for
> existentials. Please see
> 7.8.7.4. Pattern type signatures
> of the GHC user manual. The entire section 7.8.7 is worth reading.
>
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Call to arms: lambda-case is stuck and needs your help

2012-07-06 Thread Strake
On 05/07/2012, Mikhail Vorozhtsov  wrote:
> Hi.
>
> 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!
>

+1 for "\ of" multi-clause lambdas

It looks like binding "of" to me, which it ain't, but it is nicely brief...

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


Re: [Haskell-cafe] vector, alignment and SIMD through FFI

2012-07-06 Thread Bryan O'Sullivan
On Fri, Jul 6, 2012 at 1:43 PM, Thomas DuBuisson  wrote:

> The block of memory is sufficiently aligned for any of the basic
> foreign types that fits into a memory block of the allocated size.
>

That's not the same thing as a guarantee of 16-byte alignment, note, as
none of the standard foreign types have that requirement.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] vector, alignment and SIMD through FFI

2012-07-06 Thread Thomas DuBuisson
On Fri, Jul 6, 2012 at 1:06 PM, Nicolas Trangez  wrote:
> -- This fails:
> -- Ambiguous type variable `a0' in the constraint:
> --   (Storable a0) arising from a use of `sizeOf'

Here you can either tie a type knot using proxy types or you can use
the scoped type variable language extension.

Perhaps I'm missing something specific to your use, but for the
alignment issue you should be OK just calling allocBytes or one of its
variants.  I made some noise about this a bit ago and it resulted in
some extra words in the report under mallocBytes:

"""
The block of memory is sufficiently aligned for any of the basic
foreign types that fits into a memory block of the allocated size.
"""

Which I'm pretty sure GHC did, and still does, follow.

Cheers,
Thomas

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


[Haskell-cafe] cabal equivalent to "make -k"?

2012-07-06 Thread Omari Norman
When using make (or, at least, GNU make) the "-k" option keeps going
as far as possible after a compilation error. It's handy during
developing--for instance, "I know half of my code is busted, but I
just want to see if this file compiles." Is there a similar way to do
this with cabal? Thanks. --Omari

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


[Haskell-cafe] vector, alignment and SIMD through FFI

2012-07-06 Thread Nicolas Trangez
Hello Cafe,

Recently I've been playing with the implementation of an algorithm, for
which we already have highly-optimized implementations available (in
plain C/C++ as well as OCaml with calls to C through FFI).

The algorithm works on buffers/arrays/vectors/whatever you want to call
it, which needs to be combined in certain ways. This can be highly
optimized by using SIMD instructions (like the ones provides by several
SSE versions).

I'd like to get a to Haskell version which is comparable in efficiency
as the existing versions, whilst remaining as 'functional' as possible.
I don't mind jumping into some low-level C glue and FFI (using ccall or
custom primops), but this should be limited.

Currently I have something working (still highly unoptimized) using
(unboxed) vectors from the vector package, using mutable versions within
a well-contained ST environment in some places.

One hot zone of the current version is combining several vectors, and
the performance of this operation could be greatly improved by using
SIMD instructions. There's one catch though: when using these, memory
should be aligned on certain boundaries (16 byte in this case).

First and foremost, to be able to pass my vectors to some C functions, I
should change my code into using Storable vectors (which should be fine,
I guess I can expect similar performance characteristics?). I couldn't
find any information on alignment guarantees of these vectors though...

Which is how I get to my question: are there any such guarantees? If
not, are there any pointers to how to proceed with this? I guess
tracking alignment at the type level should be the goal, you can find
some code trying to explain my reasoning up to now at the end of this
email.

I have some issues with this:

- I'd need to re-implement almost all vector operations, which seems
stupid.
- It doesn't actually work right now ;-)
- It'd be nice to be able to encode 'compatible' alignment: as an
example, a 16 byte aligned buffer is also 8 byte aligned...

I hope the above explains somewhat my goal. Any thoughts & help on this
would be very welcome!

Thanks,

Nicolas


module Data.Vector.SIMD (
-- ...
) where

import qualified Data.Vector.Storable as SV

import Foreign.Storable (Storable, sizeOf)
import Foreign.Ptr (Ptr, FunPtr)
import Foreign.ForeignPtr (ForeignPtr, newForeignPtr)
import System.IO.Unsafe (unsafePerformIO)

class Alignment a where
alignment :: a -> Int

data A8Byte
instance Alignment A8Byte where
alignment _ = 8

data A16Byte
instance Alignment A16Byte where
alignment _ = 16

newtype Alignment a => SIMDVector a b = V (SV.Vector b)

replicate :: (Alignment a, Storable b) => a -> Int -> b -> SIMDVector a
b
replicate a n b = V v
  where
ptr = unsafePerformIO $ do
v <- _mm_malloc n (alignment a)
-- memset etc
return v

v = SV.unsafeFromForeignPtr0 ptr n

-- These are 2 _stub versions of the procedures since xmminstr.h (or
mm_malloc.h
-- when using GCC) contains them as inline procedures which are not
available
-- as-is in a library. There should be some C module which exports
-- _mm_malloc_stub and _mm_free_stub, which simply includes xmminstr.h
and calls
-- the underlying procedures.
foreign import ccall "_mm_malloc_stub" _mm_malloc_stub :: Int -> Int ->
IO (Ptr a)
foreign import ccall "_mm_free_stub" _mm_free_stub :: FunPtr (Ptr a ->
IO ())


_mm_malloc :: Storable a => Int -> Int -> IO (ForeignPtr a)
_mm_malloc s l = do
-- This fails:
-- Ambiguous type variable `a0' in the constraint:
--   (Storable a0) arising from a use of `sizeOf'
-- v <- c_mm_malloc (s * sizeOf (undefined :: a)) l
newForeignPtr _mm_free_stub undefined

-- This allocates a 16 byte aligned output buffer, takes 2 existing ones
and
-- calls some FFI function to perform some magic.
-- The implementation could run inside ST, if the FFI import (which e.g.
works
-- on a mutable buffer and returns IO ()) is lifted into ST using
unsafeIOToST
mySIMDFun :: SIMDVector A16Byte a -> SIMDVector A16Byte a -> SIMDVector
A16Byte a
mySIMDFun a b = undefined


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


Re: [Haskell-cafe] combining predicates, noob question

2012-07-06 Thread Brent Yorgey
On Fri, Jul 06, 2012 at 03:17:54PM -0300, Felipe Almeida Lessa wrote:
> On Fri, Jul 6, 2012 at 2:11 PM, Sebastián Krynski  wrote:
> > As I was using predicates (a -> bool) , it appeared the need for combining
> > them with a boolean operator (bool -> bool -> bool)  in order to get a new
> > predicate
> > combining the previous two. So I wrote my function combinerPred (see code
> > below). While I think this is JUST ok, i'm feeling a monad in the air.
> >  So.. where is the monad?
> >
> > combinerPred ::  (a -> Bool)  -> (a -> Bool) -> (Bool -> Bool -> Bool) ->
> > (a -> Bool)
> > combinerPred pred1 pred2 op = \x -> op (pred1 x) (pred2 x)
> 
> That's the `(->) a` monad:
> 
>   import Control.Applicative
> 
>   combinerPred ::  (a -> Bool)  -> (a -> Bool) -> (Bool -> Bool ->
> Bool) -> (a -> Bool)
>   combinerPred pred1 pred2 op = op <$> pred1 <*> pred2

By the way, I find it more natural to make 'op' the first argument,
because it is more useful to partially apply combinerPred to an
operation that it is to some predicates.  Also, in that case
combinerPred is simply liftA2:

  import Control.Applicative

  combinerPred :: (Bool -> Bool -> Bool) -> (a -> Bool) -> (a -> Bool) -> (a -> 
Bool)
  combinerPred = liftA2

-Brent

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


Re: [Haskell-cafe] combining predicates, noob question

2012-07-06 Thread Felipe Almeida Lessa
On Fri, Jul 6, 2012 at 2:11 PM, Sebastián Krynski  wrote:
> As I was using predicates (a -> bool) , it appeared the need for combining
> them with a boolean operator (bool -> bool -> bool)  in order to get a new
> predicate
> combining the previous two. So I wrote my function combinerPred (see code
> below). While I think this is JUST ok, i'm feeling a monad in the air.
>  So.. where is the monad?
>
> combinerPred ::  (a -> Bool)  -> (a -> Bool) -> (Bool -> Bool -> Bool) ->
> (a -> Bool)
> combinerPred pred1 pred2 op = \x -> op (pred1 x) (pred2 x)

That's the `(->) a` monad:

  import Control.Applicative

  combinerPred ::  (a -> Bool)  -> (a -> Bool) -> (Bool -> Bool ->
Bool) -> (a -> Bool)
  combinerPred pred1 pred2 op = op <$> pred1 <*> pred2

Cheers,

-- 
Felipe.

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


Re: [Haskell-cafe] [Haskell] ANNOUNCE: lens-family 0.0.0

2012-07-06 Thread Felipe Almeida Lessa
Hackage links for anyone as lazy as myself =).

http://hackage.haskell.org/package/lens-family-core
http://hackage.haskell.org/package/lens-family

-- 
Felipe.

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


[Haskell-cafe] ANNOUNCE: lens-family 0.0.0

2012-07-06 Thread roconnor
I'm pleased to announce the first release of lens-family-core and 
lens-family.


This package provide first class(†) functional references. In addition to 
the usual operations of getting, setting and composition, plus integration 
with the state monad, lens families provide some unique features:


* Polymorphic updating
* Cast projection functions to read-only lenses
* Cast semantic editor combinators to modify-only lenses

(†) For optimal first-class support use the lens-family package with rank 
2 / rank N polymorphism. Lens.Family.Clone allows for first-class support 
of lenses for those who require Haskell 98.


--
Russell O'Connor  
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Posting jobs on Haskellers.com

2012-07-06 Thread Bartosz Milewski
The link to the CUFP job posting is working now. (After I posted the 
previous message I found in my inbox an email telling me that the post will 
be live after it's been approved -- it is now). I was also able to post it 
on Haskellers ( http://www.haskellers.com/jobs/14 ). 

Posting on CUFP was easier and more convenient: they support HTML tags and 
preview. Haskellers needs to be improved (hopefully it should be a piece of 
cake with Yesod). We should be prepared for the incoming flood of Haskell 
jobs, if we do our job right, teaching and promoting Haskell.

On Thursday, July 5, 2012 2:24:51 PM UTC-7, Bartosz Milewski wrote:
>
> There are no job postings on Haskellers.com and I'm wondering whether it's 
> because you have to wait for the "verified" status before you can post (and 
> that's after you have successfully verified your email). Posting the job on 
> the CUFP site, on the other hand, was painless:  
> http://cufp.org/jobs/haskell-systems-administrator .

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


[Haskell-cafe] combining predicates, noob question

2012-07-06 Thread Sebastián Krynski
As I was using predicates (a -> bool) , it appeared the need for combining
them with a boolean operator (bool -> bool -> bool)  in order to get a new
predicate
combining the previous two. So I wrote my function combinerPred (see code
below). While I think this is JUST ok, i'm feeling a monad in the air.
 So.. where is the monad?

combinerPred ::  (a -> Bool)  -> (a -> Bool) -> (Bool -> Bool -> Bool) ->
 (a -> Bool)
combinerPred pred1 pred2 op = \x -> op (pred1 x) (pred2 x)


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


Re: [Haskell-cafe] [***SPAM***] Parallel Haskell Digest 11

2012-07-06 Thread Sean Leather
On Fri, Jul 6, 2012 at 4:03 PM, Eric Kow wrote:

> Subject line makes me wonder how often the digests get caught in people's
> spam filters


Oops! Should have removed that part before replying. I think it comes from
the university's mail server, and it's rather obnoxious. I tend to ignore
it.

Since you're curious, I can tell you that two out of the eleven issues (9
was the other one) were tagged as spam.

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


Re: [Haskell-cafe] Plain lambda inside banana brackets in the arrow notation

2012-07-06 Thread Tsuyoshi Ito
Dear Ertugrul,

Thank you for your input.

> To answer your question:  Arrow notation has no support for what you
> want, so if you stick with it you will have to write the inner proc
> explicitly.

Oh.  I was afraid of that.

> However:  The code may look much nicer, if you use applicative style for
> the outer computation using Applicative, Category and Profunctor [1]:

Thank you for the code.  It looks much nicer than my code, which uses
the arrow notation both for inner and outer computations.

> If you prefer, you can use arrow notation for the inner computation.

This was a blind spot for me; I had not thought of mixing the arrow
notation and the plain notation.  This definitely helps writing a code
when either the outer computation or the inner computation is simple.

Unfortunately, sometimes both the outer computation and the inner
computation involve many local variables, in which case I need the
arrow notation for both, forcing me to write the inner proc explicitly
inside the outer proc.  If someone extends the arrow notation someday
and makes this use case easier, that will be great.  For now, avoiding
the arrow notation for simple computations and writing two proc’s when
both computations are complicated seems like a reasonable compromise
to me.  Thanks a lot!

Best regards,
  Tsuyoshi

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


Re: [Haskell-cafe] [***SPAM***] Parallel Haskell Digest 11

2012-07-06 Thread Eric Kow
Ooh, nice catch.  Fixed on the HTML version.
http://www.well-typed.com/blog/67

Subject line makes me wonder how often the digests get caught in people's spam 
filters

Oh and while I'm at it, I'll take the opportunity to plug the PH Digest survey 
(I'll be annoying and make a reminder post just about the survey next week)

http://goo.gl/bP2fn

I didn't design it very well, particularly as I failed to give a clear question 
for people who don't read the digest.  I think if you don't read the digest, 
the best thing for now is just to say so in the comments form.

I may add a "I read the Parallel Haskell Digest" question if it helps later.

On 6 Jul 2012, at 14:57, Sean Leather wrote:

> Hi Eric (et Café),
> 
> On Thu, Jul 5, 2012 at 5:13 PM, Eric Kow wrote:
> *[Everybody should write everything in Go?][m7] (28 May)
> 
>  Ryan Hayes posted a small [snippet of Go][go-snippet] showing how
>  friendly he found it for writing concurrent programs, “No
>  pthread... not stupid crap... just works!”.  The program seems to
>  create 4 threads which print out 1 to 100 each. What do Haskellers
>  think? See the comments for some discussion between Haskell people
>  like Simon Marlow, and some folks in the Go community about our
>  respective approaches to the problem.
> 
> [go-snippet]: https://gist.github.com/3010649
> [m7]: 
> https://plus.google.com/app/plus/mp/588/#~loop:view=activity&aid=z13pwzbajpqeg3qmo23hgporhlywe1fd5
> 
> The [m7] link didn't work for me, but the following appears to be the 
> referenced thread:
> https://plus.google.com/10955911385859313/posts/FAmNTExSLtz
> 
> Regards,
> Sean

-- 
Eric Kow 



signature.asc
Description: Message signed with OpenPGP using GPGMail
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [***SPAM***] Parallel Haskell Digest 11

2012-07-06 Thread Sean Leather
Hi Eric (et Café),

On Thu, Jul 5, 2012 at 5:13 PM, Eric Kow wrote:

> *[Everybody should write everything in Go?][m7] (28 May)
>
>  Ryan Hayes posted a small [snippet of Go][go-snippet] showing how
>  friendly he found it for writing concurrent programs, “No
>  pthread... not stupid crap... just works!”.  The program seems to
>  create 4 threads which print out 1 to 100 each. What do Haskellers
>  think? See the comments for some discussion between Haskell people
>  like Simon Marlow, and some folks in the Go community about our
>  respective approaches to the problem.
>
> [go-snippet]: https://gist.github.com/3010649
> [m7]:
> https://plus.google.com/app/plus/mp/588/#~loop:view=activity&aid=z13pwzbajpqeg3qmo23hgporhlywe1fd5
>  [m8>


The [m7] link didn't work for me, but the following appears to be the
referenced thread:
https://plus.google.com/10955911385859313/posts/FAmNTExSLtz

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


Re: [Haskell-cafe] Plain lambda inside banana brackets in the arrow notation

2012-07-06 Thread Ertugrul Söylemez
Tsuyoshi Ito  wrote:

> How can I use combinators like repeat, which takes a plain function as
> an argument, in the arrow notation in a more readable way?  Or am I
> trying to do an impossible thing?

To answer your question:  Arrow notation has no support for what you
want, so if you stick with it you will have to write the inner proc
explicitly.

However:  The code may look much nicer, if you use applicative style for
the outer computation using Applicative, Category and Profunctor [1]:

test2 :: MyArr [Double] String
test2 = repeat 100 rmap . liftA3 (,,) id y z
where
y = arr func1
z = job1
rmap i = lmap (\(xs, y, z) -> xs !! i + y + z) (job3 (i * 2))

If you prefer, you can use arrow notation for the inner computation.

[1]: http://hackage.haskell.org/package/profunctors


Greets,
Ertugrul

-- 
Not to be or to be and (not to be or to be and (not to be or to be and
(not to be or to be and ... that is the list monad.


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


Re: [Haskell-cafe] translation between two flavors of lexically-scoped type variables

2012-07-06 Thread oleg

Kangyuan Niu wrote:
> Aren't both Haskell and SML translatable into System F, from which
> type-lambda is directly taken?

The fact that both Haskell and SML are translatable to System F does
not imply that Haskell and SML are just as expressive as System
F. Although SML (and now OCaml) does have what looks like a
type-lambda, the occurrences of that type lambda are greatly
restricted. It may only come at the beginning of a polymorphic
definition (it cannot occur in an argument, for example).

> data Ap = forall a. Ap [a] ([a] -> Int)
> Why isn't it possible to write something like:
>
> fun 'a revap (Ap (xs : 'a list) f) = f ys
>   where
> ys :: 'a list
> ys = reverse xs
>
> in SML?

This looks like a polymorphic function: an expression of the form
/\a. has the type forall a. . However, the Haskell function

> revap :: Ap -> Int
> revap (Ap (xs :: [a]) f) = f ys
>   where
> ys :: [a]
> ys = reverse xs

you meant to emulate is not polymorphic. Both Ap and Int are concrete
types. Therefore, your SML code cannot correspond to the Haskell code.

That does not mean we can't use SML-style type variables (which must
be forall-bound) with existentials. We have to write the
elimination principle for existentials explicitly

{-# LANGUAGE ExistentialQuantification, RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}

data Ap = forall a. Ap [a] ([a] -> Int)

-- Elimination principle
deconAp :: Ap -> (forall a. [a] -> ([a] -> Int) -> w) -> w
deconAp (Ap xs f) k = k xs f


revap :: Ap -> Int
revap  ap = deconAp ap revap'

revap' :: forall a. [a] -> ([a] -> Int) -> Int
revap' xs f = f ys
  where
  ys :: [a]
  ys = reverse xs


Incidentally, GHC now uses SML-like design for type
variables. However, there is a special exception for
existentials. Please see
7.8.7.4. Pattern type signatures
of the GHC user manual. The entire section 7.8.7 is worth reading.



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