Re: [Haskell-cafe] lazy A-star search

2011-10-31 Thread Eugene Kirpichov
Anton, I think the mapM inside searchBy is incorrect. You're threading state 
between exploration of different branches, which you I think shouldn't be doing.



30.10.2011, в 19:44, Anton Kholomiov anton.kholom...@gmail.com написал(а):

 I'm misunderstanding astar. I've thought that 'whole route'-heuristic 
 will prevent algorithm from going in circles. The more you circle around
 the more the whole route distance is. Thank you for showing this. 
 Here is an updated version. searchBy function contains a state.
 State value accumulates visited nodes:
 
 -- | Heuristic search. Nodes are visited from smaller to greater.
 searchBy :: Ord b = (a - b) - (a - a - Ordering) - Tree a - [a]
 searchBy f heur t = evalState (searchBy' f heur t) S.empty
 
 searchBy' :: Ord b 
 = (a - b) - (a - a - Ordering) - Tree a - State (S.Set b) [a]
 searchBy' f heur (Node v ts) = get = phi
 where phi visited
 | S.member (f v) visited = return []
 | otherwise  = 
 put (S.insert (f v) visited) 
 (v :) . foldr (mergeBy heur) [] $ 
 mapM (searchBy' f heur) ts
 
 I need to add function Ord b = (a - b). It
 converts tree nodes into visited nodes. I'm using it 
 for saving distance-values alongside with nodes
 in astar algorithm.
 
 In attachment you can find algorithm with your example. 
 
 2011/10/27 Ryan Ingram ryani.s...@gmail.com
 Also, this wasn't clear in my message, but the edges in the graph only go one 
 way; towards the top/right; otherwise the best path is ABCDEHIJ :)
 
 
 On Thu, Oct 27, 2011 at 10:48 AM, Ryan Ingram ryani.s...@gmail.com wrote:
 You're missing one of the key insights from A-star (and simple djikstra, for 
 that matter): once you visit a node, you don't have to visit it again.
 
 Consider a 5x2 2d graph with these edge costs:
 
 B 1 C 1 D 1 E 9 J
 1   1   1   1   1
 A 2 F 2 G 2 H 2 I
 
 with the start node being A, the target node being J, and the heuristic being 
 manhattan distance.  Your search will always try to take the top route, on 
 every node along the bottom path, even though you visit every node along the 
 top route in your first try at reaching the goal.  You need a way to mark 
 that a node is visited and remove it from future consideration, or else 
 you're wasting work.
 
 A-star will visit the nodes in the order ABCDE FGHIJ; your algorithm visits 
 the nodes in the order ABCDE FCDE GDE HE IJ.
 
   -- ryan
 
 On Sat, Oct 22, 2011 at 5:28 AM, Anton Kholomiov anton.kholom...@gmail.com 
 wrote:
 Recently I was looking for an A-star search algorithm. I've found a package 
 but I couldn't understand the code. Then I saw some blogposts but they
  were difficult to understand too. I thought about some easier solution that
 relies on laziness. And I've come to this:
 
 Heuristic search is like depth-first search but solutions in sub-trees 
 are concatenated with mergeBy function, that concatenates two 
 list by specific order:
 
 module Search where
 
 import Control.Applicative
 import Data.Function(on)
 import Control.Arrow(second)
 import Data.Tree
 
 -- | Heuristic search. Nodes are visited from smaller to greater.
 searchBy :: (a - a - Ordering) - Tree a - [a]
 searchBy  heur (Node v ts) = 
 v : foldr (mergeBy heur) [] (searchBy heur $ ts)
 
 -- | Merge two lists. Elements concatenated in specified order.
 mergeBy :: (a - a - Ordering) - [a] - [a] - [a]
 mergeBy _ a []  = a
 mergeBy _ []b   = b
 mergeBy p (a:as)(b:bs)  
 | a `p` b == LT= a : mergeBy p as (b:bs)
 | otherwise = b : mergeBy p bs (a:as)
 
 
 Now we can define specific heuristic search in terms of searchBy:
 
 -- | Heuristic is distance to goal.
 bestFirst :: Ord h = (a - h) - (a - [a]) - a - [a]
 bestFirst dist alts = 
 searchBy (compare `on` dist) . unfoldTree (\a - (a, alts a))
 
 -- | A-star search.
 -- Heuristic is estimated length of whole path. 
 astar :: (Ord h, Num h) = (a - h) - (a - [(a, h)]) - a - [a]
 astar dist alts s0 = fmap fst $ 
 searchBy (compare `on` astarDist) $ unfoldTree gen (s0, 0)
 where astarDist (a, d) = dist a + d
   gen (a, d)  = d `seq` ((a, d), second (+d) $ alts a)
 
 I'm wondering is it effective enough?
 
 
 Anton
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 
 
 
 Search.hs
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Hackage feature request: E-mail author when a package breaks

2011-10-31 Thread Gregory Crosswhite
Hey everyone,

I have uploaded a number of small packages to Hackage that I no longer actively 
use so that I don't find out immediately when a new version of GHC has broken 
them.  Since Hackage is going to the trouble of finding out when a package no 
longer builds anyway, could it have a feature where when a working package 
breaks with a new version of GHC the author is automatically e-mailed?  This 
would make me (and probably others) a lot more likely to notice and proactively 
fix broken packages.  (Heck, I wouldn't even necessarily mind being nagged 
about it from time to time.  :-) )

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


[Haskell-cafe] blog software in Haskell?

2011-10-31 Thread Ketil Malde

Hi,

I just upgraded my server, and set up everything again.  Except
wordpress, as 1) I'm not too fond of its user interface, and 2) it's a
big pile of PHP, difficult to keep updated, and basically a disaster
waiting to happen (and in fact, it was hacked at one point).

Before I enable it again, is there any alternatives I should consider?
Preferably written in Haskell, of course, but other suggestions welcome
as well.

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants

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


Re: [Haskell-cafe] blog software in Haskell?

2011-10-31 Thread Mihai Maruseac
On Mon, Oct 31, 2011 at 11:14 AM, Ketil Malde ke...@malde.org wrote:

 Hi,

 I just upgraded my server, and set up everything again.  Except
 wordpress, as 1) I'm not too fond of its user interface, and 2) it's a
 big pile of PHP, difficult to keep updated, and basically a disaster
 waiting to happen (and in fact, it was hacked at one point).

 Before I enable it again, is there any alternatives I should consider?
 Preferably written in Haskell, of course, but other suggestions welcome
 as well.


Hi,

Have a look at Hakyll[1]

[1]: http://jaspervdj.be/hakyll/

Mihai

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


[Haskell-cafe] Amazon AWS storage best to use with Haskell?

2011-10-31 Thread dokondr
Hi,
Please share your experience / ideas on AWS storage most friendly to
Haskell.
So far I store my data mostly in Data.Map structures serialized to text
files with write / read functions. Now I was requested to move my app and
data to Amazon cloud. As far as I know there are two main storage types
that Amazon provides: S3 - basic block storage and SimpleDB (
http://docs.amazonwebservices.com/AmazonSimpleDB/latest/GettingStartedGuide/
)
Questions:
1) I would like to continue working with my data using abstractions similar
to the ones that Data.Map provides. Any ideas how to iterate and modify
SimpleDB records in a similar powerful way as provided by Data.Map? Or
maybe S3?
2) It would be great to do development and testing offline without actually
connecting to AWS S3 / SimpleDB. Are there any AWS simulators + Haskell
libraries that  will allow to do such an offline development?
3) Any experience / ideas  with Haskell libs for NoSQL, not AWS-native,
storages, that will run well both offline and in AWS?
4) My code processes hundreds of messages. Every message is processed in
exactly the same way as the others. So the code can be easily parallelized.
Any Haskell frameworks that will allow me to run this code in a simple
concurrency model?

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


Re: [Haskell-cafe] Organizing big repository

2011-10-31 Thread Alberto G. Corona
This is not evident in hte documentation,  but Leksah does  these things
for you if you add your packages to the workspace list..

It is necessary to use the background compilation option, that is, set by
default.

Alberto


2011/10/27 Konstantin Litvinenko to.darkan...@gmail.com

 I am trying to understand how to organize my code and edit-compile-run
 cycles. I can't figure out how to setup environment in such why that when I
 build some program using cabal, cabal will rebuild program dependencies if
 some was changed. I don't want to configure/build/install manually.
 Having program 'foo' depends on lib 'bar' I want to edit some files in
 'bar' than build 'foo' and get 'bar' rebuilt and 'foo' rebuilt/relink.
 How can I do this?


 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe

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


[Haskell-cafe] Fwd: Organizing big repository

2011-10-31 Thread Alberto G. Corona
This is not evident in hte documentation,  but Leksah does  these things
for you if you add your packages to the workspace list..

It is necessary to use the background compilation option, that is, set by
default.

Alberto


2011/10/27 Konstantin Litvinenko to.darkan...@gmail.com

 I am trying to understand how to organize my code and edit-compile-run
 cycles. I can't figure out how to setup environment in such why that when I
 build some program using cabal, cabal will rebuild program dependencies if
 some was changed. I don't want to configure/build/install manually.
 Having program 'foo' depends on lib 'bar' I want to edit some files in
 'bar' than build 'foo' and get 'bar' rebuilt and 'foo' rebuilt/relink.
 How can I do this?


 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] is Haskell missing a non-instantiating polymorphic case?

2011-10-31 Thread Max Bolingbroke
On 23 October 2011 06:48, Adam Megacz meg...@cs.berkeley.edu wrote:
 The title might be a bit more provocative than necessary.

 I'm starting to suspect that there are very useful aspects of the
 parametricity of System F(C) which can't be taken advantage of by Haskell in
 its current state.  To put it briefly, case-matching on a value of type
 (forall n . T n) forces one to instantiate the n, even though the branch
 taken within the case cannot depend on n (parametricity).

