Re: [Haskell-cafe] Type families again

2010-12-02 Thread Robert Greayer
On Thu, Dec 2, 2010 at 4:39 PM, Antoine Latter aslat...@gmail.com wrote:
 On Thu, Dec 2, 2010 at 3:29 PM, Andrew Coppin
 andrewcop...@btinternet.com wrote:
 Yes, it's me. And yes, I come with yet more questions.

 With Haskell 98 (or, indeed, Haskell 2010) it is impossible to define a
 polymorphic version of head that works for [], Set and ByteString. You can
 use a higher-kinded type class for [], but that fails for Set (because you
 can't specify the Ord constraint) and fails spectacularly for ByteString
 (because it has the wrong kind). The basic problem is that the function's
 type needs to refer to the type of the container and the type of elements it
 contains, but the relationship between these types can be arbitrary.

 Type families allow you to neatly and cleanly fix the problem:

  class Head c where
    type Element c :: *
    head :: c - Element c

 It's simple, comprehensible, and it /actually works/.

 Following this success, we can define functions such as tail, join, and so
 forth.

 What we /can't/ do is define a polymorphic map function. One might try to do
 something like

  class Functor f where
    type Element f :: *
    fmap :: (Element f2 ~ y) = (x - y) - f - f2

  instance Functor [x] where
    type Element [x] = x
    fmap = map

 However, this fails. Put simply, the type for fmap fails to specify that f
 and f2 must be /the same type of thing/, just with different element types.

 The trouble is, after spending quite a bit of brainpower, I literally cannot
 think of a way of writing such a constraint. Does anybody have any
 suggestions?


 Does this do what you need?

 http://hackage.haskell.org/packages/archive/rmonad/0.6/doc/html/Control-RMonad.html#t:RFunctor

 Antoine


I think this doesn't handle the ByteString case (wrong kind).  Here's
another mostly unsatisfactory (injectivity issues) solution that may
possibly not even work though it does compile:

import qualified Data.ByteString as B
import Data.Word

type family P c z

class Mappable1 c1 c2 where
type E1 c1 c2
type E2 c1 c2
map1 :: (P c1 a ~ P c2 a) = (E1 c1 c2 - E2 c1 c2) - c1 - c2

instance Mappable1 [a] [b] where
type E1 [a] [b] = a
type E2 [a] [b] = b
map1 = map

type instance P [a] b = [b]

instance Mappable1 B.ByteString B.ByteString where
type E1 B.ByteString B.ByteString = Word8
type E2 B.ByteString B.ByteString = Word8
map1 = B.map

type instance P B.ByteString b = B.ByteString

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] GPL answers from the SFLC (WAS: Re: ANN: hakyll-0.1)

2010-03-05 Thread Robert Greayer
Pending an explicit response from the SFLC, I decided to ask the FSF
themselves what they thought of the Hackage/cabal situation.
Specifically, I asked this:

 There is a website, 'Hackage' (http://hackage.haskell.org) that hosts
 source code packages for Haskell libraries and programs.  The site
 hosts *only* source code, along with (text) descriptions of the
 packages.  Each package hosted by the site is either source code for a
 library, for a program, or for both.

 In the package description, a package author specifies what license
 applies to the source code, the common choices being LGPL, GPL, or
 BSD3.  The package author also specifies what other packages in the
 repository the package may require to compile successfully.

 The controversy in the community of users who use Hackage is whether
 or not it is a violation of the GPL for a package to be uploaded to
 Hackage specifying (for example) a BSD3 license for the code in the
 package, but also specifying that another package is a requirement for
 compilation, where that other package has been uploaded specifying (a
 version of) the GPL as its license.

 The opinion of many in the community is that since Hackage hosts only
 source code, and does not in any way combine packages (any combination
 of packages is created when a user chooses to download and compile and
 link the individual packages) there is no problem: there are no
 'derived works' combining GPL and non-GPL being distributed on the
 site.

 Others believe that having a non-GPL package have as a dependency a
 GPL package is a problem for both the package author and for Hackage;
 that this in some way violates the GPL.

 I don't believe this sort of situation is clearly addressed in your
 FAQ (at least not to the satisfaction of the Hackage user community).
 There's a certain amount of fear, uncertainty and doubt being spread
 about usage of the GPL on Hackage, which it would be great to dispel
 (or, confirm, as necessary).


Someone from the FSF responded as follows:

 A work which extends or requires a GPL work will generally also need to
 be released under the GPL, unless the GPL work provides a specific
 exception for that case. You are already familiar with the FAQ; however,
 please note http://www.fsf.org/licensing/licenses/gpl-faq.html#OOPLang
 and http://www.fsf.org/licensing/licenses/gpl-faq.html#MereAggregation .
 There is no magic to the act of linking, compiling, or a function
 invocation; these are not defining moments. It is the level of
 integration and dependency which will define whether one work is a
 derivative of another.

 Ultimately, the decision that one work is a derivative of another is a
 legal one which a court may have to decide for a particular case; a
 lawyer can give you a legal opinion. However, a good rule of thumb would
 be: if P is a GPL work, and Q is a work that would not function without
 P, then Q is probably a derivative of P and should only be conveyed to a
 third party or the public under a GPL license, in compliance with the
 license for P.

 I hope that helps.

 Thank you for your interest in free software!
 I am not a lawyer and the above is not legal advice.
 The opinions expressed above do not constitute an official position of
 the Free
 Software Foundation.

 Luigi Bai
 FSF Associate Member
 Volunteer, licens...@gnu.org

Of course, given the disclaimer at the bottom, this opinion is officially no
better than any of our opinions on the matter.  Nevertheless, I would at
least believe based on the above that this is what the FSF *wants* the GPL
to mean, and, by extension, would assume, barring other evidence that
this is what someone who chooses the GPL *wants* it to mean, and in
licensing any software that I write that depends on someone else's GPL'd
software, I'd respect those desires (without at all suggesting that this has
any bearing on how the GPL would actually be interpreted in court).

There's still a lot of gray area here -- the mere existence of a dependency
doesn't imply that a software package is useless without the dependency,
so there are many situations in which P could depend on Q and not be
a derivative of Q, because the dependency can be disabled in some way
and the software would still function.  As an example -- pandoc can be
built with or without highlighting-kate, and is useful either way.  They're both
GPL and by the same author, so there's no issue, but were that not the
case it would seem obvious that pandoc isn't derivative of -kate, and
thus could (by this reasoning) be released independently under different
terms.  The same may not be true of the hakyll / pandoc situation which
sparked this controversy.

Cheers,
Rob
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] GPL answers from the SFLC (WAS: Re: ANN: hakyll-0.1)

2010-03-04 Thread Robert Greayer
Before taking any action with respect to cabal or hackage, etc., I'd
think people would want to see their explicit response.

On Thu, Mar 4, 2010 at 12:34 PM, Tom Tobin korp...@korpios.com wrote:
 After politely pestering them again, I finally heard back from the
 Software Freedom Law Center regarding our GPL questions (quoted
 below).

 I exchanged several emails to clarify the particular issues; in short,
 the answers are No, No, N/A, and N/A.  The SFLC holds that a
 library that depends on a GPL'd library must in turn be GPL'd, even if
 the library is only distributed as source and not in binary form.
 They offered to draft some sort of explicit response if we'd find it
 useful.

 Maybe it would be useful if Cabal had some sort of licensing check
 command that could be run on a .cabal file, and warn an author if any
 libraries it depends on (directly or indirectly) are GPL'd but the
 .cabal itself does not have the license set to GPL.


 On Fri, Dec 11, 2009 at 10:21 PM, Tom Tobin korp...@korpios.com wrote:
 I'd like to get these questions out to the SFLC so we can satisfy our
 curiosity; at the moment, here's what I'd be asking:

 Background: X is a library distributed under the terms of the GPL. Y
 is another library which calls external functions in the API of X, and
 requires X to compile.  X and Y have different authors.

 1) Can the author of Y legally distribute the *source* of Y under a
 non-GPL license, such as the 3-clause BSD license or the MIT license?

 2) If the answer to 1 is no, is there *any* circumstance under which
 the author of Y can distribute the source of Y under a non-GPL
 license?

 3) If the answer to 1 is yes, what specifically would trigger the
 redistribution of a work in this scenario under the GPL?  Is it the
 distribution of X+Y *together* (whether in source or binary form)?

 4) If the answer to 1 is yes, does this mean that a BSD-licensed
 library does not necessarily mean that closed-source software can be
 distributed which is based upon such a library (if it so happens that
 the library in turn depends on a copylefted library)?

 By the way, apologies to the author of Hakyll — I'm sure this isn't
 what you had in mind when you announced your library!  I'm just hoping
 that we can figure out what our obligations are based upon the GPL,
 since I'm not so sure myself anymore.

 ___
 Haskell-Cafe 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


Re: [Haskell-cafe] Haskell RPC / Cluster

2010-02-12 Thread Robert Greayer
Perhaps not exactly what you're after, but at least in the same vein:

http://hackage.haskell.org/package/hspread
http://www.spread.org/

On Fri, Feb 12, 2010 at 8:19 AM, Rick R rick.richard...@gmail.com wrote:
 I am preparing to embark on some serious cluster oriented coding (high
 availability, monitoring, failover, etc). My primary concern is
 conforming to standards. I would also like to aid any existing project
 that fall under this scope.  HackPar seems currently targeted towards
 HPC style clustering, but the page seems to hint at future work in the
 cloud/high-availability area.

 I was looking around for RPC libs for Haskell and stumbled across this

 http://github.com/mariusaeriksen/bert

 It implements BERT, which is based on Erlang's binary serialization
 protocol. It seems to have quite a bit of support.

 Does anyone know of any other RPC modules for Haskell? In addition,
 can anyone recommend other cluster oriented modules for monitoring,
 process management, etc?

 If those don't exist, can anyone recommend some standards off of which
 to base these?
 SNMP seems obvious (and daunting), any others?


 Thanks,
 Rick
 ___
 Haskell-Cafe 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


Re: [Haskell-cafe] Type arithmetic with ATs/TFs

2010-02-12 Thread Robert Greayer
On Fri, Feb 12, 2010 at 2:11 PM, Andrew Coppin
andrewcop...@btinternet.com wrote:
 OK, well in that case, I'm utterly puzzled as to why both forms exist in the
 first place. If TFs don't allow you to do anything that can't be done with
 ATs, why have them?

 My head hurts...


I think the question is the reverse -- why do ATs exist when you can
do everything with the more general Type Families?  This is the answer
from the GHC documentation:

Type families appear in two flavours: (1) they can be defined on the
toplevel or (2) they can appear inside type classes (in which case
they are known as associated type synonyms). The former is the more
general variant, as it lacks the requirement for the type-indices to
coincide with the class parameters. However, the latter can lead to
more clearly structured code and compiler warnings if some type
instances were - possibly accidentally - omitted.

http://www.haskell.org/haskellwiki/GHC/Indexed_types#Detailed_definition_of_type_synonym_families
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type arithmetic with ATs/TFs

2010-02-11 Thread Robert Greayer
What Ryan said, and here's an example of addition with ATs,
specifically (not thoroughly tested, but tested a little).  The
translation to TFs sans ATs is straightforward.

class Add a b where
type SumType a b

instance Add Zero Zero where
type SumType Zero Zero = Zero

instance Add (Succ a) Zero where
type SumType (Succ a) Zero = Succ a

instance Add Zero (Succ a) where
type SumType Zero (Succ a) = Succ a

instance Add (Succ a) (Succ b) where
type SumType (Succ a) (Succ b) = Succ (Succ (SumType a b))


On Thu, Feb 11, 2010 at 4:10 PM, Andrew Coppin
andrewcop...@btinternet.com wrote:
 Andrew Coppin wrote:

 OK, so I sat down today and tried this, but I can't figure out how.

 There are various examples of type-level arithmetic around the place. For
 example,

 http://www.haskell.org/haskellwiki/Type_arithmetic

 (This is THE first hit on Google, by the way. Haskell is apparently THAT
 popular!) But this does type arithmetic using functional dependencies; what
 I'm trying to figure out is how to do that with associated types.

 Any hints?

 Several people have now replied to this, both on and off-list. But all the
 replies use type families, not associated types.

 Now type families are something I don't yet comprehend. (Perhaps the replies
 will help... I haven't studied them yet.) What I understand is that ATs
 allow you to write things like

  class Container c where
   type Element c :: *
   ...

 And now you can explicitly talk about the kind of element a container can
 hold, rather than relying on the type constructor having a particular kind
 or something. So the above works for containers that can hold *anything*
 (such as lists), containers which can only hold *one* thing (e.g.,
 ByteString), and containers which can hold only certain things (e.g., Set).

 ...which is great. But I can't see a way to use this for type arithmetic.
 Possibly because I don't have a dramatically solid mental model of exactly
 how it works. You'd *think* that something like

  class Add x y where
   type Sum x y :: *

  instance Add x y = Add (Succ x) y where
   type Sum (Succ x) y = Succ (Sum x y)

 ought to work, but apparently not.

 As to what type families - type declarations outside of a class - end up
 meaning, I haven't the vaguest idea. The Wiki page makes it sound
 increadibly complicated...

 ___
 Haskell-Cafe 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


Re: [Haskell-cafe] Type arithmetic with ATs

2010-02-10 Thread Robert Greayer
On Wed, Feb 10, 2010 at 2:29 PM, Andrew Coppin
andrewcop...@btinternet.com wrote:
 OK, so I sat down today and tried this, but I can't figure out how.

 There are various examples of type-level arithmetic around the place. For
 example,

 http://www.haskell.org/haskellwiki/Type_arithmetic

 (This is THE first hit on Google, by the way. Haskell is apparently THAT
 popular!) But this does type arithmetic using functional dependencies; what
 I'm trying to figure out is how to do that with associated types.

 Any hints?

 (I know for a fact that other people have done this - rule 34 requires it.)

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


With type families, something like:

type family Add m n
type instance Add (Succ n) (Succ m) = Succ (Succ (Add n m))
type instance Add Zero (Succ m) = (Succ m)
type instance Add (Succ m) Zero = (Succ m)
type instance Add Zero Zero = Zero

is this what you are after?

There's also the tfp library on hackage which has much more type level
arithmetic, using type families.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to fulfill the code-reuse destiny of OOP?

2010-01-13 Thread Robert Greayer
On Wed, Jan 13, 2010 at 4:56 AM, Martin Coxall pseudo.m...@me.com wrote:

 On 13 Jan 2010, at 09:51, Peter Verswyvelen wrote:

 On Sun, Nov 1, 2009 at 2:57 AM, Gregory Collins g...@gregorycollins.net
 wrote:

 Doing OO-style programming in Haskell is difficult and unnatural, it's
 true (although technically speaking it is possible). That said, nobody's
 yet to present a convincing argument to me why Java gets a free pass for
 lacking closures and typeclasses.

 I might be wrong, but doesn't Java's concepts of inner classes and
 interfaces together with adapter classes can be used to replace closures and
 typeclasses in a way?

 Inner classes are not a semantic replacement for closures, even if you
 discount horrific syntax. Inner classes do not close over their lexical
 environment.
 Martin

Anonymous classes in Java close over their lexical environment (can
refer to variables in that lexical environment, with values bound at
the time of instance construction) with the caveat that only local
variables/parameters marked as 'final' may be referred to.  Aside from
the horrible syntax, this is the key distinction between them, and,
say, Ruby closures.  Referring to mutable variables from inside a
closure has its drawbacks, making the horrible syntax the biggest
stumbling block to using them IMHO (other than runtime overhead, which
I believe is also an issue).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: ANN: hakyll-0.1

2009-12-09 Thread Robert Greayer
sigh -- to the list this time.


On Wed, Dec 9, 2009 at 9:16 AM, Tom Tobin korp...@korpios.com wrote:

 On Wed, Dec 9, 2009 at 4:59 AM, Ketil Malde ke...@malde.org wrote:
  Tom Tobin korp...@korpios.com writes:
  If it turns out that Hakyll *is* okay to be BSD3 licensed so
  long as neither any binary nor the GPL'd work's source is distributed
  under non-GPL terms, well ... I'll say that the meaning of BSD
  licensed will have become much less reliable, since it means you
  actually have to trace the genealogy of the libraries you use *all*
  the way back in order to understand the situation for certain.
 
  How so?  To me it's the exact converse: if the author of Hakyll may
  *not* distribute his work under the BSD license, just because it is
  intended to be linked with some GPL code, this complicates issues
  tremendously.

 For instance, it would mean that businesses which may be writing
 proprietary software can't assume they can freely use a liberally
 licensed (e.g., BSD3) library — which would *completely* go against
 the prevailing understanding of liberally licensed software.  Tainting
 your software with a GPL dependency without realizing it is a
 terrifying prospect (and certainly one of the questions I'd now like
 to pose to the SFLC).


I don't think I follow your reasoning here:  certainly, a business can use,
freely, the Hakyll library (meaning that they can redistribute, in binary
form, their executable built with it, without distributing the Hakyll source
or their own source).  They cannot freely use the Pandoc library in the same
way, because it is GPL.  Since the Hakyll library depends on the Pandoc
library, they will of course have some trouble with *building* an executable
that contains Hakyll but not Pandoc.  Both there's no hidden dependency, no
'tainting' of Hakyll involved.  There is a danger, of course, that when
installing Hakyll (via cabal) the user won't realize they've also installed
Pandoc, even though the dependency is clearly specified.  The lesson here is
that someone packaging an executable for distribution has to be aware of
everything they are building into it.  It's possible to make a mistake here,
if one is not careful.  But it doesn't require much diligence to get it
right (if you use cabal to build your executable, you have to specify your
dependencies.  Check the licensing terms of each, and comply).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: ANN: hakyll-0.1

2009-12-08 Thread Robert Greayer
On Tue, Dec 8, 2009 at 4:46 PM, Tom Tobin korp...@korpios.com wrote:

 On Tue, Dec 8, 2009 at 3:30 PM, Ben Franksen ben.frank...@online.de
 wrote:
  Ketil Malde wrote:
  Your contributions could still be licensed under a different license
  (e.g. BSD), as long as the licensing doesn't prevent somebody else to
  pick it up and relicense it under GPL.
 
  At least, that's how I understand things.
 
  Right. So hakyll is absolutely fine with a BSD3 license, AFAICS.

 Seriously, no, this is *totally* wrong reading of the GPL, probably
 fostered by a misunderstanding of the term GPL-compatible license.
 GPL-compatible means the compatibly-licensed work can be incorporated
 into the GPL'd work (the whole of which is GPL'd), *not the other way
 around*.  If you are forming a derivative work based on the GPL'd
 work, and thus you have to release that derivative work under the GPL.


The crux here is that the source code of hakyll, released on hackage, is not
a derivative of Pandoc (it contains, as far as I understand it, no Pandoc
source code).  A compiled executable *is* a derivative of Pandoc, so anyone
who *distributes* a compiled executable would need to make *all* the source
available under the GPL (including the hakyll source).  Since the hakyll
package is released under BSD3, this would be allowed (AIUI, IANAL).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: ANN: hakyll-0.1

