## Desiderata ## ================ ## This notebooks aims to: ## * Organize itself around a minimalistic, functional core (like µKanren) ## * Explore basic "notions" about nice syntax; ## Many fanciful notions about syntax abound, ## but most will saved for later notebooks. ## Methodology ## ================= ## The beginning will be rough and sloppy; any elegance will have to be accumulated later, or maybe never. ## This is a notebook, not a library --> Prior definitions will be redefined as we go along, ## so keep your eyes peeled! ## First, some odds and ends. ## For now we would like to stick to core Julia datatypes, but, aesthetically, var? = vector? is a bitter pill. ## So instead we'll use our own type just this once. ## it's best to wrap Julia types in a module, otherwise it is very difficult to change your mind module LilKanren immutable type Var id::Int end end LK = LilKanren ## Package dependencies: Lazy, Patchwork, Gadly, Dataframes ## these should be available on juliabox by default, but you may need to add ## them to your local julia install ## Also, in case you are new to Julia, the following snippets may be helpful x = LK.Var(0) y = LK.Var(0) @show x==y @show x===y #egal ## multiple dispatch gotSomeVars(x,y) = "nope" ## base case gotSomeVars(x::LK.Var,y::LK.Var) = "yes" gotSomeVars(x::LK.Var,y) = "kinda" gotSomeVars(x,y::LK.Var) = gotSomeVars(y,x) @show gotSomeVars(x,y) @show gotSomeVars(1,y) @show gotSomeVars(1,2) ## julia allows for convenient destructuring of tuples z = (1,(2,3)) (α,(β,γ)) = z ## n.b. little schemer's, (a,b) means (a . b), and there is ## no primacy of lists in Julia ## infix ∷ = gotSomeVars @show x ∷ y @show 1 ∷ y @show 1 ∷ 2 nothing ## to suppress notebook output ## On with the show, being relatively faithful from now on... ## ## A translation of µKanren ## --------------------------- ## ## Heaven ## ====== unify(u, v, s) = begin (u,s) = walk(u,s) # dramatic foreshadowing (v,s) = walk(v,s) unifyTerms(u,v,s) end ## Earth ## ===== ## The Church ## ---------- unifyTerms(u,v,s) = begin sn = unifyLeft(u,v,s) sn == nothing ? unifyLeft(v,u,s) : sn ## symmetrize end ## s -- the substitution store const empty_store = () ext_s(x,v,s) = ((x,v),s) ## st -- a (bindings,count) based state const empty_state = (empty_store,1) ## when in Rome (Julia is one's based...) const ∅ = empty_state const ∞ = empty_state ## it's a "glass half full" sort of thing... ## ∅ constraints ≡ ∞ possibilities ## The State ## -------------- unifyLeft(u,v,s) = u===v ? s : nothing # base case unifyLeft(u::LK.Var,v,s) = u==v ? s : ext_s(u,v,s) unifyLeft(u::(Any,Any),v::(Any,Any),s) = begin (uhead,utail) = u (vhead,vtail) = v s = unify(uhead,vhead,s) s == nothing ? s : unify(utail,vtail,s) end ## The Bourgeoisie ## ---------------- walk(u,s) = (u,s) ## base case walk(u::LK.Var,s) = begin (found,value) = lookup(u,s) found == :✔︎ ? walk(value,s) : (u,s) end ## And finally, Joe The Plumber ## ---------------------------- ## a pedantic man's assp <-- n.b. non-schemer's, this does not mean something dirty lookup(x,s::()) = (:✘,nothing) ## base case lookup(x,s) = begin (head,rest) = s (key,value) = head x == key ? (:✔︎, value) : lookup(x,rest) end second(x) = x[2] ## Purgatory -- aka Algebra ## ======================== equivalent(u,v) = begin (st) -> begin (s,count) = st s = unify(u,v,s) s == nothing ? mzero : unit((s,count)) end end const ≡ = equivalent fresh(f::Function) = begin (st) -> begin (bindings,count) = st var = LK.Var(count) goal = f(var) st = (bindings,count+1) goal(st) end end disj(g1,g2) = (st) -> mplus(g1(st), g2(st)) conj(g1,g2) = (st) -> bind(g1(st), g2) const ∨ = disj const ⫷ = disj #this is the picture in my head -- a weave const ∧ = conj const ⫸ = conj #this is the picture in my head -- a braid ## The Bowels of Hell... ## (or Heaven -- the whole thing is just a big snake eating its tail) ## ================================================================== const mzero = () unit(st) = (st,mzero) mplus(strand1::(),strand2) = strand2 mplus(strand1::Function,strand2) = () -> mplus(strand2,strand1()) ## A true braid mplus(strand1::(Any,Any),strand2) = (first(strand1),mplus(second(strand1),strand2)) bind(strand::(),g) = mzero bind(strand::Function,g) = () -> bind(strand(),g) bind(strand::(Any,Any),g) = mplus(g(first(strand)), bind(second(strand),g)) ## A true weave nothing ## Ok -- Let's take this puppy out for a spin... using Lazy: @>>, @> ## this should work on juliabox, if not, Pkg.add("Lazy") vars = [LK.Var(i) for i=1:10] ## order up some vars ## create a scratch store for testing s = @>> empty_store begin ext_s(vars[1], 2) ext_s(vars[2], vars[1]) ext_s(vars[1], 3) #shadows prior binding ext_s(vars[3], (:❆,vars[2])) end @show s println() @show lookup("not even close", s) @show lookup(vars[1], s) @show lookup(vars[2], s) @show lookup(vars[3], s) @show lookup(vars[4], s) nothing @show first(walk(vars[1],s)) @show first(walk(vars[2],s)) @show first(walk(vars[3],s)) @show first(walk(vars[4],s)) @show first(walk("not even close",s)) @show first(walk((:✯,vars[4]),s)) nothing ## Look, Ma! I can fly! @show unify((:❆,vars[4]), vars[3],s) # for clarity println() @show first(unify((:❆,vars[4]), vars[3],s)) ## That's nice, sweetie. nothing ## Reassured by Mother's kind encouragement, we try climbing higher... fresh() do q q ≡ :♣ end (∞) ## and little higher... ⫸( fresh() do a a ≡ :♣ end, fresh() do b ⫷( b ≡ :♠, :♡ ≡ b ) end )(∞) ## (I think) I like the above notation, but you may prefer: ∞ |> fresh(a-> a ≡ :♣) ∧ fresh(b-> (b ≡ :♠) ∨ (:♡ ≡ b) ) ## ♪ Pump up the jam ♪ ## let's make a few new toys fresh(f::Function,n) = begin (sc) -> begin (bindings,count) = sc vars = [LK.Var(i) for i=count:count+(n-1)] goal = f(vars...) sc = (bindings,count+n) goal(sc) end end fresh(3) do a,b,c ⫸( (c,:♠) ≡ (((a,b),:♣),:♠), ⫸( (:♡,a) ≡ b, a ≡ :♣ )) end (∞) fresh(3) do a,b,c ⫸( (c,:♠) ≡ (((a,b), :♣), :♣), # <-- look here ⫸( (:♡,a) ≡ b, a ≡ :♣ )) end (∞) fresh(3) do a,b,c ⫸( (c, a) ≡ (((a,b),:♣),:♣), # <-- still look here ⫸( (:♡,a) ≡ b, a ≡ :♣ )) end (∞) ## variadic paradise is one of our many goals ## but for now this will suffice ## n.b. This is not a nanny-state. BYOη⁻¹ ## (but see below for some gov't approved options) conj(goals...) = begin # avoiding an infinite loop relies # on our prior definition and # Julia's dispatch being smart re: splats conj(goals[1], conj(goals[2:end]...)) end disj(goals...) = begin disj(goals[1], disj(goals[2:end]...)) end conj(goal) = goal disj(goal) = goal fresh(3) do a,b,c ⫸( (c,:♣) ≡ (((a,b),:♣), a), (:♡,a) ≡ b, a ≡ :♣ ) end (∞) ## Our first relation! ## ## And one of our first serious transgressions: ## the output will come first --> my cult is organized around prophecies of variadic paradise ## But the cute ᵒ at the end isn't going anywhere! selectᵒ(o,tuple,which) = begin fresh(2) do a, b ⫸( (a,b) ≡ tuple, ⫷( ⫸(which ≡ :№𝟙,o ≡ a), ⫸(which ≡ :№𝟚,o ≡ b), ) ) end end fresh(2) do q,r ⫸( selectᵒ(q, (:♡, :♣), r), ⫷( r ≡ :№𝟙, r ≡ :№𝟚) ) end (∞) ## Onto divergence ## But first, in Julia, we require the following helper list() = () list(x...) = (x[1], list(x[2:end]...)) const ❀ = list # There should be more flowers in CS @show ❀(1,2,3,4) nothing ## grant ourselves a magic power # DRAGON, SLEEP! η⁻¹(goal) = :((st) -> () -> $(esc(goal))(st)) macro ☽(goal) ## It's a half moon η⁻¹(goal) end macro zzz(op, goals...) Expr(:call, op, [η⁻¹(goal) for goal in goals]...) end nothing ## What's all this poppycock about a 'nanny-state'? ## ## (now is probably a good time for a reminder that you are very likely ## reading the blustery rantings of a lunatic....) # ## First a little perspective is in order: ## The first part of the μKanren paper introduces a functional kernel for search, ## the second part demonstrates how to reintroduce features available ## in miniKanren, a relational system designed to be syntactically similar to Scheme ## (presumably for didactic and aesthetic reasons) ## ## conj+ and disj+ are offered to partially recover miniKanren's semantics, wrapping ## zzz's around the kit and kaboodle. ## ## We set out on a different path. Neither shall we prophylactically 'zzz', ## only to find that our fear of dragons makes us prisoners of our own design, ## nor shall we become crotchety misers, hoarding our power for a journey that ## we never take. ## ## Rather, we shall look to travel the Silk Roads, where a clever knack for the ## apropos application of pixie dust may just lead us to marvels beyond belief. ## ## So now we have two quests: Variadic Paradise and the Pixie Dust Legerdemain @show macroexpand(:( @☽(:❀ ≡ :♣) )) @show macroexpand(:( @zzz ∨ (:❀ ≡ :♣) (:❀ ≡ :♣) )) nothing ## Now that we have the power to put the dragon to sleep, we need a way to wake it up. ## But not this way! allIn(x)=x ## as they say in Texas Holdem' allIn(x::Function)=allIn(x()) allIn(x::(Any,Any))= begin (h,t)=x; (h,allIn(t)) end ## lilinjn is not Navajo; but if this notebook were a tapestry, ## 'allIn' would be his "ch’ihónít’i" -- use 'allIn' maybe never ## For now we will content ourselves with the following hand tools: step(x,n=1)=x step(x::Function,n=1) = begin ## In my heart, Julia is a fine Scheme; however, I don't think Jeff B. ## and co. are going to be driving around with TCO vanity plates ## anytime soon... while(typeof(x) <: Function && n > 0) x = x() n -= 1 end x end ## Oishii onigiri for the long journey ahead stepInTime(x,nanos)=x ## ♪ Chim Chimer-ee, Chim Chim Cher-ee ♪ stepInTime(x,nanos) = begin start = Base.time_ns() current = start while(typeof(x) <: Function && current-start < nanos) x = x() current = Base.time_ns() end x end ηs = 1 s = 1_000_000_000 nothing @show step(:♡) myLovely♡Thunks = () -> () -> () -> () -> :☆ @show step(myLovely♡Thunks, 2) ## ♪ gonna make you luv drunk ♪ @show step(myLovely♡Thunks, 10) ## ♪ off my thunks ♪ @show stepInTime(myLovely♡Thunks, 1ηs) @show stepInTime(myLovely♡Thunks, 1s) nothing ## rest your weary eyes, little dragon res = ∞ |> fresh(q-> (q ≡ :♠) ∨ @☽(:♡ ≡ q) ) # since we're so new to this, we'll break down the result manually @show res (res,cont) = res # <-- it's hard to have known you would have needed this in advance @show (res,cont)=step(cont) nothing ## Variadic Sleep res = ∞ |> fresh(q-> @zzz ⫷ (q ≡ :♠) (:♡ ≡ q) (q ≡ :✪) ) ## still practicing tearing down the result @show res @show res=step(res) # a pure thunk arrives this time @show (res,cont)=step(res) @show (res,cont)=step(cont) @show (res,cont)=step(cont) nothing ## Something to ponder... ## Why does it go "thunk,thunk,kebang" ## rather than "thunk, dribble, dribble"? ## Ans: Because it was broken, but hopefully now it is fixed ## (p.s. orginally there were only two clauses) foreverᵒ(o,val) = begin (o ≡ val) ∨ @☽(foreverᵒ(o,val)) end res = ∞ |> fresh(2) do q,r ⫸( foreverᵒ(r, q), r ≡ :✪ ) end ## Uncomment to hear the theme to M*A*S*H ## @show res = allIn(res) ## one last time @show res (res,cont) = res @show (res,cont) = step(cont) @show (res,cont) = step(cont) @show (res,cont) = step(cont) @show (res,cont) = step(cont) @show (res,cont) = step(cont) nothing ## Lead us not into Temptation... ## ## Reification is Lucifer's work. ## ## But at the same time, we are lunatics, not ascetics, ## and so, on this day, we grant ourselves a few guilty pleasures. ## ## (Don't worry -- when time comes around to get down with the underground, ## we plan to get our swerve on) ## First some infrastructure using Patchwork using Patchwork.HTML5 ## hackety-hack ## 'using Patchwork' embeds vital js into the output cell, ## but 'using' is meant to be idempotent in Julia, which causes issues ## when re-evaluating the entire sheet en masse. ## (the re-evaluated cell no longer has the js) ## this hack forces the js embedding regardless (possibly duplicating it) Patchwork.load_js_runtime() ## flex layout wrapper wrapper(e...) = begin d = div(style=[:display => :flex, "flex-wrap"=>:wrap]) for i=1:length(e) d = d << (div(e[i]) & [:style => [:display=>"inline-block", :margin=>"10px"]]) end d end nothing ## A Table for your Store ## (but no reification on which to rest) ## ## Can't you just feel your muscles and joints getting stiff? storeTable(s) = begin function items(s::(),res=Elem[]) return res end function items(s::(Any,Any),res=Elem[]) (b, rest) = s push!(res,binding(b, length(res)+1)) items(rest,res) end function binding(b, index) r = tr(td(var(first(b))), td(value(second(b)))) if index % 2 == 0 r = r & [:className => "alt"] end r end function var(v) s = @sprintf "%s" v span(s) end function value(v) s = @sprintf "%s" v span(s) end div( table( thead(tr(th("Var"),th("Binding"))), tbody(items(s)...))) & [:className => :datagrid] end ## and the cholesterol clogging you arteries? ## Our friend from before: s = @>> empty_store begin ext_s(vars[1], 2) ext_s(vars[2], vars[1]) ext_s(vars[1], 3) #shadows prior binding <- breaking a key invariant (Thanks, Will!) ext_s(vars[3], (:❆,vars[2])) end stable = storeTable(s) display("text/html", wrapper(stable,stable,stable,stable)) # one is never enough ## Forgetting to apply our beeswax prior to entering the neighborhood big box superstore, ## we are lulled into submission by the Sirens of Hock, ## and impulsively purchase a flimsy power tool on the way out... function slurpInTime(goal; # Mary Poppins does not approve maxResults = 10, maxSteps=1_000_000, maxTime=5s, suppressOutput=false, elideAfter=20) ## VIP's steps = 0 results = Any[] ## thank you, julia! startBytes = Base.gc_bytes() start = Base.time_ns() startGC = Base.gc_time_ns() thisStart = start thisFirstStep = steps stream = ∞ |> goal done = () -> (steps >= maxSteps || length(results) >= maxResults || current - start >= maxTime || stream == ()) steps += 1 current = Base.time_ns() while(!done()) if (typeof(stream) <: Function) stream = stream() steps += 1 else if (typeof(stream) <: (Any,Any)) push!(results, (first(stream),steps-thisFirstStep,current-thisStart)) thisFirstStep = steps thisStart = current stream = second(stream) end end current = Base.time_ns() end endGC = Base.gc_time_ns() current = Base.time_ns() endBytes = Base.gc_bytes() ######################################## ##utils function niceTime(nanos;morePrecision=false) f = morePrecision ? format2 : format if nanos < 1_000.0 "$(f(nanos)) ηs" elseif nanos < 1_000_000.0 "$(format2(nanos/1_000.0)) μs" elseif nanos < 1_000_000_000.0 "$(format2(nanos/1_000_000.0)) ms" else "$(format2(nanos/1_000_000_000.0)) s" end end function niceBytes(bytes;morePrecision=false) f = morePrecision ? format2 : format if bytes < 2^10 "$(f(bytes)) bytes" elseif bytes < 2^20 "$(format2(bytes/2^10)) KB" elseif bytes < 2^30 "$(format2(bytes/2^20)) MB" else "$(format2(bytes/2^30)) GB" end end function format(x) @sprintf "%.f" x end function format2(x) @sprintf "%.2f" x end function annotateTable(table, nextVar, steps, nanos) info = "Next: $(LK.Var(nextVar)) Steps: $(steps) Time: $(niceTime(nanos))" div(table,div(span(info) & [:style => ["font-size" => "7pt", "font-family" => "Georgia, Times New Roman"]])) end gcTime = endGC-startGC gcBytes = endBytes-startBytes runTime = current-start ######################################## ##display if !suppressOutput tables = [annotateTable(storeTable(s),count,steps, nanos) for ((s,count),steps,nanos) = results[1:min(elideAfter,length(results))]] display("text/html", wrapper(tables...)) summaryString = """ Summary: ============================== Total # of steps: $steps Total # of results: $(length(results)) ($(format2(100.0*length(results)/steps))% Hit rate) Total Time: $(niceTime(runTime)) $(niceTime(runTime/steps,morePrecision=true))/step $(niceTime(runTime/length(results),morePrecision=true))/result Total GC Time: $(niceTime(gcTime)) $(niceTime(gcTime/steps,morePrecision=true))/step $(niceTime(gcTime/length(results),morePrecision=true))/result ($(format2(100.0*gcTime/runTime))%) Total GC Bytes: $(niceBytes(gcBytes)) $(niceBytes(gcBytes/steps,morePrecision=true))/step $(niceBytes(gcBytes/length(results),morePrecision=true))/result """ if elideAfter < length(results) summaryString = "\n$(length(results)-elideAfter) Results Suppressed\n$summaryString" end display("text/html",div(pre(summaryString))) end results end ## re-define for good measure ηs = 1 s = 1_000_000_000 minutes = 60*s nothing goal = fresh(3) do a,b,c ⫸( (c,:♣) ≡ (((a,b),:♣), a), (:♡,a) ≡ b, a ≡ :♣ ) end slurpInTime(goal) nothing goal = fresh(2) do q,r ⫸( foreverᵒ(r, q), r ≡ :✪ ) end slurpInTime(goal) nothing goal = fresh(5) do q,a,b,c,decoy ⫸( ⫷(foreverᵒ(:♘,a),foreverᵒ(:♗,a)), ⫷(foreverᵒ(:♣,b),foreverᵒ(:♠,b)), ⫷(foreverᵒ(:☯,c),foreverᵒ(:☮,c)), ⫷(foreverᵒ(:♀,decoy),foreverᵒ(:♂,decoy)), ❀(a,b,c) ≡ q ) end slurpInTime(goal,maxResults=20) nothing ## Go big, or go home big = slurpInTime(goal,maxResults=1_000_000,maxSteps=10_000_000,maxTime=2minutes) nothing ## what happens if we zzz goal = fresh(5) do q,a,b,c,decoy @zzz(⫸, @zzz(⫷,foreverᵒ(:♘,a),foreverᵒ(:♗,a)), @zzz(⫷,foreverᵒ(:♣,b),foreverᵒ(:♠,b)), @zzz(⫷,foreverᵒ(:☯,c),foreverᵒ(:☮,c)), @zzz(⫷,foreverᵒ(:♀,decoy),foreverᵒ(:♂,decoy)), ❀(a,b,c) ≡ q ) end bigSnooze = slurpInTime(goal,maxResults=1_000_000,maxSteps=10_000_000,maxTime=5minutes) nothing ## The artful part of this notebook has quickly come to an end. ## ## Unable to contain our curiousity, ## we crunch a few extra numbers. ## as of Julia 0.3.4, bringing these guys in can take several seconds using Gadfly using DataArrays, DataFrames ## also the first plot can be slow nothing ## extract data ## takes several seconds.... why? score(char) = begin if char==:♘ || char==:♣ || char==:☯ || char==:♀ 1 else 0 end end vars = [LK.Var(i) for i=1:5] steps = [steps for ((s,count),steps,nanos)=big] nanos = [int(nanos) for ((s,count),steps,nanos)=big] ##not sure why I need to cast scores = [score(first(walk(vars[i],s))) for ((s,count),steps,nanos)=big, i=2:5] nothing steps = float(steps) nanos = float(nanos) scores = float(scores) nothing ## How fairly does the search sample correct answers? mean(scores,1) ## What about when we use zzz? scoresZZZ = [score(first(walk(vars[i],s))) for ((s,count),steps,nanos)=bigSnooze, i=2:5] nothing mean(scoresZZZ,1) ## Can you explain this result? -- is there a bug lurking in the bowels of hell? ## We might as well draw a few pictures ## Because Chrome+Gadfly is not that big graphpoints = 1_000 samplepoints = linspace(1,length(big), graphpoints) sample(data) = begin index = 1 result = zeros(graphpoints,3) for i=1:graphpoints mn = Inf mx = -Inf mean = 0 count = 0 while (index <= samplepoints[i]) d = data[index] mn = min(d,mn) mx = max(d,mx) mean += d count += 1 index += 1 end mean = mean/count result[i,:] = [mn,mean,mx] end result end nothing nanosamp = sample(nanos) nanoDF = DataFrame() nanoDF[:points] = samplepoints nanoDF[:min] = nanosamp[:,1] nanoDF[:mean] = nanosamp[:,2] nanoDF[:max] = nanosamp[:,3] plot(nanoDF,x=:points,y=:mean,Geom.line,Guide.title("Avg. Time/Result (nanos)")) ## Looks like we're generating quite some garbage... hitrate = 100.0*(1:length(big))./cumsum(steps) hitDF = DataFrame() hitDF[:points] = samplepoints[2:end] ## skip first point hitDF[:hitrate] = sample(hitrate)[2:end,2] ## skip first point plot(hitDF,x=:points,y=:hitrate,Geom.line,Guide.title("Hit Rate(%)"),Scale.x_log10) ## Some final thoughts: ## ## Did you look closely at all of the output? ## What about the statistics, can you explain them? ## What did you find suprising? ## ## Perhaps you liked the syntax? ## But you _do_ believe in pixie dust, don't you? ## ## That's a wrap -- See you next time for another twisted journey ################################################################# ################################################################# ## Hackety-Hack ## Some temporary work-arounds related to unresolved IJulia/juliabox warts ## Most likely, this cell nevers needs to be evaluated again ## It works by injecting mutant DNA (html) into the sheet which is then saved for posterity ##nuke the red box around unicode chars display("text/html", """ """ ) ## table styling ## generated with http://tablestyler.com/# css = ".datagrid table { border-collapse: collapse; text-align: left; width: 100%; margin:0px auto; } .datagrid {margin:0px auto; font: normal 12px/150% Georgia, Times New Roman, Times, serif; background: #fff; overflow: hidden; border: 1px solid #8C8C8C; }.datagrid table td, .datagrid table th { padding: 4px 10px; }.datagrid table thead th {background:-webkit-gradient( linear, left top, left bottom, color-stop(0.05, #8C8C8C), color-stop(1, #7D7D7D) );background:-moz-linear-gradient( center top, #8C8C8C 5%, #7D7D7D 100% );filter:progid:DXImageTransform.Microsoft.gradient(startColorstr='#8C8C8C', endColorstr='#7D7D7D');background-color:#8C8C8C; color:#FFFFFF; font-size: 13px; font-weight: bold; border-left: 1px solid #A3A3A3; } .datagrid table thead th:first-child { border: none; }.datagrid table tbody td { color: #1A1E21; border-left: 1px solid #DBDBDB;font-size: 12px;font-weight: normal; }.datagrid table tbody .alt td { background: #EBEBEB; color: #1A1E21; }.datagrid table tbody td:first-child { border-left: none; }.datagrid table tbody tr:last-child td { border-bottom: none; }.datagrid table tfoot td div { border-top: 1px solid #8C8C8C;background: #EBEBEB;} .datagrid table tfoot td { padding: 0; font-size: 12px } .datagrid table tfoot td div{ padding: 2px; }.datagrid table tfoot td ul { margin: 0; padding:0; list-style: none; text-align: right; }.datagrid table tfoot li { display: inline; }.datagrid table tfoot li a { text-decoration: none; display: inline-block; padding: 2px 8px; margin: 1px;color: #F5F5F5;border: 1px solid #8C8C8C;-webkit-border-radius: 3px; -moz-border-radius: 3px; border-radius: 3px; background:-webkit-gradient( linear, left top, left bottom, color-stop(0.05, #8C8C8C), color-stop(1, #7D7D7D) );background:-moz-linear-gradient( center top, #8C8C8C 5%, #7D7D7D 100% );filter:progid:DXImageTransform.Microsoft.gradient(startColorstr='#8C8C8C', endColorstr='#7D7D7D');background-color:#8C8C8C; }.datagrid table tfoot ul.active, .datagrid table tfoot ul a:hover { text-decoration: none;border-color: #7D7D7D; color: #F5F5F5; background: none; background-color:#8C8C8C;}div.dhtmlx_window_active, div.dhx_modal_cover_dv { position: fixed !important; }" display("text/html", "")