yilmazhuseyin
yilmazhuseyin

Reputation: 6612

Polymorphic lens without template haskell

I am trying to create a polymorphic lens decleration (without template haskell) for multiple types.

module Sample where
import Control.Lens
data A = A {_value:: Int}
data B = B {_value:: Int}
data C = C {_value:: String}
value = lens _value (\i x -> i{_value=x}) -- <<< ERROR

But I get following error:

Ambiguous occurrence ‘_value’
It could refer to either the field ‘_value’,
                         defined at library/Sample.hs:5:13
                      or the field ‘_value’, defined at 
library/Sample.hs:4:13
                      or the field ‘_value’, defined at 
library/Sample.hs:3:13
  |
6 | value = lens _value (\i x -> i{_value=x}) -- <<< ERROR
  |              ^^^^^^

So, goal is to have value lens to work on all three types A, B and C. Is there a way to achieve that? Thanks.

Upvotes: 4

Views: 613

Answers (3)

MCH
MCH

Reputation: 2214

If you want to avoid DuplicateRecordFields, another option is to define everything in its own module, though this will require qualified imports for them to be imported into the same module.

module Sample.A where
import Control.Lens
data A = A {_value:: Int}
value = lens _value (\i x -> i{_value=x})

module Sample.B where
import Control.Lens
data B = B {_value:: Int}
value = lens _value (\i x -> i{_value=x})

module Sample.C where
import Control.Lens
data C = C {_value:: String}
value = lens _value (\i x -> i{_value=x})

module Main where
import qualified Sample.A as A
import qualified Sample.B as B
import qualified Sample.C as C

main :: IO ()
main = print (A.A 0 ^. A.value, B.B 0 ^. B.value, C.C "0" ^. C.value)

Upvotes: 0

Li-yao Xia
Li-yao Xia

Reputation: 33519

Lenses can be derived without TH by generic-lens. You can specialize the generic field lens to a specific field and give it a name as follows.

{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeApplications #-}

import GHC.Generics (Generic)
import Control.Lens (Lens, (^.))
import Data.Generics.Product (HasField(field))

data A = A { _value :: Int } deriving Generic
data B = B { _value :: Int } deriving Generic
data C = C { _value :: String } deriving Generic

value :: HasField "_value" s t a b => Lens s t a b
value = field @"_value"

main :: IO ()
main = print (A 0 ^. value, B 0 ^. value, C "0" ^. value)

Upvotes: 10

Alexander Wittmond
Alexander Wittmond

Reputation: 213

Haskell does not support overloading functions the way a language like Java or C++ does. To do what you want you need to use a typeclass like so.

class HasValue a b where
    value :: Lens' a b 

data A = A {_valueA:: Int}
data B = B {_valueB:: Int}
data C = C {_valueC:: String}

instance HasValue A Int where
   value = lens _valueA (\i x -> i{_valueA=x})

instance HasValue B Int where
   value = lens _valueB (\i x -> i{_valueB=x})

instance HasValue C String where
   value = lens _valueC (\i x -> i{_valueC=x}

You'll need to enable multiparameter typeclasses to do this.

Upvotes: 4

Related Questions