2009-12-08 Thread Robert Greayer
On Tue, Dec 8, 2009 at 5:13 PM, Robert Greayer robgrea...@gmail.com wrote:


 The crux here is that the source code of hakyll, released on hackage, is
 not a derivative of Pandoc (it contains, as far as I understand it, no
 Pandoc source code).  A compiled executable *is* a derivative of Pandoc, so
 anyone who *distributes* a compiled executable would need to make *all* the
 source available under the GPL (including the hakyll source).  Since the
 hakyll package is released under BSD3, this would be allowed (AIUI, IANAL).


Not to belabor the point (I hope), but consider the following situation --
if the current version of Pandoc, 1.2.1, were released under BSD3, not GPL,
it would be obvious that the current version of hakyll could be released as
BSD3 as well.  After said hakyll release, the Pandoc maintainer would be
perfectly within his rights to release an API compatible 1.2.2 version of
Pandoc, this time licensed under the GPL.  People installing hakyll with
cabal might now be building a version of hakyll containing both GPL and BSD3
code.  This is not under either author's control, and is perfectly
allowable.  If the person downloading chooses to redistribute the hakyll
executable he's built, he must be aware of and comply with his
responsibilities under the GPL, but those would be his responsibilities, not
those of the original author of hakyll.  (AIUI -- IANAL).

(If hakyll had been released under a GPL-incompatible license -- EPL, for
example -- then the person downloading hakyll and building the executable
could *not* distribute the executable he built.  He could use it for his own
purposes, but not distribute it.  This is the implication of GPL
incompatibility.  As I Understand It.)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: ANN: hakyll-0.1

