summaryrefslogtreecommitdiff
path: root/ghc/compiler/main/Main.lhs
blob: 1712dca92039ef458fa78e2baa5a8ae1cbed22f7 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
%
% (c) The GRASP/AQUA Project, Glasgow University, 1993-1998
%
\section[GHC_Main]{Main driver for Glasgow Haskell compiler}

\begin{code}
module Main ( main ) where

#include "HsVersions.h"

import IO		( hPutStr, stderr )
import HsSyn
import BasicTypes	( NewOrData(..) )

import RdrHsSyn		( RdrNameHsModule )
import FastString	( mkFastCharString, unpackFS )
import StringBuffer	( hGetStringBuffer )
import Parser		( parse )
import Lex		( PState(..), P, ParseResult(..) )
import SrcLoc		( mkSrcLoc )

import Rename		( renameModule )

import MkIface		( startIface, ifaceDecls, endIface )
import TcModule		( TcResults(..), typecheckModule )
import Desugar		( deSugar )
import SimplCore	( core2core )
import CoreLint		( endPass )
import CoreSyn		( coreBindsSize )
import CoreTidy		( tidyCorePgm )
import CoreToStg	( topCoreBindsToStg )
import StgSyn		( collectFinalStgBinders, pprStgBindings )
import SimplStg		( stg2stg )
import CodeGen		( codeGen )
import CodeOutput	( codeOutput )

import Module		( ModuleName, moduleNameUserString )
import AbsCSyn		( absCNop )
import CmdLineOpts
import ErrUtils		( ghcExit, doIfSet, dumpIfSet )
import Maybes		( maybeToBool, MaybeErr(..) )
import TyCon		( isDataTyCon )
import Class		( classTyCon )
import UniqSupply	( mkSplitUniqSupply )

import FiniteMap	( emptyFM )
import Outputable
import Char		( isSpace )
#if REPORT_TO_MOTHERLODE && __GLASGOW_HASKELL__ >= 303
import SocketPrim
import BSD
import IOExts		( unsafePerformIO )
import NativeInfo       ( os, arch )
#endif

\end{code}

\begin{code}
main =
 --  _scc_ "main" 
 doIt classifyOpts
\end{code}

\begin{code}
parseModule :: IO (ModuleName, RdrNameHsModule)
parseModule = do
    buf <- hGetStringBuffer True{-expand tabs-} (unpackFS src_filename)
    case parse buf PState{ bol = 0#, atbol = 1#,
		           context = [], glasgow_exts = glaexts,
		           loc = mkSrcLoc src_filename 1 } of

	PFailed err -> do
		printErrs err
		ghcExit 1
		return (error "parseModule") -- just to get the types right

	POk _ m@(HsModule mod _ _ _ _ _) -> 
		return (mod, m)
  where
	glaexts | opt_GlasgowExts = 1#
		| otherwise       = 0#
\end{code}

\begin{code}
doIt :: ([CoreToDo], [StgToDo]) -> IO ()

