forums.silverfrost.com Forum Index forums.silverfrost.com
Welcome to the Silverfrost forums
 
 FAQFAQ   SearchSearch   MemberlistMemberlist   UsergroupsUsergroups   RegisterRegister 
 ProfileProfile   Log in to check your private messagesLog in to check your private messages   Log inLog in 

2D array in the Clearwin multiple selection

 
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> ClearWin+
View previous topic :: View next topic  
Author Message
DanRRight



Joined: 10 Mar 2008
Posts: 2815
Location: South Pole, Antarctica

PostPosted: Fri Apr 06, 2012 5:55 pm    Post subject: 2D array in the Clearwin multiple selection Reply with quote

As an example, suppose we are trying to write the code called "periodic table" where we will select configurations (one or many)for specific ion and somehow further process it. For example first 4 elements from Hydrogen to Beryllium have these well known configurations

config(1,1)='1s1'

config(1,2)='1s1'
config(2,2)='1s2'

config(1,3)='1s1'
config(2,3)='1s2'
config(3,3)='1s2_2s1'

config(1,4)='1s1'
config(2,4)='1s2'
config(3,4)='1s2_2s1'
config(4,4)='1s2_2s2'

It is possible to write short DO loop which will create many similar Clearwin controls for all elements of periodic table where we will be able to chose specific configurations of specific atom? It is obviously simpler to set the data for all atoms and then write just one single DO loop instead of painfully fill many lines manually.

Problem is that my several attempts of creating such loops (as below) failed. (Here i created just first 10 controls for the first 50 instead of 106 elements of periodic table)

do i=1,10
j=winio@(' Element %ta%ws%ta%8.2^ms%sf%ff&', element(i), config(:,i),intl(50), iz_Selected(:,i),cb_processRequest)
enddo

The one-dimensional arrays where i just substituted 2D arrays with 1D arrays config--> config0 and iz_Selected --> iz_Selected0 are working OK. Here is the compilable demo code where first control in the picture shows how all should work (but how it should not be written for the whole set of 106 elements) with all others controls made by do loop which does not work (but how the code should in principle be written). Is there a way to get through this with some kind of derived type setup instead of 2D array to fool Clearwin ? Or i just have done something wrong somewhere?




Code:
 
  integer  cb_processRequest
  external cb_processRequest
  character*2 element(106)
  data element/&
  &'h ',                                                                                'he',&
  &'li','be',                                                  'b ','c ','n ','o ','f ','ne',&
  &'na','mg',                                                  'al','si','p ','s ','cl','ar',&
  &'k ','ca','sc','ti','v ','cr','mn','fe','co','ni','cu','zn','ga','ge','as','se','br','kr',&
  &'rb','sr','y ','zr','nb','mo','tc','ru','rh','pd','ag','cd','in','sn','sb','te','i ','xe',&
  &'cs','ba','la','ce','pr','nd','pm','sm','eu','gd','tb','dy','ho','er','tm',&
  &     'yb','lu','hf','ta','w ','re','os','ir','pt','au','hg','tl','pb','bi','po','at','rn',&
  &'fr','ra','ac','th','pa','u ','np','pu','am','cm','bk','cf','es','fm','md','no','lw','rf','ha','??'/

  character*32 config(50,106)
  integer      iz_Selected(50,106)
  character*32 config0(50)
  integer      iz_Selected0(50)


     
  config(1,1)='1s1'

  config(1,2)='1s1'
  config(2,2)='1s2'

  config(1,3)='1s1'
  config(2,3)='1s2'
  config(3,3)='1s2_2s1'

  config(1,4)='1s1'
  config(2,4)='1s2'
  config(3,4)='1s2_2s1'
  config(4,4)='1s2_2s2'

  config0(:)=config(:,4)
  iz_Selected(:,:) = 0
  iz_Selected0(:) = 0

! On beryllium as an example of using 1D array
  i=4
  j=winio@(' Element %ta%ws%ta%8.2^ms%ff %ff&', element(i), config0,intl(50), iz_Selected0, cb_processRequest)

! Use 2D array - this is how i'd like it to look like
  do i=1,10
  j=winio@(' Element %ta%ws%ta%8.2^ms%sf%ff&', element(i), config(:,i),intl(50), iz_Selected(:,i),cb_processRequest)
  enddo

  j=winio@('%ac[Esc]&','exit')
  j=winio@('%cn%bt[Exit]')

  end

  integer function cb_processRequest()
  cb_processRequest=1
  end function      
'
Back to top
View user's profile Send private message
DanRRight



Joined: 10 Mar 2008
Posts: 2815
Location: South Pole, Antarctica

PostPosted: Sat Apr 07, 2012 2:18 pm    Post subject: Reply with quote

Well, i'm kind of succeeded myself with derived types but the programming with derived types looks even more twisted and even less pretty.

Any suggestions about using good old arrays like in my example which does not work?

Here is my derived type mess for interested with the exact functionality needed

Code:

! compilation of the file elem.f95
! FTN95 elem /link

  module dertypes

  type elementType
    character*10 configArrayDrvd(106)
  end type
  type SelectType
    integer SelectionForElementDrvd(106)
  end type

  type(elementType) elementDrvd(106)
  type(selectType)  selectDrvd(106)

  contains

  integer function cb_processRequest()
  do i=1,106
   do j=1,106
    if(selectDrvd(i)%SelectionForElementDrvd(j).ne.0) print*,selectDrvd(i)%SelectionForElementDrvd(j), i,j
   enddo   
  enddo   
  cb_processRequest=1
  end function      

  end module dertypes

  program MultipleSelectionsWithArrays
  use dertypes

  character*2 element(106)
  data element/&
  &'H ',                                                                                'He',&
  &'Li','Be',                                                  'B ','C ','N ','O ','F ','Ne',&
  &'Na','Mg',                                                  'Al','Si','P ','S ','Cl','Ar',&
  &'K ','Ca','Sc','Ti','V ','Cr','Mn','Fe','Co','Ni','Cu','Zn','Ga','Ge','As','Se','Br','Kr',&
  &'Rb','Sr','Y ','Zr','Nb','Mo','Tc','Ru','Rh','Pd','Ag','Cd','In','Sn','Sb','Te','I ','Xe',&
  &'Cs','Ba','La','Ce','Pr','Nd','Pm','Sm','Eu','Gd','Tb','Dy','Ho','Er','Tm',&
  &     'Yb','Lu','Hf','Ta','W ','Re','Os','Ir','Pt','Au','Hg','Tl','Pb','Bi','Po','At','Rn',&
  &'Fr','Ra','Ac','Th','Pa','U ','Np','Pu','Am','Cm','Bk','Cf','Es','Fm','Md','No','Lw','Rf','Ha','??'/

  elementDrvd(:) = elementType(' ') ! zeroizing
  selectDrvd(:)  = SelectType(0)

  elementDrvd(1)%configArrayDrvd(1) = '1s1' ! elementType('1s1')

  elementDrvd(2)%configArrayDrvd(1)= '1s1'
  elementDrvd(2)%configArrayDrvd(2)= '1s2'

  elementDrvd(3)%configArrayDrvd(1)= '1s1'
  elementDrvd(3)%configArrayDrvd(2)= '1s2'
  elementDrvd(3)%configArrayDrvd(3)= '2s1'

  elementDrvd(4)%configArrayDrvd(1)= '1s1'
  elementDrvd(4)%configArrayDrvd(2)= '1s2'
  elementDrvd(4)%configArrayDrvd(3)= '2s1'
  elementDrvd(4)%configArrayDrvd(4)= '2s2'

  do i=1,10
  j=winio@(' Element%ta%ws%ta%8.2^ms%sf%ff&',element(i),elementDrvd(i)%configArrayDrvd,&
  & intl(106),selectDrvd(i)%SelectionForElementDrvd,cb_processRequest)
  enddo

  j=winio@('%ac[Esc]&','exit')
  j=winio@('%cn%bt[Exit]')

  end

%configArrayDrvd
Back to top
View user's profile Send private message
JohnCampbell



Joined: 16 Feb 2006
Posts: 2554
Location: Sydney

PostPosted: Sun Apr 08, 2012 3:00 am    Post subject: Reply with quote

Dan,

could you do it with a list of %rb radio buttons.
You may also need a vertical scroll on the selection display.

My quick attempt to set up a mapping to a 1 dimensional array and display different radio buttons for each new element, could work something like:
Code:
integer select_list(1000,3)
!
!  generate selection list, indicating if new elements
n = 0
do iel = 1,106
  do k = 1,50 
     if (elementDrvd(iel)%configArrayDrvd(k) == ' ') cycle
     n = n+1
     select_list(n,1) = 1      ! selected   used for radio button
     select_list(n,2) = iel    ! element name pointer
     select_list(n,3) = k      !
   end do
end do

do i=1,n
!
   if (select_list(i,3) == 1) then    !  new element
      iel = select_list(i,2)
      k   = select_list(i,3)
      j=winio@('%ff%nl Element %ta%ws %ta%^rb%ta%ws&', element(iel), select_list(i,1), elementDrvd(iel)%configArrayDrvd(k), cb_processRequest)
   else
      k   = select_list(i,3)
      j=winio@('%ff %3ta %ta%^rb%ta%ws&',                       , select_list(i,1), elementDrvd(iel)%configArrayDrvd(k), cb_processRequest)
   end if
end do


