9 people like it.

PacMan

Single level retro game playable inside TryFsharp using the cursor keys.

PacMan game

  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: 
415: 
416: 
417: 
418: 
419: 
420: 
421: 
422: 
423: 
424: 
425: 
426: 
427: 
428: 
429: 
430: 
431: 
432: 
433: 
434: 
type Game(scene:IScene, input:IInput) =
    let createText text = scene.CreateText(text)
    let toBitmap color lines = scene.CreateBitmap(color,lines)
    let toImage (bitmap:IBitmap) = bitmap.CreateContent()
    let load s =
        let w,h,lines = Images.nameToValue |> Seq.find (fst >> (=) s) |> snd
        scene.CreateBitmap(w,h,lines).CreateContent()
    let add item = scene.Contents.Add(item)
    let remove item = scene.Contents.Remove(item)
    let contains item = scene.Contents.Contains(item)
    let set (element:IContent) (x,y) = element.Move(x - 16 |> float, y + 8 |> float)
    let maze = "
##/------------7/------------7##
##|............|!............|##
##|./__7./___7.|!./___7./__7.|##
##|o|  !.|   !.|!.|   !.|  !o|##
##|.L--J.L---J.LJ.L---J.L--J.|##
##|..........................|##
##|./__7./7./______7./7./__7.|##
##|.L--J.|!.L--7/--J.|!.L--J.|##
##|......|!....|!....|!......|##
##L____7.|L__7 |! /__J!./____J##
#######!.|/--J LJ L--7!.|#######
#######!.|!          |!.|#######
#######!.|! /__==__7 |!.|#######
-------J.LJ |      ! LJ.L-------
########.   | **** !   .########
_______7./7 |      ! /7./_______
#######!.|! L______J |!.|#######
#######!.|!          |!.|#######
#######!.|! /______7 |!.|#######
##/----J.LJ L--7/--J LJ.L----7##
##|............|!............|##
##|./__7./___7.|!./___7./__7.|##
##|.L-7!.L---J.LJ.L---J.|/-J.|##
##|o..|!.......<>.......|!..o|##
##L_7.|!./7./______7./7.|!./_J##
##/-J.LJ.|!.L--7/--J.|!.LJ.L-7##
##|......|!....|!....|!......|##
##|./____JL__7.|!./__JL____7.|##
##|.L--------J.LJ.L--------J.|##
##|..........................|##
##L--------------------------J##"

    let tops = [
        0b00000000, 0b00000000, 0b00000000
        0b00000000, 0b00000000, 0b00000000
        0b00000000, 0b00000000, 0b00000000
        0b00000000, 0b00000000, 0b00000000
        0b00000011, 0b11111111, 0b11000000
        0b00000100, 0b00000000, 0b00100000
        0b00001000, 0b00000000, 0b00010000
        0b00001000, 0b00000000, 0b00010000]
    let mids = [
        0b00001000, 0b00000000, 0b00010000
        0b00001000, 0b00000000, 0b00010000
        0b00001000, 0b00000000, 0b00010000
        0b00001000, 0b00000000, 0b00010000
        0b00001000, 0b00000000, 0b00010000
        0b00001000, 0b00000000, 0b00010000
        0b00001000, 0b00000000, 0b00010000
        0b00001000, 0b00000000, 0b00010000]
    let bots = [
        0b00001000, 0b00000000, 0b00010000
        0b00001000, 0b00000000, 0b00010000
        0b00000100, 0b00000000, 0b00100000
        0b00000011, 0b11111111, 0b11000000
        0b00000000, 0b00000000, 0b00000000
        0b00000000, 0b00000000, 0b00000000
        0b00000000, 0b00000000, 0b00000000
        0b00000000, 0b00000000, 0b00000000]
    let door' = [
        0b00000000
        0b00000000
        0b00000000
        0b00000000
        0b11111111
        0b00000000
        0b00000000
        0b00000000]
    let pill' = [
        0b00000000
        0b00000000
        0b00000000
        0b00011000
        0b00011000
        0b00000000
        0b00000000
        0b00000000]
    let power' = [
        0b00000000
        0b00011000
        0b00111100
        0b01111110
        0b01111110
        0b00111100
        0b00011000
        0b00000000]

    let fromTriple xs = 
        let convert = toBitmap Paint.Blue
        List.foldBack (fun (l,m,r) (ls,ms,rs) -> l::ls, m::ms, r::rs) xs ([],[],[])
        |> fun (l,m,r) -> convert l, convert m, convert r

    let tl, top, tr         = fromTriple tops
    let left, blank, right  = fromTriple mids
    let bl, bottom, br      = fromTriple bots
    let door = toBitmap Paint.White door'
    let pill = toBitmap Paint.Yellow pill'
    let power = toBitmap Paint.Yellow power'

    let toTile c =
        match c with
        | '=' -> door
        | '_' -> top
        | '|' -> left
        | '!' -> right
        | '/' -> tl
        | '7' -> tr
        | 'L' -> bl
        | 'J' -> br
        | '-' -> bottom
        | '.' -> pill
        | 'o' -> power
        | _ -> blank

    let isWall = function
        | '_' | '|' | '!' | '/' | '7' | 'L' | 'J' | '-' | '*' -> true
        | _ -> false

    let isEdible = function '.' | 'o' -> true | _ -> false
    let mutable totalDots = 0
    let walls = scene.AddLayer()
    let lines = maze.Split('\n')
    let tiles =
        lines |> Array.mapi (fun y line ->
            line.ToCharArray() |> Array.mapi (fun x item ->
                let tile = toTile item |> toImage
                set tile (x * 8, y * 8)
                if isEdible item then totalDots <- totalDots + 1
                if isWall item 
                then walls.Contents.Add tile |> ignore
                else scene.Contents.Add tile |> ignore
                tile
            )
        )
    let route_home =
        let numbers =
            lines |> Array.map (fun line ->
                line.ToCharArray() 
                |> Array.map (fun c -> if isWall c then System.Int32.MaxValue else -1)
            )
        let canFill (x,y) =
            y>=0 && y < numbers.Length &&
            x>=0 && x < numbers.[y].Length &&
            numbers.[y].[x] = -1
        let fill n (x,y) = numbers.[y].[x] <- n
        flood canFill fill (16,16)
        numbers

    let tileAt x y =
        if x < 0 || x > 30 then ' '
        else lines.[y].[x]

    let isWallAt (x,y) = tileAt x y |> isWall
    let p = load "p"
    let pu = load "pu1", load "pu2"
    let pd = load "pd1", load "pd2"
    let pl = load "pl1", load "pl2"
    let pr = load "pr1", load "pr2"
    
    let mutable finished = false
    let mutable lives = [for _ in 1..9 -> load "pl1"]
    do  lives |> List.iteri (fun i life -> add life; set life (16+16*i,32*8))
    do  lives <- lives |> List.rev
    let decLives () =
        lives <-
            match lives with
            | [] -> 
                let text = createText "GAME OVER"
                set text (12*8, 15*8)
                add text
                finished <- true
                []
            | x::xs -> 
                remove x
                xs

    let ghost_starts = 
        [
            "red", (16, 12), (1,0)
            "cyan", (14, 16), (1,0)
            "pink" , (16, 14), (0,-1)
            "orange" , (18, 16), (-1,0)
        ]
        |> List.map (fun (color,(x,y),v) -> 
            let blue = load "blue"
            let eyes = load "eyeu", load "eyed", load "eyel", load "eyer"
            let body = load (color+"u"), load (color+"d"), load (color+"l"), load (color+"r")
            let _,image,_,_ = body
            { Blue=blue; Eyes=eyes; Body=body; X=x*8-7; Y=y*8-3; V=v; Image=image; IsReturning=false }
        )
    let mutable ghosts = ghost_starts
    do  ghosts |> List.iter (fun ghost -> 
        add ghost.Image
        set ghost.Image (ghost.X,ghost.Y)
        )

    let mutable score = 0
    let mutable bonus = 0
    let mutable bonuses = []
    let x = ref (16 * 8 - 7)
    let y = ref (24 * 8 - 3)
    let v = ref (0,0)
    let pacman = ref p
    do  add !pacman
    do  set !pacman (!x,!y)
    let mutable powerCount = 0

    let noWall (x,y) (ex,ey) =
        let bx, by = int ((x+6+ex)/8), int ((y+6+ey)/8)
        isWallAt (bx,by) |> not

    let fillValue (x,y) (ex,ey) =
        let bx, by = int ((x+6+ex)/8), int ((y+6+ey)/8)
        route_home.[by].[bx]

    let verticallyAligned (x,y) = x % 8 = 5
    let horizontallyAligned (x,y) = y % 8 = 5

    let canGoUp (x,y) = verticallyAligned (x,y) && noWall (x,y) (0,-4)
    let canGoDown (x,y) = verticallyAligned (x,y) && noWall (x,y) (0,5)
    let canGoLeft (x,y) = horizontallyAligned (x,y) && noWall (x,y) (-4,0)
    let canGoRight (x,y) = horizontallyAligned (x,y) && noWall (x,y) (5,0)

    let fillUp (x,y) = fillValue (x,y) (0,-4)
    let fillDown (x,y) = fillValue (x,y) (0,5)
    let fillLeft (x,y) = fillValue (x,y) (-4,0)
    let fillRight (x,y) = fillValue (x,y) (5,0)

    let go (x,y) (dx,dy) =
        let x = 
            if   dx = -1 && x = 0 then 30 * 8
            elif dx = 1  && x = 30 *8 then 0
            else x
        x + dx, y + dy

    let newGhosts () =
        ghosts |> List.map (fun ghost ->
            let x, y = ghost.X, ghost.Y
            let dx, dy = ghost.V
            let u,d,l,r = ghost.Body
            let u',d',l',r' = ghost.Eyes
            let face, eye, canMove =
                match dx, dy with
                | 0,-1 -> u, u', canGoUp (x,y)
                | 0, 1 -> d, d', canGoDown (x,y)
                | -1,0 -> l, l', canGoLeft (x,y)
                | 1, 0 -> r, r', canGoRight (x,y)
                | _, _ -> invalidOp ""
            let isBackwards (a,b) =
                (a <> 0 && a = -dx) || (b <> 0 && b = -dy)
            let directions = 
                [
                if canGoUp (x,y) then yield (0,-1), fillUp (x,y)
                if canGoDown (x,y) then yield (0,1), fillDown (x,y)
                if canGoLeft (x,y) then yield (-1,0), fillLeft (x,y)
                if canGoRight(x,y) then yield (1,0), fillRight (x,y)
                ]
            let directions =
                if ghost.IsReturning then
                    directions
                    |> Seq.sortBy snd
                    |> Seq.map fst
                else
                    directions
                    |> Seq.map fst
                    |> Seq.unsort
                    |> Seq.sortBy isBackwards
            let dx, dy = directions |> Seq.head
            let x,y = go (x,y) (dx,dy)
            let returning =
                if ghost.IsReturning && 0 = (fillValue (x,y) (0,0))
                then false
                else ghost.IsReturning
            remove ghost.Image
            let face = 
                if ghost.IsReturning then eye
                else
                    if powerCount > 0 then ghost.Blue else face
            add face
            set face (x,y)
            { ghost with X = x; Y = y; V = (dx,dy); Image = face; IsReturning = returning }
        )

    let mutable ghostCounter = 0

    let updateGhosts () = 
        let modulus = if powerCount > 0 then 4 else 16
        if ghostCounter % modulus <> 0 then
            ghosts <- newGhosts ()
        ghostCounter <- ghostCounter + 1

    let updatePacman () =
        let inputs = 
            [
            if input.IsUp then yield canGoUp (!x,!y), (0,-1), pu
            if input.IsDown then yield canGoDown (!x,!y), (0,1), pd
            if input.IsLeft  then yield canGoLeft (!x,!y), (-1,0), pl
            if input.IsRight then yield canGoRight (!x,!y), (1,0), pr
            ] 
        let move ((dx,dy),(d1,d2)) =
            let x', y' = go (!x,!y) (dx,dy)
            x := x'; y := y'; v := (dx,dy)
            remove !pacman
            let d = if (!x/6 + !y/6) % 2 = 0 then d1 else d2
            add d
            pacman := d
        let availableDirections =
            inputs
            |> List.filter (fun (can,_,_) -> can)
            |> List.map (fun (_,v,f) -> v,f)
            |> Seq.sortBy (fun (v',_) -> v' = !v)
        if Seq.length availableDirections > 0 then
            availableDirections |> Seq.head |> move
        else
            let goForward =
                match !v with
                | 0,-1 -> canGoUp(!x,!y), pu
                | 0,1  -> canGoDown(!x,!y), pd
                | -1,0 -> canGoLeft(!x,!y), pl
                | 1, 0 -> canGoRight(!x,!y), pr
                | 0, 0 -> false, pu
                | _ -> invalidOp ""
            if fst goForward && inputs.Length > 0 then
                (!v, snd goForward) |> move 
        let tx, ty = int ((!x+6)/8), int ((!y+6)/8)
        if tileAt tx ty = '.' then
            if contains (tiles.[ty].[tx]) then
                score <- score + 10
                remove (tiles.[ty].[tx])
                totalDots <- totalDots - 1
        if tileAt tx ty = 'o' then
            if contains (tiles.[ty].[tx]) then
                score <- score + 50
                powerCount <- 500
                bonus <- 0
                totalDots <- totalDots - 1
            remove (tiles.[ty].[tx])
        set !pacman (!x,!y)
        if totalDots = 0 then
            let text = createText "LEVEL COMPLETED"
            set text (7*8, 15*8)
            add text
            finished <- true


    let updatePower () =
        if powerCount > 0 then
            if (powerCount/5) % 2 = 1 then walls.SetOpacity(0.5)
            else walls.SetOpacity(1.0)
        else walls.SetOpacity(1.0)
        powerCount <- powerCount - 1

    let mutable flashCount = 0

    let updateFlash () =
        if flashCount > 0 then
            if ((flashCount / 5) % 2) = 1 then (!pacman).SetOpacity(0.5)
            else (!pacman).SetOpacity(1.0)
            flashCount <- flashCount - 1
        else (!pacman).SetOpacity(1.0)

    let touchGhosts () =
        let px, py = !x, !y
        ghosts |> List.filter (fun ghost ->
            let x,y = ghost.X, ghost.Y
            ((px >= x && px < x + 13) ||
             (x < px + 13 && x >= px)) &&
            ((py >= y && py < y + 13) ||
             (y < py + 13 && y >= py))
        )

    let handleTouching () =
        let touching = touchGhosts()
        if touching.Length > 0 then
            if powerCount > 0 
            then ghosts <- ghosts |> List.mapi (fun i ghost ->
                if not ghost.IsReturning && 
                   touching |> List.exists ((=) ghost)
                then
                    score <- score + (pown 2 bonus) * 200 
                    let b = load ([|"200";"400";"800";"1600"|]).[bonus]
                    set b (ghost.X, ghost.Y)
                    add b
                    bonuses <- (100,b) :: bonuses
                    bonus <- min 3 (bonus + 1)
                    { ghost with IsReturning = true; }
                else ghost
            )
            else
                if flashCount = 0 then
                    decLives()
                    flashCount <- 30

    let updateBonuses () =
        let removals,remainders =
            bonuses 
            |> List.map (fun (count,x) -> count-1,x)
            |> List.partition (fst >> (=) 0)
        bonuses <- remainders
        removals |> List.iter (fun (_,x) -> remove x)

    let p1 = createText("SCORE")
    do  p1.Move(0.0,0.0); scene.Contents.Add(p1)
    let s1 = createText("")
    do  s1.Move(5.0*8.0,0.0); scene.Contents.Add(s1)

    let updateScore () =
        s1.SetText(sprintf "%7d" score)

    do  updateScore ()

    let update () =
        updatePacman ()
        updateGhosts ()
        handleTouching ()
        updateFlash ()
        updatePower ()
        updateBonuses ()
        updateScore ()

    member this.Update () = 
        if not finished then update ()
Multiple items
type Game =
  new : scene:IScene * input:IInput -> Game
  member Update : unit -> unit

Full name: Script.Game

--------------------
new : scene:IScene * input:IInput -> Game
val scene : IScene
type IScene =
  interface
    abstract member AddLayer : unit -> ILayer
    abstract member CreateBitmap : Paint * seq<int> -> IBitmap
    abstract member CreateBitmap : int * int * int [] [] -> IBitmap
    abstract member CreateText : string -> ITextContent
    abstract member LoadBitmap : string -> IBitmap
    abstract member Contents : IContents
  end

Full name: Script.IScene
val input : IInput
type IInput =
  interface
    abstract member IsDown : bool
    abstract member IsLeft : bool
    abstract member IsRight : bool
    abstract member IsUp : bool
  end

Full name: Script.IInput
val createText : (string -> ITextContent)
val text : string
abstract member IScene.CreateText : string -> ITextContent
val toBitmap : (Paint -> seq<int> -> IBitmap)
val color : Paint
val lines : seq<int>
abstract member IScene.CreateBitmap : Paint * seq<int> -> IBitmap
abstract member IScene.CreateBitmap : int * int * int [] [] -> IBitmap
val toImage : (IBitmap -> IContent)
val bitmap : IBitmap
type IBitmap =
  interface
    abstract member CreateContent : unit -> IContent
  end

Full name: Script.IBitmap
abstract member IBitmap.CreateContent : unit -> IContent
val load : (string -> IContent)
val s : string
val w : int
val h : int
val lines : int [] []
module Images

from Script
val nameToValue : (string * (int * int * int [] [])) list

Full name: Script.Images.nameToValue
Multiple items
module Seq

from Script

--------------------
module Seq

from Microsoft.FSharp.Collections
val find : predicate:('T -> bool) -> source:seq<'T> -> 'T

Full name: Microsoft.FSharp.Collections.Seq.find
val fst : tuple:('T1 * 'T2) -> 'T1

Full name: Microsoft.FSharp.Core.Operators.fst
val snd : tuple:('T1 * 'T2) -> 'T2

Full name: Microsoft.FSharp.Core.Operators.snd
val add : (IContent -> unit)
val item : IContent
property IScene.Contents: IContents
abstract member IContents.Add : IContent -> unit
val remove : (IContent -> unit)
abstract member IContents.Remove : IContent -> unit
val contains : (IContent -> bool)
abstract member IContents.Contains : IContent -> bool
val set : (IContent -> int * int -> unit)
val element : IContent
type IContent =
  interface
    abstract member Move : float * float -> unit
    abstract member SetOpacity : float -> unit
    abstract member Control : obj
  end

Full name: Script.IContent
val x : int
val y : int
abstract member IContent.Move : float * float -> unit
Multiple items
val float : value:'T -> float (requires member op_Explicit)

Full name: Microsoft.FSharp.Core.Operators.float

--------------------
type float = System.Double

Full name: Microsoft.FSharp.Core.float

--------------------
type float<'Measure> = float

Full name: Microsoft.FSharp.Core.float<_>
val maze : string
val tops : (int * int * int) list
val mids : (int * int * int) list
val bots : (int * int * int) list
val door' : int list
val pill' : int list
val power' : int list
val fromTriple : ((int * int * int) list -> IBitmap * IBitmap * IBitmap)
val xs : (int * int * int) list
val convert : (int list -> IBitmap)
Multiple items
type Paint =
  new : aarrggbb:int -> Paint
  member Color : int
  static member Black : Paint
  static member Blue : Paint
  static member Transparent : Paint
  static member White : Paint
  static member Yellow : Paint

Full name: Script.Paint

--------------------
new : aarrggbb:int -> Paint
property Paint.Blue: Paint
Multiple items
module List

from Microsoft.FSharp.Collections

--------------------
type List<'T> =
  | ( [] )
  | ( :: ) of Head: 'T * Tail: 'T list
  interface IEnumerable
  interface IEnumerable<'T>
  member Head : 'T
  member IsEmpty : bool
  member Item : index:int -> 'T with get
  member Length : int
  member Tail : 'T list
  static member Cons : head:'T * tail:'T list -> 'T list
  static member Empty : 'T list

Full name: Microsoft.FSharp.Collections.List<_>
val foldBack : folder:('T -> 'State -> 'State) -> list:'T list -> state:'State -> 'State

Full name: Microsoft.FSharp.Collections.List.foldBack
val l : int
val m : int
val r : int
val ls : int list
val ms : int list
val rs : int list
val l : int list
val m : int list
val r : int list
val tl : IBitmap
val top : IBitmap
val tr : IBitmap
val left : IBitmap
val blank : IBitmap
val right : IBitmap
val bl : IBitmap
val bottom : IBitmap
val br : IBitmap
val door : IBitmap
property Paint.White: Paint
val pill : IBitmap
property Paint.Yellow: Paint
val power : IBitmap
val toTile : (char -> IBitmap)
val c : char
val isWall : (char -> bool)
val isEdible : (char -> bool)
val mutable totalDots : int
val walls : ILayer
abstract member IScene.AddLayer : unit -> ILayer
val lines : string []
System.String.Split([<System.ParamArray>] separator: char []) : string []
System.String.Split(separator: string [], options: System.StringSplitOptions) : string []
System.String.Split(separator: char [], options: System.StringSplitOptions) : string []
System.String.Split(separator: char [], count: int) : string []
System.String.Split(separator: string [], count: int, options: System.StringSplitOptions) : string []
System.String.Split(separator: char [], count: int, options: System.StringSplitOptions) : string []
val tiles : IContent [] []
module Array

from Microsoft.FSharp.Collections
val mapi : mapping:(int -> 'T -> 'U) -> array:'T [] -> 'U []

Full name: Microsoft.FSharp.Collections.Array.mapi
val line : string
System.String.ToCharArray() : char []
System.String.ToCharArray(startIndex: int, length: int) : char []
val item : char
val tile : IContent
property ILayer.Contents: IContents
val ignore : value:'T -> unit

Full name: Microsoft.FSharp.Core.Operators.ignore
val route_home : int [] []
val numbers : int [] []
val map : mapping:('T -> 'U) -> array:'T [] -> 'U []

Full name: Microsoft.FSharp.Collections.Array.map
namespace System
type Int32 =
  struct
    member CompareTo : value:obj -> int + 1 overload
    member Equals : obj:obj -> bool + 1 overload
    member GetHashCode : unit -> int
    member GetTypeCode : unit -> TypeCode
    member ToString : unit -> string + 3 overloads
    static val MaxValue : int
    static val MinValue : int
    static member Parse : s:string -> int + 3 overloads
    static member TryParse : s:string * result:int -> bool + 1 overload
  end

Full name: System.Int32
field int.MaxValue = 2147483647
val canFill : (int * int -> bool)
property System.Array.Length: int
val fill : (int -> int * int -> unit)
val n : int
val flood : canFill:(int * int -> bool) -> fill:(int -> int * int -> unit) -> x:int * y:int -> unit

Full name: Script.Algorithm.flood
val tileAt : (int -> int -> char)
val isWallAt : (int * int -> bool)
val p : IContent
val pu : IContent * IContent
val pd : IContent * IContent
val pl : IContent * IContent
val pr : IContent * IContent
val mutable finished : bool
val mutable lives : IContent list
val iteri : action:(int -> 'T -> unit) -> list:'T list -> unit

Full name: Microsoft.FSharp.Collections.List.iteri
val i : int
val life : IContent
val rev : list:'T list -> 'T list

Full name: Microsoft.FSharp.Collections.List.rev
val decLives : (unit -> unit)
val text : ITextContent
val x : IContent
val xs : IContent list
val ghost_starts : Ghost list
val map : mapping:('T -> 'U) -> list:'T list -> 'U list

Full name: Microsoft.FSharp.Collections.List.map
val color : string
val v : int * int
val blue : IContent
val eyes : IContent * IContent * IContent * IContent
val body : IContent * IContent * IContent * IContent
val image : IContent
Ghost.X: int
Ghost.Y: int
Ghost.V: int * int
val mutable ghosts : Ghost list
val iter : action:('T -> unit) -> list:'T list -> unit

Full name: Microsoft.FSharp.Collections.List.iter
val ghost : Ghost
Ghost.Image: IContent
val mutable score : int
val mutable bonus : int
val mutable bonuses : (int * IContent) list
val x : int ref
Multiple items
val ref : value:'T -> 'T ref

Full name: Microsoft.FSharp.Core.Operators.ref

--------------------
type 'T ref = Ref<'T>

Full name: Microsoft.FSharp.Core.ref<_>
val y : int ref
val v : (int * int) ref
val pacman : IContent ref
val mutable powerCount : int
val noWall : (int * int -> int * int -> bool)
val ex : int
val ey : int
val bx : int
val by : int
Multiple items
val int : value:'T -> int (requires member op_Explicit)

Full name: Microsoft.FSharp.Core.Operators.int

--------------------
type int = int32

Full name: Microsoft.FSharp.Core.int

--------------------
type int<'Measure> = int

Full name: Microsoft.FSharp.Core.int<_>
val not : value:bool -> bool

Full name: Microsoft.FSharp.Core.Operators.not
val fillValue : (int * int -> int * int -> int)
val verticallyAligned : (int * 'a -> bool)
val y : 'a
val horizontallyAligned : ('a * int -> bool)
val x : 'a
val canGoUp : (int * int -> bool)
val canGoDown : (int * int -> bool)
val canGoLeft : (int * int -> bool)
val canGoRight : (int * int -> bool)
val fillUp : (int * int -> int)
val fillDown : (int * int -> int)
val fillLeft : (int * int -> int)
val fillRight : (int * int -> int)
val go : (int * int -> int * int -> int * int)
val dx : int
val dy : int
val newGhosts : (unit -> Ghost list)
val u : IContent
val d : IContent
val l : IContent
val r : IContent
Ghost.Body: IContent * IContent * IContent * IContent
val u' : IContent
val d' : IContent
val l' : IContent
val r' : IContent
Ghost.Eyes: IContent * IContent * IContent * IContent
val face : IContent
val eye : IContent
val canMove : bool
val invalidOp : message:string -> 'T

Full name: Microsoft.FSharp.Core.Operators.invalidOp
val isBackwards : (int * int -> bool)
val a : int
val b : int
val directions : ((int * int) * int) list
val directions : seq<int * int>
Ghost.IsReturning: bool
Multiple items
val sortBy : f:('a -> 'b) -> xs:System.Collections.Generic.IEnumerable<'a> -> seq<'a>

Full name: Script.Seq.sortBy

--------------------
val sortBy : projection:('T -> 'Key) -> source:seq<'T> -> seq<'T> (requires comparison)

Full name: Microsoft.FSharp.Collections.Seq.sortBy
val map : mapping:('T -> 'U) -> source:seq<'T> -> seq<'U>

Full name: Microsoft.FSharp.Collections.Seq.map
val unsort : xs:seq<'a> -> seq<'a>

Full name: Script.Seq.unsort
val head : source:seq<'T> -> 'T

Full name: Microsoft.FSharp.Collections.Seq.head
val returning : bool
Ghost.Blue: IContent
val mutable ghostCounter : int
val updateGhosts : (unit -> unit)
val modulus : int
val updatePacman : (unit -> unit)
val inputs : (bool * (int * int) * (IContent * IContent)) list
property IInput.IsUp: bool
property IInput.IsDown: bool
property IInput.IsLeft: bool
property IInput.IsRight: bool
val move : ((int * int) * (IContent * IContent) -> unit)
val d1 : IContent
val d2 : IContent
val x' : int
val y' : int
val availableDirections : seq<(int * int) * (IContent * IContent)>
val filter : predicate:('T -> bool) -> list:'T list -> 'T list

Full name: Microsoft.FSharp.Collections.List.filter
val can : bool
val f : IContent * IContent
val v' : int * int
val length : source:seq<'T> -> int

Full name: Microsoft.FSharp.Collections.Seq.length
val goForward : bool * (IContent * IContent)
property List.Length: int
val tx : int
val ty : int
val updatePower : (unit -> unit)
abstract member IContent.SetOpacity : float -> unit
val mutable flashCount : int
val updateFlash : (unit -> unit)
val touchGhosts : (unit -> Ghost list)
val px : int
val py : int
val handleTouching : (unit -> unit)
val touching : Ghost list
val mapi : mapping:(int -> 'T -> 'U) -> list:'T list -> 'U list

Full name: Microsoft.FSharp.Collections.List.mapi
val exists : predicate:('T -> bool) -> list:'T list -> bool

Full name: Microsoft.FSharp.Collections.List.exists
val pown : x:'T -> n:int -> 'T (requires member get_One and member ( * ) and member ( / ))

Full name: Microsoft.FSharp.Core.Operators.pown
val b : IContent
val min : e1:'T -> e2:'T -> 'T (requires comparison)

Full name: Microsoft.FSharp.Core.Operators.min
val updateBonuses : (unit -> unit)
val removals : (int * IContent) list
val remainders : (int * IContent) list
val count : int
val partition : predicate:('T -> bool) -> list:'T list -> 'T list * 'T list

Full name: Microsoft.FSharp.Collections.List.partition
val p1 : ITextContent
val s1 : ITextContent
val updateScore : (unit -> unit)
abstract member ITextContent.SetText : string -> unit
val sprintf : format:Printf.StringFormat<'T> -> 'T

Full name: Microsoft.FSharp.Core.ExtraTopLevelOperators.sprintf
val update : (unit -> unit)
val this : Game
member Game.Update : unit -> unit

Full name: Script.Game.Update

More information

Link:http://fssnip.net/cZ
Posted:11 years ago
Author:Phillip Trelford
Tags: game , silverlight