Re: [Haskell-cafe] Data Type Inheritance ala OO - Inheritence -- howto best in Haskell ?

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

Hi David, thanks for the links. I had a lok at the OO-paper some time ago already, heard however that its quite unusual and rather tricky to do OO-style programming in Haskell. So I'm looking for suggestions how to tackle this problem in a functional way. Cheers Phil -- 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.

I've done something perhaps similar in that I have a couple of signal
types, backed by (X, Y) vectors with Y values of different types, but
the same X type. So they can share a fair amount of implementation
that depends only on X. Still more could be shared if I could know a
"zero" value for each Y, so I wrote a SignalBase module:
class (Eq y) => Y y where
zero_y :: y
-- anything else that lets you share code
class (Storable.Storable (X, y), Y y) => Signal y
type SigVec y = V.Vector (X, y)
Now the SignalBase functions take '(Signal y) => SigVec y'. The
specific signals contain a SigVec, and the functions whose
implementations can be shared are just one line:
at :: X -> Signal y -> Y
at x sig = SignalBase.at x (sig_vec sig)
The 'y' parameter to Signal is unrelated, I use it for a phantom type
to distinguish between signals of the same implementation but
different logical meaning, but 'at' applies to all of them.
On Thu, Jun 16, 2011 at 2:16 PM, gutti
Hi David,
thanks for the links. I had a lok at the OO-paper some time ago already, heard however that its quite unusual and rather tricky to do OO-style programming in Haskell. So I'm looking for suggestions how to tackle this problem in a functional way.
Cheers Phil
-- 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

Hi Evan, that looks very interesting indeed - as still newby I try to understand: - u create a class "Y" to tackle the "zero" problem for different kinds of y vectors in a common way - u create a "Signal" class for the Y- signal inheriting interfaces from y and Storable.Storable Then u nest X and Y in a V.Vector - array and give it the type synonym SigVec. In all of this X and Y are ur types (or type synonyms) and y is a help variable. Then u define the function at -- and that where my understanding fails ? - this function takes X and sigVec and give u Y ? -- do u use it to applies all functions on SigVec on Y ? - don't u need to create instances somewhere in the process and wouldn't u then have to write all the code during the instance declaration ? Cheers Phil P.S.: - some generic question: - I read using composite datatype using the "data" keyword makes code rather slow - is nesting better ? : e.g. "data Signal Double v.Vector" versus "newtype (Double, v.Vector) - which nesting structure is most efficient - touples, lists, V.vector, ... - alternatively I'm thinking of an "external parallel list" to store information about the signals -- 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.

- u create a class "Y" to tackle the "zero" problem for different kinds of y vectors in a common way
Yes.
- u create a "Signal" class for the Y- signal inheriting interfaces from y and Storable.Storable
I wouldn't say "inheriting". It puts a restriction on 'y' saying that it has to be in Storable as well. That's unnecessary, but it saves me from having to put the restriction in all the places I use 'y'. I.e., the class below is not necessary, all it does is that instead of typing 'Storable (X, y), Y y' I can simply type 'Signal y'. So it's like a type alias for classes, except a little awkward because you need some bogus instances: class (Storable.Storable (X, y), Y y) => Signal y I don't know if it's a good idea or not, I just got tired of ugly signatures.
Then u nest X and Y in a V.Vector - array and give it the type synonym SigVec. In all of this X and Y are ur types (or type synonyms) and y is a help variable.
Sorry, there's some missing context which might make this more confusing. In SignalBase, X is a type but y is a type variable. Y is a type class that constrains the type variable 'y' (it could be named 'a' or 'b' or anything else). In SignalBase, 'at' has this signature: at :: (Signal y) => X -> SigVec y -> y Then in Signal, there is a concrete definition for 'y' called Y: newtype Signal = Signal { sig_vec :: SignalBase.SigVec Y } type X = SignalBase.X type Y = Double instance SignalBase.Signal Y -- To make the bogus empty instance for Signal happy, I have its requirements: instance Storable.Storable (X, Y) where sizeOf _ = Storable.sizeOf (undefined :: RealTime) + Storable.sizeOf (undefined :: Double) ... etc. instance SignalBase.Y Y where zero_y = 0 ... -- Now the 'at' in this module looks like: at :: X -> Signal -> Y at x sig = SignalBase.at x (sig_vec sig) I took out the phantom variable 'y' since that's orthogonal (though it's useful if you want to have several different types that can support the same operations).
- I read using composite datatype using the "data" keyword makes code rather slow - is nesting better ? : e.g. "data Signal Double v.Vector" versus "newtype (Double, v.Vector)
They're the same, a tuple is an indirection just like a two argument 'data'. And another pointer to follow in the middle is probably not going to make your code slow. If space saving is very important, you can eliminate it with the UNPACK pragma, but only think about that if you're storing very large numbers of them.
- which nesting structure is most efficient - touples, lists, V.vector, ...
Depends. The various unboxed vectors are efficient for memory and large scale transformation, lists are efficient for manipulating the front and are lazy on every single element and don't need Storable instances.
participants (4)
-
David Barbour
-
Evan Laforge
-
gutti
-
kaffeepause73