Alternative Module Definitions

lua-users home
wiki

There are many ways to define a "module" [1] in Lua.

Using the module Function

module(..., package.seeall)  -- optionally omitting package.seeall if desired

-- private
local x = 1
local function baz() print 'test' end

function foo() print("foo", x) end

function bar()
  foo()
  baz()
  print "bar"
end

-- Example usage:
require 'mymodule'
mymodule.bar()

This is also common and shorter. It uses Lua's module function. Some other ways of using the module function are in Programming in Lua [2]. However, see LuaModuleFunctionCritiqued for criticisms of this approach.

From a Table - Using Locals Internally

local M = {}

-- private
local x = 1
local function baz() print 'test' end

local function foo() print("foo", x) end
M.foo = foo

local function bar()
  foo()
  baz()
  print "bar"
end
M.bar = bar

return M

This is similar to the table approach, but even inside the module itself it uses lexicals when referring to externally faced variables. Although this code is more verbose (repetitive), lexicals can be more efficient for performance critical code and more suitable for static analysis approaches to DetectingUndefinedVariables. Futhermore, this approach prevents changes made to M--e.g. from a client--from affecting the behavior inside the module; for example, in the regular tables approach, M.bar() internally calls M.foo(), so the behavior of M.bar() will change if M.foo() were replaced. This has some implications for SandBoxes too, and it is the reason for the extra locals in etc/strict.lua in Lua 5.1.3.

localmodule

local M = {}

local x = 1  -- private

local M_baz = 1  -- public

local function M_foo()
  M_baz = M_baz + 1
  print ("foo", x, M_baz)
end

local function M_bar()
  M_foo()
  print "bar"
end

require 'localmodule'.export(M)

return M

-- Example usage:
local MM = require 'mymodule'
MM.baz = 10
MM.bar()
MM.foo = function() print 'hello' end
MM.bar()

-- Output:
-- foo     1       11
-- bar
-- hello
-- bar

This approach is more novel. It defines all externally facing variables in the module using lexical (local) variables. It makes heavy use of lexicals. Reliance on lexicals has some advantages such as when using the static analysis methods of DetectingUndefinedVariables.

The export function uses the debug module to read the current function's local variables prefixed by M_ (debug.getlocal) and expose them (read/write) through the module table M via metafunctions. The ability to write to these variables is made possible by searching for and using (whenever possible) the upvalues located in closures (debug.getupvalue/debug.getupvalue), such as in the nested closures. This avoids the repetition seen in "From a Table - Using Locals Internally". You may selectively replace M_foo style references with M.foo style references if more dynamic behavior is desired.

The implementation of localmodule assumes that symbols have not been stripped (luac -s) and that the debug module has not been removed, so this approach does have a bit more baggage.

The localmodule module is defined as

-- localmodule.lua
-- David Manura, 2008-03, Licensed under the same terms as Lua itself (MIT License).
local M = {}

-- Creates metatable.
local getupvalue = debug.getupvalue
local setupvalue = debug.setupvalue
local function makemt(t)
  local mt = getmetatable(t)
  if not mt then
    mt = {}
    setmetatable(t, mt)
  end
  local varsf,varsi = {},{}
  function mt.__index(_,k)
    local a = varsf[k]
    if a then
      local _,val = getupvalue(a,varsi[k])
      return val
    end
  end
  function mt.__newindex(_,k,v)
    local a = varsf[k]
    if a then
      setupvalue(a,varsi[k], v)
    end
  end
  return varsf,varsi
end

