Tuesday, June 23, 2015

HASKELL PARSING FILE RECORDS EXAMPLE

HASKELL PARSING FILE RECORDS EXAMPLE

REVISED: Thursday, February 8, 2024




1. INTRODUCTION

Using Haskell to parse records stored on a file is a good way to  begin learning Haskell data structures.

2. HASKELL PARSING FILE RECORDS EXAMPLE

This example parses the records in the annual customer sales file sales1945.txt to obtain the total sales for one customer.  You can create the sales1945.txt file from the Annual Sales File Listing printed by the module. Each record in the file has a field for custID (customer identification), invoice (invoice number), usd (United States Dollars), and mmddyyyy (invoice date). The example computes the total annual sales to one customer based on the custID.

Module:

:{
customerFilter  -- Function which creates a new list containing all records matching the customer ID.

customerID  -- The variable name for identification of the customer.

customerSales  -- Function which computes the customer total annual sales.

customerSalesFileRecords  -- The variable name containing all of the records for the entire annual sales file.

salesByCustomer  -- Function for user to input sales file name and customer ID.

sales  -- Function which creates a new list of only customer sales amounts.  

total  -- Function which turns each customer sales invoice amount String into a Double and totals the amounts. 

totalCustomerSales  -- The variable name for the total annual customer sales for one customer.

usdLines  -- Function which creates a new list of usd lines.

:}

module Sales where
import Data.List.Split(endBy)
import Data.List(isInfixOf, isPrefixOf)

:{
The function's purpose is to compute total annual USD sales for one customer ID.

The '.' operator is used to compose functions. Function composition is a way to "compose" two functions together into a single function.

map takes a function and a list and applies that function to every element in the list, producing a new list.

filter is a function that takes a predicate and a list and then returns the list of elements that satisfy the predicate.

A predicate is a function that tells whether something is true or not.

lines function is defined in the Data.List library. lines takes a String, and breaks it up into a list of strings, splitting on newlines.

dropWhile creates a list from another list taking from it its elements from when the condition fails for the first time till the end of the list.

isInfixOf function takes two lists and returns True iff the first list is contained, wholly and intact, anywhere within the second.

isPrefixOf function takes two lists and returns True iff the first list is a prefix of the second.

endBy creates a new list by splitting a String into chunks terminated by the given subsequence which is "@" in the example below.
 
:}

customerSales :: String -> String -> Double
customerSales customerSalesFileRecords customerID  = total.sales.usdLines $ customerFilter customerSalesFileRecords customerID
                                    where usdLines = map $ filter (isPrefixOf "usd").lines
                                               sales       = map (dropWhile (> ' ')).concat
                                               total        = sum.map (\x -> read x :: Double)
                                               customerFilter customerSalesFileRecords customerID = filter (isInfixOf customerID) $ endBy "@" customerSalesFileRecords

:{
Function purpose is for user to input sales file name and customer ID.

Function prints sales file records.

Function returns total annual USD sales for one customer ID.  
:}                                      
salesByCustomer :: IO Double
salesByCustomer = do
    putStrLn "Enter Annual Sales File Name:"  -- For example, enter sales1945.txt
    customerSalesFileRecords <- getLine >>= readFile  -- Reads in entire sales1945.txt file.
    putStrLn "\nAnnual Sales File Listing:\n"
    putStrLn customerSalesFileRecords                                 
    putStrLn "\nEnd Of Annual Sales File Listing:\n"
    putStrLn "Enter Customer ID:"  -- For example, a1a
    customerID <- getLine
    return $ customerSales customerSalesFileRecords customerID
    
main :: IO()
main = do
    totalCustomerSales <- salesByCustomer
    putStrLn ("\nCustomer Total USD Sales: " ++ show totalCustomerSales)

GHCi:

GHCi, version 9.8.1: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Prelude>

Prelude>  :load Sales
[1 of 1] Compiling Sales              (Sales.hs, interpreted )
Ok, modules loaded: Sales.
(0.09 secs, 34185296 bytes)
Prelude>

Prelude>  main
Loading package split-0.2.2 ... linking ... done.
Enter Annual Sales File Name:
sales1945.txt

Annual Sales File Listing:

custID a1a
invoice i1
usd 1.01
mmddyyyy 0101i945
@
custID b2b
invoice i2
usd 5678.05
mmddyyyy 02021945
@
custID c3c
invoice i3
usd 910.12
mmddyyyy 03101945
@
custID d4d
invoice i4
usd 1234.11
mmddyyyy 04111945
@
custID d4d
invoice i5
usd 5678.06
mmddyyyy 05211945
@
custID c3c
invoice i6
usd 910.01
mmddyyyy 06081945
@
custID b2b
invoice i7
usd 1111.08
mmddyyyy 11121945
@
custID a1a
invoice i8
usd 1000.03
mmddyyyy 11131945
@
custID a1a
invoice i9
usd 100.01
mmddyyyy 12251945
@
custID a1a
invoice i10
usd 10.02
mmddyyyy 12251945
@

End Of Annual Sales File Listing:

Enter Customer ID:
a1a

Customer Total USD Sales: 1111.07
Prelude>

3. CONCLUSION

In this tutorial you have seen a basic approach for using Haskell to parse file records.

4. 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.




Monday, June 1, 2015

HASKELL RECURSIVE DATA STRUCTURE TREE EXAMPLES

HASKELL TREE RECURSIVE DATA STRUCTURE EXAMPLES

REVISED: Wednesday, January 24, 2024




1. INTRODUCTION

To learn how to code a recursive data structure tree start with the following three basic definitions: 

-- Firstly, the basic definition of a Tree.
data Tree a = Leaf a | Branch (Tree a) (Tree a)
   deriving (Eq, Show)

A Tree a is either a leaf, containing a value of type a or a branch, from which hang two other trees of type Tree a.

-- Secondly, the basic definition of map for lists.
map              :: (a -> b) -> [a] -> [b]
map       _ [] = []
map f (x:xs) = f x : map f xs

-- Thirdly, the basic definition of foldr for lists.
foldr                 :: (a -> b -> b) -> b -> [a] -> b
foldr       f z []  = z
foldr f z (x:xs) = f x (foldr f z xs)

2. RECURSIVE DATA STRUCTURE TREE EXAMPLE 1

For details regarding this Example 1 code please refer to the following link.


module RDST1 where

import Prelude hiding (map, foldr)

data Tree a = Leaf a | Branch (Tree a) (Tree a)
   deriving (Eq, Show)

-- The basic map definition for a list is used to write the basic map definition for a tree. 
treeMap                       :: (a -> b) -> Tree a -> Tree b
treeMap                    f  = g where
   g                 (Leaf x) = Leaf (f x)
   g (Branch left right) = Branch (g left) (g right)

-- The basic foldr definition for a list is used to write the basic fold definition for a tree. 
treeFold                      :: (b -> b -> b) -> (a -> b) -> Tree a -> b
treeFold fbranch fleaf = g where g (Leaf x) = fleaf x
                                       g (Branch left right) = fbranch (g left) (g right)
 
tree1 :: Tree Integer
tree1 = Branch (Branch (Branch (Leaf 1) (Branch (Leaf 2) (Leaf 3))) (Branch (Leaf 4) (Branch (Leaf 5) (Leaf 6)))) (Branch (Branch (Leaf 7) (Leaf 8)) (Leaf 9))

tree2 :: Tree Integer
tree2 = Branch (Branch (Leaf 1) (Leaf 2)) (Branch (Leaf 3) (Leaf 4))

-- Doubles each value in tree.
doubleTree = treeMap (*2)

-- Sum of the Leaf values in tree.
sumTree = treeFold (+) id 

-- List of the Leaves of a tree.
fringeTree = treeFold (++) (: [])

main = do
    putStrLn $ "Original tree1: " ++ (show tree1)
    putStrLn $ "Original tree2: " ++ (show tree2)

GHCi:

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

Prelude>  main
Original tree1: Branch (Branch (Branch (Leaf 1) (Branch (Leaf 2) (Leaf 3))) (Branch (Leaf 4) (Branch (Leaf 5) (Leaf 6)))) (Branch (Branch (Leaf 7) (Leaf 8)) (Leaf 9))
Original tree2: Branch (Branch (Leaf 1) (Leaf 2)) (Branch (Leaf 3) (Leaf 4))
Prelude>

