Re: [Hs-Generics] FW: [Haskell-cafe] SYB vs HList (again)

2007-03-22 Thread S. Alexander Jacobson


Not sure the proposal helps me with my other issues.  The appealing 
thing about hlists is that labels are first class which means obvious 
ways of parsing URLEncoded Strings and obvious ways to render them in 
XML.  In particular HLists are actually a different type from 
positional data declarations and that is good.


-Alex-



On Wed, 21 Mar 2007, Jules Bean wrote:


S. Alexander Jacobson wrote:


Conceptually, I think what I really want is the data structure equivalent 
of type inference.  Just as I don't want to be forced to declare my 
function types, I don't want to be forced to declare my data types.  The 
field labels I use should be enough to define the shape of my type.  The 
reason this is really important is that if hlists contain hlists, the type 
declarations can get really really messy


Separately, I would really like hrecords not to have order dependency. It 
seems strange to me that (Foo .*. Bar .*. HNil) is a different type from 
(Bar .*. Foo .*. HNil).




These particular two issues : type inference based on record 'shape' and 
records without order dependency, (ignoring the SYB part of the problem for 
the moment) are both addressed in the following haskell records proposal 
(and, undoubtedly, others) 
http://research.microsoft.com/~simonpj/Haskell/records.html


Jules



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


Re: [Hs-Generics] FW: [Haskell-cafe] SYB vs HList (again)

2007-03-21 Thread Jules Bean

S. Alexander Jacobson wrote:


Conceptually, I think what I really want is the data structure 
equivalent of type inference.  Just as I don't want to be forced to 
declare my function types, I don't want to be forced to declare my 
data types.  The field labels I use should be enough to define the 
shape of my type.  The reason this is really important is that if 
hlists contain hlists, the type declarations can get really really messy


Separately, I would really like hrecords not to have order dependency. 
It seems strange to me that (Foo .*. Bar .*. HNil) is a different type 
from (Bar .*. Foo .*. HNil).




These particular two issues : type inference based on record 'shape' and 
records without order dependency, (ignoring the SYB part of the problem 
for the moment) are both addressed in the following haskell records 
proposal (and, undoubtedly, others) 
http://research.microsoft.com/~simonpj/Haskell/records.html


Jules

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


Re: [Hs-Generics] FW: [Haskell-cafe] SYB vs HList (again)

2007-03-20 Thread S. Alexander Jacobson

Oleg,


data Name  = Name String String deriving Show
newtype Salary = S Float deriving Show
data Dept  = D String Int deriving Show


I like the idea of these simpler label declarations, but I think the 
cost is that it is harder to write generic code for e.g. parsing 
urlencoded data or generating XML.  If I understand your concept here 
correctly, you need to write not only the label declaration but also 
dedicated code for parsing/generating with each label type.  For 
example, how do you extract a Name above from a urlencoded string?


Yes the hlist label declaraions I am using are very verbose, but they 
are easy to tighten with template haskell (even if I think template 
haskell is ugly).



It would be really nice if there was some way to tell Haskell that
HLists have no more fields than the ones you happen to be getting and
setting in your code. Effectively that would mean you get data
structure inference not just function type inference which would be
really cool!


I'm not sure I follow. Could you outline an example of the code you
wish work? Incidentally, a lot of the library depends on the record
types being members of some specific classes. One can define



I'd like be able to do something like this:

  $(label Salary Int) -- template haskell to define salary label
  main = do
 person - readFile blah = return . read
 print $ person # salary


In this case, haskell would assume that person has only one label, 
salary.  The read function would ignore all the other labels.   If I 
changed the code to this:


  $(label Salary Int) -- template haskell to define salary label
  $(label Name String)

  main = do
 person - readFile blah = return . read
 print $ person # salary
 print $ show (person::Name .*. Salary)

Then the code would assume that a person has both a name and a salary.

Conceptually, I think what I really want is the data structure 
equivalent of type inference.  Just as I don't want to be forced to 
declare my function types, I don't want to be forced to declare my 
data types.  The field labels I use should be enough to define the 
shape of my type.  The reason this is really important is that if 
hlists contain hlists, the type declarations can get really really 
messy


Separately, I would really like hrecords not to have order dependency. 
It seems strange to me that (Foo .*. Bar .*. HNil) is a different type 
from (Bar .*. Foo .*. HNil).


If there is no way to get the type system to do this, I think I will 
probably use template haskell to declare the types of HList records. 
I assume I can make template haskell always sort the labels before 
generating the type code.


-Alex-





On Thu, 15 Mar 2007, [EMAIL PROTECTED] wrote:



[Please follow-up to [EMAIL PROTECTED]

S. Alexander Jacobson wrote:

HLists require you to define Labels and basically only use label
values that are themselves either scalar or HLists.
...
With SYB you create field labels using newtype (or data) declarations
e.g.

   data Salary = S {salary::Float}

With HList, label declarations are really verbose e.g.

   data SalaryLabel deriving(Typeable)
   type Salary = Field (Proxy SalaryLabel) Int
   salary = proxy :: Proxy FooLabel


Actually there is no requirement that HList record names must be
scalar `labels', must be Proxies and require such a complex
declaration. From HList's high point of view, any collection can be a
record provided the type of each item is unique and there is some way
to extract the value associated with that type. The HList library
provides two implementations of Records (and there was one more,
obsolete now). There could be more. For example, I have just committed
a yet another implementation,
http://darcs.haskell.org/HList/src/RecordD.hs
Here a record is a list of things that have a type and a value and
provide a way to extract that value. The example from the end of this
file seems worth quoting:


data Name  = Name String String deriving Show
newtype Salary = S Float deriving Show
data Dept  = D String Int deriving Show

person = (Name Joe Doe) .*. (S 1000) .*. (D CIO 123) .*. emptyRecord

-- could be derived automatically, like Typeable...
instance Fieldish Name (String,String) where
fromField (Name s1 s2) = (s1,s2)
instance Fieldish Salary Float where
fromField (S n) = n
instance Fieldish Dept (String,Int) where
fromField (D s n) = (s,n)

test1 = show person
-- When a field acts as a label, only its type matters, not the contents
test2 = person .!. (Name undefined undefined)
test3 = person .!. (undefined::Salary)
test5 = person .!. (D xxx 111)





I don't know exactly how HList handles default values but I assume you
can restrict use of those values to explicit deserialization contexts.
Is that correct?


I'm not sure what you mean about the restriction of default values to
deserialization contexts. Anyway, HList provides a left-biased union
of two records: hLeftUnion r1 r2 is the record r1 

Re: [Hs-Generics] FW: [Haskell-cafe] SYB vs HList (again)

2007-03-15 Thread oleg

[Please follow-up to [EMAIL PROTECTED]

S. Alexander Jacobson wrote:
 HLists require you to define Labels and basically only use label
 values that are themselves either scalar or HLists.
 ...
 With SYB you create field labels using newtype (or data) declarations
 e.g.

data Salary = S {salary::Float}

 With HList, label declarations are really verbose e.g.

data SalaryLabel deriving(Typeable)
type Salary = Field (Proxy SalaryLabel) Int
salary = proxy :: Proxy FooLabel

Actually there is no requirement that HList record names must be 
scalar `labels', must be Proxies and require such a complex
declaration. From HList's high point of view, any collection can be a
record provided the type of each item is unique and there is some way
to extract the value associated with that type. The HList library
provides two implementations of Records (and there was one more,
obsolete now). There could be more. For example, I have just committed
a yet another implementation,
http://darcs.haskell.org/HList/src/RecordD.hs
Here a record is a list of things that have a type and a value and
provide a way to extract that value. The example from the end of this
file seems worth quoting:

 data Name  = Name String String deriving Show
 newtype Salary = S Float deriving Show
 data Dept  = D String Int deriving Show

 person = (Name Joe Doe) .*. (S 1000) .*. (D CIO 123) .*. emptyRecord

 -- could be derived automatically, like Typeable...
 instance Fieldish Name (String,String) where 
 fromField (Name s1 s2) = (s1,s2)
 instance Fieldish Salary Float where
 fromField (S n) = n
 instance Fieldish Dept (String,Int) where
 fromField (D s n) = (s,n)

 test1 = show person
 -- When a field acts as a label, only its type matters, not the contents
 test2 = person .!. (Name undefined undefined)
 test3 = person .!. (undefined::Salary)
 test5 = person .!. (D xxx 111)



 I don't know exactly how HList handles default values but I assume you
 can restrict use of those values to explicit deserialization contexts.
 Is that correct?

I'm not sure what you mean about the restriction of default values to
deserialization contexts. Anyway, HList provides a left-biased union
of two records: hLeftUnion r1 r2 is the record r1 augmented with all
the fields from r2 that didn't occur in r2. One may consider r2 to be
the record with default fields and the corresponding values.

 It would be really nice if there was some way to tell Haskell that
 HLists have no more fields than the ones you happen to be getting and
 setting in your code. Effectively that would mean you get data
 structure inference not just function type inference which would be
 really cool!

I'm not sure I follow. Could you outline an example of the code you
wish work? Incidentally, a lot of the library depends on the record
types being members of some specific classes. One can define

 newtype ClosedRecord = ClosedRecord r

To make a ClosedRecord to be a record from which we can extract the
values of some fields, we merely need to say
 instance HasField l r v = HasField l (ClosedRecord r) v
 where hLookupByLabel l (ClosedRecord r) v = hLookupByLabel l r v

Since we did not make this record the member of HExtend or HAppend, it
is not extensible.


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