Re: [Haskell-cafe] Re: Numeric type classes

2006-09-13 Thread ajb
G'day all.

Quoting Jason Dagit <[EMAIL PROTECTED]>:

> I was making an embedded domain specific language for excel
> spreadsheet formulas recently and found that making my formula
> datatype an instance of Num had huge pay offs.

Just so you know, what we're talking about here is a way to make that
even _more_ useful by dicing up Num.

> I can even use things like Prelude.sum to
> add up cells.

Ah, but the sum function only needs 0 and (+), so it doesn't need
the full power of Num.  It'd be even _more_ useful if it worked on
all data types which supported 0 and (+), but not necessarily (*):

sum :: (AdditiveAbelianMonoid a) => [a] -> a

product :: (MultiplicativeAbelianMonoid a) => [a] -> a

Those are bad typeclass names, but you get the idea.

Right now, to reuse sum, people have to come up with fake
implementations for Num operations that simply don't make sense on
their data type, like signum on Complex numbers.

>  All I really needed was to define Show and Num
> correctly,  neither of which took much mental effort or coding tricks.

You also needed to derive Eq, which gives you, in your case, structural
equality rather than semantic equality (which is probably undecidable for
your DSL).

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


[Haskell-cafe] Traversing a graph in STM

2006-09-13 Thread Einar Karttunen
Hello

Is there an elegant way of traversing a directed graph in STM?

type Node  nt et = TVar (NodeT nt et)
type Edge  et= TVar et
data NodeT nt et = NodeT nt [(Node nt et, Edge et)]

type MyGraph = Node String Int

When implementing a simple depth first search we need a way to
mark nodes (= TVars) as visited. In addition multiple concurrent
searches should be possible.

Is it possible to avoid passing around an explicit Set of visited
nodes? And is there a better way of getting TVar identity than
StableNames?

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


Re: [Haskell-cafe] Traversing a graph in STM

2006-09-13 Thread Chris Kuklewicz

Einar Karttunen wrote:

Hello

Is there an elegant way of traversing a directed graph in STM?

type Node  nt et = TVar (NodeT nt et)
type Edge  et= TVar et
data NodeT nt et = NodeT nt [(Node nt et, Edge et)]

type MyGraph = Node String Int

When implementing a simple depth first search we need a way to
mark nodes (= TVars) as visited. In addition multiple concurrent
searches should be possible.


And the concurrent searches are isolated from each other?  Or are you performing 
a single search using many threads?




Is it possible to avoid passing around an explicit Set of visited
nodes? And is there a better way of getting TVar identity than
StableNames?

- Einar Karttunen
___
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] Re: evaluate vs seq

2006-09-13 Thread apfelmus
Michael Shulman wrote:
> On 9/11/06, [EMAIL PROTECTED] <[EMAIL PROTECTED]> wrote:
>> > * (a `seq` return a) = evaluate a *right now*, then produce an IO
>> action
>> >  which, when executed, returns the result of evaluating a.  Thus, if
>> >  a is undefined, throws an exception right now.
>>
>> is a bit misleading as there is no evaluation "right now". It's better
>> to say that (a `seq` return a) is _|_ ("bottom", i.e. undefined) when a
>> == _|_.
> 
> Sure... but what about when a is not _|_?  I would also like to
> understand the difference between `seq' and `evaluate' for arguments
> that are defined.  How would you describe that without talking about
> "when" expressions are evaluated?

Ah well, the discussion goes about denotational semantics of
Haskell. Unfortunately, I did not find a good introductory website about
this. Personally, I found the explanation from Bird and Wadler's book
about infinite lists very enlightening.

The game roughly goes as follows: denotational semantics have been
invented to explain what a recursive definition should be. I mean,
thinking of functions as things that map (mathematical) sets on sets
excludes self-referencing definitions (russell's paradox!).

The solution is to think functions of as fixed points of an iterative
process: factorial is the fixed point of
   (fac f) n = if n == 0 then 1 else n*f(n-1)
what means
   (fac factorial) n == factorial n

Now, the iterative process goes as follows:
  factorial_0 n = _|_
  factorial_1 n = fac (factorial_0) n
= if n == 0 then 1 else _|_
  factorial_2 n = fac (factorial_1) n
= case n of
   0 -> 1
   1 -> 1
   _ -> _|_
and so on. Everytime, a more refined version of the ultimate goal
factorial is created, on says that
  _|_ == factorial_0 <= factorial_1 <= factorial_2 <= ...
(<= means "less or equal than")
That's why _|_ is called "bottom" (it's the smalled thing in the hierarchy).

This was about functions. In a lazy language, "normal" values can show a
similar behavior. For instance, we have
  _|_  <=  1:_|_  <= 1:2:_|_ <= 1:2:3:_|_ <= ... <= [1..]
That's how the infinite list [1..] is approximated. The inequalities
follow from the fact that bottom is below everything and that all
constructors (like (:)) are monotone (by definition), i.e.
  1:x <= 1:y  iff  x <= y

A function f is called *strict*, if it fulfills
  f _|_ = _|_
which means that it does not produce a constructor ("information")
without knowing what its argument is.




Back to your original question, we can now talk about functions in terms
of _|_ and *data constructors*. As an example, we want to think about
the meaning of (take 2 [1..]). What should this be? I mean, one argument
is an infinite list! By tracing the definition of (take 2), one finds
  take 2 _|_ == _|_ -- (btw (take 2) is strict)
  take 2 (1:_|_) == 1:_|_
  take 2 (1:(2:_|_)) == 1:(2:[])
  take 2 (1:(2:(3:_|_))) == 1:(2:[])
and so on. The right and side remains equal for all further refinements,
so we must conclude
  take 2 [1..]   == 1:(2:[]).

For the evaluate and `seq` problem, we simplify things by specializing
the polymorphic type to ([Int] -> IO [Int]). Then, we introduce two
constructors (ThrowException :: IO [Int]) and (Return :: IO [Int]) with
the obvious meaning. The semantics of `seq` are now as following:
  _|_`seq` x == _|_
  [] `seq` x == x
  (y:ys) `seq` x == x
So `seq` forces its first argument. When we define
  f x = x `seq` (Return x)
we thereby get
  f _|_== _|_
  f [] == Return []
  f (x:xs) == Return (x:xs)
To compare, the semantics of (evaluate) is
  evaluate _|_== ThrowException =/= _|_
  evaluate [] == Return []
  evaluate (x:xs) == Return (x:xs)
That should answer your question.

Please note that this answer is actually a lie, as functions must be
monotone (halting problem, fix id == _|_), but (evaluate) is not:
  _|_ <= []
yet
  evaluate _|_ == ThrowException   http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Traversing a graph in STM

2006-09-13 Thread Einar Karttunen
On 13.09 08:48, Chris Kuklewicz wrote:
> And the concurrent searches are isolated from each other?  Or are you 
> performing a single search using many threads?

Isolated from each other. Mainly dreaming of the per-transaction
variables attached to the nodes :-)

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


Re: [Haskell-cafe] Re: Numeric type classes

2006-09-13 Thread Ross Paterson
On Tue, Sep 12, 2006 at 08:59:30PM -0400, [EMAIL PROTECTED] wrote:
> One of the proposals that comes up every so often is to allow the
> declaration of a typeclass instance to automatically declare instances
> for all superclasses.  So, for example:
> 
> class (Functor m) => Monad m where
> fmap f m = m >>= return . f
> 
> instance Monad Foo where
> return a = {- ... -}
> m >>= k = {- ... -}
> fail s = {- ... -}
> 
> This will automatically declare an instance of Functor Foo.
> 
> Similarly, a finer-grained collection of numeric typeclasses could
> simply make Num a synonym for (Show a, Ord a, Ring a, Signum a).
> Declaring an instance for (Num Bar) declares all of the other
> instances that don't yet have a declaration.