Prelude>  sumTree tree1
45
Prelude>

Prelude>  doubleTree tree1 
Branch (Branch (Branch (Leaf 2) (Branch (Leaf 4) (Leaf 6))) (Branch (Leaf 8) (Branch (Leaf 10) (Leaf 12)))) (Branch (Branch (Leaf 14) (Leaf 16)) (Leaf 18))
Prelude>

Prelude>  fringeTree tree1
[1,2,3,4,5,6,7,8,9]
Prelude>

Prelude>  fringeTree tree2
[1,2,3,4]
Prelude>

Prelude>  let tree3 = doubleTree tree1
Prelude>

Prelude>  tree3
Branch (Branch (Branch (Leaf 2) (Branch (Leaf 4) (Leaf 6))) (Branch (Leaf 8) (Branch (Leaf 10) (Leaf 12)))) (Branch (Branch (Leaf 14) (Leaf 16)) (Leaf 18))
Prelude>

Prelude>  fringeTree tree3
[2,4,6,8,10,12,14,16,18]
Prelude>

3. RECURSIVE DATA STRUCTURE TREE EXAMPLE 2

For details regarding this Example 2 code please refer to the following link.


module RDST2 where

data MyTree a = MyEmptyNode
              | MyFilledNode a (MyTree a) (MyTree a)
              deriving (Eq,Ord,Show,Read)

main :: IO ()
main  =
   do
      putStrLn "Begin program"

      let aMyTree = MyFilledNode 5 (MyFilledNode 3 MyEmptyNode MyEmptyNode) (MyFilledNode 2 MyEmptyNode MyEmptyNode)
      print aMyTree
      print (sumMyTree aMyTree)

      let bMyTree = MyFilledNode "r" (MyFilledNode "s" MyEmptyNode MyEmptyNode) (MyFilledNode "a" MyEmptyNode MyEmptyNode)
      print bMyTree

      putStrLn "End program"

sumMyTree                                       :: Num a => MyTree a -> a
sumMyTree MyEmptyNode             = 0
sumMyTree (MyFilledNode n t1 t2) = n + sumMyTree t1 + sumMyTree t2

GHCi:

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

Prelude>  main
Begin program
MyFilledNode 5 (MyFilledNode 3 MyEmptyNode MyEmptyNode) (MyFilledNode 2 MyEmptyNode MyEmptyNode)
10
MyFilledNode "r" (MyFilledNode "s" MyEmptyNode MyEmptyNode) (MyFilledNode "a" MyEmptyNode MyEmptyNode)
End program
Prelude>

4. RECURSIVE DATA STRUCTURE TREE EXAMPLE 3

For details regarding this Example 3 code please refer to the following link.


module RDST3 where

import Control.Applicative

data MyTree a = MyNode a [MyTree a]
                deriving (Show)

instance Functor MyTree where
   fmap f (MyNode x treeList) = MyNode (f x) (map (fmap f) treeList)

instance Applicative MyTree where
   pure x = MyNode x []
   (MyNode f treeFunctionList) <*> (MyNode x treeElementList) =
      MyNode (f x) ( (map (fmap f) treeElementList) ++ (map (<*> (MyNode x treeElementList)) treeFunctionList) )

instance Monad MyTree where
   return x = MyNode x []
   MyNode x treeList >>= f = MyNode x' (treeList' ++ map (>>= f) treeList)
      where MyNode x' treeList' = f x

main :: IO ()
main  =
   do
      putStrLn "Program begins."

      putStrLn "Tests that prove that MyTree behaves as a type constructor."

      let tree1 = MyNode 5 [MyNode 3 [], MyNode 2 []]
      print tree1

      let tree2 = MyNode "ABC" [MyNode "DEFG" [], MyNode "HIJKL" []]
      print tree2

      putStrLn "Tests that prove that MyTree behaves as a Functor."

      print (fmap (*2) tree1)
      print (fmap length tree2)

      putStrLn "Tests that prove that MyTree behaves as an Applicative."

      print ((MyNode (*2) []) <*> tree1)
      print ((MyNode (*2) [MyNode (+100) [], MyNode (+1000) []]) <*> tree1)
      print ((MyNode init []) <*> tree2)
      print ((MyNode init [MyNode reverse [MyNode tail []]]) <*> tree2)

      putStrLn "Tests that prove that MyTree behaves as a Monad."

      print (tree1 >>= (\x -> MyNode (x+200) []))
      print (tree2 >>= (\x -> MyNode (tail x) []))

      putStrLn "Program ends."

GHCi:

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

Prelude>  main
Program begins.
Tests that prove that MyTree behaves as a type constructor.
MyNode 5 [MyNode 3 [],MyNode 2 []]
MyNode "ABC" [MyNode "DEFG" [],MyNode "HIJKL" []]
Tests that prove that MyTree behaves as a Functor.
MyNode 10 [MyNode 6 [],MyNode 4 []]
MyNode 3 [MyNode 4 [],MyNode 5 []]
Tests that prove that MyTree behaves as an Applicative.
MyNode 10 [MyNode 6 [],MyNode 4 []]
MyNode 10 [MyNode 6 [],MyNode 4 [],MyNode 105 [MyNode 103 [],MyNode 102 []],MyNode 1005 [MyNode 1003 [],MyNode 1002 []]]
MyNode "AB" [MyNode "DEF" [],MyNode "HIJK" []]
MyNode "AB" [MyNode "DEF" [],MyNode "HIJK" [],MyNode "CBA" [MyNode "GFED" [],MyNode "LKJIH" [],MyNode "BC" [MyNode "EFG" [],MyNode "IJKL" []]]]
Tests that prove that MyTree behaves as a Monad.
MyNode 205 [MyNode 203 [],MyNode 202 []]
MyNode "BC" [MyNode "EFG" [],MyNode "IJKL" []]
Program ends.
Prelude> 

5. CONCLUSION

The purpose of this article is not to discuss the code but to point out you should always start with the basic things you know about Haskell in order to understand the things you think are difficult. Learn the basic concepts they are the building blocks for understanding Haskell.

6. 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, May 21, 2015

HASKELL HIGHER ORDER FUNCTIONS

HASKELL HIGHER ORDER FUNCTIONS

REVISED: Monday, February 12, 2024




1. INTRODUCTION

A function is called higher order if it takes a function as an argument or returns a function as a result. In Haskell, we refer to functions that take other functions as arguments and return new functions as combinators.

Higher order functions taking functions as arguments include map and filter.

The term curried is normally used for higher order functions that take their arguments one at a time and return a function as a result.

Haskell higher order functions can be used to define Embedded Domain Specific Languages (EDSLs).

2. MAP

map applies a function to every element of a list.

2.1. MAP DEFINED USING LIST COMPREHENSION

Defining map using list comprehension makes it easy to see how map applies a function f x to every element of a list of xs:

-- Functions passed to other functions are written with their type declarations surrounded by parentheses; i.e., (a -> b).
-- 1st argument is a function that takes an "a" and returns a "b".
map :: (a -> b) -> [a] -> [b]
map f xs = [f x | x <- xs]

2.2. MAP DEFINED USING RECURSION

Haskell programmers never use loops. Instead they either use recursion to do looping, or they use functions like map that take other functions as arguments.

Defining map using recursion:

map :: (a -> b) -> [a] -> [b]
map f []        = []
map f (x:xs) = f x : map f xs

3. FILTER

filter selects every element from a list that satisfies a condition or predicate.

3.1. FILTER DEFINED USING LIST COMPREHENSION

Given:
p x is a condition or predicate function.
xs is a list of xs.
x is an element drawn from the list of xs.
<- is pronounced "drawn from."
| pipe is pronounced "such that."
, comma before the condition or predicate is pronounced "such that."

filter defined using list comprehension:

filter :: (a -> Bool) -> [a] -> [a]
filter p xs = [x | x <- xs , p x]

3.2. FILTER DEFINED USING RECURSION

