{-# LANGUAGE OverloadedStrings #-} -- | -- Module : Test.AWS.Data.List -- Copyright : (c) 2013-2015 Brendan Hay -- License : Mozilla Public License, v. 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.Util import Test.Tasty tests :: TestTree tests = testGroup "list" [ testGroup "query" [ testGroup "serialise" [ testGroup "non-flattened" [ testToQuery "absent" "x.name=absent" (NonFlat "absent" absent) , testToQuery "primitive" "x.itemSet.item.1=1&x.itemSet.item.2=2&x.itemSet.item.3=3&x.name=primitive" (NonFlat "primitive" (Just ([1, 2, 3] :: [Int]))) , testToQuery "complex" "x.itemSet.item.1.value=1&x.itemSet.item.2.value=2&x.name=complex" (NonFlat "complex" (Just [Item 1, Item 2])) ] , testGroup "flattened" [ testToQuery "absent/empty" "x.name=empty" (Flat "empty" empty) , testToQuery "primitive" "x.item.1=4&x.item.2=5&x.item.3=6&x.name=primitive" (Flat "primitive" (Just ([4, 5, 6] :: [Int]))) , testToQuery "complex" "x.item.1.value=9&x.item.2.value=10&x.name=complex" (Flat "complex" (Just [Item 9, Item 10])) ] ] ] , testGroup "xml" [ testGroup "deserialise" [ testGroup "non-flattened" [ testFromXML "absent" "absent" (NonFlat "absent" absent) , testFromXML "empty" "empty" (NonFlat "empty" absent) , testFromXML "primitive" "primitive123" (NonFlat "primitive" (Just ([1, 2, 3] :: [Int]))) , testFromXML "complex" "complex12" (NonFlat "complex" (Just [Item 1, Item 2])) ] , testGroup "flattened" [ testFromXML "absent/empty" "empty" (Flat "empty" empty) , testFromXML "primitive" "primitive456" (Flat "primitive" (Just ([4, 5, 6] :: [Int]))) , testFromXML "complex" "complex910" (Flat "complex" (Just [Item 9, Item 10])) ] ] , testGroup "serialise" [ testGroup "non-flattened" [ testToXML "absent" "absent" (NonFlat "absent" absent) , testToXML "primitive" "primitive123" (NonFlat "primitive" (Just ([1, 2, 3] :: [Int]))) , testToXML "complex" "complex12" (NonFlat "complex" (Just [Item 1, Item 2])) ] , testGroup "flattened" [ testToXML "absent/empty" "empty" (Flat "empty" empty) , testToXML "primitive" "primitive456" (Flat "primitive" (Just ([4, 5, 6] :: [Int]))) , testToXML "complex" "complex910" (Flat "complex" (Just [Item 9, Item 10])) ] ] ] ] empty :: Maybe [Int] empty = Just [] absent :: Maybe [Int] absent = Nothing data NonFlat a = NonFlat Text (Maybe [a]) deriving (Eq, Show) instance ToQuery a => ToQuery (NonFlat a) where toQuery (NonFlat n x) = mconcat [ "name" =: n , "itemSet" =: toQuery (toQueryList "item" <$> x) ] instance FromXML a => FromXML (NonFlat a) where parseXML x = NonFlat <$> x .@ "name" <*> (x .@? "itemSet" .!@ mempty >>= may (parseXMLList "item")) instance ToXML a => ToXML (NonFlat a) where toXML (NonFlat n x) = mconcat [ "name" @= n , "itemSet" @= toXML (toXMLList "item" <$> x) ] data Flat a = Flat Text (Maybe [a]) deriving (Eq, Show) instance ToQuery a => ToQuery (Flat a) where toQuery (Flat n x) = mconcat [ "name" =: n , toQuery (toQueryList "item" <$> x) ] instance FromXML a => FromXML (Flat a) where parseXML x = Flat <$> x .@ "name" <*> may (parseXMLList "item") x instance ToXML a => ToXML (Flat a) where toXML (Flat n x) = mconcat [ "name" @= n , toXML (toXMLList "item" <$> x) ] newtype Item = Item Int deriving (Eq, Show) instance ToQuery Item where toQuery (Item n) = "value" =: n instance FromXML Item where parseXML x = Item <$> x .@ "value" instance ToXML Item where toXML (Item n) = "value" @= n