[Haskell-cafe] Re: [Haskell] View patterns in GHC: Request for feedback

2007-07-24 Thread apfelmus
Simon Peyton-Jones wrote:
 Views have been the subject of rather inconclusive debate for a long time,
 certainly since the inception of Haskell. I'm thinking of pattern
views as a way
 to break the logjam by implementing something that is a reasonable stab,
 and seeing whether it sticks. I thought of pattern guards in the
same way,
 and they certainly seem to have stuck. But we can only find out by
trying it out.

What I fear the most is exactly that this proposal sticks and becomes
the de-facto standard :(

IMHO, the long-time debate about views is not whether they're useful (I
think they are!) but which concrete form to choose. Unfortunately, all
of the proposals so far are somehow like Dr. Jekyll and Mr. Hyde: one
side is nice but the other is rather ugly.

In the end, I might end up using the currently proposed pattern views,
not because I'm fond of the proposal but simply because they're
implemented and the pain of not using views is too big.

Regards,
apfelmus

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


[Haskell-cafe] Re: [Haskell] View patterns in GHC: Request for feedback

2007-07-25 Thread apfelmus
Jules Bean wrote:
 Have you tried using pattern guards for views?
 
 f s | y : ys - viewl s = 
 | EmptyL  - viewl s = 

Hm, I'd simply use a plain old case-expression here

  f s = case viewl s of
 y : ys - ...
 EmptyL  - ...

In other words, case-expressions are as powerful as any view pattern may
be in the single-parameter + no-nesting case.


A better example is probably  zip  for sequences (Data.Sequence.Seq):

  zip :: Seq a - Seq b - Seq (a,b)
  zip xs ys = case viewl xs of
 x : xt - case viewl ys of
 y : yt - (x,y) | zip xt yt
 EmptyL  - empty
 EmptyL  - empty

Pattern guards

  zip xs ys
| EmptyL - viewl xs = empty
| EmptyL - viewl ys = empty
| x : xt - viewl xs, y : yt - viewl ys = (x,y) | zip xt yt

Pattern guards variant

  zip xs ys
|  EmptyL - xs' = empty
|  EmptyL - ys' = empty
| x : xt - xs', y : yt - ys' = (x,y) | zip xt yt
where
xs' = viewl xs; ys' = viewl ys

View patterns

  zip (viewl - EmptyL) _  = empty
  zip _  (viewl - EmptyL) = empty
  zip (viewl - x : xs) (viewl - y : ys) = (x,y) | zip xs ys

My dream

  zip EmptyL  _   = empty
  zip _   EmptyL  = empty
  zip (x:xs) (y:ys) = (x,y) | zip xs ys


Regards,
apfelmus

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


[Haskell-cafe] Re: [Haskell] View patterns in GHC: Request for feedback

2007-07-25 Thread apfelmus
Benjamin Franksen wrote:
 apfelmus wrote:

 In other words, case-expressions are as powerful as any view pattern may
 be in the single-parameter + no-nesting case.

 This is how I do it, no pattern guards, no view patterns:
 
 zip :: Seq a - Seq b - Seq (a,b)
 zip xs ys = case (viewl xs,viewl ys) of
   (EmptyL,  _  ) - empty
   (_,   EmptyL ) - empty
   (x : xt, y : yt) - (x,y) | zip xt yt
 
 This is IMHO a lot clearer than any of the alternatives you listed, except
 your 'dream' (which is exactly what 'real' views would give us).

Splendid! That lifts the single-parameter restriction. Let's also lift
the no-nesting restriction with an audacious use of rank-2-polymorphism!
The idea is that we may match a polymorphic type (forall a . a) against
as many different pattern types as we wish. In other words, the definition

  foo :: (forall a . a) - String
  foo x = case x of
  eek - ...
  13- ...
  (x,y) - ...

should be just fine. Of course we need a class context like (forall a .
View b a = a) for a polymorphic type to be useful.

Here's (almost) a demonstration for sequence types, the code works with
hugs -98.

class View a b | b - a where
view :: a - b

data Queue a = ...

instance View (Queue a) (Queue a) where
view = id

The view from the left is

data ViewL seq a = EmptyL | a : (forall b . View (seq a) b = b)

where the key trick is to make the second component of : polymorphic.

instance View (Queue a) (ViewL Queue a) where
view q = if null q then EmptyL else head q : view (tail q)

The  zip  function can be defined just like before

zip :: Queue a - Queue b - Queue (a,b)
zip xs ys = case (view xs, view ys) of
(EmptyL,  _  ) - empty
(_,   EmptyL ) - empty
(x : xt, y : yt) - (x,y) `cons` zip xt yt

But now, we can even nest patterns

pairs :: Queue a - Queue (a,a)
pairs xs = case view xs of
x : ys - case ys of
y : zs - (x,y) `cons` pairs zs
_   - empty
_  - empty

Well, that's no true nesting since we'd like to write

pairs xs = case view xs of
x : (y : zs) - (x,y) `cons` pairs zs
_  - empty

but note that we were able to write  case ys of  instead of the
otherwise obligatory  case (view ys) of . With pattern matching on
polymorphic types, real nesting would come in reach. The point is to be
able to define both  zip  and  pairs  with one and the same operator : .


Regards,
apfelmus
Long live the we-want-real-views-or-nothing-at-all movement! :)

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


[Haskell-cafe] Re: Order of evaluation

2007-07-26 Thread apfelmus
Jon Harrop wrote:
 If you have a boolean-or expression:
 
   a || b
 
 will a be evaluated before b in Haskell as it is in other languages?

Yes, although the meaning of the phrase evaluated before is a bit
tricky in a lazy language, so it's probably better to state it with
denotational semantics alone:

   _|_  ||  b  = _|_

Maybe you also want to know whether the second argument is evaluated.
This is answered by

  True  || _|_ = True
  False || _|_ = _|_


Regards,
apfelmus

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


[Haskell-cafe] Re: [Haskell] View patterns in GHC: Request for feedback

2007-07-26 Thread apfelmus
Dan Licata wrote:
 apfelmus wrote:
 The idea is to introduce a new language extension, namely the ability to
 pattern match a polymorphic type. For demonstration, let

   class ViewInt a where
 view :: Integer - a

   instance ViewInt [Bool] where
 view n = ... -- binary representation

   data Nat = Zero | Succ Nat

   instance ViewInt Nat where
 view n = ... -- representation as peano number

 be some views of the integers. Now, I'd like to be able to write

   bar :: (forall a . ViewInt a = a) - String
   bar Zero  = ...
   bar (True:xs) = ...
 
 This doesn't make sense to me:
 
 Zero :: Nat 
 
 and therefore
 
 Zero :: ViewInt Nat = Nat
 
 but you can't generalize from that to 
 
 Zero :: forall a. ViewInt a = a
 
 E.g., Zero does not have type ViewInt [Bool] = Bool

Yes, the types of the patterns don't unify. But each one is a
specialization of the argument type. Note that the type signature is

  bar :: (forall a . ViewInt a = a) - String

which is very different from

  bar :: forall a . ViewInt a = a - String

Without the extension, we would write  bar  as follows

  bar :: (forall a . ViewInt a = a) - String
  bar x = let xNat = x :: Nat in
 case xNat of
   Zero - ...
   _- let xListBool = x :: [Bool] in
  case xListBool of
 True:xs - ...

In other words, we can specialize the polymorphic argument to each
pattern type and each equation may match successfully.

 Maybe you wanted an existential instead

No. That would indeed mean to pick the matching equation by analysing
the packed type, i.e. some equations don't match since their patterns
have the wrong type. I think that such a thing violates parametricity.

Regards,
apfelmus

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


[Haskell-cafe] Re: [Haskell] View patterns in GHC: Request for feedback

2007-07-25 Thread apfelmus
Dan Licata wrote:
 There's actually a quite simple way of doing this.  You make the view
 type polymorphic, but not in the way you did:

 myzip :: Queue a - Queue b - Queue (a,b)
 myzip a b = case (view a, view b) of
   (EmptyL, _) - empty
   (_, EmptyL) - empty
   (h1 : t1, h2 : t2) - (h1,h2) `cons` myzip a b

 pairs :: Queue a - Queue (a,a)
 pairs a = case view2 a of
 h1 : (h2 : t) - (h1, h2) `cons` pairs t
 _ - empty

 The only difference with view patterns is that you can do the view2
 inside the pattern itself:
 
 pairs (view2 - h1 : (h2 : t)) = (h1,h2) `cons` pairs t
 pairs _  = empty
 
 This would be useful if the thing you were viewing were deep inside
 another pattern.

Well, the main feature of view patterns is that you can nest them. In
other words, the canonical way of writing  pairs  would be

  pairs (view - h1 : (view - h2 : t)) = (h1,h2) `cons` pairs t
  pairs _ = empty

Nesting means to decide later on how to pattern match the nested part.
With view2, you have to make this decision before, something I want to
avoid.

For example, take the (silly) definition

  foo :: Queue a - Queue a
  foo xs = case view xs of
 x : (y : zs) - x `cons` zs
 x : ys- ys
 EmptyL - empty

Here, ys  is a Queue and  (y : zs)  is a ViewL. By scrutinizing  xs
via  view , both have to be a Queue. By scrutinizing it via  view2 ,
both have to be a ViewL. But I want to mix them.

The idea is to introduce a new language extension, namely the ability to
pattern match a polymorphic type. For demonstration, let

  class ViewInt a where
view :: Integer - a

  instance ViewInt [Bool] where
view n = ... -- binary representation

  data Nat = Zero | Succ Nat

  instance ViewInt Nat where
view n = ... -- representation as peano number

be some views of the integers. Now, I'd like to be able to write

  bar :: (forall a . ViewInt a = a) - String
  bar Zero  = ...
  bar (True:xs) = ...

Here, the patterns have different types but the key is that is
unproblematic since the polymorphic type is capable of unifying with
each one.

Given this language extension, we can make  foo  a valid definition by
using a polymorphic type as the second component of :

  data ViewL = EmptyL | Integer : (forall a . ViewInt a = a)


In the end, the double-negation translation

Integer
 = (forall a . ViewInt a = a)

can even be done implicitly and for all types. Together with the magic
class View, this would give real views.


Jón Fairbairn wrote:
 It's essential to this idea that it doesn't involve any new
 pattern matching syntax; the meaning of pattern matching for
 overloaded functions should be just as transparent as for
 non-overloaded ones.

That's what the real views would do modulo the probably minor
inconvenience that one would need to use (:) and (EmptyL) instead of
(:) and []. I doubt that the latter can be reused.

Regards,
apfelmus

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


[Haskell-cafe] Re: Zippers, Random Numbers Terrain

2007-07-30 Thread apfelmus
Thomas Conway wrote:
 To amuse myself while waiting for test-runs to complete, I was
 thinking about random terrain generation. I came across a bunch of
 nice posts by Torben Mogensen, where he describes a neat way of
 constructing random terrains by recursively subdividing right angled
 isosceles triangles. It got me thinking - it's all well and good
 subdividing to give more detail as you zoom in, but what about when
 you zoom out?

Can you post a hyperlink for an exact description of the algorithm?

 This got me thinking that it would be cool to make an infinite terrain
 generator using a zipper, so you can zoom in/out infinitely, and by
 implication, infinitely in any direction.

An infinite random terrain sounds like great fun :) I can't say whether
it's possible or whether zippers are needed without knowing the details,
though.

One problem is probably having a point of reference, i.e. one needs a
point (0,0) with a fixed height 0. In the bounded case, one has a
rectangle to subdivide instead.


Regards,
apfelmus

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


[Haskell-cafe] Re: infinite list of random elements

2007-07-31 Thread apfelmus
Chad Scherrer wrote:
 I prefer the purely functional approach as well, but I've
 been bitten several times by laziness causing space leaks in this
 context. I'm on a bit of a time crunch for this, so I avoided the
 risk.

Well, space leaks won't magically disappear if you use  IO a .

Regards,
apfelmus

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


[Haskell-cafe] Re: RLE in Haskell: why does the type variable get instantiated?

2007-07-31 Thread apfelmus
Chris Eidhof wrote:
 When binding the function composition to a variable, the type
 suddenly changes.
 
 Prelude Control.Arrow List :t map (length  head) . group
 map (length  head) . group :: (Eq a) = [a] - [(Int, a)]
 Prelude Control.Arrow List let encode = map (length  head) . group
 Prelude Control.Arrow List :t encode
 encode :: [Integer] - [(Int, Integer)]

You've tripped over the Monomorphism Restriction.

  http://haskell.org/haskellwiki/Monomorphism_restriction
  http://haskell.org/onlinereport/decls.html#sect4.5.5

In short, you have to supply a type signature

  encode :: (Eq a) = [a] - [(Int, a)]
  encode = map (length  head) . group

to get the polymorphic function type when type-classes like  Eq  or
especially  Num  are involved. Without signature, the compiler will
_default_ some the type variables mentioned in the class context to
Integer  or similar.

Note that definitions on the GHCi prompt will receive more defaulting
than those in Haskell source files. This is to make things like

  show []
  1+5

work at the prompt.

Also note that the monomorphism restriction only applies to constant
applicative forms, i.e. point-free definitions of values. In other words,

  encode x = map (length  head) . group $ x

will result in the proper polymorphic type.

Regards,
apfelmus

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


[Haskell-cafe] Re: Zippers, Random Numbers Terrain

2007-08-01 Thread apfelmus
Thomas Conway wrote:
 This got me thinking that it would be cool to make an infinite terrain
 generator using a zipper, so you can zoom in/out infinitely, and by
 implication, infinitely in any direction.

After some pondering, I think it's indeed possible and the zipper is the
right tool for the job. I'll present the idea for constructing a
one-dimensional fractal terrain but it generalizes to higher dimensions.

First, consider the task to construct a 1D fractal height function
defined on a bounded interval like [0,1].

  type Pos  = Double
  type Height   = Double

  terrain :: Interval - Pos - Height

We construct the terrain by dividing the interval in half and adjust the
height of the midpoint randomly relative to the mean of the other heights.

  data Interval = I (Pos,Pos) (Height,Height) StdGen

  terrain :: Interval - Pos - Height
  terrain i x
| x `in` left  = terrain left  x
| x `in` right = terrain right x
where
(left, right)  = bisect i

  in :: Pos - Interval - Bool
  in x (I (a,b) _ _) = a = x  x = b

  bisect :: Interval - (Interval, Interval)
  bisect (I (a,b) (ha,hb) g) =
(I (a,m) (ha,h) ga, I (m,b) (h,hb) gb)
where
m = (a+b)/2
h = (ha+hb)/2 + d * (a-b) * scale
(d,g')  = randomR (0,1) g
(ga,gb) = split g'

The factor  scale  controls the roughness of the terrain. True enough,
the function  terrain  never returns but that shouldn't be an issue to
the mathematician ;) Of course, we have to stop as soon as the interval
length is smaller than some given resolution  epsilon  (i.e. the width
of a pixel). Splitting the random number generator is not necessarily a
good idea, but I don't care right now.


For zoom-in, we want to specify different epsilons and get the same
random values each time. So, we memoize the steps to produce the height
function in an infinite tree

  data Terrain = Branch Terrain (Height,Height) Terrain

  terrain :: Interval - Terrain
  terrain i = Branch (terrain left) h (terrain right)
where
(left, right) = bisect i
I _ h _ = i

The actual rendering can be obtained from the infinite Terrain, I'll
omit it for simplicity.


For finite zoom-out, we use a zipper

  type Zipper  = (Context, Terrain)
  type Context = [Either Terrain Terrain]

  zoomInLeft, zoomInRight :: Zipper - Zipper
  zoomInLeft  (xs, Branch l h r) = (Left  r:xs, l)
  zoomInRight (xs, Branch l h r) = (Right l:xs, r)

  zoomOut :: Zipper - Zipper
  zoomOut (x:xs, t) = case x of
  Left  r - (xs, Branch t (t `joinHeights` r) r)
  Right l - (xs, Branch l (l `joinHeights` t) t)
where
joinHeights (Branch _ (ha,_) _)
(Branch _ (_,hb) _) = (ha,hb)
  zoomOut ([], _) = error You fell out of the picture!

Mnemonics: Left means that we descended into the left half, Right that
we descended into the right half of the interval.


The final step is to allow infinite zoom-out. How to do that? Well,
assume that we generate the landscape on the interval [0,1] and zoom
out. The reverse of this would be to create the landscape on the
interval [-1,1] and then zoom into the right half [0,1]. In other words,
we view [0,1] as the right half of the bigger interval [-1,1]. This in
turn can be viewed as the left half of the even bigger interval [-1,3].
In order to grow both interval bounds to infinity, we alternate between
viewing it as left half and as right half. In other words, the insight
is that *we're inside an infinite context*! Thus, generating an infinite
terrain is like generating a finite one except that we need to generate
the infinite context as well:

  terrainInfinite :: Interval - Zipper
  terrainInfinite i = (right i, terrain i)
where

right (I (m,b) (h,hb) g) = Right (terrain l) : left  i
  where
  l  = fst $ bisect i
  i  = I (a,b) (ha,hb) g'
  a  = m  - (b -m)
  ha = hb - (hb-h) + d * (a-b) * scale
  (d,g') = randomR (0,1) g

left  (I (a,m) (ha,h) g) = Left  (terrain r) : right i
  where
  r  = snd $ bisect i
  i  = I (a,b) (ha,hb) g'
  b  = m + (m-a )
  hb = h + (h-ha) + d * (a-b) * scale
  (d,g') = randomR (0,1) g

Here,  left  starts by extending a given interval to the right and
right   starts by extending it to the left.

It would be nice to run the random generator backwards, the generator
transitions in  terrainInfinite  are surely wrong, i.e. too
deterministic. Also, the scale of the random height adjustment  d  is
probably wrong. But those things are exercises for the attentive reader ;)


That concludes the infinite terrain generation for one dimension. For
higher dimension, one just needs to use 2D objects instead of intervals
to split into two or more pieces. For instance, one can divide
equilateral triangles into 4 smaller ones. In fact, it doesn't matter
whether the starting triangle is equilateral or not when using the
midpoints of the three sides to split it into four smaller triangles.

Regards,
apfelmus

[Haskell-cafe] Re: monad subexpressions

2007-08-03 Thread apfelmus
Chris Smith wrote:
 I've heard Simon (Peyton-Jones) twice now mention the desire to be able 
 to embed a monadic subexpression into a monad.  That would be 
 http://article.gmane.org/gmane.comp.lang.haskell.prime/2267 and in the 
 recent OSCON video.

I still think that this syntax extension has profound impact and is a
bad idea. Simon's and Neill's use case was the dreaded name-supply monad
where the order of effects really doesn't matter up to alpha-conversion.
The objection to that use case is that monads are not the right
abstraction for that, they're too general. Also, a workaround is to lift
functions

  f :: a - b - m c
  g :: d - m b

to

  f' :: m a - m b - m c
  g' :: m d - m b

and thus flip the need for argument sugar

  f $(g x) y   VS   f' (g' (r$ x)) (r$ y)

With r = return, the latter is Haskell98. See also

  http://thread.gmane.org/gmane.comp.lang.haskell.prime/2263/focus=2267

 Also, I got so frustrated that I ended up abandoning some code
 recently because STM is, in the end, so darn hard to use as a
 result of this issue. I'd love to see this solved, and I'm quite
 eager to do it.

This sounds suspicious, since the order of effects is of course
important in the STM monad. Can you post an example of code you intend
to abandon due to ugliness? I'd be astonished if there's no better way
to write it.

Regards,
apfelmus

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


[Haskell-cafe] Re: monad subexpressions

2007-08-03 Thread apfelmus
 the problem of programming with
monads in an applicative style. I would be sad if you'd ignore them in
case they solve your STM-code problem without compiler extension.

Regards,
apfelmus

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


[Haskell-cafe] Re: monad subexpressions

2007-08-04 Thread apfelmus
Sebastian Sylvan wrote:
 Claus Reinke wrote:
 mytransaction = do {
  x0 - readTVar xvar0
  x1 - readTVar xvar1
  :
  xn - readTVar xvarn
  return $ foo x0 x1 .. xn
 }

 ah, a concrete example. but isn't that the typical use case for ap?

 mytransaction = foo `liftM` r xvar0 `ap` r xvar1 ..
 where r = readTVar
 
 I really find it difficult to articulate why this isn't acceptable,
 because it seems so obvious to me! It's short yes, but I really don't
 think it's very clear...
 I have a hard time believing that anyone finds that natural.

I think it's entirely natural :)

Applicative functors (Control.Applicative) are the pattern behind this.
The notation may seem a little weird first, but in the end, `ap` is a
kind of explicit function application and similar to $. With the
notation from Control.Applicative, the line

  return foo `ap` r xvar0 `ap` r xvar1 `ap` ...

reads

  pure foo * r xvar0 * r xvar1 * ...

or

  foo $ r xvar0 * r xvar1 * ...

In other words, instead of using juxtaposition to apply an argument to a
 function, we use *. The type of `ap` is

  ap :: m (a - b) - m a - m b

so that it can be thought of as a generalized function application where
the function is under a monad.

The difference to $ is that * is left associative and allows for
currying. I.e. * is like $ used in the following way

  ((foo $ x0) $ x1) $ x2


Note that you can even incorporate the TVar by defining your own
generalized function application:

  apT :: STM (a - b) - TVar a - STM b
  apT f x = f `ap` readTVar x

Then,  mytransaction  reads

  mytransaction = return foo `apT` xvar0 `apT` xvar1 `apT` ...


Regards,
apfelmus

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


[Haskell-cafe] Re: Developing Programs and Proofs Spontaneously using GADT

2007-08-04 Thread apfelmus
Shin-Cheng Mu wrote:
 I am curious about the possibility of developing Haskell programs
 spontaneously with proofs about their properties and have the
 type checker verify the proofs for us, in a way one would do in
 a dependently typed language.
 
 In the exercise below, I tried to redo part of the merge-sort
 example in Altenkirch, McBride, and McKinna's introduction to
 Epigram [1]: deal the input list into a binary tree, and fold
 the tree by the function merging two sorted lists into one.
 The property I am going to show is merely that the length of
 the input list is preserved.

Cool! :)

 Given that dependent types and GADTs are such popular topics,
 I believe the same must have been done before, and there may be
 better ways to do it. If so, please give me some comments or
 references. Any comments are welcomed.
 
 {-# OPTIONS_GHC -fglasgow-exts #-}
 
 To begin with, we define the usual type-level representation
 of natural numbers and lists indexed by their lengths.
 
 data Z = Z   deriving Show
 data S a = S a   deriving Show
 
 data List a n where
   Nil :: List a Z
   Cons :: a - List a n - List a (S n)
 
 1. Append
 
 To warm up, let us see the familiar append example.
 Unfortunately, unlike Omega, Haskell does not provide type
 functions. I am not sure which is the best way to
 emulate type functions. One possibility is to introduce
 the following GADT:
 
 data Plus m n k where--- m + n = k
   PlusZ :: Plus Z n n
   PlusS :: Plus m n k - Plus (S m) n (S k)
 
 such that Plus m n k represents a proof that m + n = k.

Wouldn't type families (~ associated type synonyms) do exactly that once
they become available?

  type family   Plus :: * - * - *
  type instance Plus Z n = n
  type instance Plus (S m) n = S (Plus m n)

  append :: (Plus m n ~ k) = List a m - List a n - List a k
  append Nil ys = ys
  append (Cons x xs) ys = Cons x (append xs ys)

But I'd guess that there are some constraints on the type family
instance declarations to keep things decidable.

Viewed with the dictionary translation for type classes in mind, this is
probably exactly the alternative type of append you propose:

  append :: Plus m n k - List a m - List a n - List a k

 However, this does not type check. Assume that t has size
 n1, and u has size n. The DepSum returned by merge consists
 of a list of size i, and a proof p of type Plus m n i, for
 some i. The proof p1, on the other hand, is of type P m n k
 for some k. Haskell does not know that Plus m n is actually
 a function and cannot conclude that i=k.
 
 To explicitly state the equality, we assume that there is
 a function plusFn which, given a proof of m + n = i and
 a proof of m + n = k, yields a function converting an i
 in any context to a k. That is:
 
   plusFn :: Plus m n i - Plus m n k
   - (forall f . f i - f k)

 How do I define plusFn? I would like to employ the techniques
 related to equality types [3,4,5], but currently I have not
 yet figured out how. I've merely produced a version of
 plusFn specialised to List a:
 
 plusFn :: Plus m n h - Plus m n k - List a h - List a k
 plusFn PlusZ PlusZ xs = xs
 plusFn (PlusS p1) (PlusS p2) (Cons x xs) =
 Cons x (plusFn p1 p2 xs)
 
 Needless to say this is not satisfactory.

I remember that the

  newtype Equal a b = Proof (forall f . f a - f b)

type equality has been used to define/implement GADTs

  Ralf Hinze. Fun with phantom types.
  http://www.informatik.uni-bonn.de/~ralf/publications/With.pdf

so a general  plusFn  ought to be possible. I think that the following
induction should work (untested!):

  equalZ :: Equal Z Z
  equalS :: Equal m n - Equal (S n) (S m)

  plusFn :: Plus m n i - Plus m n k - Equal i k
  plusFn PlusZ PlusZ = equalZ
  plusFn (PlusS x) (PlusS y) = equalS (plusFn x y)

with the trivial equality proofs for natural numbers

  equalZ = Proof id

  newtype Succ f a  = InSucc { outSucc :: f (S a) }
  equalS (Proof eq) = Proof (outSucc . eq . InSucc)

The newtype is just for making the type checker recognize that  f (S a)
is indeed of the form  g a  for some type constructor  g .

Regards,
apfelmus

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


[Haskell-cafe] Re: creating graphics the functional way

2007-08-06 Thread apfelmus
Frank Buss wrote:
 I've created a small program to compose images with combinators:
 
 http://www.frank-buss.de/haskell/OlympicRings.hs.txt

 Finally, what do you think about using this concept for generating
 images? It has some advantages, e.g. it is possible to scale the
 image without quality loss. But it needs some improvement, e.g. the
 anti-aliasing doesn't look very smooth. And it is very slow, it
 needs about 40 seconds on my computer to calculate the image.

The idea of representing images simply by a function

  Int - Int - RGB

is great :) You may want to look at  Pan  and its various offsprings, in
particular  Pancito

http://www.haskell.org/haskellwiki/Applications_and_libraries/Graphics#Pan

Unfortunately, there's not much you can do about the speed.  Pan  is
faster, but it creates the illusion that you're programming in Haskell
while internally, it compiles the image generation code to C++. Very
clever, but hard to maintain and one of the reasons why it only works on
Windows.

 There are many functions like circle1Center, circle2Center, ... Is it
 possible to rewrite the program that it will be shorter, maybe using lists
 or an interpreter for a language for this kind of combinator programming
 style?

Well, you have lists for that

  type Point = (Int,Int)

  positions :: [Point]
  positions =
zip [0.5 + fromIntegral n * dx | n - [-2..2]] (cycle [y1,y2])
where
dx = 0.125
y1 = 0.15
y2 = 0.25

  colors :: [RGB]
  colors = [blue, yellow, black, green, red]

  type Image = Point - RGB

  circles :: RGB - [Image]
  circles background = map circle (zip positions colors)
where
circle (p,c) =
   fillMask (translate p ringCenter) c
   $ fillMask (translate p ringOutline) white background

 Is it possible to write functions with an arbitrary number of arguments?
 Would be nice if the average function would accept any number of pixel
 values.

Lists are the natural choice here.

 Is there a PNG writer library for Haskell? I've seen a zlib interface,
 should be not too difficult to implement it in Haskell itself.

Not that I know of. But gtk2hs has a Cairo-binding and I guess this one
supports PNG. Note that this is vector graphics though, your approach is
more general.

Regards,
apfelmus

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


[Haskell-cafe] Re: Navigating Haddock

2007-08-06 Thread apfelmus
Marc Weber wrote:
 On Sun, Aug 05, 2007 at 03:19:25PM -0700, David Pollak wrote:
Howdy,
As I'm starting to learn the Haskell libraries, I'm having a less than
fun time trying to figure out what functions operate on what types.
For example, in the documentation for HaXml, there's a description of
Document:
[1]http://www.cs.york.ac.uk/fp/HaXml/HaXml/Text-XML-HaXml-Types.html#4
However, I can't find any links to what functions accept document as a
parameter.  Am I missing some magic?

 There might be better answers. Some ways to achieve what you want:
 a) use hoogle (haskell.org/hoogle). You can use hoogle to find functions by 
 types. But I don't
 know haw to create a query such as ... - Document - ...

Hoogle unfortunately doesn't do that very well, although that would be a
great feature. But I think that  Text.XML.HaXml  isn't indexed by Hoogle
anyway?

A couple of other questions...
Can ByteStrings be substituted anywhere that takes a String (e.g.,
HaXml xmlParse)?

 In general yes, you should be able to use ByteStrings wherever a String
 is used..
 But remember that a String has some syntactic suggar becuase it's
 treated as list. Thus the : operator won't work with ByteStrings (I'm
 sure the module does define functions providing the same functionality)

Eh? These two are different types, you have to  pack  and  unpack  to
convert between. But note that this most likely voids the performance
gains from  ByteString . In other words, if a library function needs a
String , there's not much you can do. However, Henning Thielemann
reported that his use of HaXml (I think) for the parallel web (see
http://haskell.org/haskellwiki/Monad#Fun) works well with Strings.

Regards,
apfelmus

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


[Haskell-cafe] Re: Zippers, Random Numbers Terrain

2007-08-06 Thread apfelmus
Thomas Conway wrote:
 On 8/2/07, apfelmus [EMAIL PROTECTED] wrote:
 That concludes the infinite terrain generation for one dimension. For
 higher dimension, one just needs to use 2D objects instead of intervals
 to split into two or more pieces. For instance, one can divide
 equilateral triangles into 4 smaller ones. In fact, it doesn't matter
 whether the starting triangle is equilateral or not when using the
 midpoints of the three sides to split it into four smaller triangles.
 
 Nice. The issue of the RNG running backwards was what made me realize
 that rather than using StdGen in the nodes, if you simply number them
 (Hmmm - the nodes are countably infinite :-)), you can then [e.g.] use
 a cryptographic hash or similar to turn them into random numbers. You
 can seed the hash to generate different terrains.

Yes. The number of a node in the tree should be (related to) the path
from the top to the tree in binary representation. I.e. if

  node = zoomInLeft . zoomInLeft . zoomInRight $ top

then,

  number node = 112 in binary with digits 1 and 2

In contrast, breadth first numbering is a bad idea, since that would
mean numbering lots of nodes that aren't required when zooming in.


It's probably easiest to first create an infinite tree filled with
random numbers

  type Tree a = Branch (Tree a) a (Tree a)

  type Random = Double
  mkRandom :: Seed - Tree Random

and then convert that to a landscape afterwards

  terrain :: Tree Random - Tree (Height, Height)


Yet another option is available if you only use the zipper-operations to
navigate in the tree, i.e.

  data TreeRandom -- abstract and a zipper

  zoomInLeft, zoomInRight, zoomOut :: TreeRandom - TreeRandom
  top :: TreeRandom - Random

In that case, you can represent it by

  type TreeRandom = (StdGen, Zipper (Maybe Random))

Everytime you visit a node that has not been visited yet (= Nothing),
it gets a new random number from the generator. When it's already been
visited (= Just r), well then the random number associated to it won't
change. The resulting zipper may only be used in a single-threaded
fashion, however.

 You may be interested that in some of the code I wrote for the right
 angle isosceles triangle case, I got into precision problems. It turns
 out that all the vertices lie on positions with coordinates that are
 precisely sums of 2^-k (e.g. 0.5, 0.125, 0.625), yet each time you
 subdivide, the scaling factor on the side length is sqrt 2/2. The
 resultant rounding meant that instead of getting 0.5, I got
 0.53, or some such.
 
 After pondering on this for a while, I realized instead of
 representing the scale of the triangle as a Double, I could use
 (Either Double Double), with Left x representing the scale x, and
 Right x representing the scale x * sqrt 2 / 2. That way, all the
 rounding problems can be made to go away.

Cool :) Of course, the representation with Either requires the knowledge
that a scale factor cannot contain both Double-multiples of 1 and
Double-multiples of sqrt 2 at the same time. While this is clearly the
case, you can avoid thinking about it by operating in the field Q[sqrt 2]:

  data QSqrt2 = !Double :+ !Double deriving (Eq,Read,Show)

  instance Nume QSqrt2 where
 (a :+ b) + (c :+ d) = (a+c) :+ (b+d)
 (a :+ b) * (c :+ d) = (a*c + 2*b*d) :+ (a*d + b*c)

 negate (a :+ b) = negate a :+ negate b
 abs (a :+ b)= (a + sqrt 2 * b) :+ 0
 fromInteger n   = fromInteger n :+ 0

  sqrt2 = 0 :+ 1

Regards,
apfelmus

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


[Haskell-cafe] Re: Type classes: Missing language feature?

2007-08-07 Thread apfelmus
DavidA wrote:

 newtype Lex = Lex Monomial deriving (Eq)
 newtype Glex = Glex Monomial deriving (Eq)

 Now, what I'd like to do is have Lex and Glex, and any further monomial 
 orderings I define later, automatically derive Show and Num instances from 
 Monomial (because it seems like boilerplate to have to define Show and Num 
 instances by hand).

Good news: it's already implemented and called newtype deriving :)

http://www.haskell.org/ghc/docs/latest/html/users_guide/type-extensions.html#newtype-deriving

In short, you just write

 newtype Lex = Lex Monomial deriving (Eq, Show, Num)

I guess that the Show instance will add the constructor Lex , though.

Regards,
apfelmus

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


[Haskell-cafe] Re: monad subexpressions

2007-08-08 Thread apfelmus
Bulat Ziganshin wrote:
 apfelmus wrote:

 avoid the small layer of imperative code, of course. But the more you
 treat imperative code as somewhat pure, the greater the danger that the
 purely functional logic will be buried inside a mess of imperative code.
 In other words, the goal is exactly to make IO and STM uncommon,
 otherwise you loose the power the purely functional approach offers.
 
 it's point of view of theoretical purist. i consider Haskell as
 language for real world apps and need to write imperative code appears
 independently of our wishes. in paricular, it's required to write very
 efficient code, to interact with existing imperative APIs, to make
 programs which has explicit memory control (as opposite to lazy
 evaluation with GC)

No and yes. As I said, it is of course desirable to be able to describe
genuinely imperative behavior elegantly in Haskell, like explicit memory
control or concurrently accessing a bank account.

However, most genuinely imperative things are often just a building
block for a higher level functional model. The ByteString library is a
good example: the interface is purely functional, the internals are
explicit memory control. It's a bad idea to let the internal memory
control leak out and pollute an otherwise purely functional program with
IO-types.

Also, many genuinely concurrent things just aren't. An example are
UNIX pipes like say

  cat Main.hs | grep Warm, fuzzy thing

The OS creates a processes for cat and grep running concurrently and
cat passes a stream of characters to grep. By blocking on the reader
and the write side, grep reads what cat writes in real-time. Well,
but that's just good old lazy evaluation!

Regards,
apfelmus

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


[Haskell-cafe] Re: Language support for imperative code. Was: Re: monad subexpressions

2007-08-11 Thread apfelmus

Brian Hulley schrieb:

apfelmus wrote:

However, most genuinely imperative things are often just a building
block for a higher level functional model. The ByteString library is a
good example: the interface is purely functional, the internals are
explicit memory control. It's a bad idea to let the internal memory
control leak out and pollute an otherwise purely functional program with
IO-types.


Regarding the quote above, if the API must hide explicit memory control 
from the user the only way I can see of doing this would be to use 
(unsafePerformIO), which really is unsafe since Haskell relies on the 
fact that mutable operations can't escape from the IO monad in order to 
get away with not having to impose a value restriction as in ML.


Indeed, Data.ByteString makes heavy use of unsafePerformIO and
inlinePerformIO. This is safe since it's just used for efficient memory
access and (de-)allocation, the ByteStrings themselves are immutable.

If you don't use (unsafePerformIO), then the slightest need for mutable 
data structures pollutes the entire interface.


Well, any code that wants to mutate or read this data structure has to
announce so in the type signature. However, it's debatable whether
certain forms of mutation count as pollution. In fact, the simplest
mutation is just a function  s - s  . Haskell is throughly polluted
by such mutations:

  (3+) :: Int - Int
  ([1,2]++):: [Int] - [Int]
  insert x 3 :: Map String Int - Map String Int

Of course, from the purely functional point of view, this is hardly
perceived as mutation since the original value is not changed at all and
still available. In other words, the need to change a value doesn't
imply the need to discard (and thus mutate) the old one.

Mutable data structures in the sense of ephemeral (= not persistent = 
update in-place) data structure indeed do introduce the need to work in 
ST since the old version is - by definition - not available anymore. 
This may be the right thing to do when the data structure is inherently 
used in a single-threaded fashion. However, most used-to-be ephemeral 
data structures have very good persistent counterparts in Haskell. In 
the end, the type just reflects the inherent difficulty of reasoning 
about ephemeral data structures. And that's what the quoted paper 
illustrates: persistent data structures are much easier to deal with.



For example in the excellent paper you quoted

 N. Ramsey and J. Dias.
 An Applicative Control-Flow Graph Based on Huet's Zipper
 http://www.eecs.harvard.edu/~nr/pubs/zipcfg-abstract.html 
http://www.eecs.harvard.edu/%7Enr/pubs/zipcfg-abstract.html


