`StablePtr` in `ST`

2019-08-20 Thread Matthew Farkas-Dyck
I have been doing some work where i want `StablePtr`, but also to not
be confined to `IO`. I saw the following comment in
"compiler/prelude/PrimOp.hs":

Question: Why @RealWorld@ - won't any instance of @_ST@ do the job? [ADR]

It has been there for 20 years. What is the answer? If it is safe i'll
send the patch generalizing these operations.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


Re: Local types and instances

2018-04-29 Thread Matthew Farkas-Dyck
On 4/29/18, Edward Kmett  wrote:
> This isn't sound.
>
> You lose the global uniqueness of instance resolution, which is a key part
> of how libraries like Data.Set and Data.Map move the constraints from being
> carried around in the Set to the actual use sites. With "local" instances it
> is very easy to construct such a map in one local context and use it in
> another with a different instance.

Ah, i forgot to say explicitly: local instances of types declared at
greater scope are not allowed. Is it unsound nonetheless?
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-prime


Re: Exposing target language in Haskell with GHC API

2016-09-02 Thread Matthew Farkas-Dyck via Glasgow-haskell-users
Hi, thanks for the response.

On 26/08/2016, Christiaan Baaij  wrote:
> You mentioned that GHC does name mangling, but I must say I've never
> seen GHC do this.

I guess this was unclear: our compiler is mangling the names from GHC
core, lest any clash with a BlueSpec keyword. We need to find a way to
annotate the Haskell source to tell our compiler to not mangle a name.

> What GHC does do is inlining and specialisation, which might optimise
> away your carefully constructed "primitive".
>
> What I do in this case, is simply mark my "primitive" function, your
> "exposed" BlueSpec functions, as NOINLINE.

Ah, yes, it seems we will need to do this too.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


Exposing target language in Haskell with GHC API

2016-08-23 Thread Matthew Farkas-Dyck via Glasgow-haskell-users
A colleague and i are writing, as an unofficial side project, a
Haskell→Bluespec compiler, using GHC as our Haskell front-end. The
source language of the part we are writing is GHC Core. We need to
somehow expose some Bluespec terms and types to the Haskell source
program. We had a few ideas:
1. Some "NO_MANGLE" pragma which would tell GHC to not mangle the
emitted name, e.g. `x = {-# NO_MANGLE #-} x` to expose `x`
2. `foreign import prim`, not quite sure how yet
3. "CORE" pragmas, e.g. `x = {-# CORE "foo" #-} x` to expose `x`
4. "ANN" pragmas, e.g. `{-# ANN x "no_mangle" #-} x = x` to expose `x`

1 and 2 would mean modifying GHC which we'd rather not do. For 3,
we're not sure how to find the "CORE"-pragmatic annotations in a
`Core` AST. 4 seems it would work but be a little cumbersome, as the
annotation is not on the `Core` AST.

Anyone know a good way to do this?
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


Records in Haskell: Explicit Classy Records

2012-04-11 Thread Matthew Farkas-Dyck
Hello GHC users.

I made another proposal for records in Haskell, meant to solve just
the namespace problem, and no more.
http://hackage.haskell.org/trac/ghc/wiki/Records/ExplicitClassyRecords

In this system, record selectors are overloaded in
explicitly-user-declared type classes. Thus one can control the scope
as of any other type class.

Cheers,
strake

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


Re: [Haskell-cafe] I Need a Better Functional Language!

2012-04-06 Thread Matthew Farkas-Dyck
On 05/04/2012, Grigory Sarnitskiy sargrig...@ya.ru wrote:
 One could expect from a language that bears 'functional' as its
 characteristic to be able to do everything imaginable with functions.
 However, the only thing Haskell can do with functions is to apply them to
 arguments and to feed them as arguments, run in parallel (run and
 concatenate programs).

 Obviously, that's not all of the imaginable possibilities. One also can
 rewrite programs. And write programs that rewrite programs. And write
 programs that rewrite programs that rewrite the first programs and so on.
 But there is no such possibility in Haskell, except for introducing a DSL.

 Note, that the reflectivity is important.

For x86 machine: http://hackage.haskell.org/package/hdis86

Truly, I often wish to be able to pattern match on functions myself.
Alas, the function is not an algebraic data type.

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


Re: Records in Haskell: Type-Indexed Records (another proposal)

2012-03-05 Thread Matthew Farkas-Dyck
On 03/03/2012, AntC anthony_clay...@clear.net.nz wrote:
 Apart from the Quasifunctor bit, I think you'll find your proposal is a rather
 cut-down version of DORF, just using different syntactic sugar.

 (Oh, and with the arguments to Has in a different order, just to be 
 confusing.)

Not so. I chose this order to make it easier to curry.

 You do have the equivalent of fieldLabel decls. Those are all your type
 indexes: data X = X, etc.

True, but data is not a new keyword.

 And you suggest defining
 x = X

We can define x = X, if we wish, but we need not; we could rather
define x as a selector. It's just that lower-case labels are customary
in Haskell.

 Which is equivalent to DORF mapping from field name `x` to phantom type
 Proxy_x, (but DORF keeps `x` as a field selector function, similar to H98).

Ah, not quite. In DORF, the phantom type is an implicit, magical type,
but in TIR it's an explicit, declared type.

In DORF, either the magical type is in scope, or not; in the former
case, it might clash with a user-defined type, and in the latter, if I
wish to call set, how shall I type its argument?

In TIR, the key type is user-defined, so if there be a clash, then the
user is at fault.

 To make `x` a selector function instead, you'd go:
 x = (.) X   -- or probably x = get X, see below
 Which is exactly the same as DORF (after adjusting for the different order
 of
 arguments).

True.

 And presumably instead of X you'd want a LongandMeaningfulLabel?

No! Real Programmers never choose such names!

I jest. Yes, plainly, I would. X is just an example.

 And if your
 data Customer_id = Customer_id
 was always an Int field, wouldn't it help the reader and the compiler to say
 that? (That's the main extra part in fieldLabels.)

It might help the reader, but so would a simple comment. Nevertheless,
this is fair.

It might help the compiler, but that's an argument by premature
optimization, I think (^_~)

 I think you don't want all those type vars in your record decls -- but only
 vars for the mutatable types, like this:

   type R c = { X ::. Int, Y::. String, Z ::. c, ... }

 Then you don't need a Quasifunctor instance for every field, only the
 mutatable ones.

Yes, I know. That is just a very general example.

 Oh, and how do you deal with multiple record constructors as in H98:
data T a = T1 { x :: a, y :: Bool }
 | T2 { x :: a }

 It wouldn't work to have a different record type for each constructor, 'cos
 you'd turn functions that use them from mono to polymorphic (overloaded --
 needing a class and instances).

Not sure what you mean. With an argument of such a multiconstructed
type, I would do as ever in Haskell: pattern-match.

 You don't give full details for your Has instances, but presumably you'd do
 the same equality constraint style as SORF and DORF.

I assume you mean
instance (v~a) = Has k v (R a) where ...

I'm not sure why we need this, but I assume that we do, since it was
written by SPJ, so yes.

 I think you still need method get and sugar to turn the dot notation into a
 call to get. Having method (.) will usurp altogether dot as function
 composition -- you'll make a lot of enemies! And we need tight binding for
 dot
 notation, so we might as well treat it as special syntax.

Not need. (.) is quite a valid name. Nevertheless, this is fair. I
meant dot as an example (though one that might ultimately be chosen).
I like bang, myself; others seem to favour get. The trouble is, in the
latter case, that we'd need to change certain widely-used libraries...

 You don't show how you'd do record update.

Yep. It's on the wiki.
qfmap X f r is r mutated by f at X

 The litmus test is what is the
 type
 for:
 r{ X = True }
 That is: update record r, set its X field to True.

This is written as
qfmap X (const True) (r :: r) :: Quasifunctor X a Bool r s = s;

 AntC

Cheers,
strake

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


Records in Haskell: Type-Indexed Records (another proposal)

2012-03-03 Thread Matthew Farkas-Dyck
Hello all.

I wrote a new proposal for the Haskell record system. It can be found
at http://hackage.haskell.org/trac/ghc/wiki/Records/TypeIndexedRecords

Records are indexed by arbitrary Haskell types. Scope is controlled as
scope of key types. No fieldLabel declarations needed (as in DORF).

Cheers,
strake

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


[Haskell-cafe] Records in Haskell: Type-Indexed Records (another proposal)

2012-03-03 Thread Matthew Farkas-Dyck
Hello all.

I wrote a new proposal for the Haskell record system. It can be found
at http://hackage.haskell.org/trac/ghc/wiki/Records/TypeIndexedRecords

Records are indexed by arbitrary Haskell types. Scope is controlled as
scope of key types. No fieldLabel declarations needed (as in DORF).

Cheers,
strake

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


Re: [arch-haskell] [arch-general] (for Vesa and other Arch Devs on the list) Re: GHC 7.4.1 or HP 2011.4.0.0??

2012-02-22 Thread Matthew Farkas-Dyck
Drop HP. If I want a certain package, I'll get it myself.

Cheers,
MFD

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


Re: [Haskell-cafe] Rewrite this imperative in FP way

2012-02-05 Thread Matthew Farkas-Dyck
On Sun, Feb 5, 2012 at 2:28 PM, Haisheng Wu fre...@gmail.com wrote:
 for i in b:
   for j in c:
 if (i+j)3:
   d[i+j] += a[i]

 Do you have any cool solution in FP way?

Not sure whether this is cool, but here it is nonetheless:

a = repeat 1;
b = [0..3];
c = [0,2];
d = map (sum ∘ map ((a !!) ∘ fromIntegral) ∘ ($ (filter (3) ∘ map sum
∘ sequence) [b,c]) ∘ filter ∘ (≡)) [1..];

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


Re: [Haskell-cafe] Exceeding OS limits for simultaneous socket connections

2012-02-03 Thread Matthew Farkas-Dyck
Rob Stewart wrote:
 transmitting thousands of messages to each other, sometimes within a small 
 period of time.

Either SCTP or UDP seems far more appropriate than TCP (which I
assume, hopefully safely, to be at work here) for this task.

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


Re: Posting etiquette, was Re: Records in Haskell

2012-01-19 Thread Matthew Farkas-Dyck
On 19/01/2012, Malcolm Wallace malcolm.wall...@me.com wrote:
 I find it completely unreasonable for a reply to a very long post to quote
 the entire text, only to add a single line at the bottom (or worse, embedded
 in the middle somewhere).  In this case, there are 7 pages of quotation
 before your one-sentence contribution.  (That is on my laptop.  I dread to
 think how many pages it represents on a smartphone screen...)  Usually, if I
 need to scroll even to the second page-worth of quotation and have still not
 found any new text, I now just delete the post without reading it.

 Regards,
 Malcolm


Sorry.

The reason that I have done so is that my primary mail client (GMail
web) automatically folds quoted text (marked by  at start of line).
(I'm not sure whether my secondary client (mutt) can do so.)

When I first saw this message, I thought I would be slammed for
top-posts (I have been guilty a few times).

Anyhow, I shall keep this in mind.

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


Re: Type operators in GHC

2012-01-19 Thread Matthew Farkas-Dyck
On 19/01/2012, Joachim Breitner m...@joachim-breitner.de wrote:
 (I have no good idea, but here is at least one: A dot '.' as the first
 character indicates a type variable; compared to a ':' this is a
 non-capitalized character).

So that all symbols that start in dot are variables, and all others
are types/constructors?

 Also, is there maybe another way of distinguishing constructors and
 variables, besides capitalization, that works equally well for operators
 and non-operators? That could also help if a user would like to use
 unicode characters in the name of a constructor that are letters but
 don’t have a upper or titlecase variant. But then, this has probably
 been given thought a long time ago, without a better solution than
 capitalization resp. leading ':'.

Sometimes I thought to use ∀ to quantify over type variables, as
over term variables, at least as an option.

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


Re: Type operators in GHC

2012-01-19 Thread Matthew Farkas-Dyck
On 19/01/2012, Ian Lynagh ig...@earth.li wrote:
 Do you mean that in

 f :: (x, X, (+), (:+))

 only x would be a type variable and X, (+), (:+) would be type
 constructors, but that in

 g :: forall y, Y, (*), (:*) .
  (x, X, (+), (:+), y, Y, (*), (:*))

 y, Y, (*), (:*) would be type variables and x, X, (+), (:+) would be
 whatever is in scope (constructors, unless there is an enclosing forall
 that binds them)?

Just so.

 Perhaps we should be heading towards a case-insensitive syntax for type
 names.

I've often had that thought myself, for types and terms both. It would
make it much nicer to do general numeric computations in Haskell (e.g.
fluid mechanics) since one could use upper-case term names, which are
often customary. I actually designed a compiled-to-Haskell language
for just this reason (for fluid mechanics lab), but it's very crude.

That said, for word-names, the case-sensitive system we have is nice and brief.


 Thanks
 Ian


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


Re: Records in Haskell

2012-01-18 Thread Matthew Farkas-Dyck
On 18/01/2012, Gábor Lehel illiss...@gmail.com wrote:
 (I *am*, however, uncomfortable with using straight-up type level
 strings, without consideration for any particular alternative. If
 nothing else they should at least be opaque symbols which can be
 passed around and used in the supported contexts but not manipulated
 as strings. String-based hackery should be left to Template Haskell,
 and out of the type system. I can't really express at the moment why
 in particular I think it would be bad, but it feels like it would be
 bad.)


I strongly agree; plus, it's awkward (and ugly) that a selector be
desugarred to a type-level string of its key identifier, as if it were
some perverse quasiliteral.

The trouble is, if they were opaque, then how could a function be
polymorphic over all records with a certain member, with defined
semantics? How could one tell the compiler that the semantics of all
such members are the same? One must define a name, and then the
problem of namespace non-interoperability that is now a great bother
would be a greater bother yet.

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


Re: Records in Haskell

2012-01-18 Thread Matthew Farkas-Dyck
On 18/01/2012, Simon Peyton-Jones simo...@microsoft.com wrote:
 |  Has *is* a type class. It can be used and abused like any other.
 |  Record members with the same key ought to have the same semantics; the
 |  programmer must ensure this, not just call them all x or the like.
 | 
 |  Weak types these are not. The selector type is well-defined. The value
 |  type is well-defined. The record type is well-defined, but of course
 |  we define a type-class to let it be polymorphic.

 I want to mention that the issue Greg raises here is tackled under
 Representation hiding.

 The way we currently prevent random clients of a data type from selecting
 its foo field is by hiding the record selector foo. Similarly for its
 data constructors. This is Haskell's way of doing data abstraction; it may
 not be the best way, but it's Haskell's way.

 The trouble with instance declarations is that they are *always* exported.
 No hiding.

Yes. This is a fault.

I found a document, Controlling the scope of instances in Haskell,
by Gontijo and Camarão, whose goal is to solve this very problem.

http://www.dcc.ufmg.br/~camarao/controlling-the-scope-of-instances-in-Haskell-sblp2011.pdf

The link seems broken, but if so, and anyone should want a copy, feel
free to tell me and I shall send it. The size is 244 KB.

 Under Representation hiding I suggest that

 * If the record selector foo is in scope (by any name),
   then the corresponding Has instance is in scope too
   and vice versa.

 That would match up with Haskell's hiding mechanisms precisely, albeit at
 the cost of having an ad-hoc rule for Has instances.

 Simon



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


Re: [Haskell-cafe] implementing a text editor swap file

2012-01-17 Thread Matthew Farkas-Dyck
http://hackage.haskell.org/package/bytestring-mmap


On 17/01/2012, Martin DeMello martindeme...@gmail.com wrote:
 I'm writing a gtk2hs-based text editor, and would like to implement
 continuous (swap-file based) autosave the way vim and emacs do it. Any
 suggestions for how to implement this in a cross-platform manner?

 Also, is there a library that returns standard config file locations
 on a per-platform basis?

 martin

 ___
 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] implementing a text editor swap file

2012-01-17 Thread Matthew Farkas-Dyck
On 17/01/2012, Erik de Castro Lopo mle...@mega-nerd.com wrote:
 Matthew Farkas-Dyck wrote:

 http://hackage.haskell.org/package/bytestring-mmap

 Since he's editing text, its a pity there isn't a text-mmap
 package :-).

Yeah, I had the same thought.

 Erik
 --
 --
 Erik de Castro Lopo
 http://www.mega-nerd.com/

 ___
 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: Records in Haskell

2012-01-13 Thread Matthew Farkas-Dyck
On 13/01/2012, Simon Peyton-Jones simo...@microsoft.com wrote:
 Thanks to Greg for leading the records debate.  I apologise that I
 don't have enough bandwidth to make more than an occasional
 contribution.  Greg's new wiki page, and the discussion so far has
 clarified my thinking, and this message tries to express that new
 clarity.  I put a conclusion at the end.

 Simon

 Overview
 
 It has become clear that there are two elements to pretty much all the
 proposals we have on the table.  Suppose we have two types, 'S' and 'T',
 both with a field 'f', and you want to select field 'f' from a record 'r'.
 Somehow you have to disambiguate which 'f' you mean.

 (Plan A) Disambiguate using qualified names.  To select field f, say
 (S.f r) or (T.f r) respectively.

 (Plan B) Disambiguate using types. This approach usually implies
 dot-notation.
  If  (r::S), then (r.f) uses the 'f' from 'S', and similarly if
 (r::T).

 Note that

 * The Frege-derived records proposal (FDR), uses both (A) and (B)
   http://hackage.haskell.org/trac/ghc/wiki/Records/NameSpacing

 * The Simple Overloaded Record Fields (SORF) proposal uses only (B)
   http://hackage.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields

 * The Type Directed Name Resolution proposal (TDNR) uses only (B)

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

 I know of no proposal that advocates only (A).  It seems that we are agreed
 that we must make use of types to disambigute common cases.

 Complexities of (Plan B)
 
 Proposal (Plan B) sounds innocent enough.  But I promise you, it isn't.
 There has ben some mention of the left-to-right bias of Frege type
 inference engine; indeed the wohle explanation of which programs are
 accepted and which are rejected, inherently involves an understanding
 of the type inference algorithm.  This is a Very Bad Thing when the
 type inference algorithm gets complicated, and GHC's is certainly
 complicated.

 Here's an example:

type family F a b
data instance F Int [a] = Mk { f :: Int }

g :: F Int b  - ()
h :: F a [Bool] - ()

k x = (g x, x.f, h x)

 Consider type inference on k.  Initially we know nothing about the
 type of x.
  * From the application (g x) we learn that x's type has
shape (F Int something).
  * From the application (h x) we learn that x's type has
shape (F something else [Bool])
  * Hence x's type must be (F Int [Bool])
  * And hence, using the data family we can see which field
f is intended.

 Notice that
  a) Neither left to right nor right to left would suffice
  b) There is significant interaction with type/data families
 (and I can give you more examples with classes and GADTs)
  c) In passing we note that it is totally unclear how (Plan A)
 would deal with data families

 This looks like a swamp.  In a simple Hindley-Milner typed language
 you might get away with some informal heuristics, but Haskell is far
 too complicated.

 Fortunately we know exactly what to do; it is described in some detail
 in our paper Modular type inference with local assumptions
 http://www.haskell.org/haskellwiki/Simonpj/Talk:OutsideIn

 The trick is to *defer* all these decisions by generating *type constraints*
 and solving them later.  We express it like this:

G, r:t1  |-  r.f : t2,  (Has t1 f t2)

 This says that if r is in scope with type t1, then (r.f) has type t2,
 plus the constraint (Has t1 f t2), which we read as saying

