This repository has been archived on 2025-03-02. You can view files and clone it, but cannot push or open issues or pull requests.
phi/lib/Phi/X11/Atoms.hs

41 lines
1.5 KiB
Haskell
Raw Normal View History

2011-07-12 19:09:05 +02:00
{-# LANGUAGE TemplateHaskell #-}
module Phi.X11.Atoms ( Atoms(..)
, initAtoms
) where
import Control.Monad
import Language.Haskell.TH
import Graphics.X11
import Phi.X11.AtomList
2011-07-13 02:13:01 +02:00
$(let atomsName = mkName "Atoms"
2011-07-17 19:20:19 +02:00
atomNames = map (\atom -> (atom, mkName ("atom" ++ atom))) $ atoms ++ (map fst specialAtoms)
2011-07-13 02:13:01 +02:00
fields = map (\(_, name) -> (name, IsStrict, ConT ''Atom)) atomNames
in return [DataD [] atomsName [] [RecC atomsName fields] []]
2011-07-12 19:09:05 +02:00
)
initAtoms :: Display -> IO Atoms
initAtoms display =
$(do
2011-07-17 19:20:19 +02:00
normalAtomNames <- mapM (\atom -> do
2011-07-12 19:09:05 +02:00
varName <- newName ('_':atom)
2011-07-17 19:20:19 +02:00
return ([|const atom|], mkName ("atom" ++ atom), varName)
2011-07-12 19:09:05 +02:00
) atoms
2011-07-17 19:20:19 +02:00
specialAtomNames <- mapM (\(name, atomgen) -> do
varName <- newName ('_':name)
return (atomgen, mkName ("atom" ++ name), varName)
) specialAtoms
let atomNames = normalAtomNames ++ specialAtomNames
2011-07-12 19:09:05 +02:00
atomInitializers <- forM atomNames $
2011-07-17 19:20:19 +02:00
\(atomgen, _, varName) -> liftM (BindS (VarP varName)) [| internAtom display ($atomgen display) False |]
2011-07-12 19:09:05 +02:00
let atomFieldExps = map (\(_, atomName, varName) -> (atomName, VarE varName)) atomNames
2011-07-13 02:13:01 +02:00
atomsName = mkName "Atoms"
2011-07-12 19:09:05 +02:00
atomsContruction = NoBindS $ AppE (VarE 'return) $ RecConE atomsName atomFieldExps
return $ DoE $ atomInitializers ++ [atomsContruction]
)