filter :: (a -> Bool) -> [a] -> [a]
filter p [] = []
filter p (x:xs)
    | px            = x : filter p xs
    | otherwise = filter p xs

4. CURRIED

Functions with multiple arguments are defined in Haskell by currying. Currying is the process of transforming a function that takes multiple arguments into a function that takes just a single argument and returns another function if any arguments are still needed.

In Haskell, all functions are considered curried. All functions in Haskell take just single arguments.

Curried functions can be partially applied. Partial application in Haskell involves passing less than the full number of arguments to a function that takes multiple arguments.

5. EMBEDDED DOMAIN SPECIFIC LANGUAGES (EDSLs)

Higher order functions can be used in Haskell to define EDSLs which can be used to do many things including processing lists and building parsers. A Haskell EDSL is a language embedded inside of Haskell. An EDSL uses the library of functions provided by Haskell, often called combinators, because they combine their arguments into terms inside the EDSL. In essence, EDSLs are just Haskell libraries.

6. USER DEFINED

User defined higher order functions often use partial application. Partial application in Haskell involves passing less than the full number of arguments to a function that takes multiple arguments. This results in a new function taking the remaining number of parameters.

6.1. RECEIVE A FUNCTION

The function area is missing the value for the radius rThe radius function computes the area of the circle using a hard coded value of 5 for the radius r. This is done by the function radius argument func receiving the function area with argument 5 as shown below.

-- C:\Users\Tinnel\areaCircle.hs

import Data.List
import System.IO

-- Area of Circle
area :: Floating a => a -> a
area r = pi * r ^ 2  -- The function area is missing the value for the radius r.

radius :: Num a => (a -> t) -> t  -- func receives area function (a -> t).
radius func = func 5 -- radius argument 5, the constant t, is passed into function area.

areaCircle :: Double
areaCircle = radius area  -- areaCircle stores results of function radius with r of 5.

Prelude> areaCircle
78.53981633974483
Prelude> 

6.2. RETURN A FUNCTION

-- C:\Users\Tinnel\onePlus9.hs

import Data.List
import System.IO

addFunc :: Num a => a -> a -> a  -- When you type :t addFunc
addFunc x y = x + y

{-

The -> kleisli arrow operator is right associative, and function application is left associative, meaning the type signature of addFunc actually looks like this:

addFunc :: Num a => a -> (a -> a)

This means that addFunc actually takes one argument and returns a function that takes another argument and returns an Int. In other words, addFunc is a function that takes a number and returns a function that takes a number and returns the sum of the two numbers.

-}

add9 :: Integer -> Integer
add9 = addFunc 9

onePlus9 :: Integer
onePlus9 = add9 1 

Prelude> onePlus9
10
Prelude> 

7. CONCLUSION

Haskell higher order functions allow for powerful abstractions. They make it easier to think in terms of functions and design the ultimate abstraction Embeded Domain Specific Languages (EDSLs).

  8. 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, May 9, 2015

THERE ARE MANY WAYS TO WRITE HASKELL PROGRAMS

THERE ARE MANY WAYS TO WRITE HASKELL PROGRAMS

REVISED: Tuesday, February 13, 2024




1. INTRODUCTION

There are many ways to write Haskell programs. The following are just a few of the many ways you can use Haskell to solve problems and present information with batch and interactive programs.

2. BATCH PROGRAMS

Firstly, you can write Haskell pure functions also called batch programs that have no side effects. Batch programs are programs that do not need to interact with the user while they are running. Batch programs take all their inputs at the start of the program and give all their outputs at the end of the program. Batch programs are written with functions that do not interact with their environment.

When programming first started many programs were batch programs which were run in computer centers far removed from the users who would use the output. Batch programming was well suited for payroll, inventory, accounts receivable, accounts payable, personnel, and in general most business applications. Many batch programs are still used today because they lend themselves to time cut offs such as the end of the month, the end of a payroll period, or the end of any accounting period of time.

3. INTERACTIVE PROGRAMS

Secondly, you can write Haskell impure functions also called interactive programs that do have IO side effects. Interactive programs are programs that do need to interact with the user while they are running. Interactive programs read from the keyboard and write to the screen as the program is running allowing the user to control input and output. These programs are normally run at the users location instead of an off site computer center. Interactive Haskell programs can be written in many ways including stream-based interaction, the interact function, and monads.

3.1. STREAM-BASED

Early versions of Haskell used stream-based interaction as the main method of interacting with the outside world. You can think of a stream as a continuing sequence of elements bundled in chunks. Stream processing applications are very important in our society. We want to know information the instant information is created. News of world events, changes in the stock market, political decisions which could start or stop a war are all things we want to know the moment they occur. 

3.2. INTERACT FUNCTION

The interact function signature is:

interact :: (String -> String) -> IO ()

The following module uses the interact function which is a function that passes the entire input as a giant string to a function of your choice, then prints the returned string to standard output.

module InteractHaskell where

import Data.Char (toUpper)

main :: IO ()
main = interact upperCase

upperCase :: String -> String
upperCase = map toUpper

The output from GHCi is as follows:

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

Prelude>  upperCase "summer in the sun is lots of fun."
"SUMMER IN THE SUN IS LOTS OF FUN."
Prelude>  

3.3. IO ACTION MONADS

IO action monads have evolved into being the currently most often choice for writing Haskell programs. Three IO action primitives are getChar, putChar, and return. Some very basic IO action monad examples are shown below.

3.3.1. INPUT:

getChar :: IO Char           -- IO action primitive that reads a single Char from the terminal.
getLine :: IO String          -- IO action that reads a single String from the terminal.

3.3.2. OUTPUT:

putChar :: Char -> IO ()   -- IO action primitive that prints a single Char to the terminal.
putStr :: String -> IO ()    -- IO action that prints a single String to the terminal.

print :: Show a => a -> IO ()
putStrLn :: String -> IO ()
return :: Monad m => a -> m a  -- Monad is an IO action primitive that returns any type.

3.3.3. IO ACTION MONAD EXAMPLES

A sequence of actions can be combined as a single composite action using the keyword do.

Four examples of the above IO action monads using do are as follows:

3.3.3.1. Example 1

Module:

module ExOne where

ex1a :: IO ()
ex1a = do putStr "Type a Char then press Enter to echo the Char:\n"
                 x <- getChar
                 putChar x
                 putStr "\n"

ex1b :: IO ()
ex1b = do putStr "Type a String then press Enter to echo the String: \CR"
                 y <- getLine
                 putStr y
                 putStr "\CR"
                 putStr ""

ex1c :: IO (Char, Char)
ex1c = do putStr "At each blinking cursor type a Char then press Enter to echo two Char:\n"
                getChar >>= \x ->
                    getChar >>= \_ ->
                        getChar >>= \y ->
                            return (x,y)       
GHCi:

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

Prelude>  ex1a
Type a Char then press Enter to echo the Char: 
a
a
Prelude>

Prelude>  ex1b
Type a String then press Enter to echo the String: 
Hello World!
Hello World!
Prelude>  

Prelude>  ex1c
At each blinking cursor type a Char then press Enter to echo two Char:
a
b
('a','b')
Prelude>

Prelude>  :type (>>=)
(>>=) :: Monad m => m a -> (a -> m b) -> m b  -- Takes something of IO a, and a function of (a to IO b), and returns IO b.
Prelude>

3.3.3.2. Example 2

GHCi:

Prelude>  let main = putStrLn "Hello, world!"
Prelude>

Prelude>  main
Hello, world!
Prelude>

3.3.3.3. Example 3

Module:

module ExThree where

main = do putStrLn "Type a line of text and then press Enter to echo the line of text: "
                 line <- getLine
                 print line

GHCi:

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

Prelude>  main
Type a line of text and then press Enter to echo the line of text: 
Hello, world!
"Hello, world!"
Prelude> 

3.3.3.4. Example 4

Module:

module ExFour where

-- GetChar :: IO Char
-- PutChar :: Char -> IO ()

-- Reading a string from the keyboard.

myGetLine :: IO [Char]
myGetLine = do x <- getChar
                           if x == '\n' then  -- '\n' is escape sequence for new line.
                              return []
                           else
                              do xs <- myGetLine
                                   return (x:xs)  

