Simplify
[llpp.git] / Shakefile.hs
blob794f1f4957064c1ee6a6b941a1a9ae976ec2da89
1 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
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 data Bt = Native | Bytecode
27 outdir = "build"
28 mudir = "mupdf"
29 mulibs ty = [mudir </> "build" </> ty </> "libmupdf.a"
30 ,mudir </> "build" </> ty </> "libmupdfthird.a"]
31 inOutDir s = outdir </> s
32 egl = False
34 ocamlc = "ocamlc.opt"
35 ocamlopt = "ocamlopt.opt"
36 ocamldep = "ocamldep.opt"
37 ocamlflags = "-warn-error +a -w +a -g -safe-string -strict-sequence"
38 ocamlflagstbl = [("main", "-I lablGL -I wsi/x11")
39 ,("wsi/x11/wsi", "-I wsi/x11")
40 ,("config", "-I lablGL -I wsi/x11")]
41 cflags = "-Wall -Werror -D_GNU_SOURCE -O\
42 \ -g -std=c99 -pedantic-errors\
43 \ -Wunused-parameter -Wsign-compare -Wshadow"
44 ++ (if egl then " -DUSE_EGL" else "")
45 cflagstbl =
46 [("link.o"
47 ,"-I " ++ mudir ++ "/include -I "
48 ++ mudir ++ "/thirdparty/freetype/include -Wextra")
50 cclib ty =
51 "-lGL -lX11 -lmupdf -lmupdfthird -lpthread -L" ++ mudir </> "build" </> ty
52 ++ " -lcrypto" ++ (if egl then " -lEGL" else "")
53 cclibNative = cclib "native"
54 cclibRelease = cclib "release"
56 getincludes :: [String] -> [String]
57 getincludes [] = []
58 getincludes ("-I":arg:tl) = arg : getincludes tl
59 getincludes (_:tl) = getincludes tl
61 isabsinc :: String -> Bool
62 isabsinc [] = False
63 isabsinc (hd:_) = hd == '+' || hd == '/'
65 fixincludes [] = []
66 fixincludes ("-I":d:tl)
67 | isabsinc d = "-I":d:fixincludes tl
68 | otherwise = "-I":inOutDir d:fixincludes tl
69 fixincludes (e:tl) = e:fixincludes tl
71 ocamlKey comp tbl key
72 | "lablGL/" `isPrefixOf` key = (comp, ocamlflags ++ " -w -44 -I lablGL")
73 | otherwise = case lookup (dropExtension key) tbl of
74 Nothing -> (comp, ocamlflags)
75 Just f -> (comp, ocamlflags ++ " " ++ f)
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 needsrc key suff = do
86 let src' = key -<.> suff
87 let src = if src' == "help.ml" then inOutDir src' else src'
88 need [src]
89 return src
91 depscaml flags src = do
92 (Stdout stdout) <- cmd ocamldep "-one-line" incs "-I" outdir src
93 return stdout
94 where flagl = words flags
95 incs = unwords ["-I " ++ d | d <- getincludes flagl, not $ isabsinc d]
97 compilecaml comp flagl out src = do
98 let fixedflags = fixincludes flagl
99 () <- cmd comp "-c -I" outdir fixedflags "-o" out src
100 return ()
102 deplistE reqs =
103 [if takeDirectory1 n == outdir then n else inOutDir n | n <- reqs]
104 deplist Native (_ : (_, reqs) : _) = deplistE reqs
105 deplist Bytecode ((_, reqs) : _) = deplistE reqs
106 deplist _ _ = []
108 cmio target suffix oracle ordoracle = do
109 target %> \out -> do
110 let key = dropDirectory1 out
111 src <- needsrc key suffix
112 (comp, flags) <- oracle $ OcamlCmdLineOracle key
113 let flagl = words flags
114 let dep = out ++ "_dep"
115 need $ [dep]
116 ddep <- liftIO $ readFile dep
117 let deps = deplist Bytecode $ parseMakefile ddep
118 need deps
119 compilecaml comp flagl out src
120 target ++ "_dep" %> \out -> do
121 let ord = dropEnd 4 out
122 let key = dropDirectory1 ord
123 src <- needsrc key suffix
124 (_, flags) <- oracle $ OcamlCmdLineOracle key
125 mkfiledeps <- depscaml flags src
126 writeFileChanged out mkfiledeps
127 let depo = deps ++ [dep -<.> ".cmo" | dep <- deps, fit dep]
128 where
129 deps = deplist Bytecode $ parseMakefile mkfiledeps
130 fit dep = ext == ".cmi" && base /= baseout
131 where (base, ext) = splitExtension dep
132 baseout = dropExtension out
133 need (map (++ "_dep") depo)
134 unit $ ordoracle $ OcamlOrdOracle ord
136 cmx oracle ordoracle =
137 "//*.cmx" %> \out -> do
138 let key = dropDirectory1 out
139 src <- needsrc key ".ml"
140 (comp, flags) <- oracle $ OcamlCmdLineOracleN key
141 let flagl = words flags
142 mkfiledeps <- depscaml flags src
143 need (deplist Native (parseMakefile mkfiledeps))
144 unit $ ordoracle $ OcamlOrdOracleN out
145 compilecaml comp flagl out src
147 binInOutDir ty globjs depln target =
148 inOutDir target %> \out ->
150 need [inOutDir "help.cmx"]
151 need $ mulibs ty ++ globjs ++ map inOutDir ["link.o", "main.cmx"]
152 cmxs <- liftIO $ readMVar depln
153 need cmxs
154 unit $ cmd ocamlopt "-g -I lablGL -o" out
155 "unix.cmxa str.cmxa" (reverse cmxs)
156 (inOutDir "link.o") "-cclib"
157 ((if ty == "native" then cclibNative else cclibRelease) : globjs)
159 main = do
160 depl <- newMVar ([] :: [String])
161 depln <- newMVar ([] :: [String])
162 envcflags <- lookupEnv "CFLAGS"
163 shakeArgs shakeOptions { shakeFiles = outdir
164 , shakeVerbosity = Normal
165 , shakeChange = ChangeModtimeAndDigest } $ do
166 want [inOutDir "llpp"]
168 gitDescribeOracle <- addOracle $ \(GitDescribeOracle ()) -> do
169 Stdout out <- cmd "git describe --tags --dirty"
170 return (out :: String)
172 ocamlOracle <- addOracle $ \(OcamlCmdLineOracle s) ->
173 return $ ocamlKey ocamlc ocamlflagstbl s
175 ocamlOracleN <- addOracle $ \(OcamlCmdLineOracleN s) ->
176 return $ ocamlKey ocamlopt ocamlflagstbl s
178 ocamlOrdOracle <- addOracle $ \(OcamlOrdOracle s) ->
179 unless (takeExtension s == ".cmi") $
180 liftIO $ modifyMVar_ depl $ \l -> return $ s:l
182 ocamlOrdOracleN <- addOracle $ \(OcamlOrdOracleN s) ->
183 unless (takeExtension s == ".cmi") $
184 liftIO $ modifyMVar_ depln $ \l -> return $ s:l
186 cOracle <- addOracle $ \(CCmdLineOracle s) -> return $ cKey envcflags s
188 inOutDir "help.ml" %> \out -> do
189 version <- gitDescribeOracle $ GitDescribeOracle ()
190 need ["mkhelp.sh", "KEYS"]
191 Stdout f <- cmd "/bin/sh mkhelp.sh KEYS" version
192 writeFileChanged out f
194 "//*.o" %> \out -> do
195 let key = dropDirectory1 out
196 flags <- cOracle $ CCmdLineOracle key
197 let src = key -<.> ".c"
198 let dep = out -<.> ".d"
199 unit $ cmd ocamlc "-ccopt"
200 [flags ++ " -MMD -MF " ++ dep ++ " -o " ++ out] "-c" src
201 needMakefileDependencies dep
203 let globjs = map (inOutDir . (++) "lablGL/ml_") ["gl.o", "glarray.o", "raw.o"]
205 let mulib ty name = do
206 -- perhaps alwaysrerun is in order here?
207 mudir </> "build" </> ty </> name %> \_ -> do
208 unit $ cmd (Cwd "mupdf") ("make build=" ++ ty) "libs"
210 mulib "release" "libmupdf.a"
211 mulib "release" "libmupdfthird.a"
212 mulib "native" "libmupdf.a"
213 mulib "native" "libmupdfthird.a"
215 inOutDir "llpp" %> \out -> do
216 need [inOutDir "help.cmo"]
217 need $ mulibs "native" ++ globjs ++ map inOutDir ["link.o", "main.cmo"]
218 cmos <- liftIO $ readMVar depl
219 need cmos
220 unit $ cmd ocamlc "-g -custom -I lablGL -o" out
221 "unix.cma str.cma" (reverse cmos)
222 (inOutDir "link.o") "-cclib" (cclibNative : globjs)
224 binInOutDir "native" globjs depln "llpp.native"
225 binInOutDir "release" globjs depln "llpp.murel.native"
227 cmio "//*.cmi" ".mli" ocamlOracle ocamlOrdOracle
228 cmio "//*.cmo" ".ml" ocamlOracle ocamlOrdOracle
229 cmx ocamlOracleN ocamlOrdOracleN