<div dir="ltr">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.<div><br></div><div>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.</div><div><br></div><div>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.</div><div><br></div><div><div>import Control.Applicative</div><div>import Control.Monad.Trans.State.Strict</div><div>import Data.Monoid</div><div><br></div><div>import qualified Data.IntMap as M</div><div><br></div><div>newtype RowId a = RowId Int deriving (Eq)</div><div><br></div><div>data Classroom = Classroom { classroom_id :: RowId Classroom, classroom_extraFees :: Float, classroom_students :: [ RowId Student ] }</div><div>data Student = Student { student_id :: RowId Student, student_name::String, student_feesOwed::Float}</div><div><br></div><div>data Environment = Environment {</div><div>  environment_classroom :: Maybe Classroom,</div><div>  environment_students  :: M.IntMap Student</div><div>  }</div><div><br></div><div>student_totalFeesOwed :: RowId Student -> State Environment Float</div><div>student_totalFeesOwed (RowId studentId) = do</div><div>  (Environment mClassroom students) <- get</div><div>  case mClassroom of</div><div>    Nothing -> return 0.0</div><div>    Just classroom -> do</div><div>      let fees = student_feesOwed $ students M.! studentId</div><div>      return fees</div><div><br></div><div>student_addFee :: RowId Student -> Float -> State Environment ()</div><div>student_addFee studentId fee = do</div><div>  modify $ \e -> e { environment_students = M.map (addFee studentId fee) $ environment_students e }</div><div>  where</div><div>    addFee studentId fee student =</div><div>      if studentId == student_id student</div><div>      then student { student_feesOwed = student_feesOwed student + fee }</div><div>      else student</div><div><br></div><div>environment_addStudent :: Student -> State Environment ()</div><div>environment_addStudent student = do</div><div>  let (RowId key) = student_id student</div><div>      value = student</div><div>  modify $ \e -> e { environment_students = M.insert key value (environment_students e) }</div><div><br></div><div>classroom_addStudent :: Classroom -> RowId Student -> State Environment ()</div><div>classroom_addStudent classroom studentId = do</div><div>  modify $ \e -> e { environment_classroom = addStudent studentId <$> environment_classroom e }</div><div>  where</div><div>    addStudent :: RowId Student -> Classroom -> Classroom</div><div>    addStudent studentId classroom = classroom { classroom_students = studentId : (classroom_students classroom) }</div><div><br></div><div>student_registerClass :: RowId Student -> Classroom -> State Environment ()</div><div>student_registerClass studentId classroom = do</div><div>  student_addFee studentId (classroom_extraFees classroom)</div><div>  modify $ \e -> e { environment_classroom = Just classroom }</div><div>  classroom_addStudent classroom studentId</div><div>  </div><div>main = do</div><div>  let studentId = RowId 1</div><div>      student = Student studentId "Bob" 250.00</div><div>      classroom = Classroom (RowId 1) 500.00 []</div><div>      initialEnvironment = Environment Nothing mempty</div><div>  let totalFeesOwed = flip evalState initialEnvironment $ do</div><div>        environment_addStudent student</div><div>        student_registerClass studentId classroom</div><div>        totalFeesOwed <- student_totalFeesOwed studentId</div><div>        return totalFeesOwed</div><div>  putStrLn $ show totalFeesOwed</div></div><div><br></div></div><div class="gmail_extra"><br><div class="gmail_quote">On Tue, Jul 5, 2016 at 9:44 PM, Guru Devanla <span dir="ltr"><<a href="mailto:gurudev.devanla@gmail.com" target="_blank">gurudev.devanla@gmail.com</a>></span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex"><div dir="ltr"><div><div><div><div><div>Hi Michael,<br><br></div>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.<br><br></div>That said, I plan to try this approach and also see how I can enable this set up in my HUnit tests as well. <br><br></div>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!<br><br></div>Thanks<span class="HOEnZb"><font color="#888888"><br></font></span></div><span class="HOEnZb"><font color="#888888">Guru<br><div><div><div><div><br><br><br><br><br><div><br><br><br><br><br></div></div></div></div></div></font></span></div><div class="HOEnZb"><div class="h5"><div class="gmail_extra"><br><div class="gmail_quote">On Tue, Jul 5, 2016 at 7:18 PM, Michael Burge <span dir="ltr"><<a href="mailto:michaelburge@pobox.com" target="_blank">michaelburge@pobox.com</a>></span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex"><div dir="ltr"><div>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.</div><div><br></div><div>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).</div><div><br></div><div>Here's how I would start to structure your example in a larger project:</div><div><br></div><div>{-# LANGUAGE ImplicitParams,RankNTypes #-}</div><div><br></div><div>import qualified Data.IntMap as M</div><div><br></div><div>newtype RowId a = RowId Int</div><div><br></div><div>data Classroom = Classroom { classroom_id :: RowId Classroom, classroom_extraFees :: Float, classroom_students :: [ RowId Student ] }</div><div>data Student = Student { student_id :: RowId Student, student_name::String, student_feesOwed::Float}</div><div><br></div><div>data Environment = Environment {</div><div>  environment_classroom :: Classroom,</div><div>  environment_students  :: M.IntMap Student</div><div>  }</div><div><br></div><div>type Environmental a = (?e :: Environment) => a</div><div><br></div><div>classroom :: (?e :: Environment) => Classroom</div><div>classroom = environment_classroom ?e</div><div><br></div><div>students :: (?e :: Environment) => M.IntMap Student</div><div>students = environment_students ?e</div><div><br></div><div>student_totalFeesOwed :: RowId Student -> Environmental Float</div><div>student_totalFeesOwed (RowId studentId) = classroom_extraFees classroom + (student_feesOwed $ students M.! studentId)</div><div><br></div><div>main = do</div><div>  let student = Student (RowId 1) "Bob" 250.00</div><div>  let ?e = Environment {</div><div>        environment_classroom = Classroom (RowId 1) 500.00 [ RowId 1 ],</div><div>        environment_students = M.fromList [ (1, student) ]</div><div>        }</div><div>  putStrLn $ show $ student_totalFeesOwed $ RowId 1</div><div><br></div></div><div class="gmail_extra"><br><div class="gmail_quote"><div><div>On Tue, Jul 5, 2016 at 6:26 PM, Guru Devanla <span dir="ltr"><<a href="mailto:gurudev.devanla@gmail.com" target="_blank">gurudev.devanla@gmail.com</a>></span> wrote:<br></div></div><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex"><div><div><div dir="ltr"><div><div><div><div>Hello All,<br><br></div>I am just getting myself to code in Haskell and would like to design advice.  Below, I have a made up example:<br>                                                                                                                                                                                                                                                            <br>                                                                                                                                                                                                                                                                                  <br>data ClassRoom = ClassRoom { classRoomNo:: Integer, extra_fees::Float, students: Map StudentId Student}<br>data Student = Student {name::String, feesOwed::Float}<br>data StudentId = Integer                                                                                                                                                                                                                                                          <br>                                                                                                                                                                                                                                                                                  <br>get_fees_owed classroom student_id = extra_fees + feesOwed $ (students classroom) M.! studentid                                                                                                                                                                        <br><br>Here the `get_fees_owed`  needs information from the container 'classroom'.  <br><br></div><div>Here is my question/problem:<br>                                                                                                   <br></div><div>I believe I should model most of my code as expressions, rather than storing pre-computed values such as `fees_owed`.  But, <br>defining expressions involve passing the container objects all over. For example, deep down in a function that deals with just<br></div><div>one `student`, I might need the fees owed information. Without, having a reference to the container, I cannot call get_fees_owed.<br><br></div><div>Also, I think it hinders composing of functions that just deal with one student at a time, but end up with some dependency on<br></div><div>the container.<br><br></div>I have several questions related to this design hurdle, but I will start with the one above.<br><br></div>Thanks!<span><font color="#888888"><br></font></span></div><span><font color="#888888">Guru<br><br><div><div><div><div><br></div></div></div></div></font></span></div>
<br></div></div>_______________________________________________<br>
Haskell-Cafe mailing list<br>
To (un)subscribe, modify options or view archives go to:<br>
<a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe" rel="noreferrer" target="_blank">http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe</a><br>
Only members subscribed via the mailman list are allowed to post.<br></blockquote></div><br></div>
</blockquote></div><br></div>
</div></div></blockquote></div><br></div>