[Haskell-cafe] testing if values can be applied to polymorphic functions

2012-10-22 Thread alex
Hi all,

A while ago I made an unusual visual front-end for Haskell:
  http://www.youtube.com/watch?v=5KtFlGEVFGE
  https://github.com/yaxu/texture

It applies functions that are both proximal in Euclidean space, and
type-compatible.  It 'compiles' to Haskell, piped into ghci, but I
(probably unwisely) wrote it in C, and ended up having to implement
some crazed version of the Haskell type system there to get it
working.

Now I have idea for making this more interesting and practical (for
live music-making, if nothing else), and would like to re-write it all
in Haskell.  Testing type compatibility of expressions is foxing me
though.

For example, say I have (++) and [1,2,3].  I then want to see if a
value of type (Num a = [a]) can be applied to a function of type ([a]
- [a] - [a]).  I've been looking at Data.Typeable.funResultTy to do
this, e.g.:

funResultTy (typeOf ((++) :: [a] - [a] - [a])) (typeOf ([1,2,3] ::
Num a = [a]))

But I get this:
Ambiguous type variable `a0' in the constraint:
  (Typeable a0) arising from a use of `typeOf'

Being a bit more specific doesn't help:

funResultTy (typeOf ((++) :: Typeable a = [a] - [a] - [a])) (typeOf
([1,2,3] :: (Typeable a, Num a) = [a]))

I guess funResultTy doesn't work when polymorphism is involved..

Perhaps I could just use the ghc-as-a-library stuff to parse and
typecheck code - would that be the way forward?

Any pointers much appreciated!

Best wishes

alex

-- 
http://yaxu.org/

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


[Haskell-cafe] Oxford Haskell Users Group

2012-10-22 Thread Nicolas Wu
Dear all,

After a long pause over the summer, the Oxford Haskell Users Group
will be meeting this week, at 8pm on Friday 26th October, at the Mitre
pub on High Street, Oxford [1].

The group meets in an informal setting with no real agenda: typically
we turn up, have a few pints, and enjoy a good chat about what we've
been doing with Haskell. If you'd like to have more details about our
meetings, then join our mailing list [2], where our meetings are
usually announced.

The format of OxHUG will be changing slightly: we'll be meeting once a
month rather than fortnightly, and rotating the day of the week. The
full details of the meetings can be found on the OxHUG calendar [3],
though at the moment only this week's meeting is planned.

Nick

[1]: http://goo.gl/maps/QEN3o
[2]: https://groups.google.com/group/oxhug
[3]: 
https://www.google.com/calendar/embed?src=pjc31qnpq48rvvncq72utqtang%40group.calendar.google.comctz=Europe/London

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


Re: [Haskell-cafe] Blocking IO FIFOs

2012-10-22 Thread Jason Dusek
Hi Everyone,

Thanks for all your help. I've put the first working version of
this on GitHub:

  https://github.com/solidsnack/coproc

Many improvements suggested in thread have not been implemented
as yet but I hope to integrate them as part of expanding the
tool to cover other interpreters, like Python or PSQL.

--
Jason Dusek
pgp // solidsnack // C1EBC57DC55144F35460C8DF1FD4C6C1FED18A2B

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


Re: [Haskell-cafe] Why Kleisli composition is not in the Monad signature?

2012-10-22 Thread Andreas Abel
When I teach my students Haskell's monads, I never put Kleisli into my 
mouth.  I tell them that monads are for sequencing effects; and the 
sequencing is visible clearly in


  ()  :: IO a - IO b - IO b
  (=) :: IO a - (a - IO b) - IO b

but not in

  fmap :: (a - b) - IO a - IO b
  join :: IO (IO a) - IO a

To me,

  print 1  print 2

looks natural, and

  print 1 = const (print 2)

still understandable, but

  join $ fmap (const (print 2)) (print 1)

rather not (I needed ghci to get this example right).

I would not want to introduce category theory or Kleisli composition 
just to teach my students some effectful Haskell programming.


Cheers,
Andreas

On 16.10.2012 21:45, Simon Thompson wrote:


Not sure I really have anything substantial to contribute, but it's certainly 
true that if you see

   a - m b

