module Portage.MetadataSpec (spec) where import Test.Hspec import Test.Hspec.QuickCheck import qualified Data.Text as T import qualified Data.Map.Strict as Map import qualified Data.Set as S import qualified Portage.EBuild as E import Portage.Metadata import Portage.Metadata.RemoteId import qualified Hackport.Env as Env spec :: Spec spec = do -- TODO: These tests are based off old behavior and should be remade at some point -- describe "parseMetadataXML" $ do -- it "returns Nothing from an empty Text" $ do -- parseMetadataXML T.empty `shouldBe` Nothing -- it "equals makeMinimalMetadata with no USE flags" $ do -- parseMetadataXML (printMetadata Map.empty) `shouldBe` Just minimalMetadata -- it "equals makeMinimalMetadata plus the supplied USE flags" $ do -- let flags = Map.singleton "name" "description" -- parseMetadataXML (makeDefaultMetadata flags) `shouldBe` Just (makeMinimalMetadata { metadataUseFlags = flags }) describe "stripGlobalUseFlags" $ do it "should remove specified global USE flags from the metadata.xml" $ do stripGlobalUseFlags (Map.singleton "debug" "description") `shouldBe` Map.empty stripGlobalUseFlags (Map.singleton "examples" "description") `shouldBe` Map.empty stripGlobalUseFlags (Map.singleton "static" "description") `shouldBe` Map.empty stripGlobalUseFlags (Map.singleton "test" "description") `shouldBe` Map.empty prop "should ignore USE flags that are not specified as global" $ do \name description -> stripGlobalUseFlags (Map.singleton name description) == if name `elem` ["debug","examples","static","test"] then Map.empty else Map.singleton name description describe "prettyPrintFlags" $ do it "correctly handles special XML characters contained in strings" $ do let name = "foo" desc = "bar < 1.1.0" in prettyPrintFlags (Map.singleton name desc) `shouldBe` [ "\t" , "\t\t" ++ "bar < 1.1.0" ++ "" , "\t" ] it "correctly formats a single USE flag name with its description" $ do let name = "foo" description = "bar" in prettyPrintFlags (Map.singleton name description) `shouldBe` [ "\t" , "\t\t" ++ (unwords . lines $ description) ++ "" , "\t" ] it "correctly formats multiple USE flag names with their descriptions" $ do let f1 = "flag1" f2 = "flag2" d1 = "foo_desc" d2 = "bar_desc" in prettyPrintFlags (Map.fromList [(f1,d1),(f2,d2)]) `shouldBe` [ "\t" , "\t\t" ++ (unwords . lines $ d1) ++ "" , "\t\t" ++ (unwords . lines $ d2) ++ "" , "\t" ] describe "printMetadata" $ do context "when writing a minimal metadata.xml with no USE flags" $ do it "should have a certain format" $ let correctMetadata = T.pack $ unlines [ "" , "" , "" , "\t" , "\t\thaskell@gentoo.org" , "\t\tGentoo Haskell" , "\t" , "\t" , "\t\tFooBar" , "\t" , "" ] in printMetadata (minimalMetadata True E.ebuildTemplate) `shouldBe` correctMetadata context "when writing a minimal metadata.xml with no USE flags and --not-on-hackage" $ do it "should have a certain format" $ let correctMetadata = T.pack $ unlines [ "" , "" , "" , "\t" , "\t\thaskell@gentoo.org" , "\t\tGentoo Haskell" , "\t" , "" ] in printMetadata (minimalMetadata False E.ebuildTemplate) `shouldBe` correctMetadata context "when writing a metadata.xml with USE flags and a GitHub remote-id" $ do it "should have a certain format, including the element" $ do let meta = minimalMetadata True E.ebuildTemplate <> mempty { metadataUseFlags = Map.fromList [("flag1","desc1"),("flag2","desc2")] , metadataRemoteIds = S.singleton $ RemoteIdGithub "foo" "bar" } correctMetadata = T.pack $ unlines [ "" , "" , "" , "\t" , "\t\thaskell@gentoo.org" , "\t\tGentoo Haskell" , "\t" , "\t" , "\t\tdesc1" , "\t\tdesc2" , "\t" , "\t" , "\t\tFooBar" , "\t\tfoo/bar" , "\t" , "" ] in printMetadata meta `shouldBe` correctMetadata context "when writing a minimal metadata.xml with global USE flags" $ do it "should not leave an empty element" $ do let meta = (minimalMetadata True E.ebuildTemplate) { metadataUseFlags = Map.fromList [("debug","it debugs") ,("examples","some examples") ,("static","not dynamic") ,("test","it tests") ] } correctMetadata = T.pack $ unlines [ "" , "" , "" , "\t" , "\t\thaskell@gentoo.org" , "\t\tGentoo Haskell" , "\t" , "\t" , "\t\tFooBar" , "\t" , "" ] in printMetadata meta `shouldBe` correctMetadata describe "updateMetadata" $ do it "should default to minimalMetadata" $ do let cmdEnv = Env.MergeEnv Nothing "hackport" ebuild = E.ebuildTemplate in updateMetadata cmdEnv ebuild [] Nothing `shouldBe` minimalMetadata True ebuild it "should fall back to the homepage for remote-id" $ do let cmdEnv = Env.MergeEnv Nothing "hackport" ebuild = E.ebuildTemplate { E.homepage = "https://github.com/gentoo-haskell/hackport#readme" } correctRemoteId = RemoteIdGithub "gentoo-haskell" "hackport" mkCorrectMeta (Metadata e f r) = Metadata e f (S.insert correctRemoteId r) in updateMetadata cmdEnv ebuild [] Nothing `shouldBe` mkCorrectMeta (minimalMetadata True E.ebuildTemplate)