Re: [Haskell-cafe] [Alternative] change some/many semantics

2011-12-21 Thread wren ng thornton

On 12/19/11 10:20 PM, David Menendez wrote:

On Mon, Dec 19, 2011 at 6:37 PM, wren ng thorntonw...@freegeek.org  wrote:

On 12/14/11 10:58 PM, Gregory Crosswhite wrote:


Of course, this is not a simple change at all because it would have to
be done in such a way as to respect the ordering of actions --- that
is, we can't have each action executed only when the corresponding
element of the list demanded is forced, or else actions would
undesirably interleave.


Therein lies the issue. To put this in a monadic context, this is the same
reason why we can't just say:

evalState (repeatM getNext) init

e.g., to generate an infinite list of pseudorandom numbers and then discard
the final seed because we have all the numbers we'll ever need.


Sure you can. Just make sure you're using a non-strict state monad.


Fair enough. I over-simplified the example I had in mind, which cannot 
be evaded so easily.


Though it's worth pointing out that your solution relies on the specific 
property I mentioned (later in the same email), namely that it is safe 
to perform the evaluation of lazy state at any point we desire, because 
it will not interact with other side-effects[1]. Thus, this happens to 
be one of the monads which has the property necessary for being able to 
perform the reordering desired by the OP. However, if we try using your 
'repeatM' for other monads it is unlikely to work--- and for the same 
reasons that 'many' and 'some' are problematic for Maybe and lists.



[1] Barring side-effects which perform introspection on the runtime 
system (e.g., to determine current memory usage, whether a thunk has 
been forced or not, etc.).


--
Live well,
~wren

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


Re: [Haskell-cafe] [Alternative] change some/many semantics

2011-12-21 Thread David Menendez
On Wed, Dec 21, 2011 at 12:37 PM, wren ng thornton w...@freegeek.org wrote:
 On 12/19/11 10:20 PM, David Menendez wrote:

 On Mon, Dec 19, 2011 at 6:37 PM, wren ng thorntonw...@freegeek.org
  wrote:

 On 12/14/11 10:58 PM, Gregory Crosswhite wrote:


 Of course, this is not a simple change at all because it would have to
 be done in such a way as to respect the ordering of actions --- that
 is, we can't have each action executed only when the corresponding
 element of the list demanded is forced, or else actions would
 undesirably interleave.


 Therein lies the issue. To put this in a monadic context, this is the
 same
 reason why we can't just say:

    evalState (repeatM getNext) init

 e.g., to generate an infinite list of pseudorandom numbers and then
 discard
 the final seed because we have all the numbers we'll ever need.


 Sure you can. Just make sure you're using a non-strict state monad.


 Fair enough. I over-simplified the example I had in mind, which cannot be
 evaded so easily.

 Though it's worth pointing out that your solution relies on the specific
 property I mentioned (later in the same email), namely that it is safe to
 perform the evaluation of lazy state at any point we desire, because it will
 not interact with other side-effects[1]. Thus, this happens to be one of the
 monads which has the property necessary for being able to perform the
 reordering desired by the OP. However, if we try using your 'repeatM' for
 other monads it is unlikely to work--- and for the same reasons that 'many'
 and 'some' are problematic for Maybe and lists.

Yes, sequence . repeat is only sensible for non-strict monads, which
are fairly uncommon. (Identity, State, Reader, Writer, infinite
search, and various combinations thereof are the only ones I'm aware
of.) The situation is exactly analogous to many and some, which are
only meaningful for certain values in certain types, as well as to
functions like fix and folder, which can diverge if given
inappropriate arguments.

If there were a lot of code that was (1) meaningfully generic over
non-strict monads and (2) diverged for strict monads, it might make
sense to declare a subclass and restrict those functions to non-strict
monads. That won't stop someone from trying to call sequence on an
infinite list, but it does express an important precondition of the
code in the type.


-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/

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


Re: [Haskell-cafe] [Alternative] change some/many semantics

2011-12-19 Thread wren ng thornton

On 12/14/11 10:58 PM, Gregory Crosswhite wrote:

Of course, this is not a simple change at all because it would have to
be done in such a way as to respect the ordering of actions --- that
is, we can't have each action executed only when the corresponding
element of the list demanded is forced, or else actions would
undesirably interleave.


Therein lies the issue. To put this in a monadic context, this is the 
same reason why we can't just say:


evalState (repeatM getNext) init

e.g., to generate an infinite list of pseudorandom numbers and then 
discard the final seed because we have all the numbers we'll ever need. 
Hidden lurking in this expression is the fact that the state being 
passed around eventually becomes bottom. We don't especially care, since 
evalState is discarding the state, but the fact remains that we have to 
compute it. Indeed, we can't even define 'repeatM' sensibly, for the 
same reason.


We can only compute a list of responses lazily if we happen to be in a 
monad/applicative where we can guarantee that pulling all the effects up 
to the top is equivalent to performing them lazily/interleaved. However, 
even in the cases where that can be guaranteed, we don't have any 
especially good mechanism for informing GHC about that fact.


The reason why 'some' and 'many' can escape this ---in the case of 
parsers at least--- is that they will run for a (deterministic) fixed 
length of time and then return. If you're parsing any finite-length 
text, then there's an upper bound on how many times the action can run 
before it fails. This is the same reason why we can define 'replicateM' 
even though we can't define 'repeatM'. The only difference is that with 
'replicateM' the termination criterion is extrinsic to the monad (it's 
induction on Int), whereas with 'some' and 'many' the termination 
criterion is intrinsic to whatever the side-effects of the action are. 
The problem is that for Maybe and lists, there is no intrinsic state 
which would allow an action to succeed sometimes and fail other times 
(thereby providing an intrinsic means for termination).


--
Live well,
~wren

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


Re: [Haskell-cafe] [Alternative] change some/many semantics

2011-12-19 Thread wren ng thornton

On 12/15/11 8:26 AM, Gregory Crosswhite wrote:

Put another way, the problem with Maybe computations is that if there
is a failure at any point in the computation than *the entire
computation fails*, and this means that you can't lazily generate a
list of results using some/many because you can't tell whether your
computation was a success or a failure until the entire infinite
computation has been run;


exactamente.

--
Live well,
~wren

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


Re: [Haskell-cafe] [Alternative] change some/many semantics

2011-12-19 Thread David Menendez
On Mon, Dec 19, 2011 at 6:37 PM, wren ng thornton w...@freegeek.org wrote:
 On 12/14/11 10:58 PM, Gregory Crosswhite wrote:

 Of course, this is not a simple change at all because it would have to
 be done in such a way as to respect the ordering of actions --- that
 is, we can't have each action executed only when the corresponding
 element of the list demanded is forced, or else actions would
 undesirably interleave.


 Therein lies the issue. To put this in a monadic context, this is the same
 reason why we can't just say:

    evalState (repeatM getNext) init

 e.g., to generate an infinite list of pseudorandom numbers and then discard
 the final seed because we have all the numbers we'll ever need.

Sure you can. Just make sure you're using a non-strict state monad.

import Control.Monad.Identity
import Control.Monad.State.Lazy
import System.Random

repeatM :: Monad m = m a - m [a]
repeatM = sequence . repeat

nextM :: RandomGen g = StateT g Identity Int
nextM = StateT $ Identity . next

*Main g - getStdGen
*Main let ints = runIdentity $ evalStateT (repeatM nextM) g
*Main :t ints
ints :: [Int]
*Main take 5 ints
[1259974427,117524251,96384700,1814821362,997859942]
*Main take 10 ints
[1259974427,117524251,96384700,1814821362,997859942,2058526379,835643552,1075525457,727974455,388071455]
*Main ints !! 100
271901956


-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/

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


Re: [Haskell-cafe] [Alternative] change some/many semantics

2011-12-15 Thread Gregory Crosswhite

On Dec 15, 2011, at 5:40 PM, Antoine Latter wrote:

 I said 'combinators', not 'instances'.

Oh!  Okay, that was my bad then.

 A lot of popular parsers
 combinators can be written exclusively from (|) and empty, but make
 little sense for List and Maybe, and may not even function properly.
 The 'trifecta' package includes a nice reference:
 
 http://hackage.haskell.org/packages/archive/trifecta/0.49.1/doc/html/Text-Trifecta-Parser-Combinators.html
 
 See 'skipSome' through 'chainr1' - I wouldn't be surprised if most of
 these lead to the same infinite loop behavior for Maybe as the stock
 'many' and 'some' in base.
 
 These sorts of functions are what Alternative is for.

Okay, I see better now what you mean.  Thank you.

But then, if so much code based on Alternative makes little sense for List and 
Maybe, then maybe this should be a signal they we should remove their instance 
from Alternative?  After all, we already have the Monad typeclass which gives 
them essentially the same functionality.

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


Re: [Haskell-cafe] [Alternative] change some/many semantics

2011-12-15 Thread Gregory Crosswhite

On Dec 15, 2011, at 6:19 PM, Gregory Crosswhite wrote:

 After all, we already have the Monad typeclass which gives them essentially 
 the same functionality.

Make that the *Monoid* typeclass.  :-)

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


Re: [Haskell-cafe] [Alternative] change some/many semantics

2011-12-15 Thread Antoine Latter
On Thu, Dec 15, 2011 at 2:20 AM, Gregory Crosswhite
gcrosswh...@gmail.com wrote:

 On Dec 15, 2011, at 6:19 PM, Gregory Crosswhite wrote:

 After all, we already have the Monad typeclass which gives them essentially
 the same functionality.


 Make that the *Monoid* typeclass.  :-)

And this is an interesting discussion all of its own!

Should the monoid instance of a Functor do what List does - which is
analogious to its append or choice operation (where applicable), or
should it do what Maybe does, which is lift the operation into its
contained type? (That is, (Just x) `mappend` (Just y) == Just (x
`mappend` y)).

Since the Monoid instance for Maybe doesn't offer choice between
Nothing and Some, it would be nice to have a standard choice operation
that we could use for Maybe.

Which is sort of what Alternative is - offering choice over a functor
which supports it. Except that the notion of what choice means is
richer in a parser than in Maybe (parsers may backtrack (like List)
and parsing has some sort of stateful effect, which affects the
success of future parses).

It is an interesting dilemma.

I am also fond of using Alternative (disguised as MonadPlus) in the
Happstack sense, for building a web-site routing table. In the truest
sense I am composing alternative responses to an input request, but
using 'many', 'some', or 'sepEndBy` in this context would be odd.

Antoine

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


Re: [Haskell-cafe] [Alternative] change some/many semantics

2011-12-15 Thread malcolm.wallace
On 15 Dec, 2011,at 03:58 AM, Gregory Crosswhite gcrosswhite@gmailcom wrote:This is even more out there than my previous posts, but the following just occurred to me: is it absolutely necessary that some/many have produced the entire list of results before returning?No, it is not absolutely necessary. Couldn't we change their semantics so that the list of results is computed and/or extracted lazily?I do not regard that as a change in their semantics - it is perfectly allowed already Indeed, the instances of some/many that I write are already lazily-unfolding, wherever possible. It all depends simply on whether your instance of Applicative is lazy or strict.Regards, Malcolm___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [Alternative] change some/many semantics

2011-12-15 Thread Gregory Crosswhite

On Dec 15, 2011, at 9:31 PM, malcolm.wallace wrote:

 I do not regard that as a change in their semantics - it is perfectly allowed 
 already  Indeed, the instances of some/many that I write are already 
 lazily-unfolding, wherever possible.  It all depends simply on whether your 
 instance of Applicative is lazy or strict.

That makes sense.  So the problem is not with Alternative but with Maybe:  
specifically, the problem is that there is no way to write a fully lazy 
instance of Applicative for Maybe since both arguments have to be reduced to 
WHNF before we can determine the WHNF of the result of applying ($), and this 
is why some/many cannot return lazily generated lists of results.

Put another way, the problem with Maybe computations is that if there is a 
failure at any point in the computation than *the entire computation fails*, 
and this means that you can't lazily generate a list of results using some/many 
because you can't tell whether your computation was a success or a failure 
until the entire infinite computation has been run;  the only solution to this 
problem is, as others have suggested, to build domain-specific knowledge about 
Maybe into the some/many methods of Alternative instance, which I think is one 
of the good solutions that has been brought up in this discussion.  :-)

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


[Haskell-cafe] [Alternative] change some/many semantics

2011-12-14 Thread Gregory Crosswhite
Hey everyone,

This is even more out there than my previous posts, but the following just 
occurred to me:  is it absolutely necessary that some/many have produced the 
entire list of results before returning?  Couldn't we change their semantics so 
that the list of results is computed and/or extracted lazily?  For example, if 
this were the case, then we would have that (some (Just 1)) returns an infinite 
list rather than running in an infinite loop (even without defining a special 
case some implementation), which is exactly what my intuition would expect.

Of course, this is not a simple change at all because it would have to be done 
in such a way as to respect the ordering of actions --- that is, we can't have 
each action executed only when the corresponding element of the list demanded 
is forced, or else actions would undesirably interleave.  For example, in a 
parser when we use many v we expect everything matching v to be consumed by 
the time many v returns, but if instead many v only consumed as much of the 
input as we demanded from its result list then we might see a chunk of input 
matching v in another part of our parser despite having assumed we'd gotten rid 
of it, which would cause our parser to be broken.

Nonetheless, if there were some way that we could use magic fairy dust to have 
the results returned by some and many be lazily generated lists, then this 
might solve many of the problems that come up with them performing infinite 
loops in cases where it seems like they shouldn't.  :-)

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


Re: [Haskell-cafe] [Alternative] change some/many semantics

2011-12-14 Thread Antoine Latter
On Wed, Dec 14, 2011 at 9:58 PM, Gregory Crosswhite
gcrosswh...@gmail.com wrote:
 Hey everyone,

 This is even more out there than my previous posts, but the following just
 occurred to me:  is it absolutely necessary that some/many have produced the
 entire list of results before returning?  Couldn't we change their semantics
 so that the list of results is computed and/or extracted lazily?  For
 example, if this were the case, then we would have that (some (Just 1))
 returns an infinite list rather than running in an infinite loop (even
 without defining a special case some implementation), which is exactly
 what my intuition would expect.


Isn't this what Ross previously suggested? I think his suggested
instance methods for Maybe return the elements of the lists
incrementally.

 Of course, this is not a simple change at all because it would have to be
 done in such a way as to respect the ordering of actions --- that is, we
 can't have each action executed only when the corresponding element of the
 list demanded is forced, or else actions would undesirably interleave.  For
 example, in a parser when we use many v we expect everything matching v to
 be consumed by the time many v returns, but if instead many v only
 consumed as much of the input as we demanded from its result list then we
 might see a chunk of input matching v in another part of our parser despite
 having assumed we'd gotten rid of it, which would cause our parser to be
 broken.

 Nonetheless, if there were some way that we could use magic fairy dust to
 have the results returned by some and many be lazily generated lists, then
 this might solve many of the problems that come up with them performing
 infinite loops in cases where it seems like they shouldn't.  :-)

 Cheers,
 Greg

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


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


Re: [Haskell-cafe] [Alternative] change some/many semantics

2011-12-14 Thread Gregory Crosswhite

On Dec 15, 2011, at 2:13 PM, Antoine Latter wrote:

 Isn't this what Ross previously suggested? I think his suggested
 instance methods for Maybe return the elements of the lists
 incrementally.

Yes and no.  Yes, his excellent suggestion is one of my favorite ideas for what 
we should do with Alternative that I have seen so far and was the inspiration 
for my proposal, but no it is not the same idea at all.  Whereas his suggestion 
keeps the types and generic definitions of some and many the way that they are 
but overrides them manually to work for types such as Maybe, my proposal is 
that we instead change the types and generic definitions of some and many 
themselves so that they automatically do the right thing for the Maybe and List 
types.

To justify my idea in a different way, it seems to me that somehow some and 
many somehow aren't lazy enough, because if they *were* lazy enough then we 
wouldn't have to hack into them for some types (Maybe and List) in order to get 
them to generate the infinite lazy lists that we were expecting.

Again, though, this is all crazy talk, and the only way to bring my epic vision 
into creation might be through abundant use of magic fairy dust.  :-)

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


