******************************************************************************** * * * BootPic V1.0 * * (source-code) * * * * Author: Andreas Ackermann * * Assembler: Devpac V2.14D * * Date: from 21.3. to 31.3. 1991 * * Develloped under Kickstart V1.2 * * * * [see doc-file for further information]. * * * * The whole programm is split in two parts: * * 1st we look what the user wants, then we remove or install BootPic in the * * way it is requested. * * The 2nd part, which is installed resident, is responsible for showing the * * picture. * * * ******************************************************************************** incdir "Include:" include "graphics/graphics_lib.i" include "exec/exec_lib.i" include "libraries/dos_lib.i" include ":bootpic/bpic_special.i" movem.l d0/a0,-(sp) ;save commandline parameters move.l 4.w,a6 sub.l a1,a1 jsr _lvoFindTask(a6) ;find structure of our task move.l d0,a4 tst.l pr_CLI(a4) ;WB? bne.s run fromWorkbench lea pr_MsgPort(a4),a0 ;if WB we must wait for startup-msg jsr _lvowaitport(a6) lea pr_MsgPort(a4),a0 jsr _lvogetmsg(a6) move.l d0,wbenchmsg ;save message !! run movem.l (sp)+,d0/a0 ;return commandline parms bsr.s _main ;call our programm tst.l wbenchmsg ;run from WB ? beq.s _exit ;no => CLI move.l 4.w,a6 jsr _lvoforbid(a6) move.l wbenchmsg(pc),a1 ;return message jsr _lvoreplymsg(a6) _exit clr.l d0 ;no returncode rts ;the end allmeml equ $654 ;length of structure AND resident code * two macros for pc-relative code elea macro ;Extended LEA elea xx(ax),xx(ax) lea \1,a0 move.l a0,\2 endm emove macro ;Extended MOVE move.l xx,xx(pc) lea \2,a0 move.l \1,(a0) endm _main movem.l d0/a0,-(sp) ;save parms again move.l 4.w,a6 lea gfxname(pc),a1 jsr _lvooldopenlibrary(a6) move.l d0,gfxbase lea dosname(pc),a1 jsr _lvooldopenlibrary(a6) ;open gfx+dos move.l d0,dosbase move.l d0,a6 jsr _lvooutput(a6) ;get handle of CLI move.l d0,whandle tst.l wbenchmsg ;do we run under WB ? => open own window beq.s nowb move.l #oname,d1 move.l #1005,d2 jsr _lvoopen(a6) move.l d0,whandle ;opened CON:-window move.l 4.w,a6 move.l #100,d0 ;get mem for readbuffer (of CON:-window) move.l #$10002,d1 jsr _lvoallocmem(a6) move.l d0,conbuf add.l #8,a7 lea welcome(pc),a2 ;introduce ourselves bsr stringout nextround lea ycom(pc),a2 ;tell the user what to do bsr stringout move.l dosbase(pc),a6 move.l conbuf(pc),d2 move.l whandle(pc),d1 move.l #80,d3 jsr _lvoread(a6) ;read command parameters move.l conbuf(pc),a0 ;in d0 we get length of commandline clr.l remptr ;clear our flags, cause this is a loop (when run clr.b camgf ;from WB) clr.l fname bra.s parser nowb lea welcome(pc),a2 bsr stringout movem.l (sp)+,d0/a0 ;get saved parms back from stack parser ;here we get both from CLI and WB: figure out ;what the user wants subq.w #1,d0 ;any parms ? no->usage beq noparms clr.b 0(a0,d0.w) ;zero-terminate it plop bsr getspcout cmp.b #'-',(a0)+ bne noparms ;no '-' in front of parameter bclr.b #5,(a0) ;force uppercase cmp.b #'R',(a0) ;get out -r bne.s noreset move.b #1,resetvar add.l #1,a0 bra.s plop noreset cmp.b #'E',(a0) ;get out -e bne.s noremove move.b #1,mparm move.b #1,remptr add.l #1,a0 bra.s plop noremove cmp.b #'S',(a0) ;get out -s bne.s nostartup move.b #1,startup add.l #1,a0 bra.s plop nostartup cmp.b #'L',(a0) ;get out -l bne.s noload move.b #1,mparm add.l #1,a0 bsr getspcout move.l a0,fname findspc add.l #1,a0 cmp.b #' ',(a0) beq.s terminate1 tst.b (a0) bne.s findspc beq plop terminate1 clr.b (a0)+ bra plop noload cmp.b #'C',(a0)+ ;get out -c bne.s noparms ;someone typed nosense after '-' bsr getspcout moveq.w #2,d0 lea konst(pc),a1 ;there we put the color cl tst.b (a0) beq.s ende cmp.b #' ',(a0) beq.s ende sub.b #48,(a0) cmp.b #10,(a0) blt.s no15 bclr.b #5,(a0) sub.b #7,(a0) no15 and.b #%1111,(a0) move.b (a0)+,(a1)+ dbf d0,cl bra plop getspcout tst.b (a0) ;increase a0 till we find a space or zero beq.s wrt cmp.b #' ',(a0)+ beq getspcout sub.l #1,a0 rts wrt add.l #4,sp bra.s ende noparms lea use(pc),a2 bra noopen ende tst.b mparm beq.s noparms move.l 4.w,a6 ;the parms were correct, so let's kill a possibly move.l 546(a6),a3 ;installed BootPic at any rate tst.l 546(a6) beq notinstalled chknxt move.l LN_NAME(a3),a0 cmp.l #'BPic',(a0) ;go through memlist till we find BootPic beq.s bpicfound ;or till the end tst.l (a3) ;[tst.l LN_SUCC(a3)] beq notinstalled move.l (a3),a3 ;[move.l LN_SUCC(a3),a3] next node bra.s chknxt bpicfound ;we found BootPic !!! tst.b startup ;check for -s flag: if not set let's remove BootPic beq.s remove lea stext(pc),a2 ;tell the user that BPic is installed bra noopen ;return remove jsr _lvoforbid(a6) ;in a3 we still hold the memlist-node of BPic tst.l LN_PRED(a3) ;is there anyone before ? beq.s nopred ;if not, we're first move.l LN_PRED(a3),a0 ;move our successor(or zero) to the successor move.l (a3),(a0) ;of our predecessor tstsuc tst.l (a3) ;is there any successor ? beq.s predok ;no, everything ok move.l (a3),a1 ;if so we must move its address to the move.l a0,LN_PRED(a1) ;successor's address of our predecessor bra.s predok nopred move.l (a3),546(a6) ;if we're first, we must write the start of sub.l a0,a0 ;memlist into sysbase->kickmemptr bra.s tstsuc predok ;we switched off multitasking, so we can free move.w LN_NAME+4(a3),d3;the allocated memory already now (numentries) subq.w #1,d3 ;LN_NAME+4 = ML_NUMENTRIES add.l #LN_NAME+6,a3 ;start of memorypointer table fagain move.l (a3)+,a1 ;startaddress move.l (a3)+,d0 ;length jsr _lvofreemem(a6) ;free it dbf d3,fagain ;usually twice (dbf loop for reasons of compa- ;tibilty to higher versions that might follow) move.l 550(a6),a3 ;kicktagptr to a3 nentry move.l (a3),a0 move.l rt_name(a0),a0 cmp.l #'BPic',(a0) ;check first resident structure for BPic beq.s bpicf2 move.l a3,a4 ;save actual restabptr add.l #4,a3 ;next entry move.l (a3),d0 ;no more entrys ?! but we found BPic's memory and now beq.s finito ;we found not its resident structure => fatal error ! btst.l #$1f,d0 ;next entry or pointer to next restab beq.s nentry bclr.l #$1f,d0 ;clear highbit move.l d0,a3 ;lets' check next residenttable structure bra.s nentry finito lea.l fail(pc),a2 ;if we run here there was a fatal error jsr _lvopermit(a6) bra noopen bpicf2 cmp.l 550(a6),a3 ;is our actual restab the same as in kicktagptr? bne.s linkout ;if not we have a predecessor (held in a4) move.l 4(a3),d0 ;move our sucessor (or zero) to kicktagptr bclr.l #$1f,d0 ;clear highbit move.l d0,550(a6) bra.s ready linkout move.l 4(a3),4(a4) ;put our successor (or zero) to our predecessor ready jsr -612(a6) ;calc checksum (kicksumdata) move.l d0,554(a6) jsr _lvopermit(a6) lea remt(pc),a2 ;print out that we removed it bsr stringout sub.l a2,a2 tst.b remptr ;check for -e: was that all we should do? bne noopen ;yes->return, no-> let's try to load the picture notinstalled lea nrem(pc),a2 tst.b remptr ;test if user typed -e;but BPic was not there bne noopen ;return and let's tell him if so move.l dosbase(pc),a6 move.l fname(pc),d1 move.l #1005,d2 jsr _lvoopen(a6) ;try to open file lea fnf(pc),a2 move.l d0,handle beq noopen ;if error let's tell the user move.l 4.w,a6 move.l #1000,d0 move.l #$10002,d1 ;chip+clear jsr _lvoallocmem(a6);get memory for readbuffer of file lea nomem(pc),a2 move.l d0,buffer beq nobufmem move.l #allmeml,d0 move.l #$10001,d1 ;memf_public+clear jsr _lvoallocmem(a6);get memory for our special structure move.l d0,a5 ;from now on this pointer is to be found in a5 beq nostruktmem move.l dosbase(pc),a6 move.l handle(pc),d1 move.l buffer(pc),d2 moveq.l #12,d3 jsr _lvoread(a6) ;read header of file move.l buffer(pc),a4 ;buffer to address-register so that we can use lea nilbm(pc),a2 ;offsets cmp.l #'FORM',(a4) bne noiff ;no IFF->error cmp.l #'ILBM',8(a4) bne noiff ;not ILBM->error getchunk move.l handle(pc),d1 moveq.l #8,d3 jsr _lvoread(a6) ;read header of chunk lea bnf(pc),a2 ;4 Bytes code word + 4 Bytes length tst.l d0 ;end of file ? but we didn't find BODY beq noiff ;->error cmp.l #'BODY',(a4) beq bodyfound cmp.l #'CMAP',(a4) beq cmapfound cmp.l #'CAMG',(a4) beq camgfound cmp.l #'BMHD',(a4) beq bmhdfound bsr rcdata ;if we get here it wasn't any chunk we need bra.s getchunk bodyfound move.l 4.w,a6 move.l 4(a4),d0 addq.l #4,d0 move.l d0,ml_len2(a5) addq.l #8,d0 ;allocmem rounds down by 8 bytes move.l #$10002,d1 jsr _lvoallocmem(a6);memory for BODY-chunk lea nmfb(pc),a2 move.l d0,memptr beq noiff move.l d0,d2 move.l dosbase(pc),a6 bsr rcdata ;read BODY in move.l 4.w,a6 move.l 4(a4),d0 add.l #12,d0 moveq.l #4,d1 jsr _lvoallocmem(a6);fastmem ? move.l d0,a1 tst.l d0 beq.s nofast ;if there let's copy the BODY to it ! move.l d0,a3 move.l memptr(pc),a0 move.l 4(a4),d1 lsr.l #2,d1 bloop move.l (a0)+,(a1)+ ;copy BODY dbf d1,bloop move.l 4(a4),d0 add.l #12,d0 move.l memptr(pc),a1 jsr _lvofreemem(a6) ;free old chipmem bra.s memfreed nofast move.l memptr(pc),a3 memfreed move.l a3,ml_addr2(a5) tst.b camgf ;did we find CAMG ? bne.s noham lea ncamg(pc),a2 ;let's tell the user that we improvise bsr stringout cmp.w #353,vp_dwidth(a5) ;wider than 352 bytes? blt.s nohires ;it must be hires add.w #$8000,vp_modes(a5) nohires cmp.w #283,vp_dheight(a5) ;... blt.s nolace add.w #$4,vp_modes(a5) nolace cmp.w #6,depth(a5) ;HAM and Halfbright work with 6 planes bne.s noham add.w #$800,vp_modes(a5) ;I say it's HAM !!! noham move.l a5,strktptr ;put the pointer to our structure into the lea suc(pc),a2 ;resident code (will be copied later on! ) move.l gfxbase(pc),a6 lea view(a5),a1 ;init all we need to show the picture jsr _lvoinitview(a6) move.w vp_modes(a5),v_modes(a5) elea viewport(a5),v_viewport(a5) lea bitmap(a5),a0 move.w depth(a5),d0 move.w bmw(a5),d1 move.w bmh(a5),d2 jsr _lvoinitbitmap(a6) lea.l rasinfo(a5),a0 elea bitmap(a5),ri_bitmap(a5) elea rasinfo(a5),vp_rasinfo(a5) move.w vp_modes(a5),d0 ;if overscan move the picture to top left move.w #320,d1 ;corner btst.l #$f,d0 beq.s nohires2 lsl.w #1,d1 nohires2 neg.w d1 add.w vp_dwidth(a5),d1 bpl.s doit1 clr.w d1 doit1 lsr.w #1,d1 sub.w d1,v_dxoffset(a5) move.w #256,d1 btst.l #$2,d0 beq.s nolace2 lsl.w #1,d1 nolace2 neg.w d1 add.w vp_dheight(a5),d1 bpl.s doit clr.w d1 doit lsr.w #1,d1 sub.w d1,v_dyoffset(a5) lea idendity(a5),a0 ;copy code into allocated memory lea begincopy(pc),a1 move.w #endcopy-begincopy-1,d0 idlop move.b (a1)+,(a0)+ dbf d0,idlop move.l a5,ml_addr1(a5) ;intialize resident structure move.l #allmeml-20,ml_len1(a5) fillout move.w #rtc_matchword,rt_matchword(a5) elea rt_matchword(a5),rt_matchtag(a5) elea rt_SIZE(a5),rt_endskip(a5) move.b #1,rt_flags(a5) move.b #-1,rt_pri(a5) elea id_name(a5),rt_name(a5) elea id_string(a5),rt_idstring(a5) elea code(a5),rt_init(a5) move.w #2,ml_numentries(a5) ;init memlist structure elea id_name(a5),myln_name(a5) move.b #nt_memory,myln_type(a5) login move.l 4.w,a6 jsr _lvoforbid(a6) ;let's write ourselves into sysbase move.l 546(a6),a1 ;kickmemptr tst.l 546(a6) beq.s nixda ;we always use first place and put move.l a1,myln_succ(a5) ;any things that were before us behind us elea myln_succ(a5),4(a1) ;[predecessor] nixda elea myln_succ(a5),546(a6) ;and now for kicktagptr move.l a5,restab(a5) move.l 550(a6),d0 beq.s nomtag bset #$1f,d0 move.l d0,restab+4(a5) nomtag elea restab(a5),550(a6) jsr -612(a6) ;kicksumdata move.l d0,554(a6) ;fill in kickchecksum jsr _lvopermit(a6) tst.b resetvar ;does the user want to reset the machine? beq.s nostruktmem lea cod(pc),a5 lea 2,a4 jsr _lvosupervisor(a6) ;that's all ... cnop 0,4 cod reset jmp (a4) noiff ;here we run if there's an error while move.l 4.w,a6 ;loading move.l a5,a1 move.l #allmeml,d0 jsr _lvofreemem(a6) nostruktmem ;not enough memory for our structure move.l 4.w,a6 move.l buffer(pc),a1 move.l #1000,d0 jsr _lvofreemem(a6) nobufmem ;not enough mem for diskbuffer move.l dosbase(pc),a6 move.l handle(pc),d1 jsr _lvoclose(a6) noopen ;move.l dosbase(pc),a6 move.l a2,d2 beq.s noerr bsr stringout noerr tst.l wbenchmsg beq.s nowb2 ;if run from WB we read some characters lea endwb(pc),a2 ;if length=1 the user just typed RETURN bsr stringout ;so we let him type in the commandline again move.l dosbase(pc),a6 move.l conbuf(pc),d2 move.l whandle(pc),d1 moveq.l #2,d3 jsr _lvoread(a6) subq.w #1,d0 beq nextround move.l whandle(pc),d1 ;if there was typed more than RETURN we jsr _lvoclose(a6) ;close the window free the memory and move.l 4.w,a6 ;return move.l conbuf(pc),a1 move.l #100,d0 jsr _lvofreemem(a6) nowb2 move.l 4.w,a6 ;close libs move.l dosbase(pc),a1 jsr _lvocloselibrary(a6) move.l gfxbase(pc),a1 jsr _lvocloselibrary(a6) rts **//** SUBs + chunk-reading routines * print out a zero-termintated string of which the start is found in a2 stringout move.l a2,d2 move.l #-1,d3 p1 addq.l #1,d3 tst.b (a2)+ bne.s p1 move.l whandle,d1 move.l a6,-(a7) move.l dosbase(pc),a6 jsr _lvowrite(a6) move.l (sp)+,a6 rts * read in one chunk rcdata move.l 4(a4),d3 move.l handle,d1 jsr _lvoread(a6) rts * get colormap [format see at getcols ! ] cmapfound move.l 4(a4),d4 elea coltab(a5),d2 bsr rcdata move.l buffer(pc),d2 lea coltab(a5),a0 gcol move.b (a0),d0 lsr.b #4,d0 and.b #%1111,d0 move.b d0,(a0)+ dbf d4,gcol bra getchunk * here are the viewmodes camgfound bsr rcdata move.w modes+2(a4),vp_modes(a5) ;get the viewmodes move.b #1,camgf bra getchunk * get the dimensions of the picture bmhdfound bsr rcdata move.l w(a4),bmw(a5) ;w+h are .w so .l is enough for both move.b nplanes(a4),depth+1(a5) move.b masking(a4),mask(a5) lea ncomp(pc),a2 tst.b compression(a4);we won't load compressed pictures beq noiff move.w pagewidth(a4),vp_dwidth(a5) move.w pageheight(a4),vp_dheight(a5) bra getchunk **//** wbenchmsg dc.l 0 ;contains msg if run from WB conbuf dc.l 0 ;readbuffer for CON:-window remptr dc.b 0 ;set if -e was specified resetvar dc.b 0 ;set if -r was specified mparm dc.b 0 ;set if either -e or -l was specified startup dc.b 0 ;set if -s was specified camgf dc.b 0 ;set if CAMG was found dc.b 0 ;make even memptr dc.l 0 ;ptr to BODY-chunk buffer dc.l 0 ;ptr to readbuffer handle dc.l 0 ;handle of IFF-file dosbase dc.l 0 ;... whandle dc.l 0 ;handle we write to (CLI or CON:) fname dc.l 0 ;pointer to filename dosname dc.b 'dos.library',0 even oname dc.b 'CON:10/50/620/130/BootPic V1.0 © 1991 by Acki',0 even welcome dc.b 10,27,'[1;32m',' BootPic V1.0 ',27,'[0;31m','©1991 by ' dc.b 27,'[3;33m','Andreas Ackermann',27,'[0;31m',10 dc.b ' This programm is SHAREWARE. If you use it, please send ' dc.b 27,'[1;32m','5$ or 5DM',27,'[0;31m to:',10 dc.b ' Andreas Ackermann',10 dc.b ' Lorenz-Summa-Str. 10',10 dc.b ' W-8679 Oberkotzau',10 dc.b ' GERMANY',10 dc.b ' See Doc-File for detailed information !',10,10,0 even nmfb dc.b 'Not enough Memory for BODY-Chunk',10,0 even bnf dc.b 'BODY-Chunk not found',10,0 even ncamg dc.b 'Warning:CAMG-Chunk not found.',10,0 even nilbm dc.b 'This is not an ILBM-Picturefile',10,0 even nomem dc.b "Couldn't get enough Memory",10,0 even fnf dc.b "Couldn't open Picturefile",10,0 even use dc.b "Usage: BootPic -e | -l{ILBM-filename} [-c rgb][-r][-s]",10,0 even remt dc.b "Removed old BootPicture from list",10,0 even ncomp dc.b 'Picture is not compressed. Save it with DPaint and try again.',10,0 even suc dc.b 'Picture successfully installed. Have fun !',10,0 even fail dc.b 'Memlist Corrupt. Something went totally wrong !',10,0 even stext dc.b 'BootPic already installed. Changed nothing.',10,0 even nrem dc.b "BootPic was not installed. Couldn't remove it.",10,0 even ycom dc.b 27,'[10;0H',27,'[JYour commands:',0 even endwb dc.b 'Hit RETURN to go on, type anything to end',0 even * Part of Programm that shows picture after reset begincopy idname dc.b 'BPic',0,0 idstring dc.b 'BootPic,©1991 by Acki',0 dc.b 0,0,0,0,0,0,0,0 movem.l d0-7/a0-6,-(sp) move.l 4.w,a6 move.l strktptr(pc),a5 ;get ptr of our special structure move.l ml_addr2(a5),a3 ;get ptr of BODY-data lea gfxname(pc),a1 jsr _lvooldopenlibrary(a6) emove d0,gfxbase(pc) move.l #readend+8,d0 ;allocate some mem: used for move.l #$10002,d1 ;replyport and diskio jsr _lvoallocmem(a6) move.l d0,a4 move.l d0,-(sp) sub.l a1,a1 jsr _lvofindtask(a6) ;init replyport move.l d0,replyport+$10(a4) lea replyport(a4),a1 jsr _lvoaddport(a6) testagain move.l a4,a1 clr.l d0 clr.l d1 lea trddevice(pc),a0 ;open trackdiskdevice jsr _lvoopendevice(a6) tst.l d0 bne.s testagain moveq.b #0,d2 bsr readboot ;check for bootable disk in df0: tst.b d3 ;[see at readboot what d2 means !] beq cleanup showpic move.l gfxbase(pc),a6 ;clear all pointers to copperlists clr.l view+4(a5) ;so that mrgcop knows that it has to take clr.l view+8(a5) ;new copperlists ! moveq.w #4,d0 lea vp_colormap(a5),a0 cll clr.l (a0)+ dbf d0,cll move.w depth(a5),d2 ;allocate planes; if masking then alloc one lea bm_planes(a5),a2 ;more plane that isn't to be found in cmp.b #1,mask(a5) ;bm_depth beq.s nomsk subq.w #1,d2 nomsk move.w bmw(a5),d0 move.w bmh(a5),d1 jsr _lvoallocraster(a6) move.l d0,(a2)+ beq rasterfail dbf d2,nomsk clr.l (a2) ;zero-terminate bm_planes cause we'll free bsr unpackbody ;memory till we find zero move.l #32,d0 ;32 is always enough jsr _lvogetcolormap(a6) move.l d0,vp_colormap(a5) lea view(a5),a0 lea viewport(a5),a1 jsr _lvomakevport(a6) lea view(a5),a1 jsr _lvomrgcop(a6) ;generate display move.l 34(a6),d7 lea view(a5),a1 jsr _lvoloadview(a6) ;let's show it lea coltab(a5),a2 lea viewport(a5),a3 lea white(pc),a4 moveq.w #0,d0 bsr fadein ;fade picture in move.l 4.w,a6 move.l (sp),a4 move.b #1,d2 bsr readboot ;wait for bootable disk move.l gfxbase(pc),a6 lea konst(pc),a4 moveq.w #0,d0 bsr fadeout ;fade to color specified under -c move.l vp_colormap(a5),a0 ;free copperlists jsr _lvofreecolormap(a6) lea.l viewport(a5),a0 jsr _lvofreevportcoplists(a6) move.l view+4(a5),a0 jsr _lvofreecprlist(a6) move.l view+8(a5),a0 jsr _lvofreecprlist(a6) move.l d7,a1 jsr _lvoloadview(a6) ;show old view rasterfail lea bm_planes(a5),a2 nomsk2 move.l (a2)+,a0 tst.l -4(a2) beq.s meme move.w bmw(a5),d0 move.w bmh(a5),d1 jsr _lvofreeraster(a6) bra.s nomsk2 ;free planes till we find zero meme move.l 34(a6),a0 move.l 4(a0),a0 moveq.w #0,d0 lea konst(pc),a1 ;set the new color in the old viewport move.b (a1)+,d1 move.b (a1)+,d2 move.b (a1)+,d3 jsr _lvosetrgb4(a6) cleanup move.l 4.w,a6 ;clean up everything we needed to wait for move.l (sp)+,a4 ;disk lea replyport(a4),a1 jsr _lvoremport(a6) move.l a4,a1 jsr _lvoclosedevice(a6) move.l a4,a1 move.l #readend+8,d0 jsr _lvofreemem(a6) move.l gfxbase(pc),a1 jsr _lvocloselibrary(a6) movem.l (sp)+,d0-7/a0-6 rts * This routines checks for a bootable disk in df0: . * Result in d3.b : zero if a disk is there, 1 if no bootable disk in drive. * Flags: if d2.b=1 it will wait until a bootable disk is inserted readboot move.l a4,a1 lea.l replyport(a4),a0 ;put replyport int io_request structure move.l a0,14(a1) readit move.w #$5,io_command(a1) ;declare the buffer to be invalid jsr _lvodoio(a6) move.l #2*512,io_length(a1) move.w #$2,io_command(a1) lea readbuffer(a4),a0 ;read bootblock move.l a0,io_data(a1) jsr _lvodoio(a6) tst.l d0 ;any errors ? bne.s wfd ;if then goto waitfordisk calcsum lea readbuffer(a4),a0 cmp.l #$444f5300,(a0) ;check if DOS,0 [could be FFS,0 as well] bne.s wfd clr.l d0 move.w #$00ff,d1 ;calculate checksum of bootblock schleife add.l (a0)+,d0 bcc.s nof addq.l #1,d0 nof dbf d1,schleife not.l d0 beq.s noderr ;if zero, disk is bootable wfd tst.b d2 bne.s motoff ;shall we wait for disk ? moveq.b #1,d3 ;if not say there's not a bootable disk rts ;in drive and return. ;ndise cmp.b #29,31(a4) ;error ; beq.s wloop motoff clr.l io_length(a1) ;switch off motor move.w #$9,io_command(a1) jsr _lvodoio(a6) ;[if io_length=0 motor off, if 1 then on] remloop bsr chkdisk tst.l 32(a4) ;wait till no disk in drive beq.s remloop wloop bsr chkdisk tst.l 32(a4) ;wait till next one is inserted bne.s wloop bra.s readit ;let's look what we got chkdisk move.w #$e,io_command(a1) jsr _lvodoio(a6) ;check for disk in df0: btst #6,$bfe001 bne.s chkon add.l #4,a7 noderr clr.l d3 chkon rts strktptr dc.l 0 ;pointer to our special structure gfxbase dc.l 0 ;... gfxname dc.b 'graphics.library',0 even trddevice dc.b 'trackdisk.device',0 even konst dc.b $0,$5,$a,0 ;here we put the color specified by -c white dc.b $f,$f,$f,0 ;data for white color. * This routine unpacks the BODY-chunk * a3 holds a pointer to the packed BODY-data * a2 must contain pointer to bm_planes * bm_depth must be put in d4 * bm_bytesperrow could be put in d2 and bm_height could be put in d3 * [to include this in your own programms, it has to be slightly modified.] unpackbody movem.l d0-7/a0-6,-(sp) moveq.w #0,d5 move.w depth(a5),d4 lea.l bm_planes(a5),a2 cmp.b #1,mask(a5) bne.s unpackline addq.w #1,d4 UnpackLine clr.l d6 UnpackPlane move.w bm_bytesperrow(a5),d0 mulu d5,d0 move.l d0,a4 asl #2,d6 add.l 0(a2,d6.w),a4 asr #2,d6 move.l a4,a6 add.w bm_bytesperrow(a5),a6 clr.l d0 CheckPacked move.b (a3)+,d0 cmp.b #128,d0 bhi.s GoOn beq.s CheckFinished FinishLine move.b (a3)+,(a4)+ subq.b #1,d0 bpl.s FinishLine bra.s CheckFinished GoOn move.b (a3)+,d1 StoreByte move.b d1,(a4)+ addq.b #1,d0 cmp.b #1,d0 bne.s StoreByte CheckFinished cmp.l a4,a6 bhi.s CheckPacked addq.w #1,d6 cmp.w d4,d6 bne.s UnpackPlane GoOnLoop addq.w #1,d5 cmp.w bmh(a5),d5 bne.s UnpackLine movem.l (sp)+,d0-7/a0-6 rts * reads out the colors of a colormap and stores it in a piece of memory [200 * Bytes required ] in the following form: * 1st byte r, 2nd byte g and in 3rd byte b. Then the next color appears. * parms: a2=pointer to memory a3=pointer to Colormap a6=gfxbase getcols movem.l d0-2/a0-2,-(sp) moveq.w #0,d2 1$ move.l a3,a0 move.l d2,d0 jsr _lvogetrgb4(a6) move.b d0,2(a2) ;b and.b #%1111,2(a2) lsr.w #4,d0 move.b d0,1(a2) ;g and.b #%1111,1(a2) lsr.w #4,d0 move.b d0,(a2) ;r addq.w #1,d2 add.l #3,a2 cmp.w 2(a3),d2 bne.s 1$ movem.l (sp)+,d0-2/a0-2 rts * fades out a viewport to a specified color [this color must be given in a * special format: 1st byte r, 2nd g and 3rd b.(4th=0)] * before fading out it is advisable to save the colors with getcols * parms: a3=viewport a4=pointer to color d0=delaytime (see below) * [a5=dosbase] a6=gfxbase fadeout movem.l d0-7/a0-6,-(sp) move.l 4.w,a6 move.l #100,d0 move.l #$10001,d1 jsr _lvoallocmem(a6) move.l d0,a2 move.l 4(a3),a3 move.l 56(sp),a6 bsr getcols move.w 2(a3),a3 move.l a2,a5 1$ moveq.b #0,d7 moveq #2,d5 moveq #0,d6 2$ moveq #0,d4 move.l a5,a2 3$ move.b (a2),d1 move.b 1(a2),d2 move.b 2(a2),d3 move.b 0(a4,d6.w),d0 cmp.b 0(a2,d6.w),d0 blt.s 5$ beq.s 4$ addq.b #1,0(a2,d6.w) bra.s 6$ 5$ subq.b #1,0(a2,d6.w) 6$ moveq.b #1,d7 4$ move.w d4,d0 move.l 44(sp),a0 ;viewport move.l 56(sp),a6 jsr _lvosetrgb4(a6) add.l #3,a2 addq.w #1,d4 cmp.w a3,d4 bne.s 3$ ; move.l (sp),d1 ;we're before boot up so we can't use dos.lib. ; move.l 52(sp),a6 ;so we help ourselves with dbf. ; jsr _lvodelay(a6) ;delay just needed if less then 32 colors. move.l (sp),d0 10$ dbf d0,10$ addq.w #1,d6 dbf d5,2$ tst.b d7 bne.s 1$ move.l 4.w,a6 move.l a5,a1 move.l #100,d0 jsr _lvofreemem(a6) movem.l (sp)+,d0-7/a0-6 rts * fades in a viewport from a specified color [this color must be given in a * special format: 1st byte r, 2nd g and 3rd b.(4th=0)] * parms: a2=pointer to coltab as given by getcols a3=viewport * a4=pointer to color d0=delaytime (see above) [a5=dosbase] a6=gfxbase fadein movem.l d0-7/a0-6,-(sp) move.l 4(a3),a0 move.w 2(a0),d0 move.l a2,a0 add.l #100,a0 subq.w #1,d0 7$ move.b (a4),(a0)+ move.b 1(a4),(a0)+ move.b 2(a4),(a0)+ dbf d0,7$ move.l a2,a5 1$ move.w #0,a4 moveq #2,d5 moveq #0,d6 2$ moveq #0,d4 move.l a5,a2 3$ move.b 100(a2),d1 move.b 101(a2),d2 move.b 102(a2),d3 move.b 0(a2,d6.w),d0 cmp.b 100(a2,d6.w),d0 beq.s 4$ blt.s 5$ addq.b #1,100(a2,d6.w) bra.s 6$ 5$ subq.b #1,100(a2,d6.w) 6$ move.w #1,a4 4$ move.w d4,d0 move.l a3,a0 move.l 56(sp),a6 ;gfxbase from Stack jsr _lvosetrgb4(a6) add.l #3,a2 ;step to the data of the next colour addq #1,d4 ;count the number of colours that we modified move.l 4(a3),a0 ;vport->colormap to a0 cmp.w 2(a0),d4 ;compare the number of colours with our colour ;counter bne.s 3$ ;have we already modified all colours ?If not ;then let's modify the next one ; move.l (sp),d1 ;see above ; move.l 52(sp),a6 ; jsr _lvodelay(a6) move.l (sp),d0 10$ dbf d0,10$ addq.w #1,d6 ;now it's the next component's turn to be changed dbf d5,2$ ;we must do this loop three times:once for red, ;once for green and once for blue, ;so we load d5 with 2!!(3-1) in the beginning cmp.w #0,a4 ;(tst.w a4 doesn't work) find out if any changes were bne.s 1$ ;done in this loop,if not then we are ready movem.l (sp)+,d0-7/a0-6 ;clean up stackpointer rts endcopy END