[Haskell-cafe] Indent aware parser

2012-05-04 Thread Lyndon Maydwell
Hi all.

What's the best indentation-aware parser at the moment?


I see three when I look in cabal:

lyndon@pugno:~ » cabal list indent
* IndentParser
Synopsis: Combinators for parsing indentation based syntatic structures
Default available version: 0.2.1
Installed versions: [ Not installed ]
Homepage: http://www.cse.iitk.ac.in/~ppk
License:  GPL

* indentparser
Synopsis: A parser for indentation based structures
Default available version: 0.1
Installed versions: [ Not installed ]
Homepage: http://www.cse.iitk.ac.in/users/ppk/code/HASKELL/indentparser
License:  PublicDomain

* indents
Synopsis: indentation sensitive parser-combinators for parsec
Default available version: 0.3.2
Installed versions: [ Not installed ]
Homepage: http://patch-tag.com/r/salazar/indents
License:  BSD3

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


[Haskell-cafe] Problem with forall type in type declaration

2012-05-04 Thread Magicloud Magiclouds
Hi,
  Assuming this:
run :: Monad IO a - IO a
data Test = Test { f }

  Here I'd like to set f to run, like Test run. Then what is the type of f?
  The confusing (me) part is that, the argument pass to f is not fixed
on return type, like f1 :: Monad IO (), f2 :: Monad IO Int. So
data Test a = Test { f :: Monad IO a - IO a} does not work.
-- 
竹密岂妨流水过
山高哪阻野云飞

And for G+, please use magiclouds#gmail.com.

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


Re: [Haskell-cafe] Indent aware parser

2012-05-04 Thread S D Swierstra
The uulib package provides combinators for dealing with the Haskell offside 
rule. Is that what you are looking for?

 Doaitse



Op 4 mei 2012 om 09:02 heeft Lyndon Maydwell maydw...@gmail.com het volgende 
geschreven:

 Hi all.
 
 What's the best indentation-aware parser at the moment?
 
 
 I see three when I look in cabal:
 
 lyndon@pugno:~ » cabal list indent
 * IndentParser
Synopsis: Combinators for parsing indentation based syntatic structures
Default available version: 0.2.1
Installed versions: [ Not installed ]
Homepage: http://www.cse.iitk.ac.in/~ppk
License:  GPL
 
 * indentparser
Synopsis: A parser for indentation based structures
Default available version: 0.1
Installed versions: [ Not installed ]
Homepage: http://www.cse.iitk.ac.in/users/ppk/code/HASKELL/indentparser
License:  PublicDomain
 
 * indents
Synopsis: indentation sensitive parser-combinators for parsec
Default available version: 0.3.2
Installed versions: [ Not installed ]
Homepage: http://patch-tag.com/r/salazar/indents
License:  BSD3
 
 ___
 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] Indent aware parser

2012-05-04 Thread Lyndon Maydwell
I'm not parsing Haskell, so the offside rule won't be required.

I'm looking at doing a more general Cassius parser.

On Fri, May 4, 2012 at 3:50 PM, S D Swierstra doai...@uu.nl wrote:
 The uulib package provides combinators for dealing with the Haskell offside 
 rule. Is that what you are looking for?

  Doaitse



 Op 4 mei 2012 om 09:02 heeft Lyndon Maydwell maydw...@gmail.com het 
 volgende geschreven:

 Hi all.

 What's the best indentation-aware parser at the moment?


 I see three when I look in cabal:

 lyndon@pugno:~ » cabal list indent
 * IndentParser
    Synopsis: Combinators for parsing indentation based syntatic structures
    Default available version: 0.2.1
    Installed versions: [ Not installed ]
    Homepage: http://www.cse.iitk.ac.in/~ppk
    License:  GPL

 * indentparser
    Synopsis: A parser for indentation based structures
    Default available version: 0.1
    Installed versions: [ Not installed ]
    Homepage: http://www.cse.iitk.ac.in/users/ppk/code/HASKELL/indentparser
    License:  PublicDomain

 * indents
    Synopsis: indentation sensitive parser-combinators for parsec
    Default available version: 0.3.2
    Installed versions: [ Not installed ]
    Homepage: http://patch-tag.com/r/salazar/indents
    License:  BSD3

 ___
 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] Problem with forall type in type declaration