the authors are pleased to have found an Applicative solution, and 
indeed their solution has many useful and instructive aspects. However 
on page 111, hidden away in the definition of their API function to 
create a label, is a call to (ref 0)  ;-) The equivalent 
implementation in Haskell would completely destroy all hope of using 
this in a pure context and force all use of the API into the IO monad.


I don't know enough ML or have the background to judge whether this  ref 
 is really necessary, but I doubt that it can't be designed away.



Haskell is designed so that any attempt at abstracting mutable

 local state will infect the entire program

Depends on local. In general, I think is a good thing. The type 
reflects how difficult your program really is, nothing more, nothing 
less. That's how it is: persistent data and prue functions are sooo much 
easier to reason about. Implicit side effects just sweep the difficulty 
under the carpet. (I imagine a tool that makes implicit side effects 
explicitly visible in the types of say C or ML programs. I guess that 
people would scream whole nights when seeing the output of this tool on 
their programs and thus discovering how complicated the code really is 
... Well, maybe not since they're used to it during debugging anyway.)


But if the state is really local, no infection of the entire program 
takes place! The best example is probably indeed the Haskell Graphics 
library. The are pure functions for constructing graphics


  over:: Graphic - Graphic - Graphic
  polygon :: [Point] - Graphic

and some IO-infected functions to draw those onto the screen

  drawInWindow :: Window - Graphic - IO ()

Now,  Graphic  may be implemented as an abstract data type and 
drawInWindow  does the workload of interpreting it. Or, and that's how 
HGL currently implementes it, it can be an IO-action that encodes how to 
draw it


  type Graphics = Draw ()
   ~= (Brush,Font,Pen) - IO ()

That is, every graphic is infested with IO but that doesn't spread to 
the API. (It does a bit with  selectBrush  but that can be corrected.)


 (modulo use of a highly dangerous function whose
semantics is entirely unclear, depending on the vagaries of evaluation 
strategy of the particular compiler)


(yes, unsafePerformIO clearly isn't for ephemeral data structures

[Haskell-cafe] Re: zip3, zip4 ... - zipn?

2007-08-11 Thread apfelmus

Frank Buss schrieb:

Is it possible to write a function like this:

zipn n list_1 list_2 list_3 ... list_n

which implements zip3 for n=3, zip4 for n=4 etc.? Looks like variable number
of arguments are possible, like printf shows, so a general zipn should be
possible, too. If it is possible, why there are functions like zip5 and not
just zipn?


What type would this function have? It's not possible to formulate this 
type in Haskell98. The problem is that the number of arguments cannot be 
determined statically, i.e. it depends on the value of  n  at run-time. 
There are languages more freaky than Haskell (like Agda or Epigram ) 
that can do that (without dynamic typing, that is!), they are called 
dependently typed.


However, type-class hackery (or type synonym families once they're 
available in GHC) can be used to do something like that if you give the 
value of n at compile-time. I won't dwell into that, though.


Also, applicative functors can help

  GHCi :m +Control.Applicative
  GHCi (\x y z - x*(y+z)) $ ZipList [1,2,3]
* ZipList [-1,0,1] * ZipList [1,1,1]
  ZipList [0,2,6]
  GHCi

(the second command is a single line.)

Regards,
apfelmus

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


[Haskell-cafe] Re: Language support for imperative code. Was: Re: monad subexpressions

2007-08-13 Thread apfelmus

Isaac Dupree schrieb:

apfelmus wrote:
Mutable data structures in the sense of ephemeral (= not persistent = 
update in-place) data structure indeed do introduce the need to work 
in ST since the old version is - by definition - not available anymore. 


Not in the quantum/information-theoretic sense, not necessarily. Consider

import Control.Monad.ST
import Data.STRef
main = print (runST (do
   r - newSTRef 1
   notUnavailable - readSTRef r
   writeSTRef r 5
   return notUnavailable
 ))


I'm not sure what this has to do with quantum mechanics ;) but you're 
right, I forgot that. This means that either STRefs cannot be updated 
in-place or that every read operation copies the contents or something 
like that.


In any case, simple values like Ints or Bools are rather uninteresting, 
update in-place is only important for larger structures like arrays. 
Here, ST does updates in-place and retaining an array will copy it.


Regards,
apfelmus

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


[Haskell-cafe] Re: a regressive view of support for imperative programming in Haskell

2007-08-13 Thread apfelmus

Benjamin Franksen wrote:

As has been already mentioned in this thread, in
http://www.soi.city.ac.uk/~ross/papers/Applicative.html Conor McBride and
Ross Paterson invent/explain a new type class that is now part of the base
package (Control.Applicative). They also use/propose syntactic sugar for
it, i.e.

pure f * u1 * ... * un

~~ (| f u1 ... un |)

(I just made up the symbols '(|' and '|)', the concrete syntax would have to
be fixed by people more knowledgeable than me.)


The problem with [| and |] lifted to monads that this only works for
fully applied arguments, i.e. that

  handle :: IO Handle
  string :: IO String

  [| hPutStr handle string |] :: IO ()

works but

   [| hPutStr handle |]
  = join (return hPutStr `ap` handle)
 ^= join ((f :: m (a - b - m c)) `ap` (x :: m a))
  = join ( y :: m (b - m c))

is a type error.

I think this is also what makes the (- action) proposal so non-local
and what is the source of this whole discussion. The core problem is:

  Functions like  a - b - m c  can't be partially applied to
  monadic actions like  m a  without specifying the number of
  arguments in advance. In other words, such functions aren't
  curried correctly.

Clearly, LiftMn specifies the number of arguments. But _both_ the (-) 
proposal and idiom brackets specify the number of arguments too! Namely 
by requiring that all arguments are fully applied. So, neither one is 
capable of partially applying the first argument without saturating the 
call, you can only write


  handle :: IO Handle

-- define putStr in terms of the above hPutStr
  putStr :: String - IO ()
  putStr = \x - [| hPutStr handle (return x) |]
  putStr = \x - do { hPutStr (- handle) x }


One way to get currying for monads is to work with functions

  m a - m b - m c

However, this type is larger than  a - b - m c  , i.e. the function

  from :: Monad m = (a - b - m c) - (m a - m b - m c)
  from f ma mb = ma = \a - mb = \b - f a b

is not surjective since we could perform the actions in a different order

  from2 f ma mb = mb = \b - ma = \a - f a b

In other words, if someone gives you a value of type  m a - m b - m c 
 , then you can't convert it to  a - b - m c  and back without 
risking that you end up with a different result.



But there is another type suitable for currying

  m (a - m (b - m c))

which I believe is in some way equivalent to  a - b - m c

  from :: Monad m = (a - b - m c) - m (a - m (b - m c))
  from f = return $ \a - return $ \b - f a b

  to   :: Monad m = m (a - m (b - m c)) - (a - b - m c)
  to f a b = f = \g - g a = \h - h b

but I'm not sure. My assumption is that we have an equivalence

  forall a,b . m (a - m b) ~ (a - m b)

because any side effect executed by the extra m on the outside can well 
be delayed until we are supplied a value a. Well, at least when all 
arguments are fully applied, for some notion of fully applied


Anyway, here's how to curry with that type:

  (@) :: Monad m = m (a - m b) - (m a - m b)
  (@) f x = join (f `ap` x)

  hPutStr :: IO (Handle - IO (String - IO ()))
  handle  :: IO Handle

  putStr :: IO (String - IO ())
  putStr = hPutStr @ handle

With the infix type synonym

  type (~) a b = a - IO b

we can also write

  hPutStr :: IO (Handle ~ String ~ () )
  putStr  :: IO (String ~ () )

This is of course the Kleisli-Arrow which explains why currying works.


Regards,
apfelmus

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


[Haskell-cafe] Re: a regressive view of support for imperative programming in Haskell

2007-08-13 Thread apfelmus

Stefan O'Rear schrieb:

On Mon, Aug 13, 2007 at 04:35:12PM +0200, apfelmus wrote:

My assumption is that we have an equivalence

  forall a,b . m (a - m b) ~ (a - m b)

because any side effect executed by the extra m on the outside can well be 
delayed until we are supplied a value a. Well, at least when all arguments 
are fully applied, for some notion of fully applied


(\a x - a = ($ x)) ((\f - return f) X) == (β)
(\a x - a = ($ x)) (return X)   == (β)
(\x - (return X) = ($ x))   == (monad law)
(\x - ($ x) X)== (β on the sugar-hidden 'flip')
(\x - X x)== (η)
X

Up to subtle strictness bugs arising from my use of η :), you're safe.


Yes, but that's only one direction :) The other one is the problem:

 return . (\f x - f = ($ x)) =?= id

Here's a counterexample

 f :: IO (a - IO a)
 f = writeAHaskellProgram  return return

 f' :: IO (a - IO a)
 f' = return $ (\f x - f = ($ x)) $ f
 == (β)
  return $ \x - (writeAHaskellProgram  return return) = ($ x)
 == (BIND)
  return $ \x - writeAHaskellProgram  (return return = ($ x))
 == (LUNIT)
  return $ \x - writeAHaskellProgram  (($ x) return)
 == (β)
  return $ \x - writeAHaskellProgram  return x

Those two are different, because

 clever  = f   return () = writeAHaskellProgram
 clever' = f'  return () = return ()

are clearly different ;)

Regards,
apfelmus

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


[Haskell-cafe] Re: A few ideas about FRP and arbitrary access in time

2010-03-09 Thread Heinrich Apfelmus
John Meacham wrote:
 On Tue, Mar 09, 2010 at 05:23:56AM +, Aaron Denney wrote:
 On 2010-03-08, Brandon S. Allbery KF8NH allb...@ece.cmu.edu wrote:
 There is a discrete time quantum.  But unless you're doing simulations  
 at the quantum level, you really don't want to go there (even ignoring  
 that one second of real time would take a really long time to  
 calculate on current hardware :); stick to macrocosmic physics, which  
 is statistically continuous.

 That's ... contentious.  In both quantum mechanics and GR, time is
 completely, flattly, continuous.  In certain extremely speculative
 frameworks attempting to combine the regimes in which they are
 applicable, that may not be the case.  But for accepted physics models,
 time really is continous.
 
 Hmm.. I thought something interesting happened on the scale of the plank
 time, 10^-44 seconds or so. Or is that only relevant to our ability to
 _measure_ things at that scale and not the continuity of time itself as
 far as QM is concerned?

It may sound strange, but continuous quantities are often an
approximation. For instance, a bar of steel is composed of a finite
number of atoms, but if you want to know how it behaves under load
(theory of elasticity), you can model it as a continuous mass just fine
because the number of atoms is huge.

Same goes for time. It doesn't really matter what happens in minuscule
time scale; for the purpose of Newtonian mechanics, time is continuous.
(It's continuous for the purpose of modeling more fundamental theories
as well.) The key point is that this is not absolute reality, it's
just a model.


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Bytestrings and [Char]

2010-03-23 Thread Heinrich Apfelmus
Ivan Miljenovic wrote:
 Johan Tibell wrote:
 A sequence of bytes is not the same thing as a sequence of Unicode
 code points. If you want to replace String by something more efficient
 have a look at Data.Text.
 
 Though Data.Text still has the disadvantage of not being as nice to
 deal with as String, since you can't pattern match on it, etc.
 
 Whilst it may degrade performance, treating String as a list of
 characters rather than an array provides you with greater flexibility
 of how to deal with it.

Indeed. In particular,  [Char]  and  Data.Text.Text  have different
semantics and performance.

For instance,

cons :: Char - Text - Text

is O(n) whereas  (:)  is O(1). (Not sure whether stream fusion for  cons
 can change that at times.)

Furthermore, certain programs relying on laziness, like

ahh = 'a' : ahh

fibs = ' ' : zipWith plus fibs (tail fibs)
where plus x y = toEnum $ fromEnum x + fromEnum y

are not possible with  Data.Text.Text . (Whether you really need these
is another question, of course.)


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Sugar for function application

2010-03-25 Thread Heinrich Apfelmus
Tillmann Rendel wrote:
 I like this idea, because it would enable non-monadic embedded DSLs to
 use layout.
 
 For example, consider setting properties in wxHaskell:
 
   layoutSet myButton $$
 text := Ok
 on action := doSomething

You can abuse  do  notation to achieve that, by wrapping the list in a
suitable  Writer  monad

layoutSet myButton $ do
text = Ok
on action = doSomething

with

   (=) :: Property a - a - Writer Properties ()

It's ugly semantically but pleasant syntactically.


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: breadth first search one-liner?

2010-03-25 Thread Heinrich Apfelmus
Johannes Waldmann wrote:
 Dear all, there is this neat one-line BFS implementation
 
 bfs :: Eq a
 = ( a - [a] ) - a - [a]
 bfs next start =
 let xs = nub $ start : ( xs = next )
 in  xs
 
 but it has a problem: it only works for infinite graphs. This is fine:
 
 take 20 $  bfs ( \ x - [2*x, x+1] ) 1
 
 but this is not:
 
 take 20 $  bfs ( \ x - filter (0) [ div x 2, x - 1 ] ) 10
 
 
 Is there a nice way to repair this?
 (I know how to code a BFS but here I'm asking for a one-liner.)

There is a neat trick to handle the finite case which I first read about
in Leon P. Smith's article

Lloyd Allison’s Corecursive Queues: Why Continuations Matter.
http://themonadreader.wordpress.com/2009/07/29/issue-14/

Namely, you have to keep track of the current queue size so that the
program doesn't hang when the queue becomes empty:

bfs' f x = let xs = more 1 (x:xs) in x:xs
where
more 0 _  = []
more n (x:xs) = f x ++ more (n + length (f x) - 1) xs

Unfortunately, this cannot be made to work with  nub  because that would
screw up the size calculation.


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Randomized N-Queens

2010-03-27 Thread Heinrich Apfelmus
Ronald Guida wrote:
 Hi,
 
 I'm trying to solve the N-queens problem, but with a catch: I want to
 generate solutions in a random order.
 
 I know how to solve the N-queens problem; my solver (below) generates all
 possible solutions.  What I am trying to do is generate solutions in a
 random order by somehow randomizing the order in which nextRow considers
 the unused columns.  I tried adding a random number generator to the
 solution state; the problem with this approach is that whenever the solver
 backtracks, the state of the random number generator backtracks along with
 it.  In effect, I am selecting a random, but fixed, permutation for each
 row, and then I am applying that same set of permutations along all
 computational paths.  Whenever I consider row R, regardless of which path I
 have taken, I am applying row R's permutation to the unused columns.
 
 This is not the behavior I want.  I want each computational path to use a
 new, different permutation for each row.  On the other hand I also want to
 be able to take the first few solutions without waiting for all possible
 solutions to be generated.  How might I go about doing this?

 [...]
 data (RandomGen g) = SolutionState g = SolutionState
 { solnBoard :: Board
 , solnUnusedColumns :: [Int]
 , solnRandomGen :: g
 }
 
 nextRow :: (RandomGen g) = Int - Int - StateT (SolutionState g) [] ()

It's a matter of choosing the right monad stack. In particular, putting
the random number generator into the solution state pretty much forces
the undesired behavior. Random numbers are best put in a separate monad
(transformer), for reasons of abstraction which are outlined here:

  http://lukepalmer.wordpress.com/2009/01/17/use-monadrandom/
  http://apfelmus.nfshost.com/articles/random-permutations.html


Also, it's not really necessary to use the state monad to store the
solution, using a plain old parameter works just fine, as the following
code illustrates:

import Control.Monad.Random  -- from the  MonadRandom  package

-- generate a random permutation
randomPerm :: MonadRandom r = [a] - r [a]
randomPerm xs = go (length xs) xs
where
go 0 [] = return []
go n xs = do
k - getRandomR (0,n-1)
let (x,xs') = select k xs
liftM (x:) $ go (n-1) xs'

select 0 (x:xs) = (x,xs)
select k (x:xs) = let (y,ys) = select (k-1) xs in (y,x:ys)

-- 8 queens
type Pos = (Int,Int)

attacks (x1,y1) (x2,y2) =
   x1 == x2
|| y1 == y2
|| x1 - x2 == y1 - y2
|| x2 - x1 == y1 - y2

type Solution = [Pos]

solve :: Rand StdGen [Solution]
solve = solve' 8 []
where
solve' 0   qs = return [qs]
solve' row qs =
liftM concat . mapM putQueen = randomPerm [1..8]
where
putQueen col
| any (q `attacks`) qs = return []
| otherwise= solve' (row-1) (q:qs)
where q = (row,col)

test seed = evalRand solve $ mkStdGen seed



Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Seeking advice about monadic traversal functions

2010-03-31 Thread Heinrich Apfelmus
 shuffles them around,
like moving a constructor from the tree to the node list or from one
list to the other. This makes it straightforward to implement an inverse
function  synthesize  which fulfills

synthesize . analyze = id

After all, we only have to write the definition of  analyze  from right
to left!

synthesize :: State a - State a
synthesize (xs, (Cut , t ) : ts, q) =
(Cut:xs , ts, t   | q)
synthesize (xs, (Next, Nil   ) : ts, q) =
(Next:xs, ts, Nil | q)
synthesize (xs, (Next, Single x _) : ts, viewr - q : t1) =
(Next:xs, ts, Single x t1 | q)
synthesize (xs, (Next, Fork _ _  ) : ts, viewr -
(viewr - q : t1) : t2) =
(Next:xs, ts, Fork t1 t2  | q)

Looks a bit noisy, but I have simply copy  pasted the four equations
for  analyze  and interchanged the left-hand and the right-hand sides,
adjusting the view patterns.

Thus, we can invert  bfs  by repeatedly applying  synthesize  to the
final state of  bfs :

unBfs ts = (`index` 0) . queue $
until (List.null . nodes) synthesize ([],ts,empty)

By construction, we have obtained the desired

unBfs . bfs xs = id



Regards,
Heinrich Apfelmus

PS:
* I have used a double-ended queue, but we're never really using both
ends at once. An ordinary FIFO queue will suffice if we interpret it to
change direction between  bfs  and  unBfs .
* Exchanging the queue for a stack will give depth-first search and its
inverse.


--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Hughes' parallel annotations for fixing a space leak

2010-03-31 Thread Heinrich Apfelmus
Dear haskell-cafe,

I've been thinking about space leaks lately. In particular, I've been
studying the tricky example with pairs

break [] = ([],[])
break (x:xs) = if x == '\n' then ([],xs) else (x:ys,zs)
where (ys,zs) = break xs

which was discussed in the papers

Jan Sparud. Fixing some space leaks without a garbage collector.
http://bit.ly/cOxcVJ

Philip Wadler. Fixing some space leaks with a garbage collector.
http://homepages.inf.ed.ac.uk/wadler/topics/garbage-collection.html

As I understand it, GHC implements the technique from Sparud's paper, so
this is a solved problem. (It will only kick in when compiled with
optimization, though, so -O0 will make the above leak in GHC 6.10.4 if I
checked that correctly.)


Now, I'm wondering about alternative solutions. Wadler mentions some
sort of parallel combinators

break xs = (PAR before '\n' ys, PAR after '\n' zs)
where (ys,zs) = SYNCLIST xs

which were introduced by John Hughes in his Phd thesis from 1983. They
are intriguing! Unfortunately, I haven't been able to procure a copy of
Hughes' thesis, either electronic or in paper. :( Can anyone help? Are
there any other resources about this parallel approach?



Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Seeking advice about monadic traversal functions

2010-04-02 Thread Heinrich Apfelmus
Darryn Reid wrote:
 Heinrich,
 
 Thanks for your excellent response! Indeed, it was the rebuilding of the
 tree that had me stumped. I also see the benefits of using the lift
 functions, thanks again for this insight.

My pleasure. :)

By the way, there's also another, very flexible way to rebuild the tree:
give each node a unique identifier. The traversal returns a list of
labeled nodes with their children replaced by labels, like this:

[(1,Nil),(2,Single 'a' 3),(3,Nil),(4,Fork 1 2),...]

To rebuild the tree, simply put the list into a finite  map  and replace
identifiers by proper trees again.

However, this solution is essentially the same as using a mutable tree,
the unique identifiers represent memory addresses. That's why I sought
to reconstruct the tree from the structure of the traversal (using the
same intermediate queue data structure, etc.).


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: libraries [was GUI haters]

2010-04-03 Thread Heinrich Apfelmus
Michael Vanier wrote:
 aditya siram wrote:
 Yes Haskell is not strong on the GUI end of things but have you
 considered turning your desktop app into a web app? I've done this
 for a few things and really enjoyed the process. Haskell's STM is
 what makes this so nice.

 This is a great idea!  IMO this is also one of the main ways that
 GUI-based apps are likely to evolve into in the future.  Cross-platform
 GUIs are a pain in the butt in _any_ language (possibly excluding full
 language platforms like Java/.NET, and I'll bet even those were a
 nightmare for the original implementors).

This is a bad idea! :) As a long term Mac user, I have a strong dislike
for web applications that try to be desktop applications. Sagemath is
probably an example in point. Not only are the well-designed standard
GUI elements thrown out of the window (the menu bar, it belongs at the
top), it's also sluggish to navigate between pages, doesn't support drag
 drop from other applications and most importantly, doesn't play nice
 with local files.

