Classes: functional dependency (type -> value)

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... Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

Hello! The problem is that it's impossible to infer the SomeClass instance from the type SomeRole. If you do "print role", which instance should it use? I can think of two ways around it: -- 1. (dummy parameter) ------------------------------ data SomeRole a = Role1 | Role2 | Role3 deriving Show class SomeClass a where role :: SomeRole a data Foo = Foo data Bar = Bar instance SomeClass Foo where role = Role1 instance SomeClass Bar where role = Role2 main = do print (role :: SomeRole Foo) print (role :: SomeRole Bar) -- 2. (dummy argument) ------------------------------ data SomeRole = Role1 | Role2 | Role3 deriving Show class SomeClass a where role :: a -> SomeRole data Foo = Foo data Bar = Bar instance SomeClass Foo where role _ = Role1 instance SomeClass Bar where role _ = Role2 main = do print (role (undefined :: Foo)) print (role (undefined :: Bar)) ------------------------------ On Sunday 10 May 2009 15:21:39 Belka wrote:
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

2009/05/10 Belka
Some real code using wished feature:
This code has multiple issues: . It is nearly unreadable as formatted. . There are actual errors that would prevent it from compiling (pattern match on `Left` and `Just` in the same `case` expression!). Please amend the code so it is easier to read and test. -- Jason Dusek

Belka wrote:
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?
The problem is that when you write role there is no way to choose the right instance? That is, where does the compiler get a, b, c from when looking just at an invocation of role ? Therefore, the type of role has to involve a , for example as in class SomeClass a b c ... where ... role :: a -> SomeRole and used as role (undefined :: Foo) That being said, I think that type classes are not what you want here. I suggest to simply use a regular data type data SomeThing a b c = SomeThing { f1 :: ... , f2 :: ... ... , fn :: ... , role :: SomeRole } Remember that f1, f2, ... can be functions, this is a functional language, after all! "Instances" are then simply a concrete value, like for example thething :: SomeThing Foo Bar Baz thething = SomeThing { f1 = id , f2 = filter (>3) . map length , ... , role = Role1 } Regards, apfelmus -- http://apfelmus.nfshost.com
participants (4)
-
Belka
-
Daniel Schüssler
-
Heinrich Apfelmus
-
Jason Dusek