New notation for records?

  • Mom, can we add a dependency on lenses?
  • We have lenses at home.

Lenses at home:

{-# LANGUAGE AllowAmbiguousTypes, BlockArguments, DuplicateRecordFields, OverloadedLabels #-}

import Control.Monad.State (State, execState, modify)
import GHC.OverloadedLabels (IsLabel(..))
import GHC.Records (HasField(..))

setField :: HasField s a b => b -> a -> a
setField = error "wait for https://gitlab.haskell.org/ghc/ghc/-/issues/16232"

instance (HasField s a b, c ~ ()) => IsLabel s (State b () -> State a c) where
  fromLabel inner = modify (setField @s =<< execState inner . getField @s)

newtype Setter a b = Setter { (.=) :: b -> State a () }

instance HasField s a b => IsLabel s (Setter a b) where
  fromLabel = Setter (modify . setField @s)

(&~) :: a -> State a () -> a
(&~) = flip execState


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, empCar :: Car} deriving Show
data Car = Car {name :: String} deriving Show

f :: Integer -> Country -> Country
f i r =
  r &~ do
    #company do
        #boss do
            #age .= i
        #car do
            #name .= "new"
        #name .= "cmp"
    #name .= "ccc"

The deluxe version (requires 9.6+) even allows you to write:

  r &~ do
    #company do
        #"boss.age" .= i
        #"car.name" .= "new"
        #name .= "cmp"
    #name .= "ccc"

Of course, there is the minor downside that neither actually works yet, but at least there’s a plan for them to work at some point.

4 Likes