import Module qualified as

2012-08-30 Thread Christian Maeder

Hi,

my import lists would look much nicer und could be sorted more easily
if the keyword qualified could be placed before the as keyword 
instead of after import.


Therefore I suggest the alternative syntax:

 import Data.Map qualified as Map

This should be fairly simple to implement, if more users would want it.

Note, that this syntax does not work well without as since a list of 
names to be imported usually follows the module name. Also, usually 
qualified imports are used together with as to avoid the long module 
names.


Apart from sorting it would also avoid quirks like _eleven_ spaces in:

import qualified Data.Map as Map
import   Data.Map (Map)

Cheers Christian

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


Re: Please apply the comparison function given to nubBy to elements of the list in the order in which they occur in the list.

2011-09-28 Thread Christian Maeder

In case you further want to discuss this, I've re-opened
http://hackage.haskell.org/trac/ghc/ticket/2528#comment:10

So, I'm against your proposal, Cale, but suggest that you revert the 
order in your example (if you want to exploit this behavior).


Cheers Christian

Am 08.09.2011 02:07, schrieb Cale Gibbard:

I just tried this in ghci-7.0.3:

ghci  nubBy (=) [1,2,3,4]
[1]

Think about what this is doing: it is excluding 2 from the list
because 2= 1, rather than including it because 1= 2 fails.

I think an important convention when it comes to higher order
functions on lists is that to the extent which is possible, the
function parameters take elements from the list (or things computed
from those) in the order in which they occur in the original list.

If we reimplement it in the obvious way:
ghci  let nubBy f [] = []; nubBy f (x:xs) = x : filter (not . f x) (nubBy f xs)
ghci  nubBy (=) [1,2,3,4]
[1,2,3,4]

I'm aware that the Report (strangely!) explicitly leaves the behaviour
of nubBy unspecified for functions which are not equivalence
relations, but the behaviour given by the Report implementation (the
opposite of the current behaviour in GHC) is useful and desirable
nonetheless.

I'm sure I've written about this before. I'm not entirely sure what
happened to the previous thread of discussion about this, but it just
came up again for me, and I decided that I was sufficiently irritated
by it to post again.

Another thing perhaps worth pointing out is that the parameters to
mapAccumR have always been backwards (compare it with foldr). Few
enough people use this function that I'm fairly sure we could just
change it without harm.

  - Cale


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


Re: Please apply the comparison function given to nubBy to elements of the list in the order in which they occur in the list.

2011-09-21 Thread Christian Maeder

Am 20.09.2011 20:21, schrieb Edward Kmett:
[...]

I would suggest you rephrase this as a formal proposal, then I can
happily vote +1.


Seeing the wonderful interrelation between elem, nub, nubBy and i.e.

  unionBy eq xs ys =  xs ++ foldl (flip (deleteBy eq)) (nubBy eq ys) xs

  intersectBy eq xs ys =  [x | x - xs, any (eq x) ys]

(note that any (eq x) could be elemBy eq)

I see hardly a chance to make a sensible proposal.

I think, it is wrong to change the implementation of elem and 
notElem since I expect the key to be the first argument of the 
eq-comparison (in contrast to the REPORT_PRELUDE!).


But this all would not matter if the eq-function are always symmetric, 
which may be not the case in practise. So a change could break existing 
code.



I'd also suggest rephrasing rhe mapAccumR as a formal proposal. I'm not
sure yet of whether or not I'd be behind that one, but make both
proposals separately, so they can pass individually.


I also don't see a relation to mapAccumR, so why don't you make such a 
separate proposal?


C.

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


Re: Please apply the comparison function given to nubBy to elements of the list in the order in which they occur in the list.

2011-09-20 Thread Christian Maeder

Looking at the code of nubBy
http://www.haskell.org/ghc/docs/latest/html/libraries/base-4.4.0.0/src/Data-List.html#nubBy

nubBy   :: (a - a - Bool) - [a] - [a]
#ifdef USE_REPORT_PRELUDE
nubBy eq [] =  []
nubBy eq (x:xs) =  x : nubBy eq (filter (\ y - not (eq x y)) xs)
#else
nubBy eq l  = nubBy' l []
  where
nubBy' [] _ = []
nubBy' (y:ys) xs
   | elem_by eq y xs = nubBy' ys xs
   | otherwise   = y : nubBy' ys (y:xs)

-- Not exported:
-- Note that we keep the call to `eq` with arguments in the
-- same order as in the reference implementation
-- 'xs' is the list of things we've seen so far,
-- 'y' is the potential new element
elem_by :: (a - a - Bool) - a - [a] - Bool
elem_by _  _ [] =  False
elem_by eq y (x:xs) =  y `eq` x || elem_by eq y xs
#endif

I see that the USE_REPORT_PRELUDE version corresponds to your proposal, 
but the actual implementation (based on elem_by) behaves differently 
despite the same order comment!


Therefore I support your proposal to change y `eq` x in elem_by (and 
possibly improve the documentation).


Cheers Christian

Am 08.09.2011 02:07, schrieb Cale Gibbard:

I just tried this in ghci-7.0.3:

ghci  nubBy (=) [1,2,3,4]
[1]

Think about what this is doing: it is excluding 2 from the list
because 2= 1, rather than including it because 1= 2 fails.

I think an important convention when it comes to higher order
functions on lists is that to the extent which is possible, the
function parameters take elements from the list (or things computed
from those) in the order in which they occur in the original list.

If we reimplement it in the obvious way:
ghci  let nubBy f [] = []; nubBy f (x:xs) = x : filter (not . f x) (nubBy f xs)
ghci  nubBy (=) [1,2,3,4]
[1,2,3,4]

I'm aware that the Report (strangely!) explicitly leaves the behaviour
of nubBy unspecified for functions which are not equivalence
relations, but the behaviour given by the Report implementation (the
opposite of the current behaviour in GHC) is useful and desirable
nonetheless.

I'm sure I've written about this before. I'm not entirely sure what
happened to the previous thread of discussion about this, but it just
came up again for me, and I decided that I was sufficiently irritated
by it to post again.

Another thing perhaps worth pointing out is that the parameters to
mapAccumR have always been backwards (compare it with foldr). Few
enough people use this function that I'm fairly sure we could just
change it without harm.

  - Cale


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


Re: Please apply the comparison function given to nubBy to elements of the list in the order in which they occur in the list.

2011-09-20 Thread Christian Maeder
Apologies for responding to myself, but the difference between the 
REPORT_PRELUDE and the ghc implementation also applies to elem and notElem.


#ifdef USE_REPORT_PRELUDE
elem x  =  any (== x)
notElem x   =  all (/= x)
#else
elem _ []   = False
elem x (y:ys)   = x==y || elem x ys

notElem _ []=  True
notElem x (y:ys)=  x /= y  notElem x ys
#endif

So the proposal should be to swap the arguments in x==y and x /= y 
(above) which would also fix the nub implementation!


C.

Am 20.09.2011 13:46, schrieb Christian Maeder:

Looking at the old tickets
http://hackage.haskell.org/trac/ghc/ticket/2528
http://hackage.haskell.org/trac/ghc/ticket/3280

