Monads

2003-12-31 Thread Mark Carroll
Omitting the typeclass bit, I'm trying to write something like (s1 -> s2) -> StateT s1 m () -> StateT s2 m a -> StateT s1 m a That is, it sequences two StateT computations, providing a way to translate from the first's state to the second to keep the chain going. I can easily write something for

[Haskell-cafe] Building Monads from Monads

2006-03-23 Thread Daniel McAllansmith
Hi, I've got a few (9) random questions, mainly about monads and building monads from existing monads, partly trying to confirm conclusions I've come to through experimentation. Any, and all, attempts to enlighten me will be much appreciated. Thanks Daniel First, terminology. I

Re: [Haskell-cafe] Building Monads from Monads

2006-03-23 Thread Cale Gibbard
On 23/03/06, Daniel McAllansmith <[EMAIL PROTECTED]> wrote: > Hi, I've got a few (9) random questions, mainly about monads and building > monads from existing monads, partly trying to confirm conclusions I've come > to through experimentation. > > Any, and all, a

Re: [Haskell-cafe] Building Monads from Monads

2006-03-23 Thread Cale Gibbard
Oh, and almost forgot, you can check out lots of examples of this not only in the mtl, but also on the (old) Haskell Wiki. I've written a lot of simple (sometimes trivial) examples for people to look at Unique values -- very simple http://www.haskell.org/hawiki/MonadUnique A supply of values, a s

Re: [Haskell-cafe] Building Monads from Monads

2006-03-26 Thread Daniel McAllansmith
On Friday 24 March 2006 16:42, Cale Gibbard wrote: Excellent help thanks, Cale. A lot of my misunderstandings stemmed from not finding any 'instance MonadState ReaderT' when reading the code in Reader.hs, not realising that there was an instance defined in State.hs, and yet being able to use ge

Re: [Haskell-cafe] Building Monads from Monads

2006-03-26 Thread Daniel McAllansmith
On Friday 24 March 2006 16:49, Cale Gibbard wrote: > Oh, and almost forgot, you can check out lots of examples of this not > only in the mtl, but also on the (old) Haskell Wiki. I've written a > lot of simple (sometimes trivial) examples for people to look at I'll be sure to check them out. > La

Monads [beginner]

