Re: [Haskell-cafe] (Co/Contra)Functor and Comonad

2010-12-23 Thread C. McCann
On Thu, Dec 23, 2010 at 5:25 PM, Stephen Tetley
stephen.tet...@gmail.com wrote:
 On 23 December 2010 21:43, Mario Blažević mblaze...@stilo.com wrote:
 Why are Cofunctor and Comonad classes not a part of the base library?
 [SNIP]
 Later on I found that this question has been raised before by Conal Elliott,
 nearly four years ago.

 http://www.haskell.org/pipermail/libraries/2007-January/006740.html

 From a somewhat philistine persepective, that Conal's question went
 unanswered says something:

 Does anyone have useful functionality to go into a Cofunctor module
 (beyond the class declaration)?

 Successful post-H98 additions to Base (Applicative, Arrows, ...)
 brought a compelling programming style with them. For Comonads,
 Category-extras does define some extra combinators but otherwise they
 have perhaps seemed uncompelling.

As it happens, there actually is a significant programming style to go
with cofunctors. There's also a reason why it may not seem
compelling to Haskell programmers, which I will illustrate with an
analogy to other programming languages:

Consider the problem of variance in a language with a subtyping
relation and optionally mutable references. A subtype relationship A
: B can be viewed as an implicit conversion operator from A to B.
Therefore, if you have a read-only reference to something of type A,
you can create a read-only reference to something of type B. This can
be seen as analogous to mapping the implicit conversion function over
the identity functor applied to type A.

On the other hand, what if you have a mutable reference to something
of type A? You can't assign something of type B to it, because
anything reading from the reference will receive a B, and there's no
implicit conversion from B to A. However, if you instead have a
mutable reference to something of type B, you can indeed assign
something of type A to it using the implicit conversion. This is
likewise analogous to mapping the conversion over an identity
cofunctor.

In other words, contravariant functors naturally describe concepts
like destructive assignment, pushing values into a data sink of some
sort, etc.

The simplest example of a potential contravariant functor in Haskell
would be (- r), i.e., a flipped version of the basic Reader functor
(e -).

Similarly, assigning to an IORef, partially applied to the reference
itself, gives the type (a - IO ()), which is a special case of the
flipped Reader.

- C.

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


Re: [Haskell-cafe] (Co/Contra)Functor and Comonad

2010-12-23 Thread C. McCann
On Thu, Dec 23, 2010 at 11:46 PM, Mario Blažević mblaze...@stilo.com wrote:

 I don't personally care what's it called, as long as it's available. Can
 anybody point to an authoritative source for the terminology, though?
 Wikipedia claims that cofunctor is a contravariant functor.

Does nLab count as sufficiently authoritative? As far as I can tell it
just uses contravariant functor if anything, and never uses
cofunctor.

c.f. http://ncatlab.org/nlab/show/contravariant+functor

 Also, is there anything in category theory equivalent to the Functor -
 Applicative - Monad hierarchy , but with a Cofunctor/Contrafunctor at the
 base? I'm just curious, I'm not advocating adding the entire hierarchy to
 the base library. ;)

As far as I understand (which may not actually be all that far),
contravariant functors just go to or from an opposite category, a
distinction that is purely a matter of definition, not anything
intrinsic. On the other hand, Applicative and Monad are based on
endofunctors specifically, i.e. functors from a category to itself,
which would seem to necessarily exclude functors from a category to
its opposite.

There may exist constructs specifically based on such contravariant
endofunctors but I doubt they'd be *equivalent* to things like
Applicative/Monad in any particular way.

- C.

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


Re: [Haskell-cafe] Offer to mirror Hackage

2010-12-08 Thread C. McCann
On Wed, Dec 8, 2010 at 5:41 AM, Ketil Malde ke...@malde.org wrote:
 I'm a bit surprised to find that there seems to be a lot of opposition
 to this view, but perhaps the existing structure is more secure than I
 thought?

The difference is in the ability to influence other packages and
metadata, I think. You could upload a trojan to Hackage right now, but
who would ever install it? You could go to the effort of becoming
responsible for a package that people do use and then slip the trojan
in later, but the update to the package will still be visible
and--since this is now a package that people actually use--some
do-gooder will probably stumble on your nefarious plot in the process
of simple compatibility checking or such.

On the other hand, by running a malicious mirror, nothing stops you
from inserting (unsafePerformIO installRootKit) into the bytestring
package with no indication of a change.

All of this applies equally to Hackage as it stands, of course, the
difference being the implicit trust the community puts in the people
with administrative power over it. If someone else who already has
that degree of informal trust put up a mirror I don't think anyone
would have a problem using it.

As always security is a matter of degree, but Hackage is just
high-profile enough that a bit of care is probably warranted. And I
suspect that most worthwhile interim solutions to add a bit of trust
for mirrors would be almost as much effort as a complete solution.

- C.

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


Re: [Haskell-cafe] the beginning of the end

2010-12-06 Thread C. McCann
On Mon, Dec 6, 2010 at 2:33 AM, David Virebayre
dav.vire+hask...@gmail.com wrote:
 Level 5

 I'm out of layers here. I think this is all there is to it.

Level 5 is after you've spent way too much time writing questions
and/or answers that people like and have over 10k reputation. This
unlocks some basic moderation tools for helping deal with spam and
other problematic content. SO is a largely community-driven site,
rather than having a bunch of moderators appointed by the
administrators.

There's also other things that some people track, like weekly scores
and per-tag rankings. For instance, I'm apparently SO's foremost
expert on lazy-evaluation and typeclass, and the only user so far
to get a tag badge for monads. This is obviously a very significant
accomplishment.

But seriously, it's mostly just a medium for providing QA in a
structured, searchable way. In fact, you missed the most important
part by far:

Level 0:
You have an unresolved programming problem. You search the web for
information and the first Google hit is a question on StackOverflow
that describes your problem exactly. You look at the accepted answer,
find that it has the solution you need, and go on your way in a matter
of minutes.

- C.

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


Re: [Haskell-cafe] Making monadic code more concise

2010-11-15 Thread C. McCann
On Mon, Nov 15, 2010 at 12:43 PM, Ling Yang ly...@cs.stanford.edu wrote:
 Specifically: There are some DSLs that can be largely expressed as monads,
 that inherently play nicely with expressions on non-monadic values.
 We'd like to use the functions that already work on the non-monadic
 values for monadic values without calls to liftM all over the place.

It's worth noting that using liftM is possibly the worst possible way
to do this, aesthetically speaking. To start with, liftM is just fmap
with a gratuitous Monad constraint added on top. Any instance of Monad
can (and should) also be an instance of Functor, and if the instances
aren't buggy, then liftM f = (= return . f) = fmap f.

Additionally, in many cases readability is improved by using ($), an
operator synonym for fmap, found in Control.Applicative, I believe.

 The probability monad is a good example.

[snip]
 I'm interested in shortening the description of 'test', as it is
 really just a 'formal addition' of random variables. One can use liftM
 for that:

 test = liftM2 (+) (coin 0.5) (coin 0.5)

Also on the subject of Control.Applicative, note that independent
probabilities like this don't actually require a monad, merely the
ability to lift currying into the underlying functor, which is what
Applicative provides. The operator ((*) :: f (a - b) - f a - f b)
is convenient for writing such expressions, e.g.:

test = (+) $ coin 0.5 * coin 0.5

Monads are only required for lifting control flow into the functor,
which in this case amounts to conditional probability. You would not,
for example, be able to easily use simple lifted functions to write
roll a 6-sided die, flip a coin as many times as the die shows, then
count how many flips were heads.

 I think a good question as a starting point is whether it's possible
 to do this 'monadic instance transformation' for any typeclass, and
 whether or not we were lucky to have been able to instance Num so
 easily (as Num, Fractional can just be seen as algebras over some base
 type plus a coercion function, making them unusually easy to lift if
 most typeclasses actually don't fit this description).

Part of the reason Num was so easy is that all the functions produce
values whose type is the class parameter. Your Num instance could
almost be completely generic for any ((Applicative f, Num a) = f a),
except that Num demands instances of Eq and Show, neither of which can
be blindly lifted the way the numeric operations can.

I imagine it should be fairly obvious why you can't write a
non-trivial generic instance (Show a) = Show (M a) that would work
for any possible monad M--you'd need a function (show :: M a -
String) which is impossible for abstract types like IO, as well as
function types like the State monad. The same applies to (==), of
course. Trivial instances are always possible, e.g. show _ = [not
showable], but then you don't get sensible behavior when a
non-trivial instance does exist, such  as for Maybe or [].

 Note that if we consider this in a 'monadification' context, where we
 are making some choice for each lifted function, treating it as
 entering, exiting, or computing in the monad, instancing the typeclass
 leads to very few choices for each: the monadic versions of +, -, *
 must be obtained with liftM2,the monadic versions of negate, abs,
 signum must be obtained with liftM, and the monadic version of
 fromInteger must be obtained with return . 

Again, this is pretty much the motivation and purpose of
Control.Applicative. Depending on how you want to look at it, the
underlying concept is either lifting multi-argument functions into the
functor step by step, or lifting tuples into the functor, e.g. (f a, f
b) - f (a, b); the equivalence is recovered using fmap with either
(curry id) or (uncurry id).

Note that things do get more complicated if you have to deal with the
full monadic structure, but since you're lifting functions that have
no knowledge of the functor whatsoever they pretty much have to be
independent of it.

 I suppose I'm basically suggesting that the 'next step' is to somehow
 do this calculation of types on real type values, and use an inductive
 programming tool like Djinn to realize the type signatures. I think
 the general programming technique this is getting at is an orthogonal
 version of LISP style where one goes back and forth between types and
 functions, rather than data and code. I would also appreciate any
 pointers to works in that area.

