
Look into Oleg's HList (heterogeneous list) and OOHaskell
http://homepages.cwi.nl/~ralf/HList/
http://homepages.cwi.nl/~ralf/OOHaskell/
On Thu, Jun 16, 2011 at 5:08 AM, kaffeepause73
Dear all,
I'm created a timeSignal datatype as container around a "Vector Double" data type (see simple code below) and subsequently started to instanciate Num & Eq to be able to perform operations on it. Additionally I want store ifno like an index, time information and eventually an inheritence log (the log is not yet in there).
As I will in the end need up to 10 different datatypes, however using slightly different content (time signal, single value, distribution, ...) I ask myself, how I could define a super data-type with sub-data-types to inherit, but then also overload certain functions (like u would do in OO).
What is best way in haskell to achieve this ? (I'm unsure wether haskell classes are what I'm looking for)
Cheers Phil
########## Code below
import qualified Data.Vector.Unboxed as V
data TimeSig = TimeSig Int Double (V.Vector Double) -- signal Index timeStep data
getVect :: TimeSig -> (V.Vector Double) getVect (TimeSig idx dt vect)= vect
getIdx :: TimeSig -> Int getIdx (TimeSig idx dt vect) = idx
getdt :: TimeSig -> Double getdt (TimeSig idx dt vect) = dt
pzipWith :: (Double -> Double -> Double) -> TimeSig -> TimeSig -> TimeSig pzipWith f p1 p2 = TimeSig idx dt vect where vect = V.zipWith f (getVect p1) (getVect p2) idx = getIdx p1 dt = getdt p1
pmap :: (Double -> Double) -> TimeSig -> TimeSig pmap f p = TimeSig (getIdx p) (getdt p) (V.map f (getVect p))
instance Num TimeSig where (+) p1 p2 = pzipWith (+) p1 p2 (-) p1 p2 = pzipWith (-) p1 p2 negate p1 = pmap negate p1 abs p1 = pmap abs p1 (*) p1 p2 = pzipWith (*) p1 p2
instance Eq TimeSig where (==) p1 p2 = (==) (getVect p1) (getVect p2)
instance Show TimeSig where show (TimeSig idx dt vect) = "TimeSignal Nr: " ++ show idx ++ " dt: " ++ show dt ++ " val:" ++ show vect
main = do
let p = TimeSig 5 0.1 (V.fromList [0..10::Double]) putStrLn (show p) putStrLn (show (p+p))
-- View this message in context: http://haskell.1045720.n5.nabble.com/Data-Type-Inheritance-ala-OO-Inheritenc... Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe