[Haskell-cafe] Haskell Data Structure design

Michael Burge michaelburge at pobox.com
Wed Jul 6 02:18:28 UTC 2016


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/20160705/2619cd72/attachment.html>


More information about the Haskell-Cafe mailing list