Tuesday, March 26, 2013

HASKELL BEGINNER PROGRAM SKELETON: "READ FILE WRITE FILE"

HASKELL BEGINNER PROGRAM SKELETON: "READ FILE WRITE FILE"

REVISED: Monday, February 12, 2024




Haskell Beginner Program Skeleton: A "Read File Write File" Tutorial.

I. READ FILE WRITE FILE EXAMPLE

Use your editor to save the following input.txt file:

A bug sat in a silver flower
thinking silver thoughts.
A bigger bug out for a walk
climbed up that silver flower stalk
and snapped the small bug down his jaws 
without a pause
without a care
for all the bug's small silver thoughts. 
It isn't right,
it isn't fair,
that that big bug ate that little bug
because that little bug was there.
He also ate his underwear. 

Also use your editor to save output.txt file as an empty file.

A. SKELETON

module Main where

import System.IO
import Data.Char

main :: IO ()
main = do 
       inh <- openFile "input.txt" ReadMode
       outh <- openFile "output.txt" WriteMode

       -- Your code goes here, replacing the function mainloop call.

       hClose inh
       hClose outh

-- And, your code goes here, replacing the function mainloop signature and definition.

B. FLESH ON BONES

1. SAVE

Use your editor to save the following Main.hs file:

module Main where

import System.IO
import Data.Char(toUpper)

main :: IO ()     -- The main function signature.
main = do          -- Calls the main function. 
       inh <- openFile "input.txt" ReadMode
       outh <- openFile "output.txt" WriteMode
       mainloop inh outh                                       -- Calls the mainloop function.
       hClose inh
       hClose outh

mainloop :: Handle -> Handle -> IO ()     -- The mainloop function signature.
mainloop inh outh =                                         -- The mainloop function definition.
    do ineof <- hIsEOF inh
       if ineof
           then return ()
           else do inpStr <- hGetLine inh
                   hPutStrLn outh (map toUpper inpStr)
                   mainloop inh outh

The above program is color coded: Variables are blue. Haskell keywords are red. User defined functions are orange.

2. LOAD

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

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

3. RUN

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

Prelude>  main
Prelude>

When you run main in GHCi it looks like nothing has happened; however, lots of things have happened. You have read from the input.txt file, and written to the output.txt file. At first it looks odd, because the program did not write output to your screen.

Open the output.txt file with your editor and you will see the following:

A BUG SAT IN A SILVER FLOWER
THINKING SILVER THOUGHTS.
A BIGGER BUG OUT FOR A WALK
CLIMBED UP THAT SILVER FLOWER STALK
AND SNAPPED THE SMALL BUG DOWN HIS JAWS 
WITHOUT A PAUSE
WITHOUT A CARE
FOR ALL THE BUG'S SMALL SILVER THOUGHTS. 
IT ISN'T RIGHT,
IT ISN'T FAIR,
THAT THAT BIG BUG ATE THAT LITTLE BUG
BECAUSE THAT LITTLE BUG WAS THERE.
HE ALSO ATE HIS UNDERWEAR. 

4. COMPILE 

As shown below, compile Main.hs in GHC:

Prelude>  :! ghc --make "*Main"
[1 of 1] Compiling Main             ( Main.hs, Main.o )
Linking Main.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.

The Haskell keywords used in this tutorial are discussed below:

1. openFile

Prelude>  :type openFile
openFile :: FilePath -> IOMode -> IO Handle
Prelude>

inh <- openFile "input.txtReadMode

Opens the input.txt file in ReadMode and creates the input file handle inh. From this point in the program the input.txt file will be referred to by the name of its handle inh. For the time being, you can think of inh as a nickname for input.txt

outh <- openFile "output.txtWriteMode

Opens the output.txt file in WriteMode and creates the output file handle outh. From this point in the program the output.txt file will be referred to by the name of its handle nickname outh.

2. ReadMode

Prelude>  :type ReadMode
ReadMode :: IOMode
Prelude>

inh <- openFile "input.txtReadMode

When openFile opens the input.txt file, ReadMode flags the file for read mode.

3. WriteMode

Prelude>  :type WriteMode
WriteMode :: IOMode
Prelude>

outh <- openFile "output.txtWriteMode 

When openFile opens the output.txt file, WriteMode flags the file for write mode.

4. hClose

Prelude>  :type hClose
hClose :: Handle -> IO ()
Prelude>

       hClose inh
       hClose outh

hClose closes the input.txt file handle nicknamed inh; which is the same as closing the input.txt file.

hClose closes the output.txt file handle nicknamed outh; which is the same as closing the output.txt file. 

