[Haskell-cafe] Re: Memoization in Haskell?

2010-07-09 Thread Heinrich Apfelmus

Gregory Crosswhite wrote:
 You're correct in pointing out that f uses memoization inside of itself 
to cache the intermediate values that it commutes, but those values 
don't get shared between invocations of f;  thus, if you call f with the 
same value of n several times then the memo table might get 
reconstructed redundantly.  (However, there are other strategies for 
memoization that are persistent across calls.)


It should be

f = \n - memo ! n
where
memo = ..

so that  memo  is shared across multiple calls like  f 1 , f 2  etc.

Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


Re: [Haskell-cafe] Memoization in Haskell?

2010-07-09 Thread Edward Kmett
On Thu, Jul 8, 2010 at 5:30 PM, Angel de Vicente ang...@iac.es wrote:

 Hi,

 I'm going through the first chapters of the Real World Haskell book,
 so I'm still a complete newbie, but today I was hoping I could solve
 the following function in Haskell, for large numbers (n  108)

 f(n) = max(n,f(n/2)+f(n/3)+f(n/4))

 I've seen examples of memoization in Haskell to solve fibonacci
 numbers, which involved computing (lazily) all the fibonacci numbers
 up to the required n. But in this case, for a given n, we only need to
 compute very few intermediate results.

 How could one go about solving this efficiently with Haskell?

 We can do this very efficiently by making a structure that we can index in
sub-linear time.

But first,

{-# LANGUAGE BangPatterns #-}

import Data.Function (fix)

Lets define f, but make it use 'open recursion' rather than call itself
directly.

f :: (Int - Int) - Int - Int
f mf 0 = 0
f mf n = max n $ mf (div n 2) +
 mf (div n 3) +
 mf (div n 4)

You can get an unmemoized f by using `fix f`

This will let you test that f does what you mean for small values of f by
calling, for example: `fix f 123` = 144

We could memoize this by defining:

f_list :: [Int]
f_list = map (f faster_f) [0..]

faster_f :: Int - Int
faster_f n = f_list !! n

That performs passably well, and replaces what was going to take O(n^3) time
with something that memoizes the intermediate results.

But it still takes linear time just to index to find the memoized answer for
`mf`. This means that results like:

*Main Data.List faster_f 123801
248604

are tolerable, but the result doesn't scale much better than that. We can do
better!

First lets define an infinite tree:

data Tree a = Tree (Tree a) a (Tree a)
instance Functor Tree where
fmap f (Tree l m r) = Tree (fmap f l) (f m) (fmap f r)

And then we'll define a way to index into it, so we can find a node with
index n in O(log n) time instead:

index :: Tree a - Int - a
index (Tree _ m _) 0 = m
index (Tree l _ r) n = case (n - 1) `divMod` 2 of
(q,0) - index l q
(q,1) - index r q

... and we may find a tree full of natural numbers to be convenient so we
don't have to fiddle around with those indices:

nats :: Tree Int
nats = go 0 1
where
go !n !s = Tree (go l s') n (go r s')
where
l = n + s
r = l + s
s' = s * 2

Since we can index, you can just convert a tree into a list:

toList :: Tree a - [a]
toList as = map (index as) [0..]

You can check the work so far by verifying that `toList nats` gives you
[0..]

Now,

f_tree :: Tree Int
f_tree = fmap (f fastest_f) nats

fastest_f :: Int - Int
fastest_f = index f_tree

works just like with list above, but instead of taking linear time to find
each node, can chase it down in logarithmic time.

The result is considerably faster:

*Main fastest_f 12380192300
67652175206

*Main fastest_f 12793129379123
120695231674999

In fact it is so much faster that you can go through and replace Int with
Integer above and get ridiculously large answers almost instantaneously

*Main fastest_f' 1230891823091823018203123
93721573993600178112200489

*Main fastest_f' 12308918230918230182031231231293810923
11097012733777002208302545289166620866358

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


[Haskell-cafe] Other transactional arrays?

2010-07-09 Thread Emil Melnicov
Currently, Haskell have transactional arrays in
Control.Concurrent.STM.TArray implemented as Array i (TVar e)
which is array of transactional variables.  But what if I need to
place an array into TVar itself?  This is something like TVar
(IOArray i e), but with ability to read/write array elements inside
an STM transaction, and then commit changes with atomically.

I've tried to make up this arrays in the following way:

 {-# LANGUAGE MagicHash #-}
 {-# LANGUAGE UnboxedTuples #-}
 {-# OPTIONS_GHC -fno-cse #-}

 module Data.Vector.STM
   ( TVector
   , newTVector
   , newTVectorIO
   , readTVector
   , readTVectorIO
   , writeTVector
   ) where

 import GHC.Conc
 import GHC.Prim
 import GHC.Types (Int(..), IO(..))

 data MutableArray a = MutableArray (MutableArray# RealWorld a)

 data TVector a = TVector (TVar# RealWorld (MutableArray a))

 stm = STM
 {-# NOINLINE stm #-}

 newTVector :: Int - a - STM (TVector a)
 newTVector (I# i#) x = stm $ \s1# -
 case newArray# i# x s1# of { (# s2#, a# #) -
 case newTVar# (MutableArray a#) s2# of { (# s3#, t# #) -
 (# s3#, (TVector t#) #) }}

 newTVectorIO :: Int - a - IO (TVector a)
 newTVectorIO (I# i#) x = IO $ \s1# -
 case newArray# i# x s1# of { (# s2#, a# #) -
 case newTVar# (MutableArray a#) s2# of { (# s3#, t# #) -
 (# s3#, (TVector t#) #) }}

 readTVector :: TVector a - Int - STM a
 readTVector (TVector t#) (I# i#) = stm $ \s1# -
 case readTVar# t# s1# of { (# s2#, (MutableArray a#) #) -
 case readArray# a# i# s2# of { (# s3#, a #) -
 (# s3#, a #) }}

 readTVectorIO :: TVector a - Int - IO a
 readTVectorIO (TVector t#) (I# i#) = IO $ \s1# -
 case readTVarIO# t# s1#   of { (# s2#, (MutableArray a#) #) -
 case readArray# a# i# s2# of { (# s3#, a #) -
 (# s3#, a #) }}

 writeTVector :: TVector a - Int - a - STM ()
 writeTVector (TVector t#) (I# i#) x = stm $ \s1# -
 case readTVar# t# s1#of { (# s2#, (MutableArray a#) 
 #) -
 case writeArray# a# i# x s2# of { s3# -
 case writeTVar# t# (MutableArray a#) s3# of { s4# -
 (# s4#, () #) }}}

It seems like it works, but I'm in doubt about it's correctness.
Unfortunately, I don't know much about STM mechanics, so I'm asking
Cafe users (you :-) for help.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Other transactional arrays?

2010-07-09 Thread Felipe Lessa
On Fri, Jul 9, 2010 at 7:16 AM, Emil Melnicov emilm...@gmail.com wrote:
 writeTVector :: TVector a - Int - a - STM ()
 writeTVector (TVector t#) (I# i#) x = stm $ \s1# -
     case readTVar# t# s1#                    of { (# s2#, (MutableArray a#) 
 #) -
     case writeArray# a# i# x s2#             of { s3# -
     case writeTVar# t# (MutableArray a#) s3# of { s4# -
     (# s4#, () #) }}}

 It seems like it works, but I'm in doubt about it's correctness.
 Unfortunately, I don't know much about STM mechanics, so I'm asking
 Cafe users (you :-) for help.

I guess the only problem lies with writeTVector.  I don't know much
about STM implementation details as well, but reading the code for
writeTVector I can't see how it could be rollbacked.  I.e., should
something with writeTVector fail and rollback, how will the old value
get into the mutable array?

Cheers :)

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


Re: [Haskell-cafe] Memoization in Haskell?

2010-07-09 Thread Angel de Vicente

Hi,

thanks for all the replies. I'm off now to try all the suggestions...

Cheers,
Ángel de Vicente
--
http://www.iac.es/galeria/angelv/

High Performance Computing Support PostDoc
Instituto de Astrofísica de Canarias
-
ADVERTENCIA: Sobre la privacidad y cumplimiento de la Ley de Protección de 
Datos, acceda a http://www.iac.es/disclaimer.php
WARNING: For more information on privacy and fulfilment of the Law concerning 
the Protection of Data, consult http://www.iac.es/disclaimer.php?lang=en

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


Re: [Haskell-cafe] Memoization in Haskell?

2010-07-09 Thread Daniel Fischer
On Friday 09 July 2010 01:03:48, Luke Palmer wrote:
 On Thu, Jul 8, 2010 at 4:23 PM, Daniel Fischer daniel.is.fisc...@web.de 
wrote:
  On Friday 09 July 2010 00:10:24, Daniel Fischer wrote:
  You can also use a library (e.g.
  http://hackage.haskell.org/package/data- memocombinators) to do the
  memoisation for you.
 
  Well, actualy, I think http://hackage.haskell.org/package/MemoTrie
  would be the better choice for the moment, data-memocombinators
  doesn't seem to offer the functionality we need out of the box.

 I'm interested to hear what functionality MemoTrie has that
 data-memocombinators does not.  I wrote the latter in hopes that it
 would be strictly more powerful*.

It's probably my night-blindness, but I didn't see an immediate way to 
memoise a simple function on a short look at the docs, like

memo :: (ConstraintOn a) = (a - b) - a - b

, which Data.MemoTrie provides (together with memo2 and memo3, which data-
memocombinators provide too).

Taking a closer look at the docs in daylight, I see data-mc provides that 
out of the box too, the stuff is just differently named (bool, char, 
integral, ...) - which I didn't expect.

So you could take it as an indication that I'm visually impaired, or as an 
indication that the docs aren't as obvious as they could be.

Cheers,
Daniel

 Luke

 * Actually MemoTrie wasn't around when I wrote that, but I meant the
 combinatory technique should be strictly more powerful than a
 typeclass technique.  And data-memocombinators has many primitives, so
 I'm still curious.

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


[Haskell-cafe] Something that kind of resembles OO

2010-07-09 Thread Michael Mossey
I notice in algebraic data defined with named fields, you can use the 
same name inside different constructors and then apply it to any data of 
that type.


data Vehicle = Car { ident :: String, wheel :: Circle }
 | Plane { ident :: String, stick :: Line }

f :: [Vehicle] - [String]
f = map ident

This is a little like fields in a base class.

I also see that a wrong use of accessor functions will compile but give 
a runtime error:


test = wheel (Plane foo (Line 1))

Will give a runtime error.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Something that kind of resembles OO

2010-07-09 Thread Ivan Lazar Miljenovic
Michael Mossey m...@alumni.caltech.edu writes:

 I notice in algebraic data defined with named fields, you can use the
 same name inside different constructors and then apply it to any data
 of that type.

 data Vehicle = Car { ident :: String, wheel :: Circle }
  | Plane { ident :: String, stick :: Line }

 f :: [Vehicle] - [String]
 f = map ident

 This is a little like fields in a base class.

 I also see that a wrong use of accessor functions will compile but
 give a runtime error:

 test = wheel (Plane foo (Line 1))

Well, it type-checks...

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


Re: [Haskell-cafe] Talking to Java from Haskell?

2010-07-09 Thread Daniel Cook
 A simpler solution might be Facebook's thrift [1]

This is a very interesting solution.  I'll investigate Thrift further,
but it may wind up being what I do.  Does anyone know how solid this
code is in Haskell?

 the Java binary directly from Haskell using System.Process and friends, and
 rather than communicating over ports, communicate over pipes.

Cool!This is probably a second step, though - first get the code
working, then worry about
making it all fast.


On Fri, Jul 9, 2010 at 5:11 AM, sterl s.clo...@gmail.com wrote:
 Daniel Cook wrote:

 b) Wrap the Java library with some code to use a lightweight message
 queue (zeromq) to send messages to my Haskell program?  (This would
 require essentially re-implementing an abstracted subset of the the
 protocol into 0MQ messages)

 A simpler solution might be Facebook's thrift [1] (now an Apache project).
 You write a simple file in a C-inspired IDL which gives typedefs and RPC
 signatures, and not only do you get the data structures and serialization
 functions in a number of target languages including Haskell and Java, but
 you get lightweight, relatively robust, server and client implementations.
 The implementations of the Java functions can then be written in Scala or
 Clojure, so you avoid having to leave fp-land entirely. One could even run
 the Java binary directly from Haskell using System.Process and friends, and
 rather than communicating over ports, communicate over pipes. In any case,
 I've had good luck with this approach.

 Cheers,
 Sterl.

 [1] http://incubator.apache.org/thrift/

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


[Haskell-cafe] Float instance of Data.Bits

2010-07-09 Thread Sam Martin
Hi,

Is there a particular reason Float, Double, etc do not have instances of 
Data.Bits in the standard libraries? I note the Haskell 2010 report doesn't 
include them either.

In fact, I'm not actually sure how you'd implement the instance for floating 
point types without having some kind of compiler-specific extension, or a 
c-binding.

Could anyone fill in my missing knowledge here?

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


Re: [Haskell-cafe] Talking to Java from Haskell?

2010-07-09 Thread John Lato
 From: Daniel Cook danielkc...@gmail.com

 Hi,

 Someone has written a large Java library (QuickFIX/J) which speaks a
 gnarled, ugly protocol (FIX).  There don't appear to be any FIX
 protocol libraries in Hackage.  I need my Haskell program to talk to a
 3rd-party system that only speaks FIX.

 Should I:

 a) Reimplement the protocol directly Haskell?  (This appears to be 
 non-trivial)

 b) Wrap the Java library with some code to use a lightweight message
 queue (zeromq) to send messages to my Haskell program?  (This would
 require essentially re-implementing an abstracted subset of the the
 protocol into 0MQ messages)

I think you need to answer these two questions to make a decision:

1)  How stable/defined is FIX?
2)  How large of a subset of FIX do you use?

If FIX is relatively stable or has multiple (non-C) implementations in
current use, and you'd be using a large-enough subset, then I expect
implementing a Haskell implementation would be the smallest amount of
work overall.  If FIX has only one canonical implementation, changes
frequently, or you'll only use a small portion of it, then b) would
likely be simplest.

Another option would be to expose hooks to your Haskell program
through the FFI and have it called by Java.

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


Re: [Haskell-cafe] Other transactional arrays?

2010-07-09 Thread Emil Melnicov
On 9 July 2010, at 08:13
Felipe Lessa felipe.le...@gmail.com wrote:

 I guess the only problem lies with writeTVector.  I don't know much
 about STM implementation details as well, but reading the code for
 writeTVector I can't see how it could be rollbacked.  I.e., should
 something with writeTVector fail and rollback, how will the old value
 get into the mutable array?
 
 Cheers :)
 
 -- 
 Felipe.

Yes, you are right.  We can't omit writeArray# here, and this one
simply writes something to the array without any respect to transaction
log.  It seems that you can't fool Haskell's type system :)

Actually, I can use TVar (IntMap a) to solve my problem.
Nonetheless, I wonder if it is possible to access STM internals
within Haskell (e.g. through some primitives like writeLog# or
checkConsistency#), although it's hardly justified.

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


Re: [Haskell-cafe] Code Example and Haskell Patterns

2010-07-09 Thread Martijn van Steenbergen

On 7/8/10 21:36, Stephen Tetley wrote:

Hello

I suspect you will have to choose single examples for each of the
patterns/ abstractions you are interested in.

Doaitse Swierstra's library UU.Parsing is the originator or the
Applicative style. Its latest incarnation is the library
uu-parsinglib.


Applicative style has several contributors:
* AFAIK, Niklas Röjemo first came up with the names for the operators 
(as the haddock for Control.Applicative says)
* It was used heavily, popularised and expanded by (among others) 
Doaitse Swierstra
* Conor McBride and Ross Paterson recognised the pattern could be 
applied to things other than parsers


(Correct me if I'm wrong!)

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


[Haskell-cafe] hs-dotnet with Mono?

2010-07-09 Thread Daniel Cook
Hi,

Has anyone used hs-dotnet (http://haskell.forkio.com/dotnet/) with
Mono on Linux?

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


[Haskell-cafe] Re: Float instance of Data.Bits

2010-07-09 Thread Ertugrul Soeylemez
Sam Martin sam.mar...@geomerics.com wrote:

 Is there a particular reason Float, Double, etc do not have instances
 of Data.Bits in the standard libraries? I note the Haskell 2010 report
 doesn't include them either.

 In fact, I'm not actually sure how you'd implement the instance for
 floating point types without having some kind of compiler-specific
 extension, or a c-binding.

 Could anyone fill in my missing knowledge here?

Some operations wouldn't make much sense with Float, for instance the
'complement' function.  What should it return?  Also note that bit
manipulation functions could cover only a small window of the value
range.  So it could happen that x .|. y = x, even though y is nonzero.
Also rotation would be a destructive operation.

Nobody would really need the operations (we have integer types and
UArray Int Bool for bit manipulation), and they would most likely be
very slow.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife = sex)
http://ertes.de/


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


Re: [Haskell-cafe] Comments on Haskell 2010 Report

2010-07-09 Thread Brandon S Allbery KF8NH
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 7/8/10 22:25 , Alex Stangl wrote:
 1. I.E. and e.g. should be followed by commas -- unless UK usage
 differs from US standards. (Page 3 and elsewhere, although FFI chapter

I don't think I've ever seen them *followed* by commas.  Preceded, always.

- -- 
brandon s. allbery [linux,solaris,freebsd,perl]  allb...@kf8nh.com
system administrator  [openafs,heimdal,too many hats]  allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university  KF8NH
-BEGIN PGP SIGNATURE-
Version: GnuPG v2.0.10 (Darwin)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iEYEARECAAYFAkw3LQoACgkQIn7hlCsL25WpzACgiBSLqdueABWArQyQLbWBPrrs
dKkAoJHA0u65jLLaZqizJM1dPLPtVLXt
=pwq4
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Float instance of Data.Bits

2010-07-09 Thread Serguey Zefirov
2010/7/9 Ertugrul Soeylemez e...@ertes.de:
 Sam Martin sam.mar...@geomerics.com wrote:
 Nobody would really need the operations (we have integer types and
 UArray Int Bool for bit manipulation), and they would most likely be
 very slow.

They won't be slow using SSE2 or something. I can see where they could
be beneficial.

But I agree that those operations have semantics not compatible with
Data.Bits operations.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Comments on Haskell 2010 Report

2010-07-09 Thread Steve Schafer
On Fri, 09 Jul 2010 10:07:06 -0400, you wrote:

I don't think I've ever seen them *followed* by commas.  Preceded, always.

In American English, they're always followed by commas, and preceded by
comma, semicolon, dash or left parenthesis, depending on the specific
context.

Examples from various online style guides:

I am the big cheese, i.e., the boss.

The department is unattached; i.e., it is not administered by one of
the schools or colleges. 
 
Most committee members—-i.e., those who were willing to speak
out-—wanted to reject the plan. 

Most committee members (i.e., those who were willing to speak
out) wanted to reject the plan.

See also: http://www.videojug.com/film/how-to-use-ie-and-eg

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


RE: [Haskell-cafe] Re: Float instance of Data.Bits

2010-07-09 Thread Sam Martin
 Some operations wouldn't make much sense with Float, for instance the
 'complement' function.  What should it return?  Also note that bit
 manipulation functions could cover only a small window of the value
 range.  So it could happen that x .|. y = x, even though y is nonzero.
 Also rotation would be a destructive operation.

Perhaps I can illustrate this with an example. It's very common with SSE
code to interpret a float as both a mask and a number. You can exchange
the two freely.

For instance, in c-like pseudo code, you can write:
float mask = myval == 0 ? 0x : 0x
float temp = 5 / myval
float result = mask .. temp

Which returns 0 or the result of 5 / myval. Each line above turns into a
single sse instruction, and there are no branches. Bit wise operations
on Floats should operate as if you had reinterpreted the Float as an
unsigned integer.

There are plenty of other examples of bit twiddling floats. Floats have
a well defined bit representation (if a slightly complex one) so it's
perfectly reasonable to be able to manipulate it. A complement operation
on a float returns a float, and is well defined, if the output bit
pattern is one you want.

An alternative way to model this would be to provide ways to reinterpret
a float as a word32, which helps enforce static typing. I don't know of
any way of doing this in Haskell though.

Does that make more sense?

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


Re: [Haskell-cafe] Re: Float instance of Data.Bits

2010-07-09 Thread Serguey Zefirov
2010/7/9 Sam Martin sam.mar...@geomerics.com:
 Some operations wouldn't make much sense with Float, for instance the
 'complement' function.  What should it return?  Also note that bit
 manipulation functions could cover only a small window of the value
 range.  So it could happen that x .|. y = x, even though y is nonzero.
 Also rotation would be a destructive operation.

 Perhaps I can illustrate this with an example. It's very common with SSE
 code to interpret a float as both a mask and a number. You can exchange
 the two freely.

 For instance, in c-like pseudo code, you can write:
 float mask = myval == 0 ? 0x : 0x

Notwithstanding mask is compatible with float sizeof-wize you should
assign it a different type so you won't accidentally return a value of
0x.

It is cumbersome in C, and much more easier in Haskell.

Then you specify your operations over masks and floats, bind them to
SSE2 primitives and use them as you wish.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] bug in ghci ?

2010-07-09 Thread Kevin Quick

On Thu, 08 Jul 2010 09:48:34 -0700, Daniel Fischer daniel.is.fisc...@web.de 
wrote:


On Thursday 08 July 2010 18:24:05, Ben Millwood wrote:

On Thu, Jul 8, 2010 at 3:45 PM, Daniel Fischer daniel.is.fisc...@web.de

wrote:

 Well, I made the suggestion of emitting a warning on instance
 declarations without method definitions. That would be comparatively
 easy to implement (even with an additional check to only emit the
 warning if the class defines any methods) and catch many (if not most)
 cases.

Unfortunately, it would catch some perfectly valid cases, see the list
of instances for flat datatypes here:

http://hackage.haskell.org/packages/archive/deepseq/1.1.0.0/doc/html/src
/Control-DeepSeq.html

This demonstrates that there is at least one (admittedly probably not
much more than one) case where a class with methods would have a
default implementation that was total and valid in some cases.


Good point.
So one should check for more than one class-method [then defining no
methods in the instance declaration is likely to lead to a default-method
loop if there are default methods for all, otherwise GHC will warn
already].
That can of course still give rise to spurious warnings, but is less likely
to.


I would think that only mutually recursive default methods would require 
respecification and that there could be any number of default methods that were 
reasonable as is.  Since it's probably quite difficult for the Haskell compiler 
to analytically detect non-terminating v.s. terminating mutual recursion it may 
be useful to define an explicit comment flag for this case.

For example:

   class Show a where
  shows = showsPrec 5
  showsPrec _ = shows
  {-# REDEFINE_ONE: shows showsPrec #-}

This would fairly simply allow a warning to be generated for an instance which 
did not redefine one of the identified methods; it would capture that 
requirement in the same place the recursive definition was defined, it would 
avoid false warnings, and it would be backward compatible (and it might be 
Haddock-able as well).

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


Re: [Haskell-cafe] Comments on Haskell 2010 Report

2010-07-09 Thread Sean Leather
On Fri, Jul 9, 2010 at 16:23, Steve Schafer wrote:

 On Fri, 09 Jul 2010 10:07:06 -0400, brandon s. allbery wrote:
  I don't think I've ever seen them *followed* by commas.  Preceded,
 always.

 In American English, they're always followed by commas, and preceded by
 comma, semicolon, dash or left parenthesis, depending on the specific
 context.


One of the nice things about English is that there is often never an
always. See http://grammar.quickanddirtytips.com/ie-eg-oh-my.aspx for a
discussion. (For me personally, I prefer to minimize the juxtapositions of
punctuation (e.g. . and ,). As long as there's not an editor looking over my
shoulder telling me it's not acceptable, I will continue to do so.)

As for future editions of the Haskell Report, one possibility to eliminate
concerns about spelling and grammar would be to decide to follow a certain
dialect and style. This would reduce the number of comma-related comments.

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


Re: [Haskell-cafe] Code Example and Haskell Patterns

2010-07-09 Thread Stephen Tetley
Hi Martijn

I think you are right there - the tech report I linked to does credit
the interface to Niklas Röjemo, so I shouldn't have used the word
originator (as you suggested popularised would have been better).
Unfortunately the thesis doesn't seem available on the web so I can't
see how much of the applicative style it introduced.

Best wishes

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


FIX Protocol in Haskell (was Re: [Haskell-cafe] Talking to Java from Haskell?)

2010-07-09 Thread Daniel Cook
 1)  How stable/defined is FIX?

Not very.  There are several protocol versions, various vendors have
their own custom message types, there are service packs released
fairly regularly updating the protocol for new message types, etc.

 2)  How large of a subset of FIX do you use?

I will be using a relatively small subset of the available FIX
messages, and my subset will change a lot at the beginning but then
stabilize.

 work overall.  If FIX has only one canonical implementation, changes
 frequently, or you'll only use a small portion of it, then b) would
 likely be simplest.

FIX has one canonical open source implementation (actually 2, but
they're the same program ported to C++ and Java).

Another option is to use Haskell's FFI to wrap the C++ implementation.

QuickFIX is designed exactly the way you *wouldn't* design it to make
interop with Haskell easy.  The API is based on callbacks to a class
which one extends.  The C++ uses lots of templates, and the .h files
are full of macros.

On the plus side, the program has a .idl, and is already SWIG-wrapped
for C#, Python, and Ruby.  Do you (or anyone) have experience wrapping
highly stateful C++ programs with Haskell FFI?  Are there examples
around? (Xmonad comes to mind, but I don't know if X11's API is C or
C++ ..)

I think I'm going to have to recreate the various message types in
Haskell's type system anyway.  Given that, maybe I should simply use
Haskell to implement a small, clean, extensible subset of this
protocol (what I need).  I can then test it heavily against the
QuickFIX implementation.

Opinions?

-- Dan


On Fri, Jul 9, 2010 at 2:31 PM, John Lato jwl...@gmail.com wrote:
 From: Daniel Cook danielkc...@gmail.com

 Hi,

 Someone has written a large Java library (QuickFIX/J) which speaks a
 gnarled, ugly protocol (FIX).  There don't appear to be any FIX
 protocol libraries in Hackage.  I need my Haskell program to talk to a
 3rd-party system that only speaks FIX.

 Should I:

 a) Reimplement the protocol directly Haskell?  (This appears to be 
 non-trivial)

 b) Wrap the Java library with some code to use a lightweight message
 queue (zeromq) to send messages to my Haskell program?  (This would
 require essentially re-implementing an abstracted subset of the the
 protocol into 0MQ messages)

 I think you need to answer these two questions to make a decision:

 1)  How stable/defined is FIX?
 2)  How large of a subset of FIX do you use?

 If FIX is relatively stable or has multiple (non-C) implementations in
 current use, and you'd be using a large-enough subset, then I expect
 implementing a Haskell implementation would be the smallest amount of
 work overall.  If FIX has only one canonical implementation, changes
 frequently, or you'll only use a small portion of it, then b) would
 likely be simplest.

 Another option would be to expose hooks to your Haskell program
 through the FFI and have it called by Java.

 John

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


Re: [Haskell-cafe] Memoization in Haskell?

2010-07-09 Thread Mike Dillon
begin Edward Kmett quotation:
 The result is considerably faster:
 
 *Main fastest_f 12380192300
 67652175206
 
 *Main fastest_f 12793129379123
 120695231674999

I just thought I'd point out that running with these particular values
on a machine with a 32 bit Int will cause your machine to go deep into
swap... Anything constant greater that maxBound is being wrapped back to
the negative side, causing havoc to ensue. I changed the open version of
f to look like this to exclude negative values:

f :: (Int - Int) - Int - Int
f mf 0 = 0
f mf n | n  0 = error $ Invalid n value:  ++ show n
f mf n | otherwise = max n $ mf (div n 2) +
 mf (div n 3) +
 mf (div n 4)

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


Re: new haskell project (Was Re: [Haskell-cafe] Subtype polymorphism in Haskell)

2010-07-09 Thread Daniel Cook
Hi Simon,

I'm interested in this as well (you might have seen my other posts
about getting QuickFIX interfaced with Haskell).

One question (Yitzchak raises a valid point):

Why port QuantLib's structure rather than directly build an idiomatic
Haskell quantitative finance library? Especially given that the task
lends itself so nicely to functional programmming (cf the canonical
Functional Pearl by SPJ on composing financial contracts).  Just
curious about your rationale...

Cheers,
- Dan



On Tue, Jul 6, 2010 at 7:26 PM, Simon Courtenage courten...@gmail.com wrote:
 Hi,
 Just to add some details about the project I'm working on in case anyone is
 interested.  The project is called Quanthas and is being hosted on
 sourceforge at http://sourceforge.net/projects/quanthas/.  The aim of the
 project is to produce a Haskell implementation of Quantlib
 (http://sourceforge.net/projects/quantlib/)- an open source library for
 quantitative finance written in C++.  Haskell is starting to be used
 seriously in quantitative finance and risk modelling circles within the
 investment banking and finance community, so I thought there would be some
 value in producing such a version.
 If anyone is interested in helping out, we would be more than happy to hear
 from you, since the project has just started and there's a great deal to do
 (and learn!).
 Best regards
 Simon Courtenage
 On Tue, Jul 6, 2010 at 2:32 PM, Yitzchak Gale g...@sefer.org wrote:

 Hi Simon,

 Did you intentionally not reply to the list?

 Simon Courtenage wrote:
  This is for a project to port an open-source C++ library to haskell.

 Great! We'd love to give you whatever support you need
 for your efforts.

  My initial plan is to more or less preserve the way the
  library works in the first draft of the port and see how
  far we can get like that

 That's fine, as long as you truly mean the way it works,
 and not the way the code is structured. Haskell is a post-OO
 language. Its abstractions are very different than class
 structures in C++. There is no direct translation - any given
 C++ class structure could correspond to many totally different
 kinds of Haskell programs, depending on what the program
 is trying to do.

 If you are trying to find a method to transliterate a strongly
 OO-style C++ program more or less word for word into
 Haskell in a way that the class structure of the C++ will
 still be apparent in the result, you are likely in for a frustrating
 experience. You will spend a lot more time than you expected,
 and the results will be very unsatisfying. Many others have
 ended up that way.

 On the other hand, if you are willing to be a little more flexible
 in your thinking, you'll probably find the task much easier than
 you thought, enjoy it, and reap many benefits from the process
 that you never imagined.

 In any case, please keep us in the loop, we'd like to hear
 how it's going. And, uh... would you be willing to share a
 few more details about what it is that you're trying to port? ;)

 Thanks,
 Yitz


 ___
 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] Comments on Haskell 2010 Report

2010-07-09 Thread Steve Schafer
On Fri, 9 Jul 2010 17:14:31 +0200, you wrote:

One of the nice things about English is that there is often never an
always. See http://grammar.quickanddirtytips.com/ie-eg-oh-my.aspx for a
discussion.

Well, that page pretty much confirms what I said. In AMERICAN English,
they're always followed by commas. The two sources mentioned on that
page that suggest omitting the commas (Fowler's and Oxrford) are both
based on UK English.

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


Re: [Haskell-cafe] Code Example and Haskell Patterns

2010-07-09 Thread Malcolm Wallace

I think you are right there - the tech report I linked to does credit
the interface to Niklas Röjemo, so I shouldn't have used the word
originator (as you suggested popularised would have been better).
Unfortunately the thesis doesn't seem available on the web so I can't
see how much of the applicative style it introduced.


Although the whole thesis is not online, some of the papers contained  
in it are.  This one, although it appears to be on a different topic,  
does have a brief introduction to Röjemo's parser combinators in  
section 4.  He calls them monadic, even though the style is very  
obviously what we would now call applicative.


http://reference.kfupm.edu.sa/content/h/i/highlights_from_nhca_space_efficient_1916422.pdf

Röjemo's source code for an entire parser for Haskell (only slightly  
modified for newer versions of the language) is still available online  
too, in the source code of nhc98.


http://darcs.haskell.org/york-compiler98


Regards,
Malcolm

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


Re: [Haskell-cafe] Re: Memoization in Haskell?

2010-07-09 Thread Gregory Crosswhite
 That actually doesn't work as long as memo is an array, since then it 
has fixed size;  you have to also make memo an infinitely large data 
(but lazy) structure so that it can hold results for arbitrary n.  One 
option for doing this of course is to make memo be an infinite list, but 
a more space and time efficient option is to use a trie like in MemoTrie.


Cheers,
Greg

On 7/9/10 12:50 AM, Heinrich Apfelmus wrote:

Gregory Crosswhite wrote:
 You're correct in pointing out that f uses memoization inside of 
itself to cache the intermediate values that it commutes, but those 
values don't get shared between invocations of f;  thus, if you call 
f with the same value of n several times then the memo table might 
get reconstructed redundantly.  (However, there are other strategies 
for memoization that are persistent across calls.)


It should be

f = \n - memo ! n
where
memo = ..

so that  memo  is shared across multiple calls like  f 1 , f 2  etc.

Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

___
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: Float instance of Data.Bits

2010-07-09 Thread Nick Bowler
On 15:32 Fri 09 Jul , Sam Martin wrote:
 There are plenty of other examples of bit twiddling floats. Floats have
 a well defined bit representation (if a slightly complex one) so it's
 perfectly reasonable to be able to manipulate it.

Note that the Haskell report does not require IEEE 754 binary encodings.
In fact, it permits 'Float' to be a decimal floating point type.

-- 
Nick Bowler, Elliptic Technologies (http://www.elliptictech.com/)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization in Haskell?

2010-07-09 Thread Edward Kmett
Very true. I was executing the large Int-based examples on a 64 bit machine.


You can of course flip over to Integer on either 32 or 64 bit machines and
alleviate the problem with undetected overflow. Of course that doesn't help
with negative initial inputs
;)

I do agree It is still probably a good idea to either filter the negative
case like you do here, or, since it is well defined, extend the scope of the
memo table to the full Int range by explicitly memoizing negative vales as
well.

-Edward Kmett

On Fri, Jul 9, 2010 at 11:51 AM, Mike Dillon m...@embody.org wrote:

 begin Edward Kmett quotation:
  The result is considerably faster:
 
  *Main fastest_f 12380192300
  67652175206
 
  *Main fastest_f 12793129379123
  120695231674999

 I just thought I'd point out that running with these particular values
 on a machine with a 32 bit Int will cause your machine to go deep into
 swap... Anything constant greater that maxBound is being wrapped back to
 the negative side, causing havoc to ensue. I changed the open version of
 f to look like this to exclude negative values:

f :: (Int - Int) - Int - Int
f mf 0 = 0
 f mf n | n  0 = error $ Invalid n value:  ++ show n
f mf n | otherwise = max n $ mf (div n 2) +
  mf (div n
 3) +
 mf (div n
 4)

 -md

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


Re: [Haskell-cafe] Re: Transformers versus monadLib versus...

2010-07-09 Thread Edward Kmett
On Thu, Jul 8, 2010 at 12:37 PM, Yitzchak Gale g...@sefer.org wrote:

 Hi Edward,

 Edward Kmett wrote:
  It looks like there is a fairly strong effort to fix most of the most
  egregious warts in the mtl.

 btw, does this overhaul include adding Applicative instances,
 perchance?


They are already part of monads-fd and would, I presume, come along for the
ride when an mtl = monads-fd + transformers release occurs.  =)

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


Re: [Haskell-cafe] Comments on Haskell 2010 Report

2010-07-09 Thread Sean Leather
On Fri, Jul 9, 2010 at 18:35, Steve Schafer wrote:

 On Fri, 9 Jul 2010 17:14:31 +0200, Sean Leather wrote:
 One of the nice things about English is that there is often never an
 always. See http://grammar.quickanddirtytips.com/ie-eg-oh-my.aspx for a
 discussion.

 Well, that page pretty much confirms what I said. In AMERICAN English,
 they're always followed by commas. The two sources mentioned on that
 page that suggest omitting the commas (Fowler's and Oxrford) are both
 based on UK English.


And yet most of the other manuals describe the rule as usually, 
preferable/optional, and makes good sense. That refutes your claim
that they're
always followed by commas. ;)

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


[Haskell-cafe] Haskellers in Cleveland

2010-07-09 Thread Jason Felice
I've just started a Cleveland Haskellers meetup, and for some reason I
haven't thought to ask on this list yet.

If there's anybody from the Greater Cleveland, OH area who is interested,
please sign up!  I hope to keep it small and informal. I've had good luck
keeping it small so far.

There's a meetup next Saturday, in fact.

http://www.meetup.com/cle-haskell/

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


Re: [Haskell-cafe] Comments on Haskell 2010 Report

2010-07-09 Thread Gregory Crosswhite
 I don't know what the rule is, but I personally just replace i.e. 
with that is and e.g. with for example in my head, and then apply 
whatever punctuation makes sense with those substitutions.


Cheers,
Greg

On 7/9/10 12:17 PM, Sean Leather wrote:


On Fri, Jul 9, 2010 at 18:35, Steve Schafer wrote:

On Fri, 9 Jul 2010 17:14:31 +0200, Sean Leather wrote:
One of the nice things about English is that there is often
never an
always. See
http://grammar.quickanddirtytips.com/ie-eg-oh-my.aspx for a
discussion.

Well, that page pretty much confirms what I said. In AMERICAN English,
they're always followed by commas. The two sources mentioned on that
page that suggest omitting the commas (Fowler's and Oxrford) are both
based on UK English.


And yet most of the other manuals describe the rule as usually, 
preferable/optional, and makes good sense. That refutes your claim 
that they're always followed by commas. ;)


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] Comments on Haskell 2010 Report

2010-07-09 Thread Julian Fleischer
Hi,

 8. [...] Saying 0**0 is undefined seems reasonable,
 but why 0**y?
I agree on 0**y being 0 (not undefined), but why should 0**0 be undefined? x**0 
:= 1, by convention. Of course this is a still ongoing debate (regarding 
analysis of functions etc.), but the most usefull approach for /any/ 
programming language (and BTW for many mathematical proofs, too).

-Julian



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] Re: Transformers versus monadLib versus...

2010-07-09 Thread Ross Paterson
On Fri, Jul 09, 2010 at 03:13:19PM -0400, Edward Kmett wrote:
 On Thu, Jul 8, 2010 at 12:37 PM, Yitzchak Gale g...@sefer.org wrote:
 btw, does this overhaul include adding Applicative instances,
 perchance?
 
 They are already part of monads-fd and would, I presume, come along for the
 ride when an mtl = monads-fd + transformers release occurs.  =)

Actually they're in transformers with the type constructors.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Comments on Haskell 2010 Report

2010-07-09 Thread Alex Stangl
On Sat, Jul 10, 2010 at 12:12:15AM +0200, Julian Fleischer wrote:
  8. [...] Saying 0**0 is undefined seems reasonable,
  but why 0**y?
 I agree on 0**y being 0 (not undefined), but why should 0**0 be undefined? 
 x**0 := 1, by convention. Of course this is a still ongoing debate (regarding 
 analysis of functions etc.), but the most usefull approach for /any/ 
 programming language (and BTW for many mathematical proofs, too).

Hi Julian,

Glad somebody responded about something other than e.g. and i.e.

I wasn't arguing that 0**0 *ought* to be undefined, but that it
is a reasonable policy, since, as you point out, it's a matter
of ongoing debate. What I don't understand is why for y /= 0,
0**y would be undefined. Maybe the discontinuity at zero is
undesirable.

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


Re: [Haskell-cafe] Comments on Haskell 2010 Report

2010-07-09 Thread John Meacham
On Fri, Jul 09, 2010 at 06:07:04PM -0500, Alex Stangl wrote:
 I wasn't arguing that 0**0 *ought* to be undefined, but that it
 is a reasonable policy, since, as you point out, it's a matter
 of ongoing debate. What I don't understand is why for y /= 0,
 0**y would be undefined. Maybe the discontinuity at zero is
 undesirable.

I would think it is a typo in the report. Every language out there seems
to think 0**0 is 1 and 0**y | y /= 0 is 0. I am not sure whether it is
mandated by the IEEE standard but a quick review doesn't say they should
be undefined (and the report mentions all the operations with undefined
results), if anything it should be left for
instances to decide based on the underlying algebra of the specific
type and the report shouldn't mention it.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Comments on Haskell 2010 Report

2010-07-09 Thread Ivan Lazar Miljenovic
Brandon S Allbery KF8NH allb...@ece.cmu.edu writes:

 On 7/8/10 22:25 , Alex Stangl wrote:
 1. I.E. and e.g. should be followed by commas -- unless UK usage
 differs from US standards. (Page 3 and elsewhere, although FFI chapter

 I don't think I've ever seen them *followed* by commas.  Preceded,
 always.

Agreed.

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


Re: [Haskell-cafe] bug in ghci ?

2010-07-09 Thread Ivan Lazar Miljenovic
Kevin Quick qu...@sparq.org writes:

 I would think that only mutually recursive default methods would
 require respecification and that there could be any number of default
 methods that were reasonable as is.  Since it's probably quite
 difficult for the Haskell compiler to analytically detect
 non-terminating v.s. terminating mutual recursion it may be useful to
 define an explicit comment flag for this case.

 For example:

class Show a where
   shows = showsPrec 5
   showsPrec _ = shows
   {-# REDEFINE_ONE: shows showsPrec #-}

 This would fairly simply allow a warning to be generated for an
 instance which did not redefine one of the identified methods; it
 would capture that requirement in the same place the recursive
 definition was defined, it would avoid false warnings, and it would be
 backward compatible (and it might be Haddock-able as well).

This should be generalised IMO, since there might be cases where you
have to redefine either (foo  bar) || baz; of course, that makes the
syntax specification, etc. of the pragma more difficult...

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


Re: [Haskell-cafe] Comments on Haskell 2010 Report

2010-07-09 Thread Christopher Done
On 10 July 2010 01:22, Ivan Lazar Miljenovic ivan.miljeno...@gmail.com wrote:

 Brandon S Allbery KF8NH allb...@ece.cmu.edu writes:

  On 7/8/10 22:25 , Alex Stangl wrote:
  1. I.E. and e.g. should be followed by commas -- unless UK usage
  differs from US standards. (Page 3 and elsewhere, although FFI chapter
 
  I don't think I've ever seen them *followed* by commas.  Preceded,
  always.

From The Haskell 98 Library Report:

 partition takes a predicate and a list and returns a pair of lists: those 
elements of the argument list that do and do not satisfy the predicate, 
respectively; i.e., [...]

I don't think you should bother nitpicking about commas here. As
Gregory said, anywhere there is i.e., you can substitute it for
that is. Consider if the spec. was written with that is instead of
i.e., would you then criticise where and where not commas are used?
Does this arbitrary prescription really matter?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] bug in ghci ?

2010-07-09 Thread Kevin Quick

On Fri, 09 Jul 2010 16:26:13 -0700, Ivan Lazar Miljenovic 
ivan.miljeno...@gmail.com wrote:


Kevin Quick qu...@sparq.org writes:


I would think that only mutually recursive default methods would
require respecification and that there could be any number of default
methods that were reasonable as is.  Since it's probably quite
difficult for the Haskell compiler to analytically detect
non-terminating v.s. terminating mutual recursion it may be useful to
define an explicit comment flag for this case.

For example:

   class Show a where
  shows = showsPrec 5
  showsPrec _ = shows
  {-# REDEFINE_ONE: shows showsPrec #-}

This would fairly simply allow a warning to be generated for an
instance which did not redefine one of the identified methods; it
would capture that requirement in the same place the recursive
definition was defined, it would avoid false warnings, and it would be
backward compatible (and it might be Haddock-able as well).


This should be generalised IMO, since there might be cases where you
have to redefine either (foo  bar) || baz; of course, that makes the
syntax specification, etc. of the pragma more difficult...


I'm having trouble envisioning a restriction case such as you describe.  Can 
you provide an example?

The comment can't dictate that the resulting redefined method isn't still 
mutually recursive, but the warning for the lack of any override should provide 
enough of a trigger for the developer to read the docs/code and write an 
appropriate method.  If foo, bar, and baz are all interrelated it seems to me 
that an appropriate override of any of them could provide the necessary exit 
from recursion.

That's probably an interesting assertion that one of the category theorists 
around here could prove or disprove.  ;-)

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


Re: [Haskell-cafe] bug in ghci ?

2010-07-09 Thread Edward Kmett
On Fri, Jul 9, 2010 at 8:46 PM, Kevin Quick qu...@sparq.org wrote:

 On Fri, 09 Jul 2010 16:26:13 -0700, Ivan Lazar Miljenovic 
 ivan.miljeno...@gmail.com wrote:

  Kevin Quick qu...@sparq.org writes:

  I would think that only mutually recursive default methods would
 require respecification and that there could be any number of default
 methods that were reasonable as is.  Since it's probably quite
 difficult for the Haskell compiler to analytically detect
 non-terminating v.s. terminating mutual recursion it may be useful to
 define an explicit comment flag for this case.

 For example:

   class Show a where
  shows = showsPrec 5
  showsPrec _ = shows
  {-# REDEFINE_ONE: shows showsPrec #-}

 This would fairly simply allow a warning to be generated for an
 instance which did not redefine one of the identified methods; it
 would capture that requirement in the same place the recursive
 definition was defined, it would avoid false warnings, and it would be
 backward compatible (and it might be Haddock-able as well).


 This should be generalised IMO, since there might be cases where you
 have to redefine either (foo  bar) || baz; of course, that makes the
 syntax specification, etc. of the pragma more difficult...


 I'm having trouble envisioning a restriction case such as you describe.
  Can you provide an example?


Examples:

class Bifunctor f where
bimap :: (a - b) - (c - d) - f a c - f b d
first :: (a - b) - f a c - f b c
second :: (a - b) - f c a - f c b
first f = bimap f id
second = bimap id
bimap f g = second g . first f
{-# MUTUAL = first second | bimap #-}

The existing definition of Arrow is somewhat unsatisfying because its
product bifunctor definition (given by first, second and (***)) is
asymmetric. They choose to require you to define first, but could very well
use the same trick. (I am not advocating changing the well documented
historical definition of Arrow, just providing another example in the same
vein.)

class Category a = Arrow a where

arr :: (b - c) - a b c
first :: a b c - a (b,d) (c,d)
second :: a b c - a (d,b) (d,c)
(***) :: a b c - a b' c' - a (b,b') (c,c')
() :: a b c - a b c' - a b (c,c')

first = (*** id)

second = (id ***)

f *** g = first f  second g

f  g = arr (\b - (b,b))  f *** g

{-# MUTUAL first second | (***) #-}

An example that almost works would be Monad/Comonad where you can
define in terms of return/fmap/join or return/bind. However, the
definition of fmap is in another class, but if it wasn't:

class Comonad w where

liftW :: (a - b) - w a - w b
extract :: w a - a
extend :: (w a - b) - w a - w b
duplicate :: w a - w (w a)
extend = fmap f . duplicate
duplicate = extend id

{-# MUTUAL liftW duplicate | extend #-}


 The comment can't dictate that the resulting redefined method isn't still
 mutually recursive, but the warning for the lack of any override should
 provide enough of a trigger for the developer to read the docs/code and
 write an appropriate method.  If foo, bar, and baz are all interrelated it
 seems to me that an appropriate override of any of them could provide the
 necessary exit from recursion.


It turns out to be fairly tricky to pull off the definition in such a way
that you can define any one combinator in turn of the others in a big long
cycle. Foldable does this for instance in such a way that foldMap and foldr
are defined cyclically.

That's probably an interesting assertion that one of the category theorists
 around here could prove or disprove.  ;-)


I hope the above demonstrate that there are at least some fairly reasonable
(and, given your request, appropriately category theoretic!) examples where
one would want the ability to specify that there is more than one member of
a minimal mutual definition. =)

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


Re: [Haskell-cafe] bug in ghci ?

2010-07-09 Thread Alexander Solla


On Jul 9, 2010, at 5:46 PM, Kevin Quick wrote:

That's probably an interesting assertion that one of the category  
theorists around here could prove or disprove.  ;-)


It's not too hard.  I don't like thinking about it in terms of  
category theory, though.  It's easier to think about it in terms of  
universal quantification.  The assertion is equivalent to the claim  
that (forall x, forall y, P x y) iff (forall y, forall x, P x y),  
though you have to do quite a bit of packing and unpacking to get there.


Another way to see it is in terms of recursion on initial algebras.   
Given an initial algebra A, and an initial algebra B, we'll say that A  
- B represents the construction of attaching a copy of B to every  
element of A.  We can assume that A and B are disjoint, because we can  
find a normal form A' - B' for which A' and B' are disjoint, and such  
that A - B is isomorphic to A' - B'.  (To see that, assume that some  
subalgebra C is contained in both A and B.  Attaching a copy of B to  
every element of A means attaching a copy of C to each element, and  
also B \ C.  But A already contains C.  So A - B is isomorphic to A - 
 B \ C).  Note that since we can assume A and B are disjoint, we can  
also assume A and B are NOT mutually recursive.  We can always find a  
way to break that mutual recursion up.


I'm not sure how to prove that A - B and B - A, as I defined them,  
are isomorphic.  But they are.  I guess we can re-interpret A and B as  
meet semi-lattices, and A - B and B - A as their products.

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


Re: [Haskell-cafe] Functional dependencies and Peano numbers

2010-07-09 Thread wren ng thornton

Brandon S Allbery KF8NH wrote:

On 7/6/10 15:37 , Oscar Finnsson wrote:

but can they also be on a form similar to


a b c d e f g h| b c - d e f | b d g - h

 (i.e. d,e,f are decided by the b,c-combination while h is decided by
the b,d,g-combination)?


I think the answer to this is yes, but if you have an MPTC with 8
parameters then you desperately need to refactor.


Yes, you can add multiple dependencies. The syntax is to use , after the 
first |.


While having eight parameters is surely a desperate need for 
refactoring, there are times when you'd want multiple dependencies. For 
example, you can say


class F a b | a - b, b - a where...

to express a bijective function on types (that is, for every pair of A 
and B, if you know one of them then you know what the other must be 
uniquely).


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Comments on Haskell 2010 Report

2010-07-09 Thread wren ng thornton

Julian Fleischer wrote:

Hi,


8. [...] Saying 0**0 is undefined seems reasonable,
but why 0**y?

I agree on 0**y being 0 (not undefined), but why should 0**0 be undefined? x**0 
:= 1, by convention.


I'm not familiar with that convention. So far as I'm aware, the x**0=1 
vs 0**y=0 conflict leads to 0**0 being best handled as undefined. That 
is, I've not seen any arguments supporting either solution as somehow 
more natural or more helpful in mathematics. /source-please


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Comments on Haskell 2010 Report

2010-07-09 Thread wren ng thornton

Christopher Done wrote:

On 10 July 2010 01:22, Ivan Lazar Miljenovic ivan.miljeno...@gmail.com wrote:

Brandon S Allbery KF8NH allb...@ece.cmu.edu writes:


On 7/8/10 22:25 , Alex Stangl wrote:

1. I.E. and e.g. should be followed by commas -- unless UK usage
differs from US standards. (Page 3 and elsewhere, although FFI chapter

I don't think I've ever seen them *followed* by commas.  Preceded,
always.



From The Haskell 98 Library Report:



 partition takes a predicate and a list and returns a pair of lists: those 
elements of the argument list that do and do not satisfy the predicate, 
respectively; i.e., [...]


I don't think you should bother nitpicking about commas here. As
Gregory said, anywhere there is i.e., you can substitute it for
that is. Consider if the spec. was written with that is instead of
i.e., would you then criticise where and where not commas are used?
Does this arbitrary prescription really matter?


This is LaTeX folks! All prescriptivism can be solved by judicious use 
of macros. Honestly, for dealing with all the different journals' style 
guides, stuff like this should be standard fare for mere punctuation 
differences:


\NeedsTeXFormat{LaTeX2e}
\ProvidesPackage{latin}[2010/07/09 resolve style disputes]
\RequirePackage{xspace}

\newif...@comma
\...@commatrue
\declareoption{comma...@commatrue}
\declareoption{nocomma...@commafalse}
\ProcessOptions

% According to most style guides we should not italicize common
% Latin, since it needlessly draws attention to unimportant text.
% For declarativity we specify this command so that clients can
% choose to italicize if desired.
\newcommand{\latin}[1]{#1}

\newcommand{\.}{% Or choose another name if you please
\...@comma
.,\xspace
\else
.\,
\fi
}

\newcommand{\Cf}{\latin{Cf}\.}
\newcommand{\cf}{\latin{cf}\.}
\newcommand{\Eg}{\latin{E.g}\.}
\newcommand{\eg}{\latin{e.g}\.}
\newcommand{\Ie}{\latin{I.e}\.}
\newcommand{\ie}{\latin{i.e}\.}

--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Fix plugins package.

2010-07-09 Thread Andy Stewart
Hi all,

I want to use *plugins* package
(http://hackage.haskell.org/package/plugins-1.4.1)

Unfortunately, it looks broken.
Anybody can fix it?

Thanks,

  -- Andy

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


Re: [Haskell-cafe] Fix plugins package.

2010-07-09 Thread Ivan Lazar Miljenovic
Andy Stewart lazycat.mana...@gmail.com writes:

 Hi all,

 I want to use *plugins* package
 (http://hackage.haskell.org/package/plugins-1.4.1)

 Unfortunately, it looks broken.
 Anybody can fix it?

Try putting an upper bound in the constraint for `base'; since there's
no upper bound, cabal-install defaults to  4, which conflicts with
plugins _needing_ base = 4.

The hint library might also do what you want:
http://hackage.haskell.org/package/hint

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


Re: [Haskell-cafe] bug in ghci ?

2010-07-09 Thread Kevin Quick

On Fri, 09 Jul 2010 18:57:34 -0700, Edward Kmett ekm...@gmail.com wrote:

I hope the above demonstrate that there are at least some fairly reasonable
(and, given your request, appropriately category theoretic!) examples where
one would want the ability to specify that there is more than one member of
a minimal mutual definition. =)


It does, thanks!  (And thanks as well to Alexander for the description of 
proofs).

This confirms Ivan's proposal a more general form allowing grouping () and 
exclusion (|) would be needed.  The question now is: is that enough and is this a 
useful approach to the problem that should be moved forward as a more formal 
suggestion?

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


Re: [Haskell-cafe] Fix plugins package.

2010-07-09 Thread Andy Stewart
Hi Ivan,

Ivan Lazar Miljenovic ivan.miljeno...@gmail.com writes:

 Andy Stewart lazycat.mana...@gmail.com writes:

 Hi all,

 I want to use *plugins* package
 (http://hackage.haskell.org/package/plugins-1.4.1)

 Unfortunately, it looks broken.
 Anybody can fix it?

 Try putting an upper bound in the constraint for `base'; since there's
 no upper bound, cabal-install defaults to  4, which conflicts with
 plugins _needing_ base = 4.
I think not just build-depend problem, something broken in plugins
source code, below is compile error:

-- error start --

src/System/Plugins/Process.hs:59:4:
Warning: A do-notation statement discarded a result of type 
GHC.Conc.ThreadId.
 Suppress this warning by saying _ - forkIO
 (()
E.evaluate (length 
errput)
return GHC.Unit.()),
 or by using the flag -fno-warn-unused-do-bind
[ 3 of 15] Compiling System.Plugins.Parser ( src/System/Plugins/Parser.hs, 
dist/build/System/Plugins/Parser.o )

src/System/Plugins/Parser.hs:31:0:
Warning: The import of `Data.Either' is redundant
   except perhaps to import instances from `Data.Either'
 To import instances alone, use: import Data.Either()
[ 4 of 15] Compiling System.Plugins.PackageAPI ( 
src/System/Plugins/PackageAPI.hs, dist/build/System/Plugins/PackageAPI.o )

src/System/Plugins/PackageAPI.hs:61:24: Not in scope: `package'

src/System/Plugins/PackageAPI.hs:62:25: Not in scope: `package'
...
-- error end   --


 The hint library might also do what you want:
 http://hackage.haskell.org/package/hint
Wow, i didn't know it.

Infact, i want implement a *fully* hot-swapping feature for Haskell 
application, not just
re-compile/re-load module in runtime like Yi/Xmonad, i have code do that.
I want to a Haskell interpreter to evaluation expression/module in
runtime, then application can develop itself in runtime, don't need
restart.

hint library looks interesting.

Thanks for hint link.

  -- Andy

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


[Haskell-cafe] Re: Fix plugins package.

2010-07-09 Thread Andy Stewart
Andy Stewart lazycat.mana...@gmail.com writes:

 Hi Ivan,

 Ivan Lazar Miljenovic ivan.miljeno...@gmail.com writes:

 Andy Stewart lazycat.mana...@gmail.com writes:

 Hi all,

 I want to use *plugins* package
 (http://hackage.haskell.org/package/plugins-1.4.1)

 Unfortunately, it looks broken.
 Anybody can fix it?

 Try putting an upper bound in the constraint for `base'; since there's
 no upper bound, cabal-install defaults to  4, which conflicts with
 plugins _needing_ base = 4.
 I think not just build-depend problem, something broken in plugins
 source code, below is compile error:

 
 src/System/Plugins/Process.hs:59:4:
 Warning: A do-notation statement discarded a result of type 
 GHC.Conc.ThreadId.
  Suppress this warning by saying _ - forkIO
  (()
 E.evaluate (length 
 errput)
 return GHC.Unit.()),
  or by using the flag -fno-warn-unused-do-bind
 [ 3 of 15] Compiling System.Plugins.Parser ( src/System/Plugins/Parser.hs,
 dist/build/System/Plugins/Parser.o )

 src/System/Plugins/Parser.hs:31:0:
 Warning: The import of `Data.Either' is redundant
except perhaps to import instances from `Data.Either'
  To import instances alone, use: import Data.Either()
 [ 4 of 15] Compiling System.Plugins.PackageAPI ( 
 src/System/Plugins/PackageAPI.hs,
 dist/build/System/Plugins/PackageAPI.o )

 src/System/Plugins/PackageAPI.hs:61:24: Not in scope: `package'

 src/System/Plugins/PackageAPI.hs:62:25: Not in scope: `package'
 ...
Looks plugins just work on base-4 and Cabal-1.6.
Anyone can fix it make it works with Cabal-1.8?

Thanks,

  -- Andy



 The hint library might also do what you want:
 http://hackage.haskell.org/package/hint
 Wow, i didn't know it.

 Infact, i want implement a *fully* hot-swapping feature for Haskell 
 application, not just
 re-compile/re-load module in runtime like Yi/Xmonad, i have code do that.
 I want to a Haskell interpreter to evaluation expression/module in
 runtime, then application can develop itself in runtime, don't need
 restart.

 hint library looks interesting.

 Thanks for hint link.

   -- Andy

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