{-# LANGUAGE DataKinds #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE QuasiQuotes #-} -- Module : Test.AWS.Data.List -- Copyright : (c) 2013-2015 Brendan Hay -- License : This Source Code Form is subject to the terms of -- the Mozilla Public License, v. 2.0. -- A copy of the MPL can be found in the LICENSE file or -- you can obtain it at http://mozilla.org/MPL/2.0/. -- Maintainer : Brendan Hay -- Stability : experimental -- Portability : non-portable (GHC extensions) module Test.AWS.Data.List (tests) where import Network.AWS.Prelude import Test.AWS.TH import Test.AWS.Types import Test.Tasty import Test.Tasty.HUnit tests :: TestTree tests = testGroup "list" [ testGroup "deserialise xml" [ testCase "entries" $ assertXML unflattened (Entries items) , testCase "flattened" $ assertXML flattened items ] ] data Item = Item { itemText :: Text , itemDate :: Text , itemInt :: Int } deriving (Eq, Show) instance FromXML Item where parseXML x = Item <$> x .@ "Text" <*> x .@ "Date" <*> x .@ "Int" items :: List "Item" Item items = List [ Item { itemText = "828ef3fdfa96f00ad9f27c383fc9ac7" , itemDate = "2006-01-01T12:00:00.000Z" , itemInt = 5 } , Item { itemText = "fe3f123jfa96f00ad9f27c383fc9sd1" , itemDate = "2014-11-02T01:20:12" , itemInt = 123 } ] unflattened :: LazyByteString unflattened = [doc| foo N Ned 2006-01-01T12:00:00.000Z 828ef3fdfa96f00ad9f27c383fc9ac7 5 2014-11-02T01:20:12 fe3f123jfa96f00ad9f27c383fc9sd1 123 |] flattened :: LazyByteString flattened = [doc| foo N Ned 2006-01-01T12:00:00.000Z 828ef3fdfa96f00ad9f27c383fc9ac7 5 2014-11-02T01:20:12 fe3f123jfa96f00ad9f27c383fc9sd1 123 |]