initial commit of file from CVS for e-smith-lib on Wed 12 Jul 08:58:46 BST 2023

This commit is contained in:
Brian Read
2023-07-12 08:58:46 +01:00
parent 6d7e97ea37
commit a527984040
98 changed files with 14369 additions and 2 deletions

View File

@@ -0,0 +1,3 @@
{
$DB = esmith::ConfigDB->open(${DB_FILENAME});
}

View File

@@ -0,0 +1,146 @@
#!/usr/bin/perl -w
#----------------------------------------------------------------------
# copyright (C) 2005 Mitel Networks Corporation
#
# This program is free software; you can redistribute it and/or modify
# it under the terms of the GNU General Public License as published by
# the Free Software Foundation; either version 2 of the License, or
# (at your option) any later version.
#
# This program is distributed in the hope that it will be useful,
# but WITHOUT ANY WARRANTY; without even the implied warranty of
# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
# GNU General Public License for more details.
#
# You should have received a copy of the GNU General Public License
# along with this program; if not, write to the Free Software
# Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
#
#----------------------------------------------------------------------
package esmith;
use strict;
use Errno;
use DirHandle;
my $event = shift || die "must give event name parameter";
chdir "/etc/e-smith/events/$event" or die "Couldn't chdir to event directory /etc/e-smith/events/$event: $!";
my $dh = DirHandle->new("services2adjust");
exit(0) unless $dh; # Nothing to do
use esmith::ConfigDB;
use esmith::util;
my %param2char = (
down => 'd',
stop => 'd',
up => 'u',
start => 'u',
restart => 't',
sigterm => 't',
adjust => 'h',
reload => 'h',
sighup => 'h',
sigusr1 => '1',
sigusr2 => '2',
once => 'o',
pause => 'p',
alarm => 'a',
interrupt => 'i',
quit => 'q',
kill => 'k',
exit => 'x',
);
sub adjust_supervised_service
{
my ($s, @actions) = @_;
my $m = "control fifo for service $s: ";
unless (open(C, ">/service/$s/supervise/control"))
{
warn "Couldn't open $m$!";
return;
}
foreach my $p (@actions)
{
my $c = $param2char{$p};
unless ($c)
{
warn "Unrecognised param $p for service $s\n";
next;
}
warn "adjusting supervised $s ($p)\n";
unless (print C $c)
{
warn "Couldn't write to $m$!";
return;
}
}
warn "Couldn't close $m$!" unless close(C);
}
my $conf = esmith::ConfigDB->open_ro || die "Couldn't open config db";
foreach my $service (grep { !/^\./ } $dh->read())
{
my $s = $conf->get($service);
unless ($s)
{
warn "No conf db entry for service $service\n";
next;
}
my $f = "services2adjust/$service";
my @actions;
if (-l "$f")
{
@actions = ( readlink "$f" );
}
else
{
if (open(F, $f))
{
# Read list of actions from the file, and untaint
@actions = map { chomp; /([a-z]+[12]?)/ ; $1 } <F>;
close(F);
}
else
{
warn "Could not open $f: $!";
}
}
# if service is supervised and not handled by systemd
if (-d "/service/$service" && glob("/etc/rc7.d/S??$service"))
{
my $enabled = ($s->prop('status') || 'disabled') eq 'enabled';
adjust_supervised_service($service,
# stop the service if it is now disabled
$enabled ? () : 'down',
# Send the specified signal(s) to the running daemon
@actions,
# bring the service up if it is enabled (and we're not
# stopping it or running it once)
($enabled && !grep { /^(down|stop|d|once|o)$/ } @actions) ? 'up' : (),
);
}
# for service handled by former sysvinit or directly with systemd
else
{
my $enabled = ($s->prop('status') || 'disabled') eq 'enabled';
# bring the service up if it is enabled (and we're not stopping it or running it once, or using signal able to start it)
unshift(@actions,'start') if ($enabled && !grep { /^(down|stop|d|once|o|start|restart|reload-or-restart)$/ } @actions) ;
# stop the service if it is disabled
@actions = ('stop') unless $enabled;
foreach (@actions)
{
warn "adjusting non-supervised $service ($_)\n";
esmith::util::serviceControl(
NAME => $service,
ACTION => $_,
);
}
}
}

View File

@@ -0,0 +1,61 @@
#! /usr/bin/perl -w
#----------------------------------------------------------------------
# copyright (C) 2003-2007 Mitel Networks Corporation
#
# This program is free software; you can redistribute it and/or modify
# it under the terms of the GNU General Public License as published by
# the Free Software Foundation; either version 2 of the License, or
# (at your option) any later version.
#
# This program is distributed in the hope that it will be useful,
# but WITHOUT ANY WARRANTY; without even the implied warranty of
# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
# GNU General Public License for more details.
#
# You should have received a copy of the GNU General Public License
# along with this program; if not, write to the Free Software
# Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
#
#----------------------------------------------------------------------
use strict;
use File::Find;
use File::Copy;
use esmith::templates;
sub expand;
my $event = shift or die "Event name is required\n";
my $filename;
my %args;
my ($param, $value);
my $templates_dir = "/etc/e-smith/events/$event/templates2expand";
exit 0 unless -d $templates_dir;
chdir $templates_dir or die "Could not chdir to $templates_dir: $!\n";;
# Walk the tree and expand all templates referenced thereunder.
find({
no_chdir => 1,
follow => 0,
wanted => \&expand,
},
'.'
);
exit 0;
sub expand
{
return unless -f $_;
# For each file found, read the file to find
# processTemplate args, then expand the template
s/^\.//;
$filename = $_;
warn "expanding $filename\n";
esmith::templates::processTemplate({
MORE_DATA => { EVENT => $event },
TEMPLATE_PATH => $filename,
OUTPUT_FILENAME => $filename,
});
}