5. hIsEOF

Prelude>  :type hIsEOF
hIsEOF :: Handle -> IO Bool
Prelude> 

do ineof <- hIsEOF inh

hIsEOF inh returns True if no further input can be taken from inh; otherwise, it returns False. Then either True or False is bound to ineof by the <- function arrow. hIsEOF inh means execute hIsEOF inh in the IO monad and bind the result in ineof.

6. return

Prelude>  :type return
return :: Monad m => a -> m a
Prelude> 

In general, for any value, there is a computation which "does nothing", and produces that result. This is given by defining the function return for the given monad.

mainloop :: Handle -> Handle -> IO ()      -- The mainloop function signature.
mainloop inh outh =                                          -- The mainloop function definition.
    do ineof <- hIsEOF inh
       if ineof
           then return ()
           else do inpStr <- hGetLine inh
                   hPutStrLn outh (map toUpper inpStr)
                   mainloop inh outh

In our example the function mainloop has two arguments: inh and outh. The first do statement binds ineof with a True or False from hIsEof inh.

if in Haskell must always have a then and an else.

If ineof is True we are at the end of the input.txt file, then return () is executed and we return to the main function, close the input stream handle, close the output stream handle, and exit the main function.

If ineof is False the else second do first statement is executed binding inStr with the next line of characters from inhThe function map takes the function toUpper which takes a list of lower case characters inpSTR and produces a list of upper case characters which hPutStrLn writes to the output.txt file handle outh output stream. The second do third statement recursively calls the function mainloop with the two arguments inh and outh.

7. hGetLine

Prelude>  :type hGetLine
hGetLine :: Handle -> IO String
Prelude>

else do inpStr <- hGetLine inh

hGetLine reads a line from the input.txt file handle inh input stream and <- binds that line to inpStr.

8. hPutStrLn

Prelude>  :type hPutStrLn 
hPutStrLn :: Handle -> String -> IO ()
Prelude>

hPutStrLn outh (map toUpper inpStr) 

The function hPutStrLn writes a string to the output.txt file handle outh output stream and adds a newline character.

9. map

Prelude>  :type map
map :: (a -> b) -> [a] -> [b]
Prelude> 

hPutStrLn outh (map toUpper inpStr) 

In general, the function map takes any function of type (a -> b) and yields a function that takes a list of a's [a] and produces a list of b's [b]. In our example, the function map takes the function toUpper which takes a list of lower case characters inpSTR and produces a list of upper case characters which hPutStrLn writes to the output.txt file handle outh output stream.

10. toUpper

Prelude>  :type toUpper
toUpper :: Char -> Char
Prelude>

hPutStrLn outh (map toUpper inpStr)

The function toUpper converts a letter to the corresponding upper-case letter, leaving any other character unchanged. Any Unicode letter which has an upper-case equivalent is transformed. 

11. ()

Prelude>  :type ()
() :: ()
Prelude>

then return ()

In general, the () is an empty tuple, pronounced “unit”, indicating that there is no return value. In our example, then return () is executed and we return to the main function, close the input stream handle, close the output stream handle, and exit the main function.    

II. CONCLUSION

In this tutorial, you have received an introduction to the Haskell beginner program skeleton "read file write file".

III. REFERENCES

Bird, R. (2015). Thinking Functionally with Haskell. Cambridge, England: Cambridge University Press.

Davie, A. (1992). Introduction to Functional Programming Systems Using Haskell. Cambridge, England: Cambridge University Press.

Goerzen, J. & O'Sullivan, B. &  Stewart, D. (2008). Real World Haskell. Sebastopol, CA: O'Reilly Media, Inc.

Hutton, G. (2007). Programming in Haskell. New York: Cambridge University Press.

Lipovača, M. (2011). Learn You a Haskell for Great Good!: A Beginner's Guide. San Francisco, CA: No Starch Press, Inc.

Thompson, S. (2011). The Craft of Functional Programming. Edinburgh Gate, Harlow, England: Pearson Education Limited.




Saturday, March 23, 2013

HASKELL BEGINNER PROGRAM SKELETON: "MODULE MAIN"

HASKELL BEGINNER PROGRAM SKELETON: "MODULE MAIN"

REVISED: Saturday, February 10, 2024




Haskell Beginner Program Skeleton: A "Module Main" Tutorial.

I. MODULE MAIN EXAMPLE

Most people learn a new computer programming language faster by programming in that language. This tutorial shows a Haskell program skeleton a beginner can use to start programming in Haskell. First you are shown the skeleton of a program. Then you are shown how to flesh out the bones of the skeleton to write your own programs. This gives you a feedback loop which will allow you to run the code you write to see if the program output is what you intended it to be. By changing and rerunning programs you learn Haskell.

A. SKELETON

-- MODULE DECLARATION
module Main where

-- IMPORTS

-- MAIN PROGRAM
main :: IO ()
main = do


-- FUNCTIONS 

B. FLESH ON BONES

1. SAVE

Use your editor to save the following Main.hs file:

module Main where

main :: IO ()
main = do  
       putStrLn "What is your favorite pet? "  
       pet <- getLine  
       putStrLn $"Amazing! My favorite pet is also a " ++ pet ++ "!" 

2. LOAD

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

Prelude>  :load Main.hs
[1 of 1] Compiling Main       ( Main.hs, interpreted )
Ok, modules loaded: Main.
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 module Main, function main, in GHCi:

Prelude>  main
What is your favorite pet? 
Dog
Amazing! My favorite pet is also a Dog!
Prelude>

4. COMPILE 

As shown below, compile Main.hs in GHC:

Prelude>  :! ghc --make "*Main"
[1 of 1] Compiling Main             ( Main.hs, Main.o )
Linking Main.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.

The Haskell keywords used in this tutorial are discussed below:

1. module

Large programming projects are divided in parts, containing pieces of the program that belong together. These parts are called modules.

Module names are alphanumeric and must begin with an uppercase letter. The module name, in most cases, should match the filename.

You cannot have multiple modules in the same file.

2. main

main :: IO () is the main function signature.

Function main is the "entry point of a Haskell program". In order for a program to be an executable, it must have the module named Main and must contain a function called main. The type of main is that of its final expression.

3. do

do is syntactic sugar for the function bind >>=. The signature for do is:

Prelude>  :type (>>=)
(>>=) :: Monad m => m a -> (a -> m b) -> m b
Prelude>

The function bind >>= combines a monad instance m a with a computation that produces another monad instance m b from a's to produce a new monad instance m b.  

A monad is a type constructor, a function called return, and a combinator function called bind or >>=. These three elements work together to encapsulate a strategy for combining computations to produce more complex computations.

Using a "container analogy", the type constructor m is a "container" that can hold different values. m a is a "container" holding a value of type a. The return function puts a value into a "monad container". The >>= function takes the value from a "monad container" and passes it to a function to produce a "monad container" containing a new value, possibly of a different type. The >>= function is known as "bind" because it binds the value in a "monad container" to the first argument of a function. By adding logic to the binding function, a monad can implement a specific strategy for combining computations in the monad.

You use do syntax to glue together several I/O actions into one.  This way you are guaranteed that I/O actions are executed in order. The value from the last action in a do block is bound to the do block result.

do notation is simply syntactic sugar. There is nothing that can be done using do notation that cannot be done using only the standard monadic operators. But do notation is cleaner and more convenient in some cases, especially when the sequence of monadic computations is long. You should understand both the standard monadic binding notation and do notation and be able to apply each where they are appropriate.

The standard language library, named "Prelude", provides us with lots of functions that return useful primitive IO actions. In order to combine them to produce an even more complex actions, we use a "do":

c = do a <- someAction
       b <- someOtherAction
       print (bar b)
       print (foo a)
       putStrLn "done"

Here we bind "c" to an action with the following "scenario":

evaluate action "someAction" and bind its result to "a"
then, evaluate "someOtherAction" and bind its result to "b"
then, process "b" with function "bar" and print result
then, process "a" with function "foo" and print result
then, print the word "done"

4. getLine

Prelude> :type getLine
getLine :: IO String
Prelude>

getLine is an "IO action" that, when performed, produces a string.

5. putStrLn

Prelude> :type putStrLn
putStrLn :: String -> IO ()
Prelude>

The () is an empty tuple, pronounced “unit”, indicating that there is no return value from putStrLn.

6. <-

Use the <- arrow function when you want to bind results of I/O actions to names.

7. ++

Haskell's name for the “append” function is (++).

Prelude>  "Has" ++ "kell"
"Haskell"
Prelude>  

8. $

In Haskell, function application is left associative. Left associative means operators are evaluated from left to right. For example, addition and subtraction have the same precedence and they are left-associative. In the expression 10-4+2, the subtraction is done first because it is to the left of the addition, producing a value of 8.

When an argument to a function is a result of another function, you have to use parentheses.

For example:

a b (c d)

means the function a acting on two arguments, b and (c d), which itself is an application of function c to d.

