Skip to content

Commit

Permalink
Add parsers for test tables (#45)
Browse files Browse the repository at this point in the history
* Create base for customers parser

* Define types for Customer

* Write parser for Customer table

* Add parser for invoices table
  • Loading branch information
MatBon01 authored May 5, 2023
1 parent 6333d79 commit a7125e4
Show file tree
Hide file tree
Showing 7 changed files with 142 additions and 4 deletions.
14 changes: 10 additions & 4 deletions a-deeper-dive-into-relational-algebra-by-way-of-adjunctions.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,9 @@ library
Data.PointedSet,
Data.Key,
Database.Bag,
Database.IndexedTable
Database.IndexedTable,
Text.Parser.Customers,
Text.Parser.Invoices

-- Modules included in this library but not exported.
other-modules:
Expand All @@ -39,7 +41,8 @@ library
FlexibleInstances
build-depends:
base >=4.16.4.0,
array >= 0.5.4.0
array >= 0.5.4.0,
parsec >= 0.3.1.15
hs-source-dirs: src
default-language: Haskell2010

Expand Down Expand Up @@ -70,10 +73,13 @@ test-suite spec
Data.PointedSetSpec,
Data.KeySpec,
Database.BagSpec,
Database.IndexedTableSpec
Database.IndexedTableSpec,
Text.Parser.CustomersSpec,
Text.Parser.InvoicesSpec
build-depends:
base >=4.16.4.0,
hspec ^>=2.10,
a-deeper-dive-into-relational-algebra-by-way-of-adjunctions,
array >= 0.5.4.0
array >= 0.5.4.0,
parsec >= 0.3.1.15
build-tool-depends: hspec-discover:hspec-discover == 2.*
39 changes: 39 additions & 0 deletions src/Text/Parser/Customers.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,39 @@
module Text.Parser.Customers where

import Text.ParserCombinators.Parsec
import Data.Bag

type Identifier = Int
type Name = String
data Customer = C { cid :: Identifier, name :: Name } deriving (Show, Eq)

csvFile :: GenParser Char st (Bag Customer)
csvFile = do
result <- many record
eof
return (Bag result)

record :: GenParser Char st Customer
record = do
id <- cidCell
separator
name <- nameCell
eol
return (C id name)

cidCell :: GenParser Char st Identifier
cidCell = do
id <- many digit
return (read id)

nameCell :: GenParser Char st Name
nameCell = many (noneOf ",\n")

separator :: GenParser Char st Char
separator = char ','

eol :: GenParser Char st Char
eol = char '\n'

parseCSV :: String -> Either ParseError (Bag Customer)
parseCSV input = parse csvFile "(unknown)" input
56 changes: 56 additions & 0 deletions src/Text/Parser/Invoices.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,56 @@
module Text.Parser.Invoices where

import Text.ParserCombinators.Parsec
import Data.Bag

type Identifier = Int
type Date = Int
type Amount = Int

data Invoice = I
{ iid :: Identifier
, cust :: Identifier
, due :: Date
, amount :: Amount} deriving (Show, Eq)

csvFile :: GenParser Char st (Bag Invoice)
csvFile = do
result <- many invoiceRecord
eof
return (Bag result)

invoiceRecord :: GenParser Char st Invoice
invoiceRecord = do
iidCell <- identifier
separator
custIdCell <- identifier
separator
dueCell <- date
separator
amountCell <- price
eol
return (I iidCell custIdCell dueCell amountCell)

identifier :: GenParser Char st Identifier
identifier = do
id <- many digit
return (read id)

price :: GenParser Char st Amount
price = do
id <- many digit
return (read id)

date :: GenParser Char st Date
date = do
id <- many digit
return (read id)

separator :: GenParser Char st Char
separator = char ','

eol :: GenParser Char st Char
eol = char '\n'

parseCSV :: String -> Either ParseError (Bag Invoice)
parseCSV input = parse csvFile "(unknown)" input
16 changes: 16 additions & 0 deletions test/Text/Parser/CustomersSpec.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,16 @@
module Text.Parser.CustomersSpec where

import Test.Hspec
import Text.Parser.Customers
import Data.Bag as Bag
import Text.ParserCombinators.Parsec
import Data.Either

expectedOutput = Bag [C 1 "John", C 2 "Kayla"]

spec :: Spec
spec = do
describe "parseCSV" $ do
it "can correctly parse the example" $ do
testFile <- readFile "test/Text/Parser/customertest.csv"
fromRight Bag.empty (parseCSV testFile) `shouldBe` expectedOutput
16 changes: 16 additions & 0 deletions test/Text/Parser/InvoicesSpec.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,16 @@
module Text.Parser.InvoicesSpec where

import Test.Hspec
import Text.Parser.Invoices
import Data.Bag as Bag
import Text.ParserCombinators.Parsec
import Data.Either

expectedOutput = Bag [I 10 1 20160101 10, I 11 1 20160102 83, I 12 2 20160103 15]

spec :: Spec
spec = do
describe "parseCSV" $ do
it "can correctly parse the example" $ do
testFile <- readFile "test/Text/Parser/invoicestest.csv"
fromRight Bag.empty (parseCSV testFile) `shouldBe` expectedOutput
2 changes: 2 additions & 0 deletions test/Text/Parser/customertest.csv
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
1,John
2,Kayla
3 changes: 3 additions & 0 deletions test/Text/Parser/invoicestest.csv
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
10,1,20160101,10
11,1,20160102,83
12,2,20160103,15

0 comments on commit a7125e4

Please sign in to comment.