From the programmers point of view, I don't want to code my GUI in
Javascript either, I want to do it in Haskell.


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com





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


[Haskell-cafe] Re: Haskellers hate GUIs!!

2010-04-03 Thread Heinrich Apfelmus
Brandon S. Allbery KF8NH wrote:
 David Leimbach wrote:
 Having said that, are there any plans to make it really easy to get
 gtk2hs working on Mac OS X?
 
 
 It's in MacPorts.

Which doesn't necessarily make it easier. Took me 2 full days to install
gtk and it's still crashing a lot more than it's supposed to.


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Haskellers hate GUIs!!

2010-04-03 Thread Heinrich Apfelmus
Thomas Schilling wrote:
 Haskeller's certainly aren't GUI-haters!  It's just difficult in
 general to write cross-platform GUIs.  The goal *is* to put gtk2hs
 into the platform, but in order to do that, it needs to be buildable
 using Cabal.  The limiting factor is time, not motivation.

Well, expertise is also a limiting. Few people are willing to invest a
huge amount of time to learn the often arcane craft of modifying
somebody else's makefiles and build architecture.

Also, cabalizing gtk2hs won't necessarily make the compilation problems
go away. You still have to get gtk working on non-Linux systems and you
still have to deal with unexpected errors somewhere deep in the dungeons
of preprocessing for the Haskell FFI.


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Haskellers hate GUIs!!

2010-04-03 Thread Heinrich Apfelmus
Rafael Cunha de Almeida wrote:
 When using haskell, can't you just make a static binary on MacOS and Windows,
 though? Why wouldn't that work?

On MacOS, you would have to relocate the shared gtk2hs libraries and
bundle them with the application. It's actually easiest to exorcise the
paths from the compiled binary with some  otool  vodoo; Inkscape did it
this way last time I remember. There was also a gtk framework once, but
it seems to be out of date.


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Hackage accounts and real names

2010-04-05 Thread Heinrich Apfelmus
David House wrote:
 An issue came up on #haskell recently with Hackage accounts requiring
 real names. The person in question (who didn't send this email as he's
 wishing to remain anonymous) applied for a Hackage account and was
 turned down, as he refused to offer his real name for the username.

It appears to me that it's generally a good idea to adopt a pseudonym
that looks like a real name anyway. The main benefit is that no one will
notice that it's a pseudonym, thus avoiding such complications.


Ivan Miljenovic wrote:
 I would wonder _why_ anyone would refuse to do so.  Are they that
 ashamed of their own software that they wouldn't want to be associated
 with it, or is there some legal reason that they don't want to be
 associated with it?

I'm sure they have their reasons, and who am I to judge them. Most
likely, it's about googleability.


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: ANN: spec2code

2010-04-05 Thread Heinrich Apfelmus
Am 01.04.10 20:53, Greg Fitzgerald wrote:
 After 5 years of RD, I’m proud to announce the spec2code compiler.
 With spec2code, developers no longer need to acknowledge the mundane
 details of programming, such as memory allocation, bounds-checking,
 byte ordering, inheritance models or performance tuning.  spec2code
 uses the latest techniques in compiler optimization to derive a
 deterministic implementation from only a high-level specification.
 
 [...]

 Does it scale?  Absolutely, spec2code is not confined to
 specifications for which optimized algorithms are already known.
 spec2code can be used to implement operation systems, device drivers,
 build systems, package management tools, and even do your shirt
 laundry.  spec2code will change your job from programmer to
 specification author, giving you more time for meetings, managing
 email, and browsing the web.  Say goodbye to those dirty Perl scripts,
 broken C code, and ultimately, your job.  spec2code is the future of
 programming and the beginning of the end of mankind.
 
 Looking forward to obsoleting you soon,

Awesome! Given the great potential of the new  spec2code  compiler, the
reception seems to be somewhat chilly. But maybe that's because no one
likes to be obsoleted...

In fact, I do have to admit that I'm secretly working on a specification
of a program that halts exactly when  spec2code  produces a program that
does not halt. It's my only hope!


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Hughes' parallel annotations for fixing a space leak

2010-04-05 Thread Heinrich Apfelmus
Max Bolingbroke wrote:
 Heinrich Apfelmus wrote:

 As I understand it, GHC implements the technique from Sparud's paper, so
 this is a solved problem.
 
 This is not my understanding. As far as I know, the STG machine has a
 special notion of selector thunks, which represent projections from
 product data types. These selector thunks are evaluated by the GHC
 garbage collector in the manner proposed by Wadler.

Ah, that's how it is. Thanks. :)

Funny that this special garbage collector support isn't used when
compiling with -O0, though. But it makes sense to be required to use at
least -O1 when you care about resources.

 The Sparud solution is IMHO much cleaner, though!

I agree. It still requires special support from the garbage collector,
though. Namely, the gc has to short-circuit indirection nodes, otherwise
the pairs will be replaced by a long chain of indirection nodes and the
 break  example would still leak.

In a sense, Sparud's idea is about expressing selector thunks in terms
of indirections and mutable thunk updates.


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Hackage accounts and real names

2010-04-06 Thread Heinrich Apfelmus
Edward Z. Yang wrote:
 This is a pretty terrible reason, but I'm going to throw it out there:
 I like real names because they're much more aesthetically pleasing.

I agree, and this is why I phased out apfelmus in favor of the
pseudonym Heinrich Apfelmus.

So, a more accurate policy would be to accept not only real names, but
also names that look like they're real, i.e. aesthetically pleasing noms
de plumes.


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Metaprogramming in Haskell vs. Ocaml

2010-04-06 Thread Heinrich Apfelmus
Jacques Carette wrote:
 Jason Dagit wrote:
 Are you implying that template haskell is not typed?

 Indeed. [...]

 Compare with metaocaml where if you can compile you meta-program (i.e.
 code generator), then you are guaranteed that it can only ever produce
 valid, well-typed code.  Not so with TH, where you can easily generate
 junk -- which GHC will promptly figure out  and give you an error.

I'm curious, can metaocaml create new data type definitions, value
declarations or type class instances? I usually use TH to get rid of
boilerplate that I cannot get rid off in Haskell itself, for instance
for creating functional lenses for record types

data Foo = Foo { bar_ :: Int, ...}

$(DeriveLenses Foo)
-- bar :: Lens Foo Int

It seems to me that metaocaml is more used as user annotated partial
evaluation?


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: libraries [was GUI haters]

2010-04-06 Thread Heinrich Apfelmus
aditya siram wrote:
 Cocoa is probably the best GUI toolkit (open-source or otherwise) that
 I've seen. However it ties your app to the Mac (and the iPhone). And I
 don't believe there is a mature Haskell bridge.

There is hoc

  http://code.google.com/p/hoc/

but it's not on hackage and seems a bit dormant.

 And Javascript [1] is really not _that_ bad!

But it's not Haskell. :'(


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: libraries [was GUI haters]

2010-04-06 Thread Heinrich Apfelmus
Jean-Denis Koeck wrote:
 
 Question to the Mac users on the list: do you find that Qt applications
 feel native enough on your platform ? If not, any tips ?

Well, that depends on your definition of enough. :)

The most important thing is probably that cross platform applications
always look buggy, so if you can make sure that everything runs
smoothly and there are no drawing bugs or thelike, that's a big plus.

Qt applications will always look odd, the relative spacing is all off.
But using the appropriate system fonts adds a lot to consistency. Avoid
colored buttons and text.

Another key feature of native for me is that the menu bar is at the
top of the screen. Hence, all windows share the same menu. Furthermore,
the context menu should not list commands that are not available in the
top menu.

Not as important, but still unique to native Mac applications is that
accept a lot of drag  drop. For instance, to insert a picture into a
document, you can just drag  drop it from the Finder program; no need
to intricate open file dialogs. If you have a list of items that can
be rearranged, do so by means of drag  drop instead of strange Up and
Down buttons.

There's probably more, but that's what I can think of right now off the
top of my hat. :)


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Seeking advice about monadic traversal functions

2010-04-06 Thread Heinrich Apfelmus
Darryn Reid wrote:
 Martijn van Steenbergen wrote:

 A small remark: I prefer using applicative notation for this:

 go Next (Single x t1) = Single x $ rewrite f t1
 go Next (Fork t1 t2 ) = Fork $ rewrite f t1 * rewrite f t2

 
 Thanks for your comment and advice. Could you explain a little further
 your thinking? Specifically, what advantage do you find in the
 applicative notation, and when would you advise using it and when would
 you advise not using it?

The applicative notation is more general since it also applies to
applicative functors

  http://www.cs.nott.ac.uk/~ctm/IdiomLite.pdf

It's main advantage over the liftM family is that it can be used with
any number of arguments

  liftM  f m = f $ m
  liftM2 f m n   = f $ m * n
  liftM3 f m n o = f $ m * n * o
  etc.

and that's why I prefer it as well. It's very similar to function
application, too, just think of  *  as a replacement for the empty
space that separates function arguments.

The only drawback is probably that you have to

  import Control.Applicative

In fact, it doesn't actually work for monads, I think you have to wrap
it in a newtype. :D The same effect can be achieved with `ap` , though:

  liftM3 f m n p = return f `ap` m `ap` n `ap` o


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Metaprogramming in Haskell vs. Ocaml

2010-04-07 Thread Heinrich Apfelmus
Nicolas Pouillard wrote:
 Heinrich Apfelmus wrote:
 I'm curious, can metaocaml create new data type definitions, value
 declarations or type class instances?

 No metaocaml cannot do this. It is restricted to the expression
 level, and not the declaration level. Moreover you cannot pattern
 match over the generated code.

 Jacques Carette wrote:
 One thing I should have mentionned - TH and camlp4 are really 
 equivalents.  And camlp4 is as-typed-as TH (or not, depending on your 
 point of view).
 
 This is not exactly the same, TH is a bit more typed than camlp4 here is two
 examples:

Thanks for your clarifications, Jacques and Nicolas. :)

Incidentally, the distinction between camlp4 and metaocaml makes me
wonder whether it might be possible to implement the former *inside* the
latter. In other words, maybe there exists a domain specific language
inside camlp4 / TH that offers all the conveniences of metaocaml.

Of course, this doesn't work right away because camlp4 / TH are
compile-time only, but why not extend them slightly so that they can be
used during run-time, too?


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Suitable structure to represents lots of similar lists

2010-04-08 Thread Heinrich Apfelmus
Dan Piponi wrote:
 I have a situation where I have a bunch of lists and I'll frequently
 be making new lists from the old ones by applying map and filter. The
 map will be applying a function that's effectively the identity on
 most elements of the list, and filter will be using a function that
 usually gives True. This means that there is potential for a large
 amount of sharing between these lists that could be exploited,
 something that ordinary lists would do badly. Does anyone have a
 recommendation for a pure functional data structure for this case?
 
 (It reminds me a bit of my own antidiagonal type, but that's not well
 adapted to the highly dynamic situation I'm describing.)

I'm not sure whether these general properties of your maps and filters
can actually be exploited. The thing is that you still have to touch
every element anyway, so you can as well allocate a new cons cell and
garbage collect the old one while you're at it.

But if you can skip large contiguous parts of the lists, then sharing
may be worth thinking about.


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Suitable structure to represents lots of similar lists

2010-04-09 Thread Heinrich Apfelmus
Eugene Kirpichov wrote:
 I think Dan is talking about sharing the spine of the lists...
 
 How about representing the lists using something along the lines of:
 
 data List a = Nil | Leaf a | Cat (List a) (List a)
 
 data Transformed a = Changed a | Unchanged a
 [...]
 
 cat :: List a - Transformed (List a) - Transformed (List a) -
 Transformed (List a)
 cat xs (Unchanged _) (Unchanged _) = Unchanged xs
 cat xs (Changed ys') (Unchanged zs) = Changed (Cat ys' zs)
 cat xs (Unchanged ys) (Changed zs') = Changed (Cat ys zs')
 cat xs (Changed ys') (Changed zs') = Changed (Cat ys' zs')
 
 mapShared' :: (a - Transformed a) - List a - Transformed (List a)
 mapShared' f x...@nil = Unchanged xs
 mapShared' f xs@(Leaf a) = case f a of { Unchanged _ - Unchanged xs ;
 Changed a' - Changed (Leaf a') }
 mapShared' f xs@(Cat ys zs) = cat xs (mapShared' f ys) (mapShared' f zs)
 
 [...]
 
 So, looks like we preserve whole 'subtrees' shared if they were not
 'changed' by map or filter.

Yes, but do you actually gain in terms of space usage?

Oh! It appears to me that sometimes you do, namely when the list was
heavily shared before applying map and filter. But if it's used
ephemerally, you don't gain anything.


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Simple game: a monad for each player

2010-04-09 Thread Heinrich Apfelmus
Gwern Branwen wrote:
 Yves Parès limestr...@gmail.com wrote:
 [...]
 But when running the game, the program cannot switch from a player's monad
 to another.

 Do you have any suggestion?
 
 Your desires remind me of the MonadPrompt package
 http://hackage.haskell.org/package/MonadPrompt, which IIRC, has been
 used in some game demos to provide abstraction from IO/test
 harness/pure AI etc.

The game demo can be found by chasing links from the package documentation:

   http://int-e.home.tlink.de/haskell/solitaire.tar.gz


There's also my package operational

   http://hackage.haskell.org/package/operational

which implements the same concept. It's throughly explained here:

   http://apfelmus.nfshost.com/articles/operational-monad.html
   http://projects.haskell.org/operational/


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Hackage accounts and real names

2010-04-10 Thread Heinrich Apfelmus
Steve Schafer wrote:
 Heinrich Apfelmus wrote:
 
 I agree, and this is why I phased out apfelmus in favor of the
 pseudonym Heinrich Apfelmus.
 
 You mean your name isn't really Applesauce?

I would probably apply for a name change if it were. ;)


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Cabal dependency hell

2010-04-12 Thread Heinrich Apfelmus
Edward Z. Yang wrote:
 Ivan Lazar Miljenovic's wrote:
 Edward Z. Yang writes:
 I doubt you'd get very much runtime with that.  I'd suggest prompting the
 user to submit a failed build report if the build fails.

 Exactly like how Windows keeps prompting you to allow it to send an
 error report to Microsoft?  I don't know about you, but I always found
 it irritating...
 
 I think the primary irritation is that Microsoft gets all of these error
 reports and they disappear into the great black VOID.  Some public statistics
 might help alleviate the irritation.

Perhaps exactly when the user is prompted?

Would you like to send an anonymous report of this build failure to
hackage.org? Users have been uploading 189 reports so far; yours would
be the 190th report that ensures high quality Haskell packages! [y/n]


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Cabal dependency hell

2010-04-12 Thread Heinrich Apfelmus
Ivan Lazar Miljenovic wrote:
 Heinrich Apfelmus writes:
 Perhaps exactly when the user is prompted?

 Would you like to send an anonymous report of this build failure to
 hackage.org? Users have been uploading 189 reports so far; yours would
 be the 190th report that ensures high quality Haskell packages! [y/n]
 
 Which, in its own way, means that cabal-install is still phoning home;
 you then even need network access if you're building packages that
 you've already downloaded the sources for.

Good point. How about using a cached number from the last  cabal install
, then:

Would you like to send an anonymous report of this build failure to
hackage.org? Users have been uploading more than 188 reports so far to
help ensure high quality Haskell packages! [y/n]

It's just to instill a sense of activity and purpose.


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Simple game: a monad for each player

2010-04-14 Thread Heinrich Apfelmus
Bertram Felgenhauer wrote:
 Yves Parès wrote:

 I answered my own question by reading this monad-prompt example:
 http://paste.lisp.org/display/53766

 But one issue remains: those examples show how to make play EITHER a human
 or an AI. I don't see how to make a human player and an AI play SEQUENTIALLY
 (to a TicTacToe, for instance).
 
 A useful idea is to turn the construction upside-down - rather than
 implementing the game logic using MonadPrompt (or operational),
 implement the players in such a monad.
 
 A sketch:
 
 {-# LANGUAGE GADTs, EmptyDataDecls #-}
 import Control.Monad.Prompt hiding (Lift)
 
 data Game -- game state
 data Move -- move
 
 data Request m a where
 Board:: Request m Game
 MakeMove :: Move - Request m ()
 Lift :: m a - Request m a
 
 type Player m a = Prompt (Request m) a

Just a small simplification: it is not necessary to implement the  Lift
 constructor by hand, the  operational  library implements a generic
monad transformer. The following will do:

import Control.Monad.Operational

data Request a where
Board:: Request Game
MakeMove :: Move - Request ()

type Player m a = ProgramT Request m a

game :: Monad m = Player m () - Player m () - m ()
game p1 p2 = do
g - initGame
eval' g p1 p2
where
eval' g p1 p2 = viewT p1 = \p1' - eval g p1' p2

eval :: Monad m = Game -
   - Prompt Request m ()
   - Player m ()
   - m ()
eval g (Return _)_  = return ()
eval g (Board   := p1) p2 = eval' g (p1 g) p2
eval g (MakeMove mv := p1) p2 =
makeMove mv g = \g - eval' g p2 (p1 ())

This way, you are guaranteed not to break the lifting laws, too.

 What have we achieved? Both players still can only access functions from
 whatever monad m turns out to be. But now each strategy can pile its own
 custom monad stack on the  Player m  monad! And of course, the use of
 the m Monad is completely optional.

Of course, the custom monad stack has to provide a projection back to
the  Player m a  type

   runMyStackT :: MyStackT (Player m) a - Player m a

Fortunately, you can't expect anything better anyway! After all, if the
 game  function were to accept say  LogicT (Player m)  as well, this
would mean that the player or AI could interleave the game arbitrarily,
clearly not a good idea.

 Mapping between various 'm' monads may also be useful:
 
 mapPlayerM :: forall m1 m2 a . (forall a . m1 a - m2 a)
- Player m1 a - Player m2 a
 mapPlayerM m1m2 pl = runPromptC return handle pl where
 handle :: Request m1 x - (x - Player m2 a) - Player m2 a
 handle (Lift a)  x = prompt (Lift (m1m2 a)) = x
 handle (MakeMove mv) x = prompt (MakeMove mv) = x
 handle (Board)   x = prompt (Board) = x
 
 This could be used to lock out the AI player from using IO, say.

Shouldn't this actually be a member of the  MonadTrans  class?

mapMonad :: (Monad m1, Monad m2, MonadTrans t) =
(forall a . m1 a - m2 a) - t m1 a - t m2 a

?

Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Simple game: a monad for each player

2010-04-14 Thread Heinrich Apfelmus
Limestraël wrote:
 I have some difficulties to see the use of PromptT, because in the tutorial,
 this type is never mentioned, and its operations (Return and :=) are
 instead constructors of ProgramT...
 
 Would you have some concrete examples? Because there I'm a bit lost (since
 the tutorial doesn't match the operational package as it is, because of the
 type PromptT)...

The project page

http://projects.haskell.org/operational/

links to documentation that describes the differences to The
Operational Monad Tutorial, in particular the new  Prompt  and  PromptT
 types. It also links to several examples. Two small examples are also
included in the Haddock documentation.


I'd like to make it very accessible, so please don't hesitate to report
any difficulties with finding and understanding documentation and examples!


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Fwd: Re: Simple game: a monad for each player

2010-04-15 Thread Heinrich Apfelmus
Limestraël wrote:
 Okay, I start to understand better...
 
 Just, Heinrich, how would implement the mapMonad function in terms of the
 operational package?
 You just shown the signature.

Ah, that has to be implemented by the library, the user cannot implement
this. Internally, the code would be as Bertram suggests:

mapMonad :: (Monad m1, Monad m2)
 = (forall a . m1 a - m2 a)
 - ProgramT instr m1 a - ProgramT instr m2 a
mapMonad f (Lift m1)  = Lift (f m1)
mapMonad f (Bind m k) = Bind (mapMonad f m) (mapMonad f . k)
mapMonad f (Instr i)  = Instr i

I was musing that every instance of  MonadTrans  should implement this
function.

Also note that there's a precondition on  f  , namely it has to respect
the monad laws:

f (m = k) = f m = f . k
f return= return

For instance,

f :: Identity a - IO a
f x = launchMissiles  return (runIdentity x)

violates this condition.


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Fwd: Re: Simple game: a monad for each player

2010-04-15 Thread Heinrich Apfelmus
Limestraël wrote:
 I'd like to make it very accessible, so please don't hesitate to report
 any difficulties with finding and understanding documentation and examples!

 Then I think the name 'Prompt' may be misleading for those who doesn't know
 the MonadPrompt package. Maybe something like 'ProgramView' ?

Very good point. I'll change that in a future version.

 Ok, but there is no function such as mapMonad in the operational package?

No, not yet, but I'll probably add it, or at least its lesser cousin

liftT :: Program instr a - ProgramT instr m a

to a future version of the library. Still pondering.

 By the way, I noticed that ProgramT is not automatically made instance of
 MonadIO when possible. It could be:
 instance (MonadIO m) = MonadIO (ProgramT r m) where
 liftIO = lift . liftIO
 
 Is that intentional?

Yes and no. I refrained from making instances for the  mtl  classes
because I have not clearly thought about the design consequences yet.

I think that monad transformers are not the last word on modular
computational effects yet and I don't want to paint myself into a
corner. For example, as you note, the MonadIO instance could be deduced
automatically from the  MonadTrans  instance.

Of course, if I make  operational  interoperable with the  mtl , then I
better adhere to its style even if I'm not entirely happy with it.

 By the way, I finally managed to use operational to modify my TicTacToe
 game.

Yay! :D

 (One shot, by the way, I had no bugs ^^. Very nice when it happens...)
 Human player and AI are working. I'm currently fixing the Network player.
 If you are interested, I could upload my code (it can be another example of
 how to use the operational package).

Sending me / uploading your TicTacToe code would be great! I probably
won't use it verbatim, but try to simplify it a bit to turn it into
another easy to understand example of how to use  operational .


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: hamming distance allocation

2010-04-19 Thread Heinrich Apfelmus
Arnoldo Muller wrote:
 I want to generate some hamming distance statistics about a set of strings.

   filter (\x - x /= 0) $
 map (uncurry hammingX) [(xs, ys) | xs - exampl, ys - exampl]
 
 [...]

 -- function posted in this mailing list
 hamming2 :: String - String - Int
 hamming2 xs ys = length (filter not (zipWith (==) xs ys))
 
 I am executing these functions millions of times and the bottleneck of my
 program is in them as explained by running in profiling mode with  +RTS
 -K400M -p -RTS
 
 The costlier function is the hamming distance
 COST CENTREMODULE   %time %alloc
 
 hammingDistances 66.6   41.9

Another way to look at it is that you shouldn't optimize  hamming
itself, but rather make sure that it's called less often!

For instance, your expression can be replaced by

   filter (/=0) [hammingX x y | (x:xs) - tails example, y - xs]

which cuts the total running time in half. It's still quadratic in the
length of  example . I'm sure there are faster algorithms out there that
can bring it down to O(n log n) if you want.


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Fwd: Re: Simple game: a monad for each player

2010-04-19 Thread Heinrich Apfelmus
Heinrich Apfelmus wrote:
 Limestraël wrote:
 Okay, I start to understand better...

 Just, Heinrich, how would implement the mapMonad function in terms of the
 operational package?
 You just shown the signature.
 
 Ah, that has to be implemented by the library, the user cannot implement
 this. Internally, the code would be as Bertram suggests:
 
 mapMonad :: (Monad m1, Monad m2)
  = (forall a . m1 a - m2 a)
  - ProgramT instr m1 a - ProgramT instr m2 a
 mapMonad f (Lift m1)  = Lift (f m1)
 mapMonad f (Bind m k) = Bind (mapMonad f m) (mapMonad f . k)
 mapMonad f (Instr i)  = Instr i

Silly me! This can be implement by the user:

mapMonad f = id' = lift . f . viewT
where
id' :: ProgramViewT instr m1 a - ProgramT instr m2 a
id' (Return a) = return a
id' (i := k) = singleton i = mapMonad f . k

and it would be a shame for the operational approach if that were not
possible. :)


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: hamming distance allocation

2010-04-20 Thread Heinrich Apfelmus
Daniel Fischer wrote:
 Heinrich Apfelmus:

 For instance, your expression can be replaced by

filter (/=0) [hammingX x y | (x:xs) - tails example, y - xs]

 which cuts the total running time in half. It's still quadratic in the
 length of  example . I'm sure there are faster algorithms out there that
 can bring it down to O(n log n) if you want.
 
 I don't think so. You can't calculate the Hamming distance of x and z from 
 the distances between x and y and y and z, so you'd have to consider all 
 pairs of distinct strings, wouldn't you?

And there I was sure about something once, only to see that it's
actually really doubtful... ;)

The thing about the Hamming distance is that it's not a black box, so
you can't get a lower bound by counting the number of minimum calls to
hamming  that have to be made. You are essentially arguing that the
different Hamming distances are independent, which they are not. Not to
mention that there are also black-box restrictions like the triangle
inequality

d(x,z) = d(x,y) + d(y,z)

but that one is probably harmless. In short, the situation is similar to
how the sorting bound O(n*log n) does not apply to radix sort.


Still, you are right to question my O(n*log n) claim; so far, my
attempts at finding such an algorithm myself have failed.

More precisely, the goal is to make a histogram of the possible hamming
distances. We need at least O(n*w) time to do that, where n is the
number of strings and w their maximum length; after all, we have to
touch every character. For simplicity, that the characters are just
one bit each. Furthermore, we can assume that w = log n, otherwise
there are lots of duplicate strings which can be grouped together. In
this notation, the simple algorithm takes O(n^2*w) time.


I did find a straightforward divide-and-conquer algorithm to tally small
Hamming distances, but it's not good enough for the whole histogram.
Here's the specification:

countHemming :: Int - [Bool] - [Bool]
countHemming d xs ys = length [() | x-xs, y-ys, hamming x y == d]

In other words,  countHemming d xs ys  counts the number of pairings
(x,y) whose Hamming distance is exactly  d .

Now, the idea is that this can be made faster for small  d . For
instance, for  d == 0 , we are essentially just calculating the number
of different elements of  xs  and  ys . By requiring that  xs  and  ys
be sorted, this can be done in linear time

countHemming 0 xs ys = ... a variation on  merge xs ys

And for slightly larger  d , we can partition the lists by their first
bits and continue recursively

countHemming _ [] [] = 0
countHemming d xs ys =
  countHemming (d-1) x0 y1 + countHemming (d-1) x1 y0
+ countHemming d x0 y0 + countHemming d x1 y1
where
(x0,x1) = partitionByHead xs
(y0,y1) = partitionByHead ys

partitionByHead xs = (behead True xs, behead False xs)
behead b xs = [bs | (b':bs) - xs, b == b']

To estimate the running time, we set  n = length (xs ++ ys) and let

T(d,n) = running time of  countHamming d xs ys

We started with

T(0,n) = O(n)

and want to discuss the recursive case. The idea is that each list is
divided in half, so we get

T(d,n) = 2*T(d-1,n/2) + 2*T(d,n/2)

From this, we can calculate

T(1,n) = 2*T(0,n/2) + 2*T(1,n/2)
   = O(n) + 2*T(1,n/2) -- remember quicksort!
   = O(n*log n)
T(2,n) = O(n*log n) + 2*T(2,n/2)
   = O(n*(log n)^2)

and so on, yielding

T(d,n) = O(n*(log n)^d)


Alas, this can be used to search a dictionary while accounting for
spelling errors, but it's no good to calculate a full histogram because
it becomes prohibitively expensive when  d ~ w/2 ~ (log n)/2  .



Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: hamming distance allocation

2010-04-21 Thread Heinrich Apfelmus
Arnoldo Muller wrote:
 
 I believe these problems are one of the major sources of frustration for
 Haskell newbies. Things that could work in X language easily suddenly
 become problems in Haskell. When you overcome these issues then you feel
 happy again that you chose Haskell as the main programming language of your
 research project.

Well, the difference between X and Haskell is pretty much unavoidable.
If you care about space and time usage, then there is no way around
learning about lazy evaluation and Haskell's execution model.

 Is there any guide that explains more about the bad consumption pattern.
 Are there any general rules defined to avoid these issues? It helped me to
 re-read the chapter on profiling in the Real World Haskell book to sorta
 understand the problem. Is there a more detailed definition of the problem
 than in RWH?

Two of the most commonly occurring patterns are

  1) foldl' vs foldl

  2) average xs = sum xs / length xs
 vs
 average = uncurry (/) . foldl' (\(!s,!n) x - (s+x,n+1)) (0,0)

Other than that, most Haskell books offer a clear exposition of the
reduction model. For instance, there is

   Graham Hutton. Programming in Haskell, chapter 12.
   Richard Bird. Introduction to Functional Programming using Haskell
   2nd edition, chapter 7.

The wikibook contains some preliminary material, too.

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



Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: ANN: forkable-monad 0.1

2010-04-21 Thread Heinrich Apfelmus
David Anderson wrote:
 Dear Haskellers,
 
 I'm happy, and only slightly intimidated, to announce the initial
 release of forkable-monad.
 
 The short version is that forkable-monad exports a replacement forkIO
 that lets you do this:
 
 type MyMonad = ReaderT Config (StateT Ctx IO)
 
 startThread :: MyMonad ThreadId
 startThread = forkIO threadMain
 
 threadMain :: MyMonad ()
 threadMain = forever $ liftIO $ putStrLn Painless monad stack forking!
 
 Note the lack of monad stack deconstruction and reconstruction to
 transport it over to the new thread. You'll find the details in the
 Haddock documentation for the module.

Nice work!

It appears to me that this is subsumed by the recent  MonadMorphIO
proposal that Anders Kaseorg came up with, though?

   http://article.gmane.org/gmane.comp.lang.haskell.libraries/12902


   fork :: MonadMorphIO m = m () - m ()
   fork m = morphIO $ \down - forkIO (down m  return ())
down (return ())


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Hughes' parallel annotations for fixing a space leak

2010-04-22 Thread Heinrich Apfelmus
Leon Smith wrote:
 Heinrich Apfelmus wrote:
 which were introduced by John Hughes in his Phd thesis from 1983. They
 are intriguing! Unfortunately, I haven't been able to procure a copy of
 Hughes' thesis, either electronic or in paper. :( Can anyone help? Are
 there any other resources about this parallel approach?
 
 Aye,  returning lazy pairs is one of those things that seems rather
 magical in several respects.   Out of curiousity,  have you looked at
 the unsafePerformIO thought experiment near the end of my Monad Reader
 article?   It demonstrates that returning lazy pairs can introduce
 multiple code paths through a single function,  reminiscent of (but
 different than) multi-mode logical relations.   (Mercury, for example,
 optimizes relations differently depending on their mode.)

Yes, the multiple code paths phenomenon is pretty much the essence of
lazy evaluation, i.e. only one part of the whole expression is evaluated
and it depends on the demand pattern which part that is.


Thanks to the kind souls on haskell-cafe, I finally understand the
SYNCH  primitive. The idea is that in

   let (y,z) = SYNCH x in ...

the variables  y  and  z  are bound to  x , but the value of  x  is only
evaluated when *both* y and z are demanded. If you demand only y, then
evaluation will stall. Clearly, this is useless without some form of
parallelism that makes it possible to demand both at the same time.

The SYNCHLIST function is a variation on that; it also guarantees that
the list elements are consumed in lock-step.

   SYNCHLIST xs = (d1 `seq` x1, d2 `seq` x2)
   where
   (d1,d2) = SYNCH xs
   (t1,t2) = SYNCH (tail xs)
   (x1,x2) = case xs of
   [] - ([],[])
   (x:xs) - (x:t1,x:t2)


In other words, SYNCH binds a values to two different variables without
actually sharing it.


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: ANN: forkable-monad 0.1

2010-04-23 Thread Heinrich Apfelmus
David Anderson wrote:
 So, it seems that I am reinventing wheels that others have generalized
 better :-). That's fine, it's the expected result of launching and
 iterating, especially given my current command of Haskell. So I should
 now focus on reducing the reinvention.

No worries, this MonadMorphIO thing is very recent, I just wanted to
mention that it's applicable here as well. :)

 Most of the discussion that followed the message that you linked is
 currently beyond my understanding of category theory. However, I
 should probably go and talk to the maintainer of MonadCatchIO-* about
 extracting something like MonadMorphIO into a package, and making both
 their exception handling modules and this forking module reuse it.

Sounds good; although I do think that the problem of making monads
modular does not yet have a completely satisfactory answer, even with
MonadMorphIO. But that should not deter from experimentation. :)


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: FRP for game programming / artifical life simulation

2010-04-25 Thread Heinrich Apfelmus
.



Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: FRP for game programming / artifical life simulation

2010-04-29 Thread Heinrich Apfelmus
Chris Eidhof wrote:
 I agree. This would be an extremely useful feature, not only for game
 development, but also for web development. We often use continuations
 as a way to add state to the web, but this fails for two reasons:
 whenever the server restarts, or when we scale to multiple machines.

Note that for web development, you could also store a log of client
responses on the client side and replay that whenever a request is made
to get some kind of persistent session. This is only suited for
lightweight use cases, of course.

I've implemented a small demonstration as part of the operational
package, it's the  WebSessionState.lhs  on

  http://projects.haskell.org/operational/examples.html


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Fwd: Re: Simple game: a monad for each player

2010-05-01 Thread Heinrich Apfelmus
Limestraël wrote:
 Heinrich, I saw you updated your operational package (you considered my
 remark about ProgramView, thank you)

Your feedback is much appreciated. :)

 I saw you added a liftProgram function, however it is not like the mapMonad
 function you were talking about.
 mapMonad was:
 mapMonad :: (Monad m1, Monad m2) =
 (forall a . m1 a - m2 a)
- ProgramT instr m1 a
- ProgramT instr m2 a
 
 and you turned it into the less generic:
 liftProgram :: Monad m = Program instr a - ProgramT instr m a
 
 Did you change your mind?

Yes, I opted for the less generic function. My reasons were:

a)  mapMonad  has a precondition that is not caught by the type checker.
Namely, the first argument  f :: forall a. m1 a - m2 a  must respect
the monad laws, i.e.

f . return  = return
f (m = k) = f m = f . k

If the  f  supplied by the user doesn't satisfy these equations, then it
will break invariants internal to the library, which is bad.

b) Excluding  mapMonad  does not go beyond the  mtl  in that the latter
does not provide functions

mapStateT :: (Monad m1, Monad m2) =
  = (forall a . m1 a - m2 a)
  - StateT s m1 a - StateT s m2 a

either.

b') The TicTacToe example only uses  m = IO  and  m = Identity  and
liftProgram  is enough for that.

Basically, I'm unsure about the whole business of monad modularity. No
completely satisfactory solution has emerged yet, so I'm copying the
mtl  style for now.

c) Fortunately, users of the library don't lose functionality, only
convenience, because they can implement  mapMonad  themselves if they so
desire:

mapMonad f = id' = lift . f . viewT
where
id' :: ProgramViewT instr m1 a - ProgramT instr m2 a
id' (Return a) = return a
id' (i := k) = singleton i = mapMonad f . k

(This is contrary to what I said earlier,  mapMonad  does *not* have to
be a library function.)


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: FRP for game programming / artifical life simulation