2009-12-08 Thread Robert Greayer
On Tue, Dec 8, 2009 at 7:38 PM, Ivan Lazar Miljenovic 
ivan.miljeno...@gmail.com wrote:

 Apologies, Robert, for you getting this twice: I forgot to CC the list
 as well.

 Robert Greayer robgrea...@gmail.com writes:
  The crux here is that the source code of hakyll, released on hackage, is
 not
  a derivative of Pandoc (it contains, as far as I understand it, no Pandoc
  source code).  A compiled executable *is* a derivative of Pandoc, so
 anyone
  who *distributes* a compiled executable would need to make *all* the
 source
  available under the GPL (including the hakyll source).  Since the hakyll
  package is released under BSD3, this would be allowed (AIUI, IANAL).


 That is my understanding as well:

 http://www.fsf.org/licensing/licenses/gpl-faq.html#IfLibraryIsGPL

 ,
 | If a library is released under the GPL (not the LGPL), does that mean
 | that any program which uses it has to be under the GPL or a
 | GPL-compatible license?
 |
 | Yes, because the program as it is actually run includes the library.
 `

 Thus, it means your program using Pandoc can be BSD3; but it can never
 be used in a proprietary program.


There's another FAQ on GNU site that, I think, addresses the Pandoc/Hakyll
situation directly:

http://www.gnu.org/licenses/gpl-faq.html#LinkingWithGPL

You have a GPL'ed program that I'd like to link with my code to build a
proprietary program. Does the fact that I link with your program mean I have
to GPL my program?

Not exactly. It means you must release your program under a license
compatible with the GPL (more precisely, compatible with one or more GPL
versions accepted by all the rest of the code in the combination that you
link). The combination itself is then available under those GPL versions. 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: binding to C libraries on Windoww

2009-12-07 Thread Robert Greayer
On Mon, Dec 7, 2009 at 4:37 PM, Andrew Coppin
andrewcop...@btinternet.comwrote:


 And I have no problem with needing to install a Haskell compiler. If I had
 to install a seperate C compiler to make FFI to C work, that wouldn't seem
 unreasonable either. (As it happens, GHC has a C backend, so the C compiler
 just happens to be there already.) What does seem very weird is having to
 turn my Windows box into a psuedo-Unix system in order to write native
 Windows programs.

 snip

 You can't develop anything with just what's preinstalled. (Well, unless you
 could writing batch scripts...)

 Generally, if you want to develop C or C++ applications on Windows, you
 install MS Visual Studio. It gives you the compiler, linker, dependency
 management, and a whole bunch of other stuff. You typically wouldn't install
 gcc, ld and Automake. (Unless of course you were specifically trying to port
 existing Unix code, obviously.)

 It helps, I believe, if you stop thinking of MinGW with MSYS as 'a
pseudo-Unix system'.  They're billed as the minimal toolset required on
windows to use the GNU compilers and build system (and, as everybody knows,
Gnu's not Unix).  The great thing about these compilers is that they're
cross-platform and freely available, unlike MS Visual Studio.  I think that
it makes sense that open source software developers targeting multiple
platforms would want to pick a tool suite that works across all those
platforms, and the GNU tools fit that description.  Cygwin truly is a Unix
emulation, but MinGW/MSYS is just a packaging of useful open source (GNU)
tools for Windows (including a shell).  Many programs that work well as
native Windows apps, such as the GIMP, are built with them.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] seems like I'm on the wrong track

2009-12-01 Thread Robert Greayer
On Tue, Dec 1, 2009 at 8:01 PM, Michael P Mossey m...@alumni.caltech.eduwrote:

 Perhaps someone could either (1) help me do what I'm trying to do, or (2)
 show me a better way.

 I have a problem that is very state-ful and I keep thinking of it as OO,
 which is driving me crazy. Haskell is several times harder to use than
 Python in this instance, probably because I'm doing it wrong.

 To give you a larger context, this problem is essentially compiling a
 description of music (my own) into a kind of music-machine-language
 (CSound). CSound is relatively untidy.

 In this one example, in a OO way of thinking, I have data called
 AssignedNumbers that assigns integers to unique strings and keeps track of
 the used integers and next available integer (the choice of available
 integer could follow a number of conventions so I wanted to hide that in an
 ADT.) So it has an associated function:

 getNumber :: String - AssignedNumbers - (Int,AssignedNumbers)

 What getNumber does is:

  - check if the string already has a number assigned to it. If so, return
 that number.

  - if not, pick the next available number.

  - in all cases, return the possibly changed state of AssignedNumbers

 Then in a larger data structure, it contains fields of type
 AssignedNumbers. Like

 data MusicStuff = MusicStuff
  { oscillatorNumbers :: AssignedNumbers
  , tableNumbers :: AssignedNumbers
  , ... }

 I'm using MusicStuff in a State monad, so I might write a function like

 doSomeMusicStuff :: String - String - State MusicStuff (Int,Int)
 doSomeMusicStuff aString1 aString2 = do
   ms - get
   (o1,newOscNums) = getNumber aString1 (oscillatorNumbers ms)
   (t1,newTabNums) = getNumber aString2 (tableNumbers ms)
   put ms { oscillatorNumbers = newOscNums
  , tableNumbers = newTabNums }
   return (o1,t1)

 For what it does, this is extremely verbose and filled with distracting
 visual content. And this is just a very simple example---my real problem is
 several times more state-ful. Is there a better way?


As a quick observation, you might consider changing getNumber to be
something like:

nextNumber :: String - NumberGroup - State MusicStuff Int

where NumberGroup is something like

data NumberGroup = OscNums | TabNums |...

nextNumber updates the appropriate set of numbers in MusicStuff and returns
the number. doSomeMusicStuff then becomes:

doSomeMusicStuff aString1 aString2 = (,) `liftM` nextNumber OscNums `ap`
nextNumber TabNums

or better yet (applicatively)

doSomeMusicStuff aString1 aString2 = (,) $ nextNumber OscNums *
nextNumber TabNums
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] seems like I'm on the wrong track

2009-12-01 Thread Robert Greayer
On Tue, Dec 1, 2009 at 9:01 PM, Robert Greayer robgrea...@gmail.com wrote:



 On Tue, Dec 1, 2009 at 8:01 PM, Michael P Mossey 
 m...@alumni.caltech.eduwrote:

 Perhaps someone could either (1) help me do what I'm trying to do, or (2)
 show me a better way.

 I have a problem that is very state-ful and I keep thinking of it as OO,
 which is driving me crazy. Haskell is several times harder to use than
 Python in this instance, probably because I'm doing it wrong.

 To give you a larger context, this problem is essentially compiling a
 description of music (my own) into a kind of music-machine-language
 (CSound). CSound is relatively untidy.

 In this one example, in a OO way of thinking, I have data called
 AssignedNumbers that assigns integers to unique strings and keeps track of
 the used integers and next available integer (the choice of available
 integer could follow a number of conventions so I wanted to hide that in an
 ADT.) So it has an associated function:

 getNumber :: String - AssignedNumbers - (Int,AssignedNumbers)

 What getNumber does is:

  - check if the string already has a number assigned to it. If so, return
 that number.

  - if not, pick the next available number.

  - in all cases, return the possibly changed state of AssignedNumbers

 Then in a larger data structure, it contains fields of type
 AssignedNumbers. Like

 data MusicStuff = MusicStuff
  { oscillatorNumbers :: AssignedNumbers
  , tableNumbers :: AssignedNumbers
  , ... }

 I'm using MusicStuff in a State monad, so I might write a function like

 doSomeMusicStuff :: String - String - State MusicStuff (Int,Int)
 doSomeMusicStuff aString1 aString2 = do
   ms - get
   (o1,newOscNums) = getNumber aString1 (oscillatorNumbers ms)
   (t1,newTabNums) = getNumber aString2 (tableNumbers ms)
   put ms { oscillatorNumbers = newOscNums
  , tableNumbers = newTabNums }
   return (o1,t1)

 For what it does, this is extremely verbose and filled with distracting
 visual content. And this is just a very simple example---my real problem is
 several times more state-ful. Is there a better way?


 As a quick observation, you might consider changing getNumber to be
 something like:

 nextNumber :: String - NumberGroup - State MusicStuff Int

 where NumberGroup is something like

 data NumberGroup = OscNums | TabNums |...

 nextNumber updates the appropriate set of numbers in MusicStuff and returns
 the number. doSomeMusicStuff then becomes:

 doSomeMusicStuff aString1 aString2 = (,) `liftM` nextNumber OscNums `ap`
 nextNumber TabNums

 or better yet (applicatively)

 doSomeMusicStuff aString1 aString2 = (,) $ nextNumber OscNums *
 nextNumber TabNums



Oops, that's:

doSomeMusicStuff aString1 aString2 =
(,) `liftM` nextNumber aString1 OscNums `ap` nextNumber aString2 TabNums

or:

doSomeMusicStuff aString1 aString2 =
(,) $ nextNumber aString1 OscNums * nextNumber aString2 TabNums
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Status of TypeDirectedNameResolution proposal?

2009-11-18 Thread Robert Greayer
On Wed, Nov 18, 2009 at 3:10 PM, levi greenspan.l...@googlemail.com wrote:

 On Nov 18, 8:18 pm, Luke Palmer lrpal...@gmail.com wrote:
  You know, another solution to the records problem, which is not quite
  as convenient but much simpler (and has other applications) is to
  allow local modules.
 
  module Foo where
module Bar where
  data Bar = Bar { x :: Int, y :: Int }
module Baz where
  data Baz = Baz { x :: Int, y :: Int }
 
f a b = Bar.x a + Baz.y b

 +1

 Independent of TDNR I would welcome this. Maybe Ticket 2551 (Allow
 multiple modules per source file) [1] should be reconsidered.


Although ticket 2551 is not exactly what Luke is suggesting (which would be
an extension to the language, whereas, if I'm not mistaken, 2551 is just a
change to where GHC can find modules, not nesting of modules).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Some help needed to start Haskell with Yi

2009-11-18 Thread Robert Greayer
On Wed, Nov 18, 2009 at 8:15 PM, Daniel Fischer daniel.is.fisc...@web.dewrote:

 Am Donnerstag 19 November 2009 01:07:37 schrieb Henning Thielemann:
  Kapil Hari Paranjape schrieb:
   Hello,
  
   On Sat, 14 Nov 2009, Jaco van Iterson wrote:
   Only installation with 'cabal install yi' in a Cygwin shell under MS
   Windows XP ended in:
   Yi\Prelude.hs:182:9:
   Duplicate instance declarations:
 instance Category Accessor.T -- Defined at
 Yi\Prelude.hs:182:9-38
 instance Category Accessor.T
   -- Defined in data-accessor-0.2.1:Data.Accessor.Private
   cabal.exe: Error: some packages failed to install:
   yi-0.6.1 failed during the building phase. The exception was:
   exit: ExitFailure 1
  
   Seems easy to fix but I can't even find where on my drive I can find
 the
   source code.
  
   Where is the source?
 
  Seems to be that the author defined an orphan instance - something one
  should never do!

 So what do you do if you need an instance ClassX TypeY but the author of
 the package that
 defines TypeY hasn't provided one?

 You can define an orphan instance or duplicate packageY but with the
 instance. Both are
 bad. Providing an orphan instance until packageY has one seems the lesser
 evil to me.
 Are there any good options?


Whether it qualifies as 'good' or not, I'm not sure, but I think the
standard recommendation is to newtype-wrap the type you want to make an
orphan instance of, and make the instance on that (new) type.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANN: BlogLiterately-0.2

2009-11-02 Thread Robert Greayer
Due to overwhelming popular demand*, BlogLiterately (version 0.2) has been
released on Hackage.

It's a simple tool for uploading posts written in markdown and (optionally)
literate Haskell to web logs.  It relies heavily on Pandoc for markdown
processing, but adds a few twists like syntax highlighting via hscolour.
The original version was described here:

http://greayer.wordpress.com/2009/10/26/blogging-literately-in-haskell/

The new version (the first version on hackage) has been updated a bit -- to
take advantage of Pandoc highlighting extensions and to support blog
categories, mainly.  The primary documentation is just the haskell package
page:

http://hackage.haskell.org/package/BlogLiterately

It's only been tested with a WordPress blog (mine) but ought to work with
any blogging software that supports the MetaWeblog API.

Send bug reports, etc. to me...

Thanks!

* -- 2 people asked
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Market Place for Haskell development teams?

2009-10-02 Thread Robert Greayer
Fairly late to the party on this discussion, but this captured my attention:

On Tue, Sep 29, 2009 at 11:35 AM, Curt Sampson 
c...@starling-software.comwrote:


 This may be somewhat anecdotal evidence, but I disagree with both
 of your statements here. I've rarely known anybody to use Java
 cross-platform in a non-trival way, barring a few major GUI-centric
 projects such as Eclipse. (I've far more cross-platform use of Haskell
 than Java myself.) And I know of nobody who did anything serious with
 download-execution of Java.


I agree with the download/execution part of this, but I'd be willing to bet
that it is incredibly common for Java developers to write and test code in
an environment very different from the actual deployment environment.  With
Java, it requires no special forethought to write an application on a
Windows or Mac laptop, be able to run all the unit tests, etc., locally, and
then deploy the production application to a Linux or Solaris or *nix server
(or a combination) without any required recompilation.  This is a pretty
powerful selling point for the JVM as a target platform, and everywhere I've
seen Java used, it's been taken advantage of.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] oauth in haskell - reviewers?

2009-08-25 Thread Robert Greayer
On Mon, Aug 24, 2009 at 5:24 PM, Don Stewartd...@galois.com wrote:
 I notice hoauth is packaged as LGPL. Since we use static linking in GHC,
 this makes it in practice GPL. Is that the intent?

 -- Don


I don't think this is 100% true -- the requirement is to allow the end
user the ability to replace the version of the library they're using
with something else, which can be accomplished by dynamically linked
libraries, but also means that if the rest of the program is open
source (but not GPL), the requirement is satisfied.  LGPL is generally
compatible with GPL-incompatible open-source, whether statically
linked or not.  It is true it is incompatible with closed source
licensing.

There are some real situations where this might matter -- you could
use this library in an an executable in which the remainder of the
source was MPL, I think, as long as there were the possibility of
relinking with a different version of the LGPL library.  You couldn't
do this if it were GPL.  This is the section of the LGPL that mentions
this:

Do one of the following:

* 0) Convey the Minimal Corresponding Source under the terms of
this License, and the Corresponding Application Code in a form
suitable for, and under terms that permit, the user to recombine or
relink the Application with a modified version of the Linked Version
to produce a modified Combined Work, in the manner specified by
section 6 of the GNU GPL for conveying Corresponding Source.
*1) Use a suitable shared library mechanism for linking with the
Library. A suitable mechanism is one that (a) uses at run time a copy
of the Library already present on the user's computer system, and (b)
will operate properly with a modified version of the Library that is
interface-compatible with the Linked Version.

So, Haskell libraries licensed under LGPL (without the static linking
exception) force option 0, but that doesn't make them completely
equivalent to GPL. At least that's my understanding (which could be
flawed!).

-Rob

 wei.hoo:
 I recommend Learn you a Haskell for great good:
 http://learnyouahaskell.com/functors-applicative-functors-and-monoids#applicative-functors

 On Sun, Aug 23, 2009 at 12:25 PM, Diego Souzadso...@bitforest.org wrote:
  A quick search pointed me to this:
  http://www.soi.city.ac.uk/~ross/papers/Applicative.html
 
  Is there any other resources you would suggest me to read?
 
  Thanks at lot,
  --
  ~dsouza
  yahoo!im: paravinicius
  gpg key fingerprint: 71B8 CE21 3A6E F894 5B1B  9ECE F88E 067F E891 651E
  ___
  Haskell-Cafe 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

 ___
 Haskell-Cafe 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


Re: [Haskell-cafe] A voyage of undiscovery

2009-07-16 Thread Robert Greayer
On Thu, Jul 16, 2009 at 2:34 PM, Andrew
Coppinandrewcop...@btinternet.com wrote:
 I've been working hard this week, and I'm stumbled upon something which is
 probably of absolutely no surprise to anybody but me.

 Consider the following expression:

  (foo True, foo 'x')

 Is this expression well-typed?

 Astonishingly, the answer depends on where foo is defined. If foo is a
 local variable, then the above expression is guaranteed to be ill-typed.

This isn't completely accurate:

f0 _ = (foo True, foo 'x') where foo = id

is well-typed.

whereas

f1 foo = (foo True, foo 'x')

requires 'foo' to be polymorphic in its first argument.  This does
require a higher rank type, which
can't be inferred:

You could type f1 as
f1 :: (forall a . a - a)  - (Bool, Char)

and apply it to 'id'.

Or you could type it as something like:
f1 :: (forall a . a - ()) - ((),())

and apply it to 'const ()'
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-07-15 Thread Robert Greayer
On Wed, Jul 15, 2009 at 2:18 PM, Max Rabkinmax.rab...@gmail.com wrote:
 On Wed, Jul 15, 2009 at 7:33 PM, Cristiano
 Pariscristiano.pa...@gmail.com wrote:
 fib = 1:1:fib `plus` (tail fib) where plus = zipWith (+)
 ...
 ...
 This indicates that you think tying the knot should be impossible in
 Python. In my opinion this is not the case. By my definition of tying
 the knot, one needs *either* mutable variables or laziness (at least
 in simple cases). Since Python has the former, it is possible to tie
 the knot in Python.

Isn't tying the knot (in the way 'fib' does) straightforward with closures
a la Python/Ruby/Smalltalk (without mutation)?
Even in a syntactically clumsy language like Java, a
tying-the-knot implementation equivalent to the canonical Haskell one is
not difficult, e.g.

static L fibs = new L() {
public int head() { return 1; }
public L tail() {
return  new L() {
public int head() { return 1; }
public L tail() {
return new L() {
public int head() { return fibs.head() +
fibs.tail().head(); }
public L tail() { return zip(fibs.tail(),
fibs.tail().tail()); }
};
}
};
}
};

Given a definition of list L and zip...

interface L { int head(); L tail(); }
static L zip(final L l0, final L l1) {
return new L() {
public int head() { return l0.head() + l1.head(); }
public L tail() { return zip(l0.tail(), l1.tail()); }
};
}
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-07-13 Thread Robert Greayer
 It’s tempting to say, we should
 use the original English, which is British English.

Some suggest the original English remained in Britain when the North
American colonies were founded; others claim it was brought to the
Americas by the British settlers, leaving a pale imitation back in
Britain.  The truth is much stranger:  the original English was
actually smuggled out of Britain to the West Indies in a wardrobe
belonging to General Sir Ralph Abercromby, where it ended up on the
island of Trinidad after Sir Ralph took possession of that territory
in the name of the British Crown. It came to be used and modified
freely by the various immigrants to Trinidad (and later Tobago) and
their descendants (largely African, Indian, British, Portuguese,
German, Spanish, and Chinese).  Many of these peoples then emigrated,
bringing the original English to North America and back to Britain.  A
copy of it has fallen into my hands, and so I can, without bias, make
the following call: both color and colour shall be acceptable in
Haskell programming.  'Kerb' and 'gaol' are right out, however.

Cheers,
Robert

(who's grandfather is from London and grandmother from Trinidad; but
is nevertheless American)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-07-01 Thread Robert Greayer
I'm sure there's some important historical reason... but why isn't ''
used in something more prominent than the fgl package?  I understand
why it's not used for bitwise AND in Data.Bits (I assume because the
corresponding bitwise '|' operator isn't available), but all the other
single-character operators** (in the ASCII range) are used in some
core library (if not the Prelude itself).  But not ''.  Why?  It
makes sense (to me) as a Monoid 'append'.

** - according to Hoogle

On Wed, Jul 1, 2009 at 10:46 AM, Edward Kmettekm...@gmail.com wrote:
 I'm rather fond of the () suggestion, but would be happy with anything
 better than mappend! ;)

 -Ed

 On Wed, Jul 1, 2009 at 8:56 AM, Brent Yorgey byor...@seas.upenn.edu wrote:

 On Wed, Jul 01, 2009 at 12:00:50AM -0400, a...@spamcop.net wrote:
  G'day all.

 
  On Tue, Jun 30, 2009 at 08:02:48PM -0400, Daniel Peebles wrote:
 
  But we don't want to imply it's commutative either. Having something
  bidirectional like  or + feels more commutative than associative
  to me.
 
  Quoting John Meacham j...@repetae.net:
 
  Not really, think of '++', which doesn't commute but is visually
  symmetric, or Data.Sequence., or the common use of  to mean
  concatination in pretty printers.
 
  Other good examples are  and ||.

 ..wha?  But those ARE commutative.  Unless you mean with respect to
 strictness?

 -Brent
 ___
 Haskell-Cafe 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


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [: Where the bracket things are? :]

2009-06-29 Thread Robert Greayer
You can use QuasiQuotation, where your bracketing syntax looks like:

[$foo| blah blah blah |]

and 'foo' represents a quasi-quoter, and the stuff inside the brackets
is any arbitrary syntax recognized by it.

http://www.haskell.org/ghc/docs/latest/html/users_guide/template-haskell.html#th-quasiquotation


On Mon, Jun 29, 2009 at 4:51 PM, Paul Keirpk...@dcs.gla.ac.uk wrote:
 I'd like to add my own custom list delimiters to ghc; such as the [: and :]
 of Data Parallel Haskell. The purpose is mainly to learn a little about
 GHC's internals.

 Any suggestions on the GHC files I should look at first? Alternatively,
 maybe this is actually possible from outside the compiler.

 Cheers,
 Paul

 ___
 Haskell-Cafe 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


Fwd: [Haskell-cafe] Logo

2009-06-15 Thread Robert Greayer
Meant this to go to the list...


-- Forwarded message --
From: Robert Greayer robgrea...@gmail.com
To: Ashley Yakeley ash...@semantic.org


For anyone concerned the Hackage icon
(http://hackage.haskell.org/favicon.ico) is still the old blue lambda,
not the sparkling new icon (http://haskell.org/favicon.ico).

On Mon, Jun 15, 2009 at 2:39 AM, Ashley Yakeleyash...@semantic.org wrote:
 Thomas Davie wrote:

 We had a lot of fun deciding Haskell's new logo, and while I don't agree
 with the final result, it would be nice if we could now start consistently
 using it.  With that in mind, I realised that the Haskell Platform's logo is
 totally different, and did a quick mock up of a version reflecting the
 current Haskell logo.  It needs someone with the original vector graphics to
 have a play and improve it a little bit, but hopefully you'll se a concept
 you like.

 I rather like the fact that the Haskell Platform logo is distinct from the
 Haskell logo. I think it helps prevent confusion (even though the Platform
 logo is based on one of the Haskell logo competition entrants).

 http://haskell.org/haskellwiki/Haskell_Platform

 By the way, when I came to replace the Haskell logo on the wiki site, since
 the colours had not and still have not been officially decided on, I just
 picked the same colours as the Haskell Platform logo. So for the time being,
 there is a visual link between the two logos.

 --
 Ashley Yakeley
 ___
 Haskell-Cafe 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


Re: Is 78 characters still a good option? Was: [Haskell-cafe] breaking too long lines

2009-04-21 Thread Robert Greayer

Xiao-Yong Jin xj2...@columbia.edu wrote:
 Edward Kmett ekm...@gmail.com writes:
 
  I find a hard 80 character line length limit to be
  somewhat ridiculous in this
  day and age. I've long since revised my personal
  rule of thumb upwards towards
  132, if only because I can still show two windows of
  that side by side with no
  worries, along with all the IDE browsing baggage, even
  on a fairly crippled
  laptop, and I've been able to have 132 columns
  since I picked up my first
  vt220 terminal in 1984 or so.
   
 
 I prefer 3 coding windows side by side.  And being able to
 read one line at a glance is a huge advantage.  The size of
 my urxvt is 80x77 FYI.


But the discussion is about a coding standard -- surely if I claimed to like to 
have 4 windows side by side, that wouldn't be a good reason to reduce the 
standard to 40 columns?  Being able to read one line 'at a glance' seems to me 
to be improved if that line contains the complete equation, rather than just a 
fragment.  Comprehension of a group of related equations can be improved if 
they all fit on one screen (vertically).  Some code that I've written is 
intended to look like (and function as) rewrite rules  and looks vastly better 
with pattern and replacement all on the same line.  All the arguments can cut 
both ways -- for those who like coding with windows side by side, what about 
those who like coding with one window above another? Coding style is very 
situational, but the 80 character standard came about due to a once-ubiquitous 
device limitation (which no longer exists).

The *real* purpose of a coding standard, of course, is to give people something 
to argue over when they could be actually doing something more productive.  So 
in the end, it's all good, I suppose.






___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Is 78 characters still a good option? Was: [Haskell-cafe] breaking too long lines

2009-04-21 Thread Robert Greayer

wren ng thornton w...@freegeek.org wrote:

 There is a deeper reason. Much work in typography has shown
 that humans read text best when it's around 76
 characters wide; if things get narrower than that then
 cohesion is lost, if things get wider then it takes a long
 time to acquire the beginning of the next line.

My impression of the research is that it isn't nearly so conclusive. See [1] 
for a brief survey of findings for online reading speed/comprehension and a 
relatively recent study.  The results are all over the place.  Nevertheless, 
your later point - code /= text, is key.  I'd expect there's a study that 
focuses on code, though I don't have one at my fingertips.  I imagine reading 
speed for code is overall much lower than for natural language, which I expect 
is an important factor affecting eye movement.  I'd also guess that reading 
patterns are quite different -- scanning backward or forward to find a 
definition, etc.  It's different enough that I'd discount research focusing on 
natural language text as being relevant.  



[1] http://psychology.wichita.edu/surl/usabilitynews/72/LineLength.asp



  
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: logfloat 0.12.0.1

2009-04-03 Thread Robert Greayer

wren ng thornton wrote:
 Using the FFI complicates the build process for Hugs; details are noted in 
 the INSTALL file. It may also complicate building on Windows (due to ccall vs 
 stdcall),  though I'm not familiar with Windows FFI and don't have a machine 
 to test on.

On XP with GHC 6.10.1 it installed cleanly and easily via cabal-install (and a 
test program comparing results of (log . (1+)) v. log1p) showed that it worked 
properly).


  
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [Probably a dumb question] Quasiquoting

2009-03-31 Thread Robert Greayer

Andrew Coppin wrote:
| Is there some reason why you can't have antiquoting with normal TH?
| 
| I'm just trying to make sure I've understood QQ correctly...

With TH, it might not be necessary (depending on the situation)...

 {-# OPTIONS_GHC -XTemplateHaskell #-}
 module QT where

 import Language.Haskell.TH

 foo s = $([| hello  ++ s |])

The TH quotation builds a TH expression (of type Q Exp) in which there is a 
variable 's' which is free.  Since it's spliced into a context that happens to 
bind an 's', it compiles...

But you can also splice into your quotes:

 bar s = $(let v = varE (mkName s) in [| hello  ++ $v |])


  
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [Probably a dumb question] Quasiquoting

2009-03-30 Thread Robert Greayer

With some more context:

foo = ($expr 1 + 2)

v.

bar = [$expr| 1 + 2]

In the first example (assuming TH is enabled), $expr is a splice, which happens 
at compile time. 'expr' is some value of type Q Exp (the AST for a Haskell 
expression, in the quotation monad).  The application of $expr to the value 1 
+ 2 happens at runtime (assuming $expr splices a value of type String - a, 
otherwise its a compile time error).

In the second example, expr is a value of type QuasiQuoter, which contains an 
element quoteExpr, a function of type String - Q Exp, which is applied at 
compile time to the contents of the quasiquotation ( 1 + 2), and the result 
spliced in.  The value of 'foo' and 'bar' could work out to be exactly the 
same, depending on the implementation of expr in each instance.  But the 'work' 
of expr in the first instance happens when the value of foo is demanded, 
whereas in the second case, it happens at compile time.

Of course, you could also have:

foo = $(expr 1 + 2)

In this case expr is a function of type String - Q Exp, which is applied to 
its argument 1 + 2 at compile time.  It is very similar to the QQ example.  
One advantage to qq is that you can do:

foo s = [$expr|
int main(int argc, char** argv) {
printf(hello $s!\n);
}

  |]

assuming your expression parser supports anti-quotation.  Also you can in 
theory put qq's in patterns:

foo y [$expr|printf($_)|] = [$expr|printf($y)|]

although take this example with a grain of salt (I've not played with this 
aspect of quasiquotation).  Note also that antiquotation syntax is completely 
up to the QuasiQuoter (the $s, $_, could just as easily be @{s} or ***_***, or 
something else, depending on the implementation of expr).



- Original Message 
From: Andrew Coppin andrewcop...@btinternet.com
To: haskell-cafe@haskell.org
Sent: Monday, March 30, 2009 5:26:28 PM
Subject: [Haskell-cafe] [Probably a dumb question] Quasiquoting

Can somebody explain to me how

[$expr| 1 + 2 |]

is different from

($expr 1 + 2)

Other than a superficially different type signature, I'm not seeing what the 
fundamental difference is...

___
Haskell-Cafe 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


Re: [Haskell-cafe] Re: Exception handling in numeric computations

2009-03-27 Thread Robert Greayer

Henning Thielemann lemm...@henning-thielemann.de wrote:
 The usual example against clear separation of exceptions and errors is the 
 web server which catches 'error's in order to keep running. 
 However, the web server starts its parts as threads, and whenever one thread 
 runs into an 'error', it is terminated, just like an external shell
 program, that terminates with a segmentation fault. So, yes an error might be 
 turned into an exception, but these are rare cases. In 
 general it is hard or impossible to correctly clean up after an error, 
 because the error occured due to something that you as programmer
 didn't respect. The error handler could well make things worse by freeing 
 memory that is already deallocated and so on.

I don't see that as an argument against 'clear separation', really.  Having 
_some_ way of dealing an error (from within a program), in special 
circumstances doesn't preclude clearly separating how it's done from exception 
handling.  I always find it jarring when an HUnit test I've run tells me it 
encountered an 'exception', when I'm testing pure code (nevertheless I'd also 
find it annoying if the entire test run terminated because of a failed pattern 
match).

With respect to the last point - isn't proving that a given program can't 
corrupt its own RTS possible, even in the presence of errors?



  
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] base-4 + gtk2hs-0.10.0 licensing

2009-02-25 Thread Robert Greayer
Colin Paul Adams wrote:
 But IF there is no difference between LGPL and GPL for Haskell
 programs, then the licensing of gtk2hs as LGPL is just a smokescreen -
 it is effectively GPL, so you have to license your program as GPL.

 Which I'm all in favour of :-)

I actually don't think this is 100% true.  With the LGPL, you can distribute 
your program with under a non-GPL license, as long as you provide *some 
mechanism* for replacing the library and recreating the program.  Normally this 
means dynamic linking.  But it also allows you (I think) to distribute your 
program with a GPL-incompatible-but-nevertheless-open-source license, because 
that provides a mechanism for replacing the library (because you can rebuild 
the program from source).  If you license the library under GPL, you cannot 
even do that.  At least this is my understanding...


  
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Overloading functions based on arguments?

2009-02-13 Thread Robert Greayer
-- John A. De Goes wrote:

 Adding information cannot remove a contradiction from the information
 set available to the compiler.

 But it can and often does, for example, for [] or 4. What's the type of 
 either expression without more information?

[] :: [a]

4 :: Num a = a

Do I win something?


  
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell and Java interaction

2009-02-09 Thread Robert Greayer
I'm sure this isn't the solution you are looking for, but when I had to do 
something similar (integrate an Eclipse plugin to Haskell code) the simplest 
approach I found was to simply invoke the Haskell in a separate process, 
binding the stdin/stdout of the Haskell process to Java output/input streams.  
Perhaps low-tech, but has worked well for me.




- Original Message 
From: Silviu ANDRICA silviu.andr...@epfl.ch
To: haskell-cafe@haskell.org haskell-cafe@haskell.org
Sent: Monday, February 9, 2009 10:56:40 AM
Subject: [Haskell-cafe] Haskell and Java interaction

Hello,
I was wondering if there is a way to call Haskell code from Java. I tried using 
jvm-bridge(http://sourceforge.net/projects/jvm-bridge/), but I'm stuck on 
building it.

Thank you very much,
Silviu
___
Haskell-Cafe 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


Re: [Haskell-cafe] Re: Comments from OCaml Hacker Brian Hurt

2009-01-18 Thread Robert Greayer




- Original Message 
From: Andrew Coppin andrewcop...@btinternet.com
 Which is why I personally prefer HiddenTypeVariables. (This has the advantage 
 of using only pronouncible English 
words, which means you can use it when speaking out loud.)

Existential  - English, easy to pronounce
Quantify - English, easy to pronounce

I know I've been seeing those backwards E's and upside down A's in 
not-so-advanced Maths courses for a long time (since high school, I'm sure) and 
I certainly encountered them before 'Boolean'.  If you could do a geometry 
proof in high school, you have the Maths background need to understand the 
ideas.  (How they apply to types is another story, but the words shouldn't be 
scary.)

 I can't await the next Haskell standard, where at last all those
 extensions are builtin.

 This frightens me.

 At the moment, I understand how Haskell 98 works. There are lots of extensions
 out there, but I don't have to care about that because I don't use them. If I 
 read 
 somebody else's code and it contains a LANGUAGE pragma, I can immediately
 tell that the code won't be comprehendable, so I don't need to waste time 
 trying 
 to read it. But once Haskell' becomes standard, none of this holds any more.
 Haskell' code will use obscure lanuage features without warning, and unless I 
 somehow learn every extension in the set, I'll never be able to read Haskell
 again! (One presumes that they won't add any extensions which actually 
 *break* 
 backwards compatibility, so hopefully I can still pretend these troublesome
 extensions don't exist when writing my own code...)

Some of the most useful libraries (e.g. parsec, generics) use these type system 
extensions (higher rank polymorphism, existentials).  It would be great if 
these could be considered 'standard Haskell'.

___
Haskell-Cafe 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


Re: [Haskell-cafe] Haskell not ready for Foo [was: Re: Hypothetical Haskell job in New York]

2009-01-15 Thread Robert Greayer




- Original Message 
From: John A. De Goes j...@n-brain.net
On Jan 15, 2009, at 9:31 AM, John Goerzen wrote:
 AFAIK, the only language where that sort of wheel reinvention is
 popular is Java.  But then Java seems to encourage wheel reinvention
 anyhow ;-)

 The Java reinventions look and feel like Java, because they're native 
 implementations. 
 This is even more important in Haskell where the differences between 
 Haskell and C is about as large as you can get.

The Java reinventions largely exist because of the huge deployment-time 
benefits you get from pure-Java code (cross-platform portability of compiled 
(byte) code, dynamic loading of compiled code over a network, etc.).  Such 
reinventions are much less important for Haskell, since the typical deployment 
model for a Haskell program is much closer to that of a C program than a Java 
program or even a Python program.  


  
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Enum and Bounded in generic type

2008-12-30 Thread Robert Greayer
Raeck said:

 Hi, how can I make the following code work? (show all the possible values of 
 a type 'a')

 showAll :: (Eq a, Bounded a, Enum a) = a - [a]
 showAll a = [minBound..maxBound]::[a]

What you are really looking for, I think, is a polymorphic value of type [a], 
where a is some enumerable, bounded type.

allValues :: (Enum a, Bounded a) = [a]
allValues = [minBound .. maxBound]

You can omit the type signature, but then you'll run into the monomorphism 
restriction (which you'll can turn off with, e.g. -XNoMonomorphismRestriction)


  
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Can I build and install GHC 6.10.1 withoutprevious installed ghc

2008-12-22 Thread Robert Greayer
I've recently built 6.10.1 on fairly archaic RHEL servers, both 64 and 32 bit, 
and the incantation that worked most seamlessly for me was to grab a really old 
binary release (in my case 6.2 worked) that installs without intervention, and 
then build up to the latest version (6.10.1) in steps -- I built 6.6 with 6.2, 
then 6.10.1 with 6.6, and it all worked without a problem.  Of course, I'd try 
6.6/binary first, but if that doesn't work, all is not lost, older binary 
releases may still work, and you can then bootstrap from those.

Rob



- Original Message 
From: Wang, Chunye (NSN - CN/Beijing) chunye.w...@nsn.com
To: Haskell-Cafe@haskell.org
Sent: Monday, December 22, 2008 4:53:53 AM
Subject: RE: [Haskell-cafe] Can I build and install GHC 6.10.1 withoutprevious 
installed ghc

Hi Duncan,


wget
http://haskell.org/ghc/dist/6.8.2/ghc-6.8.2-x86_64-unknown-linux.tar.bz2
tar -jxvf ghc-6.8.2-x86_64-unknown-linux.tar.bz2 
cd ghc-6.8.2
./configure 

checking build system type... x86_64-unknown-linux-gnu
checking host system type... x86_64-unknown-linux-gnu
checking target system type... x86_64-unknown-linux-gnu
Which we'll further canonicalise into: x86_64-unknown-linux
checking for path to top of build tree... pwd: timer_create: Invalid
argument
configure: error: cannot determine current directory

Even though I can fixed this by ``cp /bin/pwd utils/pwd/pwd'' , there is
still similar error

``ghc-pkg.bin: timer_create: Invalid argument''

I guess any executable file generates same error message.


Best Regards
Chunye Wang chunye.w...@nsn.com


-Original Message-
From: ext Duncan Coutts [mailto:duncan.cou...@worc.ox.ac.uk] 
Sent: Monday, December 22, 2008 5:38 PM
To: Wang, Chunye (NSN - CN/Beijing)
Cc: Haskell-Cafe@haskell.org
Subject: RE: [Haskell-cafe] Can I build and install GHC 6.10.1
withoutprevious installed ghc

On Mon, 2008-12-22 at 11:53 +0800, Wang, Chunye (NSN - CN/Beijing)
wrote:
 
 I tried to install the ghc 6.8.0 last year but failed for some reason.

 Now I decide to do it again, because I'd like to try some examples in 
 Real World Haskell Now I remember why I try to install it from 
 source code, because the binary version has the following problem.

 I guess ``timer_create '' is failed because of library confliction.

I suggest you use the binary for ghc-6.8.2 (not 6.8.3) or earlier
because those were built on an old Red Hat 9 server and are thus
compatible with older versions of glibc and the Linux kernel.

If you really need ghc-6.10 (you probably do not if you're just trying
examples from the Real World Haskell book) then you can build ghc-6.10.x
from source once you have the ghc-6.8.2 binary installed.

Duncan

___
Haskell-Cafe 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


[Haskell-cafe] Hackage/Cabal/Haddock question

2008-11-21 Thread Robert Greayer
How does Hackage run 'haddock' on uploaded packages?  I had assumed it directly 
runs the cabal 'haddock' target, e.g.

runhaskell Setup.hs haddock

but it appears to perhaps be more complex than that.

Some backrgound --

haddock doesn't seem to like quasiquotation - running haddock on a source tree 
that includes quasiquotations eventually results in:

haddock: internal Haddock or GHC error: Maybe.fromJust: Nothing

(eliminating the code that contains [$xxx|] constructs gets rid of the 
error.)

so runhaskell Setup.hs haddock ends up not generating any documentation.  I 
worked around this problem by using a 'UserHook' and adding in an extra path 
element to the source path prior to running haddock via Cabal:

 main = defaultMainWithHooks (simpleUserHooks {
 preHaddock = \_ _ - return (Just $ emptyBuildInfo { hsSourceDirs = 
 [noqqsrc]},[]) })

The additional directory contains an alternate version of modules that don't 
contain quasiquotation (just types and stubs), which seems to hide the versions 
that do.  This works fine locally, but not on hackage (still get the same 
behavior in the build failure log).  Of course, I'd prefer not to have to do 
this at all, so if anyone knows a way around the problem (or if its purely my 
problem -- I'm doing something wrong), I'd appreciate hearing about it.

I'm using GHC 6.10.1, and have tried setup haddock with both the 
shipped-with-ghc version of haddock and the latest version.

Thanks,
rcg


  
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] What *not* to use Haskell for

2008-11-11 Thread Robert Greayer
--- On Tue, 11/11/08, Dave Tapley [EMAIL PROTECTED] wrote:
 So I should clarify I'm not a troll and do see
 the Haskell light. But
 one thing I can never answer when preaching to others is
 what does
 Haskell not do well?
 

'Hard' real-time applications?  I don't know that there couldn't be a 
'real-time friendly' Haskell, but for some applications, the unpredictability 
(however slight) of when, for example, garbage collection happens, or how long 
it takes, is unacceptable. (Even the unpredictability of heap 
allocation/deallocation a la malloc/free is unacceptable for some real time 
apps).  Haskell is in the same boat here with lots of other languages, of 
course.


  
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Crash!

2008-10-25 Thread Robert Greayer



--- On Fri, 10/24/08, Derek Elkins [EMAIL PROTECTED] wrote:
  Just what is the concise, compelling, unembellished
 claim regarding
  Haskell's inherent robustness?
 
 The concise, compelling, unembellished claim is: if your
 pure* Haskell
 program segfaults (or GPFs) then it's the
 implementation's fault, not
 yours. [unless your OS/Arch is stupid]
 
 This isn't unique to Haskell, every memory-safe
 language has it.
 
 * pure as in 100% pure Java which
 has similar claims

But Java's 'claim' actually works out to be easier to reason about: generally, 
with Java, no matter what 3rd party code you are using, without looking at the 
source, you know the only way (excluding a JVM/platform bug) that your code 
will segfault or otherwise corrupt the runtime system is if the 3rd party code 
includes native libraries (i.e. is non-100% pure Java -- the third party code 
is more than just collection of jar files).  

Whereas with Haskell code, you can't really know if it is safe (in this sense) 
without looking at the code in the Haskell libraries you're using.  A library 
that is 100% Haskell can be doing unsafe things *in Haskell*.  Further, many 
safe Haskell libraries require the use of 'unsafe' functions, so there's no 
(afaik) simple rubric for determining if a library is safe, and hence whether a 
program will be segfault (or memory corruption) free.

With the advent of the 'haskell platform' it seems to me that the situation 
could improve -- given that the platform has been 'blessed', you could reason 
that as long as you stick to libraries that are in the platform or libraries 
that are free of 'unsafe' functions or FFI (or any other known pitfalls), 
you've got a safe executable (and then, if it segfaults, you can blame the 
platform).  It would be extremely clever if your build tool could take 
advantage of this and tell you whether your executable was 'safe' in this 
sense, based on its analysis of the packages (or even functions) used to build 
it.  (Or perhaps this is already a solved problem and I just don't know about 
it!)



  
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Temlpate Haskell: [d| ... |]

2008-10-17 Thread Robert Greayer
--- On Fri, 10/17/08, Achim Schneider [EMAIL PROTECTED] wrote:
   declarations = [d|
  foo = bar
  bar = foo
   |]
 -fth doesn't make a difference here, I'm using
 -XTemplateHaskell with
 ghc 6.8.3
 

The following lines, verbatim, pasted into a file, work for me with 6.8.3 with 
no command line options:

{-# LANGUAGE TemplateHaskell #-}
module TH where
import Language.Haskell.TH

declarations = [d|
   foo = bar
   bar = foo
   |]

__
Do You Yahoo!?
Tired of spam?  Yahoo! Mail has the best spam protection around 
http://mail.yahoo.com 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[2]: [Haskell-cafe] Re: What I wish someone had told me...

2008-10-16 Thread Robert Greayer
 On Thu, 2008-10-16 at 15:02 +1300, Richard O'Keefe
 wrote:
  On 16 Oct 2008, at 12:09 pm, Jonathan Cast wrote:
   I am not sure how say in a Java language a
 constructor can conjure  
   up
   a value of an unknown type.
  
   Well, that's the point.  It can't, in
 Haskell or in Java.  If you
   understand that --- that you can't call the
 default constructor of a
   class that is not statically known at compile
 time
  
  If you understand that about Java, then you don't
 understand Java.
 
 God, I hope never to understand Java.  *shudder*
 
  Java reflection means that compile-time types are
 backed up by
  runtime objects belonging to Type in general, to Class
 if they
  are class types.  It also means that you can discover
 the
  default constructor by using aClass.getConstructor(),
 and you
  can invoke it by using .newInstance().
 
 Wait, what?  Why can't Java use this to keep template
 parameters around
 at run time?  Or is the article (as per which
 SetInteger and
 SetDouble are identical at run time) full of it?
 

The article (whichever it was) wasn't full of it... SetInteger and 
SetDouble are identical at runtime.  You cannot, given a Class object at 
runtime that happens to be the Class object corresponding to Set?, conjure up 
an instance of Set... but simply for the reason that Set has no constructors 
(it is an interface).  You can, however, given a class object that happens to 
be the class object corresponding to (say) HashSet, conjure up an instance of a 
HashSet, and assign it to a variable of the (static) type SetInteger or 
SetDouble... i.e.

SetInteger foo = (SetInteger) hashSetClass.newInstance();
SetDouble bar = (SetDouble) hashSetClass.newInstance();

which will generate warnings about unsafe casts, but nevertheless can compile, 
and won't cause any exceptions at runtime.



  
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[2]: [Haskell-cafe] Re: What I wish someone had told me...

2008-10-16 Thread Robert Greayer



--- On Thu, 10/16/08, Jonathan Cast [EMAIL PROTECTED] wrote:

 Can I have HashSetInteger?  Could I construct
 HashSet?, if I did?

Yes:

HashSet? blah = (HashSet?) hashSetClass.newInstance();

... compiles, and won't throw an exception if hashSetClass truly is the class 
object for HashSet.  Pretty useless, because you can't put anything *into* a 
HashSet? object...

blah.add(foo); // doesn't typecheck...

but you can do:
HashSetString blah = (HashSetString) hashSetClass.newInstance();
blah.add(foo);

works fine..




  
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[2]: [Haskell-cafe] Re: What I wish someone had told me...

2008-10-16 Thread Robert Greayer



--- On Thu, 10/16/08, Jonathan Cast [EMAIL PROTECTED] wrote:

 But I can't say new HashSet?()?
 
No... but you can say 'new HashSetT()' where T is a type variable, and then 
put a value of type T into your set, which is probably generally what you want. 
 HashSet? is a set of unknown (at compile time) element type.  It is not safe 
to put any element into such a set.  Consider:

void wrong(List? foo, List? bar) {
   foo.add(bar.get(0)); // illegal... but if it weren't...
}

...
ListInteger x = ...;
ListString y = ...;
wrong(x, y); // then this would put an String into a list of ints...

---

Perhaps there was confusion over what you meant by 'conjure up a value of an 
unknown type'... you can't explicitly instantiate a parameterized class with a 
wildcard type variable (e.g. new HashSet?).  However, you can conjure up an 
instance of any class for which you have a Class object handy, provided it is 
non-abstract and has public constructors, and then assign it to a variable with 
a wildcard in its type.





  
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[2]: [Haskell-cafe] Re: What I wish someone had told me...

2008-10-16 Thread Robert Greayer
--- On Thu, 10/16/08, Jonathan Cast [EMAIL PROTECTED] wrote:
 So if I say
 
 void wrong(List? foo, List? bar)
 
 I get two /different/ type variables implicitly filled in?
 
 If I declare a generic class, and then have a method, is
 there a way, in
 that method's parameter list, to say `the type
 parameter that was
 supplied when my class was instantiated'?
 

Yes -
class FooT {
   ...
   void right(ListT foo, ListT bar) {
  foo.add(bar.get(0));
   }

Can also do it at the method level...

void T alsoRight(ListT foo, ListT bar) { ... }

 Yikes.  So, in this instance, the difference between
 Haskell and Java
 is: if you want to disallow that call to wrong, in Haskell
 you can...
 

Not exactly... Java disallows 'wrong' from being written (without class casts 
and such), because it disallows calling a method which has a wildcard type in a 
contravariant position.  IIRC, Scala handles all this more elegantly.  If you 
stay away from '?', and stick to type variables with Java generics, though, how 
type checking with generics works in Java should be mostly unsurprising to a 
Haskeller.




  
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Stacking monads

2008-10-02 Thread Robert Greayer

--- On Thu, 10/2/08, Andrew Coppin [EMAIL PROTECTED] wrote:
 I'm lost...
 
 (What does liftM have to do with fmap?)

They're (effectively) the same function.

i.e.

liftM :: (Monad m) = (a - b) - m a - m b
fmap :: (Functor f) = (a - b) - f a - f b

liftM turns a function from a to b into a function from m a to m b;
fmap turns a function from a to b into a function from f a to f b;

If your datatype with a Monad instance also has a Functor instance (which it 
*can* have, you just need to declare the instance), then liftM is equivalent to 
fmap.






  
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] A round of golf