I wonder if you can write eta-expansion for a product type containing
an existential given your extension? If I have:

data Id a = Id a

I can currently write:

eta x = Id (case x of Id x - x)

And I have that eta x != _|_ for all x. But if I have:

data Exists = forall a. Exists a

Then I can't write the equivalent eta-expansion:

eta x = Exists (case x of Exists x - x)

The closest I can get is:

eta x = Exists (case x of Exists x - unsafeCoerce x :: ())

I'm not sure if you can do this with your extension but it smells plausible.

Max

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


Re: [Haskell-cafe] How to implement digital filters using Arrows

2011-10-31 Thread Captain Freako
Hi John,

Thanks for all your help.
I've been studying your suggested code:

 type FilterAu b c = Automaton (-) b c

  liftAu :: ((x,FilterState s)-(y,FilterState s)) - FilterState s -
FilterAu x y
  liftAu f s0 = proc x - do
 rec (y,s') - arr f - (x,s)
 s - delay s0 - s'
 returnA - y


runAutomaton is a bit cumbersome, so define a custom run function that
takes a list

  runAuto a [] = []
  runAuto (Automaton f) (x:xs) = let
(y,a) = f xt
in y:runAuto a xs

as well as the various instance definitions for Automaton.

I think I understand how the `returnA' in the last line of your
`liftAu' function is getting translated by those instance definitions
into:

c where
c = Automaton ( arr id  arr (const c) )

and, furthermore, how that is passing the supplied `y' into the first
element of the resulting couple. However, I don't understand how the
recursively defined `c' is capturing the modified filter state and
preserving it for the next call. It seems like the Automaton being
referred to by `c' is a newly constructed entity, which knows nothing
about the current state of the running Automaton.

Any help in understanding this would be greatly appreciated.

Thanks!
-db

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


Re: [Haskell-cafe] lazy A-star search

2011-10-31 Thread Anton Kholomiov
The last implementation is type-driven, so I'm trying
to understand it myself now in the light of your remark. Do you mean that
the problem
is this: to mergeBy things together I need to add the nodes to the set of
visited
nodes first? So I'm adding nodes to visited set before I've chosen the best
node.


31 октября 2011 г. 9:05 пользователь Eugene Kirpichov
ekirpic...@gmail.comнаписал:

 Anton, I think the mapM inside searchBy is incorrect. You're threading
 state between exploration of different branches, which you I think
 shouldn't be doing.



 30.10.2011, в 19:44, Anton Kholomiov anton.kholom...@gmail.com
 написал(а):

 I'm misunderstanding astar. I've thought that 'whole route'-heuristic
 will prevent algorithm from going in circles. The more you circle around
 the more the whole route distance is. Thank you for showing this.
 Here is an updated version. searchBy function contains a state.
 State value accumulates visited nodes:

 -- | Heuristic search. Nodes are visited from smaller to greater.
 searchBy :: Ord b = (a - b) - (a - a - Ordering) - Tree a - [a]
 searchBy f heur t = evalState (searchBy' f heur t) S.empty

 searchBy' :: Ord b
 = (a - b) - (a - a - Ordering) - Tree a - State (S.Set b) [a]
 searchBy' f heur (Node v ts) = get = phi
 where phi visited
 | S.member (f v) visited = return []
 | otherwise  =
 put (S.insert (f v) visited) 
 (v :) . foldr (mergeBy heur) [] $
 mapM (searchBy' f heur) ts

 I need to add function Ord b = (a - b). It
 converts tree nodes into visited nodes. I'm using it
 for saving distance-values alongside with nodes
 in astar algorithm.

 In attachment you can find algorithm with your example.

 2011/10/27 Ryan Ingram ryani.s...@gmail.com

 Also, this wasn't clear in my message, but the edges in the graph only go
 one way; towards the top/right; otherwise the best path is ABCDEHIJ :)


 On Thu, Oct 27, 2011 at 10:48 AM, Ryan Ingram ryani.s...@gmail.comwrote:

 You're missing one of the key insights from A-star (and simple djikstra,
 for that matter): once you visit a node, you don't have to visit it again.

 Consider a 5x2 2d graph with these edge costs:

 B 1 C 1 D 1 E 9 J
 1   1   1   1   1
 A 2 F 2 G 2 H 2 I

 with the start node being A, the target node being J, and the heuristic
 being manhattan distance.  Your search will always try to take the top
 route, on every node along the bottom path, even though you visit every
 node along the top route in your first try at reaching the goal.  You need
 a way to mark that a node is visited and remove it from future
 consideration, or else you're wasting work.

 A-star will visit the nodes in the order ABCDE FGHIJ; your algorithm
 visits the nodes in the order ABCDE FCDE GDE HE IJ.

   -- ryan

 On Sat, Oct 22, 2011 at 5:28 AM, Anton Kholomiov 
 anton.kholom...@gmail.com wrote:

 Recently I was looking for an A-star search algorithm. I've found a
 package
 but I couldn't understand the code. Then I saw some blogposts but they
  were difficult to understand too. I thought about some easier solution
 that
 relies on laziness. And I've come to this:

 Heuristic search is like depth-first search but solutions in sub-trees
 are concatenated with mergeBy function, that concatenates two
 list by specific order:

 module Search where

 import Control.Applicative
 import Data.Function(on)
 import Control.Arrow(second)
 import Data.Tree

 -- | Heuristic search. Nodes are visited from smaller to greater.
 searchBy :: (a - a - Ordering) - Tree a - [a]
 searchBy  heur (Node v ts) =
 v : foldr (mergeBy heur) [] (searchBy heur $ ts)

 -- | Merge two lists. Elements concatenated in specified order.
 mergeBy :: (a - a - Ordering) - [a] - [a] - [a]
 mergeBy _ a []  = a
 mergeBy _ []b   = b
 mergeBy p (a:as)(b:bs)
 | a `p` b == LT= a : mergeBy p as (b:bs)
 | otherwise = b : mergeBy p bs (a:as)


 Now we can define specific heuristic search in terms of searchBy:

 -- | Heuristic is distance to goal.
 bestFirst :: Ord h = (a - h) - (a - [a]) - a - [a]
 bestFirst dist alts =
 searchBy (compare `on` dist) . unfoldTree (\a - (a, alts a))

 -- | A-star search.
 -- Heuristic is estimated length of whole path.
 astar :: (Ord h, Num h) = (a - h) - (a - [(a, h)]) - a - [a]
 astar dist alts s0 = fmap fst $
 searchBy (compare `on` astarDist) $ unfoldTree gen (s0, 0)
 where astarDist (a, d) = dist a + d
   gen (a, d)  = d `seq` ((a, d), second (+d) $ alts a)

 I'm wondering is it effective enough?


 Anton

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




 Search.hs

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


___
Haskell-Cafe 

Re: [Haskell-cafe] Hackage feature request: E-mail author when a package breaks

2011-10-31 Thread Johan Tibell
On Mon, Oct 31, 2011 at 12:08 AM, Gregory Crosswhite
gcrosswh...@gmail.comwrote:

 I have uploaded a number of small packages to Hackage that I no longer
 actively use so that I don't find out immediately when a new version of GHC
 has broken them.  Since Hackage is going to the trouble of finding out when
 a package no longer builds anyway, could it have a feature where when a
 working package breaks with a new version of GHC the author is
 automatically e-mailed?  This would make me (and probably others) a lot
 more likely to notice and proactively fix broken packages.  (Heck, I
 wouldn't even necessarily mind being nagged about it from time to time.
  :-) )


If done well I think this is a good idea. Currently I have my buildbot
email me whenever a package breaks (although the bot doesn't automatically
install new GHCs).

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


[Haskell-cafe] Figures 6 and 7 from `Programming with Arrows'?

2011-10-31 Thread Captain Freako
Does anyone have figures 6 and 7, as well as the intervening
unnumbered figure, from `Programming with Arrows'?

Thanks,
-db

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


Re: [Haskell-cafe] Hackage feature request: E-mail author when a package breaks

2011-10-31 Thread Yitzchak Gale
Gregory Crosswhite wrote:
 could [Hackage] have a feature where when a
 working package breaks with a new version of
 GHC the author is automatically e-mailed?

This would be nice. However, there would have to be
a way for it to be turned on and off by the author.
(Spam is not nice.)

Thanks,
Yitz

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


Re: [Haskell-cafe] Amazon AWS storage best to use with Haskell?

2011-10-31 Thread dokondr
On Mon, Oct 31, 2011 at 6:50 PM, John Lenz l...@math.uic.edu wrote:


 4) My code processes hundreds of messages. Every message is processed in

 exactly the same way as the others. So the code can be easily
 parallelized. Any Haskell frameworks that will allow me to run this code
 in a simple concurrency model?


 Yes, there are many options.

 http://www.haskell.org/**haskellwiki/GHC/Concurrencyhttp://www.haskell.org/haskellwiki/GHC/Concurrency



John, thanks for detailed reply!
I am looking at Haskell Concurrency wiki, but can not figure out which
framework - STM, sparks, threads, etc. Amazon AWS will be able to scale?
As far as I know, to scale CPU and program memory in Amazon, all you can
ask from AWS is to start some number of additional extra VMs. Every VM
contains a complete image of your OS and executables, all images are
exactly the same.
That's fine with me as currently all my workflow tasks are performed by
separately compiled Haskell executables communicating via regular files.
So to reformulate my question:
- Does any Haskell  framework exist that allow to orchestrate separate
processes  (NOT threads that share the same process memory)?
On the other hand, in case there is a way to make Amazon AWS  to scale
Haskell STM, sparks, threads, etc. - I would happily rewrite my Haskell
code to use these frameworks.  So my second question:
- Is there a way to make Amazon AWS  to scale Haskell STM, sparks, threads
or any other Haskell concurrency frameworks?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2011-10-31 Thread Joey Adams
On Wed, Oct 26, 2011 at 4:24 PM, Bas van Dijk v.dijk@gmail.com wrote:
 I have one question regarding your use of atomicModifyIORef:

  x - atomicModifyIORef ref (\_ - (tmstr, ()))
  x `seq` return ()

 Can't you write that as just: writeIORef ref tmstr? If you're not
 using the previous value of the IORef there's no chance of
 inconsistency.

From the documentation at
http://hackage.haskell.org/packages/archive/base/latest/doc/html/Data-IORef.html
:

IORef operations may appear out-of-order to another thread, ...

...

atomicModifyIORef acts as a barrier to reordering. Multiple
atomicModifyIORef operations occur in strict program order.

Based on this description, it seems that atomicModifyIORef is safer
for writing to an IORef than writeIORef when there are multiple
threads reading and writing it.  If my assessment is correct, I think
Data.IORef should have an atomicWriteIORef :: IORef a - a - IO ()
function to clarify this.  I'm not completely sure about this myself.
Could someone confirm this?

Moreover, it'd be nice if there were writeIORef' and
atomicModifyIORef' functions that force the value.  Doing so would
help people avoid making the mistake described by the author.  It's a
really common mistake.

- Joey

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


Re: [Haskell-cafe] blog software in Haskell?

2011-10-31 Thread Alistair Bayley
On 31 October 2011 22:14, Ketil Malde ke...@malde.org wrote:

 I just upgraded my server, and set up everything again.  Except
 wordpress, as 1) I'm not too fond of its user interface, and 2) it's a
 big pile of PHP, difficult to keep updated, and basically a disaster
 waiting to happen (and in fact, it was hacked at one point).

 Before I enable it again, is there any alternatives I should consider?
 Preferably written in Haskell, of course, but other suggestions welcome
 as well.

http://gitit.net/
...has git and darcs storage.

http://www.haskell.org/haskellwiki/Web/Content_Management

There is also orchid:

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/orchid-0.0.6
https://github.com/sebastiaanvisser/orchid
https://github.com/sebastiaanvisser/orchid-doc

which I recall was quite pretty, but I cannot find an online demo.

Alistair

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


Re: [Haskell-cafe] Hackage feature request: E-mail author when a package breaks

2011-10-31 Thread Alexander Kjeldaas
On 31 October 2011 17:22, Yitzchak Gale g...@sefer.org wrote:

 Gregory Crosswhite wrote:
  could [Hackage] have a feature where when a
  working package breaks with a new version of
  GHC the author is automatically e-mailed?

 This would be nice. However, there would have to be
 a way for it to be turned on and off by the author.
 (Spam is not nice.)


How about sending an email to haskell-package-packate-name@haskell.org,
and then people can join that mailing list if they are interested in that
sort of stuff?  Mailman is good at doing subscribe and unsubscribe.

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


Re: [Haskell-cafe] Amazon AWS storage best to use with Haskell?

2011-10-31 Thread dokondr
On Mon, Oct 31, 2011 at 6:50 PM, John Lenz l...@math.uic.edu wrote:

 CouchDB works great, although I decided to go with SimpleDB since then it
 is amazon's problem to scale and allocate disk and so forth, which I like
 better.  For couchdb, you can use my package couchdb-enumerator on hackage.


 Regarding CouchDB. So far I have my records keyed by Id and stored in
Data.Map which I serialize to  text file. Using Data.Map functions I do
many operations with these records including mapping functions over keys
and values, accumulation, lookup, intersection, union etc.
When I move this data to CouchDB and start using couchdb-enumerator to work
with it, how natural will it be to implement all these functions that I use
from Data.Map?
Or maybe it makes more sense to store my serialized Data.Map as a blob in
CouchDB? And do not use views or similar CouchDB / SimpleDB interfaces at
all?  Just retrieve necessary blob and deserialize it to Data.Map, update
and then store modified blob to CouchDB again?

It would be great if somebody had time to implement Data.List, Data.Map,
etc on top of generic  NoSQL DB interface with specific instances for
CouchDB, SimpleDB, etc.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Amazon AWS storage best to use with Haskell?

2011-10-31 Thread Ryan Newton
For distributed execution you can look at the recent work on CloudHaskell:

   https://github.com/jepst/CloudHaskell
   http://groups.google.com/group/cloudhaskell

As for a programming model -- Philip Trinder et. al have a version of
monad-par that works in a distributed way over CloudHaskell, likewise
CloudHaskell itself provides a simple Task layer.

For a NOSQL layer -- I'm looking for the answer to that same question
myself!  We've been experimenting with Cassandra (used via the hscassandra
package based in turn on cassandra-thrift).  Already it's clear that there
are many areas that need work.  The Haskell code generated by Thrift itself
has a lot of room for improvement (for the intrepid hacker: cycles there
would be well-spent).
   We haven't tried CouchDB yet.  Please keep us posted on what you find.

I don't know if any one has a clean way for hooking a simple Haskell-ish
interface (e.g. Data.Map) up to a persistence layer.  But it seems like
there have been a bunch of papers on database supported haskell and the
like.  One of them must have solved this!

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

Cheers,
  -Ryan


On Mon, Oct 31, 2011 at 4:53 PM, dokondr doko...@gmail.com wrote:

 On Mon, Oct 31, 2011 at 6:50 PM, John Lenz l...@math.uic.edu wrote:

 CouchDB works great, although I decided to go with SimpleDB since then it
 is amazon's problem to scale and allocate disk and so forth, which I like
 better.  For couchdb, you can use my package couchdb-enumerator on hackage.


 Regarding CouchDB. So far I have my records keyed by Id and stored in
 Data.Map which I serialize to  text file. Using Data.Map functions I do
 many operations with these records including mapping functions over keys
 and values, accumulation, lookup, intersection, union etc.
 When I move this data to CouchDB and start using couchdb-enumerator to
 work with it, how natural will it be to implement all these functions that
 I use from Data.Map?
 Or maybe it makes more sense to store my serialized Data.Map as a blob in
 CouchDB? And do not use views or similar CouchDB / SimpleDB interfaces at
 all?  Just retrieve necessary blob and deserialize it to Data.Map, update
 and then store modified blob to CouchDB again?

 It would be great if somebody had time to implement Data.List, Data.Map,
 etc on top of generic  NoSQL DB interface with specific instances for
 CouchDB, SimpleDB, etc.

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


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


Re: [Haskell-cafe] How to implement digital filters using Arrows

2011-10-31 Thread John Lask

On 1/11/2011 1:35 AM, Captain Freako wrote:

you need to study ArrowLoop and understand that. In the code

rec (y,s')- arr f -  (x,s)
s- delay s0 -  s'

the state is 'captured' in the recursive binding. i.e. just like in real 
circuits the output state s is threaded back as an input.


The recursive binding is just sugar for the application of the loop 
combinator. The signature of the loop combinator is


loop :: arrow (input, feedback) (output, feedback) - arrow input output

with the loop combinator (with which recursive arrow bindings are 
defined) the function could have been defined as...


liftAu f s0 = loop (second (delay s0)  arr f )

the delay is neccessary to break the recursion. i.e. to calculate the 
next output and state the previous state is used.




liftAu :: ((x,FilterState s)-(y,FilterState s)) -  FilterState s -
FilterAu x y
liftAu f s0 = proc x -  do
   rec (y,s')- arr f -  (x,s)
   s- delay s0 -  s'
   returnA -  y



I think I understand how the `returnA' in the last line of your
`liftAu' function is getting translated by those instance definitions
into:

c where
c = Automaton ( arr id  arr (const c) )

and, furthermore, how that is passing the supplied `y' into the first
element of the resulting couple. However, I don't understand how the
recursively defined `c' is capturing the modified filter state and
preserving it for the next call. It seems like the Automaton being
referred to by `c' is a newly constructed entity, which knows nothing
about the current state of the running Automaton.

Any help in understanding this would be greatly appreciated.

Thanks!
-db





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


Re: [Haskell-cafe] Amazon AWS storage best to use with Haskell?

2011-10-31 Thread dokondr
On Tue, Nov 1, 2011 at 12:07 AM, Ryan Newton rrnew...@gmail.com wrote:

 ...
 For a NOSQL layer -- I'm looking for the answer to that same question
 myself!  We've been experimenting with Cassandra (used via the hscassandra
 package based in turn on cassandra-thrift).  Already it's clear that there
 are many areas that need work.  The Haskell code generated by Thrift itself
 has a lot of room for improvement (for the intrepid hacker: cycles there
 would be well-spent).