-- Writing a string to the screen:

myPutStr            :: String -> IO ()
myPutStr []        = return ()
myPutStr (x:xs) = do putChar x
                                   myPutStr xs
  
-- Writing a string and moving to a new line:

myPutStrLn      :: String -> IO ()
myPutStrLn xs = do myPutStr xs
                                 putChar '\n'
 
main  = do myPutStr "Enter a string then press Enter: "
                   xs <- myGetLine
                   myPutStr "The string has "
                   myPutStr (show (length xs))
                   myPutStrLn " characters counting punctuation and white-space."

GHCi:

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

Prelude>  main
Enter a string then press Enter: Hello, world!
The string has 13 characters counting punctuation and white-space.
Prelude>

4. CONCLUSION

There are many ways to write Haskell programs. The number of ways will change as time goes by because our needs as a society will change. Haskell must evolve to meet those needs or Haskell will be replaced by other languages. such as Python.

5. 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.




Friday, March 27, 2015

HASKELL UNWRAP WRAP INTRODUCTION

HASKELL UNWRAP WRAP INTRODUCTION

REVISED: Thursday, February 8, 2024




Haskell code shows copious amounts of (>>=) pronounced bind.

A Monad is a data structure which implements a Monad type class and satisfies Monad laws. A Monad typeclass defines two functions, the (>>=) and the return that know how to unwrap and wrap data. (>>=) bind is used to unwrap data and apply it to a function which takes the data as input and outputs a monad. (>>=) binds the unwrapped result of the computation on the left to the parameter of the one on the right. return is used to wrap data into a monad's type constructor.

Unwrap is the deconstructor in Haskell; destructing/unwrapping. Wrap is the constructor in Haskell; constructing/wrapping. You can also think of IO as a wrapper. The unwrapping of >>= cancels out the wrapping done by return, leaving only the function.

1. HASKELL WRAP UNWRAP EXAMPLE 1

The identity monad is a monad that does nothing special.

"Copy Paste" the following example into your text editor and "File Save As" WrapUnwrap.hs to your working directory.

module WrapUnwrap where

import Prelude hiding (Maybe(..))
import Control.Monad
import Control.Applicative

data Wrap a = Wrap a deriving Show

instance Functor Wrap where
   fmap f (Wrap a) = Wrap (f a)
   fmap _ Nothing  = Nothing

instance Monad Wrap where           
   return a = Wrap a
   Wrap a >>= f = f a   

instance Applicative Wrap where
   pure = Wrap
   Wrap f <*> Wrap a = Wrap (f a)
   _      <*> _      = Nothing

f :: Num a => a -> Wrap a
f a = Wrap (a + 1)                                -- Returns an incremented wrapped result.

(>>=) f (Wrap a) = f a                          -- unwrap does the exact opposite of wrap.

Load the example into GHCi.

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

As shown below we can take data and wrap it inside a data type and then increment it while it is wrapped in that data type:

Prelude>  f 2
Wrap 3
Prelude>

2. HASKELL UNWRAP WRAP EXAMPLE 2

Consider the following Functor:

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

instance Functor Maybe where
     fmap _ Nothing = Nothing
     fmap f (Just x)   = Just (f x)

If a value is wrapped in Just the fmap calls the function on the unwrapped value, and then rewraps it in Just.

3. HASKELL WRAP EXAMPLE 3

Wrap was easy to see in Example 1. You have to look closer to see wrap in Example 2.

"Copy Paste" the following example into your text editor and "File Save As" JustNothing.hs to your working directory.

module JustNothing where

import Prelude hiding (Maybe(..), lookup)

data Maybe a = Just a | Nothing
  deriving (Eq, Ord, Show)

pie :: [(String, String)]
pie = [("3.141592653589793", "pi")]

lookup key [] = Nothing
lookup key ((k, v) : rest) = if key == k then Just v else lookup key rest

main = do
  putStrLn "Please type pi to 15 decimal places then press Enter."
  word <- getLine  -- Notice getLine has type "getLine :: IO String",  <- is used to unwrap String from the IO action and bind it to word.
  print (lookup word pie)  -- Notice word has type "word :: String", not IO String; therefore, word is not an IO action. 
  if word == "3.141592653589793"
     then return ( "Congratulations!" )
     else main  

