
Hello, I'm pleased to announce the release of my new library, named "has", written to aim to ease pain at inconvinience of Haskell's build-in records. With the has, You can reuse accessors over records to write generic function, combine records with another. Repository is at GitHub: http://github.com/nonowarn/has Uploaded on Hackage: http://hackage.haskell.org/package/has So you can install this by "cabal install has" You can use the has in three steps (without counting installation). 1. Write {-# OPTIONS_GHC -fglasgow-exts #-} top of your code, import Data.Has module.
{-# OPTIONS_GHC -fglasgow-exts #-} import Data.Has
2. Define entities. "Entity" is data to index field in records. You can define an entity in one line.
data Foo = Foo; type instance TypeOf Foo = Int
(I lied) Before semicolon, declares entity. After semicolon, specifies the type to which the entity points. Define some entities for later examples.
data Bar = Bar; type instance TypeOf Bar = Double data Baz = Baz; type instance TypeOf Baz = String data Quux = Quux; type instance TypeOf Quux = Bool
3. Define Records by concatinating fields of entities.
type MyRecord = FieldOf Foo :&: FieldOf Bar :&: FieldOf Baz
This is almost same as writing < data MyRecord = MyRecord { foo :: Int < , bar :: Double < , baz :: String < } To construct a value of record, remove colons and replace entities in record with values, and uncapitalize some words.
aRecord :: MyRecord aRecord = fieldOf 42 & fieldOf 3.14 & fieldOf "string"
And you can play with it. To read/write/modify a value of field in records, you can use functions with names stealed from data-accessor. But uses value-level entities instead of accessors. < Foo ^. aRecord -- Reading < Foo ^= 4649 $ aRecord -- Writing < Foo ^: (*2) $ aRecord -- Modifying If we have another record type contains Foo field, You can still access the field in the same way.
type AnotherRecord = FieldOf Bar :&: FieldOf Foo anotherRecord :: AnotherRecord anotherRecord = fieldOf 2.71 & fieldOf 31
< Foo ^. anotherRecord -- And this also works Using these functions and Has constraint, You can write generic functions over records.
fooIsGreaterThan :: (Has Foo r) => r -> Int -> Bool fooIsGreaterThan r x = (Foo ^. r) > x
< aRecord `fooIsGreaterThan` 40 -- evaluated to True < anotherRecord `fooIsGreaterThan` 40 -- evaluated To False Even if you defined another record by combining records by (:&:), you can still access the field, and apply to generic functions.
type MoreRecord = FieldOf Baz :&: FieldOf Quux type CombinedRecord = AnotherRecord :&: MoreRecord combinedRecord :: CombinedRecord combinedRecord = (fieldOf 1.618 & fieldOf 39) & (fieldOf "sowaka" & fieldOf True) -- We can omit parentheses -- (even place parens anyware in record)
< combinedRecord `fooIsGreaterThan` 40 -- This yet works The Has constraint provides not only genericity but also safety. If the record doesn't satisfy the constraint, the type checker rejects it.
predicateOnRecords :: (Has Foo r, Has Quux r) => r -> Bool predicateOnRecords r = fooIsGreaterThan r 30 && (Quux ^. r)
< predicateOnRecords combinedRecord -- This is OK < predicateOnRecords aRecord -- This yields compile error More examples included in package[1] [1]: http://github.com/nonowarn/has/tree/master/examples/ This library is inspired by HList[2], and interfaces are stealed from data-accessors[3]. And lenses[4], fclabels[5], and records[6] devote themselves to similar purposes. [2]: http://hackage.haskell.org/package/HList [3]: http://hackage.haskell.org/package/data-accessor [4]: http://hackage.haskell.org/package/lenses [5]: http://hackage.haskell.org/package/fclabels [6]: http://hackage.haskell.org/package/records Enjoy! -nwn

On Tue, May 4, 2010 at 10:18 AM, HASHIMOTO, Yusaku
Hello,
I'm pleased to announce the release of my new library, named "has", written to aim to ease pain at inconvinience of Haskell's build-in records.
Hmm, nice work, looks interesting.
With the has, You can reuse accessors over records to write generic function, combine records with another.
Repository is at GitHub: http://github.com/nonowarn/has Uploaded on Hackage: http://hackage.haskell.org/package/has
So you can install this by "cabal install has"
You can use the has in three steps (without counting installation).
1. Write {-# OPTIONS_GHC -fglasgow-exts #-} top of your code,
This is going out of style. It would be nice to know specifically what LANGUAGE extensions are necessary. Luke

Hello
I'm pleased to announce the release of my new library, named "has", written to aim to ease pain at inconvinience of Haskell's build-in records.
Hmm, nice work, looks interesting.
Thanks!
You can use the has in three steps (without counting installation).
1. Write {-# OPTIONS_GHC -fglasgow-exts #-} top of your code,
This is going out of style. It would be nice to know specifically what LANGUAGE extensions are necessary.
Ah, yes. {-# LANGUAGE TypeFamilies #-} is enough for that literate haskell file, But the has depends GHC's language extensions such as UndecidableInstances, OverlappingInstances and TypeFamilies. But I'll remove OPTIONS_GHC pragma from library codes. Thank you for your suggestion. -nwn

I uploaded new version (0.4.0.1) of this package with proper pragmas.
On 5 May 2010 02:00, HASHIMOTO, Yusaku
Hello
I'm pleased to announce the release of my new library, named "has", written to aim to ease pain at inconvinience of Haskell's build-in records.
Hmm, nice work, looks interesting.
Thanks!
You can use the has in three steps (without counting installation).
1. Write {-# OPTIONS_GHC -fglasgow-exts #-} top of your code,
This is going out of style. It would be nice to know specifically what LANGUAGE extensions are necessary.
Ah, yes. {-# LANGUAGE TypeFamilies #-} is enough for that literate haskell file, But the has depends GHC's language extensions such as UndecidableInstances, OverlappingInstances and TypeFamilies. But I'll remove OPTIONS_GHC pragma from library codes. Thank you for your suggestion.
-nwn

I think I missed your point in my last post, and there are more necessary extensions need to be enabled than I wrote before. TypeFamilies, TypeOperator and FlexibleContexts extensions are necessary. So you need to write this at top of the code if you don't choose OPTIONS_GHC pragma.
{-# LANGUAGE TypeFamilies,TypeOperators,FlexibleContexts #-}
Sorry for incorrect information.
-nwn
On 5 May 2010 02:33, HASHIMOTO, Yusaku
I uploaded new version (0.4.0.1) of this package with proper pragmas.
On 5 May 2010 02:00, HASHIMOTO, Yusaku
wrote: Hello
I'm pleased to announce the release of my new library, named "has", written to aim to ease pain at inconvinience of Haskell's build-in records.
Hmm, nice work, looks interesting.
Thanks!
You can use the has in three steps (without counting installation).
1. Write {-# OPTIONS_GHC -fglasgow-exts #-} top of your code,
This is going out of style. It would be nice to know specifically what LANGUAGE extensions are necessary.
Ah, yes. {-# LANGUAGE TypeFamilies #-} is enough for that literate haskell file, But the has depends GHC's language extensions such as UndecidableInstances, OverlappingInstances and TypeFamilies. But I'll remove OPTIONS_GHC pragma from library codes. Thank you for your suggestion.
-nwn

On Tue, May 4, 2010 at 12:18 PM, HASHIMOTO, Yusaku
This library is inspired by HList[2], and interfaces are stealed from data-accessors[3]. And lenses[4], fclabels[5], and records[6] devote themselves to similar purposes.
[2]: http://hackage.haskell.org/package/HList [3]: http://hackage.haskell.org/package/data-accessor [4]: http://hackage.haskell.org/package/lenses [5]: http://hackage.haskell.org/package/fclabels [6]: http://hackage.haskell.org/package/records
Enjoy!
-nwn
Which niche does `has' fit between extensible (and more complicated) records like HList and records vs the libraries that provide only accessors? It would be nice to have some summary of the features of each, ex. lenses, fclabels and data-accessor do not permit record extension (which has seems to do). -- Adam

On 11 May 2010 03:25, adam vogt
On Tue, May 4, 2010 at 12:18 PM, HASHIMOTO, Yusaku
wrote: This library is inspired by HList[2], and interfaces are stealed from data-accessors[3]. And lenses[4], fclabels[5], and records[6] devote themselves to similar purposes.
[2]: http://hackage.haskell.org/package/HList [3]: http://hackage.haskell.org/package/data-accessor [4]: http://hackage.haskell.org/package/lenses [5]: http://hackage.haskell.org/package/fclabels [6]: http://hackage.haskell.org/package/records
Enjoy!
-nwn
Which niche does `has' fit between extensible (and more complicated) records like HList and records vs the libraries that provide only accessors?
You may find `has' useful when you want to use a label name in more than one record structures. This is achieved by HList, records and wreckage, But I think has at its interface.

Sorry for spamming, what I wanted to write is I think `has' has better
interface than other record packages in types.
There are many libraries to write function "takes an record has Foo
and Bar and returns something." But writing type of the function is
still difficult. I can't write such types using HList or records
without reading documents. I think, using has, There's few effort to
write such types.
I think `has' fits the needs of Haskellers who have the good habit of
writing a type of a function before its definition.
On 14 May 2010 07:58, HASHIMOTO, Yusaku
On 11 May 2010 03:25, adam vogt
wrote: On Tue, May 4, 2010 at 12:18 PM, HASHIMOTO, Yusaku
wrote: This library is inspired by HList[2], and interfaces are stealed from data-accessors[3]. And lenses[4], fclabels[5], and records[6] devote themselves to similar purposes.
[2]: http://hackage.haskell.org/package/HList [3]: http://hackage.haskell.org/package/data-accessor [4]: http://hackage.haskell.org/package/lenses [5]: http://hackage.haskell.org/package/fclabels [6]: http://hackage.haskell.org/package/records
Enjoy!
-nwn
Which niche does `has' fit between extensible (and more complicated) records like HList and records vs the libraries that provide only accessors?
You may find `has' useful when you want to use a label name in more than one record structures. This is achieved by HList, records and wreckage, But I think has at its interface.

On Thu, May 13, 2010 at 7:16 PM, HASHIMOTO, Yusaku
Sorry for spamming, what I wanted to write is I think `has' has better interface than other record packages in types.
There are many libraries to write function "takes an record has Foo and Bar and returns something." But writing type of the function is still difficult. I can't write such types using HList or records without reading documents. I think, using has, There's few effort to write such types.
In which manner do you need to read less documentation to write: ] f :: Has Foo r => r -> ... Instead when using HList: ] f :: HasField Foo record fieldType => ...
I think `has' fits the needs of Haskellers who have the good habit of writing a type of a function before its definition.
What does this mean exactly in terms of the type inference possible? -- Adam

There are many libraries to write function "takes an record has Foo and Bar and returns something." But writing type of the function is still difficult. I can't write such types using HList or records without reading documents. I think, using has, There's few effort to write such types.
In which manner do you need to read less documentation to write:
] f :: Has Foo r => r -> ...
Instead when using HList:
] f :: HasField Foo record fieldType => ...
HasField only gives projection function (hLookupByLabel), but Has gives projection, injection and modification function. If I want to write a generic function injecting a value into field Foo in a record by HList, I should read documentation more.
I think `has' fits the needs of Haskellers who have the good habit of writing a type of a function before its definition.
What does this mean exactly in terms of the type inference possible?
Probably, yes. it's still fragile due to some reasons e.g. the behavior of UndecidableInstances language extension.
import Data.Has data Foo = Foo; type instance TypeOf Foo = Int data Bar = Bar; type instance TypeOf Bar = Int f r = (Foo ^. r) + (Bar ^. r)
*Main> :t f f :: forall s. (Contains (Labelled Foo Int) s, Contains (Labelled Bar Int) s) => s -> TypeOf Foo -nwn
participants (3)
-
adam vogt
-
HASHIMOTO, Yusaku
-
Luke Palmer