MVSFORUMS.com Forum Index MVSFORUMS.com
A Community of and for MVS Professionals
 
 FAQFAQ   SearchSearch   Quick Manuals   RegisterRegister 
 ProfileProfile   Log in to check your private messagesLog in to check your private messages   Log inLog in 

Problem running LM functions in Batch

 
Post new topic   Reply to topic   printer-friendly view    MVSFORUMS.com Forum Index -> TSO and ISPF
View previous topic :: View next topic  
Author Message
misfit
Beginner


Joined: 01 May 2003
Posts: 26
Topics: 9
Location: India

PostPosted: Thu Jul 22, 2004 11:09 am    Post subject: Problem running LM functions in Batch Reply with quote

Hi, <<<I by mistake posted it in JCL, posting here again >>>
I have following code which works fine when executed online under TSO.
Please note, the DSNAME is passed properly before this code and there is no error there.
Code:
ADDRESS ISPEXEC                                 
"LMINIT DATAID(dsnm) DATASET(&DSNAME) "         
                                                 
"LMOPEN DATAID(&dsnm) OPTION(INPUT) "           
                                                 
mem = 'aaa'                                 
"LMMFIND DATAID(&dsnm) MEMBER(&mem) STATS(YES) " 

Now when i run my exec in batch it gives me -3 or 20 return code. I specified ADDRESS TSO on top of ADDRESS ISPEXEC but no fruits.
If i give the following, it still doesnt work
Code:

"ISPEXEC LMINIT DATAID(dsnm) DATASET(&DSNAME) "         
"ISPEXEC LMOPEN DATAID(&dsnm) OPTION(INPUT) "           
mem = 'LISTDOCO'                                       
"ISPEXEC LMMFIND DATAID(&dsnm) MEMBER(&mem) STATS(YES) "
Can someone show me the way ..

_________________
<i><b> Don't wish it were easier. Wish you were better. </b></i>
Back to top
View user's profile Send private message
kolusu
Site Admin
Site Admin


Joined: 26 Nov 2002
Posts: 12372
Topics: 75
Location: San Jose

PostPosted: Thu Jul 22, 2004 11:57 am    Post subject: Reply with quote

Misfit,

You need to run ISPF (via an ISPSTART command). You also need all the ISPF libraries.

Check this link which explains JCL to run ISPF in Batch


http://www.sillysot.com/mvs/batchpdf.htm

Hope this helps...

Cheers

Kolusu
_________________
Kolusu
www.linkedin.com/in/kolusu
Back to top
View user's profile Send private message Send e-mail Visit poster's website
misfit
Beginner


Joined: 01 May 2003
Posts: 26
Topics: 9
Location: India

PostPosted: Thu Jul 22, 2004 12:13 pm    Post subject: Reply with quote

Thanks Kolusu,
but the link is in 'Loading' status ever since Sad

Can you please suggest me any other source ..
_________________
<i><b> Don't wish it were easier. Wish you were better. </b></i>
Back to top
View user's profile Send private message
kolusu
Site Admin
Site Admin


Joined: 26 Nov 2002
Posts: 12372
Topics: 75
Location: San Jose

PostPosted: Thu Jul 22, 2004 12:19 pm    Post subject: Reply with quote

Misfit,

Find BATCHPDF in this page

http://www.sillysot.com/mvs/

Kolusu
_________________
Kolusu
www.linkedin.com/in/kolusu
Back to top
View user's profile Send private message Send e-mail Visit poster's website
misfit
Beginner


Joined: 01 May 2003
Posts: 26
Topics: 9
Location: India

PostPosted: Thu Jul 22, 2004 12:43 pm    Post subject: Reply with quote

I don't know what is the problem, but that is not working either.

Can you please post the information here or send me the same through mail at altruist_m@yahoo.com
_________________
<i><b> Don't wish it were easier. Wish you were better. </b></i>
Back to top
View user's profile Send private message
kolusu
Site Admin
Site Admin


Joined: 26 Nov 2002
Posts: 12372
Topics: 75
Location: San Jose

PostPosted: Thu Jul 22, 2004 1:13 pm    Post subject: Reply with quote

Misfit,

I am pasting the contents of the page here.


BATCHPDF: Create JCL to run ISPF in Batch