2012-05-04 Thread Yves Parès
run :: Monad IO a - IO a

Actually this type is wrong. Monad has to appear as a class constraint, for
instance :

run :: Monad m = m a - IO a

Are you trying to make:

run :: IO a - IO a
??

2012/5/4 Magicloud Magiclouds magicloud.magiclo...@gmail.com

 Hi,
  Assuming this:
 run :: Monad IO a - IO a
 data Test = Test { f }

  Here I'd like to set f to run, like Test run. Then what is the type of
 f?
  The confusing (me) part is that, the argument pass to f is not fixed
 on return type, like f1 :: Monad IO (), f2 :: Monad IO Int. So
 data Test a = Test { f :: Monad IO a - IO a} does not work.
 --
 竹密岂妨流水过
 山高哪阻野云飞

 And for G+, please use magiclouds#gmail.com.

 ___
 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] Problem with forall type in type declaration

2012-05-04 Thread Magicloud Magiclouds
Sorry, it was just a persudo code. This might be more clear:

run :: (Monad m) = m IO a - IO a

On Fri, May 4, 2012 at 4:32 PM, Yves Parès yves.pa...@gmail.com wrote:
 run :: Monad IO a - IO a

 Actually this type is wrong. Monad has to appear as a class constraint, for
 instance :

 run :: Monad m = m a - IO a

 Are you trying to make:

 run :: IO a - IO a
 ??

 2012/5/4 Magicloud Magiclouds magicloud.magiclo...@gmail.com

 Hi,
  Assuming this:
 run :: Monad IO a - IO a
 data Test = Test { f }

  Here I'd like to set f to run, like Test run. Then what is the type of
 f?
  The confusing (me) part is that, the argument pass to f is not fixed
 on return type, like f1 :: Monad IO (), f2 :: Monad IO Int. So
 data Test a = Test { f :: Monad IO a - IO a} does not work.
 --
 竹密岂妨流水过
 山高哪阻野云飞

 And for G+, please use magiclouds#gmail.com.

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





-- 
竹密岂妨流水过
山高哪阻野云飞

And for G+, please use magiclouds#gmail.com.

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


Re: [Haskell-cafe] conduit: Finalize field in PipeM

2012-05-04 Thread Michael Snoyman
On Thu, May 3, 2012 at 11:11 PM, Paolo Capriotti p.caprio...@gmail.com wrote:
 Hi,
 I'm trying to write a function to convert a conduit to a Pipe (from
 pipes-core), and I'm having trouble understanding why the `Finalize`
 field in a `PipeM` constructor returns `r`. This makes it impossible
 to create it from the corresponding `M` constructor in pipes-core,
 since `M` includes an exception handler which is not guaranteed to run
 fully, hence may not provide a return value. `HaveOutput` presents a
 similar problem.

 From a cursory look at conduit's code, it doesn't look like the return
 value of `Finalize` is ever used, and it seems that the conduits that
 actually manage to define it either have `()` as return type or just
 throw an exception. The definition of `lift` for the `MonadTrans`
 instance duplicates the base monad action there, which doesn't look
 quite right to me (isn't that supposed to contain a _cleanup_
 action?).

 Shouldn't the constructor be changed to something like `PipeM (m (Pipe
 i o m r)) (Finalize m ())` or am I completely off base here?

 Thanks.

 BR,
 Paolo

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

If you look at Source and Conduit, the `r` parameter is already set to
`()`, so in practice[1], the issue only applies to Sink. And since
`Sink` cannot have a `HaveOutput` constructor, the question is only
for the `PipeM` constructor of a `Sink`.

`pipe`ing together values always requires that the left value contain
an `r` of `()`, so theoretically this only applies to monadic
composition. If you look in the code, you can see the monadic bind
*does*, in fact, use this value[2]:

PipeM mp c = fp = PipeM ((= fp) `liftM` mp) (c = pipeClose . fp)

Likewise, this would apply to `pipeClose`[3]. But `pipeClose` is far
less interesting than monadic bind, since it is really only used for
generating new Finalize values. So let's just focus on monadic bind.

In the code above, you can see that `fp` is of type `r1 - Pipe i o m
r2`. As such, `c` *must* return a value of type `r1`, not `()`. An
alternate approach here would be to scrap the `Finalize` field
entirely, and redefine `PipeM` as simply:

PipeM (m (Pipe i o m r))

The problem with this approach is that it can force unnecessary work
in some cases. Consider the case of `sourceFile`. When it comes time
to provide a new chunk of data, the code looks something like:

foo = PipeM (readChunk handle = \bs - return (HaveOutput foo
closeHandle bs)) (closeHandle bs)

If we didn't have that Finalize field, we would be forced to read an
extra chunk of data even if its not necessary.

I think the underlying point of distinction between conduit and
pipes-core here is that, is conduit, a Pipe of type `Pipe i o m r` is
*required* to provide an `r` value ultimately. If I understand
correctly, this is not the case in pipes-core. I believe this also
explains your question about the `MonadTrans` instance: `Finalize` is
not simply clean up resources, it's clean up resources __and__
return the required `r` value. That's why we duplicate the base monad
action: it's the only way to get a value of type `r` to return.

Michael

[1] I say in practice, because someone could in theory create some
type which is not a Source, Sink, or Conduit.
[2] 
https://github.com/snoyberg/conduit/blob/master/conduit/Data/Conduit/Internal.hs#L186
[3] 
https://github.com/snoyberg/conduit/blob/master/conduit/Data/Conduit/Internal.hs#L156

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


Re: [Haskell-cafe] Generalizing (++) for monoids instead of using ()

2012-05-04 Thread Alberto G. Corona
Thinking aloud, I dónt know if the transition to more abstract type
signatures can be aleviated using language directives.
Someting like:

Restrict (++)  String - String - String

that locally would restrict the type within the module.

Althoug it does not avoid breaking the old code, It permits an easy fix.

Moreover, This may have applications in other contexts, for example
teaching, because the wild abstraction of the error messages is the
most difficult barrier in haskell learning.

Cheers

Alberto

2012/4/1 Thomas DuBuisson thomas.dubuis...@gmail.com:
 On Sun, Apr 1, 2012 at 1:58 PM, aditya bhargava
 bluemangrou...@gmail.com wrote:
 After asking this question:
 http://stackoverflow.com/questions/9963050/standard-way-of-joining-two-data-texts-without-mappend

 I found out that the new infix operator for `mappend` is (). I'm wondering
 why ghc 7.4 didn't generalize (++) to work on monoids instead.

 Such decisions should really be made by the Haskell Prime committee
 (vs GHC HQ).  In Haskell there is a continuing tension between making
 things polymorphic and to keep the prelude functions monomorphic so
 they generate simple error messages (among other arguments).  At the
 point, the additional argument of any new definition of Haskell
 remaining backwards compatible also holds weight and this slows the
 rate-of-change.

 This is not a new issue, there are a number of functions that could be
 defined more generally (common example: map/fmap).  The problem making
 such changes is a matter of consensus and will to see things though.

 Cheers,
 Thomas

 ___
 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] Generalizing (++) for monoids instead of using ()

2012-05-04 Thread Malcolm Wallace

On 4 May 2012, at 10:02, Alberto G. Corona wrote:

 Restrict (++)  String - String - String
 
 that locally would restrict the type within the module.

import qualified Prelude
import Prelude hiding ((++))

(++) :: String - String - String
(++) = Prelude.(++)

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


Re: [Haskell-cafe] Annoyed at System.Random

2012-05-04 Thread Vincent Hanquez

On 05/04/2012 01:35 AM, Thomas DuBuisson wrote:

Vincent has done great work for Haskell+Crypto so I think he knows I
mean nothing personal when I say cprng-aes has the right idea done the
wrong way.  Why a new effort vs Vincent's package?

1. cprng-aes is painfully slow.

when using the haskell AES implementation yes. with AESNI it fly, and even more 
when
i'll have time to chunk the generation to bigger blocks (says 128 AES block at a 
time)

2. It doesn't use NI instructions (or any C implementation, currently).
The NI instructions support are coming. and there's ton of already existing C 
implementation

that could just be added.


3. It isn't backtracking resistent.  I plan to follow the SP and test
against the KATs.

I'm not sure i understand this. what's backtracking resistent ?

--
Vincent

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


Re: [Haskell-cafe] Annoyed at System.Random

2012-05-04 Thread Vincent Hanquez

On 05/04/2012 04:56 AM, Thomas DuBuisson wrote:
On May 3, 2012 5:49 PM, Ertugrul Söylemez e...@ertes.de mailto:e...@ertes.de 
wrote:


Thomas DuBuisson thomas.dubuis...@gmail.com
mailto:thomas.dubuis...@gmail.com wrote:

I can't really tell whether the first two points are true.


Feel free to investigate it yourself, I've convinced myself.  Vincent has 
added NI work to cryptocipher recently, but it still needs some corners 
smoothed.  I've contacted him about some of those already.  In the end I might 
use his C/ASM code for this task, but it is still lacking the ability to check 
for the NI instruction.
My end goal is to have the user use transparently the fastest implementation 
available to their architecture/cpu providing they use the high level module. 
I've uploaded the cpu package which allows me to detect at runtime the aes 
instruction (and the architecture), but i've been distracted in implementing 
fast galois field arithmetics for GCM and XTS mode (with AES).


So any contributions going in this direction is more than welcome.

--
Vincent

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


Re: [Haskell-cafe] Generalizing (++) for monoids instead of using ()

2012-05-04 Thread Alberto G. Corona
Fine ;)

So the transition should not be so problematic. An OldPrelude.hs may
be created easily with this.

Once again, thinking aloud.

2012/5/4 Malcolm Wallace malcolm.wall...@me.com:

 On 4 May 2012, at 10:02, Alberto G. Corona wrote:

 Restrict (++)  String - String - String

 that locally would restrict the type within the module.

 import qualified Prelude
 import Prelude hiding ((++))

 (++) :: String - String - String
 (++) = Prelude.(++)

 ___
 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] Annoyed at System.Random

2012-05-04 Thread Ryan Newton

 1. cprng-aes is painfully slow.

 when using the haskell AES implementation yes. with AESNI it fly, and even
 more when
 i'll have time to chunk the generation to bigger blocks (says 128 AES
 block at a time)


One data-point -- in intel-aes I needed to do bigger blocks to get decent
performance.


  2. It doesn't use NI instructions (or any C implementation, currently).

 The NI instructions support are coming. and there's ton of already
 existing C implementation
 that could just be added.


Oh, neat.  Could you share a pointer to some C code (with GCC aes
intrinsics?) that can replace what the ASM does in the intel-aes package?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Annoyed at System.Random

2012-05-04 Thread Ryan Newton

 My end goal is to have the user use transparently the fastest
 implementation available to their architecture/cpu providing they use the
 high level module. I've uploaded the cpu package which allows me to detect
 at runtime the aes instruction (and the architecture), but i've been
 distracted in implementing fast galois field arithmetics for GCM and XTS
 mode (with AES).


Yes!  A worthy goal!

I think the proposal here is that we do the build/integration work to get
something good which is portable enough and install-reliable enough to
replace 'random'.  Then people who don't care will be using a good
implementation by default.

That was my goal when I had my own small shot at this, but what I came up
with was *very* build-fragile.  (Depended on assembler being available, or
on prebuilt binaries being included for that package.)  You can see the
Setup.hs customization I attempted to do in intel-aes to compensate, but
it's not enough.

Can we write a cabal-compatible, really robust installer that will test the
users system and always fall back rather than failing?

  -Ryan

P.S. How are you doing the CPUID test for NI instructions?  I used the
*intel provided* test for this (in intel-aes) but I still had reports of
incorrect identification on certain AMD CPUs...
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Problem with forall type in type declaration

2012-05-04 Thread Daniel Díaz Casanueva
If one parameter is not enough, you always can add more:

Test m a b = Test { f :: m IO a - IO b }

This way, if

run :: m IO a - IO a

then

Test run :: Test m a a

But for other type for your run function

run' :: m IO a - IO b

you get

Test run' :: Test m a b

So you can have different types in input and output. Anyway, your type 'm'
is applied to other two types (m IO a), so it cannot be a monad, because
monads have arity 1 as type constructors, i.e. monads have kind (* - *).
Is perhaps 'm' some kind of monad transformer?

Well, that's all I can say from your explanation of the problem! Hope it
helps!

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


Re: [Haskell-cafe] Annoyed at System.Random

2012-05-04 Thread Thomas DuBuisson
Vincent uses gcc header files to get the AES instructions:

Header files of:

#include wmmintrin.h
#include tmmintrin.h

And later calls of:

 x = _mm_aesenc_si128(m, K1);

But currently you must know you have AESNI and use a flag:

cabal install cryptocipher -faesni

But if you are wrong:

Illegal instruction (core dumped)


This is a great place to be - now we just take the CPU checking from
intel-aes, make a switch between Vincent's C and Gladman (in haskell
or out, I doesn't matter to me), graft on Ctr mode as specified then
it's all about matching the current 'random' API.

Cheers,
Thomas

On Fri, May 4, 2012 at 6:37 AM, Ryan Newton rrnew...@gmail.com wrote:
 My end goal is to have the user use transparently the fastest
 implementation available to their architecture/cpu providing they use the
 high level module. I've uploaded the cpu package which allows me to detect
 at runtime the aes instruction (and the architecture), but i've been
 distracted in implementing fast galois field arithmetics for GCM and XTS
 mode (with AES).


 Yes!  A worthy goal!

 I think the proposal here is that we do the build/integration work to get
 something good which is portable enough and install-reliable enough to
 replace 'random'.  Then people who don't care will be using a good
 implementation by default.

 That was my goal when I had my own small shot at this, but what I came up
 with was *very* build-fragile.  (Depended on assembler being available, or
 on prebuilt binaries being included for that package.)  You can see the
 Setup.hs customization I attempted to do in intel-aes to compensate, but
 it's not enough.

 Can we write a cabal-compatible, really robust installer that will test the
 users system and always fall back rather than failing?

   -Ryan

 P.S. How are you doing the CPUID test for NI instructions?  I used the
 *intel provided* test for this (in intel-aes) but I still had reports of
 incorrect identification on certain AMD CPUs...


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


Re: [Haskell-cafe] Annoyed at System.Random

2012-05-04 Thread Vincent Hanquez

On 05/04/2012 02:37 PM, Ryan Newton wrote:


My end goal is to have the user use transparently the fastest
implementation available to their architecture/cpu providing they use the
high level module. I've uploaded the cpu package which allows me to detect
at runtime the aes instruction (and the architecture), but i've been
distracted in implementing fast galois field arithmetics for GCM and XTS
mode (with AES).


Yes!  A worthy goal!

I think the proposal here is that we do the build/integration work to get 
something good which is portable enough and install-reliable enough to replace 
'random'.  Then people who don't care will be using a good implementation by 
default.


That was my goal when I had my own small shot at this, but what I came up with 
was *very* build-fragile.  (Depended on assembler being available, or on 
prebuilt binaries being included for that package.)  You can see the Setup.hs 
customization I attempted to do in intel-aes to compensate, but it's not enough.


Can we write a cabal-compatible, really robust installer that will test the 
users system and always fall back rather than failing?

That was my original plan, until i find out that it's not really possible.

For the language, i think assembly is a no-no with cabal, as such it need to be 
embedded in gcc inline assembly if you want to have something that works (unless 
there's a secret way to run assembler in a portable fashion in cabal).


Which is the reason behind why i settled on intrinsics, as i didn't have to do 
the assembly directly. It appears more portable as well
as every major compiler seems to support it (with difference of course, it would 
too simple otherwise (!))


P.S. How are you doing the CPUID test for NI instructions?  I used the *intel 
provided* test for this (in intel-aes) but I still had reports of incorrect 
identification on certain AMD CPUs...




I haven't done it yet, but it should be just a matter of this piece of code for 
Intel and AMD:


import System.Cpuid
import Data.Bits

supportAESNI :: IO Bool
supportAESNI = cpuid 1 = \(_,_,ecx,_) - ecx `testBit` 25

--
Vincent

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


Re: [Haskell-cafe] Annoyed at System.Random

2012-05-04 Thread Brandon Allbery
On Fri, May 4, 2012 at 10:11 AM, Vincent Hanquez t...@snarc.org wrote:

 For the language, i think assembly is a no-no with cabal, as such it need
 to be embedded in gcc inline assembly if you want to have something that
 works (unless there's a secret way to run assembler in a portable fashion
 in cabal).


I don't know if cabal knows this, but assembler files with .s (and maybe
.asm on Windows?) extension are recognized by most C compilers and handed
off to the assembler; as such, simply augmenting cabal's C rules with those
extensions should be sufficient.

-- 
brandon s allbery  allber...@gmail.com
wandering unix systems administrator (available) (412) 475-9364 vm/sms
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Annoyed at System.Random

2012-05-04 Thread Vincent Hanquez

On 05/04/2012 02:33 PM, Ryan Newton wrote:


1. cprng-aes is painfully slow.

when using the haskell AES implementation yes. with AESNI it fly, and even
more when
i'll have time to chunk the generation to bigger blocks (says 128 AES
block at a time)


One data-point -- in intel-aes I needed to do bigger blocks to get decent 
performance.


Yes, it's a slightly random value here, although it's a tradeoff with memory 
usage and
performance, 128 blocks would do quite well compared to any haskell 
implementation that goes 1 block at a time [1]


[1] because you'll have to drop in/out of C, and reload the SSE registers each 
time.


2. It doesn't use NI instructions (or any C implementation, currently).

The NI instructions support are coming. and there's ton of already
existing C implementation
that could just be added.


Oh, neat.  Could you share a pointer to some C code (with GCC aes intrinsics?) 
that can replace what the ASM does in the intel-aes package?

Just have a look in cryptocipher with cbits/aes/x86ni.c

--
Vincent

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


Re: [Haskell-cafe] Annoyed at System.Random

2012-05-04 Thread Vincent Hanquez

On 05/04/2012 03:05 PM, Thomas DuBuisson wrote:

Vincent uses gcc header files to get the AES instructions:

Header files of:

 #includewmmintrin.h
 #includetmmintrin.h

And later calls of:

  x = _mm_aesenc_si128(m, K1);

But currently you must know you have AESNI and use a flag:

 cabal install cryptocipher -faesni

But if you are wrong:

 Illegal instruction (core dumped)
Of course that's expected as of now, since it's not finished and i had to push a 
new release (related to some significant performance improvement for 
RSA/DH/DSA), the code is there as a technology preview.


But the goal is to turn unconditionally the AESNI flag when arch is x86 or 
x86_64, which in this case the implementation would rely on the runtime cpuid 
check to use the aesni fastpath or not.




This is a great place to be - now we just take the CPU checking from
intel-aes, make a switch between Vincent's C and Gladman (in haskell
or out, I doesn't matter to me), graft on Ctr mode as specified then
it's all about matching the current 'random' API.
Please don't take the intel-aes test implementation. it's skewed to just support 
Intel,

since it basically testing for the cpu string GenuineIntel.

The only necessary test is the cpuid 1 with ecx having the 25th bit set.
It should just work providing cpus other than intel have matching cpuid 1 layout
(which as far i'm concerned seems to be the case in most cases)

--
Vincent

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


Re: [Haskell-cafe] Annoyed at System.Random

2012-05-04 Thread Vincent Hanquez

On 05/04/2012 03:18 PM, Brandon Allbery wrote:
On Fri, May 4, 2012 at 10:11 AM, Vincent Hanquez t...@snarc.org 
mailto:t...@snarc.org wrote:


For the language, i think assembly is a no-no with cabal, as such it need
to be embedded in gcc inline assembly if you want to have something that
works (unless there's a secret way to run assembler in a portable fashion
in cabal).


I don't know if cabal knows this, but assembler files with .s (and maybe .asm 
on Windows?) extension are recognized by most C compilers and handed off to 
the assembler; as such, simply augmenting cabal's C rules with those 
extensions should be sufficient.


That might works, although you might end up with some corner case portability 
issues.
Wrapping them in C should be more practical and you could write something like 
this for maximum portability (compiler,systems,..):


#if system_that_works_with_inline_asm
asm inline(instr1; instr2;, );
#else
 /* fallback to C */
#endif

--
Vincent

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


[Haskell-cafe] Fwd: Problem with forall type in type declaration

2012-05-04 Thread Chris Smith
Oops, forgot to reply-all again...

-- Forwarded message --
From: Chris Smith cdsm...@gmail.com
Date: Fri, May 4, 2012 at 8:46 AM
Subject: Re: [Haskell-cafe] Problem with forall type in type declaration
To: Magicloud Magiclouds magicloud.magiclo...@gmail.com


On Fri, May 4, 2012 at 2:34 AM, Magicloud Magiclouds
magicloud.magiclo...@gmail.com wrote:
 Sorry, it was just a persudo code. This might be more clear:

 run :: (Monad m) = m IO a - IO a

Unfortunately, that's not more clear.  For the constraint (Monad m) to
hold, m must have the kind (* - *), so then (m IO a) is meaningless.
I assume you meant one of the following:

   run :: MonadTrans m = m IO a - IO a

or

   run :: MonadIO m = m a - IO a

(Note that MonadIO is the class from the mtl package; there is no space there).

Can you clarify which was meant?  Or perhaps you meant something else entirely?

--
Chris Smith

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


Re: [Haskell-cafe] Problem with forall type in type declaration

2012-05-04 Thread Magicloud Magiclouds
Sorry to use Monad as the example, I meant this one:
 run :: MonadTrans m = m IO a - IO a

And Daniel, I do not think adding another type b a good idea. Since
run could actually return any inside type (depending on another
function that passed to it). Even simple as different tuples would
destroy this solution.

On Fri, May 4, 2012 at 10:05 PM, Daniel Díaz Casanueva
dhelta.d...@gmail.com wrote:
 If one parameter is not enough, you always can add more:

 Test m a b = Test { f :: m IO a - IO b }

 This way, if

 run :: m IO a - IO a

 then

 Test run :: Test m a a

 But for other type for your run function

 run' :: m IO a - IO b

 you get

 Test run' :: Test m a b

 So you can have different types in input and output. Anyway, your type 'm'
 is applied to other two types (m IO a), so it cannot be a monad, because
 monads have arity 1 as type constructors, i.e. monads have kind (* - *). Is
 perhaps 'm' some kind of monad transformer?

 Well, that's all I can say from your explanation of the problem! Hope it
 helps!

 Daniel Díaz.



-- 
竹密岂妨流水过
山高哪阻野云飞

And for G+, please use magiclouds#gmail.com.

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


Re: [Haskell-cafe] conduit: Finalize field in PipeM

2012-05-04 Thread Paolo Capriotti
On Fri, May 4, 2012 at 9:40 AM, Michael Snoyman mich...@snoyman.com wrote:
 I think the underlying point of distinction between conduit and
 pipes-core here is that, is conduit, a Pipe of type `Pipe i o m r` is
 *required* to provide an `r` value ultimately. If I understand
 correctly, this is not the case in pipes-core. I believe this also
 explains your question about the `MonadTrans` instance: `Finalize` is
 not simply clean up resources, it's clean up resources __and__
 return the required `r` value. That's why we duplicate the base monad
 action: it's the only way to get a value of type `r` to return.

So, if I understand correctly, that means that if you use `lift` to
specify a monadic action, there's no way to specify a different action
for cleanup. That probably implies that there is no sensible way to
convert a pipes-core pipe to a conduit pipe, at least not if you want
the finalization semantics to be preserved.

Thanks a lot for you reply!

BR,
Paolo

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


[Haskell-cafe] Haskell and arrays

2012-05-04 Thread Morten Olsen lysgaard
I'm a bit confused on what the standard is when it comes to arrays and 
performance in Haskell.


Say I have a function that takes an n dimensional array. The array only 
contains some primitive type.
The function mutates the array in an deterministic but chaotic pattern. 
The new value of an element might depend on other values in the array, 
and the order of update might depend on what values are found.


How would I implement this in an efficient fashion in Haskell. Is the 
array package the way to go? Would vector with some custom indexing 
scheme work well?
The array package provides n dimensional indexing, vector doesn't. Does 
vector perform better than array? Is it realistic to approach the 
performance of a naive c implementation? What steps would need to be 
taken in order to achieve that?


I know there are many question here, but I don't expect perfect answers 
to them. I just need to bootstrap my map of numerics in Haskell.


PS: An example of the above function could be Gaussian elimination of a 
matrix.


--
Morten Olsen Lysgaard
NTNU-IT - Orakeltjenesten
NTNU - Physics and Mathematics

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


Re: [Haskell-cafe] Haskell and arrays

2012-05-04 Thread Johan Tibell
Hi Morten,

If speed is really important I would go with the vector package. It
has a more modern API and better performance.

-- Johan

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


[Haskell-cafe] ANN: meta-par, meta-par-accelerate and friends -- heterogeneous parallel programming

2012-05-04 Thread Ryan Newton
Hi all,

I'm happy to announce a release of meta-par, a parallel programming library
that is a successor to monad-par.

   - http://hackage.haskell.org/package/abstract-par
   - http://hackage.haskell.org/package/monad-par
   - http://hackage.haskell.org/package/meta-par
   - http://hackage.haskell.org/package/abstract-par-accelerate
   - http://hackage.haskell.org/package/meta-par-accelerate

The distributed programming components aren't released yet, but this blog
posts describes how to use the above packages to do hybrid CPU/GPU
programming:


http://parfunk.blogspot.com/2012/05/how-to-write-hybrid-cpugpu-programs.html

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


[Haskell-cafe] MonadError vs Control.Exception

2012-05-04 Thread Станислав Черничкин
Hi, guys, I'm interested in best practices in using of each approach.
Personally I like MonadError because it is more explicit and
Control.Exception-s becomes really ugly in complex scenarios.

Here an example to illustrate my idea:
http://hackage.haskell.org/packages/archive/network-conduit/0.4.0/doc/html/src/Data-Conduit-Network.html#bindPort.
All network-conduit functions can raise IOException because of
Socket-related stuff (and actually entire network-conduit is written
to deal with IOException correctry) + Bind-port can raise ErrorCall
(came from error bindPort: addrs is empty). User has to deal with
both, but have no evidence on none of them from type signatures or
documentation. Moreover, ErrorCall in this case can be caused by
IOException (we try to bind only available address, we get IOException
exception, we have no more address to try and raise ErrorCall), and I
really don’t understand, why it should be treated in a different way.

So, I hate exceptions, I blame it, I think exceptions is junk came
from OO-world and horrible languages like C# or even more horrible
like Java, and it should be wiped out from Haskell with fire. But it
is only my humble opinion. Reality shows that Haskell provides
extensive support for exceptions, it included in base libraries and
everyone uses it, but MonadError is modest part of mtl, and don’t even
have “bracket” and other useful functions. That is why I’m really
interested in any your ideas and experience on using these approaches.

Cheers, Stasik.

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


Re: [Haskell-cafe] Generalizing (++) for monoids instead of using ()

2012-05-04 Thread Jeremy Shaw
In the context of string-like types ++ seems quite sensible because
the Monoid instances concat the strings.

However, not all Monoid instances imply concatenation. A Monoid
instance might provide choice. For example, we could define a parser,

 module Main where

 import Data.Monoid

 newtype Parser a = Parser { parse :: [Char] - Maybe (a, [Char]) }

and create a Monoid instance like:

 instance Monoid (Parser a) where
 mempty = Parser $ const Nothing
 (Parser p1) `mappend` (Parser p2) =
 Parser $ \str -
 case p1 str of
   (Just (a, cs)) - Just (a, cs)
   Nothing  - p2 str

And then create some simply parser combinators:

 satisfy :: (Char - Bool) - Parser Char
 satisfy p =
 Parser $ \str -
 case str of
   (c:cs) | p c - Just (c, cs)
   _- Nothing

 char :: Char - Parser Char
 char c = satisfy (== c)

Now, imagine we want to write a parser that parses 'a' or 'b':

 ab :: Parser Char
 ab = char 'a'  char 'b'

That will parse 'a' or 'b'. But what we had used ++ for mappend instead:

 ab :: Parser Char
 ab = char 'a' ++ char 'b'

You are much more likely to assume that parses 'a' followed by 'b'.
(Even though that doesn't really make sense when you consider the
return type -- you would expect, Parser String, if that was the case).

For the same reason, many people feel that mappend was a bad choice of
name in the first place, (and that (++) = mappend just makes a bad
thing worse).

Or maybe I am totally confused and am thinking about something else..

Anyway, the subject was certainly beaten to death quite a bit over the
last couple years. I think another reason why  was chosen is that a
number of libraries were already defining () = mappend locally? (not
positive about that).

- jeremy



On Sun, Apr 1, 2012 at 3:58 PM, aditya bhargava
bluemangrou...@gmail.com wrote:
 After asking this question:
 http://stackoverflow.com/questions/9963050/standard-way-of-joining-two-data-texts-without-mappend

 I found out that the new infix operator for `mappend` is (). I'm wondering
 why ghc 7.4 didn't generalize (++) to work on monoids instead. To me, (++)
 is much more clear. () means not equal to for me. Can anyone shed light
 on this decision?


 Adit

 --
 adit.io

 ___
 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