-- Copyright (C) 2007-2008 Stefan Kersten
-- 
-- This program is free software; you can redistribute it and/or modify
-- it under the terms of the GNU General Public License as published by
-- the Free Software Foundation; either version 2 of the License, or
-- (at your option) any later version.
-- 
-- This program is distributed in the hope that it will be useful,
-- but WITHOUT ANY WARRANTY; without even the implied warranty of
-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
-- GNU General Public License for more details.
-- 
-- You should have received a copy of the GNU General Public License
-- along with this program; if not, write to the Free Software
-- Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA

module Sound.SonicVisualiser.Types where

-- | A Sonic Visualiser document.
-- Documents contain `Model's with their corresponding `Data', `Layer's and
-- `Derivation's
data Document = Document {
    docModels       :: [Model],
    docLayers       :: [Layer],
    docDerivations  :: [Derivation]
} deriving (Show)

data ModelType =
    WaveFile
  | SparseMatrix
  deriving (Eq, Show)

type Frame = Integer
type FrameCount = Integer

-- | A Model describes a particular dataset in the Sonic Visualiser project
-- file.
data Model = Model {
    modelName :: String,
    modelType :: ModelType,
    modelSampleRate :: Double,
    modelStartFrame :: Frame,
    modelEndFrame :: Frame,
    modelData :: Data,
    modelDimensions :: Int,
    modelResolution :: Int,
    modelIsMain :: Bool
} deriving (Eq, Show)

-- | The Data container, either a file on disk or a sparse matrix (a list of
-- `Point's).
data Data =
    File String
  | DataSet [Point]
  deriving (Eq, Show)

-- | A Point specifies a coordinate in a time-series sparse matrix, with an
-- optional value and label.
data Point = Point {
    pointFrame :: Frame,
    pointValue :: Maybe Double,
    pointLabel :: Maybe String
} deriving (Eq, Show)

-- | A Layer defines the visual layout of a `Model'\'s data set.
data LayerType =
    WaveForm
  | TimeRuler
  | TimeInstants
  deriving (Eq, Show)

data Layer = Layer {
    layerName :: String,
    layerModel :: Model
} deriving (Show)

-- | A Derivation links a source `Model' with a `Model' derived by some kind of
-- analysis procedure.
data Derivation = Derivation {
    derivationSource        :: Model,
    derivationModel         :: Model,
    derivationChannel       :: Int,
    derivationDomain        :: Int,
    derivationStepSize      :: Int,
    derivationBlockSize     :: Int,
    derivationWindowType    :: Int,
    derivationTransform     :: String
} deriving (Show)

-- EOF