View File

@@ -0,0 +1,35 @@
#!/usr/bin/perl -w
#----------------------------------------------------------------------
# copyright (C) 1999-2003 Mitel Networks Corporation
#
# This program is free software; you can redistribute it and/or modify
# it under the terms of the GNU General Public License as published by
# the Free Software Foundation; either version 2 of the License, or
# (at your option) any later version.
#
# This program is distributed in the hope that it will be useful,
# but WITHOUT ANY WARRANTY; without even the implied warranty of
# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
# GNU General Public License for more details.
#
# You should have received a copy of the GNU General Public License
# along with this program; if not, write to the Free Software
# Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
#
# Technical support for this program is available from Mitel Networks
# Please visit our web site www.mitel.com/sme/ for details.
#----------------------------------------------------------------------
package esmith;
use strict;
use esmith::util;
if (esmith::util::initialize_default_databases())
{
exit 0;
}
else
{
exit 1;
}

View File

View File

@@ -0,0 +1,10 @@
#------------------------------------------------------------
# !!DO NOT MODIFY THIS FILE!!
#
# Manual changes will be lost when this file is regenerated.
#
# Please read the developer's guide, which is available
# at http://www.contribs.org/development/
#
# Copyright (C) 1999-2006 Mitel Networks Corporation
#------------------------------------------------------------

View File

@@ -0,0 +1,13 @@
{
$OUT = <<HERE;
<!--
HERE
$OUT .=
Text::Template::_load_text("/etc/e-smith/templates-default/template-begin");
$OUT .= <<HERE;
-->
HERE
}

View File

@@ -0,0 +1,8 @@
{
$OUT = <<HERE;
#%PAM-1.0
HERE
$OUT .=
Text::Template::_load_text("/etc/e-smith/templates-default/template-begin");
}

View File

@@ -0,0 +1,8 @@
{
$OUT = <<HERE;
#!/usr/bin/perl -w
HERE
$OUT .=
Text::Template::_load_text("/etc/e-smith/templates-default/template-begin");
}

View File

@@ -0,0 +1,14 @@
{
$OUT = <<HERE;
<?php
/*
HERE
$OUT .=
Text::Template::_load_text("/etc/e-smith/templates-default/template-begin");
$OUT .= <<HERE;
*/
HERE
}

View File

@@ -0,0 +1,8 @@
{
$OUT = <<HERE;
#!/bin/sh
HERE
$OUT .=
Text::Template::_load_text("/etc/e-smith/templates-default/template-begin");
}

View File

@@ -0,0 +1 @@
?>

View File

@@ -0,0 +1,81 @@
# DO NOT MODIFY THIS FILE.
# This file is automatically maintained by the Mitel Networks SME Server
# configuration software. Manually editing this file may put your
# system in an unknown state.
#
# updated: Thu Mar 28 15:29:31 2002
Bart.Simpson=pseudonym|Account|bart
Bart_Simpson=pseudonym|Account|bart
Global=system
Primary=system
adm=system|Gid|4|Uid|3
admin=system|Gid|101|Uid|101
alias=system|Gid|400|Uid|400
apache=existing|Gid|48|Uid|48
bart=user|FirstName|Bart|LastName|Simpson
bin=system|Gid|1|Uid|1
cdrom=system
cgi-bin=url
console=system
daemon=system|Gid|2|Uid|2
dip=system|Gid|40
disk=system|Gid|6
dns=existing|Gid|53|Uid|53
e-smith-manager=url
e-smith-password=url
everyone=pseudonym|Account|shared|Visible|internal
floppy=system|Gid|19
ftp=system|Gid|50|Uid|14
games=system|Gid|20|Uid|12
global=system
gopher=system|Gid|30|Uid|13
halt=system
homes=system
kmem=system|Gid|9
ldap=existing|Gid|55|Uid|55
lp=system|Gid|7|Uid|4
mail=system|Gid|12|Uid|8
mailer-daemon=pseudonym|Account|admin
man=system|Gid|15
mem=system|Gid|8
mysql=existing|Gid|27|Uid|27
named=existing|Gid|25|Uid|25
netlogon=netlogon|Comment|placeholder for netlogon share
news=system|Gid|13|Uid|9
nofiles=system|Gid|400
operator=system|Gid|0|Uid|11
postgres=system
postmaster=pseudonym|Account|admin
primary=system
printers=system
public=system|Gid|103|Uid|102
qmail=system|Gid|401
qmaild=system|Gid|400|Uid|401
qmaill=system|Gid|400|Uid|402
qmailp=system|Gid|400|Uid|403
qmailq=system|Gid|401|Uid|404
qmailr=system|Gid|401|Uid|405
qmails=system|Gid|401|Uid|406
qmailscan=existing|Gid|407|Uid|407
root=system|Gid|0|Uid|0
schwern=user|Uid|500|Gid|501|FirstName|Michael|LastName|Schwern
server-manager=url
server-manual=url
shared=system|Gid|500|Visible|internal
shutdown=system
simpsons=group|Description|bar|Gid|5005|Members|bart,lisa,homer,maggie|Uid|5005
slocate=system
somegroup=group|Gid|42|Members|admin
squid=system|Gid|23|Uid|23
sync=system
sys=system|Gid|3
trend=existing|Gid|408|Uid|408
tty=system|Gid|5
user-password=url
users=system|Gid|100
utmp=system|Gid|22
uucp=system|Gid|14|Uid|10
webmail=url
wheel=system|Gid|10
www=system|Gid|102|Uid|100
wwwpublic=system