2008-09-18 Thread Robert Greayer
--- On Thu, 9/18/08, Creighton Hogg [EMAIL PROTECTED] wrote:
 If this makes anyone cringe or cry
 you're doing it wrong, I'd
 actually like to hear it.

Just to make everyone cry:

main = getArgs = \(x:_) - system (wc -l  ++ x)





  
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Can you do everything without shared-memory concurrency?

2008-09-12 Thread Robert Greayer
--- On Fri, 9/12/08, Bruce Eckel [EMAIL PROTECTED] wrote:

 OK, let me throw another idea out here. When Allen Holub
 first
 explained Actors to me, he made the statement that Actors
 prevent
 deadlocks. In my subsequent understanding of them, I
 haven't seen
 anything that would disagree with that -- as long as you
 only use
 Actors and nothing else for parallelism.
 

As I believe it is the case that you can emulate shared resources, and locks to 
control concurrent access to them, using the actor model, I can't see how this 
can be true.

rcg



  
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell Propeganda

2008-08-27 Thread Robert Greayer
--- On Wed, 8/27/08, Dan Weston [EMAIL PROTECTED] wrote:
 
 Failure to handle a null pointer is just like using
 fromJust and results 
 in the same program termination (undefined).
 
 Dan
 

Well, not (IMHO) 'just like': 'fromJust Nothing' turns into a 'catchable' 
exception in the IO Monad, but a SEGFAULT certainly doesn't.

