[Haskell-beginners] A better way to "integrate"

Giacomo Tesio giacomo at tesio.it
Wed May 21 20:03:01 UTC 2014


Actually I wonder why we don't have both Num and  Group, Ring, Field, etc...

With GeneralizedNewtypeDeriving it would be awesome!

Giacomo


On Wed, May 21, 2014 at 7:01 PM, David Thomas <davidleothomas at gmail.com>wrote:

> Yes, it "should" - in that it would be more expressive and allow types
> to catch more errors.  The current situation trades that away for
> reduced complexity.  Make whatever judgement call you want regarding
> whether that was appropriate.
>
> On Wed, May 21, 2014 at 9:57 AM, Dimitri DeFigueiredo
> <defigueiredo at ucdavis.edu> wrote:
> > Thanks, the realization that price, cost and volume are different
> quantities
> > is exactly what led me to play around with the Units library.
> >
> > I have a problem with Num. Shouldn't it be broken up into the
> fundamentals
> > of abstract algebra: Group, Ring, Field, etc? Just like is done for
> > Functors,
> > Applicative Functors, Monads, etc. It would avoid having the
> > typechecker allow me to multiply a Meter by Meter to get another Meter
> > (instead of the correct unit Meter^2).
> >
> > Cheers,
> >
> > Dimitri
> >
> >
> > Em 21/05/14 10:39, Brent Yorgey escreveu:
> >
> >> Others have given examples of implementing this using a fold.  I'd
> >> like to point out something else: by representing all these prices and
> >> volumes etc. as a bare numeric type, you are simply asking for
> >> trouble!  The reason is that it allows many nonsensical operations.
> >> For example, you could add a price and a volume.  Adding a price and a
> >> volume makes no sense, but if they are the same type then the compiler
> >> cannot help you catch such a silly mistake.
> >>
> >> I would do something like this:
> >>
> >>    {-# LANGUAGE GeneralizedNewtypeDeriving #-}
> >>
> >>    newtype Price = Price Double
> >>    -- you could also do  newtype Price a = Price a  if you want the
> >>    -- flexibility to be able to use any numeric type, though it's
> >>    probably not necessary.
> >>
> >>    newtype Volume = Volume Double
> >>      deriving Num
> >>    newtype Cost = Cost Double
> >>      deriving Num
> >>
> >> Notice I made a third type Cost, which is the result of multiplying a
> >> Price by a Volume.  If I understand the domain correctly, multiplying
> >> a Price by a Volume does not give you another Price (for example,
> >> would it make sense to multiply a Price by a Volume, and then take the
> >> result and multiply it by another Volume?).  A Price represents the
> >> value of a single share or unit of currency, whereas a Cost just
> >> represents some arbitrary amount of money.
> >>
> >> Now, what sorts of operations can one do on these types?  Notice I put
> >> "deriving Num" after Volume and Cost, which means that two Volumes can
> >> be added or subtracted to give another Volume, and similarly for Cost
> >> (unfortunately, it means they can also be multiplied, which is
> >> probably not sensible, but that's more a failing of the Num class
> >> which is not granular enough).  We also should implement
> >>
> >>    (.*) :: Price -> Volume -> Cost
> >>    Price p .* Volume v = Cost (p * v)
> >>
> >> And now you can implement essentially any of the suggested solutions,
> >> but with more descriptive types like
> >>
> >>    aggregate :: [(Price, Volume)] -> [(Cost, Volume)]
> >>
> >> and using (.*) in the key place instead of (*).  And now the type
> >> checker will make sure you don't do silly things like add a Price and
> >> a Volume, or multiply a Cost by a Price!  Hooray!
> >>
> >> -Brent
> >>
> >> On Tue, May 20, 2014 at 08:12:59PM -0600, Dimitri DeFigueiredo wrote:
> >>>
> >>> Awesome haskellers,
> >>>
> >>> I am coding up a little function that aggregates "ask orders" in a
> >>> currency exchange.
> >>> Another way to look at it, is that the function takes as input a
> >>> histogram or fdf (in list format) and outputs the cumulative
> >>> distribution cdf (also in list format). So we are kind of
> >>> "integrating" the input list.
> >>>
> >>> When given a list of asks in order of increasing price, the function
> >>> returns a list of points in the graph of the total supply curve.
> >>>
> >>> Here's an example:
> >>>
> >>> asks:                           returned list:
> >>>
> >>> [ (Price 42, Volume 0.5),      [ (Price 21,         Volume 0.5),
> >>>    (Price 50, Volume  1 ),        (Price 21+50=71,   Volume 1.5),
> >>>    (Price 55, Volume 0.2)]        (Price 21+50+11=82,Volume 1.7)]
> >>>
> >>> the returned list gives us the total supply curve (price = y-axis,
> >>> quantity/volume = x-axis, so the order is flipped)
> >>>
> >>> Summarizing
> >>>
> >>> * We're adding up the volumes. The last volume on the list is the
> >>> total volume available for sale.
> >>> * We calculate the total amount to be paid to buy the current volume
> >>> (for each item in the list).
> >>>
> >>> I have written up a simple function to do this:
> >>>
> >>> aggregate :: Num a => [(a,a)] -> [(a,a)]
> >>> aggregate xs = aggregate' 0 0 xs
> >>>
> >>> aggregate' :: Num a => a -> a -> [(a,a)] -> [(a,a)]
> >>> aggregate' _ _ [] = []
> >>> aggregate' accX accY ((x,y):ls) = let accX' = accX + x * y
> >>>                                        accY' = accY +     y
> >>>
> >>>                                        in  (accX',accY') : aggregate'
> >>> accX' accY' ls
> >>>
> >>>
> >>> main = print $ aggregate [(42,0.5),(50,1),(55,0.2)]
> >>>
> >>> However, this does not look very good to me and it feels like I'm
> >>> reinventing the wheel.
> >>>
> >>> Question: Is there a better Haskell way to do this? I'm really anal
> >>> about making it easy to read.
> >>>
> >>> Thanks!
> >>>
> >>> Dimitri
> >>> _______________________________________________
> >>> Beginners mailing list
> >>> Beginners at haskell.org
> >>> http://www.haskell.org/mailman/listinfo/beginners
> >>
> >> _______________________________________________
> >> Beginners mailing list
> >> Beginners at haskell.org
> >> http://www.haskell.org/mailman/listinfo/beginners
> >
> >
> > _______________________________________________
> > Beginners mailing list
> > Beginners at haskell.org
> > http://www.haskell.org/mailman/listinfo/beginners
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/beginners/attachments/20140521/eeac90e0/attachment.html>


More information about the Beginners mailing list