Re: [Haskell-cafe] Unicode case (in)stability and Haskell identifiers.

2012-11-02 Thread Max Rabkin
I try to maintain some knowledge of Unicode issues, but this one never occurred to me. On Fri, Nov 2, 2012 at 10:28 AM, Richard O'Keefe wrote: > Would anyone care to see and comment on the proposal > before I send it to Unicode.org? Anyone got any suggestions > before I begin to write it? > I

Re: [Haskell-cafe] GHC rendering of non-ASCII characters configurable?

2012-07-30 Thread Max Rabkin
On Sun, Jul 29, 2012 at 8:04 PM, Richard Cobbe wrote: > This is annoying because all of the Unicode charts give the code points in > hex, and indeed the charts are split into different PDFs at numbers that > are nice and round in hex but not in decimal. So in order to figure out > which character

Re: [Haskell-cafe] Question on proper use of Data.IORef

2012-06-22 Thread Max Rabkin
On Fri, Jun 22, 2012 at 5:30 PM, Captain Freako wrote: >  12 main = do >  13 let theValue = 1 >  14 print theValue >  15 theValueRef <- newIORef theValue >  16 bump theValueRef >  17 return theValue theValue is a plain old immutable Haskell variable. "newIORef" creates an IORe

Re: [Haskell-cafe] Is protocol-buffers package maintainer reachable?

2012-04-23 Thread Max Rabkin
On Mon, Apr 23, 2012 at 15:01, Paul Graphov wrote: > And what should I do if he is > unreachable? My feeling is that if you are willing to take it on, you should ask this list if anybody objects to your taking over the maintainership, and if they do not, take it over (on Hackage, this just means

[Haskell-cafe] graphviz: dotizeGraph and graphToGraph not adding positions

2011-11-10 Thread Max Rabkin
My understanding of the documentation for Data.GraphViz.dotizeGraph and graphToGraph is that they should add position attributes to a graph. But they always seem to return graphs with empty attribute lists. What am I doing wrong in the following tiny example? > dotizeGraph nonClusteredParams (insN

Re: [Haskell-cafe] Package documentation complaints -- and a suggestion

2011-10-25 Thread Max Rabkin
On Tue, Oct 25, 2011 at 11:17, Ketil Malde wrote: > Ivan Lazar Miljenovic writes: > >> Right, but first we need to define what all those terms _mean_... and >> it's no good saying your package is "stable" if you change the API in >> a large-scale fashion every release. > > I think there are bette

Re: [Haskell-cafe] ANNOUNCE: vector-bytestring-0.0.0.0

2011-10-14 Thread Max Rabkin
On Fri, Oct 14, 2011 at 13:45, Ivan Lazar Miljenovic wrote: > Though I would argue that unless you're trying to actually use for > Show/Read for serialisation, does it really matter what the Show/Read > instances for Bytestring are? Convenient debugging and REPL interaction certainly matter! --M

Re: [Haskell-cafe] Package documentation complaints -- and a suggestion

2011-10-10 Thread Max Rabkin
On Mon, Oct 10, 2011 at 10:06, Paterson, Ross wrote: > Max Rabkin writes: >> But I also have a concrete suggestion for Hackage: include the package >> synopsis on the package's page. The distinction between synopsis and >> description can be confusing, and sometimes

Re: [Haskell-cafe] Package documentation complaints -- and a suggestion

2011-10-10 Thread Max Rabkin
On Mon, Oct 10, 2011 at 03:17, John Millikin wrote: > The package summary is "Type-safe ADT-database mapping library.", which > gives some idea about what it does. Whence my suggestion to show this on the package's page. Perhaps I shouldn't have hidden that at the bottom -- I meant this as my mai

[Haskell-cafe] Package documentation complaints -- and a suggestion

2011-10-09 Thread Max Rabkin
Hi all Following a link from the Yesod book, I arrived at [1], curious to find out what groundhog was. Once there, I learned... nothing: "This library provides just the general interface and helper functions. You must use a specific backend in order to make this useful." [1] http://hackage.haskel

Re: [Haskell-cafe] Converting wiki pages into pdf

2011-09-08 Thread Max Rabkin
This doesn't answer your Haskell question, but Wikpedia has PDF-generation facilities ("Books"). Take a look at http://en.wikipedia.org/wiki/Help:Book (for single articles, just use the "download PDF" option in the sidebar). --Max On Thu, Sep 8, 2011 at 14:34, mukesh tiwari wrote: > Hello all >

Re: [Haskell-cafe] Fixed points

2011-06-11 Thread Max Rabkin
On Fri, Jun 10, 2011 at 21:05, Alexander Solla wrote: > equivalenceClosure :: (Ord a) => Relation a -> Relation a > equivalenceClosure = fix (\f -> reflexivity . symmetry . transitivity) If you want to learn about fix, this won't help you, but if you're just want the best way to calculate equival

Re: [Haskell-cafe] ANN: dtd-text DTD parser, V0.1.0.0

2011-06-05 Thread Max Rabkin
On Sun, Jun 5, 2011 at 19:13, Yitzchak Gale wrote: > I really should have edited the Cabal description of this package > before I uploaded it. It promises an attoparsec-text parser > and blaze-builder renderer for DTDs. First of all, the renderer > is vaporware - I haven't written it yet. Just the

Re: [Haskell-cafe] Comment Syntax

2011-06-03 Thread Max Rabkin
On Fri, Jun 3, 2011 at 10:32, Guy wrote: > -- followed by a symbol does not start a comment, thus for example, haddock > declarations must begin with -- |, and not --|. > > What might --| mean, if not a comment? It doesn't seem possible to define it > as an operator. GHCi, at least, allows it. P

Re: [Haskell-cafe] Apache license, any drawbacks for Haskell packages?

2011-05-09 Thread Max Rabkin
On Mon, May 9, 2011 at 10:59, Jason Dagit wrote: > On Sun, May 8, 2011 at 1:25 PM, Magnus Therning wrote: >> >> Are there any drawbacks to using the Apache license for Haskell >> packages? > > I don't think so.  It looks to be almost identical to using BSD3, which is > already quite popular for h

Re: [Haskell-cafe] How to use cabal's data-files feature and run in-place?

2011-04-22 Thread Max Rabkin
On Fri, Apr 22, 2011 at 03:46, Richard Cobbe wrote: > Unfortunately, that's not happening.  Cabal is clearly generating the > module; I can see it in dist/build/autogen.  But my copy is overriding the > autogenerated one, even for cabal builds -- at least, that's what I'm > seeing when I run the b

Re: [Haskell-cafe] Encoding of Haskell source files

2011-04-04 Thread Max Rabkin
2011/4/4 Ketil Malde : > I think the safest thing to do is to require source to be ASCII, and > provide escapes for code points >127... I used to think that until I realised it meant having -- Author: Ma\xef N\xe5me In code, single characters aren't bad (does Haskell have something like Python's

Re: [Haskell-cafe] Learn You a Haskell for Great Good - a few doubts

2011-03-04 Thread Max Rabkin
On Fri, Mar 4, 2011 at 17:37, Chris Smith wrote: > The most common use of Ord in real code, to be honest, is to use the value > in some data structure like Data.Set.Set or Data.Map.Map, which requires Ord > instances.  For this purpose, any Ord instance that is compatible with Eq > will do fine.

Re: [Haskell-cafe] Why is there no "splitSeperator" function in Data.List

2011-02-13 Thread Max Rabkin
On Mon, Feb 14, 2011 at 07:52, Evan Laforge wrote: > the simple 'join :: > String -> [String] -> String' and 'split :: String -> String -> > [String]' versions work in enough cases. BTW, this "join" is Data.List.intercalate. --Max ___ Haskell-Cafe mai

Re: [Haskell-cafe] [Haskell] ANN: case-insensitive-0.1

2011-02-07 Thread Max Rabkin
Hi Bas This could be a useful package but can you add a note that this does not do correct Unicode-aware comparison on String (though AFAICT it is correct for Text)? --Max On Mon, Feb 7, 2011 at 02:06, Bas van Dijk wrote: > Dear all, > > I had this old module laying around that I wrote some tim

Re: [Haskell-cafe] Tool for evaluating "GHCi>" lines in a source file

2011-01-23 Thread Max Rabkin
On Sun, Jan 23, 2011 at 12:35, Steffen Schuldenzucker wrote: > > Hi, > > some time ago I read of a small tool that extracts lines like "GHCi> > some_expression" from a source file and appends GHCi's output to them. > Now I can't find it again. Does anyone remember its name? No, but I can guess (i

Re: [Haskell-cafe] Polymorphic function over pairs of maybes.

2010-12-28 Thread Max Rabkin
On Tue, Dec 28, 2010 at 21:23, Edward Amsden wrote: > (Int, (String, (Int, Int))) > > and another where each individual value is a Maybe of the > corresponding type, for example: > (Maybe Int, (Maybe String, (Maybe Int, Maybe Int))) This example demonstrates exactly why you might want to avoid do

[Haskell-cafe] Re: [Haskell] intent-typing

2010-11-15 Thread Max Rabkin
I still don't understand what intent typing is, but this particular problem is discussed (with a type-based, statically checked solution) at http://blog.moertel.com/articles/2006/10/18/a-type-based-solution-to-the-strings-problem --Max On Mon, Nov 15, 2010 at 17:17, Marcus Sundman wrote: > Hi,

Re: [Haskell-cafe] Serialization of (a -> b) and IO a

2010-11-11 Thread Max Rabkin
On Thu, Nov 11, 2010 at 11:25, Bob wrote: > I don't think I agree, I didn't see a rule f == g => serialise f == serialise > g anywhere. The rule a == b => f a == f b is called referential transparency (for denotational equality, not Eq) and is (perhaps the most important) part of what is meant b

Re: [Haskell-cafe] Haskell Weekly News: Issue 155 - October 20, 2010

2010-10-21 Thread Max Rabkin
On Thu, Oct 21, 2010 at 11:38, Ketil Malde wrote: >  Are there actually people > subscribed to -cafe, but *not* to hask...@? Yes. > And if so, why? Because... > I'm always getting two copies of everything in haskell@, since > everything is cross-posted to -cafe. :) --Max

Re: [Haskell-cafe] Re: Re-order type (flip map)

2010-10-10 Thread Max Rabkin
On Mon, Oct 11, 2010 at 00:51, Ozgur Akgun wrote: > My point was: you need to find/define two operators, not just one. That > still holds :) No it doesn't. f $ g $ h $ x == f (g (h x)) == f . g . h $ x == x $$ h $$ g $$ f if you have the correct associativity for ($$) --Max ___

Re: [Haskell-cafe] Coding conventions for Haskell?

2010-09-27 Thread Max Rabkin
On Mon, Sep 27, 2010 at 22:57, Andrew Coppin wrote: >  data Foo a b = >      Foo    a   | >      Bar      b | >      Foobar a b >    deriving (Eq, Ord) > > It honestly annoys me that Haddock disagrees with me on this point... I disagree with you too, and so does your version control (if I'm wrong

[Haskell-cafe] Higher-order algorithms

2010-08-23 Thread Max Rabkin
(Accidentally sent off-list, resending) On Mon, Aug 23, 2010 at 15:03, Eugene Kirpichov wrote: > * Difference lists > I mean that not only higher-order facilities are used, but the essence > of the algorithm is some non-trivial higher-order manipulation. If I'm not mistaken, we can "defunctiona

Re: [Haskell-cafe] Maybe to Either -- is there a better way?

2010-08-04 Thread Max Rabkin
On Tue, Aug 3, 2010 at 8:33 PM, Claude Heiland-Allen wrote: > {-# LANGUAGE TemplateHaskell, ScopedTypeVariables #-} > import Language.Haskell.Djinn (djinnD) > $(djinnD "maybeToEither" [t|forall a b . a -> Maybe b ->  Either a b|]) > main = print . map (maybeToEither "foo") $ [Nothing, Just "bar"]

Re: [Haskell-cafe] Is 'flip' really necessary?

2010-07-26 Thread Max Rabkin
On Mon, Jul 26, 2010 at 10:42 PM, Nils wrote: > On 26.07.2010 08:33, David Virebayre wrote: >> >> listeEtagTot = concatMap (`listeEtagArm` cfgTypesTringle) listeArmOrd > > You can use flip as a "wildcard" aswell: > >> listeEtagTot = concatMap (listeEtagArm `flip` cfgTypesTringle) listeArmOrd > > M

Re: [Haskell-cafe] Random this! ;-)

2010-07-25 Thread Max Rabkin
On Sun, Jul 25, 2010 at 5:39 PM, michael rice wrote: > > I know, ugly, but at least I got it to work. What's a better way to generate > this list? rollNDiceIO n = sequence . replicate n $ randomRIO (1,6) {{ sequence . replicate n = replicateM n }} = replicateM n $ randomRIO (1, 6) --Max _

Re: [Haskell-cafe] Heavy lift-ing

2010-07-24 Thread Max Rabkin
On Sat, Jul 24, 2010 at 4:08 PM, aditya siram wrote: > I wouldn't-it was a bad example. My only point was that because of the > way (>>=) is implemented for lists the order of the arguments 'a' and > 'b' in 'liftM2 f a b' matters. > > -deech No, it's not. The type of liftM2 makes this clear: lif

Re: [Haskell-cafe] A question about State Monad and Monad in general

2010-07-19 Thread Max Rabkin
On Mon, Jul 19, 2010 at 10:17 AM, Ketil Malde wrote: > At it's heart, monads are "just" syntactic convenience, but like many > other syntactic conveniences, allows you to structure your code better. > Thus it's more about programmer efficiency than program efficiency. > (The "do notation" is synta

Re: [Haskell-cafe] Design for 2010.2.x series Haskell Platform site

2010-07-17 Thread Max Rabkin
On Sat, Jul 17, 2010 at 1:43 AM, Don Stewart wrote: > Here's a first cut in the repo with the new design converted to CSS > >    http://code.haskell.org/haskell-platform/download-website/ > > If anyone would like to clean it up further, please send me patches to > the style.css file or index.html.

Re: [Haskell-cafe] whine and solution about programmers not respecting documentations

2010-06-29 Thread Max Rabkin
On Tue, Jun 29, 2010 at 11:46 AM, Ketil Malde wrote: >  deleteBy :: (a -> Bool) -> [a] -> [a] > > I don't think there would be any doubt what 'deleteBy (<= 5) [1..10]' > would do. And I just don't see what the requirement for an equivalence > relation buys you. Your deleteBy is (filter . not), is

Re: [Haskell-cafe] Huffman Codes in Haskell

2010-06-22 Thread Max Rabkin
On Tue, Jun 22, 2010 at 10:18 PM, Andrew Coppin wrote: > Don Stewart wrote: >> >>    http://hackage.haskell.org/package/huffman >> >>    A simple and pure Haskell implementation of the Huffman encoding >> algorithm. >> > > What the...? > > Oh, I see. It uses another package to handle the tricky so

Re: [Haskell-cafe] name of this monadic combinator?

2010-05-30 Thread Max Rabkin
On Sun, May 30, 2010 at 8:15 PM, Mike Dillon wrote: > That second search also shows zipWith in there; I never really thought > about zipWith being like liftM2 for the list Monad. I don't believe > that's actually true for the normal list Monad, but it should be true of > an alternate list Monad al

Re: [Haskell-cafe] Google Summer of Code: BlazeHTML RFC

2010-05-28 Thread Max Rabkin
On Thu, May 27, 2010 at 2:44 PM, Pierre-Etienne Meunier wrote: > ** Advertisement ** > Have you tried the library I have written, Data.Rope ? > ** End of advertisement ** > The algorithmic complexity of most operations on ropes is way better than on > bytestrings : log n for all operations, except

Re: [Haskell-cafe] ANNOUNCE: gt-tools-0.1.4

2010-05-07 Thread Max Rabkin
On Fri, May 7, 2010 at 4:12 AM, Felipe Lessa wrote: > On Thu, May 06, 2010 at 09:30:50PM +0300, Sergei Trofimovich wrote: >> /me wonders if Miss lambdabot might like to have such functionality. >> What do you think? > > Do the terms of use of Google Translate allow it? I can't remember, but they

Re: [Haskell-cafe] Re: Re: instance Eq (a -> b)

2010-04-21 Thread Max Rabkin
On Wed, Apr 21, 2010 at 1:44 AM, Edward Kmett wrote: > Eq doesn't state anywhere that the instances should be structural, though in > general where possible it is a good idea, since you don't have to worry > about whether or not functions respect your choice of setoid. Wikipedia's definition of s

[Haskell-cafe] Garbage collecting pointers

2010-03-26 Thread Max Rabkin
On Fri, Mar 26, 2010 at 11:21 PM, Brandon S. Allbery KF8NH wrote: > On Mar 26, 2010, at 16:28 , Mads Lindstrøm wrote: >> >> For some time I have been thinking about an idea, which could limit >> Haskell's memory footprint. I don't know if the idea is crazy or clever, > > This is called pointer tag

[Haskell-cafe] Syntax programming with lexemes rather than trees?

2010-03-24 Thread Max Rabkin
[Sorry for the accidental off-list reply, Neil] On Tue, Mar 23, 2010 at 10:43 PM, Neil Mitchell wrote: > It actually sounds like your representation has structure, but you > dislike structure because it's hard to work with. It seems to me like the data has structure, but that data is not treelik

Re: [Haskell-cafe] First time haskell - parse error!

2010-03-10 Thread Max Rabkin
On Wed, Mar 10, 2010 at 3:53 PM, Stephen Tetley wrote: >   where odds = iterate (+2) 1 Or odds = [1,3..] --Max ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Computing sums

2010-02-20 Thread Max Rabkin
On Sat, Feb 20, 2010 at 9:10 PM, Andrew Coppin wrote: > PS. Epic, epic comment spam. Yeah, sorry. Every now and again I decide I should deal with it. Then I rediscover that it takes about four clicks to delete each comment. Basically, I leave my blog alone until I have something (hopefully) inter

Re: [Haskell-cafe] Virus alert while installing happstack

2010-02-14 Thread Max Rabkin
On Mon, Feb 15, 2010 at 11:28 AM, Marc Weber wrote: > unlikely. If you're in doubt you should compile from source and also > check the source which was used to compile ghc .. etc. I want to say if > you really want to be secure the amount of work is infinity. http://cm.bell-labs.com/who/ken/trust

Re: [Haskell-cafe] Collection of sets containing no sets which are a subset of another in the collection

2009-11-14 Thread Max Rabkin
On Sat, Nov 14, 2009 at 9:21 AM, Mark Wassell wrote: > Hi, > > I am looking for a data structure that will represent a collection of sets > such that no element in the collection is a subset of another set. In other > words, inserting an element that is already a subset of another element will > r

Re: [Haskell-cafe] Re: Writing great documentation

2009-11-13 Thread Max Rabkin
On Fri, Nov 13, 2009 at 10:58 PM, Simon Michael wrote: > A very common problem with online docs is fragmentation. Absolutely! Is it possible to include non-haddock documentation in a cabal package. Is it possible to have it readable on Hackage? I think this would help with the fragmentation and v

[Haskell-cafe] Writing great documentation

2009-11-13 Thread Max Rabkin
Haskellers, I have heard many complaints about the average quality on documentation. Therefore, I'd like to encourage you all to read Jacob Kaplan-Moss's series on writing great documentation: http://jacobian.org/writing/great-documentation/. The articles are themselves well-written and contain ex

[Haskell-cafe] Haskell image libraries

2009-11-08 Thread Max Rabkin
Haskellers, To add image support to fdo-notify, I need an image type. Looking through Hackage, I didn't find any image library with the following features: * Load from a variety of formats (at least PNG and JPG, I'd say) * Efficient per-pixel access, or a way to dump the image into a ByteString as

[Haskell-cafe] ANN: fdo-notify 0.1, a client for the Desktop Notifications protocol

2009-11-04 Thread Max Rabkin
Haskellers, I present to you fdo-notify, a client library for FreeDesktop.org's Desktop Notifications protocol. This is the DBUS protocol served by NotifyOSD and other notifications systems, which allows a wide variety of applications to present notifications to the user in a uniform way. The lib

Re: [Haskell-cafe] Re: Haskell Weekly News: Issue 137 - October 31, 2009

2009-11-02 Thread Max Rabkin
On Mon, Nov 2, 2009 at 6:42 AM, Benjamin L.Russell wrote: > Hey, careful now No need to start another Emacs vs. the other > 'editor' flamewar ... lest someone run "M-x nethack" and summon a > Demogorgon against you ... er, make that "M-x haskellhack," since a > Haskell version needs to be crea

Re: [Haskell-cafe] Haskell Weekly News: Issue 134 - October 10, 2009

2009-10-11 Thread Max Rabkin
Why don't you subscribe to haskell? It's much lower volume, and I think it's a better option than taking -beginners off-topic. --Max On Sun, Oct 11, 2009 at 2:10 PM, Patrick LeBoutillier wrote: > Hi, > > Could/should the Haskell Weekly News be posted to the beginners list as > well? > > I normal

Re: [Haskell-cafe] Haskell for Physicists

2009-09-30 Thread Max Rabkin
mming language. HTH, Max On Wed, Sep 30, 2009 at 9:39 PM, Khudyakov Alexey wrote: > В сообщении от Среда 30 сентября 2009 23:29:32 Max Rabkin написал: >> On Wed, Sep 30, 2009 at 9:24 PM, Alberto G. Corona > wrote: >> > Haskell: mathematics beyond numerical calculus >&g

Re: [Haskell-cafe] Haskell for Physicists

2009-09-30 Thread Max Rabkin
On Wed, Sep 30, 2009 at 9:24 PM, Alberto G. Corona wrote: > Haskell: mathematics beyond numerical calculus I'd imagine most physicists know a fair bit of mathematics beyond numerical calculus; what they might not know much about is *computation* beyond numerical calculus. --Max _

Re: [Haskell-cafe] why these two are not equivalent?

2009-09-13 Thread Max Rabkin
On Sat, Sep 12, 2009 at 9:52 PM, Diego Souza wrote: > I assumed Data.Map was a tree internally and keep elements ordered, so > the following would sort the input and print duplicates in O(n log n), > as the C++ version does: > > sbank :: [B.ByteString] -> [(B.ByteString,Int)] > sbank = toAscList .

Re: [Haskell-cafe] Re: Darcs and NFS Resolution

2009-09-12 Thread Max Rabkin
On Sat, Sep 12, 2009 at 5:22 PM, Trent W. Buck wrote: > Ew.  I'm not keen on calling mv(1) to handle each rename, let alone via > sh (which WILL explode on some paths, and allow injection attacks). rawSystem does not use sh (hence the "raw") --Max ___

Re: [Haskell-cafe] Mapping over multiple values of a list at once?

2009-08-27 Thread Max Rabkin
My first approach would be to generate the list of sliding windows: [[4,3,2],[3,2,6],[2,6,7]] after importing Data.List: > map (take 3) . tails $ [4,3,2,6,7] [[4,3,2],[3,2,6],[2,6,7],[6,7],[7],[]] Not quite what we want, but close: > filter ((== 3) . length) . map (take 3) . tails $ [4,3,2,6,7]

Re: [Haskell-cafe] Re: Thinking about what's missing in our library coverage

2009-08-04 Thread Max Rabkin
On Tue, Aug 4, 2009 at 11:56 PM, Magnus Therning wrote: >> >> AIUI, on systems with working package managers, HP will be a >> metapackage which depends on the appropriate "real" packages. > > Yes, but again, the role of HP shouldn't be to limit the pain of installing > bindings to C libraries.  Wha

Re: [Haskell-cafe] Re: Thinking about what's missing in our library coverage

2009-08-04 Thread Max Rabkin
On Tue, Aug 4, 2009 at 6:13 PM, Magnus Therning wrote: > AFAIU the plan is to separate GHC and its "platform packages", so in > the future it might not be that easy to get to the point where you > _can_ run 'cabal install'. Absolutely not. The point of HP is to make the path from bare OS to comple

Re: [Haskell-cafe] n00b question: defining datatype

2009-07-23 Thread Max Rabkin
On Thu, Jul 23, 2009 at 8:43 PM, Iain Barnett wrote: > data Task = Task { title :: String, completed :: Bool, subtasks :: [Task] } > But that's not really right, because obviously, some tasks don't have > subtasks. The empty list is a list. --Max ___ Ha

Re: [Haskell-cafe] Re: Simple quirk in behavior of `mod`

2009-07-23 Thread Max Rabkin
2009/7/23 Matthias Görgens : >> Couldn't the same be said for round-to-even, instead of rounding down >> like every other language? I doubt any beginners have ever expected >> it, but it's probably better. > > What do you mean with round-to-even?  For rounding down there's floor. Round-to-even mea

Re: [Haskell-cafe] homomorphic encryption and monads?

2009-07-15 Thread Max Rabkin
On Wed, Jul 15, 2009 at 11:54 PM, Jason Dagit wrote: > Hello, > > I have just a very vague understanding of what homomorphic encryption is, > but I was wondering if homomorphic encryption behaves as a one-way monad > (like IO). An interesting idea. Let's see where this leads. > I could be mistake

Re: [Haskell-cafe] Python vs Haskell in tying the knot

2009-07-15 Thread Max Rabkin
On Wed, Jul 15, 2009 at 7:33 PM, Cristiano Paris wrote: > fib = 1:1:fib `plus` (tail fib) where plus = zipWith (+) > > Of course, this was something I already encountered when exploring the > Y-combinator. Anyhow, I tried to translate this implementation to > Python using Iterators and this is what

Re: [Haskell-cafe] Implementing Las Vegas algorithms in Haskell

2009-07-07 Thread Max Rabkin
2009/7/7 Antoine Latter : > If I were writing it as a library function, I would leave the function > as you described and let the caller make the choice. Calling into > randomIO in a library function is extremely dubious, as a second > library could be getting and setting the random seed used by ra

Re: [Haskell-cafe] ANN: AC-Vector, AC-Colour and AC-EasyRaster-GTK

2009-07-04 Thread Max Rabkin
On Sat, Jul 4, 2009 at 9:18 PM, Andrew Coppin wrote: >>> 2. It's mind-blowingly complex. >>> >> >> Colour *is* complex. Which is why I'm so glad Russell O'Connor did all >> the hard work for me :) >> > > Well, no, because now I'm going to have to spend a few hours trying to find > out what CIE is b

Re: [Haskell-cafe] ANN: AC-Vector, AC-Colour and AC-EasyRaster-GTK

2009-07-04 Thread Max Rabkin
On Sat, Jul 4, 2009 at 8:38 PM, Andrew Coppin wrote: > A few reasons: > > 1. I never knew it existed. ;-) A good reason. However, it's good to do a quick search over Hackage before uploading (or before writing) so you know what's out there. Also, if you hadn't used an "AC-" prefix, you'd have had

Re: [Haskell-cafe] Half-integer

2009-06-28 Thread Max Rabkin
On Sun, Jun 28, 2009 at 9:29 PM, Andrew Coppin wrote: >> Which versions of base have you tested it with?  :-) >> > > Whichever one GHC 6.10.3 ships with... "ghc-pkg list base" will tell you which version you have installed. > Frankly, I highly doubt it makes any difference either way. (Does anybo

Re: [Haskell-cafe] Another question about unsafePerformIO

2009-06-25 Thread Max Rabkin
On Thu, Jun 25, 2009 at 3:49 PM, John Meacham wrote: > However, if the algorithm takes a signifigant amount > of time or resources, you may want to keep it in IO just so users can > have control over exactly when and how often it is run. If you had a pure function written in Haskell that used a lo

Re: [Haskell-cafe] ICFP contest

2009-06-24 Thread Max Rabkin
I'm part of a fairly large team. I'm the only person on the team who's done more than Project Euler problems in Haskell, so we'll probably only use Haskell if there's a library or program that does exactly what we need for some task. Likely we'll be using Perl and Python, and C++ if there's any hea

Re: [Haskell-cafe] How to determine if a FilePath is a directory name or regular file?

2009-06-22 Thread Max Rabkin
On Mon, Jun 22, 2009 at 2:54 PM, Deniz Dogan wrote: > Are you saying that when a function is named "isDirectory" you expect > it to only check for a trailing forward slash character? No. I'm saying that *if* isDirectory existed, then (isDirectory "/no/such/directory/") should equal true on Unix. I

Re: [Haskell-cafe] How to determine if a FilePath is a directory name or regular file?

2009-06-22 Thread Max Rabkin
On Mon, Jun 22, 2009 at 2:09 PM, Deniz Dogan wrote: > I think see what you mean, but I find the argument more of an excuse > to the poor naming than a solid argument for it. Following the > convention and intuition that most users have should be more important > than making the (sometimes unnecessa

Re: [Haskell-cafe] Installing agda through cabal

2009-06-19 Thread Max Rabkin
On Fri, Jun 19, 2009 at 11:20 PM, Paulo J. Matos wrote: > Shouldn't cabal make sure the library it installs are in PATH? This would require modifying the path (since there may be no writable location on the existing path). But the PATH is set by a combination of several programs written in Turing-

Re: [Haskell-cafe] curious about sum

2009-06-17 Thread Max Rabkin
On Wed, Jun 17, 2009 at 1:07 PM, Henk-Jan van Tuyl wrote: > On Wed, 17 Jun 2009 10:38:23 +0200, Yitzchak Gale wrote: > An improved reverse function: >    reverse' = foldl' (flip (:)) [] > There is no need for reverse to be lazy, so this one could replace the > original one. > reverse' is not too s

Re: [Haskell-cafe] web musing

2009-06-05 Thread Max Rabkin
On Fri, Jun 5, 2009 at 5:18 PM, Conor McBride wrote: > > Will I need to ask systems support to let me install some > haskelly sort of web server? Looks likely, I suppose. > > In general, what's an easy way to put a web front end on > functionality implemented in Haskell? > For something this simpl

Re: [Haskell-cafe] [] == []

2009-05-29 Thread Max Rabkin
On Fri, May 29, 2009 at 12:29 PM, Paul Keir wrote: > f''' = ([]::[()]) == ([]::[()]) > > (Very pretty.) > > So why doesn't ghc have 'default' instances? It does. I believe Num defaults to Integer and then to Double. Generally, though, defaults are convenient in exploratory usage but confusing in

Re: [Haskell-cafe] Re: Error message reform (was: Strange type error with associated type synonyms)

2009-05-27 Thread Max Rabkin
On Thu, May 28, 2009 at 12:03 AM, Jeff Wheeler wrote: > I absolutely agree about expected/inferred. I always forget which is > which, because I can figure both could apply to each. That's actually true for me too. When you say it like that, I remember times when I've had the same confusion. > Be

[Haskell-cafe] Error message reform (was: Strange type error with associated type synonyms)

2009-05-27 Thread Max Rabkin
On Wed, May 27, 2009 at 11:05 PM, Bulat Ziganshin wrote: > i mean just changing the words to make obvious what type was got in > what way. and check it on beginners who don't yet read your > explanations, for example teachers may test it on their students > > my English is limited... for example,

Re: Re[4]: [Haskell-cafe] Strange type error with associated type synonyms

2009-05-27 Thread Max Rabkin
On Wed, May 27, 2009 at 10:28 PM, Bulat Ziganshin wrote: > can you recall early times of your work with GHC? i think that these > words are non-obvious for novices. finally it becomes part of your instincts > as anything else often used. but it can be learning barrier. overall, > hard-to-understan

Re: Re[2]: [Haskell-cafe] Strange type error with associated type synonyms

2009-05-27 Thread Max Rabkin
On Wed, May 27, 2009 at 9:59 PM, Bulat Ziganshin wrote: > Hello Simon, > > Wednesday, May 27, 2009, 11:42:22 PM, you wrote: > > while we are here - i always had problems understanding what is > inferred and what is expected type. may be problem is just that i'm > not native speaker > > are other,

Re: [Haskell-cafe] Beginner SOS

2009-05-27 Thread Max Rabkin
Hi Manu Depending on your style, you might prefer Real World Haskell (available online or in print) or Learn You A Haskell (http://learnyouahaskell.com/). Of course, there are others, but my personal preference is for LYAH. --Max On Wed, May 27, 2009 at 7:14 PM, Manu Gupta wrote: > Dear anyone

Re: [Haskell-cafe] May all logos be freely used?

2009-05-26 Thread Max Rabkin
>From http://haskell.org/haskellwiki/Haskell_logos/New_logo_ideas : "Please submit your entries here, and attach your name to them please. To be eligible, they will need to be visible on this page (e.g. uploaded, or link to the image). The image should be freely available (a suitable freely distri

Re: Re: [Haskell-cafe] Re: A problem with par and modules boundaries...

2009-05-23 Thread Max Rabkin
On Sat, May 23, 2009 at 7:31 PM, Mario Blažević wrote: > Does anybody know of a pragma or another way to make a function *non-strict* > even > if it does always evaluate its argument? In other words, is there a way to > selectively disable the strictness optimization? parallelize a b | False = (

Re: [Haskell-cafe] "hiddenness"

2009-05-14 Thread Max Rabkin
On Thu, May 14, 2009 at 10:51 PM, Vasili I. Galchin wrote: > Hello, > > When I am compiling a module, I get "Could not find module > 'Control.Module.State': >   it is a > member of package mtl-1.1.0.2, which is hidden" > > 1

Re: [Haskell-cafe] Data.Map.Map Pattern Matching

2009-05-13 Thread Max Rabkin
On Wed, May 13, 2009 at 7:06 PM, Nico Rolle wrote: > Hi > > I tried this but it diddn't work in ghci: > > import qualified Data.Map as Map > > test :: Map.Map [Int] [[Int]] -> Bool > test (fromList[((i:is), (j:js))]) = [i] == j > > i get the : "Parse error in pattern > Failed." error. fromList is

Re: [Haskell-cafe] commending "Design concepts in programming languages"

2009-05-12 Thread Max Rabkin
On Tue, May 12, 2009 at 1:41 PM, Wolfgang Jeltsch wrote: > At least, I cannot > remember seeing the other notation (first morphism on the left) in category > theory literature so far. It’s just that my above-mentioned professor told me > that category theorists would use the first-morphism-on-the-

Re: [Haskell-cafe] Stream-fusion without the lists

2009-05-12 Thread Max Rabkin
On Tue, May 12, 2009 at 1:39 PM, Roman Leshchinskiy wrote: > let xs = map f ys in (sum xs, product xs) > > the elements of xs will be computed once if it is a list but twice if it is > a stream. If you're using lists for loops rather than data, that's what you want (what you probably really want

Re: [Haskell-cafe] Re: OT: Languages

2009-05-10 Thread Max Rabkin
On Sun, May 10, 2009 at 6:44 AM, wren ng thornton wrote: > Kalman Noel wrote: >> Esperanto, on >> the other hand, is usually described as agglutinative. > > I'll take your word for it :) Consider malsanulejestro (the head of a hospital): mal-san-ul-ej-estr-o (un-health-person-place-leader-noun, o

Re: [Haskell-cafe] Being impure within a 'pure' function

2009-04-23 Thread Max Rabkin
On Wed, Apr 22, 2009 at 10:38 AM, Daniel K. wrote: > Dijkstra's algorithm ... relies heavily on mutating arrays Well, the imperative implementation does. > Not mutating the underlying arrays would probably result in poor > performance. Indeed. Non-mutable arrays are not very performant for muta

Re: [Haskell-cafe] Looking for the fastest Haskell primes algorithm

2009-04-14 Thread Max Rabkin
On Tue, Apr 14, 2009 at 2:47 PM, Andrew Wagner wrote: > Some other ideas for things to put in this package possibly: > is_prime :: Int -> Bool I'd also add isProbablePrime using a Miller-Rabin test or somesuch, for use with large numbers. It'd have to be in a monad which supplies randomness, of c

Re: [Haskell-cafe] Trying to write 'safeFromInteger'

2009-04-07 Thread Max Rabkin
On Tue, Apr 7, 2009 at 11:43 PM, Henning Thielemann wrote: > > On Tue, 7 Apr 2009, Max Rabkin wrote: > >> The problem with your code is that the type of maxBound is >> unspecified. You need (maxBound `asTypeOf` i), or enable >> ScopedTypeVariables and use (maxBoun

Re: [Haskell-cafe] Trying to write 'safeFromInteger'

2009-04-07 Thread Max Rabkin
On Tue, Apr 7, 2009 at 11:27 PM, Kannan Goundan wrote: > Here's my code (in file "Test.hs") > >  safeFromInteger :: (Num a, Integral a, Bounded a) => Integer -> Maybe a >  safeFromInteger i = >    if i > (toInteger maxBound) >      then Nothing >      else Just (fromInteger i) > > Here's the error

Re: [Haskell-cafe] ANN: SVGFonts 0.1

2009-04-06 Thread Max Rabkin
On Mon, Apr 6, 2009 at 7:32 PM, Tillmann Vogt wrote: > It is a real library made of pure Haskell. What is wrong with my .cabal > file? The issue is not about whether it is pure Haskell. You have simply marked it up as an executable rather than a library. Executable Fonts Main-is:test/F

Re: [Haskell-cafe] The votes are in!

2009-03-24 Thread Max Rabkin
On Tue, Mar 24, 2009 at 11:41 PM, Henning Thielemann wrote: >> http://www.cs.cornell.edu/w8/~andru/cgi-perl/civs/results.pl?num_winners=1&id=E_d21b0256a4fd5ed7&algorithm=beatpath >> > Is there also a measure of how strong the winner wins over the "losers"? The runner up was beaten 135 votes to 10

Re: [Haskell-cafe] [ANN] random-shuffle package

2009-03-19 Thread Max Rabkin
On Thu, Mar 19, 2009 at 4:41 PM, Manlio Perillo wrote: > However, in this case, the package name should be changed. > I'm not sure it is a good idea to release a package that implements only one > function (but I may be wrong). Personally, I think that there is little harm in releasing a package

Re: [Haskell-cafe] A systematic method for deriving a defintion of foldl using foldr?

2009-03-11 Thread Max Rabkin
2009/3/11 R J : > 2.  I believe that the reverse implementation--namely, implementing foldr in > terms of foldl--is impossible.  What's the proof of that? That's correct. Consider their behaviour on infinite lists. --Max ___ Haskell-Cafe mailing list Ha

Re: [Haskell-cafe] How to create an online poll

2009-02-18 Thread Max Rabkin
On Wed, Feb 18, 2009 at 10:40 PM, Anton van Straaten wrote: > There's also the Condorcet Internet Voting Service: > > http://www.cs.cornell.edu/andru/civs.html This looks like exactly what we need! Any objections? --Max ___ Haskell-Cafe mailing list H

Re: [Haskell-cafe] lazy evaluation is not complete

2009-02-09 Thread Max Rabkin
On Mon, Feb 9, 2009 at 10:50 PM, Iavor Diatchki wrote: > I 0 * _ = I 0 > I x * I y = I (x * y) Note that (*) is now non-commutative (w.r.t. _|_). Of course, that's what we need here, but it means that the "obviously correct" transformation of > foo x = if x == 0 then 0 else foo (x -

Re: [Haskell-cafe] The Haskell re-branding exercise

2009-02-08 Thread Max Rabkin
On Sun, Feb 8, 2009 at 8:57 AM, Gwern Branwen wrote: > We should limit voting, and limit based on IP. If we go via email, > then anyone wishing extra votes merely needs to use mailinator.com > (and its dozens of alternate domain names, to say nothing of > competitors providing similar services) to

Re: [Haskell-cafe] Haddock Markup

2009-02-06 Thread Max Rabkin
On Fri, Feb 6, 2009 at 12:17 PM, Lennart Augustsson wrote: > It doesn't really matter if TeX is a good or bad idea for writing maths. > For our users, they might do a formula if it's TeX, they won't if it's > something else. Generally, I'd agree, but I just took a look at AsciiMathML, and it's pr

Re: [Haskell-cafe] Re: Haddock

2009-02-05 Thread 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. I personally find it useful to have Haddock comments readable in the source. And aren't there sec

  1   2   >