An idea on extensible effects (anonymous record)

Hi everyone! First of all, i don't know if this idea is already being discussed so if there's a discussion on this i'd like to follow. To illustrate, first i want to create a class like: class Has a t where get :: t -> a then i define instance for simple product type such as tuple: instance Has a (a, b) where get (a, _) = a instance Has b (a, b) where get (_, b) = b ... You can image i will use th to make lots of instance for difference tuple size. Now if i want an extensible reader, i use Has class like this: someReader :: Has Int t => Reader t Int someReader = do x <- ask return $ get x + 1 Then i can run it with any tuple with an Int field like: runReader someReader (0 :: Int, "adad”) -- 1 This typeclass almost solved all problem of my network application: sometime’s i want ensure a logger, a sql backend and a http client pool in my monad’s environment, but i don’t want to fix my environment into a record. We can add a set :: a -> t -> t, or use lens to define Has, so that we can have extensible states. We can also use Tagged to achieve something like: (Has (Tagged “SqlBackEndOne” SqlBackEnd) t, Has (Tagged “SqlBackEndTwo" SqlBackEnd) t) => Reader t () It there a library doing this, maybe in lens? or there’re some drawbacks i didn’t notice? All ideas are welcomed! Cheers~ Winter

On Mon, Nov 21, 2016 at 10:30 PM, winter
To illustrate, first i want to create a class like:
class Has a t where get :: t -> a
Does this differ significantly from fclabels or the upcoming OverloadedRecordFields extension? (Aside from being purely type driven, which has problems in your example if you compose a second Int into it.) -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

1. Yes, it’s similar to OverloadedRecordFields but doesn’t force you to use a label, and you may use Tagged to label a field if you want. 2. Yes, but again, you can use Tagged to allow same type in different disguise.
On 22 Nov 2016, at 11:32, Brandon Allbery
wrote: On Mon, Nov 21, 2016 at 10:30 PM, winter
mailto:drkoster@qq.com> wrote: To illustrate, first i want to create a class like: class Has a t where get :: t -> a
Does this differ significantly from fclabels or the upcoming OverloadedRecordFields extension? (Aside from being purely type driven, which has problems in your example if you compose a second Int into it.)
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com mailto:allbery.b@gmail.com ballbery@sinenomine.net mailto:ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net http://sinenomine.net/

>> Does this differ significantly from fclabels or the upcoming >> OverloadedRecordFields extension? (Aside from being purely type >> driven, which has problems in your example if you compose a second >> Int into it.) > 1. Yes, it’s similar to OverloadedRecordFields but doesn’t force you > to use a label, and you may use Tagged to label a field if you want. > 2. Yes, but again, you can use Tagged to allow same type in different > disguise. I can see a potential problem because you can't hide instances. Once you define a Has-relationship, you can't cheaply change it. That could lead to conflicts, unless you hack around it with orphaned instances in a separate module. But you say you want to solve conflicts with tagging – so it would be reasonable to incorporate the tag in the class from the start. Which brings us back to fclabels I suppose. MarLinn

Which brings us back to fclabels I suppose.
Can you elaborate this? I haven’t fully understand what is “incorporate the tag in the class from the start” . Thanks you. Cheer~ Winter
On 22 Nov 2016, at 15:33, MarLinn via Haskell-Cafe
wrote: Does this differ significantly from fclabels or the upcoming OverloadedRecordFields extension? (Aside from being purely type driven, which has problems in your example if you compose a second Int into it.)
1. Yes, it’s similar to OverloadedRecordFields but doesn’t force you to use a label, and you may use Tagged to label a field if you want. 2. Yes, but again, you can use Tagged to allow same type in different disguise.
I can see a potential problem because you can't hide instances. Once you define a Has-relationship, you can't cheaply change it. That could lead to conflicts, unless you hack around it with orphaned instances in a separate module. But you say you want to solve conflicts with tagging – so it would be reasonable to incorporate the tag in the class from the start. Which brings us back to fclabels I suppose.
MarLinn _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

>> Which brings us back to fclabels I suppose. > Can you elaborate this? I haven’t fully understand what is > “incorporate the tag in the class from the start” . Thanks you. Suppose you have the original definitions class Has a t where get :: t -> a instance Has a (a, b) where get (a, _) = a instance Has b (a, b) where get (_, b) = b This creates a conflict if you use an (Int,Int) tuple because there are either no definitions or two conflicting definitions for get. As a solution you propose something along the lines of Has (Tagged “GetGetsFirst” a) (a,b) All I'm saying is that it seems useful or even necessary for sanity to combine Hasand Taggedso that you can write Has “fst” a (a,b) The implementation should be something simple like class (KnownSymbol label) => Has label part whole | whole,label -> part where get :: Proxy label -> whole -> part -- 'Proxy label' is necessary because 'whole' and 'part' alone are not sufficient to determine the label. See (Int,Int). The obvious downside is that it doesn't make as much sense to have such a class now. I must admit I'm not too familiar with the alternatives, so I can't really compare it. But this was just a flaw I saw. Hope this cleared up what I meant. Cheers, MarLinn >>>> Does this differ significantly from fclabels or the upcoming >>>> OverloadedRecordFields extension? (Aside from being purely type >>>> driven, which has problems in your example if you compose a second >>>> Int into it.) >>> 1. Yes, it’s similar to OverloadedRecordFields but doesn’t force you >>> to use a label, and you may use Tagged to label a field if you want. >>> 2. Yes, but again, you can use Tagged to allow same type in >>> different disguise. >> I can see a potential problem because you can't hide instances. Once >> you define a Has-relationship, you can't cheaply change it. That >> could lead to conflicts, unless you hack around it with orphaned >> instances in a separate module. But you say you want to solve >> conflicts with tagging – so it would be reasonable to incorporate the >> tag in the class from the start. Which brings us back to fclabels I >> suppose.

Hi MarLinn! In my use case the type collision is definitely much less likely to happen, that is i often want to compose different effects like logger, sql and network ,etc. without Has class, i will have a hard time trying to compose `Reader Logger ()` and `Reader (Logger, HttpClient) ()`, since the concrete type can't be unified. If i need two different Logger in environment, i still can do it without Tagged, i can define following newtypes in library site: newtype StdLogger = StdLogger Logger newtype FileLogger = FileLogger Logger librarySite :: (Has StdLogger r, Has FileLogger r, MonadReader r m) => m () librarySite = do ... stdLogger :: StdLogger <- asks get logWith stdLogger ... fileLogger :: FileLogger <- asks get logWith fileLogger ... And in application site i should supply a (StdLogger log1, FileLogger log2, ...). Does above example illustrate my use case to you? Cheers~ Winter
On 22 Nov 2016, at 21:48, MarLinn
wrote: Which brings us back to fclabels I suppose. Can you elaborate this? I haven’t fully understand what is “incorporate the tag in the class from the start” . Thanks you.
Suppose you have the original definitions class Has a t where get :: t -> a
instance Has a (a, b) where get (a, _) = a
instance Has b (a, b) where get (_, b) = b This creates a conflict if you use an (Int,Int) tuple because there are either no definitions or two conflicting definitions for get. As a solution you propose something along the lines of Has (Tagged “GetGetsFirst” a) (a,b) All I'm saying is that it seems useful or even necessary for sanity to combine Has and Tagged so that you can write Has “fst” a (a,b) The implementation should be something simple like class (KnownSymbol label) => Has label part whole | whole,label -> part where get :: Proxy label -> whole -> part -- 'Proxy label' is necessary because 'whole' and 'part' alone are not sufficient to determine the label. See (Int,Int). The obvious downside is that it doesn't make as much sense to have such a class now. I must admit I'm not too familiar with the alternatives, so I can't really compare it. But this was just a flaw I saw. Hope this cleared up what I meant.
Cheers, MarLinn
Does this differ significantly from fclabels or the upcoming OverloadedRecordFields extension? (Aside from being purely type driven, which has problems in your example if you compose a second Int into it.)
1. Yes, it’s similar to OverloadedRecordFields but doesn’t force you to use a label, and you may use Tagged to label a field if you want. 2. Yes, but again, you can use Tagged to allow same type in different disguise. I can see a potential problem because you can't hide instances. Once you define a Has-relationship, you can't cheaply change it. That could lead to conflicts, unless you hack around it with orphaned instances in a separate module. But you say you want to solve conflicts with tagging – so it would be reasonable to incorporate the tag in the class from the start. Which brings us back to fclabels I suppose.

