1 {-# LANGUAGE GeneralizedNewtypeDeriving, TypeFamilies #-}
2 {-# OPTIONS_GHC -fno-warn-missing-signatures #-}
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
36 mulibs ty
= [mudir
</> "build" </> ty
</> "libmupdf.a"
37 ,mudir
</> "build" </> ty
</> "libmupdfthird.a"]
38 inOutDir s
= outdir
</> s
43 ocamlopt
= "ocamlopt.opt"
44 ocamlflags
= "-warn-error +a -w +a -g -safe-string -strict-sequence"
45 ocamlflagstbl
= [("main", "-I lablGL -I wsi/x11")
46 ,("wsi/x11/wsi", "-I wsi/x11")
47 ,("config", "-I lablGL -I wsi/x11")]
48 cflags
= "-D_GNU_SOURCE -O2\
49 \ -g -std=c99 -Wall -Werror -pedantic-errors\
50 \ -Wunused-parameter -Wsign-compare -Wshadow"
51 ++ (if egl
then " -DUSE_EGL" else "")
54 ,"-I " ++ mudir
++ "/include -I "
55 ++ mudir
++ "/thirdparty/freetype/include -Wextra")
58 "-lGL -lX11 -lmupdf -lmupdfthird -lpthread -L" ++ mudir
</> "build" </> ty
59 ++ " -lcrypto" ++ (if egl
then " -lEGL" else "")
60 cclibNative
= cclib
"native"
61 cclibRelease
= cclib
"release"
63 getincludes
:: [String] -> [String]
65 getincludes
("-I":arg
:tl
) = arg
: getincludes tl
66 getincludes
(_
:tl
) = getincludes tl
68 isabsinc
:: String -> Bool
70 isabsinc
(hd
:_
) = hd
== '+' || hd
== '/'
73 fixincludes
("-I":d
:tl
)
74 | isabsinc d
= "-I":d
:fixincludes tl
75 |
otherwise = "-I":inOutDir d
:fixincludes tl
76 fixincludes
(e
:tl
) = e
:fixincludes tl
79 |
"lablGL/" `
isPrefixOf` key
= (comp
, ocamlflags
++ " -w -44 -I lablGL")
80 |
otherwise = case lookup (dropExtension key
) tbl
of
81 Nothing
-> (comp
, ocamlflags
)
82 Just f
-> (comp
, ocamlflags
++ " " ++ f
)
84 cKey1 key |
"lablGL/" `
isPrefixOf` key
= "-Wno-pointer-sign -O2"
85 |
otherwise = case lookup key cflagstbl
of
87 Just f
-> f
++ " " ++ cflags
89 cKey Nothing key
= cKey1 key
90 cKey
(Just flags
) key
= flags
++ " " ++ cKey1 key
93 let src
' = key
-<.> suff
94 let src
= if src
' == "help.ml" then inOutDir src
' else src
'
98 depscaml flags src
= do
99 (Stdout
stdout) <- cmd ocamlc
"-depend -one-line" incs
"-I" outdir src
101 where flagl
= words flags
102 incs
= unwords ["-I " ++ d | d
<- getincludes flagl
, not $ isabsinc d
]
104 compilecaml comp flagl out src
= do
105 let fixedflags
= fixincludes flagl
106 cmd_ comp
"-c -I" outdir fixedflags
"-o" out src
109 [if takeDirectory1 n
== outdir
then n
else inOutDir n | n
<- reqs
]
110 deplist Native
(_
: (_
, reqs
) : _
) = deplistE reqs
111 deplist Bytecode
((_
, reqs
) : _
) = deplistE reqs
114 cmio target suffix oracle ordoracle
= do
116 let key
= dropDirectory1 out
117 src
<- needsrc key suffix
118 (comp
, flags
) <- oracle
$ OcamlCmdLineOracle key
119 let flagl
= words flags
120 let dep
= out
++ "_dep"
122 ddep
<- liftIO
$ readFile dep
123 let deps
= deplist Bytecode
$ parseMakefile ddep
125 compilecaml comp flagl out src
126 target
++ "_dep" %> \out
-> do
127 let ord = dropEnd
4 out
128 let key
= dropDirectory1
ord
129 src
<- needsrc key suffix
130 (_
, flags
) <- oracle
$ OcamlCmdLineOracle key
131 mkfiledeps
<- depscaml flags src
132 writeFileChanged out mkfiledeps
133 let depo
= deps
++ [dep
-<.> ".cmo" | dep
<- deps
, fit dep
]
135 deps
= deplist Bytecode
$ parseMakefile mkfiledeps
136 fit dep
= ext
== ".cmi" && base
/= baseout
137 where (base
, ext
) = splitExtension dep
138 baseout
= dropExtension out
139 need
(map (++ "_dep") depo
)
140 unit
$ ordoracle
$ OcamlOrdOracle
ord
142 cmx oracle ordoracle
=
143 "//*.cmx" %> \out
-> do
144 let key
= dropDirectory1 out
145 src
<- needsrc key
".ml"
146 (comp
, flags
) <- oracle
$ OcamlCmdLineOracleN key
147 let flagl
= words flags
148 mkfiledeps
<- depscaml flags src
149 need
(deplist Native
(parseMakefile mkfiledeps
))
150 unit
$ ordoracle
$ OcamlOrdOracleN out
151 compilecaml comp flagl out src
153 binInOutDir ty globjs depln target
=
154 inOutDir target
%> \out
->
156 need
[inOutDir
"help.cmx"]
157 need
$ mulibs ty
++ globjs
++ map inOutDir
["link.o", "main.cmx"]
158 cmxs
<- liftIO
$ readMVar depln
160 unit
$ cmd ocamlopt
"-g -I lablGL -o" out
161 "unix.cmxa str.cmxa" (reverse cmxs
)
162 (inOutDir
"link.o") "-cclib"
163 ((if ty
== "native" then cclibNative
else cclibRelease
) : globjs
)
166 depl
<- newMVar
([] :: [String])
167 depln
<- newMVar
([] :: [String])
168 envcflags
<- lookupEnv
"CFLAGS"
169 shakeArgs shakeOptions
{ shakeFiles
= outdir
170 , shakeVerbosity
= Normal
171 , shakeChange
= ChangeModtimeAndDigest
} $ do
172 want
[inOutDir
"llpp"]
174 gitDescribeOracle
<- addOracle
$ \(GitDescribeOracle
()) -> do
175 Stdout out
<- cmd
"git describe --tags --dirty"
176 return (out
:: String)
178 ocamlOracle
<- addOracle
$ \(OcamlCmdLineOracle s
) ->
179 return $ ocamlKey ocamlc ocamlflagstbl s
181 ocamlOracleN
<- addOracle
$ \(OcamlCmdLineOracleN s
) ->
182 return $ ocamlKey ocamlopt ocamlflagstbl s
185 unless (takeExtension s
== ".cmi") $
186 liftIO
$ modifyMVar_ d
$ \l
-> return $ s
:l
188 ocamlOrdOracle
<- addOracle
$ \(OcamlOrdOracle s
) -> ordoracle depl s
189 ocamlOrdOracleN
<- addOracle
$ \(OcamlOrdOracleN s
) -> ordoracle depln s
191 cOracle
<- addOracle
$ \(CCmdLineOracle s
) -> return $ cKey envcflags s
193 inOutDir
"help.ml" %> \out
-> do
194 version
<- gitDescribeOracle
$ GitDescribeOracle
()
195 need
["mkhelp.sh", "KEYS"]
196 Stdout f
<- cmd
"/bin/sh mkhelp.sh KEYS" version
197 writeFileChanged out f
199 "//*.o" %> \out
-> do
200 let key
= dropDirectory1 out
201 flags
<- cOracle
$ CCmdLineOracle key
202 let src
= key
-<.> ".c"
203 let dep
= out
-<.> ".d"
205 then cmd ocamlc
"-cc clang" "-ccopt"
206 ["-include diag.h " ++ flags
++ " -MMD -MF "
207 ++ dep
++ " -o " ++ out
] "-c" src
208 else cmd ocamlc
"-ccopt "
209 [flags
++ " -MMD -MF " ++ dep
++ " -o " ++ out
] "-c" src
210 needMakefileDependencies dep
212 let globjs
= map (inOutDir
. (++) "lablGL/ml_") ["gl.o", "glarray.o", "raw.o"]
214 let mulib ty name
= do
215 -- perhaps alwaysrerun is in order here?
216 mudir
</> "build" </> ty
</> name
%> \_
-> do
217 unit
$ cmd
(Cwd
"mupdf") ("make build=" ++ ty
) "libs"
219 mulib
"release" "libmupdf.a"
220 mulib
"release" "libmupdfthird.a"
221 mulib
"native" "libmupdf.a"
222 mulib
"native" "libmupdfthird.a"
224 inOutDir
"llpp" %> \out
-> do
225 need
[inOutDir
"help.cmo"]
226 need
$ mulibs
"native" ++ globjs
++ map inOutDir
["link.o", "main.cmo"]
227 cmos
<- liftIO
$ readMVar depl
229 unit
$ cmd ocamlc
"-g -custom -I lablGL -o" out
230 "unix.cma str.cma" (reverse cmos
)
231 (inOutDir
"link.o") "-cclib" (cclibNative
: globjs
)
233 binInOutDir
"native" globjs depln
"llpp.native"
234 binInOutDir
"release" globjs depln
"llpp.murel.native"
236 cmio
"//*.cmi" ".mli" ocamlOracle ocamlOrdOracle
237 cmio
"//*.cmo" ".ml" ocamlOracle ocamlOrdOracle
238 cmx ocamlOracleN ocamlOrdOracleN