Re: [Haskell-cafe] overloaded overloading?

2010-01-12 Thread Brad Larsen
Alberto,

On Tue, Jan 12, 2010 at 7:17 PM, Alberto G. Corona agocor...@gmail.com wrote:
 Hi,

 I sometimes strumble on the same quiestion that forces me to insert
 functions that process objects of a certain class inside their class
 definition.  This occurs when a computation uses the object internally,
 neiter as parameter or as a return value or in the case of existential
 types. An example of the first:


 class Example a where
     irec ::  IO a
     pr :: a →  IO String
     sample2 ::  a  →   IO ()
     sample2 _  =   do
   x ←  irec :: IO a
   pr x
   return ()

 sample :: Example a ⇒ a  →   IO ()
 sample _  =   do
   x ←  irec :: IO a
   pr x
   return ()


 With the flag -fglasgow-exts, the following error below appears in sample.
 without the flag, the error appears in both sample and sample2. I´m too lazy
 to find what concrete extension is involved and why, anyhow, in the case
 of sample, the compiler must generate a new type a1 with no context.

     Could not deduce (Example a1) from the context ()
   arising from a use of `irec' at Control\Workflow\Users.hs:73:7-10
     Possible fix:
   add (Example a1) to the context of an expression type signature
     In a stmt of a 'do' expression: x - irec :: IO a
     In the expression:
     do x - irec :: IO a
    pr x
    return ()

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

In the code for `sample', you give a type signature to x, `IO a'.
However, the `a' there is different from the `a' in the signature for
`sample'.

Perhaps ScopedTypeVariables
http://www.haskell.org/haskellwiki/ScopedTypeVariables will help?

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


Re: Re[6]: [Haskell-cafe] Boxed Mutable Arrays

2009-12-16 Thread Brad Larsen
On Wed, Dec 16, 2009 at 11:27 AM, Don Stewart d...@galois.com wrote:
[...]
 The bug described in Ticket #650, AFAICS, prevents implementation of a
 reasonable, generic hash table in Haskell.  :-(

 You can certainly implement it, it just requires that you increase the
 heap size to a bit bigger than your hash to reduce the pressure on the
 GC.

 But note, Simon's making progress,
    http://hackage.haskell.org/trac/ghc/ticket/650#comment:17

 -- Don

Nice!  Even if it is only an improvement in the constant factor, and
not a genuine fix for the problem, it sounds like a big improvement.

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


Re: Re[2]: [Haskell-cafe] Boxed Mutable Arrays

2009-12-15 Thread Brad Larsen
Bulat,

On Tue, Dec 15, 2009 at 1:51 AM, Bulat Ziganshin
bulat.zigans...@gmail.com wrote:
 Hello Brad,

 Tuesday, December 15, 2009, 1:55:41 AM, you wrote:

 How about a fast STHashTable?

 you can use array of arrays instead of large array

 --
 Best regards,
  Bulat                            mailto:bulat.zigans...@gmail.com



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


Re: Re[4]: [Haskell-cafe] Boxed Mutable Arrays

2009-12-15 Thread Brad Larsen
On Tue, Dec 15, 2009 at 11:00 AM, Bulat Ziganshin
bulat.zigans...@gmail.com wrote:
 Hello Brad,

 Tuesday, December 15, 2009, 6:53:14 PM, you wrote:

 How about a fast STHashTable?

 you can use array of arrays instead of large array

 Can you elaborate?

 what exactly? how to implement this or why it will be faster?



 --
 Best regards,
  Bulat                            mailto:bulat.zigans...@gmail.com



You said to use an array of arrays instead of a large array, in the
context of a fast hash table in ST.  Do you mean I should use an array
for hash buckets, rather than a list?

Is that what you meant?  And why would it be faster?

If the number of buckets was fixed, one could use an array of STRefs
to lists.  I believe this would avoid the bug from Ticket #650?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[6]: [Haskell-cafe] Boxed Mutable Arrays

2009-12-15 Thread Brad Larsen
On Tue, Dec 15, 2009 at 11:33 AM, Serguey Zefirov sergu...@gmail.com wrote:
 If the number of buckets was fixed, one could use an array of STRefs
 to lists.  I believe this would avoid the bug from Ticket #650?
 now i see what you mean. no, i mean trivial transformation. #650 says
 about slow GC. why it's slow? because once you made any update to the
 array, the entire array is marked as updated and scanned on next minor GC
 (which occurs after every 512 kbytes allocated, afaik). let's replace
 big array (say, of 10,000 elements) with array of 100 arrays of 100
 elements each. now, between minor GCs only some of arrays will be
 changed and entire amount of memory to be scanned will become less

 Data.IntMap?


I want to implement a more-or-less traditional, mutable, imperative
hash table in the ST monad.  Hence, I'm not considering Data.IntMap
and other persistent tree structures for its implementation, although
I have thought about it.

The bug described in Ticket #650, AFAICS, prevents implementation of a
reasonable, generic hash table in Haskell.  :-(
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Boxed Mutable Arrays

2009-12-15 Thread Brad Larsen
On Tue, Dec 15, 2009 at 12:00 PM, Gregory Collins
g...@gregorycollins.net wrote:
 Bulat Ziganshin bulat.zigans...@gmail.com writes:

 now i see what you mean. no, i mean trivial transformation. #650 says
 about slow GC. why it's slow? because once you made any update to the
 array, the entire array is marked as updated and scanned on next minor
 GC (which occurs after every 512 kbytes allocated, afaik). let's
 replace big array (say, of 10,000 elements) with array of 100 arrays
 of 100 elements each. now, between minor GCs only some of arrays will
 be changed and entire amount of memory to be scanned will become less

 I actually tried this, and modified Data.HashTable to use a two-tiered
 chunked dynamic array as you suggest. In some limited testing it was
 only about 5% faster, so I gave up on it -- you get some GC time back
 but you also pay a significant indirection penalty by adding an extra
 cache line miss for every operation.

 G
 --
 Gregory Collins g...@gregorycollins.net


Indeed!  A two-tiered implementation as Bulat describes is a big hack
anyway.  I don't want to have to dance around a bug!

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


Re: Re[6]: [Haskell-cafe] Boxed Mutable Arrays

2009-12-15 Thread Brad Larsen
Serguey,

On Tue, Dec 15, 2009 at 1:07 PM, Serguey Zefirov sergu...@gmail.com wrote:
 now i see what you mean. no, i mean trivial transformation. #650 says
 about slow GC. why it's slow? because once you made any update to the
 array, the entire array is marked as updated and scanned on next minor GC
 (which occurs after every 512 kbytes allocated, afaik). let's replace
 big array (say, of 10,000 elements) with array of 100 arrays of 100
 elements each. now, between minor GCs only some of arrays will be
 changed and entire amount of memory to be scanned will become less
 Data.IntMap?
 I want to implement a more-or-less traditional, mutable, imperative
 hash table in the ST monad.  Hence, I'm not considering Data.IntMap
 and other persistent tree structures for its implementation, although
 I have thought about it.
 The bug described in Ticket #650, AFAICS, prevents implementation of a
 reasonable, generic hash table in Haskell.  :-(

 Data.IntMap is just a limit of what Bulat suggested.

 So what was you thoughts about Data.IntMap in mutable hashmap?


I have considered using Data.IntMap to implement a sort of faux hash
table, e.g., introduce a Hashable class, and then use an IntMap to
lists of Hashable.  The result would be a pure, persistent ``hash
table''.  In such a case, however, lookup/insert/delete operations
would have average complexity logarithmic in the number of buckets.

Similarly, one could use an IntMap of STRefs to lists of items, but
that is bizarre.  If the number of buckets is fixed, it would be
better to use an immutable array of STRefs to lists.

One problem with using an IntMap of STRefs to lists or an immutable
array of STRefs to lists as part of a hash table implementation is
that you get an added indirection compared to a boxed STArray of
lists, which would be bad for performance.

To reiterate my desire:  I want an efficient, generic, mutable hash
table data structure for instances where one is already working in ST.
 This data structure should be written in regular Haskell, without
resorting to the FFI.  In cases where one is already writing code
using mutable state, a good hash table implementation could perform
better in terms of time  memory than IntMap, Map, etc.

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


[Haskell-cafe] Boxed Mutable Arrays

2009-12-14 Thread Brad Larsen
Is anyone working on fixing ticket #650
http://hackage.haskell.org/trac/ghc/ticket/650?  In short, STArray
and the garbage collector don't play well together, resulting in array
updates being non-constant time operations.  This bug makes it very
difficult/impossible to write efficient array algorithms that depend
upon mutation in Haskell.

On another note, does this (or perhaps better phrased, will this) bug
also affect Data Parallel Haskell?

I would really like to see highly efficient, mutable, boxed arrays in
Haskell!  Unfortunately, I don't have the know-how to fix Ticket 650.

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


Re: [Haskell-cafe] Boxed Mutable Arrays

2009-12-14 Thread Brad Larsen
Don,

On Mon, Dec 14, 2009 at 4:16 PM, Don Stewart d...@galois.com wrote:
 brad.larsen:
 Is anyone working on fixing ticket #650
 http://hackage.haskell.org/trac/ghc/ticket/650?  In short, STArray
 and the garbage collector don't play well together, resulting in array
 updates being non-constant time operations.  This bug makes it very
 difficult/impossible to write efficient array algorithms that depend
 upon mutation in Haskell.

 On another note, does this (or perhaps better phrased, will this) bug
 also affect Data Parallel Haskell?

 What are you using boxed arrays for?

Two immediate examples come to mind:  a generic, heap-based priority
queue using an array, or a generic hash table that has acceptable
performance.

 (DPH, vector, uvector, are all for unboxed arrays, which are not
 affected, obviously).

 -- Don

The vector package on haskell has boxed arrays.  Is DPH *really* only
for primitive, unboxed types?  If so, that's unfortunate.

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


Re: [Haskell-cafe] Boxed Mutable Arrays

2009-12-14 Thread Brad Larsen
On Mon, Dec 14, 2009 at 4:34 PM, Don Stewart d...@galois.com wrote:
 brad.larsen:
 The vector package on haskell has boxed arrays.  Is DPH *really* only
 for primitive, unboxed types?  If so, that's unfortunate.

 No, it's not only, but all the uses I've seen have been related to
 numerics, represented with unboxed types.

 I'm just curious if you have a current use case -- since that would help
 get interest in the ticket.

 -- Don


How about a fast STHashTable?  Or a fast priority queue in ST where
priorities are integers of a known size?  Such a priority queue can be
implemented as an array of sequences---int priority is array index.

I want to use such data structures for research in heuristic search
algorithms, to get top performance, more than from using an IntMap /
Map / whatever-other-persistent-data-structure.  I'm trying to at
least be ballpark competitive with C implementations of certain
heuristic search algorithms, which use the forbidden magic of mutable
data structures.

I'd prefer to work in Haskell rather than rewrite in C.  Right now, in
Haskell, it doesn't seem possible to write the kind of algorithms I am
working with, using high-performance mutable data structures, because
of the boxed array/GC bugs.

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


Re: [Haskell-cafe] Simple hash table creation

2009-11-17 Thread Brad Larsen
On Tue, Nov 17, 2009 at 4:00 PM, michael rice nowg...@yahoo.com wrote:

 Hi Gregory,

 I was wondering about that, because of the following:

 [1 of 1] Compiling Main ( hash1.hs, interpreted )
 Ok, modules loaded: Main.
 *Main ht - new (==) dummy :: IO MyHashTable
 *Main dummy mike
 7
 *Main dummy michael
 7
 *Main insert ht mike 1
 *Main toList ht
 [(mike,1)]
 *Main insert ht michael 2
 *Main toList ht
 [(michael,2),(mike,1)]
 *Main insert ht miguel 3
 *Main toList ht
 [(miguel,3),(michael,2),(mike,1)]
 *Main :t dummy miguel
 dummy miguel :: Int32
 *Main

 It seems my dummy function is being ignored. I figured I would only be able 
 to store a single value with a hash function that always returns 7. Why ask 
 for a hash function and not use it?
[...]

Most hash tables deal with collisions, i.e. the case when two keys
stored in the table hash to the same value.  In the case of your
'dummy' hash function, which always returns 7, every key hashes to the
same value, hence collisions galore.

One way to deal with collisions is to hash a key to a bucket (i.e.
list) of items, then walk down the list looking for the given key.  In
such an implementation (and I believe for hash tables in general), the
quality of the hash function greatly affects the performance of the
hash table operations.

I am not sure what implementation Data.HashTable uses.  However, I
believe Data.HashTable is not all that good:  for multi-million
element tables from Int to Int, Data.IntMap runs many times faster
than Data.HashTable.  I have no wish to start a flame war here (this
topic has in the past), but the state of affairs regarding hash tables
in Haskell is not good.

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


Re: [Haskell-cafe] Simple hash table creation

2009-11-17 Thread Brad Larsen
On Tue, Nov 17, 2009 at 4:22 PM, michael rice nowg...@yahoo.com wrote:

 So, what you're telling me is, my dummy hash function IS being used, and 
 because of collisions the other values are placed in different locations?

 Michael
[...]

If Data.HashTable is implemented using separate chaining, then all the
key/value pairs would be hashed to the same bucket (hash value 7).  If
a different scheme is used, then hash collisions would be resolved in
a different way, e.g., through linear probing.  Regardless of the
collision resolution scheme used, excessive hash collisions are bad,
and are what can cause the worst-case time complexity of hash table
operations (in most implementations) to be O(n).

The Wikipedia page on hash tables isn't bad:
http://en.wikipedia.org/wiki/Hash_table.

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


Re: [Haskell-cafe] help with Haskell performance

2009-11-10 Thread Brad Larsen
On Tue, Nov 10, 2009 at 8:20 PM, Gokul P. Nair gpnai...@yahoo.com wrote:

 --- On Sat, 11/7/09, Don Stewart d...@galois.com wrote:
  General notes:
 
   * unpack is almost always wrong.
   * list indexing with !! is almost always wrong.
   * words/lines are often wrong for parsing large files (they build large
 list structures).
   * toList/fromList probably aren't the best strategy
   * sortBy (comparing snd)
   * use insertWith'
  Spefically, avoid constructing intermediate lists, when you can process
 the
  entire file in a single pass. Use O(1) bytestring substring operations
 like
  take and drop.

 Thanks all for the valuable feedback. Switching from Regex.Posix to
 Regex.PCRE alone reduced the running time to about 6 secs and a few other
 optimizations suggested on this thread brought it down to about 5 secs ;)

 I then set out to profile the code out of curiosity to see where the bulk
 of the time was being spent and sure enough the culprit turned out to be
 unpack. My question therefore is, given a list L1 of type [(ByteString,
 Int)], how do I print it out so as to eliminate the chunk, empty markers
 associated with a bytestring? The suggestions posted here are along the
 lines of mapM_ print L1 but that's far from desirable especially because
 the generated output is for perusal by non-technical users etc.

 Thanks.


Take a look at Data.ByteString.Lazy.Char8.putStrLn.  That prints a lazy
ByteString without unpacking it, and without the internal markers.

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


Re: [Haskell-cafe] Type-level naturals multiplication

2009-10-13 Thread Brad Larsen
On Tue, Oct 13, 2009 at 3:37 AM, Simon Peyton-Jones
simo...@microsoft.com wrote:
[...]
 It's also worth noting that while undecidable instances sound scary, but 
 all it means is that the type checker can't prove that type inference will 
 terminate.  We accept this lack-of-guarantee for the programs we *run*, and 
 type inference can (worst case) take exponential time which is not so 
 different from failing to terminate; so risking non-termination in type 
 inference is arguably not so bad.

 Simon

Indeed!

On a related note, template instantiation in C++ is undecidable.  See
``C++ Templates are Turing Complete'' by Todd Veldhuizen:
http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.14.3670.
And similarly, heavy use of templates in C++ can be *extremely*
compute-intensive.

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


[Haskell-cafe] Exponential complexity of type checking (Was: Type-level naturals multiplication)

2009-10-13 Thread Brad Larsen
On Tue, Oct 13, 2009 at 3:37 AM, Simon Peyton-Jones
simo...@microsoft.com wrote:
 |  Is there any way to define type-level multiplication without requiring
 |  undecidable instances?
 |
 | No, not at the moment.  The reasons are explained in the paper Type
 | Checking with Open Type Functions (ICFP'08):
 |
 |    http://www.cse.unsw.edu.au/~chak/papers/tc-tfs.pdf
 |
 | We want to eventually add closed *type families* to the system (ie,
 | families where you can't add new instances in other modules).  For
 | such closed families, we should be able to admit more complex
 | instances without requiring undecidable instances.

 It's also worth noting that while undecidable instances sound scary, but 
 all it means is that the type checker can't prove that type inference will 
 terminate.  We accept this lack-of-guarantee for the programs we *run*, and 
 type inference can (worst case) take exponential time which is not so 
 different from failing to terminate; so risking non-termination in type 
 inference is arguably not so bad.

 Simon


I have written code that makes heavy use of multi-parameter type
classes in the ``finally tagless'' tradition, which takes several
seconds and many megabytes of memory for GHCI to infer its type.
However, that example is rather complicated, and I am not sure its
type inference complexity is exponential---it is at least very bad.

Are there any simple, well-known examples where Haskell type inference
has exponential complexity?  Or Hindley-Milner type inference, for
that matter?  (Haskell 98 is not quite Hindley-Milner?)

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


Re: [Haskell-cafe] Exponential complexity of type checking (Was: Type-level naturals multiplication)

2009-10-13 Thread Brad Larsen
On Tue, Oct 13, 2009 at 12:32 PM, Serguey Zefirov sergu...@gmail.com wrote:
 2009/10/13 Lennart Augustsson lenn...@augustsson.net:
 Yes, there are simple H-M examples that are exponential.
 x0 = undefined
 x1 = (x1,x1)
 x2 = (x2,x2)
 x3 = (x3,x3)
 ...

 xn will have a type with 2^n type variables so it has size 2^n.

 Reformulated:
 let dup x = (x,x)
 :t dup . dup . dup . dup ...

 type will be 2^(number of dup's).

 I experimented and found that GHC can stand pretty long line of dup's.
 More than 20, at least.

 One part of our program took too much time to typecheck some time ago.
 3 and half minutes for ~900 lines module. Most of operations was
 inside heavily parametrized monad (5 parameters, each is a Peano
 number). Then my colleague moved parameters into associated types of
 relevant type class and now it typechecks in ten seconds.


Good example!  I have a feeling that the `dup' example is a bit
contrived, not something that one would be likely to find in the wild.

Heavily parameterized type classes, on the other hand, are more common
in real code.  Hence, that is more likely where someone would run into
really awful type inference performance without expecting it.

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


[Haskell-cafe] Type-level naturals multiplication

2009-10-10 Thread Brad Larsen
Suppose we implement type-level naturals as so:

data Zero
data Succ a

Then, we can reflect the type-level naturals into a GADT as so (not
sure if ``reflect'' is the right terminology here):

data Nat :: * - * where
  Zero :: Nat Zero
  Succ :: Nat a - Nat (Succ a)

Using type families, we can then proceed to define type-level addition:

type family Add a b :: *
type instance Add Zero b = b
type instance Add (Succ a) b = Succ (Add a b)

Is there any way to define type-level multiplication without requiring
undecidable instances?

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


Re: [Haskell-cafe] Re: Libraries for Commercial Users

2009-10-10 Thread Brad Larsen
On Sat, Oct 10, 2009 at 5:11 PM, Don Stewart d...@galois.com wrote:
 brad.larsen:
 John,

 On Thu, Oct 8, 2009 at 3:20 PM, John A. De Goes j...@n-brain.net wrote:
 [...]
  JVM is cross-platform, and contains sufficient typing information to
  permit one to write something like, import foreign jvm
  java.list.Collection, and have typed access to the whole class and all of
  its methods.
 [...]

 Having painless Haskell - Java interoperability would be great.  I'm
 curious though:  could it really be so simple as a one-line ``import
 foreign jvm'' directive?  I imagine the purity mismatch between
 Haskell and Java would be very troublesome.

 No more so than C, surely. We're used to stateful APIs. They're a pain.
