diff --git a/.github/workflows/build.yml b/.github/workflows/build.yml index 50c5c87b..a9db863d 100644 --- a/.github/workflows/build.yml +++ b/.github/workflows/build.yml @@ -33,9 +33,9 @@ jobs: - '9.12' include: - os: macos-latest - ghc: '9.10' + ghc: '9.12' - os: windows-latest - ghc: '9.10' + ghc: '9.12' steps: - uses: actions/checkout@v5 - uses: hspec/setup-haskell@v1 diff --git a/src/Hpack/Render.hs b/src/Hpack/Render.hs index 4b929655..cdc6d300 100644 --- a/src/Hpack/Render.hs +++ b/src/Hpack/Render.hs @@ -31,7 +31,6 @@ module Hpack.Render ( , renderFlag , renderSourceRepository , renderDirectories -, formatDescription #endif ) where @@ -46,7 +45,7 @@ import Control.Monad.Reader import Hpack.Util import Hpack.Config import Hpack.Render.Hints -import Hpack.Render.Dsl hiding (sortFieldsBy) +import Hpack.Render.Dsl hiding (RenderSettings(..), defaultRenderSettings, sortFieldsBy) import qualified Hpack.Render.Dsl as Dsl data RenderEnv = RenderEnv { @@ -65,18 +64,24 @@ getPackageName = asks renderEnvPackageName renderPackage :: [String] -> Package -> String renderPackage oldCabalFile = renderPackageWith settings headerFieldsAlignment formattingHintsFieldOrder formattingHintsSectionsFieldOrder where - FormattingHints{..} = sniffFormattingHints oldCabalFile + hints@FormattingHints{..} = sniffFormattingHints oldCabalFile headerFieldsAlignment = fromMaybe 16 formattingHintsAlignment - settings = formattingHintsRenderSettings + settings = formattingHintsRenderSettings hints renderPackageWith :: RenderSettings -> Alignment -> [String] -> [(String, [String])] -> Package -> String -renderPackageWith settings headerFieldsAlignment existingFieldOrder sectionsFieldOrder Package{..} = intercalate "\n" (unlines header : chunks) +renderPackageWith RenderSettings{..} headerFieldsAlignment existingFieldOrder sectionsFieldOrder Package{..} = intercalate "\n" (unlines header : chunks) where + settings :: Dsl.RenderSettings + settings = Dsl.RenderSettings { + renderSettingsEmptyLinesAsDot = packageCabalVersion < makeCabalVersion [3] + , .. + } + chunks :: [String] chunks = map unlines . filter (not . null) . map (render settings 0) $ sortStanzaFields sectionsFieldOrder stanzas header :: [String] - header = concatMap (render settings {renderSettingsFieldAlignment = headerFieldsAlignment} 0) packageFields + header = concatMap (render settings {Dsl.renderSettingsFieldAlignment = headerFieldsAlignment} 0) packageFields packageFields :: [Element] packageFields = addVerbatim packageVerbatim . sortFieldsBy existingFieldOrder $ @@ -117,7 +122,7 @@ renderPackageWith settings headerFieldsAlignment existingFieldOrder sectionsFiel ("name", Just packageName) , ("version", Just packageVersion) , ("synopsis", packageSynopsis) - , ("description", (formatDescription packageCabalVersion headerFieldsAlignment <$> packageDescription)) + , ("description", packageDescription) , formatList "category" packageCategory , ("stability", packageStability) , ("homepage", packageHomepage) @@ -139,9 +144,7 @@ renderPackageWith settings headerFieldsAlignment existingFieldOrder sectionsFiel formatValues values = guard (not $ null values) >> (Just $ intercalate separator values) where separator :: String - separator = ",\n" ++ replicate n ' ' - where - Alignment n = max headerFieldsAlignment (Alignment $ length field + 2) + separator = ",\n" sortStanzaFields :: [(String, [String])] -> [Element] -> [Element] sortStanzaFields sectionsFieldOrder = go @@ -151,33 +154,6 @@ sortStanzaFields sectionsFieldOrder = go Stanza name fields : xs | Just fieldOrder <- lookup name sectionsFieldOrder -> Stanza name (sortFieldsBy fieldOrder fields) : go xs x : xs -> x : go xs -formatDescription :: CabalVersion -> Alignment -> String -> String -formatDescription cabalVersion (Alignment alignment) description = case map emptyLineToDot $ lines description of - x : xs -> intercalate "\n" (x : indent xs) - [] -> "" - where - n :: Int - n = max alignment (length ("description: " :: String)) - - indentation :: String - indentation = replicate n ' ' - - emptyLineToDot :: String -> String - emptyLineToDot xs - | isEmptyLine xs && cabalVersion < makeCabalVersion [3] = "." - | otherwise = xs - - indent :: [String] -> [String] - indent = map indentLine - - indentLine :: String -> String - indentLine xs - | isEmptyLine xs = "" - | otherwise = indentation ++ xs - - isEmptyLine :: String -> Bool - isEmptyLine = all isSpace - renderSourceRepository :: SourceRepository -> Element renderSourceRepository SourceRepository{..} = Stanza "source-repository head" [ Field "type" "git" diff --git a/src/Hpack/Render/Dsl.hs b/src/Hpack/Render/Dsl.hs index b4024f15..86efef3c 100644 --- a/src/Hpack/Render/Dsl.hs +++ b/src/Hpack/Render/Dsl.hs @@ -20,12 +20,14 @@ module Hpack.Render.Dsl ( #ifdef TEST , Lines (..) +, IndentOrAlign (..) , renderValue , addSortKey #endif ) where import Imports +import Data.Char (isSpace) data Element = Stanza String [Element] | Group Element Element | Field String Value | Verbatim String deriving (Eq, Show) @@ -37,7 +39,26 @@ data Value = | WordList [String] deriving (Eq, Show) -data Lines = SingleLine String | MultipleLines [String] +data Lines = SingleLine String | MultipleLines IndentOrAlign [String] + deriving (Eq, Show) + +data IndentOrAlign = + Indent + -- ^ + -- Indent lines, e.g. + -- + -- description: + -- some + -- multiline + -- description + | + Align + -- ^ + -- Align lines with field labels, e.g. + -- + -- description: some + -- multiline + -- description deriving (Eq, Show) data CommaStyle = LeadingCommas | TrailingCommas @@ -53,10 +74,11 @@ data RenderSettings = RenderSettings { renderSettingsIndentation :: Int , renderSettingsFieldAlignment :: Alignment , renderSettingsCommaStyle :: CommaStyle +, renderSettingsEmptyLinesAsDot :: Bool } deriving (Eq, Show) defaultRenderSettings :: RenderSettings -defaultRenderSettings = RenderSettings 2 0 LeadingCommas +defaultRenderSettings = RenderSettings 2 0 LeadingCommas True render :: RenderSettings -> Nesting -> Element -> [String] render settings nesting = \ case @@ -69,31 +91,55 @@ renderElements :: RenderSettings -> Nesting -> [Element] -> [String] renderElements settings nesting = concatMap (render settings nesting) renderField :: RenderSettings -> String -> Value -> [String] -renderField settings@RenderSettings{..} name value = case renderValue settings value of +renderField settings@RenderSettings{..} name = renderValue settings >>> \ case SingleLine "" -> [] - SingleLine x -> [name ++ ": " ++ padding ++ x] - MultipleLines [] -> [] - MultipleLines xs -> (name ++ ":") : map (indent settings 1) xs + SingleLine value -> [fieldName ++ value] + MultipleLines _ [] -> [] + MultipleLines Indent values -> (name ++ ":") : map (indent settings 1) values + MultipleLines Align (value : values) -> (fieldName ++ value) : map align values where Alignment fieldAlignment = renderSettingsFieldAlignment - padding = replicate (fieldAlignment - length name - 2) ' ' + + fieldName :: String + fieldName = name ++ ": " ++ fieldNamePadding + + fieldNamePadding :: String + fieldNamePadding = replicate (fieldAlignment - length name - 2) ' ' + + align :: String -> String + align = \ case + "" -> "" + value -> padding ++ value + + padding :: String + padding = replicate (length fieldName) ' ' renderValue :: RenderSettings -> Value -> Lines -renderValue RenderSettings{..} v = case v of - Literal s -> SingleLine s +renderValue RenderSettings{..} = \ case + Literal string -> case lines string of + [value] -> SingleLine value + values -> MultipleLines Align $ map emptyLineToDot values WordList ws -> SingleLine $ unwords ws LineSeparatedList xs -> renderLineSeparatedList renderSettingsCommaStyle xs CommaSeparatedList xs -> renderCommaSeparatedList renderSettingsCommaStyle xs + where + emptyLineToDot :: String -> String + emptyLineToDot xs + | isEmptyLine xs && renderSettingsEmptyLinesAsDot = "." + | otherwise = xs + + isEmptyLine :: String -> Bool + isEmptyLine = all isSpace renderLineSeparatedList :: CommaStyle -> [String] -> Lines -renderLineSeparatedList style = MultipleLines . map (padding ++) +renderLineSeparatedList style = MultipleLines Indent . map (padding ++) where padding = case style of LeadingCommas -> " " TrailingCommas -> "" renderCommaSeparatedList :: CommaStyle -> [String] -> Lines -renderCommaSeparatedList style = MultipleLines . case style of +renderCommaSeparatedList style = MultipleLines Indent . case style of LeadingCommas -> map renderLeadingComma . zip (True : repeat False) TrailingCommas -> map renderTrailingComma . reverse . zip (True : repeat False) . reverse where @@ -111,7 +157,9 @@ instance IsString Value where fromString = Literal indent :: RenderSettings -> Nesting -> String -> String -indent RenderSettings{..} (Nesting nesting) s = replicate (nesting * renderSettingsIndentation) ' ' ++ s +indent RenderSettings{..} (Nesting nesting) = \ case + "" -> "" + s -> replicate (nesting * renderSettingsIndentation) ' ' ++ s sortFieldsBy :: [String] -> [Element] -> [Element] sortFieldsBy existingFieldOrder = diff --git a/src/Hpack/Render/Hints.hs b/src/Hpack/Render/Hints.hs index 27d876b7..5f45e1c4 100644 --- a/src/Hpack/Render/Hints.hs +++ b/src/Hpack/Render/Hints.hs @@ -1,10 +1,13 @@ {-# LANGUAGE CPP #-} {-# LANGUAGE ViewPatterns #-} +{-# LANGUAGE RecordWildCards #-} module Hpack.Render.Hints ( FormattingHints (..) , sniffFormattingHints +, RenderSettings (..) +, defaultRenderSettings +, formattingHintsRenderSettings #ifdef TEST -, sniffRenderSettings , extractFieldOrder , extractSectionsFieldOrder , sanitize @@ -21,14 +24,16 @@ import Imports import Data.Char import Data.Maybe -import Hpack.Render.Dsl +import Hpack.Render.Dsl (Alignment(..), CommaStyle(..)) +import qualified Hpack.Render.Dsl as Dsl import Hpack.Util data FormattingHints = FormattingHints { formattingHintsFieldOrder :: [String] , formattingHintsSectionsFieldOrder :: [(String, [String])] , formattingHintsAlignment :: Maybe Alignment -, formattingHintsRenderSettings :: RenderSettings +, formattingHintsIndentation :: Maybe Int +, formattingHintsCommaStyle :: Maybe CommaStyle } deriving (Eq, Show) sniffFormattingHints :: [String] -> FormattingHints @@ -36,7 +41,8 @@ sniffFormattingHints (sanitize -> input) = FormattingHints { formattingHintsFieldOrder = extractFieldOrder input , formattingHintsSectionsFieldOrder = extractSectionsFieldOrder input , formattingHintsAlignment = sniffAlignment input -, formattingHintsRenderSettings = sniffRenderSettings input +, formattingHintsIndentation = sniffIndentation input +, formattingHintsCommaStyle = sniffCommaStyle input } sanitize :: [String] -> [String] @@ -124,11 +130,20 @@ sniffCommaStyle input where startsWithComma = isPrefixOf "," . dropWhile isSpace -sniffRenderSettings :: [String] -> RenderSettings -sniffRenderSettings input = RenderSettings indentation fieldAlignment commaStyle - where - indentation = max def $ fromMaybe def (sniffIndentation input) - where def = renderSettingsIndentation defaultRenderSettings +data RenderSettings = RenderSettings { + renderSettingsIndentation :: Int +, renderSettingsFieldAlignment :: Alignment +, renderSettingsCommaStyle :: CommaStyle +} deriving (Eq, Show) - fieldAlignment = renderSettingsFieldAlignment defaultRenderSettings - commaStyle = fromMaybe (renderSettingsCommaStyle defaultRenderSettings) (sniffCommaStyle input) +defaultRenderSettings :: RenderSettings +defaultRenderSettings = let Dsl.RenderSettings{..} = Dsl.defaultRenderSettings in RenderSettings{..} + +formattingHintsRenderSettings :: FormattingHints -> RenderSettings +formattingHintsRenderSettings FormattingHints{..} = defaultRenderSettings { + renderSettingsIndentation = indentation +, renderSettingsCommaStyle = commaStyle +} where + indentation = max def $ fromMaybe def formattingHintsIndentation + where def = renderSettingsIndentation defaultRenderSettings + commaStyle = fromMaybe (renderSettingsCommaStyle defaultRenderSettings) formattingHintsCommaStyle diff --git a/test/EndToEndSpec.hs b/test/EndToEndSpec.hs index fd2740f4..d37d6807 100644 --- a/test/EndToEndSpec.hs +++ b/test/EndToEndSpec.hs @@ -20,7 +20,7 @@ import Data.Version (showVersion) import qualified Hpack.Render as Hpack import Hpack.Config (packageConfig, readPackageConfig, DecodeOptions(..), defaultDecodeOptions, DecodeResult(..)) -import Hpack.Render.Hints (FormattingHints(..), sniffFormattingHints) +import Hpack.Render.Hints (FormattingHints(..), sniffFormattingHints, formattingHintsRenderSettings) import qualified Paths_hpack as Hpack (version) @@ -378,6 +378,26 @@ spec = around_ (inTempDirectoryNamed "my-package") $ do location: https://github.com/hspec/hspec |] + describe "flags" $ do + it "accepts multi-line flag descriptions" $ do + [i| + flags: + some-flag: + description: | + some + flag + description + manual: True + default: False + |] `shouldRenderTo` package [i| + flag some-flag + description: some + flag + description + manual: True + default: False + |] + describe "defaults" $ do it "accepts global defaults" $ do writeFile "defaults/sol/hpack-template/2017/defaults.yaml" [i| @@ -2113,9 +2133,9 @@ run_ userDataDir c old = do return $ case mPackage of Right (DecodeResult pkg cabalVersion _ warnings) -> let - FormattingHints{..} = sniffFormattingHints (lines old) + hints@FormattingHints{..} = sniffFormattingHints (lines old) alignment = fromMaybe 0 formattingHintsAlignment - settings = formattingHintsRenderSettings + settings = formattingHintsRenderSettings hints output = cabalVersion ++ Hpack.renderPackageWith settings alignment formattingHintsFieldOrder formattingHintsSectionsFieldOrder pkg in Right (warnings, output) diff --git a/test/Hpack/Render/DslSpec.hs b/test/Hpack/Render/DslSpec.hs index 227e9e2d..d10c8167 100644 --- a/test/Hpack/Render/DslSpec.hs +++ b/test/Hpack/Render/DslSpec.hs @@ -55,7 +55,79 @@ spec = do ] context "when rendering a Field" $ do - context "when rendering a MultipleLines value" $ do + context "with a Literal value" $ do + let + description :: [String] -> Element + description = Field "description" . Literal . unlines + + values :: [String] + values = [ + "foo" + , "bar" + , "baz" + ] + + it "renders field" $ do + render_ (Field "description" "foo") `shouldBe` ["description: foo"] + + it "formats multi-line values" $ do + render_ (description values) `shouldBe` [ + "description: foo" + , " bar" + , " baz" + ] + + it "formats empty lines" $ do + let + field = description [ + "foo" + , " " + , "baz" + ] + render_ field `shouldBe` [ + "description: foo" + , " ." + , " baz" + ] + + it "correctly handles empty lines at the beginning" $ do + render_ (description $ "" : values) `shouldBe` [ + "description: ." + , " foo" + , " bar" + , " baz" + ] + + it "takes alignment into account" $ do + let + settings :: RenderSettings + settings = defaultRenderSettings { renderSettingsFieldAlignment = 15 } + + render settings 0 (description values) `shouldBe` [ + "description: foo" + , " bar" + , " baz" + ] + + context "when cabal-version is >= 3" $ do + let + settings :: RenderSettings + settings = defaultRenderSettings { renderSettingsEmptyLinesAsDot = False } + + it "preserves empty lines" $ do + let + field = description [ + "foo" + , "" + , "baz" + ] + render settings 0 field `shouldBe` [ + "description: foo" + , "" + , " baz" + ] + + context "with MultipleLines" $ do it "takes nesting into account" $ do let field = Field "foo" (CommaSeparatedList ["bar", "baz"]) render defaultRenderSettings 1 field `shouldBe` [ @@ -92,14 +164,14 @@ spec = do renderValue defaultRenderSettings (WordList ["foo", "bar", "baz"]) `shouldBe` SingleLine "foo bar baz" it "renders CommaSeparatedList" $ do - renderValue defaultRenderSettings (CommaSeparatedList ["foo", "bar", "baz"]) `shouldBe` MultipleLines [ + renderValue defaultRenderSettings (CommaSeparatedList ["foo", "bar", "baz"]) `shouldBe` MultipleLines Indent [ " foo" , ", bar" , ", baz" ] it "renders LineSeparatedList" $ do - renderValue defaultRenderSettings (LineSeparatedList ["foo", "bar", "baz"]) `shouldBe` MultipleLines [ + renderValue defaultRenderSettings (LineSeparatedList ["foo", "bar", "baz"]) `shouldBe` MultipleLines Indent [ " foo" , " bar" , " baz" @@ -109,14 +181,14 @@ spec = do let settings = defaultRenderSettings{renderSettingsCommaStyle = TrailingCommas} it "renders CommaSeparatedList with trailing commas" $ do - renderValue settings (CommaSeparatedList ["foo", "bar", "baz"]) `shouldBe` MultipleLines [ + renderValue settings (CommaSeparatedList ["foo", "bar", "baz"]) `shouldBe` MultipleLines Indent [ "foo," , "bar," , "baz" ] it "renders LineSeparatedList without padding" $ do - renderValue settings (LineSeparatedList ["foo", "bar", "baz"]) `shouldBe` MultipleLines [ + renderValue settings (LineSeparatedList ["foo", "bar", "baz"]) `shouldBe` MultipleLines Indent [ "foo" , "bar" , "baz" diff --git a/test/Hpack/Render/HintsSpec.hs b/test/Hpack/Render/HintsSpec.hs index f4a01dc9..c3804b36 100644 --- a/test/Hpack/Render/HintsSpec.hs +++ b/test/Hpack/Render/HintsSpec.hs @@ -3,11 +3,11 @@ module Hpack.Render.HintsSpec (spec) where import Test.Hspec import Hpack.Render.Hints -import Hpack.Render.Dsl +import Hpack.Render.Dsl (CommaStyle(..)) spec :: Spec spec = do - describe "sniffRenderSettings" $ do + describe "formattingHintsRenderSettings" $ do context "when sniffed indentation is < default" $ do it "uses default instead" $ do let input = [ @@ -15,8 +15,9 @@ spec = do , "exposed-modules:" , " Foo" ] - sniffIndentation input `shouldBe` Just 0 - renderSettingsIndentation (sniffRenderSettings input) `shouldBe` 2 + hints = sniffFormattingHints input + formattingHintsIndentation hints `shouldBe` Just 0 + renderSettingsIndentation (formattingHintsRenderSettings hints) `shouldBe` 2 describe "extractFieldOrder" $ do it "extracts field order hints" $ do diff --git a/test/Hpack/RenderSpec.hs b/test/Hpack/RenderSpec.hs index 0e6995f8..fc58496a 100644 --- a/test/Hpack/RenderSpec.hs +++ b/test/Hpack/RenderSpec.hs @@ -9,7 +9,8 @@ import Control.Monad.Reader (runReader) import Hpack.Syntax.DependencyVersion import Hpack.ConfigSpec hiding (spec) import Hpack.Config hiding (package) -import Hpack.Render.Dsl +import Hpack.Render.Dsl hiding (RenderSettings, defaultRenderSettings, render) +import qualified Hpack.Render.Dsl as Dsl import Hpack.Render library :: Library @@ -26,8 +27,8 @@ renderEmptySection Empty = [] cabalVersion :: CabalVersion cabalVersion = makeCabalVersion [1,12] -cabal30 :: CabalVersion -cabal30 = makeCabalVersion [3,0,0] +render :: Element -> [FilePath] +render = Dsl.render Dsl.defaultRenderSettings 0 spec :: Spec spec = do @@ -232,7 +233,7 @@ spec = do it "renders conditionals" $ do let conditional = Conditional "os(windows)" (section Empty) {sectionDependencies = deps ["Win32"]} Nothing - render defaultRenderSettings 0 (run $ renderConditional renderEmptySection conditional) `shouldBe` [ + render (run $ renderConditional renderEmptySection conditional) `shouldBe` [ "if os(windows)" , " build-depends:" , " Win32" @@ -240,7 +241,7 @@ spec = do it "renders conditionals with else-branch" $ do let conditional = Conditional "os(windows)" (section Empty) {sectionDependencies = deps ["Win32"]} (Just $ (section Empty) {sectionDependencies = deps ["unix"]}) - render defaultRenderSettings 0 (run $ renderConditional renderEmptySection conditional) `shouldBe` [ + render (run $ renderConditional renderEmptySection conditional) `shouldBe` [ "if os(windows)" , " build-depends:" , " Win32" @@ -252,7 +253,7 @@ spec = do it "renders nested conditionals" $ do let conditional = Conditional "arch(i386)" (section Empty) {sectionGhcOptions = ["-threaded"], sectionConditionals = [innerConditional]} Nothing innerConditional = Conditional "os(windows)" (section Empty) {sectionDependencies = deps ["Win32"]} Nothing - render defaultRenderSettings 0 (run $ renderConditional renderEmptySection conditional) `shouldBe` [ + render (run $ renderConditional renderEmptySection conditional) `shouldBe` [ "if arch(i386)" , " ghc-options: -threaded" , " if os(windows)" @@ -263,7 +264,7 @@ spec = do it "conditionalises both build-depends and mixins" $ do let conditional = Conditional "os(windows)" (section Empty) {sectionDependencies = [("Win32", depInfo)]} Nothing depInfo = defaultInfo { dependencyInfoMixins = ["hiding (Blah)"] } - render defaultRenderSettings 0 (run $ renderConditional renderEmptySection conditional) `shouldBe` [ + render (run $ renderConditional renderEmptySection conditional) `shouldBe` [ "if os(windows)" , " build-depends:" , " Win32" @@ -274,77 +275,17 @@ spec = do describe "renderFlag" $ do it "renders flags" $ do let flag = (Flag "foo" (Just "some flag") True False) - render defaultRenderSettings 0 (renderFlag flag) `shouldBe` [ + render (renderFlag flag) `shouldBe` [ "flag foo" , " description: some flag" , " manual: True" , " default: False" ] - describe "formatDescription" $ do - it "formats description" $ do - let description = unlines [ - "foo" - , "bar" - ] - "description: " ++ formatDescription cabalVersion 0 description `shouldBe` intercalate "\n" [ - "description: foo" - , " bar" - ] - - it "takes specified alignment into account" $ do - let description = unlines [ - "foo" - , "bar" - , "baz" - ] - "description: " ++ formatDescription cabalVersion 15 description `shouldBe` intercalate "\n" [ - "description: foo" - , " bar" - , " baz" - ] - - it "formats empty lines" $ do - let description = unlines [ - "foo" - , " " - , "bar" - ] - "description: " ++ formatDescription cabalVersion 0 description `shouldBe` intercalate "\n" [ - "description: foo" - , " ." - , " bar" - ] - - it "correctly handles empty lines at the beginning" $ do - let description = unlines [ - "" - , "foo" - , "bar" - ] - "description: " ++ formatDescription cabalVersion 0 description `shouldBe` intercalate "\n" [ - "description: ." - , " foo" - , " bar" - ] - - context "when cabal-version is >= 3" $ do - it "preserves empty lines" $ do - let description = unlines [ - "foo" - , "" - , "bar" - ] - "description: " ++ formatDescription cabal30 0 description `shouldBe` intercalate "\n" [ - "description: foo" - , "" - , " bar" - ] - describe "renderSourceRepository" $ do it "renders source-repository without subdir correctly" $ do let repository = SourceRepository "https://github.com/hspec/hspec" Nothing - (render defaultRenderSettings 0 $ renderSourceRepository repository) + (render $ renderSourceRepository repository) `shouldBe` [ "source-repository head" , " type: git" @@ -353,7 +294,7 @@ spec = do it "renders source-repository with subdir" $ do let repository = SourceRepository "https://github.com/hspec/hspec" (Just "hspec-core") - (render defaultRenderSettings 0 $ renderSourceRepository repository) + (render $ renderSourceRepository repository) `shouldBe` [ "source-repository head" , " type: git" @@ -363,7 +304,7 @@ spec = do describe "renderDirectories" $ do it "replaces . with ./. (for compatibility with cabal syntax)" $ do - (render defaultRenderSettings 0 $ renderDirectories "name" ["."]) + (render $ renderDirectories "name" ["."]) `shouldBe` [ "name:" , " ./"