Intel® oneAPI Math Kernel Library
Ask questions and share information with other developers who use Intel® Math Kernel Library.
6985 Discussions

Failed to use MKL linked dynamically from Delphi, x64

RomanN
Novice
787 Views

Dear community,

 

Just making the first steps with MKL, sorry for the newbie question, I'm sure every experienced user knows the answer.

I tried to load load the mkl_rt.2.dll dynamically from the MKL installation directory. Before the loading, I set the environment vars exactly as env\vars.bat does. Next, I loaded the MKL_Get_Max_Threads() func and tried to call it as a "function: Integer; cdecl;"  or "function: Longint; cdecl;" or "function: NativeInt; cdecl;" I got an exception immediately in any case. I saw in the debugger how do the MKL dlls load, so some of the env vars do the job.

There is a post https://community.intel.com/t5/Intel-oneAPI-Math-Kernel-Library/Attempting-to-use-MKL-RT-2-DLL-in-Delphi-Pascal/m-p/1514178 which looks similar to my question but the author @CodingInDelphiIn2023 didn't give the final solution.

I studied https://www.intel.com/content/www/us/en/docs/onemkl/developer-guide-windows/2024-0/setting-environment-variables.html

It mentions the LD_LIBRARY_PATH var, but the vars.bat doesn't set it.

Of course, I'd like to use the math routines like dgemm() in a way how I use them now with the OpenBLAS.

So my task is very simple: just want to use installed MKL with my 64 bit application and control the calculation's threading of course. If you can share the instruction how to load mkl_rt.2.dll dynamically and use it after, I appreciate it very much.

Labels (2)
0 Kudos
1 Solution
RomanN
Novice
709 Views

Dear community and @CodingInDelphiIn2023 ,

 

I seems like I could do everything correct and got the working code which loads MKL and does some basics calls

 

program mkl_load;

{$APPTYPE CONSOLE}

{$R *.res}

uses
  System.SysUtils,
  WinAPI.Windows;

type
  int = Integer; // INTEGER*4, The size of Integer is 32 bits across all 64-bit and 32-bit platforms.
  float = Single; // 4 bytes
  Pfloat = ^float;
  enum = int;

  MKL_INT = Integer;
  PMKL_INT = ^MKL_INT;

  MKL_CHAR = AnsiChar;
  MKL_PCHAR = PAnsiChar;

  PMKLVersion = ^TMKLVersion;
  TMKLVersion = record  // MKL_PCHAR = PAnsiChar
    MajorVersion : int;
    MinorVersion : int;
    UpdateVersion : int;
    ProductStatus : MKL_PCHAR;
    Build : MKL_PCHAR;
    Processor : MKL_PCHAR;
    Platform : MKL_PCHAR;
  end;

  TCBLAS_ORDER = enum;
  TCBLAS_TRANSPOSE = enum;

const
  CblasRowMajor: TCBLAS_ORDER = 101;
  CblasColMajor: TCBLAS_ORDER = 102;

  CblasNoTrans: TCBLAS_TRANSPOSE = 111;
  CblasTrans: TCBLAS_TRANSPOSE = 112;
  CblasConjTrans: TCBLAS_TRANSPOSE = 113;

var
  MKL_Get_Version: procedure(ver: PMKLVersion); cdecl;
  MKL_Get_Version_String: procedure(buffer: MKL_PCHAR; len: int); cdecl;
  MKL_Get_Cpu_Frequency: function: Double; cdecl;
  MKL_Set_Num_Threads: procedure(nth: int); cdecl;
  MKL_Set_Dynamic: procedure(bool_MKL_DYNAMIC: int); cdecl;
  MKL_Get_Dynamic: function: int; cdecl;
  MKL_Get_Max_Threads: function: int; cdecl;
  MKL_Disable_Fast_MM: function: int; cdecl;
  MKL_Enable_Instructions: procedure(instructionSet: int); cdecl;
  MKL_Set_Threading_Layer:procedure(required_threading: int); cdecl;

  dgemm_: procedure(
    TRANSA, TRANSB: MKL_PCHAR;
    M, N, K: PMKL_INT;
    ALPHA, A: PDouble; LDA: PMKL_INT;
    B: PDouble; LDB: PMKL_INT;
    BETA: PDouble; C: PDouble; LDC: PMKL_INT); cdecl;

  DGEMM: procedure(
    const TRANSA, TRANSB: MKL_PCHAR;
    const M, N, K: PMKL_INT;
    const ALPHA, A: PDouble; const LDA: PMKL_INT;
    const B: PDouble; const LDB: PMKL_INT;
    const BETA: PDouble; C: PDouble; const LDC: PMKL_INT); cdecl;

  cblas_dgemm: procedure(
    const LAYOUT: TCBLAS_ORDER; const TRANSA, TRANSB: TCBLAS_TRANSPOSE;
    const M, N, K: MKL_INT;
    const ALPHA: Double;
    const A: PDouble; const LDA: MKL_INT;
    const B: PDouble; const LDB: MKL_INT;
    const BETA: Double;
    C: PDouble; const LDC: MKL_INT); cdecl;

  LSAME: function(const ca: MKL_PCHAR; const cb: MKL_PCHAR; const lca: int; const lcb: int): int; cdecl;
  DASUM: function (const n: PMKL_INT; const x: PDouble; const incx: PMKL_INT): Double; cdecl;

  MKLHandle: THandle;
  MKLVersion: TMKLVersion;
  VerStr: AnsiString;

  Int_Value: int;
  DoubleVector: Array[0..1] of Double;
  i, j: Integer;
  A, B, C: Array of Double;
  m, n, k: MKL_INT;
  alpha, beta: Double;
begin
  try
    MKLHandle := LoadLibrary('c:\Program Files (x86)\Intel\oneAPI\mkl\2024.0\bin\mkl_rt.2.dll');
    if MKLHandle = 0 then
      raise Exception.Create('MKL not loaded!');
    try
      // Case Sensitive!
      @MKL_Get_Version := GetProcAddress(MKLHandle, 'MKL_Get_Version');
      @MKL_Get_Version_String := GetProcAddress(MKLHandle, 'MKL_Get_Version_String');
      @MKL_Get_Cpu_Frequency := GetProcAddress(MKLHandle, 'MKL_Get_Cpu_Frequency');

      @MKL_Set_Num_Threads := GetProcAddress(MKLHandle,'MKL_Set_Num_Threads');

      @MKL_Get_Max_Threads := GetProcAddress(MKLHandle, 'MKL_Get_Max_Threads');

      @MKL_Set_Dynamic := GetProcAddress(MKLHandle,'MKL_Set_Dynamic');
      @MKL_Get_Dynamic := GetProcAddress(MKLHandle,'MKL_Get_Dynamic');

      @MKL_Enable_Instructions := GetProcAddress(MKLHandle,'MKL_Enable_Instructions');
      @MKL_Set_Threading_Layer := GetProcAddress(MKLHandle,'MKL_Set_Threading_Layer');

      @MKL_Disable_Fast_MM := GetProcAddress(MKLHandle, 'MKL_Disable_Fast_MM');

      @LSAME := GetProcAddress(MKLHandle, 'LSAME');
      @DASUM := GetProcAddress(MKLHandle, 'DASUM');

      @dgemm_ := GetProcAddress(MKLHandle, 'dgemm_');
      @DGEMM := GetProcAddress(MKLHandle, 'DGEMM');
      @cblas_dgemm := GetProcAddress(MKLHandle, 'cblas_dgemm');


      // The function return value 1 indicates that the Intel MKL memory
      // management was turned off successfully. The function return value 0 indicates a failure.
      // Disabling just for test
      Int_Value := MKL_Disable_Fast_MM();
      if Int_Value <> 1 then
        raise Exception.Create('MKL_Disable_Fast_MM() failed');

      // Library information
      SetLength(VerStr, 257);
      FillChar(VerStr[1], Length(VerStr), 0);
      MKL_Get_Version_String(PAnsiChar(VerStr), Length(VerStr) - 1);
      VerStr := Trim(String(VerStr));
      Writeln(VerStr);

      MKL_Get_Version(@MKLVersion);
      Writeln(MKLVersion.MajorVersion, '.', MKLVersion.MinorVersion, ' update ', MKLVersion.UpdateVersion, ' build ', String(MKLVersion.Build), ' (', String(MKLVersion.ProductStatus), ')');
      Writeln(String(MKLVersion.Processor), ', ', String(MKLVersion.Platform));

      Writeln;

      // Setting up
      MKL_Set_Dynamic(0);
      MKL_Set_Num_Threads(1);

      Writeln('MKL_Get_Dynamic() = ', MKL_Get_Dynamic());
      Writeln(Format('MKL_Get_Cpu_Frequency = %.2f GHz', [MKL_Get_Cpu_Frequency()]));

      // Only if MKL_Set_Dynamic(0) !!!
      Writeln('MKL_Get_Max_Threads() = ', MKL_Get_Max_Threads());

      // Very basic functions
      Writeln('LSAME(a, a) = ', LSAME('a', 'a', 1, 1));
      Writeln('LSAME(a, b) = ', LSAME('a', 'b', 1, 1));
      Writeln('LSAME(aaaa, aa) = ', LSAME('aaaa', 'aa', 4, 2));
      Writeln('LSAME(aaaa, aaaa) = ', LSAME('aaaa', 'aaaa', 4, 4));

      var Double_Value: Double := 103.58;
      DoubleVector[0] := Double_Value;
      DoubleVector[1] := Double_Value * 2.0;
      var DoubleExpected: Double := Double_Value * 3.0;

      var VectorLength: Integer := 2;
      Int_Value := 1;
      var DoubleSum := DASUM(@VectorLength, @DoubleVector[0], @Int_Value);
      Writeln('DASUM() = ', DoubleSum, ' expected is ', DoubleExpected);

      // DGEMM family test
      m := 2000;
      n := 1000;
      k := 200;
      alpha := 1.0;
      beta := 0.0;

      SetLength(A, m*k);
      SetLength(B, k*n);
      SetLength(C, m*n);
      try
        for i := 0 to Length(A) - 1 do
          A[i] := i + 1;

        for i := 0 to Length(B) - 1 do
          B[i] := -i - 1;

        for i := 0 to Length(C) - 1 do
          C[i] := 0;

        dgemm_( // dgemm_ - col major
          'N', 'N',
          @m, @n, @k,
          @alpha,
          @A[0], @m,
          @B[0], @k,
          @beta,
          @C[0], @m);

        Writeln('dgemm_: ', C[0], ', ', C[1]);

        for i := 0 to Length(C) - 1 do
          C[i] := 0;

        DGEMM(
          'N', 'N',
          @m, @n, @k,
          @alpha,
          @A[0], @m,
          @B[0], @k,
          @beta,
          @C[0], @m);

        Writeln('DGEMM: ', C[0], ', ', C[1]);

        for i := 0 to Length(C) - 1 do
          C[i] := 0;

        cblas_dgemm(
          CblasColMajor, CblasNoTrans, CblasNoTrans,
          m, n, k,
          alpha,
          @A[0], m,
          @B[0], k,
          beta,
          @C[0], m);

        Writeln('cblas_dgemm: ', C[0], ', ', C[1]);
      finally
        A := nil;
        B := nil;
        C := nil;
      end;
    finally
      FreeLibrary(MKLHandle);
    end;
  except
    on E: Exception do
      Writeln(E.ClassName, ': ', E.Message);
  end;

  {$IFDEF DEBUG}
  Readln;
  {$ENDIF}
end.

 

Of course, the code is not clean and ideal, a lot of checks must be introduced. However, it shows the general idea. No environment variables manipulations were involved! The target platform is Win64, didn't check Win32. Hope this code will help someone to load MKL for the firs time.

View solution in original post

4 Replies
CodingInDelphiIn2023
764 Views

Hey,

 

I gave up on setting the vars, it was a bit of a misdirection for me, I'm not at work right now so I can't give you the full reproduction steps but these steps were important to use the MKL_RT.2.DLL in Delphi Pascal:

  • Procedures / Functions have to be called with case sensitivity
  • Make sure the arguments you pass are the same size. 
  • For arrays - Use pointers to the first Index of the array you're passing
  • Make sure you're using the right type that matches up with the types used in C++, you'll get very unclear errors if you don't do this
  • Just install MKL, either add the redist paths to your compilers search path, or just add them somewhere else where the executable can find them. 

Carefully consider the difference between passing something by value or reference. Often a lot of the parameters will have to be passed by reference.

 

For a small sanity check here's some source code on the most basic calls you should start with, this is Delphi Pascal of course. We're delayed loading the DLL here on purpose. If these calls work you can narrow down issues to missing files or passing parameters wrongly. You could also open an elevated command prompt, run the setvars and then run your executable. If that does work then that implies a missing file issue.

MKL_INT = Int64;
   MKL_SET_NUM_THREADS: procedure(nt : MKL_INT); cdecl;
   MKL_SET_DYNAMIC: procedure(enable : MKL_INT); cdecl;
   MKL_ENABLE_INSTRUCTIONS:procedure(instructionSet:MKL_INT); cdecl;
   MKL_SET_THREADING_LAYER:procedure(required_threading:MKL_INT); cdecl;
