Re: [Haskell-cafe] Bytestring map/zipWith rationale

2013-09-12 Thread Thomas DuBuisson
On Thu, Sep 12, 2013 at 12:44 PM, Nicolas Trangez  wrote:
> I did use that a couple of times (`xor`ing 2 ByteStrings together), and was
> surprised by the omission back then, but IIRC (can't validate now), there's
> a specialised zipWith (as proposed) in the module (with some other name,
> obviously), which is not exported, but used when you 'pack' the result of
> 'zipWith' when the result is '[Word8]'... You might want to look into that.

This is correct - there is a RULES pragma that rewrites `pack (zipWith
f)` into a more efficient `zipWith'` function of the type desired (see
the bytestring package).  I was very concerned about this when writing
lots of bytestring xor code for crypto-api and was pleased to find
that, if the syntactic form matches, things get optimized as you
desire.

Thomas

>
> Nicolas
>
> On Sep 12, 2013 8:11 PM, "John Lato"  wrote:
>>
>> Carter: we don't have both.  We have one function from each category.  My
>> guess is nobody's ever really needed a really fast zipWith ::
>> (Word8->Word8->Word8) -> ByteString -> ByteString -> ByteString; that's the
>> only reason I can think of for its omission.
>>
>>
>> On Thu, Sep 12, 2013 at 10:45 AM, Carter Schonwald
>>  wrote:
>>>
>>> Scott: benchmark the two and you'll see why we have both :-)
>>>
>>>
>>> On Thursday, September 12, 2013, Scott Lawrence wrote:

 On Thu, 12 Sep 2013, Tom Ellis wrote:

> On Thu, Sep 12, 2013 at 09:21:20AM -0400, Scott Lawrence wrote:
>>
>> Something's always bothered me about map and zipWith for ByteString.
>> Why is it
>>
>> map :: (Word8 -> Word8) -> ByteString -> ByteString
>>
>> but
>>
>> zipWith :: (Word8 -> Word8 -> a) -> ByteString -> ByteString ->
>> [a]
>
>
> Well, what if you wanted to zipWith a function of type "Word8 -> Word8
> ->
> Foo" instead of "Word8 -> Word8 -> Word8"?


 Then I would do what I do with map, and call `unpack` first.

 Either of the two options is usable:

  map :: (Word8 -> Word8) -> ByteString -> ByteString
  zipWith :: (Word8 -> Word8 -> Word8) -> ByteString -> ByteString ->
 ByteString
(or)
  map :: (Word8 -> a) -> ByteString -> [a]
  zipWith :: (Word8 -> Word8 -> a) -> ByteString -> ByteString -> [a]

 I just don't understand why we have one from each.

 --
 Scott Lawrence
 ___
 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
>>
>
> ___
> 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] ordNub

2013-07-14 Thread Thomas DuBuisson
Just so people are aware - five years ago the notion of nubOrd and
nubWith was discussed and a consensus reached on including nubOrd.  I
think Bart got too busy, didn't submit a final patch, and no one with
commit access actually commited any code.

http://haskell.1045720.n5.nabble.com/GHC-2717-Add-nubWith-nubOrd-td3159919.html

I fully support an efficient nub implementation making its way into
base - it's far past time.  Using Set seems sensible.

Cheers,
Thomas



On Sun, Jul 14, 2013 at 4:20 AM, Niklas Hambüchen  wrote:
> tldr: nub is abnormally slow, we shouldn't use it, but we do.
>
>
> As you might know, Data.List.nub is O(n²). (*)
>
> As you might not know, almost *all* practical Haskell projects use it,
> and that in places where an Ord instance is given, e.g. happy, Xmonad,
> ghc-mod, Agda, darcs, QuickCheck, yesod, shake, Cabal, haddock, and 600
> more (see https://github.com/nh2/haskell-ordnub).
>
> I've taken the Ord-based O(n * log n) implementation from yi using a Set:
>
>   ordNub :: (Ord a) => [a] -> [a]
>   ordNub l = go empty l
> where
>   go _ [] = []
>   go s (x:xs) = if x `member` s then go s xs
> else x : go (insert x s) xs
>
>
> and put benchmarks on
> http://htmlpreview.github.io/?https://github.com/nh2/haskell-ordnub/blob/1f0a2c94a/report.html
> (compare `nub` vs `ordNub`).
>
> `ordNub` is not only in a different complexity class, but even seems to
> perform better than nub for very small numbers of actually different
> list elements (that's the numbers before the benchmark names).
>
> (The benchmark also shows some other potential problem: Using a state
> monad to keep the set instead of a function argument can be up to 20
> times slower. Should that happen?)
>
> What do you think about ordNub?
>
> I've seen a proposal from 5 years ago about adding a *sort*Nub function
> started by Neil, but it just died.
>
>
> (*) The mentioned complexity is for the (very common) worst case, in
> which the number of different elements in the list grows with the list
> (alias you don't have an N element list with always only 5 different
> things inside).
>
> ___
> 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] [ANN] New releases of crypto-api, DRBG, commsec, commsec-keyexchange, and cipher-aes128

2013-04-23 Thread Thomas DuBuisson
All,

I have recently released new versions of:

- crypto-api[1]:  An interface for cryptographic algorithms such as
block ciphers, hashes, and secure random number generators.  This
version includes Klondike's cbcMac and SIV modes of operation - much
thanks to his numerous patches.

- DRBG[2]: A set of deterministic random bit generators (aka CPRNGs)
based on NIST 800-90.

- commsec[3]: A communications security package that provides data in
transit security using AES-128 GCM without any external, C library,
dependencies.

- commsec-keyexchange[4]: A key exchange tool that leverages RSA keys
to establish connection's for use with the commsec package.

- cipher-aes128[5]: A re-packaging of Vincent Hanquez's excellent AES routines.

==Crypto API==

Crypto-API was first released in 2010 with an aim of providing an
interface useful to consumers of cryptographic algorithms and
providers of those algorithms.  It includes classes for block, stream,
and asymmetric ciphers as well as for random number generators,
hashes, and signature algorithms.

Recent changes include:
- Added SIV and cbcMac thanks to Klondike.  NOTE: Some of this code is
only conditionally included via a compile time flag due to GHC's slow
compilation of the CPoly module.
- Moved block cipher modes into the type classes, allowing use of
high-speed C or ASM mode implementations.
- More generator query methods in the CryptoRandomGen class.
- Updated build dependencies
- Move operations and expose them from Crypto.Util

==DRBG==

DRBG implements the Hash and HMAC based generators specified in NIST
SP 800-90.  A generator using block ciphers in CTR mode is also
provided, but is not based on the special publication.

==CommSec and CommSec-KeyExchange==

Together, these packages provide a way to start from shared RSA keys
and obtain a thread-safe secure communications channel.  A
pull-request is currently out to crypto-pubkey-openssh that would
allow the reading and use of RSA keys generated by ssh-keygen.

These packages aim to be "morally correct" in that they perform the
correct operations at an equivalent computational cost of a properly
vetted system, but are not themselves vetted for critical use.  For
small messages, commsec performs faster than the non-threadsafe
secure-sockets counterpart.  For larger messages the performance is
not as competitive due to the GCM routine not being fully optimized.

==cipher-aes128==

This package has performance benefits (vs cipher-aes) due to
function-pointer rewriting that allows us to avoid excessive checking
of the CPU info [6].  This package is hopefully going to be
short-lived with the optimizations getting folded into Vincent's
'cipher-aes' once things are mature enough.  A windows tester would
help.


Comments and patches are welcome.  Sorry if I forgot to thank anyone
who contributed, many of these projects have been neglected and I lose
context in the interim.

Cheers,
Thomas M. DuBuisson

[1] http://hackage.haskell.org/package/crypto-api
[2] http://hackage.haskell.org/package/DRBG
[3] http://hackage.haskell.org/package/commsec
[4] http://hackage.haskell.org/package/commsec-keyexchange
[5] http://hackage.haskell.org/package/cipher-aes128
[6] https://github.com/vincenthz/hs-cipher-aes/issues/8 - Up to 40%
faster for small operations.

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


Re: [Haskell-cafe] Bug in Network package

2013-04-10 Thread Thomas DuBuisson
Replying to all.  Sorry for the duplicate, Florian.

The fact that the constructor `PortNum` is exported has been argued to be a
bug in past discussions.  PortNumber is stored big endian, which leads to
behaviors that people don't expect.  I suggest you lean on the fact that
PortNumber is an instance of the Num class:

ghci
...
> 478 :: PortNumber
478

Cheers,
Thomas


On Wed, Apr 10, 2013 at 12:26 AM, Florian Hofmann <
fhofm...@techfak.uni-bielefeld.de> wrote:

> I might be mistaken, but is there a bug in the Show instance of PortNum?
>
>
> λ PortNum 1
> 256
> λ PortNum 2
> 512
> λ PortNum 3
> 768
>
> λ let (PortNum x) = PortNum 10
> λ x
> 10
>
> Tested with network-2.4.1.2
>
> ___
> 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] How can I avoid buffered reads?

2012-11-28 Thread Thomas DuBuisson
As an alternative, If there existed a Haskell package to give you fast
cryptographically secure random numbers or use the new Intel RDRAND
instruction (when available) would that interest you?

Also, what you are doing is identical to the "entropy" package on
hackage, which probably suffers from the same bug/performance issue.

Cheers,
Thomas

On Wed, Nov 28, 2012 at 11:38 AM, Leon Smith  wrote:
> I have some code that reads (infrequently) small amounts of data from
> /dev/urandom,  and because this is pretty infrequent,  I simply open the
> handle and close it every time I need some random bytes.
>
> The problem is that I recently discovered that,  thanks to buffering within
> GHC,   I was actually reading 8096 bytes when I only need 16 bytes,  and
> thus wasting entropy.   Moreover  calling hSetBuffering  handle NoBuffering
> did not change this behavior.
>
> I'm not sure if this behavior is a bug or a feature,  but in any case it's
> unacceptable for dealing with /dev/urandom.   Probably the simplest way to
> fix this is to write a little C helper function that will read from
> /dev/urandom for me,  so that I have precise control over the system calls
> involved. But I'm curious if GHC can manage this use case correctly;
> I've just started digging into the GHC.IO code myself.
>
> Best,
> Leon
>
> {-# LANGUAGE BangPatterns, ViewPatterns #-}
>
> import   Control.Applicative
> import   Data.Bits
> import   Data.Word(Word64)
> import qualified Data.ByteString as S
> import qualified Data.ByteString.Lazy as L
> import   Data.ByteString.Internal (c2w)
> import qualified System.IOas IO
> import qualified Data.Binary.Getas Get
>
> showHex :: Word64 -> S.ByteString
> showHex n = s
>   where
> (!s,_) = S.unfoldrN 16 f n
>
> f n = Just (char (n `shiftR` 60), n `shiftL` 4)
>
> char (fromIntegral -> i)
>   | i < 10= (c2w '0' -  0) + i
>   | otherwise = (c2w 'a' - 10) + i
>
> twoRandomWord64s :: IO (Word64,Word64)
> twoRandomWord64s = IO.withBinaryFile "/dev/urandom" IO.ReadMode $ \handle ->
> do
>IO.hSetBuffering handle IO.NoBuffering
>Get.runGet ((,) <$> Get.getWord64host <*> Get.getWord64host) <$> L.hGet
> handle 16
>
> main = do
>(x,y) <- twoRandomWord64s
>S.hPutStrLn IO.stdout (S.append (showHex x) (showHex y))
>
>
> {- Relevant part of strace:
>
> open("/dev/urandom", O_RDONLY|O_NOCTTY|O_NONBLOCK) = 3
> fstat(3, {st_mode=S_IFCHR|0666, st_rdev=makedev(1, 9), ...}) = 0
> ioctl(3, SNDCTL_TMR_TIMEBASE or TCGETS, 0x7367e528) = -1 EINVAL (Invalid
> argument)
> ioctl(3, SNDCTL_TMR_TIMEBASE or TCGETS, 0x7367e528) = -1 EINVAL (Invalid
> argument)
> read(3,
> "N\304\4\367/\26c\"\3218\237f\214yKg~i\310\r\262\"\224H\340y\n\376V?\265\344"...,
> 8096) = 8096
> close(3)= 0
>
> -}
>
>
> ___
> 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] performance issues with popCount

2012-09-06 Thread Thomas DuBuisson
What _should_ be happening is we should be calling GMP's popcount
function when using integer-gmp.

As for your code I worry about it:
* being too lazy, so add some bang patterns or seq
* using boxed arrays, so use unboxed
* indexing arrays by Integer comparison even when those are small
integers - just index by Int.
* will never terminate with negative values.  Sure it's a solution but
calling 'error' is more appropriate.

But really I hope you spend the time fixing base, not making a one-off
solution that will still be slow.

Cheers,
Thomas


On Thu, Sep 6, 2012 at 9:46 AM, Harald Bögeholz  wrote:
> Dear Haskell Cafe,
>
>
> I am struggling with the performance of the popCount function from
> Data.Bits.
>
> To be more precise: I downloaded the Haskell Platform 2012.2.0.0 from
> http://hackage.haskell.org/platform/ (64 bit, Mac OS X). In this version
> I found the popCount function to be broken. If I look in the online
> documentation at
> http://hackage.haskell.org/packages/archive/base/4.5.1.0/doc/html/src/Data-Bits.html#popCount
> it is already fixed, but included with my Haskell Platform was the
> broken version.
>
> Anyway, I tried this version
>
> popCount :: Integer -> Int
> popCount = go 0
> where
> go c 0 = c
> go c w = go (c+1) (w .&. (w - 1))
>
> and profiling showed that my program spent 80 % of its time counting bits.
>
> So I thought I'm clever and implement a table-based version like this:
>
> popCount' :: Integer -> Int
> popCount' = go 0
> where
> go c 0 = c
> go c w = go (c+1) (w .&. (w - 1))
>
> popCountN = 10
>
> popCountMask :: Integer
> popCountMask = shift 1 popCountN - 1
>
> popCountTable :: Array Integer Int
> popCountTable = listArray (0, popCountMask) $ map popCount' [0 ..
> popCountMask]
>
> popCount :: Integer -> Int
> popCount 0 = 0
> popCount x = popCountTable ! (x .&. popCountMask) + popCount (x `shiftR`
> popCountN)
>
>
> turns out this is even slower ... now my program spends 90 % of its time
> counting bits :-(.
>
>
> Any hints?
>
>
> Thanks
> --
> Harald Bögeholz (PGP key available from servers)
> Redaktion c't  Tel.: +49 511 5352-300  Fax: +49 511 5352-417
>http://www.ct.de/
>
>int f[9814],b,c=9814,g,i;long a=1e4,d,e,h;
>main(){for(;b=c,c-=14;i=printf("%04d",e+d/a),e=d%a)
>while(g=--b*2)d=h*b+a*(i?f[b]:a/5),h=d/--g,f[b]=d%g;}
>   (Arndt/Haenel)
>
>Affe Apfel Vergaser
>
> /* Heise Zeitschriften Verlag GmbH & Co. KG * Karl-Wiechert-Allee 10 *
>30625 Hannover * Registergericht: Amtsgericht Hannover HRA 26709 *
>Persönlich haftende Gesellschafterin: Heise Zeitschriften Verlag *
>Geschäftsführung GmbH * Registergericht: Amtsgericht Hannover, HRB
>60405 * Geschäftsführer: Ansgar Heise, Dr. Alfons Schräder */
>
> ___
> 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] Hackage is down?

2012-08-11 Thread Thomas DuBuisson
It will be down most of today - we are switching over to a new network
connection.

On Sat, Aug 11, 2012 at 11:31 AM, hanjoosten  wrote:
> Hi,
>
> Hackage seems to be down. Is there anyone out here who knows how to get it
> online again?
>
> Thanks!
>
>
>
> --
> View this message in context: 
> http://haskell.1045720.n5.nabble.com/Hackage-is-down-tp5715912.html
> Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.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] foreign import and gmp

2012-08-08 Thread Thomas DuBuisson
On Wed, Aug 8, 2012 at 3:24 PM, Lars Kuhtz  wrote:
> On 8/8/12 2:55 PM, Thomas DuBuisson wrote:
>> You need to build GHC using the integer-simple library (instead of the
>> 'integer-gmp' library).  From the 6.12.1 release notes:
>>
>> """
>> It is now possible to build GHC with a simple, BSD-licensed Haskell
>> implementation of Integer, instead of the implementation on top of
>> GMP. To do so, set INTEGER_LIBRARY to integer-simple in mk/build.mk.
>> """
>
> How to I build the Haskell platform in this case? Is it enough to just
> use a GHC that was build with INTEGER_LIBRARY=integer-simple in the
> build of the platform, or do I need to somehow configure the platform
> build to prevent packages from importing integer-gmp?

I don't understand this question largely because I don't understand
the need to consider an entity called "the Haskell Platform".  You can
build and install individual libraries.  Some of those libraries will
not build and install the trivial way (cabal install BLAH) but will
build and install when given a flag (cabal install -f integer-simple
BLAH).  I hope (but have not put in any effort) for the HP community
to push for a single solution that includes tivial compile-time
detection of the integer support, thus making flags unnecessary.

>
>> In addition, some libraries depend on integer-gmp (sadly).  This is
>> usually part of an optimization and when I see it I tend to send in a
>> patch adding an "integer-simple" flag so you can cabal install it by
>> including "-finteger-simple" on the command line (text is an example
>> of one such library).
>
> Does this mean that text does already support this flag?

Yes: http://hackage.haskell.org/packages/archive/text/0.11.2.2/text.cabal

>
>> And that's it!  Your integer operations will run slower but you should
>> get stable operation even when using the GMP library.
>
> What about operations on Integers with small values? Are they still
> efficient, i.e. directly mapped to operations on native int?

For that you'll have to look at the integer-simple package, perform
some benchmarks, or wait another five minutes for someone besides me
to answer.  Even small Int's are represented via a slightly more
involved ADT so I expect there will be more pointers and measurably
more overhead.

