Просмотр исходного кода

Use MAPM to handle number consts. Fixes #277.

woollybah 8 лет назад
Родитель
Сommit
1e0cd5501f

+ 1 - 0
config.bmx

@@ -31,6 +31,7 @@ Import Pub.zlib
 Import "options.bmx"
 Import "base.stringhelper.bmx"
 Import "base64.bmx"
+Import "mapm/mapm.bmx"
 
 ' debugging help
 Const DEBUG:Int = False

+ 3384 - 3302
expr.bmx

@@ -1,3302 +1,3384 @@
-' Copyright (c) 2013-2017 Bruce A Henderson
-'
-' Based on the public domain Monkey "trans" by Mark Sibly
-'
-' This software is provided 'as-is', without any express or implied
-' warranty. In no event will the authors be held liable for any damages
-' arising from the use of this software.
-'
-' Permission is granted to anyone to use this software for any purpose,
-' including commercial applications, and to alter it and redistribute it
-' freely, subject to the following restrictions:
-'
-'    1. The origin of this software must not be misrepresented; you must not
-'    claim that you wrote the original software. If you use this software
-'    in a product, an acknowledgment in the product documentation would be
-'    appreciated but is not required.
-'
-'    2. Altered source versions must be plainly marked as such, and must not be
-'    misrepresented as being the original software.
-'
-'    3. This notice may not be removed or altered from any source
-'    distribution.
-'
-
-Type TExpr
-	Field exprType:TType
-
-	Method ToString$()
-		Return "<TExpr>"
-	End Method
-
-	Method Copy:TExpr()
-		InternalErr
-	End Method
-
-	Method Semant:TExpr()
-		InternalErr
-	End Method
-
-	Method SemantSet:TExpr( op$,rhs:TExpr )
-		Err ToString()+" cannot be assigned to."
-	End Method
-
-	Method SemantFunc:TExpr( args:TExpr[] , throwError:Int = True, funcCall:Int = False )
-		Err ToString()+" cannot be invoked."
-	End Method
-
-	Method SemantScope:TScopeDecl()
-		Return Null
-	End Method
-
-	Method Eval$()
-		Err ToString()+" cannot be statically evaluated."
-	End Method
-
-	Method EvalConst:TExpr()
-		Local expr:TExpr = New TConstExpr.Create( exprType,Eval() ).Semant()
-		If TStringType(TConstExpr(expr).ty) Then
-			_appInstance.mapStringConsts(TConstExpr(expr).value)
-		End If
-		Return expr
-	End Method
-
-	Method Trans$()
-		Todo
-	End Method
-
-	Method TransStmt$()
-		Return Trans()
-	End Method
-
-	Method TransVar$()
-		InternalErr
-	End Method
-
-	'semant and cast
-	Method SemantAndCast:TExpr( ty:TType,castFlags:Int=0 )
-		Local expr:TExpr=Semant()
-		If expr.exprType.EqualsType( ty ) Return expr
-		Return New TCastExpr.Create( ty,expr,castFlags ).Semant()
-	End Method
-
-	'expr and ty already semanted!
-	Method Cast:TExpr( ty:TType,castFlags:Int=0 )
-		If Not exprType Then
-			Semant()
-		End If
-		If exprType.EqualsType( ty ) Return Self
-		Return New TCastExpr.Create( ty,Self,castFlags ).Semant()
-	End Method
-
-	Method SemantArgs:TExpr[]( args:TExpr[] )
-		args=args[..]
-		For Local i:Int=0 Until args.Length
-			If args[i] Then
-				If TIdentExpr(args[i]) Then
-					TIdentExpr(args[i]).isArg = True
-				End If
-				args[i]=args[i].Semant()
-
-				' if an arg is a invocation without braces, it is *probably* a function pointer.
-				If TInvokeExpr(args[i]) And Not TInvokeExpr(args[i]).invokedWithBraces Then
-					' but not if we've already processed it...
-					If Not (TInvokeExpr(args[i]).decl.attrs & FUNC_PTR) Then
-						TInvokeExpr(args[i]).exprType = New TFunctionPtrType
-						Local cp:TDecl = TInvokeExpr(args[i]).decl
-						cp.Semant
-						TInvokeExpr(args[i]).decl = TFuncDecl(TInvokeExpr(args[i]).decl.Copy(False))
-						TInvokeExpr(args[i]).decl.actual = cp
-						TInvokeExpr(args[i]).decl.attrs :| FUNC_PTR
-						TFunctionPtrType(TInvokeExpr(args[i]).exprType).func = TInvokeExpr(args[i]).decl
-
-						TInvokeExpr(args[i]).decl.semant()
-					End If
-				End If
-				
-			End If
-		Next
-		Return args
-	End Method
-
-	Method CastArgs:TExpr[]( args:TExpr[],funcDecl:TFuncDecl )
-		If args.Length>funcDecl.argDecls.Length Then
-			Err "Too many function parameters"
-		End If
-
-		' FIXME
-		'args=args.Resize( funcDecl.argDecls.Length )
-		' FIXME
-
-		For Local i:Int=0 Until funcDecl.argDecls.Length
-			' ensure funcdecl args are semanted before trying to use them.
-			If Not funcDecl.argDecls[i].IsSemanted() Then
-				funcDecl.argDecls[i].Semant()
-			End If
-
-			If i < args.length And args[i]
-				If TInvokeExpr(args[i]) And Not TInvokeExpr(args[i]).invokedWithBraces Then
-					If Not IsPointerType(funcDecl.argDecls[i].ty, TType.T_BYTE) And Not TFunctionPtrType(funcDecl.argDecls[i].ty) Then
-						Err "Unable to convert from '" + args[i].exprType.ToString() + "()' to '" + funcDecl.argDecls[i].ty.ToString() + "'"
-					End If
-				End If
-
-				If TInvokeMemberExpr(args[i]) And Not TInvokeMemberExpr(args[i]).invokedWithBraces Then
-					If Not IsPointerType(funcDecl.argDecls[i].ty, TType.T_BYTE) And Not TFunctionPtrType(funcDecl.argDecls[i].ty) Then
-						Err "Unable to convert from '" + args[i].exprType.ToString() + "()' to '" + funcDecl.argDecls[i].ty.ToString() + "'"
-					End If
-				End If
-
-				If funcDecl.argDecls[i].ty._flags & TType.T_VAR Then
-
-					If TConstExpr(args[i]) Or TBinaryExpr(args[i]) Or (TIndexExpr(args[i]) And TStringType(TIndexExpr(args[i]).expr.exprType)) Or ..
-							TInvokeExpr(args[i]) Or TInvokeMemberExpr(args[i]) Then
-						Err "Expression for 'Var' parameter must be a variable"
-					End If
-
-					' Passing a "new" object into a Var, requires us to create a local variable and pass its address instead.
-					If TNewObjectExpr(args[i]) Then
-						Local tmp:TLocalDecl=New TLocalDecl.Create( "",TNewObjectExpr(args[i]).ty,args[i],, True )
-						tmp.Semant()
-						Local v:TVarExpr = New TVarExpr.Create( tmp )
-						Local stmt:TExpr = New TStmtExpr.Create( New TDeclStmt.Create( tmp ), v ).Semant()
-						stmt.exprType = TNewObjectExpr(args[i]).ty
-						args[i] = stmt
-					End If
-				End If
-				
-				If (funcDecl.argDecls[i].ty._flags & TType.T_VAR) And Not (funcDecl.argDecls[i].ty.EqualsType(args[i].exprType)) Then
-					If (Not TObjectType(funcDecl.argDecls[i].ty)) Or (TObjectType(funcDecl.argDecls[i].ty) And Not args[i].exprType.ExtendsType(funcDecl.argDecls[i].ty)) Then
-						err "Variable for 'Var' parameter is not of matching type"
-					End If
-				End If
-
-				' re-test auto array for compatible consts.
-				If TArrayExpr(args[i]) And TArrayType(funcDecl.argDecls[i].ty) And TNumericType(TArrayType(funcDecl.argDecls[i].ty).elemType) Then
-					TArrayExpr(args[i]).toType = TArrayType(funcDecl.argDecls[i].ty).elemType
-					args[i].exprType = Null
-					args[i].Semant()
-				End If
-				args[i]=args[i].Cast( funcDecl.argDecls[i].ty )
-			Else If funcDecl.argDecls[i].init
-				If i = args.length Then
-					' extend args to add default init entry
-					args = args[..i + 1]
-				End If
-				args[i]=funcDecl.argDecls[i].init
-			Else
-				Err "Missing function argument '"+funcDecl.argDecls[i].ident+"'."
-			EndIf
-		Next
-		Return args
-	End Method
-
-	Method BalanceTypes:TType( lhs:TType,rhs:TType )
-
-		If TStringType( lhs ) Or TStringType( rhs ) Then
-			If TObjectType(lhs) Or TObjectType(rhs) Then
-				If TObjectType(lhs) And TObjectType(lhs).classDecl.ident = "Object" Then
-					Return lhs
-				End If
-				If TObjectType(rhs) And TObjectType(rhs).classDecl.ident = "Object" Then
-					Return rhs
-				End If
-			Else
-				Return New TStringType
-			End If
-		End If
-		If IsPointerType( lhs, 0, TType.T_POINTER ) Or IsPointerType( rhs, 0, TType.T_POINTER ) Then
-			If IsPointerType( lhs, 0, TType.T_POINTER ) Return lhs
-			If IsPointerType( rhs, 0, TType.T_POINTER ) Return rhs
-		End If
-		If TDouble128Type( lhs ) Or TDouble128Type( rhs ) Return New TDouble128Type
-		If TFloat128Type( lhs ) Or TFloat128Type( rhs ) Return New TFloat128Type
-		If TFloat64Type( lhs ) Or TFloat64Type( rhs ) Return New TFloat64Type
-		If TDoubleType( lhs ) Or TDoubleType( rhs ) Return New TDoubleType
-		If TFloatType( lhs ) Or TFloatType( rhs ) Return New TFloatType
-		If TFunctionPtrType( lhs ) Or TFunctionPtrType( rhs ) Then
-			If TFunctionPtrType( lhs ) Return lhs
-			If TFunctionPtrType( rhs ) Return rhs
-		End If
-		If TInt128Type( lhs ) Or TInt128Type( rhs ) Return New TInt128Type
-		If TULongType( lhs ) Or TULongType( rhs ) Return New TULongType
-		If TSizeTType( lhs ) Or TSizeTType( rhs ) Return New TSizeTType
-		If TWParamType( lhs ) Or TWParamType( rhs ) Return New TWParamType
-		If TLongType( lhs ) And TUIntType( rhs ) Return New TULongType
-		If TUIntType( lhs ) And TLongType( rhs ) Return New TULongType
-		If TLParamType( lhs ) Or TLParamType( rhs ) Return New TLParamType
-		If TLongType( lhs ) Or TLongType( rhs ) Return New TLongType
-		If TUIntType( lhs ) Or TUIntType( rhs ) Return New TUIntType
-		If TIntType( lhs ) Or TIntType( rhs ) Return New TIntType
-		If TObjectType( lhs ) And TNullDecl(TObjectType( lhs ).classDecl) Then
-			Return rhs
-		End If
-		If TObjectType( rhs ) And TNullDecl(TObjectType( rhs ).classDecl) Then
-			Return lhs
-		End If
-		If lhs.ExtendsType( rhs ) Return rhs
-		If rhs.ExtendsType( lhs ) Return lhs
-		' balance arrays - only for objects... to the lowest common denominator.
-		If TArrayType( lhs ) And TArrayType( rhs ) Then
-
-			If TObjectType(TArrayType( lhs ).elemType) And TObjectType(TArrayType( rhs ).elemType) Then
-				' lhs = Object[]
-				If TObjectType(TArrayType( lhs ).elemType).classDecl.ident = "Object" Then
-					Return lhs
-				End If
-				' rhs = Object[]
-				If TObjectType(TArrayType( rhs ).elemType).classDecl.ident = "Object" Then
-					Return rhs
-				End If
-				
-				' does one extend the other? If so, return the base type
-				If TObjectType(TArrayType( lhs ).elemType).ExtendsType(TObjectType(TArrayType( rhs ).elemType)) Then
-					Return rhs
-				End If
-
-				If TObjectType(TArrayType( rhs ).elemType).ExtendsType(TObjectType(TArrayType( lhs ).elemType)) Then
-					Return lhs
-				End If
-				
-				' no? then we will fallback to an Object type array
-				
-				' find the Object classdecl instance
-				Local modid$="brl.classes"
-				Local mdecl:TModuleDecl=_env.FindModuleDecl( modid )
-				' return an array of Objects
-				Return New TArrayType.Create(New TObjectType.Create(TClassDecl(mdecl.FindDecl( "object" ))))
-			End If
-			
-			If TObjectType(TArrayType( lhs ).elemType) And TObjectType(TArrayType( lhs ).elemType).classDecl.ident = "Object" And TStringType(TArrayType( rhs ).elemType) Then
-				Return lhs
-			End If
-
-			If TObjectType(TArrayType( rhs ).elemType) And TObjectType(TArrayType( rhs ).elemType).classDecl.ident = "Object"  And TStringType(TArrayType( lhs ).elemType) Then
-				Return rhs
-			End If
-
-			If TObjectType(TArrayType( lhs ).elemType) And TObjectType(TArrayType( lhs ).elemType).classDecl.ident = "Object"  And TArrayType(TArrayType( rhs ).elemType) Then
-				Return lhs
-			End If
-
-			If TObjectType(TArrayType( rhs ).elemType) And TObjectType(TArrayType( rhs ).elemType).classDecl.ident = "Object"  And TArrayType(TArrayType( lhs ).elemType) Then
-				Return rhs
-			End If
-
-			' balancing primitive types
-			If Not TArrayType( lhs ).elemType.EqualsType(TArrayType( rhs ).elemType) Then
-				Err "Types '" + TArrayType( lhs ).elemType.ToString() + " Array' and '" + TArrayType( rhs ).elemType.ToString() + " Array' are unrelated"
-			End If
-			
-		End If
-		Err "Can't balance types "+lhs.ToString()+" and "+rhs.ToString()+"."
-	End Method
-
-	Function CopyExpr:TExpr( expr:TExpr )
-		If Not expr Return Null
-		Return expr.Copy()
-	End Function
-
-	Function CopyArgs:TExpr[]( exprs:TExpr[] )
-		exprs=exprs[..]
-		For Local i:Int=0 Until exprs.Length
-			exprs[i]=CopyExpr( exprs[i] )
-		Next
-		Return exprs
-	End Function
-
-End Type
-
-'	exec a stmt, return an expr
-Type TStmtExpr Extends TExpr
-	Field stmt:TStmt
-	Field expr:TExpr
-
-	Method Create:TStmtExpr( stmt:TStmt,expr:TExpr )
-		Self.stmt=stmt
-		Self.expr=expr
-		Return Self
-	End Method
-
-	Method Copy:TExpr()
-		If exprType Return Self
-		Return New TStmtExpr.Create( stmt,CopyExpr(expr) )
-	End Method
-
-	Method ToString$()
-		Return "TStmtExpr(,"+expr.ToString()+")"
-	End Method
-
-	Method Semant:TExpr()
-		If exprType Return Self
-
-		stmt.Semant()
-		expr=expr.Semant()
-		exprType=expr.exprType
-		Return Self
-	End Method
-
-	Method Trans$()
-		Return _trans.TransStmtExpr( Self )
-	End Method
-
-	Method TransVar$()
-		Semant
-		Return _trans.TransStmtExpr( Self )
-	End Method
-
-End Type
-
-'	literal
-Type TConstExpr Extends TExpr
-	Field ty:TType
-	Field value$
-	Field originalValue$
-	' True if the const was identified as a specific type.
-	Field typeSpecific:Int
-
-	Method Create:TConstExpr( ty:TType,value$ )
-		originalValue = value
-		
-		If TNumericType( ty ) And IsPointerType(ty, 0, TType.T_POINTER) Then
-			Self.ty=ty
-			If value Then
-				Self.value = value
-			Else
-				Self.value="0"
-			End If
-			Return Self
-		End If
-		
-		If TIntType( ty ) Or TShortType( ty ) Or TByteType( ty ) Or TLongType( ty ) Or TUIntType( ty ) Or TULongType( ty ) Or TWParamType(ty) Or TLParamType(ty)
-			Local radix:Int
-			If value.StartsWith( "%" )
-				radix=1
-			Else If value.StartsWith( "$" )
-				radix=4
-			EndIf
-
-			If radix
-				Local val:Long = 0
-
-				For Local i:Int=1 Until value.Length
-					Local ch:Int=value[i]
-					If ch>=48 And ch<58
-						val=val Shl radix | (ch & 15)
-					Else
-						val=val Shl radix | ((ch & 15)+9)
-					EndIf
-				Next
-				If TIntType(ty) And val >= 2147483648:Long Then
-					value = String( -2147483648:Long + (val - 2147483648:Long))
-				Else
-					If TShortType( ty ) Then
-						value=String( Short(val) )
-					Else If TByteType( ty ) Then
-						value=String( Byte(val) )
-					Else
-						value=String( val )
-					End If
-				End If
-			Else
-				If TShortType( ty ) Then
-					value = String.FromLong(Short(value.ToLong()))
-				Else If TByteType( ty ) Then
-					value = String.FromLong(Byte(value.ToLong()))
-				Else
-					Local buf:Byte[64]
-					Local b:Int
-					Local v:String = value.Trim()
-					Local leading0:Int = True
-					If v Then
-						Local i:Int
-						If v[0] = Asc("+") Then
-							i = 1
-						Else If v[0] = Asc("-") Then
-							i = 1
-							buf[b] = Asc("-")
-							b:+ 1
-						End If
-						
-						While i < value.Length
-							If Not IsDigit(v[i]) Then
-								Exit
-							End If
-							If leading0 And v[i] = Asc("0") Then
-								i :+ 1
-								Continue
-							End If
-							leading0 = False
-							buf[b] = v[i]
-							
-							b :+ 1
-							i :+ 1
-						Wend
-						
-						If leading0 Then
-							value = "0"
-						Else
-							value = String.FromBytes(buf, b)
-						End If
-					Else
-						value = "0"
-					End If
-				End If
-			EndIf
-
-		Else If TDecimalType( ty )
-			If Not (value.Contains("e") Or value.Contains("E") Or value.Contains(".") Or value.Contains("inf") Or value.Contains("nan"))
-				value:+".0"
-			EndIf
-		EndIf
-		Self.ty=ty
-		Self.value=value
-		Return Self
-	End Method
-	
-	Method UpdateType(ty:TType)
-		typeSpecific = True
-		Create(ty, originalValue)
-	End Method
-
-	Method Copy:TExpr()
-		Local e:TConstExpr = New TConstExpr.Create( ty,value )
-		e.originalValue = originalValue
-		e.typeSpecific = typeSpecific
-		Return e
-	End Method
-
-	Method ToString$()
-		Return "TConstExpr(~q"+value+"~q)"
-	End Method
-
-	Method Semant:TExpr()
-		If exprType Return Self
-
-		exprType=ty.Semant()
-		Return Self
-	End Method
-
-	Method Eval$()
-		Return value
-	End Method
-
-	Method EvalConst:TExpr()
-		Return Self
-	End Method
-
-	Method Trans$()
-		Semant
-		Return _trans.TransConstExpr( Self )
-	End Method
-
-	Method SemantAndCast:TExpr( ty:TType,castFlags:Int=0 )
-		Local expr:TExpr=Semant()
-		If expr.exprType.EqualsType( ty ) Return expr
-		If value = "bbNullObject" Then
-			Err "bbNullObject"
-			Return expr
-		End If
-		Return New TCastExpr.Create( ty,expr,castFlags ).Semant()
-	End Method
-	
-	Method CompatibleWithType:Int(ty:TType)
-		If Not TDecimalType(ty) Then
-			If value.Contains("e") Or value.Contains("E") Or value.Contains(".") Or value.Contains("inf") Or value.Contains("nan") Then
-				Return False
-			End If
-			
-			Local val:Long = value.ToLong()
-			
-			If val < 0 Then
-				If TByteType(ty) Or TShortType(ty) Or TUIntType(ty) Or TULongType(ty) Or TSizeTType(ty) Or TInt128Type(ty) Or TWParamType(ty) Then
-					Return False
-				End If
-			Else
-				If TByteType(ty) Then
-					If value <> String.FromInt(Byte(Val)) Then
-						Return False
-					End If
-				End If
-
-				If TUIntType(ty) Or ((TSizeTType(ty) Or TWParamType(ty)) And WORD_SIZE = 4) Then
-					If val > 4294967296:Long Then
-						Return False
-					End If
-				End If
-				
-				If TULongType(ty) Or ((TSizeTType(ty) Or TWParamType(ty)) And WORD_SIZE = 8) Then
-					If value.length > 20 Then
-						Return False
-					Else If value.length = 20 Then
-						For Local i:Int = 0 Until value.length
-							Local v:Int = value[i]
-							Local n:Int = "18446744073709551616"[i]
-							If v < n Then
-								Exit 
-							Else If v > n Then
-								Return False
-							End If
-						Next
-					End If
-				End If
-			End If
-			
-			If TShortType(ty) Then
-				If value <> String.FromInt(Short(val)) Then
-					Return False
-				End If
-			End If
-
-			If TIntType(ty) Or (TLParamType(ty) And WORD_SIZE = 4) Then
-				If value <> String.FromInt(Int(val)) Then
-					Return False
-				End If
-			End If
-
-			If TLongType(ty) Or (TLParamType(ty) And WORD_SIZE = 8) Then
-				If value <> String.FromLong(Long(val)) Then
-					Return False
-				End If
-			End If
-			
-		End If
-		
-		Return True
-	End Method
-
-End Type
-
-Type TVarExpr Extends TExpr
-	Field decl:TVarDecl
-
-	Method Create:TVarExpr( decl:TVarDecl )
-		Self.decl=decl
-		Return Self
-	End Method
-
-	Method Copy:TExpr()
-		Return Self
-	End Method
-
-	Method ToString$()
-		Return "TVarExpr("+decl.ToString()+")"
-	End Method
-
-	Method Semant:TExpr()
-		If exprType Return Self
-		If Not decl.IsSemanted() InternalErr
-		exprType=decl.ty
-		Return Self
-	End Method
-
-	Method SemantSet:TExpr( op$,rhs:TExpr )
-		Return Semant()
-	End Method
-
-	Method Trans$()
-		Semant
-		Return _trans.TransTemplateCast( exprType,TVarDecl(decl.actual).ty,_trans.TransVarExpr( Self ) )
-	End Method
-
-	Method TransVar$()
-		Semant
-		Return _trans.TransVarExpr( Self )
-	End Method
-
-End Type
-
-Type TMemberVarExpr Extends TExpr
-	Field expr:TExpr
-	Field decl:TVarDecl
-
-	Method Create:TMemberVarExpr( expr:TExpr,decl:TVarDecl )
-		Self.expr=expr
-		Self.decl=decl
-		Return Self
-	End Method
-
-	Method Copy:TExpr()
-		Return Self
-	End Method
-
-	Method ToString$()
-		Return "TMemberVarExpr("+expr.ToString()+","+decl.ToString()+")"
-	End Method
-
-	Method Semant:TExpr()
-		If exprType Return Self
-		If Not decl.IsSemanted() InternalErr
-		exprType=decl.ty
-		Return Self
-	End Method
-
-	Method SemantSet:TExpr( op$,rhs:TExpr )
-		Return Semant()
-	End Method
-
-	Method Trans$()
-		Return _trans.TransTemplateCast( exprType,TVarDecl(decl.actual).ty,_trans.TransMemberVarExpr( Self ) )
-	End Method
-
-	Method TransVar$()
-		Return _trans.TransMemberVarExpr( Self )
- 	End Method
-
-End Type
-
-Type TInvokeExpr Extends TExpr
-	Field decl:TFuncDecl
-	Field args:TExpr[]
-	Field invokedWithBraces:Int
-	Field isArg:Int
-	Field isRhs:Int
-
-	Method Create:TInvokeExpr( decl:TFuncDecl,args:TExpr[]=Null,invokedWithBraces:Int=True, isArg:Int=False, isRhs:Int = False )
-		Self.decl=decl
-		If args Then
-			Self.args=args
-		Else
-			Self.args = New TExpr[0]
-		End If
-		Self.invokedWithBraces = invokedWithBraces
-		Self.isArg = isArg
-		Self.isRhs = isRhs
-		Return Self
-	End Method
-
-	Method Copy:TExpr()
-		Return Self
-	End Method
-
-	Method ToString$()
-		Local t$="TInvokeExpr("+decl.ToString()
-		For Local arg:TExpr=EachIn args
-			t:+","+arg.ToString()
-		Next
-		Return t+")"
-	End Method
-
-	Method Semant:TExpr()
-
-		If exprType Return Self
-
-		If Not decl.retType
-			decl.Semant()
-		End If
-		'If TIdentType(decl.retType) Then
-			exprType = decl.retType.Semant()
-		'Else
-		'	exprType=decl.retType
-		'End If
-
-		'If ((isArg Or isRhs) And Not invokedWithBraces) And (args = Null Or args.length = 0) Then
-
-		' if the call was a statement (even one written without parentheses), then invokedWithBraces is true
-		' so no complicated checks are needed here; if invokedWithBraces is false, this is definitely not a call
-		If Not invokedWithBraces Then
-			' nothing to do here, as we are a function pointer. i.e. no braces
-			' and our expression type is a function ptr...
-			exprType = New TFunctionPtrType.Create(decl)
-			
-		Else
-			args=CastArgs( args,decl )
-		End If
-		Return Self
-	End Method
-
-	Method Trans$()
-'		Return _trans.TransTemplateCast( exprType,TFuncDecl(decl.actual).retType,_trans.TransInvokeExpr( Self ) )
-		Return _trans.TransInvokeExpr( Self )
-	End Method
-
-	Method TransStmt$()
-		Return _trans.TransInvokeExpr( Self )
-	End Method
-
-	Method Eval$()
-		Return Super.Eval()
-	End Method
-
-End Type
-
-Type TInvokeMemberExpr Extends TExpr
-	Field expr:TExpr
-	Field decl:TFuncDecl
-	Field args:TExpr[]
-	Field isResize:Int	'FIXME - butt ugly!
-	Field invokedWithBraces:Int
-
-	Method Create:TInvokeMemberExpr( expr:TExpr,decl:TFuncDecl,args:TExpr[]=Null, invokedWithBraces:Int = True )
-		Self.expr=expr
-		Self.decl=decl
-		If args
-			Self.args=args
-		Else
-			Self.args = New TExpr[0]
-		End If
-		Self.invokedWithBraces = invokedWithBraces
-		Return Self
-	End Method
-
-	Method Copy:TExpr()
-		Return Self
-	End Method
-
-	Method ToString$()
-		Local t$="TInvokeMemberExpr("+expr.ToString()+","+decl.ToString()
-		For Local arg:TExpr=EachIn args
-			t:+","+arg.ToString()
-		Next
-		Return t+")"
-	End Method
-
-	Method Semant:TExpr()
-		If exprType Return Self
-
-		If Not decl.IsSemanted() decl.Semant()
-		exprType=decl.retType
-
-		args=SemantArgs( args )
-		args=CastArgs( args,decl )
-
-		'Array $resize hack!
-		If TArrayType( exprType ) And TVoidType( TArrayType( exprType ).elemType )
-			isResize=True
-			exprType=expr.exprType
-		EndIf
-
-		Return Self
-	End Method
-
-	Method Trans$()
-		'Array $resize hack!
-		If isResize Return _trans.TransInvokeMemberExpr( Self )
-
-		Return _trans.TransTemplateCast( exprType,TFuncDecl(decl.actual).retType,_trans.TransInvokeMemberExpr( Self ) )
-	End Method
-
-	Method TransStmt$()
-		Return _trans.TransInvokeMemberExpr( Self )
-	End Method
-
-End Type
-
-Type TNewObjectExpr Extends TExpr
-	Field ty:TType
-	Field args:TExpr[]
-	Field ctor:TFuncDecl
-	Field classDecl:TClassDecl
-	Field instanceExpr:TExpr
-
-	Method Create:TNewObjectExpr( ty:TType,args:TExpr[] )
-		Self.ty=ty
-		Self.args=args
-		Return Self
-	End Method
-
-	Method Copy:TExpr()
-		Return New TNewObjectExpr.Create( ty,CopyArgs(args) )
-	End Method
-
-	Method Semant:TExpr()
-		If exprType Return Self
-
-		Local it:TIdentType = TIdentType(ty)
-		Local iArgs:TExpr[] = SemantArgs(CopyArgs(args))
-
-		ty=ty.Semant(True)
-		If Not ty Then
-			' maybe it's an instance of a type ?
-			Local decl:TVarDecl = TVarDecl(_env.FindDecl(it.ident))
-			If decl And TObjectType(decl.ty) Then
-				ty = decl.ty
-				instanceExpr = New TVarExpr.Create(decl).Semant()
-			Else
-				Err "Type '"+it.ident+"' not found"
-			End If
-		End If
-		args=SemantArgs( args )
-
-		Local objTy:TObjectType=TObjectType( ty )
-		Local clsTy:TClassType=TClassType( ty )
-		If Not objTy And Not clsTy
-			Err "Expression is not a class."
-		EndIf
-		
-		' 
-		If clsTy And clsTy.instance Then
-			instanceExpr = New TSelfExpr.Semant()
-		End If
-
-		If objTy Then
-			classDecl=objTy.classDecl
-		Else
-			classDecl=clsTy.classDecl
-		End If
-
-		If Not instanceExpr Then
-			If classDecl.IsInterface() Err "Cannot create instance of an interface."
-			If classDecl.IsAbstract() Err "Cannot create instance of an abstract class."
-		End If
-		'If classDecl.IsTemplateArg() Err "Cannot create instance of a generic argument."
-		If classDecl.args And Not classDecl.instanceof Err "Cannot create instance of a generic class."
-
-		Local parts:String[]
-		If it Then
-			parts = it.ident.ToLower().Split(".")
-		End If
-
-		If classDecl.IsExtern()
-			Err "Cannot create instance of an extern type"
-			'If args Err "No suitable constructor found for class "+classDecl.ToString()+"."
-		Else
-			' if the New Type doesn't have extra idents (like a create method), then don't use the args in the search.
-			' otherwise, the args are for the constructor.
-			If Not parts Or parts.length = 1 Then
-				ctor=classDecl.FindFuncDecl( "new",args,,,,,SCOPE_CLASS_HEIRARCHY )
-				If Not ctor	Err "No suitable constructor found for class "+classDecl.ToString()+"."
-				args=CastArgs( args,ctor )
-			Else
-				ctor=classDecl.FindFuncDecl( "new",,,,,,SCOPE_CLASS_HEIRARCHY )
-				If Not ctor	Err "No suitable constructor found for class "+classDecl.ToString()+"."
-			End If
-		EndIf
-
-		classDecl.attrs:|CLASS_INSTANCED
-
-		If TClassType(ty) Then
-			exprType=New TObjectType.Create(TClassType(ty).classDecl)
-		Else
-			exprType=ty
-		End If
-		
-		If it Then
-			'Local parts:String[] = it.ident.ToLower().Split(".")
-
-			Local i:Int = 0
-			
-			While i < parts.length And parts[i] <> classDecl.IdentLower() And parts[i] <> "self"
-				i :+ 1
-			Wend
-			
-			i :+ 1
-
-			Local expr:TExpr = Self
-			Local cdecl:TClassDecl = classDecl
-			Local eType:TType = ty
-			
-			Local errorDetails:String
-
-			While i < parts.length
-				Local id:String = parts[i]
-				i :+ 1
-				
-				' find member function.method
-				Local fdecl:TFuncDecl
-				Try
-					fdecl = cdecl.FindFuncDecl(id, iArgs,,,,True,SCOPE_CLASS_HEIRARCHY)
-				Catch errorMessage:String
-					If errorMessage.StartsWith("Compile Error") Then
-						Throw errorMessage
-					Else
-						' couldn't find an exact match, look elsewhere
-						If errorMessage.StartsWith("Unable") Then
-							errorDetails = errorMessage
-						End If
-					End If
-				End Try
-				If fdecl Then
-					expr = New TInvokeMemberExpr.Create( expr,fdecl, iArgs ).Semant()
-					eType = expr.exprType
-					If TObjectType(eType) Then
-						cdecl = TObjectType(expr.exprType).classdecl
-					End If
-					If TArrayType(eType) Or TStringType(eType) Then
-						cdecl = eType.GetClass()
-					End If
-					Continue
-				End If
-				
-				' find other member decl (field, etc)
-				If Not errorDetails Then
-					Local decl:TValDecl = TValDecl(cdecl.GetDecl(id))
-					If TVarDecl(decl) Then
-						Local tmp:TLocalDecl=New TLocalDecl.Create( "", eType, expr,, True )
-						Local varExpr:TExpr = New TMemberVarExpr.Create(New TVarExpr.Create( tmp ), TVarDecl(decl)).Semant()
-						expr = New TStmtExpr.Create( New TDeclStmt.Create( tmp ), varExpr ).Semant()
-						eType = decl.ty
-						If TObjectType(eType) Then
-							cdecl = TObjectType(expr.exprType).classdecl
-						End If
-						If TArrayType(eType) Or TStringType(eType) Then
-							cdecl = eType.GetClass()
-						End If
-						Continue
-					End If
-					If TConstDecl(decl) Then
-						decl.Semant()
-						expr = New TConstExpr.Create(decl.ty, TConstDecl(decl).value).Semant()
-						eType = decl.ty
-						Continue
-					End If
-				End If	
-
-				' didn't match member or function??
-				' probably an error...
-				If errorDetails Then
-					Err errorDetails
-				Else
-					Err "Identifier '" + id + "' not found."
-				End If
-			Wend
-			
-			Return expr
-		End If
-
-		Return Self
-	End Method
-
-	Method Trans$()
-		Return _trans.TransNewObjectExpr( Self )
-	End Method
-End Type
-
-Type TNewArrayExpr Extends TExpr
-	Field ty:TType
-
-	Field expr:TExpr[]
-	
-	Method Create:TNewArrayExpr( ty:TType,expr:TExpr[] )
-
-		Self.ty=ty
-		Self.expr=expr
-		Return Self
-	End Method
-
-	Method Copy:TExpr()
-		If exprType InternalErr
-		Local cexpr:TExpr[expr.length]
-		For Local i:Int = 0 Until expr.length
-			cexpr[i] = CopyExpr(expr[i])
-		Next
-		Return New TNewArrayExpr.Create( ty,cexpr )
-	End Method
-
-	Method Semant:TExpr()
-		If exprType Return Self
-
-		ty=ty.Semant()
-		exprType=New TArrayType.Create( ty, expr.length )
-		For Local i:Int = 0 Until expr.length
-			expr[i]=expr[i].SemantAndCast( New TIntType )
-		Next
-		Return Self
-	End Method
-
-	Method Trans$()
-		Return _trans.TransNewArrayExpr( Self )
-	End Method
-
-End Type
-
-'	super.ident( args )
-Type TInvokeSuperExpr Extends TExpr
-	Field ident$
-	Field args:TExpr[]
-	Field origFuncDecl:TFuncDecl
-	Field funcDecl:TFuncDecl
-	Field classScope:TClassDecl
-	Field superClass:TClassDecl
-	
-	Field _identLower:String
-
-	Method Create:TInvokeSuperExpr( ident$,args:TExpr[] = Null, _identLower:String = Null )
-		Self.ident=ident
-		If args Then
-			Self.args=args
-		Else
-			Self.args = New TExpr[0]
-		End If
-		Self._identLower = _identLower
-		Return Self
-	End Method
-
-	Method IdentLower:String()
-		If Not _identLower Then
-			_identLower = ident.ToLower()
-		End If
-		Return _identLower
-	End Method
-
-	Method Copy:TExpr()
-		Return New TInvokeSuperExpr.Create( ident,CopyArgs(args), _identLower )
-	End Method
-
-	Method Semant:TExpr()
-		If exprType Return Self
-
-		'If _env.FuncScope().IsStatic() Err "Illegal use of Super."
-
-		classScope=_env.ClassScope()
-		superClass=classScope.superClass
-		
-		If Not superClass Err "Type has no super class."
-		
-		args=SemantArgs( args )
-		Try
-			' get the local version of the method from local class scope
-			origFuncDecl=classScope.FindFuncDecl(IdentLower(),args,,,,True,SCOPE_CLASS_LOCAL)
-		Catch errorMessage:String
-			If errorMessage.StartsWith("Compile Error") Then
-				Throw errorMessage
-			Else
-				' if there isn't one, we'll just use a Super version of it anyway as a reference.
-				origFuncDecl=classScope.FindFuncDecl(IdentLower(),args,,,,,SCOPE_CLASS_HEIRARCHY)
-			End If
-		End Try
-
-		funcDecl=superClass.FindFuncDecl( IdentLower(),args,,,,,SCOPE_CLASS_HEIRARCHY )
-
-		If Not funcDecl Err "Can't find superclass method '"+ident+"'."
-
-		' ensure the super function has been semanted
-		funcDecl.Semant()
-		
-		' for static scope, we need to change class scope to that of the super class
-		If _env.FuncScope().IsStatic() Then
-			classScope = TClassDecl(funcDecl.scope)
-		End If
-		
-		args=CastArgs( args,funcDecl )
-		exprType=funcDecl.retType
-		Return Self
-	End Method
-
-	Method Trans$()
-		Return _trans.TransInvokeSuperExpr( Self )
-	End Method
-
-End Type
-
-'	Self
-Type TSelfExpr Extends TExpr
-
-	Method Copy:TExpr()
-		Return New TSelfExpr
-	End Method
-
-	Method Semant:TExpr()
-		If exprType Return Self
-
-		'If _env.FuncScope().IsStatic() Err "Illegal use of Self within static scope."
-		Local scope:TClassDecl = _env.ClassScope()
-		If Not scope Then
-			Err "'Self' can only be used within methods."
-		End If
-		
-		Local funcScope:TFuncDecl = _env.FuncScope()
-		If funcScope.IsAnyMethod() Then
-			exprType=New TObjectType.Create( scope )
-			TObjectType(exprType).instance = True
-		Else
-			exprType=New TClassType.Create( scope )
-		End If
-
-		Return Self
-	End Method
-
-	Method Trans$()
-		Return _trans.TransSelfExpr( Self )
-	End Method
-
-End Type
-
-Const CAST_EXPLICIT:Int=1
-
-Type TCastExpr Extends TExpr
-	Field ty:TType
-	Field expr:TExpr
-	Field flags:Int
-
-	Method Create:TCastExpr( ty:TType,expr:TExpr,flags:Int=0 )
-		Self.ty=ty
-		Self.expr=expr
-		Self.flags=flags
-		Return Self
-	End Method
-
-	Method Copy:TExpr()
-		Return New TCastExpr.Create( ty,CopyExpr(expr),flags )
-	End Method
-
-	Method Semant:TExpr()
-
-		If exprType Return Self
-
-		ty=ty.Semant()
-		
-		If TInvokeExpr(expr) Then
-			TInvokeExpr(expr).isRhs = True
-		Else If TIdentExpr(expr) Then
-			TIdentExpr(expr).isRhs = True
-		End If
-		
-		expr=expr.Semant()
-
-		Local src:TType=expr.exprType
-		
-		'equal?
-		If src.EqualsType( ty ) Return expr
-
-		'upcast?
-		If src.ExtendsType( ty )
-			'cast from void[] to T[]
-			If TArrayType(src) And TVoidType( TArrayType(src).elemType )
-				Return New TConstExpr.Create( ty,"" ).Semant()
-			EndIf
-			
-			If src._flags & TType.T_VARPTR Then
-				exprType = ty
-				Return Self
-			End If
-
-			If TStringType(ty) And TObjectType(src)
-				' only if explicitly cast
-				If flags & CAST_EXPLICIT Then
-					exprType = ty
-					'Return Self
-				End If
-			End If
-			'Box/unbox?...
-			'If TObjectType( ty ) And Not TObjectType( src )
-
-				'Box!
-			'	expr=New TNewObjectExpr.Create( ty,[expr] ).Semant()
-
-			'Else
-			If TObjectType( src ) And Not TObjectType( ty ) And Not TStringType( ty )
-
-				'Unbox!
-				Local op$
-				'If TBoolType( ty )
-				'	op="ToBool"
-				'Else
-				If TIntType( ty )
-					op="ToInt"
-				Else If TFloatType( ty )
-					op="ToFloat"
-				Else If TStringType( ty )
-					op="ToString"
-				Else If IsPointerType(ty, 0, TType.T_POINTER)
-					exprType = ty
-					If flags = CAST_EXPLICIT Then
-						Return Self
-					Else
-						If Not TObjectType( src ).classDecl.IsExtern() Then
-							Return Self
-						Else
-							Return expr
-						End If
-					End If
-				Else
-					InternalErr
-				EndIf
-				Local fdecl:TFuncDecl=src.GetClass().FindFuncDecl( op,,,,,,SCOPE_ALL )
-				expr=New TInvokeMemberExpr.Create( expr,fdecl ).Semant()
-
-			EndIf
-			
-			If TNullType(src) Then
-				exprType = ty
-			End If
-			
-			If TBoolType(src) And (TNumericType(ty) Or TStringType(ty)) Then
-				exprType = ty
-			End If
-			
-			If TNumericType(src) And (TNumericType(ty) Or TStringType(ty)) Then
-				' intrinsics can only cast between selves
-				If (TIntrinsicType(src) And TIntrinsicType(ty)=Null) Or (TIntrinsicType(ty) And TIntrinsicType(src)=Null) Then
-					If TFloat64Type(src) Or TFloat64Type(ty) Then
-						If (TFloat64Type(src) And (TLongType(ty) Or TULongType(ty))) Or (TFloat64Type(ty) And (TLongType(src) Or TULongType(src))) Then
-							' ok
-						Else
-							Err "Unable to convert from "+src.ToString()+" to "+ty.ToString()+"."
-						End If
-					Else
-						Err "Unable to convert from "+src.ToString()+" to "+ty.ToString()+"."
-					End If
-				Else If TIntrinsicType(src) And TIntrinsicType(ty) Then
-					If (TFloat64Type(src) And TFloat64Type(ty)=Null) Or (TFloat64Type(ty) And TFloat64Type(src)=Null) Then
-						Err "Unable to convert from "+src.ToString()+" to "+ty.ToString()+"."
-					End If
-				End If
-				exprType = ty
-			End If
-			
-			If TObjectType(ty) And (TObjectType(src) Or TStringType(src) Or TArrayType(src)) Then
-				exprType = ty
-				Return Self
-			End If
-			
-			If TFunctionPtrType(src) And IsPointerType(ty, 0, TType.T_POINTER) Then
-				exprType = ty
-			End If
-
-		Else If TBoolType( ty )
-
-			If TVoidType( src )
-				Err "Cannot convert from Void to Int."
-			EndIf
-
-			If  flags & CAST_EXPLICIT
-				exprType=ty
-			EndIf
-
-		Else If ty.ExtendsType( src )
-
-			If flags & CAST_EXPLICIT
-
-				'if both objects or both non-objects...
-				If (TObjectType(ty)<>Null)=(TObjectType(src)<>Null) Then
-					exprType=ty
-					
-					If TFunctionPtrType(ty) And TInvokeExpr(expr) And Not TInvokeExpr(expr).invokedWithBraces Then
-						Return expr
-					End If
-					
-					Return Self
-				End If
-				
-				If (TStringType(ty) Or TArrayType(ty)) And TObjectType(src) Then
-					exprType=ty
-					Return Self
-				End If
-			'Else ' if not explicitly cast, we can't just auto-cast it ourselves here.
-				'If (TObjectType(ty)<>Null) And (TObjectType(src)<>Null) exprType=ty
-			EndIf
-
-		EndIf
-
-
-		If TArrayType(ty) And TArrayType(src) Then
-			If TArrayType(ty).dims = TArrayType(src).dims Then
-				If TArrayExpr(expr) Then
-					Local last:TType
-					For Local e:TExpr = EachIn TArrayExpr(expr).exprs
-						If TNullType(e.exprType) Then
-							Err "Auto array element has no type"
-						End If
-
-						If TObjectType(TArrayType(ty).elemType) And TObjectType(TArrayType(ty).elemType).classDecl.ident = "Object" And (TStringType(e.exprType) Or TObjectType(e.exprType) Or TArrayType(e.exprType)) Then
-							' array takes generic objects, so we don't care if source elements are the same kinds.
-						Else
-							If last <> Null And Not last.EqualsType(e.exprType) Then
-								Err "Auto array elements must have identical types"
-							End If
-							If Not TArrayType(ty).elemType.EqualsType(e.exprType) Then
-								If (TObjectType(TArrayType(ty).elemType) = Null And TStringType(TArrayType(ty).elemType) = Null) Or (TObjectType(e.exprType) = Null And TStringType(e.exprType) = Null) Then
-									Err "Unable to convert from "+src.ToString()+" to "+ty.ToString()+"."
-								Else If TStringType(e.exprType) = Null And Not TObjectType(e.exprType).ExtendsType(TObjectType(TArrayType(ty).elemType)) Then
-									Err "Unable to convert from "+src.ToString()+" to "+ty.ToString()+"."
-								End If
-							End If
-						End If
-						
-						last = e.exprType
-					Next
-				End If
-				
-				exprType = ty
-				Return Self
-			End If
-		End If
-
-		'If TStringType(src) And TStringVarPtrType(ty) Then
-		'	exprType = ty
-		'	Return Self
-		'End If
-
-'		If TArrayType(src) And TPointerType(ty) Then
-'			exprType = ty
-'			Return expr
-'		End If
-
-		If TFunctionPtrType(ty) And TInvokeExpr(expr) Then
-			' a function ptr to function ptr
-			If Not TInvokeExpr(expr).invokedWithBraces Then
-				src = New TFunctionPtrType
-				TFunctionPtrType(src).func = TInvokeExpr(expr).decl
-
-				' signatures should match
-				If TInvokeExpr(expr).decl.equalsFunc(TFunctionPtrType(ty).func)  Then
-					exprType = ty
-					Return expr
-				End If
-			Else
-				' return type should be function ptr?
-				Local retType:TType = expr.exprType
-				If TFunctionPtrType(retType) And TFunctionPtrType(ty).func.EqualsFunc(TFunctionPtrType(retType).func) Then
-					exprType = retType
-					Return expr
-				End If
-			End If
-		End If
-
-		'If TIntType(ty) And Not IsPointerType(ty, 0, TType.T_POINTER) And IsPointerType(src, 0, TType.T_POINTER) Then
-		'	exprType = ty
-		'	If flags & CAST_EXPLICIT Then
-		'		Return Self
-		'	End If
-		'	Return expr
-		'End If
-
-		' explicit cast to number
-		If IsNumericType(ty) And IsPointerType(src, 0, TType.T_POINTER) Then
-			If flags = CAST_EXPLICIT Then
-				exprType = ty
-				Return Self
-			Else
-				exprType = Null
-			End If
-		End If
-
-'		If TPointerType(ty) And TIntType(src) Then
-'			exprType = ty
-'			Return expr
-'		End If
-
-'		If TIntType(ty) And TObjectType(src) Then
-' DebugStop ' Bah woz ere
-'			exprType = ty
-'			Return expr
-'		End If
-
-		If TObjectType(src) And TNullDecl(TObjectType(src).classDecl) Then
-			exprType = ty
-			Return expr
-		End If
-
-		If TObjectType(src) And TObjectType(ty) And (ty._flags & TType.T_VAR) Then ' TODO : May be VARPTR instead?
-			'exprType = NewPointerType(TType.T_BYTE)
-			exprType = ty
-			Return Self
-		End If
-		
-		If TStringType(src) And ((src._flags & TType.T_CHAR_PTR) Or (src._flags & TType.T_SHORT_PTR)) And TStringType(ty) Then
-			exprType = ty
-			Return Self
-		End If
-		
-		' cast from "some kind of object" array to Object[]
-		If TArrayType(ty) And TArrayType(src)
-			If (TObjectType(TArrayType(src).elemType) Or TStringType(TArrayType(src).elemType) Or TArrayType(TArrayType(src).elemType)) And TObjectType(TArrayType(ty).elemType) Then
-				If TObjectType(TArrayType(ty).elemType).classDecl.ident = "Object" Then
-					exprType = ty
-					Return Self
-				End If
-			Else
-				If TArrayType(ty).dims = TArrayType(src).dims Then
-					exprType = ty
-				End If
-			End If
-		End If
-		
-		If TArrayType(ty) And TObjectType(src) 
-			If TObjectType(src).classDecl.ident = "___Array" Then
-				exprType = ty
-				Return expr
-			Else If  TObjectType(src).classDecl.ident = "Object" Then
-				exprType = ty
-				Return Self
-			End If
-		End If
-
-		If IsPointerType(ty, 0, TType.T_POINTER | TType.T_CHAR_PTR | TType.T_SHORT_PTR) Then
-			If IsNumericType(src) And Not (src._flags & TType.T_VARPTR) Then
-				'If IsPointerType(ty,0,TType.T_POINTER) Then
-				'	exprType = TNumericType(src).ToPointer()
-				'Else
-					exprType = ty
-				'End If
-				Return Self
-			Else If TNumericType(src) And (src._flags & TType.T_VARPTR) Then
-				exprType = expr.exprType
-			Else If TArrayType(src) Then
-			
-				' for functions and index access, use a new local variable
-				If Not TVarExpr(expr) And Not TMemberVarExpr(expr) Then
-					Local tmp:TLocalDecl=New TLocalDecl.Create( "", expr.exprType, expr,, True )
-					tmp.Semant()
-					Local v:TVarExpr = New TVarExpr.Create( tmp )
-					expr = New TStmtExpr.Create( New TDeclStmt.Create( tmp ), v ).Semant()
-				End If
-			
-				If TNumericType(TArrayType(src).elemType) Then
-					exprType = TNumericType(TArrayType(src).elemType).ToPointer()
-					Return Self
-				Else
-					' map arrays to byte ptr
-					exprType = TType.MapToPointerType(New TByteType)
-				End If
-			Else If TStringType(src) Then
-				exprType = ty
-				Return Self
-			End If
-		End If
-		
-		If TStringType(src) And TStringType(ty) And (ty._flags & TType.T_VAR) Then
-			exprType = ty
-			Return Self
-		End If
-
-		If TVarPtrType(ty) Then
-			If Not TVarExpr(expr) And Not TMemberVarExpr(expr) And Not (TStmtExpr(expr) And TIndexExpr(TStmtExpr(expr).expr)) Then
-				If Not TIndexExpr(expr) Or (TIndexExpr(expr) And Not TVarExpr(TIndexExpr(expr).expr) And Not TMemberVarExpr(TIndexExpr(expr).expr))  Then
-					Err "Subexpression for 'Ptr' must be a variable"
-				End If
-			End If
-			exprType = src.Copy()
-			exprType._flags :| TType.T_VARPTR
-			ty = exprType
-			Return Self
-		End If
-		
-		If TFunctionPtrType(ty) And IsPointerType(src, 0, TType.T_POINTER) Then
-			exprType = ty
-			Return Self
-		End If
-
-		If TObjectType(ty) And TObjectType(src) And TObjectType(src).classdecl.IsInterface() And flags & CAST_EXPLICIT Then
-			exprType = ty
-			Return Self
-		End If
-
-		If Not exprType
-			Err "Unable to convert from "+src.ToString()+" to "+ty.ToString()+"."
-		EndIf
-
-		If TConstExpr( expr ) Then
-
-			Local ex:TExpr = EvalConst()
-			If flags & CAST_EXPLICIT Then
-				Return New TCastExpr.Create(exprType, ex, 1).Semant()
-			Else
-				Return ex
-			End If
-		End If
-		
-		Return Self
-	End Method
-
-	Method Eval$()
-		Local val$=expr.Eval()
-		If TBoolType( exprType )
-			If TIntegralType(expr.exprType)
-				If Long( val ) Return "1"
-				Return ""
-			Else If TDecimalType( expr.exprType )
-				If Double( val ) Return "1"
-				Return ""
-			Else If TStringType( expr.exprType )
-				If val.Length Return "1"
-				Return ""
-			EndIf
-		Else If TIntType( exprType )
-			If TBoolType( expr.exprType )
-				If val Return "1"
-				Return "0"
-			EndIf
-			Return Int( val )
-		Else If TUIntType( exprType )
-			Return Long( val )
-		Else If TShortType( exprType )
-			Return Short( val )
-		Else If TFloatType( exprType )
-			Return Float( val )
-		Else If TDoubleType( exprType )
-			Return Double( val )
-		Else If TLongType( exprType )
-			Return Long( val )
-		Else If TULongType( exprType )
-			Return Long( val )
-		Else If TSizeTType( exprType )
-			Return Long( val )
-		Else If TInt128Type( exprType )
-			Return Long( val )
-		Else If TFloat128Type( exprType )
-			Return Float( val )
-		Else If TDouble128Type( exprType )
-			Return Float( val )
-		Else If TFloat64Type( exprType )
-			Return Float( val )
-		Else If TStringType( exprType )
-			If TBoolType( expr.exprType )
-				If val Return "1"
-				Return "0"
-			EndIf
-			Return String( val )
-		Else If TByteType( exprType )
-			Return Byte( val )
-		Else If TWParamType( exprType )
-			Return Long( val )
-		Else If TLParamType( exprType )
-			Return Long( val )
-		Else If TObjectType( exprType )
-			If TStringType( expr.exprType )
-				Return val
-			End If
-		EndIf
-		Return Super.Eval()
-	End Method
-
-	Method Trans$()
-		Return _trans.TransCastExpr( Self )
-	End Method
-
-	Method ToString$()
-		Local t$="TCastExpr(" + ty.ToString()
-		If expr t:+","+expr.ToString()
-		Return t+")"
-	End Method
-
-End Type
-
-'op = '+', '-', '~'
-Type TUnaryExpr Extends TExpr
-	Field op$,expr:TExpr
-
-	Method Create:TUnaryExpr( op$,expr:TExpr )
-		Self.op=op
-		Self.expr=expr
-		Return Self
-	End Method
-
-	Method Copy:TExpr()
-		Return New TUnaryExpr.Create( op,CopyExpr(expr) )
-	End Method
-
-	Method Semant:TExpr()
-		If exprType Return Self
-
-		Select op
-		Case "+","-"
-			expr=expr.Semant()
-			If Not TNumericType( expr.exprType ) Or IsPointerType(expr.exprType) Then
-				Err expr.ToString()+" must be numeric for use with unary operator '"+op+"'"
-			End If
-			exprType=expr.exprType
-			' Remove Var-ness, if required. "expr" will still be "Var"
-			If exprType._flags & TType.T_VAR Then
-				exprType = exprType.Copy()
-				exprType._flags :~ TType.T_VAR
-			End If
-		Case "~~"
-			expr=expr.Semant()
-			If Not TIntegralType(expr.exprType) Or IsPointerType(expr.exprType) Then
-				Err "Bitwise complement can only be used with integers"
-			End If
-			If TByteType(expr.exprType) Or TShortType(expr.exprType) Then
-				expr=expr.SemantAndCast( New TIntType )
-				exprType=New TIntType
-			Else
-				exprType = expr.exprType
-			End If
-		Case "not"
-			expr=expr.SemantAndCast( New TBoolType,CAST_EXPLICIT )
-			exprType=New TBoolType
-		Default
-			InternalErr
-		End Select
-
-		If TConstExpr( expr ) Return EvalConst()
-		Return Self
-	End Method
-
-	Method Eval$()
-		Local val$=expr.Eval()
-		Select op
-		Case "~~"
-			Return ~Int( val )
-		Case "+"
-			Return val
-		Case "-"
-			If val.StartsWith( "-" ) Return val[1..]
-			Return "-"+val
-		Case "not"
-			If val Return ""
-			Return "1"
-		End Select
-		InternalErr
-	End Method
-
-	Method Trans$()
-		Return _trans.TransUnaryExpr( Self )
-	End Method
-
-End Type
-
-Type TBinaryExpr Extends TExpr
-	Field op$
-	Field lhs:TExpr
-	Field rhs:TExpr
-
-	Method Trans$()
-		Return _trans.TransBinaryExpr( Self )
-	End Method
-
-	Method ToString$()
-		Return "(" + lhs.ToString() + " " + op + " " + rhs.ToString() + ")"
-	End Method
-
-End Type
-
-' * / + / & ~ | ^ shl shr
-Type TBinaryMathExpr Extends TBinaryExpr
-
-	Method Create:TBinaryMathExpr( op$,lhs:TExpr,rhs:TExpr )
-		Self.op=op
-		Self.lhs=lhs
-		Self.rhs=rhs
-		Return Self
-	End Method
-
-	Method Copy:TExpr()
-		Return New TBinaryMathExpr.Create( op,CopyExpr(lhs),CopyExpr(rhs) )
-	End Method
-
-	Method Semant:TExpr()
-		If exprType Return Self
-
-		lhs=lhs.Semant()
-
-		If TIdentExpr(rhs) Then
-			TIdentExpr(rhs).isRhs = True
-		End If
-
-		rhs=rhs.Semant()
-		
-		' operator overload?
-		If TObjectType(lhs.exprType) Then
-			Local args:TExpr[] = [rhs]
-			Try
-				Local decl:TFuncDecl = TFuncDecl(TObjectType(lhs.exprType).classDecl.FindFuncDecl(op, args,,,,True,SCOPE_CLASS_HEIRARCHY))
-				If decl Then
-					Return New TInvokeMemberExpr.Create( lhs, decl, args ).Semant()
-				End If
-			Catch error:String
-				If error.StartsWith("Compile Error") Then
-					Throw error
-				Else
-					Err "Operator " + op + " cannot be used with Objects."
-				End If
-			End Try
-		End If
-
-		Select op
-		Case "&","~~","|","shl","shr"
-			If TFloat128Type(lhs.exprType) Then
-				exprType=New TInt128Type
-			Else If TDouble128Type(lhs.exprType) Then
-				exprType=New TInt128Type
-			Else If TFloat64Type(lhs.exprType) Then
-				exprType=New TInt128Type
-			Else If TDoubleType(lhs.exprType) Then
-				exprType=New TLongType
-			Else If TFloatType(lhs.exprType) Then
-				exprType=New TIntType
-			Else If TUIntType(lhs.exprType) Then
-				exprType=New TUIntType
-			Else If TLongType(lhs.exprType) Then
-				exprType=New TLongType
-			Else If TULongType(lhs.exprType) Then
-				exprType=New TULongType
-			Else If TSizeTType(lhs.exprType) Then
-				exprType=New TSizeTType
-			Else If TWParamType(lhs.exprType) Then
-				exprType=New TWParamType
-			Else If TLParamType(lhs.exprType) Then
-				exprType=New TLParamType
-			Else
-				exprType=New TIntType
-			End If
-		Case "^"
-			exprType=New TDoubleType
-		Default
-			exprType=BalanceTypes( lhs.exprType,rhs.exprType )
-			If TStringType( exprType )
-				If op<>"+"
-					Err "Illegal string operator."
-				EndIf
-			Else If TVoidType( exprType ) Then
-				Err "Illegal operation on a void expression."
-			Else If Not TNumericType( exprType ) And Not IsPointerType( exprType, 0, TType.T_POINTER ) And Not TArrayType( exprType ) And Not TBoolType( exprType )
-				Err "Illegal expression type."
-			Else If IsPointerType( exprType, 0, TType.T_POINTER ) And op <> "+" And op <> "-" Then
-				Err "Illegal expression type."
-			Else If IsPointerType( lhs.exprType, 0, TType.T_POINTER ) And IsPointerType( rhs.exprType, 0, TType.T_POINTER ) And op <> "-" Then
-				Err "Illegal expression type."
-			EndIf
-		End Select
-
-		If (op = "+" Or op = "-") And IsPointerType(exprType, 0, TType.T_POINTER) And TNumericType(lhs.exprType) Then
-			' with pointer addition we don't cast the numeric to a pointer
-		Else
-			lhs=lhs.Cast( exprType )
-		End If
-		
-		If (op = "+" Or op = "-") And IsPointerType(exprType, 0, TType.T_POINTER) And TNumericType(rhs.exprType) Then
-			' with pointer addition we don't cast the numeric to a pointer
-		Else
-			rhs=rhs.Cast( exprType )
-		End If
-		
-		If IsPointerType( lhs.exprType, 0, TType.T_POINTER ) And IsPointerType( rhs.exprType, 0, TType.T_POINTER ) And op = "-" Then
-			exprType = New TIntType
-		End If
-
-		If TConstExpr( lhs ) And TConstExpr( rhs ) Return EvalConst()
-
-		Return Self
-	End Method
-
-	Method Eval$()
-		Local lhs$=Self.lhs.Eval()
-		Local rhs$=Self.rhs.Eval()
-		If TIntType( exprType )
-			Local x:Int=Int(lhs),y:Int=Int(rhs)
-			Select op
-			Case "^" Return x^y
-			Case "*" Return x*y
-			Case "/" Return x/y
-			Case "mod" Return x Mod y
-			Case "shl" Return x Shl y
-			Case "shr" Return x Shr y
-			Case "+" Return x + y
-			Case "-" Return x - y
-			Case "&" Return x & y
-			Case "~~" Return x ~ y
-			Case "|" Return x | y
-			End Select
-		Else If TLongType( exprType ) Or TSizeTType(exprType) Or TUIntType(exprType) Or TULongType(exprType) Or TInt128Type(exprType) Or TWParamType(exprType) Or TLParamType(exprType) 
-			Local x:Long=Long(lhs),y:Long=Long(rhs)
-			Select op
-			Case "^" Return x^y
-			Case "*" Return x*y
-			Case "/" Return x/y
-			Case "mod" Return x Mod y
-			Case "shl" Return x Shl y
-			Case "shr" Return x Shr y
-			Case "+" Return x + y
-			Case "-" Return x - y
-			Case "&" Return x & y
-			Case "~~" Return x ~ y
-			Case "|" Return x | y
-			End Select
-		Else If TFloatType( exprType )
-			Local x:Float=Float(lhs),y:Float=Float(rhs)
-			Select op
-			Case "^" Return x^y
-			Case "*" Return x * y
-			Case "/" Return x / y
-			Case "mod" Return x Mod y
-			Case "+" Return x + y
-			Case "-" Return x - y
-			End Select
-		Else If TDoubleType( exprType ) Or TFloat128Type(exprType) Or TDouble128Type(exprType) Or TFloat64Type(exprType)
-			Local x:Double=Double(lhs),y:Double=Double(rhs)
-			Select op
-			Case "^" Return x^y
-			Case "*" Return x * y
-			Case "/" Return x / y
-			Case "mod" Return x Mod y
-			Case "+" Return x + y
-			Case "-" Return x - y
-			End Select
-		Else If TStringType( exprType )
-			Select op
-			Case "+" 
-				_appInstance.removeStringConst(lhs)
-				_appInstance.removeStringConst(rhs)
-				Return lhs+rhs
-			End Select
-		EndIf
-		InternalErr
-	End Method
-
-End Type
-
-'=,<>,<,<=,>,>=
-Type TBinaryCompareExpr Extends TBinaryExpr
-	Field ty:TType
-
-	Method Create:TBinaryCompareExpr( op$,lhs:TExpr,rhs:TExpr )
-		Self.op=op
-		Self.lhs=lhs
-		Self.rhs=rhs
-		Return Self
-	End Method
-
-	Method Copy:TExpr()
-		Return New TBinaryCompareExpr.Create( op,CopyExpr(lhs),CopyExpr(rhs) )
-	End Method
-
-	Method Semant:TExpr()
-		If exprType Return Self
-
-		lhs=lhs.Semant()
-		rhs=rhs.Semant()
-
-		' operator overload?
-		If TObjectType(lhs.exprType) Then
-			Local args:TExpr[] = [rhs]
-			Try
-				Local decl:TFuncDecl = TFuncDecl(TObjectType(lhs.exprType).classDecl.FindFuncDecl(op, args,,,,True,SCOPE_CLASS_HEIRARCHY))
-				If decl Then
-					Return New TInvokeMemberExpr.Create( lhs, decl, args ).Semant()
-				End If
-			Catch error:String
-				' no overload, continue...
-			End Try
-		End If
-
-
-		ty=BalanceTypes( lhs.exprType,rhs.exprType )
-
-		lhs=lhs.Cast( ty )
-		rhs=rhs.Cast( ty )
-
-		exprType=New TBoolType
-
-		If TConstExpr( lhs ) And TConstExpr( rhs ) Return EvalConst()
-
-		Return Self
-	End Method
-
-	Method Eval$()
-		Local r:Int=-1
-		If TBoolType( ty )
-			Local lhs:Int=Int(Self.lhs.Eval())
-			Local rhs:Int=Int(Self.rhs.Eval())
-			Select op
-			Case "="  r=(lhs= rhs)
-			Case "<>" r=(lhs<>rhs)
-			End Select
-		Else If TIntType( ty )
-			Local lhs:Int=Int( Self.lhs.Eval() )
-			Local rhs:Int=Int( Self.rhs.Eval() )
-			Select op
-			Case "="  r=(lhs= rhs)
-			Case "<>" r=(lhs<>rhs)
-			Case "<"  r=(lhs< rhs)
-			Case "<=", "=<" r=(lhs<=rhs)
-			Case ">"  r=(lhs> rhs)
-			Case ">=", "=>" r=(lhs>=rhs)
-			End Select
-		Else If TLongType( ty ) Or TSizeTType( ty ) Or TUIntType( ty ) Or TULongType( ty ) Or TInt128Type(ty) Or TWParamType(ty) Or TLParamType(ty)
-			Local lhs:Long=Long( Self.lhs.Eval() )
-			Local rhs:Long=Long( Self.rhs.Eval() )
-			Select op
-			Case "="  r=(lhs= rhs)
-			Case "<>" r=(lhs<>rhs)
-			Case "<"  r=(lhs< rhs)
-			Case "<=", "=<" r=(lhs<=rhs)
-			Case ">"  r=(lhs> rhs)
-			Case ">=", "=>" r=(lhs>=rhs)
-			End Select
-		Else If TFloatType( ty )
-			Local lhs:Float=Float( Self.lhs.Eval() )
-			Local rhs:Float=Float( Self.rhs.Eval() )
-			Select op
-			Case "="  r=(lhs= rhs)
-			Case "<>" r=(lhs<>rhs)
-			Case "<"  r=(lhs< rhs)
-			Case "<=", "=<" r=(lhs<=rhs)
-			Case ">"  r=(lhs> rhs)
-			Case ">=", "=>" r=(lhs>=rhs)
-			End Select
-		Else If TDoubleType( ty ) Or TFloat128Type(ty) Or TDouble128Type(ty) Or TFloat64Type(ty)
-			Local lhs:Double=Double( Self.lhs.Eval() )
-			Local rhs:Double=Double( Self.rhs.Eval() )
-			Select op
-			Case "="  r=(lhs= rhs)
-			Case "<>" r=(lhs<>rhs)
-			Case "<"  r=(lhs< rhs)
-			Case "<=", "=<" r=(lhs<=rhs)
-			Case ">"  r=(lhs> rhs)
-			Case ">=", "=>" r=(lhs>=rhs)
-			End Select
-		Else If TStringType( ty )
-			Local lhs:String=String( Self.lhs.Eval() )
-			Local rhs:String=String( Self.rhs.Eval() )
-			Select op
-			Case "="  r=(lhs= rhs)
-			Case "<>" r=(lhs<>rhs)
-			Case "<"  r=(lhs< rhs)
-			Case "<=", "=<" r=(lhs<=rhs)
-			Case ">"  r=(lhs> rhs)
-			Case ">=", "=>" r=(lhs>=rhs)
-			End Select
-		EndIf
-		If r=1 Return "1"
-		If r=0 Return ""
-		InternalErr
-	End Method
-End Type
-
-'and, or
-Type TBinaryLogicExpr Extends TBinaryExpr
-
-	Method Create:TBinaryLogicExpr( op$,lhs:TExpr,rhs:TExpr )
-		Self.op=op
-		Self.lhs=lhs
-		Self.rhs=rhs
-		Return Self
-	End Method
-
-	Method Copy:TExpr()
-		Return New TBinaryLogicExpr.Create( op,CopyExpr(lhs),CopyExpr(rhs) )
-	End Method
-
-	Method Semant:TExpr()
-		If exprType Return Self
-
-		lhs=lhs.SemantAndCast( New TBoolType,CAST_EXPLICIT )
-		rhs=rhs.SemantAndCast( New TBoolType,CAST_EXPLICIT )
-
-		exprType=New TBoolType
-
-		If TConstExpr( lhs ) And TConstExpr( rhs ) Return EvalConst()
-
-		Return Self
-	End Method
-
-	Method Eval$()
-		Select op
-		Case "and" If lhs.Eval() And rhs.Eval() Return "1" Else Return ""
-		Case "or"  If lhs.Eval() Or rhs.Eval() Return "1" Else Return ""
-		End Select
-		InternalErr
-	End Method
-End Type
-
-Type TIndexExpr Extends TExpr
-	Field expr:TExpr
-	Field index:TExpr[]
-
-	Method Create:TIndexExpr( expr:TExpr,index:TExpr[] )
-		Self.expr=expr
-		Self.index=index
-		Return Self
-	End Method
-
-	Method Copy:TExpr()
-		If exprType Return Self
-		
-		Local ind:TExpr[]
-		For Local i:Int = 0 Until index.length
-			ind = ind + [CopyExpr(index[i])]
-		Next
-		Return New TIndexExpr.Create( CopyExpr(expr),ind )
-	End Method
-
-	Method Semant:TExpr()
-		If exprType Return Self
-
-		expr=expr.Semant()
-
-		' for functions and index access, use a new local variable
-		If Not TVarExpr(expr) And Not TMemberVarExpr(expr) Then
-			Local tmp:TLocalDecl=New TLocalDecl.Create( "", TType.MapVarPointerToPointerType(expr.exprType.Copy()), expr,, True )
-			tmp.Semant()
-			Local v:TVarExpr = New TVarExpr.Create( tmp )
-			expr = New TStmtExpr.Create( New TDeclStmt.Create( tmp ), v ).Semant()
-		End If
-
-		For Local i:Int = 0 Until index.length
-			If Not(TNumericType(expr.exprType) And IsPointerType( expr.exprType, 0 , TType.T_POINTER | TType.T_VARPTR)) Then
-				index[i]=index[i].SemantAndCast( New TUIntType, True )
-			Else
-				index[i]=index[i].Semant()
-			End If
-		Next
-
-		If TStringType( expr.exprType )
-			exprType=New TIntType
-			If index.length > 1 Then
-				Err "Illegal subexpression for string index"
-			End If
-		Else If TArrayType( expr.exprType )
-			exprType= TArrayType( expr.exprType ).elemType
-
-			If TArrayType( expr.exprType ).dims > 1 Then
-
-				' a multi-dimensional array of arrays is slightly more complex
-				If TArrayType(exprType) Then
-
-				'	Local tmpArr:TLocalDecl=New TLocalDecl.Create( "", NewPointerType(TType.T_ARRAY), expr )
-				'	Local stmt:TExpr = New TStmtExpr.Create( New TDeclStmt.Create( tmp ), Self ).Semant()
-
-					Local sizeExpr:TExpr = New TArraySizeExpr.Create(expr, Null, index)
-					index = [sizeExpr]
-					Local tmp:TLocalDecl=New TLocalDecl.Create( "", NewPointerType(TType.T_UINT), sizeExpr,,True )
-					TArraySizeExpr(sizeExpr).val = tmp
-					Local stmt:TExpr = New TStmtExpr.Create( New TDeclStmt.Create( tmp ), Self ).Semant()
-					stmt.exprType = exprType
-
-					Return stmt
-				Else
-					Local sizeExpr:TExpr = New TArraySizeExpr.Create(expr, Null, index).Semant()
-					index = [sizeExpr]
-					Local tmp:TLocalDecl=New TLocalDecl.Create( "", NewPointerType(TType.T_UINT), sizeExpr,,True )
-					TArraySizeExpr(sizeExpr).val = tmp
-					Local stmt:TExpr = New TStmtExpr.Create( New TDeclStmt.Create( tmp ), Self ).Semant()
-					stmt.exprType = exprType
-					Return stmt
-				End If
-			End If
-			'If TObjectType(exprType) And Not TStringType(exprType) And Not TArrayType(exprType) Then
-			'	Local tmp:TLocalDecl=New TLocalDecl.Create( "", exprType,expr )
-			'	Local stmt:TExpr = New TStmtExpr.Create( New TDeclStmt.Create( tmp ),New TVarExpr.Create( tmp ) ).Semant()
-			'	stmt.exprType = exprType
-			'	Return stmt
-			'End If
-		Else If TNumericType(expr.exprType) And IsPointerType( expr.exprType, 0 , TType.T_POINTER | TType.T_VARPTR)' And Not TFunctionPtrType( expr.exprType )
-			exprType=TType.MapPointerToPrim(TNumericType(expr.exprType))
-			'exprType=TType.intType
-		Else If TObjectType(expr.exprType) And TObjectType(expr.exprType).classDecl.IsStruct() And IsPointerType( expr.exprType, 0 , TType.T_POINTER | TType.T_VARPTR)' And Not TFunctionPtrType( expr.exprType )
-			exprType = expr.exprType
-		Else
-			Err "Only strings, arrays and pointers may be indexed."
-		EndIf
-
-		Return Self
-	End Method
-
-	Method SemantSet:TExpr( op$,rhs:TExpr )
-		Return Semant()
-		'Return Self
-	End Method
-	
-	Method SemantFunc:TExpr( args:TExpr[] , throwError:Int = True, funcCall:Int = False )
-		Local ex:TExpr = Semant()
-		
-		If TArrayType( expr.exprType ) And TFunctionPtrType(exprType) Then
-			exprType = TFunctionPtrType(exprType).func.retType
-		End If
-		
-		Return ex
-	End Method
-
-
-	Method Trans$()
-		Return _trans.TransIndexExpr( Self )
-	End Method
-
-	Method TransVar$()
-		Return _trans.TransIndexExpr( Self )
-	End Method
-
-	Method ToString$()
-		Return "<TIndexExpr<"+ expr.ToString() +"[" + index[0].ToString() + "]>>"
-	End Method
-	
-End Type
-
-Type TSliceExpr Extends TExpr
-	Field expr:TExpr
-	Field from:TExpr
-	Field term:TExpr
-
-	Method Create:TSliceExpr( expr:TExpr,from:TExpr,term:TExpr )
-		Self.expr=expr
-		Self.from=from
-		Self.term=term
-		Return Self
-	End Method
-
-	Method Copy:TExpr()
-		Return New TSliceExpr.Create( CopyExpr(expr),CopyExpr(from),CopyExpr(term) )
-	End Method
-
-	Method Semant:TExpr()
-		If exprType Return Self
-
-		expr=expr.Semant()
-		If (TArrayType( expr.exprType ) And TArrayType( expr.exprType ).dims = 1) Or TStringType( expr.exprType )
-			If from from=from.SemantAndCast( New TIntType )
-			If term term=term.SemantAndCast( New TIntType )
-
-			exprType=expr.exprType
-			' remove var-ness
-			If exprType._flags & TType.T_VAR Then
-				exprType = exprType.Copy()
-				exprType._flags :~ TType.T_VAR
-			End If
-		Else
-			Err "Slices can only be used with strings or one dimensional arrays"
-		EndIf
-
-'		If TConstExpr( expr ) And TConstExpr( from ) And TConstExpr( term ) Return EvalConst()
-
-		Return Self
-	End Method
-
-	Method Eval$()
-		Local from:Int=Int( Self.from.Eval() )
-		Local term:Int=Int( Self.term.Eval() )
-		If TStringType( expr.exprType )
-			Return expr.Eval()[ from..term ]
-		Else If TArrayType( expr.exprType )
-			Todo
-		EndIf
-	End Method
-
-	Method Trans$()
-		Return _trans.TransSliceExpr( Self )
-	End Method
-End Type
-
-Type TArrayExpr Extends TExpr
-	Field exprs:TExpr[]
-	
-	Field toType:TType
-
-	Method Create:TArrayExpr( exprs:TExpr[] )
-		Self.exprs=exprs
-		Return Self
-	End Method
-
-	Method Copy:TExpr()
-		Local expr:TArrayExpr = New TArrayExpr.Create( CopyArgs(exprs) )
-		expr.toType = toType
-		Return expr
-	End Method
-
-	Method Semant:TExpr()
-		If exprType Return Self
-
-		If TIdentExpr(exprs[0]) Then
-			TIdentExpr(exprs[0]).isRhs = True
-		End If
-		exprs[0]=exprs[0].Semant()
-		Local ty:TType=exprs[0].exprType
-		' convert from varptr to ptr if required
-		ty = TType.MapVarPointerToPointerType(ty.Copy())
-		
-		If TInvokeExpr(exprs[0]) And Not TInvokeExpr(exprs[0]).invokedWithBraces Then
-			ty = New TFunctionPtrType
-			Local cp:TDecl = TInvokeExpr(exprs[0]).decl
-			TInvokeExpr(exprs[0]).decl = TFuncDecl(TInvokeExpr(exprs[0]).decl.Copy())
-			TInvokeExpr(exprs[0]).decl.actual = cp
-			TInvokeExpr(exprs[0]).decl.attrs :| FUNC_PTR
-			TFunctionPtrType(ty).func = TInvokeExpr(exprs[0]).decl
-
-			For Local i:Int=1 Until exprs.Length
-				If TIdentExpr(exprs[1]) Then
-					TIdentExpr(exprs[1]).isRhs = True
-				End If
-				exprs[i]=exprs[i].Semant()
-				
-				If TInvokeExpr(exprs[i]) And Not TInvokeExpr(exprs[i]).invokedWithBraces
-					cp = TInvokeExpr(exprs[i]).decl
-					
-					TInvokeExpr(exprs[i]).decl = TFuncDecl(TInvokeExpr(exprs[i]).decl.Copy())
-					TInvokeExpr(exprs[i]).decl.actual = cp
-					TInvokeExpr(exprs[i]).decl.attrs :| FUNC_PTR
-					
-					ty=BalanceTypes( ty, New TFunctionPtrType )
-				Else
-					ty=BalanceTypes( ty,exprs[i].exprType )
-				End If
-			Next
-		Else
-			For Local i:Int=1 Until exprs.Length
-				exprs[i]=exprs[i].Semant()
-				ty=BalanceTypes( ty,exprs[i].exprType )
-			Next
-		End If
-
-		Local comp:Int = True
-		Local last:TType
-		For Local i:Int=0 Until exprs.Length
-
-			Local expr:TExpr = exprs[i]
-
-			' don't cast null types
-			If TNullType(expr.exprType) <> Null Then
-				Err "Auto array element has no type"
-			End If
-
-			Local ety:TType = expr.exprType
-			If TBoolType(ety) Then
-				ety = New TIntType
-			End If
-			
-			If last <> Null And Not last.EqualsType(ety) Then
-				If (Not TConstExpr(expr) And Not IsNumericType(ety)) Or (TConstExpr(expr) And IsNumericType(ety) And Not TConstExpr(expr).CompatibleWithType(ty)) Then
-					Err "Auto array elements must have identical types : Index " + i
-				End If
-			End If
-			
-			If toType And TConstExpr(expr) And Not TConstExpr(expr).CompatibleWithType(toType) Then
-				comp = False
-			End If
-		
-			last = ety
-			
-			exprs[i]=expr.Cast( ty )
-		Next
-
-		If comp And toType Then
-			exprType=New TArrayType.Create( toType )
-		Else
-			exprType=New TArrayType.Create( ty )
-		End If
-		Return Self
-	End Method
-
-	Method Trans$()
-		Return _trans.TransArrayExpr( Self )
-	End Method
-
-End Type
-
-Type TArraySizeExpr Extends TExpr
-
-	Field expr:TExpr
-	Field val:TDecl
-	Field index:TExpr[]
-
-	Method Create:TArraySizeExpr( expr:TExpr, val:TDecl, index:TExpr[] )
-		Self.expr=expr
-		Self.val=val
-		Self.index=index
-		Return Self
-	End Method
-
-	Method Copy:TExpr()
-		Local ind:TExpr[]
-		For Local i:Int = 0 Until index.length
-			ind = ind + [CopyExpr(index[i])]
-		Next
-		Return New TArraySizeExpr.Create( CopyExpr(expr), val, ind )
-	End Method
-
-	Method Semant:TExpr()
-		If exprType Return Self
-
-		expr=expr.Semant()
-		
-		For Local i:Int = 0 Until index.length
-			index[i]=index[i].SemantAndCast( New TUIntType )
-		Next
-		
-		exprType=NewPointerType(TType.T_UINT)
-		Return Self
-	End Method
-
-	Method Trans$()
-		Return _trans.TransArraySizeExpr( Self )
-	End Method
-
-	Method ToString$()
-		Return expr.ToString() + ".Size"
-	End Method
-
-End Type
-
-Type TIdentTypeExpr Extends TExpr
-	Field cdecl:TClassDecl
-
-	Method Create:TIdentTypeExpr( ty:TType )
-		Self.exprType=ty
-		Return Self
-	End Method
-
-	Method Copy:TExpr()
-		Return New TIdentTypeExpr.Create( exprType )
-	End Method
-
-	Method _Semant()
-		If cdecl Return
-		exprType=exprType.Semant()
-		If TArrayType(exprType) And TObjectType(TArrayType(exprType).elemType) Then
-			cdecl=TObjectType(TArrayType(exprType).elemType).classDecl
-		Else
-			cdecl=exprType.GetClass()
-		End If
-		If Not cdecl InternalErr
-	End Method
-
-	Method Semant:TExpr()
-		_Semant
-		Err "Expression can't be used in this way"
-	End Method
-
-	Method SemantFunc:TExpr( args:TExpr[] , throwError:Int = True, funcCall:Int = False )
-		_Semant
-		If args.Length=1 And args[0] Then
-			If TArrayType(exprType) Then
-				Return args[0].Cast( exprType,CAST_EXPLICIT )
-			Else
-				Return args[0].Cast( cdecl.objectType,CAST_EXPLICIT )
-			End If
-		End If
-		Err "Illegal number of arguments for type conversion"
-	End Method
-
-	Method SemantScope:TScopeDecl()
-		_Semant
-		Return cdecl
-	End	Method
-
-	Method Trans$()
-		Return _trans.TransIdentTypeExpr( Self )
-	End Method
-
-End Type
-
-Type TIdentExpr Extends TExpr
-	Field ident$
-	Field expr:TExpr
-	Field scope:TScopeDecl
-	Field static:Int
-	Field isArg:Int
-	Field isRhs:Int
-	Field fixedScope:Int
-	
-	Field _identLower:String
-
-	Method IdentLower:String()
-		If Not _identLower Then
-			_identLower = ident.ToLower()
-		End If
-		Return _identLower
-	End Method
-
-	Method Create:TIdentExpr( ident$,expr:TExpr=Null, _identLower:String = Null )
-		Self.ident=ident
-		Self.expr=expr
-		Self._identLower = _identLower
-		Return Self
-	End Method
-
-	Method Copy:TExpr()
-		Local i:TIdentExpr = New TIdentExpr.Create( ident,CopyExpr(expr), _identLower )
-		i.static = static
-		i.isArg = isArg
-		i.isRhs = isRhs
-		i.fixedScope = fixedScope
-		Return i
-	End Method
-
-	Method ToString$()
-		Local t$="TIdentExpr(~q"+ident+"~q"
-		If expr t:+","+expr.ToString()
-		Return t+")"
-	End Method
-
-	Method _Semant()
-
-		If scope Return
-
-		If expr Then
-			scope=expr.SemantScope()
-			If scope
-				static=True
-			Else
-				expr=expr.Semant()
-				scope=expr.exprType.GetClass()
-				If Not scope Then
-					Err "Expression has no scope"
-				End If
-			End If
-			fixedScope = True
-		Else
-			scope=_env
-			' determines if access is via static (like Function, or via a Type)
-			' However, for Field->Field access this is not strictly true.
-			If _env.FuncScope()=Null
-				static = TModuleDecl(_env) = Null
-			Else
-				static=_env.FuncScope().IsStatic()
-			End If
-		End If
-
-	End Method
-
-	Method IdentScope:TScopeDecl()
-		If Not expr Return _env
-
-		Local scope:TScopeDecl=expr.SemantScope()
-		If scope
-			expr=Null
-		Else
-			expr=expr.Semant()
-			scope=expr.exprType.GetClass()
-			If Not scope Err "Expression has no scope."
-		EndIf
-		Return scope
-	End Method
-
-	Method IdentErr( errorDetails:String = Null )
-		If errorDetails Then
-			Err errorDetails
-		Else
-			Err "Identifier '"+ident+"' not found."
-		End If
-	End Method
-
-	Method IdentNotFound()
-	End Method
-
-	Method IsVar()
-		InternalErr
-	End Method
-
-	Method Semant:TExpr()
-		Return SemantSet( "",Null )
-	End Method
-
-	Method SemantSet:TExpr( op$,rhs:TExpr )
-		_Semant
-
-		'Local scope:TScopeDecl=IdentScope()
-		Local vdecl:TValDecl=scope.FindValDecl( IdentLower(), static )
-		
-		If TLocalDecl( vdecl )
-			' local variable should (at least) be in the same function scope.
-			If vdecl.FuncScope() <> scope.FuncScope() Then
-				' or the local can be in localmain..
-				If TModuleDecl(scope) And vdecl.FuncScope() And vdecl.FuncScope().ident = "__LocalMain" Then
-					' ok
-				Else
-					vdecl = Null
-				End If
-			End If
-		End If
-		
-		If vdecl And fixedScope And static Then
-			If TClassDecl(vdecl.scope) And TClassDecl(scope) Then
-				If Not TClassDecl(scope).ExtendsClass(TClassDecl(vdecl.scope)) Then
-					vdecl = Null
-				End If
-			Else
-				If vdecl.scope <> scope Then
-					vdecl = Null
-				End If
-			End If
-		End If
-		
-		If vdecl
-
-			If TConstDecl( vdecl )
-'				If rhs Err "Constant '"+ident+"' cannot be modified."
-'				Return New TConstExpr.Create( vdecl.ty,TConstDecl( vdecl ).value ).Semant()
-				If rhs Err "Constant '"+ident+"' cannot be modified."
-				Local cexpr:TConstExpr =New TConstExpr.Create( vdecl.ty,TConstDecl( vdecl ).value )
-				If Not static And (TInvokeExpr( expr ) Or TInvokeMemberExpr( expr )) Return New TStmtExpr.Create( New TExprStmt.Create( expr ),cexpr ).Semant()
-				Return cexpr.Semant()
-
-			Else If TFieldDecl( vdecl ) 
-				If static Err "Field '"+ident+"' cannot be accessed from here."
-				If expr Return New TMemberVarExpr.Create( expr,TVarDecl( vdecl ) ).Semant()
-'				If expr Return New TMemberVarExpr.Create( expr,TVarDecl( vdecl ) ).Semant()
-'				If scope<>_env Or Not _env.FuncScope() Or _env.FuncScope().IsStatic() Err "Field '"+ident+"' cannot be accessed from here."
-
-			EndIf
-
-			Return New TVarExpr.Create( TVarDecl( vdecl ) ).Semant()
-		EndIf
-
-		If op And op<>"="
-
-			Local fdecl:TFuncDecl=scope.FindFuncDecl( IdentLower(),,,,,,SCOPE_ALL )
-			If Not fdecl IdentErr
-
-			If _env.ModuleScope().IsStrict() And Not fdecl.IsProperty() Err "Identifier '"+ident+"' cannot be used in this way."
-
-			Local lhs:TExpr
-
-			If fdecl.IsStatic() Or (scope=_env And Not _env.FuncScope().IsStatic())
-				lhs=New TInvokeExpr.Create( fdecl )
-			Else If expr
-				Local tmp:TLocalDecl=New TLocalDecl.Create( "",Null,expr,, True )
-				lhs=New TInvokeMemberExpr.Create( New TVarExpr.Create( tmp ),fdecl )
-				lhs=New TStmtExpr.Create( New TDeclStmt.Create( tmp ),lhs )
-			Else
-				Return Null
-			EndIf
-
-			Local bop$=op[..1]
-			Select bop
-			Case "*","/","shl","shr","+","-","&","|","~~"
-				rhs=New TBinaryMathExpr.Create( bop,lhs,rhs )
-			Default
-				InternalErr
-			End Select
-			rhs=rhs.Semant()
-		EndIf
-
-		Local args:TExpr[]
-		If rhs args=[rhs]
-
-		Local fdecl:TFuncDecl
-		
-		Try
-			fdecl=scope.FindFuncDecl( IdentLower(),args, , isArg, True,True,SCOPE_ALL )
-		Catch errorMessage:String
-			If errorMessage.StartsWith("Compile Error") Then
-				Throw errorMessage
-			End If
-		End Try
-
-		If fdecl
-			If _env.ModuleScope().IsStrict() And Not fdecl.IsProperty() And Not isArg And Not fdecl.maybeFunctionPtr Err "Identifier '"+ident+"' cannot be used in this way."
-
-			fdecl.maybeFunctionPtr = False
-			
-			If Not fdecl.IsStatic()
-				If expr Return New TInvokeMemberExpr.Create( expr,fdecl,args, False ).Semant()
-				If scope<>_env Or Not _env.FuncScope() Or _env.FuncScope().IsStatic() Err "Method '"+ident+"' cannot be accessed from here."
-			EndIf
-
-			Return New TInvokeExpr.Create( fdecl,args, False, isArg, isRhs ).Semant()
-		End If
-		
-		' maybe it's a classdecl?
-		Local cdecl:TClassDecl = TClassDecl(scope.FindDecl(IdentLower()))
-		
-		If cdecl Then
-			Local e:TIdentTypeExpr = New TIdentTypeExpr.Create(cdecl.objectType)
-			e.cdecl = cdecl
-			Return e
-		End If
-
-		Local loopLabel:String = "#" + IdentLower()
-
-		' maybe it's a loop label?
-		Local stmt:TLoopStmt = TLoopStmt(scope.FindLoop(loopLabel))
-		
-		If stmt Then
-			Return New TLoopLabelExpr.Create(stmt)
-		End If
-		
-		' maybe it's a data label?
-		Local ddecl:TDefDataDecl = TDefDataDecl(_appInstance.FindDataLabel(loopLabel))
-		
-		If ddecl Then
-			Return New TDataLabelExpr.Create(ddecl)
-		End If
-		
-		IdentErr
-	End Method
-
-	Method SemantFunc:TExpr( args:TExpr[], throwError:Int = True, funcCall:Int = False )
-
-		_Semant
-
-		Local errorDetails:String
-		Local nearestScopeError:String
-
-		'Local scope:TScopeDecl=IdentScope()
-		Local initialScope:Int = SCOPE_ALL
-		If scope And TClassDecl(scope) Then
-			initialScope = SCOPE_CLASS_HEIRARCHY
-		End If
-		
-		Local fdecl:TFuncDecl
-		Try
-			fdecl=scope.FindFuncDecl( IdentLower(),args,,,,True,initialScope )
-'			Local decl:Object=scope.FindFuncDecl( IdentLower(),args,,,,True,SCOPE_ALL )
-'			If decl Then
-'				If TFuncDecl(decl) Then
-'					fdecl = TFuncDecl(decl)
-'				Else If TFuncDeclList(decl) Then
-'					If Not TFuncDeclList(decl).IsEmpty() Then
-'						fdecl = TFuncDecl(TFuncDeclList(decl).First())
-'					End If
-'				End If
-'			End If
-		Catch errorMessage:String
-			If errorMessage.StartsWith("Compile Error") Then
-				Throw errorMessage
-			Else
-				' couldn't find an exact match, look elsewhere
-				errorDetails = errorMessage
-				If errorMessage.StartsWith("Unable") Then
-					nearestScopeError = errorDetails
-				End If
-			End If
-		End Try
-
-		' if our scope is static, but the scope of the found function/method is not
-		' then we should ignore it and continue looking higher up the scope stack.
-		If static And fdecl And Not fdecl.IsStatic() Then
-			Local scope2:TScopeDecl = fdecl.scope
-			
-			fdecl = Null
-			
-			' if fdecl was a method, this would be the Type's scope (ie. file/module)
-			If scope2.scope Then
-				fdecl = scope2.scope.FindFuncDecl( IdentLower(),args,,,,,SCOPE_CLASS_HEIRARCHY )
-			End If
-		Else If static And Not fdecl And Not fixedScope Then
-			If _env.classScope() Then
-				' try searching from our class scope
-				'fdecl = _env.classScope().FindFuncDecl( IdentLower(),args )
-
-				If Not fdecl Then				
-					' try searching from our class parent scope
-					Try
-						fdecl = _env.classScope().scope.FindFuncDecl( IdentLower(),args,,,,True,SCOPE_ALL )
-					Catch errorMessage:String
-						If errorMessage.StartsWith("Compile Error") Then
-							Throw errorMessage
-						Else
-							' couldn't find an exact match, look elsewhere
-							errorDetails = errorMessage
-							If Not nearestScopeError And errorDetails.StartsWith("Unable") Then
-								nearestScopeError = errorDetails
-							End If
-						End If
-					End Try
-				End If
-			Else If _env.ModuleScope() Then ' bah
-				' finally, try searching from our module scope
-				Try
-					fdecl = _env.ModuleScope().FindFuncDecl( IdentLower(),args,,,,True,SCOPE_ALL )
-				Catch errorMessage:String
-					If errorMessage.StartsWith("Compile Error") Then
-						Throw errorMessage
-					Else
-						' couldn't find an exact match, look elsewhere
-						errorDetails = errorMessage
-						If Not nearestScopeError And errorDetails.StartsWith("Unable") Then
-							nearestScopeError = errorDetails
-						End If
-					End If
-				End Try
-			End If
-		End If
-
-		' couldn't find it? try a global search
-		If Not fdecl And Not fixedScope Then
-			For Local mdecl:TModuleDecl = EachIn _appInstance.globalImports.Values()
-				Try
-					fdecl=mdecl.FindFuncDecl( IdentLower(), args,,,,True,SCOPE_ALL )
-				Catch errorMessage:String
-					If errorMessage.StartsWith("Compile Error") Then
-						Throw errorMessage
-					Else
-						' couldn't find an exact match, look elsewhere
-						errorDetails = errorMessage
-						If Not nearestScopeError And errorDetails.StartsWith("Unable") Then
-							nearestScopeError = errorDetails
-						End If
-					End If
-				End Try
-				If fdecl Exit
-			Next
-		End If
-
-		If fdecl
-			If Not fdecl.IsStatic()
-				If static Err "Method '"+ident+"' cannot be accessed from here."
-				If expr Return New TInvokeMemberExpr.Create( expr,fdecl,args ).Semant()
-				'If scope<>_env Or _env.FuncScope().IsStatic() Err "Method '"+ident+"' cannot be accessed from here."
-			EndIf
-			If expr And Not static Then
-				Return New TInvokeMemberExpr.Create( expr,fdecl,args ).Semant()
-			Else
-				Return New TInvokeExpr.Create( fdecl,args, funcCall ).Semant()
-			End If
-		EndIf
-
-		'If args.Length=1 And args[0] And TObjectType( args[0].exprType )
-		'	Local cdecl:TClassDecl=TClassDecl( scope.FindScopeDecl( ident ) )
-		'	If cdecl Return args[0].Cast( New TObjectType.Create(cdecl),CAST_EXPLICIT )
-		'EndIf
-
-		Local ty:TType=scope.FindType( IdentLower(),Null )
-		If ty Then
-			If args.Length=1 And args[0] Return args[0].Cast( ty,CAST_EXPLICIT )
-			Err "Illegal number of arguments for type conversion"
-		End If
-
-		If throwError Then
-			If nearestScopeError Then
-				IdentErr(nearestScopeError)
-			Else
-				IdentErr(errorDetails)
-			End If
-		End If
-	End Method
-
-	Method SemantScope:TScopeDecl()
-		If Not expr Return _env.FindScopeDecl( IdentLower() )
-		Local scope:TScopeDecl=expr.SemantScope()
-
-		' If scope is a namespace, then we are a module. Look up the module id and return it as the real scope.
-		If TNamespaceDecl(scope) Then
-			Local mdecl:TModuleDecl=TModuleDecl(scope.FindDecl(scope.IdentLower() + "." + IdentLower()))
-			If mdecl Then
-				Return mdecl
-			End If
-		End If
-
-		If scope Return scope.FindScopeDecl( IdentLower() )
-	End Method
-
-'	Method Trans$()
-'		Return _trans.TransIdentExpr( Self )
-'	End Method
-
-End Type
-
-Type TBuiltinExpr Extends TExpr
-
-	Field id:String
-	Field expr:TExpr
-
-	Method Semant:TExpr()
-		If exprType Return Self
-
-		expr=expr.Semant()
-		exprType=expr.exprType
-		Return Self
-	End Method
-
-	Method Trans$()
-		Return _trans.TransBuiltinExpr( Self )
-	End Method
-
-End Type
-
-Type TLenExpr Extends TBuiltinExpr
-
-	Method Create:TLenExpr( expr:TExpr )
-		Self.id="len"
-		Self.expr=expr
-		Return Self
-	End Method
-
-	Method Semant:TExpr()
-		If exprType Return Self
-
-		expr=expr.Semant()
-
-		' anything other than a string or array will become "1", and
-		' return a length of 1 accordingly.
-		If Not TStringType(expr.exprType) And Not TArrayType(expr.exprType) Then
-			expr = New TConstExpr.Create( New TIntType, 1 ).Semant()
-			'this is not useful for numerics
-			'expr = New TConstExpr.Create( TType.stringType, "1" ).Semant()
-			_appInstance.mapStringConsts(TConstExpr(expr).value)
-		End If
-
-		exprType=New TIntType
-		Return Self
-	End Method
-
-	Method Copy:TExpr()
-		Return New TLenExpr.Create( CopyExpr(expr) )
-	End Method
-
-	Method ToString$()
-		Return "TLenExpr("+expr.ToString()+")"
-	End Method
-
-End Type
-
-Type TAbsExpr Extends TBuiltinExpr
-
-	Method Create:TAbsExpr( expr:TExpr )
-		Self.id="abs"
-		Self.expr=expr
-		Return Self
-	End Method
-
-	Method Semant:TExpr()
-
-		If exprType Return Self
-
-		expr=expr.Semant()
-
-		If TNumericType(expr.exprType) Or TBoolType(expr.exprType) Then
-
-			If TInt128Type(expr.exprType) Err "'Abs' does not support Int128 type. Use specific intrinsic function instead."
-			If TFloat64Type(expr.exprType) Err "'Abs' does not support Float64 type. Use specific intrinsic function instead."
-			If TFloat128Type(expr.exprType) Err "'Abs' does not support Float128 type. Use specific intrinsic function instead."
-			If TDouble128Type(expr.exprType) Err "'Abs' does not support Double128 type. Use specific intrinsic function instead."
-
-			If TIntType(expr.exprType) Or TByteType(expr.exprType) Or TShortType(expr.exprType) Then
-				exprType=New TIntType
-			Else
-				exprType=expr.exprType
-			End If
-		Else
-			Err "Subexpression for 'Abs' must be of numeric type"
-		End If
-
-		Return Self
-	End Method
-
-	Method Copy:TExpr()
-		Return New TAbsExpr.Create( CopyExpr(expr) )
-	End Method
-
-	Method ToString$()
-		Return "TAbsExpr("+expr.ToString()+")"
-	End Method
-
-End Type
-
-Type TAscExpr Extends TBuiltinExpr
-
-	Method Create:TAscExpr( expr:TExpr )
-		Self.id="asc"
-		Self.expr=expr
-		Return Self
-	End Method
-
-	Method Semant:TExpr()
-		If exprType Return Self
-
-		If TConstExpr(expr) Then
-			Local cexpr:TExpr = New TConstExpr.Create(New TIntType, Asc(TConstExpr(expr).value))
-			_appInstance.removeStringConst(TConstExpr(expr).value)
-			cexpr.Semant()
-			Return cexpr
-		End If
-		
-		expr = expr.SemantAndCast( New TStringType )
-		exprType = New TIntType
-		Return Self
-	End Method
-
-	Method Copy:TExpr()
-		Return New TAscExpr.Create( CopyExpr(expr) )
-	End Method
-
-	Method ToString$()
-		Return "TAscExpr("+expr.ToString()+")"
-	End Method
-
-End Type
-
-Type TSgnExpr Extends TBuiltinExpr
-
-	Method Create:TSgnExpr( expr:TExpr )
-		Self.id="sgn"
-		Self.expr=expr
-		Return Self
-	End Method
-
-	Method Semant:TExpr()
-		If exprType Return Self
-
-		If TConstExpr(expr) Then
-			'use different calls to only return a "float sgn"
-			'when param is a float
-			Local val:String = TConstExpr(expr).value
-			Local cexpr:TExpr
-			If String(Int(val)) = val
-				cexpr = New TConstExpr.Create(New TIntType, Sgn(Int(TConstExpr(expr).value)))
-			Else
-				cexpr = New TConstExpr.Create(New TFloatType, Sgn(Float(TConstExpr(expr).value)))
-			End If
-			
-			_appInstance.removeStringConst(TConstExpr(expr).value)
-			cexpr.Semant()
-			Return cexpr
-		End If
-		
-		expr = expr.Semant()
-		
-		If Not TNumericType(expr.exprType) Then
-			Err "Subexpression for 'Sgn' must be of numeric type"
-		End If
-
-		If TInt128Type(expr.exprType) Err "'Sgn' does not support Int128 type. Use specific intrinsic function instead."
-		If TFloat64Type(expr.exprType) Err "'Sgn' does not support Float64 type. Use specific intrinsic function instead."
-		If TFloat128Type(expr.exprType) Err "'Sgn' does not support Float128 type. Use specific intrinsic function instead."
-		If TDouble128Type(expr.exprType) Err "'Sgn' does not support Double128 type. Use specific intrinsic function instead."
-		
-		exprType=expr.exprType
-		Return Self
-	End Method
-
-	Method Copy:TExpr()
-		Return New TSgnExpr.Create( CopyExpr(expr) )
-	End Method
-
-	Method ToString$()
-		Return "TSgnExpr("+expr.ToString()+")"
-	End Method
-
-End Type
-
-Type TMinExpr Extends TBuiltinExpr
-
-	Field expr2:TExpr
-
-	Method Create:TMinExpr( lhs:TExpr, rhs:TExpr )
-		Self.id="min"
-		Self.expr=lhs
-		Self.expr2=rhs
-		Return Self
-	End Method
-
-	Method Semant:TExpr()
-		If exprType Return Self
-
-		expr=expr.Semant()
-		expr2=expr2.Semant()
-		
-		If TInt128Type(expr.exprType) Or TInt128Type(expr2.exprType) Err "'Min' does not support Int128 type. Use specific intrinsic function instead."
-		If TFloat64Type(expr.exprType) Or TFloat64Type(expr2.exprType) Err "'Min' does not support Float64 type. Use specific intrinsic function instead."
-		If TFloat128Type(expr.exprType) Or TFloat128Type(expr2.exprType) Err "'Min' does not support Float128 type. Use specific intrinsic function instead."
-		If TDouble128Type(expr.exprType) Or TDouble128Type(expr2.exprType) Err "'Min' does not support Double128 type. Use specific intrinsic function instead."
-
-		exprType=BalanceTypes(expr.exprType, expr2.exprType)
-		Return Self
-	End Method
-
-	Method Copy:TExpr()
-		Return New TMinExpr.Create( CopyExpr(expr), CopyExpr(expr2) )
-	End Method
-
-	Method ToString$()
-		Return "TMinExpr("+expr.ToString()+"," + expr2.ToString() + ")"
-	End Method
-
-End Type
-
-Type TMaxExpr Extends TBuiltinExpr
-
-	Field expr2:TExpr
-
-	Method Create:TMaxExpr( lhs:TExpr, rhs:TExpr )
-		Self.id="max"
-		Self.expr=lhs
-		Self.expr2=rhs
-		Return Self
-	End Method
-
-	Method Semant:TExpr()
-		If exprType Return Self
-
-		expr=expr.Semant()
-		expr2=expr2.Semant()
-
-		If TInt128Type(expr.exprType) Or TInt128Type(expr2.exprType) Err "'Max' does not support Int128 type. Use specific intrinsic function instead."
-		If TFloat64Type(expr.exprType) Or TFloat64Type(expr2.exprType) Err "'Max' does not support Float64 type. Use specific intrinsic function instead."
-		If TFloat128Type(expr.exprType) Or TFloat128Type(expr2.exprType) Err "'Max' does not support Float128 type. Use specific intrinsic function instead."
-		If TDouble128Type(expr.exprType) Or TDouble128Type(expr2.exprType) Err "'Max' does not support Double128 type. Use specific intrinsic function instead."
-
-		exprType=BalanceTypes(expr.exprType, expr2.exprType)
-		Return Self
-	End Method
-
-	Method Copy:TExpr()
-		Return New TMaxExpr.Create( CopyExpr(expr), CopyExpr(expr2) )
-	End Method
-
-	Method ToString$()
-		Return "TMaxExpr("+expr.ToString()+"," + expr2.ToString() + ")"
-	End Method
-
-End Type
-
-Type TSizeOfExpr Extends TBuiltinExpr
-
-	Method Create:TSizeOfExpr( expr:TExpr )
-		Self.id="sizeof"
-		Self.expr=expr
-		Return Self
-	End Method
-
-	Method Semant:TExpr()
-		If exprType Return Self
-		expr=expr.Semant()
-		exprType=New TIntType
-		Return Self
-	End Method
-
-	Method Copy:TExpr()
-		Return New TSizeOfExpr.Create( CopyExpr(expr) )
-	End Method
-
-	Method ToString$()
-		Return "TSizeOfExpr("+expr.ToString()+")"
-	End Method
-
-End Type
-
-Type TChrExpr Extends TBuiltinExpr
-
-	Method Create:TChrExpr( expr:TExpr )
-		Self.id="chr"
-		Self.expr=expr
-		Return Self
-	End Method
-	
-	Method Semant:TExpr()
-		If exprType Return Self
-
-		If TConstExpr(expr) Then
-			Local cexpr:TConstExpr = New TConstExpr.Create(New TStringType, Chr(Int(TConstExpr(expr).value)))
-			cexpr.Semant()
-			_appInstance.mapStringConsts(cexpr.value)
-			Return cexpr
-		End If
-		
-		expr = expr.SemantAndCast( New TIntType )
-		exprType = New TStringType
-		Return Self
-	End Method
-
-	Method Copy:TExpr()
-		Return New TChrExpr.Create( CopyExpr(expr) )
-	End Method
-
-	Method ToString$()
-		Return "TChrExpr("+expr.ToString()+")"
-	End Method
-
-End Type
-
-
-Type TFuncCallExpr Extends TExpr
-	Field expr:TExpr
-	Field args:TExpr[]
-
-	Method Create:TFuncCallExpr( expr:TExpr,args:TExpr[]=Null )
-		Self.expr=expr
-		If args Then
-			Self.args=args
-		Else
-			Self.args = New TExpr[0]
-		End If
-		Return Self
-	End Method
-
-	Method Copy:TExpr()
-		Return New TFuncCallExpr.Create( CopyExpr(expr),CopyArgs(args) )
-	End Method
-
-	Method ToString$()
-		Local t$="TFuncCallExpr("+expr.ToString()
-		For Local arg:TExpr=EachIn args
-			t:+","+arg.ToString()
-		Next
-		Return t+")"
-	End Method
-
-	Method Semant:TExpr()
-		args=SemantArgs( args )
-		If TIndexExpr(expr) Then
-			expr = expr.SemantFunc( args, True, True )
-			exprType = expr.exprType
-			Return Self
-		Else
-			Return expr.SemantFunc( args, True, True )
-		End If
-	End Method
-
-	Method SemantFunc:TExpr( args:TExpr[] , throwError:Int = True, funcCall:Int = False )
-		' we are only likely to be called if a function returns and invokes a function pointer.
-
-		Local ex:TExpr = Semant()
-		
-		If TFunctionPtrType(ex.exprType) Then
-			exprType = TFunctionPtrType(ex.exprType).func.retType
-		End If
-		
-		Self.args = SemantArgs(args)
-		expr = ex
-		
-		Return Self
-	End Method
-
-	Method Trans$()
-		Return _trans.TransFuncCallExpr( Self )
-	End Method
-
-End Type
-
-Type TScopeExpr Extends TExpr
-	Field scope:TScopeDecl
-
-	Method Create:TScopeExpr( scope:TScopeDecl )
-		Self.scope=scope
-		Return Self
-	End Method
-
-	Method Copy:TExpr()
-		Return Self
-	End Method
-
-	Method ToString$()
-		Return "TScopeExpr("+scope.ToString()+")"
-	End Method
-
-	Method Semant:TExpr()
-		Err "Syntax error."
-	End Method
-
-	Method SemantScope:TScopeDecl()
-		Return scope
-	End Method
-End Type
-
-Type TNewExpr Extends TExpr
-	Field isSuper:Int
-	Field args:TExpr[]
-	Field ctor:TFuncDecl
-
-	Method Create:TNewExpr( args:TExpr[]=Null, isSuper:Int = False )
-		If args Then
-			Self.args=args
-		Else
-			Self.args = New TExpr[0]
-		End If
-		Self.isSuper = isSuper
-		Return Self
-	End Method
-
-	Method Copy:TExpr()
-		Return New TNewExpr.Create(CopyArgs(args), isSuper)
-	End Method
-
-	Method Semant:TExpr()
-
-		Local fdecl:TFuncDecl = _env.FuncScope()
-		If Not fdecl Or TNewDecl(fdecl) = Null Or Not _env.ClassScope() Then
-			Err "Call to constructor not valid in this context."
-		End If
-	
-		' must be first statement of New() method
-		Local stmt:TStmt = TStmt(fdecl.stmts.First())
-		
-		If TExprStmt(stmt) = Null Or TExprStmt(stmt).expr <> Self Then
-			Err "Call to constructor must be first statement in New()."
-		End If
-	
-		args=SemantArgs( args )
-		
-		' validate called constructor
-		Try
-			Local cDecl:TClassDecl = _env.ClassScope()
-			If isSuper Then
-				cDecl = cDecl.superClass
-			End If
-			ctor = cDecl.FindFuncDecl("new",args,,,,True,SCOPE_CLASS_HEIRARCHY )
-		Catch errorMessage:String
-			If errorMessage.StartsWith("Compile Error") Then
-				Throw errorMessage
-			Else
-				Err errorMessage
-			End If
-		End Try
-		
-		' TODO : expand to full recursive test
-		If ctor = fdecl Then
-			Err "Recursive constructor invocation."
-		End If
-		
-		ctor.Semant
-		
-		' attach to ctor
-		TNewDecl(fdecl).chainedCtor = Self
-		
-		Return Self
-	End Method
-
-	Method Trans$()
-		'Return _trans.TransFuncCallExpr( Self )
-	End Method
-
-End Type
-
-Type TNullExpr Extends TExpr
-
-	Method Create:TNullExpr(ty:TType)
-		exprType = ty
-		Return Self
-	End Method
-
-	Method Copy:TExpr()
-		Return New TNullExpr.Create(exprType)
-	End Method
-
-	Method Semant:TExpr()
-		Return Self
-	End Method
-
-	Method Trans$()
-		Return "NULL"
-	End Method
-
-	Method Eval$()
-		Return ""
-	End Method
-
-End Type
-
-Type TLoopLabelExpr Extends TExpr
-
-	Field loop:TLoopStmt
-
-	Method Create:TLoopLabelExpr(loop:TLoopStmt)
-		Self.loop = loop
-		Return Self
-	End Method
-	
-	Method Copy:TExpr()
-		Return New TLoopLabelExpr.Create(loop)
-	End Method
-
-	Method Semant:TExpr()
-		Return Self
-	End Method
-
-	Method Trans$()
-		DebugStop
-	End Method
-
-	Method Eval$()
-		Return ""
-	End Method
-
-End Type
-
-Type TDataLabelExpr Extends TExpr
-
-	Field dataDef:TDefDataDecl
-	
-	Method Create:TDataLabelExpr(dataDef:TDefDataDecl)
-		Self.dataDef = dataDef
-		Return Self
-	End Method
-
-	Method Copy:TExpr()
-		Return New TDataLabelExpr.Create(dataDef)
-	End Method
-
-	Method Semant:TExpr()
-		Return Self
-	End Method
-
-	Method Trans$()
-		DebugStop
-	End Method
-
-	Method Eval$()
-		Return ""
-	End Method
-
-End Type
+' Copyright (c) 2013-2017 Bruce A Henderson
+'
+' Based on the public domain Monkey "trans" by Mark Sibly
+'
+' This software is provided 'as-is', without any express or implied
+' warranty. In no event will the authors be held liable for any damages
+' arising from the use of this software.
+'
+' Permission is granted to anyone to use this software for any purpose,
+' including commercial applications, and to alter it and redistribute it
+' freely, subject to the following restrictions:
+'
+'    1. The origin of this software must not be misrepresented; you must not
+'    claim that you wrote the original software. If you use this software
+'    in a product, an acknowledgment in the product documentation would be
+'    appreciated but is not required.
+'
+'    2. Altered source versions must be plainly marked as such, and must not be
+'    misrepresented as being the original software.
+'
+'    3. This notice may not be removed or altered from any source
+'    distribution.
+'
+
+Type TExpr
+	Field exprType:TType
+
+	Method ToString$()
+		Return "<TExpr>"
+	End Method
+
+	Method Copy:TExpr()
+		InternalErr
+	End Method
+
+	Method Semant:TExpr()
+		InternalErr
+	End Method
+
+	Method SemantSet:TExpr( op$,rhs:TExpr )
+		Err ToString()+" cannot be assigned to."
+	End Method
+
+	Method SemantFunc:TExpr( args:TExpr[] , throwError:Int = True, funcCall:Int = False )
+		Err ToString()+" cannot be invoked."
+	End Method
+
+	Method SemantScope:TScopeDecl()
+		Return Null
+	End Method
+
+	Method Eval$()
+		Err ToString()+" cannot be statically evaluated."
+	End Method
+
+	Method EvalConst:TExpr()
+		Local expr:TExpr = New TConstExpr.Create( exprType,Eval() ).Semant()
+		If TStringType(TConstExpr(expr).ty) Then
+			_appInstance.mapStringConsts(TConstExpr(expr).value)
+		End If
+		Return expr
+	End Method
+
+	Method Trans$()
+		Todo
+	End Method
+
+	Method TransStmt$()
+		Return Trans()
+	End Method
+
+	Method TransVar$()
+		InternalErr
+	End Method
+
+	'semant and cast
+	Method SemantAndCast:TExpr( ty:TType,castFlags:Int=0 )
+		Local expr:TExpr=Semant()
+		If expr.exprType.EqualsType( ty ) Return expr
+		Return New TCastExpr.Create( ty,expr,castFlags ).Semant()
+	End Method
+
+	'expr and ty already semanted!
+	Method Cast:TExpr( ty:TType,castFlags:Int=0 )
+		If Not exprType Then
+			Semant()
+		End If
+		If exprType.EqualsType( ty ) Return Self
+		Return New TCastExpr.Create( ty,Self,castFlags ).Semant()
+	End Method
+
+	Method SemantArgs:TExpr[]( args:TExpr[] )
+		args=args[..]
+		For Local i:Int=0 Until args.Length
+			If args[i] Then
+				If TIdentExpr(args[i]) Then
+					TIdentExpr(args[i]).isArg = True
+				End If
+				args[i]=args[i].Semant()
+
+				' if an arg is a invocation without braces, it is *probably* a function pointer.
+				If TInvokeExpr(args[i]) And Not TInvokeExpr(args[i]).invokedWithBraces Then
+					' but not if we've already processed it...
+					If Not (TInvokeExpr(args[i]).decl.attrs & FUNC_PTR) Then
+						TInvokeExpr(args[i]).exprType = New TFunctionPtrType
+						Local cp:TDecl = TInvokeExpr(args[i]).decl
+						cp.Semant
+						TInvokeExpr(args[i]).decl = TFuncDecl(TInvokeExpr(args[i]).decl.Copy(False))
+						TInvokeExpr(args[i]).decl.actual = cp
+						TInvokeExpr(args[i]).decl.attrs :| FUNC_PTR
+						TFunctionPtrType(TInvokeExpr(args[i]).exprType).func = TInvokeExpr(args[i]).decl
+
+						TInvokeExpr(args[i]).decl.semant()
+					End If
+				End If
+				
+			End If
+		Next
+		Return args
+	End Method
+
+	Method CastArgs:TExpr[]( args:TExpr[],funcDecl:TFuncDecl )
+		If args.Length>funcDecl.argDecls.Length Then
+			Err "Too many function parameters"
+		End If
+
+		' FIXME
+		'args=args.Resize( funcDecl.argDecls.Length )
+		' FIXME
+
+		For Local i:Int=0 Until funcDecl.argDecls.Length
+			' ensure funcdecl args are semanted before trying to use them.
+			If Not funcDecl.argDecls[i].IsSemanted() Then
+				funcDecl.argDecls[i].Semant()
+			End If
+
+			If i < args.length And args[i]
+				If TInvokeExpr(args[i]) And Not TInvokeExpr(args[i]).invokedWithBraces Then
+					If Not IsPointerType(funcDecl.argDecls[i].ty, TType.T_BYTE) And Not TFunctionPtrType(funcDecl.argDecls[i].ty) Then
+						Err "Unable to convert from '" + args[i].exprType.ToString() + "()' to '" + funcDecl.argDecls[i].ty.ToString() + "'"
+					End If
+				End If
+
+				If TInvokeMemberExpr(args[i]) And Not TInvokeMemberExpr(args[i]).invokedWithBraces Then
+					If Not IsPointerType(funcDecl.argDecls[i].ty, TType.T_BYTE) And Not TFunctionPtrType(funcDecl.argDecls[i].ty) Then
+						Err "Unable to convert from '" + args[i].exprType.ToString() + "()' to '" + funcDecl.argDecls[i].ty.ToString() + "'"
+					End If
+				End If
+
+				If funcDecl.argDecls[i].ty._flags & TType.T_VAR Then
+
+					If TConstExpr(args[i]) Or TBinaryExpr(args[i]) Or (TIndexExpr(args[i]) And TStringType(TIndexExpr(args[i]).expr.exprType)) Or ..
+							TInvokeExpr(args[i]) Or TInvokeMemberExpr(args[i]) Then
+						Err "Expression for 'Var' parameter must be a variable"
+					End If
+
+					' Passing a "new" object into a Var, requires us to create a local variable and pass its address instead.
+					If TNewObjectExpr(args[i]) Then
+						Local tmp:TLocalDecl=New TLocalDecl.Create( "",TNewObjectExpr(args[i]).ty,args[i],, True )
+						tmp.Semant()
+						Local v:TVarExpr = New TVarExpr.Create( tmp )
+						Local stmt:TExpr = New TStmtExpr.Create( New TDeclStmt.Create( tmp ), v ).Semant()
+						stmt.exprType = TNewObjectExpr(args[i]).ty
+						args[i] = stmt
+					End If
+				End If
+				
+				If (funcDecl.argDecls[i].ty._flags & TType.T_VAR) And Not (funcDecl.argDecls[i].ty.EqualsType(args[i].exprType)) Then
+					If (Not TObjectType(funcDecl.argDecls[i].ty)) Or (TObjectType(funcDecl.argDecls[i].ty) And Not args[i].exprType.ExtendsType(funcDecl.argDecls[i].ty)) Then
+						err "Variable for 'Var' parameter is not of matching type"
+					End If
+				End If
+
+				' re-test auto array for compatible consts.
+				If TArrayExpr(args[i]) And TArrayType(funcDecl.argDecls[i].ty) And TNumericType(TArrayType(funcDecl.argDecls[i].ty).elemType) Then
+					TArrayExpr(args[i]).toType = TArrayType(funcDecl.argDecls[i].ty).elemType
+					args[i].exprType = Null
+					args[i].Semant()
+				End If
+				args[i]=args[i].Cast( funcDecl.argDecls[i].ty )
+			Else If funcDecl.argDecls[i].init
+				If i = args.length Then
+					' extend args to add default init entry
+					args = args[..i + 1]
+				End If
+				args[i]=funcDecl.argDecls[i].init
+			Else
+				Err "Missing function argument '"+funcDecl.argDecls[i].ident+"'."
+			EndIf
+		Next
+		Return args
+	End Method
+
+	Method BalanceTypes:TType( lhs:TType,rhs:TType )
+
+		If TStringType( lhs ) Or TStringType( rhs ) Then
+			If TObjectType(lhs) Or TObjectType(rhs) Then
+				If TObjectType(lhs) And TObjectType(lhs).classDecl.ident = "Object" Then
+					Return lhs
+				End If
+				If TObjectType(rhs) And TObjectType(rhs).classDecl.ident = "Object" Then
+					Return rhs
+				End If
+			Else
+				Return New TStringType
+			End If
+		End If
+		If IsPointerType( lhs, 0, TType.T_POINTER ) Or IsPointerType( rhs, 0, TType.T_POINTER ) Then
+			If IsPointerType( lhs, 0, TType.T_POINTER ) Return lhs
+			If IsPointerType( rhs, 0, TType.T_POINTER ) Return rhs
+		End If
+		If TDouble128Type( lhs ) Or TDouble128Type( rhs ) Return New TDouble128Type
+		If TFloat128Type( lhs ) Or TFloat128Type( rhs ) Return New TFloat128Type
+		If TFloat64Type( lhs ) Or TFloat64Type( rhs ) Return New TFloat64Type
+		If TDoubleType( lhs ) Or TDoubleType( rhs ) Return New TDoubleType
+		If TFloatType( lhs ) Or TFloatType( rhs ) Return New TFloatType
+		If TFunctionPtrType( lhs ) Or TFunctionPtrType( rhs ) Then
+			If TFunctionPtrType( lhs ) Return lhs
+			If TFunctionPtrType( rhs ) Return rhs
+		End If
+		If TInt128Type( lhs ) Or TInt128Type( rhs ) Return New TInt128Type
+		If TULongType( lhs ) Or TULongType( rhs ) Return New TULongType
+		If TSizeTType( lhs ) Or TSizeTType( rhs ) Return New TSizeTType
+		If TWParamType( lhs ) Or TWParamType( rhs ) Return New TWParamType
+		If TLongType( lhs ) And TUIntType( rhs ) Return New TULongType
+		If TUIntType( lhs ) And TLongType( rhs ) Return New TULongType
+		If TLParamType( lhs ) Or TLParamType( rhs ) Return New TLParamType
+		If TLongType( lhs ) Or TLongType( rhs ) Return New TLongType
+		If TUIntType( lhs ) Or TUIntType( rhs ) Return New TUIntType
+		If TIntType( lhs ) Or TIntType( rhs ) Return New TIntType
+		If TObjectType( lhs ) And TNullDecl(TObjectType( lhs ).classDecl) Then
+			Return rhs
+		End If
+		If TObjectType( rhs ) And TNullDecl(TObjectType( rhs ).classDecl) Then
+			Return lhs
+		End If
+		If lhs.ExtendsType( rhs ) Return rhs
+		If rhs.ExtendsType( lhs ) Return lhs
+		' balance arrays - only for objects... to the lowest common denominator.
+		If TArrayType( lhs ) And TArrayType( rhs ) Then
+
+			If TObjectType(TArrayType( lhs ).elemType) And TObjectType(TArrayType( rhs ).elemType) Then
+				' lhs = Object[]
+				If TObjectType(TArrayType( lhs ).elemType).classDecl.ident = "Object" Then
+					Return lhs
+				End If
+				' rhs = Object[]
+				If TObjectType(TArrayType( rhs ).elemType).classDecl.ident = "Object" Then
+					Return rhs
+				End If
+				
+				' does one extend the other? If so, return the base type
+				If TObjectType(TArrayType( lhs ).elemType).ExtendsType(TObjectType(TArrayType( rhs ).elemType)) Then
+					Return rhs
+				End If
+
+				If TObjectType(TArrayType( rhs ).elemType).ExtendsType(TObjectType(TArrayType( lhs ).elemType)) Then
+					Return lhs
+				End If
+				
+				' no? then we will fallback to an Object type array
+				
+				' find the Object classdecl instance
+				Local modid$="brl.classes"
+				Local mdecl:TModuleDecl=_env.FindModuleDecl( modid )
+				' return an array of Objects
+				Return New TArrayType.Create(New TObjectType.Create(TClassDecl(mdecl.FindDecl( "object" ))))
+			End If
+			
+			If TObjectType(TArrayType( lhs ).elemType) And TObjectType(TArrayType( lhs ).elemType).classDecl.ident = "Object" And TStringType(TArrayType( rhs ).elemType) Then
+				Return lhs
+			End If
+
+			If TObjectType(TArrayType( rhs ).elemType) And TObjectType(TArrayType( rhs ).elemType).classDecl.ident = "Object"  And TStringType(TArrayType( lhs ).elemType) Then
+				Return rhs
+			End If
+
+			If TObjectType(TArrayType( lhs ).elemType) And TObjectType(TArrayType( lhs ).elemType).classDecl.ident = "Object"  And TArrayType(TArrayType( rhs ).elemType) Then
+				Return lhs
+			End If
+
+			If TObjectType(TArrayType( rhs ).elemType) And TObjectType(TArrayType( rhs ).elemType).classDecl.ident = "Object"  And TArrayType(TArrayType( lhs ).elemType) Then
+				Return rhs
+			End If
+
+			' balancing primitive types
+			If Not TArrayType( lhs ).elemType.EqualsType(TArrayType( rhs ).elemType) Then
+				Err "Types '" + TArrayType( lhs ).elemType.ToString() + " Array' and '" + TArrayType( rhs ).elemType.ToString() + " Array' are unrelated"
+			End If
+			
+		End If
+		Err "Can't balance types "+lhs.ToString()+" and "+rhs.ToString()+"."
+	End Method
+
+	Function CopyExpr:TExpr( expr:TExpr )
+		If Not expr Return Null
+		Return expr.Copy()
+	End Function
+
+	Function CopyArgs:TExpr[]( exprs:TExpr[] )
+		exprs=exprs[..]
+		For Local i:Int=0 Until exprs.Length
+			exprs[i]=CopyExpr( exprs[i] )
+		Next
+		Return exprs
+	End Function
+
+End Type
+
+'	exec a stmt, return an expr
+Type TStmtExpr Extends TExpr
+	Field stmt:TStmt
+	Field expr:TExpr
+
+	Method Create:TStmtExpr( stmt:TStmt,expr:TExpr )
+		Self.stmt=stmt
+		Self.expr=expr
+		Return Self
+	End Method
+
+	Method Copy:TExpr()
+		If exprType Return Self
+		Return New TStmtExpr.Create( stmt,CopyExpr(expr) )
+	End Method
+
+	Method ToString$()
+		Return "TStmtExpr(,"+expr.ToString()+")"
+	End Method
+
+	Method Semant:TExpr()
+		If exprType Return Self
+
+		stmt.Semant()
+		expr=expr.Semant()
+		exprType=expr.exprType
+		Return Self
+	End Method
+
+	Method Trans$()
+		Return _trans.TransStmtExpr( Self )
+	End Method
+
+	Method TransVar$()
+		Semant
+		Return _trans.TransStmtExpr( Self )
+	End Method
+
+End Type
+
+'	literal
+Type TConstExpr Extends TExpr
+	Field ty:TType
+	Field value$
+	Field originalValue$
+	' True if the const was identified as a specific type.
+	Field typeSpecific:Int
+
+	Method Create:TConstExpr( ty:TType,value$ )
+		originalValue = value
+
+		If TNumericType( ty ) And IsPointerType(ty, 0, TType.T_POINTER) Then
+			Self.ty=ty
+			If value Then
+				Self.value = value
+			Else
+				Self.value="0"
+			End If
+			Return Self
+		End If
+		
+		If TIntegralType( ty ) Then
+			Local radix:Int
+			If value.StartsWith( "%" )
+				radix=1
+			Else If value.StartsWith( "$" )
+				radix=4
+			EndIf
+
+			If radix
+				Local v:TMAPM  = TMAPM.CreateMAPM()
+				Local mul:TMAPM
+				Local c:TMAPM = TMAPM.CreateMAPM()
+				
+				If radix = 1 Then
+					mul = MM_Two
+				Else
+					mul = MM_Sixteen
+				End If
+			
+				For Local i:Int=1 Until value.Length
+					Local ch:Int=value[i]
+					
+					v = v.Multiply(mul)
+					
+					If ch>=48 And ch<58
+						c.SetInt(ch & 15)
+					Else
+						c.SetInt((ch & 15)+9)
+					EndIf
+					
+					v = v.Add(c)
+				Next
+
+				value = v.ToIntString()
+
+			Else
+				Local v:TMAPM  = TMAPM.CreateMAPM(value)
+			
+				If TByteType( ty ) Then
+
+					While v.Compare(MM_MaxByte) > 0
+						v = v.Modulo(MM_MaxByteMod)
+					Wend
+					
+					While v.Compare(MM_Zero) < 0
+						v = MM_MaxByteP1.Add(v)
+					Wend
+					
+					value = v.ToIntString()
+
+				Else If TShortType( ty ) Then
+
+					While v.Compare(MM_MaxShort) > 0
+						v = v.Modulo(MM_MaxShortMod)
+					Wend
+					
+					While v.Compare(MM_Zero) < 0
+						v = MM_MaxShortP1.Add(v)
+					Wend
+					
+					value = v.ToIntString()
+				
+				Else If TIntType(ty) Or (TLParamType(ty) And WORD_SIZE = 4) Then ' fit number to Int
+
+					While v.Compare(MM_MaxInt) > 0
+						v = MM_MaxIntNeg.Add(v)
+					Wend
+					
+					While v.Compare(MM_MinInt) < 0
+						v = MM_MinIntPos.Add(v)
+					Wend
+					
+					value = v.ToIntString()
+
+				Else If TLongType(ty) Or (TLParamType(ty) And WORD_SIZE = 8) Then ' fit number to Long
+
+					While v.Compare(MM_MaxLong) > 0
+						v = MM_MaxLongNeg.Add(v)
+					Wend
+					
+					While v.Compare(MM_MinLong) < 0
+						v = MM_MinLongPos.Add(v)
+					Wend
+					
+					value = v.ToIntString()
+				
+				Else If TUIntType(ty) Or ((TSizeTType(ty) Or TWParamType(ty)) And WORD_SIZE = 4) Then ' fit number to UInt
+
+					While v.Compare(MM_MaxUInt) > 0
+						v = v.Modulo(MM_MaxUIntMod)
+					Wend
+					
+					While v.Compare(MM_Zero) < 0
+						v = MM_MaxUIntP1.Add(v)
+					Wend
+				
+					value = v.ToIntString()
+					
+				Else If TULongType(ty) Or ((TSizeTType(ty) Or TWParamType(ty)) And WORD_SIZE = 8) Then ' fit number to ULong
+					
+					While v.Compare(MM_MaxULong) > 0
+						v = v.Modulo(MM_MaxULongMod)
+					Wend
+					
+					While v.Compare(MM_Zero) < 0
+						v = MM_MaxULongP1.Add(v)
+					Wend
+				
+					value = v.ToIntString()
+					
+				Else
+					Rem
+						Local buf:Byte[64]
+						Local b:Int
+						Local v:String = value.Trim()
+						Local leading0:Int = True
+						If v Then
+							Local i:Int
+							If v[0] = Asc("+") Then
+								i = 1
+							Else If v[0] = Asc("-") Then
+								i = 1
+								buf[b] = Asc("-")
+								b:+ 1
+							End If
+							
+							While i < value.Length
+								If Not IsDigit(v[i]) Then
+									Exit
+								End If
+								If leading0 And v[i] = Asc("0") Then
+									i :+ 1
+									Continue
+								End If
+								leading0 = False
+								buf[b] = v[i]
+								
+								b :+ 1
+								i :+ 1
+							Wend
+							
+							If leading0 Then
+								value = "0"
+							Else
+								value = String.FromBytes(buf, b)
+							End If
+						Else
+							value = "0"
+						End If
+					End Rem
+				End If
+			EndIf
+
+		Else If TDecimalType( ty )
+			If Not (value.Contains("e") Or value.Contains("E") Or value.Contains(".") Or value.Contains("inf") Or value.Contains("nan"))
+				If TFloatType(ty) Then
+					value:+".00000000"
+				Else
+					value:+".0000000000000000"
+				End If
+			EndIf
+		EndIf
+		Self.ty=ty
+		Self.value = value
+		
+		Return Self
+	End Method
+	
+	Method UpdateType(ty:TType)
+		typeSpecific = True
+		Create(ty, originalValue)
+	End Method
+
+	Method Copy:TExpr()
+		Local e:TConstExpr = New TConstExpr.Create( ty,value )
+		e.originalValue = originalValue
+		e.typeSpecific = typeSpecific
+		Return e
+	End Method
+
+	Method ToString$()
+		Return "TConstExpr(~q"+value+"~q)"
+	End Method
+
+	Method Semant:TExpr()
+		If exprType Return Self
+
+		exprType=ty.Semant()
+		Return Self
+	End Method
+
+	Method Eval$()
+		Return value
+	End Method
+
+	Method EvalConst:TExpr()
+		Return Self
+	End Method
+
+	Method Trans$()
+		Semant
+		Return _trans.TransConstExpr( Self )
+	End Method
+
+	Method SemantAndCast:TExpr( ty:TType,castFlags:Int=0 )
+		Local expr:TExpr=Semant()
+		If expr.exprType.EqualsType( ty ) Return expr
+		If value = "bbNullObject" Then
+			Err "bbNullObject"
+			Return expr
+		End If
+		Return New TCastExpr.Create( ty,expr,castFlags ).Semant()
+	End Method
+	
+	Method CompatibleWithType:Int(ty:TType)
+		If Not TDecimalType(ty) Then
+			If value.Contains("e") Or value.Contains("E") Or value.Contains(".") Or value.Contains("inf") Or value.Contains("nan") Then
+				Return False
+			End If
+			
+			Local val:Long = value.ToLong()
+			
+			If val < 0 Then
+				If TByteType(ty) Or TShortType(ty) Or TUIntType(ty) Or TULongType(ty) Or TSizeTType(ty) Or TInt128Type(ty) Or TWParamType(ty) Then
+					Return False
+				End If
+			Else
+				If TByteType(ty) Then
+					If value <> String.FromInt(Byte(Val)) Then
+						Return False
+					End If
+				End If
+
+				If TUIntType(ty) Or ((TSizeTType(ty) Or TWParamType(ty)) And WORD_SIZE = 4) Then
+					If val > 4294967296:Long Then
+						Return False
+					End If
+				End If
+				
+				If TULongType(ty) Or ((TSizeTType(ty) Or TWParamType(ty)) And WORD_SIZE = 8) Then
+					If value.length > 20 Then
+						Return False
+					Else If value.length = 20 Then
+						For Local i:Int = 0 Until value.length
+							Local v:Int = value[i]
+							Local n:Int = "18446744073709551616"[i]
+							If v < n Then
+								Exit 
+							Else If v > n Then
+								Return False
+							End If
+						Next
+					End If
+				End If
+			End If
+			
+			If TShortType(ty) Then
+				If value <> String.FromInt(Short(val)) Then
+					Return False
+				End If
+			End If
+
+			If TIntType(ty) Or (TLParamType(ty) And WORD_SIZE = 4) Then
+				If value <> String.FromInt(Int(val)) Then
+					Return False
+				End If
+			End If
+
+			If TLongType(ty) Or (TLParamType(ty) And WORD_SIZE = 8) Then
+				If value <> String.FromLong(Long(val)) Then
+					Return False
+				End If
+			End If
+			
+		End If
+		
+		Return True
+	End Method
+
+End Type
+
+Type TVarExpr Extends TExpr
+	Field decl:TVarDecl
+
+	Method Create:TVarExpr( decl:TVarDecl )
+		Self.decl=decl
+		Return Self
+	End Method
+
+	Method Copy:TExpr()
+		Return Self
+	End Method
+
+	Method ToString$()
+		Return "TVarExpr("+decl.ToString()+")"
+	End Method
+
+	Method Semant:TExpr()
+		If exprType Return Self
+		If Not decl.IsSemanted() InternalErr
+		exprType=decl.ty
+		Return Self
+	End Method
+
+	Method SemantSet:TExpr( op$,rhs:TExpr )
+		Return Semant()
+	End Method
+
+	Method Trans$()
+		Semant
+		Return _trans.TransTemplateCast( exprType,TVarDecl(decl.actual).ty,_trans.TransVarExpr( Self ) )
+	End Method
+
+	Method TransVar$()
+		Semant
+		Return _trans.TransVarExpr( Self )
+	End Method
+
+End Type
+
+Type TMemberVarExpr Extends TExpr
+	Field expr:TExpr
+	Field decl:TVarDecl
+
+	Method Create:TMemberVarExpr( expr:TExpr,decl:TVarDecl )
+		Self.expr=expr
+		Self.decl=decl
+		Return Self
+	End Method
+
+	Method Copy:TExpr()
+		Return Self
+	End Method
+
+	Method ToString$()
+		Return "TMemberVarExpr("+expr.ToString()+","+decl.ToString()+")"
+	End Method
+
+	Method Semant:TExpr()
+		If exprType Return Self
+		If Not decl.IsSemanted() InternalErr
+		exprType=decl.ty
+		Return Self
+	End Method
+
+	Method SemantSet:TExpr( op$,rhs:TExpr )
+		Return Semant()
+	End Method
+
+	Method Trans$()
+		Return _trans.TransTemplateCast( exprType,TVarDecl(decl.actual).ty,_trans.TransMemberVarExpr( Self ) )
+	End Method
+
+	Method TransVar$()
+		Return _trans.TransMemberVarExpr( Self )
+ 	End Method
+
+End Type
+
+Type TInvokeExpr Extends TExpr
+	Field decl:TFuncDecl
+	Field args:TExpr[]
+	Field invokedWithBraces:Int
+	Field isArg:Int
+	Field isRhs:Int
+
+	Method Create:TInvokeExpr( decl:TFuncDecl,args:TExpr[]=Null,invokedWithBraces:Int=True, isArg:Int=False, isRhs:Int = False )
+		Self.decl=decl
+		If args Then
+			Self.args=args
+		Else
+			Self.args = New TExpr[0]
+		End If
+		Self.invokedWithBraces = invokedWithBraces
+		Self.isArg = isArg
+		Self.isRhs = isRhs
+		Return Self
+	End Method
+
+	Method Copy:TExpr()
+		Return Self
+	End Method
+
+	Method ToString$()
+		Local t$="TInvokeExpr("+decl.ToString()
+		For Local arg:TExpr=EachIn args
+			t:+","+arg.ToString()
+		Next
+		Return t+")"
+	End Method
+
+	Method Semant:TExpr()
+
+		If exprType Return Self
+
+		If Not decl.retType
+			decl.Semant()
+		End If
+		'If TIdentType(decl.retType) Then
+			exprType = decl.retType.Semant()
+		'Else
+		'	exprType=decl.retType
+		'End If
+
+		'If ((isArg Or isRhs) And Not invokedWithBraces) And (args = Null Or args.length = 0) Then
+
+		' if the call was a statement (even one written without parentheses), then invokedWithBraces is true
+		' so no complicated checks are needed here; if invokedWithBraces is false, this is definitely not a call
+		If Not invokedWithBraces Then
+			' nothing to do here, as we are a function pointer. i.e. no braces
+			' and our expression type is a function ptr...
+			exprType = New TFunctionPtrType.Create(decl)
+			
+		Else
+			args=CastArgs( args,decl )
+		End If
+		Return Self
+	End Method
+
+	Method Trans$()
+'		Return _trans.TransTemplateCast( exprType,TFuncDecl(decl.actual).retType,_trans.TransInvokeExpr( Self ) )
+		Return _trans.TransInvokeExpr( Self )
+	End Method
+
+	Method TransStmt$()
+		Return _trans.TransInvokeExpr( Self )
+	End Method
+
+	Method Eval$()
+		Return Super.Eval()
+	End Method
+
+End Type
+
+Type TInvokeMemberExpr Extends TExpr
+	Field expr:TExpr
+	Field decl:TFuncDecl
+	Field args:TExpr[]
+	Field isResize:Int	'FIXME - butt ugly!
+	Field invokedWithBraces:Int
+
+	Method Create:TInvokeMemberExpr( expr:TExpr,decl:TFuncDecl,args:TExpr[]=Null, invokedWithBraces:Int = True )
+		Self.expr=expr
+		Self.decl=decl
+		If args
+			Self.args=args
+		Else
+			Self.args = New TExpr[0]
+		End If
+		Self.invokedWithBraces = invokedWithBraces
+		Return Self
+	End Method
+
+	Method Copy:TExpr()
+		Return Self
+	End Method
+
+	Method ToString$()
+		Local t$="TInvokeMemberExpr("+expr.ToString()+","+decl.ToString()
+		For Local arg:TExpr=EachIn args
+			t:+","+arg.ToString()
+		Next
+		Return t+")"
+	End Method
+
+	Method Semant:TExpr()
+		If exprType Return Self
+
+		If Not decl.IsSemanted() decl.Semant()
+		exprType=decl.retType
+
+		args=SemantArgs( args )
+		args=CastArgs( args,decl )
+
+		'Array $resize hack!
+		If TArrayType( exprType ) And TVoidType( TArrayType( exprType ).elemType )
+			isResize=True
+			exprType=expr.exprType
+		EndIf
+
+		Return Self
+	End Method
+
+	Method Trans$()
+		'Array $resize hack!
+		If isResize Return _trans.TransInvokeMemberExpr( Self )
+
+		Return _trans.TransTemplateCast( exprType,TFuncDecl(decl.actual).retType,_trans.TransInvokeMemberExpr( Self ) )
+	End Method
+
+	Method TransStmt$()
+		Return _trans.TransInvokeMemberExpr( Self )
+	End Method
+
+End Type
+
+Type TNewObjectExpr Extends TExpr
+	Field ty:TType
+	Field args:TExpr[]
+	Field ctor:TFuncDecl
+	Field classDecl:TClassDecl
+	Field instanceExpr:TExpr
+
+	Method Create:TNewObjectExpr( ty:TType,args:TExpr[] )
+		Self.ty=ty
+		Self.args=args
+		Return Self
+	End Method
+
+	Method Copy:TExpr()
+		Return New TNewObjectExpr.Create( ty,CopyArgs(args) )
+	End Method
+
+	Method Semant:TExpr()
+		If exprType Return Self
+
+		Local it:TIdentType = TIdentType(ty)
+		Local iArgs:TExpr[] = SemantArgs(CopyArgs(args))
+
+		ty=ty.Semant(True)
+		If Not ty Then
+			' maybe it's an instance of a type ?
+			Local decl:TVarDecl = TVarDecl(_env.FindDecl(it.ident))
+			If decl And TObjectType(decl.ty) Then
+				ty = decl.ty
+				instanceExpr = New TVarExpr.Create(decl).Semant()
+			Else
+				Err "Type '"+it.ident+"' not found"
+			End If
+		End If
+		args=SemantArgs( args )
+
+		Local objTy:TObjectType=TObjectType( ty )
+		Local clsTy:TClassType=TClassType( ty )
+		If Not objTy And Not clsTy
+			Err "Expression is not a class."
+		EndIf
+		
+		' 
+		If clsTy And clsTy.instance Then
+			instanceExpr = New TSelfExpr.Semant()
+		End If
+
+		If objTy Then
+			classDecl=objTy.classDecl
+		Else
+			classDecl=clsTy.classDecl
+		End If
+
+		If Not instanceExpr Then
+			If classDecl.IsInterface() Err "Cannot create instance of an interface."
+			If classDecl.IsAbstract() Err "Cannot create instance of an abstract class."
+		End If
+		'If classDecl.IsTemplateArg() Err "Cannot create instance of a generic argument."
+		If classDecl.args And Not classDecl.instanceof Err "Cannot create instance of a generic class."
+
+		Local parts:String[]
+		If it Then
+			parts = it.ident.ToLower().Split(".")
+		End If
+
+		If classDecl.IsExtern()
+			Err "Cannot create instance of an extern type"
+			'If args Err "No suitable constructor found for class "+classDecl.ToString()+"."
+		Else
+			' if the New Type doesn't have extra idents (like a create method), then don't use the args in the search.
+			' otherwise, the args are for the constructor.
+			If Not parts Or parts.length = 1 Then
+				ctor=classDecl.FindFuncDecl( "new",args,,,,,SCOPE_CLASS_HEIRARCHY )
+				If Not ctor	Err "No suitable constructor found for class "+classDecl.ToString()+"."
+				args=CastArgs( args,ctor )
+			Else
+				ctor=classDecl.FindFuncDecl( "new",,,,,,SCOPE_CLASS_HEIRARCHY )
+				If Not ctor	Err "No suitable constructor found for class "+classDecl.ToString()+"."
+			End If
+		EndIf
+
+		classDecl.attrs:|CLASS_INSTANCED
+
+		If TClassType(ty) Then
+			exprType=New TObjectType.Create(TClassType(ty).classDecl)
+		Else
+			exprType=ty
+		End If
+		
+		If it Then
+			'Local parts:String[] = it.ident.ToLower().Split(".")
+
+			Local i:Int = 0
+			
+			While i < parts.length And parts[i] <> classDecl.IdentLower() And parts[i] <> "self"
+				i :+ 1
+			Wend
+			
+			i :+ 1
+
+			Local expr:TExpr = Self
+			Local cdecl:TClassDecl = classDecl
+			Local eType:TType = ty
+			
+			Local errorDetails:String
+
+			While i < parts.length
+				Local id:String = parts[i]
+				i :+ 1
+				
+				' find member function.method
+				Local fdecl:TFuncDecl
+				Try
+					fdecl = cdecl.FindFuncDecl(id, iArgs,,,,True,SCOPE_CLASS_HEIRARCHY)
+				Catch errorMessage:String
+					If errorMessage.StartsWith("Compile Error") Then
+						Throw errorMessage
+					Else
+						' couldn't find an exact match, look elsewhere
+						If errorMessage.StartsWith("Unable") Then
+							errorDetails = errorMessage
+						End If
+					End If
+				End Try
+				If fdecl Then
+					expr = New TInvokeMemberExpr.Create( expr,fdecl, iArgs ).Semant()
+					eType = expr.exprType
+					If TObjectType(eType) Then
+						cdecl = TObjectType(expr.exprType).classdecl
+					End If
+					If TArrayType(eType) Or TStringType(eType) Then
+						cdecl = eType.GetClass()
+					End If
+					Continue
+				End If
+				
+				' find other member decl (field, etc)
+				If Not errorDetails Then
+					Local decl:TValDecl = TValDecl(cdecl.GetDecl(id))
+					If TVarDecl(decl) Then
+						Local tmp:TLocalDecl=New TLocalDecl.Create( "", eType, expr,, True )
+						Local varExpr:TExpr = New TMemberVarExpr.Create(New TVarExpr.Create( tmp ), TVarDecl(decl)).Semant()
+						expr = New TStmtExpr.Create( New TDeclStmt.Create( tmp ), varExpr ).Semant()
+						eType = decl.ty
+						If TObjectType(eType) Then
+							cdecl = TObjectType(expr.exprType).classdecl
+						End If
+						If TArrayType(eType) Or TStringType(eType) Then
+							cdecl = eType.GetClass()
+						End If
+						Continue
+					End If
+					If TConstDecl(decl) Then
+						decl.Semant()
+						expr = New TConstExpr.Create(decl.ty, TConstDecl(decl).value).Semant()
+						eType = decl.ty
+						Continue
+					End If
+				End If	
+
+				' didn't match member or function??
+				' probably an error...
+				If errorDetails Then
+					Err errorDetails
+				Else
+					Err "Identifier '" + id + "' not found."
+				End If
+			Wend
+			
+			Return expr
+		End If
+
+		Return Self
+	End Method
+
+	Method Trans$()
+		Return _trans.TransNewObjectExpr( Self )
+	End Method
+End Type
+
+Type TNewArrayExpr Extends TExpr
+	Field ty:TType
+
+	Field expr:TExpr[]
+	
+	Method Create:TNewArrayExpr( ty:TType,expr:TExpr[] )
+
+		Self.ty=ty
+		Self.expr=expr
+		Return Self
+	End Method
+
+	Method Copy:TExpr()
+		If exprType InternalErr
+		Local cexpr:TExpr[expr.length]
+		For Local i:Int = 0 Until expr.length
+			cexpr[i] = CopyExpr(expr[i])
+		Next
+		Return New TNewArrayExpr.Create( ty,cexpr )
+	End Method
+
+	Method Semant:TExpr()
+		If exprType Return Self
+
+		ty=ty.Semant()
+		exprType=New TArrayType.Create( ty, expr.length )
+		For Local i:Int = 0 Until expr.length
+			expr[i]=expr[i].SemantAndCast( New TIntType )
+		Next
+		Return Self
+	End Method
+
+	Method Trans$()
+		Return _trans.TransNewArrayExpr( Self )
+	End Method
+
+End Type
+
+'	super.ident( args )
+Type TInvokeSuperExpr Extends TExpr
+	Field ident$
+	Field args:TExpr[]
+	Field origFuncDecl:TFuncDecl
+	Field funcDecl:TFuncDecl
+	Field classScope:TClassDecl
+	Field superClass:TClassDecl
+	
+	Field _identLower:String
+
+	Method Create:TInvokeSuperExpr( ident$,args:TExpr[] = Null, _identLower:String = Null )
+		Self.ident=ident
+		If args Then
+			Self.args=args
+		Else
+			Self.args = New TExpr[0]
+		End If
+		Self._identLower = _identLower
+		Return Self
+	End Method
+
+	Method IdentLower:String()
+		If Not _identLower Then
+			_identLower = ident.ToLower()
+		End If
+		Return _identLower
+	End Method
+
+	Method Copy:TExpr()
+		Return New TInvokeSuperExpr.Create( ident,CopyArgs(args), _identLower )
+	End Method
+
+	Method Semant:TExpr()
+		If exprType Return Self
+
+		'If _env.FuncScope().IsStatic() Err "Illegal use of Super."
+
+		classScope=_env.ClassScope()
+		superClass=classScope.superClass
+		
+		If Not superClass Err "Type has no super class."
+		
+		args=SemantArgs( args )
+		Try
+			' get the local version of the method from local class scope
+			origFuncDecl=classScope.FindFuncDecl(IdentLower(),args,,,,True,SCOPE_CLASS_LOCAL)
+		Catch errorMessage:String
+			If errorMessage.StartsWith("Compile Error") Then
+				Throw errorMessage
+			Else
+				' if there isn't one, we'll just use a Super version of it anyway as a reference.
+				origFuncDecl=classScope.FindFuncDecl(IdentLower(),args,,,,,SCOPE_CLASS_HEIRARCHY)
+			End If
+		End Try
+
+		funcDecl=superClass.FindFuncDecl( IdentLower(),args,,,,,SCOPE_CLASS_HEIRARCHY )
+
+		If Not funcDecl Err "Can't find superclass method '"+ident+"'."
+
+		' ensure the super function has been semanted
+		funcDecl.Semant()
+		
+		' for static scope, we need to change class scope to that of the super class
+		If _env.FuncScope().IsStatic() Then
+			classScope = TClassDecl(funcDecl.scope)
+		End If
+		
+		args=CastArgs( args,funcDecl )
+		exprType=funcDecl.retType
+		Return Self
+	End Method
+
+	Method Trans$()
+		Return _trans.TransInvokeSuperExpr( Self )
+	End Method
+
+End Type
+
+'	Self
+Type TSelfExpr Extends TExpr
+
+	Method Copy:TExpr()
+		Return New TSelfExpr
+	End Method
+
+	Method Semant:TExpr()
+		If exprType Return Self
+
+		'If _env.FuncScope().IsStatic() Err "Illegal use of Self within static scope."
+		Local scope:TClassDecl = _env.ClassScope()
+		If Not scope Then
+			Err "'Self' can only be used within methods."
+		End If
+		
+		Local funcScope:TFuncDecl = _env.FuncScope()
+		If funcScope.IsAnyMethod() Then
+			exprType=New TObjectType.Create( scope )
+			TObjectType(exprType).instance = True
+		Else
+			exprType=New TClassType.Create( scope )
+		End If
+
+		Return Self
+	End Method
+
+	Method Trans$()
+		Return _trans.TransSelfExpr( Self )
+	End Method
+
+End Type
+
+Const CAST_EXPLICIT:Int=1
+
+Type TCastExpr Extends TExpr
+	Field ty:TType
+	Field expr:TExpr
+	Field flags:Int
+
+	Method Create:TCastExpr( ty:TType,expr:TExpr,flags:Int=0 )
+		Self.ty=ty
+		Self.expr=expr
+		Self.flags=flags
+		Return Self
+	End Method
+
+	Method Copy:TExpr()
+		Return New TCastExpr.Create( ty,CopyExpr(expr),flags )
+	End Method
+
+	Method Semant:TExpr()
+
+		If exprType Return Self
+
+		ty=ty.Semant()
+		
+		If TInvokeExpr(expr) Then
+			TInvokeExpr(expr).isRhs = True
+		Else If TIdentExpr(expr) Then
+			TIdentExpr(expr).isRhs = True
+		End If
+		
+		expr=expr.Semant()
+
+		Local src:TType=expr.exprType
+		
+		'equal?
+		If src.EqualsType( ty ) Return expr
+
+		'upcast?
+		If src.ExtendsType( ty )
+			'cast from void[] to T[]
+			If TArrayType(src) And TVoidType( TArrayType(src).elemType )
+				Return New TConstExpr.Create( ty,"" ).Semant()
+			EndIf
+			
+			If src._flags & TType.T_VARPTR Then
+				exprType = ty
+				Return Self
+			End If
+
+			If TStringType(ty) And TObjectType(src)
+				' only if explicitly cast
+				If flags & CAST_EXPLICIT Then
+					exprType = ty
+					'Return Self
+				End If
+			End If
+			'Box/unbox?...
+			'If TObjectType( ty ) And Not TObjectType( src )
+
+				'Box!
+			'	expr=New TNewObjectExpr.Create( ty,[expr] ).Semant()
+
+			'Else
+			If TObjectType( src ) And Not TObjectType( ty ) And Not TStringType( ty )
+
+				'Unbox!
+				Local op$
+				'If TBoolType( ty )
+				'	op="ToBool"
+				'Else
+				If TIntType( ty )
+					op="ToInt"
+				Else If TFloatType( ty )
+					op="ToFloat"
+				Else If TStringType( ty )
+					op="ToString"
+				Else If IsPointerType(ty, 0, TType.T_POINTER)
+					exprType = ty
+					If flags = CAST_EXPLICIT Then
+						Return Self
+					Else
+						If Not TObjectType( src ).classDecl.IsExtern() Then
+							Return Self
+						Else
+							Return expr
+						End If
+					End If
+				Else
+					InternalErr
+				EndIf
+				Local fdecl:TFuncDecl=src.GetClass().FindFuncDecl( op,,,,,,SCOPE_ALL )
+				expr=New TInvokeMemberExpr.Create( expr,fdecl ).Semant()
+
+			EndIf
+			
+			If TNullType(src) Then
+				exprType = ty
+			End If
+			
+			If TBoolType(src) And (TNumericType(ty) Or TStringType(ty)) Then
+				exprType = ty
+			End If
+			
+			If TNumericType(src) And (TNumericType(ty) Or TStringType(ty)) Then
+				' intrinsics can only cast between selves
+				If (TIntrinsicType(src) And TIntrinsicType(ty)=Null) Or (TIntrinsicType(ty) And TIntrinsicType(src)=Null) Then
+					If TFloat64Type(src) Or TFloat64Type(ty) Then
+						If (TFloat64Type(src) And (TLongType(ty) Or TULongType(ty))) Or (TFloat64Type(ty) And (TLongType(src) Or TULongType(src))) Then
+							' ok
+						Else
+							Err "Unable to convert from "+src.ToString()+" to "+ty.ToString()+"."
+						End If
+					Else
+						Err "Unable to convert from "+src.ToString()+" to "+ty.ToString()+"."
+					End If
+				Else If TIntrinsicType(src) And TIntrinsicType(ty) Then
+					If (TFloat64Type(src) And TFloat64Type(ty)=Null) Or (TFloat64Type(ty) And TFloat64Type(src)=Null) Then
+						Err "Unable to convert from "+src.ToString()+" to "+ty.ToString()+"."
+					End If
+				End If
+				exprType = ty
+			End If
+			
+			If TObjectType(ty) And (TObjectType(src) Or TStringType(src) Or TArrayType(src)) Then
+				exprType = ty
+				Return Self
+			End If
+			
+			If TFunctionPtrType(src) And IsPointerType(ty, 0, TType.T_POINTER) Then
+				exprType = ty
+			End If
+
+		Else If TBoolType( ty )
+
+			If TVoidType( src )
+				Err "Cannot convert from Void to Int."
+			EndIf
+
+			If  flags & CAST_EXPLICIT
+				exprType=ty
+			EndIf
+
+		Else If ty.ExtendsType( src )
+
+			If flags & CAST_EXPLICIT
+
+				'if both objects or both non-objects...
+				If (TObjectType(ty)<>Null)=(TObjectType(src)<>Null) Then
+					exprType=ty
+					
+					If TFunctionPtrType(ty) And TInvokeExpr(expr) And Not TInvokeExpr(expr).invokedWithBraces Then
+						Return expr
+					End If
+					
+					Return Self
+				End If
+				
+				If (TStringType(ty) Or TArrayType(ty)) And TObjectType(src) Then
+					exprType=ty
+					Return Self
+				End If
+			'Else ' if not explicitly cast, we can't just auto-cast it ourselves here.
+				'If (TObjectType(ty)<>Null) And (TObjectType(src)<>Null) exprType=ty
+			EndIf
+
+		EndIf
+
+
+		If TArrayType(ty) And TArrayType(src) Then
+			If TArrayType(ty).dims = TArrayType(src).dims Then
+				If TArrayExpr(expr) Then
+					Local last:TType
+					For Local e:TExpr = EachIn TArrayExpr(expr).exprs
+						If TNullType(e.exprType) Then
+							Err "Auto array element has no type"
+						End If
+
+						If TObjectType(TArrayType(ty).elemType) And TObjectType(TArrayType(ty).elemType).classDecl.ident = "Object" And (TStringType(e.exprType) Or TObjectType(e.exprType) Or TArrayType(e.exprType)) Then
+							' array takes generic objects, so we don't care if source elements are the same kinds.
+						Else
+							If last <> Null And Not last.EqualsType(e.exprType) Then
+								Err "Auto array elements must have identical types"
+							End If
+							If Not TArrayType(ty).elemType.EqualsType(e.exprType) Then
+								If (TObjectType(TArrayType(ty).elemType) = Null And TStringType(TArrayType(ty).elemType) = Null) Or (TObjectType(e.exprType) = Null And TStringType(e.exprType) = Null) Then
+									Err "Unable to convert from "+src.ToString()+" to "+ty.ToString()+"."
+								Else If TStringType(e.exprType) = Null And Not TObjectType(e.exprType).ExtendsType(TObjectType(TArrayType(ty).elemType)) Then
+									Err "Unable to convert from "+src.ToString()+" to "+ty.ToString()+"."
+								End If
+							End If
+						End If
+						
+						last = e.exprType
+					Next
+				End If
+				
+				exprType = ty
+				Return Self
+			End If
+		End If
+
+		'If TStringType(src) And TStringVarPtrType(ty) Then
+		'	exprType = ty
+		'	Return Self
+		'End If
+
+'		If TArrayType(src) And TPointerType(ty) Then
+'			exprType = ty
+'			Return expr
+'		End If
+
+		If TFunctionPtrType(ty) And TInvokeExpr(expr) Then
+			' a function ptr to function ptr
+			If Not TInvokeExpr(expr).invokedWithBraces Then
+				src = New TFunctionPtrType
+				TFunctionPtrType(src).func = TInvokeExpr(expr).decl
+
+				' signatures should match
+				If TInvokeExpr(expr).decl.equalsFunc(TFunctionPtrType(ty).func)  Then
+					exprType = ty
+					Return expr
+				End If
+			Else
+				' return type should be function ptr?
+				Local retType:TType = expr.exprType
+				If TFunctionPtrType(retType) And TFunctionPtrType(ty).func.EqualsFunc(TFunctionPtrType(retType).func) Then
+					exprType = retType
+					Return expr
+				End If
+			End If
+		End If
+
+		'If TIntType(ty) And Not IsPointerType(ty, 0, TType.T_POINTER) And IsPointerType(src, 0, TType.T_POINTER) Then
+		'	exprType = ty
+		'	If flags & CAST_EXPLICIT Then
+		'		Return Self
+		'	End If
+		'	Return expr
+		'End If
+
+		' explicit cast to number
+		If IsNumericType(ty) And IsPointerType(src, 0, TType.T_POINTER) Then
+			If flags = CAST_EXPLICIT Then
+				exprType = ty
+				Return Self
+			Else
+				exprType = Null
+			End If
+		End If
+
+'		If TPointerType(ty) And TIntType(src) Then
+'			exprType = ty
+'			Return expr
+'		End If
+
+'		If TIntType(ty) And TObjectType(src) Then
+' DebugStop ' Bah woz ere
+'			exprType = ty
+'			Return expr
+'		End If
+
+		If TObjectType(src) And TNullDecl(TObjectType(src).classDecl) Then
+			exprType = ty
+			Return expr
+		End If
+
+		If TObjectType(src) And TObjectType(ty) And (ty._flags & TType.T_VAR) Then ' TODO : May be VARPTR instead?
+			'exprType = NewPointerType(TType.T_BYTE)
+			exprType = ty
+			Return Self
+		End If
+		
+		If TStringType(src) And ((src._flags & TType.T_CHAR_PTR) Or (src._flags & TType.T_SHORT_PTR)) And TStringType(ty) Then
+			exprType = ty
+			Return Self
+		End If
+		
+		' cast from "some kind of object" array to Object[]
+		If TArrayType(ty) And TArrayType(src)
+			If (TObjectType(TArrayType(src).elemType) Or TStringType(TArrayType(src).elemType) Or TArrayType(TArrayType(src).elemType)) And TObjectType(TArrayType(ty).elemType) Then
+				If TObjectType(TArrayType(ty).elemType).classDecl.ident = "Object" Then
+					exprType = ty
+					Return Self
+				End If
+			Else
+				If TArrayType(ty).dims = TArrayType(src).dims Then
+					exprType = ty
+				End If
+			End If
+		End If
+		
+		If TArrayType(ty) And TObjectType(src) 
+			If TObjectType(src).classDecl.ident = "___Array" Then
+				exprType = ty
+				Return expr
+			Else If  TObjectType(src).classDecl.ident = "Object" Then
+				exprType = ty
+				Return Self
+			End If
+		End If
+
+		If IsPointerType(ty, 0, TType.T_POINTER | TType.T_CHAR_PTR | TType.T_SHORT_PTR) Then
+			If IsNumericType(src) And Not (src._flags & TType.T_VARPTR) Then
+				'If IsPointerType(ty,0,TType.T_POINTER) Then
+				'	exprType = TNumericType(src).ToPointer()
+				'Else
+					exprType = ty
+				'End If
+				Return Self
+			Else If TNumericType(src) And (src._flags & TType.T_VARPTR) Then
+				exprType = expr.exprType
+			Else If TArrayType(src) Then
+			
+				' for functions and index access, use a new local variable
+				If Not TVarExpr(expr) And Not TMemberVarExpr(expr) Then
+					Local tmp:TLocalDecl=New TLocalDecl.Create( "", expr.exprType, expr,, True )
+					tmp.Semant()
+					Local v:TVarExpr = New TVarExpr.Create( tmp )
+					expr = New TStmtExpr.Create( New TDeclStmt.Create( tmp ), v ).Semant()
+				End If
+			
+				If TNumericType(TArrayType(src).elemType) Then
+					exprType = TNumericType(TArrayType(src).elemType).ToPointer()
+					Return Self
+				Else
+					' map arrays to byte ptr
+					exprType = TType.MapToPointerType(New TByteType)
+				End If
+			Else If TStringType(src) Then
+				exprType = ty
+				Return Self
+			End If
+		End If
+		
+		If TStringType(src) And TStringType(ty) And (ty._flags & TType.T_VAR) Then
+			exprType = ty
+			Return Self
+		End If
+
+		If TVarPtrType(ty) Then
+			If Not TVarExpr(expr) And Not TMemberVarExpr(expr) And Not (TStmtExpr(expr) And TIndexExpr(TStmtExpr(expr).expr)) Then
+				If Not TIndexExpr(expr) Or (TIndexExpr(expr) And Not TVarExpr(TIndexExpr(expr).expr) And Not TMemberVarExpr(TIndexExpr(expr).expr))  Then
+					Err "Subexpression for 'Ptr' must be a variable"
+				End If
+			End If
+			exprType = src.Copy()
+			exprType._flags :| TType.T_VARPTR
+			ty = exprType
+			Return Self
+		End If
+		
+		If TFunctionPtrType(ty) And IsPointerType(src, 0, TType.T_POINTER) Then
+			exprType = ty
+			Return Self
+		End If
+
+		If TObjectType(ty) And TObjectType(src) And TObjectType(src).classdecl.IsInterface() And flags & CAST_EXPLICIT Then
+			exprType = ty
+			Return Self
+		End If
+
+		If Not exprType
+			Err "Unable to convert from "+src.ToString()+" to "+ty.ToString()+"."
+		EndIf
+
+		If TConstExpr( expr ) Then
+
+			Local ex:TExpr = EvalConst()
+			If flags & CAST_EXPLICIT Then
+				Return New TCastExpr.Create(exprType, ex, 1).Semant()
+			Else
+				Return ex
+			End If
+		End If
+		
+		Return Self
+	End Method
+
+	Method Eval$()
+		Local val$=expr.Eval()
+		If TBoolType( exprType )
+			If TIntegralType(expr.exprType)
+				If Long( val ) Return "1"
+				Return ""
+			Else If TDecimalType( expr.exprType )
+				If Double( val ) Return "1"
+				Return ""
+			Else If TStringType( expr.exprType )
+				If val.Length Return "1"
+				Return ""
+			EndIf
+		Else If TIntType( exprType )
+			If TBoolType( expr.exprType )
+				If val Return "1"
+				Return "0"
+			EndIf
+			Return Int( val )
+		Else If TUIntType( exprType )
+			Return Long( val )
+		Else If TShortType( exprType )
+			Return Short( val )
+		Else If TFloatType( exprType )
+			Return Float( val )
+		Else If TDoubleType( exprType )
+			Return Double( val )
+		Else If TLongType( exprType )
+			Return Long( val )
+		Else If TULongType( exprType )
+			Return Long( val )
+		Else If TSizeTType( exprType )
+			Return Long( val )
+		Else If TInt128Type( exprType )
+			Return Long( val )
+		Else If TFloat128Type( exprType )
+			Return Float( val )
+		Else If TDouble128Type( exprType )
+			Return Float( val )
+		Else If TFloat64Type( exprType )
+			Return Float( val )
+		Else If TStringType( exprType )
+			If TBoolType( expr.exprType )
+				If val Return "1"
+				Return "0"
+			EndIf
+			Return String( val )
+		Else If TByteType( exprType )
+			Return Byte( val )
+		Else If TWParamType( exprType )
+			Return Long( val )
+		Else If TLParamType( exprType )
+			Return Long( val )
+		Else If TObjectType( exprType )
+			If TStringType( expr.exprType )
+				Return val
+			End If
+		EndIf
+		Return Super.Eval()
+	End Method
+
+	Method Trans$()
+		Return _trans.TransCastExpr( Self )
+	End Method
+
+	Method ToString$()
+		Local t$="TCastExpr(" + ty.ToString()
+		If expr t:+","+expr.ToString()
+		Return t+")"
+	End Method
+
+End Type
+
+'op = '+', '-', '~'
+Type TUnaryExpr Extends TExpr
+	Field op$,expr:TExpr
+
+	Method Create:TUnaryExpr( op$,expr:TExpr )
+		Self.op=op
+		Self.expr=expr
+		Return Self
+	End Method
+
+	Method Copy:TExpr()
+		Return New TUnaryExpr.Create( op,CopyExpr(expr) )
+	End Method
+
+	Method Semant:TExpr()
+		If exprType Return Self
+
+		Select op
+		Case "+","-"
+			expr=expr.Semant()
+			If Not TNumericType( expr.exprType ) Or IsPointerType(expr.exprType) Then
+				Err expr.ToString()+" must be numeric for use with unary operator '"+op+"'"
+			End If
+			exprType=expr.exprType
+			' Remove Var-ness, if required. "expr" will still be "Var"
+			If exprType._flags & TType.T_VAR Then
+				exprType = exprType.Copy()
+				exprType._flags :~ TType.T_VAR
+			End If
+		Case "~~"
+			expr=expr.Semant()
+			If Not TIntegralType(expr.exprType) Or IsPointerType(expr.exprType) Then
+				Err "Bitwise complement can only be used with integers"
+			End If
+			If TByteType(expr.exprType) Or TShortType(expr.exprType) Then
+				expr=expr.SemantAndCast( New TIntType )
+				exprType=New TIntType
+			Else
+				exprType = expr.exprType
+			End If
+		Case "not"
+			expr=expr.SemantAndCast( New TBoolType,CAST_EXPLICIT )
+			exprType=New TBoolType
+		Default
+			InternalErr
+		End Select
+
+		If TConstExpr( expr ) Return EvalConst()
+		Return Self
+	End Method
+
+	Method Eval$()
+		Local val$=expr.Eval()
+		Select op
+		Case "~~"
+			Return ~Int( val )
+		Case "+"
+			Return val
+		Case "-"
+			If val.StartsWith( "-" ) Return val[1..]
+			Return "-"+val
+		Case "not"
+			If val Return ""
+			Return "1"
+		End Select
+		InternalErr
+	End Method
+
+	Method Trans$()
+		Return _trans.TransUnaryExpr( Self )
+	End Method
+
+End Type
+
+Type TBinaryExpr Extends TExpr
+	Field op$
+	Field lhs:TExpr
+	Field rhs:TExpr
+
+	Method Trans$()
+		Return _trans.TransBinaryExpr( Self )
+	End Method
+
+	Method ToString$()
+		Return "(" + lhs.ToString() + " " + op + " " + rhs.ToString() + ")"
+	End Method
+
+End Type
+
+' * / + / & ~ | ^ shl shr
+Type TBinaryMathExpr Extends TBinaryExpr
+
+	Method Create:TBinaryMathExpr( op$,lhs:TExpr,rhs:TExpr )
+		Self.op=op
+		Self.lhs=lhs
+		Self.rhs=rhs
+		Return Self
+	End Method
+
+	Method Copy:TExpr()
+		Return New TBinaryMathExpr.Create( op,CopyExpr(lhs),CopyExpr(rhs) )
+	End Method
+
+	Method Semant:TExpr()
+		If exprType Return Self
+
+		lhs=lhs.Semant()
+
+		If TIdentExpr(rhs) Then
+			TIdentExpr(rhs).isRhs = True
+		End If
+
+		rhs=rhs.Semant()
+		
+		' operator overload?
+		If TObjectType(lhs.exprType) Then
+			Local args:TExpr[] = [rhs]
+			Try
+				Local decl:TFuncDecl = TFuncDecl(TObjectType(lhs.exprType).classDecl.FindFuncDecl(op, args,,,,True,SCOPE_CLASS_HEIRARCHY))
+				If decl Then
+					Return New TInvokeMemberExpr.Create( lhs, decl, args ).Semant()
+				End If
+			Catch error:String
+				If error.StartsWith("Compile Error") Then
+					Throw error
+				Else
+					Err "Operator " + op + " cannot be used with Objects."
+				End If
+			End Try
+		End If
+
+		Select op
+		Case "&","~~","|","shl","shr"
+			If TFloat128Type(lhs.exprType) Then
+				exprType=New TInt128Type
+			Else If TDouble128Type(lhs.exprType) Then
+				exprType=New TInt128Type
+			Else If TFloat64Type(lhs.exprType) Then
+				exprType=New TInt128Type
+			Else If TDoubleType(lhs.exprType) Then
+				exprType=New TLongType
+			Else If TFloatType(lhs.exprType) Then
+				exprType=New TIntType
+			Else If TUIntType(lhs.exprType) Then
+				exprType=New TUIntType
+			Else If TLongType(lhs.exprType) Then
+				exprType=New TLongType
+			Else If TULongType(lhs.exprType) Then
+				exprType=New TULongType
+			Else If TSizeTType(lhs.exprType) Then
+				exprType=New TSizeTType
+			Else If TWParamType(lhs.exprType) Then
+				exprType=New TWParamType
+			Else If TLParamType(lhs.exprType) Then
+				exprType=New TLParamType
+			Else
+				exprType=New TIntType
+			End If
+		Case "^"
+			exprType=New TDoubleType
+		Default
+			exprType=BalanceTypes( lhs.exprType,rhs.exprType )
+			If TStringType( exprType )
+				If op<>"+"
+					Err "Illegal string operator."
+				EndIf
+			Else If TVoidType( exprType ) Then
+				Err "Illegal operation on a void expression."
+			Else If Not TNumericType( exprType ) And Not IsPointerType( exprType, 0, TType.T_POINTER ) And Not TArrayType( exprType ) And Not TBoolType( exprType )
+				Err "Illegal expression type."
+			Else If IsPointerType( exprType, 0, TType.T_POINTER ) And op <> "+" And op <> "-" Then
+				Err "Illegal expression type."
+			Else If IsPointerType( lhs.exprType, 0, TType.T_POINTER ) And IsPointerType( rhs.exprType, 0, TType.T_POINTER ) And op <> "-" Then
+				Err "Illegal expression type."
+			EndIf
+		End Select
+
+		If (op = "+" Or op = "-") And IsPointerType(exprType, 0, TType.T_POINTER) And TNumericType(lhs.exprType) Then
+			' with pointer addition we don't cast the numeric to a pointer
+		Else
+			lhs=lhs.Cast( exprType )
+		End If
+		
+		If (op = "+" Or op = "-") And IsPointerType(exprType, 0, TType.T_POINTER) And TNumericType(rhs.exprType) Then
+			' with pointer addition we don't cast the numeric to a pointer
+		Else
+			rhs=rhs.Cast( exprType )
+		End If
+		
+		If IsPointerType( lhs.exprType, 0, TType.T_POINTER ) And IsPointerType( rhs.exprType, 0, TType.T_POINTER ) And op = "-" Then
+			exprType = New TIntType
+		End If
+
+		If TConstExpr( lhs ) And TConstExpr( rhs ) Return EvalConst()
+
+		Return Self
+	End Method
+
+	Method Eval$()
+		Local lhs$=Self.lhs.Eval()
+		Local rhs$=Self.rhs.Eval()
+		If TIntType( exprType )
+			Local x:Int=Int(lhs),y:Int=Int(rhs)
+			Select op
+			Case "^" Return x^y
+			Case "*" Return x*y
+			Case "/" Return x/y
+			Case "mod" Return x Mod y
+			Case "shl" Return x Shl y
+			Case "shr" Return x Shr y
+			Case "+" Return x + y
+			Case "-" Return x - y
+			Case "&" Return x & y
+			Case "~~" Return x ~ y
+			Case "|" Return x | y
+			End Select
+		Else If TLongType( exprType ) Or TSizeTType(exprType) Or TUIntType(exprType) Or TULongType(exprType) Or TInt128Type(exprType) Or TWParamType(exprType) Or TLParamType(exprType) 
+			Local x:Long=Long(lhs),y:Long=Long(rhs)
+			Select op
+			Case "^" Return x^y
+			Case "*" Return x*y
+			Case "/" Return x/y
+			Case "mod" Return x Mod y
+			Case "shl" Return x Shl y
+			Case "shr" Return x Shr y
+			Case "+" Return x + y
+			Case "-" Return x - y
+			Case "&" Return x & y
+			Case "~~" Return x ~ y
+			Case "|" Return x | y
+			End Select
+		Else If TFloatType( exprType )
+			Local x:Float=Float(lhs),y:Float=Float(rhs)
+			Select op
+			Case "^" Return x^y
+			Case "*" Return x * y
+			Case "/" Return x / y
+			Case "mod" Return x Mod y
+			Case "+" Return x + y
+			Case "-" Return x - y
+			End Select
+		Else If TDoubleType( exprType ) Or TFloat128Type(exprType) Or TDouble128Type(exprType) Or TFloat64Type(exprType)
+			Local x:Double=Double(lhs),y:Double=Double(rhs)
+			Select op
+			Case "^" Return x^y
+			Case "*" Return x * y
+			Case "/" Return x / y
+			Case "mod" Return x Mod y
+			Case "+" Return x + y
+			Case "-" Return x - y
+			End Select
+		Else If TStringType( exprType )
+			Select op
+			Case "+" 
+				_appInstance.removeStringConst(lhs)
+				_appInstance.removeStringConst(rhs)
+				Return lhs+rhs
+			End Select
+		EndIf
+		InternalErr
+	End Method
+
+End Type
+
+'=,<>,<,<=,>,>=
+Type TBinaryCompareExpr Extends TBinaryExpr
+	Field ty:TType
+
+	Method Create:TBinaryCompareExpr( op$,lhs:TExpr,rhs:TExpr )
+		Self.op=op
+		Self.lhs=lhs
+		Self.rhs=rhs
+		Return Self
+	End Method
+
+	Method Copy:TExpr()
+		Return New TBinaryCompareExpr.Create( op,CopyExpr(lhs),CopyExpr(rhs) )
+	End Method
+
+	Method Semant:TExpr()
+		If exprType Return Self
+
+		lhs=lhs.Semant()
+		rhs=rhs.Semant()
+
+		' operator overload?
+		If TObjectType(lhs.exprType) Then
+			Local args:TExpr[] = [rhs]
+			Try
+				Local decl:TFuncDecl = TFuncDecl(TObjectType(lhs.exprType).classDecl.FindFuncDecl(op, args,,,,True,SCOPE_CLASS_HEIRARCHY))
+				If decl Then
+					Return New TInvokeMemberExpr.Create( lhs, decl, args ).Semant()
+				End If
+			Catch error:String
+				' no overload, continue...
+			End Try
+		End If
+
+
+		ty=BalanceTypes( lhs.exprType,rhs.exprType )
+
+		lhs=lhs.Cast( ty )
+		rhs=rhs.Cast( ty )
+
+		exprType=New TBoolType
+
+		If TConstExpr( lhs ) And TConstExpr( rhs ) Return EvalConst()
+
+		Return Self
+	End Method
+
+	Method Eval$()
+		Local r:Int=-1
+		If TBoolType( ty )
+			Local lhs:Int=Int(Self.lhs.Eval())
+			Local rhs:Int=Int(Self.rhs.Eval())
+			Select op
+			Case "="  r=(lhs= rhs)
+			Case "<>" r=(lhs<>rhs)
+			End Select
+		Else If TIntType( ty )
+			Local lhs:Int=Int( Self.lhs.Eval() )
+			Local rhs:Int=Int( Self.rhs.Eval() )
+			Select op
+			Case "="  r=(lhs= rhs)
+			Case "<>" r=(lhs<>rhs)
+			Case "<"  r=(lhs< rhs)
+			Case "<=", "=<" r=(lhs<=rhs)
+			Case ">"  r=(lhs> rhs)
+			Case ">=", "=>" r=(lhs>=rhs)
+			End Select
+		Else If TLongType( ty ) Or TSizeTType( ty ) Or TUIntType( ty ) Or TULongType( ty ) Or TInt128Type(ty) Or TWParamType(ty) Or TLParamType(ty)
+			Local lhs:Long=Long( Self.lhs.Eval() )
+			Local rhs:Long=Long( Self.rhs.Eval() )
+			Select op
+			Case "="  r=(lhs= rhs)
+			Case "<>" r=(lhs<>rhs)
+			Case "<"  r=(lhs< rhs)
+			Case "<=", "=<" r=(lhs<=rhs)
+			Case ">"  r=(lhs> rhs)
+			Case ">=", "=>" r=(lhs>=rhs)
+			End Select
+		Else If TFloatType( ty )
+			Local lhs:Float=Float( Self.lhs.Eval() )
+			Local rhs:Float=Float( Self.rhs.Eval() )
+			Select op
+			Case "="  r=(lhs= rhs)
+			Case "<>" r=(lhs<>rhs)
+			Case "<"  r=(lhs< rhs)
+			Case "<=", "=<" r=(lhs<=rhs)
+			Case ">"  r=(lhs> rhs)
+			Case ">=", "=>" r=(lhs>=rhs)
+			End Select
+		Else If TDoubleType( ty ) Or TFloat128Type(ty) Or TDouble128Type(ty) Or TFloat64Type(ty)
+			Local lhs:Double=Double( Self.lhs.Eval() )
+			Local rhs:Double=Double( Self.rhs.Eval() )
+			Select op
+			Case "="  r=(lhs= rhs)
+			Case "<>" r=(lhs<>rhs)
+			Case "<"  r=(lhs< rhs)
+			Case "<=", "=<" r=(lhs<=rhs)
+			Case ">"  r=(lhs> rhs)
+			Case ">=", "=>" r=(lhs>=rhs)
+			End Select
+		Else If TStringType( ty )
+			Local lhs:String=String( Self.lhs.Eval() )
+			Local rhs:String=String( Self.rhs.Eval() )
+			Select op
+			Case "="  r=(lhs= rhs)
+			Case "<>" r=(lhs<>rhs)
+			Case "<"  r=(lhs< rhs)
+			Case "<=", "=<" r=(lhs<=rhs)
+			Case ">"  r=(lhs> rhs)
+			Case ">=", "=>" r=(lhs>=rhs)
+			End Select
+		EndIf
+		If r=1 Return "1"
+		If r=0 Return ""
+		InternalErr
+	End Method
+End Type
+
+'and, or
+Type TBinaryLogicExpr Extends TBinaryExpr
+
+	Method Create:TBinaryLogicExpr( op$,lhs:TExpr,rhs:TExpr )
+		Self.op=op
+		Self.lhs=lhs
+		Self.rhs=rhs
+		Return Self
+	End Method
+
+	Method Copy:TExpr()
+		Return New TBinaryLogicExpr.Create( op,CopyExpr(lhs),CopyExpr(rhs) )
+	End Method
+
+	Method Semant:TExpr()
+		If exprType Return Self
+
+		lhs=lhs.SemantAndCast( New TBoolType,CAST_EXPLICIT )
+		rhs=rhs.SemantAndCast( New TBoolType,CAST_EXPLICIT )
+
+		exprType=New TBoolType
+
+		If TConstExpr( lhs ) And TConstExpr( rhs ) Return EvalConst()
+
+		Return Self
+	End Method
+
+	Method Eval$()
+		Select op
+		Case "and" If lhs.Eval() And rhs.Eval() Return "1" Else Return ""
+		Case "or"  If lhs.Eval() Or rhs.Eval() Return "1" Else Return ""
+		End Select
+		InternalErr
+	End Method
+End Type
+
+Type TIndexExpr Extends TExpr
+	Field expr:TExpr
+	Field index:TExpr[]
+
+	Method Create:TIndexExpr( expr:TExpr,index:TExpr[] )
+		Self.expr=expr
+		Self.index=index
+		Return Self
+	End Method
+
+	Method Copy:TExpr()
+		If exprType Return Self
+		
+		Local ind:TExpr[]
+		For Local i:Int = 0 Until index.length
+			ind = ind + [CopyExpr(index[i])]
+		Next
+		Return New TIndexExpr.Create( CopyExpr(expr),ind )
+	End Method
+
+	Method Semant:TExpr()
+		If exprType Return Self
+
+		expr=expr.Semant()
+
+		' for functions and index access, use a new local variable
+		If Not TVarExpr(expr) And Not TMemberVarExpr(expr) Then
+			Local tmp:TLocalDecl=New TLocalDecl.Create( "", TType.MapVarPointerToPointerType(expr.exprType.Copy()), expr,, True )
+			tmp.Semant()
+			Local v:TVarExpr = New TVarExpr.Create( tmp )
+			expr = New TStmtExpr.Create( New TDeclStmt.Create( tmp ), v ).Semant()
+		End If
+
+		For Local i:Int = 0 Until index.length
+			If Not(TNumericType(expr.exprType) And IsPointerType( expr.exprType, 0 , TType.T_POINTER | TType.T_VARPTR)) Then
+				index[i]=index[i].SemantAndCast( New TUIntType, True )
+			Else
+				index[i]=index[i].Semant()
+			End If
+		Next
+
+		If TStringType( expr.exprType )
+			exprType=New TIntType
+			If index.length > 1 Then
+				Err "Illegal subexpression for string index"
+			End If
+		Else If TArrayType( expr.exprType )
+			exprType= TArrayType( expr.exprType ).elemType
+
+			If TArrayType( expr.exprType ).dims > 1 Then
+
+				' a multi-dimensional array of arrays is slightly more complex
+				If TArrayType(exprType) Then
+
+				'	Local tmpArr:TLocalDecl=New TLocalDecl.Create( "", NewPointerType(TType.T_ARRAY), expr )
+				'	Local stmt:TExpr = New TStmtExpr.Create( New TDeclStmt.Create( tmp ), Self ).Semant()
+
+					Local sizeExpr:TExpr = New TArraySizeExpr.Create(expr, Null, index)
+					index = [sizeExpr]
+					Local tmp:TLocalDecl=New TLocalDecl.Create( "", NewPointerType(TType.T_UINT), sizeExpr,,True )
+					TArraySizeExpr(sizeExpr).val = tmp
+					Local stmt:TExpr = New TStmtExpr.Create( New TDeclStmt.Create( tmp ), Self ).Semant()
+					stmt.exprType = exprType
+
+					Return stmt
+				Else
+					Local sizeExpr:TExpr = New TArraySizeExpr.Create(expr, Null, index).Semant()
+					index = [sizeExpr]
+					Local tmp:TLocalDecl=New TLocalDecl.Create( "", NewPointerType(TType.T_UINT), sizeExpr,,True )
+					TArraySizeExpr(sizeExpr).val = tmp
+					Local stmt:TExpr = New TStmtExpr.Create( New TDeclStmt.Create( tmp ), Self ).Semant()
+					stmt.exprType = exprType
+					Return stmt
+				End If
+			End If
+			'If TObjectType(exprType) And Not TStringType(exprType) And Not TArrayType(exprType) Then
+			'	Local tmp:TLocalDecl=New TLocalDecl.Create( "", exprType,expr )
+			'	Local stmt:TExpr = New TStmtExpr.Create( New TDeclStmt.Create( tmp ),New TVarExpr.Create( tmp ) ).Semant()
+			'	stmt.exprType = exprType
+			'	Return stmt
+			'End If
+		Else If TNumericType(expr.exprType) And IsPointerType( expr.exprType, 0 , TType.T_POINTER | TType.T_VARPTR)' And Not TFunctionPtrType( expr.exprType )
+			exprType=TType.MapPointerToPrim(TNumericType(expr.exprType))
+			'exprType=TType.intType
+		Else If TObjectType(expr.exprType) And TObjectType(expr.exprType).classDecl.IsStruct() And IsPointerType( expr.exprType, 0 , TType.T_POINTER | TType.T_VARPTR)' And Not TFunctionPtrType( expr.exprType )
+			exprType = expr.exprType
+		Else
+			Err "Only strings, arrays and pointers may be indexed."
+		EndIf
+
+		Return Self
+	End Method
+
+	Method SemantSet:TExpr( op$,rhs:TExpr )
+		Return Semant()
+		'Return Self
+	End Method
+	
+	Method SemantFunc:TExpr( args:TExpr[] , throwError:Int = True, funcCall:Int = False )
+		Local ex:TExpr = Semant()
+		
+		If TArrayType( expr.exprType ) And TFunctionPtrType(exprType) Then
+			exprType = TFunctionPtrType(exprType).func.retType
+		End If
+		
+		Return ex
+	End Method
+
+
+	Method Trans$()
+		Return _trans.TransIndexExpr( Self )
+	End Method
+
+	Method TransVar$()
+		Return _trans.TransIndexExpr( Self )
+	End Method
+
+	Method ToString$()
+		Return "<TIndexExpr<"+ expr.ToString() +"[" + index[0].ToString() + "]>>"
+	End Method
+	
+End Type
+
+Type TSliceExpr Extends TExpr
+	Field expr:TExpr
+	Field from:TExpr
+	Field term:TExpr
+
+	Method Create:TSliceExpr( expr:TExpr,from:TExpr,term:TExpr )
+		Self.expr=expr
+		Self.from=from
+		Self.term=term
+		Return Self
+	End Method
+
+	Method Copy:TExpr()
+		Return New TSliceExpr.Create( CopyExpr(expr),CopyExpr(from),CopyExpr(term) )
+	End Method
+
+	Method Semant:TExpr()
+		If exprType Return Self
+
+		expr=expr.Semant()
+		If (TArrayType( expr.exprType ) And TArrayType( expr.exprType ).dims = 1) Or TStringType( expr.exprType )
+			If from from=from.SemantAndCast( New TIntType )
+			If term term=term.SemantAndCast( New TIntType )
+
+			exprType=expr.exprType
+			' remove var-ness
+			If exprType._flags & TType.T_VAR Then
+				exprType = exprType.Copy()
+				exprType._flags :~ TType.T_VAR
+			End If
+		Else
+			Err "Slices can only be used with strings or one dimensional arrays"
+		EndIf
+
+'		If TConstExpr( expr ) And TConstExpr( from ) And TConstExpr( term ) Return EvalConst()
+
+		Return Self
+	End Method
+
+	Method Eval$()
+		Local from:Int=Int( Self.from.Eval() )
+		Local term:Int=Int( Self.term.Eval() )
+		If TStringType( expr.exprType )
+			Return expr.Eval()[ from..term ]
+		Else If TArrayType( expr.exprType )
+			Todo
+		EndIf
+	End Method
+
+	Method Trans$()
+		Return _trans.TransSliceExpr( Self )
+	End Method
+End Type
+
+Type TArrayExpr Extends TExpr
+	Field exprs:TExpr[]
+	
+	Field toType:TType
+
+	Method Create:TArrayExpr( exprs:TExpr[] )
+		Self.exprs=exprs
+		Return Self
+	End Method
+
+	Method Copy:TExpr()
+		Local expr:TArrayExpr = New TArrayExpr.Create( CopyArgs(exprs) )
+		expr.toType = toType
+		Return expr
+	End Method
+
+	Method Semant:TExpr()
+		If exprType Return Self
+
+		If TIdentExpr(exprs[0]) Then
+			TIdentExpr(exprs[0]).isRhs = True
+		End If
+		exprs[0]=exprs[0].Semant()
+		Local ty:TType=exprs[0].exprType
+		' convert from varptr to ptr if required
+		ty = TType.MapVarPointerToPointerType(ty.Copy())
+		
+		If TInvokeExpr(exprs[0]) And Not TInvokeExpr(exprs[0]).invokedWithBraces Then
+			ty = New TFunctionPtrType
+			Local cp:TDecl = TInvokeExpr(exprs[0]).decl
+			TInvokeExpr(exprs[0]).decl = TFuncDecl(TInvokeExpr(exprs[0]).decl.Copy())
+			TInvokeExpr(exprs[0]).decl.actual = cp
+			TInvokeExpr(exprs[0]).decl.attrs :| FUNC_PTR
+			TFunctionPtrType(ty).func = TInvokeExpr(exprs[0]).decl
+
+			For Local i:Int=1 Until exprs.Length
+				If TIdentExpr(exprs[1]) Then
+					TIdentExpr(exprs[1]).isRhs = True
+				End If
+				exprs[i]=exprs[i].Semant()
+				
+				If TInvokeExpr(exprs[i]) And Not TInvokeExpr(exprs[i]).invokedWithBraces
+					cp = TInvokeExpr(exprs[i]).decl
+					
+					TInvokeExpr(exprs[i]).decl = TFuncDecl(TInvokeExpr(exprs[i]).decl.Copy())
+					TInvokeExpr(exprs[i]).decl.actual = cp
+					TInvokeExpr(exprs[i]).decl.attrs :| FUNC_PTR
+					
+					ty=BalanceTypes( ty, New TFunctionPtrType )
+				Else
+					ty=BalanceTypes( ty,exprs[i].exprType )
+				End If
+			Next
+		Else
+			For Local i:Int=1 Until exprs.Length
+				exprs[i]=exprs[i].Semant()
+				ty=BalanceTypes( ty,exprs[i].exprType )
+			Next
+		End If
+
+		Local comp:Int = True
+		Local last:TType
+		For Local i:Int=0 Until exprs.Length
+
+			Local expr:TExpr = exprs[i]
+
+			' don't cast null types
+			If TNullType(expr.exprType) <> Null Then
+				Err "Auto array element has no type"
+			End If
+
+			Local ety:TType = expr.exprType
+			If TBoolType(ety) Then
+				ety = New TIntType
+			End If
+			
+			If last <> Null And Not last.EqualsType(ety) Then
+				If (Not TConstExpr(expr) And Not IsNumericType(ety)) Or (TConstExpr(expr) And IsNumericType(ety) And Not TConstExpr(expr).CompatibleWithType(ty)) Then
+					Err "Auto array elements must have identical types : Index " + i
+				End If
+			End If
+			
+			If toType And TConstExpr(expr) And Not TConstExpr(expr).CompatibleWithType(toType) Then
+				comp = False
+			End If
+		
+			last = ety
+			
+			exprs[i]=expr.Cast( ty )
+		Next
+
+		If comp And toType Then
+			exprType=New TArrayType.Create( toType )
+		Else
+			exprType=New TArrayType.Create( ty )
+		End If
+		Return Self
+	End Method
+
+	Method Trans$()
+		Return _trans.TransArrayExpr( Self )
+	End Method
+
+End Type
+
+Type TArraySizeExpr Extends TExpr
+
+	Field expr:TExpr
+	Field val:TDecl
+	Field index:TExpr[]
+
+	Method Create:TArraySizeExpr( expr:TExpr, val:TDecl, index:TExpr[] )
+		Self.expr=expr
+		Self.val=val
+		Self.index=index
+		Return Self
+	End Method
+
+	Method Copy:TExpr()
+		Local ind:TExpr[]
+		For Local i:Int = 0 Until index.length
+			ind = ind + [CopyExpr(index[i])]
+		Next
+		Return New TArraySizeExpr.Create( CopyExpr(expr), val, ind )
+	End Method
+
+	Method Semant:TExpr()
+		If exprType Return Self
+
+		expr=expr.Semant()
+		
+		For Local i:Int = 0 Until index.length
+			index[i]=index[i].SemantAndCast( New TUIntType )
+		Next
+		
+		exprType=NewPointerType(TType.T_UINT)
+		Return Self
+	End Method
+
+	Method Trans$()
+		Return _trans.TransArraySizeExpr( Self )
+	End Method
+
+	Method ToString$()
+		Return expr.ToString() + ".Size"
+	End Method
+
+End Type
+
+Type TIdentTypeExpr Extends TExpr
+	Field cdecl:TClassDecl
+
+	Method Create:TIdentTypeExpr( ty:TType )
+		Self.exprType=ty
+		Return Self
+	End Method
+
+	Method Copy:TExpr()
+		Return New TIdentTypeExpr.Create( exprType )
+	End Method
+
+	Method _Semant()
+		If cdecl Return
+		exprType=exprType.Semant()
+		If TArrayType(exprType) And TObjectType(TArrayType(exprType).elemType) Then
+			cdecl=TObjectType(TArrayType(exprType).elemType).classDecl
+		Else
+			cdecl=exprType.GetClass()
+		End If
+		If Not cdecl InternalErr
+	End Method
+
+	Method Semant:TExpr()
+		_Semant
+		Err "Expression can't be used in this way"
+	End Method
+
+	Method SemantFunc:TExpr( args:TExpr[] , throwError:Int = True, funcCall:Int = False )
+		_Semant
+		If args.Length=1 And args[0] Then
+			If TArrayType(exprType) Then
+				Return args[0].Cast( exprType,CAST_EXPLICIT )
+			Else
+				Return args[0].Cast( cdecl.objectType,CAST_EXPLICIT )
+			End If
+		End If
+		Err "Illegal number of arguments for type conversion"
+	End Method
+
+	Method SemantScope:TScopeDecl()
+		_Semant
+		Return cdecl
+	End	Method
+
+	Method Trans$()
+		Return _trans.TransIdentTypeExpr( Self )
+	End Method
+
+End Type
+
+Type TIdentExpr Extends TExpr
+	Field ident$
+	Field expr:TExpr
+	Field scope:TScopeDecl
+	Field static:Int
+	Field isArg:Int
+	Field isRhs:Int
+	Field fixedScope:Int
+	
+	Field _identLower:String
+
+	Method IdentLower:String()
+		If Not _identLower Then
+			_identLower = ident.ToLower()
+		End If
+		Return _identLower
+	End Method
+
+	Method Create:TIdentExpr( ident$,expr:TExpr=Null, _identLower:String = Null )
+		Self.ident=ident
+		Self.expr=expr
+		Self._identLower = _identLower
+		Return Self
+	End Method
+
+	Method Copy:TExpr()
+		Local i:TIdentExpr = New TIdentExpr.Create( ident,CopyExpr(expr), _identLower )
+		i.static = static
+		i.isArg = isArg
+		i.isRhs = isRhs
+		i.fixedScope = fixedScope
+		Return i
+	End Method
+
+	Method ToString$()
+		Local t$="TIdentExpr(~q"+ident+"~q"
+		If expr t:+","+expr.ToString()
+		Return t+")"
+	End Method
+
+	Method _Semant()
+
+		If scope Return
+
+		If expr Then
+			scope=expr.SemantScope()
+			If scope
+				static=True
+			Else
+				expr=expr.Semant()
+				scope=expr.exprType.GetClass()
+				If Not scope Then
+					Err "Expression has no scope"
+				End If
+			End If
+			fixedScope = True
+		Else
+			scope=_env
+			' determines if access is via static (like Function, or via a Type)
+			' However, for Field->Field access this is not strictly true.
+			If _env.FuncScope()=Null
+				static = TModuleDecl(_env) = Null
+			Else
+				static=_env.FuncScope().IsStatic()
+			End If
+		End If
+
+	End Method
+
+	Method IdentScope:TScopeDecl()
+		If Not expr Return _env
+
+		Local scope:TScopeDecl=expr.SemantScope()
+		If scope
+			expr=Null
+		Else
+			expr=expr.Semant()
+			scope=expr.exprType.GetClass()
+			If Not scope Err "Expression has no scope."
+		EndIf
+		Return scope
+	End Method
+
+	Method IdentErr( errorDetails:String = Null )
+		If errorDetails Then
+			Err errorDetails
+		Else
+			Err "Identifier '"+ident+"' not found."
+		End If
+	End Method
+
+	Method IdentNotFound()
+	End Method
+
+	Method IsVar()
+		InternalErr
+	End Method
+
+	Method Semant:TExpr()
+		Return SemantSet( "",Null )
+	End Method
+
+	Method SemantSet:TExpr( op$,rhs:TExpr )
+		_Semant
+
+		'Local scope:TScopeDecl=IdentScope()
+		Local vdecl:TValDecl=scope.FindValDecl( IdentLower(), static )
+		
+		If TLocalDecl( vdecl )
+			' local variable should (at least) be in the same function scope.
+			If vdecl.FuncScope() <> scope.FuncScope() Then
+				' or the local can be in localmain..
+				If TModuleDecl(scope) And vdecl.FuncScope() And vdecl.FuncScope().ident = "__LocalMain" Then
+					' ok
+				Else
+					vdecl = Null
+				End If
+			End If
+		End If
+		
+		If vdecl And fixedScope And static Then
+			If TClassDecl(vdecl.scope) And TClassDecl(scope) Then
+				If Not TClassDecl(scope).ExtendsClass(TClassDecl(vdecl.scope)) Then
+					vdecl = Null
+				End If
+			Else
+				If vdecl.scope <> scope Then
+					vdecl = Null
+				End If
+			End If
+		End If
+		
+		If vdecl
+
+			If TConstDecl( vdecl )
+'				If rhs Err "Constant '"+ident+"' cannot be modified."
+'				Return New TConstExpr.Create( vdecl.ty,TConstDecl( vdecl ).value ).Semant()
+				If rhs Err "Constant '"+ident+"' cannot be modified."
+				Local cexpr:TConstExpr =New TConstExpr.Create( vdecl.ty,TConstDecl( vdecl ).value )
+				If Not static And (TInvokeExpr( expr ) Or TInvokeMemberExpr( expr )) Return New TStmtExpr.Create( New TExprStmt.Create( expr ),cexpr ).Semant()
+				Return cexpr.Semant()
+
+			Else If TFieldDecl( vdecl ) 
+				If static Err "Field '"+ident+"' cannot be accessed from here."
+				If expr Return New TMemberVarExpr.Create( expr,TVarDecl( vdecl ) ).Semant()
+'				If expr Return New TMemberVarExpr.Create( expr,TVarDecl( vdecl ) ).Semant()
+'				If scope<>_env Or Not _env.FuncScope() Or _env.FuncScope().IsStatic() Err "Field '"+ident+"' cannot be accessed from here."
+
+			EndIf
+
+			Return New TVarExpr.Create( TVarDecl( vdecl ) ).Semant()
+		EndIf
+
+		If op And op<>"="
+
+			Local fdecl:TFuncDecl=scope.FindFuncDecl( IdentLower(),,,,,,SCOPE_ALL )
+			If Not fdecl IdentErr
+
+			If _env.ModuleScope().IsStrict() And Not fdecl.IsProperty() Err "Identifier '"+ident+"' cannot be used in this way."
+
+			Local lhs:TExpr
+
+			If fdecl.IsStatic() Or (scope=_env And Not _env.FuncScope().IsStatic())
+				lhs=New TInvokeExpr.Create( fdecl )
+			Else If expr
+				Local tmp:TLocalDecl=New TLocalDecl.Create( "",Null,expr,, True )
+				lhs=New TInvokeMemberExpr.Create( New TVarExpr.Create( tmp ),fdecl )
+				lhs=New TStmtExpr.Create( New TDeclStmt.Create( tmp ),lhs )
+			Else
+				Return Null
+			EndIf
+
+			Local bop$=op[..1]
+			Select bop
+			Case "*","/","shl","shr","+","-","&","|","~~"
+				rhs=New TBinaryMathExpr.Create( bop,lhs,rhs )
+			Default
+				InternalErr
+			End Select
+			rhs=rhs.Semant()
+		EndIf
+
+		Local args:TExpr[]
+		If rhs args=[rhs]
+
+		Local fdecl:TFuncDecl
+		
+		Try
+			fdecl=scope.FindFuncDecl( IdentLower(),args, , isArg, True,True,SCOPE_ALL )
+		Catch errorMessage:String
+			If errorMessage.StartsWith("Compile Error") Then
+				Throw errorMessage
+			End If
+		End Try
+
+		If fdecl
+			If _env.ModuleScope().IsStrict() And Not fdecl.IsProperty() And Not isArg And Not fdecl.maybeFunctionPtr Err "Identifier '"+ident+"' cannot be used in this way."
+
+			fdecl.maybeFunctionPtr = False
+			
+			If Not fdecl.IsStatic()
+				If expr Return New TInvokeMemberExpr.Create( expr,fdecl,args, False ).Semant()
+				If scope<>_env Or Not _env.FuncScope() Or _env.FuncScope().IsStatic() Err "Method '"+ident+"' cannot be accessed from here."
+			EndIf
+
+			Return New TInvokeExpr.Create( fdecl,args, False, isArg, isRhs ).Semant()
+		End If
+		
+		' maybe it's a classdecl?
+		Local cdecl:TClassDecl = TClassDecl(scope.FindDecl(IdentLower()))
+		
+		If cdecl Then
+			Local e:TIdentTypeExpr = New TIdentTypeExpr.Create(cdecl.objectType)
+			e.cdecl = cdecl
+			Return e
+		End If
+
+		Local loopLabel:String = "#" + IdentLower()
+
+		' maybe it's a loop label?
+		Local stmt:TLoopStmt = TLoopStmt(scope.FindLoop(loopLabel))
+		
+		If stmt Then
+			Return New TLoopLabelExpr.Create(stmt)
+		End If
+		
+		' maybe it's a data label?
+		Local ddecl:TDefDataDecl = TDefDataDecl(_appInstance.FindDataLabel(loopLabel))
+		
+		If ddecl Then
+			Return New TDataLabelExpr.Create(ddecl)
+		End If
+		
+		IdentErr
+	End Method
+
+	Method SemantFunc:TExpr( args:TExpr[], throwError:Int = True, funcCall:Int = False )
+
+		_Semant
+
+		Local errorDetails:String
+		Local nearestScopeError:String
+
+		'Local scope:TScopeDecl=IdentScope()
+		Local initialScope:Int = SCOPE_ALL
+		If scope And TClassDecl(scope) Then
+			initialScope = SCOPE_CLASS_HEIRARCHY
+		End If
+		
+		Local fdecl:TFuncDecl
+		Try
+			fdecl=scope.FindFuncDecl( IdentLower(),args,,,,True,initialScope )
+'			Local decl:Object=scope.FindFuncDecl( IdentLower(),args,,,,True,SCOPE_ALL )
+'			If decl Then
+'				If TFuncDecl(decl) Then
+'					fdecl = TFuncDecl(decl)
+'				Else If TFuncDeclList(decl) Then
+'					If Not TFuncDeclList(decl).IsEmpty() Then
+'						fdecl = TFuncDecl(TFuncDeclList(decl).First())
+'					End If
+'				End If
+'			End If
+		Catch errorMessage:String
+			If errorMessage.StartsWith("Compile Error") Then
+				Throw errorMessage
+			Else
+				' couldn't find an exact match, look elsewhere
+				errorDetails = errorMessage
+				If errorMessage.StartsWith("Unable") Then
+					nearestScopeError = errorDetails
+				End If
+			End If
+		End Try
+
+		' if our scope is static, but the scope of the found function/method is not
+		' then we should ignore it and continue looking higher up the scope stack.
+		If static And fdecl And Not fdecl.IsStatic() Then
+			Local scope2:TScopeDecl = fdecl.scope
+			
+			fdecl = Null
+			
+			' if fdecl was a method, this would be the Type's scope (ie. file/module)
+			If scope2.scope Then
+				fdecl = scope2.scope.FindFuncDecl( IdentLower(),args,,,,,SCOPE_CLASS_HEIRARCHY )
+			End If
+		Else If static And Not fdecl And Not fixedScope Then
+			If _env.classScope() Then
+				' try searching from our class scope
+				'fdecl = _env.classScope().FindFuncDecl( IdentLower(),args )
+
+				If Not fdecl Then				
+					' try searching from our class parent scope
+					Try
+						fdecl = _env.classScope().scope.FindFuncDecl( IdentLower(),args,,,,True,SCOPE_ALL )
+					Catch errorMessage:String
+						If errorMessage.StartsWith("Compile Error") Then
+							Throw errorMessage
+						Else
+							' couldn't find an exact match, look elsewhere
+							errorDetails = errorMessage
+							If Not nearestScopeError And errorDetails.StartsWith("Unable") Then
+								nearestScopeError = errorDetails
+							End If
+						End If
+					End Try
+				End If
+			Else If _env.ModuleScope() Then ' bah
+				' finally, try searching from our module scope
+				Try
+					fdecl = _env.ModuleScope().FindFuncDecl( IdentLower(),args,,,,True,SCOPE_ALL )
+				Catch errorMessage:String
+					If errorMessage.StartsWith("Compile Error") Then
+						Throw errorMessage
+					Else
+						' couldn't find an exact match, look elsewhere
+						errorDetails = errorMessage
+						If Not nearestScopeError And errorDetails.StartsWith("Unable") Then
+							nearestScopeError = errorDetails
+						End If
+					End If
+				End Try
+			End If
+		End If
+
+		' couldn't find it? try a global search
+		If Not fdecl And Not fixedScope Then
+			For Local mdecl:TModuleDecl = EachIn _appInstance.globalImports.Values()
+				Try
+					fdecl=mdecl.FindFuncDecl( IdentLower(), args,,,,True,SCOPE_ALL )
+				Catch errorMessage:String
+					If errorMessage.StartsWith("Compile Error") Then
+						Throw errorMessage
+					Else
+						' couldn't find an exact match, look elsewhere
+						errorDetails = errorMessage
+						If Not nearestScopeError And errorDetails.StartsWith("Unable") Then
+							nearestScopeError = errorDetails
+						End If
+					End If
+				End Try
+				If fdecl Exit
+			Next
+		End If
+
+		If fdecl
+			If Not fdecl.IsStatic()
+				If static Err "Method '"+ident+"' cannot be accessed from here."
+				If expr Return New TInvokeMemberExpr.Create( expr,fdecl,args ).Semant()
+				'If scope<>_env Or _env.FuncScope().IsStatic() Err "Method '"+ident+"' cannot be accessed from here."
+			EndIf
+			If expr And Not static Then
+				Return New TInvokeMemberExpr.Create( expr,fdecl,args ).Semant()
+			Else
+				Return New TInvokeExpr.Create( fdecl,args, funcCall ).Semant()
+			End If
+		EndIf
+
+		'If args.Length=1 And args[0] And TObjectType( args[0].exprType )
+		'	Local cdecl:TClassDecl=TClassDecl( scope.FindScopeDecl( ident ) )
+		'	If cdecl Return args[0].Cast( New TObjectType.Create(cdecl),CAST_EXPLICIT )
+		'EndIf
+
+		Local ty:TType=scope.FindType( IdentLower(),Null )
+		If ty Then
+			If args.Length=1 And args[0] Return args[0].Cast( ty,CAST_EXPLICIT )
+			Err "Illegal number of arguments for type conversion"
+		End If
+
+		If throwError Then
+			If nearestScopeError Then
+				IdentErr(nearestScopeError)
+			Else
+				IdentErr(errorDetails)
+			End If
+		End If
+	End Method
+
+	Method SemantScope:TScopeDecl()
+		If Not expr Return _env.FindScopeDecl( IdentLower() )
+		Local scope:TScopeDecl=expr.SemantScope()
+
+		' If scope is a namespace, then we are a module. Look up the module id and return it as the real scope.
+		If TNamespaceDecl(scope) Then
+			Local mdecl:TModuleDecl=TModuleDecl(scope.FindDecl(scope.IdentLower() + "." + IdentLower()))
+			If mdecl Then
+				Return mdecl
+			End If
+		End If
+
+		If scope Return scope.FindScopeDecl( IdentLower() )
+	End Method
+
+'	Method Trans$()
+'		Return _trans.TransIdentExpr( Self )
+'	End Method
+
+End Type
+
+Type TBuiltinExpr Extends TExpr
+
+	Field id:String
+	Field expr:TExpr
+
+	Method Semant:TExpr()
+		If exprType Return Self
+
+		expr=expr.Semant()
+		exprType=expr.exprType
+		Return Self
+	End Method
+
+	Method Trans$()
+		Return _trans.TransBuiltinExpr( Self )
+	End Method
+
+End Type
+
+Type TLenExpr Extends TBuiltinExpr
+
+	Method Create:TLenExpr( expr:TExpr )
+		Self.id="len"
+		Self.expr=expr
+		Return Self
+	End Method
+
+	Method Semant:TExpr()
+		If exprType Return Self
+
+		expr=expr.Semant()
+
+		' anything other than a string or array will become "1", and
+		' return a length of 1 accordingly.
+		If Not TStringType(expr.exprType) And Not TArrayType(expr.exprType) Then
+			expr = New TConstExpr.Create( New TIntType, 1 ).Semant()
+			'this is not useful for numerics
+			'expr = New TConstExpr.Create( TType.stringType, "1" ).Semant()
+			_appInstance.mapStringConsts(TConstExpr(expr).value)
+		End If
+
+		exprType=New TIntType
+		Return Self
+	End Method
+
+	Method Copy:TExpr()
+		Return New TLenExpr.Create( CopyExpr(expr) )
+	End Method
+
+	Method ToString$()
+		Return "TLenExpr("+expr.ToString()+")"
+	End Method
+
+End Type
+
+Type TAbsExpr Extends TBuiltinExpr
+
+	Method Create:TAbsExpr( expr:TExpr )
+		Self.id="abs"
+		Self.expr=expr
+		Return Self
+	End Method
+
+	Method Semant:TExpr()
+
+		If exprType Return Self
+
+		expr=expr.Semant()
+
+		If TNumericType(expr.exprType) Or TBoolType(expr.exprType) Then
+
+			If TInt128Type(expr.exprType) Err "'Abs' does not support Int128 type. Use specific intrinsic function instead."
+			If TFloat64Type(expr.exprType) Err "'Abs' does not support Float64 type. Use specific intrinsic function instead."
+			If TFloat128Type(expr.exprType) Err "'Abs' does not support Float128 type. Use specific intrinsic function instead."
+			If TDouble128Type(expr.exprType) Err "'Abs' does not support Double128 type. Use specific intrinsic function instead."
+
+			If TIntType(expr.exprType) Or TByteType(expr.exprType) Or TShortType(expr.exprType) Then
+				exprType=New TIntType
+			Else
+				exprType=expr.exprType
+			End If
+		Else
+			Err "Subexpression for 'Abs' must be of numeric type"
+		End If
+
+		Return Self
+	End Method
+
+	Method Copy:TExpr()
+		Return New TAbsExpr.Create( CopyExpr(expr) )
+	End Method
+
+	Method ToString$()
+		Return "TAbsExpr("+expr.ToString()+")"
+	End Method
+
+End Type
+
+Type TAscExpr Extends TBuiltinExpr
+
+	Method Create:TAscExpr( expr:TExpr )
+		Self.id="asc"
+		Self.expr=expr
+		Return Self
+	End Method
+
+	Method Semant:TExpr()
+		If exprType Return Self
+
+		If TConstExpr(expr) Then
+			Local cexpr:TExpr = New TConstExpr.Create(New TIntType, Asc(TConstExpr(expr).value))
+			_appInstance.removeStringConst(TConstExpr(expr).value)
+			cexpr.Semant()
+			Return cexpr
+		End If
+		
+		expr = expr.SemantAndCast( New TStringType )
+		exprType = New TIntType
+		Return Self
+	End Method
+
+	Method Copy:TExpr()
+		Return New TAscExpr.Create( CopyExpr(expr) )
+	End Method
+
+	Method ToString$()
+		Return "TAscExpr("+expr.ToString()+")"
+	End Method
+
+End Type
+
+Type TSgnExpr Extends TBuiltinExpr
+
+	Method Create:TSgnExpr( expr:TExpr )
+		Self.id="sgn"
+		Self.expr=expr
+		Return Self
+	End Method
+
+	Method Semant:TExpr()
+		If exprType Return Self
+
+		If TConstExpr(expr) Then
+			'use different calls to only return a "float sgn"
+			'when param is a float
+			Local val:String = TConstExpr(expr).value
+			Local cexpr:TExpr
+			If String(Int(val)) = val
+				cexpr = New TConstExpr.Create(New TIntType, Sgn(Int(TConstExpr(expr).value)))
+			Else
+				cexpr = New TConstExpr.Create(New TFloatType, Sgn(Float(TConstExpr(expr).value)))
+			End If
+			
+			_appInstance.removeStringConst(TConstExpr(expr).value)
+			cexpr.Semant()
+			Return cexpr
+		End If
+		
+		expr = expr.Semant()
+		
+		If Not TNumericType(expr.exprType) Then
+			Err "Subexpression for 'Sgn' must be of numeric type"
+		End If
+
+		If TInt128Type(expr.exprType) Err "'Sgn' does not support Int128 type. Use specific intrinsic function instead."
+		If TFloat64Type(expr.exprType) Err "'Sgn' does not support Float64 type. Use specific intrinsic function instead."
+		If TFloat128Type(expr.exprType) Err "'Sgn' does not support Float128 type. Use specific intrinsic function instead."
+		If TDouble128Type(expr.exprType) Err "'Sgn' does not support Double128 type. Use specific intrinsic function instead."
+		
+		exprType=expr.exprType
+		Return Self
+	End Method
+
+	Method Copy:TExpr()
+		Return New TSgnExpr.Create( CopyExpr(expr) )
+	End Method
+
+	Method ToString$()
+		Return "TSgnExpr("+expr.ToString()+")"
+	End Method
+
+End Type
+
+Type TMinExpr Extends TBuiltinExpr
+
+	Field expr2:TExpr
+
+	Method Create:TMinExpr( lhs:TExpr, rhs:TExpr )
+		Self.id="min"
+		Self.expr=lhs
+		Self.expr2=rhs
+		Return Self
+	End Method
+
+	Method Semant:TExpr()
+		If exprType Return Self
+
+		expr=expr.Semant()
+		expr2=expr2.Semant()
+		
+		If TInt128Type(expr.exprType) Or TInt128Type(expr2.exprType) Err "'Min' does not support Int128 type. Use specific intrinsic function instead."
+		If TFloat64Type(expr.exprType) Or TFloat64Type(expr2.exprType) Err "'Min' does not support Float64 type. Use specific intrinsic function instead."
+		If TFloat128Type(expr.exprType) Or TFloat128Type(expr2.exprType) Err "'Min' does not support Float128 type. Use specific intrinsic function instead."
+		If TDouble128Type(expr.exprType) Or TDouble128Type(expr2.exprType) Err "'Min' does not support Double128 type. Use specific intrinsic function instead."
+
+		exprType=BalanceTypes(expr.exprType, expr2.exprType)
+		Return Self
+	End Method
+
+	Method Copy:TExpr()
+		Return New TMinExpr.Create( CopyExpr(expr), CopyExpr(expr2) )
+	End Method
+
+	Method ToString$()
+		Return "TMinExpr("+expr.ToString()+"," + expr2.ToString() + ")"
+	End Method
+
+End Type
+
+Type TMaxExpr Extends TBuiltinExpr
+
+	Field expr2:TExpr
+
+	Method Create:TMaxExpr( lhs:TExpr, rhs:TExpr )
+		Self.id="max"
+		Self.expr=lhs
+		Self.expr2=rhs
+		Return Self
+	End Method
+
+	Method Semant:TExpr()
+		If exprType Return Self
+
+		expr=expr.Semant()
+		expr2=expr2.Semant()
+
+		If TInt128Type(expr.exprType) Or TInt128Type(expr2.exprType) Err "'Max' does not support Int128 type. Use specific intrinsic function instead."
+		If TFloat64Type(expr.exprType) Or TFloat64Type(expr2.exprType) Err "'Max' does not support Float64 type. Use specific intrinsic function instead."
+		If TFloat128Type(expr.exprType) Or TFloat128Type(expr2.exprType) Err "'Max' does not support Float128 type. Use specific intrinsic function instead."
+		If TDouble128Type(expr.exprType) Or TDouble128Type(expr2.exprType) Err "'Max' does not support Double128 type. Use specific intrinsic function instead."
+
+		exprType=BalanceTypes(expr.exprType, expr2.exprType)
+		Return Self
+	End Method
+
+	Method Copy:TExpr()
+		Return New TMaxExpr.Create( CopyExpr(expr), CopyExpr(expr2) )
+	End Method
+
+	Method ToString$()
+		Return "TMaxExpr("+expr.ToString()+"," + expr2.ToString() + ")"
+	End Method
+
+End Type
+
+Type TSizeOfExpr Extends TBuiltinExpr
+
+	Method Create:TSizeOfExpr( expr:TExpr )
+		Self.id="sizeof"
+		Self.expr=expr
+		Return Self
+	End Method
+
+	Method Semant:TExpr()
+		If exprType Return Self
+		expr=expr.Semant()
+		exprType=New TIntType
+		Return Self
+	End Method
+
+	Method Copy:TExpr()
+		Return New TSizeOfExpr.Create( CopyExpr(expr) )
+	End Method
+
+	Method ToString$()
+		Return "TSizeOfExpr("+expr.ToString()+")"
+	End Method
+
+End Type
+
+Type TChrExpr Extends TBuiltinExpr
+
+	Method Create:TChrExpr( expr:TExpr )
+		Self.id="chr"
+		Self.expr=expr
+		Return Self
+	End Method
+	
+	Method Semant:TExpr()
+		If exprType Return Self
+
+		If TConstExpr(expr) Then
+			Local cexpr:TConstExpr = New TConstExpr.Create(New TStringType, Chr(Int(TConstExpr(expr).value)))
+			cexpr.Semant()
+			_appInstance.mapStringConsts(cexpr.value)
+			Return cexpr
+		End If
+		
+		expr = expr.SemantAndCast( New TIntType )
+		exprType = New TStringType
+		Return Self
+	End Method
+
+	Method Copy:TExpr()
+		Return New TChrExpr.Create( CopyExpr(expr) )
+	End Method
+
+	Method ToString$()
+		Return "TChrExpr("+expr.ToString()+")"
+	End Method
+
+End Type
+
+
+Type TFuncCallExpr Extends TExpr
+	Field expr:TExpr
+	Field args:TExpr[]
+
+	Method Create:TFuncCallExpr( expr:TExpr,args:TExpr[]=Null )
+		Self.expr=expr
+		If args Then
+			Self.args=args
+		Else
+			Self.args = New TExpr[0]
+		End If
+		Return Self
+	End Method
+
+	Method Copy:TExpr()
+		Return New TFuncCallExpr.Create( CopyExpr(expr),CopyArgs(args) )
+	End Method
+
+	Method ToString$()
+		Local t$="TFuncCallExpr("+expr.ToString()
+		For Local arg:TExpr=EachIn args
+			t:+","+arg.ToString()
+		Next
+		Return t+")"
+	End Method
+
+	Method Semant:TExpr()
+		args=SemantArgs( args )
+		If TIndexExpr(expr) Then
+			expr = expr.SemantFunc( args, True, True )
+			exprType = expr.exprType
+			Return Self
+		Else
+			Return expr.SemantFunc( args, True, True )
+		End If
+	End Method
+
+	Method SemantFunc:TExpr( args:TExpr[] , throwError:Int = True, funcCall:Int = False )
+		' we are only likely to be called if a function returns and invokes a function pointer.
+
+		Local ex:TExpr = Semant()
+		
+		If TFunctionPtrType(ex.exprType) Then
+			exprType = TFunctionPtrType(ex.exprType).func.retType
+		End If
+		
+		Self.args = SemantArgs(args)
+		expr = ex
+		
+		Return Self
+	End Method
+
+	Method Trans$()
+		Return _trans.TransFuncCallExpr( Self )
+	End Method
+
+End Type
+
+Type TScopeExpr Extends TExpr
+	Field scope:TScopeDecl
+
+	Method Create:TScopeExpr( scope:TScopeDecl )
+		Self.scope=scope
+		Return Self
+	End Method
+
+	Method Copy:TExpr()
+		Return Self
+	End Method
+
+	Method ToString$()
+		Return "TScopeExpr("+scope.ToString()+")"
+	End Method
+
+	Method Semant:TExpr()
+		Err "Syntax error."
+	End Method
+
+	Method SemantScope:TScopeDecl()
+		Return scope
+	End Method
+End Type
+
+Type TNewExpr Extends TExpr
+	Field isSuper:Int
+	Field args:TExpr[]
+	Field ctor:TFuncDecl
+
+	Method Create:TNewExpr( args:TExpr[]=Null, isSuper:Int = False )
+		If args Then
+			Self.args=args
+		Else
+			Self.args = New TExpr[0]
+		End If
+		Self.isSuper = isSuper
+		Return Self
+	End Method
+
+	Method Copy:TExpr()
+		Return New TNewExpr.Create(CopyArgs(args), isSuper)
+	End Method
+
+	Method Semant:TExpr()
+
+		Local fdecl:TFuncDecl = _env.FuncScope()
+		If Not fdecl Or TNewDecl(fdecl) = Null Or Not _env.ClassScope() Then
+			Err "Call to constructor not valid in this context."
+		End If
+	
+		' must be first statement of New() method
+		Local stmt:TStmt = TStmt(fdecl.stmts.First())
+		
+		If TExprStmt(stmt) = Null Or TExprStmt(stmt).expr <> Self Then
+			Err "Call to constructor must be first statement in New()."
+		End If
+	
+		args=SemantArgs( args )
+		
+		' validate called constructor
+		Try
+			Local cDecl:TClassDecl = _env.ClassScope()
+			If isSuper Then
+				cDecl = cDecl.superClass
+			End If
+			ctor = cDecl.FindFuncDecl("new",args,,,,True,SCOPE_CLASS_HEIRARCHY )
+		Catch errorMessage:String
+			If errorMessage.StartsWith("Compile Error") Then
+				Throw errorMessage
+			Else
+				Err errorMessage
+			End If
+		End Try
+		
+		' TODO : expand to full recursive test
+		If ctor = fdecl Then
+			Err "Recursive constructor invocation."
+		End If
+		
+		ctor.Semant
+		
+		' attach to ctor
+		TNewDecl(fdecl).chainedCtor = Self
+		
+		Return Self
+	End Method
+
+	Method Trans$()
+		'Return _trans.TransFuncCallExpr( Self )
+	End Method
+
+End Type
+
+Type TNullExpr Extends TExpr
+
+	Method Create:TNullExpr(ty:TType)
+		exprType = ty
+		Return Self
+	End Method
+
+	Method Copy:TExpr()
+		Return New TNullExpr.Create(exprType)
+	End Method
+
+	Method Semant:TExpr()
+		Return Self
+	End Method
+
+	Method Trans$()
+		Return "NULL"
+	End Method
+
+	Method Eval$()
+		Return ""
+	End Method
+
+End Type
+
+Type TLoopLabelExpr Extends TExpr
+
+	Field loop:TLoopStmt
+
+	Method Create:TLoopLabelExpr(loop:TLoopStmt)
+		Self.loop = loop
+		Return Self
+	End Method
+	
+	Method Copy:TExpr()
+		Return New TLoopLabelExpr.Create(loop)
+	End Method
+
+	Method Semant:TExpr()
+		Return Self
+	End Method
+
+	Method Trans$()
+		DebugStop
+	End Method
+
+	Method Eval$()
+		Return ""
+	End Method
+
+End Type
+
+Type TDataLabelExpr Extends TExpr
+
+	Field dataDef:TDefDataDecl
+	
+	Method Create:TDataLabelExpr(dataDef:TDefDataDecl)
+		Self.dataDef = dataDef
+		Return Self
+	End Method
+
+	Method Copy:TExpr()
+		Return New TDataLabelExpr.Create(dataDef)
+	End Method
+
+	Method Semant:TExpr()
+		Return Self
+	End Method
+
+	Method Trans$()
+		DebugStop
+	End Method
+
+	Method Eval$()
+		Return ""
+	End Method
+
+End Type

+ 133 - 0
mapm/common.bmx

@@ -0,0 +1,133 @@
+' Copyright (c) 2008-2017 Bruce A Henderson
+' 
+' 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.
+' 
+SuperStrict
+
+Import "src/*.h"
+
+Import "src/mapmhasn.c"
+Import "src/mapmhsin.c"
+Import "src/mapm_pow.c"
+Import "src/mapm_log.c"
+Import "src/mapm_lg2.c"
+Import "src/mapm_lg4.c"
+Import "src/mapm_exp.c"
+Import "src/mapm_lg3.c"
+Import "src/mapmasin.c"
+Import "src/mapmasn0.c"
+Import "src/mapm_sin.c"
+Import "src/mapm5sin.c"
+Import "src/mapmrsin.c"
+Import "src/mapm_cpi.c"
+Import "src/mapmsqrt.c"
+Import "src/mapmcbrt.c"
+Import "src/mapmgues.c"
+Import "src/mapmfact.c"
+Import "src/mapm_gcd.c"
+Import "src/mapmipwr.c"
+Import "src/mapmpwr2.c"
+Import "src/mapm_rnd.c"
+Import "src/mapm_flr.c"
+Import "src/mapm_fpf.c"
+Import "src/mapm_rcp.c"
+Import "src/mapmstck.c"
+Import "src/mapm_div.c"
+Import "src/mapm_mul.c"
+Import "src/mapmfmul.c"
+Import "src/mapm_fft.c"
+Import "src/mapm_add.c"
+Import "src/mapmistr.c"
+Import "src/mapm_set.c"
+Import "src/mapm_fam.c"
+Import "src/mapmutil.c"
+Import "src/mapmutl2.c"
+Import "src/mapmutl1.c"
+Import "src/mapmcnst.c"
+
+Extern
+
+	Function m_apm_init:Byte Ptr()
+	Function m_apm_free(handle:Byte Ptr)
+
+	Function m_apm_set_string(handle:Byte Ptr, value:Byte Ptr)
+	Function m_apm_set_long(handle:Byte Ptr, value:Int)
+	Function m_apm_set_double(handle:Byte Ptr, value:Double)
+
+	Function m_apm_to_string(buf:Byte Ptr, decimalPlaces:Int, handle:Byte Ptr)
+	Function m_apm_to_fixpt_string(buf:Byte Ptr, decimalPlaces:Int, handle:Byte Ptr)
+	Function m_apm_to_integer_string(buf:Byte Ptr, handle:Byte Ptr)
+	Function m_apm_to_fixpt_stringex(buf:Byte Ptr, decimalPlaces:Int, handle:Byte Ptr, radix:Byte, separator:Byte, separatorCount:Int)
+
+
+	Function m_apm_absolute_value(mapm:Byte Ptr, handle:Byte Ptr)
+	Function m_apm_negate(mapm:Byte Ptr, handle:Byte Ptr)
+	Function m_apm_copy(mapm:Byte Ptr, handle:Byte Ptr)
+
+	Function m_apm_round(mapm:Byte Ptr, decimalPlaces:Int, handle:Byte Ptr)
+	Function m_apm_compare:Int(handle:Byte Ptr, mapmPtr:Byte Ptr)
+	Function m_apm_sign:Int(handle:Byte Ptr)
+	Function m_apm_exponent:Int(handle:Byte Ptr)
+	Function m_apm_significant_digits:Int(handle:Byte Ptr)
+	Function m_apm_is_integer:Int(handle:Byte Ptr)
+	Function m_apm_is_even:Int(handle:Byte Ptr)
+	Function m_apm_is_odd:Int(handle:Byte Ptr)
+
+	Function m_apm_set_random_seed(seed:Byte Ptr)
+	Function m_apm_get_random(mapm:Byte Ptr)
+	Function m_apm_add(mapm:Byte Ptr, handle:Byte Ptr, value:Byte Ptr)
+	Function m_apm_subtract(mapm:Byte Ptr, handle:Byte Ptr, value:Byte Ptr)
+	Function m_apm_multiply(mapm:Byte Ptr, handle:Byte Ptr, value:Byte Ptr)
+
+	Function m_apm_divide(mapm:Byte Ptr, decimalPlaces:Int, handle:Byte Ptr, value:Byte Ptr)
+	Function m_apm_reciprocal(mapm:Byte Ptr, decimalPlaces:Int, handle:Byte Ptr)
+	Function m_apm_integer_divide(mapm:Byte Ptr, handle:Byte Ptr, value:Byte Ptr)
+	Function m_apm_integer_div_rem(quotient:Byte Ptr, remainder:Byte Ptr, handle:Byte Ptr, value:Byte Ptr)
+	Function m_apm_factorial(mapm:Byte Ptr, handle:Byte Ptr)
+	Function m_apm_floor(mapm:Byte Ptr, handle:Byte Ptr)
+	Function m_apm_ceil(mapm:Byte Ptr, handle:Byte Ptr)
+	Function m_apm_gcd(mapm:Byte Ptr, handle:Byte Ptr, value:Byte Ptr)
+	Function m_apm_lcm(mapm:Byte Ptr, handle:Byte Ptr, value:Byte Ptr)
+	Function m_apm_sqrt(mapm:Byte Ptr, decimalPlaces:Int, handle:Byte Ptr)
+	Function m_apm_cbrt(mapm:Byte Ptr, decimalPlaces:Int, handle:Byte Ptr)
+	Function m_apm_log(mapm:Byte Ptr, decimalPlaces:Int, handle:Byte Ptr)
+	Function m_apm_log10(mapm:Byte Ptr, decimalPlaces:Int, handle:Byte Ptr)
+	Function m_apm_exp(mapm:Byte Ptr, decimalPlaces:Int, handle:Byte Ptr)
+	Function m_apm_pow(mapm:Byte Ptr, decimalPlaces:Int, handle:Byte Ptr, power:Byte Ptr)
+	Function m_apm_integer_pow(mapm:Byte Ptr, decimalPlaces:Int, handle:Byte Ptr, power:Int)
+	Function m_apm_integer_pow_nr(mapm:Byte Ptr, decimalPlaces:Int, handle:Byte Ptr, power:Int)
+
+	Function m_apm_sin(mapm:Byte Ptr, decimalPlaces:Int, handle:Byte Ptr)
+	Function m_apm_cos(mapm:Byte Ptr, decimalPlaces:Int, handle:Byte Ptr)
+	Function m_apm_sin_cos(_sin:Byte Ptr, _cos:Byte Ptr, decimalPlaces:Int, handle:Byte Ptr)
+	Function m_apm_tan(mapm:Byte Ptr, decimalPlaces:Int, handle:Byte Ptr)
+	Function m_apm_arcsin(mapm:Byte Ptr, decimalPlaces:Int, handle:Byte Ptr)
+	Function m_apm_arccos(mapm:Byte Ptr, decimalPlaces:Int, handle:Byte Ptr)
+	Function m_apm_arctan(mapm:Byte Ptr, decimalPlaces:Int, handle:Byte Ptr)
+	Function m_apm_arctan2(mapm:Byte Ptr, decimalPlaces:Int, y:Byte Ptr, x:Byte Ptr)
+	Function m_apm_sinh(mapm:Byte Ptr, decimalPlaces:Int, handle:Byte Ptr)
+	Function m_apm_cosh(mapm:Byte Ptr, decimalPlaces:Int, handle:Byte Ptr)
+	Function m_apm_tanh(mapm:Byte Ptr, decimalPlaces:Int, handle:Byte Ptr)
+	Function m_apm_arcsinh(mapm:Byte Ptr, decimalPlaces:Int, handle:Byte Ptr)
+	Function m_apm_arccosh(mapm:Byte Ptr, decimalPlaces:Int, handle:Byte Ptr)
+	Function m_apm_arctanh(mapm:Byte Ptr, decimalPlaces:Int, handle:Byte Ptr)
+
+End Extern
+
+

+ 677 - 0
mapm/mapm.bmx

@@ -0,0 +1,677 @@
+' Copyright (c) 2008-2017 Bruce A Henderson
+' 
+' 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.
+' 
+SuperStrict
+
+Import "common.bmx"
+
+Rem
+bbdoc: Maximum number of digits when converting to string.
+End Rem
+Global MAPM_MAX_DIGITS:Int = 8192
+
+Rem
+bbdoc: A numeric type for very large numbers.
+End Rem
+Type TMAPM
+
+	Field mapmPtr:Byte Ptr
+	
+	Rem
+	bbdoc: Creates a new MAPM object.
+	End Rem
+	Method New()
+		mapmPtr = m_apm_init()
+	End Method
+	
+	Rem
+	bbdoc: Creates a new MAPM object setting it to the optional @value.
+	End Rem
+	Function CreateMAPM:TMAPM(value:String = Null)
+		Return New TMAPM.Create(value)
+	End Function
+	
+	Rem
+	bbdoc: Creates a new MAPM object setting it to the optional @value.
+	End Rem
+	Method Create:TMAPM(value:String = Null)
+		If value Then
+			SetString(value)
+		End If
+		Return Self
+	End Method
+	
+	Function _create:TMAPM(mapmPtr:Byte Ptr)
+		If mapmPtr Then
+			Local this:TMAPM = New TMAPM
+			this.mapmPtr = mapmPtr
+			Return this
+		End If
+	End Function
+
+
+	Rem
+	bbdoc: Sets the MAPM value to the value specified by the string variable.
+	about: Integers and floating point are supported as is floating point with scientific notation.
+	<ul>
+	<li>Lead-in whitespace is ignored.</li>
+	<li>A lead-in '+' sign is optional.</li>
+	<li>A negative number must have '-' as the first non-whitespace char</li>
+	<li>An exponent, 'E' or 'e', is optional.</li>
+	<li>The decimal point is optional. The decimal point may be anywhere in the number, but before the exponent.</li>
+	<li>The exponent may have an optional '+' sign.</li>
+	<li>The exponent must be an integer value (no decimal point)</li>
+	</ul>
+	End Rem
+	Method SetString(value:String)
+		m_apm_set_string(mapmPtr, value)
+	End Method
+		
+	Rem
+	bbdoc: Sets the MAPM value to the value specified by the int variable.
+	End Rem
+	Method SetInt(value:Int)
+		m_apm_set_long(mapmPtr, value)
+	End Method
+	
+	Rem
+	bbdoc: Sets the MAPM value to the value specified by the double variable.
+	about: The double value will be rounded to the 15 most significant digits and then converted
+	to the MAPM value. If you want an 'exact' conversion, use the SetString method since some
+	C floating point library's may round your double in an unpredictable manner.
+	End Rem
+	Method SetDouble(value:Double)
+		m_apm_set_double(mapmPtr, value)
+	End Method
+	
+	Rem
+	bbdoc: Converts an MAPM value into a string and is meant to be used with floating point MAPM values.
+	about: The output string will always be in scientific (exponential) notation. There will
+	be a leading '-' sign for negative numbers. There will be 'decimal_places' number of digits
+	after the decimal point. If decimal_places is &gt;= 0, the value will be rounded to that number
+	of digits and then the string will be filled, with trailing zero's appended if necessary to
+	fill out the decimal place specification. If decimal_places &lt; 0, ALL the significant digits
+	of the MAPM number will be output. In some applications, it is convienent to round the value
+	yourself (see 'm_apm_round') and then display ALL the digits.
+	<p>
+	If value = 3.640083E-4
+	<pre>
+            1)  ToExpString(4)
+	        string -&gt; "3.6401E-4"
+
+            2)  ToExpString(14)
+	        string -&gt; "3.64008300000000E-4"
+
+            3)  ToExpString(-1)
+	        string -&gt; "3.640083E-4"
+	</pre>
+	</p>
+	End Rem
+	Method ToExpString:String(decimalPlaces:Int)
+		Local buf:Byte[MAPM_MAX_DIGITS + decimalPlaces]
+		m_apm_to_string(buf, decimalPlaces, mapmPtr)
+		Return String.FromCString(buf)
+	End Method
+	
+	Rem
+	bbdoc: Converts a MAPM value into a string and the output will be formatted in fixed point notation.
+	about: The output string must be large enough to hold the result.
+	<p>
+	    If decimal_places &lt; 0, ALL the significant digits of the MAPM
+	    number will be output.
+	</p>
+	<p>
+	    If decimal_places = 0, the output will be the MAPM value rounded
+	    to the nearest integer and the decimal point will be suppressed.
+	</p>
+	<p>
+	    If decimal_places is &gt; 0, the value will be rounded to that number
+	    of digits and then the string will be filled, with trailing zero's
+	    appended if necessary to fill out the decimal place specification.
+	</p>
+	<p>
+	    In some applications, it is convienent to round the value yourself
+	    (see 'Round()') and then display ALL the digits.
+	</p>
+	<pre>
+	    If value is = 3.6487451E+2 :
+
+	    1)  ToFixPtString(10)
+	        string -&gt; "364.8745100000"
+
+	    2)  ToFixPtString(1)
+	        string -&gt; "364.9"
+
+	    3)  ToFixPtString(0)
+	        string -&gt; "365"
+
+	    4)  ToFixPtString(-1)
+	        string -&gt; "364.87451"
+	</pre>
+	End Rem
+	Method ToFixPtString:String(decimalPlaces:Int)
+		Local buf:Byte[MAPM_MAX_DIGITS + SignificantDigits()]
+		m_apm_to_fixpt_string(buf, decimalPlaces, mapmPtr)
+		Return String.FromCString(buf)
+	End Method
+	
+	Rem
+	bbdoc: Converts a MAPM value into a string, outputting all significant digits.
+	about: This is equivalent to  ToFixPtString(-1)
+	End Rem
+	Method ToString:String()
+		Return ToFixPtString(-1)
+	End Method
+
+	Rem
+	bbdoc: This method is an extended version of ToFixPtString which includes 3 additional function parameters:
+	about:
+	<ul>
+	<li>@radix -  Specify the radix character desired. For example, use ',' to set the radix char to a comma.</li>
+	<li> @separator and @separatorCount - Specify a character separator every 'separator_count' characters.
+	    This is used to split up a large number with a 'delimiter' for easier readability. For example,
+		<p>
+	    If separator_char = ',' and separator_count = 3, there will be a
+	    comma inserted before every group of 3 digits in the output string.
+		</p>
+	<p>
+	    6123456789.098765321 will be formatted as "6,123,456,789.098765321"
+	</p>
+	</li>
+	</ul>
+	<p>
+	    Note that only digits before the radix char are separated.
+	</p>
+	<p>
+	    @separator OR @separatorCount = 0 is used to disable
+	    the 'char separator' feature. This would typically be used
+	    when it is only desired to change the radix character.
+	</p>
+	End Rem
+	Method ToFixPtStringEx:String(decimalPlaces:Int, radix:String, separator:String, separatorCount:Int)
+		Local buf:Byte[MAPM_MAX_DIGITS + SignificantDigits()]
+		m_apm_to_fixpt_stringex(buf, decimalPlaces, mapmPtr, Byte(radix[0]), Byte(separator[0]), separatorCount)
+		Return String.FromCString(buf)
+	End Method
+	
+	Rem
+	bbdoc: Converts an MAPM value into a string and is meant to be used with integer values.
+	about: If the MAPM number is not
+	    an integer, the function will truncate the value to the nearest
+	    integer and the output will be formatted as an integer, with a
+	    possible leading '-' sign.
+	<p>
+	Examples:
+	<pre>
+	    MAPM Value            Output String
+	    -----------            -------------
+	    3.28E+2                "328"
+	    -4.56993E+2            "-456"
+	    4.32E-3                "0"
+	    -1.62E+5               "-162000"
+	</pre>
+	    If you want the value 'rounded' to the nearest integer (NNN.99
+	    becomes NNN+1), use ToFixPtString with 0 decimal places.
+	</p>
+	End Rem
+	Method ToIntString:String()
+		Local buf:Byte[MAPM_MAX_DIGITS + SignificantDigits()]
+		m_apm_to_integer_string(buf, mapmPtr)
+		Return String.FromCString(buf)
+	End Method
+	
+	Rem
+	bbdoc: Returns the absolute MAPM value.
+	End Rem
+	Method AbsoluteValue:TMAPM()
+		Local mapm:TMAPM = New TMAPM
+		m_apm_absolute_value(mapm.mapmPtr, mapmPtr)
+		Return mapm
+	End Method
+	
+	Rem
+	bbdoc: Returns the MAPM value, negated.
+	End Rem
+	Method Negate:TMAPM()
+		Local mapm:TMAPM = New TMAPM
+		m_apm_negate(mapm.mapmPtr, mapmPtr)
+		Return mapm
+	End Method
+	
+	Rem
+	bbdoc: Returns a copy of the number.
+	End Rem
+	Method Copy:TMAPM()
+		Local mapm:TMAPM = New TMAPM
+		m_apm_copy(mapm.mapmPtr, mapmPtr)
+		Return mapm
+	End Method
+
+	Rem
+	bbdoc: Rounds the value of the number to the number of decimal places specified.
+	about: The decimal places parameter is referenced to the number when the
+	    number is in scientific notation.
+	End Rem
+	Method Round:TMAPM(decimalPlaces:Int)
+		Local mapm:TMAPM = New TMAPM
+		m_apm_round(mapm.mapmPtr, decimalPlaces, mapmPtr)
+		Return mapm
+	End Method
+		
+	Rem
+	bbdoc: Compares the number to @other.
+	about: The method will return :
+	<pre>
+	    -1 : num &lt; other
+	     0 : num = other
+	     1 : num &gt; other
+	</pre>
+	End Rem
+	Method Compare:Int(other:Object)
+		If TMAPM(other) Then
+			Return m_apm_compare(mapmPtr, TMAPM(other).mapmPtr)
+		End If
+		Return -1
+	End Method
+	
+	Rem
+	bbdoc: Returns the sign of the number.
+	about: The method will return :
+	<pre>
+	    -1 : num < 0
+	     0 : num = 0
+	     1 : num > 0
+	</pre>
+
+	End Rem
+	Method Sign:Int()
+		Return m_apm_sign(mapmPtr)
+	End Method
+	
+	Rem
+	bbdoc: Returns the exponent of the number.
+	about: <pre>
+     If apm_num = 3.86742E+12,    12 will be returned.
+                = 9.61082E-56,   -56 will be returned.
+                = 0.0              0 will be returned.
+	</pre>
+	End Rem
+	Method Exponent:Int()
+		Return m_apm_exponent(mapmPtr)
+	End Method
+	
+	Rem
+	bbdoc: Returns the number of significant digits of the number.
+	End Rem
+	Method SignificantDigits:Int()
+		Return m_apm_significant_digits(mapmPtr)
+	End Method
+	
+	Rem
+	bbdoc: Returns True if the number is an integer, False otherwise.
+	End Rem
+	Method IsInteger:Int()
+		Return m_apm_is_integer(mapmPtr)
+	End Method
+	
+	Rem
+	bbdoc: Returns True if the number is even, False otherwise.
+	about: It the number is not an integer, it will result in a warning on stderr and the
+	return value is undefined.
+	End Rem
+	Method IsEven:Int()
+		Return m_apm_is_even(mapmPtr)
+	End Method
+	
+	Rem
+	bbdoc: Returns True if the number is odd, False otherwise.
+	about: It the number is not an integer, it will result in a warning on stderr and the
+	return value is undefined.
+	End Rem
+	Method IsOdd:Int()
+		Return m_apm_is_odd(mapmPtr)
+	End Method
+	
+	Rem
+	bbdoc: Sets the randon number generator to a known starting value.
+	about: The argument should correspond to any *integer* value between 0 and (1.0E+15 - 1)
+	End Rem
+	Function SetRandomSeed(seed:String)
+		m_apm_set_random_seed(seed)
+	End Function
+	
+	Rem
+	bbdoc: Returns a random floating point number between the values 0 and 1.
+	about: The first time the function is called the generator is initialized with the system
+	time. This generator will not repeat its pattern until 1.0E+15 numbers have been generated.
+	End Rem
+	Function Random:TMAPM()
+		Local mapm:TMAPM = New TMAPM
+		m_apm_get_random(mapm.mapmPtr)
+		Return mapm
+	End Function
+	
+	Rem
+	bbdoc: Adds @value to the number, returning the result.
+	End Rem
+	Method Add:TMAPM(value:TMAPM)
+		Local mapm:TMAPM = New TMAPM
+		m_apm_add(mapm.mapmPtr, mapmPtr, value.mapmPtr)
+		Return mapm
+	End Method
+	
+	Rem
+	bbdoc: Subtracts @value from the number, returning the result.
+	End Rem
+	Method Subtract:TMAPM(value:TMAPM)
+		Local mapm:TMAPM = New TMAPM
+		m_apm_subtract(mapm.mapmPtr, mapmPtr, value.mapmPtr)
+		Return mapm
+	End Method
+	
+	Rem
+	bbdoc: Multiplies @value with the number, returning the result.
+	End Rem
+	Method Multiply:TMAPM(value:TMAPM)
+		Local mapm:TMAPM = New TMAPM
+		m_apm_multiply(mapm.mapmPtr, mapmPtr, value.mapmPtr)
+		Return mapm
+	End Method
+	
+	Rem
+	bbdoc: Divides the number by @value.
+	about: Unlike the other three basic operations, division cannot be
+	    counted on to produce non-repeating decimals, so the
+	    @decimalPlaces parameter is used to tell this routine how many
+            digits are to be calculated before stopping.
+	<p>
+	    Note that the number of decimal places is referenced to the
+	    value as if the number was in fixed point notation. Divide
+	    is the only method where decimal places is referenced to
+	    fixed point notation, all other methods are referenced to
+	    scientific notation. This was an intentional design decision
+	    so IntegerDivide' and IntegerDivRem would
+	    work as expected.
+	</p>
+	<p>
+            Division by zero creates a zero result and a warning on stderr.
+	</p>
+
+	End Rem
+	Method Divide:TMAPM(value:TMAPM, decimalPlaces:Int)
+		Local mapm:TMAPM = New TMAPM
+		m_apm_divide(mapm.mapmPtr, decimalPlaces, mapmPtr, value.mapmPtr)
+		Return mapm
+	End Method
+	
+	Rem
+	bbdoc: Returns the reciprocal of the number (compute 1.0 / number).
+	about: The result will be accurate to the number of decimal places specified.
+	<p>
+     An input of zero creates a zero result and a warning on stderr.
+	</p>
+	End Rem
+	Method Reciprocal:TMAPM(decimalPlaces:Int)
+		Local mapm:TMAPM = New TMAPM
+		m_apm_reciprocal(mapm.mapmPtr, decimalPlaces, mapmPtr)
+		Return mapm
+	End Method
+	
+	Rem
+	bbdoc: Divides the number by @value, truncating the result to an integer.
+	End Rem
+	Method IntegerDivide:TMAPM(value:TMAPM)
+		Local mapm:TMAPM = New TMAPM
+		m_apm_integer_divide(mapm.mapmPtr, mapmPtr, value.mapmPtr)
+		Return mapm
+	End Method
+	
+	Rem
+	bbdoc: Divides the number by @value, truncating the result to an integer and putting the result in @quotient and the remainder in @remainder.
+	about: So, 173 / 26 will yield a quotient of 6 and a remainder of 17.
+	<p>
+	Note that the input numbers do not necessarily have to be
+	    integers. This method can be used to split up the integer
+	    portion and fractional portion of a floating point number
+	    by calling the function with @value set to 'MM_One'. So,
+	    32.17042 can be split up into '32' and '0.17042'.
+	</p>
+	End Rem
+	Method IntegerDivRem(value:TMAPM, quotient:TMAPM, remainder:TMAPM)
+		m_apm_integer_div_rem(quotient.mapmPtr, remainder.mapmPtr, mapmPtr, value.mapmPtr)
+	End Method
+	
+	Rem
+	bbdoc: Computes the factorial of the number and returns the result.
+	about: A non-integer number will yield nonsense. Actually, the algorithm simply multiplies
+	 : (though 0! and 1! return 1)
+	<pre>
+	    N * (N - 1) * (N - 2) ... until N < 2.
+	</pre>
+	End Rem
+	Method Factorial:TMAPM()
+		Local mapm:TMAPM = New TMAPM
+		m_apm_factorial(mapm.mapmPtr, mapmPtr)
+		Return mapm
+	End Method
+	
+	Rem
+	bbdoc: Returns the number rounded downwards to the nearest integer.
+	End Rem
+	Method Floor:TMAPM()
+		Local mapm:TMAPM = New TMAPM
+		m_apm_floor(mapm.mapmPtr, mapmPtr)
+		Return mapm
+	End Method
+	
+	Rem
+	bbdoc: Returns the number rounded upwards to the nearest integer.
+	End Rem
+	Method Ceil:TMAPM()
+		Local mapm:TMAPM = New TMAPM
+		m_apm_ceil(mapm.mapmPtr, mapmPtr)
+		Return mapm
+	End Method
+	
+	Rem
+	bbdoc: Computes the GCD (greatest common divisor) of this number and @value.
+	End Rem
+	Method GCD:TMAPM(value:TMAPM)
+		Local mapm:TMAPM = New TMAPM
+		m_apm_gcd(mapm.mapmPtr, mapmPtr, value.mapmPtr)
+		Return mapm
+	End Method
+	
+	Rem
+	bbdoc: Computes the LCM (least common multi) of this number and @value.
+	End Rem
+	Method LCM:TMAPM(value:TMAPM)
+		Local mapm:TMAPM = New TMAPM
+		m_apm_lcm(mapm.mapmPtr, mapmPtr, value.mapmPtr)
+		Return mapm
+	End Method
+	
+	Rem
+	bbdoc: Returns the square root of the number.
+	about: The result will be accurate to the number of decimal places specified.
+	End Rem
+	Method Sqrt:TMAPM(decimalPlaces:Int)
+		Local mapm:TMAPM = New TMAPM
+		m_apm_sqrt(mapm.mapmPtr, decimalPlaces, mapmPtr)
+		Return mapm
+	End Method
+	
+	Rem
+	bbdoc: Returns the cube root of the number.
+	about: The result will be accurate to the number of decimal places specified.
+	End Rem
+	Method Cbrt:TMAPM(decimalPlaces:Int)
+		Local mapm:TMAPM = New TMAPM
+		m_apm_cbrt(mapm.mapmPtr, decimalPlaces, mapmPtr)
+		Return mapm
+	End Method
+	
+	Rem
+	bbdoc: Returns the natural log (base 2.718 ...) of the number.
+	about: The result will be accurate to the number of decimal places specified.
+	End Rem
+	Method Log:TMAPM(decimalPlaces:Int)
+		Local mapm:TMAPM = New TMAPM
+		m_apm_log(mapm.mapmPtr, decimalPlaces, mapmPtr)
+		Return mapm
+	End Method
+	
+	Rem
+	bbdoc: Returns the common log (base 10) of the number.
+	about: The result will be accurate to the number of decimal places specified.
+	End Rem
+	Method Log10:TMAPM(decimalPlaces:Int)
+		Local mapm:TMAPM = New TMAPM
+		m_apm_log10(mapm.mapmPtr, decimalPlaces, mapmPtr)
+		Return mapm
+	End Method
+	
+	Rem
+	bbdoc: Performs E ^ the number where 'E' is 2.718... (the exponential function).
+	about: The result will be accurate to the number of decimal places specified.
+	End Rem
+	Method Exp:TMAPM(decimalPlaces:Int)
+		Local mapm:TMAPM = New TMAPM
+		m_apm_exp(mapm.mapmPtr, decimalPlaces, mapmPtr)
+		Return mapm
+	End Method
+	
+	Rem
+	bbdoc: Raises the number to @power.
+	about: The result will be accurate to the number of decimal places specified.
+	End Rem
+	Method Pow:TMAPM(power:TMAPM, decimalPlaces:Int)
+		Local mapm:TMAPM = New TMAPM
+		m_apm_pow(mapm.mapmPtr, decimalPlaces, mapmPtr, power.mapmPtr)
+		Return mapm
+	End Method
+	
+	Rem
+	bbdoc: Raises the number to @power.
+	about: The result will be accurate to the number of decimal places specified.
+	<p>
+	    This method is considerably faster than the
+	    generic Pow method (when @power is not excessively
+	    large). The number and/or @power may be negative.
+	</p>
+	<p>
+	    See the IntPowNr for a @Pow method that does not
+	    perform any rounding operation and is more appropriate for
+	    integer only applications.
+	</p>
+	End Rem
+	Method IntPow:TMAPM(power:Int, decimalPlaces:Int)
+		Local mapm:TMAPM = New TMAPM
+		m_apm_integer_pow(mapm.mapmPtr, decimalPlaces, mapmPtr, power)
+		Return mapm
+	End Method
+	
+	Rem
+	bbdoc: Returns the number raised to @power.
+	about: This method is similiar to IntPow except the result is NOT ROUNDED (Nr). This
+	method would typically be used in an integer only application where the full precision
+	of the result is desired.
+	<p>
+	Note that @power is an integer and not a MAPM number.
+	</p>
+	<p>
+    @power must be >= zero. @power < 0 creates a zero result and a warning on stderr.
+	</p>
+	End Rem
+	Method IntPowNr:TMAPM(power:Int, decimalPlaces:Int)
+		Local mapm:TMAPM = New TMAPM
+		m_apm_integer_pow_nr(mapm.mapmPtr, decimalPlaces, mapmPtr, power)
+		Return mapm
+	End Method
+	
+	Rem
+	bbdoc: Returns the remainder of the number divided by @divisor.
+	End Rem
+	Method Modulo:TMAPM(divisor:TMAPM)
+		Local a:TMAPM = IntegerDivide(divisor)
+		Local b:TMAPM = a.Multiply(divisor)
+		Return Subtract(b)
+	End Method
+
+	Method Delete()
+		If mapmPtr Then
+			m_apm_free(mapmPtr)
+			mapmPtr = Null
+		End If
+	End Method
+
+End Type
+
+Global MM_MaxByte:TMAPM = TMAPM.CreateMAPM("255")
+Global MM_MaxByteP1:TMAPM = TMAPM.CreateMAPM("256")
+Global MM_MaxByteMod:TMAPM = TMAPM.CreateMAPM("256")
+
+Global MM_MaxShort:TMAPM = TMAPM.CreateMAPM("65535")
+Global MM_MaxShortP1:TMAPM = TMAPM.CreateMAPM("65536")
+Global MM_MaxShortMod:TMAPM = TMAPM.CreateMAPM("65536")
+
+Global MM_MaxInt:TMAPM = TMAPM.CreateMAPM("2147483647")
+Global MM_MinInt:TMAPM = TMAPM.CreateMAPM("-2147483648")
+Global MM_MaxIntNeg:TMAPM = TMAPM.CreateMAPM("-4294967296")
+Global MM_MinIntPos:TMAPM = TMAPM.CreateMAPM("4294967294")
+
+Global MM_MaxLong:TMAPM = TMAPM.CreateMAPM("9223372036854775807")
+Global MM_MinLong:TMAPM = TMAPM.CreateMAPM("-9223372036854775808")
+Global MM_MaxLongNeg:TMAPM = TMAPM.CreateMAPM("-18446744073709551616")
+Global MM_MinLongPos:TMAPM = TMAPM.CreateMAPM("18446744073709551615")
+
+Global MM_MaxUInt:TMAPM = TMAPM.CreateMAPM("4294967295")
+Global MM_MaxUIntP1:TMAPM = TMAPM.CreateMAPM("4294967296")
+Global MM_MaxUIntMod:TMAPM = TMAPM.CreateMAPM("4294967296")
+
+Global MM_MaxULong:TMAPM = TMAPM.CreateMAPM("18446744073709551615")
+Global MM_MaxULongP1:TMAPM = TMAPM.CreateMAPM("18446744073709551616")
+Global MM_MaxULongMod:TMAPM = TMAPM.CreateMAPM("18446744073709551616")
+
+
+Global MM_Zero:TMAPM = TMAPM.CreateMAPM()
+Global MM_One:TMAPM = TMAPM.CreateMAPM("1")
+Global MM_Two:TMAPM = TMAPM.CreateMAPM("2")
+Global MM_Sixteen:TMAPM = TMAPM.CreateMAPM("16")
+
+Rem
+Global RadToDeg:TMAPM = TMAPM.CreateMAPM("57.29577951308232087679815481410517033240547246656432154916024386120284714832155263244096899585111094418622338163286489328144826460124831503606826786341194212252638809746726792630798870289311076793826144263826315820961046048702050644425965684112017191205773856628043128496262420337618793729762387079034031598071962408952204518620545992339631484190696622011512660969180151478763736692316410712677403851469016549959419251571198647943521066162438903520230675617779675711331568350620573131336015650134889801878870991777643918273")
+Global DegToRad:TMAPM = TMAPM.CreateMAPM("0.017453292519943295769236907684886127134428718885417254560971914401710091146034494436822415696345094822123044925073790592483854692275281012398474218934047117319168245015010769561697553581238605305168788691271172087032963589602642490187704350918173343939698047594019224158946968481378963297818112495229298469927814479531045416008449560904606967176196468710514390888951836280826780369563245260844119508941294762613143108844183845478429899625621072806214155969235444237497596399365292916062377434350066384054631518680225870239")
+
+Global MM_Two:TMAPM = TMAPM.CreateMAPM("2")
+Global MM_Three:TMAPM = TMAPM.CreateMAPM("3")
+Global MM_Four:TMAPM = TMAPM.CreateMAPM("4")
+Global MM_Five:TMAPM = TMAPM.CreateMAPM("5")
+Global MM_Ten:TMAPM = TMAPM.CreateMAPM("10")
+
+Global MM_PI:TMAPM = TMAPM.CreateMAPM("3.1415926535897932384626433832795028841971693993751058209749445923078" + ..
+	"164062862089986280348253421170679821480865132823066470938446095505822" + ..
+	"317253594081284811174502841027019385211055596446229489549303819644288" + ..
+	"109756659334461284756482337867831652712019091456485669234603486104543" + ..
+	"266482133936072602491412737245870066063155881748815209209628292540917" + ..
+	"153643678925903600113305305488204665213841469519415116094330572703657" + ..
+	"595919530921861173819326117931051185480744623799627495673518857527248" + ..
+	"91227938183011949129833673362440656643")
+End Rem

+ 769 - 0
mapm/src/README

@@ -0,0 +1,769 @@
+**************************************************************************
+  
+				   MAPM
+
+			       Version 4.9.5
+
+			     December 10, 2007
+
+			      Michael C. Ring
+
+			    [email protected]
+
+		    Latest release will be available at
+		        http://tc.umn.edu/~ringx004
+
+***************************************************************************
+*									  *
+*  Copyright (C) 1999 - 2007   Michael C. Ring                            *
+*									  *
+*  This software is Freeware.						  *
+*									  *
+*  Permission to use, copy, and distribute this software and its          *
+*  documentation for any purpose with or without fee is hereby granted,   *
+*  provided that the above copyright notice appear in all copies and      *
+*  that both that copyright notice and this permission notice appear      *
+*  in supporting documentation.                                           *
+*									  *
+*  Permission to modify the software is granted. Permission to distribute *
+*  the modified code is granted. Modifications are to be distributed by   *
+*  using the file 'license.txt' as a template to modify the file header.  *
+*  'license.txt' is available in the official MAPM distribution.          *
+*									  *
+*  To distribute modified source code, insert the file 'license.txt'      *
+*  at the top of all modified source code files and edit accordingly.     *
+*									  *
+*  This software is provided "as is" without express or implied warranty. *
+*									  *
+***************************************************************************
+
+		---------------------------------------
+		Mike's Arbitrary Precision Math Library
+		---------------------------------------
+
+Mike's Arbitrary Precision Math Library is a set of functions that
+allow the user to perform math to any level of accuracy that is
+desired. The inspiration for this library was Lloyd Zusman's similar
+APM package that was released in ~1988. I borrowed some of his ideas
+in my implementation, creating a new data type (MAPM) and how the data
+type was used by the user. However, there were a few things I wanted
+my library to do that the original library did not :
+
+1) Round a value to any desired precision. This is very handy when
+   multiplying for many iterations. Since multiplication guarantees an
+   exact result, the number of digits will grow without bound. I wanted
+   a way to trim the number of significant digits that were retained.
+
+2) A natural support for floating point values. From most of the other
+   libraries I looked at, they seem to have a preference for integer
+   only type math manipulations. (However, this library will also do
+   integer only math if you desire).
+
+   And if a library can only do integers, it can't do ...
+
+3) Trig functions and other common C math library functions. This library
+   will perform the following functions to any desired precision level :
+   SQRT, CBRT, SIN, COS, TAN, ARC-SIN, ARC-COS, ARC-TAN, ARC-TAN2, LOG,
+   LOG10, EXP, POW, SINH, COSH, TANH, ARC-SINH, ARC-COSH, ARC-TANH, and
+   also FACTORIAL.  The full 'math.h' is not duplicated, though I think
+   these are most of the important ones. My definition of what's important
+   is what I've actually used in a real application.
+
+**************************************************************************
+
+NOTE:
+
+There is a COMPILER BUG in Microsoft's Visual C++ 7.x (VS.NET 2003) which
+prevents a C++ MAPM application from compiling.
+
+This only affects C++ applications. C applications are OK.
+
+The compiler bug creates an error C2676 similar to this:
+
+<path>...\mapm-49\M_APM.H(###) : error C2676: binary operator '-': 'MAPM'
+doesn't define this operator or a conversion to a suitable type for the
+predefined operator.
+
+To work around this bug, go to http://www.microsoft.com
+
+In the upper right corner of web page, search for "814455".
+
+The results of the search will point you to an article on how to work
+around the problem.
+
+**************************************************************************
+
+NOTE: MAPM Library History can now be found in 'history.txt'
+
+**************************************************************************
+
+ANOTHER NOTE: For the Windows/DOS distribution, the filename convention
+will always be in 8.3 format. This is because there are some users who
+still use 16 bit DOS ....
+
+(I really wasn't sure what to call this library. 'Arbitrary Precision Math'
+is a defacto standard for what this does, but that name was already taken,
+so I just put an 'M' in front of it ...)
+
+**************************************************************************
+
+MAPM LIBRARY NUMERICAL LIMITATIONS:
+
+A general floating point number is of the form:
+
+Sn.nnnnnnnnE+yyyy        ex: -4.318384739357974916E+6215
+Sn.nnnnnnnnE-yyyy        ex: +8.208237913789131096523645193E-12873
+
+'S' is the sign, + or -.
+
+In MAPM, a number (n.nnnn...) may contain up to ( INT_MAX - 1 ) digits.
+
+For example, an MAPM number with a 16 bit integer may contain 2^15 or 32,767
+digits. An MAPM number with a 32 bit integer may contain 2^31 or 2,147,483,647
+digits. All MAPM numbers are stored in RAM, there is no "data on disk" option.
+So to represent the maximum number of digits on a 32 bit CPU will require
+greater than 2 Gig of RAM.
+
+If you have a CPU with 64 bit ints, then the limitation is 2^63 or
+9,223,372,036,854,775,807. It should be a very long time before computers
+have this much RAM in them.
+
+For the exponent (yyyy), the limitations are also INT_MAX and INT_MIN.
+
+For a 16 bit CPU, the largest number you can represent is approx
+0.9999999....E+32767.    (H)
+
+For a 16 bit CPU, the smallest number you can represent (other than 0)
+is approx 0.1E-32767.   (L)
+
+For a 32 bit CPU, the largest number you can represent is approx
+0.9999999....E+2147483647.   (H)
+
+For a 32 bit CPU, the smallest number you can represent (other than 0)
+is approx 0.1E-2147483647.  (L)
+
+The limitations for negative numbers are the same as positive numbers.
+
+
+                            Real Number Axis
+
+     +------------------------+    ---    +--------------------------+
+     |                        |     |     |                          |
+    -H                       -L    0.0   +L                         +H
+
+
+
+MAPM can represent real numbers from -H to -L, 0.0, +L to +H.
+
+The number of significant digits is typically only limited by available RAM.
+
+In MAPM, numerical overflows and underflows are not handled very well
+(actually not at all). There really isn't a clean and portable way to
+detect integer overflow and underflow. Per K&R C, the result of integer
+overflow/underflow is implementation dependent. In assembly language, when
+you add two numbers, you have access to a "carry flag" to see if an overflow
+occurred. C has no analogous operator to a carry flag.
+
+It is up to the user to decide if the results are valid for a given operation.
+In a 32 bit environment, the limit is so large that this is likely not an
+issue for most typical applications. However, it doesn't take much to overflow
+a 16 bit int so care should taken in a 16 bit environment.
+
+The reaction to an integer overflow/underflow is unknown at run-time:
+
+    o) adding 2 large positive numbers may silently roll over to a
+       negative number.
+    o) in some embedded applications an integer overflow/underflow triggers
+       a hardware exception.
+
+Since I don't have control over where this library could possibly run,
+I chose to ignore the problem for now. If anyone has some suggestions
+(that's portable), please let me know.
+
+**************************************************************************
+
+KNOWN BUGS : (Other than integer overflow discussed above....) None
+
+**************************************************************************
+
+IF YOU ARE IN A HURRY ...
+
+UNIX:  (assumes gcc compiler)
+
+run    make          (build library + 4 executables)
+
+run    make -f makefile.osx      (for MAC OSX)
+
+--- OR ---
+
+run:   mklib         (this will create the library, lib_mapm.a)
+
+run:   mkdemo        (this will create 4 executables, 'calc', 'validate',
+                      'primenum', and 'cpp_demo')
+
+
+DOS / Win NT/9x  (in a DOS window for NT/9x):
+
+see the file 'README.DOS' for instructions.
+
+
+**************************************************************************
+
+calc:  This is a command line version of an RPN calculator. If you are
+       familiar with RPN calculators, the use of this program will be
+       quite obvious. The default is 30 decimal places but this can be
+       changed with the '-d' command line option. This is not an
+       interactive program, it just computes an expression from the command
+       line. Run 'calc' with no arguments to get a list of the operators.
+
+       compute : (345.2 * 87.33) - (11.88 / 3.21E-2)
+
+       calc 345.2 87.33 x 11.88 3.21E-2 / -
+       result: 29776.22254205607476635514018692
+
+
+       compute PI to 70 decimal places :  (6 * arcsin(0.5))
+
+       calc -d70 6 .5 as x
+       result :
+3.1415926535897932384626433832795028841971693993751058209749445923078164
+
+       calc -d70 -1 ac             (arccos(-1) for fastest possible way)
+
+validate : This program will compare the MAPM math functions to the C
+	   standard library functions, like sqrt, sin, exp, etc.  This
+	   should give the user a good idea that the library is operating
+	   correctly. The program will also perform high precision math
+	   using known quantities like PI, log(2), etc.
+
+	   'validate' also attempts to obtain as much code coverage of the
+	   library as is practical. I used 'gcov' (available with the gcc
+	   distribution) to test the code coverage. 100% coverage is not
+	   obtained, compromises must be made in order to have the program
+	   run in a reasonable amount of time.
+
+primenum:  This program will generate the first 10 prime numbers starting
+	   with the number entered as an argument.
+
+	   Example:  primenum 1234567890 will output (actually 1 per line):
+		     this took ~3 sec on my Linux PC, a 350MHz PII.
+
+	   1234567891, 1234567907, 1234567913, 1234567927, 1234567949,
+	   1234567967, 1234567981, 1234568021, 1234568029, 1234568047
+
+
+**************************************************************************
+
+To use the library, simply include 'm_apm.h' and link your program
+with the library, libmapm.a (unix) or mapm.lib (dos).
+
+Note: If your system creates libraries with a '.a' extension, then the
+library will be named libmapm.a. (This conforms to typical unix naming
+conventions).
+
+Note: If your system creates libraries with a '.lib' extension, then the
+library will be named mapm.lib.
+
+For unix builds, you also may need to specify the math library (-lm) when
+linking. The reason is some of the MAPM functions use an iterative algorithm.
+When you use an iterative solution, you have to supply an initial guess. I
+use the standard math library to generate this initial guess. I debated
+whether this library should be stand-alone, i.e. generate it's own initial
+guesses with some algorithm. In the end, I decided using the standard math
+library would not be a big inconvienence and also it was just too tempting
+having an immediate 15 digits of precision. When you prime the iterative
+routines with 15 accurate digits, the MAPM functions converge faster.
+
+See the file 'algorithms.used' to see a description of the algorithms I
+used in the library. Some I derived on my own, others I borrowed from people
+smarter than me. Version 2 of the library supports a 'fast' multiplication
+algorithm. The algorithm used is described in the algorithms.used file. A
+considerable amount of time went into finding fast algorithms for the
+library. However, some could possibly be even better. If anyone has a
+more efficient algorithm for any of these functions, I would like to here
+from you.
+
+See the file 'function.ref' to see a description of all the functions in
+the library and the calling conventions, prototypes, etc.
+
+See the file 'struct.ref' which documents how I store the numbers internally
+in the MAPM data structure. This will not be needed for normal use, but it
+will be very useful if you need to change/add to the existing library.
+
+**************************************************************************
+
+USING MAPM IN A MULTI-THREADED APPLICATION :
+
+Note that the default MAPM library is NOT thread safe. MAPM internal data
+structures could get corrupted if multiple MAPM functions are active at the
+same time. The user should guarantee that only one thread is performing
+MAPM functions. This can usually be achieved by a call to the operating
+system to obtain a 'semaphore', 'mutex', or 'critical code section' so the
+operating system will guarantee that only one MAPM thread will be active
+at a time.
+
+The necessary function wrappers for thread safe operation can be found in
+the sub-directory 'multi_thread' (unix) or 'multithd' (Win/Dos). For now,
+only Microsoft Visual C++ 6.0 is supported.
+
+**************************************************************************
+
+QUICK TEMPLATE FOR NORMAL USE :
+
+The MAPM math is done on a new data type called "M_APM".  This is
+actually a pointer to a structure, but the contents of the structure
+should never be manipulated: all operations on MAPM entities are done
+through a functional interface.
+
+The MAPM routines will automatically allocate enough space in their
+results to hold the proper number of digits.
+
+The caller must initialize all MAPM values before the routines can
+operate on them (including the values intended to contain results of
+calculations).  Once this initialization is done, the user never needs
+to worry about resizing the MAPM values, as this is handled inside the
+MAPM routines and is totally invisible to the user.
+
+The result of a MAPM operation cannot be one of the other MAPM operands.
+If you want this to be the case, you must put the result into a
+temporary variable and then assign (m_apm_copy) it to the appropriate operand.
+
+All of the MAPM math functions begin with m_apm_*.
+
+There are some predefined constants for your use. In case it's not obvious,
+these should never appear as a 'result' parameter in a function call.
+
+The following constants are available : (declared in m_apm.h)
+
+MM_Zero             MM_One              MM_Two             MM_Three
+MM_Four             MM_Five             MM_Ten
+MM_PI               MM_HALF_PI          MM_2_PI            MM_E
+MM_LOG_E_BASE_10    MM_LOG_10_BASE_E    MM_LOG_2_BASE_E    MM_LOG_3_BASE_E
+
+
+The non-integer constants above (PI, log(2), etc) are accurate to 128
+decimal places. The file mapmcnst.c contains these constants. I've
+included 512 digit constants in this file also that are commented out.
+If you need more than 512 digits, you can simply use the 'calc' program
+to generate more precise constants (or create more precise constants at
+run-time in your app).  The number of significant digits in the constants
+should be 6-8 more than the value specified in the #define.
+
+
+Basic plan of attack:
+
+(1)  get your 'numbers' into M_APM format.
+(2)  do your high precision math.
+(3)  get the M_APM numbers back into a format you can use.
+
+
+--------  (1)  --------
+
+#include "m_apm.h"        /* must be included before any M_APM 'declares' */
+
+M_APM    area_mapm;                /* declare your variables */
+M_APM    tmp_mapm;
+M_APM    array_mapm[10];           /* can use normal array notation */
+M_APM    array2d_mapm[10][10];
+
+area_mapm = m_apm_init()           /* init your variables */
+tmp_mapm  = m_apm_init();
+
+for (i=0; i < M; i++)              /* must init every element of the array */
+  array_mapm[i] = m_apm_init();
+
+for (i=0; i < M; i++)
+   for (j=0; j < N; j++)
+     array2d_mapm[i][j] = m_apm_init();
+
+/*
+ *   there are 3 ways to convert your number into an M_APM number
+ *   (see the file function.ref)
+ *
+ *   a) literal string   (exponential notation OK)
+ *   b) long variable
+ *   c) double variable
+ */
+
+m_apm_set_string(tmp_mapm, "5.3286E-7");
+m_apm_set_long(array_mapm[6], -872253L);
+m_apm_set_double(array2d_mapm[3][7], -529.4486711);
+
+
+--------  (2)  --------
+
+do your math ...
+
+m_apm_add(cc_mapm, aa_mapm, MM_PI);
+m_apm_divide(bb_mapm, DECIMAL_PLACES, aa_mapm, MM_LOG_2_BASE_E);
+m_apm_sin(bb_mapm, DECIMAL_PLACES, aa_mapm);
+whatever ...
+
+
+--------  (3)  --------
+
+There are 5 total functions for converting an M_APM number into something
+useful.  (See the file 'function.ref' for full function descriptions)
+
+For these 5 functions, M_APM number -> string is the conversion
+
+===================
+====  METHOD 1 ==== : floating point values	(m_apm_to_string)
+===================
+
+the format will be in scientific (exponential) notation
+
+output string = [-]n.nnnnnE+x   or ...E-x
+
+where 'n' are digits and the exponent will be always be present,
+including E+0
+
+it's easy to convert this to a double:
+
+double dtmp = atof(out_buffer);
+
+
+===================
+====  METHOD 2 ==== : floating point values	(m_apm_to_fixpt_string)
+===================				(m_apm_to_fixpt_stringex)
+						(m_apm_to_fixpt_stringexp)
+the format will be in fixed point notation
+
+output string = [-]mmm.nnnnnn
+
+where 'm' & 'n' are digits.
+
+
+===================
+====  METHOD 3 ==== : integer values		(m_apm_to_integer_string)
+===================
+
+the format will simply be digits with a possible leading '-' sign.
+
+output string = [-]nnnnnn
+
+where 'n' are digits.
+
+it's easy to convert this to a long :
+long mtmp = atol(out_buffer);
+
+... or an int :
+int itmp = atoi(out_buffer);
+
+Note that if the M_APM number has a fractional portion, the fraction
+will be truncated and only the integer portion will be output.
+
+
+char  out_buffer[1024];
+
+m_apm_to_string(out_buffer, DECIMAL_PLACES, mapm_number);
+
+m_apm_to_fixpt_string(out_buffer, DECIMAL_PLACES, mapm_number);
+
+m_apm_to_integer_string(out_buffer, mapm_number);
+
+
+**************************************************************************
+
+*********************************************************
+****  NOTES on the fixed point formatting functions  ****
+*********************************************************
+
+Assume you have the following code:
+
+
+-->   m_apm_set_string(aa_mapm, "2.0E18");
+-->   m_apm_sqrt(bb_mapm, 40, aa_mapm);
+
+-->   m_apm_to_string(buffer, 40, bb_mapm);
+-->   fprintf(stdout,"[%s]\n",buffer);
+
+-->   m_apm_to_fixpt_string(buffer, 40, bb_mapm);
+-->   fprintf(stdout,"[%s]\n",buffer);
+
+
+It is desired to compute the sqrt(2.0E+18) to
+40 significant digits. You then want the result
+output with 40 decimal places. But the output
+from above is :
+
+[1.4142135623730950488016887242096980785697E+9]
+[1414213562.3730950488016887242096980785697000000000]
+
+
+Why are there 9 '0' in the fixed point formatted string??
+
+The sqrt calculation computed 40 significant digits relative
+to the number in EXPONENTIAL format. When the number is
+output in exponential format, the 40 digits are as expected
+with an exponent of 'E+9'.
+
+The same number formatted as fixed point appears to be an
+error.  Remember, we computed 40 significant digits.  However,
+the result has an exponent of '+9'. So, 9 of the digits are
+needed *before* the decimal point. In our calculation, only
+31 digits of precision remain from our original 40. We then
+asked the fixed point formatting function to format 40 digits.
+Only 31 are left so 9 zeros are used as pad at the end to
+fulfill the 40 places asked for.
+
+Keep this in mind if you truly desire more accurate results
+in fixed point formatting and your result contains a large
+positive exponent.
+
+**************************************************************************
+
+MAPM C++ WRAPPER CLASS:
+
+Orion Sky Lawlor ([email protected]) has added a very nice C++ wrapper
+class to m_apm.h. This C++ class will have no effect if you just use
+a normal C compiler. The library will operate as before with no user
+impacts.
+
+For now, I recommend compiling the library as 'C'. The library will
+compile as a C++ library, but then it is likely that you would not
+be able to use the library in a straight C application.  Since the C++
+wrapper class works very nicely as is, there is no pressing need to compile
+the library as C++.
+
+See the file 'cpp_function.ref' to see a description of how to use
+the MAPM class.
+
+To compile and link the C++ demo program: (assuming the library is
+already built)
+
+UNIX:
+
+g++ cpp_demo.cpp lib_mapm.a -s -o cpp_demo -lm
+
+GCC for DOS: (gxx (or g++) is the C++ compiler)
+
+gxx cpp_demo.cpp lib_mapm.a -s -o cpp_demo.exe -lm
+
+
+Using the C++ wrapper allows you to do things like:
+
+// Compute the factorial of the integer n
+
+MAPM factorial(MAPM n)
+{
+	MAPM i;
+	MAPM product = 1;
+	for (i=2; i <= n; i++)
+		product *= i;
+	return product;
+}
+
+
+The syntax is the same as if you were just writing normal code, but all
+the computations will be performed with the high precision math library,
+using the new 'datatype' MAPM.
+
+The default precision of the computations is as follows:
+
+Addition, subtraction, and multiplication will maintain ALL significant
+digits.
+
+All other operations (divide, sin, etc) will use the following rules:
+
+1) if the operation uses only one input value [y = sin(x)], the result 'y'
+   will be the same precision as 'x', with a minimum of 30 digits if 'x' is
+   less than 30 digits.
+
+2) if the operation uses two input values [z = atan2(y,x)], the result 'z'
+   will be the max digits of 'x' or 'y' with a minimum of 30.
+
+The default precision is 30 digits. You can change the precision at
+any time with the function 'm_apm_cpp_precision'. (See function.ref)
+
+---->        m_apm_cpp_precision(80);
+
+will result in all operations being accurate to a minimum of 80 significant
+digits. If any operand contains more than the minimum number of digits, then
+the result will contain the max number of digits of the operands.
+
+
+NOTE!: Some real life use with the C++ wrapper has revealed a certain
+       tendency for a program to become quite slow after many iterations
+       (like in a for/while loop).  After a little debug, the reason
+       became clear. Remember that multiplication will maintain ALL
+       significant digits :
+
+       20 digit number x 20 digit number =  40 digits
+       40 digit number x 40 digit number =  80 digits
+       80 digit number x 80 digit number = 160 digits
+       etc.
+
+       So after numerous iterations, the number of significant digits
+       was growing without bound. The easy way to fix the problem is
+       to simply *round* your result after a multiply or some other
+       complex operation. For example:
+
+       #define MAX_DIGITS 256
+
+       p1 = (p0 * sin(b1) * exp(1 + u1)) / sqrt(1 + b1);
+       p1 = p1.round(MAX_DIGITS);
+
+       If you 'round' as shown here, your program will likely be
+       nearly as fast as a straight 'C' version.
+
+
+NOTE #2!
+
+       Reference the following code snippet:
+
+       ...
+
+       MAPM  pi1, pi2;
+       char  obuf[256];
+
+       m_apm_cpp_precision(62);
+
+       pi1 = 2 * asin("1");
+       pi2 = 2 * asin(1.0);
+
+       pi1.toString(obuf, 60);   printf("PI1 = [%s] \n",obuf);
+       pi2.toString(obuf, 60);   printf("PI2 = [%s] \n",obuf);
+
+       ...
+
+       On my system, the output is :
+
+PI1 = [3.141592653589793238462643383279502884197169399375105820974945E+0]
+PI2 = [3.141592653589790000000000000000000000000000000000000000000000E+0]
+
+
+       PI2 only has 15 significant digits! This is due to how the second
+       asin is called. It is called with a 'double' as the argument, hence
+       the compiler will use the default double asin function from the
+       standard library. This is likely not the intent but this would be
+       easy to miss if this was a complex calculation and we didn't know
+       the 'right' answer.
+
+       In order to force the use of the overloaded MAPM functions, call the
+       MAPM functions with a quoted string as the argument (if the argument
+       is a constant and not a variable).
+
+       This would also work (though it seems less elegant ...) :
+
+       MAPM t = 1;
+       pi2 = 2 * asin(t);
+
+-----------
+
+If you have any questions or problems with the C++ wrapper, please let
+me know. I am not very C++ proficient, but I'd still like to know about any
+problems.  Orion Sky Lawlor ([email protected]) is the one who implemented
+the MAPM class, so he'll have to resolve any real hardcore problems, if you
+have any.
+
+**************************************************************************
+
+TESTING :
+
+Testing the library was interesting.  How do I know it's right?  Since I
+test the library against the standard C runtime math library (see below)
+I have high confidence that the MAPM library is giving correct results.
+The logic here is the basic algorithms are independent of the number of
+digits calculated, more digits just takes longer.
+
+The MAPM library has been tested in the following environments :
+
+Linux i486 / gcc 2.7.2.3, gcc 2.95.2
+Linux i686 / gcc 2.91.66, gcc 2.95.2, gcc 2.95.3, gcc 3.0.4, gcc 3.2.3
+Linux i686 / Intel Linux C/C++ Compiler Verison 7.0 / 8.1
+FreeBSD 4.1 / gcc 2.95.1
+FreeBSD 4.8 / gcc 2.95.4
+FreeBSD 5.x / gcc 2.95.2, gcc 2.95.3
+Redhat Linux 8.2 / gcc 3.2
+HP-UX 9.x /gcc 2.5.8
+HP-UX 10.x / gcc 2.95.2
+Sun 5.5.1  (output from uname), gcc 3.1.1
+Sun Solaris 2.6 / gcc 2.95.1, gcc 2.95.3, gcc 3.2.3
+MAC OSX / gcc ?
+DOS 5.0 using GCC 2.8.1 for DOS
+DOS 5.0 using GCC 2.95.2 for DOS
+DOS ??? using Borland Turbo C++ 3.0
+WIN NT+SP5 using Borland C++ 5.02 IDE, 5.2 & 5.5 command line.
+WIN 2000 using National Instruments LabWindows CVI 6.0
+WIN98 using Borland C++ 5.5 command line.
+WIN98 & NT & 2000 & XP using LCC-WIN32 Ver 3.2, 3.3
+WIN98 & NT using Watcom C 11.x
+WIN95 & NT using Open Watcom 1.0
+WIN95 & WIN98 using MINGW-32 version mingw-1.0.1-20010726
+WIN95 & WIN2000 using DEV-CPP 5.0 Beta 8, 4.9.8.0
+MINGW-32 with gcc 3.2   (mingw special 20020817-1)
+MINGW-32 with gcc 3.2.3 (mingw special 20030504-1)
+WINXP & MINGW-32 with gcc 3.4.5
+WINXP & Digital Mars Compiler 8.49
+WIN?? using Metrowerks CodeWarrior Pro 7.0 for Windows
+DOS 5.0 using Microsoft C 5.1 and 8.00c  (16 bit EXEs)
+WIN98 & NT using Microsoft Visual C++ 6.0
+WIN98 & NT using Microsoft Visual C++ 7.x (VS.NET 2003 except for
+                                           known compiler bug C2676)
+
+
+
+As a general rule, when calculating a quantity to a given number of decimal
+places, I calculated 4-6 extra digits and then rounded the result to what was
+asked for. I decided to be conservative and give a correct answer rather than
+to be faster and possibly have the last 2-3 digits in error. Also, some of
+the functions call other functions (calculating arc-cos will call cos, log
+will call exp, etc.) so I had to calculate a few extra digits in each iteration
+to guarantee the loops terminated correctly.
+
+1)  I debugged the 4 basic math operations. I threw numerous test cases at
+    each of the operations until I knew they were correct.
+
+    Also note that the math.h type functions all call the 4 basic operations
+    numerous times. So if all the math.h functions work, it is highly
+    probable the 4 basic math operations work also.
+
+2)  'math.h' type functions.
+
+     SQRT:     Not real hard to check. Single stepping through the iterative
+	       loop showed it was always converging to the sqrt.
+
+     CBRT:     Similar to sqrt, single stepping through the iterative loop
+	       showed it was always converging to the cube root.
+
+     EXP:      I wrote a separate algorithm which expanded the Taylor series
+	       manually and compared the results against the library.
+
+     POW:      Straightforward since this just calls 'EXP'.
+
+     LOG:      I wrote a separate algorithm which expanded the Taylor series
+	       manually and compared the results against the library. This
+	       took a long time to execute since the normal series converges
+	       VERY slowly for the log function. This is why the LOG function
+	       uses an iterative algorithm.
+
+     LOG10:    Straightforward since this just calls 'LOG'.
+
+     SIN/COS:  I wrote a separate algorithm which expanded the Taylor series
+	       manually and compared the results against the library.
+
+     TAN:      Straightforward since this just calls 'SIN' and 'COS'.
+
+     ARC-x:    Single stepping through the iterative loop showed the arc
+	       family of functions were always converging. Also used these
+	       to compute PI. The value of PI is now known to many, many
+	       digits. I computed PI to 1000+ digits by computing:
+
+	       6 * arcsin(0.5)  and  4 * arctan(1)  and  3 * arccos(0.5)
+
+	       and compared the output to the published 'real' values of PI.
+
+	       The arc family of functions exercise considerable portions
+	       of the library.
+
+  HYPERBOLIC:  The hyperbolic functions just use exp, log, and the 4 basic
+  	       math operations. All of these functions simply use other
+	       existing functions in the library.
+
+     FINALLY:  Run the program 'validate'. This program compares the first
+	       13-14 significant digits of the standard C library against
+	       the MAPM library. If this program passes, you can feel
+	       confident that the MAPM library is giving correct results.
+
+**************************************************************************

+ 662 - 0
mapm/src/m_apm.h

@@ -0,0 +1,662 @@
+
+/* 
+ *  M_APM  -  m_apm.h
+ *
+ *  Copyright (C) 1999 - 2007   Michael C. Ring
+ *
+ *  Permission to use, copy, and distribute this software and its
+ *  documentation for any purpose with or without fee is hereby granted,
+ *  provided that the above copyright notice appear in all copies and
+ *  that both that copyright notice and this permission notice appear
+ *  in supporting documentation.
+ *
+ *  Permission to modify the software is granted. Permission to distribute
+ *  the modified code is granted. Modifications are to be distributed by
+ *  using the file 'license.txt' as a template to modify the file header.
+ *  'license.txt' is available in the official MAPM distribution.
+ *
+ *  This software is provided "as is" without express or implied warranty.
+ */
+
+/*
+ *      This is the header file that the user will include.
+ *
+ *      $Log: m_apm.h,v $
+ *      Revision 1.42  2007/12/03 02:28:25  mike
+ *      update copyright
+ *
+ *      Revision 1.41  2007/12/03 01:21:35  mike
+ *      Update license
+ *      Update version to 4.9.5
+ *
+ *      Revision 1.40  2004/05/31 22:06:02  mike
+ *      add % operator to C++ wrapper
+ *
+ *      Revision 1.39  2004/05/24 04:11:41  mike
+ *      updated version to 4.9.2
+ *
+ *      Revision 1.38  2004/04/01 03:17:19  mike
+ *      update version to 4.9.1
+ *
+ *      Revision 1.37  2004/01/02 20:40:49  mike
+ *      fix date on copyright
+ *
+ *      Revision 1.36  2004/01/02 00:52:38  mike
+ *      update version to 4.9
+ *
+ *      Revision 1.35  2003/11/23 05:12:46  mike
+ *      update version
+ *
+ *      Revision 1.34  2003/07/21 20:59:54  mike
+ *      update version to 4.8
+ *
+ *      Revision 1.33  2003/05/14 21:19:23  mike
+ *      change version string
+ *
+ *      Revision 1.32  2003/05/06 21:29:11  mike
+ *      add defines for lib versions (and prototypes)
+ *
+ *      Revision 1.31  2002/11/04 20:46:33  mike
+ *      change definition of the M_APM structure
+ *
+ *      Revision 1.30  2002/11/03 23:36:24  mike
+ *      added new function, m_apm_integer_pow_nr
+ *
+ *      Revision 1.29  2002/02/14 21:43:00  mike
+ *      add set_random_seed prototype
+ *
+ *      Revision 1.28  2001/08/28 18:29:32  mike
+ *      fix fixptstringexp
+ *
+ *      Revision 1.27  2001/08/27 22:45:03  mike
+ *      fix typo
+ *
+ *      Revision 1.26  2001/08/27 22:43:06  mike
+ *      add new fix pt functions to C++ wrapper
+ *
+ *      Revision 1.25  2001/08/26 22:09:13  mike
+ *      add new prototype
+ *
+ *      Revision 1.24  2001/08/25 16:48:21  mike
+ *      add new prototypes
+ *
+ *      Revision 1.23  2001/07/16 18:40:27  mike
+ *      add free_all_mem, trim_mem_usage prototypes
+ *
+ *      Revision 1.22  2001/07/15 20:49:21  mike
+ *      added is_odd, is_even, gcd, lcm functions
+ *
+ *      Revision 1.21  2001/03/25 21:24:55  mike
+ *      add floor and ceil functions
+ *
+ *      Revision 1.20  2000/09/23 19:05:29  mike
+ *      add _reciprocal prototype
+ *
+ *      Revision 1.19  2000/08/21 23:30:13  mike
+ *      add _is_integer function
+ *
+ *      Revision 1.18  2000/07/06 00:10:15  mike
+ *      redo declare for MM_cpp_min_precision
+ *
+ *      Revision 1.17  2000/07/04 20:59:43  mike
+ *      move MM_cpp_min_precision into cplusplus block below
+ *
+ *      Revision 1.16  2000/07/04 20:49:04  mike
+ *      move 'MM_cpp_min_precision' inside the extern "C"
+ *      brackets
+ *
+ *      Revision 1.15  2000/04/06 21:19:38  mike
+ *      minor final tweaks from Orion
+ *
+ *      Revision 1.14  2000/04/05 20:15:25  mike
+ *      add cpp_min_precision
+ *
+ *      Revision 1.13  2000/04/04 22:20:09  mike
+ *      updated some comments from Orion
+ *
+ *      Revision 1.12  2000/04/04 19:46:36  mike
+ *      fix preincrement, postincrement operators
+ *      added some comments
+ *      added 'ipow' operators
+ *
+ *      Revision 1.11  2000/04/03 22:08:35  mike
+ *      added MAPM C++ wrapper class
+ *      supplied by Orion Sky Lawlor ([email protected])
+ *
+ *      Revision 1.10  2000/04/03 18:40:28  mike
+ *      add #define atan2 for alias
+ *
+ *      Revision 1.9  2000/04/03 18:05:23  mike
+ *      added hyperbolic functions
+ *
+ *      Revision 1.8  2000/04/03 17:26:57  mike
+ *      add cbrt prototype
+ *
+ *      Revision 1.7  1999/09/18 03:11:23  mike
+ *      add new prototype
+ *
+ *      Revision 1.6  1999/09/18 03:08:25  mike
+ *      add new prototypes
+ *
+ *      Revision 1.5  1999/09/18 01:37:55  mike
+ *      added new prototype
+ *
+ *      Revision 1.4  1999/07/12 02:04:30  mike
+ *      added new function prototpye (m_apm_integer_string)
+ *
+ *      Revision 1.3  1999/05/15 21:04:08  mike
+ *      added factorial prototype
+ *
+ *      Revision 1.2  1999/05/12 20:50:12  mike
+ *      added more constants
+ *
+ *      Revision 1.1  1999/05/12 20:48:25  mike
+ *      Initial revision
+ *
+ *      $Id: m_apm.h,v 1.42 2007/12/03 02:28:25 mike Exp $
+ */
+
+#ifndef M__APM__INCLUDED
+#define M__APM__INCLUDED
+
+#ifdef __cplusplus
+/* Comment this line out if you've compiled the library as C++. */
+#define APM_CONVERT_FROM_C
+#endif
+
+#ifdef APM_CONVERT_FROM_C
+extern "C" {
+#endif
+
+typedef unsigned char UCHAR;
+
+typedef struct  {
+	UCHAR	*m_apm_data;
+	long	m_apm_id;
+	int     m_apm_refcount;       /* <- used only by C++ MAPM class */
+	int	m_apm_malloclength;
+	int	m_apm_datalength;
+	int	m_apm_exponent;
+	int	m_apm_sign;
+} M_APM_struct;
+
+typedef M_APM_struct *M_APM;
+
+
+#define MAPM_LIB_VERSION \
+    "MAPM Library Version 4.9.5  Copyright (C) 1999-2007, Michael C. Ring"
+#define MAPM_LIB_SHORT_VERSION "4.9.5"
+
+
+/*
+ *	convienient predefined constants
+ */
+
+extern	M_APM	MM_Zero;
+extern	M_APM	MM_One;
+extern	M_APM	MM_Two;
+extern	M_APM	MM_Three;
+extern	M_APM	MM_Four;
+extern	M_APM	MM_Five;
+extern	M_APM	MM_Ten;
+
+extern	M_APM	MM_PI;
+extern	M_APM	MM_HALF_PI;
+extern	M_APM	MM_2_PI;
+extern	M_APM	MM_E;
+
+extern	M_APM	MM_LOG_E_BASE_10;
+extern	M_APM	MM_LOG_10_BASE_E;
+extern	M_APM	MM_LOG_2_BASE_E;
+extern	M_APM	MM_LOG_3_BASE_E;
+
+
+/*
+ *	function prototypes
+ */
+
+extern	M_APM	m_apm_init(void);
+extern	void	m_apm_free(M_APM);
+extern	void	m_apm_free_all_mem(void);
+extern	void	m_apm_trim_mem_usage(void);
+extern	char	*m_apm_lib_version(char *);
+extern	char	*m_apm_lib_short_version(char *);
+
+extern	void	m_apm_set_string(M_APM, char *);
+extern	void	m_apm_set_double(M_APM, double);
+extern	void	m_apm_set_long(M_APM, long);
+
+extern	void	m_apm_to_string(char *, int, M_APM);
+extern  void	m_apm_to_fixpt_string(char *, int, M_APM);
+extern  void	m_apm_to_fixpt_stringex(char *, int, M_APM, char, char, int);
+extern  char	*m_apm_to_fixpt_stringexp(int, M_APM, char, char, int);
+extern  void    m_apm_to_integer_string(char *, M_APM);
+
+extern	void	m_apm_absolute_value(M_APM, M_APM);
+extern	void	m_apm_negate(M_APM, M_APM);
+extern	void	m_apm_copy(M_APM, M_APM);
+extern	void	m_apm_round(M_APM, int, M_APM);
+extern	int	m_apm_compare(M_APM, M_APM);
+extern	int	m_apm_sign(M_APM);
+extern	int	m_apm_exponent(M_APM);
+extern	int	m_apm_significant_digits(M_APM);
+extern	int	m_apm_is_integer(M_APM);
+extern	int	m_apm_is_even(M_APM);
+extern	int	m_apm_is_odd(M_APM);
+
+extern	void	m_apm_gcd(M_APM, M_APM, M_APM);
+extern	void	m_apm_lcm(M_APM, M_APM, M_APM);
+
+extern	void	m_apm_add(M_APM, M_APM, M_APM);
+extern	void	m_apm_subtract(M_APM, M_APM, M_APM);
+extern	void	m_apm_multiply(M_APM, M_APM, M_APM);
+extern	void	m_apm_divide(M_APM, int, M_APM, M_APM);
+extern	void	m_apm_integer_divide(M_APM, M_APM, M_APM);
+extern	void	m_apm_integer_div_rem(M_APM, M_APM, M_APM, M_APM);
+extern	void	m_apm_reciprocal(M_APM, int, M_APM);
+extern	void	m_apm_factorial(M_APM, M_APM);
+extern	void	m_apm_floor(M_APM, M_APM);
+extern	void	m_apm_ceil(M_APM, M_APM);
+extern	void	m_apm_get_random(M_APM);
+extern	void	m_apm_set_random_seed(char *);
+
+extern	void	m_apm_sqrt(M_APM, int, M_APM);
+extern	void	m_apm_cbrt(M_APM, int, M_APM);
+extern	void	m_apm_log(M_APM, int, M_APM);
+extern	void	m_apm_log10(M_APM, int, M_APM);
+extern	void	m_apm_exp(M_APM, int, M_APM);
+extern	void	m_apm_pow(M_APM, int, M_APM, M_APM);
+extern  void	m_apm_integer_pow(M_APM, int, M_APM, int);
+extern  void	m_apm_integer_pow_nr(M_APM, M_APM, int);
+
+extern	void	m_apm_sin_cos(M_APM, M_APM, int, M_APM);
+extern	void	m_apm_sin(M_APM, int, M_APM);
+extern	void	m_apm_cos(M_APM, int, M_APM);
+extern	void	m_apm_tan(M_APM, int, M_APM);
+extern	void	m_apm_arcsin(M_APM, int, M_APM);
+extern	void	m_apm_arccos(M_APM, int, M_APM);
+extern	void	m_apm_arctan(M_APM, int, M_APM);
+extern	void	m_apm_arctan2(M_APM, int, M_APM, M_APM);
+
+extern  void    m_apm_sinh(M_APM, int, M_APM);
+extern  void    m_apm_cosh(M_APM, int, M_APM);
+extern  void    m_apm_tanh(M_APM, int, M_APM);
+extern  void    m_apm_arcsinh(M_APM, int, M_APM);
+extern  void    m_apm_arccosh(M_APM, int, M_APM);
+extern  void    m_apm_arctanh(M_APM, int, M_APM);
+
+extern  void    m_apm_cpp_precision(int);   /* only for C++ wrapper */
+
+/* more intuitive alternate names for the ARC functions ... */
+
+#define m_apm_asin m_apm_arcsin
+#define m_apm_acos m_apm_arccos
+#define m_apm_atan m_apm_arctan
+#define m_apm_atan2 m_apm_arctan2
+
+#define m_apm_asinh m_apm_arcsinh
+#define m_apm_acosh m_apm_arccosh
+#define m_apm_atanh m_apm_arctanh
+
+#ifdef APM_CONVERT_FROM_C
+}      /* End extern "C" bracket */
+#endif
+
+#ifdef __cplusplus   /*<- Hides the class below from C compilers */
+
+/*
+    This class lets you use M_APM's a bit more intuitively with
+    C++'s operator and function overloading, constructors, etc.
+
+    Added 3/24/2000 by Orion Sky Lawlor, [email protected]
+*/
+
+extern 
+#ifdef APM_CONVERT_FROM_C
+"C" 
+#endif
+int MM_cpp_min_precision;
+
+
+class MAPM {
+protected:
+
+/*
+The M_APM structure here is implemented as a reference-
+counted, copy-on-write data structure-- this makes copies
+very fast, but that's why it's so ugly.  A MAPM object is 
+basically just a wrapper around a (possibly shared) 
+M_APM_struct myVal.
+*/
+
+
+	M_APM myVal;  /* My M_APM structure */
+	void create(void) {myVal=makeNew();}
+	void destroy(void) {unref(myVal);myVal=NULL;}
+	void copyFrom(M_APM Nval) 
+	{
+		 M_APM oldVal=myVal;
+		 myVal=Nval;
+		 ref(myVal);
+		 unref(oldVal);
+	}
+	static M_APM makeNew(void) 
+	{
+		M_APM val=m_apm_init();
+		/* refcount initialized to 1 by 'm_apm_init' */
+		return val;
+	}
+	static void ref(M_APM val) 
+	{
+		val->m_apm_refcount++;
+	}
+	static void unref(M_APM val) 
+	{
+		val->m_apm_refcount--;
+		if (val->m_apm_refcount==0)
+			m_apm_free(val);
+	}
+	
+	/* This routine is called to get a private (mutable)
+	   copy of our current value. */
+	M_APM val(void) 
+	{
+		if (myVal->m_apm_refcount==1) 
+		/* Return my private myVal */
+			return myVal;
+
+		/* Otherwise, our copy of myVal is shared--
+		   we need to make a new private copy.
+                */
+		M_APM oldVal=myVal;
+		myVal=makeNew();
+		m_apm_copy(myVal,oldVal);
+		unref(oldVal);
+		return myVal;
+	}
+	
+	/*BAD: C M_APM routines doesn't use "const" where they should--
+	  hence we have to cast to a non-const type here (FIX THIS!).
+
+	  (in due time.... MCR)
+	*/
+	M_APM cval(void) const 
+	{
+		return (M_APM)myVal;
+	}
+	/* This is the default number of digits to use for 
+	   1-ary functions like sin, cos, tan, etc.
+	   It's the larger of my digits and cpp_min_precision.
+        */
+	int myDigits(void) const 
+	{
+		int maxd=m_apm_significant_digits(cval());
+		if (maxd<MM_cpp_min_precision) maxd=MM_cpp_min_precision;
+		return maxd;
+	}
+	/* This is the default number of digits to use for 
+	   2-ary functions like divide, atan2, etc.
+	   It's the larger of my digits, his digits, and cpp_min_precision.
+        */
+	int digits(const MAPM &otherVal) const 
+	{
+		int maxd=myDigits();
+		int his=m_apm_significant_digits(otherVal.cval());
+		if (maxd<his) maxd=his;
+		return maxd;
+	}
+public:
+	/* Constructors: */
+	MAPM(void) /* Default constructor (takes no value) */
+		{create();}
+	MAPM(const MAPM &m) /* Copy constructor */
+		{myVal=(M_APM)m.cval();ref(myVal);}
+	MAPM(M_APM m) /* M_APM constructor (refcount starts at one) */
+		{myVal=(M_APM)m;ref(myVal);}
+	MAPM(const char *s) /* Constructor from string */
+		{create();m_apm_set_string(val(),(char *)s);}
+	MAPM(double d) /* Constructor from double-precision float */
+		{create();m_apm_set_double(val(),d);}
+	MAPM(int l) /* Constructor from int */
+		{create();m_apm_set_long(val(),l);}
+	MAPM(long l) /* Constructor from long int */
+		{create();m_apm_set_long(val(),l);}
+	/* Destructor */
+	~MAPM() {destroy();}
+	
+	/* Extracting string descriptions: */
+	void toString(char *dest,int decimalPlaces) const
+		{m_apm_to_string(dest,decimalPlaces,cval());}
+	void toFixPtString(char *dest,int decimalPlaces) const
+		{m_apm_to_fixpt_string(dest,decimalPlaces,cval());}
+	void toFixPtStringEx(char *dest,int dp,char a,char b,int c) const
+		{m_apm_to_fixpt_stringex(dest,dp,cval(),a,b,c);}
+	char *toFixPtStringExp(int dp,char a,char b,int c) const
+		{return(m_apm_to_fixpt_stringexp(dp,cval(),a,b,c));}
+	void toIntegerString(char *dest) const
+		{m_apm_to_integer_string(dest,cval());}
+	
+	/* Basic operators: */
+	MAPM &operator=(const MAPM &m) /* Assigment operator */
+		{copyFrom((M_APM)m.cval());return *this;}
+	MAPM &operator=(const char *s) /* Assigment operator */
+		{m_apm_set_string(val(),(char *)s);return *this;}
+	MAPM &operator=(double d) /* Assigment operator */
+		{m_apm_set_double(val(),d);return *this;}
+	MAPM &operator=(int l) /* Assigment operator */
+		{m_apm_set_long(val(),l);return *this;}
+	MAPM &operator=(long l) /* Assigment operator */
+		{m_apm_set_long(val(),l);return *this;}
+	MAPM operator++() /* Prefix increment operator */
+		{return *this = *this+MM_One;}
+	MAPM operator--() /* Prefix decrement operator */
+		{return *this = *this-MM_One;}
+	const MAPM operator++(int)  /* Postfix increment operator */
+	{
+		MAPM old = *this;
+		++(*this);          /* Call prefix increment */
+		return old;
+	}
+	const MAPM operator--(int)  /* Postfix decrement operator */
+	{
+		MAPM old = *this;
+		--(*this);          /* Call prefix decrement */
+		return old;
+	}
+	
+	/* Comparison operators */
+	int operator==(const MAPM &m) const /* Equality operator */
+	 {return m_apm_compare(cval(),m.cval())==0;}
+	int operator!=(const MAPM &m) const /* Inequality operator */
+	 {return m_apm_compare(cval(),m.cval())!=0;}
+	int operator<(const MAPM &m) const
+	 {return m_apm_compare(cval(),m.cval())<0;}
+	int operator<=(const MAPM &m) const
+	 {return m_apm_compare(cval(),m.cval())<=0;}
+	int operator>(const MAPM &m) const
+	 {return m_apm_compare(cval(),m.cval())>0;}
+	int operator>=(const MAPM &m) const
+	 {return m_apm_compare(cval(),m.cval())>=0;}
+	
+	/* Basic arithmetic operators */
+	friend MAPM operator+(const MAPM &a,const MAPM &b)
+	 {MAPM ret;m_apm_add(ret.val(),a.cval(),b.cval());return ret;}
+	friend MAPM operator-(const MAPM &a,const MAPM &b)
+	 {MAPM ret;m_apm_subtract(ret.val(),a.cval(),b.cval());return ret;}
+	friend MAPM operator*(const MAPM &a,const MAPM &b)
+	 {MAPM ret;m_apm_multiply(ret.val(),a.cval(),b.cval());return ret;}
+	friend MAPM operator%(const MAPM &a,const MAPM &b)
+	 {MAPM quot,ret;m_apm_integer_div_rem(quot.val(),ret.val(),
+		a.cval(),b.cval());return ret;}
+
+	/* Default division keeps larger of cpp_min_precision, numerator 
+	   digits of precision, or denominator digits of precision. */
+	friend MAPM operator/(const MAPM &a,const MAPM &b) 
+		{return a.divide(b,a.digits(b));}
+	
+	MAPM divide(const MAPM &m,int toDigits) const
+        	{MAPM ret;m_apm_divide(ret.val(),toDigits,cval(),
+					        m.cval());return ret;}
+	MAPM divide(const MAPM &m) const {return divide(m,digits(m));}
+	
+	/* Assignment arithmetic operators */
+	MAPM &operator+=(const MAPM &m) {*this = *this+m;return *this;}
+	MAPM &operator-=(const MAPM &m) {*this = *this-m;return *this;}
+	MAPM &operator*=(const MAPM &m) {*this = *this*m;return *this;}
+	MAPM &operator/=(const MAPM &m) {*this = *this/m;return *this;}
+	MAPM &operator%=(const MAPM &m) {*this = *this%m;return *this;}
+	
+	/* Extracting/setting simple information: */
+	int sign(void) const
+		{return m_apm_sign(cval());}
+	int exponent(void) const 
+		{return m_apm_exponent(cval());}
+	int significant_digits(void) const 
+		{return m_apm_significant_digits(cval());}
+	int is_integer(void) const 
+		{return m_apm_is_integer(cval());}
+	int is_even(void) const 
+		{return m_apm_is_even(cval());}
+	int is_odd(void) const 
+		{return m_apm_is_odd(cval());}
+
+	/* Functions: */
+	MAPM abs(void) const
+		{MAPM ret;m_apm_absolute_value(ret.val(),cval());return ret;}
+	MAPM neg(void) const
+		{MAPM ret;m_apm_negate(ret.val(),cval());return ret;}
+	MAPM round(int toDigits) const
+		{MAPM ret;m_apm_round(ret.val(),toDigits,cval());return ret;}
+	MAPM operator-(void) const {return neg();}
+
+/* I got tired of typing the various declarations for a simple 
+   1-ary real-to-real function on MAPM's; hence this define:
+   The digits-free versions return my digits of precision or 
+   cpp_min_precision, whichever is bigger.
+*/
+
+#define MAPM_1aryFunc(func) \
+	MAPM func(int toDigits) const\
+		{MAPM ret;m_apm_##func(ret.val(),toDigits,cval());return ret;}\
+	MAPM func(void) const {return func(myDigits());}
+
+	MAPM_1aryFunc(sqrt)
+	MAPM_1aryFunc(cbrt)
+	MAPM_1aryFunc(log)
+	MAPM_1aryFunc(exp)
+	MAPM_1aryFunc(log10)
+	MAPM_1aryFunc(sin)
+	MAPM_1aryFunc(asin)
+	MAPM_1aryFunc(cos)
+	MAPM_1aryFunc(acos)
+	MAPM_1aryFunc(tan)
+	MAPM_1aryFunc(atan)
+	MAPM_1aryFunc(sinh)
+	MAPM_1aryFunc(asinh)
+	MAPM_1aryFunc(cosh)
+	MAPM_1aryFunc(acosh)
+	MAPM_1aryFunc(tanh)
+	MAPM_1aryFunc(atanh)
+#undef MAPM_1aryFunc
+	
+	void sincos(MAPM &sinR,MAPM &cosR,int toDigits)
+		{m_apm_sin_cos(sinR.val(),cosR.val(),toDigits,cval());}
+	void sincos(MAPM &sinR,MAPM &cosR)
+		{sincos(sinR,cosR,myDigits());}
+	MAPM pow(const MAPM &m,int toDigits) const
+		{MAPM ret;m_apm_pow(ret.val(),toDigits,cval(),
+					  m.cval());return ret;}
+	MAPM pow(const MAPM &m) const {return pow(m,digits(m));}
+	MAPM atan2(const MAPM &x,int toDigits) const
+		{MAPM ret;m_apm_arctan2(ret.val(),toDigits,cval(),
+					    x.cval());return ret;}
+	MAPM atan2(const MAPM &x) const
+		{return atan2(x,digits(x));}
+
+	MAPM gcd(const MAPM &m) const
+		{MAPM ret;m_apm_gcd(ret.val(),cval(),m.cval());return ret;}
+
+	MAPM lcm(const MAPM &m) const
+		{MAPM ret;m_apm_lcm(ret.val(),cval(),m.cval());return ret;}
+
+	static MAPM random(void) 
+		{MAPM ret;m_apm_get_random(ret.val());return ret;}
+
+	MAPM floor(void) const
+		{MAPM ret;m_apm_floor(ret.val(),cval());return ret;}
+	MAPM ceil(void) const
+		{MAPM ret;m_apm_ceil(ret.val(),cval());return ret;}
+
+	/* Functions defined only on integers: */
+	MAPM factorial(void) const
+		{MAPM ret;m_apm_factorial(ret.val(),cval());return ret;}
+	MAPM ipow_nr(int p) const
+		{MAPM ret;m_apm_integer_pow_nr(ret.val(),
+				cval(),p);return ret;}
+	MAPM ipow(int p,int toDigits) const
+		{MAPM ret;m_apm_integer_pow(ret.val(),
+				toDigits,cval(),p);return ret;}
+	MAPM ipow(int p) const
+		{return ipow(p,myDigits());}
+	MAPM integer_divide(const MAPM &denom) const
+		{MAPM ret;m_apm_integer_divide(ret.val(),cval(),
+		                       denom.cval());return ret;}
+	void integer_div_rem(const MAPM &denom,MAPM &quot,MAPM &rem) const
+		{m_apm_integer_div_rem(quot.val(),rem.val(),cval(),
+					             denom.cval());}
+	MAPM div(const MAPM &denom) const {return integer_divide(denom);}
+	MAPM rem(const MAPM &denom) const {MAPM ret,ignored;
+		integer_div_rem(denom,ignored,ret);return ret;}
+};
+
+/* math.h-style functions: */
+
+inline MAPM fabs(const MAPM &m) {return m.abs();}
+inline MAPM factorial(const MAPM &m) {return m.factorial();}
+inline MAPM floor(const MAPM &m) {return m.floor();}
+inline MAPM ceil(const MAPM &m) {return m.ceil();}
+inline MAPM get_random(void) {return MAPM::random();}
+
+/* I got tired of typing the various declarations for a simple 
+   1-ary real-to-real function on MAPM's; hence this define:
+*/
+#define MAPM_1aryFunc(func) \
+	inline MAPM func(const MAPM &m) {return m.func();} \
+	inline MAPM func(const MAPM &m,int toDigits) {return m.func(toDigits);}
+
+/* Define a big block of simple functions: */
+	MAPM_1aryFunc(sqrt)
+	MAPM_1aryFunc(cbrt)
+	MAPM_1aryFunc(log)
+	MAPM_1aryFunc(exp)
+	MAPM_1aryFunc(log10)
+	MAPM_1aryFunc(sin)
+	MAPM_1aryFunc(asin)
+	MAPM_1aryFunc(cos)
+	MAPM_1aryFunc(acos)
+	MAPM_1aryFunc(tan)
+	MAPM_1aryFunc(atan)
+	MAPM_1aryFunc(sinh)
+	MAPM_1aryFunc(asinh)
+	MAPM_1aryFunc(cosh)
+	MAPM_1aryFunc(acosh)
+	MAPM_1aryFunc(tanh)
+	MAPM_1aryFunc(atanh)
+#undef MAPM_1aryFunc
+
+/* Computes x to the power y */
+inline MAPM pow(const MAPM &x,const MAPM &y,int toDigits)
+		{return x.pow(y,toDigits);}
+inline MAPM pow(const MAPM &x,const MAPM &y)
+		{return x.pow(y);}
+inline MAPM atan2(const MAPM &y,const MAPM &x,int toDigits)
+		{return y.atan2(x,toDigits);}
+inline MAPM atan2(const MAPM &y,const MAPM &x)
+		{return y.atan2(x);}
+inline MAPM gcd(const MAPM &u,const MAPM &v)
+		{return u.gcd(v);}
+inline MAPM lcm(const MAPM &u,const MAPM &v)
+		{return u.lcm(v);}
+#endif
+#endif
+

+ 400 - 0
mapm/src/m_apm_lc.h

@@ -0,0 +1,400 @@
+
+/* 
+ *  M_APM  -  m_apm_lc.h
+ *
+ *  Copyright (C) 1999 - 2007   Michael C. Ring
+ *
+ *  Permission to use, copy, and distribute this software and its
+ *  documentation for any purpose with or without fee is hereby granted,
+ *  provided that the above copyright notice appear in all copies and
+ *  that both that copyright notice and this permission notice appear
+ *  in supporting documentation.
+ *
+ *  Permission to modify the software is granted. Permission to distribute
+ *  the modified code is granted. Modifications are to be distributed by
+ *  using the file 'license.txt' as a template to modify the file header.
+ *  'license.txt' is available in the official MAPM distribution.
+ *
+ *  This software is provided "as is" without express or implied warranty.
+ */
+
+/*
+ *      This is the local header file needed to build the library
+ *
+ *      $Log: m_apm_lc.h,v $
+ *      Revision 1.45  2007/12/04 01:26:02  mike
+ *      add support for Digital Mars compiler
+ *
+ *      Revision 1.44  2007/12/03 01:23:54  mike
+ *      Update license
+ *
+ *      Revision 1.43  2004/05/28 19:30:16  mike
+ *      add new prototype
+ *
+ *      Revision 1.42  2003/10/25 22:36:01  mike
+ *      add support for National Instruments CVI
+ *
+ *      Revision 1.41  2003/07/21 19:42:50  mike
+ *      rename M_APM_EXIT to M_APM_FATAL
+ *      change M_APM_RETURN to 0, set M_APM_FATAL to 1
+ *
+ *      Revision 1.40  2003/07/21 19:14:29  mike
+ *      add new prototype
+ *
+ *      Revision 1.39  2003/05/04 20:09:10  mike
+ *      add support for Open Watcom 1.0
+ *
+ *      Revision 1.38  2003/05/01 21:54:04  mike
+ *      add math.h, add new prototype
+ *
+ *      Revision 1.37  2003/04/01 23:19:01  mike
+ *      add new log constants and prototypes
+ *
+ *      Revision 1.36  2003/03/30 23:02:49  mike
+ *      add new log constants and new prototypes
+ *
+ *      Revision 1.35  2002/11/03 23:21:28  mike
+ *      add new prototype, M_set_to_zero
+ *
+ *      Revision 1.34  2002/05/18 15:38:52  mike
+ *      add MINGW compiler #define
+ *
+ *      Revision 1.33  2002/02/14 19:42:59  mike
+ *      add conditional compiler stuff for Metrowerks Codewarrior compiler
+ *
+ *      Revision 1.32  2001/08/25 16:45:40  mike
+ *      add new prototype
+ *
+ *      Revision 1.31  2001/07/24 18:13:31  mike
+ *      add new prototype
+ *
+ *      Revision 1.30  2001/07/16 18:38:04  mike
+ *      add 'free_all' prototypes
+ *
+ *      Revision 1.29  2001/02/07 19:13:27  mike
+ *      eliminate MM_skip_limit_PI_check
+ *
+ *      Revision 1.28  2001/01/23 21:10:24  mike
+ *      add new prototype for M_long_2_ascii
+ *
+ *      Revision 1.27  2000/12/10 14:30:52  mike
+ *      added ifdef for LCC-WIN32 compiler
+ *
+ *      Revision 1.26  2000/12/02 19:41:45  mike
+ *      add arc functions near 0
+ *
+ *      Revision 1.25  2000/11/14 22:48:29  mike
+ *      add BORLANDC to pre-processor stuff
+ *
+ *      Revision 1.24  2000/10/22 21:17:56  mike
+ *      add _MSC_VER check for VC++ compilers
+ *
+ *      Revision 1.23  2000/10/18 23:09:27  mike
+ *      add new prototype
+ *
+ *      Revision 1.22  2000/09/23 18:55:30  mike
+ *      add new prototype fpr M_apm_sdivide
+ *
+ *      Revision 1.21  2000/08/01 22:21:55  mike
+ *      add prototype
+ *
+ *      Revision 1.20  2000/07/19 17:21:26  mike
+ *      add ifdef for older Borland compilers
+ *
+ *      Revision 1.19  2000/07/11 20:09:30  mike
+ *      add new prototype
+ *
+ *      Revision 1.18  2000/05/19 17:09:57  mike
+ *      add local copies for PI variables
+ *
+ *      Revision 1.17  2000/05/04 23:21:56  mike
+ *      change/add new global internal MAPM values
+ *
+ *      Revision 1.16  2000/04/11 18:44:43  mike
+ *      no longer need the constant 'Fifteen'
+ *
+ *      Revision 1.15  2000/04/03 17:27:08  mike
+ *      added cbrt prototype
+ *
+ *      Revision 1.14  2000/02/03 22:41:34  mike
+ *      add MAPM_* memory function defines
+ *
+ *      Revision 1.13  1999/07/09 22:46:10  mike
+ *      add skip limit integer
+ *
+ *      Revision 1.12  1999/07/08 23:35:20  mike
+ *      change constant
+ *
+ *      Revision 1.11  1999/07/08 22:55:38  mike
+ *      add new constant
+ *
+ *      Revision 1.10  1999/06/23 01:08:11  mike
+ *      added constant '15'
+ *
+ *      Revision 1.9  1999/06/20 23:38:11  mike
+ *      updated for new prototypes
+ *
+ *      Revision 1.8  1999/06/20 23:30:03  mike
+ *      added new constants
+ *
+ *      Revision 1.7  1999/06/20 19:23:12  mike
+ *      delete constants no longer needed
+ *
+ *      Revision 1.6  1999/06/20 18:50:21  mike
+ *      added more constants
+ *
+ *      Revision 1.5  1999/06/19 20:37:30  mike
+ *      add stack prototypes
+ *
+ *      Revision 1.4  1999/05/31 23:01:38  mike
+ *      delete some unneeded constants
+ *
+ *      Revision 1.3  1999/05/15 02:23:28  mike
+ *      fix define for M_COS
+ *
+ *      Revision 1.2  1999/05/15 02:16:56  mike
+ *      add check for number of decimal places
+ *
+ *      Revision 1.1  1999/05/12 20:51:22  mike
+ *      Initial revision
+ *
+ *      $Id: m_apm_lc.h,v 1.45 2007/12/04 01:26:02 mike Exp $
+ */
+
+#ifndef M__APM_LOCAL_INC
+#define M__APM_LOCAL_INC
+
+#include <stdio.h>
+#include <stdlib.h>
+#include <string.h>
+#include <math.h>
+#include "m_apm.h"
+
+/* 
+ *   this supports older (and maybe newer?) Borland compilers.
+ *   these Borland compilers define __MSDOS__
+ */
+
+#ifndef MSDOS
+#ifdef __MSDOS__
+#define MSDOS
+#endif
+#endif
+
+/* 
+ *   this supports some newer Borland compilers (i.e., v5.5).
+ */
+
+#ifndef MSDOS
+#ifdef __BORLANDC__
+#define MSDOS
+#endif
+#endif
+
+/* 
+ *   this supports the LCC-WIN32 compiler
+ */
+
+#ifndef MSDOS
+#ifdef __LCC__
+#define MSDOS
+#endif
+#endif
+
+/* 
+ *   this supports Micro$oft Visual C++ and also possibly older
+ *   straight C compilers as well.
+ */
+
+#ifndef MSDOS
+#ifdef _MSC_VER
+#define MSDOS
+#endif
+#endif
+
+/* 
+ *   this supports the Metrowerks CodeWarrior 7.0 compiler (I think...)
+ */
+
+#ifndef MSDOS
+#ifdef __MWERKS__
+#define MSDOS
+#endif
+#endif
+
+/* 
+ *   this supports the MINGW 32 compiler
+ */
+
+#ifndef MSDOS
+#ifdef __MINGW_H
+#define MSDOS
+#endif
+#endif
+
+/* 
+ *   this supports the Open Watcom 1.0 compiler
+ */
+
+#ifndef MSDOS
+#ifdef __WATCOMC__
+#define MSDOS
+#endif
+#endif
+
+/* 
+ *   this supports the Digital Mars compiler
+ */
+
+#ifndef MSDOS
+#ifdef __DMC__
+#define MSDOS
+#endif
+#endif
+
+/* 
+ *   this supports National Instruments LabWindows CVI
+ */
+
+#ifndef _HAVE_NI_LABWIN_CVI_
+#ifdef _CVI_
+#define _HAVE_NI_LABWIN_CVI_
+#endif
+#endif
+
+/*
+ *  If for some reason (RAM limitations, slow floating point, whatever) 
+ *  you do NOT want to use the FFT multiply algorithm, un-comment the 
+ *  #define below, delete mapm_fft.c and remove mapm_fft from the build.
+ */
+
+/*  #define NO_FFT_MULTIPLY  */
+
+/*
+ *      use your own memory management functions if desired.
+ *      re-define MAPM_* below to point to your functions.
+ *      an example is shown below.
+ */
+
+/*
+extern   void   *memory_allocate(unsigned int);
+extern   void   *memory_reallocate(void *, unsigned int);
+extern   void   memory_free(void *);
+
+#define  MAPM_MALLOC memory_allocate
+#define  MAPM_REALLOC memory_reallocate
+#define  MAPM_FREE memory_free
+*/
+
+/* default: use the standard C library memory functions ... */
+
+#define  MAPM_MALLOC malloc
+#define  MAPM_REALLOC realloc
+#define  MAPM_FREE free
+
+#ifndef TRUE
+#define TRUE 1
+#endif
+
+#ifndef FALSE
+#define FALSE 0
+#endif
+
+#define	M_APM_IDENT 0x6BCC9AE5
+#define	M_APM_RETURN 0
+#define	M_APM_FATAL 1
+
+/* number of digits in the global constants, PI, E, etc */
+
+#define	VALID_DECIMAL_PLACES 128
+
+extern  int     MM_lc_PI_digits;
+extern  int     MM_lc_log_digits;
+
+/*
+ *   constants not in m_apm.h
+ */
+
+extern	M_APM	MM_0_5;
+extern	M_APM	MM_0_85;
+extern	M_APM	MM_5x_125R;
+extern	M_APM	MM_5x_64R;
+extern	M_APM	MM_5x_256R;
+extern	M_APM	MM_5x_Eight;
+extern	M_APM	MM_5x_Sixteen;
+extern	M_APM	MM_5x_Twenty;
+extern	M_APM	MM_lc_PI;
+extern	M_APM	MM_lc_HALF_PI;
+extern	M_APM	MM_lc_2_PI;
+extern	M_APM	MM_lc_log2;
+extern	M_APM	MM_lc_log10;
+extern	M_APM	MM_lc_log10R;
+
+/*
+ *   prototypes for internal functions
+ */
+
+#ifndef NO_FFT_MULTIPLY
+extern	void	M_free_all_fft(void);
+#endif
+
+extern	void	M_init_trig_globals(void);
+extern	void	M_free_all_add(void);
+extern	void	M_free_all_div(void);
+extern	void	M_free_all_exp(void);
+extern	void	M_free_all_pow(void);
+extern	void	M_free_all_rnd(void);
+extern	void	M_free_all_set(void);
+extern	void	M_free_all_cnst(void);
+extern	void	M_free_all_fmul(void);
+extern	void	M_free_all_stck(void);
+extern	void	M_free_all_util(void);
+
+extern	int 	M_exp_compute_nn(int *, M_APM, M_APM);
+extern	void	M_raw_exp(M_APM, int, M_APM);
+extern	void	M_raw_sin(M_APM, int, M_APM);
+extern	void	M_raw_cos(M_APM, int, M_APM);
+extern	void	M_5x_sin(M_APM, int, M_APM);
+extern	void	M_4x_cos(M_APM, int, M_APM);
+extern	void	M_5x_do_it(M_APM, int, M_APM);
+extern	void	M_4x_do_it(M_APM, int, M_APM);
+
+extern	M_APM	M_get_stack_var(void);
+extern	void	M_restore_stack(int);
+extern	int 	M_get_sizeof_int(void);
+
+extern	void	M_apm_sdivide(M_APM, int, M_APM, M_APM);
+extern	void	M_cos_to_sin(M_APM, int, M_APM);
+extern	void	M_limit_angle_to_pi(M_APM, int, M_APM);
+extern	void	M_log_near_1(M_APM, int, M_APM);
+extern	void	M_get_sqrt_guess(M_APM, M_APM);
+extern	void	M_get_cbrt_guess(M_APM, M_APM);
+extern	void	M_get_log_guess(M_APM, M_APM);
+extern	void	M_get_asin_guess(M_APM, M_APM);
+extern	void	M_get_acos_guess(M_APM, M_APM);
+extern	void	M_arcsin_near_0(M_APM, int, M_APM);
+extern	void	M_arccos_near_0(M_APM, int, M_APM);
+extern	void	M_arctan_near_0(M_APM, int, M_APM);
+extern	void	M_arctan_large_input(M_APM, int, M_APM);
+extern	void	M_log_basic_iteration(M_APM, int, M_APM);
+extern  void    M_log_solve_cubic(M_APM, int, M_APM);
+extern	void	M_check_log_places(int);
+extern	void	M_log_AGM_R_func(M_APM, int, M_APM, M_APM);
+extern	void	M_init_util_data(void);
+extern	void	M_get_div_rem_addr(UCHAR **, UCHAR **);
+extern	void	M_get_div_rem(int,UCHAR *, UCHAR *);
+extern	void	M_get_div_rem_10(int, UCHAR *, UCHAR *);
+extern	void	M_apm_normalize(M_APM);
+extern	void	M_apm_scale(M_APM, int);
+extern	void	M_apm_pad(M_APM, int);
+extern  void    M_long_2_ascii(char *, long);
+extern	void	M_check_PI_places(int);
+extern  void    M_calculate_PI_AGM(M_APM, int);
+extern  void    M_set_to_zero(M_APM);
+extern	int	M_strposition(char *, char *);
+extern	char	*M_lowercase(char *);
+extern  void    M_apm_log_error_msg(int, char *);
+extern  void	M_apm_round_fixpt(M_APM, int, M_APM);
+
+#endif
+

+ 184 - 0
mapm/src/mapm5sin.c

@@ -0,0 +1,184 @@
+
+/* 
+ *  M_APM  -  mapm5sin.c
+ *
+ *  Copyright (C) 1999 - 2007   Michael C. Ring
+ *
+ *  Permission to use, copy, and distribute this software and its
+ *  documentation for any purpose with or without fee is hereby granted,
+ *  provided that the above copyright notice appear in all copies and
+ *  that both that copyright notice and this permission notice appear
+ *  in supporting documentation.
+ *
+ *  Permission to modify the software is granted. Permission to distribute
+ *  the modified code is granted. Modifications are to be distributed by
+ *  using the file 'license.txt' as a template to modify the file header.
+ *  'license.txt' is available in the official MAPM distribution.
+ *
+ *  This software is provided "as is" without express or implied warranty.
+ */
+
+/*
+ *      $Id: mapm5sin.c,v 1.10 2007/12/03 01:26:16 mike Exp $
+ *
+ *      This file contains the functions that implement the sin (5x)
+ *	and cos (4x) multiple angle relations
+ *
+ *      $Log: mapm5sin.c,v $
+ *      Revision 1.10  2007/12/03 01:26:16  mike
+ *      Update license
+ *
+ *      Revision 1.9  2002/11/03 21:50:36  mike
+ *      Updated function parameters to use the modern style
+ *
+ *      Revision 1.8  2001/03/25 20:57:03  mike
+ *      move cos_to_sin func in here
+ *
+ *      Revision 1.7  2000/05/04 23:50:21  mike
+ *      use multiple angle identity 4 times of larger COS angles
+ *
+ *      Revision 1.6  1999/06/30 00:08:53  mike
+ *      pass more decimal places to raw functions
+ *
+ *      Revision 1.5  1999/06/20 23:41:32  mike
+ *      changed COS to use 4x multiple angle identity instead of 5x
+ *
+ *      Revision 1.4  1999/06/20 19:42:26  mike
+ *      tweak number of dec places passed to sub-functions
+ *
+ *      Revision 1.3  1999/06/20 19:03:56  mike
+ *      changed local static variables to MAPM stack variables
+ *
+ *      Revision 1.2  1999/05/12 21:30:09  mike
+ *      replace local 5.0 with global
+ *
+ *      Revision 1.1  1999/05/10 20:56:31  mike
+ *      Initial revision
+ */
+
+#include "m_apm_lc.h"
+
+/****************************************************************************/
+void	M_5x_sin(M_APM r, int places, M_APM x)
+{
+M_APM   tmp8, tmp9;
+
+tmp8 = M_get_stack_var();
+tmp9 = M_get_stack_var();
+
+m_apm_multiply(tmp9, x, MM_5x_125R);        /* 1 / (5*5*5) */
+M_raw_sin(tmp8, (places + 6), tmp9);
+M_5x_do_it(tmp9, (places + 4), tmp8);
+M_5x_do_it(tmp8, (places + 4), tmp9);
+M_5x_do_it(r, places, tmp8);
+
+M_restore_stack(2);
+}
+/****************************************************************************/
+void	M_4x_cos(M_APM r, int places, M_APM x)
+{
+M_APM   tmp8, tmp9;
+
+tmp8 = M_get_stack_var();
+tmp9 = M_get_stack_var();
+
+/* 
+ *  if  |x| >= 1.0   use multiple angle identity 4 times
+ *  if  |x|  < 1.0   use multiple angle identity 3 times
+ */
+
+if (x->m_apm_exponent > 0)
+  {
+   m_apm_multiply(tmp9, x, MM_5x_256R);        /* 1 / (4*4*4*4) */
+   M_raw_cos(tmp8, (places + 8), tmp9);
+   M_4x_do_it(tmp9, (places + 8), tmp8);
+   M_4x_do_it(tmp8, (places + 6), tmp9);
+   M_4x_do_it(tmp9, (places + 4), tmp8);
+   M_4x_do_it(r, places, tmp9);
+  }
+else
+  {
+   m_apm_multiply(tmp9, x, MM_5x_64R);         /* 1 / (4*4*4) */
+   M_raw_cos(tmp8, (places + 6), tmp9);
+   M_4x_do_it(tmp9, (places + 4), tmp8);
+   M_4x_do_it(tmp8, (places + 4), tmp9);
+   M_4x_do_it(r, places, tmp8);
+  }
+
+M_restore_stack(2);
+}
+/****************************************************************************/
+/*
+ *     calculate the multiple angle identity for sin (5x)
+ *
+ *     sin (5x) == 16 * sin^5 (x)  -  20 * sin^3 (x)  +  5 * sin(x)  
+ */
+void	M_5x_do_it(M_APM rr, int places, M_APM xx)
+{
+M_APM   tmp0, tmp1, t2, t3, t5;
+
+tmp0 = M_get_stack_var();
+tmp1 = M_get_stack_var();
+t2   = M_get_stack_var();
+t3   = M_get_stack_var();
+t5   = M_get_stack_var();
+
+m_apm_multiply(tmp1, xx, xx);
+m_apm_round(t2, (places + 4), tmp1);     /* x ^ 2 */
+
+m_apm_multiply(tmp1, t2, xx);
+m_apm_round(t3, (places + 4), tmp1);     /* x ^ 3 */
+
+m_apm_multiply(t5, t2, t3);              /* x ^ 5 */
+
+m_apm_multiply(tmp0, xx, MM_Five);
+m_apm_multiply(tmp1, t5, MM_5x_Sixteen);
+m_apm_add(t2, tmp0, tmp1);
+m_apm_multiply(tmp1, t3, MM_5x_Twenty);
+m_apm_subtract(tmp0, t2, tmp1);
+
+m_apm_round(rr, places, tmp0);
+M_restore_stack(5);
+}
+/****************************************************************************/
+/*
+ *     calculate the multiple angle identity for cos (4x)
+ * 
+ *     cos (4x) == 8 * [ cos^4 (x)  -  cos^2 (x) ]  +  1
+ */
+void	M_4x_do_it(M_APM rr, int places, M_APM xx)
+{
+M_APM   tmp0, tmp1, t2, t4;
+
+tmp0 = M_get_stack_var();
+tmp1 = M_get_stack_var();
+t2   = M_get_stack_var();
+t4   = M_get_stack_var();
+
+m_apm_multiply(tmp1, xx, xx);
+m_apm_round(t2, (places + 4), tmp1);     /* x ^ 2 */
+m_apm_multiply(t4, t2, t2);              /* x ^ 4 */
+
+m_apm_subtract(tmp0, t4, t2);
+m_apm_multiply(tmp1, tmp0, MM_5x_Eight);
+m_apm_add(tmp0, MM_One, tmp1);
+m_apm_round(rr, places, tmp0);
+M_restore_stack(4);
+}
+/****************************************************************************/
+/*
+ *   compute  r = sqrt(1 - a ^ 2).
+ */
+void	M_cos_to_sin(M_APM r, int places, M_APM a)
+{
+M_APM	tmp1, tmp2;
+
+tmp1 = M_get_stack_var();
+tmp2 = M_get_stack_var();
+
+m_apm_multiply(tmp1, a, a);
+m_apm_subtract(tmp2, MM_One, tmp1);
+m_apm_sqrt(r, places, tmp2);
+M_restore_stack(2);
+}
+/****************************************************************************/

+ 326 - 0
mapm/src/mapm_add.c

@@ -0,0 +1,326 @@
+
+/* 
+ *  M_APM  -  mapm_add.c
+ *
+ *  Copyright (C) 1999 - 2007   Michael C. Ring
+ *
+ *  Permission to use, copy, and distribute this software and its
+ *  documentation for any purpose with or without fee is hereby granted,
+ *  provided that the above copyright notice appear in all copies and
+ *  that both that copyright notice and this permission notice appear
+ *  in supporting documentation.
+ *
+ *  Permission to modify the software is granted. Permission to distribute
+ *  the modified code is granted. Modifications are to be distributed by
+ *  using the file 'license.txt' as a template to modify the file header.
+ *  'license.txt' is available in the official MAPM distribution.
+ *
+ *  This software is provided "as is" without express or implied warranty.
+ */
+
+/*
+ *      $Id: mapm_add.c,v 1.5 2007/12/03 01:33:39 mike Exp $
+ *
+ *      This file contains basic addition/subtraction functions
+ *
+ *      $Log: mapm_add.c,v $
+ *      Revision 1.5  2007/12/03 01:33:39  mike
+ *      Update license
+ *
+ *      Revision 1.4  2003/12/04 01:15:42  mike
+ *      redo math with 'borrow'
+ *
+ *      Revision 1.3  2002/11/03 22:03:31  mike
+ *      Updated function parameters to use the modern style
+ *
+ *      Revision 1.2  2001/07/16 18:59:25  mike
+ *      add function M_free_all_add
+ *
+ *      Revision 1.1  1999/05/10 20:56:31  mike
+ *      Initial revision
+ */
+
+#include "m_apm_lc.h"
+
+static	M_APM	M_work1 = NULL;
+static	M_APM	M_work2 = NULL;
+static	int	M_add_firsttime = TRUE;
+
+/****************************************************************************/
+void	M_free_all_add()
+{
+if (M_add_firsttime == FALSE)
+  {
+   m_apm_free(M_work1);
+   m_apm_free(M_work2);
+   M_add_firsttime = TRUE;
+  }
+}
+/****************************************************************************/
+void	m_apm_add(M_APM r, M_APM a, M_APM b)
+{
+int	j, carry, sign, aexp, bexp, adigits, bdigits;
+
+if (M_add_firsttime)
+  {
+   M_add_firsttime = FALSE;
+   M_work1 = m_apm_init();
+   M_work2 = m_apm_init();
+  }
+
+if (a->m_apm_sign == 0)
+  {
+   m_apm_copy(r,b);
+   return;
+  }
+
+if (b->m_apm_sign == 0)
+  {
+   m_apm_copy(r,a);
+   return;
+  }
+  
+if (a->m_apm_sign == 1 && b->m_apm_sign == -1)
+  {
+   b->m_apm_sign = 1;
+   m_apm_subtract(r,a,b);
+   b->m_apm_sign = -1;
+   return;
+  }
+
+if (a->m_apm_sign == -1 && b->m_apm_sign == 1)
+  {
+   a->m_apm_sign = 1;
+   m_apm_subtract(r,b,a);
+   a->m_apm_sign = -1;
+   return;
+  }
+
+sign = a->m_apm_sign;         /* signs are the same, result will be same */
+
+aexp = a->m_apm_exponent;
+bexp = b->m_apm_exponent;
+
+m_apm_copy(M_work1, a);
+m_apm_copy(M_work2, b);
+
+/*
+ *  scale by at least 1 factor of 10 in case the MSB carrys
+ */
+
+if (aexp == bexp)
+  {
+   M_apm_scale(M_work1, 2);   /* shift 2 digits == 1 byte for efficiency */
+   M_apm_scale(M_work2, 2);
+  }
+else
+  {
+   if (aexp > bexp)
+     {
+      M_apm_scale(M_work1, 2);
+      M_apm_scale(M_work2, (aexp + 2 - bexp));
+     }
+   else            /*  aexp < bexp  */
+     {
+      M_apm_scale(M_work2, 2);
+      M_apm_scale(M_work1, (bexp + 2 - aexp));
+     }
+  }
+
+adigits = M_work1->m_apm_datalength;
+bdigits = M_work2->m_apm_datalength;
+
+if (adigits >= bdigits)
+  {
+   m_apm_copy(r, M_work1);
+   j = (bdigits + 1) >> 1;
+   carry = 0;
+
+   while (TRUE)
+     {
+      j--;
+      r->m_apm_data[j] += carry + M_work2->m_apm_data[j];
+
+      if (r->m_apm_data[j] >= 100)
+        {
+         r->m_apm_data[j] -= 100;
+	 carry = 1;
+	}
+      else
+         carry = 0;
+
+      if (j == 0) 
+        break;
+     }
+  }
+else
+  {
+   m_apm_copy(r, M_work2);
+   j = (adigits + 1) >> 1;
+   carry = 0;
+
+   while (TRUE)
+     {
+      j--;
+      r->m_apm_data[j] += carry + M_work1->m_apm_data[j];
+
+      if (r->m_apm_data[j] >= 100)
+        {
+         r->m_apm_data[j] -= 100;
+	 carry = 1;
+	}
+      else
+         carry = 0;
+
+      if (j == 0) 
+        break;
+     }
+  }
+
+r->m_apm_sign = sign;
+
+M_apm_normalize(r);
+}
+/****************************************************************************/
+void	m_apm_subtract(M_APM r, M_APM a, M_APM b)
+{
+int	itmp, j, flag, icompare, sign, aexp, bexp, 
+	borrow, adigits, bdigits;
+
+if (M_add_firsttime)
+  {
+   M_add_firsttime = FALSE;
+   M_work1 = m_apm_init();
+   M_work2 = m_apm_init();
+  }
+
+if (b->m_apm_sign == 0)
+  {
+   m_apm_copy(r,a);
+   return;
+  }
+  
+if (a->m_apm_sign == 0)
+  {
+   m_apm_copy(r,b);
+   r->m_apm_sign = -(r->m_apm_sign);
+   return;
+  }
+
+if (a->m_apm_sign == 1 && b->m_apm_sign == -1)
+  {
+   b->m_apm_sign = 1;
+   m_apm_add(r,a,b);
+   b->m_apm_sign = -1;
+   return;
+  }
+
+if (a->m_apm_sign == -1 && b->m_apm_sign == 1)
+  {
+   b->m_apm_sign = -1;
+   m_apm_add(r,a,b);
+   b->m_apm_sign = 1;
+   return;
+  }
+
+/* now, the signs are the same  */
+/* make a positive working copy */
+
+m_apm_absolute_value(M_work1, a);
+m_apm_absolute_value(M_work2, b);
+
+/* are they the same??  if so, the result is zero */
+
+if ((icompare = m_apm_compare(M_work1, M_work2)) == 0)
+  {
+   M_set_to_zero(r);
+   return;
+  }
+
+if (icompare == 1)             /*  |a| > |b|  (do A-B)  */
+  {
+   flag = TRUE;
+   sign = a->m_apm_sign;     
+  }
+else                           /*  |b| > |a|  (do B-A)  */
+  {
+   flag = FALSE;
+   sign = -(a->m_apm_sign);     
+  }
+
+aexp = M_work1->m_apm_exponent;
+bexp = M_work2->m_apm_exponent;
+
+if (aexp > bexp)
+  M_apm_scale(M_work2, (aexp - bexp));
+
+if (aexp < bexp)
+  M_apm_scale(M_work1, (bexp - aexp));
+
+adigits = M_work1->m_apm_datalength;
+bdigits = M_work2->m_apm_datalength;
+
+if (adigits > bdigits)
+  M_apm_pad(M_work2, adigits);
+
+if (adigits < bdigits)
+  M_apm_pad(M_work1, bdigits);
+
+if (flag)		/* perform A-B,  M_work1 - M_work2 */
+  {
+   m_apm_copy(r, M_work1);
+   j = (r->m_apm_datalength + 1) >> 1;
+   borrow = 0;
+
+   while (TRUE)
+     {
+      j--;
+      itmp = (int)r->m_apm_data[j] - ((int)M_work2->m_apm_data[j] + borrow);
+
+      if (itmp >= 0)
+        {
+         r->m_apm_data[j] = (UCHAR)itmp;
+	 borrow = 0;
+        }
+      else
+        {
+         r->m_apm_data[j] = (UCHAR)(100 + itmp);
+	 borrow = 1;
+	}
+
+      if (j == 0) 
+        break;
+     }
+  }
+else   		/* perform B-A,  M_work2 - M_work1 */
+  {
+   m_apm_copy(r, M_work2);
+   j = (r->m_apm_datalength + 1) >> 1;
+   borrow = 0;
+
+   while (TRUE)
+     {
+      j--;
+      itmp = (int)r->m_apm_data[j] - ((int)M_work1->m_apm_data[j] + borrow);
+
+      if (itmp >= 0)
+        {
+         r->m_apm_data[j] = (UCHAR)itmp;
+	 borrow = 0;
+        }
+      else
+        {
+         r->m_apm_data[j] = (UCHAR)(100 + itmp);
+	 borrow = 1;
+	}
+
+      if (j == 0) 
+        break;
+     }
+  }
+   
+r->m_apm_sign = sign;
+
+M_apm_normalize(r);
+}
+/****************************************************************************/

+ 173 - 0
mapm/src/mapm_cpi.c

@@ -0,0 +1,173 @@
+
+/* 
+ *  M_APM  -  mapm_cpi.c
+ *
+ *  Copyright (C) 1999 - 2007   Michael C. Ring
+ *
+ *  Permission to use, copy, and distribute this software and its
+ *  documentation for any purpose with or without fee is hereby granted,
+ *  provided that the above copyright notice appear in all copies and
+ *  that both that copyright notice and this permission notice appear
+ *  in supporting documentation.
+ *
+ *  Permission to modify the software is granted. Permission to distribute
+ *  the modified code is granted. Modifications are to be distributed by
+ *  using the file 'license.txt' as a template to modify the file header.
+ *  'license.txt' is available in the official MAPM distribution.
+ *
+ *  This software is provided "as is" without express or implied warranty.
+ */
+
+/*
+ *      $Id: mapm_cpi.c,v 1.4 2007/12/03 01:34:29 mike Exp $
+ *
+ *      This file contains the PI related functions.
+ *
+ *      $Log: mapm_cpi.c,v $
+ *      Revision 1.4  2007/12/03 01:34:29  mike
+ *      Update license
+ *
+ *      Revision 1.3  2002/11/05 23:10:14  mike
+ *      streamline the PI AGM algorithm
+ *
+ *      Revision 1.2  2002/11/03 21:56:21  mike
+ *      Updated function parameters to use the modern style
+ *
+ *      Revision 1.1  2001/03/25 21:01:53  mike
+ *      Initial revision
+ */
+
+#include "m_apm_lc.h"
+
+/****************************************************************************/
+/*
+ *	check if our local copy of PI is precise enough
+ *	for our purpose. if not, calculate PI so it's
+ *	as precise as desired, accurate to 'places' decimal
+ *	places.
+ */
+void	M_check_PI_places(int places)
+{
+int     dplaces;
+
+dplaces = places + 2;
+
+if (dplaces > MM_lc_PI_digits)
+  {
+   MM_lc_PI_digits = dplaces + 2;
+
+   /* compute PI using the AGM  (see right below) */
+
+   M_calculate_PI_AGM(MM_lc_PI, (dplaces + 5));
+
+   m_apm_multiply(MM_lc_HALF_PI, MM_0_5, MM_lc_PI);
+   m_apm_multiply(MM_lc_2_PI, MM_Two, MM_lc_PI);
+  }
+}
+/****************************************************************************/
+/*
+ *      Calculate PI using the AGM (Arithmetic-Geometric Mean)
+ *
+ *      Init :  A0  = 1
+ *              B0  = 1 / sqrt(2)
+ *              Sum = 1
+ *
+ *      Iterate: n = 1...
+ *
+ *
+ *      A   =  0.5 * [ A    +  B   ]
+ *       n              n-1     n-1
+ *
+ *
+ *      B   =  sqrt [ A    *  B   ]
+ *       n             n-1     n-1
+ *
+ *
+ *
+ *      C   =  0.5 * [ A    -  B   ]
+ *       n              n-1     n-1
+ *
+ *
+ *                      2      n+1
+ *     Sum  =  Sum  -  C   *  2
+ *                      n
+ *
+ *
+ *      At the end when C  is 'small enough' :
+ *                       n
+ *
+ *                    2 
+ *      PI  =  4  *  A    /  Sum
+ *                    n+1
+ *
+ *          -OR-
+ *
+ *                       2
+ *      PI  = ( A  +  B )   /  Sum
+ *               n     n
+ *
+ */
+void	M_calculate_PI_AGM(M_APM outv, int places)
+{
+M_APM   tmp1, tmp2, a0, b0, c0, a1, b1, sum, pow_2;
+int     dplaces, nn;
+
+tmp1  = M_get_stack_var();
+tmp2  = M_get_stack_var();
+a0    = M_get_stack_var();
+b0    = M_get_stack_var();
+c0    = M_get_stack_var();
+a1    = M_get_stack_var();
+b1    = M_get_stack_var();
+sum   = M_get_stack_var();
+pow_2 = M_get_stack_var();
+
+dplaces = places + 16;
+
+m_apm_copy(a0, MM_One);
+m_apm_copy(sum, MM_One);
+m_apm_copy(pow_2, MM_Four);
+m_apm_sqrt(b0, dplaces, MM_0_5);        /* sqrt(0.5) */
+
+while (TRUE)
+  {
+   m_apm_add(tmp1, a0, b0);
+   m_apm_multiply(a1, MM_0_5, tmp1);
+
+   m_apm_multiply(tmp1, a0, b0);
+   m_apm_sqrt(b1, dplaces, tmp1);
+
+   m_apm_subtract(tmp1, a0, b0);
+   m_apm_multiply(c0, MM_0_5, tmp1);
+
+   /*
+    *   the net 'PI' calculated from this iteration will
+    *   be accurate to ~4 X the value of (c0)'s exponent.
+    *   this was determined experimentally. 
+    */
+
+   nn = -4 * c0->m_apm_exponent;
+
+   m_apm_multiply(tmp1, c0, c0);
+   m_apm_multiply(tmp2, tmp1, pow_2);
+   m_apm_subtract(tmp1, sum, tmp2);
+   m_apm_round(sum, dplaces, tmp1);
+
+   if (nn >= dplaces)
+     break;
+
+   m_apm_copy(a0, a1);
+   m_apm_copy(b0, b1);
+
+   m_apm_multiply(tmp1, pow_2, MM_Two);
+   m_apm_copy(pow_2, tmp1);
+  }
+
+m_apm_add(tmp1, a1, b1);
+m_apm_multiply(tmp2, tmp1, tmp1);
+m_apm_divide(tmp1, dplaces, tmp2, sum);
+m_apm_round(outv, places, tmp1);
+
+M_restore_stack(9);
+}
+/****************************************************************************/

+ 337 - 0
mapm/src/mapm_div.c

@@ -0,0 +1,337 @@
+
+/* 
+ *  M_APM  -  mapm_div.c
+ *
+ *  Copyright (C) 1999 - 2007   Michael C. Ring
+ *
+ *  Permission to use, copy, and distribute this software and its
+ *  documentation for any purpose with or without fee is hereby granted,
+ *  provided that the above copyright notice appear in all copies and
+ *  that both that copyright notice and this permission notice appear
+ *  in supporting documentation.
+ *
+ *  Permission to modify the software is granted. Permission to distribute
+ *  the modified code is granted. Modifications are to be distributed by
+ *  using the file 'license.txt' as a template to modify the file header.
+ *  'license.txt' is available in the official MAPM distribution.
+ *
+ *  This software is provided "as is" without express or implied warranty.
+ */
+
+/*
+ *      $Id: mapm_div.c,v 1.12 2007/12/03 01:35:18 mike Exp $
+ *
+ *      This file contains the basic division functions 
+ *
+ *      $Log: mapm_div.c,v $
+ *      Revision 1.12  2007/12/03 01:35:18  mike
+ *      Update license
+ *
+ *      Revision 1.11  2003/07/21 20:07:13  mike
+ *      Modify error messages to be in a consistent format.
+ *
+ *      Revision 1.10  2003/03/31 22:09:18  mike
+ *      call generic error handling function
+ *
+ *      Revision 1.9  2002/11/03 22:06:50  mike
+ *      Updated function parameters to use the modern style
+ *
+ *      Revision 1.8  2001/07/16 19:03:22  mike
+ *      add function M_free_all_div
+ *
+ *      Revision 1.7  2001/02/11 22:30:42  mike
+ *      modify parameters to REALLOC
+ *
+ *      Revision 1.6  2000/09/23 19:07:17  mike
+ *      change _divide to M_apm_sdivide function name
+ *
+ *      Revision 1.5  2000/04/11 18:38:55  mike
+ *      use new algorithm to determine q-hat. uses more digits of
+ *      the numerator and denominator.
+ *
+ *      Revision 1.4  2000/02/03 22:45:08  mike
+ *      use MAPM_* generic memory function
+ *
+ *      Revision 1.3  1999/06/23 01:10:49  mike
+ *      use predefined constant for '15'
+ *
+ *      Revision 1.2  1999/06/23 00:55:09  mike
+ *      change mult factor to 15
+ *
+ *      Revision 1.1  1999/05/10 20:56:31  mike
+ *      Initial revision
+ */
+
+#include "m_apm_lc.h"
+
+static	M_APM	M_div_worka;
+static	M_APM	M_div_workb;
+static	M_APM	M_div_tmp7;
+static	M_APM	M_div_tmp8;
+static	M_APM	M_div_tmp9;
+
+static	int	M_div_firsttime = TRUE;
+
+/****************************************************************************/
+void	M_free_all_div()
+{
+if (M_div_firsttime == FALSE)
+  {
+   m_apm_free(M_div_worka);
+   m_apm_free(M_div_workb);
+   m_apm_free(M_div_tmp7);
+   m_apm_free(M_div_tmp8);
+   m_apm_free(M_div_tmp9);
+
+   M_div_firsttime = TRUE;
+  }
+}
+/****************************************************************************/
+void	m_apm_integer_div_rem(M_APM qq, M_APM rr, M_APM aa, M_APM bb)
+{
+m_apm_integer_divide(qq, aa, bb);
+m_apm_multiply(M_div_tmp7, qq, bb);
+m_apm_subtract(rr, aa, M_div_tmp7);
+}
+/****************************************************************************/
+void	m_apm_integer_divide(M_APM rr, M_APM aa, M_APM bb)
+{
+/*
+ *    we must use this divide function since the 
+ *    faster divide function using the reciprocal
+ *    will round the result (possibly changing 
+ *    nnm.999999...  -->  nn(m+1).0000 which would 
+ *    invalidate the 'integer_divide' goal).
+ */
+
+M_apm_sdivide(rr, 4, aa, bb);
+
+if (rr->m_apm_exponent <= 0)        /* result is 0 */
+  {
+   M_set_to_zero(rr);
+  }
+else
+  {
+   if (rr->m_apm_datalength > rr->m_apm_exponent)
+     {
+      rr->m_apm_datalength = rr->m_apm_exponent;
+      M_apm_normalize(rr);
+     }
+  }
+}
+/****************************************************************************/
+void	M_apm_sdivide(M_APM r, int places, M_APM a, M_APM b)
+{
+int	j, k, m, b0, sign, nexp, indexr, icompare, iterations;
+long    trial_numer;
+void	*vp;
+
+if (M_div_firsttime)
+  {
+   M_div_firsttime = FALSE;
+
+   M_div_worka = m_apm_init();
+   M_div_workb = m_apm_init();
+   M_div_tmp7  = m_apm_init();
+   M_div_tmp8  = m_apm_init();
+   M_div_tmp9  = m_apm_init();
+  }
+
+sign = a->m_apm_sign * b->m_apm_sign;
+
+if (sign == 0)      /* one number is zero, result is zero */
+  {
+   if (b->m_apm_sign == 0)
+     {
+      M_apm_log_error_msg(M_APM_RETURN, "\'M_apm_sdivide\', Divide by 0");
+     }
+
+   M_set_to_zero(r);
+   return;
+  }
+
+/*
+ *  Knuth step D1. Since base = 100, base / 2 = 50.
+ *  (also make the working copies positive)
+ */
+
+if (b->m_apm_data[0] >= 50)
+  {
+   m_apm_absolute_value(M_div_worka, a);
+   m_apm_absolute_value(M_div_workb, b);
+  }
+else       /* 'normal' step D1 */
+  {
+   k = 100 / (b->m_apm_data[0] + 1);
+   m_apm_set_long(M_div_tmp9, (long)k);
+
+   m_apm_multiply(M_div_worka, M_div_tmp9, a);
+   m_apm_multiply(M_div_workb, M_div_tmp9, b);
+
+   M_div_worka->m_apm_sign = 1;
+   M_div_workb->m_apm_sign = 1;
+  }
+
+/* setup trial denominator for step D3 */
+
+b0 = 100 * (int)M_div_workb->m_apm_data[0];
+
+if (M_div_workb->m_apm_datalength >= 3)
+  b0 += M_div_workb->m_apm_data[1];
+
+nexp = M_div_worka->m_apm_exponent - M_div_workb->m_apm_exponent;
+
+if (nexp > 0)
+  iterations = nexp + places + 1;
+else
+  iterations = places + 1;
+
+k = (iterations + 1) >> 1;     /* required size of result, in bytes */
+
+if (k > r->m_apm_malloclength)
+  {
+   if ((vp = MAPM_REALLOC(r->m_apm_data, (k + 32))) == NULL)
+     {
+      /* fatal, this does not return */
+
+      M_apm_log_error_msg(M_APM_FATAL, "\'M_apm_sdivide\', Out of memory");
+     }
+  
+   r->m_apm_malloclength = k + 28;
+   r->m_apm_data = (UCHAR *)vp;
+  }
+
+/* clear the exponent in the working copies */
+
+M_div_worka->m_apm_exponent = 0;
+M_div_workb->m_apm_exponent = 0;
+
+/* if numbers are equal, ratio == 1.00000... */
+
+if ((icompare = m_apm_compare(M_div_worka, M_div_workb)) == 0)
+  {
+   iterations = 1;
+   r->m_apm_data[0] = 10;
+   nexp++;
+  }
+else			           /* ratio not 1, do the real division */
+  {
+   if (icompare == 1)                        /* numerator > denominator */
+     {
+      nexp++;                           /* to adjust the final exponent */
+      M_div_worka->m_apm_exponent += 1;     /* multiply numerator by 10 */
+     }
+   else                                      /* numerator < denominator */
+     {
+      M_div_worka->m_apm_exponent += 2;    /* multiply numerator by 100 */
+     }
+
+   indexr = 0;
+   m      = 0;
+
+   while (TRUE)
+     {
+      /*
+       *  Knuth step D3. Only use the 3rd -> 6th digits if the number
+       *  actually has that many digits.
+       */
+
+      trial_numer = 10000L * (long)M_div_worka->m_apm_data[0];
+      
+      if (M_div_worka->m_apm_datalength >= 5)
+        {
+         trial_numer += 100 * M_div_worka->m_apm_data[1]
+                            + M_div_worka->m_apm_data[2];
+	}
+      else
+        {
+         if (M_div_worka->m_apm_datalength >= 3)
+           trial_numer += 100 * M_div_worka->m_apm_data[1];
+        }
+
+      j = (int)(trial_numer / b0);
+
+      /* 
+       *    Since the library 'normalizes' all the results, we need
+       *    to look at the exponent of the number to decide if we 
+       *    have a lead in 0n or 00.
+       */
+
+      if ((k = 2 - M_div_worka->m_apm_exponent) > 0)
+        {
+	 while (TRUE)
+	   {
+	    j /= 10;
+	    if (--k == 0)
+	      break;
+	   }
+	}
+
+      if (j == 100)     /* qhat == base ??      */
+        j = 99;         /* if so, decrease by 1 */
+
+      m_apm_set_long(M_div_tmp8, (long)j);
+      m_apm_multiply(M_div_tmp7, M_div_tmp8, M_div_workb);
+
+      /*
+       *    Compare our q-hat (j) against the desired number.
+       *    j is either correct, 1 too large, or 2 too large
+       *    per Theorem B on pg 272 of Art of Compter Programming,
+       *    Volume 2, 3rd Edition.
+       *    
+       *    The above statement is only true if using the 2 leading
+       *    digits of the numerator and the leading digit of the 
+       *    denominator. Since we are using the (3) leading digits
+       *    of the numerator and the (2) leading digits of the 
+       *    denominator, we eliminate the case where our q-hat is 
+       *    2 too large, (and q-hat being 1 too large is quite remote).
+       */
+
+      if (m_apm_compare(M_div_tmp7, M_div_worka) == 1)
+        {
+	 j--;
+         m_apm_subtract(M_div_tmp8, M_div_tmp7, M_div_workb);
+         m_apm_copy(M_div_tmp7, M_div_tmp8);
+	}
+
+      /* 
+       *  Since we know q-hat is correct, step D6 is unnecessary.
+       *
+       *  Store q-hat, step D5. Since D6 is unnecessary, we can 
+       *  do D5 before D4 and decide if we are done.
+       */
+
+      r->m_apm_data[indexr++] = (UCHAR)j;    /* j == 'qhat' */
+      m += 2;
+
+      if (m >= iterations)
+        break;
+
+      /* step D4 */
+
+      m_apm_subtract(M_div_tmp9, M_div_worka, M_div_tmp7);
+
+      /*
+       *  if the subtraction yields zero, the division is exact
+       *  and we are done early.
+       */
+
+      if (M_div_tmp9->m_apm_sign == 0)
+        {
+	 iterations = m;
+	 break;
+	}
+
+      /* multiply by 100 and re-save */
+      M_div_tmp9->m_apm_exponent += 2;
+      m_apm_copy(M_div_worka, M_div_tmp9);
+     }
+  }
+
+r->m_apm_sign       = sign;
+r->m_apm_exponent   = nexp;
+r->m_apm_datalength = iterations;
+
+M_apm_normalize(r);
+}
+/****************************************************************************/

+ 408 - 0
mapm/src/mapm_exp.c

@@ -0,0 +1,408 @@
+
+/* 
+ *  M_APM  -  mapm_exp.c
+ *
+ *  Copyright (C) 1999 - 2007   Michael C. Ring
+ *
+ *  Permission to use, copy, and distribute this software and its
+ *  documentation for any purpose with or without fee is hereby granted,
+ *  provided that the above copyright notice appear in all copies and
+ *  that both that copyright notice and this permission notice appear
+ *  in supporting documentation.
+ *
+ *  Permission to modify the software is granted. Permission to distribute
+ *  the modified code is granted. Modifications are to be distributed by
+ *  using the file 'license.txt' as a template to modify the file header.
+ *  'license.txt' is available in the official MAPM distribution.
+ *
+ *  This software is provided "as is" without express or implied warranty.
+ */
+
+/*
+ *      $Id: mapm_exp.c,v 1.37 2007/12/03 01:36:00 mike Exp $
+ *
+ *      This file contains the EXP function.
+ *
+ *      $Log: mapm_exp.c,v $
+ *      Revision 1.37  2007/12/03 01:36:00  mike
+ *      Update license
+ *
+ *      Revision 1.36  2004/06/02 00:29:03  mike
+ *      simplify logic in compute_nn
+ *
+ *      Revision 1.35  2004/05/29 18:29:44  mike
+ *      move exp nn calculation into its own function
+ *
+ *      Revision 1.34  2004/05/21 20:41:01  mike
+ *      fix potential buffer overflow
+ *
+ *      Revision 1.33  2004/02/18 02:46:45  mike
+ *      fix comment
+ *
+ *      Revision 1.32  2004/02/18 02:41:35  mike
+ *      check to make sure 'nn' does not overflow
+ *
+ *      Revision 1.31  2004/01/01 00:06:38  mike
+ *      make a comment more clear
+ *
+ *      Revision 1.30  2003/12/31 21:44:57  mike
+ *      simplify logic in _exp
+ *
+ *      Revision 1.29  2003/12/28 00:03:27  mike
+ *      dont allow 'tmp7' to get too small prior to divide by 256
+ *
+ *      Revision 1.28  2003/12/27 22:53:04  mike
+ *      change 1024 to 512, if input is already small, call
+ *      raw_exp directly and return
+ *
+ *      Revision 1.27  2003/03/30 21:16:37  mike
+ *      use global version of log(2) instead of local copy
+ *
+ *      Revision 1.26  2002/11/03 22:30:18  mike
+ *      Updated function parameters to use the modern style
+ *
+ *      Revision 1.25  2001/08/06 22:07:00  mike
+ *      round the 'nn' calculation to the nearest int
+ *
+ *      Revision 1.24  2001/08/05 21:58:59  mike
+ *      make 1 / log(2) constant shorter
+ *
+ *      Revision 1.23  2001/07/16 19:10:23  mike
+ *      add function M_free_all_exp
+ *
+ *      Revision 1.22  2001/07/10 21:55:36  mike
+ *      optimize raw_exp by using fewer digits as the
+ *      subsequent terms get smaller
+ *
+ *      Revision 1.21  2001/02/06 21:20:31  mike
+ *      optimize 'nn' calculation (for the future)
+ *
+ *      Revision 1.20  2001/02/05 21:55:12  mike
+ *      minor optimization, use a multiply instead
+ *      of a divide
+ *
+ *      Revision 1.19  2000/08/22 21:34:41  mike
+ *      increase local precision
+ *
+ *      Revision 1.18  2000/05/18 22:05:22  mike
+ *      move _pow to a separate file
+ *
+ *      Revision 1.17  2000/05/04 23:21:01  mike
+ *      use global var 256R
+ *
+ *      Revision 1.16  2000/03/30 21:33:30  mike
+ *      change termination of raw_exp to use ints, not MAPM numbers
+ *
+ *      Revision 1.15  2000/02/05 22:59:46  mike
+ *      adjust decimal places on calculation
+ *
+ *      Revision 1.14  2000/02/04 20:45:21  mike
+ *      re-compute log(2) on the fly if we need a more precise value
+ *
+ *      Revision 1.13  2000/02/04 19:35:14  mike
+ *      use just an approx log(2) for the integer divide
+ *
+ *      Revision 1.12  2000/02/04 16:47:32  mike
+ *      use the real algorithm for EXP
+ *
+ *      Revision 1.11  1999/09/18 01:27:40  mike
+ *      if X is 0 on the pow function, return 0 right away
+ *
+ *      Revision 1.10  1999/06/19 20:54:07  mike
+ *      changed local static MAPM to stack variables
+ *
+ *      Revision 1.9  1999/06/01 22:37:44  mike
+ *      adjust decimal places passed to raw function
+ *
+ *      Revision 1.8  1999/06/01 01:44:03  mike
+ *      change threshold from 1000 to 100 for 65536 divisor
+ *
+ *      Revision 1.7  1999/06/01 01:03:31  mike
+ *      vary 'q' instead of checking input against +/- 10 and +/- 40
+ *
+ *      Revision 1.6  1999/05/15 01:54:27  mike
+ *      add check for number of decimal places
+ *
+ *      Revision 1.5  1999/05/15 01:09:49  mike
+ *      minor tweak to POW decimal places
+ *
+ *      Revision 1.4  1999/05/13 00:14:00  mike
+ *      added more comments
+ *
+ *      Revision 1.3  1999/05/12 23:39:05  mike
+ *      change #places passed to sub functions
+ *
+ *      Revision 1.2  1999/05/10 21:35:13  mike
+ *      added some comments
+ *
+ *      Revision 1.1  1999/05/10 20:56:31  mike
+ *      Initial revision
+ */
+
+#include "m_apm_lc.h"
+
+static  M_APM  MM_exp_log2R;
+static  M_APM  MM_exp_512R;
+static	int    MM_firsttime1 = TRUE;
+
+/****************************************************************************/
+void	M_free_all_exp()
+{
+if (MM_firsttime1 == FALSE)
+  {
+   m_apm_free(MM_exp_log2R);
+   m_apm_free(MM_exp_512R);
+
+   MM_firsttime1 = TRUE;
+  }
+}
+/****************************************************************************/
+void	m_apm_exp(M_APM r, int places, M_APM x)
+{
+M_APM   tmp7, tmp8, tmp9;
+int	dplaces, nn, ii;
+
+if (MM_firsttime1)
+  {
+   MM_firsttime1 = FALSE;
+
+   MM_exp_log2R = m_apm_init();
+   MM_exp_512R  = m_apm_init();
+
+   m_apm_set_string(MM_exp_log2R, "1.44269504089");   /* ~ 1 / log(2) */
+   m_apm_set_string(MM_exp_512R,  "1.953125E-3");     /*   1 / 512    */
+  }
+
+tmp7 = M_get_stack_var();
+tmp8 = M_get_stack_var();
+tmp9 = M_get_stack_var();
+
+if (x->m_apm_sign == 0)		/* if input == 0, return '1' */
+  {
+   m_apm_copy(r, MM_One);
+   M_restore_stack(3);
+   return;
+  }
+
+if (x->m_apm_exponent <= -3)  /* already small enough so call _raw directly */
+  {
+   M_raw_exp(tmp9, (places + 6), x);
+   m_apm_round(r, places, tmp9);
+   M_restore_stack(3);
+   return;
+  }
+
+/*
+    From David H. Bailey's MPFUN Fortran package :
+
+    exp (t) =  (1 + r + r^2 / 2! + r^3 / 3! + r^4 / 4! ...) ^ q * 2 ^ n
+
+    where q = 256, r = t' / q, t' = t - n Log(2) and where n is chosen so
+    that -0.5 Log(2) < t' <= 0.5 Log(2).  Reducing t mod Log(2) and
+    dividing by 256 insures that -0.001 < r <= 0.001, which accelerates
+    convergence in the above series.
+
+    I use q = 512 and also limit how small 'r' can become. The 'r' used
+    here is limited in magnitude from 1.95E-4 < |r| < 1.35E-3. Forcing
+    'r' into a narrow range keeps the algorithm 'well behaved'.
+
+    ( the range is [0.1 / 512] to [log(2) / 512] )
+*/
+
+if (M_exp_compute_nn(&nn, tmp7, x) != 0)
+  {
+   M_apm_log_error_msg(M_APM_RETURN, 
+      "\'m_apm_exp\', Input too large, Overflow");
+
+   M_set_to_zero(r);
+   M_restore_stack(3);
+   return;
+  }
+
+dplaces = places + 8;
+
+/* check to make sure our log(2) is accurate enough */
+
+M_check_log_places(dplaces);
+
+m_apm_multiply(tmp8, tmp7, MM_lc_log2);
+m_apm_subtract(tmp7, x, tmp8);
+
+/*
+ *     guarantee that |tmp7| is between 0.1 and 0.9999999....
+ *     (in practice, the upper limit only reaches log(2), 0.693... )
+ */
+
+while (TRUE)
+  {
+   if (tmp7->m_apm_sign != 0)
+     {
+      if (tmp7->m_apm_exponent == 0)
+        break;
+     }
+     
+   if (tmp7->m_apm_sign >= 0)
+     {
+      nn++;
+      m_apm_subtract(tmp8, tmp7, MM_lc_log2);
+      m_apm_copy(tmp7, tmp8);
+     }
+   else
+     {
+      nn--;
+      m_apm_add(tmp8, tmp7, MM_lc_log2);
+      m_apm_copy(tmp7, tmp8);
+     }
+  }
+
+m_apm_multiply(tmp9, tmp7, MM_exp_512R);
+
+/* perform the series expansion ... */
+
+M_raw_exp(tmp8, dplaces, tmp9);
+
+/*
+ *   raise result to the 512 power
+ *
+ *   note : x ^ 512  =  (((x ^ 2) ^ 2) ^ 2) ... 9 times
+ */
+
+ii = 9;
+
+while (TRUE)
+  {
+   m_apm_multiply(tmp9, tmp8, tmp8);
+   m_apm_round(tmp8, dplaces, tmp9);
+
+   if (--ii == 0)
+     break;
+  }
+
+/* now compute 2 ^ N */
+
+m_apm_integer_pow(tmp7, dplaces, MM_Two, nn);
+
+m_apm_multiply(tmp9, tmp7, tmp8);
+m_apm_round(r, places, tmp9);
+
+M_restore_stack(3);                    /* restore the 3 locals we used here */
+}
+/****************************************************************************/
+/*
+	compute  int *n  = round_to_nearest_int(a / log(2))
+	         M_APM b = MAPM version of *n
+
+        returns      0: OK
+		 -1, 1: failure
+*/
+int	M_exp_compute_nn(int *n, M_APM b, M_APM a)
+{
+M_APM	tmp0, tmp1;
+void	*vp;
+char    *cp, sbuf[48];
+int	kk;
+
+*n   = 0;
+vp   = NULL;
+cp   = sbuf;
+tmp0 = M_get_stack_var();
+tmp1 = M_get_stack_var();
+
+/* find 'n' and convert it to a normal C int            */
+/* we just need an approx 1/log(2) for this calculation */
+
+m_apm_multiply(tmp1, a, MM_exp_log2R);
+
+/* round to the nearest int */
+
+if (tmp1->m_apm_sign >= 0)
+  {
+   m_apm_add(tmp0, tmp1, MM_0_5);
+   m_apm_floor(tmp1, tmp0);
+  }
+else
+  {
+   m_apm_subtract(tmp0, tmp1, MM_0_5);
+   m_apm_ceil(tmp1, tmp0);
+  }
+
+kk = tmp1->m_apm_exponent;
+if (kk >= 42)
+  {
+   if ((vp = (void *)MAPM_MALLOC((kk + 16) * sizeof(char))) == NULL)
+     {
+      /* fatal, this does not return */
+
+      M_apm_log_error_msg(M_APM_FATAL, "\'M_exp_compute_nn\', Out of memory");
+     }
+
+   cp = (char *)vp;
+  }
+
+m_apm_to_integer_string(cp, tmp1);
+*n = atoi(cp);
+
+m_apm_set_long(b, (long)(*n));
+
+kk = m_apm_compare(b, tmp1);
+
+if (vp != NULL)
+  MAPM_FREE(vp);
+
+M_restore_stack(2);
+return(kk);
+}
+/****************************************************************************/
+/*
+	calculate the exponential function using the following series :
+
+                              x^2     x^3     x^4     x^5
+	exp(x) == 1  +  x  +  ---  +  ---  +  ---  +  ---  ...
+                               2!      3!      4!      5!
+
+*/
+void	M_raw_exp(M_APM rr, int places, M_APM xx)
+{
+M_APM   tmp0, digit, term;
+int	tolerance,  local_precision, prev_exp;
+long    m1;
+
+tmp0  = M_get_stack_var();
+term  = M_get_stack_var();
+digit = M_get_stack_var();
+
+local_precision = places + 8;
+tolerance       = -(places + 4);
+prev_exp        = 0;
+
+m_apm_add(rr, MM_One, xx);
+m_apm_copy(term, xx);
+
+m1 = 2L;
+
+while (TRUE)
+  {
+   m_apm_set_long(digit, m1);
+   m_apm_multiply(tmp0, term, xx);
+   m_apm_divide(term, local_precision, tmp0, digit);
+   m_apm_add(tmp0, rr, term);
+   m_apm_copy(rr, tmp0);
+
+   if ((term->m_apm_exponent < tolerance) || (term->m_apm_sign == 0))
+     break;
+
+   if (m1 != 2L)
+     {
+      local_precision = local_precision + term->m_apm_exponent - prev_exp;
+
+      if (local_precision < 20)
+        local_precision = 20;
+     }
+
+   prev_exp = term->m_apm_exponent;
+   m1++;
+  }
+
+M_restore_stack(3);                    /* restore the 3 locals we used here */
+}
+/****************************************************************************/

+ 70 - 0
mapm/src/mapm_fam.c

@@ -0,0 +1,70 @@
+
+/* 
+ *  M_APM  -  mapm_fam.c
+ *
+ *  Copyright (C) 1999 - 2007   Michael C. Ring
+ *
+ *  Permission to use, copy, and distribute this software and its
+ *  documentation for any purpose with or without fee is hereby granted,
+ *  provided that the above copyright notice appear in all copies and
+ *  that both that copyright notice and this permission notice appear
+ *  in supporting documentation.
+ *
+ *  Permission to modify the software is granted. Permission to distribute
+ *  the modified code is granted. Modifications are to be distributed by
+ *  using the file 'license.txt' as a template to modify the file header.
+ *  'license.txt' is available in the official MAPM distribution.
+ *
+ *  This software is provided "as is" without express or implied warranty.
+ */
+
+/*
+ *      $Id: mapm_fam.c,v 1.5 2007/12/03 01:36:38 mike Exp $
+ *
+ *      This file contains the free all memory and similiar functions.
+ *
+ *      $Log: mapm_fam.c,v $
+ *      Revision 1.5  2007/12/03 01:36:38  mike
+ *      Update license
+ *
+ *      Revision 1.4  2003/03/30 21:13:05  mike
+ *      remove _log from free list
+ *
+ *      Revision 1.3  2002/02/14 13:36:27  mike
+ *      add conditional compile around free all FFT
+ *
+ *      Revision 1.2  2001/07/16 18:52:40  mike
+ *      add some comments
+ *
+ *      Revision 1.1  2001/07/16 18:41:44  mike
+ *      Initial revision
+ */
+
+#include "m_apm_lc.h"
+
+/****************************************************************************/
+void	m_apm_free_all_mem()
+{
+M_free_all_add();    /* call each module which has statically declared data */
+M_free_all_div();
+M_free_all_exp();
+
+#ifndef NO_FFT_MULTIPLY
+M_free_all_fft();
+#endif
+
+M_free_all_pow();
+M_free_all_rnd();
+M_free_all_set();
+M_free_all_cnst();
+M_free_all_fmul();
+M_free_all_stck();
+M_free_all_util();
+}
+/****************************************************************************/
+void	m_apm_trim_mem_usage()
+{
+m_apm_free_all_mem();
+m_apm_free(m_apm_init());
+}
+/****************************************************************************/

+ 955 - 0
mapm/src/mapm_fft.c

@@ -0,0 +1,955 @@
+
+/* 
+ *  M_APM  -  mapm_fft.c
+ *
+ *  This FFT (Fast Fourier Transform) is from Takuya OOURA 
+ *
+ *  Copyright(C) 1996-1999 Takuya OOURA
+ *  email: [email protected]
+ *
+ *  See full FFT documentation below ...  (MCR)
+ *
+ *  This software is provided "as is" without express or implied warranty.
+ */
+
+/*
+ *      $Id: mapm_fft.c,v 1.15 2007/12/03 01:37:42 mike Exp $
+ *
+ *      This file contains the FFT based FAST MULTIPLICATION function 
+ *      as well as its support functions.
+ *
+ *      $Log: mapm_fft.c,v $
+ *      Revision 1.15  2007/12/03 01:37:42  mike
+ *      no changes
+ *
+ *      Revision 1.14  2003/07/28 19:39:01  mike
+ *      change 16 bit constant
+ *
+ *      Revision 1.13  2003/07/21 20:11:55  mike
+ *      Modify error messages to be in a consistent format.
+ *
+ *      Revision 1.12  2003/05/01 21:55:36  mike
+ *      remove math.h
+ *
+ *      Revision 1.11  2003/03/31 22:10:09  mike
+ *      call generic error handling function
+ *
+ *      Revision 1.10  2002/11/03 22:11:48  mike
+ *      Updated function parameters to use the modern style
+ *
+ *      Revision 1.9  2001/07/16 19:16:15  mike
+ *      add function M_free_all_fft
+ *
+ *      Revision 1.8  2000/08/01 22:23:24  mike
+ *      use sizeof(int) from function call to stop
+ *      some compilers from complaining.
+ *
+ *      Revision 1.7  2000/07/30 22:39:21  mike
+ *      lower 16 bit malloc size
+ *
+ *      Revision 1.6  2000/07/10 22:54:26  mike
+ *      malloc the local data arrays
+ *
+ *      Revision 1.5  2000/07/10 00:09:02  mike
+ *      use local static arrays for smaller numbers
+ *
+ *      Revision 1.4  2000/07/08 18:24:23  mike
+ *      minor optimization tweak
+ *
+ *      Revision 1.3  2000/07/08 17:52:49  mike
+ *      do the FFT in base 10000 instead of MAPM numbers base 100
+ *      this runs faster and uses 1/2 the RAM
+ *
+ *      Revision 1.2  2000/07/06 21:04:34  mike
+ *      added more comments
+ *
+ *      Revision 1.1  2000/07/06 20:42:05  mike
+ *      Initial revision
+ */
+
+#include "m_apm_lc.h"
+
+#ifndef MM_PI_2
+#define MM_PI_2      1.570796326794896619231321691639751442098584699687
+#endif
+
+#ifndef WR5000       /* cos(MM_PI_2*0.5000) */
+#define WR5000       0.707106781186547524400844362104849039284835937688
+#endif
+
+#ifndef RDFT_LOOP_DIV     /* control of the RDFT's speed & tolerance */
+#define RDFT_LOOP_DIV 64
+#endif
+
+extern void   M_fast_mul_fft(UCHAR *, UCHAR *, UCHAR *, int);
+
+extern void   M_rdft(int, int, double *);
+extern void   M_bitrv2(int, double *);
+extern void   M_cftfsub(int, double *);
+extern void   M_cftbsub(int, double *);
+extern void   M_rftfsub(int, double *);
+extern void   M_rftbsub(int, double *);
+extern void   M_cft1st(int, double *);
+extern void   M_cftmdl(int, int, double *);
+
+static double *M_aa_array, *M_bb_array;
+static int    M_size = -1;
+
+static char   *M_fft_error_msg = "\'M_fast_mul_fft\', Out of memory";
+
+/****************************************************************************/
+void	M_free_all_fft()
+{
+if (M_size > 0)
+  {
+   MAPM_FREE(M_aa_array);
+   MAPM_FREE(M_bb_array);
+   M_size = -1;
+  }
+}
+/****************************************************************************/
+/*
+ *      multiply 'uu' by 'vv' with nbytes each
+ *      yielding a 2*nbytes result in 'ww'. 
+ *      each byte contains a base 100 'digit', 
+ *      i.e.: range from 0-99.
+ *
+ *             MSB              LSB
+ *
+ *   uu,vv     [0] [1] [2] ... [N-1]
+ *   ww        [0] [1] [2] ... [2N-1]
+ */
+
+void	M_fast_mul_fft(UCHAR *ww, UCHAR *uu, UCHAR *vv, int nbytes)
+{
+int             mflag, i, j, nn2, nn;
+double          carry, nnr, dtemp, *a, *b;
+UCHAR           *w0;
+unsigned long   ul;
+
+if (M_size < 0)                  /* if first time in, setup working arrays */
+  {
+   if (M_get_sizeof_int() == 2)  /* if still using 16 bit compilers */
+     M_size = 516;
+   else
+     M_size = 8200;
+
+   M_aa_array = (double *)MAPM_MALLOC(M_size * sizeof(double));
+   M_bb_array = (double *)MAPM_MALLOC(M_size * sizeof(double));
+   
+   if ((M_aa_array == NULL) || (M_bb_array == NULL))
+     {
+      /* fatal, this does not return */
+
+      M_apm_log_error_msg(M_APM_FATAL, M_fft_error_msg);
+     }
+  }
+
+nn  = nbytes;
+nn2 = nbytes >> 1;
+
+if (nn > M_size)
+  {
+   mflag = TRUE;
+
+   a = (double *)MAPM_MALLOC((nn + 8) * sizeof(double));
+   b = (double *)MAPM_MALLOC((nn + 8) * sizeof(double));
+   
+   if ((a == NULL) || (b == NULL))
+     {
+      /* fatal, this does not return */
+
+      M_apm_log_error_msg(M_APM_FATAL, M_fft_error_msg);
+     }
+  }
+else
+  {
+   mflag = FALSE;
+
+   a = M_aa_array;
+   b = M_bb_array;
+  }
+
+/*
+ *   convert normal base 100 MAPM numbers to base 10000
+ *   for the FFT operation.
+ */
+
+i = 0;
+for (j=0; j < nn2; j++)
+  {
+   a[j] = (double)((int)uu[i] * 100 + uu[i+1]);
+   b[j] = (double)((int)vv[i] * 100 + vv[i+1]);
+   i += 2;
+  }
+
+/* zero fill the second half of the arrays */
+
+for (j=nn2; j < nn; j++)
+  {
+   a[j] = 0.0;
+   b[j] = 0.0;
+  }
+
+/* perform the forward Fourier transforms for both numbers */
+
+M_rdft(nn, 1, a);
+M_rdft(nn, 1, b);
+
+/* perform the convolution ... */
+
+b[0] *= a[0];
+b[1] *= a[1];
+
+for (j=3; j <= nn; j += 2)
+  {
+   dtemp  = b[j-1];
+   b[j-1] = dtemp * a[j-1] - b[j] * a[j];
+   b[j]   = dtemp * a[j] + b[j] * a[j-1];
+  }
+
+/* perform the inverse transform on the result */
+
+M_rdft(nn, -1, b);
+
+/* perform a final pass to release all the carries */
+/* we are still in base 10000 at this point        */
+
+carry = 0.0;
+j     = nn;
+nnr   = 2.0 / (double)nn;
+
+while (1)
+  {
+   dtemp = b[--j] * nnr + carry + 0.5;
+   ul    = (unsigned long)(dtemp * 1.0E-4);
+   carry = (double)ul;
+   b[j]  = dtemp - carry * 10000.0;
+
+   if (j == 0)
+     break;
+  }
+
+/* copy result to our destination after converting back to base 100 */
+
+w0 = ww;
+M_get_div_rem((int)ul, w0, (w0 + 1));
+
+for (j=0; j <= (nn - 2); j++)
+  {
+   w0 += 2;
+   M_get_div_rem((int)b[j], w0, (w0 + 1));
+  }
+
+if (mflag)
+  {
+   MAPM_FREE(b);
+   MAPM_FREE(a);
+  }
+}
+/****************************************************************************/
+
+/*
+ *    The following info is from Takuya OOURA's documentation : 
+ *
+ *    NOTE : MAPM only uses the 'RDFT' function (as well as the 
+ *           functions RDFT calls). All the code from here down 
+ *           in this file is from Takuya OOURA. The only change I
+ *           made was to add 'M_' in front of all the functions
+ *           I used. This was to guard against any possible 
+ *           name collisions in the future.
+ *
+ *    MCR  06 July 2000
+ *
+ *
+ *    General Purpose FFT (Fast Fourier/Cosine/Sine Transform) Package
+ *    
+ *    Description:
+ *        A package to calculate Discrete Fourier/Cosine/Sine Transforms of 
+ *        1-dimensional sequences of length 2^N.
+ *    
+ *        fft4g_h.c  : FFT Package in C       - Simple Version I   (radix 4,2)
+ *        
+ *        rdft: Real Discrete Fourier Transform
+ *    
+ *    Method:
+ *        -------- rdft --------
+ *        A method with a following butterfly operation appended to "cdft".
+ *        In forward transform :
+ *            A[k] = sum_j=0^n-1 a[j]*W(n)^(j*k), 0<=k<=n/2, 
+ *                W(n) = exp(2*pi*i/n), 
+ *        this routine makes an array x[] :
+ *            x[j] = a[2*j] + i*a[2*j+1], 0<=j<n/2
+ *        and calls "cdft" of length n/2 :
+ *            X[k] = sum_j=0^n/2-1 x[j] * W(n/2)^(j*k), 0<=k<n.
+ *        The result A[k] are :
+ *            A[k]     = X[k]     - (1+i*W(n)^k)/2 * (X[k]-conjg(X[n/2-k])),
+ *            A[n/2-k] = X[n/2-k] + 
+ *                            conjg((1+i*W(n)^k)/2 * (X[k]-conjg(X[n/2-k]))),
+ *                0<=k<=n/2
+ *            (notes: conjg() is a complex conjugate, X[n/2]=X[0]).
+ *        ----------------------
+ *    
+ *    Reference:
+ *        * Masatake MORI, Makoto NATORI, Tatuo TORII: Suchikeisan, 
+ *          Iwanamikouzajyouhoukagaku18, Iwanami, 1982 (Japanese)
+ *        * Henri J. Nussbaumer: Fast Fourier Transform and Convolution 
+ *          Algorithms, Springer Verlag, 1982
+ *        * C. S. Burrus, Notes on the FFT (with large FFT paper list)
+ *          http://www-dsp.rice.edu/research/fft/fftnote.asc
+ *    
+ *    Copyright:
+ *        Copyright(C) 1996-1999 Takuya OOURA
+ *        email: [email protected]
+ *        download: http://momonga.t.u-tokyo.ac.jp/~ooura/fft.html
+ *        You may use, copy, modify this code for any purpose and 
+ *        without fee. You may distribute this ORIGINAL package.
+ */
+
+/*
+
+functions
+    rdft: Real Discrete Fourier Transform
+
+function prototypes
+    void rdft(int, int, double *);
+
+-------- Real DFT / Inverse of Real DFT --------
+    [definition]
+        <case1> RDFT
+            R[k] = sum_j=0^n-1 a[j]*cos(2*pi*j*k/n), 0<=k<=n/2
+            I[k] = sum_j=0^n-1 a[j]*sin(2*pi*j*k/n), 0<k<n/2
+        <case2> IRDFT (excluding scale)
+            a[k] = (R[0] + R[n/2]*cos(pi*k))/2 + 
+                   sum_j=1^n/2-1 R[j]*cos(2*pi*j*k/n) + 
+                   sum_j=1^n/2-1 I[j]*sin(2*pi*j*k/n), 0<=k<n
+    [usage]
+        <case1>
+            rdft(n, 1, a);
+        <case2>
+            rdft(n, -1, a);
+    [parameters]
+        n              :data length (int)
+                        n >= 2, n = power of 2
+        a[0...n-1]     :input/output data (double *)
+                        <case1>
+                            output data
+                                a[2*k] = R[k], 0<=k<n/2
+                                a[2*k+1] = I[k], 0<k<n/2
+                                a[1] = R[n/2]
+                        <case2>
+                            input data
+                                a[2*j] = R[j], 0<=j<n/2
+                                a[2*j+1] = I[j], 0<j<n/2
+                                a[1] = R[n/2]
+    [remark]
+        Inverse of 
+            rdft(n, 1, a);
+        is 
+            rdft(n, -1, a);
+            for (j = 0; j <= n - 1; j++) {
+                a[j] *= 2.0 / n;
+            }
+*/
+
+
+void	M_rdft(int n, int isgn, double *a)
+{
+    double xi;
+
+    if (isgn >= 0) {
+        if (n > 4) {
+            M_bitrv2(n, a);
+            M_cftfsub(n, a);
+            M_rftfsub(n, a);
+        } else if (n == 4) {
+            M_cftfsub(n, a);
+        }
+        xi = a[0] - a[1];
+        a[0] += a[1];
+        a[1] = xi;
+    } else {
+        a[1] = 0.5 * (a[0] - a[1]);
+        a[0] -= a[1];
+        if (n > 4) {
+            M_rftbsub(n, a);
+            M_bitrv2(n, a);
+            M_cftbsub(n, a);
+        } else if (n == 4) {
+            M_cftfsub(n, a);
+        }
+    }
+}
+
+
+
+void    M_bitrv2(int n, double *a)
+{
+    int j0, k0, j1, k1, l, m, i, j, k;
+    double xr, xi, yr, yi;
+    
+    l = n >> 2;
+    m = 2;
+    while (m < l) {
+        l >>= 1;
+        m <<= 1;
+    }
+    if (m == l) {
+        j0 = 0;
+        for (k0 = 0; k0 < m; k0 += 2) {
+            k = k0;
+            for (j = j0; j < j0 + k0; j += 2) {
+                xr = a[j];
+                xi = a[j + 1];
+                yr = a[k];
+                yi = a[k + 1];
+                a[j] = yr;
+                a[j + 1] = yi;
+                a[k] = xr;
+                a[k + 1] = xi;
+                j1 = j + m;
+                k1 = k + 2 * m;
+                xr = a[j1];
+                xi = a[j1 + 1];
+                yr = a[k1];
+                yi = a[k1 + 1];
+                a[j1] = yr;
+                a[j1 + 1] = yi;
+                a[k1] = xr;
+                a[k1 + 1] = xi;
+                j1 += m;
+                k1 -= m;
+                xr = a[j1];
+                xi = a[j1 + 1];
+                yr = a[k1];
+                yi = a[k1 + 1];
+                a[j1] = yr;
+                a[j1 + 1] = yi;
+                a[k1] = xr;
+                a[k1 + 1] = xi;
+                j1 += m;
+                k1 += 2 * m;
+                xr = a[j1];
+                xi = a[j1 + 1];
+                yr = a[k1];
+                yi = a[k1 + 1];
+                a[j1] = yr;
+                a[j1 + 1] = yi;
+                a[k1] = xr;
+                a[k1 + 1] = xi;
+                for (i = n >> 1; i > (k ^= i); i >>= 1);
+            }
+            j1 = j0 + k0 + m;
+            k1 = j1 + m;
+            xr = a[j1];
+            xi = a[j1 + 1];
+            yr = a[k1];
+            yi = a[k1 + 1];
+            a[j1] = yr;
+            a[j1 + 1] = yi;
+            a[k1] = xr;
+            a[k1 + 1] = xi;
+            for (i = n >> 1; i > (j0 ^= i); i >>= 1);
+        }
+    } else {
+        j0 = 0;
+        for (k0 = 2; k0 < m; k0 += 2) {
+            for (i = n >> 1; i > (j0 ^= i); i >>= 1);
+            k = k0;
+            for (j = j0; j < j0 + k0; j += 2) {
+                xr = a[j];
+                xi = a[j + 1];
+                yr = a[k];
+                yi = a[k + 1];
+                a[j] = yr;
+                a[j + 1] = yi;
+                a[k] = xr;
+                a[k + 1] = xi;
+                j1 = j + m;
+                k1 = k + m;
+                xr = a[j1];
+                xi = a[j1 + 1];
+                yr = a[k1];
+                yi = a[k1 + 1];
+                a[j1] = yr;
+                a[j1 + 1] = yi;
+                a[k1] = xr;
+                a[k1 + 1] = xi;
+                for (i = n >> 1; i > (k ^= i); i >>= 1);
+            }
+        }
+    }
+}
+
+
+
+void    M_cftfsub(int n, double *a)
+{
+    int j, j1, j2, j3, l;
+    double x0r, x0i, x1r, x1i, x2r, x2i, x3r, x3i;
+    
+    l = 2;
+    if (n > 8) {
+        M_cft1st(n, a);
+        l = 8;
+        while ((l << 2) < n) {
+            M_cftmdl(n, l, a);
+            l <<= 2;
+        }
+    }
+    if ((l << 2) == n) {
+        for (j = 0; j < l; j += 2) {
+            j1 = j + l;
+            j2 = j1 + l;
+            j3 = j2 + l;
+            x0r = a[j] + a[j1];
+            x0i = a[j + 1] + a[j1 + 1];
+            x1r = a[j] - a[j1];
+            x1i = a[j + 1] - a[j1 + 1];
+            x2r = a[j2] + a[j3];
+            x2i = a[j2 + 1] + a[j3 + 1];
+            x3r = a[j2] - a[j3];
+            x3i = a[j2 + 1] - a[j3 + 1];
+            a[j] = x0r + x2r;
+            a[j + 1] = x0i + x2i;
+            a[j2] = x0r - x2r;
+            a[j2 + 1] = x0i - x2i;
+            a[j1] = x1r - x3i;
+            a[j1 + 1] = x1i + x3r;
+            a[j3] = x1r + x3i;
+            a[j3 + 1] = x1i - x3r;
+        }
+    } else {
+        for (j = 0; j < l; j += 2) {
+            j1 = j + l;
+            x0r = a[j] - a[j1];
+            x0i = a[j + 1] - a[j1 + 1];
+            a[j] += a[j1];
+            a[j + 1] += a[j1 + 1];
+            a[j1] = x0r;
+            a[j1 + 1] = x0i;
+        }
+    }
+}
+
+
+
+void 	M_cftbsub(int n, double *a)
+{
+    int j, j1, j2, j3, l;
+    double x0r, x0i, x1r, x1i, x2r, x2i, x3r, x3i;
+    
+    l = 2;
+    if (n > 8) {
+        M_cft1st(n, a);
+        l = 8;
+        while ((l << 2) < n) {
+            M_cftmdl(n, l, a);
+            l <<= 2;
+        }
+    }
+    if ((l << 2) == n) {
+        for (j = 0; j < l; j += 2) {
+            j1 = j + l;
+            j2 = j1 + l;
+            j3 = j2 + l;
+            x0r = a[j] + a[j1];
+            x0i = -a[j + 1] - a[j1 + 1];
+            x1r = a[j] - a[j1];
+            x1i = -a[j + 1] + a[j1 + 1];
+            x2r = a[j2] + a[j3];
+            x2i = a[j2 + 1] + a[j3 + 1];
+            x3r = a[j2] - a[j3];
+            x3i = a[j2 + 1] - a[j3 + 1];
+            a[j] = x0r + x2r;
+            a[j + 1] = x0i - x2i;
+            a[j2] = x0r - x2r;
+            a[j2 + 1] = x0i + x2i;
+            a[j1] = x1r - x3i;
+            a[j1 + 1] = x1i - x3r;
+            a[j3] = x1r + x3i;
+            a[j3 + 1] = x1i + x3r;
+        }
+    } else {
+        for (j = 0; j < l; j += 2) {
+            j1 = j + l;
+            x0r = a[j] - a[j1];
+            x0i = -a[j + 1] + a[j1 + 1];
+            a[j] += a[j1];
+            a[j + 1] = -a[j + 1] - a[j1 + 1];
+            a[j1] = x0r;
+            a[j1 + 1] = x0i;
+        }
+    }
+}
+
+
+
+void 	M_cft1st(int n, double *a)
+{
+    int j, kj, kr;
+    double ew, wn4r, wk1r, wk1i, wk2r, wk2i, wk3r, wk3i;
+    double x0r, x0i, x1r, x1i, x2r, x2i, x3r, x3i;
+    
+    x0r = a[0] + a[2];
+    x0i = a[1] + a[3];
+    x1r = a[0] - a[2];
+    x1i = a[1] - a[3];
+    x2r = a[4] + a[6];
+    x2i = a[5] + a[7];
+    x3r = a[4] - a[6];
+    x3i = a[5] - a[7];
+    a[0] = x0r + x2r;
+    a[1] = x0i + x2i;
+    a[4] = x0r - x2r;
+    a[5] = x0i - x2i;
+    a[2] = x1r - x3i;
+    a[3] = x1i + x3r;
+    a[6] = x1r + x3i;
+    a[7] = x1i - x3r;
+    wn4r = WR5000;
+    x0r = a[8] + a[10];
+    x0i = a[9] + a[11];
+    x1r = a[8] - a[10];
+    x1i = a[9] - a[11];
+    x2r = a[12] + a[14];
+    x2i = a[13] + a[15];
+    x3r = a[12] - a[14];
+    x3i = a[13] - a[15];
+    a[8] = x0r + x2r;
+    a[9] = x0i + x2i;
+    a[12] = x2i - x0i;
+    a[13] = x0r - x2r;
+    x0r = x1r - x3i;
+    x0i = x1i + x3r;
+    a[10] = wn4r * (x0r - x0i);
+    a[11] = wn4r * (x0r + x0i);
+    x0r = x3i + x1r;
+    x0i = x3r - x1i;
+    a[14] = wn4r * (x0i - x0r);
+    a[15] = wn4r * (x0i + x0r);
+    ew = MM_PI_2 / n;
+    kr = 0;
+    for (j = 16; j < n; j += 16) {
+        for (kj = n >> 2; kj > (kr ^= kj); kj >>= 1);
+        wk1r = cos(ew * kr);
+        wk1i = sin(ew * kr);
+        wk2r = 1 - 2 * wk1i * wk1i;
+        wk2i = 2 * wk1i * wk1r;
+        wk3r = wk1r - 2 * wk2i * wk1i;
+        wk3i = 2 * wk2i * wk1r - wk1i;
+        x0r = a[j] + a[j + 2];
+        x0i = a[j + 1] + a[j + 3];
+        x1r = a[j] - a[j + 2];
+        x1i = a[j + 1] - a[j + 3];
+        x2r = a[j + 4] + a[j + 6];
+        x2i = a[j + 5] + a[j + 7];
+        x3r = a[j + 4] - a[j + 6];
+        x3i = a[j + 5] - a[j + 7];
+        a[j] = x0r + x2r;
+        a[j + 1] = x0i + x2i;
+        x0r -= x2r;
+        x0i -= x2i;
+        a[j + 4] = wk2r * x0r - wk2i * x0i;
+        a[j + 5] = wk2r * x0i + wk2i * x0r;
+        x0r = x1r - x3i;
+        x0i = x1i + x3r;
+        a[j + 2] = wk1r * x0r - wk1i * x0i;
+        a[j + 3] = wk1r * x0i + wk1i * x0r;
+        x0r = x1r + x3i;
+        x0i = x1i - x3r;
+        a[j + 6] = wk3r * x0r - wk3i * x0i;
+        a[j + 7] = wk3r * x0i + wk3i * x0r;
+        x0r = wn4r * (wk1r - wk1i);
+        wk1i = wn4r * (wk1r + wk1i);
+        wk1r = x0r;
+        wk3r = wk1r - 2 * wk2r * wk1i;
+        wk3i = 2 * wk2r * wk1r - wk1i;
+        x0r = a[j + 8] + a[j + 10];
+        x0i = a[j + 9] + a[j + 11];
+        x1r = a[j + 8] - a[j + 10];
+        x1i = a[j + 9] - a[j + 11];
+        x2r = a[j + 12] + a[j + 14];
+        x2i = a[j + 13] + a[j + 15];
+        x3r = a[j + 12] - a[j + 14];
+        x3i = a[j + 13] - a[j + 15];
+        a[j + 8] = x0r + x2r;
+        a[j + 9] = x0i + x2i;
+        x0r -= x2r;
+        x0i -= x2i;
+        a[j + 12] = -wk2i * x0r - wk2r * x0i;
+        a[j + 13] = -wk2i * x0i + wk2r * x0r;
+        x0r = x1r - x3i;
+        x0i = x1i + x3r;
+        a[j + 10] = wk1r * x0r - wk1i * x0i;
+        a[j + 11] = wk1r * x0i + wk1i * x0r;
+        x0r = x1r + x3i;
+        x0i = x1i - x3r;
+        a[j + 14] = wk3r * x0r - wk3i * x0i;
+        a[j + 15] = wk3r * x0i + wk3i * x0r;
+    }
+}
+
+
+
+void 	M_cftmdl(int n, int l, double *a)
+{
+    int j, j1, j2, j3, k, kj, kr, m, m2;
+    double ew, wn4r, wk1r, wk1i, wk2r, wk2i, wk3r, wk3i;
+    double x0r, x0i, x1r, x1i, x2r, x2i, x3r, x3i;
+    
+    m = l << 2;
+    for (j = 0; j < l; j += 2) {
+        j1 = j + l;
+        j2 = j1 + l;
+        j3 = j2 + l;
+        x0r = a[j] + a[j1];
+        x0i = a[j + 1] + a[j1 + 1];
+        x1r = a[j] - a[j1];
+        x1i = a[j + 1] - a[j1 + 1];
+        x2r = a[j2] + a[j3];
+        x2i = a[j2 + 1] + a[j3 + 1];
+        x3r = a[j2] - a[j3];
+        x3i = a[j2 + 1] - a[j3 + 1];
+        a[j] = x0r + x2r;
+        a[j + 1] = x0i + x2i;
+        a[j2] = x0r - x2r;
+        a[j2 + 1] = x0i - x2i;
+        a[j1] = x1r - x3i;
+        a[j1 + 1] = x1i + x3r;
+        a[j3] = x1r + x3i;
+        a[j3 + 1] = x1i - x3r;
+    }
+    wn4r = WR5000;
+    for (j = m; j < l + m; j += 2) {
+        j1 = j + l;
+        j2 = j1 + l;
+        j3 = j2 + l;
+        x0r = a[j] + a[j1];
+        x0i = a[j + 1] + a[j1 + 1];
+        x1r = a[j] - a[j1];
+        x1i = a[j + 1] - a[j1 + 1];
+        x2r = a[j2] + a[j3];
+        x2i = a[j2 + 1] + a[j3 + 1];
+        x3r = a[j2] - a[j3];
+        x3i = a[j2 + 1] - a[j3 + 1];
+        a[j] = x0r + x2r;
+        a[j + 1] = x0i + x2i;
+        a[j2] = x2i - x0i;
+        a[j2 + 1] = x0r - x2r;
+        x0r = x1r - x3i;
+        x0i = x1i + x3r;
+        a[j1] = wn4r * (x0r - x0i);
+        a[j1 + 1] = wn4r * (x0r + x0i);
+        x0r = x3i + x1r;
+        x0i = x3r - x1i;
+        a[j3] = wn4r * (x0i - x0r);
+        a[j3 + 1] = wn4r * (x0i + x0r);
+    }
+    ew = MM_PI_2 / n;
+    kr = 0;
+    m2 = 2 * m;
+    for (k = m2; k < n; k += m2) {
+        for (kj = n >> 2; kj > (kr ^= kj); kj >>= 1);
+        wk1r = cos(ew * kr);
+        wk1i = sin(ew * kr);
+        wk2r = 1 - 2 * wk1i * wk1i;
+        wk2i = 2 * wk1i * wk1r;
+        wk3r = wk1r - 2 * wk2i * wk1i;
+        wk3i = 2 * wk2i * wk1r - wk1i;
+        for (j = k; j < l + k; j += 2) {
+            j1 = j + l;
+            j2 = j1 + l;
+            j3 = j2 + l;
+            x0r = a[j] + a[j1];
+            x0i = a[j + 1] + a[j1 + 1];
+            x1r = a[j] - a[j1];
+            x1i = a[j + 1] - a[j1 + 1];
+            x2r = a[j2] + a[j3];
+            x2i = a[j2 + 1] + a[j3 + 1];
+            x3r = a[j2] - a[j3];
+            x3i = a[j2 + 1] - a[j3 + 1];
+            a[j] = x0r + x2r;
+            a[j + 1] = x0i + x2i;
+            x0r -= x2r;
+            x0i -= x2i;
+            a[j2] = wk2r * x0r - wk2i * x0i;
+            a[j2 + 1] = wk2r * x0i + wk2i * x0r;
+            x0r = x1r - x3i;
+            x0i = x1i + x3r;
+            a[j1] = wk1r * x0r - wk1i * x0i;
+            a[j1 + 1] = wk1r * x0i + wk1i * x0r;
+            x0r = x1r + x3i;
+            x0i = x1i - x3r;
+            a[j3] = wk3r * x0r - wk3i * x0i;
+            a[j3 + 1] = wk3r * x0i + wk3i * x0r;
+        }
+        x0r = wn4r * (wk1r - wk1i);
+        wk1i = wn4r * (wk1r + wk1i);
+        wk1r = x0r;
+        wk3r = wk1r - 2 * wk2r * wk1i;
+        wk3i = 2 * wk2r * wk1r - wk1i;
+        for (j = k + m; j < l + (k + m); j += 2) {
+            j1 = j + l;
+            j2 = j1 + l;
+            j3 = j2 + l;
+            x0r = a[j] + a[j1];
+            x0i = a[j + 1] + a[j1 + 1];
+            x1r = a[j] - a[j1];
+            x1i = a[j + 1] - a[j1 + 1];
+            x2r = a[j2] + a[j3];
+            x2i = a[j2 + 1] + a[j3 + 1];
+            x3r = a[j2] - a[j3];
+            x3i = a[j2 + 1] - a[j3 + 1];
+            a[j] = x0r + x2r;
+            a[j + 1] = x0i + x2i;
+            x0r -= x2r;
+            x0i -= x2i;
+            a[j2] = -wk2i * x0r - wk2r * x0i;
+            a[j2 + 1] = -wk2i * x0i + wk2r * x0r;
+            x0r = x1r - x3i;
+            x0i = x1i + x3r;
+            a[j1] = wk1r * x0r - wk1i * x0i;
+            a[j1 + 1] = wk1r * x0i + wk1i * x0r;
+            x0r = x1r + x3i;
+            x0i = x1i - x3r;
+            a[j3] = wk3r * x0r - wk3i * x0i;
+            a[j3 + 1] = wk3r * x0i + wk3i * x0r;
+        }
+    }
+}
+
+
+
+void 	M_rftfsub(int n, double *a)
+{
+    int i, i0, j, k;
+    double ec, w1r, w1i, wkr, wki, wdr, wdi, ss, xr, xi, yr, yi;
+    
+    ec = 2 * MM_PI_2 / n;
+    wkr = 0;
+    wki = 0;
+    wdi = cos(ec);
+    wdr = sin(ec);
+    wdi *= wdr;
+    wdr *= wdr;
+    w1r = 1 - 2 * wdr;
+    w1i = 2 * wdi;
+    ss = 2 * w1i;
+    i = n >> 1;
+    while (1) {
+        i0 = i - 4 * RDFT_LOOP_DIV;
+        if (i0 < 4) {
+            i0 = 4;
+        }
+        for (j = i - 4; j >= i0; j -= 4) {
+            k = n - j;
+            xr = a[j + 2] - a[k - 2];
+            xi = a[j + 3] + a[k - 1];
+            yr = wdr * xr - wdi * xi;
+            yi = wdr * xi + wdi * xr;
+            a[j + 2] -= yr;
+            a[j + 3] -= yi;
+            a[k - 2] += yr;
+            a[k - 1] -= yi;
+            wkr += ss * wdi;
+            wki += ss * (0.5 - wdr);
+            xr = a[j] - a[k];
+            xi = a[j + 1] + a[k + 1];
+            yr = wkr * xr - wki * xi;
+            yi = wkr * xi + wki * xr;
+            a[j] -= yr;
+            a[j + 1] -= yi;
+            a[k] += yr;
+            a[k + 1] -= yi;
+            wdr += ss * wki;
+            wdi += ss * (0.5 - wkr);
+        }
+        if (i0 == 4) {
+            break;
+        }
+        wkr = 0.5 * sin(ec * i0);
+        wki = 0.5 * cos(ec * i0);
+        wdr = 0.5 - (wkr * w1r - wki * w1i);
+        wdi = wkr * w1i + wki * w1r;
+        wkr = 0.5 - wkr;
+        i = i0;
+    }
+    xr = a[2] - a[n - 2];
+    xi = a[3] + a[n - 1];
+    yr = wdr * xr - wdi * xi;
+    yi = wdr * xi + wdi * xr;
+    a[2] -= yr;
+    a[3] -= yi;
+    a[n - 2] += yr;
+    a[n - 1] -= yi;
+}
+
+
+
+void 	M_rftbsub(int n, double *a)
+{
+    int i, i0, j, k;
+    double ec, w1r, w1i, wkr, wki, wdr, wdi, ss, xr, xi, yr, yi;
+    
+    ec = 2 * MM_PI_2 / n;
+    wkr = 0;
+    wki = 0;
+    wdi = cos(ec);
+    wdr = sin(ec);
+    wdi *= wdr;
+    wdr *= wdr;
+    w1r = 1 - 2 * wdr;
+    w1i = 2 * wdi;
+    ss = 2 * w1i;
+    i = n >> 1;
+    a[i + 1] = -a[i + 1];
+    while (1) {
+        i0 = i - 4 * RDFT_LOOP_DIV;
+        if (i0 < 4) {
+            i0 = 4;
+        }
+        for (j = i - 4; j >= i0; j -= 4) {
+            k = n - j;
+            xr = a[j + 2] - a[k - 2];
+            xi = a[j + 3] + a[k - 1];
+            yr = wdr * xr + wdi * xi;
+            yi = wdr * xi - wdi * xr;
+            a[j + 2] -= yr;
+            a[j + 3] = yi - a[j + 3];
+            a[k - 2] += yr;
+            a[k - 1] = yi - a[k - 1];
+            wkr += ss * wdi;
+            wki += ss * (0.5 - wdr);
+            xr = a[j] - a[k];
+            xi = a[j + 1] + a[k + 1];
+            yr = wkr * xr + wki * xi;
+            yi = wkr * xi - wki * xr;
+            a[j] -= yr;
+            a[j + 1] = yi - a[j + 1];
+            a[k] += yr;
+            a[k + 1] = yi - a[k + 1];
+            wdr += ss * wki;
+            wdi += ss * (0.5 - wkr);
+        }
+        if (i0 == 4) {
+            break;
+        }
+        wkr = 0.5 * sin(ec * i0);
+        wki = 0.5 * cos(ec * i0);
+        wdr = 0.5 - (wkr * w1r - wki * w1i);
+        wdi = wkr * w1i + wki * w1r;
+        wkr = 0.5 - wkr;
+        i = i0;
+    }
+    xr = a[2] - a[n - 2];
+    xi = a[3] + a[n - 1];
+    yr = wdr * xr + wdi * xi;
+    yi = wdr * xi - wdi * xr;
+    a[2] -= yr;
+    a[3] = yi - a[3];
+    a[n - 2] += yr;
+    a[n - 1] = yi - a[n - 1];
+    a[1] = -a[1];
+}
+

+ 132 - 0
mapm/src/mapm_flr.c

@@ -0,0 +1,132 @@
+
+/* 
+ *  M_APM  -  mapm_flr.c
+ *
+ *  Copyright (C) 2001 - 2007   Michael C. Ring
+ *
+ *  Permission to use, copy, and distribute this software and its
+ *  documentation for any purpose with or without fee is hereby granted,
+ *  provided that the above copyright notice appear in all copies and
+ *  that both that copyright notice and this permission notice appear
+ *  in supporting documentation.
+ *
+ *  Permission to modify the software is granted. Permission to distribute
+ *  the modified code is granted. Modifications are to be distributed by
+ *  using the file 'license.txt' as a template to modify the file header.
+ *  'license.txt' is available in the official MAPM distribution.
+ *
+ *  This software is provided "as is" without express or implied warranty.
+ */
+
+/*
+ *      $Id: mapm_flr.c,v 1.4 2007/12/03 01:39:12 mike Exp $
+ *
+ *      This file contains the floor and ceil functions
+ *
+ *      $Log: mapm_flr.c,v $
+ *      Revision 1.4  2007/12/03 01:39:12  mike
+ *      Update license
+ *
+ *      Revision 1.3  2002/11/05 23:25:30  mike
+ *      use new set_to_zero function instead of copy
+ *
+ *      Revision 1.2  2002/11/03 21:47:43  mike
+ *      Updated function parameters to use the modern style
+ *
+ *      Revision 1.1  2001/03/25 20:53:29  mike
+ *      Initial revision
+ */
+
+#include "m_apm_lc.h"
+
+/*
+ *      input    floor    ceil
+ *	-----	------	 ------
+ *      329.0    329.0    329.0
+ *     -837.0   -837.0   -837.0
+ *	372.64   372.0    373.0
+ *     -237.52  -238.0   -237.0
+ */
+
+/****************************************************************************/
+/* 
+ *      return the nearest integer <= input
+ */
+void	m_apm_floor(M_APM bb, M_APM aa)
+{
+M_APM	mtmp;
+
+m_apm_copy(bb, aa);
+
+if (m_apm_is_integer(bb))          /* if integer, we're done */
+  return;
+
+if (bb->m_apm_exponent <= 0)       /* if |bb| < 1, result is -1 or 0 */
+  {
+   if (bb->m_apm_sign < 0)
+     m_apm_negate(bb, MM_One);
+   else
+     M_set_to_zero(bb);
+
+   return;
+  }
+
+if (bb->m_apm_sign < 0)
+  {
+   mtmp = M_get_stack_var();
+   m_apm_negate(mtmp, bb);
+
+   mtmp->m_apm_datalength = mtmp->m_apm_exponent;
+   M_apm_normalize(mtmp);
+
+   m_apm_add(bb, mtmp, MM_One);
+   bb->m_apm_sign = -1;
+   M_restore_stack(1);
+  }
+else
+  {
+   bb->m_apm_datalength = bb->m_apm_exponent;
+   M_apm_normalize(bb);
+  }
+}
+/****************************************************************************/
+/* 
+ *      return the nearest integer >= input
+ */
+void	m_apm_ceil(M_APM bb, M_APM aa)
+{
+M_APM	mtmp;
+
+m_apm_copy(bb, aa);
+
+if (m_apm_is_integer(bb))          /* if integer, we're done */
+  return;
+
+if (bb->m_apm_exponent <= 0)       /* if |bb| < 1, result is 0 or 1 */
+  {
+   if (bb->m_apm_sign < 0)
+     M_set_to_zero(bb);
+   else
+     m_apm_copy(bb, MM_One);
+
+   return;
+  }
+
+if (bb->m_apm_sign < 0)
+  {
+   bb->m_apm_datalength = bb->m_apm_exponent;
+   M_apm_normalize(bb);
+  }
+else
+  {
+   mtmp = M_get_stack_var();
+   m_apm_copy(mtmp, bb);
+
+   mtmp->m_apm_datalength = mtmp->m_apm_exponent;
+   M_apm_normalize(mtmp);
+
+   m_apm_add(bb, mtmp, MM_One);
+   M_restore_stack(1);
+  }
+}
+/****************************************************************************/

+ 444 - 0
mapm/src/mapm_fpf.c

@@ -0,0 +1,444 @@
+
+/* 
+ *  M_APM  -  mapm_fpf.c
+ *
+ *  Copyright (C) 2001 - 2007   Michael C. Ring
+ *
+ *  Permission to use, copy, and distribute this software and its
+ *  documentation for any purpose with or without fee is hereby granted,
+ *  provided that the above copyright notice appear in all copies and
+ *  that both that copyright notice and this permission notice appear
+ *  in supporting documentation.
+ *
+ *  Permission to modify the software is granted. Permission to distribute
+ *  the modified code is granted. Modifications are to be distributed by
+ *  using the file 'license.txt' as a template to modify the file header.
+ *  'license.txt' is available in the official MAPM distribution.
+ *
+ *  This software is provided "as is" without express or implied warranty.
+ */
+
+/*
+ *      $Id: mapm_fpf.c,v 1.10 2007/12/03 01:39:57 mike Exp $
+ *
+ *      This file contains the Fixed Point Formatting functions
+ *
+ *      $Log: mapm_fpf.c,v $
+ *      Revision 1.10  2007/12/03 01:39:57  mike
+ *      Update license
+ *
+ *      Revision 1.9  2003/07/21 20:15:12  mike
+ *      Modify error messages to be in a consistent format.
+ *
+ *      Revision 1.8  2003/03/31 22:11:14  mike
+ *      call generic error handling function
+ *
+ *      Revision 1.7  2002/11/05 23:31:00  mike
+ *      use new set_to_zero call instead of copy
+ *
+ *      Revision 1.6  2002/11/03 22:33:24  mike
+ *      Updated function parameters to use the modern style
+ *
+ *      Revision 1.5  2002/02/14 19:31:44  mike
+ *      eliminate need for conditional compile
+ *
+ *      Revision 1.4  2001/08/26 22:35:50  mike
+ *      no LCC conditional needed on fixpt_string
+ *
+ *      Revision 1.3  2001/08/26 22:11:10  mike
+ *      add new 'stringexp' function
+ *
+ *      Revision 1.2  2001/08/25 22:30:09  mike
+ *      fix LCC-WIN32 compile problem
+ *
+ *      Revision 1.1  2001/08/25 16:50:59  mike
+ *      Initial revision
+ */
+
+#include "m_apm_lc.h"
+#include <ctype.h>
+
+/****************************************************************************/
+char	*m_apm_to_fixpt_stringexp(int dplaces, M_APM atmp, 
+				  char ch_radx, char ch_sep, int ct_sep)
+{
+int	places, xp, dl, ii;
+char	*cpr;
+
+places = dplaces;
+
+dl = atmp->m_apm_datalength;
+xp = atmp->m_apm_exponent;
+
+if (places < 0)				/* show ALL digits */
+  {
+   if (xp < 0)
+      ii = dl - xp;
+   else
+     {
+      if (dl > xp)
+        ii = dl;
+      else
+        ii = xp;
+     }
+  }
+else
+  {
+   ii = places;
+      
+   if (xp > 0)
+     ii += xp;
+  }
+
+if (ct_sep != 0 && ch_sep != 0 && xp > 0)
+  ii += xp / ct_sep;
+
+if ((cpr = (char *)MAPM_MALLOC((ii + 32) * sizeof(char))) == NULL)
+  return(NULL);
+
+m_apm_to_fixpt_stringex(cpr,places,atmp,ch_radx,ch_sep,ct_sep);
+
+return(cpr);
+}
+/****************************************************************************/
+void	m_apm_to_fixpt_stringex(char *s, int dplaces, M_APM atmp, 
+				char ch_radix, char ch_sep, int count_sep)
+{
+M_APM   btmp;
+char    ch, *cpd, *cps;
+int	ii, jj, kk, ct, dl, xp, no_sep_flg, places;
+
+btmp       = M_get_stack_var();
+places     = dplaces;
+cpd        = s;
+no_sep_flg = FALSE;
+
+m_apm_absolute_value(btmp, atmp);	/* do conversion of positive number */
+
+if (ch_sep == 0 || count_sep == 0)	/* no separator char OR count */
+  no_sep_flg = TRUE;
+
+/* determine how much memory to get for the temp string */
+
+dl = btmp->m_apm_datalength;
+xp = btmp->m_apm_exponent;
+
+if (places < 0)				/* show ALL digits */
+  {
+   if (xp < 0)
+      ii = dl - xp;
+   else
+     {
+      if (dl > xp)
+        ii = dl;
+      else
+        ii = xp;
+     }
+  }
+else
+  {
+   ii = places;
+      
+   if (xp > 0)
+     ii += xp;
+  }
+
+if ((cps = (char *)MAPM_MALLOC((ii + 32) * sizeof(char))) == NULL)
+  {
+   /* fatal, this does not return */
+
+   M_apm_log_error_msg(M_APM_FATAL, 
+                       "\'m_apm_to_fixpt_stringex\', Out of memory");
+  }
+
+m_apm_to_fixpt_string(cps, places, btmp);
+
+/*
+ *  the converted string may be all 'zero', 0.0000...
+ *  if so and the original number is negative,
+ *  do NOT set the '-' sign of our output string.
+ */
+
+if (atmp->m_apm_sign == -1)		/* if input number negative */
+  {
+   kk = 0;
+   jj = 0;
+
+   while (TRUE)
+     {
+      ch = cps[kk++];
+      if ((ch == '\0') || (jj != 0))
+        break;
+
+      if (isdigit((int)ch))
+        {
+	 if (ch != '0')
+	   jj = 1;
+	}
+     }
+
+   if (jj)
+     *cpd++ = '-';
+  }
+
+ct = M_strposition(cps, ".");      /* find the default (.) radix char */
+
+if (ct == -1)			   /* if not found .. */
+  {
+   strcat(cps, ".");               /* add one */
+   ct = M_strposition(cps, ".");   /* and then find it */
+  }
+
+if (places == 0)		   /* int format, terminate at radix char */
+  cps[ct] = '\0';
+else
+  cps[ct] = ch_radix;		   /* assign the radix char */
+
+/*
+ *  if the number is small enough to not have any separator char's ...
+ */
+
+if (ct <= count_sep)
+  no_sep_flg = TRUE;
+
+if (no_sep_flg)
+  {
+   strcpy(cpd, cps);
+  }
+else
+  {
+   jj = 0;
+   kk = count_sep;
+   ii = ct / count_sep;
+
+   if ((ii = ct - ii * count_sep) == 0)
+     ii = count_sep;
+
+   while (TRUE)				/* write out the first 1,2  */
+     {					/* (up to count_sep) digits */
+      *cpd++ = cps[jj++];
+
+      if (--ii == 0)
+        break;
+     }
+
+   while (TRUE)				/* write rest of the string   */
+     {
+      if (kk == count_sep)		/* write a new separator char */
+        {
+	 if (jj != ct)			/* unless we're at the radix  */
+	   {
+            *cpd++ = ch_sep;		/* note that this also disables */
+	    kk = 0;			/* the separator char AFTER     */
+	   }				/* the radix char               */
+	}
+
+      if ((*cpd++ = cps[jj++]) == '\0')
+        break;
+
+      kk++;
+     }
+  }
+
+MAPM_FREE(cps);
+M_restore_stack(1);
+}
+/****************************************************************************/
+void	m_apm_to_fixpt_string(char *ss, int dplaces, M_APM mtmp)
+{
+M_APM   ctmp;
+void	*vp;
+int	places, i2, ii, jj, kk, xp, dl, numb;
+UCHAR   *ucp, numdiv, numrem;
+char	*cpw, *cpd, sbuf[128];
+
+ctmp   = M_get_stack_var();
+vp     = NULL;
+cpd    = ss;
+places = dplaces;
+
+/* just want integer portion if places == 0 */
+
+if (places == 0)
+  {
+   if (mtmp->m_apm_sign >= 0)
+     m_apm_add(ctmp, mtmp, MM_0_5);
+   else
+     m_apm_subtract(ctmp, mtmp, MM_0_5);
+
+   m_apm_to_integer_string(cpd, ctmp);
+
+   M_restore_stack(1);
+   return;
+  }
+
+if (places > 0)
+  M_apm_round_fixpt(ctmp, places, mtmp);
+else
+  m_apm_copy(ctmp, mtmp);	  /* show ALL digits */
+
+if (ctmp->m_apm_sign == 0)        /* result is 0 */
+  {
+   if (places < 0)
+     {
+      cpd[0] = '0';		  /* "0.0" */
+      cpd[1] = '.';
+      cpd[2] = '0';
+      cpd[3] = '\0';
+     }
+   else
+     {
+      memset(cpd, '0', (places + 2));	/* pre-load string with all '0' */
+      cpd[1] = '.';
+      cpd[places + 2] = '\0';
+     }
+
+   M_restore_stack(1);
+   return;
+  }
+
+xp   = ctmp->m_apm_exponent;
+dl   = ctmp->m_apm_datalength;
+numb = (dl + 1) >> 1;
+
+if (places < 0)
+  {
+   if (dl > xp)
+     jj = dl + 16;
+   else
+     jj = xp + 16;
+  }
+else
+  {
+   jj = places + 16;
+   
+   if (xp > 0)
+     jj += xp;
+  }
+
+if (jj > 112)
+  {
+   if ((vp = (void *)MAPM_MALLOC((jj + 16) * sizeof(char))) == NULL)
+     {
+      /* fatal, this does not return */
+
+      M_apm_log_error_msg(M_APM_FATAL, 
+                          "\'m_apm_to_fixpt_string\', Out of memory");
+     }
+
+   cpw = (char *)vp;
+  }
+else
+  {
+   cpw = sbuf;
+  }
+
+/*
+ *  at this point, the number is non-zero and the the output
+ *  string will contain at least 1 significant digit.
+ */
+
+if (ctmp->m_apm_sign == -1) 	  /* negative number */
+  {
+   *cpd++ = '-';
+  }
+
+ucp = ctmp->m_apm_data;
+ii  = 0;
+
+/* convert MAPM num to ASCII digits and store in working char array */
+
+while (TRUE)
+  {
+   M_get_div_rem_10((int)(*ucp++), &numdiv, &numrem);
+
+   cpw[ii++] = numdiv + '0';
+   cpw[ii++] = numrem + '0';
+
+   if (--numb == 0)
+     break;
+  }
+
+i2 = ii;		/* save for later */
+
+if (places < 0)		/* show ALL digits */
+  {
+   places = dl - xp;
+
+   if (places < 1)
+     places = 1;
+  }
+
+/* pad with trailing zeros if needed */
+
+kk = xp + places + 2 - ii;
+
+if (kk > 0)
+  memset(&cpw[ii], '0', kk);
+
+if (xp > 0)          /* |num| >= 1, NO lead-in "0.nnn" */
+  {
+   ii = xp + places + 1;
+   jj = 0;
+
+   for (kk=0; kk < ii; kk++)
+     {
+      if (kk == xp)
+        cpd[jj++] = '.';
+
+      cpd[jj++] = cpw[kk];
+     }
+
+   cpd[ii] = '\0';
+  }
+else			/* |num| < 1, have lead-in "0.nnn" */
+  {
+   jj = 2 - xp;
+   ii = 2 + places;
+   memset(cpd, '0', (ii + 1));	/* pre-load string with all '0' */
+   cpd[1] = '.';		/* assign decimal point */
+
+   for (kk=0; kk < i2; kk++)
+     {
+      cpd[jj++] = cpw[kk];
+     }
+
+   cpd[ii] = '\0';
+  }
+
+if (vp != NULL)
+  MAPM_FREE(vp);
+
+M_restore_stack(1);
+}
+/****************************************************************************/
+void	M_apm_round_fixpt(M_APM btmp, int places, M_APM atmp)
+{
+int	xp, ii;
+
+xp = atmp->m_apm_exponent;
+ii = xp + places - 1;
+
+M_set_to_zero(btmp); /* assume number is too small so the net result is 0 */
+
+if (ii >= 0)
+  {
+   m_apm_round(btmp, ii, atmp);
+  }
+else
+  {
+   if (ii == -1)	/* next digit is significant which may round up */
+     {
+      if (atmp->m_apm_data[0] >= 50)	/* digit >= 5, round up */
+        {
+         m_apm_copy(btmp, atmp);
+	 btmp->m_apm_data[0] = 10;
+	 btmp->m_apm_exponent += 1;
+	 btmp->m_apm_datalength = 1;
+	 M_apm_normalize(btmp);
+	}
+     }
+  }
+}
+/****************************************************************************/
+

+ 284 - 0
mapm/src/mapm_gcd.c

@@ -0,0 +1,284 @@
+
+/* 
+ *  M_APM  -  mapm_gcd.c
+ *
+ *  Copyright (C) 2001 - 2007   Michael C. Ring
+ *
+ *  Permission to use, copy, and distribute this software and its
+ *  documentation for any purpose with or without fee is hereby granted,
+ *  provided that the above copyright notice appear in all copies and
+ *  that both that copyright notice and this permission notice appear
+ *  in supporting documentation.
+ *
+ *  Permission to modify the software is granted. Permission to distribute
+ *  the modified code is granted. Modifications are to be distributed by
+ *  using the file 'license.txt' as a template to modify the file header.
+ *  'license.txt' is available in the official MAPM distribution.
+ *
+ *  This software is provided "as is" without express or implied warranty.
+ */
+
+/*
+ *      $Id: mapm_gcd.c,v 1.8 2007/12/03 01:41:05 mike Exp $
+ *
+ *      This file contains the GCD and LCM functions
+ *
+ *      $Log: mapm_gcd.c,v $
+ *      Revision 1.8  2007/12/03 01:41:05  mike
+ *      Update license
+ *
+ *      Revision 1.7  2003/07/21 20:16:43  mike
+ *      Modify error messages to be in a consistent format.
+ *
+ *      Revision 1.6  2003/03/31 22:12:33  mike
+ *      call generic error handling function
+ *
+ *      Revision 1.5  2002/11/03 22:44:21  mike
+ *      Updated function parameters to use the modern style
+ *
+ *      Revision 1.4  2002/05/17 22:17:47  mike
+ *      fix comment
+ *
+ *      Revision 1.3  2002/05/17 22:16:36  mike
+ *      move even/odd util functions to mapmutl2
+ *
+ *      Revision 1.2  2001/07/15 20:55:20  mike
+ *      add comments
+ *
+ *      Revision 1.1  2001/07/15 20:48:27  mike
+ *      Initial revision
+ */
+
+#include "m_apm_lc.h"
+
+/****************************************************************************/
+/*
+ *      From Knuth, The Art of Computer Programming: 
+ *
+ *	This is the binary GCD algorithm as described
+ *	in the book (Algorithm B)
+ */
+void	m_apm_gcd(M_APM r, M_APM u, M_APM v)
+{
+M_APM   tmpM, tmpN, tmpT, tmpU, tmpV;
+int	kk, kr, mm;
+long    pow_2;
+
+/* 'is_integer' will return 0 || 1 */
+
+if ((m_apm_is_integer(u) + m_apm_is_integer(v)) != 2)
+  {
+   M_apm_log_error_msg(M_APM_RETURN, "\'m_apm_gcd\', Non-integer input");
+
+   M_set_to_zero(r);
+   return;
+  }
+
+if (u->m_apm_sign == 0)
+  {
+   m_apm_absolute_value(r, v);
+   return;
+  }
+
+if (v->m_apm_sign == 0)
+  {
+   m_apm_absolute_value(r, u);
+   return;
+  }
+
+tmpM = M_get_stack_var();
+tmpN = M_get_stack_var();
+tmpT = M_get_stack_var();
+tmpU = M_get_stack_var();
+tmpV = M_get_stack_var();
+
+m_apm_absolute_value(tmpU, u);
+m_apm_absolute_value(tmpV, v);
+
+/* Step B1 */
+
+kk = 0;
+
+while (TRUE)
+  {
+   mm = 1;
+   if (m_apm_is_odd(tmpU))
+     break;
+
+   mm = 0;
+   if (m_apm_is_odd(tmpV))
+     break;
+
+   m_apm_multiply(tmpN, MM_0_5, tmpU);
+   m_apm_copy(tmpU, tmpN);
+
+   m_apm_multiply(tmpN, MM_0_5, tmpV);
+   m_apm_copy(tmpV, tmpN);
+
+   kk++;
+  }
+
+/* Step B2 */
+
+if (mm)
+  {
+   m_apm_negate(tmpT, tmpV);
+   goto B4;
+  }
+
+m_apm_copy(tmpT, tmpU);
+
+/* Step: */
+
+B3:
+
+m_apm_multiply(tmpN, MM_0_5, tmpT);
+m_apm_copy(tmpT, tmpN);
+
+/* Step: */
+
+B4:
+
+if (m_apm_is_even(tmpT))
+  goto B3;
+
+/* Step B5 */
+
+if (tmpT->m_apm_sign == 1)
+  m_apm_copy(tmpU, tmpT);
+else
+  m_apm_negate(tmpV, tmpT);
+
+/* Step B6 */
+
+m_apm_subtract(tmpT, tmpU, tmpV);
+
+if (tmpT->m_apm_sign != 0)
+  goto B3;
+
+/*
+ *  result = U * 2 ^ kk
+ */
+
+if (kk == 0)
+   m_apm_copy(r, tmpU);
+else
+  {
+   if (kk == 1)
+     m_apm_multiply(r, tmpU, MM_Two);
+
+   if (kk == 2)
+     m_apm_multiply(r, tmpU, MM_Four);
+
+   if (kk >= 3)
+     {
+      mm = kk / 28;
+      kr = kk % 28;
+      pow_2 = 1L << kr;
+
+      if (mm == 0)
+        {
+	 m_apm_set_long(tmpN, pow_2);
+         m_apm_multiply(r, tmpU, tmpN);
+	}
+      else
+        {
+	 m_apm_copy(tmpN, MM_One);
+         m_apm_set_long(tmpM, 0x10000000L);   /* 2 ^ 28 */
+
+	 while (TRUE)
+	   {
+            m_apm_multiply(tmpT, tmpN, tmpM);
+            m_apm_copy(tmpN, tmpT);
+
+	    if (--mm == 0)
+	      break;
+	   }
+
+	 if (kr == 0)
+	   {
+            m_apm_multiply(r, tmpU, tmpN);
+	   }
+	 else
+	   {
+	    m_apm_set_long(tmpM, pow_2);
+            m_apm_multiply(tmpT, tmpN, tmpM);
+            m_apm_multiply(r, tmpU, tmpT);
+	   }
+	}
+     }
+  }
+
+M_restore_stack(5);
+}
+/****************************************************************************/
+/*
+ *                      u * v
+ *      LCM(u,v)  =  ------------
+ *                     GCD(u,v)
+ */
+
+void	m_apm_lcm(M_APM r, M_APM u, M_APM v)
+{
+M_APM   tmpN, tmpG;
+
+tmpN = M_get_stack_var();
+tmpG = M_get_stack_var();
+
+m_apm_multiply(tmpN, u, v);
+m_apm_gcd(tmpG, u, v);
+m_apm_integer_divide(r, tmpN, tmpG);
+
+M_restore_stack(2);
+}
+/****************************************************************************/
+
+#ifdef BIG_COMMENT_BLOCK
+
+/*
+ *      traditional GCD included for reference
+ *	(also useful for testing ...)
+ */
+
+/*
+ *      From Knuth, The Art of Computer Programming:
+ *
+ *      To compute GCD(u,v)
+ *          
+ *      A1:
+ *	    if (v == 0)  return (u)
+ *      A2:
+ *          t = u mod v
+ *	    u = v
+ *	    v = t
+ *	    goto A1
+ */
+void	m_apm_gcd_traditional(M_APM r, M_APM u, M_APM v)
+{
+M_APM   tmpD, tmpN, tmpU, tmpV;
+
+tmpD = M_get_stack_var();
+tmpN = M_get_stack_var();
+tmpU = M_get_stack_var();
+tmpV = M_get_stack_var();
+
+m_apm_absolute_value(tmpU, u);
+m_apm_absolute_value(tmpV, v);
+
+while (TRUE)
+  {
+   if (tmpV->m_apm_sign == 0)
+     break;
+
+   m_apm_integer_div_rem(tmpD, tmpN, tmpU, tmpV);
+   m_apm_copy(tmpU, tmpV);
+   m_apm_copy(tmpV, tmpN);
+  }
+
+m_apm_copy(r, tmpU);
+M_restore_stack(4);
+}
+/****************************************************************************/
+
+#endif
+

+ 180 - 0
mapm/src/mapm_lg2.c

@@ -0,0 +1,180 @@
+
+/* 
+ *  M_APM  -  mapm_lg2.c
+ *
+ *  Copyright (C) 2003 - 2007   Michael C. Ring
+ *
+ *  Permission to use, copy, and distribute this software and its
+ *  documentation for any purpose with or without fee is hereby granted,
+ *  provided that the above copyright notice appear in all copies and
+ *  that both that copyright notice and this permission notice appear
+ *  in supporting documentation.
+ *
+ *  Permission to modify the software is granted. Permission to distribute
+ *  the modified code is granted. Modifications are to be distributed by
+ *  using the file 'license.txt' as a template to modify the file header.
+ *  'license.txt' is available in the official MAPM distribution.
+ *
+ *  This software is provided "as is" without express or implied warranty.
+ */
+
+/*
+ *      $Id: mapm_lg2.c,v 1.9 2007/12/03 01:42:06 mike Exp $
+ *
+ *      This file contains the iterative function to compute the LOG
+ *	This is an internal function to the library and is not intended
+ *	to be called directly by the user.
+ *
+ *      $Log: mapm_lg2.c,v $
+ *      Revision 1.9  2007/12/03 01:42:06  mike
+ *      Update license
+ *
+ *      Revision 1.8  2003/05/12 17:52:15  mike
+ *      rearrange some logic
+ *
+ *      Revision 1.7  2003/05/03 11:24:51  mike
+ *      optimize decimal places
+ *
+ *      Revision 1.6  2003/05/01 21:58:27  mike
+ *      remove math.h
+ *
+ *      Revision 1.5  2003/05/01 20:53:38  mike
+ *      implement a new algorithm for log
+ *
+ *      Revision 1.4  2003/04/09 20:21:29  mike
+ *      fix rare corner condition by intentionally inducing a
+ *      10 ^ -5 error in the initial guess.
+ *
+ *      Revision 1.3  2003/03/31 22:13:15  mike
+ *      call generic error handling function
+ *
+ *      Revision 1.2  2003/03/30 21:27:22  mike
+ *      add comments
+ *
+ *      Revision 1.1  2003/03/30 21:18:07  mike
+ *      Initial revision
+ */
+
+#include "m_apm_lc.h"
+
+/****************************************************************************/
+
+/*
+ *      compute rr = log(nn)
+ *
+ *	input is assumed to not exceed the exponent range of a normal
+ *	'C' double ( |exponent| must be < 308)
+ */
+
+/****************************************************************************/
+void	M_log_solve_cubic(M_APM rr, int places, M_APM nn)
+{
+M_APM   tmp0, tmp1, tmp2, tmp3, guess;
+int	ii, maxp, tolerance, local_precision;
+
+guess = M_get_stack_var();
+tmp0  = M_get_stack_var();
+tmp1  = M_get_stack_var();
+tmp2  = M_get_stack_var();
+tmp3  = M_get_stack_var();
+
+M_get_log_guess(guess, nn);
+
+tolerance       = -(places + 4);
+maxp            = places + 16;
+local_precision = 18;
+
+/*    Use the following iteration to solve for log :
+
+                        exp(X) - N 
+      X     =  X - 2 * ------------
+       n+1              exp(X) + N 
+
+   
+      this is a cubically convergent algorithm 
+      (each iteration yields 3X more digits)
+*/
+
+ii = 0;
+
+while (TRUE)
+  {
+   m_apm_exp(tmp1, local_precision, guess);
+
+   m_apm_subtract(tmp3, tmp1, nn);
+   m_apm_add(tmp2, tmp1, nn);
+
+   m_apm_divide(tmp1, local_precision, tmp3, tmp2);
+   m_apm_multiply(tmp0, MM_Two, tmp1);
+   m_apm_subtract(tmp3, guess, tmp0);
+
+   if (ii != 0)
+     {
+      if (((3 * tmp0->m_apm_exponent) < tolerance) || (tmp0->m_apm_sign == 0))
+        break;
+     }
+
+   m_apm_round(guess, local_precision, tmp3);
+
+   local_precision *= 3;
+
+   if (local_precision > maxp)
+     local_precision = maxp;
+
+   ii = 1;
+  }
+
+m_apm_round(rr, places, tmp3);
+M_restore_stack(5);
+}
+/****************************************************************************/
+/*
+ *      find log(N)
+ *
+ *      if places < 360
+ *         solve with cubically convergent algorithm above
+ *
+ *      else
+ *
+ *      let 'X' be 'close' to the solution   (we use ~110 decimal places)
+ *
+ *      let Y = N * exp(-X) - 1
+ *
+ *	then
+ *
+ *	log(N) = X + log(1 + Y)
+ *
+ *      since 'Y' will be small, we can use the efficient log_near_1 algorithm.
+ *
+ */
+void	M_log_basic_iteration(M_APM rr, int places, M_APM nn)
+{
+M_APM   tmp0, tmp1, tmp2, tmpX;
+
+if (places < 360)
+  {
+   M_log_solve_cubic(rr, places, nn);
+  }
+else
+  {
+   tmp0 = M_get_stack_var();
+   tmp1 = M_get_stack_var();
+   tmp2 = M_get_stack_var();
+   tmpX = M_get_stack_var();
+   
+   M_log_solve_cubic(tmpX, 110, nn);
+   
+   m_apm_negate(tmp0, tmpX);
+   m_apm_exp(tmp1, (places + 8), tmp0);
+   m_apm_multiply(tmp2, tmp1, nn);
+   m_apm_subtract(tmp1, tmp2, MM_One);
+   
+   M_log_near_1(tmp0, (places - 104), tmp1);
+   
+   m_apm_add(tmp1, tmpX, tmp0);
+   m_apm_round(rr, places, tmp1);
+   
+   M_restore_stack(4);
+  }
+}
+/****************************************************************************/

+ 226 - 0
mapm/src/mapm_lg3.c

@@ -0,0 +1,226 @@
+
+/* 
+ *  M_APM  -  mapm_lg3.c
+ *
+ *  Copyright (C) 2003 - 2007   Michael C. Ring
+ *
+ *  Permission to use, copy, and distribute this software and its
+ *  documentation for any purpose with or without fee is hereby granted,
+ *  provided that the above copyright notice appear in all copies and
+ *  that both that copyright notice and this permission notice appear
+ *  in supporting documentation.
+ *
+ *  Permission to modify the software is granted. Permission to distribute
+ *  the modified code is granted. Modifications are to be distributed by
+ *  using the file 'license.txt' as a template to modify the file header.
+ *  'license.txt' is available in the official MAPM distribution.
+ *
+ *  This software is provided "as is" without express or implied warranty.
+ */
+
+/*
+ *      $Id: mapm_lg3.c,v 1.7 2007/12/03 01:42:59 mike Exp $
+ *
+ *      This file contains the function to compute log(2), log(10),
+ *	and 1/log(10) to the desired precision using an AGM algorithm.
+ *
+ *      $Log: mapm_lg3.c,v $
+ *      Revision 1.7  2007/12/03 01:42:59  mike
+ *      Update license
+ *
+ *      Revision 1.6  2003/12/09 01:25:06  mike
+ *      actually compute the first term of the AGM iteration instead
+ *      of assuming the inputs a=1 and b=10^-N.
+ *
+ *      Revision 1.5  2003/12/04 03:19:16  mike
+ *      rearrange logic in AGM to be more straight-forward
+ *
+ *      Revision 1.4  2003/05/01 22:04:37  mike
+ *      rearrange some code
+ *
+ *      Revision 1.3  2003/05/01 21:58:31  mike
+ *      remove math.h
+ *
+ *      Revision 1.2  2003/03/30 22:14:58  mike
+ *      add comments
+ *
+ *      Revision 1.1  2003/03/30 21:18:04  mike
+ *      Initial revision
+ */
+
+#include "m_apm_lc.h"
+
+/*
+ *  using the 'R' function (defined below) for 'N' decimal places :
+ *
+ *
+ *                          -N             -N
+ *  log(2)  =  R(1, 0.5 * 10  )  -  R(1, 10  ) 
+ *
+ *
+ *                          -N             -N
+ *  log(10) =  R(1, 0.1 * 10  )  -  R(1, 10  ) 
+ *
+ *
+ *  In general:
+ *
+ *                    -N                -N
+ *  log(x)  =  R(1, 10  / x)  -  R(1, 10  ) 
+ *
+ *
+ *  I found this on a web site which went into considerable detail
+ *  on the history of log(2). This formula is algebraically identical
+ *  to the formula specified in J. Borwein and P. Borwein's book 
+ *  "PI and the AGM". (reference algorithm 7.2)
+ */
+
+/****************************************************************************/
+/*
+ *	check if our local copy of log(2) & log(10) is precise
+ *      enough for our purpose. if not, calculate them so it's
+ *	as precise as desired, accurate to at least 'places'.
+ */
+void	M_check_log_places(int places)
+{
+M_APM   tmp6, tmp7, tmp8, tmp9;
+int     dplaces;
+
+dplaces = places + 4;
+
+if (dplaces > MM_lc_log_digits)
+  {
+   MM_lc_log_digits = dplaces + 4;
+   
+   tmp6 = M_get_stack_var();
+   tmp7 = M_get_stack_var();
+   tmp8 = M_get_stack_var();
+   tmp9 = M_get_stack_var();
+   
+   dplaces += 6 + (int)log10((double)places);
+   
+   m_apm_copy(tmp7, MM_One);
+   tmp7->m_apm_exponent = -places;
+   
+   M_log_AGM_R_func(tmp8, dplaces, MM_One, tmp7);
+   
+   m_apm_multiply(tmp6, tmp7, MM_0_5);
+   
+   M_log_AGM_R_func(tmp9, dplaces, MM_One, tmp6);
+   
+   m_apm_subtract(MM_lc_log2, tmp9, tmp8);               /* log(2) */
+
+   tmp7->m_apm_exponent -= 1;                            /* divide by 10 */
+
+   M_log_AGM_R_func(tmp9, dplaces, MM_One, tmp7);
+
+   m_apm_subtract(MM_lc_log10, tmp9, tmp8);              /* log(10) */
+   m_apm_reciprocal(MM_lc_log10R, dplaces, MM_lc_log10); /* 1 / log(10) */
+
+   M_restore_stack(4);
+  }
+}
+/****************************************************************************/
+
+/*
+ *	define a notation for a function 'R' :
+ *
+ *
+ *
+ *                                    1
+ *      R (a0, b0)  =  ------------------------------
+ *
+ *                          ----
+ *                           \ 
+ *                            \     n-1      2    2
+ *                      1  -   |   2    *  (a  - b )
+ *                            /              n    n
+ *                           /
+ *                          ----
+ *                         n >= 0
+ *
+ *
+ *      where a, b are the classic AGM iteration :
+ *
+ *     
+ *      a    =  0.5 * (a  + b )
+ *       n+1            n    n
+ *
+ *
+ *      b    =  sqrt(a  * b )
+ *       n+1          n    n
+ *
+ *
+ *
+ *      define a variable 'c' for more efficient computation :
+ *
+ *                                      2     2     2
+ *      c    =  0.5 * (a  - b )    ,   c  =  a  -  b
+ *       n+1            n    n          n     n     n
+ *
+ */
+
+/****************************************************************************/
+void	M_log_AGM_R_func(M_APM rr, int places, M_APM aa, M_APM bb)
+{
+M_APM   tmp1, tmp2, tmp3, tmp4, tmpC2, sum, pow_2, tmpA0, tmpB0;
+int	tolerance, dplaces;
+
+tmpA0 = M_get_stack_var();
+tmpB0 = M_get_stack_var();
+tmpC2 = M_get_stack_var();
+tmp1  = M_get_stack_var();
+tmp2  = M_get_stack_var();
+tmp3  = M_get_stack_var();
+tmp4  = M_get_stack_var();
+sum   = M_get_stack_var();
+pow_2 = M_get_stack_var();
+
+tolerance = places + 8;
+dplaces   = places + 16;
+
+m_apm_copy(tmpA0, aa);
+m_apm_copy(tmpB0, bb);
+m_apm_copy(pow_2, MM_0_5);
+
+m_apm_multiply(tmp1, aa, aa);		    /* 0.5 * [ a ^ 2 - b ^ 2 ] */
+m_apm_multiply(tmp2, bb, bb);
+m_apm_subtract(tmp3, tmp1, tmp2);
+m_apm_multiply(sum, MM_0_5, tmp3);
+
+while (TRUE)
+  {
+   m_apm_subtract(tmp1, tmpA0, tmpB0);      /* C n+1 = 0.5 * [ An - Bn ] */
+   m_apm_multiply(tmp4, MM_0_5, tmp1);      /* C n+1 */
+   m_apm_multiply(tmpC2, tmp4, tmp4);       /* C n+1 ^ 2 */
+
+   /* do the AGM */
+
+   m_apm_add(tmp1, tmpA0, tmpB0);
+   m_apm_multiply(tmp3, MM_0_5, tmp1);
+
+   m_apm_multiply(tmp2, tmpA0, tmpB0);
+   m_apm_sqrt(tmpB0, dplaces, tmp2);
+
+   m_apm_round(tmpA0, dplaces, tmp3);
+
+   /* end AGM */
+
+   m_apm_multiply(tmp2, MM_Two, pow_2);
+   m_apm_copy(pow_2, tmp2);
+
+   m_apm_multiply(tmp1, tmpC2, pow_2);
+   m_apm_add(tmp3, sum, tmp1);
+
+   if ((tmp1->m_apm_sign == 0) || 
+      ((-2 * tmp1->m_apm_exponent) > tolerance))
+     break;
+
+   m_apm_round(sum, dplaces, tmp3);
+  }
+
+m_apm_subtract(tmp4, MM_One, tmp3);
+m_apm_reciprocal(rr, places, tmp4);
+
+M_restore_stack(9);
+}
+/****************************************************************************/

+ 102 - 0
mapm/src/mapm_lg4.c

@@ -0,0 +1,102 @@
+
+/* 
+ *  M_APM  -  mapm_lg4.c
+ *
+ *  Copyright (C) 2003 - 2007   Michael C. Ring
+ *
+ *  Permission to use, copy, and distribute this software and its
+ *  documentation for any purpose with or without fee is hereby granted,
+ *  provided that the above copyright notice appear in all copies and
+ *  that both that copyright notice and this permission notice appear
+ *  in supporting documentation.
+ *
+ *  Permission to modify the software is granted. Permission to distribute
+ *  the modified code is granted. Modifications are to be distributed by
+ *  using the file 'license.txt' as a template to modify the file header.
+ *  'license.txt' is available in the official MAPM distribution.
+ *
+ *  This software is provided "as is" without express or implied warranty.
+ */
+
+/*
+ *      $Id: mapm_lg4.c,v 1.3 2007/12/03 01:43:32 mike Exp $
+ *
+ *      This file contains the LOG_NEAR_1 function.
+ *
+ *      $Log: mapm_lg4.c,v $
+ *      Revision 1.3  2007/12/03 01:43:32  mike
+ *      Update license
+ *
+ *      Revision 1.2  2003/06/02 18:08:45  mike
+ *      tweak decimal places and add comments
+ *
+ *      Revision 1.1  2003/06/02 17:27:26  mike
+ *      Initial revision
+ */
+
+#include "m_apm_lc.h"
+
+/****************************************************************************/
+/*
+	calculate log (1 + x) with the following series:
+
+              x
+	y = -----      ( |y| < 1 )
+	    x + 2
+
+
+            [ 1 + y ]                 y^3     y^5     y^7
+	log [-------]  =  2 * [ y  +  ---  +  ---  +  ---  ... ] 
+            [ 1 - y ]                  3       5       7 
+
+*/
+void	M_log_near_1(M_APM rr, int places, M_APM xx)
+{
+M_APM   tmp0, tmp1, tmp2, tmpS, term;
+int	tolerance, dplaces, local_precision;
+long    m1;
+
+tmp0 = M_get_stack_var();
+tmp1 = M_get_stack_var();
+tmp2 = M_get_stack_var();
+tmpS = M_get_stack_var();
+term = M_get_stack_var();
+
+tolerance = xx->m_apm_exponent - (places + 6);
+dplaces   = (places + 12) - xx->m_apm_exponent;
+
+m_apm_add(tmp0, xx, MM_Two);
+m_apm_divide(tmpS, (dplaces + 6), xx, tmp0);
+
+m_apm_copy(term, tmpS);
+m_apm_multiply(tmp0, tmpS, tmpS);
+m_apm_round(tmp2, (dplaces + 6), tmp0);
+
+m1 = 3L;
+
+while (TRUE)
+  {
+   m_apm_multiply(tmp0, term, tmp2);
+
+   if ((tmp0->m_apm_exponent < tolerance) || (tmp0->m_apm_sign == 0))
+     break;
+
+   local_precision = dplaces + tmp0->m_apm_exponent;
+
+   if (local_precision < 20)
+     local_precision = 20;
+
+   m_apm_set_long(tmp1, m1);
+   m_apm_round(term, local_precision, tmp0);
+   m_apm_divide(tmp0, local_precision, term, tmp1);
+   m_apm_add(tmp1, tmpS, tmp0);
+   m_apm_copy(tmpS, tmp1);
+   m1 += 2;
+  }
+
+m_apm_multiply(tmp0, MM_Two, tmpS);
+m_apm_round(rr, places, tmp0);
+
+M_restore_stack(5);                    /* restore the 5 locals we used here */
+}
+/****************************************************************************/

+ 229 - 0
mapm/src/mapm_log.c

@@ -0,0 +1,229 @@
+
+/* 
+ *  M_APM  -  mapm_log.c
+ *
+ *  Copyright (C) 1999 - 2007   Michael C. Ring
+ *
+ *  Permission to use, copy, and distribute this software and its
+ *  documentation for any purpose with or without fee is hereby granted,
+ *  provided that the above copyright notice appear in all copies and
+ *  that both that copyright notice and this permission notice appear
+ *  in supporting documentation.
+ *
+ *  Permission to modify the software is granted. Permission to distribute
+ *  the modified code is granted. Modifications are to be distributed by
+ *  using the file 'license.txt' as a template to modify the file header.
+ *  'license.txt' is available in the official MAPM distribution.
+ *
+ *  This software is provided "as is" without express or implied warranty.
+ */
+
+/*
+ *      $Id: mapm_log.c,v 1.29 2007/12/03 01:44:19 mike Exp $
+ *
+ *      This file contains the LOG and LOG10 functions.
+ *
+ *      $Log: mapm_log.c,v $
+ *      Revision 1.29  2007/12/03 01:44:19  mike
+ *      Update license
+ *
+ *      Revision 1.28  2003/07/21 20:18:06  mike
+ *      Modify error messages to be in a consistent format.
+ *
+ *      Revision 1.27  2003/06/02 17:22:46  mike
+ *      put 'log_near_1' into it's own separate module
+ *
+ *      Revision 1.26  2003/05/12 17:42:46  mike
+ *      only check for 'near 1' if exponent is 0 or 1
+ *
+ *      Revision 1.25  2003/05/04 21:08:25  mike
+ *      *** empty log message ***
+ *
+ *      Revision 1.24  2003/05/01 21:58:34  mike
+ *      remove math.h
+ *
+ *      Revision 1.23  2003/05/01 21:39:09  mike
+ *      use 'abs' call
+ *
+ *      Revision 1.22  2003/05/01 19:44:57  mike
+ *      optimize log_near_1 by calculating fewer digits
+ *      on subsequent iterations
+ *
+ *      Revision 1.21  2003/03/31 22:00:56  mike
+ *      call generic error handling function
+ *
+ *      Revision 1.20  2003/03/30 22:57:13  mike
+ *      call a new iterative log function which is cubically convergent
+ *
+ *      Revision 1.19  2002/11/03 22:14:45  mike
+ *      Updated function parameters to use the modern style
+ *
+ *      Revision 1.18  2001/07/16 19:21:16  mike
+ *      add function M_free_all_log
+ *
+ *      Revision 1.17  2000/10/22 00:24:29  mike
+ *      minor optimization
+ *
+ *      Revision 1.16  2000/10/21 16:22:50  mike
+ *      use an improved log_near_1 algorithm
+ *
+ *      Revision 1.15  2000/10/20 16:49:33  mike
+ *      update algorithm for basic log function and add new
+ *      function when input is close to '1'
+ *
+ *      Revision 1.14  2000/09/23 19:48:21  mike
+ *      change divide call to reciprocal
+ *
+ *      Revision 1.13  2000/07/11 18:58:35  mike
+ *      do it right this time
+ *
+ *      Revision 1.12  2000/07/11 18:19:27  mike
+ *      estimate a better initial precision
+ *
+ *      Revision 1.11  2000/05/19 16:14:15  mike
+ *      update some comments
+ *
+ *      Revision 1.10  2000/05/17 23:47:35  mike
+ *      recompute a local copy of log E base 10 on the fly
+ *      if more precision is needed.
+ *
+ *      Revision 1.9  2000/03/27 21:44:12  mike
+ *      determine how many iterations should be required at
+ *      run time for log
+ *
+ *      Revision 1.8  1999/07/21 02:56:18  mike
+ *      added some comments
+ *
+ *      Revision 1.7  1999/07/19 00:28:51  mike
+ *      adjust local precision again
+ *
+ *      Revision 1.6  1999/07/19 00:10:34  mike
+ *      adjust local precision during iterative loop
+ *
+ *      Revision 1.5  1999/07/18 23:15:54  mike
+ *      change local precision dynamically and change
+ *      tolerance to integers for faster iterative routine.
+ *
+ *      Revision 1.4  1999/06/19 21:08:32  mike
+ *      changed local static variables to MAPM stack variables
+ *
+ *      Revision 1.3  1999/05/15 01:34:50  mike
+ *      add check for number of decimal places
+ *
+ *      Revision 1.2  1999/05/10 21:42:32  mike
+ *      added some comments
+ *
+ *      Revision 1.1  1999/05/10 20:56:31  mike
+ *      Initial revision
+ */
+
+#include "m_apm_lc.h"
+
+/****************************************************************************/
+/*
+        Calls the LOG function. The formula used is :
+
+        log10(x)  =  A * log(x) where A = log  (e)  [0.43429448190325...]
+                                             10
+*/
+void	m_apm_log10(M_APM rr, int places, M_APM aa)
+{
+int     dplaces;
+M_APM   tmp8, tmp9;
+
+tmp8 = M_get_stack_var();
+tmp9 = M_get_stack_var();
+
+dplaces = places + 4;
+M_check_log_places(dplaces + 45);
+
+m_apm_log(tmp9, dplaces, aa);
+m_apm_multiply(tmp8, tmp9, MM_lc_log10R);
+m_apm_round(rr, places, tmp8);
+M_restore_stack(2);                    /* restore the 2 locals we used here */
+}
+/****************************************************************************/
+void	m_apm_log(M_APM r, int places, M_APM a)
+{
+M_APM   tmp0, tmp1, tmp2;
+int	mexp, dplaces;
+
+if (a->m_apm_sign <= 0)
+  {
+   M_apm_log_error_msg(M_APM_RETURN, "\'m_apm_log\', Negative argument");
+   M_set_to_zero(r);
+   return;
+  }
+
+tmp0 = M_get_stack_var();
+tmp1 = M_get_stack_var();
+tmp2 = M_get_stack_var();
+
+dplaces = places + 8;
+
+/*
+ *    if the input is real close to 1, use the series expansion
+ *    to compute the log.
+ *    
+ *    0.9999 < a < 1.0001
+ */
+
+mexp = a->m_apm_exponent;
+
+if (mexp == 0 || mexp == 1)
+  {
+   m_apm_subtract(tmp0, a, MM_One);
+   
+   if (tmp0->m_apm_sign == 0)    /* is input exactly 1 ?? */
+     {                           /* if so, result is 0    */
+      M_set_to_zero(r);
+      M_restore_stack(3);   
+      return;
+     }
+   
+   if (tmp0->m_apm_exponent <= -4)
+     {
+      M_log_near_1(r, places, tmp0);
+      M_restore_stack(3);   
+      return;
+     }
+  }
+
+/* make sure our log(10) is accurate enough for this calculation */
+/* (and log(2) which is called from M_log_basic_iteration) */
+
+M_check_log_places(dplaces + 25);
+
+if (abs(mexp) <= 3)
+  {
+   M_log_basic_iteration(r, places, a);
+  }
+else
+  {
+   /*
+    *  use log (x * y) = log(x) + log(y)
+    *
+    *  here we use y = exponent of our base 10 number.
+    *
+    *  let 'C' = log(10) = 2.3025850929940....
+    *
+    *  then log(x * y) = log(x) + ( C * base_10_exponent )
+    */
+
+   m_apm_copy(tmp2, a);
+   
+   mexp = tmp2->m_apm_exponent - 2;
+   tmp2->m_apm_exponent = 2;              /* force number between 10 & 100 */
+   
+   M_log_basic_iteration(tmp0, dplaces, tmp2);
+   
+   m_apm_set_long(tmp1, (long)mexp);
+   m_apm_multiply(tmp2, tmp1, MM_lc_log10);
+   m_apm_add(tmp1, tmp2, tmp0);
+   
+   m_apm_round(r, places, tmp1);
+  }
+
+M_restore_stack(3);                    /* restore the 3 locals we used here */
+}
+/****************************************************************************/

+ 182 - 0
mapm/src/mapm_mul.c

@@ -0,0 +1,182 @@
+
+/* 
+ *  M_APM  -  mapm_mul.c
+ *
+ *  Copyright (C) 1999 - 2007   Michael C. Ring
+ *
+ *  Permission to use, copy, and distribute this software and its
+ *  documentation for any purpose with or without fee is hereby granted,
+ *  provided that the above copyright notice appear in all copies and
+ *  that both that copyright notice and this permission notice appear
+ *  in supporting documentation.
+ *
+ *  Permission to modify the software is granted. Permission to distribute
+ *  the modified code is granted. Modifications are to be distributed by
+ *  using the file 'license.txt' as a template to modify the file header.
+ *  'license.txt' is available in the official MAPM distribution.
+ *
+ *  This software is provided "as is" without express or implied warranty.
+ */
+
+/*
+ *      $Id: mapm_mul.c,v 1.16 2007/12/03 01:45:27 mike Exp $
+ *
+ *      This file contains basic multiplication function.
+ *
+ *      $Log: mapm_mul.c,v $
+ *      Revision 1.16  2007/12/03 01:45:27  mike
+ *      Update license
+ *
+ *      Revision 1.15  2004/02/21 04:30:35  mike
+ *      minor optimization by using pointers instead of array indexes.
+ *
+ *      Revision 1.14  2003/07/21 20:18:59  mike
+ *      Modify error messages to be in a consistent format.
+ *
+ *      Revision 1.13  2003/03/31 22:14:05  mike
+ *      call generic error handling function
+ *
+ *      Revision 1.12  2002/11/03 22:25:36  mike
+ *      Updated function parameters to use the modern style
+ *
+ *      Revision 1.11  2001/07/24 18:24:26  mike
+ *      access div/rem lookup table directly
+ *      for speed
+ *
+ *      Revision 1.10  2001/02/11 22:31:39  mike
+ *      modify parameters to REALLOC
+ *
+ *      Revision 1.9  2000/07/09 00:20:03  mike
+ *      change break even point again ....
+ *
+ *      Revision 1.8  2000/07/08 18:51:43  mike
+ *      change break even point between this O(n^2)
+ *      multiply and the FFT multiply
+ *
+ *      Revision 1.7  2000/04/14 16:27:45  mike
+ *      change the break even point between the 2 multiply
+ *      functions since we made the fast one even faster.
+ *
+ *      Revision 1.6  2000/02/03 22:46:40  mike
+ *      use MAPM_* generic memory function
+ *
+ *      Revision 1.5  1999/09/19 21:10:14  mike
+ *      change the break even point between the 2 multiply choices
+ *
+ *      Revision 1.4  1999/08/09 23:57:17  mike
+ *      added more comments
+ *
+ *      Revision 1.3  1999/08/09 02:38:17  mike
+ *      tweak break even point and add comments
+ *
+ *      Revision 1.2  1999/08/08 18:35:20  mike
+ *      add call to fast algorithm if input numbers are large
+ *
+ *      Revision 1.1  1999/05/10 20:56:31  mike
+ *      Initial revision
+ */
+
+#include "m_apm_lc.h"
+
+extern void M_fast_multiply(M_APM, M_APM, M_APM);
+
+/****************************************************************************/
+void	m_apm_multiply(M_APM r, M_APM a, M_APM b)
+{
+int	ai, itmp, sign, nexp, ii, jj, indexa, indexb, index0, numdigits;
+UCHAR   *cp, *cpr, *cp_div, *cp_rem;
+void	*vp;
+
+sign = a->m_apm_sign * b->m_apm_sign;
+nexp = a->m_apm_exponent + b->m_apm_exponent;
+
+if (sign == 0)      /* one number is zero, result is zero */
+  {
+   M_set_to_zero(r);
+   return;
+  }
+
+numdigits = a->m_apm_datalength + b->m_apm_datalength;
+indexa = (a->m_apm_datalength + 1) >> 1;
+indexb = (b->m_apm_datalength + 1) >> 1;
+
+/* 
+ *	If we are multiplying 2 'big' numbers, use the fast algorithm.
+ *
+ *	This is a **very** approx break even point between this algorithm
+ *      and the FFT multiply. Note that different CPU's, operating systems,
+ *      and compiler's may yield a different break even point. This point
+ *      (~96 decimal digits) is how the test came out on the author's system.
+ */
+
+if (indexa >= 48 && indexb >= 48)
+  {
+   M_fast_multiply(r, a, b);
+   return;
+  }
+
+ii = (numdigits + 1) >> 1;     /* required size of result, in bytes */
+
+if (ii > r->m_apm_malloclength)
+  {
+   if ((vp = MAPM_REALLOC(r->m_apm_data, (ii + 32))) == NULL)
+     {
+      /* fatal, this does not return */
+
+      M_apm_log_error_msg(M_APM_FATAL, "\'m_apm_multiply\', Out of memory");
+     }
+  
+   r->m_apm_malloclength = ii + 28;
+   r->m_apm_data = (UCHAR *)vp;
+  }
+
+M_get_div_rem_addr(&cp_div, &cp_rem);
+
+index0 = indexa + indexb;
+cp = r->m_apm_data;
+memset(cp, 0, index0);
+ii = indexa;
+
+while (TRUE)
+  {
+   index0--;
+   cpr = cp + index0;
+   jj  = indexb;
+   ai  = (int)a->m_apm_data[--ii];
+
+   while (TRUE)
+     {
+      itmp = ai * b->m_apm_data[--jj];
+
+      *(cpr-1) += cp_div[itmp];
+      *cpr     += cp_rem[itmp];
+
+      if (*cpr >= 100)
+        {
+         *cpr     -= 100;
+         *(cpr-1) += 1;
+	}
+
+      cpr--;
+
+      if (*cpr >= 100)
+        {
+         *cpr     -= 100;
+         *(cpr-1) += 1;
+	}
+
+      if (jj == 0)
+        break;
+     }
+
+   if (ii == 0)
+     break;
+  }
+
+r->m_apm_sign       = sign;
+r->m_apm_exponent   = nexp;
+r->m_apm_datalength = numdigits;
+
+M_apm_normalize(r);
+}
+/****************************************************************************/

+ 178 - 0
mapm/src/mapm_pow.c

@@ -0,0 +1,178 @@
+
+/* 
+ *  M_APM  -  mapm_pow.c
+ *
+ *  Copyright (C) 2000 - 2007   Michael C. Ring
+ *
+ *  Permission to use, copy, and distribute this software and its
+ *  documentation for any purpose with or without fee is hereby granted,
+ *  provided that the above copyright notice appear in all copies and
+ *  that both that copyright notice and this permission notice appear
+ *  in supporting documentation.
+ *
+ *  Permission to modify the software is granted. Permission to distribute
+ *  the modified code is granted. Modifications are to be distributed by
+ *  using the file 'license.txt' as a template to modify the file header.
+ *  'license.txt' is available in the official MAPM distribution.
+ *
+ *  This software is provided "as is" without express or implied warranty.
+ */
+
+/*
+ *      $Id: mapm_pow.c,v 1.10 2007/12/03 01:46:07 mike Exp $
+ *
+ *      This file contains the POW function.
+ *
+ *      $Log: mapm_pow.c,v $
+ *      Revision 1.10  2007/12/03 01:46:07  mike
+ *      Update license
+ *
+ *      Revision 1.9  2002/11/05 23:39:42  mike
+ *      use new set_to_zero call
+ *
+ *      Revision 1.8  2002/11/03 22:20:59  mike
+ *      Updated function parameters to use the modern style
+ *
+ *      Revision 1.7  2001/07/16 19:24:26  mike
+ *      add function M_free_all_pow
+ *
+ *      Revision 1.6  2000/09/05 22:15:03  mike
+ *      minor tweak
+ *
+ *      Revision 1.5  2000/08/22 21:22:29  mike
+ *      if parameter yy is an integer, call the more
+ *      efficient _integer_pow function
+ *
+ *      Revision 1.4  2000/08/22 20:42:08  mike
+ *      compute more digits in the log calculation
+ *
+ *      Revision 1.3  2000/05/24 20:08:21  mike
+ *      update some comments
+ *
+ *      Revision 1.2  2000/05/23 23:20:11  mike
+ *      return 1 when input is 0^0. 
+ *
+ *      Revision 1.1  2000/05/18 22:10:43  mike
+ *      Initial revision
+ */
+
+#include "m_apm_lc.h"
+
+static	M_APM   M_last_xx_input;
+static	M_APM   M_last_xx_log;
+static	int     M_last_log_digits;
+static	int     M_size_flag = 0;
+
+/****************************************************************************/
+void	M_free_all_pow()
+{
+if (M_size_flag != 0)
+  {
+   m_apm_free(M_last_xx_input);
+   m_apm_free(M_last_xx_log);
+   M_size_flag = 0;
+  }
+}
+/****************************************************************************/
+/*
+	Calculate the POW function by calling EXP :
+
+                  Y      A                 
+                 X   =  e    where A = Y * log(X)
+*/
+void	m_apm_pow(M_APM rr, int places, M_APM xx, M_APM yy)
+{
+int	iflag, pflag;
+char    sbuf[64];
+M_APM   tmp8, tmp9;
+
+/* if yy == 0, return 1 */
+
+if (yy->m_apm_sign == 0)
+  {
+   m_apm_copy(rr, MM_One);
+   return;
+  }
+
+/* if xx == 0, return 0 */
+
+if (xx->m_apm_sign == 0)
+  {
+   M_set_to_zero(rr);
+   return;
+  }
+
+if (M_size_flag == 0)       /* init locals on first call */
+  {
+   M_size_flag       = M_get_sizeof_int();
+   M_last_log_digits = 0;
+   M_last_xx_input   = m_apm_init();
+   M_last_xx_log     = m_apm_init();
+  }
+
+/*
+ *  if 'yy' is a small enough integer, call the more
+ *  efficient _integer_pow function.
+ */
+
+if (m_apm_is_integer(yy))
+  {
+   iflag = FALSE;
+
+   if (M_size_flag == 2)            /* 16 bit compilers */
+     {
+      if (yy->m_apm_exponent <= 4)
+        iflag = TRUE;
+     }
+   else                             /* >= 32 bit compilers */
+     {
+      if (yy->m_apm_exponent <= 7)
+        iflag = TRUE;
+     }
+
+   if (iflag)
+     {
+      m_apm_to_integer_string(sbuf, yy);
+      m_apm_integer_pow(rr, places, xx, atoi(sbuf));
+      return;
+     }
+  }
+
+tmp8 = M_get_stack_var();
+tmp9 = M_get_stack_var();
+
+/*
+ *    If parameter 'X' is the same this call as it 
+ *    was the previous call, re-use the saved log 
+ *    calculation from last time.
+ */
+
+pflag = FALSE;
+
+if (M_last_log_digits >= places)
+  {
+   if (m_apm_compare(xx, M_last_xx_input) == 0)
+     pflag = TRUE;
+  }
+
+if (pflag)
+  {
+   m_apm_round(tmp9, (places + 8), M_last_xx_log);
+  }
+else
+  {
+   m_apm_log(tmp9, (places + 8), xx);
+
+   M_last_log_digits = places + 2;
+
+   /* save the 'X' input value and the log calculation */
+
+   m_apm_copy(M_last_xx_input, xx);
+   m_apm_copy(M_last_xx_log, tmp9);
+  }
+
+m_apm_multiply(tmp8, tmp9, yy);
+m_apm_exp(rr, places, tmp8);
+M_restore_stack(2);                    /* restore the 2 locals we used here */
+}
+/****************************************************************************/

+ 189 - 0
mapm/src/mapm_rcp.c

@@ -0,0 +1,189 @@
+
+/* 
+ *  M_APM  -  mapm_rcp.c
+ *
+ *  Copyright (C) 2000 - 2007   Michael C. Ring
+ *
+ *  Permission to use, copy, and distribute this software and its
+ *  documentation for any purpose with or without fee is hereby granted,
+ *  provided that the above copyright notice appear in all copies and
+ *  that both that copyright notice and this permission notice appear
+ *  in supporting documentation.
+ *
+ *  Permission to modify the software is granted. Permission to distribute
+ *  the modified code is granted. Modifications are to be distributed by
+ *  using the file 'license.txt' as a template to modify the file header.
+ *  'license.txt' is available in the official MAPM distribution.
+ *
+ *  This software is provided "as is" without express or implied warranty.
+ */
+
+/*
+ *      $Id: mapm_rcp.c,v 1.7 2007/12/03 01:46:46 mike Exp $
+ *
+ *      This file contains the fast division and reciprocal functions
+ *
+ *      $Log: mapm_rcp.c,v $
+ *      Revision 1.7  2007/12/03 01:46:46  mike
+ *      Update license
+ *
+ *      Revision 1.6  2003/07/21 20:20:17  mike
+ *      Modify error messages to be in a consistent format.
+ *
+ *      Revision 1.5  2003/05/01 21:58:40  mike
+ *      remove math.h
+ *
+ *      Revision 1.4  2003/03/31 22:15:49  mike
+ *      call generic error handling function
+ *
+ *      Revision 1.3  2002/11/03 21:32:09  mike
+ *      Updated function parameters to use the modern style
+ *
+ *      Revision 1.2  2000/09/26 16:27:48  mike
+ *      add some comments
+ *
+ *      Revision 1.1  2000/09/26 16:16:00  mike
+ *      Initial revision
+ */
+
+#include "m_apm_lc.h"
+
+/****************************************************************************/
+void	m_apm_divide(M_APM rr, int places, M_APM aa, M_APM bb)
+{
+M_APM   tmp0, tmp1;
+int     sn, nexp, dplaces;
+
+sn = aa->m_apm_sign * bb->m_apm_sign;
+
+if (sn == 0)                  /* one number is zero, result is zero */
+  {
+   if (bb->m_apm_sign == 0)
+     {
+      M_apm_log_error_msg(M_APM_RETURN, "\'m_apm_divide\', Divide by 0");
+     }
+
+   M_set_to_zero(rr);
+   return;
+  }
+
+/*
+ *    Use the original 'Knuth' method for smaller divides. On the
+ *    author's system, this was the *approx* break even point before
+ *    the reciprocal method used below became faster.
+ */
+
+if (places < 250)
+  {
+   M_apm_sdivide(rr, places, aa, bb);
+   return;
+  }
+
+/* mimic the decimal place behavior of the original divide */
+
+nexp = aa->m_apm_exponent - bb->m_apm_exponent;
+
+if (nexp > 0)
+  dplaces = nexp + places;
+else
+  dplaces = places;
+
+tmp0 = M_get_stack_var();
+tmp1 = M_get_stack_var();
+
+m_apm_reciprocal(tmp0, (dplaces + 8), bb);
+m_apm_multiply(tmp1, tmp0, aa);
+m_apm_round(rr, dplaces, tmp1);
+
+M_restore_stack(2);
+}
+/****************************************************************************/
+void	m_apm_reciprocal(M_APM rr, int places, M_APM aa)
+{
+M_APM   last_x, guess, tmpN, tmp1, tmp2;
+char    sbuf[32];
+int	ii, bflag, dplaces, nexp, tolerance;
+
+if (aa->m_apm_sign == 0)
+  {
+   M_apm_log_error_msg(M_APM_RETURN, "\'m_apm_reciprocal\', Input = 0");
+
+   M_set_to_zero(rr);
+   return;
+  }
+
+last_x = M_get_stack_var();
+guess  = M_get_stack_var();
+tmpN   = M_get_stack_var();
+tmp1   = M_get_stack_var();
+tmp2   = M_get_stack_var();
+
+m_apm_absolute_value(tmpN, aa);
+
+/* 
+    normalize the input number (make the exponent 0) so
+    the 'guess' below will not over/under flow on large
+    magnitude exponents.
+*/
+
+nexp = aa->m_apm_exponent;
+tmpN->m_apm_exponent -= nexp;
+
+m_apm_to_string(sbuf, 15, tmpN);
+m_apm_set_double(guess, (1.0 / atof(sbuf)));
+
+tolerance = places + 4;
+dplaces   = places + 16;
+bflag     = FALSE;
+
+m_apm_negate(last_x, MM_Ten);
+
+/*   Use the following iteration to calculate the reciprocal :
+
+
+         X     =  X  *  [ 2 - N * X ]
+          n+1
+*/
+
+ii = 0;
+
+while (TRUE)
+  {
+   m_apm_multiply(tmp1, tmpN, guess);
+   m_apm_subtract(tmp2, MM_Two, tmp1);
+   m_apm_multiply(tmp1, tmp2, guess);
+
+   if (bflag)
+     break;
+
+   m_apm_round(guess, dplaces, tmp1);
+
+   /* force at least 2 iterations so 'last_x' has valid data */
+
+   if (ii != 0)
+     {
+      m_apm_subtract(tmp2, guess, last_x);
+
+      if (tmp2->m_apm_sign == 0)
+        break;
+
+      /* 
+       *   if we are within a factor of 4 on the error term,
+       *   we will be accurate enough after the *next* iteration
+       *   is complete.
+       */
+
+      if ((-4 * tmp2->m_apm_exponent) > tolerance)
+        bflag = TRUE;
+     }
+
+   m_apm_copy(last_x, guess);
+   ii++;
+  }
+
+m_apm_round(rr, places, tmp1);
+rr->m_apm_exponent -= nexp;
+rr->m_apm_sign = aa->m_apm_sign;
+M_restore_stack(5);
+}
+/****************************************************************************/

+ 396 - 0
mapm/src/mapm_rnd.c

@@ -0,0 +1,396 @@
+
+/* 
+ *  M_APM  -  mapm_rnd.c
+ *
+ *  Copyright (C) 1999 - 2007   Michael C. Ring
+ *
+ *  Permission to use, copy, and distribute this software and its
+ *  documentation for any purpose with or without fee is hereby granted,
+ *  provided that the above copyright notice appear in all copies and
+ *  that both that copyright notice and this permission notice appear
+ *  in supporting documentation.
+ *
+ *  Permission to modify the software is granted. Permission to distribute
+ *  the modified code is granted. Modifications are to be distributed by
+ *  using the file 'license.txt' as a template to modify the file header.
+ *  'license.txt' is available in the official MAPM distribution.
+ *
+ *  This software is provided "as is" without express or implied warranty.
+ */
+
+/*
+ *      $Id: mapm_rnd.c,v 1.12 2007/12/03 01:47:17 mike Exp $
+ *
+ *      This file contains the Random Number Generator function.
+ *
+ *      $Log: mapm_rnd.c,v $
+ *      Revision 1.12  2007/12/03 01:47:17  mike
+ *      Update license
+ *
+ *      Revision 1.11  2003/10/25 22:55:43  mike
+ *      add support for National Instruments LabWindows CVI
+ *
+ *      Revision 1.10  2002/11/03 22:41:03  mike
+ *      Updated function parameters to use the modern style
+ *
+ *      Revision 1.9  2002/02/14 21:50:45  mike
+ *      add _set_random_seed
+ *
+ *      Revision 1.8  2001/07/16 19:30:32  mike
+ *      add function M_free_all_rnd
+ *
+ *      Revision 1.7  2001/03/20 17:19:45  mike
+ *      use a new multiplier
+ *
+ *      Revision 1.6  2000/08/20 23:46:07  mike
+ *      add more possible multupliers (no code changes)
+ *
+ *      Revision 1.5  1999/09/19 23:32:14  mike
+ *      added comments
+ *
+ *      Revision 1.4  1999/09/18 03:49:25  mike
+ *      *** empty log message ***
+ *
+ *      Revision 1.3  1999/09/18 03:35:36  mike
+ *      only prototype get_microsec for non-DOS
+ *
+ *      Revision 1.2  1999/09/18 02:35:36  mike
+ *      delete debug printf's
+ *
+ *      Revision 1.1  1999/09/18 02:26:52  mike
+ *      Initial revision
+ */
+
+#include "m_apm_lc.h"
+
+#ifndef _HAVE_NI_LABWIN_CVI_
+#ifdef MSDOS
+#include <time.h>
+#include <sys/timeb.h>
+#else
+#include <sys/time.h>
+extern  void	M_get_microsec(unsigned long *, long *);
+#endif
+#endif
+
+#ifdef _HAVE_NI_LABWIN_CVI_
+#include <time.h>
+#include <utility.h>
+#include <ansi/math.h>
+#endif
+
+extern  void	M_reverse_string(char *);
+extern  void    M_get_rnd_seed(M_APM);
+
+static	M_APM   M_rnd_aa;
+static  M_APM   M_rnd_mm;
+static  M_APM   M_rnd_XX;
+static  M_APM   M_rtmp0;
+static  M_APM   M_rtmp1;
+
+static  int     M_firsttime2 = TRUE;
+
+/*
+        Used Knuth's The Art of Computer Programming, Volume 2 as
+        the basis. Assuming the random number is X, compute
+	(where all the math is performed on integers) :
+
+	X = (a * X + c) MOD m
+
+	From Knuth:
+
+	'm' should be large, at least 2^30 : we use 1.0E+15
+
+	'a' should be between .01m and .99m and not have a simple
+	pattern. 'a' should not have any large factors in common 
+	with 'm' and (since 'm' is a power of 10) if 'a' MOD 200 
+	= 21 then all 'm' different possible values will be 
+	generated before 'X' starts to repeat.
+
+	We use 'a' = 716805947629621.
+
+	This is a prime number and also meets 'a' MOD 200 = 21. 
+	Commented out below are many potential multipliers that 
+	are all prime and meet 'a' MOD 200 = 21.
+
+	There are few restrictions on 'c' except 'c' can have no
+	factor in common with 'm', hence we set 'c' = 'a'.
+
+	On the first call, the system time is used to initialize X.
+*/
+
+/*
+ *  the following constants are all potential multipliers. they are
+ *  all prime numbers that also meet the criteria of NUM mod 200 = 21.
+ */
+
+/*
+439682071525421   439682071528421   439682071529221   439682071529821
+439682071530421   439682071532021   439682071538821   439682071539421
+439682071540021   439682071547021   439682071551221   439682071553821
+439682071555421   439682071557221   439682071558021   439682071558621
+439682071559821   439652381461621   439652381465221   439652381465621
+439652381466421   439652381467421   439652381468621   439652381470021
+439652381471221   439652381477021   439652381484221   439652381488421
+439652381491021   439652381492021   439652381494021   439652381496821
+617294387035621   617294387038621   617294387039221   617294387044421
+617294387045221   617294387048621   617294387051621   617294387051821
+617294387053621   617294387058421   617294387064221   617294387065621
+617294387068621   617294387069221   617294387069821   617294387070421
+617294387072021   617294387072621   617294387073821   617294387076821
+649378126517621   649378126517821   649378126518221   649378126520821
+649378126523821   649378126525621   649378126526621   649378126528421
+649378126529621   649378126530821   649378126532221   649378126533221
+649378126535221   649378126539421   649378126543621   649378126546021
+649378126546421   649378126549421   649378126550821   649378126555021
+649378126557421   649378126560221   649378126561621   649378126562021
+649378126564621   649378126565821   672091582360421   672091582364221
+672091582364621   672091582367021   672091582368421   672091582369021
+672091582370821   672091582371421   672091582376821   672091582380821
+716805243983221   716805243984821   716805947623621   716805947624621
+716805947629021   716805947629621   716805947630621   716805947633621
+716805947634221   716805947635021   716805947635621   716805947642221
+*/
+
+/****************************************************************************/
+void	M_free_all_rnd()
+{
+if (M_firsttime2 == FALSE)
+  {
+   m_apm_free(M_rnd_aa);
+   m_apm_free(M_rnd_mm);
+   m_apm_free(M_rnd_XX);
+   m_apm_free(M_rtmp0);
+   m_apm_free(M_rtmp1);
+
+   M_firsttime2 = TRUE;
+  }
+}
+/****************************************************************************/
+void	m_apm_set_random_seed(char *ss)
+{
+M_APM   btmp;
+
+if (M_firsttime2)
+  {
+   btmp = M_get_stack_var();
+   m_apm_get_random(btmp);
+   M_restore_stack(1);
+  }
+
+m_apm_set_string(M_rnd_XX, ss);
+}
+/****************************************************************************/
+/*
+ *  compute X = (a * X + c) MOD m       where c = a
+ */
+void	m_apm_get_random(M_APM mrnd)
+{
+
+if (M_firsttime2)         /* use the system time as the initial seed value */
+  {
+   M_firsttime2 = FALSE;
+   
+   M_rnd_aa = m_apm_init();
+   M_rnd_XX = m_apm_init();
+   M_rnd_mm = m_apm_init();
+   M_rtmp0  = m_apm_init();
+   M_rtmp1  = m_apm_init();
+
+   /* set the multiplier M_rnd_aa and M_rnd_mm */
+   
+   m_apm_set_string(M_rnd_aa, "716805947629621");
+   m_apm_set_string(M_rnd_mm, "1.0E15");
+
+   M_get_rnd_seed(M_rnd_XX);
+  }
+
+m_apm_multiply(M_rtmp0, M_rnd_XX, M_rnd_aa);
+m_apm_add(M_rtmp1, M_rtmp0, M_rnd_aa);
+m_apm_integer_div_rem(M_rtmp0, M_rnd_XX, M_rtmp1, M_rnd_mm);
+m_apm_copy(mrnd, M_rnd_XX);
+mrnd->m_apm_exponent -= 15;
+}
+/****************************************************************************/
+void	M_reverse_string(char *s)
+{
+int	ct;
+char	ch, *p1, *p2;
+
+if ((ct = strlen(s)) <= 1)
+  return;
+
+p1 = s;
+p2 = s + ct - 1;
+ct /= 2;
+
+while (TRUE)
+  {
+   ch    = *p1;
+   *p1++ = *p2;
+   *p2-- = ch;
+
+   if (--ct == 0)
+     break;
+  }
+}
+/****************************************************************************/
+
+#ifndef _HAVE_NI_LABWIN_CVI_
+
+#ifdef MSDOS
+
+/****************************************************************************/
+/*
+ *  for DOS / Win 9x/NT systems : use 'ftime' 
+ */
+void	M_get_rnd_seed(M_APM mm)
+{
+int              millisec;
+time_t 		 timestamp;
+unsigned long    ul;
+char             ss[32], buf1[48], buf2[32];
+struct timeb     timebuffer;
+M_APM		 atmp;
+
+atmp = M_get_stack_var();
+
+ftime(&timebuffer);
+
+millisec  = (int)timebuffer.millitm;    
+timestamp = timebuffer.time;
+ul        = (unsigned long)(timestamp / 7);
+ul       += timestamp + 537;
+strcpy(ss,ctime(&timestamp));        /* convert to string and copy to ss */
+
+sprintf(buf1,"%d",(millisec / 10));
+sprintf(buf2,"%lu",ul);
+
+ss[0] = ss[18];
+ss[1] = ss[17];
+ss[2] = ss[15];
+ss[3] = ss[14];
+ss[4] = ss[12];
+ss[5] = ss[11];
+ss[6] = ss[9];
+ss[7] = ss[23];
+ss[8] = ss[20];
+ss[9] = '\0';
+
+M_reverse_string(buf2);
+strcat(buf1,buf2);
+strcat(buf1,ss);
+
+m_apm_set_string(atmp, buf1);
+atmp->m_apm_exponent = 15;
+m_apm_integer_divide(mm, atmp, MM_One);
+
+M_restore_stack(1);
+}
+/****************************************************************************/
+
+#else
+
+/****************************************************************************/
+/*
+ *  for unix systems : use 'gettimeofday'
+ */
+void	M_get_rnd_seed(M_APM mm)
+{
+unsigned long    sec3;
+long             usec3;
+char             buf1[32], buf2[32];
+M_APM		 atmp;
+
+atmp = M_get_stack_var();
+M_get_microsec(&sec3,&usec3);
+
+sprintf(buf1,"%ld",usec3);
+sprintf(buf2,"%lu",sec3);
+M_reverse_string(buf2);
+strcat(buf1,buf2);
+
+m_apm_set_string(atmp, buf1);
+atmp->m_apm_exponent = 15;
+m_apm_integer_divide(mm, atmp, MM_One);
+
+M_restore_stack(1);
+}
+/****************************************************************************/
+void	 M_get_microsec(unsigned long *sec, long *usec)
+{
+struct timeval time_now;           /* current time for elapsed time check */
+struct timezone time_zone;         /* time zone for gettimeofday call     */
+
+gettimeofday(&time_now, &time_zone);                  /* get current time */
+
+*sec  = time_now.tv_sec;
+*usec = time_now.tv_usec;
+}
+/****************************************************************************/
+
+#endif
+#endif
+
+#ifdef _HAVE_NI_LABWIN_CVI_
+
+/****************************************************************************/
+/*
+ *  for National Instruments LabWindows CVI
+ */
+
+void	M_get_rnd_seed(M_APM mm)
+{
+double		 timer0;
+int		 millisec;
+char             *cvi_time, *cvi_date, buf1[64], buf2[32];
+M_APM		 atmp;
+
+atmp = M_get_stack_var();
+
+cvi_date = DateStr();
+cvi_time = TimeStr();
+timer0   = Timer();
+
+/*
+ *  note that Timer() is not syncronized to TimeStr(),
+ *  but we don't care here since we are just looking
+ *  for a random source of digits.
+ */
+
+millisec = (int)(0.01 + 1000.0 * (timer0 - floor(timer0)));
+
+sprintf(buf1, "%d", millisec);
+
+buf2[0]  = cvi_time[6];	/* time format: "HH:MM:SS" */
+buf2[1]  = cvi_time[7];
+buf2[2]  = cvi_time[3];
+buf2[3]  = cvi_time[4];
+buf2[4]  = cvi_time[0];
+buf2[5]  = cvi_time[1];
+
+buf2[6]  = cvi_date[3];	/* date format: "MM-DD-YYYY" */
+buf2[7]  = cvi_date[4];
+buf2[8]  = cvi_date[0];
+buf2[9]  = cvi_date[1];
+buf2[10] = cvi_date[8];
+buf2[11] = cvi_date[9];
+buf2[12] = cvi_date[7];
+
+buf2[13] = '4';
+buf2[14] = '7';
+buf2[15] = '\0';
+
+strcat(buf1, buf2);
+
+m_apm_set_string(atmp, buf1);
+atmp->m_apm_exponent = 15;
+m_apm_integer_divide(mm, atmp, MM_One);
+
+M_restore_stack(1);
+}
+
+#endif
+
+/****************************************************************************/
+

+ 412 - 0
mapm/src/mapm_set.c

@@ -0,0 +1,412 @@
+
+/* 
+ *  M_APM  -  mapm_set.c
+ *
+ *  Copyright (C) 1999 - 2007   Michael C. Ring
+ *
+ *  Permission to use, copy, and distribute this software and its
+ *  documentation for any purpose with or without fee is hereby granted,
+ *  provided that the above copyright notice appear in all copies and
+ *  that both that copyright notice and this permission notice appear
+ *  in supporting documentation.
+ *
+ *  Permission to modify the software is granted. Permission to distribute
+ *  the modified code is granted. Modifications are to be distributed by
+ *  using the file 'license.txt' as a template to modify the file header.
+ *  'license.txt' is available in the official MAPM distribution.
+ *
+ *  This software is provided "as is" without express or implied warranty.
+ */
+
+/*
+ *      $Id: mapm_set.c,v 1.18 2007/12/03 01:47:50 mike Exp $
+ *
+ *      This file contains the functions necessary to get C 'longs' and
+ *	'strings' into the MAPM number system. It also contains the function
+ *	to get a string from a MAPM number.
+ *
+ *      $Log: mapm_set.c,v $
+ *      Revision 1.18  2007/12/03 01:47:50  mike
+ *      Update license
+ *
+ *      Revision 1.17  2003/07/21 20:25:06  mike
+ *      Modify error messages to be in a consistent format.
+ *
+ *      Revision 1.16  2003/03/31 21:59:52  mike
+ *      call generic error handling function
+ *
+ *      Revision 1.15  2002/11/05 23:31:54  mike
+ *      use new set_to_zero call instead of copy
+ *
+ *      Revision 1.14  2002/11/03 22:24:19  mike
+ *      Updated function parameters to use the modern style
+ *
+ *      Revision 1.13  2001/07/16 19:34:16  mike
+ *      add function M_free_all_set
+ *
+ *      Revision 1.12  2001/02/11 22:33:27  mike
+ *      modify parameters to REALLOC
+ *
+ *      Revision 1.11  2001/01/23 21:16:03  mike
+ *      use dedicated call to long->ascii instead of sprintf
+ *
+ *      Revision 1.10  2000/10/25 22:57:25  mike
+ *      add cast which really wasn't needed
+ *
+ *      Revision 1.9  2000/10/25 19:57:01  mike
+ *      add free call to end of set string if the temp
+ *      string gets too big
+ *
+ *      Revision 1.8  2000/05/04 23:49:19  mike
+ *      put in more efficient set_long function
+ *
+ *      Revision 1.7  2000/02/03 22:47:15  mike
+ *      use MAPM_* generic memory function
+ *
+ *      Revision 1.6  1999/07/12 22:23:17  mike
+ *      tweak output string when input == 0
+ *
+ *      Revision 1.5  1999/07/12 02:07:56  mike
+ *      fix dec_places error (was == -1, should be < 0)
+ *
+ *      Revision 1.4  1999/06/19 21:36:57  mike
+ *      added some comments
+ *
+ *      Revision 1.3  1999/06/19 21:35:19  mike
+ *      changed local static variables to MAPM stack variables
+ *
+ *      Revision 1.2  1999/05/13 21:32:41  mike
+ *      added check for illegal chars in string parse
+ *
+ *      Revision 1.1  1999/05/10 20:56:31  mike
+ *      Initial revision
+ */
+
+#include "m_apm_lc.h"
+
+static	char *M_buf  = NULL;
+static  int   M_lbuf = 0;
+static  char *M_set_string_error_msg = "\'m_apm_set_string\', Out of memory";
+
+/****************************************************************************/
+void	M_free_all_set()
+{
+if (M_lbuf != 0)
+  {
+   MAPM_FREE(M_buf);
+   M_buf  = NULL;
+   M_lbuf = 0;
+  }
+}
+/****************************************************************************/
+void	m_apm_set_long(M_APM atmp, long mm)
+{
+int     len, ii, nbytes;
+char	*p, *buf, ch, buf2[64];
+
+/* if zero, return right away */
+
+if (mm == 0)
+  {
+   M_set_to_zero(atmp);
+   return;
+  }
+
+M_long_2_ascii(buf2, mm);     /* convert long -> ascii in base 10 */
+buf = buf2;
+
+if (mm < 0)
+  {
+   atmp->m_apm_sign = -1;
+   buf++;                     /* get past '-' sign */
+  }
+else
+  {
+   atmp->m_apm_sign = 1;
+  }
+
+len = strlen(buf);
+atmp->m_apm_exponent = len;
+
+/* least significant nibble of ODD data-length must be 0 */
+
+if ((len & 1) != 0)
+  {
+   buf[len] = '0';
+  }
+
+/* remove any trailing '0' ... */
+
+while (TRUE)
+  {
+   if (buf[--len] != '0')
+     break;
+  }
+
+atmp->m_apm_datalength = ++len;
+
+nbytes = (len + 1) >> 1;
+p = buf;
+
+for (ii=0; ii < nbytes; ii++)
+  {
+   ch = *p++ - '0';
+   atmp->m_apm_data[ii] = 10 * ch + *p++ - '0';
+  }
+}
+/****************************************************************************/
+void	m_apm_set_string(M_APM ctmp, char *s_in)
+{
+char	ch, *cp, *s, *p;
+void	*vp;
+int	i, j, zflag, exponent, sign;
+
+if (M_lbuf == 0)
+  {
+   M_lbuf = 256;
+   if ((M_buf = (char *)MAPM_MALLOC(256)) == NULL)
+     {
+      /* fatal, this does not return */
+
+      M_apm_log_error_msg(M_APM_FATAL, M_set_string_error_msg);
+     }
+  }
+
+if ((i = strlen(s_in)) > (M_lbuf - 4))
+  {
+   M_lbuf = i + 32;
+   if ((vp = MAPM_REALLOC(M_buf, M_lbuf)) == NULL)
+     {
+      /* fatal, this does not return */
+
+      M_apm_log_error_msg(M_APM_FATAL, M_set_string_error_msg);
+     }
+
+   M_buf = (char *)vp;
+  }
+
+s = M_buf;
+strcpy(s,s_in);
+
+/* default == zero ... */
+
+M_set_to_zero(ctmp);
+
+p = s;
+
+while (TRUE)
+  {
+   if (*p == ' ' || *p == '\t')
+     p++;
+   else
+     break;
+  }
+
+if (*p == '\0')
+  return;
+
+sign = 1;             /* assume number is positive */
+
+if (*p == '+')        /* scan by optional '+' sign */
+  p++;
+else
+  {
+   if (*p == '-')     /* check if number negative */
+     {
+      sign = -1;
+      p++;
+     }
+  }
+
+M_lowercase(p);       /* convert string to lowercase */
+exponent = 0;         /* default */
+   
+if ((cp = strstr(p,"e")) != NULL)
+  {
+   exponent = atoi(cp + sizeof(char));
+   *cp = '\0';          /* erase the exponent now */
+  }
+
+j = M_strposition(p,".");        /* is there a decimal point ?? */
+if (j == -1)
+  {
+   strcat(p,".");                /* if not, append one */
+   j = M_strposition(p,".");     /* now find it ... */
+  }
+
+if (j > 0)                       /* normalize number and adjust exponent */
+  {
+   exponent += j;
+   memmove((p+1),p,(j * sizeof(char)));
+  }
+
+p++;        /* scan past implied decimal point now in column 1 (index 0) */
+
+i = strlen(p);
+ctmp->m_apm_datalength = i;
+
+if ((i & 1) != 0)   /* if odd number of digits, append a '0' to make it even */
+  strcat(p,"0");    
+
+j = strlen(p) >> 1;  /* number of bytes in encoded M_APM number */
+
+/* do we need more memory to hold this number */
+
+if (j > ctmp->m_apm_malloclength)
+  {
+   if ((vp = MAPM_REALLOC(ctmp->m_apm_data, (j + 32))) == NULL)
+     {
+      /* fatal, this does not return */
+
+      M_apm_log_error_msg(M_APM_FATAL, M_set_string_error_msg);
+     }
+  
+   ctmp->m_apm_malloclength = j + 28;
+   ctmp->m_apm_data = (UCHAR *)vp;
+  }
+
+zflag = TRUE;
+
+for (i=0; i < j; i++)
+  {
+   ch = *p++ - '0';
+   if ((ch = (10 * ch + *p++ - '0')) != 0)
+     zflag = FALSE;
+
+   if (((int)ch & 0xFF) >= 100)
+     {
+      M_apm_log_error_msg(M_APM_RETURN,
+      "\'m_apm_set_string\', Non-digit char found in parse");
+
+      M_apm_log_error_msg(M_APM_RETURN, "Text =");
+      M_apm_log_error_msg(M_APM_RETURN, s_in);
+
+      M_set_to_zero(ctmp);
+      return;
+     }
+
+   ctmp->m_apm_data[i]   = ch;
+   ctmp->m_apm_data[i+1] = 0;
+  }
+
+ctmp->m_apm_exponent = exponent;
+ctmp->m_apm_sign     = sign;
+
+if (zflag)
+  {
+   ctmp->m_apm_exponent   = 0;
+   ctmp->m_apm_sign       = 0;
+   ctmp->m_apm_datalength = 1;
+  }
+else
+  {
+   M_apm_normalize(ctmp);
+  }
+
+/*
+ *  if our local temp string is getting too big,
+ *  release it's memory and start over next time.
+ *  (this 1000 byte threshold is quite arbitrary,
+ *  it may be more efficient in your app to make
+ *  this number bigger).
+ */
+
+if (M_lbuf > 1000)
+  {
+   MAPM_FREE(M_buf);
+   M_buf  = NULL;
+   M_lbuf = 0;
+  }
+}
+/****************************************************************************/
+void	m_apm_to_string(char *s, int places, M_APM mtmp)
+{
+M_APM   ctmp;
+char	*cp;
+int	i, index, first, max_i, num_digits, dec_places;
+UCHAR	numdiv, numrem;
+
+ctmp = M_get_stack_var();
+dec_places = places;
+
+if (dec_places < 0)
+  m_apm_copy(ctmp, mtmp);
+else
+  m_apm_round(ctmp, dec_places, mtmp);
+
+if (ctmp->m_apm_sign == 0)
+  {
+   if (dec_places < 0)
+      strcpy(s,"0.0E+0");
+   else
+     {
+      strcpy(s,"0");
+
+      if (dec_places > 0)
+        strcat(s,".");
+
+      for (i=0; i < dec_places; i++)
+        strcat(s,"0");
+
+      strcat(s,"E+0");
+     }
+
+   M_restore_stack(1);
+   return;
+  }
+
+max_i = (ctmp->m_apm_datalength + 1) >> 1;
+
+if (dec_places < 0)
+  num_digits = ctmp->m_apm_datalength;
+else
+  num_digits = dec_places + 1;
+
+cp = s;
+
+if (ctmp->m_apm_sign == -1)
+  *cp++ = '-';
+
+first = TRUE;
+
+i = 0;
+index = 0;
+
+while (TRUE)
+  {
+   if (index >= max_i)
+     {
+      numdiv = 0;
+      numrem = 0;
+     }
+   else
+      M_get_div_rem_10((int)ctmp->m_apm_data[index],&numdiv,&numrem);
+
+   index++;
+
+   *cp++ = numdiv + '0';
+
+   if (++i == num_digits)
+     break;
+
+   if (first)
+     {
+      first = FALSE;
+      *cp++ = '.';
+     }
+
+   *cp++ = numrem + '0';
+
+   if (++i == num_digits)
+     break;
+  }
+
+i = ctmp->m_apm_exponent - 1;
+if (i >= 0)
+  sprintf(cp,"E+%d",i);
+else
+  sprintf(cp,"E%d",i);
+
+M_restore_stack(1);
+}
+/****************************************************************************/

+ 193 - 0
mapm/src/mapm_sin.c

@@ -0,0 +1,193 @@
+
+/* 
+ *  M_APM  -  mapm_sin.c
+ *
+ *  Copyright (C) 1999 - 2007   Michael C. Ring
+ *
+ *  Permission to use, copy, and distribute this software and its
+ *  documentation for any purpose with or without fee is hereby granted,
+ *  provided that the above copyright notice appear in all copies and
+ *  that both that copyright notice and this permission notice appear
+ *  in supporting documentation.
+ *
+ *  Permission to modify the software is granted. Permission to distribute
+ *  the modified code is granted. Modifications are to be distributed by
+ *  using the file 'license.txt' as a template to modify the file header.
+ *  'license.txt' is available in the official MAPM distribution.
+ *
+ *  This software is provided "as is" without express or implied warranty.
+ */
+
+/*
+ *      $Id: mapm_sin.c,v 1.17 2007/12/03 01:48:31 mike Exp $
+ *
+ *      This file contains the top level (user callable) SIN / COS / TAN
+ *	functions.
+ *
+ *      $Log: mapm_sin.c,v $
+ *      Revision 1.17  2007/12/03 01:48:31  mike
+ *      Update license
+ *
+ *      Revision 1.16  2002/11/03 21:53:47  mike
+ *      Updated function parameters to use the modern style
+ *
+ *      Revision 1.15  2001/03/25 20:59:46  mike
+ *      move PI stuff to new file
+ *
+ *      Revision 1.14  2001/02/07 19:12:14  mike
+ *      eliminate MM_skip_limit_PI_check
+ *
+ *      Revision 1.13  2000/11/18 11:05:36  mike
+ *      minor code re-arrangement in PI AGM
+ *
+ *      Revision 1.12  2000/07/11 23:34:42  mike
+ *      adjust loop break-out for AGM PI algorithm
+ *
+ *      Revision 1.11  2000/07/11 20:19:47  mike
+ *      use new algorithm to compute PI (AGM)
+ *
+ *      Revision 1.10  2000/05/21 01:07:57  mike
+ *      use _sin_cos in _tan function
+ *
+ *      Revision 1.9  2000/05/19 17:13:56  mike
+ *      use local copies of PI variables & recompute
+ *      on the fly as needed
+ *
+ *      Revision 1.8  1999/09/21 21:03:06  mike
+ *      make sure the sign of 'sin' from M_cos_to_sin is non-zero
+ *      before assigning it from the original angle.
+ *
+ *      Revision 1.7  1999/09/18 03:27:27  mike
+ *      added m_apm_sin_cos
+ *
+ *      Revision 1.6  1999/07/09 22:50:33  mike
+ *      skip limit to PI when not needed
+ *
+ *      Revision 1.5  1999/06/20 23:42:29  mike
+ *      use new function for COS function
+ *
+ *      Revision 1.4  1999/06/20 19:27:12  mike
+ *      changed local static variables to MAPM stack variables
+ *
+ *      Revision 1.3  1999/05/17 03:54:56  mike
+ *      init globals in TAN function also
+ *
+ *      Revision 1.2  1999/05/15 02:18:31  mike
+ *      add check for number of decimal places
+ *
+ *      Revision 1.1  1999/05/10 20:56:31  mike
+ *      Initial revision
+ */
+
+#include "m_apm_lc.h"
+
+/****************************************************************************/
+void	m_apm_sin(M_APM r, int places, M_APM a)
+{
+M_APM	tmp3;
+
+tmp3 = M_get_stack_var();
+M_limit_angle_to_pi(tmp3, (places + 6), a);
+M_5x_sin(r, places, tmp3);
+M_restore_stack(1);
+}
+/****************************************************************************/
+void	m_apm_cos(M_APM r, int places, M_APM a)
+{
+M_APM	tmp3;
+
+tmp3 = M_get_stack_var();
+M_limit_angle_to_pi(tmp3, (places + 6), a);
+M_4x_cos(r, places, tmp3);
+M_restore_stack(1);
+}
+/****************************************************************************/
+void	m_apm_sin_cos(M_APM sinv, M_APM cosv, int places, M_APM aa)
+{
+M_APM	tmp5, tmp6, tmp7;
+
+tmp5 = M_get_stack_var();
+tmp6 = M_get_stack_var();
+tmp7 = M_get_stack_var();
+
+M_limit_angle_to_pi(tmp5, (places + 6), aa);
+M_4x_cos(tmp7, (places + 6), tmp5);
+
+/*
+ *   compute sin(x) = sqrt(1 - cos(x) ^ 2).
+ *
+ *   note that the sign of 'sin' will always be positive after the
+ *   sqrt call. we need to adjust the sign based on what quadrant
+ *   the original angle is in.
+ */
+
+M_cos_to_sin(tmp6, (places + 6), tmp7);
+if (tmp6->m_apm_sign != 0)
+  tmp6->m_apm_sign = tmp5->m_apm_sign;
+ 
+m_apm_round(sinv, places, tmp6);
+m_apm_round(cosv, places, tmp7);
+M_restore_stack(3);
+}
+/****************************************************************************/
+void	m_apm_tan(M_APM r, int places, M_APM a)
+{
+M_APM	tmps, tmpc, tmp0;
+
+tmps = M_get_stack_var();
+tmpc = M_get_stack_var();
+tmp0 = M_get_stack_var();
+
+m_apm_sin_cos(tmps, tmpc, (places + 4), a);
+ 
+/* tan(x) = sin(x) / cos(x) */
+
+m_apm_divide(tmp0, (places + 4), tmps, tmpc);
+m_apm_round(r, places, tmp0);
+M_restore_stack(3);
+}
+/****************************************************************************/
+void	M_limit_angle_to_pi(M_APM rr, int places, M_APM aa)
+{
+M_APM	tmp7, tmp8, tmp9;
+
+M_check_PI_places(places);
+
+tmp9 = M_get_stack_var();
+m_apm_copy(tmp9, MM_lc_PI);
+
+if (m_apm_compare(aa, tmp9) == 1)       /*  > PI  */
+  {
+   tmp7 = M_get_stack_var();
+   tmp8 = M_get_stack_var();
+
+   m_apm_add(tmp7, aa, tmp9);
+   m_apm_integer_divide(tmp9, tmp7, MM_lc_2_PI);
+   m_apm_multiply(tmp8, tmp9, MM_lc_2_PI);
+   m_apm_subtract(tmp9, aa, tmp8);
+   m_apm_round(rr, places, tmp9);
+
+   M_restore_stack(3);
+   return;
+  }
+
+tmp9->m_apm_sign = -1;
+if (m_apm_compare(aa, tmp9) == -1)       /*  < -PI  */
+  {
+   tmp7 = M_get_stack_var();
+   tmp8 = M_get_stack_var();
+
+   m_apm_add(tmp7, aa, tmp9);
+   m_apm_integer_divide(tmp9, tmp7, MM_lc_2_PI);
+   m_apm_multiply(tmp8, tmp9, MM_lc_2_PI);
+   m_apm_subtract(tmp9, aa, tmp8);
+   m_apm_round(rr, places, tmp9);
+
+   M_restore_stack(3);
+   return;
+  }
+
+m_apm_copy(rr, aa);
+M_restore_stack(1);
+}
+/****************************************************************************/

+ 520 - 0
mapm/src/mapmasin.c

@@ -0,0 +1,520 @@
+
+/* 
+ *  M_APM  -  mapmasin.c
+ *
+ *  Copyright (C) 1999 - 2007   Michael C. Ring
+ *
+ *  Permission to use, copy, and distribute this software and its
+ *  documentation for any purpose with or without fee is hereby granted,
+ *  provided that the above copyright notice appear in all copies and
+ *  that both that copyright notice and this permission notice appear
+ *  in supporting documentation.
+ *
+ *  Permission to modify the software is granted. Permission to distribute
+ *  the modified code is granted. Modifications are to be distributed by
+ *  using the file 'license.txt' as a template to modify the file header.
+ *  'license.txt' is available in the official MAPM distribution.
+ *
+ *  This software is provided "as is" without express or implied warranty.
+ */
+
+/*
+ *      $Id: mapmasin.c,v 1.28 2007/12/03 01:49:10 mike Exp $
+ *
+ *      This file contains the 'ARC' family of functions; ARC-SIN, ARC-COS,
+ *	ARC-TAN, and ARC-TAN2.
+ *
+ *      $Log: mapmasin.c,v $
+ *      Revision 1.28  2007/12/03 01:49:10  mike
+ *      Update license
+ *
+ *      Revision 1.27  2003/07/24 16:34:02  mike
+ *      update arctan_large_input
+ *
+ *      Revision 1.26  2003/07/21 20:27:48  mike
+ *      Modify error messages to be in a consistent format.
+ *
+ *      Revision 1.25  2003/07/21 19:19:26  mike
+ *      add new arctan with large input value
+ *
+ *      Revision 1.24  2003/05/01 21:58:49  mike
+ *      remove math.h
+ *
+ *      Revision 1.23  2003/04/09 21:43:00  mike
+ *      optimize iterative asin & acos with lessons learned
+ *      from the new log function
+ *
+ *      Revision 1.22  2003/03/31 21:58:11  mike
+ *      call generic error handling function
+ *
+ *      Revision 1.21  2002/11/03 21:41:54  mike
+ *      Updated function parameters to use the modern style
+ *
+ *      Revision 1.20  2001/02/07 19:07:07  mike
+ *      eliminate MM_skip_limit_PI_check
+ *
+ *      Revision 1.19  2001/02/06 21:50:56  mike
+ *      don't display accuracy when iteration count maxes out
+ *
+ *      Revision 1.18  2000/12/02 20:10:09  mike
+ *      add calls to more efficient functions if
+ *      the input args are close to zero
+ *
+ *      Revision 1.17  2000/09/05 22:18:02  mike
+ *      re-arrange code to eliminate goto from atan2
+ *
+ *      Revision 1.16  2000/05/28 23:58:41  mike
+ *      minor optimization to arc-tan2
+ *
+ *      Revision 1.15  2000/05/19 17:13:29  mike
+ *      use local copies of PI variables & recompute
+ *      on the fly as needed
+ *
+ *      Revision 1.14  2000/03/27 21:43:23  mike
+ *      dtermine how many iterations should be required at
+ *      run time for arc-sin and arc-cos
+ *
+ *      Revision 1.13  1999/09/21 21:00:33  mike
+ *      make sure the sign of 'sin' from M_cos_to_sin is non-zero
+ *      before assigning it from the original angle.
+ *
+ *      Revision 1.12  1999/07/21 03:05:06  mike
+ *      added some comments
+ *
+ *      Revision 1.11  1999/07/19 02:33:39  mike
+ *      reset local precision again
+ *
+ *      Revision 1.10  1999/07/19 02:18:05  mike
+ *      more fine tuning of local precision
+ *
+ *      Revision 1.9  1999/07/19 00:08:34  mike
+ *      adjust local precision during iterative loops
+ *
+ *      Revision 1.8  1999/07/18 22:35:56  mike
+ *      make arc-sin and arc-cos use dynamically changing
+ *      precision to speed up iterative routines for large N
+ *
+ *      Revision 1.7  1999/07/09 22:52:00  mike
+ *      skip limit PI check when not needed
+ *
+ *      Revision 1.6  1999/07/09 00:10:39  mike
+ *      use better method for arc sin and arc cos
+ *
+ *      Revision 1.5  1999/07/08 22:56:20  mike
+ *      replace local MAPM constant with a global
+ *
+ *      Revision 1.4  1999/06/20 16:55:01  mike
+ *      changed local static variables to MAPM stack variables
+ *
+ *      Revision 1.3  1999/05/15 02:10:27  mike
+ *      add check for number of decimal places
+ *
+ *      Revision 1.2  1999/05/10 21:10:21  mike
+ *      added some comments
+ *
+ *      Revision 1.1  1999/05/10 20:56:31  mike
+ *      Initial revision
+ */
+
+#include "m_apm_lc.h"
+
+/****************************************************************************/
+void	m_apm_arctan2(M_APM rr, int places, M_APM yy, M_APM xx)
+{
+M_APM   tmp5, tmp6, tmp7;
+int	ix, iy;
+
+iy = yy->m_apm_sign;
+ix = xx->m_apm_sign;
+
+if (ix == 0)       /* x == 0 */
+  {
+   if (iy == 0)    /* y == 0 */
+     {
+      M_apm_log_error_msg(M_APM_RETURN, "\'m_apm_arctan2\', Both Inputs = 0");
+      M_set_to_zero(rr);
+      return;
+     }
+
+   M_check_PI_places(places);
+   m_apm_round(rr, places, MM_lc_HALF_PI);
+   rr->m_apm_sign = iy;
+   return;
+  }
+
+if (iy == 0)
+  {
+   if (ix == 1)
+     {
+      M_set_to_zero(rr);
+     }
+   else
+     {
+      M_check_PI_places(places);
+      m_apm_round(rr, places, MM_lc_PI);
+     } 
+
+   return;
+  }
+
+/*
+ *    the special cases have been handled, now do the real work
+ */
+
+tmp5 = M_get_stack_var();
+tmp6 = M_get_stack_var();
+tmp7 = M_get_stack_var();
+
+m_apm_divide(tmp6, (places + 6), yy, xx);
+m_apm_arctan(tmp5, (places + 6), tmp6);
+
+if (ix == 1)         /* 'x' is positive */
+  {
+   m_apm_round(rr, places, tmp5);
+  }
+else                 /* 'x' is negative */
+  {
+   M_check_PI_places(places);
+
+   if (iy == 1)      /* 'y' is positive */
+     {
+      m_apm_add(tmp7, tmp5, MM_lc_PI);
+      m_apm_round(rr, places, tmp7);
+     }
+   else              /* 'y' is negative */
+     {
+      m_apm_subtract(tmp7, tmp5, MM_lc_PI);
+      m_apm_round(rr, places, tmp7);
+     }
+  }
+
+M_restore_stack(3);
+}
+/****************************************************************************/
+/*
+        Calculate arctan using the identity :
+
+                                      x
+        arctan (x) == arcsin [ --------------- ]
+                                sqrt(1 + x^2)
+
+*/
+void	m_apm_arctan(M_APM rr, int places, M_APM xx)
+{
+M_APM   tmp8, tmp9;
+
+if (xx->m_apm_sign == 0)			/* input == 0 ?? */
+  {
+   M_set_to_zero(rr);
+   return;
+  }
+
+if (xx->m_apm_exponent <= -4)			/* input close to 0 ?? */
+  {
+   M_arctan_near_0(rr, places, xx);
+   return;
+  }
+
+if (xx->m_apm_exponent >= 4)			/* large input */
+  {
+   M_arctan_large_input(rr, places, xx);
+   return;
+  }
+
+tmp8 = M_get_stack_var();
+tmp9 = M_get_stack_var();
+
+m_apm_multiply(tmp9, xx, xx);
+m_apm_add(tmp8, tmp9, MM_One);
+m_apm_sqrt(tmp9, (places + 6), tmp8);
+m_apm_divide(tmp8, (places + 6), xx, tmp9);
+m_apm_arcsin(rr, places, tmp8);
+M_restore_stack(2);
+}
+/****************************************************************************/
+/*
+
+	for large input values use :
+
+	arctan(x) =  (PI / 2) - arctan(1 / |x|)   
+
+	and sign of result = sign of original input 
+
+*/
+void	M_arctan_large_input(M_APM rr, int places, M_APM xx)
+{
+M_APM	tmp1, tmp2;
+
+tmp1 = M_get_stack_var();
+tmp2 = M_get_stack_var();
+
+M_check_PI_places(places);
+
+m_apm_divide(tmp1, (places + 6), MM_One, xx);   	   /*  1 / xx       */
+tmp1->m_apm_sign = 1;					   /* make positive */
+m_apm_arctan(tmp2, (places + 6), tmp1);
+m_apm_subtract(tmp1, MM_lc_HALF_PI, tmp2);
+m_apm_round(rr, places, tmp1);
+
+rr->m_apm_sign = xx->m_apm_sign;			  /* fix final sign */
+
+M_restore_stack(2);
+}
+/****************************************************************************/
+void	m_apm_arcsin(M_APM r, int places, M_APM x)
+{
+M_APM   tmp0, tmp1, tmp2, tmp3, current_x;
+int	ii, maxiter, maxp, tolerance, local_precision;
+
+current_x = M_get_stack_var();
+tmp0      = M_get_stack_var();
+tmp1      = M_get_stack_var();
+tmp2      = M_get_stack_var();
+tmp3      = M_get_stack_var();
+
+m_apm_absolute_value(tmp0, x);
+
+ii = m_apm_compare(tmp0, MM_One);
+
+if (ii == 1)       /* |x| > 1 */
+  {
+   M_apm_log_error_msg(M_APM_RETURN, "\'m_apm_arcsin\', |Argument| > 1");
+   M_set_to_zero(r);
+   M_restore_stack(5);
+   return;
+  }
+
+if (ii == 0)       /* |x| == 1, arcsin = +/- PI / 2 */
+  {
+   M_check_PI_places(places);
+   m_apm_round(r, places, MM_lc_HALF_PI);
+   r->m_apm_sign = x->m_apm_sign;
+
+   M_restore_stack(5);
+   return;
+  }
+
+if (m_apm_compare(tmp0, MM_0_85) == 1)        /* check if > 0.85 */
+  {
+   M_cos_to_sin(tmp2, (places + 4), x);
+   m_apm_arccos(r, places, tmp2);
+   r->m_apm_sign = x->m_apm_sign;
+
+   M_restore_stack(5);
+   return;
+  }
+
+if (x->m_apm_sign == 0)			      /* input == 0 ?? */
+  {
+   M_set_to_zero(r);
+   M_restore_stack(5);
+   return;
+  }
+
+if (x->m_apm_exponent <= -4)		      /* input close to 0 ?? */
+  {
+   M_arcsin_near_0(r, places, x);
+   M_restore_stack(5);
+   return;
+  }
+
+tolerance       = -(places + 4);
+maxp            = places + 8 - x->m_apm_exponent;
+local_precision = 20 - x->m_apm_exponent;
+
+/*
+ *      compute the maximum number of iterations
+ *	that should be needed to calculate to
+ *	the desired accuracy.  [ constant below ~= 1 / log(2) ]
+ */
+
+maxiter = (int)(log((double)(places + 2)) * 1.442695) + 3;
+
+if (maxiter < 5)
+  maxiter = 5;
+
+M_get_asin_guess(current_x, x);
+
+/*    Use the following iteration to solve for arc-sin :
+
+                      sin(X) - N
+      X     =  X  -  ------------
+       n+1              cos(X)
+*/
+
+ii = 0;
+
+while (TRUE)
+  {
+   M_4x_cos(tmp1, local_precision, current_x);
+
+   M_cos_to_sin(tmp2, local_precision, tmp1);
+   if (tmp2->m_apm_sign != 0)
+     tmp2->m_apm_sign = current_x->m_apm_sign;
+
+   m_apm_subtract(tmp3, tmp2, x);
+   m_apm_divide(tmp0, local_precision, tmp3, tmp1);
+
+   m_apm_subtract(tmp2, current_x, tmp0);
+   m_apm_copy(current_x, tmp2);
+
+   if (ii != 0)
+     {
+      if (((2 * tmp0->m_apm_exponent) < tolerance) || (tmp0->m_apm_sign == 0))
+        break;
+     }
+
+   if (++ii == maxiter)
+     {
+      M_apm_log_error_msg(M_APM_RETURN, 
+            "\'m_apm_arcsin\', max iteration count reached");
+      break;
+     }
+
+   local_precision *= 2;
+
+   if (local_precision > maxp)
+     local_precision = maxp;
+  }
+
+m_apm_round(r, places, current_x);
+M_restore_stack(5);
+}
+/****************************************************************************/
+void	m_apm_arccos(M_APM r, int places, M_APM x)
+{
+M_APM   tmp0, tmp1, tmp2, tmp3, current_x;
+int	ii, maxiter, maxp, tolerance, local_precision;
+
+current_x = M_get_stack_var();
+tmp0      = M_get_stack_var();
+tmp1      = M_get_stack_var();
+tmp2      = M_get_stack_var();
+tmp3      = M_get_stack_var();
+
+m_apm_absolute_value(tmp0, x);
+
+ii = m_apm_compare(tmp0, MM_One);
+
+if (ii == 1)       /* |x| > 1 */
+  {
+   M_apm_log_error_msg(M_APM_RETURN, "\'m_apm_arccos\', |Argument| > 1");
+   M_set_to_zero(r);
+   M_restore_stack(5);
+   return;
+  }
+
+if (ii == 0)       /* |x| == 1, arccos = 0, PI */
+  {
+   if (x->m_apm_sign == 1)
+     {
+      M_set_to_zero(r);
+     }
+   else
+     {
+      M_check_PI_places(places);
+      m_apm_round(r, places, MM_lc_PI);
+     }
+
+   M_restore_stack(5);
+   return;
+  }
+
+if (m_apm_compare(tmp0, MM_0_85) == 1)        /* check if > 0.85 */
+  {
+   M_cos_to_sin(tmp2, (places + 4), x);
+
+   if (x->m_apm_sign == 1)
+     {
+      m_apm_arcsin(r, places, tmp2);
+     }
+   else
+     {
+      M_check_PI_places(places);
+      m_apm_arcsin(tmp3, (places + 4), tmp2);
+      m_apm_subtract(tmp1, MM_lc_PI, tmp3);
+      m_apm_round(r, places, tmp1);
+     }
+
+   M_restore_stack(5);
+   return;
+  }
+
+if (x->m_apm_sign == 0)			      /* input == 0 ?? */
+  {
+   M_check_PI_places(places);
+   m_apm_round(r, places, MM_lc_HALF_PI);
+   M_restore_stack(5);
+   return;
+  }
+
+if (x->m_apm_exponent <= -4)		      /* input close to 0 ?? */
+  {
+   M_arccos_near_0(r, places, x);
+   M_restore_stack(5);
+   return;
+  }
+
+tolerance       = -(places + 4);
+maxp            = places + 8;
+local_precision = 18;
+
+/*
+ *      compute the maximum number of iterations
+ *	that should be needed to calculate to
+ *	the desired accuracy.  [ constant below ~= 1 / log(2) ]
+ */
+
+maxiter = (int)(log((double)(places + 2)) * 1.442695) + 3;
+
+if (maxiter < 5)
+  maxiter = 5;
+
+M_get_acos_guess(current_x, x);
+
+/*    Use the following iteration to solve for arc-cos :
+
+                      cos(X) - N
+      X     =  X  +  ------------
+       n+1              sin(X)
+*/
+
+ii = 0;
+
+while (TRUE)
+  {
+   M_4x_cos(tmp1, local_precision, current_x);
+
+   M_cos_to_sin(tmp2, local_precision, tmp1);
+   if (tmp2->m_apm_sign != 0)
+     tmp2->m_apm_sign = current_x->m_apm_sign;
+
+   m_apm_subtract(tmp3, tmp1, x);
+   m_apm_divide(tmp0, local_precision, tmp3, tmp2);
+
+   m_apm_add(tmp2, current_x, tmp0);
+   m_apm_copy(current_x, tmp2);
+
+   if (ii != 0)
+     {
+      if (((2 * tmp0->m_apm_exponent) < tolerance) || (tmp0->m_apm_sign == 0))
+        break;
+     }
+
+   if (++ii == maxiter)
+     {
+      M_apm_log_error_msg(M_APM_RETURN,
+            "\'m_apm_arccos\', max iteration count reached");
+      break;
+     }
+
+   local_precision *= 2;
+
+   if (local_precision > maxp)
+     local_precision = maxp;
+  }
+
+m_apm_round(r, places, current_x);
+M_restore_stack(5);
+}
+/****************************************************************************/

+ 182 - 0
mapm/src/mapmasn0.c

@@ -0,0 +1,182 @@
+
+/* 
+ *  M_APM  -  mapmasn0.c
+ *
+ *  Copyright (C) 2000 - 2007   Michael C. Ring
+ *
+ *  Permission to use, copy, and distribute this software and its
+ *  documentation for any purpose with or without fee is hereby granted,
+ *  provided that the above copyright notice appear in all copies and
+ *  that both that copyright notice and this permission notice appear
+ *  in supporting documentation.
+ *
+ *  Permission to modify the software is granted. Permission to distribute
+ *  the modified code is granted. Modifications are to be distributed by
+ *  using the file 'license.txt' as a template to modify the file header.
+ *  'license.txt' is available in the official MAPM distribution.
+ *
+ *  This software is provided "as is" without express or implied warranty.
+ */
+
+/*
+ *      $Id: mapmasn0.c,v 1.8 2007/12/03 01:49:49 mike Exp $
+ *
+ *      This file contains the 'ARC' family of functions; ARC-SIN, 
+ *	ARC-COS, ARC-TAN when the input arg is very close to 0 (zero).
+ *
+ *      $Log: mapmasn0.c,v $
+ *      Revision 1.8  2007/12/03 01:49:49  mike
+ *      Update license
+ *
+ *      Revision 1.7  2003/06/02 16:51:13  mike
+ *      *** empty log message ***
+ *
+ *      Revision 1.6  2003/06/02 16:49:48  mike
+ *      tweak the decimal places
+ *
+ *      Revision 1.5  2003/06/02 16:47:39  mike
+ *      tweak arctan algorithm some more
+ *
+ *      Revision 1.4  2003/05/31 22:38:07  mike
+ *      optimize arctan by using fewer digits as subsequent
+ *      terms get smaller
+ *
+ *      Revision 1.3  2002/11/03 21:36:43  mike
+ *      Updated function parameters to use the modern style
+ *
+ *      Revision 1.2  2000/12/02 20:11:37  mike
+ *      add comments
+ *
+ *      Revision 1.1  2000/12/02 20:08:27  mike
+ *      Initial revision
+ */
+
+#include "m_apm_lc.h"
+
+/****************************************************************************/
+/*
+        Calculate arcsin using the identity :
+
+                                      x
+        arcsin (x) == arctan [ --------------- ]
+                                sqrt(1 - x^2)
+
+*/
+void	M_arcsin_near_0(M_APM rr, int places, M_APM aa)
+{
+M_APM   tmp5, tmp6;
+
+tmp5 = M_get_stack_var();
+tmp6 = M_get_stack_var();
+
+M_cos_to_sin(tmp5, (places + 8), aa);
+m_apm_divide(tmp6, (places + 8), aa, tmp5);
+M_arctan_near_0(rr, places, tmp6);
+
+M_restore_stack(2);
+}
+/****************************************************************************/
+/*
+        Calculate arccos using the identity :
+
+        arccos (x) == PI / 2 - arcsin (x)
+
+*/
+void	M_arccos_near_0(M_APM rr, int places, M_APM aa)
+{
+M_APM   tmp1, tmp2;
+
+tmp1 = M_get_stack_var();
+tmp2 = M_get_stack_var();
+
+M_check_PI_places(places);
+M_arcsin_near_0(tmp1, (places + 4), aa);
+m_apm_subtract(tmp2, MM_lc_HALF_PI, tmp1);
+m_apm_round(rr, places, tmp2);
+
+M_restore_stack(2);
+}
+/****************************************************************************/
+/*
+	calculate arctan (x) with the following series:
+
+                              x^3     x^5     x^7     x^9
+	arctan (x)  =   x  -  ---  +  ---  -  ---  +  ---  ...
+                               3       5       7       9
+
+*/
+void	M_arctan_near_0(M_APM rr, int places, M_APM aa)
+{
+M_APM   tmp0, tmp2, tmpR, tmpS, digit, term;
+int	tolerance, dplaces, local_precision;
+long    m1;
+
+tmp0  = M_get_stack_var();
+tmp2  = M_get_stack_var();
+tmpR  = M_get_stack_var();
+tmpS  = M_get_stack_var();
+term  = M_get_stack_var();
+digit = M_get_stack_var();
+
+tolerance = aa->m_apm_exponent - (places + 4);
+dplaces   = (places + 8) - aa->m_apm_exponent;
+
+m_apm_copy(term, aa);
+m_apm_copy(tmpS, aa);
+m_apm_multiply(tmp0, aa, aa);
+m_apm_round(tmp2, (dplaces + 8), tmp0);
+
+m1 = 1L;
+
+while (TRUE)
+  {
+   /*
+    *   do the subtraction term
+    */
+
+   m_apm_multiply(tmp0, term, tmp2);
+
+   if ((tmp0->m_apm_exponent < tolerance) || (tmp0->m_apm_sign == 0))
+     {
+      m_apm_round(rr, places, tmpS);
+      break;
+     }
+
+   local_precision = dplaces + tmp0->m_apm_exponent;
+
+   if (local_precision < 20)
+     local_precision = 20;
+
+   m1 += 2;
+   m_apm_set_long(digit, m1);
+   m_apm_round(term, local_precision, tmp0);
+   m_apm_divide(tmp0, local_precision, term, digit);
+   m_apm_subtract(tmpR, tmpS, tmp0);
+
+   /*
+    *   do the addition term
+    */
+
+   m_apm_multiply(tmp0, term, tmp2);
+
+   if ((tmp0->m_apm_exponent < tolerance) || (tmp0->m_apm_sign == 0))
+     {
+      m_apm_round(rr, places, tmpR);
+      break;
+     }
+
+   local_precision = dplaces + tmp0->m_apm_exponent;
+
+   if (local_precision < 20)
+     local_precision = 20;
+
+   m1 += 2;
+   m_apm_set_long(digit, m1);
+   m_apm_round(term, local_precision, tmp0);
+   m_apm_divide(tmp0, local_precision, term, digit);
+   m_apm_add(tmpS, tmpR, tmp0);
+  }
+
+M_restore_stack(6);                    /* restore the 6 locals we used here */
+}
+/****************************************************************************/

+ 153 - 0
mapm/src/mapmcbrt.c

@@ -0,0 +1,153 @@
+
+/* 
+ *  M_APM  -  mapmcbrt.c
+ *
+ *  Copyright (C) 2000 - 2007   Michael C. Ring
+ *
+ *  Permission to use, copy, and distribute this software and its
+ *  documentation for any purpose with or without fee is hereby granted,
+ *  provided that the above copyright notice appear in all copies and
+ *  that both that copyright notice and this permission notice appear
+ *  in supporting documentation.
+ *
+ *  Permission to modify the software is granted. Permission to distribute
+ *  the modified code is granted. Modifications are to be distributed by
+ *  using the file 'license.txt' as a template to modify the file header.
+ *  'license.txt' is available in the official MAPM distribution.
+ *
+ *  This software is provided "as is" without express or implied warranty.
+ */
+
+/*
+ *      $Id: mapmcbrt.c,v 1.8 2007/12/03 01:50:32 mike Exp $
+ *
+ *      This file contains the CBRT (cube root) function.
+ *
+ *      $Log: mapmcbrt.c,v $
+ *      Revision 1.8  2007/12/03 01:50:32  mike
+ *      Update license
+ *
+ *      Revision 1.7  2003/05/05 18:17:38  mike
+ *      simplify some logic
+ *
+ *      Revision 1.6  2003/04/16 16:55:58  mike
+ *      use new faster algorithm which finds 1 / cbrt(N)
+ *
+ *      Revision 1.5  2002/11/03 21:34:34  mike
+ *      Updated function parameters to use the modern style
+ *
+ *      Revision 1.4  2000/10/30 16:42:22  mike
+ *      minor speed optimization
+ *
+ *      Revision 1.3  2000/07/11 18:03:39  mike
+ *      make better estimate for initial precision
+ *
+ *      Revision 1.2  2000/04/08 18:34:35  mike
+ *      added some more comments
+ *
+ *      Revision 1.1  2000/04/03 17:58:04  mike
+ *      Initial revision
+ */
+
+#include "m_apm_lc.h"
+
+/****************************************************************************/
+void	m_apm_cbrt(M_APM rr, int places, M_APM aa)
+{
+M_APM   last_x, guess, tmpN, tmp7, tmp8, tmp9;
+int	ii, nexp, bflag, tolerance, maxp, local_precision;
+
+/* result is 0 if input is 0 */
+
+if (aa->m_apm_sign == 0)
+  {
+   M_set_to_zero(rr);
+   return;
+  }
+
+last_x = M_get_stack_var();
+guess  = M_get_stack_var();
+tmpN   = M_get_stack_var();
+tmp7   = M_get_stack_var();
+tmp8   = M_get_stack_var();
+tmp9   = M_get_stack_var();
+
+/* compute the cube root of the positive number, we'll fix the sign later */
+
+m_apm_absolute_value(tmpN, aa);
+
+/* 
+    normalize the input number (make the exponent near 0) so
+    the 'guess' function will not over/under flow on large
+    magnitude exponents.
+*/
+
+nexp = aa->m_apm_exponent / 3;
+tmpN->m_apm_exponent -= 3 * nexp;
+
+M_get_cbrt_guess(guess, tmpN);
+
+tolerance       = places + 4;
+maxp            = places + 16;
+bflag           = FALSE;
+local_precision = 14;
+
+m_apm_negate(last_x, MM_Ten);
+
+/*   Use the following iteration to calculate 1 / cbrt(N) :
+
+                                 4
+         X     =  [ 4 * X - N * X ] / 3
+          n+1   
+*/
+
+ii = 0;
+
+while (TRUE)
+  {
+   m_apm_multiply(tmp8, guess, guess);
+   m_apm_multiply(tmp7, tmp8, tmp8);
+   m_apm_round(tmp8, local_precision, tmp7);
+   m_apm_multiply(tmp9, tmpN, tmp8);
+
+   m_apm_multiply(tmp8, MM_Four, guess);
+   m_apm_subtract(tmp7, tmp8, tmp9);
+   m_apm_divide(guess, local_precision, tmp7, MM_Three);
+
+   if (bflag)
+     break;
+
+   /* force at least 2 iterations so 'last_x' has valid data */
+
+   if (ii != 0)
+     {
+      m_apm_subtract(tmp8, guess, last_x);
+
+      if (tmp8->m_apm_sign == 0)
+        break;
+
+      if ((-4 * tmp8->m_apm_exponent) > tolerance)
+        bflag = TRUE;
+     }
+
+   local_precision *= 2;
+
+   if (local_precision > maxp)
+     local_precision = maxp;
+  
+   m_apm_copy(last_x, guess);
+   ii = 1;
+  }
+
+/* final cbrt = N * guess ^ 2 */
+
+m_apm_multiply(tmp9, guess, guess);
+m_apm_multiply(tmp8, tmp9, tmpN);
+m_apm_round(rr, places, tmp8);
+
+rr->m_apm_exponent += nexp;
+rr->m_apm_sign = aa->m_apm_sign;
+M_restore_stack(6);
+}
+/****************************************************************************/
+

+ 365 - 0
mapm/src/mapmcnst.c

@@ -0,0 +1,365 @@
+
+/* 
+ *  M_APM  -  mapmcnst.c
+ *
+ *  Copyright (C) 1999 - 2007   Michael C. Ring
+ *
+ *  Permission to use, copy, and distribute this software and its
+ *  documentation for any purpose with or without fee is hereby granted,
+ *  provided that the above copyright notice appear in all copies and
+ *  that both that copyright notice and this permission notice appear
+ *  in supporting documentation.
+ *
+ *  Permission to modify the software is granted. Permission to distribute
+ *  the modified code is granted. Modifications are to be distributed by
+ *  using the file 'license.txt' as a template to modify the file header.
+ *  'license.txt' is available in the official MAPM distribution.
+ *
+ *  This software is provided "as is" without express or implied warranty.
+ */
+
+/*
+ *      $Id: mapmcnst.c,v 1.24 2007/12/03 01:51:16 mike Exp $
+ *
+ *      This file contains declarations and initializes the constants 
+ *	used throughout the library.
+ *
+ *      $Log: mapmcnst.c,v $
+ *      Revision 1.24  2007/12/03 01:51:16  mike
+ *      Update license
+ *
+ *      Revision 1.23  2003/05/06 21:28:53  mike
+ *      add lib version functions
+ *
+ *      Revision 1.22  2003/03/30 21:14:16  mike
+ *      add local copies of log(2) and log(10)
+ *
+ *      Revision 1.21  2002/11/03 22:45:29  mike
+ *      Updated function parameters to use the modern style
+ *
+ *      Revision 1.20  2002/05/17 22:40:25  mike
+ *      call m_apm_init from cpp_precision to init the library
+ *      if it hasn't been done yet.
+ *
+ *      Revision 1.19  2001/07/16 19:40:12  mike
+ *      add function M_free_all_cnst
+ *
+ *      Revision 1.18  2001/02/07 19:17:58  mike
+ *      eliminate MM_skip_limit_PI_check
+ *
+ *      Revision 1.17  2000/05/19 16:31:02  mike
+ *      add local copies for PI variables
+ *
+ *      Revision 1.16  2000/05/04 23:52:03  mike
+ *      added new constant, 256R.
+ *      renamed _008 to _125R
+ *
+ *      Revision 1.15  2000/04/11 18:44:21  mike
+ *      no longer need the constant 'Fifteen'
+ *
+ *      Revision 1.14  2000/04/05 20:12:53  mike
+ *      add C++ min precision function
+ *
+ *      Revision 1.13  1999/07/09 22:47:48  mike
+ *      add skip limit PI check
+ *
+ *      Revision 1.12  1999/07/08 23:34:50  mike
+ *      change constant
+ *
+ *      Revision 1.11  1999/07/08 22:58:08  mike
+ *      add new constant
+ *
+ *      Revision 1.10  1999/06/23 01:09:53  mike
+ *      added new constant 15
+ *
+ *      Revision 1.9  1999/06/20 23:32:30  mike
+ *      added new constants
+ *
+ *      Revision 1.8  1999/06/20 19:24:14  mike
+ *      delete constants no longer needed
+ *
+ *      Revision 1.7  1999/06/20 18:57:29  mike
+ *      fixed missing init for new constants
+ *
+ *      Revision 1.6  1999/06/20 18:53:44  mike
+ *      added more constants
+ *
+ *      Revision 1.5  1999/05/31 23:50:30  mike
+ *      delete constants no longer needed
+ *
+ *      Revision 1.4  1999/05/14 19:50:22  mike
+ *      added more constants with more digits
+ *
+ *      Revision 1.3  1999/05/12 20:53:08  mike
+ *      added more constants
+ *
+ *      Revision 1.2  1999/05/10 21:52:24  mike
+ *      added some comments
+ *
+ *      Revision 1.1  1999/05/10 20:56:31  mike
+ *      Initial revision
+ */
+
+#include "m_apm_lc.h"
+
+int	MM_lc_PI_digits = 0;
+int	MM_lc_log_digits;
+int     MM_cpp_min_precision;       /* only used in C++ wrapper */
+
+M_APM	MM_Zero          = NULL;
+M_APM	MM_One           = NULL;
+M_APM	MM_Two           = NULL;
+M_APM	MM_Three         = NULL;
+M_APM	MM_Four          = NULL;
+M_APM	MM_Five          = NULL;
+M_APM	MM_Ten           = NULL;
+M_APM	MM_0_5           = NULL;
+M_APM	MM_E             = NULL;
+M_APM	MM_PI            = NULL;
+M_APM	MM_HALF_PI       = NULL;
+M_APM	MM_2_PI          = NULL;
+M_APM	MM_lc_PI         = NULL;
+M_APM	MM_lc_HALF_PI    = NULL;
+M_APM	MM_lc_2_PI       = NULL;
+M_APM	MM_lc_log2       = NULL;
+M_APM	MM_lc_log10      = NULL;
+M_APM	MM_lc_log10R     = NULL;
+M_APM	MM_0_85          = NULL;
+M_APM	MM_5x_125R       = NULL;
+M_APM	MM_5x_64R        = NULL;
+M_APM	MM_5x_256R       = NULL;
+M_APM	MM_5x_Eight      = NULL;
+M_APM	MM_5x_Sixteen    = NULL;
+M_APM	MM_5x_Twenty     = NULL;
+M_APM	MM_LOG_E_BASE_10 = NULL;
+M_APM	MM_LOG_10_BASE_E = NULL;
+M_APM	MM_LOG_2_BASE_E  = NULL;
+M_APM	MM_LOG_3_BASE_E  = NULL;
+
+
+static char MM_cnst_PI[] = 
+"3.1415926535897932384626433832795028841971693993751058209749445923078\
+1640628620899862803482534211706798214808651328230664709384460955";
+
+static char MM_cnst_E[] = 
+"2.7182818284590452353602874713526624977572470936999595749669676277240\
+76630353547594571382178525166427427466391932003059921817413596629";
+
+static char MM_cnst_log_2[] = 
+"0.6931471805599453094172321214581765680755001343602552541206800094933\
+93621969694715605863326996418687542001481020570685733685520235758";
+
+static char MM_cnst_log_3[] = 
+"1.0986122886681096913952452369225257046474905578227494517346943336374\
+9429321860896687361575481373208878797002906595786574236800422593";
+
+static char MM_cnst_log_10[] = 
+"2.3025850929940456840179914546843642076011014886287729760333279009675\
+7260967735248023599720508959829834196778404228624863340952546508";
+
+static char MM_cnst_1_log_10[] = 
+"0.4342944819032518276511289189166050822943970058036665661144537831658\
+64649208870774729224949338431748318706106744766303733641679287159";
+
+/*
+ *     the following constants have ~520 digits each, if needed
+ */
+
+/* 
+static char MM_cnst_PI[] = 
+"3.1415926535897932384626433832795028841971693993751058209749445923078\
+164062862089986280348253421170679821480865132823066470938446095505822\
+317253594081284811174502841027019385211055596446229489549303819644288\
+109756659334461284756482337867831652712019091456485669234603486104543\
+266482133936072602491412737245870066063155881748815209209628292540917\
+153643678925903600113305305488204665213841469519415116094330572703657\
+595919530921861173819326117931051185480744623799627495673518857527248\
+91227938183011949129833673362440656643";
+
+static char MM_cnst_E[] = 
+"2.7182818284590452353602874713526624977572470936999595749669676277240\
+766303535475945713821785251664274274663919320030599218174135966290435\
+729003342952605956307381323286279434907632338298807531952510190115738\
+341879307021540891499348841675092447614606680822648001684774118537423\
+454424371075390777449920695517027618386062613313845830007520449338265\
+602976067371132007093287091274437470472306969772093101416928368190255\
+151086574637721112523897844250569536967707854499699679468644549059879\
+3163688923009879312773617821542499923";
+
+static char MM_cnst_log_2[] = 
+"0.6931471805599453094172321214581765680755001343602552541206800094933\
+936219696947156058633269964186875420014810205706857336855202357581305\
+570326707516350759619307275708283714351903070386238916734711233501153\
+644979552391204751726815749320651555247341395258829504530070953263666\
+426541042391578149520437404303855008019441706416715186447128399681717\
+845469570262716310645461502572074024816377733896385506952606683411372\
+738737229289564935470257626520988596932019650585547647033067936544325\
+47632744951250406069438147104689946506";
+
+static char MM_cnst_log_3[] = 
+"1.0986122886681096913952452369225257046474905578227494517346943336374\
+942932186089668736157548137320887879700290659578657423680042259305198\
+210528018707672774106031627691833813671793736988443609599037425703167\
+959115211455919177506713470549401667755802222031702529468975606901065\
+215056428681380363173732985777823669916547921318181490200301038236301\
+222486527481982259910974524908964580534670088459650857484441190188570\
+876474948670796130858294116021661211840014098255143919487688936798494\
+3022557315353296853452952514592138765";
+
+static char MM_cnst_log_10[] = 
+"2.3025850929940456840179914546843642076011014886287729760333279009675\
+726096773524802359972050895982983419677840422862486334095254650828067\
+566662873690987816894829072083255546808437998948262331985283935053089\
+653777326288461633662222876982198867465436674744042432743651550489343\
+149393914796194044002221051017141748003688084012647080685567743216228\
+355220114804663715659121373450747856947683463616792101806445070648000\
+277502684916746550586856935673420670581136429224554405758925724208241\
+31469568901675894025677631135691929203";
+
+static char MM_cnst_1_log_10[] = 
+"0.4342944819032518276511289189166050822943970058036665661144537831658\
+646492088707747292249493384317483187061067447663037336416792871589639\
+065692210646628122658521270865686703295933708696588266883311636077384\
+905142844348666768646586085135561482123487653435434357317253835622281\
+395603048646652366095539377356176323431916710991411597894962993512457\
+934926357655469077671082419150479910989674900103277537653570270087328\
+550951731440674697951899513594088040423931518868108402544654089797029\
+86328682876262414401345704354613292060";
+*/
+
+
+/****************************************************************************/
+char	*m_apm_lib_version(char *v)
+{
+strcpy(v, MAPM_LIB_VERSION);
+return(v);
+}
+/****************************************************************************/
+char	*m_apm_lib_short_version(char *v)
+{
+strcpy(v, MAPM_LIB_SHORT_VERSION);
+return(v);
+}
+/****************************************************************************/
+void	M_free_all_cnst()
+{
+if (MM_lc_PI_digits != 0)
+  {
+   m_apm_free(MM_Zero);
+   m_apm_free(MM_One);
+   m_apm_free(MM_Two);
+   m_apm_free(MM_Three);
+   m_apm_free(MM_Four);
+   m_apm_free(MM_Five);
+   m_apm_free(MM_Ten);
+   m_apm_free(MM_0_5);
+   m_apm_free(MM_LOG_2_BASE_E);
+   m_apm_free(MM_LOG_3_BASE_E);
+   m_apm_free(MM_E);
+   m_apm_free(MM_PI);
+   m_apm_free(MM_HALF_PI);
+   m_apm_free(MM_2_PI);
+   m_apm_free(MM_lc_PI);
+   m_apm_free(MM_lc_HALF_PI);
+   m_apm_free(MM_lc_2_PI);
+   m_apm_free(MM_lc_log2);
+   m_apm_free(MM_lc_log10);
+   m_apm_free(MM_lc_log10R);
+   m_apm_free(MM_0_85);
+   m_apm_free(MM_5x_125R);
+   m_apm_free(MM_5x_64R);
+   m_apm_free(MM_5x_256R);
+   m_apm_free(MM_5x_Eight);
+   m_apm_free(MM_5x_Sixteen);
+   m_apm_free(MM_5x_Twenty);
+   m_apm_free(MM_LOG_E_BASE_10);
+   m_apm_free(MM_LOG_10_BASE_E);
+
+   MM_lc_PI_digits = 0;
+  }
+}
+/****************************************************************************/
+void	M_init_trig_globals()
+{
+MM_lc_PI_digits      = VALID_DECIMAL_PLACES;
+MM_lc_log_digits     = VALID_DECIMAL_PLACES;
+MM_cpp_min_precision = 30;
+
+MM_Zero          = m_apm_init();
+MM_One           = m_apm_init();
+MM_Two           = m_apm_init();
+MM_Three         = m_apm_init();
+MM_Four          = m_apm_init();
+MM_Five          = m_apm_init();
+MM_Ten           = m_apm_init();
+MM_0_5           = m_apm_init();
+MM_LOG_2_BASE_E  = m_apm_init();
+MM_LOG_3_BASE_E  = m_apm_init();
+MM_E             = m_apm_init();
+MM_PI            = m_apm_init();
+MM_HALF_PI       = m_apm_init();
+MM_2_PI          = m_apm_init();
+MM_lc_PI         = m_apm_init();
+MM_lc_HALF_PI    = m_apm_init();
+MM_lc_2_PI       = m_apm_init();
+MM_lc_log2       = m_apm_init();
+MM_lc_log10      = m_apm_init();
+MM_lc_log10R     = m_apm_init();
+MM_0_85          = m_apm_init();
+MM_5x_125R       = m_apm_init();
+MM_5x_64R        = m_apm_init();
+MM_5x_256R       = m_apm_init();
+MM_5x_Eight      = m_apm_init();
+MM_5x_Sixteen    = m_apm_init();
+MM_5x_Twenty     = m_apm_init();
+MM_LOG_E_BASE_10 = m_apm_init();
+MM_LOG_10_BASE_E = m_apm_init();
+
+m_apm_set_string(MM_One, "1");
+m_apm_set_string(MM_Two, "2");
+m_apm_set_string(MM_Three, "3");
+m_apm_set_string(MM_Four, "4");
+m_apm_set_string(MM_Five, "5");
+m_apm_set_string(MM_Ten, "10");
+m_apm_set_string(MM_0_5, "0.5");
+m_apm_set_string(MM_0_85, "0.85");
+
+m_apm_set_string(MM_5x_125R, "8.0E-3");
+m_apm_set_string(MM_5x_64R, "1.5625E-2");
+m_apm_set_string(MM_5x_256R, "3.90625E-3");
+m_apm_set_string(MM_5x_Eight, "8");
+m_apm_set_string(MM_5x_Sixteen, "16");
+m_apm_set_string(MM_5x_Twenty, "20");
+
+m_apm_set_string(MM_LOG_2_BASE_E, MM_cnst_log_2);
+m_apm_set_string(MM_LOG_3_BASE_E, MM_cnst_log_3);
+m_apm_set_string(MM_LOG_10_BASE_E, MM_cnst_log_10);
+m_apm_set_string(MM_LOG_E_BASE_10, MM_cnst_1_log_10);
+
+m_apm_set_string(MM_lc_log2, MM_cnst_log_2);
+m_apm_set_string(MM_lc_log10, MM_cnst_log_10);
+m_apm_set_string(MM_lc_log10R, MM_cnst_1_log_10);
+
+m_apm_set_string(MM_E, MM_cnst_E);
+m_apm_set_string(MM_PI, MM_cnst_PI);
+m_apm_multiply(MM_HALF_PI, MM_PI, MM_0_5);
+m_apm_multiply(MM_2_PI, MM_PI, MM_Two);
+
+m_apm_copy(MM_lc_PI, MM_PI);
+m_apm_copy(MM_lc_HALF_PI, MM_HALF_PI);
+m_apm_copy(MM_lc_2_PI, MM_2_PI);
+}
+/****************************************************************************/
+void	m_apm_cpp_precision(int digits)
+{
+if (MM_lc_PI_digits == 0)
+  {
+   m_apm_free(m_apm_init());
+  }
+
+if (digits >= 2)
+  MM_cpp_min_precision = digits;
+else
+  MM_cpp_min_precision = 2;
+}
+/****************************************************************************/

+ 278 - 0
mapm/src/mapmfact.c

@@ -0,0 +1,278 @@
+
+/* 
+ *  M_APM  -  mapmfact.c
+ *
+ *  Copyright (C) 1999 - 2007   Michael C. Ring
+ *
+ *  Permission to use, copy, and distribute this software and its
+ *  documentation for any purpose with or without fee is hereby granted,
+ *  provided that the above copyright notice appear in all copies and
+ *  that both that copyright notice and this permission notice appear
+ *  in supporting documentation.
+ *
+ *  Permission to modify the software is granted. Permission to distribute
+ *  the modified code is granted. Modifications are to be distributed by
+ *  using the file 'license.txt' as a template to modify the file header.
+ *  'license.txt' is available in the official MAPM distribution.
+ *
+ *  This software is provided "as is" without express or implied warranty.
+ */
+
+/*
+ *      $Id: mapmfact.c,v 1.11 2007/12/03 01:51:50 mike Exp $
+ *
+ *      This file contains the FACTORIAL function.
+ *
+ *      $Log: mapmfact.c,v $
+ *      Revision 1.11  2007/12/03 01:51:50  mike
+ *      Update license
+ *
+ *      Revision 1.10  2003/07/21 21:05:31  mike
+ *      facilitate 'gcov' code coverage tool by making an array smaller
+ *
+ *      Revision 1.9  2002/11/03 21:27:28  mike
+ *      Updated function parameters to use the modern style
+ *
+ *      Revision 1.8  2000/06/14 20:36:16  mike
+ *      increase size of DOS array
+ *
+ *      Revision 1.7  2000/05/29 13:15:59  mike
+ *      minor tweaks, fixed comment
+ *
+ *      Revision 1.6  2000/05/26 16:39:03  mike
+ *      minor update to comments and code
+ *
+ *      Revision 1.5  2000/05/25 23:12:53  mike
+ *      change 'nd' calculation
+ *
+ *      Revision 1.4  2000/05/25 22:17:45  mike
+ *      implement new algorithm for speed. approx 5 - 10X
+ *      faster on my PC when N! is large (> 6000)
+ *
+ *      Revision 1.3  1999/06/19 21:25:21  mike
+ *      changed local static variables to MAPM stack variables
+ *
+ *      Revision 1.2  1999/05/23 18:21:12  mike
+ *      minor variable name tweaks
+ *
+ *      Revision 1.1  1999/05/15 21:06:11  mike
+ *      Initial revision
+ */
+
+/*
+ *      Brief explanation of the factorial algorithm.
+ *      ----------------------------------------------
+ *
+ *      The old algorithm simply multiplied N * (N-1) * (N-2) etc, until 
+ *	the number counted down to '2'. So one term of the multiplication 
+ *	kept getting bigger while multiplying by the next number in the 
+ *	sequence. 
+ *
+ *      The new algorithm takes advantage of the fast multiplication 
+ *	algorithm. The "ideal" setup for fast multiplication is when 
+ *	both numbers have approx the same number of significant digits 
+ *	and the number of digits is very near (but not over) an exact 
+ *	power of 2.
+ *
+ *	So, we will multiply N * (N-1) * (N-2), etc until the number of
+ *	significant digits is approx 256.
+ *
+ *	Store this temp product into an array.
+ *
+ *	Then we will multiply the next sequence until the number of
+ *	significant digits is approx 256.
+ *
+ *	Store this temp product into the next element of the array.
+ *
+ *	Continue until we've counted down to 2.
+ *
+ *	We now have an array of numbers with approx the same number
+ *	of digits (except for the last element, depending on where it 
+ *	ended.) Now multiply each of the array elements together to
+ *	get the final product.
+ *
+ *      The array multiplies are done as follows (assume we used 11
+ *	array elements for this example, indicated by [0] - [10] ) :
+ *
+ *	initial    iter-1     iter-2       iter-3     iter-4
+ *
+ *	  [0] 
+ *	     *  ->  [0]
+ *	  [1]
+ *                      * ->    [0]
+ *
+ *	  [2] 
+ *	     *  ->  [1]
+ *	  [3]
+ *                                   * ->   [0] 
+ *
+ *	  [4] 
+ *	     *  ->  [2]
+ *	  [5]
+ *
+ *                      * ->    [1]
+ *
+ *	  [6] 
+ *	     *  ->  [3]                           *  ->  [0]
+ *	  [7]
+ *
+ *
+ *	  [8] 
+ *	     *  ->  [4]
+ *	  [9]
+ *                      * ->    [2]    ->   [1]
+ *
+ *
+ *	  [10]  ->  [5]
+ *
+ */
+
+#include "m_apm_lc.h"
+
+/* define size of local array for temp storage */
+
+#define NDIM 32
+
+/****************************************************************************/
+void	m_apm_factorial(M_APM moutput, M_APM minput)
+{
+int     ii, nmul, ndigits, nd, jj, kk, mm, ct;
+M_APM   array[NDIM];
+M_APM   iprod1, iprod2, tmp1, tmp2;
+
+/* return 1 for any input <= 1 */
+
+if (m_apm_compare(minput, MM_One) <= 0)
+  {
+   m_apm_copy(moutput, MM_One);
+   return;
+  }
+
+ct       = 0;
+mm       = NDIM - 2;
+ndigits  = 256;
+nd       = ndigits - 20;
+tmp1     = m_apm_init();
+tmp2     = m_apm_init();
+iprod1   = m_apm_init();
+iprod2   = m_apm_init();
+array[0] = m_apm_init();
+
+m_apm_copy(tmp2, minput);
+
+/* loop until multiply count-down has reached '2' */
+
+while (TRUE)
+  {
+   m_apm_copy(iprod1, MM_One);
+
+   /* 
+    *   loop until the number of significant digits in this 
+    *   partial result is slightly less than 256
+    */
+
+   while (TRUE)
+     {
+      m_apm_multiply(iprod2, iprod1, tmp2);
+
+      m_apm_subtract(tmp1, tmp2, MM_One);
+
+      m_apm_multiply(iprod1, iprod2, tmp1);
+
+      /*
+       *  I know, I know.  There just isn't a *clean* way 
+       *  to break out of 2 nested loops.
+       */
+
+      if (m_apm_compare(tmp1, MM_Two) <= 0)
+        goto PHASE2;
+
+      m_apm_subtract(tmp2, tmp1, MM_One);
+
+      if (iprod1->m_apm_datalength > nd)
+        break;
+     }
+
+   if (ct == (NDIM - 1))
+     {
+      /* 
+       *    if the array has filled up, start multiplying
+       *    some of the partial products now.
+       */
+
+      m_apm_copy(tmp1, array[mm]);
+      m_apm_multiply(array[mm], iprod1, tmp1);
+
+      if (mm == 0)
+        {
+         mm = NDIM - 2;
+	 ndigits = ndigits << 1;
+         nd = ndigits - 20;
+	}
+      else
+         mm--;
+     }
+   else
+     {
+      /* 
+       *    store this partial product in the array
+       *    and allocate the next array element
+       */
+
+      m_apm_copy(array[ct], iprod1);
+      array[++ct] = m_apm_init();
+     }
+  }
+
+PHASE2:
+
+m_apm_copy(array[ct], iprod1);
+
+kk = ct;
+
+while (kk != 0)
+  {
+   ii = 0;
+   jj = 0;
+   nmul = (kk + 1) >> 1;
+
+   while (TRUE)
+     {
+      /* must use tmp var when ii,jj point to same element */
+
+      if (ii == 0)
+        {
+         m_apm_copy(tmp1, array[ii]);
+         m_apm_multiply(array[jj], tmp1, array[ii+1]);
+        }
+      else
+         m_apm_multiply(array[jj], array[ii], array[ii+1]);
+
+      if (++jj == nmul)
+        break;
+
+      ii += 2;
+     }
+
+   if ((kk & 1) == 0)
+     {
+      jj = kk >> 1;
+      m_apm_copy(array[jj], array[kk]);
+     }
+
+   kk = kk >> 1;
+  }
+
+m_apm_copy(moutput, array[0]);
+
+for (ii=0; ii <= ct; ii++)
+  {
+   m_apm_free(array[ii]);
+  }
+
+m_apm_free(tmp1);
+m_apm_free(tmp2);
+m_apm_free(iprod1);
+m_apm_free(iprod2);
+}
+/****************************************************************************/

+ 798 - 0
mapm/src/mapmfmul.c

@@ -0,0 +1,798 @@
+
+/* 
+ *  M_APM  -  mapmfmul.c
+ *
+ *  Copyright (C) 1999 - 2007   Michael C. Ring
+ *
+ *  Permission to use, copy, and distribute this software and its
+ *  documentation for any purpose with or without fee is hereby granted,
+ *  provided that the above copyright notice appear in all copies and
+ *  that both that copyright notice and this permission notice appear
+ *  in supporting documentation.
+ *
+ *  Permission to modify the software is granted. Permission to distribute
+ *  the modified code is granted. Modifications are to be distributed by
+ *  using the file 'license.txt' as a template to modify the file header.
+ *  'license.txt' is available in the official MAPM distribution.
+ *
+ *  This software is provided "as is" without express or implied warranty.
+ */
+
+/*
+ *      $Id: mapmfmul.c,v 1.33 2007/12/03 01:52:22 mike Exp $
+ *
+ *      This file contains the divide-and-conquer FAST MULTIPLICATION 
+ *	function as well as its support functions.
+ *
+ *      $Log: mapmfmul.c,v $
+ *      Revision 1.33  2007/12/03 01:52:22  mike
+ *      Update license
+ *
+ *      Revision 1.32  2004/02/18 03:16:15  mike
+ *      optimize 4 byte multiply (when FFT is disabled)
+ *
+ *      Revision 1.31  2003/12/04 01:14:06  mike
+ *      redo math on 'borrow'
+ *
+ *      Revision 1.30  2003/07/21 20:34:18  mike
+ *      Modify error messages to be in a consistent format.
+ *
+ *      Revision 1.29  2003/03/31 21:55:07  mike
+ *      call generic error handling function
+ *
+ *      Revision 1.28  2002/11/03 22:38:15  mike
+ *      Updated function parameters to use the modern style
+ *
+ *      Revision 1.27  2002/02/14 19:53:32  mike
+ *      add conditional compiler option to disable use
+ *      of FFT multiply if the user so chooses.
+ *
+ *      Revision 1.26  2001/07/26 20:56:38  mike
+ *      fix comment, no code change
+ *
+ *      Revision 1.25  2001/07/16 19:43:45  mike
+ *      add function M_free_all_fmul
+ *
+ *      Revision 1.24  2001/02/11 22:34:47  mike
+ *      modify parameters to REALLOC
+ *
+ *      Revision 1.23  2000/10/20 19:23:26  mike
+ *      adjust power_of_2 function so it should work with
+ *      64 bit processors and beyond.
+ *
+ *      Revision 1.22  2000/08/23 22:27:34  mike
+ *      no real code change, re-named 2 local functions
+ *      so they make more sense.
+ *
+ *      Revision 1.21  2000/08/01 22:24:38  mike
+ *      use sizeof(int) function call to stop some
+ *      compilers from complaining.
+ *
+ *      Revision 1.20  2000/07/19 17:12:00  mike
+ *      lower the number of bytes that the FFT can handle. worst case
+ *      testing indicated math overflow when >= 1048576
+ *
+ *      Revision 1.19  2000/07/08 18:29:03  mike
+ *      increase define so FFT can handle bigger numbers
+ *
+ *      Revision 1.18  2000/07/06 23:20:12  mike
+ *      changed my mind. use static local MAPM numbers
+ *      for temp data storage
+ *
+ *      Revision 1.17  2000/07/06 20:52:34  mike
+ *      use init function to get local writable copies
+ *      instead of using the stack
+ *
+ *      Revision 1.16  2000/07/04 17:25:09  mike
+ *      guarantee 16 bit compilers still work OK
+ *
+ *      Revision 1.15  2000/07/04 15:40:02  mike
+ *      add call to use FFT algorithm
+ *
+ *      Revision 1.14  2000/05/05 21:10:46  mike
+ *      add comment indicating availability of assembly language
+ *      version of M_4_byte_multiply for Linux on x86 platforms.
+ *
+ *      Revision 1.13  2000/04/20 19:30:45  mike
+ *      minor optimization to 4 byte multiply
+ *
+ *      Revision 1.12  2000/04/14 15:39:30  mike
+ *      optimize the fast multiply function. don't re-curse down
+ *      to a size of 1. recurse down to a size of '4' and then
+ *      call a special 4 byte multiply function.
+ *
+ *      Revision 1.11  2000/02/03 23:02:13  mike
+ *      put in RCS for real...
+ *
+ *      Revision 1.10  2000/02/03 22:59:08  mike
+ *      remove the extra recursive function. not needed any
+ *      longer since all current compilers should not have
+ *      any problem with true recursive calls.
+ *
+ *      Revision 1.9  2000/02/03 22:47:39  mike
+ *      use MAPM_* generic memory function
+ *
+ *      Revision 1.8  1999/09/19 21:13:44  mike
+ *      eliminate unneeded local int in _split
+ *
+ *      Revision 1.7  1999/08/12 22:36:23  mike
+ *      move the 3 'simple' function to the top of file
+ *      so GCC can in-line the code.
+ *
+ *      Revision 1.6  1999/08/12 22:01:14  mike
+ *      more minor optimizations
+ *
+ *      Revision 1.5  1999/08/12 02:02:06  mike
+ *      minor optimization
+ *
+ *      Revision 1.4  1999/08/10 22:51:59  mike
+ *      minor tweak
+ *
+ *      Revision 1.3  1999/08/10 00:45:47  mike
+ *      added more comments and a few minor tweaks
+ *
+ *      Revision 1.2  1999/08/09 02:50:02  mike
+ *      add some comments
+ *
+ *      Revision 1.1  1999/08/08 18:27:57  mike
+ *      Initial revision
+ */
+
+#include "m_apm_lc.h"
+
+static int M_firsttimef = TRUE;
+
+/*
+ *      specify the max size the FFT routine can handle 
+ *      (in MAPM, #digits = 2 * #bytes)
+ *
+ *      this number *must* be an exact power of 2.
+ *
+ *      **WORST** case input numbers (all 9's) has shown that
+ *	the FFT math will overflow if the #define here is 
+ *      >= 1048576. On my system, 524,288 worked OK. I will
+ *      factor down another factor of 2 to safeguard against 
+ *	other computers have less precise floating point math. 
+ *	If you are confident in your system, 524288 will 
+ *	theoretically work fine.
+ *
+ *      the define here allows the FFT algorithm to multiply two
+ *      524,288 digit numbers yielding a 1,048,576 digit result.
+ */
+
+#define MAX_FFT_BYTES 262144
+
+/*
+ *      the Divide-and-Conquer multiplication kicks in when the size of
+ *	the numbers exceed the capability of the FFT (#define just above).
+ *
+ *	#bytes    D&C call depth
+ *	------    --------------
+ *       512K           1
+ *        1M            2
+ *        2M            3
+ *        4M            4
+ *       ...           ...
+ *    2.1990E+12       23 
+ *
+ *	the following stack sizes are sized to meet the 
+ *      above 2.199E+12 example, though I wouldn't want to
+ *	wait for it to finish...
+ *
+ *      Each call requires 7 stack variables to be saved so 
+ *	we need a stack depth of 23 * 7 + PAD.  (we use 164)
+ *
+ *      For 'exp_stack', 3 integers also are required to be saved 
+ *      for each recursive call so we need a stack depth of 
+ *      23 * 3 + PAD. (we use 72)
+ *
+ *
+ *      If the FFT multiply is disabled, resize the arrays
+ *	as follows:
+ *
+ *      the following stack sizes are sized to meet the 
+ *      worst case expected assuming we are multiplying 
+ *      numbers with 2.14E+9 (2 ^ 31) digits. 
+ *
+ *      For sizeof(int) == 4 (32 bits) there may be up to 32 recursive
+ *      calls. Each call requires 7 stack variables so we need a
+ *      stack depth of 32 * 7 + PAD.  (we use 240)
+ *
+ *      For 'exp_stack', 3 integers also are required to be saved 
+ *      for each recursive call so we need a stack depth of 
+ *      32 * 3 + PAD. (we use 100)
+ */
+
+#ifdef NO_FFT_MULTIPLY
+#define M_STACK_SIZE 240
+#define M_ISTACK_SIZE 100
+#else
+#define M_STACK_SIZE 164
+#define M_ISTACK_SIZE 72
+#endif
+
+static int    exp_stack[M_ISTACK_SIZE];
+static int    exp_stack_ptr;
+
+static UCHAR  *mul_stack_data[M_STACK_SIZE];
+static int    mul_stack_data_size[M_STACK_SIZE];
+static int    M_mul_stack_ptr;
+
+static UCHAR  *fmul_a1, *fmul_a0, *fmul_a9, *fmul_b1, *fmul_b0, 
+	      *fmul_b9, *fmul_t0;
+
+static int    size_flag, bit_limit, stmp, itmp, mii;
+
+static M_APM  M_ain;
+static M_APM  M_bin;
+
+static char   *M_stack_ptr_error_msg = "\'M_get_stack_ptr\', Out of memory";
+
+extern void   M_fast_multiply(M_APM, M_APM, M_APM);
+extern void   M_fmul_div_conq(UCHAR *, UCHAR *, UCHAR *, int);
+extern void   M_fmul_add(UCHAR *, UCHAR *, int, int);
+extern int    M_fmul_subtract(UCHAR *, UCHAR *, UCHAR *, int);
+extern void   M_fmul_split(UCHAR *, UCHAR *, UCHAR *, int);
+extern int    M_next_power_of_2(int);
+extern int    M_get_stack_ptr(int);
+extern void   M_push_mul_int(int);
+extern int    M_pop_mul_int(void);
+
+#ifdef NO_FFT_MULTIPLY
+extern void   M_4_byte_multiply(UCHAR *, UCHAR *, UCHAR *);
+#else
+extern void   M_fast_mul_fft(UCHAR *, UCHAR *, UCHAR *, int);
+#endif
+
+/*
+ *      the following algorithm is used in this fast multiply routine
+ *	(sometimes called the divide-and-conquer technique.)
+ *
+ *	assume we have 2 numbers (a & b) with 2N digits. 
+ *
+ *      let : a = (2^N) * A1 + A0 , b = (2^N) * B1 + B0      
+ *
+ *	where 'A1' is the 'most significant half' of 'a' and 
+ *      'A0' is the 'least significant half' of 'a'. Same for 
+ *	B1 and B0.
+ *
+ *	Now use the identity :
+ *
+ *               2N   N            N                    N
+ *	ab  =  (2  + 2 ) A1B1  +  2 (A1-A0)(B0-B1)  + (2 + 1)A0B0
+ *
+ *
+ *      The original problem of multiplying 2 (2N) digit numbers has
+ *	been reduced to 3 multiplications of N digit numbers plus some
+ *	additions, subtractions, and shifts.
+ *
+ *	The fast multiplication algorithm used here uses the above 
+ *	identity in a recursive process. This algorithm results in
+ *	O(n ^ 1.585) growth.
+ */
+
+
+/****************************************************************************/
+void	M_free_all_fmul()
+{
+int	k;
+
+if (M_firsttimef == FALSE)
+  {
+   m_apm_free(M_ain);
+   m_apm_free(M_bin);
+
+   for (k=0; k < M_STACK_SIZE; k++)
+     {
+      if (mul_stack_data_size[k] != 0)
+        {
+         MAPM_FREE(mul_stack_data[k]);
+	}
+     }
+
+   M_firsttimef = TRUE;
+  }
+}
+/****************************************************************************/
+void	M_push_mul_int(int val)
+{
+exp_stack[++exp_stack_ptr] = val;
+}
+/****************************************************************************/
+int	M_pop_mul_int()
+{
+return(exp_stack[exp_stack_ptr--]);
+}
+/****************************************************************************/
+void   	M_fmul_split(UCHAR *x1, UCHAR *x0, UCHAR *xin, int nbytes)
+{
+memcpy(x1, xin, nbytes);
+memcpy(x0, (xin + nbytes), nbytes);
+}
+/****************************************************************************/
+void	M_fast_multiply(M_APM rr, M_APM aa, M_APM bb)
+{
+void	*vp;
+int	ii, k, nexp, sign;
+
+if (M_firsttimef)
+  {
+   M_firsttimef = FALSE;
+
+   for (k=0; k < M_STACK_SIZE; k++)
+     mul_stack_data_size[k] = 0;
+
+   size_flag = M_get_sizeof_int();
+   bit_limit = 8 * size_flag + 1;
+
+   M_ain = m_apm_init();
+   M_bin = m_apm_init();
+  }
+
+exp_stack_ptr   = -1;
+M_mul_stack_ptr = -1;
+
+m_apm_copy(M_ain, aa);
+m_apm_copy(M_bin, bb);
+
+sign = M_ain->m_apm_sign * M_bin->m_apm_sign;
+nexp = M_ain->m_apm_exponent + M_bin->m_apm_exponent;
+
+if (M_ain->m_apm_datalength >= M_bin->m_apm_datalength)
+  ii = M_ain->m_apm_datalength;
+else
+  ii = M_bin->m_apm_datalength;
+
+ii = (ii + 1) >> 1;
+ii = M_next_power_of_2(ii);
+
+/* Note: 'ii' must be >= 4 here. this is guaranteed 
+   by the caller: m_apm_multiply
+*/
+
+k = 2 * ii;                   /* required size of result, in bytes  */
+
+M_apm_pad(M_ain, k);          /* fill out the data so the number of */
+M_apm_pad(M_bin, k);          /* bytes is an exact power of 2       */
+
+if (k > rr->m_apm_malloclength)
+  {
+   if ((vp = MAPM_REALLOC(rr->m_apm_data, (k + 32))) == NULL)
+     {
+      /* fatal, this does not return */
+
+      M_apm_log_error_msg(M_APM_FATAL, "\'M_fast_multiply\', Out of memory");
+     }
+  
+   rr->m_apm_malloclength = k + 28;
+   rr->m_apm_data = (UCHAR *)vp;
+  }
+
+#ifdef NO_FFT_MULTIPLY
+
+M_fmul_div_conq(rr->m_apm_data, M_ain->m_apm_data, 
+                                M_bin->m_apm_data, ii);
+#else
+
+/*
+ *     if the numbers are *really* big, use the divide-and-conquer
+ *     routine first until the numbers are small enough to be handled 
+ *     by the FFT algorithm. If the numbers are already small enough,
+ *     call the FFT multiplication now.
+ *
+ *     Note that 'ii' here is (and must be) an exact power of 2.
+ */
+
+if (size_flag == 2)   /* if still using 16 bit compilers .... */
+  {
+   M_fast_mul_fft(rr->m_apm_data, M_ain->m_apm_data, 
+                                  M_bin->m_apm_data, ii);
+  }
+else                  /* >= 32 bit compilers */
+  {
+   if (ii > (MAX_FFT_BYTES + 2))
+     {
+      M_fmul_div_conq(rr->m_apm_data, M_ain->m_apm_data, 
+                                      M_bin->m_apm_data, ii);
+     }
+   else
+     {
+      M_fast_mul_fft(rr->m_apm_data, M_ain->m_apm_data, 
+                                     M_bin->m_apm_data, ii);
+     }
+  }
+
+#endif
+
+rr->m_apm_sign       = sign;
+rr->m_apm_exponent   = nexp;
+rr->m_apm_datalength = 4 * ii;
+
+M_apm_normalize(rr);
+}
+/****************************************************************************/
+/*
+ *      This is the recursive function to perform the multiply. The 
+ *      design intent here is to have no local variables. Any local
+ *      data that needs to be saved is saved on one of the two stacks.
+ */
+void	M_fmul_div_conq(UCHAR *rr, UCHAR *aa, UCHAR *bb, int sz)
+{
+
+#ifdef NO_FFT_MULTIPLY
+
+if (sz == 4)                /* multiply 4x4 yielding an 8 byte result */
+  {
+   M_4_byte_multiply(rr, aa, bb);
+   return;
+  }
+
+#else
+
+/*
+ *  if the numbers are now small enough, let the FFT algorithm
+ *  finish up.
+ */
+
+if (sz == MAX_FFT_BYTES)     
+  {
+   M_fast_mul_fft(rr, aa, bb, sz);
+   return;
+  }
+
+#endif
+
+memset(rr, 0, (2 * sz));    /* zero out the result */
+mii = sz >> 1;
+
+itmp = M_get_stack_ptr(mii);
+M_push_mul_int(itmp);
+
+fmul_a1 = mul_stack_data[itmp];
+
+itmp    = M_get_stack_ptr(mii);
+fmul_a0 = mul_stack_data[itmp];
+
+itmp    = M_get_stack_ptr(2 * sz);
+fmul_a9 = mul_stack_data[itmp];
+
+itmp    = M_get_stack_ptr(mii);
+fmul_b1 = mul_stack_data[itmp];
+
+itmp    = M_get_stack_ptr(mii);
+fmul_b0 = mul_stack_data[itmp];
+
+itmp    = M_get_stack_ptr(2 * sz);
+fmul_b9 = mul_stack_data[itmp];
+
+itmp    = M_get_stack_ptr(2 * sz);
+fmul_t0 = mul_stack_data[itmp];
+
+M_fmul_split(fmul_a1, fmul_a0, aa, mii);
+M_fmul_split(fmul_b1, fmul_b0, bb, mii);
+
+stmp  = M_fmul_subtract(fmul_a9, fmul_a1, fmul_a0, mii);
+stmp *= M_fmul_subtract(fmul_b9, fmul_b0, fmul_b1, mii);
+
+M_push_mul_int(stmp);
+M_push_mul_int(mii);
+
+M_fmul_div_conq(fmul_t0, fmul_a0, fmul_b0, mii);
+
+mii  = M_pop_mul_int();
+stmp = M_pop_mul_int();
+itmp = M_pop_mul_int();
+
+M_push_mul_int(itmp);
+M_push_mul_int(stmp);
+M_push_mul_int(mii);
+
+/*   to restore all stack variables ...
+fmul_a1 = mul_stack_data[itmp];
+fmul_a0 = mul_stack_data[itmp+1];
+fmul_a9 = mul_stack_data[itmp+2];
+fmul_b1 = mul_stack_data[itmp+3];
+fmul_b0 = mul_stack_data[itmp+4];
+fmul_b9 = mul_stack_data[itmp+5];
+fmul_t0 = mul_stack_data[itmp+6];
+*/
+
+fmul_a1 = mul_stack_data[itmp];
+fmul_b1 = mul_stack_data[itmp+3];
+fmul_t0 = mul_stack_data[itmp+6];
+
+memcpy((rr + sz), fmul_t0, sz);    /* first 'add', result is now zero */
+				   /* so we just copy in the bytes    */
+M_fmul_add(rr, fmul_t0, mii, sz);
+
+M_fmul_div_conq(fmul_t0, fmul_a1, fmul_b1, mii);
+
+mii  = M_pop_mul_int();
+stmp = M_pop_mul_int();
+itmp = M_pop_mul_int();
+
+M_push_mul_int(itmp);
+M_push_mul_int(stmp);
+M_push_mul_int(mii);
+
+fmul_a9 = mul_stack_data[itmp+2];
+fmul_b9 = mul_stack_data[itmp+5];
+fmul_t0 = mul_stack_data[itmp+6];
+
+M_fmul_add(rr, fmul_t0, 0, sz);
+M_fmul_add(rr, fmul_t0, mii, sz);
+
+if (stmp != 0)
+  M_fmul_div_conq(fmul_t0, fmul_a9, fmul_b9, mii);
+
+mii  = M_pop_mul_int();
+stmp = M_pop_mul_int();
+itmp = M_pop_mul_int();
+
+fmul_t0 = mul_stack_data[itmp+6];
+
+/*
+ *  if the sign of (A1 - A0)(B0 - B1) is positive, ADD to
+ *  the result. if it is negative, SUBTRACT from the result.
+ */
+
+if (stmp < 0)
+  {
+   fmul_a9 = mul_stack_data[itmp+2];
+   fmul_b9 = mul_stack_data[itmp+5];
+
+   memset(fmul_b9, 0, (2 * sz)); 
+   memcpy((fmul_b9 + mii), fmul_t0, sz); 
+   M_fmul_subtract(fmul_a9, rr, fmul_b9, (2 * sz));
+   memcpy(rr, fmul_a9, (2 * sz));
+  }
+
+if (stmp > 0)
+  M_fmul_add(rr, fmul_t0, mii, sz);
+
+M_mul_stack_ptr -= 7;
+}
+/****************************************************************************/
+/*
+ *	special addition function for use with the fast multiply operation
+ */
+void    M_fmul_add(UCHAR *r, UCHAR *a, int offset, int sz)
+{
+int	i, j;
+UCHAR   carry;
+
+carry = 0;
+j = offset + sz;
+i = sz;
+
+while (TRUE)
+  {
+   r[--j] += carry + a[--i];
+
+   if (r[j] >= 100)
+     {
+      r[j] -= 100;
+      carry = 1;
+     }
+   else
+      carry = 0;
+
+   if (i == 0)
+     break;
+  }
+
+if (carry)
+  {
+   while (TRUE)
+     {
+      r[--j] += 1;
+   
+      if (r[j] < 100)
+        break;
+
+      r[j] -= 100;
+     }
+  }
+}
+/****************************************************************************/
+/*
+ *	special subtraction function for use with the fast multiply operation
+ */
+int     M_fmul_subtract(UCHAR *r, UCHAR *a, UCHAR *b, int sz)
+{
+int	k, jtmp, sflag, nb, borrow;
+
+nb    = sz;
+sflag = 0;      /* sign flag: assume the numbers are equal */
+
+/*
+ *   find if a > b (so we perform a-b)
+ *   or      a < b (so we perform b-a)
+ */
+
+for (k=0; k < nb; k++)
+  {
+   if (a[k] < b[k])
+     {
+      sflag = -1;
+      break;
+     }
+
+   if (a[k] > b[k])
+     {
+      sflag = 1;
+      break;
+     }
+  }
+
+if (sflag == 0)
+  {
+   memset(r, 0, nb);            /* zero out the result */
+  }
+else
+  {
+   k = nb;
+   borrow = 0;
+
+   while (TRUE)
+     {
+      k--;
+
+      if (sflag == 1)
+        jtmp = (int)a[k] - ((int)b[k] + borrow);
+      else
+        jtmp = (int)b[k] - ((int)a[k] + borrow);
+
+      if (jtmp >= 0)
+        {
+         r[k] = (UCHAR)jtmp;
+         borrow = 0;
+        }
+      else
+        {
+         r[k] = (UCHAR)(100 + jtmp);
+         borrow = 1;
+        }
+
+      if (k == 0)
+        break;
+     }
+  }
+
+return(sflag);
+}
+/****************************************************************************/
+int     M_next_power_of_2(int n)
+{
+int     ct, k;
+
+if (n <= 2)
+  return(n);
+
+k  = 2;
+ct = 0;
+
+while (TRUE)
+  {
+   if (k >= n)
+     break;
+
+   k = k << 1;
+
+   if (++ct == bit_limit)
+     {
+      /* fatal, this does not return */
+
+      M_apm_log_error_msg(M_APM_FATAL, 
+               "\'M_next_power_of_2\', ERROR :sizeof(int) too small ??");
+     }
+  }
+
+return(k);
+}
+/****************************************************************************/
+int	M_get_stack_ptr(int sz)
+{
+int	i, k;
+UCHAR   *cp;
+
+k = ++M_mul_stack_ptr;
+
+/* if size is 0, just need to malloc and return */
+if (mul_stack_data_size[k] == 0)
+  {
+   if ((i = sz) < 16)
+     i = 16;
+
+   if ((cp = (UCHAR *)MAPM_MALLOC(i + 4)) == NULL)
+     {
+      /* fatal, this does not return */
+
+      M_apm_log_error_msg(M_APM_FATAL, M_stack_ptr_error_msg);
+     }
+
+   mul_stack_data[k]      = cp;
+   mul_stack_data_size[k] = i;
+  }
+else        /* it has been malloc'ed, see if it's big enough */
+  {
+   if (sz > mul_stack_data_size[k])
+     {
+      cp = mul_stack_data[k];
+
+      if ((cp = (UCHAR *)MAPM_REALLOC(cp, (sz + 4))) == NULL)
+        {
+         /* fatal, this does not return */
+   
+         M_apm_log_error_msg(M_APM_FATAL, M_stack_ptr_error_msg);
+        }
+   
+      mul_stack_data[k]      = cp;
+      mul_stack_data_size[k] = sz;
+     }
+  }
+
+return(k);
+}
+/****************************************************************************/
+
+#ifdef NO_FFT_MULTIPLY
+
+/*
+ *      multiply a 4 byte number by a 4 byte number
+ *      yielding an 8 byte result. each byte contains
+ *      a base 100 'digit', i.e.: range from 0-99.
+ *
+ *             MSB         LSB
+ *
+ *      a,b    [0] [1] [2] [3]
+ *   result    [0]  .....  [7]
+ */
+
+void	M_4_byte_multiply(UCHAR *r, UCHAR *a, UCHAR *b)
+{
+int	      jj;
+unsigned int  *ip, t1, rr[8];
+
+memset(rr, 0, (8 * sizeof(int)));        /* zero out result */
+jj = 3;
+ip = rr + 5;
+
+/*
+ *   loop for one number [b], un-roll the inner 'loop' [a]
+ *
+ *   accumulate partial sums in UINT array, release carries 
+ *   and convert back to base 100 at the end
+ */
+
+while (1)
+  {
+   t1  = (unsigned int)b[jj];
+   ip += 2;
+
+   *ip-- += t1 * a[3];
+   *ip-- += t1 * a[2];
+   *ip-- += t1 * a[1];
+   *ip   += t1 * a[0];
+   
+   if (jj-- == 0)
+     break;
+  }
+
+jj = 7;
+
+while (1)
+  {
+   t1 = rr[jj] / 100;
+   r[jj] = (UCHAR)(rr[jj] - 100 * t1);
+
+   if (jj == 0)
+     break;
+
+   rr[--jj] += t1;
+  }
+}
+
+#endif
+
+/****************************************************************************/

+ 209 - 0
mapm/src/mapmgues.c

@@ -0,0 +1,209 @@
+
+/* 
+ *  M_APM  -  mapmgues.c
+ *
+ *  Copyright (C) 1999 - 2007   Michael C. Ring
+ *
+ *  Permission to use, copy, and distribute this software and its
+ *  documentation for any purpose with or without fee is hereby granted,
+ *  provided that the above copyright notice appear in all copies and
+ *  that both that copyright notice and this permission notice appear
+ *  in supporting documentation.
+ *
+ *  Permission to modify the software is granted. Permission to distribute
+ *  the modified code is granted. Modifications are to be distributed by
+ *  using the file 'license.txt' as a template to modify the file header.
+ *  'license.txt' is available in the official MAPM distribution.
+ *
+ *  This software is provided "as is" without express or implied warranty.
+ */
+
+/*
+ *      $Id: mapmgues.c,v 1.20 2007/12/03 01:52:55 mike Exp $
+ *
+ *      This file contains the functions that generate the initial 
+ *	'guesses' for the sqrt, cbrt, log, arcsin, and arccos functions.
+ *
+ *      $Log: mapmgues.c,v $
+ *      Revision 1.20  2007/12/03 01:52:55  mike
+ *      Update license
+ *
+ *      Revision 1.19  2003/07/21 20:03:49  mike
+ *      check for invalid inputs to _set_double
+ *
+ *      Revision 1.18  2003/05/01 21:58:45  mike
+ *      remove math.h
+ *
+ *      Revision 1.17  2003/04/16 16:52:47  mike
+ *      change cbrt guess to use reciprocal value for new cbrt algorithm
+ *
+ *      Revision 1.16  2003/04/11 14:18:13  mike
+ *      add comments
+ *
+ *      Revision 1.15  2003/04/10 22:28:35  mike
+ *      .
+ *
+ *      Revision 1.14  2003/04/09 21:33:19  mike
+ *      induce same error for asin and acos
+ *
+ *      Revision 1.13  2003/04/09 20:11:38  mike
+ *      induce error of 10 ^ -5 in log guess for known starting
+ *      point in the iterative algorithm
+ *
+ *      Revision 1.12  2003/03/27 19:32:59  mike
+ *      simplify log guess since caller guarantee's limited input magnitude
+ *
+ *      Revision 1.11  2002/11/03 21:45:53  mike
+ *      Updated function parameters to use the modern style
+ *
+ *      Revision 1.10  2001/03/20 22:08:27  mike
+ *      delete unneeded logic in asin guess
+ *
+ *      Revision 1.9  2000/09/26 17:05:11  mike
+ *      guess 1/sqrt instead of sqrt due to new sqrt algorithm
+ *
+ *      Revision 1.8  2000/04/10 21:13:13  mike
+ *      minor tweaks to log_guess
+ *
+ *      Revision 1.7  2000/04/03 17:25:45  mike
+ *      added function to estimate the cube root (cbrt)
+ *
+ *      Revision 1.6  1999/07/18 01:57:35  mike
+ *      adjust arc-sin guess for small exponents
+ *
+ *      Revision 1.5  1999/07/09 22:32:50  mike
+ *      optimize some functions
+ *
+ *      Revision 1.4  1999/05/12 21:22:27  mike
+ *      add more comments
+ *
+ *      Revision 1.3  1999/05/12 21:00:51  mike
+ *      added new sqrt guess function
+ *
+ *      Revision 1.2  1999/05/11 02:10:12  mike
+ *      added some comments
+ *
+ *      Revision 1.1  1999/05/10 20:56:31  mike
+ *      Initial revision
+ */
+
+#include "m_apm_lc.h"
+
+/****************************************************************************/
+void	M_get_sqrt_guess(M_APM r, M_APM a)
+{
+char	buf[48];
+double  dd;
+
+m_apm_to_string(buf, 15, a);
+dd = atof(buf);                     /* sqrt algorithm actually finds 1/sqrt */
+m_apm_set_double(r, (1.0 / sqrt(dd)));
+}
+/****************************************************************************/
+/*
+ *	for cbrt, log, asin, and acos we induce an error of 10 ^ -5.
+ *	this enables the iterative routine to be more efficient
+ *	by knowing exactly how accurate the initial guess is.
+ *
+ *	this also prevents some corner conditions where the iterative 
+ *	functions may terminate too soon.
+ */
+/****************************************************************************/
+void	M_get_cbrt_guess(M_APM r, M_APM a)
+{
+char	buf[48];
+double  dd;
+
+m_apm_to_string(buf, 15, a);
+dd = atof(buf);
+dd = log(dd) / 3.0;                 /* cbrt algorithm actually finds 1/cbrt */
+m_apm_set_double(r, (1.00001 / exp(dd)));
+}
+/****************************************************************************/
+void	M_get_log_guess(M_APM r, M_APM a)
+{
+char	buf[48];
+double  dd;
+
+m_apm_to_string(buf, 15, a);
+dd = atof(buf);
+m_apm_set_double(r, (1.00001 * log(dd)));        /* induce error of 10 ^ -5 */
+}
+/****************************************************************************/
+/*
+ *	the implementation of the asin & acos functions 
+ *	guarantee that 'a' is always < 0.85, so it is 
+ *	safe to multiply by a number > 1
+ */
+void	M_get_asin_guess(M_APM r, M_APM a)
+{
+char	buf[48];
+double  dd;
+
+m_apm_to_string(buf, 15, a);
+dd = atof(buf);
+m_apm_set_double(r, (1.00001 * asin(dd)));       /* induce error of 10 ^ -5 */
+}
+/****************************************************************************/
+void	M_get_acos_guess(M_APM r, M_APM a)
+{
+char	buf[48];
+double  dd;
+
+m_apm_to_string(buf, 15, a);
+dd = atof(buf);
+m_apm_set_double(r, (1.00001 * acos(dd)));       /* induce error of 10 ^ -5 */
+}
+/****************************************************************************/
+/*
+	convert a C 'double' into an M_APM value. 
+*/
+void	m_apm_set_double(M_APM atmp, double dd)
+{
+char	*cp, *p, *ps, buf[64];
+
+if (dd == 0.0)                     /* special case for 0 exactly */
+   M_set_to_zero(atmp);
+else
+  {
+   sprintf(buf, "%.14E", dd);
+   
+   if ((cp = strstr(buf, "E")) == NULL)
+     {
+      M_apm_log_error_msg(M_APM_RETURN,
+      "\'m_apm_set_double\', Invalid double input (likely a NAN or +/- INF)");
+
+      M_set_to_zero(atmp);
+      return;
+     }
+
+   if (atoi(cp + sizeof(char)) == 0)
+     *cp = '\0';
+   
+   p = cp;
+   
+   while (TRUE)
+     {
+      p--;
+      if (*p == '0' || *p == '.')
+        *p = ' ';
+      else
+        break;
+     }
+   
+   ps = buf;
+   p  = buf;
+   
+   while (TRUE)
+     {
+      if ((*p = *ps) == '\0')
+        break;
+   
+      if (*ps++ != ' ')
+        p++;
+     }
+
+   m_apm_set_string(atmp, buf);
+  }
+}
+/****************************************************************************/

+ 155 - 0
mapm/src/mapmhasn.c

@@ -0,0 +1,155 @@
+
+/* 
+ *  M_APM  -  mapmhasn.c
+ *
+ *  Copyright (C) 2000 - 2007   Michael C. Ring
+ *
+ *  Permission to use, copy, and distribute this software and its
+ *  documentation for any purpose with or without fee is hereby granted,
+ *  provided that the above copyright notice appear in all copies and
+ *  that both that copyright notice and this permission notice appear
+ *  in supporting documentation.
+ *
+ *  Permission to modify the software is granted. Permission to distribute
+ *  the modified code is granted. Modifications are to be distributed by
+ *  using the file 'license.txt' as a template to modify the file header.
+ *  'license.txt' is available in the official MAPM distribution.
+ *
+ *  This software is provided "as is" without express or implied warranty.
+ */
+
+/*
+ *      $Id: mapmhasn.c,v 1.7 2007/12/03 01:53:33 mike Exp $
+ *
+ *      This file contains the Inverse Hyperbolic SIN, COS, & TAN functions.
+ *
+ *      $Log: mapmhasn.c,v $
+ *      Revision 1.7  2007/12/03 01:53:33  mike
+ *      Update license
+ *
+ *      Revision 1.6  2003/07/24 16:28:50  mike
+ *      update arcsinh
+ *
+ *      Revision 1.5  2003/07/23 23:08:27  mike
+ *      fix problem with arcsinh when input is a very large
+ *      negative number.
+ *
+ *      Revision 1.4  2003/07/21 20:36:33  mike
+ *      Modify error messages to be in a consistent format.
+ *
+ *      Revision 1.3  2003/03/31 21:53:21  mike
+ *      call generic error handling function
+ *
+ *      Revision 1.2  2002/11/03 21:25:03  mike
+ *      Updated function parameters to use the modern style
+ *
+ *      Revision 1.1  2000/04/03 18:16:29  mike
+ *      Initial revision
+ */
+
+#include "m_apm_lc.h"
+
+/****************************************************************************/
+/*
+ *      arcsinh(x) == log [ x + sqrt(x^2 + 1) ]
+ *
+ *      also, use arcsinh(-x) == -arcsinh(x)
+ */
+void	m_apm_arcsinh(M_APM rr, int places, M_APM aa)
+{
+M_APM	tmp0, tmp1, tmp2;
+
+/* result is 0 if input is 0 */
+
+if (aa->m_apm_sign == 0)
+  {
+   M_set_to_zero(rr);
+   return;
+  }
+
+tmp0 = M_get_stack_var();
+tmp1 = M_get_stack_var();
+tmp2 = M_get_stack_var();
+
+m_apm_absolute_value(tmp0, aa);
+m_apm_multiply(tmp1, tmp0, tmp0);
+m_apm_add(tmp2, tmp1, MM_One);
+m_apm_sqrt(tmp1, (places + 6), tmp2);
+m_apm_add(tmp2, tmp0, tmp1);
+m_apm_log(rr, places, tmp2);
+
+rr->m_apm_sign = aa->m_apm_sign; 			  /* fix final sign */
+
+M_restore_stack(3);
+}
+/****************************************************************************/
+/*
+ *      arccosh(x) == log [ x + sqrt(x^2 - 1) ]
+ *
+ *      x >= 1.0
+ */
+void	m_apm_arccosh(M_APM rr, int places, M_APM aa)
+{
+M_APM	tmp1, tmp2;
+int     ii;
+
+ii = m_apm_compare(aa, MM_One);
+
+if (ii == -1)       /* x < 1 */
+  {
+   M_apm_log_error_msg(M_APM_RETURN, "\'m_apm_arccosh\', Argument < 1");
+   M_set_to_zero(rr);
+   return;
+  }
+
+tmp1 = M_get_stack_var();
+tmp2 = M_get_stack_var();
+
+m_apm_multiply(tmp1, aa, aa);
+m_apm_subtract(tmp2, tmp1, MM_One);
+m_apm_sqrt(tmp1, (places + 6), tmp2);
+m_apm_add(tmp2, aa, tmp1);
+m_apm_log(rr, places, tmp2);
+
+M_restore_stack(2);
+}
+/****************************************************************************/
+/*
+ *      arctanh(x) == 0.5 * log [ (1 + x) / (1 - x) ]
+ *
+ *      |x| < 1.0
+ */
+void	m_apm_arctanh(M_APM rr, int places, M_APM aa)
+{
+M_APM	tmp1, tmp2, tmp3;
+int     ii, local_precision;
+
+tmp1 = M_get_stack_var();
+
+m_apm_absolute_value(tmp1, aa);
+
+ii = m_apm_compare(tmp1, MM_One);
+
+if (ii >= 0)       /* |x| >= 1.0 */
+  {
+   M_apm_log_error_msg(M_APM_RETURN, "\'m_apm_arctanh\', |Argument| >= 1");
+   M_set_to_zero(rr);
+   M_restore_stack(1);
+   return;
+  }
+
+tmp2 = M_get_stack_var();
+tmp3 = M_get_stack_var();
+
+local_precision = places + 8;
+
+m_apm_add(tmp1, MM_One, aa);
+m_apm_subtract(tmp2, MM_One, aa);
+m_apm_divide(tmp3, local_precision, tmp1, tmp2);
+m_apm_log(tmp2, local_precision, tmp3);
+m_apm_multiply(tmp1, tmp2, MM_0_5);
+m_apm_round(rr, places, tmp1);
+
+M_restore_stack(3);
+}
+/****************************************************************************/

+ 113 - 0
mapm/src/mapmhsin.c

@@ -0,0 +1,113 @@
+
+/* 
+ *  M_APM  -  mapmhsin.c
+ *
+ *  Copyright (C) 2000 - 2007   Michael C. Ring
+ *
+ *  Permission to use, copy, and distribute this software and its
+ *  documentation for any purpose with or without fee is hereby granted,
+ *  provided that the above copyright notice appear in all copies and
+ *  that both that copyright notice and this permission notice appear
+ *  in supporting documentation.
+ *
+ *  Permission to modify the software is granted. Permission to distribute
+ *  the modified code is granted. Modifications are to be distributed by
+ *  using the file 'license.txt' as a template to modify the file header.
+ *  'license.txt' is available in the official MAPM distribution.
+ *
+ *  This software is provided "as is" without express or implied warranty.
+ */
+
+/*
+ *      $Id: mapmhsin.c,v 1.4 2007/12/03 01:54:06 mike Exp $
+ *
+ *      This file contains the Hyperbolic SIN, COS, & TAN functions.
+ *
+ *      $Log: mapmhsin.c,v $
+ *      Revision 1.4  2007/12/03 01:54:06  mike
+ *      Update license
+ *
+ *      Revision 1.3  2002/11/03 21:29:20  mike
+ *      Updated function parameters to use the modern style
+ *
+ *      Revision 1.2  2000/09/23 19:52:56  mike
+ *      change divide call to reciprocal
+ *
+ *      Revision 1.1  2000/04/03 18:16:26  mike
+ *      Initial revision
+ */
+
+#include "m_apm_lc.h"
+
+/****************************************************************************/
+/*
+ *      sinh(x) == 0.5 * [ exp(x) - exp(-x) ]
+ */
+void	m_apm_sinh(M_APM rr, int places, M_APM aa)
+{
+M_APM	tmp1, tmp2, tmp3;
+int     local_precision;
+
+tmp1 = M_get_stack_var();
+tmp2 = M_get_stack_var();
+tmp3 = M_get_stack_var();
+
+local_precision = places + 4;
+
+m_apm_exp(tmp1, local_precision, aa);
+m_apm_reciprocal(tmp2, local_precision, tmp1);
+m_apm_subtract(tmp3, tmp1, tmp2);
+m_apm_multiply(tmp1, tmp3, MM_0_5);
+m_apm_round(rr, places, tmp1);
+
+M_restore_stack(3);
+}
+/****************************************************************************/
+/*
+ *      cosh(x) == 0.5 * [ exp(x) + exp(-x) ]
+ */
+void	m_apm_cosh(M_APM rr, int places, M_APM aa)
+{
+M_APM	tmp1, tmp2, tmp3;
+int     local_precision;
+
+tmp1 = M_get_stack_var();
+tmp2 = M_get_stack_var();
+tmp3 = M_get_stack_var();
+
+local_precision = places + 4;
+
+m_apm_exp(tmp1, local_precision, aa);
+m_apm_reciprocal(tmp2, local_precision, tmp1);
+m_apm_add(tmp3, tmp1, tmp2);
+m_apm_multiply(tmp1, tmp3, MM_0_5);
+m_apm_round(rr, places, tmp1);
+
+M_restore_stack(3);
+}
+/****************************************************************************/
+/*
+ *      tanh(x) == [ exp(x) - exp(-x) ]  /  [ exp(x) + exp(-x) ]
+ */
+void	m_apm_tanh(M_APM rr, int places, M_APM aa)
+{
+M_APM	tmp1, tmp2, tmp3, tmp4;
+int     local_precision;
+
+tmp1 = M_get_stack_var();
+tmp2 = M_get_stack_var();
+tmp3 = M_get_stack_var();
+tmp4 = M_get_stack_var();
+
+local_precision = places + 4;
+
+m_apm_exp(tmp1, local_precision, aa);
+m_apm_reciprocal(tmp2, local_precision, tmp1);
+m_apm_subtract(tmp3, tmp1, tmp2);
+m_apm_add(tmp4, tmp1, tmp2);
+m_apm_divide(tmp1, local_precision, tmp3, tmp4);
+m_apm_round(rr, places, tmp1);
+
+M_restore_stack(4);
+}
+/****************************************************************************/

+ 117 - 0
mapm/src/mapmipwr.c

@@ -0,0 +1,117 @@
+
+/* 
+ *  M_APM  -  mapmipwr.c
+ *
+ *  Copyright (C) 1999 - 2007   Michael C. Ring
+ *
+ *  Permission to use, copy, and distribute this software and its
+ *  documentation for any purpose with or without fee is hereby granted,
+ *  provided that the above copyright notice appear in all copies and
+ *  that both that copyright notice and this permission notice appear
+ *  in supporting documentation.
+ *
+ *  Permission to modify the software is granted. Permission to distribute
+ *  the modified code is granted. Modifications are to be distributed by
+ *  using the file 'license.txt' as a template to modify the file header.
+ *  'license.txt' is available in the official MAPM distribution.
+ *
+ *  This software is provided "as is" without express or implied warranty.
+ */
+
+/*
+ *      $Id: mapmipwr.c,v 1.6 2007/12/03 01:54:39 mike Exp $
+ *
+ *      This file contains the Integer Power function.
+ *
+ *      $Log: mapmipwr.c,v $
+ *      Revision 1.6  2007/12/03 01:54:39  mike
+ *      Update license
+ *
+ *      Revision 1.5  2002/11/03 21:10:32  mike
+ *      Updated function parameters to use the modern style
+ *
+ *      Revision 1.4  2000/09/23 19:46:04  mike
+ *      change divide call to reciprocal
+ *
+ *      Revision 1.3  2000/05/24 17:03:35  mike
+ *      return 1 when input is 0^0
+ *
+ *      Revision 1.2  1999/09/18 01:34:35  mike
+ *      minor tweaks
+ *
+ *      Revision 1.1  1999/09/18 01:33:09  mike
+ *      Initial revision
+ */
+
+#include "m_apm_lc.h"
+
+/****************************************************************************/
+void	m_apm_integer_pow(M_APM rr, int places, M_APM aa, int mexp)
+{
+M_APM   tmp0, tmpy, tmpz;
+int	nexp, ii, signflag, local_precision;
+
+if (mexp == 0)
+  {
+   m_apm_copy(rr, MM_One);
+   return;
+  }
+else
+  {
+   if (mexp > 0)
+     {
+      signflag = 0;
+      nexp     = mexp;
+     }
+   else
+     {
+      signflag = 1;
+      nexp     = -mexp;
+     }
+  }
+
+if (aa->m_apm_sign == 0)
+  {
+   M_set_to_zero(rr);
+   return;
+  }
+
+tmp0 = M_get_stack_var();
+tmpy = M_get_stack_var();
+tmpz = M_get_stack_var();
+
+local_precision = places + 8;
+
+m_apm_copy(tmpy, MM_One);
+m_apm_copy(tmpz, aa);
+
+while (TRUE)
+  {
+   ii   = nexp & 1;
+   nexp = nexp >> 1;
+
+   if (ii != 0)                       /* exponent -was- odd */
+     {
+      m_apm_multiply(tmp0, tmpy, tmpz);
+      m_apm_round(tmpy, local_precision, tmp0);
+
+      if (nexp == 0)
+        break;
+     }
+
+   m_apm_multiply(tmp0, tmpz, tmpz);
+   m_apm_round(tmpz, local_precision, tmp0);
+  }
+
+if (signflag)
+  {
+   m_apm_reciprocal(rr, places, tmpy);
+  }
+else
+  {
+   m_apm_round(rr, places, tmpy);
+  }
+
+M_restore_stack(3);
+}
+/****************************************************************************/

+ 140 - 0
mapm/src/mapmistr.c

@@ -0,0 +1,140 @@
+
+/* 
+ *  M_APM  -  mapmistr.c
+ *
+ *  Copyright (C) 1999 - 2007   Michael C. Ring
+ *
+ *  Permission to use, copy, and distribute this software and its
+ *  documentation for any purpose with or without fee is hereby granted,
+ *  provided that the above copyright notice appear in all copies and
+ *  that both that copyright notice and this permission notice appear
+ *  in supporting documentation.
+ *
+ *  Permission to modify the software is granted. Permission to distribute
+ *  the modified code is granted. Modifications are to be distributed by
+ *  using the file 'license.txt' as a template to modify the file header.
+ *  'license.txt' is available in the official MAPM distribution.
+ *
+ *  This software is provided "as is" without express or implied warranty.
+ */
+
+/*
+ *      $Id: mapmistr.c,v 1.9 2007/12/03 01:55:27 mike Exp $
+ *
+ *      This file contains M_APM -> integer string function
+ *
+ *      $Log: mapmistr.c,v $
+ *      Revision 1.9  2007/12/03 01:55:27  mike
+ *      Update license
+ *
+ *      Revision 1.8  2003/07/21 20:37:09  mike
+ *      Modify error messages to be in a consistent format.
+ *
+ *      Revision 1.7  2003/03/31 21:52:07  mike
+ *      call generic error handling function
+ *
+ *      Revision 1.6  2002/11/03 22:28:02  mike
+ *      Updated function parameters to use the modern style
+ *
+ *      Revision 1.5  2001/08/06 16:58:20  mike
+ *      improve the new function
+ *
+ *      Revision 1.4  2001/08/05 23:18:48  mike
+ *      fix function when input is not an integer but the
+ *      number is close to rounding upwards (NNN.9999999999....)
+ *
+ *      Revision 1.3  2000/02/03 22:48:38  mike
+ *      use MAPM_* generic memory function
+ *
+ *      Revision 1.2  1999/07/18 01:33:04  mike
+ *      minor tweak to code alignment
+ *
+ *      Revision 1.1  1999/07/12 02:06:08  mike
+ *      Initial revision
+ */
+
+#include "m_apm_lc.h"
+
+/****************************************************************************/
+void	m_apm_to_integer_string(char *s, M_APM mtmp)
+{
+void    *vp;
+UCHAR	*ucp, numdiv, numrem;
+char	*cp, *p, sbuf[128];
+int	ct, dl, numb, ii;
+
+vp = NULL;
+ct = mtmp->m_apm_exponent;
+dl = mtmp->m_apm_datalength;
+
+/*
+ *  if |input| < 1, result is "0"
+ */
+
+if (ct <= 0 || mtmp->m_apm_sign == 0)
+  {
+   s[0] = '0';
+   s[1] = '\0';
+   return;
+  }
+
+if (ct > 112)
+  {
+   if ((vp = (void *)MAPM_MALLOC((ct + 32) * sizeof(char))) == NULL)
+     {
+      /* fatal, this does not return */
+
+      M_apm_log_error_msg(M_APM_FATAL, 
+                          "\'m_apm_to_integer_string\', Out of memory");
+     }
+
+   cp = (char *)vp;
+  }
+else
+  {
+   cp = sbuf;
+  }
+
+p  = cp;
+ii = 0;
+
+/* handle a negative number */
+
+if (mtmp->m_apm_sign == -1)
+  {
+   ii = 1;
+   *p++ = '-';
+  }
+
+/* get num-bytes of data (#digits / 2) to use in the string */
+
+if (ct > dl)
+  numb = (dl + 1) >> 1;
+else
+  numb = (ct + 1) >> 1;
+
+ucp = mtmp->m_apm_data;
+
+while (TRUE)
+  {
+   M_get_div_rem_10((int)(*ucp++), &numdiv, &numrem);
+
+   *p++ = numdiv + '0';
+   *p++ = numrem + '0';
+
+   if (--numb == 0)
+     break;
+  }
+
+/* pad with trailing zeros if the exponent > datalength */
+ 
+if (ct > dl)
+  memset(p, '0', (ct + 1 - dl));
+
+cp[ct + ii] = '\0';
+strcpy(s, cp);
+
+if (vp != NULL)
+  MAPM_FREE(vp);
+}
+/****************************************************************************/

+ 120 - 0
mapm/src/mapmpwr2.c

@@ -0,0 +1,120 @@
+
+/* 
+ *  M_APM  -  mapmpwr2.c
+ *
+ *  Copyright (C) 2002 - 2007   Michael C. Ring
+ *
+ *  Permission to use, copy, and distribute this software and its
+ *  documentation for any purpose with or without fee is hereby granted,
+ *  provided that the above copyright notice appear in all copies and
+ *  that both that copyright notice and this permission notice appear
+ *  in supporting documentation.
+ *
+ *  Permission to modify the software is granted. Permission to distribute
+ *  the modified code is granted. Modifications are to be distributed by
+ *  using the file 'license.txt' as a template to modify the file header.
+ *  'license.txt' is available in the official MAPM distribution.
+ *
+ *  This software is provided "as is" without express or implied warranty.
+ */
+
+/*
+ *      $Id: mapmpwr2.c,v 1.4 2007/12/03 01:56:21 mike Exp $
+ *
+ *      This file contains the Integer Power function and the result 
+ *	is NOT ROUNDED. The exponent must be an integer >= zero.
+ *
+ *      This will typically be used in an application where full integer
+ *	precision is required to be maintained.
+ *
+ *      $Log: mapmpwr2.c,v $
+ *      Revision 1.4  2007/12/03 01:56:21  mike
+ *      Update license
+ *
+ *      Revision 1.3  2003/07/21 20:38:06  mike
+ *      Modify error messages to be in a consistent format.
+ *
+ *      Revision 1.2  2003/03/31 21:51:23  mike
+ *      call generic error handling function
+ *
+ *      Revision 1.1  2002/11/03 21:02:04  mike
+ *      Initial revision
+ */
+
+#include "m_apm_lc.h"
+
+/****************************************************************************/
+void	m_apm_integer_pow_nr(M_APM rr, M_APM aa, int mexp)
+{
+M_APM   tmp0, tmpy, tmpz;
+int	nexp, ii;
+
+if (mexp == 0)
+  {
+   m_apm_copy(rr, MM_One);
+   return;
+  }
+else
+  {
+   if (mexp < 0)
+     {
+      M_apm_log_error_msg(M_APM_RETURN,
+            "\'m_apm_integer_pow_nr\', Negative exponent");
+
+      M_set_to_zero(rr);
+      return;
+     }
+  }
+
+if (mexp == 1)
+  {
+   m_apm_copy(rr, aa);
+   return;
+  }
+
+if (mexp == 2)
+  {
+   m_apm_multiply(rr, aa, aa);
+   return;
+  }
+
+nexp = mexp;
+
+if (aa->m_apm_sign == 0)
+  {
+   M_set_to_zero(rr);
+   return;
+  }
+
+tmp0 = M_get_stack_var();
+tmpy = M_get_stack_var();
+tmpz = M_get_stack_var();
+
+m_apm_copy(tmpy, MM_One);
+m_apm_copy(tmpz, aa);
+
+while (TRUE)
+  {
+   ii   = nexp & 1;
+   nexp = nexp >> 1;
+
+   if (ii != 0)                       /* exponent -was- odd */
+     {
+      m_apm_multiply(tmp0, tmpy, tmpz);
+
+      if (nexp == 0)
+        break;
+
+      m_apm_copy(tmpy, tmp0);
+     }
+
+   m_apm_multiply(tmp0, tmpz, tmpz);
+   m_apm_copy(tmpz, tmp0);
+  }
+
+m_apm_copy(rr, tmp0);
+
+M_restore_stack(3);
+}
+/****************************************************************************/
+

+ 191 - 0
mapm/src/mapmrsin.c

@@ -0,0 +1,191 @@
+
+/* 
+ *  M_APM  -  mapmrsin.c
+ *
+ *  Copyright (C) 1999 - 2007   Michael C. Ring
+ *
+ *  Permission to use, copy, and distribute this software and its
+ *  documentation for any purpose with or without fee is hereby granted,
+ *  provided that the above copyright notice appear in all copies and
+ *  that both that copyright notice and this permission notice appear
+ *  in supporting documentation.
+ *
+ *  Permission to modify the software is granted. Permission to distribute
+ *  the modified code is granted. Modifications are to be distributed by
+ *  using the file 'license.txt' as a template to modify the file header.
+ *  'license.txt' is available in the official MAPM distribution.
+ *
+ *  This software is provided "as is" without express or implied warranty.
+ */
+
+/*
+ *      $Id: mapmrsin.c,v 1.8 2007/12/03 01:57:00 mike Exp $
+ *
+ *      This file contains the basic series expansion functions for 
+ *	the SIN / COS functions.
+ *
+ *      $Log: mapmrsin.c,v $
+ *      Revision 1.8  2007/12/03 01:57:00  mike
+ *      Update license
+ *
+ *      Revision 1.7  2003/06/08 18:22:09  mike
+ *      optimize the raw sin algorithm
+ *
+ *      Revision 1.6  2002/11/03 21:58:27  mike
+ *      Updated function parameters to use the modern style
+ *
+ *      Revision 1.5  2001/07/10 22:14:43  mike
+ *      optimize raw_sin & cos by using fewer digits
+ *      as subsequent terms get smaller
+ *
+ *      Revision 1.4  2000/03/30 21:53:48  mike
+ *      change compare to terminate series expansion using ints instead
+ *      of MAPM numbers
+ *
+ *      Revision 1.3  1999/06/20 16:23:10  mike
+ *      changed local static variables to MAPM stack variables
+ *
+ *      Revision 1.2  1999/05/12 21:06:36  mike
+ *      changed global var names
+ *
+ *      Revision 1.1  1999/05/10 20:56:31  mike
+ *      Initial revision
+ */
+
+#include "m_apm_lc.h"
+
+/****************************************************************************/
+/*
+                                  x^3     x^5     x^7     x^9
+		 sin(x)  =  x  -  ---  +  ---  -  ---  +  ---  ...
+                                   3!      5!      7!      9!
+*/
+void	M_raw_sin(M_APM rr, int places, M_APM xx)
+{
+M_APM	sum, term, tmp2, tmp7, tmp8;
+int     tolerance, flag, local_precision, dplaces;
+long	m1, m2;
+
+sum  = M_get_stack_var();
+term = M_get_stack_var();
+tmp2 = M_get_stack_var();
+tmp7 = M_get_stack_var();
+tmp8 = M_get_stack_var();
+
+m_apm_copy(sum, xx);
+m_apm_copy(term, xx);
+m_apm_multiply(tmp8, xx, xx);
+m_apm_round(tmp2, (places + 6), tmp8);
+
+dplaces   = (places + 8) - xx->m_apm_exponent;
+tolerance = xx->m_apm_exponent - (places + 4);
+
+m1   = 2L;
+flag = 0;
+
+while (TRUE)
+  {
+   m_apm_multiply(tmp8, term, tmp2);
+
+   if ((tmp8->m_apm_exponent < tolerance) || (tmp8->m_apm_sign == 0))
+     break;
+
+   local_precision = dplaces + term->m_apm_exponent;
+
+   if (local_precision < 20)
+     local_precision = 20;
+
+   m2 = m1 * (m1 + 1);
+   m_apm_set_long(tmp7, m2);
+
+   m_apm_divide(term, local_precision, tmp8, tmp7);
+
+   if (flag == 0)
+     {
+      m_apm_subtract(tmp7, sum, term);
+      m_apm_copy(sum, tmp7);
+     }
+   else
+     {
+      m_apm_add(tmp7, sum, term);
+      m_apm_copy(sum, tmp7);
+     }
+
+   m1 += 2;
+   flag = 1 - flag;
+  }
+
+m_apm_round(rr, places, sum);
+M_restore_stack(5);
+}
+/****************************************************************************/
+/*
+                                  x^2     x^4     x^6     x^8
+		 cos(x)  =  1  -  ---  +  ---  -  ---  +  ---  ...
+                                   2!      4!      6!      8!
+*/
+void	M_raw_cos(M_APM rr, int places, M_APM xx)
+{
+M_APM	sum, term, tmp7, tmp8, tmp9;
+int     tolerance, flag, local_precision, prev_exp;
+long	m1, m2;
+
+sum  = M_get_stack_var();
+term = M_get_stack_var();
+tmp7 = M_get_stack_var();
+tmp8 = M_get_stack_var();
+tmp9 = M_get_stack_var();
+
+m_apm_copy(sum, MM_One);
+m_apm_copy(term, MM_One);
+
+m_apm_multiply(tmp8, xx, xx);
+m_apm_round(tmp9, (places + 6), tmp8);
+
+local_precision = places + 8;
+tolerance       = -(places + 4);
+prev_exp        = 0;
+
+m1   = 1L;
+flag = 0;
+
+while (TRUE)
+  {
+   m2 = m1 * (m1 + 1);
+   m_apm_set_long(tmp7, m2);
+
+   m_apm_multiply(tmp8, term, tmp9);
+   m_apm_divide(term, local_precision, tmp8, tmp7);
+
+   if (flag == 0)
+     {
+      m_apm_subtract(tmp7, sum, term);
+      m_apm_copy(sum, tmp7);
+     }
+   else
+     {
+      m_apm_add(tmp7, sum, term);
+      m_apm_copy(sum, tmp7);
+     }
+
+   if ((term->m_apm_exponent < tolerance) || (term->m_apm_sign == 0))
+     break;
+
+   if (m1 != 1L)
+     {
+      local_precision = local_precision + term->m_apm_exponent - prev_exp;
+
+      if (local_precision < 20)
+        local_precision = 20;
+     }
+
+   prev_exp = term->m_apm_exponent;
+
+   m1 += 2;
+   flag = 1 - flag;
+  }
+
+m_apm_round(rr, places, sum);
+M_restore_stack(5);
+}
+/****************************************************************************/

+ 190 - 0
mapm/src/mapmsqrt.c

@@ -0,0 +1,190 @@
+
+/* 
+ *  M_APM  -  mapmsqrt.c
+ *
+ *  Copyright (C) 1999 - 2007   Michael C. Ring
+ *
+ *  Permission to use, copy, and distribute this software and its
+ *  documentation for any purpose with or without fee is hereby granted,
+ *  provided that the above copyright notice appear in all copies and
+ *  that both that copyright notice and this permission notice appear
+ *  in supporting documentation.
+ *
+ *  Permission to modify the software is granted. Permission to distribute
+ *  the modified code is granted. Modifications are to be distributed by
+ *  using the file 'license.txt' as a template to modify the file header.
+ *  'license.txt' is available in the official MAPM distribution.
+ *
+ *  This software is provided "as is" without express or implied warranty.
+ */
+
+/*
+ *      $Id: mapmsqrt.c,v 1.19 2007/12/03 01:57:31 mike Exp $
+ *
+ *      This file contains the SQRT function.
+ *
+ *      $Log: mapmsqrt.c,v $
+ *      Revision 1.19  2007/12/03 01:57:31  mike
+ *      Update license
+ *
+ *      Revision 1.18  2003/07/21 20:39:00  mike
+ *      Modify error messages to be in a consistent format.
+ *
+ *      Revision 1.17  2003/05/07 16:36:04  mike
+ *      simplify 'nexp' logic
+ *
+ *      Revision 1.16  2003/03/31 21:50:14  mike
+ *      call generic error handling function
+ *
+ *      Revision 1.15  2003/03/11 21:29:00  mike
+ *      round an intermediate result for faster runtime.
+ *
+ *      Revision 1.14  2002/11/03 22:00:46  mike
+ *      Updated function parameters to use the modern style
+ *
+ *      Revision 1.13  2001/07/10 22:50:31  mike
+ *      minor optimization
+ *
+ *      Revision 1.12  2000/09/26 18:32:04  mike
+ *      use new algorithm which only uses multiply and subtract
+ *      (avoids the slower version which used division)
+ *
+ *      Revision 1.11  2000/07/11 17:56:22  mike
+ *      make better estimate for initial precision
+ *
+ *      Revision 1.10  1999/07/21 02:48:45  mike
+ *      added some comments
+ *
+ *      Revision 1.9  1999/07/19 00:25:44  mike
+ *      adjust local precision again
+ *
+ *      Revision 1.8  1999/07/19 00:09:41  mike
+ *      adjust local precision during loop
+ *
+ *      Revision 1.7  1999/07/18 22:57:08  mike
+ *      change to dynamically changing local precision and
+ *      change tolerance checks using integers
+ *
+ *      Revision 1.6  1999/06/19 21:18:00  mike
+ *      changed local static variables to MAPM stack variables
+ *
+ *      Revision 1.5  1999/05/31 01:40:39  mike
+ *      minor update to normalizing the exponent
+ *
+ *      Revision 1.4  1999/05/31 01:21:41  mike
+ *      optimize for large exponents
+ *
+ *      Revision 1.3  1999/05/12 20:59:35  mike
+ *      use a better 'guess' function
+ *
+ *      Revision 1.2  1999/05/10 21:15:26  mike
+ *      added some comments
+ *
+ *      Revision 1.1  1999/05/10 20:56:31  mike
+ *      Initial revision
+ */
+
+#include "m_apm_lc.h"
+
+/****************************************************************************/
+void	m_apm_sqrt(M_APM rr, int places, M_APM aa)
+{
+M_APM   last_x, guess, tmpN, tmp7, tmp8, tmp9;
+int	ii, bflag, nexp, tolerance, dplaces;
+
+if (aa->m_apm_sign <= 0)
+  {
+   if (aa->m_apm_sign == -1)
+     {
+      M_apm_log_error_msg(M_APM_RETURN, "\'m_apm_sqrt\', Negative argument");
+     }
+
+   M_set_to_zero(rr);
+   return;
+  }
+
+last_x = M_get_stack_var();
+guess  = M_get_stack_var();
+tmpN   = M_get_stack_var();
+tmp7   = M_get_stack_var();
+tmp8   = M_get_stack_var();
+tmp9   = M_get_stack_var();
+
+m_apm_copy(tmpN, aa);
+
+/* 
+    normalize the input number (make the exponent near 0) so
+    the 'guess' function will not over/under flow on large
+    magnitude exponents.
+*/
+
+nexp = aa->m_apm_exponent / 2;
+tmpN->m_apm_exponent -= 2 * nexp;
+
+M_get_sqrt_guess(guess, tmpN);    /* actually gets 1/sqrt guess */
+
+tolerance = places + 4;
+dplaces   = places + 16;
+bflag     = FALSE;
+
+m_apm_negate(last_x, MM_Ten);
+
+/*   Use the following iteration to calculate 1 / sqrt(N) :
+
+         X    =  0.5 * X * [ 3 - N * X^2 ]
+          n+1                    
+*/
+
+ii = 0;
+
+while (TRUE)
+  {
+   m_apm_multiply(tmp9, tmpN, guess);
+   m_apm_multiply(tmp8, tmp9, guess);
+   m_apm_round(tmp7, dplaces, tmp8);
+   m_apm_subtract(tmp9, MM_Three, tmp7);
+   m_apm_multiply(tmp8, tmp9, guess);
+   m_apm_multiply(tmp9, tmp8, MM_0_5);
+
+   if (bflag)
+     break;
+
+   m_apm_round(guess, dplaces, tmp9);
+
+   /* force at least 2 iterations so 'last_x' has valid data */
+
+   if (ii != 0)
+     {
+      m_apm_subtract(tmp7, guess, last_x);
+
+      if (tmp7->m_apm_sign == 0)
+        break;
+
+      /* 
+       *   if we are within a factor of 4 on the error term,
+       *   we will be accurate enough after the *next* iteration
+       *   is complete.  (note that the sign of the exponent on 
+       *   the error term will be a negative number).
+       */
+
+      if ((-4 * tmp7->m_apm_exponent) > tolerance)
+        bflag = TRUE;
+     }
+
+   m_apm_copy(last_x, guess);
+   ii++;
+  }
+
+/*
+ *    multiply by the starting number to get the final
+ *    sqrt and then adjust the exponent since we found
+ *    the sqrt of the normalized number.
+ */
+
+m_apm_multiply(tmp8, tmp9, tmpN);
+m_apm_round(rr, places, tmp8);
+rr->m_apm_exponent += nexp;
+
+M_restore_stack(6);
+}
+/****************************************************************************/

+ 142 - 0
mapm/src/mapmstck.c

@@ -0,0 +1,142 @@
+
+/* 
+ *  M_APM  -  mapmstck.c
+ *
+ *  Copyright (C) 1999 - 2007   Michael C. Ring
+ *
+ *  Permission to use, copy, and distribute this software and its
+ *  documentation for any purpose with or without fee is hereby granted,
+ *  provided that the above copyright notice appear in all copies and
+ *  that both that copyright notice and this permission notice appear
+ *  in supporting documentation.
+ *
+ *  Permission to modify the software is granted. Permission to distribute
+ *  the modified code is granted. Modifications are to be distributed by
+ *  using the file 'license.txt' as a template to modify the file header.
+ *  'license.txt' is available in the official MAPM distribution.
+ *
+ *  This software is provided "as is" without express or implied warranty.
+ */
+
+/*
+ *      $Id: mapmstck.c,v 1.11 2007/12/03 01:58:05 mike Exp $
+ *
+ *      This file contains the stack implementation for using 
+ *	local M_APM variables.
+ *
+ *      $Log: mapmstck.c,v $
+ *      Revision 1.11  2007/12/03 01:58:05  mike
+ *      Update license
+ *
+ *      Revision 1.10  2003/07/21 20:39:38  mike
+ *      Modify error messages to be in a consistent format.
+ *
+ *      Revision 1.9  2003/03/31 21:49:08  mike
+ *      call generic error handling function
+ *
+ *      Revision 1.8  2002/11/03 22:42:05  mike
+ *      Updated function parameters to use the modern style
+ *
+ *      Revision 1.7  2002/05/17 22:05:00  mike
+ *      the stack is now dynamically allocated and will grow
+ *      at run-time if needed
+ *
+ *      Revision 1.6  2001/07/16 19:47:04  mike
+ *      add function M_free_all_stck
+ *
+ *      Revision 1.5  2000/09/23 19:27:52  mike
+ *      increase stack size for new functionality
+ *
+ *      Revision 1.4  1999/07/09 00:04:47  mike
+ *      tweak stack again
+ *
+ *      Revision 1.3  1999/07/09 00:02:24  mike
+ *      increase stack size for new functions
+ *
+ *      Revision 1.2  1999/06/20 21:13:18  mike
+ *      comment out printf debug and set max stack depth
+ *
+ *      Revision 1.1  1999/06/19 20:32:43  mike
+ *      Initial revision
+ */
+
+#include "m_apm_lc.h"
+
+static	int	M_stack_ptr  = -1;
+static	int	M_last_init  = -1;
+static	int	M_stack_size = 0;
+
+static  char    *M_stack_err_msg = "\'M_get_stack_var\', Out of memory";
+
+static	M_APM	*M_stack_array;
+
+/****************************************************************************/
+void	M_free_all_stck()
+{
+int	k;
+
+if (M_last_init >= 0)
+  {
+   for (k=0; k <= M_last_init; k++)
+     m_apm_free(M_stack_array[k]);
+
+   M_stack_ptr  = -1;
+   M_last_init  = -1;
+   M_stack_size = 0;
+
+   MAPM_FREE(M_stack_array);
+  }
+}
+/****************************************************************************/
+M_APM	M_get_stack_var()
+{
+void    *vp;
+
+if (++M_stack_ptr > M_last_init)
+  {
+   if (M_stack_size == 0)
+     {
+      M_stack_size = 18;
+      if ((vp = MAPM_MALLOC(M_stack_size * sizeof(M_APM))) == NULL)
+        {
+         /* fatal, this does not return */
+
+         M_apm_log_error_msg(M_APM_FATAL, M_stack_err_msg);
+        }
+
+      M_stack_array = (M_APM *)vp;
+     }
+
+   if ((M_last_init + 4) >= M_stack_size)
+     {
+      M_stack_size += 12;
+      if ((vp = MAPM_REALLOC(M_stack_array, 
+      			    (M_stack_size * sizeof(M_APM)))) == NULL)
+        {
+         /* fatal, this does not return */
+
+         M_apm_log_error_msg(M_APM_FATAL, M_stack_err_msg);
+        }
+
+      M_stack_array = (M_APM *)vp;
+     }
+
+   M_stack_array[M_stack_ptr]     = m_apm_init();
+   M_stack_array[M_stack_ptr + 1] = m_apm_init();
+   M_stack_array[M_stack_ptr + 2] = m_apm_init();
+   M_stack_array[M_stack_ptr + 3] = m_apm_init();
+
+   M_last_init = M_stack_ptr + 3;
+
+   /* printf("M_last_init = %d \n",M_last_init); */
+  }
+
+return(M_stack_array[M_stack_ptr]);
+}
+/****************************************************************************/
+void	M_restore_stack(int count)
+{
+M_stack_ptr -= count;
+}
+/****************************************************************************/
+

+ 555 - 0
mapm/src/mapmutil.c

@@ -0,0 +1,555 @@
+
+/* 
+ *  M_APM  -  mapmutil.c
+ *
+ *  Copyright (C) 1999 - 2007   Michael C. Ring
+ *
+ *  Permission to use, copy, and distribute this software and its
+ *  documentation for any purpose with or without fee is hereby granted,
+ *  provided that the above copyright notice appear in all copies and
+ *  that both that copyright notice and this permission notice appear
+ *  in supporting documentation.
+ *
+ *  Permission to modify the software is granted. Permission to distribute
+ *  the modified code is granted. Modifications are to be distributed by
+ *  using the file 'license.txt' as a template to modify the file header.
+ *  'license.txt' is available in the official MAPM distribution.
+ *
+ *  This software is provided "as is" without express or implied warranty.
+ */
+
+/*
+ *      $Id: mapmutil.c,v 1.26 2007/12/03 01:58:49 mike Exp $
+ *
+ *      This file contains various utility functions needed by the 
+ *	library in addition to some basic user callable functions.
+ *
+ *      $Log: mapmutil.c,v $
+ *      Revision 1.26  2007/12/03 01:58:49  mike
+ *      Update license
+ *
+ *      Revision 1.25  2003/07/21 20:51:34  mike
+ *      Modify error messages to be in a consistent format.
+ *
+ *      Revision 1.24  2003/03/31 22:03:54  mike
+ *      call generic error handling function
+ *
+ *      Revision 1.23  2002/11/04 20:47:02  mike
+ *      change m_apm_init so it compiles clean with a real C++ compiler
+ *
+ *      Revision 1.22  2002/11/03 22:50:58  mike
+ *      Updated function parameters to use the modern style
+ *
+ *      Revision 1.21  2002/05/17 22:26:49  mike
+ *      move some functions into another file
+ *
+ *      Revision 1.20  2002/02/12 20:21:53  mike
+ *      eliminate unneeded working arrays in _scale
+ *      by processing the scaling operation in reverse
+ *
+ *      Revision 1.19  2001/07/24 18:29:18  mike
+ *      add util function to get address of
+ *      the div/rem lookup tables
+ *
+ *      Revision 1.18  2001/07/20 16:14:05  mike
+ *      optimize normalize yet again
+ *
+ *      Revision 1.17  2001/07/17 18:17:56  mike
+ *      another optimization to _normalize
+ *
+ *      Revision 1.16  2001/07/16 22:33:43  mike
+ *      update free_all_util
+ *
+ *      Revision 1.15  2001/07/16 19:56:26  mike
+ *      add function M_free_all_util
+ *
+ *      Revision 1.14  2001/07/16 18:10:21  mike
+ *      optimize M_apm_normalize when moving multiple '00' bytes
+ *
+ *      Revision 1.13  2001/02/11 22:36:43  mike
+ *      modify parameters to REALLOC
+ *
+ *      Revision 1.12  2001/01/23 21:17:38  mike
+ *      add dedicated long->ascii conversion (instead of sprintf)
+ *
+ *      Revision 1.11  2000/08/22 20:21:54  mike
+ *      fix m_apm_exponent with exactly 0 as the input
+ *
+ *      Revision 1.10  2000/08/22 00:01:26  mike
+ *      add zero check in is_integer
+ *
+ *      Revision 1.9  2000/08/21 23:34:44  mike
+ *      add new function _is_integer
+ *
+ *      Revision 1.8  2000/08/01 22:29:02  mike
+ *      add sizeof int function call
+ *
+ *      Revision 1.7  2000/05/19 16:21:03  mike
+ *      delete M_check_dec_places, no longer needed
+ *
+ *      Revision 1.6  2000/04/04 17:06:37  mike
+ *      initialize C++ refcount struct element to 1
+ *
+ *      Revision 1.5  2000/02/03 22:49:56  mike
+ *      use MAPM_* generic memory function
+ *
+ *      Revision 1.4  1999/09/18 03:06:41  mike
+ *      fix m_apm_exponent
+ *
+ *      Revision 1.3  1999/09/18 02:59:11  mike
+ *      added new functions
+ *
+ *      Revision 1.2  1999/05/15 02:21:14  mike
+ *      add check for number of decimal places
+ *
+ *      Revision 1.1  1999/05/10 20:56:31  mike
+ *      Initial revision
+ */
+
+#include "m_apm_lc.h"
+
+static  UCHAR	*M_mul_div = NULL;
+static  UCHAR   *M_mul_rem = NULL;
+
+static  UCHAR   M_mul_div_10[100];
+static	UCHAR   M_mul_rem_10[100];
+
+static	int	M_util_firsttime = TRUE;
+static	int     M_firsttime3 = TRUE;
+
+static	M_APM	M_work_0_5;
+
+static  char    *M_init_error_msg = "\'m_apm_init\', Out of memory";
+
+/****************************************************************************/
+M_APM	m_apm_init()
+{
+M_APM	atmp;
+
+if (M_firsttime3)
+  {
+   M_firsttime3 = FALSE;
+   M_init_util_data();
+   M_init_trig_globals();
+  }
+
+if ((atmp = (M_APM)MAPM_MALLOC(sizeof(M_APM_struct))) == NULL)
+  {
+   /* fatal, this does not return */
+
+   M_apm_log_error_msg(M_APM_FATAL, M_init_error_msg);
+  }
+
+atmp->m_apm_id           = M_APM_IDENT;
+atmp->m_apm_malloclength = 80;
+atmp->m_apm_datalength   = 1;
+atmp->m_apm_refcount     = 1;           /* not for us, for MAPM C++ class */
+atmp->m_apm_exponent     = 0;
+atmp->m_apm_sign         = 0;
+
+if ((atmp->m_apm_data = (UCHAR *)MAPM_MALLOC(84)) == NULL)
+  {
+   /* fatal, this does not return */
+
+   M_apm_log_error_msg(M_APM_FATAL, M_init_error_msg);
+  }
+
+atmp->m_apm_data[0] = 0;
+return(atmp);
+}
+/****************************************************************************/
+void	m_apm_free(M_APM atmp)
+{
+if (atmp->m_apm_id == M_APM_IDENT)
+  {
+   atmp->m_apm_id = 0x0FFFFFF0L;
+   MAPM_FREE(atmp->m_apm_data);
+   MAPM_FREE(atmp);
+  }
+else
+  {
+   M_apm_log_error_msg(M_APM_RETURN, "\'m_apm_free\', Invalid M_APM variable");
+  }
+}
+/****************************************************************************/
+void	M_free_all_util()
+{
+if (M_util_firsttime == FALSE)
+  {
+   m_apm_free(M_work_0_5);
+   M_util_firsttime = TRUE;
+  }
+
+if (M_firsttime3 == FALSE)
+  {
+   MAPM_FREE(M_mul_div);
+   MAPM_FREE(M_mul_rem);
+  
+   M_mul_div    = NULL;
+   M_mul_rem    = NULL;
+   M_firsttime3 = TRUE;
+  }
+}
+/****************************************************************************/
+/*
+ *      just a dummy wrapper to keep some compilers from complaining
+ */
+int 	M_get_sizeof_int()
+{
+return(sizeof(int));
+}
+/****************************************************************************/
+void	M_init_util_data()
+{
+int	k;
+UCHAR   ndiv, nrem;
+
+if (M_mul_div != NULL)
+  return;
+
+M_mul_div = (UCHAR *)MAPM_MALLOC(10000 * sizeof(UCHAR));
+M_mul_rem = (UCHAR *)MAPM_MALLOC(10000 * sizeof(UCHAR));
+
+if (M_mul_div == NULL || M_mul_rem == NULL)
+  {
+   /* fatal, this does not return */
+
+   M_apm_log_error_msg(M_APM_FATAL, "\'M_init_util_data\', Out of memory");
+  }
+
+ndiv = 0;
+nrem = 0;
+
+for (k=0; k < 100; k++)
+  {
+   M_mul_div_10[k] = ndiv;
+   M_mul_rem_10[k] = nrem;
+
+   if (++nrem == 10)
+     {
+      nrem = 0;
+      ndiv++;
+     }
+  }
+
+ndiv = 0;
+nrem = 0;
+
+for (k=0; k < 10000; k++)
+  {
+   M_mul_div[k] = ndiv;
+   M_mul_rem[k] = nrem;
+
+   if (++nrem == 100)
+     {
+      nrem = 0;
+      ndiv++;
+     }
+  }
+}
+/****************************************************************************/
+void	M_get_div_rem_addr(UCHAR **ndivp, UCHAR **nremp)
+{
+*ndivp = M_mul_div;
+*nremp = M_mul_rem;
+}
+/****************************************************************************/
+void	M_get_div_rem(int tbl_lookup, UCHAR *ndiv, UCHAR *nrem)
+{
+*ndiv = M_mul_div[tbl_lookup];
+*nrem = M_mul_rem[tbl_lookup];
+}
+/****************************************************************************/
+void	M_get_div_rem_10(int tbl_lookup, UCHAR *ndiv, UCHAR *nrem)
+{
+*ndiv = M_mul_div_10[tbl_lookup];
+*nrem = M_mul_rem_10[tbl_lookup];
+}
+/****************************************************************************/
+void	m_apm_round(M_APM btmp, int places, M_APM atmp) 
+{
+int	ii;
+
+if (M_util_firsttime)
+  {
+   M_util_firsttime = FALSE;
+
+   M_work_0_5 = m_apm_init();
+   m_apm_set_string(M_work_0_5, "5");
+  }
+
+ii = places + 1;
+
+if (atmp->m_apm_datalength <= ii)
+  {
+   m_apm_copy(btmp,atmp);
+   return;
+  }
+
+M_work_0_5->m_apm_exponent = atmp->m_apm_exponent - ii;
+
+if (atmp->m_apm_sign > 0)
+  m_apm_add(btmp, atmp, M_work_0_5);
+else
+  m_apm_subtract(btmp, atmp, M_work_0_5);
+
+btmp->m_apm_datalength = ii;
+M_apm_normalize(btmp);
+}
+/****************************************************************************/
+void	M_apm_normalize(M_APM atmp)
+{
+int	i, index, datalength, exponent;
+UCHAR   *ucp, numdiv, numrem, numrem2;
+
+if (atmp->m_apm_sign == 0)
+  return;
+
+datalength = atmp->m_apm_datalength;
+exponent   = atmp->m_apm_exponent;
+
+/* make sure trailing bytes/chars are 0                */
+/* the following function will adjust the 'datalength' */
+/* we want the original value and will fix it later    */
+
+M_apm_pad(atmp, (datalength + 3));
+
+while (TRUE)			/* remove lead-in '0' if any */
+  {
+   M_get_div_rem_10((int)atmp->m_apm_data[0], &numdiv, &numrem);
+
+   if (numdiv >= 1)      /* number is normalized, done here */
+     break;
+
+   index = (datalength + 1) >> 1;
+
+   if (numrem == 0)      /* both nibbles are 0, we can move full bytes */
+     {
+      i = 0;
+      ucp = atmp->m_apm_data;
+
+      while (TRUE)	 /* find out how many '00' bytes we can move */
+        {
+	 if (*ucp != 0)
+	   break;
+
+         ucp++;
+	 i++;
+	}
+
+      memmove(atmp->m_apm_data, ucp, (index + 1 - i));
+      datalength -= 2 * i;
+      exponent -= 2 * i;
+     }
+   else
+     {
+      for (i=0; i < index; i++)
+        {
+         M_get_div_rem_10((int)atmp->m_apm_data[i+1], &numdiv, &numrem2);
+         atmp->m_apm_data[i] = 10 * numrem + numdiv;
+	 numrem = numrem2;
+        }
+   
+      datalength--;
+      exponent--;
+     }
+  }
+
+while (TRUE)			/* remove trailing '0' if any */
+  {
+   index = ((datalength + 1) >> 1) - 1;
+
+   if ((datalength & 1) == 0)   /* back-up full bytes at a time if the */
+     {				/* current length is an even number    */
+      ucp = atmp->m_apm_data + index;
+      if (*ucp == 0)
+        {
+	 while (TRUE)
+	   {
+	    datalength -= 2;
+	    index--;
+	    ucp--;
+
+	    if (*ucp != 0)
+	      break;
+	   }
+	}
+     }
+
+   M_get_div_rem_10((int)atmp->m_apm_data[index], &numdiv, &numrem);
+
+   if (numrem != 0)		/* last digit non-zero, all done */
+     break;
+
+   if ((datalength & 1) != 0)   /* if odd, then first char must be non-zero */
+     {
+      if (numdiv != 0)
+        break;
+     }
+
+   if (datalength == 1)
+     {
+      atmp->m_apm_sign = 0;
+      exponent = 0;
+      break;
+     }
+     
+   datalength--;
+  }
+
+atmp->m_apm_datalength = datalength;
+atmp->m_apm_exponent   = exponent;
+}
+/****************************************************************************/
+void	M_apm_scale(M_APM ctmp, int count)
+{
+int	ii, numb, ct;
+UCHAR	*chp, numdiv, numdiv2, numrem;
+void	*vp;
+
+ct = count;
+
+ii = (ctmp->m_apm_datalength + ct + 1) >> 1;
+if (ii > ctmp->m_apm_malloclength)
+  {
+   if ((vp = MAPM_REALLOC(ctmp->m_apm_data, (ii + 32))) == NULL)
+     {
+      /* fatal, this does not return */
+
+      M_apm_log_error_msg(M_APM_FATAL, "\'M_apm_scale\', Out of memory");
+     }
+   
+   ctmp->m_apm_malloclength = ii + 28;
+   ctmp->m_apm_data = (UCHAR *)vp;
+  }
+
+if ((ct & 1) != 0)          /* move odd number first */
+  {
+   ct--;
+   chp = ctmp->m_apm_data;
+   ii  = ((ctmp->m_apm_datalength + 1) >> 1) - 1;
+
+   if ((ctmp->m_apm_datalength & 1) == 0)
+     {
+      /*
+       *   original datalength is even:
+       *
+       *   uv  wx  yz   becomes  -->   0u  vw  xy  z0
+       */
+
+      numdiv = 0;
+
+      while (TRUE)
+        {
+         M_get_div_rem_10((int)chp[ii], &numdiv2, &numrem);
+
+	 chp[ii + 1] = 10 * numrem + numdiv;
+	 numdiv = numdiv2;
+
+	 if (ii == 0)
+	   break;
+
+         ii--;
+	}
+
+      chp[0] = numdiv2;
+     }
+   else
+     {
+      /*
+       *   original datalength is odd:
+       *
+       *   uv  wx  y0   becomes  -->   0u  vw  xy
+       */
+
+      M_get_div_rem_10((int)chp[ii], &numdiv2, &numrem);
+
+      if (ii == 0)
+        {
+         chp[0] = numdiv2;
+        }
+      else
+        {
+         while (TRUE)
+           {
+            M_get_div_rem_10((int)chp[ii - 1], &numdiv, &numrem);
+
+	    chp[ii] = 10 * numrem + numdiv2;
+	    numdiv2 = numdiv;
+
+	    if (--ii == 0)
+	      break;
+	   }
+
+         chp[0] = numdiv;
+        }
+     }
+
+   ctmp->m_apm_exponent++;
+   ctmp->m_apm_datalength++;
+  }
+
+/* ct is even here */
+
+if (ct > 0)
+  {
+   numb = (ctmp->m_apm_datalength + 1) >> 1;
+   ii   = ct >> 1;
+   
+   memmove((ctmp->m_apm_data + ii), ctmp->m_apm_data, numb);
+   memset(ctmp->m_apm_data, 0, ii);
+   
+   ctmp->m_apm_datalength += ct;
+   ctmp->m_apm_exponent += ct;
+  }
+}
+/****************************************************************************/
+void	M_apm_pad(M_APM ctmp, int new_length)
+{
+int	num1, numb, ct;
+UCHAR	numdiv, numrem;
+void	*vp;
+
+ct = new_length;
+if (ctmp->m_apm_datalength >= ct)
+  return;
+  
+numb = (ct + 1) >> 1;
+if (numb > ctmp->m_apm_malloclength)
+  {
+   if ((vp = MAPM_REALLOC(ctmp->m_apm_data, (numb + 32))) == NULL)
+     {
+      /* fatal, this does not return */
+
+      M_apm_log_error_msg(M_APM_FATAL, "\'M_apm_pad\', Out of memory");
+     }
+   
+   ctmp->m_apm_malloclength = numb + 28;
+   ctmp->m_apm_data = (UCHAR *)vp;
+  }
+
+num1 = (ctmp->m_apm_datalength + 1) >> 1;
+
+if ((ctmp->m_apm_datalength & 1) != 0)
+  {
+   M_get_div_rem_10((int)ctmp->m_apm_data[num1 - 1], &numdiv, &numrem);
+   ctmp->m_apm_data[num1 - 1] = 10 * numdiv;
+  }
+
+memset((ctmp->m_apm_data + num1), 0, (numb - num1));
+ctmp->m_apm_datalength = ct;
+}
+/****************************************************************************/
+
+/*
+      debug_dsp(cc)
+      M_APM cc;
+      {
+static char buffer[8192];
+
+m_apm_to_string(buffer, -1, cc);
+printf("(dsp func) = [%s]\n",buffer);
+
+      }
+*/
+

+ 59 - 0
mapm/src/mapmutl1.c

@@ -0,0 +1,59 @@
+
+/* 
+ *  M_APM  -  mapmutl1.c
+ *
+ *  Copyright (C) 2003 - 2007   Michael C. Ring
+ *
+ *  Permission to use, copy, and distribute this software and its
+ *  documentation for any purpose with or without fee is hereby granted,
+ *  provided that the above copyright notice appear in all copies and
+ *  that both that copyright notice and this permission notice appear
+ *  in supporting documentation.
+ *
+ *  Permission to modify the software is granted. Permission to distribute
+ *  the modified code is granted. Modifications are to be distributed by
+ *  using the file 'license.txt' as a template to modify the file header.
+ *  'license.txt' is available in the official MAPM distribution.
+ *
+ *  This software is provided "as is" without express or implied warranty.
+ */
+
+/*
+ *      $Id: mapmutl1.c,v 1.4 2007/12/03 01:59:27 mike Exp $
+ *
+ *      This file contains the utility function 'M_apm_log_error_msg'
+ *
+ *	This is the only function in this file so a user can supply
+ *	their own custom version easily without changing the base library.
+ *
+ *      $Log: mapmutl1.c,v $
+ *      Revision 1.4  2007/12/03 01:59:27  mike
+ *      Update license
+ *
+ *      Revision 1.3  2003/07/21 21:00:34  mike
+ *      Modify error messages to be in a consistent format.
+ *
+ *      Revision 1.2  2003/05/05 18:38:27  mike
+ *      fix comment
+ *
+ *      Revision 1.1  2003/05/04 18:19:14  mike
+ *      Initial revision
+ */
+
+#include "m_apm_lc.h"
+
+/****************************************************************************/
+void	M_apm_log_error_msg(int fatal, char *message)
+{
+if (fatal)
+  {
+   fprintf(stderr, "MAPM Error: %s\n", message);
+   exit(100);
+  }
+else
+  {
+   fprintf(stderr, "MAPM Warning: %s\n", message);
+  }
+}
+/****************************************************************************/
+

+ 350 - 0
mapm/src/mapmutl2.c

@@ -0,0 +1,350 @@
+
+/* 
+ *  M_APM  -  mapmutl2.c
+ *
+ *  Copyright (C) 2002 - 2007   Michael C. Ring
+ *
+ *  Permission to use, copy, and distribute this software and its
+ *  documentation for any purpose with or without fee is hereby granted,
+ *  provided that the above copyright notice appear in all copies and
+ *  that both that copyright notice and this permission notice appear
+ *  in supporting documentation.
+ *
+ *  Permission to modify the software is granted. Permission to distribute
+ *  the modified code is granted. Modifications are to be distributed by
+ *  using the file 'license.txt' as a template to modify the file header.
+ *  'license.txt' is available in the official MAPM distribution.
+ *
+ *  This software is provided "as is" without express or implied warranty.
+ */
+
+/*
+ *      $Id: mapmutl2.c,v 1.7 2007/12/03 02:00:04 mike Exp $
+ *
+ *      This file contains various utility functions
+ *
+ *      $Log: mapmutl2.c,v $
+ *      Revision 1.7  2007/12/03 02:00:04  mike
+ *      Update license
+ *
+ *      Revision 1.6  2003/07/21 20:53:10  mike
+ *      Modify error messages to be in a consistent format.
+ *
+ *      Revision 1.5  2003/05/04 18:14:32  mike
+ *      move generic error handling function into a dedicated module
+ *
+ *      Revision 1.4  2003/03/31 22:02:22  mike
+ *      call generic error handling function
+ *
+ *      Revision 1.3  2002/11/03 21:19:40  mike
+ *      Updated function parameters to use the modern style
+ *
+ *      Revision 1.2  2002/05/17 22:29:46  mike
+ *      update some comments
+ *
+ *      Revision 1.1  2002/05/17 22:28:27  mike
+ *      Initial revision
+ */
+
+#include "m_apm_lc.h"
+
+/****************************************************************************/
+int	m_apm_sign(M_APM atmp)
+{
+return(atmp->m_apm_sign);
+}
+/****************************************************************************/
+int	m_apm_exponent(M_APM atmp)
+{
+if (atmp->m_apm_sign == 0)
+  return(0);
+else
+  return(atmp->m_apm_exponent - 1);
+}
+/****************************************************************************/
+int	m_apm_significant_digits(M_APM atmp)
+{
+return(atmp->m_apm_datalength);
+}
+/****************************************************************************/
+int	m_apm_is_integer(M_APM atmp)
+{
+if (atmp->m_apm_sign == 0)
+  return(1);
+
+if (atmp->m_apm_exponent >= atmp->m_apm_datalength)
+  return(1);
+else
+  return(0);
+}
+/****************************************************************************/
+int 	m_apm_is_even(M_APM aa)
+{
+int     ii, jj;
+
+if (aa->m_apm_sign == 0)
+  return(1);
+
+ii = aa->m_apm_datalength;
+jj = aa->m_apm_exponent;
+
+if (jj < ii)
+  {
+   M_apm_log_error_msg(M_APM_RETURN, "\'m_apm_is_even\', Non-integer input");
+   return(0);
+  }
+
+if (jj > ii)
+  return(1);
+
+ii = ((ii + 1) >> 1) - 1;
+ii = (int)aa->m_apm_data[ii];
+
+if ((jj & 1) != 0)      /* exponent is odd */
+  ii = ii / 10;
+
+if ((ii & 1) == 0)
+  return(1);
+else
+  return(0);
+}
+/****************************************************************************/
+int 	m_apm_is_odd(M_APM bb)
+{
+if (m_apm_is_even(bb))
+  return(0);
+else
+  return(1);
+}
+/****************************************************************************/
+void	M_set_to_zero(M_APM z)
+{
+z->m_apm_datalength = 1;
+z->m_apm_sign       = 0;
+z->m_apm_exponent   = 0;
+z->m_apm_data[0]    = 0;
+}
+/****************************************************************************/
+void	m_apm_negate(M_APM d, M_APM s)
+{
+m_apm_copy(d,s);
+if (d->m_apm_sign != 0)
+    d->m_apm_sign = -(d->m_apm_sign);
+}
+/****************************************************************************/
+void	m_apm_absolute_value(M_APM d, M_APM s)
+{
+m_apm_copy(d,s);
+if (d->m_apm_sign != 0)
+    d->m_apm_sign = 1;
+}
+/****************************************************************************/
+void	m_apm_copy(M_APM dest, M_APM src)
+{
+int	j;
+void	*vp;
+
+j = (src->m_apm_datalength + 1) >> 1;
+if (j > dest->m_apm_malloclength)
+  {
+   if ((vp = MAPM_REALLOC(dest->m_apm_data, (j + 32))) == NULL)
+     {
+      /* fatal, this does not return */
+
+      M_apm_log_error_msg(M_APM_FATAL, "\'m_apm_copy\', Out of memory");
+     }
+   
+   dest->m_apm_malloclength = j + 28;
+   dest->m_apm_data = (UCHAR *)vp;
+  }
+
+dest->m_apm_datalength = src->m_apm_datalength;
+dest->m_apm_exponent   = src->m_apm_exponent;
+dest->m_apm_sign       = src->m_apm_sign;
+
+memcpy(dest->m_apm_data, src->m_apm_data, j);
+}
+/****************************************************************************/
+int	m_apm_compare(M_APM ltmp, M_APM rtmp)
+{
+int	llen, rlen, lsign, rsign, i, j, lexp, rexp;
+
+llen  = ltmp->m_apm_datalength;
+rlen  = rtmp->m_apm_datalength;
+
+lsign = ltmp->m_apm_sign;
+rsign = rtmp->m_apm_sign;
+
+lexp  = ltmp->m_apm_exponent;
+rexp  = rtmp->m_apm_exponent;
+
+if (rsign == 0)
+  return(lsign);
+
+if (lsign == 0)
+  return(-rsign);
+
+if (lsign == -rsign)
+  return(lsign);
+
+/* signs are the same, check the exponents */
+
+if (lexp > rexp)
+  goto E1;
+
+if (lexp < rexp)
+  goto E2;
+
+/* signs and exponents are the same, check the data */
+
+if (llen < rlen)
+  j = (llen + 1) >> 1;
+else
+  j = (rlen + 1) >> 1;
+
+for (i=0; i < j; i++)
+  {
+   if (ltmp->m_apm_data[i] > rtmp->m_apm_data[i])
+     goto E1;
+
+   if (ltmp->m_apm_data[i] < rtmp->m_apm_data[i])
+     goto E2;
+  }
+
+if (llen == rlen)
+   return(0);
+else
+  {
+   if (llen > rlen)
+     goto E1;
+   else
+     goto E2;
+  }
+
+E1:
+
+if (lsign == 1)
+  return(1);
+else
+  return(-1);
+
+E2:
+
+if (lsign == 1)
+  return(-1);
+else
+  return(1);
+}
+/****************************************************************************/
+/*
+ *
+ *	convert a signed long int to ASCII in base 10
+ *
+ */
+void    M_long_2_ascii(char *output, long input)
+{
+long    t, m;
+int     i, j;
+char    *p, tbuf[64];
+
+m = input;
+p = output;
+i = 0;
+t = 2147000000L;          /* something < 2^31 */
+
+if ((m > t) || (m < -t))  /* handle the bigger numbers with 'sprintf'. */
+  {			  /* let them worry about wrap-around problems */
+   sprintf(p, "%ld", m);  /* at 'LONG_MIN', etc.                       */
+  }
+else
+  {
+   if (m < 0)             /* handle the sign */
+     {
+      *p++ = '-';
+      m = -m;
+     }
+   
+   while (TRUE)           /* build the digits in reverse order */
+     {
+      t = m / 10;
+      j = (int)(m - (10 * t));
+      tbuf[i++] = (char)(j + '0');
+      m = t;
+
+      if (t == 0)  
+        break;
+     }
+   
+   while (TRUE)           /* fill output string in the correct order */
+     {
+      *p++ = tbuf[--i];
+      if (i == 0)  
+        break;
+     }
+   
+   *p = '\0';
+  }
+}
+/****************************************************************************/
+/*
+ *      this function will convert a string to lowercase
+ */
+char    *M_lowercase(char *s)
+{
+char    *p;
+
+p = s;
+
+while (TRUE)
+  {
+   if (*p >= 'A' && *p <= 'Z')
+     *p += 'a' - 'A';
+
+   if (*p++ == '\0')  break;
+  }
+return(s);
+}
+/****************************************************************************/
+/*    returns char position of first occurence of s2 in s1
+	  or -1 if no match found
+*/
+int     M_strposition(char *s1, char *s2)
+{
+register char  ch1, ch2;
+char           *p0, *p1, *p2;
+int            ct;
+
+ct = -1;
+p0 = s1;
+
+if (*s2 == '\0')  return(-1);
+
+while (TRUE)
+  {
+   ct++;
+   p1  = p0;
+   p2  = s2;
+   ch2 = *p2;
+   
+   while (TRUE)                    /* scan until first char matches */
+     {
+      if ((ch1 = *p1) == '\0')  return(-1);
+      if (ch1 == ch2)           break;
+      p1++;
+      ct++;
+     }
+
+   p2++;                           /* check remainder of 2 strings */
+   p1++;
+   p0 = p1;
+
+   while (TRUE)
+     {
+      if ((ch2 = *p2) == '\0')  return(ct);
+      if (*p1 != ch2)           break;
+      p1++;
+      p2++;
+     }
+  }
+}
+/****************************************************************************/