2010-05-03 Thread Heinrich Apfelmus
Peter Verswyvelen wrote:
 Actually, I believe that many Yampa examples do separate the drawing
 from the update... The arrow provides the game data that *can* be
 rendered. If you provide interpolators for that game data, you can
 still achieve the same as is explained in fix your timesteps (in my
 own FRP experiments I have an update thread and a render thread).

But the arrow implementation determines the  dt  at which the arrows ~
(Time - a) - (Time - b)  are sampled, no? The end result of a Yampa
arrows is a graphic, after all.

 But IMHO fix your timestep still misses an important detail, in that
 the delta-time that is measured is the duration of the previous frame,
 and it assumed that the next frame will take as long as the previous
 (who says that integrate from the article won't take longer than
 dt?). Now say you are updating at 100 FPS = 10ms, but the next frame
 actually takes longer, say 20ms. That actually means that you should
 have passed 20ms as the delta-time of the this frame, because the real
 time is ahead now! This is really noticeable as little jerky frame
 hick-up in the motion. In my first game (1987), I added an estimator
 to compute how long the delta-time of the next frame would be, which
 results in much smoother motion: you notice that the
 frame-sampling-rate drops, but you don't see a frame hick-up. I rarely
 see this in modern games, most PC and even console games suffer from
 frame hick-up (which could be defined as the real-time moving ahead of
 the game-time for a brief moment)

I'm not sure I follow, could you elaborate on what exactly causes the
frame hick-up?

As far as I understand it, the approach of fix your time-step is that
you have a physics simulation and a rendering engine. To ensure
numerical stability, the physics are calculated with a fixed time step
dt  which can be larger than the rendering frame rate. In particular,
one step of physics simulation should take less than  dt  real time,
because otherwise you're screwed.

The graphics engine just draws as fast as possible. To ensure
smoothness, it interpolates slightly into the future. The FPS number
measures the frequency of drawn graphics, not the rate of physics
updates. There may be multiple physics steps per drawing when the latter
is slow, or the other way round, when the latter is fast.


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: What do _you_ want to see in FGL?

2010-05-10 Thread Heinrich Apfelmus
Ivan Lazar Miljenovic wrote:
 Henning Thielemann writes:

 Recently I wrote cabal-sort using FGL
   http://hackage.haskell.org/package/cabal-sort

 It sorts cabal packages topologically according to their
 dependencies. However, I was neither happy with the way FGL currently
 works, nor with the way I proposed recently (splitting into unlabelled
 and labelled graphs). I like to use the package name as node identifier.
 I do not need any label, but I need a node type different from Int.
 With current FGL I need to maintain a Map PkgName Int. Would it be
 sensible to generalize the Node type to any Ord type or does FGL use
 optimizations specific to Int? In another example I used FGL for
 finding all topological orderings of a set of database
 transactions. In this case I used an enumeration type as node
 type. Are there other applications for alternative Node types?
 
 We're considering doing this.
 
 Pros for allowing you to use a custom node type:
 * Matches your data better
 * No need for extra lookup maps when converting your data to FGL form
 
 Cons:
 * Makes type-sigs uglier/more verbose
 * Restricts the ability to optimise
 
 Using Int gives us a fixed-size data type with known good comparison
 performance and with a range that should suit most purposes.

I have the same gripe as Henning, though I'm not sure I concur with his
proposal.


Here a snippet from a quick  dirty 'make' implementation that I use for
building my website:

data Rule = Rule { ins :: [FilePath], out :: FilePath,
   effect :: IO () }

rules2Graph :: [Rule] - G.Gr (IO ()) ()
rules2Graph rules = G.mkGraph nodes' edges'
where
nodes = [(out r, conditionally (effect r) (ins r) (out r))
 | r - rules]
edges = [(i, out r, ()) | r - rules, i - ins r,
  i `Map.member` nodeMap]
  -- ignore source nodes

nodeMap = Map.fromList nodes
index k = Map.findIndex k nodeMap
nodes'  = map (\(a,b) - (index a, b)) nodes
edges'  = map (\(a,b,c) - (index a, index b, c)) edges

The nodes are file paths, labeled with a corresponding IO action to
create the file. The nodes are created from a list of rules that specify
how to create an output file from several input files.

As you can see, I had to use  Data.Map  to convert file paths into node
indexes. Ideally, the  Data.Graph.Inductive.NodeMap  module should be
used for that, but after some frustration, I found it completely
unsuitable for this task because it insists on using the graph label as
node identifier.

I am particularly unhappy about the definitions of  nodes'  and  edges'
, the clever use of  Map.findIndex  to translate indexes while keeping
track of a label and the need for mapping the indexes myself.


I'm not sure what the right solution is, but I think it definitely
involves catering for different node types. For instance, the library
could operate on a type

newtype Graph node a b = Graph (Gr a b, Data.Map.Map Int node)

or it could offer a more useful  NodeMap  type and make the  Node  type
abstract. Some systematic and simple abstractions to manage nodes is
needed anyway.

Also, hard-coding  Node = Int  feels like the wrong kind of flexibility:
the user is able to do anything with it, just in case the library forgot
some important functionality. Which is exactly what happened in my case
when I used  Map.findIndex . I prefer the library to get it right.


PS: While we're at it, I think  newNodes  should return an infinite list
of  Node  instead of requiring a fixed number to be specified in advance?


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: What do _you_ want to see in FGL?

2010-05-12 Thread Heinrich Apfelmus
Ivan Lazar Miljenovic wrote:
 Heinrich Apfelmus writes:
 I'm not sure what the right solution is, but I think it definitely
 involves catering for different node types. For instance, the library
 could operate on a type

 newtype Graph node a b = Graph (Gr a b, Data.Map.Map Int node)

 or it could offer a more useful  NodeMap  type and make the  Node  type
 abstract. Some systematic and simple abstractions to manage nodes is
 needed anyway.
 
 As I said, we're considering using an Associated Type to let users
 choose what type they want to use (probably with a default Map instance
 for this).  However, we'd recommend/push the Int-based one.

For my  make  example, I prefer a plain parameter because it would be
too verbose to define a new class that has  FilePaths  as node types.
I'd use the  Int  instead, but this defeats the point: why offer
flexible node types when it's too much of a burden to use them?

 An explicit type parameter for the vertex type is not appropriate for
 this reason: you don't want to change it.

It's true that I don't want to change the node type, but I want to curry
it. If I don't feel like writing out the node type every time, I can use
a type synonym:

   type MyGraph a b = Graph FilePath a b


Graphs with different node types don't behave differently; graphs are
parametric with respect to the node type, just like lists don't behave
differently on different element types.


 Also, hard-coding  Node = Int  feels like the wrong kind of flexibility:
 the user is able to do anything with it, just in case the library forgot
 some important functionality. Which is exactly what happened in my case
 when I used  Map.findIndex . I prefer the library to get it right.
 
 What do you mean by the library forgot some important functionality?

Ah, I'm comparing  Node = Int  to a  Node  type that is entirely
abstract. After all, conceptually,  Node  is not an integer, it's a
unique identifier.

If  Node  is abstract, then you will probably miss things like the [1..]
 that you mentioned.

Nonetheless, I would like to see  Node  to become abstract. This means
that the graph library should include a library that deals with unique
identifiers  Node . The [1..] pattern would correspond to a function

freshNodes :: () - [Node]

 PS: While we're at it, I think  newNodes  should return an infinite list
 of  Node  instead of requiring a fixed number to be specified in
 advance?
 
 Well, if we let the vertex type be _anything_ (that is an instance of
 Ord; we'll probably require that much at least, though maybe just Eq
 would make sense for list-based graphs), then how do we generate
 newNodes?  Require Enum?  Bounded?

Ah, that suggestion was for  Node = Int  or  Node = abstract . If the
library user uses his own node type, it's him who is responsible for
allocating new  Nodes .

 Really, performance aside, this is my biggest possible problem with
 generic label types is that it may make it harder to define various
 algorithms on graphs because you can no longer guarantee what you can do
 with the vertex types; as such people may resort to requring the vertex
 type to be Int or something to use a specific algorithm.

Ah, you mean algorithms that create new nodes on the fly? I don't think
that  Node = Int  works for them either, because the user might have his
own ideas about which  Ints  can appear as graph vertexes. For instance,
he might only use even numbers to denote vertexes and will be surprised
by a library algorithm that suddenly creates odd vertexes. In short,
Node  needs to be abstract for that.

Other than that, I don't see much of a difference between custom vertex
types and  Int  . Internally, you can always use  Int  to reference
nodes and keep the association between the custom vertex type and  Int
in a separate map, like this

   data Graph node a b =
   Graph { internal :: Gr a b , nodes :: Map node a }


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: What do _you_ want to see in FGL?

2010-05-12 Thread Heinrich Apfelmus
Henning Thielemann wrote:
 
 Ivan Miljenovic wrote:
 
 You're splitting apart related data into _three_ different data
 structures (the graph, vertex labels and edge labels)?  _That_ doesn't
 make sense.
 
 There are no edge labels, only vertex labels. And yes, I find separation
 of data structures for separation of concerns a good strategy.

It appears to me that the concerns of labels and vertexes are not
separate enough. After all, the point is that they have to be kept in
sync. Keeping them in sync should be the business of the graph library,
not of the user. It doesn't have to be baked into the graph type,
though,  an abstract  Node  type might work as well.


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: What do _you_ want to see in FGL?

2010-05-13 Thread Heinrich Apfelmus
Ivan Lazar Miljenovic wrote:
 Heinrich Apfelmus writes:

 Graphs with different node types don't behave differently; graphs are
 parametric with respect to the node type, just like lists don't behave
 differently on different element types.
 
 There will be a Map-based graph available that will have the node type
 parameter, but the variant that's currently called PatriciaTree will
 most likely be the preferred default one (as it will have better
 performance due to its use of IntMap).
 
 We can't require the class to have the vertex type as a type parameter
 for when we want a graph (such as PatriciaTree) _with_ a fixed vertex
 type.

Ah, ok, you want graphs that only work with one node type. If there is
at most one such graph for each node type, you could make a data type
family and retain the parameter, though

data family Graph node :: * - *
data family Graph Int  a b = PatriciaTree a b
data family Graph node a b = GenericTree

But it seems that this doesn't work because the cases overlap.


 Actually, I've looked through my code and it appears that (apart from
 verboseness), there won't be too much of a problem with removing the
 assumption of vertex type == Int.
 
 However, I can't see any reason why someone would only want to use even
 Int values.  As I think I've said before (I've been making these
 arguments in various threads and discussions, so I'm not sure if I've
 said it here): the vertex type is just an _index_ to ensure consistency,
 etc; it is _not_ IMHO meant to represent the actual data: that's what
 the labels are for.

Yes, the integers are just indexes. Of course, the example with the even
integers is a bit silly; but if the integers are actually indexes, then
it's conceptually cleaner to make them abstract, i.e.

data Node  -- constructors are not exported

and provide combinators to operate on these abstract indexes, including
a corresponding Data.Graph.Inductive.NodeMap module.

I'd like to see such an abstract  Node  type, because then the library
will provide all operations I need. It took me some time to figure out
how to best use  Int  as indexes in my example code; an abstract  Node
type and a good  NodeMap  module would have made my life much easier.

 Other than that, I don't see much of a difference between custom vertex
 types and  Int  . Internally, you can always use  Int  to reference
 nodes and keep the association between the custom vertex type and  Int
 in a separate map, like this

data Graph node a b =
Graph { internal :: Gr a b , nodes :: Map node a }
 
 Custom vertex types will work; it's just that using Int will probably
 prove to be in general more efficient and easier to use.  I haven't said
 we'll disallow custom vertex types, but I don't plan on going on the
 extreme of having optional labels, or of making the vertex type a type
 parameter for all graphs (since as I've said, you don't/can't always
 want/assume that).

Darn, I meant

data Graph node a b =
Graph { internal :: Graph Int a b, nodes :: Map Int a }

The idea is to use  Ints  internally and only store a loose association
to the custom vertex type. In particular, no  Map a Int  is required,
only from  Int  to  a . Now, I realize that the other way round is
required as well for querying the context of a node in a graph.



Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: What do _you_ want to see in FGL?

2010-05-14 Thread Heinrich Apfelmus
Ivan Miljenovic wrote:
 Heinrich Apfelmus wrote:

 Yes, the integers are just indexes. Of course, the example with the even
 integers is a bit silly; but if the integers are actually indexes, then
 it's conceptually cleaner to make them abstract, i.e.

data Node  -- constructors are not exported

 and provide combinators to operate on these abstract indexes, including
 a corresponding Data.Graph.Inductive.NodeMap module.

 I'd like to see such an abstract  Node  type, because then the library
 will provide all operations I need. It took me some time to figure out
 how to best use  Int  as indexes in my example code; an abstract  Node
 type and a good  NodeMap  module would have made my life much easier.
 
 I'm not sure I understand what you're saying here: first you said you
 wanted to be able to specify a vertex type, now you're saying that you
 don't want to know what the vertex type even is (except that it's some
 abstract Node type)?  Whilst this would make graph usage safer/more
 robust, this seems to contradict your earlier arguments...

I'd be happy with either one. :) In both cases, I want to specify a
custom vertex type.

I can either do that directly if the library permits, though I think the
solution with associated types is too cumbersome to be useful for my
make  example.

Or I get an abstract  Node  type and the library provides just the right
functions that make it easy to manage a custom vertex type myself. I had
hoped that the  Data.Graph.Inductive.NodeMap  module provides this,
which it doesn't.

In other words, the abstractness of  Node  forces the library to provide
a well-designed set of functions to work with them, and that's what I'm
after. In my  make  example, I spent the most time thinking about how to
manage the  Int  nodes, finally settling with  Data.Map.findIndex , and
I prefer the library to think about that for me.

 Darn, I meant

data Graph node a b =
Graph { internal :: Graph Int a b, nodes :: Map Int a }

 The idea is to use  Ints  internally and only store a loose association
 to the custom vertex type. In particular, no  Map a Int  is required,
 only from  Int  to  a . Now, I realize that the other way round is
 required as well for querying the context of a node in a graph.
 
 What's the point of that useless node type parameter then?  And how
 does the nodes map differ from just getting the graph label?

You're right, I now realize that this design doesn't work. But you asked
for wishes, so I wished for something. ;)


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: What do _you_ want to see in FGL?

2010-05-15 Thread Heinrich Apfelmus
Ivan Lazar Miljenovic wrote:
 Heinrich Apfelmus writes:
 I'd be happy with either one. :) In both cases, I want to specify a
 custom vertex type.
 
 Except an abstract type isn't a custom vertex type...
 
 I can either do that directly if the library permits, though I think the
 solution with associated types is too cumbersome to be useful for my
 make  example.
 
 Why?

I was under the impression that I would have to define a new graph data
type with  FilePath  as vertex type and make that an instance of  Graph
? In that case, it would be much shorter for me to stick with the clumsy

nodeMap = Map.fromList nodes
index k = Map.findIndex k nodeMap
nodes'  = map (\(a,b) - (index a, b)) nodes
edges'  = map (\(a,b,c) - (index a, index b, c)) edges

 Or I get an abstract  Node  type and the library provides just the right
 functions that make it easy to manage a custom vertex type myself. I had
 hoped that the  Data.Graph.Inductive.NodeMap  module provides this,
 which it doesn't.
 
 Not sure I follow what you're saying here; then again, my graph stuff
 has typically been to create the graph and then do stuff to it _as_ a
 graph (and not wanting/needing to get a specific node based upon its
 label, etc.).

In the  make  example, I didn't need to get a node based on its label
either. But the graph was a graph of  FilePaths  and I still have to
implement an association between that and  Int . (In fact, I don't know
of any graph whose nodes are unique integers conceptually.)

In other words, I have to make sure that every  FilePath  is mapped to a
unique integer which I can then glue into a graph. This is not hard to
do with a  Data.Map  and the four lines of code above do exactly that.
However, I still had to think about it and it took me way too long to
come up with these four lines. What I would like to see is that the
*library* has thought about that for me already.

A good way to ensure that the library has thought about that is to make
the  Node  type abstract. This way, the library has to provide the
functionality to create and manage nodes, which I would otherwise cobble
together on my own by messing with  Int .

One possibility is to offer a function

mkGraph :: Ord node = [(node,a)] - [(node,node,b)]
- (Gr a b, NodeMap node)

that accepts a custom vertex type, creates all the necessary unique
integers internally and also returns an association between the newly
created  Nodes  and the custom  node  in case I want to refer to the
nodes in the graph with the custom type.

The  NodeMap  type - while implemented as a  Data.Map - is abstract as
well and has the primitives

   empty  :: NodeMap n
   insert :: n - NodeMap n - NodeMap n
   lookup :: n - NodeMap n - Maybe Node
   lookupNode :: Node - NodeMap n - Maybe n
   delete :: Node - NodeMap n - NodeMap n

This is all you need to manage the association  node - Node . In
particular,  insert  creates new  Nodes  on the fly.

And since the nodes in the graph and the  NodeMap  will usually come in
pairs, we can as well give the pair a new name:

   type Graph node a b = (Gr a b, NodeMap node)


To summarize: an abstract  Node  type relieves me from thinking about
the association between my conceptual node type and unique identifiers.
I'd be happy with anything along these lines, the interface above is
just a suggestion.


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: ANN: Monad.Reader Issue 16

2010-05-16 Thread Heinrich Apfelmus
Brent Yorgey wrote:
 I am very pleased to announce that Issue 16 of The Monad.Reader is now
 available [1].
 
 Issue 16 consists of the following three articles:
 
 * Demand More of Your Automata by Aran Donohue
 * Iteratee: Teaching an Old Fold New Tricks by John W. Lato
 * Playing with Priority Queues by Louis Wasserman

Another great issue of my favorite Haskell magazine!


I have a remark on Louis' article. Namely, I think the description of
amortization is a bit unfortunate in a persistent setting like Haskell.
The  inc  example will still take O(1) amortized time, but not because
costs are saved in advance, you can't save anything when things are
persistent. Imagine several clones of you coming from the future and
trying to access your current bank account savings...

The real reason for O(1) is that the changes to the list are lazy and
the cost for the expensive operation is payed as tax by *future*
operations that attempt to extract elements further down the list.
This means that the amortized bound depends on the available functions
for *observing* the data structure, too.

Unfortunately, I think this makes the proof of theorem 27 more subtle:
you need to make sure that you don't pay more than O(log n) in tax for
evaluating the binary number with  log n  digits to normal form! In
other words, each increment might take O(1) time but this could create
so many taxes that printing all digits takes a lot longer.

To demonstrate the issue, consider the function

   bunk :: [Bool] - [Bool]
   bunk (True  : bs) = False : bunk bs
   bunk (False : bs) = True  : bunk bs
   bunk []   = [True]

This will take O(1) time when you only look at the head of the list
afterwards, i.e.

   head . bunk . bunk . ... . bunk $ []

is always O(n). But

   length . bunk . bunk . ... . bunk $ []

