Skip to content

Instantly share code, notes, and snippets.

@JordanMartinez
Last active June 3, 2022 23:35
Show Gist options
  • Save JordanMartinez/93b0989e4b19af317e1b1b76cc605e50 to your computer and use it in GitHub Desktop.
Save JordanMartinez/93b0989e4b19af317e1b1b76cc605e50 to your computer and use it in GitHub Desktop.
Workaround to 3243
module Main where
import Prelude
import Effect (Effect)
import Effect.Console (log)
import Record.Unsafe (unsafeSet)
import Prim.Row (class Lacks)
import Data.Symbol (class IsSymbol, SProxy(..), reflectSymbol)
import Prim.Row as Row
import TryPureScript as TP
-- | If we define our own type class that is solved
-- | using a compiler-solved type class
class RowCons :: Symbol -> Type -> Row Type -> Row Type -> Constraint
class RowCons sym t r1 r2 | sym t r1 -> r2
instance (Row.Cons sym t r1 r2) => RowCons sym t r1 r2
-- | and update APIs to use the custom type class
-- | rather than the compiler one
insert
:: forall proxy r1 r2 l a
. IsSymbol l
=> Lacks l r1
=> RowCons l a r1 r2
=> proxy l
-> a
-> Record r1
-> Record r2
insert p val r = unsafeSet (reflectSymbol p) val r
-- | then something that didn't previously compile
-- | (see https://github.com/purescript/purescript/issues/3243#issuecomment-366184022)
addField ∷ ∀ r1 r2
. RowCons "field" Boolean r1 r2
=> Lacks "field" r1
=> Record r1
-> Record r2
addField r = insert (SProxy ∷ SProxy "field") true r
-- | now compiles
addField'
:: forall r1 r2 l
. IsSymbol l
=> Lacks l r1
=> RowCons l Boolean r1 r2
=> SProxy l
-> Record r1
-> Record r2
addField' l r = insert l true r
-- | and can be used
main :: Effect Unit
main = TP.render =<< TP.withConsole do
log $ show $ addField { foo: true }
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment