Rewrite field structure

This commit is contained in:
Anton Vakhrushev 2017-11-18 12:31:08 +03:00
parent 224af7a801
commit 80b8003da4
3 changed files with 61 additions and 113 deletions

View File

@ -7,103 +7,64 @@ import Data.Char (isDigit)
import Data.Maybe import Data.Maybe
import Helper import Helper
data Range data Field
= All = Range Int
| Range Int Int
Int Int
| Sequence [Int] | Sequence [Int]
deriving (Eq, Show) deriving (Eq, Show)
data Step
= Every
| Step Int
deriving (Eq, Show)
data Field =
Field Range
Step
deriving (Eq, Show)
parseField :: String -> Constraint -> Maybe Field parseField :: String -> Constraint -> Maybe Field
parseField text = parseField' (wordsWhen (== '/') text) parseField text constraint
| isJust valueSequence = valueSequence
parseField' :: [String] -> Constraint -> Maybe Field | isJust valueRange = valueRange
parseField' [rangeText] constraint
| isJust range = Just (Field (fromJust range) Every)
| otherwise = Nothing | otherwise = Nothing
where where
range = parseFieldRange rangeText constraint valueRange = parseRange (splitRange text) constraint
parseField' [rangeText, stepText] constraint
| isJust range && isJust step = Just (Field (fromJust range) (fromJust step))
| otherwise = Nothing
where
range = parseFieldRange rangeText constraint
step = parseFieldStep stepText
parseField' _ _ = Nothing
parseFieldRange :: String -> Constraint -> Maybe Range
parseFieldRange text constraint
| text == "*" = Just All
| isJust number = Just (Range (fromJust number) (fromJust number))
| isJust range = Just (uncurry Range (fromJust range))
| isJust valueSequence = fmap Sequence valueSequence
| otherwise = Nothing
where
number = parseNumber text constraint
range = parseRange text constraint
valueSequence = parseSequence text constraint valueSequence = parseSequence text constraint
splitRange :: String -> [String]
splitRange text = take 2 $ wordsWhen (== '/') text ++ ["", ""]
isNumber :: String -> Bool isNumber :: String -> Bool
isNumber = all isDigit isNumber "" = False
isNumber text = all isDigit text
parseNumber :: String -> Constraint -> Maybe Int parseRange :: [String] -> Constraint -> Maybe Field
parseNumber text constraint parseRange [interval, step] constraint = do
| isValid = Just number (from, to) <- parseInterval interval constraint
| otherwise = Nothing step' <- parseStep step
where return (Range from to step')
number = read text :: Int parseRange _ _ = Nothing
isValid = isNumber text && number `inRange` constraint
parseRange :: String -> Constraint -> Maybe (Int, Int) parseInterval :: String -> Constraint -> Maybe (Int, Int)
parseRange text constraint parseInterval "*" (Constraint lo up) = Just (lo, up)
parseInterval text constraint
| isValid = Just (start, end) | isValid = Just (start, end)
| otherwise = Nothing | otherwise = Nothing
where where
pieces = wordsWhen (== '-') text pieces = take 2 $ wordsWhen (== '-') text ++ ["", ""]
isTwo = length pieces == 2 isNumbers = all isNumber pieces
isAllNumbers = all isNumber pieces [start, end] = map read pieces
start = read (head pieces) :: Int isValid = isNumbers && start <= end && (start, end) `inside` constraint
end = read (pieces !! 1) :: Int
isValid =
isTwo &&
isAllNumbers && start <= start && (start, end) `inside` constraint
parseSequence :: String -> Constraint -> Maybe [Int] parseStep :: String -> Maybe Int
parseStep "" = Just 1
parseStep text
| isNumber text = Just (read text)
parseStep _ = Nothing
parseSequence :: String -> Constraint -> Maybe Field
parseSequence text constraint parseSequence text constraint
| isValid = Just numbers | isValid = Just (Sequence numbers)
| otherwise = Nothing | otherwise = Nothing
where where
pieces = wordsWhen (== ',') text pieces = wordsWhen (== ',') text
isAllNumbers = all isNumber pieces isNumbers = all isNumber pieces
numbers = map read pieces numbers = map read pieces
allInRange = all (`inRange` constraint) numbers allInRange = all (`inRange` constraint) numbers
isValid = length pieces >= 2 && isAllNumbers && allInRange isValid = not (null pieces) && isNumbers && allInRange
parseFieldStep :: String -> Maybe Step
parseFieldStep "" = Just Every
parseFieldStep text
| isNumber text = Just (Step (read text))
parseFieldStep _ = Nothing
matchField :: Field -> Int -> Bool matchField :: Field -> Int -> Bool
matchField (Field range step) n = matchField (Range f t s) n = n >= f && n <= t && n `mod` s == 0
matchFieldRange range n && matchFieldStep step n matchField (Sequence xs) n = n `elem` xs
matchFieldRange :: Range -> Int -> Bool
matchFieldRange All _ = True
matchFieldRange (Range x y) n = n >= x && n <= y
matchFieldRange (Sequence xs) n = n `elem` xs
matchFieldStep :: Step -> Int -> Bool
matchFieldStep Every _ = True
matchFieldStep (Step x) n = n `mod` x == 0

View File

@ -13,49 +13,36 @@ main = hspec spec
spec :: Spec spec :: Spec
spec = do 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 "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])
-- 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)
describe "Step cant'b created from" $
it "word" $ parseFieldStep "hello" `shouldBe` Nothing
-- Field validation
describe "Field can be created from" $ do describe "Field can be created from" $ do
it "asterisk" $ it "asterisk" $
parseField "*" (Constraint 0 59) `shouldBe` Just (Field All Every) parseField "*" (Constraint 0 59) `shouldBe` Just (Range 0 59 1)
it "asterisk" $
parseField "*" (Constraint 0 0) `shouldBe` Just (Range 0 0 1)
it "asterisk with step" $ it "asterisk with step" $
parseField "*/5" (Constraint 0 59) `shouldBe` Just (Field All (Step 5)) parseField "*/5" (Constraint 0 59) `shouldBe` Just (Range 0 59 5)
it "number with step" $ it "number" $
parseField "10/5" (Constraint 0 59) `shouldBe` parseField "10" (Constraint 0 10) `shouldBe` Just (Sequence [10])
Just (Field (Range 10 10) (Step 5)) it "range" $
parseField "10-20" (Constraint 0 59) `shouldBe` Just (Range 10 20 1)
it "range with step" $ it "range with step" $
parseField "0-59/5" (Constraint 0 59) `shouldBe` parseField "0-59/5" (Constraint 0 59) `shouldBe` Just (Range 0 59 5)
Just (Field (Range 0 59) (Step 5)) it "sequence" $
parseField "1,2,3" (Constraint 0 59) `shouldBe` Just (Sequence [1, 2, 3])
-- Field negative cases
describe "Field can't be created from" $ do
it "number with step" $
parseField "10/5" (Constraint 0 59) `shouldBe` Nothing
it "sequence with step" $ it "sequence with step" $
parseField "1,3,4/5" (Constraint 0 59) `shouldBe` parseField "1,3,4/5" (Constraint 0 59) `shouldBe` Nothing
Just (Field (Sequence [1, 3, 4]) (Step 5)) it "can't be parsed from string" $
parseField "10and10" (Constraint 0 10) `shouldBe` Nothing
it "failed constraints" $
parseField "10" (Constraint 0 5) `shouldBe` Nothing
-- Field match -- Field match
describe "Field can match" $ do describe "Field can match" $ do
it "number" $ count (Field All Every) [0 .. 59] `shouldBe` 60 it "number" $ count (Range 0 59 1) [0 .. 59] `shouldBe` 60
it "range" $ count (Field (Range 10 20) Every) [0 .. 59] `shouldBe` 11 it "range" $ count (Range 10 20 1) [0 .. 59] `shouldBe` 11
it "range" $ count (Field All (Step 10)) [0 .. 59] `shouldBe` 6 it "range" $ count (Range 0 59 10) [0 .. 59] `shouldBe` 6
count :: Field -> [Int] -> Int count :: Field -> [Int] -> Int
count field values = sum $ map m values count field values = sum $ map m values