2011-07-12 19:09:05 +02:00
|
|
|
{-# LANGUAGE TemplateHaskell #-}
|
|
|
|
|
|
|
|
module Phi.X11.Atoms ( Atoms(..)
|
|
|
|
, initAtoms
|
|
|
|
) where
|
|
|
|
|
|
|
|
import Control.Monad
|
2011-09-07 16:38:36 +02:00
|
|
|
import Data.Char
|
|
|
|
import Data.List
|
|
|
|
|
2011-07-12 19:09:05 +02:00
|
|
|
import Language.Haskell.TH
|
2011-09-07 16:38:36 +02:00
|
|
|
import Graphics.XHB
|
|
|
|
import Graphics.XHB.Gen.Xproto
|
2011-07-12 19:09:05 +02:00
|
|
|
|
|
|
|
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-09-07 16:38:36 +02:00
|
|
|
fields = map (\(_, name) -> (name, IsStrict, ConT ''ATOM)) atomNames
|
2011-07-13 02:13:01 +02:00
|
|
|
in return [DataD [] atomsName [] [RecC atomsName fields] []]
|
2011-07-12 19:09:05 +02:00
|
|
|
)
|
|
|
|
|
2011-10-10 23:22:59 +02:00
|
|
|
initAtoms :: ConnectionClass c => c -> IO Atoms
|
2011-09-07 16:38:36 +02:00
|
|
|
initAtoms conn =
|
2011-07-12 19:09:05 +02:00
|
|
|
$(do
|
2011-07-17 19:20:19 +02:00
|
|
|
normalAtomNames <- mapM (\atom -> do
|
2011-09-07 16:38:36 +02:00
|
|
|
receiptName <- newName ('_':atom)
|
2011-07-12 19:09:05 +02:00
|
|
|
varName <- newName ('_':atom)
|
2011-09-07 16:38:36 +02:00
|
|
|
return ([|const atom|], mkName ("atom" ++ atom), receiptName, varName)
|
2011-07-12 19:09:05 +02:00
|
|
|
) atoms
|
2011-07-17 19:20:19 +02:00
|
|
|
specialAtomNames <- mapM (\(name, atomgen) -> do
|
2011-09-07 16:38:36 +02:00
|
|
|
receiptName <- newName ('_':name)
|
2011-07-17 19:20:19 +02:00
|
|
|
varName <- newName ('_':name)
|
2011-09-07 16:38:36 +02:00
|
|
|
return (atomgen, mkName ("atom" ++ name), receiptName, varName)
|
2011-07-17 19:20:19 +02:00
|
|
|
) specialAtoms
|
|
|
|
let atomNames = normalAtomNames ++ specialAtomNames
|
2011-09-07 16:38:36 +02:00
|
|
|
atomReceipts <- forM atomNames $
|
|
|
|
\(atomgen, _, receiptName, _) -> liftM (BindS (VarP receiptName))
|
|
|
|
[|let name = ($atomgen conn)
|
|
|
|
in internAtom conn $ MkInternAtom False (genericLength name) $ map (fromIntegral . ord) name|]
|
2011-07-12 19:09:05 +02:00
|
|
|
atomInitializers <- forM atomNames $
|
2011-09-07 16:38:36 +02:00
|
|
|
\(_, _, receiptName, varName) -> liftM (BindS (VarP varName))
|
|
|
|
[|liftM (\(Right a) -> a) $ getReply $(return $ VarE receiptName)|]
|
|
|
|
|
|
|
|
|
|
|
|
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
|
|
|
|
|
2011-09-07 16:38:36 +02:00
|
|
|
return $ DoE $ atomReceipts ++ atomInitializers ++ [atomsContruction]
|
2011-07-12 19:09:05 +02:00
|
|
|
)
|