Such features would be useful, but are unlikely to be available for
Haskell'.  If we concede that, is it still desirable to make these
changes to the class hierarchy?

I've collected some notes on these issues at

http://haskell.galois.com/cgi-bin/haskell-prime/trac.cgi/wiki/StandardClasses

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


Re: [Haskell-cafe] Slow IO

2006-09-13 Thread Udo Stenzel
Daniel Fischer wrote:
> > Most certainly not.  I'm pretty sure this is to a bug in your code.
> > Something retains a data structure which is actually unneeded.  Probably
> 
> Apparently. And my money is on a load of lines from the file (of which I need 
> only the first and last Char).

Then you're doing it wrong[TM].  You shouldn't need to keep any part of
the input in memory.  Whatever it is, nobody can tell you without seeing
the code.  Try heap profiling, should you have no idea where to look for
leaks.


> How could I solve the problem without representing the graph in some way?

By using an advanced tool called "brains".  Sorry for not being more
specific, but that's actually the fun part of the challenge and I'm not
going to spoil it for you.  ;-)


> Forgive the stupid question, but where if not RAM would the chunk currently 
> processed reside?

Oh, I overlooked "chunk".  Well, yes, the "chunk" currently processed
needs to fit into RAM.  But how much of a problem could a single Char
pose?


Donald Bruce Stewart wrote:
> I agree. Some problems simply require you to hold large strings in
> memory. And for those, [Char] conks out around 5-10M (try reversing a
> 10M [Char]).

Sure, this one just isn't of that kind.


Udo.
-- 
"Irrationality is the square root of all evil"
-- Douglas Hofstadter


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


Re: [Haskell-cafe] foreach

2006-09-13 Thread Udo Stenzel
Lemmih wrote:
>  main = do
>args <- getArgs
>flip mapM_ args $ \arg ->
>  flip mapM_ [1..3] $ \n ->
>putStrLn $ show n ++ ") " ++ arg

Or even:

main = do
args <- getArgs
putStr $ unlines [ show n ++ ") " ++ arg
 | arg <- args, n <- [1..3] ]

I'm really at a loss trying to understand why some people seem to like
the imperative style.  In fact, most  of the time, the strings in the
code above are better replaced by Doc from Text.PrettyPrint.


Udo.
-- 
Worrying is like rocking in a rocking chair -- It gives
you something to do, but it doesn't get you anywhere.


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


Re: [Haskell-cafe] Slow IO

2006-09-13 Thread Udo Stenzel
Ketil Malde wrote:
> Daniel Fischer <[EMAIL PROTECTED]> writes:
> 
> > Maybe I've misused the word segfault.
> 
> I think so.  A segfault is the operating-system complaining about an
> illegal memory access.  If you get them from Haskell, it is likely a
> bug in the compiler or run-time system (or you were using unsafeAt, or
> FFI). 

Far simpler:  This is really a segfault, and it's because of a
misfeature of Linux called "memory overcommitment".  When physical
memory runs out, Linux happily hands out more to applications requesting
it, in the vain hope that at least some of it is never accessed.
Therefore, malloc() is always successful, but when the memory is finally
accessed, it suddenly turns out that there isn't anything to access,
which results in a segfault.  No amount of error checking can prevent
that and it could have hit any process allocating memory when it ran
out.

Sane people turn overcommitment off.  Sane people wouldn't have
implemented it in the first place, either.


Udo.
-- 
The reasonable man adapts himself to the world; the unreasonable one
persists in trying to adapt the world to himself. Therefore all progress
depends on the unreasonable man. 
-- George Bernard Shaw


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


Re: [Haskell-cafe] foreach

2006-09-13 Thread Henning Thielemann

On Wed, 13 Sep 2006, Donald Bruce Stewart wrote:

> lemmih:
> > On 9/13/06, Tim Newsham <[EMAIL PROTECTED]> wrote:
> > >I was rewriting some non-haskell code in haskell and came up with this
> > >construct:
> > >
> > >   foreach l f = mapM_ f l
> > >
> > >   main = do
> > >   args <- getArgs
> > >   foreach args (\arg -> do
> > >   foreach [1..3] (\n -> do
> > >   putStrLn ((show n) ++ ") " ++ arg)
> > >)
> > >)
> > >
> > >which is reminiscent of foreach in other languages.  Seems fairly
> > >useful and I was wondering how hard it would be to add some syntactic
> > >sugar to the "do" construct to make it a little prettier (ie.
> > >not require the parenthesis, binding and nested do, as:
> > >
> > >   main = do
> > >   args <- getArgs
> > >   foreach args arg
> > >   foreach [1..3] n
> > >   putStrLn ((show n) ++ ") " ++ arg)
> > >
> > >would this type of transformation be possible with template haskell
> > >or does this need stronger support from the parser to pull off?
> > 
> > How about:
> > 
> >  main = do
> >args <- getArgs
> >flip mapM_ args $ \arg ->
> >  flip mapM_ [1..3] $ \n ->
> >putStrLn $ show n ++ ") " ++ arg
> > 
> 
> Which is, with current Control.Monad:
> 
>main = do
>  args <- getArgs
>  forM_ args $ \arg ->
>forM_ [1..3] $ \n ->
>  putStrLn $ show n ++ ") " ++ arg
> 
> I think Tim is looking for an if-then-else "real syntax" feel to his
> `foreach' though. I.e. TH or some small preprocessor.

Adding sugar or using Template Haskell for such a simple task is a bit
unreasonable. I think Tim should use mapM a little bit and then he will
probably need no longer a special syntax.


If you want more sugar, what about the list monad?

main = do
 args <- getArgs
 sequence_ $
   do arg <- args
  n <- [1..3]
  return (putStrLn $ show n ++ ") " ++ arg)

or

main = do
 args <- getArgs
 sequence_ $
   liftM2 (\arg n -> putStrLn $ show n ++ ") " ++ arg)
  args [1..3]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Numeric type classes

2006-09-13 Thread Henning Thielemann

On Tue, 12 Sep 2006, Aaron Denney wrote:

> On 2006-09-12, Bryan Burgers <[EMAIL PROTECTED]> wrote:
> > And another problem I can see is that, for example, the Integers are a
> > group over addition, and also a group over multiplication;
> 
> Not over multiplication, no, because there is no inverse.
> 
> I know of no good way to express that a given data type obeys the
> same interface two (or more) ways.  Some OO languages try to handle the
> case of of an abstract base class being inherited twice through two
> different intermediate classes, but none of them do it well.

Some examples are:
  Cardinals are a lattice with respect to (min,max) and (gcd,lcm)
  Sequences are rings if the multiplication is defined as
1) element-wise multiplication
2) convolution

We could certainly go a similar way and define newtypes in order to
provide different sets of operations for the same data structure.

 One issue is, that we have some traditional arithmetical signs and want
to use them in the traditional way. But there is no simple correspondence
between signs and laws. Both "+" and "*" fulfill monoid or group laws
depending on the type. If we had a sign for "group operation", say "." we
had to write "'.' of the additive group of rationals" instead of "+" and
"'.' of the multiplicative group of rationals" instead of "*". I don't
know how to handle this in a programming language.
 We also know that floating point numbers violate most basic laws. But
also wrappers to other languages violate basic laws. E.g. if the Haskell
expression (a+b) is mapped to an expression of a foreign language, say
(add a b), then (b+a) will be mapped to (add b a). That is, this instance
of Haskell's (+) is not commutative.
 The mathematical concept of calling a tuple of a set of objects and some
operations a group, a ring or whatever is not exactly mapped to Haskell's
type classes. It is even used laxly in mathematics. One often says "the
set of integers is a ring".
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] Slow IO

2006-09-13 Thread Bulat Ziganshin
Hello Ketil,

Wednesday, September 13, 2006, 10:41:13 AM, you wrote:

> But a String is something like 8 or 12 bytes per character, a
> ByteString gets you down to 1.

12-16. Char itself, pointer to the next list element, and two boxes
around them - this count for 16 bytes on 32-bit CPU. but cells with
small Char are preallocated at program startup, so it will be 12 bytes
for ascii-only strings

but that is not the whole story :)  copying GC makes program's memory
usage 3 times larger, on average, than it really allocates while
compacting GC has only 2x overhead

ByteStrings are allocated in _unmovable_ part of GHC heap, so they
don't suffer from this problem. of course, it is not free -
program that creates and destroys large number of ByteStrings will
suffer from memory holes, which is right the problem solved by ghc's GC

so, for program that only allocates the difference may be 24/36 times
on average while for create-use-destroy-loop scenarios i can't make
any detailed prognoses

also, traversing those lengthy lists on GCs is very time-consuming



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re[2]: [Haskell-cafe] foreach

2006-09-13 Thread Bulat Ziganshin
Hello Henning,

Wednesday, September 13, 2006, 1:12:35 PM, you wrote:

> Adding sugar or using Template Haskell for such a simple task is a bit
> unreasonable. I think Tim should use mapM a little bit and then he will
> probably need no longer a special syntax.

i disagree. lack of good syntax makes imperative programming in
Haskell less convenient. i want to have such syntax in order to make
Haskell great imperative language:

sum <- new 0
arr <- new Array[1..3]
for i in [1..3] do
  sum += i
  arr[i] := sum
for i in [1..3] while arr[i]<2 do
  print arr[i]

it will be even better to have ability to define such syntax
constructs in user program


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re[2]: [Haskell-cafe] foreach

2006-09-13 Thread Bulat Ziganshin
Hello Udo,

Wednesday, September 13, 2006, 12:53:38 PM, you wrote:

>>  main = do
>>args <- getArgs
>>flip mapM_ args $ \arg ->
>>  flip mapM_ [1..3] $ \n ->
>>putStrLn $ show n ++ ") " ++ arg

> Or even:

> main = do
> args <- getArgs
> putStr $ unlines [ show n ++ ") " ++ arg
>  | arg <- args, n <- [1..3] ]

> I'm really at a loss trying to understand why some people seem to like
> the imperative style.  In fact, most  of the time, the strings in the
> code above are better replaced by Doc from Text.PrettyPrint.

because REAL code is somewhat larger than examples. try to rewrite the
following:

  directory_blocks  <-  (`mapM` splitBy (opt_group_dir command) 
files_to_archive)
( \filesInOneDirectory -> do
  datablocks  <-  (`mapM` splitToSolidBlocks filesInOneDirectory)
( \filesInOneDataBlock -> do 
  let compressor = map (freearcLimitDictionary$ clipToMaxInt totalBytes)
   (data_compressor filesInOneDataBlock)
  totalBytes = sum$ map (fiSize.cfFileInfo) filesInOneDataBlock
  copy_solid_block = isWholeSolidBlock filesInOneDataBlock
  writeBlock pipe DATA_BLOCK compressor copy_solid_block $ do
dir <- if copy_solid_block then do
 sendP pipe (CopySolidBlock filesInOneDataBlock)
 return$ map fileWithCRC filesInOneDataBlock   
   else if (compressor==[aFAKE_COMPRESSION]) then do
 sendP pipe (FakeFiles filesInOneDataBlock)
 return$ map (FileWithCRC 0 . cfFileInfo) 
filesInOneDataBlock
   else do
 mapMaybeM (read_file command bufOps decompress_pipe) 
filesInOneDataBlock
processDir dir   
return dir
)
  blocks_info  <-  replicateM (length datablocks) (getP backdoor)
  arcpos <- archiveGetPos archive
  
  writeControlBlock DIR_BLOCK dir_compressor $ do
archiveWriteDir blocks_info arcpos receiveBuf sendBuf
)




-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


[Haskell-cafe] Re: foreach

2006-09-13 Thread Henning Thielemann

On Wed, 13 Sep 2006, Bulat Ziganshin wrote:

> Wednesday, September 13, 2006, 1:12:35 PM, you wrote:
> 
> > Adding sugar or using Template Haskell for such a simple task is a bit
> > unreasonable. I think Tim should use mapM a little bit and then he will
> > probably need no longer a special syntax.
> 
> i disagree. lack of good syntax makes imperative programming in
> Haskell less convenient. i want to have such syntax in order to make
> Haskell great imperative language:
> 
> sum <- new 0
> arr <- new Array[1..3]
> for i in [1..3] do
>   sum += i
>   arr[i] := sum
> for i in [1..3] while arr[i]<2 do
>   print arr[i]

let arr = scanl1 (+) [1..3]
in  mapM_ print (takeWhile (<2) arr)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Numeric type classes

2006-09-13 Thread Lennart Augustsson

The sum function really only needs the argument list to be a monoid.
And the same is true for the product function, but with 1 and * as  
the monoid operators.  Sum and product are really the same function. :)


I don't think Haskell really has the mechanisms for setting up an  
algebraic class hierarchy the right way.  Consider some classes we  
might want to build:

SemiGroup
Monoid
AbelianMonoid
Group
AbelianGroup
SemiRing
Ring
...

The problem is that going from, say, AbelianMonoid to SemiRing you  
want to add a new Monoid (the multiplicative) to the class.  So  
SemiRing is a subclass of Monoid in two different way, both for + and  
for *.

I don't know of any nice way to express this is Haskell.

-- Lennart

On Sep 13, 2006, at 03:26 , [EMAIL PROTECTED] wrote:


G'day all.

Quoting Jason Dagit <[EMAIL PROTECTED]>:


I was making an embedded domain specific language for excel
spreadsheet formulas recently and found that making my formula
datatype an instance of Num had huge pay offs.


Just so you know, what we're talking about here is a way to make that
even _more_ useful by dicing up Num.


I can even use things like Prelude.sum to
add up cells.


Ah, but the sum function only needs 0 and (+), so it doesn't need
the full power of Num.  It'd be even _more_ useful if it worked on
all data types which supported 0 and (+), but not necessarily (*):

sum :: (AdditiveAbelianMonoid a) => [a] -> a

product :: (MultiplicativeAbelianMonoid a) => [a] -> a

Those are bad typeclass names, but you get the idea.

Right now, to reuse sum, people have to come up with fake
implementations for Num operations that simply don't make sense on
their data type, like signum on Complex numbers.


 All I really needed was to define Show and Num
correctly,  neither of which took much mental effort or coding  
tricks.


You also needed to derive Eq, which gives you, in your case,  
structural
equality rather than semantic equality (which is probably  
undecidable for

your DSL).

Cheers,
Andrew Bromage
___
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: Numeric type classes

2006-09-13 Thread Henning Thielemann

On Wed, 13 Sep 2006, Lennart Augustsson wrote:

> The sum function really only needs the argument list to be a monoid.
> And the same is true for the product function, but with 1 and * as the monoid
> operators.  Sum and product are really the same function. :)

... which got the same name, too, namely 'foldl'. 'sum' and 'product'
derive the operation and the neutral element from the operand types,
'foldl' expect them explicitly.

> I don't think Haskell really has the mechanisms for setting up an algebraic
> class hierarchy the right way.  Consider some classes we might want to build:
> SemiGroup
> Monoid
> AbelianMonoid
> Group
> AbelianGroup
> SemiRing
> Ring
> ...
> 
> The problem is that going from, say, AbelianMonoid to SemiRing you want to add
> a new Monoid (the multiplicative) to the class.  So SemiRing is a subclass of
> Monoid in two different way, both for + and for *.
> I don't know of any nice way to express this is Haskell.

Thanks for confirming what I wrote. :-)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Numeric type classes

2006-09-13 Thread ajb
G'day all.

Quoting Henning Thielemann <[EMAIL PROTECTED]>:

> ... which got the same name, too, namely 'foldl'.

You mean foldr.  The place of foldl is a bit tricky, but in this case
it requires that the monoid be Abelian.

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


[Haskell-cafe] Re: Numeric type classes

2006-09-13 Thread Henning Thielemann

On Wed, 13 Sep 2006 [EMAIL PROTECTED] wrote:

> G'day all.
> 
> Quoting Henning Thielemann <[EMAIL PROTECTED]>:
> 
> > ... which got the same name, too, namely 'foldl'.
> 
> You mean foldr.  The place of foldl is a bit tricky, but in this case
> it requires that the monoid be Abelian.

A monoid operation is associative, isn't it?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why does this program eat RAM?

2006-09-13 Thread Jan-Willem Maessen


On Sep 5, 2006, at 7:05 AM, Chris Kuklewicz wrote:


Bulat Ziganshin wrote:

Hello Bertram,
Tuesday, September 5, 2006, 12:24:57 PM, you wrote:

A quick hack up to use Data.ByteString uses a lot less ram, though
profiling still shows 95% of time spent in the building the Map.

Data.HashTable may be a faster alternative for Map (if ordering isn't
required)


I found Data.HashTable a bit slow (ghc 6.4).  Perhaps HsJudy (see  
http://cmarcelo.blogspot.com/ and http://judy.sourceforge.net/ and  
http://www.mail-archive.com/haskell@haskell.org/msg18766.html )


I'd urge programmers to give the version of Data.HashTable in 6.6 a  
try.  It uses a simple multiplicative hash function (a la Knuth)  
which seems to be dramatically better in practice.  It also uses a  
rather simpler hash table implementation which seems to perform  
slightly better in practice (if this isn't true for your application  
I'm keen to know).


As Udo Stenzel points out, we still need to examine the entire string  
in order to hash, and some problems may do better with something like  
a StringMap---I understand many information retrieval applications  
use Trie-like data structures for exactly this reason.


-Jan-Willem Maessen


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




smime.p7s
Description: S/MIME cryptographic signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Slow IO

2006-09-13 Thread Daniel Fischer
Am Mittwoch, 13. September 2006 11:07 schrieben Sie:
> Daniel Fischer wrote:
> > > Most certainly not.  I'm pretty sure this is to a bug in your code.
> > > Something retains a data structure which is actually unneeded. 
> > > Probably
> >
> > Apparently. And my money is on a load of lines from the file (of which I
> > need only the first and last Char).
>
> Then you're doing it wrong[TM].  You shouldn't need to keep any part of

Yes, I did it wrong, but I didn't keep anything (but the first and last Char 
of each line) in memory on purpose. I hoped for the lines to be read one 
after the other, head and last extracted - possibly immediately passed to 
accumArray, but I wouldn't necessarily expect that - and the already used 
lines thrown in the dustbin on next GC. Maybe the compiler couldn't figure 
out that it wouldn't access these lines anymore.

> the input in memory.  Whatever it is, nobody can tell you without seeing
> the code.  Try heap profiling, should you have no idea where to look for
> leaks.

Profiling (hy,hc) shows that the IO part of the programme holds on to tons of 
lists - that couldn't be anything but parts of the file-contents, I believe.
>
> > How could I solve the problem without representing the graph in some way?
>
> By using an advanced tool called "brains".  Sorry for not being more
> specific, but that's actually the fun part of the challenge and I'm not
> going to spoil it for you.  ;-)
>
> > Forgive the stupid question, but where if not RAM would the chunk
> > currently processed reside?
>
> Oh, I overlooked "chunk".  Well, yes, the "chunk" currently processed
> needs to fit into RAM.  But how much of a problem could a single Char
> pose?

Well, if it's the last straw...
But not much, I presume and even though it might be that we must have a few 
thousand Chars inmemory, that shouldn't do much harm either.

>
> Donald Bruce Stewart wrote:
> > I agree. Some problems simply require you to hold large strings in
> > memory. And for those, [Char] conks out around 5-10M (try reversing a
> > 10M [Char]).
>
> Sure, this one just isn't of that kind.

Yes, but I didn't tell the compiler :-(

>
>
> Udo.

Cheers,
Daniel

-- 

"In My Egotistical Opinion, most people's C programs should be
indented six feet downward and covered with dirt."
-- Blair P. Houghton

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


[Haskell-cafe] [OT] A DSL for state machines

2006-09-13 Thread Stephane Bortzmeyer
Sorry, this is a bit off-topic but I post here because:

* it is about a DSL and many Haskellers are fond of DSLs,

* the first implementation is written in Haskell.

http://www.cosmogol.fr/

describes a proposal to the IETF to standardize the language used for
finite state machines (which are common in IETF standards), much like
ABNF is standardized in RFC 4234, to describe grammars.

The reference implementation, available at
http://www.cosmogol.fr/shadok.html is in Haskell.

Bug reports, patches, advices, flames, opinions and criticisms are
welcome.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: Re: [Haskell-cafe] Serialising types with existential data constructors

2006-09-13 Thread Misha Aizatulin
Einar Karttunen wrote:
> >   I've been using existentially quantified data constructors like
> > 
> > > data Box = forall a. Cxt a => Box a
> 
> If you can include Typeable into the mix then serializing works.
> 
> Serialize the value as " ".
> 
> When deserializing use a Map  
> and get the appropriate decoder from there for the type in question.

  This is indeed the only solution I see so far. It has a serious
problem though: as soon as I write the mapping, I limit once and for all
the set of all types that can be used with my box. And I do so in a
non-extensible way - if someone later would like to use my box with some
other type in it, they wouldn't be able to.

  In fact, I start wondering, how OO languages solve the same problem.
I'll take a look at Java now.

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


RE: Re: [Haskell-cafe] Serialising types with existential data constructors

2006-09-13 Thread Ralf Lammel
> I start wondering, how OO languages solve the same problem.

Conceptually, what is needed is a mapping of the "head" of the input to a type. 
This is indeed a recurring problem in OO languages; think of object 
serialization or XML/Object mapping. One common way of accomplishing the 
mapping is to associate custom attributes (aka annotations) with classes that 
exactly define "when you see this element tag, instantiate this class". It is 
then the task of a compile-time or run-time reflection to gather these 
attributes and generate code from it -- code that actually constructs instances 
according to the mapping and the input.

Klaus Ostermann and I allude to this non-trivial extensibility problem in our 
GPCE 2006 paper and we started to look into ways (not in that paper) to resolve 
the problem in a principled way.

Best,
Ralf


> -Original Message-
> From: [EMAIL PROTECTED] [mailto:haskell-cafe-
> [EMAIL PROTECTED] On Behalf Of Misha Aizatulin
> Sent: Wednesday, September 13, 2006 8:13 AM
> To: haskell-cafe@haskell.org
> Subject: RE: Re: [Haskell-cafe] Serialising types with existential data
> constructors
>
> Einar Karttunen wrote:
> > >   I've been using existentially quantified data constructors like
> > >
> > > > data Box = forall a. Cxt a => Box a
> >
> > If you can include Typeable into the mix then serializing works.
> >
> > Serialize the value as " ".
> >
> > When deserializing use a Map  
> > and get the appropriate decoder from there for the type in question.
>
>   This is indeed the only solution I see so far. It has a serious
> problem though: as soon as I write the mapping, I limit once and for all
> the set of all types that can be used with my box. And I do so in a
> non-extensible way - if someone later would like to use my box with some
> other type in it, they wouldn't be able to.
>
>   In fact, I start wondering, how OO languages solve the same problem.
> I'll take a look at Java now.
>
> Cheers,
>Misha
> ___
> 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] foreach

2006-09-13 Thread Brandon Moore

Tim Newsham wrote:
I was rewriting some non-haskell code in haskell and came up with this 
construct:


foreach l f = mapM_ f l

main = do
args <- getArgs
foreach args (\arg -> do
foreach [1..3] (\n -> do
putStrLn ((show n) ++ ") " ++ arg)
)
)

which is reminiscent of foreach in other languages. Seems fairly
useful and I was wondering how hard it would be to add some syntactic
sugar to the "do" construct to make it a little prettier (ie.
not require the parenthesis, binding and nested do, as:

main = do
args <- getArgs
foreach args arg
foreach [1..3] n
putStrLn ((show n) ++ ") " ++ arg)

would this type of transformation be possible with template haskell
or does this need stronger support from the parser to pull off?
I'm pretty sure you need parser support to pull off something like this, 
if by "pull off" you mean providing this syntax with less lexical 
overhead than the pure Haskell code. You'll have $( ) from a macro 
invocation, and [| |] around the body, or putting the body in a string 
literal.

TH is handy for metaprogramming, but not very good for syntax extension.

As for syntax design, the original isn't so bad. The only thing truly 
useless are the parentheses or $. Some visual indication that args is 
being bound is nice, plus the \bindings notation scales nicely to 
constructs binding more names. "do" is arguable, at least it seems 
pretty popular to use something similar with loops in syntaxes heavier 
on keywords than symbols.


Couldn't '\' delimit a subexpression, as parentheses do? Would there be 
any ambiguity in accepting code like State \s -> (s, s) instead of 
requiring State $ \s -> (s, s), or taking


main = do
args <- getArgs
foreach args \arg -> do
foreach [1..3] \n -> do
putStrLn ((show n) ++ ") " ++ arg

It would be a bit odd to have a kind of grouping the always starts 
explicitly and ends implicitly, but other than that it seems pretty 
handy, harmless, and natural (I know I've tried to write this sort of 
thing often enough)


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


Re: [Haskell-cafe] Re: Numeric type classes

2006-09-13 Thread Brian Hulley

Henning Thielemann wrote:

On Wed, 13 Sep 2006, Lennart Augustsson wrote:

I don't think Haskell really has the mechanisms for setting up an
algebraic class hierarchy the right way.  Consider some classes we
might want to build: SemiGroup
Monoid
AbelianMonoid
Group
AbelianGroup
SemiRing
Ring
...

The problem is that going from, say, AbelianMonoid to SemiRing you
want to add a new Monoid (the multiplicative) to the class.  So
SemiRing is a subclass of Monoid in two different way, both for +
and for *.
I don't know of any nice way to express this is Haskell.


Thanks for confirming what I wrote. :-)


If the above is equivalent to saying "Monoid is a *superclass* of SemiRing 
in two different ways", then can someone explain why this approach would not 
work (posted earlier):


   data Multiply = Multiply
   data Add = Add

   class Group c e where
   group :: c -> e -> e -> e
   identity :: c -> e
   inverse :: c -> e -> e

   instance Group Multiply Rational where
   group Multiply x y = ...
   identity Multiply = 1
   inverse Multiply x = ...

   instance Group Add Rational where
   group Add x y = ...
   identity Add = 0
   inverse Add x = ...

   (+) :: Group Add a => a -> a -> a
   (+) = group Add

   (*) = group Multiply

   class (Group Multiply a, Group Add a) => Field a where ...

If the objection is just that you can't make something a subclass in two 
different ways, the above is surely a counterexample. Of course I made the 
above example more fixed than it should be ie:


   class (Group mult a, Group add a) => Field mult add a where ...

and only considered the relationship between groups and fields - obviously 
other classes would be needed before and in-between, but perhaps the problem 
is that even with extra parameters (to represent *all* the parameters in the 
corresponding tuples used in maths), there is no way to get a hierarchy?


Thanks, Brian.
--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com 


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


[Haskell-cafe] ffi question

2006-09-13 Thread Maverick
Hi, I have a question about ffi in Hugs98 (WinHugs-May2006.exe), the Hugs98 documentation says:"Only the ccall, stdcall and dotnet calling conventions are supported. All others are   flagged as errors."But I can't get a dotnet import, the ffihugs returns me an error:ffihugs "example.hs" "Prueba.cs" -lm  runhugs: Error occurred  ERROR "example.hs":6 - Foreign import calling convention "dotnet" not supportedWhy is this? hugs really don't support the "dotnet" calling convention or I have an error?.Thanks.Alvaro S.   
		LLama Gratis a cualquier PC del Mundo.Llamadas a fijos y móviles desde 1 céntimo por minuto.http://es.voice.yahoo.com___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Numeric type classes

2006-09-13 Thread Jacques Carette
Your solution would imply[1] that all Rational are multiplicatively 
invertible -- which they are not.


The Rationals are not a multiplicative group -- although the _positive_ 
Rationals are.  You can't express this in Haskell's type system AFAIK.


Your basic point is correct: if you are willing to use a tag (like 
Multiply and Add), then you can indeed have a domain be seen as matching 
an interface in 2 different ways.  Obviously, this can be extended to n 
different ways with appropriate interfaces. 


Jacques

[1] imply in the sense of intensional semantics, since we all know that 
Haskell's type system is not powerful enough to enforce axioms.


PS: if you stick to 2 Monoidal structures, you'll be on safer grounds.

Brian Hulley wrote:
If the above is equivalent to saying "Monoid is a *superclass* of 
SemiRing in two different ways", then can someone explain why this 
approach would not work (posted earlier):


   data Multiply = Multiply
   data Add = Add

   class Group c e where
   group :: c -> e -> e -> e
   identity :: c -> e
   inverse :: c -> e -> e

   instance Group Multiply Rational where
   group Multiply x y = ...
   identity Multiply = 1
   inverse Multiply x = ...

   instance Group Add Rational where
   group Add x y = ...
   identity Add = 0
   inverse Add x = ...

   (+) :: Group Add a => a -> a -> a
   (+) = group Add

   (*) = group Multiply

   class (Group Multiply a, Group Add a) => Field a where ...

If the objection is just that you can't make something a subclass in 
two different ways, the above is surely a counterexample. Of course I 
made the above example more fixed than it should be ie:


   class (Group mult a, Group add a) => Field mult add a where ...

and only considered the relationship between groups and fields - 
obviously other classes would be needed before and in-between, but 
perhaps the problem is that even with extra parameters (to represent 
*all* the parameters in the corresponding tuples used in maths), there 
is no way to get a hierarchy?


Thanks, Brian.

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


Re: [Haskell-cafe] foreach

2006-09-13 Thread Tim Newsham

 foreach l f = mapM_ f l


... rename to forM_ as per previous emails ...

I would like to add to this.  The previous loop runs the code
once independantly for each item in the list.  Sometimes you want
to carry state through the loop:

v = init
foreach x list do
code
v = update v

(I know that this can be done with IORefs, but ignoring that for now)
for looping with a carried variable:

forXM_ init [] f = ()
forXM_ init (x:xs) f = do
i' <- f init x
forXM_ i' xs f

or with a returned value (the carried variable at the end of the loop):

forXM init [] f = init
forXM init (x:xs) f = do
i' <- f init x
forXM i' xs f

used as:

forXM_ 0 [1,2,3,4] (\x n ->
putStrLn $ unwords [show x, " -> ", show n]
return $ x + n
 )

looping a fixed number of times when the loop index is not needed:

loopM_ n f = forM_ [1..n] (\n -> f)

used as:

loopM_ 5 (
print "hello"
 )

with a carried variable (with and without a result):

loopXM_ i n f = forXM_ i [1..n] (\x n -> f x)
loopXM  i n f = forXM  i [1..n] (\x n -> f x)

(is this related to foldM_?) used as:

loopXM_ 1 5 (\x ->
print x
return (x * x + x)
 )

do..while loop with a carried variable:

untilXM_ i p f = do
i' <- f i
when (p i') (untilXM_ f i')
untilXM i p f = do
i' <- f i
if (p i') then (untilXM_ f i') else (return i')

used as:

untilXM_ 1 (< 100) (\x ->
print x
return (x * x + x)
 )

Some of these also make sense in pure-functional code (obviously not the 
ones with no return values).  For example the following iteration with a 
loop-carried variable:


s = 0
foreach n [1,2,3,4]
s += n
return s

is "foldl (+) 0 [1,2,3,4]" and we can mimic the syntax by reordering
the arguments:

forX i l f = foldl f i l

forX 0 [1,2,3,4] (\x n ->
x + n
 )

Obviously many of these examples can be rewritten easily without using
these constructs, but as was pointed out earlier in the thread, larger,
more complicated programs are more difficult to juggle around.  These
constructs are fairly easy to understand, at least for people coming
from an imperative background...

I recently rewrote a small (a few hundred lines of code) imperative
program in haskell using these constructs without changing the structure
of the code very much.  Maybe I'm missing the point somewhat (I'm still
learning haskell) by trying to mimick imperative constructs in haskell,
but the translation was much simpler (and mechanical) this way...

Tim Newsham
http://www.thenewsh.com/~newsham/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Numeric type classes

2006-09-13 Thread Aaron Denney
On 2006-09-13, Ross Paterson <[EMAIL PROTECTED]> wrote:
> On Tue, Sep 12, 2006 at 08:59:30PM -0400, [EMAIL PROTECTED] wrote:
>> One of the proposals that comes up every so often is to allow the
>> declaration of a typeclass instance to automatically declare instances
>> for all superclasses.  So, for example:
>> 
>> class (Functor m) => Monad m where
>> fmap f m = m >>= return . f
>> 
>> instance Monad Foo where
>> return a = {- ... -}
>> m >>= k = {- ... -}
>> fail s = {- ... -}
>> 
>> This will automatically declare an instance of Functor Foo.
>> 
>> Similarly, a finer-grained collection of numeric typeclasses could
>> simply make Num a synonym for (Show a, Ord a, Ring a, Signum a).
>> Declaring an instance for (Num Bar) declares all of the other
>> instances that don't yet have a declaration.
>
> Such features would be useful, but are unlikely to be available for
> Haskell'.  If we concede that, is it still desirable to make these
> changes to the class hierarchy?

Absolutely.  It needs to be fixed, and much better now than later.

-- 
Aaron Denney
-><-

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


Re: [Haskell-cafe] Re: evaluate vs seq

2006-09-13 Thread Michael Shulman

On 9/13/06, [EMAIL PROTECTED] <[EMAIL PROTECTED]> wrote:

So `seq` forces its first argument. When we define
  f x = x `seq` (Return x)
we thereby get
  f _|_== _|_
  f [] == Return []
  f (x:xs) == Return (x:xs)
To compare, the semantics of (evaluate) is
  evaluate _|_== ThrowException =/= _|_
  evaluate [] == Return []
  evaluate (x:xs) == Return (x:xs)
That should answer your question.


I must not be phrasing my question very well; I feel like we're
talking past each other.  It seems to me that when writing actual
programs (rather than reasoning about denotational semantics) the
reason one would use `seq' or `evaluate' is to force something to be
evaluated "now" rather than "later", i.e. to get around Haskell's
default lazy execution.

Your semantics say that (x `seq` return x) and (evaluate x) have the
same result when x is anything other than _|_.  All well and good, but
(return x) *also* has those same results when x is not _|_.  Why would
one use the former two rather than (return x), if x is known not to be
_|_?  Because they evaluate x at different "times", right?  Even though
the eventual return value is the same, and thus the *semantics* are the
same.  So laying aside the formal semantics, what is the difference in
terms of actual, real, Haskell programs?

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


[Haskell-cafe] Re: Serialising types with existential data constructors

2006-09-13 Thread Ashley Yakeley

Misha Aizatulin wrote:

  This is indeed the only solution I see so far. It has a serious
problem though: as soon as I write the mapping, I limit once and for all
the set of all types that can be used with my box. And I do so in a
non-extensible way - if someone later would like to use my box with some
other type in it, they wouldn't be able to.


This doesn't really help you now, but extending Haskell with open types 
and functions would solve this...

http://www.informatik.uni-bonn.de/~loeh/OpenDatatypes.pdf
http://haskell.org/haskellwiki/Extensible_datatypes

--
Ashley Yakeley

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


Re: [Haskell-cafe] foreach

2006-09-13 Thread Michael Shulman

On 9/13/06, Henning Thielemann <[EMAIL PROTECTED]> wrote:

If you want more sugar, what about the list monad?

main = do
 args <- getArgs
 sequence_ $
   do arg <- args
  n <- [1..3]
  return (putStrLn $ show n ++ ") " ++ arg)


Or, what about using ListT to combine it with IO, eliminating the need for
two separate `do' blocks?

main = (>> return ()) $ runListT $ do
arg <- ListT getArgs
n <- ListT $ return [1..3]
liftIO $ putStrLn ((show n) ++ ") " ++ arg)

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


[Haskell-cafe] MonadList?

2006-09-13 Thread Michael Shulman

In another thread, I wrote:

main = (>> return ()) $ runListT $ do
arg <- ListT getArgs
n <- ListT $ return [1..3]
liftIO $ putStrLn ((show n) ++ ") " ++ arg)


The frequent occurence of "ListT $ return" in my code when I use the ListT
monad transformer has made me wonder why there isn't a standard typeclass
`MonadList', like those for the other monad transformers, encapsulating
the essence of being a "list-like" monad -- in this case, the ability to
select from a list of things.  I quickly wrote one for myself:

class MonadList m where
   option :: [a] -> m a

instance MonadList [] where
   option = id

instance (Monad m) => MonadList (ListT m) where
   option = ListT . return

Has anyone else thought about or done something like this?

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


Re: Re[2]: [Haskell-cafe] foreach

2006-09-13 Thread Jeremy Shaw
At Wed, 13 Sep 2006 15:24:39 +0400,
Bulat Ziganshin wrote:

> because REAL code is somewhat larger than examples. try to rewrite the
> following:
> 
>   directory_blocks  <-  (`mapM` splitBy (opt_group_dir command) 
> files_to_archive)
> ( \filesInOneDirectory -> do
>   datablocks  <-  (`mapM` splitToSolidBlocks filesInOneDirectory)
> ( \filesInOneDataBlock -> do 
>   let compressor = map (freearcLimitDictionary$ clipToMaxInt 
> totalBytes)
>(data_compressor filesInOneDataBlock)
>   totalBytes = sum$ map (fiSize.cfFileInfo) filesInOneDataBlock
>   copy_solid_block = isWholeSolidBlock filesInOneDataBlock
>   writeBlock pipe DATA_BLOCK compressor copy_solid_block $ do
> dir <- if copy_solid_block then do
>  sendP pipe (CopySolidBlock filesInOneDataBlock)
>  return$ map fileWithCRC filesInOneDataBlock   
>else if (compressor==[aFAKE_COMPRESSION]) then do
>  sendP pipe (FakeFiles filesInOneDataBlock)
>  return$ map (FileWithCRC 0 . cfFileInfo) 
> filesInOneDataBlock
>else do
>  mapMaybeM (read_file command bufOps decompress_pipe) 
> filesInOneDataBlock
> processDir dir   
> return dir
> )
>   blocks_info  <-  replicateM (length datablocks) (getP backdoor)
>   arcpos <- archiveGetPos archive
>   
>   writeControlBlock DIR_BLOCK dir_compressor $ do
> archiveWriteDir blocks_info arcpos receiveBuf sendBuf
> )

One transformation might be to get rid of the, if..then..else if..
like this:

 do dir <- case () of
   _ | copy_solid_block -> 
do sendP pipe (CopySolidBlock 
filesInOneDataBlock)
   return$ map fileWithCRC filesInOneDataBlock  
 
| (compressor==[aFAKE_COMPRESSION]) ->
do sendP pipe (FakeFiles filesInOneDataBlock)
   return$ map (FileWithCRC 0 . cfFileInfo) 
filesInOneDataBlock
| otherwise ->
mapMaybeM (read_file command bufOps 
decompress_pipe) filesInOneDataBlock

Not sure if that is actually better or not :)

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


Re: [Haskell-cafe] MonadList?

2006-09-13 Thread Bertram Felgenhauer
Michael Shulman wrote:
> 
> class MonadList m where
>option :: [a] -> m a
[...]

There's no need for an extra class, it can be done with MonadPlus:

option :: MonadPlus m => [a] -> m a
option = msum . map return

This definition came up before, for example here:
   http://www.haskell.org/haskellwiki/Sudoku

enjoy,

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


Re: [Haskell-cafe] MonadList?

2006-09-13 Thread Michael Shulman

On 9/13/06, Bertram Felgenhauer <[EMAIL PROTECTED]> wrote:

Michael Shulman wrote:
>
> class MonadList m where
>option :: [a] -> m a
[...]

There's no need for an extra class, it can be done with MonadPlus:

option :: MonadPlus m => [a] -> m a
option = msum . map return


But this doesn't always give the behavior I want.  It works for any
monad of the form (ListT m), but not for a monad like (ErrorT e []).
I would want

runErrorT $ do
 x <- option [1..3]
 return x

to return [Right 1, Right 2, Right 3], but with your definition it
returns [Right 1].  This is because (ErrorT e []) inherits its
instance of MonadPlus from Error, not from [].  (Is there a reason for
this, or is it just assumed that this is the more frequently desired
behavior?)  However, I declare