as a generalisation of the usual function type, a - b, then return generalises 
the identity and
kleisli generalises function composition. This makes the types pretty memorable 
(and often the
definitions too).

Simon


On 16 Oct 2012, at 20:14, David Thomas davidleotho...@gmail.com wrote:


class Monad m where
  return :: a - m a
  kleisli :: (a - m b) - (b - m c) - (a - m c)


Simon Thompson | Professor of Logic and Computation
School of Computing | University of Kent | Canterbury, CT2 7NF, UK
s.j.thomp...@kent.ac.uk | M +44 7986 085754 | W www.cs.kent.ac.uk/~sjt


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




--
Andreas AbelDu bist der geliebte Mensch.

Theoretical Computer Science, University of Munich
Oettingenstr. 67, D-80538 Munich, GERMANY

andreas.a...@ifi.lmu.de
http://www2.tcs.ifi.lmu.de/~abel/

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


[Haskell-cafe] Maximum bipartite matching: 24 lines

2012-10-22 Thread Stefan Klinger
Hello.

I have written a function that calculates maximum cardinality matchings
on bipartite graphs.  It's only 24 lines of code.

It seems (tested, not proven) to run faster, use less memory, and scale
better than using MaxFlow from FGL with constant weight and additional
source and sink nodes.  But it's not as good as Hopcroft–Karp would be.

Attached is the module MaxMatching which also contains extensive
documentation of the rationale behind its design.  I would hope to get
any feedback on this: What do you think about the approach?  Did I
oversee anything?  Do you know of any other purely functional solution
to this problem?

Just as an exmaple, run `ghci MaxMatching.lhs` and then use

matching $ S.fromList [(1,'a'),(1,'b'),(2,'a'),(2,'c'),(3,'b')]

to calculate a maximum cardinality matching of the graph shown below.

1---a   Note the somewhat awkward type of the matching
 \ /function, returning a Map instead of a Set, with the
  X edges being backwards!
 / \
2   b   matching :: (Ord b, Ord a) = S.Set (a, b) - M.Map b a
 \ /
  X On my machine, it takes less than 2s on 10k edges
 / \or 225 nodes.
3   c

Comments are welcome!

Thank you!
Stefan


-- 
Stefan Klinger  o/klettern
/\/  bis zum
send plaintext only - max size 32kB - no spam \   Abfallen
http://stefan-klinger.de

Module  : MaxMatching
Description : Maximum cardinality bipartite matching
Copyright   : © 2012 Stefan Klinger http://stefan-klinger.de/
License : GNU AGPL 3 http://www.gnu.org/licenses/agpl-3.0.html

Maintainer  : Stefan Klinger http://stefan-klinger.de/
Stability   : unstable

Find a maximum cardinality matching on a bipartite graph, using an
augmenting path algorithm.



 module MaxMatching ( matching ) where

 import qualified Data.Map as M
 import qualified Data.Set as S


Basics
--

A bipartite graph has “left” and “right” nodes, we assume the types α
and β for them.  Each edge then is an (α,β) pair, i.e., there are no
edges between nodes on the same side.

A “matching” is a subset of the edges, so that each node is incident to
at most one edge that is in the matching.  We are looking for a matching
that contains as many edges as possible.  With respect to a fixed
matching, an edge is called “matched” iff it is part of the matching.  A
node is called “free” iff it is not incident to any matched edge.

An “augmenting path” contains no cycles, starts at a free α-node,
terminates at a free β-node, and strictly alternately traverses
unmatched and matched edges.  Exactly the first and last node of an
augmenting path are free, the inner nodes are not.

The algo is based on the idea of repeatedly finding an augmenting path
with respect to a current matching, starting from the empty matching,
similar to Hopcroft–Karp.  When an augmenting path is found, all of its
matched edges become unmatched, and vice versa, thus incrementing the
matching's size by one.


Implementation
--

The input graph is of type `Set (α,β)` which implies being bipartite and
simple.  It also denies isolated nodes, but they cannot be matched
anyways.

