summaryrefslogtreecommitdiff
path: root/ghc/compiler/parser/UgenUtil.lhs
blob: 5530035f1d150a48dca0e22db040dd0071ccdb9e (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
Glues lots of things together for ugen-generated
.hs files here

\begin{code}
module UgenUtil (
	-- stuff defined here
	module UgenUtil,
	Addr
    ) where

#include "HsVersions.h"

import GlaExts
import Name
import SrcLoc		( mkSrcLoc, noSrcLoc, SrcLoc )
import FastString	( FastString, mkFastCharString, mkFastCharString2 )
\end{code}

\begin{code}
type UgnM a
  = (FastString,Module,SrcLoc)	   -- file, module and src_loc carried down
  -> IO a

{-# INLINE returnUgn #-}
{-# INLINE thenUgn #-}

returnUgn x stuff = return x

thenUgn x y stuff
  = x stuff	>>= \ z ->
    y z stuff

initUgn :: UgnM a -> IO a
initUgn action = action (SLIT(""),mkSrcModule "",noSrcLoc)

ioToUgnM :: IO a -> UgnM a
ioToUgnM x stuff = x
\end{code}

\begin{code}
type ParseTree = Addr

type U_VOID_STAR = Addr
rdU_VOID_STAR ::  Addr -> UgnM U_VOID_STAR
rdU_VOID_STAR x = returnUgn x

type U_long = Int
rdU_long ::  Int -> UgnM U_long
rdU_long x = returnUgn x

type U_stringId = FastString
rdU_stringId :: Addr -> UgnM U_stringId
{-# INLINE rdU_stringId #-}
rdU_stringId s = returnUgn (mkFastCharString s)

type U_numId = Int -- ToDo: Int
rdU_numId :: Addr -> UgnM U_numId
rdU_numId i = rdU_stringId i `thenUgn` \ y -> returnUgn ((read (_UNPK_ y))::Int)

type U_hstring = FastString
rdU_hstring :: Addr -> UgnM U_hstring
rdU_hstring x
  = ioToUgnM (_ccall_ get_hstring_len   x)  `thenUgn` \ len ->
    ioToUgnM (_ccall_ get_hstring_bytes x)  `thenUgn` \ bytes ->
    returnUgn (mkFastCharString2 bytes len)
\end{code}

\begin{code}
setSrcFileUgn :: FastString -> UgnM a -> UgnM a
setSrcFileUgn file action stuff@(_,mod,loc) = action (file,mod,loc)

getSrcFileUgn :: UgnM FastString
getSrcFileUgn stuff@(file,mod,loc) = returnUgn file stuff

setSrcModUgn :: Module -> UgnM a -> UgnM a
setSrcModUgn mod action stuff@(file,_,loc) = action (file,mod,loc)

getSrcModUgn :: UgnM Module
getSrcModUgn stuff@(file,mod,loc) = returnUgn mod stuff

mkSrcLocUgn :: U_long -> (SrcLoc -> UgnM a) -> UgnM a
mkSrcLocUgn ln action (file,mod,_)
  = action loc (file,mod,loc)
  where
    loc = mkSrcLoc file ln

getSrcLocUgn :: UgnM SrcLoc
getSrcLocUgn stuff@(file,mod,loc) = returnUgn loc stuff
\end{code}