Need to run ISPF services or Edit in batch but don't know how to set up the JCL? Let the BATCHPDF edit macro do it for you. It uses the allocations you already have in your TSO session as a model for the JCL so that you don't need to know where all of the ISPF libraries are on your system.

BATCHPDF is available as sourcecode.


Function
Create JCL to run ISPF in batch using your TSO allocations as a model.

Calling Syntax from within an ISPF edit session:
BATCHPDF

The contents of the data in your edit session are replaced with the JCL. Modify the jobcard, and other items as need, add your ISPF code or a call to it and you should be done.

Installation
Place batchpdf.txt in a library allocated to SYSEXEC or SYSPROC and call the member BATCHPDF (actually any member name will do).
Output

Sample output of the BatchPDF macro
Code:

//DNADELI JOB (ACCT),NOTIFY=DNADEL,MSGLEVEL=(1,1)                       
//*-------------------------------------------------------------------*
//*                       Create Startup CLIST                        *
//*-------------------------------------------------------------------*
//GENER0   EXEC PGM=IEBGENER
//SYSUT1   DD *
 
 ISPEXEC VGET (ZTIMEL)       /* ISPF services can run here */
 WRITE &ZTIMEL
 
 /* Add any setup here                                       */
 /* And start your program here.  Use ISPEXEC SELECT.        */
 /*                                                          */
 /* To invoke the editor, code a line like:                  */
 /*   ISPEXEC EDIT DATASET('FRED.CNTL(BUBBA)') MACRO(BINKY)  */
 /* and remember that the macro must do an END or CANCEL.    */
 
 
 /* You can set the step return code if you want.            */
 SET ZISPFRC = 0
 ISPEXEC VPUT (ZISPFRC) SHARED     /* set step return code */
 
//SYSUT2   DD DISP=(NEW,PASS),DSN=&&CLIST0(TEMPNAME),
//            SPACE=(TRK,(1,1,2),RLSE),UNIT=SYSALLDA,
//            DCB=(LRECL=80,BLKSIZE=0,DSORG=PO,RECFM=FB)
//PROFILE  DD DISP=(NEW,CATLG),DSN=DNADEL.T166657.ISPPROF,
//            SPACE=(TRK,(10,10,5)),UNIT=SYSALLDA,
//            DCB=(LRECL=80,BLKSIZE=0,DSORG=PO,RECFM=FB)
//SYSPRINT DD DUMMY
//SYSIN    DD DUMMY
//*-------------------------------------------------------------------*
//*              Initialize profile data set (optional)               *
//*-------------------------------------------------------------------*
//* COPY     EXEC PGM=IEBCOPY
//* SYSPRINT DD  DUMMY
//* SYSIN    DD  DUMMY
//* SYSUT1   DD  DISP=SHR,DSN=DNADEL.OS390R5.ISPPROF
//* SYSUT2   DD  DISP=(OLD,PASS),DSN=*.GENER0.PROFILE
//*-------------------------------------------------------------------*
//*                            Invoke ISPF                            *
//*-------------------------------------------------------------------*
//BATCHPDF EXEC PGM=IKJEFT01,DYNAMNBR=128
//STEPLIB  DD DISP=SHR,DSN=ISPFLPA.OS390R5.SISPLPA             SPF603
//         DD DISP=SHR,DSN=ISPFLNK.OS390R5.SISPLOAD            SPF603
//         DD DISP=SHR,DSN=ISPF.OS390R5.SISPSASC               SPF603
//         DD DISP=SHR,DSN=DNADEL.TASID.LOAD                   SPF601
//ISPPLIB  DD DISP=SHR,DSN=ISPF.OS390R5.SISPPENU               SPF603
//ISPSLIB  DD DISP=SHR,DSN=ISPF.OS390R5.SISPSENU               SPF603
//         DD DISP=SHR,DSN=ISPF.OS390R5.SISPSLIB               SPF603
//ISPMLIB  DD DISP=SHR,DSN=ISPF.OS390R5.SISPMENU               SPF603
//ISPILIB  DD DISP=SHR,DSN=ISPF.OS390R5.SISPSAMP               SPF603
//ISPPROF  DD DISP=(OLD,PASS),DSN=DNADEL.T166657.ISPPROF
//ISPTABL  DD DISP=(OLD,PASS),DSN=DNADEL.T166657.ISPPROF
//ISPTLIB  DD DISP=(OLD,PASS),DSN=DNADEL.T166657.ISPPROF
//         DD DISP=SHR,DSN=DNADEL.OS390R5.ISPPROF              SPF605
//         DD DISP=SHR,DSN=ISPF.OS390R5.SISPTENU               SPF603
//ISPCTL0  DD DISP=(NEW,DELETE),SPACE=(TRK,(10,10)),UNIT=VIO,
//            DCB=(LRECL=80,BLKSIZE=0,DSORG=PS,RECFM=FB)
//ISPCTL1  DD DISP=(NEW,DELETE),SPACE=(TRK,(10,10)),UNIT=VIO,
//            DCB=(LRECL=80,BLKSIZE=0,DSORG=PS,RECFM=FB)
//ISPWRK1  DD DISP=(NEW,DELETE),SPACE=(TRK,(10,10)),UNIT=VIO,
//            DCB=(LRECL=80,BLKSIZE=0,DSORG=PS,RECFM=FB)
//ISPLST1  DD DISP=(NEW,DELETE),SPACE=(TRK,(10,10)),
//            DCB=(LRECL=133,BLKSIZE=0,DSORG=PS,RECFM=VB)
//ISPLOG   DD SYSOUT=*,
//            DCB=(LRECL=120,BLKSIZE=2400,DSORG=PS,RECFM=FB)
//ISPLIST  DD SYSOUT=*,DCB=(LRECL=121,BLKSIZE=1210,RECFM=FBA)
//* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
//SYSTSPRT DD SYSOUT=*
//SYSTSIN  DD *
 PROFILE PREFIX(DNADEL)
 ISPSTART CMD(%TEMPNAME) NEWAPPL(ISR)