hi winter, This seems to be equivalent to the idea behind the multistate package [1], and its MultiReader type [2]. The `MonadMultiReader` class [3] does a lookup in a type-level (linked) list similar to your Tuple-focussed `Has` class. [1] https://hackage.haskell.org/package/multistate [2] hackage.haskell.org/package/multistate-0.7.1.1/docs/Control-Monad-MultiReader.html [3] https://hackage.haskell.org/package/multistate-0.7.1.1/docs/Control-Monad-Tr... The type signature would become
(MonadMultiReader (Tagged “SqlBackEndOne” SqlBackEnd) m, MonadMultiReader (Tagged “SqlBackEndTwo" SqlBackEnd) m) => m ()
Note that one main drawback of this approach is the necessity of dropping the functional dependency present on MultiReader (for MonadMultiReader). So the cost of automatic type-based lookup is less type inference; a simple example would be `mAsk >>= print` being ambiguous where `ask >>= print` is not (if the surrounding `m` is known). -- lennart On 22/11/16 04:30, winter wrote:
Hi everyone!
First of all, i don't know if this idea is already being discussed so if there's a discussion on this i'd like to follow.
To illustrate, first i want to create a class like:
class Has a t where get :: t -> a
then i define instance for simple product type such as tuple:
instance Has a (a, b) where get (a, _) = a
instance Has b (a, b) where get (_, b) = b
...
You can image i will use th to make lots of instance for difference tuple size. Now if i want an extensible reader, i use Has class like this:
someReader :: Has Int t => Reader t Int someReader = do x <- ask return $ get x + 1
Then i can run it with any tuple with an Int field like:
runReader someReader (0 :: Int, "adad”) -- 1
This typeclass almost solved all problem of my network application: sometime’s i want ensure a logger, a sql backend and a http client pool in my monad’s environment, but i don’t want to fix my environment into a record.
We can add a set :: a -> t -> t, or use lens to define Has, so that we can have extensible states. We can also use Tagged to achieve something like:
(Has (Tagged “SqlBackEndOne” SqlBackEnd) t, Has (Tagged “SqlBackEndTwo" SqlBackEnd) t) => Reader t ()
It there a library doing this, maybe in lens? or there’re some drawbacks i didn’t notice? All ideas are welcomed!
Cheers~ Winter
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

Hi, Lennart there're several extensible effect systems build around HList(typed aligned sequence in general), but one thing bother me is that HList 's efficiency. I'm not sure if HList can be totally inlined. But as far as I can tell, inline tuple field is very easy for ghc. I'd be very happy if you can prove me HList is just fine. I also want to reuse mtl as much as possible, so it's easier for beginner to get started, thus there's no need to create another monad transformers library. After all, `Has x r` is short than `MonadXXX x m`, so you won't have a long signature all the way down. Cheers Winter~ 发自我的 iPhone
在 2016年12月1日,上午12:13,lennart spitzner
写道: hi winter,
This seems to be equivalent to the idea behind the multistate package [1], and its MultiReader type [2]. The `MonadMultiReader` class [3] does a lookup in a type-level (linked) list similar to your Tuple-focussed `Has` class.
[1] https://hackage.haskell.org/package/multistate [2] hackage.haskell.org/package/multistate-0.7.1.1/docs/Control-Monad-MultiReader.html [3] https://hackage.haskell.org/package/multistate-0.7.1.1/docs/Control-Monad-Tr...
The type signature would become
(MonadMultiReader (Tagged “SqlBackEndOne” SqlBackEnd) m, MonadMultiReader (Tagged “SqlBackEndTwo" SqlBackEnd) m) => m ()
Note that one main drawback of this approach is the necessity of dropping the functional dependency present on MultiReader (for MonadMultiReader). So the cost of automatic type-based lookup is less type inference; a simple example would be `mAsk >>= print` being ambiguous where `ask >>= print` is not (if the surrounding `m` is known).
-- lennart
On 22/11/16 04:30, winter wrote: Hi everyone!
First of all, i don't know if this idea is already being discussed so if there's a discussion on this i'd like to follow.
To illustrate, first i want to create a class like:
class Has a t where get :: t -> a
then i define instance for simple product type such as tuple:
instance Has a (a, b) where get (a, _) = a
instance Has b (a, b) where get (_, b) = b
...
You can image i will use th to make lots of instance for difference tuple size. Now if i want an extensible reader, i use Has class like this:
someReader :: Has Int t => Reader t Int someReader = do x <- ask return $ get x + 1
Then i can run it with any tuple with an Int field like:
runReader someReader (0 :: Int, "adad”) -- 1
This typeclass almost solved all problem of my network application: sometime’s i want ensure a logger, a sql backend and a http client pool in my monad’s environment, but i don’t want to fix my environment into a record.
We can add a set :: a -> t -> t, or use lens to define Has, so that we can have extensible states. We can also use Tagged to achieve something like:
(Has (Tagged “SqlBackEndOne” SqlBackEnd) t, Has (Tagged “SqlBackEndTwo" SqlBackEnd) t) => Reader t ()
It there a library doing this, maybe in lens? or there’re some drawbacks i didn’t notice? All ideas are welcomed!
Cheers~ Winter
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
participants (4)
-
Brandon Allbery
-
lennart spitzner
-
MarLinn
-
winter