[R-SIG-Mac] R and Haskell (Having My Cake...)
Dominic Steinitz
dominic at steinitz.org
Mon Oct 12 13:54:25 CEST 2015
All,
As someone who uses both R and Haskell and a Mac in my day job, I am very excited by the news that this now works on Macs.
> http://tweag.github.io/HaskellR/ <http://tweag.github.io/HaskellR/>
For example, if I want to use Nelder-Mead in Haskell then all I have to do is the code below most of which is boilerplate and took me about 20 minutes. Plotting is also supported although I tend to use the the native Haskell charts package most of the time.
Oh and the answer is
> (505.0,1.000035627670639,-6.432963549964604e-4,2.105887833352907e-6,69,0)
Not bad but not brilliant but it is Nelder-Mead after all.
> {-# LANGUAGE QuasiQuotes #-}
>
> import H.Prelude as H
> import Language.R.QQ
>
> import qualified Foreign.R as R
> import qualified Foreign.R.Type as R
>
> import Data.Int
> import Control.DeepSeq
>
> xs, ys :: [Double]
> xs = [1.0..10.0]
> ys = [1.0..10.0]
>
> cost :: Double -> Double -> Double
> cost m c =
> sum $
> map (^2) $
> zipWith (-) (map (\x -> m * x + c) xs) ys
>
> nmMin :: IO (Double, Double, Double, Double, Int32, Int32)
> nmMin = runRegion $ do
> initParms <- [r| c(2.0,1.0) |]
> initVal <- H.fromSEXP . R.cast R.SReal <$>
> [r| (function(v) costH_hs(v[1], v[2])) (initParms_hs) |]
> relaxMin <- [r| optimx(c(2.0,1.0), function(v) costH_hs(v[1], v[2]), method = "Nelder-Mead") |]
> mMin <- H.fromSEXP . R.cast R.SReal <$> [r| relaxMin_hs$p1 |]
> cMin <- H.fromSEXP . R.cast R.SReal <$> [r| relaxMin_hs$p2 |]
> vMin <- H.fromSEXP . R.cast R.SReal <$> [r| relaxMin_hs$value |]
> fEvals <- H.fromSEXP . R.cast R.SInt <$> [r| as.integer(relaxMin_hs$fevals) |]
> convCode <- H.fromSEXP . R.cast R.SInt <$> [r| as.integer(relaxMin_hs$convcode) |]
> return $!! (initVal, mMin, cMin, vMin, fEvals, convCode)
> where
> costH :: Double -> Double -> R s Double
> costH m c = return $ cost m c
>
> main :: IO ()
> main =
> withEmbeddedR defaultConfig $ do
> runRegion $ do
> _ <- [r| install.packages(c("numDeriv", "optimx"), repos = "http://cran.us.r-project.org") |]
> _ <- [r| library('numDeriv') |]
> _ <- [r| library('optimx') |]
> return ()
> results <- nmMin
> putStrLn $ Prelude.show results
Dominic Steinitz
dominic at steinitz.org
http://idontgetoutmuch.wordpress.com
[[alternative HTML version deleted]]
More information about the R-SIG-Mac
mailing list