[Haskell-cafe] Lazy language on JVM/CLR

2010-02-08 Thread Tony Morris
as pure, lazy programming to run on the JVM in Java and Scala programming languages. I expect others have forethought and perhaps even experimented with such a language. Are there any dangers to be wary of that undo the entire endeavour? Thanks for any insights. -- Tony Morris http://tmorris.net

Re: [Haskell-cafe] What is the meaning of tilde ("~") symbol

2010-02-14 Thread Tony Morris
there is one on > Hackage without any instances: > http://hackage.haskell.org/package/algebra > I do too. I also wish there was an associative: class F f where k :: f a -> f a -> f a without the zero component. -- Tony Morris http://tmorris.net/

[Haskell-cafe] Retrospective type-class extension

2010-05-19 Thread Tony Morris
me to retrospectively apply such a notion? Ideally something like this would be handy if it could somehow be retrospectively applied: Monad <- Applicative <- Pointed <- Functor -- Tony Morris http://tmorris.net/ ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] Retrospective type-class extension

2010-05-19 Thread Tony Morris
Ivan Miljenovic wrote: > On 20 May 2010 14:42, Tony Morris wrote: > >> We all know that "class (Functor f) => Monad f" is preferable but its >> absence is a historical mistake. We've all probably tried once: >> >> instance (Functor f) => M

Re: [Haskell-cafe] Retrospective type-class extension

2010-05-20 Thread Tony Morris
(f a) -> f a >> >> This would be a great idea, for the sake of logic, first (a monad >> which is not a functor doesn't make sense), and also to eliminate >> redudancy (fmap = liftM, ap = (<*>), etc.) >> >> 2010/5/20 Tony Morris > <mailto:tonymor...@

Re: [Haskell-cafe] Type-Level Programming

2010-06-26 Thread Tony Morris
_ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe -- Tony Morris http://tmorris.net/ ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Getting the x out

2009-04-21 Thread Tony Morris
________ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -- Tony Morris http://tmorris.net/ ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] name for monad-like structure?

2009-04-28 Thread Tony Morris
__ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > Are you sure it supports (>>) :: m a -> m b -> m b and not mplus :: m a -> m a -> m a ? -- Tony Morris http://tmorris.net/ __

Re: [Haskell-cafe] Combining computations

2009-05-03 Thread Tony Morris
l.org/mailman/listinfo/haskell-cafe > Hi Michael, You'll want the Data.Maybe.listToMaybe and Data.Maybe.maybeToList functions. -- Tony Morris http://tmorris.net/ ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] instance Monad (Except err)

2009-05-04 Thread Tony Morris
_ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > I'm sure you could, but then ap /= (<*>). This seems related to a question that I once as

Re: [Haskell-cafe] instance Monad (Except err)

2009-05-04 Thread Tony Morris
gt; is useful as an error monad: > > instance Monad (Except e) where > (OK x) >>= f = f x > Failed e >>= _ = Failed e > return = OK > > This obeys all the monad laws. > > Thanks, > > Neil. > _

Re: [Haskell-cafe] Re: Non Empty List?

2009-06-04 Thread Tony Morris
to the functions that operate on the > structure, ie. the lookups, inserts, delete etc. > > Günther > > ___ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > --

Re: [Haskell-cafe] When folding is there a way to pick out the last point being processed?

2009-06-11 Thread Tony Morris
> Regards, > Casey > ___ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -- Tony Morris http://tmorris.net/ ___ Haskell-Cafe

Re: [Haskell-cafe] I need a hint in list processing

2009-06-14 Thread Tony Morris
to use it something like > > case all_choices sets of > [] -> there are no such choices > (first_choice:_) -> first_choice is one such choice > > For inputs like [[1,2],[2,1],[1]] there is of course no such > choice function. > > > _

Re: [Haskell-cafe] I need a hint in list processing

2009-06-14 Thread Tony Morris
Just guessing. How do you know it's an accident? Richard O'Keefe wrote: > > On 15 Jun 2009, at 4:26 pm, Tony Morris wrote: > >> Prelude Data.List> nub . concat $ [[2, 3], [1, 2], [2, 3, 4], [1, 2, 3]] >> [2,3,1,4] > > In this particular case. But that&#

[Haskell-cafe] List spine traversal

2009-06-28 Thread Tony Morris
Is there a canonical function for traversing the spine of a list? I could use e.g. (seq . length) but this feels dirty, so I have foldl' (const . const $ ()) () which still doesn't feel right. What's the typical means of doing this? -- Tony Morris htt

Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-06-30 Thread Tony Morris
ding the obvious (<+) for > 'flip mappend' which is sometimes useful. > > > I actually think this proposal is pretty excellent. I happen to agree. -- Tony Morris http://tmorris.net/ ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Library function for map+append

2009-08-18 Thread Tony Morris
t append > > but with less efficiency. Or am I wrong? > > Thanks > >Dusan > > ___ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > mapapp = ((++) .) . map

[Haskell-cafe] FOL

2007-06-04 Thread Tony Morris
; Bool l False q = not q l _ _ = True m :: Bool -> Bool -> Bool m p _ = not p n :: Bool -> Bool -> Bool -- implication n False _ = True n _ q = q o :: Bool -> Bool -> Bool -- negation of conjunction NAND o False _ = True o _ q = not q p :: Bool -> Bool ->

[Haskell-cafe] Memo + IORef

2007-06-16 Thread Tony Morris
I was told on #haskell (IRC) the other day that it is possible to write a general memoisation table using IORef and unsafePerformIO. I can't think of how this can be achieved without writing to a file, since a function cannot hold state between invocations. What am I missing? -- Tony Morris

[Haskell-cafe] Memoisation + unsafePerformIO

2007-07-08 Thread Tony Morris
) instance (Ord k) => Memo k v where memo f k = error("todo: binary tree") - -- Tony Morris http://tmorris.net/ -BEGIN PGP SIGNATURE- Version: GnuPG v1.4.6 (GNU/Linux) Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org iD8DBQFGkZlFmnpgrYe6r60R

[Haskell-cafe] CPS versus Pattern Matching performance

2007-07-10 Thread Tony Morris
-> b instead of pattern matching a returned Maybe value? Is there something a bit more concrete on this issue? -- Tony Morris http://tmorris.net/ ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] CPS versus Pattern Matching performance

2007-07-10 Thread Tony Morris
Thanks Don, Is your explanation specific to maybe? Or does that apply to all functions? Suppose the following function for lists: f :: [a] -> b -> (a -> [a] -> b) -> b ...instead of pattern matching [] and (x:xs) Tony Morris http://tmorris.net/ Donald Bruce Stewart wrote: >

Re: [Haskell-cafe] CPS versus Pattern Matching performance

2007-07-10 Thread Tony Morris
Thanks for the explanations - fully understood. Tony Morris http://tmorris.net/ Jonathan Cast wrote: > On Tuesday 10 July 2007, Tony Morris wrote: >> Thanks Don, >> Is your explanation specific to maybe? Or does that apply to all functions? >> >> Suppose the f

Re: [Haskell-cafe] Very freaky

2007-07-10 Thread Tony Morris
s and it gets a little confusing. A friend of mine has the > same problem with his category theory book. Same here! I found his Category Theory book quite difficult and I will have to revisit it. I have only just started TaPL, but I am enjoying it thor

Re: [Haskell-cafe] In-place modification

2007-07-15 Thread Tony Morris
ence. "Just ignore the rubbish and the rubbish will go away" usually works for me, but it isn't in this case. How about we all try it at once? Tony Morris http://tmorris.net/ -BEGIN PGP SIGNATURE- Version: GnuPG v1.4.6 (GNU/Linux) Comment: Using GnuPG with Mozilla -

[Haskell-cafe] Why does Data.Map exist when...

2007-07-16 Thread Tony Morris
, _) = a == a' instance (Ord a) => Ord (MyPair a b) where MP (a, _) `compare` MP(a', _) = a `compare` a' type Map' k a = Set (MyPair k a) - -- Tony Morris http://tmorris.net/ -BEGIN PGP SIGNATURE- Version: GnuPG v1.4.6 (GNU/Linux) Comment: Using GnuPG with

Re: [Haskell-cafe] Is this haskelly enough?

2007-07-17 Thread Tony Morris
-BEGIN PGP SIGNED MESSAGE- Hash: SHA1 David F. Place wrote: > The use of >>= is just an obscure way of saying (flip concatMap). Correction. The use of >>= is a more general way of saying (flip concatMap). Tony Morris http://tmorris.net/ -BEGIN PGP SIGNATURE-

[Haskell-cafe] Geometry

2007-08-26 Thread Tony Morris
ywords with which to google! - -- Tony Morris http://tmorris.net/ -BEGIN PGP SIGNATURE- Version: GnuPG v1.4.6 (GNU/Linux) Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org iD8DBQFG0iM6mnpgrYe6r60RAqfDAJ4gFAdr7zP1ehLl8H2MaCzCNfAvhQCgmL8D 4nrxrK13O9EBNv/ojPIMJXI= =eaxX --

Re: [Haskell-cafe] Spot the difference!

2007-09-19 Thread Tony Morris
Paul FYI If \_ -> foo confuses you, you might wish to use const foo instead. Tony Morris http://tmorris.net/ -BEGIN PGP SIGNATURE- Version: GnuPG v1.4.6 (GNU/Linux) Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org iD8DBQFG8fizmnpgrYe6r60RAqKBAKCKQ76HMtJ8jsgJ5nmX8ECROOcirQCfQgK

Re: [Haskell-cafe] Composition Operator

2007-09-21 Thread Tony Morris
ead that is up to you, but here is one way of reading it: "accepts a function a to c and returns a function. The function returned takes a function a to b and returns a function a to c" The expression f(g(x)) in C-style languages is similar to (f . g) x Tony Morris http://tmorris.net/

Re: [Haskell-cafe] Composition Operator

2007-09-22 Thread Tony Morris
-BEGIN PGP SIGNED MESSAGE- Hash: SHA1 Peter Verswyvelen wrote: > Tony Morris wrote: > >> is the same as: >> (.) :: (b -> c) -> ((a -> b) -> (a -> c)) >> .. >> "accepts a function a to c and returns a function. The function returned >&g

Re: [Haskell-cafe] Re: Wikipedia on first-class object

2007-12-29 Thread Tony Morris
> Please respect others who have signed up to Haskell-Cafe to discuss Haskell and not meaningless drivel. - -- Tony Morris http://tmorris.net/ Hey! We had 40,000 lines of C# here yesterday, but now there are 40 lines of... Dear God, what is a catamorphism?" -BEGIN PGP SIGNATU

Re: [Haskell-cafe] haskellwiki and Project Euler

2008-02-23 Thread Tony Morris
askell.org/mailman/listinfo/haskell-cafe You're going the right way about having the answers published in more ways than just the Haskell wiki. I'm only making a prediction, not a threat. -- Tony Morris http://tmorris.net/ ___ Haskell-Ca

[Haskell-cafe] Monad transformers, design

2010-07-31 Thread Tony Morris
ather impractical instance (Copointed m, Integral a) => Ints (InterT m a) where ints (InterT a) = ints (copoint a) {- So it seems that for some type-classes it is possible to implement for both the data type and the transformer, but not all type-classes. Is there a general approach t

Re: [Haskell-cafe] Monad transformers, design

2010-07-31 Thread Tony Morris
gah you're right, @mtl had confuzzled me. Well that changes things then, thanks. Ross Paterson wrote: > On Sat, Jul 31, 2010 at 10:56:31PM +1000, Tony Morris wrote: > >> -- Suppose some data type >> newtype Inter a = Inter (Int -> a) >> >> -- and

[Haskell-cafe] lambdacats

2010-08-05 Thread Tony Morris
Hello, does anyone happen to have the lambdacats page cached? The domain ( arcanux.org) and server have disappeared and the wayback machine doesn't have the images. -- Tony Morris http://tmorris.net/ ___ Haskell-Cafe mailing list Haskell

Re: [Haskell-cafe] lambdacats

2010-08-05 Thread Tony Morris
I wonder if the original site is recoverable from this, but I suspect there are some missing. On Fri, Aug 6, 2010 at 2:33 PM, Don Stewart wrote: > ivan.miljenovic: > > On 6 August 2010 14:12, Tony Morris wrote: > > > Hello, does anyone happen to have the lambdacats page ca

Re: [Haskell-cafe] Unwrapping newtypes

2010-09-08 Thread Tony Morris
t > such a seemingly trivial problem seems so hard to do. > > I am wondering if I am missing something really, really obvious. > > Any suggestions? Or is there perhaps a more Haskelly way to place type > constraints on a more generic type? > > Kevin > __

Re: [Haskell-cafe] Re: Unwrapping newtypes

2010-09-08 Thread Tony Morris
on how I could use that extension? > > Here is an example: {-# LANGUAGE GeneralizedNewtypeDeriving #-} class C a where c :: a -> Int data G = G instance C G where c _ = 7 newtype H = H G deriving C -- Tony Morris http://tmorris.net/ _

[Haskell-cafe] Network.HTTP, BasicAuth+Headers

2010-10-04 Thread Tony Morris
uest equivalent to the following curl: curl --basic -u "user:pass" -H "Accept: application/xml" -H "Content-type: application/xml" "https://host/path"; It seems with Network.Browser I cannot send headers, but with Network.HTTP I cannot see how to send the Basi

Re: [Haskell-cafe] Re: Re: A rant against the blurb on the Haskell front page

2010-10-16 Thread Tony Morris
been coined to (and probably actually does) sound more commerce > friendly. To countermand such an effect, we can point out that most > libraries have non-copyleft licenses and that there are a number of > companies who have done and still do a lot to support and advance Haskell. > &

[Haskell-cafe] Non-hackage cabal source

2010-11-02 Thread Tony Morris
download http://myhackage/packages/package/MyPackage-0.0.1.tar.gz : ErrorMisc "Unsucessful HTTP code: 404" Why is cabal even making this request? Why is it not making the request to http://myhackage/packages/MyPackage/0.0.1/MyPackage-0.0.1.tar.gz Thanks for any tips. -- Tony M

Re: [Haskell-cafe] Very silly

2008-10-13 Thread Tony Morris
C++ templates, implemented via run-time >>> dictionaries and other modules may define new instances >>> > >> Personally, I have no clue how C++ templates work [yet]. (As in, I'm > > they are known as generics in java/c# > > Except they're not. Java Generics are so

Re: [Haskell-cafe] About do notation.

2008-10-14 Thread Tony Morris
gt; > I cannot figure out what is the (>>) and (>>=) way of this. > > Thanks. ___ > Haskell-Cafe mailing list Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > getArgs >>= (\a -&g

Re: [Haskell-cafe] Function composition

2008-12-26 Thread Tony Morris
> > > -- > > _______ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe - -- Tony Morris ht

Re: [Haskell-cafe] Cal, Clojure, Groovy, Haskell, OCaml, etc.

2009-09-28 Thread Tony Morris
> - a community > > - good library > > - a package manager > > Thoughts? > -- > Regards, > Casey > ___ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mail

Re: [Haskell-cafe] Comments requested: succ Java

2009-09-29 Thread Tony Morris
John A. De Goes wrote: > write them yourself (at a cost of several to dozens of man years), Is that right? -- Tony Morris http://tmorris.net/ ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/hask

Re: [Haskell-cafe] Cal, Clojure, Groovy, Haskell, OCaml, etc.

2009-09-30 Thread Tony Morris
to understand stuff like that > might be to go thorugh it and convert it to use parens instead of $, > full application instead of ., and so on.) > > cjs > -- Tony Morris http://tmorris.net/ ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Applicative but not Monad

2009-10-30 Thread Tony Morris
g list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -- Tony Morris http://tmorris.net/ ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Working with multiple projects

2009-11-10 Thread Tony Morris
I have two projects that I intend to put on hackage soon. One depends on the other. I have "cabaled" both. I am wondering how others work with this kind of set up where changes are made to both libraries as they work. -- Tony Morris http://t

Re: [Haskell-cafe] Working with multiple projects

2009-11-11 Thread Tony Morris
I don't want to have to upload every time I make a minor change as I am working. Surely there is an easier way. Martijn van Steenbergen wrote: > Tony Morris wrote: >> I have two projects that I intend to put on hackage soon. One depends >> on the other. I have "cabaled&

Re: [Haskell-cafe] Implicit newtype unwrapping

2009-12-02 Thread Tony Morris
o ambiguous code? > > Thanks, > > Martijn. > ___ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -- Tony Morris http://tmorris.net/ ___

Re: [Haskell-cafe] Finding HP

2009-12-03 Thread Tony Morris
then in my own humble opinion, snapping back with "\"Are you sure this isn't a user error?\" is not a particularly nice response" is not a particularly nice response. -- Tony Morris http://tmorris.net/ ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Children elements with HXT

2009-12-22 Thread Tony Morris
pElem "tag" (xpWrap (uncurry Tag, k &&& v) (xpPair (xpAttr "k" xpText) (xpAttr "v" xpText))) When I run, I get the following result: Main> run = runX (xunpickleDocument xpWay [] "way.xml") [Way {tags = []}] Why is the tags list empty ins

Re: [Haskell-cafe] Children elements with HXT

2009-12-22 Thread Tony Morris
Adding (a_remove_whitespace,v_1) as a parser option when running solves it. Silly me. Tony Morris wrote: > I am trying to parse XML using HXT following > http://www.haskell.org/haskellwiki/HXT/Conversion_of_Haskell_data_from/to_XML > > Here is my XML file (way.xml): > > ver

[Haskell-cafe] (liftM join .) . mapM

2009-12-29 Thread Tony Morris
Can (liftM join .) . mapM be improved? (Monad m) => (a -> m [b]) -> [a] -> m [b] -- Tony Morris http://tmorris.net/ ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] ghc -e

2010-01-06 Thread Tony Morris
Can I import a module when using ghc -e? e.g. ghc -e "import Control.Monad; forM [[1,2,3]] reverse" -- Tony Morris http://tmorris.net/ ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] ghc -e

2010-01-06 Thread Tony Morris
Gwern Branwen wrote: > On Wed, Jan 6, 2010 at 7:23 PM, Tony Morris wrote: > >> ghc -e "import Control.Monad; forM [[1,2,3]] reverse" >> > > As of 6.10.2, the bug whereby the GHC API lets you use functions from > anywhere just by naming them (Java-st

Re: [Haskell-cafe] Language simplicity

2010-01-12 Thread Tony Morris
rise to me that C++ has the most > keywords. But then, if I were to add AMOS Professional, that had well > over 800 keywords at the last count... > > _______ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > Java has 53 reserved words. -

Re: [Haskell-cafe] Parse error

2010-01-17 Thread Tony Morris
____ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -- Tony Morris http://tmorris.net/ ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Maybe, maybe not.

2010-01-26 Thread Tony Morris
ensionally) possible total functions with >>> that type, as far as I can see :) >>> >> Is the other one... const? >> > > As far as I can tell, yes. > > -- Tony Morris http://tmorris.net/ ___ Haskell

Re: [Haskell-cafe] Maybe, maybe not.

2010-01-26 Thread Tony Morris
Ivan Miljenovic wrote: > 2010/1/27 Tony Morris : > >> It might be more obvious by giving: >> >> fromMaybe :: a -> (a -> x, x) -> x >> > > I actually found this more confusing, and am not sure of its validity: > should that be "May

[Haskell-cafe] 2D Array

2006-12-03 Thread Tony Morris
I wish to pass a 2 dimensional array to use in a back-tracking algorithm. Since I will be doing lots of inserts, a Data.Array is unsuitable. It seems that a Map Int (Map Int a) is the most suitable structure, but this seems cumbersome. Is there anything more appropriate? -- Tony Morris http

[Haskell-cafe] Memoisation

2007-02-25 Thread Tony Morris
5. I have already calculated the factorial of 5, but now I must do it again. I have thought of various ways of preventing this; perhaps passing an Array in a state monad. I'm wondering if there is a general solution for this kind of problem. Thanks for any tips. -- Tony Morris htt

[Haskell-cafe] Is Excel a FP language?

2007-04-24 Thread Tony Morris
guage, which I think is almost enough to fully support my position (emphasis on "almost"). -- Tony Morris http://tmorris.net/ ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] global variables

2007-05-17 Thread Tony Morris
t;global" also requires a declaration of the domain of discourse, which is decided arbitrarily and shifts many times throughout any real attempt to resolve the issue. Ever heard the phrase, "of course it works! it works on my machine!"? Tony Morris http://tmorris.net/ signature.asc

Re: [Haskell-cafe] Re: Memoization

2007-05-27 Thread Tony Morris
ntial quantifier looks like a backward capital E ∃ Look up "first-order logic" if you're interested in learning more about this topic. PS: What does OOC stand for? Out Of Curiosity? Tony Morris http://tmorris.net/ ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] The C Equiv of != in Haskell

2007-05-28 Thread Tony Morris
HHoogle, not Google, and rightly so. Did you take a look at the given link? Here it is again http://www.haskell.org/hoogle/?q=a%20-%3E%20a%20-%3E%20Bool Hold onto that jerky knee! Tony Morris http://tmorris.net/ signature.asc Description: OpenPGP digital signature _

Re: [Haskell-cafe] Traversals of monomorphic containers

2013-09-03 Thread Tony Morris
These questions are exactly what Control.Lens answers. On 04/09/2013 12:50 PM, "Mario Blažević" wrote: > On 09/02/13 06:53, Nicolas Trangez wrote: > >> # Redirected to haskell-cafe >> >> On Sun, 2013-09-01 at 14:58 +0400, Artyom Kazak wrote: >> >>> Would this be an appropriate place to propose a

Re: [Haskell-cafe] Using lenses

2013-10-03 Thread Tony Morris
Lenses for nested sum types e.g. Either. On 03/10/2013 6:08 PM, "Simon Peyton-Jones" wrote: > (I sent this to ‘libraries’ but Kim-Ee suggested adding Café, where so > many smart people hang out.) > > ** ** > > Friends > > ** ** > > Some of you will know that I’ve promised to give a talk

[Haskell-cafe] Test.QuickCheck.Gen

2008-05-01 Thread Tony Morris
he error?), or if the current scenario is acceptable. I'm seeking comments about this, thanks! - -- Tony Morris http://tmorris.net/ -BEGIN PGP SIGNATURE- Version: GnuPG v1.4.6 (GNU/Linux) Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org iD8DBQFIGjO6mnpgrYe6r60RAtohAK

[Haskell-cafe] lambdabot on GHC 6.8.2

2008-05-19 Thread Tony Morris
038) against GHC 6.8.2. Am I hitting this bug? If so, can I get around it to get a working lambdabot? Thanks for any tips. - -- Tony Morris http://tmorris.net/ -BEGIN PGP SIGNATURE- Version: GnuPG v1.4.6 (GNU/Linux) Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.

Re: [Haskell-cafe] zlib, missing zlib.h

2008-05-30 Thread Tony Morris
-BEGIN PGP SIGNED MESSAGE- Hash: SHA1 apt-get install zlib1g-dev Tony Morris http://tmorris.net/ Real-world problems are simply degenerate cases of pure mathematical problems. Thomas Hartman wrote: > Tried to install > > http://hackage.haskell.org/cgi-bin/hackage-script

Re: [Haskell-cafe] Having trouble with zip12..

2008-07-06 Thread Tony Morris
@check \x -> (nub . nub) x == nub x -- is nub idempotent? OK, passed 500 tests. - -- Tony Morris http://tmorris.net/ -BEGIN PGP SIGNATURE- Version: GnuPG v1.4.6 (GNU/Linux) Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org iD8DBQFIcS9LmnpgrYe6r60RAiDOAKCJlDaqNd5ssgxr

[Haskell-cafe] Applicative/Monad for Either

2009-01-21 Thread Tony Morris
`mappend` e2)) (Z (Left e1)) <*> (Z (Right _)) = Z (Left e1) (Z (Right _)) <*> (Z (Left e2)) = Z (Left e2) (Z (Right f)) <*> (Z (Right a)) = Z (Right (f a)) instance (Monoid e) => Monad (Z e) where return = pure (Z e) >>= f = error "todo" -- ? - -