Re: [Haskell-cafe] [Alternative] change some/many semantics

2011-12-14 Thread Antoine Latter
On Wed, Dec 14, 2011 at 10:33 PM, Gregory Crosswhite
gcrosswh...@gmail.com wrote:

 On Dec 15, 2011, at 2:13 PM, Antoine Latter wrote:

 Isn't this what Ross previously suggested? I think his suggested
 instance methods for Maybe return the elements of the lists
 incrementally.


 Yes and no.  Yes, his excellent suggestion is one of my favorite ideas for
 what we should do with Alternative that I have seen so far and was the
 inspiration for my proposal, but no it is not the same idea at all.  Whereas
 his suggestion keeps the types and generic definitions of some and many the
 way that they are but overrides them manually to work for types such as
 Maybe, my proposal is that we instead change the types and generic
 definitions of some and many themselves so that they automatically do the
 right thing for the Maybe and List types.


Unless the Alternative and Applicative type classes offer class
methods to guarantee laziness, we'll have a hard time writing
functions with those guarantees. Such is the cost of parametric
polymorphism! But also the beauty - in the absence of any laziness
guaranteeing functions on the class, we are promised that a
polymorphic function can't be using magic fairy dust behind our back.

We could add some sort of laziness guaranteeing combinators to the
class interface, but that would restrict its membership even further.

Or we could not use 'some' and 'many' with list and maybe :-)

Antoine

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


Re: [Haskell-cafe] [Alternative] change some/many semantics

2011-12-14 Thread Brandon Allbery
On Wed, Dec 14, 2011 at 23:49, Antoine Latter aslat...@gmail.com wrote:

 Or we could not use 'some' and 'many' with list and maybe :-)


Yes, yes, we get the message, a wink and a nod is all that's needed to
discard the nonsensical notion that types and typeclasses *mean* something.

-- 
brandon s allbery  allber...@gmail.com
wandering unix systems administrator (available) (412) 475-9364 vm/sms
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [Alternative] change some/many semantics

2011-12-14 Thread Antoine Latter
On Wed, Dec 14, 2011 at 10:57 PM, Brandon Allbery allber...@gmail.com wrote:
 On Wed, Dec 14, 2011 at 23:49, Antoine Latter aslat...@gmail.com wrote:

 Or we could not use 'some' and 'many' with list and maybe :-)


 Yes, yes, we get the message, a wink and a nod is all that's needed to
 discard the nonsensical notion that types and typeclasses *mean* something.


That's the interesting thing about type-classes like Alternative and
Functor - they mean very little, and are used in widely varying
contexts. Heck, Control.Monad.void has the type signature Functor f a
= f a - f () - how many functors is that operator sensible for?

There are a lot of combinators you can build from (|) and empty that
go terribly wrong for Maybe and List but are still quite useful. Even
the operators at hand ('many' and 'some') are partial in parsing, but
I'm not prepared to throw them out.

Antoine

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


Re: [Haskell-cafe] [Alternative] change some/many semantics

2011-12-14 Thread Gregory Crosswhite

On Dec 15, 2011, at 3:36 PM, Antoine Latter wrote:

 That's the interesting thing about type-classes like Alternative and
 Functor - they mean very little, and are used in widely varying
 contexts.

So... your point is that in the Haskell community we don't tend to care about 
whether our types, typeclasses, typeclass instances, etc. make any sense at all?

 Heck, Control.Monad.void has the type signature Functor f a
 = f a - f () - how many functors is that operator sensible for?

All of them.  I can't conceive of a single case where this would result in an 
undefined operation;  can you?

Furthermore when people write code using monadic combinators they toss out 
results all the time so this kind of function makes perfect sense.

 There are a lot of combinators you can build from (|) and empty that
 go terribly wrong for Maybe and List but are still quite useful.

Yes, you *could* do that, but the whole point is that you shouldn't.  
Typeclasses generally come with informal laws that must be obeyed.  If your 
instance does not obey those laws, then it should not be an instance.

Incidentally, exactly what use cases do you have in mind?

 Even
 the operators at hand ('many' and 'some') are partial in parsing, but
 I'm not prepared to throw them out.

