Re: [Haskell-cafe] relational data representation in memory using haskell?

2008-05-21 Thread Salvatore Insalaco
2008/5/22 Marc Weber <[EMAIL PROTECTED]>:
> I'd like to illustrate two different ideas using a small example:
> (A)
>data CD = CD { title :: String, tracks :: [ Track ] }
>data Track = Track { track :: String, cd :: CD }
>data PDB = PDB { cds :: Set CD, tracks :: Set Track }
>
> because it's not using foreign ids but kind of pointers I'll call this
> the pointer method

This doesn't look like a relational structure at all in Haskell.
Let's take the CD and Track relations. In a relational database you
have something like:
CD (1, 'Querying about you')
Track (1, 'Inserting some love', 1)
Track (2, 'Updating my feelings', 1)
Track (3, 'Deleting my hopes', 1)

In an imperative language you can do something similar in memory using
objects (you can in haskell to with IORefs and so on, but let's stay
on "data"). You get something like:

0x000 CD('Querying about you')
0x004 Track('Inserting some love, 0x004)
...

In Haskell when you say:
>data Track = Track { track :: String, cd :: CD }

You are not storing in Track a reference, a pointer or something
similar to a CD, you are storing a *value* (low level you probably
have a pointer, but you have not pointer semantics). As you noticed,
you cannot "update" the CD title without changing each Track. That's a
way to store information, and a good way too, but it's not a
relational structure by any extent.

If you want to use this structure for your relational data you need two things:
1) Something that will convert from a value-based representation of
data to something relational (aka ORM in the OO world... a FRM? VRM?).
2) A relational storage (internal or external).

If you want to use "normal" Haskell ADT, are you sure that a
relational storage is what you want? Keeping that in memory doesn't
give you some advantages of relational databases (e.g. uniform
representation), and the impedance between the functional and the
relational world is not easy to manage.

Maybe I misunderstood what you are trying to accomplish, and you only
want to do a generic data structure with fast lookups on the content
of the items? Or do you really need relational semantics?

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


Re: [Haskell-cafe] relational data representation in memory using haskell?

2008-05-21 Thread Dan Weston
Consider SQLite [1], which is "a software library that implements a 
self-contained, serverless, zero-configuration, transactional SQL 
database engine."


It is embeddable, can reside completely in memory (including the data), 
and can be saved and restored to disk when needed. It neatly fills the 
niche between maps and a client/server database model.


It has a C API which you can wrap as needed with the FFI, and you 
wouldn't need more than a dozen or so functions to start with (it 
understands SQL too).


[1] http://www.sqlite.org/

Marc Weber wrote:

On Wed, May 21, 2008 at 05:05:21PM -0700, Jeremy Shaw wrote:

At Thu, 22 May 2008 01:04:24 +0200,
Marc Weber wrote:


Some way representing relational data which is typically stored in
databases such as Postgresql..

Rewriting something like Postgresql in haskell would take ages..
So I'd be satisfied with having in memory representation only (this
would fit the HAppS state system very well .. :)
Are you familiar with the HAppS IxSet library? 

Yes - not with all that sybwith-class stuff though.
There are some issues:
its dynamic : doesn't this waste some CPU cycles?
no multi indexes..
maybe some space leaks because the data type containing the Maps is
build after each filter maybe leaving unevaluating chunks - Saizan has
told me about it on HAppS.. And you can't extend it to the degree I'd
like to (eg throw a query at it and let the system figure out which
indexes to use)
And last but not least: It does'nt support relations at all yet.
So all the effort adding / checking foreign keys etc has to be done
anyway.

Thanks Marc
___
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] relational data representation in memory using haskell?

2008-05-21 Thread Marc Weber
On Wed, May 21, 2008 at 05:05:21PM -0700, Jeremy Shaw wrote:
> At Thu, 22 May 2008 01:04:24 +0200,
> Marc Weber wrote:
> 
> > Some way representing relational data which is typically stored in
> > databases such as Postgresql..
> > 
> > Rewriting something like Postgresql in haskell would take ages..
> > So I'd be satisfied with having in memory representation only (this
> > would fit the HAppS state system very well .. :)
> 
> Are you familiar with the HAppS IxSet library? 
Yes - not with all that sybwith-class stuff though.
There are some issues:
its dynamic : doesn't this waste some CPU cycles?
no multi indexes..
maybe some space leaks because the data type containing the Maps is
build after each filter maybe leaving unevaluating chunks - Saizan has
told me about it on HAppS.. And you can't extend it to the degree I'd
like to (eg throw a query at it and let the system figure out which
indexes to use)
And last but not least: It does'nt support relations at all yet.
So all the effort adding / checking foreign keys etc has to be done
anyway.

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


Re: [Haskell-cafe] Ubuntu and ghc

2008-05-21 Thread Darrin Thompson
2008/5/21 Galchin, Vasili <[EMAIL PROTECTED]>:
> Hi Dan,
>
>  I am still looking into this myself. I just stumbled across the URL
> below. i would suggest keeping an eye on this URL for more news.
>

I quit using the ubuntu debs. I've just been downloading the linux
binaries and runing them in some odd subdir, and using
--prefix=/path/to/my/ghc with cabal, and much happier for it. Is there
some value with the official debs that I'm missing?

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


Re: [Haskell-cafe] relational data representation in memory using haskell?

2008-05-21 Thread Jeremy Shaw
At Thu, 22 May 2008 01:04:24 +0200,
Marc Weber wrote:

> Some way representing relational data which is typically stored in
> databases such as Postgresql..
> 
> Rewriting something like Postgresql in haskell would take ages..
> So I'd be satisfied with having in memory representation only (this
> would fit the HAppS state system very well .. :)

Are you familiar with the HAppS IxSet library? 

You would do something like:



$( deriveAll [''Ord,''Eq,''Read,''Show,''Default] 
   [d|
data CD = CD AlbumTitle Artist [Track]
newtype Artist = Artist String
newtype AlbumTitle = AlbumTitle String
data Track = Track TrackTitle TrackIndex 
newtype TrackIndex = TrackIndex Int
newtype TrackTitle = TrackTitle String
  |])

$(inferIxSet "CDS" 'noCalcs [''AlbumTitle, ''TrackTitle, ''Artist])

This creates a table with indexs on AlbumTitle, TrackTitle, and
Artist.

You can do a simple query like:

  mycds @= (Artist "Wesley Willis")

to get all the tracks by Wesley Willis.

You should be able to build joins, etc on top of that. 

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


Re: [Haskell-cafe] one-way monads

2008-05-21 Thread Creighton Hogg
On Wed, May 21, 2008 at 6:37 PM, Neil Mitchell <[EMAIL PROTECTED]> wrote:

> Hi
>
> > Real Haskell Programmers Only Use Top Level IO!
> >
> > (But then again, real programmers wouldn't use Haskell:
> > http://www.pbm.com/~lindahl/real.programmers.html
> )
>
> It's amazing how many phone interviews I've done where the HR person
> at the other end tries to tick the "knows Pascal" box, despite me
> trying my hardest to pronounce Haskell. Maybe Haskell ==
> Pascal, under some fairly light equality
>
> Thanks
>
> Neil
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>

I've had the same experience!  I don't swallow my 'h's in the slightest, so
I'm presuming that it's just overly eager pattern matching.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] one-way monads

2008-05-21 Thread Neil Mitchell
Hi

> Real Haskell Programmers Only Use Top Level IO!
>
> (But then again, real programmers wouldn't use Haskell:
> http://www.pbm.com/~lindahl/real.programmers.html)

It's amazing how many phone interviews I've done where the HR person
at the other end tries to tick the "knows Pascal" box, despite me
trying my hardest to pronounce Haskell. Maybe Haskell ==
Pascal, under some fairly light equality

Thanks

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


Re: [Haskell-cafe] one-way monads

2008-05-21 Thread Dan Piponi
On Wed, May 21, 2008 at 4:08 PM, Lennart Augustsson
<[EMAIL PROTECTED]> wrote:
> I certainly don't use 50% IO monads.  I regard any use of the IO monad
> except at the top level as a failure. :)

