module Network.OpenID.Types (
AssocType(..)
, SessionType(..)
, Association(..)
, Params
, ReturnTo
, Realm
, Resolver
, Provider
, parseProvider
, showProvider
, providerURI
, modifyProvider
, Identifier(..)
, Error(..)
, assocString
) where
import Data.List
import Data.Word
import Network.URI
import Network.HTTP
import Network.Stream
data AssocType = HmacSha1 | HmacSha256
deriving (Read,Show)
assocString :: AssocType -> String
assocString HmacSha1 = "HMAC-SHA1"
assocString HmacSha256 = "HMAC-SHA256"
data SessionType = NoEncryption | DhSha1 | DhSha256
instance Show SessionType where
show NoEncryption = "no-encryption"
show DhSha1 = "DH-SHA1"
show DhSha256 = "DH-SHA256"
instance Read SessionType where
readsPrec _ str
| "no-encryption" `isPrefixOf` str = [(NoEncryption, drop 13 str)]
| "DH-SHA1" `isPrefixOf` str = [(DhSha1, drop 7 str)]
| "DH-SHA256" `isPrefixOf` str = [(DhSha256, drop 9 str)]
| otherwise = []
data Association = Association
{ assocExpiresIn :: Int
, assocHandle :: String
, assocMacKey :: [Word8]
, assocType :: AssocType
} deriving (Show,Read)
type Params = [(String,String)]
type ReturnTo = String
type Realm = String
type Resolver m = Request String -> m (Either ConnError (Response String))
newtype Provider = Provider { providerURI :: URI } deriving (Eq,Show)
parseProvider :: String -> Maybe Provider
parseProvider = fmap Provider . parseURI
showProvider :: Provider -> String
showProvider (Provider uri) = uriToString (const "") uri []
modifyProvider :: (URI -> URI) -> Provider -> Provider
modifyProvider f (Provider uri) = Provider (f uri)
newtype Identifier = Identifier { getIdentifier :: String }
deriving (Eq,Show,Read)
newtype Error = Error String deriving Show