[Haskell-cafe] HTTP client library supporting Server sent events ?

Alexandre Mazari scaroo at gmail.com
Wed Apr 29 13:07:09 UTC 2015


In an effort to build an Haskell client library for the Firebase service
[0], which rely heavily on HTTP event source/server sent events [1], I am
looking for an HTTP client lib supporting this spec.

AFAIK, both WAI and yesod handle the mechanism server-side but nor
http-client, wreq or http-streams seem to provide the client counterpart.

Am I looking in the wrong direction?

SSE are basically '\n' separated yaml messages over a kept open http
response stream. I guess a seasoned Haskell dev could build a solution
quite easily but o couldn't find a way to keep the response stream opened.

Ideally a conduit/pipe sink exposing each message could be exposed for
further parsing and usage.

I'd be very glassful of someone could help me contribute such handling or
come up with a solution.

Thanks for your time,
Alexandre

[0] https://www.firebase.com/docs/rest/api/
[1] http://www.w3.org/TR/2011/WD-eventsource-20110208/
Le 29 avr. 2015 14:02, <haskell-cafe-request at haskell.org> a écrit :

Send Haskell-Cafe mailing list submissions to
        haskell-cafe at haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
or, via email, send a message with subject or body 'help' to
        haskell-cafe-request at haskell.org

You can reach the person managing the list at
        haskell-cafe-owner at haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Haskell-Cafe digest..."