Real Haskell Programmers Only Use Top Level IO!

(But then again, real programmers wouldn't use Haskell:
http://www.pbm.com/~lindahl/real.programmers.html)
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] one-way monads

2008-05-21 Thread Don Stewart
lennart:
> I certainly don't use 50% IO monads.  I regard any use of the IO monad
> except at the top level as a failure. :)

IO fail

-- Don

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


Re: [Haskell-cafe] one-way monads

2008-05-21 Thread Lennart Augustsson
I certainly don't use 50% IO monads.  I regard any use of the IO monad
except at the top level as a failure. :)

On Wed, May 21, 2008 at 7:14 PM, Dan Weston <[EMAIL PROTECTED]> wrote:
> Dan Doel wrote:
>>
>> On Tuesday 20 May 2008, [EMAIL PROTECTED] wrote:
>>>
>>> Actually, it's true less than 50% of the time.  In particular, it's
>>> not true of any monad transformer.
>>
>> Sure it is. Any particular transformer t typically comes with some
>> particular way of writing a function of type t m a -> m a (you may have to
>> throw away some t-related stuff, of course).
>>
>> Since a specific transformed monad is built from a specific monad, and a
>> specific transformer, and specific transformers are likely to have a
>> function of type t m a -> m a, and specific monads are likely to have
>> functions of type m a -> a, you can compose them to get a function of type t
>> m a -> a for the specific monad t m. And so on for transformed-transformed
>> monads. :)
>>
>> That only fails if either of the specific pieces fails to have the right
>> function, which happens well under 50% of the time, I think (IO and STM are
>> the ones that immediately occur to me (barring a certain evil function),
>> although you could make a case for ST by technicality; no failing
>> transformers come to mind (except CCT if we're counting ST), but I haven't
>> wracked my brain very hard).
>>
>> -- Dan
>
> The claim was "less than 50% of the time", not "less than 50% of the monads
> in the standard libraries". I wonder what fraction of monads in real code
> the IO monad alone accounts for? 50% does not seem implausible to me.
>
> Dan Weston
>
> ___
> 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] relational data representation in memory using haskell?

2008-05-21 Thread Marc Weber
I'm kind of stuck that's why I'm posting here to ask wether this makes
sense at all, maybe someone else has already done it?

What I'd like to have:

Some way representing relational data which is typically stored in
databases such as Postgresql..

Rewriting something like Postgresql in haskell would take ages..
So I'd be satisfied with having in memory representation only (this
would fit the HAppS state system very well .. :)
Why ?
* type safety
* less conversions compared to SQL data
* no need to switch processes, parse SQL etc so maybe it's even faster?
  (a small benchmark showed that inserting 2 Ints into a list was 8
   times faster than using MySQL parsing 2 INSERT INTO x (1)
   statements )


I'd like to illustrate two different ideas using a small example:
(A)
data CD = CD { title :: String, tracks :: [ Track ] }
data Track = Track { track :: String, cd :: CD }
data PDB = PDB { cds :: Set CD, tracks :: Set Track }

because it's not using foreign ids but kind of pointers I'll call this
the pointer method

using uniq ids it would look like this:
(B)
data CD = CD { id : Int,  title :: String, tracks :: [Int ] }
data Track = Track { trackId :: Int,  track :: String, cd :: Int }
data IDB = IDB { cds :: Map Int CD, tracks :: Map Int Track }
I will call it I DB (I = using ids)

PDB: pro : * less work when doing joins (no need to look foreign rows up)
 con : * you need uniq ids or such when serializing to disk
   * When updating a track you'll also have to update the pointer
 stored in cds. and if you had another table shelfs.. this
 had to be updated as well..

IDB: the other way round


I find the idea not using any lookups when using joins appealing.

Of course having a simple
data Table = Table Map UniqId Rec 

isn't enough, sometimes you need more than one index or even a multi index:
data Table = Table { byId :: Map Int Rec
 , byNameAndAge :: Map String (Map Int (Set Rec)) }

Note that I've used Set here as well because this index does'nt have to
be uniq! starting to write an
insertTable :: Table -> Rec -> Table
more than twice is getting tedious..

Of course you can start using some type hackery to insert a rec
into all maps automatically.. but you'll get into trouble making
the type system apply the best index not the first matching one.
(I bet this could be done using HList etc somehow as well.. )
So my current attempt is defining the database using some data types and
make template haskell derive those insertIntoTable and update functions.

I've added the draft below. But before continuing spending much time on
it I'd like to get your advice: Is there a chance that it will pay off?

Some general considerations:
haskell solution con:
haskell can get close to C but in general it may be >10 times slower 
when
not caring too much about design or writing low level (see recent thread
about md5 or one where David Roundy has said something about a matrix 
thread:
only 10 times slower?)

Using a garbage collector on database data (some hundred MB)
might not be the optimal way because I feel you can tell exactly
when you no longer need a piece of allocated memory here?
So some time might be wasted.

projects tend to run longer as expected.. And if data no longer
fits into memory .. :(... -> bad performance
I think systems such as postgresql do scale much better if you
have some gbs of data and only use the most recent X records
frequently.. So maybe you'll have to spend time later which
you've won by using a haskell relational data representation in
memory only.. Another solution: use clusters - I don't have any
experience.
 
pro:
much more safety (STM, type system ..) there are less
possibilities making compared to C / PHP etc

Do you also think (A) is more interesting because some load (looking up
foreign keys) is moved on insert / delete and update operations taking
less time in but are called more frequently thus maybe reducing peak
load on queries?

Of course some time would have to be spend on queries wich might
look like this:
let queryresult = $(query ( tables + constraints + relations ) ) db
automatically generating the query function taking into account expected
index cardinality etc..

Any comments, suggestions, links to existing solutions (except coddfish,
haskelldb) ?

Marc Weber


draft
= types represeting tables and db 
module RDMH.Types where
import Language.Haskell.TH
import Language.Haskell.TH.Syntax

data Uniqueness = Uniq | NotUniq deriving (Show, Eq)
data ModifyMode = InsertOnly | UpdateInsert | UpdateInsertDelete deriving 
(Show, Eq)

type TypeS = String -- a name of a data type (data A = ..)

data Index = I {
uniqueness :: Uniqueness
, key :: Exp  -- a fuction rec 

Re: [Haskell-cafe] Ubuntu and ghc

2008-05-21 Thread Galchin, Vasili
Hi Dan,

 I am still looking into this myself. I just stumbled across the URL
below. i would suggest keeping an eye on this URL for more news.

Vasili

On Wed, May 21, 2008 at 5:45 PM, Dan Weston <[EMAIL PROTECTED]>
wrote:

> Now you tell me! I also upgraded late last night and got the exact same
> problem. :(
>
> I just uninstalled the ghc from the Update Manager and was going to
> reinstall tonight. Are you saying that something else is screwed up because
> of this?
>
> Galchin, Vasili wrote:
>
>> Hello,
>>
>>   https://bugs.launchpad.net/ubuntu/+source/gtk2hs/+bug/229489 
>> this is almost identical to my problem. I am just trying to help others on
>> this list who are using Ubuntu Linux to avoid my predicament!
>>
>> Kind regards, Vasili
>>
>>
>> 
>>
>> ___
>> 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] Ubuntu and ghc

2008-05-21 Thread Dan Weston
Now you tell me! I also upgraded late last night and got the exact same 
problem. :(


I just uninstalled the ghc from the Update Manager and was going to 
reinstall tonight. Are you saying that something else is screwed up 
because of this?


Galchin, Vasili wrote:

Hello,

   https://bugs.launchpad.net/ubuntu/+source/gtk2hs/+bug/229489  
this is almost identical to my problem. I am just trying to help others 
on this list who are using Ubuntu Linux to avoid my predicament!


Kind regards, Vasili




___
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] Ubuntu and ghc

2008-05-21 Thread Galchin, Vasili
Hello,

   https://bugs.launchpad.net/ubuntu/+source/gtk2hs/+bug/229489 
this is almost identical to my problem. I am just trying to help others on
this list who are using Ubuntu Linux to avoid my predicament!

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


Re: [Haskell-cafe] Newbie: State monad example questions

2008-05-21 Thread Dmitri O.Kondratiev
-- Jules, Oliver, thanks! Things are getting clarified, I hope.
-- Let me summarize how I now understand getAny operation, please correct me
if I am wrong.

getAny :: (Random a) => State StdGen a
getAny = do g  <- get
(x,g') <- return $ random g
put g'
return x

{--
getAny operation may be abbreviated as:

do {
-- 1) x calculation, equivalent to (x,g2) = random g1
-- 2) return x ~> State $ \s -> (x,s) -- puts x into State container

Thus getAny returns a State instantiated with a function which is a
composition of several binds <<= from the above 'do' block and which
calculates 'x'
--}

-- Then we can use  this State object (returned by getAny) in a function
generating random values such as:

makeRnd :: StdGen -> (Int, StdGen)
makeRnd = runState (do
  y <- getAny
  return y)

{--
where:

y <- getAny
return y

passes a first value from the tuple generated by getAny State function  into
'y' and puts 'y' into a new State object.
After that 'runState' in makeRnd extracts from this new State a function
parametrized by 'y' value.
As a result we get curried 'makeRnd' which we can call with some generator
instance and get a random value.
--}

On Wed, May 21, 2008 at 10:31 PM, Olivier Boudry <[EMAIL PROTECTED]>
wrote:

> On Wed, May 21, 2008 at 11:10 AM, Dmitri O.Kondratiev <[EMAIL PROTECTED]>
> wrote:
>
>> But how will 'g1' actually get delivered from 'makeRandomValueST g1' to
>> invocation of 'getAny' I don't yet understand!
>>
>>
> It may be easier to understand the state passing if you remove the do
> notation and replace get, put and return with their definition in the
> instance declarations (Monad and MonadState).
>
> getAny :: (Random a) => State StdGen a
> getAny = do g  <- get
> (x,g') <- return $ random g
> put g'
> return x
>
> get = State $ \s -> (s, s) -- copy the state as a return value and pass
> state
> put s = State $ \_ -> ((), s) -- return unit, ignore the passed state and
> replace it with the state given as parameter.
> return a = State $ \s -> (a, s) -- return given value and pass state.
>
> getAnyNoSugar :: (Random a) => State StdGen a
> getAnyNoSugar = (State $ \s -> (s, s)) >>= \g ->
> (State $ \s -> (random g, s)) >>= \(x,g') ->
> (State $ \_ -> ((), g')) >>
> (State $ \s -> (x, s))
>
> The function is still useable this way and the state transformations should
> be a bit more visible. The first element of the tuple is the value that will
> be used to call the next function (of type Monad m => a -> m b). The second
> element of the tuple is the state and the (>>=) operator will handle passing
> it between actions.
>
> Desugaring the (>>=) and (>>) operators would give you something like this
> (I replaced `s` with `y` in the `put` and `return` desugaring and simplified
> it):
>
> State $ \s = let
>   (g, s') = (\y -> (y,y)) s
>   ((x,g'), s'') = (\y -> (random g, y)) s'
>   (_, s''') = (\_ -> ((), g')) s''
>   in (x, s''')
>
> Which is explict state passing between function calls. Extract the State
> using `runState`, run it with an initial state and it should give you the
> expected result.
>
> Regards,
>
> Olivier.
>



-- 
Dmitri O. Kondratiev
[EMAIL PROTECTED]
http://www.geocities.com/dkondr
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] MD5 performance optimizations

2008-05-21 Thread Salvatore Insalaco
2008/5/21 Andrew Coppin <[EMAIL PROTECTED]>:
> Woo!
>
> Salvatore kindly sent me a Darcs patch, and applying it does indeed make it
> run faster. Yay!

Hi Andrew,
I'm glad that -fvia-c works for you: maybe it's a Mac OS X specific bug?

Anyway, did you compile with -fvia-c -optc-O3? I expect
register-intensive code like this to be at least 20% faster with gcc.

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


Re: [Haskell-cafe] MD5 performance optimizations

2008-05-21 Thread Andrew Coppin

Woo!

Salvatore kindly sent me a Darcs patch, and applying it does indeed make it run 
faster. Yay!

[Note that -fvia-c works just fine for me. It doesn't appear to produce a huge 
speed difference, but it compiles just fine.]

Thanks for the tips, guys! :-D The changes are in the online Darcs repo.



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


Re: [Haskell-cafe] Newbie: State monad example questions

2008-05-21 Thread Olivier Boudry
On Wed, May 21, 2008 at 11:10 AM, Dmitri O.Kondratiev <[EMAIL PROTECTED]>
wrote:

> But how will 'g1' actually get delivered from 'makeRandomValueST g1' to
> invocation of 'getAny' I don't yet understand!
>
>
It may be easier to understand the state passing if you remove the do
notation and replace get, put and return with their definition in the
instance declarations (Monad and MonadState).

getAny :: (Random a) => State StdGen a
getAny = do g  <- get
(x,g') <- return $ random g
put g'
return x

get = State $ \s -> (s, s) -- copy the state as a return value and pass
state
put s = State $ \_ -> ((), s) -- return unit, ignore the passed state and
replace it with the state given as parameter.
return a = State $ \s -> (a, s) -- return given value and pass state.

getAnyNoSugar :: (Random a) => State StdGen a
getAnyNoSugar = (State $ \s -> (s, s)) >>= \g ->
(State $ \s -> (random g, s)) >>= \(x,g') ->
(State $ \_ -> ((), g')) >>
(State $ \s -> (x, s))

The function is still useable this way and the state transformations should
be a bit more visible. The first element of the tuple is the value that will
be used to call the next function (of type Monad m => a -> m b). The second
element of the tuple is the state and the (>>=) operator will handle passing
it between actions.

Desugaring the (>>=) and (>>) operators would give you something like this
(I replaced `s` with `y` in the `put` and `return` desugaring and simplified
it):

State $ \s = let
  (g, s') = (\y -> (y,y)) s
  ((x,g'), s'') = (\y -> (random g, y)) s'
  (_, s''') = (\_ -> ((), g')) s''
  in (x, s''')

Which is explict state passing between function calls. Extract the State
using `runState`, run it with an initial state and it should give you the
expected result.

Regards,

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


Re: [Haskell-cafe] one-way monads

2008-05-21 Thread Dan Weston

Dan Doel wrote:

On Tuesday 20 May 2008, [EMAIL PROTECTED] wrote:

Actually, it's true less than 50% of the time.  In particular, it's
not true of any monad transformer.


Sure it is. Any particular transformer t typically comes with some particular 
way of writing a function of type t m a -> m a (you may have to throw away 
some t-related stuff, of course).


Since a specific transformed monad is built from a specific monad, and a 
specific transformer, and specific transformers are likely to have a function 
of type t m a -> m a, and specific monads are likely to have functions of 
type m a -> a, you can compose them to get a function of type t m a -> a for 
the specific monad t m. And so on for transformed-transformed monads. :)


That only fails if either of the specific pieces fails to have the right 
function, which happens well under 50% of the time, I think (IO and STM are 
the ones that immediately occur to me (barring a certain evil function), 
although you could make a case for ST by technicality; no failing 
transformers come to mind (except CCT if we're counting ST), but I haven't 
wracked my brain very hard).


-- Dan


The claim was "less than 50% of the time", not "less than 50% of the 
monads in the standard libraries". I wonder what fraction of monads in 
real code the IO monad alone accounts for? 50% does not seem implausible 
to me.


Dan Weston

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


[Haskell-cafe] Re: Return user state in Parsec

2008-05-21 Thread Achim Schneider
Maciej Podgurski <[EMAIL PROTECTED]> wrote:

> Hi,
> 
> I'm currently writing a parser using the Parsec library. What I want
> is to store the order of each subparser called in a user state. So
> every single parser will be marked with a label that is stored in a
> special treelike structure when the parser is run.
> 
> My problem is to return the last state of this structure when a parse 
> error occurred. This information shall be used to display a kind of 
> stack trace showing the order of the parser calls for debug purposes. 
> Any ideas how to achieve this?
> 
Write the parser in a way that can never, ever fail, and return the
parse error as part of your tree. That is, write a wrapper that puts
optionMaybe's around every parser you call and records label, position
and everything, and maybe go ahead and roll your own monad inside of
ParsecT

PS: don't try to influence the parsing based on state, if you don't
feel like despairing. Messy cans of worms lay ahead.


-- 
(c) this sig last receiving data processing entity. Inspect headers for
past copyright information. All rights reserved. Unauthorised copying,
hiring, renting, public performance and/or broadcasting of this
signature prohibited. 

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


RE: [Haskell-cafe] [Solved] Installing Cabal-Install

2008-05-21 Thread Aditya Siram

That worked. Thank you.


> Date: Wed, 21 May 2008 12:22:33 -0400
> From: [EMAIL PROTECTED]
> To: [EMAIL PROTECTED]
> Subject: Re: [Haskell-cafe] Installing Cabal-Install
> CC: haskell-cafe@haskell.org
> 
> On Wed, May 21, 2008 at 12:11 PM, Aditya Siram  wrote:
>>
>> Hi all,
>> I am trying to install cabal-install so I can install xmonad-contrib. I have 
>> all the dependancies in place but when I do:
>> runhaskell Setup.lhs build
>> I get:
>> Hackage/Types.hs:19:29:
>>Module `Distribution.Version' does not export `Dependency'
>>
>> Any ideas?
> 
> If you're trying to install cabal-install from its darcs repo, you
> need the latest Cabal from *its* repo.
> 
> darcs get --partial http://darcs.haskell.org/cabal/
> 
> You'll have to build and install Cabal, then build cabal-install against it.
> 
> -- 
>  Denis

_
E-mail for the greater good. Join the i’m Initiative from Microsoft.
http://im.live.com/Messenger/IM/Join/Default.aspx?source=EML_WL_ 
GreaterGood___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Return user state in Parsec

2008-05-21 Thread Maciej Podgurski

Hi,

I'm currently writing a parser using the Parsec library. What I want is 
to store the order of each subparser called in a user state. So every 
single parser will be marked with a label that is stored in a special 
treelike structure when the parser is run.


My problem is to return the last state of this structure when a parse 
error occurred. This information shall be used to display a kind of 
stack trace showing the order of the parser calls for debug purposes. 
Any ideas how to achieve this?


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


Re: [Haskell-cafe] Installing Cabal-Install

2008-05-21 Thread Denis Bueno
On Wed, May 21, 2008 at 12:11 PM, Aditya Siram <[EMAIL PROTECTED]> wrote:
>
> Hi all,
> I am trying to install cabal-install so I can install xmonad-contrib. I have 
> all the dependancies in place but when I do:
> runhaskell Setup.lhs build
> I get:
> Hackage/Types.hs:19:29:
>Module `Distribution.Version' does not export `Dependency'
>
> Any ideas?

If you're trying to install cabal-install from its darcs repo, you
need the latest Cabal from *its* repo.

darcs get --partial http://darcs.haskell.org/cabal/

You'll have to build and install Cabal, then build cabal-install against it.

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


[Haskell-cafe] Installing Cabal-Install

2008-05-21 Thread Aditya Siram

Hi all,
I am trying to install cabal-install so I can install xmonad-contrib. I have 
all the dependancies in place but when I do:
runhaskell Setup.lhs build
I get:
Hackage/Types.hs:19:29:
Module `Distribution.Version' does not export `Dependency'

Any ideas?

Thanks ...
Deech
_
Make every e-mail and IM count. Join the i’m Initiative from Microsoft.
http://im.live.com/Messenger/IM/Join/Default.aspx?source=EML_WL_ 
MakeCount___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Newbie: State monad example questions

2008-05-21 Thread Jules Bean

Dmitri O.Kondratiev wrote:

Jules,

Stupid question, please bear with me:

x :: Int -- x declared, but not constructed
x = 1 -- x constructed

s1 :: State StdGen a -- s1 declared, yes, but why s1 is *also already 
constructed* ?


it's not.

it's constructed when you do

s1 = return 1

... or ...

s1 = get >>= put

.. or some other more complex interaction, perhaps using do notation.

It's the >>= or the return that construct the State, just as the '1' is 
enough to construct the Int.


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


Re: [Haskell-cafe] Newbie: State monad example questions

2008-05-21 Thread Dmitri O.Kondratiev
Jules,

Stupid question, please bear with me:

x :: Int -- x declared, but not constructed
x = 1 -- x constructed

s1 :: State StdGen a -- s1 declared, yes, but why s1 is *also already
constructed* ?

On Wed, May 21, 2008 at 6:54 PM, Jules Bean <[EMAIL PROTECTED]> wrote:

> Dmitri O.Kondratiev wrote:
>
>> Thanks everybody for your help!
>> Oliver,  you provided an excellent write-up  on  State  monad without
>>  going  into 'scary' :) details, great work indeed!
>> Alas,  in this case I need the details, and in particular the most scary
>> ones!
>>
>> So let's start with fundamental and most intriguing  (to me) things:
>>
>> getAny :: (Random a) => State StdGen a
>> getAny = do g <- get -- magically get the current StdGen
>>
>> First line above declares a data type:
>>
>> State StdGen a
>>
>> which is constructed with the function:
>>
>> State {runState :: (StdGen -> (a, StdGen))}
>>
>> Q1: Where in the example (
>> http://www.haskell.org/all_about_monads/examples/example15.hs) data of
>> this type *actually gets constructed* ?
>>
>
> Actually get constructed?
>
> It gets constructed by >>= and return, both of which construct state
> objects:
>
> instance Monad (State s) where
>return a = State $ \s -> (a, s)
>m >>= k  = State $ \s -> let
>(a, s') = runState m s
>in runState (k a) s'
>
>
> How do >>= and return get called? Well you can see explicit calls to
> return. The >>= is implicit in the way do-notation is desugared.
>
> getAny = do g  <- get
>let (x,g') = random g
>put g'
>return x
>
> rewrites to
>
> getAny = get >>= \g -> ( let (x,g') = random g in (put g' >> return x) )
>
> where I have added some not strictly necessary ()s and taken the liberty of
> changing the confusing "a <- return x" idiom to "let a = x".
>
> So the *actually gets constructed* part is that use of >>= .
>
> HTH,
>
> Jules
>



-- 
Dmitri O. Kondratiev
[EMAIL PROTECTED]
http://www.geocities.com/dkondr
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Newbie: State monad example questions

2008-05-21 Thread Dmitri O.Kondratiev
State is a data type. As any other data type it can be instantiated. State
instance is a structure of one record that contains (\s ->(a,s)) lambda
function. This function can be parametrized by types of its arguments 's'
and 'a'. I don't see magic here :)

Ok, then from declaration:

getAny :: (Random a) => State StdGen a
getAny = do g <- get

we can say that looking at type 'State StdGen a' compiler concludes that
later on in the 'do' block statements like:

g <- get

will resolve into bind function (>>=) *as bind is defined for State monad*.
Fine, I assume compiler is capable of such reasoning.

Then
g <- get
may be written as:

get >>= \g -> ...

To understand how State monad work, I wrote MyState data type that emulates
State and (>=>) 'bind' function that emulates 'real' bind (>>=)
implementation for State monad:

(>=>) :: MyState StdGen Int -> (Int -> MyState StdGen Int) ->  MyState
StdGen Int
(MyState ms) >=> fn =  MyState(\seed -> let(v1, newSeed) = ms seed
   ms2 = fn v1
in (runState ms2) newSeed)

Inserting 'get' into >>= (or >=> in my code) will in fact result in thinking
about State instance that 'get' returns as denoted by 'ms' in this code of
mine.
>From 'get' definition follows that function hiding behind 'ms' State
instance is:

\s -> (s,s)

So when later we will feed generator 'g1' into this function will get:
(g1,g1)
And we also will get:
v1 = g1
newSeed = g1
ms2 = fn g1

and finally 'g' in expression 'g <- get' will be equal to 'g1' that will be
later fed in through the function call:

'makeRandomValueST g1'

But how will 'g1' actually get delivered from 'makeRandomValueST g1' to
invocation of 'getAny' I don't yet understand!


On Wed, May 21, 2008 at 5:55 PM, Olivier Boudry <[EMAIL PROTECTED]>
wrote:

> On Wed, May 21, 2008 at 8:42 AM, Dmitri O.Kondratiev <[EMAIL PROTECTED]>
> wrote:
>
>> So let's start with fundamental and most intriguing  (to me) things:
>>
>> getAny :: (Random a) => State StdGen a
>> getAny = do g <- get -- magically get the current StdGen
>>
>> First line above declares a data type:
>>
>> State StdGen a
>>
>> which is constructed with the function:
>>
>> State {runState :: (StdGen -> (a, StdGen))}
>>
>> Q1: Where in the example (
>> http://www.haskell.org/all_about_monads/examples/example15.hs) data of
>> this type *actually gets constructed* ?
>
>
> In getAny and getOne. Their signature has type `State StdGen a`. The use of
> the do notation to chain the actions and the use of get and put from the
> State Monad make this function a `State StdGen a`.
>
>
>> Looking at example15.hs code we see the following sequence:
>>
>> 1) makeRandomValue g -- where g is a StdGen instance, ok
>>
>> 2) makeRandomValue g ~> expands into ~>
>>
>> ~>  (runState (do { ...; b <- getAny;...})) g
>>
>>
>> This last expression puzzles me. I can understand, for example, this:
>>
>> State StdGen a :: aState
>> StdGen:: g1
>>
>> (v, g2) = (runStae aState) g1 -- this returns a state function which is
>> then passed a generator g1, and as result returns pair (value, new generaor)
>>
>> But '(runState (do ...)) g' implies that expression (do ...)  must be
>> somehow of type 'State StdGen a' ?
>> Yet, when we call 'makeRandomValue g' we just pass to this function
>> g::StgGen
>>
>> So, my next question:
>> Q2: How (do {...;b <- getAny;...}) becomes an *instance* of type 'State
>> StdGen a' ?
>>
>
> In 2) I suppose you're talking of `makeRandomValueST` as `makeRandomValue`
> is the function that runs without the State Monad.
>
> makeRandomValueST does not build a `State StdGen a` it uses `runState` to
> run the (do block) which has type `State StdGen a`.
>
> Using `runState` will run an action which has `State s a` type on an
> initial state `s` and return a `(a, s)` tuple.
>
> `makeRandomValueST` does just the same using its parameter `g :: StdGen` as
> initial state and returning a tuple of type `(MyType, StdGen)`. Now what
> makes the do-block used in `runState` an instance of type `State StdGen a`
> is type inference. `runState` expects a `State s a` as first argument and
> `s` as second argument. The function signature, the use of `>>=` and
> `return` (desugared do-block) to combine actions and the use of actions
> already having that type like `getAny` and `getOne` will make your do block
> a `State StdGen a`.
>
> I'm not sure we can talk of building an instance of `State s a`. It's a
> "parameterized variant" of `State s a` which itself is an instance of the
> Monad class. We're just assigning types to the `s` and `a` type variables in
> `State s a`.
>
> In short `runState` takes the value (s -> (a, s)) out of the State monad.
> In the case of the State Monad that value is a function and it is run on the
> initial state. Its usually what runX functions do. They have type
> `(Monad m) => m a -> a`.
>
> Actions in the State Monad have type `State (s -> (a, s))`. The value
> stored in the State constructor is a

Re: [Haskell-cafe] Newbie: State monad example questions

2008-05-21 Thread Jules Bean

Dmitri O.Kondratiev wrote:

Thanks everybody for your help!
Oliver,  you provided an excellent write-up  on  State  monad without  
going  into 'scary' :) details, great work indeed!
Alas,  in this case I need the details, and in particular the most scary 
ones!


So let's start with fundamental and most intriguing  (to me) things:

getAny :: (Random a) => State StdGen a
getAny = do g <- get -- magically get the current StdGen

First line above declares a data type:

State StdGen a

which is constructed with the function:

State {runState :: (StdGen -> (a, StdGen))}

Q1: Where in the example 
(http://www.haskell.org/all_about_monads/examples/example15.hs) data of 
this type *actually gets constructed* ?


Actually get constructed?

It gets constructed by >>= and return, both of which construct state 
objects:


instance Monad (State s) where
return a = State $ \s -> (a, s)
m >>= k  = State $ \s -> let
(a, s') = runState m s
in runState (k a) s'


How do >>= and return get called? Well you can see explicit calls to 
return. The >>= is implicit in the way do-notation is desugared.


getAny = do g  <- get
let (x,g') = random g
put g'
return x

rewrites to

getAny = get >>= \g -> ( let (x,g') = random g in (put g' >> return x) )

where I have added some not strictly necessary ()s and taken the liberty 
of changing the confusing "a <- return x" idiom to "let a = x".


So the *actually gets constructed* part is that use of >>= .

HTH,

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


Re: [Haskell-cafe] ghc-pkg package.conf files?

2008-05-21 Thread Brandon S. Allbery KF8NH


On 2008 May 21, at 2:35, Galchin, Vasili wrote:

hmm ... ;^). I found and read through part of ghc-pkg.hs ..  
ghc-6.8.2/utils/ghc-pkg/ .. I have 6 "broken" Haskell package  
databases (not debian) under /usr/lib/haskell-packages/ghc6/lib/.  
When I run ghc-pkg on them I get [EMAIL PROTECTED]:/usr/lib/haskell- 
packages/ghc6/lib/cairo-0.9.12.1$ ghc-pkg -- 
package=cairo.package.conf list

ghc-pkg: cairo.package.conf: parse error in package config file



ghc doesn't use those; sounds like vendor packages with presumably  
some way to combine them into the master package.conf.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] Newbie: State monad example questions

2008-05-21 Thread Olivier Boudry
On Wed, May 21, 2008 at 8:42 AM, Dmitri O.Kondratiev <[EMAIL PROTECTED]>
wrote:

> So let's start with fundamental and most intriguing  (to me) things:
>
> getAny :: (Random a) => State StdGen a
> getAny = do g <- get -- magically get the current StdGen
>
> First line above declares a data type:
>
> State StdGen a
>
> which is constructed with the function:
>
> State {runState :: (StdGen -> (a, StdGen))}
>
> Q1: Where in the example (
> http://www.haskell.org/all_about_monads/examples/example15.hs) data of
> this type *actually gets constructed* ?


In getAny and getOne. Their signature has type `State StdGen a`. The use of
the do notation to chain the actions and the use of get and put from the
State Monad make this function a `State StdGen a`.


> Looking at example15.hs code we see the following sequence:
>
> 1) makeRandomValue g -- where g is a StdGen instance, ok
>
> 2) makeRandomValue g ~> expands into ~>
>
> ~>  (runState (do { ...; b <- getAny;...})) g
>
>
> This last expression puzzles me. I can understand, for example, this:
>
> State StdGen a :: aState
> StdGen:: g1
>
> (v, g2) = (runStae aState) g1 -- this returns a state function which is
> then passed a generator g1, and as result returns pair (value, new generaor)
>
> But '(runState (do ...)) g' implies that expression (do ...)  must be
> somehow of type 'State StdGen a' ?
> Yet, when we call 'makeRandomValue g' we just pass to this function
> g::StgGen
>
> So, my next question:
> Q2: How (do {...;b <- getAny;...}) becomes an *instance* of type 'State
> StdGen a' ?
>

In 2) I suppose you're talking of `makeRandomValueST` as `makeRandomValue`
is the function that runs without the State Monad.

makeRandomValueST does not build a `State StdGen a` it uses `runState` to
run the (do block) which has type `State StdGen a`.

Using `runState` will run an action which has `State s a` type on an initial
state `s` and return a `(a, s)` tuple.

`makeRandomValueST` does just the same using its parameter `g :: StdGen` as
initial state and returning a tuple of type `(MyType, StdGen)`. Now what
makes the do-block used in `runState` an instance of type `State StdGen a`
is type inference. `runState` expects a `State s a` as first argument and
`s` as second argument. The function signature, the use of `>>=` and
`return` (desugared do-block) to combine actions and the use of actions
already having that type like `getAny` and `getOne` will make your do block
a `State StdGen a`.

I'm not sure we can talk of building an instance of `State s a`. It's a
"parameterized variant" of `State s a` which itself is an instance of the
Monad class. We're just assigning types to the `s` and `a` type variables in
`State s a`.

In short `runState` takes the value (s -> (a, s)) out of the State monad. In
the case of the State Monad that value is a function and it is run on the
initial state. Its usually what runX functions do. They have type
`(Monad m) => m a -> a`.

Actions in the State Monad have type `State (s -> (a, s))`. The value stored
in the State constructor is a function. Combining two actions using the
`>>=` and `>>` functions (hidden or not in a do-block) just create a bigger
`s -> (a, s)` function. The function is "hidden" in a `State` constructor
just to ensure you don't run it when you don't want to. When you whant to
run the "big function" you first have to take it out of the State
constructor using the accessor `runState` and then run it on the initial
state. The end result is of course a (a, s) tuple.

Clear as mud, isn't it? It tooks me lots of time to understand how the State
Monad works. I read many tutorial and still understood nothing about it. Its
only by looking at the source code, playing with it and trying to rewrite
the State Monad that I finally got an understanding of it. So I'm not sure
you'll get it before you go through the same kind of path.

The key to understand this Monad, at least based on my experience, is to
keep in mind that `>>=` just assembles small state passing functions into
bigger ones, but does not run the built function until you explicitly use
the `runState` function on it.

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


Re: [Haskell-cafe] RealFloat constraint on Complex type

2008-05-21 Thread Bryan O'Sullivan
Richard A. O'Keefe wrote:

>> I think the practice of constraint in type definitions is generally
>> discouraged,
> 
> Is this true?  If so, why?

As a practical matter, a Haskell 98 constraint infects every place you
might like to use the type.  They're like prion proteins, corrupting
everything they touch, replicating implacably as they go.

Here's the usual pattern that leads to the abandonment of constraints on
types by the previously innocent coder.  You add the constraint in the
one place you think you need it, only to find that the type checker
insists that three more are now required on previously pristine code
that otherwise never mentions your type.  You reluctantly add the
constraint to those, and the compiler demands another seven uses.  Now
your code is littered with meaningless spaghetti constraints that
obfuscate your original intent.

The same contagion also costs you the ability to derive instances of
many useful built-in typeclasses, such as Functor.  The constraint on
the type requires that a function such as fmap must have the constraint,
too, and thus the plague continues.

Pre-GADT syntax doesn't have this problem.

  {-# LANGUAGE GADTs #-}

  data Foo a = Show a => Foo a

  foo :: Foo a -> a
  foo (Foo a) = a

Notice the change in the location of the constraint, and the lack of a
need for a constraint on the function foo.  Real GADTs avoid the problem
in a similar way.

  data Bar a where
  Bar :: Show a => a -> Bar a

  bar :: Bar a -> a
  bar (Bar a) = a
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] RealFloat constraint on Complex type

2008-05-21 Thread Henning Thielemann


On Tue, 20 May 2008, Conal Elliott wrote:


GHC's (maybe Haskell98's?) Complex type is defined with a RealFloat
constraint on type type itself, rather than on some of the instances and
functions:

   data (RealFloat a) => Complex a  = !a :+ !a

I think the practice of constraint in type definitions is generally
discouraged, and I'm wondering if there are reasons other than history for
having the constraint here.  Is removing it on the table for Haskell'?

I just got bit by what I think is a typical problem.  I added a VectorSpace
instance for 'Complex a' and discovered that my 'a' must be in RealFloat,
even though I use only zero, addition, subtraction, and scaling.

I suspect this gripe has been raised before ...


Actually, in NumericPrelude there is no such constraint and Complex is an 
instance of Module and VectorSpace:

  http://darcs.haskell.org/numericprelude/src/Number/Complex.hs
  http://hackage.haskell.org/cgi-bin/hackage-scripts/package/numeric-prelude
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: HaXml and the XHTML 1.0 Strict DTD

2008-05-21 Thread Malcolm Wallace
Peter Gammie <[EMAIL PROTECTED]> wrote:

> Can you lay out some kind of plan for HaXml? (is 1.13.x now dead, is  
> 1.19.x stable, ...?) This would help for new-ish projects like mine.

The 1.13.x stable branch sees minimal maintenance only, mostly to repair
it to build after each new release of ghc breaks something.

Versions 1.14 - 1.19 (i.e. the darcs repo) introduce several API
changes.  I think those have now pretty-much stablised, but
unfortunately the work to realise the benefit of those changes
throughout the codebase is still incomplete in some places.  That is why
I have not frozen and released this branch as 2.0 yet.

For forward compatibility I would definitely recommend that a new
project using HaXml should start with the 1.19 branch, not 1.13.

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


Re: [Haskell-cafe] Newbie: State monad example questions

2008-05-21 Thread Dmitri O.Kondratiev
Thanks everybody for your help!
Oliver,  you provided an excellent write-up  on  State  monad without
going  into 'scary' :) details, great work indeed!
Alas,  in this case I need the details, and in particular the most scary
ones!

So let's start with fundamental and most intriguing  (to me) things:

getAny :: (Random a) => State StdGen a
getAny = do g <- get -- magically get the current StdGen

First line above declares a data type:

State StdGen a

which is constructed with the function:

State {runState :: (StdGen -> (a, StdGen))}

Q1: Where in the example (
http://www.haskell.org/all_about_monads/examples/example15.hs) data of this
type *actually gets constructed* ?

Looking at example15.hs code we see the following sequence:

1) makeRandomValue g -- where g is a StdGen instance, ok

2) makeRandomValue g ~> expands into ~>

~>  (runState (do { ...; b <- getAny;...})) g


This last expression puzzles me. I can understand, for example, this:

State StdGen a :: aState
StdGen:: g1

(v, g2) = (runStae aState) g1 -- this returns a state function which is then
passed a generator g1, and as result returns pair (value, new generaor)

But '(runState (do ...)) g' implies that expression (do ...)  must be
somehow of type 'State StdGen a' ?
Yet, when we call 'makeRandomValue g' we just pass to this function
g::StgGen

So, my next question:
Q2: How (do {...;b <- getAny;...}) becomes an *instance* of type 'State
StdGen a' ?


On Tue, May 20, 2008 at 7:01 PM, Olivier Boudry <[EMAIL PROTECTED]>
wrote:

> 2008/5/19 Dmitri O.Kondratiev <[EMAIL PROTECTED]>:
>
>> I am trying to understand State monad example15 at:
>> http://www.haskell.org/all_about_monads/html/statemonad.html
>>
>>
> Hi Dmitri,
>
> I'm not sure you need to understand everything about Monad and do-notation
> to use the State Monad. So I will try to explain its use without talking
> about those scary topics. ;-)
>
> In Haskell you use the state monad when you want to hide state passing
> between function calls. As Haskell is pure you cannot change state. You can
> just create a new state and return it along with the value. In haskell you
> would do this by returning the value and new state in a tuple. State passing
> functions usually have the type `s -> (a, s)` where a is the type of the
> return value and s is the type of the State.
>
> This is exactly what the `random` function does. It gets a state and
> returns a tuple made of a value and a new state (StdGen: is a new seed for
> the random generator) to be used on the next `random` function call .
>
> Without the state monad you have to explicitely pass the new seed between
> calls to `random` as using the same seed for all function calls would always
> give you the same "not so random" number.
>
> Explicit state passing would look like this.
>
> get3RandomInts :: StdGen -> (Int, Int, Int)
> get3RandomInts g1 =
> let (r1, g2) = random g1
> (r2, g3) = random g2
> (r3, _)  = random g3
> in (r1, r2, r3)
>
> It's tedious, unreadable and error prone as it's easy to mess up the
> numbering (based on my experience).
>
> The State Monad allow you to hide the state passing. You don't have to give
> the state as an argument and your function won't return a changed state
> along with the data. Code running in the State Monad will look like this:
>
> getAny :: (Random a) => State StdGen a
> getAny = do g <- get -- magically get the current StdGen
> let (x, g') = random g
> put g' -- magically save the new StdGen for later
> return x
>
> get3RandomIntsWithState :: State StdGen (Int, Int, Int)
> get3RandomIntsWithState = do
> r1 <- getAny -- you don't care about stdgen passing
> r2 <- getAny
> r3 <- getAny
> return (r1, r2, r3)
>
> To use your get3RandomIntsWithState function you need to run it using one
> of runState (returns the (value, state)) or evalState (returns the value).
>
> main :: IO ()
> main = do
> g <- getStdGen
> let t = evalState get3RandomsWithState g
> print t
>
> The interesting bits are in the getAny function. The State Monad provides
> you with 2 new function, get and set. If you look at this function as
> blackboxes; `get` will retrieve the current State and `put` will save a new
> State. You don't need to worry about how the State is passed from one getAny
> function call to another as long as they're run in the same `evalState`
> call.
>
> Now getAny can be simplified. If you look at the random function and at the
> State newtype declaration you will see that a State is a `s -> (a, s)`
> function "hidden" in the State constructor.
>
> newtype State s a = State {runState :: s -> (a, s)}
>
> random is also of the type `s -> (a, s)` even if variables are labelled `g`
> and `a`
>
> random :: (RandomGen g, Random a) => g -> (a, g)
>
> So wrapping the random function into the State constructor will just give
> you a getAny function for free.
>
> getAny :: (Random a) => State StdGen a
> getAny = State ra

[Haskell-cafe] Re: HaXml and the XHTML 1.0 Strict DTD

2008-05-21 Thread Peter Gammie

On 21/05/2008, at 5:44 PM, Malcolm Wallace wrote:


Peter Gammie <[EMAIL PROTECTED]> wrote:




Using a slightly hacked HaXml v1.13.3, I get this from DtdToHaskell:

data Table = Table Table_Attrs (Maybe Caption)
   (OneOf2 [Col] [Colgroup]) (Maybe Thead) (Maybe  
Tfoot)

   (OneOf2 (List1 Tbody) (List1 Tr))
   deriving (Eq,Show)


This looks entirely correct to me.


I realised that as soon as I sent it. :-)


My expectation is that we can have a  without a  or
 child.


Ah, yes I can see why that is permitted, but I guess HaXml's validator
is not yet smart enough to be able to choose whether it has seen an
empty list of  or an empty list of .  :-)

Here is a suggested fix.  Let me know if it works for you.  In
src/Text/XML/HaXml/Validate.hs, around line 220, use the following  
diff

over the local defn of 'choice':

   choice elem ns cps =  -- return only those parses that don't give  
any errors
   [ rem | ([],rem) <- map (\cp-> checkCP elem (definite cp) ns)  
cps ]

+   ++ [ ns | all possEmpty cps ]
   where definite (TagName n Query)  = TagName n None
 definite (Choice cps Query) = Choice cps None
 definite (Seq cps Query)= Seq cps None
 definite (TagName n Star)   = TagName n Plus
 definite (Choice cps Star)  = Choice cps Plus
 definite (Seq cps Star) = Seq cps Plus
 definite x  = x
+ possEmpty (TagName _ mod)   = mod `elem` [Query,Star]
+ possEmpty (Choice cps None) = all possEmpty cps
+ possEmpty (Choice _ mod)= mod `elem` [Query,Star]
+ possEmpty (Seq cps None)= all possEmpty cps
+ possEmpty (Seq _ mod)   = mod `elem` [Query,Star]


Fantastic, thanks, that seems to work fine. A couple of nits: your use  
of `elem` refers to Prelude.elem, so I added the Prelude as a  
qualified import as P and changed those shadowed references to `P.elem`.


I will try to send you a patch against 1.13.3 with all these little  
bits and pieces, when my project is finished.


Can you lay out some kind of plan for HaXml? (is 1.13.x now dead, is  
1.19.x stable, ...?) This would help for new-ish projects like mine.



Are there other places, apart from the validator, where a similar
problem arises?


I do not know, I am merely using the DTD and HTML parsers, the CFilter  
combinators, the pretty printer and the validator. They all seem fine  
on a cursory check.


(In general HaXml has been working quite well. Thanks for producing  
such a long-lived and well-thought-out library.)


cheers
peter

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


[Haskell-cafe] Re: HaXml and the XHTML 1.0 Strict DTD

2008-05-21 Thread Malcolm Wallace
Peter Gammie <[EMAIL PROTECTED]> wrote:

>(caption?, (col*|colgroup*), thead?, tfoot?, (tbody+|tr+))>
> 
> Using a slightly hacked HaXml v1.13.3, I get this from DtdToHaskell:
> 
> data Table = Table Table_Attrs (Maybe Caption)
> (OneOf2 [Col] [Colgroup]) (Maybe Thead) (Maybe Tfoot)
> (OneOf2 (List1 Tbody) (List1 Tr))
> deriving (Eq,Show)

This looks entirely correct to me.

> My expectation is that we can have a  without a  or  
>  child.

Ah, yes I can see why that is permitted, but I guess HaXml's validator
is not yet smart enough to be able to choose whether it has seen an
empty list of  or an empty list of .  :-)

Here is a suggested fix.  Let me know if it works for you.  In 
src/Text/XML/HaXml/Validate.hs, around line 220, use the following diff
over the local defn of 'choice':

choice elem ns cps =  -- return only those parses that don't give any errors
[ rem | ([],rem) <- map (\cp-> checkCP elem (definite cp) ns) cps ]
+   ++ [ ns | all possEmpty cps ]
where definite (TagName n Query)  = TagName n None
  definite (Choice cps Query) = Choice cps None
  definite (Seq cps Query)= Seq cps None
  definite (TagName n Star)   = TagName n Plus
  definite (Choice cps Star)  = Choice cps Plus
  definite (Seq cps Star) = Seq cps Plus
  definite x  = x
+ possEmpty (TagName _ mod)   = mod `elem` [Query,Star]
+ possEmpty (Choice cps None) = all possEmpty cps
+ possEmpty (Choice _ mod)= mod `elem` [Query,Star] 
+ possEmpty (Seq cps None)= all possEmpty cps
+ possEmpty (Seq _ mod)   = mod `elem` [Query,Star]

Are there other places, apart from the validator, where a similar
problem arises?

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


Re: [Haskell-cafe] Newbie: State monad example questions

2008-05-21 Thread Yitzchak Gale
Thomas Hartman wrote:
> I would be interested in seeing good motivating examples for use of
> the state monad...
> Okay, it's good for randomness. What else?
> ...I saw an example about
> using state to uniquely label elements of a tree
> So, are there any other simple motivating examples that show what
> state is really good for?

I find that there are two basic ways that the State monad
is useful for me.

One is when functions have an extra parameter, or a
tuple return type, that is not really a natural part of the
meaning of the function but is only there for keeping state.
In those cases, a state monad makes the intention
more clear. The examples you mentioned - random
generators and tree labeling - are both of this type.

This first use is especially helpful when there are
several functions that all share the same state.

The other use is for backtracking. In the monad StateT s [],
the state is re-initialized to its original value for each
item of the list. Here is a fully spelled out example:

http://haskell.org/haskellwiki/Sudoku#Backtrack_monad_solver

The first solver on that page, by Cale Gibbard, is a
more elegant way to do the same thing without
spelling out so explicitly all the details of how the
monad is giving you the backtracking effect.
A few other solvers also use a backtracking monad.

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


[Haskell-cafe] Re: HaXml and the XHTML 1.0 Strict DTD

2008-05-21 Thread Peter Gammie

On 30/04/2008, at 5:32 PM, Malcolm Wallace wrote:


Peter Gammie <[EMAIL PROTECTED]> wrote:


The most-recent darcs version relies on a newer ByteString than I
have, so it is not easy for me to test it.


I believe there was a patch to fix this.  Apparently only one  
version of
the bytestring package (0.9.0.1) ever exported the 'join' function,  
and
a different version with the same number (but not exporting 'join')  
was

uploaded to Hackage!  'Join' has since been replaced by 'intercalate',
which is available in all versions 0.9.x.


Thanks. I don't doubt it works with a newer bytestring, I just can't  
readily use such a thing.



A recent (this year) darcs version failed to parse the DTD, yielding
this error:


I didn't try the full XHTML DTD, but the fragment you included in your
message was parsed just fine by the darcs version of HaXml/ 
DtdToHaskell.


Can you please try the full XHTML 1.0 Strict DTD? At the same time,  
can you verify that it handles this part of it properly (circa line  
854):




Using a slightly hacked HaXml v1.13.3, I get this from DtdToHaskell:

data Table = Table Table_Attrs (Maybe Caption)
   (OneOf2 [Col] [Colgroup]) (Maybe Thead) (Maybe  
Tfoot)

   (OneOf2 (List1 Tbody) (List1 Tr))
   deriving (Eq,Show)

My expectation is that we can have a  without a  or  
 child. The W3 validator seems to agree with that  
interpretation. When I use the HaXml validator with this DTD I get  
this (e.g.):


Element  should contain (caption?,(col*| 
colgroup*),thead?,tfoot?,(tbody+|tr+)) but does not.


Element  should contain (col*|colgroup*) but does not.

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


Re: [Haskell-cafe] Rotating backdrop (aka learning Haskell)

2008-05-21 Thread Yann Golanski
Quoth Derek Elkins on Tue, May 20, 2008 at 11:45:57 -0500
> On Tue, 2008-05-20 at 10:55 +0200, Ketil Malde wrote:
> > Yann Golanski <[EMAIL PROTECTED]> writes:
> > 
> > > 1- Get a list out of a file:  I managed to do that using the following:
> > >
> > > parseImageFile :: FilePath -> IO [String]
> > > parseImageFile file = do inpStr <- readFile file
> > >  return $ filter (/="") (breaks (=='\n') inpStr)
> > >
> > > Nice, simple and I understand what it is doing.  
> > 
> > Can be improved:
> > 
> >   breaks (=='\n') == lines  -- easier to read, no?
> >   filter (/="") == filter (not . null)  -- more polymorphic, not important 
> > here
> >   do x <- expr1==  expr1 >>= return . expr2 
> >  return $ expr2 x  -- i.e. "readFile f >>= return . filter 
> > (not.null) . lines"
> 
> do x <- expr1; return $ expr2 x 
> == expr1 >>= return . expr2
> == liftM expr2 expr1 -- or fmap (a.k.a. <$>) if you like
> 
> So,
> liftM (filter (not . null) . lines) readFile
> alternatively,
> filter (not . null) . lines <$> readFile

I'm sorry, this is a little beyond me.  Could you elaborate a little
more on what this actually does?

-- 
[EMAIL PROTECTED] -= H+ =- www.kierun.org
   PGP:   009D 7287 C4A7 FD4F 1680  06E4 F751 7006 9DE2 6318


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


RE: [Haskell-cafe] RealFloat constraint on Complex type

2008-05-21 Thread Bayley, Alistair
> From: [EMAIL PROTECTED] 
> [mailto:[EMAIL PROTECTED] On Behalf Of 
> Richard A. O'Keefe
> 
> On 21 May 2008, at 9:25 am, Conal Elliott wrote:
> > I think the practice of constraint in type definitions is 
> generally  
> > discouraged,
> 
> Is this true?  If so, why?
> If I have a data type that simply doesn't make sense unless 
> some of the
> type variables belong to certain classes, _shouldn't_ that be stated
> clearly in the declaration rather than hidden elsewhere?


I recall this from Graham Klyne, but I think his use case might be a bit
different:

http://www.ninebynine.org/Software/Learning-Haskell-Notes.html#type-clas
ses-and-data

I don't know all the pros and cons (are there pros, other than the
documentation argument you gave?). I think:
 1. adding the constraint has some costs, and very few benefits
 2. nobody does it much, if at all. Probably for the first reason.

Alistair
*
Confidentiality Note: The information contained in this message,
and any attachments, may contain confidential and/or privileged
material. It is intended solely for the person(s) or entity to
which it is addressed. Any review, retransmission, dissemination,
or taking of any action in reliance upon this information by
persons or entities other than the intended recipient(s) is
prohibited. If you received this in error, please contact the
sender and delete the material from any computer.
*

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


Re: [Haskell-cafe] Newbie: State monad example questions

2008-05-21 Thread Thomas Hartman
I would be interested in seeing good motivating examples for use of
the state monad, other than that example from All About Monads.

Okay, it's good for randomness. What else?

Reading the source code for State, I think I saw an example about
using state to uniquely label elements of a tree with ascending
integers, such that equal leaves in the original tree are also equal
in the int-labeled tree. But this struck me as something that could be
more elegantly done with some kind of tree fold.

So, are there any other simple motivating examples that show what
state is really good for?

Thomas.

Am 19. Mai 2008 16:04 schrieb Dmitri O.Kondratiev <[EMAIL PROTECTED]>:
> I am trying to understand State monad example15 at:
> http://www.haskell.org/all_about_monads/html/statemonad.html
>
> Example 15 uses getAny that I don't understand at all how it works:
>
> getAny :: (Random a) => State StdGen a
> getAny = do g  <- get
> (x,g') <- return $ random g
> put g'
> return x
>
>
> Questions:
> 1) random has type:
> random :: (Random a, RandomGen g) => g -> (a, g)
>
> and for State monad:
>
> return a = State (\s -> (a, s))
>
> then:
> return (random g) = State (\s -> ((a,g), s))
>
> Is  it correct?
>
> 2) What x and g' will match to in:
>do ...
> (x,g') <- return $ random g
>
> which, as I understand equals to:
>do ...
> (x,g') <- State (\s -> ((a,g), s))
>
> What x and g' will match to in the last expression?
>
> 3) In general, in do expression (pseudo):
> do { x <- State (\s -> (a, s)); ...}
>
> What x will refer to? Will x stand for a whole lambda function: \s -> (a, s)
> ?
>
> 4) How 'g <- get' works in this function (getAny) ?
> 5) Why we need 'put g'?
>
> Thanks!
>
>
> ___
> 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