Okay, I must confess that this straw man has been causing my patience to get a 
little thing.  *Nobody* here is saying that many and some should be thrown out, 
since there are clearly many contexts where they are very useful.  The *most* 
that has been suggested is that they should be moved into a subclass in order 
to make it explicit when they are sensible, and that is *hardly* banning them.

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


Re: [Haskell-cafe] [Alternative] change some/many semantics

2011-12-14 Thread Brandon Allbery
On Thu, Dec 15, 2011 at 02:23, Gregory Crosswhite gcrosswh...@gmail.comwrote:

 On Dec 15, 2011, at 3:36 PM, Antoine Latter wrote:

 Even
 the operators at hand ('many' and 'some') are partial in parsing, but
 I'm not prepared to throw them out.


 Okay, I must confess that this straw man has been causing my patience to
 get a little thing.  *Nobody* here is saying that many and some should be
 thrown out, since there are clearly many contexts where they are very
 useful.  The *most* that has been suggested is that they should be moved
 into a subclass in order to make it explicit when they are sensible, and
 that is *hardly* banning them.


This.

I was always under the impression that the Haskell Way was to capture
constraints in the type system instead of letting them be runtime failures;
here we have some combinators that appear to require an additional
constraint, and active opposition to describing that constraint in the
type!

-- 
brandon s allbery  allber...@gmail.com
wandering unix systems administrator (available) (412) 475-9364 vm/sms
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [Alternative] change some/many semantics

2011-12-14 Thread Antoine Latter
On Thu, Dec 15, 2011 at 1:23 AM, Gregory Crosswhite
gcrosswh...@gmail.com wrote:

 On Dec 15, 2011, at 3:36 PM, Antoine Latter wrote:

 There are a lot of combinators you can build from (|) and empty that
 go terribly wrong for Maybe and List but are still quite useful.


 Yes, you *could* do that, but the whole point is that you shouldn't.
  Typeclasses generally come with informal laws that must be obeyed.  If your
 instance does not obey those laws, then it should not be an instance.


I said 'combinators', not 'instances'. A lot of popular parsers
combinators can be written exclusively from (|) and empty, but make
little sense for List and Maybe, and may not even function properly.
The 'trifecta' package includes a nice reference:

http://hackage.haskell.org/packages/archive/trifecta/0.49.1/doc/html/Text-Trifecta-Parser-Combinators.html

See 'skipSome' through 'chainr1' - I wouldn't be surprised if most of
these lead to the same infinite loop behavior for Maybe as the stock
'many' and 'some' in base.

These sorts of functions are what Alternative is for.

Maybe I'm missing something fundamental here.

Antoine

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


Re: [Haskell-cafe] [Alternative] change some/many semantics

2011-12-14 Thread Antoine Latter
On Thu, Dec 15, 2011 at 1:40 AM, Antoine Latter aslat...@gmail.com wrote:
 On Thu, Dec 15, 2011 at 1:23 AM, Gregory Crosswhite
 gcrosswh...@gmail.com wrote:

 On Dec 15, 2011, at 3:36 PM, Antoine Latter wrote:

 There are a lot of combinators you can build from (|) and empty that
 go terribly wrong for Maybe and List but are still quite useful.


 Yes, you *could* do that, but the whole point is that you shouldn't.
  Typeclasses generally come with informal laws that must be obeyed.  If your
 instance does not obey those laws, then it should not be an instance.



To clarify - I dropped Greg's sentence Incidentally, exactly what use
cases do you have in mind?, which is most of what I was addressing in
my previous email.

 I said 'combinators', not 'instances'. A lot of popular parsers
 combinators can be written exclusively from (|) and empty, but make
 little sense for List and Maybe, and may not even function properly.
 The 'trifecta' package includes a nice reference:

 http://hackage.haskell.org/packages/archive/trifecta/0.49.1/doc/html/Text-Trifecta-Parser-Combinators.html

 See 'skipSome' through 'chainr1' - I wouldn't be surprised if most of
 these lead to the same infinite loop behavior for Maybe as the stock
 'many' and 'some' in base.

 These sorts of functions are what Alternative is for.

 Maybe I'm missing something fundamental here.

 Antoine

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