Type t1 must have a field f of type t2

 We gather up all the constraints and solve them.  In solving them
 we may figure out t1 from some *other* constraint (to the left or
 right, it's immaterial. That allow us to solve *this* constraint.

 So it's all quite simple, uniform, and beautiful.  It'll fit right
 into GHC's type-constraint solver.

 But note what has happened: we have simply re-invented SORF.  So the
 conclusion is this:

the only sensible way to implement FDR is using SORF.

 What about overloading?
 ~~~
 A feature of SORF is that you can write functions like this

k :: Has r f Int = r - Int
k r = r.f + 1

 Function 'k' works on any record that has a field 'f'.  This may be
 cool, but it wasn't part of our original goal.  And indeed neither FDR
 nor TDNR offer it.

 But, the Has constraints MUST exist, in full glory, in the constraint
 solver.  The only question is whether you can *abstract* over them.
 Imagine having a Num class that you could not abstract over. So you
 could write

k1 x = x + x :: Float
k2 x = x + x :: Integer
k3 x = x + x :: Int

 using the same '+' every time, which generates a Num constraint. The
 type signature fixes the type to Float, Integer, Int respectively, and
 tells you which '+' to use.  And that is exactly what ML does!

 But Haskell doesn't.  The Coolest Thing about Haskell is that you get
 to *abstract* over those Num constraints, so you can write

   k :: Num a = a 

Re: Composition operator [was: Re: Records in Haskell]

2012-01-13 Thread Matthew Farkas-Dyck
On 12/01/2012, Morten Brodersen morten.broder...@constrainttec.com wrote:
 Even if Unicode is not required, there is still a fallout. Let's look at
 a simple scenario:

 Somebody uploads a nice useful Haskell module that include a number of
 Unicode symbols.

 Unfortunately most unix/windows/tools/source controls/editors out there
 are Ascii only.

If so, most unix/windows/tools/source controls/editors out there are broken.

 So people who wants to use the module now potentially need to convert
 the code to Ascii (and potentially back again) in order to use it with
 non-Unicode tools.

No, people need to get Unicode (or, better yet, when possible,
code-agnostic) tools.

 Yes it is *of course* doable but all of that just because of a
 *relatively simple problem to do with how you access record fields? Really?

 That is IMHO a clear example of shooting birds with nuclear rockets.

 Let me suggest that a simple non-nuclear alternative would be for people
 interested in Unicode symbols to use an editor that auto converts from
 Haskell Ascii to Haskell Unicode when loading and (of course) back again
 when saving. You can do that today. You can even pick your own Ascii
 from/to Unicode mapping. No need to argue about whether a symbol is
 prettier than another. All of this without forcing the rest of the
 (couldn't care less about record access syntax) Haskell community to
 have to deal with Unicode :-)

That is (in my opinion) a clear example of shooting foes in heavy
armour with bird-shot. From a muzzle-loader.

 Morten

 On 13/01/12 14:43, Brandon Allbery wrote:
 On Thu, Jan 12, 2012 at 22:32, Morten Brodersen
 morten.broder...@constrainttec.com
 mailto:morten.broder...@constrainttec.com wrote:

 Requiring unicode characters for the Haskell syntax to solve a
 *relatively* simple problem is a bad bad idea.


 Nobody said anything about requiring it.

 --
 brandon s allbery allber...@gmail.com mailto:allber...@gmail.com
 wandering unix systems administrator (available) (412) 475-9364 vm/sms




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


Re: Composition operator [was: Re: Records in Haskell]

2012-01-13 Thread Matthew Farkas-Dyck
On 13/01/2012, Herbert Valerio Riedel h...@gnu.org wrote:
 On Fri, 2012-01-13 at 15:16 +1100, Morten Brodersen wrote:
 Unfortunately most unix/windows/tools/source controls/editors out
 there are Ascii only.

 So after about 20 years the unicode standard has been around, the
 quantification most still applies? Maybe I'm using a
 non-representative platform, but every tool for manipulating source-code
 I use nowadays has support for the unicode charset w/ with at least the
 utf8 encoding...

This is my experience also.

 -- hvr


 ___
 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: Records in Haskell

2012-01-12 Thread Matthew Farkas-Dyck
On 09/01/2012, Greg Weber g...@gregweber.info wrote:
 Thank you for all your feedback! I updated the wiki page accordingly.

 Let us stop and take note of what this feedback is about: the most
 convenient syntax for manipulating records, and much of this feedback
 applies to any records proposal. That is, there are no fundamental
 objections to the implementation of this records implementation. If you
 give this kind of general feedback then I assume you are fine with the
 name-spacing records implementation.

 At this point I feel we are largely waiting on feedback from implementers
 to give the implementation critiques or a green light.

 But that does not need to stop us from continuing our discussion of the
 best syntax for using records.
 For the left-right, right-left issue, I added a discussion and potential
 solution through partial application:

 Partial application provides a potential solution:

(b . .a) r

 So if we have a function f r = b r.a then one can write it points-free:

b . .a

 Our longer example from above:

e . d . .c . .b . .a

 At first glance it may look odd, but it is starting to grow on me. Let us
 consider more realistic usage with longer names:

echo . delta . .charlie . .beta . .alpha

 Is there are more convenient syntax for this? b .a
 Note that a move to a different operator for function composition
 (discussed in dot operator section) would make things easier to parse:

b ~ .a

 where the unicode dot might be even nicer.

I told you so (^_^)

Unicode dot (∘) would be optimal, since that's what it's for. If to
type '∘' is awkward, then one can use (Control.Category.). We need
not (and, in my opinion, should not) define another operator.

 On Mon, Jan 9, 2012 at 3:15 AM, wren ng thornton w...@freegeek.org wrote:

 quux (y . (foo.  bar).baz (f . g)) moo
 It's not that easy to distinguish from
 quux (y . (foo.  bar) . baz (f . g)) moo



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


Re: Records in Haskell

2012-01-12 Thread Matthew Farkas-Dyck
On 09/01/2012, Isaac Dupree m...@isaac.cedarswampstudios.org wrote:
 You mean this wiki page, right?:
 http://hackage.haskell.org/trac/ghc/wiki/Records/NameSpacing

 That is, there are no fundamental
 objections to the implementation of this records implementation.

 I think that might be overly optimistic... I think there's a risk that
 SPJ finds an irritating complication to type inference  the rest of us
 aren't type-system-savvy enough to continue trying to guess at that :)
 But I think you're referring to whether we object to ad-hoc overloading
 of record field names (neither parametric nor class-based polymorphism),
 if no difficulties crop up.  Some of the concerns on
 http://www.haskell.org/haskellwiki/TypeDirectedNameResolution apply --
 I'm not sure to what extent, but address those concerns rather than
 require those people to repeat themselves again! :)

 (If we dodge all those obstacles, well, a better record system is better!)


 Regardless, I think the proposal needs more precision, so I tried for
 syntax.  And got this thousand word email just about syntax, in several
 sections of reasoning, sorry!

 --so here are my conclusions/suggestions up front in case you prefer,
 most complicated first - look later for details in a different order,
 referenced by [number].


 Given that type inference for expr.field decides between several
 different possible meanings of field, which fields in scope count as
 possibilities?  I concluded All identifiers 'field' in top-level scope
 (i.e. declared in this module or imported unqualified from another
 module), but no local let/lambda bindings. [1]

 I have an unrelated record/module system tweak suggestion to prevent
 leaks of the field-ness of exports meant only as functions. [2]

 .field, for any identifier field, is a postfix operator that binds
 more tightly than function application. [1]

 I don't care whether the expression and .field are permitted to be
 separated by whitespace or not. [4]

 (.field) as a section: should it always require parentheses? (assuming
 there is a way to type-inference the unapplied dot operator usefully at
 all). [3]

 The Type.{...} / expr.{...} variations look probably fine (Syntax for
 updates in the wiki). [5]

 Allow TyCon.field for selecting a specific version of field, but
 only if there isn't a module in scope as TyCon in which case it's
 interpreted as Module.field. [7]

 Allow expr.TyCon.field / expr.Module.field wherever expr.field is
 allowed. [8]

 I bikesheddily suggest field@expr rather than expr.field (I'd be
 alright with either/both). [6]




 = Defining the basic dot syntax for record field selection =

 [1]
 .x, for any identifier x, is a postfix operator that binds more tightly
 than function application.  This operator does not constrain the type of
 its operand or its result.  After regular type inference, the type
 system collects in-scope xs and does something to try to choose one.

 (As a non-type-system-expert, I'm not addressing what does something
 means in this email, besides capitalizing TYPE INFERENCE where I suspect
 there might (or might not) be extra problems.  Anyway, I wish the
 algorithm do the right thing for expr.x.y.z.)


 But which in-scope xes does it collect?  Regular Haskell scope would
 completely break let x = var.x if we wished to allow let x = var.x.

 How about: all record fields 'x' declared in this module or imported
 (qualified[??] or unqualified) from another module.

 [[[
 Should qualified ones be allowed?
 Pro: if you import Data.Map qualified, as is common (let's just pretend
 that Maps have members), then someMap.field works.

 Pro: it's like allowing qualified imports for instance declaration
 class-member-definitions.

 Con: it's not really like that. It makes qualified imports a weaker
 protection, as the class/instance exception can lead to no ambiguity,
 but this can lead to ambiguity.  The PVP would make a sad face.

 Con: using unqualified import with (..) would easily bring the field
 names into scope.  Fictitiously, import qualified Data.Map as Map;
 import Data.Map(Map(..)).

 Observation: allowing qualified imports, but not following the
 class/instance system's style of including everything in the transitive
 closure of imported modules, still prevents you (Pro) from breaking
 intentional abstraction barriers, but (Con?) requires you to import the
 operators for types you receive but don't import.

 Opinion: only unqualified imports should be part of the selection process.
 ]]]

 [[[
 Problem: Restricting the selection to only record fields further
 compromises an existing imperfect property of Haskell:
 module Library (Type, constructor, deconstructor) where
 data Type = Constructor { deconstructor :: Int }
 -- let's pretend it's a bounds-limited int or such.
 constructor int | int = 3  int  17 = Constructor int

 Currently, importers of the module can observe that 'deconstructor' is a
 record-field by importing Library(Type(..)) and getting 

Re: Records in Haskell

2012-01-12 Thread Matthew Farkas-Dyck
On 12/01/2012, Greg Weber g...@gregweber.info wrote:
 I added this and your Control.Category. to the wiki.

Thanks.

 I am not sure about the tuple proposal - tuples normally imply an ordering,
 which would imply that all record fields must be accounted for at least
 with an empty comma or an underscore, particularly if updating the last
 field in a record. For records we want a syntax where we can pick out one
 or many fields to update and ignore the rest.

Sorry, my proposal was unclear. This is not what I meant; rather, I
meant that one could write
let r.(x, y) = (x', y')
whatever other fields might be in r. I clarify further on the wiki.

That said, I notice now that this syntax is quite verbose, far more so
than the .{} syntax, which is a loss. I think the brevity worth the
added complexity.

 My feeling on  is that ~ is slightly more intuitive than  because it
 looks like an arrow which I equate with functions, and  is more
 difficult to parse because I have to recognize three in a row of the same
 character . However, if everyone likes using the unicode dot, then it
 doesn't matter what the non-unicode symbol is, and re-using existing
 symbols is certainly advantageous.



 On Thu, Jan 12, 2012 at 10:02 AM, Matthew Farkas-Dyck
 strake...@gmail.comwrote:

 On 09/01/2012, Isaac Dupree m...@isaac.cedarswampstudios.org wrote:
  You mean this wiki page, right?:
  http://hackage.haskell.org/trac/ghc/wiki/Records/NameSpacing
 
  That is, there are no fundamental
  objections to the implementation of this records implementation.
 
  I think that might be overly optimistic... I think there's a risk that
  SPJ finds an irritating complication to type inference  the rest of us
  aren't type-system-savvy enough to continue trying to guess at that :)
  But I think you're referring to whether we object to ad-hoc overloading
  of record field names (neither parametric nor class-based polymorphism),
  if no difficulties crop up.  Some of the concerns on
  http://www.haskell.org/haskellwiki/TypeDirectedNameResolution apply --
  I'm not sure to what extent, but address those concerns rather than
  require those people to repeat themselves again! :)
 
  (If we dodge all those obstacles, well, a better record system is
 better!)
 
 
  Regardless, I think the proposal needs more precision, so I tried for
  syntax.  And got this thousand word email just about syntax, in several
  sections of reasoning, sorry!
 
  --so here are my conclusions/suggestions up front in case you prefer,
  most complicated first - look later for details in a different order,
  referenced by [number].
 
 
  Given that type inference for expr.field decides between several
  different possible meanings of field, which fields in scope count as
  possibilities?  I concluded All identifiers 'field' in top-level scope
  (i.e. declared in this module or imported unqualified from another
  module), but no local let/lambda bindings. [1]
 
  I have an unrelated record/module system tweak suggestion to prevent
  leaks of the field-ness of exports meant only as functions. [2]
 
  .field, for any identifier field, is a postfix operator that binds
  more tightly than function application. [1]
 
  I don't care whether the expression and .field are permitted to be
  separated by whitespace or not. [4]
 
  (.field) as a section: should it always require parentheses? (assuming
  there is a way to type-inference the unapplied dot operator usefully at
  all). [3]
 
  The Type.{...} / expr.{...} variations look probably fine (Syntax for
  updates in the wiki). [5]
 
  Allow TyCon.field for selecting a specific version of field, but
  only if there isn't a module in scope as TyCon in which case it's
  interpreted as Module.field. [7]
 
  Allow expr.TyCon.field / expr.Module.field wherever expr.field is
  allowed. [8]
 
  I bikesheddily suggest field@expr rather than expr.field (I'd be
  alright with either/both). [6]
 
 
 
 
  = Defining the basic dot syntax for record field selection =
 
  [1]
  .x, for any identifier x, is a postfix operator that binds more tightly
  than function application.  This operator does not constrain the type of
  its operand or its result.  After regular type inference, the type
  system collects in-scope xs and does something to try to choose one.
 
  (As a non-type-system-expert, I'm not addressing what does something
  means in this email, besides capitalizing TYPE INFERENCE where I suspect
  there might (or might not) be extra problems.  Anyway, I wish the
  algorithm do the right thing for expr.x.y.z.)
 
 
  But which in-scope xes does it collect?  Regular Haskell scope would
  completely break let x = var.x if we wished to allow let x = var.x.
 
  How about: all record fields 'x' declared in this module or imported
  (qualified[??] or unqualified) from another module.
 
  [[[
  Should qualified ones be allowed?
  Pro: if you import Data.Map qualified, as is common (let's just pretend
  that Maps have members

Re: Records in Haskell

2012-01-08 Thread Matthew Farkas-Dyck
On 08/01/2012, Gábor Lehel illiss...@gmail.com wrote:
 2012/1/8 Greg Weber g...@gregweber.info:


 2012/1/8 Gábor Lehel illiss...@gmail.com

 Thank you. I have a few questions/comments.



 The module/record ambiguity is dealt with in Frege by preferring
 modules and requiring a module prefix for the record if there is
 ambiguity.

 I think I see why they do it this way (otherwise you can't refer to a
 module if a record by the same name is in scope), but on the other
 hand it would seem intuitive to me to choose the more specific thing,
 and a record feels more specific than a module. Maybe you could go
 that way and just not give your qualified imports the same name as a
 record? (Unqualified imports are in practice going to be hierarchical,
 and no one's in the habit of typing those out to disambiguate things,
 so I don't think it really matters if qualified records shadow them.)


 In the case where a Record has the same name as its containing module it
 would be more specific than a module, and preferring it makes sense. I
 think
 doing this inside the module makes sense, as one shouldn't need to refer
 to
 the containing module's name. We should think more about the case where
 module  records are imported.



 Expressions of the form x.n: first infer the type of x. If this is
 just an unbound type variable (i.e. the type is unknown yet), then
 check if n is an overloaded name (i.e. a class operation). [...] Under
 no circumstances, however, will the notation x.n contribute in any way
 in inferring the type of x, except for the case when n is a class
 operation, where an appropriate class constraint is generated.

 Is this just a simple translation from x.n to n x? What's the
 rationale for allowing the x.n syntax for, in addition to record
 fields, class methods specifically, but no other functions?


 It is a simple translation from x.n to T.n x
 The key point being the function is only accessible through the record's
 namespace.
 The dot is only being used to tap into a namespace, and is not available
 for
 general function application.

 I think my question and your answer are walking past each other here.
 Let me rephrase. The wiki page implies that in addition to using the
 dot to tap into a namespace, you can also use it for general function
 application in the specific case where the function is a class method
 (appropriate class constraint is generated etc etc). I don't
 understand why. Or am I misunderstanding?






 Later on you write that the names of record fields are only accessible
 from the record's namespace and via record syntax, but not from the
 global scope. For Haskell I think it would make sense to reverse this
 decision. On the one hand, it would keep backwards compatibility; on
 the other hand, Haskell code is already written to avoid name clashes
 between record fields, so it wouldn't introduce new problems. Large
 gain, little pain. You could use the global-namespace function as you
 do now, at the risk of ambiguity, or you could use the new record
 syntax and avoid it. (If you were to also allow x.n syntax for
 arbitrary functions, this could lead to ambiguity again... you could
 solve it by preferring a record field belonging to the inferred type
 over a function if both are available, but (at least in my current
 state of ignorance) I would prefer to just not allow x.n for anything
 other than record fields.)


 Perhaps you can give some example code for what you have in mind - we do
 need to figure out the preferred technique for interacting with old-style
 records. Keep in mind that for new records the entire point is that they
 must be name-spaced. A module could certainly export top-level functions
 equivalent to how records work now (we could have a helper that generates
 those functions).

 Let's say you have a record.

 data Record = Record { field :: String }

 In existing Haskell, you refer to the accessor function as 'field' and
 to the contents of the field as 'field r', where 'r' is a value of
 type Record. With your proposal, you refer to the accessor function as
 'Record.field' and to the contents of the field as either
 'Record.field r' or 'r.field'. The point is that I see no conflict or
 drawback in allowing all of these at the same time. Writing 'field' or
 'field r' would work exactly as it already does, and be ambiguous if
 there is more than one record field with the same name in scope. In
 practice, existing code is already written to avoid this ambiguity so
 it would continue to work. Or you could write 'Record.field r' or
 'r.field', which would work as the proposal describes and remove the
 ambiguity, and work even in the presence of multiple record fields
 with the same name in scope.

 The point is that I see what you gain by allowing record fields to be
 referred to in a namespaced way, but I don't see what you gain by not
 allowing them to be referred to in a non-namespaced way. In theory you
 wouldn't care because the non-namespaced way is 

[Haskell-cafe] Monadic computation must now do IO, fails when type changed to IO.

2012-01-05 Thread Matthew Farkas-Dyck
Dear fellow Haskellers,

I have written an SMTP server (Main.hs at http://hpaste.org/56134,
full git repo at http://strake.zanity.net:1104/ymail.git), which
works, mostly – it responds to every message with that it was sent
properly, whether it was or not. (Try it: send an e-mail by SMTP to
this_is_not_a_u...@strake.zanity.net or somesuch.) The reason is, that
it simply tells the message (envelope, data) in a Writer monad, which
is later piped to the local delivery agent.

As I said, this works, but of course is suboptimal. I tried to change
the type of main_ to
(MonadState MTPState m, MonadIO m) = [Char] - m ([Char], [Char]),
just calling LDA in main_ (when mode is MTPTextMode) rather than
after, but then the program output nil.

I'm not sure what the problem is – I thought IO might not be lazy
enough so I tried a lazy wrapped-IO monad, in vain.

How, then, can this program call the LDA, wait to know whether it
worked or failed, and then respond?

Thanks for any help.

Cheers,
M Farkas-Dyck

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


Re: Records in Haskell

2012-01-02 Thread Matthew Farkas-Dyck
On 02/01/2012, Simon Peyton-Jones simo...@microsoft.com wrote:
 It seems to me that there's only one essential missing language feature,
 which is appropriately-kinded type-level strings (and, ideally, the ability
 to reflect these strings back down to the value level). Given that, template
 haskell, and the HList bag of tricks, I'm confident that  a fair number of
 elegant records packages can be crafted. Based on that experience, we can
 then decide what syntactic sugar would be useful to elide the TH layer
 altogether.

 I think we can do this part without much trouble, once the dust has settled
 on -XPolyKinds.  It certainly fits with all the work we've been doing
 recently on the kind system. I agree that it's a fairly basic requirement;
 for example, it's also assumed by
 http://hackage.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields

 Specifically

 *Allow String as a new kind


 *Now you can define classes or types with kinds like

 MyCls :: String - a - Constraint

 T :: String - *


 *Provide type-level string literals, so that foo :: String

 Open questions:

 *Is String (at the kind level) a synonym for [Char]?  I'm inclined
 *not* to do this initially, because it would require us to have promoted
 character literals too -- and the implementation of record labels as strings
 of type-level cons-cells is not going to be efficient.

 *If String is not a kind level synonym for [Char], maybe it should
 have a different name.  For example,   foo :: Label?  Or Atom?   After
 all, if it doesn't behave like a Haskell string it probably should not have
 the same name.

I agree. In this case, though, I think we ought to allow
kind-polymorphic quoted type-level literals, thus:
foobar :: Label
or
foobar :: String
at least.

 *Are there any operations over Labels?

 *I don't know exactly what you have in mean by the ability to
 reflect the type-level string at the value level.

 Simon

 From: Gershom Bazerman [mailto:gersh...@gmail.com]
 Sent: 31 December 2011 19:12
 To: Simon Peyton-Jones
 Cc: Greg Weber; glasgow-haskell-users@haskell.org
 Subject: Re: Records in Haskell

 On Dec 31, 2011, at 1:28 PM, Simon Peyton-Jones wrote:
 The trouble is that I just don't have the bandwidth (or, if I'm honest, the
 motivation) to drive this through to a conclusion. And if no one else does
 either, perhaps it isn't *that* important to anyone.  That said, it clearly
 is *somewhat* important to a lot of people, so doing nothing isn't very
 satisfactory either.

 Usually I feel I know how to move forward, but here I don't.

 Simon
 It seems to me that there's only one essential missing language feature,
 which is appropriately-kinded type-level strings (and, ideally, the ability
 to reflect these strings back down to the value level). Given that, template
 haskell, and the HList bag of tricks, I'm confident that  a fair number of
 elegant records packages can be crafted. Based on that experience, we can
 then decide what syntactic sugar would be useful to elide the TH layer
 altogether.

 Beyond that, it would really help namespacing in general to appropriately
 extend the module system to allow multiple modules to be declared within a
 single file -- or, better yet, submodules. I know that this introduces a
 few corner cases that need to be thought through -- what happens with
 overlapping declarations, for example. But I tend to think the path here is
 relatively straightforward and obvious, and the added expressive power
 should make namespacing issues much more tractable. Like the type-level
 strings proposal, this isn't about implementing records as such -- rather,
 it's about generally extending the expressive power of the language so that
 record systems--among other things--are easier to write.

 Cheers,
 Gershom


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


Re: Records in Haskell

2011-12-31 Thread Matthew Farkas-Dyck
 It seems to me that there's only one essential missing language feature,
 which is appropriately-kinded type-level strings

Isn't this possible now with type → kind promotion?

 Cheers,
 Gershom

Cheers, (and Happy New Year),
MFD

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


Re: Records in Haskell

2011-12-30 Thread Matthew Farkas-Dyck
On 30/12/2011, Andriy Polischuk quux...@gmail.com wrote:
 Yet another idea:
 Consider using '\' as record access operator. No conflicts with anything at
 all, and,
 moreover, it really looks like hierarchical access. Reminds of filesystems
 though.

I hope this is a joke.


 Matthew Farkas-Dyck wrote

 Another thought:
 Perhaps bang as record selection operator. It would avoid further
 corner cases of dot, and it's not unprecedented in Haskell (e.g.
 Data.Map.!).



 --
 View this message in context:
 http://haskell.1045720.n5.nabble.com/Records-in-Haskell-tp4806095p5109437.html
 Sent from the Haskell - Glasgow-haskell-users mailing list archive at
 Nabble.com.

 ___
 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: Records in Haskell

2011-12-30 Thread Matthew Farkas-Dyck
Certainly not no conflicts: lambda expressions.


On 30/12/2011, Colin Adams colinpaulad...@gmail.com wrote:
 On 30 December 2011 15:55, Matthew Farkas-Dyck strake...@gmail.com wrote:

 On 30/12/2011, Andriy Polischuk quux...@gmail.com wrote:
  Yet another idea:
  Consider using '\' as record access operator. No conflicts with anything
 at
  all, and,
  moreover, it really looks like hierarchical access. Reminds of
 filesystems
  though.

 I hope this is a joke.


 Why?


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


Re: Records in Haskell

2011-12-30 Thread Matthew Farkas-Dyck
On 30/12/2011, Andriy Polischuk quux...@gmail.com wrote:
 You're right, i should have written ambiguities instead.
 That was not joke, just i somehow didn't notice Chris Smith answer.

Hm. I though at first that if backslash were the selection operator,
then there must be programs of unclear semantics, but actually I can't
find any.

I'm sorry if my earlier message seemed unkind, by the way; it wasn't
meant to be.

 However, I think, there are some drawbacks in using dot for that in
 comparison with qualified imports access. The latter is easier to
 distinguish from composition by eye, because module-identifier is always one
 word, starting from uppercase letter (which, moreover, in many editors is
 highlighted differently). But in field access left operand is not always
 atomic - it can be expression.

 Consider this example:
 quux (y . (foo . bar).baz (f . g)) moo
 It's not that easy to distinguish from
 quux (y . (foo . bar) . baz (f . g)) moo

Yeah, that's why I dislike dot as compose operator (^_~)


 Matthew Farkas-Dyck wrote

 Certainly not no conflicts: lambda expressions.



 --
 View this message in context:
 http://haskell.1045720.n5.nabble.com/Records-in-Haskell-tp4806095p5111428.html
 Sent from the Haskell - Glasgow-haskell-users mailing list archive at
 Nabble.com.

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


Backslash is a possibility then, it seems, but in my opinion breaks
the principle of least surprise, i.e. I can't believe it's not
lambda!

Cheers,
Matthew Farkas-Dyck

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


Re: GeneralizedNewtypeDeriving

2011-12-27 Thread Matthew Farkas-Dyck
*query*

Ah. So it does.

Thanks. I'll learn this language yet (^_~)

On 27/12/2011, Chris Dornan ch...@chrisdornan.com wrote:
 That’s as maybe but last time I looked (I don’t have it to hand) the OED
 generally accepts –ize or –ise spellings for British English (maybe even
 favouring the former).

 Chris

 From: glasgow-haskell-users-boun...@haskell.org
 [mailto:glasgow-haskell-users-boun...@haskell.org] On Behalf Of David Fox
 Sent: 27 December 2011 14:50
 To: Matthew Farkas-Dyck
 Cc: GHC users
 Subject: Re: GeneralizedNewtypeDeriving

 My guess is that Americans were involved.
 On Mon, Dec 26, 2011 at 7:24 AM, Matthew Farkas-Dyck strake...@gmail.com
 wrote:
 Just of curiosity, why is it spelt with a z? Is it spelt thus in
 Scottish English? I thought that generalised is written throughout
 Great Britain.

 Cheers,
 MFD

 ___
 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


GeneralizedNewtypeDeriving

2011-12-26 Thread Matthew Farkas-Dyck
Just of curiosity, why is it spelt with a z? Is it spelt thus in
Scottish English? I thought that generalised is written throughout
Great Britain.

Cheers,
MFD

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


Re: Records in Haskell

2011-12-21 Thread Matthew Farkas-Dyck
Fair enough.


On 20/12/2011, Chris Smith cdsm...@gmail.com wrote:
 On Tue, Dec 20, 2011 at 5:57 PM, Matthew Farkas-Dyck
 strake...@gmail.com wrote:
 Another thought:
 Perhaps bang as record selection operator. It would avoid further
 corner cases of dot, and it's not unprecedented in Haskell (e.g.
 Data.Map.!).

 We already have weird syntax rules for dot, and the proposed change
 (i.e., dot is an identifier when surrounded with spaces, else it's
 reserved syntax) actually makes the rules *simpler* in some ways
 rather than more complex... so why wouldn't we do it that way?

 The more difficult bit isn't about quirks of syntax, but rather about
 some significant semantic issues and differing design goals should
 we have a built-in notion of lenses... if so, which formulation...
 what kinds of punning do we want to preserve, and how deeply should
 punning go in the semantics, versus be a shallow kind of sugar... how
 does that interact with the type system... and so on.  These are the
 significant problems.


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


Re: [Haskell-cafe] Alternative versus Monoid

2011-12-21 Thread Matthew Farkas-Dyck
On 21/12/2011, Bas van Dijk v.dijk@gmail.com wrote:
 On 16 December 2011 16:26, Yves Parès limestr...@gmail.com wrote:
 1) What about the First type? Do we {-# DEPRECATE #-} it?

 Personnaly, I'm in favor of following the same logic than Int:
 Int itself is not a monoid. You have to be specific: it's either Sum or
 Mult.

 It should be the same for Maybe: we remove its instance of Monoid, and we
 only use First and Last.

 The reason you need to be specific with Int is that it's not clear
 which semantics (sum or product) you want. The semantics of Maybe are
 clear: it's failure-and-prioritized-choice.

 Changing the order of the arguments of mappend should be the job of Dual.

 If we really want to drop the Monoid instance for Maybe and keep First
 and Last and also want to be consistent we should also drop the Monoid
 instances of [a], a-b, Endo a and of all the tuples. And instead
 define Monoid instance for First [a], Last [a], First (a-b), Last
 (a-b), etc. I don't think this is what we want.

 Regards,

 Bas

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


Fair point. I concede.

If Monoid were necessarily inner-type-gnostic then we'd also have to
drop instance Monoid [a].

Cheers,
Matthew Farkas-Dyck

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


Re: Records in Haskell

2011-12-20 Thread Matthew Farkas-Dyck
Another thought:
Perhaps bang as record selection operator. It would avoid further
corner cases of dot, and it's not unprecedented in Haskell (e.g.
Data.Map.!).
If one wished to use dot, one could do this:

import Prelude hiding ((.));
import Control.Category.Unicode((∘));

(.) = (!);

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


Re: [Haskell-cafe] If you'd design a Haskell-like language, what would you do different?

2011-12-20 Thread Matthew Farkas-Dyck
With GHC 7.0.3:

$ cat test.hs
class ℝ a where {
  test :: a;
};

(∈) :: Eq a = a - [a] - Bool;
x ∈ (y:ys) = x == y || x ∈ ys;

main = putStrLn Two of three ain't bad (^_~);
$ runhaskell test.hs
Two of three ain't bad (^_~)
$

On 20/12/2011, David Fox dds...@gmail.com wrote:
 On Mon, Dec 19, 2011 at 11:20 AM, Robert Clausecker fuz...@gmail.comwrote:

 Image you would create your own language with a paradigm similar to
 Haskell or have to chance to change Haskell without the need to keep any
 compatibility. What stuff would you add to your language, what stuff
 would you remove and what problems would you solve completely different?

 Thanks in advance for all answers, yours


 One thing that concerns me is the use of capital letters to distinguish
 type and class names and constructors from values.  If I was doing it over
 I would use a typographical distinction like italics for types, bold for
 classes.  That way we could have a constructor named ∅, a function named ∈,
 a class named ℝ.



Cheers,
Matthew Farkas-Dyck

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


Re: [Haskell-cafe] [Alternative] summary of my understanding so far

2011-12-17 Thread Matthew Farkas-Dyck
On 16/12/2011, Gregory Crosswhite gcrosswh...@gmail.com wrote:

 On Dec 17, 2011, at 12:35 PM, Matthew Farkas-Dyck wrote:

 (1) If we do (4), then the documentation ought to be adequate as-is.

 I see your point that if we do (4) then some and many are no longer
 problematic for Maybe and [], and thus we don't need warnings for those
 types.  However, nonetheless we will *still* need *big warnings* *for the
 sake of others who write Alternative instances* for new types to make sure
 that these instances do not fall into the same trap as Maybe and [].  That
 is, we want to let future authors of instances know about the conditions
 under which they will need to write their own versions of some and maybe in
 order to make sure that these methods have sensible behavior.

 Finally, if we adopt (4) then we will need to change the documentation to
 remove least from least solutions of the equations since the phrase will
 no longer be correct.  Better still, we could replace the phrase entirely
 with something like least *converging* solutions of the equations. (*)

Ah, true. Sorry.

 In addition to this, we also really need some additional documentation
 explaining what the point of some and many are, since few people have any
 clue about them.  :-)

Myself, I think it's quite clear by the axioms given, but I certainly
shan't grouch about more/better documentation.

 Cheers,
 Greg

 (*) P.S:

 Dear people who are better at this kind of technical language than I:

 I am fully aware of the fact that the phrase least converging solutions of
 the equations [...] is sloppy wording at best and absolutely wrong at
 worst, but hopefully you should at least understand what I am *trying* to
 get at.  Thus, I would welcome either your feedback on what it is that I am
 supposed to be thinking and saying, or an explanation about why the idea I
 am trying to conceive and convey is so intrinsically poorly formed that I am
 best off just giving up on it.  ;-)

Actually, now that I think of it, they are not, in general, the least
converging solutions -- in the case of a parser, for example, (some
(pure x)) would nevertheless diverge (I think).
Perhaps least sane solutions (^_^)

Cheers,
Matthew Farkas-Dyck

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


Re: [Haskell-cafe] Alternative versus Monoid

2011-12-17 Thread Matthew Farkas-Dyck
On 17/12/2011, Gregory Crosswhite gcrosswh...@gmail.com wrote:

 On Dec 17, 2011, at 12:51 PM, Matthew Farkas-Dyck wrote:

 By my reason, the instance (Monoid a = Monoid (Maybe a)) is
 appropriate, since we have another class for inner-type-agnostic
 choice -- Alternative! (and MonadPlus, but that's essentially the
 same, and would be if (Functor m = Applicative m = Monad m), as it
 ought).

 Yes, but the problem here is that having different behavior for Alternative,
 MonadPlus, and Monoid instances is inherently confusing, in the sense that
 this would almost certainly surprise someone who wasn't already aware of the
 difference between the instances.

On 17/12/2011, Conor McBride co...@strictlypositive.org wrote:
 So your argument is to create incoherence because we can. I'm not
 convinced.

No, my argument is that Monoid and Alternative ought to have nonsame
semantics, since one is a class of types of kind (*), and the other,
(* - *). Thus, Monoid operations ought to mean the whole type, and
Alternative operations, just the outer type.

It shouldn't be a surprise -- it's impossible to put a constraint on
the inner type for an Alternative instance, since there is none (^_~)

  (Functor m = Applicative m = Monad m), as it ought.
 and as it already is in Strathclyde...

By default superclass instances, you mean? If so (and I understand
correctly), that's not quite the same; If I write, for (Applicative
FooBar - FooBar)
instance Monad FooBar where x = f = ...
then return would be undefined, despite pure (which ought to be in its
own class, anyhow (ō_ō)).

Cheers,
Matthew Farkas-Dyck

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


Re: [Haskell-cafe] [Alternative] summary of my understanding so far

2011-12-16 Thread Matthew Farkas-Dyck
On 15/12/2011, Gregory Crosswhite gcrosswh...@gmail.com wrote:
 1) Documentation really needs to be improved
 2) some/many cannot be physically separated from Alternative, but there
 *might* be an advantage to creating a subclass for them anyway purely for
 the sake of conveying more information about a type to users
 3) Maybe and [] are sensible instances of Alternative, even if many/some
 often enters an infinite loop.
 4) It is possible to provide special instance of many/some that satisfy the
 equations of many/some, with the slight disadvantage that these solutions
 are no longer the least solutions.

 Based on all of this, at this moment in time it seems to me that the most
 sensible way forward is to fix the documentation, tweak the definition of
 Alternative to no longer require the least solutions of the equations, and
 then to adopt the new instances for Maybe and [].

 Thoughts?

