Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.
29274 Discussions

How to change the look of a Console Application ?

jim_cox
Beginner
5,093 Views
Much of our existing Fortran code stream is compiled as Console Applications

I've been asked if we can 'modernise' the look of these display windows

Is it possible to set the font, the foregound and the background colours of a Console window?

Thankx and happy Friday to all...

Jimmy
0 Kudos
21 Replies
Steven_L_Intel1
Employee
4,537 Views
I suggest you take a look at QuickWin. Create a new project using the Fortran QuickWin Application template and add your existing sources to it. Run it.

You can customize many aspects. See Using Intel Visual Fortran to Create and Build Windows*-Based Applications for details. You'll be interested in SETFONT, SETTEXTCOLOR and more.
0 Kudos
jim_cox
Beginner
4,537 Views
Tried that

But the application crashes on the write when

SUBROUTINE MSGERR( ERRMSG )
IMPLICIT NONE
CHARACTER*(*) ERRMSG

write(*,*) errmsg

RETURN
END


Gets called :(

Any thoughts ?

0 Kudos
Steven_L_Intel1
Employee
4,537 Views
Nope. Nothing wrong with that subroutine. Anything a console application does should "just work" in QuickWin. What is the error that you get? (Full and complete text please.)
0 Kudos
jim_cox
Beginner
4,537 Views



when errmsg =
' *** This release of TRACKS expected a version V5.2 data file (found V7.0) '
0 Kudos
Steven_L_Intel1
Employee
4,537 Views
Curious. Some reason you're using /iface:cvf? Did you actually create a new project or did you just change the run-time library type?
0 Kudos
jim_cox
Beginner
4,537 Views
Created a new project,

but needed to use /iface:cvf to link in a couple of old external libraries we use.

Edit - later:

Interesting - been playing with QuickWin - can't get it to work with our old code - changing the interface settings on the program and libraries causes a number of link errors and/or some code to stop working. It looks like we would have to give our library calls a makeover to get it work.

Quickwin also appears to give us not quite what we want - a single simple output window. While I can maximise the child window and delete the menus 1 - 6, I can't get rid of the icon menu. And to make best use of the fonts I would need to make all the output routines use outgtext.

Is there really no way to set the text and background colors in a console window ? - thats all we actually need

Thankx again

Jim

0 Kudos
Steven_L_Intel1
Employee
4,537 Views
Just for grins - create another new project, this time as a console application, with the same settings otherwise as for the QuickWin. Does it run ok? If it does, are you willing to give us a test program that reproduces the problem?
0 Kudos
jim_cox
Beginner
4,537 Views
Grins you want? Try this



C****************************************************************
PROGRAM MAIN
C****************************************************************
C
USE IFQWIN

WRITE(*,*)'Hello world'

pause


END PROGRAM MAIN





Built as a new console window in a new solution it works fine

Swap to using Quickwin libaries and you get Access Violations


If you create a new quickwin project it works fine.

There is a difference in the linker command line - one is /subsystem:windows the other is /subsystem:console - I think this may be where the problem lies...

I've just gone back to my original example - swapped both the runtime library and the subsystem settings and it works ....

Thanks for your support - I do hope your bosses realise how much we value it.

Cheers

Jim




0 Kudos
mecej4
Honored Contributor III
4,537 Views
In a command window (CMD.EXE), you can select Properties/Defaults and choose foreground and background color, font and font size. Is that not good enough?

There are third party screen drivers that support ANSI escape sequences, too.
0 Kudos
jim_cox
Beginner
4,537 Views
Yes you can change the cmd window - But the settings dont "stick"

And ansi escapes only work if you have the ansi driver installed - and are obnoxious if you dont...
0 Kudos
mecej4
Honored Contributor III
4,537 Views
> But the settings dont "stick"

There are two ways to make them stick. I usually have to set these options only after a fresh install of Windows.

(i) If you change them through Properties, when you click OK after changing, you will be offered a choice to apply the changes to the shortcut (sticky) or just for the current session.

(ii) If you change them through Defaults, the changes will be in effect the next time that you run the shortcut.

In Windows-7, you may have to open a CMD window with Administrator privileges before changing the settings in order to make the changes stick.
0 Kudos
Steven_L_Intel1
Employee
4,537 Views
Right - this is why I said "create a new project" and not just change the library settings. Indeed, as you found, there is also the linker's "Subsystem" option to change.

Glad to hear you have it working.
0 Kudos
joerg_kuthe
Novice
4,537 Views

Maybe the Fortran library qtConsole offers a solution.

Joerg Kuthe
www.qtsoftware.com

0 Kudos
SergeyKostrov
Valued Contributor II
4,537 Views
Quoting jim.cox
...Is it possible to set the font, the foregound and the background colours of a Console window?..

There is a set of Win32 API functions to do most of the tasks you want. Please take a look attopics 'Console Functions' and
'Console Screen Buffers' on MSDN.

Best regards,
Sergey
0 Kudos
anthonyrichards
New Contributor III
4,537 Views
To change text and background colours, see SetConsoleTextAttribute, but you must use WriteConsole, ReadConsole, writeFile, ReadFile to interact with the console for that to work.

Or, if you feel adventurous, you can try the undocumented, but extant API functions described here:

http://blogs.microsoft.co.il/blogs/pavely/archive/2009/07/23/changing-console-fonts.aspx
0 Kudos
Gabriel_Toro
Beginner
4,537 Views
Steve,

I believeyou sent mescreenio.lib and oldnames.lib many years ago. If they work with Intel Fortran and Windows 7, they may be useful in this case.

Thanks,

Gabriel
0 Kudos
Steven_L_Intel1
Employee
4,537 Views
Sorry, I don't have screenio.lib. oldnames.lib is provided by the Visual C++ libraries.
0 Kudos
marshall-l-buhl
Beginner
4,537 Views

Steve,

We are also considering porting our programs to QuickWin.  The kids these days seem lost when it comes to the console.  We also need to be compatible with gfortran on Windows and Linux because some people just like to cause me grief.  ;-)  I was hoping we could fairly easily wrap QuickWin around our console apps.  We already segregate all system-specific code in files for each system/compiler.  No system-specific code goes in the main files.  We don't even write to the screen except in the system files.  We use the same system files for all our programs.

One reason for going to QuickWin is that we would like to know the size of the console so we know where to wrap messages.  Apparently, it is not possible to find the width of a cmd.exe console from within a program, but it is with QuickWin windows.  Colors would be nice too.

One concern I have is performance, which is of paramount importance.  We can afford to lose 10% or so and hope for faster computers next year, but a factor of two or more would be problematic for our simulations.

Any advice would be greatly appreciated.

Marshall

0 Kudos
Steven_L_Intel1
Employee
4,537 Views

I am not aware that using QuickWin impacts performance.  The only possible issue there is if your program outputs LOTS of text - rendering the text to the window is more compute-intensive than in a console window.

0 Kudos
JVanB
Valued Contributor II
4,282 Views

If you want this to work in gfortran, avoid quickwin.
I tested this in gfortran:
[fortran]module console_stuff
   use ISO_C_BINDING
   implicit none
   private
   integer, parameter, public :: BOOL = C_INT
   integer, parameter, public :: HANDLE = C_INTPTR_T
   integer, parameter, public :: ULONG = C_LONG
   integer, parameter, public :: SHORT = C_SHORT
   integer, parameter, public :: WORD = C_SHORT
   integer, parameter, public :: DWORD = C_LONG
   integer, parameter, public :: COLORREF = DWORD
   integer(DWORD), parameter, public :: STD_OUTPUT_HANDLE = -11
   integer(WORD), parameter, public :: FOREGROUND_BLUE = int(Z"1",WORD)
   integer(WORD), parameter, public :: FOREGROUND_GREEN = int(Z"2",WORD)
   integer(WORD), parameter, public :: FOREGROUND_RED = int(Z"4",WORD)
   integer(WORD), parameter, public :: FOREGROUND_INTENSITY = int(Z"8",WORD)
   integer(WORD), parameter, public :: BACKGROUND_BLUE = int(Z"10",WORD)
   integer(WORD), parameter, public :: BACKGROUND_GREEN = int(Z"20",WORD)
   integer(WORD), parameter, public :: BACKGROUND_RED = int(Z"40",WORD)
   integer(WORD), parameter, public :: BACKGROUND_INTENSITY = int(Z"80",WORD)
   integer(WORD), parameter, public :: COMMON_LVB_LEADING_BYTE = int(Z"100",WORD)
   integer(WORD), parameter, public :: COMMON_LVB_TRAILING_BYTE = int(Z"200",WORD)
   integer(WORD), parameter, public :: COMMON_LVB_GRID_HORIZONTAL = int(Z"400",WORD)
   integer(WORD), parameter, public :: COMMON_LVB_GRID_LVERTICAL = int(Z"800",WORD)
   integer(WORD), parameter, public :: COMMON_LVB_GRID_RVERTICAL = int(Z"1000",WORD)
   integer(WORD), parameter, public :: COMMON_LVB_REVERSE_VIDEO = int(Z"4000",WORD)
   integer(WORD), parameter, public :: COMMON_LVB_UNDERSCORE = int(Z"8000",WORD)
   type, bind(C), public :: T_COORD
      integer(SHORT) x
      integer(SHORT) y
   end type T_COORD
   type, bind(C), public :: T_SMALL_RECT
      integer(SHORT) Left
      integer(SHORT) Top
      integer(SHORT) Right
      integer(SHORT) Bottom
   end type T_SMALL_RECT
   type, bind(C), public :: T_CONSOLE_SCREEN_BUFFER_INFO
      type(T_COORD) dwSize
      type(T_COORD) dwCursorPosition
      integer(WORD) wAttributes
      type(T_SMALL_RECT) srWindow
      type(T_COORD) dwMaximumWindowSize
   end type T_CONSOLE_SCREEN_BUFFER_INFO
   public GetConsoleScreenBufferInfo
   interface
      function GetConsoleScreenBufferInfo(hConsoleOutput, &
         lpConsoleScreenBufferInfo) bind(C,name='GetConsoleScreenBufferInfo')
         import
         implicit none
!gcc$ attributes stdcall :: GetConsoleScreenBufferInfo
         integer(BOOL) GetConsoleScreenBufferInfo
         integer(HANDLE), value :: hConsoleOutput
         type(T_CONSOLE_SCREEN_BUFFER_INFO) lpConsoleScreenBufferInfo
      end function GetConsoleScreenBufferInfo
   end interface
   public GetLastError
   interface
      function GetLastError() bind(C,name='GetLastError')
         import
         implicit none
!gcc$ attributes stdcall :: GetLastError
         integer(HANDLE) GetLastError
      end function GetLastError
   end interface
   public SetConsoleTextAttribute
   interface
      function SetConsoleTextAttribute(hConsoleOutput, wAttributes) &
         bind(C,name='SetConsoleTextAttribute')
         import
         implicit none
!gcc$ attributes stdcall :: SetConsoleTextAttribute
         integer(BOOL) SetConsoleTextAttribute
         integer(HANDLE), value :: hConsoleOutput
         integer(WORD), value :: wAttributes
      end function SetConsoleTextAttribute
   end interface
   public GetStdHandle
   interface
      function GetStdHandle(nStdHandle) bind(C,name='GetStdHandle')
         import
         implicit none
!gcc$ attributes stdcall :: GetStdHandle
         integer(HANDLE) GetStdHandle
         integer(DWORD), value :: nStdHandle
      end function GetStdHandle
   end interface
end module console_stuff

program main
   use console_stuff
   implicit none
   type(T_CONSOLE_SCREEN_BUFFER_INFO) lpConsoleScreenBufferInfo
   integer(BOOL) result4
   integer(HANDLE) hConsoleOutput
   integer(WORD) wAttributes

   hConsoleOutput = GetSTdHandle(STD_OUTPUT_HANDLE)
   result4 = GetConsoleScreenBufferInfo(hConsoleOutput,lpConsoleScreenBufferInfo)
   write(*,'("Buffer width = ",i0,", Buffer Height = ",i0)') &
      lpConsoleScreenBufferInfo%dwSize
   wAttributes = iany([FOREGROUND_RED,FOREGROUND_INTENSITY,BACKGROUND_BLUE])
   result4 = SetConsoleTextAttribute(hConsoleOutput,wAttributes)
   write(*,'(a)') 'Hello, world'
   result4 = SetConsoleTextAttribute(hConsoleOutput,lpConsoleScreenBufferInfo%wAttributes)
end program main[/fortran]

0 Kudos
Reply