Well, I don't think there's any good way to do this in Haskell
directly, in general. There's a GHC extension that can automatically
derive Functor for many types, but nothing to automatically derive
Applicative as far as I know (other than in trivial cases with newtype
deriving)--I suspect due to Applicative instances being far less often
uniquely determined than for Functor. And while a fully generic
instance can be written and used for any Applicative and Num, the
impossibility of sensible instances for Show and Eq, 

Re: [Haskell-cafe] Bracket around every IO computation monad

2010-11-15 Thread C. McCann
On Sun, Nov 7, 2010 at 7:40 PM, Mitar mmi...@gmail.com wrote:
 I have a class Neuron which has (among others) two functions: attach
 and deattach. I would like to make a way to call a list/stack/bunch of
 attach functions in a way that if any of those fail (by exception),
 deattach for previously already attached values (called attach on
 them) are deattached (called deattach on them).


Perhaps I'm misunderstanding how this works, but it seems like this
could all be done fairly simply using standard combinators in
Control.Monad.

 growNeurons :: [IO Growable] - IO [Growable]
 growNeurons attaches = growNeurons' attaches []
  where growNeurons' [] ls      = return ls
        growNeurons' (a:ats) ls = bracketOnError a (\(Growable l) -
 deattach l) (\l - growNeurons' ats (l:ls))

Isn't this mostly a reimplementation of mapM? Given a list of [IO
Growable], you map over it to put a bracket around each one, then
sequence the result (which I believe performs exactly the sort of
nested monadic recursion you're doing here). I think that something
like this ought to be equivalent:

growNeurons :: [IO Growable] - IO [Growable]
growNeurons = mapM (\a - bracketOnError a (\(Growable l) - deattach l) return)

 So I give growNeurons a list of attach actions and it returns a list
 of attached values ((live)neurons). This works nice, but syntax to use
 it is ugly:

 neurons - growNeurons [
    do { a - attach nerve1; return $ Growable a },
    do { a - attach nerve2; return $ Growable a },
    do { a - attach nerve3; return $ Growable a }
  ]

Along the lines of what Felipe suggested, this could possibly be
simplified to something like:

growNeurons  $ map (fmap Growable . attach) [nerve1, nerve2, nerve3]

...except that this won't work if the nerves have different types. In
many cases there's a trivial translation to get rid of existential
types, and I suspect it would work here, but I'm not sure what else
you might be doing with them. Existential types tend to be more
trouble than they're worth, in my experience.

 It seems to me that all this could be wrapped into a monad. So that I
 would be able to call something like:

 neurons - growNeurons' $ do
    attach nerve1
    attach nerve2
    attach nerve3

I'm not sure why you'd want to do it this way, relying on the monad to
provide the sequencing. Isn't it more convenient to use a list of
neurons, as above?

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


Re: [Haskell-cafe] Serialization of (a - b) and IO a

2010-11-12 Thread C. McCann
On Fri, Nov 12, 2010 at 4:24 AM, Ketil Malde ke...@malde.org wrote:
 IMO, it's morally different, you're now operating on a file, and you
 shouldn't rely on the contents being predictable.  You can make the
 sin-bin argument that IO can do anything, but I think there's a moral
 distinction between

  serialize :: a - IO ByteString
  x - serialize f

 and

  serialize :: a - Opaque
  store :: Opaque - FilePath - IO ()

Any distinction here is mostly at the level of API design and informal
semantics; I'm inclined to agree with your preference, but as far as
impacts on the formal semantics of pure code go, these are essentially
equivalent.

 You could probably already snarf chunks of the heap and dump them to file.

Yep, and this is pretty much the reason, taken to its logical
conclusion, why almost all bets are off about what IO computations can
potentially do.

 I suppose one could object that this isn't actually serializing
 anything at all; to which I would respond that, in pure code, how do
 you expect to tell the difference?

 Nice one :-)

 I guess the real question is what are the useful, pure operations on an
 opaque type that can contain arbitrary functions.

I would be very surprised if there were any that couldn't just as well
be done on the function directly. Even extracting type information
could be problematic if done incorrectly! Consider a function
(inspectType :: Opaque - Serialization.Type), where the Show instance
for Type produces an approximation of the type signature the function
was declared with. Reasonable? Nope, we just broke everything. Imagine
a function taking an argument of type ((a, a) - a). If by serializing
the argument it can recover the declared type signature it could
distinguish between fst and ((\(x, _) - x) :: forall a. (a, a) - a),
which again opens the door to non-parametric behavior. On the other
hand, (inspectType :: Opaque - Data.Typeable.TypeRep) would probably
be safe, because it supports only monomorphic types.

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


Re: [Haskell-cafe] Serialization of (a - b) and IO a

2010-11-11 Thread C. McCann
On Thu, Nov 11, 2010 at 10:53 AM, Ketil Malde ke...@malde.org wrote:
 ..and you are able to tell the difference.  Am I wrong in thinking that
 this could be made to work if serialization was to/from an opaque type
 instead of (Byte)String, so that the *only* operations would be
 serialization and deserialization (and possibly storing to/from file)?

This was my first thought as well! However, reading to/from a file
would of course be in IO, at which point you'd be free to read the
file back in through normal means to get at the representation. So in
that respect, this is equivalent to (a - b) - IO String.

Outside of IO, it would pretty much have to be limited to serializing
and deserializing. You'd be able to create opaque tokens representing
functions, pass them around, and/or extract the function in order to
apply it. Conveniently, it turns out that Haskell already has support
for this, you can implement it as follows:

 module Serialize.Pure (OpaqueFunction, serialize, deserialize) where

 newtype OpaqueFunction a b = Opaque { deserialize :: a - b }

 serialize = Opaque

Toss in some existential types as desired, if you want to hide the
function's actual type.

I suppose one could object that this isn't actually serializing
anything at all; to which I would respond that, in pure code, how do
you expect to tell the difference?

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


[Haskell-cafe] Serialization of (a - b) and IO a

2010-11-11 Thread C. McCann
Oops, forgot to send this to the list... sorry, Sjoerd.

On Thu, Nov 11, 2010 at 11:54 AM, Sjoerd Visscher sjo...@w3future.com wrote:
 You would lose many uses of equational reasoning in your programs. Have you
 every substituted 'x * 2' for the expression 'x + x' in one of your programs,
 or vice versa? You can no longer do that, because someone may be serializing
 the function you're writing, checking how it's implemented, and relying it.

 Yes, but it would not break any existing code. It would only break code that 
 knowingly did the wrong thing.

Or code that unknowingly depends transitively on code that does the
wrong thing. In that regard it would be much like unsafePerformIO, and
about as trustworthy. Better off just having any such serialize be
safely in IO, and let people who want to live dangerously just use
unsafePerformIO to get around it.

 We already have a weak case of this, since (\x - undefined x) can be
 distinguished from undefined using seq, but that can be hand-waved away by 
 not
 worrying about bottoms so much. That isn't going to work for serialize.

 Why not?

I'd venture that perhaps because seq only behaves differently when one
possible outcome is _|_. An unsafe serialize could distinguish between
two non-bottom values, which means the sketchy behavior could be free
to wreak havoc in code that's not crashing.

For instance, assuming serialize can be applied to functions of any
type, it would probably be trivial to write a function (isExpr :: a -
Bool) that reports whether an arbitrary term is a primitive value or
the result of some expression, which then lets you write a function
with type (forall a. a - a) that is NOT equivalent to id, which could
then be passed freely into any other piece of code you like. That
sounds like buckets of fun, doesn't it?

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


Re: [Haskell-cafe] Serialization of (a - b) and IO a

2010-11-11 Thread C. McCann
On Thu, Nov 11, 2010 at 1:57 PM, Stephen Tetley
stephen.tet...@gmail.com wrote:
 On 11 November 2010 18:01, C. McCann c...@uptoisomorphism.net wrote:

 For instance, assuming serialize can be applied to functions of any
 type, it would probably be trivial to write a function (isExpr :: a -
 Bool) that reports whether an arbitrary term is a primitive value or
 the result of some expression [SNIP]

 Persistent functional languages usually give serialized values
 including closures a dynamic type. So can you write isExpr :: Dynamic
 - Bool ?

But it's not the type of the serialized value that's at issue, it's
the type of the serializable values. Anything that lets you convert an
arbitrary closure into something with internals open to inspection
will likely have dire consequences for parametricity and referential
transparency. Remember, the problem isn't what you do with the
serialized form itself, it's what you can learn via it about the
original value it was serialized from. To retain sanity, either types
that can be serialized must be marked explicitly (perhaps in the
context, similar to having a Data.Typeable constraint) to indicate
potential non-parametric shenanigans, or the result of serializing and
inspecting a value must be quarantined off, such as with IO. Or some
other mechanism, but those seem like the obvious choices.

Having a full serialization function without some restriction along
those lines would be like renaming unsafePerformIO to runIO, moving it
to Control.Monad.IO, and telling people hey, just don't misuse this
and everything will be okay.

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


Re: [Haskell-cafe] Serialization of (a - b) and IO a

2010-11-11 Thread C. McCann
On Thu, Nov 11, 2010 at 3:30 PM, Stephen Tetley
stephen.tet...@gmail.com wrote:
 The conclusion notes in passing that OCaml's persistence isn't
 referentially transparent. If the Haskell version wasn't, I'd expect a
 mea culpa from the authors at this point.

From a quick glance at the paper, the Haskell version is referentially
transparent in the standard, trivial sense: the persistence operations
all return IO actions. This is of course perfectly fine. What started
this thread, however, was the idea of a serialization function
producing something like a pure ByteString, and why that, as opposed
to (IO ByteString), would be extremely problematic.

What it boils down to is just that any pure serialization function
would necessarily do nothing useful. Serializing closures from IO
actions, on the other hand, I think is a great idea, though probably
difficult to implement!

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


