[Haskell-cafe] Automatic differentiation and dimension types

adam vogt vogt.adam at gmail.com
Sat Jan 18 08:57:39 UTC 2014


Hi Douglas,

Looks like it's pretty straightforward to use the "dimensional" and
"ad" packages together:

{-# LANGUAGE RankNTypes #-}
import qualified Numeric.AD as AD
import qualified Numeric.AD.Types as AD
import Numeric.Units.Dimensional.Prelude
import Numeric.Units.Dimensional
import qualified Prelude as P

diff :: (Div y x y', Num a) =>
        (forall s. AD.Mode s => Dimensional v x (AD.AD s a)
                             -> Dimensional v y (AD.AD s a))
        -> Dimensional v x a -> Dimensional v y' a
diff f z = Dimensional $ AD.diff (unD . f . Dimensional) (unD z)
unD (Dimensional a) = a

-- a dumb example
ke velocity = velocity*velocity*(1*~kilo gram)
main = print $ diff ke (3 *~ (metre/second))
-- prints 6.0 m kg s^-1

It might be nice to have a package that wraps up the rest of the
functionality in "ad" (gradients, the different modes etc.). I'm not
sure there are convenient vectors/matrices that can have each element
with a different type (units).

Regards,
Adam

On Fri, Jan 17, 2014 at 4:23 PM, Douglas McClean
<douglas.mcclean at gmail.com> wrote:
> Has anyone explored the intersection between automatic differentiation and
> dimension types (like those in the dimensional package or along the lines of
> any of the approaches discussed at
> http://www.haskell.org/haskellwiki/Physical_units)?
>
> It's tricky because for ordinary automatic differentiation the types are all
> the same, but when dimensions get involved that isn't the case, you have to
> keep dividing by the dimension of the infinitesimal.
>
> -Doug McClean
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list