Cheers,
Thomas

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


Re: [Haskell-cafe] foreign import and gmp

2012-08-08 Thread Thomas DuBuisson
You need to build GHC using the integer-simple library (instead of the
'integer-gmp' library).  From the 6.12.1 release notes:

"""
It is now possible to build GHC with a simple, BSD-licensed Haskell
implementation of Integer, instead of the implementation on top of
GMP. To do so, set INTEGER_LIBRARY to integer-simple in mk/build.mk.
"""

In addition, some libraries depend on integer-gmp (sadly).  This is
usually part of an optimization and when I see it I tend to send in a
patch adding an "integer-simple" flag so you can cabal install it by
including "-finteger-simple" on the command line (text is an example
of one such library).

And that's it!  Your integer operations will run slower but you should
get stable operation even when using the GMP library.

Cheers,
Thomas

On Wed, Aug 8, 2012 at 2:45 PM, Lars Kuhtz  wrote:
> Hi all,
>
> There have been rumors that recent versions of GHC may allow foreign
> imports of objects that link against gmp without interfering with the
> gmp imports in integer-gmp. What is the current state of that issue?
> What is the currently recommended way to deal with that problem?
>
> Thanks,
> Lars
>
>
> ___
> 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] Community-wide RFP

2012-08-03 Thread Thomas DuBuisson
There is an ignored reddit for that
(http://www.reddit.com/r/haskell_proposals), but somewhere good?  I
don't think so.

Thomas

On Fri, Aug 3, 2012 at 8:02 AM, Black Mephistopheles
 wrote:
> Is there a place - on the Haskell Wiki perhaps - with a list of desired
> Haskell-related projects? Both for programs written in Haskell, as well as
> things to help, and enhance the programming experience?
>
> Walt "BMeph" Rorie-Baety
>
> I am an eyewitness to what you committed in that location.
>
>
>
>
> ___
> 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] 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


Re: [Haskell-cafe] What is the difference between runhaskell and compile?

2012-05-24 Thread Thomas DuBuisson
If it is simple then please paste it somewhere.  Perhaps stackoverflow
would be a better medium for this discussion.

-Thomas

On Thu, May 24, 2012 at 8:05 PM, Magicloud Magiclouds
 wrote:
> Hi there,
>  The code could not be simpler. Just ldapInit, ldapSimpleBind.
>  I just found that the code works with ghci, too. So to sum up,
> ghci/runhaskell works, ghc not.
>
> On Thu, May 24, 2012 at 8:15 PM, Vincent Ambo  wrote:
>> Can you paste your code somewhere? I'm using the LDAP package at work (for 
>> authenticating a Yesod app) and a quick test of the basic LDAP package in 
>> GHCi works for me:
>>
>> λ> import LDAP
>> λ> ldap <- ldapInit "10.0.0.12" ldapPort
>> λ> ldapSimpleBind ldap "geva" "**"
>> λ> let desiredAttr = LDAPAttrList ["name"]
>> λ> let searchDN = Just "OU=Redacted,DC=redacted,DC=com"
>> λ> let searchFilter = Just "sAMAccountName=geva"
>> λ> ldapSearch ldap searchDN LdapScopeSubtree searchFilter desiredAttr False
>> [LDAPEntry {ledn = "CN=Vincent Ambo,OU=Redacted,DC=redacted,DC=com", leattrs 
>> = [("name",["Vincent Ambo"])]}]
>>
>> It also works in compiled applications and in source files run with 
>> runhaskell.
>>
>> Our directory server runs Active Directory.
>>
>> On May 24, 2012, at 11:36 AM, Magicloud Magiclouds wrote:
>>
>>> Hi,
>>>  I am writing a small program using LDAP hackage. A weird problem occured.
>>>  When the code was run by runhaskell, things were fine, worked as expected.
>>>  But when ghc compiled (no any args), and ran, I got this: LDAP
>>> error: ldapSimpleBind: LDAPException LdapServerDown(-1): Can't contact
>>> LDAP server.
>>>  There is sure no problem with the server.
>>>  So I am confused. I thought the two supposed to be the same.
>>> --
>>> 竹密岂妨流水过
>>> 山高哪阻野云飞
>>>
>>> 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

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


Re: [Haskell-cafe] Can Haskell outperform C++?

2012-05-21 Thread Thomas DuBuisson
On Mon, May 21, 2012 at 7:53 AM, Yves Parès  wrote:
>> Not necessarily.  For example the 'nub' function from Data.List could be
>> much faster.  Unfortunately this would also change its type.  O(n²)
>> complexity is really the best you can get with the Eq constraint.
>
> Why not in that kind of cases provide a second function (named differently),
> together with the original function, and specify they're differences (i.e.
> wrt performances) in the doc?
> It seems like a pretty quick and honest trade-off to me.


WRT nub, Bart Massey did exactly this in his "nubOrd" proposal.  He
obtained consensus then failed to finish the ticket [1].  If this
particular case is of interest to you or anyone else then I suggest
you take the patches, re-propose and see it finished.  If you are
interested in this general category of issue, I think this is a case
study in how costly even our seemingly light weight proposals process
is in terms of proposer time investment.

Cheers,
Thomas

[1] http://hackage.haskell.org/trac/ghc/ticket/2717

>
> 2012/5/21 Ertugrul Söylemez 
>>
>> Ryan Newton  wrote:
>>
>> > I do think we have the opposite problem, however, in much Haskell code
>> > -- people are using the clean, obviously correct, but inefficient code
>> > even in standard library functions that really should be optimized
>> > like crazy!
>>
>> Not necessarily.  For example the 'nub' function from Data.List could be
>> much faster.  Unfortunately this would also change its type.  O(n²)
>> complexity is really the best you can get with the Eq constraint.  You
>> have to change to Ord for better performance.
>>
>> In other words:  Some optimizations change the semantics, and semantics
>> is taken very seriously in Haskell, for which I'm grateful.
>>
>>
>> Greets,
>> Ertugrul
>>
>> --
>> Key-ID: E5DD8D11 "Ertugrul Soeylemez "
>> FPrint: BD28 3E3F BE63 BADD 4157  9134 D56A 37FA E5DD 8D11
>> Keysrv: hkp://subkeys.pgp.net/
>>
>> ___
>> 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] Annoyed at System.Random

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

Header files of:

#include 
#include 

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  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-03 Thread Thomas DuBuisson
On May 3, 2012 5:49 PM, "Ertugrul Söylemez"  wrote:

> 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.
> > 2. It doesn't use NI instructions (or any C implementation,
> > currently).
> > 3. It isn't backtracking resistent.  I plan to follow the SP and test
> > against the KATs.
>
> 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.


>  If they are,
> they should be really easy to fix and don't really require a new package
>

'random' isn't a new package.  We can't simply rename any package depending
on crypto-api and add a new face because we should also consider the build
deps.

About the third point:  This should be easy to fix and would probably be
> the only breaking change (in that it would generate different sequences
> than before).  However, it is questionable whether you want AES at all
> in this case.  A hash function-based PRNG would probably be better.
> This could indeed justify a new library.  On the other hand you want NI
> instructions.
>

There are many ways to make a CTR based DRBG backtrack resistant.  As I've
alluded to already - I'd just go with the NIST SP.


> > 4. Lots of people still use "random" by default, so it would be good
> > to have StdGen be something reasonable, where "reasonable" is from as
> > many perspectives as we can manage.
>
> Of course this is not cprng-aes' fault, so this point is one of its own
> unrelated to my original response.


This is the core of the proposal, ignoring this is to ignore the purpose of
the entire thread.



>  StdGen is really unfortunate and
> should be replaced, but by what?  In an older thread this question
> turned out to be difficult to answer.


It was difficult back then because there was some confusion about adhering
to the Haskell Report.  Well, Random isn't part of Haskell 2010+ and older
standards include a copy in their own package, so we (read: Ryan) have a
much freer hand.

Cheers,
Thomas

P.S. The email seems pointed, but I'm just merrily making points.
___
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-03 Thread Thomas DuBuisson
On Thu, May 3, 2012 at 5:26 PM, Ertugrul Söylemez  wrote:
> Thomas DuBuisson  wrote:
>
>> I've grown annoyed at System.Random enough (specifically, StdGen).
>> How much, if any, pushback would there be if I put together a FFI
>> binding to a C AES-CTR based RNG.  There are many advantages:
>>
>> [...]
>>
>> I'd be tempted to pull in the 'entropy' package for seeding, but will
>> make that a separate proposal.
>
> Why reinvent the wheel?
>
>    <http://hackage.haskell.org/package/cprng-aes>
>
> Has both a System.Random and a Crypto-API interface.  As such it is
> already connected to the 'entropy' package.

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.
2. It doesn't use NI instructions (or any C implementation, currently).
3. It isn't backtracking resistent.  I plan to follow the SP and test
against the KATs.
4. Lots of people still use "random" by default, so it would be good
to have StdGen be something reasonable, where "reasonable" is from as
many perspectives as we can manage.

This isn't to say that we could use much of the structure and
higher-level code that Vincent has already done.

Cheers,
Thomas

>
>
> Greets,
> Ertugrul
>
> --
> nightmare = unsafePerformIO (getWrongWife >>= sex)
> http://ertes.de/
>
> ___
> 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] Annoyed at System.Random

2012-05-03 Thread Thomas DuBuisson
Ryan,
I've grown annoyed at System.Random enough (specifically, StdGen).
How much, if any, pushback would there be if I put together a FFI
binding to a C AES-CTR based RNG.  There are many advantages:

0) The API wouldn't have to change (though some parts should, and some
change is already planned)
1) It can be fast (maybe not MT fast, but really quite good)
2) It's secure and the splitting properties can be related to
cryptographic problems.
3) It could use Intel NI instructions when available.
4) It's NIST standardized, so there exist known answer tests.
5) We could expose a method to fill an arbitrary buffer :: Storable a
=> Ptr a -> Int -> IO ()
6) The rest of the community doesn't have to do any of the work.

I'd be tempted to pull in the 'entropy' package for seeding, but will
make that a separate proposal.

Cheers,
Thomas

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


Re: [Haskell-cafe] ANNOUNCE: planar-graph-1.0

2012-04-27 Thread Thomas DuBuisson
Good work, Ivan.  Despite your numerous previous pointers, I still
haven't look at this API.  I'm glad to see this release, it's great
motivation and I'll probably look through it this weekend.

Thanks for all the graph library work you do,
Thomas

On Fri, Apr 27, 2012 at 4:07 PM, Ivan Lazar Miljenovic
 wrote:
> I uploaded this [1] yesterday, posted the blog article [2] about it...
> but forgot to send a message to the lists!
>
> [1]: http://hackage.haskell.org/package/planar-graph
> [2]: http://ivanmiljenovic.wordpress.com/2012/04/27/announcing-planar-graph/
>
> planar-graph is an implementation of, strangely enough, planar graphs
> (that is, a graph that contains an embedding on a surface, can be
> drawn with no edge crossings and has a specific ordering of edges).
> It handles graphs on planes and spheres, but I'm not sure about other
> surfaces (and there seems to be little demand for such).
>
> This probably won't be of many use to people, but as I described in
> the blog post, I've been using this as a test bed for graph library
> design (specifically usage of abstract node/edge identifiers, using
> half-edges and the serialisation/encoding setup).
>
> --
> 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

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


Re: [Haskell-cafe] Uploading a new hsc2hs

2012-04-25 Thread Thomas DuBuisson
On Wed, Apr 25, 2012 at 5:27 PM, Antoine Latter  wrote:
> On Wed, Apr 25, 2012 at 4:59 PM, Thomas DuBuisson
>  wrote:
>> Warning:
>>
>> I, not the maintainer of hsc2hs, will be uploading a trivial fix for
>> hsc2hs to hackage (new build deps).  Even after public attempts to
>> contact anyone in charge of hsc2hs (last January) there still has been
>> no word.  Speak now or forever hold your peace.
>>
>
> I don't think I've ever installed hsc2hs from Hackage as it ships with GHC.

Fair point, and Ian has been the one pushing patches to the repo
lately.  Ian - any objections to me bumping to version 0.68 and
uploading that to hackage?

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


[Haskell-cafe] Uploading a new hsc2hs

2012-04-25 Thread Thomas DuBuisson
Warning:

I, not the maintainer of hsc2hs, will be uploading a trivial fix for
hsc2hs to hackage (new build deps).  Even after public attempts to
contact anyone in charge of hsc2hs (last January) there still has been
no word.  Speak now or forever hold your peace.

Cheers,
Thomas


P.S. I still think c2hs is the right philosophy even if it's too verbose.

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


Re: [Haskell-cafe] building ghc on arch linux ARM?

2012-04-08 Thread Thomas DuBuisson
On Sun, Apr 8, 2012 at 4:03 PM, Francesco Mazzoli  wrote:
> No, it is not possible to build GHC without GHC. Building GHC on ARM is
> going to be extremely tricky (I'm not sure anyone has ever done it).

I used to use an unregistered build of GHC built by someone in the
Debian community - it worked well enough.

Cheers,
Thomas

>
> What you should be able to do easily with the next release is cross-compile
> to ARM through the LLVM backend.
>
> Francesco.
>
>
> On 08/04/12 23:28, . wrote:
>>
>> Hi Cafe,
>> I hope this is the right place to ask this kind of stuff.
>> I would like to try ghc on a panda board (armv7l) with arch linux.
>> There is apparently no pre-built package, so I was trying the
>> instructions to build, from here:
>> .
>>
>> However, I still seem to need a ghc and ghc-pkg installed: I am getting
>> this error message:
>> 
>> checking for tar... /bin/tar
>> checking for gpatch... no
>> checking for patch... /usr/bin/patch
>> checking for dtrace... no
>> checking for HsColour... no
>> checking for xmllint... no
>> configure: WARNING: cannot find xmllint in your PATH, you will not be
>> able to validate your documentation
>> checking for xsltproc... no
>> configure: WARNING: cannot find xsltproc in your PATH, you will not be
>> able to build the HTML documentation
>> checking for dblatex... no
>> configure: WARNING: cannot find dblatex in your PATH, you will not be
>> able to build the PDF and PS documentation
>> checking for ghc-pkg matching ... configure: error: Cannot find matching
>> ghc-pkg
>>
>> -
>>
>> Does anyone know if it is possible to build ghc without ghc on this
>> platform?
>> I was using the tarball sources for ghc 7.4.1.
>>
>>
>> Thanks,
>> Christian
>>
>>
>>
>> ___
>> 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] Generalizing (++) for monoids instead of using (<>)

2012-04-01 Thread Thomas DuBuisson
On Sun, Apr 1, 2012 at 1:58 PM, aditya bhargava
 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


Re: [Haskell-cafe] Where to get kansas-lava version 2.5

2012-02-22 Thread Thomas DuBuisson
Have you tried just bumping the version number of the kansas-lava repo
head?  Or asking Andy about it?

At any rate, it looks like you're over-eager for the bleeding edge.
KU hasn't even released 0.2.5 to hackage, as you noted, and users
aren't typically expected to pull the latest from the source repo.

Cheers,
Thomas

On Wed, Feb 22, 2012 at 8:46 PM, dilawar rajput  wrote:
> Hello Cafe,
>
> Greetings from Mumbai.
>
> Does anyone know where to get kansas-lava version 2.5?
>
> On their github repository (as well as on Hackage), they have not posteed
> version 2.5. However their kansas-lava-cores requires version kansas-lava
> 2.5.
>
> Currently I am working with kansas-lava 2.4 but I can not use their latest
> kansas-lava-core with it.
>
> --
> Dilawar
>
>
> ___
> 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] Disabling warning over ranges of source lines

2012-02-19 Thread Thomas DuBuisson
Using GHC, is there any way to disable warnings (entirely or
selectively) during a section of source code?  I ask because of some
Template Haskell that periodically generates unused code and I'd
rather not see the warnings or rework the macros (beyond emitting some
sort of "disable" and "re-enable" pragma which probably isn't in the
AST now that I think about it).

Cheers,
Thomas

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


Re: [Haskell-cafe] [ANN] Crypto-API 0.9 Release

2012-01-31 Thread Thomas DuBuisson
Oh, sorry for the omission!  I've worked out of HEAD for long enough
that I though that was in 0.8.

On Tue, Jan 31, 2012 at 5:36 PM, Felipe Almeida Lessa
 wrote:
> Also:
>
>  * MacKey has phantom types.
>
> This seems to be the only breaking change [1].

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


[Haskell-cafe] [ANN] Crypto-API 0.9 Release

2012-01-31 Thread Thomas DuBuisson
Crypto-API is a generic interface for cryptographic operations,
defining classes for hashes, ciphers, and random number generation
while also providing convenience functions such as block cipher modes
and padding. Maintainers of hash and cipher implementations are
encouraged to add instances for the classes defined in Crypto.Classes.
Crypto users are similarly encouraged to use the interfaces defined in
the Classes module.

Release 0.9 Changes:
* Crypto.Classes now exports 'Data.Serialize.encode'
* AsymCipher now has proper fundeps
* cpolysArr is no longer one big line

Cheers,
Thomas

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


Re: [Haskell-cafe] [web-devel] [ANNOUNCE] First release of crypto-conduit

2012-01-08 Thread Thomas DuBuisson
Aristid Breitkreuz  wrote:
> To use the hash, I have to convert it to a ByteString, and then I
> suddenly have lost all this safety. I don't really see how there is
> any real safety gained.

But that isn't true for all users.  Sometimes a hash is computed long
before it is transmitted, so while you're passing it around you can be
sure it won't be confused with other raw data (basically, what Vincent
said).  Also, some users never want to convert to a bytestring - using
the Eq and Ord instances are enough.

> That said, just exposing a direct method of getting to that ByteString
> without cereal (as Thomas proposed) would be an improvement.

I'll do this and release crypto-api 0.9 soonish.

Cheers,
Thomas

>
>
>
> Aristid
>
>
> 2012/1/8 Vincent Hanquez :
>> On 01/08/2012 04:12 AM, Aristid Breitkreuz wrote:
>>>
>>> Why? I don't actually need the hash object for anything, usually. All
>>> I need is the ByteString, and then I need to learn how to use the
>>> cereal package to get it...
>>
>> The whole rationale i believe, is having meaningful types associated to your
>> values so that the type checker can do its job. i.e. you don't start mixing
>> a hash (in binary form) and a random piece of file.
>>
>> My only problem with the Serialize instance, is that dependencies (cereal in
>> this case) trickle through to the user of the API, which would be solved by
>> Thomas' suggestion.
>>
>> --
>> Vincent
>
> ___
> 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] [web-devel] [ANNOUNCE] First release of crypto-conduit

2012-01-07 Thread Thomas DuBuisson
> Why? I don't actually need the hash object for anything, usually. All
> I need is the ByteString, and then I need to learn how to use the
> cereal package to get it...

What would you think if Crypto.Classes exported Data.Serialize.encode?
 Or how about if it exported Antoine's hash suggestion (under a
different name)?

Cheers,
Thomas

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


Re: [Haskell-cafe] FGL custom node identification (Label -> Node lookup)

2011-11-24 Thread Thomas DuBuisson
My thinking on this was that something akin to NodeMap should be
_part_ of the graph structure.  This would be more convenient and
allow the graph and nodemap operations to apply to a single data
structure.

Instead of:

insMapNode_ :: (Ord a, DynGraph g) => NodeMap a -> a -> g a b -> g a b

You could have:

insMapNode_ :: (Ord a, DynGraph g) => a -> g a b -> g a b

The only think stopping us from making a product data type like this
is the inflexibility of the type classes, right?  Were we able to
define (&) to update the nodemap too then we could keep these to
structures in sync automatically instead of expecting the programmer
to keep them paired correctly.

Cheers,
Thomas

On Thu, Nov 24, 2011 at 1:42 AM, Ivan Lazar Miljenovic
 wrote:
> On 24 November 2011 20:33, Thomas DuBuisson  
> wrote:
>> All,
>>
>> The containers library has a somewhat primitive but certainly useful
>> Data.Graph library.  Building a graph with this library simultaneously
>> results in the lookup functions:
>>
>>   m1 :: Vertex -> (node, key, [key])
>>   m2 :: key -> Maybe Vertex
>>
>> (where 'key' is like FGL's 'label' but is assumed to be unique)
>>
>> This is exactly what I wanted when building and analyzing a call graph
>> in FGL.  To that end, I started making a graph type that tracked label
>> to Node mappings, wrapping Data.Graph.Inductive.Gr,  and assuming the
>> labels are all unique.
>>
>> The classes for such a graph actually aren't possible.  The ability to
>> build a mapping from a node's 'label' to the 'Node' requires extra
>> context (ex: Hashable, Ord, or at least Eq), but such context can not
>> be provided due to the typeclass construction.
>>
>> Is there any chance we can change the Graph and DiaGraph classes to
>> expose the type variables 'a' and 'b'?
>>
>>    class Graph gr a b where ...
>>    class (Graph gr) => DynGraph gr a b where ...
>>
>> This would allow instances to provide the needed context:
>>
>>    instance (Hashable a, Hashable b) => Graph UniqueLabel a b where
>>          ...
>>          buildGraph = ... some use of containers libraries that
>> require context ...
>>          ...
>>    lookupNode :: Hashable a => UniqueLabel a b -> a -> Node
>>    -- etc
>>
>>
>> Cheers,
>> Thomas
>>
>> P.S.  Please do educate me if I simply missed or misunderstood some
>> feature of FGL.
>
> Well, there *is* the NodeMap module, but I haven't really used it so
> I'm not sure if it does what you want.
>
> We did start upon a version of FGL which had these type variables in
> the class, but it got a little fiddly; the ability to have superclass
> constraints should solve this but I haven't touched FGL for a while,
> as I've been working on some other graph library code for planar
> graphs, with the plan to take my experience from writing this library
> into a "successor" to FGL.
>
> However, my experience with designing this planar graph library has
> led me to using abstract (i.e. non-exported constructor) ID types for
> nodes and edges and finding them rather useful, but then I'm more
> concerned about the _structure_ of the graph rather than the items
> stored within it.  As such, I'd appreciate you explaining to me
> (off-list is OK) why you want/need such a label -> node mapping so
> that I can try and work out a way to incorporate such functionality.
>
> --
> Ivan Lazar Miljenovic
> ivan.miljeno...@gmail.com
> IvanMiljenovic.wordpress.com
>

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


[Haskell-cafe] FGL custom node identification (Label -> Node lookup)

2011-11-24 Thread Thomas DuBuisson
All,

The containers library has a somewhat primitive but certainly useful
Data.Graph library.  Building a graph with this library simultaneously
results in the lookup functions:

   m1 :: Vertex -> (node, key, [key])
   m2 :: key -> Maybe Vertex

(where 'key' is like FGL's 'label' but is assumed to be unique)

This is exactly what I wanted when building and analyzing a call graph
in FGL.  To that end, I started making a graph type that tracked label
to Node mappings, wrapping Data.Graph.Inductive.Gr,  and assuming the
labels are all unique.

The classes for such a graph actually aren't possible.  The ability to
build a mapping from a node's 'label' to the 'Node' requires extra
context (ex: Hashable, Ord, or at least Eq), but such context can not
be provided due to the typeclass construction.

Is there any chance we can change the Graph and DiaGraph classes to
expose the type variables 'a' and 'b'?

class Graph gr a b where ...
class (Graph gr) => DynGraph gr a b where ...

This would allow instances to provide the needed context:

instance (Hashable a, Hashable b) => Graph UniqueLabel a b where
  ...
  buildGraph = ... some use of containers libraries that
require context ...
  ...
lookupNode :: Hashable a => UniqueLabel a b -> a -> Node
-- etc


Cheers,
Thomas

P.S.  Please do educate me if I simply missed or misunderstood some
feature of FGL.

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


Re: [Haskell-cafe] Error when installing RSA (for yesod) with GHC 7.2.1

2011-10-24 Thread Thomas DuBuisson
Try to install with: cabal install RSA 'random == 1.0.1.0'

I'm guessing the issue is your "random" library is less than 1.0.1 and
also includes an instance of Word8 (in other words, the GHC release
you use pulled an unofficial version from the repo).

Cheers,
Thomas

On Mon, Oct 24, 2011 at 2:13 PM, Yves Parès  wrote:
> I'm using GHC 7.2.1 and cabal-install 0.8 (Cabal 1.8.0.2), and when
> "cabal install rsa"
>
> I got the error
> $ cabal install rsa
> Resolving dependencies...
> Configuring RSA-1.0.6.2...
> Preprocessing library RSA-1.0.6.2...
> Preprocessing executables for RSA-1.0.6.2...
> Building RSA-1.0.6.2...
> [1 of 1] Compiling Codec.Crypto.RSA ( Codec/Crypto/RSA.hs,
> dist/build/Codec/Crypto/RSA.o )
>
> Codec/Crypto/RSA.hs:580:10:
>     Duplicate instance declarations:
>   instance Random Word8 -- Defined at Codec/Crypto/RSA.hs:580:10-21
>   instance Random Word8 -- Defined in System.Random
> cabal: Error: some packages failed to install:
> RSA-1.0.6.2 failed during the building phase. The exception was:
> ExitFailure 1
>
> Apparently it's an instance being declared twice.
> However RSA hackage page states that it compiles under GHC 7.2:
> http://hackage.haskell.org/package/RSA
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>

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


Re: [Haskell-cafe] ANNOUNCE: GA-1.0, a library for working with genetic algorithms

2011-09-29 Thread Thomas DuBuisson
This is neat - thanks for putting in the time and effort (and
releasing the work to Hackage).  A few questions:

* What GA-nerdy things does this do under the hood (I haven't looked
  at the source)?  It looks like it's a GA framework almost more than
  the actual algorithm itself.  I see crossover and mutation can be
  defined by the user and understand there are limitations to what the
  GA package can do (seeing as it is so polymorphic), but certainly it
  could provide alternate fitness measures (adjusted, normalized,
  standard), over-selection, elitism, automatically defined functions
  (sometimes called encapsulation), and optimization (I think this is
  referred to as "editing" by Koza).

* Have you considered using Binary or Serialize to make the
  checkpointing? (I assume checkpointing is using the Show and Read
  instances right now)

* Have you considered alternate random sources (Mersenne)?  Perhaps
  I'm being silly as most GAs are computationally dominated by the
  fitness measurement.

* Is there a plan for parallel computations?  Beyond what I can do
with scorePop?

* What does it mean if a score returns 'Nothing'?

On a related note, I've recently put some work into using the Typeable
and Dynamic modules to build a GA system in which the primitives could
hold heterogeneous types.  I'll describe it below incase you are 1)
interested in doing it yourself, but actually completeing it (unlike
me) or 2) are already doing it so I won't be tempted to revisit the
work and duplicate effort.  From the look of your package, this would
be just an special instance of your Entity class.

The basic idea was to allow the use of arbitrary Haskell types to be
lifted into a generic genetic algorithm:

{- BEGIN CODE -}
evolveSolution = do
  let funcs = [mkPrim (:), mkPrim lookup, mkPrim delete, mkPrim
insert] ++ map mkPrim [0..100] ++ map mkPrim [(+),(*),(-)]
  allFuncs = funcs ++ primsForContainersPackage -- my package
should have eventually provided such collections
  fitness f = f 503 == 0
  gaConf = mkGA funcs (mkPrim fitness) defaultConfig
  in evolve gaConf
{- END CODE -}

In the system each individual is an operator and a list of arguments,
each contained in their own Dynamic type.  All individuals include 1)
a mapping from type to sub-trees that are of that type and 2) a
mapping of types to functions that will construct the same individual
(that is: Map typ (typ -> Individual)).  The union of the domain of
these to mappings show what, if any, opportunities for crossover exist
between any two individuals.

The global configuration maintains all the primitives needed to
generate new individuals, which means sub-trees can also be generated
to allow mutation.

The main two issues that made me stop (read: I didn't recognize these
as the core issue till I'd already hacked around without thinking
about why what I'm doing wasn't quite right) were:

1) I didn't have a good way to dynamically safely coerce one type,
ty1, into another type, ty2.  For example, when given "t_1 -> t_2 ->
... -> t_n -> r" and needed "b_1 -> b_2 -> ... -> b_m -> r" where m <
n and there was a injective mapping between the b, t type variables I
still had bugs in the actual coercion.

A more concrete example of this point: given "Int -> Float -> Float",
I wanted to coerce it into a function of type "Float -> Int -> Float"
or "Float -> Float" or "Int -> Float".  Usually my solution worked,
but I think a bug lingered (needs testing, which I don't have time
for now).

2) Generation of individuals in "highly heterogenious" configurations
was basically non-terminating without special effort.  I was going to
make a routine to compute the minimum depth given any particular
primitive, then removed any primitive from consideration if the
minimum depth put me over the maximum depth for the individual.

So a bit long winded, but that was the effort in a nutshell.  If
nothing else I hope it was entertaining.  I'm sure it's doable but I
haven't the time of focus to do it properly, and won't for a while.

Cheers,
Thomas


On Thu, Sep 29, 2011 at 12:45 PM, Kenneth Hoste  wrote:
> Hello,
>
> I'm proud to announce the v1.0 release of GA [1], my library for working with 
> genetic algorithms in Haskell.
> Source repo is available on github. [2]
>
> This is a major version bump compared to the previous v0.2 release, because 
> the library is pretty mature now in my view.
>
> Major features:
>
> * flexible user-friendly API for working with genetic algorithms
> * Entity type class to let user define entity definition, scoring, etc.
> * abstraction over monad, resulting in a powerful yet simple interface
> * support for scoring entire population at once
> * support for checkpointing each generation, and restoring from last 
> checkpoint
> * convergence detection, as defined by user
> * also available: random searching, user-defined progress output
> * illustrative toy examples included
>
> I'm happy to take any questions or suggestions that yo

[Haskell-cafe] [ANN] crypto-api-tests

2011-09-27 Thread Thomas DuBuisson
The crypto-api test modules have been split out into their own
package, crypto-api-tests.  Additionally, the tests now use the
test-framework package.  This should make it much easier for
hash/cipher maintainers to integrate into their existing testing
infrastructure.  For example:

$ cabal update ; cabal install cryptocipher crypto-api crypto-api-tests

{- BEGIN CODE -}
import Test.Framework
import Test.AES (makeAESTests)
import Crypto.Cipher.AES (AES128)

main = do
  ts <- makeAESTests (a :: AES128)
  defaultMain ts
{- END CODE -}

$ ghc test.hs ; ./test
...
snip
...
OFBVarTxt128d.txt-125: [OK]
OFBVarTxt128d.txt-126: [OK]
OFBVarTxt128d.txt-127: [OK]
Block Cipher tests (ident):
  ECBEncDecID: [OK, passed 100 tests]
  CBCEncDecID: [OK, passed 100 tests]
  CFBEncDecID: [OK, passed 100 tests]
  OFBEncDecID: [OK, passed 100 tests]
  CTREncDecID: [OK, passed 100 tests]
Block Cipher tests (lazy/string bytestring equality):
  ECBStringLazyEq: [OK, passed 100 tests]
  CBCStrictLazyEq: [OK, passed 100 tests]
  CFBStrictLazyEq: [OK, passed 100 tests]
  OFBStrictLazyEq: [OK, passed 100 tests]
  CTRStrictLazyEq: [OK, passed 100 tests]

 Properties   Test Cases Total
 Passed  10   2272   2282
 Failed  00  0
 Total   10   2272   2282

Patches for more algorithms and/or property tests for classes of
algorithms are certainly welcome.

Cheers,
Thomas

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


[Haskell-cafe] A Crypto-API-Tests package

2011-09-26 Thread Thomas DuBuisson
FYI, since I figure you three are the ones interested in this right now:

I'll be releasing crypto-api-tests [1] to hackage someday (this
weekend?).  If you want to give it a spin or add KATS before the first
release then feel free.  OTOH, it's not like I'd stop accepting
patches after release 0.1.

Cheers,
Thomas

[1] https://github.com/TomMD/crypto-api-tests

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


Re: [Haskell-cafe] [ANNOUNCE] skein-0.1: Skein, a family of cryptographic hash functions. Includes Skein-MAC as well.

2011-09-21 Thread Thomas DuBuisson
>  The skein
> package comes with the "golden" KATs sent by the Skein team to NIST

Great! Care to add that to the crypto-api test code?

Cheers,
Thomas

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


Re: [Haskell-cafe] efficient chop

2011-09-13 Thread Thomas DuBuisson
This was a recent question on StackOverflow:

http://stackoverflow.com/questions/6270324/in-haskell-how-do-you-trim-whitespace-from-the-beginning-and-end-of-a-string/6270382#6270382

Where I started:

If you have serious text processing needs then use the text package
from hackage.

And concluded:

A quick Criterion benchmark tells me that (for a particularly long
string of words with spaces and ~200 pre and post spaces) my trim
takes 1.6 ms, the trim using reverse takes 3.5ms, and Data.Text.strip
takes 0.0016 ms.

Cheers,
Thomas

On Tue, Sep 13, 2011 at 8:03 PM, Kazu Yamamoto  wrote:
> Hello Cafe,
>
> I would like to have an efficient implementation of the chop function.
> As you guess, the chop function drops spaces in the tail of a list.
>
>   chop " foo  bar baz   "
>   ->   " foo  bar baz"
>
> A naive implementation is as follows:
>
>    chopReverse :: String -> String
>    chopReverse = reverse . dropWhile isSpace . reverse
>
> But this is not elegant. foldr version is as follows:
>
>    chopFoldr :: String -> String
>    chopFoldr = foldr f []
>      where
>        f c []
>          | isSpace c = []
>          | otherwise = c:[]
>        f c cs = c:cs
>
> But this code is slower than chopReverse in some cases.
>
> Are there any more efficient implementations of chop? Any suggestions?
>
> --Kazu
>
> ___
> 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] hoogle data no connection to host http://code.galois.com/darcs/haskell-platform ...

2011-08-26 Thread Thomas DuBuisson
The Galois link works fine for me now - it also worked for me earlier
today when I ran hoogle data for my own system.  I suggest you try
again, possibly with a better internet connection?

Cheers,
Thomas

On Fri, Aug 26, 2011 at 12:39 AM, informationen  wrote:
> Hi,
>
> i installed Hoogle succesfullly with
> cabal install hoogle
>
> then i try to run
> hoogle data
>
> but the connection to
> http://code.galois.com/darcs/haskell-platform/haskell-platform.cabal
> times out.
> How can i download the data needed for the hoogle command line
> tool?
>
> Greetings
> Chris
>
> ___
> 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] - Try to install ssh package by cabal.

2011-08-23 Thread Thomas DuBuisson
FYI: It's usually good to CC the package maintainer when a build fails
for non-trivial reasons.

At first glance it seems the SSH package was released when version 0.3
of the ASN package was current.  The ASN package is now on version 0.5
- so you can either add that constraint into the SSH package and try
again or fix the SSH package to work with ASN 0.5 and send in a patch
if that proves to be the case.

Cheers,
Thomas

P.S. It does appear that the ASN changes break this, but when I add
the version constraint I see that SSH implicitly uses
FlexibleInstances, which must be made explicit in GHC 7 via a LANGUAGE
pragma or equivalent.