//SYSEXEC  DD DISP=SHR,DSN=ISPF.OS390R5.SISPEXEC               SPF603
//         DD DISP=SHR,DSN=ISPF.OS390R5.SISPSAMP               SPF603
//         DD DISP=SHR,DSN=SYS1.SBPXEXEC                       O9B2P1
//         DD DISP=SHR,DSN=FAN.V1R3M0.SFANCMD                  F1P01P
//         DD DISP=SHR,DSN=EAG.V1R1M0.EAGCMD                   F1P01P
//         DD DISP=SHR,DSN=DGI.V1R4M0.SDGICMD                  C1P02P   
//SYSPROC  DD DSN=&&CLIST0,DISP=(OLD,DELETE)                           
//         DD DISP=SHR,DSN=DNADEL.CLIST.FB                     SPF602
//         DD DISP=SHR,DSN=ISPF.OS390R5.SISPCLIB               SPF603
//*-------------------------------------------------------------------*
//*                 Delete temporary profile data set                 *
//*-------------------------------------------------------------------*
//DELPROF  EXEC PGM=IEFBR14
//DELETEDD DD DSN=DNADEL.T166657.ISPPROF,DISP=(OLD,DELETE)



Batchpdf edit macro
Code:

/* REXX - Generate JCL to run ISPF in batch using the current        */
/*        TSO session allocations.                                   */
/*                                                                   */
/*        This is an ISPF edit macro.                                */
/*                                                                   */
/*     Usage:  Place this in your REXX or CLIST library as           */
/*             Member BATCHPDF.                                      */
/*             Edit any edit session and enter BATCHPDF.             */
/*             The edit session should then contain working JCL for  */
/*             using ISPF in batch.  Change the job card as          */
/*             needed and add or remove ddnames and data sets as     */
/*             needed.                                               */
/*                                                                   */
/*                                                                   */
/*     Author: Doug Nadel  http://www.sillysot.com/mvs               */
/*                                                                   */
/*             I'd like to thank Gilbert Saint-Flour for the SWAREQ  */
/*             subroutine. http://members.home.net/gsf/              */
/*                                                                   */
/*     Notes:  The JCL generated creates a cataloged data set for    */
/*             Use as an ISPF profile and tables data set.  This     */
/*             data set is used for ISPPROF, ISPTABL and ISPTABL.    */
/*             You can add an iebcopy step before the ikjeft01       */
/*             step if you need to copy an existing profile onto     */
/*             that data set.  That data set is automatically        */
/*             deleted in the end change the 'tempdsn' name if       */
/*             needed.                                               */
/*                                                                   */
/*             If you have a member called jobcard in the pds you    */
/*             are editing when you run this, it will be copied in   */
/*             to the JCL automatically.  Otherwise a default        */
/*             job card will be inserted.                            */
/*                                                                   */
/*             The JCL generated also uses a temporary CLIST.        */
/*             Place invocation of your program there.               */
/*                                                                   */
/*     Version History: 1.00 Feb 10, 2000  - initial release         */
/*     Version History: 1.01 Feb 11, 2000  - profile init step       */
/*                                         - minor reformatting      */
/*-------------------------------------------------------------------*/
Address isredit
'MACRO'
If sysvar(syspref) <> '' Then
  If sysvar(syspref) <> userid() Then
    prefix=sysvar(syspref)'.'userid()
  Else
    prefix=sysvar(syspref)
