Question

1) I need to pass a field constructor parameter to a function. I made some tests but i was unable to do so. Is it possible? Otherwise, is it possible with lens package?

2) Is it possible in a MonadState to modify a field using modify? (I made a few attempts, but without success. For example: modify (second = "x") does not work.

import Control.Monad.State

data Test = Test {first :: Int, second :: String} deriving Show

dataTest = Test  {first = 1, second = ""}

test1 = runStateT modif1 dataTest -- OK

test2 = runStateT (modif2 "!") dataTest -- OK

test3 = runStateT (modif3 second) dataTest -- WRONG


-- modif1 :: StateT Test IO ()
modif1 = do
  st <- get
  r <- lift getLine
  put $ st {second = "x" ++ r} 


-- modif2 :: String -> StateT Test IO ()
modif2 s = do
  stat <- get
  r <- lift getLine
  put $  stat {second = "x" ++ r ++ s}

-- modif3 :: ???? -> StateT Test IO ()
modif3 fc = do
  stat <- get
  r <- lift getLine
  put $  stat {fc = "x" ++ r}

-- When i try to load the module, this is the result:
-- ghc > Failed:
--  ProvaRecord.hs:33:16:`fc' is not a (visible) constructor field name
Was it helpful?

Solution

As you said, you're probably looking for lenses. A lens is a value that allows to read, set or modify a given field. Usually with Control.Lens, you define fields with underscores and you use makeLenses to create full-featured lenses.

There are many combinators that allow lenses to be used together within MonadState. In your case we can use %=, which in this case would be specialized to type

(MonadState s m) => Lens' s b -> (b -> b) -> m ()

which modifies a state value using a given lens and a function that operates on the inside value.

Your example could be rewritten using lenses as follows:

{-# LANGUAGE TemplateHaskell, RankNTypes #-}
import Control.Lens
import Control.Monad.State

data Test = Test { _first :: Int
                 , _second :: String
                 }
    deriving Show

-- Generate `first` and `second` lenses.
$(makeLenses ''Test)

-- | An example of a universal function that modifies any lens.
-- It reads a string and appends it to the existing value.
modif :: Lens' a String -> StateT a IO ()
modif l = do
    r <- lift getLine
    l %= (++ r)


dataTest :: Test
dataTest = Test  { _first = 1, _second = "" }

test :: IO Test
test = execStateT (modif second) dataTest
Licensed under: CC-BY-SA with attribution
Not affiliated with StackOverflow
scroll top