On Tue, Aug 23, 2011 at 11:58 AM, Loïc Maury  wrote:
> Hello,
>
> I try to install the ssh package with cabal, but
> unfortunately that doesn't work, I have this error :
>
> src/SSH/Crypto.hs:70:16:
> Couldn't match expected type `Data.ASN1.Types.ASN1t' with actual type
> `ASN1ConstructionType'
>
> I'am on Debian with ghc-7.0.1
>
> I don't know how I can resolve this issue ?
>
> Thank you for help
>
> Loïc
>
> ___
> 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] Question about data

2011-08-19 Thread Thomas DuBuisson
This is not a valid data declaration.  You can't have a "Float" field
without any constructor name and have it still of type
"MathExpression".  I suggest you do something like:

data MathExpr = MathFloat Float


So you may declare pi:

let mathPi = MathFloat pi  -- note "pi" is defined in the prelude alread


Cheers,
Thomas

On Fri, Aug 19, 2011 at 1:40 PM, Paul Reiners  wrote:
> I've created a simple type declaration:
>
> data MathExpression = Float
>     | Add MathExpression MathExpression
>     | Subtract MathExpression MathExpression
>     | Multiply MathExpression MathExpression
>     | Divide MathExpression MathExpression
>       deriving (Show)
>
> Now how do I create an instance of MathExpression which is just a Float?
>
> This doesn't work:
>
> *Main> let pi = 3.14 :: MathExpression
>
> :1:10:
>     No instance for (Fractional MathExpression)
>   arising from the literal `3.14'
>     Possible fix:
>   add an instance declaration for (Fractional MathExpression)
>     In the expression: 3.14 :: MathExpression
>     In an equation for `pi': pi = 3.14 :: MathExpression
>
>
>
> ___
> 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] Compilation error in Chapter 5 of "Real World Haskell"

2011-08-18 Thread Thomas DuBuisson
This is a linking issue.  It seems GHC 7 automatically feeds the
linker SimpleJSON.o so when you explicitly provide it too then you get
those conflicts.  All you need to do is call:

> ghc -o simple Main.hs

Unless you're using GHC 6, then the original command is correct:

> ghc -o simple Main.hs SimpleJSON.o

Or even better, use the --make flag as that works with either version:

> ghc --make -o simple Main.hs

Cheers,
Thomas

On Wed, Aug 17, 2011 at 10:37 AM, Paul Reiners  wrote:
> I'm trying to do the following from Chapter 5 of "Real World Haskell":
>
> Our choice of naming for the source file and function is deliberate. To
> create an executable, ghc expects a module named Main that contains a
> function named main. The main function is the one that will be called when
> we run the program once we've built it. 6 comments
>
> ghc -o simple Main.hs SimpleJSON.o
>
> ---from
> http://book.realworldhaskell.org/read/writing-a-library-working-with-json-data.html
>
> When I do that, I get this error:
>
> C:\ch05>ghc -o simple Main.hs SimpleJSON.o
> [2 of 2] Compiling Main ( Main.hs, Main.o )
> Linking simple.exe ...
> SimpleJSON.o:fake:(.data+0x0): multiple definition of
> `SimpleJSON_getArray_closure'
> .\SimpleJSON.o:fake:(.data+0x0): first defined here
> SimpleJSON.o:fake:(.text+0x54): multiple definition of
> `SimpleJSON_getArray_info'
> .\SimpleJSON.o:fake:(.text+0x54): first defined here
> SimpleJSON.o:fake:(.data+0x4): multiple definition of
> `SimpleJSON_getObject_closure'
> .\SimpleJSON.o:fake:(.data+0x4): first defined here
>
> What's going wrong here?
>
>
> ___
> 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 is Random in System?

2011-08-16 Thread Thomas DuBuisson
I think of it as natural for exactly the reason you stated (the data
comes from the OS).  It seems even more natural to me in the entropy
package module 'System.Entropy' as I am accustom to the phrase system
entropy.  Equally, I would fine a 'Network.Entropy' module acceptable
under the assumption it connects to one of the public random number
servers for it's data.

Perhaps a top level "Random." should be used, but that too can be
questioned.  For example, when I import the module "Random" or perhaps
"Random.Generators" would I get fast prngs?  Cryptographic prngs?
Both?  Something else (both slow and weak, like what we have now ;-)
)?

Cheers,
Thomas

On Tue, Aug 16, 2011 at 1:04 PM, Evan Laforge  wrote:
> I've noticed there's a convention to put modules having to deal with
> randomness into System.Random.  I thought System was for OS
> interaction?  Granted getting a random seed usually means going to the
> OS, but isn't the rest of it, like generating random sequences,
> distributions, selecting based on probability, shuffling, etc. all
> non-OS related algorithms?
>
> I'm not sure where I would expect Random to go, perhaps Math or maybe
> the toplevel, but under System seems, well, random...
>
> I notice random-fu puts it under Data, which is also not where I'd
> look, except that you always look in Data because everything goes into
> Data... but algorithms dealing with random numbers aren't really data
> structures either, are they?
>
> ___
> 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] Simple Parsec example

2011-08-07 Thread Thomas DuBuisson
I suggest you install hoogle or use the web interface as it can easily
answer such questions for you:

http://www.haskell.org/hoogle/?hoogle=commaSep
http://www.haskell.org/hoogle/?hoogle=integer+%2bparsec

Cheers,
Thomas

On Sun, Aug 7, 2011 at 11:44 AM, michael rice  wrote:

> What other imports must I add to get this to run. I can't seem to get it
> right.
>
> Michael
>
> =
>
> import Text.ParserCombinators.Parsec.Prim
>
> main = case (parse numbers "" "11, 2, 43") of
>  Left err  -> print err
>  Right xs  -> print (sum xs)
>
> numbers = commaSep integer
>
> ==
>
> [michael@sabal ~]$ ghc --make parsetest.hs
> [1 of 1] Compiling Main ( parsetest.hs, parsetest.o )
>
> parsetest.hs:7:11: Not in scope: `commaSep'
>
> parsetest.hs:7:20: Not in scope: `integer'
> [michael@sabal ~]$
>
>
> ___
> 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] Fwd: The Typeable class is changing

2011-07-11 Thread Thomas DuBuisson
Alberto G. Corona  wrote:
> What to do when the data has been defined in other package and provides no
> Typeable instance?

You'd have to use standalone deriving, which I hope gets into Haskell 201X.


module A where

data A = A

{-# LANGUAGE StandaloneDeriving, DeriveDataTypeable #-}
module B where

import A
import Data.Typeable

deriving instance Typeable A


Cheers,
Thomas



>
> 2011/7/11 Yitzchak Gale 
>>
>> Simon Marlow has announced[1] on the Haskell Libraries
>> list that the Typeable class is changing.
>>
>> The standard way to create a Typeable instance is
>> just to derive it. If you do that, you will not be affected
>> by this change.
>>
>> But it seems that many packages create Typeable
>> instances by explicitly using mkTyCon. If your package
>> does this, it will eventually break, after a deprecation
>> period.
>>
>> Please respond to this thread if you own a package
>> that will be affected by this change.
>>
>> Can someone who has quick access to the entire contents
>> of Hackage please do a grep and find out exactly which
>> packages on Hackage will be affected? Thanks.
>>
>> -Yitz
>>
>> [1] http://www.haskell.org/pipermail/libraries/2011-July/016546.html
>>
>> ___
>> 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] The Typeable class is changing

2011-07-11 Thread Thomas DuBuisson
On Mon, Jul 11, 2011 at 1:22 PM, jutaro  wrote:
> I hope that typeRepKey is no longer in the IO monad (for the simple reason to
> teach me that the key can change between session).

If it's implementation dependent then I see no reason for it to be in
IO (this was mentioned on another ML).  On the other hand, something
that changes run-to-run strikes me as good to keep in IO, otherwise
I'd be too tempted to serialize & save it for some purpose and get
confused while a later read was corrupt.

Cheers,
Thomas

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


Re: [Haskell-cafe] (no subject)

2011-07-06 Thread Thomas DuBuisson
Ian,
This requires dynamic typing using Data.Dynamic (for application) and
Data.Typeable (to do the typing).   Namely, you are asking for the
"dynApply" function:

 START CODE
import Data.Dynamic
import Data.Typeable
import Control.Monad

maybeApp :: (Typeable a, Typeable b, Typeable c) => a -> b -> Maybe c
maybeApp a = join . fmap fromDynamic . dynApply (toDyn a) . toDyn
 END CODE

In the above we obtain representations of your types in the form of
"Dynamic" data types using toDyn.  Then, using dynApply, we get a
value of type "Maybe Dynamic", which we convert back into a "c" type
with fromDynamic.  The "join" is just there to collapse the type from
a "Maybe (Maybe c)" into the desired type of "Maybe c".

Cheers,
Thomas

P.S.
If I totally misunderstood, and you want static typing then you just
need to realize you _don't_ want types "a" and "b" (fully polymorphic)
but rather types (b -> c) and b:

apply :: (b -> c) -> b -> c
apply a b = a b

But this seems rather silly, so I hope you were looking for my first answer.


On Wed, Jul 6, 2011 at 2:12 AM, Ian Childs  wrote:
> Suppose I have two terms s and t of type "a" and "b" respectively, and I
> want to write a function that returns s applied to t if "a" is an arrow type
> of form "b -> c", and nothing otherwise. How do i convince the compiler to
> accept the functional application only in the correct instance?
>
> Thanks,
> Ian
>
> ___
> 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] Splitting Hackage Packages and re-exporting entire modules (with same module name)

2011-07-04 Thread Thomas DuBuisson
All,

I have decided it would be beneficial to split System.Crypto.Random
and the rest of crypto-api into different packages.  Is there I way I
can create a package, "entropy", with System.Crypto.Random but
continue to expose that module from crypto-api (allowing people who
use that module some time to move)?  If so, how?  If not, does anyone
else see value in this and how it can be added to the infrastructure?

Cheers,
Thomas

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


[Haskell-cafe] ANNOUNCING: Hac PDX II - A Portland Haskell Hackathon

2011-06-30 Thread Thomas DuBuisson
WHAT: A Haskell Hackathon

WHEN:
July 22-24 (Friday, Saturday, Sunday)
10:00 AM to 5:30 PM

WHERE:
Forth Avenue Building (FAB, 1900 SW 4th Ave) Room 10
Portland, Oregon 97201

WHERE, take 2:
FAB10 is a small auditorium just inside the west most Harrison Street entrance.

URL: http://haskell.org/haskellwiki/HacPDX-II

WHAT, take 2:
HacPDX-II is a Haskell Hackathon where beginners and experts alike can
come to work on the Haskell projects of their choice - individually or
in groups.  If you don't have a project then never fear, come and pick
one up or join a group (see the wiki for a list of projects).

EQUIPMENT:
You should bring a laptop with wireless (802.11). Ethernet is unavailable.

Registration:
Please RSVP by e-mailing thomas.dubuisson+hacpdx at gmail.com, as well
as add your name to the attendees Wiki page (see above URL).


Hope to see you there,
Thomas

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


Re: [Haskell-cafe] If Python now has a good email library; how challenging is it to call Python from Haskell?

2010-10-27 Thread Thomas DuBuisson
How does python having an e-mail library change the situation with
calling Python from Haskell?

On Wed, Oct 27, 2010 at 10:43 AM,   wrote:
> :)
>
>
> ___
> 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] Proving stuff about IORefs

2010-10-16 Thread Thomas DuBuisson
I must be missing the point of the proof.  The value of 'f r' is _|_.
Practically speaking, it will eventually stack overflow.  Why is
proving anything about this interesting?  Why do you think the store
will ever happen on the original r?

Cheers,
Thomas

On Sat, Oct 16, 2010 at 6:21 PM, Ben Franksen  wrote:
> I have a formal proof where I am stuck at a certain point.
>
> Suppose we have a function
>
>  f :: IORef a -> IO b
>
> I want to prove that
>
>  f r == do
>    s1 <- readIORef r
>    r' <- newIORef s1
>    x <- f r'
>    s3 <- readIORef r'
>    writeIORef r s3
>    return x
>
> What happens here is that the temporary IORef r' takes the place of the
> argument r, and after we apply f to it we take its content and store it in
> the original r. This should be the same as using r as argument to f in the
> first place.
>
> How can I prove this formally?
>
> Cheers
> Ben
>
> ___
> 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] In what language...?

2010-10-15 Thread Thomas DuBuisson
I think you would enjoy reading (and working) through TAPL[1] and/or
Software Foundations[2] if this interests you.

Cheers,
Thomas

[1] 
http://www.amazon.com/Types-Programming-Languages-Benjamin-Pierce/dp/0262162091
[2] http://www.cis.upenn.edu/~bcpierce/sf/

On Fri, Oct 15, 2010 at 1:36 PM, Andrew Coppin
 wrote:
>  Yesterday I read a rather interesting paper:
>
> http://www.cl.cam.ac.uk/~mb566/papers/tacc-hs09.pdf
>
> It's fascinating stuff, and I *think* I understand the gist of what it's
> saying. However, the paper is utterly festooned with formulas that look so
> absurdly over-the-top that they might almost be a spoof of a mathematical
> formula rather than the real thing. A tiny fraction of the notation is
> explained in the , but the rest is simply "taken to be obvious". The
> paper also uses several ordinary English words in a way that suggests that
> they are supposed to have a more specific technical meaning - but I have no
> idea what.
>
> Does anybody have any idea which particular dialect of pure math this paper
> is speaking? (And where I can go read about 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] Layered maps

2010-10-08 Thread Thomas DuBuisson
Alex,

The containers library can do this already - there are no constraints
on the elements of a Map.  For example:

> type TripleNestedMap a = Map Int (Map Char (Map String a))

But this is rather silly as you can just do:

> type MapOfTriples a = Map (Int ,Char, String) a

for most uses.

Cheers,
Thomas

On Fri, Oct 8, 2010 at 2:23 PM, Alex Rozenshteyn  wrote:
> Does there exist a library which allows me to have maps whose elements are
> maps whose elements ... with a convenient syntax.
>
> Alternatively, does there exist a library like Data.Tree where forests are
> sets rather than lists?
>
> --
>           Alex R
>
> ___
> 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] ByteString missing rewrite RULES (zipWith' f a = pack . zipWith f a)

2010-10-05 Thread Thomas DuBuisson
>  I don't have a horse in this race; but I am curious as to why
>  you wouldn't ask for `chunkOverhead = 16' as that seems to be
>  your intent as well as what the expression works out to on any
>  machine in common use.

Sorry, after I sent my long explanation I see what you are really
asking.  I was going by the assumption that someone really did measure
and find out that keeping the length and pointer information in the
same page as the bytestring data is a significant win.  While saying
"chunkOverhead = 16" would still work it's simply false for imaginary
128bit Haskell machines (Cell SPEs?), and I don't like betting against
commercial changes in computing.

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


Re: [Haskell-cafe] ByteString missing rewrite RULES (zipWith' f a = pack . zipWith f a)

2010-10-05 Thread Thomas DuBuisson
>  I don't have a horse in this race; but I am curious as to why
>  you wouldn't ask for `chunkOverhead = 16' as that seems to be
>  your intent as well as what the expression works out to on any
>  machine in common use.

To avoid copying data when perform FFI calls to common cipher routines
(such operations usually work on 128 bit blocks).

If you have a Haskell program performing full disk encryption (FDE)
then its reasonable to expect large amounts of data to need
encrypted/decrypted.  Reading in Lazy ByteStrings you get 32k -
chunkOverhead sized strict bytestrings, which is a 64 bit multiple on
32 bit machines.  IOW, for an operation like "cbc key iv lazyBS" you
will 1) encrypt 32K-16B 2) copy the remainder (8 bytes) and the next
chunk (32K - 8B) into a new strict bytestring 3) encrypt the full 32K
chunk 4) repeat.

There are other ways to do it, but the fastest ways involve making
your delicate and extremely security sensitive cipher algorithm work
on partial blocks or build the notion of linked lists of buffers (lazy
byte strings) into the implementation (which is often in C).

Unfortunately, this problem only gets worse as you expand your scope.
Hash algorithms have a much wider array of block sizes (512 to 1024
bits are very common) and we don't want to waste 1024 - 64 bits per
32KB chunk, so I didn't request that.  In situations where people know
they'll be hashing large files and explicitly use Lazy ByteStrings
they could use hGetN to set the chunk size to something agreeable.

A less programmer-intensive solution would be to have chunks at a full
32K.  I'm not sure how much of a performance problem this would
introduce (to all users of bytestrings) due to caching (other
issues?).  Did anyone measured it when the initial implementation
decided to do it this way?

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


[Haskell-cafe] ByteString missing rewrite RULES (zipWith' f a = pack . zipWith f a)

2010-10-05 Thread Thomas DuBuisson
All,

(I notice ByteString still isn't under l...@h.o ownership, which is good
because this way I can avoid the bureaucracy and e-mail the
maintainers directly)

The following is a Data.ByteString comment for the (non-exported)
function zipWith'
--
-- | (...) Rewrite rules
-- are used to automatically covert zipWith into zipWith' when a pack is
-- performed on the result of zipWith.
--

This implies there should be a rule:
{-# RULES
"ByteString specialise zipWith'" forall (f :: Word8 -> Word8 -> Word8) p q .
zipWith' f p q = pack (zipWith f p q)
  #-}

But no such rule exists in the ByteString source (the inverse rule
using 'unpack' does exist).

1) Is this an omission?  Can we fix it?  It's a rather important rule
for crypto-api.
2) Can we export zipWith' so people can be explicit?  If not, can we
get the comment about the rule placed somewhere so it will make its
way to the generated Haddock documentation for general users?

3) Very different issue:
Could .Lazy export hGetN or have defaultChunkSize configurable by a
CPP/compile time macro?

If not, perhaps we could make "chunkOverhead = max 16 (2 * sizeOf
(undefined ::Int))" so it will be the same on 64 and 32 bit systems (a
128 bit boundary, nice and fast for most modern cipher algorithms,
sadly asking for it to match hash block sizes is a bit much).

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


Re: [Haskell-cafe] can't find in hayoo

2010-09-29 Thread Thomas DuBuisson
In addition to hoogle I suggest you check out hackage too.  I think
you'll be particularly interested in "base64-bytestring":

http://hackage.haskell.org/package/base64-bytestring

Cheers,
Thomas