(1) If we do (4), then the documentation ought to be adequate as-is.
(2) In my opinion, no. If one is writing code polymorphic in
(Alternative f = f), then one needn't worry. If one is using such
code, then one ought to know whether some and many are sane for the
types in question, anyhow (O_ō)
(4) This is very reasonable; not the least solutions, but hey, they
converge (^_^)

 Cheers,
 Greg

Cheers,
Matthew Farkas-Dyck

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


Re: [Haskell-cafe] Alternative versus Monoid

2011-12-16 Thread Matthew Farkas-Dyck
On 15/12/2011, Conor McBride co...@strictlypositive.org wrote:

 On 15 Dec 2011, at 15:19, Brent Yorgey wrote:

 On Thu, Dec 15, 2011 at 06:49:13PM +1000, Gregory Crosswhite wrote:

 So at the end of the day... what is the point of even making Maybe
 and [] instances of Alternative?

 The Alternative and Monoid instances for [] are equivalent.  However,
 the Alternative and Monoid instances for Maybe are not. To wit:

 (Just (Sum  4)) | (Just (Sum 3))
  Just (Sum {getSum = 4})

 (Just (Sum 4)) `mappend` (Just (Sum 3))
  Just (Sum {getSum = 7})

 The current monoid instance for Maybe is, in my view, unfortunate.

 Types are about semantic purpose, not just data representation.
 Many purposes can be represented in the same way. We should identify
 the purpose of a type (or type constructor), then define instances
 consistent with that purpose. And better, we acquire by instance
 inference compound instances consistent with that purpose! (A similar
 view is often articulated well by Conal Elliott. But perhaps it's
 just a Con thing.)

 The purpose of Maybe, it seems to me, is to model failure and
 prioritized choice, after the manner of exceptions. It's clear
 what the failure-and-prioritized-choice monoid is.

 It so happens that the same data representation can be used to make
 a semigroup into a monoid by attaching an identity element. That's
 a different semantic purpose, which deserves a different type.

 This really bites. I really like being able to write things like