-- Makes locals in caller accessible via the table P.
local function export(P)
  P = P or {}

  local varsf,varsi = makemt(P)

  -- For each local variable, attempt to locate an upvalue
  -- for it in one of the local functions.
  --
  -- TODO: This may have corner cases. For example, we might want to
  -- check that these functions are lexically nested in the current
  -- function (possibly with something like lbci).
  for i=1,math.huge do
    local name,val = debug.getlocal(2, i)
    if val == nil then break end
    if type(val) == 'function' then
      local f = val
      for j=1,math.huge do
        local name,val = debug.getupvalue(f, j)
        if val == nil then break end
        if name:find("M_") == 1 then
          name = name:sub(3)
          varsf[name] = f
          varsi[name] = j
          --print('DEBUG:upvalue', name)
        end
      end
    end
  end

  -- For each local variable, it no upvalue was found, just
  -- resort to making a copy of it instead.
  for i=1,math.huge do
    local name,val = debug.getlocal(2, i)
    if val == nil then break end
    if name:find("M_") == 1 then
      name = name:sub(3)
      if not varsf[name] then
        rawset(P, name, val)
        --print('DEBUG:copy', name)
      end
    end
  end

  return P
end
M.export = export

return M

Pattern: Module System with Public/Private Namespaces

As noted in Programming in Lua, 2nd edition p.144, when using the Lua 5.1 module system with the package.seeall option (or the equivalent setmetatable(M, {__index = _G}) trick), there is a peculiarity in that global variables are accessible through the module table. For example, if you have a module named complex defined as such:

-- complex.lua
module("complex", package.seeall)
-- ...

then doing

require "complex"
print(complex.math.sqrt(2))

prints the square root of 2 because math is a global variable. Furthermore, if a global variable with name complex already exists (possibly defined in some unrelated file), then the require will fail:

-- put this in the main program:
complex = 123
-- then deep in some module do this:
local c = require "complex"
--> fails with "name conflict for module 'complex'"

This is a type of namespace pollution and possibly a source of errors.

The problem as I see it is that the environment used internally by the module is the same as the table exposed to the client of the module. We can make these two separate tables as given in the below solution:

-- cleanmodule.lua

-- Declare module cleanly.
-- Create both public and private namespaces for module.
-- Global assignments inside module get placed in both
-- public and private namespaces.
function cleanmodule(modname)
  local pub = {}     -- public namespace for module
  local priv = {}  -- private namespace for module
  local privmt = {}
  privmt.__index = _G
  privmt.__newindex = function(priv, k, v)
    --print("DEBUG:add",k,v)
    rawset(pub, k, v)
    rawset(priv, k, v)
  end
  setmetatable(priv, privmt)
  setfenv(2, priv)

  package.loaded[modname] = pub
end

-- Require module, but store module only in
-- private namespace of caller (not public namespace).
function cleanrequire(name)
  local result = require(name)
  rawset(getfenv(2), name, result)
  return result
end

Example usage:

-- test.lua
require "cleanmodule"

m2 = 123  -- variable that happens to have same name as a module

cleanrequire "m1"

m1.test()

assert(m1)
assert(not m1.m2)  -- works correctly!
assert(m1.test)
assert(m1.helper)

assert(m2 == 123)  -- works correctly!

print("done")

-- m1.lua
cleanmodule(...)

cleanrequire "m2"

function helper()
  print("123")
end

function test()
  helper()
  m2.test2()
end

assert(not m1)
assert(test)
assert(helper)

assert(m2)
assert(m2.test2)
assert(not m2.m1)
assert(not m2.m2)

-- m2.lua
cleanmodule(...)

function test2()
  print(234)
end

Output:

123
234
done

Take #2 - Here is the latest refinement of the previous code. This version only replaces module not require.

-- cleanmodule.lua

-- Helper function added to modules defined by cleanmodule
-- to support importing module symbols into client namespace.
-- Usage:
--   local mm = require "mymodule"  -- only local exported
--   require "mymodule" ()          -- export module table to environment
--   require "mymodule" ":all"      -- export also all functions
--                                     to environment.
--   require "mymodule" (target,":all")  -- export instead to given table
local function import(public, ...)
  -- Extract arguments.
  local target, options = ...
  if type(target) ~= "table" then
    target, options = nil, target
  end
  target = target or getfenv(2)

  -- Export symbols.
  if options == ":all" then
    for k,v in pairs(public) do target[k] = v end
  end

  -- Build public module tables in caller.
  local prevtable, prevprevtable, prevatom = target, nil, nil
  public._NAME:gsub("[^%.]+", function(atom)
    local table = rawget(prevtable, atom)
    if table == nil then
      table = {}; rawset(prevtable, atom, table)
    elseif type(table) ~= 'table' then
      error('name conflict for module ' .. public._NAME, 4)
    end
    prevatom = atom; prevprevtable = prevtable; prevtable = table
  end)
  rawset(prevprevtable, prevatom, public)

  return public
end

-- Declare module cleanly.
-- Create both public and private namespaces for module.
-- Global assignments inside module get placed in both
-- public and private namespaces.
function cleanmodule(modname)
  local pubmt = {__call = import}
  local pub = {import = import, _NAME = modname} -- public namespace for module
  local priv = {_PUBLIC = pub, _PRIVATE = priv,
                _NAME = modname} -- private namespace for module
  local privmt = {
    __index = _G,
    __newindex = function(priv, k, v)
      rawset(pub, k, v)
      rawset(priv, k, v)
    end
  }
  setmetatable(pub, pubmt)
  setmetatable(priv, privmt)
  setfenv(2, priv)

  pub:import(priv)

  package.loaded[modname] = pub
end

This is typically used in this way:

-- somemodule.lua
require "cleanmodule"
cleanmodule(...)

local om = require "othermodule"

om.hello()

require "othermodule" ()

othermodule.hello()

require "othermodule" ":all"

hello()

The caller has full control in deciding how it wants to the called module to modify the caller's (private) namespace.

One small problem you might run into is when setting a global twice:

cleanmodule(...)
local enable_spanish = true
function test() print("hello") end
if enable_spanish then test = function() print("hola") end end

Here, the metamethod only activates on the first set, so the public namespace will incorrectly contain the first function defined above. The work around is to explicitly set to nil:

cleanmodule(...)
local enable_spanish = true
function test() print("hello") end
if enable_spanish then test = nil; test = function() print("hola") end end

(This example was originally in LuaDesignPatterns.)

--DavidManura, 200703

Take #3 - Here is some further refinement of Take #2. This is a trivial change but might be useful. I placed the cleanmodule code in an anonymous function and called the anonymous function. I also included _G in the private module table. This code can be placed at the beginning of any module file and will not replace any functions at all. It has the same problem as Take #2 when replacing a value but the same workaround will work.


(function (modname)
	-- Helper function added to modules defined by cleanmodule
	-- to support importing module symbols into client namespace.
	-- Usage:
	--   local mm = require "mymodule"  -- only local exported
	--   require "mymodule" ()          -- export module table to environment
	--   require "mymodule" ":all"      -- export also all functions
	--                                     to environment.
	--   require "mymodule" (target,":all")  -- export instead to given table
	local function import(public, ...)
		-- Extract arguments.
		local target, options = ...
		if type(target) ~= "table" then
			target, options = nil, target
		end
		target = target or getfenv(2)

		-- Export symbols.
		if options == ":all" then
			for k,v in pairs(public) do target[k] = v end
		end

		-- Build public module tables in caller.
		local prevtable, prevprevtable, prevatom = target, nil, nil
		public._NAME:gsub("[^%.]+", function(atom)
			local table = rawget(prevtable, atom)
			if table == nil then
				table = {}; rawset(prevtable, atom, table)
			elseif type(table) ~= 'table' then
				error('name conflict for module ' .. public._NAME, 4)
			end
			prevatom = atom; prevprevtable = prevtable; prevtable = table
		end)
		rawset(prevprevtable, prevatom, public)

		return public
	end

	local pubmt = {__call = import}
	local pub = {import = import, _NAME = modname} -- public namespace for module
	local priv = {_PUBLIC = pub, _PRIVATE = priv,
		_NAME = modname, _G = _G } -- private namespace for module
	local privmt = {
		__index = _G,
		__newindex = function(priv, k, v)
			rawset(pub, k, v)
			rawset(priv, k, v)
		end
	}
	setmetatable(pub, pubmt)
	setmetatable(priv, privmt)
	setfenv(2, priv)

	pub:import(priv)

	package.loaded[modname] = pub
end)(...)
--PeterSchwier?, 2009Feb04

