Challenge: FeatureFlag pure functions

What I mean is that presumably, the rest of the application also needs the database connection, and there wouldnt be a way to share the db connection between the flag-fetching and the rest of the app, youd have to initialize it twice

But this is also moot because for our specific use case, we have to take the db conn in as an argument to our main function, so we’d have to smuggle that into the global unsafePerformIO action anyway

Question: if the program can’t connect to the database, is it expected to keep running, or is it allowed to fail or end?

I mean, yes I agree it’s generally a terrible idea. But I don’t see a better option here, other than making everything monadic or passing a constraint or argument everywhere.

For simplicity, assume it will never fail to connect. It’s not an issue for us, since we get a connection in the entrypoint (again, we have a really weird set up).

That makes me wonder what the application architecture is. For the dumb “parse a set of requests into a set of known functions” case the immutability doesn’t matter: you’d just have a feature flag blob that is woven into every function, then an external request could be used alter the flags.

I think the simplest solution is basically what you did - -XImplicitParams (no need for reflection tbh) + a way to fetch the flags through IO. It really isn’t a complicated problem…

The main complication I can see is if your feature flags type is a record that in turn imports a lot of internal modules for custom types. That is doomed to fail as the project grows - I’ve seen some pretty egregious compilation time waste due to this at scale. But you can use some sort of dynamic solution instead of a record that’d work just as well (e.g. TypeRepMap or one of its friends).

1 Like

If this is a greenfield project, then you could consider investing your efforts in lightning fast build and re-deploy.

That way, your feature flag toggling is changing a line in the source code, which is really what everyone wishes they could do instead of parsing annoying config files.

It’s mentally easier to think about immutable processes—where you tear down the existing thing and make a new fresh thing—rather than modifying a running process in-place.

It’s unlikely GHC Haskell will ever achieve this, though not impossible, but Unison might achieve it if not already; I haven’t used it for something real. That or another CAS-based language; only in that setting can you avoid recompiling and run only the tests that need to re-run. Achieving redeploy of a large service measured in seconds is barely imaginable in any other setting.

I personally think it’s a good mental exercise to consider many types of problems (such as this one) as symptomatic of deployment pain. Having to stick IO in our code to “cheat” when really what we want is faster updates is a bit sad, but practical.

3 Likes

In theory, I’d agree. Except if your greenfield project is deployed as a feature in a legacy system that has a really long deploy cycle. Say, perhaps, the greenfield project is a binary that the legacy system calls to do a thing, and for security reasons, that binary has to be bundled with the legacy system instead of being able to be pulled from some repository, which can be updated out of band

It won’t be a “better” option at all once this is implemented:

  • with mutual exclusion, all threads will have to wait their turn to access the DB, so not much better that being -single-threaded;

  • without mutual exclusion - are you absolutely sure that DB is immutable? If not, joyous nondeterminism awaits…


So assuming (!!!) the DB is immutable, and each access of it doesn’t have secondary effects that the rest of the program can observe…the DB could be treated as one large implicit argument to the entire program, in the same way $+ in Miranda™ was. But you only have to look at the GHC DynFlags experience to see how badly that can go wrong.

The only other suggestion I can think of right now would be to look at:

…maybe you can reuse the technique it describes.

Main.hs:

import System.IO.Unsafe

import Flags

experimental_f = 4

f :: Integer -> Integer
f x
    | flag = x * 2
    | otherwise = x * 4
    where
        flag = unsafePerformIO $ getFlag experimental_f

main :: IO ()
main = do
    print $ f 10
    setFlag experimental_f True
    print $ f 10
    setFlag experimental_f False
    print $ f 10
    print "done"

Flags.hs:

{-# LANGUAGE CApiFFI #-}

module Flags (
    getFlag,
    setFlag
) where

import Foreign.C.Types

foreign import capi "libflags.h flags" c_flags :: CInt -> CInt -> CInt -> IO CInt

getFlag :: Integer -> IO Bool
getFlag flag = do
    v <- c_flags (CInt 0) (CInt (fromInteger flag)) (CInt 0)
    return $ if v == 0 then False else True

setFlag :: Integer -> Bool -> IO ()
setFlag flag value = do
    _ <- c_flags (CInt 1) (CInt (fromInteger flag)) (CInt (if value then 1 else 0))
    return ()

libflags.h:

int flags(int mode, int flag, int value);

libflags.c:

int flags(int mode, int flag, int value) {
    static int f[128] = {0};
    return mode ? f[flag] = value : f[flag];
}

GHC is the greatest C compiler, you get Haskell for free.

2 Likes

The mention of pure functions in the title piqued my interest. I have been wanting to write a blog entry that includes use of the dependent-sum and dependent-map packages, and this topic is a good one.

TLDR:

data FeatureFlag :: Type -> Type where
  Fix_202407_SomeBug_42 :: FeatureFlag Bool
  Ref_202407_SomeBusinessLogic :: FeatureFlag Bool

deriveGEq ''FeatureFlag
deriveGCompare ''FeatureFlag
deriveGShow ''FeatureFlag

type FeatureFlagMap = DMap FeatureFlag Identity

newtype FeatureFlagConfig (tag :: FeatureFlag a)
  = FeatureFlagConfig
    { config :: Maybe a
    }
  deriving (Eq, Show)

lookup
  :: FeatureFlag a
  -> FeatureFlagMap
  -> FeatureFlagConfig (tag :: FeatureFlag a)
lookup ff = FeatureFlagConfig . fmap runIdentity . DMap.lookup ff

Details:

  1. Problem definition blog
  2. Implementation using a global, without tagged configuration blog
  3. Implementation using a global, with tagged configuration blog
  4. Tests blog
    • Without tagged configuration tests
    • With tagged configuration tests
2 Likes