Re: Abstracting over things that can be unpacked

2012-03-05 Thread Aleksey Khudyakov
> As I mentioned further up in the email, I think this needs to be done at
> compile time. However, I'm not sure type classes are the right mechanism, as
> they don't guarantee that the polymorphism is resolved at compile time.
> Perhaps type families, in some form, is the right solution.
>
There is problem with type families. Currently GHC is unable to unpack them[1].

[1] http://hackage.haskell.org/trac/ghc/ticket/3990

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


How to declare polymorphic instances for higher-kinded types?

2012-03-05 Thread Herbert Valerio Riedel
Hello *,

For simple-kinded type variables, instances of the type
  
instance NFData a => NFData [a]
instance NFData a => NFData (Maybe a)
instance (NFData a, NFData b) => NFData (a, b)
   
are common and can be defined effortless; now I wanted do something
similiar for a type with a phantom type parameter:
   
{-# LANGUAGE KindSignatures, TypeSynonymInstances #-}

import Control.Applicative
import Control.Monad

data DataBase = DataBase -- specific type not relevant here

data Res
data Unres

-- provides operation to transform an unresolved `Foo_ Unres` to a resolved 
`Foo_ Res`
class Resolvable (e :: * -> *) where
resolve :: DataBase -> e Unres -> Either String (e Res)
  
  
-- trivial /resolvable/ type
data Foo_ r = Foo

instance Resolvable Foo_ where
resolve _ x = return Foo
  
...it was no problem to define the polymorphic operations outside of
an instance:
  
-- Maybe (polymorphic 0 or 1 element container)
resolveMaybe :: Resolvable e => DataBase -> Maybe (e Unres) -> Either 
String (Maybe (e Res))
resolveMaybe db (Just x) = Just <$> resolve db x
resolveMaybe db Nothing  = pure Nothing

-- Pairs
resolvePair :: (Resolvable e0, Resolvable e1)
=> DataBase -> (e0 Unres, e1 Unres) -> Either String (e0 Res, 
e1 Res)
resolvePair db (x,y) = (,) <$> resolve db x <*> resolve db y
  
...but when I tried to wrap those into polymorphic instances in the style
of the instances at the beginning of this mail, I wasn't able to
convince GHC:
  
The following attempts wouldn't work:
  
instance Resolvable e => Resolvable (Maybe e) where
resolve = resolveMaybe
  
-- GHC fails with:
--  Expecting one more argument to `e'
--  In the instance declaration for `Resolvable (Maybe e)'
  
Fair enough, but trying to workaround this by defining a type-synonym to
get an (*->*)-kinded expression didn't work either, as currying doesn't
seem to be supported at the type-level (is there a language-extension
for that?):
  
type Maybe_ e r = Maybe (e r)
  
instance Resolvable e => Resolvable (Maybe_ e) where
resolve = resolveMaybe
  
-- GHC fails with:
--  Type synonym `Maybe_' should have 2 arguments, but has been given 1
--  In the instance declaration for `Resolvable (Maybe_ e)'
  


So, am I really out of luck here, wanting to define polymorphic instances
in combination with phantom-types, or is there a trick I haven't thought
of yet?



PS: while experimenting, I accidentally triggered the following GHC
exception:

 *** Exception: compiler/rename/RnSource.lhs:429:14-81:
  Irrefutable pattern failed for pattern
Data.Maybe.Just (inst_tyvars, _, SrcLoc.L _ cls, _)

...alas I lost the Haskell-code causing this; is this a known issue?
Should I try harder to reproduce it again?

cheers,
  hvr
-- 


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


Re: Why I (Don't!) Want Global Field Names (By Default)

2012-03-05 Thread AntC
Gershom Bazerman  gmail.com> writes:

> 
> ... I want to put forward
> at least one strong motivation for global field names (aka
> SORF-style) rather than locally declared field names as a default.

Hi Gershom,

One of the things that's surprised me contributing to this thread is not just 
that different people rate different features with different priority (that's 
common in requirements analysis, to try to 'weight' each objective); but that 
what some people think is absolutely critical others think is absolutely to be 
avoided. (The Best example of that is the furore about dot notation.) 

So you're not going to expect me to agree with you.

A couple of very strange things I noticed about your expectations for software 
development, so I'm happy to make clear the context I'm expecting:

* Yes, I expect you "to pull in the entire namespace for [the] database
  at once". That is: in a large-scale database-oriented application,
  you would declare **all** your field labels (aka data dictionary)
  in one module, and import that into every sub-module.
  That's been standard practice in all the software shops I've worked in
  since around 1984 (System/38).
  That's exactly what Chris Done's example did, which started my thinking
  around what became DORF.
  I am, frankly, astonished anyone would contemplate any other approach
  in this day and age. Because ...

* As you say, tracing all the dependencies from code mods is hard work.
  Developers are very poor at it. Computers are superb.
  I expect you to run a nightly build, why not make it easy for yourself?
  http://www.joelonsoftware.com/articles/fog23.html
  http://www.joelonsoftware.com/articles/fog43.html
  Those articles date from over a decade ago!
  Software shops I've worked in have run nightly builds since around mid-90's.

  (It'd be interesting to hear from the ghc dev team:
   do they run a nightly build?
   Although ghc is not a database-intensive application.)

And what on earth sort of hardware are you running that your builds are "time 
consuming"? This is just not an issue in 2012. I expect large-scale 
applications with (say) hundreds of tables, thousands of fields, 100k's LOC to 
rebuild in a few hours.


So to my substantive answer:
* The realistic situation in modern software engineering is that you assemble
  your application out of libraries/packages.
* You have no control over the naming used in them.
* What's worse, developers are so used to strong namespacing controls,
  that they often use generic names that are likely to appear elsewhere.
  (And especially if it's in a technical domain with well-agreed jargon.)
* So you're highly likely to get clashes 'by accident'.
* Haskell's module/namespacing controls are perfectly adequate to manage this.
* And OO, as a technique insists on namespace control,
  to implement encapsulation/representation-hiding.

* In database-oriented applications, re-using the same name on different tables
  is deliberate and intentional (_not_ by accident).
* H98 is simply awful for this. DORF addresses that issue.
* That said, nothing in DORF stops you creating global names:
  simply export/import them everywhere unqualified.
  See: that wasn't too painful, was it?

So our point of difference comes down to: what behaviour "By Default".
* DORF expects it's more likely you'll want namespace control.
  And makes it hardly more difficult to be global.
  And uses module-based namespace control that is already industry-standard,
  viz: Haskell 98's approach.

* SORF 'imposes' global everywhere,
  And makes it possible but awkward to control name scope.

My litmus test for your approach (as for Ian's):
* My record has fields `x`, `y`, and `z`:
  - `x` is to be gettable and settable
  - `y` is to be gettable but not settable
  - `z` is to be hidden and unguessable

Please explain how your PrivateLabel approach handles those. It's not a case 
of whether it's possible, but rather how awkward.

AntC




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


Re: How to declare polymorphic instances for higher-kinded types?

2012-03-05 Thread Andres Löh
Hi.

Here's a way that seems to work for me. I haven't tested in detail.
There may be problems, or also easier ways to achieve the same. The
DataKinds extension isn't essential. I've just used it for fun.

Cheers,
  Andres

-- 
Andres Löh, Haskell Consultant
Well-Typed LLP, http://www.well-typed.com
{-# LANGUAGE TypeFamilies, ConstraintKinds, KindSignatures, TypeSynonymInstances, DataKinds #-}
module Resolve where

import GHC.Exts
import Control.Applicative
import Control.Monad

data DataBase = DataBase -- specific type not relevant here

data Resolved = Res | Unres

-- provides operation to transform an unresolved `Foo_ Unres` to a resolved `Foo_ Res`
class Resolvable e where
type ResFun e (a :: Resolved) :: *   -- replace the 'Resolved' argument in 'e' with 'a'
type ResArg e (a :: Resolved) :: Constraint  -- force the 'Resolved' argument in 'e' to be 'a'
resolve :: (ResArg e 'Unres) => DataBase -> e -> Either String (ResFun e 'Res)

-- trivial /resolvable/ type
data Foo_ (r :: Resolved) = Foo
  deriving Show

instance Resolvable (Foo_ r) where
type ResFun (Foo_ r) a = Foo_ a
type ResArg (Foo_ r) a = r ~ a
resolve _ x = return Foo

-- Maybe (polymorphic 0 or 1 element container)
resolveMaybe :: (Resolvable e, ResArg e 'Unres) => DataBase -> Maybe e -> Either String (Maybe (ResFun e 'Res))
resolveMaybe db (Just x) = Just <$> resolve db x
resolveMaybe db Nothing  = pure Nothing

instance Resolvable e => Resolvable (Maybe e) where
type ResFun (Maybe e) a = Maybe (ResFun e a)
type ResArg (Maybe e) a = ResArg e a
resolve db x = resolveMaybe db x

-- Pairs
resolvePair :: (Resolvable e0, Resolvable e1, ResArg e0 'Unres, ResArg e1 'Unres)
=> DataBase -> (e0, e1) -> Either String (ResFun e0 'Res, ResFun e1 'Res)
resolvePair db (x,y) = (,) <$> resolve db x <*> resolve db y

instance (Resolvable e0, Resolvable e1) => Resolvable (e0, e1) where
type ResFun (e0, e1) a = (ResFun e0 a, ResFun e1 a)
type ResArg (e0, e1) a = (ResArg e0 a, ResArg e1 a)
resolve db x = resolvePair db x
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Why I Want Global Field Names (By Default)

2012-03-05 Thread AntC
Gershom Bazerman  gmail.com> writes:

> 

Gershom, an implementation question for your proposed approach to 
representation-hiding:

(It's always easy to wave away awkwardness if you don't show the full 
mechanism. Please write up your proposal on the wiki to the same level of 
detail as SORF -- at least!.)

> However, we can do one better, and recover DORF and SORF behavior at
> once!
> 
>     class Label a
> 
>     class Label f => Has (r :: *) (f :: *) (t :: *) where
> 
>    get :: r -> t
> 
>    instance Label (a :: String)
> 

SORF is not proposing any change to data decls syntax, or the namespacing 
around field selector functions. How do you get from the data decl to the Has 
instance? (So that the program can get/set within its private module.)

Specifically, with:
> 
>    data MyPrivateLabel
> 
>    instance Label MyPrivateLabel
> 

How to get a data decl to generate a Has instance for MyPrivateLabel, and 
avoid generating a Has instance for the String Kind?

How (within the private module) to desugar a call to get (or dot notation) to 
use MyPrivateLabel?

And record update?

(Remember that unlike DORF, SORF's field access is syntax-directed: it 
desugars dot notation to a hard-coded String Kind for the field. There's no 
clear proposal for record update as yet)

> ...  If everyone finds this agreeable (and I can
> imagine no reason they wouldn't!) ...

That's a misleading remark: you're asking people to agree to a half-baked and 
sketchy proposal.

I do not "find this agreeable", and I think I've put forward heaps of reasons 
to disagree.

I expect you to:
* explain what changes you're proposing to existing syntax
* detail how to desugar that syntax to available Haskell
* detail the existing syntax you're going to desugar differently
* ideally build a prototype to prove it
* demonstrate in the prototype how the namespace control works

Then we can hold the beauty pageant.

(Oh yes: and explain what you'd have instead of dot notation, so that we can 
fire up another syntax debate ;-)

AntC



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


Re: partially applied type synonyms

2012-03-05 Thread Herbert Valerio Riedel
Arie Peterson writes:

> Is there a good reason that partially applied type synonyms cannot be made
> instances of classes?

[...]

> Partially applied type synonyms are, in a sense, the anonymous functions
> at the type level, and one might argue that they deserve the same
> 'first-class member status' as the lambda at the value level.

According to SPJ, the problem seems to be requiring higher-order
unification for this to happen:

 http://www.haskell.org/pipermail/glasgow-haskell-users/2005-April/008340.html

Does anyone here know (as SPJ's response is quite a few years old) if
there's been made any progress since back then?

cheers,
hvr


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


Re: partially applied type synonyms

2012-03-05 Thread Brandon Allbery
On Mon, Mar 5, 2012 at 06:55, Herbert Valerio Riedel  wrote:

> Arie Peterson writes:
> > Is there a good reason that partially applied type synonyms cannot be
> made
> > instances of classes?
>
>
> http://www.haskell.org/pipermail/glasgow-haskell-users/2005-April/008340.html
>
> Does anyone here know (as SPJ's response is quite a few years old) if
> there's been made any progress since back then?
>

I'm pretty sure it's just as undecidable now as it was then.

-- 
brandon s allbery  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: How to declare polymorphic instances for higher-kinded types?

2012-03-05 Thread Herbert Valerio Riedel
Andres Löh  writes:

> Here's a way that seems to work for me. I haven't tested in detail.
> There may be problems, or also easier ways to achieve the same. The
> DataKinds extension isn't essential. I've just used it for fun.

looks interesting

If I get it right, the trick is to use a *-kinded (instead of a
*->*-kinded) argument for the class & instances and have a "type
function" that is able to phantom-retag an already applied
type-constructor `Foo_ Unres` to a differently applied type-constructor
`Foo_ Res`.

The only thing that disturbs me is that I have to define explicit
boilerplate type family declarations for all twenty or so
non-polymorphic instances which'd look always the same, i.e.

type ResFun (t r) a = t a
type ResArg (t r) a = t ~ a

...could that be defined as an override-able default somehow?

cheers,
hvr
-- 

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


Re: How to declare polymorphic instances for higher-kinded types?

2012-03-05 Thread Andres Löh
Hi.

> If I get it right, the trick is to use a *-kinded (instead of a
> *->*-kinded) argument for the class & instances and have a "type
> function" that is able to phantom-retag an already applied
> type-constructor `Foo_ Unres` to a differently applied type-constructor
> `Foo_ Res`.

Yes.

> The only thing that disturbs me is that I have to define explicit
> boilerplate type family declarations for all twenty or so
> non-polymorphic instances which'd look always the same, i.e.
>
> type ResFun (t r) a = t a
> type ResArg (t r) a = t ~ a
>
> ...could that be defined as an override-able default somehow?

The only way I can quickly think of that might work is to go via
another type family. However, this requires "UndecidableInstances":

type family GetF e :: Resolved -> *
type instance GetF (f x) = f

-- provides operation to transform an unresolved `Foo_ Unres` to a
resolved `Foo_ Res`
class Resolvable e where
type ResFun e (a :: Resolved) :: *
type ResFun e a = GetF e a
type ResArg e (a :: Resolved) :: Constraint
type ResArg e a = GetF e a ~ e
...

Then, for types like Foo, you can just write:

instance Resolvable (Foo_ r) where
resolve _ x = return Foo

I.e., you shouldn't need the type family declarations.

Cheers,
  Andres

-- 
Andres Löh, Haskell Consultant
Well-Typed LLP, http://www.well-typed.com

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


thoughts on the record update problem

2012-03-05 Thread Barney Hilken
There are actually four problems with overloaded record update, not three as 
mentioned on the SORF page. This is an attempt to solve them.

  The SORF update mechanism.
--

SORF suggests adding a member set to the class Has which does the actual 
updating just as get does the selecting. So

set :: Has r f t => t -> r -> r

and r {n1 = x1, n2 = x2} is translated as

set @ "n2" x2 (set @ "n1" x1)


  The Problems.
-

1. It's not clear how to define set for virtual record selectors. For example, 
we might define

data Complex = Complex {re :: Float, im :: Float}

instance Has Complex "arg" Float where
get r = atan2 r.im r.re

but if we want to set "arg", what should be kept constant? The obvious answer 
is "mod", but we haven't even defined it, and there are plenty of cases where 
there is no obvious answer.

2. If the data type has one or more parameters, updates can change the type of 
the record. Set can never do this, because of its type. What is more, if 
several fields depend on the parameter, for example

data Twice a = Twice {first :: a, second :: a}

any update of "first" which changes the type must also update "second" at the 
same time to keep the type correct. No hacked version of set can do this.

3. The Haskel implementation of impredicative polymorphism (from the Boxy Types 
paper) isn't strong enough to cope with higher rank field types in instances of 
set.

4. The translation of multiple updates into multiple applications of set is not 
the same as the definition of updates in the Haskel report, where updates are 
simultaneous not sequential. This would be less efficient, and in the case of 
virtual record selectors, it wouldn't be equal, and is arguably incorrect.


Point 3 could possibly be fixed by improving the strength of the type system, 
but SPJ says this is a hard problem, and no-one else seems ready to tackle it. 
Points 1, 2 & 4 suggest that any solution must deal not with individual fields 
but with sets of fields that can sensibly be updated together.


  The Proposed Solution.
--

This is an extension to SORF. I don't know if the same approach could be 
applied to other label systems.

1. Introduce a new form of class declaration:

class Rcls r where
r {n1 :: t1, n2 :: t2}

is translated as

class (Has r n1 t1, Has r n2 t2) => Rcls r where
setRcls :: t1 -> t2 -> r -> r

setRcls is used internally but hidden from the user.

2. Instances of record classes can use a special form of default. So

data Rec = Rec {n1 :: t1, n2 :: t2}

instance Rcls Rec

is translated as

instance Rcls Rec where
setRcls x1 y1 (Rec _ _) = Rec x1 y1

provided all the fields in the class occur in the data type with the correct 
types. In general, the definition of the update function is the same as the 
Haskel98 translation of update, solving problem 4.

3. The syntax of record updates must be changed to include the class:

r {Rcls| n1 = x1, n2 = x2}

is translated as

setRcls x1 x2 r

Updating a subset of the fields is allowed, so

r {Rcls| n1 = x1}

is translated as

setRcls x1 (r.n2) r


4. Non default instances use the syntax:

instance Rcls Rec where
r {Rcls| n1 = x1, n2 = x2} = ...x1..x2..

which is translated as

instance Rcls Rec where
setRcls x1 y1 r = ...x1..x2..

in order to allow virtual selectors. This solves problem 1, because updates are 
grouped together in a meaningful way. An extended example is given below.

5. Record classes can have parameters, so

class TwiceClass r where
r a {first :: a, second :: a}
data Twice a = Twice {first :: a, second :: a}
instance TwiceClass Twice

translates as

class TwiceClass r where
setTwiceClass :: a -> a -> r b -> r a
data Twice a = Twice {first :: a, second :: a}
instance TwiceClass Twice where
setTwiceClass x y (Twice _ _) = Twice x y

which allows updates to change the type correctly. This solves problem 2.

6. Problem 3 *almost* works. The translation of

class HRClass r where
r {rev :: forall a. [a] -> [a]}

is

class Has r "rev" (forall a. [a] -> [a]) => HRClass r where
setHRClass :: (forall a.[a] -> [a]) -> r -> r

which is fine as far as updating is concerned, but the context is not 
(currently) allowed by ghc. I have no idea whether allowing polymorphic types 
in contexts would be a hard problem for ghc or not. None of my attempted 
work-rounds have been entirely satisfactory, but I might have missed something.


  Comments
-

1. This makes the "special syntax for Has" pretty useless. When you have a set 
of labels you want to use together, you usually want to use update 

Re: thoughts on the record update problem

2012-03-05 Thread Greg Weber
Thanks so much for stepping up and attempting a solution at our big
problem, Barney!

I would ask everyone restrict their comments on this for now solely as
to figuring out whether it makes updates work. There has been a lively
debate about ideal details on a record implementation, but until
updates are solved it is all a moot point.

On Mon, Mar 5, 2012 at 10:36 AM, Barney Hilken  wrote:
> There are actually four problems with overloaded record update, not three as 
> mentioned on the SORF page. This is an attempt to solve them.
>
>  The SORF update mechanism.
> --
>
> SORF suggests adding a member set to the class Has which does the actual 
> updating just as get does the selecting. So
>
>        set :: Has r f t => t -> r -> r
>
> and r {n1 = x1, n2 = x2} is translated as
>
>        set @ "n2" x2 (set @ "n1" x1)
>
>
>  The Problems.
> -
>
> 1. It's not clear how to define set for virtual record selectors. For 
> example, we might define
>
>        data Complex = Complex {re :: Float, im :: Float}
>
>        instance Has Complex "arg" Float where
>                get r = atan2 r.im r.re
>
> but if we want to set "arg", what should be kept constant? The obvious answer 
> is "mod", but we haven't even defined it, and there are plenty of cases where 
> there is no obvious answer.
>
> 2. If the data type has one or more parameters, updates can change the type 
> of the record. Set can never do this, because of its type. What is more, if 
> several fields depend on the parameter, for example
>
>        data Twice a = Twice {first :: a, second :: a}
>
> any update of "first" which changes the type must also update "second" at the 
> same time to keep the type correct. No hacked version of set can do this.
>
> 3. The Haskel implementation of impredicative polymorphism (from the Boxy 
> Types paper) isn't strong enough to cope with higher rank field types in 
> instances of set.
>
> 4. The translation of multiple updates into multiple applications of set is 
> not the same as the definition of updates in the Haskel report, where updates 
> are simultaneous not sequential. This would be less efficient, and in the 
> case of virtual record selectors, it wouldn't be equal, and is arguably 
> incorrect.
>
>
> Point 3 could possibly be fixed by improving the strength of the type system, 
> but SPJ says this is a hard problem, and no-one else seems ready to tackle 
> it. Points 1, 2 & 4 suggest that any solution must deal not with individual 
> fields but with sets of fields that can sensibly be updated together.
>
>
>  The Proposed Solution.
> --
>
> This is an extension to SORF. I don't know if the same approach could be 
> applied to other label systems.
>
> 1. Introduce a new form of class declaration:
>
>        class Rcls r where
>                r {n1 :: t1, n2 :: t2}
>
> is translated as
>
>        class (Has r n1 t1, Has r n2 t2) => Rcls r where
>                setRcls :: t1 -> t2 -> r -> r
>
> setRcls is used internally but hidden from the user.
>
> 2. Instances of record classes can use a special form of default. So
>
>        data Rec = Rec {n1 :: t1, n2 :: t2}
>
>        instance Rcls Rec
>
> is translated as
>
>        instance Rcls Rec where
>                setRcls x1 y1 (Rec _ _) = Rec x1 y1
>
> provided all the fields in the class occur in the data type with the correct 
> types. In general, the definition of the update function is the same as the 
> Haskel98 translation of update, solving problem 4.
>
> 3. The syntax of record updates must be changed to include the class:
>
>        r {Rcls| n1 = x1, n2 = x2}
>
> is translated as
>
>        setRcls x1 x2 r
>
> Updating a subset of the fields is allowed, so
>
>        r {Rcls| n1 = x1}
>
> is translated as
>
>        setRcls x1 (r.n2) r
>
>
> 4. Non default instances use the syntax:
>
>        instance Rcls Rec where
>                r {Rcls| n1 = x1, n2 = x2} = ...x1..x2..
>
> which is translated as
>
>        instance Rcls Rec where
>                setRcls x1 y1 r = ...x1..x2..
>
> in order to allow virtual selectors. This solves problem 1, because updates 
> are grouped together in a meaningful way. An extended example is given below.
>
> 5. Record classes can have parameters, so
>
>        class TwiceClass r where
>                r a {first :: a, second :: a}
>        data Twice a = Twice {first :: a, second :: a}
>        instance TwiceClass Twice
>
> translates as
>
>        class TwiceClass r where
>                setTwiceClass :: a -> a -> r b -> r a
>        data Twice a = Twice {first :: a, second :: a}
>        instance TwiceClass Twice where
>                setTwiceClass x y (Twice _ _) = Twice x y
>
> which allows updates to change the type correctly. This solves problem 2.
>
> 6. Problem 3 *almost* works. The translation of
>
>        class HRClass r where
>                r {rev :: forall a. [a] -> [a]}
>
> is
>
>        class Has r "rev" (forall a. [a] -> [a]) =>

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

2012-03-05 Thread Matthew Farkas-Dyck
On 03/03/2012, AntC  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


Re: Why I Want Global Field Names (By Default)

2012-03-05 Thread wren ng thornton

On 3/5/12 12:03 AM, Gershom Bazerman wrote:

So, suppose we have a locally declared fields solution (such as DORF).
Now, where do these fields live? Arguably, we want a module per record.


Rather, part of the point of all this is precisely that we *don't* want 
one module per record. That's the organization required presently, since 
it's the only way to use the module system for namespace resolution. 
Ideally we should be able to define multiple records with the same field 
name within a single module, rather than being forced to break the 
module up into many files (and polluting the module namespace along the 
way).


Also, if your goal is to have a global namespace, that can be 
approximated precisely by placing all declarations in a single module. 
In virtue of being in a single module, they're all in the same 
namespace; the client then just has to import your "global" module in 
order to get everything. Indeed this has the benefit of modularity 
because if my code depends on two separate projects which both want 
"global" namespaces, this would allow me to use them simultaneously. If 
we are to have any packaging and code reuse at all, this ability to 
compose multiple packages is absolutely essential.


Furthermore, this would *avoid* spurious recompilation, since if I 
upgrade my dependency on project A then I don't need to recompile any 
modules which only depend on project B.


--
Live well,
~wren

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


Re: Error while installing new packages with GHC 7.4.1

2012-03-05 Thread Albert Y. C. Lai

On 12-02-29 09:30 PM, Brent Yorgey wrote:

I wonder about the possibility of making a simple tool to parse the
output of cabal install -v3 and visualize/organize it in some sort of
way to make this process easier.  What might such
visualization/organization look like?


The most useful information is like this (let's say someone orders 
"cabal install -v3 x"):


will add array-0.4.999 for
  x-2.3's array >= 0.4.999
  containers-0.4.2.1's array any
  Cabal-1.14.0's array >= 0.1 && < 0.5
  ignoring existing array-0.4.0.0
will replace containers-0.4.2.1 for
  Cabal-1.14.0's containers >= 0.1 && < 0.5
  change of array
  ignoring existing containers-0.4.2.1
will replace Cabal-1.14.0 for
  x-2.3's Cabal >= 1.12
  change of array, containers, process
  ignoring existing Cabal-1.14.0
will add x-2.3 for
  command's x any

(remark: change of process happened in a previous session and noticed now)

Most of this information is not found the output of cabal install -v3.

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