Add PrimCall to the STG layer and update Core -> STG translation
[ghc-hetmet.git] / compiler / codeGen / CgClosure.lhs
1 %
2 % (c) The University of Glasgow 2006
3 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
4 %
5 \section[CgClosure]{Code generation for closures}
6
7 This module provides the support code for @StgToAbstractC@ to deal
8 with {\em closures} on the RHSs of let(rec)s.  See also
9 @CgCon@, which deals with constructors.
10
11 \begin{code}
12 module CgClosure ( cgTopRhsClosure, 
13                    cgStdRhsClosure, 
14                    cgRhsClosure,
15                    emitBlackHoleCode,
16                    ) where
17
18 #include "HsVersions.h"
19
20 import {-# SOURCE #-} CgExpr ( cgExpr )
21
22 import CgMonad
23 import CgBindery
24 import CgHeapery
25 import CgStackery
26 import CgProf
27 import CgTicky
28 import CgParallel
29 import CgInfoTbls
30 import CgCallConv
31 import CgUtils
32 import ClosureInfo
33 import SMRep
34 import Cmm
35 import CmmUtils
36 import CLabel
37 import StgSyn
38 import CostCentre       
39 import Id
40 import Name
41 import Module
42 import ListSetOps
43 import Util
44 import BasicTypes
45 import StaticFlags
46 import DynFlags
47 import Constants
48 import Outputable
49 import FastString
50
51 import Data.List
52 \end{code}
53
54 %********************************************************
55 %*                                                      *
56 \subsection[closures-no-free-vars]{Top-level closures}
57 %*                                                      *
58 %********************************************************
59
60 For closures bound at top level, allocate in static space.
61 They should have no free variables.
62
63 \begin{code}
64 cgTopRhsClosure :: Id
65                 -> CostCentreStack      -- Optional cost centre annotation
66                 -> StgBinderInfo
67                 -> UpdateFlag
68                 -> [Id]         -- Args
69                 -> StgExpr
70                 -> FCode (Id, CgIdInfo)
71
72 cgTopRhsClosure id ccs binder_info upd_flag args body = do
73   {     -- LAY OUT THE OBJECT
74     let name = idName id
75   ; lf_info  <- mkClosureLFInfo id TopLevel [] upd_flag args
76   ; srt_info <- getSRTInfo
77   ; mod_name <- getModuleName
78   ; let descr         = closureDescription mod_name name
79         closure_info  = mkClosureInfo True id lf_info 0 0 srt_info descr
80         closure_label = mkLocalClosureLabel name $ idCafInfo id
81         cg_id_info    = stableIdInfo id (mkLblExpr closure_label) lf_info
82         closure_rep   = mkStaticClosureFields closure_info ccs True []
83
84          -- BUILD THE OBJECT, AND GENERATE INFO TABLE (IF NECESSARY)
85   ; emitDataLits closure_label closure_rep
86   ; forkClosureBody (closureCodeBody binder_info closure_info
87                                      ccs args body)
88
89   ; returnFC (id, cg_id_info) }
90 \end{code}
91
92 %********************************************************
93 %*                                                      *
94 \subsection[non-top-level-closures]{Non top-level closures}
95 %*                                                      *
96 %********************************************************
97
98 For closures with free vars, allocate in heap.
99
100 \begin{code}
101 cgStdRhsClosure
102         :: Id
103         -> CostCentreStack      -- Optional cost centre annotation
104         -> StgBinderInfo
105         -> [Id]                 -- Free vars
106         -> [Id]                 -- Args
107         -> StgExpr
108         -> LambdaFormInfo
109         -> [StgArg]             -- payload
110         -> FCode (Id, CgIdInfo)
111
112 cgStdRhsClosure bndr cc _bndr_info _fvs args body lf_info payload 
113   = do  -- AHA!  A STANDARD-FORM THUNK
114   {     -- LAY OUT THE OBJECT
115     amodes <- getArgAmodes payload
116   ; mod_name <- getModuleName
117   ; let (tot_wds, ptr_wds, amodes_w_offsets) 
118             = mkVirtHeapOffsets (isLFThunk lf_info) amodes
119
120         descr        = closureDescription mod_name (idName bndr)
121         closure_info = mkClosureInfo False      -- Not static
122                                      bndr lf_info tot_wds ptr_wds 
123                                      NoC_SRT    -- No SRT for a std-form closure
124                                      descr
125                 
126   ; (use_cc, blame_cc) <- chooseDynCostCentres cc args body
127
128         -- BUILD THE OBJECT
129   ; heap_offset <- allocDynClosure closure_info use_cc blame_cc amodes_w_offsets
130
131         -- RETURN
132   ; returnFC (bndr, heapIdInfo bndr heap_offset lf_info) }
133 \end{code}
134
135 Here's the general case.
136
137 \begin{code}
138 cgRhsClosure    :: Id
139                 -> CostCentreStack      -- Optional cost centre annotation
140                 -> StgBinderInfo
141                 -> [Id]                 -- Free vars
142                 -> UpdateFlag
143                 -> [Id]                 -- Args
144                 -> StgExpr
145                 -> FCode (Id, CgIdInfo)
146
147 cgRhsClosure bndr cc bndr_info fvs upd_flag args body = do
148   {     -- LAY OUT THE OBJECT
149         -- If the binder is itself a free variable, then don't store
150         -- it in the closure.  Instead, just bind it to Node on entry.
151         -- NB we can be sure that Node will point to it, because we
152         -- havn't told mkClosureLFInfo about this; so if the binder
153         -- _was_ a free var of its RHS, mkClosureLFInfo thinks it *is*
154         -- stored in the closure itself, so it will make sure that
155         -- Node points to it...
156     let
157         name         = idName bndr
158         is_elem      = isIn "cgRhsClosure"
159         bndr_is_a_fv = bndr `is_elem` fvs
160         reduced_fvs | bndr_is_a_fv = fvs `minusList` [bndr]
161                     | otherwise    = fvs
162
163   ; lf_info <- mkClosureLFInfo bndr NotTopLevel fvs upd_flag args
164   ; fv_infos <- mapFCs getCgIdInfo reduced_fvs
165   ; srt_info <- getSRTInfo
166   ; mod_name <- getModuleName
167   ; let bind_details :: [(CgIdInfo, VirtualHpOffset)]
168         (tot_wds, ptr_wds, bind_details) 
169            = mkVirtHeapOffsets (isLFThunk lf_info) (map add_rep fv_infos)
170
171         add_rep info = (cgIdInfoArgRep info, info)
172
173         descr        = closureDescription mod_name name
174         closure_info = mkClosureInfo False      -- Not static
175                                      bndr lf_info tot_wds ptr_wds
176                                      srt_info descr
177
178         -- BUILD ITS INFO TABLE AND CODE
179   ; forkClosureBody (do
180         {       -- Bind the fvs
181           let 
182               -- A function closure pointer may be tagged, so we
183               -- must take it into account when accessing the free variables.
184               mbtag       = tagForArity (length args)
185               bind_fv (info, offset)
186                 | Just tag <- mbtag
187                 = bindNewToUntagNode (cgIdInfoId info) offset (cgIdInfoLF info) tag
188                 | otherwise
189                 = bindNewToNode (cgIdInfoId info) offset (cgIdInfoLF info)
190         ; mapCs bind_fv bind_details
191
192                 -- Bind the binder itself, if it is a free var
193         ; whenC bndr_is_a_fv (bindNewToReg bndr nodeReg lf_info)
194         
195                 -- Compile the body
196         ; closureCodeBody bndr_info closure_info cc args body })
197
198         -- BUILD THE OBJECT
199   ; let
200         to_amode (info, offset) = do { amode <- idInfoToAmode info
201                                      ; return (amode, offset) }
202   ; (use_cc, blame_cc) <- chooseDynCostCentres cc args body
203   ; amodes_w_offsets <- mapFCs to_amode bind_details
204   ; heap_offset <- allocDynClosure closure_info use_cc blame_cc amodes_w_offsets
205
206         -- RETURN
207   ; returnFC (bndr, heapIdInfo bndr heap_offset lf_info) }
208
209
210 mkClosureLFInfo :: Id           -- The binder
211                 -> TopLevelFlag -- True of top level
212                 -> [Id]         -- Free vars
213                 -> UpdateFlag   -- Update flag
214                 -> [Id]         -- Args
215                 -> FCode LambdaFormInfo
216 mkClosureLFInfo bndr top fvs upd_flag args
217   | null args = return (mkLFThunk (idType bndr) top fvs upd_flag)
218   | otherwise = do { arg_descr <- mkArgDescr (idName bndr) args
219                    ; return (mkLFReEntrant top fvs args arg_descr) }
220 \end{code}
221
222
223 %************************************************************************
224 %*                                                                      *
225 \subsection[code-for-closures]{The code for closures}
226 %*                                                                      *
227 %************************************************************************
228
229 \begin{code}
230 closureCodeBody :: StgBinderInfo
231                 -> ClosureInfo     -- Lots of information about this closure
232                 -> CostCentreStack -- Optional cost centre attached to closure
233                 -> [Id]
234                 -> StgExpr
235                 -> Code
236 \end{code}
237
238 There are two main cases for the code for closures.  If there are {\em
239 no arguments}, then the closure is a thunk, and not in normal form.
240 So it should set up an update frame (if it is shared).
241 NB: Thunks cannot have a primitive type!
242
243 \begin{code}
244 closureCodeBody _binder_info cl_info cc [{- No args i.e. thunk -}] body = do
245   { body_absC <- getCgStmts $ do
246         { tickyEnterThunk cl_info
247         ; ldvEnterClosure cl_info  -- NB: Node always points when profiling
248         ; thunkWrapper cl_info $ do
249                 -- We only enter cc after setting up update so
250                 -- that cc of enclosing scope will be recorded
251                 -- in update frame CAF/DICT functions will be
252                 -- subsumed by this enclosing cc
253             { enterCostCentre cl_info cc body
254             ; stmtsC [CmmComment $ mkFastString $ showSDoc $ ppr body]
255             ; cgExpr body }
256         }
257     
258   ; emitClosureCodeAndInfoTable cl_info [] body_absC }
259 \end{code}
260
261 If there is /at least one argument/, then this closure is in
262 normal form, so there is no need to set up an update frame.
263
264 The Macros for GrAnSim are produced at the beginning of the
265 argSatisfactionCheck (by calling fetchAndReschedule).  There info if
266 Node points to closure is available. -- HWL
267
268 \begin{code}
269 closureCodeBody _binder_info cl_info cc args body 
270   = ASSERT( length args > 0 )
271   do {  -- Get the current virtual Sp (it might not be zero, 
272         -- eg. if we're compiling a let-no-escape).
273     vSp <- getVirtSp
274   ; let (reg_args, other_args) = assignCallRegs (addIdReps args)
275         (sp_top, stk_args)     = mkVirtStkOffsets vSp other_args
276
277         -- Allocate the global ticky counter
278   ; let ticky_ctr_lbl = mkRednCountsLabel (closureName cl_info) (clHasCafRefs cl_info)
279   ; emitTickyCounter cl_info args sp_top
280
281         -- ...and establish the ticky-counter 
282         -- label for this block
283   ; setTickyCtrLabel ticky_ctr_lbl $ do
284
285         -- Emit the slow-entry code
286   { reg_save_code <- mkSlowEntryCode cl_info reg_args
287
288         -- Emit the main entry code
289   ; blks <- forkProc $
290             mkFunEntryCode cl_info cc reg_args stk_args
291                            sp_top reg_save_code body
292   ; emitClosureCodeAndInfoTable cl_info [] blks
293   }}
294
295
296
297 mkFunEntryCode :: ClosureInfo
298                -> CostCentreStack
299                -> [(Id,GlobalReg)]        -- Args in regs
300                -> [(Id,VirtualSpOffset)]  -- Args on stack
301                -> VirtualSpOffset         -- Last allocated word on stack
302                -> CmmStmts                -- Register-save code in case of GC
303                -> StgExpr
304                -> Code
305 -- The main entry code for the closure
306 mkFunEntryCode cl_info cc reg_args stk_args sp_top reg_save_code body = do
307   {     -- Bind args to regs/stack as appropriate,
308         -- and record expected position of sps
309   ; bindArgsToRegs  reg_args
310   ; bindArgsToStack stk_args
311   ; setRealAndVirtualSp sp_top
312
313         -- Enter the cost-centre, if required
314         -- ToDo: It's not clear why this is outside the funWrapper,
315         --       but the tickyEnterFun is inside. Perhaps we can put
316         --       them together?
317   ; enterCostCentre cl_info cc body
318
319         -- Do the business
320   ; funWrapper cl_info reg_args reg_save_code $ do
321         { tickyEnterFun cl_info
322         ; cgExpr body }
323   }
324 \end{code}
325
326 The "slow entry" code for a function.  This entry point takes its
327 arguments on the stack.  It loads the arguments into registers
328 according to the calling convention, and jumps to the function's
329 normal entry point.  The function's closure is assumed to be in
330 R1/node.
331
332 The slow entry point is used in two places:
333
334  (a) unknown calls: eg. stg_PAP_entry 
335  (b) returning from a heap-check failure
336
337 \begin{code}
338 mkSlowEntryCode :: ClosureInfo -> [(Id,GlobalReg)] -> FCode CmmStmts
339 -- If this function doesn't have a specialised ArgDescr, we need
340 -- to generate the function's arg bitmap, slow-entry code, and
341 -- register-save code for the heap-check failure
342 -- Here, we emit the slow-entry code, and 
343 -- return the register-save assignments
344 mkSlowEntryCode cl_info reg_args
345   | Just (_, ArgGen _) <- closureFunInfo cl_info
346   = do  { emitSimpleProc slow_lbl (emitStmts load_stmts)
347         ; return save_stmts }
348   | otherwise = return noStmts
349   where
350      name = closureName cl_info
351      has_caf_refs = clHasCafRefs cl_info
352      slow_lbl = mkSlowEntryLabel name has_caf_refs
353
354      load_stmts = mkStmts load_assts `plusStmts` mkStmts [stk_adj_pop, jump_to_entry]
355      save_stmts = oneStmt stk_adj_push `plusStmts`  mkStmts save_assts
356
357      reps_w_regs :: [(CgRep,GlobalReg)]
358      reps_w_regs = [(idCgRep id, reg) | (id,reg) <- reverse reg_args]
359      (final_stk_offset, stk_offsets)
360         = mapAccumL (\off (rep,_) -> (off + cgRepSizeW rep, off))
361                     0 reps_w_regs
362
363      load_assts = zipWithEqual "mk_load" mk_load reps_w_regs stk_offsets
364      mk_load (rep,reg) offset = CmmAssign (CmmGlobal reg) 
365                                           (CmmLoad (cmmRegOffW spReg offset)
366                                                    (argMachRep rep))
367
368      save_assts = zipWithEqual "mk_save" mk_save reps_w_regs stk_offsets
369      mk_save (rep,reg) offset = ASSERT( argMachRep rep `cmmEqType` globalRegType reg )
370                                 CmmStore (cmmRegOffW spReg offset) 
371                                          (CmmReg (CmmGlobal reg))
372
373      stk_adj_pop   = CmmAssign spReg (cmmRegOffW spReg final_stk_offset)
374      stk_adj_push  = CmmAssign spReg (cmmRegOffW spReg (- final_stk_offset))
375      jump_to_entry = CmmJump (mkLblExpr (enterLocalIdLabel name has_caf_refs)) []
376 \end{code}
377
378
379 %************************************************************************
380 %*                                                                      *
381 \subsubsection[closure-code-wrappers]{Wrappers around closure code}
382 %*                                                                      *
383 %************************************************************************
384
385 \begin{code}
386 thunkWrapper:: ClosureInfo -> Code -> Code
387 thunkWrapper closure_info thunk_code = do
388   { let node_points = nodeMustPointToIt (closureLFInfo closure_info)
389
390     -- HWL: insert macros for GrAnSim; 2 versions depending on liveness of node
391     -- (we prefer fetchAndReschedule-style context switches to yield ones)
392   ; if node_points 
393     then granFetchAndReschedule [] node_points 
394     else granYield              [] node_points
395
396         -- Stack and/or heap checks
397   ; thunkEntryChecks closure_info $ do
398         {
399           dflags <- getDynFlags
400           -- Overwrite with black hole if necessary
401         ; whenC (blackHoleOnEntry dflags closure_info && node_points)
402                 (blackHoleIt closure_info)
403         ; setupUpdate closure_info thunk_code }
404                 -- setupUpdate *encloses* the thunk_code
405   }
406
407 funWrapper :: ClosureInfo       -- Closure whose code body this is
408            -> [(Id,GlobalReg)]  -- List of argument registers (if any)
409            -> CmmStmts          -- reg saves for the heap check failure
410            -> Code              -- Body of function being compiled
411            -> Code
412 funWrapper closure_info arg_regs reg_save_code fun_body = do
413   { let node_points = nodeMustPointToIt (closureLFInfo closure_info)
414
415   {-
416         -- Debugging: check that R1 has the correct tag
417   ; let tag = funTag closure_info
418   ; whenC (tag /= 0 && node_points) $ do
419         l <- newLabelC
420         stmtC (CmmCondBranch (CmmMachOp mo_wordEq [cmmGetTag (CmmReg nodeReg),
421                                                    CmmLit (mkIntCLit tag)]) l)
422         stmtC (CmmStore (CmmLit (mkWordCLit 0)) (CmmLit (mkWordCLit 0)))
423         labelC l
424   -}
425
426         -- Enter for Ldv profiling
427   ; whenC node_points (ldvEnterClosure closure_info)
428
429         -- GranSim yeild poin
430   ; granYield arg_regs node_points
431
432         -- Heap and/or stack checks wrap the function body
433   ; funEntryChecks closure_info reg_save_code 
434                    fun_body
435   }
436 \end{code}
437
438
439 %************************************************************************
440 %*                                                                      *
441 \subsubsubsection[update-and-BHs]{Update and black-hole wrappers}
442 %*                                                                      *
443 %************************************************************************
444
445
446 \begin{code}
447 blackHoleIt :: ClosureInfo -> Code
448 -- Only called for closures with no args
449 -- Node points to the closure
450 blackHoleIt closure_info = emitBlackHoleCode (closureSingleEntry closure_info)
451
452 emitBlackHoleCode :: Bool -> Code
453 emitBlackHoleCode is_single_entry = do
454
455   dflags <- getDynFlags
456
457         -- If we wanted to do eager blackholing with slop filling,
458         -- we'd need to do it at the *end* of a basic block, otherwise
459         -- we overwrite the free variables in the thunk that we still
460         -- need.  We have a patch for this from Andy Cheadle, but not
461         -- incorporated yet. --SDM [6/2004]
462         --
463         -- Profiling needs slop filling (to support LDV profiling), so
464         -- currently eager blackholing doesn't work with profiling.
465         --
466         -- Previously, eager blackholing was enabled when ticky-ticky
467         -- was on. But it didn't work, and it wasn't strictly necessary 
468         -- to bring back minimal ticky-ticky, so now EAGER_BLACKHOLING 
469         -- is unconditionally disabled. -- krc 1/2007
470
471   let eager_blackholing =  not opt_SccProfilingOn
472                         && dopt Opt_EagerBlackHoling dflags
473
474   if eager_blackholing
475      then do
476           tickyBlackHole (not is_single_entry)
477           let bh_info = CmmReg (CmmGlobal EagerBlackholeInfo)
478           stmtC (CmmStore (CmmReg nodeReg) bh_info)
479      else
480           nopC
481 \end{code}
482
483 \begin{code}
484 setupUpdate :: ClosureInfo -> Code -> Code      -- Only called for closures with no args
485         -- Nota Bene: this function does not change Node (even if it's a CAF),
486         -- so that the cost centre in the original closure can still be
487         -- extracted by a subsequent enterCostCentre
488 setupUpdate closure_info code
489   | closureReEntrant closure_info
490   = code
491
492   | not (isStaticClosure closure_info)
493   = if closureUpdReqd closure_info
494     then do { tickyPushUpdateFrame;  pushUpdateFrame (CmmReg nodeReg) code }
495     else do { tickyUpdateFrameOmitted; code }
496  
497   | otherwise   -- A static closure
498   = do  { tickyUpdateBhCaf closure_info
499
500         ; if closureUpdReqd closure_info
501           then do       -- Blackhole the (updatable) CAF:
502                 { upd_closure <- link_caf closure_info True
503                 ; pushUpdateFrame upd_closure code }
504           else do
505                 { -- krc: removed some ticky-related code here.
506                 ; tickyUpdateFrameOmitted
507                 ; code }
508     }
509
510
511 -----------------------------------------------------------------------------
512 -- Entering a CAF
513 --
514 -- When a CAF is first entered, it creates a black hole in the heap,
515 -- and updates itself with an indirection to this new black hole.
516 --
517 -- We update the CAF with an indirection to a newly-allocated black
518 -- hole in the heap.  We also set the blocking queue on the newly
519 -- allocated black hole to be empty.
520 --
521 -- Why do we make a black hole in the heap when we enter a CAF?
522 --    
523 --     - for a  generational garbage collector, which needs a fast
524 --       test for whether an updatee is in an old generation or not
525 --
526 --     - for the parallel system, which can implement updates more
527 --       easily if the updatee is always in the heap. (allegedly).
528 --
529 -- When debugging, we maintain a separate CAF list so we can tell when
530 -- a CAF has been garbage collected.
531
532 -- newCAF must be called before the itbl ptr is overwritten, since
533 -- newCAF records the old itbl ptr in order to do CAF reverting
534 -- (which Hugs needs to do in order that combined mode works right.)
535 --
536
537 -- ToDo [Feb 04]  This entire link_caf nonsense could all be moved
538 -- into the "newCAF" RTS procedure, which we call anyway, including
539 -- the allocation of the black-hole indirection closure.
540 -- That way, code size would fall, the CAF-handling code would 
541 -- be closer together, and the compiler wouldn't need to know
542 -- about off_indirectee etc.
543
544 link_caf :: ClosureInfo
545          -> Bool                -- True <=> updatable, False <=> single-entry
546          -> FCode CmmExpr       -- Returns amode for closure to be updated
547 -- To update a CAF we must allocate a black hole, link the CAF onto the
548 -- CAF list, then update the CAF to point to the fresh black hole.
549 -- This function returns the address of the black hole, so it can be
550 -- updated with the new value when available.  The reason for all of this
551 -- is that we only want to update dynamic heap objects, not static ones,
552 -- so that generational GC is easier.
553 link_caf cl_info _is_upd = do
554   {     -- Alloc black hole specifying CC_HDR(Node) as the cost centre
555   ; let use_cc   = costCentreFrom (CmmReg nodeReg)
556         blame_cc = use_cc
557   ; hp_offset <- allocDynClosure bh_cl_info use_cc blame_cc []
558   ; hp_rel    <- getHpRelOffset hp_offset
559
560         -- Call the RTS function newCAF to add the CAF to the CafList
561         -- so that the garbage collector can find them
562         -- This must be done *before* the info table pointer is overwritten, 
563         -- because the old info table ptr is needed for reversion
564   ; emitRtsCallWithVols (sLit "newCAF") [CmmHinted (CmmReg nodeReg) AddrHint] [node] False
565         -- node is live, so save it.
566
567         -- Overwrite the closure with a (static) indirection 
568         -- to the newly-allocated black hole
569   ; stmtsC [ CmmStore (cmmRegOffW nodeReg off_indirectee) hp_rel
570            , CmmStore (CmmReg nodeReg) ind_static_info ]
571
572   ; returnFC hp_rel }
573   where
574     bh_cl_info :: ClosureInfo
575     bh_cl_info = cafBlackHoleClosureInfo cl_info
576
577     ind_static_info :: CmmExpr
578     ind_static_info = mkLblExpr mkIndStaticInfoLabel
579
580     off_indirectee :: WordOff
581     off_indirectee = fixedHdrSize + oFFSET_StgInd_indirectee*wORD_SIZE
582 \end{code}
583
584
585 %************************************************************************
586 %*                                                                      *
587 \subsection[CgClosure-Description]{Profiling Closure Description.}
588 %*                                                                      *
589 %************************************************************************
590
591 For "global" data constructors the description is simply occurrence
592 name of the data constructor itself.  Otherwise it is determined by
593 @closureDescription@ from the let binding information.
594
595 \begin{code}
596 closureDescription :: Module            -- Module
597                    -> Name              -- Id of closure binding
598                    -> String
599         -- Not called for StgRhsCon which have global info tables built in
600         -- CgConTbls.lhs with a description generated from the data constructor
601 closureDescription mod_name name
602   = showSDocDumpOneLine (char '<' <>
603                     (if isExternalName name
604                       then ppr name -- ppr will include the module name prefix
605                       else pprModule mod_name <> char '.' <> ppr name) <>
606                     char '>')
607    -- showSDocDumpOneLine, because we want to see the unique on the Name.
608 \end{code}
609