the USE_REPORT_PRELUDE version of nub is also different
from the implementation, but both variants fulfill nub = nubBy (==)
(the prelude version by definition).

So when we change the nubBy implmentation we also need to change the nub
implementation (which is more difficult, because it uses elem).

Cheers Christian

Am 20.09.2011 12:59, schrieb Christian Maeder:

Looking at the code of nubBy
http://www.haskell.org/ghc/docs/latest/html/libraries/base-4.4.0.0/src/Data-List.html#nubBy



nubBy :: (a - a - Bool) - [a] - [a]
#ifdef USE_REPORT_PRELUDE
nubBy eq [] = []
nubBy eq (x:xs) = x : nubBy eq (filter (\ y - not (eq x y)) xs)
#else
nubBy eq l = nubBy' l []
where
nubBy' [] _ = []
nubBy' (y:ys) xs
| elem_by eq y xs = nubBy' ys xs
| otherwise = y : nubBy' ys (y:xs)

-- Not exported:
-- Note that we keep the call to `eq` with arguments in the
-- same order as in the reference implementation
-- 'xs' is the list of things we've seen so far,
-- 'y' is the potential new element
elem_by :: (a - a - Bool) - a - [a] - Bool
elem_by _ _ [] = False
elem_by eq y (x:xs) = y `eq` x || elem_by eq y xs
#endif

I see that the USE_REPORT_PRELUDE version corresponds to your proposal,
but the actual implementation (based on elem_by) behaves differently
despite the same order comment!

Therefore I support your proposal to change y `eq` x in elem_by (and
possibly improve the documentation).

Cheers Christian

Am 08.09.2011 02:07, schrieb Cale Gibbard:

I just tried this in ghci-7.0.3:

ghci nubBy (=) [1,2,3,4]
[1]

Think about what this is doing: it is excluding 2 from the list
because 2= 1, rather than including it because 1= 2 fails.

I think an important convention when it comes to higher order
functions on lists is that to the extent which is possible, the
function parameters take elements from the list (or things computed
from those) in the order in which they occur in the original list.

If we reimplement it in the obvious way:
ghci let nubBy f [] = []; nubBy f (x:xs) = x : filter (not . f x)
(nubBy f xs)
ghci nubBy (=) [1,2,3,4]
[1,2,3,4]

I'm aware that the Report (strangely!) explicitly leaves the behaviour
of nubBy unspecified for functions which are not equivalence
relations, but the behaviour given by the Report implementation (the
opposite of the current behaviour in GHC) is useful and desirable
nonetheless.

I'm sure I've written about this before. I'm not entirely sure what
happened to the previous thread of discussion about this, but it just
came up again for me, and I decided that I was sufficiently irritated
by it to post again.

Another thing perhaps worth pointing out is that the parameters to
mapAccumR have always been backwards (compare it with foldr). Few
enough people use this function that I'm fairly sure we could just
change it without harm.

- Cale


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


Proposal: add ghc -fwarn-non-ascii warning flag

2011-04-07 Thread Christian Maeder

similar in spirit to the -fwarn-tabs warning.

C.

P.S. In the mean time you may use 
http://projects.haskell.org/style-scanner/ (Caveat, it crashes on latin1 
files when compiled with ghc-6.12 or greater.)



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


Re: [Colin Paul Adams] Re: Proposal: Define UTF-8 to be the encoding of Haskell source files

2011-04-07 Thread Christian Maeder

Am 07.04.2011 13:09, schrieb Roel van Dijk:

Please take a look at the following file:
http://code.haskell.org/numerals/src/Text/Numeral/Language/ZH.hs


Great, that file made my firefox open infinitely many tabs (so that I 
had to close it).


C.

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


Re: [Colin Paul Adams] Re: Proposal: Define UTF-8 to be the encoding of Haskell source files

2011-04-07 Thread Christian Maeder

Am 07.04.2011 13:09, schrieb Roel van Dijk:

Please take a look at the following file:
http://code.haskell.org/numerals/src/Text/Numeral/Language/ZH.hs


The code would not suffer much if it were pure ASCII. I would prefer 
(ascii) haddock links to explain the various code points.


C.

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


Re: Propsal: NoDatatypeContexts

2010-07-20 Thread Christian Maeder
Christian Maeder schrieb:
 Ian Lynagh schrieb:
[...]
 http://hackage.haskell.org/trac/haskell-prime/wiki/NoDatatypeContexts
 
 I'm for this proposal, although I've got an example where I need this
 context, namely for DrIFT to derive a proper context for instances.
 
 DrIFT doesn't know that the Read instance for Data.Set.Set relies on Ord
 of the elements. For
 
 data Ord symbol = ExtSign sign symbol = ExtSign
   { plainSign :: sign
   , nonImportedSymbols :: Set.Set symbol
   } deriving Show
 
 DrIFT cannot derive the Read (or our deserialization) instance without
 the Ord symbol = context.

It would be interesting to know (or if at all) i.e. uniplate (proposed
for the haskell platform) or other generic stuff can handle this case
(as alternative to DrIFT).

A short look at http://www.haskell.org/haskellwiki/Uniplate did not
immediate help on this matter.

Template Haskell may be possible, too.

Can some expert for generic programming elaborate on this? (I once had a
good paper comparing the various approaches, but I can no longer find it.)

Pointers are welcome.

Cheers Christian

 
 However, ghc is able by deriving (Show, Read) to see
 
 instance (Ord symbol, Read sign, Read symbol) =
  Read (ExtSign sign symbol)
 
 without the context.
 
 Cheers Christian
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Propsal: NoDatatypeContexts

2010-07-20 Thread Christian Maeder
José Pedro Magalhães schrieb:
 Hello all,
 
 DrIFT cannot derive the Read (or our deserialization) instance without
 the Ord symbol = context.
 
 That's because DrIFT is simply copying this context to the Read
 instance, right? Perhaps the best way to do it would be to copy the
 context of the Read instance for Set and use that instead (though I know
 that DrIFT does not have access to that).
 
 It would be interesting to know (or if at all) i.e. uniplate (proposed
 for the haskell platform) or other generic stuff can handle this case
 (as alternative to DrIFT).
 
 From what I know, most generic programming approaches simply ignore
 constrained datatypes. I thought about them in the design of a generic
 programming library for replacing the Haskell deriving mechanism [1]. I
 think it's easy to support them, but actually we don't support them,
 since we also think they are not used very often and should disappear.

I agree, that the context on datatypes should be ignored and disappear.
But I still want to derive a deserialization instance (like for Read)
with the proper context (i.e. without manual interaction) from the
component types (like ghc can somehow by deriving Read if Data.Set.Set
is a type component).