When looking for an augmenting path, travelling “right” to a β-node, is
always via an unmatched edge, and travelling “left” to an α-node is
always via a matched edge.  Since a β-node can have at most one matched
edge, it is sufficient to store the matching in a map of type `Map β α`,
i.e., backwards.  The invariant is being a proper matching, i.e., being
injective.

 matching :: (Ord a, Ord b) = S.Set (a,b) - M.Map b a
 matching g = opt (M.keys fwd, []) fwd M.empty
 where

Travelling right, we can choose any unmatched edge.  To this end, the
entire graph is maintained as a “forward mapping” of type `Map α [β]`,
listing all β-nodes adjacent to an α-node.

 fwd = foldr (\(x,y) - M.insertWith (++) x [y]) M.empty $ S.toList g


Given two lists of (initially all) free and (initially no) failed
α-nodes, the forward mapping, and an (initially empty) matching, the
optimizer function…

 opt :: (Ord a, Ord b) = ([a],[a]) - M.Map a [b] - M.Map b a - M.Map b a

…repeatedly calls `right` on each free α-node, i.e., starts a path
search from `x`, hoping to get a better matching back.

If no better matching is found, then `x` is is set aside as a failed
node for reconsideration in later iterations.  Otherwise, `x` is part of
the matching and removed from the list of free nodes.  Also, the failed
nodes set aside previously are appended to the free nodes, since they
may lead to an augmenting path with the new matching.

 opt (x:free,failed) fwd mat
 = either (flip (opt (free,x:failed)) mat) (opt (free++failed,[]) fwd)
   $ right fwd [] x
 where

`right` returns either `Right` a better matching if an augmenting path
starting at `x` 

Re: [Haskell-cafe] Maximum bipartite matching: 24 lines

2012-10-22 Thread Eugene Kirpichov
Hi,

fwd = foldr (\(x,y) - M.insertWith (++) x [y]) M.empty $ S.toList g

Use foldl' here, foldr is absolutely useless here and it only consumes
the stack space as your operation is strict.

As for the actual code: I'd prefer the code itself to be more
readable, rather than have a lot of literate comments around it;
currently, IMO all the uncurry's, flips, eithers, maybes and
point-free style hurt readability heavily. I think it would be better
to devise your own very simple datatypes for this.

Maybe I'm too capricious or heretically unhaskellish, I'll probably
try to write my own version as an exercise :)

On Mon, Oct 22, 2012 at 1:28 PM, Stefan Klinger
all-li...@stefan-klinger.de wrote:
 Hello.

 I have written a function that calculates maximum cardinality matchings
 on bipartite graphs.  It's only 24 lines of code.

 It seems (tested, not proven) to run faster, use less memory, and scale
 better than using MaxFlow from FGL with constant weight and additional
 source and sink nodes.  But it's not as good as Hopcroft–Karp would be.

 Attached is the module MaxMatching which also contains extensive
 documentation of the rationale behind its design.  I would hope to get
 any feedback on this: What do you think about the approach?  Did I
 oversee anything?  Do you know of any other purely functional solution
 to this problem?

 Just as an exmaple, run `ghci MaxMatching.lhs` and then use

 matching $ S.fromList [(1,'a'),(1,'b'),(2,'a'),(2,'c'),(3,'b')]

 to calculate a maximum cardinality matching of the graph shown below.

 1---a   Note the somewhat awkward type of the matching
  \ /function, returning a Map instead of a Set, with the
   X edges being backwards!
  / \
 2   b   matching :: (Ord b, Ord a) = S.Set (a, b) - M.Map b a
  \ /
   X On my machine, it takes less than 2s on 10k edges
  / \or 225 nodes.
 3   c

 Comments are welcome!

 Thank you!
 Stefan


 --
 Stefan Klinger  o/klettern
 /\/  bis zum
 send plaintext only - max size 32kB - no spam \   Abfallen
 http://stefan-klinger.de

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




-- 
Eugene Kirpichov
http://www.linkedin.com/in/eugenekirpichov
We're hiring! http://tinyurl.com/mirantis-openstack-engineer

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


Re: [Haskell-cafe] A yet another question about subtyping and heterogeneous collections

2012-10-22 Thread AntC
Dmitry Vyal akamaus at gmail.com writes:

 
 On 10/19/2012 06:14 AM, AntC wrote:
  Roman Cheplyaka roma at ro-che.info writes:
 
[snip]
  instance (Upcast a b, Upcast b c) = Upcast a c where
 upcast = (upcast :: b - a) . (upcast :: c - b)
  This is the offending instance. Remember, GHC only looks at the instance
  head (Upcast a c here) when it decides which instance to use.
 
  Roman
 
  Hi Dmitry, looks like you've got the classic (show . read) difficulty. In
  your Upcast a c instance, the compiler is trying to figure out the type 
of b.
 
  You might think there's only one 'chain' to get from (say) type A to type 
D --
  that is via Upcast A B to Upcast B C to Upcast C D; but there's also an
  instance Upcast x x -- which means there could be any number of Upcast A A,
  Upcast B B, etc links in the chain.
 
  (And this doesn't count all the other possible instances that might be 
defined
  in other modules -- for all the compiler knows at that point.)
 
  The modern way to handle this is using type functions (aka type families 
aka
  associated types), but I'm not sure how that would apply here. (And, for 
the
  record, the old-fashioned way would use functional dependencies, as per the
  Heterogenous Collections paper aka 'HList's).
 
  AntC
 
 
 Hello Antony,
 do I understand you correctly, that the error message is the result of 
 compiler using depth first search of some kind when calculating 
 instances?  Also can you please elaborate a bit more on using functional 
 dependencies for this problem? Upcast x y is not a function, it's a 
 relation, y can be upcasted to different x'es and different y's can be 
 upcasted to single x.
 
 Dmitry
 

Hi Dmitry, you've specified UndecidableInstances (which means you're 
saying trust me, I know what I'm doing). So the compiler isn't trying 
to 'calculate' instances so much as follow your logic, and the error mesage 
means that it can't follow. I'm guessing that the stack overflow is because 
it's tryng to search, and getting into a loop of Upcast x x == Upcast x x 
== ... Increasing the stack size is not likely to help.

You could try removing the Upcast x x instance to see what happens and 
understand it better. (But I can see this won't help with solving the bigger 
problem.) 

The more usual approach for heterogeneous collections (for example in HList, 
or somewhat differently in lenses) is to define a class 'Has x r' (record r 
has field x), with methods get/set. Define instances for all your 'base' 
collection types and their fields. Then define an instance for the subtype to 
inherit from the supertype.

But that does require a strict hierarchy of sub-/super-types, so your wish to 
upcast in any direction won't fit.

For your general question on functional dependencies, you'll need to read the 
wiki's. Relations and functions are isomorphic (and that's what fundeps takes 
advantage of); but it needs careful structuring of the instances to make type 
inference tractable.

HTH
AntC



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


Re: [Haskell-cafe] Fast parsing of unboxed values without boxing them in the parser?

2012-10-22 Thread Bryan O'Sullivan
On Tue, Oct 23, 2012 at 3:26 AM, Eugene Kirpichov ekirpic...@gmail.comwrote:

 I'm thinking that a CPS-style parser type could allow returning an
 unboxed value as a result of the compiler inlining and fusing together
 the parsing code and the code that consumes the parsed value.

 Are there any libraries that work like this?


Both cereal (for binary) and attoparsec (text) are written in a CPS style
that can support this in principle. For parsers of even modest complexity,
GHC won't necessarily succeed at unboxing values, though; you have to
inspect the Core to see if what's going on matches what you're hoping for.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Hackage Package Discoverability

2012-10-22 Thread Myles C. Maxfield
Hello,
I am the author/maintainer of the 'punycode' hackage package. After 4
months, I just found that punycode conversion already exists in the
Data.Encoding.BootString package inside the 'encoding' package. I'd like to
deprecate my package in favor of the 'encoding' package.

However, I would also like to solve the discoverability problem of people
not knowing to look in the 'encoding' package when they're looking for the
punycode algorithm. (I certainly didn't look there, and as a result, I
re-implemented the algorithm). My initial thought is to keep my package in
the hackage database, but put a big label on it saying DEPRECATED: Use
Data.Encoding.BootString instead. Is there a better way to make this
algorithm discoverable?

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