{-# LANGUAGE OverloadedStrings #-} import Test.Hspec import Control.Monad.Catch (MonadThrow) import Control.Monad.Trans.Resource (runResourceT) import Data.Text (Text) import Data.XML.Types (Event) import Text.XML.Stream.Parse hiding (force) import Data.Conduit import qualified Data.Conduit.List as CL import Data.Conduit.OSM import Data.Conduit.OSM.Types main :: IO () main = hspec $ do describe "parser success" $ do it "parse node with tags" $ do parsed <- runTest testCase01 conduitOSM parsed `shouldBe` [OSM 0.6 (Just "lulz generator") Nothing [Node 52.153 22.341 (NWRCommon "43221" (Just True) Nothing Nothing Nothing [Tag ("shop", "alcohol"), Tag ("area", "safe")])] [] []] it "parse way" $ do parsed <- runTest testCase03 conduitOSM parsed `shouldBe` [OSM 0.6 (Just "lulz generator") Nothing [] [Way [Nd "1234", Nd "2345", Nd "3456"] (NWRCommon "1995" (Just True) Nothing Nothing Nothing [Tag ("rodzaj drogi", "do ukochanej")]) ] [] ] it "parse relation" $ do parsed <- runTest testCase04 conduitOSM parsed `shouldBe` [OSM 0.6 (Just "lulz generator") Nothing [] [] [Relation [Member NWRn "1234" Nothing] (NWRCommon "4747" (Just True) Nothing Nothing Nothing [Tag ("testk", "testv")])]] describe "parser throws error" $ do it "should throw when reading a double value fails" $ do runTest testCase02 conduitOSM `shouldThrow` errorCall "Could not parse attribute value" describe "reading from file" $ do it "should be able to read using sourceFileOSM" $ do parsed <- runResourceT $ sourceFileOSM "test/readingTest.xml" $$ CL.consume parsed `shouldBe` [OSM 0.6 Nothing Nothing [Node 12.34 34.56 (NWRCommon "1111" Nothing Nothing Nothing Nothing [])] [] []] describe "parsing ommiting osm tag" $ do it "parse nwr at once" $ do parsed <- runTest testCase05 conduitNWR parsed `shouldMatchList` [ N (Node 52.153 22.341 (NWRCommon "43221" (Just True) Nothing Nothing Nothing [])), W (Way [Nd "12"] (NWRCommon "1337" (Just True) Nothing Nothing Nothing [])), R (Relation [Member NWRn "1234" Nothing] (NWRCommon "4747" (Just True) Nothing Nothing Nothing [Tag ("testk", "testv")])) ] it "parse nodes using conduitNodes" $ do parsed <- runTest testCase01 conduitNodes parsed `shouldBe` [Node 52.153 22.341 (NWRCommon "43221" (Just True) Nothing Nothing Nothing [Tag ("shop", "alcohol"), Tag ("area", "safe")])] it "parse ways using conduitWays" $ do parsed <- runTest testCase03 conduitWays parsed `shouldBe` [Way [Nd "1234", Nd "2345", Nd "3456"] (NWRCommon "1995" (Just True) Nothing Nothing Nothing [Tag ("rodzaj drogi", "do ukochanej")])] it "parse relations using conduitRelations" $ do parsed <- runTest testCase04 conduitRelations parsed `shouldBe` [Relation [Member NWRn "1234" Nothing] (NWRCommon "4747" (Just True) Nothing Nothing Nothing [Tag ("testk", "testv")])] it "parse items from many osm tags" $ do parsed <- runTest testCase06 conduitNWR parsed `shouldMatchList` [ N (Node 52 20 (NWRCommon "21" (Just True) Nothing Nothing Nothing [])), N (Node 52.153 22.341 (NWRCommon "43221" (Just True) Nothing Nothing Nothing [])) ] runTest :: MonadThrow m => Source m Text -> Conduit Event m a -> m [a] runTest tcase cond = tcase $$ parseText' def =$ cond =$ CL.consume xmlPrefix :: Text xmlPrefix = "" testCase01 :: Monad m => Source m Text testCase01 = CL.sourceList [xmlPrefix , "" , "" , "" , "" , "" , "" ] testCase02 :: Monad m => Source m Text testCase02 = CL.sourceList [xmlPrefix , "" , "" , "" , "" , "" ] testCase03 :: Monad m => Source m Text testCase03 = CL.sourceList [xmlPrefix , "" , "" , "" , "" , "" , "" , "" , "" ] testCase04 :: Monad m => Source m Text testCase04 = CL.sourceList [xmlPrefix , "" , "" , "" , "" , "" , "" ] testCase05 :: Monad m => Source m Text testCase05 = CL.sourceList [xmlPrefix , "" , "" , "" , "" , "" , "" , "" , "" , "" , "" ] testCase06 :: Monad m => Source m Text testCase06 = CL.sourceList [xmlPrefix , "" , "" , "" , "" , "" , "" ]