Re: [Haskell-cafe] Efficient temporary file storage??

2012-01-23 Thread Vincent Hanquez

On 01/24/2012 07:33 AM, Gregory Crosswhite wrote:

On 1/24/12 9:43 AM, Felipe Almeida Lessa wrote:

Use cereal [1], usually it's fast and easy enough.


Out of curiosity, is binary no longer the recommended standard for such things?


binary got only an interface for processing lazy bytestring.
cereal is able to do strict and lazy bytestring and got a partial interface like 
attoparsec (which is required to do proper network/io processing).


Fortunately it's very simple to convert between the two, since the actual 
serialization API is really close.


Features-wise, in my view, cereal is a superset of binary. the only thing 
missing that i've noticed is that you can't tell how many bytes you have 
processed with cereal.


--
Vincent

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


Re: [Haskell-cafe] Efficient temporary file storage??

2012-01-23 Thread Gregory Crosswhite

On 1/24/12 9:43 AM, Felipe Almeida Lessa wrote:

Use cereal [1], usually it's fast and easy enough.


Out of curiosity, is binary no longer the recommended standard for such 
things?


Cheers,
Greg

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


Re: [Haskell-cafe] Contributing to http-conduit

2012-01-23 Thread Michael Snoyman
On Tue, Jan 24, 2012 at 8:37 AM, Myles C. Maxfield
 wrote:
> I have attached a patch to add a redirect chain to the Response datatype.
> Comments on this patch are very welcome.

I thought that this isn't necessary since a client wanting to track
all the redirects could just handle them manually by setting the
redirect count to 0.

> I was originally going to include the entire Request object in the
> redirection chain, but Request objects are parameterized with a type 'm', so
> including a 'Request m' field would force the Response type to be
> parameterized as well. I felt that would be too large a change, so I made
> the type of the redirection chain W.Ascii.
>
> Perhaps its worth using the 'forall' keyword to get rid of the pesky 'm'
> type parameter for Requests?
>
> data RequestBody
>     = RequestBodyLBS L.ByteString
>     | RequestBodyBS S.ByteString
>     | RequestBodyBuilder Int64 Blaze.Builder
>     | forall m. RequestBodySource Int64 (C.Source m Blaze.Builder)
>     | forall m. RequestBodySourceChunked (C.Source m Blaze.Builder)

There'd be no way to run the request body then (try compiling the code
after that change).

Michael

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


Re: [Haskell-cafe] Contributing to http-conduit

2012-01-23 Thread Myles C. Maxfield
I have attached a patch to add a redirect chain to the Response datatype.
Comments on this patch are very welcome.

I was originally going to include the entire Request object in the
redirection chain, but Request objects are parameterized with a type 'm',
so including a 'Request m' field would force the Response type to be
parameterized as well. I felt that would be too large a change, so I made
the type of the redirection chain W.Ascii.

Perhaps its worth using the 'forall' keyword to get rid of the pesky 'm'
type parameter for Requests?

data RequestBody
= RequestBodyLBS L.ByteString
| RequestBodyBS S.ByteString
| RequestBodyBuilder Int64 Blaze.Builder
| forall m. RequestBodySource Int64 (C.Source m Blaze.Builder)
| forall m. RequestBodySourceChunked (C.Source m Blaze.Builder)

--Myles

On Mon, Jan 23, 2012 at 3:31 AM, Michael Snoyman wrote:

> On Mon, Jan 23, 2012 at 1:20 PM, Aristid Breitkreuz
>  wrote:
> > Rejecting cookies is not without precedent.
> >
> > If you must force cookie handling upon us, at least make it possible to
> > selectively reject them.
> >
> > Aristid
>
> If you turn off automatic redirects, then you won't have cookie
> handling. I'd be interested to hear of a use case where you would want
> to avoid passing cookies after a redirect.
>
> Michael
>
From d60bc1adf4af5a038432c35cde222654dfabf6dd Mon Sep 17 00:00:00 2001
From: "Myles C. Maxfield" 
Date: Mon, 23 Jan 2012 21:44:12 -0800
Subject: [PATCH] Adding a redirection chain field to Responses

---
 Network/HTTP/Conduit.hs  |7 ---
 Network/HTTP/Conduit/Request.hs  |   24 +++-
 Network/HTTP/Conduit/Response.hs |7 ---
 3 files changed, 31 insertions(+), 7 deletions(-)

diff --git a/Network/HTTP/Conduit.hs b/Network/HTTP/Conduit.hs
index 794a62a..879d5a8 100644
--- a/Network/HTTP/Conduit.hs
+++ b/Network/HTTP/Conduit.hs
@@ -147,7 +147,7 @@ http
 -> Manager
 -> ResourceT m (Response (C.Source m S.ByteString))
 http req0 manager = do
-res@(Response status hs body) <-
+res@(Response _ status hs body) <-
 if redirectCount req0 == 0
 then httpRaw req0 manager
 else go (redirectCount req0) req0
@@ -160,7 +160,7 @@ http req0 manager = do
   where
 go 0 _ = liftBase $ throwIO TooManyRedirects
 go count req = do
-res@(Response (W.Status code _) hs _) <- httpRaw req manager
+res@(Response uri (W.Status code _) hs _) <- httpRaw req manager
 case (300 <= code && code < 400, lookup "location" hs) of
 (True, Just l'') -> do
 -- Prepend scheme, host and port if missing
@@ -192,7 +192,8 @@ http req0 manager = do
 then "GET"
 else method l
 }
-go (count - 1) req'
+response <- go (count - 1) req'
+return $ response {requestChain = (head uri) : (requestChain 
response)}
 _ -> return res
 
 -- | Get a 'Response' without any redirect following.
diff --git a/Network/HTTP/Conduit/Request.hs b/Network/HTTP/Conduit/Request.hs
index e6e8876..a777285 100644
--- a/Network/HTTP/Conduit/Request.hs
+++ b/Network/HTTP/Conduit/Request.hs
@@ -7,6 +7,7 @@ module Network.HTTP.Conduit.Request
 , ContentType
 , Proxy (..)
 , parseUrl
+, unParseUrl
 , browserDecompress
 , HttpException (..)
 , alwaysDecompress
@@ -39,7 +40,7 @@ import qualified Network.HTTP.Types as W
 
 import Control.Exception (Exception, SomeException, toException)
 import Control.Failure (Failure (failure))
-import Codec.Binary.UTF8.String (encodeString)
+import Codec.Binary.UTF8.String (encode, encodeString)
 import qualified Data.CaseInsensitive as CI
 import qualified Data.ByteString.Base64 as B64
 
@@ -207,6 +208,27 @@ parseUrl2 full sec s = do
 (readDec rest)
 x -> error $ "parseUrl1: this should never happen: " ++ show x
 
+unParseUrl :: Request m -> W.Ascii
+unParseUrl Request { secure = secure'
+   , host = host'
+   , port = port'
+   , path = path'
+   , queryString = querystring'
+   } = S.concat
+  [ "http"
+  , if secure' then "s" else S.empty
+  , "://"
+  , host'
+  , case (secure', port') of
+  (True, 443) -> S.empty
+  (True, p) -> S.pack $ encode $ ":" ++ show p
+  (False, 80) -> S.empty
+  (False, p) -> S.pack $ encode $ ":" ++ show p
+  , path'
+  , "?"
+  , querystring'
+  ]
+
 data HttpException = StatusCodeException W.Status W.ResponseHeaders
| InvalidUrlException String String
| TooManyRedirects
diff --git a/Network/HTTP/Conduit/Response.hs b/Network/HTTP/Conduit/Response.hs
index 5c6fd23..c183e34 100644
--- a/Network/HTTP/Conduit/Response.hs
+++ b/Network/HTTP/Conduit/Response.hs
@@ -33,7 +33,8 @@ import Network.HTTP.Conduit.Chunk
 
 -- | A simple representation of the HTTP 

Re: [Haskell-cafe] Efficient temporary file storage??

2012-01-23 Thread Tom Murphy
It's not as efficient for Maps, but you might want to look at the
swapper package:

http://hackage.haskell.org/package/swapper

It transfers Haskell data structures (any functors) directly to and from disk.

Tom

On 1/23/12, Krzysztof Skrzętnicki  wrote:
> From my experience I can recommend msgpack (
> http://hackage.haskell.org/package/msgpack) as being extremely fast. It
> comes with optimized prepared instances for common data structures which is
> very nice, because you don't have to roll your own version with library
> like cereal (which is indeed very fast, but simply less convenient).
>
> Best regards,
> Krzysztof Skrzętnicki
>
> On Tue, Jan 24, 2012 at 00:37, Nick Rudnick
> wrote:
>
>> Dear all,
>>
>> if you want to temporarily store haskell data in a file – do you have a
>> special way to get it done efficiently?
>>
>> In an offline, standalone app, I am continuously reusing data volumes of
>> about 200MB, representing Map like tables of a rather simple structure,
>>
>> key: (Int,Int,Int)
>> value: [((Int,Int),LinkId)]
>>
>>
>> which take quite a good deal of time to produce.
>>
>> Is there a recommendation about how to 'park' such data tables most
>> efficiently in files – any format acceptable, quick loading time is the
>> most desirable thing.
>>
>> Thanks a lot in advance, Nick
>>
>> ___
>> 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] Natural Transformations and fmap

2012-01-23 Thread Brent Yorgey
On Mon, Jan 23, 2012 at 09:06:52PM -0800, Ryan Ingram wrote:
> On Mon, Jan 23, 2012 at 8:05 PM, Daniel Fischer <
> daniel.is.fisc...@googlemail.com> wrote:
> 
> > On Tuesday 24 January 2012, 04:39:03, Ryan Ingram wrote:
> > > At the end of that paste, I prove the three Haskell monad laws from the
> > > functor laws and "monoid"-ish versions of the monad laws, but my proofs
> > > all rely on a property of natural transformations that I'm not sure how
> > > to prove; given
> > >
> > > type m :-> n = (forall x. m x -> n x)
> > > class Functor f where fmap :: forall a b. (a -> b) -> f a -> f b
> > > -- Functor identity law: fmap id = id
> > > -- Functor composition law fmap (f . g) = fmap f . fmap g
> > >
> > > Given Functors m and n, natural transformation f :: m :-> n, and g :: a
> > > -> b, how can I prove (f . fmap_m g) = (fmap_n g . f)?
> >
> > Unless I'm utterly confused, that's (part of) the definition of a natural
> > transformation (for non-category-theorists).
> >
> 
> Alright, let's pretend I know nothing about natural transformations and
> just have the type declaration
> 
> type m :-> n = (forall x. m x -> n x)
> 
> And I have
> f :: M :-> N
> g :: A -> B
> instance Functor M -- with proofs of functor laws
> instance Functor N -- with proofs of functor laws
> 
> How can I prove
>   fmap g. f :: M A -> N B
>   =
>   f . fmap g :: M A -> N B
> 
> I assume I need to make some sort of appeal to the parametricity of
> M :-> N.

This is in fact precisely the "free theorem" you get from the
parametricity of f.  Parametricity means that f must act "uniformly"
for all x -- which is an intuitive way of saying that f really is a
natural transformation.

-Brent

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


Re: [Haskell-cafe] bindings for libvirt

2012-01-23 Thread Erik de Castro Lopo
Ilya Portnov wrote:

> For my current projects, i'd also like to have bindings to libvirt. I
> even started to write something for them, using c2hs. If someone is
> interested, i could put my current (very basic) code to, say, github…

+1

Erik
-- 
--
Erik de Castro Lopo
http://www.mega-nerd.com/

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


Re: [Haskell-cafe] bindings for libvirt

2012-01-23 Thread Michael Litchard
Ilya,
  Yes please. Examining your code would go a long way toward
helping me with this project.

On Mon, Jan 23, 2012 at 9:26 PM, Ilya Portnov  wrote:
> On 16 янв, 03:27, Michael Litchard  wrote:
>> Due to the direction things are going at work, I have become
>> interested in Haskell bindings forlibvirt. Noticed that this hasn't
>> been done yet. I was wondering if this was due to lack of motivation,
>> or if there were some difficult hurdles withlibvirtthat make the
>> project cost-prohibitive. If it's the former, I don't see a problem
>> proceeding with exploration. If it's the latter, I'd like to know what
>> the hurdles are.
>
> Hello.
>
> For my current projects, i'd also like to have bindings to libvirt. I
> even started to write something for them, using c2hs. If someone is
> interested, i could put my current (very basic) code to, say, github...
>
> Seems there will no big problems, but libvirt API is not so small, so
> it'll take time to write full bindings.
>
> WBR, Ilya Portnov.
>
> ___
> 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] Natural Transformations and fmap

2012-01-23 Thread Eugene Kirpichov
Have you tried generating a free theorem for :-> ? (I haven't as I'm writing 
from my phone)



24.01.2012, в 9:06, Ryan Ingram  написал(а):

> On Mon, Jan 23, 2012 at 8:05 PM, Daniel Fischer 
>  wrote:
> On Tuesday 24 January 2012, 04:39:03, Ryan Ingram wrote:
> > At the end of that paste, I prove the three Haskell monad laws from the
> > functor laws and "monoid"-ish versions of the monad laws, but my proofs
> > all rely on a property of natural transformations that I'm not sure how
> > to prove; given
> >
> > type m :-> n = (forall x. m x -> n x)
> > class Functor f where fmap :: forall a b. (a -> b) -> f a -> f b
> > -- Functor identity law: fmap id = id
> > -- Functor composition law fmap (f . g) = fmap f . fmap g
> >
> > Given Functors m and n, natural transformation f :: m :-> n, and g :: a
> > -> b, how can I prove (f . fmap_m g) = (fmap_n g . f)?
> 
> Unless I'm utterly confused, that's (part of) the definition of a natural
> transformation (for non-category-theorists).
> 
> Alright, let's pretend I know nothing about natural transformations and just 
> have the type declaration
> 
> type m :-> n = (forall x. m x -> n x)
> 
> And I have
> f :: M :-> N
> g :: A -> B
> instance Functor M -- with proofs of functor laws
> instance Functor N -- with proofs of functor laws
> 
> How can I prove
>   fmap g. f :: M A -> N B
>   =
>   f . fmap g :: M A -> N B
> 
> I assume I need to make some sort of appeal to the parametricity of M :-> N. 
>  
> > Is there some
> > more fundamental law of natural transformations that I'm not aware of
> > that I need to use?  Is it possible to write a natural transformation
> > in Haskell that violates this law?
> >
> >   -- ryan
> 
> 
> ___
> 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] bindings for libvirt

2012-01-23 Thread Ilya Portnov
On 16 янв, 03:27, Michael Litchard  wrote:
> Due to the direction things are going at work, I have become
> interested in Haskell bindings forlibvirt. Noticed that this hasn't
> been done yet. I was wondering if this was due to lack of motivation,
> or if there were some difficult hurdles withlibvirtthat make the
> project cost-prohibitive. If it's the former, I don't see a problem
> proceeding with exploration. If it's the latter, I'd like to know what
> the hurdles are.

Hello.

For my current projects, i'd also like to have bindings to libvirt. I
even started to write something for them, using c2hs. If someone is
interested, i could put my current (very basic) code to, say, github…

Seems there will no big problems, but libvirt API is not so small, so
it'll take time to write full bindings.

WBR, Ilya Portnov.

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


Re: [Haskell-cafe] Natural Transformations and fmap

2012-01-23 Thread Ryan Ingram
On Mon, Jan 23, 2012 at 8:05 PM, Daniel Fischer <
daniel.is.fisc...@googlemail.com> wrote:

> On Tuesday 24 January 2012, 04:39:03, Ryan Ingram wrote:
> > At the end of that paste, I prove the three Haskell monad laws from the
> > functor laws and "monoid"-ish versions of the monad laws, but my proofs
> > all rely on a property of natural transformations that I'm not sure how
> > to prove; given
> >
> > type m :-> n = (forall x. m x -> n x)
> > class Functor f where fmap :: forall a b. (a -> b) -> f a -> f b
> > -- Functor identity law: fmap id = id
> > -- Functor composition law fmap (f . g) = fmap f . fmap g
> >
> > Given Functors m and n, natural transformation f :: m :-> n, and g :: a
> > -> b, how can I prove (f . fmap_m g) = (fmap_n g . f)?
>
> Unless I'm utterly confused, that's (part of) the definition of a natural
> transformation (for non-category-theorists).
>

Alright, let's pretend I know nothing about natural transformations and
just have the type declaration

type m :-> n = (forall x. m x -> n x)

And I have
f :: M :-> N
g :: A -> B
instance Functor M -- with proofs of functor laws
instance Functor N -- with proofs of functor laws

How can I prove
  fmap g. f :: M A -> N B
  =
  f . fmap g :: M A -> N B

I assume I need to make some sort of appeal to the parametricity of M :-> N.



> > Is there some
> > more fundamental law of natural transformations that I'm not aware of
> > that I need to use?  Is it possible to write a natural transformation
> > in Haskell that violates this law?
> >
> >   -- ryan
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Some thoughts on Type-Directed Name Resolution

2012-01-23 Thread Steve Horne
There's a proposal at the moment to add support for TDNR to Haskell - to 
leverage "the power of the dot" (e.g. for intellisense).


http://hackage.haskell.org/trac/haskell-prime/wiki/TypeDirectedNameResolution

I approve of the goal, but I'd like to suggest a different approach.

My basic idea is stolen from Bertrand Meyer (Object-Oriented Software 
Construction, second edition). Basically, a class *is* both a module and 
a type. Quote...


  Classes as modules

  Object orientation is primarily an architectural technique: its major 
effect is on the

  modular structure of software systems.

  The key role here is again played by classes. A class describes not 
just a type of

  objects but also a modular unit. In a pure object-oriented approach:

   Classes should be the only modules.

By the logic of equivalence relations, we can conclude that a type *is* 
a module. Only I'd adapt that a little. In C++, the following operators 
can all be used to access the "module" for some type or value...


 * ::   Scope resolution
 * .Member dereference
 * ->   Member dereference via a pointer
 * .*   Member-pointer dereference
 * ->*  Member-pointer dereference via a pointer

In C++, a type and an instance each have their own modules. A (smart) 
pointer has its own module, separate from the module for the type it 
points to. And member-pointers exist because sometimes there's a need to 
reference a member without knowing or (yet) caring which instance.


We already have member pointers - the functions that map an instance to 
the field value. It would make some sense if these could be placed in a 
module associated with the type (not the instance).


When an instance is created of a type, that can effectively (without 
run-time overhead) create a new module associated with the new instance. 
This will contain the same field-access functions, but with the instance 
parameter already curried in.


So there's no real need for any new meaning of the . operator - it's 
just access to names within a module. And there's no need for a new 
mechanism for accessing fields - only for a way to place them in that 
module scope, and a little sugar that gives us the same field-access 
function but with the instance parameter already curried in.


Once we have these modules containing compiler-generated field-access 
functions, though, it makes some sense to allow additional functions 
(and perhaps types) to be added within that types module explicitly by 
the programmer. It may also make sense to allow functions to be 
explicitly defined which will be added to the instance-modules and 
support the prefix-instance-parameter sugar.


Finally, as with C++, when dealing with IORef and similar, it make make 
sense to have a separate -> operator (spelled differently, of course). 
Or it could use the standard dot. C++ and D disagree in this (in C++, 
the smart pointer has its own module separate from the pointed-at 
instance - in D, there is no -> or equivalent).


As an aside, Ada has already gone through a related transition. The 
original Ada 83 had variant records, but no "true classes". In Ada 95, 
"tagged types" were added which were like variant records, but which 
supported inheritance and run-time dispatch. The discriminant is 
replaced by a "tag" which is presumably implemented as a virtual table 
pointer. However, functions and procedures weren't members. The typical 
call of a "method" would be...


packagename.procedure_name ( instance_arg, other_args );

Ada 2005 added some workarounds to allow conventional OOP call notation. 
See section 1.3 of the Ada 2005 rationale for details. However, it all 
feels a bit kludgy. In particular, the procedures and functions still 
aren't members - there are just some special rules for when they can be 
used as if they were. I've not actually used Ada 2005, but I'd bet some 
confusion can result from that.


Personally, I think Meyer was at least partly right - if types (and 
instances) are modules, the kludge-factor is much lower. C++ actually 
doesn't get this quite right IMO (you can access static class members 
through the instance objects, for example, not just through the 
classes), but C++ classes *do* act mostly like modules and that is a 
very useful trait - particularly within the declarative sublanguage 
(templates etc).


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


Re: [Haskell-cafe] [C][enums][newbie] What is natural Haskell representation of such enum?

2012-01-23 Thread Mike Burns
On 2012-01-23 13.45.50 -0800, David Barbour wrote:
> If your classes are more like `interfaces`, you could use Typeclasses to
> model them. Otherwise, look into OOHaskell. But I think your program
> architecture will simply be different in idiomatic Haskell than in
> idiomatic C++.

If your OO is very design patterned, and especially if it prefers
composition over inheritence, you can port it sorta directly, sometimes.

For example, all the classes that implement an interface become a sum
type, and their methods are functions that take a value of the sum type.

interface MusicCompilation { def trackListing() : [Song] }
class Record implements MusicCompilation { ... }
class BlogPost implements MusicCompilation { ... }

Could translate to

data MusicCompilation = Record [Song] | BlogPost [Song]

trackListing (Record xs) = xs
trackListing (BlogPost xs) = xs

The more your OO looks like C, the harder this will be.

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


Re: [Haskell-cafe] Natural Transformations and fmap

2012-01-23 Thread Daniel Fischer
On Tuesday 24 January 2012, 04:39:03, Ryan Ingram wrote:
> At the end of that paste, I prove the three Haskell monad laws from the
> functor laws and "monoid"-ish versions of the monad laws, but my proofs
> all rely on a property of natural transformations that I'm not sure how
> to prove; given
> 
> type m :-> n = (forall x. m x -> n x)
> class Functor f where fmap :: forall a b. (a -> b) -> f a -> f b
> -- Functor identity law: fmap id = id
> -- Functor composition law fmap (f . g) = fmap f . fmap g
> 
> Given Functors m and n, natural transformation f :: m :-> n, and g :: a
> -> b, how can I prove (f . fmap_m g) = (fmap_n g . f)?

Unless I'm utterly confused, that's (part of) the definition of a natural 
transformation (for non-category-theorists).

> Is there some
> more fundamental law of natural transformations that I'm not aware of
> that I need to use?  Is it possible to write a natural transformation
> in Haskell that violates this law?
> 
>   -- ryan


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


[Haskell-cafe] Natural Transformations and fmap

2012-01-23 Thread Ryan Ingram
I've been playing around with the relationship between monoids and monads
(see
http://www.jonmsterling.com/posts/2012-01-12-unifying-monoids-and-monads-with-polymorphic-kinds.htmland
http://blog.sigfpe.com/2008/11/from-monoids-to-monads.html), and I put
together my own implementation which I'm quite happy with, that you can see
at http://hpaste.org/56903 ; relying only on the extensions RankNTypes,
TypeOperators, NoImplicitPrelude, ScopedTypeVariables;

At the end of that paste, I prove the three Haskell monad laws from the
functor laws and "monoid"-ish versions of the monad laws, but my proofs all
rely on a property of natural transformations that I'm not sure how to
prove; given

type m :-> n = (forall x. m x -> n x)
class Functor f where fmap :: forall a b. (a -> b) -> f a -> f b
-- Functor identity law: fmap id = id
-- Functor composition law fmap (f . g) = fmap f . fmap g

Given Functors m and n, natural transformation f :: m :-> n, and g :: a ->
b, how can I prove (f . fmap_m g) = (fmap_n g . f)?  Is there some more
fundamental law of natural transformations that I'm not aware of that I
need to use?  Is it possible to write a natural transformation in Haskell
that violates this law?

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


Re: [Haskell-cafe] Finding longest common prefixes in a list

2012-01-23 Thread Gwern Branwen
On Sat, Jan 21, 2012 at 8:18 AM, Twan van Laarhoven  wrote:
> Notice that there are lots of "miku-X" prefixes found. This is probably not
> what you want. What exactly do you want the algorithm to do? For example, ""
> is obviously a prefix of every string, but it is not very long. On the other
> hand, each string is a prefix of itself, but that prefix is shared by only
> one string (usually).
>
> By the way, the sort and compare adjacent pairs approach corresponds to
> "atLeastThisManyDescendants 2".

Ah, now the code makes sense to me. It's longer, but it is a heck of a
lot more principled and readable, so I'm happy to replace my version
with yours. It's not too hard to convert it into a CLI filter with
optional depth (default of 2, replicating original behavior):

import qualified Data.Map as Map
import System.Environment (getArgs)
import Data.List (sortBy)
import Data.Ord (comparing)

main :: IO ()
main = do arg <- getArgs
  let n = if null arg then 2 else read (head arg) :: Int
  interact (unlines .  chunk n . lines)

chunk :: Int -> [String] -> [String]
chunk n = map prefix . sortByLength . atLeastThisManyDescendants n . fromList
  where sortByLength :: [CommonPrefix Char] -> [CommonPrefix Char]
sortByLength = sortBy (comparing (numDescendant . names))
.

And the results seem kosher (printing just the prefixes is probably
the best idea, but wouldn't be too hard to switch to printing full
filenames - just filter the original file list with the extracted
prefix from each CommonPrefix):

$ ls music/vocaloid/| runhaskell lcp.hs 5
miku-s
miku-t
miku-r
rin-
miku-a
gumi-
luka-
$ ls music/vocaloid/| runhaskell lcp.hs 4
miku-h
miku-m
miku-n
miku-p
miku-s
miku-t
miku-r
rin-
miku-a
gumi-
luka-
$ ls music/vocaloid/| runhaskell lcp.hs # with 2
chorus-
gumi-mo
gumi-s
kaito-
luka-emon
luka-t
miku-acolorlinkingworld-
miku-akayaka
miku-cleantears-remind2011natsu-
miku-dan
miku-ele
miku-galaxyodyssey-
miku-ha
miku-inn
miku-jemappelle-motion-
miku-kz-
miku-lo
miku-m@rk-
miku-plustellia-壁の彩度-
miku-ro
miku-se
miku-ta
miku-the
miku-tinyparadise-
miku-ジラートP-birthdayofeden-
miku-杯本選
miku-般若心経
niconicochorus-
yuki-
len-
luka-di
miku-re:package-
miku-n
rin-

-- 
gwern
http://www.gwern.net
import qualified Data.Map as Map
import System.Environment (getArgs)
import Data.List (sortBy)
import Data.Ord (comparing)

main :: IO ()
main = do arg <- getArgs
  let n = if null arg then 2 else read (head arg) :: Int
  interact (unlines .  chunk n . lines)

chunk :: Int -> [String] -> [String]
chunk n = map prefix . sortByLength . atLeastThisManyDescendants n . fromList
  where sortByLength :: [CommonPrefix Char] -> [CommonPrefix Char]
sortByLength = sortBy (comparing (numDescendant . names))

-- A trie datatype
data Trie a = Trie { numLeafs, numDescendant :: !Int
   , children :: Map.Map a (Trie a) }

instance (Show a) => Show (Trie a) where
showsPrec _ t = showString "fromList " . shows (toList t)

-- The empty trie
empty :: Trie a
empty = Trie 0 0 Map.empty

-- A trie that contains a single string
singleton :: Ord a => [a] -> Trie a
singleton [] = Trie 1 1 Map.empty
singleton (x:xs) = Trie 0 1 (Map.singleton x (singleton xs))

-- Merge two tries
merge :: Ord a => Trie a -> Trie a -> Trie a
merge (Trie l d c) (Trie l' d' c')
= Trie (l+l') (d+d') (Map.unionWith merge c c')

fromList :: Ord a => [[a]] -> Trie a
fromList = foldr (merge . singleton) empty

toList :: Trie a -> [[a]]
toList (Trie l _ c)
= replicate l []
++ [ x:xs | (x,t) <- Map.toList c, xs <- toList t ]

data CommonPrefix a = Prefix { prefix :: [a], names :: Trie a }

instance (Show a) => Show (CommonPrefix a) where
showsPrec _ (Prefix p ns) = shows p . showString " ++ " . shows (toList ns)

-- Find prefixes that have at least minD descendants.
-- when there is a prefix xs with >=minD descendants, then shorter prefixes will not be returned
atLeastThisManyDescendants :: Int -> Trie a -> [CommonPrefix a]
atLeastThisManyDescendants minD trie@(Trie _ d c)
| d < minD = [] -- too few descendants
| null forChildren = [Prefix [] trie] -- all longer prefixes have too few descendants, but this prefix doesn't
| otherwise = forChildren -- there are longer prefixes with enough descendants, return them
  where
forChildren = [ Prefix (x:pfx) nms
  | (x,t) <- Map.toList c
  , Prefix pfx nms <- atLeastThisManyDescendants minD t ]

{- *Main> mapM_ (print . prefix) $ atLeastThisManyDescendants 4 test1
   "gumi-"
   "luka-"
   "miku-a"
   "miku-h"
   "miku-m"
   "miku-n"
   "miku-p"
   "miku-r"
   "miku-s"
   "miku-t"
   "rin-"
test1 :: Trie Char
test1 = fromList
  ["chorus-kiminoshiranaimonogatari.ogg"
  ,"chorus-mrmusic.ogg"
  ,"choucho-lastnightgoodnight.ogg"
  ,"dylanislame-aikotoba.ogg"
  ,"electriclove-エレクトリック・ラブ-korskremix.ogg"
  ,"gumi-bacon8-justhangingaround.ogg"
  ,"gumi-iapologizetoyou.ogg"
  ,"gumi-montblanc.ogg"
  ,

Re: [Haskell-cafe] Efficient temporary file storage??

2012-01-23 Thread Krzysztof Skrzętnicki
>From my experience I can recommend msgpack (
http://hackage.haskell.org/package/msgpack) as being extremely fast. It
comes with optimized prepared instances for common data structures which is
very nice, because you don't have to roll your own version with library
like cereal (which is indeed very fast, but simply less convenient).

Best regards,
Krzysztof Skrzętnicki

On Tue, Jan 24, 2012 at 00:37, Nick Rudnick wrote:

> Dear all,
>
> if you want to temporarily store haskell data in a file – do you have a
> special way to get it done efficiently?
>
> In an offline, standalone app, I am continuously reusing data volumes of
> about 200MB, representing Map like tables of a rather simple structure,
>
> key: (Int,Int,Int)
> value: [((Int,Int),LinkId)]
>
>
> which take quite a good deal of time to produce.
>
> Is there a recommendation about how to 'park' such data tables most
> efficiently in files – any format acceptable, quick loading time is the
> most desirable thing.
>
> Thanks a lot in advance, Nick
>
> ___
> 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] Efficient temporary file storage??

2012-01-23 Thread Felipe Almeida Lessa
On Mon, Jan 23, 2012 at 9:37 PM, Nick Rudnick
 wrote:
> if you want to temporarily store haskell data in a file – do you have a
> special way to get it done efficiently?
>
> In an offline, standalone app, I am continuously reusing data volumes of
> about 200MB, representing Map like tables of a rather simple structure,
>
> key: (Int,Int,Int)
> value: [((Int,Int),LinkId)]
>
>
> which take quite a good deal of time to produce.
>
> Is there a recommendation about how to 'park' such data tables most
> efficiently in files – any format acceptable, quick loading time is the most
> desirable thing.

Use cereal [1], usually it's fast and easy enough.  If you need to be
able to access your files for a long time, consider using safecopy [2]
(which internally uses cereal as well).

[1] http://hackage.haskell.org/package/cereal
[2] http://hackage.haskell.org/package/safecopy

HTH,

-- 
Felipe.

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


[Haskell-cafe] Efficient temporary file storage??

2012-01-23 Thread Nick Rudnick
Dear all,

if you want to temporarily store haskell data in a file – do you have a
special way to get it done efficiently?

In an offline, standalone app, I am continuously reusing data volumes of
about 200MB, representing Map like tables of a rather simple structure,

key: (Int,Int,Int)
value: [((Int,Int),LinkId)]


which take quite a good deal of time to produce.

Is there a recommendation about how to 'park' such data tables most
efficiently in files – any format acceptable, quick loading time is the
most desirable thing.

Thanks a lot in advance, Nick
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [C][enums][newbie] What is natural Haskell representation of such enum?

2012-01-23 Thread David Barbour
If you want a simple translation, use Word8 (from Data.Word) for the type
and use Data.Bits for operations on it just like in C++. This would offer
you storage efficiency (if stored as a strict field).

If you want idiomatic Haskell, constructor of the form:

  data ObjectType = Object | Item | Container | Unit | Player, etc.

Then simply put intelligence into the `isContainer` or `toWord8`, etc.
translations. This latter approach will be more extensible in the long run,
since you might find you want some parameterized object types.

Re: OO Classes and Haskell

If your classes are more like `interfaces`, you could use Typeclasses to
model them. Otherwise, look into OOHaskell. But I think your program
architecture will simply be different in idiomatic Haskell than in
idiomatic C++.

Regards,

Dave


On Mon, Jan 23, 2012 at 1:14 PM, Daniel Hlynskyi wrote:

> Thanks. This and previous email are answers to question I asked. But not
> the answer to question I mean.
> I'll describe the whole task, as Yves Parès suggested.
>
> I'm trying to convert C++ code to Haskell. I have such hierarchy: class
> Object, class Item : Object, class Container : Item. Another one example:
> class Unit : Object, class Player : Unit. Each constructor do things like
> this:
>
> Object::Object()
> {
> objectType= TYPEMASK_OBJECT;
> // ... lots of code ...
> }
>
>
> Item::Item()
> {
> objectType |= TYPEMASK_ITEM;
> // ...
> }
>
> Container::Container(): Item()
> {
> objectType |= (TYPEMASK_ITEM | TYPEMASK_CONTAINER);
> // ...
> }
>
>
> What is objectType? This field is used when a networksend packet is
> created. In the packet it is 1 byte of flags, so it is in object hierarchy.
>
> So the question was: what type should objectType field have in Haskell? I
> think it must not mimic enum. What the structure have I to use? There is
> one more problem - there may be lots of objects, lots of, so memory
> efficiency is also suggested.
> And side question: what to do with classes? =) Maybe there is simple rule
> to convert OO hierarchy to FP.
>
> 23 січня 2012 р. 12:15 Malcolm Wallace  написав:
>
>
>> > 2012/1/22 Данило Глинський 
>> > What is natural Haskell representation of such enum?
>> >
>> > enum TypeMask
>> > {
>> >UNIT,
>> >GAMEOBJECT,
>> >
>> >CREATURE_OR_GAMEOBJECT = UNIT | GAMEOBJECT
>> > };
>>
>> I don't think that definition makes any sense in C, because UNIT is 0, so
>> UNIT | GAMEOBJECT == GAMEOBJECT == 1
>>
>> Nevertheless, in Haskell something vaguely similar might be:
>>
>> data TypeMask = UNIT | GAMEOBJECT | CREATURE_OR_GAMEOBJECT
>>
>> > // 1-byte flaged enum
>> > enum TypeMask
>> > {
>> >// ...
>> >UNIT= 0x0004,
>> >GAMEOBJECT  = 0x0008,
>> >// ...
>> >
>> >CREATURE_OR_GAMEOBJECT = UNIT | GAMEOBJECT
>> >WORLDOBJECT = UNIT | PLAYER | GAMEOBJECT | DYNAMICOBJECT | CORPSE
>> >// ... even more enum combos ...
>> > };
>>
>> import Data.Bits
>> data TypeMask = UNIT | GAMEOBJECT | CREATURE_OR_GAMEOBJECT | WORLDOBJECT
>> instance Enum TypeMask where
>>fromEnum UNIT = 0x4
>>fromEnum GAMEOBJECT = 0x8
>>fromEnum CREATURE_OR_GAMEOBJECT = fromEnum UNIT .|. fromEnum GAMEOBJECT
>>fromEnum WORLDOBJECT = fromEnum UNIT .|. fromEnum PLAYER .|. fromEnum
>> GAMEOBJECT
>>   .|. fromEnum DYNAMICOBJECT .|. fromEnum CORPSE
>>
>>toEnum 0x4 = UNIT
>>toEnum 0x8 = GAMEOBJECT
>>toEnum _   = error "unspecified enumeration value of type TypeMask"
>>
>> isCreatureOrGameObject :: Int -> Bool
>> isCreatureOrGameObject x = (x .|. fromEnum CREATURE_OR_GAMEOBJECT) /= 0
>>
>> isWorldObject :: Int -> Bool
>> isWorldObject x = (x .|. fromEnum WORLDOBJECT) /= 0
>>
>> -- But fundamentally, this is not an idiomatic Haskell way of doing
>> things.
>> -- The other posts in this thread have shown more Haskell-ish
>> translations.
>>
>>
>>
>
> ___
> 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] Monads, do and strictness

2012-01-23 Thread David Barbour
Space leaks, time leaks, resource leaks, subtle divergence issues when
filtering lists, etc.

On Mon, Jan 23, 2012 at 11:57 AM, Jake McArthur wrote:

> On Mon, Jan 23, 2012 at 10:45 AM, David Barbour 
> wrote:
> > the repeated failures of attempting to model stream processing with
> infinite
> > lists,
>
> I'm curious about what failures you're talking about.
>
> - Jake
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [C][enums][newbie] What is natural Haskell representation of such enum?

2012-01-23 Thread Daniel Hlynskyi
Thanks. This and previous email are answers to question I asked. But not
the answer to question I mean.
I'll describe the whole task, as Yves Parès suggested.

I'm trying to convert C++ code to Haskell. I have such hierarchy: class
Object, class Item : Object, class Container : Item. Another one example:
class Unit : Object, class Player : Unit. Each constructor do things like
this:

Object::Object()
{
objectType= TYPEMASK_OBJECT;
// ... lots of code ...
}


Item::Item()
{
objectType |= TYPEMASK_ITEM;
// ...
}

Container::Container(): Item()
{
objectType |= (TYPEMASK_ITEM | TYPEMASK_CONTAINER);
// ...
}


What is objectType? This field is used when a networksend packet is
created. In the packet it is 1 byte of flags, so it is in object hierarchy.

So the question was: what type should objectType field have in Haskell? I
think it must not mimic enum. What the structure have I to use? There is
one more problem - there may be lots of objects, lots of, so memory
efficiency is also suggested.
And side question: what to do with classes? =) Maybe there is simple rule
to convert OO hierarchy to FP.

23 січня 2012 р. 12:15 Malcolm Wallace  написав:

>
> > 2012/1/22 Данило Глинський 
> > What is natural Haskell representation of such enum?
> >
> > enum TypeMask
> > {
> >UNIT,
> >GAMEOBJECT,
> >
> >CREATURE_OR_GAMEOBJECT = UNIT | GAMEOBJECT
> > };
>
> I don't think that definition makes any sense in C, because UNIT is 0, so
> UNIT | GAMEOBJECT == GAMEOBJECT == 1
>
> Nevertheless, in Haskell something vaguely similar might be:
>
> data TypeMask = UNIT | GAMEOBJECT | CREATURE_OR_GAMEOBJECT
>
> > // 1-byte flaged enum
> > enum TypeMask
> > {
> >// ...
> >UNIT= 0x0004,
> >GAMEOBJECT  = 0x0008,
> >// ...
> >
> >CREATURE_OR_GAMEOBJECT = UNIT | GAMEOBJECT
> >WORLDOBJECT = UNIT | PLAYER | GAMEOBJECT | DYNAMICOBJECT | CORPSE
> >// ... even more enum combos ...
> > };
>
> import Data.Bits
> data TypeMask = UNIT | GAMEOBJECT | CREATURE_OR_GAMEOBJECT | WORLDOBJECT
> instance Enum TypeMask where
>fromEnum UNIT = 0x4
>fromEnum GAMEOBJECT = 0x8
>fromEnum CREATURE_OR_GAMEOBJECT = fromEnum UNIT .|. fromEnum GAMEOBJECT
>fromEnum WORLDOBJECT = fromEnum UNIT .|. fromEnum PLAYER .|. fromEnum
> GAMEOBJECT
>   .|. fromEnum DYNAMICOBJECT .|. fromEnum CORPSE
>
>toEnum 0x4 = UNIT
>toEnum 0x8 = GAMEOBJECT
>toEnum _   = error "unspecified enumeration value of type TypeMask"
>
> isCreatureOrGameObject :: Int -> Bool
> isCreatureOrGameObject x = (x .|. fromEnum CREATURE_OR_GAMEOBJECT) /= 0
>
> isWorldObject :: Int -> Bool
> isWorldObject x = (x .|. fromEnum WORLDOBJECT) /= 0
>
> -- But fundamentally, this is not an idiomatic Haskell way of doing things.
> -- The other posts in this thread have shown more Haskell-ish translations.
>
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] where to put general-purpose utility functions

2012-01-23 Thread Joey Hess
David Fox wrote:
> I try to create a workflow for this sort of thing.  I create a package
> with a name like set-extra, with one module Data.Set.Extra and an
> alternative Data.Set module that exports both the old Data.Set and the
> symbols in Data.Set.Extra.  Then I email the maintainers of the
> Containers package with a suggestion.  After a while I upload
> set-extra to hackage if I need to use set-extra in another hackage
> package.

Thanks, that's the most helpful hint.
It matches MissingH's use of .Utils modules too.

Jean-Marie Gaillourdet wrote:
> Personally, I've always been avoiding those grab-bags of functionality like
> MissingH and other libraries. Not because I think they don't provide anything
> useful. But, because their level of maintenance is not clear to me. A rather
> large library of utility functions tends to need many dependencies on other
> hackage packages. That makes the question of maintenance even more important.

It's not clear to me either. I used MissingH starting out because I
personally know and trust John and/or he cowrote RWH.
Don't know that I would have otherwise.

(And I only use Data.String.Utils, System.Cmd.Utils, and Data.Bits.Utils
from it.)

> As others have pointed out some of your functions may already exist in some
> widely used package. And other might be easy to be replaced by some idiom. 
> Don't
> underestimate the depth of Haskell and it's well thought libraries. I am
> regularly amazed by finding some new way to combine seemingly trivial 
> functions
> to do some non-trivial task. Every time that happens I can remove some of my
> utility functions.

Well, this is certianly true, on the other hand then you end up with a
pattern of repeatedly combining some trivial functions in a certian way,
and it then makes sense to formalize that. It's better to have `fromMaybe`
than to repeatedly use `id` with `maybe`.

Tristan Ravitch wrote:
> >   whenM :: Monad m => m Bool -> m () -> m ()   -- also >>?
> >   unlessM :: Monad m => m Bool -> m () -> m () -- also >>!
> >   firstM :: Monad m => (a -> m Bool) -> [a] -> m (Maybe a)
> 
> IfElse 
> (http://hackage.haskell.org/packages/archive/IfElse/0.85/doc/html/Control-Monad-IfElse.html)
> has a few of these.

whenM is in a dozen packages, the others fewer but scattered here and
there. I also found >>? and >>! somewhere on hackage once but not sure
where.

> >   Various path manipulation functions such as:
> >   absPath :: FilePath -> IO FilePath
> 
> Is this different from canonicalizePath in directory?

Yes; it doesn't require the path to exist.

> >   Other stuff:
> >
> >   separate :: (a -> Bool) -> [a] -> ([a], [a])
> 
> Is this partition from Data.List?

No; it's like break but does not include the separating character in the
snd list.

> >   format :: Format -> Variables -> String
> 
> This looks like it might be similar to HStringTemplate

This particular format allows for things like "${foo} ${bar;10} ${baz;-10}\n"
so it's sort of printf like, but not entirely.

> >   withTempFile :: Template -> (FilePath -> Handle -> IO a) -> IO a
> 
> temporary 
> (http://hackage.haskell.org/packages/archive/temporary/1.1.2.3/doc/html/System-IO-Temp.html)
> has a few variants of this one

Indeed, however all its functions can fail if getTemporaryDirectory
fails; this one puts the temp file in "." in that case.

Simon Hengel wrote:
> >   headMaybe :: [a] -> Maybe a
> 
> Is this the same as Data.Maybe.maybeToList?

Rather listToMaybe.. it is the same as that in fact.
Though I also have a lastMaybe that does not have an equivilant in Data.Maybe.

> >   readMaybe :: Read a => String -> Maybe a
> 
> This has been added to base recently [1].

Great! Although there are multiple ways to choose to implement this. 
I found it useful to make it succeed even if not all the string was
consumed, or when there are multiple valid results. I've renamed
mine readish.

-- 
eee shy jo


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


Re: [Haskell-cafe] ghc-api Static Semantics?

2012-01-23 Thread Ozgur Akgun
Hi,

I don't know what you actually need, but if haskell-src-exts is an option,
it is quite a bit easier to use (definitely easier to understand for me!).
Especially when used together with Uniplate.

For example, for a given piece of AST one can get all the identifiers used
like so:

[ x | Ident x <- universeBi ast ]

Finding where they are bound shouldn't be very hard either.

Hope this helps,
Ozgur

On 23 January 2012 17:33, Christopher Brown  wrote:

> Hi,
>
> I was wondering if anyone could tell me if it's possible to get an AST
> from the ghc-api decorated with static-semantics?
> In particular, I am interested in use and bind locations for all names in
> the AST together with the module they are bound, etc.
>
> Looking through the online docs, there doesn't seem to be a way to do this.
> Even if I can tell from the AST where a variable is bound that would be
> enough,  if this is by making all names unique and qualified that would be
> better than nothing.
>
> Hope someone can help,
> Chris.
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monads, do and strictness

2012-01-23 Thread Jake McArthur
On Mon, Jan 23, 2012 at 10:45 AM, David Barbour  wrote:
> the repeated failures of attempting to model stream processing with infinite
> lists,

I'm curious about what failures you're talking about.

- Jake

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


[Haskell-cafe] ghc-api Static Semantics?

2012-01-23 Thread Christopher Brown
Hi,

I was wondering if anyone could tell me if it's possible to get an AST from the 
ghc-api decorated with static-semantics? 
In particular, I am interested in use and bind locations for all names in the 
AST together with the module they are bound, etc.

Looking through the online docs, there doesn't seem to be a way to do this. 
Even if I can tell from the AST where a variable is bound that would be enough, 
 if this is by making all names unique and qualified that would be better than 
nothing.

Hope someone can help,
Chris.

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


Re: [Haskell-cafe] Monads, do and strictness

2012-01-23 Thread David Barbour
Thanks for the reference. I base my opinion on my own observations - e.g.
the repeated failures of attempting to model stream processing with
infinite lists, the relative success of modeling exceptions explicitly with
monads compared to use of `fail` or SomeException, etc..

On Mon, Jan 23, 2012 at 6:29 AM, Sebastian Fischer wrote:

> On Sun, Jan 22, 2012 at 5:25 PM, David Barbour 
> wrote:
> > The laws for monads only apply to actual values and combinators of the
> monad algebra
>
> You seem to argue that, even in a lazy language like Haskell,
> equational laws should be considered only for values, as if they where
> stated for a total language. This kind of reasoning is called "fast
> and loose" in the literature and the conditions under which it is
> justified are established by Danielsson and others:
>
>
> http://www.cse.chalmers.se/~nad/publications/danielsson-et-al-popl2006.html
>
> Sebastian
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monads, do and strictness

2012-01-23 Thread Sebastian Fischer
On Sun, Jan 22, 2012 at 5:25 PM, David Barbour  wrote:
> The laws for monads only apply to actual values and combinators of the monad 
> algebra

You seem to argue that, even in a lazy language like Haskell,
equational laws should be considered only for values, as if they where
stated for a total language. This kind of reasoning is called "fast
and loose" in the literature and the conditions under which it is
justified are established by Danielsson and others:

http://www.cse.chalmers.se/~nad/publications/danielsson-et-al-popl2006.html

Sebastian

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


[Haskell-cafe] ANN: OpenCL 1.0.3.0 package

2012-01-23 Thread Luis Cabellos
Hello,

I update the OpenCL package with the last changes. The most important
thing, currently it fully implements OpenCL 1.0.

IMPORTANT, some functions change signature (e,g: clSetKernelArg, and
clCreateContext* )

Thanks all comments in the previous version, issues and pulls in github.

# Where to get it

* Hackage page (http://hackage.haskell.org/package/OpenCL)
* Repository (https://github.com/zhensydow/opencl)
* Bugs (https://github.com/zhensydow/opencl/issues)

# Changes

 * Move to Control.Parallel.OpenCL  (thanks Jason Dagit)
 * Added Image functions
 * Added clExecuteNativeKernel
 * Fixes on Windows, Macos and Linux versions (thanks Anthony Cowley,
ehird, axman6)
 * Fix bug with preprocessor code in OpenCL source code
 * Fix clSetKernelArg to allow cannot specify size of local memory arrays

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


Re: [Haskell-cafe] Contributing to http-conduit

2012-01-23 Thread Michael Snoyman
On Mon, Jan 23, 2012 at 1:20 PM, Aristid Breitkreuz
 wrote:
> Rejecting cookies is not without precedent.
>
> If you must force cookie handling upon us, at least make it possible to
> selectively reject them.
>
> Aristid

If you turn off automatic redirects, then you won't have cookie
handling. I'd be interested to hear of a use case where you would want
to avoid passing cookies after a redirect.

Michael

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


Re: [Haskell-cafe] Contributing to http-conduit

2012-01-23 Thread Aristid Breitkreuz
Rejecting cookies is not without precedent.

If you must force cookie handling upon us, at least make it possible to
selectively reject them.

Aristid
Am 23.01.2012 08:44 schrieb "Michael Snoyman" :

> That's a violation of the spec. Having a server set a cookie and then
> "not really mean it" or something along those lines would be invalid.
> And having a server not set a cookie at all means having this feature
> would be irrelevant.
>
> On Mon, Jan 23, 2012 at 9:42 AM, Aristid Breitkreuz
>  wrote:
> > Indeed, I disagree on 2. Sometimes there is an API and cookies are just
> not
> > part of it (and redirects are).
> >
> > Aristid
> >
> > Am 23.01.2012 08:16 schrieb "Michael Snoyman" :
> >
> >> The only times cookies would be used would be:
> >>
> >> 1. If you explicitly use it.
> >> 2. If you have redirects turned on, and a page that redirects you also
> >> sets a cookie.
> >>
> >> I would think that we would want (2) to be on regardless of user
> >> setting, do you disagree?
> >>
> >> Michael
> >>
> >> On Mon, Jan 23, 2012 at 8:46 AM, Aristid Breitkreuz
> >>  wrote:
> >> > Just make sure Cookie handling can be disabled completely.
> >> >
> >> > Aristid
> >> >
> >> > Am 23.01.2012 07:44 schrieb "Michael Snoyman" :
> >> >>
> >> >> On Mon, Jan 23, 2012 at 8:31 AM, Myles C. Maxfield
> >> >>  wrote:
> >> >> > 1. Oops - I overlooked the fact that the redirectCount attribute
> of a
> >> >> > Request is exported (it isn't listed on the documentation probably
> >> >> > because
> >> >> > the constructor itself isn't exported. This seems like a flaw in
> >> >> > Haddock...). Silly me. No need to export httpRaw.
> >> >> >
> >> >> > 2. I think that stuffing many arguments into the 'http' function is
> >> >> > ugly.
> >> >> > However, I'm not sure that the number of arguments to 'http' could
> >> >> > ever
> >> >> > reach an unreasonably large amount. Perhaps I have bad foresight,
> but
> >> >> > I
> >> >> > personally feel that adding cookies to the http request will be the
> >> >> > last
> >> >> > thing that we will need to add. Putting a bound on this growth of
> >> >> > arguments
> >> >>
> >> >> I completely disagree here. If we'd followed this approach, rawBody,
> >> >> decompress, redirectCount, and checkStatus all would have been
> >> >> arguments. There's a reason we use a settings data type[1] here.
> >> >>
> >> >> [1] http://www.yesodweb.com/blog/2011/10/settings-types
> >> >>
> >> >> > makes me more willing to think about this option. On the other
> hand,
> >> >> > using a
> >> >> > BrowserAction to modify internal state is very elegant. Which
> >> >> > approach
> >> >> > do
> >> >> > you think is best? I think I'm leaning toward the upper-level
> Browser
> >> >> > module
> >> >> > idea.
> >> >> >
> >> >> > If there was to be a higher-level HTTP library, I would argue that
> >> >> > the
> >> >> > redirection code should be moved into it, and the only high-level
> >> >> > function
> >> >> > that the Network.HTTP.Conduit module would export is 'http' (or
> >> >> > httpRaw).
> >> >> > What do you think about this?
> >> >>
> >> >> I actually don't want to move the redirection code out from where it
> >> >> is right now. I think that redirection *is* a basic part of HTTP. I'd
> >> >> be more in favor of just bundling cookies in with the current API,
> >> >> possibly with the IORef approach I'd mentioned (unless someone wants
> >> >> to give a different idea). Having a single API that provides both
> >> >> high-level and low-level approaches seems like a win to me.
> >> >>
> >> >> Michael
> >> >>
> >> >> ___
> >> >> 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] where to put general-purpose utility functions

2012-01-23 Thread Jean-Marie Gaillourdet
Hi,

On 21.01.2012, at 21:20, Joey Hess wrote:

> My problem now is that as I start new projects, I want to have my haskell
> utility functions available, and copying them around is not ideal. So, put
> them on hackage. But where, exactly? It already has several grab bag utility
> libraries. The only one with much traction is MissingH. Using the others
> makes a program have an unusual dependency, which while only a cabal
> install away, would make work for distributions that want to package the
> program. I've ruled out using a couple on that basis. Doesn't encourage me
> to add another one.
> 
> My 2000+ lines of reusable code are a grab-bag of generic utility
> functions. Looking them over (see Appendix), I could try to get portions
> into existing libraries on hackage, but it's unlikely I'd find a home
> for most of them, so I'm still left with this problem of what to do.
> 
> I wonder if the model used for xmonad-contrib, of a big library package,
> that is very open to additions from contributors, would be helpful here?
> 
> John, any interest in moving MissingH in this direction? I get the
> impression it's not otherwise changing much lately, and parts of it are
> becoming naturally obsolete, maybe this could inject some life into it.
> Any other thoughts you have on grab-bag utility libraries on hackage
> also appreciated.

Personally, I've always been avoiding those grab-bags of functionality like 
MissingH and other libraries. Not because I think they don't provide anything 
useful. But, because their level of maintenance is not clear to me. A rather 
large library of utility functions tends to need many dependencies on other 
hackage packages. That makes the question of maintenance even more important. 

As others have pointed out some of your functions may already exist in some 
widely used package. And other might be easy to be replaced by some idiom. 
Don't underestimate the depth of Haskell and it's well thought libraries. I am 
regularly amazed by finding some new way to combine seemingly trivial functions 
to do some non-trivial task. Every time that happens I can remove some of my 
utility functions.

Therefore, I would reuse my own collection of utility code as a separate 
repository to be included as a sub repository in other projects. Mercurial and 
Git support that very well, I am not sure about darcs' support for that. This 
approach allows you to avoid copy&paste reuse and it allows you to evolve your 
personal collection at your speed without worrying for backwards compatibility 
or API changes.

Publishing a library on hackage comes --- at least in an ideal world --- with 
some commitment to document it, keep it compiling and working with a set of 
compiler and library permutations, fix bugs and so on. In short it comes with a 
commitment to maintain it. At least for some time. If you would just like to 
drop some pile of code in hope someone will find it useful. Do that, but 
perhaps there might be better places for that than hackage.

Cheers,
  Jean



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


Re: [Haskell-cafe] Can't install hspec

2012-01-23 Thread Malcolm Wallace

On 23 Jan 2012, at 07:01, Erik de Castro Lopo wrote:

>/tmp/hspec-0.9.04062/hspec-0.9.0/Setup.lhs:2:10:
>Could not find module `System'
>It is a member of the hidden package `haskell98-2.0.0.0'.

In ghc-7.2, you cannot use the haskell98 package in conjunction with the base 
package.  The simplest solution is the replace the "import System" with the 
appropriate replacement module in base: most probably System.Environment, 
System.Exit, or similar.

Regards,
Malcolm

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


Re: [Haskell-cafe] [C][enums][newbie] What is natural Haskell representation of such enum?

2012-01-23 Thread Malcolm Wallace

> 2012/1/22 Данило Глинський 
> What is natural Haskell representation of such enum?
> 
> enum TypeMask
> {
>UNIT,
>GAMEOBJECT,
> 
>CREATURE_OR_GAMEOBJECT = UNIT | GAMEOBJECT
> };

I don't think that definition makes any sense in C, because UNIT is 0, so UNIT 
| GAMEOBJECT == GAMEOBJECT == 1

Nevertheless, in Haskell something vaguely similar might be:

data TypeMask = UNIT | GAMEOBJECT | CREATURE_OR_GAMEOBJECT

> // 1-byte flaged enum
> enum TypeMask
> {
>// ...
>UNIT= 0x0004,
>GAMEOBJECT  = 0x0008,
>// ...
> 
>CREATURE_OR_GAMEOBJECT = UNIT | GAMEOBJECT
>WORLDOBJECT = UNIT | PLAYER | GAMEOBJECT | DYNAMICOBJECT | CORPSE 
>// ... even more enum combos ...
> };

import Data.Bits
data TypeMask = UNIT | GAMEOBJECT | CREATURE_OR_GAMEOBJECT | WORLDOBJECT
instance Enum TypeMask where
fromEnum UNIT = 0x4
fromEnum GAMEOBJECT = 0x8
fromEnum CREATURE_OR_GAMEOBJECT = fromEnum UNIT .|. fromEnum GAMEOBJECT
fromEnum WORLDOBJECT = fromEnum UNIT .|. fromEnum PLAYER .|. fromEnum 
GAMEOBJECT
   .|. fromEnum DYNAMICOBJECT .|. fromEnum CORPSE

toEnum 0x4 = UNIT
toEnum 0x8 = GAMEOBJECT
toEnum _   = error "unspecified enumeration value of type TypeMask"

isCreatureOrGameObject :: Int -> Bool
isCreatureOrGameObject x = (x .|. fromEnum CREATURE_OR_GAMEOBJECT) /= 0

isWorldObject :: Int -> Bool
isWorldObject x = (x .|. fromEnum WORLDOBJECT) /= 0

-- But fundamentally, this is not an idiomatic Haskell way of doing things.
-- The other posts in this thread have shown more Haskell-ish translations.



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