Any example code of using hscassandra package would really help!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] lazy A-star search

2011-10-31 Thread Ryan Ingram
On Sun, Oct 30, 2011 at 8:44 AM, Anton Kholomiov
anton.kholom...@gmail.comwrote:

 I'm misunderstanding astar. I've thought that 'whole route'-heuristic
 will prevent algorithm from going in circles. The more you circle around
 the more the whole route distance is.


Sort of.  Consider the tree in my example graph:

A -1- B -1- C -1- D -1- E -9- J
  -2- F -1- C -1- D -1- E -9- J
-2- G -1- D -1- E -9- J
  -2- H -1- E -9- J
-2- I -1- J

There's no circling going on as you depth-first search this tree, even
though you are wasting time visiting the same node multiple times.

However, the thing you know with A*/djikstra is this: If I have visited a
node, there is no shorter path to that node.  So any time I encounter that
node again, I must have at least as long of a path, and so any later nodes
along that path can't be any better along this path.

Effectively, you are pruning the tree:
A -1- B -1- C -1- D -1- E -9- J ***
  -2- F -1- C ***
-2- G -1- D ***
  -2- H -1- E ***
-2- I -1- J GOAL
(*** = pruned branches)

since the second time you visit C, you know the first path was faster, so
there is no reason to continue to visit D/E again.  This is even more
noticable in graphs with multidirectional edges, as the tree is infinitely
deep at every cycle.

