[Haskell-cafe] An idea on extensible effects (anonymous record)
lennart spitzner
lsp at informatik.uni-kiel.de
Wed Nov 30 16:13:21 UTC 2016
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-Trans-MultiReader-Class.html
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.
>
More information about the Haskell-Cafe
mailing list