Saturday, March 16, 2013

HASKELL JSON

HASKELL JSON

REVISED: Friday, October 25, 2024




Haskell JSON.

I.  HASKELL JSON

JavaScript Object Notation (JSON) language is a lightweight data-interchange format for storing and transmitting structured data over a network connection.

JSON supports four basic types of value: strings, numbers, booleans, and a special value named null.

A value can be a string in double quotes, or a number, or true or false or null, or an object or an array. These structures can be nested.

A string is a sequence of zero or more Unicode characters, wrapped in double quotes, using backslash escapes. A character is represented as a single character string. A string is very much like a C or Java string. If we want to construct a JSON string, we must provide a String value as an argument to the JString constructor.

A number is very much like a C or Java number, except that the octal and hexadecimal formats are not used.

An array is an ordered collection of values. An array begins with [ left bracket and ends with ] right bracket. Values are separated by , comma.

Whitespace can be inserted between any pair of tokens. Excepting a few encoding details, that completely describes the language.

The language provides two compound types: an array is an ordered sequence of values, and an object is an unordered collection of name value pairs. The names in an object are always strings; the values in an object or array can be of any type.

II.  HASKELL JSON EXAMPLE

A. SAVE HASKELL JSON EXAMPLE

"Copy Paste" the following module into your text editor and "File, Save As" MyJSON.hs to your working directory:

module MyJSON     -- Haskell representation of JSON's types.
        (
           JValue(..)
        ,  getString
        ,  getInt
        ,  getDouble
        ,  getBool
        ,  getObject
        ,  getArray
        ,  isNull
       )  where

data JValue = JString String   -- JString constructor requires String argument.
                    | JNumber Double
                    | JBool Bool
                    | JNull
                    | JObject [(String, JValue)]
                    | JArray [JValue]
                      deriving (Eq, Ord, Show)
 
getString :: JValue -> Maybe String
getString (JString s) = Just s
getString _                = Nothing

getInt (JNumber n) = Just (truncate n)
getInt _                   = Nothing

getDouble (JNumber n) = Just n
getDouble _                   = Nothing

getBool (JBool b) = Just b
getBool _             = Nothing

getObject (JObject o) = Just o
getObject _                 = Nothing

getArray (JArray a) = Just a
getArray _               = Nothing

isNull v                    = v == JNull

B. LOAD HASKELL JSON EXAMPLE

Load the above file MyJSON.hs into GHCi as shown below:

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

C. COMPILE HASKELL JSON EXAMPLE

The -c option tells GHC to only generate object code. If we were to omit the -c option, the compiler would attempt linking, generating a complete executable. That would fail, because we have not written a main function, which GHC calls to start the execution of a standalone program.

Prelude>  :! ghc -c "MyJSON.hs"
Prelude>  

After GHC completes, if we list the contents of the directory, it should contain two new files: MyJSON.hi and MyJSON.o. The former is an interface file, in which GHC stores information about the names exported from our module in machine-readable form. The latter is an object file, which contains the generated machine code.

D. SAVE HASKELL MAIN FUNCTION EXAMPLE

"Copy Paste" the following module into your text editor and "File, Save As" Main.hs to your working directory:

module Main where

import MyJSON     -- GHC will locate MyJSON module in working directory.

main = print (JObject [("Hello", JNumber 1), ("JSON", JBool False)])

E. LOAD HASKELL MAIN FUNCTION EXAMPLE

Load the above module Main.hs  into GHCi as shown below:

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

F. COMPILE HASKELL MAIN FUNCTION EXAMPLE

We are omitting the -c option when we invoke GHC, so it will attempt to link, generate an executable. As our command line suggests, GHC is perfectly able to both compile source files and link an executable in a single invocation.

We pass GHC a new option, -o, which takes one argument: this is the name of the executable, object file, output file, that GHC should create. Here, we have decided to name the program testJSON. On Windows, the program will have the suffix .exe, but on Unix variants there will not be a suffix.

Finally, we supply the name of our new source file, Main.hs.

