The actual, entire, complete definitions of sequence and sequence_ are
(or at least, could be):
> sequence [] = return []
> sequence (m:ms) = do
> x <- m
> xs <- sequence ms
> return (x:xs)
>
> -- or, equivalently:
> sequence' = foldr (liftM2 (:)) (return [])
>
> sequence_ [] = return ()
> s
On Oct 30, 2010, at 2:30 PM, Mark Spezzano wrote:
If you use the type with Maybe Int like so:
sequence [Just 1, Nothing, Just 2]
then the result is Nothing.
Whereas sequence [Just 1, Just 2, Just 3] gives
Just [1, 2, 3]
Try
do x <- Just 1
y <- Nothing
z <- Just 2
That is a result of the implementation of the specific Monad instance, and
that does depend on the type, as you say (but it isn't determined for
sequence(_) specifically).
Nothing >>= f = Nothing
Just x >>= f = f x
is why a Nothing "pollutes" the sequenced lists of Maybes. If Maybe is a
Monad rep
On 30 October 2010 16:30, Mark Spezzano wrote:
> Not exactly. If you use the type with Maybe Int like so:
>
> sequence [Just 1, Nothing, Just 2]
>
> then the result is Nothing.
>
> Whereas sequence [Just 1, Just 2, Just 3] gives
>
> Just [1, 2, 3]
>
> Why?
>
> I assume there's special implementati
Not exactly. If you use the type with Maybe Int like so:
sequence [Just 1, Nothing, Just 2]
then the result is Nothing.
Whereas sequence [Just 1, Just 2, Just 3] gives
Just [1, 2, 3]
Why?
I assume there's special implementations of sequence and sequence_ depending on
the type of monad used.
On 2010-10-30 07:07, Mark Spezzano wrote:
Hi,
Can somebody please explain exactly how the monad functions "sequence" and
"sequence_" are meant to work?
I have almost every Haskell textbook, but there's surprisingly little
information in them about the two functions.
From what I can gather,
On Wed, Apr 8, 2009 at 5:20 PM, Ben Franksen wrote:
> Sebastian Fischer wrote:
>> > {-# LANGUAGE Rank2Types #-}
>>
>> Dear Haskellers,
>>
>> I just realized that we get instances of `Monad` from pointed functors
>> and instances of `MonadPlus` from alternative functors.
>>
>> Is this folklore?
>>
Sebastian Fischer wrote:
> > {-# LANGUAGE Rank2Types #-}
>
> Dear Haskellers,
>
> I just realized that we get instances of `Monad` from pointed functors
> and instances of `MonadPlus` from alternative functors.
>
> Is this folklore?
>
> > import Control.Monad
> > import Control.Applicative
>
"Apfelmus, Heinrich" wrote:
> [...] but this is very different from using a particular monad like
> the state monad and hoping that using it somehow gives an insight into
> the problem domain.
You're right, mostly. However, there are a lot of problems, where you
cannot provide any useful abstra
Ertugrul Soeylemez wrote:
> [...]
Thank you for your reply, I think I can refine my thoughts. And make
them much longer... ;)
The elegance I have in mind comes from abstraction, that is when a type
takes a meaning on its own, independent of its implementation. Let's
take the example of vector gr
On Tue, 2009-01-13 at 19:44 -0500, Dan Doel wrote:
> On Tuesday 13 January 2009 7:27:10 pm Luke Palmer wrote:
> > > When GHC starts optimizing (Writer Builder) as well as it optimizes PutM,
> > > then
> > > that will be a cogent argument. Until then, one might argue that it
> > > misses "the whole
On Tue, Jan 13, 2009 at 07:44:17PM -0500, Dan Doel wrote:
> On Tuesday 13 January 2009 7:27:10 pm Luke Palmer wrote:
> > Surely PutM and Writer Put have almost the same performance?! (I am
> > worried if not -- if not, can you give an indication why?)
>
> The underlying monoid is Builder. The po
On Tue, 2009-01-13 at 19:19 -0500, Dan Doel wrote:
> On Tuesday 13 January 2009 5:51:09 pm Luke Palmer wrote:
> > On Tue, Jan 13, 2009 at 11:21 AM, Tim Newsham wrote:
> > > I have seen several libraries where all functions of a monad have the
> > >
> > >> monadic result (), e.g. Binary.Put and oth
On Tuesday 13 January 2009 7:27:10 pm Luke Palmer wrote:
> > When GHC starts optimizing (Writer Builder) as well as it optimizes PutM,
> > then
> > that will be a cogent argument. Until then, one might argue that it
> > misses "the whole point of Put".
>
> Well it can still serve as an optimization
On Tue, Jan 13, 2009 at 5:19 PM, Dan Doel wrote:
> On Tuesday 13 January 2009 5:51:09 pm Luke Palmer wrote:
> > On Tue, Jan 13, 2009 at 11:21 AM, Tim Newsham wrote:
> > > I have seen several libraries where all functions of a monad have the
> > >
> > >> monadic result (), e.g. Binary.Put and oth
On Tuesday 13 January 2009 5:51:09 pm Luke Palmer wrote:
> On Tue, Jan 13, 2009 at 11:21 AM, Tim Newsham wrote:
> > I have seen several libraries where all functions of a monad have the
> >
> >> monadic result (), e.g. Binary.Put and other writing functions. This is
> >> a clear indicator, that th
On Tue, Jan 13, 2009 at 11:21 AM, Tim Newsham wrote:
> I have seen several libraries where all functions of a monad have the
>> monadic result (), e.g. Binary.Put and other writing functions. This is
>> a clear indicator, that the Monad instance is artificial and was only
>> chosen because of the
I have seen several libraries where all functions of a monad have the
monadic result (), e.g. Binary.Put and other writing functions. This is
a clear indicator, that the Monad instance is artificial and was only
chosen because of the 'do' notation.
Maybe that was the initial reason, but I've act
On Tue, Jan 13, 2009 at 10:16:32AM +, ChrisK wrote:
> Henning Thielemann wrote:
>> I have seen several libraries where all functions of a monad have the
>> monadic result (), e.g. Binary.Put and other writing functions. This is
>> a clear indicator, that the Monad instance is artificial and was
Henning Thielemann wrote:
I have seen several libraries where all functions of a monad have the
monadic result (), e.g. Binary.Put and other writing functions. This is
a clear indicator, that the Monad instance is artificial and was only
chosen because of the 'do' notation.
I completely disagre
Ertugrul Soeylemez schrieb:
> "Apfelmus, Heinrich" wrote:
>
>> The insistence on avoiding monads by experienced Haskellers, in
>> particular on avoiding the IO monad, is motivated by the quest for
>> elegance.
>>
>> The IO and other monads make it easy to fall back to imperative
>> programming pa
As a physicist, I think that programming, like any design in general, is all
about making as little use of brain resources as possible at the time of
solving problems and to transmit the solution to others. This is the reason
why it is pervasive in all kinds of engineering the concepts of modularit
Lennart Augustsson wrote:
Agda has made the choice that you can have (almost) any sequence of
characters in identifiers. It works fine, but forces you to use white
space (which I do anyway).
No _'s though, which is exactly what Jason was after. :-)
Still, Agda rocks.
Martijn.
___
Agda has made the choice that you can have (almost) any sequence of
characters in identifiers. It works fine, but forces you to use white
space (which I do anyway).
-- Lennart
On Sun, Jan 11, 2009 at 4:28 PM, Martijn van Steenbergen
wrote:
> minh thu wrote:
>>
>> I always thought that instead
Hello Miguel,
Sunday, January 11, 2009, 7:06:54 PM, you wrote:
> I believe it was Bulat Ziganshin who once proposed parsing
> x + y*z + t as x + (y * z) + t
> and
> x + y * z + t as (x + y) * (z + t)
x+y * z+t should be here
--
Best regards,
Bulat
Indeed but what's wrong in writing x + y (with additional spaces) ?
Having the possiblity to write for instance +blah instead of inventing
things such as $>* is neat in my opinion (in code or for
typesetting)...
I believe it was Bulat Ziganshin who once proposed parsing
x + y*z + t
2009/1/11 Martijn van Steenbergen :
> minh thu wrote:
>>
>> I always thought that instead of having two classes of characters, one
>> for variable (and function) names and the
>> other for operators, only the first charater of the identifier could
>> mean it's one or the others,
>> so *vec or +poin
minh thu wrote:
I always thought that instead of having two classes of characters, one
for variable (and function) names and the
other for operators, only the first charater of the identifier could
mean it's one or the others,
so *vec or +point would be valid operator names and thus >_> too. And
I always thought that instead of having two classes of characters, one
for variable (and function) names and the
other for operators, only the first charater of the identifier could
mean it's one or the others,
so *vec or +point would be valid operator names and thus >_> too. And
C++ could be a Dat
It is really too bad we can not define the operators
>_> ^_^ <_<
These are significant from an internationalization standpoint;
and they'd make the language so much more competitive
vis-a-vis LOLCode.
--
Jason Dusek
2009/1/10 Brandon S. Allbery KF8NH :
> On 2009 Jan 10, at 15:19
Ertugrul Soeylemez wrote:
> Personally I prefer this:
>
> somethingWithRandomsM :: (Monad m, Random a) => m a -> Something a
Of course, there is something missing here:
somethingWithRandomsM :: (Monad m, Random a) => m a -> m (Something a)
Sorry.
Greets,
Ertugrul.
--
nightmare = unsaf
"Apfelmus, Heinrich" wrote:
> Ertugrul Soeylemez wrote:
>
> > Let me tell you that usually 90% of my code is monadic and there is
> > really nothing wrong with that. I use especially State monads and
> > StateT transformers very often, because they are convenient and are
> > just a clean combina
Holy concatenated operators, Batman!
Is that an operator or Batman?
> (yes, I know, 3 operators)
>
> --
> brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
> system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
> electrical and computer engineering, carne
On 2009 Jan 10, at 15:19, Peter Verswyvelen wrote:
h3 x = f x <^(+)^> g x
Is that an operator or Batman?
(yes, I know, 3 operators)
--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical an
>
> For example, which of these is easier to read?
>
> f,g :: Int -> [Int]
>
> h1 :: Int -> [Int]
> h1 x = do
>fx <- f x
>gx <- g x
>return (fx + gx)
>
> h2 :: Int -> [Int]
> h2 x = (+) <$> f x <*> g x
>
> h3 :: Int -> [Int]
> h3 x = f x + g x -- not legal, of course, but wouldn't it
My issue is that there seem to be many cases where the syntax
extension does *almost* what I want, but not quite. And there isn't
any method to extend it, so you are left with two choices:
(1) Go back to unsugared syntax
(2) Hack your technique into the constraints of the existing syntax exten
Related to this issue, I have a question here.
I might be wrong, but it seems to me that some Haskellers don't like
writing monads (with do notation) or arrows (with proc sugar) because of the
fact they have to abandon the typical applicative syntax, which is so close
to the beautiful lambda calc
Ertugrul Soeylemez wrote:
Hello fellow Haskellers,
When I read questions from Haskell beginners, it somehow seems like they
try to avoid monads and view them as a last resort, if there is no easy
non-monadic way. I'm really sure that the cause for this is that most
tutorials deal with monads ve
John,
You write:
> Yes, you are describing 'co-monads'.
>
Good catch, but actually, that's too weak. i'm requesting something that is
both a monad and a co-monad. That makes it something like a bi-algebra, or a
Hopf algebra. This, however, is not the full story. i'm looking for a
reference to the
On Mon, 2007-12-17 at 09:58 -0500, David Menendez wrote:
>
>
> On Dec 17, 2007 4:34 AM, Yitzchak Gale <[EMAIL PROTECTED]> wrote:
> Derek Elkins wrote:
> > There is another very closely related adjunction that is
> less often
> > mentioned.
> >
> > (
On Dec 17, 2007 4:34 AM, Yitzchak Gale <[EMAIL PROTECTED]> wrote:
> Derek Elkins wrote:
> > There is another very closely related adjunction that is less often
> > mentioned.
> >
> > ((-)->C)^op -| (-)->C
> > or
> > a -> b -> C ~ b -> a -> C
> >
> > This gives rise to the monad,
> > M a = (a -> C)
Derek Elkins wrote:
> There is another very closely related adjunction that is less often
> mentioned.
>
> ((-)->C)^op -| (-)->C
> or
> a -> b -> C ~ b -> a -> C
>
> This gives rise to the monad,
> M a = (a -> C) -> C
> this is also exactly the comonad it gives rise to (in the op category
> which e
On Sun, 2007-12-16 at 13:49 +0100, apfelmus wrote:
> Dan Weston wrote:
> > newtype O f g a = O (f (g a)) -- Functor composition: f `O` g
> >
> > instance (Functor f, Functor g) => Functor (O f g) where ...
> > instance Adjunction f g => Monad (O g f) where ...
> > instance Adjunction f
Dan Weston wrote:
newtype O f g a = O (f (g a)) -- Functor composition: f `O` g
instance (Functor f, Functor g) => Functor (O f g) where ...
instance Adjunction f g => Monad (O g f) where ...
instance Adjunction f g => Comonad (O f g) where ...
class (Functor f, Functor g
PR Stanley wrote:
> Does the list consider
>
http://en.wikibooks.org/w/index.php?title=Haskell/Understanding_monads&oldid=933545
> a reliable tutorial on monads and, if not, could you recommend an
> onlien alternative please?
I strongly recommend the original papers by Philip Wadler, especially th
On 1 Aug 2007, at 21:23, Greg Meredith wrote:
But, along these lines i have been wondering for a while... the
monad laws present an alternative categorification of monoid. At
least it's alternative to monoidoid. In the spirit of this thought,
does anyone know of an expansion of the monad ax
Arie,
Thanks for your thoughtful reply. Comments in-lined.
Best wishes,
--greg
Date: Thu, 2 Aug 2007 03:06:51 +0200 (CEST)
> From: "Arie Peterson" <[EMAIL PROTECTED]>
> Subject: Re: [Haskell-cafe] Re: monads and groups -- instead of loops
> To: haskell-cafe@haskell.o
If you haven't read it, you might be interested in the paper
Alimarine et al, "There and Back Again: Arrows for Invertible Programming"
which can be found at
http://www.st.cs.ru.nl/papers/2005/alia2005-biarrowsHaskellWorkshop.pdf
Dan Weston
Greg Meredith wrote:
Haskellians,
But, along these
Math alert: mild category theory.
Greg Meredith wrote:
> But, along these lines i have been wondering for a while... the monad laws
> present an alternative categorification of monoid. At least it's
> alternative to monoidoid.
I wouldn't call monads categorifications of monoids, strictly speakin
Haskellians,
But, along these lines i have been wondering for a while... the monad laws
present an alternative categorification of monoid. At least it's alternative
to monoidoid. In the spirit of this thought, does anyone know of an
expansion of the monad axioms to include an inverse action? Here,
Brandon, Jeremy, et al,
Thanks for the pointers. The paper by OlegK, et al, articulates exactly the
structure i was noticing, except that i was coming at it from the other end.
i was noticing that a wide range of these CSP-style problems could be
decomposed into a trivial monad (e.g., list, multi
Wolfgang Jeltsch wrote:
Am Samstag, 26. November 2005 03:56 schrieb Geoffrey Alan Washburn:
[lots of code]
It's interesting to note how verbose Java is in comparison to Haskell, at
least, concerning this monad stuff.
I'd agree. However, my original point was that my version that uses
gen
Am Samstag, 26. November 2005 03:56 schrieb Geoffrey Alan Washburn:
> [lots of code]
It's interesting to note how verbose Java is in comparison to Haskell, at
least, concerning this monad stuff.
Best wishes,
Wolfgang
___
Haskell-Cafe mailing list
Haske
Shae Matijs Erisson wrote:
Gregory Woodhouse <[EMAIL PROTECTED]> writes:
My knowledge of functional programming is pretty much limited to Haskell,
Scheme, and a smattering of Common Lisp. Are there languages other than
Haskell that explicitly use monads? How about "not so explicitly"?
Java ht
Shae Matijs Erisson wrote:
Please respond with any language implementations I've missed.
C++ http://www.cc.gatech.edu/~yannis/fc++/New1.5/lambda.html#monad
Jim
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/lis
55 matches
Mail list logo