Else
  prefix=userid()
Do Until sysdsn("'"tempdsn"'") <> 'OK' /* set up temp ds name        */
  tempdsn=prefix'.T'substr(reverse(time('L')),1,6)'.ISPPROF'
End
'X ALL .ZL .ZF'                        /* exclude all                */
'DEL ALL X'                            /* and now delete everything  */
'CAPS OFF'                             /* insure lower case is
                                          allowed                    */
lineno=0
ddnames='ISPLLIB ISPPLIB ISPSLIB ISPMLIB ISPILIB'
Call listdsi 'SYSPROC FILE'
Address ispexec 'CONTROL ERRORS RETURN'
'COPY JOBCARD AFTER 0'
copyrc=rc
Address ispexec 'CONTROL ERRORS CANCEL'
'CAPS OFF'                             /* in case copy changed caps  */
If copyrc>0 Then
  Call add '//'userid()'I JOB (ACCT),NOTIFY='userid()',MSGLEVEL=(1,1)'
'(LINENO) = linenum .zl'               /* Start adding at top        */
/*-------------------------------------------------------------------*/
Call comment 'Create Startup CLIST'
Call add '//GENER0   EXEC PGM=IEBGENER                              '
Call add '//SYSUT1   DD *                                          '
Call add '                          '
Call add ' ISPEXEC VGET (ZTIMEL)       /* ISPF services can run here */'
Call add ' WRITE &ZTIMEL            '
Call add ' '
Call scomment 'Add any setup here'
Call scomment 'And start your program here.  Use ISPEXEC SELECT.'
Call scomment ' '
Call scomment 'To invoke the editor, code a line like:'
Call scomment "  ISPEXEC EDIT DATASET('FRED.CNTL(BUBBA)') MACRO(BINKY)"
Call scomment 'and remember that the macro must do an END or CANCEL.'
Call add ' '
Call add ' '
Call scomment 'You can set the step return code if you want.'
Call add ' SET ZISPFRC = 0          '
Call add ' ISPEXEC VPUT (ZISPFRC) SHARED     /* set step return code */'
Call add ' '
Call add '//SYSUT2   DD DISP=(NEW,PASS),DSN=&&CLIST0(TEMPNAME),'
Call add '//            SPACE=(TRK,(1,1,2),RLSE),UNIT=SYSALLDA,    '
Call add '//            DCB=(LRECL='syslrecl',BLKSIZE=0,'||,
  'DSORG=PO,RECFM='sysrecfm')   '
Call add '//PROFILE  DD DISP=(NEW,CATLG),DSN='tempdsn','
Call add '//            SPACE=(TRK,(10,10,5)),UNIT=SYSALLDA,'
Call add '//            DCB=(LRECL=80,BLKSIZE=0,DSORG=PO,RECFM=FB) '
Call add '//SYSPRINT DD DUMMY                                      '
Call add '//SYSIN    DD DUMMY                                      '
/*-------------------------------------------------------------------*/
Call comment 'Initialize profile data set (optional)'
Call add '//* COPY     EXEC PGM=IEBCOPY                               '
Call add '//* SYSPRINT DD  DUMMY                                      '
Call add '//* SYSIN    DD  DUMMY                                      '
Call get_allocations 'ISPPROF '
Call add '//* SYSUT1   DD  DISP=SHR,DSN='dsname.1
Call add '//* SYSUT2   DD  DISP=(OLD,PASS),DSN=*.GENER0.PROFILE'
/*-------------------------------------------------------------------*/
Call comment 'Invoke ISPF'
Call add '//BATCHPDF EXEC PGM=IKJEFT01,DYNAMNBR=128                 '
Call insert 'STEPLIB ','STEPLIB '
Do dds=1 to words(ddnames)
  ddname=subword(ddnames,dds,1)
  Call insert ddname,ddname
End
Call add '//ISPPROF  DD DISP=(OLD,PASS),DSN='tempdsn
Call add '//ISPTABL  DD DISP=(OLD,PASS),DSN='tempdsn
Call add '//ISPTLIB  DD DISP=(OLD,PASS),DSN='tempdsn
Call insert 'ISPTLIB ',' '
Call add '//ISPCTL0  DD DISP=(NEW,DELETE),SPACE=(TRK,(10,10)),UNIT=VIO,'
Call add '//            DCB=(LRECL=80,BLKSIZE=0,DSORG=PS,RECFM=FB)  '
Call add '//ISPCTL1  DD DISP=(NEW,DELETE),SPACE=(TRK,(10,10)),UNIT=VIO,'
Call add '//            DCB=(LRECL=80,BLKSIZE=0,DSORG=PS,RECFM=FB)  '
Call add '//ISPWRK1  DD DISP=(NEW,DELETE),SPACE=(TRK,(10,10)),UNIT=VIO,'
Call add '//            DCB=(LRECL=80,BLKSIZE=0,DSORG=PS,RECFM=FB)  '
Call add '//ISPLST1  DD DISP=(NEW,DELETE),SPACE=(TRK,(10,10)),'
Call add '//            DCB=(LRECL=133,BLKSIZE=0,DSORG=PS,RECFM=VB)'
Call add '//ISPLOG   DD SYSOUT=*,'
Call add '//            DCB=(LRECL=120,BLKSIZE=2400,DSORG=PS,RECFM=FB)'
Call add '//ISPLIST  DD SYSOUT=*,DCB=(LRECL=121,BLKSIZE=1210,RECFM=FBA)'
Call add '//* 'copies('- ',32)
Call add '//SYSTSPRT DD SYSOUT=*'
Call add '//SYSTSIN  DD *'
If sysvar(syspref) <> '' Then
  Call add ' PROFILE PREFIX('sysvar(syspref)')'
Else
  Call add ' PROFILE NOPREFIX'
Call add ' ISPSTART CMD(%TEMPNAME) NEWAPPL(ISR)'
Call insert 'SYSEXEC ','SYSEXEC'
Call add '//SYSPROC  DD DSN=&&CLIST0,DISP=(OLD,DELETE)'
Call insert 'SYSPROC ',''
Call add '//*'copies('-',67)'*'
Call add '//*'center(' Delete temporary profile data set ',67)'*'
Call add '//*'copies('-',67)'*'
Call add '//DELPROF  EXEC PGM=IEFBR14         '
Call add '//DELETEDD DD DSN='tempdsn',DISP=(OLD,DELETE)'
'LOCATE .ZF'
Exit 1
/*------------------ Subroutines follow -----------------------------*/
/*-------------------------------------------------------------------*/
get_allocations:  Procedure Expose ddname. dsname. volume.
Numeric digits 10                      /* Allow up to 7fffffff       */
Drop ddname. dsname. volume.
tiotptr=24+ptr(12+ptr(ptr(ptr(16))))   /* Get ddname array           */
tioelngh=c2d(stg(tiotptr,1))           /* Nength of 1st entry        */
a=0
ddname=' '
Do Until tioelngh=0                    /* Scan until dd found        */
  tioeddnm=strip(stg(tiotptr+4,8))     /* Get ddname from tiot       */
  If substr(tioeddnm,1,1) <>'00'x Then
    Do
      If substr(tioeddnm,1,1) <>" " Then
        ddname=tioeddnm
      If ddname=Arg(1) Then
        Do
          a=a+1
          ddname.a=ddname
          tioelngh=c2d(stg(tiotptr,1)) /* Length of next entry       */
          tioejfcb=stg(tiotptr+12,3)
          jfcb=swareq(tioejfcb)        /* Convert sva to 31-Bit addr */
          dsname.a=strip(stg(jfcb,44)) /* Dsname jfcbdsnm            */
          volume.a=storage(d2x(jfcb+118),6)/* Volser jfcbvols (Not
                                          used)                      */
        End
    End
  tiotptr=tiotptr+tioelngh             /* Get next entry             */
  tioelngh=c2d(stg(tiotptr,1))         /* Get entry length           */
