Copyright | (c) 2017 Cristian Adrián Ontivero |
---|---|
License | BSD3 |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Safe |
Language | Haskell2010 |
Synopsis
- data Config = Config {
- colorSettings :: ColorSettings
- dimensionSettings :: DimensionSettings
- gradientSettings :: GradientSettings
- shouldUsePropertyTraits :: Bool
- shouldCleanRules :: Bool
- shouldMinifyTimingFunctions :: Bool
- shouldMinifyFilterFunctions :: Bool
- shouldRemoveQuotes :: Bool
- fontweightSettings :: FontWeightSettings
- shouldMinifyTransformOrigin :: Bool
- shouldMinifyMicrosyntax :: Bool
- shouldMinifyKeyframeSelectors :: Bool
- shouldMinifyTransformFunction :: Bool
- shouldConvertEscaped :: Bool
- shouldConvertNullPercentages :: Bool
- shouldRemoveEmptyBlocks :: Bool
- shouldRemoveDuplicateSelectors :: Bool
- shouldNormalizeQuotes :: Bool
- letterCase :: LetterCase
- selectorSorting :: SortingMethod
- declarationSorting :: SortingMethod
- rulesMergeSettings :: RulesMergeSettings
- data ColorSettings
- data DimensionSettings
- data GradientSettings
- data FontWeightSettings
- data LetterCase
- data SortingMethod
- defaultConfig :: Config
- data RulesMergeSettings
Documentation
The configuration used for minifying.
data ColorSettings Source #
Instances
Eq ColorSettings Source # | |
Defined in Hasmin.Config (==) :: ColorSettings -> ColorSettings -> Bool # (/=) :: ColorSettings -> ColorSettings -> Bool # | |
Show ColorSettings Source # | |
Defined in Hasmin.Config showsPrec :: Int -> ColorSettings -> ShowS # show :: ColorSettings -> String # showList :: [ColorSettings] -> ShowS # |
data DimensionSettings Source #
Instances
Eq DimensionSettings Source # | |
Defined in Hasmin.Config (==) :: DimensionSettings -> DimensionSettings -> Bool # (/=) :: DimensionSettings -> DimensionSettings -> Bool # | |
Show DimensionSettings Source # | |
Defined in Hasmin.Config showsPrec :: Int -> DimensionSettings -> ShowS # show :: DimensionSettings -> String # showList :: [DimensionSettings] -> ShowS # |
data GradientSettings Source #
Instances
Eq GradientSettings Source # | |
Defined in Hasmin.Config (==) :: GradientSettings -> GradientSettings -> Bool # (/=) :: GradientSettings -> GradientSettings -> Bool # | |
Show GradientSettings Source # | |
Defined in Hasmin.Config showsPrec :: Int -> GradientSettings -> ShowS # show :: GradientSettings -> String # showList :: [GradientSettings] -> ShowS # |
data FontWeightSettings Source #
Instances
Eq FontWeightSettings Source # | |
Defined in Hasmin.Config (==) :: FontWeightSettings -> FontWeightSettings -> Bool # (/=) :: FontWeightSettings -> FontWeightSettings -> Bool # | |
Show FontWeightSettings Source # | |
Defined in Hasmin.Config showsPrec :: Int -> FontWeightSettings -> ShowS # show :: FontWeightSettings -> String # showList :: [FontWeightSettings] -> ShowS # |
data LetterCase Source #
Instances
Eq LetterCase Source # | |
Defined in Hasmin.Config (==) :: LetterCase -> LetterCase -> Bool # (/=) :: LetterCase -> LetterCase -> Bool # | |
Show LetterCase Source # | |
Defined in Hasmin.Config showsPrec :: Int -> LetterCase -> ShowS # show :: LetterCase -> String # showList :: [LetterCase] -> ShowS # |
data SortingMethod Source #
Instances
Eq SortingMethod Source # | |
Defined in Hasmin.Config (==) :: SortingMethod -> SortingMethod -> Bool # (/=) :: SortingMethod -> SortingMethod -> Bool # | |
Show SortingMethod Source # | |
Defined in Hasmin.Config showsPrec :: Int -> SortingMethod -> ShowS # show :: SortingMethod -> String # showList :: [SortingMethod] -> ShowS # |
defaultConfig :: Config Source #
A default config with most settings enabled. Used by the minify function, mainly for testing purposes.
data RulesMergeSettings Source #
Instances
Eq RulesMergeSettings Source # | |
Defined in Hasmin.Config (==) :: RulesMergeSettings -> RulesMergeSettings -> Bool # (/=) :: RulesMergeSettings -> RulesMergeSettings -> Bool # | |
Show RulesMergeSettings Source # | |
Defined in Hasmin.Config showsPrec :: Int -> RulesMergeSettings -> ShowS # show :: RulesMergeSettings -> String # showList :: [RulesMergeSettings] -> ShowS # |