2002-12-12 Thread maas
What are Monads? Where can I read about then? I read that there´s some mathematical foundation under this concept, where can read about these theories? +-+ | Marcos Aurélio Almeida da Silva | | E-mail: [EMAIL PROTECTED

Simple monads

2003-06-26 Thread Mark Carroll
Not really seeing why Unique is in the IO monad, not deeply understanding the use of Haskell extensions in the State source, and wanting to try to learn a bit more about monads, I thought I'd try to write my own monad for the first time: something for producing a series of unique labels. Th

Re: Monads

2003-12-31 Thread Christopher Milton
Mark, I'm no expert, but does it help to start from withStateT? > withStateT :: (s -> s) -> StateT s m a -> StateT s m a > withStateT f m = StateT $ runStateT m . f There are some notes about computations and lifting state transformers in Modular Denotational Semantics for Compiler Construction

Re: Monads

2003-12-31 Thread Ken Shan
Mark Carroll <[EMAIL PROTECTED]> wrote in article <[EMAIL PROTECTED]> in gmane.comp.lang.haskell.cafe: > Omitting the typeclass bit, I'm trying to write something like > (s1 -> s2) -> StateT s1 m () -> StateT s2 m a -> StateT s1 m a > > That is, it sequences two StateT computations, providing a w

Re: Monads

2003-12-31 Thread Mark Carroll
On Wed, 31 Dec 2003, Ken Shan wrote: > Don't you need a (s2 -> s1) function as well, to translate the final > state back into StateT s1? Yes, you're right: the thing actually running the stateful computation presumably expects to start it with a state of type s1 and to be able to extract from it

A View of Monads (Re: performance of monads)

2002-01-16 Thread Eray Ozkural (exa)
-BEGIN PGP SIGNED MESSAGE- Hash: SHA1 Let me offer a differing view of Monads. Monads are a way to write type-safe imperative programs within a functional framework. It's just an advanced version of PROGN kludge in LISP. Since they are based on a linear flow of "commands&q

Re: A View of Monads (Re: performance of monads)

2002-01-16 Thread Artie Gold
"Eray Ozkural (exa)" wrote: > > -BEGIN PGP SIGNED MESSAGE- > Hash: SHA1 > > Let me offer a differing view of Monads. > > Monads are a way to write type-safe imperative programs within a functional > framework. It's just an advanced version of PR

Re: A View of Monads (Re: performance of monads)

2002-01-21 Thread Hamilton Richards
At 12:47 PM -0600 1/16/02, Eray Ozkural (exa) wrote: > >Let me offer a differing view of Monads. > >Monads are a way to write type-safe imperative programs within a functional >framework. It's just an advanced version of PROGN kludge in LISP. > >Since they are based on

Re: A View of Monads (Re: performance of monads)

2002-02-18 Thread Richard Uhtenwoldt
Artie Gold writes: >One way to think of it is to look at a program as a partially ordered >set of calculations; some calculations need to occur before others, >other groups can occur in any order. In an imperative language you >specify a total ordering (which is overkill). This is a weak argumen

Re: A View of Monads (Re: performance of monads)

2002-02-19 Thread Eray Ozkural
-BEGIN PGP SIGNED MESSAGE- Hash: SHA1 Hi Richard, On Tuesday 19 February 2002 06:57, Richard Uhtenwoldt wrote: > > This is a weak argument. > > First of all it is not the case that imperative coders always specify a > total ordering: multitasking, threading and interrupts (and their > pr

[Haskell-cafe] Monads

2007-12-03 Thread PR Stanley
Hi 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? Thanks, Paul ___ Haskell-Cafe mailing

performance of monads

2002-01-16 Thread Eric Allen Wohlstadter
I see a lot of literature that says that monads "simulate" the effects of imperative programming concepts. It seems to me that the relative performance of monadic implementations must be equivalant to imperative ones to provide a strong case for functional programming. For examp

Re: Monads [beginner]

2002-12-12 Thread Benderjgdefault
In a message dated 12/12/2002 2:45:31 PM Eastern Standard Time, [EMAIL PROTECTED] writes: > What are Monads? > Where can I read about then? > > I read that there´s some mathematical foundation under this > concept, where > can read about these theories? A large set of art

Re: Monads [beginner]

2002-12-12 Thread Joel Wright
I've found this page a very helpful introduction to Monads and monadic programming. http://www.dcs.gla.ac.uk/~nww/Monad.html Have fun, Joel. On Thu, 2002-12-12 at 19:45, [EMAIL PROTECTED] wrote: > What are Monads? > Where can I read about then? > > I read that theres

Re: Monads [beginner]

2002-12-13 Thread Keith Wansbrough
Hi Joel and Jim - thanks for your useful responses to Marcos' question. I've added them to the UsingMonads page of the Haskell Wiki, http://www.haskell.org/wiki/wiki?UsingMonads Hope that's OK. Feel free to edit or extend or add your names if you like. To everyone else on the list: please ad

Re: Combining Monads

2003-04-12 Thread Dominic Steinitz
OTECTED] > > When replying, please edit your Subject line so it is more specific > than "Re: Contents of Haskell-Cafe digest..." > > > Today's Topics: > >1. Combining monads (Mark T.B. Carroll) >2. Re: Combining monads (Scott Turner) >3. Re: Combini

Re: Combining Monads

2003-04-12 Thread Eray Ozkural
On Saturday 12 April 2003 23:52, Dominic Steinitz wrote: > For the theory, look at > Triples, Toposes and Theories by Barr & Wells. I think it's chapter 7 but I > haven't got it in front of me. > This looks like it's quickly getting out of the realm of programming :) Cheers, -- Eray Ozkural (ex

RE: Simple monads

2003-06-26 Thread Hal Daume
> (a) People could point out to me where I'm still confused, as > revealed by > my code. Is it needlessly complicated? looks pretty reasonable to me :) as to why Unique is in the IO monad is probabyl because if it were in any other monad, you could start the monad twice and thus get a repeat of

Re: Simple monads

2003-06-26 Thread Derek Elkins
e necessary because the state type depends on the monad (get would have type forall s.Monad m => m -> s otherwise which is rather meaningless), the function dependencies tell the type checker that the state type is completely determined by the monad type. > and > wanting to try to

Re: Simple monads

2003-06-27 Thread Christian Maeder
not deeply understanding the use of Haskell extensions in the State source, I'm assuming Control.Monad.State's source in which case -no- extensions are used for -State- (well, at least I don't see any quickly glancing). Extensions are used for the -MonadState class-. The portable parts of Con

Re: Simple monads

2003-06-27 Thread Christian Maeder
The previous "newtype Labeller a = Labeller (Int -> (Int, a))" (the result tuple is reversed within Control.Monad.State) would simply become (untested): newtype Labeller a = State Int a newLabel = do { n <- get; put (n + 1); return (Label n) } runLabeller l = execState l minBound it must be "e

Re: Simple monads

2003-06-27 Thread Wolfgang Jeltsch
On Friday, 2003-06-27, 12:55, CEST, Christian Maeder wrote: > [...] > The portable parts of Control.Monad.State (that are sufficient for most > cases) should be in an extra module (maybe called Control.Monad.StateTypes). > In addition further non-overloaded names for put, get, gets and modify woul

Re: Simple monads

2003-06-27 Thread Wolfgang Jeltsch
On Thursday, 2003-06-26, 23:57, CEST, Derek Elkins wrote: > [...] > > not deeply understanding the use of Haskell extensions in the State > > source, > > I'm assuming Control.Monad.State's source in which case -no- extensions are > used for -State- (well, at least I don't see any quickly glancing)

Re: Simple monads

2003-06-27 Thread Graham Klyne
rstanding the use of Haskell extensions in the State source, and wanting to try to learn a bit more about monads, I thought I'd try to write my own monad for the first time: something for producing a series of unique labels. This is how it turned out: =

Re: Simple monads

2003-06-30 Thread Christian Maeder
The portable parts of Control.Monad.State (that are sufficient for most cases) should be in an extra module (maybe called Control.Monad.StateTypes). In addition further non-overloaded names for put, get, gets and modify would be needed (maybe putState, getState, etc.) I fear, this would complicate

Monads and Maybe

2003-08-19 Thread Konrad Hinsen
I have been following the recent "Monad tutorial" discussion with interest, and even read the tutorial, which is a useful addition to the existing Haskell documentation. So useful in fact that it raises a question... The whole monad mechanism seems to geared towards functions of one argument, p

[Haskell-cafe] Monads

2012-09-29 Thread Vasili I. Galchin
Hello, I would an examples of monads that are pure, i.e. no side-effects. Thank you, Vasili ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Parametrized monads

2009-06-15 Thread Miguel Mitrofanov
Hi! Suppose I want to create a specific monad as a combination of monad transformers - something like "StateT smth1 (ReaderT smth2 Identity)". As you can see, each transformer is parametrized with a type of kind *. I want to abstract these parameters, so that instead of "StateT smth..." I can w

[Haskell-cafe] Pesky monads...

2007-05-19 Thread Andrew Coppin
I've been getting some pretty weird complaints from the type checker. And I just figured out why! Grr... Is there any function that does the same thing as "until", but in a monad? ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haske

[Haskell-cafe] Mysterious monads

2007-05-27 Thread Andrew Coppin
Take a look at the following: data Writer o v = Writer [o] v instance Monad (Writer o) where return v = Writer [] v (Writer os v) >>= f = let (Writer os' v') = f v in Writer (os ++ os') v' write :: o -> Writer o () write o = Writer [o] () writes :: [o] -> Writer o () wri

[Haskell-cafe] Java Monads?

2007-06-04 Thread Greg Meredith
HaskellyCaffeinated, i noticed that there was a JavaMonad lib kicking around on the web, but all the links i can find are stale. Does anybody have a live pointer to this lib? Best wishes, --greg -- L.G. Meredith Managing Partner Biosimilarity LLC 505 N 72nd St Seattle, WA 98103 +1 206.650.374

[Haskell-cafe] Explaining monads

2007-08-09 Thread Brian Brunswick
7; is better than 'IO a->b'. The full title of this is really 'Explaining monads by comparison with comonads and arrows', but I didn't want to scare people off without putting in the above hook! We start with a simple single value of type 'a', and then we

[Haskell-cafe] Re:Explaining monads

2007-08-14 Thread Gregory Propf
ntially that function in every real program? - Greg - Original Message From: Jeff Polakow <[EMAIL PROTECTED]> To: [EMAIL PROTECTED] Cc: [EMAIL PROTECTED]; Haskell-Cafe Sent: Tuesday, August 14, 2007 8:45:06 AM Subject: Re: [Haskell-cafe] Explaining monads One general intu

[Haskell-cafe] "Prime" monads?

2007-09-11 Thread Greg Meredith
Haskellians, Is there a characterization of "prime" monads? Here the notion of factorization i'm thinking about is decomposition into adjoint situations. For example, are there monads for which there are only the Kleisli and Eilenberg-Moore decompositions into adjoint situations?

[Haskell-cafe] Hello Monads

2006-09-07 Thread Hans van Thiel
Hello All, Being at the "Hello Monads" level, and having spent many hours on understanding the following code from YAHT, maybe this will be helpful to others. {-cross ls1 ls2 = do x <- ls1 y <- ls2 return (x,y) -} In the List Mo

[Haskell-cafe] collection monads

2006-10-03 Thread Matthias Fischmann
another beginners question about monads: given the type | data (Ix x) => Permutation x = Permutation [x] i wanted to define | instance Monad Permutation where | return xs = Permutation xs but of course nothing about the monad class guarantees xs to be of type list. the monad class se

[Haskell-cafe] layout monads

2006-10-03 Thread Thomas Conway
Hi All, Next monad query [*] In the 1995 paper "Composing Haggis", layout is done using a monad to compose individual elements. To modernize the syntax consider (forgive the operator, but it avoids parentheses): infixl 1 <| f <| x = f x mylayout = do hbox <| do button

[Haskell-cafe] collection monads

2006-10-04 Thread tpledger
Matthias Fischmann wrote: > another beginners question about monads: given the type > > | data (Ix x) => Permutation x = Permutation [x] > > i wanted to define > > | instance Monad Permutation where > | return xs = Permutation xs > > but of course nothing about

[Haskell-cafe] collection monads

2006-10-08 Thread tpledger
Matthias Fischmann wrote: > > Do you expect the contained type x to change during a > > sequence of monadic actions? e.g. would you ever use (>>=) > > at the type 'Permutation Int -> (Int -> Permutation Bool) -> > > Permutation Bool'? > > no, i don't need that. but aside from > the fact that > >

[Haskell-cafe] Stratified monads

2006-12-11 Thread Mark T.B. Carroll
I was interested to read David Espinosa's "Stratified Monads" paper at http://www-swiss.ai.mit.edu/~dae/papers/sm.ps.Z I'm not sure I actually understand them properly yet, but I'm already curious about if anybody's played with them in Haskell, or how useful it w

[Haskell-cafe] Stacking monads

2008-10-02 Thread Andrew Coppin
rking correctly... I'd really prefer to just layer error handling on the top. But I just can't get it to work right. It's s fiddly untangling the multiple monads to try to *do* any useful work. Does anybody have any idea how this whole monad stacking craziness is *supposed* to work? ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Composing monads

2007-11-22 Thread Maurí­cio
Hi, If I have two computations a->IO b and b->IO c, can I join them to get an a->IO c computation? I imagine something like a liftM dot operator. Thanks, Maurício ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/li

Re: [Haskell-cafe] Monads

2007-12-03 Thread Radosław Grzanka
Hi, 2007/12/3, PR Stanley <[EMAIL PROTECTED]>: > Hi > 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 really

[Haskell-cafe] Re: Monads

2007-12-03 Thread Ben Franksen
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 Wa

[Haskell-cafe] Pythonic monads

2006-02-03 Thread Graham Klyne
Constructing some code today in Python, using some functional-style coding idioms, I found myself wondering if there would be any real benefit to using a monad-based implementation (i.e. other than to demonstrate that it can be done). The application that sparked this line of thought was a simple

[Haskell-cafe] Teaching Monads

2008-06-07 Thread Ronald Guida
Monads in Haskell are a topic that I, like most beginners, find difficult and "mind-twisting". Now that I think I understand monads, they seem to be very simple; I've read that this is a common experience. So I wonder, what would it take to help beginners catch on with a min

[Haskell-cafe] Swapping Monads

2008-07-07 Thread Dominic Steinitz
I have a solution so this is for interest only. It is not normally the case that two monads compose to give another monad. Monad transformers capture when this is possible. However, when there is a "swap" function satisfying some commutative diagrams then it can be proved that the mona

Small confusion with monads

2001-10-04 Thread Dmitry Olyenyov
Hello! Can anybody help me with writing function that does following: I have the list ["file1","file2","file3"] and I need the function to return me the list of contents of these files. contents :: [String] -> [String] contents (file:files) = do c <- readFile file Thanks in advance

independant monads used together?

2001-11-10 Thread Jan-Willem Maessen
Pixel <[EMAIL PROTECTED]> asks: > I'm trying to achieve something like (ocaml) > [code deleted] > which is a foldl on 2 iterators. I've managed to use monads for one iterator, > but i completly miss the way to work with 2 monads. Is there really no other > solu

independant monads used together?

2001-11-09 Thread Pixel
I'm trying to achieve something like (ocaml) let rec zipfold f init it1 it2 = if it1#is_end || it2#is_end then init else let v1, v2 = it1#value, it2#value in it1#next ; it2#next ; zipfold f (f v1 v2 init) it1 it2 which is a foldl on 2 iterators. I've managed to use

Re: performance of monads

2002-01-16 Thread Manuel M. T. Chakravarty
Eric Allen Wohlstadter <[EMAIL PROTECTED]> wrote, > I see a lot of literature that says that monads "simulate" the effects of > imperative programming concepts. It seems to me that the relative > performance of monadic implementations must be equivalant to imperative &

Re: performance of monads

2002-01-16 Thread William Lee Irwin III
2002 at 08:59:14PM +1100, Manuel M. T. Chakravarty wrote: > PS: These optimisations will usually only apply to monads > that are defined as part of the system libraries of a > Haskell system, not to user-defined ones (unless a user > uses non-standard system features to impleme

Re: performance of monads

2002-01-16 Thread Jon Fairbairn
> I see a lot of literature that says that monads "simulate" the effects of > imperative programming concepts. I think that's just bad wording. To take a rather trite point of view, in a language such as C /everything/ is done within a monad, and all types, even int, are re

Re: performance of monads

2002-01-23 Thread Paul Hudak
Eric Allen Wohlstadter wrote: > I see a lot of literature that says that monads "simulate" the effects of > imperative programming concepts. It seems to me that the relative > performance of monadic implementations must be equivalant to imperative > ones to provide a stro

Re: performance of monads

2002-01-24 Thread Jorge Adriano
> I agree with others who mentioned that viewing monads as simply > providing a way to sequentialize things or to program imperatively is > the wrong way to look at them. Yes, Lists are the classical example. > That said, the EFFICIENCY of monads is often poorly understood. To

Re: performance of monads

2002-01-24 Thread John Hughes
I've felt need to use State monads in two distinct situations: ... And I've seen two distict aproaches. Using a State monad like one provided with GHC (1), or a state monad like the one defined in the paper "Moands for the Working Haskell

Re: performance of monads

2002-01-27 Thread Jorge Adriano
On Thursday 24 January 2002 14:09, John Hughes wrote: > I've felt need to use State monads in two distinct situations: > ... > > And I've seen two distict aproaches. Using a State monad like one > provided with GHC (1), or a state monad like the one def

Re: monads, modules, sandboxes

2002-08-21 Thread Richard Uhtenwoldt
this will be my last message on this topic as I need to stop reading this list for a few months. Alastair Reid writes: >A potential difference (which Richard Uhtenwoldt hints at) is that it >can be hard to control the flow of OS capabilities as the capability >is passed from one process to anoth

Re: Monads and Maybe

2003-08-19 Thread Wolfgang Jeltsch
On Tuesday, 2003-08-19, 12:42, CEST, Konrad Hinsen wrote: > I have been following the recent "Monad tutorial" discussion with interest, > and even read the tutorial, which is a useful addition to the existing > Haskell documentation. So useful in fact that it raises a question... > > The whole mona

Re: Monads and Maybe

2003-08-19 Thread C T McBride
Hi > > As an example, I'll use the Maybe monad. Suppose I want to write code to > > handle experimental data, in which there might be missing values. I might > > then decide to represent measurements by data of type "Maybe Double", with > > missing values represented by "Nothing". I could then go

Re: Monads and Maybe

2003-08-20 Thread Derek Elkins
On Tue, 19 Aug 2003 14:09:16 +0100 (BST) C T McBride <[EMAIL PROTECTED]> wrote: > Hi > > > > As an example, I'll use the Maybe monad. Suppose I want to write > > > code to handle experimental data, in which there might be missing > > > values. I might then decide to represent measurements by data

Re: Monads and Maybe

2003-08-21 Thread C T McBride
h) => Fun (Comp g h) where eta x = Comp (eta (eta x)) Comp ghf <$> Comp ghs = Comp (eta (<$>) ghf <$> ghs) That's to say, you can define <$> for the composition of two Funs, hence of two Monads, but, if I recall correctly, it's rather harder to define >

Re: Monads and Maybe

2003-08-21 Thread Jon Cast
uot;. Is there any mechanism to handle > that? Yes. Many complicated proposals have been made, but there's a straightforward, general mechanism: > addMaybe :: Num alpha => Maybe alpha -> Maybe alpha -> Maybe alpha > addMaybe a b = a >>= \x -> >b >&g

Re: Monads and Maybe

2003-08-21 Thread Martin Norbäck
tor 2003-08-21 klockan 22.26 skrev Jon Cast: > Yes. Many complicated proposals have been made, but there's a > straightforward, general mechanism: > > > addMaybe :: Num alpha => Maybe alpha -> Maybe alpha -> Maybe alpha > > addMaybe a b = a >>= \x -> > >b >>= \y -> > >

Re: Monads and Maybe

2003-08-21 Thread Doaitse Swierstra
On dinsdag, aug 19, 2003, at 15:09 Europe/Amsterdam, C T McBride wrote: Hi As an example, I'll use the Maybe monad. Suppose I want to write code to handle experimental data, in which there might be missing values. I might then decide to represent measurements by data of type "Maybe Double", wi

Re: Monads and Maybe

2003-08-21 Thread Jon Cast
> tor 2003-08-21 klockan 22.26 skrev Jon Cast: > > Yes. Many complicated proposals have been made, but there's a > > straightforward, general mechanism: > > > > > addMaybe :: Num alpha => Maybe alpha -> Maybe alpha -> Maybe alpha > > > addMaybe a b = a >>= \x -> > > >b >>= \y -> >

Re: Monads and Maybe

2003-08-22 Thread Ashley Yakeley
turn f) => Monad f where (>>=) :: f a -> (a -> f b) -> f b fail :: String -> f a; fail = error; Certain functions that seem to require Monads actually work with any FunctorApplyReturn. For instance: class (Functor f) => ExtractableFunctor f where fExtract :: (F

Re: Monads and Maybe

2003-08-23 Thread Ross Paterson
On Thu, Aug 21, 2003 at 11:32:47AM +0100, C T McBride wrote: > My point, however, is not to use <$> with that type, but the more general > > class Fun f where > eta :: x -> f x > (<$>) :: f (s -> t) -> f s -> f t > > Is there a better name for Fun? Is it ancient and venerable? Am I an >

Re: Monads and Maybe

2003-08-29 Thread C T McBride
g (Show,Eq) > instance Monoidal s => Fun (K s) where > eta _ = K m0 > K x <$> K y = K (x <+> y) > infixl 9 > () :: (Functorial g,Monoidal s) => (x -> s) -> g x -> s > f gx = unK ((K . f) <^> gx) *** 3 what extra syntax might be nic

Newbie qustion about monads

2003-10-02 Thread Juanma Barranquero
I have an extremely-newbie question about monads and how to interpret the monadic laws; I asked that same question yesterday on IRC and the answers were interesting but non-conclusive (to me anyway). I'm trying to learn monads by reading "All About Monads", version 1.0.2. I thoug

Re: [Haskell-cafe] Monads

2012-09-29 Thread Kristopher Micinski
You have fallen into the misconception that monads are impure, they are not. Many monad tutorials begin (erroneously) with the lines "monads allow you to do impure programming in Haskell." This is false, monads are pure, it's IO that's impure, not the monadic programming st

Re: [Haskell-cafe] Monads

2012-09-29 Thread KC
From: http://www.haskell.org/haskellwiki/Monad "The computation doesn't have to be impure and can be pure itself as well. Then monads serve to provide the benefits of separation of concerns, and automatic creation of a computational "pipeline"." On Sat, Sep 29,

Re: [Haskell-cafe] Monads

2012-09-30 Thread Tillmann Rendel
Vasili I. Galchin wrote: I would an examples of monads that are pure, i.e. no side-effects. One view of programming in monadic style is: You call return and >>= all the time. (Either you call it directly, or do notation calls it for you). So if you want to understand whether a mona

Re: [Haskell-cafe] Monads

2012-09-30 Thread Albert Y. C. Lai
On 12-09-29 09:57 PM, Vasili I. Galchin wrote: I would an examples of monads that are pure, i.e. no side-effects. What does "side effect" mean, to you? Definition? Because some people say "State has no side effect", and some other people say "State has side

Re: [Haskell-cafe] Monads

2012-09-30 Thread wren ng thornton
On 9/30/12 7:00 AM, Tillmann Rendel wrote: Vasili I. Galchin wrote: I would an examples of monads that are pure, i.e. no side-effects. One view of programming in monadic style is: You call return and >>= all the time. (Either you call it directly, or do notation calls it for you). So

Re: [Haskell-cafe] Monads

2012-09-30 Thread Jake McArthur
On Sep 30, 2012 10:56 AM, "Albert Y. C. Lai" wrote: > > On 12-09-29 09:57 PM, Vasili I. Galchin wrote: >> >> I would an examples of monads that are pure, i.e. no side-effects. > > > What does "side effect" mean, to you? Definition? When d

Re: [Haskell-cafe] Monads

2012-09-30 Thread Kristopher Micinski
On Sun, Sep 30, 2012 at 6:33 PM, Jake McArthur wrote: > > On Sep 30, 2012 10:56 AM, "Albert Y. C. Lai" wrote: >> >> On 12-09-29 09:57 PM, Vasili I. Galchin wrote: >>> >>> I would an examples of monads that are pure, i.e. no >>> side

Re: [Haskell-cafe] Monads

2012-09-30 Thread Albert Y. C. Lai
On 12-09-30 06:33 PM, Jake McArthur wrote: When discussing monads, at least, a side effect is an effect that is triggered by merely evaluating an expression. A monad is an interface that decouples effects from evaluation. I don't understand that definition. Or maybe I do subconsciousl

Re: [Haskell-cafe] Monads

2012-10-01 Thread Jon Fairbairn
"Albert Y. C. Lai" writes: > On 12-09-30 06:33 PM, Jake McArthur wrote: >> When discussing monads, at least, a side effect is an effect that is >> triggered by merely evaluating an expression. A monad is an interface >> that decouples effects from evaluati

Re: [Haskell-cafe] Monads

2012-10-01 Thread Albert Y. C. Lai
On 12-10-01 05:34 AM, Jon Fairbairn wrote: "Albert Y. C. Lai" writes: On 12-09-30 06:33 PM, Jake McArthur wrote: When discussing monads, at least, a side effect is an effect that is triggered by merely evaluating an expression. A monad is an interface that decouples effects from

[Haskell-cafe] are Monads with slightly stricter types in instances still Monads?

2007-01-30 Thread Julien Oster
mputation would be bound to operate on the same type, would this be without any undesirable implications? For the sake of understanding monads better, I tried to write several custom monads which may or may not be useful. Among those were: * The Tracker Monad - tracks every result of every s

Re: [Haskell-cafe] are Monads with slightly stricter types in instances still Monads?

2007-01-30 Thread Bryan Donlan
- join being a part of the fundamental theoretical structure of monads: join :: Monad m => m (m a) -> m a For the sake of understanding monads better, I tried to write several custom monads which may or may not be useful. Among those were: * The Tracker Monad - tracks every result of

[Haskell-cafe] Monads in Scala, XSLT, Unix shell pipes was Re: Monads in ...

2005-11-26 Thread Shae Matijs Erisson
Geoffrey Alan Washburn <[EMAIL PROTECTED]> writes: > Scala can do much better still because it has first-class functions and > algebraic data types ("case classes"). Comments on http://lambda-the-ultimate.org/node/view/1136 include links to Scala http://scala.epfl.ch/examples/files/simpleInterpr

[Haskell-cafe] continuations and monads

2013-08-17 Thread Christopher Howard
Q: Are the "continuations" in Scheme related to the "monads" from Haskell? If so, could someone elaborate on that? ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Monads from Functors

2009-04-08 Thread Sebastian Fischer
I recognized that Janis Voigtlaender defines the type `ContT` under the name `C` in Section 3 of his paper on "Asymptotic Improvement of Computations over Free Monads" (available at http://wwwtcs.inf.tu-dresden.de/~voigt/mpc08.pdf) and gives a monad instance without constraints on the f

[Haskell-cafe] Re: Parametrized monads

2009-06-15 Thread Ashley Yakeley
Miguel Mitrofanov wrote: Suppose I want to create a specific monad as a combination of monad transformers - something like "StateT smth1 (ReaderT smth2 Identity)". As you can see, each transformer is parametrized with a type of kind *. I want to abstract these parameters, so that instead of "St

[Haskell-cafe] Re: Parametrized monads

2009-06-15 Thread Miguel Mitrofanov
Probably. I have two objections against using type families. Both are pretty much theoretical. First, it seems to me that using type families would require some other extensions. Multi-parameter type classes are OK, but, in my experience, the road from them to the darkness of undecidable

[Haskell-cafe] Re: Parametrized monads

2009-06-15 Thread Ashley Yakeley
Miguel Mitrofanov wrote: First, it seems to me that using type families would require some other extensions. Multi-parameter type classes are OK, but, in my experience, the road from them to the darkness of undecidable instances is quite short, and I don't feel very safe on these grounds. Act

[Haskell-cafe] Re: Parametrized monads

2009-06-15 Thread Miguel Mitrofanov
What do you mean, without instances? How do you call "data instance" declarations? On 16 Jun 2009, at 02:16, Ashley Yakeley wrote: Miguel Mitrofanov wrote: First, it seems to me that using type families would require some other extensions. Multi-parameter type classes are OK, but, in my e

Re: [Haskell-cafe] Pesky monads...

2007-05-19 Thread Matthew Cox
at, 19 May 2007 19:49:40 +0100 Subject: [Haskell-cafe] Pesky monads... I've been getting some pretty weird complaints from the type checker. And I just figured out why! Grr... Is there any function that does the same thing as "until", but in a monad? __

Re: [Haskell-cafe] Pesky monads...

2007-05-19 Thread Andrew Coppin
exit the loop instead... Oh, wait, for some monads that fires an error. Hmm. Nice try. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Pesky monads...

2007-05-19 Thread Matthew Cox
else f x >>= untilM pred f Think of a computation in the State monad, a predicate will probably want to consult that state. Matthew Cox - Original Message - From: Matthew Cox To: Sent: Sat, 19 May 2007 13:10:40 -0600 Subject: Re: [Haskell-cafe] Pesky monads... You can define one:

Re: [Haskell-cafe] Pesky monads...

2007-05-19 Thread haskell
I previously worked out how to use the monad transformers to make a when / repeat control structure that admitted both break and continue statements. It uses a ContT monad transformer to provide the escape semantics and the Reader to store the continuation. I'll paste the code here: > -- By Chri

Re: [Haskell-cafe] Pesky monads...

2007-05-19 Thread Donald Bruce Stewart
matt: > It occurred to me that the predicate will generally be a monadic function > itself, so here's a > refined version: > > :: Monad m => (a -> m Bool) -> (a -> m a) -> a -> m a > untilM pred f x = do c <- pred x > if c then return x > else f x >

  1   2   3   4   5   6   7   8   9   10   >