cibercitizen1
cibercitizen1

Reputation: 21476

Haskell: Implementing a design with an interface and a polymorphic function

Again I'm requesting comments about how a given design should be implemented in Haskell. Thanks in advance to everyone providing helpful comments. Also I hope this could be an aid to other Haskell novices like me, having a practical sample code.

This time, we have a polymorphic function doSampling (in module Samples) that takes a generic function f and a list of reals (indexes) and returns a Samples (indexes, values=f(indexes)). We want implement doSampling only once, as it doesn't matter if is f is a Polynomial or a Sinus. For that, we have introduced an interface Function, and have Polynomial and Sinus types implement it. The following is the design being implemented:

enter image description here

Edit 1:

There is a debate on the Function interface (class in Haskell). It has been suggested it is not actually necessary, as doSampling may take a "nude" function (Double -> Double) instead. But, how to do it, if you need some extra state within the nude function (coeffs for a polynomial, amp+freq+phase for a sinus?

Edit 2:

Very good answers by kosmikus and by Chris Taylor. Thanks. A key idea in both: have

doSampling :: (Double -> Double) -> [Double] -> Samples

This is: it takes a function (Double -> Double) (instead of Function) and list and returns samples.

My intention was to keep the state of Polynomials and Sinuses. That is not regarded in Chris answer, but it is in kosmikus'. On the other hand, the weak point in kosmikus version could be how to extend its Function definition if you don't have access to the source code.

I would also point out:

In sum

My own approach

main (usage)

import Polynomial
import Sinus
import Function
import Samples

-- ...............................................................
p1 = Polynomial [1, 0, 0.5]  -- p(x) =  1 + 0.5x^2 
s1 = Sinus 2 0.5 3 -- f(x) = 2 sin(0.5x + 3) 

-- ...............................................................

-- sample p1 from 0 to 5
m1 = doSampling p1  [0, 0.5 .. 5]
m2 = doSampling s1  [0, 0.5 .. 5]

-- ...............................................................
-- main
-- ...............................................................
main =  do
    putStrLn "Hello"
        print $ value p1 2
        print $ value s1 (pi/2)
        print $ pairs m1
        print $ pairs m2

Function

module Function where    
-- ...............................................................
-- "class type"  : the types belonging to this family of types
--    must implement the following functions:
--          + value : takes a function and a real and returns a real
-- ...............................................................
class Function f where 
    value :: f -> Double -> Double
        -- f is a type variable, this is:
        -- f is a type of the Function "family" not an actual function

Samples

module Samples where

import Function

-- ...............................................................
-- Samples: new data type
-- This is the constructor and says it requieres
-- two list, one for the indexes (xs values) and another
-- for the values ( ys = f (xs) )
-- this constructor should not be used, instead use 
-- the "factory" function: new_Samples that performs some checks
-- ...............................................................
data Samples = Samples { indexes :: [Double] , values :: [Double] }
     deriving (Show)

-- ...............................................................
-- constructor: it checks lists are equal size, and indexes are sorted
new_Samples :: [Double] -> [Double] -> Samples
new_Samples ind val 
             | (length ind) /= (length val) = samplesVoid
             | not $ isSorted ind = samplesVoid
             | otherwise = Samples ind val

-- ...............................................................
-- sample a funcion
-- it takes a funcion f and a list of indexes and returns
-- a Samples calculating the values array as f(indexes)
doSampling :: (Function f) => f -> [Double] -> Samples
doSampling f ind = new_Samples ind vals
              where 
                    vals = [ value f x | x <- ind ]

-- ...............................................................
-- used as "error" in the construction
samplesVoid = Samples [] []

-- ...............................................................
size :: Samples -> Int
size samples = length (indexes samples)   
-- ...............................................................
-- utility function to get a pair (index,value) out of a Samples
pairs :: Samples -> [(Double, Double)]
pairs samples = pairs' (indexes samples) (values samples)

pairs' :: [Double] -> [Double] -> [(Double, Double)]
pairs' [] [] = []
pairs' [i] [v] = [(i,v)]
pairs' (i:is) (v:vs) = (i,v) : pairs' is vs


-- ...............................................................
-- to check whether a list is sorted (<)
isSorted :: (Ord t) => [t] -> Bool
isSorted [] = True
isSorted [e] = True
isSorted (e1:(e2:tail))
         | e1 < e2 = isSorted (e2:tail)
         | otherwise = False

Sinus

module Sinus where

-- ...............................................................
import Function

-- ...............................................................
-- Sinus: new data type
-- This is the constructor and says it requieres
-- a three reals
-- ...............................................................
data Sinus = Sinus { amplitude :: Double, frequency :: Double, phase :: Double }
     deriving (Show)

-- ...............................................................
-- we say that a Sinus is a Function (member of the class Function)
-- and then, how value is implemented
instance Function Sinus where
         value s x = (amplitude s) * sin ( (frequency s)*x + (phase s))

Polynomial

module Polynomial where

-- ...............................................................
import Function

-- ...............................................................
-- Polynomial: new data type
-- This is the constructor and says it requieres
-- a list of coefficients
-- ...............................................................
data Polynomial = Polynomial { coeffs :: [Double] }
     deriving (Show)

-- ...............................................................
degree :: Polynomial -> Int
degree p = length (coeffs p)  - 1

-- ...............................................................
-- we say that a Polynomial is a Function (member of the class Function)
-- and then, how value is implemented
instance Function Polynomial where
         value p x = value' (coeffs p) x 1

--  list of coeffs -> x -> pw (power of x) -> Double
value' :: [Double] -> Double -> Double -> Double
value' (c:[]) _ pw =  c * pw
value' (c:cs) x pw =  (c * pw) + (value' cs x x*pw)

Upvotes: 1

Views: 446

Answers (2)

kosmikus
kosmikus

Reputation: 19637

[Expanded my comment on request.]

I'd probably do this roughly as follows:

import Data.Functor

-- Use a datatype rather than a class. Yes, this makes it harder to
-- add new types of functions later, and in turn easier to define new
-- operations. ("expression problem")
data Function =
    Sinus { amplitude :: Double, frequency :: Double, phase :: Double }
  | Polynomial { coeffs :: [Double] }
  deriving (Show)

-- Interpreting a Function as an actual function.
value :: Function -> (Double -> Double)
value (Sinus amp freq ph) x = amp * sin (freq * x + ph)
value (Polynomial cs)     x = value' cs x

-- Rewrite value' to not require non-empty lists. This can also be
-- nicely written as a fold.
value' :: [Double] -> Double -> Double
value' []     _ = 0
value' (c:cs) x = c + x * value' cs x

data Samples = Samples { indexes :: [Double] , values :: [Double] }
  deriving (Show)

-- Use Maybe to detect error conditions, instead of strange values
-- such as voidSamples.
newSamples :: [Double] -> [Double] -> Maybe Samples
newSamples ind val 
  | length ind /= length val = Nothing
  | not $ isSorted ind       = Nothing
  | otherwise                = Just (Samples ind val)

doSampling :: (Double -> Double) -> [Double] -> Maybe Samples
doSampling f ind = newSamples ind (map f ind)

isSorted :: (Ord t) => [t] -> Bool
isSorted []  = True
isSorted [e] = True
isSorted (e1:e2:es)
  | e1 < e2   = isSorted (e2:es)
  | otherwise = False

-- This is just zip.
pairs :: Samples -> [(Double, Double)]
pairs (Samples idxs vals) = zip idxs vals

p1 = Polynomial [1, 0, 0.5]  -- p(x) =  1 + 0.5x^2 
s1 = Sinus 2 0.5 3 -- f(x) = 2 sin(0.5x + 3) 

m1 = doSampling (value p1) [0, 0.5 .. 5]
m2 = doSampling (value s1) [0, 0.5 .. 5]

-- The <$> maps over a Maybe.
main =  do
  putStrLn "Hello"
  print $ value p1 2
  print $ value s1 (pi/2)
  print $ pairs <$> m1
  print $ pairs <$> m2

Upvotes: 3

Chris Taylor
Chris Taylor

Reputation: 47382

You certainly don't need the Function class. All this heavyweight class, instance, member variable fluff is one of the things that Haskell is designed to avoid. Pure functions can be much more flexible.

Here's a simple way of doing what you want.

type Sample = ([Double], [Double])

newSample xs vs
  | isSorted xs && length xs == length vs = (indices, values)
  | otherwise                             = ([], [])

pairs = uncurry zip

doSampling :: (Double -> Double) -> [Double] -> Sample
doSampling f xs = newSample xs (map f xs)

mkPolynomial :: [Double] -> (Double -> Double)
mkPolynomial coefs x = go coefs
  where
    go  []    = 0
    go (c:cs) = c + x * go cs

mkSinus :: Double -> Double -> Double -> (Double -> Double)
mkSinus amp freq phase x = amp * sin (freq * x + phase)

p1 = mkPolynomial [1, 0, 0.5] -- 1 + 0.5x^2
s1 = mkSinus 2 0.5 3          -- 2 sin(0.5x + 3)

m1 = doSampling p1 [0, 0.5 .. 5]
m2 = doSampling s1 [0, 0.5 .. 5]

main :: IO ()
main = do
  print $ p1 2
  print $ s1 (pi/2)
  print $ pairs m1
  print $ pairs m2

Upvotes: 12

Related Questions