Tuesday, April 9, 2013

HASKELL MODULES DATA HIDING

HASKELL MODULES DATA HIDING

REVISED: Monday, February 12, 2024




Haskell Data Hiding.

I. HASKELL DATA MODULES

You are reading "Haskell Modules Data Hiding", the second half of the "Haskell Data Modules" tutorial.


The two parts of this tutorial are a very brief outline of "Haskell Programming Tutorial 6 - Modules" by Sankha Mukherjee. 

A. SKELETON

STEP 1: We start off with the following file containing the vector functions:

module MyVectorsF where

(·) :: (Float, Float, Float) -> (Float, Float, Float) -> Float
(·) (x1, x2, x3)(y1, y2, y3) =  x1*y1+x2*y2+x3*y3

(×) :: (Float, Float, Float) -> (Float, Float, Float) -> (Float, Float, Float)
(×) (x1, x2, x3)(y1, y2, y3) =  (x2*y3-x3*y2, x3*y1-x1*y3, x1*y2-x2*y1)

1. Create a new data type.

data Vec = V3DCart Float Float Float
        deriving (Show)

We use the data keyword to define a new data type. The part before the = denotes the data type, which is Vec. The parts after the = are value constructors. They specify the different values that this data type can have. V3DCart is a value constructor that has three fields, parameters, which take floats. Value constructors are actually functions that return a value of a data type. The value constructor V3DCart returns a value of data type Vec. Adding deriving (Show) at the end makes our Vec data type part of the Show type class so Haskell knows how to get the string representation of our value and then Haskell prints that out to the terminal. Value constructors are just functions that take the fields as parameters and return a value of some data type as a result. Not exporting the value constructors of a data type makes them more abstract in such a way that we hide their implementation. Also, whoever uses our module can not pattern match against the value constructors.

2. Create accessor function.

make3DCV :: Float -> Float -> Float -> Vec
make3DCV a b c = V3DCart a b c

Type constructors can take types as parameters to produce new types. The a b c shown above are type parameters. Because there are type parameters involved, we call make3DCV a type constructor. Type parameters are useful because we can make different types with them depending on what kind of types we want contained in our data type. If our data type acts as some kind of box container, as does Vec, it is good to use type parameters. The parts after the = are value constructors. Value constructors specify the different values that make3DCV can have. V3DCart is a value constructor that has three fields, a b c type parameters.  Value constructors are actually functions that return a value of a data type. The value constructor V3DCart returns a value of data type Vec. 

3. Create a new type class.

class VectorC a where
        (·) :: a -> a -> Float
        (×) :: a -> a -> a

We use the classs keyword to define a new type class, which is VectorCType classes are like interfaces. We do not make data from type classes. The a after VectorC is the data type variable and it means that a will play the role of the data type that we will soon be making when we make an instance of VectorC. It does not have to be called a, it does not even have to be one letter, it just has to be a lowercase word. Then, we define several functions; e.g., (·) and (×). It is not mandatory to implement the function bodies themselves, we just have to specify the type declarations for the functions. 

4. Create instances of the new type class.

instance VectorC  Vec where
        (·) (V3DCart x1 x2 x3) (V3DCart y1 y2 y3) = x1*y1+x2*y2+x3*y3
        (×) (V3DCart x1 x2 x3) (V3DCart y1 y2 y3) = (V3DCart (x2*y3-x3*y2) (x3*y1-x1*y3) (x1*y2-x2*y1))

We make an instance of VectorC by using the instance keyword. So class is for defining new type classes and instance is for making our data types instances of type classes. When we were defining VectorC,  we wrote class VectorC a where and we said that a plays the role of whichever data type will be made an instance later on. We can see that clearly here, because when we are making an instance, we write instance VectorC  Vec where. We replace the a with the actual data type Vec.

In summary, first, we  create a new data type Vec. Second, we create accessor functions make3DCV. Third, we think about what the Vec data type can act like and create type classes VectorC, that can behave in that way. Fourth, the functions of our new data type Vec,  are made instances of that type class VectorC. Notice, the behavior of type classes is achieved by defining functions or just type declarations that we then implement. When we say that a data type is an instance of a type class, we mean that we can use the functions (·) and (×), that the type class defines with that data type.

STEP 2: We start off with the following file containing the main function:

import MyVectorsF

main = do
    print $ (2,4,5) · (0,1,0)
    print $ (2,4,5) × (0,1,0)

1. Call imported accessor functions.

    let a = make3DCV 2 4 5
    let b = make3DCV 0 2 0

2. Print new output.

    print $ a · b
    print $ a × b

B. FLESH ON BONES

1. SAVE

Save has two steps. "Save Step 1" saves the vector functions. "Save Step 2" saves the main function.

SAVE STEP 1

Use your editor to save  MyVectorsF.hs which is the final draft of vector dot product, and cross product, function signatures and definitions:

module MyVectorsF (make3DCV, VectorC(..)) where   -- Export accessor functions and everything in the class.

class VectorC a where   -- Creates a new "type class" VectorC, which takes any generic data type a.

    (·) :: a -> a -> Float    -- Generic function signatures which take any data type a.
    (×) :: a -> a -> a

data Vec = V3DCart Float Float Float   -- Creates a new "data type" Vec.
    deriving (Show)

make3DCV :: Float -> Float -> Float -> Vec   -- Accessor function returns data type Vec.

make3DCV a b c = V3DCart a b c

instance VectorC Vec where   -- Instances of the "type class" must agree with function signatures.

    (·) (V3DCart x1 x2 x3) (V3DCart y1 y2 y3) = x1*y1+x2*y2+x3*y3
    (×) (V3DCart x1 x2 x3) (V3DCart y1 y2 y3) = (V3DCart (x2*y3-x3*y2) (x3*y1-x1*y3) (x1*y2-x2*y1))

SAVE STEP 2

Use your editor to save MyVetorsM.hs which is the final draft of the main function:

import MyVectorsF

main = do

    let a = make3DCV 2 4 5   -- Calls imported accessor function.
    let b = make3DCV 0 2 0

    print $ a · b

    print $ a × b

2. LOAD

Load has two steps. "Load Step 1" loads the vector functions. "Load Step 2" loads the main function.

LOAD STEP 1

As shown below, load the above MyVectorsF.hs file into GHCi:

Prelude>  :load MyVectorsF
[1 of 1] Compiling MyVectorsF      ( MyVectorsF.hs, interpreted )
Ok, modules loaded: MyVectorsF.
Prelude>  

LOAD STEP 2

As shown below, load the above MyVectorsM.hs file into GHCi:

Prelude>  :load MyVectorsM
[1 of 2] Compiling MyVectorsF       ( MyVectorsF.hs, interpreted )
[2 of 2] Compiling Main             ( MyVectorsM.hs, interpreted )
Ok, modules loaded: Main, MyVectorsF.
Prelude>  

Now that we have loaded Main, we can run functions in GHCi that were defined in Main.

3. RUN

As shown below, run the function main, in GHCi:

Prelude>  main
8.0
V3DCart (-10.0) 0.0 4.0
Prelude>  

If we want to see the type of the accessor function make3DCV we can do the following:

Prelude>  :load MyVectorsF
Ok, modules loaded: MyVectorsF.
Prelude>

Prelude>  :type make3DCV
make3DCV :: Float -> Float -> Float -> MyVectorsF.Vec
Prelude>

It says, if you want a vector, give me three Floats. However, if you want to see the type of MyVectorsF.Vec watch what happens. It says I am not going to tell you what a vector is.

Prelude>  :type MyVectorsF2.Vec
<interactive>:1:1: Not in scope: data constructor `MyVectorsF2.Vec'
Prelude> 

The representation of MyVectorsF.Vec is hidden from you, the user. 

4. COMPILE 

As shown below, compile MyVectorsM.hs in GHC:

Prelude>  :! ghc --make "*MyVectorsM"
[1 of 2] Compiling MyVectorsF       ( MyVectorsF.hs, MyVectorsF.o )
[2 of 2] Compiling Main                  ( MyVectorsM.hs, MyVectorsM.o )
Linking MyVectorsM.exe ...
Prelude>  

The compile is shown so you know it compiles without error.

C. COMMENTS

Use the program shown above as an example. Rewrite the example and make it your own program.

Repeat 1. thru 3. above until your new program works the way you want it to work. Each time you make changes in your editor to your program, make sure you save the file and load it in GHCi.

II. CONCLUSION

In this tutorial, you have been introduced to the advantages of using "Haskell Modules Data Hiding."

III. REFERENCE

Haskell Programming by Sankha Mukherjee

Haskell Tutorial 6 - Modules