[Haskell] 2-D Plots, graphical representation of massive data

Frédéric Nicolier f.nicolier at iut-troyes.univ-reims.fr
Sun Aug 29 12:02:45 EDT 2004


I have done some code in order to interface haskell and octave. It is
actually very simple, but it works.
The communication between octave and haskell is done via files. I'm
planning to change this and use sockets.
This file belongs to my project : use haskell for image/signal
procesing algorithms.

For my opinion, people (in image processing reseach) uses
matlab/octave because it allow bad programmers to test new algorithms
very easy. Haskell can do better  in this task.

Fred

\begin{code}
-----------------------------------------------------------------------------
-- |
-- Module      :  HipsExternal
-- Copyright   :  (c) Fred Nicolier 2004
-- License     :  GPL
--
-- Maintainer  :  Fred Nicolier
-- Stability   :  experimental
-- Portability :  portable
-- 
-- Links to external computation engine (octave)
--
-- Examples:
--
-- >myCos :: Num a => a -> Double
-- >myCos x =  head.head.octaveFunc $ ["a=" ++ show x,
-- >                                   "export(cos(a))"]
-- >
-- >doubleOct :: Num a => [a] -> [Double]
-- >doubleOct list = head.octaveFunc $ ["a=" ++ show list,
-- >                                    "export(2*a)"]
-- 
-- >fftOct list
-- >    = octaveFunc ["s=" ++ show list,
-- >                  "f=fft(s)",
-- >                  "export(real(f),imag(f))"]
-----------------------------------------------------------------------------

module HipsExternal (octaveExec,
                     octaveSend,
                     octaveFunc
                     ) where

import System
import IO
import System.IO.Unsafe

-- ---------------------------------------------------------
-- ---------------------------------------------------------

octaveExec :: [String] -> IO String
octaveExec cmds =
    do
    system ("./octaveshell \"" ++ cmd ++ "\"")
    readFile "export.dat"
        where cmd = foldr insertSep "" cmds
              insertSep a b = a ++ ";" ++ b

octaveSend :: [String] -> IO ExitCode
octaveSend cmds =
    do
    system ("./octaveshell \"" ++ cmd ++ "\" &")
        where cmd = foldr insertSep "" cmds
              insertSep a b = a ++ ";" ++ b

octaveFunc :: [String] -> [[Double]]
octaveFunc = (map $ (map read).words).lines.unsafePerformIO.octaveExec

\end{code}

octaveshell is just a excutable file containing :

\begin{code}
#!/bin/sh
echo "$*" | octave -qf
\end{code}

Fred Nicolier


-------------------------------------------------
This mail sent through IMP: http://horde.org/imp/


More information about the Haskell mailing list