-- Use hmatrix and gnuplot bindings to plot unit dimensioned features. import Control.Monad import qualified Data.Array.Unboxed as A import Data.List import qualified Data.Packed.Matrix as G import qualified Data.Packed.Vector as G import qualified Graphics.Gnuplot.Simple as P import qualified Numeric.Container as G import qualified Sound.Analysis.Meapsoft as M import System.Environment normalize :: G.Vector Double -> G.Vector Double normalize v = let l = G.minElement v r = G.maxElement v d = r - l v' = G.addConstant (negate l) v in G.scale (recip d) v' fromArray :: A.UArray (Int, Int) Double -> G.Matrix Double fromArray m = (r G.>< c) (A.elems m) where ((r0,c0),(r1,c1)) = A.bounds m r = r1-r0+1 c = c1-c0+1 main :: IO () main = do a <- getArgs unless (length a > 1) (error ("feature-file feature ..\n" ++ show M.feature_names)) let (fn:ns) = a (Right mp) <- M.read_meap fn let fs = M.features mp uf = map (\n -> M.required_feature n fs) ("onset_time":ns) ar = M.uarray_data mp m = fromArray ar ufc = map M.feature_column uf vs = G.toRows (G.extractRows ufc (G.trans m)) vs' = map normalize vs (ot:ls) = map G.toList vs' ls' = map (zip ot) ls P.plotPaths [P.XLabel "onset_time", P.YLabel (intercalate "," ns)] ls'