Load the example into GHCi:

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

Run the example in GHCi:

Prelude>  main
Please type pi to 15 decimal places then press Enter.
3.141592653589793
Just "pi"
"Congratulations!"
Prelude>

4. SUMMARY

The Haskell programming language is a functional language that makes heavy use of monads. 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. In other words, if x is a computation, and f is a function x >>= f is a computation which runs x, then applies f to its result, getting a computation which it then runs. Monads in Haskell can be thought of as composable computation descriptions.

5. CONCLUSION

Using return and bind we can wrap data and manipulate the wrapped data while keeping that data wrapped. We can also chain functions together that wrap. And in the process of doing these things we learn how monads work.

The unwrap wrap analogy is used to help you acquire intuition regarding how monads work. However, do not take unwrap wrap too literally. Unwrap wrap are mental tools to help you eventually gain the insight needed to think of monads in a computational context not in a unwrap wrap context.

6. 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.




Monday, March 16, 2015

HASKELL LOOKUP TABLE DICTIONARY

HASKELL LOOKUP TABLE DICTIONARY

REVISED: Wednesday, January 24, 2024





1. HASKELL LOOKUP TABLE DICTIONARY

Shown below is a simple easy to understand Haskell lookup table dictionary program:

module Rhymes where

import Prelude hiding (Maybe(..), lookup)

{-
Representing failure using Maybe monad.
Using monads for error handling, also known as exception handling.
Data keyword introduces type Maybe a.
a is a place holder a generic variable.
Just and Nothing are constructors of type Maybe.
-}

data Maybe a = Just a | Nothing
deriving (Eq, Ord, Show)

{-
Lookup Table Dictionary.
A lookup table dictionary relates keys k to values v.
First tuple String is the key k.
Second tuple String is the value v.
-}

rhyme :: [(String, String)]
rhyme = [("fleece", "fleas")
           ,("snow", "go")
          ,("walk", "stalk")
          ,("jaws", "pause")
          ,("fair", "there")
          ,("there", "underwear")
          ,("nose", "toes")
  ,("nice", "lice")
  ,("toes", "blows")
          ,("lice", "ice")]

{-
Function for looking up keys k in Lookup Table Dictionary.
Found value v is returned wrapped in a Just.
You could unwrap Maybe with case statements.

rest is rest of Table.

-}

lookup key [] = Nothing   -- Empty String
lookup key ((k, v) : rest) = if key == k then Just v else lookup key rest

{-
No key match default value.
-}

fromMaybe def (Just a) = a
fromMaybe def Nothing = def

{-
getLine can be thought of as a monadic function of type () -> IO String a monadic action which reads a line of text from the terminal, returning the line of text read as a string. However, its type is IO String. 

putStrLn is a function which happens to be in the IO monad and takes a string as input and displays it on the terminal, also outputting a newline character at the end.

-}

main = do
  putStrLn "Type word to rhyme or type exit then press Enter."
  word <- getLine
  if word == "exit"
      then do 
             return ()
      else do  
              let poetry = lookup word rhyme
             print (fromMaybe "Not found! Update Poetry Lookup Table Dictionary!" poetry)
             main    

2. EXAMPLE PROGRAM OUTPUT

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

Prelude>  main
Type word to rhyme or type exit then press Enter.
fleece
"fleas"
Type word to rhyme or type exit then press Enter.
snow
"go"
Type word to rhyme or type exit then press Enter.
exit
Prelude>

3. EXAMPLE POEM

Mary had a little lamb,
its fleas were white as snow.
And everywhere that Mary went,
its fleas were sure to go.

4. lookup AND Maybe a

As you know a lookup table dictionary is a table which relates keys to values. As shown above the lookup function and the Maybe a features work very well with a lookup table dictionary. I was very impressed with how easy it was to create and use a lookup table dictionary.

Please share with us your comments concerning your successful and unsuccessful lookup table dictionary experiences.

5. CONCLUSION

In this tutorial you have been introduced to the Haskell lookup table dictionary.

6. 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.