Visionaire Studio 4.2.5 Released

  • #20, by tristan-kangMonday, 30. November 2015, 20:52 9 years ago
    Just so you know if you notice something's not right but you didn't make back up old shader script.


    --
    -- Shader Toolkit Hue, Saturation, Luminance, Blur, Noise, Camera Control, Bloom, Random Effects
    -- (c) 2014 Simon Scheckel, Visionaire Studio Engine - with edits by AFRLme
    -- Version 0.8.9 [updated 29/09/2014 for 4.1, added some save functionality 9/10, bugfix version 24/10/2014]
    --
    -- Matrix functions from https://github.com/davidm/lua-matrix/blob/master/lua/matrix.lua
    -- Developers: Michael Lutz (chillcode) - original author David Manura http://lua-users.org/wiki/DavidManura
    --
    -- Usage:
    --
    -- all factors like zoom, scale are normally 1 to have no change
    -- delay in ms
    -- hue in 0-1 (0 = red, 0.5 = cyan, 1 = red again)
    --
    -- easing functions: Back, Bounce, Circ, Cubic, Elastic, Linear, None, Quad, Quint, Sine, all In/Out/InOut
    -- examples: easeBackOut, easeLinearIn, easeElasticInOut etc
    -- More information about that: http://easings.net
    --
    -- shaderZoomCharacter(name, c_scale, delay, easing)
    -- shaderZoomObject(object, c_scale, delay, easing)
    -- shaderFollowCharacter(name, c_scale, delay)
    -- shaderStopFollow()
    -- shaderViewport(zoom, x, y, rotation, delay, easing) rotation in 0-2Pi (full turn)
    -- shaderPan(offset, delay, easing, axis)
    -- shaderRotate(degree, delay, easing) -- degree values 0 to 359 (automatically converts value to Pi)
    -- shaderZoom(zoom, delay, easing)
    -- on: 1 = on, 0 = off
    --
    -- shaderNoise(on, strength, delay) -- strength * noise + color, so strength 0 white
    -- shaderBlur(radius, delay)
    -- shaderSaturation(factor, delay)
    -- shaderLightness(offset, delay)
    -- shaderContrast(contrast, delay)
    -- shaderHue(target, delay)
    -- shaderColorize(hue, strength, delay)
    --
    -- shaderActivate()
    -- shaderDeactivate()
    --
    -- shaderGlow(on, radius, exposure)
    -- shaderAddEffect(name)
    -- shaderRemoveEffect(name)
    -- shaderEffectParam(shader, name, value)
    -- shaderLamp(index, type, position, targetpos, falloff, ambient, diffuse, diffusefactor, exponent, cutoff)
    --
    -- Effects at the time:
    --[[
    warp1
    tv1
    ripple1
    ripple2
    ascii
    edgeglow
    chroma
    ripple3
    warp2
    ripple4
    pearls
    highlight
    fourbit
    tv2
    tv3
    tv4
    --
    -- Read no further if the word matrix multiplication frightens you
    --]]

    local matrix = {_TYPE='module', _NAME='matrix', _VERSION='0.2.11.20120416'}
    local matrix_meta = { }

    function matrix:new( rows, columns, value )
    if type( rows ) == "table" then
    if type(rows[1]) ~= "table" then
    return setmetatable( {{rows[1]},{rows[2]},{rows[3]}},matrix_meta )
    end
    return setmetatable( rows,matrix_meta )
    end
    local mtx = {}
    local value = value or 0
    if columns == "I" then
    for i = 1,rows do
    mtx = {}
    for j = 1,rows do
    if i == j then
    mtx[j] = 1
    else
    mtx[j] = 0
    end
    end
    end
    else
    for i = 1,rows do
    mtx = {}
    for j = 1,columns do
    mtx[j] = value
    end
    end
    end
    return setmetatable( mtx,matrix_meta )
    end

    function matrix.mul( m1, m2 )
    local mtx = {}
    for i = 1,#m1 do
    mtx = {}
    for j = 1,#m2[1] do
    local num = m1[1] * m2[1][j]
    for n = 2,#m1[1] do
    num = num + m1[n] * m2[n][j]
    end
    mtx[j] = num
    end
    end
    return setmetatable( mtx, matrix_meta )
    end

    function matrix.tofloat( m1 )
    local mtx = {}
    local pos = 1
    for i = 1,#m1 do
    for j = 1,#m1[1] do
    mtx[pos] = m1[j]
    pos=pos+1
    end
    end
    return mtx
    end

    matrix_meta.__mul = matrix.mul
    matrix_meta.__index = {tofloat = matrix.tofloat}

    setmetatable( matrix, { __call = function( ... ) return matrix.new( ... ) end } )

    -- End of matrix functions


    function string.fromhex(str)
    return (str:gsub('..', function (cc)
    return string.char(tonumber(cc, 16))
    end))
    end

    function string.tohex(str)
    return (str:gsub('.', function (c)
    return string.format('%02X', string.byte(c))
    end))
    end

    --
    -- Source: http://lua-users.org/wiki/DataDumper

    --[[ DataDumper.lua
    Copyright (c) 2007 Olivetti-Engineering SA

    Permission is hereby granted, free of charge, to any person
    obtaining a copy of this software and associated documentation
    files (the "Software"), to deal in the Software without
    restriction, including without limitation the rights to use,
    copy, modify, merge, publish, distribute, sublicense, and/or sell
    copies of the Software, and to permit persons to whom the
    Software is furnished to do so, subject to the following
    conditions:

    The above copyright notice and this permission notice shall be
    included in all copies or substantial portions of the Software.

    THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND,
    EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES
    OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND
    NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT
    HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY,
    WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING
    FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR
    OTHER DEALINGS IN THE SOFTWARE.
    ]]

    local dumplua_closure = [[
    local closures = {}
    local function closure(t)
    closures[#closures+1] = t
    t[1] = assert(loadstring(t[1]))
    return t[1]
    end

    for _,t in pairs(closures) do
    for i = 2,#t do
    debug.setupvalue(t[1], i-1, t)
    end
    end
    ]]

    local lua_reserved_keywords = {
    'and', 'break', 'do', 'else', 'elseif', 'end', 'false', 'for',
    'function', 'if', 'in', 'local', 'nil', 'not', 'or', 'repeat',
    'return', 'then', 'true', 'until', 'while' }

    local function keys(t)
    local res = {}
    local oktypes = { stringstring = true, numbernumber = true }
    local function cmpfct(a,b)
    if oktypes[type(a)..type(b)] then
    return a < b
    else
    return type(a) < type(b)
    end
    end
    for k in pairs(t) do
    res[#res+1] = k
    end
    table.sort(res, cmpfct)
    return res
    end

    local c_functions = {}
    for _,lib in pairs{'_G', 'string', 'table', 'math',
    'io', 'os', 'coroutine', 'package', 'debug'} do
    local t = _G[lib] or {}
    lib = lib .. "."
    if lib == "_G." then lib = "" end
    for k,v in pairs(t) do
    if type(v) == 'function' and not pcall(string.dump, v) then
    c_functions[v] = lib..k
    end
    end
    end

    function DataDumper(value, varname, fastmode, ident)
    local defined, dumplua = {}
    -- Local variables for speed optimization
    local string_format, type, string_dump, string_rep =
    string.format, type, string.dump, string.rep
    local tostring, pairs, table_concat =
    tostring, pairs, table.concat
    local keycache, strvalcache, out, closure_cnt = {}, {}, {}, 0
    setmetatable(strvalcache, {__index = function(t,value)
    local res = string_format('%q', value)
    t[value] = res
    return res
    end})
    local fcts = {
    string = function(value) return strvalcache[value] end,
    number = function(value) return value end,
    boolean = function(value) return tostring(value) end,
    ['nil'] = function(value) return 'nil' end,
    ['function'] = function(value)
    return string_format("loadstring(%q)", string_dump(value))
    end,
    userdata = function(value)
    if value.getId ~= nil then
    return value:getId().id .. " " .. value:getName()
    else
    return "userdata"
    end
    end,
    thread = function() error("Cannot dump threads") end,
    }
    local function test_defined(value, path)
    if defined[value] then
    if path:match("^getmetatable.*%)$") then
    out[#out+1] = string_format("s%s, %s)\n", path:sub(2,-2), defined[value])
    else
    out[#out+1] = path .. " = " .. defined[value] .. "\n"
    end
    return true
    end
    defined[value] = path
    end
    local function make_key(t, key)
    local s
    if type(key) == 'string' and key:match('^[_%a][_%w]*$') then
    s = key .. "="
    else
    s = "[" .. dumplua(key, 0) .. "]="
    end
    t[key] = s
    return s
    end
    for _,k in ipairs(lua_reserved_keywords) do
    keycache[k] = '["'..k..'"] = '
    end
    if fastmode then
    fcts.table = function (value)
    -- Table value
    local numidx = 1
    out[#out+1] = "{"
    for key,val in pairs(value) do
    if key == numidx then
    numidx = numidx + 1
    else
    out[#out+1] = keycache[key]
    end
    local str = dumplua(val)
    out[#out+1] = str..","
    end
    if string.sub(out[#out], -1) == "," then
    out[#out] = string.sub(out[#out], 1, -2);
    end
    out[#out+1] = "}"
    return ""
    end
    else
    fcts.table = function (value, ident, path)
    if test_defined(value, path) then return "nil" end
    -- Table value
    local sep, str, numidx, totallen = " ", {}, 1, 0
    local meta, metastr = (debug or getfenv()).getmetatable(value)
    if meta then
    ident = ident + 1
    metastr = dumplua(meta, ident, "getmetatable("..path..")")
    totallen = totallen + #metastr + 16
    end
    for _,key in pairs(keys(value)) do
    local val = value[key]
    local s = ""
    local subpath = path
    if key == numidx then
    subpath = subpath .. "[" .. numidx .. "]"
    numidx = numidx + 1
    else
    s = keycache[key]
    if not s:match "^%[" then subpath = subpath .. "." end
    subpath = subpath .. s:gsub("%s*=%s*$","")
    end
    s = s .. dumplua(val, ident+1, subpath)
    str[#str+1] = s
    totallen = totallen + #s + 2
    end
    if totallen > 80 then
    sep = "\n" .. string_rep(" ", ident+1)
    end
    str = "{"..sep..table_concat(str, ","..sep).." "..sep:sub(1,-3).."}"
    if meta then
    sep = sep:sub(1,-3)
    return "setmetatable("..sep..str..","..sep..metastr..sep:sub(1,-3)..")"
    end
    return str
    end
    fcts['function'] = function (value, ident, path)
    if test_defined(value, path) then return "nil" end
    if c_functions[value] then
    return c_functions[value]
    elseif debug == nil or debug.getupvalue(value, 1) == nil then
    return string_format("loadstring(%q)", string_dump(value))
    end
    closure_cnt = closure_cnt + 1
    local res = {string.dump(value)}
    for i = 1,math.huge do
    local name, v = debug.getupvalue(value,i)
    if name == nil then break end
    res[i+1] = v
    end
    return "closure " .. dumplua(res, ident, "closures["..closure_cnt.."]")
    end
    end
    function dumplua(value, ident, path)
    return fcts[type(value)](value, ident, path)
    end
    if varname == nil then
    varname = "return "
    elseif varname:match("^[%a_][%w_]*$") then
    varname = varname .. " = "
    end
    if fastmode then
    setmetatable(keycache, {__index = make_key })
    out[1] = varname
    table.insert(out,dumplua(value, 0))
    return table.concat(out)
    else
    setmetatable(keycache, {__index = make_key })
    local items = {}
    for i=1,10 do items = '' end
    items[3] = dumplua(value, ident or 0, "t")
    if closure_cnt > 0 then
    items[1], items[6] = dumplua_closure:match("(.*\n)\n(.*)")
    out[#out+1] = ""
    end
    if #out > 0 then
    items[2], items[4] = "local t = ", "\n"
    items[5] = table.concat(out)
    items[7] = varname .. "t"
    else
    items[2] = varname
    end
    return table.concat(items)
    end
    end

    -- End of DataDumper
    --
    -- Shader Metatable

    shaders_compiled = {}
    local shader_meta = {}
    local shader = {}
    function shader:new (this, id, fsh, vsh)
    local shader = {}
    shader.num = shaderCompile(fsh,vsh)
    shader.id = id
    if shaders_compiled[id] == nil then
    shaders_compiled[id] = {}
    end
    return setmetatable( shader, shader_meta )
    end
    shader_meta.__call = function(this)
    return this.num
    end
    shader_meta.__newindex = function(this, field, value)
    shaders_compiled[this.id][field] = value
    shaderUniform(this.num, field, value)
    end
    setmetatable( shader, { __call = function( ... ) return shader:new( ... ) end } )
    function tween(val,newval,delay,ease)
    startTween(val, _G[val], newval, delay,ease)
    end


    basic_vsh=[[#ifdef GL_ES
    precision lowp float;
    precision lowp int;
    #endif
    varying vec2 texcoord;
    uniform mat4 mvp_mat;
    attribute vec2 position;
    attribute vec2 uv;
    uniform int pass;
    void main ()
    {
    gl_Position = mvp_mat * vec4(position.x,position.y,0.0,1.0);
    texcoord = uv;
    }]]

    ----------------------------
    basic_fsh=[[#ifdef GL_ES
    precision highp float;
    precision lowp int;
    #endif
    #define iChannel0 composite
    #define iResolution resolution
    #define iGlobalTime time
    #define iMouse mouse
    uniform float time;
    uniform sampler2D composite;
    uniform int pass;
    uniform vec2 mouse;
    uniform vec2 resolution;
    varying vec2 texcoord;]]

    ----------------------------
    shaders = {_temporary_=0, c_scene = game.CurrentScene,
    ---------------------------
    glownum = shader("glow",[[#ifdef GL_ES
    precision lowp float;
    precision lowp int;
    #endif
    varying vec2 texcoord;
    uniform mat4 mvp_mat;
    attribute vec2 position;
    attribute vec2 uv;
    uniform int pass;
    uniform int firstpass;
    uniform int lastpass;
    uniform float down;

    mat4 scale4 = mat4(1.0/down,0,0,0,
    0,1.0/down,0,0,
    0,0,1,0,
    0,0,0,1);
    mat3 scale = mat3(1,0,0, 0,1,0, 0,0,1);
    void main ()
    {
    if(pass==lastpass)
    gl_Position = mvp_mat * vec4(position.x,position.y,0.0,1.0);
    else
    gl_Position = mvp_mat * (scale4 * vec4(position.x,position.y,0.0,1.0));
    if(pass > firstpass)
    scale=mat3(1.0/down,0,0,0,1.0/down,0,0,1.0-1.0/down,1);
    texcoord = (scale*vec3(uv,1.0)).xy;
    }]], [[#ifdef GL_ES
    precision highp float;
    precision lowp int;
    #endif
    uniform sampler2D composite;
    uniform int pass;
    uniform float exposure;
    varying vec2 texcoord;
    uniform vec2 weights;
    uniform int firstpass;
    uniform int lastpass;
    uniform vec2 resolution;

    void identity() {
    vec4 col = exposure*texture2D(composite, texcoord.st);
    col.a=1.0;
    gl_FragColor = col;
    }

    void blurFast(){
    vec4 sum = vec4(0.0);
    float blurSize=1.0/resolution.x*(5.0-float(pass-firstpass+1));
    sum += texture2D(composite, vec2(texcoord.x - blurSize, texcoord.y - blurSize)) * weights[0];
    sum += texture2D(composite, vec2(texcoord.x - blurSize, texcoord.y + blurSize)) * weights[0];
    sum += texture2D(composite, vec2(texcoord.x, texcoord.y)) * weights[1];
    sum += texture2D(composite, vec2(texcoord.x + blurSize, texcoord.y - blurSize)) * weights[0];
    sum += texture2D(composite, vec2(texcoord.x + blurSize, texcoord.y + blurSize)) * weights[0];
    gl_FragColor = sum;
    }

    void main()
    {
    if(pass==lastpass)
    identity();
    else if(pass==firstpass)
    gl_FragColor = 2.0*max(vec4(0.0),texture2D(composite, texcoord).rgba-0.5);
    else
    blurFast();
    }]]),
    ----------------------------
    bnum = shader("blur",[[#ifdef GL_ES
    precision lowp float;
    precision lowp int;
    #endif
    varying vec2 texcoord;
    uniform mat4 mvp_mat;
    attribute vec2 position;
    attribute vec2 uv;
    uniform int pass;
    uniform int firstpass;
    uniform int lastpass;
    uniform float down;

    mat4 scale4 = mat4(1.0/down,0,0,0,
    0,1.0/down,0,0,
    0,0,1,0,
    0,0,0,1);
    mat3 scale = mat3(1,0,0, 0,1,0, 0,0,1);
    void main ()
    {
    if(pass==lastpass)
    gl_Position = mvp_mat * vec4(position.x,position.y,0.0,1.0);
    else
    gl_Position = mvp_mat * (scale4 * vec4(position.x,position.y,0.0,1.0));
    if(pass>firstpass)
    scale=mat3(1.0/down,0,0,0,1.0/down,0,0,1.0-1.0/down,1);
    texcoord = (scale*vec3(uv,1.0)).xy;
    }]], [[#ifdef GL_ES
    precision highp float;
    precision lowp int;
    #endif

    uniform sampler2D composite;
    uniform int pass;
    uniform float exposure;
    varying vec2 texcoord;
    uniform vec2 weights;
    uniform int firstpass;
    uniform int lastpass;
    uniform vec2 resolution;

    void identity() {
    vec4 col = exposure*texture2D(composite, texcoord.st);
    col.a=1.0;
    gl_FragColor = col;
    }

    void blurFast(){
    vec4 sum = vec4(0.0);
    float blurSize=1.0/resolution.x*(5.0-float(pass-firstpass));
    sum += texture2D(composite, vec2(texcoord.x - blurSize, texcoord.y - blurSize)) * weights[0];
    sum += texture2D(composite, vec2(texcoord.x - blurSize, texcoord.y + blurSize)) * weights[0];
    sum += texture2D(composite, vec2(texcoord.x, texcoord.y)) * weights[1];
    sum += texture2D(composite, vec2(texcoord.x + blurSize, texcoord.y - blurSize)) * weights[0];
    sum += texture2D(composite, vec2(texcoord.x + blurSize, texcoord.y + blurSize)) * weights[0];
    gl_FragColor = sum;
    }

    void main()
    {
    if(pass==lastpass)
    identity();
    else
    blurFast();
    }]]),
    ----------------------------
    num = shader("num",[[#ifdef GL_ES
    precision lowp float;
    precision lowp int;
    #endif
    varying vec2 texcoord;
    uniform mat4 mvp_mat;
    uniform mat4 cam_mat;
    attribute vec2 position;
    attribute vec2 uv;
    uniform int pass;
    void main ()
    {
    gl_Position = mvp_mat * (cam_mat * vec4(position.x,position.y,0.0,1.0));
    texcoord = uv;
    }]],[[#ifdef GL_ES
    precision highp float;
    precision lowp int;
    #endif

    uniform sampler2D composite;
    uniform int pass;
    uniform int noise;
    uniform float noiseFactor;
    uniform float iTime;
    uniform vec2 weights;
    uniform vec4 shader_coeff;
    varying vec2 texcoord;

    void identity() {
    gl_FragColor = texture2D(composite, texcoord.st);
    }

    float rand(vec2 co){
    return fract(sin(dot(co.xy ,vec2(12.9898,78.233))) * 43758.5453);
    }

    vec3 rgb2hsv(vec3 c)
    {
    vec4 K = vec4(0.0, -1.0 / 3.0, 2.0 / 3.0, -1.0);
    vec4 p = mix(vec4(c.bg, K.wz), vec4(c.gb, K.xy), step(c.b, c.g));
    vec4 q = mix(vec4(p.xyw, c.r), vec4(c.r, p.yzx), step(p.x, c.r));

    float d = q.x - min(q.w, q.y);
    float e = 1.0e-10;
    return vec3(abs(q.z + (q.w - q.y) / (6.0 * d + e)), d / (q.x + e), q.x);
    }

    vec3 hsv2rgb(vec3 c)
    {
    vec4 K = vec4(1.0, 2.0 / 3.0, 1.0 / 3.0, 3.0);
    vec3 p = abs(fract(c.xxx + K.xyz) * 6.0 - K.www);
    return c.z * mix(K.xxx, clamp(p - K.xxx, 0.0, 1.0), c.y);
    }
    void sat()
    {
    vec4 textureColor = texture2D(composite, texcoord.st);

    vec3 fragRGB = textureColor.rgb;
    vec3 fragHSV = rgb2hsv(fragRGB);
    fragHSV.x += shader_coeff[0];
    fragHSV.y *= shader_coeff[1];
    fragHSV.z = (fragHSV.z - 0.5)*shader_coeff[2]+0.5+shader_coeff[3];
    fragRGB = hsv2rgb(fragHSV);
    fragHSV.x = weights[1];
    vec3 fragRGBC = hsv2rgb(fragHSV);
    vec4 color = vec4(mix(fragRGB, fragRGBC, weights[0]), textureColor.w);
    if(noise==1)
    color+= noiseFactor*rand(texcoord.xy+vec2(iTime*2.0,0.0));
    gl_FragColor=color;
    }
    void main()
    {
    sat();
    }]])}

    shader_coeff0=0
    shader_coeff1=1
    shader_coeff2=1
    shader_coeff3=0
    shader_blur=0
    shader_downsize=1
    shader_colorize=0
    shader_color=0
    shader_iTime = 0
    shader_noise=0
    shader_noiseStrength=0.0
    shader_passes=2
    shader_active = true
    shader_glow = 0
    shader_glowradius = 0
    shader_glowexp = 1

    shader_rotate=0.0
    shader_scale = 1.0
    shader_offsetx = 0.0
    shader_offsety = 0.0
    shader_follow = {on=0, name="", c_scale=1, easing = easeQuintOut, delay = 0}

    c_res=game.WindowResolution

    shaders.num.weights = {shader_colorize,shader_color}
    shaders.num.shader_coeff = {shader_coeff0,shader_coeff1,shader_coeff2,shader_coeff3}
    shaders.glownum.resolution = {c_res.x,c_res.y}
    shaders.bnum.resolution = {c_res.x,c_res.y}

    -- * function that stops following specified character & resets camera back to default * --
    function shaderStopFollow(easing)
    shader_follow.on = 0
    shaderViewport(1, 0, 0, 0, shader_follow.delay, easing)
    unregisterEventHandler("mainLoop", "followCharacter")
    end

    -- * function that smoothly follows specified character * --
    function shaderFollowCharacter(name, c_scale, delay, easing)
    if name == "" then name = game.CurrentCharacter:getName() end
    if shader_follow.on == 0 then registerEventHandler("mainLoop", "followCharacter") end
    shader_follow.on = 1
    shader_follow.name = name
    shader_follow.c_scale = c_scale
    shader_follow.delay = delay
    shader_follow.easing = easing
    end

    function shaderZoomCharacter(name, c_scale, delay, easing)
    local c_position={}
    if(name=="")then
    c_position=game.CurrentCharacter.Position
    else
    c_position=Characters[name].Position
    end
    local c_scroll=game.ScrollPosition
    c_position.x=c_position.x-c_scroll.x
    c_position.y=c_position.y-c_scroll.y
    c_position.x=c_position.x-(c_res.x/c_scale/2)
    c_position.y=c_position.y-(c_res.y/c_scale/1.2)
    shaderViewport(c_scale, c_position.x, c_position.y, 0, delay, easing)
    end

    function shaderZoomObject(object, c_scale, delay, easing)
    local c_position=object.Position
    local c_scroll=game.ScrollPosition
    c_position.x=c_position.x-c_scroll.x
    c_position.y=c_position.y-c_scroll.y
    c_position.x=c_position.x-(c_res.x/c_scale/2)
    c_position.y=c_position.y-(c_res.y/c_scale/1.2)
    shaderViewport(c_scale, c_position.x, c_position.y, 0, delay, easing)
    end

    function shaderNoise(strength, delay)
    startTween("shader_noiseStrength", shader_noiseStrength, strength, delay, easeLinearInOut)
    end

    function shaderSaturation(factor, delay)
    startTween("shader_coeff1",shader_coeff1,factor,delay,easeLinearInOut)
    end

    function shaderLightness(offset, delay)
    startTween("shader_coeff3",shader_coeff3,offset,delay,easeLinearInOut)
    end

    function shaderContrast(contrast, delay)
    startTween("shader_coeff2",shader_coeff2,contrast,delay,easeLinearInOut)
    end

    function shaderHue(target, delay)
    startTween("shader_coeff0",shader_coeff0,target,delay,easeLinearInOut)
    end

    function shaderColorize(hue, strength, delay)
    startTween("shader_colorize",shader_colorize,strength,delay,easeLinearIn)
    shader_color=hue
    end

    function shaderViewport(zoom, x, y, rotation, delay, easing)
    startTween("shader_offsetx", shader_offsetx, x, delay,easing)
    startTween("shader_offsety", shader_offsety, y, delay,easing)
    startTween("shader_scale", shader_scale, zoom, delay,easing)
    startTween("shader_rotate", shader_rotate, rotation, delay,easing)
    end

    -- * allows you to pan the camera left or right * --
    function shaderPan(offset, delay, easing, axis)
    if axis then
    startTween("shader_offsety", shader_offsety, offset, delay, easing)
    else
    startTween("shader_offsetx", shader_offsetx, offset, delay, easing)
    end
    end

    -- * allows you to zoom the camera in or out * --
    function shaderZoom(zoom, delay, easing)
    startTween("shader_scale", shader_scale, zoom, delay, easing)
    end

    -- * allows you to rotate the screen (w/ degree instead of pi) * --
    function shaderRotate(degree, delay, easing)
    degree = (degree / 360 * 2 * 3.14) -- convert degree to pi
    startTween("shader_rotate", shader_rotate, degree, delay, easing)
    end

    -- * function that follows character; only active when loop enabled * --
    function followCharacter()
    shaderZoomCharacter(shader_follow.name, shader_follow.c_scale, shader_follow.delay, shader_follow.easing)
    end

    shader_effects = {_temporary_=0,
    warp1={shader=basic_fsh..[[uniform float strength;
    void main(void)
    {
    float t = iGlobalTime * 0.5;
    vec2 uv = texcoord;
    float aspect = iResolution.x / iResolution.y;

    mat3 xform = mat3(cos(sin(t)), sin(t *0.25), 0.0,
    -sin(t * 0.25), cos(cos(t)), 0.0,
    cos(t / 2.0) * 0.2, sin(t) * 0.2, 1.0);

    uv = (xform * vec3(uv, 1.0)).xy * vec2(aspect, 1.0);

    uv.x -= sin(t) + cos(t * 2.0 + cos(uv.x) * sin(t * 2.0) * 2.0) / 2.0;
    uv.y += cos(t + uv.y * 0.5) + sin(uv.y * cos(t)) + sin(cos(t * 0.5) * length(uv));
    uv= mix(texcoord,uv,strength);
    uv = mod(uv, 1.0);

    vec3 color = texture2D(iChannel0, uv).xyz;

    gl_FragColor.xyz = color;
    gl_FragColor.w = 1.0;
    }]] } ,
    light1={shader=basic_fsh..[[
    uniform vec3 lightpos, targetpos;
    uniform int lights_count;
    struct light {
    int type;
    vec3 position;
    vec3 targetpos;
    vec3 lightfalloff;
    vec3 ambient;
    vec3 diffuse;
    float diffusefactor;
    float exponent;
    float cutoff;
    };
    uniform light lights[6];

    #define OFFSET_X 1
    #define OFFSET_Y 1
    #define DEPTH 10.

    vec3 sample(const int x, const int y)
    {
    vec2 uv = (gl_FragCoord.xy + vec2(x, y)) / iResolution.xy;
    return texture2D(iChannel0, uv).xyz;
    }

    float luminance(vec3 c)
    {
    return dot(c, vec3(.2126, .7152, .0722));
    }

    vec3 normal(void)
    {
    float R = abs(luminance(sample( OFFSET_X,0)));
    float L = abs(luminance(sample(-OFFSET_X,0)));
    float D = abs(luminance(sample(0, OFFSET_Y)));
    float U = abs(luminance(sample(0,-OFFSET_Y)));

    float X = (L-R) * .5;
    float Y = (U-D) * .5;

    return normalize(vec3(X, Y, 1. / DEPTH));
    }

    void main(void)
    {
    vec3 n=vec3(0.0,0.0,1.0);
    vec3 diffuse = texture2D(composite, texcoord).rgb;

    float att = 0.0;
    vec3 color=vec3(0.0);

    for(int i = 0; i < lights_count; i++)
    {
    vec3 lightDir = vec3(lights.position-vec3(gl_FragCoord.xy,0.0));
    float NdotL = max(dot(n,normalize(lightDir)),0.0);
    float dist = length(lightDir);

    if (lights.type == 0)
    {
    if (NdotL > 0.0)
    {
    float spotEffect = dot(normalize(lights.targetpos-lights.position), normalize(-lightDir));
    if (spotEffect > lights.cutoff)
    {
    spotEffect = pow(spotEffect,lights.exponent);
    att = spotEffect / (lights.lightfalloff[0] + lights.lightfalloff[1] * dist + lights.lightfalloff[2] * dist * dist);
    color += att * (diffuse * lights.diffuse * (NdotL * lights.diffusefactor) + lights.ambient);
    }
    }
    }
    else
    {
    att = 1.0 / (lights.lightfalloff[0] + lights.lightfalloff[1] * dist + lights.lightfalloff[2] * dist * dist);
    color += att * (diffuse * lights.diffuse * (NdotL * lights.diffusefactor) + lights.ambient);
    //color = vec3(NdotL);
    }
    }

    gl_FragColor = vec4(color, 1.);
    }]]},
    tv1 = {shader = basic_fsh..[[

    #define BLACK_AND_WHITE
    #define LINES_AND_FLICKER
    #define BLOTCHES
    #define GRAIN
    #define FREQUENCY 15.0
    vec2 uv;
    float rand(vec2 co){
    return fract(sin(dot(co.xy ,vec2(12.9898,78.233))) * 43758.5453);
    }
    float rand(float c){
    return rand(vec2(c,1.0));
    }
    float randomLine(float seed)
    {
    float b = 0.01 * rand(seed);
    float a = rand(seed+1.0);
    float c = rand(seed+2.0) - 0.5;
    float mu = rand(seed+3.0);
    float l = 1.0;
    if ( mu > 0.2)
    l = pow( abs(a * uv.x + b * uv.y + c ), 1.0/8.0 );
    else
    l = 2.0 - pow( abs(a * uv.x + b * uv.y + c), 1.0/8.0 );
    return mix(0.5, 1.0, l);
    }
    float randomBlotch(float seed)
    {
    float x = rand(seed);
    float y = rand(seed+1.0);
    float s = 0.01 * rand(seed+2.0);
    vec2 p = vec2(x,y) - uv;
    p.x *= iResolution.x / iResolution.y;
    float a = atan(p.y,p.x);
    float v = 1.0;
    float ss = s*s * (sin(6.2831*a*x)*0.1 + 1.0);
    if ( dot(p,p) < ss ) v = 0.2;
    else
    v = pow(dot(p,p) - ss, 1.0/16.0);
    return mix(0.3 + 0.2 * (1.0 - (s / 0.02)), 1.0, v);
    }
    void main(void)
    {
    uv = gl_FragCoord.xy / iResolution.xy;
    float t = float(int(iGlobalTime * FREQUENCY));
    vec2 suv = uv + 0.002 * vec2( rand(t), rand(t + 23.0));
    vec3 image = texture2D( iChannel0, vec2(suv.x, suv.y) ).xyz;
    #ifdef BLACK_AND_WHITE
    // Pass it to B/W
    float luma = dot( vec3(0.2126, 0.7152, 0.0722), image );
    vec3 oldImage = luma * vec3(0.7, 0.7, 0.7);
    #else
    vec3 oldImage = image;
    #endif
    float vI = 16.0 * (uv.x * (1.0-uv.x) * uv.y * (1.0-uv.y));
    vI *= mix( 0.7, 1.0, rand(t + 0.5));
    vI += 1.0 + 0.4 * rand(t+8.);
    vI *= pow(16.0 * uv.x * (1.0-uv.x) * uv.y * (1.0-uv.y), 0.4);
    #ifdef LINES_AND_FLICKER
    int l = int(8.0 * rand(t+7.0));
    if ( 0 < l ) vI *= randomLine( t+6.0+17.* float(0));
    if ( 1 < l ) vI *= randomLine( t+6.0+17.* float(1));
    if ( 2 < l ) vI *= randomLine( t+6.0+17.* float(2));
    if ( 3 < l ) vI *= randomLine( t+6.0+17.* float(3));
    if ( 4 < l ) vI *= randomLine( t+6.0+17.* float(4));
    if ( 5 < l ) vI *= randomLine( t+6.0+17.* float(5));
    if ( 6 < l ) vI *= randomLine( t+6.0+17.* float(6));
    if ( 7 < l ) vI *= randomLine( t+6.0+17.* float(7));
    #endif
    #ifdef BLOTCHES
    int s = int( max(8.0 * rand(t+18.0) -2.0, 0.0 ));
    if ( 0 < s ) vI *= randomBlotch( t+6.0+19.* float(0));
    if ( 1 < s ) vI *= randomBlotch( t+6.0+19.* float(1));
    if ( 2 < s ) vI *= randomBlotch( t+6.0+19.* float(2));
    if ( 3 < s ) vI *= randomBlotch( t+6.0+19.* float(3));
    if ( 4 < s ) vI *= randomBlotch( t+6.0+19.* float(4));
    if ( 5 < s ) vI *= randomBlotch( t+6.0+19.* float(5));
    #endif
    gl_FragColor.xyz = oldImage * vI;
    #ifdef GRAIN
    gl_FragColor.xyz *= (1.0+(rand(uv+t*.01)-.2)*.15);
    #endif
    }]]},
    ripple1 = {shader = basic_fsh..[[
    // Simple Water shader. (c) Victor Korsun, bitekas@gmail.com; 2012.
    // Attribution-ShareAlike CC License.
    const float PI = 3.1415926535897932;
    const float speed = 0.2;
    const float speed_x = 0.3;
    const float speed_y = 0.3;
    const float emboss = 0.50;
    const float intensity = 2.4;
    const int steps = 8;
    const float frequency = 6.0;
    const int angle = 7; // better when a prime
    const float delta = 60.;
    const float intence = 700.;
    const float reflectionCutOff = 0.012;
    const float reflectionIntence = 200000.;
    float col(vec2 coord)
    {
    float delta_theta = 2.0 * PI / float(angle);
    float col = 0.0;
    float theta = 0.0;
    for (int i = 0; i < steps; i++)
    {
    vec2 adjc = coord;
    theta = delta_theta*float(i);
    adjc.x += cos(theta)*time*speed + time * speed_x;
    adjc.y -= sin(theta)*time*speed - time * speed_y;
    col = col + cos( (adjc.x*cos(theta) - adjc.y*sin(theta))*frequency)*intensity;
    }
    return cos(col);
    }
    void main(void)
    {
    vec2 p = texcoord, c1 = p, c2 = p;
    float cc1 = col(c1);
    c2.x += iResolution.x/delta;
    float dx = emboss*(cc1-col(c2))/delta;
    c2.x = p.x;
    c2.y += iResolution.y/delta;
    float dy = emboss*(cc1-col(c2))/delta;
    c1.x += dx*2.;
    c1.y = (c1.y+dy*2.);
    float alpha = 1.+dot(dx,dy)*intence;
    float ddx = dx - reflectionCutOff;
    float ddy = dy - reflectionCutOff;
    if (ddx > 0. && ddy > 0.)
    alpha = pow(alpha, ddx*ddy*reflectionIntence);
    c1=mod(c1,1.0);
    vec4 col = texture2D(iChannel0,c1)*(alpha);
    gl_FragColor = col;
    }
    ]]},
    ripple2 = {shader = basic_fsh..[[
    float count = 10.0;
    float strength = 0.9;
    void main(void)
    {
    vec2 uv = texcoord;
    float w = (0.5 - (uv.x)) * (iResolution.x / iResolution.y);
    float h = 0.5 - uv.y;
    float distanceFromCenter = sqrt(w * w + h * h);
    float sinArg = distanceFromCenter * count - iGlobalTime * 10.0;
    float slope = cos(sinArg) ;
    vec4 color = texture2D(iChannel0, uv + strength * normalize(vec2(w, h)) * slope * 0.05);
    gl_FragColor = color;
    }
    ]]},
    ascii = {shader = basic_fsh..[[
    // Bitmap to ASCII (not really) fragment shader by movAX13h, September 2013
    // If you change the input channel texture, disable this:
    float character(float n, vec2 p) // some compilers have the word "char" reserved
    {
    p = floor(p*vec2(4.0, -4.0) + 2.5);
    if (clamp(p.x, 0.0, 4.0) == p.x && clamp(p.y, 0.0, 4.0) == p.y)
    {
    if (int(mod(n/exp2(p.x + 5.0*p.y), 2.0)) == 1) return 1.0;
    }
    return 0.0;
    }

    void main()
    {
    vec3 col = texture2D(iChannel0, floor(gl_FragCoord.xy/8.0)*8.0/iResolution.xy).rgb;
    float gray = (col.r + col.g + col.b)/3.0;
    float n = 65536.0; // .
    if (gray > 0.2) n = 65600.0; // :
    if (gray > 0.3) n = 332772.0; // *
    if (gray > 0.4) n = 15255086.0; // o
    if (gray > 0.5) n = 23385164.0; // &
    if (gray > 0.6) n = 15252014.0; // 8
    if (gray > 0.7) n = 13199452.0; // @
    if (gray > 0.8) n = 11512810.0; // #
    vec2 p = mod(gl_FragCoord.xy/4.0, 2.0) - vec2(1.0);
    col = col*character(n, p);
    gl_FragColor = vec4(col, 1.0);
    }
    ]]},
    edgeglow = {shader = basic_fsh..[[
    float d = sin(iGlobalTime * 5.0)*0.5 + 1.5;
    float lookup(vec2 p, float dx, float dy)
    {
    vec2 uv = (p.xy + vec2(dx * d, dy * d)) / iResolution.xy;
    vec4 c = texture2D(iChannel0, uv.xy);
    return 0.2126*c.r + 0.7152*c.g + 0.0722*c.b;
    }
    void main(void)
    {
    vec2 p = gl_FragCoord.xy;
    float gx = 0.0;
    gx += -1.0 * lookup(p, -1.0, -1.0);
    gx += -2.0 * lookup(p, -1.0, 0.0);
    gx += -1.0 * lookup(p, -1.0, 1.0);
    gx += 1.0 * lookup(p, 1.0, -1.0);
    gx += 2.0 * lookup(p, 1.0, 0.0);
    gx += 1.0 * lookup(p, 1.0, 1.0);
    float gy = 0.0;
    gy += -1.0 * lookup(p, -1.0, -1.0);
    gy += -2.0 * lookup(p, 0.0, -1.0);
    gy += -1.0 * lookup(p, 1.0, -1.0);
    gy += 1.0 * lookup(p, -1.0, 1.0);
    gy += 2.0 * lookup(p, 0.0, 1.0);
    gy += 1.0 * lookup(p, 1.0, 1.0);
    float g = gx*gx + gy*gy;
    float g2 = g * (sin(iGlobalTime) / 2.0 + 0.5);
    vec4 col = texture2D(iChannel0, p / iResolution.xy);
    col += vec4(0.0, g, g2, 1.0);
    gl_FragColor = col;
    }
    ]]},
    chroma = {shader = basic_fsh..[[
    // MIT License (MIT)
    // Copyright (c) 2014 Justin Saunders
    void main(void)
    {
    vec2 uv = texcoord;
    float d = length(uv - vec2(0.5,0.5));
    float blur = 0.0;
    blur = (1.0 + sin(iGlobalTime*6.0)) * 0.5;
    blur *= 1.0 + sin(iGlobalTime*16.0) * 0.5;
    blur = pow(blur, 3.0);
    blur *= 0.05;
    blur *= d;
    vec3 col;
    col.r = texture2D( iChannel0, vec2(uv.x+blur,uv.y) ).r;
    col.g = texture2D( iChannel0, uv ).g;
    col.b = texture2D( iChannel0, vec2(uv.x-blur,uv.y) ).b;
    float scanline = sin(uv.y*800.0)*0.04;
    col -= scanline;
    col *= 1.0 - d * 0.5;
    gl_FragColor = vec4(col,1.0);
    }
    ]]},
    ripple3 = {shader = basic_fsh..[[
    void main(void)
    {
    vec2 uv = texcoord;
    uv.x += (sin((uv.y + (iGlobalTime * 0.07)) * 45.0) * 0.009) +
    (sin((uv.y + (iGlobalTime * 0.1)) * 35.0) * 0.005);
    vec4 texColor = texture2D(iChannel0,uv);
    gl_FragColor = texColor;
    }
    ]]},
    warp2 = {shader = basic_fsh..[[
    uniform float strength;
    void main(void)
    {
    vec2 uv = texcoord;
    float y =
    0.7*sin((uv.y + iGlobalTime) * 4.0) * 0.038 +
    0.3*sin((uv.y + iGlobalTime) * 8.0) * 0.010 +
    0.05*sin((uv.y + iGlobalTime) * 40.0) * 0.05;

    float x =
    0.5*sin((uv.y + iGlobalTime) * 5.0) * 0.1 +
    0.2*sin((uv.x + iGlobalTime) * 10.0) * 0.05 +
    0.2*sin((uv.x + iGlobalTime) * 30.0) * 0.02;

    gl_FragColor = texture2D(iChannel0, mix(uv, 0.79*(uv + vec2(y+0.11, x+0.11)), strength));
    }
    ]]},
    ripple4 = {shader = basic_fsh..[[
    void main(void)
    {
    vec2 uv = texcoord;

    float w = (0.5 - (uv.x)) * (iResolution.x / iResolution.y);
    float h = 0.5 - uv.y;
    vec2 dv = vec2(w,h);
    float distanceFromCenter = sqrt(dot(dv,dv));

    float sinArg = distanceFromCenter * 10.0 - iGlobalTime * 10.0;
    float slope = cos(sinArg) ;
    vec4 color = texture2D(iChannel0, uv + normalize(vec2(w, h)) * slope * 0.01);

    gl_FragColor = color;
    }
    ]]},
    pearls={shader=basic_fsh..[[
    // Size of the quad in pixels
    const float size = 7.0;

    // Radius of the circle
    const float radius = size * 0.5 * 0.75;

    void main(void)
    {
    // Current quad in pixels
    vec2 quadPos = floor(gl_FragCoord.xy / size) * size;
    // Normalized quad position
    vec2 quad = quadPos/iResolution.xy;
    // Center of the quad
    vec2 quadCenter = (quadPos + size/2.0);
    // Distance to quad center
    float dist = length(quadCenter - gl_FragCoord.xy);

    vec4 texel = texture2D(iChannel0, quad);
    if (dist > radius)
    {
    gl_FragColor = vec4(0.25);
    }
    else
    {
    gl_FragColor = texel;
    }
    }
    ]]},
    highlight={shader=basic_fsh..[[
    uniform float strength;
    const bool leftToRight = false;
    float slopeSign = (leftToRight ? -1.0 : 1.0);
    float slope1 = 5.0 * slopeSign;
    float slope2 = 7.0 * slopeSign;
    void main(void)
    {


    vec2 uv = gl_FragCoord.xy / iResolution.xy;
    float bright =
    - sin(uv.y * slope1 + uv.x * 30.0+ iGlobalTime *3.10) *.2
    - sin(uv.y * slope2 + uv.x * 37.0 + iGlobalTime *3.10) *.1
    - cos( + uv.x * 2.0 * slopeSign + iGlobalTime *2.10) *.1
    - sin( - uv.x * 5.0 * slopeSign + iGlobalTime * 2.0) * .3;

    float modulate = abs(cos(iGlobalTime*.1) *.5 + sin(iGlobalTime * .7)) *.5;
    bright *= modulate;
    vec4 pix = texture2D(iChannel0,uv);
    pix.rgb += 1.0*clamp(bright / 1.0,0.0,1.0);
    gl_FragColor = pix;
    }
    ]]},
    fourbit={shader=basic_fsh..[[
    // 4BIT COLOR
    // Maps into DawnBringer's 4-bit (16 color) palette http://www.pixeljoint.com/forum/forum_posts.asp?TID=12795
    // Also see the amazing ASCII shadertoy: https://www.shadertoy.com/view/lssGDj
    float hash(vec2 p) { return fract(1e4 * sin(17.0 * p.x + p.y * 0.1) * (0.1 + abs(sin(p.y * 13.0 + p.x)))); }
    float compare(vec3 a, vec3 b) {
    // Increase saturation
    a = max(vec3(0.0), a - min(a.r, min(a.g, a.b)) * 0.25);
    b = max(vec3(0.0), b - min(b.r, min(b.g, b.b)) * 0.25);
    a*=a*a;
    b*=b*b;
    vec3 diff = (a - b);
    return dot(diff, diff);
    }
    void main(void) {
    const float pixelSize = 4.0;
    vec2 c = floor(gl_FragCoord.xy / pixelSize);
    vec2 coord = c * pixelSize;
    vec3 src = texture2D(iChannel0, coord / iResolution.xy).rgb;
    // Track the two best colors
    vec3 dst0 = vec3(0), dst1 = vec3(0);
    float best0 = 1e3, best1 = 1e3;
    # define TRY(R, G, B) { const vec3 tst = vec3(R, G, B); float err = compare(src, tst); if (err < best0) { best1 = best0; dst1 = dst0; best0 = err; dst0 = tst; } }
    TRY(0.078431, 0.047059, 0.109804);
    TRY(0.266667, 0.141176, 0.203922);
    TRY(0.188235, 0.203922, 0.427451);
    TRY(0.305882, 0.290196, 0.305882);
    TRY(0.521569, 0.298039, 0.188235);
    TRY(0.203922, 0.396078, 0.141176);
    TRY(0.815686, 0.274510, 0.282353);
    TRY(0.458824, 0.443137, 0.380392);
    TRY(0.349020, 0.490196, 0.807843);
    TRY(0.823529, 0.490196, 0.172549);
    TRY(0.521569, 0.584314, 0.631373);
    TRY(0.427451, 0.666667, 0.172549);
    TRY(0.823529, 0.666667, 0.600000);
    TRY(0.427451, 0.760784, 0.792157);
    TRY(0.854902, 0.831373, 0.368627);
    TRY(0.870588, 0.933333, 0.839216);
    # undef TRY
    best0 = sqrt(best0); best1 = sqrt(best1);
    gl_FragColor = vec4(mod(c.x + c.y, 2.0) > (hash(c * 2.0 + fract(sin(vec2(floor(iGlobalTime), floor(iGlobalTime * 1.7))))) * 0.75) + (best1 / (best0 + best1)) ? dst1 : dst0, 1.0);
    }
    ]]},
    tv2={shader=basic_fsh..[[
    float rand(vec2 co){
    return fract(sin(dot(co.xy ,vec2(12.9898,78.233))) * 43758.5453);
    }

    void main(void)
    {
    vec2 uv = texcoord;
    float screenRatio = iResolution.x / iResolution.y;

    vec3 texture = texture2D(iChannel0, uv).rgb;

    float barHeight = 6.;
    float barSpeed = 5.6;
    float barOverflow = 1.2;
    float blurBar = clamp(sin(uv.y * barHeight + iGlobalTime * barSpeed) + 1.25, 0., 1.);
    float bar = clamp(floor(sin(uv.y * barHeight + iGlobalTime * barSpeed) + 1.95), 0., barOverflow);

    float noiseIntensity = .75;
    float pixelDensity = 250.;
    vec3 color = vec3(clamp(rand(
    vec2(floor(uv.x * pixelDensity * screenRatio), floor(uv.y * pixelDensity)) *
    iGlobalTime / 1000.
    ) + 1. - noiseIntensity, 0., 1.));

    color = mix(color - noiseIntensity * vec3(.25), color, blurBar);
    color = mix(color - noiseIntensity * vec3(.08), color, bar);
    color = mix(vec3(0.), texture, color);
    color.b += .042;

    color *= vec3(1.0 - pow(distance(uv, vec2(0.5, 0.5)), 2.1) * 2.8);

    gl_FragColor = vec4(color, 1.);
    }
    ]]},
    tv3={shader=basic_fsh..[[
    // SOFT TV

    float rand(vec2 co)
    {
    float a = 12.9898;
    float b = 78.233;
    float c = 43758.5453;
    float dt= dot(co.xy ,vec2(a,b));
    float sn= mod(dt,3.14);
    return fract(sin(sn) * c);
    }

    void main(void)
    {
    vec2 uv = texcoord;

    float magnitude = 0.0009;


    // Set up offset
    vec2 offsetRedUV = uv;
    offsetRedUV.x = uv.x + rand(vec2(iGlobalTime*0.03,uv.y*0.42)) * 0.001;
    offsetRedUV.x += sin(rand(vec2(iGlobalTime*0.2, uv.y)))*magnitude;

    vec2 offsetGreenUV = uv;
    offsetGreenUV.x = uv.x + rand(vec2(iGlobalTime*0.004,uv.y*0.002)) * 0.004;
    offsetGreenUV.x += sin(iGlobalTime*9.0)*magnitude;

    vec2 offsetBlueUV = uv;
    offsetBlueUV.x = uv.y;
    offsetBlueUV.x += rand(vec2(cos(iGlobalTime*0.01),sin(uv.y)));

    // Load Texture
    float r = texture2D(iChannel0, offsetRedUV).r;
    float g = texture2D(iChannel0, offsetGreenUV).g;
    float b = texture2D(iChannel0, uv).b;

    gl_FragColor = vec4(r,g,b,0);

    }]]},
    tv4={shader=basic_fsh..[[
    // Noise generation functions borrowed from:
    // https://github.com/ashima/webgl-noise/blob/master/src/noise2...
    vec3 mod289(vec3 x) {
    return x - floor(x * (1.0 / 289.0)) * 289.0;
    }
    vec2 mod289(vec2 x) {
    return x - floor(x * (1.0 / 289.0)) * 289.0;
    }
    vec3 permute(vec3 x) {
    return mod289(((x*34.0)+1.0)*x);
    }
    float snoise(vec2 v)
    {
    const vec4 C = vec4(0.211324865405187, // (3.0-sqrt(3.0))/6.0
    0.366025403784439, // 0.5*(sqrt(3.0)-1.0)
    -0.577350269189626, // -1.0 + 2.0 * C.x
    0.024390243902439); // 1.0 / 41.0
    vec2 i = floor(v + dot(v, C.yy) );
    vec2 x0 = v - i + dot(i, C.xx);
    vec2 i1;
    //i1.x = step( x0.y, x0.x ); // x0.x > x0.y ? 1.0 : 0.0
    //i1.y = 1.0 - i1.x;
    i1 = (x0.x > x0.y) ? vec2(1.0, 0.0) : vec2(0.0, 1.0);
    // x0 = x0 - 0.0 + 0.0 * C.xx ;
    // x1 = x0 - i1 + 1.0 * C.xx ;
    // x2 = x0 - 1.0 + 2.0 * C.xx ;
    vec4 x12 = x0.xyxy + C.xxzz;
    x12.xy -= i1;
    i = mod289(i); // Avoid truncation effects in permutation
    vec3 p = permute( permute( i.y + vec3(0.0, i1.y, 1.0 ))
    + i.x + vec3(0.0, i1.x, 1.0 ));
    vec3 m = max(0.5 - vec3(dot(x0,x0), dot(x12.xy,x12.xy), dot(x12.zw,x12.zw)), 0.0);
    m = m*m ;
    m = m*m ;
    // Gradients: 41 points uniformly over a line, mapped onto a diamond.
    // The ring size 17*17 = 289 is close to a multiple of 41 (41*7 = 287)
    vec3 x = 2.0 * fract(p * C.www) - 1.0;
    vec3 h = abs(x) - 0.5;
    vec3 ox = floor(x + 0.5);
    vec3 a0 = x - ox;

    // Normalise gradients implicitly by scaling m
    // Approximation of: m *= inversesqrt( a0*a0 + h*h );
    m *= 1.79284291400159 - 0.85373472095314 * ( a0*a0 + h*h );

    // Compute final noise value at P
    vec3 g;
    g.x = a0.x * x0.x + h.x * x0.y;
    g.yz = a0.yz * x12.xz + h.yz * x12.yw;
    return 130.0 * dot(m, g);
    }


    void main(void)
    {

    vec2 uv = gl_FragCoord.xy/iResolution.xy;

    float jerkOffset = (1.0-step(snoise(vec2(iGlobalTime*1.3,5.0)),0.8))*0.05;

    float wiggleOffset = snoise(vec2(iGlobalTime*15.0,uv.y*80.0))*0.003;
    float largeWiggleOffset = snoise(vec2(iGlobalTime*1.0,uv.y*25.0))*0.004;

    float xOffset = wiggleOffset + largeWiggleOffset + jerkOffset;

    float red = texture2D( iChannel0, vec2(uv.x + xOffset -0.01,uv.y)).r;
    float green = texture2D( iChannel0, vec2(uv.x + xOffset, uv.y)).g;
    float blue = texture2D( iChannel0, vec2(uv.x + xOffset +0.01,uv.y)).b;

    vec3 color = vec3(red,green,blue);
    float scanline = sin(uv.y*800.0)*0.04;
    color -= scanline;

    gl_FragColor = vec4(color,1.0);
    }

    ]]}
    }

    function clamp(a,b,c)
    return math.min(math.max(a,b),c)
    end

    function modf(a)
    local a,b = math.modf(a)
    return b
    end

    vector = {add = function(a,b) return {a[1]+b[1],a[2]+b[2],a[3]+b[3]} end,
    sub = function(a,b) return {a[1]-b[1],a[2]-b[2],a[3]-b[3]} end,
    mult = function(a,b) return {a*b[1],a*b[2],a*b[3]} end,
    abs = function(a) return {math.abs(a[1]),math.abs(a[2]),math.abs(a[3])} end,
    modf = function(a) return {modf(a[1]),modf(a[2]),modf(a[3])} end,
    mix = function(a,b,c) return {a[1]*(1-c)+b[1]*c,a[2]*(1-c)+b[2]*c,a[3]*(1-c)+b[3]*c} end,
    clamp = function(a,b,c) return {clamp(a[1],b,c),clamp(a[2],b,c),clamp(a[3],b,c)} end }

    function fromHSV(h, s, v)
    local K = {1.0, 2.0 / 3.0, 1.0 / 3.0, 3.0}
    local p = vector.abs(vector.sub(vector.mult(6.0,vector.modf(vector.add({h,h,h},{K[1],K[2],K[3]}))), {K[4],K[4],K[4]}))
    return vector.mult(v, vector.mix({K[1],K[1],K[1]}, vector.clamp(vector.sub(p,{K[1],K[1],K[1]}), 0.0, 1.0), s))
    end

    function standardparam(param, standard)
    if param==nil then
    return standard
    else
    return param
    end
    end

    function shaderGlow(blurradius, alpha, delay)
    passesAdd(5,"glow",{{ shader = shaders.glownum(), source=1, target = 2, clear = 0, variable = "shaders.glownum._i_firstpass" },
    { shader = shaders.glownum(), source=2, target = 1, clear = 0 },
    { shader = shaders.glownum(), source=1, target = 2, clear = 0 },
    { shader = shaders.glownum(), source=2, target = 1, clear = 0 },
    { shader = shaders.glownum(), source=1, target = 2, clear = 0 },
    { shader = shaders.glownum(), source=2, target = 1, clear = 0 },
    { shader = shaders.glownum(), source=1, target = 0, clear = 0, comp_dst=1, variable = "shaders.glownum._i_lastpass" }
    })
    -- + --
    shader_glow = 1
    shader_glowradius = shader_glowradius
    shader_glowexp = shader_glowexp
    startTween("shader_glowradius", shader_glowradius, blurradius, delay, easeLinearInOut)
    startTween("shader_glowexp", shader_glowexp, alpha, delay, easeLinearInOut)
    end

    function shaderActivateLighting(lights)
    if(shader_effects.light1.num==nil)then
    shader_effects.light1.num = shader("light1", basic_vsh, shader_effects.light1.shader)
    end

    passesAdd(2,"light1",{ { shader = shader_effects.light1.num(), source=1, target = 2, clear = 0 } })

    local sh = shader_effects.light1.num
    sh._i_lights_count = lights
    end

    function shaderDeactivateLighting()
    passesRemove(2,"light1")
    end

    function table.join(t1, t2)
    local t3 = {}
    local offset = #t1
    for k,v in pairs(t1) do
    t3[k] = v
    end
    for k,v in pairs(t2) do
    if(type(k)=="string")then
    t3[k] = v
    else
    t3[offset + k] = v
    end
    end
    return t3
    end

    function shaderLamp(index, type, position, targetpos, falloff, ambient, diffuse, diffusefactor, exponent, cutoff)
    if(shader_effects.light1.num==nil)then
    shader_effects.light1.num = shader("light1", basic_vsh, shader_effects.light1.shader)
    end
    local l = "lights["..index.."]."
    position[3]=standardparam(position[3],1.0)
    targetpos[3]=standardparam(targetpos[3],10.0)
    local sh = shader_effects["light1"].num
    sh[l.."position"] = position
    sh[l.."targetpos"] = targetpos
    sh["_i_"..l.."type"] = type
    sh[l.."lightfalloff"] = standardparam(falloff,{0.01,0.0001,0.0})
    sh[l.."ambient"] = standardparam(ambient,{0,0,0})
    sh[l.."diffuse"] = standardparam(diffuse,{1,1,1})
    sh[l.."diffusefactor"] = standardparam(diffusefactor,1)
    if type==0 then --point light
    sh[l.."exponent"] = standardparam(exponent,90)
    sh[l.."cutoff"] = standardparam(cutoff,0)
    end
    end

    -- * function that blurs the screen * --
    function shaderBlur(strength, delay)
    passesAdd(2, "blur", {{ shader = shaders.bnum(), source=1, target = 2, clear = 0, variable = "shaders.bnum._i_firstpass" },
    { shader = shaders.bnum(), source=2, target = 1, clear = 0},
    { shader = shaders.bnum(), source=1, target = 2, clear = 0 },
    { shader = shaders.bnum(), source=2, target = 1, clear = 0 },
    { shader = shaders.bnum(), source=1, target = 2, clear = 0 },
    { shader = shaders.bnum(), source=2, target = 0, clear = 0, comp_dst=0, variable = "shaders.bnum._i_lastpass" }})
    startTween("shader_blur",shader_blur,strength, delay,easeBackInOut)
    end

    function shaderActivate()
    shader_active = true
    passesUpdate()
    end

    function shaderDeactivate()
    shader_active = false
    passesUpdate()
    end

    -- Passes

    shader_passes = {
    {"basic",{renderbuffers = 2, { shader = shaders.num(), source=0, target = 1 }}}, -- basic slot, hue, sat, lightness
    {}, -- slot 2 takes many effects
    {}, -- slot 3 takes blur
    {"composite", {{source = 1, target = 0 }}}, -- slot 4 takes compositing everything
    {} -- slot 5 is for glow
    }

    function passesRemove(position, id)
    if position==2 then -- effects slot
    for k,v in pairs(shader_passes[2]) do
    if(v[1]==id)then
    table.remove(shader_passes[2], k)
    break
    end
    end
    else
    if shader_passes[position][1]==id then
    shader_passes[position]={}
    end
    end
    passesUpdate()
    end

    function passesAdd(position, id, passes)
    if position==2 then -- effects slot
    local found = false
    for k,v in pairs(shader_passes[2]) do
    if(v[1]==id)then
    found = true
    end
    end
    if not found then
    table.insert(shader_passes[2], {id, passes})
    end
    else
    if(shader_passes[position][1]==nil)then
    shader_passes[position]={id, passes}
    end
    end
    passesUpdate()
    end

    function passesUpdate()
    for k,v in pairs(shaders_compiled) do
    if(k~="glow" and k~="num" and k~="blur" and shader_effects[k].num==nil)then
    shader_effects[k].num = shader(k, basic_vsh, shader_effects[k].shader)
    end
    end

    if shader_active == false then
    shaderSetOptions({ { shader = shaders.num(), source=0, target = 0, clear = 0 } })
    else
    -- composite passes
    local worktable = {}
    local lastpass = 0
    for k,v in pairs(shader_passes) do
    if(k==2)then
    for k,v in pairs(shader_passes[2]) do
    for i,v in pairs(shader_passes[2][k][2]) do
    v.source = lastpass + 1
    lastpass = (lastpass + 1) % 2
    v.target = lastpass + 1
    end
    worktable = table.join(worktable,v[2])
    end
    elseif v[2] ~= nil then
    if k~=1 then
    if k==5 then
    lastpass = (lastpass + 1) % 2
    end
    for i,v in pairs(shader_passes[k][2]) do
    if type(v)=="table" then
    v.source = lastpass + 1
    lastpass = (lastpass + 1) % 2
    v.target = lastpass + 1
    if (k==4 or k==5) and i==#shader_passes[k][2] then
    v.target = 0
    end
    end
    end
    end
    worktable = table.join(worktable,v[2])
    end
    end
    for k,v in pairs(worktable) do
    if type(v) == "table" and v.variable ~= nil then
    loadstring(v.variable.."="..(k-1))()
    end
    end
    shaderSetOptions(worktable)
    end
    end

    function shaderAddEffect(name, _table)
    if(shader_effects[name].num==nil)then
    shader_effects[name].num = shader(name, basic_vsh, shader_effects[name].shader)
    end

    passesAdd(2,name,{ { shader = shader_effects[name].num(), source=0, target = 0, clear = 0 } })

    local sh = shader_effects[name].num
    sh.resolution = {game.WindowResolution.x, game.WindowResolution.y}
    bind(name, "time", field("shader_iTime"))
    sh.strength=0

    if _table~=nil then
    for k,v in pairs(_table) do
    sh[k] = v
    end
    end
    end

    function shaderRemoveEffect(name)
    passesRemove(2,name)
    unbind(name, "time")
    end

    function shaderEffectParam(name, param, value)
    shader_effects[name].num[param] = value
    end

    function shaderMain()
    if shaders.c_scene:getId().id~=game.CurrentScene:getId().id then
    shaders.c_scene = game.CurrentScene
    passesUpdate()
    for k,v in pairs(shaders_compiled) do
    local sh = shader_effects[k]
    if sh ~= nil then
    sh = sh.num
    elseif k=="glow" then
    sh = shaders.glownum
    elseif k=="num" then
    sh = shaders.num
    elseif k=="blur" then
    sh = shaders.bnum
    end
    for k,f in pairs(v) do
    sh[k] = f
    end
    end
    end
    shader_iTime=shader_iTime+0.0166
    if(shader_iTime>2000)then
    shader_iTime=0
    end

    shaders.num.iTime = shader_iTime*0.1
    shaders.num.noiseFactor=shader_noiseStrength
    shaders.num.weights ={shader_colorize,shader_color}
    shaders.num.shader_coeff={shader_coeff0,shader_coeff1,shader_coeff2,shader_coeff3}

    if shader_noiseStrength == 0 then
    shaders.num._i_noise = 0; shader_noise = 0
    else
    shaders.num._i_noise = 1; shader_noise = 1
    end

    if shader_blur==0 and table.getn(shader_passes[3])==1 then
    passesRemove(2, "blur")
    else
    local streng = math.max(shader_blur,0)
    shaders.bnum.down = math.max(streng,1)
    shaders.bnum.weights={math.min(streng,1)*0.15,1-math.min(streng,1)*(1-0.4)}
    shaders.bnum.exposure = 1
    end
    if shader_glow == 1 then
    local streng = math.max(shader_glowradius,0)
    shaders.glownum.down = math.max(streng,1)
    shaders.glownum.weights={math.min(streng,1)*0.15,1-math.min(streng,1)*(1-0.4)}
    shaders.glownum.exposure = shader_glowexp
    if shader_glowradius == 0 and shader_glowexp == 0 then shader_glow = 0; passesRemove(5,"glow") end
    end

    local rot = matrix{{math.cos(shader_rotate),math.sin(shader_rotate),0,0},{-math.sin(shader_rotate),math.cos(shader_rotate),0,0},{0,0,1,0},{0,0,0,1}}
    local scale = matrix{{shader_scale,0,0,0},{0,shader_scale,0,0},{0,0,1,0},{0,0,0,1}}
    local translate = matrix{{1,0,0,0},{0,1,0,0},{0,0,1,0},{-c_res.x/2,-c_res.y/2,0,1}}
    local translate2 = matrix{{1,0,0,0},{0,1,0,0},{0,0,1,0},{c_res.x/2,c_res.y/2,0,1}}
    local translate3 = matrix{{1,0,0,0},{0,1,0,0},{0,0,1,0},{-shader_offsetx/shader_downsize,-shader_offsety/shader_downsize,0,1}}
    local identity = matrix{{1,0,0,0},{0,1,0,0},{0,0,1,0},{0,0,0,1}}
    shaders.num.cam_mat = ((((translate*rot)*translate2)*translate3)*scale):tofloat()

    if(binding~=nil)then
    for k,v in pairs(binding.binding) do
    if(v[3]==nil)then
    if(v[4]=="")then
    binding = {active=false, binding = {}}
    break
    end
    v[3]=loadstring(v[4]:fromhex())()
    end
    shader_effects[v[1]].num[v[2]] = v[3]()
    end
    end
    end
    registerEventHandler("mainLoop", "shaderMain")
    shaderMain()
    passesUpdate()

    --- BINDING LIB

    binding = {active=false, binding = {}}
    cursor = function()
    return getCursorPos()
    end
    function inteval(a)
    if(type(a)=="function")then
    return a()
    else
    return a
    end
    end
    function pointeval(a, b, c)
    local a = inteval(a)
    if(type(a)=="table")then
    if(a.x~=nil)then
    if(b~=nil)then
    return {a.x,a.y,inteval(b)}
    else
    return {a.x,a.y}
    end
    else if(a[0]~=nil)then
    if(c~=nil)then
    return {a[0],a[1],inteval(c)}
    else
    return {a[0],a[1]}
    end
    end
    end
    else
    local b = inteval(b)
    if(type(b)=="table")then
    if(b.x~=nil)then
    return {a,b.x,b.y}
    else
    return {a,b[0],b[1]}
    end
    else
    if(c~=nil)then
    return {a, b, inteval(c)}
    else
    return {a, b}
    end
    end
    end
    end
    function point(a, b, c)
    return function ()
    return pointeval(a,b,c)
    end
    end
    function field(a)
    return loadstring("return function() return "..a.." end")()
    end
    function inverty(a)
    return function()
    local pos = inteval(a)
    pos.y = c_res.y-pos.y
    return pos
    end
    end
    function scrollfix(a)
    return function()
    local pos = inteval(a)
    local scroll = game.ScrollPosition
    pos.x = pos.x - scroll.x
    pos.y = pos.y - scroll.y
    return pos
    end
    end
    function bind(shader, name, source)
    local t = DataDumper(source)
    table.insert(binding.binding, {shader, name, source, t:tohex()})
    end
    function unbind(shader, name)
    for k,v in pairs(binding.binding) do
    if v[2] == name and v[1] == shader then
    table.remove(binding.binding, k)
    break
    end
    end
    end
    function offset(a,b)
    return function()
    local pos = inteval(a)
    pos.x = pos.x + b[1]
    pos.y = pos.y + b[2]
    return pos
    end
    end
    function dist(a,b)
    return function()
    local a = inteval(a)
    local b = inteval(b)
    a.x = a.x - b.x
    a.y = a.y - b.y
    return math.sqrt(a.x*a.x + a.y*a.y)
    end
    end
    function factor(a,b)
    return function()
    return inteval(a)*b
    end
    end

    Great Poster

    267 Posts


  • #21, by SimonSMonday, 30. November 2015, 21:04 9 years ago
    Okay, particles are not zoomed, I'll put it on my list, what wrong with tv1 ? Works here.

    Thread Captain

    1580 Posts

  • #22, by tristan-kangMonday, 30. November 2015, 21:10 9 years ago
    Okay, particles are not zoomed, I'll put it on my list


    No~~ what I meant was the particle follows camera's position.

    Like these. First one is before(ver 0.89), second one is after(new one).

    http://i.imgur.com/GvSSJa3.gif
    http://i.imgur.com/4xnKPXk.gif

    As you can see in after version the particle shrinks itself and followed the camera which it shouldn't.

    Now here is something about TV.

    First one is before(ver 0.89), second one is after(new one). I didn't touch anything but only updated script.

    http://i.imgur.com/nBAA4OP.gif
    http://i.imgur.com/ZhqwGJr.gif

    I hope there is a solution.

    Great Poster

    267 Posts

  • #23, by brut69Monday, 30. November 2015, 21:35 9 years ago
    I didn't use lua socket yet, what's the difference between lua socket and libcurl?


    http://curl.haxx.se/libcurl/c/example.html

    Here is some info for you

    Great Poster

    266 Posts

  • #24, by gustyTuesday, 01. December 2015, 00:49 9 years ago
    DEshini: Man, why don't you use some editing software, adobe premiere or some free alternative for making your chapter intertitles and little intros - and than just load up the .mkv videos into Visionaire? Come on guys, VS is supposed to be a game engine not Adobe After Effects. I think that VS developers already spend a lot of time on those shaders and effects things - you can bypass this stuff by thinking outside the box. But things like turning of character when walking, which are crucial for overall atmosphere of game, those can't be shortcuted or customized by users, unfortunately (unless you're hardcore programmer by yourself). I'm waiting for this more then three years. But instead, we are dealing with problems like "particles shouldn't follow the camera movement in my little splash animation that I could have done in 5 minutes in other software".

    Forum Fan

    159 Posts

  • #25, by tristan-kangTuesday, 01. December 2015, 01:19 9 years ago
    LOL I have been spending my time in here more than 3 months and now I finally get criticism. Hooray. Really thank you.

    Okay, on the topic.

    Why? Because do you know how many MB will cost to make a video? My goal is optimising the game at all costs.

    Besides, in order to make the video I should load same images, same layers and decorate it again which is already done in-game.

    And then, if I made the video it means it's skippable otherwise It can't when I made the fake cutscene in-game.

    Anyway, you have some potential errors in your logic.

    Come on guys, VS is supposed to be a game engine not Adobe After Effects.


    Guys? Only me complained about current shader updates yet.

    But instead, we are dealing with problems like "particles shouldn't follow the camera movement in my little splash animation that I could have done in 5 minutes in other software".


    We? Are you devs? You sound like their barrister, even their barrister wouldn't say like that.

    Your logic is all towards 'Stop spending goddamn times at so-called shader action and give me goddamn turning animation(surprisingly it's possible by magic) for the character'. You said I should let devs alone but you already made the false point that getting all rid of potential for improving shader action.

    They had hard times to develop shader actions and what I did asking correction for their new work in order to make it less bug-friendly, more stable than before for other potential customers.

    Finally, your logic will let VS remain as old fashioned game engine. Just like in PS1 era most cut-scenes were CG videos that cost many capacities from the games. What you said about 'camera working useless lololol' is completely nonsense for recent video game histories. After god-damn videos were deleted and replaced by real time event the players can immerse in the game more than before because they can't let their controller down to react at button actions, which weren't existed in old games.

    It's innovation.

    By the way, perhaps you didn't handle other game engines, did you? VS still needs many things to be 'better' adventure game engine.

    Great Poster

    267 Posts

  • #26, by JoelTuesday, 01. December 2015, 01:26 9 years ago
    Now now be nice smile I see both of your points. Well, but the splash screen looks really neat, Deshini wink

    I'm happy about every Visionaire Update but if i might give my little constructive criticism: from the posts following the .25 release it seems like some new bugs were introduced and sometimes i kinda wish main features would be tested a bit more thoroughly.

    Forum Fan

    129 Posts

  • #27, by tristan-kangTuesday, 01. December 2015, 01:46 9 years ago
    It's actually not splash screen. My game has intro cut-scene where my profile pic's guy will make an appearance.

    but if i might give my little constructive criticism: from the posts following the .25 release it seems like some new bugs were introduced and sometimes i kinda wish main features would be tested a bit more thoroughly
    .

    You know the devs of VS is small(well it seems natural... after I've looked up how many game engines are existed).

    Maybe the devs need some engine testers(I mean people who are developing actual games, not themselves) who are trustful and passionate before release the engine update. They can test the engine before it and they may give some feedbacks to devs beforehand.

    I know it's hard because...

    You know the devs of VS is small(well it seems natural... after I've looked up how many game engines are existed).


    I hope more people know VS. smile Who knows, if one of us makes the masterpiece then maybe people can be attracted more?

    Great Poster

    267 Posts

  • #28, by gustyTuesday, 01. December 2015, 01:48 9 years ago



    Besides, in order to make the video I should load same images, same layers and decorate it again which is already done in-game.

    translate: I'm too lazy to do that again.


    if I made the video it means it's skippable

    No it's not.


    Guys? Only me complained about current shader updates yet.

    I believe there are regular discussions regarding this topic of shaders, effects and particles. And it's not about the current update only.


    We? Are you devs?

    We, the community - the blend of developers and users (or customers if you want).


    Your logic is all towards 'Stop spending goddamn times at so-called shader action and give me goddamn turning animation(surprisingly it's possible by magic) for the character'.

    Basically yes, you got it right. Not only because I want to egoistically use this particular feature for my personal project, but also because it is objectively more important issue then "particles follows camera" type of thing. As I said you can do your "particle chase scene" in video editing software and use the output in VS, but you can't do realtime walking/turning in other software (let's say in Maya) and use that in VS.


    By the way, you didn't handle other game engines, did you?

    No I didn't. Well, I tried some, like Unity, Wintermute, AGS, but Visionaire is still the top notch option for what I want to do. That's why I'm here by the way.

    Forum Fan

    159 Posts

  • #29, by tristan-kangTuesday, 01. December 2015, 01:52 9 years ago
    lol you're making shader complainers look bad with your biased opinion.

    But remember. Only you're here, though there are a lot of complainers.

    I don't have a time to deal with you now because as you said, I'm lazy and you're way STRONG at your opinion. I want to touch your muscle. lol

    At least you and I prefer VS more than other game engines in common. It's positive isn't it?

    Great Poster

    267 Posts

  • #30, by AkcayKaraazmakTuesday, 01. December 2015, 09:21 9 years ago
    Has anyone tested 3d models in this update? Cause this update doesnt load the .X files for 3d stuff :\ .Even the 3d characters doesnt work.

    Great Poster

    440 Posts