Re: [Haskell-cafe] Is let special?

2010-11-03 Thread C. McCann
2010/11/3 Petr Pudlak d...@pudlak.name:
 f = (\x - x x) (\y - y)
 g = let x = \y - y in x x

 The function f is not typable in the Hindley-Milner type system, while g
 is is (and its type is a - a). The reason is that in the first case (f),
 the typing system tries to assign a single type to x, which is impossible

And just to be clear, this is specific to the H-M system. The function
f is typeable--but not inferable--in GHC-Haskell-with-extensions,
i.e. the definition:

 {-# LANGUAGE Rank2Types #-}

 f = ((\x - x x) :: forall a. (forall b. b - b) - a - a) (\y - y)

...is valid and will have the correct type for f. The more
restricted system provided by H-M is interesting largely because
everything typeable in it is also inferable.

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


Re: [Haskell-cafe] Edit Hackage

2010-10-30 Thread C. McCann
On Sat, Oct 30, 2010 at 11:34 AM, Ketil Malde ke...@malde.org wrote:
 Stack Overflow and Reddit are at least improvements over the traditional
 web forums, starting to acquire some of the features Usenet had twenty
 years ago.  Much like Planet-style meta-blogs and RSS syndication makes
 it liveable to follow blogs.

Very much this. I mourn Usenet's potential as much as anyone, but life
goes on. I'll also note that some private sites take reasonable
steps to promote openness. To use Stack Overflow as an example again,
all content on the site is under a Creative Commons license and they
provide torrents of raw data dumps containing everything but private
information about users. So if someone wanted, it'd be possible
(probably even easy) to do something like mirror all the content in
the [haskell] tag somewhere on haskell.org without any advertising or
extraneous SO-related stuff cluttering it up, perhaps re-organized
into a more structured FAQ format.

 The important thing is making all the resources visible, and bringing
 stuff together.  HWN is great, I don't follow Reddit, but I do click on
 the links that look interesting.  Is there something going in the other
 direction, pointing SO users to mailing list threads, for instance?
 Most web-based email archives seem to suck - where can we point to a nice
 URL to get an overview of a -cafe thread?

Well, it's always good form to provide relevant links in SO answers,
but I'm more likely to direct people to the wiki on Haskell.org, the
online Haskell report, Hackage, various blogs, or occasional research
papers. I have seen relevant -cafe threads mentioned on occasion,
typically using the archive at haskell.org/pipermail and linking to a
specific message.

As you say, most email archives leave something to be desired. As far
as I know, the best way to find anything in old -cafe threads is to do
a google search with
site:http://www.haskell.org/pipermail/haskell-cafe/;, and there's no
good way to get an overview. Especially as topic drift leads to
subject lines being uninformative (I mean, Edit Hackage? What?).

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


Re: [Haskell-cafe] who's in charge?

2010-10-29 Thread C. McCann
On Fri, Oct 29, 2010 at 8:31 AM, Ben Millwood hask...@benmachine.co.uk wrote:
 Besides, I'd think that often what Haskell developers lack is time
 more than skill - there are plenty of tasks that could be done without
 advanced knowledge of deep abstractions, if only someone could put
 aside a few weekends for them. For example, writing low-level FFI
 bindings is almost mechanical (i.e. requires basically no actual
 ingenuity) with the right tools, but it takes time and effort, so
 libraries go unbound.

It's more than just that; when talking about libraries for some
specific task, what matters most is actually the language-agnostic
knowledge of the task itself. Particularly in the case of IO-oriented
libraries with lots of FFI bindings, someone who knows the underlying
C library (or what-have-you) inside and out is probably going to get
the best results from writing a library, even with little knowledge of
Haskell.

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


Re: [Haskell-cafe] Edit Hackage

2010-10-29 Thread C. McCann
On Thu, Oct 28, 2010 at 9:13 PM, Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com wrote:
 IIUC, [one of] the prime motivating factor[s] behind both reddit and
 StackOverflow is the accumulation of karma, which leads to people
 posting just to try and accumulate karma even if they don't know what
 they're talking about.  Here, we are (hopefully) above such mundane
 things.

Er, I suppose I should defend Stack Overflow a bit here. Yes, it has
the whole reputation score thing, but actually does a pretty good
job using it to motivate good activity without encouraging the sort
of endless inane karma-pandering that tends to show up eventually on
more general discussion-oriented sites. Usually the worst thing that
happens--at least on the [haskell] tag--is quick-draw answers shooting
from the hip and misreading the question slightly.

Furthermore, Stack Overflow isn't really a place to track for
information. It's a special-purpose site for programming-related QA.
You either go there to ask for help with a problem, or you keep an eye
out for new questions in order to answer them. It's not a discussion
site and the vast majority of -cafe would be horrendously off-topic
there (the question starting this thread, for instance, is only
tangentially programming-related and probably wouldn't really belong).
Also, the questions tend to be simple, beginner-level stuff for the
most part, not ones that are likely to interest Haskell veterans (in
fact, more advanced questions are liable to go unanswered, other than
Simon or Don fielding an occasional question regarding gritty
practical details about GHC).

So essentially, participating on SO isn't really about the Haskell
community as-is; it's about helping people learn Haskell and (by
extension) promoting the language and hopefully bringing new people
in. And for that purpose, SO's structure and design really do make it
a better medium than the alternatives. But I wouldn't fault anyone for
not bothering with it, if they're not interested in spending lots of
time helping beginners out with the only reward being a slightly
larger number on their account profile page.

 Another point against reddit: Don posted a link to my survey on the
 naming of fgl a few months back.  Someone then queried [1] the two
 naming choices that were available on reddit rather than reading the
 discussions that had already taken place here on -cafe or bothering to
 actually ask _me_.  Similar things go with submitted blog posts:
 rather than discussing the content as comments on the blog post, they
 discuss them on reddit thus depriving readers of the post itself of
 what they think.

Speaking of not wanting more places to keep track of, that's precisely
why I rarely bother with blog comments and would find discussions on
reddit preferable: it's a single place to go, and keeps things more
unified and consistent than whatever comment system some random blog
has (most of which are more awkward to use than reddit, as well). Of
course, having separate discussions going on in each is probably the
worst of both worlds.

Overall, I expect Don has a better feel than anyone else for where the
Haskell community as a whole goes; if he says the balance is shifting
away from -cafe I'd take that first as a statement of fact, not
advocacy. I'd also venture to guess that, from the standpoint of a
newcomer, reddit, Stack Overflow, and the like are the most visible
parts of the Haskell community by a good margin, which means that as
the community continues to grow any bias in favor of such places will
likely do the same. So it goes...

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


Re: [Haskell-cafe] Edit Hackage

2010-10-29 Thread C. McCann
On Fri, Oct 29, 2010 at 6:13 PM, Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com wrote:
 So you'd prefer to have the discussion about a blog post be made
 distinct from the blog post itself?  Why not keep them together, also
 so that people finding the blog post from someplace other than reddit
 (e.g. planet.haskell.org) can find them?

Well, I'd most prefer that absolutely everything I'm interested in be
conveniently kept together in one place, of course, but that's not
really practical. Failing that, yes, I think reddit (or something like
it) makes a better medium for discussion of broad topics than does the
comment system on most blogs. Given a shared subject matter, e.g.
Haskell, having one place with discussions about relevant posts from
multiple blogs provides a richer overall context than does any one
individual post.

Anyway, lots of blogs these days have little submit/discuss this post
on four-hundred-and-thirteen different web 2.0 social news sites!!
buttons after every post, so it's not exactly hard to find them...

 Neither the Haskell reddit nor Stack Overflow are linked to from
 haskell.org and there is nothing to indicate that they are official.

I skimmed the last couple months of archives for
beginn...@haskell.org, found some straightforward questions, and for
each one put a few keywords into a google search. About half the time
there was a relevant question on Stack Overflow in the first page of
results, at least once actually showing up ahead of the mail message I
was searching based off of.

The idea of community is a rather fluid and consensus-based sort of
thing. At some point, visibility is the same thing as being
official. (And yes, they are actually linked from haskell.org, but
I'm not sure how much that's really worth.)

  Also, wasn't it Don that started (and is mainly responsible) for
 linking to Haskell articles on reddit?

Maybe. Is there anything related to publicising Haskell that Don
*hasn't* done? :) And I think he's only mainly responsible insofar
as he tends to find and submit the good links first.

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


Re: [Haskell-cafe] Re: Current thinking on CompositionAsDot issue in haskell prime?

2010-10-29 Thread C. McCann
On Fri, Oct 29, 2010 at 7:54 PM, wren ng thornton w...@freegeek.org wrote:
 I'm sort of torn on this issue. On the one hand (#) has great potential as
 an operator, on the other hand I've found that having something like
 -XMagicHash (or TeX's \makeatletter and \makeatother) can be really helpful
 when you want to expose some guts but also want to keep folks from using
 them accidentally.

Haskell officially supports unicode in identifiers, right? Why not
pick some obscure and little-used symbol and leave the ones that are
conveniently placed on standard keyboards for normal use?

I suggest U+2621.

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


Re: [Haskell-cafe] Re: Current thinking on CompositionAsDot issue in haskell prime?

2010-10-29 Thread C. McCann
On Fri, Oct 29, 2010 at 10:30 PM, wren ng thornton w...@freegeek.org wrote:
 I suggest U+2621.

 I'm not sure I'd've ever recognized a funny 'z' as caution sign... :)

Well, I'm operating under the assumption that it's one of these:
http://en.wikipedia.org/wiki/Bourbaki_dangerous_bend_symbol

I would not be at all surprised at people working on Unicode being
familiar with Knuth's use of the symbol.

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


Re: [Haskell-cafe] Re: Who is afraid of arrows, was Re: ANNOUNCE: Haskell XML Toolbox Version 9.0.0

2010-10-13 Thread C. McCann
On Wed, Oct 13, 2010 at 3:50 AM, Heinrich Apfelmus
apfel...@quantentunnel.de wrote:
 Combined with = /  you have multiple reading direction in the same
 expression, as in

 expression      ( c . b . a ) `liftM` a1 = a2 = a3
 reading order     6   5   4            1      2      3

 That's why I'm usually using  =  instead of  = .

Does it bother you that (=) is defined to be infixr 1, while ($)
and (*) are infixl 4? Or is that just me?

For instance, I might write the above expression as something like:

a3 = a2 = a . b . c $ a1

But this still seems awkward, because it mixes different fixities and
I have to mentally regroup things when reading it. Right associativity
here does make a certain amount of sense for monads, but
left-associativity is consistent with plain function application and
feels more natural to me.

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


Re: Who is afraid of arrows, was Re: [Haskell-cafe] ANNOUNCE: Haskell XML Toolbox Version 9.0.0

2010-10-12 Thread C. McCann
On Tue, Oct 12, 2010 at 8:56 AM, Uwe Schmidt u...@fh-wedel.de wrote:
 No, but there is no point in using a formalism that adds complexity
 without adding functionality.  Arrows are more awkward to use than
 monads because they were intentionally designed to be less powerful than
 monads in order to cover situations in which one could not use a monad.
 When your problem is solved by a monad there is no point in using arrows
 since an arrow require you to jump through extra hoops to accomplish the
 same goal.

 As I understood, John Hughes invented the arrows as a generalisation
 of monads, you say it's a less powerful concept. I'm a bit puzzled with
 that. Could you explain these different views.

These are the same thing, the difference is whether you're talking
about how many different concepts are compatible with an abstract
structure as opposed to what can be done universally with such a
structure. Adding the ability to do more things with a structure
necessarily reduces the number of concepts that structure applies to.

Perhaps a more familiar example is the relationship Functor 
Applicative  Monad. Going left to right adds power, making generic
code more expressive but reducing the number of concepts that can be
represented as instances; going right to left adds generality,
limiting what generic code can do but enabling more instances.

That said, I dislike calling arrows a generalization of monads--it's
not incorrect as such, but I don't think it aids understanding. It
really is much better to think of them as generalized functions, which
they explicitly are if you look at the borrowed category theory
terminology being used. They're generalized monads only in the sense
that functions (a - m b) form arrows in a category, as far as I can
tell.

 No, that is not at all the problem with arrows.  The problem with arrows
 is that they are more restrictive than monads in two respects.  First,
 unlike monads, in general they do not let you perform an arbitrary
 action in response to an input. ...

 It's rather easy to define some choice combinators. Or am I
 missing the point?

The key point is that arrows in full generality--meaning instances of
Arrow only, not other type classes--are not higher-order because no
internal application operator is provided. The ArrowApply class gives
you full higher-order generalized functions, at the cost of giving up
some useful limitations (read: static guarantees about code behavior)
that make reasoning about arrow-based structures potentially easier.

So, a general arrow can perform different actions and produce
different output based on input it receives, but it can't take *other
arrows* and pick different ones to use depending on its input.

 The combinator does the following: The input of the whole arrow
 is fed into g, g computes some result and this result together with the
 input is used for evaluating f'.  The ($) is something similar to ($).

There's no shortage of ways to deal with the issue, but they all rely
on using combinator *functions*, not arrows. The result is that
arrow-based expressions tend to be internally less flexible, following
pre-defined paths, similar to how expressions using Applicative can't
embed control flow the way ones using Monad can. Which is fine for
many purposes, of course.

Essentially, arrows lend themselves best to composing first-order
computations to create larger computations with a fixed structure. If
you find yourself forced to frequently use ArrowApply or other means
of eliminating higher-order structure--e.g., anything that results in
an arrow with an output type that contains fewer instances of the
arrow's own type constructor than does the input type--it may be worth
considering if arrows are really what you want to use.

Personally, though, I think monads are really overkill in many cases
and strongly prefer, where possible, to use Applicative or Arrow.

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


Re: Who is afraid of arrows, was Re: [Haskell-cafe] ANNOUNCE: Haskell XML Toolbox Version 9.0.0

2010-10-12 Thread C. McCann
On Tue, Oct 12, 2010 at 3:00 PM, Paolo G. Giarrusso
p.giarru...@gmail.com wrote:
 Were you writing a paper, your comment would be fully valid. Here
 we're talking about a library for people to use in practice. In the
 middle, somebody should make sure that people without a PhD can learn
 arrows, by providing documentation. The problem might be just
 educational, and it's not restricted to arrows, but it is still a
 valid problem.

Oh, for crying out loud, no it isn't. I don't have a PhD. I don't have
any graduate degree at all. I didn't learn anything about functional
programming back when I was an undergraduate at a
not-exactly-prestigious school, never mind category theory or abstract
algebra or any of that stuff, and I only started even learning Haskell
barely a year ago.

Arrows are easy to understand. Yes, really.

I'll agree that a lot of libraries on hackage could stand to have
better documentation and examples of usage--and I've not actually used
HXT itself so I can't speak to how well it does--but I honestly cannot
begin to imagine how using a fairly straightforward type class that's
part of the core libraries included with the most popular compiler is
a problem.

 When you write a library for general consumption (like here), you
 should strive to have a simple and effective interface for people.

Arrows *are* a simple and effective interface. Whether they're the
best interface to choose for any specific library is a trickier
question, of course, but that's because choosing how to structure a
library interface is always difficult.

 Try to think of what's happening. Even the existence of this thread is
 surprising. Haskell programmers, and experienced ones, are discussing
 about how to express a two arguments function with arrows.
 Can you imagine a C programmer asking that? The answer would be RTFM
 or STFW, or less polite than that. And that's GOOD. You can use
 arrows because you got an useful intuition of them. Good for you.

There's only one way to express a general arrow with two inputs: Use a
tuple, because general arrows can't be curried. The discussion is
about converting a two-argument function to an arrow directly vs.
using one argument as a parameter to a function that constructs a
single-input arrow, and the only reason it's an issue is because the
syntax for supplying a constant argument to an arrow is a bit clunkier
than doing so for a function.

A better analogy might be programmers using some OO language
discussing whether some piece of usually-static data that an object
needs should be a method parameter (likely creating a bunch of
redundant code) or set just once by a constructor parameter (awkward
in those cases where it does need to change).

It is, as Sebastiaan Visser said, an engineering problem, not a
conceptual problem. Avoiding arrows would simply produce a different
set of engineering problems to consider.

 Some people argue for 2), but the research bias of the community is
 still quite strong. And you can't achieve 2) well working with a
 research methodology. For instance, somebody needs to write _complete_
 documentation (I see there is some, but it doesn't cover the basic
 questions you are discussing), intended for users, rather than papers.
 Like it happens for any other language.

I do get a little tired of finding libraries whose only documentation
consists of a couple papers, found in PDF form on the author's
university homepage (or worse, no documentation at all). But expecting
a library like HXT to walk someone through how to use libraries that
are included with GHC seems a bit unreasonable.

 Of course, nobody _has to do_ anything. I'm a PhD student, I couldn't
 work on any of this because it wouldn't count for my career. But at
 least I'm aware my work won't be usable for purpose 2). (Intermediate
 situations, like writing a paper _and_ a dumbed-down version for
 general consumption, are also possible of course).

I don't like the idea that things need to be dumbed-down for general
use. Programmers aren't stupid and they can learn new ideas. Talking
about stuff like it's some crazy incomprehensible deep magic that only
super-geniuses can understand is silly and not helpful.

...Well, that all probably came out sounding harsher than I intended,
my apologies if so. I'm just a little weary of seeing ideas like
arrows made out to be more complicated than they really are; I
honestly think at least 90% of what makes them seem difficult is
people telling each other how difficult they are!

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


Re: [Haskell-cafe] BPMN and BPEL

2010-09-08 Thread C. McCann
On Wed, Sep 8, 2010 at 3:38 PM, Hector Guilarte hector...@gmail.com wrote:
 If somebody can point out really good reasons on why I should use Haskell to
 do my work, please let me know them, they might help me convincing my
 bosses. On the other hand, if you believe Haskell is a bad language for this
 kind of task, and why C# or any other .NET language would be better, I'm
 welcome to hear your reasons, they might convince me.

Well, how comfortable are you with Haskell? If you're roughly as
proficient in it as you are in C#, you could probably bang out a
prototype using Haskell in a fraction of the time with fewer bugs.
Most software projects get massively revised from the initial version
anyway, so using a more productive language and then rewriting for the
production version can still be a net win, especially since you can
use the prototype as a specification or reference implementation
(e.g., you get some QA for free by running the two on identical input
and checking for identical output). And of course, maintenance and
scalability don't matter in a prototype.

If it goes well, you'll have proven that Haskell has value (without
forcing a long-term, up-front commitment to it), probably improved the
quality of the C# version, and gotten the chance to write Haskell at
work.

Furthermore, in this particular case, you say it's a mapper between
data description languages. While I obviously don't know the details,
applying transformations to complex, easily-inspected data structures
is a classic example of a problem ideally suited to a functional
language with pattern matching, be it Haskell, F#, or any other
ML-influenced language--thus making Haskell even more advantageous for
rapid prototyping.

Also helpful are various Haskell-inspired features added to C# in the
last few years, making it feasible to port a large subset of Haskell
to C# fairly directly.

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


Re: [Haskell-cafe] Restricted type classes

2010-09-03 Thread C. McCann
On Fri, Sep 3, 2010 at 11:47 AM, John Lato jwl...@gmail.com wrote:
 On Fri, Sep 3, 2010 at 1:29 PM, Ivan Lazar Miljenovic 
 ivan.miljeno...@gmail.com wrote:
 On 3 September 2010 22:23, John Lato jwl...@gmail.com wrote:
  Do you have a kind * implementation of Foldable?  I'd be interested in
  seeing it, because I was unable to create a usable implementation (based
  upon the RMonad scheme) on my last attempt.

 I was going to make it a subset of Foldable: fold, foldr, foldl, etc.

 So you don't have a working implementation yet?  I ended up thinking this is
 impossible, although I don't remember the reasoning that led me to that
 conclusion (and I could very well be wrong).
 I would suggest that you check this before going too far along the
 restricted-monad path.

This sounds odd to me. An RMonad-style version of Foldable is straightforward:

class RFoldable t where
rfold :: Control.RMonad.Suitable t a = (a - b - b) - b - t a - b

instance RFoldable Data.Set.Set where
rfold = Data.Set.fold

A similar class for types of kind * is also straightforward:

class Reduce t where
type Elem t
reduce :: (Elem t - r - r) - r - t - r

instance Reduce Data.ByteString.ByteString where
type Elem Data.ByteString.ByteString = Word8
reduce = Data.ByteString.foldr

Both seem to work as I'd expect. Am I missing something? Foldable is
pretty trivial--perhaps it was Traversable that you found problematic?

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


Re: [Haskell-cafe] Re: Hackage on Linux

2010-08-27 Thread C. McCann
On Fri, Aug 27, 2010 at 7:40 AM, Andrew Coppin
andrewcop...@btinternet.com wrote:
 Unfortunately, I haven't found anything for Windows yet which has syntax
 hilighting for Haskell.

 I use SciTE, which has hilighting for a bazillion languages (including XML
 and JSON), but not Haskell sadly.

Veering somewhat offtopic, but last time I checked, SciTE does have
lexer support for Haskell, it just doesn't actually include (for
unknown reasons) a language properties file to go with it. If you give
it one, syntax highlighting mostly works. You can write your own if
you like--the .properties files have a pretty simple
property.name=value syntax, which is mildly amusing in the context
of this email thread--or borrow someone else's, such as this one:
http://www4.in.tum.de/~haftmann/resources/haskell.properties A few
tweaks in the global properties are required to get everything
working--I don't remember the details, but it didn't take me long to
figure it out.

Also, on Windows, I'm aware of at least Notepad++ that has some very
basic syntax highlighting for Haskell working out of the box. It's
based on Scintilla, as well, so should feel comfortable to someone
accustomed to SciTE.

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


Re: [Haskell-cafe] Haskell and SciTE (was: Hackage on Linux)

2010-08-27 Thread C. McCann
On Fri, Aug 27, 2010 at 12:57 PM, Andrew Coppin
andrewcop...@btinternet.com wrote:
 C. McCann wrote:

 On Fri, Aug 27, 2010 at 7:40 AM, Andrew Coppin
 andrewcop...@btinternet.com wrote:


 Unfortunately, I haven't found anything for Windows yet which has syntax
 hilighting for Haskell.

 I use SciTE, which has hilighting for a bazillion languages (including
 XML
 and JSON), but not Haskell sadly.


 Veering somewhat offtopic, but last time I checked, SciTE does have
 lexer support for Haskell, it just doesn't actually include (for
 unknown reasons) a language properties file to go with it.

 OK. Well maybe it's just the version I've got then? Or maybe, as you say,
 because it's not enabled I don't know it's there.

Going by the Scintilla release history, it's been in there for about
five years, but you wouldn't find it just by using SciTE, since all
the menu options and such are controlled by the .properties files,
none of which mention Haskell...

Anyway, if the version you have is less than five years old, you
should be able to drop the file I linked to alongside the other
language files, make a few global properties changes to add Haskell to
the menus, probably a couple other minor things, and be good to go.
I'd offer more detail, but I set mine up when I first started learning
Haskell (about a year ago) and have since forgotten what needed to be
done.

 Ah yes. The reason I seldom update SciTE is that it then takes hours to put
 all the configuration back to the way I like it. (Especially if option names
 have changed or defaults are different now.)

 SciTE is a nice editor, but not especially well documented. (And, what, they
 haven't made a configuration editor yet? :-P )

Yes, well. SciTE isn't so much an editor as a bit of trivial code to
demonstrate the functionality of the Scintilla editor widget, which
people (such as myself) insist on using as if it were a proper editor.
If you want something friendlier, I'm afraid you're on your own.
Unfortunately, there don't seem to be any Haskell bindings for
Scintilla...

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


Re: [Haskell-cafe] Fwd: Semantics of iteratees, enumerators, enumeratees?

2010-08-24 Thread C. McCann
On Mon, Aug 23, 2010 at 11:41 PM, wren ng thornton w...@freegeek.org wrote:
 I believe the denotation of an iteratee is the transition function for an
 automaton (or rather a transducer). I hesitate to speculate on the specific
 kind of automaton without thinking about it, so maybe finite, maybe
 deterministic, but then again maybe not.

An iteratee is indeed an automaton, specifically one in an unknown
(but non-terminal) state. Consider the types in the iteratee
package:

newtype IterateeG c el m a = IterateeG (StreamG c el - m (IterGV c el m a))

data IterGV c el m a = Done a (StreamG c el)
 | Cont (IterateeG c el m a) (Maybe 
ErrMsg)

data StreamG c el = EOF (Maybe ErrMsg) | Chunk (c el)

Abbreviating a bit and inlining the auxiliary data types:

Iteratee c e m a = Iteratee
( Either (Maybe ErrMsg) (c e)
  - m ( Either (a, Either (Maybe ErrMsg) (c e))
(Iteratee c e m a, Maybe ErrMsg) ) )

Although the stream bits--which actually represent a single chunk of
input--are self-contained, so it might clarify things to parameterize
the iteratee over the entire chunk type, subsuming the c and e
parameters:

Iteratee s m a = Iteratee (s - m (Either (a, s) (Iteratee s m a,
Maybe ErrMsg)))

In practice you wouldn't want to do that because you want the c and
e parameters to be readily available. Perhaps a type family would
make more sense here for the type now called s? There's also the
matter of errors in the input stream, but that doesn't really impact
the underlying structure in a significant way.

We have a type parameter m :: * - *, which sounds suspiciously like
an intended monad. It's wrapping an Either value, which amounts to
just EitherT, like the one in category-extras.

Iteratee s m a = Iteratee (s - EitherT (a, s) m (Iteratee s m a,
Maybe ErrMsg))

A function to a monadic value is just a Kleisli arrow.

Iteratee s m a = Iteratee (Kleisli (EitherT (a, s) m)) s (Iteratee
s m a, Maybe ErrMsg)

Which sets things up to use the Automaton transformer in the arrows package.

Iteratee s m a = Automaton (Kleisli (EitherT (a, s) m)) s (Maybe ErrMsg)

The Automaton type describes a Mealy-style stream transducer where the
underlying arrow combines the transition function and state, and the
input and output to the arrow are the per-step input and output of the
automaton.

The iteratee automaton here produces only a stream of (Maybe ErrMsg)
as output, so it really isn't much of a transducer. EitherT describes
a computation that can be cut short, which in this case essentially
augments the automaton with an explicit halt state.

So, we have:

- An Iteratee describes a running state machine, paused at an outgoing
transition, awaiting another chunk of input.
- After receiving input, the Iteratee does one of two things:
- Halt, returning unused input and a final result value.
- Return an action in the underlying monad, containing the
post-transition state machine and an optional error message.
- The Iteratee type is parameterized by three types: a single chunk of
input, an underlying monad, and a final result value; generic iteratee
functions are thus independent of any of those.

The Enumerator types are the other half of the system: an arbitrary
data source that sits there and turns the crank, feeding in chunks of
data, until it decides to stop.

The types in the enumerator package follow almost the same scheme,
but with things rotated around a little bit: What it calls Iteratee is
a monadic action, representing a state machine paused at an ingoing
transition, which will yield either an outgoing transition function, a
halting state with a final result, or an error.

What sets an iteratee-style design apart from something conventional
based on a State monad is that the iteratee conceals its internal
state completely (in fact, there's no reason an iteratee even has to
be the same function step-to-step, or have a single consistent
state type--almost has an existential flavor, really), but is at
another function's mercy when it comes to actually doing anything.

All of which doesn't really shed too much light on the denotation of
these things, I suppose, as there's barely anything there to talk
about; the iteratee automaton itself is a terribly simple construct,
relying on an underlying monad to perform actions, on an external
push data source to recurse, and being given only bite-size chunks
of data at each step. It's little more than foldl with a pause
button attached.

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


Re: [Haskell-cafe] Fwd: Semantics of iteratees, enumerators, enumeratees?

2010-08-24 Thread C. McCann
On Tue, Aug 24, 2010 at 11:44 AM, John Lato jwl...@gmail.com wrote:
 Aren't they closer - in implementation and by supported operations -
 to resumptions monads?

 See many papers by William Harrison here:
 http://www.cs.missouri.edu/~harrisonwl/abstracts.html

 I'm not familiar with resumption monads.  I'll have to read some of the
 papers and get back to you.

From glancing at the papers myself, the concept seems quite simple.
The cheap threads paper defines a minimal resumption monad as:

data Res a = Done a | Pause (Res a)

...which is just a single value nested in a bunch of superfluous
constructors. It then parameterizes this by an arbitrary monad to
create a resumption monad transformer:

data ResT m a = Done a | Pause (m (ResT m a))

From which we can obtain an automaton with a halt state using the
reader monad, or an (Iteratee m) using (ReaderT chunk m). But this is
in fact somewhat misleading, because ResT is not actually a monad
transformer except in a trivial sense! (=) is defined for (ResT m)
as:

(Done v) = f = f v
(Pause r) = f = Pause (r = \k - return (k = f))

Which is equivalent to:

(Done v) = f = f v
(Pause r) = f = Pause (fmap (= f) r)

In other words, ResT constructs a Monad from any Functor, not just
another Monad. If memory serves me, this is actually nothing more than
the free monad of the functor.

In fact, this makes a lot more sense than my earlier reduction in
terms of an Automaton arrow: Given a chunk type c and some Functor
f, the functor composition of ((-) c) and f gives another functor,
the free monad of which is roughly an Iteratee for c and f, modulo
some details regarding error handling and returning unused input that
I don't think change the essential structure significantly.

The obvious question of what the dual of a resumption monad (and, by
extension, an Iteratee) looks like is simple enough. The minimal
resumption monad is the free monad of Identity; the cofree comonad of
Identity is an infinite stream of values. An Iteratee is an automaton
built from functor composition with Reader; the cofree comonad of the
same also gives an automaton, but one with no halting state that
produces an output immediately at each step based on the current
state, akin to a Moore-style machine instead of the Mealy-style
Automaton arrow. Being a source of data, either form of co-resumption
comonad would probably make a serviceable Enumerator type, given some
recursive driver function that pulls data from the stream and stuffs
it into the Iteratee.

All of which leads me to suspect that any implementation of Iteratees
could probably be replaced by category-extras and about eleven lines
of zygohistomorphic prepromorphisms or whatever.

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


Re: [Haskell-cafe] the overlapping instance that wasn't?

2010-08-24 Thread C. McCann
On Tue, Aug 24, 2010 at 4:42 PM, Michael Vanier mvanie...@gmail.com wrote:
 Adding OverlappingInstances to the language pragmas fixes the problem.  My
 question is: why is this an overlapping instance?  It would make sense if
 Int was an instance of Nat, but it isn't.  Is this just a limitation in the
 way overlapping instances are identified?

The problem is that instance selection doesn't work the (obvious,
seemingly-sensible) way you thought it did. In short, instance
contexts are only examined after the fact; your second instance
describes an instance of Show for *all* n, which of course overlaps
absolutely everything. Only after selecting a uniquely matching
instance (or, with OverlappingInstances, the best match in some
sense) are instance contexts taken into consideration, potentially
causing a compilation error if the context isn't satisfied, but not
discarding the instance and looking for another one instead.

The reason it works this way has to do with the nature of type classes
being open. By analogy, imagine a hypothetical extension that allows
a function to be defined across multiple modules, with new equations
for the function added anywhere, no defined ordering of equations, and
equations for such a function automatically brought into scope by
importing a module defining one (even if nothing else in the module
is), with the particular expression to evaluate being chosen at
runtime by pattern matching with all the equations that are in scope.

Now add another extension that allows a single argument to match the
patterns for multiple equations for a function, with the compiler
magically deciding whether, say, ([Just 5, Nothing], _) is a better
match than ((x:_), []). That's OverlappingInstances, and if it doesn't
make your skin crawl a little bit it probably should!

There are assorted tricks and hacks with overlapping instances to
accomplish various feats of type metaprogramming (usually also
involving undecidable instances, which are arguably less unnerving
than overlapping), for which the best textbook is probably Oleg's
website. It's unfortunately the case that a lot of useful things would
require data kinds and/or closed type classes; lacking those,
overlapping instances let you fake most of it with only minor loss of
sanity points. Fortunately, you don't need to worry about any of that
for your particular problem here.

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


Re: [Haskell-cafe] More Flexible Monad Transformer OR Bad Coding Style

2010-08-09 Thread C. McCann
On Mon, Aug 9, 2010 at 3:42 PM, Job Vranish job.vran...@gmail.com wrote:
 For monads like StateT, WriterT, ReaderT, the order doesn't matter (except
 perhaps for some pesky performance details). However, for monad transformers
 like ErrorT or ListT, the order _does_ matter.

Is it really correct to say that order doesn't matter for the
transformers you mention? More precise would be to say that order
doesn't matter when two or more of those are stacked *consecutively*.
Unless a function is completely independent of what other functions do
with the state values, it can matter a great deal what order two State
transformers occur in if there happens to be a ContT sandwiched
between them. Furthermore, MonadState doesn't even promise that much;
an arbitrary transformer that provides state operations may not
commute generally with a StateT. Imagine, for instance, a state
transformer augmented with error checking and transactions, that rolls
back to a checkpoint if something 'put's an invalid state value.

A polymorphic function with multiple monad typeclasses is thus
effectively asserting that it does something sensible and well-defined
for any set of transformers providing those classes, for any ordering
of those transformers in the stack, and with any other possible
transformers inside, outside, or amidst them. Combinatorics are not
your friend here.

Monad transformer polymorphism leads all too easily into a pit of
despair. Don't go there unwisely.

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


Re: [Haskell-cafe] Comments on Haskell 2010 Report

2010-07-12 Thread C. McCann
On Sat, Jul 10, 2010 at 6:40 PM, Julian Fleischer
julian.fleisc...@fu-berlin.de wrote:
 I guess I'm actually messing things up using the word natural - how can 
 expand the multiplication of zero with itself zero times be natural?

How could it not be?

That is to say, what initial value would make sense for folding (*)
over a list of numbers to compute the product?

- C.

p.s. -- [[mconcat]] = [[foldr mappend mempty]]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] checking types with type families

2010-07-07 Thread C. McCann
On Sat, Jul 3, 2010 at 4:28 PM, Dan Doel dan.d...@gmail.com wrote:
 It's potentially not just a violation of intent, but of soundness. The
 following code doesn't actually work, but one could imagine it working:

  class C a b | a - b

  instance C () a

  -- Theoretically works because C a b, C a c implies that b ~ c
  --
  -- GHC says b doesn't match c, though.
  f :: (C a b, C a c) = a - (b - r) - c - r
  f x g y = g y

The funny part is that GHC eventually would decide they match, but not
until after it complains about (g y). For instance, if you do this:

f :: (C a b, C a c) = a - (b - r) - c - r
f x g y = undefined

...and load it into GHCi, it says the type is:

 :t f
f :: (C a c) = a - (c - r) - c - r

As far as I can tell, type variables in scope simultaneously that
should be equal because of fundeps will eventually be unified, but
too late to make use of it without using some sort of type class-based
indirection. This can lead to interesting results when combined with
UndecidableInstances. For instance, consider the following:

class C a b c | a b - c where
c :: a - c - c
c = flip const

instance C () b (c, c)

f x = (c x ('a', 'b'), c x (True, False))

g :: (c, c) - (c, c)
g = c ()

This works fine: Because b remains ambiguous, the c parameters
also remain distinct; yet for the same reason, a effectively
determines c anyway, such that g ends up with the type (forall c.
(c, c) - (c, c)), rather than something like (forall c. c - c) or
(forall b c. (C () b c) = c - c). But if we remove the (seemingly
unused) parameter b from the fundep...

class C a b c | a - c where

...GHC now, understandably enough, complains that it can't match Char
with Bool. It will still accept this:

f x = c x ('a', 'b')
g x = c x (True, False)

...but not if you add this as well:

h x = (f x, g x)

Or even this:

h = (f (), g ())

On the other hand, this is still A-OK:

f = c () ('a', 'b')
g = c () (True, False)

h = (f, g)

Note that all of the above is without venturing into the
OverlappingInstances pit of despair.

I don't know if this is how people expect this stuff to work, but I've
made occasional use of it--introducing a spurious parameter in order
to have a fundep that uniquely determines a polymorphic type. Perhaps
there's a better way to do that?

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


Re: [Haskell-cafe] Type-Level Programming

2010-06-26 Thread C. McCann
On Sat, Jun 26, 2010 at 3:27 AM, Jason Dagit da...@codersbase.com wrote:
 The types can depend on values.  For example, have you ever notice we have
 families of functions in Haskell like zip, zip3, zip4, ..., and liftM,
 liftM2, ...?
 Each of them has a type that fits into a pattern, mainly the arity
 increases.  Now imagine if you could pass a natural number to them and have
 the type change based on that instead of making new versions and
 incrementing the name.  That of course, is only the tip of the iceberg.

That's also a degenerate example, because it doesn't actually require
dependent types. What you have here are types dependent on *numbers*,
not *values* specifically. That type numbers are rarely built into
non-dependently-typed languages is another matter; encoding numbers
(inefficiently) as types is mind-numbingly simple in Haskell, not
requiring even any exciting GHC extensions (although encoding
arithmetic on those numbers will soon pile the extensions on).

Furthermore, families of functions of the flavor you describe are
doubly degenerate examples: The simplest encoding for type numbers are
the good old Peano numerals, expressed as nested type constructors
like Z, S Z, S (S Z), and so on... but the arity of a function is
*already* expressed as nested type constructors like [b] - ([a] -
[(b, a)]), [c] - ([b] - ([a] -[(c,b, a)])), and such! The only
complication here is that the zero type changes for each number[0],
but in a very practical sense these functions already encode type
numbers.

Many alleged uses for dependent types are similarly trivial--using
them only as a shortcut for doing term-like computations on types.
With sufficient sweat, tears, and GHC extensions, most if not all of
said degenerate examples can be encoded directly at the type level.

For those following along at home, here's a quick cheat-sheet on
playing with type programs in GHC:
- Type constructors build new type values
- Type classes in general associate types with term values inhabiting them
- Type families and MPTCs with fundeps provide functions on types
- When an instance is selected, everything in its context is evaluated
- Instance selection that depends on the result of another type
function provides a sort of lazy evaluation (useful for control
structures)
- Getting anything interesting done usually needs UndecidableInstances
plus Oleg's TypeEq and TypeCast classes

Standard polymorphism also involves functions on types in a sense, but
doesn't allow computation on them. As a crude analogy, one could think
of type classes as allowing pattern matching on types, whereas
parametric polymorphism can only bind types to generic variables
without inspecting constructors.

  Haskell's type system is sufficiently expressive that we can encode many
 instances of dependent types by doing some extra work.

Encoding *actual* instances of dependent types in some fashion is
indeed possible, but it's a bit trickier. The examples you cite deal
largely with making the  degenerate cases more pleasant to work with;
the paper by a charming bit of Church-ish encoding that weaves the
desired number-indexed function right into the definition of the zero
and successor, and she... well, she's a sight to behold to be sure,
but at the end of the day she's not really doing all that much either.

Since any value knowable at compile-time can be lifted to the type
level one way or another, non-trivial faux-dependent types must depend
on values not known until run-time--which of course means that the
exact type will be unknown until run-time as well, i.e., an
existential type. For instance, Oleg's uses of existential types to
provide static guarantees about some property of run-time values[1]
can usually be reinterpreted as a rather roundabout way of replicating
something most naturally expressed by actual dependent types.

Which isn't to say that type-level programming isn't useful, of
course--just that if you know the actual type at compile-time, you
don't really need dependent types.

- C.

[0] This is largely because of how Haskell handles tuples--the result
of a zipN function is actually another type number, not a zero, but
there's no simple way to find the successor of a tuple. More sensible,
from a number types perspective, would be to construct tuples using ()
as zero and (_, n) as successor. This would give us zip0 :: [()], zip1
:: [a] - [(a, ())], zip2 :: [b] - ([a] - [(b, (a, ()))]), and so
on. The liftM and zipWith functions avoid this issue.
[1] See http://okmij.org/ftp/Haskell/types.html#branding and
http://okmij.org/ftp/Haskell/regions.html for instance.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type-Level Programming

2010-06-26 Thread C. McCann
On Sat, Jun 26, 2010 at 6:55 PM, Erik de Castro Lopo
mle...@mega-nerd.com wrote:
 One problem with dependent types as I understand it is that type
 inference is not guaranteed to terminate.

Full type inference is undecidable in most interesting type systems
anyway. It's possible for the simply-typed λ-calculus, but the best
you can do beyond that is probably the Damas/Hindley/Milner algorithm
which covers a (rather useful) subset of System F. This is the heart
of Haskell's type inference, but some GHC extensions make type
inference undecidable, such as RankNTypes.

Type inference being undecidable is only a problem insofar as it
requires adding explicit type annotations until the remaining types
can be inferred.

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


Re: [Haskell-cafe] Re: How does one get off haskell?

2010-06-18 Thread C. McCann
On Fri, Jun 18, 2010 at 8:37 AM, Daniel Fischer
daniel.is.fisc...@web.de wrote:
 Haven't you heard?  Enough unit tests give you almost the same security
 as a good static type system at the expense of more code!

 Uh, wait, why is that an advantage again? :p

 Duh, because it's much faster to develop in a dynamically typed language.
 Writing out all those type signatures costs time. Much more time than
 writing a few dozen unit tests per function, right?

That's... not really fair. A static type system DOES impose
limitations, and arguing with the compiler about whether some code is
acceptable does take time. Even a handful of simple unit tests will
catch the majority of possible errors, and things that require deep
metaprogramming wizardry in Haskell can be stupidly trivial in
something like Ruby. If writing something in Haskell would mean ten
lines of metaprogramming and type signatures for every single line of
code, but a few unit tests and some quick-and-dirty Python would
provide acceptable results, I'd go with the latter.

The better question is when do the benefits of static typing outweigh
the costs imposed?. If you're using Java, the answer is probably
never, but even in Haskell I don't think the answer is quite
always.

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


Re: [Haskell-cafe] A question on existential types and Church encoding

2010-06-01 Thread C. McCann
On Tue, Jun 1, 2010 at 3:40 PM, Cory Knapp cory.m.kn...@gmail.com wrote:
 In the new type, the parameter 'a' is misleading. It has no connection to
 the
 'a's on the right of the equals sign. You might as well write:

  type CB = forall a. a - a - a

 Ah! That makes sense. Which raises a new question: Is this type too
 general? Are there functiosn which are semantically non-boolean which fit
 in that type, and would this still be the case with your other suggestion
 (i.e. cand p q = p (q t f) f )?

Because the type is universally quantified, any function with that
signature can only manipulate the values it's given, having no way of
creating new values of that type, or inspecting them in any way. It
receives two values and returns one, so (ignoring _|_) only two
implementations are possible: (\x _ - x) and (\_ x - x), which are
the Church booleans. Intuitively, observe that the function must, and
may only, make a decision between two options--thus providing exactly
one bit of information, no more and no less.

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


Re: [Haskell-cafe] Why Either = Left | Right instead of something like Result = Success | Failure

2010-05-27 Thread C. McCann
On Thu, May 27, 2010 at 10:25 AM, Ionut G. Stan ionut.g.s...@gmail.com wrote:
 I was just wondering if there's any particular reason for which the two
 constructors of the Either data type are named Left and Right. I'm thinking
 that something like Success | Failure or Right | Wrong would have been a
 little better.

Because that would confuse matters when using the type for something
other than representing success or failure.

Either is a generic sum type. That is, Either A B only means either
you have an A, or you have a B. Use of Left to represent failure is
merely a matter of convention. Similarly, the generic product type in
Haskell is the 2-tuple--(A, B) only means you have both an A and a
B.

Left and Right work well because they don't carry much extra semantic
baggage, and they make it easy to remember which type parameter goes
with which constructor. Other than the mnemonic value, something even
more bland like This and That would work as well.

Personally, I advocate instead using Sinister and Dexter. Nice and
catchy, don't you think?

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


Re: [Haskell-cafe] Chuch encoding of data structures in Haskell

2010-05-27 Thread C. McCann
2010/5/27 Günther Schmidt gue.schm...@web.de:
 I'm exploring the use of church encodings of algebraic data types in
 Haskell.
 Since it's hard to imagine being the first to do so I wonder if folks here
 could point me to some references on the subject.

 I'm looking for examples of church encodings in Haskell a little bit beyond
 Church Booleans and Church Numerals.

The fully general description of Church encoding is rather simple, but
I've rarely seen it described explicitly. Consider the type of Church
encodings for Bool, Either, and the 2-tuple (written here as Pair
for clarity):

churchedBool :: t - t - t
churchedEither :: (a - t) - (b - t) - t
churchedPair :: (a - b - t) - t

And compare the signatures for the constructors of the non-Church encoded types:

True :: Bool
False :: Bool
Left :: a - Either a b
Right :: b - Either a b
Pair :: a - b - Pair a b

We can observe two patterns: 1) The Church encodings take as many
arguments as the type has constructors 2) The type of each argument is
the same as the signature of a constructor, except returning an
arbitrary type. As this suggests, Church decoding is as simple as
applying the Church encoded type to each of the constructors.

From the above, a general description of Church encoding can be
deduced: The encoding of a value is a function that replaces each data
constructor with an arbitrary function. The Church encoding
represents, in a way, the most generalized means of using values of
that type--which is why Haskell already includes variations of Church
encode functions for a few standard types, like so:

encodeEither x = \f g - either f g x
encodeMaybe x = \z f - maybe z f x
encodeTuple x = \f - uncurry f x
encodeBool x = \t e - if x then t else e

But what of Church numerals? First, we must consider the
Church-encoding of recursive data types. Given arbitrary nested data
types, there's nothing else that can be done--the outer types know
nothing of the types they contain. But if an inner type is known to be
the same as the outer type, there are two options for the encoding:
Work only with the outermost value, as with non-recursive types, or
work with the recursive value as a whole, by having the outermost
value pass its arguments inward.

Now, consider the signature of a Church numeral:

churchedNumeral :: (t - t) - t - t

Given the above, what can we say about the equivalent decoded data
type? It takes two arguments, so we have two constructors. The second
argument is a single value, so the associated constructor is nullary.
The first argument must be associated with a unary constructor, but
look at the parameter it takes: the same type as the result! This is
how we can tell that Church numerals are the encoding of a recursive
type. Since the only way a recursive constructor can do anything with
the values it contains is to pass its arguments inward, the value it
has to work with is the result of doing so. Thus, the other
constructor must take a single argument of its own type. What does
this look like as a standard data type?

data Nat = S Nat | Z

Good old inefficient Peano numbers, of course!

Keeping all that in mind, consider a List type, and both ways of encoding it:

data List a = Nil | Cons a (List a)

churchedListOuter :: t - (a - ___ - t) - t
churchedListRecursive :: t - (a - t - t) - t

For the outermost method, what type belongs in place of the ___? The
second argument of Cons is itself a List, so naively we would like to
simply put the type of churchedListOuter itself in place of ___, but
that won't work. In fact, nothing will work here, because recursion on
an outermost encoded list is impossible in a typed λ-calculus
without some means of using general recursion provided as a primitive
operation. Nested tuples can be used, but the length of the list will
be reflected in the type, preventing polymorphism over arbitrary
lists. This is also why Church encoding is most often seen in the
setting of the untyped λ-calculus.

The implicitly recursive encoding, however, presents no such problems.
So, perhaps a function to Church encode lists would be useful? Indeed
it would, and as before, it already exists:

encodeList x = \z f - foldr f z x

Recall the earlier observation that decoding involves applying the
encoded type to its equivalent constructors; the same holds true for
recursive types, as demonstrated by right-folding a list with (:) and
[], or applying a Church numeral to 0 and (+ 1).

Regarding recursive data types as the least fixed point of a
non-recursive data type is thus tied to replacing the outermost
encoding with the recursive encoding, and the Church encode
function for a recursive type is simply a generalized right fold,
partially applied.

Now, the descriptions above are rather informal, and ignore the
possibility of infinite lazy recursive data structures, among other
gaps; but perhaps will help to get you started regardless.

- C.
___
Haskell-Cafe mailing list

Re: [Haskell-cafe] Re: Chuch encoding of data structures in Haskell

2010-05-27 Thread C. McCann
On Thu, May 27, 2010 at 9:11 PM, Stefan Monnier
monn...@iro.umontreal.ca wrote:
 I.e. to make such an encoding really usable, you need deep
 polymorphism (which GHC supports just fine, but which is not part of
 the Haskell standard).

Ah, yes, and thank you for pointing that out. My message involved a
great deal of hand-waving that I neglected to clearly identify as
such. The same caveat of course applies to most Church encodings. For
instance, the proper type of a (recursive) encoded list would be:

type ChurchList a = ∀t. t - (a - t - t) - t

...where a is fixed as the type of the list elements. Thus, cons
ought to look something like this charming type:

cons :: ∀a. a - (∀t. t - (a - t - t) - t) - (∀t. t - (a - t - t) - t)

For extra fun, try writing an instance such as:

instance (Show a) = Show (ChurchList a) where [...etc.]

...at which point, perhaps, we remind ourselves that the language is
named Haskell, not Alonzo, and drop the whole matter.

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


Re: [Haskell] Re: [Haskell-cafe] Work on Video Games in Haskell

2010-05-26 Thread C. McCann
On Wed, May 26, 2010 at 11:01 PM, Ben Lippmeier b...@ouroborus.net wrote:
 While we can all acknowledge the technical impossibility of identifying the 
 original source language of a piece of code...


 Uh,

∀p (PieceOfCode(p) - CanIdentifySourceLanguage(p))

is clearly false, while

∃p (PieceOfCode(p) - CanIdentifySourceLanguage(p))

is clearly true.

Natural language does a rather poor job of making quantification unambiguous.

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


Re: [Haskell-cafe] Haskell, Queries and Monad Comprehension

2010-05-24 Thread C. McCann
2010/5/23 Günther Schmidt gue.schm...@web.de:
 is there anybody currently using Haskell to construct or implement a query
 language?

I've a half-baked, type-indexed (in HList style) implementation of
relational algebra lying around somewhere, if that counts as a query
language. I was experimenting with using it as a sort of abstract
collection interface, which actually worked rather nicely I think, but
I didn't have time to flesh it out completely. In particular, only
very simple queries and limited kinds of relation composition were
supported. Definitely just toy code, though, and dreadfully
inefficient; if you're looking for an actual implementation meaning
usable interface to an external persistence layer then disregard
this.

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


Re: [Haskell-cafe] ambiguous type variable problem when using forall, multiparameter type classes, and constraints on polymorphic values (and syb-with-class)

2010-05-21 Thread C. McCann
On Fri, May 21, 2010 at 12:30 PM, Jeremy Shaw jer...@n-heptane.com wrote:
 Adding all the scoped type variable stuff does not seem to help. Alas,
 I can not figure out if this is a limitation of the type-checker, or
 something that is fundamentally impossible. Nor can I figure out how
 to work around the issue.

It's either one, depending on how you look at. To explain:

 The problem I have is when I try to add an additional constraint on 'm',
 such as (Monad m) =

 -- bar2 :: forall a m r. (Monad m, Data (Foo m) a, Num r) = a - r
 -- bar2 x = sum $ gmapQ (undefined :: Proxy (Foo m)) (bar2 :: forall b.
 (Monad m, Data (Foo m) b, Num r) = b - r) x

How might the compiler decide what specific m is meant when this
function is called, so that it can make sure that it's always a Monad?
All it has to work with are a and r. The only connection to m is
via the Data instance, but the second parameter to Data alone is not
really sufficient to find a specific instance--in fact, there could
well be multiple such instances.

 bar1 :: forall a m r. (Data (Foo m) a, Num r) = a - r
 bar1 x = sum $ gmapQ (undefined :: Proxy (Foo m)) bar1 x

Note that m is actually ambiguous here as well, but GHC won't
complain until it needs to care about the specific type. If everything
looks fully polymorphic GHC will just shrug, but by adding a class
constraint to the definition's context, you force the issue.

A classic, minimalist example of this problem--class constraints on
types that don't appear in the function signature--is the function
show . read. The type is just  String - String, but the behavior
depends on an unknown intermediate type.

 In my real code I need to define the data instance like:

 -- instance (Monad m) = Data (Foo m) a

 Which, by itself is fine. But that results in my needing to add (Monad
 m) to the 'bar' function. And that is what I can't figure out how to
 do..

The question you should answer first is: How do you expect the bar
function to know which monad to use--or, if it doesn't matter which
monad it picks, why do you care that it's given a monad at all?

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


Re: [Haskell-cafe] Proposal to solve Haskell's MPTC dilemma

2010-05-20 Thread C. McCann
On Thu, May 20, 2010 at 12:25 PM, Max Bolingbroke
batterseapo...@hotmail.com wrote:
 Available instances are not a natural addition to this list. In
 particular, using that information can cause programs to become
 untypeable when the module or *any module it imports transitively*
 defines a new instance. This leads to programs that are extremely
 fragile in the face of changes in the libraries!

This is an unavoidable consequence of MPTCs being open, is it not? If
data types or function declarations permitted the post facto addition
of new constructors or pattern matches, similar headaches would ensue
due to non-locality of transitive propagation. Clearly open type
classes are useful; open data types and functions would be useful as
well, actually, but it would be madness to permit *only* open
declarations. Yet, that is the situation with type classes.

I wonder: Of cases where overload resolution via available instances
would be reasonable, how many would also make sense as a closed type
class? By comparison, it seems that many uses of OverlappingInstances
are really just trying to express a closed type class with one or more
default instances, akin to functions with _ patterns. I think, though
I'm not certain, that both would be straightforward and non-fragile
for a closed type class.

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


Re: [Haskell-cafe] Re: What makes Haskell difficult as .NET?

2010-05-14 Thread C. McCann
On Fri, May 14, 2010 at 8:39 PM, Maciej Piechotka uzytkown...@gmail.com wrote:
 1. Haskell Class/Type famillies/... are conceptually different then
 classes and interfaces.

I believe interfaces would be roughly equivalent to the subset of
single-parameter type classes such that:
  - All type class methods are functions
  - The first argument of each function is the class's type parameter,
fully applied to any type parameters it needs
  - The class's type parameter appears nowhere else

Painfully limited, but better than nothing. This would mostly make it
problematic to export Haskell functions with type class constraints to
other .NET languages, though. I suspect large sections of the .NET
libraries could be expressed in Haskell without too much trouble
(well, besides everything being in IO), except that getting Haskell to
interact nicely with the concept of subtyping in inheritance
hierarchies might be awkward. Also potentially problematic is that (if
memory serves me) .NET can only handle type parameters with kind *,
which excludes types parameterized by type constructors, such as monad
transformers.

Irritatingly, a lot of stuff in the .NET framework is almost, but not
quite, equivalent to some really key bits of Haskell. For instance,
Enumerable.SelectA,B(IEnumerableA, FuncA,B) is almost fmap, but
returns an existential type instead. I guess IEnumerableT is
something akin to Foldable, with cheap kludgy imitations of fmap and
(=) bolted on after the fact.

Explicit type checks might be necessary in places as well, to deal
with .NET's feeble and unreliable type system. Some boilerplate
involving Data.Typeable/Data.Dynamic ought to suffice.

 2. As .Net does not differentiate between IO a and a Haskell cannot feel
 completely native (hand-made FFI or everything in IO)

Wouldn't be any worse than using most C bindings in Haskell as is. Or
using a lot of .NET libraries in F#, to be honest, if you try to write
functional-idiomatic instead of quasi-imperative code.

Though, considering the near-omnipresent possibility of null
references, most .NET functions would actually need to return
something of the form IO (Maybe a).

 3. .Net does differentiate between variables and functions with 0
 arguments.

Yes, though the latter are easy enough to use. Property getters are
nullary functions, likewise the FuncTResult delegate type. You can
even write nullary lambda expressions as () = ..., though nullary
lambda abstraction is kind of a contradiction in terms.

A combination of a nullary pure function and a mutable static variable
to cache the result of evaluating it would provide something similar
to lazy terms in Haskell.

 4. .Net types are not lazy. String is not [Char]. Arrays are used in
 many places.

On the other hand, many of the hot new features on the .NET platform
are built around lazy collections with IEnumerableT, which is
primarily used as if it were the list monad (e.g., LINQ syntax being
sort of a monad comprehension).

In summary: So close, yet so far. It'd probably work just well enough
to be viable, but be too painful to be enjoyable. I use C# at the
day job, so I notice these things often...

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


Re: [Haskell-cafe] Functions of type foo :: f a - g a

2010-05-11 Thread C. McCann
On Tue, May 11, 2010 at 2:06 PM, John Meacham j...@repetae.net wrote:
 A better way might be

 class (Functor f, Functor g) = FunctorPair f g where
        transformFunctor :: f a - g a

 though, I am not sure what your use is, there isn't an obvious instance
 to me, but I don't know what your motivating task is.

Furthermore, to select an instance at this point both Functors must be
known in context of use, which exhausts pretty much the entire
informational content of the instance--raising the question of what
benefit is drawn from a type class at all, as opposed to simply
passing around functions of type f a - g a as needed. Consider that
fmap doesn't require a multi-parameter type class for each pair a, b,
it just takes a function (a - b).

The only way a type class would make sense here, I think, is with a
fundep uniquely determining a particular natural transformation based
on one of the Functors, at which point I'm not sure that the concept
of natural transformation is what you're actually trying to model.

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