On Wed, Sep 29, 2010 at 9:41 AM, Roderick Ford  wrote:
> The idea was to go from
> Prelude> :t Data.ByteString.readFile
> Data.ByteString.readFile
>   :: FilePath -> IO Data.ByteString.Internal.ByteString
>
> to here
> Prelude> :t Codec.Binary.Base64.encode
> Codec.Binary.Base64.encode :: [GHC.Word.Word8] -> String
>
> unless there is another/easier way
>
> Roderick
>
>> Date: Wed, 29 Sep 2010 09:23:37 -0700
>> Subject: Re: [Haskell-cafe] can't find in hayoo
>> From: thomas.dubuis...@gmail.com
>> To: develo...@live.com
>> CC: haskell-cafe@haskell.org
>>
>> By and large hayoo is the alta-vista of Haskell search - it has a huge
>> database but isn't well organized or good at prioritizing. Use Hoogle
>> when doing type-based searches for functions in the typical GHC load.
>>
>> http://haskell.org/hoogle/?hoogle=%3A%3A+ByteString+-%3E+[Word8]
>>
>> Also, what's with the non-standard module specification
>> "GHC.Word.Word8"? You should use Data.Word.
>>
>> Cheers,
>> Thomas
>>
>> On Wed, Sep 29, 2010 at 9:03 AM, Roderick Ford  wrote:
>> > ByteString -> [GHC.Word.Word8]
>
> ___
> 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] can't find in hayoo

2010-09-29 Thread Thomas DuBuisson
By and large hayoo is the alta-vista of Haskell search - it has a huge
database but isn't well organized or good at prioritizing.  Use Hoogle
when doing type-based searches for functions in the typical GHC load.

http://haskell.org/hoogle/?hoogle=%3A%3A+ByteString+-%3E+[Word8]

Also, what's with the non-standard module specification
"GHC.Word.Word8"?  You should use Data.Word.

Cheers,
Thomas

On Wed, Sep 29, 2010 at 9:03 AM, Roderick Ford  wrote:
> ByteString -> [GHC.Word.Word8]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [fp-embedded] Which Haskell DSL for writing C? (Was ANN: Copilot 0.22 -- A stream DSL for writing embedded C.)

2010-09-21 Thread Thomas DuBuisson
> The best reference for Copilot's constraints is this paper: 
> .

Non-Haskell programmers should note that paper has a few typos (Lee,
please correct me if I'm mistaken).  Section 4.1 is where I'm at so
far and I see missing backticks (shoulld be `implies`) and missing
parenthesis in "drop 2 (var temps)".

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


[Haskell-cafe] [ANN] Crypto-API 0.1.0.0

2010-09-20 Thread Thomas DuBuisson
Crypto-API is a project aimed at unifying algorithm developers and
users by presenting a uniform typeclass interface to low level
algorithms and providing generalized helper functions for the
(slightly) higher-level interactions needed by crypto-users.  The main
features are typeclasses (hash, cipher, signing and RNG), block cipher
modes, platform independent entropy/seed acquisition, padding, testing
and benchmarking.

This release represents a fleshing out of the testing infrastructure,
addition of padding mechanisms, and a reduction in build dependencies.
 In particular, I want to encourage package maintainers of TwoFish,
AES, and SHA* algorithms to use the included test infrastructure -
examples can be found on the homepage.

== Project Management ==
Homepage: http://trac.haskell.org/crypto-api/wiki
Bug trac: http://trac.haskell.org/crypto-api/report/1
Repo: http://code.haskell.org/crypto-api/

== API Removals ==
* Test.ParseNistKATs doesn't use Parsec and has a barebones interface.
* Crypto.Random does not export "AsRG" or "Splittable" (see change
log, 'random' build dep removed)

== API Additions ==
* class Signing p v | p -> v, v -> p where ...
* instance Monad (Either GenError) where ...
* cereal >= 0.2 && < 0.4 (was == 0.2.*)
* Testing
 ** Tests are split from Test.Crypto
 ** SHA, HMAC tests are new and from NIST CAVP KATs
 ** AES CFB128 mode KATs
 ** TwoFish NIST KATs
 ** Cipher property tests included (enc . dec ~ id, and many mode
specific tests)
* Crypto.Padding is included with PKCS5 and ESP padding methods.
* "blockSizeBytes" helper function is now included

== Build Dependencies ==
While I've never had objections to dependencies (this is what cabal is
for and removing unused code is what GHC+linkers are for), I feel this
is a good minimum and hope others agree.  Some potential users made
noise about having both Binary and Cereal and just the number of deps
in general.

* deps removed: binary, parsec, random (and indirectly: time, old-locale)
* deps remaining: base, tagged, bytestring, cereal, filepath, directory
* indirect deps remaining: data-default, containers, arrays

To reiterate, the only deps above a normal GHC baseline are tagged,
cereal, and data-default.

CHANGE LOG (since 0.0.0.2)
* Add 'Signing' class.
* Tests showing the strict and lazy Crypto.Modes functions are eq
* Basic BlockCipher property tests (enc . dec ~ id)
* Enable tests for CFB128
* Added ESP and PCKS5 padding
* add a 'blockSizeBytes' helper
* TwoFish KATs
* Bump 'cereal' version bound to include 0.3
* instance Monad (Either GenError)  -- that was an obvious oversight
* Remove the 'binary' dep. (cereal makes more sense and can be
leveraged in Binary.{Get,Put} routines).
* Removed the 'parsec' dep, which was only needed for Test.* but not
even that now.
* Updated the CPP tests for Windows in System.Random.Crypto (still
need a tester)
* Fixed up the testing infrastructure.  Algorithms now use separate
modules (Test.SHA, Test.HMAC, Test.AES).  more NIST KATs included:
~1000 SHA tests, hundreds of SHA HMAC tests.
* Fixed ugly bug for HMACs using keys > blockSize (eep! Obvious
interop problem, but there was no-less security in the hmac result)
* Removes the 'random' dep and by extension removes indirect deps on
time and old-locale.  Random was only used to provide trivial lifting
of a newtype wrapped CryptoRandomGen instances into the RandomGen
class, which was of questionable sense in the first place.

== TODO ==
* Improve benchmarking infrastructure
** Improved reporting
** Benchmark modes and other higher-level functions, but in a generic way
** Benchmark asymmetric algorithms
* Optimize block cipher modes
* Statistical RNG tests
* Portability testing (Mac, Windows testing needed)

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


Re: [Haskell-cafe] ANN: happstack-auth-0.2

2010-09-18 Thread Thomas DuBuisson
Why are you using Crypto?  I'm hoping to make "Crypto" as we know it
obsolete.  To that end, I've been working on a unified interface
(crypto-api) and after the algorithms packages catch up I planned to
make a meta package "crypto-algs".

Cheers,
Thomas

On Sat, Sep 18, 2010 at 11:19 AM, Nils Schweinsberg  wrote:
> Am 17.09.2010 22:06, schrieb Nils Schweinsberg:
>>
>> [1] http://hackage.haskell.org/package/happstack-auth
>
> Hackage fails to build this package:
>
> http://hackage.haskell.org/packages/archive/happstack-auth/0.2/logs/failure/ghc-6.12
>
> However, "Crypto == 4.*" should be on hackage:
>
> http://hackage.haskell.org/package/Crypto-4.2.1
>
> Is there anything I can do with my package to get this to build?
> ___
> 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] Curious why "cabal upgrade parsec" not installing latest version

2010-09-15 Thread Thomas DuBuisson
Parsec 3 is unloved by much of the community because it's evidently
slower than parsec 2.  For this reason the community remains divided
over the two versions and cabal has special "preferred versions" of
particular packages.  To force installation of parsec 3, over the
"preferred" parsec 2, you simply execute "cabal install 'parsec >= 3'"

Cheers,
Thomas

On Wed, Sep 15, 2010 at 7:47 PM, Peter Schmitz  wrote:
> Not that I'm having any problem with parsec 2.1.0.1, but I guess I
> would like to install the latest (3.1.0), unless there is a reason
> not to.
>
> I can't seem to get Cabal to do so; thanks in advance for any help.
>
> I don't understand part of the output from "cabal install --dry-run
> --reinstall -v parsec" at the end below, which includes:
> "selecting parsec-2.1.0.1 (hackage) and discarding parsec-2.0,
> 2.1.0.0, 3.0.0, 3.0.1 and 3.1.0".
>
> (http://hackage.haskell.org/package/parsec seems to point to 3.1.0.)
>
>
> Under Windows XP:
>
>> H:\proc\dev\cmd>cabal update
>> Downloading the latest package list from hackage.haskell.org
>>
>> H:\proc\dev\cmd>cabal info parsec
>> * parsec           (library)
>>     Synopsis:      Monadic parser combinators
>>     Latest version available: 3.1.0
>>     Latest version installed: 2.1.0.1
>>     Homepage:      http://www.cs.uu.nl/~daan/parsec.html
>>     Bug reports:   [ Not specified ]
>>     Description:   Parsec is designed from scratch as an industrial-strength
>>                    parser library. It is simple, safe, well documented (on 
>> the
>>                    package homepage), has extensive libraries and good error
>>                    messages, and is also fast. It is defined as a monad
>>                    transformer that can be stacked on arbitrary monads, and 
>> it
>>                    is also parametric in the input stream type.
>>     Category:      Parsing
>>     License:       BSD3
>>     Author:        Daan Leijen , Paolo Martini 
>> 
>>     Maintainer:    Derek Elkins 
>>     Source repo:   [ Not specified ]
>>     Flags:         base4
>>     Dependencies:  mtl -any, bytestring -any, base >=4 && <5, syb -any,
>>                    base >=3.0.3 && <4
>>     Documentation: [ Not installed ]
>>     Cached:        No
>>     Modules:
>>         Text.ParserCombinators.Parsec
>>         Text.ParserCombinators.Parsec.Char
>>         Text.ParserCombinators.Parsec.Combinator
>>         Text.ParserCombinators.Parsec.Error
>>         Text.ParserCombinators.Parsec.Expr
>>         Text.ParserCombinators.Parsec.Language
>>         Text.ParserCombinators.Parsec.Perm
>>         Text.ParserCombinators.Parsec.Pos
>>         Text.ParserCombinators.Parsec.Prim
>>         Text.ParserCombinators.Parsec.Token
>>
>>
>> H:\proc\dev\cmd>cabal upgrade parsec
>> Resolving dependencies...
>> No packages to be installed. All the requested packages are already 
>> installed.
>> If you want to reinstall anyway then use the --reinstall flag.
>>
>>
>> H:\proc\dev\cmd>cabal install  --dry-run  --reinstall  parsec
>> Resolving dependencies...
>> In order, the following would be installed (use -v for more details):
>> parsec-2.1.0.1
>>
>>
>> H:\proc\dev\cmd>cabal install  --dry-run  --reinstall -v  parsec
>> H:\proc\tools\Haskell Platform\2010.1.0.0\bin\ghc.exe --numeric-version
>> looking for package tool: ghc-pkg near compiler in
>> H:\proc\tools\Haskell Platform\2010.1.0.0\bin
>> found package tool in
>> H:\proc\tools\Haskell Platform\2010.1.0.0\bin\ghc-pkg.exe
>> H:\proc\tools\Haskell Platform\2010.1.0.0\bin\ghc-pkg.exe --version
>> H:\proc\tools\Haskell Platform\2010.1.0.0\bin\ghc.exe --supported-languages
>> Reading installed packages...
>> H:\proc\tools\Haskell Platform\2010.1.0.0\bin\ghc-pkg.exe dump --global
>> H:\proc\tools\Haskell Platform\2010.1.0.0\bin\ghc-pkg.exe dump --user
>> Reading available packages...
>> Resolving dependencies...
>> selecting parsec-2.1.0.1 (hackage) and discarding parsec-2.0,
>> 2.1.0.0, 3.0.0, 3.0.1 and 3.1.0
>> selecting base-3.0.3.2 (installed) and 4.2.0.0 (installed) and discarding
>> syb-0.1.0.0, 0.1.0.1, 0.1.0.2, 0.1.0.3, 0.2 and 0.2.1
>> selecting ffi-1.0 (installed)
>> selecting ghc-prim-0.2.0.0 (installed)
>> selecting integer-gmp-0.2.0.0 (installed)
>> selecting rts-1.0 (installed)
>> selecting syb-0.1.0.2 (installed)
>> In order, the following would be installed:
>> parsec-2.1.0.1 (reinstall) changes: base-4.2.0.0 -> 3.0.3.2
>>
>> H:\proc\dev\cmd>
>
> --
> ___
> 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] [PREANNOUNCE] Crypto-API Major Version Bump (0.1.0.0)

2010-09-15 Thread Thomas DuBuisson
On Wed, Sep 15, 2010 at 6:38 PM, Felipe Lessa  wrote:
> On Wed, Sep 15, 2010 at 9:54 PM, Thomas DuBuisson
>  wrote:
>> * cereal >= 0.2 && < 0.3 (was == 0.2.*)
>
> Do you mean, >= 0.2 && < 0.4?

Yes, that was what I ment, thanks!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] [PREANNOUNCE] Crypto-API Major Version Bump (0.1.0.0)

2010-09-15 Thread Thomas DuBuisson
All,
Ironing out crypto-api, I have commited the below changes mostly
intended to streamline crypto-api and focus it on the main purpose of
connecting algorithm developers with slightly higher-level (and
generic) function needed by crypto-users.  Feel free to object,
comment, or recommend additional alterations before 0.1 is released.
Padding, NIST KATs for TwoFish, and a generalized/testable CFB mode
might appear before release, but no promises.

PROJECT MANAGEMENT:
Homepage: http://trac.haskell.org/crypto-api/wiki
Bug trac: http://trac.haskell.org/crypto-api/report/1
Repo: http://code.haskell.org/crypto-api/

API CHANGES
* instance Monad (Either GenError) where ...
* cereal >= 0.2 && < 0.3 (was == 0.2.*)
* Test.{HMAC,SHA,AES} now exist / are split from Test.Crypto
 ** SHA and HMAC tests are new and from NIST CAVP KAT collection - no
more rolling your own testing!
* Test.ParseNistKATs doesn't use Parsec and has a barebones interface.
* Crypto.Random does not export "AsRG" or "Splittable" (see change
log, 'random' build dep removed)

DEPENDENCIES
While I've never had objections to dependencies (this is what cabal is
for and removing unused code is what GHC+linkers are for), I feel this
is a good minimum and hope others agree.  Some potential users made
noise about having both Binary and Cereal and just the number of deps
in general.

* deps removed: binary, parsec, random (and indirectly: time, old-locale)
* deps remaining: base, tagged, bytestring, cereal, filepath, directory
* indirect deps remaining: data-default, containers, arrays

CHANGE LOG (since 0.0.0.2)
* Bump 'cereal' version bound to include 0.3
* instance Monad (Either GenError)  -- that was an obvious oversight
* Remove the 'binary' dep. (cereal makes more sense and can be
leveraged in Binary.{Get,Put} routines).
* Removed the 'parsec' dep, which was only needed for Test.* but not
even that now.
* Updated the CPP tests for Windows in System.Random.Crypto (still
need a tester)
* Fixed up the testing infrastructure.  Algorithms now use separate
modules (Test.SHA, Test.HMAC, Test.AES).  more NIST KATs included:
~1000 SHA tests, hundreds of SHA HMAC tests.
* Fixed ugly bug for HMACs using keys > blockSize (eep! Obvious
interop problem, but there was no-less security in the hmac result)
* Removes the 'random' dep and by extension removes indirect deps on
time and old-locale.  Random was only used to provide trivial lifting
of a newtype wrapped CryptoRandomGen instances into the RandomGen
class, which was of questionable sense in the first place.

TESTING
I've been using the HEAD crypto-api, specifically Test.{HMAC,SHA,AES},
Crypto.{Classes,HMAC} and Benchmark.{BlockCipher,Hash}, with instances
for SimpleAES, cryptohash, pureMD5, and SHA packages with good
success.  My HEAD DRBG (NIST SP 800-90) code uses Crypto.Random and
Crypto.Classes libraries to good effect, thus far things seem to flow
well.

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


Re: [Haskell-cafe] A new cabal odissey: cabal-1.8 breaking its own neck by updating its dependencies

2010-09-11 Thread Thomas DuBuisson
> - when recompiling a package with ABI changes, does cabal always
> update dependent packages?

If Foo depends on Bar and there is a new version of Foo that specifies
a newer version of Bar then yes, the newer library being depended on
will be build too (out of necessity).

OTOH, if you are building a new version of a package on which others
depend it won't build all the others.  Ex: build a new "containers"
package doesn't cause any of the ~1400 packages depending on it to be
rebuilt.

> It seems "not always" - it didn't update
> itself, nor refuse the breaking upgrade,

I don't really know what "it" is.  Something to do with recompiling
Cabal and cabal-install I take it, but I'll refrain from comment
seeing as I don't understand what you're doing.

> - is there a "specification" of which are the "core" packages?

Are there packages on which the community standardizes?  That's the
goal of Haskell-Platform [1], but I don't place any special value in a
package being in HP yet - I just work with whatever package on Hackage
fills my need and am under the impression this is most peoples mode of
operation.

> While package
> removal is not supported through cabal, it is sometimes needed

Why?  What I see is a need for users to understand ghc-pkg (or
whatever package management tool exists for their Haskell compiler).
Should "cabal uninstall" provide a unified interface to some number of
Haskell compiler packaging systems?  It could but doesn't seem like a
priority.

Cheers,
Thomas

[1] http://hackage.haskell.org/platform/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] [ANN] Crypto-API 0.0.0.1 Released

2010-09-07 Thread Thomas DuBuisson
At long last and after much fruitful discussion on
librar...@haskell.org, Crypto-API is having its first release, version
0.0.0.1!

Crypto-API is a generic interface for cryptographic operations,
platform independent & quality entropy acquisition, property tests and
known-answer tests (KATs) for common algorithms, and a basic benchmark
infrastructure.  Maintainers of hash and cipher implementations are
encouraged to add instances for the classes defined in Crypto.Classes.
 Crypto users are similarly encouraged to use the interfaces provided.

