Unbreak unoconv
[llpp.git] / Shakefile.hs
blobf880af54f5a26e9e57a202097127a136c6dfb164
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.cmo", ("-I lablGL", "sed -f pp.sed", ["pp.sed"]))
36 ,("config.cmo", ("-I lablGL", "", []))
38 ocamlflagstbln = [("main.cmx", ("-I lablGL", "sed -f pp.sed", ["pp.sed"]))
39 ,("config.cmx", ("-I lablGL", "", []))
41 cflags = "-Wall -Werror -D_GNU_SOURCE -O\
42 \ -g -std=c99 -pedantic-errors\
43 \ -Wunused-parameter -Wsign-compare -Wshadow\
44 \ -DVISAVIS"
45 ++ (if egl then " -DUSE_EGL" else "")
46 cflagstbl =
47 [("link.o"
48 ,"-I " ++ mudir ++ "/include -I "
49 ++ mudir ++ "/thirdparty/freetype/include -Wextra")
51 cclib = "-lGL -lX11 -lmupdf -lmupdfthird\
52 \ -lpthread -L" ++ mudir ++ "/build/native -lcrypto"
53 ++ (if egl then " -lEGL" else "")
55 getincludes :: [String] -> [String]
56 getincludes [] = []
57 getincludes ("-I":arg:tl) = arg : getincludes tl
58 getincludes (_:tl) = getincludes tl
60 isabsinc :: String -> Bool
61 isabsinc [] = False
62 isabsinc (hd:_) = hd == '+' || hd == '/'
64 fixincludes [] = []
65 fixincludes ("-I":d:tl)
66 | isabsinc d = "-I":d:fixincludes tl
67 | otherwise = "-I":inOutDir d:fixincludes tl
68 fixincludes (e:tl) = e:fixincludes tl
70 ocamlKey comp tbl key
71 | "lablGL/" `isPrefixOf` key = (comp, "-I lablGL", [], [])
72 | otherwise = case lookup 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 cmio target suffix oracle ordoracle = do
116 target %> \out -> do
117 let key = dropDirectory1 out
118 src <- needsrc key suffix
119 (comp, flags, ppflags, deps') <- oracle $ OcamlCmdLineOracle key
120 let flagl = words flags
121 let dep = out ++ "_dep"
122 need $ dep : deps'
123 ddep <- liftIO $ readFile dep
124 let deps = deplist $ parseMakefile ddep
125 need deps
126 compilecaml comp flagl ppflags out src
127 target ++ "_dep" %> \out -> do
128 let ord = dropEnd 4 out
129 let key = dropDirectory1 ord
130 src <- needsrc key suffix
131 (_, flags, ppflags, deps') <- oracle $ OcamlCmdLineOracle key
132 mkfiledeps <- depscaml flags ppflags src
133 writeFileChanged out mkfiledeps
134 let depo = deps ++ [dep -<.> ".cmo" | dep <- deps, fit dep]
135 where
136 deps = deplist $ parseMakefile mkfiledeps
137 fit dep = ext == ".cmi" && base /= baseout
138 where (base, ext) = splitExtension dep
139 baseout = dropExtension out
140 need ((map (++ "_dep") depo) ++ deps')
141 unit $ ordoracle $ OcamlOrdOracle ord
142 where
143 deplist [] = []
144 deplist ((_, reqs) : _) =
145 [if takeDirectory1 n == outdir then n else inOutDir n | n <- reqs]
147 cmx oracle ordoracle =
148 "//*.cmx" %> \out -> do
149 let key = dropDirectory1 out
150 src <- needsrc key ".ml"
151 (comp, flags, ppflags, deps') <- oracle $ OcamlCmdLineOracleN key
152 let flagl = words flags
153 mkfiledeps <- depscaml flags ppflags src
154 need ((deplist $ parseMakefile mkfiledeps) ++ deps')
155 unit $ ordoracle $ OcamlOrdOracleN out
156 compilecaml comp flagl ppflags out src
157 where
158 deplist (_ : (_, reqs) : _) =
159 [if takeDirectory1 n == outdir then n else inOutDir n | n <- reqs]
160 deplist _ = []
162 main = do
163 depl <- newMVar ([] :: [String])
164 depln <- newMVar ([] :: [String])
165 envcflags <- lookupEnv "CFLAGS"
166 shakeArgs shakeOptions { shakeFiles = outdir
167 , shakeVerbosity = Normal
168 , shakeChange = ChangeModtimeAndDigest } $ do
169 want [inOutDir "llpp"]
171 gitDescribeOracle <- addOracle $ \(GitDescribeOracle ()) -> do
172 Stdout out <- cmd "git describe --tags --dirty"
173 return (out :: String)
175 ocamlOracle <- addOracle $ \(OcamlCmdLineOracle s) ->
176 return $ ocamlKey ocamlc ocamlflagstbl s
178 ocamlOracleN <- addOracle $ \(OcamlCmdLineOracleN s) ->
179 return $ ocamlKey ocamlopt ocamlflagstbln s
181 ocamlOrdOracle <- addOracle $ \(OcamlOrdOracle s) ->
182 unless (takeExtension s == ".cmi") $
183 liftIO $ modifyMVar_ depl $ \l -> return $ s:l
185 ocamlOrdOracleN <- addOracle $ \(OcamlOrdOracleN s) ->
186 unless (takeExtension s == ".cmi") $
187 liftIO $ modifyMVar_ depln $ \l -> return $ s:l
189 cOracle <- addOracle $ \(CCmdLineOracle s) -> return $ cKey envcflags s
191 inOutDir "help.ml" %> \out -> do
192 version <- gitDescribeOracle $ GitDescribeOracle ()
193 need ["mkhelp.sh", "KEYS"]
194 Stdout f <- cmd "/bin/sh mkhelp.sh KEYS" version
195 writeFileChanged out f
197 "//*.o" %> \out -> do
198 let key = dropDirectory1 out
199 flags <- cOracle $ CCmdLineOracle key
200 let src = key -<.> ".c"
201 let dep = out -<.> ".d"
202 unit $ cmd ocamlc "-ccopt"
203 [flags ++ " -MMD -MF " ++ dep ++ " -o " ++ out] "-c" src
204 needMakefileDependencies dep
206 let globjs = map (inOutDir . (++) "lablGL/ml_") ["gl.o", "glarray.o", "raw.o"]
207 inOutDir "llpp" %> \out -> do
208 need (globjs ++ map inOutDir ["link.o", "main.cmo", "help.cmo"])
209 cmos <- liftIO $ readMVar depl
210 need cmos
211 unit $ cmd ocamlc "-g -custom -I lablGL -o" out
212 "unix.cma str.cma" (reverse cmos)
213 (inOutDir "link.o") "-cclib" (cclib : globjs)
215 inOutDir "llpp.native" %> \out -> do
216 need (globjs ++ map inOutDir ["link.o", "main.cmx", "help.cmx"])
217 cmxs <- liftIO $ readMVar depln
218 need cmxs
219 unit $ cmd ocamlopt "-g -I lablGL -o" out
220 "unix.cmxa str.cmxa" (reverse cmxs)
221 (inOutDir "link.o") "-cclib" (cclib : globjs)
223 cmio "//*.cmi" ".mli" ocamlOracle ocamlOrdOracle
224 cmio "//*.cmo" ".ml" ocamlOracle ocamlOrdOracle
225 cmx ocamlOracleN ocamlOrdOracleN