Today's Topics:

   1. Re: Coplanarity or Colinearity [Was: low-cost matrix      rank?]
      (Richard A. O'Keefe)
   2. Re: Prime sieve and Haskell demo (Doug McIlroy)
   3. Re: Prime sieve and Haskell demo (Kim-Ee Yeoh)
   4. Wiki user (fr33domlover)
   5. Re: Wiki user (Henk-Jan van Tuyl)
   6. Re: Wiki user (fr33domlover)
   7. Re: dependent types, singleton types.... (Richard Eisenberg)


----------------------------------------------------------------------

Message: 1
Date: Wed, 29 Apr 2015 13:14:36 +1200
From: "Richard A. O'Keefe" <ok at cs.otago.ac.nz>
To: Mike Meyer <mwm at mired.org>
Cc: Haskell-Cafe <Haskell-Cafe at haskell.org>
Subject: Re: [Haskell-cafe] Coplanarity or Colinearity [Was: low-cost
        matrix  rank?]
Message-ID: <28B3FCD1-5BE8-4769-8BA9-A20D8426F4C2 at cs.otago.ac.nz>
Content-Type: text/plain; charset=us-ascii


On 26/04/2015, at 1:53 am, Mike Meyer <mwm at mired.org> wrote:
> My real problem is that I've got a list of points in R3  and want to
decide if they determine a plane, meaning they are coplanar but not
colinear. Similarly, given a list of points in R2, I want to verify that
they aren't colinear. Both of these can be done by converting the list of
points to a matrix and finding the rank of the matrix, but I only use the
rank function in the definitions of colinear and coplanar.

To compute the rank of a matrix,
perform elementary row operations
until the matrix is left in echelon form;
the number of nonzero rows remaining in
the reduced matrix is the rank.

(
http://www.cliffsnotes.com/math/algebra/linear-algebra/real-euclidean-vector-spaces/the-rank-of-a-matrix
)

A matrix is in row echelon form when it
satisfies the following conditions:
* The first non-zero element in each row,
  called the leading entry, is 1
* Each leading entry is in a column to
  the right of the leading entry in the
  previous row
* Rows with all zero elements, if any,
  are below rows having a non-zero element.

(http://stattrek.com/matrix-algebra/echelon-transform.aspx)
Row echelon forms aren't unique, but for determining
the rank of a matrix, that doesn't matter.

Code working on a list of points left as an exercise for
the reader.



------------------------------

Message: 2
Date: Tue, 28 Apr 2015 21:36:52 -0400
From: Doug McIlroy <doug at cs.dartmouth.edu>
To: haskell-cafe at haskell.org
Subject: Re: [Haskell-cafe] Prime sieve and Haskell demo
Message-ID: <201504290136.t3T1aqI1020799 at coolidge.cs.dartmouth.edu>
Content-Type: text/plain; charset=us-ascii

With deep apologies for sending the wrong file, I try again.

Doug

>> How about simply changing `sieve` to `trialDiv`?  It's not that I
>> don't like the given example, because it gives a very small use case
>> for laziness that is difficult enough to reproduce in an eagerly
>> evaluated language.
>
> Is it really so difficult to reproduce in a strict language? Here is
> that Haskell example in OCaml
>
> let primes =
>   let rec trialDiv (Cons (p,xs)) =
>     Cons (p, lazy (trialDiv @@ filter (fun x -> x mod p <> 0) @@
Lazy.force xs))
>   in trialDiv @@ iota 2

I'm afraid I don't understand why the program isn't a sieve. Is
the concern that the sequence of integers is thinned by dropping
composites rather than by merely marking them and counting across
them? Or is it that a trace of lazy evaluation will show that all
the divisibility tests on a single integer are clustered together
in time? Or something I haven't thought of?

Of course the program can be written in any Turing-complete language,
but the effort is likely to cause beads of sweat, like "lazy",
"force", or "spawn" to be shed on the algorithmic pearl. The sieve
can even be written succinctly as a bash shell script (below),
which exhibits warts (e.g. five flavors of parentheses) but no sweat.

Though both the Ocaml and the shell code are compact, neither dulls
the luster that lazy evaluation imparts to the Haskell.

    sift() {
        while true; do
            read p
            if (( $p % $1 != 0 )); then echo $p; fi
        done }

    sink() { read p; echo $p; sift $p | sink }

    seq 2 1000000 | sink



------------------------------

Message: 3
Date: Wed, 29 Apr 2015 09:42:03 +0700
From: Kim-Ee Yeoh <ky3 at atamo.com>
To: Doug McIlroy <doug at cs.dartmouth.edu>
Cc: Haskell Cafe <haskell-cafe at haskell.org>
Subject: Re: [Haskell-cafe] Prime sieve and Haskell demo
Message-ID:
        <CAPY+ZdQsu4iotcjO7wRwqsLg34jnoQ7rhHWQ=rYwYBOVBnUj4g at mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

On Wed, Apr 29, 2015 at 8:36 AM, Doug McIlroy <doug at cs.dartmouth.edu> wrote:

> I'm afraid I don't understand why the program isn't a sieve. Is
> the concern that the sequence of integers is thinned by dropping
> composites rather than by merely marking them and counting across
> them? Or is it that a trace of lazy evaluation will show that all
> the divisibility tests on a single integer are clustered together
> in time? Or something I haven't thought of?
>

When I reread Ertugrul's original email, I see that he's alerting to the
danger of derision. There will be people who will mock Haskell for having
an un-performant and un-Eratosthenian non-sieve on its front page.

As in, Haskell people don't even know their basic math, ha ha.

It used to be fibonaccis. That's too inviting of derision. Primes are more
noble, so the thinking goes.

That very small space on the face of Haskell must perform incredible
duties. Among them, it has to showcase beautiful syntax, see:

https://github.com/haskell-infra/hl/issues/46#issuecomment-72331664

HTH,
-- Kim-Ee
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <
http://mail.haskell.org/pipermail/haskell-cafe/attachments/20150429/7bf2d4e8/attachment-0001.html
>

------------------------------

Message: 4
Date: Wed, 29 Apr 2015 09:07:36 +0300
From: fr33domlover <fr33domlover at riseup.net>
To: "Haskell-Cafe" <haskell-cafe at haskell.org>
Subject: [Haskell-cafe] Wiki user
Message-ID: <mailman.8.1430308802.9745.haskell-cafe at haskell.org>
Content-Type: text/plain; charset=US-ASCII

Hello,

The Haskell Wiki says automatic registration has been disabled, and that I
should send an e-mail. Could you please create a wiki account for me? The
username I'd like to have is: akrasner.

Thanks in advance!


------------------------------

Message: 5
Date: Wed, 29 Apr 2015 11:21:48 +0200
From: "Henk-Jan van Tuyl" <hjgtuyl at chello.nl>
To: Haskell-Cafe <haskell-cafe at haskell.org>, fr33domlover
        <fr33domlover at riseup.net>
Subject: Re: [Haskell-cafe] Wiki user
Message-ID: <op.xxukara8pz0j5l at alquantor>
Content-Type: text/plain; charset=iso-8859-15; format=flowed;
        delsp=yes

On Wed, 29 Apr 2015 08:07:36 +0200, fr33domlover <fr33domlover at riseup.net>
wrote:

> should send an e-mail. Could you please create a wiki account for me? The
> username I'd like to have is: akrasner.

Done.

Regards,
Henk-Jan van Tuyl


--
Folding at home
What if you could share your unused computer power to help find a cure? In
just 5 minutes you can join the world's biggest networked computer and get
us closer sooner. Watch the video.
http://folding.stanford.edu/


http://Van.Tuyl.eu/
http://members.chello.nl/hjgtuyl/tourdemonad.html
Haskell programming
--


------------------------------

Message: 6
Date: Wed, 29 Apr 2015 14:25:02 +0300
From: fr33domlover <fr33domlover at riseup.net>
To: "Henk-Jan van Tuyl" <hjgtuyl at chello.nl>
Cc: Haskell-Cafe <haskell-cafe at haskell.org>
Subject: Re: [Haskell-cafe] Wiki user
Message-ID: <mailman.9.1430308802.9745.haskell-cafe at haskell.org>
Content-Type: text/plain; charset=US-ASCII

Thank you very much!


On Wed, 29 Apr 2015 11:21:48 +0200
"Henk-Jan van Tuyl" <hjgtuyl at chello.nl> wrote:

> On Wed, 29 Apr 2015 08:07:36 +0200, fr33domlover <fr33domlover at riseup.net>
> wrote:
>
> > should send an e-mail. Could you please create a wiki account for me?
The
> > username I'd like to have is: akrasner.
>
> Done.
>
> Regards,
> Henk-Jan van Tuyl
>
>



------------------------------

Message: 7
Date: Wed, 29 Apr 2015 07:43:45 -0400
From: Richard Eisenberg <eir at cis.upenn.edu>
To: "Nicholls, Mark" <nicholls.mark at vimn.com>
Cc: "haskell-cafe at haskell.org" <haskell-cafe at haskell.org>
Subject: Re: [Haskell-cafe] dependent types, singleton types....
Message-ID: <6CF4D7D9-76A1-4B2A-9ABE-3409739FFD56 at cis.upenn.edu>
Content-Type: text/plain; charset="windows-1252"

Hello Mark,

Your suspicion that your singleton tree type is wrong is well-founded.

The problem is that, in my opinion, that exercise is mentioned too early in
the tutorial. To properly implement a singleton type for a parameterized
type, like a binary tree, you will need `data family Sing (a :: k)`, as
explained just a little bit further down in the post. You'll need to
rewrite your definition for singleton numbers and booleans to work with
`Sing` as well.

Your code except the definition for SBranch is all correct. The problem
with your definition is that you don't get the right information when
pattern-matching. For example, say you have x with type `SBTree a`. If you
successfully pattern match against `SBranch SZ SLeaf SLeaf`, you would want
to learn `a ~ Branch Z Leaf Leaf`. But that's not what you'll get in your
implementation: you'll get a type error saying that we don't know that `a0`
is an `SNat`, where `a ~ Branch a0 Leaf Leaf`, or something like that. The
type-level information is simply encoded in the wrong place for this to
work out.

Write back and I'll give you the full answer if this isn't enough to get
you moving in the right direction!

Richard

On Apr 28, 2015, at 10:45 AM, "Nicholls, Mark" <nicholls.mark at vimn.com>
wrote:

> Can someone check my answer (no I?m not doing an assessment?I?m actually
learning stuff out of interest!)
>
> working through
>
>
https://www.fpcomplete.com/user/konn/prove-your-haskell-for-great-safety/dependent-types-in-haskell
>
> still there is a section about singleton types and the exercise is
>
> ?Exercise: Define the binary tree type and implement its singleton type.?
>
> Ok, I think I?m probably wrong?.a binary tree is something like?
>
> > data BTree a = Leaf | Branch a (BTree a) (BTree a)
>
> With DataKind
>
> My logic goes?
> Leaf is an uninhabited type, so I need a value isomorphic to it?.
>
> Easy?
>
> > data SBTree a where
> >   SLeaf :: SBTree Leaf
>
> Things like
> Branch Integer Leaf  (Branch String Leaf Leaf)
> Are uninhabited?so I need to add
>
> >   SBranch :: (a :: *) -> (SBTree (b :: BTree *)) -> (SBTree (c :: BTree
*)) -> SBTree (Branch a b c)
>
> ?
>
> It compiles?but?.is it actually correct?
> Things like
>
> > y = SBranch (SS (SS SZ)) SLeaf SLeaf
> > z = SBranch (SS (SS SZ)) (SBranch SZ SLeaf SLeaf) SLeaf
>
> Seem to make sense ish.
>
> From: Nicholls, Mark
> Sent: 28 April 2015 9:33 AM
> To: Nicholls, Mark
> Subject: sds
>
> Hello,
>
> working through
>
>
https://www.fpcomplete.com/user/konn/prove-your-haskell-for-great-safety/dependent-types-in-haskell
>
> but a bit stuck...with an error...
>
> > {-# LANGUAGE DataKinds, TypeFamilies, TypeOperators,
UndecidableInstances, GADTs, StandaloneDeriving #-}
>
> > data Nat = Z | S Nat
>
> > data Vector a n where
> >   Nil  :: Vector a Z
> >   (:-) :: a -> Vector a n -> Vector a (S n)
> > infixr 5 :-
>
> I assume init...is a bit like tail but take n - 1 elements from the
front....but...
>
> > init' :: Vector a ('S n) -> Vector a n
> > init' (x :- Nil) = Nil
> > init' (x :- xs@(_ :- _)) = x :- (init' xs)
>
> > zipWithSame :: (a -> b -> c) -> Vector a n -> Vector b n -> Vector c n
> > zipWithSame f Nil Nil = Nil
> > zipWithSame f (x :- xs) (y :- xs@(_ :- _)) = Nil
>
> Mark Nicholls | Senior Technical Director, Programmes & Development -
Viacom International Media Networks
> A: 17-29 Hawley Crescent London NW1 8TT | e: Nicholls.Mark at vimn.com T: +44
(0)203 580 2223
>
> <image001.png>
>
>
>
> CONFIDENTIALITY NOTICE
>
> This e-mail (and any attached files) is confidential and protected by
copyright (and other intellectual property rights). If you are not the
intended recipient please e-mail the sender and then delete the email and
any attached files immediately. Any further use or dissemination is
prohibited.
>
> While MTV Networks Europe has taken steps to ensure that this email and
any attachments are virus free, it is your responsibility to ensure that
this message and any attachments are virus free and do not affect your
systems / data.
>
> Communicating by email is not 100% secure and carries risks such as
delay, data corruption, non-delivery, wrongful interception and
unauthorised amendment. If you communicate with us by e-mail, you
acknowledge and assume these risks, and you agree to take appropriate
measures to minimise these risks when e-mailing us.
>
> MTV Networks International, MTV Networks UK & Ireland, Greenhouse,
Nickelodeon Viacom Consumer Products, VBSi, Viacom Brand Solutions
International, Be Viacom, Viacom International Media Networks and VIMN and
Comedy Central are all trading names of MTV Networks Europe.  MTV Networks
Europe is a partnership between MTV Networks Europe Inc. and Viacom
Networks Europe Inc.  Address for service in Great Britain is 17-29 Hawley
Crescent, London, NW1 8TT.
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

-------------- next part --------------
An HTML attachment was scrubbed...
URL: <
http://mail.haskell.org/pipermail/haskell-cafe/attachments/20150429/5cfd0d5d/attachment-0001.html
>

------------------------------

Subject: Digest Footer

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe at haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe


------------------------------

End of Haskell-Cafe Digest, Vol 140, Issue 52
*********************************************
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20150429/923c05de/attachment.html>


More information about the Haskell-Cafe mailing list