I haven’t used the optics
package in anger but I know that the lens
equivalent will force you to use ^?
to get a Maybe
if you’re getting anything derived from company
(good!), but will silently not update anything if you’re setting the company
on an AlienCountry
(worse than a run-time error, maybe?). It’s one of the few design issues I’ve found with lens
—I wish the basic setting operators had been specialized to something like Traversal1
, with more verbose operators reserved for those optics on which setting might be a no-op.
Generic field optics are lenses, so if you try to access a partial field, you’ll get a compilation error.
>>> data X = X1 { name1 :: String, name2 :: String } | X2 { name1 :: String } deriving (Generic,Show)
>>> let x1 = X1 "foo" "bar"
>>> x1 ^. #name1
"foo"
>>> x1 ^. #name2
<interactive>:7:7: error: [GHC-64725]
• Data constructor ‘X2’ doesn't have a field named ‘name2’
• In the second argument of ‘(^.)’, namely ‘#name2’
In the expression: x1 ^. #name2
In an equation for ‘it’: it = x1 ^. #name2
For partial fields you need to use gafield
which is an affine traversal:
>>> let x2 = X2 "foo"
>>> x2 ^? gafield @"name1"
Just "foo"
>>> x2 ^? gafield @"name2"
Nothing
So far, so samesies; the real question is what does x2 & gafield @"name2" .~ "lasagna"
do?
The failure should be forced to be acknowledged.
Given
data Foo = Bar {x :: Int, y :: Char} | Baz {x :: Int}
I can conclude that x is a field of a value of type Foo, and y is a partial field of a value of type Foo. The HasField I implemented could not be total. Foo can’t implement HasField. It’s wrong. Conceptually.
A total interface:
{-# LANGUAGE FunctionalDependencies, AllowAmbiguousTypes #-}
class HasField x r a | x r -> a where
hasField :: r -> (a -> r, a)
getField :: r -> a
getField = snd . hasField @x
setField :: r -> a -> r
setField = fst . hasField @x
class HasPartialField x r a | x r -> a where
hasPartialField :: r -> Maybe (a -> r, a)
getPartialField :: r -> Maybe a
getPartialField = fmap snd . hasPartialField @x
setPartialField :: r -> Maybe (a -> r)
setPartialField = fmap fst . hasPartialField @x
Examples:
data Oof = Oof { e :: Char }
data Quux = Quux { v :: Int }
data Foo = Bar {x :: Int, y :: Char, oof :: Oof } | Baz {x :: Int, z :: Quux, oof :: Oof}
-- introducing ? to access partial fields
-- and ?. is flipped fromMaybe
f :: Foo -> Int
f foo = foo.x
g :: Foo -> Char
g foo = foo?y ?. 'c'
h :: Foo -> Int
h foo = foo?z.v ?. 1
i :: Foo -> Char
i foo = foo.oof.e
j :: Int -> Foo -> Foo
j n foo = foo { x = n }
k :: Int -> Foo -> Foo
k n foo = foo { ?z.v = n } ?. foo
foo.z -- error
foo?.x -- error
-- ? is used for HasPartialField
-- . is used for HasField
{-
foo.bar.baz.quux desugars to
getField @quux . getField @baz . getField @bar $ foo
foo.bar?baz.quux desugars to
do
x0 <- Just (getField @bar foo)
x1 <- getPartialField @baz x0
x2 <- Just (getField @quux x1)
Just x2
foo { bar.baz.quux = a } desugars to
let x0 = getField @bar foo
x1 = getField @baz x0
x2 = getField @quux x1
in setField @bar (setField @baz (setField @quux x2 a) x1) x0
foo { bar?baz.quux = a } desugars to
do
x0 <- Just (getField @bar foo)
x1 <- getPartialField @baz x0
x2 <- Just (getField @quux x1)
Just (setField @bar (setField @baz (setField @quux x2 a) x1) x0)
-}
Another option would be to force records to live in one type only
record Foo = Bar { x :: Int, y :: Int } -- OK
record Foo = Bar { x :: Int, y :: Int } | Baz { z :: Int } -- error
to ensure no partial fields. But you still have problems
record Foo = Foo { x :: Int, y :: Int }
record Bar = Bar {x :: Int, y :: Int }
data Baz = B1 Foo | B2 Bar
baz.x -- error
baz.y -- error
-- you need to pattern match before you access it
-- a deeply nested Baz in a record breaks the streak of . overloads
All of these considerations makes you respect libraries more, huh?
Unfortunately implementing this interface can’t take full advantage of the desugaring provided for OverloadedRecordDot and OverloadedRecordUpdate and you need quasiquoters.
Might as well use optics. I do wonder how the generated core from a naive implementation would compare.
I butchered optics playing with it, and figured you could do this:
RecordUpdater.hs:
module RecordUpdater where
import Data.Functor.Identity
type RecordUpdater s t a b = (a -> Identity b) -> s -> Identity t
set' :: RecordUpdater s t a b -> (a -> b) -> s -> t
set' l f = runIdentity . l (Identity . f)
set :: RecordUpdater s t a b -> b -> s -> t
set l b = set' l (\_ -> b)
mkRecordUpdater :: (s -> a) -> (s -> b -> t) -> RecordUpdater s t a b
mkRecordUpdater sa sbt afb s = sbt s <$> afb (sa s)
Got a half baked van Laarhoven lens.
Main.hs:
data Foo a = Foo { fooName :: String, fooPoly :: a } deriving (Show)
fooName' = mkRecordUpdater fooName (\s b -> s { fooName = b })
fooPoly' = mkRecordUpdater fooPoly (\s b -> s { fooPoly = b })
main :: IO ()
main = do
let innerFoo = Foo { fooName = "I am inner foo.", fooPoly = "Stop here." }
let foo = Foo { fooName = "I am foo.", fooPoly = innerFoo }
print foo
let y = (fooName . fooPoly) foo
print y
let x = set (fooPoly' . fooName') "Updated name." foo
print x
So basically:
- I recycle the Haskell98 record getters.
- I make half baked lenses that are extremely easy to copy paste. Notice that the setters are half lenses and that the name is the getter with an apostrophe in the end. If you need to rename fields it’s as easy as replacing all instances with a text editor or IDE and the setter is done.
- No dependencies, generics or Template Haskell, this is as ergonomic as it gets.
Now all you need to do is avoid partial fields and separate one record per module if you want to duplicate names and you’re good to go. Better than HasField
since it can update your record from Foo a
to Foo b
. You can make a (&) = flip (.)
if you want to keep the same order composing getters and composing setters.
Mom, can we get lenses for deep nesting?
Mom: we can compose lenses at home.
Home:
data Foo a = Foo
{ fooName :: String
, fooPoly :: a
} deriving (Show)
fooName' s f = s { fooName = f (fooName s) }
fooPoly' s f = s { fooPoly = f (fooPoly s) }
(%) = flip flip
main = do
let foo3 = Foo { fooName = "foo3", fooPoly = 3 }
let foo2 = Foo { fooName = "foo2", fooPoly = foo3 }
let foo1 = Foo { fooName = "foo1", fooPoly = foo2 }
print $ fooName . fooPoly . fooPoly $ foo1
print $ const "New name" % fooName' % fooPoly' % fooPoly' $ foo1
Another low tech solution.