Volunteer for a panel at HIW 2019

2019-07-26 Thread Iavor Diatchki
Hello, I am sending this on behalf of Nikki Vazou, who is organizing this year's HIW---she is looking for a volunteer to represent Haskell' on a panel, but the haskell-prime list is restricted to only members. Details are in her message below. If you are interested, please respond directly to

Re: Default module header `module Main where`

2017-05-16 Thread Iavor Diatchki
One potential difference between the two is that the current behavior allows the `Main` module to import `main` from another module, while the new behavior would fail in that case. For example, a file that has only a single line: import SomeOtherModule(main) This still seems like a fairly

Re: Default module header `module Main where`

2017-05-16 Thread Iavor Diatchki
That seems fairly reasonable to me. -Iavor On Tue, May 16, 2017 at 7:18 AM, Joachim Breitner wrote: > Hi, > > a very small proposal to be considered for Haskell': > > Currently, the report states > > An abbreviated form of module, consisting only of the module

Re: GitHub proposal repo permissions

2016-10-19 Thread Iavor Diatchki
Hi, I think Herbert added me to the correct group, thanks! On Tue, Oct 18, 2016 at 10:24 AM, David Luposchainsky via Haskell-prime < haskell-prime@haskell.org> wrote: > On 12.10.2016 19:09, Iavor Diatchki wrote: > > could someone with access fix it, maybe David > > I’m j

GitHub proposal repo permissions

2016-10-12 Thread Iavor Diatchki
Hello, I was just trying to update the `Haskel 2020` project as it is not in sync with the actual pull-requests, bit I can't see a way to do it. Am I missing something, or do I simply not have the required permissions? If this is indeed a permissions issue, could someone with access fix it

Proposal: accept tuple sections

2016-10-12 Thread Iavor Diatchki
Hello, it seems that there isn't much controversy over the TupleSections propsal, so I'd like to move the we accept it for the next language standard. Does anyone have any objections? -Iavor ___ Haskell-prime mailing list Haskell-prime@haskell.org

Process question

2016-10-04 Thread Iavor Diatchki
Hello, Now that we've started with a few proposal, I am realizing that I have no idea how to proceed from here. In particular: 1. How would I request I proposal to be rejected 2. How would I request that a proposal be accepted Ideas? -Iavor ___

Re: Step-by-step guide for creating a new proposal

2016-10-04 Thread Iavor Diatchki
-prime < haskell-prime@haskell.org> wrote: > On 04.10.2016 01:27, Iavor Diatchki wrote: > > During our Haskell Prime lunch meeting at ICFP, I promised to create a > detailed > > step-by-step guide for creating Haskell Prime proposals on GitHub. The > > instr

Step-by-step guide for creating a new proposal

2016-10-03 Thread Iavor Diatchki
Hello, During our Haskell Prime lunch meeting at ICFP, I promised to create a detailed step-by-step guide for creating Haskell Prime proposals on GitHub. The instructions are now available here: https://github.com/yav/rfcs/blob/instructions/step-by-step-instructions.md Please have a look and

Re: minutes from committee meeting at ICFP

2016-10-02 Thread Iavor Diatchki
Hello, I just got back to the US, and have started uploading videos in earnest. Hopefully, I'll get to the Haskell Symposium pretty soon, and the whole discussion was recorded so that everyone can listen to it. I started taking notes at the beginning of the discussion, but then got distracted,

Re: Limber separators

2016-05-12 Thread Iavor Diatchki
On Sat, May 7, 2016 at 1:44 AM, Jon Fairbairn wrote: > > > The one this violates is “never make language design decisions > to work around deficiencies in tools” The problem is that diff > does its work in ignorance of the syntax and consequently > produces poor

Re: Scope of committee (can we do *new* things?)

2016-05-12 Thread Iavor Diatchki
I disagree that we should be standardizing language features that have not been implemented. I think having an implementation is important because: 1. the act of implementing a feature forces you to work out details that you may not have thought of ahead of time. For example, for a small

Re: The GADT debate

2016-05-08 Thread Iavor Diatchki
Hello, what is the state with the semantic specification of GADTs? I am wondering if they fit in the usual CPO-style semantics for Haskell, or do we need some more exotic mathematical structure to give semantics to the language. -Iavor On Sun, May 8, 2016 at 8:36 AM, Carter Schonwald

Re: Are there GHC extensions we'd like to incorporate wholesale?

2016-05-03 Thread Iavor Diatchki
Hello, I think it'd be great to get started by specifying a few simple extensions, such as the ones Lennart listed. Even though they are very well understood, and we have text about them in the GHC manual, we'd still have to think of how to integrate their descriptions with the rest of the

Re: relaxing instance declarations

2013-04-29 Thread Iavor Diatchki
Hello, I think that if we want something along those lines, we should consider a more general construct that allows declarations to scope over other declarations (like SML's `local` construct). It would be quite arbitrary to restrict this only to instances. -Iavor On Mon, Apr 29, 2013 at

Re: What is a punctuation character?

2012-03-20 Thread Iavor Diatchki
, Iavor Diatchki iavor.diatc...@gmail.com wrote: Hello, I am also not an expert but I got curious and did a bit of Wikipedia reading.  Based on what I understood, here are two (related) questions that it might be nice to clarify in a future version of the report: 1. What is the alphabet used

Re: What is a punctuation character?

2012-03-16 Thread Iavor Diatchki
Hello, I am also not an expert but I got curious and did a bit of Wikipedia reading. Based on what I understood, here are two (related) questions that it might be nice to clarify in a future version of the report: 1. What is the alphabet used by the grammar in the Haskell report? My

Re: FW: 7.4.1-pre: Show Integral

2011-12-24 Thread Iavor Diatchki
Hello, The discussion on the libraries list is archived here: http://www.haskell.org/pipermail/libraries/2011-September/016699.html There hasn't been a corresponding discussion for Haskell Prime so, technically, GHC deviates from the standard. -Iavor On Fri, Dec 23, 2011 at 9:41 AM, Simon

Re: TypeFamilies vs. FunctionalDependencies type-level recursion

2011-08-07 Thread Iavor Diatchki
Hello, On Tue, Aug 2, 2011 at 6:10 PM, Simon Peyton-Jones simo...@microsoft.com wrote: Julien: we should start a wiki page (see http://hackage.haskell.org/trac/ghc/wiki/Commentary, and look for the link to Type level naturals; one like that).  On the wiki you should  * add a link to the

Re: TypeFamilies vs. FunctionalDependencies type-level recursion

2011-07-30 Thread Iavor Diatchki
Helllo, On Sat, Jul 30, 2011 at 2:11 AM, o...@okmij.org wrote: Second, what is the status of Nat kinds and other type-level data that Conor was/is working on? Nat kinds and optimized comparison of Nat kinds would be most welcome. Type level lists are better still (relieving us from

Re: TypeFamilies vs. FunctionalDependencies type-level recursion

2011-06-15 Thread Iavor Diatchki
Hello, On Wed, Jun 15, 2011 at 10:49 AM, dm-list-haskell-pr...@scs.stanford.eduwrote: At Wed, 15 Jun 2011 10:10:14 -0700, Iavor Diatchki wrote: Hello, On Wed, Jun 15, 2011 at 12:25 AM, Simon Peyton-Jones simo...@microsoft.com wrote: | class C a b | a - b where

Re: In opposition of Functor as super-class of Monad

2011-01-05 Thread Iavor Diatchki
Hi, indeed, this is called ap in Control.Monad. So if we have an instance of Monad, all that needs to be done to support the other instances is: instance (SameContextAsTheMonadInstance) = Functor MyType where fmap = liftM instance (SameContextAsTheMonadInstance) = Applicative MyType where pure =

Re: PROPOSAL: Include record puns in Haskell 2011

2010-02-26 Thread Iavor Diatchki
Hello, In order to keep the discussion structured I have created two tickets in the haskell-prime trac system (http://hackage.haskell.org/trac/haskell-prime): * Proposal 1: Add pre-Haskell'98 style punning and record disambiguation (ticket #136) * Proposal 2: Add record-wildcards (ticket

PROPOSAL: Include record puns in Haskell 2011

2010-02-24 Thread Iavor Diatchki
Hello, (Malcolm, sorry for the double post, I forgot to CC the list) I was thinking mostly about the old-time-y punning, where I can write a label, say theField, and it automatically gets expanded to theField = theField, in record patterns and record constructing expressions. The only corner case

Re: [Haskell] Nominations for the Haskell 2011 committee

2009-12-29 Thread Iavor Diatchki
Hello, I would like to participate in the design of Haskell 2011. I have used Haskell for about 10 years, commercially at Galois Inc, for the last 3. I have a good understanding of all parts of the language and various implementations, and I have a particular interest in its type system and

Re: Unsafe hGetContents

2009-10-10 Thread Iavor Diatchki
Hello, well, I think that the fact that we seem to have a program context that can distinguish f1 from f2 is worth discussing because I would have thought that in a pure language they are interchangable. The question is, does the context in Oleg's example really distinguish between f1 and f2?

Re: Proposals and owners

2009-08-08 Thread Iavor Diatchki
I thought that the intended semantics was supposed to be that the only element is bottom (hence the proposal to add a related empty case construct)? On Thu, Aug 6, 2009 at 3:49 PM, Ross Patersonr...@soi.city.ac.uk wrote: On Wed, Jul 29, 2009 at 02:34:26PM -0400, Stephanie Weirich wrote: Ok,

Re: Proposals and owners

2009-07-31 Thread Iavor Diatchki
+1. I completely agree. On Fri, Jul 31, 2009 at 6:04 PM, Lennart Augustssonlenn...@augustsson.net wrote: I think that a natural extension to allowing empty data declarations would be to allow empty case expressions. On Wed, Jul 29, 2009 at 7:34 PM, Stephanie Weirichsweir...@cis.upenn.edu

Re: StricterLabelledFieldSyntax

2009-07-26 Thread Iavor Diatchki
Hello, I am strongly against this change. The record notation works just fine and has been doing so for a long time. The notation is really not that confusing and, given how records work in Haskell, makes perfect sense (and the notation has nothing to do with the precedence of application

Re: StricterLabelledFieldSyntax

2009-07-26 Thread Iavor Diatchki
Hello, On Sun, Jul 26, 2009 at 10:01 PM, Isaac Dupreem...@isaac.cedarswampstudios.org wrote: Iavor Diatchki wrote: Hello, I am strongly against this change.  The record notation works just fine and has been doing so for a long time.  The notation is really not that confusing and, given how

Re: Proposal: Deprecate ExistentialQuantification

2009-07-23 Thread Iavor Diatchki
Hello, Sorry for responding so late---I just saw the thread. I don't think that we should deprecate the usual way to define existentials. While the GADT syntax is nice in some cases, there are also examples when it is quite verbose. For example, there is a lot of repetition in datatypes that

Re: Proposal: Deprecate ExistentialQuantification

2009-07-23 Thread Iavor Diatchki
, KindSignatures #-} module GADT where data Foo :: * - * where  Foo :: Int - Foo Int Iavor Diatchki wrote: Hello, Sorry for responding so late---I just saw the thread.  I don't think that we should deprecate the usual way to define existentials.  While the GADT syntax is nice in some cases

Re: what about moving the record system to an addendum?

2009-07-07 Thread Iavor Diatchki
Hello, I do not think that we should remove the current record/named fields syntax, at least for the moment. I use it a lot, and I do not want to add extra pragmas or extensions to my cabal file. In fact, one of the purposes of Haskell', the way I understand it, is exactly to just choose a

Re: Mutually-recursive/cyclic module imports

2008-09-01 Thread Iavor Diatchki
Hi, a free copy is available at: http://www.purely-functional.net/yav/publications/modules98.pdf (the source code, is also available at the same site). Hope that this helps, -Iavor On Tue, Aug 26, 2008 at 4:33 PM, John Meacham [EMAIL PROTECTED] wrote: On Tue, Aug 26, 2008 at 04:31:33PM -0700,

Re: PROPOSAL: Make Applicative a superclass of Monad

2008-06-29 Thread Iavor Diatchki
Hello, I think that this is a good change to make, and I don't think that it is in any way related to the introduction of class aliases, which is a fairly major extension (i.e., it requires changes to the compiler), that we have no experience with, and whose design has not really be tried out in

Re: The monomorphism restriction and monomorphic pattern bindings

2008-04-28 Thread Iavor Diatchki
Hi, On Mon, Apr 28, 2008 at 9:42 AM, Simon Marlow [EMAIL PROTECTED] wrote: Ok. So I counter-propose that we deal with pattern bindings like this: The static semantics of a pattern binding are given by the following translation. A binding 'p = e' has the same meaning as the set of

Re: RFC: qualified vs unqualified names in defining instance methods

2008-04-26 Thread Iavor Diatchki
Hello, On Fri, Apr 25, 2008 at 3:00 PM, Simon Marlow [EMAIL PROTECTED] wrote: ... It would be slightly strange if record construction required the unqualified name, but record update required the qualified name, when the field name is only in scope qualified. So that indicates that we

Re: RFC: qualified vs unqualified names in defining instance methods

2008-04-25 Thread Iavor Diatchki
Hello, I think that the H98 change was a good one. Qualified names should only be used in _uses_ of variables (to disambiguate) and not in definitions because (hopefully) there is nothing to disambiguate in a definition. By the way, method definitions already have a distinction between what is

Re: The monomorphism restriction and monomorphic pattern bindings

2008-04-23 Thread Iavor Diatchki
Hello, Removing the MR seems reasonable. I am a little less certain about the MPB rule though. I suspect that, as the wiki page points out, many uses of pattern bindings are monomorphic but still, there seem to be a number of examples on the wiki where people have run into this problem. So I am

Re: Status of Haskell Prime Language definition

2007-10-16 Thread Iavor Diatchki
Hello, On 10/16/07, apfelmus [EMAIL PROTECTED] wrote: Iavor Diatchki wrote: apfelmus wrote: fundeps are too tricky to get powerful and sound at the same time. I am not aware of any soundness problems related to functional dependencies---could you give an example? http

Re: Make it possible to evaluate monadic actions when assigningrecord fields

2007-07-16 Thread Iavor Diatchki
Hello, I find the naming of values that is introduced by the do notation useful and I am not at all convinced that the extra sugar that is being proposed here makes the language simpler. It seems to me that the only way to know that a piece of code is safe would be to: i) do the translation in

Re: default fixity for `quotRem`, `divMod` ??

2007-06-18 Thread Iavor Diatchki
Hi, This seems like a good idea. We should make sure that we are writing down such bugfixes somewhere besides the mailing list so that they do not get lost. -Iavor On 6/18/07, Isaac Dupree [EMAIL PROTECTED] wrote: -BEGIN PGP SIGNED MESSAGE- Hash: SHA1 I was just bitten in ghci by

Re: Wanted: warning option for usages of unary minus

2007-05-14 Thread Iavor Diatchki
Hello, I agree with Simon on this one: x-1 should parse as expected (i.e., the infix operator - applied to two arguments x and 1). Having this result in a type error would be confusing to both beginners and working Haskell programmers. I think that if we want to change anything at all, we

Polymorphic strict fields

2007-04-30 Thread Iavor Diatchki
Hello, At present, the Haskell report specifies the semantics of strict datatype fields (the ones marked with !) in terms of the strict application operator $! [Section 4.2.1, paragraph Strictness flags]. However, if we were to add polymorphic fields to Haskell, then we cannot use this

Re: type aliases and Id

2007-03-19 Thread Iavor Diatchki
Hello, On 3/19/07, Lennart Augustsson [EMAIL PROTECTED] wrote: Ravi, Ganesh and I were discussing today what would happen if one adds Id as a primitive type constructor. How much did you have to change the type checker? Presumably if you need to unify 'm a' with 'a' you now have to set m=Id.

Re: do-and-if-then-else modification

2007-02-19 Thread Iavor Diatchki
Hello, On 2/18/07, Benjamin Franksen [EMAIL PROTECTED] wrote: Section 3.6 Conditionals would have to be changed accordingly. It still says exp - if exp1 then exp2 else exp3. Thanks! I fixed this too. Just for the record, I don't think that this change is particularly useful at all. We

Re: rank-2 vs. arbitrary rank types

2007-02-06 Thread Iavor Diatchki
Hello, Thanks for the responses! Here are my replies (if the email seems too long please skip to the last 2 paragraphs) Simon PJ says: Hmm. To be consistent, then, you'd have to argue for rank-2 data constructors only, since rank-2 functions can be simulated in the way you describe. I

Re: rank-2 vs. arbitrary rank types

2007-02-03 Thread Iavor Diatchki
Hello, (I'll respond on this thread as it seems more appropriate) Simon PJ's says: * Rank-N is really no harder to implement than rank-2. The Practical type inference.. paper gives every line of code required. The design is certainly much cleaner and less ad-hoc than GHC's old rank-2 design,

Polymorphic components, so far

2007-02-01 Thread Iavor Diatchki
Hello, Thanks to everyone who took time to comment on my notes. My Isaac's previous post spawned a few separate discussions so I though I'd send a separate message to summarize the status of what has happened so far with regard to polymorphic components. * Rank-2 vs Rank-n types. I think that

Re: Polymorphic components, so far

2007-02-01 Thread Iavor Diatchki
Hello, (Apologies for the two emails, I accidentally hit the send button on my client before I had finished the first e-mail...) * Rank-2 vs Rank-n types. I think that this is the most important issue that we need to resolve which is why I am placing it first :-) Our options (please feel free

Polymorphic Components

2007-01-21 Thread Iavor Diatchki
Hello, I have written some notes about changes to Haskell 98 that are required to add the polymorphic components extension. The purpose of the notes is to enumerate all the details that need to be specified in the Haskell report. I don't have access to the haskell-prime wiki so I attached the

Re: Are pattern guards obsolete?

2006-12-13 Thread Iavor Diatchki
Hi, I am not clear why you think the current notation is confusing... Could you give a concrete example? I am thinking of something along the lines: based on how - works in list comprehensions and the do notation, I would expect that pattern guards do XXX but instead, they confusingly do YYY.

Re: character literal question

2006-12-02 Thread Iavor Diatchki
Hello, It does actually make syntax hilighting more complex, and introduces another special case. How is that another special case? If anything, it seems to be removing a special case because there is no need for an escape of the form \'. Do you have a concrete example of what it complicates?

character literal question

2006-12-01 Thread Iavor Diatchki
Hello, Is there a reason why we have to escape the character ' (apostrophe) when used in a character literal? For example, we have to write '\'' instead of '''. (With syntax highlighting, the second is a lot better looking than the first.) It seems that in this case we do not need the escape

Re: Teaching

2006-11-30 Thread Iavor Diatchki
Hello, On 11/30/06, Philippa Cowderoy [EMAIL PROTECTED] wrote: On Wed, 29 Nov 2006, Ashley Yakeley wrote: That something might confuse the beginning user should count for nothing if it does not annoy the more experienced user. This experienced user regularly uses a haskell interpreter for

Re: Re[2]: Teaching

2006-11-30 Thread Iavor Diatchki
Hello, On 11/30/06, Bulat Ziganshin [EMAIL PROTECTED] wrote: Hello Iavor, how about using Haskell for scripting? i find it as great alternative to perl/ruby, particularly because i don't want to remember two languages, particularly because of great data processing instruments I am

Re: digit groups

2006-10-25 Thread Iavor Diatchki
Hello, while people are discussing different notations for literals, I thought I should mention that in my work I have found it useful to write literals ending in K (kilo), M (mega) or G (giga) for large numbers. For example, I can write 4K for (4 * 2^10), or 8M for (8 * 2^20) or 2G for (2 *

Re: Monomorphism restriction

2006-10-14 Thread Iavor Diatchki
Hello, On 10/14/06, Bulat Ziganshin [EMAIL PROTECTED] wrote: Hello haskell-prime, first is the monomorphism restriction. why isn't it possible to check _kind_ of parameter-less equation and apply monomorphism restrictions only to values of kind '*'? so, this: sum = foldr1 (*) will become

Re: Proposal for stand-alone deriving declarations?

2006-10-05 Thread Iavor Diatchki
Hello, A question about the syntax: would there be a problem if we made the 'deriving' declaration look like an instance? Then we would not need the special identifier 'for', and also we have a more standard looking notation. I am thinking something like: deriving Show SomeType deriving Eq

Re: Pattern guards

2006-09-28 Thread Iavor Diatchki
Hello, I think that pattern guards are a nice generalization of ordinary guards and they should be added to the language. Of course, as you point out, we can encode them using the Maybe monad, but the same is true for nested patterns, and I don't think that they should be removed from Haskell.

Re: Re[2]: Pattern guards

2006-09-28 Thread Iavor Diatchki
Hello, This particular example we can do with pattern guards (although it seems that a simple 'case' is more appropriate for this example) On 9/28/06, Bulat Ziganshin [EMAIL PROTECTED] wrote: Hello Conor, Thursday, September 28, 2006, 10:30:46 PM, you wrote: gcd x y | compare x y - LT

Re: map and fmap

2006-08-28 Thread Iavor Diatchki
Hello, On 8/28/06, John Hughes [EMAIL PROTECTED] wrote: No, map was never overloaded--it was list comprehensions that were overloaded as monad comprehensions in Haskell 1.4. That certainly did lead to problems of exactly the sort John M is describing. I just checked the reports for Haskell

Re: map and fmap

2006-08-23 Thread Iavor Diatchki
Hello, On 8/22/06, John Meacham [EMAIL PROTECTED] wrote: I am not talking about type signatures, I am talking about having to annotate in the middle of a term. f x y | x `member` map g freeVars y = having to become f x y | x `member` map g (freeVars y :: [Id]) = There is no

Re: map and fmap

2006-08-22 Thread Iavor Diatchki
Hello, I agree that this is a small change, and I don't expect that it will happen. On 8/21/06, John Meacham [EMAIL PROTECTED] wrote: Yeah, the change doesn't seem worth it to me. And I still have concerns about ambiguity errors, if a beginner ever has to use an explicit type signature it sort

map and fmap

2006-08-14 Thread Iavor Diatchki
Hello, I never liked the decision to rename 'map' to 'fmap', because it introduces two different names for the same thing (and I find the name `fmap' awkward). As far as I understand, this was done to make it easier to learn Haskell, by turning errors like Cannot discharge constraint 'Functor X'

Re: termination for FDs and ATs

2006-05-03 Thread Iavor Diatchki
Hello, On 5/3/06, Stefan Wehr [EMAIL PROTECTED] wrote: class C a class F a where type T a instance F [a] where type T [a] = a class (C (T a), F a) = D a where m :: a - Int instance C a = D [a] where m _ = 42 If you now try to derive D [Int], you get ||- D

Re: FDs and confluence

2006-04-15 Thread Iavor Diatchki
Hello, On 4/13/06, Ross Paterson [EMAIL PROTECTED] wrote: They are equivalent, but C [a] b d, Num c and C [a] c d, Num c are not. I agree that this is the case if you are thinking of forall a b c d. (C [a] b d, Num c) = (C [a] c d, Num c) Here is a counter example (assume we also add an

Re: FDs and confluence

2006-04-13 Thread Iavor Diatchki
Hello, On 4/12/06, Claus Reinke [EMAIL PROTECTED] wrote: that's why Ross chose a fresh variable in FD range position: in the old translation, the class-based FD improvement rule no longer applies after reduction because there's only one C constraint left, and the instance-based FD improvement

Haskell prime wiki

2006-04-13 Thread Iavor Diatchki
Hello, The wiki page says that we should alert the committee about inaccuracies etc of pages, so here are some comments about the page on FDs (http://hackage.haskell.org/trac/haskell-prime/wiki/FunctionalDependencies) 1) The example for non-termination can be simplified to: f = \x y - (x .*.