E.g.
 import Control.Exception as C
 import Data.Maybe
 main = do
(fromJust Nothing = ( \ s - putStrLn s)) `C.catch` 
(\ _ - putStrLn ok)

prints 'ok', whereas:

 import Foreign.Ptr
 import Foreign.Storable
 import qualified Control.Exception as E
 main = poke nullPtr '\0' `E.catch` (\ _ - putStrLn ok)

just segfaults...





  
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] What's in a name?

2008-08-16 Thread Robert Greayer



--- On Sat, 8/16/08, Andrew Coppin [EMAIL PROTECTED] wrote:
  Although it is possible to hide packages by GHC options, we should not
  do this, because several libraries might use different Hash tables and 
  it would not be possible to write a program which uses many of these 
  libraries. It's better to add a distinguishing part to the module 
  name, like Data.HashTable.Coppin or so.
 
 This is more the sort of thing I had in mind, yes.

This seems to be a common approach, but it runs counter to the objective of 
separating 'provenance' from module naming.  'Coppin' is (part of, sans 
version) the provenance of the hashtable implementation, so I'm not sure how 
this sort of scheme is better than just shoving the unique prefix at the front 
of the module, e.g.

Coppin.Data.Hashtable

Though embedding the provenance down in the hierarchy is a common pattern,  I 
think it is can be pretty messy.  For example, the Parsec package exposes many 
modules, including Text.Parsec.String and 
Text.ParserCombinators.Parsec.Token -- the provenance appears at different 
levels in the hierarchy.  If you're going to shove the package name in there, 
it seems simpler to me to just shove it at the front: 
Parsec.Text.ParserCombinators.Token.  The package mounting scheme might solve 
this (though it seems to me that it requires that source for packages be kept 
around.  I may be wrong).

 (As I already pointed out, there's at least 3 packages called bianry,  
 which is just confusing.)

