Skip to content

Instantly share code, notes, and snippets.

@tbidne
Created October 7, 2022 02:07
Show Gist options
  • Save tbidne/7a4884bbb08fa56380c70d4adc8104b9 to your computer and use it in GitHub Desktop.
Save tbidne/7a4884bbb08fa56380c70d4adc8104b9 to your computer and use it in GitHub Desktop.
Optics type inference example
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
module Optics.Inference where
import Optics.Core (A_Lens, LabelOptic (labelOptic), lens, set)
data Foo = MkFoo {foo1 :: String, foo2 :: ()}
deriving (Show)
-- The recommended definition, per
-- https://hackage.haskell.org/package/optics-core-0.4.1/docs/Optics-Label.html#g:8
instance (k ~ A_Lens, a ~ String, b ~ String) => LabelOptic "foo1" k Foo Foo a b where
labelOptic = lens (\(MkFoo x _) -> x) (\(MkFoo _ y) x -> MkFoo x y)
data Bar = MkBar {bar1 :: String, bar2 :: ()}
-- Q: What happens if we use a single alias?
instance (k ~ A_Lens, a ~ String) => LabelOptic "bar1" k Bar Bar a a where
labelOptic = lens (\(MkBar x _) -> x) (\(MkBar _ y) x -> MkBar x y)
foo :: Foo
foo = MkFoo "foo" ()
-- No problems here...
-- >>> foo1set
-- MkFoo {foo1 = "new", foo2 = ()}
foo1set :: Foo
foo1set = set #foo1 "new" foo
bar :: Bar
bar = MkBar "bar" ()
-- A: fails to compile!
--
-- • Overlapping instances for Is k0 A_Setter
-- arising from a use of ‘set’
-- Matching instances:
-- instance [overlappable] (TypeError ...) => Is k l
-- -- Defined in ‘Optics.Internal.Optic.Subtyping’
-- instance Is k k -- Defined in ‘Optics.Internal.Optic.Subtyping’
-- instance Is A_Lens A_Setter
-- -- Defined in ‘Optics.Internal.Optic.Subtyping’
-- ...plus four others
-- (use -fprint-potential-instances to see them all)
-- (The choice depends on the instantiation of ‘k0’
-- To pick the first instance above, use IncoherentInstances
-- when compiling the other instance declarations)
-- • In the expression: set #bar1 "new" bar
-- In an equation for ‘bar1set’: bar1set = set #bar1 "new" bartypecheck(-Wdeferred-type-errors)
bar1set :: Bar
bar1set = set #bar1 "new" bar
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment