exhausted simplifier ticks and hs-boot files

2019-08-05 Thread Ganesh Sittampalam
Hi,

The code below (also attached - unzip and run go.sh) triggers the GHC
panic "Simplifier ticks exhausted", and I'm unsure whether I should view
it as an instance of the known infelicity in the inliner
(https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/bugs.html#bugs-ghc)

My code does have a recursive datatype, but the recursion isn't
contravariant, which is the case described in "Secrets of the GHC
inliner"
(https://www.microsoft.com/en-us/research/wp-content/uploads/2002/07/inline.pdf,
section 4).

It's cut down from some real code where I have a mutually recursive
datatype that I want to define across two modules for code structuring
reasons, meaning I need a .hs-boot file. I haven't been able to
reproduce it without the .hs-boot file - if I put everything in one
module it stops happening.

I've tried with a range of GHC versions from 8.2.x to an early version
of 8.8. It happens with -O1 and not -O0, but I haven't managed to find a
specific optimisation that triggers it.

Is this just an instance of the known problem in a different guise, or
is it something different and worth a bug report?

Cheers,

Ganesh

T2.hs-boot
---
module T2 where

data T2

mapP_T2 :: (Int -> Int) -> T2 -> T2

T1.hs
-
module T1 where

import {-# SOURCE #-} T2

data T1 = T1 T2

mapP_T1 :: (Int -> Int) -> T1 -> T1
mapP_T1 _ (T1 xs) = T1 (mapP_T2 id xs)

T2.hs
-

module T2 where

import T1

data T2 = T2 T1

mapP_T2 :: (Int -> Int) -> T2 -> T2
mapP_T2 f (T2 t) = T2 (mapP_T1 f t)

go :: T1 -> T1
go = mapP_T1 id

GHC output
--
$ ghc --make T2.hs -O1 -fsimpl-tick-factor=1000 -ddump-simpl-stats)
[...]
ghc.exe: panic! (the 'impossible' happened)
  (GHC version 8.2.2 for x86_64-unknown-mingw32):
Simplifier ticks exhausted
  When trying UnfoldingDone mapP_T2
  To increase the limit, use -fsimpl-tick-factor=N (default 100)
  If you need to do this, let GHC HQ know, and what factor you needed
  Total ticks: 61203

  24481 PreInlineUnconditionally
6121 ds_i17h
6120 f_a16p
6120 ds_d17d
6120 ds1_i17i
  12241 UnfoldingDone
6121 mapP_T1
6120 mapP_T2
  24481 BetaReduction
6121 ds_i17h
6120 f_a16p
6120 ds_d17d
6120 ds1_i17i
<>
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


Re: [core libraries] Re: Tightening up on inferred type signatures

2014-04-30 Thread Ganesh Sittampalam
On 23/04/2014 20:04, dm-list-haskell-librar...@scs.stanford.edu wrote:
 Edward Kmett ekm...@gmail.com writes:
 
 You can wind up in perfectly legitimate situations where the name for the
 type you are working with isn't in scope, but where you can write a
 combinator that would infer to have that type. I'd hate to lose that.

 It is admittedly of marginal utility at first glance, but there are some
 tricks that actually need it, and it can also arise if a type synonym
 expands to a type that isn't exported or brought into scope, so trying to
 push this line of reasoning too far I is possibly not too productive.
 
 Good point.  In particular, it's not weird at all want to export type
 synonyms on their own, particularly where ghost type parameters are used
 to select between only a few cases.  Consider something like this
 (inspired by postgresql-orm):

Is there an abstraction being protected by only exporting the type
synonym in cases like this?

Cheers,

Ganesh
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: PROPOSAL: Literate haskell and module file names

2014-03-16 Thread Ganesh Sittampalam
The behaviour could be invoked only for lower-case parts, but that may
prove problematic on case-insensitive filesystems like Windows.

On 16/03/2014 13:52, Carter Schonwald wrote:
 Idk, this behavior of doing Data.Vector.lhs seems pretty awesome.  I
 actually might start doing that.  That ghc allows that seems pretty darn
 awesome. And handy too
 
 On Sunday, March 16, 2014, Merijn Verstraaten mer...@inconsistent.nl
 mailto:mer...@inconsistent.nl wrote:
 
 My personal approach would have been to make ghc accept Foo.*.lhs,
 maintaining a list of potential file format seems arduous and error
 prone.
 
 Cheers,
 Merijn
 
 On Mar 16, 2014, at 14:13 , Joachim Breitner wrote:
  Hi,
 
  Am Sonntag, den 16.03.2014, 13:56 +0100 schrieb Merijn Verstraaten:
  Cons:
 
  GHC would have to either maintain a possibly long of variants to look
  for ([.hs, .lhs, .rst.lhs, .md.lhs, .svg.lhs, .docx.lhs]),
  or look for Foo.*.lhs.
 
  I’d find the latter acceptable, but it should be noted.
 
  Greetings,
  Joachim
 
  --
  Joachim “nomeata” Breitner
   m...@joachim-breitner.de javascript:; •
 http://www.joachim-breitner.de/
   Jabber: nome...@joachim-breitner.de javascript:;  • GPG-Key:
 0x4743206C
   Debian Developer: nome...@debian.org javascript:;
  ___
  Glasgow-haskell-users mailing list
  Glasgow-haskell-users@haskell.org javascript:;
  http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
 
 
 
 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
 

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: ANNOUNCE: GHC 7.8.1 Release Candidate 1

2014-02-03 Thread Ganesh Sittampalam
Just to note a problem I encountered on Windows, which may well be user
error.

I unpacked the mingw tarball and added the bin directory from it to my
path. cabal install then failed with cabal.exe: does not exist after
producing some other output.

Running with -v3 suggested that the actual problem was that the ld on my
path couldn't read the .o files produced by GHC. I changed my path to
also include the mingw\bin directory from the tarball, and then all was
fine.


On 03/02/2014 22:35, Austin Seipp wrote:
 We are pleased to announce the first release candidate for GHC 7.8.1:
 
 http://www.haskell.org/ghc/dist/7.8.1-rc1/
 http://www.haskell.org/ghc/docs/7.8.1-rc1/html/
 
 This includes the source tarball and bindists for Windows, Linux, OS
 X, FreeBSD, and Solaris, on x86 and x86_64. There is a signed copy of
 the SHA256 hashes available (attached) using my GPG key (keyid
 0x3B58D86F).
 
 We plan to make the 7.8.1 RC2 release quite soon, as we're aware of
 some existing issues.
 
 Please test as much as possible; bugs are much cheaper if we find them
 before the release!
 
 
 
 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
 

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: RFC: include a cabal-install executable in future GHC releases

2014-01-21 Thread Ganesh Sittampalam
I feel this blurs the roles of GHC and the Platform.

Can't the cabal-install that comes with the Platform can be used with a
later GHC installation? If that's correct, then the only use case that
this proposal covers is someone who wants to use a bleeding edge GHC and
no other version on a new machine. A separate binary distribution of
cabal-install should be more than adequate for that and it avoids
coupling GHC to other things.

So a weak -1.


On 20/01/2014 00:02, Carter Schonwald wrote:
 Hey everyone,
 
 I'd like to propose that GHC releases 7.8.1 onwards include a
 cabal-install (aka cabal) executable, but not include the library deps
 of cabal-install that aren't already distributed with ghc.(unless ghc
 should have those deps baked in, which theres very very good reasons not
 to do.). 
 
 currently if someone wants just a basic haskell install of the freshest
 ghc  they have to install a ghc bindist, then do a boostrap build of
 cabal-install by hand (if they want to actually get anything done :) ). 
 
 This is not a human friendly situation for folks who are new to haskell
 tooling, but want to try out haskell dev on a server style vm or the like! 
 
 point being: It'd be great for haskell usability (and egads amounts of
 config time, even by seasoned users) the ghc bindists / installers
 included a cabal-install binary
 
 thoughts?
 -Carter
 
 
 
 
 
 ___
 Libraries mailing list
 librar...@haskell.org
 http://www.haskell.org/mailman/listinfo/libraries
 

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: RFC: include a cabal-install executable in future GHC releases

2014-01-21 Thread Ganesh Sittampalam
If you can't find any better options, I can try to run a buildbot on a
laptop that's probably mostly online.


On 21/01/2014 19:32, Johan Tibell wrote:
 We could offer OS X and Linux binaries in addition to the Windows
 binaries already downloaded on the cabal home page
 (http://www.haskell.org/cabal/) if someone could commit to building them.
 
 Aside: Right now building the Windows binaries is a very ad-hoc process
 (I email Mikhail who has a Windows machine and ask him to build one).
 I'm not very keen to make the process even slower, given that that will
 mean I will make fewer cabal releases. Ideally the binaries could be
 produced on a build bot. The very least we should have the Makefile in
 the cabal repo being able to create the binary in a reproducible manner.
 
 -- Johan
 
 
 
 On Tue, Jan 21, 2014 at 11:22 AM, Ganesh Sittampalam gan...@earth.li
 mailto:gan...@earth.li wrote:
 
 I feel this blurs the roles of GHC and the Platform.
 
 Can't the cabal-install that comes with the Platform can be used with a
 later GHC installation? If that's correct, then the only use case that
 this proposal covers is someone who wants to use a bleeding edge GHC and
 no other version on a new machine. A separate binary distribution of
 cabal-install should be more than adequate for that and it avoids
 coupling GHC to other things.
 
 So a weak -1.
 
 
 On 20/01/2014 00:02, Carter Schonwald wrote:
  Hey everyone,
 
  I'd like to propose that GHC releases 7.8.1 onwards include a
  cabal-install (aka cabal) executable, but not include the library deps
  of cabal-install that aren't already distributed with ghc.(unless ghc
  should have those deps baked in, which theres very very good
 reasons not
  to do.).
 
  currently if someone wants just a basic haskell install of the
 freshest
  ghc  they have to install a ghc bindist, then do a boostrap build of
  cabal-install by hand (if they want to actually get anything done
 :) ).
 
  This is not a human friendly situation for folks who are new to
 haskell
  tooling, but want to try out haskell dev on a server style vm or
 the like!
 
  point being: It'd be great for haskell usability (and egads amounts of
  config time, even by seasoned users) the ghc bindists / installers
  included a cabal-install binary
 
  thoughts?
  -Carter
 
 
 
 
 
  ___
  Libraries mailing list
  librar...@haskell.org mailto:librar...@haskell.org
  http://www.haskell.org/mailman/listinfo/libraries
 
 
 ___
 Libraries mailing list
 librar...@haskell.org mailto:librar...@haskell.org
 http://www.haskell.org/mailman/listinfo/libraries
 
 

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: default roles

2013-10-09 Thread Ganesh Sittampalam
I think it would be ok to expect the constructors to be visible, even
though it might need to a lot being needed.

BTW I think you might need S1 visible as well otherwise how would you
convert (S1 True :: S Bool Int) into (S1 True :: S Bool Age)?

If you don't derive the role from constructor visibility then I think it
should fail-safe and default to the nominal role - valid Haskell 2010
code shouldn't be exposed to an abstraction leak just because it's GHC
compiling it.


On 08/10/2013 14:23, Richard Eisenberg wrote:
 Pedro is suggesting a way for a Haskell type-level program to gain
 access to role information. This might indeed be useful, but it
 doesn't seem terribly related to the problem of defaults /
 abstraction. The problem has to do with definitions like these:

  module A where
  data S a b = S1 a | S2 b
  data T a b = MkT (S a b)

  module B where
  import A ( {- what goes here? -} )
 
  class C a where
mkT :: T Bool a
 
  instance C Int where ...
  newtype Age = MkAge Int deriving C

 What constructors do we need in order to convert the (C Int) instance
 to (C Age) by hand? To me, it looks like we need MkT and S2, but not
 S1. Yet, this is not obvious and seems to be quite confusing.

 I hope this helps understanding the issue!
 Richard

 On Oct 8, 2013, at 4:01 AM, José Pedro Magalhães drei...@gmail.com
 mailto:drei...@gmail.com wrote:

 Hi,

 On Tue, Oct 8, 2013 at 3:21 AM, Richard Eisenberg e...@cis.upenn.edu
 mailto:e...@cis.upenn.edu wrote:

 We considered this for a while, but it led to a strange design --
 to do it right, you would have to import all constructors for all
 datatypes *recursively* out to the leaves, starting at the
 datatypes mentioned in the class for which you wanted to use GND.
 This would mean potentially a whole lot of imports for symbols
 not actually used in the text of a program.


 I'm not sure I understand why constructors are involved in this.
 Wouldn't something like
 the following potentially be useful?

 data Role = Nominal | Representational | Phantom | Fun Role Role

 type family HasRole (t :: k) :: Role

 data MyData a b = MyData a
 data MyGADT a b where MyGADT :: MyGADT a Int

 type instance HasRole MyData  = Fun Representational Phantom
 type instance HasRole MyGADT  = Fun Representational Nominal
 type instance HasRole Traversable = Nominal

 HasRole instances would be automatically given by GHC.


 Cheers,
 Pedro




___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: default roles

2013-10-07 Thread Ganesh Sittampalam
Is it possible to tie the role to whether the data constructor is
visible or not?

On 07/10/2013 14:26, Richard Eisenberg wrote:
 As you may have heard, /roles/ will be introduced with GHC 7.8. Roles
 are a mechanism to allow for safe 0-cost conversions between newtypes
 and their base types. GeneralizedNewtypeDeriving (GND) already did this
 for class instances, but in an unsafe way -- the feature has essentially
 been retrofitted to work with roles. This means that some uses of GND
 that appear to be unsafe will no longer work. See the wiki page [1] or
 slides from a recent presentation [2] for more info.
 
 [1] : http://ghc.haskell.org/trac/ghc/wiki/Roles
 [2] : http://www.cis.upenn.edu/~eir/papers/2013/roles/roles-slides.pdf
 
 I am writing because it's unclear what the *default* role should be --
 that is, should GND be allowed by default? Examples follow, but the
 critical issue is this:
 
 * If we allow GND by default anywhere it is type-safe, datatypes (even
 those that don't export constructors) will not be abstract by default.
 Library writers would have to use a role annotation everywhere they wish
 to declare a datatype they do not want users to be able to inspect.
 (Roles still keep type-*un*safe GND from happening.)
 
 * If we disallow GND by default, then perhaps lots of current uses of
 GND will break. Library writers will have to explicitly declare when
 they wish to permit GND involving a datatype.
 
 Which do we think is better?
 
 Examples: The chief example demonstrating the problem is (a hypothetical
 implementation of) Set:
 
 module Set (Set) where   -- note: no constructors exported!

 data Set a = MkSet [a]
 insert :: Ord a = a - Set a - Set a
 ...
 
 {-# LANGUAGE GeneralizedNewtypeDeriving, StandaloneDeriving #-}
 module Client where

 import Set

 newtype Age = MkAge Int deriving Eq

 instance Ord Age where
   (MkAge a) `compare` (MkAge b) = b `compare` a   -- flip operands,
 reversing the order

 class HasSet a where
   getSet :: Set a

 instance HasSet Int where
   getSet = insert 2 (insert 5 empty)

 deriving instance HasSet Age

 good :: Set Int
 good = getSet

 bad :: Set Age
 bad = getSet
 
 According to the way GND works, `good` and `bad` will have the same
 runtime representation. But, using Set operations on `bad` would indeed
 be bad -- because the Ord instance for Age is different than that for
 Int, Set operations will fail unexpectedly on `bad`. The problem is that
 Set should really be abstract, but we've been able to break this
 abstraction with GND. Note that there is no type error in these
 operations, just wrong behavior.
 
 So, if we default to *no* GND, then the deriving line above would have
 an error and this problem wouldn't happen. If we default to *allowing*
 GND, then the writer of Set would have to include
 type role Set nominal
 in the definition of the Set module to prevent the use of GND. (Why that
 peculiar annotation? See the linked further reading, above.)
 
 Although it doesn't figure in this example, a library writer who wishes
 to allow GND in the default-no scenario would need a similar annotation
 type role Foo representational
 to allow it.
 
 There are clearly reasons for and against either decision, but which is
 better? Let the users decide!
 
 Discussion time: 2 weeks.
 
 Thanks!
 Richard
 
 
 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
 

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


implicit params in instance contexts

2013-07-16 Thread Ganesh Sittampalam
Hi,

It seems that from GHC 7.4, the prohibition on implicit parameter
constraints in instance declarations has been relaxed. The program below
gives the error Illegal constraint ?fooRev::Bool in GHC 7.2.1 but
loads fine in GHC 7.4.2 and GHC 7.6.2.

I can't spot anything about this in the release notes, and the
documentation
(http://www.haskell.org/ghc/docs/7.6.3/html/users_guide/other-type-extensions.html#idp49069584)
still says You can't have an implicit parameter in the context of a
class or instance declaration.

So I wonder if this happened by accident, perhaps as part of the
ConstraintKinds work or similar?

I've wanted this feature a few times so if it's going to stay I might
start using it. However it is a bit dangerous, so if it was added by
accident it might warrant some discussion before deciding to keep it.
For example as the value set2 below shows, it can be used to violate
datatype invariants.

Cheers,

Ganesh


{-# LANGUAGE ImplicitParams #-}
module Ord where

import Data.Set ( Set )
import qualified Data.Set as Set

newtype Foo = Foo Int
deriving (Eq, Show)

instance (?fooRev :: Bool) = Ord Foo where
Foo a `compare` Foo b =
if ?fooRev then b `compare` a else a `compare` b

set1 = let ?fooRev = False in Set.fromList [Foo 1, Foo 3]

set2 = let ?fooRev = True in Set.insert (Foo 2) set1
-- Ord set2
-- fromList [Foo 2,Foo 1,Foo 3]

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell-cafe] How does one create an input handle bound to a string instead of a file?

2013-02-28 Thread Ganesh Sittampalam
Hi,

On 27/02/2013 20:38, John D. Ramsdell wrote:
 How does one create a value of type System.IO.Handle for reading that
 takes its input from a string instead of a file?  I'm looking for the
 equivalent of java.io.StringReader in Java.  Thanks in advance.

http://hackage.haskell.org/package/bytestring-handle can make handles
that read and write to ByteStrings.

Cheers,

Ganesh



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


Re: [Haskell-cafe] How does one create an input handle bound to a string instead of a file?

2013-02-28 Thread Ganesh Sittampalam
Hi John,

Using bytestring-handle, you can get this with something like

stringHandle :: String - Handle
stringHandle s = readHandle False (Data.ByteString.Char8.pack s)

[note the complete disregard of encoding issues in the use of
Data.ByteString.Char8]

Cheers,

Ganesh

On 28/02/2013 13:32, John D. Ramsdell wrote:
 I think I wasn't clear about my question.  I want something that
 creates a value of type System.IO.Handle.  You see, I have a high
 performance S-expression parser that I'd like to use in GHCi reading
 strings while at the command loop.
 
 Here is more details on my module SExpr that exports the SExpr data
 type and the load function.  The desired function is called
 stringHandle.
 
 -- An S-expression
 data SExpr
 = S String -- A symbol
 | Q String -- A quoted string
 | N Int-- An integer
 | L [SExpr a]  -- A proper list
 
 -- Read one S-expression or return Nothing on EOF
 load :: Handle - IO (Maybe (SExpr Pos))
 
 In GHCi, I want to type something like:
 
 SExpr let h = stringHandle ()
 SExpr load h
 Just (L [])
 SExpr load h
 Nothing
 SExpr
 
 It seems to me right now that I have to implement a duplicate parser
 that implements Read.  At least S-expression parsing is easy.
 
 John
 
 On Thu, Feb 28, 2013 at 3:02 AM, Ganesh Sittampalam gan...@earth.li wrote:
 Hi,

 On 27/02/2013 20:38, John D. Ramsdell wrote:
 How does one create a value of type System.IO.Handle for reading that
 takes its input from a string instead of a file?  I'm looking for the
 equivalent of java.io.StringReader in Java.  Thanks in advance.

 http://hackage.haskell.org/package/bytestring-handle can make handles
 that read and write to ByteStrings.

 Cheers,

 Ganesh


 


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


Re: GHC 7.8 release?

2013-02-10 Thread Ganesh Sittampalam
On 10/02/2013 21:43, Ian Lynagh wrote:
 On Sun, Feb 10, 2013 at 09:30:23PM +, Simon Peyton-Jones wrote:
 |   You may ask what use is a GHC release that doesn't cause a wave of 
 updates?
 |  And hence that doesn't work with at least some libraries.  Well, it's a 
 very useful
 |  forcing function to get new features actually out and tested.
 |  
 |  But the way you test new features is to write programs that use them,
 |  and programs depend on libraries.

 That is of course ideal, but the ideal carries costs.  A half way house is a 
 release whose library support will be patchy.
 
 But that's not what happens. GHC 7.8 is released. Someone installs it in
 order to try to use TypeHoles when developing their program. But their
 program depends on text, so they send Bryan a mail saying that text
 doesn't build with 7.8. And so the wave of updates begins.

As the maintainer of a low-level package (HTTP), I certainly see this
kind of pressure starting even before a GHC release - e.g.
https://github.com/haskell/HTTP/issues/36

As one of the maintainers of a high-level tool (darcs) that aims to
always build against the current HP, I generate this kind of pressure
myself: once GHC is released, I expect it to be in the HP within 3-6
months, so I need to get started quickly. I can't even check darcs
itself until the dependencies work.

I don't think there are any easy answers :-/

Ganesh


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell-cafe] Heads up: planned removal of String instances from HTTP package

2013-01-30 Thread Ganesh Sittampalam
Unfortunately I lack the time for a wholesale cleanup. If others have
proposals and are willing to supply the patches that's a different matter!

On 30/01/2013 08:01, Alfredo Di Napoli wrote:
 Maybe (just my 2 cents!) since you are going to broke the API anyway, go
 for it
 and seize the occasion to really clean up :)
 Obviously I'm saying this from a non-http-user point of view, maybe if I had
 some code in production affected by this, my suggestion would have been
 different :P
 
 Regards,
 A.
 
 On 30 January 2013 07:00, Ganesh Sittampalam gan...@earth.li
 mailto:gan...@earth.li wrote:
 
 On 29/01/2013 22:46, Johan Tibell wrote:
  On Tue, Jan 29, 2013 at 2:15 PM, Ganesh Sittampalam
 gan...@earth.li mailto:gan...@earth.li wrote:
  tl;dr: I'm planning on removing the String instances from the HTTP
  package. This is likely to break code. Obviously it will involve
 a major
  version bump.
 
  I think it's the right thing to do. Providing a little upgrade guide
  should help things to go smoother.
 
 One obvious cheap-and-dirty migration is via a newtype wrapper for
 String that embeds the old broken behaviour (char8 encoding). Perhaps
 the package should provide that? (with appropriate warnings etc)
 
 Ganesh
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org mailto: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] Heads up: planned removal of String instances from HTTP package

2013-01-29 Thread Ganesh Sittampalam
Hi,

tl;dr: I'm planning on removing the String instances from the HTTP
package. This is likely to break code. Obviously it will involve a major
version bump.

The basic reason is that this instance is rather broken in itself. A
String ought to represent Unicode data, but the HTTP wire format is
bytes, and HTTP makes no attempt to handle encoding.

This was discussed on the libraries@ list a while back, but I'm happy to
discuss further if there's a general feeling that this is a bad thing to do:

http://www.haskell.org/pipermail/libraries/2012-September/018426.html

I will probably upload the new version in a week or two.

Cheers,

Ganesh

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


Re: [Haskell-cafe] Heads up: planned removal of String instances from HTTP package

2013-01-29 Thread Ganesh Sittampalam
On 29/01/2013 22:46, Johan Tibell wrote:
 On Tue, Jan 29, 2013 at 2:15 PM, Ganesh Sittampalam gan...@earth.li wrote:
 tl;dr: I'm planning on removing the String instances from the HTTP
 package. This is likely to break code. Obviously it will involve a major
 version bump.
 
 I think it's the right thing to do. Providing a little upgrade guide
 should help things to go smoother.

One obvious cheap-and-dirty migration is via a newtype wrapper for
String that embeds the old broken behaviour (char8 encoding). Perhaps
the package should provide that? (with appropriate warnings etc)

Ganesh

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


Re: Dynamic libraries by default and GHC 7.8

2012-11-28 Thread Ganesh Sittampalam
On 28/11/2012 13:13, Ian Lynagh wrote:

 My general feeling about Windows is that it's ok for the end result to
 be a little annoying, because Windows DLLs *are* annoying and it's
 nothing to do with GHC.

 In particular I think in practice most Windows developers will have
 admin rights and could live with the ghc installation and cabal install
 having to be done as elevated operations. Where they weren't done with
 admin rights, then ghc -o could warn the user that the DLLs need to be
 copied locally (or even copy them itself and tell the user it happened).
 
 Personally, I would prefer the C stub option to that.

I think that one would be ok too, but I somewhat prefer SxS simply
because of the long-term costs of being non-standard.

 More generally, if you can implement the half a plan you mentioned
 elsewhere in the thread for quickly building both static and dynamic
 ways, then the combination of the ABI and performance issues mean that
 I'm marginally in favour of keeping static linking as the default for
 executables on all platforms, but building the dynamic libraries for ghci.
 
 That would solve the installing libraries takes twice as long problem,
 but not the ghci can't load modules compiled with ghc -c problem.

Can't ghc -c also produce both static and dynamic objects? I guess only
one of the two could be called sourcefile.o

Cheers,

Ganesh


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell-cafe] How to determine correct dependency versions for a library?

2012-11-17 Thread Ganesh Sittampalam
On 09/11/2012 18:35, Clark Gaebel wrote:
 I think we just use dependencies different things. This is a problem
 inherent in cabal.
 
 When I (and others) specify a dependency, I'm saying My package will
 work with these packages. I promise.
 When you (and others) specify a dependency, you're saying If you use a
 version outside of these bounds, my package will break. I promise.
 
 They're similar, but subtly different. There are merits to both of these
 strategies, and it's unfortunate that this isn't specified in the PVP [1].

I always understood that the policy was the former, i.e. allowing a
version means you positively expect it to work. Otherwise, why does the
PVP insist on upper bounds? You can't in general know that the package
will break with a version that doesn't exist yet.

As this thread and others show, there is of course a substantial set of
people that would prefer the policy to be the latter.

Cheers,

Ganesh

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


Re: Installing binary tarball fails on Linux

2012-10-01 Thread Ganesh Sittampalam
On 01/10/2012 12:05, Simon Marlow wrote:

 This probably means that you have packages installed in your ~/.cabal
 from a 32-bit GHC and you're using a 64-bit one, or vice-versa.  To
 avoid this problem you can configure cabal to put built packages into a
 directory containing the platform name.

How does one do this? I ran into this problem a while ago and couldn't
figure it out:
http://stackoverflow.com/questions/12393750/how-can-i-configure-cabal-to-use-different-folders-for-32-bit-and-64-bit-package

Ganesh


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell-cafe] Destructive updates to plain ADTs

2012-09-09 Thread Ganesh Sittampalam
On 09/09/2012 11:03, Milan Straka wrote:

 I was hoping for some Addr# trick or something like that. If
 I understand the GHC runtime correctly, rewriting a pointer in an ADT
 should not break any garbage collecting and similar.

Don't you need to worry about having something in the old generation
suddenly pointing to something in a younger generation?

Ganesh

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


Re: 7.6.1 RC1 panic coVarsOfTcCo:Bind

2012-08-24 Thread Ganesh Sittampalam
Hi Simon,

Now I get the below.

I tarred up the project + dependencies and put it at
http://urchin.earth.li/~ganesh/temp/tcproblem.tar.bz (run build.sh), or
I'm happy to keep testing on my machine.

Cheers,

Ganesh


ghc.exe: panic! (the 'impossible' happened)
  (GHC version 7.6.0.20120822 for i386-unknown-mingw32):
ds_ev_term
cobox{v a6Aho} [lid] `cast`
(main:Darcs.Test.Patch.WithState.WithState{tc r1oms}
model{tv t4H} [tv]
(main:Darcs.Witnesses.Ordered.FL{tc
r1iNn} prim{tv t4D} [tv]
 main:Darcs.Witnesses.Ordered.:{tc
r1iNy} main:Darcs.Witnesses.Ordered.FL{tc r1iNn}

prim{tv t4D} [tv])
 ghc-prim:GHC.Types.~{(w) tc 31Q}
main:Darcs.Test.Patch.WithState.WithState{tc r1oms}
(Sym
cobox{v a6AgE} [lid])
   
main:Darcs.Witnesses.Ordered.FL{tc r1iNn}
  
prim{tv t4D} [tv]

main:Darcs.Witnesses.Ordered.:{tc r1iNy}
main:Darcs.Witnesses.Ordered.FL{tc r1iNn}


prim{tv t4D} [tv])
(let {EvBinds{cobox{v a6zY5} [lid]
= cobox{v a6Aho} [lid] `cast`
(main:Darcs.Test.Patch.WithState.WithState{tc r1oms}
  model{tv t4H} [tv]
 
(main:Darcs.Witnesses.Ordered.FL{tc r1iNn}
 prim{tv t4D} [tv]
  
main:Darcs.Witnesses.Ordered.:{tc r1iNy}
main:Darcs.Witnesses.Ordered.FL{tc r1iNn}

  
prim{tv t4D} [tv])
  
ghc-prim:GHC.Types.~{(w) tc 31Q}
main:Darcs.Test.Patch.WithState.WithState{tc r1oms}

 
(Sym


cobox{v a6AgE} [lid])

 
main:Darcs.Witnesses.Ordered.FL{tc r1iNn}


prim{tv t4D} [tv]

  
main:Darcs.Witnesses.Ordered.:{tc r1iNy}
main:Darcs.Witnesses.Ordered.FL{tc r1iNn}

  
prim{tv t4D} [tv])
  cobox{v a6zY6} [lid] = CO t{tv a6zY1} [tv]}}
 cobox{v a6zY5} [lid] xx{tv a6zY3} [sk] yy{tv a6zY4} [sk]
 - t{tv a6zY1} [tv])

Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug

On 22/08/2012 08:40, Simon Peyton-Jones wrote:
 Ah.  Hmm.  I see.

 Can you try this in TcEvidence

 -- We expect only coercion bindings
 go_bind :: EvBind - VarSet
 go_bind (EvBind _ (EvCoercion co)) = go co
 go_bind (EvBind _ (EvId v))= unitVarSet v
 go_bind other = pprPanic coVarsOfTcCo:Bind (ppr other)

 with this instead?

 -- We expect only coercion bindings, so use evTermCoercion 
 go_bind :: EvBind - VarSet
 go_bind (EvBind _ tm) = go (evTermCoercion tm)

 I think that'll fix it.

 Simon

 | -Original Message-
 | From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-
 | haskell-users-boun...@haskell.org] On Behalf Of Ganesh Sittampalam
 | Sent: 22 August 2012 06:32
 | To: glasgow-haskell-users@haskell.org
 | Subject: 7.6.1 RC1 panic coVarsOfTcCo:Bind
 | 
 | Hi,
 | 
 | I'm getting the panic below when building darcs 2.8 with GHC 7.6. It'll
 | take some effort to cut it down or give repro instructions for an
 | uncut-down version (I needed to hack a lot of underlying packages to be
 | able to even get as far as doing this build), so could someone confirm
 | that it's worth it before I do so? I can't spot anything already
 | reporting this in trac.
 | 
 | Cheers,
 | 
 | Ganesh
 | 
 | ghc.exe: panic! (the 'impossible' happened)
 |   (GHC version 7.6.0.20120810 for i386-unknown-mingw32):
 | coVarsOfTcCo:Bind
 | cobox{v a6Czs} [lid]
 |   = cobox{v a6CTr} [lid] `cast`
 | (main:Darcs.Test.Patch.WithState.WithState{tc r1LL8}
 | model{tv tC} [tv]
 | 
 | (main:Darcs.Witnesses.Ordered.FL{tc r1Dy1} prim{tv ty} [tv]
 | 
 | main:Darcs.Witnesses.Ordered.:{tc r1Dyc}
 | main:Darcs.Witnesses.Ordered.FL{tc

7.6.1 RC1 panic coVarsOfTcCo:Bind

2012-08-21 Thread Ganesh Sittampalam
Hi,

I'm getting the panic below when building darcs 2.8 with GHC 7.6. It'll
take some effort to cut it down or give repro instructions for an
uncut-down version (I needed to hack a lot of underlying packages to be
able to even get as far as doing this build), so could someone confirm
that it's worth it before I do so? I can't spot anything already
reporting this in trac.

Cheers,

Ganesh

ghc.exe: panic! (the 'impossible' happened)
  (GHC version 7.6.0.20120810 for i386-unknown-mingw32):
coVarsOfTcCo:Bind
cobox{v a6Czs} [lid]
  = cobox{v a6CTr} [lid] `cast`
(main:Darcs.Test.Patch.WithState.WithState{tc r1LL8}
model{tv tC} [tv]
   
(main:Darcs.Witnesses.Ordered.FL{tc r1Dy1} prim{tv ty} [tv]

main:Darcs.Witnesses.Ordered.:{tc r1Dyc}
main:Darcs.Witnesses.Ordered.FL{tc r1Dy1}


prim{tv ty} [tv])
 ghc-prim:GHC.Types.~{(w) tc 31Q}
main:Darcs.Test.Patch.WithState.WithState{tc r1LL8}
   
(Sym cobox{v a6CSH} [lid])
   
main:Darcs.Witnesses.Ordered.FL{tc r1Dy1}
  
prim{tv ty} [tv]

main:Darcs.Witnesses.Ordered.:{tc r1Dyc} main:Darcs.Witnesses.Order
ed.FL{tc r1Dy1}


prim{tv ty} [tv])

Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: build failures when hiding non-visible imports

2012-08-20 Thread Ganesh Sittampalam
On 17/08/2012 11:18, Simon Peyton-Jones wrote:
 | Would it be reasonable to change ghc's behavior to treat this 
 | (ie an 'import' statement that hides something that isn't exported) as a
 | warning instead of an error?
 
 Yes, that would be easy if it's what everyone wants. Any other opinions?

I don't feel strongly either way, but I'd just argue that if it happens
it should happen for 7.6.1 to get maximum benefit.

Otherwise packages will still need preprocessor hacks to hide
Prelude.catch in the meantime (or to use explicit imports from the
Prelude, which would be pretty annoying).

Cheers,

Ganesh

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell-cafe] haskell.org is so fragile

2012-07-12 Thread Ganesh Sittampalam
Hi,

On 12/07/2012 13:06, Takayuki Muranushi wrote:
 Today I have observed that hackage.haskell.org/ timeout twice (in the
 noon and in the evening.)
 
 What is the problem? Is it that haskell users have increased so that
 haskell.org is overloaded? That's very good news.
 I am eager to donate some money if it requires server reinforcement.

The issue is unfortunately more to do with sysadmin resources than
server hardware; there's noone with the time to actively manage the
server and make sure that it's running well. Any ideas for improving the
situation would be gratefully received.

Today there were some problems with some processes taking up a lot of
resources. One of the problems was the hackage search script, which has
been disabled for now.

Cheers,

Ganesh




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


Re: problem with FFI and libsane

2012-06-07 Thread Ganesh Sittampalam
On 07/06/2012 12:08, Simon Marlow wrote:

 I don't completely understand what is going wrong here, but it looks
 like an interaction between the RTS's use of a timer signal and the
 libsane library.  You can make it work by turning off GHC's timer with
 +RTS -V0.
[..]
 The signal has always been SIGVTALRM, as far as I can tell.  Which is
 confusing - if the signal had changed, I could understand that being the
 cause of the difference in behaviour.  Perhaps it is just that system
 calls are being interrupted by the signal more often than they were
 before, and libsane does not properly handle EINTR.  I looked at the
 strace output and can't see any use of a signal by libsane.

I see, thanks. I'll do some digging into libsane and see if I can work
out more details.

Cheers,

Ganesh

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


problem with FFI and libsane

2012-06-06 Thread Ganesh Sittampalam
Hi,

I'm having some trouble making Haskell bindings to libsane (a scanner
access library: http://www.sane-project.org/)

When I build the cut down sample of my code (below) with GHC 7.4.1 with
the non-threaded runtime, it hangs at runtime in the call to
c'sane_get_devices (after printing go). Pressing ^C causes it to
continue and print done before exiting.

If I compile with GHC 7.2.2 non-threaded, it doesn't hang, printing
first go then done after a few seconds. That pause is expected, as
it's also seen in the equivalent C version (also below).

If I switch to the threaded runtime, then things go wrong differently.
Most of the time there's a hang after go and after pressing ^C they
just exit immediately, without printing done. This doesn't change
between 7.2.2 and 7.4.1. Occasionally, things do work and I get go
then done.

All these symptoms seem to point to some kind of threading problem, and
I believe that libsane is using pthreads, although ldd doesn't report it
and strace only shows it loading the library.

The platform is Linux x86, and I've reproduced the behaviour on two
different machines (Debian and Ubuntu). I've also tried with GHC
7.4.1.20120508, the most recent i386 snapshot I could fine.

Is there anything obvious I'm doing wrong, or something I could try next?

Cheers,

Ganesh

Haskell code:

{-# LANGUAGE ForeignFunctionInterface #-}
import Foreign.Marshal.Alloc
import Foreign.Ptr
import System.IO
import Foreign.C.Types

foreign import ccall sane_init c'sane_init
  :: Ptr CInt - Callback - IO CUInt

type Callback = FunPtr (Ptr CChar - Ptr CChar - Ptr CChar - IO ())

foreign import ccall sane_exit c'sane_exit
  :: IO ()

-- the () in the ptr type is incorrect, but in
-- this cut-down example we never try to dereference it
foreign import ccall sane_get_devices c'sane_get_devices
  :: Ptr (Ptr (Ptr ())) - CInt - IO CUInt


main :: IO ()
main = do
   hSetBuffering stdout NoBuffering
   _ - c'sane_init nullPtr nullFunPtr
   putStrLn go
   ptr - malloc
   _ - c'sane_get_devices ptr 0
   putStrLn done
   c'sane_exit


C code:

#include sane/sane.h
#include stdlib.h

int main()
{
   sane_init(NULL, NULL);
   puts(go);
   const SANE_Device **ptr;
   sane_get_devices(ptr, 0);
   puts(done);
   sane_exit();
}

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell-cafe] Fwd: Now Accepting Applications for Mentoring Organizations for GSoC 2012

2012-03-01 Thread Ganesh Sittampalam
FYI, Edward Kmett has volunteered to do it again.

On 28/02/2012 16:23, Johan Tibell wrote:
 Hi all,
 
 Anyone interested in acting as an admin for haskell.org
 http://haskell.org this year? I'm afraid I won't have time. It's not
 that much work (filling in some information, sending out some emails,
 making sure things happen in time.)
 
 -- Forwarded message --
 From: *Carol Smith* car...@google.com mailto:car...@google.com
 Date: Mon, Feb 27, 2012 at 11:47 AM
 Subject: Now Accepting Applications for Mentoring Organizations for GSoC
 2012
 To: Google Summer of Code Announce
 google-summer-of-code-annou...@googlegroups.com
 mailto:google-summer-of-code-annou...@googlegroups.com
 
 
 Hi all,
 
 We're pleased to announce the applications for mentoring organizations
 for GoogleSummer of Code 2012 are now being accepted [1]. Please go
 Melange [2] to apply on behalf of your organization. Please note that
 the application period [3] closes on 9 March at 23:00 UTC. We will not
 accept any late applications for any reason.
 
 [1]
 - 
 http://google-opensource.blogspot.com/2012/02/mentoring-organization-applications-now.html
 [2] - http://www.google-melange.com
 [3] - http://www.google-melange.com/gsoc/events/google/gsoc2012
 
 Cheers,
 Carol
 
 --
 You received this message because you are subscribed to the Google
 Groups Google Summer of Code Announce group.
 To post to this group, send email to
 google-summer-of-code-annou...@googlegroups.com
 mailto:google-summer-of-code-annou...@googlegroups.com.
 To unsubscribe from this group, send email to
 google-summer-of-code-announce+unsubscr...@googlegroups.com
 mailto:google-summer-of-code-announce%2bunsubscr...@googlegroups.com.
 For more options, visit this group at
 http://groups.google.com/group/google-summer-of-code-announce?hl=en.
 
 
 
 
 ___
 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] Fwd: Now Accepting Applications for Mentoring Organizations for GSoC 2012

2012-03-01 Thread Ganesh Sittampalam
On 01/03/2012 21:37, Johan Tibell wrote:
 On Thu, Mar 1, 2012 at 12:54 PM, Ganesh Sittampalam gan...@earth.li
 mailto:gan...@earth.li wrote:
 
 FYI, Edward Kmett has volunteered to do it again.
 
 
 That's great since he's the most experienced GSoC admin we have. :)
 
 There's still room for a replacement for me. I had a few people show
 interest so far.

Maybe I'm confused about the roles, then. Were you co-admins previously,
or something else?

Ganesh


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


Re: [Haskell-cafe] Why were unfailable patterns removed and fail added to Monad?

2012-01-21 Thread Ganesh Sittampalam
On 20/01/2012 03:23, Edward Z. Yang wrote:
 Oh, I'm sorry! On a closer reading of your message, you're asking not
 only asking why 'fail' was added to Monad, but why unfailable patterns
 were removed.
 
 Well, from the message linked:
 
 In Haskell 1.4 g would not be in MonadZero because (a,b) is unfailable
 (it can't fail to match).  But the Haskell 1.4 story is unattractive 
 becuase
 a) we have to introduce the (new) concept of unfailable
 b) if you add an extra constructor to a single-constructor type
then pattern matches on the original constructor suddenly 
 become
failable
 
 (b) is a real killer: suppose that you want to add a new constructor and
 fix all of the places where you assumed there was only one constructor.
 The compiler needs to emit warnings in this case, and not silently transform
 these into failable patterns handled by MonadZero...

It's pretty ugly, but what about using a different 'do' to select the
MonadZero behaviour? failable-do Foo x - bar translates to mzero,
whereas do Foo x - bar translates to an error. That way programmer
intent is captured locally.

failable-do is a straw man name :-)

Ganesh

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


Re: Unit unboxed tuples

2011-12-23 Thread Ganesh Sittampalam
On 23/12/2011 13:46, Ian Lynagh wrote:
 On Fri, Dec 23, 2011 at 01:34:49PM +, Simon Peyton-Jones wrote:

 Arguments   Boxed  Unboxed
 3   ( , , )(# , , #)
 2   ( , )  (# , #)
 1
 0   () (# #)

 Simple, uniform.
 
 Uniform horizontally, but strange vertically!

It's worth mentioning that if you want to write code that's generic over
tuples in some way, the absence of a case for singletons is actually a
bit annoying - you end up adding something like a One constructor to
paper over the gap. But I can't think of any nice syntax for that case
either.

Cheers,

Ganesh

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell] Proposal to incorporate Haskell.org

2011-12-16 Thread Ganesh Sittampalam
Hi,

As mentioned in the committee's annual report
(http://haskellorg.wordpress.com/2011/10/26/first-year-report/), our
attempt to join SFC has stalled because they don't have the capacity to
accept new projects at the moment.

We therefore applied to join SPI (http://www.spi-inc.org/), and they
have now offered us associated project status
(http://www.spi-inc.org/projects/associated-project-howto/).

We intend to accept this offer, but are taking this final opportunity to
seek feedback from the community before doing so.

SPI is very like SFC in what it does and how it operates, so we don't
expect this to make any substantial differences to the FAQ quoted below.

Regards,

Ganesh
on behalf of the haskell.org committee

On 10/05/2011 23:44, Don Stewart wrote:
 Hello everyone.
 
 The haskell.org committee[1], in the interest of the long-term stability
 of the open source Haskell community infrastructure, has decided to
 incorporate haskell.org as a legal entity. This email outlines our
 recommendation, and seeks input from the community on this decision.
 
 The committee's proposal is that haskell.org incorporate as an entity
 under the Software Freedom Conservancy umbrella organization (the same group
 that Darcs joined recently):
 
 http://sfconservancy.org/
 
 If we proceed with this move, haskell.org will be a legal entity, and
 registered as a non-profit, allowing us to more directly accept
 (US tax-deductible) donations, and to invest in assets that benefit the
 Haskell open source community.
 
 We welcome your feedback on the proposal attached below.
 
 -- Don Stewart (on behalf of the Haskell.org committee)
 
 
 
 
 
 = A proposal for the incorporation of Haskell.org =
 
 In recent years, haskell.org has started to receive assets, e.g. money from
 Google Summer Of Code, donations for Hackathons, and a Sparc machine for use 
 in
 GHC development. We have also started spending this money: in particular, on
 hosting haskell.org itself. There is also interest in running fundraising
 drives for specific things such as Hackathon sponsorship and hosting fees.
 
 However, haskell.org doesn't currently exist as a legal entity, meaning that
 these assets have had to be held on our behalf by other entities, such as
 Galois and various universities. This leads to tricky situations, with no-one
 being sure who should decide how the haskell.org assets can be used.
 
 To solve these problems, we propose that haskell.org applies to become a 
 member
 project of the Software Freedom Conservancy (SFC)
 http://conservancy.softwarefreedom.org/. The SFC is a non-profit 
 organization
 that provides free financial and administrative services to open source
 projects. Additionally, it has 501(c)(3) status, meaning donations from the US
 are tax-deductible. The SFC would hold haskell.org's money and other assets,
 and would be able to accept donations on behalf of haskell.org.
 
 The haskell.org committee, as described here [2], will make decisions on
 spending assets and other decisions related to governing the non-profit.
 
 
 Before proceeding, we are inviting input from the community in the form
 of specific objections or queries regarding the plan.
 
 We've tried to answer some of the most likely questions:
 
 Q: Does this mean that my Haskell project must now be covered by a
  copyleft licence such as GPL?
 A: No, but Haskell projects using haskell.org resource should use an
 Open Source licence
  http://www.opensource.org/licenses/alphabetical.
 
 Q: Will it still be possible to use community.h.o to host
  non-open-source material, such as academic papers?
 A: An overall minority of such content, as is the current situation, is
 not a problem.
 
 Q: Will it still be possible to have job ads on the haskell.org mailing
 lists and website?
 A: Yes.
 
 Q: Will this affect our ability to host the Haskell Symposium
 http://www.haskell.org/haskell-symposium/  and Industrial Haskell
 Grouphttp://industry.haskell.org/  webpages within haskell.org?
 A: No.
 
 Q: What will be the relationship between haskell.org and other
 organizations such as the Haskell Symposium and Industrial Haskell
 Group?
 A: Those organisations will continue to exist as separate entities.
 
 Q: If an umbrella non-profit organisation The Haskell Foundation was
 created, would haskell.org be able to join it?
 A: Yes. It's likely that in such a scenario, the Haskell Foundation
 would become the owner of the haskell.org domain name, with the cost
 divided between the members. The entity that is part of the SFC would
 be renamed community.haskell.org in order to avoid confusion.
 
 [1]: http://www.haskell.org/haskellwiki/Haskell.org_committee
 [2]: http://www.haskell.org/haskellwiki/Haskell.org_committee#Operation
 
 ___
 Haskell mailing list
 hask...@haskell.org
 

Re: [Haskell] Proposal to incorporate Haskell.org

2011-12-16 Thread Ganesh Sittampalam
BTW as with the Don's original message about incorporating, I
distributed this widely to increase awareness, but please restrict any
feedback to haskell-cafe@ and committee@.

Sorry for the noise!

Ganesh

On 16/12/2011 09:08, Ganesh Sittampalam wrote:
 Hi,
 
 As mentioned in the committee's annual report
 (http://haskellorg.wordpress.com/2011/10/26/first-year-report/), our
 attempt to join SFC has stalled because they don't have the capacity to
 accept new projects at the moment.
 
 We therefore applied to join SPI (http://www.spi-inc.org/), and they
 have now offered us associated project status
 (http://www.spi-inc.org/projects/associated-project-howto/).
 
 We intend to accept this offer, but are taking this final opportunity to
 seek feedback from the community before doing so.
 
 SPI is very like SFC in what it does and how it operates, so we don't
 expect this to make any substantial differences to the FAQ quoted below.
 
 Regards,
 
 Ganesh
 on behalf of the haskell.org committee
 
 On 10/05/2011 23:44, Don Stewart wrote:
 Hello everyone.

 The haskell.org committee[1], in the interest of the long-term stability
 of the open source Haskell community infrastructure, has decided to
 incorporate haskell.org as a legal entity. This email outlines our
 recommendation, and seeks input from the community on this decision.

 The committee's proposal is that haskell.org incorporate as an entity
 under the Software Freedom Conservancy umbrella organization (the same group
 that Darcs joined recently):

 http://sfconservancy.org/

 If we proceed with this move, haskell.org will be a legal entity, and
 registered as a non-profit, allowing us to more directly accept
 (US tax-deductible) donations, and to invest in assets that benefit the
 Haskell open source community.

 We welcome your feedback on the proposal attached below.

 -- Don Stewart (on behalf of the Haskell.org committee)



 

 = A proposal for the incorporation of Haskell.org =

 In recent years, haskell.org has started to receive assets, e.g. money from
 Google Summer Of Code, donations for Hackathons, and a Sparc machine for use 
 in
 GHC development. We have also started spending this money: in particular, on
 hosting haskell.org itself. There is also interest in running fundraising
 drives for specific things such as Hackathon sponsorship and hosting fees.

 However, haskell.org doesn't currently exist as a legal entity, meaning that
 these assets have had to be held on our behalf by other entities, such as
 Galois and various universities. This leads to tricky situations, with no-one
 being sure who should decide how the haskell.org assets can be used.

 To solve these problems, we propose that haskell.org applies to become a 
 member
 project of the Software Freedom Conservancy (SFC)
 http://conservancy.softwarefreedom.org/. The SFC is a non-profit 
 organization
 that provides free financial and administrative services to open source
 projects. Additionally, it has 501(c)(3) status, meaning donations from the 
 US
 are tax-deductible. The SFC would hold haskell.org's money and other assets,
 and would be able to accept donations on behalf of haskell.org.

 The haskell.org committee, as described here [2], will make decisions on
 spending assets and other decisions related to governing the non-profit.


 Before proceeding, we are inviting input from the community in the form
 of specific objections or queries regarding the plan.

 We've tried to answer some of the most likely questions:

 Q: Does this mean that my Haskell project must now be covered by a
  copyleft licence such as GPL?
 A: No, but Haskell projects using haskell.org resource should use an
 Open Source licence
  http://www.opensource.org/licenses/alphabetical.

 Q: Will it still be possible to use community.h.o to host
  non-open-source material, such as academic papers?
 A: An overall minority of such content, as is the current situation, is
 not a problem.

 Q: Will it still be possible to have job ads on the haskell.org mailing
 lists and website?
 A: Yes.

 Q: Will this affect our ability to host the Haskell Symposium
 http://www.haskell.org/haskell-symposium/  and Industrial Haskell
 Grouphttp://industry.haskell.org/  webpages within haskell.org?
 A: No.

 Q: What will be the relationship between haskell.org and other
 organizations such as the Haskell Symposium and Industrial Haskell
 Group?
 A: Those organisations will continue to exist as separate entities.

 Q: If an umbrella non-profit organisation The Haskell Foundation was
 created, would haskell.org be able to join it?
 A: Yes. It's likely that in such a scenario, the Haskell Foundation
 would become the owner of the haskell.org domain name, with the cost
 divided between the members. The entity that is part of the SFC would
 be renamed community.haskell.org in order to avoid

Re: [Haskell] Proposal to incorporate Haskell.org

2011-12-16 Thread Ganesh Sittampalam
Hi,

As mentioned in the committee's annual report
(http://haskellorg.wordpress.com/2011/10/26/first-year-report/), our
attempt to join SFC has stalled because they don't have the capacity to
accept new projects at the moment.

We therefore applied to join SPI (http://www.spi-inc.org/), and they
have now offered us associated project status
(http://www.spi-inc.org/projects/associated-project-howto/).

We intend to accept this offer, but are taking this final opportunity to
seek feedback from the community before doing so.

SPI is very like SFC in what it does and how it operates, so we don't
expect this to make any substantial differences to the FAQ quoted below.

Regards,

Ganesh
on behalf of the haskell.org committee

On 10/05/2011 23:44, Don Stewart wrote:
 Hello everyone.
 
 The haskell.org committee[1], in the interest of the long-term stability
 of the open source Haskell community infrastructure, has decided to
 incorporate haskell.org as a legal entity. This email outlines our
 recommendation, and seeks input from the community on this decision.
 
 The committee's proposal is that haskell.org incorporate as an entity
 under the Software Freedom Conservancy umbrella organization (the same group
 that Darcs joined recently):
 
 http://sfconservancy.org/
 
 If we proceed with this move, haskell.org will be a legal entity, and
 registered as a non-profit, allowing us to more directly accept
 (US tax-deductible) donations, and to invest in assets that benefit the
 Haskell open source community.
 
 We welcome your feedback on the proposal attached below.
 
 -- Don Stewart (on behalf of the Haskell.org committee)
 
 
 
 
 
 = A proposal for the incorporation of Haskell.org =
 
 In recent years, haskell.org has started to receive assets, e.g. money from
 Google Summer Of Code, donations for Hackathons, and a Sparc machine for use 
 in
 GHC development. We have also started spending this money: in particular, on
 hosting haskell.org itself. There is also interest in running fundraising
 drives for specific things such as Hackathon sponsorship and hosting fees.
 
 However, haskell.org doesn't currently exist as a legal entity, meaning that
 these assets have had to be held on our behalf by other entities, such as
 Galois and various universities. This leads to tricky situations, with no-one
 being sure who should decide how the haskell.org assets can be used.
 
 To solve these problems, we propose that haskell.org applies to become a 
 member
 project of the Software Freedom Conservancy (SFC)
 http://conservancy.softwarefreedom.org/. The SFC is a non-profit 
 organization
 that provides free financial and administrative services to open source
 projects. Additionally, it has 501(c)(3) status, meaning donations from the US
 are tax-deductible. The SFC would hold haskell.org's money and other assets,
 and would be able to accept donations on behalf of haskell.org.
 
 The haskell.org committee, as described here [2], will make decisions on
 spending assets and other decisions related to governing the non-profit.
 
 
 Before proceeding, we are inviting input from the community in the form
 of specific objections or queries regarding the plan.
 
 We've tried to answer some of the most likely questions:
 
 Q: Does this mean that my Haskell project must now be covered by a
  copyleft licence such as GPL?
 A: No, but Haskell projects using haskell.org resource should use an
 Open Source licence
  http://www.opensource.org/licenses/alphabetical.
 
 Q: Will it still be possible to use community.h.o to host
  non-open-source material, such as academic papers?
 A: An overall minority of such content, as is the current situation, is
 not a problem.
 
 Q: Will it still be possible to have job ads on the haskell.org mailing
 lists and website?
 A: Yes.
 
 Q: Will this affect our ability to host the Haskell Symposium
 http://www.haskell.org/haskell-symposium/  and Industrial Haskell
 Grouphttp://industry.haskell.org/  webpages within haskell.org?
 A: No.
 
 Q: What will be the relationship between haskell.org and other
 organizations such as the Haskell Symposium and Industrial Haskell
 Group?
 A: Those organisations will continue to exist as separate entities.
 
 Q: If an umbrella non-profit organisation The Haskell Foundation was
 created, would haskell.org be able to join it?
 A: Yes. It's likely that in such a scenario, the Haskell Foundation
 would become the owner of the haskell.org domain name, with the cost
 divided between the members. The entity that is part of the SFC would
 be renamed community.haskell.org in order to avoid confusion.
 
 [1]: http://www.haskell.org/haskellwiki/Haskell.org_committee
 [2]: http://www.haskell.org/haskellwiki/Haskell.org_committee#Operation
 
 ___
 Haskell mailing list
 Haskell@haskell.org
 

Re: [Haskell] Proposal to incorporate Haskell.org

2011-12-16 Thread Ganesh Sittampalam
BTW as with the Don's original message about incorporating, I
distributed this widely to increase awareness, but please restrict any
feedback to haskell-cafe@ and committee@.

Sorry for the noise!

Ganesh

On 16/12/2011 09:08, Ganesh Sittampalam wrote:
 Hi,
 
 As mentioned in the committee's annual report
 (http://haskellorg.wordpress.com/2011/10/26/first-year-report/), our
 attempt to join SFC has stalled because they don't have the capacity to
 accept new projects at the moment.
 
 We therefore applied to join SPI (http://www.spi-inc.org/), and they
 have now offered us associated project status
 (http://www.spi-inc.org/projects/associated-project-howto/).
 
 We intend to accept this offer, but are taking this final opportunity to
 seek feedback from the community before doing so.
 
 SPI is very like SFC in what it does and how it operates, so we don't
 expect this to make any substantial differences to the FAQ quoted below.
 
 Regards,
 
 Ganesh
 on behalf of the haskell.org committee
 
 On 10/05/2011 23:44, Don Stewart wrote:
 Hello everyone.

 The haskell.org committee[1], in the interest of the long-term stability
 of the open source Haskell community infrastructure, has decided to
 incorporate haskell.org as a legal entity. This email outlines our
 recommendation, and seeks input from the community on this decision.

 The committee's proposal is that haskell.org incorporate as an entity
 under the Software Freedom Conservancy umbrella organization (the same group
 that Darcs joined recently):

 http://sfconservancy.org/

 If we proceed with this move, haskell.org will be a legal entity, and
 registered as a non-profit, allowing us to more directly accept
 (US tax-deductible) donations, and to invest in assets that benefit the
 Haskell open source community.

 We welcome your feedback on the proposal attached below.

 -- Don Stewart (on behalf of the Haskell.org committee)



 

 = A proposal for the incorporation of Haskell.org =

 In recent years, haskell.org has started to receive assets, e.g. money from
 Google Summer Of Code, donations for Hackathons, and a Sparc machine for use 
 in
 GHC development. We have also started spending this money: in particular, on
 hosting haskell.org itself. There is also interest in running fundraising
 drives for specific things such as Hackathon sponsorship and hosting fees.

 However, haskell.org doesn't currently exist as a legal entity, meaning that
 these assets have had to be held on our behalf by other entities, such as
 Galois and various universities. This leads to tricky situations, with no-one
 being sure who should decide how the haskell.org assets can be used.

 To solve these problems, we propose that haskell.org applies to become a 
 member
 project of the Software Freedom Conservancy (SFC)
 http://conservancy.softwarefreedom.org/. The SFC is a non-profit 
 organization
 that provides free financial and administrative services to open source
 projects. Additionally, it has 501(c)(3) status, meaning donations from the 
 US
 are tax-deductible. The SFC would hold haskell.org's money and other assets,
 and would be able to accept donations on behalf of haskell.org.

 The haskell.org committee, as described here [2], will make decisions on
 spending assets and other decisions related to governing the non-profit.


 Before proceeding, we are inviting input from the community in the form
 of specific objections or queries regarding the plan.

 We've tried to answer some of the most likely questions:

 Q: Does this mean that my Haskell project must now be covered by a
  copyleft licence such as GPL?
 A: No, but Haskell projects using haskell.org resource should use an
 Open Source licence
  http://www.opensource.org/licenses/alphabetical.

 Q: Will it still be possible to use community.h.o to host
  non-open-source material, such as academic papers?
 A: An overall minority of such content, as is the current situation, is
 not a problem.

 Q: Will it still be possible to have job ads on the haskell.org mailing
 lists and website?
 A: Yes.

 Q: Will this affect our ability to host the Haskell Symposium
 http://www.haskell.org/haskell-symposium/  and Industrial Haskell
 Grouphttp://industry.haskell.org/  webpages within haskell.org?
 A: No.

 Q: What will be the relationship between haskell.org and other
 organizations such as the Haskell Symposium and Industrial Haskell
 Group?
 A: Those organisations will continue to exist as separate entities.

 Q: If an umbrella non-profit organisation The Haskell Foundation was
 created, would haskell.org be able to join it?
 A: Yes. It's likely that in such a scenario, the Haskell Foundation
 would become the owner of the haskell.org domain name, with the cost
 divided between the members. The entity that is part of the SFC would
 be renamed community.haskell.org in order to avoid

Re: [Haskell-cafe] [Haskell] Proposal to incorporate Haskell.org

2011-12-16 Thread Ganesh Sittampalam
Hi,

As mentioned in the committee's annual report
(http://haskellorg.wordpress.com/2011/10/26/first-year-report/), our
attempt to join SFC has stalled because they don't have the capacity to
accept new projects at the moment.

We therefore applied to join SPI (http://www.spi-inc.org/), and they
have now offered us associated project status
(http://www.spi-inc.org/projects/associated-project-howto/).

We intend to accept this offer, but are taking this final opportunity to
seek feedback from the community before doing so.

SPI is very like SFC in what it does and how it operates, so we don't
expect this to make any substantial differences to the FAQ quoted below.

Regards,

Ganesh
on behalf of the haskell.org committee

On 10/05/2011 23:44, Don Stewart wrote:
 Hello everyone.
 
 The haskell.org committee[1], in the interest of the long-term stability
 of the open source Haskell community infrastructure, has decided to
 incorporate haskell.org as a legal entity. This email outlines our
 recommendation, and seeks input from the community on this decision.
 
 The committee's proposal is that haskell.org incorporate as an entity
 under the Software Freedom Conservancy umbrella organization (the same group
 that Darcs joined recently):
 
 http://sfconservancy.org/
 
 If we proceed with this move, haskell.org will be a legal entity, and
 registered as a non-profit, allowing us to more directly accept
 (US tax-deductible) donations, and to invest in assets that benefit the
 Haskell open source community.
 
 We welcome your feedback on the proposal attached below.
 
 -- Don Stewart (on behalf of the Haskell.org committee)
 
 
 
 
 
 = A proposal for the incorporation of Haskell.org =
 
 In recent years, haskell.org has started to receive assets, e.g. money from
 Google Summer Of Code, donations for Hackathons, and a Sparc machine for use 
 in
 GHC development. We have also started spending this money: in particular, on
 hosting haskell.org itself. There is also interest in running fundraising
 drives for specific things such as Hackathon sponsorship and hosting fees.
 
 However, haskell.org doesn't currently exist as a legal entity, meaning that
 these assets have had to be held on our behalf by other entities, such as
 Galois and various universities. This leads to tricky situations, with no-one
 being sure who should decide how the haskell.org assets can be used.
 
 To solve these problems, we propose that haskell.org applies to become a 
 member
 project of the Software Freedom Conservancy (SFC)
 http://conservancy.softwarefreedom.org/. The SFC is a non-profit 
 organization
 that provides free financial and administrative services to open source
 projects. Additionally, it has 501(c)(3) status, meaning donations from the US
 are tax-deductible. The SFC would hold haskell.org's money and other assets,
 and would be able to accept donations on behalf of haskell.org.
 
 The haskell.org committee, as described here [2], will make decisions on
 spending assets and other decisions related to governing the non-profit.
 
 
 Before proceeding, we are inviting input from the community in the form
 of specific objections or queries regarding the plan.
 
 We've tried to answer some of the most likely questions:
 
 Q: Does this mean that my Haskell project must now be covered by a
  copyleft licence such as GPL?
 A: No, but Haskell projects using haskell.org resource should use an
 Open Source licence
  http://www.opensource.org/licenses/alphabetical.
 
 Q: Will it still be possible to use community.h.o to host
  non-open-source material, such as academic papers?
 A: An overall minority of such content, as is the current situation, is
 not a problem.
 
 Q: Will it still be possible to have job ads on the haskell.org mailing
 lists and website?
 A: Yes.
 
 Q: Will this affect our ability to host the Haskell Symposium
 http://www.haskell.org/haskell-symposium/  and Industrial Haskell
 Grouphttp://industry.haskell.org/  webpages within haskell.org?
 A: No.
 
 Q: What will be the relationship between haskell.org and other
 organizations such as the Haskell Symposium and Industrial Haskell
 Group?
 A: Those organisations will continue to exist as separate entities.
 
 Q: If an umbrella non-profit organisation The Haskell Foundation was
 created, would haskell.org be able to join it?
 A: Yes. It's likely that in such a scenario, the Haskell Foundation
 would become the owner of the haskell.org domain name, with the cost
 divided between the members. The entity that is part of the SFC would
 be renamed community.haskell.org in order to avoid confusion.
 
 [1]: http://www.haskell.org/haskellwiki/Haskell.org_committee
 [2]: http://www.haskell.org/haskellwiki/Haskell.org_committee#Operation
 
 ___
 Haskell mailing list
 hask...@haskell.org
 

Re: [Haskell-cafe] [Haskell] Proposal to incorporate Haskell.org

2011-12-16 Thread Ganesh Sittampalam
BTW as with the Don's original message about incorporating, I
distributed this widely to increase awareness, but please restrict any
feedback to haskell-cafe@ and committee@.

Sorry for the noise!

Ganesh

On 16/12/2011 09:08, Ganesh Sittampalam wrote:
 Hi,
 
 As mentioned in the committee's annual report
 (http://haskellorg.wordpress.com/2011/10/26/first-year-report/), our
 attempt to join SFC has stalled because they don't have the capacity to
 accept new projects at the moment.
 
 We therefore applied to join SPI (http://www.spi-inc.org/), and they
 have now offered us associated project status
 (http://www.spi-inc.org/projects/associated-project-howto/).
 
 We intend to accept this offer, but are taking this final opportunity to
 seek feedback from the community before doing so.
 
 SPI is very like SFC in what it does and how it operates, so we don't
 expect this to make any substantial differences to the FAQ quoted below.
 
 Regards,
 
 Ganesh
 on behalf of the haskell.org committee
 
 On 10/05/2011 23:44, Don Stewart wrote:
 Hello everyone.

 The haskell.org committee[1], in the interest of the long-term stability
 of the open source Haskell community infrastructure, has decided to
 incorporate haskell.org as a legal entity. This email outlines our
 recommendation, and seeks input from the community on this decision.

 The committee's proposal is that haskell.org incorporate as an entity
 under the Software Freedom Conservancy umbrella organization (the same group
 that Darcs joined recently):

 http://sfconservancy.org/

 If we proceed with this move, haskell.org will be a legal entity, and
 registered as a non-profit, allowing us to more directly accept
 (US tax-deductible) donations, and to invest in assets that benefit the
 Haskell open source community.

 We welcome your feedback on the proposal attached below.

 -- Don Stewart (on behalf of the Haskell.org committee)



 

 = A proposal for the incorporation of Haskell.org =

 In recent years, haskell.org has started to receive assets, e.g. money from
 Google Summer Of Code, donations for Hackathons, and a Sparc machine for use 
 in
 GHC development. We have also started spending this money: in particular, on
 hosting haskell.org itself. There is also interest in running fundraising
 drives for specific things such as Hackathon sponsorship and hosting fees.

 However, haskell.org doesn't currently exist as a legal entity, meaning that
 these assets have had to be held on our behalf by other entities, such as
 Galois and various universities. This leads to tricky situations, with no-one
 being sure who should decide how the haskell.org assets can be used.

 To solve these problems, we propose that haskell.org applies to become a 
 member
 project of the Software Freedom Conservancy (SFC)
 http://conservancy.softwarefreedom.org/. The SFC is a non-profit 
 organization
 that provides free financial and administrative services to open source
 projects. Additionally, it has 501(c)(3) status, meaning donations from the 
 US
 are tax-deductible. The SFC would hold haskell.org's money and other assets,
 and would be able to accept donations on behalf of haskell.org.

 The haskell.org committee, as described here [2], will make decisions on
 spending assets and other decisions related to governing the non-profit.


 Before proceeding, we are inviting input from the community in the form
 of specific objections or queries regarding the plan.

 We've tried to answer some of the most likely questions:

 Q: Does this mean that my Haskell project must now be covered by a
  copyleft licence such as GPL?
 A: No, but Haskell projects using haskell.org resource should use an
 Open Source licence
  http://www.opensource.org/licenses/alphabetical.

 Q: Will it still be possible to use community.h.o to host
  non-open-source material, such as academic papers?
 A: An overall minority of such content, as is the current situation, is
 not a problem.

 Q: Will it still be possible to have job ads on the haskell.org mailing
 lists and website?
 A: Yes.

 Q: Will this affect our ability to host the Haskell Symposium
 http://www.haskell.org/haskell-symposium/  and Industrial Haskell
 Grouphttp://industry.haskell.org/  webpages within haskell.org?
 A: No.

 Q: What will be the relationship between haskell.org and other
 organizations such as the Haskell Symposium and Industrial Haskell
 Group?
 A: Those organisations will continue to exist as separate entities.

 Q: If an umbrella non-profit organisation The Haskell Foundation was
 created, would haskell.org be able to join it?
 A: Yes. It's likely that in such a scenario, the Haskell Foundation
 would become the owner of the haskell.org domain name, with the cost
 divided between the members. The entity that is part of the SFC would
 be renamed community.haskell.org in order to avoid

Re: [Haskell-cafe] [Haskell] Proposal to incorporate Haskell.org

2011-12-16 Thread Ganesh Sittampalam
On 16/12/2011 10:59, Giovanni Tirloni wrote:
 On Fri, Dec 16, 2011 at 7:08 AM, Ganesh Sittampalam gan...@earth.li
 mailto:gan...@earth.li wrote:
 
  Q: If an umbrella non-profit organisation The Haskell Foundation was
  created, would haskell.org http://haskell.org be able to
 join it?
  A: Yes. It's likely that in such a scenario, the Haskell Foundation
  would become the owner of the haskell.org http://haskell.org
 domain name, with the cost
  divided between the members. The entity that is part of the
 SFC would
  be renamed community.haskell.org
 http://community.haskell.org in order to avoid confusion.
 
 
 Would it be a too ambitious goal to create the Haskell Foundation at
 this moment?

It would be a lot of administrative effort - managing accounts, tax
filings, etc. While it would give us more control, I don't think the
benefits would be very significant.

So in my view for now it's best not to go it alone.

Cheers,

Ganesh

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


Re: [Haskell-cafe] [Haskell] Proposal to incorporate Haskell.org

2011-12-16 Thread Ganesh Sittampalam
On 16/12/2011 13:21, Thomas Schilling wrote:
 On 16 December 2011 11:10, Ganesh Sittampalam gan...@earth.li wrote:
 On 16/12/2011 10:59, Giovanni Tirloni wrote:

 Would it be a too ambitious goal to create the Haskell Foundation at
 this moment?

 It would be a lot of administrative effort - managing accounts, tax
 filings, etc. While it would give us more control, I don't think the
 benefits would be very significant.

 So in my view for now it's best not to go it alone.
 
 I agree.  If at some point we feel that having a Haskell Foundation
 would be desirable (despite the additional overheads) there shouldn't
 be anything stopping us from doing so.  Are there any drawbacks in
 joining such an organisation?  How do they finance their overheads?
 Would a donation to haskell.org include a fee to SPI?  I couldn't find
 any information on their website.

Yes - 5% goes to SPI to cover their overheads. It's detailed in
http://www.spi-inc.org/projects/associated-project-howto/ but not on
their donations page at http://www.spi-inc.org/donations/.

5% seems reasonable to me and in line with what similar donation
aggregators charge, for example the Charities Aid Foundation in the UK
charges 4%:
https://www.cafonline.org/my-personal-giving/plan-your-giving/individual-charity-account.aspx

In effect we've been getting the admin for free from Galois up till now,
but it's been getting too troublesome for them.

Cheers,

Ganesh

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


[Haskell] list problem on projects.haskell.org

2011-11-27 Thread Ganesh Sittampalam
Hi,

There was a problem with the mailman daemon on projects.haskell.org
which meant that mail wasn't delivered from around Nov 11th till
yesterday (Nov 26th). It looks like the mail was correctly queued up
during that period and was all delivered when the daemon was restarted
yesterday.

Apologies for any inconvenience.

Cheers,

Ganesh

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


[Haskell] haskell.org 2011-12 committee

2011-11-23 Thread Ganesh Sittampalam
Hi,

The haskell.org committee for 2011-12 has been formed:

Edward Z. Yang [term ends 2013]
Ganesh Sittampalam [chair until May 2012, term ends 2012]
Vo Minh Thu [term ends 2013]
Mark Lentczner [term ends 2013]
Brent Yorgey [term ends 2014]
Jason Dagit [term ends 2014]
Edward Kmett [term ends 2014]

As well as two members (Ian Lynagh and Malcolm Wallace) from the 2010-11
committee retiring at the end of their terms, two other members (Johan
Tibell and Don Stewart) chose to resign as they didn’t have as much time
as they’d have liked to commit and we received enough self-nominations
to replace them.

This does mean a bit more than expected turnover in the committee
membership, but we felt it best to have a committee that can be suitably
responsive in the future. We’d like to thank all the departing members
for their service to the committee as it got started.

We’ve also tracked down the details of our accounts for the last year,
so we will post something about that as previously promised, as soon as
we have time to write the information up for presentation.

Our main priority for the coming months will be to finally settle the
incorporation issue.

Ganesh
on behalf of the haskell.org committee

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


encoding and paths, again

2011-11-13 Thread Ganesh Sittampalam
Hi,

I'm not entirely clear on what the overall situation will be once Simon
M's patch to add .ByteString versions to unix is added in GHC 7.4.1.

In particular the original problem darcs ran into was with
getDirectoryContents in the directory package. That in turn uses the
unix package on Posix systems and another code path based on Win32 on
Windows
(http://hackage.haskell.org/packages/archive/directory/1.1.0.1/doc/html/src/System-Directory.html#getDirectoryContents)

So a couple of questions:

(1) Does Win32 need similar additions? I can't spot any substantial
changes to it for Max's PEP383, but I'm not sure if any lower-level
library changes might have affected it.

(2) What's the recommended way of doing the equivalent of
getDirectoryContents for RawFilePath? Do we also need to add raw
versins to the directory package?

Cheers,

Ganesh


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: behaviour change in getDirectoryContents in GHC 7.2?

2011-11-02 Thread Ganesh Sittampalam
Hi Max,

On 01/11/2011 10:23, Max Bolingbroke wrote:

 This is my implementation of Python's PEP 383 [1] for Haskell.
 
 IMHO this behaviour is much closer to what users expect.For example,
 getDirectoryContents . = print shows Unicode filenames properly.
 As a result of this change we were able to close quite a few
 outstanding GHC bugs.

Many thanks for your reply and all the subsequent followups and bugfixing.

The workaround you propose seems a little complex and it might be a bit
problematic that 100% roundtripping can't be guaranteed even once your
fix is applied. Do you think it would be reasonable/feasible for darcs
to have its own version of getDirectoryContents that doesn't try to do
any translation in the first place? It might make sense to make a
separate package that others could use to.

BTW I was trying to find the patch where this changed but couldn't - was
it a consequence of
https://github.com/ghc/packages-base/commit/509f28cc93b980d30aca37008cbe66c677a0d6f6
?

Cheers,

Ganesh

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


behaviour change in getDirectoryContents in GHC 7.2?

2011-11-01 Thread Ganesh Sittampalam
Hi,

I'm just investigating what we can do about a problem with darcs'
handling of non-ASCII filenames on GHC 7.2.

The issue is apparently that as of GHC 7.2, getDirectoryContents now
tries to decode filenames in the current locale, rather than converting
a stream of bytes into characters: http://bugs.darcs.net/issue2095

I found an old thread on the subject:
http://www.haskell.org/pipermail/haskell-cafe/2009-June/062795.html and
some GHC tickets (e.g. http://hackage.haskell.org/trac/ghc/ticket/3300)

Can anyone point me at the rationale and details of the change and/or
suggest workarounds?

Cheers,

Ganesh





___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


[Haskell] haskell.org committee: first-year report

2011-10-26 Thread Ganesh Sittampalam
This report is also posted to
http://haskellorg.wordpress.com/2011/10/26/first-year-report/

The haskell.org committee is reaching the end of its first year of
operation, so it's time to look back and see what has been achieved.

*haskell.org incorporation*

The most important work for the year has been trying to get the
ownership of haskell.org resources -- principally some money from our
GSoC participation, and various machines -- on a sounder footing.

At the moment, Galois is kindly holding funds on behalf of haskell.org.
However, this causes them administrative difficulties and it would also
be better for haskell.org for them to be held separately in a vehicle
with tax-free status (at least in the US) that can also accept donations.

The main option we have been exploring is joining the Software Freedom
Conservancy (http://www.sfconservancy.org
http://www.sfconservancy.org/). After seeking the community's consent,
we have contacted them to begin the application process. Unfortunately
they are currently rather overworked and as they prioritise work for
existing projects over accepting new ones, we do not yet know when there
will be progress with this.

In the meantime we are also investigating joining an alternative,
Software in the Public Interest (http://www.spi-inc.org
http://www.spi-inc.org/). Discussions about this option are still ongoing.

The committee would like to thank Jason Dagit who has been helping us to
make progress on this issue over the last few months, with the support
of his employer Galois.

*Subdomain policy*

In response to various requests for subdomains of haskell.org, we have
formulated the following policy, now (belatedly!) documented
athttp://www.haskell.org/haskellwiki/Haskell.org_domain#Policy_on_adding_new_subdomains

/Subdomains should be used for *services *rather than *content*/.

Content should be normally be hosted at subpaths
of http://www.haskell.org http://www.haskell.org/

So for example a Haskell graphics related website should normally go
athttp://www.haskell.org/graphics, rather
than http://graphics.haskell.org http://graphics.haskell.org/.

In contrast, during the year, we did add revdeps.hackage.haskell.org for
a hackage reverse-dependency lookup service, and of course
hackage.haskell.org already exists.

Clearly the line between services and content, and indeed the precise
definitions of each, is something of a grey area, and we are certainly
happy to be flexible particularly if there are technical or other
reasons for doing things one way. Our overall goal is to minimise
unnecessary proliferation of subdomains and to try to keep the
haskell.org domain reasonably well organised, while still helping people
do useful things with it.

*Move of www.haskell.org http://www.haskell.org/ to a new dedicated host*

**For many years, www.haskell.org http://www.haskell.org/ was
generously hosted by Paul Hudak at Yale. This was becoming increasingly
expensive for him so in late 2010 we moved to a new dedicated host
(lambda.haskell.org). At the same time we put in place a policy that
lambda would host only meta community resources, thus limiting the
number of people who need to have accounts on it. For some time before
this new project content had been created on community.haskell.org
anyway, and this move gave us the opportunity to move legacy sites
such as gtk2hs over to community. In addition, community.haskell.org is
now also a VM running on the same machine.

The committee as a whole's involvement in this was only to approve the
change -- the sysadmin team did all the actual work.

*General*

The haskell.org infrastructure as a whole is still in a rather tenuous
state. While the extreme unreliability we saw for a while has improved
with the reorganisation , the  level of sysadmin resource/involvement is
still inadequate. The committee is open to ideas on how to improve the
situation.

Unfortunately we can't provide a full statement of haskell.org's
accounts with this report; we are doing our best to track down the
necessary information and will produce them as soon as possible. Better
control and visibility of our finances and assets is of course one of
the benefits we are seeking by affiliating with SFC or SPI.

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


[Haskell] haskell.org committee: Call for nominations

2011-10-18 Thread Ganesh Sittampalam
Dear Haskellers,

The first year of the haskell.org committee is drawing to a close and it
is therefore time to seek replacements for those members whose term is
expiring.

This year two members are retiring, Ian Lynagh and Malcolm Wallace. The
rest of the committee would like to thank them for their excellent
service, both from the time before the committee was formed when they
amongst the people who handled similar responsibilities on a more
informal basis, and over the last year.

To nominate yourself, please send an e-mail to committee at haskell.org
by 29 October 2011. The retiring members are eligible to re-nominate
themselves.

Please feel free to include any information about yourself that you
think will help us to make a decision.

Being a member of the committee does not require a significant amount of
time, but committee members should aim to be responsive during
discussions when the committee is called upon to make
a decision.

More details about the committee's roles and responsibilities are on

http://www.haskell.org/haskellwiki/Haskell.org_committee

If you have any questions about the process, please feel free to e-mail
us at committee at haskell.org or to contact one of us individually.

We will shortly also be producing a report and accounts covering the
first year of operation of the committee.

Regards,

Ganesh
On behalf of the haskell.org committee

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


Re: accessing compilation parameters from template haskell

2011-09-16 Thread Ganesh Sittampalam
Would making a template-haskell-ghc package make sense? Might be
overkill just for my requirement but there could be other things like
support for GHC-specific language extensions that might also logically
belong there.

On 16/09/2011 08:21, Simon Peyton-Jones wrote:
 The difficulty here is that the TH library, by design, doesn't depend on GHC. 
  So we can't have a TH function
   getFlags :: Q DynFlags
 or (as you suggest, more or less)
   runTc :: TcM a - Q a
 because to write those type signatures in Language.Haskell.TH.Syntax you'd 
 need to import GHC.
 
 There's no difficulty in *practice*!  Q more or less *is* TcM.
 
 Still I don't really know how to get around this in a beautiful way.
 
 Simon
 
 | -Original Message-
 | From: glasgow-haskell-users-boun...@haskell.org 
 [mailto:glasgow-haskell-users-
 | boun...@haskell.org] On Behalf Of Ganesh Sittampalam
 | Sent: 16 September 2011 06:42
 | To: GHC users
 | Subject: accessing compilation parameters from template haskell
 | 
 | Hi,
 | 
 | It would be useful to access the current compilation parameters or even
 | an entire RunGhc monad from inside a Template Haskell splice. Is there
 | any way to do this?
 | 
 | The reason I want to do this is I'm using the ghc API at runtime to
 | dynamically execute code, and I want both the dynamically loaded code
 | and static code to use a shared runtime module that defines some types
 | used for communication across the boundary. To guarantee the internal
 | representations etc are the same, I store the object file of the runtime
 | during compilation then load it dynamically at runtime - but to make
 | this work I need to know where the object file is (-odir and -hidir) and
 | I also need to know or be able to deduce the GHC DynFlags so I can
 | replicate them at runtime.
 | 
 | I could also achieve this goal by putting my runtime in a separate
 | package and installing it first, but that's less self-contained and
 | would be a pain during development.
 | 
 | Cheers,
 | 
 | Ganesh
 | 
 | ___
 | Glasgow-haskell-users mailing list
 | Glasgow-haskell-users@haskell.org
 | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
 
 


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


accessing compilation parameters from template haskell

2011-09-15 Thread Ganesh Sittampalam
Hi,

It would be useful to access the current compilation parameters or even
an entire RunGhc monad from inside a Template Haskell splice. Is there
any way to do this?

The reason I want to do this is I'm using the ghc API at runtime to
dynamically execute code, and I want both the dynamically loaded code
and static code to use a shared runtime module that defines some types
used for communication across the boundary. To guarantee the internal
representations etc are the same, I store the object file of the runtime
during compilation then load it dynamically at runtime - but to make
this work I need to know where the object file is (-odir and -hidir) and
I also need to know or be able to deduce the GHC DynFlags so I can
replicate them at runtime.

I could also achieve this goal by putting my runtime in a separate
package and installing it first, but that's less self-contained and
would be a pain during development.

Cheers,

Ganesh

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Records in Haskell

2011-09-15 Thread Ganesh Sittampalam
On 15/09/2011 15:43, Ian Lynagh wrote:
 On Thu, Sep 15, 2011 at 08:47:30AM +, Simon Peyton-Jones wrote:

 Provoked the (very constructive) Yesod blog post on Limitations of 
 Haskell, and the follow up discussion, I've started a wiki page to collect 
 whatever ideas we have about the name spacing issue for record fields.

 http://hackage.haskell.org/trac/ghc/wiki/Records

 As Simon M said on Reddit, this is something we'd like to fix; but we need a 
 consensus on how to fix it.
 
 Re TypeDirectedNameResolution, I would actually prefer it if it were
 less general. i.e. if you were to write
 x.f
 then f would be required to be a record selector.
 
 Then there's no need for the If there is exactly one f whose type
 matches that of x unpleasantness. Instead, the type of x must be
 inferred first (without any knowledge about the type of f), and then we
 know immediately which f is being referred to.

One benefit of TDNR is to replicate the discoverability of APIs that OO
programming has - if x :: Foo then typing x. in an IDE gives you a
list of things you can do with a Foo. (Obviously it's not a complete lis
for various reasons, but it does allow the author of Foo and others to
design discoverable APIs.)

So I think we'd be losing quite a bit to force f to be a record selector.

Ganesh

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


[Haskell] Announce: HTTP-4000.1.2

2011-08-10 Thread Ganesh Sittampalam
Hi,

I've just uploaded HTTP-4000.1.2, which just bumps the base dependency
to work with GHC 4.2.1.

I'm aware that there are a bunch of pending patches people have sent me,
including some from several months ago that I haven't even acknowledged
- sorry! I hope to integrate these at CamHac this weekend and upload a
slightly bigger update then.

Please note that I'm only the HTTP maintainer because noone else seems
to want the job, and it's thus not getting much attention. I'd be very
happy for someone else to take over or share the load.

Cheers,

Ganesh

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


Re: [Haskell-cafe] Exception for NaN

2011-05-12 Thread Ganesh Sittampalam
On 12/05/2011 19:41, Nick Bowler wrote:
 On 2011-05-12 21:14 +0400, Grigory Sarnitskiy wrote:

 I don't want NaN to propagate, it is merely stupid, it should be terminated.
 
 NaN propagation is not stupid.  Frequently, components of a computation
 that end up being NaN turn out to be irrelevant at a later point, in
 which case the NaNs can be discarded.

Unfortunately, if a NaN reaches a comparison operation, it can lead to
an end result that doesn't contain NaNs, but was still influenced by one.

Ganesh

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


Re: Proposal to incorporate Haskell.org

2011-05-11 Thread Ganesh Sittampalam
On 11/05/2011 10:33, Yitzchak Gale wrote:
 Don Stewart wrote:
 The haskell.org committee... has decided to
 incorporate haskell.org as a legal entity. This email outlines our
 recommendation, and seeks input from the community on this decision.
 
 Thanks, good news! And thanks for posting to multiple
 lists for maximum public notification to the community.
 
 Can the committee now designate a single list for further discussion
 please?

Sorry about the noise. I think haskell-cafe is the best choice for
further discussion.

Please, everyone send further followups to any message in this thread to
just haskell-c...@haskell.org and commit...@haskell.org, or just to
commit...@haskell.org if you want to respond privately.

Ganesh
(haskell.org committee member)

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell] Proposal to incorporate Haskell.org

2011-05-11 Thread Ganesh Sittampalam
On 11/05/2011 10:33, Yitzchak Gale wrote:
 Don Stewart wrote:
 The haskell.org committee... has decided to
 incorporate haskell.org as a legal entity. This email outlines our
 recommendation, and seeks input from the community on this decision.
 
 Thanks, good news! And thanks for posting to multiple
 lists for maximum public notification to the community.
 
 Can the committee now designate a single list for further discussion
 please?

Sorry about the noise. I think haskell-cafe is the best choice for
further discussion.

Please, everyone send further followups to any message in this thread to
just haskell-c...@haskell.org and commit...@haskell.org, or just to
commit...@haskell.org if you want to respond privately.

Ganesh
(haskell.org committee member)

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


Re: [Haskell-cafe] Proposal to incorporate Haskell.org

2011-05-11 Thread Ganesh Sittampalam
On 11/05/2011 06:08, Antoine Latter wrote:

 Which assets would move over to the SFC? The domain name? Any sort of
 hosting could then be leased by the SFC to whomever is doing this now.
 I'm a bit fuzzy here.

Everything but the domain name, so that the Haskell community as a whole
can retain the ability to do other things with it in future that aren't
subject to licensing constraints. Current cash and hardware would move over.

Ganesh
(haskell.org committee member)

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


Re: [Haskell-cafe] Proposal to incorporate Haskell.org

2011-05-11 Thread Ganesh Sittampalam
On 11/05/2011 10:33, Yitzchak Gale wrote:
 Don Stewart wrote:
 The haskell.org committee... has decided to
 incorporate haskell.org as a legal entity. This email outlines our
 recommendation, and seeks input from the community on this decision.
 
 Thanks, good news! And thanks for posting to multiple
 lists for maximum public notification to the community.
 
 Can the committee now designate a single list for further discussion
 please?

Sorry about the noise. I think haskell-cafe is the best choice for
further discussion.

Please, everyone send further followups to any message in this thread to
just haskell-cafe@haskell.org and commit...@haskell.org, or just to
commit...@haskell.org if you want to respond privately.

Ganesh
(haskell.org committee member)

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


Re: [Haskell-cafe] A small Darcs anomoly

2011-04-27 Thread Ganesh Sittampalam
On 26/04/2011 12:17, Malcolm Wallace wrote:
 
 On 25 Apr 2011, at 11:13, Andrew Coppin wrote:
 
 On 24/04/2011 06:33 PM, Jason Dagit wrote:

 This is because of a deliberate choice that was made by David Roundy.
 In darcs, you never have multiple branches within a single darcs
 repository directory tree.

 Yes, this seems clear. I'm just wondering whether or not it's the best 
 design choice.
 
 It seems to me to be a considerable insight.  Branches and repositories are 
 the same thing.  There is no need for two separate concepts.  The main reason 
 other VCSes have two concepts is because one of them is often more 
 efficiently implemented (internally) than the other.  But that's silly - how 
 much better to abstract over the mental clutter, and let the implementation 
 decide how its internals look!
 
 So in darcs, two repositories on the same machine share the same files (like 
 a branch), but if they are on different machines, they have separate copies 
 of the files.  The difference is a detail that you really don't need to know 
 or care about.
 
 It does mean that you duplicate information. You have [nearly] the same set 
 of patches stored twice,
 
 No, if on the same machine, the patches only appear once, it is just the 
 index that duplicates some information (I think).  In fact just as if it were 
 a branch in another VCS.

Unfortunately, I don't think this is quite true, because being able to
switch between multiple branches in the same working directory means you
can reuse build products when switching branches. Depending on how
radical the branch shift is, this can be a substantial win, and it's the
main reason that darcs might in future implement in-repo branching of
some form.

Ganesh

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


Re: weird behaviour of context resolution with FlexibleContexts and TypeFamilies

2011-02-26 Thread Ganesh Sittampalam

Hi Dimitrios,

Done: http://hackage.haskell.org/trac/ghc/ticket/4981

BTW although I said in my original email that this happened on GHC 6.12 
as well as GHC 7, it looks like that's not the case for the cutdown 
example. I'm fairly sure that it happened with my original code; let me 
know if it's important to know and I'll go back and check on that.


Cheers,

Ganesh

On 26/02/2011 02:01, Dimitrios Vytiniotis wrote:


Hi Ganesh, you are right Simon's answer is not correct.

The cause of your problem is I believe quite involved -- I think I 
know what's going on (Simon: it seems to be
an overlap problem indeed but between a different instance and given 
arising from a superclass when trying to
solve a 'silent parameter' wanted) but I can't build the compiler on 
my OS X tonight to verify my thoughts.


I will hopefully be able to say more over the weekend. Can you submit 
a bug report in the meanwhile?


Or I will do it tomorrow.

Thanks!
d-




*From:* glasgow-haskell-users-boun...@haskell.org 
[glasgow-haskell-users-boun...@haskell.org] on behalf of Ganesh 
Sittampalam [gan...@earth.li]

*Sent:* Friday, February 25, 2011 4:39 PM
*To:* Simon Peyton-Jones
*Cc:* glasgow-haskell-users@haskell.org; Sittampalam, Ganesh
*Subject:* Re: weird behaviour of context resolution with 
FlexibleContexts and TypeFamilies


Hi Simon,

You talk about the timing of application of the instance declaration
  instancePatchInspect (PrimOf p)) = Conflict p

but the constraint is actually defined in the class declaration, and I 
don't have any instance declarations for Conflict p itself.

classPatchInspect (PrimOf p)) = Conflict p

Does that make a difference to your answer, or do you mean that the 
constraint in the class declaration automatically gives rise to the 
same behaviour?


Ganesh

On 25/02/2011 09:06, Simon Peyton-Jones wrote:


You are doing something very delicate here, akin to overlapping 
instances.


You have an instance

instancePatchInspect (PrimOf p)) = Conflict p

and a function

clever :: (Conflict (OnPrim p), ..) = ...

So if a constraint (Conflict blah) arises in the RHS of clever, the 
instance declaration will immediately apply; and then the type check 
fails.  But if it just so happens to precisely match the provided 
constraint (Conflict (OnPrim p)), you want to use the provided 
constraint.  In effect the type signature and the instance overlap.


Arguably, GHC should refrain from applying the instance if there is 
any possibility of a “given” constraint matching.  Currently it’s a 
bit random; but it’s a very weird situation.


But first, is this really what you intend?

Simon

*From:*glasgow-haskell-users-boun...@haskell.org 
[mailto:glasgow-haskell-users-boun...@haskell.org] *On Behalf Of 
*Sittampalam, Ganesh

*Sent:* 24 February 2011 07:41
*To:* glasgow-haskell-users@haskell.org
*Subject:* weird behaviour of context resolution with 
FlexibleContexts and TypeFamilies


Hi,

If I build the code below with -DVER=2, I get a complaint about 
PatchInspect (PrimOf p) being missing from the context of 
cleverNamedResolve.


This doesn't happen with -DVER=1 or -DVER=3

I presume that type class resolution is operating slightly 
differently in the different cases, but it's quite confusing - in the 
original code joinPatches did something useful and I was trying to 
inline the known instance definition. I would have expected it to be 
consistent between all three cases, either requiring the context or not.


Is it a bug, or just one of the risks one takes by using 
FlexibleContexts?


I've tried this with GHC 6.12.3 and with 7.0.2RC2.

Cheers,

Ganesh

{-# LANGUAGE CPP, TypeFamilies, FlexibleContexts #-}
module Class ( cleverNamedResolve ) where

data FL p = FL p

class PatchInspect p where
instance PatchInspect p = PatchInspect (FL p) where

type family PrimOf p
type instance PrimOf (FL p) = PrimOf p

data WithName prim = WithName prim

instance PatchInspect prim = PatchInspect (WithName prim) where

class (PatchInspect (PrimOf p)) = Conflict p where
resolveConflicts :: p - PrimOf p

instance Conflict p = Conflict (FL p) where
resolveConflicts = undefined

type family OnPrim p

#if VER==1
class FromPrims p where

instance FromPrims (FL p) where

joinPatches :: FromPrims p = p - p
#else
#if VER==2
joinPatches :: FL p - FL p
#else
joinPatches :: p - p
#endif
#endif

joinPatches = id

cleverNamedResolve :: (Conflict (OnPrim p)
  ,PrimOf (OnPrim p) ~ WithName (PrimOf p))
   = FL (OnPrim p) - WithName (PrimOf p)
cleverNamedResolve = resolveConflicts . joinPatches




==
Please access the attached hyperlink for an important electronic 
communications disclaimer:

http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html

Re: weird behaviour of context resolution with FlexibleContexts and TypeFamilies

2011-02-25 Thread Ganesh Sittampalam

Hi Simon,

You talk about the timing of application of the instance declaration
  instancePatchInspect (PrimOf p)) = Conflict p

but the constraint is actually defined in the class declaration, and I 
don't have any instance declarations for Conflict p itself.

classPatchInspect (PrimOf p)) = Conflict p

Does that make a difference to your answer, or do you mean that the 
constraint in the class declaration automatically gives rise to the same 
behaviour?


Ganesh

On 25/02/2011 09:06, Simon Peyton-Jones wrote:


You are doing something very delicate here, akin to overlapping 
instances.


You have an instance

instancePatchInspect (PrimOf p)) = Conflict p

and a function

clever :: (Conflict (OnPrim p), ..) = ...

So if a constraint (Conflict blah) arises in the RHS of clever, the 
instance declaration will immediately apply; and then the type check 
fails.  But if it just so happens to precisely match the provided 
constraint (Conflict (OnPrim p)), you want to use the provided 
constraint.  In effect the type signature and the instance overlap.


Arguably, GHC should refrain from applying the instance if there is 
any possibility of a given constraint matching.  Currently it's a 
bit random; but it's a very weird situation.


But first, is this really what you intend?

Simon

*From:*glasgow-haskell-users-boun...@haskell.org 
[mailto:glasgow-haskell-users-boun...@haskell.org] *On Behalf Of 
*Sittampalam, Ganesh

*Sent:* 24 February 2011 07:41
*To:* glasgow-haskell-users@haskell.org
*Subject:* weird behaviour of context resolution with FlexibleContexts 
and TypeFamilies


Hi,

If I build the code below with -DVER=2, I get a complaint about 
PatchInspect (PrimOf p) being missing from the context of 
cleverNamedResolve.


This doesn't happen with -DVER=1 or -DVER=3

I presume that type class resolution is operating slightly differently 
in the different cases, but it's quite confusing - in the original 
code joinPatches did something useful and I was trying to inline the 
known instance definition. I would have expected it to be consistent 
between all three cases, either requiring the context or not.


Is it a bug, or just one of the risks one takes by using 
FlexibleContexts?


I've tried this with GHC 6.12.3 and with 7.0.2RC2.

Cheers,

Ganesh

{-# LANGUAGE CPP, TypeFamilies, FlexibleContexts #-}
module Class ( cleverNamedResolve ) where

data FL p = FL p

class PatchInspect p where
instance PatchInspect p = PatchInspect (FL p) where

type family PrimOf p
type instance PrimOf (FL p) = PrimOf p

data WithName prim = WithName prim

instance PatchInspect prim = PatchInspect (WithName prim) where

class (PatchInspect (PrimOf p)) = Conflict p where
resolveConflicts :: p - PrimOf p

instance Conflict p = Conflict (FL p) where
resolveConflicts = undefined

type family OnPrim p

#if VER==1
class FromPrims p where

instance FromPrims (FL p) where

joinPatches :: FromPrims p = p - p
#else
#if VER==2
joinPatches :: FL p - FL p
#else
joinPatches :: p - p
#endif
#endif

joinPatches = id

cleverNamedResolve :: (Conflict (OnPrim p)
  ,PrimOf (OnPrim p) ~ WithName (PrimOf p))
   = FL (OnPrim p) - WithName (PrimOf p)
cleverNamedResolve = resolveConflicts . joinPatches




==
Please access the attached hyperlink for an important electronic 
communications disclaimer:

http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html
==


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


[Haskell] ANNOUNCE: darcs 2.5.1

2011-02-10 Thread Ganesh Sittampalam

Hi,

The darcs team is pleased to announce the release of darcs 2.5.1, a minor 
upgrade for the 2.5 release. The main focus of this release is support for 
the GHC 7.0 series and the upcoming February 2011 Haskell Platform, but 
the release also includes a few bug fixes and minor usability 
improvements. A detailed changelog is below.


Installing
--
The easiest way to install darcs 2.5.1 from source is by first installing 
the Haskell Platform (http://www.haskell.org/platform). If you have 
installed the Haskell Platform or cabal-install, you can install this 
release by doing:


  $ cabal update
  $ cabal install darcs-2.5.1

Alternatively, you can download the tarball from
http://darcs.net/releases/darcs-2.5.1.tar.gz and build it by hand as
explained in the README file.

Versions of GHC from 6.10.x to 7.0.x are supported.

The 2.5 branch is also available as a darcs repository from 
http://darcs.net/releases/branch-2.5


Binaries

These will be posted to http://wiki.darcs.net/Binaries as they become 
available.



Reporting bugs
--
If you have an issue with darcs 2.5.1, you can report it via the web on 
http://bugs.darcs.net/ . You can also report bugs by email to bugs at 
darcs.net.



Changelog
-

 * Include original text in conflict marks

   Conflicts are now marked up as

   v v v v v v v
   original text before any conflicting patch
   =
   conflicting result A
   *
   conflicting result B
   
   ^ ^ ^ ^ ^ ^ ^

   The inclusion of the original text makes it much easier to understand
   what the changes on either side of the conflict were.

   This is only an incremental improvement to our conflict marking, which
   we understand is still hard to use. More substantial improvements are
   in the works.

 * Support GHC 7.0 and various recent library versions
   (http://bugs.darcs.net/issue2008, http://bugs.darcs.net/issue2019)

   This should mean that darcs 2.5.1 will work with the upcoming Feb 2011
   Haskell Platform release.

 * Restrict the GHC version in the cabal file

   This means that cabal builds will explicitly fail if an unsupported GHC
   version is encountered, which should cause less user confusion.

 * Update warning message about old-fashioned repositories

   It now points to a wiki page explaining our deprecation plan
   (http://wiki.darcs.net/OF)

 * Guard against non-repository paths during get
   (http://bugs.darcs.net/issue2035)

   Darcs normally checks for paths that point outside the repository when
   applying patches, but this check was missing in the case of get.

 * Darcs library API: make the program name configurable

   This makes it easier for external users of the library API to reuse
   Darcs' framework for handling commands.

 * darcs send now prints the remote repository address up front

   Previously it would first read the remote repository, which made it
   hard to see what was happening when accessing the remote repository
   hung.

 * Informational message about --set-default is now disabled by explicit
   use of --no-set-default
   (http://bugs.darcs.net/issue2003)

   This allows users to silence the message by placing 'pull
   no-set-default', 'push no-set-default' and 'send no-set-default'
   in ~/.darcs/defaults or _darcs/prefs/defaults.

 * Handle _darcs/format correctly on get
   (http://bugs.darcs.net/issue1978)

   This is mainly a forwards compatibility issue as no existing version
   of darcs would create format files that are affected by this bug.

 * Fix linking with libdarcs on Windows
   (http://bugs.darcs.net/issue2015)

   This was a simple problem with a missing object file.

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


Re: [darcs-users] How to develop on a (GHC) branch with darcs

2010-12-09 Thread Ganesh Sittampalam

On Thu, 9 Dec 2010, Simon Marlow wrote:


On 08/12/2010 17:39, Yitzchak Gale wrote:


Some of those are already in the works, and all except possibly
(5) are known to be within reach. So the answer is yes, this
problem is now on the verge of being solved in Darcs.


I think that might be a little overoptimistic.  The fundamental problem with 
darcs is that nobody understands the semantics.  Until there's a proper 
semantics that people can understand, I don't think the problems with merging 
and conflicts can really be fixed.  Even if the semantics can be nailed down, 
there are some difficult UI issues to solve.


We're not moving to v2 patches right now because we have enough experience 
with v1 to know how to avoid the bugs, but I'm less sure we could avoid the 
bugs in v2.  To the darcs folk: do you think this is unfounded paranoia?


Sadly, no.


On the other hand, I suppose GHC HQ can't afford to have
a revolt on their hands. So if the majority of people doing the
actual work on GHC want to change to git and are willing to put
in the effort to make the change, it will probably happen regardless.


Opinion on whether we should switch seems to be pretty evenly split at the 
moment (personally I'm agnostic).  Besides that, the main stumbling block is 
that the GHC tree consists of about 20 repos, with different maintainers, so 
making it so that a GHC developer only needs to use one VC tool could be 
tricky.


My feeling is that a bridge should be quite feasible and would offer those 
contributors who want it the opportunity to do their GHC development in 
git and only use darcs when submitting their final changes or when working 
in unbridged repos. I'm not too familiar with the structure of the GHC 
repo but I suspect that only a few of the subrepos are big or active 
enough that darcs is really painful.


Cheers,

Ganesh

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [darcs-users] How to develop on a (GHC) branch with darcs

2010-12-09 Thread Ganesh Sittampalam

On Wed, 8 Dec 2010, Stephen J. Turnbull wrote:


Ganesh Sittampalam writes:

 I think there are three things that can help with this problem:

 1) a darcs rebase command. This will give you a nice way to manage the
 workflow already discussed, and you won't have to squish everything
 through into a mega-patch. You'll still have to periodically abandon one
 branch for another though (but I think that's also the case with git
 rebase).

I'm not sure what you mean by abandon.


I mean the same as in the git world. The rebased patches have new 
identities, and if my ideas for tracking the relationship don't work out, 
they will have no relationship to the old patches.


[your very clear explanation of that snipped]


 I also have some hope, though this is more speculative, of offering
 a clean way of tracking the relationship between the old branch and
 the new branch so that any stray patches against the old branch can
 be cleanly rebased to the new branch later on.

As explained above, DAG-based VCSes like git can't do this cleanly
(that is one way of expressing the reason why rebase is severely
deprecated in some circles), and I don't think git will be able to do
so in the near future.  OTOH, if Darcs gets rebase but can't handle
this, I'd have to count that as a net minus.  Recombinant patching is
really what Darcs is all about IMO.


darcs rebase is essentially about giving up on the recombinant patching 
because that's not working out for whatever reason. It's primarily 
intended as an alternative to manually reapplying patches to new branches 
using diff-and-patch, which is something significant numbers of people 
have ended up having to do. People generally want/need to do this to avoid 
conflicts, because:


(a) darcs conflict handling can blow up, both because of exponential 
merges (primarily with v1 patches) and because of bugs


(b) the UI for dealing with conflicts isn't really that pleasant and in 
particular once you've resolved a conflict it's a little painful to see 
the overall effect of the conflict resolution together with the underlying 
patch



In practice, git rebase needs to be kept private to a single user, and
is impractical even if private, if the user has propagated the branch
to other local repositories.  Because git branching is so lightweight,
nobody really sees this as a big problem; throwaway branches are used
all the time as interim steps in many operations (eg, git stash).
Darcs branches, on the other hand, are much more heavyweight (modulo
the work you propose on colocated branches, but that's farther away
than rebase is).

IMHO YMMV.  But I strongly recommend you think carefully about this.
Analogies to git rebase are a trap here.  It's implemented differently
and used to solve different problems from the way rebase is proposed
for use in Darcs.


My understanding is that one of the main uses for git rebase is for 
cleaning up history prior to submission. In that regard I think there's 
a substantial overlap with what darcs rebase is intended for.


Thanks for the detailed comments.

Ganesh

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [darcs-users] How to develop on a (GHC) branch with darcs

2010-12-06 Thread Ganesh Sittampalam

On Mon, 6 Dec 2010, Simon Peyton-Jones wrote:


I too wish there was a good solution here.  I've taken to making dated repos, 
thus
http://darcs.haskell.org/ghc-new-co-17Nov10


When it becomes unusable, I make a brand new repo, with a new date 
starting from HEAD, pull all the old patches, unrecord them all, 
rerecord a mega-patch, and commit.


This is darcs's primary shortcoming.  It is well known, and the darcs 
folk are working on it.  But I don't think they expect to have a 
solution anytime soon. (Please correct me if I'm wrong.)


I think there are three things that can help with this problem:

1) a darcs rebase command. This will give you a nice way to manage the 
workflow already discussed, and you won't have to squish everything 
through into a mega-patch. You'll still have to periodically abandon one 
branch for another though (but I think that's also the case with git 
rebase). I also have some hope, though this is more speculative, of 
offering a clean way of tracking the relationship between the old branch 
and the new branch so that any stray patches against the old branch can be 
cleanly rebased to the new branch later on.


I'm actively working on rebase (with some gaps to refactor the darcs 
codebase to make working on it easier) and very much hope to have it in 
the next darcs release. Simon M has already tried out an experimental 
version and was quite positive about it, though there's significant work 
yet to do. If anyone else wants to try it, please do: see the thread at 
http://lists.osuosl.org/pipermail/darcs-users/2010-August/024924.html


2) multi-branch repos. We've pretty much agreed we need these; I think the 
strongest motivation is being able to keep the same build products around 
when switching branches. No concrete plans, but perhaps the release after 
next if we can manage it?


3) Better performance when there are conflicts, so you don't have to 
rebase as often/ever. For this you need a new patch format. GHC is using 
v1 patches, but darcs also now has v2 patches, which get into exponential 
merges much less often - but it's still possible, and we know of bugs in 
the merging which can hit in complex cases (v1 patches also have a few 
buggy corner cases). You also have to go through an explicit conversion 
step to switch to v2. I think we need to have another go at figuring out 
the problem once and for all (i.e. v3) but we don't know for sure how to 
do this.


Something related, but not exactly addressing the problems you 
all describe is:


4) Better UI around managing conflicts - one frequently requested thing is 
to be able to see the names of the patches that caused the conflicts. I'm 
working on this actively (it's also useful for rebase) and I also 
hope/expect to have this in the next release. Another thing that'll 
definitely be in the next release is that conflict marks will include the 
original text as well, so you can work out what changes each side of the 
conflict made. In my experience that actually makes a huge difference and 
it's very annoying we didn't do it earlier.


and, once we've got better at the basics,

5) we'd love to add new patch types that reduce the number of conflicts 
you get at all. Some ideas include hunk move patches that track when you 
move code from place to place, identation patches, and patches that track 
character changes to an individual line. Again, no timescale, but having 
refactored some of the core patch code recently it's now much clearer how 
we could do this.


Finally, I think the future holds more hybrid environments where different 
people use different VCSes and bridge between them. (At least, I hope so, 
it's the only hope darcs has of staying relevant in the wider world :-). 
Petr Rockai's recent darcs-fastconvert tool offers incremental darcs-git 
conversions, which I think should allow people who are happier with git to 
use that instead and only convert back to darcs to submit their patches.

[It may be that previous tools also offered this, I'm not certain.]

Cheers,

Ganesh

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell-cafe] Type families again

2010-12-03 Thread Ganesh Sittampalam

On Thu, 2 Dec 2010, Robert Greayer wrote:


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:


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:


I spent a while looking at this a couple of months ago after a similar 
question. What I came up with is below; I haven't got as far as 
deciding whether or how to incorporate this into rmonad. Also, the Const 
type actually already exists in Control.Applicative.


Cheers,

Ganesh

{-# LANGUAGE GADTs, TypeFamilies, MultiParamTypeClasses, FlexibleInstances, 
ScopedTypeVariables, RankNTypes #-}

module Control.RMonad.Wibble where

import Control.RMonad
import Data.ByteString (ByteString)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Char8 as BSC
import Data.Suitable
import GHC.Word (Word8)

-- Part I

-- a little warmup: ByteStrings

-- We have two choices for BSWrapper. Either make
-- it a GADT, which means we can leave out the match on the
-- argument constraints below, or make it a H98 phantom.
-- The second option seems cleaner and more symmetric.
-- It also means we can us newtype to avoid runtime overhead.

-- data BSWrapper a where
--   BSWrapper :: ByteString - BSWrapper Word8

newtype BSWrapper a = BSWrapper ByteString

data instance Constraints BSWrapper a = (a ~ Word8) = BSConstraints

instance Suitable BSWrapper Word8 where
  constraints = BSConstraints

instance RFunctor BSWrapper where
  -- We could also use withResConstraints by rearranging the arguments to mymap 
so Constraints is last
  fmap = mymap constraints constraints
where mymap :: forall x y . Constraints BSWrapper x - Constraints BSWrapper y - (x 
- y) - BSWrapper x - BSWrapper y
  mymap BSConstraints BSConstraints f (BSWrapper x) = BSWrapper (BS.map 
f x)

-- Part II

-- OK, now let's generalise:

-- Having a class here rather than a plain type family isn't really necessary,
-- but it feels natural
class SingletonContainer c where
   type ContainedType c :: *

-- data SingletonWrapper c a where
--   SingletonWrapper :: SingletonContainer c = c - SingletonWrapper c 
(ContainedType c)

-- This is just a generic Const type. Is there a standard one somewhere else?
newtype SingletonWrapper c a = SingletonWrapper c

data instance Constraints (SingletonWrapper c) a = (a ~ ContainedType c) = 
SingletonConstraints

-- important to use the type equality constraint here instead of inlining it
-- on the RHS, as otherwise instance resolution would get stuck
instance (a ~ ContainedType c) = Suitable (SingletonWrapper c) a where
  constraints = SingletonConstraints

class SingletonContainer c = Mappable c where
   lmap :: (ContainedType c - ContainedType c) - c - c

instance Mappable c = RFunctor (SingletonWrapper c) where
  fmap = mymap constraints constraints
where mymap :: forall x y
 . Constraints (SingletonWrapper c) x
- Constraints (SingletonWrapper c) y
- (x - y)
- SingletonWrapper c x
- SingletonWrapper c y
  mymap SingletonConstraints SingletonConstraints f (SingletonWrapper 
x) = SingletonWrapper (lmap f x)


-- so, why is Word8 the blessed instance? Why not Char (from 
Data.ByteString.Char8)?
instance SingletonContainer ByteString where
   type ContainedType ByteString = Word8


-- Part III

-- and finally, let's try to generalise the Singleton concept:

-- using the Const concept again...
newtype Const a b = Const a

instance Show a = Show (Const a b) where
  show (Const x) = show x

data instance Constraints (Const ByteString) a =
   (a ~ Word8) = BSConstraintsWord8
 | (a ~ Char) = BSConstraintsChar

instance Suitable (Const ByteString) Word8 where
   constraints = BSConstraintsWord8

instance Suitable (Const ByteString) Char where
   constraints = BSConstraintsChar

instance RFunctor (Const ByteString) where
  fmap = mymap constraints constraints
where mymap :: forall x y
 . Constraints (Const ByteString) x
- Constraints (Const ByteString) y
- (x - y) - Const ByteString x - Const 

[Haskell-cafe] HTTP 4000.1.0 release

2010-11-09 Thread Ganesh Sittampalam

Hi,

I've just released HTTP 4000.1.0 to hackage:

 - Fixed a bug that caused infinite loops for some URLs on some platforms 
(whether the URL was a trigger is probably related to the size of the 
returned data, and the affected platforms. Based on a patch by Daniel 
Wagner.


   - This is technically a breaking change (and hence there is an API 
version bump) as the fix introduces a new member to the HStream class 
which can be used to define a new payload type instead of 
String/ByteString, but I scanned hackage and noone actually seems to be 
doing that.


 - Applied a patch by Antoine Latter to fix a bug in the handling of 
301 and 307 response codes. Here's his description of the change:


***
The Network.Browser module is a convenience layer over the
Network.Http modules offering many of the niceties one would expect in
a web-browser - cookies, user authentication, and transparent handling
of redirects.

When using Network.Browser, previously (since version 4000.0.8) a
redirect response code of 301 or 307 from the server would force the
redirected request to be sent as a GET, even if the original request
was of some other HTTP method. This behavior is only appropriate for a
response code of 302 or 303 and has been fixed.
***

The upstream repo is now on github: https://github.com/haskell/HTTP, 
though I may well switch back to darcs if I remain maintainer for long.


I'd like to emphasise that I have no particular desire to maintain HTTP 
and if anyone else would like to take over they would be very welcome!


Cheers,

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


Re: [Haskell-cafe] Bug in HTTP (bad internal error handling)

2010-11-03 Thread Ganesh Sittampalam

On Wed, 3 Nov 2010, Simon Marlow wrote:


On 29/10/2010 23:24, Ganesh Sittampalam wrote:


4000.0.10 should fix the reported issue with fail and Either, and bumps
the base dep to build with GHC 7.0


That's great.  Any chance you could also look at this one, which appears to 
be a pretty serious bug for some people, and has a patch?


http://hackage.haskell.org/trac/ghc/ticket/4251


Sure, I'll do it this weekend. Given that the HTTP test suite is pretty 
minimal, we'll just have to hope for no unintended side-effects 
though (which also applies to the previous change, of course).


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


Re: MonoLocalBinds and darcs

2010-11-02 Thread Ganesh Sittampalam

Hi Neil,

On Tue, 2 Nov 2010, Neil Mitchell wrote:


Make sure you are using RC2 of the compiler, from what I remember RC1
required signatures it shouldn't have, or enabled MonoLocalBinds more
than it should - RC2 required less signatures. However, your code
could well just be heavily using the relevant features.


I was using RC2. But darcs uses GADTs globally so MonoLocalBinds is always 
on.


I've now retested with NoMonoLocalBinds properly enabled and I just needed 
one extra signature. That's quite compelling, but I'm aware it's not 
considered a reliable feature so I'm not quite sure which way to go.


The NPlusKPatterns thing seems to have been a red herring btw, I can't 
reproduce it now.


Cheers,

Ganesh
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell-cafe] Bug in HTTP (bad internal error handling)

2010-10-29 Thread Ganesh Sittampalam

On Fri, 22 Oct 2010, Sigbjorn Finne wrote:


On Fri, Oct 22, 2010 at 9:35 AM, Sittampalam, Ganesh 
ganesh.sittampa...@credit-suisse.com wrote:


libraries@, what's the right way to proceed? Can I make a Debian-style
non-maintainer upload with minimal changes to fix urgent issues like
these?



I'd be much obliged if you could, and I do apologise for leaving all of this
just hanging.


I've just done this. Thanks for the blessing.

4000.0.10 should fix the reported issue with fail and Either, and bumps 
the base dep to build with GHC 7.0



No time available for Haskell projects these days unfortunately, Opera
engine development taking up most of my waking hours. Getting someone to
take over HTTP would be best, or maybe rewrite it altogether..it is not the
prettiest thing around :)


I'm not particularly keen on taking over maintainership, but I guess if 
noone else wants it I could take it over and do at least minimal updates 
like this.


Any other volunteers?

Cheers,

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


Re: [Haskell-cafe] Bug in HTTP (bad internal error handling)

2010-10-24 Thread Ganesh Sittampalam

On Sun, 24 Oct 2010, Bit Connor wrote:


On Sat, Oct 23, 2010 at 8:49 PM, Ganesh Sittampalam gan...@earth.li wrote:


I'm just looking at fixing this so I can make an upload as discussed with
Sigbjorn. I guess the best thing to do is to make all the calls to fail into
something more explicit.


Yep. Ideally, simpleHTTP and its friends should never throw an IO
exception (and should certainly never call prelude's error, as
happens now). Network errors and other errors should be reported by
returning an appropriate ConnError Result:


I'm not going to try to audit for that exhaustively right now, but I've 
changed all the calls to fail that were broken by the Either change, so 
hopefully we should be back where we started.


I've put a repo up with the changes and a base dependency bump at 
http://urchin.earth.li/git/HTTP - could you (and anyone else interested) 
give it a try? I haven't done anything but the most minimal testing and in 
particular I haven't made any effort to reproduce your specific problem.


I plan to upload this as HTTP-4000.0.10 in the next few days.

Cheers,

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


Re: [Haskell-cafe] Bug in HTTP (bad internal error handling)

2010-10-23 Thread Ganesh Sittampalam

Hi Bit,

On Thu, 21 Oct 2010, Bit Connor wrote:


On Sat, Oct 16, 2010 at 10:29 AM, Claus Reinke claus.rei...@talk21.com wrote:

After it catches this error, the function returns (line 376):

return (fail (show e))

The fail is running in the Either monad (The Result type = Either).
This calls the default Monad implementation of fail, which is just a
call to plain old error. This basically causes the entire program to
crash.



Actually, it appears that simpleHTTP isn't actually supposed to throw
an IOException, and it is instead supposed to return a ConnError
result. So the real fix is to fix the code to make this happen. But


Sounds like a victim of
  http://hackage.haskell.org/trac/ghc/ticket/4159

For mtl clients, 'fail' for 'Either' used to call 'Left'. That was
changed, though the ticket does not indicate the library
versions affected.


This looks like the problem. Any idea how to get the HTTP package
fixed? I could try making a patch myself, but I would prefer hearing
from the HTTP maintainer first, who doesn't seem to be around.


I'm just looking at fixing this so I can make an upload as discussed with 
Sigbjorn. I guess the best thing to do is to make all the calls to fail 
into something more explicit.


BTW, can you confirm that you were using GHC 7.0 (or 6.13) when this went 
wrong?


Cheers,

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


Re: ANNOUNCE: GHC 7.0.1 Release Candidate 1

2010-09-27 Thread Ganesh Sittampalam

On Sun, 26 Sep 2010, Ian Lynagh wrote:


We are pleased to announce the first release candidate for GHC 7.0.1:

   http://new-www.haskell.org/ghc/dist/7.0.1-rc1/

This includes the source tarball, installers for OS X and Windows, and
bindists for amd64/Linux and i386/Linux.

Please test as much as possible; bugs are much cheaper if we find them
before the release!


gan...@nevis:~/dataenc$ cabal install regex-posix
Resolving dependencies...
Configuring regex-posix-0.94.4...
Preprocessing library regex-posix-0.94.4...
Building regex-posix-0.94.4...
[1 of 6] Compiling Text.Regex.Posix.Wrap ( 
dist/build/Text/Regex/Posix/Wrap.hs, dist/build/Text/Regex/Posix/Wrap.o )

SpecConstr
Function `lvl_s2xM{v} [lid]'
  has three call patterns, but the limit is 0
Use -fspec-constr-count=n to set the bound
Use -dppr-debug to see specialisations
ghc: panic! (the 'impossible' happened)
  (GHC version 7.0.0.20100924 for x86_64-unknown-linux):
initC: srt_lbl

Let me know if you'd prefer this to be recorded in trac or would like me 
to try to cut it down.


Cheers,

Ganesh


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell-cafe] Re: explicit big lambdas

2010-03-19 Thread Ganesh Sittampalam

On Fri, 19 Mar 2010, o...@okmij.org wrote:



Paul Brauner wrote:

is there a way in some haskell extension to explicit (system F's) big
lambdas and (term Type) applications in order to help type inference?


Actually, yes: newtype constructor introductions may act as a big
lambda, with constructor elimination acting as type applications:
http://okmij.org/ftp/Haskell/types.html#some-impredicativity


Newtypes are also handy for turning type functions (defined by type
families) into real lambdas. For example, given the following code


Isn't this the equivalent of explicitly naming a function rather than
making an anonymous one with lambda?

Cheers,

Ganesh
___
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 Ganesh Sittampalam

On Tue, 8 Dec 2009, Tom Tobin 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 combination of haykll and pandoc clearly must be GPL. I don't think it 
automatically follows from that that hakyll taken alone must be GPL. One 
might argue that the hakyll itself must be a derivative work as it builds 
on pandoc, but equally there may well be at least some pieces of hakyll 
that have independent uses; in addition someone might write a 
API-compatible replacement for pandoc that was BSD3. I would therefore 
argue for clearly marking the hakyll source as BSD3, so long as there is 
some way to clearly signal that anything compiled from it will necessarily 
be GPL.


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


[Haskell-cafe] call for help: FOSDEM devroom

2009-11-08 Thread Ganesh Sittampalam

Hi,

I'm thinking of trying to get a devroom for haskell.org at the next 
FOSDEM, which is Saturday-Sunday February 6th-7th 2010 in Brussels: 
http://www.fosdem.org/2010/call-developer-rooms


The idea would be to try to introduce Haskell to people at FOSDEM who were 
interested, and thus help build our ties with We'd try to have a few 
introductory talks about Haskell, and some demos etc. It would probably 
also make sense to talk about/demo darcs at the same time.


Apparently there's a lot of demand so it's a bit of a long shot, and I 
expect we'd only get one day, which is probably all we'd need.


To make this work, we'll need several reasonably experienced Haskellers to 
turn up to help out with the talks, demos and talking to people in 
general. I've got a couple of people interested already but need more.


So, please could you let me know, preferably within the next week, whether 
you would be interested in coming along and helping. You can email me 
directly or on-list as you prefer.


The deadline for actually making the application for the devroom is 22nd 
November.


Cheers,

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


RE: GHC 6.12.1 and impredicative polymorphism

2009-11-02 Thread Ganesh Sittampalam

On Fri, 30 Oct 2009, Sittampalam, Ganesh wrote:


Simon Peyton-Jones wrote:


Fortunately, I don't think a lot of people use the feature in anger.
Please yell if you *are* using impredicative polymorphism for
something serious.  But if you are, we need to think of a workaround.
The current situation seems unsustainable.


I think darcs is using it. At least, I had to enable
ImpredicativePolymorphism to successfully build darcs with GHC 6.11 (a
snapshot from about February), although the flag is not required with
GHC 6.10. I haven't had a chance to try with the RC yet, but will do
this weekend.

I'll have to check the full details of why it's needed, but from memory
I think it can be worked around at the cost of more verbosity by using
some newtypes in appropriate places.


OK, I confirm the changes are fairly trivial. The main issue is that a 
couple of functions want to instantiate the argument to IO with a type 
scheme:


restrictBoring :: IO (forall t m. FilterTree t m = t m - t m)

The newtype workaround works fine here and doesn't affect too much of the 
code. In one other place some code had type [(String, Foo)] where Foo is a 
type synonym for (forall x y . something), but it turned out the nested 
quantification wasn't required so (forall x y . [(String, something)]) 
was ok in this case, if a little uglier.


(Patch sent to darcs-users)

Cheers,

Ganesh
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


array-0.2.0.0 doesn't build with 6.12rc1

2009-10-31 Thread Ganesh Sittampalam

[ 6 of 10] Compiling Data.Array.IO( Data/Array/IO.hs, 
dist/build/Data/Array/IO.o )

Data/Array/IO.hs:73:13:
`haFD' is not a (visible) field of constructor `Handle__'

Data/Array/IO.hs:73:22:
`haBuffer' is not a (visible) field of constructor `Handle__'

Data/Array/IO.hs:73:36:
`haIsStream' is not a (visible) field of constructor `Handle__'

Data/Array/IO.hs:74:5: Not in scope: data constructor `Buffer'

Data/Array/IO.hs:74:13:
`bufBuf' is not a (visible) field of constructor `Buffer'

Data/Array/IO.hs:74:25:
`bufWPtr' is not a (visible) field of constructor `Buffer'

Data/Array/IO.hs:74:36:
`bufRPtr' is not a (visible) field of constructor `Buffer'

Data/Array/IO.hs:75:4: Not in scope: `bufferEmpty'

Data/Array/IO.hs:82:24:
`bufWPtr' is not a (visible) constructor field name

Data/Array/IO.hs:82:35:
`bufRPtr' is not a (visible) constructor field name

Data/Array/IO.hs:86:24:
`bufRPtr' is not a (visible) constructor field name

Data/Array/IO.hs:95:27:
Not in scope: type constructor or class `RawBuffer'

Data/Array/IO.hs:101:10: Not in scope: `readRawBuffer'

Data/Array/IO.hs:125:22:
`haFD' is not a (visible) field of constructor `Handle__'

Data/Array/IO.hs:125:31:
`haBuffer' is not a (visible) field of constructor `Handle__'

Data/Array/IO.hs:125:45:
`haIsStream' is not a (visible) field of constructor `Handle__'

Data/Array/IO.hs:127:18: Not in scope: data constructor `Buffer'

Data/Array/IO.hs:127:26:
`bufBuf' is not a (visible) field of constructor `Buffer'

Data/Array/IO.hs:127:42:
`bufWPtr' is not a (visible) field of constructor `Buffer'

Data/Array/IO.hs:127:53:
`bufSize' is not a (visible) field of constructor `Buffer'

Data/Array/IO.hs:135:30:
`bufWPtr' is not a (visible) constructor field name

Data/Array/IO.hs:142:7: Not in scope: data constructor `Buffer'

Data/Array/IO.hs:142:15:
`bufBuf' is not a (visible) field of constructor `Buffer'

Data/Array/IO.hs:142:27:
`bufState' is not a (visible) field of constructor `Buffer'

Data/Array/IO.hs:142:36:
Not in scope: data constructor `WriteBuffer'

Data/Array/IO.hs:143:8:
`bufRPtr' is not a (visible) field of constructor `Buffer'

Data/Array/IO.hs:143:19:
`bufWPtr' is not a (visible) field of constructor `Buffer'

Data/Array/IO.hs:143:34:
`bufSize' is not a (visible) field of constructor `Buffer'

Data/Array/IO.hs:151:22:
Not in scope: type constructor or class `RawBuffer'

Data/Array/IO.hs:151:43:
Not in scope: type constructor or class `RawBuffer'

Data/Array/IO.hs:153:22:
Not in scope: type constructor or class `RawBuffer'

Data/Array/IO.hs:153:35:
Not in scope: type constructor or class `RawBuffer'

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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

2009-09-12 Thread Ganesh Sittampalam

On Sat, 12 Sep 2009, Brandon S. Allbery KF8NH wrote:


On Sep 12, 2009, at 11:22 , Trent W. Buck wrote:

Jason Dagit da...@codersbase.com writes:

which ensures that when the operating system is not WIN32, that
renaming of files will be performed by the OS shell.


I'm also puzzled as to why this works -- surely mv(1) assumes POSIX
semantics, too?  I would be interested in seeing the exact error
transcript, preferably as an issue on bugs.d.n.  I'm not sure the
problem has been diagnosed correctly.


In order to handle the case where you're moving across filesystems, mv(1) 
gracefully degrades to cp + rm.  rename(2) does not.  This also happens to 
work around compatibility issues with native CIFS (and possibly older HP/UX, 
not that anyone likely cares).


I don't think that darcs is ever likely to want to do a move across 
filesystems - unless someone has actually put a mount point in the middle 
of their darcs repo (and perhaps not even then for the metadata operations 
such as the one that was failing here, as I think those are all inside a 
single directory).


Darcs already has a WIN32-specific workaround for renaming going wrong 
when the new file exists, and my initial guess was that was what was going 
wrong here. The workaround just tries to remove the new file and retries 
the rename. The original poster doesn't make clear whether he tried my 
suggested fix enabling that workaround unconditionally before resorting to 
shelling out.


Cheers,

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


Re: [Haskell-cafe] Darcs 2.3 and NFS

2009-09-09 Thread Ganesh Sittampalam

On Wed, 9 Sep 2009, Lewis-Sandy, Darrell wrote:

Windows Vista, Ubuntu 9.04 32-bit, Ubuntu 64 bit, etc).  I have a 
windows file share that is accessible to all the machines, and has been 
permanently mounted as a CIFS share on the Linux machines.


I have built darcs 2.3 on the Ubuntu 9.04 (Jaunty) 32 bit box and am 
able to execute darcs commands against any local folders, but am 
consistently getting an error message when I try to push or put to the 
NFS:


darcs: ./_darcs/tentative_pristine-0:rename: already exists (File 
exists)


At a guess, Windows filesystem semantics are causing trouble here and 
darcs doesn't know to work around them. There's some code in 
src/Workaround.hs that sets up a custom renameFile function on Windows - 
try changing that so that it's unconditionally enabled?


Following up on darcs-users would be best though you might need to 
subscribe.


Cheers,

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


Re: finalizers on handles

2009-06-23 Thread Ganesh Sittampalam

On Tue, 23 Jun 2009, Brandon S. Allbery KF8NH wrote:


On Jun 23, 2009, at 09:41 , Simon Marlow wrote:

main = do
(ih, oh, _, _) - runInteractiveProcess cat [] Nothing Nothing
comphszp - hGetContents oh
print (length comphszp)
-- hClose ih -- with this line they both deadlock



Note that you can trigger this in any language; it's a classic beginner 
error with pipes (see, for example, the documentation for open2/open3 in 
Perl or Python for other examples).  Detecting this in the type system 
would be an interesting idea, but de facto I think this is a it hurts 
when I do this.


Sure - but it hurts more when in some environments you get away with it 
and others you don't.


Ganesh
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


finalizers on handles

2009-06-20 Thread Ganesh Sittampalam

Hi,

I recently spent a while debugging a problem where a program deadlocked in 
the non-threaded runtime, but ran fine in the threaded runtime, despite 
the program having no blocking FFI calls, and boiled it down to the 
following test case:


module Main(main) where

import System
import System.IO
import System.Process

main = do
   (ih, oh, _, _) - runInteractiveProcess cat [] Nothing Nothing
   comphszp - hGetContents oh
   print (length comphszp)
   -- hClose ih -- with this line they both deadlock

The reason for the deadlock is fairly straightforward; since ih isn't 
closed before comphszp is fully demanded, no progress can be made. My 
guess is that the threaded runtime is fine because ih is dead at that 
point, and the finalizer for ih gets a chance to run, closing ih.


If I'm right, is it really sensible for every handle to have this 
finalizer? Closing a pipe has externally visible side 
effects beyond just the release of resources, so it doesn't seem like it 
should happen non-deterministically.


Cheers,

Ganesh
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell-cafe] Re: Darcs - dependencies between repositories (aka forests)

2009-03-29 Thread Ganesh Sittampalam

On Sun, 29 Mar 2009, Peter Verswyvelen wrote:


Module A requires B. When a new developer wants to get the source code, he
does a darcs get server://program/A, which gives him only the latest
version of A. So he manually needs to do darcs get server://program/B
(that B is required is usually discovered after a compilation error, talking
to other developers to find out what the dependencies are, or by reading the
cabal file). Furthermore it is unclear which version of A required which
version of B (so you can't really roll back to old versions).

Now assume you don't have 2 modules but dozens...

To me, any version control system should be able to track dependencies
between repositories. Something similar like Cabal's dependency system.

So my question is really, how do you solve the dependency tracking between
several Darcs repositories?


There's an (unimplemented) proposal by David Roundy for darcs sub-repos 
that would solve this problem: you have a darcs patch type 
that means depend on this patch from this other darcs repo which will be 
checked out in a given subdirectory. I think that solves precisely the 
problem you describe, and I think it should be implemented :-)


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


GHC 6.10 changes for recursive calls to class instances

2009-02-19 Thread Ganesh Sittampalam

Hi,

I have a problem in GHC 6.10 with functions in a class instance calling 
other functions in the same class instance. It seems that the dictionary 
is freshly constructed for this call, despite being already available.


The reason I care is that I want to memoise some expensive computations 
inside the dictionary for each instance. [Obviously I also have to make 
sure that the dictionary isn't constructed multiple times by external 
callers, but I can make other arrangements to ensure that.]


To see the problem in action, run main from the attached code. In GHC 6.8 
and before, this only executes the trace statement once. In GHC 6.10, the 
trace statement executes twice, at all optimisation levels.


This seems related to
http://hackage.haskell.org/trac/ghc/ticket/2902, but I'm a little unclear
on whether it's the same problem or not.

Cheers,

Ganesh{-# LANGUAGE ScopedTypeVariables #-}
module RecDict where

import Debug.Trace

class Foo a where
   tname :: a - String

   mem1 :: a - Int

   mem2 :: a - Int
   mem2 = let opt = trace (Ouch! Imagine this is really expensive! Called for  ++ tname (undefined :: a)) (2 * mem1 (undefined :: a))
  in \a - opt

   mem3 :: a - Int


instance Foo () where
   tname _ = ()

   mem1 _ = 0

   mem3 _ = 0

data T a = T a

instance Foo a = Foo (T a) where
   tname ~(T a) = T ( ++ tname a ++ )

   mem1 ~(T a) = 1 + mem1 a

   mem3 a = 1 + mem2 a

add :: Foo a = a - Int
add a = mem2 a + mem3 a

main = print $ add (T ())
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell-cafe] manipulating predicate formulae

2008-12-04 Thread Ganesh Sittampalam

Hi,

That sounds like it might be quite useful. What I'm doing is generating 
some predicates that involve addition/subtraction/comparison of integers 
and concatenation/comparison of lists of some abstract thing, and then 
trying to simplify them. An example would be simplifying


\exists p_before . \exists p_after . \exists q_before . \exists q_after . 
\exists as . \exists bs . \exists cs . (length p_before == p_pos  length 
q_before == q_pos  (p_before == as  q_after == cs)  p_before ++ 
p_new ++ p_after == as ++ p_new ++ bs ++ q_old ++ cs  as ++ p_new ++ bs 
++ q_old ++ cs == q_before ++ q_old ++ q_after)


into

q_pos - (p_pos + length p_new) = 0

which uses some properties of length as well as some arithmetic. I don't 
expect this all to be done magically for me, but I'd like as much help as 
possible - at the moment I've been growing my own library of predicate 
transformations but it's all a bit ad-hoc.


If I could look at your code I'd be very interested.

Cheers,

Ganesh

On Thu, 4 Dec 2008, Immanuel Normann wrote:


Hi Ganesh,

manipulating predicate formulae was a central part of my PhD research. I
implemented some normalization and standarcization functions in Haskell -
inspired by term rewriting (like normalization to Boolean ring
representation) as well as (as far as I know) novell ideas (standardization
of quantified formulae w.r.t associativity and commutativity).
If you are interested in that stuff I am pleased to provide you with more
information. May be you can describe in more detail what you are looking
for.

Best,
Immanuel

2008/11/30 Ganesh Sittampalam [EMAIL PROTECTED]


Hi,

Are there any Haskell libraries around for manipulating predicate formulae?
I had a look on hackage but couldn't spot anything.

I am generating complex expressions that I'd like some programmatic help in
simplifying.

Cheers,

Ganesh
___
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] manipulating predicate formulae

2008-12-04 Thread Ganesh Sittampalam
Thanks - I'll take a look. One pre-emptive question: if I want to use it, 
it'd be more convenient, though not insurmountable, if that code was 
BSD3-licenced, since it will fit in better with the licence for camp 
http://projects.haskell.org/camp, which I might eventually want to 
integrate my code into. (the predicates I described are intended to be the 
commutation conditions for patches). Is that likely to be possible?


Cheers,

Ganesh

On Fri, 5 Dec 2008, Immanuel Normann wrote:


Hi,

you can browse my code
here.http://trac.informatik.uni-bremen.de:8080/hets/browser/trunk/Search/CommonIt
has become part of
Hets http://www.dfki.de/sks/hets the Heterogeneous Tool Set which is a
parsing, static analysis and proof management tool combining various tools
for different specification languages.
However, let me warn you: the code isn't yet well documented at parts also
ad hoc. Don't know whether it can help to solve your tasks.
The goal of my normalization code is to bring formulae via equivalence
transformations and alpha-renaming into a standard or normal form such that
for instance the following three formulae become syntactically identical
(i.e. not just modulo alpha equivalence or modulo associativity and
commutativity):

\begin{enumeratenumeric}
 \item $\forall \varepsilon . \varepsilon  0 \Rightarrow \exists \delta .
 \forall x. \forall y. 0  |x - y| \wedge |x - y|  \delta \Rightarrow | f
 (x) - f (y) |  \varepsilon$

 \item $\forall \varepsilon . \exists \delta . \forall x, y. \varepsilon 
0
 \Rightarrow (0  |x - y| \wedge |x - y|  \delta \Rightarrow | f (x) - f
(y)  |  \varepsilon)$

 \item $\forall e . \exists d . \forall a,b. e  0
 \wedge |a - b|  d \wedge 0  |a - b| \Rightarrow | f (a) - f (b) |  e$
\end{enumeratenumeric}

Cheers,

Immanuel



2008/12/4 Ganesh Sittampalam [EMAIL PROTECTED]


Hi,

That sounds like it might be quite useful. What I'm doing is generating
some predicates that involve addition/subtraction/comparison of integers and
concatenation/comparison of lists of some abstract thing, and then trying to
simplify them. An example would be simplifying

\exists p_before . \exists p_after . \exists q_before . \exists q_after .
\exists as . \exists bs . \exists cs . (length p_before == p_pos  length
q_before == q_pos  (p_before == as  q_after == cs)  p_before ++ p_new
++ p_after == as ++ p_new ++ bs ++ q_old ++ cs  as ++ p_new ++ bs ++ q_old
++ cs == q_before ++ q_old ++ q_after)

into

q_pos - (p_pos + length p_new) = 0

which uses some properties of length as well as some arithmetic. I don't
expect this all to be done magically for me, but I'd like as much help as
possible - at the moment I've been growing my own library of predicate
transformations but it's all a bit ad-hoc.

If I could look at your code I'd be very interested.

Cheers,

Ganesh


On Thu, 4 Dec 2008, Immanuel Normann wrote:

 Hi Ganesh,


manipulating predicate formulae was a central part of my PhD research. I
implemented some normalization and standarcization functions in Haskell -
inspired by term rewriting (like normalization to Boolean ring
representation) as well as (as far as I know) novell ideas
(standardization
of quantified formulae w.r.t associativity and commutativity).
If you are interested in that stuff I am pleased to provide you with more
information. May be you can describe in more detail what you are looking
for.

Best,
Immanuel

2008/11/30 Ganesh Sittampalam [EMAIL PROTECTED]

 Hi,


Are there any Haskell libraries around for manipulating predicate
formulae?
I had a look on hackage but couldn't spot anything.

I am generating complex expressions that I'd like some programmatic help
in
simplifying.

Cheers,

Ganesh
___
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] manipulating predicate formulae

2008-12-01 Thread Ganesh Sittampalam

On Sun, 30 Nov 2008, Neil Mitchell wrote:


http://www.cs.york.ac.uk/fp/darcs/proposition/

Unreleased, but might be of interest. It simplifies propositional
formulae, and can do so using algebraic laws, custom simplifications
or BDDs. I don't really use this library, so if it is of interest to
you, its all yours :-)


Thanks, but I don't think a propositional library is a good starting point 
for a predicate library - the problems are too different. Sadly my 
predicates are over infinite domains, otherwise BDDs would have been 
really nice :-(


Cheers,

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


Re: [Haskell-cafe] Re: howto tuple fold to do n-ary cross product?

2008-11-30 Thread Ganesh Sittampalam

On Sun, 30 Nov 2008, Brandon S. Allbery KF8NH wrote:


On 2008 Nov 30, at 12:43, Max Rabkin wrote:


It seems to me like this would all be easy if (a,b,c,d) was sugar for
(a,(b,(c,d))), and I can't see a disadvantage to that.



No disadvantage aside from it making tuples indistinguishable from lists.


No, they'd still have statically known length and be heterogenous, it 
would just change some strictness properties.


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


[Haskell-cafe] manipulating predicate formulae

2008-11-30 Thread Ganesh Sittampalam

Hi,

Are there any Haskell libraries around for manipulating predicate 
formulae? I had a look on hackage but couldn't spot anything.


I am generating complex expressions that I'd like some programmatic help 
in simplifying.


Cheers,

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


Re: [Haskell-cafe] Re: Comparing GADTs for Eq and Ord

2008-09-15 Thread Ganesh Sittampalam

On Mon, 15 Sep 2008, Tom Hawkins wrote:


OK.  But let's modify Expr so that Const carries values of different types:

data Expr :: * - * where
 Const :: a - Term a
 Equal :: Term a - Term a - Term Bool

How would you then define:

Const a === Const b  = ...


Apart from the suggestions about Data.Typeable etc, one possibility is to 
enumerate the different possible types that will be used as parameters to 
Const in different constructors, either in Expr or in a new type.


So IntConst :: Int - Expr Int, etc

Or Const :: Const a - Expr a and IntConst :: Int - Const Int etc

Not very pleasant though.

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


Re: [Haskell-cafe] Re: Top Level -

2008-09-07 Thread Ganesh Sittampalam

On Sat, 6 Sep 2008, Brandon S. Allbery KF8NH wrote:


On 2008 Sep 6, at 18:25, Ashley Yakeley wrote:


2. If the dynamic loader loads an endless stream of different modules
containing initialisers, memory will thus leak.


I think if the issue is this vs. not being able to guarantee any 
once-only semantics, i consider the former necessary overhead for proper 
program behavior.


Not leaking memory is an important part of proper program behaviour.

And that, given that there exists extra-program global state that 
one might want to access, once-only initialization is a necessity.


In what cases? In the case of buffered I/O there's no reason (in theory) 
you couldn't unload libc, do unbuffered I/O for a while, then reload libc 
and start again.


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


[Haskell-cafe] Re: Top Level -

2008-09-07 Thread Ganesh Sittampalam

On Sat, 6 Sep 2008, Ashley Yakeley wrote:


Ganesh Sittampalam wrote:
The set of ACIO expressions exp is the static initialisers of M. The 
RTS must note when each static initialiser is run, and cache its result 
val. Let's call this cache of vals the static results cache of M.


When M is loaded, and a static results cache for M already exists, then 
it will be used for the vals of M.


This sounds reachable to me, and therefore static overhead and not a 
leak.


You can call it what you like, but it's still unacceptable behaviour, 
particularly since clients of M will have no way of telling from its 
API that it will happen.


That what will happen?


That memory will be used and not ever be reclaimable.

Suppose I am writing something that I intend to be used as part of a 
plug-in that is reloaded in different forms again and again. And I see 
module K which does something I want, so I use it. It so happens that K 
uses M, which has a -. If I knew that using K in my plug-in would cause a 
memory leak, I would avoid doing so; but since the whole point of - is to 
avoid making the need for some state visible in the API.


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


Re: [Haskell-cafe] Re: Top Level -

2008-09-07 Thread Ganesh Sittampalam

On Sun, 7 Sep 2008, Brandon S. Allbery KF8NH wrote:

You seem to think we must never insure that something will only be run 
once, that any program that does require this is broken.  As such, the 
standard Haskell libraries (including some whose interfaces are H98) are 
unfixably broken and you'd better start looking elsewhere for your 
correct behavior.


Data.Unique might be unfixably broken, though perhaps some requirement 
that it not be unloaded while any values of type Unique are still around 
could solve the problem - though it's hard to see how this could be 
implemented sanely. But Data.Unique could (a) probably be replaced with 
something in terms of IORefs and (b) is pretty ugly anyway, since it 
forces you into IO.


I'm sure that for many other examples, re-initialisation would be fine. 
For example Data.HashTable just uses a global for instrumentation for 
performance tuning, which could happily be reset if it got unloaded and 
then reloaded. System.Random could get a new StdGen. I haven't yet had 
time to go through the entire list that Adrian Hey posted to understand 
why they are being used, though.


I'd also point out that if you unload and load libraries in C, global 
state will be lost and re-initialised.


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


[Haskell-cafe] Re: Top Level -

2008-09-07 Thread Ganesh Sittampalam

On Sun, 7 Sep 2008, Ashley Yakeley wrote:


Ganesh Sittampalam wrote:
Suppose I am writing something that I intend to be used as part of a 
plug-in that is reloaded in different forms again and again. And I see 
module K which does something I want, so I use it. It so happens that K 
uses M, which has a -. If I knew that using K in my plug-in would cause a 
memory leak, I would avoid doing so; but since the whole point of - is to 
avoid making the need for some state visible in the API.


The results from the - in M will only be stored once for the life of the 
RTS, no matter how many times your plug-ins are reloaded.


Sorry, I keep forgetting that. OK, so you can't get an endless stream of 
leaks unless you use - yourself, or modules on your system keep getting 
upgraded to new versions.


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


[Haskell-cafe] Re: Top Level -

2008-09-06 Thread Ganesh Sittampalam

On Sat, 6 Sep 2008, Ashley Yakeley wrote:


Ganesh Sittampalam wrote:
But it's limited to the initialisers. An IORef holding an Integer isn't 
much memory, and it only ever gets leaked once.



It happens every time you load and unload, surely?


No. An initialiser is only ever run once per run of the RTS.


Oh, I see. Yes, sorry.

Since it's of the order of the number of uniquely identified 
initialisers, it's arguably not a memory leak so much as a static 
overhead. The only way to get a continuous leak is to load and unload an 
endless stream of _different_ modules, each with their own initialisers.


I would call it a leak if something that is no longer being used cannot be 
reclaimed. The endless stream of different modules is possible in 
long-running systems where the code being run evolves or changes over time 
(e.g. something like lambdabot, which runs user-provided code).


Cheers,

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


Re: [Haskell-cafe] Re: Top Level -

2008-09-06 Thread Ganesh Sittampalam

On Sat, 6 Sep 2008, Brandon S. Allbery KF8NH wrote:


On 2008 Sep 6, at 6:10, Ashley Yakeley wrote:


The set of ACIO expressions exp is the static initialisers of M. The RTS 
must note when each static initialiser is run, and cache its result val. 
Let's call this cache of vals the static results cache of M.


When M is loaded, and a static results cache for M already exists, then it 
will be used for the vals of M.


This sounds reachable to me, and therefore static overhead and not a 
leak.


You can call it what you like, but it's still unacceptable behaviour, 
particularly since clients of M will have no way of telling from its API 
that it will happen.


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


Re: [Haskell-cafe] Re: Top Level -

2008-09-06 Thread Ganesh Sittampalam

On Sat, 6 Sep 2008, Brandon S. Allbery KF8NH wrote:

On 2008 Sep 6, at 11:22, Ganesh Sittampalam wrote:

On Sat, 6 Sep 2008, Brandon S. Allbery KF8NH wrote:

On 2008 Sep 6, at 6:10, Ashley Yakeley wrote:
The set of ACIO expressions exp is the static initialisers of M. The 
RTS must note when each static initialiser is run, and cache its result 
val. Let's call this cache of vals the static results cache of M.
When M is loaded, and a static results cache for M already exists, then 
it will be used for the vals of M.


This sounds reachable to me, and therefore static overhead and not a 
leak.


You can call it what you like, but it's still unacceptable behaviour, 
particularly since clients of M will have no way of telling from its 
API that it will happen.


You want run-once behavior without giving the runtime the ability to 
tell that it's already been run?


I don't want run-once behaviour, other people do. I'm just trying to pin 
down what it would mean.


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


Re: [Haskell-cafe] Functional references

2008-09-05 Thread Ganesh Sittampalam

On Fri, 5 Sep 2008, Jules Bean wrote:

I think it would be worth spending some time (on this mailing list, 
perhaps, or in another forum) trying to hash out a decent API which 
meets most people's requirements, rather than ending up with 4 or 5 
slightly different ones.


This sounds like a good plan, but please make sure the result is as free 
as GHC, rather than GPL like data-accessor is. It's so simple that it 
being GPL just drives people for whom licencing is an issue to write an 
alternative rather than consider complying.


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


Re: [Haskell-cafe] Top Level -

2008-09-05 Thread Ganesh Sittampalam

On Fri, 5 Sep 2008, Ashley Yakeley wrote:


Sittampalam, Ganesh wrote:

Ashley Yakeley wrote:

I really don't know enough about the RTS to know. The alternative 
would be to keep all initialised values when the module is unloaded. 
I'm guessing this is more feasible.


Easier, but a guaranteed memory leak.


But it's limited to the initialisers. An IORef holding an Integer isn't 
much memory, and it only ever gets leaked once.


It happens every time you load and unload, surely?

Also I thought this was a general discussion with Data.Unique as a 
concrete example; something else might leak substantially more memory. 
Your witnesses stuff would leak one Integer per module, wouldn't it?


Finally, any memory leak at all can be unacceptable in some contexts. It's 
certainly not something we should just dismiss as oh, it's only small.


Cheers,

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


[Haskell-cafe] Re: [Haskell] Top Level -

2008-09-02 Thread Ganesh Sittampalam

On Tue, 2 Sep 2008, Ashley Yakeley wrote:


Ganesh Sittampalam wrote:
I have a feeling it might be non-trivial; the dynamically loaded bit of 
code will need a separate copy of the module in question, since it might be 
loaded into something where the module is not already present.


Already the dynamic loader must load the module into the same address 
space and GC, i.e. the same runtime. So it should be able to make sure 
only one copy gets loaded.


I don't think it's that easy, modules aren't compiled independently of 
each other, and there are lots of cross-module optimisations and so on.


What is the status of dynamic loading in Haskell? What does hs-plugins 
do currently?


I don't know for sure, but I think it would load it twice.

In any case, what I'm trying to establish below is that it should be a 
safety property of - that the entire module (or perhaps mutually 
recursive groups of them?) can be duplicated safely - with a new name, or 
as if with a new name - and references to it randomly rewritten to the 
duplicate, as long as the result still type checks. If that's the case, 
then it doesn't matter whether hs-plugins loads it twice or not.


Let's suppose some other module uses a -, but returns things based on that 
- that are some standard type, rather than a type it defines itself. Is 
module duplication still safe?


In this case, duplicate modules of different versions is as safe as 
different modules. In other words, this situation:


 mypackage-1.0 that uses -
 mypackage-2.0 that uses -

is just as safe as this situation:

 mypackage-1.0 that uses -
 otherpackage-1.0 that uses -

The multiple versions issue doesn't add any problems.


Agreed - and I further claim that duplicating the entire module itself 
can't cause any problems.


Well, let me put it this way; since I don't like -, and I don't 
particularly mind Typeable, I wouldn't accept IOWitness as an example of 
something that requires - to implement correctly, because I don't see any 
compelling feature that you can only implement with -.


Why don't you like -? Surely I've addressed all the issues you raise?


I'm still not happy that the current specification is good enough, 
although I think this thread is getting closer to something that might 
work.


Even with a good specification for -, I would rather see the need for 
once-only state reflected in the type of things that have such a need.


There is an obligation regarding dynamic loading, but it looks like 
dynamic loading might need work anyway.


I think the obligation should be on -, and the obligation is the 
duplication rule I proposed above.


Since this is a matter of aesthetics, I imagine it will end with a list of 
pros and cons.


Agreed.

There's some unsafety somewhere in both Typeable and IOWitnesses, and in 
both cases it can be completely hidden from the user - with Typeable, just 
don't let the user define the typeOf function at all themselves. 


It's worse than that. If you derive an instance of Typeable for your 
type, it means everyone else can peer into your constructor functions 
and other internals. Sure, it's not unsafe, but it sure is ugly.


True. I would argue that this is better solved with a better typeclass 
hierarchy (e.g. one class to supply a witness-style representation that 
only supports equality, then the typereps on top of that if you want 
introspection too).


Sometimes you want to do witness equality tests rather than type equality 
tests. For instance, I might have a foo exception and a bar exception, 
both of which carry an Int. Rather than create new Foo and Bar types, I 
can just create a new witness for each.


This is precisely what newtype is designed for, IMO. We don't need another 
mechanism to handle it.


It's not what newtype is designed for. Newtype is designed to create 
usefully new types. Here, we're only creating different dummy types so 
that we can have different TypeRep values, which act as witnesses. It's 
the TypeReps that actually do the work.


newtype is frequently used to create something that you can make a 
separate set of typeclass instances for. This is no different. You can 
argue that this use of newtype is wrong, but there's no point in 
just providing an alternative in one specific case.


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


Re: [Haskell-cafe] Re: [Haskell] Top Level -

2008-09-02 Thread Ganesh Sittampalam

On Tue, 2 Sep 2008, Adrian Hey wrote:


Ganesh Sittampalam wrote:
You see this as a requirement that can be discharged by adding the ACIO 
concept; I see it as a requirement that should be communicated in the type.


Another way of looking at it is that Data.Unique has associated with it 
some context in which Unique values are safely comparable. You want that 
context to always be the top-level/RTS scope, I would like the defining 
that context to be part of the API.


But why pick on Data.Unique as special? Because I just happened to have
pointed out it uses a global variable?


Only because I thought it was the running example.

If you didn't know this I suspect this issue just wouldn't be an issue 
at all. Why haven't you raised a ticket complaining about it's API 
having the wrong type sigs? :-)


Because I don't use it, and even if I did use it I would just live with 
the API it has.



There's shed loads of information and semantic subtleties about pretty
much any operation you care to think of in the IO monad that isn't
communicated by it's type. All you know for sure is that it's weird,
because if it wasn't it wouldn't be in the IO monad.


It does actually claim a specification, namely that no two calls to 
newUnique return values that compare equal.



We have to have something concrete to discuss and this is the simplest.
Like I said there are a dozen or so other examples in the base package
last time I counted


Would you mind listing them? It might help provide some clarity to the 
discussion.


Here's what you can't find in the libs distributed with ghc. Note this
does not include all uses of unsafePerformIO. It only includes uses
to make a global variable.


Thanks. It'd probably be a good addition to the wiki page on this topic 
for these to be catalogued in terms of why they are needed, though I'm 
(probably) not volunteering to do it :-)


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


Re: [Haskell-cafe] Re: [Haskell] Top Level -

2008-09-01 Thread Ganesh Sittampalam

On Mon, 1 Sep 2008, Adrian Hey wrote:


Actually all this use of the tainted and derogatory term global
variable is causing me to be imprecise. All MVars/IORefs have global 
main/process scope whether or not they're bound to something at the

top level.


Global variable is exactly the right term to use, if we are following 
the terminology of other languages. We don't call the result of malloc/new 
etc a global variable, unless it is assigned to something with top-level 
scope.


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


Re: [Haskell-cafe] Re: [Haskell] Top Level -

2008-09-01 Thread Ganesh Sittampalam

On Mon, 1 Sep 2008, John Meacham wrote:


On Mon, Sep 01, 2008 at 10:45:05PM +0100, Ganesh Sittampalam wrote:

Actually all this use of the tainted and derogatory term global
variable is causing me to be imprecise. All MVars/IORefs have global
main/process scope whether or not they're bound to something at the
top level.


Global variable is exactly the right term to use, if we are following
the terminology of other languages. We don't call the result of
malloc/new etc a global variable, unless it is assigned to something
with top-level scope.


global variable is not a very precise term in other languages for
various platforms too a lot of times.  for instance, windows dll's have
the ability to share individual variables across all loadings of said
dll. (for better or worse.)


Interesting, is this just within a single process?

Haskell certainly has more advanced scoping capabilities than other 
languages so we need a more refined terminology. I think 'IO scope' is 
the more precise term, as it implys the scope is that of the IO monad 
state. which may or may not correspond to some external 'process scope'.


Hmm, to me that implies that if the IO monad stops and restarts, e.g. when 
a Haskell library is being called from an external library, then the scope 
stops and starts again (which I presume is not the intention of - ?)


But I don't really care that much about the name, if there is consensus on 
what to call it that doesn't cause ambiguities with OS processes etc.


Cheers,

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


Re: [Haskell-cafe] Re: [Haskell] Top Level -

2008-09-01 Thread Ganesh Sittampalam

On Mon, 1 Sep 2008, Brandon S. Allbery KF8NH wrote:


On 2008 Sep 1, at 18:08, Ganesh Sittampalam wrote:

On Mon, 1 Sep 2008, John Meacham wrote:



for instance, windows dll's have
the ability to share individual variables across all loadings of said
dll. (for better or worse.)


Interesting, is this just within a single process?


Last I checked, it was across processes; that is, every DLL has its own 
(optional) data segment which is private to the DLL but shared across 
all system-wide loaded instances of the DLL.  This actually goes back to 
pre-NT Windows.


Sounds like a recipe for fun :-)

Haskell certainly has more advanced scoping capabilities than other 
languages so we need a more refined terminology. I think 'IO scope' is the 
more precise term, as it implys the scope is that of the IO monad state. 
which may or may not correspond to some external 'process scope'.


Hmm, to me that implies that if the IO monad stops and restarts, e.g. when 
a Haskell library is being called from an external library, then the scope 
stops and starts again (which I presume is not the intention of - ?)


It tells me the flow of execution has temporarily exited the scope of the IO 
monad, but can return to it.  The state is suspended, not exited.


In that case we could equally call the things library scope, as that's 
the only scope they're visible in unless exported. Anyway, as long as 
we're clear on what it means, the name doesn't really matter.


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


Re: [Haskell-cafe] Re: [Haskell] Top Level -

2008-09-01 Thread Ganesh Sittampalam

On Mon, 1 Sep 2008, Adrian Hey wrote:


Ganesh Sittampalam wrote:
On Sun, 31 Aug 2008, Adrian Hey wrote: 

Eh? Please illustrate your point with Data.Unique. What requirements
does it place on it's context? (whatever that might mean :-)


It requires that its context initialises it precisely once.


It's context being main? If so this is true, but I don't see why this
is  a problem. [...]  Also ACIO monad properties guarantee that it's
always initialised to the same value regardless of when this occurs.
So I don't see the problem.


You see this as a requirement that can be discharged by adding the ACIO 
concept; I see it as a requirement that should be communicated in the 
type.


Another way of looking at it is that Data.Unique has associated with it 
some context in which Unique values are safely comparable. You want that 
context to always be the top-level/RTS scope, I would like the defining 
that context to be part of the API.


Data.Unique is actually a poor example, as it is actually fine to 
initialise it multiple times as long as the resulting Unique values 
aren't treated as coming from the same datatype.


I just don't see what you're getting at. There's no problem here
and Data.Unique is not special.


See the conversation with Ashley - you can have multiple copies of 
Data.Unique loaded without problem, as long as the resulting Unique 
datatypes aren't comparable with each other.



myCount :: MVar Int
myCount - newMVar 0

In a hypothetical second initialisation, do you mean..
1 - myCount somehow gets rebound to a different/new MVar


I mean this. Or, more precisely, that a *different* myCount gets bound to 
a different MVar.



But equally it can be implemented with IORefs,


Actually it couldn't as IORefs are not an Ord instance.


Well, perhaps one could be added (along with hashing). Or perhaps it's not 
really needed; I don't know as I've never used Data.Unique, and I doubt I 
ever would as when I need a name supply I also want human readable names, 
and I can't think of any other uses for it, though no doubt some exist.



so it's not a good advert for the need for global variables.


Oh please!

We have to have something concrete to discuss and this is the simplest.
Like I said there are a dozen or so other examples in the base package
last time I counted


Would you mind listing them? It might help provide some clarity to the 
discussion.


and plenty of people have found that other libs/ffi bindings need them 
for safety reasons. Or at least they need something that has global 
main/process scope and so far the unsafePerformIO hack is the only known 
way to get that and still keep APIs stable,sane and modular.


Again, some specific examples would help.


Also, AFAICS going the way that seems to be suggested of having all this
stuff reflected in the arguments/types of API is going to make it
practically impossible to have platform independent APIs if all platform
specific implementation detail has to be accounted for in this way.


It can all be wrapped up in a single abstract context argument; the only 
platform bleed would be if one platform needed a context argument but 
others didn't.



I think there are two cases to consider here.

A Data.Unique style library, which requires genuinely *internal* state, and 
which is agnostic to having multiple copies of itself loaded 
simultaneously. In that case, there is no requirement for a process-level 
scope for -, just that each instance of the library is only initialised 
once - the RTS can do this, as can any dynamic loader.


The other is some library that really cannot be safely loaded multiple 
times, because it depends on some lower-level shared resource. Such a 
library simply cannot be made safe without cooperation from the thing that 
controls that shared resource, because you cannot prevent a second copy of 
it being loaded by something you have no control over.


If the - proposal were only about supporting the first of these 
applications, I would have far fewer objections to it. But it would have 
nothing to do with process-level scope, then.


The - proposal introduces no new problems that aren't already with us.
It solves 1 problem in that at least there's no room for the compiler to
get it wrong or for people do use dangerous things when using the
unsafePerformIO hack. I think that is really the only problem that can
be solved at the level of Haskell language definition.


I just want to be clear that the second of the two categories above cannot 
be used to justify the proposal, as it does not make them safe.



I also think we need to be careful about the use of the term process.

IMO when we say the process defined by main, we are talking about an
abstract process that is essentially defined by Haskell and may have
nothing in common with a process as defined by various OS's (assuming
there's an OS involved at all). Perhaps we should try be more clear and
say Haskell process or OS process as appropriate. In particular

  1   2   >