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

2012-01-20 Thread Erik de Castro Lopo
Myles C. Maxfield wrote:

> I am interested in contributing to the http-conduit library. I've been
> using it for a little while and reading through its source, but have felt
> that it could be improved with two features:
> 
>- Allowing the caller to know the final URL that ultimately resulted in
>the HTTP Source.

+1

>- Making the redirection aware of cookies.

+1

> I'd be happy to do both of these things,

I made a couple of small contributions to Michael's http-enumerator library
via the Github issue tracker and pull-request mechanism. Michael has always
responded relatively quickly and seems very open to suggestions for
improvements to his library.

Cheers,
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


[Haskell-cafe] Contributing to http-conduit

2012-01-20 Thread Myles C. Maxfield
To: Michael Snoyman, author and maintainer of http-conduit
CC: haskell-cafe

Hello!

I am interested in contributing to the http-conduit library. I've been
using it for a little while and reading through its source, but have felt
that it could be improved with two features:

   - Allowing the caller to know the final URL that ultimately resulted in
   the HTTP Source. Because httpRaw is not exported, the caller can't even
   re-implement the redirect-following code themselves. Ideally, the caller
   would be able to know not only the final URL, but also the entire chain of
   URLs that led to the final request. I was thinking that it would be even
   cooler if the caller could be notified of these redirects as they happen in
   another thread. There are a couple ways to implement this that I have been
   thinking about:
  - A straightforward way would be to add a [W.Ascii] to the type of
  Response, and getResponse can fill in this extra field.
getResponse already
  knows about the Request so it can tell if the response should be
gunzipped.
  - It would be nice for the caller to be able to know in real time
  what URLs the request is being redirected to. A possible way to do this
  would be for the 'http' function to take an extra argument of type (Maybe
  (Control.Concurrent.Chan W.Ascii)) which httpRaw can push URLs