Re: [Haskell-cafe] Function const (Binding)

2009-02-07 Thread Tony Morris
to get what I want) > > Thank you for your answers. > > Greetz TKM > > -- > > > ___ Haskell-Cafe > mailing list Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe - -- Tony

Re: [Haskell-cafe] Monad explanation

2009-02-09 Thread Tony Morris
has the type signature of a value. getChar has the signature RealWorld -> (RealWorld, Char) - -- Tony Morris http://tmorris.net/ * * Anteromedial Heterotopic Osseous Impingement Syndrome *

Re: [Haskell-cafe] Monad explanation

2009-02-09 Thread Tony Morris
ng, but one > must remember that IO is abstract. > > -- Lennart > > On Mon, Feb 9, 2009 at 10:26 AM, Tony Morris > wrote: Gregg Reynolds wrote: >>>> The point being that the metalanguage commonly used to >>>> describe IO in Haskell contains a logical cont

Re: [Haskell-cafe] Monad explanation

2009-02-09 Thread Tony Morris
ce if it ever > "gets in contact with" the top level it will be executed. But the > fact that IO types also behave as values makes Haskell a very > powerful imperative language. > > On Mon, Feb 9, 2009 at 11:14 AM, Tony Morris > wrote: You're right - my statement is ina

Re: [Haskell-cafe] Functor0?

