[Haskell-cafe] Haskell Data Structure design
Guru Devanla
gurudev.devanla at gmail.com
Sat Jul 9 01:57:26 UTC 2016
Hi Michael,
I have been taking this approach of State Monads and I have hit upon 3
common patterns that I think may not be the idiomatic way of dealing with
state. I would like to continue with the example we have to explain those
scenarios. Any input on this would be great..
1. I see that almost in every function I deal with state, I have e <- get
, expression in the begining. I always ending up having to use the state to
query for different values. I guess this is OK.
2. In deeply nested function, where I pass state, I also end up calling
evalState a couple of times to get to some values. Is that common. Here is
one example, from our toy problem.
first_student_owes_more :: RowId Student -> RowId Student -> State
Environment Bool
first_student_owes_more student_1 student_2 = do
e <- get
let fees_owed_by_student_1 = evalState (student_totalFeesOwed student_1)
$ e
let fees_owed_by_student_2 = evalState (student_totalFeesOwed student_2)
$ e
return $ fees_owed_by_student_1 > fees_owed_by_student_2
You see, I have to evalState twice to get to what I want. Is that a common
way to use the State.
3. I also end up performing evalState while mapping over a list of values.
Say, I wanted to loop around a list of students to perform the function in
(2), then invariable for each iteration of Map, I am calling evalState once.
This gets hairy, if the value in my State is a Data.Map structure.
Am I using the State Monad in a round about way?
Thanks
Guru
On Wed, Jul 6, 2016 at 8:39 PM, Guru Devanla <gurudev.devanla at gmail.com>
wrote:
> The State monad makes a lot of sense for this. I was initially hesitant to
> go down this path *fearing* monads. But, today I was able to change most of
> my code to work with the same pattern you provided. Also, my initial
> impression on State monads was that, it was not a good idea to carry a *big
> blob* of State around. That impression comes from the thought process
> influenced by imperative programming. After coding up this, it is a lot
> clear that State monad declares operations and it is not the `state` itself
> that is carried around. I am elated!
>
> Thank you for the help. I may have more questions as I progress down this
> path.
>
> Thanks
> Guru
>
>
> On Tue, Jul 5, 2016 at 10:30 PM, Michael Burge <michaelburge at pobox.com>
> wrote:
>
>> The implicit parameter approach is best if the environment never changes,
>> or at least doesn't change during the computation You can rebind the
>> variable in the middle of a computation, but it's not a good road to go
>> down.
>>
>> The easiest way to simulate a changing environment is to use the State
>> monad. There are other techniques: lenses, nested patterns, rebinding an
>> implicit parameter, ST monad, generating a list of changes and applying the
>> changes to the original state, etc. But - despite having to change your
>> syntax somewhat - I think you'll find it easiest to use a state monad to
>> manage this.
>>
>> Here's a somewhat verbose example of using State to track updates. You
>> can make it less verbose, but I chose to keep it simple. In this example,
>> it updates student_feesOwed as part of registering for a class. So we no
>> longer need to calculate anything: It just grabs the value off of the
>> Student.
>>
>> import Control.Applicative
>> import Control.Monad.Trans.State.Strict
>> import Data.Monoid
>>
>> import qualified Data.IntMap as M
>>
>> newtype RowId a = RowId Int deriving (Eq)
>>
>> data Classroom = Classroom { classroom_id :: RowId Classroom,
>> classroom_extraFees :: Float, classroom_students :: [ RowId Student ] }
>> data Student = Student { student_id :: RowId Student,
>> student_name::String, student_feesOwed::Float}
>>
>> data Environment = Environment {
>> environment_classroom :: Maybe Classroom,
>> environment_students :: M.IntMap Student
>> }
>>
>> student_totalFeesOwed :: RowId Student -> State Environment Float
>> student_totalFeesOwed (RowId studentId) = do
>> (Environment mClassroom students) <- get
>> case mClassroom of
>> Nothing -> return 0.0
>> Just classroom -> do
>> let fees = student_feesOwed $ students M.! studentId
>> return fees
>>
>> student_addFee :: RowId Student -> Float -> State Environment ()
>> student_addFee studentId fee = do
>> modify $ \e -> e { environment_students = M.map (addFee studentId fee)
>> $ environment_students e }
>> where
>> addFee studentId fee student =
>> if studentId == student_id student
>> then student { student_feesOwed = student_feesOwed student + fee }
>> else student
>>
>> environment_addStudent :: Student -> State Environment ()
>> environment_addStudent student = do
>> let (RowId key) = student_id student
>> value = student
>> modify $ \e -> e { environment_students = M.insert key value
>> (environment_students e) }
>>
>> classroom_addStudent :: Classroom -> RowId Student -> State Environment ()
>> classroom_addStudent classroom studentId = do
>> modify $ \e -> e { environment_classroom = addStudent studentId <$>
>> environment_classroom e }
>> where
>> addStudent :: RowId Student -> Classroom -> Classroom
>> addStudent studentId classroom = classroom { classroom_students =
>> studentId : (classroom_students classroom) }
>>
>> student_registerClass :: RowId Student -> Classroom -> State Environment
>> ()
>> student_registerClass studentId classroom = do
>> student_addFee studentId (classroom_extraFees classroom)
>> modify $ \e -> e { environment_classroom = Just classroom }
>> classroom_addStudent classroom studentId
>>
>> main = do
>> let studentId = RowId 1
>> student = Student studentId "Bob" 250.00
>> classroom = Classroom (RowId 1) 500.00 []
>> initialEnvironment = Environment Nothing mempty
>> let totalFeesOwed = flip evalState initialEnvironment $ do
>> environment_addStudent student
>> student_registerClass studentId classroom
>> totalFeesOwed <- student_totalFeesOwed studentId
>> return totalFeesOwed
>> putStrLn $ show totalFeesOwed
>>
>>
>> On Tue, Jul 5, 2016 at 9:44 PM, Guru Devanla <gurudev.devanla at gmail.com>
>> wrote:
>>
>>> Hi Michael,
>>>
>>> That is excellent. I read about Implicit parameters after reading your
>>> post. I like this approach better than Reader monad for my current use
>>> case. I wanted to stay away from Reader Monad given that this is my first
>>> experimental project and dealing with Reader Monads into levels of nested
>>> function calls involved lot more head-ache for me.
>>>
>>> That said, I plan to try this approach and also see how I can enable
>>> this set up in my HUnit tests as well.
>>>
>>> One other question, I have regarding this design is as follows: Say,
>>> during the progress of the computation, the `student_feesOwed` changes, and
>>> therefore we have a new instance of classroom with new instance of student
>>> in it (with the updated feesOwed). I am guessing, this would mean, wrapping
>>> up this new instance into the environment from there on and calling the
>>> subsequent functions. Is that assumption, right. Nevertheless, I will play
>>> with approach tomorrow and report back!
>>>
>>> Thanks
>>> Guru
>>>
>>>
>>>
>>>
>>>
>>>
>>>
>>>
>>>
>>>
>>>
>>> On Tue, Jul 5, 2016 at 7:18 PM, Michael Burge <michaelburge at pobox.com>
>>> wrote:
>>>
>>>> When I have functions that are pure but depend on some common state(say
>>>> in a config file, or retrieved from a database at startup), I like to use
>>>> implicit parameters to hide it. You can use a type alias to avoid it
>>>> cluttering up most signatures. Below, a value of type 'Environmental Float'
>>>> means 'A float value, dependent on some fixed environment containing all
>>>> students and the single unique classroom'. If you have a deep chain of
>>>> 'Environmental a' values, the implicit parameter will be automatically
>>>> propagated to the deepest parts of the expression.
>>>>
>>>> You could also use a Reader monad, but they seem to require more
>>>> invasive syntactic changes: They are better if you later expect to need
>>>> other monads like IO, but if you're just doing calculations they're
>>>> overkill. You could also define a type alias 'Environmental a = Environment
>>>> -> a', but then if you have multiple such states they don't compose
>>>> well(they require you to apply the implicit state in the correct order, and
>>>> it can be a little awkward to propagate the parameter).
>>>>
>>>> Here's how I would start to structure your example in a larger project:
>>>>
>>>> {-# LANGUAGE ImplicitParams,RankNTypes #-}
>>>>
>>>> import qualified Data.IntMap as M
>>>>
>>>> newtype RowId a = RowId Int
>>>>
>>>> data Classroom = Classroom { classroom_id :: RowId Classroom,
>>>> classroom_extraFees :: Float, classroom_students :: [ RowId Student ] }
>>>> data Student = Student { student_id :: RowId Student,
>>>> student_name::String, student_feesOwed::Float}
>>>>
>>>> data Environment = Environment {
>>>> environment_classroom :: Classroom,
>>>> environment_students :: M.IntMap Student
>>>> }
>>>>
>>>> type Environmental a = (?e :: Environment) => a
>>>>
>>>> classroom :: (?e :: Environment) => Classroom
>>>> classroom = environment_classroom ?e
>>>>
>>>> students :: (?e :: Environment) => M.IntMap Student
>>>> students = environment_students ?e
>>>>
>>>> student_totalFeesOwed :: RowId Student -> Environmental Float
>>>> student_totalFeesOwed (RowId studentId) = classroom_extraFees classroom
>>>> + (student_feesOwed $ students M.! studentId)
>>>>
>>>> main = do
>>>> let student = Student (RowId 1) "Bob" 250.00
>>>> let ?e = Environment {
>>>> environment_classroom = Classroom (RowId 1) 500.00 [ RowId 1 ],
>>>> environment_students = M.fromList [ (1, student) ]
>>>> }
>>>> putStrLn $ show $ student_totalFeesOwed $ RowId 1
>>>>
>>>>
>>>> On Tue, Jul 5, 2016 at 6:26 PM, Guru Devanla <gurudev.devanla at gmail.com
>>>> > wrote:
>>>>
>>>>> Hello All,
>>>>>
>>>>> I am just getting myself to code in Haskell and would like to design
>>>>> advice. Below, I have a made up example:
>>>>>
>>>>>
>>>>>
>>>>>
>>>>> data ClassRoom = ClassRoom { classRoomNo:: Integer, extra_fees::Float,
>>>>> students: Map StudentId Student}
>>>>> data Student = Student {name::String, feesOwed::Float}
>>>>> data StudentId =
>>>>> Integer
>>>>>
>>>>>
>>>>>
>>>>> get_fees_owed classroom student_id = extra_fees + feesOwed $ (students
>>>>> classroom) M.! studentid
>>>>>
>>>>>
>>>>>
>>>>> Here the `get_fees_owed` needs information from the container
>>>>> 'classroom'.
>>>>>
>>>>> Here is my question/problem:
>>>>>
>>>>>
>>>>> I believe I should model most of my code as expressions, rather than
>>>>> storing pre-computed values such as `fees_owed`. But,
>>>>> defining expressions involve passing the container objects all over.
>>>>> For example, deep down in a function that deals with just
>>>>> one `student`, I might need the fees owed information. Without, having
>>>>> a reference to the container, I cannot call get_fees_owed.
>>>>>
>>>>> Also, I think it hinders composing of functions that just deal with
>>>>> one student at a time, but end up with some dependency on
>>>>> the container.
>>>>>
>>>>> I have several questions related to this design hurdle, but I will
>>>>> start with the one above.
>>>>>
>>>>> Thanks!
>>>>> Guru
>>>>>
>>>>>
>>>>>
>>>>> _______________________________________________
>>>>> Haskell-Cafe mailing list
>>>>> To (un)subscribe, modify options or view archives go to:
>>>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>>>>> Only members subscribed via the mailman list are allowed to post.
>>>>>
>>>>
>>>>
>>>
>>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20160708/8df987dd/attachment.html>
More information about the Haskell-Cafe
mailing list