Thanks Christian

 
 
 Cheers,
 Pedro
 
 [1] José Pedro Magalhães, Atze Dijkstra, Johan Jeuring, and Andres Löh.
 A generic deriving mechanism for Haskell.
 http://dreixel.net/research/pdf/gdmh_draft.pdf (see Section 7.1 for the
 discussion on constrained datatypes)
 
 
 On Tue, Jul 20, 2010 at 10:46, Christian Maeder
 christian.mae...@dfki.de mailto:christian.mae...@dfki.de wrote:
 
 Christian Maeder schrieb:
  Ian Lynagh schrieb:
 [...]
 
 http://hackage.haskell.org/trac/haskell-prime/wiki/NoDatatypeContexts
 
  I'm for this proposal, although I've got an example where I need this
  context, namely for DrIFT to derive a proper context for instances.
 
  DrIFT doesn't know that the Read instance for Data.Set.Set relies
 on Ord
  of the elements. For
 
  data Ord symbol = ExtSign sign symbol = ExtSign
{ plainSign :: sign
, nonImportedSymbols :: Set.Set symbol
} deriving Show
 
  DrIFT cannot derive the Read (or our deserialization) instance without
  the Ord symbol = context.
 
 It would be interesting to know (or if at all) i.e. uniplate (proposed
 for the haskell platform) or other generic stuff can handle this case
 (as alternative to DrIFT).
 
 A short look at http://www.haskell.org/haskellwiki/Uniplate did not
 immediate help on this matter.
 
 Template Haskell may be possible, too.
 
 Can some expert for generic programming elaborate on this? (I once had a
 good paper comparing the various approaches, but I can no longer
 find it.)
 
 Pointers are welcome.
 
 Cheers Christian
 
 
  However, ghc is able by deriving (Show, Read) to see
 
  instance (Ord symbol, Read sign, Read symbol) =
   Read (ExtSign sign symbol)
 
  without the context.
 
  Cheers Christian
 ___
 Haskell-prime mailing list
 Haskell-prime@haskell.org mailto:Haskell-prime@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-prime
 
 
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Propsal: NoDatatypeContexts

