Cosmetics
[llpp.git] / Shakefile.hs
blobd2275dc94369c96220b10f491b8fe7191b43daa4
1 {-# LANGUAGE GeneralizedNewtypeDeriving, TypeFamilies #-}
2 {-# OPTIONS_GHC -fno-warn-missing-signatures #-}
3 import Data.List.Extra
4 import Control.Monad
5 import Control.Concurrent.MVar
6 import Development.Shake
7 import Development.Shake.Util
8 import Development.Shake.Classes
9 import Development.Shake.FilePath
10 import System.Environment (lookupEnv)
12 newtype OcamlOrdOracle = OcamlOrdOracle String
13 deriving (Show,Typeable,Eq,Hashable,Binary,NFData)
14 newtype OcamlOrdOracleN = OcamlOrdOracleN String
15 deriving (Show,Typeable,Eq,Hashable,Binary,NFData)
16 newtype OcamlCmdLineOracle = OcamlCmdLineOracle String
17 deriving (Show,Typeable,Eq,Hashable,Binary,NFData)
18 newtype OcamlCmdLineOracleN = OcamlCmdLineOracleN String
19 deriving (Show,Typeable,Eq,Hashable,Binary,NFData)
20 newtype CCmdLineOracle = CCmdLineOracle String
21 deriving (Show,Typeable,Eq,Hashable,Binary,NFData)
22 newtype GitDescribeOracle = GitDescribeOracle ()
23 deriving (Show,Typeable,Eq,Hashable,Binary,NFData)
25 type instance RuleResult GitDescribeOracle = String
26 type instance RuleResult OcamlCmdLineOracle = (String, String)
27 type instance RuleResult OcamlCmdLineOracleN = (String, String)
28 type instance RuleResult OcamlOrdOracle = ()
29 type instance RuleResult OcamlOrdOracleN = ()
30 type instance RuleResult CCmdLineOracle = String
32 data Bt = Native | Bytecode
34 outdir = "build"
35 mudir = "mupdf"
36 mulibs ty = [mudir </> "build" </> ty </> "libmupdf.a"
37 ,mudir </> "build" </> ty </> "libmupdfthird.a"]
38 inOutDir s = outdir </> s
39 egl = False
41 ocamlc = "ocamlc.opt"
42 ocamlopt = "ocamlopt.opt"
43 ocamlflags = "-warn-error +a -w +a -g -safe-string -strict-sequence"
44 ocamlflagstbl = [("main", "-I lablGL -I wsi/x11")
45 ,("wsi/x11/wsi", "-I wsi/x11")
46 ,("config", "-I lablGL -I wsi/x11")]
47 cflags = "-Wall -Werror -D_GNU_SOURCE -O\
48 \ -g -std=c99 -pedantic-errors\
49 \ -Wunused-parameter -Wsign-compare -Wshadow"
50 ++ (if egl then " -DUSE_EGL" else "")
51 cflagstbl =
52 [("link.o"
53 ,"-I " ++ mudir ++ "/include -I "
54 ++ mudir ++ "/thirdparty/freetype/include -Wextra")
56 cclib ty =
57 "-lGL -lX11 -lmupdf -lmupdfthird -lpthread -L" ++ mudir </> "build" </> ty
58 ++ " -lcrypto" ++ (if egl then " -lEGL" else "")
59 cclibNative = cclib "native"
60 cclibRelease = cclib "release"
62 getincludes :: [String] -> [String]
63 getincludes [] = []
64 getincludes ("-I":arg:tl) = arg : getincludes tl
65 getincludes (_:tl) = getincludes tl
67 isabsinc :: String -> Bool
68 isabsinc [] = False
69 isabsinc (hd:_) = hd == '+' || hd == '/'
71 fixincludes [] = []
72 fixincludes ("-I":d:tl)
73 | isabsinc d = "-I":d:fixincludes tl
74 | otherwise = "-I":inOutDir d:fixincludes tl
75 fixincludes (e:tl) = e:fixincludes tl
77 ocamlKey comp tbl key
78 | "lablGL/" `isPrefixOf` key = (comp, ocamlflags ++ " -w -44 -I lablGL")
79 | otherwise = case lookup (dropExtension key) tbl of
80 Nothing -> (comp, ocamlflags)
81 Just f -> (comp, ocamlflags ++ " " ++ f)
83 cKey1 key | "lablGL/" `isPrefixOf` key = "-Wno-pointer-sign -O2"
84 | otherwise = case lookup key cflagstbl of
85 Nothing -> cflags
86 Just f -> f ++ " " ++ cflags
88 cKey Nothing key = cKey1 key
89 cKey (Just flags) key = flags ++ " " ++ cKey1 key
91 needsrc key suff = do
92 let src' = key -<.> suff
93 let src = if src' == "help.ml" then inOutDir src' else src'
94 need [src]
95 return src
97 depscaml flags src = do
98 (Stdout stdout) <- cmd ocamlc "-depend -one-line" incs "-I" outdir src
99 return stdout
100 where flagl = words flags
101 incs = unwords ["-I " ++ d | d <- getincludes flagl, not $ isabsinc d]
103 compilecaml comp flagl out src = do
104 let fixedflags = fixincludes flagl
105 cmd_ comp "-c -I" outdir fixedflags "-o" out src
107 deplistE reqs =
108 [if takeDirectory1 n == outdir then n else inOutDir n | n <- reqs]
109 deplist Native (_ : (_, reqs) : _) = deplistE reqs
110 deplist Bytecode ((_, reqs) : _) = deplistE reqs
111 deplist _ _ = []
113 cmio target suffix oracle ordoracle = do
114 target %> \out -> do
115 let key = dropDirectory1 out
116 src <- needsrc key suffix
117 (comp, flags) <- oracle $ OcamlCmdLineOracle key
118 let flagl = words flags
119 let dep = out ++ "_dep"
120 need $ [dep]
121 ddep <- liftIO $ readFile dep
122 let deps = deplist Bytecode $ parseMakefile ddep
123 need deps
124 compilecaml comp flagl out src
125 target ++ "_dep" %> \out -> do
126 let ord = dropEnd 4 out
127 let key = dropDirectory1 ord
128 src <- needsrc key suffix
129 (_, flags) <- oracle $ OcamlCmdLineOracle key
130 mkfiledeps <- depscaml flags src
131 writeFileChanged out mkfiledeps
132 let depo = deps ++ [dep -<.> ".cmo" | dep <- deps, fit dep]
133 where
134 deps = deplist Bytecode $ parseMakefile mkfiledeps
135 fit dep = ext == ".cmi" && base /= baseout
136 where (base, ext) = splitExtension dep
137 baseout = dropExtension out
138 need (map (++ "_dep") depo)
139 unit $ ordoracle $ OcamlOrdOracle ord
141 cmx oracle ordoracle =
142 "//*.cmx" %> \out -> do
143 let key = dropDirectory1 out
144 src <- needsrc key ".ml"
145 (comp, flags) <- oracle $ OcamlCmdLineOracleN key
146 let flagl = words flags
147 mkfiledeps <- depscaml flags src
148 need (deplist Native (parseMakefile mkfiledeps))
149 unit $ ordoracle $ OcamlOrdOracleN out
150 compilecaml comp flagl out src
152 binInOutDir ty globjs depln target =
153 inOutDir target %> \out ->
155 need [inOutDir "help.cmx"]
156 need $ mulibs ty ++ globjs ++ map inOutDir ["link.o", "main.cmx"]
157 cmxs <- liftIO $ readMVar depln
158 need cmxs
159 unit $ cmd ocamlopt "-g -I lablGL -o" out
160 "unix.cmxa str.cmxa" (reverse cmxs)
161 (inOutDir "link.o") "-cclib"
162 ((if ty == "native" then cclibNative else cclibRelease) : globjs)
164 main = do
165 depl <- newMVar ([] :: [String])
166 depln <- newMVar ([] :: [String])
167 envcflags <- lookupEnv "CFLAGS"
168 shakeArgs shakeOptions { shakeFiles = outdir
169 , shakeVerbosity = Normal
170 , shakeChange = ChangeModtimeAndDigest } $ do
171 want [inOutDir "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 ocamlc ocamlflagstbl s
180 ocamlOracleN <- addOracle $ \(OcamlCmdLineOracleN s) ->
181 return $ ocamlKey ocamlopt ocamlflagstbl s
183 let ordoracle d s =
184 unless (takeExtension s == ".cmi") $
185 liftIO $ modifyMVar_ d $ \l -> return $ s:l
187 ocamlOrdOracle <- addOracle $ \(OcamlOrdOracle s) -> ordoracle depl s
188 ocamlOrdOracleN <- addOracle $ \(OcamlOrdOracleN s) -> ordoracle depln s
190 cOracle <- addOracle $ \(CCmdLineOracle s) -> return $ cKey envcflags s
192 inOutDir "help.ml" %> \out -> do
193 version <- gitDescribeOracle $ GitDescribeOracle ()
194 need ["mkhelp.sh", "KEYS"]
195 Stdout f <- cmd "/bin/sh mkhelp.sh KEYS" version
196 writeFileChanged out f
198 "//*.o" %> \out -> do
199 let key = dropDirectory1 out
200 flags <- cOracle $ CCmdLineOracle key
201 let src = key -<.> ".c"
202 let dep = out -<.> ".d"
203 unit $ cmd ocamlc "-ccopt"
204 [flags ++ " -MMD -MF " ++ dep ++ " -o " ++ out] "-c" src
205 needMakefileDependencies dep
207 let globjs = map (inOutDir . (++) "lablGL/ml_") ["gl.o", "glarray.o", "raw.o"]
209 let mulib ty name = do
210 -- perhaps alwaysrerun is in order here?
211 mudir </> "build" </> ty </> name %> \_ -> do
212 unit $ cmd (Cwd "mupdf") ("make build=" ++ ty) "libs"
214 mulib "release" "libmupdf.a"
215 mulib "release" "libmupdfthird.a"
216 mulib "native" "libmupdf.a"
217 mulib "native" "libmupdfthird.a"
219 inOutDir "llpp" %> \out -> do
220 need [inOutDir "help.cmo"]
221 need $ mulibs "native" ++ globjs ++ map inOutDir ["link.o", "main.cmo"]
222 cmos <- liftIO $ readMVar depl
223 need cmos
224 unit $ cmd ocamlc "-g -custom -I lablGL -o" out
225 "unix.cma str.cma" (reverse cmos)
226 (inOutDir "link.o") "-cclib" (cclibNative : globjs)
228 binInOutDir "native" globjs depln "llpp.native"
229 binInOutDir "release" globjs depln "llpp.murel.native"
231 cmio "//*.cmi" ".mli" ocamlOracle ocamlOrdOracle
232 cmio "//*.cmo" ".ml" ocamlOracle ocamlOrdOracle
233 cmx ocamlOracleN ocamlOrdOracleN