will take O(n^2). You'd have to show that this doesn't happen with  inc .


For more on how to do amortized analysis in a persistent setting, see
also Okasaki's book

  Purely Functional Data Structures.
  http://www.cs.cmu.edu/~rwh/theses/okasaki.pdf

I have collected some mailing lists posts on his debit method here:

  http://apfelmus.nfshost.com/articles/debit-method.html


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: What do _you_ want to see in FGL?

2010-05-17 Thread Heinrich Apfelmus
Ivan Lazar Miljenovic wrote:
 Heinrich Apfelmus writes:

 I was under the impression that I would have to define a new graph data
 type with  FilePath  as vertex type and make that an instance of  Graph
 ? [..]
 
 Well, we'll provide a Map-based one that lets you specify the vertex
 type as a type parameter; this functionality (type parameter being ued
 for the vertex type) won't be required since not all graphs will be able
 to chop and choose which vertex type to use.

Ah, that would indeed make it easy. Maybe make the map based graph
generic, so that it can be used with any primitive graph implementation?

   data VertexGraph node gr a b = VG (gr a b) (BiMap node (Vertex gr))

   instance (Ord node, Graph gr) = Graph VertexGraph node gr where

But this is probably not worth the hassle because if you really want
performance, you shouldn't choose another  gr  but rather make your own
instance with a custom map. I think it's fine to supply a default choice
for  gr .

 In the  make  example, I didn't need to get a node based on its label
 either. But the graph was a graph of  FilePaths  and I still have to
 implement an association between that and  Int . (In fact, I don't know
 of any graph whose nodes are unique integers conceptually.)

 In other words, I have to make sure that every  FilePath  is mapped to a
 unique integer which I can then glue into a graph. This is not hard to
 do with a  Data.Map  and the four lines of code above do exactly that.
 However, I still had to think about it and it took me way too long to
 come up with these four lines. What I would like to see is that the
 *library* has thought about that for me already.
 
 Right; I'm going to look at merging this import-like functionality from
 Graphalyze (which already does this).
 
 [snip]

 To summarize: an abstract  Node  type relieves me from thinking about
 the association between my conceptual node type and unique identifiers.
 I'd be happy with anything along these lines, the interface above is
 just a suggestion.
 
 Well, you can consider the current Int vertex type to be a (not-so-)
 abstract vertex type; it might be an idea to wrap this up so people
 don't mess with it themselves though.

That would be much appreciated. :)


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: What do _you_ want to see in FGL?

2010-05-18 Thread Heinrich Apfelmus
Ivan Lazar Miljenovic wrote:
 Heinrich Apfelmus writes:
 Ivan Lazar Miljenovic wrote:

 Well, we'll provide a Map-based one that lets you specify the vertex
 type as a type parameter; this functionality (type parameter being ued
 for the vertex type) won't be required since not all graphs will be able
 to chop and choose which vertex type to use.

 Ah, that would indeed make it easy. Maybe make the map based graph
 generic, so that it can be used with any primitive graph implementation?

data VertexGraph node gr a b = VG (gr a b) (BiMap node (Vertex gr))