procedure LoadMKL;
begin
{$IF DEFINED(WIN32) or DEFINED(WIN64)}
   try
      if MKLHandle = 0 then
      begin
         MKLHandle:=LoadLibrary('MKL\mkl_rt.2.dll');

         @mkl_SET_NUM_THREADS:=GetProcAddress(MKLHandle,'MKL_Set_Num_Threads'); // Case Sensitive!
         @mkl_SET_DYNAMIC:=GetProcAddress(MKLHandle,'MKL_Set_Dynamic'); // Case Sensitive!
         @mkl_ENABLE_INSTRUCTIONS:=GetProcAddress(MKLHandle,'MKL_Enable_Instructions'); // Case Sensitive!
         @mkl_SET_THREADING_LAYER:=GetProcAddress(MKLHandle,'MKL_Set_Threading_Layer'); // Case Sensitive!

         //MKL_ENABLE_INSTRUCTIONS(2);
         //MKL_SET_THREADING_LAYER(0);
         MKL_SET_NUM_THREADS(1);
         //MKL_SET_DYNAMIC(0);


         @PARDISO:=GetProcAddress(MKLHandle,'pardiso');

         @PARDISOINIT:=GetProcAddress(MKLHandle,'pardisoinit');
      end;
   except
      on E: Exception do ShowMessage(E.ClassName + ' error raised, with message : ' + E.Message);
   end;
{$ENDIF}
end;

 

RomanN
Novice
742 Views

Many thanks to your reply!

 

I made a small console app just to try the MKL to load.

  1. I confirm that mkl_rt.2.dll was able to load with no environment vars set in prior. That's really nice! I even didn't add the path to any of the IDE configurations or search paths.
  2. I could call MKL_Get_Version(), MKL_Get_Version_String(), MKL_Get_Cpu_Frequency() and MKL_Get_Dynamic() successfully but MKL_Get_Max_Threads() raised an exception. After reading the forums, I tried MKL_Set_Dynamic(0) and MKL_Set_Num_Threads(4) before call to MKL_Get_Max_Threads(). This worked and it returned 4. So my initial problem of getting exception of calling the MKL_Get_Max_Threads() is solved.

You also mentioned the redist paths. Did you mean the some kind of folder which contains the redistributive modules of MKL? My installation went to "c:\Program Files (x86)\Intel\oneAPI\mkl\2024.0\bin", and I couldn't locate any redist-looking folders in the parent folders. Well, for me it is not critical, I won't even try to redistribute MKL. I'll detect it in the system and add to the options to selects for the math calculations.

So my next step is to call some of BLAS/LAPACK functions. I already saw that procedures declarations differ from original BLAS/LAPACK or OpenBLAS which I use now. MKL passes most of the arguments by ref. Hope that everything will go well.

0 Kudos
RomanN
Novice
710 Views

Dear community and @CodingInDelphiIn2023 ,

 

I seems like I could do everything correct and got the working code which loads MKL and does some basics calls

 

program mkl_load;

{$APPTYPE CONSOLE}

{$R *.res}

uses
  System.SysUtils,
  WinAPI.Windows;

type
  int = Integer; // INTEGER*4, The size of Integer is 32 bits across all 64-bit and 32-bit platforms.
  float = Single; // 4 bytes
  Pfloat = ^float;
  enum = int;

  MKL_INT = Integer;
  PMKL_INT = ^MKL_INT;

  MKL_CHAR = AnsiChar;
  MKL_PCHAR = PAnsiChar;

  PMKLVersion = ^TMKLVersion;
  TMKLVersion = record  // MKL_PCHAR = PAnsiChar
    MajorVersion : int;
    MinorVersion : int;
    UpdateVersion : int;
    ProductStatus : MKL_PCHAR;
    Build : MKL_PCHAR;
    Processor : MKL_PCHAR;
    Platform : MKL_PCHAR;
  end;

  TCBLAS_ORDER = enum;
  TCBLAS_TRANSPOSE = enum;

const
  CblasRowMajor: TCBLAS_ORDER = 101;
  CblasColMajor: TCBLAS_ORDER = 102;

  CblasNoTrans: TCBLAS_TRANSPOSE = 111;
  CblasTrans: TCBLAS_TRANSPOSE = 112;
  CblasConjTrans: TCBLAS_TRANSPOSE = 113;

