module Network.OpenID.Normalization where
import Network.OpenID.Types
import Control.Applicative
import Control.Monad
import Data.List
import Network.URI hiding (scheme,path)
normalizeIdentifier :: Identifier -> Maybe Identifier
normalizeIdentifier = normalizeIdentifier' (const Nothing)
normalizeIdentifier' :: (String -> Maybe String) -> Identifier
-> Maybe Identifier
normalizeIdentifier' xri (Identifier str)
| null str = Nothing
| "xri://" `isPrefixOf` str = Identifier `fmap` xri str
| head str `elem` "=@+$!" = Identifier `fmap` xri str
| otherwise = fmt `fmap` (url >>= norm)
where
url = parseURI str <|> parseURI ("http://" ++ str)
norm uri = validScheme >> return u
where
scheme = uriScheme uri
validScheme = guard (scheme == "http:" || scheme == "https:")
u = uri { uriFragment = "", uriPath = path }
path | null (uriPath uri) = "/"
| otherwise = uriPath uri
fmt u = Identifier
$ normalizePathSegments
$ normalizeEscape
$ normalizeCase
$ uriToString (const "") u []