[Haskell-cafe] HXT is slow?

2011-01-11 Thread Patrick Hurst
Is it just me, or is HXT slow? I noticed that both reading a document
from a file, as well as running computations, are exceedingly slow,
with simple stuff like 'get the contents of everything with a given
class' taking .3 seconds for a 400KB HTML file in Python using lxml
and 2 seconds using HXT with tagSoup and compiled with -O2.

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


[Haskell-cafe] Improving HList programming/debugging (longish)

2011-01-11 Thread jeff p
This message shows how to slightly reformulate HLists (and other type-level
things) to get better type-checking and more informative error messages. The
technique is interesting in that it uses GADTs and functional dependencies and
seems to not be implementable with associated type synonyms. It also makes
higher-order HList programming/debugging much more tractable.

Programming with HLists, at least in our experience, encourages GHC to produce
long and inscrutable type errors. This confusing behaviour is caused by the
open nature of type classes-- GHC (as per the Haskell specification) will
meekly report a conditional type (i.e. expression has type a if a constraint
holds) rather than decisively commit to reporting a type error. By using GADTs
and equality constraints, we can force GHC to be a lot more decisive.

> {-# LANGUAGE
>   EmptyDataDecls,
>   FlexibleInstances,
>   FunctionalDependencies,
>   GADTs,
>   MultiParamTypeClasses,
>   NoMonomorphismRestriction,
>   ScopedTypeVariables,
>   TypeFamilies,
>   TypeOperators,
>   UndecidableInstances
> #-}

We'll start with a standard type level list.

> data Nil
> data x :* xs
> infixr 5 :*

Rather than have direct terms for constructing these lists, we'll make a GADT
for HLists, and use the constructors from the GADT.

> data HList a where
>   Nil :: HList Nil
>   (:*) :: x -> HList xs -> HList (x :* xs)

Notice that every construction of an HList has a type of the form HList a, e.g.:

  *Main> :t 'a' :* () :* Nil
  'a' :* () :* Nil :: HList (Char :* (() :* Nil))

This definition of HLists allows the type checker to rule out malformed term
level representations of HLists:

  *Main> :t 1 :* ()

  :1:5:
  Couldn't match expected type `HList xs' against inferred type `()'
  In the second argument of `(:*)', namely `()'
  In the expression: 1 :* ()

We can now write hHead and hTail:

> hHead :: HList (x :* xs) -> x
> hHead (x :* _) = x

> hTail :: HList (x :* xs) -> HList xs
> hTail (_ :* xs) = xs

In order to have higher-order functions on HLists (e.g. fold), we need a way
to apply and evaluate type-level representations of functions to arguments.

> class HEval f x res | f x -> res where
> hEval :: f -> x -> res

By assuming the function argument to HEval is in weak head normal form, we
will avoid having to write a general eval function at the expense of having to
explicitly sequence calls to hEval ourselves.

We can now write hMap.

> class HMAP f xs res | f xs -> res where
> hMap :: f -> HList xs -> HList res
> instance HMAP f Nil Nil where
> hMap _ Nil = Nil
> instance (HEval f x v, HMAP f xs vs) => HMAP f (x :* xs) (v :* vs) where
> hMap f (x :* xs) = hEval f x :* hMap f xs

We can turn hHead and hTail into type-level functions which can be
mapped over HLists.

> data HHead = HHead
> instance (arg ~ HList (x :* xs)) => HEval HHead arg x
> where hEval _ = hHead

> data HTail = HTail
> instance (arg ~ HList (x :* xs)) => HEval HTail arg (HList xs)
> where hEval _ = hTail

Notice that the result of HTail is a HList.

Here is an example:

  *Main> :t hMap HHead (('a' :* "b" :* Nil) :* (() :* Nil) :* Nil)
  hMap HHead (('a' :* "b" :* Nil) :* (() :* Nil) :* Nil)
:: HList (Char :* (() :* Nil))

By putting an equality constraint in the context of the HEval instances and a
variable in the head, rather than putting the actual type in the head, we
force GHC to use the proper HEval clause for each type-level function, and to
eagerly type-check the evaluation of the function.

  *Main> :t hMap HHead (('a' :* "b" :* Nil) :* "c" :* Nil)

  Top level:
  Couldn't match expected type `HList (v :* xs)'
 against inferred type `[Char]'

If we use a more naive version of the HEval clause for HHead

> data HHead0 = HHead0
> instance HEval HHead0 (HList (x :* xs)) x where
> hEval _ = hHead

then GHC won't notice the type-level type error

  *Main> :t hMap HHead0 (('a' :* "b" :* Nil) :* "c" :* Nil)
  hMap HHead0 (('a' :* "b" :* Nil) :* "c" :* Nil)
:: (HEval HHead0 [Char] v) => HList (Char :* (v :* Nil))

until it is actually forced to look at the result type of the hMap.

  *Main> :t hMap HHead0 (('a' :* "b" :* Nil) :* "c" :* Nil) :: HList
(Char :* Char :* Nil)

  :1:0:
  No instance for (HEval HHead0 [Char] Char)
arising from a use of `hMap' at :1:0-46
  Possible fix:
add an instance declaration for (HEval HHead0 [Char] Char)
  In the expression:
hMap HHead0 (('a' :* "b" :* Nil) :* "c" :* Nil) ::
  HList (Char :* (Char :* Nil))

And the resulting error message is a missing instance, rather than a type clash.

Incidentally, an associated type synonym version of this technique seems to
break down at this point since type indices on an associated type must match
the class instance head; i.e. we can't seem to write HEval with an associated
type synonym instead of a functional dependency.

The remainder of this message is just

[Haskell-cafe] MonadRandom-computation that does not terminate

2011-01-11 Thread Tim Baumgartner
Hi,

I'm having difficulties with this function I wrote:

iterateR :: (MonadRandom m) => (a -> m a) -> a -> m [a]
iterateR g s = do
  s' <- g s
  return (s:) `ap` iterateR g s'

I'm running the computation with evalRandIO and surprisingly the first call
of main in ghci succeeds, but the second does not terminate. Reproducible.
Any clues what I'm doing wrong here?

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


Re: [Haskell-cafe] GHC.Ptr, Foreign.Storable, Data.Storable.Endian, looking for good examples of usage

2011-01-11 Thread Aaron Gray
On 11 January 2011 18:54, Antoine Latter  wrote:

> On Tue, Jan 11, 2011 at 10:22 AM, Aaron Gray 
> wrote:
> > On 11 January 2011 00:02, Antoine Latter  wrote:
> >>
> >> On Mon, Jan 10, 2011 at 5:23 PM, Aaron Gray  >
> >> wrote:
> >> > On 10 January 2011 22:30, Henning Thielemann
> >> > 
> >> > wrote:
> >> >>
> >> >> John Lato schrieb:
> >> >>
> >> >> > You could use my "word24" package[1] (GHC only) to provide
> >> >> > non-aligned
> >> >> > 24-bit word and int types with Storable instances.  You should be
> >> >> > able
> >> >> > to write a binary instance (or whatever blaze-builder needs) fairly
> >> >> > simply from this.  Little-endian only ATM, but BE could be added if
> >> >> > necessary.
> >> >>
> >> >> Good to know that! However, I think for the original poster the
> binary
> >> >> package is perfect. This way he does not worry about unsafe peeking
> and
> >> >> poking around in memory.
> >> >>
> >> >
> >> > Yes. I have came back to looking at the binary package, the only thing
> >> > is I
> >> > think I have to build my own primatives with it as it is big-endian,
> >> > where
> >> > ActionScript Byte Code format is little-endian. It does provide some
> >> > little-endian functions but they are not brought to the surface. It
> also
> >> > seems to roll its own serializations.
> >>
> >> The 'binary' package supports big-endian, little-endian and
> >> host-endian construction in the Data.Binary.Builder module, so you
> >> hopefully won't need to reimplement too much.
> >>
> >
> > Are there any examples of usage anywhere ? It does not seem to have 24bit
> > values either.
> > I am still thinking of implementing my own following the straight
> > Data.Binary package as an example.
> > Aaron
> >
>
> I used Data.Binary.Builder in an implementation of the memcached
> binary protocol:
>
> http://hackage.haskell.org/packages/archive/starling/0.3.0/doc/html/Network-Starling-Core.html
>
>
Nice code, I like the Serialize and Deserialize classes. Its a
shame Data.Binary does not use them.


> I'm sure other folks can chime in with good examples if that one isn't
> clear - the package 'binary' is pretty popular.
>
> You'd have to write your own putWord24be/le or whatever you need out
> of the 'singleton :: Word8 -> Builder' function. But that seems
> simpler than reimplementing Data.Binary.
>

Yes.

Thanks,

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


[Haskell-cafe] ArchLinux binary repository available for beta testing

2011-01-11 Thread Peter Simons
Hi guys,

those of you who use the ArchLinux distribution might be interested to know
that a team of volunteers has put together a binary package repository that
complements the set of Haskell packages that's already being distributed by
ArchLinux. Subscribers of that repository can use Pacman to install all of
Haskell Platform 2010.2.0.0 as well as a few other popular packages such as
bnfc, hledger, pandoc, sifflet, and yesod on both i686 and x86_64. If you
want to use the repository, then append the following two lines at the end
of your /etc/pacman.conf file:

  [haskell]
  Server = http://andromeda.kiwilight.com/$repo/$arch

Please be aware of the fact that this is the very first public announcement
of this repository, so you should consider it as being in a kind of beta
state. Basically, if your Linux machine is responsible for controlling some
large nuclear power plant or something, you probably shouldn't be using
this. Everyone else is encouraged to try it out. If you encounter problems,
have questions, or would like to make suggestions, then please raise an
issue at . Of course, you're
also welcome to provide feedback by posting to the haskell-cafe mailing list
or to arch-hask...@haskell.org.

Many people have contributed to this effort in one way or another. Don
Stewart originally wrote the cabal2arch tool that is being used to generate
the HABS tree on which this repository is based. Rémy Oudompheng has
extended that tool and the underlying ArchLinux library significantly, and
he has also written most of the build system that's being used to compile
the binary packages. Magnus Therning has compiled all the x86_64 binaries.
The i686 binaries were compiled by Yours Truely. Kaiting Chen is kindly
hosting the repository on his server. Furthermore, there are many other
people who have submitted bug reports, suggestions, and fixes by way of AUR.

Have fun,
Peter


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


Re: [Haskell-cafe] GHC.Ptr, Foreign.Storable, Data.Storable.Endian, looking for good examples of usage

2011-01-11 Thread Antoine Latter
On Tue, Jan 11, 2011 at 10:22 AM, Aaron Gray  wrote:
> On 11 January 2011 00:02, Antoine Latter  wrote:
>>
>> On Mon, Jan 10, 2011 at 5:23 PM, Aaron Gray 
>> wrote:
>> > On 10 January 2011 22:30, Henning Thielemann
>> > 
>> > wrote:
>> >>
>> >> John Lato schrieb:
>> >>
>> >> > You could use my "word24" package[1] (GHC only) to provide
>> >> > non-aligned
>> >> > 24-bit word and int types with Storable instances.  You should be
>> >> > able
>> >> > to write a binary instance (or whatever blaze-builder needs) fairly
>> >> > simply from this.  Little-endian only ATM, but BE could be added if
>> >> > necessary.
>> >>
>> >> Good to know that! However, I think for the original poster the binary
>> >> package is perfect. This way he does not worry about unsafe peeking and
>> >> poking around in memory.
>> >>
>> >
>> > Yes. I have came back to looking at the binary package, the only thing
>> > is I
>> > think I have to build my own primatives with it as it is big-endian,
>> > where
>> > ActionScript Byte Code format is little-endian. It does provide some
>> > little-endian functions but they are not brought to the surface. It also
>> > seems to roll its own serializations.
>>
>> The 'binary' package supports big-endian, little-endian and
>> host-endian construction in the Data.Binary.Builder module, so you
>> hopefully won't need to reimplement too much.
>>
>
> Are there any examples of usage anywhere ? It does not seem to have 24bit
> values either.
> I am still thinking of implementing my own following the straight
> Data.Binary package as an example.
> Aaron
>

I used Data.Binary.Builder in an implementation of the memcached
binary protocol:
http://hackage.haskell.org/packages/archive/starling/0.3.0/doc/html/Network-Starling-Core.html

I'm sure other folks can chime in with good examples if that one isn't
clear - the package 'binary' is pretty popular.

You'd have to write your own putWord24be/le or whatever you need out
of the 'singleton :: Word8 -> Builder' function. But that seems
simpler than reimplementing Data.Binary.

The package blaze-builder might have primitives for converting a
Storable instance into a Builder function, but I don't have any direct
experience with it.

Antoine

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


Re: [Haskell-cafe] GHC.Ptr, Foreign.Storable, Data.Storable.Endian, looking for good examples of usage

2011-01-11 Thread Aaron Gray
On 11 January 2011 00:02, Antoine Latter  wrote:

> On Mon, Jan 10, 2011 at 5:23 PM, Aaron Gray 
> wrote:
> > On 10 January 2011 22:30, Henning Thielemann <
> lemm...@henning-thielemann.de>
> > wrote:
> >>
> >> John Lato schrieb:
> >>
> >> > You could use my "word24" package[1] (GHC only) to provide non-aligned
> >> > 24-bit word and int types with Storable instances.  You should be able
> >> > to write a binary instance (or whatever blaze-builder needs) fairly
> >> > simply from this.  Little-endian only ATM, but BE could be added if
> >> > necessary.
> >>
> >> Good to know that! However, I think for the original poster the binary
> >> package is perfect. This way he does not worry about unsafe peeking and
> >> poking around in memory.
> >>
> >
> > Yes. I have came back to looking at the binary package, the only thing is
> I
> > think I have to build my own primatives with it as it is big-endian,
> where
> > ActionScript Byte Code format is little-endian. It does provide some
> > little-endian functions but they are not brought to the surface. It also
> > seems to roll its own serializations.
>
> The 'binary' package supports big-endian, little-endian and
> host-endian construction in the Data.Binary.Builder module, so you
> hopefully won't need to reimplement too much.
>
>
Are there any examples of usage anywhere ? It does not seem to have 24bit
values either.

I am still thinking of implementing my own following the straight
Data.Binary package as an example.

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


[Haskell-cafe] Possible participation on parallel programming book

2011-01-11 Thread Michael Oswald

Hello,


Just found the following in the Ada group:

There is an open source E-Book about parallel programming, where people 
can participate (via patches for a git repository):


http://lwn.net/Articles/421425/

Since Haskell has very good parallel capabilities, maybe the community 
would also be interested in participating?



lg,
Michael


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


Re: [Haskell-cafe] [Haskell] School of Expression pages missing from haskell.org

2011-01-11 Thread Henning Thielemann


On Tue, 11 Jan 2011, Julian Gilbey wrote:


Does anyone know what has happened to the Haskell School of Expression
(SOE) webpages?  The link from books for learning Haskell now gives a
404 Not Found error.


Maybe caused by the recent server move.

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


Re: [Haskell-cafe] GHC.Ptr, Foreign.Storable, Data.Storable.Endian, looking for good examples of usage

2011-01-11 Thread Henning Thielemann


On Mon, 10 Jan 2011, Aaron Gray wrote:


Yes. I have came back to looking at the binary package, the only thing is I 
think I have
to build my own primatives with it as it is big-endian, where ActionScript Byte 
Code
format is little-endian. It does provide some little-endian functions but they 
are not
brought to the surface. It also seems to roll its own serializations.


Maybe the storable-endian types can be equipped with 'Binary' instances.

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


Re: [Haskell-cafe] GHC.Ptr, Foreign.Storable, Data.Storable.Endian, looking for good examples of usage

2011-01-11 Thread John Lato
>
> On 10 January 2011 16:36, Antoine Latter  wrote:
>
> > On Mon, Jan 10, 2011 at 10:17 AM, Aaron Gray  >
> > wrote:
> > > On 10 January 2011 16:13, Daniel Fischer <
> > daniel.is.fisc...@googlemail.com>
> > > wrote:
> > >>
> > >> On Monday 10 January 2011 16:45:36, Aaron Gray wrote:
> > >> >
> > >> > This is interesting, what does the following line do :-
> > >> >
> > >> > data Int24 = I24# Int# deriving (Eq, Ord)
> > >> >
> > >> > regarding the I24# and Int#, are these inbuilt ?
> > >>
> > >> Int# is the raw machine int (4 or 8 bytes) and I24# is the
> constructor.
> > >> GHC
> > >> uses the magic hash '#' to denote raw unboxed types (and the
> > constructors
> > >> making ordinary boxed Haskell types from these, e.g. there's
> > >>
> > >> data Int = I# Int#
> > >> data Word = W# Word#
> > >> data Double = D# Double#
> > >>
> > >> and more defined in base [GHC.Types, GHC.Word]).
> > >
> > > So the 24 bit value is actually stored as a 32bit value. Meaning I will
> > have
> > > to do my own IO reader and writer code to a ByteString.
> > > Thanks,
> > > Aaron
> > >
> >
> > I don't think so - the Storable instance provided for the Int24 type
> > peeks and pokes 24-bit values. At least, that what I understand John's
> > earlier message to mean.
>
>
> Yes looking at the code it does support 24bit peeks and pokes.
>

This is correct (at least it's how it's meant to work).  24bit values are
represented as 32bit words for ops, but peeks and pokes are 24bit.

If all you want to do is read/write 24bit values there's nothing wrong with
binary, but if you ever want to use them the Word24 and Int24 types are nice
to have.

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