Prelude>  :! ghc  -o testJSON Main.hs   -- GHC will locate module in working directory.
[2 of 2] Compiling Main             ( Main.hs, Main.o )
Linking testJSON.exe ...
Prelude>  

When compiling, if GHC notices that it has already compiled a source file into an object file, it will only recompile the source file if we have modified it.

G. RUN HASKELL MAIN FUNCTION EXAMPLE

Once GHC has finished compiling and linking our simple program, we can run it from the command line as follows:

Prelude>  :load Main.hs
Ok, modules loaded: Main, MyJSON.
Prelude>

Prelude>  main
JObject [("Hello",JNumber 1.0),("JSON",JBool False)]
it :: ()
Prelude>  

III. CONCLUSION

In this tutorial, you have received an introduction to Haskell JSON.

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


Wednesday, March 13, 2013

HASKELL ALGEBRAIC DATA TYPES

HASKELL ALGEBRAIC DATA TYPES

REVISED: Friday, October 25, 2024




Haskell Algebraic Data Types.

I.  DEFINING YOUR OWN HASKELL DATA TYPES

A Haskell data type is a "record".

data is the keyword used to start a type definition of a new type in Haskell. 

You cannot declare new data types inside functions.

GHCi will print the result of an I/O action if and only if:

1. The result type is an instance of Show.

2. The result type is not ().

Type and data constructor names must always start with a capital letter; variables, including names of functions, must always start with a lowercase letter. Infix symbol "operator" constructors start with a : colon. Having an additional : at the end of an infix symbol "operator" is optional.

In Haskell, the names of types and values are independent of each other. We only use a type constructor; i.e., the type's name in a type declaration or a type signature. We only use a value constructor in actual code. Because these uses are distinct, there is no ambiguity if we give a type constructor and a value constructor the same name. If we are writing a type signature, we must be referring to a type constructor. If we are writing an expression, we must be using the value constructor.

A. DEFINING A NEW DATA TYPE

data (Type constructor) = (Value constructor or data constructor or function name) (type components or fields or function arguments)

It is very important to distinguish between the type constructor and the value constructor. When declaring a data type, the part before the = is the type constructor and the constructors after it, possibly separated by pipes |'s, are value constructors.

Use record syntax when a constructor has several fields and it's not obvious which field is which. 

B. NAMING TYPES AND VALUES

It is legal and normal for a type constructor and a value constructor to have the same name.

C. TYPE SYNONYMS

To give a type a more descriptive name we can introduce a synonym at any time for an existing type. The type keyword introduces a type synonym. The new name is on the left of the = and the existing name is on the right. Type synonyms make code more readable. A type synonym can be used to create a shorter name for a type that has a long name. We still use the same value constructors to create a value of the type.

D. ALGEBRAIC DATA TYPES

Algebraic data types are types that can be modeled using simple algebra, namely addition and multiplication.

All of the data types that we define with the data keyword are algebraic data types.

Algebraic data types correspond to a struct in C or C++, and its components correspond to the fields of a struct. The fields in the Haskell type are anonymous and positional. Algebraic data types are sometimes referred to as enumeration types.

Adding distinct data type declarations will benefit you in both type safety and readability.

An algebraic data type can have more than one value constructor. Each value constructor is separated in the definition by a pipe | character, which can be read as “or”.

We will create the following data class type Shape which can be a Circle or a Rectangle:

data Shape = Circle Float Float Float | Rectangle Float Float Float Float deriving (Show)

The Circle value constructor has three fields, which take floats. When we write a value constructor, we can add types after it and those types define the values, the value constructor, will contain. Here, the first two fields are the coordinates of the center of the circle, the third field is the radius of the circle. 

The Rectangle value constructor has four fields which accept floats. The first two are the coordinates to the upper left corner of the rectangle and the second two are coordinates to the lower right corner of the rectangle.

Value constructors are functions that return a value of a data type.

Prelude>  :type Circle
Circle :: Float -> Float -> Float -> Shape
Prelude>

Prelude>  :type Rectangle
Rectangle :: Float -> Float -> Float -> Float -> Shape
Prelude>  

E. CLASS INSTANCE DECLARATIONS

To derive an instance, the syntax is:

instance «preconditions» => Class «type» where
  «method» = «definition»

The part before the "=>" is the context, while the part after the "=>" is the head of the instance declaration.

A type may not be declared an instance of a particular class more than once in a program.

A type class is a sort of an interface that defines some behavior. A type can be made an instance of a type class if it supports that behavior. First we make our data type and then we think about what it can act like. If it can act like something that can be equated, we make it an instance of the Eq type class. If it can act like something that can be ordered, we make it an instance of the Ord type class. We can make our types instances of type classes by implementing the functions defined by the type classes.

Haskell separates the definition of a type from the definition of the methods associated with that type.

There is no access control, such as public or private class constituents, built into the Haskell class system. Instead, the module system must be used to hide or reveal components of a type class.

With a type class defined, we proceed to make existing types instances of it.

Type classes are not types, but categories of types; therefore, the instances of a type class are not values, but types.

Type synonyms defined with the type keyword cannot be made instances of a type class.

If we add deriving (Show) at the end of a data declaration, Haskell automatically makes that type part of the Show type class.

Haskell can automatically make our type an instance of any of the following type classes: Eq, Ord, Enum, Bounded, Show, Read. Haskell can derive the behavior of our types in these contexts if we use the deriving keyword when making our data type.

1. Eq 

Equality operators == and /=

2. Ord 

Comparison operators < <= > >=; min, max and compare.

In order to declare a type to be an instance of Ord you must already have declared it an instance of Eq in other words Ord is a subclass of Eq.

3. Enum 

For enumerations only. Allows the use of list syntax such as [Blue .. Green].

4. Bounded 

Also for enumerations, but can also be used on types that have only one constructor. Provides minBound and maxBound, the lowest and highest values that the type can take.

5. Show 

Defines the function show, which converts a value into a string, and other related functions.

6. Read 

Defines the function read, which parses a string into a value of the type, and other related functions.

F. KINDS

Types are labels values carry so we can reason about the values. Types have their own labels, called kinds. A kind is the type of a type. We can examine the kind of a type by using the :k command in GHCi.

Prelude>  :kind Int
Int :: *
Prelude>  

A * means that the type kind is a concrete type. A concrete type kind is a type that does not take any type parameters. Values can only have types that are concrete types. A * is pronounced "star" or "type". 

Prelude>  :kind Maybe
Maybe :: * -> *
Prelude>  

The Maybe type constructor takes one concrete type, like Int, and then returns a concrete type like Maybe Int. And that is what its kind tells us. Just like Int -> Int means that a function takes an Int and returns an Int, * -> * means that the type constructor takes one concrete type kind and returns a concrete type kind.

Prelude>  :kind Maybe Int
Maybe Int :: *
Prelude>  

We use :k on a type to get its kind, just like we can use :t on a value to get its type. Types are the labels of values and kinds are the labels of types and there are parallels between the two.

Prelude>  :kind Either
Either :: * -> * -> *
Prelude>

Either takes two concrete type kinds as type parameters to produce a concrete type kind. It looks like a type declaration of a function that takes two values and returns something. Type constructors are curried, just like functions, so we can partially apply them.

Prelude>  :kind Either String 
Either String :: * -> *
Prelude>

Prelude>  :kind Either String Int
Either String Int :: *
Prelude> 

If we wanted to make Either a part of the Functor typeclass, we would have to partially apply it because Functor wants types that take only one parameter while Either takes two. In other words, Functor wants types of kind * -> * and so we would have to partially apply Either to get a type of kind * -> * instead of its original type of kind * -> * -> *.
 
class Functor f where   
    fmap :: (a -> b) -> f a -> f b


The f type variable is used as a type that takes one concrete type kind to produce a concrete type kind. We know it has to produce a concrete type kind because it is used as the type of a value in a function. And from that, we can deduce that, types that want to be friends with Functor, have to be of type kind * -> *.

A class and type must have the same kind.

II. NEWTYPE

newtype is for making a completely new type out of an existing type. A newtype declaration creates a new type in much the same way as dataExcept for the keyword, the newtype declaration uses the same syntax as a data declaration with a single constructor containing a single field. Both newtype and the single constructor data introduce a single value constructor, but the value constructor introduced by newtype is strict and the value constructor introduced by data is lazy.

Types declared with the data keyword are lifted. Haskell provides the newtype keyword, for the construction of unlifted types.

In Haskell, the newtype declaration creates a new type from an existing one. A type created by newtype differs from an algebraic data type in that the representation of an algebraic data type has an extra level of indirection. This difference may make access to the representation less efficient. The difference is reflected in different rules for pattern matching.

When you make a new type from an existing type by using the newtype keyword, you can only have one value constructor and that value constructor can only have one field. But with data, you can make data types that have several value constructors and each constructor can have zero or more fields. Therefore, newtype normally processes faster.

III. CONCLUSION

In this tutorial, you have received an introduction to Haskell algebraic data types.

IV. 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 11, 2013

HASKELL STRINGS AND CHARACTERS

HASKELL STRINGS AND CHARACTERS

REVISED: Friday, February 9, 2024




Haskell Strings and Characters.

I.  HASKELL STRINGS

Because strings are just special kinds of lists, any polymorphic function that operates on lists can also be applied to strings.

A Haskell text string is surrounded by double quotes.

The putStrLn function prints a string.

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

Prelude>  putStrLn "Hello, World!"
Hello, World!
Prelude>  

A text string is a list of individual characters.

Prelude>  let a = ['H', 'e', 'l', 'l', 'o', ',', ' ',  'W', 'o', 'r', 'l', 'd', '!']
Prelude>

Prelude>  a
"Hello, World!"
Prelude>  

Prelude>  :type a
a :: [Char]
Prelude>

The name String is often used instead of [Char] list of characters. String is a synonym or alias for [Char] list of characters.

An empty String is written "", and is a synonym for [].

Regular list operators can be used to construct new strings.

Prelude>  'H' : "askell"
"Haskell"
Prelude>

Haskell's name for the “append” function is (++).  Append is associative. It is more efficient to associate to the right rather than the left. When comparing sequential computing and parallel computing, sequential computing is slower than parallel computing.

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

Prelude>  :t (++)
(++) :: [a] -> [a] -> [a]
Prelude>  

(++) :: [a] -> [a] -> [a]
[] ++ ys        = ys                         -- Empty list.
(x:xs) ++ ys = x : (xs ++ ys))       -- Constructed list.

Prelude>  :t words
words :: String -> [String]
Prelude>

Prelude>  :t unwords
unwords :: [String] -> String
Prelude>

Prelude>  words "Happy birthday little fellow!"
["Happy","birthday","little","fellow!"]
Prelude>

Prelude>  unwords ["Happy","birthday","little","fellow!"]
"Happy birthday little fellow!"
Prelude>  

II.  HASKELL CHARACTERS

A single character is enclosed in single quotes.

A Char value represents a Unicode character.

Prelude>  :info Char
data Char = GHC.Types.C# GHC.Prim.Char# -- Defined in `GHC.Types'
instance Bounded Char -- Defined in `GHC.Enum'
instance Enum Char -- Defined in `GHC.Enum'
instance Eq Char -- Defined in `GHC.Classes'
instance Ord Char -- Defined in `GHC.Classes'
instance Read Char -- Defined in `GHC.Read'
instance Show Char -- Defined in `GHC.Show'
Prelude>  

Haskell represents a text string as a list of Char values, the type “list of Char” is written [Char].

The function rTheyEq has type [Char] and requires two [Char] arguments to create a Bool parameter; however, as shown below the arguments are input as "character strings."

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

import Data.List
import System.IO

rTheyEq :: [Char] -> [Char] -> Bool
rTheyEq [] [] = True
rTheyEq (x:xs) (y:ys) = x == y && rTheyEq xs ys
rTheyEq _ _ = False

Prelude> :l rTheyEq
[1 of 1] Compiling Main            ( rTheyEq.hs, interpreted )

Ok, modules loaded: Main.
Prelude>

Prelude> rTheyEq "Yes" "No"
False
Prelude>

III. HASKELL ESCAPE CHARACTERS

A. \n NEW LINE

Prelude>  putStrLn "Line 1 \nLine 2"
Line 1 
Line 2                                                          -- New line!
Prelude>

unlines takes a list, and returns it interleaved with newlines \n.

Prelude>  unlines ["aa","bb","cc","dd","ee"]
"aa\nbb\ncc\ndd\nee\n"
Prelude>

lines is the reverse of unlines.

Prelude>  lines "aa\nbb\ncc\ndd\nee\n"
["aa","bb","cc","dd","ee"]
Prelude>

B. \t TAB

Prelude>  putStrLn "Line 1\n\tLine 2"
Line 1 
     Line 2                                                    -- New line with a tab.
Prelude>  

IV. HASKELL SHORTCUT

Save the following as sumNQuickCheck.hs

import Test.QuickCheck

prop_sum :: Integer -> Property

prop_sum n = n >= 0 ==> sum [1..n] == n * (n+1) `div` 2

Then open GHCi; import Test.QuickCheck; :load sumNQuickCheck; and run quickCheck prop_sum as shown below:

Prelude>  import Test.QuickCheck
Prelude>

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

Prelude>  quickCheck prop_sum
+++ OK, passed 100 tests.
Prelude>  

The above is QuickCheck's proof that the output of the two functions is the same.

This is an example of asymptotic analysis where a linear function's output is compared to a quadratic function's output. Even though their output is the same; you should always program with linear functions.

V. CONCLUSION

Learning to use Haskell strings and characters will help you all during your career.

VI. 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 4, 2013

HASKELL PARSERS

HASKELL PARSERS

REVISED: Wednesday, January 24, 2024




Haskell Parsers.

I.  HASKELL BASIC PARSER

Almost every program uses some form of parser to pre-process its input. A parser is normally a program that analyses a piece of text to determine its syntactic structure. A parser is also normally a function that takes a string and returns some form of tree. Our first example will be parsing a "comma separated value" (CSV) file. Each line in a CSV file is a record, and each field in the record is separated from the next by a comma. We will work from the following skeleton:

A. FILE

A CSV file contains 0 or more lines, each of which is terminated by the end-of-line character \n.

B. LINE

A line contains 1 or more cells, separated by a comma.

C. CELL

A cell contains 0 or more characters, which must be neither the comma nor the end-of-line character \n.

D. END-OF-LINE

The end-of-line character is the newline, \n

II.  HASKELL PARSEC

You can import the Parsec library which was written by Graham Hutton and Daan Leijen as follows:

Prelude> import Text.ParserCombinators.Parsec
Prelude> 

Parsing is divided into two stages. The first stage is lexical analysis, the domain of tools like Flex. The second stage is parsing itself, performed by programs such as Bison. Both lexical analysis and parsing can be performed by Parsec.

Parsec is a monadic library. Parsec defines its own parsing monad, GenParser.  Parsec provides both simple parsing functions, and helper functions to tie them all together. We will use Parsec's parser library to combine small parsing functions into more sophisticated parsers. 

III.  HASKELL PARSEC EXAMPLE PARSER 1

"Copy Paste" the following csv1 parser example into your text editor and "File, Save As" csv1.hs to your working directory:

-- file: csv1.hs
import Text.ParserCombinators.Parsec

{- A CSV file contains 0 or more lines, each of which is terminated
   by the end-of-line character (eol). -}
csvFile :: GenParser Char st [[String]]   -- First function is csvFile.
csvFile = 
    do result <- many line
       eof
       return result

{- Each line contains 1 or more cells, separated by a comma. -}
line :: GenParser Char st [String]
line = 
    do result <- cells
       eol                       -- end of line
       return result
       
{- Build up a list of cells.  Try to parse the first cell, then figure out 
 what ends the cell. -}
cells :: GenParser Char st [String]
cells = 
    do first <- cellContent
       next <- remainingCells
       return (first : next)