I presume that cb_processRequest could retreive which button was selected, then identified which button from 1:n and then which element iel,k

My idea is controling the display of each button may be better than a multiple selection list.

Alternatively you could format the %ms multiple selection drop down list as character array that describes each element option from 1:n. This would not have the description of each selection like the formatted %rb list.
Hope this is not a useless idea.

John
Back to top
View user's profile Send private message
DanRRight



Joined: 10 Mar 2008
Posts: 2815
Location: South Pole, Antarctica

PostPosted: Sun Apr 08, 2012 3:05 pm    Post subject: Reply with quote

Good suggestion and interesting trickery with its implementation ! Made me think and try and inspired other things. Thanks, John
Back to top
View user's profile Send private message
DanRRight



Joined: 10 Mar 2008
Posts: 2815
Location: South Pole, Antarctica

PostPosted: Fri Apr 13, 2012 12:02 pm    Post subject: Reply with quote

Well, as it always happen after implementing the solution with the radiobuttons popping out in separate window (because it was hard to place all of them on one main window without scrolling which before did not work well) i found the solution for the initial problem. The fun is that it's an obvious standard Fortran77

Code:

  integer  cb_processRequest
  external cb_processRequest
  character*2 element(106)
  data element/&
  &'H ',                                                                                'He',&
  &'Li','Be',                                                  'B ','C ','N ','O ','F ','Ne',&
  &'Na','Mg',                                                  'Al','Si','P ','S ','Cl','Ar',&
  &'K ','Ca','Sc','Ti','V ','Cr','Mn','Fe','Co','Ni','Cu','Zn','Ga','Ge','As','Se','Br','Kr',&
  &'Rb','Sr','Y ','Zr','Nb','Mo','Tc','Ru','Rh','Pd','Ag','Cd','In','Sn','Sb','Te','I ','Xe',&
  &'Cs','ba','la','ce','pr','nd','pm','sm','eu','gd','tb','dy','ho','er','tm',&
  &     'yb','lu','hf','ta','w ','re','os','ir','pt','au','hg','tl','pb','bi','po','at','Rn',&
  &'Fr','ra','ac','th','pa','u ','np','pu','am','cm','bk','cf','es','fm','md','no','lw','rf','ha','??'/

  character*32 configs2D(106,106)     ! Array(conf, iz)
  integer      iz_Selected2D(106,106) ! Array(conf, iz)
  character*32 configs1D(106)         ! Array(conf)
  integer      iz_Selected1D(106)     ! Array(conf)


     
  configs2D(1,1)='1s1'

  configs2D(1,2)='1s1'
  configs2D(2,2)='1s2'

  configs2D(1,3)='1s1'
  configs2D(2,3)='1s2'
  configs2D(3,3)='1s2_2s1'

  configs2D(1,4)='1s1'
  configs2D(2,4)='1s2'
  configs2D(3,4)='1s2_2s1'
  configs2D(4,4)='1s2_2s2'

  configs1D(:)=configs2D(:,4)
  iz_Selected2D(:,:) = 0
  iz_Selected1D(:) = 0

! On beryllium as an example 1D arrays work fine
  i=4
  j=winio@(' Element %ta%ws%ta%8.2^ms%ff %ff&', element(i), configs1D,intl(50), iz_Selected1D, cb_processRequest)

  do i=1,10
! Using 2D array like this does not work
!  j=winio@(' Element %ta%ws%ta%8.2^ms%sf%ff&', element(i), config(:,i),intl(106), iz_Selected(:,i),cb_processRequest)
!  and this way it works fine
   call FoolingClearwin (configs2D(1,i), iz_Selected2D(1,i), element(i))
  enddo

  j=winio@('%ac[Esc]&','exit')
  j=winio@('%cn%bt[Exit]')

  end

  integer function cb_processRequest()
  cb_processRequest=1
  end function      

  subroutine FoolingClearwin (Configs1Dsub, iz_Selected1Dsub, elementSub)
  integer  cb_processRequest
  external cb_processRequest
  character*32 Configs1Dsub(106)
  character*2 elementSub
  j=winio@(' Element %ta%ws%ta%8.2^ms%sf%ff&', elementSub, Configs1Dsub,intl(106), iz_Selected1Dsub,cb_processRequest)
  end subroutine


But seems the radiobutton solution is very practical too. Here it is how it looks now - you click on small icon and it shows existing configurations and allows then to be chosen

Back to top
View user's profile Send private message
Display posts from previous:   
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> ClearWin+ All times are GMT + 1 Hour
Page 1 of 1

 
Jump to:  
You cannot post new topics in this forum
You cannot reply to topics in this forum
You cannot edit your posts in this forum
You cannot delete your posts in this forum
You cannot vote in polls in this forum


Powered by phpBB © 2001, 2005 phpBB Group