{-# LANGUAGE TemplateHaskell,TypeSynonymInstances,FlexibleInstances,MultiParamTypeClasses #-} import Control.Lens import Data.Existential newtype MyType = MyType { _myTypeCell :: Cell MyClass } class (Eq a, Show a) => MyClass a where makeFields ''MyType -- makeFields create an Iso' MyType (Cell Eq) called cell, -- i.e. MyType is made into an instance of HasCell. instance Eq MyType where (==) = cellEqual' (==) instance Show MyType where show = ("MyType " ++) . readCell' show instance MyClass Int where instance MyClass Char where instance MyClass a => MyClass [a] where main :: IO () main = do let xs = [makeCell (7 :: Int),makeCell "hello",makeCell [1,2,3::Int]] xs :: [MyType] print $ xs == xs -- prints True let ys = xs & traverse._Cell' .~ (8 :: Int) ys' = replicate 3 $ makeCell (8 :: Int) zs = [makeCell (8 :: Int),makeCell "hello",makeCell [1,2,3::Int]] zs :: [MyType] zs' = xs & traverse .~ makeCell (8 :: Int) zs' :: [MyType] zs'' = xs & traverse %~ readCell' (makeCell . show) zs'' :: [MyType] print $ xs == ys -- prints False print $ ys == ys' -- prints False print $ zs == ys -- prints True print $ zs' == ys' -- prints True print zs -- prints [MyType 8,MyType "hello",MyType [1,2,3]] print zs' -- prints [MyType 8,MyType 8,MyType 8] print zs'' -- prints [MyType "7",MyType "\"hello\"",MyType "[1,2,3]"]