newtype P a x = P ([a] - Maybe (x, [a])) deriving Monoid

 and then make MonadPlus/Alternative instances just by copying the
 monoid that results, but it doesn't work!

 It's unfortunate that we don't have local quantification in
 constraints, so we can't write (forall x. Monoid (f x)), hence the
 need for constructor classes doing basically the same job, with,
 of necessity, newly renamed members. I think it compounds the
 problem to choose inconsistent behaviour between the constructor
 class and the underlying type class.

 Maybe I'm an extremist, but I'd prefer it if every Alternative
 instance was constructed by duplicating a polymorphic Monoid
 instance.

 Meanwhile, as for the issue which kicked this off, I do think it's
 good to document and enforce meaningful (i.e. total on total input)
 usages of operations by types where practical. At present, refining
 one type class into several to account for subtle issues (like
 whether some/many actually work) is expensive, even if it's
 desirable. I'd once again plug default superclass instances and
 Control.Newtype, then suggest that the library might benefit from a
 little pruning.

 All the best

 Conor

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


By my reason, the instance (Monoid a = Monoid (Maybe a)) is
appropriate, since we have another class for inner-type-agnostic
choice -- Alternative! (and MonadPlus, but that's essentially the
same, and would be if (Functor m = Applicative m = Monad m), as it
ought).

Cheers,
Matthew Farkas-Dyck

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


[Haskell-cafe] Cabal: Disjunctive Build-Depends

2011-12-12 Thread Matthew Farkas-Dyck
Hello all.

I have written some code that can be compiled with either of two
libraries, with no modification. How can I tell Cabal?

I tried || but it failed to parse.

I could find which package is available in the build script, and then
call defaultMainNoRead with the appropriate GenericPackageDescription,
but I'm not sure how to find this system-agnostically.

Thanks for any help.

Cheers,
Matthew Farkas-Dyck

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


Re: [Haskell-cafe] Cabal: Disjunctive Build-Depends

2011-12-12 Thread Matthew Farkas-Dyck
Grand. Thanks!


On 12/12/2011, Felipe Almeida Lessa felipe.le...@gmail.com wrote:
 On Mon, Dec 12, 2011 at 6:25 PM, Matthew Farkas-Dyck
 strake...@gmail.com wrote:
 I have written some code that can be compiled with either of two
 libraries, with no modification. How can I tell Cabal?

 I tried || but it failed to parse.

 I could find which package is available in the build script, and then
 call defaultMainNoRead with the appropriate GenericPackageDescription,
 but I'm not sure how to find this system-agnostically.

 You just need to use flags.  Something like

 Flag usethis
   Description:  Use this instead of that
   Default:  False

 Library
   Build-depends: ...everything else...
   if flag(usethis)
 Build-depends: this == 0.1.*
   else
 Build-depends: that == 4.0.*

 You don't need to care about usethis.  If 'that' is not installed but
 'this' is, Cabal will automatically turn 'usethis' flag on.

 Cheers,

 --
 Felipe.



-- 
Matthew Farkas-Dyck

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


[arch-haskell] apkg: Fetch, build, and install packages from Hackage

2011-11-26 Thread Matthew Farkas-Dyck
Hello all:

I have written a tool to fetch, build, and install packages, and all
packages they need, and so on. Packages are fetched straight from
Hackage and installed with pacman. I plan to enable it to fetch from
the local filesystem and AUR but so far this seems broken. (Hackage
fetch is not broken.)

https://aur.archlinux.org/packages.php?ID=54339
https://gitorious.org/apkg

I know that someone asked of late on arch-haskell of just such a tool,
so I hope that it will be found useful.

-- strake

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


Re: Records in Haskell

2011-11-04 Thread Matthew Farkas-Dyck
I really like Simon PJ's proposal for records in Haskell. Some
reasons for this are:
- Anonymous record types. For example, an anonymous record type can
easily hold ad-hoc keyword arguments. (Oh, just noticed that said in
the document.)
- To quote the document, We can express polymorphic update (a
standard awkward case) quite nicely. (If I'm not mistaken (please
tell me if so), OverloadedRecordFields proposal fails here.)
- Nice syntax (in my opinion).

Possible record member set syntax:
let x.k = value in x
Pros:
- No new syntax
- Least Surprise
Cons:
- Verbosity (especially such: (\ x - let x.k = value in x))

On 20/10/2011, Simon Peyton-Jones simo...@microsoft.com wrote:
 | Subject: Re: Records in Haskell
 |
 | I have added my proposal to the wiki.The only downsides to it that I can
 see are:

 Thanks to Barney for articulating a proposal for records in Haskell.  Over
 various plane rides and ICFP chats I've worked out some more details.  It's
 not as simple as I'd hoped.

 I'm underwater with stuff at the moment but I did find the time to capture a
 summary here
   http://hackage.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields

 Please do correct errors, suggest solutions, or explore variants.

 Simon

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



-- 
Matthew Farkas-Dyck

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


Re: Records in Haskell

2011-11-04 Thread Matthew Farkas-Dyck
On 04/11/2011, Simon Peyton-Jones simo...@microsoft.com wrote:
 | I really like Simon PJ's proposal for records in Haskell. Some
 | reasons for this are:

 Which one?  You'll need to give your readers an explicit link

 S


Sorry.

http://research.microsoft.com/en-us/um/people/simonpj/Haskell/records.html

-- 
Matthew Farkas-Dyck

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


Profile: zero total time

2011-07-07 Thread Matthew Farkas-Dyck
I am trying to take a profile of a program, but when I run it, the
total time (as given in the profiling report file) is zero!

total time  =0.00 secs   (0 ticks @ 20 ms)

However, the -s option yields the following data:

   3,429,300,984 bytes allocated in the heap
 210,760,024 bytes copied during GC
  23,647,224 bytes maximum residency (13 sample(s))
   3,536,968 bytes maximum slop
  58 MB total memory in use (0 MB lost due to fragmentation)

  Generation 0:  6339 collections, 0 parallel,  1.14s,  1.42s elapsed
  Generation 1:13 collections, 0 parallel,  0.28s,  0.34s elapsed

  INIT  time0.00s  (  0.00s elapsed)
  MUT   time   96.60s  (124.50s elapsed)
  GCtime1.42s  (  1.75s elapsed)
  RPtime0.00s  (  0.00s elapsed)
  PROF  time0.00s  (  0.00s elapsed)
  EXIT  time0.00s  (  0.00s elapsed)
  Total time   98.02s  (126.25s elapsed)

  %GC time   1.4%  (1.4% elapsed)

  Alloc rate35,498,347 bytes per MUT second

  Productivity  98.5% of total user, 76.5% of total elapsed

The time taken by each cost centre is also zero. The program is
compiled with options -prof -auto-all -caf-all by GHC 7.0.3 and run
with RTS options -p -s.

The true time taken is certainly NOT zero. How is this possible?

Thanks.

Cheers,
Matthew Farkas-Dyck

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


Re: Profile: zero total time

2011-07-07 Thread Matthew Farkas-Dyck
Sorry, I ought to have mentioned:

$ uname -sr
Linux 2.6.38

On 7 July 2011 14:03, Daniel Fischer daniel.is.fisc...@googlemail.com wrote:
 On Thursday 07 July 2011, 20:44:57, Matthew Farkas-Dyck wrote:
 I am trying to take a profile of a program, but when I run it, the
 total time (as given in the profiling report file) is zero!

 If you're on a Mac, it could be

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




-- 
Matthew Farkas-Dyck

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