Fix native builds
[llpp.git] / Shakefile.hs
blob4e91174714c9ffee89b07c59e898b183355c4d20
1 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
2 {-# OPTIONS_GHC -fno-warn-missing-signatures #-}
3 import Data.List.Extra
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.Classes
10 import Development.Shake.FilePath
11 import System.Environment (lookupEnv)
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 = "mupdf"
28 inOutDir s = outdir </> s
29 egl = False
31 ocamlc = "ocamlc.opt"
32 ocamlopt = "ocamlopt.opt"
33 ocamldep = "ocamldep.opt"
34 ocamlflags = "-warn-error +a -w +a -g -safe-string -strict-sequence"
35 ocamlflagstbl = [("main", ("-I lablGL", "sed -f pp.sed", ["pp.sed"]))
36 ,("config", ("-I lablGL", "", []))
38 cflags = "-Wall -Werror -D_GNU_SOURCE -O\
39 \ -g -std=c99 -pedantic-errors\
40 \ -Wunused-parameter -Wsign-compare -Wshadow\
41 \ -DVISAVIS -DCSS_HACK_TO_READ_EPUBS_COMFORTABLY"
42 ++ (if egl then " -DUSE_EGL" else "")
43 cflagstbl =
44 [("link.o"
45 ,"-I " ++ mudir ++ "/include -I "
46 ++ mudir ++ "/thirdparty/freetype/include -Wextra")
48 cclib ty =
49 "-lGL -lX11 -lmupdf -lmupdfthird -lpthread -L" ++ mudir </> "build" </> ty
50 ++ " -lcrypto" ++ (if egl then " -lEGL" else "")
51 cclibNative = cclib "native"
52 cclibRelease = cclib "release"
54 getincludes :: [String] -> [String]
55 getincludes [] = []
56 getincludes ("-I":arg:tl) = arg : getincludes tl
57 getincludes (_:tl) = getincludes tl
59 isabsinc :: String -> Bool
60 isabsinc [] = False
61 isabsinc (hd:_) = hd == '+' || hd == '/'
63 fixincludes [] = []
64 fixincludes ("-I":d:tl)
65 | isabsinc d = "-I":d:fixincludes tl
66 | otherwise = "-I":inOutDir d:fixincludes tl
67 fixincludes (e:tl) = e:fixincludes tl
69 ocamlKey comp tbl key
70 | "lablGL/" `isPrefixOf` key =
71 (comp, ocamlflags ++ " -w -44 -I lablGL", [], [])
72 | otherwise = case lookup (dropExtension key) tbl of
73 Nothing -> (comp, ocamlflags, [], [])
74 Just (f, [], deps) -> (comp, ocamlflags ++ " " ++ f, [], deps)
75 Just (f, pp, deps) -> (comp, ocamlflags ++ " " ++ f, ["-pp", pp], deps)
77 cKey1 key | "lablGL/" `isPrefixOf` key = "-Wno-pointer-sign -O2"
78 | otherwise = case lookup key cflagstbl of
79 Nothing -> cflags
80 Just f -> f ++ " " ++ cflags
82 cKey Nothing key = cKey1 key
83 cKey (Just flags) key = flags ++ " " ++ cKey1 key
85 fixppfile s ("File":_:tl) = ("File \"" ++ s ++ "\","):tl
86 fixppfile _ l = l
88 fixpp :: String -> String -> String
89 fixpp r s = unlines [unwords $ fixppfile r $ words x | x <- lines s]
91 ppppe ExitSuccess _ _ = return ()
92 ppppe _ src emsg = error $ fixpp src emsg
94 needsrc key suff = do
95 let src' = key -<.> suff
96 let src = if src' == "help.ml" then inOutDir src' else src'
97 need [src]
98 return src
100 depscaml flags ppflags src = do
101 (Stdout stdout, Stderr emsg, Exit ex) <-
102 cmd ocamldep "-one-line" incs "-I" outdir ppflags src
103 ppppe ex src emsg
104 return stdout
105 where flagl = words flags
106 incs = unwords ["-I " ++ d | d <- getincludes flagl, not $ isabsinc d]
108 compilecaml comp flagl ppflags out src = do
109 let fixedflags = fixincludes flagl
110 (Stderr emsg, Exit ex) <-
111 cmd comp "-c -I" outdir fixedflags "-o" out ppflags src
112 ppppe ex src emsg
113 return ()
115 deplist [] = []
116 deplist ((_, reqs) : _) =
117 [if takeDirectory1 n == outdir then n else inOutDir n | n <- reqs]
119 deplistx (_ : (_, reqs) : _) =
120 [if takeDirectory1 n == outdir then n else inOutDir n | n <- reqs]
121 deplistx [] = []
123 cmio target suffix oracle ordoracle = do
124 target %> \out -> do
125 let key = dropDirectory1 out
126 src <- needsrc key suffix
127 (comp, flags, ppflags, deps') <- oracle $ OcamlCmdLineOracle key
128 let flagl = words flags
129 let dep = out ++ "_dep"
130 need $ dep : deps'
131 ddep <- liftIO $ readFile dep
132 let deps = deplist $ parseMakefile ddep
133 need deps
134 compilecaml comp flagl ppflags out src
135 target ++ "_dep" %> \out -> do
136 let ord = dropEnd 4 out
137 let key = dropDirectory1 ord
138 src <- needsrc key suffix
139 (_, flags, ppflags, deps') <- oracle $ OcamlCmdLineOracle key
140 mkfiledeps <- depscaml flags ppflags src
141 writeFileChanged out mkfiledeps
142 let depo = deps ++ [dep -<.> ".cmo" | dep <- deps, fit dep]
143 where
144 deps = deplist $ parseMakefile mkfiledeps
145 fit dep = ext == ".cmi" && base /= baseout
146 where (base, ext) = splitExtension dep
147 baseout = dropExtension out
148 need (map (++ "_dep") depo ++ deps')
149 unit $ ordoracle $ OcamlOrdOracle ord
151 cmx oracle ordoracle =
152 "//*.cmx" %> \out -> do
153 let key = dropDirectory1 out
154 src <- needsrc key ".ml"
155 (comp, flags, ppflags, deps') <- oracle $ OcamlCmdLineOracleN key
156 let flagl = words flags
157 mkfiledeps <- depscaml flags ppflags src
158 need (deplistx (parseMakefile mkfiledeps) ++ deps')
159 unit $ ordoracle $ OcamlOrdOracleN out
160 compilecaml comp flagl ppflags out src
162 binInOutDir globjs depln target =
163 inOutDir target %> \out ->
165 need (globjs ++ map inOutDir ["link.o", "main.cmx", "help.cmx"])
166 cmxs <- liftIO $ readMVar depln
167 need cmxs
168 unit $ cmd ocamlopt "-g -I lablGL -o" out
169 "unix.cmxa str.cmxa" (reverse cmxs)
170 (inOutDir "link.o") "-cclib" (cclibRelease : globjs)
172 main = do
173 depl <- newMVar ([] :: [String])
174 depln <- newMVar ([] :: [String])
175 envcflags <- lookupEnv "CFLAGS"
176 shakeArgs shakeOptions { shakeFiles = outdir
177 , shakeVerbosity = Normal
178 , shakeChange = ChangeModtimeAndDigest } $ do
179 want [inOutDir "llpp"]
181 gitDescribeOracle <- addOracle $ \(GitDescribeOracle ()) -> do
182 Stdout out <- cmd "git describe --tags --dirty"
183 return (out :: String)
185 ocamlOracle <- addOracle $ \(OcamlCmdLineOracle s) ->
186 return $ ocamlKey ocamlc ocamlflagstbl s
188 ocamlOracleN <- addOracle $ \(OcamlCmdLineOracleN s) ->
189 return $ ocamlKey ocamlopt ocamlflagstbl s
191 ocamlOrdOracle <- addOracle $ \(OcamlOrdOracle s) ->
192 unless (takeExtension s == ".cmi") $
193 liftIO $ modifyMVar_ depl $ \l -> return $ s:l
195 ocamlOrdOracleN <- addOracle $ \(OcamlOrdOracleN s) ->
196 unless (takeExtension s == ".cmi") $
197 liftIO $ modifyMVar_ depln $ \l -> return $ s:l
199 cOracle <- addOracle $ \(CCmdLineOracle s) -> return $ cKey envcflags s
201 inOutDir "help.ml" %> \out -> do
202 version <- gitDescribeOracle $ GitDescribeOracle ()
203 need ["mkhelp.sh", "KEYS"]
204 Stdout f <- cmd "/bin/sh mkhelp.sh KEYS" version
205 writeFileChanged out f
207 "//*.o" %> \out -> do
208 let key = dropDirectory1 out
209 flags <- cOracle $ CCmdLineOracle key
210 let src = key -<.> ".c"
211 let dep = out -<.> ".d"
212 unit $ cmd ocamlc "-ccopt"
213 [flags ++ " -MMD -MF " ++ dep ++ " -o " ++ out] "-c" src
214 needMakefileDependencies dep
216 let globjs = map (inOutDir . (++) "lablGL/ml_") ["gl.o", "glarray.o", "raw.o"]
217 inOutDir "llpp" %> \out -> do
218 need (globjs ++ map inOutDir ["link.o", "main.cmo", "help.cmo"])
219 cmos <- liftIO $ readMVar depl
220 need cmos
221 unit $ cmd ocamlc "-g -custom -I lablGL -o" out
222 "unix.cma str.cma" (reverse cmos)
223 (inOutDir "link.o") "-cclib" (cclibNative : globjs)
225 binInOutDir globjs depln "llpp.native"
226 binInOutDir globjs depln "llpp.murel.native"
228 cmio "//*.cmi" ".mli" ocamlOracle ocamlOrdOracle
229 cmio "//*.cmo" ".ml" ocamlOracle ocamlOrdOracle
230 cmx ocamlOracleN ocamlOrdOracleN