instance (Error e) => MonadList (ErrorT e []) where
   option = lift

then the above code does return [Right 1, Right 2, Right 3].

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


[Haskell-cafe] Re: Numeric type classes

2006-09-13 Thread Ashley Yakeley

Aaron Denney wrote:


I know of no good way to express that a given data type obeys the
same interface two (or more) ways.


The best approach here is to use data structures instead of classes:

data Monoid a = MkMonoid
{
  monoidNull :: a,
  monoidFunc :: a -> a -> a
}

--
Ashley Yakeley

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


Re: [Haskell-cafe] MonadList?

2006-09-13 Thread Twan van Laarhoven

Michael Shulman wrote:

The frequent occurence of "ListT $ return" in my code when I use the ListT
monad transformer has made me wonder why there isn't a standard typeclass
`MonadList', like those for the other monad transformers, encapsulating
the essence of being a "list-like" monad -- in this case, the ability to
select from a list of things.  I quickly wrote one for myself:

class MonadList m where
   option :: [a] -> m a


Another use for this class is for selecting a random option:

> instance MonadList SomeMonadWithRandomness where
>option os = pos <- randomRM (0, length os - 1)
>return (os !! pos)

It can also be used for the Nondet monad described in 
http://haskell.org/hawiki/NonDeterminism, and as a replacement for the 
Parsec combinator 'choice' (which IMHO is a better name). Although msum 
might suffice in these cases.


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


Re: [Haskell-cafe] Weak pointers and referential transparency???

2006-09-13 Thread tpledger
Brian Hulley wrote:
> [EMAIL PROTECTED] wrote:
[...]
> > My reading of the semantics
> >
(http://haskell.org/ghc/docs/latest/html/libraries/base/System-Mem-Weak.html#4)
> > is that you can be sure the proxy *object* is gone.
>
> My problem is that I don't know what to make of the word
> "object" in the  context of Haskell ie when can I be sure
> that a value is actually being  represented as a pointer
> to a block of memory and not stored in registers or
> optimized out? Or is the compiler clever enough to
> preserve the concept of  "object" despite such
> optimizations? I had been designing my Model/Proxy  data
> types with the Java notion of "everything is a pointer to
> an object"  but is this always correct relative to Haskell
> as a language or is it just a  consequence of the current
> GHC implementation?

In the context of System.Mem.Weak, but not necessarily GHC,
we're concerned solely with garbage collection of heap
objects.  So yes, that's Java-like.  AFAIK.

An example of something outside that context is a GHC Int#
(unboxed Int).  It never inhabits the heap, and isn't
allowed to be passed to a function where a polymorphic
parameter is expected (such as mkWeak).

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


[Haskell-cafe] Optimization problem

2006-09-13 Thread Magnus Jonsson

Dear Haskell Cafe,

When programming the other day I ran into this problem. What I want to do 
is a function that would work like this:


splitStreams::Ord a=>[(a,b)]->[(a,[b])]


splitStreams [(3,x),(1,y),(3,z),(2,w)]

[(3,[x,z]),(1,[y]),(2,[w])]

I don't care about the order that the pairs are output, so the answer 
could just as well be [(2,[w],(3,[x,z]),(1,[y])]. However I do care about 
the order of the xyzw:s, so (3,[z,x]) could not be part of the solution in 
this example.


Furthermore it should work on infinite lists. It can't eat the whole 
list before producing any output.


Now, it's not too hard to come up with an inefficient solution that 
traverses the input list multiple times. For example a sieving solution:


import Data.List

splitStreams [] = []
splitStreams ((channel,msg):rest) =
let (myMsgs,otherMsgs) =
  partition (\(c,_)->c==channel) rest
in (channel, msg : map snd myMsgs) : splitStreams otherMsgs

I'm afraid this algorithm is O(n*m) time in the worst case, where n is the 
length of the input list, and m is the number of unique channels.


But is there any way to write it such that each element is touched only 
once? Or at least an O(n*log(m)) algorithm?


Any takers?

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


Re: [Haskell-cafe] Optimization problem

2006-09-13 Thread Twan van Laarhoven

Magnus Jonsson wrote:

Dear Haskell Cafe,

When programming the other day I ran into this problem. What I want to 
do is a function that would work like this:


splitStreams::Ord a=>[(a,b)]->[(a,[b])]


splitStreams [(3,x),(1,y),(3,z),(2,w)]


[(3,[x,z]),(1,[y]),(2,[w])]


A O(n log(n)) algorithm is easy if you use Data.Map:

> import qualified Data.Map as Map
>
> splitStreamsMap :: Ord a => [(a,b)] -> Map.Map a [b]
> splitStreamsMap = foldl add Map.empty
>  where add (a,b) m = Map.insertWith (++) a [b]
>
> splitStreams = Map.fromList . splitStreamsMap

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


Re: [Haskell-cafe] Optimization problem

2006-09-13 Thread Magnus Jonsson
Nice try Twan but your example fails on infinite lists. I cleaned up 
your example so that it compiles:


import qualified Data.Map as Map

splitStreamsMap :: Ord a => [(a,b)] -> Map.Map a [b]
splitStreamsMap = foldl add Map.empty
  where add m (a,b) = Map.insertWith (++) a [b] m

splitStreams :: Ord a => [(a,b)] -> [(a,[b])]
splitStreams = Map.toList . splitStreamsMap

It fails to return a value on this test:

take 2 $ snd $ head $ splitStreams (map (\x -> (0 ,x)) [1..])

/ Magnus

On Thu, 14 Sep 2006, Twan van Laarhoven wrote:


Magnus Jonsson wrote:

Dear Haskell Cafe,

When programming the other day I ran into this problem. What I want to do 
is a function that would work like this:


splitStreams::Ord a=>[(a,b)]->[(a,[b])]


splitStreams [(3,x),(1,y),(3,z),(2,w)]


[(3,[x,z]),(1,[y]),(2,[w])]


A O(n log(n)) algorithm is easy if you use Data.Map:


import qualified Data.Map as Map

splitStreamsMap :: Ord a => [(a,b)] -> Map.Map a [b]
splitStreamsMap = foldl add Map.empty
 where add (a,b) m = Map.insertWith (++) a [b]

splitStreams = Map.fromList . splitStreamsMap


Twan


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


[Haskell-cafe] Optimization problem

2006-09-13 Thread tpledger
Magnus Jonsson wrote:
[...]
> but your example fails on infinite lists
[...]
> take 2 $ snd $ head $ splitStreams (map (\x -> (0 ,x))
[1..])

Any approach, even sieving, will struggle with infinite
lists, won't it?

(take 2 . snd . head . splitStreams) [(i, i) | i <-
[0..]]

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


[Haskell-cafe] program execution and laziness

2006-09-13 Thread Tim Newsham

I'm having a problem with program execution in win32 which seems
to be tied to laziness.  The function I'm using is:

runCmd cmd outdir dir base ext = do
let argv = words cmd
(i,o,e,p) <- runInteractiveProcess (head argv) (drop 1 argv) Nothing 
Nothing

hClose i
out <- hGetContents o
-- print out
x <- waitForProcess p
hClose o
hClose e
case x of
ExitSuccess  -> return 0
(ExitFailure n)  -> return n

this is hanging indefinitely when I run it in win32.  If I add
in the print statement (commented out above) it works fine!  So
I can only imagine that waitForProcess is hanging when I haven't
drained the stdout stream.

How can I force hGetContents to be strict (or at least to completely
process the stream prior to the waitForProcess command)?

Tim Newsham
http://www.thenewsh.com/~newsham/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Optimization problem

2006-09-13 Thread Magnus Jonsson

On Thu, 14 Sep 2006 [EMAIL PROTECTED] wrote:


Any approach, even sieving, will struggle with infinite
lists, won't it?

   (take 2 . snd . head . splitStreams) [(i, i) | i <-
[0..]]


Yes, if you expect two messages but only one comes then you'll 
wait forever, true.




Regards,
Tom

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


Re: [Haskell-cafe] Re: Numeric type classes

2006-09-13 Thread David Menendez
Ross Paterson writes:

> Such features would be useful, but are unlikely to be available for
> Haskell'.  If we concede that, is it still desirable to make these
> changes to the class hierarchy?
> 
> I've collected some notes on these issues at
> 
>
http://haskell.galois.com/cgi-bin/haskell-prime/trac.cgi/wiki/
StandardClasses

Coincidentally, I spent some time last week thinking about a replacement
for the Num class. I think I managed to come up with something that's
more flexible than Num, but still mostly comprehensible.



> class Monoid a where
>   zero :: a
>   (+) :: a -> a -> a

Laws:
identity : zero + a == a == a + zero
associativity : a + (b + c) == (a + b) + c

Motivation:
Common superclass for Group and Semiring.

> class Monoid a => Group a where
>   negate :: a -> a
>   (-) :: a -> a -> a
> 
>   a - b = a + negate b
>   negate a = zero - a

Laws:
negate (negate a) == a
a + negate a == zero == negate a + a

Motivation:
Money, dimensional quantities, vectors.

An Abelian group is just a group where (+) is commutative. If there's a
need, we can declare a subclass.

For non-Abelian groups, it's important to note that (-) provides right
subtraction.

> class Monoid a => Semiring a where
>   one :: a
>   (*) :: a -> a -> a

Laws:
identity : one * a == a == a * one
associativity : a * (b * c) == (a * b) * c
zero annihilation : zero * a == zero == a * zero

Motivation:
Natural numbers support addition and multiplication, but not
negation.

Unexpectedly, instances of MonadPlus and ArrowPlus can also be
considered Semirings, with (>>) and (>>>) being the multiplication.

Since Semiring is a subclass of Monoid, we get the (+,0) instance for
free. The following wrapper implements the (*,1) monoid.

> newtype Prod a = Prod { unProd :: a }
>
> instance (Semiring a) => Monoid (Prod a) where
>   zero = Prod one
>   Prod a + Prod b = Prod (a * b)

> class (Semiring a, Group a) => Ring a where
>   fromInteger :: Integer -> a

Placing 'fromInteger' here is similar to Num in spirit, but perhaps
undesirable.

I'm not sure what the contract is for fromInteger. Perhaps something
like,

fromInteger 0 = zero
fromInteger 1 = one
fromInteger n | n < 0 = negate (fromInteger (negate n))
fromInteger n = one + fromInteger (n-1)

Which, actually, could also be a default definition.

The original Num class is essentially a Ring with abs, signum, show, and
(==).

> class (Ring a, Eq a, Show a) => Num a where
> abs :: a -> a
> signum :: a -> a

These are probably best put in a NormedRing class or something.



I don't have enough math to judge the classes like Integral, Real,
RealFrac, etc, but Fractional is fairly straightforward.

> class Ring a => DivisionRing a where
>   recip :: a -> a
>   (/) :: a -> a -> a
>   fromRational :: Rational -> a
> 
>   a / b = a * recip b
>   recip a = one / a

Laws:
recip (recip a) == a, unless a == zero
a * recip a == one == recip a * a, unless a == zero

Motivation:
A division ring is essentially a field that doesn't require
multiplication to commute, which allows us to include quaternions and
other non-commuting division algebras.

Again, (/) represents right division.



These show up a lot, but don't have standard classes.

> class (Group g) => GroupAction g a | a -> g where
> add :: g -> a -> a

Laws:
add (a + b) c == add a (add b c)
add zero c == c

Motivation:
Vectors act on points, durations act on times, groups act on
themselves (another wrapper can provide that, if need be).

> class (GroupAction g a) => SymmetricGroupAction g a | a -> g where
> diff :: a -> a -> g

Laws:
diff a b == negate (diff b a)
diff (add a b) b == a

Motivation:
I'm not sure whether this is the correct class name, but it's
certainly a useful operation when applicable.

> class (Ring r, Group a) => Module r a | a -> r where
> mult :: r -> a -> a

Laws:
mult (a * b) c == mult a (mult b c)
mult one c == c

Motivation:
Scalar multiplication is fairly common. A module is essentially a
vector space over a ring, instead of a field.

It's fairly trivial to write an adapter to produce a GroupAction
instance for any Module.



For illustration, here's an example with vectors and points:

> data Pt a = Pt a a deriving (Eq, Show)
> data Vec a = Vec a a deriving (Eq, Show)
> 
> instance (Ring a) => Monoid (Vec a) where
>   zero = Vec 0 0
>   Vec x y + Vec x' y' = Vec (x + x') (y + y')
> 
> instance (Ring a) => Group (Vec a) where
>   Vec x y - Vec x' y' = Vec (x - x') (y - y')
> 
> instance (Ring a) => Module a (Vec a) where
>   mult a (Vec x y) = Vec (a * x) (a * y)
>   
> instance (Ring a) => GroupAction (Vec a) (Pt a) where
>   add (Vec dx dy) (Pt x y) = Pt (dx + x) (dy + y)
> 
> instance (Ring a) => SymmetricGroupAction (Vec a) (Pt a) where
>   diff (Pt x y) (Pt x' y') = Vec (x - x') (y - y')
>
> midpoint p1 p2 = add (mult 0.5 (diff p1 p2)) p

Re[2]: [Haskell-cafe] foreach

2006-09-13 Thread Bulat Ziganshin
Hello Michael,

Thursday, September 14, 2006, 12:44:37 AM, you wrote:

> Or, what about using ListT to combine it with IO, eliminating the need for
> two separate `do' blocks?

according to my experience, in most cases we need two do blocks just
because outer one contains more code after inner one finishes up


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] program execution and laziness

2006-09-13 Thread Bulat Ziganshin
Hello Tim,

Thursday, September 14, 2006, 5:32:24 AM, you wrote:
>  out <- hGetContents o
>  -- print out

> How can I force hGetContents to be strict (or at least to completely
> process the stream prior to the waitForProcess command)?

return $! last out


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Re: Numeric type classes

2006-09-13 Thread ajb
G'day all.

Quoting Henning Thielemann <[EMAIL PROTECTED]>:

> A monoid operation is associative, isn't it?

Duh.  Yes.  Sorry.  Need caffeine.

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