Re: [Haskell-cafe] Execution of external command

2007-12-16 Thread Jonathan Cast


On 14 Dec 2007, at 1:21 AM, Jules Bean wrote:


Evan Laforge wrote:
it seems that script may be not terminated if its output isn't  
read, so

better code should be

(_, h, g, _) - runInteractiveCommand script params
result - hGetLine h
hGetContents h = evaluate.length
hGetContents g = evaluate.length

Tangent here, but does anyone else think that something like
hGetContentsEagerly would be handy in System.IO?


YES!

Jules

PS we could give it a nice sensible name like hGetContents. We  
could renaming the existing hGetContents to  
hUnsafeGetContentsDontUseThisUnlessYouHaveSpentThreeMonthsLearningGHCs 
ExecutionSemanticsOrYouWillRegretIt


On the contrary, it's great for writing filters.   OTOH, using the  
result of hGetContents interleaved with other IO actions feels like a  
reversion to the bad old days of dialogs (which it is, of course).


jcc


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


Re: [Haskell-cafe] Questions about the Functor class and it's use in Data types à la carte

2007-12-16 Thread Dominic Steinitz
 keep in mind that Haskell composition (.)
 is not really composition in the category-theoretic
 sense, because it adds extra laziness. Use this

Do you have a counter-example of (.) not being function composition in
the categorical sense?



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


Re: [Haskell-cafe] Questions about the Functor cl ass and it's use in Data types à la carte

2007-12-16 Thread Jonathan Cast

On 16 Dec 2007, at 2:23 AM, Dominic Steinitz wrote:


keep in mind that Haskell composition (.)
is not really composition in the category-theoretic
sense, because it adds extra laziness. Use this


Do you have a counter-example of (.) not being function composition in
the categorical sense?


Let bot be the function defined by

bot :: alpha - beta
bot = bot

By definition,

(.) = \ f - \ g - \ x - f (g x)

Then

  bot . id
= ((\ f - \ g - \ x - f (g x)) bot) id
= (\ g - \ x - bot (g x)) id
= \ x - bot (g x)

which /= bot since (seq bot () = bot) but (seq (\ x - M) () = ())  
regardless of what expression we substitute for M.


jcc

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


Re: [Haskell-cafe] Questions about the Functor class and it's use in Data types à la carte

2007-12-16 Thread Dominic Steinitz
 Do you have a counter-example of (.) not being function composition in
 the categorical sense?
 
 Let bot be the function defined by
 
 bot :: alpha - beta
 bot = bot
 
 By definition,
 
 (.) = \ f - \ g - \ x - f (g x)
 
 Then
 
bot . id
 = ((\ f - \ g - \ x - f (g x)) bot) id
 = (\ g - \ x - bot (g x)) id
 = \ x - bot (g x)

I didn't follow the reduction here. Shouldn't id replace g everywhere?

This would give

= \x - bot x

and by eta reduction

= bot

 
 which /= bot since (seq bot () = bot) but (seq (\ x - M) () = ())  
 regardless of what expression we substitute for M.
 

Why is seq introduced?

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


Re: [Haskell-cafe] Questions about the Functor cl ass and it's use in Data types à la carte

2007-12-16 Thread Jonathan Cast

On 16 Dec 2007, at 3:21 AM, Dominic Steinitz wrote:

Do you have a counter-example of (.) not being function  
composition in

the categorical sense?


Let bot be the function defined by

bot :: alpha - beta
bot = bot

By definition,

(.) = \ f - \ g - \ x - f (g x)

Then

   bot . id
= ((\ f - \ g - \ x - f (g x)) bot) id
= (\ g - \ x - bot (g x)) id
= \ x - bot (g x)


I didn't follow the reduction here. Shouldn't id replace g everywhere?


Yes, sorry.


This would give

= \x - bot x

and by eta reduction


This is the point --- by the existence of seq, eta reduction is  
unsound in Haskell.




= bot



which /= bot since (seq bot () = bot) but (seq (\ x - M) () = ())
regardless of what expression we substitute for M.



Why is seq introduced?


Waiting for computers to get fast enough to run Haskell got old.