Any concepts or functions of general use to more than one
cryptographic algorithm (ex: padding) is within scope of this package.

Hackage: http://hackage.haskell.org/package/crypto-api
Haddock: http://web.cecs.pdx.edu/~dubuisst/crypto-api-0.0.0.1/html/index.html
Blog: http://tommd.wordpress.com/2010/09/07/crypto-api-released/

At it's heart, Crypto-API is an interface to cryptographic algorithms
allowing crypto developers to provide a minimal, low level interface
and reuse generic higher-level functions while freeing crypto users
from specifying a particular algorithm or implementation.

 Highlights 
* Five type classes of Hash, BlockCipher, AsymCipher, StreamCipher,
and CryptoRandomGen
* Generic algorithms implemented using these class interfaces (ex:
block cipher modes of operation, hashing and HMAC)
* Platform independent acquisition of entropy for cryptographic use
(using /dev/urandom on *nix and the CryptoAPI on windows)
* Test suite and parsing of NIST KAT files
* Rudimentary benchmarking for BlockCipher, Hash, and RNGs

 Hash Example 
The hash developer defines a class instances:

> instance Hash MD5Context MD5Digest where
>outputLength = Tagged 128
>blockLength  = Tagged 512
>initialCtx   = md5InitialContext
>updateCtx= md5Update
>finalize = md5Finalize

The hash user can remain agnostic about which type of hash is used:

> authMessage :: Hash ctx dgst => B.ByteString -> MacKey -> dgst -> Bool
> authMessage msg k = (==) (hmac' k msg)

More examples can be found on the blog post.

Versioning
I don't intend to bump the version number for API changes in modules
that aren't built by default (Test.Crypto, Benchmark.Crypto).
Otherwise the PVP is in effect.  Let me know if this isn't
appreciated.

 Changes Since Release Candidate 
* Haddock documentation
* Crypto.HMAC uses MacKey to help users keep the key and message separate

Remaining TODO
* Optimize block cipher modes and add new ones
* Migrate Crypto.Random to the "random" package, pending conversation
and agreement.
* a signature class is planned for signature-only algorithms (DSA)
   class (Binary k, Serialize k) => Signing k where
   sign :: ...
   verify :: ...
* Verify Crypto.Random works on Windows (more likely: fix it) once a
Windows dev shows interest.
* Build and test Crypto.Padding
* Expand test suite.  Include other hashes, modes, block algorithms,
cipher properties.
* Improve benchmarks, use CryptoRandomGen class in benchmark.
* More Haddock documentation
* Consider adding "buildIV :: (CryptoRandomGen g) => g -> Either
GenError iv" routine to StreamCipher interface

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


Re: [Haskell-cafe] ANNOUNCE: secure-sockets version 1.0

2010-09-06 Thread Thomas DuBuisson
>> You could have gone to Hackage and checked your protocols correctness
>> using CPSA, not that the side-channel attacks would be discovered by
>> such a tool.
>
> Interesting. I had seen CPSA announced at one point, but there appears to be
> no documentation whatsoever. Did I miss the doc links?

There's lots of documentation:

$ cabal unpack cpsa
$ cd cpsa*
$ cd doc
$ ls *.pdf -- or you might have to build from .tex, I can't recall.

> The two large families of side-channel attacks that I know of and that have
> been popular (== successful) recently are:
> ... timing and cache miss attacks ...
> Am I making sense?

So much sense it's painful.  (that's a 'yes')

> Another of my tentative projects was to write a C library that implements
> popular crypto building blocks, with a large battery of tests for
> correctness and resistance to timing attacks.

But how does that prevent a timing-based information flow if the
consuming Haskell application is the one performing the branch?  Are
you assuming all information flow in the Haskell program is so
high-level its not cryptographically important, thus protecting these
low-level primitives is sufficient?  Also, if you feel any of these
tests would fit into the Test.Crypto module (or a submodule) then
please feel free to send in a patch or start some discussion.

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


Re: [Haskell-cafe] ANNOUNCE: secure-sockets version 1.0

2010-09-06 Thread Thomas DuBuisson
David said:
> I'd be interested with breaking the dependency on OpenSSL, for various
> reasons:
> [snip]

Can't say I'm surprised by these.  Its unfortunate the situation
hasn't improved.  I recall a half decent O'Reilly book on OpenSSL but
if you weren't using it as a cookbook (and wanted a 1-off solution)
then it wasn't so useful.

> So, a replacement would need to be a complete replacement for TLS. I did in
> fact try to start with this, implementing my own simpler TLS-ish protocol,
> using crypto primitives directly. It took a group of crypto experts about 5
> minutes to punch 3 different holes in the protocol

You could have gone to Hackage and checked your protocols correctness
using CPSA, not that the side-channel attacks would be discovered by
such a tool.

> That said, with the Haskell Crypto API stabilizing, I've been toying with
> the project of a pure Haskell TLS implementation, which would solve the
> annoying dependency issue while hanging on to a hardened protocol.

I'm releasing crypto-api-0.1 on Tuesday so if you have any last minute
comments now is the time!

> However,
> this is also far from a simple endeavor, especially if the implementation is
> to be hardened against side-channel attacks, which I'm not even sure is
> possible in Haskell.

Well, to determine if that's possible we'd need a definition of
side-channel attack which is counter to many definitions of
side-channel ;-).  Perhaps a list of common ones OpenSSL thinks it
addresses would give us a good start.

If you start on such a task (Haskell TLS) then perhaps you could drop
a line to l...@h.o or c...@h.o?

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


Re: [Haskell-cafe] ANNOUNCE: secure-sockets version 1.0

2010-09-06 Thread Thomas DuBuisson
On Mon, Sep 6, 2010 at 9:16 AM, Thomas DuBuisson
 wrote:
> Good work Dan!

Sorry!  David.  Good work David.  Not sure where "Dan" came from.

 Would you be interested in providing a build option