var
  MKL_Get_Version: procedure(ver: PMKLVersion); cdecl;
  MKL_Get_Version_String: procedure(buffer: MKL_PCHAR; len: int); cdecl;
  MKL_Get_Cpu_Frequency: function: Double; cdecl;
  MKL_Set_Num_Threads: procedure(nth: int); cdecl;
  MKL_Set_Dynamic: procedure(bool_MKL_DYNAMIC: int); cdecl;
  MKL_Get_Dynamic: function: int; cdecl;
  MKL_Get_Max_Threads: function: int; cdecl;
  MKL_Disable_Fast_MM: function: int; cdecl;
  MKL_Enable_Instructions: procedure(instructionSet: int); cdecl;
  MKL_Set_Threading_Layer:procedure(required_threading: int); cdecl;

  dgemm_: procedure(
    TRANSA, TRANSB: MKL_PCHAR;
    M, N, K: PMKL_INT;
    ALPHA, A: PDouble; LDA: PMKL_INT;
    B: PDouble; LDB: PMKL_INT;
    BETA: PDouble; C: PDouble; LDC: PMKL_INT); cdecl;

  DGEMM: procedure(
    const TRANSA, TRANSB: MKL_PCHAR;
    const M, N, K: PMKL_INT;
    const ALPHA, A: PDouble; const LDA: PMKL_INT;
    const B: PDouble; const LDB: PMKL_INT;
    const BETA: PDouble; C: PDouble; const LDC: PMKL_INT); cdecl;

  cblas_dgemm: procedure(
    const LAYOUT: TCBLAS_ORDER; const TRANSA, TRANSB: TCBLAS_TRANSPOSE;
    const M, N, K: MKL_INT;
    const ALPHA: Double;
    const A: PDouble; const LDA: MKL_INT;
    const B: PDouble; const LDB: MKL_INT;
    const BETA: Double;
    C: PDouble; const LDC: MKL_INT); cdecl;

  LSAME: function(const ca: MKL_PCHAR; const cb: MKL_PCHAR; const lca: int; const lcb: int): int; cdecl;
  DASUM: function (const n: PMKL_INT; const x: PDouble; const incx: PMKL_INT): Double; cdecl;

  MKLHandle: THandle;
  MKLVersion: TMKLVersion;
  VerStr: AnsiString;

  Int_Value: int;
  DoubleVector: Array[0..1] of Double;
  i, j: Integer;
  A, B, C: Array of Double;
  m, n, k: MKL_INT;
  alpha, beta: Double;
begin
  try
    MKLHandle := LoadLibrary('c:\Program Files (x86)\Intel\oneAPI\mkl\2024.0\bin\mkl_rt.2.dll');
    if MKLHandle = 0 then
      raise Exception.Create('MKL not loaded!');
    try
      // Case Sensitive!
      @MKL_Get_Version := GetProcAddress(MKLHandle, 'MKL_Get_Version');
      @MKL_Get_Version_String := GetProcAddress(MKLHandle, 'MKL_Get_Version_String');
      @MKL_Get_Cpu_Frequency := GetProcAddress(MKLHandle, 'MKL_Get_Cpu_Frequency');

      @MKL_Set_Num_Threads := GetProcAddress(MKLHandle,'MKL_Set_Num_Threads');

      @MKL_Get_Max_Threads := GetProcAddress(MKLHandle, 'MKL_Get_Max_Threads');

      @MKL_Set_Dynamic := GetProcAddress(MKLHandle,'MKL_Set_Dynamic');
      @MKL_Get_Dynamic := GetProcAddress(MKLHandle,'MKL_Get_Dynamic');

      @MKL_Enable_Instructions := GetProcAddress(MKLHandle,'MKL_Enable_Instructions');
      @MKL_Set_Threading_Layer := GetProcAddress(MKLHandle,'MKL_Set_Threading_Layer');

      @MKL_Disable_Fast_MM := GetProcAddress(MKLHandle, 'MKL_Disable_Fast_MM');

      @LSAME := GetProcAddress(MKLHandle, 'LSAME');
      @DASUM := GetProcAddress(MKLHandle, 'DASUM');

      @dgemm_ := GetProcAddress(MKLHandle, 'dgemm_');
      @DGEMM := GetProcAddress(MKLHandle, 'DGEMM');
      @cblas_dgemm := GetProcAddress(MKLHandle, 'cblas_dgemm');


      // The function return value 1 indicates that the Intel MKL memory
      // management was turned off successfully. The function return value 0 indicates a failure.
      // Disabling just for test
      Int_Value := MKL_Disable_Fast_MM();
      if Int_Value <> 1 then
        raise Exception.Create('MKL_Disable_Fast_MM() failed');

      // Library information
      SetLength(VerStr, 257);
      FillChar(VerStr[1], Length(VerStr), 0);
      MKL_Get_Version_String(PAnsiChar(VerStr), Length(VerStr) - 1);
      VerStr := Trim(String(VerStr));
      Writeln(VerStr);

      MKL_Get_Version(@MKLVersion);
      Writeln(MKLVersion.MajorVersion, '.', MKLVersion.MinorVersion, ' update ', MKLVersion.UpdateVersion, ' build ', String(MKLVersion.Build), ' (', String(MKLVersion.ProductStatus), ')');
      Writeln(String(MKLVersion.Processor), ', ', String(MKLVersion.Platform));

      Writeln;

      // Setting up
      MKL_Set_Dynamic(0);
      MKL_Set_Num_Threads(1);

      Writeln('MKL_Get_Dynamic() = ', MKL_Get_Dynamic());
      Writeln(Format('MKL_Get_Cpu_Frequency = %.2f GHz', [MKL_Get_Cpu_Frequency()]));

      // Only if MKL_Set_Dynamic(0) !!!
      Writeln('MKL_Get_Max_Threads() = ', MKL_Get_Max_Threads());

      // Very basic functions
      Writeln('LSAME(a, a) = ', LSAME('a', 'a', 1, 1));
      Writeln('LSAME(a, b) = ', LSAME('a', 'b', 1, 1));
      Writeln('LSAME(aaaa, aa) = ', LSAME('aaaa', 'aa', 4, 2));
      Writeln('LSAME(aaaa, aaaa) = ', LSAME('aaaa', 'aaaa', 4, 4));

      var Double_Value: Double := 103.58;
      DoubleVector[0] := Double_Value;
      DoubleVector[1] := Double_Value * 2.0;
      var DoubleExpected: Double := Double_Value * 3.0;

      var VectorLength: Integer := 2;
      Int_Value := 1;
      var DoubleSum := DASUM(@VectorLength, @DoubleVector[0], @Int_Value);
      Writeln('DASUM() = ', DoubleSum, ' expected is ', DoubleExpected);

      // DGEMM family test
      m := 2000;
      n := 1000;
      k := 200;
      alpha := 1.0;
      beta := 0.0;

      SetLength(A, m*k);
      SetLength(B, k*n);
      SetLength(C, m*n);
      try
        for i := 0 to Length(A) - 1 do
          A[i] := i + 1;

        for i := 0 to Length(B) - 1 do
          B[i] := -i - 1;

        for i := 0 to Length(C) - 1 do
          C[i] := 0;

        dgemm_( // dgemm_ - col major
          'N', 'N',
          @m, @n, @k,
          @alpha,
          @A[0], @m,
          @B[0], @k,
          @beta,
          @C[0], @m);

        Writeln('dgemm_: ', C[0], ', ', C[1]);

        for i := 0 to Length(C) - 1 do
          C[i] := 0;

        DGEMM(
          'N', 'N',
          @m, @n, @k,
          @alpha,
          @A[0], @m,
          @B[0], @k,
          @beta,
          @C[0], @m);

        Writeln('DGEMM: ', C[0], ', ', C[1]);

        for i := 0 to Length(C) - 1 do
          C[i] := 0;

        cblas_dgemm(
          CblasColMajor, CblasNoTrans, CblasNoTrans,
          m, n, k,
          alpha,
          @A[0], m,
          @B[0], k,
          beta,
          @C[0], m);

        Writeln('cblas_dgemm: ', C[0], ', ', C[1]);
      finally
        A := nil;
        B := nil;
        C := nil;
      end;
    finally
      FreeLibrary(MKLHandle);
    end;
  except
    on E: Exception do
      Writeln(E.ClassName, ': ', E.Message);
  end;

  {$IFDEF DEBUG}
  Readln;
  {$ENDIF}
end.

 

Of course, the code is not clean and ideal, a lot of checks must be introduced. However, it shows the general idea. No environment variables manipulations were involved! The target platform is Win64, didn't check Win32. Hope this code will help someone to load MKL for the firs time.

VarshaS_Intel
Moderator
653 Views

Hi Roman,

 

Thanks for posting in Intel Communities.

 

Thanks for sharing the detailed explanation and solution. It’s great to know that the issue has been resolved, in case you run into any other issues please feel free to create a new thread.

 

Have a Good Day!

 

Thanks & Regards,

Varsha

 

0 Kudos
Reply