The parentheses can be removed by using the $ operator.

a b $ c d 

The $ function is also called "function application". Function application with $ is right-associative. Using $ we do not have to write as many parentheses. When a $ is encountered, the expression on its right is applied as the parameter to the function on its left. $ means that function application can be treated just like another function. For example, we can map function application over a list of functions.  

Prelude> :t ($)
($) :: (a -> b) -> a -> b
Prelude>

$ has the lowest precedence of any operator. The apply $ operator is used to leave out the closing parentheses in a Haskell statement. When you see a $ mentally replace it with a left open parentheses,  and mentally place the right closing parentheses at the end of the statement. Neither a $ nor a closing parentheses is coded at the end of the statement.

II. CONCLUSION

In this tutorial, you have received an introduction to the Haskell beginner program skeleton "module main".

III. REFERENCES

Bird, R. (2015). Thinking Functionally with Haskell. Cambridge, England: Cambridge University Press.

Davie, A. (1992). Introduction to Functional Programming Systems Using Haskell. Cambridge, England: Cambridge University Press.

Goerzen, J. & O'Sullivan, B. &  Stewart, D. (2008). Real World Haskell. Sebastopol, CA: O'Reilly Media, Inc.

Hutton, G. (2007). Programming in Haskell. New York: Cambridge University Press.

Lipovača, M. (2011). Learn You a Haskell for Great Good!: A Beginner's Guide. San Francisco, CA: No Starch Press, Inc.

Thompson, S. (2011). The Craft of Functional Programming. Edinburgh Gate, Harlow, England: Pearson Education Limited.




Thursday, March 21, 2013

HASKELL MONAD TYPE CLASS

HASKELL MONAD TYPE CLASS

REVISED: Monday, February 12, 2024




Haskell Monad Type Class.

I.  HASKELL MONOID VERSUS MONAD TYPE CLASS

Monads are unavoidable, because they are the only way to do IO without violating referential transparency that given a function and an input value, you will always receive the same output. The essence of monads is composition.

As you study monads keep in mind it is no more necessary to understand monad theory to perform Haskell I/O than it is to understand group theory to do simple arithmetic. That said, the information below is for those of us who would like an introduction to monad theory with the objective of understanding monad theory.

A monad consists of a type constructor M and two operations, bind >>= and return. The return operation takes a value from a plain type and puts it into a monadic container using the constructor. The bind >>= operation performs the reverse process, extracting the original value from the container and passing it to the associated next function in the pipeline. This process effectively creates an action that chooses the next action based on the results of previous actions. Therefore, we should be able to determine our next action based on the results of previous actions.  The Haskell programming language is a functional language that makes heavy use of monads, and includes syntactic sugar to make monadic composition more convenient.  

(M t) -> (t -> M u) -> (M u)   -- Two common ways of describing a monad.
IO a → (a → IO b) → IO b

If M is the name of the monad and t is a data type, then M t is the corresponding type in the monad.

The unit function has the polymorphic type t → M t, which Haskell represents by return.

Binding operation of polymorphic type (M t) → (t → M u) → (M u), which Haskell represents by the infix operator >>= which is read as "bind"

As shown above Haskell has an operator >>= pronounced "bind" with type IO a → (a → IO b) → IO b. That is, the operand on the left is an I/O action that returns a value of type a; the operand on the right is a function that can pick an I/O action based on the value produced by the action on the left. The resulting combined action, when performed, performs the first action, then evaluates the function with the first action's return value, then performs the second action, and finally returns the second action's value.

For example:

Use your editor to save the following MonadPipeline.hs file:

main =
       putStrLn "What is your name?" >> 
       getLine >>= \name ->
       putStrLn ("Nice to meet you, " ++ name ++ "!")

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

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

Prelude>  main
What is your name?
Elcric
Nice to meet you, Elcric!
Prelude>  

The pipeline structure of the bind >>= operator ensures that the getLine and putStrLn operations get evaluated only once and in the given order, so that the side-effects of extracting text from the input stream and writing to the output stream are correctly handled in the functional pipeline.

A. FUNCTOR

Every monad is a functor which transforms one category into another category.

class Functor f where
   fmap :: (a -> b) -> f a -> f b

Think of a functor as a type of container where we are permitted to apply a single function to every object in the container.

If f is a functor, and we are given a function of type (a -> b), and a container of type (f a), we can get a new container of type (f b).

B. MONOID

Given

  is for every.
  is an element of.
  is a function.
  is there exists.
:   is such that.
is defined to be.

then

a Monoid is a function () that satisfies the following:

1. The Set (S) is closed under the binary function ().

∀ a,b ∈ S: ab ∈ S

2. The binary function is associative.

∀ a,b,c ∈ S: (ab)c = a(bc)

3. e is the identity element.

∃ e∈S: ∀ a∈S: ea = ae = a

C. MONAD LAWS

As shown below the three monad laws can be described in many different ways. Each author seems to have their own favorite descriptions.

Four commonly used descriptions of the three laws that monads must obey are color coded below for comparison:

1. Left Identity

return a >>= f ≡ f a

return >=> f == f

id . f  ==  f

return x >>= f ==  f x

2. Right Identity

m >>= return ≡ m

f >=> return == f

f . id ==  f

mv >>= return ==  mv

3. Associativity

(m >>= f) >>= g ≡ m >>= (\x -> f x >>= g)

(f >=> g) >=> h == f >=> (g >=> h)

(f . g) . h == f . (g . h)

(mv >>= f) >>= g == mv >>= (\x -> (f x >>= g))

1. Left Identity

return a >>= f ≡ f a

2. Right Identity

m >>= return ≡ m

3. Associativity

(m >>= f) >>= g ≡ m >>= (\x -> f x >>= g)

1. Left Identity

return >=> f == f

2. Right Identity

f >=> return == f

3. Associativity

(f >=> g) >=> h == f >=> (g >=> h)

1. Left Identity

id . f  ==  f

2. Right Identity

f . id ==  f

3. Associativity

(f . g) . h == f . (g . h)

1. Left Identity

return x >>= f ==  f x

2. Right Identity

mv >>= return ==  mv

3. Associativity

(mv >>= f) >>= g == mv >>= (\x -> (f x >>= g))

Monad is a type class. To be an instance of the Monad type class, you must provide the functions (>>=) and return. The function (>>) will be derived from (>>=). >>= is called an argument in the monadic world.

Prelude> :type (>>)
(>>) :: Monad m => m a -> m b -> m b
Prelude>

Prelude> :type (>>=)
(>>=) :: Monad m => m a -> (a -> m b) -> m b
Prelude>

Prelude> :type return
return :: Monad m => a -> m a
Prelude>

m stands for Monad.

Everything before the => symbol is called a class constraint.

Using the same symbol or name for different operations is called overloading. A type that contains one or more class constraints is called ad hoc polymorphism, better known as overloaded. In Haskell, type classes provide a structured way to control ad hoc polymorphism, or overloading.

D. MONAD

NO SIDE EFFECTS

The following identity Functor is also a  monad, a monad with no side effects.

data I a = I a
instance Functor I where
    fmap f (I x) = I (f x)

The identity function takes one argument and returns that argument.

Composing functions with no side effects:

g :: a -> b  -- Function g has input type a and output type b.
f  :: b -> c  -- Function f has input type b and output type c.

f o g :: a -> c

Their composition f o g is defined as first the application of function g to a variable of type a and then the application of function f to the output of g a variable of type b.

SIDE EFFECTS

Monads make possible the composition of functions with side effects, we have to use bind instead of normal function composition.

Given M is a monad, we want to compose the following two functions.

g :: a -> M b
f  :: b -> M c

The output of g is of type a ->  M b and f is of type b -> M c. Therefore, >>= is of type 

M b -> (b -> M c) -> M c

f composed with g is taking the output of g and passing it to f.

g  >>= f

>>= takes the output of which is of type M b and also takes the function f
which is of type b -> M c and produces the output of f which is of type M c.

M b -> (b -> M c) -> M c

which is the type of  >>= bind.

By providing the definition of the function

M b -> (b -> M c) -> M c

we provide the way for the functions

g :: a -> M b
f  :: b -> M c

to be composed.

II. CONCLUSION

In this tutorial, you have received an introduction to the Haskell monad type class.

III. REFERENCES

Bird, R. (2015). Thinking Functionally with Haskell. Cambridge, England: Cambridge University Press.

Davie, A. (1992). Introduction to Functional Programming Systems Using Haskell. Cambridge, England: Cambridge University Press.

Goerzen, J. & O'Sullivan, B. &  Stewart, D. (2008). Real World Haskell. Sebastopol, CA: O'Reilly Media, Inc.

Hutton, G. (2007). Programming in Haskell. New York: Cambridge University Press.

Lipovača, M. (2011). Learn You a Haskell for Great Good!: A Beginner's Guide. San Francisco, CA: No Starch Press, Inc.

Thompson, S. (2011). The Craft of Functional Programming. Edinburgh Gate, Harlow, England: Pearson Education Limited.