2010-07-19 Thread Christian Maeder
Ian Lynagh schrieb:
 Hi all,
 
 H98 and H2010 allow a context to be given for datatypes, e.g. the
 Eq a in
 
 data Eq a = Foo a = Constr a
 
 I have made a proposal to remove support for that context (ticket #139).
 More details are on the proposal wiki page:
 
 http://hackage.haskell.org/trac/haskell-prime/wiki/NoDatatypeContexts

I'm for this proposal, although I've got an example where I need this
context, namely for DrIFT to derive a proper context for instances.

DrIFT doesn't know that the Read instance for Data.Set.Set relies on Ord
of the elements. For

data Ord symbol = ExtSign sign symbol = ExtSign
  { plainSign :: sign
  , nonImportedSymbols :: Set.Set symbol
  } deriving Show

DrIFT cannot derive the Read (or our deserialization) instance without
the Ord symbol = context.

However, ghc is able by deriving (Show, Read) to see

instance (Ord symbol, Read sign, Read symbol) =
 Read (ExtSign sign symbol)

without the context.

Cheers Christian

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


Re: prefix minus and infix resolution

2010-07-15 Thread Christian Maeder
Hi Atze,

I share your desire for simplicity. In fact, I think my proposal is
simpler than the existing ones of hugs, ghc, nhc98 and the language
descriptions (98, 2010), although it's basically a matter of tuning.

Layout and the type system are far more involving and should not
interfere with fixity resolution!

Simon said somewhere that fixity resolution takes basically 12 lines of
haskell code. (My algorithm has 40 but shorter ones.)

Furthermore, fixity resolution is a nice subject for teaching in
conjunction with expression evaluation.

I added a remark to the end of
http://hackage.haskell.org/trac/haskell-prime/wiki/PrefixMinusResolution
about rejecting prefix minus applications that do not bind tightly. It
would use the same resolution algorithm with one modified line.

It says: reject - 1 ^ 2 always without parens in order to avoid the
too simple (wrong) resolution as (- 1) ^ 2.

C.

Atze Dijkstra schrieb:
 On  14 Jul, 2010, at 14:22 , Christian Maeder wrote:
 
 Atze Dijkstra schrieb:
 Hi,

 I prefer the simplicity of 
 http://hackage.haskell.org/trac/haskell-prime/wiki/NegationBindsTightly 
 over the more involved proposal.
 It's a simple design choice but hard to put into practice for
 compatibility reasons.
 
 It would indeed mean that some programs break, but is that bad? The situation 
 would be similar to the removal of N+K patterns (finding out how many 
 programs are influenced by it, requiring time to phase out, options to turn 
 on/off the feature, etc). Sometimes some cleanup is required to make place 
 for new stuff or to keep things manageable/implementable.
 
 What I want(ed) to emphasize is a concern for the implementability of Haskell 
 as a whole and some sanity checks when considering the addition of feature X:
 
 (1) can some idea not be expressed without X?
 In this case 'no' because proper use of parenthesis can express the 
 programmers intention.
 
 (2) can X be explained (and understood) by a 1st year student (or any other 
 language beginner)?
 In this case explaining would be more difficult because the student mentally 
 has to perform the same algorithm as the compiler does for X. On top of that 
 the fixity environment must be remembered by the programmer. Using 
 parenthesis is simpler.
 
 Of course such a list can be larger, but this seems relevant here.
 
 fortran and python have infix power operators that bind more tightly
 than unary minus. The mathematical unusual silent interpretation of - x
 ^ 2 as (- x) ^ 2 is the problem (and not that I better should write
 - (x ^ 2)).

 Other languages i.e. C do not have a power operator!
 Does - pow x 2 read better? Leave it to users to define ^ and **
 as they like?
 
 I like your proposal as it stands, it solves a problem, sure! But like other 
 seemingly innocent and nice solutions it also introduces less evident 
 problems in other areas: for the programmer (must know more), for the 
 implementer (because complexity of the whole is (sort of) quadratic in the 
 number of features). In particular for parsing expressions I believe no 
 compiler fully correctly did implement the (previous, Haskell98) language 
 definition, so from an implementers point of view I prefer to first simplify 
 matters until its implementable.
 To make this more concrete, UHC currently implements 
 http://hackage.haskell.org/trac/haskell-prime/wiki/NegationBindsTightly. Not 
 so much as a choice by desire, but out of necessity when debugging the parser 
 for a problem which turned out to be caused by an error in layout parsing 
 triggered by allowing nested do-statements have the same indentation. 
 Simplicity in another part of the language (related to '-') did help to 
 isolate the problem.
 
 cheers,
 
 Cheers Christian

 This is also much more clearer, less dependent on context info (i.e.
 the fixity of other operators), thus understandable without inspecting
 the definition of ^ in some other module, and thus also easier to
 explain (to students), and thus lessening the steepness of Haskells
 learning curve somewhat.
 cheers,

 On  13 Jul, 2010, at 18:38 , Christian Maeder wrote:

 Hi,

 I'm asking for support of:

 http://hackage.haskell.org/trac/haskell-prime/wiki/PrefixMinusResolution

 Cheers Christian

 Simon Marlow schrieb:
 BTW, here's a related proposal made by Simon PJ earlier this year:

 http://hackage.haskell.org/trac/haskell-prime/wiki/NegationBindsTightly

 please consider merging the proposals, or at least clearly identifying
 the differences, if any.
 ___
 Haskell-prime mailing list
 Haskell-prime@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-prime

- Atze -

 Atze Dijkstra, Department of Information and Computing Sciences. /|\
 Utrecht University, PO Box 80089, 3508 TB Utrecht, Netherlands. / | \
 Tel.: +31-30-2534118/1454 | WWW  : http://www.cs.uu.nl/~atze . /--|  \
 Fax : +31-30-2513971  | Email: a...@cs.uu.nl

operators ~ and @

2010-07-15 Thread Christian Maeder
Hi,

the language description contains ~ and @ as reserved:

  reservedop → .. | : | :: | = | \ | | | - | - | @ | ~ | =

These operators are only used within patterns.
I see no reason to leave them user-definable and usable within expressions.

The only change in the grammar would be, to disallow them as
infix varop in funlhs:

  funlhs → var apat { apat }
| pat varop⟨@|~⟩ pat
...

They could be defined as (@) and (~).

A similar restriction exists for the unary minus in right sections.

Once the bang ! moves into patterns it would be just a further
symbol among ⟨@|~⟩.

Is this worth creating a proper proposal?
http://hackage.haskell.org/trac/haskell-prime/wiki/Process

It is not that I recommend defining (@) or (~) as operators (although
maybe useful in a few domains), it's just to make the language more
orthogonal wrt ! that is already used in types and will be possibly
even more so via bang patterns.

(! is currently not reserved and used in libraries as operator)

Cheers Christian
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: prefix minus and infix resolution

2010-07-14 Thread Christian Maeder
Malcolm Wallace schrieb:
 I'm asking for support of:
 http://hackage.haskell.org/trac/haskell-prime/wiki/PrefixMinusResolution
 
 Just to note that nhc98 appears to fulfill the outcome of this
 resolution algorithm already, with the exception of example x7, which is
 parsed as -(4#5).

Because it seems to (unnecessarily) check if the operator # is
left-associative. I assume that for infixr 6 # the term -4 # 5 # 6
is resolved as -(4 # (5 # 6)) (like it would be for ^).

How can I try out nhc98? My old installation is broken and
http://www.haskell.org/haskellwiki/Implementations#nhc98
refers to no implementation. Is Yhc the compiler I should try?

 
 However, nhc98 goes further and permits the declaration of arbitrary
 prefix operators, using the syntax
 
 prefix negate 6 -

yes, this is a nice extension.

 yes, in addition to
 
 infix 6 -
 
 I think the rationale is that the prefix symbol must map to a
 non-symbolic function name, because the same symbol may also refer to a
 function of a different type when used infix. 

Currently there is no haskell way to _define_ a prefix operator
therefore prefix minus is bound to negate explicitly as above (nhc98) or
implicitly built-in (ghc and hugs).

Prefix- and Infix-usage can be distinguished by the lexer:

  - a ... - prefix

  a - ... - infix

Furthermore, prefix minus can not be qualified (bug or feature?).

Prelude.- only refers to the infix version and Prelude.- 1 is rejected
(by ghc and hugs).

Cheers Christian

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


Re: prefix operators

2010-07-13 Thread Christian Maeder
Simon Peyton-Jones schrieb:
 Yes, I somewhat hacked up the rules for ! in an ad-hoc way.  I really wanted 
 to allow
 
   f !x !y = (x,y)
 
 which meant a bit of fiddling, because LHSs are parsed as terms, so this is 
 parsed as
 
   (f ! x) ! y
 
 (ie as infix operators) and I have to squizzle around to re-interpret them as 
 prefix operators.  Not very cool.  Something unified would be a Good Thing.

I assume

  f -x -y = ...

is also parsed as

  (f - x) - y

and later rejected as Parse error in pattern.

The (possibly) indented interpretation f (-x) (-y) or f (!x) (!y)
simply contradicts the interpretation as terms with binary operators.

With bang patterns the binary operator ! can no longer be defined as:

  f !x =

http://www.haskell.org/ghc/docs/6.12.2/html/users_guide/bang-patterns.html#bang-patterns-sem

This case is not mention under
http://www.haskell.org/ghc/docs/6.12.2/html/users_guide/syntax-extns.html#syntax-stolen

One could consider whitespace (which already happens with $ in
template haskell), but that's questionable, too.

Since we make a new language spec knowing many extensions, it would be
possible to disallow more bits in the standard in order to avoid stolen
syntax by extensions.

But disallowing infix pattern using ! is non-orthogonal and making !
a reserved op like ~ would break some libraries.

Should rec become a reserved keyword, because I had to rename it when
switching on extensions?

I would not mind if forall (and exist) became a keyword (although
not required, since forall can only occur within types).

Should $ be followed by whitespace (or forbidden), just to allow
compilation using template haskell, too?

I don't know the impact of -XMagicHash on infix stuff using # or ##.

I think, it's unfortunate that the (scanner and) parser depends on
extensions. It would be better to parse a language superset and let
static analysis deal with (known) extensions.

Christian

 
 Simon
 
 
 
 | -Original Message-
 | From: haskell-prime-boun...@haskell.org [mailto:haskell-prime-
 | boun...@haskell.org] On Behalf Of John Meacham
 | Sent: 08 July 2010 00:59
 | To: haskell-prime@haskell.org
 | Subject: prefix operators
 | 
 | It occurred to me the other day that Haskell (w/ bang patterns) now has
 | 3 prefix operators, all of which are defined independently and follow
 | their own special rules for parsing. we have (-), (!) and (~).
 | 
 | It would seem to me that we should somehow be able to unify the
 | mechanism behind parsing these, as in practice, it seems that prefix
 | operators are useful in haskell.
 | 
 | We have some similarities, - and ! are both infix and prefix operators,
 | ~ is not. ! and ~ can only be in patterns as prefix, (-) can be in both
 | patterns and expressions.
 | 
 | But it seems like we may be able to come up with a common way of parsing
 | them all, prolog has had user defined infix, prefix, and postfix
 | operators (sharing the same name even) and is still able to parse things
 | properly so I don't think there will be a technical issue.
 | 
 | My first impulse is to treat application as just another binary operator
 | with a certain precedence and find appropriate precedences for !,~,- in
 | the new framework.
 | 
 | note: I am not proposing user defined prefix operators, just musing
 | about whether we can unify the rules behind parsing the current three
 | prefix operators, perhaps folding them into the fixity resolution
 | algorithm.
 | 
 | John
 | 
 | --
 | John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
 | ___
 | Haskell-prime mailing list
 | Haskell-prime@haskell.org
 | http://www.haskell.org/mailman/listinfo/haskell-prime
 
 
 
 
 
 ___
 Haskell-prime mailing list
 haskell-prime-hc+z4ntrilbafugrpc6...@public.gmane.org
 http://www.haskell.org/mailman/listinfo/haskell-prime

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


Re: prefix minus and infix resolution

2010-07-13 Thread Christian Maeder
Simon Marlow schrieb:
 BTW, here's a related proposal made by Simon PJ earlier this year:
 
 http://hackage.haskell.org/trac/haskell-prime/wiki/NegationBindsTightly
 
 please consider merging the proposals, or at least clearly identifying
 the differences, if any.

Thanks for pointing this out.

The difference lies in:

 - 1 ^ 2

which is currently (and by my proposal) resolved to - (1 ^ 2) whereas
it would be resolved to (-1) ^ 2 if negation binds tightly.

Christian

 
 Cheers,
 Simon
 
 On 12/07/2010 08:40, Christian Maeder wrote:
 Hi Simon and other fixity resolution friends,

 Fixity resolution starts from a sequence of expressions (lexp)
 interspersed by operator symbols, where some expressions may be preceded
 by unary minus signs.

 Between an operator and a following unary minus sign must be white space
 for the haskell lexer (as in x == -1).

 A binary minus is recognized (by the lexer), because it _follows_ an
 expression (lexp) unlike an unary minus (that precedes).

 Conceptually fixity resolution can be divided into two steps:

 1. resolve prefix applications of unary minus
 2. resolve infix applications

 There's no doubt how to resolve mere infix applications using
 precedences and associativity (2. step):

 A term
a `o` b `p` c
 is uniquely resolve as:
   2.a) (a `o` b) `p` c
   if prec(o)  prec(p)
   or prec(o) = prec(p) and both operator are left associative
   2.b) a `o` (b `p` c)
   if prec(p)  prec(o)
   or prec(o) = prec(p) and both operator are right associative
   2.c) unresolved otherwise

 The prefix applications of unary minus is a bit unusual (compared to
 other prefix applications) in that it binds weaker than multiplication:

   - 1 * 2 is to be resolved as - (1 * 2)

 This weak binding is irrelevant for multiplication but essential for
 exponentiation, ie. -x^2, and can make a difference for user defined
 infix operators, that bind strongest by default!

 Resolution of prefix - (1. step) works as follows:

 Unary minus applications extend as far to the right as _infix_ operators
 (no unary minus) have higher precedence than + or -.

 A term like
- a * b ^ c  - d ^ e * f
 is resolved as
- (a * b ^ c)  - (d ^ e * f)
 or with more parens as
(- (a * b ^ c))  (- (d ^ e * f))
 which further resolves by infix resolution (2. step) to
(- (a * (b ^ c)))  (- ((d ^ e) * f))

 In fact, this should finish fixity resolution, but the current haskell
 state unnecessarily restricts resolution further:

 3.a) a * - b is rejected, because * binds stronger than -
 3.b) a + - b is rejected, because + and - are not both right
 associative

 although both terms can be uniquely resolved to a * (- b) a + (- b).

 In other words, the operator to the left of an unary minus can be
 completely ignored for prefix minus resolution, simply because prefix
 minus does not have a left argument (like the binary minus)!

 Without this restriction polynomials like
   - a + - b * x + - c * - x ^ 2
 would uniquely resolve to
   ((- a) + (- (b * x))) + (- (c * (- (x ^ 2

 I think hugs handles this correctly!

 Let us assume a user-defined (non- or) right-associative operator #
 with the same precedence as + and - (infix[r] 6 #).

 3.c) both - a # b and a # - b are rejected,
because # is not left-associative (like -).

 This unnecessary restriction rules out a (user-defined) polynomial like
   - a # - b * x
 for two reason (namely the two unary minus signs).

 Because an operator like # is not predefined, this restriction does
 not hurt as much as it does for + (and binary -).

 The unrestricted fixity resolution (1. and 2. step only, without
 restrictions 3.) can be further extended to allow multiple unary minus
 prefix applications.

 infixexp -   {-} lexp { op {-} lexp }

 White space is needed between - signs for lexing.
 Extended cases of 3.a) and 3.b) would be legal:
a * - - b resolves uniquely to a * (- (- b))
a + - - b resolves uniquely to a + (- (- b))

 It is, however, worth to remark that two consecutive unary - sign
 cannot be simply omitted:
a * - - b * c resolves to a * (- (- (b * c)))
whereas a * b * c resolves to (a * b) * c

 Even if double negation is the identity the grouping of factors has
 changed.

 An (alternative) implementation of the unrestricted fixity resolution
 can be found at:
 http://hackage.haskell.org/trac/ghc/ticket/4180

 In comparison to the current restricted version the guard that checks
 the left operator before the unary minus can be omitted. Also giving the
 unary minus the same precedence and associativity than the binary minus
 makes the algorithm more restrictive. The unary minus needs a higher
 precedence than the binary - and a lower one than * or /:

 Using http://darcs.haskell.org/haskell-prime it is enough to change:

 -type Prec   = Int
 +type Prec   = Float

 -   = do guard (prec1  6)
 -(r, rest')- parseNeg (Op - 6 Leftfix) rest
 +   = do
 +(r, rest')- parseNeg (Op - 6.5

remark on hugs for Re: prefix minus and infix resolution

2010-07-12 Thread Christian Maeder
Christian Maeder schrieb:
[...]
 Without this restriction polynomials like
  - a + - b * x + - c * - x ^ 2
 would uniquely resolve to
  ((- a) + (- (b * x))) + (- (c * (- (x ^ 2
 
 I think hugs handles this correctly!

yes it does this case.

 
 Let us assume a user-defined (non- or) right-associative operator #
 with the same precedence as + and - (infix[r] 6 #).
 
 3.c) both - a # b and a # - b are rejected,
   because # is not left-associative (like -).

hugs rejects only the case - a # b:
ERROR - Ambiguous use of unary minus with (#)

So hugs still considers associativity for - (but does not consider the
operator to the left of an unary minus.)

C.

 This unnecessary restriction rules out a (user-defined) polynomial like
  - a # - b * x

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


Re: Second draft of the Haskell 2010 report available

2010-07-08 Thread Christian Maeder
Simon Marlow schrieb:
 If we changed patterns in the same way as you suggest for expressions
 above, then this would become clearer, right?

By this change you would loose the important restriction that - is
only legal to denote negated (integer or float) constants, which would
then move from the grammar to the informal description.

Any choice is fine.

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


Re: fixity resolution

2010-07-07 Thread Christian Maeder
Christian Maeder schrieb:
 http://www.haskell.org/~simonmar/haskell-2010-draft-report-2/haskellch10.html#x17-17300010
 
 Fixity resolution also applies to Haskell patterns, but patterns are a
 subset of expressions so in what follows we consider only expressions
 for simplicity.

I suggest to change also applies to Haskell patterns to

also applies to Haskell patterns and left hand sides of infix function
bindings

 The string 1 * - 1 is legal as pattern, but rejected as expression!

Further points:

1. - 1 * 1 is accepted as legal pattern, but differently resolved for
expressions! Should one not reject these (rare) patterns, too?

2. I would rather allow 1 * - 1 and 1 + - 1 to be legal as
expressions (with its unambiguous interpretation).

3. Associativity should not matter for the non-binary -!

So the following resolutions are possible:

1 + - 2 + 3 ~~~ (1 + -2) + 3
1 + - 2 * 3 ~~~ 1 + -(2 * 3)

infix 6 ##  -- same precedence like + but different associativity

- 1 ## 2 ~~~ (-1) ## 2

An infix-expression following an unary minus is resolved independently
first. If the top-level operator has a strictly higher precedence than
- its resolved as minus term, otherwise the same procedure is applied
to the left argument of the infix expression. (If the left argument is
no infix expression, we are done by plain prefix application of minus.)

 
 Furthermore fixity resolution does not distinguish between constructors
 and other operators as it should according to the grammar:
 
 pat→  lpat qconop pat  (infix constructor)
   |   lpat
 
 
 funlhs →  var apat { apat }
   |   pat varop pat

add a description:
|   pat varop pat   (infix binding)

   |   ( funlhs ) apat { apat }
 
 
 a : b * c : d = undefined is currently rejected with:

A similar example is given in 4.4.3.1  Function bindings. It should be
referenced in 10.6  Fixity Resolution

Cheers Christian

 
 cannot mix `:' [infixr 5] and `Main.*' [infixl 9] in the same infix
 expression
 
 but should be fine by the given grammar (rule pat varop pat).
 
 Cheers Christian
 
 P.S. like in my proposal for infixexp I would change pat to:
 
 pat→  pat qconop pat   (infix constructor)
   |   lpat
 
 for the sake of a better presentation only.
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: fixity resolution

2010-07-07 Thread Christian Maeder
Simon Marlow schrieb:
 The string 1 * - 1 is legal as pattern, but rejected as expression!
 
 Well, it's not a pattern (* is a varop, not a conop), and it's an
 illegal funlhs (* has greater precedence than prefix -).

it is legal as funlhs (ghc-6.12.3)!

1 * - 1 = 2


Main 1 Main.* (-1)
2

see also:
http://hackage.haskell.org/trac/ghc/ticket/4176

Christian

 
 Furthermore fixity resolution does not distinguish between constructors
 and other operators as it should according to the grammar:

 pat  → lpat qconop pat  (infix constructor)
 | lpat


 funlhs  → var apat { apat }
 | pat varop pat
 | ( funlhs ) apat { apat }


 a : b * c : d = undefined is currently rejected with:

 cannot mix `:' [infixr 5] and `Main.*' [infixl 9] in the same infix
 expression

 but should be fine by the given grammar (rule pat varop pat).
 
 The grammar specifies a superset of the language; fixity resolution may
 reject something that is legal according to the grammar.  That's the
 change we made in Haskell 2010: the grammar no longer attempts to
 describe the language precisely with respect to fixity resolution, for
 good reasons
 (http://hackage.haskell.org/trac/haskell-prime/wiki/FixityResolution).
 
 See section 4.4.3.1  Function bindings:
 
 
 Note that fixity resolution applies to the infix variants of the
 function binding in the same way as for expressions (Section 10.6).
 Applying fixity resolution to the left side of the equals in a function
 binding must leave the varop being defined at the top level. For
 example, if we are defining a new operator ## with precedence 6, then
 this definition would be illegal:
   a ## b : xs = exp
 
 because : has precedence 5, so the left hand side resolves to (a ## x) :
 xs, and this cannot be a pattern binding because (a ## x) is not a valid
 pattern.
 
 
 
 Perhaps this could be clearer, please do suggest improvements.
 
 
 P.S. like in my proposal for infixexp I would change pat to:

 pat  → pat qconop pat  (infix constructor)
 | lpat
 
 is there any need to do that?  The grammar is non-ambiguous right now.
 
 Cheers,
 Simon
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Second draft of the Haskell 2010 report available

2010-07-07 Thread Christian Maeder
Simon Marlow schrieb:
 prefix negation should move to lexp to
 be consistent with lpat

prefix negation should not move to lexp, because this would rule out
- 1 ^ 2 as negated infix expression - (1 ^ 2), whereas a negated
infix pattern is impossible. Unary minus is no constructor and cannot be
defined. The latter should be (or is already?) mentioned somewhere.

You could move prefix negation to lexp, if you allow the fixity
resolution to construct negated infix expression that are not covered by
the grammar (as currently happens anyway).

Moving prefix negation from lpat to pat to be consistent with infixexp
would be overkill, though.

Christian

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


Re: fixity resolution

2010-07-07 Thread Christian Maeder
Simon Marlow schrieb:
[...]
 1. - 1 * 1 is accepted as legal pattern, but differently resolved for
 expressions! Should one not reject these (rare) patterns, too?
 
 That's the GHC bug, right?

Yes!

 2. I would rather allow 1 * - 1 and 1 + - 1 to be legal as
 expressions (with its unambiguous interpretation).
 
 Yes, me too, but that's a matter for a new proposal.
 
 3. Associativity should not matter for the non-binary -!

 So the following resolutions are possible:

 1 + - 2 + 3 ~~~  (1 + -2) + 3
 1 + - 2 * 3 ~~~  1 + -(2 * 3)

 infix 6 ##  -- same precedence like + but different associativity

 - 1 ## 2 ~~~  (-1) ## 2
 
 Yes, again I agree.  The current fixity resolution is more strict than
 it needs to be.  The intention in Haskell 2010 was not to change the way
 fixity resolution worked, but rather to avoid the problems caused by
 having it as part of the grammar.

The grammar (in particular an ambiguous one) describes a superset of the
language and need not change with a changed fixity resolution (or type
analysis).

 
 If you make a proposal to change this, then I would probably support it.

A larger case would be 1 * - 2 * 3,
that I would resolve to 1 * - (2 * 3) by resolving everything after
- first. This is sort of an arbitrary choice, but probably ok and in
the same spirit than resolving - 2 * 3 to - (2 * 3).

C.

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


Re: Second draft of the Haskell 2010 report available

2010-07-06 Thread Christian Maeder

http://www.haskell.org/~simonmar/haskell-2010-draft-report-2/haskellch3.html

infixexp →  lexp qop infixexp (infix operator application)
|   - infixexp(prefix negation)
|   lexp

This grammar rule describes a right associative nesting of (any) infix
operators qop and prefix negation as binding weaker than any infix.

Thus a parser would create from - 1 /= 1  a the tree
 - (1 /= (1  a)).

Would it not be better to give an ambiguous grammar and leave it to the
infix resolution algorithm to allow only the intended trees, rather than
letting the infix resolution algorithm correct a wrong tree?

My suggestion would be to change the rule to:

infixexp →  infixexp qop infixexp (infix operator application)
|   - infixexp(prefix negation)
|   lexp

thus only replacing the first lexp by infixexp.

Cheers Christian

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


fixity resolution

2010-07-06 Thread Christian Maeder
http://www.haskell.org/~simonmar/haskell-2010-draft-report-2/haskellch10.html#x17-17300010

Fixity resolution also applies to Haskell patterns, but patterns are a
subset of expressions so in what follows we consider only expressions
for simplicity.

The string 1 * - 1 is legal as pattern, but rejected as expression!

Furthermore fixity resolution does not distinguish between constructors
and other operators as it should according to the grammar:

pat  →  lpat qconop pat  (infix constructor)
|   lpat


funlhs   →  var apat { apat }
|   pat varop pat
|   ( funlhs ) apat { apat }


a : b * c : d = undefined is currently rejected with:

cannot mix `:' [infixr 5] and `Main.*' [infixl 9] in the same infix
expression

but should be fine by the given grammar (rule pat varop pat).

Cheers Christian

P.S. like in my proposal for infixexp I would change pat to:

pat  →  pat qconop pat   (infix constructor)
|   lpat

for the sake of a better presentation only.
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Haskell 2010 libraries

2010-04-30 Thread Christian Maeder
Malcolm Wallace schrieb:
 In many ways this corresponds to my preferred solution, although I would
 rephrase it thus:
 
   * Deprecate use of the base package,  (I do not mean to remove base,
 just to freeze it, and discourage its general use.)
   * Create a new haskell2010 package (for ghc this will be built on top
 of base, but other compilers might make a different choice).
   * Create a new portablebase package which contains (or re-exports)
 all of the remaining useful and portable parts of the current base
 _and_ haskell2010.
   * Create a new ghcextras package which re-exports (or defines afresh)
 all of the useful but non-portable parts of the current base.
 
 So haskell2010 would be stable and unchanging.  portablebase would
 be a superset of haskell2010, and continue to evolve with community
 input, and parts of it would eventually migrate into haskell2011,
 haskell2012, etc.  Meanwhile ghcextras would clearly delineate those
 language/library features that are not portable, and it could continue
 to grow, or indeed shrink, with some parts migrating into portablebase
 as the language definition adopts extensions, or as other compilers
 adopt implementation strategies.
 
 To illustrate the forward compatibility story, I envisage that when
 haskell2011 is created, a new version of portablebase would depend
 on (and re-export) it instead of haskell2010.  This would be OK
 because the portablebase API would be non-decreasing, and new Reports
 should not make library changes that have not already been trialled in
 the community.  On the other hand, the ghcextras package would be free
 to shrink as functionality is gradually transferred to portablebase.
 
 Because I suggest that portablebase re-export the haskell2010 API in
 its entirety, it would be impossible to use both packages explicitly at
 the same time from a single module - users would need to choose one or
 the other.  Also, packages which currently depend on base should be
 encouraged to upgrade to a dependency on haskell2010 rather than on
 portablebase, if possible, because it provides greater stability of
 interface.
 
 The overall dependency graph would look something like this:
 
   /--- stablestuff   /-- less-stable-stuff
  /  /
  base ---  haskell2010 --- portablebase ---\
   \--  ghcextras   -\=== experimental-stuff

Why do you want portablebase to be a superset of haskell2010 by
re-export? Is it not better to have a package baseextras that depends
on haskell2010 but only exports additional modules.

Other packages can decide to depend on haskell2010 only or on
haskell2010 and baseextras (instead of portablebase alone).

Or do you want modules from haskell2010 also to be portablebase but
with additional functions (rather than putting new functions into new
modules)?

Cheers Christian

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


Re: RFC: Fixing floating point conversions.

2010-02-25 Thread Christian Maeder
Nick Bowler schrieb:
 *** Idea #2 ***
 
 Similar to #1, except using a generic type instead of Double.
 
 Define a new type, call it FloatConvert, which represents rational plus
 other values.  Something along the lines of:
 
   data FloatConvert
   = FCZero Bool   -- Signed zero
   | FCInfinity Bool   -- Signed infinity
   | FCNaN Integer -- Generic NaN
   | FCFinite Rational -- Finite, non-zero value

interesting. What is the Integer in FCNaN for?

 Add two new methods to the RealFloat class:
 
   toFloatConvert   :: RealFloat a = a - FloatConvert
   fromFloatConvert :: RealFloat a = FloatConvert - a
 
 and a function:
 
   toFloating :: (RealFloat a, RealFloat b) = a - b
   toFloating = fromFloatConvert . toFloatConvert
 
 Advantages:
   * No extensions (other than this one) beyond Haskell 98 are required.
   * Simple to define instances, exactly two functions per floating type.
   * Easy to add floating types to the language, and easy for users to
 define their own in libraries.
 
 Disadvantages:
   * A data type whose sole purpose is to convert floating types seems
 like a wart.
   * While the free-form encoding of NaN values will allow conversion
 from a type to itself to be the identity function, it may make
 it tricky to perform the ideal conversion between different
 types.

I don't understand this last point about free-form encoding of NaN

I would come up with a data type like:

  data ExtNum a
= NegativeZero
| NaN
| Infinity Bool
| Num a

add instances for the classes, Eq, Ord, Num, 
(depending on a that must be at least from the class Num for 0)

and use ExtNum Rational for floating point conversions.

Cheers Christian
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Fixity

2010-02-15 Thread Christian Maeder
let me try again to fix the issue. Apologies, if you mind.

Christian Maeder schrieb:
 S. Doaitse Swierstra schrieb:
 weird :: Int - Int
 weird = (if True then 3 else 5+)

 is perfectly correct Haskell?
 
 Yes, this is legal according to the grammar
 http://haskell.org/onlinereport/syntax-iso.html
 but rejected by ghc and hugs, because 5+ is illegal.

5+ is illegal, but therefore neither ghc nor hugs only parse the 5
and assume that the if-then-else-expression is finished after this 5
and leave the + to form the section as ((if True then 3 else 5)+)

 The problem is to allow let-, if-, do-, and lambda-expressions
 to the left of operators (qop), because for those the meta rule
 extend as far as possible should apply.

Do- and case-expressions do not fall in the same class than let-, if-,
and lambda-expressions. An operator following let, if and lambda should
be impossible because such an operator should belong to the last
expression inside let, if and lambda.

But do- and case- expressions are terminated by a closing brace. The
point is, when this closing brace is inserted.

weird2 m = (do m )

Inserting } between m and  because m  is illegal, leads to
the same problem as above for if-then-else. } should be inserted
before the ). hugs and ghc fail because they expect an fexp following
.

 Switching to the new grammar
 http://hackage.haskell.org/trac/haskell-prime/wiki/FixityResolution
 
 infixexp - exp10 qop infixexp
 | - infixexp
 | exp10
 
 should be replaced by:
 
 infixexp - fexp qop infixexp
| exp10
 
 (omitting the negate rule)

 or shorter: infixexp - { fexp qop } exp10


Assuming that braces are properly inserted, my above (too restrictive)
rule can be extended to  include case- and do-expressions to cdexp (in
order to allow operators between them):

cdexp  - fexp
| - fexp  (negation)
| do { stmts }
| case exp of { alts }

exp10  - cdexp
| \ apat1 ... apatn - exp  (n=1)
| let decls in exp
| if exp then exp else exp

infixexp  - cdexp qop infixexp
   | exp10

(or: infixexp - { cdexp qop } exp10)

 Left sections should look like:
 
  ( {fexp qop} fexp qop )
 
 It would be even possible to avoid parenthesis around sections, because
 a leading or trailing operator (or just a single operator) uniquely
 determines the kind of expression.

The need to put sections into parenthesis is one cause for the current
confusion. Inside the parenthesis the following expressions iexp are
expected:

iexp - qop  (operator turned to prefix-function)
  | infixexp  (parenthesized expression)
  | infixexp :: [context =] type (parenthesized typed expression)
  | qop infixexp  (right section)
  | { cdexp qop } cdexp qop   (left section)

So another solution would be, to make such expression globally legal in
the grammar and reject a single operator, left-, and right sections
during a separate infix analysis in a similar way as a == b == c is
first fully parsed but rejected later, because == is non-associative.

In fact any (non-empty) sequence of qop and exp10 expressions could be
made a legal expression (for the parser only) that is further subject to
infix resolution.

(This would for example also allow outfix operators via:

iexp - qop { cdexp qop }
  | ...

if desirable for haskell prime.)

Is this better now?
Cheers Christian

 
 Negation should be added independently to fexp (and possibly to exp10, too)
 
 fexp   -  [fexp] aexp (function application)
 minusexp - fexp | - fexp
 
 infixexp - minusexp qop infixexp
| exp10
| - exp10
 
 (unless some wants the old FORTRAN behaviour of unary - to bind weaker
 than infix multiplication and exponentiation.)
 
 Cheers Christian
 
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Fixity was: Negation

2010-02-14 Thread Christian Maeder
S. Doaitse Swierstra schrieb:
 weird :: Int - Int
 weird = (if True then 3 else 5+)
 
 is perfectly correct Haskell?

Yes, this is legal according to the grammar
http://haskell.org/onlinereport/syntax-iso.html
but rejected by ghc and hugs, because 5+ is illegal.

The problem is to allow let-, if-, do-, and lambda-expressions
to the left of operators (qop), because for those the meta rule
extend as far as possible should apply.

Switching to the new grammar
http://hackage.haskell.org/trac/haskell-prime/wiki/FixityResolution

infixexp - exp10 qop infixexp
| - infixexp
| exp10

should be replaced by:

infixexp - fexp qop infixexp
   | exp10

(omitting the negate rule)

or shorter: infixexp - { fexp qop } exp10

Left sections should look like:

 ( {fexp qop} fexp qop )

It would be even possible to avoid parenthesis around sections, because
a leading or trailing operator (or just a single operator) uniquely
determines the kind of expression.

Negation should be added independently to fexp (and possibly to exp10, too)

fexp -  [fexp] aexp (function application)
minusexp - fexp | - fexp

infixexp - minusexp qop infixexp
   | exp10
   | - exp10

(unless some wants the old FORTRAN behaviour of unary - to bind weaker
than infix multiplication and exponentiation.)

Cheers Christian
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Fixity was: Negation

2010-02-14 Thread Christian Maeder
Christian Maeder schrieb:
 S. Doaitse Swierstra schrieb:
 weird :: Int - Int
 weird = (if True then 3 else 5+)

[...]

 infixexp - fexp qop infixexp
| exp10

This is no good, because it would exclude:

   do ...
 ++ do

expressions.

 It would be even possible to avoid parenthesis around sections, because
 a leading or trailing operator (or just a single operator) uniquely
 determines the kind of expression.

Maybe this is a solution to the above problem, because 5+ could be
legally parsed (and only rejected during type inference).

C.

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


Re: Negation

2010-02-09 Thread Christian Maeder
 | I imagine it would be something like deleting the production
 | 
 | lexp6-  - exp7

The rational for the current choice was the example:

f x = -x^2

 | and adding the production
 | 
 | exp10-  - fexp

But I would also recommend this change.

It would also make sense to allow - before let, if and case or
another - expression, but that's a matter of taste.

Cheers Christian
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: DoAndIfThenElse

2009-11-27 Thread Christian Maeder
S. Doaitse Swierstra schrieb:
[..]
 \begin{code}
 main = do
  if True then putStrLn 1;
  else putStrLn 2
 \end{code}

 This does also not work with hugs (; at the end)
 
 This does not work since now you have two ;'s; one because you wrote
 one and one because you did not indent the else. Allowing this
 additional ; was done to prevent confusion, and as you can see even more
 confusion pops up now;-{{ That is why I expressed my concerns about this
 grammar patch.
 
  Doaitse

Indeed, these semicolons are confusing. I think it should be possible to
allow then and else starting in the same column as if without
these ;s (in a do block).

Christian

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


DoAndIfThenElse

2009-11-26 Thread Christian Maeder
Hi,

seeing Haskell 2010 and
http://hackage.haskell.org/trac/haskell-prime/wiki/DoAndIfThenElse

saying:
Compiler support ¶
GHC full (no flag)

I wonder why I still get a parse error (possibly incorrect
indentation) for:

\begin{code}
main = do
  if True then putStrLn 1
  else putStrLn 2
\end{code}

Can I try out this feature somehow?

Cheers Christian
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: DoAndIfThenElse

2009-11-26 Thread Christian Maeder
David Virebayre schrieb:
 Isn't the proposal about :
 
 \begin{code}
 main = do
  if True then putStrLn 1
  ;else putStrLn 2
 \end{code}

This should go through, too, but also does not for me according to
http://hackage.haskell.org/trac/haskell-prime/wiki/DoAndIfThenElse

cite
Change the syntax for conditionals to

exp - if exp1 [;] then exp2 [;] else exp3

i.e., add optional semicolons before then and else, making the above
example legal. This has been recently added to jhc, GHC and Hugs, and so
far it has not caused any problems.
/cite

But the main purpose of the proposal was to support the notation without
 ; and the indentation by at least one character.

I just do not see that it has been recently added to GHC
I've checked ghc-6.10.4 and 6.12.0.20091010

Cheers Christian

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


empty decls Re: Proposals and owners

2009-07-30 Thread Christian Maeder
Stephanie Weirich wrote:
 Ok, I've put together a page on EmptyDataDecls:
 
 http://hackage.haskell.org/trac/haskell-prime/wiki/EmptyDataDecls

This reminds me to the related ticket:
http://hackage.haskell.org/trac/ghc/ticket/393

If a dummy definition can be supplied for a function, then also a dummy
constructor value can be supplied for a data type.

If empty bindings and/or data types are supported the compiler can at
least better warn about them.

Cheers Christian

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


Re: Suggestion for bang patterns documentation

2009-02-27 Thread Christian Maeder
Brian Bloniarz wrote:
 I got confused by the GHC documentation recently, I was wondering how
 it could be improved. From:
 http://www.haskell.org/ghc/docs/latest/html/users_guide/bang-patterns.html

Seeing the rule
 pat ::= !pat

you'll probably want to avoid patterns like: !!pat, ! ! pat, or ~ !
~ pat.

Even the current http://www.haskell.org/onlinelibrary/exps.html#sect3.17.1

  apat - ~ apat

allows ~ ~x. (Note the space!) So maybe a separate non-terminal bpat
should be used with:

 bpat - [~|!] apat

(and bpat used within pat). You may also want to exclude v@ ~(...) in
favor of ~v@(...).

 A bang only really has an effect if it precedes a variable or wild-card 
 pattern:
 f3 !(x,y) = [x,y]
 f4 (x,y)  = [x,y]
 Here, f3 and f4 are identical; putting a bang before a pattern that
 forces evaluation anyway does nothing.

Maybe the duality (if it is one) should be added that an irrefutable
pattern above would make a difference but not within the let below.

 The first sentence is true, but only in settings where the pattern is being
 evaluated eagerly -- the bang in:
 f3 a = let !(x,y) = a in [1,x,y]
 f4 a = let (x,y) = a in [1,x,y]
 has an effect.

Cheers Christian

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


template haskell syntax

2007-08-24 Thread Christian Maeder
Hi,

for haskell prime I suggest to change the stolen syntax
 [e|, [p|, [d|, [t|

to [|letter| in order to avoid the confusion with list comprehensions.

Cheers Christian
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime