1 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
2 {-# OPTIONS_GHC -fno-warn-missing-signatures #-}
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 data Bt
= Native | Bytecode
30 inOutDir s
= outdir
</> s
34 ocamlopt
= "ocamlopt.opt"
35 ocamldep
= "ocamldep.opt"
36 ocamlflags
= "-warn-error +a -w +a -g -safe-string -strict-sequence"
37 ocamlflagstbl
= [("main", ("-I lablGL", "sed -f pp.sed", ["pp.sed"]))
38 ,("config", ("-I lablGL", "", []))
40 cflags
= "-Wall -Werror -D_GNU_SOURCE -O\
41 \ -g -std=c99 -pedantic-errors\
42 \ -Wunused-parameter -Wsign-compare -Wshadow"
43 ++ (if egl
then " -DUSE_EGL" else "")
46 ,"-I " ++ mudir
++ "/include -I "
47 ++ mudir
++ "/thirdparty/freetype/include -Wextra")
50 "-lGL -lX11 -lmupdf -lmupdfthird -lpthread -L" ++ mudir
</> "build" </> ty
51 ++ " -lcrypto" ++ (if egl
then " -lEGL" else "")
52 cclibNative
= cclib
"native"
53 cclibRelease
= cclib
"release"
55 getincludes
:: [String] -> [String]
57 getincludes
("-I":arg
:tl
) = arg
: getincludes tl
58 getincludes
(_
:tl
) = getincludes tl
60 isabsinc
:: String -> Bool
62 isabsinc
(hd
:_
) = hd
== '+' || hd
== '/'
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
71 |
"lablGL/" `
isPrefixOf` key
=
72 (comp
, ocamlflags
++ " -w -44 -I lablGL", [], [])
73 |
otherwise = case lookup (dropExtension key
) tbl
of
74 Nothing
-> (comp
, ocamlflags
, [], [])
75 Just
(f
, [], deps
) -> (comp
, ocamlflags
++ " " ++ f
, [], deps
)
76 Just
(f
, pp
, deps
) -> (comp
, ocamlflags
++ " " ++ f
, ["-pp", pp
], deps
)
78 cKey1 key |
"lablGL/" `
isPrefixOf` key
= "-Wno-pointer-sign -O2"
79 |
otherwise = case lookup key cflagstbl
of
81 Just f
-> f
++ " " ++ cflags
83 cKey Nothing key
= cKey1 key
84 cKey
(Just flags
) key
= flags
++ " " ++ cKey1 key
86 fixppfile s
("File":_
:tl
) = ("File \"" ++ s
++ "\","):tl
89 fixpp
:: String -> String -> String
90 fixpp r s
= unlines [unwords $ fixppfile r
$ words x | x
<- lines s
]
92 ppppe ExitSuccess _ _
= return ()
93 ppppe _ src emsg
= error $ fixpp src emsg
96 let src
' = key
-<.> suff
97 let src
= if src
' == "help.ml" then inOutDir src
' else src
'
101 depscaml flags ppflags src
= do
102 (Stdout
stdout, Stderr emsg
, Exit ex
) <-
103 cmd ocamldep
"-one-line" incs
"-I" outdir ppflags src
106 where flagl
= words flags
107 incs
= unwords ["-I " ++ d | d
<- getincludes flagl
, not $ isabsinc d
]
109 compilecaml comp flagl ppflags out src
= do
110 let fixedflags
= fixincludes flagl
111 (Stderr emsg
, Exit ex
) <-
112 cmd comp
"-c -I" outdir fixedflags
"-o" out ppflags src
117 [if takeDirectory1 n
== outdir
then n
else inOutDir n | n
<- reqs
]
118 deplist Native
(_
: (_
, reqs
) : _
) = deplistE reqs
119 deplist Bytecode
((_
, reqs
) : _
) = deplistE reqs
122 cmio target suffix oracle ordoracle
= do
124 let key
= dropDirectory1 out
125 src
<- needsrc key suffix
126 (comp
, flags
, ppflags
, deps
') <- oracle
$ OcamlCmdLineOracle key
127 let flagl
= words flags
128 let dep
= out
++ "_dep"
130 ddep
<- liftIO
$ readFile dep
131 let deps
= deplist Bytecode
$ parseMakefile ddep
133 compilecaml comp flagl ppflags out src
134 target
++ "_dep" %> \out
-> do
135 let ord = dropEnd
4 out
136 let key
= dropDirectory1
ord
137 src
<- needsrc key suffix
138 (_
, flags
, ppflags
, deps
') <- oracle
$ OcamlCmdLineOracle key
139 mkfiledeps
<- depscaml flags ppflags src
140 writeFileChanged out mkfiledeps
141 let depo
= deps
++ [dep
-<.> ".cmo" | dep
<- deps
, fit dep
]
143 deps
= deplist Bytecode
$ parseMakefile mkfiledeps
144 fit dep
= ext
== ".cmi" && base
/= baseout
145 where (base
, ext
) = splitExtension dep
146 baseout
= dropExtension out
147 need
(map (++ "_dep") depo
++ deps
')
148 unit
$ ordoracle
$ OcamlOrdOracle
ord
150 cmx oracle ordoracle
=
151 "//*.cmx" %> \out
-> do
152 let key
= dropDirectory1 out
153 src
<- needsrc key
".ml"
154 (comp
, flags
, ppflags
, deps
') <- oracle
$ OcamlCmdLineOracleN key
155 let flagl
= words flags
156 mkfiledeps
<- depscaml flags ppflags src
157 need
(deplist Native
(parseMakefile mkfiledeps
) ++ deps
')
158 unit
$ ordoracle
$ OcamlOrdOracleN out
159 compilecaml comp flagl ppflags out src
161 binInOutDir globjs depln target
=
162 inOutDir target
%> \out
->
164 let mulibs
= [mudir
</> "build" </> "native" </> "libmupdf.a"
165 ,mudir
</> "build" </> "native" </> "libmupdfthird.a"]
166 need
(mulibs
++ globjs
++ map inOutDir
["link.o", "main.cmx", "help.cmx"])
167 cmxs
<- liftIO
$ readMVar depln
169 unit
$ cmd ocamlopt
"-g -I lablGL -o" out
170 "unix.cmxa str.cmxa" (reverse cmxs
)
171 (inOutDir
"link.o") "-cclib" (cclibRelease
: globjs
)
174 depl
<- newMVar
([] :: [String])
175 depln
<- newMVar
([] :: [String])
176 envcflags
<- lookupEnv
"CFLAGS"
177 shakeArgs shakeOptions
{ shakeFiles
= outdir
178 , shakeVerbosity
= Normal
179 , shakeChange
= ChangeModtimeAndDigest
} $ do
180 want
[inOutDir
"llpp"]
182 gitDescribeOracle
<- addOracle
$ \(GitDescribeOracle
()) -> do
183 Stdout out
<- cmd
"git describe --tags --dirty"
184 return (out
:: String)
186 ocamlOracle
<- addOracle
$ \(OcamlCmdLineOracle s
) ->
187 return $ ocamlKey ocamlc ocamlflagstbl s
189 ocamlOracleN
<- addOracle
$ \(OcamlCmdLineOracleN s
) ->
190 return $ ocamlKey ocamlopt ocamlflagstbl s
192 ocamlOrdOracle
<- addOracle
$ \(OcamlOrdOracle s
) ->
193 unless (takeExtension s
== ".cmi") $
194 liftIO
$ modifyMVar_ depl
$ \l
-> return $ s
:l
196 ocamlOrdOracleN
<- addOracle
$ \(OcamlOrdOracleN s
) ->
197 unless (takeExtension s
== ".cmi") $
198 liftIO
$ modifyMVar_ depln
$ \l
-> return $ s
:l
200 cOracle
<- addOracle
$ \(CCmdLineOracle s
) -> return $ cKey envcflags s
202 inOutDir
"help.ml" %> \out
-> do
203 version
<- gitDescribeOracle
$ GitDescribeOracle
()
204 need
["mkhelp.sh", "KEYS"]
205 Stdout f
<- cmd
"/bin/sh mkhelp.sh KEYS" version
206 writeFileChanged out f
208 "//*.o" %> \out
-> do
209 let key
= dropDirectory1 out
210 flags
<- cOracle
$ CCmdLineOracle key
211 let src
= key
-<.> ".c"
212 let dep
= out
-<.> ".d"
213 unit
$ cmd ocamlc
"-ccopt"
214 [flags
++ " -MMD -MF " ++ dep
++ " -o " ++ out
] "-c" src
215 needMakefileDependencies dep
217 let globjs
= map (inOutDir
. (++) "lablGL/ml_") ["gl.o", "glarray.o", "raw.o"]
219 let mulib ty name
= do
220 -- perhaps alwaysrerun is in order here?
221 mudir
</> "build" </> ty
</> name
%> \_
-> do
222 unit
$ cmd
(Cwd
"mupdf") ("make build=" ++ ty
) "libs"
224 mulib
"release" "libmupdf.a"
225 mulib
"release" "libmupdfthird.a"
226 mulib
"native" "libmupdf.a"
227 mulib
"native" "libmupdfthird.a"
229 inOutDir
"llpp" %> \out
-> do
230 let mulibs
= [mudir
</> "build" </> "native" </> "libmupdf.a"
231 ,mudir
</> "build" </> "native" </> "libmupdfthird.a"]
232 need
(mulibs
++ globjs
++ map inOutDir
["link.o", "main.cmo", "help.cmo"])
233 cmos
<- liftIO
$ readMVar depl
235 unit
$ cmd ocamlc
"-g -custom -I lablGL -o" out
236 "unix.cma str.cma" (reverse cmos
)
237 (inOutDir
"link.o") "-cclib" (cclibNative
: globjs
)
239 binInOutDir globjs depln
"llpp.native"
240 binInOutDir globjs depln
"llpp.murel.native"
242 cmio
"//*.cmi" ".mli" ocamlOracle ocamlOrdOracle
243 cmio
"//*.cmo" ".ml" ocamlOracle ocamlOrdOracle
244 cmx ocamlOracleN ocamlOrdOracleN