into. If the
  caller doesn't want to use this variable, they can simply pass Nothing.
  Otherwise, the caller can create an IO thread which reads the Chan until
  some termination condition is met (Perhaps this will change the
type of the
  extra argument to (Maybe (Chan (Maybe W.Ascii. I like this solution,
  though I can see how it could be considered too heavyweight.
   - Making the redirection aware of cookies. There are redirects around
   the web where the first URL returns a Set-Cookie header and a 3xx code
   which redirects to another site that expects the cookie that the first HTTP
   transaction set. I propose to add an (IORef to a Data.Set of Cookies) to
   the Manager datatype, letting the Manager act as a cookie store as well as
   a repository of available TCP connections. httpRaw could deal with the
   cookie store. Network.HTTP.Types does not declare a Cookie datatype, so I
   would probably be adding one. I would probably take it directly from
   Network.HTTP.Cookie.

I'd be happy to do both of these things, but I'm hoping for your input on
how to go about this endeavor. Are these features even good to be pursuing?
Should I be going about this entirely differently?

Thanks,
Myles C. Maxfield

P.S. I'm curious about the lack of Network.URI throughout
Network.HTTP.Conduit. Is there a particular design decision that led you to
use raw ascii strings?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to get Cabal to spit out a .a library suitable for linking into C/Objective-C

2012-01-20 Thread Jeremy O'Donoghue
Hi David,

On 20 January 2012 22:34, David Pollak wrote:

> On Mon, Jan 16, 2012 at 1:32 PM, Jason Dagit  wrote:
>
>> Did you figure out what you need to know?
>
>
> Sadly, no.
>
>
>>  If not, I would suggest
>> asking this same question but on StackOverflow (assuming you haven't
>> already asked there).
>>
>
I missed this question the first time around. Sorry.

I don't have a canned answer to your question, but on the wxHaskell team we
have recently been working on (ab)using Cabal to produce shared libraries,
and almost everything is just as applicable to static libraries. It's not
all working yet, but some of the following pointers might help you to
understand how to make Cabal linking configurable.

http://wewantarock.wordpress.com/2010/11/03/building-a-shared-library-in-cabal/
http://sourceforge.net/mailarchive/message.php?msg_id=28520475
http://sourceforge.net/mailarchive/message.php?msg_id=28665900


> Great suggestion.  Thanks!
>
>
>> On Mon, Dec 19, 2011 at 2:35 PM, David Pollak
>>  wrote:
>> > Howdy,
>> >
>> > I'm trying to figure out how to get Cabal configured to compile and
>> link my
>> > Haskell code such that the code can be part of C and/or Objective-C code
>> > such that all the Haskell dependencies are rolled into a .a file and
>> can be
>> > linked by a normal C linker (e.g., ld).
>> >
>> > I've been
>> > through
>> http://haskell.org/ghc/docs/6.12.2/html/users_guide/ffi-ghc.html#using-own-main
>> > and the associated linked, but I'm unable to find out the Cabal
>> incantation
>> > to output a library that's linkable into my other code.  Any pointers or
>> > examples would be greatly appreciated.
>> >
>> > Thanks,
>> >
>> > David
>>
>
Best regards
Jeremy
___
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-20 Thread Gwern Branwen
On Fri, Jan 20, 2012 at 1:57 PM, Twan van Laarhoven  wrote:
> Here is some example code (untested):

Well, you're right that it doesn't work. I tried to fix the crucial
function, 'atLeastThisManyDescendants', but it's missing something
because varying parts doesn't much affect the results when I try it
out on example input - it either returns everything or nothing, it
seems:

atLeastThisManyDescendants :: Int -> Trie a -> [CommonPrefix a]
atLeastThisManyDescendants minD trie@(Trie l d t')
   | d < minD = []
   | null forChildren = [Prefix [] trie]
   | otherwise = forChildren
 where
   forChildren = [ Prefix (x:pfx) nms
 | (x,t) <- Map.toList t'
 , Prefix pfx nms <- atLeastThisManyDescendants l t ]

-- 
gwern
http://www.gwern.net

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


Re: [Haskell-cafe] How to get Cabal to spit out a .a library suitable for linking into C/Objective-C

2012-01-20 Thread David Pollak
On Mon, Jan 16, 2012 at 1:32 PM, Jason Dagit  wrote:

> Did you figure out what you need to know?


Sadly, no.


>  If not, I would suggest
> asking this same question but on StackOverflow (assuming you haven't
> already asked there).
>

Great suggestion.  Thanks!


>
> Jason
>
>
> On Mon, Dec 19, 2011 at 2:35 PM, David Pollak
>  wrote:
> > Howdy,
> >
> > I'm trying to figure out how to get Cabal configured to compile and link
> my
> > Haskell code such that the code can be part of C and/or Objective-C code
> > such that all the Haskell dependencies are rolled into a .a file and can
> be
> > linked by a normal C linker (e.g., ld).
> >
> > I've been
> > through
> http://haskell.org/ghc/docs/6.12.2/html/users_guide/ffi-ghc.html#using-own-main
> > and the associated linked, but I'm unable to find out the Cabal
> incantation
> > to output a library that's linkable into my other code.  Any pointers or
> > examples would be greatly appreciated.
> >
> > Thanks,
> >
> > David
> >
> > --
> > Visi.Pro, Cloud Computing for the Rest of Us http://visi.pro
> > Lift, the simply functional web framework http://liftweb.net
> > Follow me: http://twitter.com/dpp
> > Blog: http://goodstuff.im
> >
> >
> >
> > ___
> > Haskell-Cafe mailing list
> > Haskell-Cafe@haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
> >
>



-- 
Visi.Pro, Cloud Computing for the Rest of Us http://visi.pro
Lift, the simply functional web framework http://liftweb.net
Follow me: http://twitter.com/dpp
Blog: http://goodstuff.im
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to get Cabal to spit out a .a library suitable for linking into C/Objective-C

2012-01-20 Thread David Pollak
On Mon, Dec 26, 2011 at 4:40 PM, Donn Cave  wrote:

> Sorry about the belated response, but this shouldn't be a problem since
> it isn't going to be very helpful anyway!
>
> I've managed to follow the process described on this page:
> http://www.haskell.org/haskellwiki/Using_Haskell_in_an_Xcode_Cocoa_project
> to link Haskell code to a non-Haskell main program, via Xcode.
>
> You've probably already seen this, it's mostly about a few iterations
> of trial and error linking, to get the list of GHC library dependencies,
> which is what you need whether you're using Xcode or not.  If you really
> need a single library with your code and all those dependencies, that
> may be technically feasible, though awfully tedious.
>

Thanks for the pointer.  I had already read this.  I am looking for a
non-trial-and-error mechanism for creating a statically linked .a file.
 It's Step 8 in the article.

Thanks for your help.

David


>
> The only clear problem I encountered while experimenting with it is that
> GHC run time options need ghc -rtsopts, so they're unavailable if your
> program isn't built by ghc.  I believe I worked around that with a special
> rtsmain.o, could probably recover the details if that's of interest.
>
>Donn
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



-- 
Visi.Pro, Cloud Computing for the Rest of Us http://visi.pro
Lift, the simply functional web framework http://liftweb.net
Follow me: http://twitter.com/dpp
Blog: http://goodstuff.im
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Idris

2012-01-20 Thread Ozgur Akgun
Just by looking at the hackage dependencies, it doesn't look like it has
unix-only dependencies. Maybe the Boehm garbage collector?
http://www.hpl.hp.com/personal/Hans_Boehm/gc/

Also, Idris has a mailing list, Edwin would be more likely to respond
there: http://groups.google.com/group/idris-lang

HTH,
Ozgur

On 20 January 2012 19:15, Ryan Ingram  wrote:

> Has anyone played with Idris (http://idris-lang.org/) at all?  It looks
> interesting, and I'd love to play with it, but unfortunately I only have
> windows machines up and running at the moment and the documentation seems
> to imply it only builds on unixy systems.
>
> I'm curious how difficult it would be to get a win32 implementation up and
> running.
>
>   -- ryan
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why were unfailable patterns removed and "fail" added to Monad?

2012-01-20 Thread Ryan Ingram
I don't currently have anything to add to this discussion, but I want to
encourage you all to keep having it because I think it has potential to
improve the language in the "do things right or don't do them at all"
philosophy that Haskell tends towards.

  -- ryan

On Fri, Jan 20, 2012 at 6:32 AM, Jacques Carette wrote:

> On 19/01/2012 10:19 PM, Edward Z. Yang wrote:
>
>>  In other words,
>> MonadZero has no place in dealing with pattern match failure!
>>
>>  I completely agree.  See "Bimonadic semantics for basic pattern matching
> calculi" [1] for an exploration of just that.  In the language of that
> paper, the issue is that there is a monad of effects for actions, and a
> monad of effects for pattern matching, and while these are very lightly
> related, they really are quite different.  By varying both monads, one can
> easily vary through a lot of different behaviour for pattern-matching as
> found in the literature.
>
> I should add that if we had known about some of the deeper structures of
> pattern matching (as in Krishnaswami's Focusing on Pattern Matching [2],
> published 3 years *later*), we could have simplified our work.
>
> Jacques
>
> [1] http://www.cas.mcmaster.ca/~**kahl/Publications/Conf/Kahl-**
> Carette-Ji-2006a.html
> [2] 
> http://www.cs.cmu.edu/~neelk/**pattern-popl09.pdf
>
>
> __**_
> 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] Idris

2012-01-20 Thread Ryan Ingram
Has anyone played with Idris (http://idris-lang.org/) at all?  It looks
interesting, and I'd love to play with it, but unfortunately I only have
windows machines up and running at the moment and the documentation seems
to imply it only builds on unixy systems.

I'm curious how difficult it would be to get a win32 implementation up and
running.

  -- 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-20 Thread Twan van Laarhoven

On 20/01/12 18:45, Gwern Branwen wrote:

Recently I wanted to sort through a large folder of varied files and
figure out what is a 'natural' folder to split out, where natural
means something like>4 files with the same prefix.



My idea for an algorithm would be: build a trie for the input strings, 
and then look for the deepest subtries with more than one child.


For example, a trie containing the strings
  chorus-kiminoshiranaimonogatari.ogg
  chorus-mrmusic.ogg
  choucho-lastnightgoodnight.ogg

looks like:
   (3 items)
  c   (3 items)
   h   (3 items)
o   (3 items)
 r   (2 items)
  u   (2 items)
   s   (2 items)
-   (2 items)
 k   (1 item)
  i   (1 item)
   minoshiranaimonogatari.ogg
 m   (1 item)
  r   (1 item)
   music.ogg
 u   (1 item)
  c   (1 item)
   ho-lastnightgoodnight.ogg
Where actually the lines with more than one character are also subtrees 
of subtrees of subtrees.



Here is some example code (untested):


import qualified Data.Map as Map

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

-- 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 empty . map singleton

toList :: Ord a => 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 }

atLeastThisManyDescendants :: Int -> Trie a -> [CommonPrefix a]
atLeastThisManyDescendants minD trie@(Trie l d t)
| d < minD = []
| null forChildren = [Prefix [] trie]
| otherwise = forChildren
  where
forChildren = [ Prefix (x:pfx) names
  | (x,t) <- Map.toList c
  , Prefix pfx names <- atLeastThisManyDescendants n t ]



Twan

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


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

2012-01-20 Thread Gwern Branwen
Recently I wanted to sort through a large folder of varied files and
figure out what is a 'natural' folder to split out, where natural
means something like >4 files with the same prefix. (This might be
author, genre, subject, whatever I felt was important when I was
naming the file.) Now usually I name files with hyphens as the
delimiters like the hypothetical '1998-wadler-monads.pdf', and it
would be easy to write a stdin/stdout filter to break Strings on
hyphens and sort by whatever is most common. But this is rather
hardwired, can I solve the more general problem of finding the longest
common prefixes, whatever they are?

This turns out to be much more difficult than simply finding 'the'
longest common prefix (which is usually ""). I found an algorithm of
sorts at http://stackoverflow.com/a/6634624 but it was easier
described than implemented. Eventually I wrote what I *think* is a
correct program, but it's definitely of the write-only sort. Perhaps
people have better implementations somewhere? I saw a lot of
discussion of tries, but I didn't go that route.

The code, followed by an example:

#!/usr/bin/env runhaskell

import Data.List (intercalate, isPrefixOf, nub, sort)

main :: IO ()
main = interact (unlines . intercalate [""] . chunkFiles . lines )

-- basic algorithm from 
chunkFiles :: Ord a => [[a]] -> [[[a]]]
chunkFiles f = map (\(_,b) -> filter (isPrefixOf b) f) $ sort $
map (\x -> (countPrefixes x f,x)) (e $ bar f)

sharedPrefixes :: Ord a => [[a]] -> [a]
sharedPrefixes [] = []
sharedPrefixes s = foldr1 sp2 s
  where sp2 l1 l2 = map fst . takeWhile (uncurry (==)) $ zip l1 l2

traverse :: Ord a => [[a]] -> [[a]]
traverse [] = []
traverse x = sharedPrefixes (take 2 x) : traverse (drop 1 x)

bar :: Ord a => [[a]] -> [[a]]
bar = nub . sort . traverse . sort

countPrefixes :: (Ord a) => [a] -> [[a]] -> Int
countPrefixes x xs = length $ filter (x `isPrefixOf`) xs

e :: Eq a => [[a]] -> [[a]]
e y = map fst $ filter snd $ map (\x -> (x, (==) 1 $ length . filter
id $ map (x `isPrefixOf`) y)) y

{- Example input from `ls`:

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
gumi-mozaikrole.ogg
gumi-ハッピーシンセサイザ.ogg
gumi-showasengirl.ogg
gumi-sweetfloatflatsスイートフロートアパート.ogg
gumi-timewarpedafterchoppingmystagbeetle.ogg
gumi-オリジナル曲-付きホシメグリ.ogg
gumi-ミクオリジナル親友.ogg
kaito-byakkoyano.ogg
kaito-flowertail.ogg
kasaneteto-tam-ochamekinou重音テト吹っ切れたおちゃめ機能.ogg
len-crime-timetosaygoodbye.ogg
len-fire◎flower.ogg
len-ponponpon.ogg
lily-prototype.ogg
luka-apolxcore-waitingforyou.ogg
luka-dimトロイ.ogg
luka-dion-myheartwillgoon.ogg
luka-dirgefilozofio-dirgeasleepinjesus.ogg
luka-アゴアニキ-doubelariatダブルラリアット.ogg
luka-emon-heartbeats.ogg
luka-emonloid3-ハローハロー.ogg
luka-everybreathyoutake.ogg
luka-オリジナル-garden.ogg
luka-justbefriends.ogg
lukameiko-gemini.ogg
luka-milkyway.ogg
luka-やみくろ-かいぎ.ogg
luka-tic-tick.ogg
luka-torinouta.ogg
luka-zeijakukei-shounenshoujo.ogg
luka-勝手にアニメ-nologic-作ってみた.ogg
luka-駄目人間.ogg
meiko-artemis-awake.ogg
miku-9ronicleプラチナ.ogg
miku-acolorlinkingworld-この世界の下で.ogg
miku-acolorlinkingworld-青い花.ogg
miku-a+jugos-lullabyforkindness.ogg
miku-akayaka-beacon.ogg
miku-akayakap-sunrise.ogg
miku-aoihana.ogg
miku-arabianresponse.ogg
miku-avtechno-tear.ogg
miku-こえをきかせてcicci.ogg
miku-cleantears-remind2011natsu-greenhillzonecrystiararemix.ogg
miku-cleantears-remind2011natsu-夏影summerwindremix.ogg
miku-clocklockworks.ogg
miku-dancedancevol2-runner.ogg
miku-daniwellp-chaoticuniverse.ogg
miku-dixieflatline-shinonomescrumble.ogg
miku-electricloveエレクトリックラヴ.ogg
miku-elegumitokyo-kissmebaby.ogg
miku-galaxyodyssey-cryingirl.ogg
miku-galaxyodyssey-galaxyspacelines.ogg
miku-hakamairi.ogg
miku-haruna.ogg
miku-heartshooter.ogg
miku-hoshikuzutokakera.ogg
miku-innes.ogg
miku-innocence初音ミク.ogg
miku-jemappelle-motion-likeyou.ogg
miku-jemappelle-motion-ohwell.ogg
miku-jevannip-myfavoritesummer.ogg
miku-kakokyuudance-過呼吸ダンス.ogg
miku-kz-packaged.ogg
miku-kz-tellyourworld.ogg
miku-lastscene.ogg
miku-lostmemories付き-初音ミク.ogg
miku-lovelyday.ogg
miku-いいわけlove_song.ogg
mikulukagumi-prayfor.ogg
miku-maple-初音ミク楓-オリジナル曲.ogg
miku-more1.5.ogg
mik...@rk-eklosion.ogg
mik...@rk-kirch.ogg
miku-nana-ボーナストラック-ハッピー般若コア.ogg
miku-nekomimiswitch.ogg
miku-nightrainbow.ogg
miku-noyounome.ogg
miku-むかしむかしのきょうのぼくオリジナル.ogg
miku-pandolistp-neverendinghammertime.ogg
miku-ジラートP-birthdayofeden-deepsleep.ogg
miku-ジラートP-birthdayofeden-水中読書.ogg
miku-plustellia-dear.ogg
miku-plustellia-壁の彩度-crazygirl.ogg
miku-plustellia-壁の彩度-discoradio.ogg
miku-ぽわぽわP-ストロボライト.ogg
miku-rabbitforgets.ogg
miku-re:package-lastnightgoodnight.ogg
miku-re:package-ourmusic.ogg
miku-re:package-sutorobonaitsu.ogg
miku-rollinggirl.ogg
miku-ryo-メルト-melt.ogg
miku-senseiniitteyaro.ogg
miku-sevencolors-レモネード.ogg
miku-shoukinosatadenia.ogg
miku-stratosphere.ogg
miku-supernova.ogg
miku-t

Re: [Haskell-cafe] In-memory Handle for testing

2012-01-20 Thread Simon Hengel
> There might still be some things in GHC.IO.Handle that assume FD
> handles - I haven't tried it in a while.

For now I'm only using putStr and putStrLn on the handle, and that seems
to work.  Thanks!

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


Re: [Haskell-cafe] instance (Enum a) => IArray UArray a

2012-01-20 Thread Twan van Laarhoven

On 20/01/12 16:31, Mikhail Arefiev wrote:
> Is there a reason why there is no instance of (Enum a) =>  IArray
> UArray a (other than that it will require OverlappingInstances and/or
> IncoherentInstances if e. g. UArray of Bools is used in the same
> code)?
>
> ...
>
> Does having such thing make any sense?

The problem is that there are Enum instances for things for which 
to/fromEnum doesn't make sense, such as Double, Float and Integer.


   Prelude> fromEnum (12345678901234567890 :: Integer)
   -6101065172474983726

You wouldn't want your Integers to be stored as Ints in an array.


Twan

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


Re: [Haskell-cafe] In-memory Handle for testing

2012-01-20 Thread Antoine Latter
On Fri, Jan 20, 2012 at 5:53 AM, Simon Hengel  wrote:
> For testing I want to stub handles, performing all reads and writes in
> memory (and in process, so no mmap).  From looking at the documentation
> of mkFileHandle[1], I think this should be possible.  But it requires
> some work.  Is there already something out there?
>

John Miliken has one on Hackage:

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

I had a read-only version that I used for testing things a ways back:

http://hackage.haskell.org/trac/ghc/attachment/ticket/4144/ByteStringHandle.hs

There might still be some things in GHC.IO.Handle that assume FD
handles - I haven't tried it in a while.

Antoine

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


[Haskell-cafe] instance (Enum a) => IArray UArray a

2012-01-20 Thread Mikhail Arefiev
Is there a reason why there is no instance of (Enum a) => IArray
UArray a (other than that it will require OverlappingInstances and/or
IncoherentInstances if e. g. UArray of Bools is used in the same
code)?

I have written one with the help of StackOverflow
(http://stackoverflow.com/questions/8941386/), here is the source
code:

 - UArrays.hs: http://hpaste.org/56728
 - BenchmarkUArray.hs: http://hpaste.org/56729
 - Makefile: http://hpaste.org/56727

Running the benchmark with +RTS -s on the UArray version shows

   1,283,705,968 bytes allocated in the heap
 113,304 bytes copied during GC
  80,027,864 bytes maximum residency (2 sample(s))
 744,128 bytes maximum slop
 155 MB total memory in use (0 MB lost due to fragmentation)

versus

 567,014,904 bytes allocated in the heap
 962,651,888 bytes copied during GC
 324,111,008 bytes maximum residency (3 sample(s))
   2,887,992 bytes maximum slop
 545 MB total memory in use (0 MB lost due to fragmentation)

on the boxed (Array Int Color) version.  Also, boxed enum time is
1.75s and unboxed is 0.45s.

The benchmark may be silly (I am not experienced in testing for
Haskell performance), and I would be grateful for any tips on how to
improve it to achieve more accurate measurements.

Does having such thing make any sense?

--
Best regards,
Arefiev

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


Re: [Haskell-cafe] Parsing workflow

2012-01-20 Thread S D Swierstra

On Oct 31, 2010, at 17:15 , Nils Schweinsberg wrote:

> Am 31.10.2010 16:53, schrieb Vo Minh Thu:
>> I can't really tell from your description, but maybe this is because
>> of the way Parsec works when it deals with alternatives. When you
>> combine several parsers with e.g. '<|>' or 'choice', an alternative
>> that can consume some input but fails will make the whole combined
>> parser fail too. So you have to either factorize you parsers or use
>> the 'try'. See the documentation for 'try' at
>> http://hackage.haskell.org/packages/archive/parsec/3.1.0/doc/html/Text-Parsec-Prim.html
>> .
>> 
> 
> This is exactly what gives me headaches. It's hard to tell where you need 
> try/lookAhead and where you don't need them. And I don't really feel 
> comfortable wrapping everything into try blocks...

This is precisely why you should use a more general parser library like 
uu-parsing and try to avoid the more low-level techniques used in Parsec; 
uu-parsinglib avoids all the confusion arising from the use of try constructs. 
It furthermore gives you an online result, error correction and nice error 
messages. Its Utils module contains a lot of useful "standards" elements you 
might want to recognise.

Thus far i have only happy users, and if you are having any problems please let 
me know.


   Doaitse

PS: for all parsing libraries it holds that parsing times are negligeable when 
compared to the time spent on what you want to do with the parsed result.


> ___
> 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 were unfailable patterns removed and "fail" added to Monad?

2012-01-20 Thread Jacques Carette

On 19/01/2012 10:19 PM, Edward Z. Yang wrote:

  In other words,
MonadZero has no place in dealing with pattern match failure!

I completely agree.  See "Bimonadic semantics for basic pattern matching 
calculi" [1] for an exploration of just that.  In the language of that 
paper, the issue is that there is a monad of effects for actions, and a 
monad of effects for pattern matching, and while these are very lightly 
related, they really are quite different.  By varying both monads, one 
can easily vary through a lot of different behaviour for 
pattern-matching as found in the literature.


I should add that if we had known about some of the deeper structures of 
pattern matching (as in Krishnaswami's Focusing on Pattern Matching [2], 
published 3 years *later*), we could have simplified our work.


Jacques

[1] 
http://www.cas.mcmaster.ca/~kahl/Publications/Conf/Kahl-Carette-Ji-2006a.html

[2] http://www.cs.cmu.edu/~neelk/pattern-popl09.pdf

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


Re: [Haskell-cafe] Serializing UTCTimes

2012-01-20 Thread Ertugrul Söylemez
Bas van Dijk  wrote:

> However I have no idea how to serialize the DiffTime stored in an
> UTCTime:
>
> instance Serialize DiffTime where
> get = ?
> put = ?

Note that DiffTime has this weird property that there is a Real
instance, so you have a toRational function. ;)

To go the other way you have a Fractional instance, so you also have
'fromRational'.


Greets,
Ertugrul

-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/


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


Re: [Haskell-cafe] Serializing UTCTimes

2012-01-20 Thread Bas van Dijk
On 20 January 2012 15:03, Bas van Dijk  wrote:
> What's the recommended way for serializing (with the cereal package) an 
> UTCTime?

I'm now using the datetime package so I can do:

import Data.DateTime (fromSeconds, toSeconds)

instance Serialize UTCTime where
get = fromSeconds <$> get
put = put . toSeconds

But I will have to look at the code of datetime to see if I'm not
loosing precision.

Bas

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


[Haskell-cafe] Serializing UTCTimes

2012-01-20 Thread Bas van Dijk
Hello,

What's the recommended way for serializing (with the cereal package) an UTCTime?

It's easy to give Serialize instances for UTCTime and Day:

instance Serialize UTCTime where
get = liftM2 UTCTime get get
put (UTCTime day time) = put day >> put time

instance Serialize Day where
get = liftM Day get
put = put . toModifiedJulianDay

However I have no idea how to serialize the DiffTime stored in an UTCTime:

instance Serialize DiffTime where
get = ?
put = ?

Regards,

Bas

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


Re: [Haskell-cafe] Why were unfailable patterns removed and "fail" added to Monad?

2012-01-20 Thread Scott Turner

On 2012-01-19 23:52, Michael Snoyman wrote:

maybe I should file a feature request: provide an extra warning
flag (turned on by -Wall) that will warn when you match on a failable
pattern.


I fully agree if it's IO, so that a failed pattern match leads to an 
exception.  The "nice" implementations of fail in the List and Maybe 
monads are a different story.


Ideally one would want to be able to turn on a warning whenever IO is 
used in a way which could generate a pattern match exception.  This 
would call for a type distinction, as you said, "reinstate the MonadZero 
constraint".


Here's an idea that might address SPJ's "killer".
  b) if you add an extra constructor to a single-constructor
 type then pattern matches on the original constructor
 suddenly become failable

Another binding operator might be introduced so that the code would show 
the intention either to have a failable or non-failable pattern match.

 do (x,y) <- pair   failable, requires MonadZero
 do (x,y) <=- pair  requires non-failable pattern
supports Monads that should not fail

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


Re: [Haskell-cafe] Why were unfailable patterns removed and "fail" added to Monad?

2012-01-20 Thread James Cook
Actually, that's not what this conversation is about - it's about what to with 
those types of bindings instead of the way 1.4 had been doing it.

On Jan 19, 2012, at 10:19 PM, Edward Z. Yang wrote:

> Hello Gregory,
> 
> The original (1998!) conversation can be found here:
> 
>http://www.mail-archive.com/haskell@haskell.org/msg03002.html
> 
> I think Simon Peyton-Jones' example really sums up the whole issue:
> 
>But [MonadZero] really sticks in my craw.  How can we explain this:
> 


[MonadZero] is not the correct summary here.  "(1)" refers to the proposal of 
replacing the "failable" with "refutable" in the semantics, which leads to the 
weird example he then gives.


>f :: Monad m => m (a,b) -> m a
>f m1 = do { x <- m1; return (fst x) }
> 
>g :: MonadZero m => m (a,b) -> m a
>g m1 = do { (a,b) <- m1; return a }
> 
>h :: Monad m => m (a,b) -> m a
>h m1 = do { ~(a,b) <- m1; return a }
> 
>Why must g be in MonadZero?  Because the pattern (a,b) is refutable (by
>bottom).
> 

Again, this is the situation under a proposal where MonadZero is still inferred 
for some bindings, as in 1.4, but not for "unfailable" ones as 1.4 would have 
specified - for "refutable" ones.  All of those would count as unfailable under 
1.4 and so none would require MonadZero.

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


Re: [Haskell-cafe] Why were unfailable patterns removed and "fail" added to Monad?

2012-01-20 Thread James Cook
On Jan 20, 2012, at 1:40 AM, Michael Snoyman wrote:

> On Jan 20, 2012 8:31 AM, "John Meacham"  wrote:
> >
> > > As expected, no warnings. But if I change this "unfailable" code above
> > > to the following failable version:
> > >
> > >data MyType = Foo | Bar
> > >
> > >test myType = do
> > >Foo <- myType
> > >return ()
> > >
> > > I *still* get no warnings! We didn't make sure the compiler spits out
> > > warnings. Instead, we guaranteed that it *never* will.
> >
> > This is actually the right useful behavior. using things like
> >
> > do
> >   Just x <- xs
> >   Just y <- ys
> >   return (x,y)
> >
> > will do the right thing, failing if xs or ysresults in Nothing. for
> > instance, in the list monad, it will create the cross product of the
> > non Nothing members of the two lists. a parse monad may backtrack and
> > try another route, the IO monad will create a useful (and
> > deterministic/catchable) exception pointing to the exact file and line
> > number of the pattern match. The do notation is the only place in
> > haskell that allows us to hook into the pattern matching mechanism of
> > the language in a general way.
> >
> >John
> 
> I mention later that this is a "feature, not a bug" to some people, but I'm 
> not one of them. The convenience of having this feature is IMO far outweighed 
> by the cost of the runtime errors it can produce if you use the pattern 
> matching in the wrong monad (e.g., IO, Reader, Writer...).
> 
It seems like there must be deeper reasons than stated so far for wanting to 
remove the "failable" concept from the spec, because all the ones given so far 
seem more like pros than cons.

For example, those runtime errors would be type errors!  And when adding 
additional constructors to a single-constructor type, it would not silently 
change the meaning in most places - it would cause type errors in places where 
the binding no longer makes sense and "change the meaning" in a predictable way 
(the way it does now) in places where it does make sense.  The former sounds 
fantastic to me, and the latter sounds acceptable (but a warning for those who 
don't find it acceptable would be a good idea too).

There is of course still a risk that adding a constructor can cause silent 
misbehavior in code that uses those type of bindings in monads that _are_ 
instances of MonadZero, but personally the number of times I have been bitten 
by that or heard of anyone else actually being bitten by it (i.e., zero) is a 
lot smaller than the number of times I've decided a "failable" binding was just 
the right concise-and-clear way to implement a parser, filter, etc.  The only 
problem I have with that style is the fact that it is not rejected in places 
where it doesn't make sense.

-- James

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


[Haskell-cafe] In-memory Handle for testing

2012-01-20 Thread Simon Hengel
For testing I want to stub handles, performing all reads and writes in
memory (and in process, so no mmap).  From looking at the documentation
of mkFileHandle[1], I think this should be possible.  But it requires
some work.  Is there already something out there?

Cheers,
Simon

[1] 
http://hackage.haskell.org/packages/archive/base/4.4.1.0/doc/html/GHC-IO-Handle.html#v:mkFileHandle

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


Re: [Haskell-cafe] partial type annotations

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

On 20.01.2012, at 09:30, Paul R wrote:

> Hi,
> 
>> x :: Integer <- instruction1 -- Require ScopedTypeVariables

This is still enabled by the PatternSignatures extensions. 
> 
> Indeed, that does require ScopedTypeVariables to be enabled, but this
> basic use case is not clearly covered in the ScopedTypeVariables
> documentation.
http://www.haskell.org/ghc/docs/latest/html/users_guide/other-type-extensions.html#pattern-type-sigs
> 
> Also, it is not clear to me why ScopedTypeVariables is required at all
> here, as Integer is a literal type and not a signature-bound type
> variable.

In current GHC version PatternSignatures is deprecated and instead integrated 
into ScopedTypeVariables.

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


[Haskell-cafe] Haddock 2.8.1 and alex 3.0.1

2012-01-20 Thread cwr

Building haddock 2.8.1 with alex 3.0.1 I get the error message:

[ 7 of 33] Compiling Haddock.Lex  ( dist/build/Haddock/Lex.hs,  
dist/build/Haddock/Lex.o )


src/Haddock/Lex.x:150:17:
Couldn't match expected type `AlexInput'
   against inferred type `(t, t1, t2)'
In the first argument of `alexScan', namely `inp'
In the expression: alexScan inp sc
In the expression:
case alexScan inp sc of {
  AlexEOF -> []
  AlexError _ -> error "lexical error"
  AlexSkip inp' _ -> go inp' sc
  AlexToken (inp'@(pos', _, _)) len act
->

Haddock 2.8.1 builds correctly (or at least completely) with alex 2.3.5
I'm not sure if this is a bug or a feature - if it's a feature, then the
dependencies for haddock 2.8.1 need updating.

Will




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


Re: [Haskell-cafe] partial type annotations

2012-01-20 Thread Paul R
Hi,

> x :: Integer <- instruction1 -- Require ScopedTypeVariables

Indeed, that does require ScopedTypeVariables to be enabled, but this
basic use case is not clearly covered in the ScopedTypeVariables
documentation.

Also, it is not clear to me why ScopedTypeVariables is required at all
here, as Integer is a literal type and not a signature-bound type
variable.

-- 
  Paul

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


Re: [Haskell-cafe] Not an isomorphism, but what to call it?

2012-01-20 Thread Sean Leather
On Thu, Jan 19, 2012 at 23:21, Dan Doel wrote:

> A is a retract of B.
>
>http://nlab.mathforge.org/nlab/show/retract
>
> g is the section, f is the rectraction. You seem to have it already.
> The definition needn't be biased toward one of the functions.
>

Great! That's what I was looking for. Thanks!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe