New notation for records?

Similar, using lenses, which will work today - Lenses with OverloadedRecordDot :slight_smile: With optics you can give every Optic a HasField fairly easily and avoid having the separate the thing, ironically bringing it back to how lens code looks (composition with .) at least for nested fields only.

1 Like

Trying to write my own implementation of

$(set ["countryCompany", "companyBoss", "employeeAge"]) i r

in Template Haskell to match

g r i = r { countryCompany = (countryCompany r) { companyBoss = (companyBoss (countryCompany r)) { employeeAge = i } } }

but I just straight up suck at it. :cry:

Why not use a notation, similar to elm? It is a lot more human readable and is roughly as powerful as our current system. And it probably would still keep the door open for extensible/… Records.

Maybe I am alone on this but I dislike the reliance on lenses, arcane syntax and/or another use of do-notation. Why not a simple {a | b = c}, meaning the record a, where the field b has the value c.

(I know, there is a problem around Haskell’s records having a constructor opposed to elm’s, but that is probably a solvable issue)

1 Like

In my opinion, once a typeclass like SetField exists, we should repurpose OverloadedRecordDot for setting, using techniques similar to the ones seen in this thread. I don’t think overloading existing setting syntax, or adding new baked-in syntax, would be necessary.

OP said they were familiar with OverloadedRecordUpdate, but for everyone else, the simple syntax r { foo.bar = 1 } is already reserved and ready to use with an implementation of setField (which you can provide manually or wait for GHC to supply).

The notation is already Elm like.

r { f = a, g = b }
--- vs
{ r | f = a, g = b }

What Elm has that Haskell (98) doesn’t is that it uses maps under the hood for record types and the fields are overloaded.

Elm has actually the same problem I’m bringing up. And they don’t have typeclasses or Template Elm. If they want to use elm-monocle they have to type the lens wiring by hand. The “official response” is that updating deeply nested records is an antipattern and all your data structures should be flat. Or hidden in modules with all the setter pipeline wiring hidden.

3 Likes

Yes I like elm’s notation. The difficulty introducing it into Haskell is backwards compatibility. Consider:

x = foo { a | b = c }
y = Bar { d | e = f }

For the first, the compiler seeing foo { ... } will think that’s a record update to value foo. For the second, the compiler seeing Bar { ... } will think that’s constructor Bar using record syntax – not Bar applied positionally to a single value, that happens to be a record update.

So the choice of notation will have to be module-wide and backwards-incompatible. All those Libraries (including Base/Prelude) will never change. So Haskellers will need to read both notations.

Btw, there is a dormant GHC proposal for introducing row types, but looks like there are some non-trivial unsolved questions because the author decided to turn it into a PhD thesis.

4 Likes

I got better.

Setter.hs:

{-# LANGUAGE TemplateHaskell #-}

module Setter where

import Language.Haskell.TH

set :: [Name] -> Q Exp
set names = return $ LamE [VarP a, VarP r] (go names (VarE r))
    where
        a = mkName "a"
        r = mkName "r"
        go ns acc = case ns of
            [n]    -> RecUpdE acc [(n, VarE a)]
            n : zs -> RecUpdE acc [(n, go zs (AppE (VarE n) acc))]
            _      -> error "no fields?"

And the example.

Main.hs:

{-# LANGUAGE TemplateHaskell #-}

import Setter

data Country = Country { countryName :: String, countryCompany :: Company } deriving (Show)
data Company = Company { companyName :: String, companyBoss :: Employee, companyCar :: Car } deriving (Show)
data Employee = Employee { employeeName :: String, employeeAge :: Integer, employeeCar :: Car } deriving (Show)
data Car = Car { carName :: String } deriving (Show)

example :: Integer -> Country -> Country
example i = $(set ['countryCompany, 'companyBoss, 'employeeAge]) i
          . $(set ['countryCompany, 'companyCar, 'carName]) "new"
          . $(set ['countryCompany, 'companyName]) "cmp"
          . $(set ['countryName]) "ccc"

main :: IO ()
main = do
    let car1 = Car { carName = "car1" }
    let car2 = Car { carName = "car2" }
    let boss = Employee { employeeName = "Carl", employeeAge = 30, employeeCar = car2 }
    let comp = Company { companyName = "Acme", companyBoss = boss, companyCar = car1 }
    let ctry = Country { countryName = "Scotland", countryCompany = comp }
    print ctry
    print $ example 420 ctry

Lenses at home.

Out of curiosity, if you’re already eating Template Haskell, what’s stopping you from using actual lenses?

Actually? Nothing, really.

Pros of lenses:

  • nuclear bomb solution
  • versatile, composable

Cons of lenses:

  • nuclear bomb solution, do you really need it?
  • 30 package dependency
  • pollutes the namespace with redundancy on the record accessors with lens counterpart, introduces lens types when initially you just had the record types and the accessors

Pros of my silly script:

  • uses the basics, Haskell98 compatible
  • you drop it off on a file and that’s it, it just works
  • only depends on template-haskell which comes with GHC out of the box, enable the extension and your script is good to go
  • doesn’t need AllowAmbiguousTypes, FunctionalDependencies, UndecidableInstances or others

Cons of my silly script:

  • generates boilerplate which may or may not be optimized to anything sensible
  • you can only set one thing at a time which generates even more boilerplate
  • reducing all the boilerplate introduces quasiquotation and you might as well write setters with the full record notation or use lenses if you’re going to bother with a parser
  • why not use vinyl or record?

I will keep it on a file of utils, for scripts.

See Optics.Generic and Optics.Label. lens isn’t the only library with a solution and this gets rid of (most of?) your cons.

1 Like

optics has an impressively small dependency graph. i think they all ship with ghc? de facto stdlib stuff

2 Likes

It is in fact a pretty nifty alternative to lens.

{-# LANGUAGE DuplicateRecordFields, TemplateHaskell, DataKinds, TypeFamilies, UndecidableInstances, OverloadedLabels #-}

import Optics
import Optics.TH

data Country = Country { name :: String, company :: Company } deriving (Show)
data Company = Company { name :: String, boss :: Employee, car :: Car } deriving (Show)
data Employee = Employee { name :: String, age :: Integer, car :: Car } deriving (Show)
data Car = Car { name :: String } deriving (Show)

makeFieldLabelsNoPrefix ''Country
makeFieldLabelsNoPrefix ''Company
makeFieldLabelsNoPrefix ''Employee
makeFieldLabelsNoPrefix ''Car

example :: Integer -> Country -> Country
example i = set (#company % #boss % #age) i
          . set (#company % #car % #name) "Batmobile"
          . set (#company % #name) "Aperture"
          . set (#name) "Canada"

main :: IO ()
main = do
    let car1 = Car { name = "car1" }
    let car2 = Car { name = "car2" }
    let boss = Employee { name = "Carl", age = 30, car = car2 }
    let comp = Company { name = "Acme", boss = boss, car = car1 }
    let ctry = Country { name = "Scotland", company = comp }
    print ctry
    print $ example 420 ctry

Makes replacing lenses easy and also quite as handy. You can choose Generics, TH, symbol spaghetti or lens like interface.

1 Like

For Template Haskell learning purposes I went and downloaded this and used Template Haskell to provide an overloading function to generate all the boilerplate for a record that wants to use OverloadedRecordUpdate.

Experimental.hs:

{-# LANGUAGE AllowAmbiguousTypes, FunctionalDependencies, TemplateHaskell #-}

module Experimental (
    HasField (..),
    getField,
    setField,
    overloadRecords
) where

import Language.Haskell.TH

class HasField x r a | x r -> a where
    -- | Function to get and set a field in a record.
    hasField :: r -> (a -> r, a)

getField :: forall x r a. (HasField x r a) => r -> a
getField = snd . hasField @x

setField :: forall x r a. (HasField x r a) => r -> a -> r
setField = fst . hasField @x

overloadRecords :: [Name] -> Q [Dec]
overloadRecords tNames = do
    foldr (\tName qDecs -> do
        nDecs <- overloadRecord tName
        pDecs <- qDecs
        return (pDecs ++ nDecs)) (return []) tNames

overloadRecord :: Name -> Q [Dec]
overloadRecord tName = do
    tDec <- getTypeDec
    dCons <- getDataCons tDec
    foldr (\a b -> do
        xd <- inst a (getCompleteType tDec) dCons
        xp <- b
        return (xd ++ xp)) (return []) (agroupFs (extractFs dCons) [])
    where
        getTypeDec = do
            i <- reify tName
            case i of
                TyConI d -> return d
                _        -> error $ "unsupported type " ++ show tName
        getDataCons td = case td of
            DataD _ _ _ _ cs _ -> return cs
            _                  -> error $ "no cons for " ++ show tName
        getCompleteType td = case td of
            DataD _ t ks _ _ _ -> mf (fmap kf ks) t
            _                  -> error $ "no kinds for " ++ show tName
            where
                kf (PlainTV n _) = n
                kf (KindedTV n _ _) = n
                mf ps t = case ps of
                    [x]    -> appT (conT t) (varT x)
                    x : xs -> appT (mf xs t) (varT x)
                    _      -> conT t
        extractFs rs = case rs of
            r : xs -> z r ++ extractFs xs
            _      -> []
            where
                z (RecC c fs) = fmap (\(n, _, t) -> (n, t, c)) fs
                z _           = []
        agroupFs xs acc = case xs of
            []             -> acc
            (n, t, c) : ys -> inc (\(n2, t2, c2) -> (n2, t2, c : c2)) (\(n2, _, _) -> n2 == n) (n, t, [c]) (agroupFs ys acc)
            where
                inc z h x zs = case span (not . h) zs of
                    (_, [])     -> x : zs
                    (a, b : bs) -> a ++ (z b : bs)
        inst (fieldName, fieldType, dataCons) fullT dCons =
            [d|
                instance HasField $(litT (strTyLit fieldStr)) $(fullT) $(return fieldType) where
                    hasField r = $(caseE [| r |] matches)
              |]
            where
                fieldStr = reverse . takeWhile (/= '.') . reverse . show $ fieldName
                o = "v"
                matches = fmap (\dcn -> let vats = fmap varP (mt dCons dcn)
                                            pats = conP dcn vats
                                            body = normalB [| (\x -> $(vt dCons dcn [| x |]), $(varE (mkName o))) |]
                                        in match pats body []) dataCons ++ [fin]
                    where
                        err = "No match in record selector " ++ fieldStr
                        fin = match wildP (normalB [| error $(litE (stringL err)) |]) []
                mt rs consName = case rs of
                    (RecC c fs) : xs -> if consName == c then p fs 0 else mt xs consName
                    _                -> []
                    where
                        p ((n, _, _) : js) num = (if n == fieldName then mkName o else mkName (o ++ show num)) : p js (num + 1)
                        p _ _                  = []
                vt rs consName xq = case rs of
                    (RecC c fs) : xs -> if consName == c then p (prep fs) else vt xs consName xq
                    _                -> conE consName
                    where
                        prep = reverse . zip [0..] . fmap (\(n, _, _) -> n)
                        p [] = conE consName
                        p ((i, x) : xs) = appE (p xs) (if x == fieldName then xq else varE (mkName (o ++ show i)))

{-
instance "name" Country String where
    hasField r = case r of
        Country v v1 -> (\x -> Country x v1, v)
        AlienCountry v v1 -> (\x -> Country x v1, v)
        _ -> error "no match"
-}

Main.hs:

{-# LANGUAGE DuplicateRecordFields, OverloadedRecordDot, OverloadedRecordUpdate, RebindableSyntax #-}
{-# LANGUAGE DataKinds, TemplateHaskell #-}

import Prelude
import Experimental

data Country a = Country { name :: String, company :: Company } | AlienCountry { name :: String, poly :: a } deriving (Show)
data Company = Company { name :: String, boss :: Employee, car :: Car } deriving (Show)
data Employee = Employee { name :: String, age :: Integer, car :: Car } deriving (Show)
data Car = Car { name :: String } deriving (Show)

overloadRecords [''Country, ''Company, ''Employee, ''Car]

main :: IO ()
main = do
    let car1 = Car { name = "car1" }
    let car2 = Car { name = "car2" }
    let boss = Employee { name = "Carl", age = 30, car = car2 }
    let comp = Company { name = "Acme", boss = boss, car = car1 }
    let ctry = Country { name = "Scotland", company = comp }
    print (ctry :: Country String)
    print $ ctry.company.boss.age
    let uc = ctry { company.boss.age = 420, company.boss.car.name = "new car" }
    print (uc :: Country String)
    let alien = AlienCountry { name = "Canada", poly = Company { name = "Alien Corp", boss = boss, car = car2 }}
    print alien
    print $ alien.poly.name
    let ac = alien { name = "Brazil", poly.boss.age = 999 }
    print ac

Only to realize I was using the old proposal and not the new one and I can’t just flip the types to finally see the “typechecked only” example work (because of ambiguous errors).

The good thing is that my example just works, like how original records do. Which is good… and bad. Good because it works, with the simple ergonomics that implies. Bad because there’s no type checking that the member you are calling is effectively part of the value (e.g asking for the company of AlienCountry is valid in old Haskell, valid here, and gives a runtime error if you do so).

Now I’m wondering how it would look like with optics.

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.

1 Like

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:

  1. I recycle the Haskell98 record getters.
  2. 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.
  3. 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.