Dealing with configuration data

Liyang Hu liyang@nerv.cx
Fri, 27 Sep 2002 04:16:20 +0100


--oJ71EGRlYNjSvfq7
Content-Type: multipart/mixed; boundary="wq9mPyueHGvFACwf"
Content-Disposition: inline


--wq9mPyueHGvFACwf
Content-Type: text/plain; charset=us-ascii
Content-Disposition: inline
Content-Transfer-Encoding: quoted-printable

Evening all,

Thanks for all the replies and suggestions! They've been extremely
helpful.

On Wed, Sep 25, 2002 at 04:34:02PM -0700, Hal Daume III wrote:
> Okay, this is "bad" but I claim it's okay, iff it is used as in:

In the end, I opted for the global IORef through unsafePerformIO scheme;
implicit parameters seemed too `bleedin' edge' for me... (that and I had
in mind to also retro-fit the idea on top of WASH-CGI[0]; I don't want
to make more changes than I absolutely have to.)

(I haven't yet read John Hughes' paper on the topic though; that should
be quite fun.)

One thing to watch out for though: hGetContents is *not* your friend. At
least it isn't if you're going to let it defer its work until you're
inside modifyIORef... see the attached prefs.hs, line 28 onwards. Just
for reference, I'm using GHC 5.02.2.

I must have went almost insane trying to figure out why I was still
getting the default settings, when every single line of the code seemed
to state the contrary; I had already written up prefs.hs to post to the
list to ask for help, when I noticed that if I put in the line ``mapM_
putStrLn kvs'' before I update the IORef, I get my new settings. If
I leave it out, I get the defaults. Then it hit me -- hGetContents was
lazily deferring its reads. A quickie alternative hGetLines seems to
have fixed the problem.

But I'm still not sure *why* that was a problem in the first place...
Can anyone explain? (Looking at the library source didn't help.) Surely
modifyIORef would have reduced kvs to head normal form (correct termino-
logy?) just like putStrLn did?

*sigh* This can't be good for my mental health. <g>

Thanks everyone,
/Liyang
BTW: I'm on both the main and -cafe lists; you don't have to CC me. ^_-
[0] http://www.informatik.uni-freiburg.de/~thiemann/WASH/
--=20
=2E--{ Liyang HU }--{ http://nerv.cx/ }--{ Caius@Cam }--{ ICQ: 39391385 }--.
| ``Computer games don't affect kids, I mean if Pac Man affected us as   |
| kids, we'd all be running around in darkened rooms, munching pills and |
| listening to repetitive music.''                                       |

--wq9mPyueHGvFACwf
Content-Type: text/plain; charset=us-ascii
Content-Disposition: attachment; filename="prefs.hs"

module Main where

import Prelude
import Char ( isSpace, toLower )
import IO
import IOExts ( IORef, modifyIORef, newIORef, readIORef, unsafePerformIO )

-- Bung everything inside a record, to save us multiple IORefs
data Config = Config
    { cfgSomeSetting :: String }

configRef = unsafePerformIO $ newIORef $ Config
    { cfgSomeSetting = "this is the default setting" }

config = unsafePerformIO $ readIORef configRef

-- as a shortcut / compatibility with existing code
someSetting = cfgSomeSetting config

-- returns lines in reverse order, I know, but it's irrelevant
hGetLines h = get [] where
    get ls = (hGetLine h >>= get . (: ls)) `catch` (const $ return ls)

-- *should* be called first thing in main (if at all);
-- otherwise madness ensues...
loadConfig :: FilePath -> IO ()
loadConfig conf = bracket (openFile conf ReadMode) hClose $ \ h -> do
    kvs <- fmap (map keyVal . filter isNotComment . lines) (hGetContents h)
    --kvs <- fmap (map keyVal . filter isNotComment) (hGetLines h)
    --mapM_ putStrLn kvs
    modifyIORef configRef (\ c -> foldl cfgLine c kvs) where
    keyVal s = (map toLower key, dropWhile isSpace rest)
        where (key, rest) = break isSpace s

    isNotComment ('#':_) = False
    isNotComment []      = False
    isNotComment _       = True

    cfgLine c ("setting", v) = c { cfgSomeSetting = v }
    cfgLine c _ = c -- ignore everything else

main = do
    loadConfig "prefs.conf"
    local <- readIORef configRef
    mapM_ putStrLn [ cfgSomeSetting local, cfgSomeSetting config, someSetting ]


--wq9mPyueHGvFACwf
Content-Type: text/plain; charset=us-ascii
Content-Disposition: attachment; filename="prefs.conf"

# ignored
setting overridden


--wq9mPyueHGvFACwf
Content-Type: text/plain; charset=us-ascii
Content-Disposition: attachment; filename=Makefile

GHC=ghc -O2
PACKAGES=-package lang
SRC=prefs.hs

all: $(SRC:.hs=)

%: %.hs
	@$(GHC) --make $(@) -o $@ $(PACKAGES) $<

clean:
	rm -f *.hi *.o $(SRC:.hs=)

.PHONY: clean ghci


--wq9mPyueHGvFACwf--

--oJ71EGRlYNjSvfq7
Content-Type: application/pgp-signature
Content-Disposition: inline

-----BEGIN PGP SIGNATURE-----
Version: GnuPG v1.0.6 (GNU/Linux)
Comment: moo! (ID: 7B632CB8)

iEYEARECAAYFAj2TzYQACgkQ1QR4EHtjLLg3JgCgwhm+pMumR6XdWTxz66/F2rya
NrcAoI75ViSlKhwng0DsJBOBqsdSiC7f
=IGrg
-----END PGP SIGNATURE-----

--oJ71EGRlYNjSvfq7--