On Fri, 2009-04-10 at 01:03 -0400, Brandon S. Allbery KF8NH wrote:
> On 2009 Apr 10, at 0:52, Jonathan Cast wrote:
> > On Fri, 2009-04-10 at 00:46 -0400, Brandon S. Allbery KF8NH wrote:
> >>> IO a ~ World -> (a, World)
> >>
> >> I still don't unders
On Fri, 2009-04-10 at 07:29 +0400, Miguel Mitrofanov wrote:
> On 10 Apr 2009, at 06:30, Jonathan Cast wrote:
> > do
> > s <- readFile "/my_file"
> > writeFile "/my_file" "Hello, world!\n"
> > threadDelay 1 --
On Fri, 2009-04-10 at 00:46 -0400, Brandon S. Allbery KF8NH wrote:
> On 2009 Apr 10, at 0:33, Heinrich Apfelmus wrote:
> > Luke Palmer wrote:
> >> Miguel Mitrofanov wrote:
> >>
> >>> I'm not sure what you mean by that, but semantically IO is
> >>> definitely
> *not* a state monad. Under any
On Thu, 2009-04-09 at 22:47 -0400, Brandon S. Allbery KF8NH wrote:
> On 2009 Apr 9, at 22:30, Jonathan Cast wrote:
> > On Thu, 2009-04-09 at 21:57 -0400, Brandon S. Allbery KF8NH wrote:
> >> On 2009 Apr 9, at 16:09, Luke Palmer wrote:
> >>> On Thu, Apr 9, 2009
On Thu, 2009-04-09 at 21:57 -0400, Brandon S. Allbery KF8NH wrote:
> On 2009 Apr 9, at 16:09, Luke Palmer wrote:
> > On Thu, Apr 9, 2009 at 1:33 PM, Miguel Mitrofanov
> > wrote:
> > I'm not sure what you mean by that, but semantically
> > IO is definitely
> >
On Thu, 2009-04-09 at 12:31 -0400, Brandon S. Allbery KF8NH wrote:
> On 2009 Apr 9, at 11:47, Mark Spezzano wrote:
> > How exactly do monads “solve” the problem of referential
> > transparency? I understand RT to be such that a function can be
> > replaced with a actual value.
> >
> > Since a mon
On Thu, 2009-04-09 at 01:24 +0200, Ben Franksen wrote:
> BTW, is this (ContT t) somehow related to the 'free monad' over t?
The free monad over t is just
data FreeMonad t a
= Return a
| JoinLift (t (FreeMonad t a))
instance Functor t => Monad (FreeMonad t) where
return = Return
On Wed, 2009-04-08 at 17:30 +0200, Thomas Davie wrote:
> On 8 Apr 2009, at 17:20, Jonathan Cast wrote:
>
> > On Wed, 2009-04-08 at 16:57 +0200, Thomas Davie wrote:
> >> We have two possible definitions of an "iterateM" function:
> >>
> >> it
On Wed, 2009-04-08 at 16:57 +0200, Thomas Davie wrote:
> We have two possible definitions of an "iterateM" function:
>
> iterateM 0 _ _ = return []
> iterateM n f i = (i:) <$> (iterateM (n-1) f =<< f i)
>
> iterateM n f i = sequence . scanl (>>=) (return i) $ replicate n f
>
> The former uses pr
On Tue, 2009-04-07 at 14:31 +0100, Neil Mitchell wrote:
> Hi
>
> >>> Is it me or the above package is not included in Hoogle?
> >>
> >> afair, Neil, being windows user, includes only packages available for
> >> his own system
> >>
> >> there was a large thread a few months ago and many peoples vot
On Thu, 2009-04-02 at 16:13 -0700, Lyle Kopnicky wrote:
> Hi folks,
>
> Since the time package is not included in ghc-6.10.2, I installed it
> via cabal. Then I tried to configure my project, and it says that the
> dependency is missing. Mysterious. Can anyone explain?
>
> l...@lwk-desktop:~/deve
On Sat, 2009-03-28 at 01:27 +0100, Henning Thielemann wrote:
> Jonathan Cast schrieb:
>
> >> i.e., that application's
> >> file decoding result should be an Either type that anticipates that
> >> the file encoding may be invalid.
> >
> > Th
On Fri, 2009-03-27 at 21:16 -0700, Donn Cave wrote:
> Quoth Henning Thielemann ,
> > On Fri, 27 Mar 2009, Donn Cave wrote:
> >
> >> Quoth Jonathan Cast ,
> >>
> >>> An `error' is any condition where the correct response is for the
> >>&
On Sat, 2009-03-28 at 12:51 +0300, Gregory Petrosyan wrote:
> On Sat, Mar 28, 2009 at 10:53 AM, Ketil Malde wrote:
> > So the difference between an exception or an error type is mainly what
> > you intend to do about it. There's no point in wrapping divisions in
> > Maybe unless you actually are
On Fri, 2009-03-27 at 14:26 -0700, Kirk Martinez wrote:
> Your powersOfTwo function, since it gets memoized automatically (is
> this the case for all functions of zero arguments?),
It is the case for all functions which have zero arguments *at the time
they are presented to the code generator*. T
On Fri, 2009-03-27 at 20:38 +0300, Gregory Petrosyan wrote:
> On Fri, Mar 27, 2009 at 7:31 PM, Donn Cave wrote:
> > Quoth John Lato ,
> >
> >> An exception is caused by some sort of interaction with the run-time
> >> system (frequently a hardware issue). The programmer typically can't
> >> check
On Fri, 2009-03-27 at 09:31 -0700, Donn Cave wrote:
> Quoth John Lato ,
>
> > An exception is caused by some sort of interaction with the run-time
> > system (frequently a hardware issue). The programmer typically can't
> > check for these in advance, but can only attempt to recover after
> > the
On Fri, 2009-03-27 at 12:24 +, Chris Kuklewicz wrote:
> Jonathan Cast wrote:
> > Sure. Which also points out that the original safeDiv wasn't actually
> > safe, since there's no guarantee of what evaluate will do with x and y.
> > (Actually, there's not
On Thu, 2009-03-26 at 21:57 -0400, wren ng thornton wrote:
> Jonathan Cast wrote:
> > Xiao-Yong Jin wrote:
> > > > Xiao-Yong Jin wrote:
> > > > > So I have another question. Is the following function safe
> > > > > and legitimate?
>
On Thu, 2009-03-26 at 17:27 -0500, Vasili I. Galchin wrote:
> ok .. how about API independent? ;^)
Last I checked VMS, OS/360 (NB: not dead by a long shot), etc. had APIs
too.
What you really mean is `does not break when run against Windows's
pseudo-POSIX API despite Microsoft's best efforts' :)
On Thu, 2009-03-26 at 17:16 -0500, Vasili I. Galchin wrote:
> Hello,
>
> I have been looking through Hackage and using Hoogle to "fork
> and execute" a program in an OS-independent way, i.e. neutral from
> POSIX and Win32 APIs. Does such a library function exist?
System.Process.createProces
On Thu, 2009-03-26 at 12:29 -0700, Thomas Hartman wrote:
> > I wonder if JHC
> > or some other compiler might work better with these examples?
>
> Are you saying that different compilers might give different answers?
>
> Yikes!
>
> Too clever indeed!
No, they might produce code with different p
On Thu, 2009-03-26 at 14:23 -0400, Xiao-Yong Jin wrote:
> Henning Thielemann writes:
>
> > On Thu, 26 Mar 2009, Xiao-Yong Jin wrote:
> >
> >> So I have another question. Is the following function safe
> >> and legitimate?
> >>
> >>> safeDiv :: (Exception e, Integral a) =>
> >>>a -> a
On Wed, 2009-03-25 at 22:32 +0100, Henning Thielemann wrote:
> On Wed, 25 Mar 2009, Jonathan Cast wrote:
>
> > On Wed, 2009-03-25 at 07:39 -0400, Xiao-Yong Jin wrote:
> >>
> >> Could you elaborate more about why this kind of breakage
> >> wouldn'
On Wed, 2009-03-25 at 21:18 +, Andrew Coppin wrote:
> I'M ON WINDOWS! ;-)
We've noticed...
jcc
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
On Wed, 2009-03-25 at 12:48 -0700, Dan Weston wrote:
> > However, there is something to be said for code that just looks like a
> > duck and quacks like a duck. It's less likely to surprise you.
> >
> > So... I insist... Easy for a beginner to read == better!
>
> All you have said is that one b
On Wed, 2009-03-25 at 10:00 -0700, Donn Cave wrote:
> Quoth Jonathan Cast :
> > On Wed, 2009-03-25 at 09:15 -0700, Donn Cave wrote:
>
> >> OK, these are interesting phenomena. From a practical point of view,
> >> though, I could see someone weighing the potentia
On Wed, 2009-03-25 at 09:15 -0700, Donn Cave wrote:
> Quoth Lennart Augustsson :
>
> > Some examples of what might happen:
>
> OK, these are interesting phenomena. From a practical point of view,
> though, I could see someone weighing the potential costs and benefits
> of a exception handler out
On Wed, 2009-03-25 at 15:32 +, Simon Marlow wrote:
> Jonathan Cast wrote:
> > On Wed, 2009-03-25 at 15:09 +, Simon Marlow wrote:
> >> the ordering that the state monad expects
> >> (and I can never remember which way around they are in
> >> Control.Mon
On Wed, 2009-03-25 at 03:01 +, Robin Green wrote:
> On Wed, 25 Mar 2009 08:25:40 -0700
> Jonathan Cast wrote:
>
> > Define
> >
> > swap (a, b) = (b, a)
>
> By the way, if you want to be "too smart", there's a generalised
> version
On Wed, 2009-03-25 at 15:09 +, Simon Marlow wrote:
> the ordering that the state monad expects
> (and I can never remember which way around they are in Control.Monad.State).
Really? I found it obvious once I figured out it how simple it made
(>>=). With the order from Control.Monad.State (w
On Wed, 2009-03-25 at 07:39 -0400, Xiao-Yong Jin wrote:
> Jonathan Cast writes:
>
> > On Tue, 2009-03-24 at 23:13 -0700, Donn Cave wrote:
> >> Quoth Duncan Coutts :
> >>
> >> > You must not do this. It breaks the semantics of the language.
> >>
On Tue, 2009-03-24 at 23:13 -0700, Donn Cave wrote:
> Quoth Duncan Coutts :
>
> > You must not do this. It breaks the semantics of the language.
> >
> > Other people have given practical reasons why you should not but a
> > theoretical reason is that you've defined a non-continuous function.
> > T
On Tue, 2009-03-24 at 16:43 -0700, Donn Cave wrote:
> If he really intended to promote some dumb code as a better
> alternative to some otherwise equivalent smart code,
`Smart' is Manlio's term --- or, rather, his characterization of his
friends' reaction upon seeing some inscrutable piece of (app
On Tue, 2009-03-24 at 23:15 +0100, Manlio Perillo wrote:
> Dan Piponi ha scritto:
> >> Miguel Mitrofanov wrote:
> >>> takeList = evalState . mapM (State . splitAt)
> >
> >> However, ironically, I stopped using them for pretty
> >> much the same reason that Manlio is saying.
> >
> > Are you saying
On Tue, 2009-03-24 at 22:43 +0100, Manlio Perillo wrote:
> Jonathan Cast ha scritto:
> > [...]
> >
> > I think, in general, the best way to document the purpose of the
> > function is
> >
> > -- | Split a function into a sequence of partitions of speci
On Tue, 2009-03-24 at 22:33 +0300, Eugene Kirpichov wrote:
> Pretty cool once you know what the function does, but I must admit I
> wouldn't immediately guess the purpose of the function when written in
> this way.
I wouldn't immediately guess the purpose of the function written in any
way.
I thi
On Tue, 2009-03-24 at 19:42 +0100, Manlio Perillo wrote:
> Tim Newsham ha scritto:
> >> These friends are very interested in Haskell, but it seems that the
> >> main reason why they don't start to seriously learning it, is that
> >> when they start reading some code, they feel the "Perl syndrome"
On Tue, 2009-03-17 at 12:59 +0100, Ketil Malde wrote:
> Duncan Coutts writes:
>
> >> [..] I have a sneaking suspicion [exceptions] actually *is* `unsafe'. Or,
> >> at
> >> least, incapable of being given a compositional, continuous semantics.
>
> > Basically if we can only catch exceptions in
On Tue, 2009-03-17 at 12:40 +, Claus Reinke wrote:
> >> So that first step already relies on IO (where the two are equivalent).
> > Come again?
>
> The first step in your implication chain was (without the return)
>
> throw (ErrorCall "urk!") <= 1
> ==> evaluate (throw (ErrorCall "urk
On Tue, 2009-03-17 at 13:06 +0100, Wolfgang Jeltsch wrote:
> Am Dienstag, 17. März 2009 10:54 schrieben Sie:
> > Wolfgang Jeltsch writes:
> > > By the way, the documentation of Control.Category says that a category is
> > > a monoid (as far as I remember). This is wrong. Category laws correspond
>
On Tue, 2009-03-17 at 01:16 +, Claus Reinke wrote:
> >> > > "exception handling" which allows to "catch" programming errors.
> >> > And which I have a sneaking suspicion actually *is* `unsafe'. Or, at
> >> > least, incapable of being given a compositional, continuous semantics.
> >> "A semanti
On Mon, 2009-03-16 at 22:01 +, Duncan Coutts wrote:
> On Mon, 2009-03-16 at 14:17 -0700, Jonathan Cast wrote:
> > On Mon, 2009-03-16 at 22:12 +0100, Henning Thielemann wrote:
> > > On Sun, 15 Mar 2009, Claus Reinke wrote:
> > >
> > > > import Data
On Mon, 2009-03-16 at 22:12 +0100, Henning Thielemann wrote:
> On Sun, 15 Mar 2009, Claus Reinke wrote:
>
> > import Data.IORef
> > import Control.Exception
> >
> > main = do
> > r <- newIORef 0
> > let v = undefined
> > handle (\(ErrorCall _)->print "hi">>return 42) $ case f v of
> > 0
On Sun, 2009-03-15 at 18:11 -0700, Ryan Ingram wrote:
> On Sun, Mar 15, 2009 at 1:56 PM, Jonathan Cast
> wrote:
> >> But not if you switch the (x <- ...) and (y <- ...) parts:
> >>
> >> main = do
> >> r <- newIORef 0
> >>
On Mon, 2009-03-16 at 01:04 +0100, Daniel Fischer wrote:
> Am Montag, 16. März 2009 00:47 schrieb Jonathan Cast:
> > On Mon, 2009-03-16 at 00:14 +0100, Daniel Fischer wrote:
> >
> > > > > However, I understand
> > > > > "unsafeInterleaveIO
On Mon, 2009-03-16 at 00:14 +0100, Daniel Fischer wrote:
> Am Sonntag, 15. März 2009 23:30 schrieb Jonathan Cast:
> > On Sun, 2009-03-15 at 23:18 +0100, Daniel Fischer wrote:
> > > Am Sonntag, 15. März 2009 22:20 schrieb Jonathan Cast:
> > > > There is *no* guaran
On Sun, 2009-03-15 at 23:18 +0100, Daniel Fischer wrote:
> Am Sonntag, 15. März 2009 22:20 schrieb Jonathan Cast:
> > There is *no* guarantee that main0 prints 0, while main1 prints 1, as
> > claimed. The compiler is in fact free to produce either output given
> > either p
On Sun, 2009-03-15 at 22:09 +0100, Daniel Fischer wrote:
> Am Sonntag, 15. März 2009 21:56 schrieb Jonathan Cast:
> > On Sun, 2009-03-15 at 21:43 +0100, Daniel Fischer wrote:
> > > Am Sonntag, 15. März 2009 21:25 schrieb Jonathan Cast:
> > > > On Sun, 2009-03-15 at
On Sun, 2009-03-15 at 21:43 +0100, Daniel Fischer wrote:
> Am Sonntag, 15. März 2009 21:25 schrieb Jonathan Cast:
> > On Sun, 2009-03-15 at 13:02 -0700, Ryan Ingram wrote:
> >
> > > Furthermore, due to the monad laws, if f is total, then reordering the
> > > (x &l
On Sun, 2009-03-15 at 13:02 -0700, Ryan Ingram wrote:
> unsafeInterleaveIO allows embedding side effects into a pure
> computation. This means you can potentially observe if some pure
> value has been evaluated or not; the result of your code could change
> depending how lazy/strict it is, which
On Sat, 2009-03-14 at 02:12 +1000, Matthew Brecknell wrote:
> Ross Paterson wrote:
> > No. Choose an arbitrary element shape :: f () and define
> >point x = fmap (const x) shape
>
> Interesting. Is the arbitrariness of the shape some sort of evidence
> that Pointed is not really a very u
On Sun, 2009-03-08 at 19:34 -0500, Bjorn Buckwalter wrote:
> Hi all,
>
> What is your preferred method of parsing floating point numbers (from
> String to Float/Double)? Parsec it seems only does positive floats out
> of the box and PolyParse requires the float to be on scientific form
> (exponent
On Thu, 2009-03-05 at 15:36 -0800, Daryoush Mehrtash wrote:
> In this chat server implementation
> http://www.haskell.org/haskellwiki/Implement_a_chat_server
>
> forkIO is used with fix as in:
>
> reader <- forkIO $ fix $ \loop -> do
>
> (nr', line) <- readChan chan'
> when (nr /
On Thu, 2009-03-05 at 13:08 +, Simon Marlow wrote:
> Lennart Augustsson wrote:
> > I don't see any breaking of referential transparence in your code.
> > Every time you do an IO operation the result is basically
> > non-deterministic since you are talking to the outside world.
> > You're assumi
On Wed, 2009-03-04 at 01:35 +0100, Henning Thielemann wrote:
> On Tue, 3 Mar 2009, Peter Verswyvelen wrote:
>
> > Now, does a similar theory exist of functions that always have one
> > input and one output, but these inputs and outputs are *always*
> > tuples? Or maybe this does not make any sense
On Thu, 2009-02-26 at 22:34 -0500, Brandon S. Allbery KF8NH wrote:
> There's something I'm missing in all of this.
>
> Perl is in the process of rebooting itself (perl6 is syntactically
> very different from perl5; the closest it's ever previously gotten to
> this kind of radical change was th
On Fri, 2009-02-27 at 00:04 +0100, Achim Schneider wrote:
> Jonathan Cast wrote:
> > (I am actually writing my own language;
> > when I get something usable for real work, I may very well just plain
> > un-subscribe from haskell-cafe, even though I will continue
On Thu, 2009-02-26 at 15:23 -0700, John A. De Goes wrote:
> On Feb 26, 2009, at 1:36 PM, Jonathan Cast wrote:
> > On Thu, 2009-02-26 at 13:25 -0700, John A. De Goes wrote:
> >> No, I hate C and will never use it again in my entire life unless
> >> forced to at the point
On Thu, 2009-02-26 at 22:45 +0100, Johan Tibell wrote:
> Hi all,
>
> I find it quite inconvenient to use the `recv` function in
> Network.Socket as it throws an exception when reaching EOF and there's
> no way to check whether EOF has been reached before calling `recv`.
> This means that all calls
On Thu, 2009-02-26 at 13:25 -0700, John A. De Goes wrote:
> No, I hate C and will never use it again in my entire life unless
> forced to at the point of a gun.
Why? Its libraries are far better, its editors are far better [1], its
compilers are far better, its tool support is far better, it's
On Thu, 2009-02-26 at 13:18 -0700, John A. De Goes wrote:
> Are you saying has been no progress since K&R C in the number of
> libraries available to C programmers? And that C programmers still
> have to edit files with vi and compile and link by specifying all
> files on the command-line?
>
On Thu, 2009-02-26 at 06:30 -0700, John A. De Goes wrote:
> On Feb 25, 2009, at 7:49 PM, Achim Schneider wrote:
> > "John A. De Goes" wrote:
> >
> >> The problem is that PL research is probably not going to stop
> >> evolving in our lifetimes. Yes, that research needs a venue, but why
> >> should
On Thu, 2009-02-26 at 13:52 +0100, Daniel Fischer wrote:
> Am Donnerstag, 26. Februar 2009 13:41 schrieb John Lato:
> > I didn't phrase this well. In the context of my argument, "design for
> > cross-platform" meant "avoid platform-limiting choices in the absence
> > of any compelling reasons othe
On Wed, 2009-02-25 at 17:54 -0700, John A. De Goes wrote:
> It's a chicken-egg thing. A Linux or OS X developer tries Haskell and
> finds he can write useful programs right away, with a minimum of fuss.
> But a Windows user tries Haskell and finds he has access to very few
> of the really goo
On Wed, 2009-02-25 at 10:18 -0800, Kim-Ee Yeoh wrote:
>
> Heinrich Apfelmus wrote:
> >
> > Now,
> >
> >(forall a. T[a]) -> S
> >
> > is clearly true while
> >
> >exists a. (T[a] -> S)
> >
> > should be nonsense: having one example of a marble that is either red or
> > blue does in no
On Wed, 2009-02-25 at 10:23 +, John Lato wrote:
> 4. Cross-platform concerns are something that responsible developers
> need to consider, just like localization and i18n. I.e., why
> *shouldn't* you think of that?
Sorry, wtf? I have a *responsibility* to design software for a
miserably poo
On Sat, 2009-02-21 at 07:25 -0700, John A. De Goes wrote:
> I think the (valid) concern is that too many people are choosing
> platform-specific packages when there are alternatives available
> (albeit not as convenient in some cases), and this really hurts the
> Windows community because Win
On Fri, 2009-02-20 at 09:17 +, Neil Mitchell wrote:
> Hi
>
> > 1) Show all the functions (when the number is low), but place platform
> > specific functions under separate headers: "Windows",
> > "Linux/BSD/POSIX", "OS X", etc.
>
> If a function isn't available on all OS's then all Hoogle wou
On Thu, 2009-02-19 at 23:06 +0200, Roman Cheplyaka wrote:
> * Wouter Swierstra [2009-02-19 11:58:38+0100]
> > There are several problems with this approach.
> >
> > For example, I can show:
> >
> > const 0 (head []) = 0
> >
> > But if I pretend that I don't know that Haskell is lazy:
> >
> > const
On Wed, 2009-02-18 at 16:28 +0100, Daniel van den Eijkel wrote:
> Dear Haskellers,
>
> please can anybody tell me what [::] means or where to read about it?
> A
> few days ago I saw this for the first time in my life, at the list of
> instances of the Functor class, and I don't know where to loo
On Mon, 2009-02-16 at 19:36 +0100, Wolfgang Jeltsch wrote:
> Am Montag, 16. Februar 2009 19:22 schrieb Wolfgang Jeltsch:
> > Am Montag, 16. Februar 2009 19:04 schrieb Kim-Ee Yeoh:
> > > Despite its rank-2 type, runST really doesn't have anything to do with
> > > existential quantification.
> >
> >
On Fri, 2009-02-13 at 21:57 +0100, Daniel Fischer wrote:
> Am Freitag, 13. Februar 2009 21:08 schrieb Jonathan Cast:
> > On Fri, 2009-02-13 at 12:15 -0700, John A. De Goes wrote:
> > > On Feb 13, 2009, at 12:07 PM, Jonathan Cast wrote:
> > > > Exactly! But if it
On Fri, 2009-02-13 at 12:15 -0700, John A. De Goes wrote:
> On Feb 13, 2009, at 12:07 PM, Jonathan Cast wrote:
> > Exactly! But if it fails, why on earth should any other use of map in
> > the module succeed?
> Because more information is known about other usages of map. Such
On Fri, 2009-02-13 at 12:06 -0700, John A. De Goes wrote:
> On Feb 13, 2009, at 11:49 AM, Jonathan Cast wrote:
> > It breaks type inference. I explained this at the time. I can
> > explain
> > it again:
> >
> > import Data.List
> >
On Fri, 2009-02-13 at 20:06 +0100, Daniel Fischer wrote:
> Am Freitag, 13. Februar 2009 19:49 schrieb Jonathan Cast:
> > On Fri, 2009-02-13 at 11:45 -0700, John A. De Goes wrote:
> > > On Feb 13, 2009, at 11:32 AM, Jonathan Cast wrote:
> > > > I believe the la
On Fri, 2009-02-13 at 11:45 -0700, John A. De Goes wrote:
> On Feb 13, 2009, at 11:32 AM, Jonathan Cast wrote:
> > I believe the last time it was brought up, the proposal was that type
> > inference should fail on certain typeable terms. That doesn't count.
>
>
&
On Fri, 2009-02-13 at 11:29 -0700, John A. De Goes wrote:
> On Feb 13, 2009, at 11:23 AM, Jonathan Cast wrote:
> > Usually `when no ambiguity can arise', no? Plenty of mathematical
> > practice rests on imprecision and the expectation that the human
> > reader
> &g
On Fri, 2009-02-13 at 11:12 -0700, John A. De Goes wrote:
> I come from a mathematical background (in which it is quite common to
> "overload" function names and operators in particular)
Usually `when no ambiguity can arise', no? Plenty of mathematical
practice rests on imprecision and the expe
On Fri, 2009-02-13 at 11:08 +0100, Heinrich Apfelmus wrote:
> Jonathan Cast wrote:
> >
> > NB: This example is *precisely* why I will never adopt MathML as an
> > authoring format. Bowing and scraping at the alter of W3C is not worth
> > using such a terrible syntax, n
On Fri, 2009-02-13 at 11:15 +1100, John Ky wrote:
> Hi Johnaton,
>
> Ah yes. That makes sense. Is there a way to define type r to be all
> types except functions?
Not without overlapping instances. I *think* if you turn on {-#
LANGUAGE OverlappingInstances #-} then
instance Broadcast r wher
On Fri, 2009-02-13 at 13:30 +1300, Richard O'Keefe wrote:
> Let's take this example from the web.
>x2 +
> 4x +
> 4
NB: This example is *precisely* why I will never adopt MathML as an
authoring format. Bowing and scraping at the alter of W3C is not worth
using such a terrible syntax,
On Thu, 2009-02-12 at 23:36 +, Edsko de Vries wrote:
> Hi,
>
> I can desugar
>
> do x' <- x
> f x'
>
> as
>
> x >>= \x -> f x'
>
> which is clearly the same as
>
> x >>= f
>
> However, now consider
>
> do x' <- x
> y' <- y
> f x' y'
>
> desugared, this is
>
>
On Fri, 2009-02-13 at 10:34 +1100, John Ky wrote:
> Hi Haskell Cafe,
>
> I tried using type families over functions, but when I try it
> complains that the two lines marked conflict with each other.
>
> class Broadcast a where
>type Return a
>broadcast :: a -> Return a
> instance Broadca
On Thu, 2009-02-12 at 19:04 +0100, Lennart Augustsson wrote:
> They are not unsafe in the way unsafePerformIO is,
I beg permission to demur:
newtype Unsafe alpha = Unsafe { unUnsafe :: alpha }
instance Typeable (Unsafe alpha) where
typeOf _ = typeOf ()
pseudoSafeCoerce :: alpha -> Mayb
On Fri, 2009-02-06 at 14:56 +0100, Deniz Dogan wrote:
> 2009/2/6 Jonathan Cast :
> > Emacs' terminal is also lacking all the modern conveniences, like
> > addressable cursors and builtin line-editing designed for 1970s printing
> > terminals and practically
On Fri, 2009-02-06 at 09:40 +0100, David Waern wrote:
> 2009/2/6 Max Rabkin :
> > On Thu, Feb 5, 2009 at 4:25 PM, David Waern wrote:
> >> As for running arbitrary commands, I think we are opening up to a lot
> >> of unfamiliar syntax. I'd like to hear what everyone thinks about
> >> that.
> >
> >
On Fri, 2009-02-06 at 08:30 +0100, Achim Schneider wrote:
> Jonathan Cast wrote:
> > On Mon, 2009-02-02 at 20:55 +, Andrew Coppin wrote:
> > > Deniz Dogan wrote:
> > > > Learn You a Haskell for Great Good (http://learnyouahaskell.com/)
> > >
> >
On Mon, 2009-02-02 at 20:55 +, Andrew Coppin wrote:
> Deniz Dogan wrote:
> > Learn You a Haskell for Great Good (http://learnyouahaskell.com/)
>
> Mmm, interesting.
>
> Does anybody else think it would be neat if GHCi really did colourise
> your input like that?
Bleah. More terminal hackin
On Fri, 2009-02-06 at 00:51 +0100, Peter Verswyvelen wrote:
> On Thu, Feb 5, 2009 at 8:20 PM, ChrisK
> wrote:
> Since this is strict there is no laziness and the code must
> evaluate the input and output "State RealWorld" to ensure they
> are not bottom or error.
> Interes
On Thu, 2009-02-05 at 15:52 -0800, David Leimbach wrote:
>
>
> On Thu, Feb 5, 2009 at 2:38 PM, Jonathan Cast
> wrote:
>
> On Thu, 2009-02-05 at 13:01 -0800, David Leimbach wrote:
> >
> >
> > On Thu, Fe
On Thu, 2009-02-05 at 13:01 -0800, David Leimbach wrote:
>
>
> On Thu, Feb 5, 2009 at 12:27 PM, Jonathan Cast
> wrote:
>
> On Thu, 2009-02-05 at 12:21 -0800, David Leimbach wrote:
> >
> >
> > On Thu, Fe
On Thu, 2009-02-05 at 16:11 -0500, Andrew Wagner wrote:
> So we all know the age-old rule of thumb, that unsafeXXX is simply
> evil and anybody that uses it should be shot (except when it's ok).
> I understand that unsafeXXX allows impurity, which defiles our ability
> to reason logically about h
On Thu, 2009-02-05 at 12:21 -0800, David Leimbach wrote:
>
>
> On Thu, Feb 5, 2009 at 11:25 AM, Andrew Wagner
> wrote:
> I think the point of the Monad is that it
> works as a container of stuff, that still
> allows mathemat
On Thu, 2009-02-05 at 20:46 +0100, Lennart Augustsson wrote:
> You are absolutely right. The statement
> "The values of the IO monad are programs that do IO. "
> is somewhat nonsensical. Values don't do anything, they just are.
Technically, programs don't do anything either. I think of values
On Thu, 2009-02-05 at 11:47 -0700, m...@justinbogner.com wrote:
> Jake McArthur writes:
> > m...@justinbogner.com wrote:
> > | Oops, sent this off list the first time, here it is again.
> > |
> > | Jake McArthur writes:
> > |> m...@justinbogner.com wrote:
> > |> | Bind is a sequencing operator ra
On Thu, 2009-02-05 at 01:10 +0100, Manlio Perillo wrote:
> Yitzchak Gale ha scritto:
> > In our case, the Python division first does a quick estimate
> > of the sizes of the two integers, and just returns zero if it
> > sees that there will be underflow on conversion to double.
> > So I made the fo
On Wed, 2009-02-04 at 23:55 +0200, Tymur Porkuian wrote:
> > Huh? You can't actually over-ride function application --- Haskell's
> > built-in application always does exactly the same thing, at every type.
> It's a metaphor.
Oh, right. That one word that means `inaccurate way of putting things'
On Wed, 2009-02-04 at 23:13 +0200, Tymur Porkuian wrote:
> Actually, I understand these types in terms of containers that
> override standard method of function application for their contents.
Huh? You can't actually over-ride function application --- Haskell's
built-in application always does ex
On Wed, 2009-02-04 at 22:16 +0200, Tymur Porkuian wrote:
> For me, the key to understanding monads was that monad is "a value
> that know how to apply functions to itself". Or, more correctly, a
> container that knows how to apply functions to whatever is inside it.
Close. (Monads are not `values
1 - 100 of 581 matches
Mail list logo