View File

@@ -0,0 +1,95 @@
#!/usr/bin/perl -w
# Overall tests for esmith::config
use strict;
use File::Copy;
use Test::More 'no_plan';
use_ok('esmith::config');
my %Expect = ( foo => 'bar',
'this key' => 'has whitespace',
'that key ' => 'has trailing whitespace',
' another key' => 'has leading whitespace',
'this value' => ' has leading whitespace',
'that value' => 'has trailing whitespace ',
'tricky value' => 'with=equals.',
);
# so we don't bork the original.
my $Scratch = '10e-smith-lib/mydummy.conf';
copy('10e-smith-lib/dummy.conf', $Scratch);
END { unlink $Scratch }
my %config;
tie %config, 'esmith::config', $Scratch;
ok( tied %config, 'tie worked' );
is_deeply( \%config, \%Expect, 'read in the config properly' );
# Test the tied interface.
is_deeply( [sort keys %config], [sort keys %Expect], 'keys' );
is_deeply( [sort values %config], [sort values %Expect], 'values' );
is_deeply( [@config{'foo', 'this key'}], [@Expect{'foo', 'this key'}],
'hash slice');
$config{foo} = 'baz';
is( $config{foo}, 'baz', 'STORE' );
my %config_copy;
tie %config_copy, 'esmith::config', $Scratch;
is( $config_copy{foo}, 'baz', ' STORE saved' );
SKIP: {
skip "Locking is broken in perl 5.6.0", 2 if $] eq 5.006;
tied(%config_copy)->_lock_write;
my $start_time = time;
{
local $ENV{PERL5LIB} = join ':', @INC;
system(qq{$^X -Mesmith::config -e 'alarm 4; tie %config, "esmith::config", q{$Scratch}'});
}
cmp_ok( time - 2, '<=', $start_time, 'write locks dont prevent read' );
tied(%config_copy)->_lock_write;
$start_time = time;
{
local $ENV{PERL5LIB} = join ':', @INC;
system(qq{$^X -Mesmith::config -e 'alarm 4; tie %config, "esmith::config", q{$Scratch}; \$config{foo} = 42'});
}
cmp_ok( time - 1, '>=', $start_time, 'write locks prevent writes' );
};
my $new_conf = 'I_dont_exist';
unlink $new_conf;
ok( !-e $new_conf, 'config file doesnt exist' );
END { unlink $new_conf }
tie %config, 'esmith::config', $new_conf;
is( keys %config, 0, 'new() from nonexistent config' );
$config{wibble} = 'wobble';
tie %config_copy, 'esmith::config', $new_conf;
is( $config_copy{wibble}, 'wobble', ' new config file written' );
SKIP: {
skip "Locking is broken in perl 5.6.0", 1 if $] eq 5.006;
# There was a bug where if you set something to its existing value
# it wouldn't unlock properly.
my $Alarm;
eval {
local $SIG{ALRM} = sub { $Alarm = 1; die "ALARM!\n"; };
alarm 1;
$config_copy{wibble} = $config_copy{wibble};
$config{wibble} = 42;
alarm 0;
};
ok( !$Alarm, 'Unlocking works for setting the same value' );
};

View File

@@ -0,0 +1,13 @@
#!/usr/bin/perl -Tw
use strict;
use esmith::config;
use Test::More tests => 2;
my %config;
tie %config, 'esmith::config', '10e-smith-lib/dummy.conf';
my $value = $config{foo};
# Config values *should* be tained, but code depends on them not being.
is( $value, 'bar', 'tied to the dummy database' );
ok( eval { () = join('', $value), kill 0; 1; }, 'config values not tainted' );

View File

