Format source code
This commit is contained in:
@ -1,19 +1,18 @@
|
||||
module ConstraintSpec (main, spec) where
|
||||
module ConstraintSpec
|
||||
( main
|
||||
, spec
|
||||
) where
|
||||
|
||||
import Test.Hspec
|
||||
|
||||
import Constraint
|
||||
import Constraint
|
||||
import Test.Hspec
|
||||
|
||||
main :: IO ()
|
||||
main = hspec spec
|
||||
|
||||
spec :: Spec
|
||||
spec = describe "Constraint" $ do
|
||||
it "can be created from number" $
|
||||
makeRangeFromNumber 10 `shouldBe` Constraint 10 10
|
||||
|
||||
it "validate number" $
|
||||
10 `inRange` Constraint 0 10 `shouldBe` True
|
||||
|
||||
it "validate number" $
|
||||
10 `inRange` Constraint 15 20 `shouldBe` False
|
||||
spec =
|
||||
describe "Constraint" $ do
|
||||
it "can be created from number" $
|
||||
makeRangeFromNumber 10 `shouldBe` Constraint 10 10
|
||||
it "validate number" $ 10 `inRange` Constraint 0 10 `shouldBe` True
|
||||
it "validate number" $ 10 `inRange` Constraint 15 20 `shouldBe` False
|
||||
|
@ -1,9 +1,12 @@
|
||||
module FieldSpec (main, spec) where
|
||||
module FieldSpec
|
||||
( main
|
||||
, spec
|
||||
) where
|
||||
|
||||
import Foreign.Marshal.Utils (fromBool)
|
||||
import Test.Hspec
|
||||
import Constraint
|
||||
import Field
|
||||
import Constraint
|
||||
import Field
|
||||
import Foreign.Marshal.Utils (fromBool)
|
||||
import Test.Hspec
|
||||
|
||||
main :: IO ()
|
||||
main = hspec spec
|
||||
@ -13,72 +16,48 @@ spec = do
|
||||
describe "Number" $ do
|
||||
it "can be parsed from string" $
|
||||
parseNumber "10" (Constraint 0 10) `shouldBe` Just 10
|
||||
|
||||
it "can't be parsed from string" $
|
||||
parseNumber "10and10" (Constraint 0 10) `shouldBe` Nothing
|
||||
|
||||
it "fails constraints" $
|
||||
parseNumber "10" (Constraint 0 5) `shouldBe` Nothing
|
||||
|
||||
-- Field validation
|
||||
|
||||
describe "Field Range can be created from" $ do
|
||||
it "asterisk" $
|
||||
parseFieldRange "*" (Constraint 0 0) `shouldBe` Just All
|
||||
|
||||
it "asterisk" $ parseFieldRange "*" (Constraint 0 0) `shouldBe` Just All
|
||||
it "number" $
|
||||
parseFieldRange "10" (Constraint 0 10) `shouldBe` Just (Range 10 10)
|
||||
|
||||
it "range" $
|
||||
parseFieldRange "10-20" (Constraint 0 59) `shouldBe` Just (Range 10 20)
|
||||
|
||||
it "sequence" $
|
||||
parseFieldRange "1,2,3" (Constraint 0 59) `shouldBe` Just (Sequence [1, 2, 3])
|
||||
|
||||
parseFieldRange "1,2,3" (Constraint 0 59) `shouldBe`
|
||||
Just (Sequence [1, 2, 3])
|
||||
-- Field Step validation
|
||||
|
||||
describe "Step can be created from" $ do
|
||||
it "empty string" $
|
||||
parseFieldStep "" `shouldBe` Just Every
|
||||
|
||||
it "number" $
|
||||
parseFieldStep "5" `shouldBe` Just (Step 5)
|
||||
|
||||
it "empty string" $ parseFieldStep "" `shouldBe` Just Every
|
||||
it "number" $ parseFieldStep "5" `shouldBe` Just (Step 5)
|
||||
describe "Step cant'b created from" $ do
|
||||
it "word" $
|
||||
parseFieldStep "hello" `shouldBe` Nothing
|
||||
|
||||
it "word" $ parseFieldStep "hello" `shouldBe` Nothing
|
||||
-- Field validation
|
||||
|
||||
describe "Field can be created from" $ do
|
||||
it "asterisk" $
|
||||
parseField "*" (Constraint 0 59) `shouldBe` Just (Field All Every)
|
||||
|
||||
it "asterisk with step" $ do
|
||||
parseField "*/5" (Constraint 0 59) `shouldBe` Just (Field All (Step 5))
|
||||
|
||||
it "number with step" $ do
|
||||
parseField "10/5" (Constraint 0 59) `shouldBe` Just (Field (Range 10 10) (Step 5))
|
||||
|
||||
parseField "10/5" (Constraint 0 59) `shouldBe`
|
||||
Just (Field (Range 10 10) (Step 5))
|
||||
it "range with step" $ do
|
||||
parseField "0-59/5" (Constraint 0 59) `shouldBe` Just (Field (Range 0 59) (Step 5))
|
||||
|
||||
parseField "0-59/5" (Constraint 0 59) `shouldBe`
|
||||
Just (Field (Range 0 59) (Step 5))
|
||||
it "sequence with step" $ do
|
||||
parseField "1,3,4/5" (Constraint 0 59) `shouldBe` Just (Field (Sequence [1, 3, 4]) (Step 5))
|
||||
|
||||
parseField "1,3,4/5" (Constraint 0 59) `shouldBe`
|
||||
Just (Field (Sequence [1, 3, 4]) (Step 5))
|
||||
-- Field match
|
||||
|
||||
describe "Field can match" $ do
|
||||
it "number" $
|
||||
count (Field All Every) [0..59] `shouldBe` 60
|
||||
|
||||
it "range" $
|
||||
count (Field (Range 10 20) Every) [0..59] `shouldBe` 11
|
||||
|
||||
it "range" $
|
||||
count (Field All (Step 10)) [0..59] `shouldBe` 6
|
||||
|
||||
it "number" $ count (Field All Every) [0 .. 59] `shouldBe` 60
|
||||
it "range" $ count (Field (Range 10 20) Every) [0 .. 59] `shouldBe` 11
|
||||
it "range" $ count (Field All (Step 10)) [0 .. 59] `shouldBe` 6
|
||||
|
||||
count :: Field -> [Int] -> Int
|
||||
count field values = sum $ map m values
|
||||
where m = fromBool . matchField field
|
||||
where
|
||||
m = fromBool . matchField field
|
||||
|
@ -1,21 +1,20 @@
|
||||
module HelperSpec (main, spec) where
|
||||
module HelperSpec
|
||||
( main
|
||||
, spec
|
||||
) where
|
||||
|
||||
import Test.Hspec
|
||||
import Helper
|
||||
import Helper
|
||||
import Test.Hspec
|
||||
|
||||
main :: IO ()
|
||||
main = hspec spec
|
||||
|
||||
spec :: Spec
|
||||
spec = describe "Splitting" $ do
|
||||
it "can process empty string" $
|
||||
wordsWhen (== '-') "" `shouldBe` []
|
||||
|
||||
it "can process only one word" $
|
||||
wordsWhen (== '-') "10" `shouldBe` ["10"]
|
||||
|
||||
it "can separated by '-'" $
|
||||
wordsWhen (== '-') "10-20" `shouldBe` ["10", "20"]
|
||||
|
||||
it "can be separated by ','" $
|
||||
wordsWhen (== ',') "10,20,30" `shouldBe` ["10", "20", "30"]
|
||||
spec =
|
||||
describe "Splitting" $ do
|
||||
it "can process empty string" $ wordsWhen (== '-') "" `shouldBe` []
|
||||
it "can process only one word" $ wordsWhen (== '-') "10" `shouldBe` ["10"]
|
||||
it "can separated by '-'" $
|
||||
wordsWhen (== '-') "10-20" `shouldBe` ["10", "20"]
|
||||
it "can be separated by ','" $
|
||||
wordsWhen (== ',') "10,20,30" `shouldBe` ["10", "20", "30"]
|
||||
|
@ -1,9 +1,11 @@
|
||||
module PatternSpec (main, spec) where
|
||||
module PatternSpec
|
||||
( main
|
||||
, spec
|
||||
) where
|
||||
|
||||
import Test.Hspec
|
||||
import Data.Dates
|
||||
|
||||
import Pattern
|
||||
import Data.Dates
|
||||
import Pattern
|
||||
import Test.Hspec
|
||||
|
||||
main :: IO ()
|
||||
main = hspec spec
|
||||
@ -11,33 +13,24 @@ main = hspec spec
|
||||
spec :: Spec
|
||||
spec = do
|
||||
describe "Cron pattern" $ do
|
||||
|
||||
it "createParts" $
|
||||
length (createParts "* * * * * *") `shouldBe` 6
|
||||
|
||||
it "createParts" $ length (createParts "* * * * * *") `shouldBe` 6
|
||||
it "matches fixed time" $
|
||||
let
|
||||
ptn = "* * * * * *"
|
||||
date = DateTime 2017 10 11 0 0 0
|
||||
in
|
||||
match ptn date `shouldBe` True
|
||||
|
||||
let ptn = "* * * * * *"
|
||||
date = DateTime 2017 10 11 0 0 0
|
||||
in match ptn date `shouldBe` True
|
||||
it "matches all minutes" $
|
||||
let
|
||||
ptn = "* * * * * *"
|
||||
dates = [DateTime 2017 10 11 0 i 0 | i <- [0..59]]
|
||||
in
|
||||
countMatches ptn dates `shouldBe` 60
|
||||
|
||||
let ptn = "* * * * * *"
|
||||
dates = [DateTime 2017 10 11 0 i 0 | i <- [0 .. 59]]
|
||||
in countMatches ptn dates `shouldBe` 60
|
||||
it "matches exactly moment" $
|
||||
let
|
||||
date = DateTime 2017 10 11 0 0 0
|
||||
ptn = "0 0 11 10 * 2017"
|
||||
in
|
||||
match ptn date `shouldBe` True
|
||||
|
||||
let date = DateTime 2017 10 11 0 0 0
|
||||
ptn = "0 0 11 10 * 2017"
|
||||
in match ptn date `shouldBe` True
|
||||
|
||||
countMatches :: String -> [DateTime] -> Int
|
||||
countMatches p xs = sum $ map (f p) xs
|
||||
where
|
||||
f x d = if match x d then 1 else 0
|
||||
f x d =
|
||||
if match x d
|
||||
then 1
|
||||
else 0
|
||||
|
Reference in New Issue
Block a user