On hackage? I only see one with that the exact name binary.


  
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] What's in a name?

2008-08-15 Thread Robert Greayer
--- On Sat, 8/16/08, wren ng thornton [EMAIL PROTECTED] wrote:
 Personally, I have major qualms with the Java package
 naming scheme. In 
 particular, using domain names sets the barrier to entry
 much too high 
 for casual developers (e.g. most of the Haskell user base).
 Yes, DNs are 
 cheap and plentiful, but this basically requires a lifetime
 lease of the 
 DN in question and the migration path is covered in
 brambles. The 
 alternative is simply to lie and make up a DN, in which
 case this 
 degenerates into the exact same resource quandary as doing
 nothing (but 
 with high overhead in guilt or registration paperwork).

This does sound in theory like a real problem; the actual practice has worked 
out much differently for Java: the existence of durable domains willing to host 
development of small libraries for the Java space are plentiful.  In other 
words, the barrier to entry has turned out to be quite low.

Nevertheless, hackage of course provides an even cheaper alternative to 
DN-based naming, since package names registered on hackage are guaranteed 
unique (across the hackage-using community).  The ubiquitous convention for 
Haskell could easily be that if you want your library to interoperate without 
conflict, register it on hackage (otherwise you take your chances, just as in 
Java if you ignore the DN-based convention).  Having the ability to use package 
names to avoid module-name conflicts (i.e. an agile packaging system, in your 
words) would still be needed.

The need to *recompile* to avoid conflicts is a problem though, if haskell 
aspires to attract commercial package vendors.  I don't know how it could be 
avoided though.

rcg



  
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Template Haskell ListT wrinkle

2008-06-24 Thread Robert Greayer

In messing around with TH, I noticed (what I consider
to be an) odd wrinkle in the handling of list types
within TH's syntax meta-data.  For example, given the
program at the end of this email, which prints out the
TH representation of the types 'Ints' and '[Int]',
where 'Ints' is just a type-alias for '[Int]', the
following results are generated:

Ints is: AppT (ConT GHC.Base.[]) (ConT GHC.Base.Int)
[Int] is: AppT ListT (ConT GHC.Base.Int)

type0, 'Ints' resolves to the application of the named
type constructor GHC.Base.[] to the named type
constructor GHC.Base.Int (which makes perfect
sense).  type1, '[Int]' resolves to the application of
the 'built-in' ListT type constructor to the named
type constructor GHC.Base.Int (which also makes
perfect sense).  What's odd (to me) is that in one
situation, the 'named' constructor 'GHC.Base.[]'
appears, and in the other, the 'built-in' constructor
appears.

Does anyone have insight into why this might be? 
(These results were obtained with GHC 6.8.2, btw).

 {-# OPTIONS_GHC -XTemplateHaskell #-}
 module Main where
 import Language.Haskell.TH

 type Ints = [Int]

 type0 = $( reify ''Ints = (\ (TyConI (TySynD _ _
t)) - return $ show t) = \s - [| s |])
 type1 = $( [t| [Int] |] = return . show = \s -
[| s |])

 main = do
putStrLn (Ints is:  ++ type0)
putStrLn ([Int] is:  ++ type1)

Thanks
rcg


  
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Trying to write a very simple HTTP Client

2008-05-23 Thread Robert Greayer

--- Eric [EMAIL PROTECTED] wrote:

 Hi all,
 
 I've written the following program to connect to a
 submit an HTTP GET 
 request to a server and print the response:
 
 module Main where
 
 import Network
 import System.IO
 
 main = withSocketsDo go
 
 go = do putStrLn Connecting...
 out - connectTo haskell.org
 (PortNumber 80)
 hPutStrLn out GET /\r
 hPutStrLn out Host: haskell.org\r
 hPutStrLn out \r
 cs- hGetLine out
 hClose out
 print cs
 
 When I run the program, however, I get the following
 error:
 
 HTTPClient: socket: 1872: hGetLine: end of file
 
 Can anyone see what's wrong?
 
 
 E.

Try calling 'hFlush out' prior to the call to
hGetLine.   I believe the output to the socket is
buffered, so the receiver isn't seeing your GET
request, and eventually closes the connection on its
end, leading to the EOF on  the hGetLine.


 
 ___
 Haskell-Cafe 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