Skip to content
This repository has been archived by the owner on Feb 2, 2019. It is now read-only.

Commit

Permalink
add unit tests for all Frege modules
Browse files Browse the repository at this point in the history
otherwise gradle build will fail due to Frege/frege-gradle-plugin#39
  • Loading branch information
mabre committed Sep 10, 2017
1 parent 28c41ae commit 796daf7
Show file tree
Hide file tree
Showing 10 changed files with 80 additions and 16 deletions.
12 changes: 0 additions & 12 deletions cliparser/src/test/java/DummyTest.java

This file was deleted.

Original file line number Diff line number Diff line change
@@ -0,0 +1,10 @@
module Language.CSPM.UnicodeSymbolsTest
where

import Test.QuickCheck

import Data.Maybe
import Language.CSPM.UnicodeSymbols

test :: Property
test = once $ lookupDefaultSymbol (fromJust $ lookupToken '') == Just ('', "<->")
Original file line number Diff line number Diff line change
@@ -0,0 +1,10 @@
module Language.CSPM.VersionTest
where

import Test.QuickCheck

import Language.CSPM.TranslateToProlog
import Data.Version

test :: Property
test = once $ showVersion toPrologVersion == "0.6.1.1"
5 changes: 1 addition & 4 deletions cspmparser/CSPM-cspm-frontend-java/build.gradle
Original file line number Diff line number Diff line change
@@ -1,7 +1,4 @@
plugins {
id "org.frege-lang" version "0.8"
}

apply plugin: 'java'
apply plugin: 'maven-publish'
apply plugin: 'application'

Expand Down
11 changes: 11 additions & 0 deletions cspmparser/CSPM-cspm-frontend/src/test/frege/Main/VersionTest.fr
Original file line number Diff line number Diff line change
@@ -0,0 +1,11 @@
module Main.ExecCommandTest

where

import Test.QuickCheck

import Main.ExecCommand
import Data.Version

test :: Property
test = once $ showVersion cmdVersion == "0.1.0.0"
8 changes: 8 additions & 0 deletions cspmparser/Data/src/test/frege/Data/SetTest.fr
Original file line number Diff line number Diff line change
@@ -0,0 +1,8 @@
package frege.data.SetTest where

import Test.QuickCheck

import frege.data.Set

singletonTest :: Property
singletonTest = once $ insert 1 empty == singleton 1
Original file line number Diff line number Diff line change
@@ -0,0 +1,22 @@
module Text.ParserCombinators.Parsec.ParsecText where

import Test.QuickCheck

import Text.ParserCombinators.Parsec.Parsec
import Text.ParserCombinators.Parsec.Token
import Text.ParserCombinators.Parsec.Language

csvLine :: Parser [String]
csvLine = csvCell `sepBy` (haskell.comma)

csvCell :: Parser String
csvCell = do
cell <- many $ noneOf ",\n"
return $ packed cell

parseCsvLine :: String -> Either ParseError [String]
parseCsvLine str = parse csvLine "" (unpacked str)

test :: Property
test = let Right result = parseCsvLine "Foo,Bar" in
once $ result == ["Foo", "Bar"]
5 changes: 5 additions & 0 deletions cspmparser/PrettyPrint/src/test/frege/dummy.fr
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
module Text where

import Test.QuickCheck

-- only here so that gradle build does not fail (https://github.com/Frege/frege-gradle-plugin/issues/39)
8 changes: 8 additions & 0 deletions cspmparser/State/src/test/frege/Control/Monad/StateTest.fr
Original file line number Diff line number Diff line change
@@ -0,0 +1,8 @@
module Text.XML.Light.Test where

import Test.QuickCheck

import frege.control.monad.MState

simpleTest :: Property
simpleTest = once $ runState (return 'X') 1 == ('X', 1)
5 changes: 5 additions & 0 deletions cspmparser/XmlLight/src/test/frege/dummy.fr
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
module Text.XML.Light.Test where

import Test.QuickCheck

-- only here so that gradle build does not fail (https://github.com/Frege/frege-gradle-plugin/issues/39)

0 comments on commit 796daf7

Please sign in to comment.