Oh, you mean here?  Equality (=) for pickier Haskellers always means  
Leibnitz' equality:


Given x, y :: alpha

x = y if and only if for all functions f :: alpha - (), f x = f y

f ranges over all functions definable in Haskell, (for some version  
of the standard), and since Haskell 98 defined seq, the domain of f  
includes (`seq` ()).  So since bot and (\ x - bot x) give different  
results when handed to (`seq` ()), they must be different.


The `equational reasoning' taught in functional programming courses  
is unsound, for this reason.  It manages to work as long as  
everything terminates, but if you want to get picky you can find  
flaws in it (and you need to get picky to justify extensions to  
things like infinite lists).


jcc

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


Re: [Haskell-cafe] Questions about the Functor class and it's use in Data types à la carte

2007-12-16 Thread Roberto Zunino
Yitzchak Gale wrote:
 When using seq and _|_ in the context of categories,
 keep in mind that Haskell composition (.)
 is not really composition in the category-theoretic
 sense, because it adds extra laziness. Use this
 instead:
 
 (.!) f g x = f `seq` g `seq` f (g x)

   id .! undefined
== \x - undefined
/= undefined

Probably you meant

   (.!) f g = f `seq` g `seq` (f . g)

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


Re: [Haskell-cafe] Questions about the Functor class and it's use in Data types à la carte

2007-12-16 Thread Roberto Zunino
Dominic Steinitz wrote:
 This would give
 
 = \x - bot x
 
 and by eta reduction

This is the point: eta does not hold if seq exists.

  undefined `seq` 1 == undefined
  (\x - undefined x) `seq` 1 == 1

The (.) does not form a category argument should be something like:

  id . undefined == (\x - id (undefined x)) /= undefined

where the last inequation is due to the presence of seq. That is,
without seq, there is no way to distinguish between undefined and (const
undefined), so you could use a semantic domain where they coincide. In
that case, eta does hold.

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


[Haskell-cafe] Re: Monads that are Comonads and the role of Adjunction

2007-12-16 Thread apfelmus

Dan Weston wrote:

newtype O f g a = O (f (g a))   -- Functor composition:  f `O` g

instance (Functor f, Functor g) = Functor (O f g) where ...
instance Adjunction f g = Monad   (O g f) where ...
instance Adjunction f g = Comonad (O f g) where ... 


class (Functor f, Functor g) = Adjunction f g | f - g, g - f where
  leftAdjunct  :: (f a - b) - a - g b
  rightAdjunct :: (a - g b) - f a - b
--

Functors are associative but not generally commutative. Apparently a 
Monad is also a Comonad if there exist left (f) and right (g) adjuncts 
that commute.


Yes, but that's only sufficient, not necessary.

Jules and David already pointed out that while every monad comes from an 
adjunction, this adjunction usually involves categories different from 
Hask. So, there are probably no adjoint functors f and g in Hask such that


  [] ~= g `O` f

or


data L a = One a | Cons a (L a)   -- non-empty list


  L ~= g `O` f

(proof?) Yet, both are monads and the latter is even a comonad.

Moreover, f and g can only commute if they have the same source and 
target category (Hask in our case). And even when they don't commute, 
the resulting monad could still be a comonad, too.


My category theory study stopped somewhere between Functor and 
Adjunction, but is there any deep magic you can describe here in a 
paragraph or two? I feel like I will never get Monad and Comonad until I 
understand Adjunction.


Alas, I wish I could, but I have virtually no clue about adjoint 
functors myself :)


I only know the classic example that conjunction and implication

  f a = (a,S)
  g b = S - b

are adjoint

  (a,S) - b  =  a - (S - b)

which is just well-known currying. We get the state monad

  (g `O` f) a = S - (S,a)

and the stream comonad

  (f `O` f) a = (S, S - a)

out of that.


Regards
apfelmus

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


Re: [Haskell-cafe] Questions about the Functor class and it's use in Data types à la carte

2007-12-16 Thread Yitzchak Gale
I wrote:
 (.!) f g x = f `seq` g `seq` f (g x)

Roberto Zunino wrote:
id .! undefined
 == \x - undefined
 /= undefined

 Probably you meant

(.!) f g = f `seq` g `seq` (f . g)

Yes, thank you.

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


Re: Re: [Haskell-cafe] Questions about the Functor class and it's use in Data types à la carte

2007-12-16 Thread jerzy . karczmarczuk
Roberto Zunino writes: 


without seq, there is no way to distinguish between undefined and (const
undefined), 


no way to distinguish is perhaps too strong. They have slightly
different types. 



Jerzy Karczmarczuk 



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


Re: [Haskell-cafe] Implementing a MUD server in haskell

2007-12-16 Thread Jules Bean

Jack Kelly wrote:

struct room{
  ...
  struct player * players;
  ...
};

struct player{
  ...
  struct room * room;
  ...
};

 From what I can see, I'd use a record type for players and rooms, but 
I'm not sure how to replicate the pointer effects: 


Essentially you have to choose some form of identity (relational DB fans 
might call it a key) for your players and rooms. My gut feeling is 
that String will do fine; it's nice for debugging, gives rise to a 
natural way to write your admin commands and so on. However, it may not 
be quite good enough (100 mobs all called an orc need individual keys) 
and you may end up using an Int or Int64 for your key.


Once you've chosen a key, you can do something very like the C++ 
structure, but instead you have


Room { ... players :: [String] ... }

Player { ... room :: String }

..although you may find life is made more pleasant by

newtype RoomID = RoomID String
newtype PlayerID = PlayerID String

which improves the looks of your types, helps the compiler help you, and 
also makes it easier to change to another representation later.


I should mention, actually, that there is also the naive solution:

Room { ... players :: [Player] ... }
Player { ... room :: Room ... }

The main reason to dislike this is that if something in a Player 
structure changes, you have to remember to change all the references to 
it... Depending on your design, it may be that rooms themselves can't 
really change, so this may not matter for rooms (except for the player 
list, but maybe we don't need that, read on...)


 keeping each player
pointing to a single instance of a consistent world and maintaining the 
invariant that (given: p :: Player, r :: Room):


p `elem` (Room.players r) = (Player.room p == r)


There are always two techniques for maintaining invariants. One is to 
design your data structures so it is impossible to violate them, (our DB 
fan would call this normalization), and the other is to ensure that all 
modifications are carried out via a relatively small set of functions 
which are responsible to maintaining the invariant (which the DB fan 
would call middleware).


In solution 1, you would simply not store the player list in the room 
structure at all. Instead, you would only store the room in the player, 
and whenever you wanted to answer the question Which players are in 
this room you would do a quick search through all players to find them


playersInRoom :: Room - [Player]
playersInRoom r = [p | p - allplayers, (room p) == r]
-- Just like a database! In SQL we'd say:
-- SELECT p FROM allplayers WHERE p.room = r

Of course the disadvantage to this is the linear search through all the 
players. Depending on how often this is performed, this may actually 
cost you less that explicitly caching the value inside the room.


In solution 2, of course, whenever you  move a player from room A to 
room B you do it via a function which is explicitly designed to keep 
everythign up to date:


movePlayer PlayerID - RoomID - RoomID - Game ()
movePlayer pid raid rbid = do
  p - getPlayer pid
  setPlayer pid (p {room = rbid})
  ra - getRoom raid
  rb - getRoom rbid
  setRoom raid (ra {players = (players ra)\\[pid]} )
  setRoom rbid (rb {players = pid : (players rb)} )

Which I've written in an imaginary Game monad, and using rather ugly 
low-level combinators get/set Room/Player. You could make it look much 
more pleasant in practice with some better chosen combinators.


Still I think solution 1 (don't store redundant data which can get out 
of sync) has a lot to recommend it and solution 2 may be premature 
optimization; i.e. implement solution 2, which is a kind of caching of 
computed data, only once you've convinced yourself that recalculating 
that data every time really is slowing you down.


This needs to stand up to concurrent modification of a shared world 
structure, but I think I'll set up the concurrency controls after I get 
my head around this.t
The simplest way to do this is to bundle all your big shared mutable 
world into a single MVar. What this amounts to is perfect brute force 
serialisation of the actual modification part: i.e. all world 
modifications share a global lock. This is easy to implement and easy to 
reason about.


If that turns out to be too restrictive, then you split up the MVars 
into smaller pieces, but then you have to think a bit harder to convince 
yourself it is safe.


Jules

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


Re: [Haskell-cafe] Questions about the Fu nctor class and it's use in Data types à la c arte

2007-12-16 Thread Jules Bean

[EMAIL PROTECTED] wrote:

Roberto Zunino writes:

without seq, there is no way to distinguish between undefined and (const
undefined), 


no way to distinguish is perhaps too strong. They have slightly
different types.


At a particular type which they both inhabit, such as (a-b) or, to be 
concrete, (Int - Int), there is no way to distinguish without seq.


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


Re: [Haskell-cafe] Implementing a MUD server in haskell

2007-12-16 Thread Jack Kelly

Jules Bean wrote:

Jack Kelly wrote: -snip-

Essentially you have to choose some form of identity (relational DB fans 
might call it a key) for your players and rooms. My gut feeling is 
that String will do fine; it's nice for debugging, gives rise to a 
natural way to write your admin commands and so on. However, it may not 
be quite good enough (100 mobs all called an orc need individual keys) 
and you may end up using an Int or Int64 for your key.


Perhaps doing the keying on an Int and then having a [String] of names 
that entities can be called is the way to go. List comprehensions will 
still work:


let ents = [ ent | ent - allents, name `elem` (Entity.aliases ent) ] in
-- ...

but so will addressing an object uniquely when needed:

let target = listToMaybe $ [ ent | ent - allents, id == (Entity.id ent) 
] in

-- ...
Once you've chosen a key, you can do something very like the C++ 
structure: -snip-


I'm thinking of doing the following (based on some suggestions from 
#haskell):


data Room = Room {...}
type Zone = Data.Map String Room
type World = Data.Map String Zone
type ZoneID = String
type RoomID = String
data Location = Location { zone :: ZoneID, room :: RoomID}
data Player = Player { location :: Location, ... }

Aside: When should I use newtype vs type? From what I understand, both 
create type aliases that are only relevant at compile time, but newtype 
disallows things like:


-- Bad
newtype Fred = Fred String
putStrLn $ Fred this won't work

as a rule of thumb, is it `better' to newtype things so that the type 
system can trip you up?



