Re: [Haskell-cafe] haskell in online contests

2009-11-29 Thread Daniel Fischer
Am Samstag 28 November 2009 21:21:20 schrieb vishnu:
 this is where I've gotten to.
 http://moonpatio.com/fastcgi/hpaste.fcgi/view?id=5120#a5120
 strangely enough Ive gotten no speedup at all from the substitution cost
 UArray (though I had to make it Int, Int to deal with digits.).

Converting the characters with letterValue takes time. I'm a little surprised 
that it 
takes so much time, though. I would have expected it to still be faster than 
Map.

If you make 

subArray :: UArray (Char,Char) Int
subArray = array (('0','0'),('z'z')) ...

you avoid the conversion at the price of a larger array. It's still small 
enough to have 
the entire computation data in the cache, so it should be faster.

However, the Chars are converted to Ints for array-indexing anyway (I think 
Char is 
internally represented as a machine integer [wrapped in a constructor], so this 
is 
basically a no-op, even if not, it's going to be much faster than letterValue), 
so why not 
avoid the conversions (except once on reading) completely and work with Ints?

Change all (UArray Int Char) to (UArray Int Int) and let

getArray :: BS.ByteString - UArray Int Int
getArray xs = listArray (1, fromIntegral (BS.length xs)) (map letterValue $ 
BS.unpack xs)

replace

substitutionCost (orig ! i) (new ! j)

with

subArray!(orig!i,new!j)

and remove substitutionCost (optional), that's all you need to change in your 
code - 
except: please fix the typo

-- calculating the Leveishtein distance as described here 
...^^ 

:)

 But still I wonder if there's something else I missed. Im really curious what 
 lazyness
 you used to go from 60 to 1.6? I always thought lazyness was automatic and
 seq made strictness possible.

What you need is a sufficiently lazy *algorithm* to compute (min 3 $ distance 
orig new).
For top speed, you must implement that algorithm sufficiently strictly ;)
You might want to read carefully the Possible improvements section on WP to 
get an idea.

I'll try to explain without giving too much away to respect the spirit of the 
codechef 
challenge.


The Levenshtein algorithm for computing the cost of the cheapest editing 
sequence(s) 
transforming start (length m) into target (length n) computes the lowest costs 
for 
transforming initial sequences of start (length i) to initial sequences of 
target (length 
j), i ranging from 0 to m, j from 0 to n, altogether (m+1)*(n+1) costs.
The costs for i == 0 or j == 0 are easily determined and if you calculate the 
costs in an 
appropriate order, calculating each cost is cheap.

We are only interested in whether the cost (distance) is 0, 1, 2 or larger than 
2.
So whenever we stray more than two steps from the diagonal, we can stop.
You approximate that behaviour by writing the value 3 to all cells far enough 
off the 
diagonal.
But you're still writing (m+1)*(n+1) values/thunks to the array. Since the 
actual 
calculation of the costs is cheap, you don't win very much (cuts down execution 
time by a 
little more than half - not bad, but much more is possible).

Also, you're always walking down the entire diagonal, even if one can see much 
sooner that 
the cost is larger than 2. Consider

thisends - herestop

The last letters differ, so the cost is one of
a) 2+cost (thisend - heresto)-- substitution (s,p)
b) 1+cost (thisends - heresto)   -- insert p
c) 1+cost (thisend - herestop)   -- delete s

a) last letters differ, another branch adding at least 1 to the cost, so after 
the second 
step we know that route leads to a total larger than 2
b) and c) need three steps to ascertain that the total cost exceeds 2

Now for long strings with large Levenshtein distance, this is typical 
(occasionally you'll 
encounter identical letters, but that doesn't take much time since it doesn't 
involve a 
branching), after three levels of branching, you know the cost exceeds 2, no 
need to go 
further.

So a properly lazy algorithm stops processing as soon as it's certain that the 
distance is 
larger than 2.

One way to do it is to calculate the distance using lazy Peano numbers and 
checking 
whether it's larger than 2:

-

data Nat
= Zero
| Succ Nat

n2i :: Nat - Int
n2i (Succ n) = 1 + n2i n
n2i _ = 0

i2n :: Int - Nat
i2n 0 = Zero
i2n n = Succ (i2n (n-1))

minN :: Nat - Nat - Nat
minN (Succ m) (Succ n) = Succ (minN m n)
minN _ _ = Zero

ldistance :: UArray Int Char - UArray Int Char - Nat
ldistance orig new = minN (Succ (Succ (Succ Zero))) $ go m n
  where
m = snd $ bounds orig
n = snd $ bounds new
go i j
| i == 0= i2n j
| j == 0= i2n i
| a == b= go (i-1) (j-1)
| otherwise = let h = costArray!(a,b)
  x = case h of
1 - Succ (go (i-1) (j-1))
2 - Succ (Succ (go (i-1) (j-1)))
  y = 

Re: [Haskell-cafe] namespaces for values, types, and classes

2009-11-29 Thread Stuart Cook
On Sun, Nov 29, 2009 at 8:42 AM, pbrowne patrick.bro...@comp.dit.ie wrote:
 Question 3) Instances are not named so can they be imported?

Whenever you import a module, you automatically import all of its
instances as well. In fact, there is no way to *not* include instances
when importing a module.

Furthermore, any instances you import are automatically re-exported by
your own module. The upshot is that importing any module will
automatically include any instances defined in the transitive closure
of module dependencies, and there's nothing you can do to stop it.

(Yes, this is sometimes very irritating, though I appreciate some of
the motivations behind it. It's also one of the reasons why “orphan
instances” are discouraged.)


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


Re: [Haskell-cafe] instance Binary UTCTime (Was: Oprhan instances)