End
ddname.0=a
Return
/*-------------------------------------------------------------------*/
ptr:  Return c2d(storage(d2x(Arg(1)),4)) /* Return a pointer         */
/*-------------------------------------------------------------------*/
stg:  Return storage(d2x(Arg(1)),Arg(2)) /* Return storage           */
/*-------------------------------------------------------------------*/
swareq:  Procedure
If right(c2x(Arg(1)),1) \= 'F' Then    /* SWA=BELOW ?                */
  Return c2d(Arg(1))+16                /* YES, RETURN SVA+16         */
sva = c2d(Arg(1))                      /* CONVERT TO DECIMAL         */
tcb = ptr(540)                         /* TCB PSATOLD                */
jscb = ptr(tcb+180)                    /* JSCB TCBJSCB               */
qmpl = ptr(jscb+244)                   /* QMPL JSCBQMPI              */
qmat = ptr(qmpl+24)                    /* QMAT QMADD                 */
Do While sva>65536
  qmat = ptr(qmat+12)                  /* NEXT QMAT QMAT+12          */
  sva=sva-65536                        /* 010006F -> 000006F         */
End
Return ptr(qmat+sva+1)+16
/*-------------------------------------------------------------------*/
scomment:                              /* Add comments in sample     */
Call add ' /* 'left(Arg(1),56)' */'
Return
/*-------------------------------------------------------------------*/
comment:                               /* Add block comments         */
/* Add comments in sample                                            */
Call add '//*'copies('-',67)'*'
Call add '//*'center(' 'Arg(1)' ',67)'*'
Call add '//*'copies('-',67)'*'
Return
/*-------------------------------------------------------------------*/
add:                                   /* Add lines to the JCL       */
Parse Arg line
'LINE_AFTER 'lineno' = (LINE)'
lineno=lineno+1
Return
/*-------------------------------------------------------------------*/
insert:  Procedure Expose ddname. dsname. lineno
ddname=Arg(2)
Call get_allocations Arg(1)
If ddname.0>0 Then
  Do a = 1 to ddname.0
    line= '//'left(ddname,9)'DD DISP=SHR,DSN='dsname.a
    If length(line)<63 Then
      line=substr(line,1,63)||volume.a;else
    If length(line)<65 Then
      line=line volume.a
    Call add line
    ddname=''
  End
Return

_________________
Kolusu
www.linkedin.com/in/kolusu
Back to top
View user's profile Send private message Send e-mail Visit poster's website
misfit
Beginner


Joined: 01 May 2003
Posts: 26
Topics: 9
Location: India

PostPosted: Sun Jul 25, 2004 11:48 pm    Post subject: Reply with quote

Very Happy
Thanks Kolusu, it worked !! and sorry for being late in reply.

I was just wondering how many of those parameters are absolutely necessasry for the execution. As i know the ISP*LIBs, i get them using ISRDDN. So do i need the other stuff
e.g.
ISPEXEC VGET (ZTIMEL) /* ISPF services can run here */
WRITE &ZTIMEL
Also, the BATCHPDS creates one new profile. Can i use my own profile for this.

Cheers also for Doug Nadel Smile
_________________
<i><b> Don't wish it were easier. Wish you were better. </b></i>
Back to top
View user's profile Send private message
misfit
Beginner


Joined: 01 May 2003
Posts: 26
Topics: 9
Location: India

PostPosted: Sun Jul 25, 2004 11:58 pm    Post subject: Reply with quote

I found a similar post here .. which clarified most of my doubts ..
_________________
<i><b> Don't wish it were easier. Wish you were better. </b></i>
Back to top
View user's profile Send private message
Display posts from previous:   
Post new topic   Reply to topic   printer-friendly view    MVSFORUMS.com Forum Index -> TSO and ISPF All times are GMT - 5 Hours
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


MVSFORUMS
Powered by phpBB © 2001, 2005 phpBB Group