Take #4 - Here a rework of Take #2. This achieves public/private namespaces within the existing framework of the module function (without replacing module nor require). However, it does nothing to address the problem of the module function writing to _G rather than to the client's private environment (which might be thought of as an orthogonal problem solvable by redefining module).

-- package/clean.lua
--
-- To be used as an option to function module to expose global
-- variables to the private implementation (like package.seeall)
-- but not expose them through the public interface.
--
-- Changes the environment to a private environment that proxies _G.
-- Writes to the private environment are trapped to write to both
-- the private environment and module (the module's public API).
--
-- Example:
--
--  -- baz.lua
--  module(..., package.clean)
--  function foo() print 'test' end
--  function bar() foo() end
--
-- Now, a client using this module
--
--  require "baz"
--  assert(not baz.print) -- globals not exposed (unlike package.seeall)
--  baz.bar() -- ok
--
-- Careful: Redefinitions will not propogate to module.  Allowing that
-- would require making the private environment an empty proxy table.
--
-- Note: this addresses only one aspect of the problems with the module
-- function.  It does not addess the global namespace pollution issues.  Doing
-- so likely requires redefining the module function to write to the client's
-- private environment rather than _G, or avoiding
-- the module function entirely using a simple table approach [1]).
--
-- [1] http://lua-users.org/wiki/ModuleDefinition
--
-- Released under the public domain.  David Manura, 2009-09-14.
function package.clean(module)
  local privenv = {_PACKAGE_CLEAN = true}
  setfenv(3, setmetatable(privenv,
      {__index=_G, __newindex=function(_,k,v) rawset(privenv,k,v); module[k]=v end}
  ))
end

return package.clean

-- package/veryclean.lua
--
-- This is similar to package.clean except that the public interface is
-- maintained in a separate table M, even in the private implementation.
--
-- Example:
--
--  -- baz.lua
--  module(..., package.veryclean)
--  function M.foo() print 'test' end
--  function M.bar() M.foo() end
--
-- This makes public methods more explicit and also simplifies
-- the implementation.
--
-- Released under the public domain.  David Manura, 2009-09-14.

function package.veryclean(module)
  local privenv = {M=module, _PACKAGE_VERYCLEAN = true}
  setfenv(3, setmetatable(privenv, {__index=_G}))
end

return package.veryclean

-- package/strict.lua
--
-- Here's an optional replacement for strict.lua compatible with
-- package.clean and package.veryclean.  Example:
--
--  module(..., package.veryclean, package.strict)
--
-- Released under the public domain.  David Manura, 2009-09-14.
function package.strict(t)
  local privenv = getfenv(3)
  local top = debug.getinfo(3,'f').func

  local mt = getmetatable(privenv)

  function mt.__index(t,k)
    local v=_G[k]
    if v ~= nil then return v end
    error("variable '" .. k .. "' is not declared", 2)
  end

  if rawget(privenv, '_PACKAGE_CLEAN') then
    local old_newindex = assert(mt.__newindex)
    function mt.__newindex(t,k,v)
      if debug.getinfo(2,'f').func ~= top then
        error("assign to undeclared variable '" .. k .. "'", 2)
      end
      old_newindex(t,k,v)
    end
  else
    function mt.__newindex(t,k,v)
      error("assign to undeclared variable '" .. k .. "'", 2)
      old_newindex(t,k,v)
    end
  end
end

return package.strict

Take #5 - a rework of Take #4 on package.clean(). Uses proxy tables to solve the redeclaration problem. Inherits CLEAN_ENV instead of _G to avoid seeing the polluted global environment, thus solving the problem of dependencies hiding that module() introduces. You could copy the contents of _G into CLEAN_ENV at the very beginning of your program for instance so that modules always see a Lua environment clean of any externally introduced dependencies.

-- kinda bloated at 4 tables and a closure per module :)
local CLEAN_ENV = { pairs = pairs, unpack = unpack, ... }
local P_meta = {__index = CLEAN_ENV}
function package.clean(M)
  local P = setmetatable({}, P_meta)
  setfenv(3, setmetatable({}, {__index = P, __newindex = function(t,k,v) M[k]=v; P[k]=v; end}))
end

--CosminApreutesei, 2009oct

Take #6 an adaption of Take #1 -- the first example, with inspiration from #4 to split module and seeall into orthogonal functions. Here, we use one single table for the module namespace, to avoid all sync issues with the double system. The private module environment is an empty proxy table, with a custom-defined lookup routine (_M[k] or _G[k], that's it). The indirections in private lookups assume that module lookups are more important to be fast externally than internally (you can use locals internally).

-- clean.lua
-- Adaption of "Take #1" of cleanmodule by Ulrik Sverdrup
-- My additions are in the public domain
--
-- Functions:
--  clean.module
--  clean.require
--  clean.seeall

-- Declare module cleanly:
--  module is registered in package.loaded,
--  but not inserted in the global namespace
local function _module(modname, ...)
  local _M = {}     -- namespace for module
  setfenv(2, _M)

  -- Define for partial compatibility with module()
  _M._M = _M
  _M._NAME = modname
  -- FIXME: _PACKAGE

  -- Apply decorators to the module
  if ... then
    for _, func in ipairs({...}) do
      func(_M)
    end
  end

  package.loaded[modname] = _M
end

-- Called as clean.module(..., clean.seeall)
-- Use a private proxy environment for the module,
-- so that the module can access global variables.
--  + Global assignments inside module get placed in the module
--  + Lookups in the private module environment query first the module,
--    then the global namespace.
local function _seeall(_M)
  local priv = {}   -- private environment for module
  local privmt = {}
  privmt.__index = function(priv, k)
    return _M[k] or _G[k]
  end
  privmt.__newindex = _M
  setmetatable(priv, privmt)
  setfenv(3, priv)
end

-- NOTE: Here I recommend a rawset version of
-- http://lua-users.org/wiki/SetVariablesAndTablesWithFunction
-- But it is left out here for brevity.
-- Require module, but store module only in
-- private namespace of caller (not public namespace).
local g_require = require
local function _require(name)
  local result = g_require(name)
  rawset(getfenv(2), name, result)
  return result
end

-- Ironically, this module is not itself clean, so that it
-- can be used with 'require'
module(...)

module = _module
seeall = _seeall
require = _require

-- Ulrik, 2010apr

Take #7 possible module declaration for Lua 5.2

-- init.lua
function module(...) 
	local m={}
	for k,v in ipairs{...} do
		if type(v)=="table" then setmetatable(m,{__index=v})
		elseif type(v)=="function" then v(m) 
		elseif type(v)=="string" then m.notes=v end
	end
	return m
end

-- init-2.lua
function makeenv(list,r0) 
	local r={}
	for i in string.gmatch(list,"%a+") do r[i]=_G[i] end
	for k,v in pairs(r0) do r[k]=v end
	return r
end
function safeenv(m)
	return makeenv([[getmetatable assert pcall select type rawlen rawequal rawset rawget tonumber next tostring xpcall error ipairs unpack setmetatable pairs
	string,math,table,coroutine,bit32,_VERSION]],m)
end
function stdenv(m) 
	m=safeenv(m)
	m=makeenv([[print loadfile require load loadstring dofile collectgarbage os io package debug]],m)
	return m
end

-- module1.lua
return module("my mega module",safeenv{trace=print},function(_ENV) -- safe module. there are no load require ... even no print
	a=20 -- public var
	local b=30 -- private var
	function dump(x) for k,v in pairs(x) do trace(k,v) end end
	local function do_something() a=a+1 end -- private function
end)

-- module2.lua
return module("some description",_G,function(_ENV) -- see all module
	public_var=12345
	local private_var=54321
	public_fn=print
	local private_fn=print
end)

-- test1.lua
local m1=require "module1"
m1.dump(m1)

See Also


RecentChanges · preferences
edit · history
Last edited February 19, 2015 6:01 pm GMT (diff)