2009-11-29 Thread Duncan Coutts
On Thu, 2009-11-26 at 16:40 -0500, David Menendez wrote:

 The problem with this solution is that it doesn't scale. If we have M
 packages providing types and N packages providing classes, then we
 need M*N additional packages for orphans.
 
 The best long-term solution is probably extending Cabal to handle this
 more transparently, perhaps by allowing packages to depend on flagged
 versions of other packages (e.g., foomonad = 4.0   4.1  HAS_MTL)

Not going to happen. Such packages could not be translated into binary
distro packages.

Duncan

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


[Haskell-cafe] Help mixing pure and IO code

2009-11-29 Thread papa . eric
Hi haskell helpers,

Learning haskell, I wanted to explore how to write pure code and then
add some IO on top of it, keeping the main code pure. The idea was to
write a very simple two-player game, then define some strategies to
play it that do not involve IO, and finally use strategies involving
Random or IO (ask the user). I failed to reuse the pure code, and
the only solution I found was to rewrite most things for IO. Here is
my attempt in literate haskell, it is quite short, I hope someone will
be kind enough to tell me what I have missed... Thanks for any answer!

The game is: each player in turn chooses a number, and wins if this
number has already been chosen twice (the third occurrence wins).

 import Debug.Trace
 import Control.Monad

Choosing a number is a move, a game is all moves played so far.

 type Move = Int
 type Game = [Move]
 
 newGame :: Game
 newGame = []

Game updating rule, Nothing for a winning move (the game stops) else Just
the ongoing game.

 update :: Game - Move - Maybe Game
 update game move = if move `wins` game then Nothing else Just (move:game)
 where move `wins` game = length (filter (== move) game) == 2

Let's give a name to both players, mainly for tracing purposes.

 data Player = Player1 | Player2 deriving Show

 myTrace :: Player - Move - (a - a)
 myTrace player move = trace ((show player) ++  plays  ++ (show move))

A strategy looks at the game and proposes the next move, and may
involve state.

 class Strategy a where
 proposeNext :: Game - a - (Move, a)

The game engine takes two strategies and returns the winner, tracing
what is going on.

runGame starts from a new (empty) game, runGame' updates an ongoing
game and keeps track of who is Player1 or Player2.

 runGame :: (Strategy a1, Strategy a2) = a1 - a2 - Player
 runGame x y = runGame' (Player1, x) (Player2, y) newGame

 runGame' :: (Strategy a1, Strategy a2) =
   (Player, a1) - (Player, a2) - Game - Player
 runGame' (px, x) (py, y) game =   -- x and y are strategies
 let (move, x') = proposeNext game x
 follows = case update game move of
 Nothing - px -- winning move
 Just nextgame - runGame' (py, y) (px, x') nextgame
 in myTrace px move $ follows

An example of a pure strategy that plays a fixed list of numbers, then
zeroes.

 data Fixed = Fixed [Move] deriving Show
 
 instance Strategy Fixed where
 proposeNext game s = case s of
Fixed [] - (0, Fixed [])
Fixed (x:xs) - (x, Fixed xs)

Now you may run
runGame (Fixed [1,2,3]) (Fixed [3,2,1,3])
and Player2 will win.

Now I want the user to be asked for moves. This one works quite well,
asking *once* the user for a list of moves.

 askFixed :: String - IO Fixed
 askFixed name = liftM Fixed askio
 where askio = putStr (name ++ , pick a list of numbers: )  readLn

I could easily reuse runGame:

 runGameSingleIO :: (Strategy a1, Strategy a2) = IO a1 - IO a2 - IO Player
 runGameSingleIO = liftM2 runGame

And this works:
runGameSingleIO (askFixed Joe) (askFixed Jack)

Now I want each user to be asked for moves repeatedly until there is a
win. This was my first try, using an infinite list and hoping lazyness
would work.

 
 askUntil :: String - IO Fixed
 askUntil name = liftM Fixed (sequence $ repeat askio)
 where askio = putStr (name ++ , pick a number: )  readLn

However it does not work, if I evaluate:
liftM2 runGame (askUntil Joe) (askUntil Jack)
then Joe is indefinitely asked for his move...

Now, I supposed that IO [Move] was maybe (when triggered) a unitary
action returning the whole list with no lazyness, and that I would
rather need to have IO attached to individual moves [IO Move], so that
they could be triggered independently. Am I right, or is it still
subtler?

Anyway, I imagined I needed to start from

 data FixedIO = FixedIO [IO Move]

And that's where I failed. I could not define any instance of Strategy
that could be turned to a (IO Strategy) and reuse runGame, and use [IO
Move] somewhere. I could not bring the inner IOs of [IO Move] to be
syhthetised in front of IO Strategy. Was it possible?

All I was able to contrive is a new definition of Strategy and runGame
for the IO case. This seems very awkward. Here it is:

 class StrategyIO a where
 proposeNextIO :: Game - a - IO (Move, a)
 
 runGameIO :: (StrategyIO a1, StrategyIO a2) = a1 - a2 - IO Player
 runGameIO x y = runGameIO' (Player1, x) (Player2, y) newGame
 
 runGameIO' :: (StrategyIO a1, StrategyIO a2) =
   (Player, a1) - (Player, a2) - Game - IO Player
 runGameIO' (px, x) (py, y) game =
 do (move, x') - proposeNextIO game x
case update game move of
  Nothing - return px
  Just nextgame - runGameIO' (py, y) (px, x') nextgame

Then FixedIO could be made a strategy:

 instance StrategyIO FixedIO where
 proposeNextIO game s = case s of
  FixedIO [] - return (0, FixedIO [])
   

Re: [Haskell-cafe] some help debugging ghci build on powerpc