{- The cell either ends with a comma, indicating that 1 or more cells follow,
 or it doesn't, indicating that we are at the end of the cells for this line. -}
remainingCells :: GenParser Char st [String]
remainingCells =
    (char ',' >> cells)            -- Found comma?  More cells coming
    <|> (return [])               -- No comma?  Return [], no more cells

{- Each cell contains 0 or more characters, which must not be a comma or
EOL.  -}
cellContent :: GenParser Char st String
cellContent = 
    many (noneOf ",\n")

{- The end of line character is \n.  -}
eol :: GenParser Char st Char
eol = char '\n'

parseCSV :: String -> Either ParseError [[String]]   -- Function parseCSV.
parseCSV input = parse csvFile "(unknown)" input

IV. HASKELL PARSEC PARSER FUNCTION DEMONSTRATION 1

Open GHCi as shown below:

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> 

Load csv1 into GHCi as follows:

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

Call the function parseCSV without input:

Prelude>  parseCSV ""
Loading package transformers-0.3.0.0 ... linking ... done.
Loading package array-0.5.0.0 ... linking ... done.
Loading package deepseq-1.3.0.2 ... linking ... done.
Loading package bytestring-0.10.4.0 ... linking ... done.
Loading package mtl-2.1.3.1 ... linking ... done.
Loading package text-1.1.0.0 ... linking ... done.
Loading package parsec-3.1.5 ... linking ... done.
Right []
it :: Either ParseError [[String]]
Prelude>

Call the function parseCSV with input:

Prelude>  parseCSV "Hello, World!\n"
Right [["Hello"," World!"]]
it :: Either ParseError [[String]]
Prelude>
  
V.  HASKELL PARSEC EXAMPLE PARSER 2

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

-- file: csv2.hs
import Text.ParserCombinators.Parsec

csvFile = endBy line eol
line = sepBy cell (char ',')
cell = many (noneOf ",\n")
eol = char '\n'

parseCSV :: String -> Either ParseError [[String]]
parseCSV input = parse csvFile "(unknown)" input

VI. HASKELL PARSEC PARSER FUNCTION DEMONSTRATION 2

Load csv2 into GHCi as shown below:

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

Call the function parseCSV without input:

Prelude>  parseCSV ""
Right []
it :: Either ParseError [[String]]
Prelude> 

Call the function parseCSV with input:

Prelude>  parseCSV "Hello, World!\n"
Right [["Hello"," World!"]]
it :: Either ParseError [[String]]
Prelude>  
  
VII.  HASKELL PARSEC EXAMPLE PARSER 3

"Copy Paste" the following example into your text editor and then "File, Save As" csv3.hs to your working directory:

-- file: csv3.hs
import Text.ParserCombinators.Parsec

csvFile = endBy line eol
line = sepBy cell (char ',')
cell = quotedCell <|> many (noneOf ",\n\r")

quotedCell = 
    do char '"'
       content <- many quotedChar
       char '"' <?> "quote at end of cell"
       return content

quotedChar =
        noneOf "\""
    <|> try (string "\"\"" >> return '"')

eol =   try (string "\n\r")
    <|> try (string "\r\n")
    <|> string "\n"
    <|> string "\r"
    <?> "end of line"

parseCSV :: String -> Either ParseError [[String]]
parseCSV input = parse csvFile "(unknown)" input

main =
    do c <- getContents
       case parse csvFile "(stdin)" c of
            Left e -> do putStrLn "Error parsing input:"
                         print e
            Right r -> mapM_ print r

VIII. HASKELL PARSEC PARSER FUNCTION DEMONSTRATION 3

Load csv3 into GHCi as shown below:

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

Call parseCSV without input:

Prelude>  parseCSV "\n"
Right [[""]]
Prelude>

Call parseCSV with correctly formatted input:

Prelude>  parseCSV "Hello, World!\n"
Right [["Hello"," World!"]]
Prelude>

Call parseCSV with incorrectly formatted input:

Prelude>  parseCSV "Hello, World!"
Left "(unknown)" (line 1, column 14):
unexpected end of input
expecting "," or end of line
Prelude>

Call parseCSV with correctly formatted input:

Prelude>  parseCSV "NA,NA\n"
Right [["NA","NA"]]
Prelude>  

IX. CONCLUSION

This tutorial has given you an introduction to the Haskell parsec parser function!

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