> that replaces the OpenSSL dependency with something more stand-alone?
> Or does ossl perform a significant part of the TLS protocol work for
> you (vs just being used for algorithms)?
>
> Anyone impatient for the midnight haddocking can see the docs here:
> http://web.cecs.pdx.edu/~dubuisst/secure-sockets-1.0/html/
>
> Cheers,
> Thomas
>
> On Sun, Sep 5, 2010 at 10:26 PM, David Anderson  wrote:
>> Hi,
>> I'm happy to announce the first release of secure-sockets, a library which
>> aims to simplify the task of communicating securely between two
>> authenticated peers.
>> 
>> -- What it is
>> 
>> The API mimicks that of Network.Socket, and introduces the additional notion
>> of peer identity, which is distinct from the endpoint address (host and
>> port). Connections can only be established between two peers who know and
>> expect to be communicating with each other.
>> Transport security is implicitly taken care of: an established
>> Network.Secure.Connection implies that each end of the connection
>> successfully authenticated to the other, and that they have setup strong
>> encryption for your data.
>> 
>> -- What it isn't
>> 
>> The library leans towards the "zero configuration" end of the spectrum, and
>> basically Just Works. This means that if you know exactly what you want and
>> need for the cipher, authentication algorithm, key type and length, key
>> exchange protocol, HMAC algorithm, rekeying intervals, random number
>> source... Then secure-sockets is not for you.
>> If on the other hand you just want to replace your current cleartext
>> "cipher" and faith-based "authentication" code with something that gives you
>> a good chance of being secure (see caveats in docs), without diving into the
>> rich madness that is full blown SSL, then you might want to take a look.
>> This library assumes that both ends of a connection are using it. The goal
>> of secure-sockets is not to allow you to connect to any SSL-enabled server,
>> or to speak a particular standard flavor of authentication protocol.
>> Internally, secure-sockets uses SSL to achieve its goals, so you might get
>> lucky if you do it just right, but that is an implementation detail. The
>> library is designed to help you easily secure communications between two
>> programs whose implementation you control, not between you and anything out
>> there.
>> 
>> -- Links
>> 
>> Homepage: http://secure-hs.googlecode.com/
>> Hackage page: http://hackage.haskell.org/package/secure-sockets
>> Bug tracker: http://code.google.com/p/secure-hs/issues/list
>> Code repository: https://secure-hs.googlecode.com/hg
>> 
>> -- Thanks
>> 
>> I'd like to thank my employer, Google. Not only did they not get mad at the
>> idea that I might want to hack on Haskell during working hours (as my "20%
>> project"), they also made it very painless for me to open source this code
>> when the time came.
>> 
>> -- Questions?
>> 
>> Questions, comments, suggestions and patches can be filed in the issue
>> tracker, emailed directly to me, or thrown out on haskell-cafe.
>> Hope you find this code useful!
>> - Dave
>> ___
>> Haskell-Cafe mailing list
>> Haskell-Cafe@haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: secure-sockets version 1.0

2010-09-06 Thread Thomas DuBuisson
Good work Dan!  Would you be interested in providing a build option
that replaces the OpenSSL dependency with something more stand-alone?
Or does ossl perform a significant part of the TLS protocol work for
you (vs just being used for algorithms)?

Anyone impatient for the midnight haddocking can see the docs here:
http://web.cecs.pdx.edu/~dubuisst/secure-sockets-1.0/html/

Cheers,
Thomas

On Sun, Sep 5, 2010 at 10:26 PM, David Anderson  wrote:
> Hi,
> I'm happy to announce the first release of secure-sockets, a library which
> aims to simplify the task of communicating securely between two
> authenticated peers.
> 
> -- What it is
> 
> The API mimicks that of Network.Socket, and introduces the additional notion
> of peer identity, which is distinct from the endpoint address (host and
> port). Connections can only be established between two peers who know and
> expect to be communicating with each other.
> Transport security is implicitly taken care of: an established
> Network.Secure.Connection implies that each end of the connection
> successfully authenticated to the other, and that they have setup strong
> encryption for your data.
> 
> -- What it isn't
> 
> The library leans towards the "zero configuration" end of the spectrum, and
> basically Just Works. This means that if you know exactly what you want and
> need for the cipher, authentication algorithm, key type and length, key
> exchange protocol, HMAC algorithm, rekeying intervals, random number
> source... Then secure-sockets is not for you.
> If on the other hand you just want to replace your current cleartext
> "cipher" and faith-based "authentication" code with something that gives you
> a good chance of being secure (see caveats in docs), without diving into the
> rich madness that is full blown SSL, then you might want to take a look.
> This library assumes that both ends of a connection are using it. The goal
> of secure-sockets is not to allow you to connect to any SSL-enabled server,
> or to speak a particular standard flavor of authentication protocol.
> Internally, secure-sockets uses SSL to achieve its goals, so you might get
> lucky if you do it just right, but that is an implementation detail. The
> library is designed to help you easily secure communications between two
> programs whose implementation you control, not between you and anything out
> there.
> 
> -- Links
> 
> Homepage: http://secure-hs.googlecode.com/
> Hackage page: http://hackage.haskell.org/package/secure-sockets
> Bug tracker: http://code.google.com/p/secure-hs/issues/list
> Code repository: https://secure-hs.googlecode.com/hg
> 
> -- Thanks
> 
> I'd like to thank my employer, Google. Not only did they not get mad at the
> idea that I might want to hack on Haskell during working hours (as my "20%
> project"), they also made it very painless for me to open source this code
> when the time came.
> 
> -- Questions?
> 
> Questions, comments, suggestions and patches can be filed in the issue
> tracker, emailed directly to me, or thrown out on haskell-cafe.
> Hope you find this code useful!
> - Dave
> ___
> 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] Re: Crypto-API is stabilizing

2010-09-04 Thread Thomas DuBuisson
Sorry, the example was all messed up, even if it did communicate what
I wanted its just so broken I must fix.

Slightly contrived example:

   buildAgreementMessage :: (Monad m, CryptoRandomGen g,
ASymetricCipher k) => g -> k -> m (B.ByteString, (k,k), g)
   buildAgreementMessages g k = do
   ((p,q),g') <- eitherToFail (buildKeyPair g)
   let pBS = encode p
   msg = runPut $ do
   putByteString agreementHeader
   putWord16be (B.length pBS)
   putByteString pBS
   return $ (sign msg k, (p,q), g')

Again, this is simply trying to re-enforce the fact that buildKeyPair
(formerly 'generateKeyPair') does have a place.

Cheers,
Thomas

On Sat, Sep 4, 2010 at 7:45 AM, Thomas DuBuisson
 wrote:
>
> Slightly contrived example:
>
>    buildAgreementMessage :: (Monad m, CryptoRandomGen g,
> ASymetricCipher k) => g -> k -> m (B.ByteString,g)
>    buildAgreementMessages g k = do
>        (e,g') <- liftM eitherToFail (buildAsymKey g `asTypeOf` k)
>        let eBS = encode e
>            msg = runPut (putByteString agreementHeader >> putWord16be
> (B.length eBS) >> putByteString eBS)
>        return msg
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Crypto-API is stabilizing

2010-09-04 Thread Thomas DuBuisson
On Sat, Sep 4, 2010 at 3:23 AM, Heinrich Apfelmus
 wrote:
>>> A better reason is the data structure has
>>> no way to implement generateKeyPair.
>
> That's a non-problem: each algorithm (RSA, DSA, ...) implements a
> function with the same type as  generateKeyPair . Compare
>
>   rsa :: RangomGen g => BitLength -> g -> ((Key,Key), g)
>
> vs
>
>   ((k1 :: RSA, k2), g') = generateKeyPair g
>
> You always have to write down the name of the algorithm ("RSA") when
> using  generateKeyPair , so you may as well drop it entirely.

That simply isn't true.  What if you have a key exchange in which the
ephemeral key is of the same type as your signing key?

Slightly contrived example:

buildAgreementMessage :: (Monad m, CryptoRandomGen g,
ASymetricCipher k) => g -> k -> m (B.ByteString,g)
buildAgreementMessages g k = do
(e,g') <- liftM eitherToFail (buildAsymKey g `asTypeOf` k)
let eBS = encode e
msg = runPut (putByteString agreementHeader >> putWord16be
(B.length eBS) >> putByteString eBS)
return msg
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Crypto-API is stabilizing

2010-09-03 Thread Thomas DuBuisson
>> If MR the more agreeable path
>> then I'll do it, though this means I use the unholy "fail" function.
>
> You don't want to use monads because the Monad class defines the fail
> function?

Sorry, I phrased this better on the blog comment.  I don't want to use
"MonadRandom m => m (p,p)" (MonadRandom + fail) instead of "Either
GenError (B,ByteString, g)" because it limits my options for failure
down to a piddly "fail :: String -> m a" (ignoring exceptions) - right
now my options for failure are much richer,  I can say ReseedRequred
or NotEnoughEntropy etc, giving the user errors that can be handled by
a simple pattern matching case expression.

>> In general, I like this approach, but what are
>>  encrypt privateKey
>>or
>>  decrypt publicKey
>>
>> supposed to do? A type-class solution also does not *prevent* programmers to 
>> perform such non-sensical calls
>
>Would it be desirable to prohibit such calls using the type system?

As was earlier pointed out, these are actually valid operations for
many public key systems.  In fact, it's possible to use these for
signing or verifying messages:

Signing ==> encrypt privateKey . encode . hash
Verifying signature ==> \sig msg -> decrypt publicKey sig == encode (hash msg)

What makes a key public and another private is simply your pick of
which to publish and which to protect as jealously as my daughter
guards her cup of water (seriously, I can't get it from her).


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


Re: [Haskell-cafe] Re: Crypto-API is stabilizing

2010-09-02 Thread Thomas DuBuisson
On Thu, Sep 2, 2010 at 3:07 PM, Sebastian Fischer
 wrote:
>>  data Key = Key {
>>               encrypt   :: B.ByteString -> B.ByteString,
>>               decrypt   :: B.ByteString -> B.ByteString,
>>               keyLength :: BitLength,
>>               serialize :: B.ByteString}
>>
>>  rsa :: RandomGen g => BitLength -> g -> ((Key,Key), g)

One reason against this is simply that all the other constructs
(block/stream cipher, hashes) are classes, it would be odd for there
to be a single exception.  A better reason is the data structure has
no way to implement generateKeyPair.

> Why not use
>
>    generateKeypair :: MonadRandom m => BitLength -> m (Maybe (p,p))

Because MonadRandom dictates mtl, and is heavier weight than a single
class.  I was hoping to keep this agnostic (mtl is only required for
testing or benchmarks in crypto-api).  If MR the more agreeable path
then I'll do it, though this means I use the unholy "fail" function.
Even if that's the case (and more people weighing in would help) I
still want to include Data.Crypto.Random and welcome comments.

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


[Haskell-cafe] Re: Crypto-API is stabilizing

2010-09-02 Thread Thomas DuBuisson
Marcel noted:
> A central interface to get the output of a PRNG would be nice,
> preferably not constrained to Int like RandomGen.

While BOS said:
> Also, don’t use RandomGen for your asymmetric PRNG. The
> default implementation in System.Random gives absolutely
> disastrous performance, and the typeclass is just
> misdesigned (the split function shouldn’t be present).

Ok, ok.  I never liked RandomGen either - I start this whole thing
because of my PRNG and it doesn't fit RandomGen one bit.

I've build Data.Crypto.Random.RandomGenerator - a new class that fixes
the aspects of RandomGen I don't like.  This is something I was
considering anyway, so it's probably best now and not as an API upset
in a couple months.

There is a blog on this [1], but the main points about the new class are:

1) Generates bytestrings, not Ints
2) Generalized PRNG construction and reseeding
3) 'split' is in a different class.
4) Clean failure via Either (RandomGen forced you to use exceptions)

And minor points
- Providing additional entropy while requesting data is allowed and
has a default instance so most users can ignore this all together.
- a newtype wrapper and instance allows all RandomGenerator instances
to be used as RandomGen when needed.

Who cares about this?  Anyone wanting to get random IVs for block
cipher modes (without getIV_IO) and anyone wanting to generate
asymmetric keys using the AsymCipher class.

What can you do?  Accept this API, help improve the API, or argue that
we should stick with RandomGen (despite short-comings noted on the
blog).  Please pick one and get to it!

Cheers,
Thomas

P.S. I would like to get crypto-api onto hackage by the end of the
first week of September, but understand this is a fairly large change
and will slide that date if there is an unusual strong objection.

[1] 
http://tommd.wordpress.com/2010/09/02/a-better-foundation-for-random-values-in-haskell/

>
> Designing a random interface that provides something as high a level
> as monad random, is easy enough to make instances for (like RandomGen)
> and is feature rich enough to allow reseeding, additional entropy
> input, personalization, and failure is a non-trivial design task.
> Having ran into the dilemma of how to provide a reasonable high-level
> interface for DRBG, I agree with your statement but don't know how a
> solution would look.
>
> FYI, BOS had a similar suggestion (on the blog) of moving away from
> RandomGen but I'm not clear on what I'd move toward.
>
> Cheers,
> Thomas
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Crypto-API is stabilizing

2010-08-26 Thread Thomas DuBuisson
>>class (Binary p, Serialize p) => AsymCipher p where
>>generateKeypair :: RandomGen g => g -> BitLength -> Maybe ((p,p),g)
>>encryptAsym :: p -> B.ByteString -> B.ByteString
>>decryptAsym :: p -> B.ByteString -> B.ByteString
>>asymKeyLength   :: p -> BitLength
>
> Regarding AsymCipher:
> Some algorithms do not lend themselves to encryption/decryption or have
> special properties which differentiate their use in enc/dec an
> signing/verifying.
>
> I propose the following two additions for the class:
> signAsym :: p -> B.ByteString -> B.ByteString
> verifyAsym :: p -> B.ByteString -> Bool
>
> This way algorithms can leave parts undefined which do not apply to
> them or hide their different behaviour.

I am strongly against classes for which we already know instanes will
need a good deal of undefined routines.

> Another possibility would be a split of AsymCipher into AsymCipherEnc
> (which is just like the old AsymCipher) and AsymCipherSig for
> Signatures. Textbook-RSA is special, since it can implement both
> classes with a minimum of effort, but a clean separation would be nice
> (and there wouldn't be that many undefined functions).

Perhaps even zero undefined functions.  I like this suggestion, though
I'm not aware of any haskell implementations that will take advantage
of a "Signature" class yet.  Unless someone can point to something
like a DSA or ECDSA on hackage I'll probably release crypto-api 0.1
without this class (it would still likely appear in a later version
after further consideration).

> Another thing:
> A central interface to get the output of a PRNG would be nice,
> preferably not constrained to Int like RandomGen.

Designing a random interface that provides something as high a level
as monad random, is easy enough to make instances for (like RandomGen)
and is feature rich enough to allow reseeding, additional entropy
input, personalization, and failure is a non-trivial design task.
Having ran into the dilemma of how to provide a reasonable high-level
interface for DRBG, I agree with your statement but don't know how a
solution would look.

FYI, BOS had a similar suggestion (on the blog) of moving away from
RandomGen but I'm not clear on what I'd move toward.

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


[Haskell-cafe] Crypto-API is stabilizing

2010-08-23 Thread Thomas DuBuisson
All,

Crypto-API - a unified interface to which I hope hash and cipher
algorithms will adhere - has recently gotten a reasonable amount of
polish work.  I continue to welcome all comments!  A blog on its
current interface is online [1] as are darcs repositories of the
crypto-api package [2].  Recent changes includes added block cipher
modes, platform-independent RNG, tests, a simplistic benchmark
framework, and minor tweaks of the classes.  I've made experimental
hash, block cipher and stream cipher instances.  Almost no
optimizations have been made as of yet!

Thanks to everyone for their past comments!  I have made numerous
changes based on input received.  If you feel I didn't respond
properly to your suggestion then please ping me again - this is purely
a spare time effort and things do fall through the cracks.

Cheers,
Thomas

[1] 
http://tommd.wordpress.com/2010/08/23/a-haskell-api-for-cryptographic-algorithms/
[2] http://community.haskell.org/~tommd/crypto/

(If you're wondering why you're BCCed its probably because you worked
on a crypto-related Haskell package)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Microsoft's Singularity Project and Haskell

2010-07-31 Thread Thomas DuBuisson
On Sat, Jul 31, 2010 at 8:27 PM, wren ng thornton  wrote:
> Thomas DuBuisson wrote:
>>>
>>> And note that we wouldn't need unsafePerformIO for the FFI if all
>>> programs were made in Haskell ;).
>>
>> Perhaps that's true, though entirely unrealistic, in the application
>> world.  In the OS world you need access to machine registers and
>> special instructions (CR3 anyone? CP15?) which isn't built into any
>> language save assembly - for these FFI will always come in handy.
>>
>> Also, Haskell continues to have an unfortunate lack of primitives
>> suitable for casting types (ex: zero copy form a bytestring like
>> entity to Word32s).  In this realm FFI can outperform cleaner looking
>> code that must rely on individual byte reads.
>
> The FFI doesn't always require unsafePerformIO,

True.  I mis-read the previous e-mail as "we wouldn't need
unsafePerformIO OR (vs for) the FFI "  so please ignore that response
to a non-existent statement!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Microsoft's Singularity Project and Haskell

2010-07-31 Thread Thomas DuBuisson
> And note that we wouldn't need unsafePerformIO for the FFI if all
> programs were made in Haskell ;).

Perhaps that's true, though entirely unrealistic, in the application
world.  In the OS world you need access to machine registers and
special instructions (CR3 anyone? CP15?) which isn't built into any
language save assembly - for these FFI will always come in handy.

Also, Haskell continues to have an unfortunate lack of primitives
suitable for casting types (ex: zero copy form a bytestring like
entity to Word32s).  In this realm FFI can outperform cleaner looking
code that must rely on individual byte reads.

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


Re: [Haskell-cafe] Memory and Threads - MVars or TVars

2010-07-29 Thread Thomas DuBuisson
On Thu, Jul 29, 2010 at 6:53 AM, Job Vranish  wrote:
>
> You might try pulling downloading the package ('cabal fetch org'  will do
> this) and changing the base dependency (to >= 4.1) in the orc.cabal file

cabal also has an 'unpack' command for the particularly lazy (me).  Ex:

 cabal unpack orc ; sed "s/base\W*>= 4.2/base >= 4.1/" orc*/*.cabal ;
cd orc* ; cabal install

Should unpack, fix the .cabal file, and install.

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


Re: [Haskell-cafe] Chart package segfaults when rendering to window

2010-07-26 Thread Thomas DuBuisson
Can you boil this down to some simple example code?  Are you using a
recent version of Chart?  And your definition of "latest" gtk2hs is
11, right?  How about your gtk+ C library, it what? 2.20?

Cheers,
Thomas

On Mon, Jul 26, 2010 at 9:39 PM,   wrote:
> Seems to be ok rendering to png files.
>
> I was wondering if anybody has been using Chart and may have seen the
> same thing.

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


Re: [Haskell-cafe] Experiences with cabal-install and Hackage

2010-07-22 Thread Thomas DuBuisson
Not to discourage this brainstorming, but many of what people think to
be "new ideas" are being implemented by a GsoC student [1] already.
Yay!

>>> I've rather recently started to use cabal-install to install packages
>>> from Hackage.  Unfortunately, so far many packages fail to install.  I
>>> try to email authors/maintainers, but when I check build logs on
>>> Hackage, I discover that some of these packages have failed building for
>>> some time.

The hackage build logs can be misleading - many system specific
packages may or may not build on hackage because it just isn't the
right OS.  Still other packages require particular C libraries that
the hackage server doesn't have.  For these reasons the build reports
will come from end developer systems (see linked blog).

>>> Wouldn't it make sense to provide automated notification of the package
>>> author when a package fails to build?  I certainly would like to know
>>> about it, but of course, I never remember to check back to see.

Yes, but because this comes from the cabal-installer vs hackage there
was more work needing done.

>> How about taking it one step further, actually "hiding" unmaintained
>> packages after a grace period?

Talk to Gracenotes and Coutts - they can be found on #hackage frequently.

Cheers,
Thomas

[1] http://cogracenotes.wordpress.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Porting ELF statifier to Haskell!

2010-07-22 Thread Thomas DuBuisson
Interesting tool.  For my recent work I too have found a use for the
elf package, but its lack of a full binary instance and no parsing of
.symtab or .dynstr sections limits its usefulness.  This isn't a
debilitating limitation - you can use elf for basic inspection then
perform mutations via objcopy and ld, which are more likely to have
any oddities / corner cases accounted for anyway.

Thomas

On Wed, Jul 21, 2010 at 9:20 PM, C K Kashyap  wrote:
> Hi,
> At my work we ran into a situation where we started wishing there was a way
> to take a dynamically linked executable and create a statically linked
> bundle out of it. Little bit of googling got me to statifier -
> http://statifier.sourceforge.net/statifier/main.html. The project seems a
> little old and when I tried it out on my 32bit RHEL5 box, the statically
> linked file did not run. So I thought it would be a good exercise to try and
> use Haskell's Elf module (Data.Elf) and attempt to build a statifier. Just
> wanted to understand if anyone's tried this before or have any advice for
> me.
> --
> Regards,
> Kashyap
>
> ___
> 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] HTTP Redirect With HTTPS Rejected

2010-07-20 Thread Thomas DuBuisson
Sorry, I ment to say CC the maintainer and the author if that wasn't obvious.

Thomas

On Tue, Jul 20, 2010 at 2:00 PM, Thomas DuBuisson
 wrote:
> You should be CCing the author and creator (different people) of the
> library.  Not everyone in the Haskell universe is subscribed to -cafe
> or any other ML.
>
> Cheers,
> Thomas
>
> On Tue, Jul 20, 2010 at 1:49 PM, aditya siram  wrote:
>> The problem is that any page that that responds with 301.302,303 or
>> 307 and redirects to an "https" is rejected by the library.
>>
>> The code that does the rejection is in "Network.Browser" on line 865.
>> It only accepts "http:". Why was this design decision made? It makes
>> it impossible for me to use this library for my project.
>>
>> -deech
>>
>>
>>
>> On Tue, Jul 20, 2010 at 3:30 PM, aditya siram  wrote:
>>> Hi all,
>>> I am trying to simply download a web page using the HTTP library. It
>>> works fine with "http://www.google.com"; but a redirecting page like
>>> "http://gmail.com"; creates an error. Code is at
>>> http://hpaste.org/fastcgi/hpaste.fcgi/view?id=27864#a27864.
>>>
>>> Thanks ,
>>> -deech
>>>
>> ___
>> 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] HTTP Redirect With HTTPS Rejected

2010-07-20 Thread Thomas DuBuisson
You should be CCing the author and creator (different people) of the
library.  Not everyone in the Haskell universe is subscribed to -cafe
or any other ML.

Cheers,
Thomas

On Tue, Jul 20, 2010 at 1:49 PM, aditya siram  wrote:
> The problem is that any page that that responds with 301.302,303 or
> 307 and redirects to an "https" is rejected by the library.
>
> The code that does the rejection is in "Network.Browser" on line 865.
> It only accepts "http:". Why was this design decision made? It makes
> it impossible for me to use this library for my project.
>
> -deech
>
>
>
> On Tue, Jul 20, 2010 at 3:30 PM, aditya siram  wrote:
>> Hi all,
>> I am trying to simply download a web page using the HTTP library. It
>> works fine with "http://www.google.com"; but a redirecting page like
>> "http://gmail.com"; creates an error. Code is at
>> http://hpaste.org/fastcgi/hpaste.fcgi/view?id=27864#a27864.
>>
>> Thanks ,
>> -deech
>>
> ___
> 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] Deprecated gtk2hs functions

2010-07-16 Thread Thomas DuBuisson
You mean something like buttonPressEvent [1]?

> on button buttonPressEvent

You can define signals, the constructor is exposed.



[1] 
http://www.haskell.org/gtk2hs/docs/current/Graphics-UI-Gtk-Abstract-Widget.html#v%3AexposeEvent


On Fri, Jul 16, 2010 at 11:36 AM, Alex Rozenshteyn  wrote:
> I recently started playing around with gtk2hs.
> I noticed that `onClicked`, `afterClicked`, etc. functions have been
> deprecated, presumably in favor of the `on` and `after` functions in the
> Glib signals module, but I couldn't find a collection of the appropriate
> signals to replace the functionality.
>
> Am I simply being blind?
>
> --
>           Alex R
>
> ___
> 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] Re: cryptohash and an incremental API

2010-07-14 Thread Thomas DuBuisson
Vincent said:
> couple of comments around the hashes interface:
>
> * updateCtx works on blockLength, instead of working on arbitrary size...

So for performance reasons you seem to prefer Semantics 1.2?

"""
1.2 Multiple of blockSize bytes
Implementations are encouraged to consume data (continue updating,
encrypting, or decrypting) until there is less than blockSize bits
available.
"""

Also, I'll amend 1.2 and say the hashUpdate/encrypt/decrypt functions
should only consume n * blockSize bytes, tracking the remainder will
be done at the higher level.  Also, the higher level default
implementations should only pass n * blocksize inputs to these
functions.

I can see how that's reasonable and am strongly considering using
these semantics instead of 1.1.

> * hash is a generic operation based on the class Hash. In my case, it improve
> performance by not running the pure init/update/finalize exposed, but use the 
> hidden
> impure function. I realized yesterday it's not as much as i though since i had
> a bug in my benchmark, but it's still there (100ms for 500mb of data).

Humm, 0.2 sections  / GB is significant so again I can be swayed - it
isn't like I can't have a default definition of hash (and others) when
its part of the class instance.

> * Why is the digest of a specific type ? I like representing different
> things with different types, but i'm not sure what do you gain with digests
> though.

This I am less flexible on.  My thought on how people will use this
library is centered around the instantiation of classes on the keys
used or resulting digests.  Anyone wanting ByteString results can
simply use Data.[Serialize,Binary].encode.

Here is a user getting a sha256 hash:
  let h = hash contents :: SHA256

or the type could be implicit due to context (not shown):
  let h = hash contents


> * is strength really useful in the Hash class ? it might be accurate when the
> thing get implemented, but i'm not sure what would happens over time, and 
> flaws
> are discovered. would people actually updates it ?

Will people actually update it?  I hope so but if they don't are we
really worse off than not having any strength numbers?  People who
care about strength will likely keep track of the algorithms on which
they depend.  I added strength largely because the Hash class came
from DRBG (NIST SP 800-90) and that needed strength values.

If we don't have strength then applications like DRBG need a way to
know which algorithm each data type represents then to look up that
algorithm their its own table of algorithm strength - very messy.  I'd
imaging crypto-api would have to look something like:

\begin{code}
data HashAlgorithm = MD5 | SHA1 | SHA256 | SHA512 | ...

class Hash d c | d -> c, c -> d where
...
algorithm :: Tagged d HashAlgorithm
...
\end{code}

I don't consider this a win - crypto-api now enumerating all hash
algorithms wanting Hash instances.

> The blockCipher should exposes the chaining modes as overridable typeclass
> functions, with default generic implementations that use encryptBlocks. For
> example the haskell AES package has different C implementations for each
> chaining modes (e.g. cbc, ebc), and i suspect that using a generic chaining
> implementation would slow things down.

As with "hash" being part of the hash typeclass, I don't have a strong
objection here.  It allows particular implementations to be slightly
higher performance and does not preclude default definitions.  This is
rather messier than I wanted, but the reasoning seems sound.

WRT your specific examples:
 encryptBlocksCBC :: k -> ByteString -> (k, ByteString)
 decryptBlocksCBC :: k -> ByteString -> (k, ByteString)

These I do object to.  The key does not change as the CBC algorithm
progresses, but contextual information does.  My initial mode
implementations have types like:

cbc :: (BlockCipher k) => k -> IV k -> ByteString -> (ByteString, IV k)

In other words, initialization vectors are explicit and separate from
the key.  The type parameter on IV allows us to build an IV of proper
size, something like:

buildIV :: (BlockCipher k, MonadRandom m) => m (IV k)

and it is always true that
iv :: IV k
iv <- buildIV
B.length (encode iv) == blockSize `for` (undefined :: k)

> and my last comment, is that i don't understand the streamcipher interface
> you're proposing.  I've got a (inefficient) RC4 implementation that has this
> interface:
>
> stream :: Ctx -> B.ByteString -> (Ctx, B.ByteString)
> streamlazy :: Ctx -> L.ByteString -> (Ctx, L.ByteString)

My interface was just a quick hack with me understanding it would
likely change -  I didn't know there was a Haskell RC4 binding or
implementation and will happily follow your lead here.  Is this
implementation on hackage?


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


Re: [Haskell-cafe] Marshalling

2010-07-13 Thread Thomas DuBuisson
That code is effectively copying the data (thats what those peeks /
pokes do), so it stands to reason it would be slow by most performance
standards.  The reason ByteStrings are fast when used both by C and
Haskell is there is a zero-copy `useAsCString`.

Cheers,
Thomas

On Tue, Jul 13, 2010 at 7:49 AM, Phyx  wrote:
> Marshalling large amount of data from and to C
>
> http://phyx.pastebin.com/WXGBr1bX shows the code I use to do this (it's
> autogenerated, so just looking at 1 block should be enough)
>
> The tool is mine, so i can change the code it generates, but i would need to
> know how to do it better first.
>
> On Tue, Jul 13, 2010 at 3:30 PM, Magnus Therning 
> wrote:
>>
>> On Tue, Jul 13, 2010 at 13:29, Phyx  wrote:
>> > Hello
>> >
>> > I'm wondering if anyone ever benchmarked marshalling in Haskell/GHC. No
>> > matter how much I optimize my Haskell code my program still seems to run
>> > slow, which leads me to beleive that Marshalling is painfully slow.
>> >
>> > Does anyone know a way I can test this and fix it?
>>
>> What kind of marshalling are you referring to?
>>
>> /M
>>
>> --
>> Magnus Therning                        (OpenPGP: 0xAB4DFBA4)
>> magnus@therning.org          Jabber: magnus@therning.org
>> http://therning.org/magnus         identi.ca|twitter: magthe
>
>
> ___
> 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] PNG sample on haskellwiki

2010-07-12 Thread Thomas DuBuisson
I don't know about that code, but have had good experiences on two
projects using the DevIL binding library found on hackage [1].  I
tried pngload [2] originally, but that isn't full featured enough for
real use.  iirc, stb-image [3] had a similar issue of being too
bare-bones; the haddock comments agree ("PNG 8-bit only").

In summary, thank you Luke for a good package.

Cheers,
Thomas

[1] http://hackage.haskell.org/package/Codec-Image-DevIL
[2] http://hackage.haskell.org/package/pngload
[3] 
http://hackage.haskell.org/packages/archive/stb-image/0.2/doc/html/Codec-Image-STB.html

On Mon, Jul 12, 2010 at 9:51 AM, C K Kashyap  wrote:
> Hi,
>
> I tried out the code on this page http://haskell.org/haskellwiki/Library/PNG
> but the png file that'e emitted does not seem to open properly with image
> viewing tools. Has anyone tried it out?
>
> I added this bit for supplying the data for image creation -
>
> count=100
> row = take count (cycle [True,False])
> rows = take 100 (repeat row)
> image = png rows
>
> main=writeFile "hello.png" image
>
>
>
> --
> Regards,
> Kashyap
>
> ___
> 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] GHC vs GCC

2010-03-26 Thread Thomas DuBuisson
> Using bang patterns didn't help almost anything here. Using rem
> instead of mod made the time go from 45s to 40s. Now, using -fvia-C
> really helped (when I used rem but not using mod). It went down to
> 10s.

Bang patterns should have helped tons - it isn't GHC thats at fault
here and yes it does tco.  I attached a version w/ excessive bangs
below.  Did you compile with "ghc --make -O3 -fforce-recomp"?

Cheers,
Thomas

main = print $ rangeI 0 0

rangeK :: Int -> Int -> Int -> Int -> Int
rangeK !i !j !k !acc =
if k < 1000
  then
   if i * i + j * j + k * k `rem` 7 == 0
   then rangeK i j (k+1) (acc+1)
   else rangeK i j (k+1) acc
   else acc

rangeJ :: Int -> Int -> Int -> Int
rangeJ !i !j !acc =
   if j < 1000
then rangeJ i (j+1) (acc + rangeK i j 0 0)
else acc

rangeI :: Int -> Int -> Int
rangeI !i !acc =
   if i < 1000
then rangeI (i+1) (acc + (rangeJ i 0 0))
else acc
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] GHC vs GCC

2010-03-26 Thread Thomas DuBuisson
On Fri, Mar 26, 2010 at 6:16 PM, Felipe Lessa  wrote:
> I'd guess that the LLVM backend could generate code that is at least
> as fast as gcc. It would be nice if you could test it.

NCG done with GHC 6.12.1 w/ -O3
LLVM using a version of HEAD w/ -O3
GCC version 4.4.3 w/ -O3
Please take note Johns benchmark of JHC showing it beats everything
here (including C).
Also note -Odph did not alter performance from -O3.


[to...@mavlo Test]$ time ./blahC
143

real0m4.124s
user0m4.032s
sys 0m0.013s

[to...@mavlo Test]$ time ./blahLLVM
143

real0m5.045s
user0m4.984s
sys 0m0.006s


[to...@mavlo Test]$ time ./blahNCG
143

real0m5.960s
user0m5.872s
sys 0m0.008s

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


Re: [Haskell-cafe] Re: Bytestrings and [Char]

2010-03-23 Thread Thomas DuBuisson
> If you read the source code, length do not read the data, that's why
> it is so fast. It cannot be done for UTF-8 strings.

I think at this point most the amazement is directed at Data.Text
being slower than good old [Char] (at least for this operation - we
should probably expand our view to more than one operation).

> Hey, normal string way faster than GNU wc!

No - you need to perform a fair comparison.  Try "wc -c" to only count
characters (not lines and words too).  I'd provide numbers but my wc
doesn't seem to support UTF-8 and not sure what package contains a
unicode aware wc.

> readChar :: L.ByteString -> Maybe Int64
> readChar bs = do (c,_) <- L.uncons bs
>                 return (choose (fromEnum c))
>  where
>  choose :: Int -> Int64
>  choose c
>    | c < 0xc0  = 1
>    | c < 0xe0  = 2
>    | c < 0xf0  = 3
>    | c < 0xf8  = 4
>    | otherwise = 1
>
> inspired by Data.ByteString.Lazy.UTF8, same performances as GNU wc (it
> is cheating because it do not check the validity of the multibyte char).

Ah, interesting and a worth-while cheat.

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


Re: [Haskell-cafe] Bytestrings and [Char]

2010-03-23 Thread Thomas DuBuisson
BOS:
> Well, your benchmarks are highly suspect.

Attached is another benchmark with similar results.  This is no
criterion benchmark but I did try to adjust a wee bit for cache
issues.  Suffice to say I am not yet impressed with Data.Text
performance wise.

In the broader scope I feel there is a deeper point here:
Data.ByteString is how most data is available in a program (be it from
a file, network, or other library/device).  With all this data we
really should have some sort of zero-copy "safeCoerce" that can expose
the bytestring as an O(1) unboxed array of some safe length.  I know
this would have been nice for pureMD5, which did use an ugly
unsafePerformIO hack just to get Word16s but even those got boxed up
at horrible cost (it now uses 'cereal' to get the Word16 - even worse
performance but it lets me ignore endianess of the architecture).


 OT 
Beating the dead horse: I once wrote and deleted a blog post ranting
about how to get Word16 in C vs in Haskell:
   word = ((uint16_t *)p)[index];
or
  word = unsafePerformIO $ withForeignPtr ptr $ \ptr' -> let p =
castPtr (plusPtr ptr' off) in peekElemOff p index

That Haskell snippet takes significantly longer to both write and run.
 END OT 


Code and benchmark numbers included below, all complaints about the
accuracy of the benchmark are welcome.

NOTE: tLog is a daily #haskell log file repeated many times ~ 59MB.
---
[to...@mavlo Test]$ ./read tLog
Normal String + System.IO "61443120": 1.467924s
Data.ByteString.Lazy "61450365": 0.023285s
Data.ByteString.Lazy.UTF8 "61443120": 3.305154s
Data.Text.Lazy "61443120": 3.99178s

- CODE -
import Data.Time
import qualified Data.ByteString.Lazy as L
import qualified Data.ByteString.Lazy.UTF8 as U
import qualified Data.Text.Lazy as T
import qualified Data.Text.Lazy.IO as TO
import System.IO
import System.Environment (getArgs)
import Control.Monad (sequence_, when)

main = do
[file] <- getArgs
let time (f, desc)  = do
s <- getCurrentTime
r <- f
let !r' = r
t <- getCurrentTime
let d = diffUTCTime t s
when (length desc > 0)
(putStrLn $ desc ++ " " ++ show r' ++ ": " ++ show d)
ops = [
(readFile file >>= return . show . length, "")
  , (readFile file >>= return . show . length, "Normal
String + System.IO")
  , (L.readFile file >>= return . show . L.length, "")
  , (L.readFile file >>= return . show . L.length,
"Data.ByteString.Lazy")
  , (L.readFile file >>= return . show . U.length, "")
  , (L.readFile file >>= return . show . U.length,
"Data.ByteString.Lazy.UTF8")
  , (TO.readFile file >>= return . show . T.length, "")
  , (TO.readFile file >>= return . show . T.length,
"Data.Text.Lazy")
  ]
mapM_ time ops
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Trace

2010-03-19 Thread Thomas DuBuisson
> Hi,
> I'm a new Haskell programmer and am trying to output the values of some of
> the variables (for debugging) as the program executes.

Debugging?  Use the GHCi debugger.

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


Re: [Haskell-cafe] SoC Proposals?

2010-03-16 Thread Thomas DuBuisson
Be sure to try your user name without any capitals - that worked for me...

On Tue, Mar 16, 2010 at 6:59 PM, Jeff Wheeler  wrote:
> Is there any way to propose a SoC idea right now? My account doesn't
> seem to have been created correctly, so I can't login to the Trac.
>
> I think it'd be interesting for a student to abstract the layout model
> in xmonad, separating it into an independent library. Other
> applications could then use this library, like Yi, for other types of
> tiling.
>
> I'd love to see other ideas related to Yi, too. It's a great project
> but on the verge of death (although the maintainer, JPB, is interested
> in mentoring).
>
> --
> Jeff Wheeler
>
> Undergraduate, Electrical Engineering
> University of Illinois at Urbana-Champaign
> ___
> 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] Num instance for Lazy ByteStrings (was: NumLazyByteString Package License)

2010-03-08 Thread Thomas DuBuisson
> Is NumLazyByteString a newtype around Bytestring.Lazy that interprets the
> bit stream represented by the ByteString as integer?

Not exactly.  There is not newtype wrapper.  NumLazyByteString is:

instance Num L.ByteString where
 ...
instance Enum L.ByteString where
 ...
instance Integral L.ByteString where
 ...
instance Bits L.ByteString where
 ...

> If so, could this also
> be done using a newtype around [Integer], where appropriately large Integers
> are used? If yes, you may find
>  http://code.haskell.org/numeric-prelude/src/Number/Positional.hs
>  useful.

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


[Haskell-cafe] Num instance for Lazy ByteStrings (was: NumLazyByteString Package License)

2010-03-08 Thread Thomas DuBuisson
Tristan and other interested parties on the Cafe,

Answering your question first, Tristan: I was going to use BSD3 (if it
isn't already) for the NumLazyByteString.

For the cafe too:
A while ago I made a Num instance for LPS; it is currently on my
code.haskell.org account.  Notice this isn't on Hackage yet and the
semantics will be different soon.  Most notably I want to ensure
divide and anything else implemented through 'asInteger' and
'asInteger2' results in a bytestring of length equal to the largest of
the operands.

If that isn't clear then let me be very explicit.  NumLazyByteString
intentionally allows overflow!  If you want operations (mod 2^40) then
you need only work with bytestrings of length 5 bytes and the
operations will result in 5 byte ByteString.  This is already true for
basic operations (bit operations, +, -, *) but is not yet done for
quot, rem, quotRem, divMod, mod, /, and other you can see leverage
Integer instead of using custom code.

Any desire for non-overflowing operations (basically, re-expressing
Integer as LazyByteString) would have to be done as an newtype with a
Num instance that grows the bytestring to the necessary level,
preventing overflow prior to calling NumLazyByteString.

Finally, I intend for numerous operations to be lazy.  If you add two
infinite bytestrings you should be able to get the result of that
operation (modulo some finite value) using NumLazyByteString.  This is
obviously not true for those operations leveraging Integer.

Any comments or requests on the future of this Library are welcome -
I'll probably get around to finishing it and putting it on Hackage in
a couple weeks.

Cheers,
Thomas

On Sun, Mar 7, 2010 at 9:24 PM, Tristan Ravitch  wrote:
> I found myself adding Bits and Num instances for ByteStrings when I
> found your implementation (which is much better than mine was shaping
> up to be).  Do you have any particular license in mind for it?
>
> I used it in an implementation of the Delta Debugging algorithm
> (http://www.st.cs.uni-saarland.de/dd/), which I was thinking I would
> like to release, and wanted to make sure the licensing could work out
> properly.
>
> Thanks,
> --
> Tristan Ravitch
> travi...@cs.wisc.edu
> http://pages.cs.wisc.edu/~travitch
>
> -BEGIN PGP SIGNATURE-
> Version: GnuPG v1.4.10 (GNU/Linux)
>
> iEYEARECAAYFAkuUiiUACgkQJklRJNuIcWSxmACfVblD+gR/Fv57teNTArSfXhHg
> NtsAnRqBvinNesMk3mxMxDERw5MBn9jZ
> =Jm4O
> -END PGP SIGNATURE-
>
>


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


Re: [Haskell-cafe] how to get a string from file

2010-03-03 Thread Thomas DuBuisson
On Wed, Mar 3, 2010 at 10:26 AM, Pradeep Wickramanayake  wrote:
> getItemFile :: IO String

This says getItemFile is an action that returns a string.  No arguments.

> getItemFile test = ...

And your implementation obviously requires a file path as an argument.
 You wanted a type signature of:

getItemFile :: FilePath -> IO String

or perhaps more simply (FilePath is just an alias for String):

getItemFile :: String -> IO String

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


Re: [Haskell-cafe] Profiling

2010-02-21 Thread Thomas DuBuisson
> How do I tell Cabal to install the necessary code?

set:
"library-profiling: True"

in your ~/.cabal/config file and never deal with this again (for any
new packages you install).  use --reinstall -p to updat existing
packages.

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


Re: GUI (was: Re: [Haskell-cafe] DLL on Windows)

2010-02-17 Thread Thomas DuBuisson
On Wed, Feb 17, 2010 at 3:17 AM, Jeremy O'Donoghue
 wrote:
> You're probably correct about the dependencies. I have never tried to
> compile wxHaskell against GHC 6.12.1
>
> I'm waiting for Haskell Platform to be released to make the required
> changes since (working primarily on Windows) I just don't have time to
> create a complete GHC 6.12 installation with most of the HP libraries
> (some of which are a pain to get working on Windows).

FYI, it also seems the current version of wxcore assumes something
that isn't true about Cabal (again, I use Cabal 1.8.0.2).  I just
tested with ghc-6.10.4 + Cabal 1.8.0.2 + cabal-install 0.8.0 and
received what is probably a well known complaint:

[to...@mavlo ~]$ cabal install wx
Resolving dependencies...
[1 of 1] Compiling Main (
/tmp/wxcore-0.12.1.23133/wxcore-0.12.1.2/Setup.hs,
/tmp/wxcore-0.12.1.23133/wxcore-0.12.1.2/dist/setup/Main.o )

/tmp/wxcore-0.12.1.23133/wxcore-0.12.1.2/Setup.hs:15:57:
Couldn't match expected type `GenericPackageDescription'
   against inferred type `Either
GenericPackageDescription
PackageDescription'
  Expected type: (GenericPackageDescription, HookedBuildInfo)
  Inferred type: (Either
GenericPackageDescription PackageDescription,
  HookedBuildInfo)
In the `confHook' field of a record
In the first argument of `defaultMainWithHooks', namely
`simpleUserHooks {confHook = myConfHook}'

/tmp/wxcore-0.12.1.23133/wxcore-0.12.1.2/Setup.hs:51:37:
Couldn't match expected type `GenericPackageDescription'
   against inferred type `Either
GenericPackageDescription
PackageDescription'
In the expression: pkg0
In the second argument of `confHook', namely `(pkg0, pbi)'
In a stmt of a 'do' expression:
lbi <- confHook simpleUserHooks (pkg0, pbi) flags
cabal: Error: some packages failed to install:
wx-0.12.1.2 depends on wxcore-0.12.1.2 which failed to install.
wxcore-0.12.1.2 failed during the configure step. The exception was:
ExitFailure 1
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: GUI (was: Re: [Haskell-cafe] DLL on Windows)

2010-02-16 Thread Thomas DuBuisson
On Tue, Feb 16, 2010 at 3:48 PM, Henk-Jan van Tuyl  wrote:
> On Tue, 16 Feb 2010 18:57:20 +0100, Neil Mitchell 
> wrote:
>
>> I used to recommend Gtk2hs over wxHaskell for GUI development as there
>> was always a version that worked on Windows with the latest GHC
>> release. I think I might have to switch back to recommending C# for
>> GUI development...
>
> The latest revision of wxHaskell can be compiled relatively easy, so that
> wxHaskell can be used immediately for the latest version of GHC.

Exciting allegation, but it doesn't quite check out with GHC 6.12.1 +
cabal 1.8.0.2 and cabal-install 0.8 (see below).  I would expect this
issue to be easily resolved by specifying "containers <= 0.3.*" in the
"wxdirect" package, but cabal is misbehaving (for me) and stating
wxdirect needs reinstalled with a supposedly newer version of
containers, 0.2.0.1.

Thomas

[to...@mavlo ~]$ cabal install wx
Resolving dependencies...
Downloading containers-0.2.0.1...
Configuring containers-0.2.0.1...
Preprocessing library containers-0.2.0.1...
Building containers-0.2.0.1...

Data/IntMap.hs:182:7:
Could not find module `Data.Data':
  It is a member of the hidden package `base'.
  Perhaps you need to add `base' to the build-depends in your .cabal file.
  Use -v to see a list of the files searched for.
cabal: Error: some packages failed to install:
containers-0.2.0.1 failed during the building phase. The exception was:
ExitFailure 1
wx-0.12.1.2 depends on containers-0.2.0.1 which failed to install.
wxcore-0.12.1.2 depends on containers-0.2.0.1 which failed to install.
wxdirect-0.12.1.1 depends on containers-0.2.0.1 which failed to install.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: sendfile leaking descriptors on Linux?

2010-02-11 Thread Thomas DuBuisson
Bardur Arantsson  wrote:
>> ...
>>       then do errno <- getErrno
>>               if errno == eAGAIN
>>                 then do
>>                    threadDelay 100
>>                    sendfile out_fd in_fd poff bytes
>>                 else throwErrno "Network.Socket.SendFile.Linux"
>>      else return (fromIntegral sbytes)
>
> That is, I removed the threadWaitWrite in favor of just adding a
> "threadDelay 100" when eAGAIN is encountered.
>
> With this code, I cannot provoke the leak.
>
> Unfortunately this isn't really a solution -- the CPU is pegged at
> ~50% when I do this and it's not exactly elegant to have a hardcoded
> 100 ms delay in there. :)

I don't think it matters wrt the desired final solution, but this is
NOT a 100 ms delay.  It is a 0.1 ms delay, which is less than a GHC
time slice and as such is basically a tight loop.  If you use a
reasonable value for the delay you will probably see the CPU being
almost completely idle.

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


  1   2   3   >