Native target
[llpp.git] / Build.hs
blob6a47b45b8f43e88b7fbf6b1cc024162865ab0b22
1 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
2 {-# OPTIONS_GHC -fno-warn-missing-signatures #-}
3 import Data.List
4 import System.Exit
5 import Control.Monad
6 import Control.Concurrent.MVar
7 import Development.Shake
8 import Development.Shake.Util
9 import Development.Shake.Config ()
10 import Development.Shake.Classes
11 import Development.Shake.FilePath
13 newtype OcamlOrdOracle = OcamlOrdOracle String
14 deriving (Show,Typeable,Eq,Hashable,Binary,NFData)
15 newtype OcamlOrdOracleN = OcamlOrdOracleN String
16 deriving (Show,Typeable,Eq,Hashable,Binary,NFData)
17 newtype OcamlCmdLineOracle = OcamlCmdLineOracle String
18 deriving (Show,Typeable,Eq,Hashable,Binary,NFData)
19 newtype OcamlCmdLineOracleN = OcamlCmdLineOracleN String
20 deriving (Show,Typeable,Eq,Hashable,Binary,NFData)
21 newtype CCmdLineOracle = CCmdLineOracle String
22 deriving (Show,Typeable,Eq,Hashable,Binary,NFData)
23 newtype GitDescribeOracle = GitDescribeOracle ()
24 deriving (Show,Typeable,Eq,Hashable,Binary,NFData)
26 outdir = "build"
27 mudir = "/home/malc/x/rcs/git/mupdf"
28 inOutDir s = outdir </> s
30 ocamlc = "ocamlc.opt"
31 ocamlopt = "ocamlopt.opt"
32 ocamldep = "ocamldep.opt"
33 ocamlflags = "-warn-error +a -w +a -g -safe-string"
34 ocamlflagstbl = [("main.cmo", ("-I lablGL", "sed -f pp.sed"))
35 ,("config.cmo", ("-I lablGL", ""))
37 ocamlflagstbln = [("main.cmx", ("-I lablGL", "sed -f pp.sed"))
38 ,("config.cmx", ("-I lablGL", ""))
40 cflags = "-Wall -Werror -D_GNU_SOURCE -O\
41 \ -g -std=c99 -pedantic-errors\
42 \ -Wunused-parameter -Wsign-compare -Wshadow"
43 cflagstbl =
44 [("link.o"
45 ,"-I " ++ mudir ++ "/include -I "
46 ++ mudir ++ "/thirdparty/freetype/include -Wextra")
48 cclib = "-lGL -lX11 -lmupdf -lz -lfreetype -ljpeg\
49 \ -ljbig2dec -lopenjpeg -lmujs\
50 \ -lpthread -L" ++ mudir ++ "/build/native -lcrypto"
52 getincludes :: [String] -> [String]
53 getincludes [] = []
54 getincludes ("-I":arg:tl) = arg : getincludes tl
55 getincludes (_:tl) = getincludes tl
57 isabsinc :: String -> Bool
58 isabsinc [] = False
59 isabsinc (hd:_) = hd == '+' || hd == '/'
61 fixincludes [] = []
62 fixincludes ("-I":d:tl)
63 | isabsinc d = "-I":d:fixincludes tl
64 | otherwise = "-I":inOutDir d:fixincludes tl
65 fixincludes (e:tl) = e:fixincludes tl
67 ocamlKey key | "lablGL/" `isPrefixOf` key = (ocamlc, "-I lablGL", [])
68 | otherwise = case lookup key ocamlflagstbl of
69 Nothing -> (ocamlc, ocamlflags, [])
70 Just (f, []) -> (ocamlc, ocamlflags ++ " " ++ f, [])
71 Just (f, pp) -> (ocamlc, ocamlflags ++ " " ++ f, ["-pp", pp])
73 ocamlKeyN key | "lablGL/" `isPrefixOf` key = (ocamlopt, "-I lablGL", [])
74 | otherwise = case lookup key ocamlflagstbln of
75 Nothing -> (ocamlopt, ocamlflags, [])
76 Just (f, []) -> (ocamlopt, ocamlflags ++ " " ++ f, [])
77 Just (f, pp) -> (ocamlopt, ocamlflags ++ " " ++ f, ["-pp", pp])
79 cKey key | "lablGL/" `isPrefixOf` key = "-Wno-pointer-sign -O2"
80 | otherwise = case lookup key cflagstbl of
81 Nothing -> cflags
82 Just f -> f ++ " " ++ cflags
84 fixppfile s ("File":_:tl) = ("File \"" ++ s ++ "\","):tl
85 fixppfile _ l = l
87 fixpp :: String -> String -> String
88 fixpp r s = unlines [unwords $ fixppfile r $ words x | x <- lines s]
90 ppppe ExitSuccess _ _ = return ()
91 ppppe _ src emsg = error $ fixpp src emsg
93 needsrc key suff = do
94 let src' = key -<.> suff
95 let src = if src' == "help.ml" then inOutDir src' else src'
96 need [src]
97 return src
99 cmio target suffix oracle ordoracle = do
100 target %> \out -> do
101 let key = dropDirectory1 out
102 src <- needsrc key suffix
103 (comp, flags, ppflags) <- oracle $ OcamlCmdLineOracle key
104 let flagl = words flags
105 let dep = out ++ "_dep"
106 need [dep]
107 ddep <- liftIO $ readFile dep
108 let deps = deplist $ parseMakefile ddep
109 need deps
110 let fixedflags = fixincludes flagl
111 (Stderr emsg2, Exit ex2) <-
112 cmd comp "-c -I" outdir fixedflags "-o" out ppflags src
113 ppppe ex2 src emsg2
114 return ()
115 target ++ "_dep" %> \out -> do
116 let key' = dropDirectory1 out
117 let key = reverse (drop 4 $ reverse key')
118 src <- needsrc key suffix
119 (_, flags, ppflags) <- oracle $ OcamlCmdLineOracle key
120 let flagl = words flags
121 let incs = unwords ["-I " ++ d | d <- getincludes flagl
122 , not $ isabsinc d]
123 (Stdout stdout, Stderr emsg, Exit ex) <-
124 cmd ocamldep "-one-line" incs ppflags src
125 ppppe ex src emsg
126 writeFileChanged out stdout
127 let depo = deps ++ [dep -<.> ".cmo" | dep <- deps, fit dep]
128 where
129 deps = deplist $ parseMakefile stdout
130 fit dep = ext == ".cmi" && base /= baseout
131 where (base, ext) = splitExtension dep
132 baseout = dropExtension out
133 need $ map (++ "_dep") depo
134 let ord = reverse (drop 4 $ reverse out)
135 unit $ ordoracle $ OcamlOrdOracle ord
136 return ()
137 where
138 deplist [] = []
139 deplist ((_, reqs) : _) =
140 [if takeDirectory1 n == outdir then n else inOutDir n | n <- reqs]
142 cmx oracle ordoracle = do
143 "//*.cmx" %> \out -> do
144 let key = dropDirectory1 out
145 src <- needsrc key ".ml"
146 (comp, flags, ppflags) <- oracle $ OcamlCmdLineOracleN key
147 let flagl = words flags
148 let incs = unwords ["-I " ++ d | d <- getincludes flagl
149 , not $ isabsinc d]
150 (Stdout stdout, Stderr emsg, Exit ex) <-
151 cmd ocamldep "-one-line" incs ppflags src
152 ppppe ex src emsg
153 need $ deplist $ parseMakefile stdout
154 unit $ ordoracle $ OcamlOrdOracleN out
155 let fixedflags = fixincludes flagl
156 (Stderr emsg2, Exit ex2) <-
157 cmd comp "-c -I" outdir fixedflags "-o" out ppflags src
158 ppppe ex2 src emsg2
159 return ()
160 where
161 deplist (_ : (_, reqs) : _) =
162 [if takeDirectory1 n == outdir then n else inOutDir n | n <- reqs]
163 deplist _ = []
165 main = do
166 depl <- newMVar ([] :: [String])
167 depln <- newMVar ([] :: [String])
168 shakeArgs shakeOptions { shakeFiles = outdir
169 , shakeVerbosity = Normal
170 , shakeChange = ChangeModtimeAndDigest } $ do
171 want ["build/llpp"]
173 gitDescribeOracle <- addOracle $ \(GitDescribeOracle ()) -> do
174 Stdout out <- cmd "git describe --tags --dirty"
175 return (out :: String)
177 ocamlOracle <- addOracle $ \(OcamlCmdLineOracle s) ->
178 return $ ocamlKey s
180 ocamlOracleN <- addOracle $ \(OcamlCmdLineOracleN s) ->
181 return $ ocamlKeyN s
183 ocamlOrdOracle <- addOracle $ \(OcamlOrdOracle s) ->
184 unless (takeExtension s == ".cmi") $
185 liftIO $ modifyMVar_ depl $ \l -> return $ s:l
187 ocamlOrdOracleN <- addOracle $ \(OcamlOrdOracleN s) ->
188 unless (takeExtension s == ".cmi") $
189 liftIO $ modifyMVar_ depln $ \l -> return $ s:l
191 cOracle <- addOracle $ \(CCmdLineOracle s) -> return $ cKey s
193 inOutDir "help.ml" %> \out -> do
194 version <- gitDescribeOracle $ GitDescribeOracle ()
195 need ["mkhelp.sh", "KEYS"]
196 Stdout f <- cmd "/bin/sh mkhelp.sh KEYS" version
197 writeFileChanged out f
199 "//*.o" %> \out -> do
200 let key = dropDirectory1 out
201 flags <- cOracle $ CCmdLineOracle key
202 let src = key -<.> ".c"
203 let dep = out -<.> ".d"
204 unit $ cmd ocamlc "-ccopt"
205 [flags ++ " -MMD -MF " ++ dep ++ " -o " ++ out] "-c" src
206 needMakefileDependencies dep
208 inOutDir "llpp" %> \out -> do
209 let objs = map (inOutDir . (++) "lablGL/ml_") ["gl.o", "glarray.o", "raw.o"]
210 need (objs ++ map inOutDir ["link.o", "main.cmo", "help.cmo"])
211 cmos <- liftIO $ readMVar depl
212 need cmos
213 unit $ cmd ocamlc "-g -custom -I lablGL -o" out
214 "unix.cma str.cma" (reverse cmos)
215 (inOutDir "link.o") "-cclib" (cclib : objs)
217 inOutDir "llpp.native" %> \out -> do
218 let objs = map (inOutDir . (++) "lablGL/ml_") ["gl.o", "glarray.o", "raw.o"]
219 need (objs ++ map inOutDir ["link.o", "main.cmx", "help.cmx"])
220 cmxs <- liftIO $ readMVar depln
221 need cmxs
222 unit $ cmd ocamlopt "-g -I lablGL -o" out
223 "unix.cmxa str.cmxa" (reverse cmxs)
224 (inOutDir "link.o") "-cclib" (cclib : objs)
226 cmio "//*.cmi" ".mli" ocamlOracle ocamlOrdOracle
227 cmio "//*.cmo" ".ml" ocamlOracle ocamlOrdOracle
228 cmx ocamlOracleN ocamlOrdOracleN