Oops, forgot my references

[1] Original post: http://www.twanvl.nl/blog/haskell/cps-functional-references
[2] polymorphic update support: http://r6.ca/blog/20120623T104901Z.html
[3] another post about these: http://comonad.com/reader/2012/mirrored-lenses/

On Fri, Aug 3, 2012 at 1:53 PM, Ryan Ingram <ryani.spam@gmail.com> wrote:


On Fri, Aug 3, 2012 at 10:11 AM, Jonathan Geddes <geddes.jonathan@gmail.com> wrote:
The nice part about the SEC functions is that
they compose as regular functions. Lenses are
super powerful in that they form a category.
Unfortunately using categories other than
functions feels a tad unwieldy because you
have to hide something from prelude and then
import Category. (A bit like exceptions,
currently).

FWIW this is also true for van Laarhoven lenses[1]

type FTLens a b = forall f. Functor f => (b -> f b) -> (a -> f a)

newtype Const a b = Const { unConst :: a } deriving Functor

get :: FTLens a b -> a -> b
get ft = unConst . ft Const

{-
ft :: forall f. (b -> f b) -> (a -> f a)
Const :: forall x. b -> Const b x
ft Const :: a -> Const b a
-}

newtype Id a = Id { unId :: a } deriving Functor

set :: FTLens a b -> b -> a -> a
set ft b = unId . ft (\_ -> Id b)

modify :: FTLens a b -> (b -> b) -> a -> a
modify ft k = unId . ft (Id . k)

-- example
fstLens :: FTLens (a,b) a
fstLens aToFa (a,b) = (,b) <$> aToFa a

-- and you get
compose :: FTLens b c -> FTLens a b -> FTLens a c
compose = (.)

identity :: FTLens a a
identity = id





If you like the look of "set" with lenses,
you could define a helper function to use
with SEC updaters.

>set :: ((b -> a) -> c) -> a -> c
>set sec = sec . const
>
>--and then use it like so:
>setPersonsSalary :: Salary -> Person -> Person
>setPersonsSalary salary = set personsSalary' salary

With it you can use an updater as a setter.
I'd like to reiterate one of finer points of
the original proposal.

>The compiler could disallow using old-style
>update syntax for fields whose SEC update
>function is not in scope, giving us
>fine-grained control over access and update.
>On the other hand we currently have to create
>new functions to achieve this (exporting the
>getter means exporting the ability to update
>[using update syntax] as well, currently).

And now back to lenses:

>it is really convenient how lenses let you compose the getter
>and setter together.

I don't recall too many cases where having the
getter and setter and modifier all in one
place was terribly useful. Could anyone give
me an example? But again, where that is
useful, a lens can be created from a getter
and a SEC updater.

Thoughts?

--Jonathan

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