Re: [Haskell-cafe] dear traversable

2010-07-31 Thread Henning Thielemann


On Fri, 30 Jul 2010, Ben wrote:


dear traversable geniuses --

i am looking for better implementations of

unzipMap :: M.Map a (b, c) - (M.Map a b, M.Map a c)
unzipMap m = (M.map fst m, M.map snd m)


Maybe:

   mapPair (M.fromAscList, M.fromAscList) $
   unzip $ map (\(a,(b,c)) - ((a,b), (a,c))) $ M.toAscList m
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Announce type-level-natural-number-1.0: Simple, Haskell 2010-compatible type level natural numbers

2010-07-31 Thread Henning Thielemann


On Fri, 30 Jul 2010, John Meacham wrote:


Heh. I was just thinking I needed type level naturals last night at the
pub.


I thought about type level naturals yesterday when working with HList and 
found that HList's dependency on TemplateHaskell is quite heavy.



I wanted to support gcc's vector type extension in jhc

http://gcc.gnu.org/onlinedocs/gcc/Vector-Extensions.html

which allow diretly expressing vector operations that use the SIMD
features of modern CPUS, I didn't want to pre-create every possible
choice so encoding the size as a type level number makes sense.


The llvm wrapper supports CPU vector data types by decimal type level 
numbers from the type-level package as phantom type parameters, which I 
found nice to use. However the whole type level arithmetic is quite slow.


Btw. I got to know that there is a difference between Vector computing and 
SIMD computing, most notably that Vector units (like Altivec and SSE) 
support vector element shuffling and SIMD machines (like GPUs) do not.

  
http://perilsofparallel.blogspot.com/2008/09/larrabee-vs-nvidia-mimd-vs-simd.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] dear traversable

2010-07-31 Thread Stephen Tetley
On 31 July 2010 06:45, wren ng thornton w...@freegeek.org wrote:
 Ben wrote:

 dear traversable geniuses --

 i am looking for better implementations of

 unzipMap :: M.Map a (b, c) - (M.Map a b, M.Map a c)
 unzipMap m = (M.map fst m, M.map snd m)

 I don't think you can give a more efficient implementation using the public
 interface of Data.Map. You need to have a sort of mapping function that
 allows you to thread them together, either via continuations or via a
 primitive:

Unless I'm missing something. This one has one traversal...

unzipMap :: Ord a = M.Map a (b, c) - (M.Map a b, M.Map a c)
unzipMap = M.foldrWithKey fn (M.empty,M.empty)
  where
fn k a (m1,m2) = (M.insert k (fst a) m1, M.insert k (snd a) m2)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Database.CouchDB broken?

2010-07-31 Thread Martin Hilbig

hi,

try it this way:

http://gist.github.com/501951

note the type annotations and the added req param include_docs=true for
getAllDocs.

the first error is created by ghci, since it dont know the specific type

Database.CouchDB :t runCouchDB' $ getDoc (db test) (doc xyz) 
runCouchDB' $ getDoc (db test) (doc xyz)

  :: (JSON a) = IO (Maybe (Doc, Rev, a))

but why doesnt it complain about the ambiguous type variable `a', like
in `read 124`?

the addition of the include_docs=true request parameter really should be
in the getAllDocs function itself.

i'll fix this and put it in my own haskell-couchdb repo, as well as the
simple bulk and attachment apis i implemented, stay tuned ;)

have fun
martin

On 19.07.2010 19:08, Moritz Ulrich wrote:

Hello,

I'm currently learning Haskell and I want to write a small tool to
collect some data in a CouchDB-Database Sadly, the Database.CouchDB
module from hackage (and from git) seems broken. It looks like a bug
 deep in the JSON handling of the lib.

Some examples can be found in this gist:
http://gist.github.com/475323 ('test' is a database with two simple
documents, the doc with the id '8e9112011580882422393f6291000f7d'
exists)

I filed an issue, but the maintainer hasn't responded in 5 days. Is
there anything I missed?

Thanks in advance!


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


Re: [Haskell-cafe] Announce type-level-natural-number-1.0: Simple, Haskell 2010-compatible type level natural numbers

2010-07-31 Thread Alexey Khudyakov
On Fri, 30 Jul 2010 15:20:55 -0700
John Meacham j...@repetae.net wrote:
   type family Add n m :: *
  
   type instance Add Zero  Zero   = Zero
   type instance Add Zero (SuccessorTo n) = SuccessorTo n
   type instance Add (SuccessorTo n) m= SuccessorTo (Add n m)
  
  Standard package is could be somewhat difficult. Standards are
  undeniably good but one size doesn't fit all rule does apply here.
  Your package couldn't be used to represent big numbers. Little real
  work has been done on this so it's reasonable to expect progress or
  even some breakthough. 
 
 I thought there was some elegant way to express type level numbers
 using balanced ternary, but I can't find a reference to it at the
 moment.
 
Balanced ternary is useful for represeting signed integers.
Implementation of next, prev and basic arithmetic operations is not
very elegant

Some time ago I wrote implementation of type level numbers using binary
and balanced ternary encoding. Will upload to hackage soon. 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] dear traversable

2010-07-31 Thread Ross Paterson
On Fri, Jul 30, 2010 at 08:13:43PM -0700, Ben wrote:
 dear traversable geniuses --
 
 i am looking for better implementations of
 
 unzipMap :: M.Map a (b, c) - (M.Map a b, M.Map a c)
 unzipMap m = (M.map fst m, M.map snd m)
 
 unliftMap :: (Ord a) = M.Map a (b - c) - M.Map a b - M.Map a c
 unliftMap mf ma = M.mapWithKey (\k v - mf M.! k $ v) ma
 
 the first is obviously inefficient as it traverses the map twice.  the
 second just seems like it is some kind of fmap.

The second one assumes that every key in ma is also in mf.  A generalization
without that assumption is

  unliftMap = intersectionWith id

As Wren said, it looks like a * operator, but in this case there's no
corresponding pure function.  To make the laws work, pure x would have
to be a map that took every key to x.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] what's the best environment for haskell work?

2010-07-31 Thread Rustom Mody
Do most people who work with haskell use emacs/vi/eclipse or something
else??

Personal Note: I used gofer some 15 years ago.  At that time I hacked
up a emacs mode (I did not know of any then) along with some changes
to gofer to have gofer inside emacs rather than vi inside gofer.

Things have got more exciting now -- just trying to catch up!!

[Note: My preferrred/default OS is debian-squeeze]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Re: Can we come out of a monad?

2010-07-31 Thread Anton van Straaten

Jason Catena wrote:

On Jul 30, 11:17 am, Anton van Straaten wrote:

Prelude :m Control.Monad.State
Prelude Control.Monad.State let addToState :: Int - State Int ();
addToState x = do s - get; put (s+x)
Prelude Control.Monad.State let mAdd4 = addToState 4
Prelude Control.Monad.State :t mAdd4
m :: State Int ()
Prelude Control.Monad.State let s = execState mAdd4 2
Prelude Control.Monad.State :t s
s :: Int
Prelude Control.Monad.State s
6


By this example State doesn't seem to give you anything more than a
closure would


Sure, the example was just intended to show a value being extracted from 
a monad, which was what was being asked about.



since it doesn't act like much of an accumulator (by,
for example, storing 6 as its new internal value).


Actually, in the example, the put (s+x) does store 6 as the new value 
of the state.  It's just that the example doesn't do anything with this 
new state other than extract it using execState.


You can use functions like addToState in a larger expression, though. 
E.g., the following updates the internal state on each step and returns 14:


  execState (addToState 4  addToState 5  addToState 3) 2


Could you use State for something like storing the latest two values
of a Fibonacci series?

For example, each time you call it, it
generates the next term, discards the oldest term, and stores the
newly-generated term?


You should really try to implement this as an exercise, in which case 
don't read any further!


*

*

*

(OK, now I've assuaged my guilt about providing answers)

Here's the simplest imaginable implementation of your spec (the type 
alias is purely for readability):


type Fib a = State (Integer, Integer) a

fibTerm :: Fib Integer
fibTerm = do
(a,b) - get
put (b,a+b)
return a

When you run the Fib monad, you provide it with a pair of adjacent 
Fibonacci numbers such as (0,1), or, say, (55,89).


If you only run one of them, all it does is return the first element of 
the state it's provided with.  Chaining a bunch together gives you a 
Fibonacci computation.


For convenience and readability, here's a runner for the Fib monad:

runFib :: Fib a - a
runFib = flip evalState (0,1)


And could you then use this Fibonacci State monad in a lazy
computation, to grab for example the first twenty even Fibonacci
numbers, without computing and storing the series beyond what the
filter asks for?


Easily:

fibList :: [Integer]
fibList = runFib $ sequence (repeat fibTerm)

main = print $ take 20 (filter even fibList)


We can generate Fibonacci series double-recursively in a lazy
computation.  Would it be more or less efficient to use a Fibonacci
State monad instead?  


If you're thinking of comparing to a non-memoizing implementation, then 
the Fib monad version is a bajillion times faster, just because it 
avoids repeated computation.


But your mention of lazy makes me think you might be referring to a 
list-based implementation (since laziness doesn't help a naive 
implementation at all).  Using lists is much more efficient since it 
effectively memoizes.  E.g. this:


fibs = 0 : 1 : zipWith (+) fibs (tail fibs)

...is faster and more memory efficient than the Fib monad, but not so 
much that it'd matter for most purposes.  Fib's performance could be 
improved in various ways, too.



Would the State implementation provide a larger
range before it blew the stack (which tail-recursion should prevent),
or became too slow for impatient people?


The Fib monad performs very well.  fib 5 takes 1.6 seconds on my 
machine.  The non-memoizing double-recursing version can only get to 
about fib 27 in the same time, with similar memory usage, but that may 
not have been what you wanted to compare to.



Would Haskell memoize already-generated values in either case?  Could
we write a general memoizer across both the recursive and State
implementations, or must we write a specific one to each case?


By using a list in fibList above, we get memoization for free.  Although 
it may not be quite what you were asking for, lists in Haskell can be 
thought of as a kind of general memoizer.


Anton

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


Re: [Haskell-cafe] what's the best environment for haskell work?

2010-07-31 Thread Ivan Lazar Miljenovic
Rustom Mody rustompm...@gmail.com writes:

 Do most people who work with haskell use emacs/vi/eclipse or something
 else??

Most people seem to use either Emacs, a vi-like editor or some other
specialised editor (TextMate, etc.).  Some people do use the Haskell
editor yi (available on Hackage); there's also active development of the
Haskell IDE Leksah as well as some Haskell interfaces for traditional
IDEs like Eclipse and Visual Studio.

-- 
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] what's the best environment for haskell work?

2010-07-31 Thread Johan Tibell
On Sat, Jul 31, 2010 at 12:07 PM, Rustom Mody rustompm...@gmail.com wrote:

 Do most people who work with haskell use emacs/vi/eclipse or something
 else??


I use Emacs and haskell-mode.

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


Re: [Haskell-cafe] what's the best environment for haskell work?

2010-07-31 Thread Alberto G. Corona
leksah

2010/7/31 Johan Tibell johan.tib...@gmail.com

 On Sat, Jul 31, 2010 at 12:07 PM, Rustom Mody rustompm...@gmail.comwrote:

 Do most people who work with haskell use emacs/vi/eclipse or something
 else??


 I use Emacs and haskell-mode.

 Johan


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


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


[Haskell-cafe] Re: what's the best environment for haskell work?

2010-07-31 Thread Kevin Jardine
On Windows, I've used cedit for various projects for years and was
delighted to discover that it comes with a Haskell syntax colouring
file.

See:

http://cedit.sourceforge.net/

It supports collections of project files and compiling directly from
the editor.

I also use Eclipse for (sigh) PHP projects but at least under Windows
the Eclipse support available for Haskell appears to be limited. For
example the older versions do not appear to have a way to jump
immediately to a function definition and I could not get the more
recent versions to work at all (Eclipse users, feel free to correct me
if I missed something.) Cedit does not have a jump-to-function feature
either but it is much smaller and in my experience more stable than
Eclipse under Windows.

Kevin

On Jul 31, 12:07 pm, Rustom Mody rustompm...@gmail.com wrote:
 Do most people who work with haskell use emacs/vi/eclipse or something
 else??

 Personal Note: I used gofer some 15 years ago.  At that time I hacked
 up a emacs mode (I did not know of any then) along with some changes
 to gofer to have gofer inside emacs rather than vi inside gofer.

 Things have got more exciting now -- just trying to catch up!!

 [Note: My preferrred/default OS is debian-squeeze]
 ___
 Haskell-Cafe mailing list
 haskell-c...@haskell.orghttp://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] dear traversable

2010-07-31 Thread wren ng thornton

Stephen Tetley wrote:

wren ng thornton wrote:

Ben wrote:


unzipMap :: M.Map a (b, c) - (M.Map a b, M.Map a c)
unzipMap m = (M.map fst m, M.map snd m)


I don't think you can give a more efficient implementation using the public
interface of Data.Map. You need to have a sort of mapping function that
allows you to thread them together, either via continuations or via a
primitive:


Unless I'm missing something. This one has one traversal...

unzipMap :: Ord a = M.Map a (b, c) - (M.Map a b, M.Map a c)
unzipMap = M.foldrWithKey fn (M.empty,M.empty)
  where
fn k a (m1,m2) = (M.insert k (fst a) m1, M.insert k (snd a) m2)


Well, that's one traversal of the original map, but you have to traverse 
the new maps repeatedly with all those M.insert calls. And since 
Data.Map is a balanced tree, that could lead to a whole lot of work 
rebalancing things.


However, because we are not altering the set of keys, we are guaranteed 
that the structure of both new maps will be identical to the structure 
of the old map. Therefore, with the right primitives, we can keep one 
finger in each of the three maps and traverse them all in parallel 
without re-traversing any part of the spine. (The Either and Or variants 
will have some retraversal as the smart constructors prune out the spine 
leading to deleted keys. But this is, arguably, necessary.)


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


Re: [Haskell-cafe] dear traversable

2010-07-31 Thread Claude Heiland-Allen

On 31/07/10 12:13, wren ng thornton wrote:

Stephen Tetley wrote:

wren ng thornton wrote:

Ben wrote:


unzipMap :: M.Map a (b, c) - (M.Map a b, M.Map a c)
unzipMap m = (M.map fst m, M.map snd m)


I don't think you can give a more efficient implementation using the
public
interface of Data.Map. You need to have a sort of mapping function that
allows you to thread them together, either via continuations or via a
primitive:


Unless I'm missing something. This one has one traversal...

unzipMap :: Ord a = M.Map a (b, c) - (M.Map a b, M.Map a c)
unzipMap = M.foldrWithKey fn (M.empty,M.empty)
where
fn k a (m1,m2) = (M.insert k (fst a) m1, M.insert k (snd a) m2)


Well, that's one traversal of the original map, but you have to traverse
the new maps repeatedly with all those M.insert calls. And since
Data.Map is a balanced tree, that could lead to a whole lot of work
rebalancing things.

However, because we are not altering the set of keys, we are guaranteed
that the structure of both new maps will be identical to the structure
of the old map. Therefore, with the right primitives, we can keep one
finger in each of the three maps and traverse them all in parallel
without re-traversing any part of the spine. (The Either and Or variants
will have some retraversal as the smart constructors prune out the spine
leading to deleted keys. But this is, arguably, necessary.)



Why not something like this (with the correctness proof as an exercise):

\begin{code}

import Data.Map (Map)
import qualified Data.Map as M

unzipMap :: Map a (b, c) - (Map a b, Map a c)
unzipMap m =
  let (ab, ac) = unzip . map fiddle . M.toAscList $ m
  in  (M.fromDistinctAscList ab, M.fromDistinctAscList ac)
  where
fiddle :: (x, (y, z)) - ((x, y), (x, z))
fiddle (x, (y, z)) = ((x, y), (x, z))

\end{code}


(and I now see after writing this that Henning Thielemann wrote much the 
same some hours ago, however there are some slight differences so I'm 
sending this anyway)



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


[Haskell-cafe] Re: Can we come out of a monad?

2010-07-31 Thread Ertugrul Soeylemez
Brent Yorgey byor...@seas.upenn.edu wrote:

 On Fri, Jul 30, 2010 at 03:46:09AM -0700, Kevin Jardine wrote:
 
  When I plunged into Haskell earlier this year, I had no problem with
  understanding static typing, higher level functions and even
  separating pure functions from IO functions.
 
  The more I learn about monads, however, the less I understand them.
  I've seen plenty of comments suggesting that monads are easy to
  understand, but for me they are not.

 Lies.  [...]

 Even worse, this misguided but common insistence that monads are easy
 to understand inevitably makes people feel stupid when they discover
 that they aren't.

 Monads are hard to understand.  But they are *worth understanding*.

I agree to some extent, but only to some.  Mostly the problem of people
is that they are trying to understand monads as opposed to specific
instances.  It's better to learn the IO monad, state monads, the
list monad, the Maybe monad, the Parser monad, etc.

My experience is that the more specific examples you learn, the more you
will see the common design pattern.  Eventually it will make /click/ and
out of a sudden the lights will turn on.

So what's monad?  It's nothing.  Simple.

Better ask:  What's the Maybe monad?.


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] dear traversable

2010-07-31 Thread Stephen Tetley
On 31 July 2010 12:13, wren ng thornton w...@freegeek.org wrote:

 Well, that's one traversal of the original map, but you have to traverse the
 new maps repeatedly with all those M.insert calls. And since Data.Map is a
 balanced tree, that could lead to a whole lot of work rebalancing things.


Thanks. Indeed, I was missing that the traversal is cheap compared to
the rebuilding.

Although I haven't calculated the Big-O scores suspect that original
post will actually be the best, the solutions that metamorph into a
list and out again look like they're doing needless extra work.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Monad transformers, design

2010-07-31 Thread Tony Morris
Hello I have a question regarding monad transformers and how to design
an API with a transformer. I have a narrowed code example of the
question. Please see the questions in the comments below.



import Data.Monoid
import Control.Monad

-- Suppose some data type
newtype Inter a = Inter (Int - a)

-- and a monad transformer for that data type.
newtype InterT m a = InterT (m (Inter a))

-- It's easy to implement this type-class
instance (Monoid a) = Monoid (Inter a) where
  mempty = Inter (const mempty)
  Inter a `mappend` Inter b = Inter (a `mappend` b)

-- and for the transformer too by lifting into the monad
instance (Monad m, Monoid a) = Monoid (InterT m a) where
  mempty = InterT (return mempty)
  InterT a `mappend` InterT b = InterT (liftM2 mappend a b)

-- But what about this type-class?
class Ints a where
  ints :: a - Int - Int

-- Seems easy enough
instance (Integral a) = Ints (Inter a) where
  ints (Inter a) n = fromIntegral (a n)

-- OH NO!
{-
instance (Monad m, Integral a) = Ints (InterT m a) where
  ints (InterT a) n = error OH NO!
-}

-- We could try this
class Copointed f where
  copoint :: f a - a

-- but it seems rather impractical
instance (Copointed m, Integral a) = Ints (InterT m a) where
  ints (InterT a) = ints (copoint a)

{-
So it seems that for some type-classes it is possible to implement
for both the data type and the transformer, but not all type-classes.

Is there a general approach to this problem?
-}



-- 
Tony Morris
http://tmorris.net/


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


Re: [Haskell-cafe] Monad transformers, design

2010-07-31 Thread Ross Paterson
On Sat, Jul 31, 2010 at 10:56:31PM +1000, Tony Morris wrote:
 -- Suppose some data type
 newtype Inter a = Inter (Int - a)
 
 -- and a monad transformer for that data type.
 newtype InterT m a = InterT (m (Inter a))

The monad transformer should be Inter (m a).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: using the orc library

2010-07-31 Thread Günther Schmidt

Dear Edward,

I hope that there is a more orc integrated solution. I think the 
scenario I described here is quite common.


Günther

Am 31.07.10 00:16, schrieb Edward Z. Yang:

Excerpts from Günther Schmidt's message of Fri Jul 30 16:16:38 -0400 2010:

I'd like to download 1,000 web pages with up to 6 six concurrent
downloads at a time.

How can I express such a thread limit within the orc EDSL?


One solution that comes to mind is place all 1000 web pages in an MVar
containing a queue of URLs to process (a list will probably suffice),
and then use Orc to orchestrate six threads that pull a page from the queue
and make a download.  Admittedly, Orc doesn't buy you very much in this
scenario until you add timeout handling and such.

Cheers,
Edward



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


Re: [Haskell-cafe] Re: Microsoft's Singularity Project and Haskell

2010-07-31 Thread Tim Matthews
SPJ http://research.microsoft.com/en-us/people/simonpj/default.aspx and
probably many others are actually employed at Microsoft research centers. It
looks like Microsoft just hasn't been able to find a suitable spot to push
Haskell. Haskell influenced F# because they needed a functional language
that targeted CLR, and included OO and mutable data.

IMO Haskell is even better than their languages


Maybe so but singularity actually provides the whole os apis via clr
interfaces compared to mainstream windows os where the underlying apis are
all in C, C++ and COM. The common intermediate language is not tied to any
specific programming language such as C# or VB, it's more generic than that,
and has it's advantages. Safety is something they wish to achieve but afaik
their main goal is to write an OS in managed code.

Haskell does provide a safe runtime but afaik unlike the clr it's tied to
the haskell language. I think there has also been some attempts to write an
OS in haskell too though, but that's another story...
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monad transformers, design

2010-07-31 Thread Tony Morris
gah you're right, @mtl had confuzzled me.

Well that changes things then, thanks.

Ross Paterson wrote:
 On Sat, Jul 31, 2010 at 10:56:31PM +1000, Tony Morris wrote:
   
 -- Suppose some data type
 newtype Inter a = Inter (Int - a)

 -- and a monad transformer for that data type.
 newtype InterT m a = InterT (m (Inter a))
 

 The monad transformer should be Inter (m a).
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

   

-- 
Tony Morris
http://tmorris.net/


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


[Haskell-cafe] Constructor question

2010-07-31 Thread michael rice
From: Data.Complex

data (RealFloat a) = Complex a
  = !a :+ !a

What's the purpose of the exclamation marks?

Michael



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


Re: [Haskell-cafe] dear traversable

2010-07-31 Thread Claude Heiland-Allen

On 31/07/10 13:49, Stephen Tetley wrote:

Although I haven't calculated the Big-O scores suspect that original
post will actually be the best, the solutions that metamorph into a
list and out again look like they're doing needless extra work.


They're both O(size m) time, and yes the original is best (not least for 
its simplicity and elegance);  I now think that (on my part) it was a 
case of following optimisation strategies without thinking hard enough 
whether they apply: ie, traversing only once can be beneficial for space 
reasons under certain circumstances [1]


But as Data.Map is spine-strict, there is no space saving here by 
traversing only once, as the spine is already there taking up O(size m) 
space before we even start traversing (whereas with lazy lists the spine 
might not be taking up any space yet).



[1] to give a classic example:

mean :: Fractional a = [a] - a
mean xs = sum xs / genericLength xs

which often consumes O(length xs) space, reducible to O(1) if only one 
traversal is performed.



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


Re: [Haskell-cafe] Constructor question

2010-07-31 Thread Ivan Lazar Miljenovic
michael rice nowg...@yahoo.com writes:

 From: Data.Complex

 data (RealFloat a) = Complex a
   = !a :+ !a

 What's the purpose of the exclamation marks?

Forcing; it means that the values are evaluated (up to WHNF) before the
Complex value is constructed:

http://www.haskell.org/ghc/docs/6.12.1/html/users_guide/bang-patterns.html

-- 
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] Re: Microsoft's Singularity Project and Haskell

2010-07-31 Thread Alberto G. Corona
I guess that the house
OShttp://www.google.com/search?hl=ensafe=offq=+house+OS+haskellaq=faqi=g-sx7aql=oq=gs_rfai=has
no one of these problems that singularity tries to solve in the first
place.

The problem of general OSs is: we have unsafe code, so what we do to deal
with it?. The usual option is the isolation trough virtual addresses so that
every pointer address is virtual. This imposes cost in task switching and
pointer handling.   The singularity alternative seems to be to check the
managed code for pointer violations at installation time.

In singularity they pretend to extend the reach of types, defined in .NET at
the assembly level for inter program and inter language safety, to  the OS
level for runtime safety. This goal is interesting, because a well defined
type system, without unsafe operations permitted, managed at the OS level
could permit pure code to run wildly in real memory very fast, for example.
With effects defined in the type system the advantages may be greater.


2010/7/31 Tim Matthews tim.matthe...@gmail.com


 SPJ http://research.microsoft.com/en-us/people/simonpj/default.aspx and
 probably many others are actually employed at Microsoft research centers. It
 looks like Microsoft just hasn't been able to find a suitable spot to push
 Haskell. Haskell influenced F# because they needed a functional language
 that targeted CLR, and included OO and mutable data.


 IMO Haskell is even better than their languages


 Maybe so but singularity actually provides the whole os apis via clr
 interfaces compared to mainstream windows os where the underlying apis are
 all in C, C++ and COM. The common intermediate language is not tied to any
 specific programming language such as C# or VB, it's more generic than that,
 and has it's advantages. Safety is something they wish to achieve but afaik
 their main goal is to write an OS in managed code.

 Haskell does provide a safe runtime but afaik unlike the clr it's tied to
 the haskell language. I think there has also been some attempts to write an
 OS in haskell too though, but that's another story...

 ___
 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] Constructor question

2010-07-31 Thread michael rice
Thanks, Ivan.

I may be back later, after I read

http://en.wikibooks.org/wiki/Haskell/Laziness

Michael

--- On Sat, 7/31/10, Ivan Lazar Miljenovic ivan.miljeno...@gmail.com wrote:

From: Ivan Lazar Miljenovic ivan.miljeno...@gmail.com
Subject: Re: [Haskell-cafe] Constructor question
To: michael rice nowg...@yahoo.com
Cc: haskell-cafe@haskell.org
Date: Saturday, July 31, 2010, 9:32 AM

michael rice nowg...@yahoo.com writes:

 From: Data.Complex

 data (RealFloat a) = Complex a
   = !a :+ !a

 What's the purpose of the exclamation marks?

Forcing; it means that the values are evaluated (up to WHNF) before the
Complex value is constructed:

http://www.haskell.org/ghc/docs/6.12.1/html/users_guide/bang-patterns.html

-- 
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] Constructor question

2010-07-31 Thread Ben Millwood
On Sat, Jul 31, 2010 at 2:32 PM, Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com wrote:

 Forcing; it means that the values are evaluated (up to WHNF) before the
 Complex value is constructed:

 http://www.haskell.org/ghc/docs/6.12.1/html/users_guide/bang-patterns.html


Actually, this isn't a bang pattern: the 'a' here is not a pattern,
it's a type variable. Strictness flags in data declarations are a
haskell98 feature.

See:

http://www.haskell.org/onlinereport/haskell2010/haskellch4.html#x10-680004.2

the paragraph on Strictness Flags a little way down that page.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-07-31 Thread Dan Doel
On Saturday 31 July 2010 8:13:37 am Ertugrul Soeylemez wrote:
 I agree to some extent, but only to some.  Mostly the problem of people
 is that they are trying to understand monads as opposed to specific
 instances.  It's better to learn the IO monad, state monads, the
 list monad, the Maybe monad, the Parser monad, etc.

I think there are 'easy' answers to what are monads, too, at least in the 
way they tend to appear in Haskell. But, the easiness may well depend on 
having background that isn't common in computer programming.

Some of it is, though. Embedded domain-specific language is a buzz phrase 
these days, so it's probably safe to assume most folks are familiar with the 
idea. From that starting point, one might ask how to approach EDSLs from a 
more mathematical perspective, and making use of the type system. We might be 
led to the following:

1) We want to distinguish 'programs written in the EDSL' via types somehow. It 
may not make sense to use EDSL operations just anywhere in the overall 
program.

2) Algebra looks promising for talking about languages. Our DSLs will probably 
have some base operations, which we'll combine to make our programs. So, our 
EDSL type above should probably be related to algebraic theories somehow.

Once we've decided on the above, well, monads are a way in category theory of 
talking about algebraic theories. So it stands to reason that a lot of the 
EDSLs we're interested in will be monads. And so, by talking about monads in 
general, we can construct operations that make sense in and on arbitrary EDSLs 
(like, say, sequence = stick together several expressions).

And that covers a lot of what monads are used for in Haskell.

  'Maybe a' designates expressions in a language with failure
  'Either e a' designates expressions with a throw operation
  'State s a' allows get and put
  'IO a' has most of the features in imperative languages.
  etc.

So the 'easy' answer is that (embedded) languages tend to be algebraic 
theories, and monads are a way of talking about those. Of course, that general 
answer may still be pretty meaningless if you don't know what algebraic 
theories are, so it's still probably good to look at specific monads.

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


Re: [Haskell-cafe] Constructor question

2010-07-31 Thread Ivan Lazar Miljenovic
Ben Millwood hask...@benmachine.co.uk writes:

 On Sat, Jul 31, 2010 at 2:32 PM, Ivan Lazar Miljenovic
 ivan.miljeno...@gmail.com wrote:

 Forcing; it means that the values are evaluated (up to WHNF) before the
 Complex value is constructed:

 http://www.haskell.org/ghc/docs/6.12.1/html/users_guide/bang-patterns.html


 Actually, this isn't a bang pattern: the 'a' here is not a pattern,
 it's a type variable. Strictness flags in data declarations are a
 haskell98 feature.

 See:

 http://www.haskell.org/onlinereport/haskell2010/haskellch4.html#x10-680004.2

 the paragraph on Strictness Flags a little way down that page.

Ugh, yeah; I should read what links I google for before putting them in
emails :s

-- 
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] what's the best environment for haskell work?

2010-07-31 Thread Joachim Breitner
Hi,

Am Samstag, den 31.07.2010, 15:37 +0530 schrieb Rustom Mody:
 Do most people who work with haskell use emacs/vi/eclipse or something
 else??
 
 Personal Note: I used gofer some 15 years ago.  At that time I hacked
 up a emacs mode (I did not know of any then) along with some changes
 to gofer to have gofer inside emacs rather than vi inside gofer.
 
 Things have got more exciting now -- just trying to catch up!!
 
 [Note: My preferrred/default OS is debian-squeeze]

I’m using vim myself, but the Debian Haskell Team has packaged leksah
and it is available in squeeze. If you have any problems with the
packaging, we would like to hear about them. 

(So far, we had zero feedback from leksah users on Debian, so I don’t
know if there exist any)

Greetings,
Joachim

-- 
Joachim nomeata Breitner
  mail: m...@joachim-breitner.de | ICQ# 74513189 | GPG-Key: 4743206C
  JID: nome...@joachim-breitner.de | http://www.joachim-breitner.de/
  Debian Developer: nome...@debian.org


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Constructor question

2010-07-31 Thread michael rice
This Joni Mitchell lyric just popped into my head:

I've looked at clouds from both sides now
From up and down, and still somehow
It's cloud illusions I recall
I really don't know clouds at all

A LOT of cool stuff here, but the learning curve is murder.

Michael



--- On Sat, 7/31/10, Ivan Lazar Miljenovic ivan.miljeno...@gmail.com wrote:

From: Ivan Lazar Miljenovic ivan.miljeno...@gmail.com
Subject: Re: [Haskell-cafe] Constructor question
To: michael rice nowg...@yahoo.com
Cc: haskell-cafe@haskell.org
Date: Saturday, July 31, 2010, 9:32 AM

michael rice nowg...@yahoo.com writes:

 From: Data.Complex

 data (RealFloat a) = Complex a
   = !a :+ !a

 What's the purpose of the exclamation marks?

Forcing; it means that the values are evaluated (up to WHNF) before the
Complex value is constructed:

http://www.haskell.org/ghc/docs/6.12.1/html/users_guide/bang-patterns.html

-- 
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] Constructor question

2010-07-31 Thread michael rice
Ok, got ! and WHNF.

Thanks,

Michael

--- On Sat, 7/31/10, Ivan Lazar Miljenovic ivan.miljeno...@gmail.com wrote:

From: Ivan Lazar Miljenovic ivan.miljeno...@gmail.com
Subject: Re: [Haskell-cafe] Constructor question
To: michael rice nowg...@yahoo.com
Cc: haskell-cafe@haskell.org
Date: Saturday, July 31, 2010, 9:32 AM

michael rice nowg...@yahoo.com writes:

 From: Data.Complex

 data (RealFloat a) = Complex a
   = !a :+ !a

 What's the purpose of the exclamation marks?

Forcing; it means that the values are evaluated (up to WHNF) before the
Complex value is constructed:

http://www.haskell.org/ghc/docs/6.12.1/html/users_guide/bang-patterns.html

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com



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


[Haskell-cafe] Laziness question

2010-07-31 Thread michael rice
From: http://en.wikibooks.org/wiki/Haskell/Laziness


Given two functions of one parameter, f and g, we say f is stricter than g if f 
x evaluates x to a deeper level than g x

Exercises

   1. Which is the stricter function?

f x = length [head x]
g x = length (tail x)



Prelude let f x = length [head x]
Prelude let g x = length (tail x)
Prelude f undefined
1
Prelude g undefined
*** Exception: Prelude.undefined
Prelude 



So, g is stricter than f?

Wouldn't both functions need to evaluate x to the same level, *thunk* : *thunk* 
to insure listhood?

f x = length [head *thunk* : *thunk*]
g x = length (tail *thunk* : *thunk*)

Michael



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


Re: [Haskell-cafe] Laziness question

2010-07-31 Thread Henning Thielemann
michael rice schrieb:

 So, g is stricter than f?
 
 Wouldn't both functions need to evaluate x to the same level, *thunk* :
 *thunk* to insure listhood?

No. :-)

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


Re: [Haskell-cafe] Laziness question

2010-07-31 Thread Ben Millwood
On Sat, Jul 31, 2010 at 4:56 PM, michael rice nowg...@yahoo.com wrote:

 From: http://en.wikibooks.org/wiki/Haskell/Laziness


 Given two functions of one parameter, f and g, we say f is stricter than g if 
 f x evaluates x to a deeper level than g x

 Exercises

    1. Which is the stricter function?

 f x = length [head x]
 g x = length (tail x)



 Prelude let f x = length [head x]
 Prelude let g x = length (tail x)
 Prelude f undefined
 1
 Prelude g undefined
 *** Exception: Prelude.undefined
 Prelude



 So, g is stricter than f?

 Wouldn't both functions need to evaluate x to the same level, *thunk* : 
 *thunk* to insure listhood?

 f x = length [head *thunk* : *thunk*]
 g x = length (tail *thunk* : *thunk*)

 Michael


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


Notice the two different kinds of brackets being used in f versus g :)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Laziness question

2010-07-31 Thread michael rice
OK, in f, *length* already knows it's argument is a list.

In g, *length* doesn't know what's inside the parens, extra evaluation there. 
So g is already ahead before we get to what's inside the [] and ().

But since both still have eval x to *thunk* : *thunk*,  g evaluates to a 
deeper level?

Michael


 Wouldn't both functions need to evaluate x to the same level, *thunk* : 
 *thunk* to insure listhood?

 f x = length [head *thunk* : *thunk*]
 g x = length (tail *thunk* : *thunk*)

 Michael


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


Notice the two different kinds of brackets being used in f versus g :)

--- On Sat, 7/31/10, Ben Millwood hask...@benmachine.co.uk wrote:

From: Ben Millwood hask...@benmachine.co.uk
Subject: Re: [Haskell-cafe] Laziness question
To: michael rice nowg...@yahoo.com
Cc: haskell-cafe@haskell.org
Date: Saturday, July 31, 2010, 12:38 PM

On Sat, Jul 31, 2010 at 4:56 PM, michael rice nowg...@yahoo.com wrote:

 From: http://en.wikibooks.org/wiki/Haskell/Laziness


 Given two functions of one parameter, f and g, we say f is stricter than g if 
 f x evaluates x to a deeper level than g x

 Exercises

    1. Which is the stricter function?

 f x = length [head x]
 g x = length (tail x)



 Prelude let f x = length [head x]
 Prelude let g x = length (tail x)
 Prelude f undefined
 1
 Prelude g undefined
 *** Exception: Prelude.undefined
 Prelude



 So, g is stricter than f?

 Wouldn't both functions need to evaluate x to the same level, *thunk* : 
 *thunk* to insure listhood?

 f x = length [head *thunk* : *thunk*]
 g x = length (tail *thunk* : *thunk*)

 Michael


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


Notice the two different kinds of brackets being used in f versus g :)



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


Re: [Haskell-cafe] Laziness question

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

On 7/31/10 12:59 , michael rice wrote:
 OK, in f, *length* already knows it's argument is a list.
 
 In g, *length* doesn't know what's inside the parens, extra evaluation
 there. So g is already ahead before we get to what's inside the [] and ().
 
 But since both still have eval x to *thunk* : *thunk*,  g evaluates to a
 deeper level?

The whole point of laziness is that f *doesn't* have to eval x.

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

iEYEARECAAYFAkxUXbgACgkQIn7hlCsL25X5dQCdFskJ8+DdIVnJtsYVAFJkHcHO
yjEAoMuoKU2yXLKVcLFGumLb0IJAVxnx
=5KJ5
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Problem loading hxt

2010-07-31 Thread David Place

 Hello:

I am trying to load hxt into my Haskell Platform 2010.2.0.0 on OSX.  I 
get the following bizarre comment:


David-Places-Mac-Mini:dev2 davidplace$ cabal install hxt
Resolving dependencies...
cabal: dependencies conflict: ghc-6.12.3 requires directory ==1.0.1.1 however
directory-1.0.1.1 was excluded because ghc-6.12.3 requires directory ==1.0.1.2

I see that I have the older directory in my global package list and the newer 
one in my local list.  Help?  Thanks.

David-Places-Mac-Mini:dev2 davidplace$ ghc-pkg list
/Library/Frameworks/GHC.framework/Versions/612/usr/lib/ghc-6.12.3/package.conf.d
   Cabal-1.8.0.6
   GLUT-2.1.2.1
   HTTP-4000.0.9
   HUnit-1.2.2.1
   OpenGL-2.2.3.0
   QuickCheck-2.1.1.1
   array-0.3.0.1
   base-3.0.3.2
   base-4.2.0.2
   bin-package-db-0.0.0.0
   bytestring-0.9.1.7
   cgi-3001.1.7.3
   containers-0.3.0.0
   deepseq-1.1.0.0
   directory-1.0.1.1
   dph-base-0.4.0
   dph-par-0.4.0
   dph-prim-interface-0.4.0
   dph-prim-par-0.4.0
   dph-prim-seq-0.4.0
   dph-seq-0.4.0
   extensible-exceptions-0.1.1.1
   ffi-1.0
   fgl-5.4.2.3
   filepath-1.1.0.4
   ghc-6.12.3
   ghc-binary-0.5.0.2
   ghc-prim-0.2.0.0
   haskell-src-1.0.1.3
   haskell98-1.0.1.1
   hpc-0.5.0.5
   html-1.0.1.2
   integer-gmp-0.2.0.1
   mtl-1.1.0.2
   network-2.2.1.7
   old-locale-1.0.0.2
   old-time-1.0.0.5
   parallel-2.2.0.1
   parsec-2.1.0.1
   pretty-1.0.1.1
   process-1.0.1.3
   random-1.0.0.2
   regex-base-0.93.2
   regex-compat-0.93.1
   regex-posix-0.94.2
   rts-1.0
   stm-2.1.2.1
   syb-0.1.0.2
   template-haskell-2.4.0.1
   time-1.1.4
   unix-2.4.0.2
   xhtml-3000.2.0.1
   zlib-0.5.2.0
/Users/davidplace/.ghc/i386-darwin-6.12.3/package.conf.d
   Cabal-1.8.0.6
   binary-0.5.0.2
   directory-1.0.1.2
   fingertree-0.0.1.0
   haskell98-1.0.1.1
   process-1.0.1.3
   random-1.0.0.2
   time-1.2.0.3
   uu-parsinglib-2.4.2
   uu-parsinglib-2.4.4
   uu-parsinglib-2.4.5
   uu-parsinglib-2.5.0
   uulib-0.9.12



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


Re: [Haskell-cafe] Laziness question

2010-07-31 Thread Ben Millwood
On Sat, Jul 31, 2010 at 5:59 PM, michael rice nowg...@yahoo.com wrote:

 OK, in f, *length* already knows it's argument is a list.

 In g, *length* doesn't know what's inside the parens, extra evaluation there. 
 So g is already ahead before we get to what's inside the [] and ().

According to the types, we already know both are lists. The question
is, of course, what kind of list.

 But since both still have eval x to *thunk* : *thunk*,  g evaluates to a 
 deeper level?

 Michael


I think this question is being quite sneaky. The use of head and tail
is pretty much irrelevant. Try the pointfree versions:

f = length . (:[]) . head
g = length . tail

and see if that helps you see why f is lazier than g.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Laziness question

2010-07-31 Thread Albert Y. C. Lai

On 10-07-31 01:30 PM, Brandon S Allbery KF8NH wrote:

On 7/31/10 12:59 , michael rice wrote:

But since both still have eval x to *thunk* : *thunk*,  g evaluates to a
deeper level?


The whole point of laziness is that f *doesn't* have to eval x.


To elaborate, in computer-friendly syntax:

f x = length (red_herring : [])

length cares about cons cells (:) and nil [] only. You have already 
hardcoded exactly those. Enough said... err, enough evaluated.

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


[Haskell-cafe] ANNOUNCE: Takusen 0.8.6

2010-07-31 Thread Jason Dagit
Hello,

The Takusen team would like to announce the latest release of Takusen,
0.8.6.  This is primarily a bug fix and test suite enhancement
release.  The most notable new feature is limited support for string
encodings with ODBC.  The full list of changes is included at the
at the end of this announcement.

= Interested in Takusen development? =

Takusen is looking for a new long term maintainer.  I have agreed to
fill the role of maintainer for now, but we are seeking an
enthusiastic individual with spare time and a desire to lead Takusen
development.

= How to get it =

This release is available on hackage:
  cabal update  cabal install Takusen

The source code is available on code.haskell.org:
  darcs get http://code.haskell.org/takusen


= New features =

- Alistair Bayley:

  * Database/PostgreSQL/PGFunctions.lhs: show instance for UUID prints
Word64s in hex.

  * Database/PostgreSQL/Enumerator.lhs: add UUID and marshaling
functions.

  * Database/PostgreSQL/PGFunctions.lhs: add UUID and marshalling
functions.

  * Database/ODBC/OdbcFunctions.hsc: add support for different String
encodings. New functions to marshal to/from various encodings
(Latin1, UTF8, UTF16), and bind/get functions changed to use
these.

- Daniel Corson
  * binary data with postgres

= Bug fixes =

- Alistair Bayley:

  * Database/ODBC/OdbcFunctions.hsc: fix bug in
mkBindBufferForStorable for Nothing (null) case: pass -1
(sqlNullData) as value size.

  * Database/ODBC/OdbcFunctions.hsc: use sqlNullData in
bindParamString Nothing case, rather than -1. A bit more
descriptive.

  * Database/ODBC/Enumerator.lhs: store bind buffers in stmt object,
so we retain reference to them for lifetime of statement. Destroy
with statement (well, lose the reference). Should fix bind errors
found by Jason Dagit.

  * Database/ODBC/Enumerator.lhs: Oracle only supports two transaction
isolation levels (like Postgres). String output bind parameters
have max size 8000 (we use 7999 because module OdbcFunctions adds
one to the size).

  * Database/ODBC/OdbcFunctions.hsc: string parameters have different
SQL data types when binding columns (SQL_CHAR) and parameters
(SQL_VARCHAR). Oracle only supports two transaction isolation
levels.

  * Database/PostgreSQL/PGFunctions.lhs: fix byteaUnesc and add
byteaEsc.


= Refactoring =

- Jason Dagit:
  * update urls in cabal file

- Alistair Bayley:

  * Takusen.cabal: fixed QuickCheck version spec.

  * Takusen.cabal: bump version to 0.8.6.

  * Database/ODBC/OdbcFunctions.hsc: makeUtcTimeBuffer: pass struct
size as both buffer size and data size in call to mkBindBuffer.

  * Database/ODBC/OdbcFunctions.hsc: mkBindBufferForStorable calls
mkBindBuffer (reduces duplicated code).

  * Database/ODBC/Enumerator.lhs: add instance for EnvInquiry to
change session char encoding.

  * Database/ODBC/Enumerator.lhs: add comments to beginTransaction.

  * Database/Util.lhs: print printArrayContents, to match function
name.

  * Database/PostgreSQL/Enumerator.lhs: expose byteaEsc and
byteaUnesc.

= New tests and changes to tests =

- Alistair Bayley:

  * Database/ODBC/Test/OdbcFunctions.lhs: added testBindDouble to test
Nothing (null) case for Storable types.

  * Database/ODBC/Test/OdbcFunctions.lhs: split transaction isolation
level tests so there is one test per level. String marshaling
tests use 0x10FF40 as max unicode codepoint, because that keeps
Oracle happy. Max size for String parameter buffer is 7999 (SQL
Server restriction). Don't bury errors raised by tests; print, but
continue. Fix fixture cleanup bug in testBindOutput (dropped wrong
procedure).

  * Database/ODBC/Test/Enumerator.lhs: suffix xxx to bindOutput test
expected value.

  * Database/PostgreSQL/Test/PGFunctions.lhs: tests for UUID.

  * Database/PostgreSQL/Test/Enumerator.lhs: round-trip test for UUID.

  * Database/PostgreSQL/Test/PGFunctions.lhs: test select of UUID
value.

  * Database/ODBC/Test/OdbcFunctions.lhs: set client charset to UTF8
when postgresql.

  * Database/Test/Enumerator.lhs: add order-bys to tests with unions.

  * Database/PostgreSQL/Test/PGFunctions.lhs: add order-by to union
test.

  * Database/ODBC/Test/Enumerator.lhs: set char encoding to
UTF8. inquire InfoDbmsName already returns lowercase.

  * Takusen.cabal: add random to build-depends for tests.

  * Database/Test/Enumerator.lhs: make test fixtures more friendly to
MS Access.

  * Database/ODBC/Test/OdbcFunctions.lhs: tests modified for MS Access
(date tests), plus use new char-encoding aware functions.

  * Database/ODBC/Test/Enumerator.lhs: change boundary dates test to
not use union. Union seems to make MS Access choke.

  * Database/PostgreSQL/Test/PGFunctions.lhs: add tests for bytea,
including QuickCheck roundtrip.

  * Database/PostgreSQL/Test/Enumerator.lhs: add bytea bind and select
test.

Re: [Haskell-cafe] Laziness question

2010-07-31 Thread michael rice
From Hoogle:

  
Query: (:[])


  Error: 
unexpected :
expecting #, ,, forall, (, [, ! or )
Bad symbol

Prelude let h = length . (:[]) . head
Prelude h undefined
1
Prelude :t (:[])
(:[]) :: a - [a]
Prelude h []
1    this comes as a surprise
Prelude 

Are you saying:

[ head x ]  -  [ *thunk* ]   and   length [ *thunk* ] -  1, independent of 
what *thunk* is, even head [], i.e., *thunk* never needs be evaluated?

Michael




--- On Sat, 7/31/10, Ben Millwood hask...@benmachine.co.uk wrote:

From: Ben Millwood hask...@benmachine.co.uk
Subject: Re: [Haskell-cafe] Laziness question
To: michael rice nowg...@yahoo.com
Cc: haskell-cafe@haskell.org
Date: Saturday, July 31, 2010, 1:47 PM

On Sat, Jul 31, 2010 at 5:59 PM, michael rice nowg...@yahoo.com wrote:

 OK, in f, *length* already knows it's argument is a list.

 In g, *length* doesn't know what's inside the parens, extra evaluation there. 
 So g is already ahead before we get to what's inside the [] and ().

According to the types, we already know both are lists. The question
is, of course, what kind of list.

 But since both still have eval x to *thunk* : *thunk*,  g evaluates to a 
 deeper level?

 Michael


I think this question is being quite sneaky. The use of head and tail
is pretty much irrelevant. Try the pointfree versions:

f = length . (:[]) . head
g = length . tail

and see if that helps you see why f is lazier than g.



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


Re: [Haskell-cafe] Laziness question

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

On 7/31/10 14:24 , michael rice wrote:
 Are you saying:
 
 [ head x ]  -  [ *thunk* ]   and   length [ *thunk* ] -  1, independent of
 what *thunk* is, even head [], i.e., *thunk* never needs be evaluated?

Exactly.  (I was being cagey because the first response was cagey, possibly
suspecting a homework question although it seems like an odd time for it.)

length not only does not look inside of the thunk, it *can't* look inside
it; all it knows is that it has a list, it specifically does *not* know what
that list can hold.  So the only thing it can do is count the number of
unknown somethings in the list.

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

iEYEARECAAYFAkxUa54ACgkQIn7hlCsL25XVpgCeIxWwVWhjYQQ86uE2JeJD7mCB
mKUAn3WwhrgrYyudv/E8pn5a0HB4gLA9
=H++/
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Laziness question

2010-07-31 Thread Tillmann Rendel

michael rice wrote:

f x = length [head x]
g x = length (tail x)

Wouldn't both functions need to evaluate x to the same level, *thunk* : 
*thunk* to insure listhood?


There is no need to insure listhood at run time, since Haskell is 
statically typed.


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


Re: [Haskell-cafe] Laziness question

2010-07-31 Thread michael rice
Subtle stuff.

Thanks, everyone, for your patience. You've been VERY helpful. Great list!

Michael

--- On Sat, 7/31/10, Brandon S Allbery KF8NH allb...@ece.cmu.edu wrote:

From: Brandon S Allbery KF8NH allb...@ece.cmu.edu
Subject: Re: [Haskell-cafe] Laziness question
To: haskell-cafe@haskell.org
Date: Saturday, July 31, 2010, 2:29 PM

-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 7/31/10 14:24 , michael rice wrote:
 Are you saying:
 
 [ head x ]  -  [ *thunk* ]   and   length [ *thunk* ] -  1, independent of
 what *thunk* is, even head [], i.e., *thunk* never needs be evaluated?

Exactly.  (I was being cagey because the first response was cagey, possibly
suspecting a homework question although it seems like an odd time for it.)

length not only does not look inside of the thunk, it *can't* look inside
it; all it knows is that it has a list, it specifically does *not* know what
that list can hold.  So the only thing it can do is count the number of
unknown somethings in the list.

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

iEYEARECAAYFAkxUa54ACgkQIn7hlCsL25XVpgCeIxWwVWhjYQQ86uE2JeJD7mCB
mKUAn3WwhrgrYyudv/E8pn5a0HB4gLA9
=H++/
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe



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


[Haskell-cafe] Type Families: deleting from HList.

2010-07-31 Thread Serguey Zefirov
Is it possible to delete an element from heterogenous list using type
families alone?

I can do it using multiparameter type classes:
class Del a list result
instance Del a (a,list) list
instance Del a list list' = Del a (a',list) list'
instance Del a () ()

I tried to express the same using type families:
type family Del a list
type instance Del a () = ()
type instance Del a (a,list) = list
type instance Del a (a',list) = (a',Del a list)

to no avail. I got conflicting family instance declarations error.

I tried to express that with associated type synonyms that contains
both multiparameter type classes and type families:
class HDel a list where type Del a list
instance HDel a () where type Del a () = ()
instance HDel a (a,list) where type Del a (a,list) = list
instance HDel a list = HDel a (a',list) where type Del a (a',list) =
(a',Del a list)

And I once again got conflicting family instance declaration.

It looks like right now there is no way to express type equality or
inequality with type families, even when they are combined with
multiparameter type classes.

What is the right way to express something like that? Only MPTC?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Microsoft's Singularity Project and Haskell

2010-07-31 Thread David Leimbach
Haskell's great and all but it does have a few warts when it comes to how
much real trust one  should put into the type system.

Some compromises still exist like unsafePerformIO that you can't detect
simply by looking at the types of functions.

In order to live up to the hype and the marketing around Haskell, really
things like unsafePerformIO should not be allowed at all.

The type of

unsafePerformIO $ fireTheMissles  return 3 ::Int

is just Int after all.

Does Singularity also have such back doors?

Dave

On Sat, Jul 31, 2010 at 6:53 AM, Alberto G. Corona agocor...@gmail.comwrote:

 I guess that the house 
 OShttp://www.google.com/search?hl=ensafe=offq=+house+OS+haskellaq=faqi=g-sx7aql=oq=gs_rfai=has
  no one of these problems that singularity tries to solve in the first
 place.

 The problem of general OSs is: we have unsafe code, so what we do to deal
 with it?. The usual option is the isolation trough virtual addresses so that
 every pointer address is virtual. This imposes cost in task switching and
 pointer handling.   The singularity alternative seems to be to check the
 managed code for pointer violations at installation time.

 In singularity they pretend to extend the reach of types, defined in .NET
 at the assembly level for inter program and inter language safety, to  the
 OS level for runtime safety. This goal is interesting, because a well
 defined type system, without unsafe operations permitted, managed at the OS
 level could permit pure code to run wildly in real memory very fast, for
 example. With effects defined in the type system the advantages may be
 greater.


 2010/7/31 Tim Matthews tim.matthe...@gmail.com


 SPJ http://research.microsoft.com/en-us/people/simonpj/default.aspx and
 probably many others are actually employed at Microsoft research centers. It
 looks like Microsoft just hasn't been able to find a suitable spot to push
 Haskell. Haskell influenced F# because they needed a functional language
 that targeted CLR, and included OO and mutable data.


 IMO Haskell is even better than their languages


 Maybe so but singularity actually provides the whole os apis via clr
 interfaces compared to mainstream windows os where the underlying apis are
 all in C, C++ and COM. The common intermediate language is not tied to any
 specific programming language such as C# or VB, it's more generic than that,
 and has it's advantages. Safety is something they wish to achieve but afaik
 their main goal is to write an OS in managed code.

 Haskell does provide a safe runtime but afaik unlike the clr it's tied to
 the haskell language. I think there has also been some attempts to write an
 OS in haskell too though, but that's another story...

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



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


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


Re: [Haskell-cafe] dear traversable

2010-07-31 Thread wren ng thornton

Claude Heiland-Allen wrote:

On 31/07/10 12:13, wren ng thornton wrote:

Stephen Tetley wrote:

wren ng thornton wrote:

Ben wrote:


unzipMap :: M.Map a (b, c) - (M.Map a b, M.Map a c)
unzipMap m = (M.map fst m, M.map snd m)


I don't think you can give a more efficient implementation using the
public
interface of Data.Map. You need to have a sort of mapping function that
allows you to thread them together, either via continuations or via a
primitive:


Unless I'm missing something. This one has one traversal...

unzipMap :: Ord a = M.Map a (b, c) - (M.Map a b, M.Map a c)
unzipMap = M.foldrWithKey fn (M.empty,M.empty)
where
fn k a (m1,m2) = (M.insert k (fst a) m1, M.insert k (snd a) m2)


Well, that's one traversal of the original map, but you have to traverse
the new maps repeatedly with all those M.insert calls. And since
Data.Map is a balanced tree, that could lead to a whole lot of work
rebalancing things.

However, because we are not altering the set of keys, we are guaranteed
that the structure of both new maps will be identical to the structure
of the old map. Therefore, with the right primitives, we can keep one
finger in each of the three maps and traverse them all in parallel
without re-traversing any part of the spine. (The Either and Or variants
will have some retraversal as the smart constructors prune out the spine
leading to deleted keys. But this is, arguably, necessary.)


Why not something like this (with the correctness proof as an exercise):

\begin{code}

import Data.Map (Map)
import qualified Data.Map as M

unzipMap :: Map a (b, c) - (Map a b, Map a c)
unzipMap m =
  let (ab, ac) = unzip . map fiddle . M.toAscList $ m
  in  (M.fromDistinctAscList ab, M.fromDistinctAscList ac)
  where
fiddle :: (x, (y, z)) - ((x, y), (x, z))
fiddle (x, (y, z)) = ((x, y), (x, z))

\end{code}


That O(n)+O(n) is much better than the O(n)*2*O(log n) 
foldrWithKey/insert version. But it's still about the same as the 
original 2*O(n) map fst/map snd version. With the primitive I mentioned 
we could reduce the constant factor by about half.


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


Re: [Haskell-cafe] dear traversable

2010-07-31 Thread wren ng thornton

wren ng thornton wrote:
That O(n)+O(n) is much better than the O(n)*2*O(log n) 
foldrWithKey/insert version. But it's still about the same as the 
original 2*O(n) map fst/map snd version. With the primitive I mentioned 
we could reduce the constant factor by about half.


Oops, the foldrWithKey/insert should be O(n) + n*2*O(log n).

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


Re: [Haskell-cafe] Re: Microsoft's Singularity Project and Haskell

2010-07-31 Thread Serguey Zefirov
2010/7/31 David Leimbach leim...@gmail.com:
 Haskell's great and all but it does have a few warts when it comes to how
 much real trust one  should put into the type system.
 Some compromises still exist like unsafePerformIO that you can't detect
 simply by looking at the types of functions.

Okay, you should look into modules' imports. This worked well for Ada
(as far as I can remember - but I didn't program, i just read a book;)
and wasn't concern back then and isn't now.

 In order to live up to the hype and the marketing around Haskell, really
 things like unsafePerformIO should not be allowed at all.

You can use Haskell to generate quite safe code and that generator
will use much of haskell type system while not suffering from
unsafePerformIO.

 The type of
 unsafePerformIO $ fireTheMissles  return 3 ::Int
 is just Int after all.
 Does Singularity also have such back doors?

This is what new Microsoft OS Barrelfish does:
http://www.barrelfish.org/fof_plos09.pdf
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Can we come out of a monad?

2010-07-31 Thread aditya siram
Each monad implementation is different. In the case of the State monad your
'execState' call extracts a non-monadic value.

Of the basic monads I found the State monad the most confusing because of
the complicated way in which it threads state through the computation. In
the end, desugaring the do-notation and tracing through the code manually
was the most helpful to me so I encourage you to do the same. After I did
this a couple of times I got the gist of it.

I have attached a trace of your State monad functions 'modifiedImage' and
'drawPixels' which shows the intermediate stages explicitly. If you follow
the steps you will see that there is no magic in how a non-monadic value is
extracted from the State monad.

Let me know if I can be of more help.

-deech


When I am looking at a confusing monad like the State monad

On Fri, Jul 30, 2010 at 1:23 AM, C K Kashyap ckkash...@gmail.com wrote:

 Hi,
 In the code here -
 http://hpaste.org/fastcgi/hpaste.fcgi/view?id=28393#a28393
 If I look at the type of modifiedImage, its simply ByteString - but isn't
 it actually getting into and back out of the state monad? I am of the
 understanding that once you into a monad, you cant get out of it? Is this
 breaking the monad scheme?
 --
 Regards,
 Kashyap

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


-- First we need some pieces from the Monad library 
newtype State s a = State {runState :: a - (a,s)}
  = runState :: State s a - (a - (a,s)) 

execState = snd (runState m s)

-- Bind operation for State monads
m = k = State $ \s - let
  (a, s') = runState m s
in runState (k a) s'
  
-- Your example with the last two 'setPixel ...' lines removed for simplicity
drawPixels = do
  setPixel 5 10 (255, 255, 255)
  setPixel 100 100 (255, 0, 0)
  setPixel 101 100 (255, 0, 0)
  
modifiedImage = execState drawPixels  blankImage

-- Your example with each call to 'setPixel ...' replaced with some shortened
-- names. So, for example, pix_5_10 = setPixel 5 10 (255,255,255)
drawPixels = do
  pix_5_10
  pix_100_100
  pix_101_100
 
-- Desugared version of drawPixel
drawPixels
  = pix_5_10  =
\_ - pix_100_100 = 
\_ - pix101_100

-- Trace of drawPixels  
drawPixels
  = State $ \s - let (a,s') = runState (State (\a - ((), pix_5_10 a))) s
in runState ((\_ - State (\a - ((),pix_100_100 a)) =
  \_ - State (\a - ((),pix_101_100 a))) a)
 s'
   
  = State $ \s - runState ((\_ - State $ \a - ((),pix_100_100 a) =
 \_ - State $ \a - ((),pix_101_100 a)) ())
(pix_5_10 s)
  = State $ \s - runState (State $
   \s - runState (State $ \a - ((),pix_101_100 
a)) $ pix_100_100 s)
   (pix_5_10 s)
  = State $ \s - runState (State $
   \s - (\a - ((),pix_101_100 a)) $ pix_100_100 s)
   (pix_5_10 s')
  = State $ \s - (\s - \a - ((),pix_101_100 a) $ pix_100_100 s) pix_5_10 s   


-- Trace of modifiedImage
modifiedImage = execState drawPixels blankImage
  = execState (State $ \s - (\s - \a - ((),pix_101_100 a) $ 
pix_100_100 s) pix_5_10 s) blankImage
  = snd (\s - (\s - \a - ((),pix_101_100 a) $ pix_100_100 s) 
pix_5_10 s) blankImage
  = snd ((\s - (\a - ((),pix_101_100 a)) $ pix_100_100 s) $ 
pix_5_10 blankImage
  = snd ((\a - ((),pix_101_100 a)) pix_100_100 $ pix_5_10 
blankImage)
  = snd ((), pix_101_100 $ pix_100_100 $ pix_5_10 blankImage)
  = pix_101_100 $ pix_100_100 $ pix_5_10 blankImage

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


Re: [Haskell-cafe] Re: Microsoft's Singularity Project and Haskell

2010-07-31 Thread wren ng thornton

David Leimbach wrote:

Haskell's great and all but it does have a few warts when it comes to how
much real trust one  should put into the type system.

Some compromises still exist like unsafePerformIO that you can't detect
simply by looking at the types of functions.

In order to live up to the hype and the marketing around Haskell, really
things like unsafePerformIO should not be allowed at all.


As I mentioned in the thread about escaping monads, you actually have a 
proof obligation in order to use unsafePerformIO. The only problem is 
that those obligations are not captured in the source language itself, 
so you must trust the code you link against, separately from any trust 
induced by type checking.


There are very real reasons for wanting a function that can take an IO A 
into A, which is why unsafePerformIO was added in the FFI addendum. The 
only way to correct this situation is to (a) add a proof theory to the 
Haskell language, a la dependent types; or, (b) to break apart the IO 
sin bin so that we can track the more innocuous parts independently from 
launching missiles. Of course, the second approach also requires proof 
that information from the, e.g., RTS monad does not leak into the return 
value of runRTS. To do this in general without loosing the power we want 
from RTS, we'll need to add a proof theory to the language in order to 
demonstrate that two functions are extensionally equal. So really, the 
first option is the only one; in which case you might as well switch to 
Agda or the like.


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


Re: [Haskell-cafe] Laziness question

2010-07-31 Thread wren ng thornton

Brandon S Allbery KF8NH wrote:

michael rice wrote:

Are you saying:

[ head x ]  -  [ *thunk* ]   and   length [ *thunk* ] -  1, independent of
what *thunk* is, even head [], i.e., *thunk* never needs be evaluated?


Exactly.  (I was being cagey because the first response was cagey, possibly
suspecting a homework question although it seems like an odd time for it.)

length not only does not look inside of the thunk, it *can't* look inside
it; all it knows is that it has a list, it specifically does *not* know what
that list can hold.  So the only thing it can do is count the number of
unknown somethings in the list.


Not entirely true:

stupidlyStrictLength :: [a] - Integer
stupidlyStrictLength [] = 0
stupidlyStrictLength (x:xs) = x `seq` 1 + stupidlyStrictLength xs

Though, of course, if we actually wanted this function we should use an 
accumulator in order to avoid stack overflow when evaluating the 
(1+(1+...0)) thunk at the end.


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


Re: [Haskell-cafe] Laziness question

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

On 7/31/10 16:58 , wren ng thornton wrote:
 Brandon S Allbery KF8NH wrote:
 michael rice wrote:
 Are you saying:

 [ head x ]  -  [ *thunk* ]   and   length [ *thunk* ] -  1, independent of
 what *thunk* is, even head [], i.e., *thunk* never needs be evaluated?

 Exactly.  (I was being cagey because the first response was cagey, possibly
 suspecting a homework question although it seems like an odd time for it.)

 length not only does not look inside of the thunk, it *can't* look inside
 it; all it knows is that it has a list, it specifically does *not* know what
 that list can hold.  So the only thing it can do is count the number of
 unknown somethings in the list.
 
 Not entirely true:
 
 stupidlyStrictLength :: [a] - Integer
 stupidlyStrictLength [] = 0
 stupidlyStrictLength (x:xs) = x `seq` 1 + stupidlyStrictLength xs

Given all the messes seq makes (hey, go behind the compiler's back and
touch this arbitrary value of arbitrary type), I generally consider it to
be unsafeSeq :)

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

iEYEARECAAYFAkxUlg4ACgkQIn7hlCsL25U41ACgy88GrDKrhfhNn8IiwYPA92qw
Kn0AnilNyNJsPZXKIp86NEuWW4ECLVuv
=hsLW
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Microsoft's Singularity Project and Haskell

2010-07-31 Thread Felipe Lessa
On Sat, Jul 31, 2010 at 5:23 PM, David Leimbach leim...@gmail.com wrote:
 Does Singularity also have such back doors?

The CLR doesn't load machine code, it loads bytecodes.  So it is
possible to statically analyse the module and see hmmm, this module
uses unsafePerformIO, I'll reject it.  If the bytecode is ok, only
then it is JITed into efficient machine code.

And note that we wouldn't need unsafePerformIO for the FFI if all
programs were made in Haskell ;).

Cheers,

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


Re: [Haskell-cafe] Re: Microsoft's Singularity Project and Haskell

2010-07-31 Thread Thomas DuBuisson
 And note that we wouldn't need unsafePerformIO for the FFI if all
 programs were made in Haskell ;).

Perhaps that's true, though entirely unrealistic, in the application
world.  In the OS world you need access to machine registers and
special instructions (CR3 anyone? CP15?) which isn't built into any
language save assembly - for these FFI will always come in handy.

Also, Haskell continues to have an unfortunate lack of primitives
suitable for casting types (ex: zero copy form a bytestring like
entity to Word32s).  In this realm FFI can outperform cleaner looking
code that must rely on individual byte reads.

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


[Haskell-cafe] Re: dear traversable

2010-07-31 Thread Ben
dear applicative geniuses --

thanks for all the help.  some comments :

1) the fromList / unzip versions are nice but as others have pointed
out, construction is more expensive than traversal (or traversal w/
copying, like Data.Map.map.)  hopefully the maintainers of Data.Map et
al will consider adding one-traversal unzip functions.

2) i too would love John Meacham's unionWithJoin function.  i might
call that outerJoin myself.  there was discussion about this at some
point in time on the libraries list, i'm not sure what happened to it.

3) wren, thanks for the (applicative) pointer.  when i tried to
interrogate hoogle it pointed me there too -- though i had to boil
down my question several times.  i think it went something like this

Map a (b - c) - Map a b - Map a c
-- no answer

m a (b - c) - m a b - m a c
-- no answer

m (b - c) - m b - m c
-- * and a million other hits

at which point i'd practically answered the question myself.  this is
not a knock on hoogle -- i often have this experience, it seems to
lead me in the right direction Socratically.

4) ross, i had to ask ghci to even believe your code type-checks!  i
didn't realize currying worked that way -- i've never thought to pass
in functions of different arities.  as an experiment, i tried

Prelude Data.Map :t intersectionWith 1
intersectionWith 1
  :: (Num (a - b - c), Ord k) = Map k a - Map k b - Map k c

Prelude Data.Map :t intersectionWith (const 1)
intersectionWith (const 1)
  :: (Num (b - c), Ord k) = Map k a - Map k b - Map k c

Prelude Data.Map :t intersectionWith id
intersectionWith id
  :: (Ord k) = Map k (b - c) - Map k b - Map k c

Prelude Data.Map :t intersectionWith (\a b c - c)
intersectionWith (\a b c - c)
  :: (Ord k) = Map k a - Map k b - Map k (t - t)

all of which make sense to me now, but still honestly blow my mind!

best regards, b

ps actually the first two don't make much sense to me, when i think
about it.

On Fri, Jul 30, 2010 at 8:13 PM, Ben midfi...@gmail.com wrote:
 dear traversable geniuses --

 i am looking for better implementations of

 unzipMap :: M.Map a (b, c) - (M.Map a b, M.Map a c)
 unzipMap m = (M.map fst m, M.map snd m)

 unliftMap :: (Ord a) = M.Map a (b - c) - M.Map a b - M.Map a c
 unliftMap mf ma = M.mapWithKey (\k v - mf M.! k $ v) ma

 the first is obviously inefficient as it traverses the map twice.  the
 second just seems like it is some kind of fmap.

 any ideas?

 ben

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


Re: [Haskell-cafe] Re: Microsoft's Singularity Project and Haskell

2010-07-31 Thread wren ng thornton

Thomas DuBuisson wrote:

And note that we wouldn't need unsafePerformIO for the FFI if all
programs were made in Haskell ;).


Perhaps that's true, though entirely unrealistic, in the application
world.  In the OS world you need access to machine registers and
special instructions (CR3 anyone? CP15?) which isn't built into any
language save assembly - for these FFI will always come in handy.

Also, Haskell continues to have an unfortunate lack of primitives
suitable for casting types (ex: zero copy form a bytestring like
entity to Word32s).  In this realm FFI can outperform cleaner looking
code that must rely on individual byte reads.


The FFI doesn't always require unsafePerformIO, it's just there for 
those cases where the foreign function is truly side-effecting (and 
therefore should be linked to with the type (...-IO A)) but we know 
it's safe/referentially-transparent to ignore those effects at some call 
site.


You can link to foreign code without giving it an IO type. The zero-copy 
version of converting bytestrings is one example where the foreign 
function is pure, and therefore doesn't need to be linked to as IO.


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


Re: [Haskell-cafe] Re: Microsoft's Singularity Project and Haskell

2010-07-31 Thread Thomas DuBuisson
On Sat, Jul 31, 2010 at 8:27 PM, wren ng thornton w...@freegeek.org wrote:
 Thomas DuBuisson wrote:

 And note that we wouldn't need unsafePerformIO for the FFI if all
 programs were made in Haskell ;).

 Perhaps that's true, though entirely unrealistic, in the application
 world.  In the OS world you need access to machine registers and
 special instructions (CR3 anyone? CP15?) which isn't built into any
 language save assembly - for these FFI will always come in handy.

 Also, Haskell continues to have an unfortunate lack of primitives
 suitable for casting types (ex: zero copy form a bytestring like
 entity to Word32s).  In this realm FFI can outperform cleaner looking
 code that must rely on individual byte reads.

 The FFI doesn't always require unsafePerformIO,

True.  I mis-read the previous e-mail as we wouldn't need
unsafePerformIO OR (vs for) the FFI   so please ignore that response
to a non-existent statement!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: dear traversable

2010-07-31 Thread wren ng thornton

Ben wrote:

4) ross, i had to ask ghci to even believe your code type-checks!  i
didn't realize currying worked that way -- i've never thought to pass
in functions of different arities.  as an experiment, i tried


N.B. intersectionWith id == intersectionWith ($), which might cause it 
to make a bit more sense. ($) is an infix version of 'id' restricted to 
function types. But then, ($) is a weird combinator; e.g., flip($) is 
the T combinator for type lifting.





Prelude Data.Map :t intersectionWith 1
intersectionWith 1
  :: (Num (a - b - c), Ord k) = Map k a - Map k b - Map k c

[...]

ps actually the first two don't make much sense to me, when i think
about it.


In order to allow overloading of literals, discrete numeric literals are 
parsed as if wrapped in fromInteger(_::Integer) and continuous numeric 
literals are parsed as if wrapped in fromRational(_::Rational). Thus,


Prelude :t 1
1 :: (Num t) = t
Prelude :t 1.0
1.0 :: (Fractional t) = t

So, since intersectionWith is expecting an (a-b-c) we figure out that 
1 must be interpreted as belonging to that type, which means we need a 
Num(a-b-c) instance.


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


[Haskell-cafe] Re: what's the best environment for haskell work?

2010-07-31 Thread rustom
On Jul 31, 7:21 pm, Joachim Breitner m...@joachim-breitner.de wrote:
 Hi,

 Am Samstag, den 31.07.2010, 15:37 +0530 schrieb Rustom Mody:

  Do most people who work with haskell use emacs/vi/eclipse or something
  else??

  Personal Note: I used gofer some 15 years ago.  At that time I hacked
  up a emacs mode (I did not know of any then) along with some changes
  to gofer to have gofer inside emacs rather than vi inside gofer.

  Things have got more exciting now -- just trying to catch up!!

  [Note: My preferrred/default OS is debian-squeeze]

 I’m using vim myself, but the Debian Haskell Team has packaged leksah
 and it is available in squeeze. If you have any problems with the
 packaging, we would like to hear about them.

 (So far, we had zero feedback from leksah users on Debian, so I don’t
 know if there exist any)

 Greetings,
 Joachim

I guess I am going to start with emacs -- since that seems to work (re
Johan Tibell above).

However I do have an issue regarding debian packaging.

At first I installed ghc
This brought in

ghc6 ghc6-doc libbsd-dev libgmp3-dev libgmpxx4ldbl

I also added haskell98-report haskell98-tutorial darcs

Then I discovered haskell-platform. I was pleased to discover that the
link took me directly to the squeeze repos so there is no version
mismatch between haskell-platorm and squeeze.

apt-getting haskell-platform gave me

alex cabal-install happy haskell-platform libghc6-cgi-dev
libghc6-deepseq-dev libghc6-glut-dev libghc6-haskell-src-dev
libghc6-html-dev libghc6-http-dev libghc6-hunit-dev
libghc6-network-dev libghc6-opengl-dev libghc6-parallel-dev
libghc6-parsec2-dev libghc6-quickcheck2-dev libghc6-stm-dev
libghc6-xhtml-dev

However when trying to compile ghc from source I got an error that
wanted ghc6-prof
So I got that

Looking around in synaptic (gui for apt) I find that there are a large
number of libghc-somethings that I still have not got.

So then the question: Whats the real point of the haskell-platform
package -- if specific libraries have to be got separately?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe