admin管理员组

文章数量:1410682

I have a simple App written in Haskell with a configuration parameter. This parameter should be there in production, but I might like to run the app locally without it. It seems like a waste to check if the parameter is there every time I use it so I would rather check it once an somehow carry around a proof that it is there. I just can't seem to find an ergonomic way of doing this when I have multiple parameters that independently might not be there.

The original app could look like this.

newtype Cfg = Cfg Int deriving Show
newtype CfgA = CfgA Int deriving Show

loadConfig0 :: IO Cfg
loadConfig0 = return $ Cfg 0
loadConfigA :: IO CfgA
loadConfigA = return $ CfgA 1

data MyConfig = MyConfig
 { cfg0 :: Cfg
 , cfgA :: CfgA
 }

doStuffA :: CfgA -> IO ()
doStuffA = putStrLn . show

doStuff :: MyConfig -> IO ()
doStuff = doStuffA . cfgA

runApp :: MyConfig -> IO ()
runApp = doStuff

loadConfig :: IO MyConfig
loadConfig =
  MyConfig <$> loadConfig0 <*> loadConfigA

main :: IO ()
main = loadConfig >>= runApp

To allow the parameter to be missing I could just change the config type

data MyConfig = MyConfig
 { cfg0 :: Cfg
 , cfgA :: Maybe CfgA
 }
data NoConfigFound = NoConfigFound deriving (Show,Exception)
doStuffA' :: (Maybe CfgA) -> IO ()
doStuffA' Nothing = throwIO NoConfigFound
doStuffA' (Just cfgA) = doStuffA cfgA

But then I check if the configuration parameter is there everytime I use it. Why not check it once and carry around this proof?

I came of with these changes (plus changes to some type-signatures)

data MyConfig f = MyConfig
 { cfg0 :: Cfg
 , cfgA :: f CfgA
 }
class DoStuffA cfg where
  doStuffA' :: cfg -> IO ()

instance DoStuffA (MyConfig Proxy) where
  doStuffA' _ = throwIO NoConfigFound

instance DoStuffA (MyConfig Identity) where
  doStuffA' = doStuffA . runIdentity . cfgA

data SomeConfig =
  forall f. DoStuffA (MyConfig f) => SomeConfig (MyConfig f)

loadConfig :: IO SomeConfig
loadConfig = do
  cfg0 <- loadConfig0
  loadConfigA >>= return . \case
    Nothing -> SomeConfig $ MyConfig cfg0 Proxy
    Just cfgA -> SomeConfig $ MyConfig cfg0 (Identity cfgA)

runApp' :: SomeConfig -> IO ()
runApp' (SomeConfig cfg) = runApp cfg

This works. However, if I have many different configuration parameters that independently might not be there then this approach get's out of hand. Every instance declaration will have 10 type parameters only distinguished by the order and the loadConfig will have an impossible amount of cases to check.

-- What parameter is what?
-- This is why we have records at the value level, but what to do at the type level?
instance DoStuffA (MyConfig Proxy b d c e f) where
  doStuffA' _ = throwIO NoConfigFound


loadConfig :: IO SomeConfig
loadConfig = do
  cfg0 <- loadConfig0
  cfgA <- loadConfigA
  cfgB <- loadConfigB
  cfgC <- loadConfigC
  cfgD <- loadConfigD
  return $ case (cfgA,cfgB,cfgC,cfgD) of
    (Nothing,Nothing,Nothing,Nothing) ->
       SomeConfig $ MyConfig (Identity cfg0) Proxy Proxy Proxy Proxy
     ??????

Am I missing something obvious here? Is there some elegant way of solving this or a different way of solving the original problem? Or is this simple not worth it - just stick with the Maybe types from the second example. Maybe all these extra classes is actually worse than just checking the maybe type...

I also tried this type

data MyConfig a = MyConfig
 { cfg0 :: Cfg
 , cfgA :: a
 }

but the code was mostly the same

Hope to get your input on this!

I have a simple App written in Haskell with a configuration parameter. This parameter should be there in production, but I might like to run the app locally without it. It seems like a waste to check if the parameter is there every time I use it so I would rather check it once an somehow carry around a proof that it is there. I just can't seem to find an ergonomic way of doing this when I have multiple parameters that independently might not be there.

The original app could look like this.

newtype Cfg = Cfg Int deriving Show
newtype CfgA = CfgA Int deriving Show

loadConfig0 :: IO Cfg
loadConfig0 = return $ Cfg 0
loadConfigA :: IO CfgA
loadConfigA = return $ CfgA 1

data MyConfig = MyConfig
 { cfg0 :: Cfg
 , cfgA :: CfgA
 }

doStuffA :: CfgA -> IO ()
doStuffA = putStrLn . show

doStuff :: MyConfig -> IO ()
doStuff = doStuffA . cfgA

runApp :: MyConfig -> IO ()
runApp = doStuff

loadConfig :: IO MyConfig
loadConfig =
  MyConfig <$> loadConfig0 <*> loadConfigA

main :: IO ()
main = loadConfig >>= runApp

To allow the parameter to be missing I could just change the config type

data MyConfig = MyConfig
 { cfg0 :: Cfg
 , cfgA :: Maybe CfgA
 }
data NoConfigFound = NoConfigFound deriving (Show,Exception)
doStuffA' :: (Maybe CfgA) -> IO ()
doStuffA' Nothing = throwIO NoConfigFound
doStuffA' (Just cfgA) = doStuffA cfgA

But then I check if the configuration parameter is there everytime I use it. Why not check it once and carry around this proof?

I came of with these changes (plus changes to some type-signatures)

data MyConfig f = MyConfig
 { cfg0 :: Cfg
 , cfgA :: f CfgA
 }
class DoStuffA cfg where
  doStuffA' :: cfg -> IO ()

instance DoStuffA (MyConfig Proxy) where
  doStuffA' _ = throwIO NoConfigFound

instance DoStuffA (MyConfig Identity) where
  doStuffA' = doStuffA . runIdentity . cfgA

data SomeConfig =
  forall f. DoStuffA (MyConfig f) => SomeConfig (MyConfig f)

loadConfig :: IO SomeConfig
loadConfig = do
  cfg0 <- loadConfig0
  loadConfigA >>= return . \case
    Nothing -> SomeConfig $ MyConfig cfg0 Proxy
    Just cfgA -> SomeConfig $ MyConfig cfg0 (Identity cfgA)

runApp' :: SomeConfig -> IO ()
runApp' (SomeConfig cfg) = runApp cfg

This works. However, if I have many different configuration parameters that independently might not be there then this approach get's out of hand. Every instance declaration will have 10 type parameters only distinguished by the order and the loadConfig will have an impossible amount of cases to check.

-- What parameter is what?
-- This is why we have records at the value level, but what to do at the type level?
instance DoStuffA (MyConfig Proxy b d c e f) where
  doStuffA' _ = throwIO NoConfigFound


loadConfig :: IO SomeConfig
loadConfig = do
  cfg0 <- loadConfig0
  cfgA <- loadConfigA
  cfgB <- loadConfigB
  cfgC <- loadConfigC
  cfgD <- loadConfigD
  return $ case (cfgA,cfgB,cfgC,cfgD) of
    (Nothing,Nothing,Nothing,Nothing) ->
       SomeConfig $ MyConfig (Identity cfg0) Proxy Proxy Proxy Proxy
     ??????

Am I missing something obvious here? Is there some elegant way of solving this or a different way of solving the original problem? Or is this simple not worth it - just stick with the Maybe types from the second example. Maybe all these extra classes is actually worse than just checking the maybe type...

I also tried this type

data MyConfig a = MyConfig
 { cfg0 :: Cfg
 , cfgA :: a
 }

but the code was mostly the same

Hope to get your input on this!

Share asked Mar 7 at 11:04 user1830971user1830971 431 silver badge3 bronze badges
Add a comment  | 

3 Answers 3

Reset to default 6

Trees that grow is a technique to deal with this kind of configuration.

Instead of having many parameters for the different combinations of available configuration, you have a single parameter that determines the available configurations via a type family.

data MyConfig p = MyConfig
  { cfgA :: CfgAOf p
  , cfgB :: CfgBOf p
  , cfgC :: CfgCOf p
  ...
  }

type family CfgAOf (p :: Type) :: Type
type family CfgBOf (p :: Type) :: Type
type family CfgCOf (p :: Type) :: Type

-- Full configuration

data Full
type instance CfgAOf Full = CfgA
type instance CfgBOf Full = CfgB
type instance CfgCOf Full = CfgC

-- Nil configuration

data Nil
type instance CfgAOf Nil = ()
type instance CfgBOf Nil = ()
type instance CfgCOf Nil = ()

-- A mixed configuration

data OnlyA
type instance CfgAOf OnlyA = CfgA
type instance CfgBOf OnlyA = ()
type instance CfgCOf OnlyA = ()

Functions that need a configuration to be there can require an equality constraint:

usesCfgA :: GetCfgA p ~ CfgA => MyConfig p -> IO ()
usesCfgA c = ...
  where a = cfgA p -- a :: CfgA

Functions that need to dynamically branch on the presence of a config can do so via a class

class GetCfgA p where
  getCfgA :: MyConfig p -> Maybe CfgA
instance GetCfgA Full where
  getCfgA = Just . cfgA
instance GetCfgA Nil where
  getCfgA _ = Nothing

-- Do something or other depending on the presence of a CfgA
thing :: GetCfgA p => MyConfig p -> IO ()
thing c = case getCfgA c of
  Just a -> ...
  Nothing -> ...

One way would be to replace your data with the actions you can perform on that data, as in the usual alternative to the "existential antipattern". If you're concerned about being able to inspect/debug the configuration, you can make one of the actions you can perform be to return a Maybe with the configuration data inside.

data Cfg = Cfg { cfgA :: CfgA, cfgB :: CfgB }
data CfgA = CfgA { doStuffA :: IO () }
data CfgB = CfgB { cfgB :: Maybe Int, doStuffB :: IO () }

loadCfgA :: IO CfgA
loadCfgA = catch (CfgA . rawDoStuffA <$> readFile "a.cfg") \e ->
    if isDoesNotExistError e
    then pure CfgA { doStuffA = throwIO NoConfigFound }
    else throwIO e

justCfgB :: String -> CfgB
justCfgB b_ = CfgB { cfgB = Just b, doStuffB = rawDoStuffB b }
    where b = read b_

nothingCfgB :: CfgB
nothingCfgB = CfgB { cfgB = Nothing, doStuffB = throwIO NoConfigFound }

loadCfgB :: IO CfgB
loadCfgB = catch (justCfgB <$> readFile "b.cfg") \e ->
    if isDoesNotExistError e
    then pure nothingCfgB
    else throwIO e

loadCfg :: IO Cfg
loadCfg = liftA2 Cfg loadCfgA loadCfgB

Do you actually need to catch and handle NoConfigFound for some reason? If you just expect the program to error out if it ends up trying to access a missing CfgA, have you considered setting cfgA = error "no CfgA specified"?

Ultimately, the most straightforward and efficient type-level witness that a CfgA is available is the CfgA that already appears in doStuff :: CfgA -> IO ().

When it isn't available in a non-production, testing context, it seems legitimate to "fake" the witness with an error value.

本文标签: Type witness for presence of configuration parameters in HaskellStack Overflow