Home | History | Annotate | Line # | Download | only in uvm
uvm_pdaemon.c revision 1.4
      1 /*	$NetBSD: uvm_pdaemon.c,v 1.4 1998/02/07 11:09:33 mrg Exp $	*/
      2 
      3 /*
      4  * XXXCDC: "ROUGH DRAFT" QUALITY UVM PRE-RELEASE FILE!
      5  *         >>>USE AT YOUR OWN RISK, WORK IS NOT FINISHED<<<
      6  */
      7 /*
      8  * Copyright (c) 1997 Charles D. Cranor and Washington University.
      9  * Copyright (c) 1991, 1993, The Regents of the University of California.
     10  *
     11  * All rights reserved.
     12  *
     13  * This code is derived from software contributed to Berkeley by
     14  * The Mach Operating System project at Carnegie-Mellon University.
     15  *
     16  * Redistribution and use in source and binary forms, with or without
     17  * modification, are permitted provided that the following conditions
     18  * are met:
     19  * 1. Redistributions of source code must retain the above copyright
     20  *    notice, this list of conditions and the following disclaimer.
     21  * 2. Redistributions in binary form must reproduce the above copyright
     22  *    notice, this list of conditions and the following disclaimer in the
     23  *    documentation and/or other materials provided with the distribution.
     24  * 3. All advertising materials mentioning features or use of this software
     25  *    must display the following acknowledgement:
     26  *	This product includes software developed by Charles D. Cranor,
     27  *      Washington University, the University of California, Berkeley and
     28  *      its contributors.
     29  * 4. Neither the name of the University nor the names of its contributors
     30  *    may be used to endorse or promote products derived from this software
     31  *    without specific prior written permission.
     32  *
     33  * THIS SOFTWARE IS PROVIDED BY THE REGENTS AND CONTRIBUTORS ``AS IS'' AND
     34  * ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
     35  * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
     36  * ARE DISCLAIMED.  IN NO EVENT SHALL THE REGENTS OR CONTRIBUTORS BE LIABLE
     37  * FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
     38  * DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
     39  * OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
     40  * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
     41  * LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
     42  * OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
     43  * SUCH DAMAGE.
     44  *
     45  *	@(#)vm_pageout.c        8.5 (Berkeley) 2/14/94
     46  * from: Id: uvm_pdaemon.c,v 1.1.2.32 1998/02/06 05:26:30 chs Exp
     47  *
     48  *
     49  * Copyright (c) 1987, 1990 Carnegie-Mellon University.
     50  * All rights reserved.
     51  *
     52  * Permission to use, copy, modify and distribute this software and
     53  * its documentation is hereby granted, provided that both the copyright
     54  * notice and this permission notice appear in all copies of the
     55  * software, derivative works or modified versions, and any portions
     56  * thereof, and that both notices appear in supporting documentation.
     57  *
     58  * CARNEGIE MELLON ALLOWS FREE USE OF THIS SOFTWARE IN ITS "AS IS"
     59  * CONDITION.  CARNEGIE MELLON DISCLAIMS ANY LIABILITY OF ANY KIND
     60  * FOR ANY DAMAGES WHATSOEVER RESULTING FROM THE USE OF THIS SOFTWARE.
     61  *
     62  * Carnegie Mellon requests users of this software to return to
     63  *
     64  *  Software Distribution Coordinator  or  Software.Distribution (at) CS.CMU.EDU
     65  *  School of Computer Science
     66  *  Carnegie Mellon University
     67  *  Pittsburgh PA 15213-3890
     68  *
     69  * any improvements or extensions that they make and grant Carnegie the
     70  * rights to redistribute these changes.
     71  */
     72 
     73 /*
     74  * uvm_pdaemon.c: the page daemon
     75  */
     76 
     77 #include <sys/param.h>
     78 #include <sys/proc.h>
     79 #include <sys/systm.h>
     80 #include <sys/kernel.h>
     81 
     82 #include <vm/vm.h>
     83 #include <vm/vm_page.h>
     84 #include <vm/vm_kern.h>
     85 
     86 #include <uvm/uvm.h>
     87 
     88 UVMHIST_DECL(pdhist);
     89 
     90 /*
     91  * local prototypes
     92  */
     93 
     94 static void		uvmpd_scan __P((void));
     95 static boolean_t	uvmpd_scan_inactive __P((struct pglist *));
     96 static void		uvmpd_tune __P((void));
     97 
     98 
     99 /*
    100  * uvm_wait: wait (sleep) for the page daemon to free some pages
    101  *
    102  * => should be called with all locks released
    103  * => should _not_ be called by the page daemon (to avoid deadlock)
    104  */
    105 
    106 void uvm_wait(wmsg)
    107 
    108 char *wmsg;
    109 
    110 {
    111   int timo = 0;
    112   int s = splbio();
    113 
    114   /*
    115    * check for page daemon going to sleep (waiting for itself)
    116    */
    117 
    118   if (curproc == uvm.pagedaemon_proc) {
    119     /*
    120      * now we have a problem: the pagedaemon wants to go to sleep until
    121      * it frees more memory.   but how can it free more memory if it is
    122      * asleep?  that is a deadlock.   we have two options:
    123      *  [1] panic now
    124      *  [2] put a timeout on the sleep, thus causing the pagedaemon to
    125      *	    only pause (rather than sleep forever)
    126      *
    127      * note that option [2] will only help us if we get lucky and some
    128      * other process on the system breaks the deadlock by exiting or
    129      * freeing memory (thus allowing the pagedaemon to continue).
    130      * for now we panic if DEBUG is defined, otherwise we hope for the
    131      * best with option [2]  (better yet, this should never happen in
    132      * the first place!).
    133      */
    134 
    135     printf("pagedaemon: deadlock detected!\n");
    136     timo = hz >> 3;		/* set timeout */
    137 #if defined(DEBUG)
    138     panic("pagedaemon deadlock");	/* DEBUG: panic so we can debug it */
    139 #endif
    140   }
    141 
    142   simple_lock(&uvm.pagedaemon_lock);
    143   thread_wakeup(&uvm.pagedaemon);		/* wake the daemon! */
    144   UVM_UNLOCK_AND_WAIT(&uvmexp.free, &uvm.pagedaemon_lock, FALSE, wmsg, timo);
    145 
    146   splx(s);
    147 }
    148 
    149 
    150 /*
    151  * uvmpd_tune: tune paging parameters
    152  *
    153  * => called when ever memory is added (or removed?) to the system
    154  * => caller must call with page queues locked
    155  */
    156 
    157 static void uvmpd_tune()
    158 
    159 {
    160   UVMHIST_FUNC("uvmpd_tune"); UVMHIST_CALLED(pdhist);
    161 
    162   uvmexp.freemin = uvmexp.npages / 20;
    163   uvmexp.freemin = max(uvmexp.freemin, (16*1024)/PAGE_SIZE);  /* at least 16K */
    164   uvmexp.freemin = min(uvmexp.freemin, (256*1024)/PAGE_SIZE); /* at most 256K */
    165 
    166   uvmexp.freetarg = (uvmexp.freemin * 4) / 3;
    167   if (uvmexp.freetarg <= uvmexp.freemin)
    168     uvmexp.freetarg = uvmexp.freemin + 1;
    169 
    170   /* uvmexp.inactarg: computed in main daemon loop */
    171 
    172   uvmexp.wiredmax = uvmexp.npages / 3;
    173   UVMHIST_LOG(pdhist, "<- done, freemin=%d, freetarg=%d, wiredmax=%d",
    174 	      uvmexp.freemin, uvmexp.freetarg, uvmexp.wiredmax, 0);
    175 }
    176 
    177 /*
    178  * uvm_pageout: the main loop for the pagedaemon
    179  */
    180 
    181 void uvm_pageout()
    182 
    183 {
    184   int npages = 0;
    185   int s;
    186   struct uvm_aiodesc *aio, *nextaio;
    187   UVMHIST_FUNC("uvm_pageout"); UVMHIST_CALLED(pdhist);
    188 
    189   UVMHIST_LOG(pdhist,"<starting uvm pagedaemon>", 0, 0, 0, 0);
    190 
    191   /*
    192    * ensure correct priority and set paging parameters...
    193    */
    194 
    195   uvm.pagedaemon_proc = curproc;
    196   (void) spl0();
    197   uvm_lock_pageq();
    198   npages = uvmexp.npages;
    199   uvmpd_tune();
    200   uvm_unlock_pageq();
    201 
    202   /*
    203    * main loop
    204    */
    205   while (TRUE) {
    206 
    207     /*
    208      * carefully attempt to go to sleep (without losing "wakeups"!).
    209      * we need splbio because we want to make sure the aio_done list
    210      * is totally empty before we go to sleep.
    211      */
    212 
    213     s = splbio();
    214     simple_lock(&uvm.pagedaemon_lock);
    215 
    216     /*
    217      * if we've got done aio's, then bypass the sleep
    218      */
    219 
    220     if (uvm.aio_done.tqh_first == NULL) {
    221       UVMHIST_LOG(maphist,"  <<SLEEPING>>",0,0,0,0);
    222       UVM_UNLOCK_AND_WAIT(&uvm.pagedaemon, &uvm.pagedaemon_lock, FALSE,
    223 			  "daemon_slp", 0);
    224       uvmexp.pdwoke++;
    225       UVMHIST_LOG(pdhist,"  <<WOKE UP>>",0,0,0,0);
    226 
    227       /* relock pagedaemon_lock, still at splbio */
    228       simple_lock(&uvm.pagedaemon_lock);
    229     }
    230 
    231     /*
    232      * check for done aio structures
    233      */
    234 
    235     aio = uvm.aio_done.tqh_first;		/* save current list (if any)*/
    236     if (aio) {
    237       TAILQ_INIT(&uvm.aio_done);		/* zero global list */
    238     }
    239 
    240     simple_unlock(&uvm.pagedaemon_lock);	/* unlock */
    241     splx(s);					/* drop splbio */
    242 
    243     /*
    244      * first clear out any pending aios (to free space in case we
    245      * want to pageout more stuff).
    246      */
    247 
    248     for (/*null*/; aio != NULL ; aio = nextaio) {
    249 
    250       uvmexp.paging -= aio->npages;
    251       nextaio = aio->aioq.tqe_next;
    252       aio->aiodone(aio);
    253 
    254     }
    255 
    256     /*
    257      * now lock page queues and recompute inactive count
    258      */
    259     uvm_lock_pageq();
    260 
    261     if (npages != uvmexp.npages) {		/* check for new pages? */
    262       npages = uvmexp.npages;
    263       uvmpd_tune();
    264     }
    265 
    266     uvmexp.inactarg = (uvmexp.active + uvmexp.inactive) / 3;
    267     if (uvmexp.inactarg <= uvmexp.freetarg)
    268       uvmexp.inactarg = uvmexp.freetarg + 1;
    269 
    270     UVMHIST_LOG(pdhist,"  free/ftarg=%d/%d, inact/itarg=%d/%d",
    271 	uvmexp.free, uvmexp.freetarg, uvmexp.inactive, uvmexp.inactarg);
    272 
    273     /*
    274      * scan if needed
    275      * [XXX: note we are reading uvm.free without locking]
    276      */
    277     if (uvmexp.free < uvmexp.freetarg || uvmexp.inactive < uvmexp.inactarg)
    278       uvmpd_scan();
    279 
    280     /*
    281      * done scan.  unlock page queues (the only lock we are holding).
    282      */
    283     uvm_unlock_pageq();
    284 
    285     /*
    286      * done!    restart loop.
    287      */
    288     thread_wakeup(&uvmexp.free);
    289   }
    290   /*NOTREACHED*/
    291 }
    292 
    293 /*
    294  * uvmpd_scan_inactive: the first loop of uvmpd_scan broken out into
    295  * 	its own function for ease of reading.
    296  *
    297  * => called with page queues locked
    298  * => we work on meeting our free target by converting inactive pages
    299  *    into free pages.
    300  * => we handle the building of swap-backed clusters
    301  * => we return TRUE if we are exiting because we met our target
    302  */
    303 
    304 static boolean_t uvmpd_scan_inactive(pglst)
    305 
    306 struct pglist *pglst;
    307 
    308 {
    309   boolean_t retval = FALSE;	/* assume we haven't hit target */
    310   int s, free, result;
    311   struct vm_page *p, *nextpg;
    312   struct uvm_object *uobj;
    313   struct vm_page *pps[MAXBSIZE/PAGE_SIZE], **ppsp;
    314   int npages;
    315   struct vm_page *swpps[MAXBSIZE/PAGE_SIZE]; 		/* XXX: see below */
    316   int swnpages, swcpages;				/* XXX: see below */
    317   int swslot, oldslot;
    318   struct vm_anon *anon;
    319   boolean_t swap_backed;
    320   vm_offset_t start;
    321   UVMHIST_FUNC("uvmpd_scan_inactive"); UVMHIST_CALLED(pdhist);
    322 
    323   /*
    324    * note: we currently keep swap-backed pages on a seperate inactive
    325    * list from object-backed pages.   however, merging the two lists
    326    * back together again hasn't been ruled out.   thus, we keep our
    327    * swap cluster in "swpps" rather than in pps (allows us to mix clustering
    328    * types in the event of a mixed inactive queue).
    329    */
    330 
    331   /*
    332    * swslot is non-zero if we are building a swap cluster.  we want
    333    * to stay in the loop while we have a page to scan or we have
    334    * a swap-cluster to build.
    335    */
    336   swslot = 0;
    337   swnpages = swcpages = 0;
    338   free = 0;
    339 
    340   for (p = pglst->tqh_first ; p != NULL || swslot != 0 ; p = nextpg) {
    341 
    342     /*
    343      * note that p can be NULL iff we have traversed the whole
    344      * list and need to do one final swap-backed clustered pageout.
    345      */
    346     if (p) {
    347       /*
    348        * update our copy of "free" and see if we've met our target
    349        */
    350       s = splimp();
    351       uvm_lock_fpageq();
    352       free = uvmexp.free;
    353       uvm_unlock_fpageq();
    354       splx(s);
    355 
    356       if (free >= uvmexp.freetarg) {
    357 	UVMHIST_LOG(pdhist,"  met free target: exit loop", 0, 0, 0, 0);
    358 	retval = TRUE;		/* hit the target! */
    359 	if (swslot == 0)
    360 	  break;	/* exit now if no swap-i/o pending */
    361 	p = NULL;	/* set p to null to signal final swap i/o */
    362       }
    363     }
    364 
    365     uobj = NULL;	/* be safe and shut gcc up */
    366     anon = NULL;	/* be safe and shut gcc up */
    367 
    368     if (p) {	/* if (we have a new page to consider) */
    369       /*
    370        * we are below target and have a new page to consider.
    371        */
    372       uvmexp.pdscans++;
    373       nextpg = p->pageq.tqe_next;
    374 
    375       /*
    376        * move referenced pages back to active queue and skip to next page
    377        * (unlikely to happen since inactive pages shouldn't have any
    378        *  valid mappings and we cleared reference before deactivating).
    379        */
    380       if (pmap_is_referenced(PMAP_PGARG(p))) {
    381 	uvm_pageactivate(p);
    382 	uvmexp.pdreact++;
    383 	continue;
    384       }
    385 
    386       /*
    387        * first we attempt to lock the object that this page belongs to.
    388        * if our attempt fails we skip on to the next page (no harm done).
    389        * it is important to "try" locking the object as we are locking in the
    390        * wrong order (pageq -> object) and we don't want to get deadlocked.
    391        *
    392        * the only time we exepct to see an ownerless page (i.e. a page
    393        * with no uobject and !PQ_ANON) is if an anon has loaned a page
    394        * from a uvm_object and the uvm_object has dropped the ownership.
    395        * in that case, the anon can "take over" the loaned page and
    396        * make it its own.
    397        */
    398 
    399       /* is page part of an anon or ownerless ? */
    400       if ((p->pqflags & PQ_ANON) || p->uobject == NULL) {
    401 
    402 	anon = p->uanon;
    403 
    404 #ifdef DIAGNOSTIC
    405         /* to be on inactive q, page must be part of _something_ */
    406         if (anon == NULL)
    407           panic("pagedaemon: page with no anon or object detected - loop 1");
    408 #endif
    409 
    410 	if (!simple_lock_try(&anon->an_lock))
    411 	  continue;		/* lock failed, skip this page */
    412 
    413         /* if the page is ownerless, claim it in the name of "anon"! */
    414         if ((p->pqflags & PQ_ANON) == 0) {
    415 #ifdef DIAGNOSTIC
    416           if (p->loan_count < 1)
    417             panic("pagedaemon: non-loaned ownerless page detected - loop 1");
    418 #endif
    419           p->loan_count--;
    420           p->pqflags |= PQ_ANON;      /* anon now owns it */
    421         }
    422 
    423 	if (p->flags & PG_BUSY) {
    424 	  simple_unlock(&anon->an_lock);
    425 	  uvmexp.pdbusy++;
    426 	  continue;		/* someone else owns page, skip it */
    427 	}
    428 
    429 	uvmexp.pdanscan++;
    430 
    431       } else {
    432 
    433 	uobj = p->uobject;
    434 
    435 	if (!simple_lock_try(&uobj->vmobjlock))
    436 	  continue;		/* lock failed, skip this page */
    437 
    438 	if (p->flags & PG_BUSY) {
    439 	  simple_unlock(&uobj->vmobjlock);
    440 	  uvmexp.pdbusy++;
    441 	  continue;		/* someone else owns page, skip it */
    442 	}
    443 
    444 	uvmexp.pdobscan++;
    445 
    446       }
    447 
    448       /*
    449        * we now have the object and the page queues locked.  the page is
    450        * not busy.   if the page is clean we can free it now and continue.
    451        */
    452 
    453       if (p->flags & PG_CLEAN) {
    454 	/* zap all mappings with pmap_page_protect... */
    455 	pmap_page_protect(PMAP_PGARG(p), VM_PROT_NONE);
    456 	uvm_pagefree(p);
    457 	uvmexp.pdfreed++;
    458 
    459 	if (anon) {
    460 #ifdef DIAGNOSTIC
    461 	  /*
    462 	   * an anonymous page can only be clean if it has valid
    463 	   * backing store.
    464 	   */
    465 	  if (anon->an_swslot == 0)
    466 	    panic("pagedaemon: clean anon page without backing store?");
    467 #endif
    468 	  anon->u.an_page = NULL;		/* remove from object */
    469 	  simple_unlock(&anon->an_lock);
    470 	} else {
    471 	  /* pagefree has already removed the page from the object */
    472 	  simple_unlock(&uobj->vmobjlock);
    473 	}
    474 	continue;
    475       }
    476 
    477       /*
    478        * this page is dirty, skip it if we'll have met
    479        * our free target when all the current pageouts complete.
    480        */
    481       if (free + uvmexp.paging > uvmexp.freetarg)
    482       {
    483 	if (anon) {
    484 	  simple_unlock(&anon->an_lock);
    485 	} else {
    486 	  simple_unlock(&uobj->vmobjlock);
    487 	}
    488 	continue;
    489       }
    490 
    491       /*
    492        * the page we are looking at is dirty.   we must clean it before
    493        * it can be freed.  to do this we first mark the page busy so that
    494        * no one else will touch the page.   we write protect all the mappings
    495        * of the page so that no one touches it while it is in I/O.
    496        */
    497 
    498       swap_backed = ((p->pqflags & PQ_SWAPBACKED) != 0);
    499       uvmexp.pdpageouts++;
    500       p->flags |= PG_BUSY;		/* now we own it */
    501       UVM_PAGE_OWN(p, "scan_inactive");
    502       pmap_page_protect(PMAP_PGARG(p), VM_PROT_READ);
    503 
    504       /*
    505        * for swap-backed pages we need to (re)allocate swap space.
    506        */
    507       if (swap_backed) {
    508 
    509 	/*
    510 	 * free old swap slot (if any)
    511 	 */
    512 	if (anon) {
    513 	  if (anon->an_swslot) {
    514 	    uvm_swap_free(anon->an_swslot, 1);
    515 	    anon->an_swslot = 0;
    516 	  }
    517 	} else {
    518 	  oldslot = uao_set_swslot(uobj, p->offset/PAGE_SIZE, 0); /* remove */
    519 	  if (oldslot)
    520 	    uvm_swap_free(oldslot, 1); /* free */
    521 	}
    522 
    523 	/*
    524 	 * start new cluster (if necessary)
    525 	 */
    526 	if (swslot == 0) {
    527 	  swnpages = MAXBSIZE/PAGE_SIZE;	/* want this much */
    528 	  swslot = uvm_swap_alloc(&swnpages, TRUE);
    529 
    530 	  if (swslot == 0) {
    531 	    /* no swap?  give up! */
    532 	    p->flags &= ~PG_BUSY;
    533             UVM_PAGE_OWN(p, NULL);
    534 	    if (anon)
    535 	      simple_unlock(&anon->an_lock);
    536 	    else
    537 	      simple_unlock(&uobj->vmobjlock);
    538 	    continue;
    539 	  }
    540 	  swcpages = 0;	/* cluster is empty */
    541 	}
    542 
    543 	/*
    544 	 * add block to cluster
    545 	 */
    546 	swpps[swcpages] = p;
    547 	if (anon)
    548 	  anon->an_swslot = swslot + swcpages;
    549 	else
    550 	  uao_set_swslot(uobj, p->offset/PAGE_SIZE, swslot + swcpages);
    551 	swcpages++;
    552 
    553 	/* done (swap-backed) */
    554       }
    555 
    556       /* end: if (p) [end of "if we have new page to consider"] */
    557     } else {
    558 
    559       swap_backed = TRUE; /* if p == NULL we must be doing a last swap i/o */
    560 
    561     }
    562 
    563     /*
    564      * now consider doing the pageout.
    565      *
    566      * for swap-backed pages, we do the pageout if we have either
    567      * filled the cluster (in which case (swnpages == swcpages) or
    568      * run out of pages (p == NULL).
    569      *
    570      * for object pages, we always do the pageout.
    571      */
    572     if (swap_backed) {
    573 
    574       if (p) {	/* if we just added a page to cluster */
    575 	if (anon)
    576 	  simple_unlock(&anon->an_lock);
    577 	else
    578 	  simple_unlock(&uobj->vmobjlock);
    579 	if (swcpages < swnpages)	/* cluster not full yet? */
    580 	  continue;
    581       }
    582 
    583       /* starting I/O now... set up for it */
    584       npages = swcpages;
    585       ppsp = swpps;
    586       start = (vm_offset_t) swslot;	/* for swap-backed pages only */
    587 
    588       /* if this is final pageout we could have a few extra swap blocks */
    589       if (swcpages < swnpages) {
    590 	uvm_swap_free(swslot + swcpages, (swnpages - swcpages));
    591       }
    592 
    593     } else {
    594 
    595       /* normal object pageout */
    596       ppsp = pps;
    597       npages = sizeof(pps) / sizeof(struct vm_page *);
    598       start = 0;	/* not looked at because PGO_ALLPAGES is set */
    599 
    600     }
    601 
    602     /*
    603      * now do the pageout.
    604      *
    605      * for swap_backed pages we have already built the cluster.
    606      * for !swap_backed pages, uvm_pager_put will call the object's
    607      * "make put cluster" function to build a cluster on our behalf.
    608      *
    609      * we pass the PGO_PDFREECLUST flag to uvm_pager_put to instruct
    610      * it to free the cluster pages for us on a successful I/O (it always
    611      * does this for un-successful I/O requests).  this allows us to
    612      * do clustered pageout without having to deal with cluster pages
    613      * at this level.
    614      *
    615      * note locking semantics of uvm_pager_put with PGO_PDFREECLUST:
    616      *  IN:  locked: uobj (if !swap_backed), page queues
    617      * OUT:  locked: uobj (if !swap_backed && result != VM_PAGER_PEND)
    618      *      !locked: page queues, uobj (if swap_backed || VM_PAGER_PEND)
    619      *
    620      * [the bit about VM_PAGER_PEND saves us one lock-unlock pair]
    621      */
    622 
    623     /* locked: uobj (if !swap_backed), page queues */
    624     result = uvm_pager_put((swap_backed) ? NULL : uobj, p, &ppsp, &npages,
    625 			   PGO_ALLPAGES|PGO_PDFREECLUST, start, 0);
    626     /* locked: uobj (if !swap_backed && result != PEND) */
    627     /* unlocked: page queues, object (if swap_backed || result == PEND) */
    628 
    629     /*
    630      * if we did i/o to swap, zero swslot to indicate that we are
    631      * no longer building a swap-backed cluster.
    632      */
    633 
    634     if (swap_backed)
    635       swslot = 0;		/* done with this cluster */
    636 
    637     /*
    638      * first, we check for VM_PAGER_PEND which means that the async I/O
    639      * is in progress and the async I/O done routine will clean up
    640      * after us.   in this case we move on to the next page.
    641      *
    642      * there is a very remote chance that the pending async i/o can
    643      * finish _before_ we get here.   if that happens, our page "p"
    644      * may no longer be on the inactive queue.   so we verify this
    645      * when determining the next page (starting over at the head if
    646      * we've lost our inactive page).
    647      */
    648 
    649     if (result == VM_PAGER_PEND) {
    650       uvmexp.paging += npages;
    651       uvm_lock_pageq();				/* relock page queues */
    652       uvmexp.pdpending++;
    653       if (p) {
    654 	if (p->pqflags & PQ_INACTIVE)
    655 	  nextpg = p->pageq.tqe_next;		/* reload! */
    656 	else
    657 	  nextpg = pglst->tqh_first;		/* reload! */
    658       } else {
    659 	nextpg = NULL;				/* done list */
    660       }
    661       continue;
    662     }
    663 
    664     /*
    665      * clean up "p" if we have one
    666      */
    667 
    668     if (p) {
    669       /*
    670        * the I/O request to "p" is done and uvm_pager_put has freed
    671        * any cluster pages it may have allocated during I/O.  all
    672        * that is left for us to do is clean up page "p" (which is
    673        * still PG_BUSY).
    674        *
    675        * our result could be one of the following:
    676        *   VM_PAGER_OK: successful pageout
    677        *
    678        *   VM_PAGER_AGAIN: tmp resource shortage, we skip to next page
    679        *   VM_PAGER_{FAIL,ERROR,BAD}: an error.   we "reactivate"
    680        *		page to get it out of the way (it will eventually
    681        *		drift back into the inactive queue for a retry).
    682        *   VM_PAGER_UNLOCK: should never see this as it is only
    683        *		valid for "get" operations
    684        */
    685 
    686       /* relock p's object: page queues not lock yet, so no need for "try" */
    687       if (swap_backed) {	/* !swap_backed case: already locked... */
    688 	if (anon)
    689 	  simple_lock(&anon->an_lock);
    690 	else
    691 	  simple_lock(&uobj->vmobjlock);
    692       }
    693 
    694 #ifdef DIAGNOSTIC
    695       if (result == VM_PAGER_UNLOCK)
    696 	panic("pagedaemon: pageout returned invalid 'unlock' code");
    697 #endif
    698 
    699       /* handle PG_WANTED now */
    700       if (p->flags & PG_WANTED)
    701 	thread_wakeup(p);			/* still holding object lock */
    702       p->flags &= ~(PG_BUSY|PG_WANTED);
    703       UVM_PAGE_OWN(p, NULL);
    704 
    705       /* released during I/O? */
    706       if (p->flags & PG_RELEASED) {
    707 	if (anon) {
    708 	  anon->u.an_page = NULL;	/* remove page so we can get nextpg */
    709 	  simple_unlock(&anon->an_lock);/* XXX needed? */
    710 	  uvm_anfree(anon);		/* kills anon */
    711 	  pmap_page_protect(PMAP_PGARG(p), VM_PROT_NONE);
    712 	  anon = NULL;
    713 	  uvm_lock_pageq();
    714 	  nextpg = p->pageq.tqe_next;
    715 	  uvm_pagefree(p);			/* free released page */
    716 
    717 	} else {
    718 
    719 #ifdef DIAGNOSTIC
    720 	  if (uobj->pgops->pgo_releasepg == NULL)
    721 	    panic("pagedaemon: no pgo_releasepg function");
    722 #endif
    723 
    724 	  /*
    725 	   * pgo_releasepg nukes the page and gets "nextpg" for us.
    726 	   * it returns with the page queues locked (when given nextpg ptr).
    727 	   */
    728 	  if (!uobj->pgops->pgo_releasepg(p, &nextpg))
    729 	    uobj = NULL;			/* uobj died after release */
    730 
    731 	  /*
    732 	   * lock page queues here so that they're always locked
    733 	   * at the end of the loop.
    734 	   */
    735 	  uvm_lock_pageq();
    736 	}
    737 
    738       } else {	/* page was not released during I/O */
    739 
    740 	uvm_lock_pageq();
    741 	nextpg = p->pageq.tqe_next;
    742 
    743 	if (result != VM_PAGER_OK) {
    744 
    745 	  /* pageout was a failure... */
    746 	  if (result != VM_PAGER_AGAIN)
    747 	    uvm_pageactivate(p);
    748 	  pmap_clear_reference(PMAP_PGARG(p));
    749 	  /* XXXCDC: if (swap_backed) FREE p's swap block? */
    750 
    751 	} else {
    752 
    753 	  /* pageout was a success... */
    754 	  pmap_clear_reference(PMAP_PGARG(p));
    755 	  pmap_clear_modify(PMAP_PGARG(p));
    756 	  p->flags |= PG_CLEAN;
    757 	  /* XXX: could free page here, but old pagedaemon does not */
    758 
    759 	}
    760       }
    761 
    762       /*
    763        * drop object lock (if there is an object left).   do a safety
    764        * check of nextpg to make sure it is on the inactive queue
    765        * (it should be since PG_BUSY pages on the inactive queue can't
    766        * be re-queued [note: not true for active queue]).
    767        */
    768 
    769       if (anon)
    770 	simple_unlock(&anon->an_lock);
    771       else if (uobj)
    772 	simple_unlock(&uobj->vmobjlock);
    773 
    774     } /* if (p) */ else {
    775 
    776       /* if p is null in this loop, make sure it stays null in next loop */
    777       nextpg = NULL;
    778 
    779       /*
    780        * lock page queues here just so they're always locked
    781        * at the end of the loop.
    782        */
    783       uvm_lock_pageq();
    784     }
    785 
    786     if (nextpg && (nextpg->pqflags & PQ_INACTIVE) == 0) {
    787       printf("pagedaemon: invalid nextpg!   reverting to queue head\n");
    788       nextpg = pglst->tqh_first;	/* reload! */
    789     }
    790 
    791   }		/* end of "inactive" 'for' loop */
    792   return(retval);
    793 }
    794 
    795 /*
    796  * uvmpd_scan: scan the page queues and attempt to meet our targets.
    797  *
    798  * => called with pageq's locked
    799  */
    800 
    801 void uvmpd_scan()
    802 
    803 {
    804   int s, free, pages_freed, page_shortage;
    805   struct vm_page *p, *nextpg;
    806   struct uvm_object *uobj;
    807   boolean_t got_it;
    808   UVMHIST_FUNC("uvmpd_scan"); UVMHIST_CALLED(pdhist);
    809 
    810   uvmexp.pdrevs++;		/* counter */
    811 
    812 #ifdef __GNUC__
    813   uobj = NULL;	/* XXX gcc */
    814 #endif
    815   /*
    816    * get current "free" page count
    817    */
    818   s = splimp();
    819   uvm_lock_fpageq();
    820   free = uvmexp.free;
    821   uvm_unlock_fpageq();
    822   splx(s);
    823 
    824 #ifndef __SWAP_BROKEN
    825   /*
    826    * swap out some processes if we are below our free target.
    827    * we need to unlock the page queues for this.
    828    */
    829   if (free < uvmexp.freetarg) {
    830 
    831     uvmexp.pdswout++;
    832     UVMHIST_LOG(pdhist,"  free %d < target %d: swapout", free, uvmexp.freetarg,
    833 		0,0);
    834     uvm_unlock_pageq();
    835     uvm_swapout_threads();
    836     pmap_update();		/* update so we can scan inactive q */
    837     uvm_lock_pageq();
    838 
    839   }
    840 #endif
    841 
    842   /*
    843    * now we want to work on meeting our targets.   first we work on our
    844    * free target by converting inactive pages into free pages.  then
    845    * we work on meeting our inactive target by converting active pages
    846    * to inactive ones.
    847    */
    848 
    849   UVMHIST_LOG(pdhist, "  starting 'free' loop",0,0,0,0);
    850   pages_freed = uvmexp.pdfreed;	/* so far... */
    851 
    852   /*
    853    * do loop #1!   alternate starting queue between swap and object based
    854    * on the low bit of uvmexp.pdrevs (which we bump by one each call).
    855    */
    856 
    857   got_it = FALSE;
    858   if ((uvmexp.pdrevs & 1) != 0 && uvmexp.nswapdev != 0)
    859     got_it = uvmpd_scan_inactive(&uvm.page_inactive_swp);
    860   if (!got_it)
    861     got_it = uvmpd_scan_inactive(&uvm.page_inactive_obj);
    862   if (!got_it && (uvmexp.pdrevs & 1) == 0 && uvmexp.nswapdev != 0)
    863     (void) uvmpd_scan_inactive(&uvm.page_inactive_swp);
    864 
    865   /*
    866    * we have done the scan to get free pages.   now we work on meeting
    867    * our inactive target.
    868    */
    869 
    870   page_shortage = uvmexp.inactarg - uvmexp.inactive;
    871   pages_freed = uvmexp.pdfreed - pages_freed; /* # pages freed in loop */
    872   if (page_shortage <= 0 && pages_freed == 0)
    873     page_shortage = 1;
    874 
    875   UVMHIST_LOG(pdhist, "  second loop: page_shortage=%d", page_shortage,0,0,0);
    876   for (p = uvm.page_active.tqh_first ;
    877        p != NULL && page_shortage > 0 ; p = nextpg) {
    878 
    879     nextpg = p->pageq.tqe_next;
    880     if (p->flags & PG_BUSY)
    881       continue;			/* quick check before trying to lock */
    882 
    883     /*
    884      * lock owner
    885      */
    886     /* is page anon owned or ownerless? */
    887     if ((p->pqflags & PQ_ANON) || p->uobject == NULL) {
    888 
    889 #ifdef DIAGNOSTIC
    890       if (p->uanon == NULL)
    891         panic("pagedaemon: page with no anon or object detected - loop 2");
    892 #endif
    893 
    894       if (!simple_lock_try(&p->uanon->an_lock))
    895         continue;
    896 
    897       /* take over the page? */
    898       if ((p->pqflags & PQ_ANON) == 0) {
    899 
    900 #ifdef DIAGNOSTIC
    901         if (p->loan_count < 1)
    902           panic("pagedaemon: non-loaned ownerless page detected - loop 2");
    903 #endif
    904 
    905         p->loan_count--;
    906         p->pqflags |= PQ_ANON;
    907       }
    908 
    909     } else {
    910 
    911       if (!simple_lock_try(&p->uobject->vmobjlock))
    912         continue;
    913 
    914     }
    915 
    916     if ((p->flags & PG_BUSY) == 0) {
    917       pmap_page_protect(PMAP_PGARG(p), VM_PROT_NONE);
    918       /* no need to check wire_count as pg is "active" */
    919       uvm_pagedeactivate(p);
    920       uvmexp.pddeact++;
    921       page_shortage--;
    922     }
    923 
    924     if (p->pqflags & PQ_ANON)
    925       simple_unlock(&p->uanon->an_lock);
    926     else
    927       simple_unlock(&p->uobject->vmobjlock);
    928   }
    929 
    930   /*
    931    * done scan
    932    */
    933 }
    934