I wonder if there is a way to represent this more directly as
tree-pruning.  It's weird, because you are pruning the tree based on
visiting other branches of the tree.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] arr considered harmful

2011-10-31 Thread Ryan Ingram
I know it's a bit of an 'intentionally provocative' title, but with the
recent discussions on Arrows I thought it timely to bring this up.

Most of the conversion from arrow syntax into arrows uses 'arr' to move
components around. However, arr is totally opaque to the arrow itself, and
prevents describing some very useful objects as arrows.

For example, I would love to be able to use the arrow syntax to define
objects of this type:

data Circuit a b where
Const :: Bool - Circuit () Bool
Wire :: Circuit a a
Delay :: Circuit a a
And :: Circuit (Bool,Bool) Bool
Or :: Circuit (Bool,Bool) Bool
Not :: Circuit Bool Bool
Then :: Circuit a b - Circuit b c - Circuit a c
Pair :: Circuit a c - Circuit b d - Circuit (a,b) (c,d)
First :: Circuit a b - Circuit (a,c) (b,c)
Swap :: Circuit (a,b) (b,a)
AssocL :: Circuit ((a,b),c) (a,(b,c))
AssocR :: Circuit (a,(b,c)) ((a,b),c)
Loop :: Circuit (a,b) (a,c) - Circuit b c
etc.

Then we can have code that examines this concrete data representation,
converts it to VHDL, optimizes it, etc.

However, due to the presence of the opaque 'arr', there's no way to make
this type an arrow without adding an 'escape hatch'
Arr :: (a - b) - Circuit a b
which breaks the abstraction: circuit is supposed to represent an actual
boolean circuit; (Arr not) is not a valid circuit because we've lost the
information about the existence of a 'Not' gate.

The arrow syntax translation uses arr to do plumbing of variables.  I think
a promising project would be to figure out exactly what plumbing is needed,
and add those functions to a sort of 'PrimitiveArrow' class.  All of these
plumbing functions are trivially implemented in terms of 'arr', when it
exists, but if it doesn't, it should be possible to use the arrow syntax
regardless.

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


Re: [Haskell-cafe] arr considered harmful

2011-10-31 Thread Daniel Peebles
Have you seen Adam Megacz's work on generalized arrows? I think he proposes
to kill arr and has done a decent amount of work on it.

On Mon, Oct 31, 2011 at 8:33 PM, Ryan Ingram ryani.s...@gmail.com wrote:

 I know it's a bit of an 'intentionally provocative' title, but with the
 recent discussions on Arrows I thought it timely to bring this up.

 Most of the conversion from arrow syntax into arrows uses 'arr' to move
 components around. However, arr is totally opaque to the arrow itself, and
 prevents describing some very useful objects as arrows.

 For example, I would love to be able to use the arrow syntax to define
 objects of this type:

 data Circuit a b where
 Const :: Bool - Circuit () Bool
 Wire :: Circuit a a
 Delay :: Circuit a a
 And :: Circuit (Bool,Bool) Bool
 Or :: Circuit (Bool,Bool) Bool
 Not :: Circuit Bool Bool
 Then :: Circuit a b - Circuit b c - Circuit a c
 Pair :: Circuit a c - Circuit b d - Circuit (a,b) (c,d)
 First :: Circuit a b - Circuit (a,c) (b,c)
 Swap :: Circuit (a,b) (b,a)
 AssocL :: Circuit ((a,b),c) (a,(b,c))
 AssocR :: Circuit (a,(b,c)) ((a,b),c)
 Loop :: Circuit (a,b) (a,c) - Circuit b c
 etc.

 Then we can have code that examines this concrete data representation,
 converts it to VHDL, optimizes it, etc.

 However, due to the presence of the opaque 'arr', there's no way to make
 this type an arrow without adding an 'escape hatch'
 Arr :: (a - b) - Circuit a b
 which breaks the abstraction: circuit is supposed to represent an actual
 boolean circuit; (Arr not) is not a valid circuit because we've lost the
 information about the existence of a 'Not' gate.

 The arrow syntax translation uses arr to do plumbing of variables.  I
 think a promising project would be to figure out exactly what plumbing is
 needed, and add those functions to a sort of 'PrimitiveArrow' class.  All
 of these plumbing functions are trivially implemented in terms of 'arr',
 when it exists, but if it doesn't, it should be possible to use the arrow
 syntax regardless.

   -- ryan

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


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


Re: [Haskell-cafe] arr considered harmful

2011-10-31 Thread Felipe Almeida Lessa
On Mon, Oct 31, 2011 at 10:33 PM, Ryan Ingram ryani.s...@gmail.com wrote:
 The arrow syntax translation uses arr to do plumbing of variables.  I think
 a promising project would be to figure out exactly what plumbing is needed,
 and add those functions to a sort of 'PrimitiveArrow' class.  All of these
 plumbing functions are trivially implemented in terms of 'arr', when it
 exists, but if it doesn't, it should be possible to use the arrow syntax
 regardless.

There are already generalized arrows [1].  Is that what you are looking for?

Cheers,

[1] http://www.cs.berkeley.edu/~megacz/garrows/

-- 
Felipe.

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


Re: [Haskell-cafe] arr considered harmful

2011-10-31 Thread Ryan Ingram
This seems basically what I'm talking about, except even more hardcore.  I
think mostly what I'm suggesting is that the GHC arrow preprocessor to
compile to something like generalized arrows, by default, with current
Arrows as a special case.

  -- ryan

On Mon, Oct 31, 2011 at 5:48 PM, Felipe Almeida Lessa 
felipe.le...@gmail.com wrote:

 On Mon, Oct 31, 2011 at 10:33 PM, Ryan Ingram ryani.s...@gmail.com
 wrote:
  The arrow syntax translation uses arr to do plumbing of variables.  I
 think
  a promising project would be to figure out exactly what plumbing is
 needed,
  and add those functions to a sort of 'PrimitiveArrow' class.  All of
 these
  plumbing functions are trivially implemented in terms of 'arr', when it
  exists, but if it doesn't, it should be possible to use the arrow syntax
  regardless.

 There are already generalized arrows [1].  Is that what you are looking
 for?

 Cheers,

 [1] http://www.cs.berkeley.edu/~megacz/garrows/

 --
 Felipe.

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