@@ -0,0 +1,103 @@
# DO NOT MODIFY THIS FILE.
# This file is automatically maintained by the Mitel Networks SME Server
# configuration software. Manually editing this file may put your
# system in an unknown state.
#
# updated: Fri Feb 28 16:41:34 2003
AccessType=dedicated
ActiveAccounts=0
AdminEmail=
ConsoleMode=login
ContactEmail=
ContactName=
ContactOrg=
DialupConnOffice=long
DialupConnOutside=long
DialupConnWeekend=long
DialupFreqOffice=every15min
DialupFreqOutside=everyhour
DialupFreqWeekend=everyhour
DialupModemDevice=/dev/ttyS1
DialupPhoneNumber=
DialupUserAccount=useraccount
DialupUserPassword=userpassword
DomainName=e-smith.com
DynDnsAccount=dnsaccount
DynDnsPassword=dnspassword
DynDnsService=off
EmailUnknownUser=return
EthernetDriver1=pcnet32
EthernetDriver2=unknown
ExternalDHCP=off
ExternalNetmask=255.255.255.0
GatewayIP=192.168.16.1
LocalIP=192.168.16.228
LocalNetmask=255.255.255.0
MinUid=5000
PasswordSet=yes
PreviousConfiguration=/home/e-smith/db/configuration.previous
SMTPSmartHost=
SambaDomainMaster=no
SambaServerName=pretz
SambaWorkgroup=mitel-networks
ServiceAccountId=
ServiceDomainName=
ServiceTargetIP=
SquidParent=
SquidParentPort=
StatusReports=off
SystemMode=serveronly
SystemName=pretz
TimeZone=US/Eastern
UnsavedChanges=yes
atalk=service|InitscriptOrder|91|status|enabled
auth=service|access|public|status|enabled
bazbar=service|status|enabled
blades=service|Host|service.e-smith.com|status|enabled
bootstrap-console=service|InitscriptOrder|35|Run|no|status|enabled
branding=service|modified|000000000000|status|enabled
crond=service|InitscriptOrder|40|status|enabled
ctrlaltdel=service|status|enabled
dhcpd=service|InitscriptOrder|65|end|192.168.16.250|start|192.168.16.65|status|disabled
diald=service|InitscriptOrder|57|status|disabled
fetchmail=service|FreqOffice|every5min|FreqOutside|every30min|FreqWeekend|never|Method|standard|SecondaryMailAccount|popaccount|SecondaryMailPassword|poppassword|SecondaryMailServer|mail.myisp.xxx|status|disabled
flexbackup=backupservice|erase_rewind_only|true
ftp=service|access|private|accessLimits|off|status|enabled
hdparm=service|InitscriptOrder|40|status|disabled
horde=service|status|disabled
httpd-admin=service|InitscriptOrder|86|status|enabled
httpd-e-smith=service|InitscriptOrder|85|access|private|status|enabled
imap=service|access|private|status|enabled
imp=service|status|disabled
ippp=service|InitscriptOrder|55|status|enabled
ipsec=service|InitscriptOrder|90|PubKey|0sAQOoIKaOMuDqSdCZJXgv9QI86DAuAwbbvn8uoKn2lRQ9ZVPTn9Ow5znhuw/GopsYD2eujhtvkQo7fszAhWbEpn+lW2LzLCbZYaDov7j8Q9CpeJSVgeuzaBcw3OenSL3ltTwWWtG0pvyaYsfepNqVYvo64YVmrxo0O7dCECySMVBZkQ==|status|disabled
isdn=service|Protocol|2|UseSyncPPP|yes|status|disabled
keytable=service|InitscriptOrder|25|status|enabled
ldap=service|InitscriptOrder|80|access|private|defaultCity|Ottawa|defaultCompany|XYZ Corporation|defaultDepartment|Main|defaultPhoneNumber|555-5555|defaultStreet|123 Main Street|status|enabled
lilo=service|AddressMode|linear
local=service|InitscriptOrder|99|status|enabled
lpd=service|InitscriptOrder|60|status|enabled
mariadb=service|InitscriptOrder|90|status|enabled
masq=service|InitscriptOrder|06|Logging|none|Stealth|no|status|disabled
modSSL=service|status|enabled
mysql.init=service|InitscriptOrder|99|status|enabled
named=service|chroot|yes|status|enabled|Forwarder1|1.2.3.4
network=service|InitscriptOrder|10|status|enabled
ntpd=service|InitscriptOrder|55|status|disabled
php=service|status|enabled
popd=service|access|private|status|enabled
pppoe=service|DemandIdleTime|no|InitscriptOrder|57|SynchronousPPP|no|status|disabled
pptpd=service|sessions|10|status|disabled
qmail=service|InitscriptOrder|80|status|enabled
random=service|InitscriptOrder|20|status|enabled
rsyslog=service|InitscriptOrder|05|status|enabled
scanner=service|ScannerFns|iscan|UpdateTime|1:14|scanMail|yes|status|enabled
smb=service|InitscriptOrder|91|RoamingProfiles|no|status|enabled
smtpd=service|access|public|status|enabled
smtpfwdd=service|InitscriptOrder|81|status|enabled
squid=service|InitscriptOrder|90|status|enabled
sshd=service|InitscriptOrder|85|PasswordAuthentication|yes|PermitRootLogin|yes|access|private|status|enabled
sync=service|Host|service.e-smith.com|LastId|0|SuccessId|0|SyncFrequency|1|SyncMinute|57|status|disabled
telnet=service|access|private|status|disabled
wibble=42
xinetd=service|InitscriptOrder|50|status|enabled

View File

@@ -0,0 +1,215 @@
#!/usr/bin/perl -w
# Overall test for esmith::db
use File::Copy;
use esmith::TestUtils;
use Test::More 'no_plan';
use_ok('esmith::db');
my %Expect = (
Foo => ['Bar', {}],
Night => ['Day', {}],
Squid => ['cephalopod', {
arms => 10,
species => 'Loligo',
}
],
# Ensure that empty values are read in properly.
Octopus => ['cephalopod', {
arms => 8,
species => '',
}
],
# Ensure that escaped pipes are read in properly.
Pipe => ['art', { pipe => 'this is not a \| got that?'}],
# Ensure that escaped newlines are handled properly.
Haiku => ['poem', { words =>
"Damian Conway\n".
"God damn! Damian Conway\n".
"Damian Conway"
}
]
);
my $Scratch_Conf = '10e-smith-lib/db_scratch.conf';
copy '10e-smith-lib/db_dummy.conf', $Scratch_Conf;
END { unlink $Scratch_Conf }
my %config;
tie %config, 'esmith::config', $Scratch_Conf;
ok( tied %config, 'tied to the dummy config file' );
isnt( keys %config, 0, ' and theres something in there' );
is( db_get_type(\%config, 'Foo'), 'Bar', 'simple db_get_type' );
my @keys = db_get(\%config);
is_deeply( [sort @keys], [sort keys %Expect],
'db_get() all keys' );
foreach my $key (@keys) {
my($type, %properties) = db_get(\%config, $key);
my($exp_type, $exp_properties) = @{$Expect{$key}};
is( $type, $exp_type, "db_get - type - $key" );
is( db_get_type(\%config, $key), $exp_type, "db_get_type" );
is_deeply( \%properties, $exp_properties, "db_get - prop" );
is_deeply( {db_get_prop(\%config, $key)}, $exp_properties,
"db_get_prop - all properties");
while( my($prop, $val) = each %properties ) {
is( db_get_prop(\%config, $key, $prop), $val,
"db_get_prop - single prop - $prop");
}
}
is( db_get_type(\%config, 'I_dont_exist'), undef,
'db_get_type on non-existent key' );
is( db_get_prop(\%config, 'I_dont_exist'), undef,
' db_get_prop' );
is( db_get_prop(\%config, 'Squid', 'feet'), undef,
'db_get_prop on non-existent prop' );
is( db_delete_prop(\%config, 'I_dont_exist', 'feet'), undef,
'db_delete_prop on non-existent key' );
is( db_get(\%config, 'Squid'), 'cephalopod|arms|10|species|Loligo',
'db_get a raw value');
{
package TieOut;
sub TIEHANDLE {
bless( \(my $scalar), $_[0]);
}
sub PRINT {
my $self = shift;
$$self .= join('', @_);
}
sub read {
my $self = shift;
return substr($$self, 0, length($$self), '');
}
}
my $out = tie *STDOUT, 'TieOut';
db_show(\%config);
is( $out->read, <<SHOW, 'db_show() all' );
Foo=Bar
Haiku=poem
words=Damian Conway\nGod damn! Damian Conway\nDamian Conway
Night=Day
Octopus=cephalopod
arms=8
species=
Pipe=art
pipe=this is not a \\| got that?
Squid=cephalopod
arms=10
species=Loligo
SHOW
db_show(\%config, 'Squid');
is( $out->read, <<SHOW, 'db_show() one key' );
Squid=cephalopod
arms=10
species=Loligo
SHOW
db_print(\%config);
is( $out->read, <<PRINT, 'db_print all' );
Foo=Bar
Haiku=poem|words|Damian Conway\nGod damn! Damian Conway\nDamian Conway
Night=Day
Octopus=cephalopod|arms|8|species|
Pipe=art|pipe|this is not a \\| got that?
Squid=cephalopod|arms|10|species|Loligo
PRINT
db_print(\%config, 'Squid');
is( $out->read, <<PRINT, 'db_print one key' );
Squid=cephalopod|arms|10|species|Loligo
PRINT
db_print_type(\%config);
is( $out->read, <<PRINT_TYPE, 'db_print_type all keys' );
Foo=Bar
Haiku=poem
Night=Day
Octopus=cephalopod
Pipe=art
Squid=cephalopod
PRINT_TYPE
db_print_type(\%config, 'Squid');
is( $out->read, <<PRINT_TYPE, 'db_print_type one key' );
Squid=cephalopod
PRINT_TYPE
db_print_prop(\%config, 'Squid');
is( $out->read, <<PRINT_PROP, 'db_print_prop all props' );
arms=10
species=Loligo
PRINT_PROP
db_print_prop(\%config, 'Squid', 'arms');
is( $out->read, <<PRINT_PROP, 'db_print_prop one prop' );
arms=10
PRINT_PROP
undef $out;
untie *STDOUT;
db_set(\%config, 'Wibble', 'dribble|hip|hop');
my($type, %props) = db_get(\%config, 'Wibble');
is( $type, 'dribble', 'db_set with raw value' );
is_deeply( \%props, { hip => 'hop' }, ' again' );
db_set(\%config, 'Wibble', 'word', { thingy => 'yep' });
($type, %props) = db_get(\%config, 'Wibble');
is( $type, 'word', 'db_set');
is_deeply( \%props, { thingy => 'yep' } );
db_set_type(\%config, 'Wibble', 'yibble');
is( db_get_type(\%config, 'Wibble'), 'yibble', 'db_set_type' );
db_set_prop(\%config, 'Wibble', har => 'far');
is( db_get_prop(\%config, 'Wibble', 'har'), 'far', 'db_set_prop' );
### Test read-only open()
my $scratch = scratch_copy('10e-smith-lib/configuration.conf');
ok( chmod 0444, $scratch );
my $ro_db = esmith::DB::db->open_ro($scratch);
eval { $ro_db->new_record('wibble', { type => 'something' }) };
like( $@, qr/read-only/ );
my $sshd = $ro_db->get('sshd');
eval { $sshd->set_prop('foo', 'bar') };
like( $@, qr/read-only/ );
is( $sshd->prop('foo'), undef );
eval { $sshd->delete_prop('status') };
like( $@, qr/read-only/ );
isnt( $sshd->prop('status'), undef );
eval { $sshd->merge_props(foo => 'bar') };
like( $@, qr/read-only/ );
is( $sshd->prop('foo'), undef );
eval { $sshd->reset_props(foo => 'bar') };
like( $@, qr/read-only/ );
is( $sshd->prop('foo'), undef );
eval { $sshd->delete };
like( $@, qr/read-only/ );
ok( $ro_db->get('sshd') );

View File

@@ -0,0 +1,4 @@
{
$DB = esmith::ConfigDB->open("${DB_FILENAME}");
}

View File

@@ -0,0 +1,3 @@
{
$DB->new_record("quux", {type=>'service', status=>'enabled'});
}

View File

@@ -0,0 +1,7 @@
# Dummy configuration file for testing esmith::db
Foo=Bar
Night=Day
Squid=cephalopod|arms|10|species|Loligo
Pipe=art|pipe|this is not a \| got that?
Haiku=poem|words|Damian Conway\nGod damn! Damian Conway\nDamian Conway
Octopus=cephalopod|arms|8|species|

View File

@@ -0,0 +1,141 @@
#!/usr/bin/perl -w
# vim: ft=perl:
use strict;
use esmith::util;
use esmith::ConfigDB;
use Test::More 'no_plan';
use File::Copy qw(copy);
use POSIX qw(tmpnam);
# What we want to do is run initialize-default-databases on a scratch
# db and check the results.
my $dbhome = '/tmp/dbhome';
my $dbroot = '/etc/e-smith/db';
system('rm', '-rf', $dbhome);
system('mkdir', '-p', $dbhome) == 0
or die "Can't create $dbhome: $!\n";
ok( esmith::util::initialize_default_databases(dbhome => $dbhome),
"initialize_default_databases created successfully" );
# Confirm the default settings.
walk_dbtree($dbroot, 'defaults');
# Test that forced options were forced.
walk_dbtree($dbroot, 'force');
# We should now have default configuration files. We can go through each
# setting specified by the defaults and confirm that it is correct.
# To test migration, we should take a typical 5.6 set of databases and migrate
# those. The existing .conf databases in the 10e-smith-lib directory are
# styled after 5.6, and suitable for this.
foreach my $dummyconf (qw(accounts.conf domains.conf networks.conf
configuration.conf hosts.conf))
{
# Copy them over the ones in our test directory, and then migrate them.
my $dest;
($dest = $dummyconf) =~ s/\.conf$//;
$dest = "$dbhome/$dest";
copy($dummyconf, $dest) or die "Can't copy $dummyconf to $dest: $!\n";
}
# Migrate the directory.
ok( esmith::util::initialize_default_databases(dbhome => $dbhome),
"initialize_default_databases migrated successfully" );
#run_migrate_tests($dbhome, $dbroot);
system('rm', '-rf', $dbhome);
exit 0;
sub walk_dbtree
{
my $dbroot = shift;
my $mode = shift;
die unless $mode =~ /^(defaults|force)$/;
opendir(DBROOT, $dbroot) or die "Can't open $dbroot: $!\n";
my @dbfiles = grep { -d "$dbroot/$_" }
grep { !/^\./ } readdir DBROOT;
closedir(DBROOT);
foreach my $dbfile (@dbfiles)
{
# Handle the defaults in this case.
my $defaultdir = "$dbroot/$dbfile/defaults";
next if not -e $defaultdir;
opendir(DEFAULTDIR, $defaultdir) or die "Can't open $defaultdir: $!\n";
my @keys = grep { -d "$defaultdir/$_" }
grep { !/^\./ } readdir DEFAULTDIR;
closedir(DEFAULTDIR);
# There should now be a db file output at the dbhome.
ok( -e "$dbhome/$dbfile", "$dbfile db exists" );
my $db = esmith::ConfigDB->open_ro("$dbhome/$dbfile");
ok( defined $db, "$dbhome/$dbfile loads properly" );
# Loop on all the keys.
foreach my $keydir (@keys)
{
my $key_fullpath = "$defaultdir/$keydir";
opendir(KEYDIR, $key_fullpath)
or die "Can't open $key_fullpath: $!\n";
my @propfiles = grep { -f "$key_fullpath/$_" }
grep { !/^\./ } readdir KEYDIR;
closedir(KEYDIR);
foreach my $propfile (@propfiles)
{
my $propfile_fullpath = "$key_fullpath/$propfile";
# Open each and check what the default should be.
open(PROPFILE, "<$propfile_fullpath")
or die "Can't open $propfile_fullpath: $!\n";
chomp( my $propval = <PROPFILE> );
close(PROPFILE);
if ($keydir eq 'ActiveAccounts')
{
print "get_prop on $keydir, $propfile returns ";
print $db->get_prop($keydir, $propfile) . "\n";
print "propval is $propval\n";
}
ok( $db->get_prop($keydir, $propfile) eq $propval,
"property $propfile of record $keydir has correct $mode value of $propval" );
}
}
}
}
# FIXME: This works, but the numbers of the tests are thrown off. We probably
# want to eval the test block of code instead.
sub run_migrate_tests
{
my $dbhome = shift;
my $dbroot = shift;
opendir(DBROOT, $dbroot) or die "Can't open $dbroot: $!\n";
my @dbfiles = grep { -d "$dbroot/$_" }
grep { !/^\./ } readdir DBROOT;
closedir(DBROOT);
foreach my $dbfile (@dbfiles)
{
# Handle the defaults in this case.
my $migratedir = "$dbroot/$dbfile/migrate";
next if not -e $migratedir;
opendir(MIGRATEDIR, $migratedir) or die "Can't open $migratedir: $!\n";
my @migrate_fragments = grep { !/^\./ } readdir MIGRATEDIR;
closedir(MIGRATEDIR);
foreach my $migrate_fragment (sort @migrate_fragments)
{
my $tempname = tmpnam() or die "Can't obtain tempfile: $!\n";
my $pod2test = '/usr/bin/pod2test';
system($pod2test, "$migratedir/$migrate_fragment", $tempname);
if (! -e $tempname)
{
warn "The fragment $migrate_fragment apparently has no embedded tests\n";
next;
}
system('/usr/bin/perl', $tempname);
}
}
}

View File

@@ -0,0 +1,3 @@
test=domain|foo|bar
foo=domain|baz|quux
wombat=notadomain

View File

@@ -0,0 +1,11 @@
foo=bar
this key=has whitespace
that key =has trailing whitespace
another key=has leading whitespace
this value= has leading whitespace
that value=has trailing whitespace
# this is a comment. ignore it.
# this is a comment = too
tricky value=with=equals.

View File

@@ -0,0 +1,13 @@
# DO NOT MODIFY THIS FILE.
# This file is automatically maintained by the Mitel Networks SME Server
# configuration software. Manually editing this file may put your
# system in an unknown state.
#
# updated: Fri Mar 11 18:21:42 2002
ftp.mydomain.xxx=host|ExternalIP||HostType|Self|InternalIP||MACAddress||Visibility|Local
mail.mydomain.xxx=host|ExternalIP||HostType|Self|InternalIP||MACAddress||Visibility|Local
myserver.mydomain.xxx=host|ExternalIP||HostType|Local|InternalIP||MACAddress||Visibility|Local
otherhost.mydomain.xxx=host|ExternalIP||HostType|Local|InternalIP|192.168.1.3|MACAddress||Visibility|Local
www.mydomain.xxx=host|ExternalIP||HostType|Self|InternalIP||MACAddress||Visibility|Local
www.otherdomain.xxx=host|ExternalIP||HostType|Self|InternalIP||MACAddress||Visibility|Local
foo.otherdomain.xxx=host|ExternalIP||HostType|Self|InternalIP||MACAddress||Visibility|Local

View File

@@ -0,0 +1 @@
I am an English license.

View File

@@ -0,0 +1 @@
Je suis une license francais. Or something like that.

View File

@@ -0,0 +1 @@
10.0.0.0=network|Mask|255.255.255.0|Router|default

View File

@@ -0,0 +1 @@
sysconfig=configuration|KeyboardType|pc|Keytable|us|Language|en_US|ReleaseVersion|6.0alpha2

View File

@@ -0,0 +1 @@
sysconfig=configuration|KeyboardType|pc|Keytable|us|Language|fr_CA|ReleaseVersion|6.0alpha2

View File

@@ -0,0 +1,111 @@
#!/usr/bin/perl -w
use esmith::TestUtils qw(scratch_copy);
use File::Path;
use Test::More 'no_plan';
use_ok('esmith::templates', qw(:DEFAULT removeBlankLines));
use esmith::config;
my %config;
tie %config, 'esmith::config', '10e-smith-lib/scratch.conf';
$ENV{ESMITH_CONFIG_DB} = '10e-smith-lib/scratch.conf';
END { unlink '10e-smith-lib/scratch.conf' }
my $Scratch_Temp_Dir = 'template_scratch_dir';
my $Scratch_Temp = "$Scratch_Temp_Dir/dummy";
mkpath "$Scratch_Temp_Dir/10e-smith-lib";
END { rmtree $Scratch_Temp_Dir }
# processTemplate() is going to be Loud and Helpful about skipping
# things like CVS directories.
$SIG{__WARN__} = sub { return if $_[0] =~ /^Skipping directory/ };
$config{Koala_Say} = "This is not the bear you're looking for.";
processTemplate({ CONFREF => \%config,
OUTPUT_PREFIX => $Scratch_Temp_Dir,
OUTPUT_FILENAME => 'dummy',
TEMPLATE_PATH => 'templates',
TEMPLATE_EXPAND_QUEUE => [
'10e-smith-lib'
],
FILTER => \&removeBlankLines,
UID => $<,
GID => (split / /, $()[0]
});
ok( -f $Scratch_Temp, 'file generated' );
ok( -s $Scratch_Temp, ' its not empty' );
open(SCRATCH, $Scratch_Temp) || die $!;
my $out;
{ local $/; $out = <SCRATCH>; }
close SCRATCH;
my $koala_output = <<'THIS';
# This is the beginning of the beginning
# confref ok
----------------------------------------
< This is not the bear you're looking for. >
----------------------------------------
\
\ .
___ //
{~._.~}//
( Y )K/
()~*~()
(_)-(_)
Luke
Skywalker
koala
# This is the end, My only friend, the end of our elaborate templates, the end
THIS
is( $out, $koala_output, 'file generated properly' );
$out = processTemplate({
CONFREF => \%config,
TEMPLATE_PATH => 'templates',
TEMPLATE_EXPAND_QUEUE => [
'10e-smith-lib'
],
FILTER => sub { $_[0] =~ /^\s*$/ ? '' : $_[0] },
UID => $<,
GID => (split / /, $()[0],
OUTPUT_TYPE => 'string'
});
is( $out, $koala_output, 'string generated properly' );
my $h_scratch = scratch_copy('10e-smith-lib/hosts.conf');
my $a_scratch = scratch_copy('10e-smith-lib/accounts.conf');
use esmith::AccountsDB;
use esmith::HostsDB;
my $acct = esmith::AccountsDB->open($a_scratch);
my $host = esmith::HostsDB->open($h_scratch);
$out = processTemplate({
MORE_DATA => { Author => 'Douglas Adams' },
TEMPLATE_PATH => 'templates_DB',
TEMPLATE_EXPAND_QUEUE => [
'10e-smith-lib'
],
OUTPUT_TYPE => 'string'
});
is( $out, <<'THIS', 'DB & MORE_DATA' );
Chapter 1
The story so far:
In the beginning the Universe was created. This has made a lot
of people very angry and been widely regarded as a bad move.
-- Douglas Adams
$DB ok
default vars ok
confref not defined
The end of labor is to gain leisure.
THIS

View File

@@ -0,0 +1,20 @@
{
my $ksez = $Koala_Say;
my $line = '-' x length $ksez;
$OUT = <<KOALA_SEZ;
$line
< $ksez >
$line
KOALA_SEZ
}
\
\ .
___ //
\{~._.~\}//
( Y )K/
()~*~()
(_)-(_)
Luke
Skywalker
koala

View File

@@ -0,0 +1,3 @@
# This is the beginning of the beginning
# { keys %$confref == 1 && exists $confref->{Koala_Say}
? "confref ok" : "confref not ok" }

View File

@@ -0,0 +1 @@
# This is the end, My only friend, the end of our elaborate templates, the end

View File

@@ -0,0 +1,20 @@
{
my $ksez = $Koala_Say;
my $line = '-' x length $ksez;
$OUT = <<KOALA_SEZ;
$line
< $ksez >
$line
KOALA_SEZ
}
\
\ .
___ //
\{~._.~\}//
( Y )K/
()~*~()
(_)-(_)
Luke
Skywalker
koala

View File

@@ -0,0 +1 @@
# This is the end, My only friend, the end of our elaborate templates, the end

View File

@@ -0,0 +1,9 @@
{ '$DB ok' if defined $DB && $DB->isa('esmith::ConfigDB') }
{ my $ok = 1;
foreach my $rec ($DB->get_all) {
my $key = $rec->key;
my $type = $rec->props <= 1 ? "SCALAR" : "HASH";
$ok = 0 unless *{$key}{$type};
}
'default vars ok' if $ok;
}

View File

@@ -0,0 +1,7 @@
{ if( *{confref}{SCALAR} ) {
"confref not defined";
} else {
"confref defined"
}
}

View File

@@ -0,0 +1,10 @@
Chapter 1
The story so far:
In the beginning the Universe was created. This has made a lot
of people very angry and been widely regarded as a bad move.
-- { # Testing MORE_DATA
$Author
}

View File

@@ -0,0 +1,2 @@
The end of labor is to gain leisure.

View File

@@ -0,0 +1,112 @@
# This file stores uid/gid information from the CreatingSystemUsers topic of
# the Engineering Wiki. It is read by the uidgid.t test script. Please keep it
# up to date.
[passwd]
0 root 0
1 bin 1
2 daemon 2
3 adm 4
4 lp 7
8 mail 12
9 news 13
10 uucp 14
11 operator 0
12 games 100
13 gopher 30
14 ftp 50
23 squid 23
27 mysql 27
32 rpc 32
37 rpm 37
38 ntp 38
48 apache 48
53 dns 53
55 ldap 55
69 vcsa 69
74 sshd 74
77 pcap 77
99 nobody 99
100 www 101
101 admin 101
102 public 103
400 alias 400
401 qmaild 400
402 qmaill 400
403 qmailp 400
404 qmailq 401
405 qmailr 401
406 qmails 401
407 qmailscan 407
408 jabber 408
410 dnscache 410
411 dnslog 411
420 nutups 420
421 trend 421
422 fax 422
451 stunnel 451
452 memtestlog 452
1001 imaplog 1001
1002 smelog 1002
1003 cvmlog 1003
1004 mn_dvr 1004
1005 spamd 1005
2999 smelastsys 2999
[group]
0 root
1 bin
2 daemon
3 sys
4 adm
5 tty
6 disk
7 lp
8 mem
9 kmem
10 wheel
12 mail
13 news
14 uucp
15 man
19 floppy
20 games
21 slocate
22 utmp
23 squid
27 mysql
30 gopher
32 rpc
37 rpm
38 ntp
40 dip
48 apache
50 ftp
53 dns
54 lock
55 ldap
69 vcsa
74 sshd
77 pcap
99 nobody
100 users
101 admin
102 www
103 public
400 nofiles
401 qmail
407 qmailscan
408 jabber
410 dnscache
411 dnslog
420 nutups
421 trend
422 fax
451 stunnel
452 memtestlog
500 shared
1001 imaplog
1002 smelog
1003 cvmlog
1004 mn_dvr
1005 spamd
2999 smelastsys

View File

@@ -0,0 +1,78 @@
#!/usr/bin/perl -w
# vim: ft=perl:
use strict;
use Test::More 'no_plan';
use Unix::PasswdFile;
use Unix::GroupFile;
use constant TRUE => 1;
use constant FALSE => 0;
my $conffile = 'uidgid.conf';
exit 1 if not -e $conffile;
my %passwdlist = ();
my %grouplist = ();
my $passwd = FALSE;
my $group = FALSE;
open(CONF, "<$conffile") or die "Can't open $conffile: $!\n";
while(<CONF>)
{
next if /^(#|\s)/;
if (/\[passwd]/)
{
$passwd = TRUE;
next;
}
elsif (/\[group]/)
{
$group = TRUE;
$passwd = FALSE;
next;
}
next if not $passwd and not $group;
if ($passwd)
{
my ($uid, $name, $gid) = split;
$passwdlist{$name}{uid} = $uid;
$passwdlist{$name}{gid} = $gid;
}
elsif ($group)
{
my ($gid, $name) = split;
$grouplist{$name} = $gid;
}
}
close(CONF);
# We can now confirm the uid and gid of every user, and the gid of every
# group, on the system.
# I don't know of a good way to query every user on the system, so for now
# lets just read them from the passwd file.
my $pw = Unix::PasswdFile->new('/etc/passwd', mode => 'r')
or die "Can't open /etc/passwd: $!\n";
foreach my $user ($pw->users)
{
my ($name,$passwd,$uid,$gid,undef) = getpwnam($user);
ok( exists $passwdlist{$name}, "user $name is on our list" );
ok( $uid == $passwdlist{$name}{uid}, "user $name has uid of $uid" );
ok( $gid == $passwdlist{$name}{gid}, "user $name has gid of $gid" );
}
my $gr = Unix::GroupFile->new('/etc/group', mode => 'r')
or die "Can't open /etc/group: $!\n";
foreach my $group ($gr->groups)
{
my ($name,$passwd,$gid,$members) = getgrnam($group);
ok( exists $grouplist{$name}, "group $name is on our list" );
ok( $gid == $grouplist{$name}, "group $group has gid of $gid" );
}
exit 0;