instance (Ord node, Graph gr) = Graph VertexGraph node gr where
 
 Not sure I understand what the point of the `gr' is there; what I meant
 was something like:
 
 newtype MapGraph node a b = MG (Map node (Map node b, a, Map node b))

Yes; what I mean is that you can retrofit a custom vertex type to any
graph implementation that uses a fixed vertex type. So, let's say that

   data Gr a b = .. -- graph with vertex type  Vertex Gr = Int

then

   type Gr' node a b = CustomVertex node Gr a b

   data CustomVertex node gr a b = CV (gr a b) (Map node (Vertex gr))

is a graph with custom vertex type  node .


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: What do _you_ want to see in FGL?

2010-05-19 Thread Heinrich Apfelmus
Ivan Lazar Miljenovic wrote:
 Heinrich Apfelmus writes:
 Yes; what I mean is that you can retrofit a custom vertex type to any
 graph implementation that uses a fixed vertex type. So, let's say that

data Gr a b = .. -- graph with vertex type  Vertex Gr = Int

 then

type Gr' node a b = CustomVertex node Gr a b

data CustomVertex node gr a b = CV (gr a b) (Map node (Vertex gr))

 is a graph with custom vertex type  node .
 
 Sounds like it's more complicated than it's worth tbh ;-)

Yup. ;)


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Stone age programming for space age hardware?

2010-06-08 Thread Heinrich Apfelmus
Michael Schuerig wrote:
 I was dumbfounded, although I have known all this. I have no personal 
 experience with either embedded or real time software, but I've been 
 aware that C still is the most popular language for that purpose and 
 that coding standards are very restrictive.
 
 The real reason behind my surprise was, that I was wondering how more 
 modern languages could make inroads into such an environment. Haskell 
 without recursion and dynamic memory allocation? Hard to imagine.

I have absolutely no experience with real time system, but if I were
tasked to write with these coding standards, I would refuse and instead
create a small DSL in Haskell that compiles to the requested subset of C.

After all, the question is this: why use C if you don't actually use C?
The reason is probably that designing/writing a proper DSL is considered
too error prone, but with today's theorem provers, this should no longer
be the case.


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Stone age programming for space age hardware?

2010-06-09 Thread Heinrich Apfelmus
Michael Schuerig wrote:
 Heinrich Apfelmus wrote:

 I have absolutely no experience with real time system, but if I were
 tasked to write with these coding standards, I would refuse and
 instead create a small DSL in Haskell that compiles to the requested
 subset of C.
 
 That suggestion is similar to the approach taken by verifiable 
 languages, as Matthias describes it in a parallel reply.
 
 Now, the interesting question is, whether it is possible to define a DSL 
 that's expressive enough and still can be translated to a very 
 restrictive subset of C. I wouldn't expect the on-board functionality of 
 a space probe or rover to be trivial.
 
 I think it would count as cheating if you compile down a DSL to C code 
 that only takes a fixed chunk of memory, but then itself manages blocks 
 of that memory dynamically.

Ah, I had in mind that the embedded DSL represents the target subset of
C verbatim, very much in the spirit of Lennart Augustsson's
reimplementation of BASIC

   http://tinyurl.com/augustss-BASIC
   http://hackage.haskell.org/cgi-bin/hackage-scripts/package/BASIC

In other words, I'm thinking of a direct copy of the target language in
Haskell.


This way, you can use the type system to reject programs that don't
adhere to the coding standards, which would be the main point of this
embedding.

But you get a huge benefit on top of that: Haskell now serves as a macro
language and you can implement many abstractions that are not directly
available in the target language, like custom control structures
(foreach) or exceptions (to organize these abundant checks for error
conditions).

Of course, the main goal of the NASA restrictions is to make the code so
simple that it has no obvious deficiencies, but what better way is there
to do that than finding and expressing - even small-scale -
abstractions? (The  foreach  statement seems to be a convincing example.)

 As I understood Holzmann in his talk, use of C is a kind of cultural 
 heritage at JPL.

Ah well, the shackles of habit... In the matter of program design, I am
unconvinced of any cultural heritage that is not based on the
mathematical clarity of Edsger W. Dijkstra. ;)

 BTW, thanks for your recent video on GADTs.

My pleasure. :) I'm already planning another video experiment.


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Help with Bird problem 3.3.3

2010-06-11 Thread Heinrich Apfelmus
Günther Schmidt wrote:
 
 I'm just re-reading the book again, this time doing the exercises though :)
 
 Is there a site with solutions for the exercises?

Unless you count the haskell-cafe and beginners mailing lists as sites,
I don't know any sites which have the solutions. ;)


Problem 3.3.3: Construct a program for division from the specification

  (m * n) / n = m

and prove that it's correct.


Sketch of a solution: To define  a / n , the usual approach of
subtracting  n  from the first argument until something less than  n
remains will work. Correctness can then be proven by induction on  m .



Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Harder than you'd think

2010-06-13 Thread Heinrich Apfelmus
Marc Weber wrote:
 Andrew Coppin wrote:
 What I ended up writing is this: 
 http://www.hpaste.org/fastcgi/hpaste.fcgi/view?id=25782
   lookup :: KeyID - Key - Container - Maybe Value
 
 Does anybody have a less-insane way of doing this?
 
 Sure: 
 
   type MyMap = Map (KeyID, Key) Value
 
 Don't use multiple keys. Put the keys into a tuple and use that as key.

Actually, it's a disjoint sum type:

  data a :+: b = Inl a | Inr b   -- also known as  Either

  type DB3 e k1 k2 k2 = D1 e (k1 :+: k2 :+: k3)

Hm, that's not quite right either because every  e  has multiple keys.
The following should work, however:

  type DB3 e k1 k2 k2 = D1 e k1 :*: DB1 e k2 :*: DB2 e k3

  lookup :: (k1 :+: k2 :+: k3) - DB3 e k1 k2 k3 - Maybe e


In any case, I recommend using a special key type for combining keys
anyway, as explained here

  http://article.gmane.org/gmane.comp.lang.haskell.cafe/23648



Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Different choice operations in a continuation monad

2010-06-15 Thread Heinrich Apfelmus
Sebastian Fischer wrote:
 Holger Siegel wrote: 

 orElse :: CMaybe a a - CMaybe a a - CMaybe r a
 CMaybe ca `orElse` CMaybe cb = CMaybe (\k - (ca return `mplus` cb
 return) = k)
 
 I still don't understand why it is impossible to provide `orElse` with
 the original type. I will think more about the reason you gave.

The reason is that you have chosen the wrong type for your
continuation monad; it should be

  newtype CMaybe a = CMaybe (forall r. (a - Maybe r) - Maybe r)


Personally, I recommend to stop thinking about continuations altogether
and instead use the approach I've outlined in The Operational Monad
Tutorial

  http://apfelmus.nfshost.com/articles/operational-monad.html

to define and think about monads. In particular, performing the
refunctionalization I mentioned in the subsection Connection with the
Continuation Monad shows that the right type should indeed contain a
 forall r .



Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Different choice operations in a continuation monad

2010-06-16 Thread Heinrich Apfelmus
Sebastian Fischer wrote:
 Heinrich Apfelmus wrote:

 The reason is that you have chosen the wrong type for your
 continuation monad; it should be

  newtype CMaybe a = CMaybe (forall r. (a - Maybe r) - Maybe r)
 
 Yes, with this type `orElse` has the same type as `mplus`, which is very
 nice.
 
 Aside
 
 Personally, I recommend to stop thinking about continuations altogether
 and instead use the approach I've outlined in The Operational Monad
 Tutorial
 
 I appreciate your operational monad tutorial both for the idea and how
 you explained it. But the advice stop thinking about X because Y is
 better feels odd to me. Before I know by myself that Y is better than X
 (which requires thinking about both X and Y) I don't feel comfortable
 following such advice. Afterwards, I don't need such advice ;)

Very true. :) My flimsy personally was an attempt to declare my
recommendation optional. I failed to say the right thing even then, for
I don't mean to stop thinking about continuations in general, just to
discourage them as foundation for implementing other monads.

 There may be more to X than just Y. IIRC, there is more to
 'continuations' than 'monads'. For example, the implementation of
 `callCC` does not type check with your changed data type.

Ah, indeed,  callCC  in the operational setting is much trickier than I
thought. However, it also seems to be the reason why your original
approach does not work so well!

Basically, your choice of implementation

  newtype CMaybe r a = CMaybe ((a - Maybe r) - Maybe r)

supplies a default semantics for  callCC . But this means that when
implementing  orElse , you also have to consider its interaction with
callCC , even when you actually don't want to expose or implement a
callCC  function.

As for the interaction: what should

  ((callCC ($ 0)  mzero) `orElse` return 2) = return . (+3)

be? If the scope of  callCC  should not extend past  orElse , then this
evaluates to  return 5 . But this choice of scope dictates the type that
Holger mentioned.

If the the scope of  callCC  should extend beyond the  orElse , so that
the whole thing evaluates to  mzero ,  orElse  will have the type of
mplus . But then, I think that your implementation type  CMaybe  needs
to be more sophisticated because  orElse  now needs to detect whether
the argument contains a call to  callCC  or not in order to distinguish

  ((callCC ($ 0)  mzero) `orElse` return 2) = return . (+3)

  == mzero

from

  (mzero `orElse` return 2) = return . (+3)

  == return 5


In short, the interaction between  orElse  and  callCC  is tricky, and
it would be unfortunate to be forced to consider it due to a premature
choice of implementation type. This can't happen with the operational
approach, because that one merely implements the free monad over a set
of operations.

 I shall try to implement a monad that supports two choice operations
 (one which fulfills the distributive law and one which satisfies the
 cancellation property) with the operational package.

The main task will probably be to figure out the interaction between
mplus  and  orElse , i.e. to consider what stuff like

   a `orElse` (b `mplus` c)

should evaluate to.


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Different choice operations in a continuation monad

2010-06-18 Thread Heinrich Apfelmus
Heinrich Apfelmus wrote:
 Sebastian Fischer wrote:

 For example, the implementation of
 `callCC` does not type check with your changed data type.
 
 [snip]
 
 As for the interaction: what should
 
   ((callCC ($ 0)  mzero) `orElse` return 2) = return . (+3)
 
 be? If the scope of  callCC  should not extend past  orElse , then this
 evaluates to  return 5 . But this choice of scope dictates the type that
 Holger mentioned.
 
 If the the scope of  callCC  should extend beyond the  orElse , so that
 the whole thing evaluates to  mzero ,  orElse  will have the type of
 mplus . But then, I think that your implementation type  CMaybe  needs
 to be more sophisticated because  orElse  now needs to detect whether
 the argument contains a call to  callCC  or not in order to distinguish
 
   ((callCC ($ 0)  mzero) `orElse` return 2) = return . (+3)
 
   == mzero
 
 from
 
   (mzero `orElse` return 2) = return . (+3)
 
   == return 5

Out of curiosity, I've implemented these semantics with  operational .
Code attached.

Took me a while to figure out how to implement  callCC , but it turns
out to be straightforward if you simply carry around the current
continuation as an additional parameter.

It doesn't seem to be possible to implement this with just the  CMaybe r
a  type, in particular since the implementation I gave cannot be
refunctionalized to said type. In other words, there is probably no
associative operation

orElse :: CMaybe r a - CMaybe r a - CMaybe r a

with identity `mzero` that satisfies the cancellation law. I don't have
a proof, but the argument that it doesn't interact well with the default
implementation of  callCC  seems strong to me.


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com
{-
A small language with both a choice operationa  orElse  and  callCC

In response to
http://www.haskell.org/pipermail/haskell-cafe/2010-June/079029.html
--}
{-# LANGUAGE GADTs, RankNTypes, TypeSynonymInstances, FlexibleInstances #-}
import Control.Monad.Identity
import Control.Monad

import Control.Monad.Operational

{-
Language definition
--}
-- primitive instructions
data Instruction r a where
CallCC :: ((forall b. a - M r b) - M r a) - Instruction r a
Jump   :: M r r - Instruction r a
OrElse :: M r a - M r a - Instruction r a
MZero  :: Instruction r a

jump   = singleton . Jump -- not exported, needed to implement  callCC
callCC = singleton . CallCC
orElse m n = singleton (OrElse m n)

instance MonadPlus (ProgramT (Instruction r) Identity) where
mzero = singleton MZero
mplus = undefined -- ignore

-- main type
type M r a = Program (Instruction r) a

-- examples
example1, example2 :: M Int Int
example1 = ((callCC (\k - k 0)  mzero) `orElse` return 2) = return . (+3)
example2 = (mzero `orElse` return 2) = return . (+3)

{-
Interpreter
--}
-- global interpreter
interpret :: M r r - Maybe r
interpret m = case (eval return . view) m of
JumpR mr  - interpret mr
ReturnR a - Just a
MZeroR- Nothing

-- helper type for the interpreter
data Result r a where
ReturnR :: a - Result r a
MZeroR  :: Result r a
JumpR   :: M r r - Result r a

-- local interpreter
-- Passes around the current continuation  kk  so that we can 
-- implement  callCC , but never continues evaluation with  kk
eval :: (a - M r r) - ProgramView (Instruction r) a - Result r a
eval kk (Return a)  = ReturnR a
eval kk (CallCC f   := k) = (eval kk . view) $ f (jump . kk') = k
where kk' = k = kk
eval kk (OrElse n m := k) = case (eval kk' . view) n of
ReturnR a - (eval kk . view) (k a)
JumpR  mr - JumpR mr
MZeroR- (eval kk . view) (m = k)
where kk' = k = kk
eval kk (MZero  := k) = MZeroR
eval kk (Jump mr:= k) = JumpR mr


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


[Haskell-cafe] Re: Different choice operations in a continuation monad

2010-06-18 Thread Heinrich Apfelmus
Sebastian Fischer wrote:
 Edward Kmett wrote:
 Sebastian Fischer wrote:
 Heinrich Apfelmus wrote:
 newtype CMaybe a = CMaybe (forall r. (a - Maybe r) - Maybe r)
 Yes, with this type `orElse` has the same type as `mplus`, which is
 very nice.

 This type is the same as Codensity Maybe using category-extras which
 is a 'bit bigger than Maybe'. (To see why, figure out how Codensity
 Reader is isomorphic to State!) This is the wiggle room you're using
 to get the distributive operator.
 
 I encounter the Codensity type constructor every now and then. I used it
 to Reinvent Haskell Backtracking, learned about implementing a state
 monad with a reader monad wrapped in Codensity when implementing  Lazy
 Nondeterministic Programming and Janis Voigtländer also used it to
 improve the asymptotics of free monads.
 
 I wonder whether for every monad `m` and `a :: Codensity m a`
 
 getCodensity a f  =  getCodensity a return = f
 
 Is this true? Why (not)?

It's not true.

  a = Codensity $ \x - Just 42
  f = return . (+1)

getCodensity a f= Just 42
  ≠ getCodensity a return = f = Just 42 = f = Just 43

It probably is true if  a  is only built from  = , return  and actions
from the original monad, though.


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Different choice operations in a continuation monad

2010-06-18 Thread Heinrich Apfelmus
David Menendez wrote:
 Heinrich Apfelmus wrote:
 Sebastian Fischer wrote:

 I wonder whether for every monad `m` and `a :: Codensity m a`

 getCodensity a f  =  getCodensity a return = f

 Is this true? Why (not)?

 It's not true.

  a = Codensity $ \x - Just 42
  f = return . (+1)

getCodensity a f= Just 42
  ≠ getCodensity a return = f = Just 42 = f = Just 43
 
 What definition are you using for Codensity? Under the definition I'm
 familiar with, that definition of a is invalid.

Oops, silly me! I was thinking of

   Codensity r a = Codensity ((a - m r) - m r)

which is wrong, of course.

 newtype Codensity m a = Codensity { runCodensity :: forall b. (a - m
 b) - m b }
 
 Which is not to say that you can't come up with improper values of
 Codensity. E.g.,
 
Codensity (\k - k ()  k ())
 
\m - Codensity (\k - k () = \b - m  return b)

An example that is not generic in the base monad  m , i.e. that makes
use of  m = Maybe  is

a = Codensity $ \k - k 0 `orElse` k 1  -- orElse  on plain  Maybe
  f n = if even n then Nothing else Just n

  runCodensity a f= Just 1
  runCodensity a return = f = Just 0 = f = Nothing


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Different choice operations in a continuation monad

2010-06-19 Thread Heinrich Apfelmus
Sebastian Fischer wrote:
 
 Consider the given Definitions of `CMaybe r a` with
 `fromCMaybe`, `mzero`, `mplus`, `orElse`, and additionally:
 
 toCMaybe :: Maybe a - CMaybe r a
 toCMaybe a = CMaybe (\k - a = k)
 
 getCMaybe :: CMaybe r a - (a - Maybe r) - Maybe r
 getCMaybe (CMaybe a) = a
 
 Much to my surprise, your example lead me to the following inequations:
 
 a  /=  toCMaybe (fromCMaybe a)
 
 because for ``a = return False `mplus` return True``  we have
 
 getCMaybe a guard  =  Just ()
 getCMaybe (toCMaybe (fromCMaybe a)) guard  =  Nothing
 
 Also:
 
 a  /=  mzero `orElse` a
 
 because for the same `a` we have
 
  getCMaybe a guard  =  Just ()
 getCMaybe (mzero `orElse` a) guard  =  Nothing
 
 Also:
 
 a  /=  a `orElse` mzero
 
 because for the same `a` we have
 
  getCMaybe a guard  =  Just ()
 getCMaybe (a `orElse` mzero) guard  =  Nothing
 
 Pretty unfortunate. `mzero` is neither a left nor a right identity of
 `orElse`.

The reason is that in this implementation,  orElse  evaluates  mplus
too early

x `orElse` (return False `mplus` return True)
  = x `orElse` return False

and does not keep track of the fact that  mplus  does not decide for an
alternative until the very end.

 Is `mzero` an identity for `orElse` in your code or can we create a
 counter example like the one above? Can you add a distributive `mplus`
 to your code that would behave differently in the examples above?

In my code,  mzero  is indeed an identity for  orElse  as can be seen
from the definition of the case

   eval kk (OrElse n m := k) = case (eval kk' . view) n of
  ...   - ...
  MZeroR- (eval kk . view) (m = k)

where  n  evaluates to  MZeroR .


It shouldn't be difficult to add a distributive  mplus ; it's definitely
straightforward if we drop  callCC . The observation is any action can
be brought into one of the forms

   mzero
   return a `mplus` return b `mplus` ...

which corresponds to the list type  [a] . This, in turn, can be used to
define  orElse  via pattern matching on the first argument.

   a `orElse` b = case a of { mzero - b ; _ - a }

With the standard type definitions, the interpreter reads

   interpret :: Program Language a - Maybe a
   interpret = listToMaybe . eval . view

   -- evaluate to a normal form
   eval :: ProgramView Language a - [a]
   eval (Return a   := k) = [a]
   eval (MZero  := k) = []
   eval (MPlus n m  := k) = (eval . view) (n = k)
   ++ (eval . view) (m = k)
   eval (OrElse n m := k) = case (eval . view) n of
   [] - (eval . view) (m = k)
   xs - concatMap (eval . view . k) xs


The call pattern of this interpreter shows that you can implement your
type as

   newtype CMaybe a = CMaybe { forall b . (a - [b]) - [b] }

but, as I said, this type is not good way of thinking about it in my
opinion.


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Continuations and coroutines

2010-06-22 Thread Heinrich Apfelmus

Paul Johnson wrote:

Yves Parès wrote:
It helps me understand better, but would you have some simple code 
that would do that ?


http://www.cs.chalmers.se/~koen/pubs/jfp99-monad.ps


You can also understand coroutines and continuations in terms of 
operational semantics. Here is a reimplementation of Koen Claessen's 
poor man's concurrency monad based on this approach:


  PoorMansConcurrency.hs
  http://projects.haskell.org/operational/examples.html


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Different choice operations in a continuation monad

2010-06-22 Thread Heinrich Apfelmus

Sebastian Fischer wrote:

Heinrich Apfelmus wrote:


[...] you can implement your type as

  newtype CMaybe a = CMaybe { forall b . (a - [b]) - [b] }


Yes. For me it was interesting to see how far we get by wrapping `Maybe` 
in `Codensity`: we get more than `Maybe` but not as much as `[]`.


Well, you can implement it with  Maybe  as well, at the price of 
duplicated computations. The idea is that for the implementation of 
orElse , we're not interested in the full list of results, only in 
whether this list is empty or not. This leads to


   eval :: ProgramView Language a - Maybe a
   eval (Return a   := k) = Just a
   eval (MZero  := k) = Nothing
   eval (MPlus n m  := k) = (eval . view) (n = k)
  `mplus` (eval . view) (m = k)
   eval (OrElse n m := k) = case (eval . view) n of
   Nothing - (eval . view) (m = k)
   Just _  - (eval . view) (n = k)

Thanks to lazy evaluation, this is not too inefficient, even.


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: When the unknown is unknown

2010-06-24 Thread Heinrich Apfelmus

Martin Drautzburg wrote:
From which angle would you approach problems like this? Should I get my hands 
on a prolog-in-haskel implementation (which indeed seems to exist)? Or should 
I roll my own poor-man's prolog? Or is this a 
constraint-satisfaction-problem? Or is there even a more straight-forward 
more haskellish pattern, which solves such problems?


I don't think that a general Prolog implementation is the right 
approach, but if you do need one, have a look at the demonstration 
projects for the Hugs interpreter:


   http://darcs.haskell.org/hugs98/demos/prolog/


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Finding zipper for custom tree

2010-07-02 Thread Heinrich Apfelmus

Luke Palmer wrote:

I would just use List.  IIRC the derivative of list is:

data DList a = DLIst [a] [a]

Understood as the elements before the focused one and those after it.
Unfortunately I can't remember how that is derived, and my own
experiments failed to come up with anything similar.  That may
indicate that the rest of this message is nonsense.


Note that there is a really subtle difference between derivative and 
zipper which is probably the source of confusion. For lists, both are 
the same, though.


The derivative of the list type with respect to the element type is

  d List   = d (\a - 1 + a * List a)
   = \a - List a + a * d List a
  d List a = List a + a * d List a
  d List a ~ List a * List a

The very last isomorphism of types is not trivial and probably the 
reason why you were stumped.



data DTree a = P | D [(a, DTree a)]

Can be written algebraically as:

DTree a = 1 + List (a * DTree a)
DTree a = Mu f. 1 + List (a * f)

Differentiating:

DDTree a = Mu f. DList (a * f) * a
DDTree a = DList (a * DTree a) * a


The difference between zipper and derivative shows up here. Namely, your 
second equation for  DDTree a  does not follow from the first, it should be


   DDTree a = DList (a * DDTree a) * a
 ^^ two Ds


To understand this intuitively, DDTree a is the context in which a
DTree can appear within itself. 


The context in which  DDTree a  can appear within itself is indeed the 
zipper. But this is different from the derivative with respect to  a , 
which gives the context in which  a  can appear within  DDTree a .


To get the zipper, you have to derive the pattern functor with the 
respect to the variable that will tie the recursion, in this case  f .


  d (DTreeF a) = d (\f - 1 + List (a * f))
   = 0 + (d (\g - List g) (a * f)) * d (\f - a * f)
   = d List (a * f) * a

 So that is:  The (a * DTree a)s that
 appeared before and after the current list element, together with the
 a that was paired with the current element.

Then, the zipper is a *list* of these things:

  ContextDTree a = List (DList (a * DTree a) * a)

After all, what you describe is only the context of  DTree a  within a 
single level, but it might be many levels down in the tree.



Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Finding zipper for custom tree

2010-07-02 Thread Heinrich Apfelmus

Sergey Mironov wrote:

Hello list!
I am trying to understand zipper concept using papers like [1] and [2].
Though main idea looks clear, I still have a problem in applying it for
custom data types.

Please help me with deriving Zipper-type from


data DTree a = P | D [(a, DTree)]


Looking in [1] ('Zippers via Differentiation' chapter) I tried to do
the following:

1. Find a DTreeF type which is a pattern functor ([2], chapter 2.1) of my DTree
2. Write DTreeF in 'algebraic' form (using '+' and '*')
3. Find DTreeF' - derivative of DTreeF
4. Define my zipper type using list of DTreeF'


These are the right steps.


Step 1 likely ends with


data DTreeF a x = P | D [(a,x)]


[2] says that using this pattern functor one could build a fixed-point
version of DTree:


data Fix f = In {out :: (f (Fix f))}
data DTreeFP = Fix DTreeF


but seems that I have nothing to do with it right now.


The fixed point is just another way to write  DTree .

DTreeFP a = DTree a


Step 2 is my main question:

In [1] authors did it for binary tree:

data Tree a = Leaf a | Bin (Tree a) (Tree a)

data TreeF a x = Leaf a | Bin x x

and thus

TreeF = a + x * x

TreeF' = x + x

My DTree has inner list of tuples. How should I rewrite it in terms of
'+' and '*' ?


Ah, you can't write it in terms of only '+' and '*' because you also 
have the list type in there:


DTreeF = 1 + List (a * x)
 ^^ List involves a fixed point

So, to find the derivate, you have to calculate the derivative of  List 
 first:


List' x = List x * List x

and then you can use the chain rule to find  DTreeF .


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: finding the right mathematical model

2010-07-07 Thread Heinrich Apfelmus

Günther Schmidt wrote:

Hi list,

the problem I have stems from the app I had developed. What my app does 
is to split the money a hospital receives for a case to the departments 
involved in a fair way.


An additional requirement however was to allow the users of the app to 
re-map any revenue shares credited to certain departments to other 
departments. Such cases are sometimes due to politics within the 
hospital and also have more legitimate reasons, like saying the 
radiology should not receive shares for surgical procedures but those 
shares should be redirected to the General surgery department.


The feature is already implemented, but I'm not pleased with it, 
especially since I did not develop a mathematical model for it.


Details:

It boils down to model mappings, or rather what sort of data structure 
would be suited for this kind of thing.


Dept A is mapped to itself
A - A

Dept B is mapped to Dept C
B - C

Dept C is mapped to Dept C
C - C

Dept D is mapped to Dept A
D - A

It should not be possible to construct looping mappings, ie.

  1. A - B
  2. B - C
  3. C - A

...


What sort of model would be suitable to describe this, some sort of matrix?


You probably want a graph where the nodes represent departments and 
edges represent the mappings. To implement graphs in Haskell, have a 
look at the functional graph library


  http://hackage.haskell.org/package/fgl

If that's too complicated for you and your graphs are really small, you 
can also use a toy implementation like


  type Graph = [(Node,   -- Department
[Node])  -- List of Departments it shares revenue to
   ]

To test whether a graph has cycles (looping mapping), you can use a 
depth-first search.



Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Memoization in Haskell?

2010-07-09 Thread Heinrich Apfelmus

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


It should be

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

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

Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Memoization in Haskell?

2010-07-10 Thread Heinrich Apfelmus

Gregory Crosswhite wrote:

Heinrich Apfelmus wrote:

Gregory Crosswhite wrote:

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


It should be

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

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


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


Oops, silly me! I erroneously thought that the code was using  f 
instead  of  (memo !) in the definition of the array, like this


  f :: (Integral a, Ord a, Ix a) = a - a
  f n = memo ! n
  where
  memo = array (0,n) $ (0,0) :
 [(i, max i (f (i `quot` 2)
 + f (i `quot` 3) + f (i `quot` 4)))
 | i - [1 .. n]]

But since  memo  depends on  n , it cannot be lifted outside the lambda 
abstraction.



Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com


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


[Haskell-cafe] Re: Equivalence of two expressions

2010-07-12 Thread Heinrich Apfelmus

Grigory Sarnitskiy wrote:

I'm not very familiar with algebra and I have a question.

Imagine we have ring K. We also have two expressions formed by
elements from K and binary operations (+) (*) from K.

Can we decide weather these two expressions are equivalent? If there
is such an algorithm, where can I find something in Haskell about it?

If there is no such algorithm for a ring, maybe there is for a field?


Deciding whether two elements are equal depends a lot on the ring K in 
question. For instance, if K is the ring of polynomials in one variable, 
you have, every element has the normal form


   a_0 + a_1 * x + a_2 * x^2 + .. + a_n * x^n

and you can compare coefficients to decide whether equalities like

   (x-1)(x^2+x+1) = x^3 - 1

hold. For polynomial rings in several variables, things are trickier, 
but there is Buchberger's algorithm that can be used to solve such problems.



As Michael already mentioned, the problem is undecidable in general 
since it includes group rings.



Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: lambda calculus and equational logic

2010-07-15 Thread Heinrich Apfelmus

Patrick Browne wrote:

In Haskell what roles are played by 1)lambda calculus and 2) equational
logic? Are these roles related?


Thanks for your clear and helpful responses.
I am aware that this question can lead to into very deep water.
I am comparing Haskell with languages based on equational logic (EL)
(e.g. Maude/CafeOBJ, lets call them ELLs).  I need to identify the
fundamental distinction between the semantics of ELLs and Haskell. The
focus of my original question was just the purely functional, side
effect free, part of Haskell.

Semantics can be understood under three headings:
*Denotational Semantics; is a model theoretical approach which describes
a program in terms of precise mathematical objects (e.g. sets and
functions) which provide meaning to a program text.
*Operational semantics: provides a technique for computing a result, ELs
use term rewriting systems for their operational semantics.
*Proof  theoretic semantic:  syntactically derivable proofs, can use the
rules of a logic

The relationship between the denotational and the proof theoretic
semantic is important for soundness and completeness. Which was sort of
 behind my original question.


Would it be fair to say
1)Lambda calculus provides the operational semantics for Haskell

2)Maybe equational logic provides the denotational semantics.

3)I am not sure of proof theoretic semantic for Haskell.
  The Curry-Howard correspondence is a proof theoretic view but only at
  type level.

Obviously, the last three points are represent my efforts to address
this question. Hopefully the café can comment on the accuracy of these
points.


Lambda calculus is the basis for all three types of semantics:

1) Call-by-need (usually, implementations of Haskell are free to choose 
other evaluation strategies as long as the denotational semantics match)


2) The denotational semantics of a lambda calculus with general 
recursion, see also


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

3) Not sure what you mean by proof theoretic semantics. Apparently, the 
trace of any program execution like, say


   product [1..5] - 1 * product [2..5] - .. - 120

is a proof that the initial and the final expression denote the same value.

The Curry-Howards correspondence is about the type system, viewing types 
as logical propositions and programs as their proofs.




Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Finding zipper for custom tree

2010-07-16 Thread Heinrich Apfelmus

Sergey Mironov wrote:


Sorry for late answer. Luke, Heinrich - thank you very much for explanations.
I feel that I need more reading to get familiar with differentiation
of functors and chain rule. Could you suggest some books or papers?


For differentiation of data types, there is for example

  Conor McBride
  The Derivative of a Regular Type is its Type of One-Hole Contexts.
  http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.22.8611

but I'm not sure whether it's easier to understand than the wikibook.

For more on using functors to model algebraic data types, see also

  R Backhouse, P Jansson, J Jeuring, L Meertens
  Generic Programming - An Introduction -
  http://www.cse.chalmers.se/~patrikj/poly/afp98/

A corresponding chapter in the wikibook (Datatype algebra) has not 
been written, so far.



Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Designing a DSL?

2009-10-03 Thread Heinrich Apfelmus
Günther Schmidt wrote:
 there are numerous examples on how to implement a DSL, but I haven't
 been able to figure out how to design one.
 
 I mean I have a pretty good idea of the problem domain, I've coded it
 over and over again until I got it right. Now I'd like to express that
 part as a DSL instead of hard coding it as before so I can be more
 prepared if I need to change or amend it. Ideally I'd only have to
 change the interpreter, right?
 
 And that I find to be the really tricky part, how do I *design* a DSL?

Since every well-designed DSL is, by definition, a unique experience,
it's hard to answer that question in general. I think that designing
DSLs in Haskell is best learned from the following classic papers

  John Hughes. The Design of a Pretty-printing Library.
  http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.38.8777

  Philip Wadler. A prettier printer.
  http://homepages.inf.ed.ac.uk/wadler/topics/
language-design.html#prettier

  Richard Bird. A program to solve Sudoku
  Slides: http://icfp06.cs.uchicago.edu/bird-talk.pdf
  Paper: http://cs.tufts.decenturl.com/richard-bird-sudoku

  Simon Peyton Jones, Jean-Marc Eber, Julian Seward.
  Composing contracts: an adventure in financial engineering.
  http://research.microsoft.decenturl.com/composing-contracts

and Hudak's book

  Paul Hudak. The Haskell School of Expression.
  http://www.haskell.org/soe/


The main principle is probably best summarized as: think long and hard
to make it as simple and beautiful as possible.


Regards,
apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Generalizing IO

2009-10-07 Thread Heinrich Apfelmus
David Menendez wrote:
 Floptical Logic wrote:
 The code below is a little interactive program that uses some state.
 It uses StateT with IO to keep state.  My question is: what is the
 best way to generalize this program to work with any IO-like
 monad/medium?  For example, I would like the program to function as it
 does now using stdin but I would also like it to function over IRC
 using the Net monad from
 http://haskell.org/haskellwiki/Roll_your_own_IRC_bot.  Thanks for
 any suggestions.
 
 Instead of specifying the monad implementation, specify the interface.
 That is, you are using state operations (from MonadState) and IO
 operations (from MonadIO). Try removing all the type signatures that
 mention PDState and see what you get.
 
 E.g., loop :: (MonadState PD m, MonadIO m) = m a

Alternatively, you can use algebraic data types instead of type classes
to generalize one program to different implementations. For monads, this
can be achieved with

 http://hackage.haskell.org/package/MonadPrompt

In particular, the idea is to turn every effect like

  getLine

into a constructor

  GetLine

and have different implementations pattern match on that.


Regards,
apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Re: Any example of concurrent haskell application?

2009-10-09 Thread Heinrich Apfelmus
Daryoush Mehrtash wrote:
 I am trying to learn more about concurrent applications in Haskell by
 studying an existing a real application source code.   I would very much
 appreciate if you can recommend an application that you feel has done a good
 job in implementing a real time application in Haskell.

It doesn't really use much concurrency, but the web server
implementation detailed in

  Simon Marlow.
  Writing High-Performance Server Applications in Haskell
Case Study: A Haskell Web Server
  http://www.haskell.org/~simonmar/papers/web-server.ps.gz

is a simple and well documented example.


Regards,
apfelmus

--
http://apfelmus.nfshost.com

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


<    1   2   3   4   5   6   7   8   9   >