Skip to content

Instantly share code, notes, and snippets.

@lorenzo
Last active October 27, 2016 10:33
Show Gist options
  • Save lorenzo/02f541cb5735ec0df41a075464147bac to your computer and use it in GitHub Desktop.
Save lorenzo/02f541cb5735ec0df41a075464147bac to your computer and use it in GitHub Desktop.
src/Main.hs:43:33: error:
• Couldn't match type ‘()’ with ‘[Prop]’
Expected type: C.ConduitM (Maybe [Prop]) () (ResourceT IO) ()
Actual type: C.ConduitM (Maybe ()) () (ResourceT IO) ()
• In the second argument of ‘(=$=)’, namely ‘cleanChunks’
In the expression: parseHotels =$= cleanChunks
In an equation for ‘streamResults’:
streamResults = parseHotels =$= cleanChunks
{-# LANGUAGE OverloadedStrings #-}
module Main where
import Control.Monad (void)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Resource
import qualified Conduit as C
import Data.Conduit (($$), (=$), (.|), (=$=))
import qualified Data.Conduit.Combinators as CC
import qualified Data.Conduit.List as CL
import Data.Maybe (fromMaybe)
import Data.Text (Text, unpack)
import Text.XML.Stream.Parse
import Text.Read (readMaybe)
data Hotel = Hotel
{ identifier :: !Int
, name :: !Text
, address :: !Text
, country :: !Text
} deriving (Show, Eq)
data Prop
= Name !Text
| Country !Text
| Address !Text
| City !Text
| ID !Int
| Lat !Float
| Lng !Float
| Reviews !Int
| Rating !Float
| Stars !Float
deriving (Show, Eq)
main :: IO ()
main =
runResourceT $
parseFile def "hotelscombined.xml" $$ streamResults =$=
CL.mapM_ (lift . print)
streamResults = parseHotels =$= cleanChunks
cleanChunks = CL.catMaybes =$= chunker 5
chunker n = do
xs <- C.takeC n
C.yield xs
parseHotels = void $ tagNoAttr "Hotels" $ manyYield parseHotel
parseHotel = tagNoAttr "Hotel" $ choose [hotelParser]
hotelParser = do
props <- manyIgnore propParser ignoreParser
return $
case props of
Country "GB":ps -> Just ps
_ -> Nothing
ignoreParser = ignoreTree (`notElem` goodTags)
propParser =
choose
[ textParser "CountryCode" Country
, textParser "HotelAddress" Address
, textParser "HotelName" Name
, numberParser "HotelID" ID
, numberParser "Latitude" Lat
, numberParser "Longitude" Lng
, numberParser "NumberOfReviews" Reviews
, numberParser "OverallRating" Rating
, textParser "PlaceName" City
, numberParser "StarRating" Stars
]
textParser name constructor = do
str <- tagNoAttr name content
return $
case str of
Just "" -> Nothing
Just x -> Just (constructor x)
_ -> Nothing
numberParser name constructor = do
a <- tagNoAttr name content
return $
case a of
Just x -> constructor <$> (readMaybe . unpack) x
_ -> Nothing
goodTags =
[ "HotelName"
, "CountryCode"
, "HotelAddress"
, "HotelID"
, "Latitude"
, "Longitud"
, "NumberOfReviews"
, "OverallRating"
, "PlaceName"
, "StarRating"
]
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment