Chemistry-Harmonia

 view release on metacpan or  search on metacpan

Changes  view on Meta::CPAN


0.118  2013-05-18
	- Fixed the subroutine prepare_mix() for Perl v5.17.x, v5.18.0 ("Hash randomization")
	- Fixed tests of the subroutine stoichiometry() for Perl v5.17.x, v5.18.0 ("Hash randomization")

0.111  2013-05-18
	- Fixed tests for new subroutine stoichiometry()

0.11  2013-05-17
	- Added new powerfull subroutine stoichiometry()
	- Added new subroutine brutto_formula()
	- Fixed a problem with the 0 for C0, H0, N0, P0 and others to-> {Co CO}, {Ho HO}...
	- Removing of points in late of the formulas
	- Added tests, examples into documentation
	- README revised
	- Refused to use the module Regexp::Common (due to a problem of unpredictable changes. Replaced it a my pure perl code)
	- High-speed optimization
	- Algorithm of OSE recognition is refined
	- Correction and optimization of sub 'good_formula'

0.08  2011-12-05T11:11:11+02:00
    [In sub 'oxidation_state']
	- high-speed optimization in 2 times;
	- algorithm of OSE recognition is refined;
    [Correction and optimization of sub 'good_formula']
	- 1, !, | -> l/I/i for I, Al, Cl, Tl, Li, Bi, Ni, Si
	- Aq, Hq, Mq, Rq, Sq -> Ag, Hg, Mg, Rg, Sg;
	- Q -> O
	- $ -> s
	- And many others optimizations;
	- New tests are added.

0.0777  2011-06-15T22:22:22+02:00
    - add to Makefile.PL modules Test::LongString & Test::Pod

0.07  2011-06-12T22:22:22+02:00
    - 'good_formula' subroutine is added.
    - 'prepare_mix' subroutine is added.
    - 'class_cir_brutto' subroutine is added.
    - 'ttc_reaction' subroutine is added.
    - Protesting over 22,100 unique inorganic reactions.
    - For 'oxidation_state' is considerable refined the algorithm.
    - Protesting over 6,200 well and few know unique inorganic substances.
    - For 'parse_chem_mix' is considerable refined the algorithm.
    - Numerous errors are eliminated and others.
    - The documentation is added.
    - Tests for all subroutines are added and optimized the existing.

MANIFEST  view on Meta::CPAN

Changes
lib/Chemistry/Harmonia.pm
Makefile.PL
MANIFEST			This list of files
README
t/01-oxidation_state.t
t/02-good_formula.t
t/03-parse_chem_mix.t
t/04-prepare_mix.t
t/05-class_cir_brutto.t
t/06-ttc_reaction.t
t/07-stoichiometry.t
t/08-brutto_formula.t

META.yml                                 Module YAML meta-data (added by MakeMaker)
META.json                                Module JSON meta-data (added by MakeMaker)

lib/Chemistry/Harmonia.pm  view on Meta::CPAN

require Exporter;

our @ISA = qw(Exporter);

our %EXPORT_TAGS = ( 'all' => [ qw(
			parse_chem_mix
			prepare_mix
			oxidation_state
			redox_test
			class_cir_brutto
			good_formula
			brutto_formula
			stoichiometry
			ttc_reaction
			) ],
		    'redox' => [ qw(
			parse_chem_mix
			prepare_mix
			oxidation_state
			redox_test
			) ],
		    'equation' => [ qw(
			parse_chem_mix
			prepare_mix
			class_cir_brutto
			good_formula
			brutto_formula
			stoichiometry
			ttc_reaction
			) ],
);

our @EXPORT_OK = ( @{ $EXPORT_TAGS{'all'} } );

our @EXPORT = qw( );

our $VERSION = '0.118';

use base qw(Exporter);


# Returns array of "good" chemical formulas
sub good_formula{
    my $substance = shift || return;
    my $opts = shift;

    for( $substance ){
	my $m = '(?:1|!|\|)';	# mask

	# Replacement by iodine
	s/^(\W*)$m(\d*)$/$1I$2/;
	s/j/I/ig;

lib/Chemistry/Harmonia.pm  view on Meta::CPAN

	    my @cf = ( "\u$_", uc );

	    if( /$mz/ && exists( $opts->{'zero2oxi'} ) ){
		my @a = @cf;
		s/$mz/O/g for @a;
		return [ @cf, @a ];
	    }
	    return \@cf;
	}

	# Normalization of oxide-coated formulas (written through '*')
	if(/\*/){
	    my %k;
	    my $l = 1;
	    for my $i (split /\*/){
		if($i =~ /^(\d+)[a-zA-Z]/){	# Integer coefficient
		    $k{ $1 } = $1;

		}elsif($i =~ /^(\d*\.(\d+))/){ # Fractional coefficient
		    $k{ $1 } = $1;
		    $l *= 10 if length $2 >= length $l;

lib/Chemistry/Harmonia.pm  view on Meta::CPAN

	}
    }

    if( @w ){	# Search by fragments of anchor symbols 
	my $m = join '|', @w;

	for my $f (split /($m)/, $s){

	    &_in_gf($f, \@i_maU, \@i_maUl, $cf);

	    if( $#{$cf} ){ # For >1 formula
		# To leave the longest fragments
		for( my $i = $#$cf; $i > 0; $i-- ){
		    splice @$cf, $i, 1 if length( $cf->[$i] ) < length( $cf->[0] );
		}
	    }
	}
	return 1;
    }

    # Difficult fragment

lib/Chemistry/Harmonia.pm  view on Meta::CPAN

	    'a' => $atoms,
	    'r' => $rank,
	    };
}

# Calculation common identifier for reaction:
#	Alphabetic CLASS
# and
#	Chemical Interger Reaction (CIR) identifier
# also
#	brutto (gross) formulas of substances
sub class_cir_brutto{
    my( $ce, $coef ) = @_;
    $ce || return;

    my( %elm, %bf, @cir );

    for my $c ( @$ce ){
	for my $s ( @$c ){

	    # stoichiometry coefficient
	    my $k = exists $coef->{$s} ? $coef->{$s} : 1; 

	    my %e = Chemistry::File::Formula->parse_formula( $s );

	    # for brutto
	    $bf{ $s } = join '', map( "$_$e{$_}", sort{ $a cmp $b } keys %e );

	    # for cir
	    push @cir, $k.$bf{ $s };

	    # For class
	    @elm{ keys %e } = ''; # reaction atoms
	}
    }

    # CLASS, CIR of reaction and hash: formula => brutto of substances
    return [ join( '', sort { $a cmp $b } keys %elm ),
	     ( cksum( join '+', sort { $a cmp $b } @cir ) )[0],
	     \%bf ];
}


# Transformation substance arrays to chemical mix (equation)
# $ce -- ref to array of substance arrays
# $opts ->{ }	 (facultative parameters)
#	->'substances' -- ref to array of real (required) substances

lib/Chemistry/Harmonia.pm  view on Meta::CPAN

	}
    }

    if( $sign != 0 ){ # chemical mix to brutto-normalize

	# if assume all coefficients positive '+'
	if( $opts->{'norma'} != 1 ){
	    $opts->{'coefficients'}{$_} *= -1 for @{ $ce->[1] };
	}

	my @cir; # for brutto-formula
	while( my($s, $c) = each %{ $opts->{'coefficients'} } ){
	    $c || next;
	    my $ip = $sign * $c > 0 ? 0 : 1;

	    my $ff = abs($c)." $s";

	    my %e = Chemistry::File::Formula->parse_formula( $ff );
	    $cir[$ip]{$ff} = join '', map( "$_$e{$_}", sort{ $a cmp $b} keys %e );
	}
	# Result
	$_ = join(' == ', map{ join ' + ',sort {$_->{$a} cmp $_->{$b}} keys %{$_} } @cir);

    }else{
	if( exists( $opts->{'substances'} ) && @{ $opts->{'substances'} } ){
	    # List of real substances is specified
	    my %bs;
	    @bs{ @{ $opts->{'substances'} } } = ();

lib/Chemistry/Harmonia.pm  view on Meta::CPAN


sub _search_atoms_subs{
    my $chem_eq = shift;

    my %tmp_subs;	# Atoms of substance
    my %atoms;		# Atom hash

    for my $i ( @$chem_eq ){
	for my $s ( @$i ){
	    # Atoms of substance
	    my %f = eval{ Chemistry::File::Formula->parse_formula( $s ) } or
croak("'$s' is not substance!");

	    for( keys %f ){
		$tmp_subs{$s}{$_} = $f{$_};
		$atoms{$_}++; # Atom balance
	    }
	}
    }

    while( my($k,$v) = each %atoms){

lib/Chemistry/Harmonia.pm  view on Meta::CPAN


    # Atom (stoichiometry) matrix vectors (quantity of atoms for each substance)
    my %atoms_substance;
    for my $subs (keys %tmp_subs){
	$atoms_substance{$subs} = [ map { $tmp_subs{$subs}{$_} || 0 } keys %atoms ];
    }

    return( \%atoms_substance, scalar(keys %atoms) );
}

# Transform classic into brutto (gross) formula
sub brutto_formula{
    my $s = shift;

    my %e = eval{ Chemistry::File::Formula->parse_formula( $s ) } or
croak("'$s' is not substance!");

    return( join( '', map{ "$_$e{$_}" } sort { $a cmp $b } keys %e ) );
}

# Decomposes the chemical equation to
# arrays of initial substances and products
sub parse_chem_mix{
    $_ = shift; # List of substances with delimiters (spaces, comma, + )
    my $coef = shift; # hash of coefficients

lib/Chemistry/Harmonia.pm  view on Meta::CPAN

	}
    }

    $r;
}

sub _in_os{
    my $chem_sub = shift;

    # prepare atomic composition of substance
    my %nf = eval{ Chemistry::File::Formula->parse_formula( $chem_sub ) };
    return unless keys %nf;

    # Count of "pure" atoms each element of substance
    $_ = $chem_sub;
    s/\d+//g;	# remove digits
    my %num = Chemistry::File::Formula->parse_formula( $_ );

    # Ions: { element }{ length }{ ion-pattern }[ [ array OSE ] ]
    my $ions = &_read_ions( $chem_sub );

    # Read Pauling electronegativity and OSE:
	# atom electronegativity, oxidation state, intermetallic compound
    my( $atom_el_neg, $atom_OS, $intermet ) = &_read_atoms( \%nf );
    return if keys( %$atom_el_neg ) != keys( %nf );

    my $prop;	# Result:

lib/Chemistry/Harmonia.pm  view on Meta::CPAN

	    if( $num{$e} == 1 ){ # One atom of element in substance
	        push @{ $prop->{$e}{'num'} }, $nf{$e};

	    }else{
		my $count = 0;
		$_ = $chem_sub;

		# Search ion-group. Remove all atoms of element, except current
		s{ ($m) }{ $1 if $count++ == $j }gex;

		my %f = Chemistry::File::Formula->parse_formula( $_ );
		push @{ $prop->{ $e }{'num'} }, $f{ $e };
	    }
	}
    }

    # Two pass: 1st -- ion recognition, 0th -- without ions (possible)
    for my $yni (1, 0){
	my $no_ion = 1;		# no ions

	my $balance_A = 0;	# for Electronic balance

lib/Chemistry/Harmonia.pm  view on Meta::CPAN

		    $ek{$1}[1] = $v; # OSE for group

		    my $n_ek = $#{ $ek{$1}[0] }; # number of element-substitutions
		    $max_n_ek = $n_ek if $n_ek > $max_n_ek; # max list
		}
	    }

	    my $iter = variations_with_repetition( [ (0..$max_n_ek) ], scalar( keys %ek ) );
ELEMENT_MACRO_1:
	    while (my $p = $iter->next) {
		my $m = $frm; # macro-formula (mask)
		my $i = 0;
		for my $em (sort keys %ek){
		    my $e = $ek{ $em }[0][ $p->[$i++] ];	# element
		    next ELEMENT_MACRO_1 unless defined $e; # pattern have ended

		    $m =~ s/$em/$e/g; # Construct ion mask
		}

		next unless $chem_sub =~ /($m)/; # Ions in substance aren't present

lib/Chemistry/Harmonia.pm  view on Meta::CPAN


=head1 NAME

Chemistry::Harmonia - Decision of simple and difficult chemical puzzles.

=head1 SYNOPSIS

  use Chemistry::Harmonia qw( :all );
  use Data::Dumper;

  for my $formula ('Fe3O4', '[Cr(CO(NH2)2)6]4[Cr(CN)6]3'){
    my $ose = oxidation_state( $formula );
    print Dumper $ose;
  }

Will print something like:

  $VAR1 = {
          'O' => {
                  'num' => [ 4 ],
                  'OS' => [ [ -2 ] ]
                 },

lib/Chemistry/Harmonia.pm  view on Meta::CPAN

Preparation of the chemical mix (equation) from reagent and product arrays:

  my $ce = [ [ 'K', 'O2'], [ 'K2O', 'Na2O2', 'K2O2', 'KO2' ] ];
  my $k = { 'K2O' => 1, 'Na2O2' => 0, 'K2O2' => 2, 'KO2' => 3 };
  print prepare_mix( $ce, { 'coefficients' => $k } ),"\n";

Will output:

  K + O2 == 1 K2O + 0 Na2O2 + 2 K2O2 + 3 KO2

'Synthesis' of the good :) chemical formula(s):

  my $abracadabra = 'ggg[crr(cog(nhz2)2)6]4[qcr(cn)5j]3qqq';
  print Dumper good_formula( $abracadabra );

Will output:

  $VAR1 = [
           '[Cr(CO(NH2)2)6]4[Cr(CN)5I]3',
           '[Cr(Co(NH2)2)6]4[Cr(CN)5I]3'
          ];

Calculation CLASS-CIR and brutto (gross) formulas of substances
for reaction. See example:

  my $mix = '2 KMnO4 + 5 H2O2 + 3 H2SO4 --> 1 K2SO4 + 2 MnSO4 + 8 H2O + 5 O2';
  my %cf;
  my $ce = parse_chem_mix( $mix, \%cf );
  print Dumper class_cir_brutto( $ce, \%cf );

Will output:

  $VAR1 = [

lib/Chemistry/Harmonia.pm  view on Meta::CPAN

            'O2' => 'O2',
            'MnSO4' => 'Mn1O4S1',
            'KMnO4' => 'K1Mn1O4',
            'K2SO4' => 'K2O4S1',
            'H2SO4' => 'H2O4S1',
            'H2O2' => 'H2O2',
            'H2O' => 'H2O1'
          }
        ];

Transforms classic chemical formula of substance into the brutto formula:

 print brutto_formula( '[Cr(CO(NH2)2)6]4[Cr(CN)6]3' );

Will output:

  C42Cr7H96N66O24

TTC reaction. Proceeding example above:

  print Dumper ttc_reaction( $ce );

Will output:

lib/Chemistry/Harmonia.pm  view on Meta::CPAN


The module provides the necessary subroutines to solve some puzzles of the
general inorganic and physical chemistry. The methods implemented in this module,
are all oriented to known rules and laws of general and physical chemistry.

=head1 SUBROUTINES

Chemistry::Harmonia provides these subroutines:

    stoichiometry( $mix_of_substances [, \%facultative_parameters ] )
    oxidation_state( $formula_of_substance )
    parse_chem_mix( $mix_of_substances [, \%coefficients ] )
    good_formula( $abracadabra [, { 'zero2oxi' => 1 } ] )
    brutto_formula( $formula_of_substance )
    prepare_mix( \@reactants_and_products [, \%facultative_parameters ] )
    class_cir_brutto( \@reactants_and_products [, \%coefficients ] )
    ttc_reaction( \@reactants_and_products )


All of them are context-sensitive.


=head2 stoichiometry( $mix_of_substances [, \%facultative_parameters ] )

lib/Chemistry/Harmonia.pm  view on Meta::CPAN

        ];

For some mix of substabces solution is able to be very long, so you can use C<'redox_pairs'>.

The C<stoichiometry> protesting for over 24,600 unique inorganic reactions.
Yes, to me it was hard to make it.

Beware use very big C<$mix_of_substances>!


=head2 oxidation_state( $formula_of_substance )

This subroutine returns a hierarchical hash-reference of hash integer 
oxidation state (key 'OS') and hash with the number of atoms for 
each element (key 'num') for the inorganic C<$formula_of_substance>.

Always use the upper case for the first character in the element name
and the lower case for the second character from Periodic Table. Examples: Na,
Ag, Co, Ba, C, O, N, F, etc. Compare: Co - cobalt and CO - carbon monoxide.

For very difficult mysterious formula (usually organic) returns C<undef>.
It will be good if to set, for example, 'Pb3C2O7' and 'Pt2Cl6' as
'{PbCO3}2{PbO}' and '{PtCl2}{PtCl4}'.

If you doesn't know formulas of chemical elements and/or Periodic Table
use subroutine C<good_formula()>.
I insist to do it always anyway :)

Now C<oxidation_state()> is checked for over 6760 unique inorganic substances.


=head2 parse_chem_mix( $mix_of_substances [, \%coefficients ] )

A chemical equation consists of the chemical formulas of the reactants
and products. This subroutine parses C<$mix_of_substances> (usually chemical equation)
to list of the reactants (initial substances) and products
(substances formed in the chemical reaction).
It is the most simple and low-cost way to carry out reaction without
reactants :).

Separator of the reactants from products can be sequence '=', '-' 
together or without one or some '>'. For example: 
=, ==, =>, ==>, ==>>, -, --, ->, -->, ->>> etc.
Spaces round a separator are not essential.
If the separator is not set, last substance of a mix will be a product only.

Each individual substance's chemical formula is separated from others by a plus
sign ('+'), comma (','), semicolon (';') and/or space.
Valid examples:

  print Dumper parse_chem_mix( 'KNO3 + S ; K2SO4 , NO SO2' );

Will print:

  $VAR1 = [
            [ 'KNO3','S','K2SO4','NO' ],
            [ 'SO2' ]

lib/Chemistry/Harmonia.pm  view on Meta::CPAN

  ' = 2Al O'  to-> [ ['=','Al'], ['O'] ], {'Al' => 2}
  '0Al = O2 Al2O3'  to-> [ ['O2'], ['Al2O3'] ]
  '2Al 1 2 3 4 Ca 5 6 Al2O3 7 8 9'  to-> [ ['Al', 'Ca'], ['Al2O3'] ], {'Al2O3' => 56, 'Al' => 2, 'Ca' => 1234}
  '2Al 1 2 3 4 Ca 5 6 Al2O3'  to-> [ ['Al', 'Ca'], ['Al2O3'] ], {'Al2O3' => 56, 'Al' => 2, 'Ca' => 1234}
  '2Al 1 2 3 4 Ca 5 6 = Al2O3'  to-> [ ['Al', 'Ca56'], ['Al2O3'] ], {'Al' => 2, 'Ca56' => 1234}
  '2Al 1 2 3 4 Ca 5 6 = Al2O3 CaO 9'  to-> [ ['Al', 'Ca56'], ['Al2O3', 'CaO'] ], {'Al' => 2, 'Ca56' => 1234}
  'Al O + 2 = Al2O3'  to-> [ ['Al', 'O'], ['Al2O3'] ], {'Al2O3' => 2}
  'Cr( OH )  3 + NaOH = Na3[ Cr( OH )  6  ]'  to-> [ ['Cr(OH)3', 'NaOH'], ['Na3[Cr(OH)6]'] ]


=head2 good_formula( $abracadabra [, { 'zero2oxi' => 1 } ] )

This subroutine parses C<$abracadabra> to array reference of "good" chemical
formula(s). The "good" formula it does NOT mean chemically correct.
The subroutine C<oxidation_state()> will help with a choice chemically
correct formula.

Algorithm basis is the robust sense and chemical experience.

  'Co'   to->  'Co'
  'Cc'   to->  'CC'
  'co'   to->  'CO', 'Co'
  'CO2'  to->  'CO2'
  'Co2'  to->  'Co2', 'CO2'
  'mo2'  to->  'Mo2'

The good formula(s) there are chemical elements, brackets ()[]{} and
digits only. C<good_formula()> love oxygen.
Fraction will be scaled in the integer.

Fragments A*B, xC*yD are transformed to {A}{B}, {C}x{D}y
(here A, B, C, D - groups of chemical elements, digits and brackets ()[]{};
x, y - digits only). Next examples:

  '0.3al2o3*1.5sio2'  to->  '{Al2O3}{SIO2}5', '{Al2O3}{SiO2}5'
  'al2(so4)3*10h20'   to->  '{Al2(SO4)3}{H20}10'
  '..,,..mg0,,,,.*si0...s..,..'  to->  '{MgO}{SIOS}', '{MgO}{SiOS}'

lib/Chemistry/Harmonia.pm  view on Meta::CPAN


  '00O02'  to->  'OOOO2'
  'h02'    to->  'Ho2', 'HO2'

However:

  'h20'    to->  'H20'

The forced conversion of zero to oxygen is set by parameter C<'zero2oxi'>:

  my $chem_formulas = good_formula( 'h20', { 'zero2oxi' => 1 } );

Output C<@$chem_formulas>:

  'H20', 'H2O'

If mode of paranoiac is necessary, then transform C<$abracadabra>
to low case as:

    lc $abracadabra

Beware use very long C<$abracadabra>!


=head2 brutto_formula( $formula_of_substance )

This subroutine transforms classic chemical C<$formula_of_substance> into the brutto (bruta, gross) formula:

 print brutto_formula( '[Cr(CO(NH2)2)6]4[Cr(CN)6]3' );

Output:

  'C42Cr7H96N66O24'

In brutto formula every the chemical element identified through its chemical symbol.
The atom number of every present chemical element in the classic C<$formula_of_substance> indicated 
by the sequebatur number.


=head2 prepare_mix( \@reactants_and_products [, \%facultative_parameters ] )

This subroutine simple but useful. It forms the chemical mix (equation)
from ref to array of arrays C<\@reactants_and_products>,
i.e. is C<parse_chem_mix> antipode.

The following can be  C<\%facultative_parameters>:

lib/Chemistry/Harmonia.pm  view on Meta::CPAN


Will print:

  O2 + 2 K == 1 K2O2 + 0 KO2


=head2 class_cir_brutto( \@reactants_and_products [, \%coefficients ] )

This subroutine calculates Unique Common Identifier of Reaction 
C<\@reactants_and_products> with stoichiometry C<\%coefficients>
and brutto (gross) formulas of substances, i.e ref to array:
0th - alphabetic CLASS, 1th - Chemical Integer Reaction Identifier (CIR),
2th - hash brutto substances.

  my $reaction = '1 H2O + 1 CO2 --> 1 H2CO3';
  my %cf;
  my $ce = parse_chem_mix( $reaction, \%cf );
  print Dumper class_cir_brutto( $ce, \%cf );

Will print

lib/Chemistry/Harmonia.pm  view on Meta::CPAN

Each of the subroutines can be exported on demand, as in

  use Chemistry::Harmonia qw( oxidation_state );

the tag C<redox> exports the subroutines C<oxidation_state>, C<redox_test>,
C<parse_chem_mix> and C<prepare_mix>:

  use Chemistry::Harmonia qw( :redox );

the tag C<equation> exports the subroutines C<stoichiometry>,
C<good_formula>, C<brutto_formula>,
C<parse_chem_mix>, C<prepare_mix>, C<class_cir_brutto> and
C<ttc_reaction>:

  use Chemistry::Harmonia qw( :equation );

and the tag C<all> exports them all:

  use Chemistry::Harmonia qw( :all );


t/02-good_formula.t  view on Meta::CPAN

use strict;
use warnings;

use Test::More 'no_plan';

BEGIN { use_ok('Chemistry::Harmonia') };
use Chemistry::Harmonia qw(:all);

##### Test good_formula() #####

my $dt = &datest;

for my $abracadabra ( keys %$dt ){
    is_deeply( [ sort @{ good_formula( $abracadabra ) } ],
		[ sort @{ $dt->{$abracadabra} }], "good formula test '$abracadabra'" );
}

$dt = { 'h20' => [ 'H20', 'H2O' ],
	'l1202' => ['Li202', 'Li2O2'],
	'a120' => [ 'Al20', 'Al2O' ],
	'a1203' => [ 'Al203', 'Al2O3' ],
	'Si204' => [ 'Si204', 'SI204', 'Si2O4', 'SI2O4' ],
	};

for my $abracadabra ( keys %$dt ){
    is_deeply( [ sort @{ good_formula( $abracadabra, { 'zero2oxi' => 1 } ) } ],
		[ sort @{ $dt->{$abracadabra} }], "good formula option 'zero2oxi'" );
}

exit;

sub datest{
    return {
	'H04' => [ 'Ho4', 'HO4' ],
	'H3P04' => [ 'H3Po4', 'H3PO4' ],
	'H2C03' => [ 'H2Co3', 'H2CO3' ],
	'HN03' => [ 'HNo3', 'HNO3' ],

t/08-brutto_formula.t  view on Meta::CPAN

use strict;
use warnings;

use Test::More 'no_plan';

BEGIN { use_ok('Chemistry::Harmonia') };
use Chemistry::Harmonia qw(:all);

##### Test brutto_formula() #####

my $dt = &datest;

for my $f ( keys %$dt ){
    is_deeply( brutto_formula( $f ), $dt->{ $f }, "gross_formula test '$f'" );
}

exit;

sub datest{
    return {
	'[Cr(CO(NH2)2)6]4[Cr(CN)6]3' => 'C42Cr7H96N66O24',
	'{(NH4)6[MnMo9O32]}{H2O}30' => 'H84Mn1Mo9N6O62',
	'{Pb(CH3COO)2}{H2O}3' => 'C4H12O7Pb1',
    }



( run in 0.282 second using v1.01-cache-2.11-cpan-26ccb49234f )