summaryrefslogtreecommitdiff
path: root/2.3-1/includes
diff options
context:
space:
mode:
authorSiddhesh Wani2015-05-25 14:46:31 +0530
committerSiddhesh Wani2015-05-25 14:46:31 +0530
commit6a320264c2de3d6dd8cc1d1327b3c30df4c8cb26 (patch)
tree1b7bd89fdcfd01715713d8a15db471dc75a96bbf /2.3-1/includes
downloadScilab2C-6a320264c2de3d6dd8cc1d1327b3c30df4c8cb26.tar.gz
Scilab2C-6a320264c2de3d6dd8cc1d1327b3c30df4c8cb26.tar.bz2
Scilab2C-6a320264c2de3d6dd8cc1d1327b3c30df4c8cb26.zip
Original Version
Diffstat (limited to '2.3-1/includes')
-rw-r--r--2.3-1/includes/blas.h160
-rw-r--r--2.3-1/includes/constant.h34
-rw-r--r--2.3-1/includes/f2c.h245
-rw-r--r--2.3-1/includes/lapack.h168
-rw-r--r--2.3-1/includes/machine.h.in80
-rw-r--r--2.3-1/includes/notFound.h18
-rw-r--r--2.3-1/includes/sci2clib.h297
7 files changed, 1002 insertions, 0 deletions
diff --git a/2.3-1/includes/blas.h b/2.3-1/includes/blas.h
new file mode 100644
index 00000000..86ab62f6
--- /dev/null
+++ b/2.3-1/includes/blas.h
@@ -0,0 +1,160 @@
+/*
+ * Scilab ( http://www.scilab.org/ ) - This file is part of Scilab
+ * Copyright (C) 2008-2008 - INRIA - Bruno JOFRET
+ *
+ * This file must be used under the terms of the CeCILL.
+ * This source file is licensed as described in the file COPYING, which
+ * you should have received as part of this distribution. The terms
+ * are also available at
+ * http://www.cecill.info/licences/Licence_CeCILL_V2-en.txt
+ *
+ */
+
+#ifndef __BLAS_H__
+#define __BLAS_H__
+
+
+#ifndef _MACRO_C2F_
+#define _MACRO_C2F_
+#define C2F(name) name##_
+#endif
+/*
+ SUBROUTINE DGEMM ( TRANSA, TRANSB, M, N, K, ALPHA, A, LDA, B, LDB,
+ $ BETA, C, LDC )
+* .. Scalar Arguments ..
+ CHARACTER*1 TRANSA, TRANSB
+ INTEGER M, N, K, LDA, LDB, LDC
+ DOUBLE PRECISION ALPHA, BETA
+* .. Array Arguments ..
+ DOUBLE PRECISION A( LDA, * ), B( LDB, * ), C( LDC, * )
+* ..
+C WARNING : this routine has been modified for Scilab (see comments
+C Cscilab) because algorithm is not ok if A matrix contains NaN
+C (NaN*0 should be NaN, not 0)
+* Purpose
+* =======
+*
+* DGEMM performs one of the matrix-matrix operations
+*
+* C := alpha*op( A )*op( B ) + beta*C,
+*
+* where op( X ) is one of
+*
+* op( X ) = X or op( X ) = X',
+*
+* alpha and beta are scalars, and A, B and C are matrices, with op( A )
+* an m by k matrix, op( B ) a k by n matrix and C an m by n matrix.
+*
+* Parameters
+* ==========
+*
+* TRANSA - CHARACTER*1.
+* On entry, TRANSA specifies the form of op( A ) to be used in
+* the matrix multiplication as follows:
+*
+* TRANSA = 'N' or 'n', op( A ) = A.
+*
+* TRANSA = 'T' or 't', op( A ) = A'.
+*
+* TRANSA = 'C' or 'c', op( A ) = A'.
+*
+* Unchanged on exit.
+*
+* TRANSB - CHARACTER*1.
+* On entry, TRANSB specifies the form of op( B ) to be used in
+* the matrix multiplication as follows:
+*
+* TRANSB = 'N' or 'n', op( B ) = B.
+*
+* TRANSB = 'T' or 't', op( B ) = B'.
+*
+* TRANSB = 'C' or 'c', op( B ) = B'.
+*
+* Unchanged on exit.
+*
+* M - INTEGER.
+* On entry, M specifies the number of rows of the matrix
+* op( A ) and of the matrix C. M must be at least zero.
+* Unchanged on exit.
+*
+* N - INTEGER.
+* On entry, N specifies the number of columns of the matrix
+* op( B ) and the number of columns of the matrix C. N must be
+* at least zero.
+* Unchanged on exit.
+*
+* K - INTEGER.
+* On entry, K specifies the number of columns of the matrix
+* op( A ) and the number of rows of the matrix op( B ). K must
+* be at least zero.
+* Unchanged on exit.
+*
+* ALPHA - DOUBLE PRECISION.
+* On entry, ALPHA specifies the scalar alpha.
+* Unchanged on exit.
+*
+* A - DOUBLE PRECISION array of DIMENSION ( LDA, ka ), where ka is
+* k when TRANSA = 'N' or 'n', and is m otherwise.
+* Before entry with TRANSA = 'N' or 'n', the leading m by k
+* part of the array A must contain the matrix A, otherwise
+* the leading k by m part of the array A must contain the
+* matrix A.
+* Unchanged on exit.
+*
+* LDA - INTEGER.
+* On entry, LDA specifies the first dimension of A as declared
+* in the calling (sub) program. When TRANSA = 'N' or 'n' then
+* LDA must be at least max( 1, m ), otherwise LDA must be at
+* least max( 1, k ).
+* Unchanged on exit.
+*
+* B - DOUBLE PRECISION array of DIMENSION ( LDB, kb ), where kb is
+* n when TRANSB = 'N' or 'n', and is k otherwise.
+* Before entry with TRANSB = 'N' or 'n', the leading k by n
+* part of the array B must contain the matrix B, otherwise
+* the leading n by k part of the array B must contain the
+* matrix B.
+* Unchanged on exit.
+*
+* LDB - INTEGER.
+* On entry, LDB specifies the first dimension of B as declared
+* in the calling (sub) program. When TRANSB = 'N' or 'n' then
+* LDB must be at least max( 1, k ), otherwise LDB must be at
+* least max( 1, n ).
+* Unchanged on exit.
+*
+* BETA - DOUBLE PRECISION.
+* On entry, BETA specifies the scalar beta. When BETA is
+* supplied as zero then C need not be set on input.
+* Unchanged on exit.
+*
+* C - DOUBLE PRECISION array of DIMENSION ( LDC, n ).
+* Before entry, the leading m by n part of the array C must
+* contain the matrix C, except when beta is zero, in which
+* case C need not be set on entry.
+* On exit, the array C is overwritten by the m by n matrix
+* ( alpha*op( A )*op( B ) + beta*C ).
+*
+* LDC - INTEGER.
+* On entry, LDC specifies the first dimension of C as declared
+* in the calling (sub) program. LDC must be at least
+* max( 1, m ).
+* Unchanged on exit.
+*
+*
+* Level 3 Blas routine.
+*/
+/*
+void dgemm_(char *TRANSA, char* TRANSB, int *M, int *N, int *K,
+ double *ALPHA, double *A, int *LDA,
+ double *B, int *LDB, double *BETA,
+ double *C, int *LDC);*/
+
+extern int C2F(dgemm)();
+extern int C2F(idamax)() ;/* could be transcribe easaly in c */
+extern int C2F(daxpy) () ;/* could be transcribe easaly in c */
+extern int C2F(dscal) () ;/* could be transcribe easaly in c */
+extern int C2F(dasum) () ;/* could be transcribe easaly in c */
+
+
+#endif /* !__BLAS_H__ */
diff --git a/2.3-1/includes/constant.h b/2.3-1/includes/constant.h
new file mode 100644
index 00000000..14543b61
--- /dev/null
+++ b/2.3-1/includes/constant.h
@@ -0,0 +1,34 @@
+/*
+ * Scilab ( http://www.scilab.org/ ) - This file is part of Scilab
+ * Copyright (C) 2006-2008 - INRIA - Bruno JOFRET
+ *
+ * This file must be used under the terms of the CeCILL.
+ * This source file is licensed as described in the file COPYING, which
+ * you should have received as part of this distribution. The terms
+ * are also available at
+ * http://www.cecill.info/licences/Licence_CeCILL_V2-en.txt
+ *
+ */
+
+#ifndef __CONSTANT_H__
+#define __CONSTANT_H__
+
+#include <math.h>
+
+#define FPI 3.1415926535897931159980f
+#define DPI 3.1415926535897931159980
+
+#define NEPER 2.7182818284590450907956
+
+#define PI DPI
+#define SCI2C_PI DPI
+#define SCI2C_E NEPER
+#define SCI2C_T 1
+#define SCI2C_F 0
+#define SCI2C_NAN nan("")
+#define SCI2C_INF 1e100000
+#define SCI2C_IMG_C FloatComplex(0,1)
+#define SCI2C_IMG_Z DoubleComplex(0,1)
+
+#endif /* !__CONSTANT_H__ */
+
diff --git a/2.3-1/includes/f2c.h b/2.3-1/includes/f2c.h
new file mode 100644
index 00000000..a90a1ef5
--- /dev/null
+++ b/2.3-1/includes/f2c.h
@@ -0,0 +1,245 @@
+/* f2c.h -- Standard Fortran to C header file */
+
+/** barf [ba:rf] 2. "He suggested using FORTRAN, and everybody barfed."
+
+ - From The Shogakukan DICTIONARY OF NEW ENGLISH (Second edition) */
+
+#ifndef F2C_INCLUDE
+#define F2C_INCLUDE
+
+#ifdef FORDLL
+#define IMPORT extern __declspec (dllimport)
+#else
+#define IMPORT
+#endif
+
+#ifdef FORDLL
+#define Extern __declspec (dllimport)
+#else
+#define Extern
+#endif
+
+
+
+typedef long int integer;
+typedef unsigned long int uinteger;
+typedef char *address;
+typedef short int shortint;
+typedef float real;
+typedef double doublereal;
+typedef struct { real r, i; } complex;
+typedef struct { doublereal r, i; } doublecomplex;
+typedef long int logical;
+typedef short int shortlogical;
+typedef char logical1;
+typedef char integer1;
+#ifdef INTEGER_STAR_8 /* Adjust for integer*8. */
+typedef long long longint; /* system-dependent */
+typedef unsigned long long ulongint; /* system-dependent */
+#define qbit_clear(a,b) ((a) & ~((ulongint)1 << (b)))
+#define qbit_set(a,b) ((a) | ((ulongint)1 << (b)))
+#endif
+
+#define TRUE_ (1)
+#define FALSE_ (0)
+
+/* Extern is for use with -E */
+#ifndef Extern
+#define Extern extern
+#endif
+
+/* I/O stuff */
+
+#ifdef f2c_i2
+/* for -i2 */
+typedef short flag;
+typedef short ftnlen;
+typedef short ftnint;
+#else
+typedef long int flag;
+typedef long int ftnlen;
+typedef long int ftnint;
+#endif
+
+/*external read, write*/
+typedef struct
+{ flag cierr;
+ ftnint ciunit;
+ flag ciend;
+ char *cifmt;
+ ftnint cirec;
+} cilist;
+
+/*internal read, write*/
+typedef struct
+{ flag icierr;
+ char *iciunit;
+ flag iciend;
+ char *icifmt;
+ ftnint icirlen;
+ ftnint icirnum;
+} icilist;
+
+/*open*/
+typedef struct
+{ flag oerr;
+ ftnint ounit;
+ char *ofnm;
+ ftnlen ofnmlen;
+ char *osta;
+ char *oacc;
+ char *ofm;
+ ftnint orl;
+ char *oblnk;
+} olist;
+
+/*close*/
+typedef struct
+{ flag cerr;
+ ftnint cunit;
+ char *csta;
+} cllist;
+
+/*rewind, backspace, endfile*/
+typedef struct
+{ flag aerr;
+ ftnint aunit;
+} alist;
+
+/* inquire */
+typedef struct
+{ flag inerr;
+ ftnint inunit;
+ char *infile;
+ ftnlen infilen;
+ ftnint *inex; /*parameters in standard's order*/
+ ftnint *inopen;
+ ftnint *innum;
+ ftnint *innamed;
+ char *inname;
+ ftnlen innamlen;
+ char *inacc;
+ ftnlen inacclen;
+ char *inseq;
+ ftnlen inseqlen;
+ char *indir;
+ ftnlen indirlen;
+ char *infmt;
+ ftnlen infmtlen;
+ char *inform;
+ ftnint informlen;
+ char *inunf;
+ ftnlen inunflen;
+ ftnint *inrecl;
+ ftnint *innrec;
+ char *inblank;
+ ftnlen inblanklen;
+} inlist;
+
+#define VOID void
+
+union Multitype { /* for multiple entry points */
+ integer1 g;
+ shortint h;
+ integer i;
+ /* longint j; */
+ real r;
+ doublereal d;
+ complex c;
+ doublecomplex z;
+ };
+
+typedef union Multitype Multitype;
+
+/*typedef long int Long;*/ /* No longer used; formerly in Namelist */
+
+struct Vardesc { /* for Namelist */
+ char *name;
+ char *addr;
+ ftnlen *dims;
+ int type;
+ };
+typedef struct Vardesc Vardesc;
+
+struct Namelist {
+ char *name;
+ Vardesc **vars;
+ int nvars;
+ };
+typedef struct Namelist Namelist;
+
+#define abs(x) ((x) >= 0 ? (x) : -(x))
+#define dabs(x) (doublereal)abs(x)
+
+
+#ifndef min
+#define min(a,b) ((a) <= (b) ? (a) : (b))
+#endif
+
+#ifndef max
+#define max(a,b) ((a) >= (b) ? (a) : (b))
+#endif
+
+#define dmin(a,b) (doublereal)min(a,b)
+#define dmax(a,b) (doublereal)max(a,b)
+#define bit_test(a,b) ((a) >> (b) & 1)
+#define bit_clear(a,b) ((a) & ~((uinteger)1 << (b)))
+#define bit_set(a,b) ((a) | ((uinteger)1 << (b)))
+
+/* procedure parameter types for -A and -C++ */
+
+#define F2C_proc_par_types 1
+#ifdef __cplusplus
+typedef int /* Unknown procedure type */ (*U_fp)(...);
+typedef shortint (*J_fp)(...);
+typedef integer (*I_fp)(...);
+typedef real (*R_fp)(...);
+typedef doublereal (*D_fp)(...), (*E_fp)(...);
+typedef /* Complex */ VOID (*C_fp)(...);
+typedef /* Double Complex */ VOID (*Z_fp)(...);
+typedef logical (*L_fp)(...);
+typedef shortlogical (*K_fp)(...);
+typedef /* Character */ VOID (*H_fp)(...);
+typedef /* Subroutine */ int (*S_fp)(...);
+#else
+typedef int /* Unknown procedure type */ (*U_fp)();
+typedef shortint (*J_fp)();
+typedef integer (*I_fp)();
+typedef real (*R_fp)();
+typedef doublereal (*D_fp)(), (*E_fp)();
+typedef /* Complex */ VOID (*C_fp)();
+typedef /* Double Complex */ VOID (*Z_fp)();
+typedef logical (*L_fp)();
+typedef shortlogical (*K_fp)();
+typedef /* Character */ VOID (*H_fp)();
+typedef /* Subroutine */ int (*S_fp)();
+#endif
+/* E_fp is for real functions when -R is not specified */
+typedef VOID C_f; /* complex function */
+typedef VOID H_f; /* character function */
+typedef VOID Z_f; /* double complex function */
+typedef doublereal E_f; /* real function with -R not specified */
+
+/* undef any lower-case symbols that your C compiler predefines, e.g.: */
+
+#ifndef Skip_f2c_Undefs
+#undef cray
+#undef gcos
+#undef mc68010
+#undef mc68020
+#undef mips
+#undef pdp11
+#undef sgi
+#undef sparc
+#undef sun
+#undef sun2
+#undef sun3
+#undef sun4
+#undef u370
+#undef u3b
+#undef u3b2
+#undef u3b5
+#undef unix
+#undef vax
+#endif
+#endif
diff --git a/2.3-1/includes/lapack.h b/2.3-1/includes/lapack.h
new file mode 100644
index 00000000..0bee916e
--- /dev/null
+++ b/2.3-1/includes/lapack.h
@@ -0,0 +1,168 @@
+/*
+ * Scilab ( http://www.scilab.org/ ) - This file is part of Scilab
+ * Copyright (C) 2007-2008 - INRIA - Bruno JOFRET
+ *
+ * This file must be used under the terms of the CeCILL.
+ * This source file is licensed as described in the file COPYING, which
+ * you should have received as part of this distribution. The terms
+ * are also available at
+ * http://www.cecill.info/licences/Licence_CeCILL_V2-en.txt
+ *
+ */
+
+#ifndef __LAPACK_H__
+#define __LAPACK_H__
+
+#ifndef _MACRO_C2F_
+#define _MACRO_C2F_
+#define C2F(name) name##_
+#endif
+
+#include "doubleComplex.h"
+
+#ifdef __cplusplus
+extern "C" {
+#endif
+
+#define getRelativeMachinePrecision() dlamch_("e", 1L)
+#define getOverflowThreshold() dlamch_("o", 1L)
+#define getUnderflowThreshold() dlamch_("u", 1L)
+
+#define getOneNorm(lines,cols,in,work) dlange_("1", lines, cols, in, lines, work)
+#define resolveSystemLinear(cols1,row2,cpytranIn1,pIpiv, transposeOfIn2,info) \
+ dgetrs_ ("N" ,cols1, row2, cpytranIn1 , cols1, pIpiv,transposeOfIn2, cols1, info) ;
+
+
+
+
+/**
+ * -- LAPACK auxiliary routine (version 3.0) --
+ * Univ. of Tennessee, Univ. of California Berkeley, NAG Ltd.,
+ * Courant Institute, Argonne National Lab, and Rice University
+ * October 31, 1992
+ *
+ * Purpose
+ * =======
+ *
+ * DLAMCH determines double precision machine parameters.
+ *
+ * Arguments
+ * =========
+ *
+ * CMACH (input) CHARACTER*1
+ * Specifies the value to be returned by DLAMCH:
+ * = 'E' or 'e', DLAMCH := eps
+ * = 'S' or 's , DLAMCH := sfmin
+ * = 'B' or 'b', DLAMCH := base
+ * = 'P' or 'p', DLAMCH := eps*base
+ * = 'N' or 'n', DLAMCH := t
+ * = 'R' or 'r', DLAMCH := rnd
+ * = 'M' or 'm', DLAMCH := emin
+ * = 'U' or 'u', DLAMCH := rmin
+ * = 'L' or 'l', DLAMCH := emax
+ * = 'O' or 'o', DLAMCH := rmax
+ *
+ * where
+ *
+ * eps = relative machine precision
+ * sfmin = safe minimum, such that 1/sfmin does not overflow
+ * base = base of the machine
+ * prec = eps*base
+ * t = number of (base) digits in the mantissa
+ * rnd = 1.0 when rounding occurs in addition, 0.0 otherwise
+ * emin = minimum exponent before (gradual) underflow
+ * rmin = underflow threshold - base**(emin-1)
+ * emax = largest exponent before overflow
+ * rmax = overflow threshold - (base**emax)*(1-eps)
+ *
+ * =====================================================================
+ **/
+extern double dlamch_ (char *CMACH, unsigned long int i);
+
+extern double dlange_ (char* NORM, int* M, int* N, double* A, int* LDA , double* WORK);
+
+extern double dgetrf_ (int* M, int* N , double* A , int* LDA , int* IPIV , int* INFO);
+
+extern double dgecon_ (char* NORM, int* N, double* A, int* LDA, double* ANORM,
+ double* RCOND, double* WORK , int* IWORK, int* INFO ) ;
+
+extern double dgetrs_ (char* TRANS, int* N, int* NRHS, double* A, int* LDA,
+ int* IPIV, double* B, int* LDB, int* INFO ) ;
+
+extern double dgelsy_ (int* M, int* N, int* NRHS, double* A, int* LDA,
+ double* B, int* LDB, int* JPVT, double* RCOND, int* RANK,
+ double* WORK, int* LWORK, int* INFO) ;
+
+extern double dlacpy_ (char* NORM, int* M, int* N, double* A, int* LDA,
+ double* B, int* LDB );
+
+extern double dgetri_ (int* N , double* A , int* LDA , int* IPIV , double* WORK,
+ int* LWORK , int* INFO ) ;
+
+
+/****** doubleComplex fortran function ************/
+extern double zgelsy_ (int*,int*,int*,doubleComplex*,int*,doubleComplex*,int*,int*,double*,int*,doubleComplex*,int*,double*,int*) ;
+
+
+extern double zlamch_ ();
+
+extern double zlange_ (char*,int*,int*,doubleComplex*,int*,doubleComplex*);
+
+extern double zgetrf_ (int *, int *, doubleComplex *, int *, int *, int *);
+
+extern double zgecon_ ( char*,int*,doubleComplex*,int*,double*,double*,doubleComplex*,double*,int*) ;
+
+extern double zgetrs_ ( char *,int*,int*,doubleComplex*,int*,int*,doubleComplex*,int*,int*) ;
+
+extern double zlacpy_ (char*,int*,int*,doubleComplex*,int*,doubleComplex*,int*);
+
+extern double zgetri_ (int*,doubleComplex*,int*,int*,doubleComplex*,int*,int*) ;
+/*extern int zgelsy_ ();*/
+
+/*certainly have some blas functions in */
+extern int C2F(split)();
+extern int C2F(exch)();
+
+extern int C2F(balbak)();
+extern double C2F(ddot)();
+extern int C2F(pade)();
+extern int C2F(dcopy)();
+extern int C2F(dscal)();
+
+extern int C2F(dgeco)();
+extern int C2F(dgesl)();
+extern int C2F(coef)();
+extern int C2F(cerr)();
+extern int C2F(dclmat)();
+extern int C2F(dexpm1)();
+extern int C2F(wexpm1)();
+extern int C2F(drot)();
+
+extern int C2F(intexpm) ();
+
+extern int C2F(zcopy)(int*,doubleComplex *,int*,doubleComplex*,int*);
+
+extern int C2F(dgemm)(char *,char*,int*,int*,int*,double*,double*,int*,double*,int*,double*,double*,int*);
+extern int C2F(idamax)() ;/* could be transcribe easily in c */
+extern int C2F(daxpy) () ;/* could be transcribe easily in c */
+extern int C2F(dscal) () ;/* could be transcribe easily in c */
+extern int C2F(dasum) () ;/* could be transcribe easily in c */
+
+/* used in chol */
+extern int C2F(dpotrf)(char*,int*,double*,int*,int*);
+extern int C2F(zpotrf)(char*,int*,doubleComplex*,int*,int*);
+
+/* used in logm */
+extern int C2F(zgeev)(char*,char*,int*,doubleComplex*,int*,doubleComplex*,
+ doubleComplex*,int*,doubleComplex*,int*,doubleComplex*,int *,doubleComplex*,int*);
+
+extern int C2F(zheev)(char*,char*,int*,doubleComplex*,int*,double*,doubleComplex*,int*,double*,int*);
+
+/* used in spec */
+extern int C2F(dgeev)(char*,char*,int*,double*,int*,double*,double*,double*,int*,double*,int*,double*,int*,int*);
+extern int C2F(dsyev)(char*,char*,int*,double*,int*,double*,double*,int*,int*);
+
+#ifdef __cplusplus
+} /* extern "C" */
+#endif
+#endif /* !__LAPACK_H__ */
diff --git a/2.3-1/includes/machine.h.in b/2.3-1/includes/machine.h.in
new file mode 100644
index 00000000..c38655b9
--- /dev/null
+++ b/2.3-1/includes/machine.h.in
@@ -0,0 +1,80 @@
+/* includes/machine.h.in. Generated from configure.ac by autoheader. */
+
+/* Define to 1 if your Fortran compiler doesn't accept -c and -o together. */
+#undef F77_NO_MINUS_C_MINUS_O
+
+/* Define to 1 if you have the <complex.h> header file. */
+#undef HAVE_COMPLEX_H
+
+/* Define to 1 if you have the <dlfcn.h> header file. */
+#undef HAVE_DLFCN_H
+
+/* Define to 1 if you have the <inttypes.h> header file. */
+#undef HAVE_INTTYPES_H
+
+/* Define to 1 if you have the <memory.h> header file. */
+#undef HAVE_MEMORY_H
+
+/* Define to 1 if stdbool.h conforms to C99. */
+#undef HAVE_STDBOOL_H
+
+/* Define to 1 if you have the <stdint.h> header file. */
+#undef HAVE_STDINT_H
+
+/* Define to 1 if you have the <stdlib.h> header file. */
+#undef HAVE_STDLIB_H
+
+/* Define to 1 if you have the <strings.h> header file. */
+#undef HAVE_STRINGS_H
+
+/* Define to 1 if you have the <string.h> header file. */
+#undef HAVE_STRING_H
+
+/* Define to 1 if you have the <sys/stat.h> header file. */
+#undef HAVE_SYS_STAT_H
+
+/* Define to 1 if you have the <sys/types.h> header file. */
+#undef HAVE_SYS_TYPES_H
+
+/* Define to 1 if you have the <unistd.h> header file. */
+#undef HAVE_UNISTD_H
+
+/* Define to 1 if the system has the type `_Bool'. */
+#undef HAVE__BOOL
+
+/* Define to the sub-directory in which libtool stores uninstalled libraries.
+ */
+#undef LT_OBJDIR
+
+/* Define to 1 if your C compiler doesn't accept -c and -o together. */
+#undef NO_MINUS_C_MINUS_O
+
+/* Name of package */
+#undef PACKAGE
+
+/* Define to the address where bug reports for this package should be sent. */
+#undef PACKAGE_BUGREPORT
+
+/* Define to the full name of this package. */
+#undef PACKAGE_NAME
+
+/* Define to the full name and version of this package. */
+#undef PACKAGE_STRING
+
+/* Define to the one symbol short name of this package. */
+#undef PACKAGE_TARNAME
+
+/* Define to the home page for this package. */
+#undef PACKAGE_URL
+
+/* Define to the version of this package. */
+#undef PACKAGE_VERSION
+
+/* Define to 1 if you have the ANSI C header files. */
+#undef STDC_HEADERS
+
+/* Version number of package */
+#undef VERSION
+
+/* With the Atlas Lib */
+#undef WITH_ATLAS
diff --git a/2.3-1/includes/notFound.h b/2.3-1/includes/notFound.h
new file mode 100644
index 00000000..2d5ee1c2
--- /dev/null
+++ b/2.3-1/includes/notFound.h
@@ -0,0 +1,18 @@
+/*
+ * Scilab ( http://www.scilab.org/ ) - This file is part of Scilab
+ * Copyright (C) 2007-2008 - INRIA - Bruno JOFRET
+ *
+ * This file must be used under the terms of the CeCILL.
+ * This source file is licensed as described in the file COPYING, which
+ * you should have received as part of this distribution. The terms
+ * are also available at
+ * http://www.cecill.info/licences/Licence_CeCILL_V2-en.txt
+ *
+ */
+
+#ifndef __NOT_FOUND_H__
+#define __NOT_FOUND_H__
+
+#define NOT_FOUND -1
+
+#endif /* !__NOT_FOUND_H__ */
diff --git a/2.3-1/includes/sci2clib.h b/2.3-1/includes/sci2clib.h
new file mode 100644
index 00000000..eff4cf05
--- /dev/null
+++ b/2.3-1/includes/sci2clib.h
@@ -0,0 +1,297 @@
+#ifndef __SCI2CLIB_H__
+#define __SCI2CLIB_H__
+
+#include <stdlib.h>
+#include <string.h>
+#include <math.h>
+/* #include "SCI2CMacroInterface.h" */
+/* #include "notFound.h" */
+/* #include "doubleComplex.h" */
+/* #include "floatComplex.h" */
+/* #include "RealToComplex.h" */
+/* #include "OpEqual.h" */
+/* #include "OpIns.h" */
+/* #include "OpExt.h" */
+/* #include "FileManagement.h" */
+/* #include "OpLogNe.h" */
+/* #include "OpLogGt.h" */
+/* #include "OpLogLt.h" */
+/* #include "OpLogGe.h" */
+/* #include "OpLogLe.h" */
+/* #include "OpLogEq.h" */
+/* #include "OpLogOr.h" */
+/* #include "OpLogAnd.h" */
+/* #include "OpLogNot.h" */
+/* #include "ConvertPrecision.h" */
+
+/* CONSTANT */
+#include "constant.h"
+
+/* LIB */
+/* interfacing lapack */
+#include "lapack.h"
+/* interfacing blas */
+#include "blas.h"
+
+/* AUXILIARY FUNCTIONS */
+
+/* interfacing abs */
+#include "abs.h"
+#include "int_abs.h"
+/* interfacing conj */
+#include "conj.h"
+#include "int_conj.h"
+/* interfacing disp */
+#include "disp.h"
+#include "int_disp.h"
+/* interfacing find */
+#include "find.h"
+#include "find2d.h"
+#include "int_find.h"
+/* interfacing frexp */
+#include "frexp.h"
+/* interfacing isempty */
+#include "isempty.h"
+#include "int_isempty.h"
+/* interfacing isnan */
+#include "isnan.h"
+#include "int_isnan.h"
+/* interfacing length */
+#include "length.h"
+#include "int_length.h"
+/* interfacing max */
+#include "max.h"
+#include "int_max.h"
+/* interfacing min */
+#include "min.h"
+#include "int_min.h"
+/* interfacing pythag */
+#include "pythag.h"
+/* interfacing sign */
+#include "sign.h"
+#include "int_sign.h"
+/* interfacing size */
+#include "size.h"
+#include "int_size.h"
+/* interfacing type */
+#include "type.h"
+#include "int_type.h"
+/* interfacing rand */
+#include "rand.h"
+#include "int_rand.h"
+
+/* ELEMENTARY FUNCTIONS */
+
+/* interfacing acos */
+#include "acos.h"
+#include "int_acos.h"
+/* interfacing acosh */
+#include "acosh.h"
+#include "int_acosh.h"
+/* interfacing asin */
+#include "asin.h"
+#include "int_asin.h"
+/* interfacing asinh */
+#include "asinh.h"
+#include "int_asinh.h"
+/* interfacing atan */
+#include "atan.h"
+#include "atan2.h"
+#include "int_atan.h"
+/* interfacing atanh */
+#include "atanh.h"
+#include "int_atanh.h"
+/* interfacing cos */
+#include "cos.h"
+#include "int_cos.h"
+/* interfacing ceil */
+#include "ceil.h"
+#include "int_ceil.h"
+/* interfacing cosh */
+#include "cosh.h"
+#include "int_cosh.h"
+/* interfacing exp */
+#include "exp.h"
+#include "int_exp.h"
+/* interfacing fix */
+#include "fix.h"
+#include "int_fix.h"
+/* interfacing floor */
+#include "floor.h"
+#include "int_floor.h"
+/* interfacing int */
+#include "int.h"
+#include "int_int.h"
+/* interfacing lnp1m1 */
+#include "lnp1m1.h"
+/* interfacing log */
+#include "log.h"
+#include "int_log.h"
+/* interfacing log10 */
+#include "log10.h"
+#include "int_log10.h"
+/* interfacing log1p */
+#include "log1p.h"
+#include "int_log1p.h"
+/* interfacing pow */
+#include "pow.h"
+#include "matrixPow.h"
+#include "int_OpHat.h"
+#include "int_OpDotHat.h"
+/* interfacing round */
+#include "round.h"
+#include "int_round.h"
+/* interfacing sin */
+#include "sin.h"
+#include "int_sin.h"
+/* interfacing sinh */
+#include "sinh.h"
+#include "int_sinh.h"
+/* interfacing sqrt */
+#include "sqrt.h"
+#include "int_sqrt.h"
+/* interfacing tan */
+#include "tan.h"
+#include "int_tan.h"
+/* interfacing tanh */
+#include "tanh.h"
+#include "int_tanh.h"
+
+/* IMPLICIT LISTS */
+/* interfacing implicitList/OpColon */
+#include "implicitList.h"
+#include "int_OpColon.h"
+
+
+/* OPERATIONS */
+/* interfacing assignation */
+#include "int_OpEqual.h"
+/* interfacing addition */
+#include "addition.h"
+#include "int_OpPlus.h"
+/* interfacing subtraction */
+#include "subtraction.h"
+#include "int_OpMinus.h"
+/* interfacing multiplication */
+#include "multiplication.h"
+#include "matrixMultiplication.h"
+#include "int_OpStar.h"
+#include "int_OpDotStar.h"
+/* interfacing division */
+#include "division.h"
+#include "matrixDivision.h"
+#include "int_OpSlash.h"
+#include "int_OpDotSlash.h"
+#include "int_OpBackSlash.h"
+#include "int_OpDotBackSlash.h"
+/* interfacing comparison */
+#include "int_OpLogNot.h"
+#include "int_OpLogEq.h"
+#include "int_OpLogNe.h"
+#include "int_OpLogGt.h"
+#include "int_OpLogGe.h"
+#include "int_OpLogLt.h"
+#include "int_OpLogLe.h"
+#include "int_OpLogAnd.h"
+#include "int_OpLogOr.h"
+/* interfacing insertion */
+#include "int_OpIns.h"
+
+
+/* MATRIX OPERATIONS */
+/* interfacing extraction */
+#include "int_OpExt.h"
+/* interfacing cat */
+#include "cat.h"
+#include "int_OpRc.h"
+#include "int_OpCc.h"
+/* interfacing chol */
+#include "chol.h"
+#include "int_chol.h"
+/* interfacing determinant */
+#include "determ.h"
+#include "int_det.h"
+/* interfacing expm */
+#include "matrixExponential.h"
+#include "int_expm.h"
+/* interfacing eye */
+#include "eye.h"
+#include "int_eye.h"
+/* interfacing fill */
+#include "fill.h"
+/* interfacing inversion */
+#include "matrixInversion.h"
+#include "int_invert.h"
+/* interfacing infinite norm */
+#include "infiniteNorm.h" /* interfacing ones */
+#include "ones.h"
+#include "int_ones.h"
+/* interfacing spec */
+#include "spec.h"
+#include "int_spec.h"
+/* interfacing trace */
+#include "matrixTrace.h"
+#include "int_trace.h"
+/* interfacing tranpose */
+#include "matrixTranspose.h"
+#include "int_OpApex.h"
+#include "int_OpDotApex.h" /* interfacing zeros */
+#include "zeros.h"
+#include "int_zeros.h"
+
+
+
+/* SIGNAL PROCESSING */
+/* interfacing convol */
+#include "conv.h"
+#include "conv2d.h"
+#include "int_convol.h"
+/* interfacing fft */
+#include "fft.h"
+#include "fft_internal.h"
+#include "int_fft.h"
+/* interfacing fftshift */
+#include "fftshift.h"
+#include "int_fftshift.h"
+/* interfacing ifft */
+#include "ifft.h"
+#include "ifft_internal.h"
+#include "int_ifft.h"
+/* interfacing lev */
+#include "lev.h"
+#include "int_lev.h"
+
+
+
+/* STATISTICS FUNCTIONS */
+
+/* interfacing max */
+#include "statMax.h"
+/* interfacing min */
+#include "statMin.h"
+/* interfacing mean */
+#include "mean.h"
+#include "int_mean.h"
+/* interfacing stdevf */
+#include "stdevf.h"
+#include "int_stdevf.h"
+/* interfacing meanf */
+#include "meanf.h"
+#include "int_meanf.h"
+/* interfacing sum */
+#include "sum.h"
+#include "int_sum.h"
+/* interfacing prod */
+#include "prod.h"
+#include "int_prod.h"
+/* interfacing variance */
+#include "variance.h"
+#include "int_variance.h"
+
+/* TYPE */
+/* interfacing real */
+#include "int_real.h"
+/* interfacing imag */
+#include "int_imag.h"
+
+#endif /* !__SCI2CLIB_H__ */