I should mention, actually, that there is also the naive solution:

 -snip-
That does seem like a bad idea.


There are always two techniques for maintaining invariants.
In solution 1, you would simply not store the player list in the room 
structure at all. Instead, you would only store the room in the player, 
and whenever you wanted to answer the question Which players are in 
this room you would do a quick search through all players to find them


playersInRoom :: Room - [Player]
playersInRoom r = [p | p - allplayers, (room p) == r]
-- Just like a database! In SQL we'd say:
-- SELECT p FROM allplayers WHERE p.room = r

Of course the disadvantage to this is the linear search through all the 
players. Depending on how often this is performed, this may actually 
cost you less that explicitly caching the value inside the room.


I'd not thought of doing it that way. Maybe because keeping a couple of 
pointers in sync in C is less painful then coding up a search to 
generate an appropriate list. Learning to stop looking through the 
imperative lens is hard.


In solution 2, of course, whenever you  move a player from room A to 
room B you do it via a function which is explicitly designed to keep 
everythign up to date:


movePlayer PlayerID - RoomID - RoomID - Game ()
movePlayer pid raid rbid = do
  p - getPlayer pid
  setPlayer pid (p {room = rbid})
  ra - getRoom raid
  rb - getRoom rbid
  setRoom raid (ra {players = (players ra)\\[pid]} )
  setRoom rbid (rb {players = pid : (players rb)} )

Which I've written in an imaginary Game monad, and using rather ugly 
low-level combinators get/set Room/Player. You could make it look much 
more pleasant in practice with some better chosen combinators.


Game looks like it'd behave like some kind of specialisation of State, 
but since there'd be responses sent out to the sockets, I'm thinking of 
something like StateT GameState IO (). Is it worth having the StateT 
because IO already handles some concept of state? If so, will running 
something like:


forkIO $ evalStateT gameLoop initialstate

work or will the IO actions be queued up until the end of gameLoop? The 
idea of building a Game monad is attractive regardless because I'll 
still need functions like movePlayer regardless of which path is chosen.


Still I think solution 1 (don't store redundant data which can get out 
of sync) has a lot to recommend it and solution 2 may be premature 
optimization; i.e. implement solution 2, which is a kind of caching of 
computed data, only once you've convinced yourself that recalculating 
that data every time really is slowing you down.


I think I'll go with solution 1. It's conceptually simpler and if it's 
slow I can profile and optimise later, right?


The simplest way to do this is to bundle all your big shared mutable 
world into a single MVar. What this amounts to is perfect brute force 
serialisation of the actual modification part: i.e. all world 
modifications share a global lock. This is easy to implement and easy to 
reason about.


I think that my fear of doing this was again instinctive premature 
optimisation.


If that turns out to be too restrictive, then you split up the MVars 
into smaller pieces, but then you have to think a bit harder to convince 
yourself it is safe.


Another idea that I picked up from the Simple TCP server 
(http://sequence.complete.org/node/258) is to have a single thread 

Re: [Haskell-cafe] Questions about the Functor class and it's use in Data types à la carte

2007-12-16 Thread Dominic Steinitz
Roberto Zunino wrote:
 Dominic Steinitz wrote:
 This would give

 = \x - bot x

 and by eta reduction
 
 This is the point: eta does not hold if seq exists.
 
   undefined `seq` 1 == undefined
   (\x - undefined x) `seq` 1 == 1
 

Ok I've never used seq and I've never used unsavePerformIO. Provided my
program doesn't contain these then can I assume that eta reduction holds
and that (.) is categorical composition?

 The (.) does not form a category argument should be something like:
 
   id . undefined == (\x - id (undefined x)) /= undefined
 
 where the last inequation is due to the presence of seq. That is,
 without seq, there is no way to distinguish between undefined and (const
 undefined), so you could use a semantic domain where they coincide. In
 that case, eta does hold.

It would be a pretty odd semantic domain where 1 == undefined. Or
perhaps, I should say not a very useful one.

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


Re: [Haskell-cafe] Questions about the Functor class and it's use in Data types à la carte

2007-12-16 Thread Dominic Steinitz
Jonathan Cast wrote:
 On 16 Dec 2007, at 3:21 AM, Dominic Steinitz wrote:
 
 Do you have a counter-example of (.) not being function composition in
 the categorical sense?

 Let bot be the function defined by

 bot :: alpha - beta
 bot = bot

 By definition,

 (.) = \ f - \ g - \ x - f (g x)

 Then

bot . id
 = ((\ f - \ g - \ x - f (g x)) bot) id
 = (\ g - \ x - bot (g x)) id
 = \ x - bot (g x)

 I didn't follow the reduction here. Shouldn't id replace g everywhere?
 
 Yes, sorry.
 
 This would give

 = \x - bot x

 and by eta reduction
 
 This is the point --- by the existence of seq, eta reduction is unsound
 in Haskell.
 

Am I correct in assuming that if my program doesn't contain seq then I
can reason using eta reduction?


 Why is seq introduced?
 
 Waiting for computers to get fast enough to run Haskell got old.
 

I'm guessing you were not being entirely serious here but I think that's
a good answer.

 Oh, you mean here?  Equality (=) for pickier Haskellers always means
 Leibnitz' equality:
 
 Given x, y :: alpha
 
 x = y if and only if for all functions f :: alpha - (), f x = f y
 
 f ranges over all functions definable in Haskell, (for some version of
 the standard), and since Haskell 98 defined seq, the domain of f
 includes (`seq` ()).  So since bot and (\ x - bot x) give different
 results when handed to (`seq` ()), they must be different.
 
 The `equational reasoning' taught in functional programming courses is
 unsound, for this reason.  It manages to work as long as everything
 terminates, but if you want to get picky you can find flaws in it (and
 you need to get picky to justify extensions to things like infinite lists).
 

Reasoning as though you were in a category with a bottom should be ok as
long as seq isn't present? I'm recalling a paper by Freyd on CPO
categories which I can't lay my hands on at the moment or find via a
search engine. I suspect Haskell (without seq) is pretty close to a CPO
category.

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


Re: [Haskell-cafe] Questions about the Functor cl ass and it's use in Data types à la carte

2007-12-16 Thread Sterling Clover


Am I correct in assuming that if my program doesn't contain seq then I
can reason using eta reduction?


You may be well aware of this, but the wiki page on the correctness  
of short cut fusion (http://haskell.org/haskellwiki/ 
Correctness_of_short_cut_fusion) really helped me to get at least a  
basic intuition for how to reason around the oddities introduced by  
seq. Some of the papers linked were very handy as well, although I'll  
confess to only partially understanding them.


--s

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


Re: [Haskell-cafe] Implementing a MUD server in haskell

2007-12-16 Thread Luke Palmer
On Dec 16, 2007 1:45 PM, Jules Bean [EMAIL PROTECTED] wrote:
  This needs to stand up to concurrent modification of a shared world
  structure, but I think I'll set up the concurrency controls after I get
  my head around this.t
 The simplest way to do this is to bundle all your big shared mutable
 world into a single MVar. What this amounts to is perfect brute force
 serialisation of the actual modification part: i.e. all world
 modifications share a global lock. This is easy to implement and easy to
 reason about.

 If that turns out to be too restrictive, then you split up the MVars
 into smaller pieces, but then you have to think a bit harder to convince
 yourself it is safe.

STM! Why use Haskell concurrently and not use STM?  STM is beautiful.

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


Re: [Haskell-cafe] Questions about the Functor cl ass and it's use in Data types à la carte

2007-12-16 Thread Jonathan Cast

On 16 Dec 2007, at 9:47 AM, Dominic Steinitz wrote:


Jonathan Cast wrote:

On 16 Dec 2007, at 3:21 AM, Dominic Steinitz wrote:

Do you have a counter-example of (.) not being function  
composition in

the categorical sense?


Let bot be the function defined by

bot :: alpha - beta
bot = bot

By definition,

(.) = \ f - \ g - \ x - f (g x)

Then

   bot . id
= ((\ f - \ g - \ x - f (g x)) bot) id
= (\ g - \ x - bot (g x)) id
= \ x - bot (g x)


I didn't follow the reduction here. Shouldn't id replace g  
everywhere?


Yes, sorry.


This would give

= \x - bot x

and by eta reduction


This is the point --- by the existence of seq, eta reduction is  
unsound

in Haskell.



Am I correct in assuming that if my program doesn't contain seq then I
can reason using eta reduction?


Yes.



Why is seq introduced?


Waiting for computers to get fast enough to run Haskell got old.



I'm guessing you were not being entirely serious here but I think  
that's

a good answer.


Oh, you mean here?  Equality (=) for pickier Haskellers always means
Leibnitz' equality:

Given x, y :: alpha

x = y if and only if for all functions f :: alpha - (), f x = f y

f ranges over all functions definable in Haskell, (for some  
version of

the standard), and since Haskell 98 defined seq, the domain of f
includes (`seq` ()).  So since bot and (\ x - bot x) give different
results when handed to (`seq` ()), they must be different.

The `equational reasoning' taught in functional programming  
courses is

unsound, for this reason.  It manages to work as long as everything
terminates, but if you want to get picky you can find flaws in it  
(and
you need to get picky to justify extensions to things like  
infinite lists).




Reasoning as though you were in a category with a bottom should be  
ok as

long as seq isn't present? I'm recalling a paper by Freyd on CPO
categories which I can't lay my hands on at the moment or find via a
search engine. I suspect Haskell (without seq) is pretty close to a  
CPO

category.


Not quite --- not if by `a category with bottom' you mean the  
standard category of pointed CPOs and strict functions, because  
Haskell functions aren't necessarily strict.


In the actual category Hask, you don't even have finite products,  
because surjective pairing still fails (seq can be defined in the  
special case of pairs directly in Haskell).


The usual solution is to ensure that everything terminates (more  
precisely, that everythin is total).  In that case, you can pretend  
you're in a nice, neat purely set-theoretic model most of the time,  
and only worry about CPOs when you need to do fixed-point or partial- 
list induction or something like that.


jcc


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


[Haskell-cafe] announcing darcs 2.0.0pre2

2007-12-16 Thread David Roundy
I am pleased to announce the availability of the second prerelease of darcs
two, darcs 2.0.0pre2.  This release fixes several severe performance bugs
that were present in the first prerelease.  These issues were identified
and fixed thanks to the helpful testing of Simon Marlow and Peter Rockai.
We also added support for compilation under ghc 6.4, so even more users
should be able to test this release.

As before, some information about the prerelease is available at:

http://wiki.darcs.net/index.html/DarcsTwo

You can either use darcs to grab the latest darcs, or you can download a
tarball at:

http://darcs.net/darcs2.0.0pre2.tar.gz

A few outstanding performance issues are:

1. darcs whatsnew performance has dropped for hashed repositories due to no
   longer tracking file-modification times.  We need to reenable this
   feature, but it's not quite clear how best to do so.

2. darcs get on a hashed repository is not as fast as the older darcs get
   --partial.  We could fix this by enabling the downloading of a single
   file _darcs/pristine.hashed.tar.gz.  This eliminates the potential
   benefits of caching file downloads on darcs get (currently a second
   get of the same remote repository is almost free if you've enabled a
   global cache), so we may want to make this behavior optional.

I hope we can get even more testing with this release, and look forward to
finding and fixing any remaining performance regressions (or bugs, of
course)!

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


Re: [Haskell-cafe] [RFC] benchmarks of bytestrings, teaser

2007-12-16 Thread Roman Leshchinskiy

Don Stewart wrote:


 cnt:: B.ByteString - Int64
 cnt bs = B.length (B.filter (== ' ') bs)


 [...]
 
Now, this memory result is suspicious, I wonder if the now obsolete 'array fusion'

is messing things up. In Data.ByteString.Lazy, we have:


Are you sure you have a fusible length? I think I only added it to NDP 
after stream fusion went in.


Roman

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


Re: [Haskell-cafe] [RFC] benchmarks of bytestrings, teaser

2007-12-16 Thread Don Stewart
rl:
 Don Stewart wrote:
 
  cnt:: B.ByteString - Int64
  cnt bs = B.length (B.filter (== ' ') bs)
 
  [...]
  
 Now, this memory result is suspicious, I wonder if the now obsolete 'array 
 fusion'
 is messing things up. In Data.ByteString.Lazy, we have:
 
 Are you sure you have a fusible length? I think I only added it to NDP 
 after stream fusion went in.

It was the array fusion from prior to the stream stuff (foldl . filter).
Which was in fact messing up the simplifier. I've fixed this, (turned
off array fusion for now), and things are back to normal. (well, much
faster, actually).

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


Re: [Haskell-cafe] [RFC] benchmarks of bytestrings, teaser

2007-12-16 Thread Don Stewart
I've had a look at how some of the code was being compiled for 
strict and lazy bytestrings, and also which rules weren't firing.
With some small tweaks the code seems back in good shape.

An updated bytestring library is at :


http://hackage.haskell.org/cgi-bin/hackage-scripts/package/bytestring-0.9.0.2

Enjoy! :)



Summary: the suspicious lazy bytestring program works now. (constant
space, and fastest overall, as expected originally)

Program 1, lazy bytestring length . filter

Yesterday:
./A +RTS -sstderr  150M  1.01s user 0.10s system 98% cpu 1.123 total
40M allocated

  * Today (fixed!):
./A +RTS -sstderr  150M  0.26s user 0.06s system 96% cpu 0.332 total
2M allocated

Reason, deprecated array fusion mucking up the optimiser.

I think we can close this regression.



Also, I had a look at Program 3: lazy bytestring, custom loop

Unchanged. 2.4s, constant space. This was a bit slow.

Further investigation shows lots of unnecessary bounds checks, as we
take apart the Chunk lazy bytestring type, then test and continue.

This representation was chosen to make it possible to process chunks
efficiently, so that we can avoid these bounds check. 

Something like this instead:

cnt :: Int - B.ByteString - Int
cnt n B.Empty= n
cnt n (B.Chunk x xs) = cnt (n + cnt_strict 0 x) xs  -- process lazy 
spine

-- now we can process a chunk without checking for Empty
where
cnt_string !i !s-- then strict 
chunk 
| S.null s  = i
| c == ' '  = cnt_strict (i+1) t
| otherwise = cnt_strict i t
  where
(c,t) = (S.w2c (S.unsafeHead s), S.unsafeTail s) -- no 
bounds check

main = do s - B.getContents; print (cnt 0 s)

Let's us avoid redundant checks for Empty, while allowing 'go' to
avoid unnecessary checks for the empty strict bytestring. This is 
some 4x faster.

This alternating between lazy spines and strict chunk processing is
the best way to get reliable performance from lazy bytestring custom loops.

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


Re: [Haskell-cafe] Re: Monads that are Comonads and the role of Adjunction

2007-12-16 Thread Derek Elkins
On Sun, 2007-12-16 at 13:49 +0100, apfelmus wrote:
 Dan Weston wrote:
  newtype O f g a = O (f (g a))   -- Functor composition:  f `O` g
 
  instance (Functor f, Functor g) = Functor (O f g) where ...
  instance Adjunction f g = Monad   (O g f) where ...
  instance Adjunction f g = Comonad (O f g) where ... 
 
  class (Functor f, Functor g) = Adjunction f g | f - g, g - f where
leftAdjunct  :: (f a - b) - a - g b
rightAdjunct :: (a - g b) - f a - b
  --
  
  Functors are associative but not generally commutative. Apparently a 
  Monad is also a Comonad if there exist left (f) and right (g) adjuncts 
  that commute.
 
 Yes, but that's only sufficient, not necessary.
 
 Jules and David already pointed out that while every monad comes from an 
 adjunction, this adjunction usually involves categories different from 
 Hask. So, there are probably no adjoint functors f and g in Hask such that
 
[] ~= g `O` f
 
 or
 
  data L a = One a | Cons a (L a)   -- non-empty list
 
L ~= g `O` f
 
 (proof?) Yet, both are monads and the latter is even a comonad.
 
 Moreover, f and g can only commute if they have the same source and 
 target category (Hask in our case). And even when they don't commute, 
 the resulting monad could still be a comonad, too.
 
  My category theory study stopped somewhere between Functor and 
  Adjunction, but is there any deep magic you can describe here in a 
  paragraph or two? I feel like I will never get Monad and Comonad until I 
  understand Adjunction.
 
 Alas, I wish I could, but I have virtually no clue about adjoint 
 functors myself :)

Learn about representability.  Representability is the core of category
theory.  (Though, of course, it is closely related to adjunctions.)

 I only know the classic example that conjunction and implication
 
f a = (a,S)
g b = S - b
 
 are adjoint
 
(a,S) - b  =  a - (S - b)
 
 which is just well-known currying. We get the state monad
 
(g `O` f) a = S - (S,a)
 
 and the stream comonad
 
(f `O` f) a = (S, S - a)
 
 out of that.

There is another very closely related adjunction that is less often
mentioned. 

((-)-C)^op -| (-)-C
or
a - b - C ~ b - a - C

This gives rise to the monad,
M a = (a - C) - C
this is also exactly the comonad it gives rise to (in the op category
which ends up being the above monad in the normal category).

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


[Haskell-cafe] Patter matching beginner question

2007-12-16 Thread Adam Smyczek

Hi all,
I assume the following behavior has a trivial explanation.

When I write:
case name of
a - ...
b - ...
everything works fine.

But when I extract a and b to constants:

c_a = a :: String
c_b = b :: String

case name of
c_a - ...
c_b - ...
I get Patterns match(es) are overlapped.

Adam

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


Re: [Haskell-cafe] Patter matching beginner question

2007-12-16 Thread Brandon S. Allbery KF8NH


On Dec 16, 2007, at 23:35 , Adam Smyczek wrote:


case name of
c_a - ...
c_b - ...
I get Patterns match(es) are overlapped.


You can't use arbitrary expressions in patterns; any name (not a data  
constructor) used in one creates a new lambda binding (shadowing any  
existing binding) which receives the value at that point in the  
pattern.  So


 case name of
   c_a - ...

captures the value of name in a new binding c_a.

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