2012-01-15 Thread Tony Morris
tinfo/haskell-cafe ? http://hackage.haskell.org/packages/archive/newtype/0.2/doc/html/Control-Newtype.html ? -- Tony Morris http://tmorris.net/ ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Not an isomorphism, but what to call it?

2012-01-19 Thread Tony Morris
> > ___ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe It is not clear to me exactly what you are asking, so shot in the dark: injection or surjection? - -- Tony Morris http

Re: [Haskell-cafe] Does somebody know about these functions?

2012-02-29 Thread Tony Morris
On 01/03/12 14:40, wren ng thornton wrote: > Of course, you can simplify the implementation by: > > inter f xs = zipWith f xs (tail xs) inter f = zipWith f <*> tail -- Tony Morris http://tmorris.net/ ___ Haskell-Cafe mailing li

[Haskell-cafe] Haskell source AST zipper with state

2012-05-02 Thread Tony Morris
Is there a library to traverse a source AST keeping state? -- Tony Morris http://tmorris.net/ ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Unit and pair

2012-05-08 Thread Tony Morris
g list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe data-lens has something similar (Tensor): http://hackage.haskell.org/packages/archive/data-lens/2.10.0/doc/html/Control-Category-Product.html -- Tony Morris http://tmorris.net/ ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Perth Functional Programmers meetup group launched

2012-06-13 Thread Tony Morris
askell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe -- Tony Morris http://tmorris.net/ ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Martin Odersky on "What's wrong with Monads"

2012-06-24 Thread Tony Morris
t; > > ___ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe -- Tony Morris http://tmorris.net/ ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Flipping type constructors

2012-08-13 Thread Tony Morris
ages/archive/TypeCompose/0.9.1/doc/html/src/Control-Compose.html#Flip I was wondering if there are any well-developed techniques to deal with this? Of course, I could just write my own Flip with the appropriate kinds and be done with it. Maybe there is a more suitable way? -- Tony Morris http:/

Re: [Haskell-cafe] Why Kleisli composition is not in the Monad signature?

2012-10-23 Thread Tony Morris
fe 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 -- Tony Morris http://tmorris.net/ ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] foldr (.) id

2012-10-26 Thread Tony Morris
ful when I need to > map a function over the list before composing. Does this function, or the > more general "foldr fmap id", defined in a library anywhere? I googled and > hoogled, but no luck so far. > > Thanks, > Greg > > > > __

[Haskell-cafe] Segment Tree based Set

2012-10-28 Thread Tony Morris
e seems like a more appropriate data structure to store the ranges. Does such a library exist? -- Tony Morris http://tmorris.net/ ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Segment Tree based Set

2012-10-28 Thread Tony Morris
Er, oops. ...can be implemented as: \a rs -> let s = Set.fromList (rs >>= \(a, b) -> [a..b]) in a `member` s Something like that! On Mon, Oct 29, 2012 at 2:48 PM, Tony Morris wrote: > Hi, > I was wondering if anyone knows of a package implementing a fast lookup > for

Re: [Haskell-cafe] Segment Tree based Set

2012-10-29 Thread Tony Morris
18:36, Roman Cheplyaka wrote: > If you searched hackage, you'd find > http://hackage.haskell.org/package/SegmentTree > > Roman > > * Tony Morris [2012-10-29 15:38:07+1000] >> Er, oops. >> >> ...can be implemented as: >> \a rs -> let s = Set.fromList (rs

Re: [Haskell-cafe] Segment Tree based Set

2012-10-29 Thread Tony Morris
Yeah that looks useful indeed. I am surprised there isn't a DIET on hackage. On Tue, Oct 30, 2012 at 3:55 AM, Stephen Tetley wrote: > Are Martin Erwig's "diets" anything close? > > http://web.engr.oregonstate.edu/~erwig/diet/ > > On 29 October 2012 04:48, To

Re: [Haskell-cafe] Control.bimap?

2012-12-12 Thread Tony Morris
_ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe -- Tony Morris http://tmorris.net/ ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] CoArbitrary

2013-02-08 Thread Tony Morris
" away the argument. I hope I have phrased this in a way to make the point. I found it a bit difficult to articulate and I do wonder (hope!) that others encounter similar scenarios. Thanks for any tips! -- Tony Morris http://tmorris.net/ _

Re: [Haskell-cafe] CoArbitrary

2013-02-10 Thread Tony Morris
ion that uses the argument?" -- fmap const -- type-checks, but ignores the argument, unlike e.g. QuickCheck which uses CoArbitrary to "perturb" that result with the argument. support libraries instance Functor Op where fmap f (DoubleOp g) = DoubleOp (f . g) fmap f

[Haskell-cafe] LambdaJam 2013

2013-03-04 Thread Tony Morris
et to the goal. So feel free to send me an email or I am on IRC (dibblego), lurking around the #haskell channel or privmsg if you like. Personally, I would love see more haskell submissions :) LambdaJam2013 call for papers: http://www.yowconference.com.au/lambdajam/Call.html -- Tony Morris

Re: [Haskell-cafe] mapFst and mapSnd

2013-05-30 Thread Tony Morris
class BinaryFunctor f where bimap :: (a -> c) -> (b -> d) -> f a b -> f c d mapFst = (`bimap id`) mapSnd = bimap id On 31/05/2013 12:16 PM, "Shachaf Ben-Kiki" wrote: > On Thu, May 30, 2013 at 7:12 PM, Shachaf Ben-Kiki > wrote: > > One generalization of them is to lenses. For example `lens` h

[Haskell-cafe] category-extras clash with transformers

2010-11-20 Thread Tony Morris
packages failed to install: category-extras-0.53.5 failed during the building phase. The exception was: ExitFailure 1 - -- Tony Morris http://tmorris.net/ -BEGIN PGP SIGNATURE- Version: GnuPG v1.4.10 (GNU/Linux) Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org

  1   2   >