doIt (core_cmds, stg_cmds)
  = doIfSet opt_Verbose 
	(hPutStr stderr "Glasgow Haskell Compiler, version " 	>>
 	 hPutStr stderr compiler_version                    	>>
	 hPutStr stderr ", for Haskell 98, compiled by GHC version " >>
	 hPutStr stderr booter_version				>>
	 hPutStr stderr "\n")					>>

	--------------------------  Reader  ----------------
    show_pass "Parser"	>>
    _scc_     "Parser"
    parseModule		>>= \ (mod_name, rdr_module) ->

    dumpIfSet opt_D_dump_parsed "Parser" (ppr rdr_module) >>

    dumpIfSet opt_D_source_stats "Source Statistics"
	(ppSourceStats False rdr_module)	 	>>

    -- UniqueSupplies for later use (these are the only lower case uniques)
    mkSplitUniqSupply 'r'	>>= \ rn_uniqs 	-> -- renamer
    mkSplitUniqSupply 'a'	>>= \ tc_uniqs 	-> -- typechecker
    mkSplitUniqSupply 'd'	>>= \ ds_uniqs 	-> -- desugarer
    mkSplitUniqSupply 'r'	>>= \ ru_uniqs 	-> -- rules
    mkSplitUniqSupply 'c'	>>= \ c2s_uniqs -> -- core-to-stg
    mkSplitUniqSupply 'u'	>>= \ tidy_uniqs -> -- tidy up
    mkSplitUniqSupply 'g'	>>= \ st_uniqs  -> -- stg-to-stg passes
    mkSplitUniqSupply 'n'	>>= \ ncg_uniqs -> -- native-code generator

	--------------------------  Rename  ----------------
    show_pass "Renamer" 			>>
    _scc_     "Renamer"

    renameModule rn_uniqs rdr_module		>>= \ maybe_rn_stuff ->
    case maybe_rn_stuff of {
	Nothing -> 	-- Hurrah!  Renamer reckons that there's no need to
			-- go any further
			reportCompile mod_name "Compilation NOT required!" >>
			return ();
	
	Just (this_mod, rn_mod, iface_file_stuff, rn_name_supply, imported_modules) ->
			-- Oh well, we've got to recompile for real


	--------------------------  Start interface file  ----------------
    -- Safely past renaming: we can start the interface file:
    -- (the iface file is produced incrementally, as we have
    -- the information that we need...; we use "iface<blah>")
    -- "endIface" finishes the job.
    startIface this_mod iface_file_stuff	>>= \ if_handle ->


	--------------------------  Typechecking ----------------
    show_pass "TypeCheck" 				>>
    _scc_     "TypeCheck"
    typecheckModule tc_uniqs rn_name_supply
		    iface_file_stuff rn_mod	        >>= \ maybe_tc_stuff ->
    case maybe_tc_stuff of {
	Nothing -> ghcExit 1;	-- Type checker failed

	Just (tc_results@(TcResults {tc_tycons  = local_tycons, 
		   	 	     tc_classes = local_classes, 
		   	 	     tc_insts   = inst_info })) ->


	--------------------------  Desugaring ----------------
    _scc_     "DeSugar"
    deSugar this_mod ds_uniqs tc_results	>>= \ (desugared, rules, h_code, c_code) ->


	--------------------------  Main Core-language transformations ----------------
    _scc_     "Core2Core"
    core2core core_cmds desugared rules			>>= \ (simplified, imp_rule_ids) ->

	-- Do the final tidy-up
    tidyCorePgm tidy_uniqs this_mod
		simplified imp_rule_ids			>>= \ (tidy_binds, tidy_imp_rule_ids) -> 


	--------------------------  Convert to STG code -------------------------------
    show_pass "Core2Stg" 			>>
    _scc_     "Core2Stg"
    let
	stg_binds   = topCoreBindsToStg c2s_uniqs tidy_binds
    in

	--------------------------  Simplify STG code -------------------------------
    show_pass "Stg2Stg" 			>>
    _scc_     "Stg2Stg"
    stg2stg stg_cmds this_mod st_uniqs stg_binds >>= \ (stg_binds2, cost_centre_info) ->


	--------------------------  Interface file -------------------------------
	-- Dump instance decls and type signatures into the interface file
    _scc_     "Interface"
    let
	final_ids = collectFinalStgBinders (map fst stg_binds2)
    in
    coreBindsSize tidy_binds `seq`
--	TEMP: the above call zaps some space usage allocated by the
--	simplifier, which for reasons I don't understand, persists
--	thoroughout code generation

    ifaceDecls if_handle local_tycons local_classes 
	       inst_info final_ids tidy_binds imp_rule_ids	>>
    endIface if_handle						>>
	    -- We are definitely done w/ interface-file stuff at this point:
	    -- (See comments near call to "startIface".)


	--------------------------  Code generation -------------------------------
    show_pass "CodeGen" 			>>
    _scc_     "CodeGen"
    codeGen this_mod imported_modules
	    cost_centre_info
	    local_tycons local_classes 
	    stg_binds2				>>= \ abstractC ->


	--------------------------  Code output -------------------------------
    show_pass "CodeOutput" 				>>
    _scc_     "CodeOutput"
    codeOutput this_mod c_code h_code abstractC ncg_uniqs	>>


	--------------------------  Final report -------------------------------
    reportCompile mod_name (showSDoc (ppSourceStats True rdr_module)) >>

    ghcExit 0
    } }
  where
    -------------------------------------------------------------
    -- ****** help functions:

    show_pass
      = if opt_D_show_passes
	then \ what -> hPutStr stderr ("*** "++what++":\n")
	else \ what -> return ()

ppSourceStats short (HsModule name version exports imports decls src_loc)
 = (if short then hcat else vcat)
        (map pp_val
	       [("ExportAll        ", export_all), -- 1 if no export list
		("ExportDecls      ", export_ds),
		("ExportModules    ", export_ms),
		("Imports          ", import_no),
		("  ImpQual        ", import_qual),
		("  ImpAs          ", import_as),
		("  ImpAll         ", import_all),
		("  ImpPartial     ", import_partial),
		("  ImpHiding      ", import_hiding),
		("FixityDecls      ", fixity_ds),
		("DefaultDecls     ", default_ds),
	      	("TypeDecls        ", type_ds),
	      	("DataDecls        ", data_ds),
	      	("NewTypeDecls     ", newt_ds),
	      	("DataConstrs      ", data_constrs),
		("DataDerivings    ", data_derivs),
	      	("ClassDecls       ", class_ds),
	      	("ClassMethods     ", class_method_ds),
	      	("DefaultMethods   ", default_method_ds),
	      	("InstDecls        ", inst_ds),
	      	("InstMethods      ", inst_method_ds),
	      	("TypeSigs         ", bind_tys),
	      	("ValBinds         ", val_bind_ds),
	      	("FunBinds         ", fn_bind_ds),
	      	("InlineMeths      ", method_inlines),
		("InlineBinds      ", bind_inlines),
--	      	("SpecialisedData  ", data_specs),
--	      	("SpecialisedInsts ", inst_specs),
	      	("SpecialisedMeths ", method_specs),
	      	("SpecialisedBinds ", bind_specs)
	       ])
  where
    pp_val (str, 0) = empty
    pp_val (str, n) 
      | not short   = hcat [text str, int n]
      | otherwise   = hcat [text (trim str), equals, int n, semi]
    
    trim ls     = takeWhile (not.isSpace) (dropWhile isSpace ls)

    fixity_ds   = length [() | FixD d <- decls]
		-- NB: this omits fixity decls on local bindings and
		-- in class decls.  ToDo

    tycl_decls  = [d | TyClD d <- decls]
    (class_ds, data_ds, newt_ds, type_ds) = countTyClDecls tycl_decls

    inst_decls  = [d | InstD d <- decls]
    inst_ds     = length inst_decls
    default_ds  = length [() | DefD _ <- decls]
    val_decls   = [d | ValD d <- decls]

    real_exports = case exports of { Nothing -> []; Just es -> es }
    n_exports  	 = length real_exports
    export_ms  	 = length [() | IEModuleContents _ <- real_exports]
    export_ds  	 = n_exports - export_ms
    export_all 	 = case exports of { Nothing -> 1; other -> 0 }

    (val_bind_ds, fn_bind_ds, bind_tys, bind_specs, bind_inlines)
	= count_binds (foldr ThenBinds EmptyBinds val_decls)

    (import_no, import_qual, import_as, import_all, import_partial, import_hiding)
	= foldr add6 (0,0,0,0,0,0) (map import_info imports)
    (data_constrs, data_derivs)
	= foldr add2 (0,0) (map data_info tycl_decls)
    (class_method_ds, default_method_ds)
	= foldr add2 (0,0) (map class_info tycl_decls)
    (inst_method_ds, method_specs, method_inlines)
	= foldr add3 (0,0,0) (map inst_info inst_decls)


    count_binds EmptyBinds        = (0,0,0,0,0)
    count_binds (ThenBinds b1 b2) = count_binds b1 `add5` count_binds b2
    count_binds (MonoBind b sigs _) = case (count_monobinds b, count_sigs sigs) of
				        ((vs,fs),(ts,_,ss,is)) -> (vs,fs,ts,ss,is)

    count_monobinds EmptyMonoBinds	  	   = (0,0)
    count_monobinds (AndMonoBinds b1 b2)  	   = count_monobinds b1 `add2` count_monobinds b2
    count_monobinds (PatMonoBind (VarPatIn n) r _) = (1,0)
    count_monobinds (PatMonoBind p r _)            = (0,1)
    count_monobinds (FunMonoBind f _ m _)          = (0,1)

    count_sigs sigs = foldr add4 (0,0,0,0) (map sig_info sigs)

    sig_info (Sig _ _ _)          = (1,0,0,0)
    sig_info (ClassOpSig _ _ _ _) = (0,1,0,0)
    sig_info (SpecSig _ _ _)      = (0,0,1,0)
    sig_info (InlineSig _ _)      = (0,0,0,1)
    sig_info _                    = (0,0,0,0)

    import_info (ImportDecl _ _ qual as spec _)
	= add6 (1, qual_info qual, as_info as, 0,0,0) (spec_info spec)
    qual_info False  = 0
    qual_info True   = 1
    as_info Nothing  = 0
    as_info (Just _) = 1
    spec_info Nothing 	        = (0,0,0,1,0,0)
    spec_info (Just (False, _)) = (0,0,0,0,1,0)
    spec_info (Just (True, _))  = (0,0,0,0,0,1)

    data_info (TyData _ _ _ _ constrs derivs _ _)
	= (length constrs, case derivs of {Nothing -> 0; Just ds -> length ds})
    data_info other = (0,0)

    class_info (ClassDecl _ _ _ meth_sigs def_meths _ _ _ _ _)
	= case count_sigs meth_sigs of
	    (_,classops,_,_) ->
	       (classops, addpr (count_monobinds def_meths))
    class_info other = (0,0)

    inst_info (InstDecl _ inst_meths inst_sigs _ _)
	= case count_sigs inst_sigs of
	    (_,_,ss,is) ->
	       (addpr (count_monobinds inst_meths), ss, is)

    addpr :: (Int,Int) -> Int
    add1  :: Int -> Int -> Int
    add2  :: (Int,Int) -> (Int,Int) -> (Int, Int)
    add3  :: (Int,Int,Int) -> (Int,Int,Int) -> (Int, Int, Int)
    add4  :: (Int,Int,Int,Int) -> (Int,Int,Int,Int) -> (Int, Int, Int, Int)
    add5  :: (Int,Int,Int,Int,Int) -> (Int,Int,Int,Int,Int) -> (Int, Int, Int, Int, Int)
    add6  :: (Int,Int,Int,Int,Int,Int) -> (Int,Int,Int,Int,Int,Int) -> (Int, Int, Int, Int, Int, Int)

    addpr (x,y) = x+y
    add1 x1 y1  = x1+y1
    add2 (x1,x2) (y1,y2) = (x1+y1,x2+y2)
    add3 (x1,x2,x3) (y1,y2,y3) = (x1+y1,x2+y2,x3+y3)
    add4 (x1,x2,x3,x4) (y1,y2,y3,y4) = (x1+y1,x2+y2,x3+y3,x4+y4)
    add5 (x1,x2,x3,x4,x5) (y1,y2,y3,y4,y5) = (x1+y1,x2+y2,x3+y3,x4+y4,x5+y5)
    add6 (x1,x2,x3,x4,x5,x6) (y1,y2,y3,y4,y5,y6) = (x1+y1,x2+y2,x3+y3,x4+y4,x5+y5,x6+y6)
\end{code}

\begin{code}
compiler_version :: String
compiler_version =
     case (show opt_HiVersion) of
	[x]	 -> ['0','.',x]
	ls@[x,y] -> "0." ++ ls
	ls       -> go ls
 where
  -- 10232353 => 10232.53
  go ls@[x,y] = '.':ls
  go (x:xs)   = x:go xs

booter_version
 = case "\ 
	\ __GLASGOW_HASKELL__" of
    ' ':n:ns -> n:'.':ns
    ' ':m    -> m
\end{code}

\begin{code}
reportCompile :: ModuleName -> String -> IO ()
#if REPORT_TO_MOTHERLODE && __GLASGOW_HASKELL__ >= 303
reportCompile mod_name info
  | not opt_ReportCompile = return ()
  | otherwise = (do 
      sock <- udpSocket 0
      addr <- motherShip
      sendTo sock (moduleNameUserString mod_name ++ ';': compiler_version ++ 
		   ';': os ++ ';':arch ++ '\n':' ':info ++ "\n") addr
      return ()) `catch` (\ _ -> return ())

motherShip :: IO SockAddr
motherShip = do
  he <- getHostByName "laysan.dcs.gla.ac.uk"
  case (hostAddresses he) of
    []    -> IOERROR (userError "No address!")
    (x:_) -> return (SockAddrInet motherShipPort x)

--magick
motherShipPort :: PortNumber
motherShipPort = mkPortNumber 12345

-- creates a socket capable of sending datagrams,
-- binding it to a port
--  ( 0 => have the system pick next available port no.)
udpSocket :: Int -> IO Socket
udpSocket p = do
  pr <- getProtocolNumber "udp"
  s  <- socket AF_INET Datagram pr
  bindSocket s (SockAddrInet (mkPortNumber p) iNADDR_ANY)
  return s
#else
reportCompile _ _ = return ()
#endif

\end{code}