--------------------------------------------------------------------
-- |
-- Module      : Flickr.Places
-- Description : flickr.places - geo locating photos.
-- Copyright   : (c) Sigbjorn Finne, 2008
-- License     : BSD3
--
-- Maintainer  : Sigbjorn Finne <sof@forkIO.com>
-- Stability   : provisional
-- Portability : portable
--
-- flickr.places API, locating photos by places and geo.
--------------------------------------------------------------------
module Flickr.Places where

import Flickr.Monad
import Flickr.Types
import Flickr.Types.Import

-- | Return a list of place IDs for a query string.
-- The flickr.places.find method is not a geocoder. 
-- It will round up to the nearest place type to 
-- which place IDs apply. For example, if you pass 
-- it a street level address it will return the city 
-- that contains the address rather than the street, 
-- or building, itself.
find :: String -> FM (PlaceQuery, [Place])
find q = 
  flickTranslate toPlaces $ 
    flickrCall "flickr.places.find"
               [("query", q)]

-- | Return a place ID for a latitude, longitude and accuracy triple.
-- 
-- The flickr.places.findByLatLon method is not meant to be 
-- a (reverse) geocoder in the traditional sense. It is designed
-- to allow users to find photos for "places" and will round
-- up to the nearest place type to which corresponding place IDs 
-- apply.
-- 
-- For example, if you pass it a street level coordinate it will 
-- return the city that contains the point rather than the street, 
-- or building, itself.
-- 
-- It will also truncate latitudes and longitudes to three 
-- decimal points.
findByLatLon :: Latitude -> Longitude -> Maybe Accuracy -> FM (PlaceQuery, [Place])
findByLatLon la lon acc = 
  flickTranslate toPlaces $ 
    flickCall "flickr.places.findByLatLon" 
              (mbArg "accuracy" (fmap show acc) $
	         [("lat", la),("lon", lon)])

-- | Return a list of locations with public photos that are parented by a Where on Earth (WOE) or Places ID.
getChildrenWithPhotosPublic :: Either PlaceID WhereOnEarthID
                            -> FM (PlaceQuery, [Place])
getChildrenWithPhotosPublic pw = 
  flickTranslate toPlaces $
    flickrCall "flickr.places.getChildrenWithPhotosPublic"
               (eiArg "place_id" "woe_id" pw [])

-- | Lookup information about a place, by its flickr.com/places URL.
getInfoByUrl :: URLString -> FM LocationPlace
getInfoByUrl url = 
  flickTranslate toLocationPlace $
    flickrCall "flickr.places.getInfoByUrl"
               [ ("url", url) ]

-- | Get informations about a place.
getInfo :: Either PlaceID WhereOnEarthID -> FM LocationPlace
getInfo pw = 
  flickTranslate toLocationPlace $
    flickrCall "flickr.places.getInfo"
               (eiArg "place_id" "woe_id" pw [])

-- | Return a list of the top 100 unique places clustered by a given placetype for a user. 
placesForUser :: PlaceType
              -> Maybe WhereOnEarthID
	      -> Maybe PlaceID
	      -> Maybe Threshold
	      -> FM [Place]
placesForUser pt woe_id pid th = withReadPerm $
 flickTranslate toPlacesList $
   flickCall "flickr.places.placesForUser" 
             (mbArg "woe_id" woe_id  $ 
	      mbArg "place_id" pid   $
	      mbArg "threshold" (fmap show th) $
  	            [("place_type", pt)])

-- | Find Flickr Places information by Place Id.
resolvePlaceId :: PlaceID -> FM LocationPlace
resolvePlaceId pid = 
  flickTranslate toLocationPlace $
   flickrCall "flickr.places.resolvePlaceId" 
              [("place_id", pid)]

-- | Find Flickr Places information by Place URL.
resolvePlaceURL :: URLString -> FM LocationPlace
resolvePlaceURL purl = 
  flickTranslate toLocationPlace $
    flickrCall "flickr.places.resolvePlaceURL" 
               [("url", purl)]