Re: [Haskell-cafe] arr considered harmful

2011-10-31 Thread Paterson, Ross
Ryan Ingram writes:
 Most of the conversion from arrow syntax into arrows uses 'arr' to move 
 components around. However, arr is totally opaque to the arrow itself, and 
 prevents describing some very useful objects as arrows.

 For example, I would love to be able to use the arrow syntax to define 
 objects of this type:

 data Circuit a b where
 Const :: Bool - Circuit () Bool
 Wire :: Circuit a a
 Delay :: Circuit a a
 And :: Circuit (Bool,Bool) Bool
 Or :: Circuit (Bool,Bool) Bool
 Not :: Circuit Bool Bool
 Then :: Circuit a b - Circuit b c - Circuit a c
 Pair :: Circuit a c - Circuit b d - Circuit (a,b) (c,d)
 First :: Circuit a b - Circuit (a,c) (b,c)
 Swap :: Circuit (a,b) (b,a)
 AssocL :: Circuit ((a,b),c) (a,(b,c))
 AssocR :: Circuit (a,(b,c)) ((a,b),c)
 Loop :: Circuit (a,b) (a,c) - Circuit b c
 etc.

 Then we can have code that examines this concrete data representation, 
 converts it to VHDL, optimizes it, etc.

 However, due to the presence of the opaque 'arr', there's no way to make this 
 type an arrow without adding an 'escape hatch'
 Arr :: (a - b) - Circuit a b
 which breaks the abstraction: circuit is supposed to represent an actual 
 boolean circuit; (Arr not) is not a valid circuit because we've lost the 
 information about the existence of a 'Not' gate.

If you require the circuit to be parametric in the value types, you can limit 
the types of function you can pass to arr to simple plumbing.
See the netlist example at the end of my Fun of Programming slides 
(http://www.soi.city.ac.uk/~ross/papers/fop.html).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Amazon AWS storage best to use with Haskell?

2011-10-31 Thread Ryan Newton

  Any example code of using hscassandra package would really help!


I'll ask my student.  We may have some simple examples.

Also, I have no idea as to their quality but I was pleasantly surprised to
find three different amazon related packages on Hackage (simply by
searching for the word Amazon in the package list).

   http://hackage.haskell.org/package/hS3
   http://hackage.haskell.org/package/hSimpleDB
   http://hackage.haskell.org/package/aws

It would be great to know if these work.

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


[Haskell-cafe] ghc 7.2.1 Generics problem

2011-10-31 Thread Magicloud Magiclouds
Hi,
  I do not know why, my ghc 7.2.1 does not seem to support
DeriveRepresentable. I compiled the ghc 7.2.1 myself by ghc 7.0.4. All
options default.

$ ghc Types/TopTalkerRecord.hs

Types/TopTalkerRecord.hs:2:14:
Unsupported extension: DeriveRepresentable

$ ghc --version
The Glorious Glasgow Haskell Compilation System, version 7.2.1
-- 
竹密岂妨流水过
山高哪阻野云飞

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