[Haskell-cafe] Classes: functional dependency (type -> value)
Belka
lambda-belka at yandex.ru
Sun May 10 09:21:39 EDT 2009
Hello, communion people!
I seek for your advice in a matter, where it's really hard for me to
determine a good programming style.
Here's the problem. I'm generalizing multiple authorization procedures to
one, using class definition. (if of any interest, the code is in the end.)
The problem essense is folowing:
----------------
data SomeRole = Role1 | Role2 | Role3
class SomeClass a b c | a -> b, c where
f1 :: ...
f2 :: ...
...
fn :: ...
role :: SomeRole -- <-- here is the problem
I want to have a fuctional dependency from a type "a" on a value of *role*,
so that I could easily "inspect" the *role* from within any other class
members.
Is it possible? Or do I rougly violate some style traditions?
Some real code using wished feature:
---------------------------------------
data AuthentificationPurpose = JustValidateInput | JustGenerateForOutput |
ValidateInputAndGenerateForOutput
type AuthSucceded = Bool
class AuthentificationStructure t_env t_realInput t_assumption t_keySet |
t_realInput -> t_assumptionInput, t_keySet where
authentificationPurpose :: AuthentificationPurpose
makeAssumption :: t_env -> t_realInput -> IO (Either ErrorMessage
t_assumption)
makeFinalKeySet :: (t_realInput, t_assumption) -> t_keySet
validateRealKeySet_with_Assumed :: t_realInput -> t_keySet -> Maybe
ErrorMessage
tryLogTheValidKey :: t_env -> (t_realInput, t_assumption)
-> IO (Maybe ErrorMessage)
tryLogTheAuthTry :: t_env -> (t_realInput, t_assumption,
AuthSucceded) -> IO (Maybe ErrorMessage)
authentificate :: AuthentificationStructure t_env t_realInput
t_assumptionInput t_keySet => t_env -> t_businessInput -> IO (Either
ErrorMessage (t_assumption, t_keySet))
authentificate env realInput = do err_or_assumption <- makeAssumption env
realInput
case err_or_assumption of
Left err_msg -> return $ Left "Error!
Assumption maker failed. Lower level error message: " ++ err_msg
Just assumption -> do
key_set <- makeFinalKeySet
(realInput, assumption)
err_or_keyset1 <- case
authentificationPurpose of
JustGenerateForOutput -> return $ Right key_set
JustValidateInput -> do
mb_failure <- validateRealKeySet_with_Assumed t_realInput key_set
case mb_failure of
Just err_msg -> return $ Left "Error! Invalid set of auth keys. Lower level
error message: " ++ err_msg
Nothing -> return $ Right key_set
ValidateInputAndGenerateForOutput
err_or_keyset2 <- case
err_or_keyset1 of
Left
err_msg -> return err_or_keyset1
Right key_set -> do
mb_failure <- tryLogTheValidKey env (realInput, assumption)
case mb_failure of
Just err_msg -> return $ Left "Error! Could not log valid key. Lower level
error message: " ++ err_msg
Nothing -> return err_or_keyset1
mb_failure <-
tryLogTheAuthTry env (realInput, assumption, isRight err_or_keyset2)
case mb_failure of
Just err_msg1 -> case
err_or_keyset2 of
Left err_msg2 -> return $ Left ("1. " ++ err_msg2 ++ "\n2. " ++ err_msg1)
Right _ -> return $ Left err_msg1
Nothing -> case
err_or_keyset2 of
Left err_msg -> return $ Left err_msg
Right key_set -> return $ Right (assumption, key_set)
---------------------------------
Best regards, Belka
--
View this message in context: http://www.nabble.com/Classes%3A-functional-dependency-%28type--%3E-value%29-tp23470077p23470077.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
More information about the Haskell-Cafe
mailing list