166 lines
8.5 KiB
Haskell
166 lines
8.5 KiB
Haskell
module TestLexer where
|
|
|
|
import Test.HUnit
|
|
import Lib
|
|
|
|
testPars :: Test
|
|
testPars = TestCase (assertEqual "recognize parentheses"
|
|
[Lib.TokLPar, Lib.TokRPar]
|
|
(lexStr "()"))
|
|
|
|
testSymbol :: Test
|
|
testSymbol = TestCase (assertEqual "recognize symbols"
|
|
[Lib.TokSymbol "hello", Lib.TokSymbol "world"]
|
|
(lexStr "hello world"))
|
|
|
|
testQuotedPars :: Test
|
|
testQuotedPars = TestCase (assertEqual "recognize quoted parentheses"
|
|
[Lib.TokQuote, Lib.TokLPar, Lib.TokRPar]
|
|
(lexStr "'()"))
|
|
|
|
testLoneQuoteIsSymbol :: Test
|
|
testLoneQuoteIsSymbol = TestCase (assertEqual "a quote on its own is just a symbol"
|
|
[Lib.TokSymbol "'", Lib.TokSymbol "'"]
|
|
(lexStr "' '"))
|
|
|
|
testCharacter :: Test
|
|
testCharacter = TestCase (assertEqual "recognize characters"
|
|
[Lib.TokCharacter 'a']
|
|
(lexStr "'a'"))
|
|
|
|
testQuotedSymbol :: Test
|
|
testQuotedSymbol = TestCase (assertEqual "recognize quoted symbols"
|
|
[Lib.TokQuote, Lib.TokSymbol "hello"]
|
|
(lexStr "'hello"))
|
|
|
|
testUnicodeCharacter :: Test
|
|
testUnicodeCharacter = TestCase (assertEqual "recognize unicode characters"
|
|
[Lib.TokCharacter '📎']
|
|
(lexStr "'📎'"))
|
|
|
|
testSimpleIntegers :: Test
|
|
testSimpleIntegers = TestCase (assertEqual "recognize basic integers"
|
|
[Lib.TokNumber 42]
|
|
(lexStr "42\t"))
|
|
|
|
testFractionalNumber :: Test
|
|
testFractionalNumber = TestCase (assertEqual "recognize numbers with fractional components"
|
|
[Lib.TokNumber 42.123]
|
|
(lexStr "42.123 "))
|
|
|
|
testExponentialInteger :: Test
|
|
testExponentialInteger = TestCase (assertEqual "recognize integers with exponents"
|
|
[Lib.TokNumber 42e123]
|
|
(lexStr "42e123\n"))
|
|
|
|
testExponential :: Test
|
|
testExponential = TestCase (assertEqual "recognize fractional numbers with exponents"
|
|
[Lib.TokNumber 42.03e12]
|
|
(lexStr "42.03E+12\r"))
|
|
|
|
testNegativeNumber :: Test
|
|
testNegativeNumber = TestCase (assertEqual "recognize negative numbers"
|
|
[Lib.TokNumber (-42.03e-12)]
|
|
(lexStr "-42.03e-12"))
|
|
|
|
testMalformedNumbersAreSymbols :: Test
|
|
testMalformedNumbersAreSymbols = TestCase (assertEqual "recognize symbols that arise from invalid numbers"
|
|
[Lib.TokSymbol "-", Lib.TokSymbol "123abc", Lib.TokSymbol "-123.01f23"]
|
|
(lexStr "- 123abc -123.01f23"))
|
|
|
|
testStringsAreRecognized :: Test
|
|
testStringsAreRecognized = TestCase (assertEqual
|
|
"recognize strings"
|
|
[Lib.TokStr "\43981asdf\b\f\r\n\t\\/"]
|
|
(lexStr "\"\\uabcdasdf\\b\\f\\r\\n\\t\\\\\\/\""))
|
|
|
|
testUnclosedStringsAreSymbols :: Test
|
|
testUnclosedStringsAreSymbols = TestCase (assertEqual
|
|
"this would make for a terrible symbol, but it can hypothetically start with a double quote"
|
|
[Lib.TokSymbol "\"hello", Lib.TokSymbol "world"]
|
|
(lexStr "\"hello world"))
|
|
|
|
testLexComplexProgram :: Test
|
|
testLexComplexProgram = TestCase (assertEqual
|
|
"lex an entire program"
|
|
[
|
|
Lib.TokLPar,
|
|
Lib.TokSymbol "defun",
|
|
Lib.TokSymbol "pomodoro-toggle-state",
|
|
Lib.TokLPar,
|
|
Lib.TokRPar,
|
|
Lib.TokStr "Restart the pomodoro timer and switch to the other state.",
|
|
Lib.TokLPar,
|
|
Lib.TokSymbol "interactive",
|
|
Lib.TokRPar,
|
|
Lib.TokLPar,
|
|
Lib.TokSymbol "cond",
|
|
Lib.TokLPar,
|
|
Lib.TokLPar,
|
|
Lib.TokSymbol "equal",
|
|
Lib.TokSymbol "pomodoro-state",
|
|
Lib.TokQuote,
|
|
Lib.TokSymbol "working",
|
|
Lib.TokRPar,
|
|
Lib.TokLPar,
|
|
Lib.TokSymbol "setq",
|
|
Lib.TokSymbol "pomodoro-state",
|
|
Lib.TokQuote,
|
|
Lib.TokSymbol "break",
|
|
Lib.TokRPar,
|
|
Lib.TokRPar,
|
|
Lib.TokLPar,
|
|
Lib.TokLPar,
|
|
Lib.TokSymbol "equal",
|
|
Lib.TokSymbol "pomodoro-state",
|
|
Lib.TokQuote,
|
|
Lib.TokSymbol "break",
|
|
Lib.TokRPar,
|
|
Lib.TokLPar,
|
|
Lib.TokSymbol "setq",
|
|
Lib.TokSymbol "pomodoro-state",
|
|
Lib.TokQuote,
|
|
Lib.TokSymbol "working",
|
|
Lib.TokRPar,
|
|
Lib.TokRPar,
|
|
Lib.TokLPar,
|
|
Lib.TokSymbol "t",
|
|
Lib.TokLPar,
|
|
Lib.TokSymbol "user-error",
|
|
Lib.TokStr "Invalid pomodoro state",
|
|
Lib.TokRPar,
|
|
Lib.TokRPar,
|
|
Lib.TokRPar,
|
|
Lib.TokLPar,
|
|
Lib.TokSymbol "setq",
|
|
Lib.TokSymbol "pomodoro-start-time",
|
|
Lib.TokLPar,
|
|
Lib.TokSymbol "floor",
|
|
Lib.TokLPar,
|
|
Lib.TokSymbol "float-time",
|
|
Lib.TokRPar,
|
|
Lib.TokRPar,
|
|
Lib.TokRPar,
|
|
Lib.TokRPar
|
|
]
|
|
(lexStr ";; This is a comment\n(defun pomodoro-toggle-state () ; This is another comment\n\"Restart the pomodoro timer and switch to the other state.\"\n(interactive; a third comment\n)\n(cond ((equal pomodoro-state 'working)\n(setq pomodoro-state 'break))\n((equal pomodoro-state 'break)\n(setq pomodoro-state 'working))\n(t\n(user-error \"Invalid pomodoro state\")))\n(setq pomodoro-start-time (floor (float-time))))"))
|
|
|
|
tests :: Test
|
|
tests = TestList [
|
|
TestLabel "test paretheses are detected" testPars,
|
|
TestLabel "test symbols are recognized" testSymbol,
|
|
TestLabel "test quoted parentheses are detected" testQuotedPars,
|
|
TestLabel "test single quotes without symbols or characters are symbols themselves" testLoneQuoteIsSymbol,
|
|
TestLabel "test characters are recognized" testCharacter,
|
|
TestLabel "test quoted symbols are recognized" testQuotedSymbol,
|
|
TestLabel "test unicode characters are recognized" testUnicodeCharacter,
|
|
TestLabel "test simple integers are recognized" testSimpleIntegers,
|
|
TestLabel "test fractional numbers are recognized" testFractionalNumber,
|
|
TestLabel "test integers with exponential component are recognized" testExponentialInteger,
|
|
TestLabel "test exponential number is recognized" testExponential,
|
|
TestLabel "test negative numbers are recognized" testNegativeNumber,
|
|
TestLabel "test malformed numbers count as symbols" testMalformedNumbersAreSymbols,
|
|
TestLabel "test strings are recognized" testStringsAreRecognized,
|
|
TestLabel "test unclosed strings are symbols" testUnclosedStringsAreSymbols,
|
|
TestLabel "test lexing a complete program" testLexComplexProgram
|
|
]
|