[...]

The use of foreign C libraries in Haskell is typically done through
definition of lots of boilerplate code, putting a safe, workable
Haskell veneer over the library.  Right?

I got the impression (perhaps wrongly) that John was suggesting a
simple one-line ``import foreign jvm LIBRARY'' directive to let you
use LIBRARY without writing all that boilerplate.  Which would be very
convenient, but is rather different than the situation with C
libraries.

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


Re: [Haskell-cafe] Num instances for 2-dimensional types

2009-10-05 Thread Brad Larsen
On Mon, Oct 5, 2009 at 10:36 AM, Miguel Mitrofanov
miguelim...@yandex.ru wrote:
[...]
 Of course, it's OK to call anything numbers provided that you stated
 explicitly what exactly you would mean by that. But then you have to drop
 all kind of stuff mathematicians developed for the usual notion of numbers.
 In the same way, you shouldn't use the Num class for your numbers.

 On the other hand, people can (ab)use the Num class as they wish, and it's
 their business until they ask a question about it somewhere outside - which
 makes the business not only theirs.
[...]

The Num class has `negate' as part of its definition.  Natural numbers
are numbers, but I don't believe there is any sensible definition of
`negate' for them.

Haskell 98's numeric hierarchy combines many operations which should
be separate.  As further evidence, every bit of Haskell I have seen
that does symbolic manipulation of numeric expressions either leaves
out instances that would make the syntax more convenient, or else
defines partial instances because certain class functions have no
sensible definition for symbolic expressions.

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


Re: [Haskell-cafe] Cal, Clojure, Groovy, Haskell, OCaml, etc.

2009-09-29 Thread Brad Larsen
Don,

On Mon, Sep 28, 2009 at 11:52 PM, Don Stewart d...@galois.com wrote:
 brad.larsen:
 On Mon, Sep 28, 2009 at 11:11 PM, Hong Yang hyang...@gmail.com wrote:
 [...]
  Maybe later on we can add an Example section to Description, Synopsis, and
  Documentation sections produced by Haddock.
 
  Also, having a section for comments is helpful. This is the case especially
  when there are several similar packages coexisting, comments can help 
  people
  choose which one to use.
 
  Thanks,
 
  Hong
 [...]

 +1

 I'd like to see people writing comparative reviews of libraries in each
 category, and publishing those reviews online.

 -- Don

If there were a comments section for the packages on Hackage, it would
lower the barrier to entry for writing such comparisons. :-)

It takes a good chunk of time to write up a detailed, informative blog
post, with performance measurements, etc. for competing packages.
Many people do not have the time to do an in-depth review of a
package; I am grateful when people do take the time to such reviews.
If there were a comments or review section on Hackage (a la CPAN), I
imagine that more people would provide feedback.

Another issue with the published package comparisons is an indexing
problem.  At present, the only way for potential users of a package to
find reviews is through actively searching for them via Google or
asking other Haskellers.  With a comments area for a package, one
could link to an off-site, in-depth review.

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


Re: [Haskell-cafe] Cal, Clojure, Groovy, Haskell, OCaml, etc.

2009-09-28 Thread Brad Larsen
On Mon, Sep 28, 2009 at 11:11 PM, Hong Yang hyang...@gmail.com wrote:
[...]
 Maybe later on we can add an Example section to Description, Synopsis, and
 Documentation sections produced by Haddock.

 Also, having a section for comments is helpful. This is the case especially
 when there are several similar packages coexisting, comments can help people
 choose which one to use.

 Thanks,

 Hong
[...]

+1

I'd love to see more examples in the Haddock documentation for packages.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] A proposals

2009-09-27 Thread Brad Larsen
On Sun, Sep 27, 2009 at 5:29 PM, Louis Wasserman
wasserman.lo...@gmail.com wrote:
 I'd like to see something resembling as-patterns in type signatures.
 Specifically, there are cases where I'm inclined to use
 (m ~ pat) in a type context when m isn't otherwise constrained, just so I
 can use m as an abbreviation for pat.  To reduce these cases, I'd like to
 see the syntax m...@pat allowed for use in type signatures, with m becoming
 simply an alias for pat.  Thoughts?

 I've added a ticket here.

 Louis Wasserman
 wasserman.lo...@gmail.com
 http://profiles.google.com/wasserman.louis

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


I was looking for a feature like this just the other day, for more
succinctly defining a type class that made use of several associated
type synonyms.

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


Re: [Haskell-cafe] An issue with EDSLs in the ``finally tagless'' tradition

2009-09-26 Thread Brad Larsen
Edward,

On Sat, Sep 26, 2009 at 11:41 AM, Edward Kmett ekm...@gmail.com wrote:
 I would just like to add that Oleg and Chung-chieh made sure in their
 finally tagless paper to use monomorphic lifting of literals explicitly to
 avoid this sort of ambiguity. Using Num or another typeclass is fine as long
 as all you want to do is evaluate your EDSL. But what about partial
 evaluation? CPS transformation? Compilation? You might be able to muddle
 through the first two, but compilation will derail your solution. Ultimately
 you will not be able to work over arbitrary Num instances if you want to do
 more than interpret. That was the main point of the monomorphic int :: Int
 - r Int, char :: Char - r Char methods they were using. If all I know
 about something is that there is a valid Num instance for it I have no way
 to emit machine code for it.
 -Edward
[...]

If thye type parameter is present in the class head, you can put
constraints on it in your instances.  E.g.,

class ENum repr a where
  constant :: a - repr a
  add :: repr a - repr a - repr a

newtype E a = E { unE :: a }

instance (Num a) = ENum E a where
  constant = E

Similarly to the ENum instance for an evaluator, E, you could define a
type class for code gen:

data UntypedIntermediate = ConstInt Int | ConstFloat Float | Add
Intermediate Intermediate

class Emittable a where
  emit :: a - UntypedIntermediate

instance Emittable Int where
  emit i = ConstInt i

instance Emittable Float where
  emit f = ConstFloat f

Then, you could do compilation, given an Emittable constraint:

newtype C a = C { unC :: UntypedIntermediate }

instance (Emittable a) = ENum C a where
  constant e = C $ emit $ unC e
  add e1 e2 = C $ Add (emit $ unC e1) (emit $ unC e2)


I think that by using the strategy of lifting type parameters into
class head, and by defining the type classes  instances you need for
a certain interpretation, you can modularly define tagless EDSLs, i.e.
define the language once, as a collection of typeclasses, and then be
able to define arbitrary interpretations of that EDSL, in separate
modules, without having to modify the EDSL type classes.

(Note:  I haven't tried running the above code.)

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


[Haskell-cafe] Re: Beginning of a meta-Haskell [was: An issue with the ``finally tagless'' tradition]

2009-09-25 Thread Brad Larsen
Oleg,

On Thu, Sep 24, 2009 at 1:54 AM,  o...@okmij.org wrote:

 The topic of an extensible, modular interpreter in the tagless final
 style has come up before. A bit more than a year ago, on a flight from
 Frankfurt to San Francisco I wrote two interpreters for a trivial
 subset of Haskell or ML (PCF actually), just big enough for Power,
 Fibonacci and other classic functions. The following code is a
 fragment of meta-Haskell. It defines the object language and two
 interpreters: one is the typed meta-circular interpreter, and the
 other is a non-too-pretty printer. We can write the expression once:

 power =
   fix $ \self -
   lam $ \x - lam $ \n -
     if_ (n = 0) 1
         (x * ((self $$ x) $$ (n - 1)))

 and interpret it several times, as an integer

 -- testpw :: Int
 testpw = (unR power) (unR 2) ((unR 7)::Int)
 -- 128

 or as a string

 -- testpwc :: P.String
 testpwc = showQC power

 {-
  (let self0 = (\\t1 - (\\t2 - (if (t2 = 0) then 1 else (t1 * ((self0  t1) 
  (t2 - 1)) in self0)
 -}

 The code follows. It is essentially Haskell98, with the exception of
 multi-parameter type classes (but no functional dependencies, let
 alone overlapping instances).

 {-# LANGUAGE NoMonomorphismRestriction, NoImplicitPrelude #-}
 {-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-}

 -- A trivial introduction to `meta-Haskell', just enough to give a taste
 -- Please see the tests at the end of the file

 module Intro where

 import qualified Prelude as P
 import Prelude (Monad(..), (.), putStrLn, IO, Integer, Int, ($), (++),
                (=), Bool(..))
 import Control.Monad (ap)
 import qualified Control.Monad.State as S

 -- Definition of our object language
 -- Unlike that in the tagless final paper, the definition here is spread
 -- across several type classes for modularity

 class QNum repr a where
    (+) :: repr a - repr a - repr a
    (-) :: repr a - repr a - repr a
    (*) :: repr a - repr a - repr a
    negate :: repr a - repr a
    fromInteger :: Integer - repr a
 infixl 6 +, -
 infixl 7 *

 class QBool repr where
    true, false :: repr Bool
    if_ :: repr Bool - repr w - repr w - repr w

 class QBool repr = QLeq repr a where
    (=) :: repr a - repr a - repr Bool
 infix 4 =

 -- Higher-order fragment of the language

 class QHO repr  where
    lam  :: (repr a - repr r) - repr (a - r)
    ($$) :: repr (a - r) - (repr a - repr r)
    fix  :: (repr a - repr a) - repr a
 infixr 0 $$

 -- The first interpreter R -- which embeds the object language in
 -- Haskell. It is a meta-circular interpreter, and so is trivial.
 -- It still could be useful if we wish just to see the result
 -- of our expressions, quickly
 newtype R a = R{unR :: a}

 instance P.Num a = QNum R a where
    R x + R y = R $ x P.+ y
    R x - R y = R $ x P.- y
    R x * R y = R $ x P.* y
    negate      = R . P.negate . unR
    fromInteger = R . P.fromInteger

 instance QBool R where
    true  = R True
    false = R False
    if_ (R True)  x y = x
    if_ (R False) x y = y

 instance QLeq R Int where
    R x = R y = R $ x P.= y

 instance QHO R where
    lam f      = R $ unR . f . R
    R f $$ R x = R $ f x
    fix f      = f (fix f)

 -- The second interpreter: pretty-printer
 -- Actually, it is not pretty, but sufficient

 newtype S a = S{unS :: S.State Int P.String}

 instance QNum S a where
    S x + S y = S $ app_infix + x y
    S x - S y = S $ app_infix - x y
    S x * S y = S $ app_infix * x y
    negate (S x) = S $ (return $ \xc - (negate  ++ xc ++ )) `ap` x
    fromInteger = S . return . P.show

 app_infix op x y = do
  xc - x
  yc - y
  return $ ( ++ xc ++   ++ op ++   ++ yc ++ )

 instance QBool S where
    true  = S $ return True
    false = S $ return False
    if_ (S b) (S x) (S y) = S $ do
                                bc - b
                                xc - x
                                yc - y
                                return $ (if  ++ bc ++  then  ++ xc ++
                                          else  ++ yc ++ )
 instance QLeq S a where
    S x = S y = S $ app_infix = x y

 newName stem = do
  cnt - S.get
  S.put (P.succ cnt)
  return $ stem ++ P.show cnt

 instance QHO S where
  S x $$ S y = S $ app_infix  x y

  lam f = S $ do
             name - newName t
             let xc = name
             bc - unS . f . S $ return xc
             return $ (\\ ++ xc ++  -  ++ bc ++ )

  fix f = S $ do
             self - newName self
             let sc = self
             bc - unS . f . S $ return sc
             return $ (let  ++ self ++  =  ++ bc ++  in  ++ sc ++ )

 showQC :: S a - P.String
 showQC (S m) = S.evalState m (unR 0)

 -- 
 --   Tests

 -- Perhaps the first test should be the power function...
 -- The following code can be interpreted and compiled just as it is...

 power =
  fix $ \self -
  lam $ \x - lam $ \n -
    if_ (n = 0) 1
        (x * ((self $$ x) $$ (n - 1)))

 -- The interpreted result
 -- testpw :: 

Re: [Haskell-cafe] An issue with EDSLs in the ``finally tagless'' tradition

2009-09-24 Thread Brad Larsen
The modularity problem I speak of is that to add a new interpretation of the
DSL, I will likely have to modify the EDSL definition to add additional
constraints.  Ideally, I would like to be able to define the EDSL once, in a
module, and be able to write arbitrary interpretations of it in other
modules, without having to go back and change the EDSL definition.

Regards,
Bradford Larsen

On Sep 24, 2009 2:15 AM, Luke Palmer lrpal...@gmail.com wrote:

On Wed, Sep 23, 2009 at 10:24 PM, Brad Larsen brad.lar...@gmail.com wrote:
 On Wed, Sep 23, 2009 ...

 I would like to see an example of this unmodularity, making use of the 
polymorphism, so I can ...
 [...]

  A simple test case, combining boolean expressions and arithmetic
expressions:  test1 = con...
Looks great!  So, where is the modularity problem?

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


Re: [Haskell-cafe] An issue with EDSLs in the ``finally tagless'' tradition

2009-09-24 Thread Brad Larsen
Bruno,

On Thu, Sep 24, 2009 at 1:20 AM, Bruno Oliveira br...@ropas.snu.ac.kr wrote:
 Hello Brad,

 I believe that the problem you encountered is not quite the expression
 problem (which is about adding new constructors and functions modularly),
 but rather about refining *existing* constructs with more specific types.
 One could argue that they are related though but, for your own sake, you may
 want to use a term that more directly points to the problem in question.
[...]

Indeed, for finding existing approaches to this problem, it is prudent
to know what others refer to it as.  If you squint a little, this
looks like an instance of the expression problem: type classes are
(families of) constructors, and instances of those type classes (i.e.,
interpretations) are functions on those constructors.


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


Re: [Haskell-cafe] An issue with EDSLs in the ``finally tagless'' tradition

2009-09-24 Thread Brad Larsen
Wren,

On Thu, Sep 24, 2009 at 8:36 PM, wren ng thornton w...@freegeek.org wrote:
 Brad Larsen wrote:

 The modularity problem I speak of is that to add a new interpretation of
 the
 DSL, I will likely have to modify the EDSL definition to add additional
 constraints.  Ideally, I would like to be able to define the EDSL once, in
 a
 module, and be able to write arbitrary interpretations of it in other
 modules, without having to go back and change the EDSL definition.

 The canonical, if theoretically unsatisfying, way to do this is to lift all
 type variables into the class specification. Thus, instead of

class Foo f where
foo :: forall a. a - f a

 we would instead have

class Foo f a where
foo :: a - f a

 According to the intention of the design, variables thus lifted should
 remain polymorphic in instances however they can have contexts applied to
 them:

instance (Num a) = Foo F a where
foo = ...

 The reason this is unsatisfying is that there's no way to enforce that
 instances don't ground these variables, which can interfere with the
 validity of applying certain laws/transformations. Also, if you need to lift
 more than one variable in the same class then it can be tricky to do the
 encoding right. For instance, when converting Monad into this form (e.g. so
 we can define an instance for Set) it is prudent to separate it into one
 class for return and another for join/(=)/(). But it does solve the
 problem at hand.

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


I have experimented some in the past day with this canonical technique
of lifting type variables into the class specification.  This is
somewhat successful; however, one problem is that when multiple
variables are lifted into the specification, ambiguity creeps in (and
over-generality?), in the absence of superclass constraints or
functional dependencies.

So, for example, Foo seems to work well, but Bar does not:

class Foo a where
...

class Bar a b where
...

One can alleviate the ambiguity of Bar by splitting it into two
classes, similarly to splitting up Monad:

class PreBar a where
...

class (PreBar a) = Bar a b where
...

It's not clear to me that such a decomposition is always possible.
I'll keep experimenting with modular, tagless EDSLs...

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


[Haskell-cafe] An issue with EDSLs in the ``finally tagless'' tradition

2009-09-23 Thread Brad Larsen
I seem to have run into an instance of the expression problem [1], or
something very similar, when experimenting with ``finally tagless''
EDSLs, and don't see a good way to work around it.

I have been experimenting with embedded DSLs, using the techniques
described in a couple recent papers [2,3].  The idea is this:
implement an embedded DSL using type classes, rather than ADTs or
GADTs.  This allows one to define analyses, queries, and manipulations
of EDSL programs independently, as class instances.  Furthermore, by
using type classes rather than data types, there is no interpretive
overhead in the analyses, queries, and manipulations on the EDSL
programs.  Finally, using type classes permits greater modularity, as
an EDSL can be defined as the combination of several simpler EDSLs
[3].

Suppose we have a type class for simple integer arithmetic expressions:

 class IntArithExpr exp where
   integer :: Integer - exp Integer
   add :: exp Integer - exp Integer - exp Integer

We can write an evaluator for these expressions like this:

 newtype E a = E { eval :: a }

 instance IntArithExpr E where
   integer   = E
   add e1 e2 = E (eval e1 + eval e2)

 -- eval $ add (integer 20) (integer 22) == 42

The trouble comes in when defining a more general arithmetic
expression type class.  Suppose we want polymorphic arithmetic
expressions:

 class PolyArithExpr exp where
   constant :: a - exp a
   addP :: exp a - exp a - exp a

We then try to define an evaluator:

 -- instance PolyArithExpr E where
 --   constant   = E
 --   addP e1 e2 = E (eval e1 + eval e2)  -- bzzt!

The instance definition for `addP' is not type correct:
Could not deduce (Num a) from the context ()
  arising from a use of `+' at /home/blarsen/mail.lhs:42:20-36

One way to remedy this is to change the class definition of
PolyArithExpr so that `addP' has a Num constraint on `a':

 class PolyArithExprFixed exp where
   pae_constant :: a - exp a
   pae_add  :: Num a = exp a - exp a - exp a

which allows us to define an evaluator:

 instance PolyArithExprFixed E where
   pae_constant = E
   pae_add e1 e2 = E (eval e1 + eval e2)

I find this ``fix'' lacking, however: to define a new interpretation
of the EDSL, we may be forced to change the DSL definition.  This is
non-modular, and seems like an instance of the expression
problem. (There may be a multiparameter type class solution for this.)

How can one define the polymorphic arithmetic EDSL without cluttering
up the class definitions with interpretation-specific constraints, and
still write the desired interpretations?


Sincerely,
Bradford Larsen



References:

  [1] Philip Wadler.  The Expression Problem.  November 12, 1998.
  http://www.daimi.au.dk/~madst/tool/papers/expression.txt.

  [2] Jacques Carette, Oleg Kiselyov, and Chung-chieh Shan.  Finally
  Tagless, Partially Evaluated: Tagless Staged Interpreters for
  Simpler Typed Languages.  APLAS 2007.

  [3] Robert Atkey, Sam Lindley, and Jeremy Yallop.  Unembedding
  Domain-Specific Languages.  ICFP Haskell Symposium 2009.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] An issue with EDSLs in the ``finally tagless'' tradition

2009-09-23 Thread Brad Larsen
Luke,

On Wed, Sep 23, 2009 at 11:12 PM, Luke Palmer lrpal...@gmail.com wrote:
 On Wed, Sep 23, 2009 at 7:59 PM, Brad Larsen brad.lar...@gmail.com wrote:
 The trouble comes in when defining a more general arithmetic
 expression type class.  Suppose we want polymorphic arithmetic
 expressions:

 class PolyArithExpr exp where
   constant :: a - exp a
   addP :: exp a - exp a - exp a

 We then try to define an evaluator:

 -- instance PolyArithExpr E where
 --   constant   = E
 --   addP e1 e2 = E (eval e1 + eval e2)  -- bzzt!

 The instance definition for `addP' is not type correct:
Could not deduce (Num a) from the context ()
  arising from a use of `+' at /home/blarsen/mail.lhs:42:20-36

 One way to remedy this is to change the class definition of
 PolyArithExpr so that `addP' has a Num constraint on `a':

 class PolyArithExprFixed exp where
   pae_constant :: a - exp a
   pae_add  :: Num a = exp a - exp a - exp a

 which allows us to define an evaluator:

 instance PolyArithExprFixed E where
   pae_constant = E
   pae_add e1 e2 = E (eval e1 + eval e2)

 I find this ``fix'' lacking, however: to define a new interpretation
 of the EDSL, we may be forced to change the DSL definition.  This is
 non-modular, and seems like an instance of the expression
 problem. (There may be a multiparameter type class solution for this.)

 I don't know what you expect from pae_add, such that it could add a
 couple of a's without knowing anything about them.  Don't think of Num
 as a implementation detail, think of it as information about that a.
 An implementation which adds another typeclass constraint is requiring
 too much information, and either the implementation is undefinable
 (that happens, but it's always for a good reason), or the interface is
 weaker than you wrote.

 I don't know what kind of implementation would add another constraint
 on a.  Are you referring maybe to a specialized interpreter for
 Integer math?  Well, if this is truly a polymorphic type that needs a
 constructor class, there could be some non-Integer math in the middle
 somewhere, and your interpreter would be incorrect.

 I would like to see an example of this unmodularity, making use of the
 polymorphism, so I can understand what you're asking better.

 Luke


The idea with these type classes is that an EDSL can be defined,
separately from any interpretation of its programs.

Instead of evaluating an EDSL program, suppose you want to
pretty-print it, using some pretty-printing type class, along the
lines of this:

import Text.PrettyPrint

class PrettyPrintable a where
  pretty :: a - Doc

newtype P = P { unP :: Doc }

instance PolyArithExpr P where
  constant  = P . pretty-- bzzt!
Cannot deduce (PrettyPrintable a)
  add e1 e2 = P (pretty e1 + text + + pretty e2)  -- bzzt!
Cannot deduce (PrettyPrintable a)

To write a pretty-printing interpretation for polymorphic arithmetic
expressions, we do not need a Num constraint, but we do need a
PrettyPrintable constraint.  So, we might ``remedy'' the definition of
PolyArithExpr so that we could write the evaluator and pretty-printer:

class PolyArithExprFixedAgain exp where
  constant_fixed_again :: (Num a, PrettyPrintable a) = a - exp a
  add_fixed_again  :: (Num a, PrettyPrintable a) = a - exp a

Similarly, if we wanted to marshall an EDSL program over the network
or to disk, we would have to modify PolyArithExprFixedAgain to add
another constraint.  Such modification would be necessary for other
interesting interpretations, such as compilation to native code.

Perhaps the problem I have encountered is more clear now.  With my
current approach, the EDSL ``language definition'' and interpretations
of EDSL programs are intertwined.  Hence, this is a close relative of
the ``expression problem''.  I want language definition and language
interpretations to be decoupled.


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


Re: [Haskell-cafe] An issue with EDSLs in the ``finally tagless'' tradition

2009-09-23 Thread Brad Larsen
Luke,

On Wed, Sep 23, 2009 at 11:12 PM, Luke Palmer lrpal...@gmail.com wrote:
 On Wed, Sep 23, 2009 at 7:59 PM, Brad Larsen brad.lar...@gmail.com wrote:
 The trouble comes in when defining a more general arithmetic
 expression type class.  Suppose we want polymorphic arithmetic
 expressions:

 class PolyArithExpr exp where
   constant :: a - exp a
   addP :: exp a - exp a - exp a

 We then try to define an evaluator:

 -- instance PolyArithExpr E where
 --   constant   = E
 --   addP e1 e2 = E (eval e1 + eval e2)  -- bzzt!

 The instance definition for `addP' is not type correct:
Could not deduce (Num a) from the context ()
  arising from a use of `+' at /home/blarsen/mail.lhs:42:20-36

 One way to remedy this is to change the class definition of
 PolyArithExpr so that `addP' has a Num constraint on `a':

 class PolyArithExprFixed exp where
   pae_constant :: a - exp a
   pae_add  :: Num a = exp a - exp a - exp a

 which allows us to define an evaluator:

 instance PolyArithExprFixed E where
   pae_constant = E
   pae_add e1 e2 = E (eval e1 + eval e2)

 I find this ``fix'' lacking, however: to define a new interpretation
 of the EDSL, we may be forced to change the DSL definition.  This is
 non-modular, and seems like an instance of the expression
 problem. (There may be a multiparameter type class solution for this.)

 I don't know what you expect from pae_add, such that it could add a
 couple of a's without knowing anything about them.  Don't think of Num
 as a implementation detail, think of it as information about that a.
 An implementation which adds another typeclass constraint is requiring
 too much information, and either the implementation is undefinable
 (that happens, but it's always for a good reason), or the interface is
 weaker than you wrote.

 I don't know what kind of implementation would add another constraint
 on a.  Are you referring maybe to a specialized interpreter for
 Integer math?  Well, if this is truly a polymorphic type that needs a
 constructor class, there could be some non-Integer math in the middle
 somewhere, and your interpreter would be incorrect.

 I would like to see an example of this unmodularity, making use of the
 polymorphism, so I can understand what you're asking better.

 Luke



To elaborate a point I mentioned in my original email, and discussed
in ``Unembedding Domain-Specific Languages'' by Atkey, Lindley, and
Yallop: EDSLs defined using type classes in this way can be freely
combined, and so you can cobble together an EDSL from several smaller EDSLs.

For example, we can define an EDSL for boolean expressions:

class BooleanExpr exp where
  true  :: exp Bool
  false :: exp Bool
  cond  :: exp Bool - exp a - exp a - exp a
  (*) :: exp Bool - exp Bool - exp Bool
  (||*) :: exp Bool - exp Bool - exp Bool

  infixr 3 (*)
  infixr 2 (||*)

Then, combined with PolyArithExprFixed, we can define an EDSL
supporting polymorphic arithmetic and boolean expressions, as well as
an evaluator for this language.  (I've repeated the PolyArithExprFixed
and previous evaluator stuff for reference.)

class PolyArithExprFixed exp where
  pae_constant :: a - exp a
  pae_add  :: Num a = exp a - exp a - exp a

class (BooleanExpr exp, PolyArithExprFixed exp) = BoolArithExpr exp

-- a well-typed evaluator
newtype E a = E { unE :: a }

instance BooleanExpr E where
  true   = E True
  false  = E False
  cond p t f = if unE p then t else f
  e1 * e2  = E (unE e1  unE e2)
  e1 ||* e2  = E (unE e1 || unE e2)

instance PolyArithExprFixed E where
  pae_constant  = E
  pae_add e1 e2 = E (unE e1 + unE e2)


A simple test case, combining boolean expressions and arithmetic expressions:

test1 = cond (true * false)
 (pae_constant 0)
 (pae_add (pae_constant 22) (pae_constant 20))
-- unE test1 === 42


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


Re: [Haskell-cafe] An issue with EDSLs in the ``finally tagless'' tradition

2009-09-23 Thread Brad Larsen
Peter,

On Thu, Sep 24, 2009 at 12:22 AM, Peter Gammie pete...@gmail.com wrote:
[...]

 Ambiguity is IMHO best handled with a judicious application of type (or
 data) families, but you can get surprisingly far by simply requiring that
 every class member mention all type variables in the class head. YMMV of
 course.

 cheers
 peter

Can you say more about the use of type/data families?

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


Re: [Haskell-cafe] Re: cabal: : openFile: does not exist (No such file or directory)

2009-09-02 Thread Brad Larsen
I had the same issue, using the ghc 6.10.4 generic linux tarball on Ubuntu
Jaunty x86_64.  I attempted to install a newer Haskell Platform over the
older one.

I'm not sure what causes the issue.  After several attempts to remedy it
without success, I ended up completely reinstalling ghc and ghc-related
things on my system, and not using the Haskell Platform.  Drastic, but I
don't get those cabal errors any more.

Regards,
Bradford Larsen

On Aug 31, 2009 2:43 PM, Fernando Henrique Sanches 
fernandohsanc...@gmail.com wrote:

Sorry for ressurecting the thread, my I'm having the same problem here.

Deleting the .cabal/config file shows only temporary results, and -v3 isn't
helping:

~/sources/haskell-platform-2009.2.0.2 % cabal update
Config file /home/fernando/.cabal/config not found.
Writing default configuration to /home/fernando/.cabal/config
Downloading the latest package list from hackage.haskell.org
~/sources/haskell-platform-2009.2.0.2 % cabal update

cabal: :: openFile: does not exist (No such file or directory)
~/sources/haskell-platform-2009.2.0.2 % cabal update -v3

cabal: ?: openFile: does not exist (No such file or directory)
I'm on Ubuntu 9.04 x64. ghc 6.10.4

This is the output of the mentioned describe-parsec command, but I don't
know what to do with it:

~/sources/haskell-platform-2009.2.0.2 % ghc-pkg describe parsec-2.1.0.1
name: parsec
version: 2.1.0.1
license: BSD3
copyright:
maintainer: Daan Leijen d...@cs.uu.nl
stability:
homepage: http://www.cs.uu.nl/~daan/parsec.html
package-url:
description: Parsec is designed from scratch as an industrial-strength
parser
 library.  It is simple, safe, well documented (on the package
 homepage), has extensive libraries and good error messages,
 and is also fast.
category: Parsing
author: Daan Leijen d...@cs.uu.nl
exposed: True
exposed-modules: Text.ParserCombinators.Parsec.Language
 Text.ParserCombinators.Parsec.Token
 Text.ParserCombinators.Parsec.Error
 Text.ParserCombinators.Parsec.Char
 Text.ParserCombinators.Parsec.Combinator
 Text.ParserCombinators.Parsec.Expr
 Text.ParserCombinators.Parsec.Perm
 Text.ParserCombinators.Parsec.Pos
 Text.ParserCombinators.Parsec.Prim
Text.ParserCombinators.Parsec
hidden-modules:
import-dirs: /usr/local/lib/parsec-2.1.0.1/ghc-6.10.4
library-dirs: /usr/local/lib/parsec-2.1.0.1/ghc-6.10.4
hs-libraries: HSparsec-2.1.0.1
extra-libraries:
extra-ghci-libraries:
include-dirs:
includes:
depends: base-4.1.0.0
hugs-options:
cc-options:
ld-options:
framework-dirs:
frameworks:
haddock-interfaces: /usr/local/share/doc/parsec-2.1.0.1/html/parsec.haddock
haddock-html: /usr/local/share/doc/parsec-2.1.0.1/html


Fernando Henrique Sanches

On Thu, Jul 30, 2009 at 7:52 AM, Mike Pentney mike.pent...@physics.org
wrote:   I had a simil...

___
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] Haskell as a religion

2008-12-18 Thread Brad Larsen
On Thu, 18 Dec 2008 11:27:14 -0500, Brandon S. Allbery KF8NH 
allb...@ece.cmu.edu wrote:

 On 2008 Dec 18, at 9:13, John Goerzen wrote:
 Some ideas in Haskell are easy to integrate into other languages: see
 list comprehensions in Python.  I don't see Perl picking up pervasive
 laziness anytime soon, nor Python compile-time type inference.

 I think perl6 is specced with pervasive laziness, although I'm not
 sure it's actually implemented anywhere.

I'm not sure about pervasive, but I read somewhere that Perl 6's lists are 
head-strict, tail-lazy by default...

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


Re: [Haskell-cafe] Re: Go Haskell! - array libraries

2008-11-29 Thread Brad Larsen
On Fri, 28 Nov 2008 19:00:38 -0500, Roman Leshchinskiy [EMAIL PROTECTED] 
wrote:

 On 29/11/2008, at 10:47, Claus Reinke wrote:
[...]
 And would it be difficult for you all to agree on a standard API, to
 make switching between the alternatives easy (if
 it is indeed impossible to unify their advantages in a single library,
 the reasons for which should also be documented somewhere)?

 Yes, it is very difficult. A sensible API for a standard array library
 is something that needs more research. FWIW, I don't know of any other
 language that has what I'd like to see in Haskell. C++ probably comes
 closest but they have it easy - they don't do fusion.
[...]

Would you elaborate on what you'd like to see in an array library?  And perhaps 
which C++ array library you are thinking of?  Your C++ comment caught my 
attention, and now I'm curious.  Surely you don't mean C-style arrays. :-D

Regards,
Brad Larsen



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


Re: [Haskell-cafe] Very silly

2008-10-13 Thread Brad Larsen
On Mon, 13 Oct 2008 23:32:30 -0400, Tommy M. McGuire [EMAIL PROTECTED] wrote:

 Andrew Coppin wrote:
 Bulat Ziganshin wrote:
 people that make critique on haskell type classes, don't take into
 account that it's unlike C++ templates, implemented via run-time
 dictionaries and other modules may define new instances

 Personally, I have no clue how C++ templates work [yet]. (As in, I'm
 learning C++, but I haven't got to that chapter yet.)

 Some guy told me that templates are the best feature in the language,
 and proceeded to show me a huge chunk of highly complex-looking code
 which is approximately equivilent to

  join :: Array x - Array x - Array x

 I was unimpressed.

 Actually, that's a lie. I was impressed that such a low-level language
 could manage even that much abstraction. But I still prefer the Haskell
 way...

 C++ values have sizes:

class foo {
  int x;
};

 is half (ahem; make that different from) the size of

class bar {
  int x;
  int y;
};

 As a result, doing parametric polymorphism requires duct taping
 something suspiciously similar to cpp macros to the type system.  Hence,
 how C++ templates work: weirdly.

 Java (and presumably C#) generics are very much like a weakened
 version of normal parametric polymorphism.  C++ templates are an attempt
 at the same thing in a completely different landscape.  I'd be willing
 to bet that Some Guy's code was very close to exactly equivalent to your
 join.

 Now, as to what C++ templates have to do with Haskell type classes, I
 dunno...

In the next C++ standard, type checking capabilities are being added to 
templates---concepts specify a set of operations a templated type must 
support.  See http://en.wikipedia.org/wiki/C%2B%2B0x#Concepts.  Seems 
somewhat similar to Haskell typeclasses to me, but perhaps the similarity is 
merely superficial. :-)

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


Re: [Haskell-cafe] timing question

2008-08-03 Thread Brad Larsen
Arie,

foldl1 is not strict in its function argument.  Using it will cause stack 
overflows for large lists.

For example:

GHCi, version 6.8.2: http://www.haskell.org/ghc/  :? for help
Loading package base ... linking ... done.
Prelude foldl1 (+) [0..100]
*** Exception: stack overflow

foldl1' from Data.List is strict in its function argument, and is probably what 
you want.

See also http://www.haskell.org/haskellwiki/Stack_overflow.

Regards,
Brad Larsen


On Sun, 03 Aug 2008 07:06:40 -0400, Arie Groeneveld [EMAIL PROTECTED] wrote:

 Sorry, should go the forum.

 Ok, thanks. In this case the list consists of 6-digit alphanumeric
 codes. So doing something like:

 foldl1 (\x y - g y) xs

 will do the job?


 =@@i


 Bulat Ziganshin schreef:
 Hello Arie,

 Sunday, August 3, 2008, 1:56:43 PM, you wrote:

 *Main last . f $ xs

 this way you will get only spin of list computed, not elements
 itself. something like sum should be used instead




 ___
 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] a really dumb posting question ;^(

2008-07-30 Thread Brad Larsen
Vasili,

You respond to whatever message interests you, just like normal email.
 Make sure the message is CC'd or addressed to
haskell-cafe@haskell.org to allow everyone to see it.

Regards,
Brad Larsen

2008/7/31 Galchin, Vasili [EMAIL PROTECTED]:
 Hello,

 What do I do to do a followup haskell cafe posting? E.g. I want to put a
 posting on the category theory thread!

 Kind regards, Vasili

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


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


Re: [Haskell-cafe] More fun with micro-benchmarks and optimizations. (GHC vs Perl)

2008-07-23 Thread Brad Larsen
And against gawk 3.1.5:

$ time awk -F: '{sum += 1 / $2} END{print sum}' test.out
3155.63

real0m0.197s
user0m0.184s
sys 0m0.004s

compared to Don's Haskell version:

$ time ./fastSum  test.out
3155.62664377

real0m0.072s
user0m0.056s
sys 0m0.004s

compared to the Corey's perl version:

$ time perl Sum.pl
Duration (sec): 3155.6266438

real0m0.181s
user0m0.164s
sys 0m0.012s


Regards,
Brad Larsen


On Wed, 23 Jul 2008 15:01:24 -0400, Don Stewart [EMAIL PROTECTED] wrote:

 coreyoconnor:
 I have the need to regularly write tiny programs that analyze output
 logs. The output logs don't have a consistent formatting so I
 typically choose Perl for these tasks.

 The latest instance of having to write such a program was simple
 enough I figured I'd try my hand at using Haskell instead. The short
 story is that I could quickly write a Haskell program that achieved
 the goal. Yay! However, the performance was ~8x slower than a
 comparable Perl implementation. With a lot of effort I got the Haskell
 version to only 2x slower. A lot of the optimization was done with
 guesses that the performance difference was due to how each line was
 being read from the file. I couldn't determine much using GHC's
 profiler.

 {-# OPTIONS -fbang-patterns #-}

 import qualified Data.ByteString.Char8 as S
 import Data.ByteString.Lex.Double
 import Debug.Trace

 main = print . go 0 = S.getContents
   where
 go !n !s = case readDouble str of
 Nothing - n
 Just (k,t)  - let delta = 1.0 / k in go (n+delta) t
 where
 (_, xs) = S.break ((==) ':') s
 str = S.drop 2 xs

 It uses the bytestring-lexing package on Hackage to read the Doubles
 out,

 $ ghc --make Fast.hs -O2 -fvia-C -optc-O2
 $ time  ./Fast  test.out
 3155.62664377
 ./Fast  test.out  0.07s user 0.01s system 97% cpu 0.078 total

 So that's twice as fast as the perl entry on my box,

 $ time perl Sum.pl  test.out
 Duration (sec): 3155.6266438
 perl Sum.pl  test.out  0.15s user 0.03s system 100% cpu 0.180 total

 Note that the safe Double lexer uses a bit of copying, so
 we can in fact do better still with a non-copying Double parser,
 but that's only for the hardcore.

 -- Don
 ___
 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] Integer = infinite precision integer? How?

2008-07-04 Thread Brad Larsen
On Fri, 04 Jul 2008 02:49:44 -0400, leledumbo [EMAIL PROTECTED] wrote:

 Does anyone have an explanation how Haskell implement this? Or a pointer to a
 article describing this?

GMP is presently used in GHC (at least according to 
http://hackage.haskell.org/trac/ghc/wiki/ReplacingGMPNotes).

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


[Haskell-cafe] Type issues for a foldable trie in Haskell

2008-01-20 Thread Brad Larsen

Hello there,

I have written a trie in Haskell generalized to Eq a = [a] rather than  
simply String.  I want to make this type an instance of Foldable, but I've  
run into a type dilemma.  My datatypes look like this:


data TrieElem a = Elem a | Start | End
  deriving (Read, Show, Eq, Ord)

data Trie a = Trie {label :: TrieElem a
   ,children :: [Trie a]}
  deriving (Read, Show, Eq, Ord)

The signature of Data.Foldable.foldr is (Data.Foldable.Foldable t) = (a  
- b - b) - b - t a - b.  However, I want the functions in Foldable to  
operate on the _list type_ that Trie stores rather than the _elements_ of  
that list type---Trie a stores lists of type a.  For example, a Trie  
storing strings would have type Trie Char, and I want Trie Char to be  
Foldable, but where the functions operate on String rather than Char.


So, with the datatype definitions of Trie and TrieElem as they are above,  
to define a fold function that operates the way I want would have  
signature ([a] - b - b) - b - Trie a - b, which is no good for making  
Trie a an instance of Foldable.


Hopefully this doesn't just seem like rambling :-).  How might I rewrite  
my datatypes to do what I want, preferably without using ghc extensions?   
Thanks!


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


Re: [Haskell-cafe] Type System (Was: Currying and Partial Evaluation)

2008-01-08 Thread Brad Larsen

On Tue, 08 Jan 2008 18:59:22 -0500, Achim Schneider [EMAIL PROTECTED] wrote:


Achim Schneider [EMAIL PROTECTED] wrote:


Prelude let y f = f $ y f
Prelude :t y
y :: (b - b) - b


Just out of curiosity: Where the heck does 'a' hide?



Beg pardon?  Are you referring to the type of y being described with 'b'  
instead of 'a'?


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


Re: [Haskell-cafe] A Foldable binary search tree

2007-12-23 Thread Brad Larsen
On Sun, 23 Dec 2007 06:42:52 -0500, Neil Mitchell [EMAIL PROTECTED]  
wrote:



Hi Brad,


 Experience has taught me to _never_ put class contexts on data
 definitions. Now you can't write something as simple as Empty - you
 have to give it a class context. This is just plain annoying.

With the class context in the BST definition, ghc gives no complaints  
when

I evaluate Empty:


In some circumstances, you need to give a type sig. For example using  
Hugs:


Main Empty
ERROR - Cannot find show function for:
*** Expression : Empty
*** Of type: BST a

I guess GHC has enough defaulting to display this anyway.


Sorry, forgot to mention that my BST derives Show.

You'll also have the dreaded-evil-horrid monomorhpism restriction if you  
type.


empty = Empty

Thanks

Neil


More stuff for me to read about :-)

Brad


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


Re: [Haskell-cafe] Why does this blow the stack?

2007-12-21 Thread Brad Larsen
On Fri, 21 Dec 2007 12:13:04 -0500, Justin Bailey [EMAIL PROTECTED]  
wrote:



Given this function:

  dropTest n = head . drop n $ [1..]

I get a stack overflow when n is greater than ~ 550,000 . Is that
inevitable behavior for large n? Is there a better way to do it?

Justin


I'm curious as well.  My first thought was to try the (!!) operator.   
Typing


  Prelude [1..] !! 55

overflows the stack on my computer, as does dropTest 55.


The code for (!!) is apparently as follows:

xs !! n | n  0 =  error Prelude.!!: negative index
[] !! _ =  error Prelude.!!: index too large
(x:_)  !! 0 =  x
(_:xs) !! n =  xs !! (n-1)

Isn't this tail recursive?  What is eating up the stack?


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


Re: [Haskell-cafe] Creating a type for a subset of the integers

2007-12-20 Thread Brad Larsen
On Wed, 19 Dec 2007 02:00:53 -0500, Jules Bean [EMAIL PROTECTED]  
wrote:



Brad Larsen wrote:

Hi there list,
 How would one go about creating a new type for a subset of the  
integers, for (contrived) example just the even integers?  I was  
thinking of making a new type

 newtype EvenInt = EvenInt Integer
 but the problem with this is that it accepts any integer, even odd  
ones.  So to prevent this, the module does not export the constructor  
for it---rather, the module exports a function `mkEvenInt' that creates  
an EvenInt if the given value is acceptable or raises an error  
otherwise.

  What's the right way to do this?  Thanks!


There are two ways:

(1) Have a representation which admits invalid values, and provide  
combinators which only perfect validity, and prove that consumers using  
your combinators can't produce invalid values.


(2) Have a cleverly designed representation such that every  
representation is valid.


An example here, for (2) would be to store n/2; there is a bijection  
between 'Integer' and 'EvenInt' given by n/2.


To make sure I understand, an example of (1) would be to export only a  
``smart constructor'' that somehow converts invalid values to valid ones  
(say, add 1 to arguments that are odd)?


In your example of 2, how would you go about storing n/2?  Store just n as  
in (newtype EvenInt = EvenInt Integer) and then write all functions that  
deal with EvenInts so that they account for the division by two?


In real, more complex problems, (2) often isn't possible and we resort  
to (1). E.g. the representation of balanced trees (AVL? RedBlack?)  
admits invalid values (both unbalanced trees and out-of-order trees) and  
  we rely on the reduced set of combinators never to generate one.


Jules


In my particular case, or what I actually want to do, is define a finite  
segment of the integers (0-42, say) as a new type and have that checked at  
compile time.  Any way of doing this w/o defining Peano numbers or a whole  
bunch of nullary constructors (i.e. I'm hoping to be able to define a type  
whose constructor will accept only Integer arguments between 0 and 42)?


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


[Haskell-cafe] Creating a type for a subset of the integers

2007-12-18 Thread Brad Larsen

Hi there list,

How would one go about creating a new type for a subset of the integers,  
for (contrived) example just the even integers?  I was thinking of making  
a new type


newtype EvenInt = EvenInt Integer

but the problem with this is that it accepts any integer, even odd ones.   
So to prevent this, the module does not export the constructor for  
it---rather, the module exports a function `mkEvenInt' that creates an  
EvenInt if the given value is acceptable or raises an error otherwise.



What's the right way to do this?  Thanks!


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