Initialize a data type in (Writer (Endo a)) monoid

Hi. I have the following data type
import Data.Monoid import Control.Monad.Writer
data Graph = Graph {graphTitle :: String, graphPoints :: [Int]} deriving (Show) emptyGraph :: Graph emptyGraph = Graph {graphTitle = "", graphPoints = []}
Then i want to initialize it in Writer monad using (Dual (Endo Graph)) as monoid:
type GraphM t = WriterT (Dual (Endo Graph)) t
myGraph :: Monad t => GraphM t [Int] myGraph = do tell (setTitle "ab") tell (setTitle "ABCD") tell (modifyPoints (1 :)) tell (modifyPoints (2 :)) return [1, 2]
and then i can use it e.g. like
getGraph :: Monad t => (GraphM t a) -> t Graph getGraph m = do g <- execWriterT m return (appEndo (getDual g) emptyGraph)
printGraph :: IO () printGraph = getGraph myGraph >>= print
And to make this work i need two functions implemented for each record of Graph: get :: Graph -> a set :: a -> Graph -> Graph I can define per-record instances of them, like
setTitle :: String -> Dual (Endo Graph) setTitle x = Dual . Endo $ \g -> g{graphTitle = x}
modifyPoints :: ([Int] -> [Int]) -> Dual (Endo Graph) modifyPoints f = Dual . Endo $ \g -> let xs = graphPoints g in g{graphPoints = f xs}
but if Graph has many records, for most of them these 'set' functions ('get' functions i'll have from records) will look very similar. Is there a way how i can define all of them "in one row", i.e. using some generic 'set' implementation to which i should only pass e.g. record name or smth else? I.e. so, that above myGraph will look like .. tell(set r x) .. where r is record name (or smth else referencing particulat record) and x is value.

On Mon, Jan 13, 2014 at 09:54:55PM +0400, Dmitriy Matrosov wrote:
but if Graph has many records, for most of them these 'set' functions ('get' functions i'll have from records) will look very similar. Is there a way how i can define all of them "in one row", i.e. using some generic 'set' implementation to which i should only pass e.g. record name or smth else? I.e. so, that above myGraph will look like
.. tell(set r x) ..
Yes, you can do this with the 'lens' package. The package is big and complicated, but here's all you need to know: 0) import Control.Lens 1) Name your fields with underscores:
data Graph = Graph { _graphTitle :: String, _graphPoints :: [Int] } deriving (Show)
2) Add the line
$(makeLenses ''Graph)
after the definition of Graph (also be sure the TemplateHaskell extension is enabled) 3) Now you can use the 'view' and 'set' functions (or their infix equivalents, (^.) and (.~)), like so: .. tell (set graphTitle x) .. or tell (graphTitle .~ x) makeLenses generated a special lens called 'graphTitle' from the field name '_graphTitle'. Of course the above doesn't actually typecheck since (set graphTitle x) is a function but you need a Dual Endo, but you can easily make your own custom set function that adds the Dual Endo wrapper, etc. -Brent
participants (2)
-
Brent Yorgey
-
Dmitriy Matrosov