Skip to content

Commit

Permalink
Fix BgSize Eq instance, polish test imports
Browse files Browse the repository at this point in the history
  • Loading branch information
contivero committed Mar 10, 2017
1 parent a5ec30e commit 4a070a1
Show file tree
Hide file tree
Showing 20 changed files with 113 additions and 109 deletions.
2 changes: 1 addition & 1 deletion hasmin.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -68,14 +68,14 @@ library
, Hasmin.Types.Position
, Hasmin.Types.BgSize
, Hasmin.Utils
, Hasmin.Types.TimingFunction
other-modules: Hasmin.Parser.Utils
, Hasmin.Properties
, Hasmin.Types.Selector
, Hasmin.Types.Gradient
, Hasmin.Types.PercentageLength
, Hasmin.Types.Shadow
, Hasmin.Types.String
, Hasmin.Types.TimingFunction
build-depends: base >=4.9 && <5.1
, attoparsec >=0.12 && <0.14
, bytestring >=0.10.2.0 && <0.11
Expand Down
25 changes: 13 additions & 12 deletions src/Hasmin/Types/BgSize.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,8 +8,8 @@
-- Portability : non-portable
--
-----------------------------------------------------------------------------
module Hasmin.Types.BgSize
( BgSize(..)
module Hasmin.Types.BgSize (
BgSize(..)
, Auto(..)
) where

Expand All @@ -32,14 +32,16 @@ data BgSize = Cover
deriving Show

instance Eq BgSize where
Cover == Cover = True
Contain == Contain = True
BgSize a b == BgSize c d = fstParamEquality a c && b `equals` d
where equals (Just (Right Auto)) Nothing = True
equals Nothing (Just (Right Auto)) = True
equals x y = x == y
fstParamEquality (Left x) (Left y) = isZero x && isZero y || x == y
fstParamEquality x y = x == y
Cover == Cover = True
Contain == Contain = True
BgSize a b == BgSize c d = ftsArgEq a c && b `equals` d
where equals (Just (Right Auto)) Nothing = True
equals Nothing (Just (Right Auto)) = True
equals (Just (Left x)) (Just (Left y)) = isZero x && isZero y || x == y
equals x y = x == y
ftsArgEq (Left x) (Left y) = isZero x && isZero y || x == y
ftsArgEq x y = x == y
_ == _ = False

instance ToText BgSize where
toBuilder Cover = "cover"
Expand All @@ -55,11 +57,10 @@ instance Minifiable BgSize where
pure $ if True {- shouldMinifyBgSize conf -}
then minifyBgSize b
else b
where minFirst (Left a) = Left <$> minifyWith a
where minFirst (Left a) = Left <$> minifyWith a
minFirst (Right Auto) = pure (Right Auto)
minifyWith x = pure x

minifyBgSize :: BgSize -> BgSize
minifyBgSize (BgSize l (Just (Right Auto))) = BgSize l Nothing
minifyBgSize x = x

4 changes: 2 additions & 2 deletions src/Hasmin/Types/FilterFunction.hs
Original file line number Diff line number Diff line change
Expand Up @@ -51,8 +51,8 @@ instance Eq FilterFunction where
HueRotate a == HueRotate b = a == b
DropShadow a b c d == DropShadow e f g h =
a == e && b == f && d == h && c `thirdValueEq` g
where thirdValueEq Nothing (Just (Distance 0 PX)) = True
thirdValueEq (Just (Distance 0 PX)) Nothing = True
where thirdValueEq Nothing (Just (Distance 0 _)) = True
thirdValueEq (Just (Distance 0 _)) Nothing = True
thirdValueEq x y = x == y
_ == _ = False
instance ToText FilterFunction where
Expand Down
22 changes: 14 additions & 8 deletions src/Hasmin/Types/TimingFunction.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,8 @@
--
-----------------------------------------------------------------------------
module Hasmin.Types.TimingFunction (
TimingFunction(..), StepsSecondParam(..)
TimingFunction(..)
, StepsSecondParam(..)
) where

import Control.Monad.Reader (ask)
Expand All @@ -29,8 +30,13 @@ import Hasmin.Types.Numeric
-- 3. <https://developer.mozilla.org/en-US/docs/Web/CSS/timing-function Mozilla summary>
data TimingFunction = CubicBezier Number Number Number Number
| Steps Int (Maybe StepsSecondParam)
| Ease | EaseIn | EaseInOut | EaseOut
| Linear | StepEnd | StepStart
| Ease
| EaseIn
| EaseInOut
| EaseOut
| Linear
| StepEnd
| StepStart
deriving (Show)

instance Eq TimingFunction where
Expand Down Expand Up @@ -66,12 +72,12 @@ toSteps StepStart = Just $ Steps 1 (Just Start)
toSteps _ = Nothing


data StepsSecondParam = Start | End -- End is the default value
data StepsSecondParam = Start
| End -- End is the default value
deriving (Eq, Show)
instance ToText StepsSecondParam where
toBuilder Start = "start"
toBuilder End = "end"

instance ToText TimingFunction where
toBuilder (CubicBezier a b c d) = "cubic-bezier("
<> mconcatIntersperse toBuilder (singleton ',') [a,b,c,d]
Expand All @@ -89,9 +95,9 @@ instance ToText TimingFunction where
instance Minifiable TimingFunction where
minifyWith x = do
conf <- ask
if shouldMinifyTimingFunctions conf
then pure $ minifyTimingFunction x
else pure x
pure $ if shouldMinifyTimingFunctions conf
then minifyTimingFunction x
else x

minifyTimingFunction :: TimingFunction -> TimingFunction
minifyTimingFunction x@(CubicBezier a b c 1)
Expand Down
28 changes: 24 additions & 4 deletions tests/Hasmin/TestUtils.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,10 @@
{-# LANGUAGE OverloadedStrings #-}

module Hasmin.TestUtils where
module Hasmin.TestUtils (
module Hasmin.TestUtils
, module Test.QuickCheck
, module Test.Hspec
) where

import Test.Hspec
import Test.QuickCheck
Expand All @@ -11,14 +15,15 @@ import Data.Attoparsec.Text (Parser)
import Control.Applicative (liftA2, liftA3)
import Control.Monad (liftM4)

import Hasmin.Types.BgSize
import Hasmin.Types.Class
import Hasmin.Types.Color
import Hasmin.Types.Declaration
import Hasmin.Types.Dimension
import Hasmin.Types.FilterFunction
import Hasmin.Types.Numeric
import Hasmin.Types.Position
import Hasmin.Types.FilterFunction
import Hasmin.Types.BgSize
import Hasmin.Types.Color
import Hasmin.Types.TimingFunction
import Hasmin.Utils

-- | Check that a color is equivalent to their minified representation form
Expand Down Expand Up @@ -97,6 +102,21 @@ instance Arbitrary BgSize where
instance Arbitrary Auto where
arbitrary = pure Auto

instance Arbitrary StepsSecondParam where
arbitrary = oneof [pure Start, pure End]

instance Arbitrary TimingFunction where
arbitrary = oneof [ liftM4 CubicBezier arbitrary arbitrary arbitrary arbitrary
, liftA2 Steps arbitrary arbitrary
, pure Ease
, pure EaseIn
, pure EaseInOut
, pure EaseOut
, pure Linear
, pure StepEnd
, pure StepStart
]

instance Arbitrary Color where
arbitrary = oneof [ fmap Named colorKeyword
, liftA3 mkHex3 hexChar hexChar hexChar
Expand Down
5 changes: 1 addition & 4 deletions tests/Hasmin/Types/BgSizeSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,9 +2,6 @@

module Hasmin.Types.BgSizeSpec where

import Test.Hspec
import Test.QuickCheck

import Data.Text (Text)
import Hasmin.Parser.Value
import Hasmin.Types.Class
Expand All @@ -13,7 +10,7 @@ import Hasmin.TestUtils

quickcheckBgSize :: Spec
quickcheckBgSize =
describe "Quickcheck tests for <bg-size>" $
describe "Quickcheck tests for <bg-size>" .
it "Minified <bg-size> maintains semantical equivalence" $
property (prop_minificationEq :: BgSize -> Bool)

Expand Down
18 changes: 8 additions & 10 deletions tests/Hasmin/Types/ColorSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,19 +2,17 @@

module Hasmin.Types.ColorSpec where

import Test.Hspec
import Test.QuickCheck
import Hasmin.Parser.Value
import Hasmin.TestUtils

import Test.Hspec.Attoparsec (parseSatisfies, (~>))
import Data.Text (Text)
import Control.Applicative (liftA2)
import Control.Monad
import Data.Foldable
import Data.Maybe (fromJust)
import Control.Monad
import Control.Applicative (liftA2)
import Hasmin.Types.Color
import Data.Text (Text)
import Test.Hspec.Attoparsec (parseSatisfies, (~>))

import Hasmin.Parser.Value
import Hasmin.TestUtils
import Hasmin.Types.Class
import Hasmin.Types.Color
import Hasmin.Types.Numeric

colorTests :: Spec
Expand Down
9 changes: 4 additions & 5 deletions tests/Hasmin/Types/DeclarationSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,13 +2,12 @@

module Hasmin.Types.DeclarationSpec where

import Test.Hspec
import Data.Foldable (traverse_)
import Data.Monoid ((<>))
import Data.Text (Text)

import Hasmin.Parser.Internal
import Hasmin.TestUtils

import Data.Text (Text)
import Data.Monoid ((<>))
import Data.Foldable (traverse_)
import Hasmin.Types.Class
import Hasmin.Types.Declaration

Expand Down
3 changes: 0 additions & 3 deletions tests/Hasmin/Types/DimensionSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,9 +2,6 @@

module Hasmin.Types.DimensionSpec where

import Test.Hspec
import Test.QuickCheck

import Control.Applicative (liftA2)

import Hasmin.Types.Dimension
Expand Down
3 changes: 0 additions & 3 deletions tests/Hasmin/Types/FilterFunctionSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,9 +2,6 @@

module Hasmin.Types.FilterFunctionSpec where

import Test.Hspec
import Test.QuickCheck

import Data.Text (Text)
import Hasmin.Parser.Value
import Hasmin.Types.Class
Expand Down
7 changes: 1 addition & 6 deletions tests/Hasmin/Types/GradientSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,14 +2,9 @@

module Hasmin.Types.GradientSpec where

import Test.Hspec
-- import Test.QuickCheck
-- import Hasmin.Parser.Internal

-- import Test.Hspec.Attoparsec (shouldParse, parseSatisfies, (~>))
import Control.Monad.Reader (runReader)
import Data.Text (Text)
-- import Data.Attoparsec.Text (Parser)

import Hasmin.Parser.Value
import Hasmin.Types.Class
import Hasmin.Config
Expand Down
3 changes: 0 additions & 3 deletions tests/Hasmin/Types/PositionSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,9 +2,6 @@

module Hasmin.Types.PositionSpec where

import Test.Hspec
import Test.QuickCheck

import Data.Text (Text)
import Control.Monad (liftM4)

Expand Down
3 changes: 0 additions & 3 deletions tests/Hasmin/Types/RepeatStyleSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,9 +2,6 @@

module Hasmin.Types.RepeatStyleSpec where

import Test.Hspec
import Test.QuickCheck

import Data.Text (Text)
import Control.Applicative (liftA2)
import Hasmin.Parser.Value
Expand Down
10 changes: 5 additions & 5 deletions tests/Hasmin/Types/SelectorSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,14 +2,14 @@

module Hasmin.Types.SelectorSpec where

import Test.Hspec
import Hasmin.Parser.Internal
import Hasmin.TestUtils

import Control.Monad.Reader (runReader)
import Data.Text (Text)
import Hasmin.Types.Class

import Hasmin.Config
import Hasmin.Parser.Internal
import Hasmin.TestUtils
import Hasmin.Types.Class


anplusbMinificationTests :: Spec
anplusbMinificationTests =
Expand Down
2 changes: 0 additions & 2 deletions tests/Hasmin/Types/ShadowSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,8 +2,6 @@

module Hasmin.Types.ShadowSpec where

import Test.Hspec

import Data.Text (Text)
import Hasmin.Parser.Value
import Hasmin.Types.Class
Expand Down
6 changes: 2 additions & 4 deletions tests/Hasmin/Types/StringSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,14 +2,12 @@

module Hasmin.Types.StringSpec where

import Test.Hspec
import Data.Text (Text)

import Hasmin.Parser.Value
import Hasmin.TestUtils

import Data.Text (Text)
import Hasmin.Types.Class


quotesNormalizationTests :: Spec
quotesNormalizationTests =
describe "Quotes Normalization" $ do
Expand Down
7 changes: 3 additions & 4 deletions tests/Hasmin/Types/StylesheetSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,13 +2,12 @@

module Hasmin.Types.StylesheetSpec where

import Test.Hspec
import Data.Text (Text)

import Hasmin.Parser.Internal
import Hasmin.TestUtils
import Hasmin.Types.Class

import Data.Text (Text)

atRuleTests :: Spec
atRuleTests = do
describe "at rules parsing and printing" $
Expand Down Expand Up @@ -73,7 +72,7 @@ atRuleTestsInfo =
-- "@counter-style circled-alpha{system:fixed;symbols:Ⓐ Ⓑ Ⓒ;suffix:" "}")
-- ,("@font-feature-values Jupiter Sans { @swash { delicate: 1; flowing: 2; } }",
-- "@font-feature-values Jupiter Sans{@swash{delicate:1;flowing:2}}",
]
]

spec :: Spec
spec = atRuleTests
Expand Down
Loading

0 comments on commit 4a070a1

Please sign in to comment.