2009-11-29 Thread Duncan Coutts
On Sun, 2009-11-22 at 16:22 -0800, Brian Denheyer wrote:
 I'm trying to build ghc so that ghci will be included under linux power-pc.
 
 The build dies here:
 
 /tmp/ghc21791_0/ghc21791_0.s: Assembler messages:
 
 /tmp/ghc21791_0/ghc21791_0.s:15:0:
  Error: junk at end of line, first unrecognized character is `@'


 I was hoping that this was a bit of cruft and someone could direct me
 to a fix for the assembly portion so I can get a little farther along.

Make sure it's reported in the ghc trac. If you want to work on it
yourself then ask for guidance on the ghc users mailing list.

Duncan

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


Re: [Haskell-cafe] Help mixing pure and IO code

2009-11-29 Thread Bulat Ziganshin
Hello papa,

Sunday, November 29, 2009, 5:11:23 PM, you wrote:

 add some IO on top of it, keeping the main code pure. The idea was to
 write a very simple two-player game, then define some strategies to
 play it that do not involve IO

ho i could do it:

class Strategy state where
  initState :: state
  nextMove :: state - (Move,state)
  updateState :: (Move,state) - state

where initState gives initial state,
nextMove returns move and updated internal state
updateState updates state with opponent's move

then you can develop any IO front-end that runs two strategies each
against other


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] Help mixing pure and IO code

2009-11-29 Thread klondike
papa.e...@free.fr escribió:
 Hi haskell helpers,

 Learning haskell, I wanted to explore how to write pure code and then
 add some IO on top of it, keeping the main code pure. The idea was to
 write a very simple two-player game, then define some strategies to
 play it that do not involve IO, and finally use strategies involving
 Random or IO (ask the user). I failed to reuse the pure code, and
 the only solution I found was to rewrite most things for IO. Here is
 my attempt in literate haskell, it is quite short, I hope someone will
 be kind enough to tell me what I have missed... Thanks for any answer!
I know mainly two options, the first is using unsafe IO which is a small
heresy.

The other is using the Control.Monad lift function which will apply pure
functions over IO ones returning an IOized type.

Ie if we have an
  b :: IO Int
  b = return 3
and we do
  c = lift (+ 2) b
We will get IO(5) when we use c





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


Re: [Haskell-cafe] control-monad-failure and mtl

2009-11-29 Thread Jose Iborra

On 28/11/2009, at 22:08, Edward Z. Yang wrote:

 Hello folks,
 
 I took advantage of Thanksgiving weekend to port my application to use
 Control.Monad.Failure, and learned (slightly painfully) that I still
 needed to pick some mechanism to instantiate my failure monads as.
 After the experience, I have three questions/comments:
 
 1. Why isn't there an instance for Either in mtl? (There is one for
 Transformers.  The error message left me very puzzled there: the docs
 clearly claimed the instance existed, and only a little source code
 diving elucidated the situation.)  Copying the instance declaration
 from the transformers version seems to fix it.
 

There is indeed an Monad instance for Either in mtl,
declared in the module Control.Monad.Error.
I can't explain why your compiler cannot find it.
Can you paste a blurb of code somewhere?


 2. I was having difficulty instantiating MonadFailure as an ErrorT
 for an arbitrary monad.  Here is an example:
 
{-# LANGUAGE PackageImports, FlexibleContexts #-}
 
import mtl Control.Monad.Error
import mtl Control.Monad.State
import Control.Monad.Failure
 
data MyError = MyError String
instance Error MyError where
strMsg = MyError
 
type MyMonad = ErrorT MyError (State Integer)
 
failureFunction :: MonadFailure MyError m = Integer - m Integer
failureFunction 0 = failure $ MyError Cannot use zero
failureFunction n = return (n - 1)
 
-- instantiate
monadicFunction :: MyMonad Integer
monadicFunction = failureFunction 23
 
 Which results in the following error:
 
failure.hs:19:18:
No instance for (MonadFailure
   MyError (ErrorT MyError (State Integer)))
  arising from a use of `failureFunction' at failure.hs:19:18-35
Possible fix:
  add an instance declaration for
  (MonadFailure MyError (ErrorT MyError (State Integer)))
In the expression: failureFunction 23
In the definition of `monadicFunction':
monadicFunction = failureFunction 23
 
 Which seems to contradict the documentation and source code, which states:
 
Instances: [...]
(Error e, Monad m) = MonadFailure e (ErrorT e m)
 
 How do I misunderstand?
 

You need to import Control.Monad.Failure.MTL in order to bring the MTL 
instances into scope.
The reason for this is that we provide instances both for MTL and transformers 
in the same 
package. These have to live in different modules to avoid a conflict due to the 
duplicated 
monad instance for Either.


 3. In a motivating example, one of the goals of MonadFailure is to let
 us mix the error code of third-party modules into the generic failure mode.
 Control.Monad.Failure appears to give the machinery for instantiating a 
 generic
 failure monad, but it doesn't have any facilities for the opposite direction:
 that is, marshalling a specific error form into the generic error form.  Am I
 mistaken, and if not, would it be a welcome addition to the library?

Very likely. Existing error handling packages such as control-monad-exception 
and attempt
already provide this feature to convert other error forms into their specific 
error types.
If this can be abstracted cleanly for a generic form of failure,
then I would definitely support including it in control-monad-failure.

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


Re: [Haskell-cafe] ghci breakpoints

2009-11-29 Thread Jose Iborra
Hi Sean,

it looks like your Focus module is not interpreted and thus has no breakpoints.
(that error message could be easily improved to let you know this)

The ghci debugger only works with interpreted code, you can either delete all 
the
*.hi and *.o temporary files or simply use the flag -fbyte-code to ensure that
ghci loads the code in interpreted mode.

By the way, the ghci debugger has a few quirks more.
You probably want to give a read to the debugger docs in the GHC manual if you
plan to use it for anything non trivial.

Thanks,
pepe

On 29/11/2009, at 06:18, Sean McLaughlin wrote:

 Hello,
 
  I'm having trouble setting breakpoints from ghci.  I load the files
 and I can tell things are working correctly because I can run the
 program and list the locations where I want to set breakpoints.  E.g.
 
 Prelude :list Focus.focus
 510   focus :: forall s m. Class s m = Neg - m [Foci]
 511   focus f =
 512 let ats = Path.atoms f
 
 But when I try to set a breakpoint I get
 
 Prelude :break Focus.focus
 No breakpoints found at that location.
 
 Does anyone have ideas about what I'm doing wrong in this case?  Do I
 need to load with some special options to have breakpoints work?
 
 Thanks,
 
 Sean
 ___
 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] Re: ANNOUNCE: Clutterhs 0.1

2009-11-29 Thread Matt Arsenault
On Sun, 2009-11-29 at 08:09 +0100, Gour wrote:

 
 What do you think about binding Moblin's nbtk (now it's called mx) ?
 
Right now I'm working on finishing Clutter, Clutter-gtk, and COGL.

 Otoh, are you aware of:
 
  http://github.com/elliottt/clutter 
  http://github.com/yav/clutter
 
 

I found that quite a while after I started working. I messaged them, but
didn't really get a response.


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


[Haskell-cafe] Hoogle Down

2009-11-29 Thread Elliot Wolk

hello!
im not sure that this is the correct mailing list for saying so, and 
also whether or not today's down-ness is just scheduled maintenance, but 
hoogle appears to be down again. sorry if this is known/redundant/not 
the right place!


thanks, elliot


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


Re: [Haskell-cafe] Help mixing pure and IO code

2009-11-29 Thread Felipe Lessa
On Sun, Nov 29, 2009 at 03:11:23PM +0100, papa.e...@free.fr wrote:
 However, I wonder how to do it reusing the pure versions,
 runGame and Strategy?

There's a nice approach to this problem which is described and
implemented in the MonadPrompt package[1].  Basically you have

prompt :: MonadPrompt p m = p a - m a

which allows you to interact with the outside world.  The beauty
here is that the interection is generic, you may write a pure
simulator (like yours), an IO-heavy game (like what you're
trying) and possibly more, like unit tests and property checks.

Cheers,

[1] http://hackage.haskell.org/package/MonadPrompt

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


[Haskell-cafe] peekCString free memory

2009-11-29 Thread El Barto
Hello,
I get a segfault when I do
str - peekCString ptr
free ptr
return (Just str)

But not when I don't free the C pointer.
I also get the same behaviour with ByteString.packCString...

Could you please tell me if the memory is correctly freed by GHC  when I
don't do it myself?
And how can I specify a custom free function (i.e. xmlFree function in
libxml2)?
Maybe I should use a data type with two fields : the String/ByteString and
the ForeignPtr to the CString?

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


Re: [Haskell-cafe] peekCString free memory

2009-11-29 Thread Thomas DuBuisson
Could you expand on this fragment of code?  Perhaps a fullying
compilable example?  It depends how you are getting the pointer, not
how you are reading data out of the pointer.  For example, if you use
withCString to get ptr then the memory will be freed automatically.

Thomas

On Sun, Nov 29, 2009 at 9:00 AM, El Barto elbart...@gmail.com wrote:
 Hello,
 I get a segfault when I do
 str - peekCString ptr
 free ptr
 return (Just str)

 But not when I don't free the C pointer.
 I also get the same behaviour with ByteString.packCString...

 Could you please tell me if the memory is correctly freed by GHC  when I
 don't do it myself?
 And how can I specify a custom free function (i.e. xmlFree function in
 libxml2)?
 Maybe I should use a data type with two fields : the String/ByteString and
 the ForeignPtr to the CString?

 Regards

 ___
 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] instance Binary UTCTime (Was: Oprhan instances)

2009-11-29 Thread Alexander Dunlap
On Sun, Nov 29, 2009 at 5:37 AM, Duncan Coutts
duncan.cou...@googlemail.com wrote:
 On Thu, 2009-11-26 at 16:40 -0500, David Menendez wrote:

 The problem with this solution is that it doesn't scale. If we have M
 packages providing types and N packages providing classes, then we
 need M*N additional packages for orphans.

 The best long-term solution is probably extending Cabal to handle this
 more transparently, perhaps by allowing packages to depend on flagged
 versions of other packages (e.g., foomonad = 4.0   4.1  HAS_MTL)

 Not going to happen. Such packages could not be translated into binary
 distro packages.

 Duncan


Wouldn't the distro just choose one set of flags for each package and
then other packages would either be satisfied or not satisfied based
on which flags had been chosen? It seems to me that distros could even
offer multiple options for the same package with different flags set.
What wouldn't work?

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


Re: [Haskell-cafe] peekCString free memory

2009-11-29 Thread Bulat Ziganshin
Hello El,

Sunday, November 29, 2009, 8:00:02 PM, you wrote:

segfault is due to free, you may omit peekCString call.
you should free only memory that was malloced and not freed other way

 Hello,
 I get a segfault when I do
 str - peekCString ptr
 free ptr
 return (Just str)

 But not when I don't free the C pointer.
 I also get the same behaviour with ByteString.packCString...

  Could you please tell me if the memory is correctly freed by GHC  when I 
 don't do it myself?
 And how can I specify a custom free function (i.e. xmlFree function in 
 libxml2)?
 Maybe I should use a data type with two fields : the
 String/ByteString and the ForeignPtr to the CString?
  
 Regards
   


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] peekCString free memory

2009-11-29 Thread Duncan Coutts
On Sun, 2009-11-29 at 18:00 +0100, El Barto wrote:
 Hello,
 I get a segfault when I do
 str - peekCString ptr
 free ptr
 return (Just str)

As Thomas says, you've not really given us enough info here.

I'll make some guesses and observations anyway :-)

 But not when I don't free the C pointer.

Are you sure the C code does not also free the memory? That would lead
to a double-free which can easily manifest as a segfault.

 I also get the same behaviour with ByteString.packCString...

That's pretty odd since packCString does not free the C string, it makes
a copy. I suppose it could possibly segfault if your C string was not
actually null terminated (as C strings must be).

There are also variants that do not copy, such as
unsafePackMallocCString. See the docs for a description.

 Could you please tell me if the memory is correctly freed by GHC  when
 I don't do it myself?
 And how can I specify a custom free function (i.e. xmlFree function in
 libxml2)?

See the documentation for ForeignPtr.

 Maybe I should use a data type with two fields : the String/ByteString
 and the ForeignPtr to the CString?

Is your C String supposed to be freed using the C free() function, or is
it supposed to be freed using xmlFree() or something?

Duncan

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


Re: [Haskell-cafe] peekCString free memory

2009-11-29 Thread El Barto
Thanks for your help  time,

I checked the C API documentation:
http://xmlsoft.org/html/libxml-xmlreader.html#xmlTextReaderValue
The result must be deallocated with xmlFree()

I pushed the sources here:
http://github.com/gwenn/libxml-reader

My problem is with the function at line 249 in Text.XML.LibXML.XmlReader
To make it work, I have to comment out the line where xmlFree is called.

-- xmlChar * xmlTextReaderValue(xmlTextReaderPtr reader)
-- Returns:the string or NULL if not available. The result must be
deallocated with xmlFree()
foreign import ccall unsafe xmlreader.h xmlTextReaderValue
c_xmlTextReaderValue :: Ptr XmlTextReader - IO (CString)
value :: (MonadIO m) = XmlReader - m (Maybe B.ByteString)
value (XmlReader reader_fp) = liftIO $
withForeignPtr reader_fp $ \reader_ptr - do
cstr - c_xmlTextReaderValue reader_ptr
fromPtr B.packCString cstr c_xmlFree

fromPtr :: (Ptr a - IO b) - Ptr a - (Ptr a - IO ()) - IO (Maybe b)
fromPtr c2h ptr free | ptr == nullPtr = return Nothing
 | otherwise = do
r - c2h ptr
free ptr -- FIXME
return (Just r)

May be the binding to xmlFree is wrong?
foreign import ccall unsafe xmlreader.h xmlFree
c_xmlFree :: Ptr a - IO ()

To test, you will need libxml2-dev:
$ runhaskell Setup configure --extra-include-dirs=/usr/include/libxml2/
$ runhaskell Setup build
$ ./dist/build/Test/Test

C functions are described here:
http://xmlsoft.org/html/libxml-xmlreader.html
And here:
http://xmlsoft.org/html/libxml-globals.html

Regards.

On Sun, Nov 29, 2009 at 7:02 PM, Duncan Coutts duncan.cou...@googlemail.com
 wrote:

 On Sun, 2009-11-29 at 18:00 +0100, El Barto wrote:
  Hello,
  I get a segfault when I do
  str - peekCString ptr
  free ptr
  return (Just str)

 As Thomas says, you've not really given us enough info here.

 I'll make some guesses and observations anyway :-)

  But not when I don't free the C pointer.

 Are you sure the C code does not also free the memory? That would lead
 to a double-free which can easily manifest as a segfault.

  I also get the same behaviour with ByteString.packCString...

 That's pretty odd since packCString does not free the C string, it makes
 a copy. I suppose it could possibly segfault if your C string was not
 actually null terminated (as C strings must be).

 There are also variants that do not copy, such as
 unsafePackMallocCString. See the docs for a description.

  Could you please tell me if the memory is correctly freed by GHC  when
  I don't do it myself?
  And how can I specify a custom free function (i.e. xmlFree function in
  libxml2)?

 See the documentation for ForeignPtr.

  Maybe I should use a data type with two fields : the String/ByteString
  and the ForeignPtr to the CString?

 Is your C String supposed to be freed using the C free() function, or is
 it supposed to be freed using xmlFree() or something?

 Duncan


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


[Haskell-cafe] Partially applied functions

2009-11-29 Thread Casey Hawthorne
You can pattern match on the right hand side of '|' in a list
comprehension, since a list comprehension is just the list monad.


Just changed a few things.
Hopefully this answers the OP's question and any interested others.

add :: Int - Int - Int
add x y = x + y

-- a list of partially applied functions
adds = [add 3, add 5, add 7, add 3, add 5, add 8]

-- an example usage of the list
kP pred = map (\ f - f 10 ) (addPs pred)

-- Wanted to do things like this.
-- add3s = filter (?) adds -- add3s = [add 3, add 3]
-- addEvens = filter (?) adds --addEvens = [add 8]

-- addPs num = [ x | x - adds, x 0 == num ]
-- Changed 'x' to 'f' indicating a function application.
addPs pred = [ f | f - adds, pred (f 0) ]

-- Main kP (==3)
-- Main kP even

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


Re: [Haskell-cafe] instance Binary UTCTime (Was: Oprhan instances)

2009-11-29 Thread David Menendez
On Sun, Nov 29, 2009 at 8:37 AM, Duncan Coutts
duncan.cou...@googlemail.com wrote:
 On Thu, 2009-11-26 at 16:40 -0500, David Menendez wrote:

 The problem with this solution is that it doesn't scale. If we have M
 packages providing types and N packages providing classes, then we
 need M*N additional packages for orphans.

 The best long-term solution is probably extending Cabal to handle this
 more transparently, perhaps by allowing packages to depend on flagged
 versions of other packages (e.g., foomonad = 4.0   4.1  HAS_MTL)

 Not going to happen. Such packages could not be translated into binary
 distro packages.

Do you mean that specific idea won't happen, or that no attempt will
be made to reduce the orphan problem?

-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] FAD

2009-11-29 Thread Ozgur Akgun
While searching for a design tool for Haskell, I've come across the PhD
thesis of Dan Russell http://www.cs.kent.ac.uk/pubs/2001/1152/
He also mentioned the tool in cafe some time ago:
http://www.haskell.org/pipermail/haskell-cafe/2003-June/004606.html

Does anyone in the cafe, or himself, direct me to the download link of this
tool; so that I can try it out.

Cheers,

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


Re: [Haskell-cafe] Data.Binary and error handling

2009-11-29 Thread Khudyakov Alexey
В сообщении от 27 ноября 2009 23:55:47 Don Stewart написал:
 alexey.skladnoy:
  It does but it was already noted that cereal uses strict bytestrings
  which are not really convenient when dealing with huge inputs. One may
  end up using both binary and cereal which is not really satisfactory.
 
 It is quite hard to do a good job of lazy input, but explicit checked
 errors (turning it into an Either Error a makes the whole stream
 strict!).
 
Surprisingly it seems that it's not possible to avoid unexpected end of input 
error without forcing input. Primitive parsers fail in that case and only 
reasonably way to check against this is 'remaining' function which forces 
input. Moreover it's very inconvenient to check before significant fraction of 
calls that input has sufficient length.

Of course it's possible to implement robust parsers with getWord8  isEmpty 
duo but this is theoretical possibility.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] instance Binary UTCTime (Was: Oprhan instances)

2009-11-29 Thread Duncan Coutts
On Sun, 2009-11-29 at 16:42 -0500, David Menendez wrote:
 On Sun, Nov 29, 2009 at 8:37 AM, Duncan Coutts
 duncan.cou...@googlemail.com wrote:
  On Thu, 2009-11-26 at 16:40 -0500, David Menendez wrote:
 
  The problem with this solution is that it doesn't scale. If we have M
  packages providing types and N packages providing classes, then we
  need M*N additional packages for orphans.
 
  The best long-term solution is probably extending Cabal to handle this
  more transparently, perhaps by allowing packages to depend on flagged
  versions of other packages (e.g., foomonad = 4.0   4.1  HAS_MTL)
 
  Not going to happen. Such packages could not be translated into binary
  distro packages.
 
 Do you mean that specific idea won't happen, or that no attempt will
 be made to reduce the orphan problem?

I mean specifically proposal to change the Cabal package semantics such
that they cannot be translated into native system binary packages on
various platforms.

It's vital to distributing our work that we can produce sensible binary
packages on the platforms that people want to use.

I should also note that distros will not look kindly on solutions that
require N * M separate packages.

Duncan

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


Re: [Haskell-cafe] instance Binary UTCTime (Was: Oprhan instances)

2009-11-29 Thread Duncan Coutts
On Sun, 2009-11-29 at 09:55 -0800, Alexander Dunlap wrote:
 On Sun, Nov 29, 2009 at 5:37 AM, Duncan Coutts
 duncan.cou...@googlemail.com wrote:
  On Thu, 2009-11-26 at 16:40 -0500, David Menendez wrote:
 
  The problem with this solution is that it doesn't scale. If we have M
  packages providing types and N packages providing classes, then we
  need M*N additional packages for orphans.
 
  The best long-term solution is probably extending Cabal to handle this
  more transparently, perhaps by allowing packages to depend on flagged
  versions of other packages (e.g., foomonad = 4.0   4.1  HAS_MTL)
 
  Not going to happen. Such packages could not be translated into binary
  distro packages.
 
  Duncan
 
 
 Wouldn't the distro just choose one set of flags for each package and
 then other packages would either be satisfied or not satisfied based
 on which flags had been chosen?

Here's the system I assumed you were talking about. You can tell me if I
misunderstood.

Instead of having N * M packages, you have a package that provides
optional instances. For example package A defines a class and
optionally provides instances for types defined in B. If you select to
have it depend on B then the instances are provided, otherwise not.

In a source based system this seems to work ok, you would provide
optional instances for all the packages you already happen to have
installed. Though if later you install another package that could have
had optional instances provided then you have to go recompiling things.

It's slightly worse for binary packages because the distro has to decide
up front if they're going to provide the optional instances or not.
Since someone might need them then you end up picking the maximal set of
optional dependencies and you end up pulling in all sorts of apparently
unrelated packages.

Then the other bit you suggested foomonad = 4.0   4.1  HAS_MTL
would be needed to be able to express that you want a package that has
been built with a particular optional instance provided. This is the bit
that cannot be translated into packages in most distros. Yes you could
pick the flags up front, but you have to pick a single assignment that
satisfies everyone.

 It seems to me that distros could even offer multiple options for the
 same package with different flags set.

Most distros cannot handle installing multiple instances of the same
version of a package.

Duncan

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


[Haskell-cafe] Haskell Weekly News: Issue 141 - November 29, 2009

2009-11-29 Thread jfredett

---
Haskell Weekly News
http://sequence.complete.org/hwn/20091129
Issue 141 - November 29, 2009
---
   Welcome to issue 141 of HWN, a newsletter covering developments in the
   [1]Haskell community.

   Firstly, sorry for the late HWN, a turkey coma is equal parts gift and
   curse. This week, we have some very exciting news, a new Haskell
   standard -- Haskell 2010 -- was announced, including several small
   changes. Also, we have lots of new packages, a possible Boston-area
   Hackathon coming up soon, and some great discussion. I won't hold you
   back from skipping all that and just reading the funny quotes!
   Haskellers, your (belated) Haskell Weekly News!

Announcements

   Haskell 2010. Simon Marlow [2]announced the new revision of Haskell,
   Haskell 2010. Part of the new, less monolithic Haskell Prime process,
   Haskell 2010 includes several changes to the Haskell Language,
   including support for nonstandard if-then-else syntax (particularly wrt
   `do` notation and indentation), pattern guards, and several other
   changes. See the post for details.

   Clutterhs 0.1. Matt Arsenault [3]announced Clutterhs, version 0.1. A
   set of bindings for Clutter, a GObject based library for creating 2.5D
   interfaces using OpenGL.

   Interesting experiences of test automation in Haskell? Automation of
   Software Test 2010. John Hughes [4]announced a 'heads up' for the
   Automation af Software Test 2010 workshop

   NoSlow - Microbenchmarks for array libraries. Roman Leshchinskiy
   [5]announced his benchmark suite for various array and list libraries.

   CMCS 2010: First call for papers. Alexandra Silva [6]announced a first
   call for papers for the Tenth International Workshop on Coalgebraic
   Methods in Computer Science, taking place 26-28 March 2010, in Paphos,
   Cyprus.

   GPCE'10 First Call for Papers. Bruno Oliveira [7]announced a first call
   for papers for the Ninth International Conference on Generative
   Programming and Component Engineering. GPCE 2010 October 10-13, in
   Eindhoven, The Netherlands.

   Call for Participation: TLDI'10. Andrew Kennedy [8]announced a call for
   participation in the 2010 ACM SIGPLAN Workshop on Types in Language
   Design and Implementation

   Deadline Extension: JSC Special Issue on Automated Specification and
   Verification of Web Systems. demis [9]announced an extension to the
   paper deadline for the JSC Special Issue on Automated Specification and
   Verification of Web Systems.

   VSTTE 2010: Verified Software -- Second Call for Papers. Gudmund Grov
   [10]announced the second call for papers for the Third International
Conference on Verified Software: Theories, Tools, and Experiments

   GPipe-1.1.0 with greatly improved performance. Tobias Bexelius
   [11]announced a new version of the GPipe package, now with greatly
   improved performance.

   wumpus-core. Stephen T [12]announced a new version of the wumpus-core
   package, a library for drawing 2D vector pictures, supporting output to
   SVG and postscript.

   package-vt-0.1.3.3, Haskell Package Versioning Tool. Krzysztof
   Skrzetnicki [13]announced the first release of his automatic version
   tracking tool, package-vt.

   Elerea 1.1. Patai Gergely [14]announced a new version of Elerea, a
   simple pull-based FRP library. Elerea (and FRP in general) allow for
   stream oriented programming, typically done in a applicative style.

   mecha-0.0.4. Tom Hawkins [15]announced a new version of Mecha, a little
   constructive solid modeling language intended for doing 3D CAD.

   atom-0.1.2. Tom Hawkins [16]announced a new release of Atom, a DSL for
   designing hard realtime embedded software with Haskell. This release
   adds guarded division operations, a new scheduling constraint, and a
   new rule scheduling algorithm.

   Managing Cabal Dependencies using Nix and Hack-nix. Marc Weber
   [17]announced a package for dealing with Cabal dependencies on the Nix
   OS platform.

Discussion

   haskell in online contests. vishnu [18]asked about using Haskell in
   online contests, and particularly dealing with the SPOJ tool for
   judging programs.

   Namespaces for values, types, and classes. Sebastian Fischer
   [19]suggested allowing a namespace separation between class-names and
   other language elements.

   I miss OO. Michael Mossey [20]lamented his desire for Object-oriented
   features in Haskell, this led to a interesting discussion about name
   punning and typeclasses.

   Haskell Hackathon in Boston January 29th-31st? Ravi Nanavati
   [21]proposed a potential Hackathon in this editor's favorite city, to
   be held the 29th to the 31st.

Blog noise

   [22]Haskell news from the [23]blogosphere. Blog posts from people new
   to the Haskell community are marked with , be sure to welcome them!
 * Dan Piponi (sigfpe): [24

Re: [Haskell-cafe] instance Binary UTCTime (Was: Oprhan instances)

2009-11-29 Thread Alexander Dunlap
On Sun, Nov 29, 2009 at 4:41 PM, Duncan Coutts
duncan.cou...@googlemail.com wrote:
 On Sun, 2009-11-29 at 09:55 -0800, Alexander Dunlap wrote:
 On Sun, Nov 29, 2009 at 5:37 AM, Duncan Coutts
 duncan.cou...@googlemail.com wrote:
  On Thu, 2009-11-26 at 16:40 -0500, David Menendez wrote:
 
  The problem with this solution is that it doesn't scale. If we have M
  packages providing types and N packages providing classes, then we
  need M*N additional packages for orphans.
 
  The best long-term solution is probably extending Cabal to handle this
  more transparently, perhaps by allowing packages to depend on flagged
  versions of other packages (e.g., foomonad = 4.0   4.1  HAS_MTL)
 
  Not going to happen. Such packages could not be translated into binary
  distro packages.
 
  Duncan
 

 Wouldn't the distro just choose one set of flags for each package and
 then other packages would either be satisfied or not satisfied based
 on which flags had been chosen?

 Here's the system I assumed you were talking about. You can tell me if I
 misunderstood.

 Instead of having N * M packages, you have a package that provides
 optional instances. For example package A defines a class and
 optionally provides instances for types defined in B. If you select to
 have it depend on B then the instances are provided, otherwise not.

 In a source based system this seems to work ok, you would provide
 optional instances for all the packages you already happen to have
 installed. Though if later you install another package that could have
 had optional instances provided then you have to go recompiling things.

 It's slightly worse for binary packages because the distro has to decide
 up front if they're going to provide the optional instances or not.
 Since someone might need them then you end up picking the maximal set of
 optional dependencies and you end up pulling in all sorts of apparently
 unrelated packages.

 Then the other bit you suggested foomonad = 4.0   4.1  HAS_MTL
 would be needed to be able to express that you want a package that has
 been built with a particular optional instance provided. This is the bit
 that cannot be translated into packages in most distros. Yes you could
 pick the flags up front, but you have to pick a single assignment that
 satisfies everyone.

Well, that happens anyway with most packages since distros have to
choose one set of flags that works. The proposal I was commenting on
would just allow packages to depend on flags of other packages and so
be explicit about this.


 It seems to me that distros could even offer multiple options for the
 same package with different flags set.

 Most distros cannot handle installing multiple instances of the same
 version of a package.

Well, what I've seen is having different packages, i.e.
foo-quickcheck, foo-no-quickcheck as separate packages.

(Note that I can't take credit for suggesting the idea, I was just
asking you about your objection.)

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


Re: [Haskell-cafe] instance Binary UTCTime

2009-11-29 Thread Ivan Lazar Miljenovic
Alexander Dunlap alexander.dun...@gmail.com writes:

 Well, that happens anyway with most packages since distros have to
 choose one set of flags that works. The proposal I was commenting on
 would just allow packages to depend on flags of other packages and so
 be explicit about this.


Consider this problem:

* Package Foo has an optional instance, enabled with the --foo flag.

* Package Bar wants that instance.

* Package Baz doesn't want that instance, since it uses its own custom
  instance (e.g. yi's instance of Category for Data.Accessor.Basic.T,
  which clashes with the one added to data-accessor 0.2.1).

* You want to install both Bar and Baz.

Which one do you end up using?  You can't have the same version of Foo
installed twice (as far as I know anyway).

It would be nice to have a separate namespace in exports/imports for
instances so you _can_ selectively override them if you so wish, but
that will probably cause other problems.

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Are there standard idioms for lazy, pure error handling?

2009-11-29 Thread John Millikin
I'm working on a library which needs to operate on large data sets, so
I'd like to use lazy values. The library consists of pure functions
from Text to [Event] and back. Normally, I use Maybe or Either for
error handling in pure code, but using these precludes lazy
evaluation. Using exceptions requires any errors to be handled in IO,
which is annoying.

The idealized signatures of the functions are:

import qualified Data.Text.Lazy as TL
data Event = EventA | EventB | EventC
parse :: TL.Text - Either ParseError [Event]
serialize :: [Event] - Either SerializeError TL.Text


I've considered two possible error handling modes, both adapted from
procedural language style. The first is simply including errors in the
event list.

import qualified Data.Text as T
parse :: TL.Text - [Either ParseError Event]
serialize :: [Event] - [Either SerializeError T.Text] -- use TL.fromChunks


The second uses monadic callbacks, based on side effects:

parse :: Monad m = (Event - m ()) - (ParseError - m ()) - TL.Text - m ()
serialize :: Monad m = (T.Text - m ()) - (SerializeError - m ())
- [Event] - m ()


The main problem I see with these is that they don't indicate or
enforce that an error terminates the event/text streams. The first
allows multiple errors in a row, or events to follow an error. The
second just feels ugly, because using it in pure code requires
clients to build a Writer (possibly wrapped with ErrorT) and deal with
the associated plumbing.

Is there any sort of standard idiom for handling this problem? It
seems that somebody must have run across it before, but the resources
I can find on lazy error handling all assume the code is impure
(returning IO, etc).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Haskell Job Openings (Pune, IN)

2009-11-29 Thread Tom Hawkins
We finally got some open reqs in Eaton's engineering center in Pune,
India.  Could involve a little Haskell programming, or a lot,
depending on what you want to do.

http://jobsearch.naukri.com/job-listings-Senior-Engineer-Automotive-Embedded-Eaton-Technologies-Pvt-Ltd-Pune-3-to-7-years-151109000171-

I'd be happy to forward on any resumes to the hiring manager.

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


[Haskell-cafe] hscolour + unicode

2009-11-29 Thread Sean McLaughlin
Hello,

  Is there a way to get the source documentation from cabal haddock
--hyperlink-source to show up with unicode characters preserved?
Right now the unicode from my comments and source programs are being
mangled.  I tried the --haddock-option=--use-unicode option, but it
seems to only work on the haddock docs, not the sources that are
hscoloured and linked.

Thanks,

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


Re: [Haskell-cafe] Are there standard idioms for lazy, pure error handling?

2009-11-29 Thread Malcolm Wallace

I'm working on a library which needs to operate on large data sets, so
I'd like to use lazy values. ...

import qualified Data.Text as T
parse :: TL.Text - [Either ParseError Event]



I would say that this is the most desirable approach, if you are  
generating a sequence, and want lazy processing of the elements.   
Indeed, in my own experience, this is the only reasonable way to deal  
with very large datasets, without running out of memory.



The main problem I see with these is that they don't indicate or
enforce that an error terminates the event/text streams. The first
allows multiple errors in a row, or events to follow an error.


Are you sure that there can be no error recovery, to continue with  
events after a mal-formed event has been discarded?  In many cases, it  
is possible.  However, if you really want to terminate the stream at  
the first error, and to reflect this in the type, then I guess you can  
define your own list type:


data ListThenError e a = Cons a (ListThenError e a)
   | Error e

Of course this has the disadvantage that then your consumer must  
change to use this type too.


Regards,
Malcolm

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


Re: [Haskell-cafe] Are there standard idioms for lazy, pure error handling?

2009-11-29 Thread Luke Palmer
On Sun, Nov 29, 2009 at 11:08 PM, Malcolm Wallace
malcolm.wall...@cs.york.ac.uk wrote:
 Are you sure that there can be no error recovery, to continue with events
 after a mal-formed event has been discarded?  In many cases, it is possible.
  However, if you really want to terminate the stream at the first error, and
 to reflect this in the type, then I guess you can define your own list type:

 data ListThenError e a = Cons a (ListThenError e a)
                       | Error e

 Of course this has the disadvantage that then your consumer must change to
 use this type too.

If it is correct, there is no disadvantage.  Using a list when it is
not the appropriate structure will make both the producer and the
consumer code uglier. You might gain a little notational convenience,
but you bubble implicit assumptions, such as an error terminates a
stream, through the code where they can not be checked.

Of course, when you have a stream from which errors can be recovered,
do not use a type that terminates with errors.

Everything cleans up so nicely when your model perfectly captures your problem.

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