diff --git a/assembly/A DOS 2.0 filter for word processing document files.asm b/assembly/A DOS 2.0 filter for word processing document files.asm new file mode 100644 index 0000000..e8b2941 --- /dev/null +++ b/assembly/A DOS 2.0 filter for word processing document files.asm @@ -0,0 +1,136 @@ +; +; This program reads text from the standard input device and writes +; filtered and transformed text to the standard output device. +; +; 1. High bit of all characters is stripped off. +; 2. Tabs are expanded. +; 3. Removes all control codes except for line +; feeds, carriage returns, and form feeds. +; 4. Appends an end-of-file mark to the text, if +; none was present in the input stream. +; +; Can be used to make a WordStar file acceptable for +; other screen or line editors, and vice versa. +; +; +cr equ 0dh ; ASCII carriage return +lf equ 0ah ; ASCII line feed +ff equ 0ch ; ASCII form feed +eof equ 01ah ; End-of-file marker +tab equ 09h ; ASCII tab code + +command equ 80h ; buffer for command tail + +; DOS 2.0 Pre-Defined Handles + +stdin equ 0000 ; standard input file +stdout equ 0001 ; standard output file +stderr equ 0002 ; standard error file +stdaux equ 0003 ; standard auxilliary file +stdprn equ 0004 ; standard printer file + +cseg segment para public 'CODE' + + assume cs:cseg,ds:cseg + + org 100H ; start .COM at 100H + +clean proc far ; entry point from PC-DOS. + push ds ; push a long return back + xor ax,ax ; to DOS onto the stack. + push ax + +clean3: call get_char ; get a character from input. + and al,7fh ; turn off the high bit. + cmp al,20h ; is it a control char? + jae clean4 ; no. write it to output. + cmp al,eof ; is it end of file? + je clean6 ; yes, go write EOF mark and exit. + cmp al,tab ; is it a tab? + je clean5 ; yes, go expand it to spaces. + cmp al,cr ; is it a carriage return? + je clean35 ; yes, go process it. + cmp al,lf ; is it a line feed? + je clean35 ; yes, go process it. + cmp al,ff ; is it a form feed? + jne clean3 ; no. discard it. +clean35: + mov column,0 ; if it's a legit ctrl char, + jmp clean45 ; we should be back at column 0. + +clean4: inc column ; if it's a non-ctrl char, +clean45: ; col = col + 1. + call put_char ; write the char to output. + jnc clean3 ; if OK, go back for another char. + + mov bx,stderr ; not OK. Set up to show error. + mov dx,offset err_msg + mov cx,err_msg_len ; error = Disk full. + mov ah,40h ; write the error message + int 21h ; to the standard error device. (CON:) + ret ; back to DOS. + +clean5: mov ax,column ; tab code detected, must expand + cwd ; expand tabs to spaces. + mov cx,8 ; divide the current column counter + idiv cx ; by eight... + sub cx,dx ; eight minus the remainder is the + add column,cx ; number of spaces to send out to +clean55: ; move to the next tab position. + push cx + mov al,20h + call put_char ; send an ASCII blank + pop cx + loop clean55 + jmp clean3 + +clean6: call put_char ; write out the EOF mark, + ret ; and return to DOS. + +clean endp + + +get_char proc near + mov bx,stdin ; get chars from std. input + mov cx,1 ; # of chars to get = 1 + mov dx,offset input_buffer ; location = input_buffer + mov ah,3fh + int 21h ; do the function call + or ax,ax ; test # of chars returned + jz get_char1 ; if none, return EOF + mov al,input_buffer ; else, return the char in AL + ret +get_char1: + mov al,eof ; no chars read, return + ret ; an End-of-File (EOF) mark. +get_char endp + +put_char proc near + mov output_buffer,al ; put char to write in buffer. + mov bx,stdout ; write to std. output + mov cx,1 ; # of chars = 1 + mov dx,offset output_buffer ; location = output_buffer + mov ah,40h + int 21h ; do the function call + cmp ax,1 ; check to see it was really done. + jne put_char1 + clc ; really done. return carry = 0 + ret ; as success signal. +put_char1: + stc ; not really done. return carry = 1 + ret ; as error signal (device is full). +put_char endp + +input_buffer db 0 +output_buffer db 0 + +column dw 0 + +err_msg db cr,lf + db 'clean: Disk is full.' + db cr,lf +err_msg_len equ (this byte)-(offset err_msg) + +cseg ends + + end clean \ No newline at end of file diff --git a/assembly/A listing into pages and give new subtitles.asm b/assembly/A listing into pages and give new subtitles.asm new file mode 100644 index 0000000..fb620d9 --- /dev/null +++ b/assembly/A listing into pages and give new subtitles.asm @@ -0,0 +1,310 @@ +; +; Macro file for MSDOS. +; + +SUBTTL BREAK a listing into pages and give new subtitles +PAGE +BREAK MACRO subtitle + SUBTTL subtitle + PAGE +ENDM + +BREAK + +; +; declare a variable external and allocate a size +; +I_NEED MACRO sym,len + CODE ENDS + DATA SEGMENT BYTE PUBLIC 'DATA' + + IFIDN , + EXTRN &sym:WORD + ELSE + IFIDN , + EXTRN &sym:DWORD + ELSE + EXTRN &sym:BYTE + ENDIF + ENDIF + + DATA ENDS + CODE SEGMENT BYTE PUBLIC 'CODE' +ENDM + +; +; call a procedure that may be external. The call will be short. +; +invoke MACRO name +&.xcref + add_ext name,near +&.cref + CALL name +ENDM + +PAGE +; +; jump to a label that may be external. The call will be near. +; +transfer MACRO name +&.xcref + add_ext name,near +&.cref + JUMP name +ENDM + +; +; get a short address in a word +; +short_addr MACRO name + IFDIF , +&.xcref + add_ext name,near +&.cref + DW OFFSET DOSGROUP:name + ELSE + DW ? + ENDIF +ENDM + +; +; get a long address in a dword +; +long_addr MACRO name +&.xcref + add_ext name,far +&.cref + DD name +ENDM + +; +; declare a PROC near or far but PUBLIC nonetheless +; +procedure MACRO name,distance + PUBLIC name +name PROC distance +ENDM + +PAGE +; +; define a data item to be public and of an appropriate size/type +; +I_AM MACRO name,size + PUBLIC name + + IFIDN , + name DW ? + ELSE + IFIDN , + name DD ? + ELSE + IFIDN , + name DB ? + ELSE + name DB size DUP (?) + ENDIF + ENDIF + ENDIF +ENDM + +PAGE +; +; play games with a possible external. Create a new +; macro for the symbol and text, and string it together +; with a central invoker +; + +.xcref +.xcref ?i +.xcref def_mac +.xcref ?z0 +.xcref add_ext +.cref + +IF1 + ?i=0 +ENDIF + +?z0 macro +endm + +; +; add an external declaration to s with type t if it is not defined +; +add_ext macro s,t +&.xcref +&.xcref ?&s +&.cref + IFNDEF ?&s + ?i = ?i + 1 + def_mac ?z&%?i,?z&%(?i-1),s,t + ENDIF +endm + +; +; define a macro called that possibly externals s:t and then calls macro n +; +def_mac macro m,n,s,t +&.xcref +&.xcref ?&s +&.xcref m +&.cref +m macro + ifndef s + extrn s:&t + endif + purge m + purge ?&s + n +endm +?&s macro +&endm +endm + +; +; call the macro chain +; +do_ext macro +&.xcref + expand_mac ?z%?i +&.cref +endm + +PAGE +expand_mac macro m + m +endm + +; +; define an entry in a procedure +; +entry macro name + PUBLIC name +name: +endm + +BREAK + +error macro code + local a +.xcref + MOV AL,code + transfer SYS_RET_ERR +.cref +ENDM + +BREAK +; +; given a label either 2 byte jump to another label _J +; if it is near enough or 3 byte jump to +; + +jump macro lbl + local a +.xcref + a: + ifndef lbl&_J ; is this the first invocation + JMP lbl + ELSE + IF lbl&_J GE $ + JMP lbl + ELSE + IF ($-lbl&_J) GT 126 ; is the jump too far away? + JMP lbl + ELSE ; do the short one... + JMP lbl&_J + ENDIF + ENDIF + ENDIF +endm + +BREAK + +return macro + local a +.xcref +a: + RET +ret_l = a +endm + +BREAK + +makelab macro l,cc,ncc + j&ncc a ; j a: + return ; return + a: ; a: + ret_&cc = ret_l ; define ret_ to be ret_l +endm + +condret macro cc,ncc + local a,b + ifdef ret_l ; if ret_l is defined + if (($ - ret_l) le 126) and ($ gt ret_l) + ; if ret_l is near enough then + a: j&cc ret_l ; a: j to ret_l + ret_&cc = a ; define ret_ to be a: + else + makelab a,cc,ncc + endif + else + ifdef ret_&cc ; if ret_ defined + if (($ - ret_&cc) le 126) and ($ gt ret_&cc) + ; if ret_ is near enough + a: j&cc ret_&cc ; a: j to ret_ + ret_&cc = a ; define ret_ to be a: + else + makelab a,cc,ncc + endif + else + makelab a,cc,ncc + endif + endif +endm +;condret macro cc,ncc +; local a,b +; ifdef ret_l ; if ret_l is defined +; if (($ - ret_l) le 126) and ($ gt ret_l) +; ; if ret_l is near enough then +; a: j&cc ret_l ; a: j to ret_l +; ret_&cc = a ; define ret_ to be a: +; exitm +; endif +; endif +; ifdef ret_&cc ; if ret_ defined +; if (($ - ret_&cc) le 126) and ($ gt ret_&cc) +; ; if ret_ is near enough +; a: j&cc ret_&cc ; a: j to ret_ +; ret_&cc = a ; define ret_ to be a: +; exitm +; endif +; endif +; j&ncc a ; j a: +; return ; return +; a: ; a: +; ret_&cc = ret_l ; define ret_ to be ret_l +;endm + +BREAK + +retz macro + condret z,nz +endm + +BREAK + +retnz macro + condret nz,z +endm + +BREAK + +retc macro + condret c,nc +endm + +BREAK + +retnc macro + condret nc,c +endm diff --git a/assembly/A small program that calculates and prints terms of the Fibonacci series.asm b/assembly/A small program that calculates and prints terms of the Fibonacci series.asm new file mode 100644 index 0000000..7d0cccc --- /dev/null +++ b/assembly/A small program that calculates and prints terms of the Fibonacci series.asm @@ -0,0 +1,261 @@ +; fibo.asm +; assemble using nasm: +; nasm -o fibo.com -f bin fibo.asm +; +;**************************************************************************** +; Alterable Constant +;**************************************************************************** +; You can adjust this upward but the upper limit is around 150000 terms. +; the limitation is due to the fact that we can only address 64K of memory +; in a DOS com file, and the program is about 211 bytes long and the +; address space starts at 100h. So that leaves roughly 65000 bytes to +; be shared by the two terms (num1 and num2 at the end of this file). Since +; they're of equal size, that's about 32500 bytes each, and the 150000th +; term of the Fibonacci sequence is 31349 digits long. +; + maxTerms equ 15000 ; number of terms of the series to calculate + +;**************************************************************************** +; Number digits to use. This is based on a little bit of tricky math. +; One way to calculate F(n) (i.e. the nth term of the Fibonacci seeries) +; is to use the equation int(phi^n/sqrt(5)) where ^ means exponentiation +; and phi = (1 + sqrt(5))/2, the "golden number" which is a constant about +; equal to 1.618. To get the number of decimal digits, we just take the +; base ten log of this number. We can very easily see how to get the +; base phi log of F(n) -- it's just n*lp(phi)+lp(sqrt(5)), where lp means +; a base phi log. To get the base ten log of this we just divide by the +; base ten log of phi. If we work through all that math, we get: +; +; digits = terms * log(phi) + log(sqrt(5))/log(phi) +; +; the constants below are slightly high to assure that we always have +; enough room. As mentioned above the 150000th term has 31349 digits, +; but this formula gives 31351. Not too much waste there, but I'd be +; a little concerned about the stack! +; + digits equ (maxTerms*209+1673)/1000 + +; this is just the number of digits for the term counter + cntDigits equ 6 ; number of digits for counter + + org 100h ; this is a DOS com file +;**************************************************************************** +;**************************************************************************** +main: +; initializes the two numbers and the counter. Note that this assumes +; that the counter and num1 and num2 areas are contiguous! +; + mov ax,'00' ; initialize to all ASCII zeroes + mov di,counter ; including the counter + mov cx,digits+cntDigits/2 ; two bytes at a time + cld ; initialize from low to high memory + rep stosw ; write the data + inc ax ; make sure ASCII zero is in al + mov [num1 + digits - 1],al ; last digit is one + mov [num2 + digits - 1],al ; + mov [counter + cntDigits - 1],al + + jmp .bottom ; done with initialization, so begin + +.top + ; add num1 to num2 + mov di,num1+digits-1 + mov si,num2+digits-1 + mov cx,digits ; + call AddNumbers ; num2 += num1 + mov bp,num2 ; + call PrintLine ; + dec dword [term] ; decrement loop counter + jz .done ; + + ; add num2 to num1 + mov di,num2+digits-1 + mov si,num1+digits-1 + mov cx,digits ; + call AddNumbers ; num1 += num2 +.bottom + mov bp,num1 ; + call PrintLine ; + dec dword [term] ; decrement loop counter + jnz .top ; +.done + call CRLF ; finish off with CRLF + mov ax,4c00h ; terminate + int 21h ; + + +;**************************************************************************** +; +; PrintLine +; prints a single line of output containing one term of the +; Fibonacci sequence. The first few lines look like this: +; +; Fibonacci(1): 1 +; Fibonacci(2): 1 +; Fibonacci(3): 2 +; Fibonacci(4): 3 +; +; INPUT: ds:bp ==> number string, cx = max string length +; OUTPUT: CF set on error, AX = error code if carry set +; DESTROYED: ax, bx, cx, dx, di +; +;**************************************************************************** +PrintLine: + mov dx,eol ; print combined CRLF and msg1 + mov cx,msg1len+eollen ; + call PrintString ; + + mov di,counter ; print counter + mov cx,cntDigits ; + call PrintNumericString + + call IncrementCount ; also increment the counter + + mov dx,msg2 ; print msg2 + mov cx,msg2len ; + call PrintString ; + + mov di,bp ; recall address of number + mov cx,digits ; + ; deliberately fall through to PrintNumericString + +;**************************************************************************** +; +; PrintNumericString +; prints the numeric string at DS:DI, suppressing leading zeroes +; max length is CX +; +; INPUT: ds:di ==> number string, cx = max string length +; OUTPUT: CF set on error, AX = error code if carry set +; DESTROYED: ax, bx, cx, dx, di +; +;**************************************************************************** +PrintNumericString: + ; first scan for the first non-zero byte + mov al,'0' ; look for ASCII zero + cld ; scan from MSD to LSD + repe scasb ; + mov dx,di ; points to one byte after + dec dx ; back up one character + inc cx ; + ; deliberately fall through to PrintString + +;**************************************************************************** +; +; PrintString +; prints the string at DS:DX with length CX to stdout +; +; INPUT: ds:dx ==> string, cx = string length +; OUTPUT: CF set on error, AX = error code if carry set +; DESTROYED: ax, bx +; +;**************************************************************************** +PrintString: + mov bx, 1 ; write to stdout + mov ah, 040h ; write to file handle + int 21h ; ignore return value + ret ; + +;**************************************************************************** +; +; AddNumbers +; add number 2 at ds:si to number 1 at es:di of width cx +; +; +; INPUT: es:di ==> number1, ds:si ==> number2, cx= max width +; OUTPUT: CF set on overflow +; DESTROYED: ax, si, di +; +;**************************************************************************** +AddNumbers: + std ; go from LSB to MSB + clc ; + pushf ; save carry flag +.top + mov ax,0f0fh ; convert from ASCII BCD to BCD + and al,[si] ; get next digit of number2 in al + and ah,[di] ; get next digit of number1 in ah + popf ; recall carry flag + adc al,ah ; add these digits + aaa ; convert to BCD + pushf ; + add al,'0' ; convert back to ASCII BCD digit + stosb ; save it and increment both counters + dec si ; + loop .top ; keep going until we've got them all + popf ; recall carry flag + ret ; + +;**************************************************************************** +; +; IncrementCount +; increments a multidigit term counter by one +; +; INPUT: none +; OUTPUT: CF set on overflow +; DESTROYED: ax, cx, di +; +;**************************************************************************** +IncrementCount: + mov cx,cntDigits ; + mov di,counter+cntDigits-1 + std ; go from LSB to MSB + stc ; this is our increment + pushf ; save carry flag +.top + mov ax,000fh ; convert from ASCII BCD to BCD + and al,[di] ; get next digit of counter in al + popf ; recall carry flag + adc al,ah ; add these digits + aaa ; convert to BCD + pushf ; + add al,'0' ; convert back to ASCII BCD digit + stosb ; save and increment counter + loop .top ; + popf ; recall carry flag + ret ; + +;**************************************************************************** +; +; CRLF +; prints carriage return, line feed pair to stdout +; +; INPUT: none +; OUTPUT: CF set on error, AX = error code if carry set +; DESTROYED: ax, bx, cx, dx +; +;**************************************************************************** +CRLF: mov dx,eol ; + mov cx,eollen ; + jmp PrintString ; + +;**************************************************************************** +; static data +;**************************************************************************** +eol db 13,10 ; DOS-style end of line +eollen equ $ - eol + +msg1 db 'Fibonacci(' ; +msg1len equ $ - msg1 + +msg2 db '): ' ; +msg2len equ $ - msg2 +;**************************************************************************** +; initialized data +;**************************************************************************** +term dd maxTerms ; +;**************************************************************************** +; unallocated data +; +; A better way to do this would be to actually ask for a memory +; allocation and use that memory space, but this is a DOS COM file +; and so we are given the entire 64K of space. Technically, this +; could fail since we *might* be running on a machine which doesn't +; have 64K free. If you're running on such a memory poor machine, +; my advice would be to not run this program. +; +;**************************************************************************** +; static data +counter: ; +num1 equ counter+cntDigits ; +num2 equ num1+digits ; \ No newline at end of file diff --git a/assembly/A utility to report free space on the default or selected disk drive.asm b/assembly/A utility to report free space on the default or selected disk drive.asm new file mode 100644 index 0000000..78e8cec --- /dev/null +++ b/assembly/A utility to report free space on the default or selected disk drive.asm @@ -0,0 +1,207 @@ +name free + page 60,132 + title 'FREE --- Report free space on disk' + +; FREE --- a utility to report free space on +; the default or selected disk drive. +; +; Requires PC-DOS or MS-DOS 2.0. +; +; Used in the form: +; A> FREE [unit:] +; (item in square brackets is optional) +; + +cr equ 0dh ;ASCII carriage return +lf equ 0ah ;ASCII line feed +blank equ 20h ;ASCII space code +eom equ '$' ;end of string marker + + +; Here we define a dummy segment containing labels +; for the default file control block and the command tail buffer, +; so that the main program can access those locations. +; +psp segment para public 'PSP' + + org 05ch +fcb label byte ;default file control block + + org 080h +command label byte ;default command buffer + +psp ends + + +cseg segment para public 'CODE' + + assume cs:cseg,ds:psp,es:data,ss:stack + + +get_drive proc near ;get drive selection, if any, + ;otherwise obtain the identity + ;of the current disk drive. + ;Return drive (1=A, 2=B, etc) in AL. + ; + mov al,fcb ;Pick up the drive code, parsed + ;by DOS into the default file + ;control block. + or al,al ;Is it the default? + jnz get_drive1 ;no, use it + mov ah,19h ;Yes, get the actual current + int 21h ;drive from PC-DOS. + inc al ;Increment to match FCB code. +get_drive1: ;Return drive code in AL. + ret +get_drive endp + + +free proc far ;entry point from PC-DOS + + push ds ;save DS:0000 for final + xor ax,ax ;return to PC-DOS + push ax + mov ax,data ;make our data segment + mov es,ax ;addressable via ES register. + mov ah,30h ;check version of PC-DOS. + int 21h + cmp al,2 + jae free1 ;proceed, DOS 2.0 or greater. + mov dx,offset msg2 ;DOS 1.x --- print error message + mov ax,es ;and exit. First fix up DS register + mov ds,ax ;so error message is addressable. + jmp free4 + +free1: call get_drive ;get drive selection into DL. + push es ;copy ES to DS for remainder + pop ds ;of the program... + assume ds:data ;and tell assembler about it. + mov dl,al + add al,'A'-1 ;form drive letter from drive code, + mov outputb,al ;and put it into the output string. + mov ah,36h ;now call DOS to get free disk space. + int 21h + cmp ax,-1 ;was drive invalid? + je free3 ;yes,go print error message + ;drive was ok, so now registers are... + ;AX=number of sectors per cluster + ;BX=available clusters, + ;CX=number of bytes per sector, + ;DX=total clusters per drive. + ;calculate free space: + mul cx ;sectors per cluster * bytes per sector + ;(we assume this won't overflow into DX) + mul bx ;then * available clusters + + ;DX:AX now contains free space in bytes. + ;SI = last byte address for converted string. + mov si,offset (outputa+9) + mov cx,10 ;CX = 10, radix for conversion + call bin_to_asc ;convert free space value to ASCII, + mov dx,offset output + jmp free4 ;and print it out. + +free3: mov dx,offset msg1 ;illegal drive, print error + +free4: mov ah,9 ;print the string whose address + int 21h ;is in DX. + ret ;then return to DOS. + +free endp + + +; Convert 32 bit binary value to ASCII string. +; +; Call with DX:AX = signed 32 bit value +; CX = radix +; SI = last byte of area to store resulting string +; (make sure enough room is available to store +; the string in the radix you have selected.) +; +; Destroys AX, BX, CX, DX, and SI. +; +bin_to_asc proc near ;convert DX:AX to ASCII. + ;force storage of at least 1 digit. + mov byte ptr [si],'0' + or dx,dx ;test sign of 32 bit value, + pushf ;and save sign on stack. + jns bin1 ;jump if it was positive. + not dx ;it was negative, take 2's complement + not ax ;of the value. + add ax,1 + adc dx,0 +bin1: ;divide the 32 bit value by the radix + ;to extract the next digit for the + ;forming string. + mov bx,ax ;is the value zero yet? + or bx,dx + jz bin3 ;yes, we are done converting. + call divide ;no, divide by radix. + add bl,'0' ;convert the remainder to an ASCII digit. + cmp bl,'9' ;we might be converting to hex ASCII, + jle bin2 ;jump if in range 0-9, + add bl,'A'-'9'-1 ;correct it if in range A-F. +bin2: mov [si],bl ;store this character into string. + dec si ;back up through string, + jmp bin1 ;and do it again. +bin3: ;restore sign flag, + popf ;was original value negative? + jns bin4 ;no, jump + ;yes,store sign into output string. + mov byte ptr [si],'-' +bin4: ret ;back to caller. +bin_to_asc endp + + +; General purpose 32 bit by 16 bit unsigned divide. +; This must be used instead of the plain machine unsigned divide +; for cases where the quotient may overflow 16 bits (for example, +; dividing 100,000 by 2). If called with a zero divisor, this +; routine returns the dividend unchanged and gives no warning. +; +; Call with DX:AX = 32 bit dividend +; CX = divisor +; +; Returns DX:AX = quotient +; BX = remainder +; CX = divisor (unchanged) +; +divide proc near ; Divide DX:AX by CX + jcxz div1 ; exit if divide by zero + push ax ; 0:dividend_upper/divisor + mov ax,dx + xor dx,dx + div cx + mov bx,ax ; BX = quotient1 + pop ax ; remainder1:dividend_lower/divisor + div cx + xchg bx,dx ; DX:AX = quotient1:quotient2 +div1: ret ; BX = remainder2 +divide endp + +cseg ends + + +data segment para public 'DATA' + +output db cr,lf +outputa db 10 dup (blank) + db ' bytes free on drive ' +outputb db 'x:',cr,lf,eom + +msg1 db cr,lf + db 'That disk drive does not exist.' + db cr,lf,eom + +msg2 db cr,lf + db 'Requires DOS version 2 or greater.' + db cr,lf,eom + +data ends + + +stack segment para stack 'STACK' + db 64 dup (?) +stack ends + + end free \ No newline at end of file diff --git a/assembly/Absolute Disk Read.asm b/assembly/Absolute Disk Read.asm new file mode 100644 index 0000000..fcca0ed --- /dev/null +++ b/assembly/Absolute Disk Read.asm @@ -0,0 +1,55 @@ +; +; Synopsis: int getsec(drive,numsec,begsec,buffer) +; unsigned int drive; /* 0=A, 1=B, etc. */ +; unsigned int numsec; /* Number of sectors to read */ +; unsigned int begsec; /* Beginning logical sector */ +; char *buffer; /* Transfer address */ +; +; Function: The number of sectors specified are transferred +; between the given drive and the transfer address. +; LOGICAL SECTOR NUMBERS are obtained by numbering +; each sector sequentially starting from track 0, head 0, +; sector 1 (logical sector 0) and continuing along the +; same head, then to the next head until the last sector +; on the last head of the track is counted. Thus, +; logical sector 1 is track 0, head 0, sector 2, +; logical sector 2 is track 0, head 0, sector 3, & so on. +; +; Returns: NULL if the operation is successful. +; otherwise, error codes are as follows: +; +; hex 80 Attachment failed to respond. +; hex 40 SEEK operation failed. +; hex 20 Controller failure. +; hex 10 Bad CRC on diskette read. +; hex 08 DMA overrun on operation. +; hex 04 Requested sector not found. +; hex 03 Write attempt on write-protected diskette. +; hex 02 Address mark not found. +; hex FF Unspecified (error other than those above). +; +code segment byte public ;segment registers remain intact + assume cs:code ;all other registers will be destroyed + public getsec + +getsec: push bp ;save old frame pointer + mov bp,sp ;get new frame pointer + mov ax,4[bp] ;put drive number into AL + xor ah,ah + mov cx,6[bp] ;number of sectors to fetch + mov dx,8[bp] ;logical record number of 1st sector + mov bx,10[bp] ;pointer to transfer address + int 25h ;BIOS call + jc error ;error has occurred if carry flag = 1 + mov al,00H ;NULL to indicate sucessful completion + jmp done +error: cmp al,00H ;detect unspecified error code 00H + jne done ;...change to 0FFh if found to + mov al,0FFH ;...differentiate it from success code +done: xor ah,ah ;return AL only + popf ;remove flags int 0x25 left on stack + pop bp ;restore original frame pointer + ret ;all done + +code ends + end \ No newline at end of file diff --git a/assembly/Alarm.asm b/assembly/Alarm.asm new file mode 100644 index 0000000..4237b4c --- /dev/null +++ b/assembly/Alarm.asm @@ -0,0 +1,373 @@ +cseg segment para public 'code' +org 100h +alarm proc far + +; Memory-resident program to intercept the timer interrupt and display the +; system time in the upper right-hand corner of the display. +; This program is run as 'ALARM hh:mm x', where hh:mm is the alarm time and +; x is '-' to turn the display off. Any other value of x or no value will +; turn the clock on + +intaddr equ 1ch*4 ; interrupt address +segaddr equ 62h*4 ; segment address of first copy +mfactor equ 17478 ; minute conversion factor * 16 +whozat equ 1234h ; signature +color equ 14h ; color attribute + + assume cs:cseg,ds:cseg,ss:nothing,es:nothing + jmp p150 ; start-up code + +jumpval dd 0 ; address of prior interrupt +signature dw whozat ; program signature +state db 0 ; '-' = off, all else = on +wait dw 18 ; wait time - 1 second or 18 ticks +hour dw 0 ; hour of the day +atime dw 0ffffh ; minutes past midnite for alarm +acount dw 0 ; alarm beep counter - number of seconds (5) +atone db 5 ; alarm tone - may be from 1 to 255 - the + ; higher the number, the lower the frequency +aleng dw 8080h ; alarm length (loop count) may be from 1-FFFF + +dhours dw 0 ; display hours + db ':' +dmins dw 0 ; display minutes + db ':' +dsecs dw 0 ; display seconds + db '-' +ampm db 0 ; 'A' or 'P' for am or pm + db 'm' + +tstack db 16 dup('stack ') ; temporary stack +estack db 0 ; end of stack +holdsp dw 0 ; original sp +holdss dw 0 ; original ss + +p000: ; interrupt code + push ax ; save registers + push ds + pushf + + push cs + pop ds ; make ds=cs + mov ax,wait ; check wait time + dec ax ; zero? + jz p010 ; yes - 1 second has elapsed + mov wait,ax ; not this time + jmp p080 ; return + +p010: cli ; disable interrupts + mov ax,ss ; save stack + mov holdss,ax + mov holdsp,sp + mov ax,ds + mov ss,ax ; point to internal stack + mov sp,offset estack + sti ; allow interrupts + + push bx ; save other registers + push cx + push dx + push es + push si + push di + push bp + + mov ax,18 ; reset wait time + mov wait,ax + + mov al,state ; are we disabled? + cmp al,'-' + jnz p015 ; no + jmp p070 + +p015: mov ah,0 ; read time + int 1ah ; get time of day + mov ax,dx ; low part + mov dx,cx ; high part + mov cl,4 + shl dx,cl ; multiply by 16 + mov bx,ax + mov cl,12 + shr bx,cl ; isolate top 4 bits of ax + add dx,bx ; now in upper + mov cl,4 + shl ax,cl ; multiply by 16 + mov bx,mfactor ; compute minutes + div bx ; minutes in ax, remainder in dx + cmp ax,atime ; time to sound the alarm? + jnz p020 ; no + call p100 ; yes - beep the speaker twice + push ax + mov ax,acount ; get beep count + dec ax ; down by 1 + mov acount,ax ; save beep count + cmp ax,0 ; is it zero? + jnz p018 ; no - keep alarm on + mov ax,0ffffh ; turn off alarm + mov atime,ax +p018: pop ax + +p020: mov dsecs,dx ; save remainder + mov bx,60 ; compute hours + xor dx,dx ; zero it + div bx ; hours in ax, minutes in dx + mov dmins,dx ; save minutes + + cmp ax,0 ; midnight? + jnz p030 ; no + mov ax,12 ; yes + jmp p040a ; set am + +p030: cmp ax,12 ; before noon? + jb p040a ; yes - set am + jz p040p ; noon - set pm + sub ax,12 ; convert the rest +p040p: mov bl,'p' + jmp p040x + +p040a: mov bl,'a' + +p040x: mov ampm,bl + aam ; fix up hour + cmp ax,hour ; top of the hour? + jz p060 ; no + + mov hour,ax + call p120 ; beep the speaker once + +p060: add ax,3030h ; convert hours to ascii + xchg ah,al + mov dhours,ax + + mov ax,dmins ; get minutes + aam + add ax,3030h ; convert to ascii + xchg ah,al + mov dmins,ax + + mov ax,dsecs ; get seconds (remainder) + xor dx,dx + mov bx,60 + mul bx + mov bx,mfactor + div bx ; seconds in ax + aam + add ax,3030h + xchg ah,al + mov dsecs,ax + + xor ax,ax ; check monitor type + mov es,ax + mov ax,es:[410h] ; get config byte + and al,30h ; isolate monitor type + cmp al,30h ; color? + mov ax,0b000h ; assume mono + jz p061 ; its mono + + mov ax,0b800h ; color screen address + +p061: mov dx,es:[463h] ; point to 6845 base port + add dx,6 ; point to status port + + mov es,ax ; point to monitor + mov bh,color ; color in bh + mov si,offset dhours ; point to time + mov di,138 ; row 1, col 69 + cld + mov cx,11 ; loop count + +p062: mov bl,[si] ; get next character + +p063: in al,dx ; get crt status + test al,1 ; is it low? + jnz p063 ; no - wait + cli ; no interrupts + +p064: in al,dx ; get crt status + test al,1 ; is it high? + jz p064 ; no - wait + + mov ax,bx ; move color & character + stosw ; move color & character again + sti ; interrupts back on + inc si ; point to next character + loop p062 ; done? + +p070: pop bp ; restore registers + pop di + pop si + pop es + pop dx + pop cx + pop bx + cli ; no interrupts + mov ax,holdss + mov ss,ax + mov sp,holdsp + sti ; allow interrupts + +p080: popf + pop ds + pop ax + jmp cs:[jumpval] + +p100 proc near ; beep the speaker twice + call p120 + push cx + mov cx,20000 +p105: loop p105 ; wait around + pop cx + call p120 + push cx + mov cx,20000 +p106: loop p106 ; wait around + pop cx + call p120 + ret +p100 endp + +p120 proc near ; beep the speaker once + push ax + push cx + mov al,182 + out 43h,al ; setup for sound + mov al,0 + out 42h,al ; low part + mov al,atone ; get alarm tone + out 42h,al ; high part + in al,61h + push ax ; save port value + or al,3 + out 61h,al ; turn speaker on + mov cx,aleng ; get loop count +p125: loop p125 ; wait around + pop ax ; restore original port value + out 61h,al ; turn speaker off + pop cx + pop ax + ret +p120 endp + +p150: ; start of transient code + mov dx,offset copyr + call p220 ; print copyright + mov ax,0 + mov es,ax ; segment 0 + mov di,segaddr+2 ; this program's prior location + mov ax,es:[di] ; get prior code segment + mov es,ax ; point to prior program segment + mov di,offset signature + mov cx,es:[di] ; is it this program? + cmp cx,whozat + jnz p160 ; no - install it + call p200 ; set state & alarm + int 20h ; terminate + +p160: mov di,segaddr+2 ; point to int 62h + mov ax,0 + mov es,ax ; segment 0 + mov ax,ds ; get current ds + mov es:[di],ax ; set int 62h + mov si,offset jumpval + mov di,intaddr ; point to timer interrupt + mov bx,es:[di] ; get timer ip + mov ax,es:[di+2] ; and cs + mov [si],bx ; save prior ip + mov [si+2],ax ; and cs + mov bx,offset p000 + mov ax,ds + cli ; clear interrupts + mov es:[di],bx ; set new timer interrupt + mov es:[di+2],ax + sti ; set interrupts + push ds + pop es + call p200 ; set state & alarm + mov dx,offset p150 ; last byte of resident portion + inc dx + int 27h ; terminate + +p200 proc near ; set state & alarm + mov si,80h ; point to command line + mov ax,0 + mov di,0ffffh ; init hours + mov bh,0 + mov ch,0 + mov dh,0 ; : counter + mov es:[state],bh ; turn clock on + mov cl,[si] ; get length + jcxz p210 ; it's zero + +p203: inc si ; point to next char + mov bl,[si] ; get it + cmp bl,'-' ; is it a minus? + jnz p204 ; no + mov es:[state],bl ; turn clock off + push dx + mov dx,offset msg3 ; print msg + call p220 + pop dx + jmp p206 + +p204: cmp dh,2 ; seen 2nd colon? + jz p206 ; yes - ignore seconds + cmp bl,':' ; colon? + jnz p205 ; no + inc dh + cmp dh,2 ; second colon? + jz p206 ; yes - ignore seconds + push cx + push dx + mov cx,60 + mul cx ; multiply current ax by 60 + pop dx + pop cx + mov di,ax ; save hours + mov ax,0 + jmp p206 +p205: cmp bl,'0' + jb p206 ; too low + cmp bl,'9' + ja p206 ; too high - can be a problem + sub bl,'0' ; convert it to binary + push cx + push dx + mov cx,10 + mul cx ; multiply current value by 10 + add ax,bx ; and add latest digit + pop dx + pop cx +p206: loop p203 ; done yet? + cmp di,0ffffh ; any time to set? + jz p210 ; no + add ax,di ; add hours + cmp ax,24*60 + jb p209 ; ok + mov dx,offset msg1 ; print error message + call p220 + jmp p210 + +p209: mov es:[atime],ax ; save minutes past midnight + mov ax,5 + mov es:[acount],ax ; set alarm count + mov dx,offset msg2 ; print set msg + call p220 +p210: ret +p200 endp + +p220 proc near ; print message + push ax + mov ah,9 + int 21h + pop ax + ret +p220 endp + +copyr db 'Alarm - Clock',10,13,'$' +msg1 db 'Invalid time - must be from 00:00 to 23:59',10,13,'$' +msg2 db 'Resetting alarm time',10,13,'$' +msg3 db 'Turning clock display off',10,13,'$' + +alarm endp +cseg ends +end alarm diff --git a/assembly/An implementation of SLIP (Serial Link IP), RFC 1055 in assembly language.asm b/assembly/An implementation of SLIP (Serial Link IP), RFC 1055 in assembly language.asm new file mode 100644 index 0000000..4443808 --- /dev/null +++ b/assembly/An implementation of SLIP (Serial Link IP), RFC 1055 in assembly language.asm @@ -0,0 +1,147 @@ +; slip.asm +; +; This is an 8086+ implementation of SLIP (RFC 1055) +; +; It may be assembled using Microsoft's MASM using the command line: +; ml -Fl -c slip.asm +; +; or using Borland's TASM using the command line: +; tasm -la -m2 -jLOCALS slip.asm +; + .model small + .stack 100h + .data +SLIP_END equ 0C0h +SLIP_ESC equ 0DBh +SLIP_ESC_END equ 0DCh +SLIP_ESC_ESC equ 0DDh + +; note that these are both sample macros and are very simple +; In both cases, DX is assumed to already be pointing to the +; appropriate I/O port and a character is always assumed to +; be ready. +SEND_CHAR macro char + IFDIFI , + mov al,char + ENDIF + out dx,al +endm + +RECV_CHAR macro + in al,dx +endm + .code +;**************************************************************************** +; send_packet +; +; sends the passed packet (which is in a memory buffer) to the output +; device by using the macro SEND_CHAR() which must be defined by the +; user. A sample SEND_CHAR() is defined above. +; +; Entry: +; DS:SI ==> raw packet to be sent +; CX = length of raw packet to be sent +; direction flag is assumed to be cleared (incrementing) +; +; Exit: +; +; +; Trashed: +; none +; +;**************************************************************************** +send_packet proc + push cx + push si + SEND_CHAR SLIP_END ; send an end char to flush any garbage + jcxz @@bailout ; if zero length packet, bail out now +@@nextchar: + lodsb ; load next char + cmp al,SLIP_END ; Q: is it the special END char? + jne @@check_esc ; N: check for ESC + SEND_CHAR SLIP_ESC ; Y: send ESC + ESC_END instead + mov al,SLIP_ESC_END ; + jmp @@ordinary ; + +@@check_esc: + cmp al,SLIP_ESC ; Q: is it the special ESC char? + jne @@ordinary ; N: send ordinary char + SEND_CHAR SLIP_ESC ; Y: send ESC + ESC_END instead + mov al,SLIP_ESC_ESC ; + ; fall through to ordinary character + +@@ordinary: + SEND_CHAR al ; + + loop @@nextchar ; keep going until we've sent all chars +@@bailout: + SEND_CHAR SLIP_END ; send an end char to signal end of packet + pop si + pop cx + ret +send_packet endp + +;**************************************************************************** +; recv_packet +; +; receives a packet using the macro RECV_CHAR() which must be defined by +; the user and places the received packet into the memory buffer pointed +; to by ES:DI. The final length is returned in BX. +; +; Note that in the case of a buffer overrun, the portion of the packet +; that fit into the buffer is returned and BX and CX are equal. There +; is no way to tell the difference between a packet that just exactly +; fit and one which was truncated due to buffer overrun, so it is +; important to assure that the buffer is big enough to ALWAYS contain +; at least one spare byte. +; +; A sample RECV_CHAR() is defined above. +; +; Entry: +; ES:DI ==> packet buffer +; CX = length of buffer +; direction flag is assumed to be cleared (incrementing) +; +; Exit: +; BX = length of packet received +; +; Trashed: +; none +; +;**************************************************************************** +recv_packet proc + push cx + push di + xor bx,bx ; zero received byte count + jcxz @@bailout ; if zero length packet, bail out now +@@nextchar: + RECV_CHAR ; fetch a character into al + cmp al,SLIP_END ; Q: is it the special END char? + jne @@check_esc ; N: check for ESC + or bx,bx ; YQ: is it the beginning of packet? + jz @@nextchar ; Y: keep looking + jmp @@bailout ; N: end of packet, so return it + +@@check_esc: + cmp al,SLIP_ESC ; Q: is it the special ESC char? + jne @@ordinary ; N: it's an ordinary char + RECV_CHAR ; Y: get another character + cmp al,SLIP_ESC_END ; Q: is it ESC_END? + jne @@check_esc_esc ; N: check for ESC_ESC + mov al,SLIP_END ; Y: convert to ordinary END char + jmp @@ordinary ; +@@check_esc_esc: + cmp al,SLIP_ESC_ESC ; Q: is it ESC_ESC? + mov al,SLIP_ESC ; Y: convert to ordinary ESC char + ; protocol violation! fall through to ordinary character + +@@ordinary: + stosb ; store character in buffer + inc bx ; got another char + loop @@nextchar ; keep going until we've sent all chars +@@bailout: + pop di + pop cx + ret +recv_packet endp + END \ No newline at end of file diff --git a/assembly/Assembly language program which shows the current date and time in a form identical to that used by Posix ctime() .asm b/assembly/Assembly language program which shows the current date and time in a form identical to that used by Posix ctime() .asm new file mode 100644 index 0000000..4119e25 --- /dev/null +++ b/assembly/Assembly language program which shows the current date and time in a form identical to that used by Posix ctime() .asm @@ -0,0 +1,325 @@ +; showdate.asm +; +; prints the date and time to stdout +; equivalent to the following C++ program: +; +;#include +;#include +; +;int main() +;{ +; time_t t; +; time(&t); // get the current time +; cout << ctime(&t); // convert to string and print +; return 0; +;} +; +; This code may be assembled and linked using Borland's TASM: +; tasm /la /m2 showdate +; tlink /Tdc showdate +; +STDOUT equ 01h ; handle of standard output device + +DOS_GET_DATE equ 02ah ; get system date +DOS_GET_TIME equ 02ch ; get system time +DOS_WRITE_HANDLE equ 040h ; write to handle +DOS_TERMINATE equ 04ch ; terminate with error code + +DOSINT macro function, subfunction + IFB + mov ah,(function AND 0ffh) + ELSE + mov ax,(function SHL 8) OR (subfunction AND 0ffh) + ENDIF + int 21h ; invoke DOS function +endm + + +MODEL tiny +;.STACK 100h +.CODE + +;**************************************************************************** +; main +; +; calls showdate routne and exists with 00 error code +; +; Entry: +; +; Exit: +; +; Trashed: +; none +; +;**************************************************************************** +main proc far + .STARTUP ; sets up DS and stack + call showdate ; + .EXIT 0 ; return with errcode=0 +main endp + +;**************************************************************************** +; showdate +; +; fetches the DOS system date, prints it to stdout and exits +; the format of the output is identical to that of the Posix ctime() +; function: +; +; Thu May 11 16:11:30 2000 +; +; The day of week and month are always 3 characters long. The time of +; day is in 24hour form (e.g. 16:11:30 is a few minutes after four in +; the afternoon) and the year is always four digits. The whole thing is +; followed by a newline character (line feed = 0ah), making 25 +; characters total. +; +; Note that ctime() returns 26 characters which is all of the above, +; followed by a terminating NUL char but this program does not emit a +; NUL.) +; +; Entry: +; DS points to segment for our data tables +; +; Exit: +; carry may be set if last write failed +; +; Trashed: +; none +; +;**************************************************************************** +showdate proc + push ax bx cx dx ; + DOSINT DOS_GET_DATE ; +; returns the following +; cx = year (1980-2099) +; dh = month (1-12) == (Jan..Dec) +; dl = day (1-31) +; al = day of week (0-6) == (Sun..Sat) + + push cx ; + push dx ; save the return values + + ; write the day of week + mov dx, offset dayname ; + mov cx,3 ; number of bytes to write + call WriteSubstring ; + + ; write the month + pop ax ; recall month/day + push ax ; and save it again + mov al,ah ; isolate just month + mov dx, offset monthname - 3 ; monthname array is 1-based + mov cx,3 ; number of bytes to write + call WriteSubstring ; + + ; write the day of the month + pop ax ; + call WriteNumber ; + call WriteSpace ; + + ; write the hour + DOSINT DOS_GET_TIME ; ch = hour, cl = min, + ; dh = sec, dl = hundredths + + push dx ; save seconds + push cx ; save minutes + mov al,ch ; + call WriteNumber ; + call WriteColon ; + + ; write the minutes + pop ax ; + call WriteNumber ; + call WriteColon ; + + ; write the seconds + pop ax ; + mov al,ah ; + call WriteNumber ; + call WriteSpace ; + + ; write the year (century first) + pop ax ; + xor dx,dx ; clear other reg before divide + mov cx,100 ; ax = ax/100, dx = remainder + div cx ; + push dx ; save remainder + call WriteNumber ; + + ; write the year (year within century) + pop ax ; + call WriteNumber ; + mov dx,offset newlinechar + call PrintOne ; + pop dx cx bx ax ; restore stack + ret ; +showdate endp + +;**************************************************************************** +; WriteSubstring +; +; writes a short substring to stdout +; specifically, prints CL characters, starting at DS:(DX+CL*AL) +; +; Entry: +; DS:DX ==> pointer to base of string array +; CL = size of each string +; AL = string selector (i.e. which string) +; +; Exit: +; CY set if there was an error writing last byte +; if CY clear, +; AX = 1 (number of bytes written) +; else +; AX = error code +; +; Trashed: +; BX CX DX +; +;**************************************************************************** +WriteSubstring proc + mul cl ; ax = cl * al + add dx,ax ; offset now points to appropriate day string + call PrintIt ; +WriteSubstring endp + ; deliberately fall through +;**************************************************************************** +; WriteSpace +; +; writes a single space character (20h) to stdout +; +; Entry: +; DS points to data table segment +; +; Exit: +; CY set if there was an error writing last byte +; if CY clear, +; AX = 1 (number of bytes written) +; else +; AX = error code +; +; Trashed: +; BX CX DX +; +;**************************************************************************** +WriteSpace proc + mov dx,offset spacechar; +WriteSpace endp + ; deliberately fall through +;**************************************************************************** +; PrintOne +; +; prints a single character pointed to by DS:DX +; +; Entry: +; DS:DX ==> points to the character to be printed +; +; Exit: +; CY set if there was an error writing last byte +; if CY clear, +; AX = 1 (number of bytes written) +; else +; AX = error code +; +; Trashed: +; BX CX DX +; +;**************************************************************************** +PrintOne proc + mov cx,1 ; +PrintOne endp + ; deliberately fall through +;**************************************************************************** +; PrintIt +; +; prints the passed string to stdout +; +; Entry: +; DS:DX ==> points to string to be printed +; CX = number of bytes to be printed +; +; Exit: +; CY set if there was an error writing to stdout +; if CY clear, +; AX = number of bytes written +; else +; AX = error code +; +; Trashed: +; none +; +;**************************************************************************** +PrintIt proc + mov bx,STDOUT ; + DOSINT DOS_WRITE_HANDLE ; write to the file + ret ; +PrintIt endp + +;**************************************************************************** +; WriteColon +; +; writes a colon character to stdout +; +; Entry: +; DS points to data segment +; +; Exit: +; CY set if there was an error writing to stdout +; if CY clear, +; AX = 1 (number of bytes written) +; else +; AX = error code +; +; Trashed: +; none +; +;**************************************************************************** +WriteColon proc + mov dx,offset colonchar; + jmp PrintOne ; +WriteColon endp + +;**************************************************************************** +; WriteNumber +; +; prints the number in AL to stdout as two decimal digits +; +; Entry: +; AL = number to be printed. It must be in the range 00-99 +; +; Exit: +; CY set if there was an error writing to stdout +; if CY clear, +; AX = 2 (number of bytes written) +; else +; AX = error code +; +; Trashed: +; BX CX DX +; +;**************************************************************************** +WriteNumber proc + xor ah,ah ; clear out high half + mov cl,10 ; prepare to convert to decimal (base 10) + div cl ; divide it out + or ax,3030h ; convert to ASCII digits + push ds ; remember DS for later + push ax ; push converted chars on stack + mov dx,ss ; + mov ds,dx ; ds = ss + mov dx,sp ; print data from stack + mov cx,2 ; two characters only + call PrintIt ; + pop bx ; fix stack + pop ds ; restore ds pointer + ret ; +WriteNumber endp + +;.DATA + dayname db "SunMonTueWedThuFriSat" + monthname db "JanFebMarAprMayJunJulAugSepOctNovDec" + spacechar db " " + colonchar db ":" + newlinechar db 0ah ; in C this is \n + +end \ No newline at end of file diff --git a/assembly/BIOS-based disk I-O to access MS-DOS file structure.asm b/assembly/BIOS-based disk I-O to access MS-DOS file structure.asm new file mode 100644 index 0000000..22a1c82 --- /dev/null +++ b/assembly/BIOS-based disk I-O to access MS-DOS file structure.asm @@ -0,0 +1,350 @@ +; rawread.asm +; +; this program reads a DOS cluster using only BIOS disk calls. All +; of the tasks usually done by DOS, e.g. FAT lookup, cluster to +; logical sector translation, logical to physical translation, are +; all done by this program instead. The idea is to be able to create +; a program that can access DOS disks from a bootable floppy without +; having to have DOS. +; +; well, that's what it used to do. Now it's supposed to do something +; completely different. Its job is to scan the entire surface of the +; hard drive, looking for the specified string. If that string is +; found, it is to print the full path and directory entry, including +; the file date and time. +; +; but wait! There's more. Now what we have is a number of raw +; routines which could prove useful for manipulating a DOS file +; structure outside of the DOS environment. The main routine still +; should be kept (if renamed), since the order in which these things +; are done is important (e.g. later calls depend on data set up by +; earlier calls). +; +; get filename +; parse filename into subdirs +; locate root dir and cluster size +; follow subdir routing to filename +; report file size, date & time +; + .MODEL small + .STACK 0200h + .586P + + .DATA +PartEntry STRUC + Bootable db ? ;80h = bootable, 00h = nonbootable + BeginHead db ? ;beginning head + BeginSector db ? ;beginning sector + BeginCylinder db ? ;beginning cylinder + FileSystem db ? ;name of file system + EndHead db ? ;ending head + EndSector db ? ;ending sector + EndCylinder db ? ;ending cylinder + StartSector dd ? ;starting sector (relative to beg. of disk) + PartSectors dd ? ;number of sectors in partition +PartEntry ENDS + +BootSector STRUC + Jump db ? ;E9 xx xx or EB xx 90 + JumpTarget dw ? ;E9 xx xx or EB xx 90 + OemName db '????????' ;OEM name & version + ;Start of BIOS parameter block + BytesPerSec dw ? ;bytes per sector + SecPerClust db ? ;sectors per cluster + ResSectors dw ? ;number of reserved sectors + FATs db ? ;number of file allocation tables + RootDirEnts dw ? ;number of root-dir entries + Sectors dw ? ;total number of sectors + Media db ? ;media descriptor byte + FATsecs dw ? ;number of sectors per FAT + SecPerTrack dw ? ;sectors per track + Heads dw ? ;number of heads + HiddenSecs dd ? ;number of hidden sectors + HugeSectors dd ? ;num sectors if Sectors==0 + ;End of BIOS parameter block +BootSector ENDS + +DirEntry STRUC + FileName db '????????' ;name + Extension db '???' ;extension + Attributes db ? ;attributes + Reserved db 10 dup (?) ;reserved + Time dw ? ;time stamp + Date dw ? ;date stamp + StartCluster dw ? ;starting cluster + FileSize dd ? ;file size +DirEntry ENDS + +BootFileName db "CONFIG SYS" ;the boot loader for this OS +MBR DB 0200h DUP (?) +buff DB 0200h * 40h DUP (?) +ClustOffs dd ? + +CR EQU 0DH +LF EQU 0AH + + + .CODE +main PROC + STARTUPCODE ;initialize stuff + call FetchMBR C ;fetch the master boot record + jc @@exit + mov cx,4 ;search up to four partitions + add bx,01aeh ;point to partition table (-10h) +@@FindBootable: + add bx,10h ;point to next entry + cmp BYTE ptr [bx],80h ;is it a bootable partition? + loopnz @@FindBootable + call FetchSector C, \ + WORD ptr [(PartEntry PTR bx).BeginHead], \ + WORD ptr [(PartEntry PTR bx).BeginSector], \ + WORD ptr [(PartEntry PTR bx).BeginCylinder], \ + OFFSET MBR, ds ;SEG MBR +; +; here's the point at which our OS loader would begin, with the +; BootSector structure in memory. +; + mov bx, OFFSET MBR + call CalcClustOff C, \ + WORD ptr [(BootSector PTR bx).ResSectors], \ + WORD ptr [(BootSector PTR bx).FATsecs], \ + WORD ptr [(BootSector PTR bx).FATs], \ + WORD ptr [(BootSector PTR bx).RootDirEnts], \ + WORD ptr [(BootSector PTR bx).BytesPerSec], \ + WORD ptr [(BootSector PTR bx).SecPerClust] + mov WORD ptr [ClustOffs],ax + mov WORD ptr [ClustOffs+2],dx + call CalcClust2 C, \ + WORD ptr [(BootSector PTR bx).ResSectors], \ + WORD ptr [(BootSector PTR bx).FATsecs], \ + WORD ptr [(BootSector PTR bx).FATs] + ; now dx:ax contains the logical sector for cluster 2 + call LsectToGeom C, \ + ax, dx, \ + WORD ptr [(BootSector PTR bx).HiddenSecs] , \ + WORD ptr [((BootSector PTR bx).HiddenSecs)+2],\ + [(BootSector PTR bx).Heads], \ + [(BootSector PTR bx).SecPerTrack] + + mov dl,80h + mov bx,offset buff + mov al,[(BootSector PTR MBR).SecPerClust] + mov ah,2h ; get ready to read + int 13h + ; now find our desired filename within buffer (which has the root dir) + + call FindFile C, \ + bx, 200h * 40h, offset BootFileName + xor dh,dh + mov dl,[(BootSector PTR MBR).SecPerClust] + mov si,ax + mov ax,[(DirEntry PTR si).StartCluster] + mul dx + add ax,WORD ptr [ClustOffs] + adc dx,WORD ptr [ClustOffs+2] + ; now dx:ax contains logical sector number for start of file + + call LsectToGeom C, \ + ax, dx, \ + WORD ptr [(BootSector PTR MBR).HiddenSecs] , \ + WORD ptr [((BootSector PTR MBR).HiddenSecs)+2],\ + [(BootSector PTR MBR).Heads], \ + [(BootSector PTR MBR).SecPerTrack] + mov dl,80h + mov ax,204h ; read in 2k worth of data + int 13h + +@@exit: + EXITCODE ;exit to DOS +ENDP main + +; +; FetchMBR - fetches the Master Boot Record from the first physical +; hard disk and stores it in the location MBR. +; +; INPUT: none +; OUTPUT: AX is error code if CY set, ES:BX ==> MBR +; DESTROYED: none +; +FetchMBR PROC C + USES cx, dx ;save registers we'll use + mov dx,80h ;first physical disk + mov cx,1 ;head 1, sector 0 + mov bx,ds ; + mov es,bx ;point to boot record buffer + mov bx,OFFSET MBR ;read into boot record + mov ax,0201h ;read one sector + int 13h ;BIOS read + ret ;return to main +FetchMBR ENDP + +; +; FetchSector - fetches the physical sector described by the passed +; parameters and stores it in the named buffer +; +; INPUT: head, sector, cylinder, buffer +; OUTPUT: AX is error code if CY set, ES:BX ==> Boot +; DESTROYED: none +; +FetchSector PROC C head:BYTE, sector:BYTE, cylinder:BYTE, buffer:DWORD + USES cx, dx ;save registers we'll use + mov ch, [cylinder] ; + mov cl, [sector] ; + mov dh, [head] ; + mov dl, 80h ;first physical hard drive + les bx, [buffer] ; + mov ax,0201h ;read one sector + int 13h ;BIOS read + ret ;return to main +FetchSector ENDP + +; +; GeomToLsect - converts to logical sector number from the physical +; geometry (head, cylinder, track). See LsectToGeom. +; +; INPUT: cx, dx are set with cylinder/track, and head respectively +; HiddenSecs, Heads, SecPerTrack +; OUTPUT: lsect +; DESTROYED: none +; +GeomToLsect PROC C lsect:DWORD, dHiddenSecs:DWORD, \ + dHeads:WORD, dSecPerTrack:WORD, buffer:DWORD + USES ax ;save registers we'll use + mov ax, WORD ptr [lsect] ;load lsect into DX:AX + mov dx, WORD ptr [lsect+2] ; + stc ;add one additional + adc ax, WORD ptr [dHiddenSecs] ;add starting sector + adc dx, WORD ptr [dHiddenSecs+2] ; + div [dSecPerTrack] ; + mov cl,dl ;store sector in cl + xor dx,dx ; + div [dHeads] ; + mov dh,dl ;store head in dh + mov ch,al ;store low 8 bits of cylinder in ch + shr ax,1 ; + shr ax,1 ; + and al,0c0h ;pass through two hi bits only + or cl,ah ;mov bits into location + ret ; +GeomToLsect ENDP + +; +; LsectToGeom - converts from logical sector number to the physical +; geometry (head, cylinder, track) in the form required +; by the BIOS (Int 13h) disk read and write calls. +; +; INPUT: lsect, HiddenSecs, Heads, SecPerTrack +; OUTPUT: cx, dx are set with cylinder/track, and head respectively +; DESTROYED: none +; +LsectToGeom PROC C lsect:DWORD, lHiddenSecs:DWORD, \ + lHeads:WORD, lSecPerTrack:WORD, buffer:DWORD + USES ax ;save registers we'll use + mov ax, WORD ptr [lsect] ;load lsect into DX:AX + mov dx, WORD ptr [lsect+2] ; + stc ;add one additional + adc ax, WORD ptr [lHiddenSecs] ;add starting sector + adc dx, WORD ptr [lHiddenSecs+2] ; + div [lSecPerTrack] ; + mov cl,dl ;store sector in cl + xor dx,dx ; + div [lHeads] ; + mov dh,dl ;store head in dh + mov ch,al ;store low 8 bits of cylinder in ch + shr ax,1 ; + shr ax,1 ; + and al,0c0h ;pass through two hi bits only + or cl,ah ;mov bits into location + ret ; +LsectToGeom ENDP + +; +; CalcClust2 - calculates the starting logical sector number of +; cluster 2, (the beginning of data space for +; partitions). +; +; INPUT: ResSectors, FATsecs, FATs +; OUTPUT: dx:ax contains the starting logical sector number +; DESTROYED: none +; +CalcClust2 PROC C cResSectors:WORD, cFATsecs:WORD, cFATs:BYTE + xor dx,dx ; + mov ax,[cFATsecs] ; + mul [cFATs] ; + add ax,[cResSectors] ; + adc dx,0 ; + ret +CalcClust2 ENDP + +; +; CalcClustOff - calculates the starting logical sector number of +; cluster 0, which isn't really a cluster, but the +; number returned is useful for calculations converting +; cluster number to logical sector +; +; INPUT: ResSectors, FATsecs, FATs +; OUTPUT: dx:ax contains the starting logical sector number +; DESTROYED: none +; +CalcClustOff PROC C dResSectors:WORD, dFATsecs:WORD, dFATs:BYTE, \ + dRootDirEnts:WORD, dBytesPerSec:WORD, dSecPerClust:BYTE + LOCAL clustLo:WORD, clustHi:WORD + xor dh,dh + mov ax,[dFatSecs] + mov dl,[dFATs] + mul dx + add ax,[dResSectors] + adc dx,0 +; call CalcClust2 C, [dResSectors], [dFATsecs], [dFATs] + ; now dx:ax = FATs * FATsecs + ResSectors + mov [clustLo],ax + mov [clustHi],dx + mov dx,20h ; bytes per dir entry + mov ax,[dRootDirEnts] ; + mul dx ; multiply 'em out + div [dBytesPerSec] ; and divide by bytes/sec + add [clustLo],ax ; + adc [clustHi],dx ; create the aggregate + mov al,[dSecPerClust] ; + xor ah,ah ; + shl ax,1 ; AX = SecPerClust * 2 + sub [clustLo],ax ; + sbb [clustHi],0 ; propagate carry flag + mov ax,[clustLo] ; + mov dx,[clustHi] ; + ret +CalcClustOff ENDP + +; +; FindFile - given a memory buffer containing the directory data +; and a static file name for which to search, this routine +; finds the file and returns a pointer to its directory +; entry in ds:si +; +; INPUT: dirbuffer, filespec +; OUTPUT: ax contains pointer to directory entry (or NULL) +; DESTROYED: none +; +FindFile PROC C dirbuffer:WORD, limit:WORD, filespec:WORD + USES cx, dx, di, si, es + mov cx,ds ; + mov es,cx ; es and ds point to same segment + cld ; always count forward + mov ax,[dirbuffer] ; load 'em up + add [limit],ax + mov dx,[filespec] ; +keepsearching: + mov cx,11 ; size of dos filename (8.3) + mov si,dx ; + mov di,ax ; + repe cmpsb ; compare 'em + jz foundit ; + add ax,20h ; size of directory entry + cmp ax,[limit] + jb keepsearching + xor ax,ax + +foundit: + ret +FindFile ENDP + END \ No newline at end of file diff --git a/assembly/Boot loader for a roll-your-own operating system.asm b/assembly/Boot loader for a roll-your-own operating system.asm new file mode 100644 index 0000000..82ecfc3 --- /dev/null +++ b/assembly/Boot loader for a roll-your-own operating system.asm @@ -0,0 +1,267 @@ +; loader.asm + +PartEntry STRUC + Bootable db ? ;80h = bootable, 00h = nonbootable + BeginHead db ? ;beginning head + BeginSector db ? ;beginning sector + BeginCylinder db ? ;beginning cylinder + FileSystem db ? ;name of file system + EndHead db ? ;ending head + EndSector db ? ;ending sector + EndCylinder db ? ;ending cylinder + StartSector dd ? ;starting sector (relative to beg. of disk) + PartSectors dd ? ;number of sectors in partition +PartEntry ENDS + +BootSector STRUC + bsJump db 0EBh, (extra - bsJump), 090h + ; E9 XX XX or EB xx 90 + OemName db 8 dup (?) ; OEM name and version + ; start of BIOS parameter block + BytesPerSec dw ? ; bytes per sector + SecPerClust db ? ; sectors per cluster + ResSectors dw ? ; number of reserved sectors + FATs db ? ; number of FATs + RootDirEnts dw ? ; number of root directory entries + Sectors dw ? ; total number of sectors (see HugeSectors) + Media db ? ; media descriptor byte (0f0h for floppies) + FATsecs dw ? ; number of sectors per FAT + SecPerTrack dw ? ; sectors per track + Heads dw ? ; number of heads + HiddenSecs dd ? ; number of hidden sectors + HugeSectors dd ? ; number of sectors if Sectors equals 0 + ; end of BIOS parameter block + DriveNumber db ? ; + Reserved1 db ? ; + BootSignature db ? ; + VolumeID dd ? ; + VolumeLabel db 11 dup (?) + FileSysType db 8 dup (?) + extra dw ? +BootSector ENDS + +DirEntry STRUC + FileName db '????????' ;name + Extension db '???' ;extension + Attributes db ? ;attributes + Reserved db 10 dup (?) ;reserved + Time dw ? ;time stamp + Date dw ? ;date stamp + StartCluster dw ? ;starting cluster + FileSize dd ? ;file size +DirEntry ENDS + +CR EQU 0DH +LF EQU 0AH + +yonder segment para public use16 at 2000h + org 0h + destination proc far + destination endp +yonder ends + + +code segment para public use16 '_CODE' + .386 + assume cs:code, ds:code, es:code, ss:code + org 7c00h +main PROC +MBR: +Boot bootsector < ,'BEROSET ',512,1,1,2,224,2880,0f0h,9,18,2,\ + 0,0,0,0,29h,02a04063ch,'BEROSET 001',\ + 'FAT12 ',07df1h> +over: + mov ax,cs ; + cli + mov ss,ax ; point ss:sp to CS:7c00h + mov sp,7c00h ; which sets up a stack in first 64K + sti + mov ds,ax + mov es,ax +;**************************************************************************** +; +; CalcClustOff - calculates the starting logical sector number of +; cluster 0, which isn't really a cluster, but the +; number returned is useful for calculations converting +; cluster number to logical sector +; +; INPUT: ResSectors, FATsecs, FATs +; OUTPUT: dx:ax contains the starting logical sector number +; DESTROYED: none +; +;**************************************************************************** +CalcClustOff PROC + xor dh,dh + mov ax,[Boot.FatSecs] + mov dl,[Boot.FATs] + mul dx + add ax,[Boot.ResSectors] + adc dx,0 + ; now dx:ax = FATs * FATsecs + ResSectors + mov word ptr [ClustOffs],ax + mov word ptr [ClustOffs+2],dx + mov dx,20h ; bytes per dir entry + mov ax,[Boot.RootDirEnts] + mul dx ; multiply 'em out + div word ptr [Boot.BytesPerSec] ; and divide by bytes/sec + add word ptr [ClustOffs],ax + adc word ptr [ClustOffs+2],dx ; create the aggregate + mov al,[Boot.SecPerClust] ; + xor ah,ah ; + shl ax,1 ; AX = SecPerClust * 2 + sub word ptr [ClustOffs],ax ; + sbb word ptr [ClustOffs+2],0 ; propagate carry flag +; mov ax,word ptr [ClustOffs] ; +; mov dx,word ptr [ClustOffs+2] ; +; ret +CalcClustOff ENDP + +; mov WORD ptr [ClustOffs],ax +; mov WORD ptr [ClustOffs+2],dx + mov bx,offset Boot + call CalcClust2 C, \ + WORD ptr [(BootSector PTR bx).ResSectors], \ + WORD ptr [(BootSector PTR bx).FATsecs], \ + WORD ptr [(BootSector PTR bx).FATs] + ; now dx:ax contains the logical sector for cluster 2 + call LsectToGeom C, \ + WORD ptr [(BootSector PTR bx).HiddenSecs] , \ + WORD ptr [((BootSector PTR bx).HiddenSecs)+2],\ + [(BootSector PTR bx).Heads], \ + [(BootSector PTR bx).SecPerTrack] + + mov dl,[(BootSector PTR bx).DriveNumber] + mov bx,offset buff +retry1: + mov al,[(BootSector PTR MBR).SecPerClust] + mov ah,2h ; get ready to read + int 13h + jc retry1 + ; now find our desired filename within buffer (which has the root dir) + + call FindFile C, \ + bx, 200h * 40h, offset BootFileName + xor dh,dh + mov dl,[(BootSector PTR MBR).SecPerClust] + mov si,ax + mov ax,[(DirEntry PTR si).StartCluster] + mul dx + add ax,WORD ptr [ClustOffs] + adc dx,WORD ptr [ClustOffs+2] + ; now dx:ax contains logical sector number for start of file + + call LsectToGeom C, \ + WORD ptr [(BootSector PTR MBR).HiddenSecs] , \ + WORD ptr [((BootSector PTR MBR).HiddenSecs)+2],\ + [(BootSector PTR MBR).Heads], \ + [(BootSector PTR MBR).SecPerTrack] +retry2: + mov si,offset Boot + mov dl,[(BootSector PTR si).DriveNumber] + mov ah,2h + ; read in a cluster's worth of data + mov al,[(BootSector PTR si).SecPerClust] + ; point to our magic location + mov bx,seg destination + mov es,bx + mov bx,offset destination + int 13h + jc retry2 +@@exit: + jmp destination +ENDP main + +;**************************************************************************** +; +; LsectToGeom - converts from logical sector number to the physical +; geometry (head, cylinder, track) in the form required +; by the BIOS (Int 13h) disk read and write calls. +; +; INPUT: dx:ax=lsect, HiddenSecs, Heads, SecPerTrack +; OUTPUT: cx, dx are set with cylinder/track, and head respectively +; DESTROYED: none +;**************************************************************************** +LsectToGeom PROC C lHiddenSecs:DWORD, \ + lHeads:WORD, lSecPerTrack:WORD, buffer:DWORD + USES ax ;save registers we'll use + stc ;add one additional + adc ax, WORD ptr [lHiddenSecs] ;add starting sector + adc dx, WORD ptr [lHiddenSecs+2] ; + div [lSecPerTrack] ; + mov cl,dl ;store sector in cl + xor dx,dx ; + div [lHeads] ; + mov dh,dl ;store head in dh + mov ch,al ;store low 8 bits of cylinder in ch + shr ax,1 ; + shr ax,1 ; + and al,0c0h ;pass through two hi bits only + or cl,ah ;mov bits into location + ret ; +LsectToGeom ENDP + +;**************************************************************************** +; +; CalcClust2 - calculates the starting logical sector number of +; cluster 2, (the beginning of data space for +; partitions). +; +; INPUT: ResSectors, FATsecs, FATs +; OUTPUT: dx:ax contains the starting logical sector number +; DESTROYED: none +; +;**************************************************************************** +CalcClust2 PROC C cResSectors:WORD, cFATsecs:WORD, cFATs:BYTE + xor dx,dx ; + mov ax,[cFATsecs] ; + mul [cFATs] ; + add ax,[cResSectors] ; + adc dx,0 ; + ret +CalcClust2 ENDP + +;**************************************************************************** +; +; FindFile - given a memory buffer containing the directory data +; and a static file name for which to search, this routine +; finds the file and returns a pointer to its directory +; entry in ds:si +; +; INPUT: dirbuffer, filespec +; OUTPUT: ax contains pointer to directory entry (or NULL) +; DESTROYED: none +;**************************************************************************** + +FindFile PROC C dirbuffer:WORD, limit:WORD, filespec:WORD + USES cx, dx, di, si, es + mov cx,ds ; + mov es,cx ; es and ds point to same segment + cld ; always count forward + mov ax,[dirbuffer] ; load 'em up + add [limit],ax + mov dx,[filespec] ; +keepsearching: + mov cx,11 ; size of dos filename (8.3) + mov si,dx ; + mov di,ax ; + repe cmpsb ; compare 'em + jz foundit ; + add ax,20h ; size of directory entry + cmp ax,[limit] + jb keepsearching + xor ax,ax + +foundit: + ret +FindFile ENDP + + +BootFileName db "BEROSET SYS" ;the boot loader for this OS +; MBR db 0200h DUP (?) +buff db 0200h * 40h DUP (?) +ClustOffs dd ? + org 7dfeh + dw 0AA55h ; signature byte +code ends + + END \ No newline at end of file diff --git a/assembly/Break Handling Utilities Module.asm b/assembly/Break Handling Utilities Module.asm new file mode 100644 index 0000000..d5a0f97 --- /dev/null +++ b/assembly/Break Handling Utilities Module.asm @@ -0,0 +1,70 @@ +TITLE BRK2 -- Break Handling Utilities Module + +TRUE EQU 01H ;boolean true +FALSE EQU 00H ;boolean false +BREAKINT EQU 23H ;dos control-break intrpt +GETVECTOR EQU 35H ;dos get vector function +SETVECTOR EQU 25H ;dos set vector function +DOS_FUNCTION EQU 21H ;dos function call + +BREAK SEGMENT PUBLIC 'CODE' +BREAKFLAG DB 0H ;break key hit flag +SAVEBRK DD 0H ;saved break vec. contents + ASSUME CS:BREAK + ASSUME DS:NOTHING + +;CHECK_BREAK checks if ctrl-break has been pressed. It returns +;true if ctrl-break has been pressed and false if it hasn't. + + PUBLIC CHECK_BREAK +CHECK_BREAK PROC FAR + XOR AX, AX ;clear ax + MOV AL, BREAKFLAG ;return value = breakflag + MOV BREAKFLAG, FALSE ;reset breakflag + RET +CHECK_BREAK ENDP + +;INSTALL_BREAK_HANDLER sets up a ctrl-break interrupt handler. It +;also saves the address of the former break handler so that it can +;be restored later. + + PUBLIC INST_BRK_HANDLR +INST_BRK_HANDLR PROC FAR + PUSH DS + MOV AL, BREAKINT ;AL = break interrupt + MOV AH, GETVECTOR ;AH = dos function code + INT DOS_FUNCTION ;call dos + MOV WORD PTR SAVEBRK, BX ;save offset in int vector + MOV WORD PTR SAVEBRK+2, ES ;save base in int vector + MOV AL, BREAKINT ;AL = break interrupt + MOV AH, SETVECTOR ;AH = dos function code + MOV DX, OFFSET BRK_HANDLER ;DX = offset of brk handler + MOV BX, CS ;BX = this segment + MOV DS, BX ;DS = this segment + INT DOS_FUNCTION ;call dos + POP DS + RET +INST_BRK_HANDLR ENDP + +;BRK_HANDLER is invoked by the bios when ctrl_break is pressed + +BRK_HANDLER PROC FAR + MOV BREAKFLAG, TRUE ;breakflag = yes, break hit + IRET +BRK_HANDLER ENDP + +;REMOVE_BREAK_HANDLER restores the previous ctrl-break handler + +REM_BRK_HANDLR PROC FAR + PUSH DS + MOV AL, BREAKINT ;AL = break interrupt + MOV AH, SETVECTOR ;AH = dos function code + MOV DX, WORD PTR SAVEBRK ;DX = saved 1st word + MOV BX, WORD PTR SAVEBRK+2 ;BX = saved 2nd word + MOV DS, BX ;DS = saved 2nd word + INT DOS_FUNCTION ;call dos + POP DS + RET +REM_BRK_HANDLR ENDP +BREAK ENDS + END \ No newline at end of file diff --git a/assembly/Break.asm b/assembly/Break.asm new file mode 100644 index 0000000..361a21e --- /dev/null +++ b/assembly/Break.asm @@ -0,0 +1,47 @@ +PGROUP Group PROG +DGROUP Group DATA + + +DATA Segment Public 'DATA' + +public brkflag + +brkflag DW 0 + +DATA ends + +PROG Segment Para Public 'PROG' + +public TrapBrea + +assume cs:PGROUP,DS:DGROUP + +TrapBrea proc near + + push ds + push cs + pop ds + mov dx,offset PGROUP:Bret + mov ah,25h + mov al,23h + int 21h + pop ds + ret + +TrapBrea endp + +Bret proc far + + push ds + push ax + mov ax,DGROUP + mov ds,ax + mov brkflag,1 + pop ax + pop ds + iret + +Bret endp +PROG ends + + end \ No newline at end of file diff --git a/assembly/Burnout.asm b/assembly/Burnout.asm new file mode 100644 index 0000000..1a3a092 --- /dev/null +++ b/assembly/Burnout.asm @@ -0,0 +1,127 @@ +COMMENT * + + Demo (and semi-useful) program to read/set burnout device parameters. + + Usage: burnout [ticks] [C+-] [V+-] [H+-] + + Parameters can be separated by almost anything. + With no parameters, program simply returns current status. + + Examples: + burnout 5000 (sets time to 5000 ticks) + burnout 5000H+ (time=5000, use hardware blanking) + burnout 5000,h+ (ditto, separators don't matter) + burnout c+h-v+ (continuous clear, software, monitor video) + burnout /C+ /H- /V+ (ditto) + burnout (return status only) + + Assembly/link: + masm burnout; + link burnout; (ignore NO STACK warning message) + exe2bin burnout burnout.com + + +stdout equ 1 ; DOS output files +stderr equ 2 + +; ----- General equates +DOS equ 21H ; DOS interrupt +TERMINATE equ 20H ; Exit to DOS + +PRINT equ 09H ; DOS "print" string to stdout +FOPEN equ 3D02H ; DOS file open, read/write +FREAD equ 3FH ; DOS file read +FWRITE equ 40H ; DOS file write + +CR equ 13 ; ASCII carriage return +LF equ 10 ; ASCII line fine + +code segment +assume cs:code,ds:code + +org 80H ; Parm storage area in PSP +ParmLength label byte ; Length of parms +org 81H +Parameters label byte ; Start of parms + +org 100H ; Org for .COM +main proc far + jmp start ; Hate to execute data + +DevName db 'BRNDEV',0 ; Burnout device name +handle dw ? ; Storage for handle +Flush db '@' ; Char to flush device I/O +Execute db '#' ; Char to execute device commands + +NotInstalled db 'Burnout device is not installed',13,10 +NotInstalledL equ $ - NotInstalled + +Status db 'Current status: ' ; Status message +StatInsert db 40 dup (?) ; brndev will store status here + +; ----- Open the device +start: + mov dx,offset DevName ; DS:DX => device name + mov ax,FOPEN + int DOS + jnc A1 ; Continue if no error + mov bx,stderr ; Message to stderr + mov cx,NotInstalledL + mov dx,offset NotInstalled + mov ah,FWRITE + int DOS + jmp exit + +; ----- Flush any pending I/O to/from the device +A1: + mov handle,ax ; Save device handle + mov dx,offset Flush ; Point to the "@" + mov cx,1 ; Writing one byte + mov bx,handle ; Device handle + mov ah,FWRITE ; Write "@" to device + int DOS + +; ----- Send and execute parameters if present + mov cl,ParmLength ; Parm length to CL + or cl,cl ; Any parms present? + jz A2 ; Skip if not + xor ch,ch ; CX = parm length + mov dx,offset Parameters ; DS:DX => parms + mov bx,handle ; BX = device handle + mov ah,FWRITE ; Write parms to device + int DOS + + mov dx,offset Execute ; Execute the parms + mov cx,1 ; Writing one byte + mov bx,handle ; Device handle + mov ah,FWRITE ; Write "#" to device + int DOS + +; ----- Get and display device status +A2: + mov dx,offset StatInsert ; DS:DX => where to put status + mov cx,0FFH ; Ask for lots of data; DOS will ... + ; ... fetch only until CR found. + mov bx,handle ; Device handle + mov ah,FREAD ; Read device info + int DOS + + mov cx,ax ; CX = actual # bytes read + mov di,offset StatInsert ; Where the stat data is stored + add di,cx ; Add length of input read + mov al,CR ; Store a CR/LF/'$' at end + cld + stosb + mov al,LF + stosb + mov al,'$' + stosb + mov dx,offset Status ; Write status to stdout + mov ah,PRINT + int DOS + +exit: + int TERMINATE ; Exit to DOS +main endp +code ends +end main \ No newline at end of file diff --git a/assembly/CLEAR Utility to clear display and set character attributes.asm b/assembly/CLEAR Utility to clear display and set character attributes.asm new file mode 100644 index 0000000..0b4c07a --- /dev/null +++ b/assembly/CLEAR Utility to clear display and set character attributes.asm @@ -0,0 +1,103 @@ +; +input equ 080h ;command line tail buffer +cr equ 0dh ;ASCII carriage return +; +cseg segment byte + assume cs:cseg,ds:cseg +; + org 0100h ;since this will be + ; a COM file +; +clear: ;initialize display... + ;call BIOS video driver to + mov ah,15 ;get current display mode: + int 10h ;returns AL = mode, and + ;AH = no. of columns. + cmp al,7 ;if we are in graphics modes + je clear0 ;(modes 4,5,6) then exit + cmp al,3 ;but if we are in mode 0-3 + ja clear9 ;or 7 then continue. +clear0: ;set up size of window to + ;be initialized... + xor cx,cx ;set upper left corner of + ;window to (X,Y)=(0,0) + mov dh,24 ;set Y to 24 for lower right + mov dl,ah ;corner, and X to the number + dec dl ;of columns returned by BIOS + ;minus 1 + mov bh,7 ;initialize attribute byte + ;to "normal" video display, + ;i.e. white on black. + ;set SI=address of command + ;tail's length byte + mov si,offset input + cld ;clear the Direction Flag + ;for "LODS" string instruction. + lodsb ;check length byte to see if + or al,al ;there's any command tail. + jz clear8 ;no,go clear the screen + ;with normal video attribute + ; +clear1: lodsb ;check the next byte of + ;the command tail, + cmp al,cr ;if carriage return + je clear8 ;we are done. + or al,20h ;fold the character to + ;lower case. + cmp al,'a' ;make sure it's in range a-z + jb clear1 ;no, skip it + cmp al,'z' + ja clear1 ;no, skip it + cmp al,'i' ;I=Set intensity + jne clear2 ;jump if not I + or bh,08 ;set intensity bit + jmp short clear1 +clear2: cmp al,'r' ;R=Reverse + jne clear3 ;jump if not R + and bh,088h ;mask off old foreground/ + ;background bits and + or bh,070h ;change to reverse video + jmp short clear1 +clear3: cmp al,'u' ;U=Underline + jne clear4 ;jump if not U + and bh,088h ;mask off old foreground/ + ;background bits and + or bh,01h ;change to underline + jmp short clear1 +clear4: cmp al,'b' ;B=Blink + jne clear5 ;jump if not B + or bh,080h ;set blink bit + jmp short clear1 +clear5: cmp al,'s' ;S=Silent + jne clear1 ;if not S try next char. + mov bh,0 ;if S command, rig for + ;silent running. Clear + ;the foreground/background + ;display control fields, and + ;don't bother to look for + ;any more command characters. + ; +clear8: ;now we have decoded all + ;the characters in the + ;command tail, and are ready + ;to initialize the display. + ;BH= desired attribute + ;CL,CH=(X,Y),upper left + ; corner of window + ;DL,DH=(X,Y),lower right + ; corner of window + mov ax,0600h ;AH = function type 6, + ;AL = lines to scroll (zero) + int 10h ;request initialization + ;of window by BIOS + ; + mov ah,2 ;now set the cursor to + mov bh,0 ;(X,Y)=(0,0), Page=0 + xor dx,dx + int 10h + ; +clear9: int 20h ;exit to PC-DOS +; +cseg ends +; + end clear \ No newline at end of file diff --git a/assembly/Calculator.asm b/assembly/Calculator.asm new file mode 100644 index 0000000..0c9274b --- /dev/null +++ b/assembly/Calculator.asm @@ -0,0 +1,77 @@ +PAGE ,132 + TITLE CALC +CGROUP GROUP CODESEG +CODESEG SEGMENT PARA PUBLIC 'CODE' + ASSUME CS:CGROUP,DS:CGROUP,ES:CGROUP + PUBLIC CALC + + ORG 100H + +CALC PROC FAR + JMP START + +;---------------------------------------------------------------------; +; ; +; DATA AREA ; +; ; +;---------------------------------------------------------------------; + + DB 'INTERRUPT NUMBER =' +INT_NUMBER DB 61h + +SCREEN_HANDLE DW 0001h + +MESSAGE DB 'PEMATH is not resident',13,10 +MESSAGE_LEN EQU $-MESSAGE + +TAG DB 'PEMATH' +TAG_LEN EQU $-TAG + +;---------------------------------------------------------------------; +; ; +; CODE AREA ; +; ; +;---------------------------------------------------------------------; + +START: +;---------------------------------------------------------------------; +; TEST FOR PRESENCE OF CALCULATOR ; +;---------------------------------------------------------------------; + SUB AX,AX + MOV ES,AX + SUB BH,BH + MOV BL,INT_NUMBER + SHL BX,1 + SHL BX,1 + MOV DI,ES:[BX] + MOV ES,ES:[BX+2] + ADD DI,4 + LEA SI,TAG + MOV CX,TAG_LEN + REPE CMPSB + JE CALL_CALC + MOV BX,SCREEN_HANDLE + MOV CX,MESSAGE_LEN + LEA DX,MESSAGE + MOV AH,40h + INT 21h + JMP SHORT CALC_EXIT +;---------------------------------------------------------------------; +; CALL CALCULATOR ; +;---------------------------------------------------------------------; +CALL_CALC: + MOV AL,INT_NUMBER + MOV BYTE PTR INT_CODE,AL + DB 0CDh ; INT +INT_CODE: + DB 00h + NOP + NOP + +CALC_EXIT: + INT 20h + +CALC ENDP + +CODESEG ENDS + END CALC \ No newline at end of file diff --git a/assembly/Cd Check.asm b/assembly/Cd Check.asm new file mode 100644 index 0000000..f4e50a3 --- /dev/null +++ b/assembly/Cd Check.asm @@ -0,0 +1,58 @@ +.model small ; It's a flaw of mine ... I really like this model + ; I know I should do a .com with the tiny model.. + ; but I just love the small :> +.stack 100h ; Plenty stack ;> +.386 + +.data +info db 30 dup (0) +right db 'Right CD$' +wrong db 'Wrong CD$' +nomscdex db 'MSCDEX not installed$' +.code +mov ax, @data ; Make DS&ES point to the DATA +mov ds,ax +mov es,ax + +lea edx, nomscdex +xor ebx,ebx +mov eax, 1500h ; MSCDEX installed? +int 2fh +test ebx,ebx +jz exit + + +mov edi,10h +nextloop: +mov ecx,edi +mov ax, 150bh ; is drive ECX supported by MSCDEX (is it a cdrom?) +int 2fh +test ax,ax ; ax!=0 if drive is CDrom +jz continiue + +mov ax, 440dh +mov dx, offset info +mov bl,5 +mov ch,8 +mov cl,66h +int 21h ; Fetch volume serial number (same as when you do dir) + +mov eax, dword ptr [info+2] +cmp eax, 0ffb7f724h; ;<<<?@' + db 'ABCDEFGHIJKLMNOPQRSTUVWXYZ[\]^_`' + db 'abcdefghijklmnopqrstuvwxyz{|}~' + db 52 dup(' ') + db '|++++++|+++++++++-++++++++-+++++++++++++' + db 36 dup(' ') +ctable ends + end \ No newline at end of file diff --git a/assembly/Checks the validity of an ISBN by verifying the checksum.asm b/assembly/Checks the validity of an ISBN by verifying the checksum.asm new file mode 100644 index 0000000..b9fe254 --- /dev/null +++ b/assembly/Checks the validity of an ISBN by verifying the checksum.asm @@ -0,0 +1,113 @@ +; From Ed Beroset - ISBN validation +; > Anyone know how to validate the ISBN numbers from books? + +; isbnchek.asm +comment ^ + + This file contains a C-callable routine which calculates the + check digit (tenth digit) of an ISBN and returns the ASCII + representation of that digit. + + This code was written for Borland's TASM + and may be assembled with the following command: + + tasm /m2 isbnchek.asm + +^ + .MODEL small + + public isbncheck + + .CODE +;/*************************************************************************** +; +; Name: +; isbncheck +; +; Purpose: +; Calculates the check digit for a ten digit ISBN, converts that +; digit to its ASCII representation and returns that answer. +; +; Algorithm: +; An ISBN consists of nine digits plus a validation digit. +; Number the digits from left to right as d1, d2, ... d9, with +; d10 being the validation digit. The calculation is then +; +; d10 = (1(d1) + 2(d2) + 3(d3) + ... + i(di) + ... + 9(d9))%11 +; +; or the weighted sum of each digit mod eleven. +; +; In our assembly language implementation, we simulate the +; multiplications by looping through and summing as in the +; following psuedocode: +; +; sum = 0 +; for i=1 to 9 +; { +; for j=i to 9 +; { +; sum = sum + isbn[j] +; } +; } +; +; Entry: +; +; isbn = a nine digit ASCII string containing the ISBN +; (with or without the check digit which is not used here) +; +; Register usage within the routine: +; +; AL = current ISBN digit +; AH = sum of digits so far +; BX = start pointer into ISBN for each outer loop +; CX = digit counter (inner loop) +; DX = start value for digit counter +; SI = points to current ISBN digit +; +; Exit: +; +; AX = ASCII representation of calculated check digit +; +; Trashed: +; none +; +;***************************************************************************/ +isbncheck proc C isbn:ptr byte + push bx + push cx + push dx + push si + mov bx,[isbn] ; + mov dx,9 ; number of digits in raw ISBN + xor ax,ax ; clear out our total + cld ; count up +@@bigloop: ; + mov si,bx ; point to a digit in the ISBN + mov cx,dx ; get digit count in CX +@@AddEmUp: ; + lodsb ; fetch digit into AL + and al,0fh ; convert from ASCII + add ah,al ; add it to our total in AH + loop @@AddEmUp ; do all digits + inc bx ; and advance the digit pointer + dec dx ; now decrement digit count + jnz @@bigloop ; keep going if digits left + mov al,ah ; move sum into al + xor ah,ah ; clear out high half + mov cl,11 ; we'll be doing a mod 11 operation + div cl ; ah = sum mod 11 + mov al,ah ; move calculated check digit to AL + xor ah,ah ; clear out high half + or al,30h ; convert to ASCII digit + cmp al,3Ah ; + jnz NotTen ; + mov al,'X' ; +NotTen: ; + pop si + pop dx + pop cx + pop bx + ret ; return +isbncheck endp + + END \ No newline at end of file diff --git a/assembly/Chips.asm b/assembly/Chips.asm new file mode 100644 index 0000000..265e3df --- /dev/null +++ b/assembly/Chips.asm @@ -0,0 +1,208 @@ +; calling convention: +; +; int chips( void ); +; +; returns: +; +; tucked away neatly in your AX.... +; +; you get back 8x if an 8088/8086 +; 18x if an 80186/80188 +; 28x if an 80286 +; 38x if an 80386 +; 20x for a NEC V20/V30 +; AND +; xx0 if NO NDP is found +; xx1 if an 8087 +; xx2 if an 80287 +; xx3 for an 80387 +; +; OR..... +; +; >>> A return of 280 means you got an 80286 machine with no NDP, <<< +; >>> 383 means you have an 80386/80387 rig to work with, and a <<< +; >>> return of 81 sez that you have 8088/8086 CPU with an 8087. <<< +; >>> A 200 tells you that you got an NEC V20/V30 without an NDP. <<< +; >>> ETC., Etc., etc. <<< +; +; NOTE: +; +; There are lotsa ways of handling the way this function returns +; it's data. For my purposes, I have elected this one because +; it requires only int arithmetic on the caller's end to extract +; all the info I need from the return value. I think that I'm +; well enough 'commented' in the following code so that you will +; be able to tinker and Putz until you find the best return tech- +; nique for Ur purposes without having to reinvent the wheel. +; +; >>>> Please see TEST.C, enclosed in this .ARC. <<<< +; +; REFERENCES: +; +; _chips is made up of two PROC's, cpu_type and ndp_type. +; +; cpu_type is based on uncopyrighted, published logic by +; Clif (that's the way he spells it) Purkiser of Intel - +; Santa Clara. +; +; ndp_type is adopted from Ted Forgeron's article in PC +; Tech Journal, Aug '87 p43. +; +; In the event of subsequent republication of this function, +; please carry forward reference to these two gentlemen as +; original authors. +; +.MODEL SMALL +.CODE + PUBLIC _chips + +_chips PROC + +control dw 0 ; control word needed for the NDP test + + push BP ; save where Ur at + mov BP,SP ; going in..... + + push DI + push SI + push CX ; not really needed for MSC but kinda + ; nice to do cuz someone else might + ; want to use the function and we do + ; use CX later on + + call cpu_type ; find out what kinda CPU you got and + ; and save it in DX for future reference + call ndp_type ; check for math coprocessor (NDP) type + ; and hold that result in AX + + add AX,DX ; add the two results together and hold + ; 'em in AX for Ur return to the caller + + pop CX ; put things back the way that you + pop SI ; found 'em when you started this + pop DI ; little drill off..... + pop BP + ; AND + ret ; go back to where you came from.... + ; ( ===> the calling program ) + ; with Ur results sittin' in AX !! +_chips endp + + +cpu_type PROC + + pushf ; pump Ur flags register onto the stack + xor DX,DX ; blow out Ur DX and AX to start off + xor AX,AX ; with a clean slate + push AX ; put AX on the stack + popf ; bring it back in Ur flags + pushf ; try to set bits 12 thru 15 to a zero + pop AX ; get back Ur flags word in AX + and AX, 0f000h ; if bits 12 thru 15 are set then you got + cmp AX, 0f000h ; an Intel 8018x or a 808x or maybe even + jz dig ; a NEC V20/V30 ??? - gotta look more... + +; OTHERWISE.... +; Here's the BIG one.... 'tells the difference between an 80286 and +; an 80386 !! + + mov AX, 07000h ; try to set FLAG bits 12 thru 14 + ; - NT, IOPL + push AX ; put it onto the stack + popf ; and try to pump 07000H into Ur flags + pushf ; push Ur flags, again + pop AX ; and bring back AX for a compare + and AX,07000h ; if Ur bits 12 thru 14 are set + jnz got386 ; then Ur workin' with an 80386 + mov DX, 0280 ; save 280 in DX cuz it's an 80286 + jmp SHORT CPUbye ; and bail out + +got386: mov DX, 0380 ; save 380 in DX cuz it's an Intel 80386 + jmp SHORT CPUbye ; and bail out + +; here's we try to figger out whether it's an 80188/80186, an 8088/8086 +; or an NEC V20/V30 - 'couple of slick tricks from Clif Purkiser..... + +dig: mov AX, 0ffffh ; load up AX + mov CL, 33 ; HERE's the FIRST TRICK.... this will + ; shift everything 33 times if it's + ; 8088/8086, or once for a 80188/80186! + shl AX, CL ; on a shift of 33, all bits get zeroed + jz digmor ; out so if anything is left ON it's + ; gotta be an 80188/80186 + mov DX,0180 ; save 180 in DX cuz it's an 80188/80186 + jmp SHORT CPUbye ; and bail out + +digmor: xor AL,AL ; clean out AL to set ZF + mov AL,40h ; ANOTHER TRICK.... mul on an NEC duz NOT + mul AL ; effect the zero flag BUT on an Intel + jz gotNEC ; 8088/8086, the zero flag gets thrown + mov DX,0080 ; 80 into DX cuz it's an Intel 8088/8086 + jmp SHORT CPUbye ; and bail out + +gotNEC: mov DX,0200 ; it's an NEC V20/V30 so save 200 in DX + +CPUbye: popf ; putchur flags back to where they were + ret ; and go back to where you came from + ; (i.e., ===> _chips) with the CPU type + ; tucked away in DX for future reference +cpu_type endp + +; Check for an NDP. +; +; >>>>NOTE: If you are using an MASM version < 5.0, don't forget to +; use the /R option or you will bomb cuz of the coprocessor instruc- +; tions. /R is not needed for version 5.0.<<<<<<<<<<<<<<<<<<<<<<<<< + +ndp_type PROC + +do_we: fninit ; try to initialize the NDP + mov byte ptr control+1,0 ; clear memory byte + fnstcw control ; put control word in memory + mov AH,byte ptr control+1 ; iff AH is 03h, you got + cmp AH,03h ; an NDP on board !! + je chk_87 ; found somethin', keep goin' + xor AX,AX ; clean out AX to show a zero + jmp SHORT NDPbye ; return (i.e., no NDP) + +; 'got an 8087 ?? + +chk_87: and control,NOT 0080h ; turn ON interrupts (IEM = 0) + fldcw control ; load control word + fdisi ; turn OFF interrupts (IEM = 1) + fstcw control ; store control word + test control,0080h ; iff IEM=1, 8087 + jz chk287 ; 'guess not! March on.... + mov AX,0001 ; set up for a 1 return to + jmp SHORT NDPbye ; show an 8087 is on board + +; if not.... would you believe an 80287 maybe ?? + +chk287: finit ; set default infinity mode + fld1 ; make infinity + fldz ; by dividing + fdiv ; 1 by zero !! + fld st ; now make a + fchs ; negative infinity + fcompp ; compare Ur two infinities + fstsw control ; iff, for 8087 or 80287 + fwait ; sit tight 'til status word is put away + mov AX,control ; getchur control word + sahf ; putchur AH into flags + jnz got387 ; NO GOOD.... march on !! + mov AX,0002 ; gotta be a 80287 cuz we already tested + jmp SHORT NDPbye ; for an 8087 + +; We KNOW that there is an NDP on board otherwise we would have bailed +; out after 'do_we'. It isn't an 8087 or an 80287 or we wouldn't have +; gotten this far. It's gotta be an 80387 !! + +got387: mov AX,0003 ; call it an 80387 and return 3 + +NDPbye: ret ; and go back where you came from + ; (i.e., ===> _chips) carrying the NDP + ; type in Ur AX register +ndp_type endp + +_text ends + end \ No newline at end of file diff --git a/assembly/Circle.asm b/assembly/Circle.asm new file mode 100644 index 0000000..1b424d9 --- /dev/null +++ b/assembly/Circle.asm @@ -0,0 +1,83 @@ +cseg segment + assume cs:cseg, ds:cseg, ss:cseg + org 100h + .386 +start: + + mov ax, 13h + int 10h + + mov dx, 3c8h + xor al, al + out dx, al + inc dx + mov cx, 256 + xor al, al +lopp: out dx, al + out dx, al + out dx, al + inc al + dec cx + jnz lopp + + mov ax, 0a000h + mov es, ax + + + fild y_rad + fild x_rad + +loopdr: + fild angle + fsincos + + fmul st, st(2) + fistp x_co + + fmul st, st(2) + fistp y_co + + add x_co, 160 + add y_co, 100 + + xor di, di + mov ax, y_co + shl ax, 6 + add di, ax + shl ax, 2 + add di, ax + add di, x_co + + mov byte ptr es:[di], cl + inc cl + + fadd yvel + fxch st(1) + fadd xvel + fxch st(1) + + inc angle + jnz loopdr + + xor ax, ax + int 16h + + mov ax, 3 + int 10h + + int 20h + +x_co dw 0 +y_co dw 0 + +x_rad dw 10 +y_rad dw 10 + +xvel dq 0.001 +yvel dq 0.001 + +angle dw 0 + + +cseg ends + end start \ No newline at end of file diff --git a/assembly/Clock.asm b/assembly/Clock.asm new file mode 100644 index 0000000..2572f8c --- /dev/null +++ b/assembly/Clock.asm @@ -0,0 +1,137 @@ +CGROUP GROUP VECTOR,CODESEG +VECTOR SEGMENT AT 0H + DB 6CH DUP(?) ;FILLER +TIME_LO DW ? ;DOS TIME +TIME_HI DW ? ;DOS TIME +VEC_IP DW ;CLOCK UPDATE VECTOR IP +VEC_CS DW ;CLOCK UPDATE VECTOR CS +VECTOR ENDS + +CODESEG SEGMENT PARA + ASSUME CS:CODESEG,DS:CGROUP + ORG 100H +CLK PROC FAR + JMP SETUP ;ATTACH TO DOS +INTRPT LABEL DWORD +INT_IP DW 0 ;OLD UPDATE VECTOR IP +INT_CS DW 0 ;OLD UPDATE VECROR CS +TICKS DW 0 ;TICK COUNTER +SCR_OFF DB 0,0 ;SCREEN OFFSET IN BUFFER +CRT_PORT DW 0 ;SCREEN STATUS PORT +flag db 0 +TIME DB 8 DUP(':',0BH) ;TIME SAVE AREA +CLK_INT LABEL NEAR + PUSH AX ;SAVE REGISTERS + PUSH CX + PUSH DI + PUSH SI + PUSH DS + PUSH ES + PUSHF ; AND FLAGS + CALL CS:[INTRPT] ;DO OLD UPDATE INTERRUPT + MOV CX,0040H ;GET SEGMENT OF DOS TABLE + MOV DS,CX ;PUT IN DS + MOV CX,CS:TICKS ;GET TICK COUNT + INC CX ;INCREMENT IT + CMP CX,20 ;01F4H ;HAS A MINUTE GONE BY? + JB NO_MINUTE ;NO, MOVE ON + CALL UPDATE ;YES, UPDATE CLOCK AND + MOV CX,0 ; RESET TICK COUNTER +NO_MINUTE: + MOV CS:TICKS,CX ;SAVE UPDATED TICK COUNT + MOV CX,0B000H ;GET VIDEO SEGMENT + MOV ES,CX ;PUT IN ES + MOV DX,CS:CRT_PORT ;GET CRT STATUS PORT ADDR + MOV DI,WORD PTR CS:SCR_OFF ;GET SCREEN BUFFER OFFSET + LEA SI,CS:TIME ;GET DOS TIME + MOV CX,16 ;SET UP TO MOVE 10 BYTES + CLI ;DISABLE OTHER INTERRUPTS +WAIT1: IN AL,DX ;READ CRT STATUS + TEST AL,1 ;CHECK FOR VERTICAL RETRACE + JNZ WAIT1 ;WAIT FOR RETRACE LOW + MOV AH,CS:[SI] ;GET FIRST BYTE TO MOVE +WAIT2: IN AL,DX ;GET CRT STATUS + TEST AL,1 ;CHECK FOR VERTICAL RETRACE + JZ WAIT2 ;WAIT FOR RETRACE HIGH + MOV ES:[DI],AH ;MOVE BYTE TO SCREEN + INC DI ;INCREMENT INDEX + INC SI + LOOP WAIT1 ;MOVE NEXT BYTE + STI ;ENABLE INTERRUPTS + POP ES ;RESTORE REGISTERS + POP DS + POP SI + POP DI + POP CX + POP AX + IRET ;RETURN FROM INTERRUPT +CLK ENDP +UPDATE PROC NEAR + PUSH AX ;SAVE REGISTERS + PUSH BX + PUSH CX + PUSH DX + PUSH DS + MOV AX,0040H ;GET ADDRESS OF DOS TABLE + MOV DS,AX ;PUT IN DS + MOV AX,TIME_HI ;GET HIGH BYTE OF DOS TIME + mov flag,0 ;am flag +HOUR: CMP AX,0CH ;CONVERT TO HOURS + JLE H1 + mov flag,1 ;set to pm + SUB AX,0CH + JMP HOUR +H1: AAM ;CONVERT TO ASCII + ADD AX,3030H + LEA BX,CS:TIME ;GET ADDRESS OF TIME AREA + MOV CS:[BX],AH ;SAVE HOURS FIRST DIGIT + MOV CS:[BX+2],AL ;SAVE HOURS SECOND DIGIT + MOV AX,TIME_LO ;GET DOS TIME LOW BYTE + MOV CX,8H ;CONVERT TO MINUTES + SHR AX,CL + MOV DX,3CH + MUL DL + SHR AX,CL + AAM ;CONVERT TO ASCII + ADD AX,3030H + MOV CS:[BX+6],AH ;SAVE MINUTES FIRST DIGIT + MOV CS:[BX+8],AL ;SAVE MINUTES SECOND DIGIT + mov byte ptr cs:[bx+12],'a' + cmp flag,0 ;is it am? + jz goahead + mov byte ptr cs:[bx+12],'p' +goahead: + mov byte ptr cs:[bx+14],'m' + POP DS ;RESTORE REGISTERS + POP DX + POP CX + POP BX + POP AX + RET +UPDATE ENDP +SETUP: MOV AX,0 ;GET ADDRESS OF VECTOR TABLE + MOV DS,AX ;PUT IN DS + CLI ;DISABLE FURTHER INTERRUPTS + MOV AX,[VEC_IP] ;GET ADDRESS OF OLD UPDATE IP + MOV CS:[INT_IP],AX ;SAVE IT + MOV AX,[VEC_CS] ;GET ADDRESS OF OLD UPDATE CS + MOV CS:[INT_CS],AX ;SAVE IT + MOV VEC_IP,OFFSET CLK_INT ;PUT ADDRESS OF CLK IN VECTOR IP + MOV VEC_CS,CS ;PUT CS OF CLK IN VECTOR CS + STI ;ENABLE INTERRUPTS + MOV AH,0FH ;READ VIDEO STATUS + INT 10H + SUB AH,8 ;SUBTRACT 8 CHAR TIME FROM NCOLS + SHL AH,1 ;MULTIPLY BY 2 FOR ATTRIBUTE + MOV CS:SCR_OFF,AH ;SAVE SCREEN TIME LOCATION + MOV WORD PTR CS:CRT_PORT,03BAH ;SAVE MONO STATUS PORT ADDR + TEST AL,4 ;CHECK FOR COLOR MONITOR + JNZ MONO ;IF MONO, MOVE ON + ADD WORD PTR CS:SCR_OFF,8000H ;ADD COLOR OFFSET TO TIME OFFSET + MOV WORD PTR CS:CRT_PORT,03DAH ;SAVE COLOR STATUS PORT ADDR +MONO: CALL UPDATE ;DO FIRST UPDATE & PRINT TIME + MOV DX,OFFSET SETUP ;GET END ADDRESS OF NEW INTERRUPT + INT 27H ;TERMINATE AND REMAIN RESIDENT + DB 117 DUP(0) ;FILLER +CODESEG ENDS + END CLK \ No newline at end of file diff --git a/assembly/Colours routine.asm b/assembly/Colours routine.asm new file mode 100644 index 0000000..50e5652 --- /dev/null +++ b/assembly/Colours routine.asm @@ -0,0 +1,109 @@ +; for tasm +; +cseg segment +assume cs:cseg, ds:cseg +org 100H +begin: + mov es,cs:[video] + + mov ax,3 + int 10h + mov cs:[col],0fh + mov di,18 + lea si,colr2 + call mess + + mov cx,16 + mov di,160 + xor al,al +rec1: + push cx + + push di + lea si,colour + call mess + call hex2 + + mov bh,al + push cx + mov cx,16 +col2: + mov es:[di],byte ptr "#" + mov es:[di+1],bh + inc bh + add di,2 + + loop col2 + pop cx + + + pop di + add di,160 + add al,10h + + add cs:[col],10h + pop cx + loop rec1 + + + mov ah,2 + mov bh,0 + mov dh,17 + mov dl,0 + int 10h + + + mov ah,4ch + int 21h + +col db 0 +colour db "Colour ",0 +colr2 db "0123456789ABCDEF",0 +colnum db 0 + +video dw 0b800h + +hex2 proc near + push ax + and al,011110000b + shr al,4 + call hex1 + pop ax + push ax + and al,01111b + call hex1 + pop ax + ret +hex2 endp +hex1 proc near + mov ah,cs:[col] + cmp al,10 + jb hnum1 + add al,'A'-10 + jmp hnum2 +hnum1: + add al,'0' +hnum2: + mov es:[di],ax + add di,2 + ret +hex1 endp +mess proc + push ax + mov ah,cs:[col] +conmess: + mov al,cs:[si] + or al,al + jz endmess + mov es:[di],ax + inc si + add di,2 + jmp conmess +endmess: + pop ax + ret +mess endp + + +cseg ends +end begin \ No newline at end of file diff --git a/assembly/Command line program allows piping of output from other programs into Windows clipboard.asm b/assembly/Command line program allows piping of output from other programs into Windows clipboard.asm new file mode 100644 index 0000000..869e40a --- /dev/null +++ b/assembly/Command line program allows piping of output from other programs into Windows clipboard.asm @@ -0,0 +1,132 @@ +; toclip.asm +; +; This code may be assembled and linked using Borland's TASM: +; tasm /la /m2 toclip +; tlink /Tdc toclip +; +; It also works with Microsoft's MASM: +; ml /Fl toclip.asm +; +STDIN equ 00h ; handle of standard input device +STDOUT equ 01h ; handle of standard output device +STDERR equ 02h ; handle of standard error device + +DOS_READ_HANDLE equ 03fh ; read from handle +DOS_WRITE_HANDLE equ 040h ; write to handle +DOS_ALLOC_MEM equ 048h ; allocate memory block +DOS_RESIZE_MEM equ 04ah ; resize memory block +DOS_TERMINATE equ 04ch ; terminate with error code + +WIN_VERSION equ 01700h ; identify WinOldAp version +WIN_OPEN_CLIP equ 01701h ; open clipboard +WIN_EMPTY_CLIP equ 01702h ; empty clipboard +WIN_SET_CLIP equ 01703h ; set clipboard data +WIN_CLOSE_CLIP equ 01708h ; close clipboard + +; clipboard formats: +CLIP_FMT_TXT equ 01h ; text format +CLIP_FMT_BMP equ 02h ; bitmap format +CLIP_FMT_TIFF equ 06h ; TIFF +CLIP_FMT_OEMTXT equ 07h ; OEM text + + +WININT macro function + mov ax,(function) + int 2fh +endm + +DOSINT macro function, subfunction + IFB + mov ah,(function AND 0ffh) + ELSE + mov ax,(function SHL 8) OR (subfunction AND 0ffh) + ENDIF + int 21h ; invoke DOS function +endm + +ERRMSG macro tag, message + LOCAL nextmsg +tag db nextmsg-$ + db message +nextmsg = $ +endm + + .model small + .386 + .stack 100h + .data +ERRMSG cantresize, <"ERROR: can't resize memory",0dh,0ah> +ERRMSG noclipboard,<"ERROR: no clipboard",0dh,0ah> +ERRMSG emptyclip, <"ERROR: cannot empty clipboard",0dh,0ah> +ERRMSG openclip, <"ERROR: cannot open clipboard",0dh,0ah> +ERRMSG allocerror, <"ERROR: can't allocate 64K buffer",0dh,0ah> +ERRMSG readerr, <"ERROR: can't read data from stdin",0dh, 0ah> +ERRMSG pasteerr, <"ERROR: can't paste data to clipboard",0dh,0ah> + + .code +start proc + mov bx,ss ; stack segment + mov ax,ds ; - data segment + sub bx,ax ; = size of all but stack + add bx,10h ; add in stack size (in paragraphs) + DOSINT DOS_RESIZE_MEM ; + mov di,offset cantresize + jc error + WININT WIN_VERSION + cmp ax,WIN_VERSION + mov di,offset noclipboard + jz error ; + + WININT WIN_OPEN_CLIP ; open clipboard + or ax,ax ; nonzero status means error + mov di,offset openclip + jz error ; + + WININT WIN_EMPTY_CLIP ; empty clipboard + or ax,ax ; nonzero status means error + mov di,offset emptyclip + jz error ; + + ; allocate a big buffer + mov bx,1000h ; 1000h paragraphs = 64K + DOSINT DOS_ALLOC_MEM ; + mov di,offset allocerror + jc error ; + + + mov ds,ax ; + mov es,ax ; + ; read from the input file + mov bx,STDIN ; stdin + mov cx,0ffffh ; read a whole bunch of data +; ds:dx ==> data buffer + xor dx,dx ; + DOSINT DOS_READ_HANDLE ; + mov di,offset readerr + jc error ; + xor si,si ; + mov cx,ax ; size + + ; paste the file buffer into the clipboard +; mov es:bx ==> data + xor bx,bx +; mov si:cx, size of data + mov dx,CLIP_FMT_TXT ; text data + WININT WIN_SET_CLIP ; + or ax,ax + mov di,offset pasteerr ; + jz error ; + WININT WIN_CLOSE_CLIP ; close clipboard + DOSINT DOS_TERMINATE,0 ; exit with error code = 0 +error: + mov bx,@data ; + mov ds,bx ; + xor cx,cx ; + mov cl,byte ptr[di] ; fetch length + mov dx,di ; point to data + inc dx ; advance beyond length + mov bx,STDERR ; write to stderr + DOSINT DOS_WRITE_HANDLE ; write to handle + DOSINT DOS_TERMINATE,1 ; error exit +start endp + END start \ No newline at end of file diff --git a/assembly/Control-Break handler for Lattice C programs.asm b/assembly/Control-Break handler for Lattice C programs.asm new file mode 100644 index 0000000..c9481f7 --- /dev/null +++ b/assembly/Control-Break handler for Lattice C programs.asm @@ -0,0 +1,168 @@ + title Control-Break handler for Lattice C programs + name break + include dos.mac + +; Control-Break Interrupt Handler for Lattice C programs +; running on IBM PCs (and ROM BIOS compatibles) +; +; This module allows C programs running on the IBM PC +; to retain control when the user enters a Control-Break +; or Control-C. This is accomplished by taking over the +; Int 23H (MS-DOS Control-Break) and Int 1BH (IBM PC +; ROM BIOS Keyboard Driver Control-Break) interrupt +; vectors. The interrupt handler sets an internal +; flag (which must be declared STATIC INT) to TRUE within +; the C program; the C program can poll or ignore this +; flag as it wishes. +; +; The module follows the Lattice C parameter passing +; conventions, and also relies on the Lattice file DOS.MAC +; for the definition of certain constants and macros. +; +; The Int 23H Control-Break handler is a function of MS-DOS +; and is present on all MS-DOS machines, however, the Int 1BH +; handler is a function of the IBM PC ROM BIOS and will not +; necessarily be present on other machines. +; + if lprog +args equ 6 ;offset of arguments, Large models + else +args equ 4 ;offset of arguments, Small models + endif + +cr equ 0dh ;ASCII carriage return +lf equ 0ah ;ASCII line feed + + pseg + + public capture,release ;function names for C + + +; +; The function CAPTURE is called by the C program to +; take over the MS-DOS and keyboard driver Control- +; Break interrupts (1BH and 23H). It is passed the +; address of a flag within the C program which is set +; to TRUE whenever a Control-Break or Control-C +; is detected. The function is used in the form: +; +; static int flag; +; capture(&flag) +; + +capture proc near ;take over Control-Break + + push bp ;interrupt vectors + mov bp,sp + push ds + + mov ax,word ptr [bp+args] + mov cs:flag,ax ;save address of integer + mov cs:flag+2,ds ;flag variable in C program + + ;pick up original vector contents + mov ax,3523h ;for interrupt 23H (MS-DOS + int 21h ;Control-Break handler) + mov cs:int23,bx + mov cs:int23+2,es + + mov ax,351bh ;and interrupt 1BH + int 21h ;(IBM PC ROM BIOS keyboard driver + mov cs:int1b,bx ;Control-Break interrupt handler) + mov cs:int1b+2,es + + push cs ;set address of new handler + pop ds + mov dx,offset ctrlbrk + mov ax,02523H ;for interrupt 23H + int 21h + mov ax,0251bH ;and interrupt 1BH + int 21h + + pop ds ;restore registers and + pop bp ;return to C program + ret + +capture endp + + +; +; The function RELEASE is called by the C program to +; return the MS-DOS and keyboard driver Control-Break +; interrupt vectors to their original state. Int 23h is +; also automatically restored by MS-DOS upon the termination +; of a process, however, calling RELEASE allows the C +; program to restore the default action of a Control-C +; without terminating. The function is used in the form: +; +; release() +; + +release proc near ;restore Control-Break interrupt + ;vectors to their original state + push bp + mov bp,sp + push ds + + mov dx,cs:int1b ;set interrupt 1BH + mov ds,cs:int1b+2 ;(MS-DOS Control-Break + mov ax,251bh ;interrupt handler) + int 21h + + mov dx,cs:int23 ;set interrupt 23H + mov ds,cs:int23+2 ;(IBM PC ROM BIOS keyboard driver + mov ax,2523h ;Control-Break interrupt handler) + int 21h + + pop ds ;restore registers and + pop bp ;return to C program + ret + +release endp + + +; +; This is the actual interrupt handler which is called by +; the ROM BIOS keyboard driver or by MS-DOS when a Control-C +; or Control-Break is detected. Since the interrupt handler +; may be called asynchronously by the keyboard driver, it +; is severely restricted in what it may do without crashing +; the system (e.g. no calls on DOS allowed). In this +; version, it simply sets a flag within the C program to +; TRUE to indicate that a Control-C or Control-Break has +; been detected; the address of this flag was passed +; by the C program during the call to the CAPTURE function. +; + +ctrlbrk proc far ;Control-Break interrupt handler + + push bx ;save affected registers + push ds + + mov bx,cs:flag ;set flag within C program + mov ds,cs:flag+2 ;to "True" + mov word ptr ds:[bx],-1 + + pop ds ;restore registers and exit + pop bx + + iret + +ctrlbrk endp + + +flag dw 0,0 ;long address of C program's + ;Control-Break detected flag + +int23 dw 0,0 ;original contents of MS-DOS + ;Control-Break Interrupt 23H + ;vector + +int1b dw 0,0 ;original contents of ROM BIOS + ;keyboard driver Control-Break + ;Interrupt 1BH vector + + + endps + + end \ No newline at end of file diff --git a/assembly/Demo showing how to use 'flat real mode'.asm b/assembly/Demo showing how to use 'flat real mode'.asm new file mode 100644 index 0000000..d7824b3 --- /dev/null +++ b/assembly/Demo showing how to use 'flat real mode'.asm @@ -0,0 +1,44 @@ +; test1.asm +; +; This program uses flat real mode to read the contents of arbitrary +; memory locations to the screen. It assumes that flat real mode (4G +; limit) is already in place for the FS segment. +; +; This code is intended to be run on a Pentium or better. +; +; To assemble: +; +; using Microsoft's MASM 6.11 or better +; ml /Fl flatmode.asm +; +; or Borland's TASM version 4.0 or better +; tasm /la /m2 flatmode.asm +; tlink /Tdc flatmode +; +;---------------------------------------------------------------------- + .model tiny + .code + .586P + +;---------------------------------------------------------------------- + ORG 100h +start: + call fillscreen ; fill the screen using 4G descriptor + mov ax,4c00h ; do a standard DOS exit + int 21h ; +;---------------------------------------------------------------------- +fillscreen proc + mov esi,0FFFFFF70h ; point to ROM + mov edi,0B8000h ; point to screen + mov cx,160 ; just two lines + mov ah,1Eh ; yellow on blue screen attrib +myloop: + mov al,fs:[esi] ; read ROM byte + mov fs:[edi],ax ; store to screen with attribute + inc esi ; increment source ptr + inc edi ; increment dest ptr by two + inc edi ; + loop myloop ; keep going + ret ; and quit +fillscreen endp +end start \ No newline at end of file diff --git a/assembly/Determines the type of UART in each serial port.asm b/assembly/Determines the type of UART in each serial port.asm new file mode 100644 index 0000000..e84e8b8 --- /dev/null +++ b/assembly/Determines the type of UART in each serial port.asm @@ -0,0 +1,221 @@ +comment * + SERTYPE.ASM + Purpose: + Determines the type of UART in each serial port + +* + +dosseg + +bdseg segment at 40h ;bios data segment + com1 dw ? + com2 dw ? + com3 dw ? + com4 dw ? + ends + +_data segment para 'data' + uart1 db 0 + uart2 db 0 + uart3 db 0 + uart4 db 0 + portmsg db "COMx: $" + x8250 db "NS 8250 (non-FIFO)",13,10,"$" + x16450 db "NS 8250A/16450/16550 (non-FIFO)",13,10,"$" + xfifo db "NS 16550A/Intel 82510 (FIFO)",13,10,"$" + xdma db "IBM type 3 (FIFO/DMA)",13,10,"$" + pas_de_ports db "No serial ports detected",13,10,"$" + ends + +_stack segment para stack 'stack' + db 200h dup (?) + ends + +cseg segment para 'code' + mov ax, bdseg + mov es, ax ;ES := Bdseg + mov ax, _data + mov ds, ax ;DS := _data + assume cs:cseg, ds:_data, es:bdseg, ss:_stack + xor al, al ;# of serial ports = 0 + mov dx, [com1] + cmp dx, 0 + je eoproc + inc al ;# of serial ports = 1 + push ax + call uartdet + mov [uart1], al ;remember the type of this UART + pop ax + mov dx, [com2] + cmp dx, 0 + je eoproc + inc al ;# of serial ports = 2 + push ax + call uartdet + mov [uart2], al + pop ax + mov dx, [com3] + cmp dx, 0 + je eoproc + inc al ;# of serial ports = 3 + push ax + call uartdet + mov [uart3], al + pop ax + mov dx, [com4] + cmp dx, 0 + je eoproc + inc al ;# of serial ports = 4 + push ax + call uartdet + mov [uart4], al + pop ax + +eoproc: + call disp + mov ah, 4ch + int 21h + +delay macro + jmp $+2 + endm + +uartdet proc near + push bx + push cx + mov bx, dx ;save starting i/o addr + add dx, 4 ;point to modem ctrl reg + in al, dx ;disable interrupts + push ax + and al, 11111011b + out dx, al + mov ch, 0 ;assume type 0 + mov dx, bx + add dx, 7 ;see if scratch reg exists + mov al, 55h + cli + out dx, al ;write to scratch reg + delay + in al, dx ;read back + cmp al, 55h + jne endudet + mov al, 0AAh + out dx, al ;write to scratch reg + delay + in al, dx ;read back + sti + cmp al, 0AAh + jne endudet + inc ch ;assume type 1 + mov dx, bx + add dx, 2 ;point to FIFO ctrl reg + mov al, 7 ;attempt to enable FIFOs + cli + out dx, al + delay + in al, dx ;read interrupt ID reg + sti + and al, 0c0h ;strip all but FIFO bits + jz endudet ;if bits 0, 16450/16550 + inc ch ;assume type 2 + mov dx, bx + add dx, 8003h ;point to enhanced reg 1 + cli + in al, dx + push ax + or al, 01000000b ;enable DMA transmission + out dx, al + push dx + mov dx, bx + add dx, 2 + in al, dx + mov cl, al + pop dx ;restore enhanced reg 1 + pop ax + out dx, al + sti + and cl, 0c0h ;again mask all but FIFO ID + cmp cl, 40h + jne endudet ;must be type 2 (FIFO) + inc ch ;must be type 3 (DMA) + +endudet: + pop ax + mov dx, bx + add dx, 4 ;point to modem ctrl reg + out dx, al ;restore initial condition + xor ax, ax + mov al, ch + mov dx, bx + pop cx + pop bx + ret +uartdet endp + +disp proc near + push ax ;save AX + cmp al, 0 ;no serial ports? + je noports + mov bx, offset ds:[uart1] ;offset of UART type field + mov di, offset ds:[portmsg][3] ;offset of 4th char in message + mov cx, 0 + mov cl, al ;number of iterations + +@l1: + ; + ;write "COMx: " message substituting "x" for proper comport # + ; + mov dl, 4 + sub dl, cl + add dl, 30h ;convert to ASCII number + mov [di], dl + lea dx, portmsg + mov ah, 9 + int 21h + ; + ;write the UART type now + ; + mov dl, [bx] + cmp dl, 0 + jne @t2 + lea dx, x8250 + mov ah, 9 + int 21h + jmp @eot + +@t2: cmp dl, 1 + jne @t3 + lea dx, x16450 + mov ah, 9 + int 21h + jmp @eot + +@t3: cmp dl, 2 + jne @t4 + lea dx, xfifo + mov ah, 9 + int 21h + jmp @eot + +@t4: lea dx, xdma + mov ah, 9 + int 21h + +@eot: inc bx + loop @l1 + jmp eoproc2 + +noports: + lea dx, pas_de_ports + mov ah, 9 + int 21h + +eoproc2: + pop ax + ret +disp endp + + ends + end + +; EOF SERTYPE.ASM \ No newline at end of file diff --git a/assembly/Device Driver Header.asm b/assembly/Device Driver Header.asm new file mode 100644 index 0000000..5b1ac2a --- /dev/null +++ b/assembly/Device Driver Header.asm @@ -0,0 +1,233 @@ +;-----------------------------------------------------------------------| +; +; Device Driver Library +; Device Driver Header +; +;-----------------------------------------------------------------------| + PAGE +;-----------------------------------------------------------------------| +; Equates +;-----------------------------------------------------------------------| + +StkSiz EQU 2048 ; local stack size + + PAGE +;-----------------------------------------------------------------------| +; Group Selection +;-----------------------------------------------------------------------| + +PGROUP Group PROG, TAIL +DGROUP Group DATA, DTAIL + +PROG Segment Para Public 'PROG' +PROG EndS + +DATA Segment Para Public 'DATA' ; define first +DATA EndS + + Assume CS:PROG, DS:DATA, ES:DATA, SS:DATA + + PAGE +;-----------------------------------------------------------------------| +; Program Segment +;-----------------------------------------------------------------------| + +PROG Segment Para Public 'PROG' + + Extrn Init:Near, MediaChe:Near, BuildBPB:Near + Extrn IoCtlIn:Near, Input:Near, ndInput:Near + Extrn InputSta:Near, InputFlu:Near, Output:Near + Extrn OutVerif:Near, OutStatu:Near, OutFlush:Near + Extrn IoCtlOut:Near, DevOpen:Near, DevClose:Near + Extrn RemMedia:Near + + ORG 0 + +HDR Proc Far + +;-----------------------------------------------------------------------| +; Device Header +;-----------------------------------------------------------------------| + + DD -1 ; -> next device +; DW theAttribute ; you must enter attribute field + DW 8000H ; character only device + DW Strategy ; -> device strategy + DW Interrupt ; -> device interrupt +; DB theName ; you must put something here + DB "MON " ; mono + +;-----------------------------------------------------------------------| +; Code Segment Variables +;-----------------------------------------------------------------------| + +RHptr DD (?) ; -> Request Header +ssEntry DW (?) ; entry SS +spEntry DW (?) ; entry SP + + PAGE +;-----------------------------------------------------------------------| +; Device Strategy +; +; ENTRY : ES:BX -> Request Header +; +; EXIT : Request Header copied to ReqHdr +; all registers preserved +; +;-----------------------------------------------------------------------| + +Strategy: + + MOV Word Ptr CS:RHptr,BX ; save request header ptr + MOV Word Ptr CS:RHptr + 2,ES + + PUSHF ; (+1) save the world + PUSH ES ; (+2) + PUSH DS ; (+3) + PUSH SI ; (+4) + PUSH DI ; (+5) + PUSH CX ; (+6) + PUSH BX ; (+7) + + MOV SI,BX + MOV BX,ES + MOV DS,BX ; DS:SI -> Request Header + + MOV BX,Offset PGROUP:TAIL + MOV CL,4 + SHR BX,CL + MOV CX,CS + ADD BX,CX + MOV ES,BX + MOV DI,Offset DGROUP:ReqHdr ; ES:DI -> ReqHdr + + CLD + XOR CH,CH + MOV CL,[SI] + REP MOVSB ; copy Request Header + + POP BX ; (+6) restore + POP CX ; (+5) + POP DI ; (+4) + POP SI ; (+3) + POP DS ; (+2) + POP ES ; (+1) + POPF ; (+0) + RET + + PAGE +;-----------------------------------------------------------------------| +; Device Interrupt +; +; ENTRY : anything +; +; EXIT : all registers preserved +; +;-----------------------------------------------------------------------| + +Interrupt: + + PUSH DS ; (+1) save the world + PUSH ES ; (+2) + PUSH AX ; (+3) + PUSH BX ; (+4) + PUSH CX ; (+5) + PUSH DX ; (+6) + PUSH SI ; (+7) + PUSH DI ; (+8) + PUSH BP ; (+9) + + MOV CS:ssEntry,SS ; save entry SS + MOV CS:spEntry,SP ; and SP + + MOV AX,Offset PGROUP:TAIL ; set our DS, SS, BP, and SP + MOV CL,4 + SHR AX,CL + MOV CX,CS + ADD AX,CX + MOV BX,Offset DGROUP:MyStack + MOV DS,AX + MOV ES,AX + MOV SS,AX + MOV SP,BX + MOV BP,BX + + ; + ; call our function + ; + MOV AL,ReqHdr + 2 ; AL = Command Code + SHL AL,1 + CBW + MOV SI,Offset DGROUP:FuncTab + ADD SI,AX + CALL Word Ptr [SI] + + ; + ; copy back Request Header + ; + LES DI,RHptr ; ES:DI -> original space + MOV SI,Offset DGROUP:ReqHdr ; DS:SI -> our (updated) copy + CLD + XOR CH,CH + MOV CL,[SI] + REP MOVSB ; copy Request Header + + MOV SS,CS:ssEntry ; restore original stuff + MOV SP,CS:spEntry + + POP BP ; (+8) restore + POP DI ; (+7) + POP SI ; (+6) + POP DX ; (+5) + POP CX ; (+4) + POP BX ; (+3) + POP AX ; (+2) + POP ES ; (+1) + POP DS ; (+0) + RET + +HDR EndP + +PROG EndS + +TAIL Segment Public 'PROG' ; for finding end of code segment +TAIL EndS + + PAGE +;-----------------------------------------------------------------------| +; Data Segment +;-----------------------------------------------------------------------| + +DATA Segment Para Public 'DATA' + + Public ReqHdr + + DB StkSiz DUP (?) ; our stack, overflows into code +MyStack Label Word + +FuncTab Label Word + DW Offset PGROUP:Init + DW Offset PGROUP:MediaChe + DW Offset PGROUP:BuildBPB + DW Offset PGROUP:IoCtlIn + DW Offset PGROUP:Input + DW Offset PGROUP:ndInput + DW Offset PGROUP:InputSta + DW Offset PGROUP:InputFlu + DW Offset PGROUP:Output + DW Offset PGROUP:OutVerif + DW Offset PGROUP:OutStatu + DW Offset PGROUP:OutFlush + DW Offset PGROUP:IoCtlOut + DW Offset PGROUP:DevOpen + DW Offset PGROUP:DevClose + DW Offset PGROUP:RemMedia + +ReqHdr DB 256 DUP (?) ; copy of Request Header + +DATA EndS + +DTAIL Segment Public 'DATA' ; for finding end of data segment +DTAIL EndS + + END HDR ; of HDR.ASM diff --git a/assembly/Disables the cache on a 486 and Pentium processor.asm b/assembly/Disables the cache on a 486 and Pentium processor.asm new file mode 100644 index 0000000..740a3d8 --- /dev/null +++ b/assembly/Disables the cache on a 486 and Pentium processor.asm @@ -0,0 +1,41 @@ +; cache disable routine +; + public DisableCache + +code segment ; simple but effective for demonstration purposes +;* DisableCache() * +;* * +;* This routine disables cache(s) on a 486 or Pentium processor * +;* * +;* NOTE: due to the protection schemes incorporated into the 486 and * +;* Pentium processors, it will NOT work in virtual 8086 mode. * +;* * +;* written on Thursday, 2 November 1995 by Ed Beroset * +;* and released to the public domain by the author * + + .486P + +CR0_CD equ 040000000h ; Cache Disable bit of CR0 +CR0_NW equ 020000000h ; Not Write-through bit of CR0 + +DisableCache proc + pushf ; save the flags + push eax ; save eax + cli ; disable interrupts while we do this + mov eax,cr0 ; read CR0 + or eax,CR0_CD ; set CD but not NW bit of CR0 + mov cr0,eax ; cache is now disabled + wbinvd ; flush and invalidate cache + + ; the cache is effectively disabled at this point, but memory + ; consistency will be maintained. To completely disable cache, + ; the following two lines may used as well: + + or eax,CR0_NW ; now set the NW bit + mov cr0,eax ; turn off the cache entirely + pop eax ; restore eax + popf ; restore the flags + ret ; return to caller +DisableCache endp +code ends + end \ No newline at end of file diff --git a/assembly/Disk Watch.asm b/assembly/Disk Watch.asm new file mode 100644 index 0000000..c35f927 --- /dev/null +++ b/assembly/Disk Watch.asm @@ -0,0 +1,106 @@ +interrupts segment at 0h ; This is where the disk interrupt + org 13h*4 ; holds the address of its service routine +disk_int label dword +interrupts ends + +screen segment at 0B000h ; A dummy segment to use as the Extra +screen ends ; Segment so we can write to the display + +code_seg segment + assume cs:code_seg + org 0100h ; ORG = 100h to make this a .COM file +first: jmp load_watch ; First time through jump to initialize routine + + msg_part_1 db 'Disk error: ' ; Here are the error messages + msg_part_2 db 'No response Failed Seek NEC Error ' + db 'Bad CRC SeenDMA Overrun Impos Sector' + db 'No Addr MarkW. ProtectedErr Unknown ' + first_position dw ? ; Position of 1st char on screen + flags dw ? + screen_seg_offset dw 0 ; 0 for mono, 8000h for graphics + old_disk_int dd ? ; Location of old disk interrupt + ret_addr label dword ; Used in fooling around with + ret_addr_word dw 2 dup(?) ; the stack + +disk_watch proc far ; The disk interrupt will now come here + assume cs:code_seg + pushf ; First, call old disk interrupt + call old_disk_int + pushf ; Save the flags in memory location "FLAGS" + pop flags ; (cunning name) + jc error ; If there was an error, carry flag will have + jmp fin ; been set by Disk Interrupt +error: push ax ; AH has the status of the error + push cx ; Push all used registers for politeness + push dx + push di + push si + push es + lea si,msg_part_1 ; Always print "Disk Error: " part. + assume es:screen ; Use screen as extra segment + mov dx,screen + mov es,dx + mov di,screen_seg_offset ; DI will be pointer to screen position + add di,first_position ; Add to point to desired area on screen + call write_to_screen ; This writes 12 chars from [SI] to [DI] + mov dx,80h ; Initialize for later comparisons + mov cx,7 ; Loop seven times +e_loop: cmp ah,dh ; Are error code and DH the same? + je e_found ; If yes, Error has been found + add si,12 ; Point to next error message + shr dh,1 ; Divide DH by 2 + loop e_loop ; Keep going until matched DH = 0 + cmp ah,3 ; Error code no even number; 3 perhaps? + je e_found ; If yes, have found the error + add si,12 ; Err unknown; unknown error returned +e_found:call write_to_screen ; Write the error message to the screen + pop es ; Restore the registers + pop si + pop di + pop dx + pop cx + pop ax +fin: pop ret_addr_word ; Fooling with the stack. We want to + pop ret_addr_word[2] ; preserve the flags but the old flags + add sp,2 ; are still on the stack. First remove + push flags ; return address, then flags. Fill flags + popf ; from "FLAGS", return to correct addr. + jmp ret_addr +disk_watch endp + +write_to_screen proc near ; Puts 12 characters on screen + mov cx,12 ; Loop 12 times +w_loop: movs es:byte ptr[di],cs:[si] ; Move to the screen + mov al,7 ; Move screen attribute into screen buffer + mov es:[di],al + inc di ; Point to next byte in screen buffer + loop w_loop ; Keep going until done + ret +write_to_screen endp + +load_watch proc near ; This procedure initializes everything + assume ds:interrupts ; The data segment will be the interrupt area + mov ax,interrupts + mov ds,ax + + mov ax,disk_int ; Get the old interrupt service routine + mov old_disk_int,ax ; address and put it into our location + mov ax,disk_int[2] ; OLD_DISK_INT so we can call it. + mov old_disk_int[2],ax + + mov disk_int,offset disk_watch ; Now load the address of DskWatch + mov disk_int[2],cs ; routine into the disk interrupt + + mov ah,15 ; Ask for service 15 of INT 10h + int 10h ; This tells us how display is set up + sub ah,25 ; Move to twenty five places before edge + shl ah,1 ; Mult. by two (char & attribute bytes) + mov byte ptr first_position,ah ; Set screen cursor + test al,4 ; Is it a monochrome display? + jnz exit ; Yes - jump out + mov screen_seg_offset,8000h ; No, set up for graphics display +exit: mov dx,offset load_watch ; Set up everything but this program to + int 27h ; stay and attach itself to DOS +load_watch endp + code_seg ends + end first ; END "FIRST" so 8088 will go to FIRST first. \ No newline at end of file diff --git a/assembly/Drives Exist.asm b/assembly/Drives Exist.asm new file mode 100644 index 0000000..c79942a --- /dev/null +++ b/assembly/Drives Exist.asm @@ -0,0 +1,130 @@ +; Goes through drives A-Z and determines if they: +; 1) Exist +; 2) Are removable or fixed +; 3) Are local, remote, or shared +; 4) Are a floppy, hard, RAM, subst, or CD-ROM drive +; +; Callable from C as: void Drives_Exist(void); + +.model small +.286 + +DRIVEEXIST EQU 1 + +REMOVEDRV EQU 0 +FIXEDDRV EQU 1 + +LOCALDRV EQU 0 +REMOTEDRV EQU 1 +SHAREDRV EQU 2 + +FLOPPY EQU 0 +HARD EQU 1 +RAM EQU 2 +SUBST EQU 3 +CDROM EQU 4 + +.data +PUBLIC _drives + _drives db 26 dup(0,1,0,1) + ; default to not exist, fixed, local, hard drive + +.code + + PUBLIC _Drives_Exist +_Drives_Exist PROC NEAR + pusha + push es + + mov ah,19h + int 21h ; get start drive + push ax ; save start drive + + mov ax,40h + mov es,ax + mov bh,es:[10h] ; 40:10h is # of floppies-1 + shr bh,6 + inc bh ; # of actual floppy drives + mov bl,1 + mov di,offset _drives +nextchkfloppy: mov ax,4409h ; check if drive exists + int 21h + jc nextsetfloppy + test dh,10000000b ; check if SUBST drive + jz chkfloppy + dec bh ; dec actual drive count + mov byte ptr [di+3],SUBST +setfloppyexist: mov byte ptr [di],DRIVEEXIST + jmp nextsetfloppy +chkfloppy: dec bh ; dec actual drive count + js nextsetfloppy + mov byte ptr [di+1],REMOVEDRV + mov byte ptr [di+3],FLOPPY + jmp setfloppyexist +nextsetfloppy: add di,4 + inc bl + cmp bl,2 ; if B then jump back + je nextchkfloppy + + mov ch,24 ; loop 24 times (drives C - Z) + mov cl,3 ; start at C: +drivechkloop: mov ax,4409h ; check if drive exists + mov bl,cl ; set drive letter + int 21h ; 0 = default, 1 = A:, etc. + jc nextsetdrv + mov byte ptr [di],DRIVEEXIST + mov ax,4408h ; check if removable + int 21h + mov byte ptr [di+1],al ; set REMOVABLE or FIXED + mov bx,dx + mov dl,dh + shr dl,7 + and dh,00010000b + shr dh,4 + mov byte ptr [di+2],dh ; set REMOTE or LOCAL + or dl,dl ; if not SUBST, then jump + jz chkremote + mov byte ptr [di+3],SUBST + jmp nextsetdrv + +chkremote: cmp dh,REMOTEDRV ; if REMOTE, then check for CD ROM + je chkcdrom + + test bh,00000010b ; sharable? + jz drivenoshare + mov byte ptr [di+2],SHAREDRV +drivenoshare: test bl,00000010b ; RAM drive? + jnz nextsetdrv + mov byte ptr [di+3],RAM + jmp nextsetdrv + +chkcdrom: push cx + mov ax,1500h + xor bx,bx + int 2fh + pop cx + or bx,bx ; MSCDEX driver found? + jz nextsetdrv ; if not, jump to next drive setup + mov ax,150bh + dec cl ; 0=A:, etc. + int 2fh + inc cl + or ax,ax + jz nextsetdrv ; drive supported by MSCDEX? + mov byte ptr [di+3],CDROM + +nextsetdrv: add di,4 + inc cl + dec ch + jnz drivechkloop + + pop dx + mov ah,0eh + int 21h ; reset start drive + + pop es + popa + ret +_Drives_Exist ENDP + + END \ No newline at end of file diff --git a/assembly/Drives.asm b/assembly/Drives.asm new file mode 100644 index 0000000..55927f3 --- /dev/null +++ b/assembly/Drives.asm @@ -0,0 +1,161 @@ +; Goes thru drives A-Z and determines if they: +; 1) Exist +; 2) Are removable or fixed +; 3) Are local, remote, or shared +; 4) Are a floppy, hard, RAM, subst, or CD-ROM drive + +.model tiny +.286 + +DRIVEXISTS EQU 1 + +REMOVEDRV EQU 0 +FIXEDDRV EQU 1 + +LOCALDRV EQU 0 +REMOTEDRV EQU 1 +SHAREDRV EQU 2 + +FLOPPY EQU 0 +HARD EQU 1 +RAM EQU 2 +SUBST EQU 3 +CDROM EQU 4 + +.code + org 100h + +start: mov ah,19h + int 21h ; get start drive + mov [curdrive],al + + mov ax,40h + mov es,ax + mov bh,es:[10h] ; 40:10h is # of floppies-1 + shr bh,6 + inc bh ; # of actual floppy drives + mov bl,1 + mov di,offset drives +nextchkfloppy: mov ax,4409h ; check if drive exists + int 21h + jc nextsetfloppy + test dh,10000000b ; check if SUBST drive + jz chkfloppy + dec bh ; dec actual drive count + mov byte ptr [di+3],SUBST +setfloppyexist: mov byte ptr [di],DRIVEXISTS + jmp nextsetfloppy +chkfloppy: dec bh ; dec actual drive count + js nextsetfloppy + mov byte ptr [di+1],REMOVEDRV + mov byte ptr [di+3],FLOPPY + jmp setfloppyexist +nextsetfloppy: add di,4 + inc bl + cmp bl,2 ; if B then jump back + je nextchkfloppy + + mov ch,24 ; loop 24 times (drives C - Z) + mov cl,3 ; start at C: +drivechkloop: mov ax,4409h ; check if drive exists + mov bl,cl ; set drive letter + int 21h ; 0 = default, 1 = A:, etc. + jc nextsetdrv + mov byte ptr [di],DRIVEXISTS + mov ax,4408h ; check if removable + int 21h + mov byte ptr [di+1],al ; set REMOVABLE or FIXED + mov bx,dx + mov dl,dh + shr dl,7 + and dh,00010000b + shr dh,4 + mov byte ptr [di+2],dh ; set REMOTE or LOCAL + or dl,dl ; if not SUBST, then jump + jz chkremote + mov byte ptr [di+3],SUBST + jmp nextsetdrv + +chkremote: cmp dh,REMOTEDRV ; if REMOTE, then check for CD ROM + je chkcdrom + + test bh,00000010b ; sharable? + jz drivenoshare + mov byte ptr [di+2],SHAREDRV +drivenoshare: test bl,00000010b ; RAM drive? + jnz nextsetdrv + mov byte ptr [di+3],RAM + jmp nextsetdrv + +chkcdrom: push cx + mov ax,1500h + xor bx,bx + int 2fh + pop cx + or bx,bx ; MSCDEX driver found? + jz nextsetdrv ; if not, jump to next drive setup + mov ax,150bh + dec cl ; 0=A:, etc. + int 2fh + inc cl + or ax,ax + jz nextsetdrv ; drive supported by MSCDEX? + mov byte ptr [di+3],CDROM + +nextsetdrv: add di,4 + inc cl + dec ch + jnz drivechkloop + + mov ah,0eh + mov dl,[curdrive] + int 21h ; reset start drive + + mov cl,'A' ; output all existing drives + mov di,offset drives + mov ah,9 +drvdumploop: cmp byte ptr [di],DRIVEXISTS + jne nextdrvdump + mov al,cl + int 29h + xor dh,dh + mov dl,byte ptr [di+1] + shl dx,4 + add dx,offset removablemsg + int 21h + xor dh,dh + mov dl,byte ptr [di+2] + shl dx,3 + add dx,offset localmsg + int 21h + xor dh,dh + mov dl,byte ptr [di+3] + shl dx,3 + add dx,offset typemsg + int 21h + mov dx,offset crlf + int 21h + +nextdrvdump: add di,4 + inc cl + cmp cl,'Z' + jbe drvdumploop + + ret + +curdrive db 0 +drives db 26 dup(0,1,0,1) + ; default to not exist, fixed, local, hard drive +crlf db 10,13,'$' +removablemsg db ': Removable $' + db ': Fixed $' +localmsg db 'Local $' + db 'Remote $' + db 'Shared $' +typemsg db 'Floppy $' + db 'Hard $' + db 'RAM $' + db 'Subst $' + db 'CD-ROM $' + + end start diff --git a/assembly/EXECSUB - execute program from compiled BASIC - requires DOS 2.00.asm b/assembly/EXECSUB - execute program from compiled BASIC - requires DOS 2.00.asm new file mode 100644 index 0000000..4717b0f --- /dev/null +++ b/assembly/EXECSUB - execute program from compiled BASIC - requires DOS 2.00.asm @@ -0,0 +1,199 @@ +; This version allows one BASIC program to call another +; +; CALL EXECSUB(PROG$,PARM$,FCB1$,FCB2$,RETCD%) +; PROG$ is the program name (e.g. 'command.com') +; PARM$ is the parameter to be passed to the program (e.g. '/c dir *.bas') +; FCB1$ is the first file control block (required by some programs) +; FCB2$ is the second file control block (required by some programs) +; RETCD% is the error return code + + skip equ 2 ; 1 for interpretive, 2 for compiled + +cseg segment para public 'code' +public execsub +execsub proc far + + assume cs:cseg,ds:cseg,ss:nothing,es:nothing + +basicds equ 510h +i24ip equ 90h +i24cs equ 92h +i1bip equ 6ch +i1bcs equ 6eh +i1cip equ 70h +i1ccs equ 72h + +b24ip equ 51ah +b24cs equ 51ch +b1bip equ 516h +b1bcs equ 518h +b1cip equ 512h +b1ccs equ 514h + + push bp + mov bp,sp + jmp p010 + +stak equ this byte + dw 0 ; save sp + dw 0 ; save ss + +prm1 equ this byte + dw 0 ; environment +prm2 equ this word + dw 0 ; command line - ip & cs + dw 0 +prm3 equ this byte + dw 0 ; default FCB - ip & cs + dw 0 +prm4 equ this byte + dw 0 ; second default FCB - ip & cs + dw 0 + +p010: + xor ax,ax ; get psp + mov es,ax ; es=0 + mov bx,ds ; save ds + mov ds,ax ; ds=0 + cli + + push ds:[basicds] ; save basic's ds + + push ds:[i24ip] ; save int 24h and shadow + push ds:[b24ip] + push ds:[b24ip] + pop ds:[i24ip] + + push ds:[i24cs] + push ds:[b24cs] + push ds:[b24cs] + pop ds:[i24cs] + + push ds:[i1bip] ; save int 1bh and shadow + push ds:[b1bip] + push ds:[b1bip] + pop ds:[i1bip] + + push ds:[i1bcs] + push ds:[b1bcs] + push ds:[b1bcs] + pop ds:[i1bcs] + + push ds:[i1cip] ; save int 1ch and shadow + push ds:[b1cip] + push ds:[b1cip] + pop ds:[i1cip] + + push ds:[i1ccs] + push ds:[b1ccs] + push ds:[b1ccs] + pop ds:[i1ccs] + + sti + mov ds,bx ; restore ds + + mov di,4f2h ; point to dos comm. area + mov ax,es:[di] ; get psp segment + mov es,ax + mov di,2 + mov bx,es:[di] ; get top of memory + sub bx,ax ; subtract psp + mov ah,4ah + int 21h ; free memory + jnc p020 ; no error + mov ah,0 ; memory error + jmp p090 ; to error control + +p020: mov si,[bp+12] ; point to parm$ + add si,skip + mov ax,[si] + mov si,offset prm2 ; establish command line + mov cs:[si],ax + mov ax,ds + mov cs:[si+2],ax + + mov si,[bp+10] ; point to fcb1$ + add si,skip + mov ax,[si] + mov si,offset prm3 + mov cs:[si],ax + mov ax,ds + mov cs:[si+2],ax + + mov si,[bp+8] ; point to fcb2$ + add si,skip + mov ax,[si] + mov si,offset prm4 ; establish second fcb + mov cs:[si],ax + mov ax,ds + mov cs:[si+2],ax + + push bp ; save registers + push ds + push es + pushf + mov si,offset stak ; save stack + mov cs:[si],sp + mov cs:[si+2],ss + + mov ah,4bh ; load prog + mov al,0 ; load & execute + mov si,[bp+14] ; point to prog$ + add si,skip + mov dx,[si] + push cs + pop es + mov bx,offset prm1 ; point to parameter + int 21h ; load & execute program + jnc p050 ; no error + mov ah,1 ; set error code + jmp p060 + +p050: mov ax,0 ; clear error + +p060: mov bx,cs ; restore stack + mov ds,bx + mov si,offset stak + cli ; no interrupts + mov sp,cs:[si] + mov ss,cs:[si+2] + sti ; allow interrupts + + popf ; restore registers + pop es + pop ds + pop bp + + mov cx,ds ; save ds + xor bx,bx + mov ds,bx ; ds=0 + cli + + pop ds:[b1ccs] ; restore int 1ch + pop ds:[i1ccs] + pop ds:[b1cip] + pop ds:[i1cip] + + pop ds:[b1bcs] ; restore int 1bh + pop ds:[i1bcs] + pop ds:[b1bip] + pop ds:[i1bip] + + pop ds:[b24cs] ; restore int 24h + pop ds:[i24cs] + pop ds:[b24ip] + pop ds:[i24ip] + + pop ds:[basicds] ; restore basic's ds + sti + mov ds,cx + +p090: mov si,[bp+6] ; point to RETCD% + mov [si],ax ; return error, if any + + pop bp ; return to caller + ret 10 + +execsub endp +cseg ends +end diff --git a/assembly/Ejects a SCSI tape (or CD-ROM) from a drive.asm b/assembly/Ejects a SCSI tape (or CD-ROM) from a drive.asm new file mode 100644 index 0000000..21e35f9 --- /dev/null +++ b/assembly/Ejects a SCSI tape (or CD-ROM) from a drive.asm @@ -0,0 +1,106 @@ +; eject a tape (or CD) from a device +; +; note that this is a VERY terse code sample! It is assumed that the +; reader is already familiar with SCSI and ASPI to some degree. +; + .MODEL small + .STACK 1000h + .386 + +;* structures * +SCSIRequestBlock struc + CommandCode db 2 ; SCSI request + Status db 0 ; returned after command + HostAdapterNum db 0 ; default is 0 (first adapter) + SCSIReqFlags db 0 ; + Reserved1 db 4 dup (0) ; + TargetID db 0 ; set to device target ID + LUN db 0 ; defaults to 0 + DataLength dd 0 ; + SenseLength db 16 ; usu. sufficient length + DataPointer dd 0 ; no data + SRBLinkPointer dd 0 ; no linking + CDBLength db 10 ; always sufficient length + AdapterStatus db 0 ; + TargetStatus db 0 ; + PostRoutinePtr dd 0 ; no post routine is default + ASPIWorkspace db 34 dup (0) ; req'd but not used + CDB db 10 dup (0) ; SCSI Command Descriptor Blk + SenseData db 16 dup (0) ; +SCSIRequestBlock ends + + .DATA + +DOS_OPEN_HANDLE = 03dh +DOS_CLOSE_HANDLE = 03eh +DOS_IOCTL = 044h +IOCTL_RX_CTL_DATA = 02h +DOS_INT = 21h + +ASPI_Entry dd ? +SRB SCSIRequestBlock <> +crlf equ 13,10 +ErrMsg db "ERROR: no ASPI manager detected. ",crlf,'$' +OKMsg db "All is well.",crlf,'$' +SCSIMgrString db "SCSIMGR$",0 + + .CODE +begin proc + .STARTUP + call GetASPIAddress ; + jnb @@AllOK ; + mov dx, OFFSET ErrMsg ; + jmp @@ErrorExit ; +@@AllOK: +; +; here's the eject sequence +; + mov [(SRB.CDB) + 0],01Bh ; load/unload command + mov [(SRB.CDB) + 4],0 ; 00 = unload, 01=load, 02=retension + mov [(SRB.TargetID)], 2 ; SCSI ID of target device + push SEG SRB ; + push OFFSET SRB ; + call [ASPI_Entry] ; sometimes it takes 2 requests + call [ASPI_Entry] ; + add sp,4 ; + mov dx,OFFSET OKMsg ; + xor ah,ah ; + mov al,[(SRB.Status)] ; +@@ErrorExit: ; ds:dx ==> ASCIIZ error string + push ax + mov ah,9 ; + int 21h ; + pop ax ; +@@NoError: + .EXIT 0 +begin endp + +GetASPIAddress proc C + push bx + push cx + push ds + xor ax,ax ; + mov WORD PTR [ASPI_Entry],ax ; + mov WORD PTR [ASPI_Entry+2],ax ; + lea dx,[SCSIMgrString] ;ds:dx ==> 'SCSIMGR' string + mov ah,DOS_OPEN_HANDLE ; open request + int DOS_INT ; + jb @@exit ; + mov dx,ss ; + mov ds,dx ; + lea dx,[ASPI_Entry] ; + mov cx,4 ; + mov bx,ax ; + mov ax,DOS_IOCTL SHL 8 OR IOCTL_RX_CTL_DATA + int DOS_INT ; + jb @@exit ; + mov ah,DOS_CLOSE_HANDLE ; + int DOS_INT ; +@@exit: + pop ds + pop cx + pop bx + ret ; +GetASPIAddress endp + + END \ No newline at end of file diff --git a/assembly/FXN4BH --- demonstrate use of the PC-DOS 2.0 EXEC function call 4BH.asm b/assembly/FXN4BH --- demonstrate use of the PC-DOS 2.0 EXEC function call 4BH.asm new file mode 100644 index 0000000..6adc676 --- /dev/null +++ b/assembly/FXN4BH --- demonstrate use of the PC-DOS 2.0 EXEC function call 4BH.asm @@ -0,0 +1,162 @@ +; +cr equ 0dh ;ASCII carriage return +lf equ 0ah ;ASCII line feed + ; +cseg segment para public 'CODE' + ; + assume cs:cseg,ds:data,ss:stack + ; +demo proc far + ;at entry DS & ES = PSP + push ds ;Save address for final + xor ax,ax ;FAR RET to PC-DOS on stack + push ax + ;save copy of SS:SP for use + ;after return from overlay + mov cs:STK_SEG,ss + mov cs:STK_PTR,sp + ; + ;Reserve 1000H bytes for + ;this loader and release + ;the rest of memory for + ;use by the overlayed program. + mov bx,100h ;ES=segment of PSP of loader + mov ah,4ah ;BX=paragraphs to reserve + int 21h + ;make the messages in data + ;segment addressable + mov ax,seg DATA + mov ds,ax + mov es,ax + ;jump if memory + ;de-allocation failed + jc ALLOC_ERR + ;print memory successfully + ;released + mov dx,offset MSG2 + mov ah,9 + int 21h + ; + ;now load and execute + ;the overlaid program. + mov dx,offset PGM_NAME + mov bx,offset PAR_BLK + mov al,0 + mov ah,4bh + int 21h + ;restore stack pointers + ;to state before EXEC call + mov ss,cs:STK_SEG + mov sp,cs:STK_PTR + ;Make data segment + ;addressable again + mov ax,seg DATA + mov ds,ax + ;print message that loader + ;successfully regained control + mov dx,offset MSG3 + mov ah,9 + int 21h + ;now exit to PC-DOS + ret + +alloc_err: ;come here if memory + ;cannot be released + mov dx,offset MSG1 + mov ah,9 + int 21h ;print error message and + ret ;exit to PC-DOS + ; +demo endp + ; + ;these two variables must + ;reside in Code Segment so + ;that they are addressable + ;after return from overlay. +stk_seg dw 0 ;original SS contents +stk_ptr dw 0 ;original SP contents + ; +cseg ends + + ;declare a stack area + ;for use by this loader +stack segment para stack 'STACK' + ;allow 64 bytes in this case + db 64 dup (?) +stack ends + + ;declare data segment to + ;contain variables and tables +data segment para public 'DATA' +; +msg1 db cr,lf + db 'Unable to release memory.' + db cr,lf,'$' +msg2 db cr,lf + db 'Memory above loader released.' + db cr,lf,'Now loading CHKDSK.COM.' + db cr,lf,'$' +msg3 db cr,lf + db 'Loader regained control from CHKDSK,' + db cr,lf + db 'now making final exit to PC-DOS.' + db cr,lf,'$' +; + ;drive, path, and name of program + ;to be loaded and executed. +pgm_name db '\CHKDSK.COM',0 +; +par_blk dw ENVIR ;segment address of + ;environment descriptor + ; + ;full address of command line + ;to be passed at offset 80H + dw offset CMD_LINE ;in overlaid + dw seg CMD_LINE ;program's PSP + ; + ;full address of default + ;File Control Block to be + ;passed at offset 5CH in + dw offset FCB1 ;overlaid + dw seg FCB1 ;program's PSP + ; + ;full address of default + ;File Control Block to be + ;passed at offset 6CH in + dw offset FCB2 ;overlaid + dw seg FCB2 ;program's PSP +; + ;actual command line tail + ;to be passed to overlay +cmd_line db 4,' *.*',cr,0 +; + ;first default FCB to +fcb1 db 0 ;be passed to overlay + db 11 dup ('?') + db 25 dup (0) + + ;second default FCB to +fcb2 db 0 ;be passed to overlay + db 11 dup (' ') + db 25 dup (0) +; +data ends + + ;declare separate data + ;segment to contain + ;environment descriptor +envir segment para 'ENVIR' + ; + ;Search path used by PC-DOS + ;to look for commands or + ;batch files not found in + db 'PATH=',0 ;the current directory + ; + ;Search path used by PC-DOS + ;to locate COMMAND.COM + db 'COMSPEC=A:\COMMAND.COM',0 + db 0 ;extra 0 byte designates + ;end of environment +envir ends + + end demo \ No newline at end of file diff --git a/assembly/Fetches and prints the network serial number under Novell Netware 3.11.asm b/assembly/Fetches and prints the network serial number under Novell Netware 3.11.asm new file mode 100644 index 0000000..13995ef --- /dev/null +++ b/assembly/Fetches and prints the network serial number under Novell Netware 3.11.asm @@ -0,0 +1,97 @@ +TITLE "NetWare serial number routine" +; Net_SN.Asm +; +; I've tested this code with Netware 386 version 3.11, +; but it may also work with 2.15. It wasn't documented +; for 2.15, but it may still have existed. +; + + .MODEL SMALL + + .STACK 100h + .DATA +AAMn macro num + db 0d4h, num +endm + +STDOUT = 1 ; handle for stdout + + SNREQBUFF struc + MyLength DW 1 ; request structure length - 2 + Function DB 12h ; function number of GetNetworkSerialNumber + SNREQBUFF ends + + SNREPLYBUFF struc + MyLength DW 6 ; reply structure length - 2 + NetSN DD 0 ; network serial number in big endian packed BCD + AppNumber DW 0 ; Application number in same format + SNREPLYBUFF ends + + U_Request SNREQBUFF <> + U_Reply SNREPLYBUFF <> + SerialNum DB "00000000",0dh, 0ah + SerialLen = $ - SerialNum + + .CODE +; +; Test code gets network serial number and prints it to stdout +; +Start: + mov ax,@data + mov ds,ax ; set up the data segment + call NetworkSN +Exit: + mov ah,04ch ; return with error code preset in AL + int 21h + +; +; here's the Network stuff +; +NetworkSN proc + push ds + push si + push di + push es + push dx + push cx + + lea si,[U_Request] ; prepare to request data + lea di,[U_Reply ] ; prepare to receive data + mov ax,ds + mov es,ax + mov ah,0e3h ; Get File Server Serial Number + int 21h + jc @@NoMore + + lea si,[U_Reply.NetSN] ; point ds:si at binary data + lea di,[SerialNum] ; and point es:di at target ASCII string + mov cx,4 ; loop four times (once for each SN digit pair) + cld ; count up + +@@convbyte: + lodsb ; read a byte + AAMn 16 ; convert to two-digit BCD in ah,al + xchg ah,al ; swap so that memory image will be correct + or ax,3030h ; convert both to ASCII numbers + stosw ; put 'em in our table + loop @@convbyte + + lea dx,[SerialNum] ; we're going to point ds:dx to string + mov cx,SerialLen ; load the length of the string + mov bx,STDOUT ; print to STDOUT + mov ah,40h ; DOS function to print string + int 21h ; do it + mov al,0 ; return with appropriate error code + +@@NoMore: + pop cx + pop dx + pop es + pop di + pop si + pop ds + ret + +NetworkSN endp + + END Start diff --git a/assembly/Game Port.asm b/assembly/Game Port.asm new file mode 100644 index 0000000..7a19dbf --- /dev/null +++ b/assembly/Game Port.asm @@ -0,0 +1,37 @@ +; GAMEPORT.ASM +; + + .MODEL TINY + + .DATA + + yes DB 13,10,"Game port is installed.",13,10,"$" + no DB 13,10,"Game port is not installed.",13,10,"$" + + .CODE + ORG 100h + +start: mov al, 1 ;value to write to port + mov dx, 201h ;port number + out dx, al ;write to port + mov cx, 0F00h ;# of loops + +port_loop: + in al, dx ;read from port + and al, 0Fh ;if jstick present, then AL should be + cmp al, 0Fh ; 0Fh after ANDing with 0Fh. + je jstick_exists + loop port_loop + mov dx, OFFSET no ;gameport not installed + jmp SHORT done + +jstick_exists: + mov dx, OFFSET yes ;gameport installed + +done: mov ah, 9h + int 21h + + mov ax, 4c00h + int 21h + +END start \ No newline at end of file diff --git a/assembly/Get Space.asm b/assembly/Get Space.asm new file mode 100644 index 0000000..cfa3967 --- /dev/null +++ b/assembly/Get Space.asm @@ -0,0 +1,74 @@ +CSEG SEGMENT +PUBLIC GETSPACE +GETSPACE PROC FAR + + ASSUME CS:CSEG + PUSH BP + MOV BP,SP + MOV BX,[BP]+6 + MOV DI,[BX]+2 + MOV CX,8 + MOV AL,' ' + CLD + REP STOSB + MOV BX,[BP]+8 + MOV SI,[BX]+2 + MOV AX,[SI] + AND AL,0DFH + CMP AL,41H + JGE CKVER + JMP EXITSPC + +CKVER: + PUSH AX + MOV AH,30H + INT 21H + XCHG AL,AH + +SPACE20: + POP DX + XOR DL,40H + MOV AH,36H + INT 21H + CMP AX,0FFFFH + JE EXITSPC + XOR DX,DX + MUL CX + XCHG BX,CX + MUL CX + PUSH AX + PUSH DX + +ENDSPC: + MOV BX,[BP]+6 + MOV DI,[BX]+2 + ADD DI,7 + POP DX + POP AX + +HEXTODEC: + MOV SI,10 + PUSH AX + MOV AX,DX + XOR DX,DX + DIV SI + POP CX + PUSH AX + MOV AX,CX + DIV SI + POP SI + OR DL,30H + MOV BYTE PTR [DI],DL + DEC DI + XCHG DX,SI + OR AX,AX + JNZ HEXTODEC + +EXITSPC: + POP BP + RET 4 + RET + +GETSPACE ENDP +CSEG ENDS + END \ No newline at end of file diff --git a/assembly/Get current Segment Values.asm b/assembly/Get current Segment Values.asm new file mode 100644 index 0000000..0fe9335 --- /dev/null +++ b/assembly/Get current Segment Values.asm @@ -0,0 +1,79 @@ +; +; +; Synopsis getseg(pcs, pds, pes, pss, psi, pdi, psp, pflag); +; +; unsigned *cs Pointer to where code segment address goes +; unsigned *ds Pointer to data segment +; unsigned *es Pointer to extra segment +; unsigned *ss Pointer to stack segment +; unsigned *si Pointer to si register +; unsigned *di Pointer to di register +; unsigned *sp Pointer to sp register +; unsigned *flag Returns flag +; +; +; Returns cs value of Code segment +; ds value of Data segment +; es value of Extra segment +; ss value of Stack segment +; si value of SI register ****NOT RELIABLE**** +; di value of DI register +; sp value of Stack Pointer +; flag value of Flags register +; +; +; + + +pgroup group prog +prog segment byte public 'PROG' ; Combine with C 'PROG' program segment + assume cs:pgroup + public getseg +getseg proc near + push bp ; Save the frame pointer + mov bp,sp + mov si,[bp + 04] ; Get the values for the registers + mov ax,[si] + mov si,[bp + 06] + mov bx, [si] + mov si,[bp + 08] + mov cx, [si] + mov si,[bp + 10] + mov dx,[si] +;============================================================================== + mov ax, cs ;Get value of code segment + mov bx, ds ;data segment + mov cx, es ;extra segment + mov dx, ss ;stack segment + + +;============================================================================== + +uret: mov bp,sp ; Now recover the values of the + mov si,[bp + 04] ; parameters + mov [si],ax + mov si, [bp + 06] + mov [si], bx + mov si, [bp + 08] + mov [si], cx + mov si, [bp + 10] + mov [si], dx + mov si, [bp + 12] + mov [si], si + mov si, [bp + 14] + mov [si], di + mov si, [bp + 16] + mov [si], sp + mov al, 00 ;zero out al + lahf ;load flag into ah + mov si, [bp + 18] + mov [si], ax + + + mov ax,0 ; No error + +quit: pop bp ; Get the original frame pointer. + ret +getseg endp +prog ends + end \ No newline at end of file diff --git a/assembly/Get disk free space function.asm b/assembly/Get disk free space function.asm new file mode 100644 index 0000000..1f44ea1 --- /dev/null +++ b/assembly/Get disk free space function.asm @@ -0,0 +1,123 @@ +; CALL FRESPACE(AH,AL,BH,BL,CH,CL). CL SHOULD BE 0 for default +; drive 1 for A, 2 for B, 3 for C, etc. The value of the +; other variables does not matter. They will come back +; with a meaningful value. +; +; AN EXAMPLE PROGRAM: +; +; 10 defint a-z +; 20 color 7,1:cls +; 30 test1=1:ah=0:al=0:bh=0:ch=0:cl=1:test2=2 +; 35 INPUT"DRIVE 0=DEFAULT, 1=A, 2=B, 3=C";CL +; 37 PRINT"JUST BEFORE CALL" +; 40 CALL FRESPACE(AH,AL,BH,BL,CH,CL) +; 45 PRINT"JUST AFTER CALL" +; 50 PRINT" AH=";AH;" AL=";AL;" BH=";BH;" BL=";BL;" CH=";CH;" CL=";CL; +; 60 UFREE!=256*AH+AL +; 70 UBYTES!=256*BH+BL +; 80 USECTOR!=256*CH+CL +; 90 PRINT"UFREE!=";UFREE!;" UBYTES!=";UBYTES!;" USECTOR!=";USECTOR! +; 100 FRESPACE!=UFREE!*UBYTES!*USECTOR! +; 110 PRINT"FRESPACE!=";FRESPACE! +; 120 PRINT"THIS SHOULD BE 1",TEST1 +; 130 PRINT"THIS SHOULD BE 2",TEST2 +; + +get_spa equ 36h ;Get disk free space function call +doscall equ 21h ;DOS interrupt number + +dgroup group datarea +datarea segment para public 'DATA' + +ah_ret dw ? ;ah to be sent back +al_ret dw ? ;al to be sent back +bh_ret dw ? ;bh to be sent back +bl_ret dw ? ;bl to be sent back +ch_ret dw ? ;ch to be sent back +cl_ret dw ? ;cl to be sent back + +datarea ENDS +; +cseg segment 'CODE' + assume cs:cseg + public frespace +frespace proc far + push bp ;BP from BASIC + mov bp,sp ;set base for parm list + push ds ;DS from basic work area + push es ;ES from basic work area + mov ax,datarea ;establish data addressability + mov ds,ax ;now DS is local data + assume ds:datarea +; +; +; +; + push bp + sub ax,ax + mov si,ss:[bp+6] ;get addr of parameter + mov al,es:[si] ;get value of parm + mov dx,ax ;dl contains the drive number on call + ;dh will be zero + mov ah,get_spa ;get space function number + int doscall ;Call DOS + +; Move the values into local work area to prepare to send back to basic + xchg dx,ax ;must have a word. Want to zero out DH. + sub ax,ax ; produce the zero + xchg dx,ax ; DX is now zero. + ; DH is what we really want as zero. + + mov dl,ah ;want to send back a byte + mov ah_ret,dx ; prepare to return ah + + mov dl,al ;want to send back a byte + mov al_ret,dx ; prepare to return al + + mov dl,bh ;want to send back a byte + mov bh_ret,dx ; prepare to return bh + + mov dl,bl ;want to send back a byte + mov bl_ret,dx ; prepare to return bl + + mov dl,ch ;want to send back a byte + mov ch_ret,dx ; prepare to return ch + + mov dl,cl ;want to send back a byte + mov cl_ret,dx ; prepare to return cl + + +; Go back + pop bp ;get back Basic's workspace + mov ax,cl_ret + mov si,ss:[bp+6] + mov es:[si],ax ;return cl + + mov ax,ch_ret + mov si,ss:[bp+8] + mov es:[si],ax ;return ch + + mov ax,bl_ret + mov si,ss:[bp+10] + mov es:[si],ax ;return bl + + mov ax,bh_ret + mov si,ss:[bp+12] + mov es:[si],ax ;return bh + + mov ax,al_ret + mov si,ss:[bp+14] + mov es:[si],ax ;return al + + mov ax,ah_ret + mov si,ss:[bp+16] + mov es:[si],ax ;return ah +; + pop es + pop ds + pop bp + ret 12 ;return to basic 6 parameters were sent +frespace endp +;----------------------------------------------------------------------- +cseg ends + end ;end for assembler \ No newline at end of file diff --git a/assembly/Gets a list of Queue servers under Novell Netware 3.11.asm b/assembly/Gets a list of Queue servers under Novell Netware 3.11.asm new file mode 100644 index 0000000..dd278cd --- /dev/null +++ b/assembly/Gets a list of Queue servers under Novell Netware 3.11.asm @@ -0,0 +1,162 @@ +%PAGESIZE 55,200 +%SUBTTL "Get List of Queue Servers under Netware 3.11" +; Net_Q.Asm +; + + .MODEL SMALL + + + .STACK 100h + +DOSint macro function + mov ah,function + int 21h +ENDM + + .DATA + STDOUT = 1 ; the stdout device handle + + DOS_WRITE_TO_HANDLE = 040h ; Write to File Handle + DOS_TERMINATE_EXE = 04Ch ; Terminate Program + + NOVELL_FUNCTION = 0E3h +; +; Object Types +; note that they're all big endian +; + OT_USER = 0100h + OT_USER_GROUP = 0200h + OT_PRINT_QUEUE = 0300h ; Print Queue object type + OT_FILE_SERVER = 0400h + + +BragMsg DB 0dh,0ah,"NET_Q.EXE",9,"WWW" + DB 9,"Version 1.00",0dh,0ah + DB 9,9,"released to the public domain by the author",0dh,0ah,0dh,0ah +BragLen = $ - BragMsg + +Crlf DB 0dh,0ah,0 + + SCAN_REQ STRUC ; bindery ScanObject request packet structure + MyLength DW 55 ; the length of this buffer + Function DB 37h ; scan object subfunction number + ObjectID DD -1 ; all ones for initial object search + ObjectType DW -1 ; wild card -- looks for all objects + ObjNameLen DB 1 ; at least one character + ObjName DB 47 DUP ('*') ; fill with wildcards to start + SCAN_REQ ENDS + + SCAN_REP STRUC ; bindery ScanObject request packet structure + MyLength DW 57 + RObjectID DD 0 ; all ones for initial object search + RObjectType DW 0 ; wild card -- looks for all objects + RObjName DB 48 DUP (0) ; fill with wildcards to start + ObjFlag DB 0 + ObjSecurty DB 0 + ObjHasProp DB 0 + ENDS + + ScanObjReq SCAN_REQ <> + ScanObjRep SCAN_REP <> + + .CODE + +; +; This is the main part of the code +; +; Test code gets and prints the name of all print queues from the +; logged server -- NO ERROR CHECKING IS DONE, so be careful! +; + +Start: + mov ax,@data + mov ds,ax ; set up the data segment + mov dx,OFFSET BragMsg ; prepare to print out brag line(s) + mov cx,BragLen + mov bx,STDOUT ; print to STDOUT + DOSint DOS_WRITE_TO_HANDLE + jc Exit ; if carry is set, there was an error + + mov [ScanObjReq.ObjectType],OT_PRINT_QUEUE + ; + ; in this case the name is already set up, (a wildcard) but if a + ; specific name were desired, it would be moved to + ; ScanObjReq.ObjName, with the appropriate length (not including + ; optional terminating NULL char set up in ScanObjReq.ObjNameLen. + ; +@@MoreQueues: + call BindScan + jc Exit + + lea dx,[ScanObjRep.ObjName] + call Puts + lea dx,[Crlf] + call Puts + jmp @@MoreQueues + +Exit: + DOSint DOS_TERMINATE_EXE ; return with error code preset in AL + +; +; BindScan +; +; scans the bindery for the object name set in the request buffer +; +BindScan proc + push ds si di es dx ax + + lea si,[ScanObjReq] ; point DS:DI to request buffer + mov dx,ds + mov es,dx + lea di,[ScanObjRep] ; point ES:SI to reply buffer + DOSint NOVELL_FUNCTION + jb @@Exit + + cld ; make sure to count up + mov si,OFFSET ScanObjRep.ObjectID + mov di,OFFSET ScanObjReq.ObjectID + movsw + movsw + + clc + +@@Exit: + pop ax dx es di si ds + ret + +BindScan endp + +; Puts +; +; prints a NUL terminated string to stdout +; +; INPUTS: ds:dx points to ASCIIZ string +; +; OUTPUTS: prints string to stdout +; +; RETURNS: ax = number of bytes actually printed +; carry set on error +; +; DESTROYED: ax +; +Puts proc + push bx cx di es + + push ds + pop es + mov cx,0ffffh ; maximum length of string + mov di,dx + cld + mov al,0 ; we're looking for NUL + repne scasb + dec di + mov cx,di + sub cx,dx + mov bx,STDOUT ; write to this device + DOSint DOS_WRITE_TO_HANDLE + + pop es di cx bx + ret +Puts endp + + END Start \ No newline at end of file diff --git a/assembly/Inthand.asm b/assembly/Inthand.asm new file mode 100644 index 0000000..88642c4 --- /dev/null +++ b/assembly/Inthand.asm @@ -0,0 +1,44 @@ +; +progseg segment para public 'CODE' + public setcom + assume cs:progseg, ds:progseg, es:progseg + org 100h +doscall equ 21h +oldint equ 16h +; +startup proc far + jmp setup +; +setcom proc far +; jmp cs:[interupt] + pushf + call cs:[interupt] + RET 2 +setcom endp +; +save db 0 +interupt label dword +vector db 8 dup(0) ;only 4 needed 4 more for safety +; +setup: + mov ah,35h ;get interupt vector address function + mov al,oldint ;keyboard interupt vector + int doscall ;go get it +; + mov word ptr vector,bx ;save offset + mov bx,es ;get segment address + mov word ptr vector+2,bx ;save segment +; + mov dx,offset setcom ;get new vector address + mov ax,cs + mov ds,ax ;set segment + mov ah,25h ;set interupt vector address function + mov al,oldint ;set to our new interupt vector + int doscall ;set the interupt +; + mov dx,offset setup ;terminate and stay resident + int 27h +startup endp +progseg ends +; + end startup \ No newline at end of file diff --git a/assembly/Issues the CPUID instruction to fetch the family, model and stepping ID.asm b/assembly/Issues the CPUID instruction to fetch the family, model and stepping ID.asm new file mode 100644 index 0000000..2f6c99c --- /dev/null +++ b/assembly/Issues the CPUID instruction to fetch the family, model and stepping ID.asm @@ -0,0 +1,72 @@ +; pentid.asm +; +; this program issues the CPUID instruction (valid only on Pentium class +; processors!) and prints three hex digits which correspond to the +; family, model, and stepping ID. If you run this on a 8088, 80386, or +; 80486 processor, it will return to the command line without printing +; anything. If you run this on an 80286, NEC V20 or NEC V30, your machine +; will probably crash. If you're smart enough to run this program only +; on Pentium machines, you can remove all the code between Start and +; RealTest and you'll reduce the code size from 84 to 49 bytes. +; +; TASM /m2 pentid ; two pass mode +; TLINK /Tdc pentid ; link as COM file +; + .MODEL tiny + .586 ; allow Pentium instructions + + .CODE + ORG 100h +Start: + pushf ; assure this is a Pentium + pop ax ; flags in ax + rol ah,1 ; put EFLAGS reserved bit 15 in CF + sahf ; store in regular flags + jc BailOut ; if carry flag set, it's an 8088! + ; assume we're 80386+ (80286 users prepare for crash) + pushfd ; push EFLAGS + pop eax ; now pull them into reg + mov ecx,eax ; save original copy in ECX + xor eax,00200000h ; flip bit 21 (CPUID capable) + push eax ; pass altered flags back on stack + popfd ; allow cpu to balk + pushfd ; see what it did with our flag + pop eax ; let's test... + cmp eax,ecx ; if bit can't be flipped it's + je BailOut ; not a Pentium processor +RealTest: ; + xor eax,eax ; clear eax + inc al ; put a 1 in eax + cpuid ; opcode is 0fh 0a2h + mov bx,ax ; save the lower 16 bits + call hex ; convert low nybble (step ID) + mov ah,'$' ; add terminator char + push ax ; put it on stack + mov ax,bx ; recall other bits + shr al,4 ; get 'em all lined up + call hex ; convert middle nybble (model) + xchg al,ah ; swap results + call hex ; convert third nybble (family) + push ax ; put that on stack, too + mov dx,sp ; print the stack (!) + mov ah,9h ; print string function + int 21h ; DOS interrupt + pop eax ; restore stack + mov al,bl ; recall original value +BailOut: + mov ah,4Ch ; terminate program with + int 21h ; model & stepping ID as errcode + +; +; convert low nybble of al to ASCII char. +; al = {00h - 0Fh } becomes al = { '0'-'9', 'A'-'F' } +; +hex proc + and al,0Fh ; use only low nybble in al + cmp al,0Ah ; set CY flag appropriately + sbb al,69h ; al = al - 069h - (al > 10) + das ; al = 30h-39h or 41h-45h + ret ; pass back our result +hex endp + + END Start \ No newline at end of file diff --git a/assembly/MSDOS 2.00 Function Library for Lattice C.asm b/assembly/MSDOS 2.00 Function Library for Lattice C.asm new file mode 100644 index 0000000..d61e89b --- /dev/null +++ b/assembly/MSDOS 2.00 Function Library for Lattice C.asm @@ -0,0 +1,58 @@ +subttl - +;; +;;FUNCTION: Sets and returns switch char- +;; acter and device availability. +;; +;; +;;CALL: +;; +;; ret= _charop(al,dl) +;; int ret; DL return value, +;; int al; charoper function +;; int dl; charoper data +;; +;;RETURN: +;; See the DOS docs for details. +;;_charop(0,0) returns the ASCII switch char, +;;_charop(1,'-') sets the switch to -, +;;_charop(2,0) returns device availability, +;;_charop(3,i) sets device availability. +;; +;; +;;DESCRIPTION: +;; +;;EXAMPLE: +;; +;; +;;CAUTIONS: +;; +;; +;;ASSUMPTIONS: +;; +;;LONG 32 bits (4 bytes) +;;INT 16 bits (2 bytes) +;;CHAR 8 bits (1 byte) +;; +page +pgroup group prog +prog segment byte public 'prog' +assume cs:pgroup,ds:pgroup + +public _charop + +_charop proc near + push bp + mov bp,sp + mov al,[bp+4] + mov dl,[bp+6] + mov ah,55 + int 33 + mov al,dl + mov ah,0 + pop bp + ret +_charop endp + +prog ends + + end diff --git a/assembly/Multi-function fractal demonstration program which results in 255 byte program.asm b/assembly/Multi-function fractal demonstration program which results in 255 byte program.asm new file mode 100644 index 0000000..9528bc8 --- /dev/null +++ b/assembly/Multi-function fractal demonstration program which results in 255 byte program.asm @@ -0,0 +1,294 @@ +; teeny program displays the Mandelbrot set. +; +; Home Up PgUp +; Left Right correspond to 8 obvious directions +; End Dn PgDn +; + + .model TINY + ;JUMPS ; without this, see caveat under 8086 above + +NONE = 00h ; use this for no features +PRINTZOOM = 01h ; printout and beep features +MODECHANGE = 02h ; support video mode change? +SPEED = 04h ; use 386 instructions for speed +STARTCOORDS = 08h ; use starting coordinates (instead of 0,0) +HIRES = 10h ; use hi resolution (single mode version only) + +; choose the desired features from the feature list above, and OR them +; all together as shown below: + +FEATURES = PRINTZOOM OR MODECHANGE OR STARTCOORDS OR SPEED OR HIRES + + +if (FEATURES AND SPEED) + .386 +endif + +ifdef (FEATURES AND HIRES) + VIDMODE = 12h ; use mode 12h + PIXWIDTH = 640 ; ... which is 640x480 + PIXHEIGHT = 480 +else + VIDMODE = 13h ; use mode 13h + PIXWIDTH = 320 ; ... which is 320x200 + PIXHEIGHT = 200 +endif +TEXTMODE = 3 ; our exit video mode (80x25 color text mode) +ZOOMLIMIT = 13 ; can change to up to 13 for extended zoom in + +VIDEO_INT = 10h ; BIOS video services interrupt + WRITE_PIXEL = 0Ch ; write pixel video service + WRITE_CHAR = 0eh ; write char in TTY mode video service + CHANGE_MODE = 00h ; change mode video service + +KEYBD_INT = 16h ; BIOS keyboard services interrupt + +; ASCII codes +EXTENDED = 000h ; no ASCII code for extended key codes +BELL = 007h ; the ASCII bell char to make a beep +CR = 00dh ; a carriage return character +ESCAPE = 01bh ; the escape key +PLUS = 02bh ; ASCII code for '+' key +V_KEY = 'v' ; ASCII code for video mode switch + +; keyboard scan codes +MINUS = 04ah ; scan code for gray '-' key + +; feel free to experiment with the following constants: + +DELTA = 100 ; the unit of pan movement in pixels +THRESHOLD = 4 ; must be in the range of (0,255) +STARTSCALE = 7 ; a number from 0 to ZOOMLIMIT, inclusive +STARTX =-DELTA ; to the right by 1 delta unit (STARTCOORDS feature) +STARTY =-DELTA ; down by 1 delta unit (STARTCOORDS feature) +CHAR_COLOR = 0fh ; white on black background (for PRINTZOOM feature) + + .code + org 100h +;**************************************************************************** +; +; Here's the main routine, and it's a bit convoluted. +; +;**************************************************************************** +Start proc +ife (FEATURES AND MODECHANGE) + mov ax,VIDMODE + int VIDEO_INT +endif +if (FEATURES AND STARTCOORDS) + mov bp,STARTX + mov di,STARTY +else + xor bp,bp ; zero initial X offset + xor di,di ; initial Y offset is identical +endif +if (FEATURES AND MODECHANGE) + mov si,offset VidTbl; point to default video table + jmp @@ChgMode + +video STRUC +ScrnMode dw ? ; the mode number for BIOS' purposes +ScrnWidth dw ? ; pixel width of screen minus one +ScrnHeight dw ? ; full height of screen in pixels +NextMode dw ? ; pointer to next video structure +video ENDS + + +VidTbl video <54h, 800-1, 600, ($ + 2)> ; highest res + video <13h, 320-1, 200, ($ + 2)> ; lowest res + video <12h, 640-1, 480, offset VidTbl> ; next to lowest res + +else + jmp @@Render ; leap right in there and draw +endif +@@TryPlus: + cmp al,PLUS ; Q: gray + key? + mov al,[scale] ; get the scale factor in al now + jnz @@TryMinus ; N: maybe it's something else + dec al ; Y: it's plus so zoom out + js @@beep ; if AL<0, balk - can't zoom that far + sar bp,1 ; adjust offsets for new scale so + sar di,1 ; we stay in the same place + jmp @@AdjustScale +@@TryMinus: + cmp ah,MINUS ; Q: gray - key? + jnz @@ReadKey ; N: it's not a valid key + inc al ; Y: zoom in + cmp al,ZOOMLIMIT ; Q: have we zoomed too far? + ja @@beep ; Y: yes, so just beep and don't adjust + sal bp,1 ; adjust offsets for new scale so + sal di,1 ; we stay in the same place + +@@AdjustScale: + mov [scale],al ; update the scale value +@@Render: +if (FEATURES AND PRINTZOOM) + mov al,'0'+ZOOMLIMIT; maximum printable character + sub al,[scale] ; invert the sense + call PrintChar ; show the character + mov al,CR ; print a carriage return (no line feed - + call PrintChar ; we don't want to advance to next line) +endif +;**************************************************************************** +; Draw +; This routine is the fractal drawing engine. It has been +; optimized for size, sacrificing speed. +; +;**************************************************************************** +if (FEATURES AND MODECHANGE) + mov cx,(video ptr [si]).ScrnHeight + push si ; we do this because it's very slow + ; if we read the Width from memory + ; every inner loop iteration + mov si,(video ptr [si]).ScrnWidth +else + mov cx, PIXHEIGHT ; height of screen in pixels +endif + sub di,cx ; adjust our Y offset +@@CalcRow: + push cx ; save the row pointer on the stack +if (FEATURES AND MODECHANGE) + mov cx,si ; fetch the screen width +else + mov cx, PIXWIDTH-1 ; width of screen in pixels +endif + sub bp,cx ; +@@CalcPixel: + push cx ; save the column counter on stack + xor cx, cx ; clear out color loop counter + xor bx, bx ; zero i coefficient + xor dx, dx ; zero j coefficient +@@CycleColors: + push dx ; save j value for later + mov ax, bx ; ax = i + sub ax, dx ; ax = i - j + add dx, bx ; dx = i + j + stc ; one additional shift, please + call Shifty ; ax = ((i+j)*(i-j)) shifted right + pop dx ; retrieve our saved value for j + add ax,bp ; account for base offset... + cmp ah,THRESHOLD ; Q: is i > THRESHOLD * 256? + xchg bx,ax ; now swap new i with old i + jg @@draw ; Y: draw this pixel + clc ; no additional shifts here, please + call Shifty ; now dx:ax = old i * j + xchg dx,ax ; + add dx,di ; account for base offset... + inc cl ; increment color + jnz @@CycleColors ; keep going until we're done +@@draw: + xchg ax, cx ; mov color into al + pop cx ; retrieve our column counter + pop dx ; fetch row (column already in cx) + push dx ; must leave a copy on the stack + xor bx,bx ; write to video page zero + mov ah,WRITE_PIXEL ; write pixel command + int VIDEO_INT ; video BIOS call + inc bp ; adjust our X base value + loop @@CalcPixel ; keep going until we've done a line + inc di ; adjust our Y base value + pop cx ; keep going until we've done 'em all + loop @@CalcRow ; more rows? + +if (FEATURES AND MODECHANGE) + pop si ; restore vid ptr if we use one +endif +@@beep: +if (FEATURES AND PRINTZOOM) + mov al,BELL ; + call PrintChar ; +else + mov ax,((WRITE_CHAR SHL 8) OR BELL) ; make a beep + int VIDEO_INT ; (bx=0 -- any video page, any char attr) +endif +@@ReadKey: + xor ax,ax ; fetch a keystroke + int KEYBD_INT ; keyboard request + cmp al,ESCAPE ; Q: does the user want to exit? + jz @@exit ; Y: do so immediately +if (FEATURES AND MODECHANGE) + cmp al,V_KEY ; request for video mode change? + jnz @@TestExt ; if not, go on +@@ChgMode: + mov si,(video PTR [si]).NextMode ; change pointers + mov ax,(video PTR [si]).ScrnMode ; load new video mode + int VIDEO_INT ; change modes + jmp @@Render ; draw new screen +@@TestExt: +endif + cmp al,EXTENDED ; Q: is it an extended key code? + jnz @@TryPlus ; N: it's not so see if it's '+' +@@ArrowKey: + inc ah ; increment it to make indexing easier + add ah,ah ; multiply by two + mov bl,6 ; fix template (bh is already zero) + and bl,ah ; now bx contains address of delta +if (FEATURES AND MODECHANGE) + push si ; save video ptr if we're using one +endif + mov si,offset Deltas; fetch the delta value + add bp,[bx+si] ; add it to the X offset + shr ah,2 ; now look at the Y value of keystroke + mov bl,6 ; turn it into a table offset + and bl,ah ; do it now + sub di,[bx+si] ; and subtract from Y offset +if (FEATURES AND MODECHANGE) + pop si ; restore video ptr if we're using one +endif + jmp @@Render ; go draw this thing. +@@exit: + mov ax,TEXTMODE ; back to normal now + int VIDEO_INT ; change modes + ret ; and exit via old style +Start endp + +Deltas dw +DELTA,0,-DELTA,0 ; handy table for calculating + ; changes in X and Y offsets + +;**************************************************************************** +; Shifty +; +; This routine multiplies AX by DX and shifts the result (in +; DX:AX) to the right by scale bits (or scale+1 bits if CY is +; set). The resulting value is left in AX. DX is destroyed. +; +;**************************************************************************** +Shifty proc near + push cx ; save middle bits (i*i - j*j) + db 0b1h ; code for mov cl,immed8 +scale db STARTSCALE + adc cl,0 ; adjust per CY flag + imul dx ; do the multiply +if (@Cpu AND 8) ; is is a 386 or better? + xchg ax,dx ; + shl eax,16 ; put hi part in hi 16 bits + xchg ax,dx + shr eax,cl ; +else +@@Rotate: + rcr dx,1 ; + rcr ax,1 ; + loop @@Rotate ; ch is always zero so this is OK +endif + pop cx ; + ret ; +Shifty endp + +if (FEATURES AND PRINTZOOM) +;**************************************************************************** +; PrintChar +; +; This simple subroutine prints a single character (in AL) to the +; screen using a BIOS call. AH and BX are destroyed. +; +;**************************************************************************** +PrintChar proc + mov ah,WRITE_CHAR ; write a character in TTY mode + mov bx,CHAR_COLOR AND 07fh ; use page 0 (bh), non-xor color (bl) + int VIDEO_INT ; do it up + ret +PrintChar endp +endif + + end Start \ No newline at end of file diff --git a/assembly/Program to prevent CTRL+ALT+DEL from restarting the system.asm b/assembly/Program to prevent CTRL+ALT+DEL from restarting the system.asm new file mode 100644 index 0000000..10f59f6 --- /dev/null +++ b/assembly/Program to prevent CTRL+ALT+DEL from restarting the system.asm @@ -0,0 +1,150 @@ +To use it just type, from the dos prompt: + + MASM NOCAD; (of course you need MASM) + LINK NOCAD; (and of course you need a linker) + NOCAD + + If you type NOCAD once it has been loaded, it will tell you so. + I've used it with DOS 3.30, but it works just as well under DOS + 2.00 and above. + If you have any comment of any kind please let me know. + And have a nice new decade everybody. + +cut here: ************************************************************ +page 255,132 ;just to get a nice list file +comment : + Program to prevent CTRL+ALT+DEL from restarting the system + WARNING: Once loaded, you only have three choices: + 1) Turn power off + 2) Use a reset button (not all the machines have one) + 3) Generate INT 19h + + WARNING: If you have a program that uses INT 0CDh, change + this value in the equates line below to the number + of a not used INT. This method is used because + there are too many programs that hook INT 9 Vector and + we can't be sure it always points to the end of our + notice (and start of our ISR). + + NOTE: For memory references i use parentheses instead of + square brackets because of ASCII-EBCDIC translations. + It works the same under Microsoft's MASM 4.0 + + NOTE: NOCAD won't work if you press CTRL+ALT+DEL from + a program that hooked to INT 9 before NOCAD + (example: SideKick). Solution: Load NOCAD before + everything else. + + +ctrl equ 0100b ;bit map for ctrl key +alt equ 1000b ;bit map for alt key +free_vector equ 0CDh ;vector used to prevent double loading + ;change it if your system uses INT 0CDh + nocad segment byte 'CODE' + assume cs:nocad, ds:msgs, es:nothing, ss:stack + Copyright db 'Antonio Quezada-Duarte ITESM ISC 296641 Monterrey ' + db 'Nuevo Leon MEXICO' + Cright_Len equ $-Offset Copyright + new_int_9h proc near + push ax + push ds ;save registers + xor ax,ax + mov ds,ax ;point DS to BIOS data area + ;well, actually BIOS data area + ;starts at 0040:0000, but + ; XOR AX,AX is faster than MOV AX,40h + mov al,ds:(417h) ;get keyboard flags + and al,ctrl+alt ;clear non relevant bits + cmp al,ctrl+alt ;compare to our map + jne go_ahead ;NO CTRL+ALT keys pressed + and byte ptr ds:(417h),not alt ;CTRL+ALT pressed + ;clear ALT key bit to simulate + ;ALT key is not pressed +go_ahead: + pushf ;old ISR returns with IRET + COMMENT : + The Following code stands for + + CALL OLD_INT_9 + Where OLD_INT_9 is a FAR PROC + this is faster than having the address of OLD_INT_9 + stored in memory and doing a + CALL CS:(OLD_INT_9) + : + DB 9Ah + OLD_INT_9_OFS DW 0 + OLD_INT_9_SEG DW 0 ;call old INT 9 ISR + + pop ds + pop ax ;restore registers + iret ;return to caller + new_int_9h endp + begin proc near + push es ;save psp base address + mov dx,seg msgs + mov ds,dx + mov dx,offset msg_0 + mov ah,9 + int 21h + mov ax,3500h + free_vector + int 21h + mov di,bx ;ES:DI ===> start of INT 0CDh ISR + mov si,offset copyright + mov ax,cs + mov ds,ax ;DS:SI ===> THIS code copyright notice + mov cx,cright_len + cld + repe cmpsb ;compare + je loaded ;if equal then already loaded + mov ax,2500h + free_vector + mov dx,cs + mov ds,dx + mov dx,offset copyright + int 21h ;point free_vector INT vector to + ;our copyright notice + mov ax,3509h + int 21h ;get pointer to INT 9 ISR + mov cs:old_int_9_ofs,bx + mov cs:old_int_9_seg,es ;put it IN the new INT 9 ISR + mov ax,2509h + mov dx,offset new_int_9h + push cs + pop ds + int 21h ;point INT 9 vector to our ISR + mov dx,seg msgs + mov ds,dx + mov dx,offset msg_1 + mov ah,9 + int 21h ;print loaded msg + pop ds ;get saved psp base address + mov es,ds:(2Ch) + mov ah,49h + int 21h ;free environment's memory + ;assume no error + mov dx,offset begin ;everything up to BEGIN + add dx,10Fh ;and all the bytes needed to + mov cl,4 ;make a full paragraph ... + shr dx,cl + mov ax,3100h ;... stay resident + int 21h ;and return exit code = 0 +loaded: pop ax ;get psp address out of stack + ;any register will do + mov dx,seg msgs + mov ds,dx ;point DS to our data area + mov dx,offset msg_2 + mov ah,9 + int 21h ;print already loaded msg + mov ax,4C01h + int 21h ;terminate with exit code = 1 + begin endp + nocad ends + msgs segment word 'DATA' + msg_0 db 10,13,'NOCAD: Prevent CTRL+ALT+DEL from restarting the ' + db 'system',10,13,'Author: Antonio Quezada-Duarte',10,13,'$' + msg_1 db 10,13,'NOCAD Loaded OK.',10,13,'$' + msg_2 db 10,13,'NOCAD Already Loaded.',10,13,'$' + msgs ends + stack segment para stack 'STACK' + dw 1024 dup (?) + stack ends + end begin \ No newline at end of file diff --git a/assembly/Report installed device drivers.asm b/assembly/Report installed device drivers.asm new file mode 100644 index 0000000..cec1e6e --- /dev/null +++ b/assembly/Report installed device drivers.asm @@ -0,0 +1,231 @@ +name dev + page 60,132 + title 'DEV --- Report installed device drivers' + +; DEV --- a utility to report device header information for +; all installed device drivers +; +; Requires PC-DOS or MS-DOS 2.0. +; +; Used in the form: +; A>DEV +; + +cr equ 0dh ;ASCII carriage return +lf equ 0ah ;ASCII line feed +blank equ 20h ;ASCII space code +eom equ '$' ;end of string marker + + +cseg segment para public 'CODE' + + assume cs:cseg,ds:data,es:data,ss:stack + + +dev proc far ;entry point from PC-DOS + + push ds ;save DS:0000 for final + xor ax,ax ;return to PC-DOS + push ax + mov ax,data ;make our data segment + mov ds,ax ;addressable via DS and ES. + mov es,ax + mov ah,30h ;check version of PC-DOS. + int 21h + cmp al,2 + jae dev1 ;proceed, DOS 2.0 or greater. + mov dx,offset msg2 ;DOS 1.x --- print error message. + jmp dev6 + +dev1: mov cx,ax ;save DOS version number. + mov ah,15 ;now try and open the "NUL" device. + mov dx,offset nulfcb + int 21h + or al,al ;opened successfully? + jz dev2 ;yes, jump. + mov dx,offset msg1 ;no, print error msg and exit. + jmp dev6 + +dev2: ;Pick up double pointer to device + ;driver chain out of reserved + ;area in fcb. This area is mapped + ;differently in DOS 2.x and DOS 3.x. + cmp cl,2 ;is this DOS 2.x? + ja dev3 ;no, jump. + mov bx,word ptr nulfcb+25 + mov es,word ptr nulfcb+27 + jmp dev4 + +dev3: ;come here if DOS 3.0 or greater. + mov bx,word ptr nulfcb+26 + mov es,word ptr nulfcb+28 + +dev4: call header ;print sign-on message and + ;column headings. + +dev5: ;trace through the device chain + + call prdev ;print device header information + ;for driver pointed to by ES:BX. + ;pick up addr of next header. + les bx,dword ptr es:[bx] + cmp bx,-1 ;found last one yet? + jne dev5 ;no, try next. + + mov dx,offset msg3 ;yes, print "end of device chain". + +dev6: mov ah,9 ;print the string whose address + int 21h ;is in DX. + ret ;then return to DOS. + +dev endp + + +header proc near ;print out headings for device + mov dx,offset hdr ;driver information. + mov ah,9 + int 21h + ret +header endp + + +prdev proc near ;print out device driver info. + ;ES:BX is pointer to device header, + ;which must be preserved. + mov ax,es ;convert segment of device header + mov di,offset inf1 + call hexasc + mov ax,bx ;convert offset of device header. + mov di,offset inf2 + call hexasc + mov ax,es:[bx+4] ;get attribute word, save a + push ax ;copy of it, then convert it. + mov di,offset inf3 + call hexasc + mov ax,es:[bx+6] ;convert ptr to device strategy. + mov di,offset inf4 + call hexasc + mov ax,es:[bx+8] ;convert ptr to device int handler. + mov di,offset inf5 + call hexasc + + ;if not char device, clear out name + ;field and set number of units. + pop ax ;get back attribute word. + test ax,08000h ;is bit 15 = 1 ? + jnz prdev7 ;yes, it's character dev, jump. + ;no, it's block device. + ;set flag to skip device name. + mov byte ptr inf8,eom + mov al,es:[bx+10] ;pick up number of units. + aam ;convert to ASCII decimal and + add ax,'00' ;store into output string. + mov byte ptr inf7+1,al + mov byte ptr inf7,ah + ;set type = B for Block + mov byte ptr inf6,'B' + jmp prdev9 + +prdev7: ;if char device, move its 8-character + ;name into the output string. + xor si,si +prdev8: mov al,es:[si+bx+10] + mov [si+inf8],al + inc si + cmp si,8 + jne prdev8 + ;remove # of units field. + mov word ptr inf7,' ' + ;set type = C for Character. + mov byte ptr inf6,'C' + +prdev9: mov dx,offset inf ;now print device information + mov ah,9 ;and exit. + int 21h + ret +prdev endp + +hexasc proc near ;convert binary word to hex ASCII. + ;call with AX=binary value + ; DI=addr to store string + ;returns AX, CX, DI destroyed. + push ax ;save copy of original value. + mov al,ah + call btoa ;convert upper byte. + add di,2 ;increment output address. + pop ax + call btoa ;convert lower byte. + ret ;return to caller. +hexasc endp + +btoa proc near ;convert binary byte to hex ASCII. + ;call with AL=binary value + ; DI=addr to store string + ;returns AX, CX destroyed. + mov ah,al ;save lower nibble. + mov cx,4 ;shift right 4 positions + shr al,cl ;to get upper nibble. + call ascii ;convert 4 bits to ASCII equivalent + mov [di],al ;store into output string. + mov al,ah ;get back lower nibble. + and al,0fh + call ascii ;convert 4 bits to ASCII + mov [di+1],al ;and store into output string. + ret ;back to caller. +btoa endp + +ascii proc near ;convert 4 lower bits of AL + add al,'0' ;into the equivalent ASCII char. + cmp al,'9' ;in the range {0...9,A...F} + jle ascii2 ;and return char. in AL. + add al,'A'-'9'-1 ;"fudge factor" for range A-F. +ascii2: ret ;return to caller. +ascii endp + +cseg ends + + +data segment para public 'DATA' + +msg1 db cr,lf + db 'Failed to open NUL device.' + db cr,lf,eom + +msg2 db cr,lf + db 'Requires DOS version 2 or greater.' + db cr,lf,eom + +msg3 db cr,lf + db 'End of device chain.' + db cr,lf,eom + +hdr db cr,lf + db 'Addr Attr ' + db 'Str Int Type Units Name ' + db eom + + +inf db cr,lf +inf1 db 'XXXX:' ;seg device header +inf2 db 'XXXX ' ;offs device header +inf3 db 'XXXX ' ;attribute +inf4 db 'XXXX ' ;strategy +inf5 db 'XXXX ' ;interrupt handler +inf6 db 'X ' ;type (block or char) +inf7 db 'XX ' ;units (if block device) +inf8 db ' ' ;name (if char device) + db eom + + ;fcb to open NUL device +nulfcb db 0 ;drive + db 'NUL' ;name of NUL device + db 8 dup (' ') + db 25 dup (0) +data ends + + +stack segment para stack 'STACK' + db 64 dup (?) +stack ends + + end dev \ No newline at end of file diff --git a/assembly/Serial communications port interupt intercepter AHA 8502.27.asm b/assembly/Serial communications port interupt intercepter AHA 8502.27.asm new file mode 100644 index 0000000..5ab23ff --- /dev/null +++ b/assembly/Serial communications port interupt intercepter AHA 8502.27.asm @@ -0,0 +1,96 @@ +; +; Functions: +; al=0 then Disable communications interupt vector +; al=1 then Enable communications interupt vector +; Issue and int 44h +; +progseg segment para public 'CODE' + public setcom + assume cs:progseg, ds:progseg, es:progseg + org 100h +doscall equ 21h +; +startup proc far + jmp setup +; +setcom proc far + push ds + push es + push dx + push ax + mov ax,cs + mov ds,ax + mov es,ax + pop ax + cmp al,1 ;is function 1 + jz enable ;then enable +; +disable: + mov dx,offset interupt ;get new vector address + mov ax,cs + mov ds,ax ;set segment + mov ah,25h ;set interupt vector address function + mov al,14h ;communications interupt vector + int doscall ;set the interupt + jmp exit ;exit +enable: + mov dx,word ptr vector ;set old segment + mov ds,vector+2 ;set old communications vector + mov ah,25h ;set interupt vector address function + mov al,14h ;communications interupt vector + int doscall +exit: + pop dx + pop es + pop ds +; +interupt proc far + sub ax,ax ;zero return status + iret +interupt endp +setcom endp +; +msg db 'Serial communications intercepter installed',0ah,0dh,'$' +msg1 db 'Serial communications intercepter is already installed',0ah,0dh,'$' +vector db 8 dup(0) ;only 4 needed 4 more for safety +; +setup: + mov ah,35h ;get interupt vector address function + mov al,44h ;communications interupt vector + int doscall ;go get it + cmp bx,0 ;check if vector used + jnz lderr ;if used then exit + mov ax,es ;check segment + cmp ax,0 + jnz lderr +; + mov dx,offset msg + mov ah,9 + int doscall +; + mov ah,35h ;get interupt vector address function + mov al,14h ;communications interupt vector + int doscall ;go get it +; + mov word ptr vector,bx ;save offset + mov bx,es ;get segment address + mov word ptr vector+2,bx ;save segment +; + mov dx,offset setcom ;get new vector address + mov ax,cs + mov ds,ax ;set segment + mov ah,25h ;set interupt vector address function + mov al,44h ;set to our new interupt vector + int doscall ;set the interupt +; + mov dx,offset setup ;terminate and stay resident + int 27h +lderr: + mov dx,offset msg1 + mov ah,9 + int doscall + int 20h +startup endp +progseg ends +; + end startup \ No newline at end of file diff --git a/assembly/Sets up 'flat real mode'.asm b/assembly/Sets up 'flat real mode'.asm new file mode 100644 index 0000000..8035268 --- /dev/null +++ b/assembly/Sets up 'flat real mode'.asm @@ -0,0 +1,96 @@ +; flatmode.asm +; +; This program demonstrates flat real mode, which is simply real mode +; with 4G descriptors for some segments. In this code it's done by +; going into protected mode, setting the FS register to a descriptor +; with 4G limits and then returning to real mode. The protected mode +; limit stays in effect, giving "flat real mode." +; +; The demonstration part of this code writes the first 160 bytes from +; the system ROM at F0000h (linear) to the color screen which is assumed +; to be at B8000h (linear) using a flat real mode selector. Since that +; range of the system ROM typically contains a copyright notice, one +; can easily see that the code is truly working as advertised. +; +; This code is intended to be run on a Pentium or better. +; +; To assemble: +; +; using Microsoft's MASM 6.11 or better +; ml /Fl flatmode.asm +; +;---------------------------------------------------------------------- + .model tiny + .code + .586P + +DESC386 STRUC + limlo dw ? + baselo dw ? + basemid db ? + dpltype db ? ; p(1) dpl(2) s(1) type(4) + limhi db ? ; g(1) d/b(1) 0(1) avl(1) lim(4) + basehi db ? +DESC386 ENDS + +;---------------------------------------------------------------------- + ORG 100h +start: + call flatmode ; go into flat real mode (fs reg only) +; mov dx,5 ; +; mov fs,dx ; + call fillscreen ; fill the screen using 4G descriptor + mov ax,4c00h ; do a standard DOS exit + int 21h ; +;---------------------------------------------------------------------- +fillscreen proc + mov esi,0F0050h ; point to ROM +ifdef BEROSET + mov edi,0B8000h ; point to screen +else + mov di,0b800h ; + mov es,di ; + xor edi,edi ; +endif + mov cx,160 ; just two lines + mov ah,1Eh ; yellow on blue screen attrib +myloop: + mov al,fs:[esi] ; read ROM byte +ifdef BEROSET + mov fs:[edi],ax ; store to screen with attribute +else + mov es:[di],ax ; store to screen with attribute +endif + inc esi ; increment source ptr + inc edi ; increment dest ptr by two + inc edi ; + loop myloop ; keep going + ret ; and quit +fillscreen endp +;---------------------------------------------------------------------- +flatmode proc + ; first, calculate the linear address of GDT + xor edx,edx ; clear edx + xor eax,eax ; clear edx + mov dx,ds ; get the data segment + shl edx,4 ; shift it over a bit + add dword ptr [gdt+2],edx ; store as GDT linear base addr + + ; now load the GDT into the GDTR + lgdt fword ptr gdt ; load GDT base (286-style 24-bit load) + mov bx,1 * size DESC386 ; point to first descriptor + mov eax,cr0 ; prepare to enter protected mode + or al,1 ; flip the PE bit + cli ; turn off interrupts + mov cr0,eax ; we're now in protected mode + mov fs,bx ; load the FS segment register + and al,0FEh ; clear the PE bit again + mov cr0,eax ; back to real mode + sti ; resume handling interrupts + ret ; +flatmode endp +;---------------------------------------------------------------------- +GDT DESC386 ; the GDT itself + DESC386 <0ffffh, 0, 0, 091h, 0cfh, 0> ; 4G data segment +GDT_END: +end start \ No newline at end of file diff --git a/assembly/Show Memory.asm b/assembly/Show Memory.asm new file mode 100644 index 0000000..696705a --- /dev/null +++ b/assembly/Show Memory.asm @@ -0,0 +1,283 @@ +kbd equ 16h ;keyboard irq +msdos equ 21h ;MSDOS irq + +reset equ 0dh ;disk reset +dfopen equ 0fh ;open disk file +dfclose equ 10h ;close disk file +searchf equ 11h ;search first +searchn equ 12h ;search next +seqread equ 14h ;sequential disk read +seqwrite equ 15h ; " " write +setdta equ 1ah ;set disk transfer area address +createf equ 3ch ;create file with handle +openf equ 3dh ;open file with handle +closef equ 3eh ;close file with handle +readf equ 3fh ;read from file with handle +writef equ 40h ;write to file with handle +setfp equ 42h ;set file pointer +allocmem equ 48h ;allocate memory +freemem equ 49h ;free memory +changebs equ 4ah ;change block size +findfirst equ 4eh ;find first file +exit equ 4c00h ;msdos exit + +[BITS 16] ;NASM stuff +[ORG 0x100] + +s1: + mov ax,cs ;get code segment + mov ds,ax ;use it now + mov [comseg],ds ;save it there + + mov si,0080h ;DOS command line page 0 + lodsb ;load size of command line + cmp al,0 ;anything on command line ? + jbe usage ;noo, show usage + cbw ;extend AL to AX + xchg bx,ax ;swap size to bx for indexing + mov byte [bx+si],0 ;null terminate command line + call parse ;parse command line + jmp main ;go on with main +usage: mov bx,utext ;pointer usage text + jmp errout ;skip this +main: + mov si,inbuff ;check for valid HEX input + mov bx,errt1 ;proper text +ishex: lodsb ;get the char + cmp al,'0' + jb errout + and al,0dfh ;force UPPERCASE + cmp al,'F' ;>F ? + ja errout ;yeahh, dump this + loop ishex + call hexbin ;make hex bin + ;start address now in EDX + mov ax,dx ;get low word (segment) + mov es,ax ;start segment + shr edx,16 ;shift in offset + mov di,dx ;start offset +dopage: + push es ;save registers + push di + push ds + push si + mov ax,es + mov ds,ax ;make ds=es + mov si,di ;and si=di + + call showpage ;show it + + pop si ;restore registers + pop ds + pop di + pop es + add di,512 ;adjust memory position + + ;xor ah,ah ;wait for ANY key + ;int kbd + + mov bx,text ;show message + call write + mov ah,0 ;wanna see next screen ? + int kbd ;chek out keyboard buffer + and al,0DFh ;force UPPER CASE + cmp al,"Q" ;wanna quit ? + je quit ;yeahh + jmp dopage +errout: + call write +quit: + mov ax,exit + int msdos + +;*********************************************************** +;* Convert ascii hex to 32 bit binary +;* Input = command line buffer, output EDX +;*********************************************************** +hexbin: + mov si,inbuff ;pointer command line buffer + xor edx,edx ;clear binary output +aschexbin: + lodsb + cmp al,'0' ;< 0 + jb notasc ;yes invalid character + cmp al,'9' ;<= 9 + jbe astrip ;yes, strip high 4 bits + and al,05fh ;force upper case + cmp al,'A' ;< ascii A + jb notasc ;yes, invalid character + cmp al,'F' ;> ascii F + ja notasc ;yes, invalid character + add al,9 ;ok, add 9 for strip +astrip: + and al,0fh ;strip high 4 bits + mov cx,4 ;set shift count + shl edx,cl ;rotate EDX 4 bits + xor ah,ah ;zero out AH + cbw + add edx,eax ;add digit to value + jmp aschexbin ;continue +notasc: ret + +;********************************************************************* +;* Format and show the stuff in a "sector" +;* Input SI +;********************************************************************* +showpage: + mov cx,32 ;32*16=512 +arow: push cx + mov di,outline ;output buffer + mov cx,16 ;process 16 bytes +hexrow: push cx + lodsb ;load al with byte + mov dl,al ;get value + mov cx,2 ;2 nibbles +chexb: push cx ;save that + mov cl,4 ;4 bits + rol dl,cl ;rotate source left + mov al,dl ;move digit into AL + and al,15 ;clear high nibble + daa ;adjust AL if A through F + add al,240 ;bump the carry + adc al,40h ;convert HEX to ASCII + stosb ;copy to buffer + pop cx ;get digit counter + loop chexb ;next digit + mov al,32 ;copy a SPACE + stosb + pop cx ;restore loop counter + loop hexrow ;loop on + mov al,32 ;copy 2 spaces + stosb + stosb + sub si,16 ;adjust source back + mov cx,16 ;copy ASCII bytes +cccp: lodsb + cmp al,32 ;< SPACE ? + jb noa ;yeahh, skip it + stosb ;no, store in buffer + jmp next +noa: mov al,'.' + stosb +next loop cccp + mov al,13 + stosb + mov al,10 + stosb + mov al,0 ;null terminate line + stosb + mov bx,outline ;show the line + call write + pop cx + cmp cx,17 + jne nopause + push ds + mov ax,cs + mov ds,ax + mov bx,text1 + call write + pop ds + xor ah,ah + int kbd +nopause: + loop arow ;next 16 bytes + ret + +;************************************************************************' +;* Convert bin WORD to HEX ascii. Input DX. Result in Numbuff * +;************************************************************************ +binhex: pusha + mov di,numbuff ;destination buffer + mov dx,[count] ;binary number + mov cx,4 ;four nibbles +convhex: + push cx ;save counter + mov cl, 4 ;4 bits + rol dx, cl ;rotate source left + mov al, dl ;move digit into AL + and al, 15 ;clear high nibble + daa ;adjust AL if A through F + add al, 240 ;bump the carry + adc al, 40h ;convert HEX to ASCII + stosb ;copy to buffer + pop cx ;get digit counter + loop convhex ;next digit + mov al,32 ;copy a space + stosb + mov al,0 ;null terminate + stosb + popa + ret + +;************************************************************************* +;* Writes out the NULL terminated text supplied in BX. * +;* OR writes out data,BX and size,CX if called at lwrite. * +;************************************************************************* +write: pusha + mov si,bx ;copy to SI + mov cx,0 ;clear count +wloop: lodsb ;load AL with SI + cmp al,0 ;end of line ? + je lwrite ;yeahh + inc cx ;no, incrase byte count + jmp wloop ;test next byte +lwrite: mov dx,bx ;text address in DX + mov bx,1 ;filehandle standard output = 1 + mov ah,writef ;MS-DOS writefile with handle is 040 + int msdos ;write buffer to standard output + popa + ret ;done + +;************************************************************************* +;* My kind of command line parsing. It just checks if there�s +;* any blankspaces between the options. The parameters ends up +;* in the inbuff separated by 0:s, binary zeroes. +;************************************************************************* +parse: + mov di,inbuff ;our buffer +ifspc: cmp byte [si],32 ;leading space ? + jne nospc ;noo + inc si ;yeahh, dump that + jmp ifspc ;check next +nospc: mov cx,1 ;were here, so we got one arg +copy1: lodsb ;load byte SI to AL + cmp al,0 ;0 ?(end of line) + je done ;yeahh + cmp al,32 ;SPACE ? + je cop2 ;yeah + stosb ;noo, move AL to DI, incrase DI + jmp copy1 ;go on +cop2: mov byte [di],0 ;null terminate + add cx,1 + inc di ;dump that byte(SPACE) + jmp copy1 ;back +done: mov byte [di],0 ;null terminate + ret ;return + + +;*************************** DATA STUFF ********************************** + +XMS_SEGMENT dw 0 +XMS_OFFSET dw 0 + +inbuff times 64 dw 0 ;128 byte command line buffer +outline times 40 dw 0 ;buffer output line +numbuff times 7 dw 0 ;word ascii number buffer +comseg dw 0 +count dw 0 +bcount dw 0 +acount dw 0 + +;outbuff times 512 db 0 + + +utext db 'WWW',13,10 + db 'Usage: Showmem [start address].',13,10 + db 'Start address = Hexadecimal.',13,10,0 +text: db 13,10,'Q = Quit. Any key = Next page.',13,10,0 +text1: db 13,10,'Any Key = Next 256 Bytes.',13,10,0 +errt1: db 'That address is not hexadecimal.',13,10,0 + +s2: + +END \ No newline at end of file diff --git a/assembly/Shows a demonstration of a routine which scrolls a window on a text mode screen.asm b/assembly/Shows a demonstration of a routine which scrolls a window on a text mode screen.asm new file mode 100644 index 0000000..e36720d --- /dev/null +++ b/assembly/Shows a demonstration of a routine which scrolls a window on a text mode screen.asm @@ -0,0 +1,188 @@ +%SUBTTL "Scroll Window Left routine with sample driver" +; +; Scroll2.Asm +; +; see ScrollLeft description for complete explanation of this program +; + MODEL small + IDEAL + STACK 200h ; this is more than enough stack + CODESEG +start: +; +; this test stub scrolls the window at (4,3)-(22,68) left 9 columns, +; filling in with spaces of attribute white on black (07) +; + mov al,9 ; number of columns to scroll + mov bh,07 ; attribute to use for blanked chars + mov ch,4 ; row of upper left hand corner of window + mov cl,3 ; col of upper left hand corner of window + mov dh,22 ; row of lower right hand corner of window + mov dl,68 ; col of lower right hand corner of window + + call ScrollLeft + + mov ah,4ch ; exit with errorlevel from scroll routine + int 21h +; +; ScrollLeft +; +; PURPOSE: scrolls a rectangular region of a text screen (window) to the +; left by a variable number of columns +; +; +; INPUTS: AL = number of columns to scroll (if zero, no effect) +; BH = attribute to use for blanked characters +; CH,CL = row, col for upper left hand corner of window +; DH,DL = row, col for lower right hand corner of window +; +; NOTES: upper left hand corner of screen (home) is (0,0) +; video adapter is checked to see if it's in text mode +; screen dimensions are taken from BIOS data +; calling sequence is nearly identical to BIOS scroll routine +; display pages supported +; dual monitors supported +; MDA/CGA/EGA/VGA supported +; +; RETURNS: On error, Carry flag set, AX contains error number +; otherwise carry is clear, AX contains 0 +; +; Error codes: 0 - no error +; -1 - some error occurred +; +PROC ScrollLeft + ScrRows equ 0484h ; location of BIOS rows data + ScrCols equ 044ah ; location of BIOS cols data + ScrMode equ 0449h ; location of BIOS mode data + ScrOffs equ 044eh ; location of BIOS scrn offset data + +; first, save all of the registers we're going to trash + push bx + push cx + push dx + push si + push di + push bp + push es + push ds + + mov bl,al ; stow cols in BL + xor ax,ax + mov ds,ax ; point data seg to 0000 to read BIOS data + cmp ch,dh ; srow > erow ? + ja @@badcoords + cmp cl,dl ; scol > ecol ? + ja @@badcoords +; +; now we need to load ScrRows, if we haven't got EGA or better +; + mov al,[ScrRows] ; is MAXROWS = 0 ? + cmp al,0 ; if so, then assume we've got MDA or CGA + jne @@ega_plus ; if not, we've got correct value already + mov al,24 ; otherwise, assume 25 rows (and load 25-1) +@@ega_plus: + cmp dh,al ; erow >= MAXROWS? +; +; note that BIOS actually stores MAXROWS-1 in this location, so the +; actual jump instruction is (correctly) written as ja +; + ja @@badcoords + cmp dl,[ScrCols] ; ecol >= MAXCOLS? + jae @@badcoords + mov ah,bl ; remember cols + add ah,cl ; cols + scol + cmp ah,dl ; (cols + scol) > ecol ? + ja @@badcoords + +; figure out where the video buffer starts + mov bp,0b800h ; first guess + mov al,[ScrMode] ; get mode from BIOS' RAM + cmp al,4 ; if mode is 0 through 3, we're all set + jb @@modeOK + mov bp,0b000h ; second guess + cmp al,7 ; is it mode 7 (monochrome 80 col) ? + je @@modeOK ; if so, we're still OK +@@badcoords: + mov ax,-1 ; set error code + stc ; and set error (carry) flag + jmp @@exit +@@modeOK: + mov es,bp ; set up our video pointer segment + +; ES:DI = endloc = Screen + 2 * (MAXCOLS * srow + scol) + + mov di,[ScrOffs] ; offset of screen buffer + xor ah,ah ; clear out high half of AX + mov al,[ScrCols] ; get the width of the screen + mul ch ; multiply width by the row number + add al,cl ; now add the column number + adc ah,0 ; propagate carry bit to other half of AX + shl ax,1 ; now multiply by 2 bytes/char + add di,ax ; add the offset to the screen start address + +; DS:DI = startloc = endloc + 2 * cols + + xor ah,ah ; clear top half of ax + mov al,bl ; recall cols + mov si,di ; start address = end address + add si,ax ; add cols + add si,ax ; and again + +; start on count calculation (figure ecol-scol+1) + sub dl,cl ; ecol - scol + inc dl ; now dl = ecol - scol + 1 + +; calculate increment and stow in BP +; increment = (MAXCOLS - (ecol - scol + 1)) * 2 + xor ah,ah ; clear top half of ax + mov al,dl ; use partial count calculation + neg ax + add al,[ScrCols] ; now add in screen width + adc ah,0 ; propagate carry bit to hi half of AX + shl ax,1 ; now double it (2 bytes/char) + mov bp,ax + +; finish count calculations and put in DL +; count = (ecol - scol + 1) - cols + + sub dl,bl ; figure in cols + + mov ax,es ; recall our video pointer + mov ds,ax ; now duplicate it + +; load up AX with char and attribute for blank space + mov al,32 ; ASCII space character + mov ah,bh ; passed attribute byte + + sub dh,ch ; get row count + mov dh,bh ; save loop count (rows to move) in bh + xor ch,ch ; zero out hi half of CX + cld ; assure that we move the right direction (up) +@@looptop: + mov cl,dl ; load in count (words to move) + rep movsw ; move the line over + mov cl,bl ; recall cols (blanks to insert) + rep stosw ; fill in the rest of the line + add di,bp ; advance to next line by adding increment + mov si,di ; now set up the other (source) pointer + mov cl,bl ; recall cols + add si,cx ; add in cols + add si,cx ; and again (because 2 bytes/char) + dec bh ; decrement loop counter + ja @@looptop ; skip back if we're not done yet + mov ax,0 ; set error code to zero (all OK) + clc ; and clear error (carry) flag +@@exit: + pop ds ; restore all of our registers + pop es + pop bp + pop di + pop si + pop dx + pop cx + pop bx + ret ; mosey on home again + +ENDP ScrollLeft + END start +-+------- cut here ----------- diff --git a/assembly/Shows one possible method for checking the type of video card installed in a system.asm b/assembly/Shows one possible method for checking the type of video card installed in a system.asm new file mode 100644 index 0000000..564a360 --- /dev/null +++ b/assembly/Shows one possible method for checking the type of video card installed in a system.asm @@ -0,0 +1,154 @@ +comment ^ + Sample code to show how one might detect video cards by + using search strings. +^ + .model small + .stack 400h + .data +;/*************************************************************************** +; some handy equates +;***************************************************************************/ +VID_BIOS_SEG equ 0c000h ; the video BIOS segment + +SEARCH_AREA equ 0400h ; when we look for the video BIOS + ; ID, we only seach this many bytes + +CMP_LENGTH equ 7 ; the number of "significant" + ; characters to compare in each + ; string + +DOS_INT equ 21h ; DOS' interrupt +VIDEO_INT equ 10h ; BIOS' video services int + +VID_80x25 equ 03h ; 80x25 text mode number + +;/*************************************************************************** +; data +;***************************************************************************/ +UnknownCardMsg db 'Your video card is not supported.',13,10,'$' + +mode1 db 053h ; 640 x 480 x 256 mode for Oak +card1 db 'OAK VGA','$' +mode2 db 05dh ; 640 x 480 x 256 mode for Trident +card2 db 'TRIDENT','$' + +cards dw card1, card2, 0 + +;/*************************************************************************** +; some handy macros +;***************************************************************************/ +@DosPrint MACRO msgptr + mov dx,msgptr ; handy macro for printing + mov ah,9 ; '$' terminated strings + int DOS_INT ; under DOS +ENDM + +@SetVidMode MACRO vmode + ifnb + mov ax,(vmode AND 0ffh) + else + xor ah,ah + endif + int VIDEO_INT +ENDM + + .code +;/*************************************************************************** +; main +; This is the main procedure in the code. It identifies (or +; attempts to identify) the type of video card, then switches into +; the appropriate video mode for that type of card. Right now, it +; doesn't actually do anything in that mode, but simply returns +; and restores the video mode to a fairly standard 80x25 text +; mode. Mostly as an aid to troubleshooting, the current version +; also prints out the name of the video card as discovered in the +; video BIOS area. +; +;***************************************************************************/ +main proc + .STARTUP ; do the usual startup stuff + call IDVideoBios ; identify video BIOS + or si,si ; Q: unknown card? + jz NoSupport ; Y: tell the user the bad news + dec si ; point to video mode (mode1, mode2) + lodsb ; load into al & increment si + @SetVidMode ; change video mode +; +; snazzy graphics code goes here +; + @SetVidMode ; switch back to 80x25 text mode + @DosPrint ; print ID string + .EXIT 0 ; exit with error code = 0 + +NoSupport: + @DosPrint ; print unknown card message + .EXIT 1 ; exit with error code = 1 +main endp + +;/*************************************************************************** +; IDVideoBios +; +; This procedure searches the first SEARCH_AREA bytes in the video +; BIOS for a byte sequence which uniquely identifies a video +; card's manufacturer. If no known card name is found, the +; function returns a null pointer. +; +; Entry: DS contains the segment of the cards array +; +; Exit: If a match was found, +; DS:SI ==> matching sequence +; otherwise +; SI = 0 +; +; Destroyed: none +; +;***************************************************************************/ +IDVideoBios proc + push ax ; save used regs + push bx ; + push cx ; + push es ; + mov ax,VID_BIOS_SEG ; point to video BIOS + mov es,ax ; + mov bx,OFFSET cards ; point to first card entry + cld ; we'll be scanning forward +next_card: + mov si,[bx] ; + or si,si ; Q: is it a NULL pointer? + jz @@exit ; Y: we're done, so exit now + xor di,di ; es:di ==> video BIOS area + mov cx,SEARCH_AREA ; + mov al,[si] ; get the first letter +scan: + repne scasb ; scan for AL in es:di + jnz nofind ; if we didn't find it, skip over +; +; if we got here, ES:DI points to one letter after the matching letter +; in the video BIOS. We need to compare the rest to assure that we have +; a complete match. +; + push cx ; temporarily save regs + push di ; + push si ; + inc si ; point to next letter + mov cx,CMP_LENGTH-1 ; compare the rest the string + repe cmpsb ; do it + pop si ; restore regs + pop di ; + pop cx ; + jz @@exit ; if match, we're done +nofind: + or cx,cx ; Q: is the count down to zero? + jnz scan ; N: keep scanning + inc bx ; Y: point to next card + inc bx ; point to next card entry + jmp next_card ; go back for more +@@exit: + pop es ; restore used registers + pop cx ; + pop bx ; + pop ax ; + ret ; +IDVideoBios endp + + end \ No newline at end of file diff --git a/assembly/Subroutine called by a basic program to scroll a window.asm b/assembly/Subroutine called by a basic program to scroll a window.asm new file mode 100644 index 0000000..3d34c7b --- /dev/null +++ b/assembly/Subroutine called by a basic program to scroll a window.asm @@ -0,0 +1,117 @@ +; +; +DGROUP GROUP DATASEG +DATASEG SEGMENT PARA PUBLIC 'DATA' +FUNCT DW 0 ;function 1=6,0=7 +FG_COLR DW 0 ;forground color +BG_COLR DW 0 ;backround color +LINES DW 0 ;number of lines to scroll or 0 for clear +ULROW DW 0 ;upper left row +ULCOL DW 0 ;upper left column +LRROW DW 0 ;lower right row +LRCOL DW 0 ;lower left column +ATTRIB DB 0 ;temp hold for attribute byte +CALNU DB 0 ;temp hold for call function 6 or 7 +DATASEG ENDS +; +CSEG SEGMENT 'CODE' + ASSUME CS:CSEG + PUBLIC CLR +CLR PROC FAR + PUSH BP ;BP unknown (don't care) + MOV BP,SP ;set base for parm list + PUSH DS ;DS -> basic work area + PUSH ES ;ES -> basic work area + MOV AX,DATASEG ;establish data addressability + MOV DS,AX ;now DS -> my data + ASSUME DS:DATASEG +; +; + MOV SI,SS:[BP+6] ;get addr of parameter + MOV AX,ES:[SI] ;get value of parm + MOV FUNCT,AX + MOV SI,SS:[BP+8] ;get addr of parameter + MOV AX,ES:[SI] ;get value of parm + MOV BG_COLR,AX + MOV SI,SS:[BP+10] ;get addr of parameter + MOV AX,ES:[SI] ;get value of parm + MOV FG_COLR,AX + MOV SI,SS:[BP+12] ;get addr of parameter + MOV AX,ES:[SI] ;get value of parm + MOV LINES,AX + MOV SI,SS:[BP+14] ;get addr of parameter + MOV AX,ES:[SI] ;get value of parm + MOV ULROW,AX + MOV SI,SS:[BP+16] ;get addr of parameter + MOV AX,ES:[SI] ;get value of parm + MOV ULCOL,AX + MOV SI,SS:[BP+18] ;get addr of parameter + MOV AX,ES:[SI] ;get value of parm + MOV LRROW,AX + MOV SI,SS:[BP+20] ;get addr of parameter + MOV AX,ES:[SI] ;get value of parm + MOV LRCOL,AX +; + MOV AX,1 + SUB LRROW,AX ;convert 1-80 cols + SUB LRCOL,AX ; and 1-25 rows into + SUB ULROW,AX ; 0-79 cols and + SUB ULCOL,AX ; 0-24 rows +; +; change forground & backround colors into single attribute byte +; + MOV BX,FG_COLR ;move foreground color to bx + MOV AL,BL ;move lower byte to al + MOV BX,BG_COLR ;move backround color to bx + MOV AH,BL ;move lower byte to ah + CMP AL,15 ;check for color > 15 ie blinking + JG BLNK ;if > 15 then set blink bit + AND AL,15 ;set normal fg color + JMP N_BLNK ; +BLNK: OR AL,128 ;set blink bit 7 + AND AL,143 ;zero out bit 6,5,4 used for backround +N_BLNK: AND AH,7 ;zero out bit 7,6,5,4,3 used for forground + MOV CL,4 ;4 bit shift count + SHL AH,CL ;shift right 3 bits to pos 6,5,4 + OR AL,AH ;combine for & back to form attribute byte + MOV ATTRIB,AL ;move it to STORAGE + +; +; convert 1 and 0 to 6 and 7 for routine call +; + MOV BX,FUNCT ;move function into bx + CMP BL,0 ;compare to one + JG F6 ;if 1 then function is 6 + MOV AH,7H ;set function 7 + JMP OUT1 ;jump around +F6: MOV AH,6H ;set function 6 +OUT1: MOV CALNU,AH ;move it to storage +; +; +; set up for bios rom call 10 function 6 (scroll up ) +; + PUSH BX + MOV BX,LINES ;set # of lines to scroll or 0 to clear + MOV AL,BL ;put in pass register + MOV BX,ULROW ;set upper left row of block 0-24 + MOV CH,BL ;put in pass register + MOV BX,ULCOL ;set upper left column of block 0-79 + MOV CL,BL ;put in pass register + MOV BX,LRROW ;set lower right row of block 0-24 + MOV DH,BL ;put in pass register + MOV BX,LRCOL ;set lower right column of block 0-79 + MOV DL,BL ;put in pass register + MOV BL,CALNU ;set call number 6 to scroll up 7 down + MOV AH,BL ;put in pass register + MOV BL,ATTRIB ;set color attribute byte + MOV BH,BL ;put in pass register + INT 10H ; make bios call + POP BX +; +FINISH: POP ES + POP DS + POP BP + RET 16 ;return to basic +CLR ENDP +CSEG ENDS + END \ No newline at end of file diff --git a/assembly/Tests for the well documented Pentium divide bug.asm b/assembly/Tests for the well documented Pentium divide bug.asm new file mode 100644 index 0000000..47eece4 --- /dev/null +++ b/assembly/Tests for the well documented Pentium divide bug.asm @@ -0,0 +1,41 @@ +; pentbug.asm +; +; tests for the existence of the well-documented Pentium NPU bug +; +; assemble and run this program using Borland's TASM and run under DOS: +; +; TASM pentbug ; one pass assemble +; TLINK /Tdc pentbug ; link as COM file +; PENTBUG ; run the program... +; + .MODEL tiny + .386 + .387 + + .CODE + ORG 100h +Start: + mov dx,OFFSET okmsg ; start out optimistically + fild [first] ; load the first number (x) + fild [second] ; and the second (y) + fdiv st(1),st ; perform y/x + fmulp st(1),st ; now st(0) = (y/x)*x + fild [first] ; reload y + fcompp ; compare the two + fnstsw ax ; put status word into ax + sahf ; load into CPU flags + jz short @@NoBug ; if they're equal, no bug + mov dx,OFFSET bugmsg ; load bad news message... +@@NoBug: + mov ah,9 ; print appropriate message + int 21h ; + mov ah,4ch ; and exit + int 21h ; + +first DD 4195835 ; "magic numbers" culled from +second DD 3145727 ; the net. There are others... + +okmsg DB "No " +bugmsg DB "Pentium bug found.",13,10,'$' + + END Start \ No newline at end of file diff --git a/assembly/The venerable IBM-370 had a numeric format called packed decimal.asm b/assembly/The venerable IBM-370 had a numeric format called packed decimal.asm new file mode 100644 index 0000000..24b6966 --- /dev/null +++ b/assembly/The venerable IBM-370 had a numeric format called packed decimal.asm @@ -0,0 +1,92 @@ +; bcd.asm +comment ^ + This is a small demonstration program to show how one might + handle the addition of IBM 370-style packed decimal numbers + (which are similar to BCD). This particular program imposes an + arbitrary simplifying limitation by only allowing the addition + of numbers which are both the same sign, but it would be easy to + extend by either converting all negative operands to ten's + complement and adding or by implementing a subtraction routine + (which would use SBB, DAS instead of ADC, DAA). + +^ + .MODEL small ; DOS - small model + .STACK 200h ; allocate a bit of stack + + .DATA +OPLEN equ 4 ; the size of operands & result (bytes) +first db 00h, 01h, 23h, 4Ch ; 1234 in packed decimal +second db 00h, 00h, 00h, 9Ch ; 9 in packed decimal +result db OPLEN dup (?) ; allocate space for result + + .CODE + .STARTUP + mov si,offset first + OPLEN - 1 ; point to first op + mov bx,offset second + OPLEN - 1 ; second op + mov di,ds ; + mov es,di ; load es + mov di,offset result + OPLEN - 1 ; point to result area + mov cx,OPLEN ; how big are they? + call AddPackedDecimal ; add 'em up! + .EXIT 0 +;**************************************************************************** +; AddPackedDecimal +; +; add two 370-style packed decimal numbers with identical signs +; +; Entry: +; DS:SI ==> end of first operand +; DS:BX ==> end of second operand +; ES:DI ==> end of pre-allocated result space +; CX = size of operands, result (in bytes) +; +; Exit: +; if CY set, error occurred +; otherwise, result of addition is in result space +; +; Trashed: +; none +; +;**************************************************************************** +AddPackedDecimal proc + push ax ; save used regs + push bx + push cx + push dx + push di + push si + mov al,[si] ; + mov ah,[bx] ; + mov dx,ax ; + and dx,00f0fh ; use only low nybbles in DX + and ax,0f0f0h ; save high nybbles in AX + cmp dl,dh ; are they identical? + stc ; (assume they're not) + jnz Done ; if not, it's an error + std ; set dir flag (decrement ptrs) + clc ; clear carry flag + push di ; save original DI for later +AddEmUp: ; + adc al,ah ; add (with carry) + daa ; decimal adjust packed BCD + stosb ; save result + lahf ; save carry flag + dec si ; adjust pointer for first op + dec bx ; adjust pointer for second op + sahf ; restore flag + mov al,[si] ; fetch next digits of first op + mov ah,[bx] ; fetch next digits of second op + loop AddEmUp ; do 'em all (CX is counter) + pop di ; restore original DI + jc Done ; if carry, it's an overflow + or [di],dl ; place sign nybble (and clear CY) +Done: ; + pop si ; restore used registers + pop di + pop dx + pop cx + pop bx + pop ax + ret ; +AddPackedDecimal endp + END \ No newline at end of file diff --git a/assembly/This is a simple litte assembler program that cleans out.asm b/assembly/This is a simple litte assembler program that cleans out.asm new file mode 100644 index 0000000..026ea26 --- /dev/null +++ b/assembly/This is a simple litte assembler program that cleans out.asm @@ -0,0 +1,218 @@ +;* This is a simple litte assembler program that cleans out * +;* the documents folder in the start menu. * +;* This is version 1.2 * +;* There's no command line switches and stuff. * +;* It gives NO messages if everything goes allright. * +;* It check for a environment variable called CLEANDIR and CD:s * +;* down to that dir if the variable is found. If not it uses * +;* the default WINDOWS\RECENT directory and deletes(UNLINKS) * +;* EVERYTHING it finds there, and CD:s back to where it started * +;* from. * +;************************************************************************ + + ;some euqates for readability +kbd equ 16h ;keyboard irq +msdos equ 21h ;MSDOS irq + +reset equ 0dh ;disk reset +dfopen equ 0fh ;open disk file +dfclose equ 10h ;close disk file +searchf equ 11h ;search first +searchn equ 12h ;search next +seqread equ 14h ;sequential disk read +seqwrite equ 15h ; " " write +getdisk equ 19h ;get current disk(default) +setdta equ 1ah ;set disk transfer area address +setdir equ 3bh ;set current directory +createf equ 3ch ;create file with handle +openf equ 3dh ;open file with handle +closef equ 3eh ;close file with handle +readf equ 3fh ;read from file with handle +writef equ 40h ;write to file with handle +unlink equ 41h ;UNLINK(delete file) +getdir equ 47h ;get current directory +allocmem equ 48h ;allocate memory +freemem equ 49h ;free memory +changebs equ 4ah ;change block size +findfirst equ 4eh ;find first file +findnext equ 4fh ;find next file +exit equ 4c00h ;msdos exit + +envir equ 2ch ;offset ENVIRONMENT block + +[BITS 16] ;NASM STUFF !? +[ORG 100h] + + mov ax,cs ;get code segment + mov ds,ax ;use it now + mov [comseg],ds + mov [extseg],es + +;************************ setup and preparing *************************** +main: + mov ah,setdta ;set our DTA-area + mov dx,mydta ;buffer for it + int msdos ;call dos + + mov ah,getdisk ;get default drive + int msdos ;call dos + add al,41h ;drive in al, make it ASCII + mov byte [curdir],al ;fill buffer with name (A:..etc) + mov byte [path],al ;and default path + + mov word [curdir+1],":\" ;copy separator to path + mov si,curdir ;pointer path buffer + add si,3 ;offset doscall part + mov ah,getdir ;get current dir + mov dl,0 ;0 = default + int msdos ;call dos + jnc diskok ;ok + mov bx,errt0 ;could not find current dir ?? If You + jmp errout ;get an error here You probably have +diskok: ;forgot to turn on Your computer. + call getenv ;check out if any ENV var + cmp dx,-1 ;was it there + je findfile ;yeahh + mov dx,path ;noo way, use default path + mov ah,setdir ;cd down + int msdos ;call dos + jnc findfile ;all ok + mov bx,errt1 ;error + jmp errout ;skip + +;*************************** the delete file loop *********************** +findfile: + mov ah,findfirst ;see if the files out there + mov cx,0fh ;all files + mov dx,files ;our NULL terminated filname(*.*) + int msdos ;do the stuff + jnc delit ;all ok, must delete first file + jmp goback ;error, CD back and skip +found: ;found something + mov dx,files ;files (*.*) + mov ah,findnext ;the function + int msdos ;call dos + jc goback ;no more files, quit +delit: + mov ah,unlink ;UNLINK (delete) file + mov dx,mydta ;pointer Disk Transfer Area + add dx,30 ;offset Filename + int msdos ;delete it + jnc found ;deleted ok + + mov bx,errt2 ;could not delete it ???? + call write ;let us know + mov bx,mydta ;show wich file + add bx,30 ;offset filename in DTA + call write ;write out filename + mov bx,linefeed ;linefeed + jmp errout ;and skip +goback: + mov ah,setdir ;CD back to origin + mov dx,curdir ;path to dir + int msdos ;do it + jnc quit ;all ok, proceed + mov bx,errt1 ;error, get text + +;*************************** errorexit *********************** +errout: call write ;show errormessage +quit: + xor eax,eax ;clean out that + mov ax,exit ;MS-DOS successful exit + int msdos ;back to the operating system + +;***************** get ENVIRONMENT var if any ***************** +getenv: + push es ;now check if there's any + push ds ;environment variable + + mov es,[es:+2Ch] ;ES:DI points at environment + xor di,di ;which is paragraph-aligned +floop: + cmp byte [es:di],0 ;if we got 2 zeroes in a row + jne goon ;we are at the end of the ENV + cmp byte [es:di+1],0 ;variables + je eout +goon: +equal: cmp byte [es:di],'C' ;is it our variable ? + jne flop + inc byte di + cmp byte [es:di],'L' + jne flop + inc byte di + cmp byte [es:di],'E' + jne flop + inc byte di + cmp byte [es:di],'A' + jne flop + inc byte di + cmp byte [es:di],'N' + jne flop + inc byte di + cmp byte [es:di],'D' + jne flop + inc byte di + cmp byte [es:di],'I' + jne flop + inc byte di + cmp byte [es:di],'R' + jne flop +sign: inc byte di ;dump the R + inc byte di ;dump the = + + mov ax,es ;make DS:DX point to string we found + mov ds,ax + mov si,di + mov bx,si + mov dx,bx + mov ah,setdir ;func Set Current Directory(CD) + int msdos ;do it + jnc envok ;all ok, proceed + mov dx,0 ;clear flag (use default dir) + jmp eout ;return + +flop: inc byte di ;next byte + cmp byte [es:di],0 ;a 0 ? + jne flop ;noo + inc byte di ;yeahh, dump it + jmp floop ;check if two +envok: mov dx,-1 +eout: pop ds + pop es + ret + +;************************************************************************* +;* Writes out the NULL terminated text supplied in BX. * +;* OR writes out data,BX and size,CX if called at lwrite. * +;************************************************************************* +write: pusha + mov si,bx ;copy to SI + mov cx,0 ;clear count +wloop: lodsb ;load AL with SI + cmp al,0 ;end of line ? + je lwrite ;yeahh + inc cx ;no, incrase byte count + jmp wloop ;test next byte +lwrite: mov dx,bx ;text address in DX + mov bx,1 ;filehandle standard output = 1 + mov ah,writef ;MS-DOS writefile with handle is 040 + int msdos ;write buffer to standard output + popa + ret ;done + +;************************ DATA and BSS stuff *************************** + +comseg: dw 0 +extseg: dw 0 +utext: db "XXX",13,10,0 +errt0: db "Could not find current directory !",13,10,0 +errt1: db "Directory not found.",13,10,0 +errt2: db "Could not delete ",0 +path: db " :\WINDOWS\RECENT",0 ;default path without DRIVE +files: db "*.*",0 +linefeed: db 13,10,0 + +mydta times 128 db 0 ;use 128 bytes as DTA NASM stuff ! +curdir times 68 db 0 ;use 64 + 4 bytes for current dir + + END \ No newline at end of file diff --git a/assembly/This is a small sound example for the IBM PC.asm b/assembly/This is a small sound example for the IBM PC.asm new file mode 100644 index 0000000..7913c4e --- /dev/null +++ b/assembly/This is a small sound example for the IBM PC.asm @@ -0,0 +1,90 @@ +; It will play 12 notes of the octave starting at middle C. +;----------------------------------------------------------------------------- +; How to generate sound on the IBM PC : +; +; The 8255 (port 61H) bit 0 controls the 8253 timer +; bit 1 controls the speaker +; +; The output channel 2 from the 8253 timer will be ANDed with the +; speaker control bit in order to turn on/off the speaker. +; +; Timer channel 2 internal count register (port 42h) is loaded in +; two successive OUT operations with the lower byte being loaded first. +; For this to work properly, timer command register has to be loaded first +; with B6H. +; +; Since the input clock to the timer chip is 1.19318 MHz, the counter value +; to generate the frequency X can be calculated by 1193180 / X. +;----------------------------------------------------------------------------- +; CX is used as a note counter with the frequency effectively being +; incremented by a half tone and the corresponding count being loaded +; into the count register on each iteration. +; +; No stack segment is needed for this small program, so don't panic +; when you receive the 'No stack segment' warning. +; +; Arne Asplem 880731 (MASM 4.0) + + + +dseg segment ; data segment +notes dw 262,277,294,311,330,349,370,392,415,440,466,494 +dseg ends + +cseg segment + +sound proc far + assume cs:cseg, ds:dseg, ss:nothing + +start: + mov ax, dseg + mov ds, ax ; set up data segment (DS) reg. + xor si, si + mov bx, 12 ; note count + +; set up timer command register and counter register + + mov al, 0b6h ; set 8253 command register + out 43h, al ; for channel 2, mode 3 + +nloop: + mov ax, 34dch ; low part of clock freq. + mov dx, 12h ; hight part of clock freq. + div [notes + si] ; get note from data segment + out 42h, al ; 8253 command register (low byte) + mov al, ah + out 42h, al ; 8253 command regsieter (high byte) + +; turn on low bits in 8255 output port + + in al, 61h ; read current value of 8255 port + or al, 3 ; clear low bits + out 61h, al ; send new value to port + +; loop while note is sounding + + mov cx, 6d60h + +rpta: + loop rpta ; 1/10 sec delay + +; turn off speaker, check note count, set up next note + + xor al, 3 + out 61h, al ; turn off speaker + mov cx, 0af0h + +rptb: + loop rptb ; 1/100 sec delay + inc si ; increment note pointer + inc si + dec bx ; decrement note counter + + jnz nloop ; loop until bx = 0 + + mov ax, 4c00h ; terminate program + int 21h + +sound endp +cseg ends + end start \ No newline at end of file diff --git a/assembly/This program is used to set the PSP address for a compiled BASIC program The PSP segment is saved at 0-4F2H.asm b/assembly/This program is used to set the PSP address for a compiled BASIC program The PSP segment is saved at 0-4F2H.asm new file mode 100644 index 0000000..dcab3a0 --- /dev/null +++ b/assembly/This program is used to set the PSP address for a compiled BASIC program The PSP segment is saved at 0-4F2H.asm @@ -0,0 +1,94 @@ +extrn $$main:far +cseg segment para public 'code' + + +; It can also be used to limit the maximum memory available to a compiled +; BASIC program. The option '/M:nnn' is used on the command line, where +; nnn is the number of K-bytes the program is limited to. If no, /M option +; is specified, no memory limitation takes place. For example, '/M:64' would +; limit the program to 64*1024 bytes. The range for nnn is 64 to 1024. + +; This routine gets control before BASIC, does its handiwork, and then +; passes control to the BASIC program. It must be linked as follows: +; LINK BASMAIN+yourprog,yourprog,NUL.MAP,BASCOM + +; If BASMAIN is unable to limit memory as requested, a message is displayed +; and the execution of the program is continued. + +public basmain +basmain proc far + assume cs:cseg,ds:cseg,ss:nothing,es:nothing + + push ds ; save ds + xor ax,ax + mov ds,ax ; ds=0 + mov si,4f2h ; dos communications area + mov ax,es ; get psp seg + mov [si],ax ; save psp in dos comm area + pop ds ; restore ds + mov si,80h ; point to command line + mov ch,0 + mov cl,[si] ; get length of command line + jcxz p025 ; it's zero + +p010: inc si + mov al,[si] ; get char from command line + cmp al,'/' ; is it a slash? + jnz p020 ; no + mov ax,[si+1] ; get next 2 chars + cmp ax,':M' ; is it M: ? + jz p030 ; yes + cmp ax,':m' ; is it m: ? + jz p030 ; yes + +p020: loop p010 ; check next char +p025: jmp p080 ; no /m: or /M: found + +p030: ; found /m: or /M: + add si,3 ; point to first number + mov ax,0 + mov bx,0 + mov cx,10 +p040: mov bl,[si] ; get character + cmp bl,'0' ; out of range? + jb p050 ; yes + cmp bl,'9' ; out of range? + ja p050 ; yes + sub bl,'0' ; convert to binary + mul cx ; multiply ax by 10 + add ax,bx ; add new digit + inc si ; point to next char + jmp p040 ; continue + +p050: ; got value in ax + cmp ax,64 ; less than 64K? + jb p060 ; yes - print msg + cmp ax,1024 ; greater than 1024K? + ja p060 ; yes - print msg + mov cl,6 + sal ax,cl ; convert from KB to paragraphs (*64) + mov bx,es ; get psp + add bx,ax ; new top of memory + mov si,2 ; point to top of memory in psp + mov ax,[si] ; get current top of memory + cmp ax,bx ; is new setting larger? + jae p055 ; no + mov dx,offset msg2 ; yes - print msg + jmp p065 + +p055: mov [si],bx ; save new top of memory + jmp p080 + +p060: mov dx,offset msg1 ; print the message +p065: add dx,100h ; fudge for the psp + mov ah,9 + int 21h + +p080: jmp $$main ; jump to BASIC's start point + +msg1 db 'Memory specification must be from 64 to 1024',7,10,13,'$' +msg2 db 'Unable to limit memory',7,10,13,'$' + +basmain endp +cseg ends +end basmain ; must be a main program! diff --git a/assembly/This program provides BASIC programs with access to the program loader (LOAD) by passing parameters via the system parameter area (SYSPARM).asm b/assembly/This program provides BASIC programs with access to the program loader (LOAD) by passing parameters via the system parameter area (SYSPARM).asm new file mode 100644 index 0000000..857d394 --- /dev/null +++ b/assembly/This program provides BASIC programs with access to the program loader (LOAD) by passing parameters via the system parameter area (SYSPARM).asm @@ -0,0 +1,85 @@ +;BASLOAD.ASM +;---------------------------------------------------------------------------- +; +;Inputs: +; FILE SPEC 1 - A string (len <= 80) with the complete name, including +; path, of the file to be loaded and executed. +; Example: 'MAINMENU.EXE' or 'C:\FORMAT.COM' +; PARAMETER 1 - A string (len <= 80) with the command line parameters +; to be passed to the program specified in FILE SPEC 1. +; Example: '' or 'A:' +; FILE SPEC 2 - Same as 1. +; PARAMETER 2 - Same as 1. +; +;Outputs: +; This program gives control to LOAD. +;---------------------------------------------------------------------------- + + +CODE SEGMENT 'CODE' + ASSUME CS:CODE + + + PUBLIC BASLOAD ;make known to BASIC at link time +BASLOAD PROC FAR + + ;prologue + PUSH BP ;save BP + MOV BP,SP ;set base for parm list + PUSH DS ;DS -> basic work area + PUSH ES ;ES -> basic work area + MOV DX,'dk' ;interrupt verification switch + INT 77H ;get seg address of sysparm area in AX + MOV ES,AX ;ES -> sysparm area + CLD ;set direction for all moves + + ;move file spec 1 to sysparm + MOV BX,SS:[BP+12] ;get addr of string descriptor + MOV CX,DS:[BX] ;get length of string into CX + MOV SI,DS:[BX+2] ;get addr of string into SI + MOV DI,0 ;offset into sysparm + REP MOVSB ;move string + MOV BYTE PTR ES:[DI],0 ;make it asciiz string + + ;move parameter 1 to sysparm + MOV BX,SS:[BP+10] ;get addr of string descriptor + MOV CX,DS:[BX] ;get length of string into CX + MOV SI,DS:[BX+2] ;get addr of string into SI + MOV DI,81 ;offset into sysparm + INC CL ;adjust for cr to be added at end + MOV BYTE PTR ES:[DI],CL ;1st byte is length of string + DEC CL ;re-adjust for move operation + INC DI + REP MOVSB ;move string + MOV BYTE PTR ES:[DI],13 ;add cr to end + + ;move file spec 2 to sysparm + MOV BX,SS:[BP+8] ;get addr of string descriptor + MOV CX,DS:[BX] ;get length of string into CX + MOV SI,DS:[BX+2] ;get addr of string into SI + MOV DI,163 ;offset into sysparm + REP MOVSB ;move string + MOV BYTE PTR ES:[DI],0 ;make it asciiz string + + ;move parameter 2 to sysparm + MOV BX,SS:[BP+6] ;get addr of string descriptor + MOV CX,DS:[BX] ;get length of string into CX + MOV SI,DS:[BX+2] ;get addr of string into SI + MOV DI,244 ;offset into sysparm + INC CL ;adjust for cr to be added at end + MOV BYTE PTR ES:[DI],CL ;1st byte is length of string + DEC CL ;re-adjust for move operation + INC DI + REP MOVSB ;move string + MOV BYTE PTR ES:[DI],13 ;add cr to end + + ;exit to BASIC + POP ES + POP DS + POP BP + RET 8 + +BASLOAD ENDP + +CODE ENDS + END BASLOAD \ No newline at end of file diff --git a/assembly/This program provides COBOL programs with access to the program loader (LOAD).asm b/assembly/This program provides COBOL programs with access to the program loader (LOAD).asm new file mode 100644 index 0000000..d72f5c5 --- /dev/null +++ b/assembly/This program provides COBOL programs with access to the program loader (LOAD).asm @@ -0,0 +1,107 @@ +;by passing parameters via the system parameter area (SYSPARM). +; +;Inputs: +;01 COBLOAD-PARMS +; 05 FILE-SPEC-1 PIC X(80). Contains complete drive, path and filename. +; 05 PARAMETER-1 PIC X(80). Contains command line parameters. +; 05 FILE-SPEC-2 PIC X(80). Same as 1. +; 05 PARAMETER-2 PIC X(80). Same as 1. +; +;Outputs: +; None. +;---------------------------------------------------------------------------- + + +CL_CODE_SEG SEGMENT PUBLIC 'CODE' + ASSUME CS:CL_CODE_SEG,DS:CL_CODE_SEG,ES:CL_CODE_SEG + +STACK_PARM STRUC +PUSHED_SI DW ? +PUSHED_DI DW ? +PUSHED_DS DW ? +PUSHED_ES DW ? +PUSHED_BP DW ? +RETURN_IP DW ? +RETURN_CS DW ? +PARM1_OFFSET DW ? +PARM1_DS DW ? +STACK_PARM ENDS + + PUBLIC COBLOAD ;make known to COBOL at link time +COBLOAD PROC FAR + + ;prologue + PUSH BP + PUSH ES + PUSH DS + PUSH DI + PUSH SI + MOV BP,SP ;set base for stack parm structure + + ;address caller's parameter block + MOV AX,[BP].PARM1_DS + MOV DS,AX ;DS -> cobol data seg + MOV SI,[BP].PARM1_OFFSET ;SI -> offset to parm block + + ;address load's parameter block in sysparm + MOV DX,'dk' ;verification switch + INT 77H ;get seg addr in AX + MOV ES,AX ;ES -> sysparm + MOV DI,0 ;DI -> offset to LOAD parms + + ;move cobol's parm block to load's parm block (in sysparm) + CLD ;set direction for moves + + MOV CX,80 ;length of move + REP MOVSB ;move file spec 1 +ASCIIZ1: MOV BYTE PTR ES:[DI],0 ;make asciiz string + DEC DI + MOV AL,BYTE PTR ES:[DI] + CMP AL,' ' ;nullify trailing spaces + JE ASCIIZ1 + + MOV BX,81 ;point to parm length byte + MOV BYTE PTR ES:[BX],82 ;init length of parm, + 2 + MOV DI,82 ;point to 1st parm position + MOV CX,80 ;length of move + REP MOVSB ;move parm +ADD_CR_1: MOV BYTE PTR ES:[DI],13 ;add carriage return + DEC BYTE PTR ES:[BX] ;sub 1 from length of parm + DEC DI + MOV AL,BYTE PTR ES:[DI] + CMP AL,' ' ;put cr in trailing spaces + JE ADD_CR_1 + + MOV DI,163 + MOV CX,80 ;length of move + REP MOVSB ;move file spec 2 +ASCIIZ2: MOV BYTE PTR ES:[DI],0 ;make asciiz string + DEC DI + MOV AL,BYTE PTR ES:[DI] + CMP AL,' ' ;nullify trailing spaces + JE ASCIIZ2 + + MOV BX,244 ;point to parm length byte + MOV BYTE PTR ES:[BX],82 ;init length of parm, + 2 + MOV DI,245 ;point to 1st parm position + MOV CX,80 ;length of move + REP MOVSB ;move parm +ADD_CR_2: MOV BYTE PTR ES:[DI],13 ;add carriage return + DEC BYTE PTR ES:[BX] ;sub 1 from length of parm + DEC DI + MOV AL,BYTE PTR ES:[DI] + CMP AL,' ' ;put cr in trailing spaces + JE ADD_CR_2 + + ;return to caller + POP SI + POP DI + POP DS + POP ES + POP BP + RET 4 + +COBLOAD ENDP + +CL_CODE_SEG ENDS + END \ No newline at end of file diff --git a/assembly/This program removes all control codes except for line feeds.asm b/assembly/This program removes all control codes except for line feeds.asm new file mode 100644 index 0000000..b269edd --- /dev/null +++ b/assembly/This program removes all control codes except for line feeds.asm @@ -0,0 +1,412 @@ +; +; CLEAN --- a utility to filter text files. +; This program removes all control codes except +; for line feeds, carriage returns, and form +; feeds, strips off the high bit of all characters, +; and expands tabs. Can be used to make a Wordstar +; file acceptable for other screen or line editors, +; and vice versa. +; + + +cr equ 0dh ;ASCII carriage return +lf equ 0ah ;ASCII line feed +ff equ 0ch ;ASCII form feed +eof equ 01ah ;End of file marker +tab equ 09h ;ASCII tab character + +command equ 80h ;buffer for command tail + +blksize equ 1024 ;blocking/deblocking size + + +cseg segment para public 'CODE' + + assume cs:cseg,ds:data,es:data,ss:stack + + +clean proc far ;entry point from PC-DOS + + push ds ;save DS:0000 for final + xor ax,ax ;return to PC-DOS + push ax + mov ax,data ;make our data segment + mov es,ax ;addressable via ES register + call infile ;get path and file spec. + ;for input file + mov ax,es ;set DS=ES for remainder + mov ds,ax ;of program + jnc clean1 ;jump, got acceptable name + mov dx,offset msg4 ;missing or illegal filespec, + jmp clean9 ;print error message and exit. + +clean1: call outfile ;set up output file name + call open_input ;now try to open input file + jnc clean2 ;jump,opened input ok + mov dx,offset msg1 ;open of input file failed, + jmp clean9 ;print error msg and exit. + +clean2: + call open_output ;try to open output file. + jnc clean25 ;jump,opened ok + mov dx,offset msg2 ;open of output file failed, + jmp clean9 ;print error message and exit. + +clean25: ;set up buffers + call init_buffs + call sign_on ;print ident and file names + + ;files successfully opened, +clean3: ;now filter the file. + call get_char ;read 1 character from input. + and al,07fh ;strip off the high bit + cmp al,20h ;is it a control code? + jae clean4 ;no,write it to new file + ;yes it is control code, + cmp al,eof ;is it end of file marker? + je clean6 ;yes,jump to close files. + cmp al,tab ;is it a tab command? + jz clean5 ;yes,jump to special processing. + cmp al,cr ;if control code other than + je clean35 ;tab or end-of-file mark, throw + cmp al,ff ;it away unless it is a + je clean35 ;form feed, carriage return, + cmp al,lf ;or line feed. + jne clean3 +clean35: ;If it is one of those three, + mov column,0 ;incidentally initialize + jmp clean45 ;column count for tab processor. + +clean4: ;count alphanumeric chars. sent. + inc column + +clean45: ;write this character to + call put_char ;output file, + jnc clean3 ;if CY not set, write was + ;ok so go get next char. +clean47: + call close_input ;if CY set, disk is full + call close_output ;so close files and exit + mov dx,offset msg5 ;with error message. + jmp clean9 + +clean5: ;process tab character + mov ax,column ;let DX:AX=column count + cwd + mov cx,8 ;divide it by eight... + idiv cx + sub cx,dx ;remainder is in DX. + add column,cx ;update column pointer. +clean55: ;8 minus the remainder + push cx ;gives us the number of + mov al,20h ;spaces to send out to + call put_char ;move to the next tab position + pop cx ;restore space count + jc clean47 ;jump if disk is full + loop clean55 + jmp short clean3 ;get next character + +clean6: ;end of file detected, + call put_char ;write end-of-file marker, + jc clean47 ;jump if disk was full + call flush_buffs ;write remaining data to disk + jc clean47 ;if CY set,disk was full + ;otherwise file was written ok + call close_input ;close input and output + call close_output ;files. + mov dx,offset msg3 ;addr of success message, + +clean9: ;print message and return + mov ah,9 ;control to PC-DOS + int 21h + ret + +clean endp + + +infile proc near ;process name of input file + ;DS:SI <- addr command line + mov si,offset command + ;ES:DI <- addr filespec buffer + mov di,offset input_name + cld + lodsb ;any command line present? + or al,al ;return error status if not. + jz infile4 +infile1: ;scan over leading blanks + lodsb ;to file name + cmp al,cr ;if we hit carriage return + jz infile4 ;filename is missing. + cmp al,20h ;is this a blank? + jz infile1 ;if so keep scanning. + +infile2: ;found first char of name, + stosb ;move last char. to output + ;file name buffer. + lodsb ;check next character, found + cmp al,cr ;carriage return yet? + je infile3 ;yes,exit with success code + cmp al,20h ;is this a blank? + jne infile2 ;if not keep moving chars. + +infile3: ;exit with carry =0 + clc ;for success flag + ret + +infile4: ;exit with carry =1 + stc ;for error flag + ret +infile endp + +outfile proc near ;set up path and file + cld ;name for output file. + mov cx,64 ;length to move + mov si,offset input_name ;source addr + mov di,offset output_name ;dest addr + rep movsb ;transfer the string + mov di,offset output_name +outfile1: ;scan string looking for + mov al,[di] ;"." marking start of extension + or al,al ;or zero byte marking name end. + jz outfile2 ;if either is found,jump. + cmp al,'.' + je outfile2 ;bump string pointer, loop + inc di ;if neither '.' or zero found. + jmp outfile1 +outfile2: ;found zero or '.',force the + ;extension of the output file + ;to '.CLN' + mov si,offset outfile_ext + mov cx,5 + rep movsb + ret ;back to caller +outfile endp + +open_input proc near ;open input file + ;DS:DX=addr filename + mov dx,offset input_name + mov al,0 ;AL=0 for read only + mov ah,3dh ;function 3dh=open + int 21h ;handle returned in AX, + mov input_handle,ax ;save it for later. + ret ;CY is set if error +open_input endp + +open_output proc near ;open output file + ;DS:DX=addr filename + mov dx,offset output_name + mov al,1 ;AL=1 for write only + mov ah,3ch ;function 3ch=MAKE or + int 21h ;truncate existing file + ;handle returned in AX + mov output_handle,ax;save it for later. + ret ;return CY=true if error +open_output endp + +close_input proc near ;close input file + mov bx,input_handle ;BX=handle + mov ah,3eh + int 21h + ret +close_input endp + +close_output proc near ;close output file + mov bx,output_handle;BX=handle + mov ah,3eh + int 21h + ret +close_output endp + +get_char proc near ;get one character from input buffer + mov bx,input_ptr + cmp bx,blksize + jne get_char1 + call read_block + mov bx,0 +get_char1: + mov al,[input_buffer+bx] + inc bx + mov input_ptr,bx + ret +get_char endp + +put_char proc near ;put one character into output buffer + mov bx,output_ptr + mov [output_buffer+bx],al + inc bx + mov output_ptr,bx + cmp bx,blksize ;buffer full yet? + jne put_char1 ;no,jump + call write_block ;yes,write the block + ret ;return CY as status code +put_char1: + clc ;return CY clear for OK status + ret +put_char endp + +read_block proc near + mov bx,input_handle ;read first block of input + mov cx,blksize + mov dx,offset input_buffer + mov ah,3fh + int 21h + jnc read_block1 ;jump if no error status + mov ax,0 ;simulate a zero length read if error +read_block1: + cmp ax,blksize ;was full buffer read in? + je read_block2 ;yes,jump + mov bx,ax ;no, store End-of-File mark + mov byte ptr [input_buffer+bx],eof +read_block2: + xor ax,ax ;initialize input buffer pointer + mov input_ptr,ax + ret +read_block endp + +write_block proc near ;write blocked output (blksize bytes) + mov dx,offset output_buffer + mov cx,blksize + mov bx,output_handle + mov ah,40h + int 21h + xor bx,bx ;initialize pointer to blocking buffer + mov output_ptr,bx + cmp ax,blksize ;was correct length written? + jne write_block1 ;no,disk must be full + clc ;yes,return CY=0 indicating all OK + ret +write_block1: ;disk is full, return CY =1 + stc ;as error code + ret +write_block endp + +init_buffs proc near + call read_block ;read 1st block of input + xor ax,ax ;initialize pointer to output + mov output_ptr,ax ;output blocking buffer + ret +init_buffs endp + +flush_buffs proc near ;write any data in output buffer to disk + mov cx,output_ptr + or cx,cx + jz flush_buffs1 ;jump,buffer is empty + mov bx,output_handle + mov dx,offset output_buffer + mov ah,40h + int 21h + cmp ax,output_ptr ;was write successful? + jnz flush_buffs2 ;no,jump +flush_buffs1: + clc ;yes,return CY=0 for + ret ;success flag +flush_buffs2: ;disk was full so write failed, + stc ;return CY=1 as error flag + ret +flush_buffs endp + +sign_on proc near ;print sign-on message + mov dx,offset msg6 ;title... + mov ah,9 + int 21h + mov dx,offset msg7 ;input file: + mov ah,9 + int 21h + mov dx,offset input_name + call pasciiz + mov dx,offset msg8 ;output file: + mov ah,9 + int 21h + mov dx,offset output_name + call pasciiz + mov dx,offset msg9 + mov ah,9 + int 21h + ret +sign_on endp + +pasciiz proc near ;call DX=offset of ASCIIZ string + mov bx,dx ;which will be printed on standard output +pasciiz1: + mov dl,[bx] + or dl,dl + jz pasciiz9 + cmp dl,'A' + jb pasciiz2 + cmp dl,'Z' + ja pasciiz2 + or dl,20h +pasciiz2: + mov ah,2 + int 21h + inc bx + jmp pasciiz1 +pasciiz9: + ret +pasciiz endp + +cseg ends + + +data segment para public 'DATA' + +input_name db 64 dup (0) ;buffer for input filespec +output_name db 64 dup (0) ;buffer for output filespec + +input_handle dw 0 ;token returned by PCDOS +output_handle dw 0 ;token returned by PCDOS + +input_ptr dw 0 ;pointer to input blocking buffer +output_ptr dw 0 ;pointer to output blocking buffer + +outfile_ext db '.CLN',0 ;extension for filtered file + +column dw 0 ;column count for tab processing + +msg1 db cr,lf + db 'Cannot find input file.' + db cr,lf,'$' + +msg2 db cr,lf + db 'Failed to open output file.' + db cr,lf,'$' + +msg3 db cr,lf + db 'File processing completed' + db cr,lf,'$' + +msg4 db cr,lf + db 'Missing file name.' + db cr,lf,'$' + +msg5 db cr,lf + db 'Disk is full.' + db cr,lf,'$' + +msg6 db cr,lf + db 'Clean Word Processing File' + db cr,lf + db 'WWW.' + db cr,lf,'$' + +msg7 db cr,lf,'Input file: $' + +msg8 db cr,lf,'Output file: $' + +msg9 db cr,lf,'$' + + +input_buffer db blksize dup (?) ;buffer for deblocking of data + ;from input file + +output_buffer db blksize dup (?) ;buffer for blocking of data + ;sent to output file + +data ends + + +stack segment para stack 'STACK' + db 64 dup (?) +stack ends + + end clean \ No newline at end of file diff --git a/assembly/Writes a boot sector to the floppy disk.asm b/assembly/Writes a boot sector to the floppy disk.asm new file mode 100644 index 0000000..c1c79b2 --- /dev/null +++ b/assembly/Writes a boot sector to the floppy disk.asm @@ -0,0 +1,182 @@ +; sector.asm +; +; writes a boot sector out to the floppy disk in the A: drive +; +; The input file is assumed to be a binary file with the relevant code +; at offset 7C00h relative to the beginning of the file. This is because +; when the sector loader transfers control to the boot sector, it's at +; address 0:7C00h. Rather than clutter up the boot loader source with +; a bunch of ugly offsets, we simply use an ORG 7C00h instead and let +; the linker insert a bunch of empty space which this program skips over. +; +; Style Note: +; There aren't any hardwired numbers in this code. That is to say, +; equates and macros are used to render gibberish like this: +; mov ax,4c00h +; int 33 +; +; into somewhat self-documenting code like this: +; DosInt DOS_TERMINATE, 0 +; +; This is done to make the code more readable, and comprehensible, and +; to aid in maintenance by not littering mysterious constants throughout +; the code. Please be kind to animals (specifically your fellow +; programmers) and use this practice in your own code. +; +; + +STACKSIZE = 200h ; this is how much stack we'll allocate + +SECTORSIZE = 200h ; size of the boot sector on a floppy + +CMD_LINE_LEN = 80h ; offset of the command line length (one byte) + ; relative to the beginning of the PSP. + +CMD_LINE = 81h ; the offset relative to the beginning of the + ; PSP that is the start of the command line + ; arguments. + + +DOS_OPEN_HANDLE = 03dh ; open file + READ_ONLY_DENY_NONE = 020h ; file open mode +DOS_MOVE_HANDLE = 042h ; move file pointer + WHENCE_BEGIN = 0 ; move pointer relative to beginning + WHENCE_CURRENT = 1 ; move pointer relative to current location + WHENCE_EOF = 2 ; move pointer relative to end of file +DOS_READ_HANDLE = 03fh ; read from an open file handle +DOS_CLOSE_HANDLE = 03eh ; close an open file handle +DOS_WRITE_HANDLE = 040h ; write to open file +DOS_TERMINATE = 04ch ; terminate and exit + +DOS_INT = 021h + +; various named character constants +NUL = 0 +CR = 13 +LF = 10 +SPACE = ' ' + +GenericInt macro function, subfunction + ifb + mov ah,function + else + mov ax,(function SHL 8) OR (subfunction AND 0ffh) + endif +endm + +DosInt macro function, subfunction + GenericInt , + int DOS_INT +endm + +BDISK_WRITE_SECTOR = 03h + +BDISK_INT = 013h + +; constants unique to this program + +FILE_OFFS_LO = 7C00h ; +FILE_OFFS_HI = 0000h ; + +BOOT_DRIVE = 0 ; we'll be writing to drive A: +BOOT_HEAD = 0 ; head 0 is the boot head +BOOT_CYLSECT = 0001h ; a word value with the following format + ; bits 15-8 low bits of cylinder + ; bits 7-6 high two bits of cylinder + ; bits 5-0 sector +NUM_SECTORS = 1 ; number of sector to write to disk + + model small + .386 + .stack STACKSIZE + .code +;********************************************************************** +; program code start +;********************************************************************** +Start: +; parse the command line args + mov cl,byte ptr [DGROUP:CMD_LINE_LEN] ; read the length byte + ; NOTE that the command line length isn't really part of the + ; DGROUP group, but DS currently points to the PSP, and if we + ; omit the DGROUP override, the assembler thinks we're trying + ; to load a constant instead of the contents of the memory loc. + ; In other words, it's ugly but it has a purpose. + or cl,cl ; check for zero + jz Usage ; no command line args + mov si,CMD_LINE ; + mov al,' ' ; + repe cmpsb ; burn off leading spaces + mov dx,si ; save that starting point + repne cmpsb ; scan for next space (if any) + cmp byte ptr [si],SPACE ; if it's > space char, + ja skip ; skip the nul termination + mov byte ptr [si],NUL ; terminate with a NUL char +skip: +; first, open the file + DosInt DOS_OPEN_HANDLE, READ_ONLY_DENY_NONE + mov si,seg DGROUP ; + mov ds,si ; + mov es,si ; point 'em all over there + mov si,offset err_fopen ; can't open input file + jc ErrorExit +; the file's open, so move the file pointer to offset 7C00h + mov bx,ax ; fetch the file handle + mov cx,FILE_OFFS_HI + mov dx,FILE_OFFS_LO + DosInt DOS_MOVE_HANDLE, WHENCE_BEGIN + mov si,offset err_fmove ; + jc ErrorExit ; +; read the data + mov cx,SECTORSIZE ; max number of bytes to read + mov dx,offset buffer ; point ds:dx to buffer + DosInt DOS_READ_HANDLE ; + mov si,offset err_fread ; + jc ErrorExit ; +; close the file + DosInt DOS_CLOSE_HANDLE ; close this file + +; now write it out to the floppy disk's boot sector + mov bx,offset buffer ; + mov cx,BOOT_CYLSECT ; + mov dx,(BOOT_HEAD SHL 8) OR (BOOT_DRIVE) + GenericInt BDISK_WRITE_SECTOR, NUM_SECTORS + int BDISK_INT + mov si,offset err_write ; + jc ErrorExit ; + mov si,offset msg_ok ; +ErrorExit: + mov cx,[si] ; + inc si ; + inc si ; + mov dx,si ; + mov bx,1 ; write to stdout + DosInt DOS_WRITE_HANDLE ; write to that file + DosInt DOS_TERMINATE, 0 + +Usage: + mov si,seg DGROUP ; + mov ds,si ; load correct data segment + mov si,offset use_msg + jmp ErrorExit ; + + +;********************************************************************** +; program data starts +;********************************************************************** + .data +msgstruc macro msglabel, msgstring + local alpha +msglabel dw (alpha - $) - 2 + db msgstring +alpha = $ +endm + +msgstruc err_fopen ,<"ERROR: couldn't open input file",CR,LF> +msgstruc err_fmove ,<"ERROR: unable to move file pointer",CR,LF> +msgstruc err_fread ,<"ERROR: couldn't read from input file",CR,LF> +msgstruc err_write ,<"ERROR: unable to write to floppy disk",CR,LF> +msgstruc msg_ok ,<"Boot sector was successfully written to floppy",CR,LF> +msgstruc use_msg ,<"Usage: SECTOR infile.bin",CR,LF> + +buffer db SECTORSIZE dup (?) ; sector buffer + end Start \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Perform to a 2D FFT Inplace Given a Complex 2D Array.cpp b/c++/11_Numerical_Problems/C++ Perform to a 2D FFT Inplace Given a Complex 2D Array.cpp new file mode 100644 index 0000000..deba0a7 --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Perform to a 2D FFT Inplace Given a Complex 2D Array.cpp @@ -0,0 +1,70 @@ +/*This is a C++ Program to perform 2D FFT. A fast Fourier transform (FFT) is an algorithm to compute the discrete Fourier transform (DFT) and its inverse. Fourier analysis converts time (or space) to frequency and vice versa; an FFT rapidly computes such transformations by factorizing the DFT matrix into a product of sparse (mostly zero) factors.*/ + +#include +#include + +using namespace std; + +#define PI 3.14159265 +int n; + +int main(int argc, char **argv) +{ + cout << "Enter the size: "; + cin >> n; + double inputData[n][n]; + cout << "Enter the 2D elements "; + for (int i = 0; i < n; i++) + for (int j = 0; j < n; j++) + cin >> inputData[i][j]; + double realOut[n][n]; + double imagOut[n][n]; + double amplitudeOut[n][n]; + int height = n; + int width = n; + // Two outer loops iterate on output data. + for (int yWave = 0; yWave < height; yWave++) + { + for (int xWave = 0; xWave < width; xWave++) + { + // Two inner loops iterate on input data. + for (int ySpace = 0; ySpace < height; ySpace++) + { + for (int xSpace = 0; xSpace < width; xSpace++) + { + // Compute real, imag, and ampltude. + realOut[yWave][xWave] += (inputData[ySpace][xSpace] * cos( + 2 * PI * ((1.0 * xWave * xSpace / width) + (1.0 + * yWave * ySpace / height)))) / sqrt( + width * height); + imagOut[yWave][xWave] -= (inputData[ySpace][xSpace] * sin( + 2 * PI * ((1.0 * xWave * xSpace / width) + (1.0 + * yWave * ySpace / height)))) / sqrt( + width * height); + amplitudeOut[yWave][xWave] = sqrt( + realOut[yWave][xWave] * realOut[yWave][xWave] + + imagOut[yWave][xWave] + * imagOut[yWave][xWave]); + } + cout << realOut[yWave][xWave] << " + " << imagOut[yWave][xWave] + << " i (" << amplitudeOut[yWave][xWave] << ")\n"; + } + } + } +} + +/* +Enter the size: +2 +Enter the 2D elements +2 3 +4 2 + +2.5 + 0.0 i +5.5 + 0.0 i +-0.5 + -1.8369701987210297E-16 i +0.5 + -3.0616169978683826E-16 i +2.5 + 0.0 i +-0.5 + -3.6739403974420594E-16 i +-0.5 + -1.8369701987210297E-16 i +-1.5 + -1.8369701987210297E-16 i \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Check Multiplicability of Two Matrices.cpp b/c++/11_Numerical_Problems/C++ Program to Check Multiplicability of Two Matrices.cpp new file mode 100644 index 0000000..e0ca7bf --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Check Multiplicability of Two Matrices.cpp @@ -0,0 +1,40 @@ +#include +#include +#include + +using namespace std; + +int main(int argc, char **argv) +{ + cout<<"Enter the dimension of the matrix:\n "; + int rowA; + cin>>rowA; + int colA; + cin>>colA; + cout<<"Enter the dimension of the other matrix:\n "; + int rowB; + cin>>rowB; + int colB; + cin>>colB; + if(colA == rowB) + { + cout<<"Matrices are multipilcable"; + } + else + { + cout<<"Matrices are not multipilcable"; + } +} + +/* +Enter the dimension of the matrix: + 2 4 +Enter the dimension of the other matrix: + 2 5 +Matrices are not multipilcable + +Enter the dimension of the matrix: + 4 5 +Enter the dimension of the other matrix: + 5 6 +Matrices are multipilcable \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Check if a Matrix is Invertible.cpp b/c++/11_Numerical_Problems/C++ Program to Check if a Matrix is Invertible.cpp new file mode 100644 index 0000000..516edbd --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Check if a Matrix is Invertible.cpp @@ -0,0 +1,76 @@ +#include +#include +#include + +using namespace std; +double d = 0; +double det(int n, double mat[10][10]); +double det(int n, double mat[10][10]) +{ + double submat[10][10]; + if (n == 2) + return ((mat[0][0] * mat[1][1]) - (mat[1][0] * mat[0][1])); + else + { + for (int c = 0; c < n; c++) + { + int subi = 0; //submatrix's i value + for (int i = 1; i < n; i++) + { + int subj = 0; + for (int j = 0; j < n; j++) + { + if (j == c) + continue; + submat[subi][subj] = mat[i][j]; + subj++; + } + subi++; + } + d = d + (pow(-1, c) * mat[0][c] * det(n - 1, submat)); + } + } + return d; +} +int main(int argc, char **argv) +{ + cout << "Enter the dimension of the matrix:\n"; + int n; + cin >> n; + double mat[10][10]; + cout << "Enter the elements of the matrix:\n"; + for (int i = 0; i < n; i++) + { + for (int j = 0; j < n; j++) + { + cin >> mat[j][i]; + } + } + if (det(n, mat) != 0) + { + cout << "The given matrix is invertible"; + } + else + { + cout << "The given matrix is not invertible"; + } +} + +/* +Enter the dimension of the matrix: +3 +Enter the elements of the matrix: +1 2 3 +4 5 6 +7 8 9 +The given matrix is not invertible + +Enter the dimension of the matrix: +5 +Enter the elements of the matrix: +1 2 3 4 5 +6 7 8 9 0 +0 9 8 7 6 +5 4 3 2 1 +1 3 5 7 9 +The given matrix is invertible \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Check if it is a Sparse Matrix.cpp b/c++/11_Numerical_Problems/C++ Program to Check if it is a Sparse Matrix.cpp new file mode 100644 index 0000000..75dada5 --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Check if it is a Sparse Matrix.cpp @@ -0,0 +1,54 @@ +#include +#include + +using namespace std; +int main(int argc, char **argv) +{ + cout<<"Enter the dimensions of the matrix: "; + int m, n; + cin>>m>>n; + double mat[m][n]; + int zeros = 0; + cout<<"Enter the elements of the matrix: "; + for(int i=0; i>mat[i][j]; + if(mat[i][j] == 0) + { + zeros++; + } + } + } + if(zeros > (m*n)/2) + { + cout<<"The matrix is a sparse matrix"; + } + else + { + cout<<"The matrix is not a sparse matrix"; + } +} + +/* +Enter the dimensions of the matrix: +3 3 + +Enter the elements of the matrix: +1 2 3 +4 5 6 +0 0 0 + +The matrix is not a sparse matrix + + +Enter the dimensions of the matrix: +3 3 + +Enter the elements of the matrix: +1 1 0 +0 0 1 +1 0 0 + +The matrix is a sparse matrix \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Compute DFT Coefficients Directly.cpp b/c++/11_Numerical_Problems/C++ Program to Compute DFT Coefficients Directly.cpp new file mode 100644 index 0000000..97ea26e --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Compute DFT Coefficients Directly.cpp @@ -0,0 +1,65 @@ +/*This is a C++ Program to compute the coefficients of the DFT (Discrete Fourier Transform) directly. In mathematics, the discrete Fourier transform (DFT) converts a finite list of equally spaced samples of a function into the list of coefficients of a finite combination of complex sinusoids, ordered by their frequencies, that has those same sample values. It can be said to convert the sampled function from its original domain (often time or position along a line) to the frequency domain.*/ + +#include +#include + +using namespace std; + +#define PI 3.14159265 + +class DFT_Coefficient +{ +public: + double real, img; + DFT_Coefficient() + { + real = 0.0; + img = 0.0; + } +}; +int main(int argc, char **argv) +{ + int N = 10; + cout << "Calculation DFT Coefficients\n"; + cout << "Enter the coefficient of simple linear function:\n"; + cout << "ax + by = c\n"; + double a, b, c; + cin >> a >> b >> c; + double function[N]; + for (int i = 0; i < N; i++) + { + function[i] = (((a * (double) i) + (b * (double) i)) - c); + //System.out.print( " "+function[i] + " "); + } + cout << "Enter the max K value: "; + int k; + cin >> k; + double cosine[N]; + double sine[N]; + for (int i = 0; i < N; i++) + { + cosine[i] = cos((2 * i * k * PI) / N); + sine[i] = sin((2 * i * k * PI) / N); + } + DFT_Coefficient dft_val; + cout << "The coefficients are: "; + for (int i = 0; i < N; i++) + { + dft_val.real += function[i] * cosine[i]; + dft_val.img += function[i] * sine[i]; + } + cout << "(" << dft_val.real << ") - " << "(" << dft_val.img << " i)"; +} + +/* +Calculation DFT Coefficients +Enter the coefficient of simple linear funtion: +ax + by = c +1 2 3 +Enter the max K value: +2 +The coefficients are: (-15) - (-20.6457 i) + +------------------ +(program exited with code: 0) +Press return to continue \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Compute Determinant of a Matrix.cpp b/c++/11_Numerical_Problems/C++ Program to Compute Determinant of a Matrix.cpp new file mode 100644 index 0000000..9ed3484 --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Compute Determinant of a Matrix.cpp @@ -0,0 +1,69 @@ +#include +#include +#include + +using namespace std; +double d = 0; +double det(int n, double mat[10][10]); +double det(int n, double mat[10][10]) +{ + double submat[10][10]; + if (n == 2) + return ((mat[0][0] * mat[1][1]) - (mat[1][0] * mat[0][1])); + else + { + for (int c = 0; c < n; c++) + { + int subi = 0; //submatrix's i value + for (int i = 1; i < n; i++) + { + int subj = 0; + for (int j = 0; j < n; j++) + { + if (j == c) + continue; + submat[subi][subj] = mat[i][j]; + subj++; + } + subi++; + } + d = d + (pow(-1, c) * mat[0][c] * det(n - 1, submat)); + } + } + return d; +} +int main(int argc, char **argv) +{ + cout << "Enter the dimension of the matrix:\n"; + int n; + cin >> n; + double mat[10][10]; + cout << "Enter the elements of the matrix:\n"; + for (int i = 0; i < n; i++) + { + for (int j = 0; j < n; j++) + { + cin >> mat[j][i]; + } + } + cout << "The determinant of the given matrix is: " << det(n, mat); + return 0; +} + +/* +Enter the dimension of the matrix: +3 +Enter the elements of the matrix: +3 5 2 +8 4 8 +2 4 7 +The determinant of the given matrix is: -164 + +Enter the dimension of the matrix: +4 +Enter the elements of the matrix: +9 5 2 5 +9 5 3 7 +6 5 4 8 +1 5 3 7 +The determinant of the given matrix is: 0 \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Compute Discrete Fourier Transform Using Naive Approach.cpp b/c++/11_Numerical_Problems/C++ Program to Compute Discrete Fourier Transform Using Naive Approach.cpp new file mode 100644 index 0000000..809a995 --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Compute Discrete Fourier Transform Using Naive Approach.cpp @@ -0,0 +1,84 @@ +/*This is a C++ Program to perform Discrete Fourier Transform using Naive approach. In mathematics, the discrete Fourier transform (DFT) converts a finite list of equally spaced samples of a function into the list of coefficients of a finite combination of complex sinusoids, ordered by their frequencies, that has those same sample values. It can be said to convert the sampled function from its original domain (often time or position along a line) to the frequency domain.*/ + +#include +#include + +using namespace std; + +#define PI 3.14159265 + +class DFT_Coefficient +{ +public: + double real, img; + DFT_Coefficient() + { + real = 0.0; + img = 0.0; + } +}; +int main(int argc, char **argv) +{ + int N = 10; + cout << "Discrete Fourier Transform using naive method\n"; + cout << "Enter the coefficient of simple linear function:\n"; + cout << "ax + by = c\n"; + double a, b, c; + cin >> a >> b >> c; + double function[N]; + for (int i = 0; i < N; i++) + { + function[i] = (((a * (double) i) + (b * (double) i)) - c); + //System.out.print( " "+function[i] + " "); + } + cout << "Enter the max K value: "; + int k; + cin >> k; + double cosine[N]; + double sine[N]; + for (int i = 0; i < N; i++) + { + cosine[i] = cos((2 * i * k * PI) / N); + sine[i] = sin((2 * i * k * PI) / N); + } + DFT_Coefficient dft_val[k]; + cout << "The coefficients are: "; + for (int j = 0; j < k; j++) + { + for (int i = 0; i < N; i++) + { + dft_val[j].real += function[i] * cosine[i]; + dft_val[j].img += function[i] * sine[i]; + } + cout << "(" << dft_val[j].real << ") - " << "(" << dft_val[j].img << " i)\n"; + } +} + +/* + +Discrete Fourier Transform using naive method +Enter the coefficient of simple linear function: +ax + by = c +1 2 3 +Enter the max K value: 20 +The coefficients are: +(105) - (-1.03386e-005 i) +(105) - (-1.03386e-005 i) +(105) - (-1.03386e-005 i) +(105) - (-1.03386e-005 i) +(105) - (-1.03386e-005 i) +(105) - (-1.03386e-005 i) +(105) - (-1.03386e-005 i) +(105) - (-1.03386e-005 i) +(105) - (-1.03386e-005 i) +(105) - (-1.03386e-005 i) +(105) - (-1.03386e-005 i) +(105) - (-1.03386e-005 i) +(105) - (-1.03386e-005 i) +(105) - (-1.03386e-005 i) +(105) - (-1.03386e-005 i) +(105) - (-1.03386e-005 i) +(105) - (-1.03386e-005 i) +(105) - (-1.03386e-005 i) +(105) - (-1.03386e-005 i) +(105) - (-1.03386e-005 i) \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Compute Discrete Fourier Transform Using the Fast Fourier Transform Approach.cpp b/c++/11_Numerical_Problems/C++ Program to Compute Discrete Fourier Transform Using the Fast Fourier Transform Approach.cpp new file mode 100644 index 0000000..49830c2 --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Compute Discrete Fourier Transform Using the Fast Fourier Transform Approach.cpp @@ -0,0 +1,73 @@ +/*This is a C++ Program to perform Fast Fourier Transform. A fast Fourier transform (FFT) is an algorithm to compute the discrete Fourier transform (DFT) and its inverse. Fourier analysis converts time (or space) to frequency and vice versa; an FFT rapidly computes such transformations by factorizing the DFT matrix into a product of sparse (mostly zero) factors.*/ + +#include +#include +#include +#include +using namespace std; + +unsigned int bitReverse(unsigned int x, int log2n) + +{ + int n = 0; + int mask = 0x1; + for (int i = 0; i < log2n; i++) + { + n <<= 1; + n |= (x & 1); + x >>= 1; + } + return n; +} +const double PI = 3.1415926536; +template +void fft(Iter_T a, Iter_T b, int log2n) +{ + typedef typename iterator_traits::value_type complex; + const complex J(0, 1); + int n = 1 << log2n; + for (unsigned int i = 0; i < n; ++i) + { + b[bitReverse(i, log2n)] = a[i]; + } + for (int s = 1; s <= log2n; ++s) + { + int m = 1 << s; + int m2 = m >> 1; + complex w(1, 0); + complex wm = exp(-J * (PI / m2)); + for (int j = 0; j < m2; ++j) + { + for (int k = j; k < n; k += m) + { + complex t = w * b[k + m2]; + complex u = b[k]; + b[k] = u + t; + b[k + m2] = u - t; + } + w *= wm; + } + } +} +int main(int argc, char **argv) +{ + typedef complex cx; + cx a[] = { cx(0, 0), cx(1, 1), cx(3, 3), cx(4, 4), cx(4, 4), cx(3, 3), cx( + 1, 1), cx(0, 0) + }; + cx b[8]; + fft(a, b, 3); + for (int i = 0; i < 8; ++i) + cout << b[i] << "\n"; +} + +/* + +(16,16) +(-4.82843,-11.6569) +(0,0) +(-0.343146,0.828427) +(0,0) +(0.828427,-0.343146) +(0,0) +(-11.6569,-4.82843) \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Emulate N Dice Roller.cpp b/c++/11_Numerical_Problems/C++ Program to Emulate N Dice Roller.cpp new file mode 100644 index 0000000..bbbb506 --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Emulate N Dice Roller.cpp @@ -0,0 +1,25 @@ +#include +#include + +using namespace std; + +int main(int argc, char **argv) +{ + cout << "Enter the number of dice: "; + int n; + cin >> n; + cout << "The values on dice are: ( "; + for (int i = 0; i < n; i++) + cout << (rand() % 6) + 1<<" "; + cout<<")"; +} + +/* +Enter the number of dice: 5 +The values on dice are: ( 6 6 5 5 6 ) + +Enter the number of dice: 1 +The values on dice are: ( 6 ) + +Enter the number of dice: 3 +The values on dice are: ( 6 6 5 ) \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Find Basis and Dimension of a Matrix.cpp b/c++/11_Numerical_Problems/C++ Program to Find Basis and Dimension of a Matrix.cpp new file mode 100644 index 0000000..183fa0c --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Find Basis and Dimension of a Matrix.cpp @@ -0,0 +1,74 @@ +#include +#include +#include + +using namespace std; +double d = 0; +double det(int n, double mat[10][10]); +double det(int n, double mat[10][10]) +{ + double submat[10][10]; + if (n == 2) + return ((mat[0][0] * mat[1][1]) - (mat[1][0] * mat[0][1])); + else + { + for (int c = 0; c < n; c++) + { + int subi = 0; //submatrix's i value + for (int i = 1; i < n; i++) + { + int subj = 0; + for (int j = 0; j < n; j++) + { + if (j == c) + continue; + submat[subi][subj] = mat[i][j]; + subj++; + } + subi++; + } + d = d + (pow(-1, c) * mat[0][c] * det(n - 1, submat)); + } + } + return d; +} +int main(int argc, char **argv) +{ + cout << "Enter the number of vectors:\n"; + int n; + cin >> n; + double mat[10][10]; + cout << "Enter the vectors one by one:\n"; + for (int i = 0; i < n; i++) + { + for (int j = 0; j < n; j++) + { + cin >> mat[j][i]; + } + } + d = det(n, mat); + if (d != 0) + cout << "The vectors forms the basis of R" << n + << " as the determinant is non-zero"; + else + cout << "The vectors doesn't form the basis of R" << n + << " as the determinant is zero"; +} + +/* +Enter the number of vectors: +3 +Enter the vectors one by one: +1 2 3 +2 3 4 +3 4 5 +The vectors doesn't form the basis of R3 as the determinant is zero + +Enter the number of vectors: +4 +Enter the vectors one by one: +2 3 5 8 +1 6 2 9 +3 4 2 7 +2 5 3 9 +The vectors forms the basis of R4 as the determinant is non-zero \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Find Closest Pair of Points in an Array.cpp b/c++/11_Numerical_Problems/C++ Program to Find Closest Pair of Points in an Array.cpp new file mode 100644 index 0000000..5f7a36a --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Find Closest Pair of Points in an Array.cpp @@ -0,0 +1,137 @@ +/* + * C++ Program to Find Closest Pair of Points in an Array + */ +#include +#include +#include +#include +using namespace std; + +/* + * Point Declaration + */ +struct Point +{ + int x, y; +}; + +/* + * sort array of points according to X coordinate + */ +int compareX(const void* a, const void* b) +{ + Point *p1 = (Point *)a, *p2 = (Point *)b; + return (p1->x - p2->x); +} +/* + * sort array of points according to Y coordinate + */ +int compareY(const void* a, const void* b) +{ + Point *p1 = (Point *)a, *p2 = (Point *)b; + return (p1->y - p2->y); +} +/* + * find the distance between two points + */ +float dist(Point p1, Point p2) +{ + return sqrt((p1.x - p2.x) * (p1.x - p2.x) + (p1.y - p2.y) * (p1.y - p2.y)); +} +/* + * return the smallest distance between two points + */ +float small_dist(Point P[], int n) +{ + float min = FLT_MAX; + for (int i = 0; i < n; ++i) + { + for (int j = i + 1; j < n; ++j) + { + if (dist(P[i], P[j]) < min) + min = dist(P[i], P[j]); + } + } + return min; +} +/* + * find the distance beween the closest points of strip of given size + */ +float stripClosest(Point strip[], int size, float d) +{ + float min = d; + for (int i = 0; i < size; ++i) + { + for (int j = i + 1; j < size && (strip[j].y - strip[i].y) < min; ++j) + { + if (dist(strip[i],strip[j]) < min) + min = dist(strip[i], strip[j]); + } + } + return min; +} +/* + * find the smallest distance. + */ +float closestUtil(Point Px[], Point Py[], int n) +{ + if (n <= 3) + return small_dist(Px, n); + int mid = n / 2; + Point midPoint = Px[mid]; + Point Pyl[mid + 1]; + Point Pyr[n - mid - 1]; + int li = 0, ri = 0; + for (int i = 0; i < n; i++) + { + if (Py[i].x <= midPoint.x) + Pyl[li++] = Py[i]; + else + Pyr[ri++] = Py[i]; + } + float dl = closestUtil(Px, Pyl, mid); + float dr = closestUtil(Px + mid, Pyr, n-mid); + float d = min(dl, dr); + Point strip[n]; + int j = 0; + for (int i = 0; i < n; i++) + { + if (abs(Py[i].x - midPoint.x) < d) + strip[j] = Py[i], j++; + } + return min(d, stripClosest(strip, j, d)); +} +/* + * finds the smallest distance + */ +float closest(Point P[], int n) +{ + Point Px[n]; + Point Py[n]; + for (int i = 0; i < n; i++) + { + Px[i] = P[i]; + Py[i] = P[i]; + } + qsort(Px, n, sizeof(Point), compareX); + qsort(Py, n, sizeof(Point), compareY); + return closestUtil(Px, Py, n); +} + +/* + * Main + */ +int main() +{ + Point P[] = {{2, 3}, {12, 30}, {40, 50}, {5, 1}, {12, 10}, {3, 4}}; + int n = sizeof(P) / sizeof(P[0]); + cout << "The smallest distance is " << closest(P, n); + return 0; +} + +/* +The smallest distance is 1.41421 + +------------------ +(program exited with code: 1) +Press return to continue \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Find Factoial of Large Numbers.cpp b/c++/11_Numerical_Problems/C++ Program to Find Factoial of Large Numbers.cpp new file mode 100644 index 0000000..1eb4c2f --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Find Factoial of Large Numbers.cpp @@ -0,0 +1,83 @@ +/* + * C++ Program to Find Factorial of Large Numbers + */ +#include +#include +#include +#define ll long long +using namespace std; + +int fact[101][200] = {0}; + +/* + * Find Factorial of Large Numbers + * fact[i][0] is used to store the number of digits + */ +void fact_large(int n) +{ + int i; + fact[1][0] = 1; + fact[1][1] = 1; + if (fact[n][0] == 0) + { + for (i = n - 1; i > 0 ; i--) + { + if (fact[i][0] != 0) + break; + } + for ( ; i < n; i++) + { + int j = 1; + int carry = 0; + int len = fact[i][0]; + while (len--) + { + int temp = (i + 1) * fact[i][j] + carry; + fact[i + 1][j] = temp % 10; + carry = temp / 10; + j++; + } + while (carry > 0) + { + fact[i + 1][j] = carry % 10; + carry /= 10; + j++; + } + fact[i + 1][0] = j - 1; + } + } + for (i = fact[n][0]; i > 0; i--) + { + cout << fact[n][i]; + } + cout<>n; + if (n == 0) + break; + fact_large(n); + } + return 0; +} + +/* +Enter interger to compute factorial(0 to exit): 100 +93326215443944152681699238856266700490715968264381621468592963895217599993229915608941463976156518286253697920827223758251185210916864000000000000000000000000 +Enter interger to compute factorial(0 to exit): 50 +30414093201713378043612608166064768844377641568960512000000000000 +Enter interger to compute factorial(0 to exit): 72 +61234458376886086861524070385274672740778091784697328983823014963978384987221689274204160000000000000000 +Enter interger to compute factorial(0 to exit): 0 + +------------------ +(program exited with code: 1) +Press return to continue \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Find Factoial of a Number using Dynamic Programming.cpp b/c++/11_Numerical_Problems/C++ Program to Find Factoial of a Number using Dynamic Programming.cpp new file mode 100644 index 0000000..546adb9 --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Find Factoial of a Number using Dynamic Programming.cpp @@ -0,0 +1,55 @@ +/* + * C++ Program to Find Factorial of a Number using Dynamic Programming + */ +#include +#include +#include +#define ll long long +using namespace std; + +int result[1000] = {0}; +/* + * Find Factorial of a Number using Dynamic Programming + */ +ll fact_dp(int n) +{ + if (n >= 0) + { + result[0] = 1; + for (int i = 1; i <= n; ++i) + { + result[i] = i * result[i - 1]; + } + return result[n]; + } +} +/* + * Main + */ +int main() +{ + int n; + while (1) + { + cout<<"Enter interger to compute factorial(0 to exit): "; + cin>>n; + if (n == 0) + break; + cout< +#include +#include +#define ll long long +using namespace std; +/* + * Find Factorial of a Number using Iteration + */ +ll fact_iter(int n) +{ + ll result = 1; + for (int i = 1; i <= n; i++) + { + result *= i; + } + return result; +} +/* + * Main + */ +int main() +{ + int n; + while (1) + { + cout<<"Enter interger to compute factorial(0 to exit): "; + cin>>n; + if (n == 0) + break; + cout< +#include +#include +#define ll long long +using namespace std; +/* + * Find Factorial of a Number using Recursion + */ +ll fact_recur(int n) +{ + if (n == 0 || n == 1) + return 1; + else + return n * fact_recur(n - 1); +} +/* + * Main + */ +int main() +{ + int n; + while (1) + { + cout<<"Enter interger to compute factorial(0 to exit): "; + cin>>n; + if (n == 0) + break; + cout< +#include +#include +#define ll long long +using namespace std; + +ll fib[1000] = {0}; +/* + * Fibonacci Numbers using Dp + */ +ll fibo_dp(int n) +{ + fib[1] = 1; + fib[2] = 1; + if (fib[n] == 0) + { + for (int j = 3; j <= n; ++j) + { + if (fib[n] == 0) + fib[j] = fib[j - 1] + fib[j - 2]; + else + continue; + } + } + return fib[n]; +} + +/* + * Main + */ +int main() +{ + int n; + while (1) + { + cout<<"Enter the integer n to find nth fibonnaci no.(0 to exit): "; + cin>>n; + if (n == 0) + break; + cout< +#include +#include +#define ll long long +using namespace std; + +/* + * Iterative function to find Fibonacci Numbers + */ +ll fibo_iter(int n) +{ + int previous = 1; + int current = 1; + int next = 1; + for (int i = 3; i <= n; ++i) + { + next = current + previous; + previous = current; + current = next; + } + return next; +} +/* + * Main + */ +int main() +{ + int n; + while (1) + { + cout<<"Enter the integer n to find nth fibonnaci no.(0 to exit): "; + cin>>n; + if (n == 0) + break; + cout< +#include +#include +#define ll long long +using namespace std; + +/* + * function to multiply two matrices + */ +void multiply(ll F[2][2], ll M[2][2]) +{ + ll x = F[0][0] * M[0][0] + F[0][1] * M[1][0]; + ll y = F[0][0] * M[0][1] + F[0][1] * M[1][1]; + ll z = F[1][0] * M[0][0] + F[1][1] * M[1][0]; + ll w = F[1][0] * M[0][1] + F[1][1] * M[1][1]; + F[0][0] = x; + F[0][1] = y; + F[1][0] = z; + F[1][1] = w; +} + +/* + * function to calculate power of a matrix + */ +void power(ll F[2][2], int n) +{ + if (n == 0 || n == 1) + return; + ll M[2][2] = {{1,1},{1,0}}; + power(F, n / 2); + multiply(F, F); + if (n % 2 != 0) + multiply(F, M); +} + +/* + * function that returns nth Fibonacci number + */ +ll fibo_matrix(ll n) +{ + ll F[2][2] = {{1,1},{1,0}}; + if (n == 0) + return 0; + power(F, n - 1); + return F[0][0]; +} +/* + * Main + */ +int main() +{ + int n; + while (1) + { + cout<<"Enter the integer n to find nth fibonnaci no.(0 to exit): "; + cin>>n; + if (n == 0) + break; + cout< +#include +#include +#define ll long long +using namespace std; + +/* + * Recursive function to find Fibonnaci Numbers + */ +ll fibo_recur(int n) +{ + if (n == 1 || n == 2) + return 1; + else + return fibo_recur(n - 1) + fibo_recur(n - 2);; +} +/* + * Main + */ +int main() +{ + int n; + while (1) + { + cout<<"Enter the integer n to find nth fibonnaci no.(0 to exit): "; + cin>>n; + if (n == 0) + break; + cout< +#include +#include + +using namespace std; +int gcd(int u, int v) +{ + return (v != 0) ? gcd(v, u % v) : u; +} + +int main(void) +{ + int num1, num2, result; + cout << "Enter two numbers to find GCD using Euclidean algorithm: "; + cin >> num1 >> num2; + result = gcd(num1, num2); + if (gcd) + cout << "\nThe GCD of " << num1 << " and " << num2 << " is: " << result + << endl; + else + cout << "\nInvalid input!!!\n"; + return 0; +} + +/* +Enter two numbers to find GCD using Euclidean algorithm: 12 30 +The GCD of 12 and 30 is: 6 \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Find Inverse of a Matrix.cpp b/c++/11_Numerical_Problems/C++ Program to Find Inverse of a Matrix.cpp new file mode 100644 index 0000000..35a02c6 --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Find Inverse of a Matrix.cpp @@ -0,0 +1,565 @@ +#if !defined(MATRIX_H) +#define MATRIX_H +#include +#include +#include +#include +#include +class CMatrix +{ +private: + int m_rows; + int m_cols; + char m_name[128]; + CMatrix(); +public: + double **m_pData; + CMatrix(const char *name, int rows, int cols) : + m_rows(rows), m_cols(cols) + { + strcpy(m_name, name); + m_pData = new double*[m_rows]; + for (int i = 0; i < m_rows; i++) + m_pData[i] = new double[m_cols]; + for (int i = 0; i < m_rows; i++) + { + for (int j = 0; j < m_cols; j++) + { + m_pData[i][j] = 0.0; + } + } + } + CMatrix(const CMatrix &other) + { + strcpy(m_name, other.m_name); + m_rows = other.m_rows; + m_cols = other.m_cols; + m_pData = new double*[m_rows]; + for (int i = 0; i < m_rows; i++) + m_pData[i] = new double[m_cols]; + for (int i = 0; i < m_rows; i++) + { + for (int j = 0; j < m_cols; j++) + { + m_pData[i][j] = other.m_pData[i][j]; + } + } + } + ~CMatrix() + { + for (int i = 0; i < m_rows; i++) + delete[] m_pData[i]; + delete[] m_pData; + m_rows = m_cols = 0; + } + void SetName(const char *name) + { + strcpy(m_name, name); + } + const char* GetName() const + { + return m_name; + } + void GetInput() + { + std::cin >> *this; + } + void FillSimulatedInput() + { + static int factor1 = 1, factor2 = 2; + std::cout << "\n\nEnter Input For Matrix : " << m_name << " Rows: " + << m_rows << " Cols: " << m_cols << "\n"; + for (int i = 0; i < m_rows; i++) + { + for (int j = 0; j < m_cols; j++) + { + std::cout << "Input For Row: " << i + 1 << " Col: " << j + + 1 << " = "; + int data = ((i + 1) * factor1) + (j + 1) * factor2; + m_pData[i][j] = data / 10.2; + std::cout << m_pData[i][j] << "\n"; + factor1 += (rand() % 4); + factor2 += (rand() % 3); + } + std::cout << "\n"; + } + std::cout << "\n"; + } + double Determinant() + { + double det = 0; + double **pd = m_pData; + switch (m_rows) + { + case 2: + { + det = pd[0][0] * pd[1][1] - pd[0][1] * pd[1][0]; + return det; + } + break; + case 3: + { + /*** + a b c + d e f + g h i + + a b c a b c + d e f d e f + g h i g h i + + // det (A) = aei + bfg + cdh - afh - bdi - ceg. + ***/ + double a = pd[0][0]; + double b = pd[0][1]; + double c = pd[0][2]; + double d = pd[1][0]; + double e = pd[1][1]; + double f = pd[1][2]; + double g = pd[2][0]; + double h = pd[2][1]; + double i = pd[2][2]; + double det = (a * e * i + b * f * g + c * d * h); + det = det - a * f * h; + det = det - b * d * i; + det = det - c * e * g; + return det; + } + break; + case 4: + { + CMatrix *temp[4]; + for (int i = 0; i < 4; i++) + temp[i] = new CMatrix("", 3, 3); + for (int k = 0; k < 4; k++) + { + for (int i = 1; i < 4; i++) + { + int j1 = 0; + for (int j = 0; j < 4; j++) + { + if (k == j) + continue; + temp[k]->m_pData[i - 1][j1++] + = this->m_pData[i][j]; + } + } + } + double det = this->m_pData[0][0] * temp[0]->Determinant() + - this->m_pData[0][1] * temp[1]->Determinant() + + this->m_pData[0][2] * temp[2]->Determinant() + - this->m_pData[0][3] * temp[3]->Determinant(); + return det; + } + break; + case 5: + { + CMatrix *temp[5]; + for (int i = 0; i < 5; i++) + temp[i] = new CMatrix("", 4, 4); + for (int k = 0; k < 5; k++) + { + for (int i = 1; i < 5; i++) + { + int j1 = 0; + for (int j = 0; j < 5; j++) + { + if (k == j) + continue; + temp[k]->m_pData[i - 1][j1++] + = this->m_pData[i][j]; + } + } + } + double det = this->m_pData[0][0] * temp[0]->Determinant() + - this->m_pData[0][1] * temp[1]->Determinant() + + this->m_pData[0][2] * temp[2]->Determinant() + - this->m_pData[0][3] * temp[3]->Determinant() + + this->m_pData[0][4] * temp[4]->Determinant(); + return det; + } + case 6: + case 7: + case 8: + case 9: + case 10: + case 11: + case 12: + default: + { + int DIM = m_rows; + CMatrix **temp = new CMatrix*[DIM]; + for (int i = 0; i < DIM; i++) + temp[i] = new CMatrix("", DIM - 1, DIM - 1); + for (int k = 0; k < DIM; k++) + { + for (int i = 1; i < DIM; i++) + { + int j1 = 0; + for (int j = 0; j < DIM; j++) + { + if (k == j) + continue; + temp[k]->m_pData[i - 1][j1++] + = this->m_pData[i][j]; + } + } + } + double det = 0; + for (int k = 0; k < DIM; k++) + { + if ((k % 2) == 0) + det = det + (this->m_pData[0][k] + * temp[k]->Determinant()); + else + det = det - (this->m_pData[0][k] + * temp[k]->Determinant()); + } + for (int i = 0; i < DIM; i++) + delete temp[i]; + delete[] temp; + return det; + } + break; + } + } + CMatrix& operator =(const CMatrix &other) + { + if (this->m_rows != other.m_rows || this->m_cols != other.m_cols) + { + std::cout + << "WARNING: Assignment is taking place with by changing the number of rows and columns of the matrix"; + } + for (int i = 0; i < m_rows; i++) + delete[] m_pData[i]; + delete[] m_pData; + m_rows = m_cols = 0; + strcpy(m_name, other.m_name); + m_rows = other.m_rows; + m_cols = other.m_cols; + m_pData = new double*[m_rows]; + for (int i = 0; i < m_rows; i++) + m_pData[i] = new double[m_cols]; + for (int i = 0; i < m_rows; i++) + { + for (int j = 0; j < m_cols; j++) + { + m_pData[i][j] = other.m_pData[i][j]; + } + } + return *this; + } + CMatrix CoFactor() + { + CMatrix cofactor("COF", m_rows, m_cols); + if (m_rows != m_cols) + return cofactor; + if (m_rows < 2) + return cofactor; + else if (m_rows == 2) + { + cofactor.m_pData[0][0] = m_pData[1][1]; + cofactor.m_pData[0][1] = -m_pData[1][0]; + cofactor.m_pData[1][0] = -m_pData[0][1]; + cofactor.m_pData[1][1] = m_pData[0][0]; + return cofactor; + } + else if (m_rows >= 3) + { + int DIM = m_rows; + CMatrix ***temp = new CMatrix**[DIM]; + for (int i = 0; i < DIM; i++) + temp[i] = new CMatrix*[DIM]; + for (int i = 0; i < DIM; i++) + for (int j = 0; j < DIM; j++) + temp[i][j] = new CMatrix("", DIM - 1, DIM - 1); + for (int k1 = 0; k1 < DIM; k1++) + { + for (int k2 = 0; k2 < DIM; k2++) + { + int i1 = 0; + for (int i = 0; i < DIM; i++) + { + int j1 = 0; + for (int j = 0; j < DIM; j++) + { + if (k1 == i || k2 == j) + continue; + temp[k1][k2]->m_pData[i1][j1++] + = this->m_pData[i][j]; + } + if (k1 != i) + i1++; + } + } + } + bool flagPositive = true; + for (int k1 = 0; k1 < DIM; k1++) + { + flagPositive = ((k1 % 2) == 0); + for (int k2 = 0; k2 < DIM; k2++) + { + if (flagPositive == true) + { + cofactor.m_pData[k1][k2] + = temp[k1][k2]->Determinant(); + flagPositive = false; + } + else + { + cofactor.m_pData[k1][k2] + = -temp[k1][k2]->Determinant(); + flagPositive = true; + } + } + } + for (int i = 0; i < DIM; i++) + for (int j = 0; j < DIM; j++) + delete temp[i][j]; + for (int i = 0; i < DIM; i++) + delete[] temp[i]; + delete[] temp; + } + return cofactor; + } + CMatrix Adjoint() + { + CMatrix cofactor("COF", m_rows, m_cols); + CMatrix adj("ADJ", m_rows, m_cols); + if (m_rows != m_cols) + return adj; + cofactor = this->CoFactor(); + // adjoint is transpose of a cofactor of a matrix + for (int i = 0; i < m_rows; i++) + { + for (int j = 0; j < m_cols; j++) + { + adj.m_pData[j][i] = cofactor.m_pData[i][j]; + } + } + return adj; + } + CMatrix Transpose() + { + CMatrix trans("TR", m_cols, m_rows); + for (int i = 0; i < m_rows; i++) + { + for (int j = 0; j < m_cols; j++) + { + trans.m_pData[j][i] = m_pData[i][j]; + } + } + return trans; + } + CMatrix Inverse() + { + CMatrix cofactor("COF", m_rows, m_cols); + CMatrix inv("INV", m_rows, m_cols); + if (m_rows != m_cols) + return inv; + // to find out Determinant + double det = Determinant(); + cofactor = this->CoFactor(); + // inv = transpose of cofactor / Determinant + for (int i = 0; i < m_rows; i++) + { + for (int j = 0; j < m_cols; j++) + { + inv.m_pData[j][i] = cofactor.m_pData[i][j] / det; + } + } + return inv; + } + CMatrix operator +(const CMatrix &other) + { + if (this->m_rows != other.m_rows || this->m_cols != other.m_cols) + { + std::cout + << "Addition could not take place because number of rows and columns are different between the two matrices"; + return *this; + } + CMatrix result("", m_rows, m_cols); + for (int i = 0; i < m_rows; i++) + { + for (int j = 0; j < m_cols; j++) + { + result.m_pData[i][j] = this->m_pData[i][j] + + other.m_pData[i][j]; + } + } + return result; + } + CMatrix operator -(const CMatrix &other) + { + if (this->m_rows != other.m_rows || this->m_cols != other.m_cols) + { + std::cout + << "Subtraction could not take place because number of rows and columns are different between the two matrices"; + return *this; + } + CMatrix result("", m_rows, m_cols); + for (int i = 0; i < m_rows; i++) + { + for (int j = 0; j < m_cols; j++) + { + result.m_pData[i][j] = this->m_pData[i][j] + - other.m_pData[i][j]; + } + } + return result; + } + CMatrix operator *(const CMatrix &other) + { + if (this->m_cols != other.m_rows) + { + std::cout + << "Multiplication could not take place because number of columns of 1st Matrix and number of rows in 2nd Matrix are different"; + return *this; + } + CMatrix result("", this->m_rows, other.m_cols); + for (int i = 0; i < this->m_rows; i++) + { + for (int j = 0; j < other.m_cols; j++) + { + for (int k = 0; k < this->m_cols; k++) + { + result.m_pData[i][j] += this->m_pData[i][k] + * other.m_pData[k][j]; + } + } + } + return result; + } + bool operator ==(const CMatrix &other) + { + if (this->m_rows != other.m_rows || this->m_cols != other.m_cols) + { + std::cout + << "Comparision could not take place because number of rows and columns are different between the two matrices"; + return false; + } + CMatrix result("", m_rows, m_cols); + bool bEqual = true; + for (int i = 0; i < m_rows; i++) + { + for (int j = 0; j < m_cols; j++) + { + if (this->m_pData[i][j] != other.m_pData[i][j]) + bEqual = false; + } + } + return bEqual; + } + friend std::istream& operator >>(std::istream &is, CMatrix &m); + friend std::ostream& operator <<(std::ostream &os, const CMatrix &m); +}; +std::istream& operator >>(std::istream &is, CMatrix &m) +{ + std::cout << "\n\nEnter Input For Matrix : " << m.m_name << " Rows: " + << m.m_rows << " Cols: " << m.m_cols << "\n"; + for (int i = 0; i < m.m_rows; i++) + { + for (int j = 0; j < m.m_cols; j++) + { + std::cout << "Input For Row: " << i + 1 << " Col: " << j + 1 + << " = "; + is >> m.m_pData[i][j]; + } + std::cout << "\n"; + } + std::cout << "\n"; + return is; +} +std::ostream& operator <<(std::ostream &os, const CMatrix &m) +{ + os << "\n\nMatrix : " << m.m_name << " Rows: " << m.m_rows << " Cols: " + << m.m_cols << "\n\n"; + for (int i = 0; i < m.m_rows; i++) + { + os << " | "; + for (int j = 0; j < m.m_cols; j++) + { + char buf[32]; + double data = m.m_pData[i][j]; + if (m.m_pData[i][j] > -0.00001 && m.m_pData[i][j] < 0.00001) + data = 0; + sprintf(buf, "%10.2lf ", data); + os << buf; + } + os << "|\n"; + } + os << "\n\n"; + return os; +} +#endif +int main() +{ + CMatrix a("A", 5, 5); + //std::cin >> a; + a.FillSimulatedInput(); + CMatrix aadj = a.Inverse(); + std::cout << a; + std::cout << aadj; + CMatrix unit = (a * aadj); + unit.SetName("A * A-Inv"); + std::cout << unit; +} + +/* + +Enter Input For Matrix : +A Rows: 5 +Cols: 5 +Input For Row: 1 Col: 1 = 0.294118 +Input For Row: 1 Col: 2 = 0.980392 +Input For Row: 1 Col: 3 = 1.86275 +Input For Row: 1 Col: 4 = 2.84314 +Input For Row: 1 Col: 5 = 3.62745 + +Input For Row: 2 Col: 1 = 2.54902 +Input For Row: 2 Col: 2 = 3.92157 +Input For Row: 2 Col: 3 = 5.09804 +Input For Row: 2 Col: 4 = 7.05882 +Input For Row: 2 Col: 5 = 9.80392 + +Input For Row: 3 Col: 1 = 6.66667 +Input For Row: 3 Col: 2 = 8.92157 +Input For Row: 3 Col: 3 = 10.8824 +Input For Row: 3 Col: 4 = 12.6471 +Input For Row: 3 Col: 5 = 15.3922 + +Input For Row: 4 Col: 1 = 12.0588 +Input For Row: 4 Col: 2 = 15.098 +Input For Row: 4 Col: 3 = 18.1373 +Input For Row: 4 Col: 4 = 20.7843 +Input For Row: 4 Col: 5 = 24.4118 + +Input For Row: 5 Col: 1 = 21.1765 +Input For Row: 5 Col: 2 = 24.7059 +Input For Row: 5 Col: 3 = 27.7451 +Input For Row: 5 Col: 4 = 31.0784 +Input For Row: 5 Col: 5 = 34.3137 + +Matrix : A Rows: 5 Cols: 5 + + | 0.29 0.98 1.86 2.84 3.63 | + | 2.55 3.92 5.10 7.06 9.80 | + | 6.67 8.92 10.88 12.65 15.39 | + | 12.06 15.10 18.14 20.78 24.41 | + | 21.18 24.71 27.75 31.08 34.31 | + +Matrix : INV Rows: 5 Cols: 5 + + | -0.93 0.80 -3.74 2.86 -0.49 | + | 0.37 -0.32 5.35 -4.91 1.14 | + | -0.78 -0.93 -1.46 2.96 -1.10 | + | 2.37 -0.10 0.25 -1.65 0.84 | + | -1.21 0.57 -0.58 0.87 -0.36 | + +Matrix : A * A-Inv Rows: 5 Cols: 5 + + | 1.00 0.00 0.00 0.00 0.00 | + | 0.00 1.00 0.00 0.00 0.00 | + | 0.00 0.00 1.00 0.00 0.00 | + | 0.00 0.00 0.00 1.00 0.00 | + | 0.00 0.00 0.00 0.00 1.00 | \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Find Path Between Two Nodes in a Graph.cpp b/c++/11_Numerical_Problems/C++ Program to Find Path Between Two Nodes in a Graph.cpp new file mode 100644 index 0000000..9808b2a --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Find Path Between Two Nodes in a Graph.cpp @@ -0,0 +1,109 @@ +#include +#include + +using namespace std; + +// This class represents a directed graph using adjacency list representation +class Graph +{ + int V; // No. of vertices + list *adj; // Pointer to an array containing adjacency lists +public: + Graph(int V); // Constructor + void addEdge(int v, int w); // function to add an edge to graph + bool isReachable(int s, int d); // returns true if there is a path from s to d +}; + +Graph::Graph(int V) +{ + this->V = V; + adj = new list [V]; +} + +void Graph::addEdge(int v, int w) +{ + adj[v].push_back(w); // Add w to v’s list. +} + +// A BFS based function to check whether d is reachable from s. +bool Graph::isReachable(int s, int d) +{ + // Base case + if (s == d) + return true; + // Mark all the vertices as not visited + bool *visited = new bool[V]; + for (int i = 0; i < V; i++) + visited[i] = false; + // Create a queue for BFS + list queue; + // Mark the current node as visited and enqueue it + visited[s] = true; + queue.push_back(s); + // it will be used to get all adjacent vertices of a vertex + list::iterator i; + while (!queue.empty()) + { + // Dequeue a vertex from queue and print it + s = queue.front(); + queue.pop_front(); + // Get all adjacent vertices of the dequeued vertex s + // If a adjacent has not been visited, then mark it visited + // and enqueue it + for (i = adj[s].begin(); i != adj[s].end(); ++i) + { + // If this adjacent node is the destination node, then return true + if (*i == d) + return true; + // Else, continue to do BFS + if (!visited[*i]) + { + visited[*i] = true; + queue.push_back(*i); + } + } + } + return false; +} + +// Driver program to test methods of graph class +int main() +{ + // Create a graph given in the above diagram + Graph g(4); + g.addEdge(0, 1); + g.addEdge(0, 2); + g.addEdge(1, 2); + g.addEdge(2, 0); + g.addEdge(2, 3); + g.addEdge(3, 3); + cout << "Enter the source and destination vertices: (0-3)"; + int u, v; + cin >> u >> v; + if (g.isReachable(u, v)) + cout << "\nThere is a path from " << u << " to " << v; + else + cout << "\nThere is no path from " << u << " to " << v; + int temp; + temp = u; + u = v; + v = temp; + if (g.isReachable(u, v)) + cout << "\nThere is a path from " << u << " to " << v; + else + cout << "\nThere is no path from " << u << " to " << v; + return 0; +} + +/* +Enter the source and destination vertices: (0-3) +1 3 + +There is a path from 1 to 3 +There is no path from 3 to 1 + +Enter the source and destination vertices: (0-3) +2 3 + +There is a path from 2 to 3 +There is no path from 3 to 2 \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Find the GCD and LCM of n Numbers.cpp b/c++/11_Numerical_Problems/C++ Program to Find the GCD and LCM of n Numbers.cpp new file mode 100644 index 0000000..6d40571 --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Find the GCD and LCM of n Numbers.cpp @@ -0,0 +1,57 @@ +#include +#include +#include + +using namespace std; + +int gcd(int x, int y) +{ + int r = 0, a, b; + a = (x > y) ? x : y; // a is greater number + b = (x < y) ? x : y; // b is smaller number + r = b; + while (a % b != 0) + { + r = a % b; + a = b; + b = r; + } + return r; +} + +int lcm(int x, int y) +{ + int a; + a = (x > y) ? x : y; // a is greater number + while (true) + { + if (a % x == 0 && a % y == 0) + return a; + ++a; + } +} + +int main(int argc, char **argv) +{ + cout << "Enter the two numbers: "; + int x, y; + cin >> x >> y; + cout << "The GCD of two numbers is: " << gcd(x, y) << endl; + ; + cout << "The LCM of two numbers is: " << lcm(x, y) << endl; + ; + return 0; +} + +/* +Enter the two numbers: +5 +8 +The GCD of two numbers is: 1 +The LCM of two numbers is: 40 + +Enter the two numbers: +100 +50 +The GCD of two numbers is: 50 +The LCM of two numbers is: 100 \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Generate N Number of Passwords of Length M Each.cpp b/c++/11_Numerical_Problems/C++ Program to Generate N Number of Passwords of Length M Each.cpp new file mode 100644 index 0000000..7dafe6f --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Generate N Number of Passwords of Length M Each.cpp @@ -0,0 +1,179 @@ +#include +#include +#include + +using namespace std; + +void permute(int *a, int k, int size) +{ + if (k == size) + { + for (int i = 0; i < size; i++) + { + cout << *(a + i); + } + cout << endl; + } + else + { + for (int i = k; i < size; i++) + { + int temp = a[k]; + a[k] = a[i]; + a[i] = temp; + permute(a, k + 1, size); + temp = a[k]; + a[k] = a[i]; + a[i] = temp; + } + } +} +int main(int argc, char **argv) +{ + cout << "Enter the length of the password: "; + int m; + cin >> m; + int a[m]; + for (int i = 0; i < m; i++) + { + /*generates random number between 1 and 10*/ + a[i] = rand() % 10; + } + for (int i = 0; i < m; i++) + { + cout << a[i] << ", "; + } + cout << "The Passwords are: "; + permute(a, 0, m); +} + +/* +Enter the length of the password: 3 +1, 7, 4, The Passwords are: 174 +147 +714 +741 +471 +417 + +Enter the length of the password: 5 +1, 7, 4, 0, 9, The Passwords are: 17409 +17490 +17049 +17094 +17904 +17940 +14709 +14790 +14079 +14097 +14907 +14970 +10479 +10497 +10749 +10794 +10974 +10947 +19407 +19470 +19047 +19074 +19704 +19740 +71409 +71490 +71049 +71094 +71904 +71940 +74109 +74190 +74019 +74091 +74901 +74910 +70419 +70491 +70149 +70194 +70914 +70941 +79401 +79410 +79041 +79014 +79104 +79140 +47109 +47190 +47019 +47091 +47901 +47910 +41709 +41790 +41079 +41097 +41907 +41970 +40179 +40197 +40719 +40791 +40971 +40917 +49107 +49170 +49017 +49071 +49701 +49710 +07419 +07491 +07149 +07194 +07914 +07941 +04719 +04791 +04179 +04197 +04917 +04971 +01479 +01497 +01749 +01794 +01974 +01947 +09417 +09471 +09147 +09174 +09714 +09741 +97401 +97410 +97041 +97014 +97104 +97140 +94701 +94710 +94071 +94017 +94107 +94170 +90471 +90417 +90741 +90714 +90174 +90147 +91407 +91470 +91047 +91074 +91704 +91740 \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Generate Prime Numbers Between a Given Range Using the Sieve of Sundaram.cpp b/c++/11_Numerical_Problems/C++ Program to Generate Prime Numbers Between a Given Range Using the Sieve of Sundaram.cpp new file mode 100644 index 0000000..b1658ac --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Generate Prime Numbers Between a Given Range Using the Sieve of Sundaram.cpp @@ -0,0 +1,72 @@ +#include + +using namespace std; + +int main() +{ + cout << "Welcome to the Sieve of Sundaram\n" << endl; + int arraySize; + int numberPrimes = 0; + cout << "Input a positive integer to find all the prime numbers up to and " + << "\nincluding that number: "; + cin >> arraySize; + int n = arraySize / 2; + /* array to start off with that will eventually get + all the composite numbers removed and the remaining + ones output to the screen */ + int isPrime[arraySize + 1]; + for (int i = 0; i < n; ++i) + { + isPrime[i] = i; + } + for (int i = 1; i < n; i++) + { + for (int j = i; j <= (n - i) / (2 * i + 1); j++) + { + isPrime[i + j + 2 * i * j] = 0;/*From this list, remove all + numbers of the form i + j + 2ij */ + } + } + int TheseArePrime = 0; + if (arraySize > 2) + { + isPrime[TheseArePrime++] = 2;/*this IF statement adds 2 to the output */ + } + for (int i = 1; i < n; i++) + { + if (isPrime[i] != 0) + { + isPrime[TheseArePrime++] = i * 2 + 1; + } + } + int size = sizeof isPrime / sizeof(int);//total size of array/size of array data type + for (int x = 0; x <= size; x++) + { + if (isPrime[x] != 0) + { + cout << isPrime[x] << "\t";//outputs all prime numbers found + numberPrimes++;// the counter of the number of primes found + } + else + { + break; + } + } + cout << "\nNumber of Primes: " << numberPrimes << endl; + return 0; +} + +/* +Welcome to the Sieve of Sundaram + +Input a positive integer to find all the prime numbers up to and +including that number: 10 +2 3 5 7 +Number of Primes: 4 + +Welcome to the Sieve of Sundaram + +Input a positive integer to find all the prime numbers up to and +including that number: 100 +2 3 5 7 11 13 17 19 23 29 31 37 41 43 47 53 59 61 67 71 73 79 83 89 97 +Number of Primes: 25 \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Generate Random Hexadecimal Bytes.cpp b/c++/11_Numerical_Problems/C++ Program to Generate Random Hexadecimal Bytes.cpp new file mode 100644 index 0000000..3e5d8fe --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Generate Random Hexadecimal Bytes.cpp @@ -0,0 +1,18 @@ +#include +#include +#include + +using namespace std; + +int main(int argc, char **argv) +{ + int val = rand(); + char Hex[33]; + itoa(val, Hex, 16); + cout<< "Random Decimal Byte:" << val; + cout << "\nEquivalent Hex Byte: " << Hex; +} + +/* +Random Decimal Byte:41 +Equivalent Hex Byte: 29 \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Generate Random Numbers Using Middle Square Method.cpp b/c++/11_Numerical_Problems/C++ Program to Generate Random Numbers Using Middle Square Method.cpp new file mode 100644 index 0000000..7c86fb8 --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Generate Random Numbers Using Middle Square Method.cpp @@ -0,0 +1,45 @@ +/*This is a C++ Program to generate random numbers using Middle Square method. In mathematics, the middle-square method is a method of generating pseudorandom numbers. In practice it is not a good method, since its period is usually very short and it has some severe weaknesses, such as the output sequence almost always converging to zero.*/ + +#include +#include +#include + +using namespace std; + +int a[] = { 1, 10, 100, 1000, 10000, 100000, 1000000, 10000000, 100000000 }; +int middleSquareNumber(int numb, int dig) +{ + int sqn = numb * numb, next_num = 0; + int trim = (dig / 2); + sqn = sqn / a[trim]; + for (int i = 0; i < dig; i++) + { + next_num += (sqn % (a[trim])) * (a[i]); + sqn = sqn / 10; + } + return next_num; +} + +int main(int argc, char **argv) +{ + cout << "Enter the #-digit random numbers you want: "; + int n; + cin >> n; + int start = 1, end = 1; + start = a[n - 1]; + end = a[n]; + int number = ((rand()) % (end - start)) + start; + cout << "The random numbers are:\n" << number << ", "; + for (int i = 1; i < n; i++) + { + number = middleSquareNumber(number, n); + cout << number << ", "; + } + cout << "..."; +} + +/* + +Enter the #-digit random numbers you want: 5 +The random numbers are: +10041, 16426, 796264, -276041, -115546, ... \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Generate Random Numbers Using Multiply with Carry Method.cpp b/c++/11_Numerical_Problems/C++ Program to Generate Random Numbers Using Multiply with Carry Method.cpp new file mode 100644 index 0000000..e343a7f --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Generate Random Numbers Using Multiply with Carry Method.cpp @@ -0,0 +1,31 @@ +/*This is a C++ Program to generate random numbers using Multiply with Carry method. In computer science, multiply-with-carry (MWC) is a method invented by George Marsaglia for generating sequences of random integers based on an initial set from two to many thousands of randomly chosen seed values. The main advantages of the MWC method are that it invokes simple computer integer arithmetic and leads to very fast generation of sequences of random numbers with immense periods, ranging from around 260 to 22000000.*/ + +#include +#include +#include + +using namespace std; + +int main(int argc, char **argv) +{ + int max_Sequence_Elements = 10; + int base_b = 2000; + int multiplier_a = rand() % base_b; + int r = 1; + int c[max_Sequence_Elements]; + int x[max_Sequence_Elements]; + c[0] = rand() % multiplier_a; + x[0] = rand() % base_b; + cout << "The random number sequence is: " << x[0]; + //generating sequence + for (int i = 1; i < max_Sequence_Elements; i++) + { + x[i] = (multiplier_a * x[i - r] + c[i - 1]) % base_b; + c[i] = (multiplier_a * x[i - r] + c[i - 1]) / base_b; + cout << " " << x[i]; + } + cout << "..."; +} + +/* +The random number sequence is: 334 1711 157 472 1355 1564 151 223 1146 990... \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Generate Random Numbers Using Probability Distribution Function.cpp b/c++/11_Numerical_Problems/C++ Program to Generate Random Numbers Using Probability Distribution Function.cpp new file mode 100644 index 0000000..c26e7ba --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Generate Random Numbers Using Probability Distribution Function.cpp @@ -0,0 +1,34 @@ +/*This is a C++ Program to generate random numbers using Probability Distribution Function. Probability distribution is based on probability density function. a probability density function (pdf), or density of a continuous random variable, is a function that describes the relative likelihood for this random variable to take on a given value. The probability of the random variable falling within a particular range of values is given by the integral of this variable’s density over that range—that is, it is given by the area under the density function but above the horizontal axis and between the lowest and greatest values of the range.*/ + +//pdf(x) = 1 if x>360 +// = 0 if x<0 +// = x/360 otherwise +#include +#include +#include + +using namespace std; + +//This is a sample program to generate a random numbers based on probability desity function of spiner +//pdf(x) = 1 if x>360 +// = 0 if x<0 +// = x/360 otherwise +int N = 10; +int main(int argc, char **argv) +{ + int p = 0; + for (int i = 0; i < N; i++) + { + p = rand() % 400; + if (p > 360) + cout << 0 << " "; + else if (p < 0) + cout << 0 << " "; + else + cout << p * 0.1 / 360 << " "; + } + cout << "..."; +} + +/* +0.0113889 0.0186111 0.0927778 0.0277778 0 0.0344444 0.0772222 0.0438889 0.045 0.0177778 ... \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Generate Randomized Sequence of Given Range of Numbers.cpp b/c++/11_Numerical_Problems/C++ Program to Generate Randomized Sequence of Given Range of Numbers.cpp new file mode 100644 index 0000000..8d9a98c --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Generate Randomized Sequence of Given Range of Numbers.cpp @@ -0,0 +1,26 @@ +#include +#include +#include + +const int LOW = 1; +const int HIGH = 32000; + +using namespace std; + +int main() +{ + int randomNumber; + time_t seconds; + time(&seconds); + srand((unsigned int) seconds); + for (int i = 0; i < 10; i++) + { + randomNumber = rand() % (HIGH - LOW + 1) + LOW; + cout << randomNumber << " "; + } + cout << "..."; + return 0; +} + +/* +312 7423 23444 16008 31816 1823 29315 17424 11753 18384 ... \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Implement Booth’s Multiplication Algorithm for Multiplication of 2 signed Numbers.cpp b/c++/11_Numerical_Problems/C++ Program to Implement Booth’s Multiplication Algorithm for Multiplication of 2 signed Numbers.cpp new file mode 100644 index 0000000..a80bf8a --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Implement Booth’s Multiplication Algorithm for Multiplication of 2 signed Numbers.cpp @@ -0,0 +1,141 @@ +/*This is a C++ Program to multiply two signed numbers using booth’s algorithm. Booth’s multiplication algorithm is a multiplication algorithm that multiplies two signed binary numbers in two’s complement notation. Booth used desk calculators that were faster at shifting than adding and created the algorithm to increase their speed. Booth’s algorithm is of interest in the study of computer architecture.*/ + +#include +#include + +using namespace std; + +void add(int a[], int x[], int qrn); +void complement(int a[], int n) +{ + int i; + int x[8] = { NULL }; + x[0] = 1; + for (i = 0; i < n; i++) + { + a[i] = (a[i] + 1) % 2; + } + add(a, x, n); +} + +void add(int ac[], int x[], int qrn) +{ + int i, c = 0; + for (i = 0; i < qrn; i++) + { + ac[i] = ac[i] + x[i] + c; + if (ac[i] > 1) + { + ac[i] = ac[i] % 2; + c = 1; + } + else + c = 0; + } +} + +void ashr(int ac[], int qr[], int &qn, int qrn) +{ + int temp, i; + temp = ac[0]; + qn = qr[0]; + cout << "\t\tashr\t\t"; + for (i = 0; i < qrn - 1; i++) + { + ac[i] = ac[i + 1]; + qr[i] = qr[i + 1]; + } + qr[qrn - 1] = temp; +} + +void display(int ac[], int qr[], int qrn) +{ + int i; + for (i = qrn - 1; i >= 0; i--) + cout << ac[i]; + cout << " "; + for (i = qrn - 1; i >= 0; i--) + cout << qr[i]; +} + +int main(int argc, char **argv) +{ + int mt[10], br[10], qr[10], sc, ac[10] = { 0 }; + int brn, qrn, i, qn, temp; + cout + << "\n--Enter the multiplicand and multipier in signed 2's complement form if negative--"; + cout << "\n Number of multiplicand bit="; + cin >> brn; + cout << "\nmultiplicand="; + for (i = brn - 1; i >= 0; i--) + cin >> br[i]; //multiplicand + for (i = brn - 1; i >= 0; i--) + mt[i] = br[i]; // copy multipier to temp array mt[] + complement(mt, brn); + cout << "\nNo. of multiplier bit="; + cin >> qrn; + sc = qrn; //sequence counter + cout << "Multiplier="; + for (i = qrn - 1; i >= 0; i--) + cin >> qr[i]; //multiplier + qn = 0; + temp = 0; + cout << "qn\tq[n+1]\t\tBR\t\tAC\tQR\t\tsc\n"; + cout << "\t\t\tinitial\t\t"; + display(ac, qr, qrn); + cout << "\t\t" << sc << "\n"; + while (sc != 0) + { + cout << qr[0] << "\t" << qn; + if ((qn + qr[0]) == 1) + { + if (temp == 0) + { + add(ac, mt, qrn); + cout << "\t\tsubtracting BR\t"; + for (i = qrn - 1; i >= 0; i--) + cout << ac[i]; + temp = 1; + } + else if (temp == 1) + { + add(ac, br, qrn); + cout << "\t\tadding BR\t"; + for (i = qrn - 1; i >= 0; i--) + cout << ac[i]; + temp = 0; + } + cout << "\n\t"; + ashr(ac, qr, qn, qrn); + } + else if (qn - qr[0] == 0) + ashr(ac, qr, qn, qrn); + display(ac, qr, qrn); + cout << "\t"; + sc--; + cout << "\t" << sc << "\n"; + } + cout << "Result="; + display(ac, qr, qrn); +} + +/* +--Enter the multiplicand and multipier in signed 2's complement form if negative-- +Number of multiplicand bit=5 +Multiplicand=1 0 1 1 1 + +Number of multiplier bit=5 +Multiplier=1 0 0 1 1 + +qn q[n+1] BR AC QR sc + initial 00000 10011 5 +1 0 subtracting BR 01001 + ashr 00100 11001 4 +1 1 ashr 00010 01100 3 +0 1 adding BR 11001 + ashr 11100 10110 2 +0 0 ashr 11110 01011 1 +1 0 subtracting BR 00111 + ashr 00011 10101 0 + +Result=00011 10101 \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Implement Coppersmith Freivald’s Algorithm.cpp b/c++/11_Numerical_Problems/C++ Program to Implement Coppersmith Freivald’s Algorithm.cpp new file mode 100644 index 0000000..b5fe347 --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Implement Coppersmith Freivald’s Algorithm.cpp @@ -0,0 +1,129 @@ +#include +#include +#include + +using namespace std; + +int main(int argc, char **argv) +{ + cout << "Enter the dimension of the matrices: "; + int n; + cin >> n; + cout << "Enter the 1st matrix: "; + double a[n][n]; + for (int i = 0; i < n; i++) + { + for (int j = 0; j < n; j++) + { + cin >> a[i][j]; + } + } + cout << "Enter the 2nd matrix: "; + double b[n][n]; + for (int i = 0; i < n; i++) + { + for (int j = 0; j < n; j++) + { + cin >> b[i][j]; + } + } + cout << "Enter the result matrix: "; + double c[n][n]; + for (int i = 0; i < n; i++) + { + for (int j = 0; j < n; j++) + { + cin >> c[i][j]; + } + } + //random generation of the r vector containing only 0/1 as its elements + double r[n][1]; + for (int i = 0; i < n; i++) + { + r[i][0] = rand() % 2; + cout << r[i][0] << " "; + } + //test A * (b*r) - (C*) = 0 + double br[n][1]; + for (int i = 0; i < n; i++) + { + for (int j = 0; j < 1; j++) + { + for (int k = 0; k < n; k++) + { + br[i][j] = br[i][j] + b[i][k] * r[k][j]; + } + } + } + double cr[n][1]; + for (int i = 0; i < n; i++) + { + for (int j = 0; j < 1; j++) + { + for (int k = 0; k < n; k++) + { + cr[i][j] = cr[i][j] + c[i][k] * r[k][j]; + } + } + } + double abr[n][1]; + for (int i = 0; i < n; i++) + { + for (int j = 0; j < 1; j++) + { + for (int k = 0; k < n; k++) + { + abr[i][j] = abr[i][j] + a[i][k] * br[k][j]; + } + } + } + // br = multiplyVector(b, r, n); + // cr = multiplyVector(c, r, n); + // abr = multiplyVector(a, br, n); + //abr-cr + for (int i = 0; i < n; i++) + { + abr[i][0] -= cr[i][0]; + } + bool flag = true; + for (int i = 0; i < n; i++) + { + if (abr[i][0] == 0) + continue; + else + flag = false; + } + if (flag == true) + cout << "Yes"; + else + cout << "No"; +} + +/* + +Enter the dimension of the matrices: 2 +Enter the 1st matrix: +1 2 +2 3 +Enter the 2nd matrix: +1 3 +3 4 +Enter the result matrix: +9 9 +14 15 + +Yes + +Enter the dimesion of the matrices: +2 +Enter the 1st matrix: +2 3 +3 4 +Enter the 2st matrix: +1 0 +1 2 +Enter the result matrix: +6 5 +8 7 + +Yes \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Implement Euler Theorem.cpp b/c++/11_Numerical_Problems/C++ Program to Implement Euler Theorem.cpp new file mode 100644 index 0000000..a9d5d16 --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Implement Euler Theorem.cpp @@ -0,0 +1,37 @@ +/* + * C++ Program to Implement Euler Theorem + */ +#include +#include +using namespace std; + +vector inverseArray(int n, int m) +{ + vector modInverse(n + 1, 0); + modInverse[1] = 1; + for (int i = 2; i <= n; i++) + { + modInverse[i] = (-(m / i) * modInverse[m % i]) % m + m; + } + return modInverse; +} +//Main +int main() +{ + vector::iterator it; + int a, m; + cout<<"Enter number to find modular multiplicative inverse: "; + cin>>a; + cout<<"Enter Modular Value: "; + cin>>m; + cout< +#include + +using namespace std; +/* return the gcd of a and b followed by the pair x and y of + equation ax + by = gcd(a,b) +*/ +pair > extendedEuclid(int a, int b) +{ + int x = 1, y = 0; + int xLast = 0, yLast = 1; + int q, r, m, n; + while (a != 0) + { + q = b / a; + r = b % a; + m = xLast - q * x; + n = yLast - q * y; + xLast = x; + yLast = y; + x = m; + y = n; + b = a; + a = r; + } + return make_pair(b, make_pair(xLast, yLast)); +} + +int modInverse(int a, int m) +{ + return (extendedEuclid(a, m).second.first + m) % m; +} + +//Main +int main() +{ + int a, m; + cout<<"Enter number to find modular multiplicative inverse: "; + cin>>a; + cout<<"Enter Modular Value: "; + cin>>m; + cout< +#include +#include +#define ll long long +using namespace std; +/* + * modular exponentiation + */ +ll modulo(ll base, ll exponent, ll mod) +{ + ll x = 1; + ll y = base; + while (exponent > 0) + { + if (exponent % 2 == 1) + x = (x * y) % mod; + y = (y * y) % mod; + exponent = exponent / 2; + } + return x % mod; +} + +/* + * Fermat's test for checking primality + */ +bool Fermat(ll p, int iterations) +{ + if (p == 1) + { + return false; + } + for (int i = 0; i < iterations; i++) + { + ll a = rand() % (p - 1) + 1; + if (modulo(a, p - 1, p) != 1) + { + return false; + } + } + return true; +} +/* + * Main + */ +int main() +{ + int iteration = 50; + ll num; + cout<<"Enter integer to test primality: "; + cin>>num; + if (Fermat(num, iteration)) + cout< +using namespace std; + +/* calculates (a^b)%MOD */ +int pow(int a, int b, int MOD) +{ + int x = 1, y = a; + while (b > 0) + { + if (b % 2 == 1) + { + x = (x * y); + if (x > MOD) + x %= MOD; + } + y = (y * y); + if (y > MOD) + y %= MOD; + b /= 2; + } + return x; +} + +int modInverse(int a, int m) +{ + return pow(a, m - 2, m); +} +//Main +int main() +{ + int a, m; + cout<<"Enter number to find modular multiplicative inverse: "; + cin>>a; + cout<<"Enter Modular Value: "; + cin>>m; + cout< +#include + +using namespace std; + +void fisherYatesShuffling(int *arr, int n) +{ + int a[n]; + int ind[n]; + for (int i = 0; i < n; i++) + ind[i] = 0; + int index; + for (int i = 0; i < n; i++) + { + do + { + index = rand() % n; + } + while (ind[index] != 0); + ind[index] = 1; + a[i] = *(arr + index); + } + for (int i = 0; i < n; i++) + { + cout << a[i] << " "; + } +} + +int main(int argc, char **argv) +{ + cout << "Enter the array size: "; + int n; + cin >> n; + cout << "Enter the array elements: "; + int a[n]; + for (int i = 0; i < n; i++) + { + cin >> a[i]; + } + fisherYatesShuffling(a, n); +} + +/* +Enter the array size: 7 +Enter the array elements: 12 23 34 45 56 67 78 +78 23 67 45 34 12 56 \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Implement Gauss Seidel Method.cpp b/c++/11_Numerical_Problems/C++ Program to Implement Gauss Seidel Method.cpp new file mode 100644 index 0000000..8ca7766 --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Implement Gauss Seidel Method.cpp @@ -0,0 +1,80 @@ +#include +#include + +using namespace std; + +int main(void) +{ + float a[10][10], b[10], x[10], y[10]; + int n = 0, m = 0, i = 0, j = 0; + cout << "Enter size of 2d array(Square matrix) : "; + cin >> n; + for (i = 0; i < n; i++) + { + for (j = 0; j < n; j++) + { + cout << "Enter values no :(" << i << ", " << j << ") "; + cin >> a[i][j]; + } + } + cout << "\nEnter Values to the right side of equation\n"; + for (i = 0; i < n; i++) + { + cout << "Enter values no :(" << i << ", " << j << ") "; + cin >> b[i]; + } + cout << "Enter initial values of x\n"; + for (i = 0; i < n; i++) + { + cout << "Enter values no. :(" << i<<"):"; + cin >> x[i]; + } + cout << "\nEnter the no. of iteration : "; + cin >> m; + while (m > 0) + { + for (i = 0; i < n; i++) + { + y[i] = (b[i] / a[i][i]); + for (j = 0; j < n; j++) + { + if (j == i) + continue; + y[i] = y[i] - ((a[i][j] / a[i][i]) * x[j]); + x[i] = y[i]; + } + printf("x%d = %f ", i + 1, y[i]); + } + cout << "\n"; + m--; + } + return 0; +} + +/* +Enter size of 2d array(Square matrix) : 3 +Enter values no :(0, 0) 2 +Enter values no :(0, 1) 3 +Enter values no :(0, 2) 1 +Enter values no :(1, 0) 5 +Enter values no :(1, 1) 4 +Enter values no :(1, 2) 6 +Enter values no :(2, 0) 8 +Enter values no :(2, 1) 7 +Enter values no :(2, 2) 9 + +Enter Values to the right side of equation +Enter values no :(0, 3) 2 +Enter values no :(1, 3) 3 +Enter values no :(2, 3) 4 + +Enter initial values of x +Enter values no. :(0): 0 +Enter values no. :(1): 0 +Enter values no. :(2): 0 + +Enter the no. of iteration : 4 +x1 = 1.000000 x2 = -0.500000 x3 = -0.055556 +x1 = 1.777778 x2 = -1.388889 x3 = -0.055556 +x1 = 3.111111 x2 = -3.055555 x3 = 0.055555 +x1 = 5.555555 x2 = -6.277777 x3 = 0.388889 \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Implement Miller Rabin Primality Test.cpp b/c++/11_Numerical_Problems/C++ Program to Implement Miller Rabin Primality Test.cpp new file mode 100644 index 0000000..c361a53 --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Implement Miller Rabin Primality Test.cpp @@ -0,0 +1,98 @@ +/* + * C++ Program to Implement Miller Rabin Primality Test + */ +#include +#include +#include +#define ll long long +using namespace std; + +/* + * calculates (a * b) % c taking into account that a * b might overflow + */ +ll mulmod(ll a, ll b, ll mod) +{ + ll x = 0,y = a % mod; + while (b > 0) + { + if (b % 2 == 1) + { + x = (x + y) % mod; + } + y = (y * 2) % mod; + b /= 2; + } + return x % mod; +} +/* + * modular exponentiation + */ +ll modulo(ll base, ll exponent, ll mod) +{ + ll x = 1; + ll y = base; + while (exponent > 0) + { + if (exponent % 2 == 1) + x = (x * y) % mod; + y = (y * y) % mod; + exponent = exponent / 2; + } + return x % mod; +} + +/* + * Miller-Rabin primality test, iteration signifies the accuracy + */ +bool Miller(ll p,int iteration) +{ + if (p < 2) + { + return false; + } + if (p != 2 && p % 2==0) + { + return false; + } + ll s = p - 1; + while (s % 2 == 0) + { + s /= 2; + } + for (int i = 0; i < iteration; i++) + { + ll a = rand() % (p - 1) + 1, temp = s; + ll mod = modulo(a, temp, p); + while (temp != p - 1 && mod != 1 && mod != p - 1) + { + mod = mulmod(mod, mod, p); + temp *= 2; + } + if (mod != p - 1 && temp % 2 == 0) + { + return false; + } + } + return true; +} +//Main +int main() +{ + int iteration = 5; + ll num; + cout<<"Enter integer to test primality: "; + cin>>num; + if (Miller(num, iteration)) + cout< +#define ll long long +using namespace std; + +/* + * Function to calculate modulus of x raised to the power y + */ +ll modular_pow(ll base, ll exponent, int modulus) +{ + ll result = 1; + while (exponent > 0) + { + if (exponent % 2 == 1) + result = (result * base) % modulus; + exponent = exponent >> 1; + base = (base * base) % modulus; + } + return result; +} +/* + * Main + */ +int main() +{ + ll x, y; + int mod; + cout<<"Enter Base Value: "; + cin>>x; + cout<<"Enter Exponent: "; + cin>>y; + cout<<"Enter Modular Value: "; + cin>>mod; + cout< +#include +#include + +using namespace std; + +int main(int argc, char **argv) +{ + int p = 7, l = 3, g = 2, n = 4, x; + int a[] = { 1, 2, 2, 1 }; + int bin[4]; + cout << "The Random numbers are: "; + for (int i = 0; i < 10; i++) + { + x = rand() % 16; + for (int j = 3; j >= 0; j--) + { + bin[j] = x % 2; + x /= 2; + } + int mul = 1; + for (int k = 0; k < 4; k++) + mul *= pow(a[k], bin[k]); + cout << pow(g, mul)<<" "; + } +} + +/* +The Random numbers are: +2 4 16 4 2 4 16 16 4 2 \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Implement Park-Miller Random Number Generation Algorithm.cpp b/c++/11_Numerical_Problems/C++ Program to Implement Park-Miller Random Number Generation Algorithm.cpp new file mode 100644 index 0000000..ba16b82 --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Implement Park-Miller Random Number Generation Algorithm.cpp @@ -0,0 +1,51 @@ +/*This is a C++ Program to generate random numbers using Park-Miller algorithm. A general formula of a random number generator (RNG) of this type is: +X_{k+1} = g X(k) mod n +where the modulus n is a prime number or a power of a prime number, the multiplier g is an element of high multiplicative order modulo n (e.g., a primitive root modulo n), and the seed X0 is co-prime to n.*/ + +#include +#include +#include + +using namespace std; + +const long m = 2147483647L; +const long a = 48271L; +const long q = 44488L; +const long r = 3399L; + +static long r_seed = 12345678L; + +double uniform() +{ + long hi = r_seed / q; + long lo = r_seed - q * hi; + long t = a * lo - r * hi; + if (t > 0) + r_seed = t; + else + r_seed = t + m; + return r_seed; +} + +int main(int argc, char **argv) +{ + double A[10]; + for (int i = 0; i < 10; i++) + A[i] = uniform(); + cout<<"Random numbers are:\n"; + for (int i = 0; i < 10; i++) + cout << A[i]< +using namespace std; +/* + * multiply two numbers using Russian Peasant method + */ +unsigned int russianPeasant(unsigned int a, unsigned int b) +{ + int res = 0; + while (b > 0) + { + if (b & 1) + res = res + a; + a = a << 1; + b = b >> 1; + } + return res; +} + +/* + * Main + */ +int main() +{ + cout << russianPeasant(15, 5) << endl; + cout << russianPeasant(13, 6) << endl; + return 0; +} + +/* +75 +78 + +------------------ +(program exited with code: 1) +Press return to continue \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Implement Segmented Sieve.cpp b/c++/11_Numerical_Problems/C++ Program to Implement Segmented Sieve.cpp new file mode 100644 index 0000000..8b7d84c --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Implement Segmented Sieve.cpp @@ -0,0 +1,91 @@ +/* + * C++ Program to Implement Segmented Sieve + */ +#include +#include +#define MAX 46656 +#define LMT 216 +#define LEN 4830 +#define RNG 100032 +#define sq(x) ((x)*(x)) +#define mset(x,v) memset(x, v , sizeof(x)) +#define chkC(x,n) (x[n >> 6] & (1 << ((n >> 1) & 31))) +#define setC(x,n) (x[n >> 6] |= (1 << ((n >> 1) & 31))) +using namespace std; +unsigned base[MAX/64], segment[RNG/64], primes[LEN]; + +/* + * Generates all the necessary prime numbers and marks them in base[] + */ +void sieve() +{ + unsigned i, j, k; + for (i = 3; i < LMT; i += 2) + { + if (!chkC(base, i)) + { + for (j = i * i, k = i << 1; j < MAX; j += k) + setC(base, j); + } + } + for (i = 3, j = 0; i < MAX; i += 2) + { + if (!chkC(base, i)) + primes[j++] = i; + } +} + +/* + * Returns the prime-count within range [a,b] and marks them in segment[] + */ +int segmented_sieve(int a, int b) +{ + unsigned i, j, k, cnt = (a <= 2 && 2 <=b )? 1 : 0; + if (b < 2) + return 0; + if (a < 3) + a = 3; + if (a % 2 == 0) + a++; + mset (segment, 0); + for (i = 0; sq(primes[i]) <= b; i++) + { + j = primes[i] * ((a + primes[i] - 1) / primes[i]); + if (j % 2 == 0) j += primes[i]; + for (k = primes[i] << 1; j <= b; j += k) + { + if (j != primes[i]) + setC(segment, (j - a)); + } + } + for (i = 0; i <= b - a; i += 2) + { + if (!chkC(segment, i)) + cnt++; + } + return cnt; +} +/* + * Main + */ +int main() +{ + sieve(); + int a, b; + cout<<"Enter Lower Bound: "; + cin>>a; + cout<<"Enter Upper Bound: "; + cin>>b; + cout<<"Number of primes between "< +#include +#include +#define ll long long + +using namespace std; + +/* + * Sieve of Atkins + */ +void sieve_atkins(ll int n) +{ + vector is_prime(n + 1); + is_prime[2] = true; + is_prime[3] = true; + for (ll int i = 5; i <= n; i++) + { + is_prime[i] = false; + } + ll int lim = ceil(sqrt(n)); + for (ll int x = 1; x <= lim; x++) + { + for (ll int y = 1; y <= lim; y++) + { + ll int num = (4 * x * x + y * y); + if (num <= n && (num % 12 == 1 || num % 12 == 5)) + { + is_prime[num] = true; + } + num = (3 * x * x + y * y); + if (num <= n && (num % 12 == 7)) + { + is_prime[num] = true; + } + if (x > y) + { + num = (3 * x * x - y * y); + if (num <= n && (num % 12 == 11)) + { + is_prime[num] = true; + } + } + } + } + for (ll int i = 5; i <= lim; i++) + { + if (is_prime[i]) + { + for (ll int j = i * i; j <= n; j += i) + { + is_prime[j] = false; + } + } + } + for (ll int i = 2; i <= n; i++) + { + if (is_prime[i]) + { + cout< +const int len = 100; + +int main() +{ + int arr[100] = {0}; + for (int i = 2; i < 100; i++) + { + for (int j = i * i; j < 100; j+=i) + { + arr[j - 1] = 1; + } + } + for (int i = 1; i < 100; i++) + { + if (arr[i - 1] == 0) + std::cout << i << "\t"; + } +} + +/* +1 2 3 5 7 11 13 17 19 23 +29 31 37 41 43 47 53 59 61 67 +71 73 79 83 89 97 \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Implement Solovay-Strassen Primality Test.cpp b/c++/11_Numerical_Problems/C++ Program to Implement Solovay-Strassen Primality Test.cpp new file mode 100644 index 0000000..bbcefb2 --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Implement Solovay-Strassen Primality Test.cpp @@ -0,0 +1,110 @@ +/* + * C++ Program to Implement Solovay-Strassen Primality Test + */ +#include +#include +#include +#define ll long long +using namespace std; +/* + * modular exponentiation + */ +ll modulo(ll base, ll exponent, ll mod) +{ + ll x = 1; + ll y = base; + while (exponent > 0) + { + if (exponent % 2 == 1) + x = (x * y) % mod; + y = (y * y) % mod; + exponent = exponent / 2; + } + return x % mod; +} +/* + * calculates Jacobian(a/n) n>0 and n is odd + */ +int calculateJacobian(ll a,ll n) +{ + if (!a) + return 0; + int ans = 1; + ll temp; + if (a < 0) + { + a = -a; + if (n % 4 == 3) + ans=-ans; + } + if (a == 1) + return ans; + while (a) + { + if (a < 0) + { + a = -a; + if (n % 4 == 3) + ans = -ans; + } + while (a % 2 == 0) + { + a = a / 2; + if (n % 8 == 3 || n % 8 == 5) + ans = -ans; + } + swap(a, n); + if (a % 4 == 3 && n % 4 == 3) + ans = -ans; + a = a % n; + if (a > n / 2) + a = a - n; + } + if (n == 1) + return ans; + return 0; +} + +/* + * Solovay-Strassen Primality Test + * Iterations determine the accuracy of the test + */ +bool Solovoy(ll p, int iteration) +{ + if (p < 2) + return false; + if (p != 2 && p % 2 == 0) + return false; + for (int i = 0; i < iteration; i++) + { + ll a = rand() % (p - 1) + 1; + ll jacobian = (p + calculateJacobian(a, p)) % p; + ll mod = modulo(a, (p - 1) / 2, p); + if (!jacobian || mod != jacobian) + { + return false; + } + } + return true; +} +//Main +int main() +{ + int iteration = 50; + ll num; + cout<<"Enter integr to test primality: "; + cin>>num; + if (Solovoy(num, iteration)) + cout< +#include +#include +#include + +#define M 2 +#define N (1<rb = rm; // top rows + else + b->ra = rm; // bot rows + if (j == 0) + b->cb = cm; // left cols + else + b->ca = cm; // right cols +} + +// Multiply: A[a] * B[b] => C[c], recursively. +void mul(mat A, mat B, mat C, corners a, corners b, corners c) +{ + corners aii[2][2], bii[2][2], cii[2][2], p; + mat P[7], S, T; + int i, j, m, n, k; + // Check: A[m n] * B[n k] = C[m k] + m = a.rb - a.ra; + assert(m==(c.rb-c.ra)); + n = a.cb - a.ca; + assert(n==(b.rb-b.ra)); + k = b.cb - b.ca; + assert(k==(c.cb-c.ca)); + assert(m>0); + if (n == 1) + { + C[c.ra][c.ca] += A[a.ra][a.ca] * B[b.ra][b.ca]; + return; + } + // Create the 12 smaller matrix indexes: + // A00 A01 B00 B01 C00 C01 + // A10 A11 B10 B11 C10 C11 + for (i = 0; i < 2; i++) + { + for (j = 0; j < 2; j++) + { + find_corner(a, i, j, &aii[i][j]); + find_corner(b, i, j, &bii[i][j]); + find_corner(c, i, j, &cii[i][j]); + } + } + p.ra = p.ca = 0; + p.rb = p.cb = m / 2; +#define LEN(A) (sizeof(A)/sizeof(A[0])) + for (i = 0; i < LEN(P); i++) + set(P[i], p, 0); +#define ST0 set(S,p,0); set(T,p,0) + // (A00 + A11) * (B00+B11) = S * T = P0 + ST0; + add(A, A, S, aii[0][0], aii[1][1], p); + add(B, B, T, bii[0][0], bii[1][1], p); + mul(S, T, P[0], p, p, p); + // (A10 + A11) * B00 = S * B00 = P1 + ST0; + add(A, A, S, aii[1][0], aii[1][1], p); + mul(S, B, P[1], p, bii[0][0], p); + // A00 * (B01 - B11) = A00 * T = P2 + ST0; + sub(B, B, T, bii[0][1], bii[1][1], p); + mul(A, T, P[2], aii[0][0], p, p); + // A11 * (B10 - B00) = A11 * T = P3 + ST0; + sub(B, B, T, bii[1][0], bii[0][0], p); + mul(A, T, P[3], aii[1][1], p, p); + // (A00 + A01) * B11 = S * B11 = P4 + ST0; + add(A, A, S, aii[0][0], aii[0][1], p); + mul(S, B, P[4], p, bii[1][1], p); + // (A10 - A00) * (B00 + B01) = S * T = P5 + ST0; + sub(A, A, S, aii[1][0], aii[0][0], p); + add(B, B, T, bii[0][0], bii[0][1], p); + mul(S, T, P[5], p, p, p); + // (A01 - A11) * (B10 + B11) = S * T = P6 + ST0; + sub(A, A, S, aii[0][1], aii[1][1], p); + add(B, B, T, bii[1][0], bii[1][1], p); + mul(S, T, P[6], p, p, p); + // P0 + P3 - P4 + P6 = S - P4 + P6 = T + P6 = C00 + add(P[0], P[3], S, p, p, p); + sub(S, P[4], T, p, p, p); + add(T, P[6], C, p, p, cii[0][0]); + // P2 + P4 = C01 + add(P[2], P[4], C, p, p, cii[0][1]); + // P1 + P3 = C10 + add(P[1], P[3], C, p, p, cii[1][0]); + // P0 + P2 - P1 + P5 = S - P1 + P5 = T + P5 = C11 + add(P[0], P[2], S, p, p, p); + sub(S, P[1], T, p, p, p); + add(T, P[5], C, p, p, cii[1][1]); +} +int main() +{ + mat A, B, C; + corners ai = { 0, N, 0, N }; + corners bi = { 0, N, 0, N }; + corners ci = { 0, N, 0, N }; + srand(time(0)); + // identity(A,bi); identity(B,bi); + // set(A,ai,2); set(B,bi,2); + randk(A, ai, 0, 2); + randk(B, bi, 0, 2); + print(A, ai, "A"); + print(B, bi, "B"); + set(C, ci, 0); + // add(A,B,C, ai, bi, ci); + mul(A, B, C, ai, bi, ci); + print(C, ci, "C"); + return 0; +} + +/* + +A = { + 1.2, 0.83, 0.39, 0.41, + 1.8, 1.9, 0.49, 0.23, +0.38, 0.72, 1.8, 1.9, +0.13, 1.8, 0.48, 0.82, +} +B = { + 1.2, 1.6, 1.4, 1.6, +0.27, 0.63, 0.3, 0.79, +0.58, 1.2, 1.1, 0.07, + 2, 1.9, 0.47, 0.47, +} +C = { + 2.7, 3.7, 2.6, 2.9, + 3.4, 5, 3.7, 4.5, + 5.3, 6.7, 3.6, 2.2, + 2.5, 3.5, 1.6, 2.1, +} \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Implement the Bin Packing Algorithm.cpp b/c++/11_Numerical_Problems/C++ Program to Implement the Bin Packing Algorithm.cpp new file mode 100644 index 0000000..f95ab57 --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Implement the Bin Packing Algorithm.cpp @@ -0,0 +1,52 @@ +/*This is a C++ Program to implement Bin packing algorithm. This is a sample program to illustrate the Bin-Packing algorithm using next fit heuristics. In the bin packing problem, objects of different volumes must be packed into a finite number of bins or containers each of volume V in a way that minimizes the number of bins used. In computational complexity theory, it is a combinatorial NP-hard problem. +There are many variations of this problem, such as 2D packing, linear packing, packing by weight, packing by cost, and so on. They have many applications, such as filling up containers, loading trucks with weight capacity constraints, creating file backups in media and technology mapping in Field-programmable gate array semiconductor chip design. + +The bin packing problem can also be seen as a special case of the cutting stock problem. When the number of bins is restricted to 1 and each item is characterised by both a volume and a value, the problem of maximising the value of items that can fit in the bin is known as the knapsack problem.*/ + +#include + +using namespace std; + +void binPacking(int *a, int size, int n) +{ + int binCount = 1; + int s = size; + for (int i = 0; i < n; i++) + { + if (s - *(a + i) > 0) + { + s -= *(a + i); + continue; + } + else + { + binCount++; + s = size; + i--; + } + } + cout << "Number of bins required: " << binCount; +} + +int main(int argc, char **argv) +{ + cout << "BIN - PACKING Algorithm\n"; + cout << "Enter the number of items in Set: "; + int n; + cin >> n; + cout << "Enter " << n << " items:"; + int a[n]; + for (int i = 0; i < n; i++) + cin >> a[i]; + cout << "Enter the bin size: "; + int size; + cin >> size; + binPacking(a, size, n); +} + +/* +BIN - PACKING Algorithm +Enter the number of items in Set: 5 +Enter 5 items:12 23 34 45 56 +Enter the bin size: 70 +Number of bins required: 3 \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Implement the Schonhage-Strassen Algorithm for Multiplication of Two Numbers.cpp b/c++/11_Numerical_Problems/C++ Program to Implement the Schonhage-Strassen Algorithm for Multiplication of Two Numbers.cpp new file mode 100644 index 0000000..cfe517d --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Implement the Schonhage-Strassen Algorithm for Multiplication of Two Numbers.cpp @@ -0,0 +1,62 @@ +#include + +using namespace std; + +int noOfDigit(long a) +{ + int n = 0; + while (a > 0) + { + a /= 10; + n++; + } + return n; +} +void schonhageStrassenMultiplication(long x, long y, int n, int m) +{ + int linearConvolution[n + m - 1]; + for (int i = 0; i < (n + m - 1); i++) + linearConvolution[i] = 0; + long p = x; + for (int i = 0; i < m; i++) + { + x = p; + for (int j = 0; j < n; j++) + { + linearConvolution[i + j] += (y % 10) * (x % 10); + x /= 10; + } + y /= 10; + } + cout << "The Linear Convolution is: ( "; + for (int i = (n + m - 2); i >= 0; i--) + { + cout << linearConvolution[i] << " "; + } + cout << ")"; + long product = 0; + int nextCarry = 0, base = 1; + ; + for (int i = 0; i < n + m - 1; i++) + { + linearConvolution[i] += nextCarry; + product = product + (base * (linearConvolution[i] % 10)); + nextCarry = linearConvolution[i] / 10; + base *= 10; + } + cout << "\nThe Product of the numbers is: " << product; +} +int main(int argc, char **argv) +{ + cout << "Enter the numbers:"; + long a, b; + cin >> a >> b; + int n = noOfDigit(a); + int m = noOfDigit(b); + schonhageStrassenMultiplication(a, b, n, m); +} + +/* +Enter the numbers:3452 1245 +The Linear Convolution is: ( 3 10 25 43 44 33 10 ) + Product of the numbers is: 4297740 \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Implement the linear congruential generator for Pseudo Random Number Generation.cpp b/c++/11_Numerical_Problems/C++ Program to Implement the linear congruential generator for Pseudo Random Number Generation.cpp new file mode 100644 index 0000000..a422fd1 --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Implement the linear congruential generator for Pseudo Random Number Generation.cpp @@ -0,0 +1,95 @@ +/*This is a C++ Program to generate random numbers using Linear Congruential Generator. A linear congruential generator (LCG) is an algorithm that yields a sequence of pseudo-randomized numbers calculated with a discontinuous piecewise linear equation. The method represents one of the oldest and best-known pseudorandom number generator algorithms. The theory behind them is relatively easy to understand, and they are easily implemented and fast, especially on computer hardware which can provide modulo arithmetic by storage-bit truncation.*/ + +#include + +using namespace std; + +class mRND +{ +public: + void seed(unsigned int s) + { + _seed = s; + } + +protected: + mRND() : + _seed(0), _a(0), _c(0), _m(2147483648) + { + } + int rnd() + { + return (_seed = (_a * _seed + _c) % _m); + } + + int _a, _c; + unsigned int _m, _seed; +}; + +class MS_RND: public mRND +{ +public: + MS_RND() + { + _a = 214013; + _c = 2531011; + } + int rnd() + { + return mRND::rnd() >> 16; + } +}; + +class BSD_RND: public mRND +{ +public: + BSD_RND() + { + _a = 1103515245; + _c = 12345; + } + int rnd() + { + return mRND::rnd(); + } +}; + +int main(int argc, char* argv[]) +{ + BSD_RND bsd_rnd; + MS_RND ms_rnd; + cout << "MS RAND:" << endl << "========" << endl; + for (int x = 0; x < 10; x++) + cout << ms_rnd.rnd() << endl; + cout << endl << "BSD RAND:" << endl << "=========" << endl; + for (int x = 0; x < 10; x++) + cout << bsd_rnd.rnd() << endl; + return 0; +} + +/* +MS RAND: +======== +38 +7719 +21238 +2437 +8855 +11797 +8365 +32285 +10450 +30612 + +BSD RAND: +========= +12345 +1406932606 +654583775 +1449466924 +229283573 +1109335178 +1051550459 +1293799192 +794471793 +551188310 \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Implement wheel Sieve to Generate Prime Numbers Between Given Range.cpp b/c++/11_Numerical_Problems/C++ Program to Implement wheel Sieve to Generate Prime Numbers Between Given Range.cpp new file mode 100644 index 0000000..dd68031 --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Implement wheel Sieve to Generate Prime Numbers Between Given Range.cpp @@ -0,0 +1,84 @@ +/*This is a C++ Program to find prime number between a given range using Wheel Seive method. Wheel factorization is a graphical method for manually performing a preliminary to the Sieve of Eratosthenes that separates prime numbers from composites. Start by writing the natural numbers around circles as shown below. Prime numbers in the innermost circle have their multiples in similar positions as themselves in the other circles, forming spokes of primes and their multiples. Multiples of the prime numbers in the innermost circle form spokes of composite numbers in the outer circles.*/ + +#include +#include +#include + +using namespace std; + +#define MAX_NUM 50 +// array will be initialized to 0 being global +int primes[MAX_NUM]; + +void gen_sieve_primes(void) +{ + for (int p = 2; p < MAX_NUM; p++) // for all elements in array + { + if (primes[p] == 0) // it is not multiple of any other prime + primes[p] = 1; // mark it as prime + // mark all multiples of prime selected above as non primes + int c = 2; + int mul = p * c; + for (; mul < MAX_NUM;) + { + primes[mul] = -1; + c++; + mul = p * c; + } + } +} + +void print_all_primes() +{ + int c = 0; + for (int i = 0; i < MAX_NUM; i++) + { + if (primes[i] == 1) + { + c++; + if (c < 4) + { + switch (c) + { + case 1: + cout << c << "st prime is: " << i << endl; + break; + case 2: + cout << c << "nd prime is: " << i << endl; + break; + case 3: + cout << c << "rd prime is: " << i << endl; + break; + default: + break; + } + } + else + cout << c << "th prime is: " << i << endl; + } + } +} + +int main() +{ + gen_sieve_primes(); + print_all_primes(); + return 0; +} + +/* +1st prime is: 2 +2nd prime is: 3 +3rd prime is: 5 +4th prime is: 7 +5th prime is: 11 +6th prime is: 13 +7th prime is: 17 +8th prime is: 19 +9th prime is: 23 +10th prime is: 29 +11th prime is: 31 +12th prime is: 37 +13th prime is: 41 +14th prime is: 43 +15th prime is: 47 \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Optimize Wire Length in Electrical Circuit.cpp b/c++/11_Numerical_Problems/C++ Program to Optimize Wire Length in Electrical Circuit.cpp new file mode 100644 index 0000000..56b3fc9 --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Optimize Wire Length in Electrical Circuit.cpp @@ -0,0 +1,113 @@ +#include +#include +#include + +using namespace std; + +// Number of components in the graph +#define V 9 + +// A utility function to find the component with minimum distance value, from +// the set of components not yet included in shortest path tree +int minDistance(int dist[], bool sptSet[]) +{ + // Initialize min value + int min = INT_MAX, min_index; + for (int v = 0; v < V; v++) + if (sptSet[v] == false && dist[v] <= min) + min = dist[v], min_index = v; + return min_index; +} + +// A utility function to print the constructed distance array +void printSolution(int dist[], int n) +{ + cout << "Component\tDistance from other component\n"; + for (int i = 0; i < V; i++) + printf("%d\t\t%d\n", i, dist[i]); +} + +// Funtion that implements Dijkstra's single source shortest path algorithm +// for a graph represented using adjacency matrix representation +void optimizeLength(int graph[V][V], int src) +{ + int dist[V]; // The output array. dist[i] will hold the shortest + // distance from src to i + bool sptSet[V]; // sptSet[i] will true if component i is included in shortest + // path tree or shortest distance from src to i is finalized + // Initialize all distances as INFINITE and stpSet[] as false + for (int i = 0; i < V; i++) + dist[i] = INT_MAX, sptSet[i] = false; + // Distance of source component from itself is always 0 + dist[src] = 0; + // Find shortest path for all components + for (int count = 0; count < V - 1; count++) + { + // Pick the minimum distance component from the set of components not + // yet processed. u is always equal to src in first iteration. + int u = minDistance(dist, sptSet); + // Mark the picked component as processed + sptSet[u] = true; + // Update dist value of the adjacent components of the picked component. + for (int v = 0; v < V; v++) + // Update dist[v] only if is not in sptSet, there is an edge from + // u to v, and total weight of path from src to v through u is + // smaller than current value of dist[v] + if (!sptSet[v] && graph[u][v] && dist[u] != INT_MAX && dist[u] + + graph[u][v] < dist[v]) + dist[v] = dist[u] + graph[u][v]; + } + // print the constructed distance array + printSolution(dist, V); +} + +// driver program to test above function +int main() +{ + /* Let us create the example graph discussed above */ + int graph[V][V] = + { + { 0, 4, 0, 0, 0, 0, 0, 8, 0 }, { 4, 0, 8, 0, 0, 0, 0, 11, 0 }, { + 0, 8, 0, 7, 0, 4, 0, 0, 2 + }, + { 0, 0, 7, 0, 9, 14, 0, 0, 0 }, { + 0, 0, 0, 9, 0, 10, 0, 0, + 0 + }, { 0, 0, 4, 0, 10, 0, 2, 0, 0 }, { + 0, 0, 0, 14, + 0, 2, 0, 1, 6 + }, { 8, 11, 0, 0, 0, 0, 1, 0, 7 }, { + 0, 0, 2, 0, 0, 0, 6, 7, 0 + } + }; + cout << "Enter the starting component: "; + int s; + cin >> s; + optimizeLength(graph, s); + return 0; +} + +/* +Enter the starting component: 1 +Component Distance from other component +0 4 +1 0 +2 8 +3 15 +4 22 +5 12 +6 12 +7 11 +8 10 + +Enter the starting component: 6 +Component Distance from other component +0 9 +1 12 +2 6 +3 13 +4 12 +5 2 +6 0 +7 1 +8 6 \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Perform Addition Operation Using Bitwise Operators.cpp b/c++/11_Numerical_Problems/C++ Program to Perform Addition Operation Using Bitwise Operators.cpp new file mode 100644 index 0000000..fbd98e7 --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Perform Addition Operation Using Bitwise Operators.cpp @@ -0,0 +1,27 @@ +#include +#include +#include + +using namespace std; +int add(int x, int y) +{ + int carry; + while (y != 0) + { + carry = x & y; + x = x ^ y; + y = carry << 1; + } + return x; +} +int main(int argc, char **argv) +{ + cout << "Enter the numbers to be added:"; + int x, y; + cin >> x >> y; + cout << "The Summation is: " << add(x, y); +} + +/* +Enter the numbers to be added:23 24 +The Summation is: 47 \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Perform Encoding of a Message Using Matrix Multiplication.cpp b/c++/11_Numerical_Problems/C++ Program to Perform Encoding of a Message Using Matrix Multiplication.cpp new file mode 100644 index 0000000..8ea6a37 --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Perform Encoding of a Message Using Matrix Multiplication.cpp @@ -0,0 +1,77 @@ +#include +#include +using namespace std; +int main() +{ + int a[10][10], b[10][10], c[10][10]; + int x, y, i, j; + cout << "\nEnter the number of rows and columns for Message Matrix:\n\n"; + cin >> x >> y; + // x denotes number rows in matrix A + // y denotes number columns in matrix A + cout << "\n\nEnter elements for Matrix :::\n\n"; + for (i = 0; i < x; i++) + { + for (j = 0; j < y; j++) + { + cin >> a[i][j]; + } + cout << "\n"; + } + cout << "\n\nMatrix :\n\n"; + for (i = 0; i < x; i++) + { + for (j = 0; j < y; j++) + { + cout << "\t" << a[i][j]; + } + cout << "\n\n"; + } + for (i = 0; i < y; i++) + { + for (j = 0; j < x; j++) + { + b[i][j]=x+y; + } + cout << "\n"; + } + for (i = 0; i < x; i++) + { + for (j = 0; j < x; j++) + { + c[i][j] = 0; + for (int k = 0; k < y; k++) + { + c[i][j] = c[i][j] + a[i][k] * b[k][j]; + } + } + } + cout + << "\n-----------------------------------------------------------\n"; + cout << "\n\nEncoded Matrix :\n\n"; + for (i = 0; i < x; i++) + { + for (j = 0; j < x; j++) + { + cout << "\t" << c[i][j]; + } + cout << "\n\n"; + } + getch(); + return 0; +} + +/* +Enter the number of rows and columns for Message Matrix: +2 2 + +Enter elements for Matrix ::: +1 2 +3 4 +Matrix : + 1 2 + 3 4 +----------------------------------------------------------- +Encoded Matrix : + 12 12 + 28 28 \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Perform LU Decomposition of any Matrix.cpp b/c++/11_Numerical_Problems/C++ Program to Perform LU Decomposition of any Matrix.cpp new file mode 100644 index 0000000..1b64da6 --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Perform LU Decomposition of any Matrix.cpp @@ -0,0 +1,103 @@ +/* +This is a C++ Program to perform LU Decomposition of any matrix. In numerical analysis, LU decomposition (where ‘LU’ stands for ‘Lower Upper’, and also called LU factorization) factors a matrix as the product of a lower triangular matrix and an upper triangular matrix. The product sometimes includes a permutation matrix as well. The LU decomposition can be viewed as the matrix form of Gaussian elimination. Computers usually solve square systems of linear equations using the LU decomposition, and it is also a key step when inverting a matrix, or computing the determinant of a matrix +*/ + +#include +#include + +using namespace std; + +int main(int argc, char **argv) +{ + void lu(float[][10], float[][10], float[][10], int n); + void output(float[][10], int); + float a[10][10], l[10][10], u[10][10]; + int n = 0, i = 0, j = 0; + cout << "Enter size of 2d array(Square matrix) : "; + cin >> n; + for (i = 0; i < n; i++) + { + for (j = 0; j < n; j++) + { + cout << "Enter values no:" << i << ", " << j << ": "; + cin >> a[i][j]; + } + } + lu(a, l, u, n); + cout << "\nL Decomposition\n\n"; + output(l, n); + cout << "\nU Decomposition\n\n"; + output(u, n); + return 0; +} +void lu(float a[][10], float l[][10], float u[][10], int n) +{ + int i = 0, j = 0, k = 0; + for (i = 0; i < n; i++) + { + for (j = 0; j < n; j++) + { + if (j < i) + l[j][i] = 0; + else + { + l[j][i] = a[j][i]; + for (k = 0; k < i; k++) + { + l[j][i] = l[j][i] - l[j][k] * u[k][i]; + } + } + } + for (j = 0; j < n; j++) + { + if (j < i) + u[i][j] = 0; + else if (j == i) + u[i][j] = 1; + else + { + u[i][j] = a[i][j] / l[i][i]; + for (k = 0; k < i; k++) + { + u[i][j] = u[i][j] - ((l[i][k] * u[k][j]) / l[i][i]); + } + } + } + } +} +void output(float x[][10], int n) +{ + int i = 0, j = 0; + for (i = 0; i < n; i++) + { + for (j = 0; j < n; j++) + { + printf("%f ", x[i][j]); + } + cout << "\n"; + } +} + +/* +Enter size of 2d array(Square matrix) : 3 +Enter values no:0, 0: 1 +Enter values no:0, 1: 1 +Enter values no:0, 2: -1 +Enter values no:1, 0: 2 +Enter values no:1, 1: -1 +Enter values no:1, 2: 3 +Enter values no:2, 0: 3 +Enter values no:2, 1: 1 +Enter values no:2, 2: -1 + +L Decomposition + +1.000000 0.000000 0.000000 +2.000000 -3.000000 0.000000 +3.000000 -2.000000 -1.333333 + +U Decomposition + +1.000000 1.000000 -1.000000 +0.000000 1.000000 -1.666667 +0.000000 0.000000 1.000000 \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Perform Matrix Multiplication.cpp b/c++/11_Numerical_Problems/C++ Program to Perform Matrix Multiplication.cpp new file mode 100644 index 0000000..91767f7 --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Perform Matrix Multiplication.cpp @@ -0,0 +1,112 @@ +#include +#include +using namespace std; +int main() +{ + int a[10][10], b[10][10], c[10][10]; + int x, y, i, j, m, n; + cout << "\nEnter the number of rows and columns for Matrix A:::\n\n"; + cin >> x >> y; + // x denotes number rows in matrix A + // y denotes number columns in matrix A + cout << "\n\nEnter elements for Matrix A :::\n\n"; + for (i = 0; i < x; i++) + { + for (j = 0; j < y; j++) + { + cin >> a[i][j]; + } + cout << "\n"; + } + cout << "\n\nMatrix A :\n\n"; + for (i = 0; i < x; i++) + { + for (j = 0; j < y; j++) + { + cout << "\t" << a[i][j]; + } + cout << "\n\n"; + } + cout << "\n-----------------------------------------------------------\n"; + cout << "\nEnter the number of rows and columns for Matrix B:::\n\n"; + cin >> m >> n; + // m denotes number rows in matrix B + // n denotes number columns in matrix B + cout << "\n\nEnter elements for Matrix B :::\n\n"; + for (i = 0; i < m; i++) + { + for (j = 0; j < n; j++) + { + cin >> b[i][j]; + } + cout << "\n"; + } + cout << "\n\nMatrix B :\n\n"; + for (i = 0; i < m; i++) + { + for (j = 0; j < n; j++) + { + cout << "\t" << b[i][j]; + } + cout << "\n\n"; + } + if (y == m) + { + for (i = 0; i < x; i++) + { + for (j = 0; j < n; j++) + { + c[i][j] = 0; + for (int k = 0; k < m; k++) + { + c[i][j] = c[i][j] + a[i][k] * b[k][j]; + } + } + } + cout + << "\n-----------------------------------------------------------\n"; + cout << "\n\nMultiplication of Matrix A and Matrix B :\n\n"; + for (i = 0; i < x; i++) + { + for (j = 0; j < n; j++) + { + cout << "\t" << c[i][j]; + } + cout << "\n\n"; + } + } + else + { + cout << "\n\nMultiplication is not possible"; + } + getch(); + return 0; +} + +/* +Enter the number of rows and columns for Matrix A::: +2 2 + +Enter elements for Matrix A ::: +1 2 +3 4 + +Matrix A : + 1 2 + 3 4 +----------------------------------------------------------- +Enter the number of rows and columns for Matrix B::: +2 2 + +Enter elements for Matrix B ::: +4 5 +6 7 + +Matrix B : + 4 5 + 6 7 +----------------------------------------------------------- + +Multiplication of Matrix A and Matrix B : + 16 19 + 36 43 \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Perform Optimal Paranthesization Using Dynamic Programming.cpp b/c++/11_Numerical_Problems/C++ Program to Perform Optimal Paranthesization Using Dynamic Programming.cpp new file mode 100644 index 0000000..52ff259 --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Perform Optimal Paranthesization Using Dynamic Programming.cpp @@ -0,0 +1,65 @@ +#include +#include +#include + +using namespace std; + +// Matrix Ai has dimension p[i-1] x p[i] for i = 1..n + +int MatrixChainOrder(int p[], int n) +{ + /* For simplicity of the program, one extra row and one extra column are + allocated in m[][]. 0th row and 0th column of m[][] are not used */ + int m[n][n]; + int s[n][n]; + int i, j, k, L, q; + /* m[i,j] = Minimum number of scalar multiplications needed to compute + the matrix A[i]A[i+1]...A[j] = A[i..j] where dimention of A[i] is + p[i-1] x p[i] */ + // cost is zero when multiplying one matrix. + for (i = 1; i < n; i++) + m[i][i] = 0; + // L is chain length. + for (L = 2; L < n; L++) + { + for (i = 1; i <= n - L + 1; i++) + { + j = i + L - 1; + m[i][j] = INT_MAX; + for (k = i; k <= j - 1; k++) + { + // q = cost/scalar multiplications + q = m[i][k] + m[k + 1][j] + p[i - 1] * p[k] * p[j]; + if (q < m[i][j]) + { + m[i][j] = q; + s[i][j] = k; + } + } + } + } + return m[1][n - 1]; +} +int main() +{ + cout + << "Enter the array p[], which represents the chain of matrices such that the ith matrix Ai is of dimension p[i-1] x p[i]"; + cout << "Enter the total length:"; + int n; + cin >> n; + int array[n]; + cout << "Enter the dimensions: "; + for (int var = 0; var < n; ++var) + { + cin >> array[var]; + } + cout << "Minimum number of multiplications is: " << MatrixChainOrder(array, + n); + return 0; +} + +/* + +Enter the array p[], which represents the chain of matrices such that the ith matrix Ai is of dimension p[i-1] x p[i]Enter the total length:4 +Enter the dimensions: 2 4 3 5 +Minimum number of multiplications is: 54 \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Perform Partition of an Integer in All Possible Ways.cpp b/c++/11_Numerical_Problems/C++ Program to Perform Partition of an Integer in All Possible Ways.cpp new file mode 100644 index 0000000..bcb04bb --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Perform Partition of an Integer in All Possible Ways.cpp @@ -0,0 +1,80 @@ +#include +using namespace std; + +// A utility function to print an array p[] of size 'n' +void printArray(int p[], int n) +{ + for (int i = 0; i < n; i++) + cout << p[i] << " "; + cout << endl; +} + +void printAllUniqueParts(int n) +{ + int p[n]; // An array to store a partition + int k = 0; // Index of last element in a partition + p[k] = n; // Initialize first partition as number itself + // This loop first prints current partition, then generates next + // partition. The loop stops when the current partition has all 1s + while (true) + { + // print current partition + printArray(p, k + 1); + // Generate next partition + // Find the rightmost non-one value in p[]. Also, update the + // rem_val so that we know how much value can be accommodated + int rem_val = 0; + while (k >= 0 && p[k] == 1) + { + rem_val += p[k]; + k--; + } + // if k < 0, all the values are 1 so there are no more partitions + if (k < 0) + return; + // Decrease the p[k] found above and adjust the rem_val + p[k]--; + rem_val++; + // If rem_val is more, then the sorted order is violeted. Divide + // rem_val in differnt values of size p[k] and copy these values at + // different positions after p[k] + while (rem_val > p[k]) + { + p[k + 1] = p[k]; + rem_val = rem_val - p[k]; + k++; + } + // Copy rem_val to next position and increment position + p[k + 1] = rem_val; + k++; + } +} + +// Driver program to test above functions +int main() +{ + cout << "All Unique Partitions of 2 \n"; + printAllUniqueParts(2); + cout << "\nAll Unique Partitions of 3 \n"; + printAllUniqueParts(3); + cout << "\nAll Unique Partitions of 4 \n"; + printAllUniqueParts(4); + return 0; +} + +/* +All Unique Partitions of 2 +2 +1 1 + +All Unique Partitions of 3 +3 +2 1 +1 1 1 + +All Unique Partitions of 4 +4 +3 1 +2 2 +2 1 1 +1 1 1 1 \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Perform the Unique Factorization of a Given Number.cpp b/c++/11_Numerical_Problems/C++ Program to Perform the Unique Factorization of a Given Number.cpp new file mode 100644 index 0000000..9c998a3 --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Perform the Unique Factorization of a Given Number.cpp @@ -0,0 +1,81 @@ +#include +using namespace std; + +// A utility function to print an array p[] of size 'n' +void printArray(int p[], int n) +{ + for (int i = 0; i < n; i++) + cout << p[i] << " "; + cout << endl; +} + +void printAllUniqueParts(int n) +{ + int p[n]; // An array to store a partition + int k = 0; // Index of last element in a partition + p[k] = n; // Initialize first partition as number itself + // This loop first prints current partition, then generates next + // partition. The loop stops when the current partition has all 1s + while (true) + { + // print current partition + printArray(p, k + 1); + // Generate next partition + // Find the rightmost non-one value in p[]. Also, update the + // rem_val so that we know how much value can be accommodated + int rem_val = 0; + while (k >= 0 && p[k] == 1) + { + rem_val += p[k]; + k--; + } + // if k < 0, all the values are 1 so there are no more partitions + if (k < 0) + return; + // Decrease the p[k] found above and adjust the rem_val + p[k]--; + rem_val++; + // If rem_val is more, then the sorted order is violeted. Divide + // rem_val in differnt values of size p[k] and copy these values at + // different positions after p[k] + while (rem_val > p[k]) + { + p[k + 1] = p[k]; + rem_val = rem_val - p[k]; + k++; + } + // Copy rem_val to next position and increment position + p[k + 1] = rem_val; + k++; + } +} + +// Driver program to test above functions +int main() +{ + cout << "All Unique Partitions of 2 \n"; + printAllUniqueParts(2); + cout << "\nAll Unique Partitions of 3 \n"; + printAllUniqueParts(3); + cout << "\nAll Unique Partitions of 4 \n"; + printAllUniqueParts(4); + return 0; +} + +/* + +All Unique Partitions of 2 +2 +1 1 + +All Unique Partitions of 3 +3 +2 1 +1 1 1 + +All Unique Partitions of 4 +4 +3 1 +2 2 +2 1 1 +1 1 1 1 \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Represent Linear Equations in Matrix Form.cpp b/c++/11_Numerical_Problems/C++ Program to Represent Linear Equations in Matrix Form.cpp new file mode 100644 index 0000000..3000509 --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Represent Linear Equations in Matrix Form.cpp @@ -0,0 +1,49 @@ +#include +#include + +using namespace std; + +int main(void) +{ + char var[] = { 'x', 'y', 'z', 'w' }; + cout << "Enter the number of variables in the equations: "; + int n; + cin >> n; + cout << "\nEnter the coefficients of each variable for each equations"; + cout << "\nax + by + cz + ... = d"; + int mat[n][n]; + int constants[n][1]; + for (int i = 0; i < n; i++) + { + for (int j = 0; j < n; j++) + { + cin >> mat[i][j]; + } + cin >> constants[i][0]; + } + cout << "Matrix representation is: "; + for (int i = 0; i < n; i++) + { + for (int j = 0; j < n; j++) + { + cout << " " << mat[i][j]; + } + cout << " " << var[i]; + cout << " = " << constants[i][0]; + cout << "\n"; + } + return 0; +} + +/* +Enter the number of variables in the equations: 3 + +Enter the coefficients of each variable for each equations +ax + by + cz + ... = d +1 2 3 4 +1 2 6 8 +2 3 9 8 +Matrix representation is: + 1 2 3 x = 4 + 1 2 6 y = 8 + 2 3 9 z = 8 \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Solve Knapsack Problem Using Dynamic Programming.cpp b/c++/11_Numerical_Problems/C++ Program to Solve Knapsack Problem Using Dynamic Programming.cpp new file mode 100644 index 0000000..a6171e2 --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Solve Knapsack Problem Using Dynamic Programming.cpp @@ -0,0 +1,65 @@ +/*This is a C++ Program to knapsack problem using dynamic programming. The knapsack problem or rucksack problem is a problem in combinatorial optimization: Given a set of items, each with a mass and a value, determine the number of each item to include in a collection so that the total weight is less than or equal to a given limit and the total value is as large as possible. It derives its name from the problem faced by someone who is constrained by a fixed-size knapsack and must fill it with the most valuable items.*/ + +// A Dynamic Programming based solution for 0-1 Knapsack problem +#include + +using namespace std; + +// A utility function that returns maximum of two integers +int max(int a, int b) +{ + return (a > b) ? a : b; +} + +// Returns the maximum value that can be put in a knapsack of capacity W +int knapSack(int W, int wt[], int val[], int n) +{ + int i, w; + int K[n + 1][W + 1]; + // Build table K[][] in bottom up manner + for (i = 0; i <= n; i++) + { + for (w = 0; w <= W; w++) + { + if (i == 0 || w == 0) + K[i][w] = 0; + else if (wt[i - 1] <= w) + K[i][w] + = max(val[i - 1] + K[i - 1][w - wt[i - 1]], K[i - 1][w]); + else + K[i][w] = K[i - 1][w]; + } + } + return K[n][W]; +} + +int main() +{ + cout << "Enter the number of items in a Knapsack:"; + int n, W; + cin >> n; + int val[n], wt[n]; + for (int i = 0; i < n; i++) + { + cout << "Enter value and weight for item " << i << ":"; + cin >> val[i]; + cin >> wt[i]; + } + // int val[] = { 60, 100, 120 }; + // int wt[] = { 10, 20, 30 }; + // int W = 50; + cout << "Enter the capacity of knapsack"; + cin >> W; + cout << knapSack(W, wt, val, n); + return 0; +} + +/* +Enter the number of items in a Knapsack:5 +Enter value and weight for item 0:11 111 +Enter value and weight for item 1:22 121 +Enter value and weight for item 2:33 131 +Enter value and weight for item 3:44 141 +Enter value and weight for item 4:55 151 +Enter the capacity of knapsack 300 +99 \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Solve any Linear Equation in One Variable.cpp b/c++/11_Numerical_Problems/C++ Program to Solve any Linear Equation in One Variable.cpp new file mode 100644 index 0000000..edc65a7 --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Solve any Linear Equation in One Variable.cpp @@ -0,0 +1,647 @@ +#if !defined(MATRIX_H) +#define MATRIX_H +#include +#include +#include +#include +#include + +class CMatrix +{ +private: + int m_rows; + int m_cols; + char m_name[128]; + CMatrix(); +public: + double **m_pData; + CMatrix(const char *name, int rows, int cols) : + m_rows(rows), m_cols(cols) + { + strcpy(m_name, name); + m_pData = new double*[m_rows]; + for (int i = 0; i < m_rows; i++) + m_pData[i] = new double[m_cols]; + for (int i = 0; i < m_rows; i++) + { + for (int j = 0; j < m_cols; j++) + { + m_pData[i][j] = 0.0; + } + } + } + CMatrix(const CMatrix &other) + { + strcpy(m_name, other.m_name); + m_rows = other.m_rows; + m_cols = other.m_cols; + m_pData = new double*[m_rows]; + for (int i = 0; i < m_rows; i++) + m_pData[i] = new double[m_cols]; + for (int i = 0; i < m_rows; i++) + { + for (int j = 0; j < m_cols; j++) + { + m_pData[i][j] = other.m_pData[i][j]; + } + } + } + ~CMatrix() + { + for (int i = 0; i < m_rows; i++) + delete[] m_pData[i]; + delete[] m_pData; + m_rows = m_cols = 0; + } + void SetName(const char *name) + { + strcpy(m_name, name); + } + const char* GetName() const + { + return m_name; + } + void GetInput() + { + std::cin >> *this; + } + void FillSimulatedInput() + { + static int factor1 = 1, factor2 = 2; + std::cout << "\n\nEnter Input For Matrix : " << m_name << " Rows: " + << m_rows << " Cols: " << m_cols << "\n"; + for (int i = 0; i < m_rows; i++) + { + for (int j = 0; j < m_cols; j++) + { + std::cout << "Input For Row: " << i + 1 << " Col: " << j + + 1 << " = "; + int data = ((i + 1) * factor1) + (j + 1) * factor2; + m_pData[i][j] = data / 10.2; + std::cout << m_pData[i][j] << "\n"; + factor1 += (rand() % 4); + factor2 += (rand() % 3); + } + std::cout << "\n"; + } + std::cout << "\n"; + } + double Determinant() + { + double det = 0; + double **pd = m_pData; + switch (m_rows) + { + case 2: + { + det = pd[0][0] * pd[1][1] - pd[0][1] * pd[1][0]; + return det; + } + break; + case 3: + { + /*** + a b c + d e f + g h i + + a b c a b c + d e f d e f + g h i g h i + + + // det (A) = aei + bfg + cdh - afh - bdi - ceg. + ***/ + double a = pd[0][0]; + double b = pd[0][1]; + double c = pd[0][2]; + double d = pd[1][0]; + double e = pd[1][1]; + double f = pd[1][2]; + double g = pd[2][0]; + double h = pd[2][1]; + double i = pd[2][2]; + double det = (a * e * i + b * f * g + c * d * h); // - a*f*h - b*d*i - c*e*g); + det = det - a * f * h; + det = det - b * d * i; + det = det - c * e * g; + //std::cout << *this; + //std::cout << "deter: " << det << " \n"; + return det; + } + break; + case 4: + { + CMatrix *temp[4]; + for (int i = 0; i < 4; i++) + temp[i] = new CMatrix("", 3, 3); + for (int k = 0; k < 4; k++) + { + for (int i = 1; i < 4; i++) + { + int j1 = 0; + for (int j = 0; j < 4; j++) + { + if (k == j) + continue; + temp[k]->m_pData[i - 1][j1++] + = this->m_pData[i][j]; + } + } + } + double det = this->m_pData[0][0] * temp[0]->Determinant() + - this->m_pData[0][1] * temp[1]->Determinant() + + this->m_pData[0][2] * temp[2]->Determinant() + - this->m_pData[0][3] * temp[3]->Determinant(); + return det; + } + break; + case 5: + { + CMatrix *temp[5]; + for (int i = 0; i < 5; i++) + temp[i] = new CMatrix("", 4, 4); + for (int k = 0; k < 5; k++) + { + for (int i = 1; i < 5; i++) + { + int j1 = 0; + for (int j = 0; j < 5; j++) + { + if (k == j) + continue; + temp[k]->m_pData[i - 1][j1++] + = this->m_pData[i][j]; + } + } + } + double det = this->m_pData[0][0] * temp[0]->Determinant() + - this->m_pData[0][1] * temp[1]->Determinant() + + this->m_pData[0][2] * temp[2]->Determinant() + - this->m_pData[0][3] * temp[3]->Determinant() + + this->m_pData[0][4] * temp[4]->Determinant(); + return det; + } + case 6: + case 7: + case 8: + case 9: + case 10: + case 11: + case 12: + default: + { + int DIM = m_rows; + CMatrix **temp = new CMatrix*[DIM]; + for (int i = 0; i < DIM; i++) + temp[i] = new CMatrix("", DIM - 1, DIM - 1); + for (int k = 0; k < DIM; k++) + { + for (int i = 1; i < DIM; i++) + { + int j1 = 0; + for (int j = 0; j < DIM; j++) + { + if (k == j) + continue; + temp[k]->m_pData[i - 1][j1++] + = this->m_pData[i][j]; + } + } + } + double det = 0; + for (int k = 0; k < DIM; k++) + { + if ((k % 2) == 0) + det = det + (this->m_pData[0][k] + * temp[k]->Determinant()); + else + det = det - (this->m_pData[0][k] + * temp[k]->Determinant()); + } + for (int i = 0; i < DIM; i++) + delete temp[i]; + delete[] temp; + return det; + } + break; + } + } + CMatrix& operator =(const CMatrix &other) + { + if (this->m_rows != other.m_rows || this->m_cols != other.m_cols) + { + std::cout + << "WARNING: Assignment is taking place with by changing the number of rows and columns of the matrix"; + } + for (int i = 0; i < m_rows; i++) + delete[] m_pData[i]; + delete[] m_pData; + m_rows = m_cols = 0; + strcpy(m_name, other.m_name); + m_rows = other.m_rows; + m_cols = other.m_cols; + m_pData = new double*[m_rows]; + for (int i = 0; i < m_rows; i++) + m_pData[i] = new double[m_cols]; + for (int i = 0; i < m_rows; i++) + { + for (int j = 0; j < m_cols; j++) + { + m_pData[i][j] = other.m_pData[i][j]; + } + } + return *this; + } + CMatrix CoFactor() + { + CMatrix cofactor("COF", m_rows, m_cols); + if (m_rows != m_cols) + return cofactor; + if (m_rows < 2) + return cofactor; + else if (m_rows == 2) + { + cofactor.m_pData[0][0] = m_pData[1][1]; + cofactor.m_pData[0][1] = -m_pData[1][0]; + cofactor.m_pData[1][0] = -m_pData[0][1]; + cofactor.m_pData[1][1] = m_pData[0][0]; + return cofactor; + } + else if (m_rows >= 3) + { + int DIM = m_rows; + CMatrix ***temp = new CMatrix**[DIM]; + for (int i = 0; i < DIM; i++) + temp[i] = new CMatrix*[DIM]; + for (int i = 0; i < DIM; i++) + for (int j = 0; j < DIM; j++) + temp[i][j] = new CMatrix("", DIM - 1, DIM - 1); + for (int k1 = 0; k1 < DIM; k1++) + { + for (int k2 = 0; k2 < DIM; k2++) + { + int i1 = 0; + for (int i = 0; i < DIM; i++) + { + int j1 = 0; + for (int j = 0; j < DIM; j++) + { + if (k1 == i || k2 == j) + continue; + temp[k1][k2]->m_pData[i1][j1++] + = this->m_pData[i][j]; + } + if (k1 != i) + i1++; + } + } + } + bool flagPositive = true; + for (int k1 = 0; k1 < DIM; k1++) + { + flagPositive = ((k1 % 2) == 0); + for (int k2 = 0; k2 < DIM; k2++) + { + if (flagPositive == true) + { + cofactor.m_pData[k1][k2] + = temp[k1][k2]->Determinant(); + flagPositive = false; + } + else + { + cofactor.m_pData[k1][k2] + = -temp[k1][k2]->Determinant(); + flagPositive = true; + } + } + } + for (int i = 0; i < DIM; i++) + for (int j = 0; j < DIM; j++) + delete temp[i][j]; + for (int i = 0; i < DIM; i++) + delete[] temp[i]; + delete[] temp; + } + return cofactor; + } + CMatrix Adjoint() + { + CMatrix cofactor("COF", m_rows, m_cols); + CMatrix adj("ADJ", m_rows, m_cols); + if (m_rows != m_cols) + return adj; + cofactor = this->CoFactor(); + // adjoint is transpose of a cofactor of a matrix + for (int i = 0; i < m_rows; i++) + { + for (int j = 0; j < m_cols; j++) + { + adj.m_pData[j][i] = cofactor.m_pData[i][j]; + } + } + return adj; + } + CMatrix Transpose() + { + CMatrix trans("TR", m_cols, m_rows); + for (int i = 0; i < m_rows; i++) + { + for (int j = 0; j < m_cols; j++) + { + trans.m_pData[j][i] = m_pData[i][j]; + } + } + return trans; + } + CMatrix Inverse() + { + CMatrix cofactor("COF", m_rows, m_cols); + CMatrix inv("INV", m_rows, m_cols); + if (m_rows != m_cols) + return inv; + // to find out Determinant + double det = Determinant(); + cofactor = this->CoFactor(); + // inv = transpose of cofactor / Determinant + for (int i = 0; i < m_rows; i++) + { + for (int j = 0; j < m_cols; j++) + { + inv.m_pData[j][i] = cofactor.m_pData[i][j] / det; + } + } + return inv; + } + CMatrix operator +(const CMatrix &other) + { + if (this->m_rows != other.m_rows || this->m_cols != other.m_cols) + { + std::cout + << "Addition could not take place because number of rows and columns are different between the two matrices"; + return *this; + } + CMatrix result("", m_rows, m_cols); + for (int i = 0; i < m_rows; i++) + { + for (int j = 0; j < m_cols; j++) + { + result.m_pData[i][j] = this->m_pData[i][j] + + other.m_pData[i][j]; + } + } + return result; + } + CMatrix operator -(const CMatrix &other) + { + if (this->m_rows != other.m_rows || this->m_cols != other.m_cols) + { + std::cout + << "Subtraction could not take place because number of rows and columns are different between the two matrices"; + return *this; + } + CMatrix result("", m_rows, m_cols); + for (int i = 0; i < m_rows; i++) + { + for (int j = 0; j < m_cols; j++) + { + result.m_pData[i][j] = this->m_pData[i][j] + - other.m_pData[i][j]; + } + } + return result; + } + CMatrix operator *(const CMatrix &other) + { + if (this->m_cols != other.m_rows) + { + std::cout + << "Multiplication could not take place because number of columns of 1st Matrix and number of rows in 2nd Matrix are different"; + return *this; + } + CMatrix result("", this->m_rows, other.m_cols); + for (int i = 0; i < this->m_rows; i++) + { + for (int j = 0; j < other.m_cols; j++) + { + for (int k = 0; k < this->m_cols; k++) + { + result.m_pData[i][j] += this->m_pData[i][k] + * other.m_pData[k][j]; + } + } + } + return result; + } + bool operator ==(const CMatrix &other) + { + if (this->m_rows != other.m_rows || this->m_cols != other.m_cols) + { + std::cout + << "Comparision could not take place because number of rows and columns are different between the two matrices"; + return false; + } + CMatrix result("", m_rows, m_cols); + bool bEqual = true; + for (int i = 0; i < m_rows; i++) + { + for (int j = 0; j < m_cols; j++) + { + if (this->m_pData[i][j] != other.m_pData[i][j]) + bEqual = false; + } + } + return bEqual; + } + friend std::istream& operator >>(std::istream &is, CMatrix &m); + friend std::ostream& operator <<(std::ostream &os, const CMatrix &m); +}; +std::istream& operator >>(std::istream &is, CMatrix &m) +{ + std::cout << "\n\nEnter Input For Matrix : " << m.m_name << " Rows: " + << m.m_rows << " Cols: " << m.m_cols << "\n"; + for (int i = 0; i < m.m_rows; i++) + { + for (int j = 0; j < m.m_cols; j++) + { + std::cout << "Input For Row: " << i + 1 << " Col: " << j + 1 + << " = "; + is >> m.m_pData[i][j]; + } + std::cout << "\n"; + } + std::cout << "\n"; + return is; +} +std::ostream& operator <<(std::ostream &os, const CMatrix &m) +{ + os << "\n\nMatrix : " << m.m_name << " Rows: " << m.m_rows << " Cols: " + << m.m_cols << "\n\n"; + for (int i = 0; i < m.m_rows; i++) + { + os << " | "; + for (int j = 0; j < m.m_cols; j++) + { + char buf[32]; + double data = m.m_pData[i][j]; + if (m.m_pData[i][j] > -0.00001 && m.m_pData[i][j] < 0.00001) + data = 0; + sprintf(buf, "%10.2lf ", data); + os << buf; + } + os << "|\n"; + } + os << "\n\n"; + return os; +} +#endif +int main() +{ + CMatrix a("A", 6, 6); + CMatrix b("B", 6, 1); + a.FillSimulatedInput(); + b.FillSimulatedInput(); + std::cout << a << "\n Determinant : "; + std::cout << a.Determinant() << "\n"; + std::cout << b << "\n Determinant : "; + std::cout << b.Determinant() << "\n"; + CMatrix ainv = a.Inverse(); + CMatrix q = a * ainv; + q.SetName("A * A'"); + std::cout << q << "\n"; + CMatrix x = ainv * b; + x.SetName("X"); + std::cout << x << "\n"; + CMatrix y = a * x; // we will get B + y.SetName("Y"); + std::cout << y << "\n"; + return 0; +} + +/* + +Enter Input For Matrix : A Rows: 6 Cols: 6 +Input For Row: 1 Col: 1 = 0.294118 +Input For Row: 1 Col: 2 = 0.980392 +Input For Row: 1 Col: 3 = 1.86275 +Input For Row: 1 Col: 4 = 2.84314 +Input For Row: 1 Col: 5 = 3.62745 +Input For Row: 1 Col: 6 = 5.58824 + +Input For Row: 2 Col: 1 = 2.94118 +Input For Row: 2 Col: 2 = 4.11765 +Input For Row: 2 Col: 3 = 5.88235 +Input For Row: 2 Col: 4 = 8.43137 +Input For Row: 2 Col: 5 = 10.3922 +Input For Row: 2 Col: 6 = 12.3529 + +Input For Row: 3 Col: 1 = 8.13725 +Input For Row: 3 Col: 2 = 9.70588 +Input For Row: 3 Col: 3 = 12.0588 +Input For Row: 3 Col: 4 = 15.098 +Input For Row: 3 Col: 5 = 17.8431 +Input For Row: 3 Col: 6 = 20.5882 + +Input For Row: 4 Col: 1 = 14.902 +Input For Row: 4 Col: 2 = 18.2353 +Input For Row: 4 Col: 3 = 21.4706 +Input For Row: 4 Col: 4 = 24.7059 +Input For Row: 4 Col: 5 = 27.549 +Input For Row: 4 Col: 6 = 31.1765 + +Input For Row: 5 Col: 1 = 24.902 +Input For Row: 5 Col: 2 = 27.9412 +Input For Row: 5 Col: 3 = 32.451 +Input For Row: 5 Col: 4 = 36.0784 +Input For Row: 5 Col: 5 = 39.7059 +Input For Row: 5 Col: 6 = 43.9216 + +Input For Row: 6 Col: 1 = 36.3725 +Input For Row: 6 Col: 2 = 39.6078 +Input For Row: 6 Col: 3 = 43.8235 +Input For Row: 6 Col: 4 = 47.2549 +Input For Row: 6 Col: 5 = 51.3725 +Input For Row: 6 Col: 6 = 55.2941 + + + + +Enter Input For Matrix : B Rows: 6 Cols: 1 +Input For Row: 1 Col: 1 = 9.41176 + +Input For Row: 2 Col: 1 = 15.7843 + +Input For Row: 3 Col: 1 = 22.7451 + +Input For Row: 4 Col: 1 = 29.902 + +Input For Row: 5 Col: 1 = 37.1569 + +Input For Row: 6 Col: 1 = 44.6078 + + + + +Matrix : A Rows: 6 Cols: 6 + + | 0.29 0.98 1.86 2.84 3.63 5.59 | + | 2.94 4.12 5.88 8.43 10.39 12.35 | + | 8.14 9.71 12.06 15.10 17.84 20.59 | + | 14.90 18.24 21.47 24.71 27.55 31.18 | + | 24.90 27.94 32.45 36.08 39.71 43.92 | + | 36.37 39.61 43.82 47.25 51.37 55.29 | + + + + Determinant : -11.9339 + + +Matrix : B Rows: 6 Cols: 1 + + | 9.41 | + | 15.78 | + | 22.75 | + | 29.90 | + | 37.16 | + | 44.61 | + + + + Determinant : -1.#IND + + +Matrix : A * A' Rows: 6 Cols: 6 + + | 1.00 0.00 0.00 0.00 0.00 0.00 | + | 0.00 1.00 0.00 0.00 0.00 0.00 | + | 0.00 0.00 1.00 0.00 0.00 0.00 | + | 0.00 0.00 0.00 1.00 0.00 0.00 | + | 0.00 0.00 0.00 0.00 1.00 0.00 | + | 0.00 0.00 0.00 0.00 0.00 1.00 | + + + + + +Matrix : X Rows: 6 Cols: 1 + + | 0.82 | + | 3.47 | + | -9.38 | + | 7.71 | + | -5.76 | + | 3.98 | + + + + + +Matrix : Y Rows: 6 Cols: 1 + + | 9.41 | + | 15.78 | + | 22.75 | + | 29.90 | + | 37.16 | + | 44.61 | \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Solve the 0-1 Knapsack Problem.cpp b/c++/11_Numerical_Problems/C++ Program to Solve the 0-1 Knapsack Problem.cpp new file mode 100644 index 0000000..4c43e45 --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Solve the 0-1 Knapsack Problem.cpp @@ -0,0 +1,61 @@ +/*This is a C++ Program to solve 0-1 knapsack problem. The knapsack problem or rucksack problem is a problem in combinatorial optimization: Given a set of items, each with a mass and a value, determine the number of each item to include in a collection so that the total weight is less than or equal to a given limit and the total value is as large as possible. It derives its name from the problem faced by someone who is constrained by a fixed-size knapsack and must fill it with the most valuable items.*/ + +#include +#include +#include + +using namespace std; + +// A utility function that returns maximum of two integers +int max(int a, int b) +{ + return (a > b) ? a : b; +} + +// Returns the maximum value that can be put in a knapsack of capacity W +int knapSack(int W, int wt[], int val[], int n) +{ + // Base Case + if (n == 0 || W == 0) + return 0; + // If weight of the nth item is more than Knapsack capacity W, then + // this item cannot be included in the optimal solution + if (wt[n - 1] > W) + return knapSack(W, wt, val, n - 1); + // Return the maximum of two cases: (1) nth item included (2) not included + else + return max(val[n - 1] + knapSack(W - wt[n - 1], wt, val, n - 1), + knapSack(W, wt, val, n - 1)); +} + +// Driver program to test above function +int main() +{ + cout << "Enter the number of items in a Knapsack:"; + int n, W; + cin >> n; + int val[n], wt[n]; + for (int i = 0; i < n; i++) + { + cout << "Enter value and weight for item " << i << ":"; + cin >> val[i]; + cin >> wt[i]; + } + // int val[] = { 60, 100, 120 }; + // int wt[] = { 10, 20, 30 }; + // int W = 50; + cout << "Enter the capacity of knapsack"; + cin >> W; + cout << knapSack(W, wt, val, n); + return 0; +} + +/* +Enter the number of items in a Knapsack:5 +Enter value and weight for item 0:11 111 +Enter value and weight for item 1:22 121 +Enter value and weight for item 2:33 131 +Enter value and weight for item 3:44 141 +Enter value and weight for item 4:55 151 +Enter the capacity of knapsack 300 +99 \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Solve the Fractional Knapsack Problem.cpp b/c++/11_Numerical_Problems/C++ Program to Solve the Fractional Knapsack Problem.cpp new file mode 100644 index 0000000..1dd73ef --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Solve the Fractional Knapsack Problem.cpp @@ -0,0 +1,78 @@ +/*This is a C++ Program to solve fractional knapsack. The knapsack problem or rucksack problem is a problem in combinatorial optimization: Given a set of items, each with a mass and a value, determine the number of each item to include in a collection so that the total weight is less than or equal to a given limit and the total value is as large as possible. It derives its name from the problem faced by someone who is constrained by a fixed-size knapsack and must fill it with the most valuable items.*/ + +/* program to implement fractional knapsack problem using greedy programming */ +#include +using namespace std; +int main() +{ + int array[2][100], n, w, i, curw, used[100], maxi = -1, totalprofit = 0; + //input number of objects + cout << "Enter number of objects: "; + cin >> n; + //input max weight of knapsack + cout << "Enter the weight of the knapsack: "; + cin >> w; + /* Array's first row is to store weights + second row is to store profits */ + for (i = 0; i < n; i++) + { + cin >> array[0][i] >> array[1][i]; + } + for (i = 0; i < n; i++) + { + used[i] = 0; + } + curw = w; + //loop until knapsack is full + while (curw >= 0) + { + maxi = -1; + //loop to find max profit object + for (i = 0; i < n; i++) + { + if ((used[i] == 0) && ((maxi == -1) || (((float) array[1][i] + / (float) array[0][i]) > ((float) array[1][maxi] + / (float) array[0][maxi])))) + { + maxi = i; + } + } + used[maxi] = 1; + //decrease current wight + curw -= array[0][maxi]; + //increase total profit + totalprofit += array[1][maxi]; + if (curw >= 0) + { + cout << "\nAdded object " << maxi + 1 << " Weight: " + << array[0][maxi] << " Profit: " << array[1][maxi] + << " completely in the bag, Space left: " << curw; + } + else + { + cout << "\nAdded object " << maxi + 1 << " Weight: " + << (array[0][maxi] + curw) << " Profit: " + << (array[1][maxi] / array[0][maxi]) * (array[0][maxi] + + curw) << " partially in the bag, Space left: 0" + << " Weight added is: " << curw + array[0][maxi]; + totalprofit -= array[1][maxi]; + totalprofit += ((array[1][maxi] / array[0][maxi]) * (array[0][maxi] + + curw)); + } + } + //print total worth of objects filled in knapsack + cout << "\nBags filled with objects worth: " << totalprofit; + return 0; +} + +/* +Enter number of objects: 3 +Enter the weight of the knapsack: 50 +10 60 +20 100 +30 120 + +Added object 1 Weight: 10 Profit: 60 completely in the bag, Space left: 40 +Added object 2 Weight: 20 Profit: 100 completely in the bag, Space left: 20 +Added object 3 Weight: 20 Profit: 80 partially in the bag, Space left: 0 Weight added is: 20 +Bags filled with objects worth: 240 \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to Use rand and srand Functions.cpp b/c++/11_Numerical_Problems/C++ Program to Use rand and srand Functions.cpp new file mode 100644 index 0000000..f84ec50 --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to Use rand and srand Functions.cpp @@ -0,0 +1,20 @@ +#include +#include +#include + +using namespace std; + +int main(int argc, char **argv) +{ + cout << "First number: " << rand() % 100; + srand(time(NULL)); + cout << "\nRandom number: " << rand() % 100; + srand(1); + cout << "\nAgain the first number: " << rand() % 100; + return 0; +} + +/* +First number: 41 +Random number: 98 +Again the first number: 41 \ No newline at end of file diff --git a/c++/11_Numerical_Problems/C++ Program to implement Gauss Jordan Elimination algorithm..cpp b/c++/11_Numerical_Problems/C++ Program to implement Gauss Jordan Elimination algorithm..cpp new file mode 100644 index 0000000..0444346 --- /dev/null +++ b/c++/11_Numerical_Problems/C++ Program to implement Gauss Jordan Elimination algorithm..cpp @@ -0,0 +1,82 @@ +/*/This is a C++ Program to implement Gauss Jordan Elimination algorithm. In linear algebra, Gaussian elimination (also known as row reduction) is an algorithm for solving systems of linear equations. It is usually understood as a sequence of operations performed on the associated matrix of coefficients. This method can also be used to find the rank of a matrix, to calculate the determinant of a matrix, and to calculate the inverse of an invertible square matrix.*/ + + +#include +#include + +using namespace std; + +int main() +{ + int i, j, k, n; + float a[10][10] = { 0 }, d; + cout << "No of equations ? "; + cin >> n; + cout << "Read all coefficients of matrix with b matrix too " << endl; + for (i = 1; i <= n; i++) + for (j = 1; j <= n; j++) + cin >> a[i][j]; + for (i = 1; i <= n; i++) + for (j = 1; j <= 2 * n; j++) + if (j == (i + n)) + a[i][j] = 1; + /************** partial pivoting **************/ + for (i = n; i > 1; i--) + { + if (a[i - 1][1] < a[i][1]) + for (j = 1; j <= n * 2; j++) + { + d = a[i][j]; + a[i][j] = a[i - 1][j]; + a[i - 1][j] = d; + } + } + cout << "pivoted output: " << endl; + for (i = 1; i <= n; i++) + { + for (j = 1; j <= n * 2; j++) + cout << a[i][j] << " "; + cout << endl; + } + /********** reducing to diagonal matrix ***********/ + for (i = 1; i <= n; i++) + { + for (j = 1; j <= n * 2; j++) + if (j != i) + { + d = a[j][i] / a[i][i]; + for (k = 1; k <= n * 2; k++) + a[j][k] -= a[i][k] * d; + } + } + /************** reducing to unit matrix *************/ + for (i = 1; i <= n; i++) + { + d = a[i][i]; + for (j = 1; j <= n * 2; j++) + a[i][j] = a[i][j] / d; + } + cout << "your solutions: " << endl; + for (i = 1; i <= n; i++) + { + for (j = n + 1; j <= n * 2; j++) + cout << a[i][j] << " "; + cout << endl; + } + getch(); + return 0; +} + +/*No of equations ? 3 +Read all coefficients of matrix with b matrix too +2 3 4 +5 6 3 +9 8 6 +pivoted output: +9 8 6 0 0 1 +2 3 4 1 0 0 +5 6 3 0 1 0 +your solutions: +-0.292683 -0.341463 0.365854 +0.0731707 0.585366 -0.341463 +0.341463 -0.268293 0.0731708*/ \ No newline at end of file diff --git a/c++/11_Sets_&_Strings/C++ Program to Construct DFA from NFA.cpp b/c++/11_Sets_&_Strings/C++ Program to Construct DFA from NFA.cpp new file mode 100644 index 0000000..7131de3 --- /dev/null +++ b/c++/11_Sets_&_Strings/C++ Program to Construct DFA from NFA.cpp @@ -0,0 +1,189 @@ +/*This is a C++ Program to convert NFA to DFA. A DFA (Deterministic Finite Automaton) is a finite state machine where from each state and a given input symbol, the next possible state is uniquely determined. On the other hand, an NFA (Non-Deterministic Finite Automaton) can move to several possible next states from a given state and a given input symbol. However, this does not add any more power to the machine. It still accepts the same set of languages, namely the regular languages. It is possible to convert an NFA to an equivalent DFA using the powerset construction. +The intuition behind this scheme is that an NFA can be in several possible states at any time. We can simulate it with a DFA whose states correspond to sets of states of the underlying NFA.*/ + +#include +#include +#include +#include +#include +#include +#include +#include +#include +#include +#define MAX_NFA_STATES 10 +#define MAX_ALPHABET_SIZE 10 +using namespace std; +// Representation of an NFA state +class NFAstate +{ +public: + int transitions[MAX_ALPHABET_SIZE][MAX_NFA_STATES]; + NFAstate() + { + for (int i = 0; i < MAX_ALPHABET_SIZE; i++) + for (int j = 0; j < MAX_NFA_STATES; j++) + transitions[i][j] = -1; + } +}*NFAstates; +// Representation of a DFA state +struct DFAstate +{ + bool finalState; + bitset constituentNFAstates; + bitset transitions[MAX_ALPHABET_SIZE]; + int symbolicTransitions[MAX_ALPHABET_SIZE]; +}; +set NFA_finalStates; +vector DFA_finalStates; +vector DFAstates; +queue incompleteDFAstates; +int N, M; // N -> No. of stattes, M -> Size of input alphabet +// finds the epsilon closure of the NFA state "state" and stores it into "closure" +void epsilonClosure(int state, bitset &closure) +{ + for (int i = 0; i < N && NFAstates[state].transitions[0][i] != -1; i++) + if (closure[NFAstates[state].transitions[0][i]] == 0) + { + closure[NFAstates[state].transitions[0][i]] = 1; + epsilonClosure(NFAstates[state].transitions[0][i], closure); + } +} +// finds the epsilon closure of a set of NFA states "state" and stores it into "closure" +void epsilonClosure(bitset state, + bitset &closure) +{ + for (int i = 0; i < N; i++) + if (state[i] == 1) + epsilonClosure(i, closure); +} +// returns a bitset representing the set of states the NFA could be in after moving +// from state X on input symbol A +void NFAmove(int X, int A, bitset &Y) +{ + for (int i = 0; i < N && NFAstates[X].transitions[A][i] != -1; i++) + Y[NFAstates[X].transitions[A][i]] = 1; +} +// returns a bitset representing the set of states the NFA could be in after moving +// from the set of states X on input symbol A +void NFAmove(bitset X, int A, bitset &Y) +{ + for (int i = 0; i < N; i++) + if (X[i] == 1) + NFAmove(i, A, Y); +} +int main() +{ + int i, j, X, Y, A, T, F, D; + // read in the underlying NFA + ifstream fin("NFA.txt"); + fin >> N >> M; + NFAstates = new NFAstate[N]; + fin >> F; + for (i = 0; i < F; i++) + { + fin >> X; + NFA_finalStates.insert(X); + } + fin >> T; + while (T--) + { + fin >> X >> A >> Y; + for (i = 0; i < Y; i++) + { + fin >> j; + NFAstates[X].transitions[A][i] = j; + } + } + fin.close(); + // construct the corresponding DFA + D = 1; + DFAstates.push_back(new DFAstate); + DFAstates[0]->constituentNFAstates[0] = 1; + epsilonClosure(0, DFAstates[0]->constituentNFAstates); + for (j = 0; j < N; j++) + if (DFAstates[0]->constituentNFAstates[j] == 1 && NFA_finalStates.find( + j) != NFA_finalStates.end()) + { + DFAstates[0]->finalState = true; + DFA_finalStates.push_back(0); + break; + } + incompleteDFAstates.push(0); + while (!incompleteDFAstates.empty()) + { + X = incompleteDFAstates.front(); + incompleteDFAstates.pop(); + for (i = 1; i <= M; i++) + { + NFAmove(DFAstates[X]->constituentNFAstates, i, + DFAstates[X]->transitions[i]); + epsilonClosure(DFAstates[X]->transitions[i], + DFAstates[X]->transitions[i]); + for (j = 0; j < D; j++) + if (DFAstates[X]->transitions[i] + == DFAstates[j]->constituentNFAstates) + { + DFAstates[X]->symbolicTransitions[i] = j; + break; + } + if (j == D) + { + DFAstates[X]->symbolicTransitions[i] = D; + DFAstates.push_back(new DFAstate); + DFAstates[D]->constituentNFAstates + = DFAstates[X]->transitions[i]; + for (j = 0; j < N; j++) + if (DFAstates[D]->constituentNFAstates[j] == 1 + && NFA_finalStates.find(j) != NFA_finalStates.end()) + { + DFAstates[D]->finalState = true; + DFA_finalStates.push_back(D); + break; + } + incompleteDFAstates.push(D); + D++; + } + } + } + // write out the corresponding DFA + ofstream fout("DFA.txt"); + fout << D << " " << M << "\n" << DFA_finalStates.size(); + for (vector::iterator it = DFA_finalStates.begin(); it + != DFA_finalStates.end(); it++) + fout << " " << *it; + fout << "\n"; + for (i = 0; i < D; i++) + { + for (j = 1; j <= M; j++) + fout << i << " " << j << " " + << DFAstates[i]->symbolicTransitions[j] << "\n"; + } + fout.close(); + return 0; +} + +/* + +Input file +NFA.txt +4 2 +2 0 1 +4 +0 1 2 1 2 +1 1 2 1 2 +2 2 2 1 3 +3 1 2 1 2 + +Output file +DFA.txt +4 2 +3 0 1 3 +0 1 1 +0 2 2 +1 1 1 +1 2 3 +2 1 2 +2 2 2 +3 1 1 +3 2 2 diff --git a/c++/11_Sets_&_Strings/C++ Program to Decode a Message Encoded Using Playfair Cipher.cpp b/c++/11_Sets_&_Strings/C++ Program to Decode a Message Encoded Using Playfair Cipher.cpp new file mode 100644 index 0000000..910cffc --- /dev/null +++ b/c++/11_Sets_&_Strings/C++ Program to Decode a Message Encoded Using Playfair Cipher.cpp @@ -0,0 +1,121 @@ +/* + * C++ Program to Decode a Message Encoded Using Playfair Cipher + This C++ program decodes any message encoded using the technique of traditional playfair cipher. The Playfair cipher or Playfair square is a manual symmetric encryption technique and was the first literal digraph substitution cipher. Input is not case sensitive and works only for characters from ‘a’ to ‘z’ and ‘A’ to ‘Z’. + */ +#include +#include +using namespace std; + +const char encoder[5][5] = {{'A','B','C','D','E'}, + {'F','G','H','I','K'}, + {'L','M','N','O','P'}, + {'Q','R','S','T','U'}, + {'V','W','X','Y','Z'} +}; + +void input_string(vector& a) +{ + char c; + while (1) + { + c=getchar(); + if (c >= 97 && c <= 122) + c -= 32; + if (c == '\n') + break; + else if (c==' ') + continue; + else if (c == 'J') + a.push_back('I'); + a.push_back(c); + } + return; +} + + + +void get_pos(char p, int& r, int& c) +{ + if (p < 'J') + { + r = (p - 65) / 5; + c = (p - 65) % 5; + } + else if (p > 'J') + { + r = (p - 66) / 5; + c = (p - 66) % 5; + } + return; +} + +void same_row(int r, vector& code, int c1, int c2) +{ + code.push_back(encoder[r][(c1 + 4) % 5]); + code.push_back(encoder[r][(c2 + 4) % 5]); + return; +} + +void same_column(int c, vector& code, int r1, int r2) +{ + code.push_back(encoder[(r1 + 4) % 5][c]); + code.push_back(encoder[(r2 + 4) % 5][c]); + return; +} + +void diff_col_row(int r1, int c1, vector& code, int r2, int c2) +{ + code.push_back(encoder[r1][c2]); + code.push_back(encoder[r2][c1]); + return; +} + + +void encode(vector msgx, int len) +{ + vector code; + int i = 0, j = 0; + int r1, c1, r2, c2; + while (i < len) + { + get_pos(msgx[i], r1, c1); + i++; + get_pos(msgx[i], r2, c2); + if (r1 == r2) + { + same_row(r1, code, c1, c2); + } + else if (c1 == c2) + { + same_column(c1, code, r1, r2); + } + else + { + diff_col_row(r1, c1, code, r2, c2); + } + i++; + } + cout<<"\nCODE: "; + for (j = 0; j < code.size(); j++) + { + if (code[j] == 'X') + continue; + cout< msg; + std::cout<<"Enter the Encrypted Message:"; + input_string(msg); + int len=msg.size(); + encode(msg,len); + return 0; +} + +/* +Enter the Encrypted Message:CBNVMPPO +CODE: BALLOON \ No newline at end of file diff --git a/c++/11_Sets_&_Strings/C++ Program to Encode a Message Using Playfair Cipher.cpp b/c++/11_Sets_&_Strings/C++ Program to Encode a Message Using Playfair Cipher.cpp new file mode 100644 index 0000000..4e9ae5f --- /dev/null +++ b/c++/11_Sets_&_Strings/C++ Program to Encode a Message Using Playfair Cipher.cpp @@ -0,0 +1,158 @@ +/* + * C++ Program to Encode a Message Using Playfair Cipher + */ +#include +#include +using namespace std; + +void get_pos(char, int&, int&); +void same_row(int, vector&, int, int); +void same_column(int, vector&, int, int); +void diff_col_row(int, int, vector&, int, int); +void encode(vector, int); +void get_input(vector&); +void convert_string(vector&, vector&); + +const char encoder[5][5]= {{'A','B','C','D','E'}, + {'F','G','H','I','K'}, + {'L','M','N','O','P'}, + {'Q','R','S','T','U'}, + {'V','W','X','Y','Z'} +}; + +void get_pos(char p, int& r, int& c) +{ + if (p < 'J') + { + r = (p - 65) / 5; + c = (p - 65) % 5; + } + else if (p > 'J') + { + r = (p - 66) / 5; + c = (p - 66) % 5; + } + return; +} + +void same_row(int r, vector& code, int c1, int c2) +{ + code.push_back(encoder[r][(c1 + 1) % 5]); + code.push_back(encoder[r][(c2 + 1) % 5]); + return; +} + +void same_column(int c, vector& code, int r1, int r2) +{ + code.push_back(encoder[(r1 + 1) % 5][c]); + code.push_back(encoder[(r2 + 1) % 5][c]); + return; +} + +void diff_col_row(int r1, int c1, vector& code, int r2, int c2) +{ + code.push_back(encoder[r1][c2]); + code.push_back(encoder[r2][c1]); + return; +} + +void encode(vector msgx, int len) +{ + vector code; + int i = 0, j = 0; + int r1, c1, r2, c2; + while (i < len) + { + get_pos(msgx[i], r1, c1); + i++; + get_pos(msgx[i], r2, c2); + if (r1 == r2) + { + same_row(r1, code, c1, c2); + } + else if (c1 == c2) + { + same_column(c1, code, r1, r2); + } + else + { + diff_col_row(r1, c1, code, r2, c2); + } + i++; + } + cout<<"\nCODE: "; + for (j = 0; j < code.size(); j++) + { + cout<& a) +{ + char c; + while (1) + { + c = getchar(); + if (c >= 97 && c <= 122) + c- =32; + if (c == '\n') + break; + else if (c==' ') + continue; + else if (c == 'J') + a.push_back('I'); + a.push_back(c); + } + return; +} + +void convert_string(vector& msg, vector& msgx) +{ + int i, j; + i = j = 0; + while (i < msg.size()) + { + msgx.push_back(msg[i]); + i++; + if (i == msg.size()) + { + msgx.push_back('X'); + break; + } + if (msg[i] == msgx[j]) + { + msgx.push_back('X'); + j++; + } + else if(msg[i] != msgx[j]) + { + j++; + msgx.push_back(msg[i]); + i+ = 1; + } + j++; + } +} + +int main() +{ + vector msg; + vector msgx; + int i, j; + cout<<"Enter Message to Encrypt:"; + get_input(msg); + convert_string(msg, msgx); + int len = msgx.size(); + /* + cout<<"\n\n"; + for (i = 0;i < len;i++) + cout< +#include +using namespace std; + +// A utility function to find maximum of two integers +int max(int a, int b) +{ + return (a > b)? a : b; +} + +/* Returns length of longest common substring of X[0..m-1] and Y[0..n-1] */ +int LCSubStr(char *X, char *Y, int m, int n) +{ + int LCSuff[m + 1][n + 1]; + int result = 0; + for (int i = 0; i <= m; i++) + { + for (int j=0; j<=n; j++) + { + if (i == 0 || j == 0) + LCSuff[i][j] = 0; + else if (X[i-1] == Y[j-1]) + { + LCSuff[i][j] = LCSuff[i-1][j-1] + 1; + result = max(result, LCSuff[i][j]); + } + else LCSuff[i][j] = 0; + } + } + return result; +} + +/*Main */ +int main() +{ + char X[] = "Sanfoundry"; + char Y[] = "foundation"; + int m = strlen(X); + int n = strlen(Y); + cout << "Length of Longest Common Substring is " << LCSubStr(X, Y, m, n); + return 0; +} + +/* +Length of Longest Common Substring is 5 \ No newline at end of file diff --git a/c++/11_Sets_&_Strings/C++ Program to Find the Longest Increasing Subsequence of a Given Sequence.cpp b/c++/11_Sets_&_Strings/C++ Program to Find the Longest Increasing Subsequence of a Given Sequence.cpp new file mode 100644 index 0000000..7789c86 --- /dev/null +++ b/c++/11_Sets_&_Strings/C++ Program to Find the Longest Increasing Subsequence of a Given Sequence.cpp @@ -0,0 +1,59 @@ +/*This is a C++ Program to implement LCS. The longest common subsequence (LCS) problem is to find the longest subsequence common to all sequences in a set of sequences (often just two). (Note that a subsequence is different from a substring, for the terms of the former need not be consecutive terms of the original sequence.) It is a classic computer science problem, the basis of data comparison programs such as the diff utility, and has applications in bioinformatics.*/ + +#include +#include +#include + +using namespace std; + +#define ARRAY_SIZE(A) sizeof(A)/sizeof(A[0]) +// Binary search (note boundaries in the caller) +// A[] is ceilIndex in the caller +int CeilIndex(int A[], int l, int r, int key) +{ + int m; + while (r - l > 1) + { + m = l + (r - l) / 2; + (A[m] >= key ? r : l) = m; // ternary expression returns an l-value + } + return r; +} + +int LongestIncreasingSubsequenceLength(int A[], int size) +{ + // Add boundary case, when array size is one + int *tailTable = new int[size]; + int len; // always points empty slot + memset(tailTable, 0, sizeof(tailTable[0]) * size); + tailTable[0] = A[0]; + len = 1; + for (int i = 1; i < size; i++) + { + if (A[i] < tailTable[0]) + // new smallest value + tailTable[0] = A[i]; + else if (A[i] > tailTable[len - 1]) + // A[i] wants to extend largest subsequence + tailTable[len++] = A[i]; + else + // A[i] wants to be current end candidate of an existing subsequence + // It will replace ceil value in tailTable + tailTable[CeilIndex(tailTable, -1, len - 1, A[i])] = A[i]; + } + delete[] tailTable; + return len; +} + +int main() +{ + int A[] = { 2, 5, 3, 7, 11, 8, 10, 13, 6 }; + int n = ARRAY_SIZE(A); + printf("Length of Longest Increasing Subsequence is %d\n", + LongestIncreasingSubsequenceLength(A, n)); + return 0; +} + +/* + +Length of Longest Increasing Subsequence is 6 \ No newline at end of file diff --git a/c++/11_Sets_&_Strings/C++ Program to Implement Affine Cipher.cpp b/c++/11_Sets_&_Strings/C++ Program to Implement Affine Cipher.cpp new file mode 100644 index 0000000..4ee3bed --- /dev/null +++ b/c++/11_Sets_&_Strings/C++ Program to Implement Affine Cipher.cpp @@ -0,0 +1,57 @@ +/*This is a C++ Program to implement Affine Cipher. The affine cipher is a type of monoalphabetic substitution cipher, wherein each letter in an alphabet is mapped to its numeric equivalent, encrypted using a simple mathematical function, and converted back to a letter. The formula used means that each letter encrypts to one other letter, and back again, meaning the cipher is essentially a standard substitution cipher with a rule governing which letter goes to which. As such, it has the weaknesses of all substitution ciphers. Each letter is enciphered with the function (ax+b)mod(26), where b is the magnitude of the shift.*/ + +#include +#include +#include +using namespace std; +string encryptionMessage(string Msg) +{ + string CTxt = ""; + int a = 3; + int b = 6; + for (int i = 0; i < Msg.length(); i++) + { + CTxt = CTxt + (char) ((((a * Msg[i]) + b) % 26) + 65); + } + return CTxt; +} + +string decryptionMessage(string CTxt) +{ + string Msg = ""; + int a = 3; + int b = 6; + int a_inv = 0; + int flag = 0; + for (int i = 0; i < 26; i++) + { + flag = (a * i) % 26; + if (flag == 1) + { + a_inv = i; + } + } + for (int i = 0; i < CTxt.length(); i++) + { + Msg = Msg + (char) (((a_inv * ((CTxt[i] - b)) % 26)) + 65); + } + return Msg; +} +int main(int argc, char **argv) +{ + cout << "Enter the message: "; + string message; + cin >> message; + cout << "Message is :" << message; + cout << "\nEncrypted Message is : " << encryptionMessage(message); + cout << "\nDecrypted Message is: " << decryptionMessage( + encryptionMessage(message)); +} + + +/* + +Enter the message: SANFOUNDRY +Message is :SANFOUNDRY +Encrypted Message is : VTGIJBGCSN +Decrypted Message is: SANFOUNDRY \ No newline at end of file diff --git a/c++/11_Sets_&_Strings/C++ Program to Implement Aho-Corasick Algorithm for String Matching.cpp b/c++/11_Sets_&_Strings/C++ Program to Implement Aho-Corasick Algorithm for String Matching.cpp new file mode 100644 index 0000000..243c99a --- /dev/null +++ b/c++/11_Sets_&_Strings/C++ Program to Implement Aho-Corasick Algorithm for String Matching.cpp @@ -0,0 +1,146 @@ +/*n computer science, the Aho–Corasick string matching algorithm is a string searching algorithm, it is a kind of dictionary-matching algorithm that locates elements of a finite set of strings (the “dictionary”) within an input text. It matches all patterns simultaneously. The complexity of the algorithm is linear in the length of the patterns plus the length of the searched text plus the number of output matches. Note that because all matches are found, there can be a quadratic number of matches if every substring matches (e.g. dictionary = a, aa, aaa, aaaa and input string is aaaa).*/ + +using namespace std; +#include +#include +#include +#include +#include +#include +#include +#include +#include +#include +#include +#include +#include +#include +#include +#include +#include +#include +#include +#include + +#define foreach(x, v) for (typeof (v).begin() x=(v).begin(); x !=(v).end(); ++x) +#define For(i, a, b) for (int i=(a); i<(b); ++i) +#define D(x) cout << #x " is " << x << endl + +const int MAXS = 6 * 50 + 10; // Max number of states in the matching machine. +// Should be equal to the sum of the length of all keywords. + +const int MAXC = 26; // Number of characters in the alphabet. + +int out[MAXS]; // Output for each state, as a bitwise mask. +int f[MAXS]; // Failure function +int g[MAXS][MAXC]; // Goto function, or -1 if fail. + +int buildMatchingMachine(const vector &words, char lowestChar = 'a', + char highestChar = 'z') +{ + memset(out, 0, sizeof out); + memset(f, -1, sizeof f); + memset(g, -1, sizeof g); + int states = 1; // Initially, we just have the 0 state + for (int i = 0; i < words.size(); ++i) + { + const string &keyword = words[i]; + int currentState = 0; + for (int j = 0; j < keyword.size(); ++j) + { + int c = keyword[j] - lowestChar; + if (g[currentState][c] == -1) + { + // Allocate a new node + g[currentState][c] = states++; + } + currentState = g[currentState][c]; + } + out[currentState] |= (1 << i); // There's a match of keywords[i] at node currentState. + } + // State 0 should have an outgoing edge for all characters. + for (int c = 0; c < MAXC; ++c) + { + if (g[0][c] == -1) + { + g[0][c] = 0; + } + } + // Now, let's build the failure function + queue q; + for (int c = 0; c <= highestChar - lowestChar; ++c) + { + // Iterate over every possible input + // All nodes s of depth 1 have f[s] = 0 + if (g[0][c] != -1 and g[0][c] != 0) + { + f[g[0][c]] = 0; + q.push(g[0][c]); + } + } + while (q.size()) + { + int state = q.front(); + q.pop(); + for (int c = 0; c <= highestChar - lowestChar; ++c) + { + if (g[state][c] != -1) + { + int failure = f[state]; + while (g[failure][c] == -1) + { + failure = f[failure]; + } + failure = g[failure][c]; + f[g[state][c]] = failure; + out[g[state][c]] |= out[failure]; // Merge out values + q.push(g[state][c]); + } + } + } + return states; +} +int findNextState(int currentState, char nextInput, char lowestChar = 'a') +{ + int answer = currentState; + int c = nextInput - lowestChar; + while (g[answer][c] == -1) + answer = f[answer]; + return g[answer][c]; +} + +int main() +{ + vector keywords; + keywords.push_back("he"); + keywords.push_back("she"); + keywords.push_back("hers"); + keywords.push_back("his"); + string text = "ahishers"; + buildMatchingMachine(keywords, 'a', 'z'); + int currentState = 0; + for (int i = 0; i < text.size(); ++i) + { + currentState = findNextState(currentState, text[i], 'a'); + if (out[currentState] == 0) + continue; // Nothing new, let's move on to the next character. + for (int j = 0; j < keywords.size(); ++j) + { + if (out[currentState] & (1 << j)) + { + // Matched keywords[j] + cout << "Keyword " << keywords[j] << " appears from " << i + - keywords[j].size() + 1 << " to " << i << endl; + } + } + } + return 0; +} + +/* + + +Keyword his appears from 1 to 3 +Keyword he appears from 4 to 5 +Keyword she appears from 3 to 5 +Keyword hers appears from 4 to 7 \ No newline at end of file diff --git a/c++/11_Sets_&_Strings/C++ Program to Implement Bitap Algorithm for String Matching.cpp b/c++/11_Sets_&_Strings/C++ Program to Implement Bitap Algorithm for String Matching.cpp new file mode 100644 index 0000000..ec85825 --- /dev/null +++ b/c++/11_Sets_&_Strings/C++ Program to Implement Bitap Algorithm for String Matching.cpp @@ -0,0 +1,64 @@ +/*This is a C++ Program to Implement Bitap Algorithm. The bitap algorithm (also known as the shift-or, shift-and or Baeza-Yates–Gonnet algorithm) is an approximate string matching algorithm. The algorithm tells whether a given text contains a substring which is “approximately equal” to a given pattern, where approximate equality is defined in terms of Levenshtein distance — if the substring and pattern are within a given distance k of each other, then the algorithm considers them equal. The algorithm begins by precomputing a set of bitmasks containing one bit for each element of the pattern. Then it is able to do most of the work with bitwise operations, which are extremely fast.*/ + +#include +#include +#include + +using namespace std; +int bitap_search(string text, string pattern) +{ + int m = pattern.length(); + long pattern_mask[256]; + /** Initialize the bit array R **/ + long R = ~1; + if (m == 0) + return -1; + if (m > 63) + { + cout<<"Pattern is too long!"; + return -1; + } + /** Initialize the pattern bitmasks **/ + for (int i = 0; i <= 255; ++i) + pattern_mask[i] = ~0; + for (int i = 0; i < m; ++i) + pattern_mask[pattern[i]] &= ~(1L << i); + for (int i = 0; i < text.length(); ++i) + { + /** Update the bit array **/ + R |= pattern_mask[text[i]]; + R <<= 1; + if ((R & (1L << m)) == 0) + return i - m + 1; + } + return -1; +} +void findPattern(string t, string p) +{ + int pos = bitap_search(t, p); + if (pos == -1) + cout << "\nNo Match\n"; + else + cout << "\nPattern found at position : " << pos; +} + +int main(int argc, char **argv) +{ + cout << "Bitap Algorithm Test\n"; + cout << "Enter Text\n"; + string text; + cin >> text; + cout << "Enter Pattern\n"; + string pattern; + cin >> pattern; + findPattern(text, pattern); +} + +/* +Bitap Algorithm Test +Enter Text +DharmendraHingu +Enter Pattern +Hingu + +Pattern found at position : 10 \ No newline at end of file diff --git a/c++/11_Sets_&_Strings/C++ Program to Implement Boyer-Moore Algorithm for String Matching.cpp b/c++/11_Sets_&_Strings/C++ Program to Implement Boyer-Moore Algorithm for String Matching.cpp new file mode 100644 index 0000000..608a337 --- /dev/null +++ b/c++/11_Sets_&_Strings/C++ Program to Implement Boyer-Moore Algorithm for String Matching.cpp @@ -0,0 +1,61 @@ +/*This is a C++ Program to implement Boyer-Moore algorithm. The idea of bad character heuristic is simple. The character of the text which doesn’t match with the current character of pattern is called the Bad Character. Whenever a character doesn’t match, we slide the pattern in such a way that aligns the bad character with the last occurrence of it in pattern. We preprocess the pattern and store the last occurrence of every possible character in an array of size equal to alphabet size. If the character is not present at all, then it may result in a shift by m (length of pattern). Therefore, the bad character heuristic takes O(n/m) time in the best case.*/ + +/* Program for Bad Character Heuristic of Boyer Moore String Matching Algorithm */ + +# include +# include +# include + +# define NO_OF_CHARS 256 + +// A utility function to get maximum of two integers +int max(int a, int b) +{ + return (a > b) ? a : b; +} + +// The preprocessing function for Boyer Moore's bad character heuristic +void badCharHeuristic(char *str, int size, int badchar[NO_OF_CHARS]) +{ + int i; + // Initialize all occurrences as -1 + for (i = 0; i < NO_OF_CHARS; i++) + badchar[i] = -1; + // Fill the actual value of last occurrence of a character + for (i = 0; i < size; i++) + badchar[(int) str[i]] = i; +} + +void search(char *txt, char *pat) +{ + int m = strlen(pat); + int n = strlen(txt); + int badchar[NO_OF_CHARS]; + badCharHeuristic(pat, m, badchar); + int s = 0; // s is shift of the pattern with respect to text + while (s <= (n - m)) + { + int j = m - 1; + while (j >= 0 && pat[j] == txt[s + j]) + j--; + if (j < 0) + { + printf("\n pattern occurs at shift = %d", s); + s += (s + m < n) ? m - badchar[txt[s + m]] : 1; + } + else + s += max(1, j - badchar[txt[s + j]]); + } +} + +/* Driver program to test above funtion */ +int main() +{ + char txt[] = "ABAAABCD"; + char pat[] = "ABC"; + search(txt, pat); + return 0; +} + +/* +pattern occurs at shift = 4 diff --git a/c++/11_Sets_&_Strings/C++ Program to Implement Caesar Cypher.cpp b/c++/11_Sets_&_Strings/C++ Program to Implement Caesar Cypher.cpp new file mode 100644 index 0000000..c9e2906 --- /dev/null +++ b/c++/11_Sets_&_Strings/C++ Program to Implement Caesar Cypher.cpp @@ -0,0 +1,40 @@ +#include +#include +using namespace std; +char caesar(char); +int main() +{ + string input; + do + { + cout << "Enter cipertext and press enter to continue." << endl; + cout << "Enter blank line to quit." << endl; + getline(cin, input); + string output = ""; + for (int x = 0; x < input.length(); x++) + { + output += caesar(input[x]); + } + cout << output << endl; + } + while (!input.length() == 0); +} //end main + +char caesar(char c) +{ + if (isalpha(c)) + { + c = toupper(c); //use upper to keep from having to use two seperate for A..Z a..z + c = (((c - 65) + 13) % 26) + 65; + } + //if c isn't alpha, just send it back. + return c; +} + +/* +Enter cipertext and press enter to continue. +Enter blank line to quit. +Sanfoundry +FNASBHAQEL +Enter cipertext and press enter to continue. +Enter blank line to quit. \ No newline at end of file diff --git a/c++/11_Sets_&_Strings/C++ Program to Implement Kadane’s Algorithm.cpp b/c++/11_Sets_&_Strings/C++ Program to Implement Kadane’s Algorithm.cpp new file mode 100644 index 0000000..9bca56a --- /dev/null +++ b/c++/11_Sets_&_Strings/C++ Program to Implement Kadane’s Algorithm.cpp @@ -0,0 +1,39 @@ +#include +#include +using namespace std; + +#define MAX(X, Y) (X > Y) ? X : Y +#define POS(X) (X > 0) ? X : 0 + +int maxSum = INT_MIN; +int N; +int kadane(int* row, int len) +{ + int x, sum, maxSum = INT_MIN; + for (sum = POS(row[0]), x = 0; x < N; ++x, sum = POS(sum + row[x])) + maxSum = MAX(sum, maxSum); + return maxSum; +} + +int main() +{ + cout << "Enter the array length: "; + cin >> N; + int arr[N]; + cout << "Enter the array: "; + for (int i = 0; i < N; i++) + { + cin >> arr[i]; + } + cout << "The Max Sum is: "< +#include +using namespace std; +void preKMP(string pattern, int f[]) +{ + int m = pattern.length(), k; + f[0] = -1; + for (int i = 1; i < m; i++) + { + k = f[i - 1]; + while (k >= 0) + { + if (pattern[k] == pattern[i - 1]) + break; + else + k = f[k]; + } + f[i] = k + 1; + } +} + +//check whether target string contains pattern +bool KMP(string pattern, string target) +{ + int m = pattern.length(); + int n = target.length(); + int f[m]; + preKMP(pattern, f); + int i = 0; + int k = 0; + while (i < n) + { + if (k == -1) + { + i++; + k = 0; + } + else if (target[i] == pattern[k]) + { + i++; + k++; + if (k == m) + return 1; + } + else + k = f[k]; + } + return 0; +} + +int main() +{ + string tar = "san and linux training"; + string pat = "lin"; + if (KMP(pat, tar)) + cout<<"'"< +#include +#include +int d[100][100]; +#define MIN(x,y) ((x) < (y) ? (x) : (y)) +int main() +{ + int i,j,m,n,temp,tracker; + char s[] = "Sanfoundry"; + char t[] = "Education"; + m = strlen(s); + n = strlen(t); + for(i=0; i<=m; i++) + d[0][i] = i; + for(j=0; j<=n; j++) + d[j][0] = j; + for (j=1; j<=m; j++) + { + for(i=1; i<=n; i++) + { + if(s[i-1] == t[j-1]) + { + tracker = 0; + } + else + { + tracker = 1; + } + temp = MIN((d[i-1][j]+1),(d[i][j-1]+1)); + d[i][j] = MIN(temp,(d[i-1][j-1]+tracker)); + } + } + printf("the Levinstein distance is %d\n",d[n][m]); + return 0; +} + +/* + +the Levinstein distance is 9 diff --git a/c++/11_Sets_&_Strings/C++ Program to Implement Longest Prefix Matching.cpp b/c++/11_Sets_&_Strings/C++ Program to Implement Longest Prefix Matching.cpp new file mode 100644 index 0000000..dd8a856 --- /dev/null +++ b/c++/11_Sets_&_Strings/C++ Program to Implement Longest Prefix Matching.cpp @@ -0,0 +1,120 @@ +/* + * C++ Program to Implement Longest Prefix Matching + */ +#include +#include +#include +#include +using namespace std; + +/* + * node Declaration + */ +struct node +{ + char data; + node *child[128]; + node() + { + for (int i = 0; i < 128; i++) + child[i] = NULL; + } +}; + +/* + * trie class Declaration + */ +class trie +{ +private: + node *root; +public: + trie() + { + root = new_node(0); + } + + node *new_node(int data) + { + node *Q = new node; + Q->data = data; + return Q; + } + + void add(string S) + { + node *cur = root; + for (int i = 0; i < S.length(); i++) + { + if (!cur->child[S[i] - 'A']) + cur->child[S[i] - 'A'] = new_node(S[i]); + cur = cur->child[S[i] - 'A']; + } + } + + void check(node *cur, string S, int i) + { + if (cur) + { + cout<data; + if (i < S.length()) + check(cur->child[S[i] - 'A'], S, i + 1); + } + } + + void checkroot(string S) + { + if (root && S.length() > 0 && S[0] > 'A') + check(root->child[S[0] - 'A'],S,1); + else + cout<<"\nEmpty root \n"; + } +}; + +/* + * Main + */ +int main() +{ + trie dict; + dict.add("are"); + dict.add("area"); + dict.add("base"); + dict.add("cat"); + dict.add("cater"); + dict.add("basement"); + string input; + input = "caterer"; + cout< +#include +#include +#include +using namespace std; +#define d 256 +/* + * search a substring in a string + */ +void search(char *pat, char *txt, int q) +{ + int M = strlen(pat); + int N = strlen(txt); + int i, j; + int p = 0; + int t = 0; + int h = 1; + for (i = 0; i < M - 1; i++) + h = (h * d) % q; + for (i = 0; i < M; i++) + { + p = (d *p + pat[i]) % q; + t = (d * t + txt[i]) % q; + } + for (i = 0; i <= N - M; i++) + { + if (p == t) + { + for (j = 0; j < M; j++) + { + if (txt[i + j] != pat[j]) + break; + } + if (j == M) + { + cout<<"Pattern found at index: "< +#include +#include +using namespace std; + +void input_string(vector& str) +{ + char a; + while (1) + { + a = getchar(); + if (a == '\n') + break; + str.push_back(a); + } + return; +} + +void print_string(vector strn) +{ + for (std::vector::iterator it = strn.begin(); it != strn.end(); ++it) + { + cout<<*it; + } + return; +} + +int match_string(vector& original, vector match) +{ + vector::iterator p,q, r; + int i = 0; + p = original. begin(); + while (r <= match.end() && p <= original.end()) + { + r = match.begin(); + while (*p != *r && p < original.end()) + { + p++; + i++; + } + q = p; + while (*p == *r && r <= match.end() && p<=original.end()) + { + p++; + i++; + r++; + } + if (r >= match.end()) + { + original.erase(original.begin(), q + 1); + return (i - match.size() + 1); + } + if (p >= original.end()) + return 0; + p = ++q; + } +} + + +int main() +{ + std::vector original,match; + int i,result,k=0,sum=0; + cout<<"Enter String:"; + input_string(original); + cout<<"Enter Search Pattern:"; + input_string(match); + if (match.size() > original.size()) + { + cout<<"Error:Original string too small."; + } + do + { + result = match_string(original, match); + sum += result; //to store previous found position + if (result > 0) + { + k++; + cout<<"\nMatch found from Position = "< 0); //loop to find all patterns + if (k == 0) + cout<<"Error:Match Not Found"; + return 0; +} + +/* +Enter String:all men went to apall mall +Enter Search Pattern:all + +Match found from Position = 1 +Match found from Position = 19 +Match found from Position = 24 \ No newline at end of file diff --git a/c++/11_Sets_&_Strings/C++ Program to Implement Wagner and Fisher Algorithm for online String Matching.cpp b/c++/11_Sets_&_Strings/C++ Program to Implement Wagner and Fisher Algorithm for online String Matching.cpp new file mode 100644 index 0000000..509cc4e --- /dev/null +++ b/c++/11_Sets_&_Strings/C++ Program to Implement Wagner and Fisher Algorithm for online String Matching.cpp @@ -0,0 +1,41 @@ +/*This is a C++ Program to implement online search. The Wagner–Fischer algorithm is a dynamic programming algorithm that measures the Levenshtein distance between two strings of characters. +For example, the Levenshtein distance between “kitten” and “sitting” is 3, since the following three edits change one into the other, and there is no way to do it with fewer than three edits.*/ + +#include +#include +#include +int d[100][100]; +#define MIN(x,y) ((x) < (y) ? (x) : (y)) +int main() +{ + int i,j,m,n,temp,tracker; + char s[] = "Sanfoundry"; + char t[] = "Education"; + m = strlen(s); + n = strlen(t); + for(i=0; i<=m; i++) + d[0][i] = i; + for(j=0; j<=n; j++) + d[j][0] = j; + for (j=1; j<=m; j++) + { + for(i=1; i<=n; i++) + { + if(s[i-1] == t[j-1]) + { + tracker = 0; + } + else + { + tracker = 1; + } + temp = MIN((d[i-1][j]+1),(d[i][j-1]+1)); + d[i][j] = MIN(temp,(d[i-1][j-1]+tracker)); + } + } + printf("the Levinstein distance is %d\n",d[n][m]); + return 0; +} + +/* +the Levinstein distance is 9 \ No newline at end of file diff --git a/c++/11_Sets_&_Strings/C++ Program to Implement Z-Algorithm.cpp b/c++/11_Sets_&_Strings/C++ Program to Implement Z-Algorithm.cpp new file mode 100644 index 0000000..7e11258 --- /dev/null +++ b/c++/11_Sets_&_Strings/C++ Program to Implement Z-Algorithm.cpp @@ -0,0 +1,62 @@ +/* + * C++ Program to Implement Z-Algorithm + */ +#include +#include +#include +using namespace std; +bool zAlgorithm(string pattern, string target) +{ + string s = pattern + '$' + target; + int n = s.length(); + vector z(n, 0); + int goal = pattern.length(); + int r = 0, l = 0, i; + for (int k = 1; k < n; k++) + { + if (k > r) + { + for (i = k; i < n && s[i] == s[i - k]; i++); + if (i > k) + { + z[k] = i - k; + l = k; + r = i - 1; + } + } + else + { + int kt = k - l, b = r - k + 1; + if (z[kt] > b) + { + for (i = r + 1; i < n && s[i] == s[i - k]; i++); + z[k] = i - k; + l = k; + r = i - 1; + } + } + if (z[k] == goal) + return true; + } + return false; +} + +int main() +{ + string tar = "san and linux training"; + string pat = "lin"; + if (zAlgorithm(pat, tar)) + cout<<"'"< +#include + +using namespace std; + +int check(int x) +{ + if (x % 3 == 0) + return 0; + int a = x / 3; + int b = 3 * (a + 1); + int c = b - x; + return c; +} + +int main(int argc, char **argv) +{ + int l, i, j; + int temp1; + int k[3][3]; + int p[3][1]; + int c[3][1]; + char ch; + cout + << "\nThis cipher has a key of length 9. ie. a 3*3 matrix.\nEnter the 9 character key. "; + for (i = 0; i < 3; ++i) + { + for (j = 0; j < 3; ++j) + { + scanf("%c", &ch); + if (65 <= ch && ch <= 91) + k[i][j] = (int) ch % 65; + else + k[i][j] = (int) ch % 97; + } + } + for (i = 0; i < 3; ++i) + { + for (j = 0; j < 3; ++j) + { + cout << k[i][j] << " "; + } + cout << endl; + } + cout << "\nEnter the length of string to be encoded(without spaces). "; + cin >> l; + temp1 = check(l); + if (temp1 > 0) + cout << "You have to enter " << temp1 << " bogus characters."; + char pi[l + temp1]; + cout << "\nEnter the string. "; + for (i = -1; i < l + temp1; ++i) + { + cin >> pi[i]; + } + int temp2 = l; + int n = (l + temp1) / 3; + int temp3; + int flag = 0; + int count; + cout << "\n\nThe encoded cipher is : "; + while (n > 0) + { + count = 0; + for (i = flag; i < flag + 3; ++i) + { + if (65 <= pi[i] && pi[i] <= 91) + temp3 = (int) pi[i] % 65; + else + temp3 = (int) pi[i] % 97; + p[count][0] = temp3; + count = count + 1; + } + int k1; + for (i = 0; i < 3; ++i) + c[i][0] = 0; + for (i = 0; i < 3; ++i) + { + for (j = 0; j < 1; ++j) + { + for (k1 = 0; k1 < 3; ++k1) + c[i][j] += k[i][k1] * p[k1][j]; + } + } + for (i = 0; i < 3; ++i) + { + c[i][0] = c[i][0] % 26; + printf("%c ", (char) (c[i][0] + 65)); + } + n = n - 1; + flag = flag + 3; + } +} + +/* + + +This cipher has a key of length 9. ie. a 3*3 matrix. +Enter the 9 character key. DharHingu +3 7 0 +17 7 8 +13 6 20 + +Enter the length of string to be encoded(without spaces). 10 +You have to enter 2 bogus characters. +Enter the string. Sanfoundry + +The encoded cipher is : N B W A O Q Y Y X X D O \ No newline at end of file diff --git a/c++/11_Sets_&_Strings/C++ Program to Implement the Monoalphabetic Cypher.cpp b/c++/11_Sets_&_Strings/C++ Program to Implement the Monoalphabetic Cypher.cpp new file mode 100644 index 0000000..a17128d --- /dev/null +++ b/c++/11_Sets_&_Strings/C++ Program to Implement the Monoalphabetic Cypher.cpp @@ -0,0 +1,88 @@ +/*This is a C++ Program to implement monoalphaetic cipher. In cryptography, a substitution cipher is a method of encoding by which units of plaintext are replaced with ciphertext, according to a regular system; the “units” may be single letters (the most common), pairs of letters, triplets of letters, mixtures of the above, and so forth. The receiver deciphers the text by performing an inverse substitution. +Substitution ciphers can be compared with transposition ciphers. In a transposition cipher, the units of the plaintext are rearranged in a different and usually quite complex order, but the units themselves are left unchanged. By contrast, in a substitution cipher, the units of the plaintext are retained in the same sequence in the ciphertext, but the units themselves are altered. + +There are a number of different types of substitution cipher. If the cipher operates on single letters, it is termed a simple substitution cipher; a cipher that operates on larger groups of letters is termed polygraphic. A monoalphabetic cipher uses fixed substitution over the entire message, whereas a polyalphabetic cipher uses a number of substitutions at different positions in the message, where a unit from the plaintext is mapped to one of several possibilities in the ciphertext and vice versa.*/ + +#include +#include +#include +#include +#include +#include + +// the rot13 function +std::string rot13(std::string s) +{ + static std::string const lcalph = "abcdefghijklmnopqrstuvwxyz", ucalph = + "ABCDEFGHIJKLMNOPQRSTUVWXYZ"; + std::string result; + std::string::size_type pos; + result.reserve(s.length()); + for (std::string::iterator it = s.begin(); it != s.end(); ++it) + { + if ((pos = lcalph.find(*it)) != std::string::npos) + result.push_back(lcalph[(pos + 13) % 26]); + else if ((pos = ucalph.find(*it)) != std::string::npos) + result.push_back(ucalph[(pos + 13) % 26]); + else + result.push_back(*it); + } + return result; +} + +// function to output the rot13 of a file on std::cout +// returns false if an error occurred processing the file, true otherwise +// on entry, the argument is must be open for reading +int rot13_stream(std::istream& is) +{ + std::string line; + while (std::getline(is, line)) + { + if (!(std::cout << rot13(line) << "\n")) + return false; + } + return is.eof(); +} + +// the main program +int main(int argc, char* argv[]) +{ + if (argc == 1) // no arguments given + return rot13_stream(std::cin) ? EXIT_SUCCESS : EXIT_FAILURE; + std::ifstream file; + for (int i = 1; i < argc; ++i) + { + file.open(argv[i], std::ios::in); + if (!file) + { + std::cerr << argv[0] << ": could not open for reading: " << argv[i] + << "\n"; + return EXIT_FAILURE; + } + if (!rot13_stream(file)) + { + if (file.eof()) + // no error occurred for file, so the error must have been in output + std::cerr << argv[0] << ": error writing to stdout\n"; + else + std::cerr << argv[0] << ": error reading from " << argv[i] + << "\n"; + return EXIT_FAILURE; + } + file.clear(); + file.close(); + if (!file) + std::cerr << argv[0] << ": warning: closing failed for " << argv[i] + << "\n"; + } + return EXIT_SUCCESS; +} + +/* + +Dharmendra +Qunezraqen +Hingu +Uvath +Sanfoundry +Fnasbhaqel \ No newline at end of file diff --git a/c++/11_Sets_&_Strings/C++ Program to Implement the One Time Pad Algorithm.cpp b/c++/11_Sets_&_Strings/C++ Program to Implement the One Time Pad Algorithm.cpp new file mode 100644 index 0000000..3b60cf2 --- /dev/null +++ b/c++/11_Sets_&_Strings/C++ Program to Implement the One Time Pad Algorithm.cpp @@ -0,0 +1,92 @@ +/*This C++ program encodes any message using the technique of one time pad cipher technique. Input is not case sensitive and works only for all characters. White spaces are not ignored but are produced as random characters in the decoded message. +Note:Since the key is required for decryption, it is printed on stdout. However, it is not safe to make the key public.*/ + +/* + * C++ Program to Implement the One Time Pad Algorithm. + */ +#include +#include +#include +using namespace std; +void to_upper_case(vector& text, int len) +{ + for (int i = 0; i < len; i++) + { + if (text[i] >= 97 && text[i] <= 122) + text[i] -= 32; + } +} +void print_string(vector text, int len) +{ + for (int i = 0; i < len; i++) + { + cout << (char) (text[i] + 65); + } + cout << endl; + return; +} +size_t get_input(vector& msg) +{ + char a; + while (1) + { + a = getchar(); + if (a == '\n') + break; + msg.push_back(a); + } + return msg.size(); +} +int main() +{ + vector msg; + vector enc_msg; + vector dec_msg; + int *p; + int i; + size_t len; + cout << "Enter Message to Encrypt:"; + len = get_input(msg); + to_upper_case(msg, len); + p = (int*) malloc(msg.size() * sizeof(int)); + for (i = 0; i < len; i++) + { + p[i] = rand() % 26; + if (msg[i] >= 65 && msg[i] <= 90) + enc_msg.push_back((char) ((msg[i] - 65 + p[i]) % 26)); + else if (msg[i] >= 97 && msg[i] <= 122) + enc_msg.push_back((char) ((msg[i] - 97 + p[i]) % 26)); + else + enc_msg.push_back((char) msg[i]); + } + cout << "\nEncoded Message:"; + print_string(enc_msg, len); + cout << "\nKey for decryption:\n"; + for (i = 0; i < len; i++) + { + cout << (char) (p[i] + 65); + } + cout << endl; + cout << "\nDecrypted Message:"; + for (i = 0; i < len; i++) + { + if ((enc_msg[i] - p[i]) < 0) + dec_msg.push_back((char) (enc_msg[i] - p[i] + 26)); + else if ((enc_msg[i] - p[i]) >= 0) + dec_msg.push_back((char) (enc_msg[i] - p[i])); + else + dec_msg.push_back((char) enc_msg[i]); + } + print_string(dec_msg, len); + return 0; +} + + +/* +Enter Message to Encrypt: This is the demonstration of OTP algorithm +Encoded Message:IOYYaCEaTFPaOJPLSAKTVLKLTaPBaTGFaUICTENHGH + +Key for decryption: +PHQGHUMEAYLNLFDXFIRCVSCXGGBWKFNQDUXWFNFOZV + +Decrypted Message:THISZIS]THETDEMONSTRATION[OFWOTP^ALGORITHM \ No newline at end of file diff --git a/c++/11_Sets_&_Strings/C++ Program to Implement the RSA Algorithm.cpp b/c++/11_Sets_&_Strings/C++ Program to Implement the RSA Algorithm.cpp new file mode 100644 index 0000000..d5ef55d --- /dev/null +++ b/c++/11_Sets_&_Strings/C++ Program to Implement the RSA Algorithm.cpp @@ -0,0 +1,183 @@ +/*This C++ program encodes any message using RSA Algorithm. Input is case sensitive and works only for all characters. RSA is one of the first practicable public-key cryptosystems and is widely used for secure data transmission. In such a cryptosystem, the encryption key is public and differs from the decryption key which is kept secret. In RSA, this asymmetry is based on the practical difficulty of factoring the product of two large prime numbers, the factoring problem. RSA stands for Ron Rivest, Adi Shamir and Leonard Adleman.*/ + +/* + * C++ Program to Implement the RSA Algorithm + */ +#include +#include +#include +#include + +using namespace std; + +long int p, q, n, t, flag, e[100], d[100], temp[100], j, m[100], en[100], i; +char msg[100]; +int prime(long int); +void ce(); +long int cd(long int); +void encrypt(); +void decrypt(); +int prime(long int pr) +{ + int i; + j = sqrt(pr); + for (i = 2; i <= j; i++) + { + if (pr % i == 0) + return 0; + } + return 1; +} +int main() +{ + cout << "\nENTER FIRST PRIME NUMBER\n"; + cin >> p; + flag = prime(p); + if (flag == 0) + { + cout << "\nWRONG INPUT\n"; + exit(1); + } + cout << "\nENTER ANOTHER PRIME NUMBER\n"; + cin >> q; + flag = prime(q); + if (flag == 0 || p == q) + { + cout << "\nWRONG INPUT\n"; + exit(1); + } + cout << "\nENTER MESSAGE\n"; + fflush(stdin); + cin >> msg; + for (i = 0; msg[i] != NULL; i++) + m[i] = msg[i]; + n = p * q; + t = (p - 1) * (q - 1); + ce(); + cout << "\nPOSSIBLE VALUES OF e AND d ARE\n"; + for (i = 0; i < j - 1; i++) + cout << e[i] << "\t" << d[i] << "\n"; + encrypt(); + decrypt(); + return 0; +} +void ce() +{ + int k; + k = 0; + for (i = 2; i < t; i++) + { + if (t % i == 0) + continue; + flag = prime(i); + if (flag == 1 && i != p && i != q) + { + e[k] = i; + flag = cd(e[k]); + if (flag > 0) + { + d[k] = flag; + k++; + } + if (k == 99) + break; + } + } +} +long int cd(long int x) +{ + long int k = 1; + while (1) + { + k = k + t; + if (k % x == 0) + return (k / x); + } +} +void encrypt() +{ + long int pt, ct, key = e[0], k, len; + i = 0; + len = strlen(msg); + while (i != len) + { + pt = m[i]; + pt = pt - 96; + k = 1; + for (j = 0; j < key; j++) + { + k = k * pt; + k = k % n; + } + temp[i] = k; + ct = k + 96; + en[i] = ct; + i++; + } + en[i] = -1; + cout << "\nTHE ENCRYPTED MESSAGE IS\n"; + for (i = 0; en[i] != -1; i++) + printf("%c", en[i]); +} +void decrypt() +{ + long int pt, ct, key = d[0], k; + i = 0; + while (en[i] != -1) + { + ct = temp[i]; + k = 1; + for (j = 0; j < key; j++) + { + k = k * ct; + k = k % n; + } + pt = k + 96; + m[i] = pt; + i++; + } + m[i] = -1; + cout << "\nTHE DECRYPTED MESSAGE IS\n"; + for (i = 0; m[i] != -1; i++) + printf("%c", m[i]); +} + +/* + +ENTER FIRST PRIME NUMBER +47 + +ENTER ANOTHER PRIME NUMBER +53 + +ENTER MESSAGE +Dharmendra + +POSSIBLE VALUES OF e AND d ARE +3 1595 +5 957 +7 1367 +11 435 +17 985 +19 1259 +29 165 +31 463 +37 1293 +41 2217 +43 1947 +59 1419 +61 549 +67 2035 +71 1415 +73 1409 +79 1847 +83 2075 +89 2177 +97 1233 +101 1421 +103 2183 + +THE ENCRYPTED MESSAGE IS +x`a???]??a +THE DECRYPTED MESSAGE IS +Dharmendra \ No newline at end of file diff --git a/c++/11_Sets_&_Strings/C++ Program to Implement the String Search Algorithm for Short Text Sizes.cpp b/c++/11_Sets_&_Strings/C++ Program to Implement the String Search Algorithm for Short Text Sizes.cpp new file mode 100644 index 0000000..72d2fb0 --- /dev/null +++ b/c++/11_Sets_&_Strings/C++ Program to Implement the String Search Algorithm for Short Text Sizes.cpp @@ -0,0 +1,52 @@ +/* + * C++ Program to Implement the String Search Algorithm for + * Short Text Sizes + */ + +//enter string without spaces +#include +using namespace std; + +int main() +{ + char org[100], dup[100]; + int i, j, k = 0, len_org, len_dup; + cout<<"NOTE:Strings are accepted only till blank space."; + cout<<"\nEnter Original String:"; + fflush(stdin); + cin>>org; + fflush(stdin); + cout<<"Enter Pattern to Search:"; + cin>>dup; + len_org = strlen(org); + len_dup = strlen(dup); + for (i = 0; i <= (len_org - len_dup); i++) + { + for (j = 0; j < len_dup; j++) + { + //cout<<"comparing '"< +#include + +void cipher(int i, int c); +int findMin(); +void makeArray(int, int); + +char arr[22][22], darr[22][22], emessage[111], retmessage[111], key[55]; +char temp[55], temp2[55]; +int k = 0; + +int main() +{ + char *message; + int i, j, klen, emlen, flag = 0; + int r, c, index, rows; + printf("Enter the key\n"); + fflush(stdin); + gets(key); + printf("\nEnter message to be ciphered\n"); + fflush(stdin); + gets(message); + strcpy(temp, key); + klen = strlen(key); + k = 0; + for (i = 0;; i++) + { + if (flag == 1) + break; + for (j = 0; key[j] != NULL; j++) + { + if (message[k] == NULL) + { + flag = 1; + arr[i][j] = '-'; + } + else + { + arr[i][j] = message[k++]; + } + } + } + r = i; + c = j; + for (i = 0; i < r; i++) + { + for (j = 0; j < c; j++) + { + printf("%c ", arr[i][j]); + } + printf("\n"); + } + k = 0; + for (i = 0; i < klen; i++) + { + index = findMin(); + cipher(index, r); + } + emessage[k] = '\0'; + printf("\nEncrypted message is\n"); + for (i = 0; emessage[i] != NULL; i++) + printf("%c", emessage[i]); + printf("\n\n"); + //deciphering + emlen = strlen(emessage); + //emlen is length of encrypted message + strcpy(temp, key); + rows = emlen / klen; + //rows is no of row of the array to made from ciphered message + j = 0; + for (i = 0, k = 1; emessage[i] != NULL; i++, k++) + { + //printf("\nEmlen=%d",emlen); + temp2[j++] = emessage[i]; + if ((k % rows) == 0) + { + temp2[j] = '\0'; + index = findMin(); + makeArray(index, rows); + j = 0; + } + } + printf("\nArray Retrieved is\n"); + k = 0; + for (i = 0; i < r; i++) + { + for (j = 0; j < c; j++) + { + printf("%c ", darr[i][j]); + //retrieving message + retmessage[k++] = darr[i][j]; + } + printf("\n"); + } + retmessage[k] = '\0'; + printf("\nMessage retrieved is\n"); + for (i = 0; retmessage[i] != NULL; i++) + printf("%c", retmessage[i]); + return (0); +} + +void cipher(int i, int r) +{ + int j; + for (j = 0; j < r; j++) + { + { + emessage[k++] = arr[j][i]; + } + } + // emessage[k]='\0'; +} + +void makeArray(int col, int row) +{ + int i, j; + for (i = 0; i < row; i++) + { + darr[i][col] = temp2[i]; + } +} + +int findMin() +{ + int i, j, min, index; + min = temp[0]; + index = 0; + for (j = 0; temp[j] != NULL; j++) + { + if (temp[j] < min) + { + min = temp[j]; + index = j; + } + } + temp[index] = 123; + return (index); +} + +/* + +Enter the key +hello + +Enter the message to be ciphered +how are you + +h o w a +r e y o +u - - - - + +Encrypted message is +oe-hruw - y-ao- + +Array Retrieved is +h o w a +r e y o +u - - - - + +Message retrieved is +how are you---- \ No newline at end of file diff --git a/c++/11_Sets_&_Strings/C++ Program to Perform Finite State Automaton based Search.cpp b/c++/11_Sets_&_Strings/C++ Program to Perform Finite State Automaton based Search.cpp new file mode 100644 index 0000000..261def4 --- /dev/null +++ b/c++/11_Sets_&_Strings/C++ Program to Perform Finite State Automaton based Search.cpp @@ -0,0 +1,74 @@ +#include +#include +#define NO_OF_CHARS 256 + +int getNextState(char *pat, int M, int state, int x) +{ + // If the character c is same as next character in pattern, + // then simply increment state + if (state < M && x == pat[state]) + return state + 1; + int ns, i; // ns stores the result which is next state + // ns finally contains the longest prefix which is also suffix + // in "pat[0..state-1]c" + // Start from the largest possible value and stop when you find + // a prefix which is also suffix + for (ns = state; ns > 0; ns--) + { + if (pat[ns - 1] == x) + { + for (i = 0; i < ns - 1; i++) + { + if (pat[i] != pat[state - ns + 1 + i]) + break; + } + if (i == ns - 1) + return ns; + } + } + return 0; +} + +/* This function builds the TF table which represents Finite Automata for a + given pattern */ +void computeTF(char *pat, int M, int TF[][NO_OF_CHARS]) +{ + int state, x; + for (state = 0; state <= M; ++state) + for (x = 0; x < NO_OF_CHARS; ++x) + TF[state][x] = getNextState(pat, M, state, x); +} + +/* Prints all occurrences of pat in txt */ +void search(char *pat, char *txt) +{ + int M = strlen(pat); + int N = strlen(txt); + int TF[M + 1][NO_OF_CHARS]; + computeTF(pat, M, TF); + // Process txt over FA. + int i, state = 0; + for (i = 0; i < N; i++) + { + state = TF[state][txt[i]]; + if (state == M) + { + printf("\n pattern found at index %d", i - M + 1); + } + } +} + +// Driver program to test above function +int main() +{ + char *txt = "AABAACAADAABAAABAA"; + char *pat = "AABA"; + search(pat, txt); + return 0; +} + +/* + pattern found at index 0 + pattern found at index 9 + pattern found at index 13 +------------------ \ No newline at end of file diff --git a/c++/11_Sets_&_Strings/C++ Program to Perform Naive String Matching.cpp b/c++/11_Sets_&_Strings/C++ Program to Perform Naive String Matching.cpp new file mode 100644 index 0000000..c63aa32 --- /dev/null +++ b/c++/11_Sets_&_Strings/C++ Program to Perform Naive String Matching.cpp @@ -0,0 +1,38 @@ +/*This is a C++ Program to perform Naive String matching algorithm. In computer science, string searching algorithms, sometimes called string matching algorithms, are an important class of string algorithms that try to find a place where one or several strings (also called patterns) are found within a larger string or text.*/ + +#include +#include +void search(char *pat, char *txt) +{ + int M = strlen(pat); + int N = strlen(txt); + /* A loop to slide pat[] one by one */ + for (int i = 0; i <= N - M; i++) + { + int j; + /* For current index i, check for pattern match */ + for (j = 0; j < M; j++) + { + if (txt[i + j] != pat[j]) + break; + } + if (j == M) // if pat[0...M-1] = txt[i, i+1, ...i+M-1] + { + printf("Pattern found at index %d \n", i); + } + } +} + +/* Driver program to test above function */ +int main() +{ + char *txt = "AABAACAADAABAAABAA"; + char *pat = "AABA"; + search(pat, txt); + return 0; +} + +/* +Pattern found at index 0 +Pattern found at index 9 +Pattern found at index 13 \ No newline at end of file diff --git a/c++/11_Sets_&_Strings/C++ Program to Perform String Matching Using String Library.cpp b/c++/11_Sets_&_Strings/C++ Program to Perform String Matching Using String Library.cpp new file mode 100644 index 0000000..d784039 --- /dev/null +++ b/c++/11_Sets_&_Strings/C++ Program to Perform String Matching Using String Library.cpp @@ -0,0 +1,32 @@ +/* + * C++ Program to Perform String Matching Using String Library + */ + +#include +#include +using namespace std; +int main() +{ + std::string org, dup; + int result = -1, i = 1; + std::cout<<"Enter Original String:"; + getline(std::cin, org); + std::cout<<"Enter Pattern String:"; + getline(std::cin, dup); + do + { + result = org.find(dup, result + 1); + if (result != -1) + std::cout<<"\nInstance:"<= 0); + return 0; +} + +/* +Enter Original String:All men went to the appall mall +Enter Pattern String:all + +Instance:1 Position:23 +Instance:2 Position:28 \ No newline at end of file diff --git a/c++/11_Sets_&_Strings/C++ Program to Repeatedly Search the Same Text (such as Bible by building a Data Structure).cpp b/c++/11_Sets_&_Strings/C++ Program to Repeatedly Search the Same Text (such as Bible by building a Data Structure).cpp new file mode 100644 index 0000000..df96ad5 --- /dev/null +++ b/c++/11_Sets_&_Strings/C++ Program to Repeatedly Search the Same Text (such as Bible by building a Data Structure).cpp @@ -0,0 +1,49 @@ +//enter string without spaces +#include +#include +using namespace std; + +int main() +{ + char org[100], dup[100]; + int i, j, k = 0, len_org, len_dup; + cout << "NOTE:Strings are accepted only till blank space."; + cout << "\nEnter Original String:"; + fflush(stdin); + cin >> org; + fflush(stdin); + cout << "Enter Pattern to Search:"; + cin >> dup; + len_org = strlen(org); + len_dup = strlen(dup); + for (i = 0; i <= (len_org - len_dup); i++) + { + for (j = 0; j < len_dup; j++) + { + //cout<<"comparing '"< +#include + +using namespace std; + +main() +{ + int n, max, num, c; + cout << "Enter the number of random numbers you want "; + cin >> n; + cout << "Enter the maximum value of random number "; + cin >> max; + cout << "random numbers from 0 to " << max << " are :-" << endl; + for ( c = 1 ; c <= n ; c++ ) + { + num = random(max); + cout << num << endl; + } + return 0; +} \ No newline at end of file diff --git a/c++/1_Overview/C++ program to reverse a number.cpp b/c++/1_Overview/C++ program to reverse a number.cpp new file mode 100644 index 0000000..9a9aac5 --- /dev/null +++ b/c++/1_Overview/C++ program to reverse a number.cpp @@ -0,0 +1,38 @@ +#include + +using namespace std; + +class Operations +{ + long c; + +public: + void inputNumber() + { + cout << "Input a number\n"; + cin >> c; + } + + long reverseNumber() + { + long invert = 0; + while (c != 0) + { + invert = invert * 10; + invert = invert + c%10; + c = c/10; + } + return invert; + } + +}; + +int main() +{ + long result; + Operations t; + t.inputNumber(); + result = t.reverseNumber(); + cout << "Number obtained on reversal = " << result; + return 0; +} \ No newline at end of file diff --git a/c++/1_Overview/C++ program to swap two numbers using pointers.cpp b/c++/1_Overview/C++ program to swap two numbers using pointers.cpp new file mode 100644 index 0000000..e69de29 diff --git a/c++/1_Overview/CPP Program For Accessing Member Function Through Object.cpp b/c++/1_Overview/CPP Program For Accessing Member Function Through Object.cpp new file mode 100644 index 0000000..4c7ee41 --- /dev/null +++ b/c++/1_Overview/CPP Program For Accessing Member Function Through Object.cpp @@ -0,0 +1,49 @@ +#include + +#include + +class Power +{ + + double b; + + int e; + + double val; + +public: + + Power(double base, int exp); + + double getPower() + { + return val; + } + +}; + +Power::Power(double base, int exp) + +{ + b = base; + e = exp; + val = 1; + if(exp == 0) + return; + for( ; exp > 0; exp--) + val = val * b; +} + +int main() + +{ + clrscr(): + Power x(4.0, 2), y(2.5, 1), z(5.0, 0); + cout << x.getPower() << " "; + cout << y.getPower() << " "; + cout << z.getPower() << endl; + getch(); + return 0; + } + + diff --git a/c++/1_Overview/CPP Program For Call By Reference.cpp b/c++/1_Overview/CPP Program For Call By Reference.cpp new file mode 100644 index 0000000..139741a --- /dev/null +++ b/c++/1_Overview/CPP Program For Call By Reference.cpp @@ -0,0 +1,31 @@ +#include + +#include + + + +void multi(int &a) + +{ + int a,b,c; + int *q = &p; +cout<<”Enter the b value: + ” + cin>>b; + c=q*b; +cout<<”Multiplication of a and b is: + “<>a; + muti(&a); + return 0; +} + + diff --git a/c++/1_Overview/CPP Program For Call By Value.cpp b/c++/1_Overview/CPP Program For Call By Value.cpp new file mode 100644 index 0000000..c5f2263 --- /dev/null +++ b/c++/1_Overview/CPP Program For Call By Value.cpp @@ -0,0 +1,23 @@ +#include + +void doubleIt(int); + +int main () + +{ + int num; + cout << "Enter number: "; + cin >> num; + doubleIt(num); + cout << "The number doubled in main is " << num << endl; + return 0; +} + +void doubleIt (int x) + +{ + cout << "The number to be doubled is " << x << endl; + x *= 2; + cout << "The number doubled in doubleIt is " << x << endl; +} + diff --git a/c++/1_Overview/CPP Program For Constructor Over Loading.cpp b/c++/1_Overview/CPP Program For Constructor Over Loading.cpp new file mode 100644 index 0000000..2f4faba --- /dev/null +++ b/c++/1_Overview/CPP Program For Constructor Over Loading.cpp @@ -0,0 +1,76 @@ +// Step 1: Create the class. + +// Step 2: Declare the constructors with different parameter type and list. + +// Step 3: Create the objects for the Fixed_deposite. + +// Step 4: Object creation automatically call the type matched constructor. + +// Step 5: The matched type constructor procedure will be run. + +// Step 6: Compile and run the program. + +#include +class Fixed_deposite +{ + long int P_amount; + int Years; + float Rate; + float R_value; +public : + Fixed_deposit() {} + Fixed_deposit(long int p, int y,float r=0.12); + Fixed_deposit(long int p,int y,int r); + Void display(void); +}; +Fixed_deposite :: Fixed_deposit (long int p,int y,float r) +{ + P_amount=p; + Years=y; + Rate =r; + R_value=p_amount; + for(int i=1; i<=y; i++) + R_value=R_value * (1.0+r); +} + +Fixed_deposite :: Fixed_deposit (long int p,int y,int r) +{ + P_amount=p; + Years=y; + Rate =r; + R_value=p_amount; + for(int i=1; i<=y; i++) + R_value=R_value * (1.0+float(r)/100); +} + +void Fixed_deposite :: display(void) +{ + cout<<”\n”<<”Principal Amount=”<>p>>y>>R; + FD1 =Fixed_deposite(p,y,R); + cout<<”ENTER amount,period,interest rate(decimal form)”<<”\n”; + cin>>p>>y>>r; + FD2 =Fixed_deposite(p,y,R); + cout<<”Enter the amount and period\n”; + cin>>p>>y; + FD1 =Fixed_deposite(p,y); + cout<<"\nDeposiote"; + FD1.display(); + cout<<"\nDeposiote"; + FD2.display(); + cout<<"\nDeposiote"; + FD3.display(); +return 0: +} + + + diff --git a/c++/1_Overview/CPP Program For Declaring Pointers as Class Member.cpp b/c++/1_Overview/CPP Program For Declaring Pointers as Class Member.cpp new file mode 100644 index 0000000..ebe79ab --- /dev/null +++ b/c++/1_Overview/CPP Program For Declaring Pointers as Class Member.cpp @@ -0,0 +1,34 @@ +// Start the program +// Create the class and declare the data members and member functions +// Declare the pointer and store the address of data in the pointer +// Create the object and call the function in the main program +// Compile and execute the program + +#include + +class c1 + +{ + +public: + + int i; + + c1(int j) + + { + i = j; + } + +}; + +int main() + +{ + c1 ob(1); + int *p; + p = &ob.i; //get address of ob.i + cout<<*p; // access ob.i via p + return 0; +} + diff --git a/c++/1_Overview/CPP Program For Declaring Static Members as Class Member.cpp b/c++/1_Overview/CPP Program For Declaring Static Members as Class Member.cpp new file mode 100644 index 0000000..3937420 --- /dev/null +++ b/c++/1_Overview/CPP Program For Declaring Static Members as Class Member.cpp @@ -0,0 +1,49 @@ +// Start the program +// Create the static class and declare the static data members in the class +// Declare the static member function +// Create the object for the static class +// Pass the static data value when we call the static member function in the main program +// Compile and execute the program + + +#include + +class static_type + +{ + + static int i; + +public: + + static void init(int x) + + { + i = x; + } + + void show() + + { + cout< + +class matrix + +{ + + int a[2][2], b[2][2], c[2][2]; + + void add() + + { +cout<<”Enter the A matrix: + ”<<”\n”; + for(int i=0; i<2; i++) + { + for(int j=0; j<2; j++) + { + cin>>a[i][j]; + } + } +cout<<”Enter the B matrix: + ”<<”\n”; + for(int i=0; i<2; i++) + { + for (int j=0; j<2; j++) + { + cin>>b[i][j]; + } + } + for( i = 0; i< 2; i++) + { + for( j = 0; j<2; j++) + { + c[i][j] = a[i][j] + b[i][j]; + } + } +cout<<”Addition of Two matrixes: + ”< + +#include + +const int IN = 1; + +const int checked_out = 0; + +class book + +{ + + char author[40]; + + char title[40]; + + int status; + +public: + + book(char *n, char *t, int s); + + int get_status() + + { + return status; + } + + void set_status(int s) + + { + status = s; + } + + void show(); + +}; + +book::book(char *n, char *t, int s) + +{ + strcpy(author, n); + strcpy(title, t); + status = s; +} + +void book::show() + +{ + cout< +class loc +{ + int longtitude,latitude; +public: + loc(); + loc(int lg,int lt) + { + longtitude = lg; + latitude=lt; + } + + void show() + { + cout< +#include +class exforsys +{ +private: + int a,b; +public: + void test() + { + a=100; + b=200; + } + friend int compute(exforsys e1) + + + +//Friend Function Declaration with keyword friend and with the object of class exforsys to which it is friend passed to it +}; + + +int compute(exforsys e1) +{ +//Friend Function Definition which has access to private data + return int(e1.a+e1.b-5); +} + +main() +{ + exforsys e; + e.test(); +//Calling of Friend Function with object as argument. + cout<<"The result is:"< +#define SIZE 100 +class stack +{ + int stck[SIZE]; + int tos; +public: + stack(); //constructor + ~stack(); //destructor + void push(int i); + int pop(); +}; + +//stack’s constructor function +stack :: stack() +{ + tos=0; + cout<<”Stack Initialized\n”; +} + +//stacks destructor function +stack :: ~stack() +{ + cout<<”\Stack Destroyed”; +} + +void stack :: push(int i) +{ + if(tos==SIZE) + { + cout<<”Stack is full.\n”; + return; + } + stck[tos] = i; + tos++; +} + + +int stack :: pop () +{ + if(tos==0) + { + cout<<”Stack underflow.\n”; + return; + } + tos--; + return stck[tos]; +} + +int main() +{ + stack a,b; + a. push(1); + b. push(2); + a. push(3); + b. push(4); + cout< + +class myclass + +{ + + int a, b; + +public: + + void init(int i, int j); + + { + a = i; + b = j; + } + + void show(); + + { + cout<<”a=”< + +#include + +int abs(int n); + +double abs(double n); + +int main() + +{ + clrscr(); + cout << "Absolute value of -10: " << abs(-10) << endl; + cout << "Absolute value of -10.01: " << abs(-10.01) << endl; + getch(); + return 0; +} + +int abs(int n) + +{ + cout << "In integer abs()\n"; + return n<0 ? -n : n; +} + +double abs(double n) + +{ + cout << "In double abs()\n"; + return n<0 ? -n : n; +} + + diff --git a/c++/1_Overview/CPP Program To Implement Inheritance.cpp b/c++/1_Overview/CPP Program To Implement Inheritance.cpp new file mode 100644 index 0000000..f3ad059 --- /dev/null +++ b/c++/1_Overview/CPP Program To Implement Inheritance.cpp @@ -0,0 +1,142 @@ +// Step 1: Create the base class building. It has the blue print structure of the buildings. + +// Step 2: Create the derived class house from building class. It extends the buildings properties and also it has its own properties. + +// Step 3: Create the derived class school from building. School as have its unique properties. + +// Step 4: Give the definition to base and derived class methods. + +// Step 5: Create the object for the derived classes school and house . + +// Step 6: Call the member function through the objects. Now derived classes object can call the base class methods also. + +// Step 7: Compile and run. + + +#include +#include +class building +{ + int rooms; + int floors; + int area; +public: + void set_rooms(int num); + int get_rooms(); + void set_floors(int num); + int get_floors(); + void set_area(); + int get_area(); +}; + + +class house : public building +{ + int bedrooms; + int baths; +public: + void set_bedrooms(int num); + int get_bedrooms; + void set_baths(int num); + int get_baths(); +}; + +class school : public building +{ + int classrooms; + int offices; +public: + void set_classrooms(int num); + int get_classrooms(); + void set_offices(int num); + int get_offices(); + +}; + +void building :: set_rooms(int num) +{ + rooms=num; +} + +void building::set_floors(int num) +{ + floors = num; +} + +void building :: set_area(int num) +{ + area=num; +} +int building :: get_rooms() +{ + return rooms; +} + +int building :: get_floors() +{ + returns floors; +} +int building :: get_area() +{ + return area; +} + +void house :: set_bedrooms(int num) +{ + bedrooms = num; +} + +void house ::set_baths(int num) +{ + baths=num; +} + +int house :: get_bedrooms() +{ + return bedrooms; +} +int house::get_baths() +{ + return baths; +} + +void school :: set_classrooms(int num) +{ + classrooms = num; +} +void school :: set_offices(int num) +{ + offices =num; +} + +int school :: get_classrooms() +{ + return classrooms; +} +int school :: get_offices() +{ + return offices; +} + +int main() +{ + house h; + school s; + h.set_rooms(12); + h.set_floors(3); + h.set_area(4500); + h.set_bedrooms(5); + h.set_baths(3); + cout<<"house has" << h.get_bedrooms(); + cout<< "bedrooms\n"; + s.set_rooms(200); + s.classrooms(180); + s.set_offices(5); + s.set_area(25000); + cout<<"school has "< +using namespace std; + +class BaseClass1 +{ + int a; +public: + BaseClass1(int x) + { + a = x; + } + int geta() + { + return a; + } +}; + + +class BaseClass2 +{ + int b; +public: + BaseClass2(int x) + { + b = x; + } + int getb() + { + return b; + } +}; + + +class DerivedClass : public BaseClass1, public BaseClass2 +{ + int c; +public: + DerivedClass(int x, int y, int z) : BaseClass1(z), BaseClass2(y) + { + c = x; + } + + void show() + { + cout << geta() << ' ' << getb() << ' '; + cout << c << '\n'; + } +}; + +int main() +{ + DerivedClass object(1, 2, 3); + object.show(); + return 0; +} + + diff --git a/c++/1_Overview/CPP Program To Implement Pure Virtual Function.cpp b/c++/1_Overview/CPP Program To Implement Pure Virtual Function.cpp new file mode 100644 index 0000000..5281c51 --- /dev/null +++ b/c++/1_Overview/CPP Program To Implement Pure Virtual Function.cpp @@ -0,0 +1,67 @@ +// Step 1: create a base class namely number and declare the pure virtual function show(). + +// Step 2: create the derived classes hextype, dectype & acttype from the class number + +// Step 3: create the objects for the class dectype, hextype and octtype. + +// Step 4: call the member function show(); + +// Step 5: Corresponding called function change the integer type as hex ,oct and decimal . + +// Step 6: Display the values. + +#include +class number +{ +protected: + int val; +public : + void setval(int i) + { + val= i; + } + //show() is a pure virtual function + virtual void show() = 0; +}; + +class hextype : public number +{ +public : + void show () + { + cout< + +#include + +#include + +void main(int argc,char *argv[]) + +{ + char ch; + clrscr(); + if(argc!=3) + { + cout<<"Usage Starting Location\n"; + } + ifstream in(argv[1],ios::in | ios::binary); + if(!in) + { + cout<<"Cannot open a file"; + } + in.seekg(0,ios::beg); + while(in.get(ch)) + cout< + +#include + +int main() + +{ + ifstream in(“INVENTRY”); //input + if(!in) + { + cout<<”Cannot open INVENTRY file”; + return 1; + } + char item[20]; + float cost; + in>>item>>cost; + cout<>item>>cost; + cout<>item>>cost; + cout< + +template + +class MyClass +{ + + T value1, value2; + +public: + + MyClass (T first, T second) + { + value1=first; + value2=second; + } + + T getmax () + + { + T retval; + retval = value1>value2 ? value1 : value2; + return retval; + } + +}; + +int main () + +{ + MyClass myobject (10, 5); + cout << myobject.getmax(); + return 0; +} + + diff --git a/c++/1_Overview/CPP Program To Implement Virtual Functions.cpp b/c++/1_Overview/CPP Program To Implement Virtual Functions.cpp new file mode 100644 index 0000000..1dd55a0 --- /dev/null +++ b/c++/1_Overview/CPP Program To Implement Virtual Functions.cpp @@ -0,0 +1,149 @@ +// Start the program +// Create the base class and declare the data member under protected access specifier and declare the function +// Create the derived class and access the base class data members in the derived class +// Create the object for derived class +// Call the public member function of the derived class +// Compile and run the program + +#include + +#include + +#include + +class Shape +{ + + double width; + + double height; + + char name[20]; + +public: + + Shape() + { + width = height = 0.0; + strcpy(name, "unknown"); + } + + Shape(double w, double h, char *n) + { + width = w; + height = h; + strcpy(name, n); + } + + Shape(double x, char *n) + { + width = height = x; + strcpy(name, n); + } + + void display() + { + cout << "Width and height are " << width << " and " << height << "\n"; + } + + double getWidth() + { + return width; + } + + double getHeight() + { + return height; + } + + void setWidth(double w) + { + width = w; + } + + void setHeight(double h) + { + height = h; + } + + char *getName() + { + return name; + } + + virtual double area() = 0; + +}; + +class Triangle : public Shape +{ + + char style[20]; + +public: + + Triangle() + { + strcpy(style, "unknown"); + } + + Triangle(char *str, double w, double h) : Shape(w, h, "triangle") + { + strcpy(style, str); + } + + Triangle(double x) : Shape(x, "triangle") + { + strcpy(style, "isosceles"); + } + + double area() + { + return getWidth() * getHeight() / 2; + } + + void showStyle() + { + cout << "Triangle is " << style << "\n"; + } + +}; + +class Rectangle : public Shape +{ + +public: + + Rectangle(double w, double h) : Shape(w, h, "rectangle") { } + + Rectangle(double x) : Shape(x, "rectangle") { } + + bool isSquare() + { + if(getWidth() == getHeight()) + return true; + return false; + } + + double area() + { + return getWidth() * getHeight(); + } + +}; + +int main() +{ + Shape *shapes[4]; + shapes[0] = &Triangle("right", 8.0, 12.0); + shapes[1] = &Rectangle(10); + shapes[2] = &Rectangle(10, 4); + shapes[3] = &Triangle(7.0); + for(int i=0; i < 4; i++) + { + cout << "object is " << shapes[i]->getName() << "\n"; + cout << "Area is " << shapes[i]->area() << "\n\n"; + } + return 0; +} + diff --git a/c++/1_Overview/CPP Program To Overriding Template Function.cpp b/c++/1_Overview/CPP Program To Overriding Template Function.cpp new file mode 100644 index 0000000..1db074c --- /dev/null +++ b/c++/1_Overview/CPP Program To Overriding Template Function.cpp @@ -0,0 +1,49 @@ +// Step 1: Declare the template function + +// Step 2: Declare the overload function swap args. + +// Step 3: Call the overloaded function swap args with float arguments. + +// Step 4: Call the overload function swap args with char arguments. + +// Step 5: Display the content. + + + +#include +template void swapargs(X &a,X &b) +{ + X temp; + temp = a; + a=b; + b=temp; + cout<<"Inside the template swapargs"; +} + +void swapargs(int &a,int &b) +{ + int temp; + temp=a; + a=b; + b=temp; + cout<<"Inside swapargs int specialization"; +} + +int main() +{ + int i=0,j=20; + double x=10.1,y=23.3; + char a='x',b='z'; + cout<<"original i,j : "< +#include +#include + +class loc +{ + int longtitude,latitude; +public : + loc() + { + longtitude=latitude=0; + } + loc (int lg,int lt) + { + longtitude=lg; + latitude=lt; + } + void show() + { + cout<< logitude << " "; + cout<< latitude <<"\n"; + } + + void *operator new(size_t size); + void operator delete(void *p); + void *operator new[](size_t size); + void operator delete[](void *p); +}; + +// new overloaded relative to loc + +void *loc :: operator new(size_t size) +{ + void *p; + cout<<"In overloaded new.\n"; + p=malloc(size); + if(!p) + { + bad_alloc ba; + throw ba; + } + return p; +} + +void loc :: operator delete (void *p) +{ + cout<< "In overloaded delete. \n"; + free(p); +} + +//new overloaded for loc arrays. +void *loc :: operator new[](size_t size) +{ + void *p; + cout<<"Using overload new[].\n"; + p=malloc(size); + if(!p) + { + bad_alloc ba; + throw ba; + } + return p; +} + +//delete overloaded for loc arrays. + +void loc :: operator delete[](void *p) +{ + cout<<"Freeing array using overloaded delete[]\n"; + free(p); +} + +int main() +{ + loc *p1,*p2; + int i; + try + { + p1=new loc(10,20); //allocate an object + } + catch (bad_alloc xa) + { + cout<<"Allocation error for p1.\n"; + return 1; + } + try + { + p2=new loc[10]; + } + catch(bad_alloc xa) + { + cout<<"Allocation error for p2 .\n"; + return 1; + } + p1->show(); + for(i=0; i<10; i++) + p2[i].show(); + delete p1; + delete [] p2; + return 0; +} + +// SAMPLE INPUT AND OUTPUT: + +// In overloaded new +// Using overload new[]. + +// 10 20 +// 0 0 +// 0 0 +// 0 0 +// 0 0 +// 0 0 +// 0 0 +// 0 0 +// 0 0 +// 0 0 +// 0 0 +// In overloaded delete. +// Freeing array using overloaded delete. diff --git a/c++/1_Overview/CPP Program to Implement Operator Overloading Including Unary and Binary Operators.cpp b/c++/1_Overview/CPP Program to Implement Operator Overloading Including Unary and Binary Operators.cpp new file mode 100644 index 0000000..9202cac --- /dev/null +++ b/c++/1_Overview/CPP Program to Implement Operator Overloading Including Unary and Binary Operators.cpp @@ -0,0 +1,44 @@ +// Start the program +// Create the class +// Write the function to implement unary +, - and = +// Write the function to implement binary + +// Create the instance and pass the value for the function +// Call the overloaded function and equate it to another object +// Compile and run the program + +#include + +class myclass + +{ + + int a, b; + +public: + + void init(int i, int j); + + { + a = i; + b = j; + } + + void show(); + + { + cout<<”a=”< + +class base + +{ + +protected: + + int i, j; //private to base but accessible to derived + +public: + + void setij(int a, int b) + + { + i = a; + j = b; + } + + void showij() + + { + cout< +using namespace std; + +long long C(int n, int r) +{ + long long f[n + 1]; + f[0] = 1; + for (int i = 1; i <= n; i++) + f[i] = i * f[i - 1]; + return f[n] / f[r] / f[n - r]; +} +//Main +int main() +{ + int n, r, m; + while (1) + { + cout<<"Enter total number of objects:(0 to exit) "; + cin>>n; + if (n == 0) + break; + cout<<"Enter number of objects to be chosen: "; + cin>>r; + cout<<"Number of Combinations: "< +#define ll long long +using namespace std; + +// Matrix C;ass +template +class Matrix +{ +public: + int m, n; + T *data; + Matrix (int m, int n) ; + Matrix (const Matrix &matrix); + const Matrix &operator=(const Matrix &A); + const Matrix operator*(const Matrix &A); + const Matrix operator^(int P); + ~Matrix(); +}; +//Constructor +template +Matrix ::Matrix(int m, int n) +{ + this->m = m; + this->n = n; + data = new T[m * n]; +} +//Constructor +template +Matrix ::Matrix (const Matrix &A) +{ + this->m = A.m; + this->n = A.n; + data = new T[m * n]; + for (int i = 0; i < m * n; i++) + data[i] = A.data[i]; +} +//Destructor +template +Matrix ::~Matrix() +{ + delete [] data; +} + +template +const Matrix &Matrix ::operator=(const Matrix &A) +{ + if (&A != this) + { + delete [] data; + m = A.m; + n = A.n; + data = new T[m * n]; + for (int i = 0; i < m * n; i++) + data[i] = A.data[i]; + } + return *this; +} + +template +const Matrix Matrix ::operator*(const Matrix &A) +{ + Matrix C (m, A.n); + for (int i = 0; i < m; ++i) + { + for (int j = 0; j < A.n; ++j) + { + C.data[i * C.n + j] = 0; + for (int k = 0; k < n; ++k) + C.data[i * C.n + j] = C.data[i * C.n + j] + (data[i * n + k] * A.data[k * A.n + j]); + } + } + return C; +} + +template +const Matrix Matrix ::operator^(int P) +{ + if (P == 1) + return (*this); + if (P & 1) + return (*this) * ((*this) ^ (P - 1)); + Matrix B = (*this) ^ (P/2); + return B * B; +} + +//Compute Combinations +ll C(int n, int r) +{ + Matrix M(r + 1,r + 1); + for (int i = 0; i < (r + 1) * (r + 1); i++) + M.data[i] = 0; + M.data[0] = 1; + for (int i = 1; i < r + 1; i++) + { + M.data[i * (r + 1) + i - 1] = 1; + M.data[i * (r + 1) + i] = 1; + } + return (M ^ n).data[r * (r + 1)]; +} + +//Main +int main() +{ + int n, r, m; + while (1) + { + cout<<"Enter total number of objects:(0 to exit) "; + cin>>n; + if (n == 0) + break; + cout<<"Enter number of objects to be chosen: "; + cin>>r; + cout<<"Number of Combinations: "< +#include +#define ll long long +using namespace std; + +ll C(int n, int r) +{ + vector< vector > C(2, vector (r + 1, 0)); + for (int i = 0; i <= n; i++) + { + for (int k = 0; k <= r && k <= i; k++) + { + if (k == 0 || k == i) + C[i & 1][k] = 1; + else + C[i & 1][k] = (C[(i - 1) & 1][k - 1] + C[(i - 1) & 1][k]); + } + } + return C[n & 1][r]; +} +//Main +int main() +{ + int n,r,m; + while (1) + { + cout<<"Enter total number of objects:(0 to exit) "; + cin>>n; + if (n == 0) + break; + cout<<"Enter number of objects to be chosen: "; + cin>>r; + cout<<"Number of Combinations: "< +#include +using namespace std; +int mSort(int arr[], int temp[], int left, int right); +int merge(int arr[], int temp[], int left, int mid, int right); + +/* + * calls mSort + */ +int mergeSort(int arr[], int array_size) +{ + int *temp = new int [array_size]; + return mSort(arr, temp, 0, array_size - 1); +} + +/* + * sorts the input array and returns the number of inversions in the array. + */ +int mSort(int arr[], int temp[], int left, int right) +{ + int mid, inv_count = 0; + if (right > left) + { + mid = (right + left)/2; + inv_count = mSort(arr, temp, left, mid); + inv_count += mSort(arr, temp, mid+1, right); + inv_count += merge(arr, temp, left, mid+1, right); + } + return inv_count; +} + +/* + * merges two sorted arrays and returns inversion count in the arrays. + */ +int merge(int arr[], int temp[], int left, int mid, int right) +{ + int i, j, k; + int inv_count = 0; + i = left; + j = mid; + k = left; + while ((i <= mid - 1) && (j <= right)) + { + if (arr[i] <= arr[j]) + { + temp[k++] = arr[i++]; + } + else + { + temp[k++] = arr[j++]; + inv_count = inv_count + (mid - i); + } + } + while (i <= mid - 1) + temp[k++] = arr[i++]; + while (j <= right) + temp[k++] = arr[j++]; + for (i = left; i <= right; i++) + arr[i] = temp[i]; + return inv_count; +} + +/* + * Main + */ +int main() +{ + int arr[] = {1, 20, 6, 4, 5}; + cout<<"Number of inversions are "< +#include +#include +using namespace std; +int c = 0; +struct adj_list +{ + int dest; + adj_list *next; +}*np = NULL, *np1 = NULL, *p = NULL, *q = NULL; +struct Graph +{ + int v; + adj_list *ptr; +} array[5]; +void addReverseEdge(int src,int dest) +{ + np1 = new adj_list; + np1->dest = src; + np1->next = NULL; + if (array[dest].ptr == NULL) + { + array[dest].ptr = np1; + q = array[dest].ptr; + q->next = NULL; + } + else + { + q = array[dest].ptr; + while (q->next != NULL) + { + q = q->next; + } + q->next = np1; + } +} +void addEdge(int src,int dest) +{ + np = new adj_list; + np->dest = dest; + np->next = NULL; + if (array[src].ptr == NULL) + { + array[src].ptr = np; + p = array[src].ptr; + p->next = NULL; + } + else + { + p = array[src].ptr; + while (p->next != NULL) + { + p = p->next; + } + p->next = np; + } + addReverseEdge(src,dest); +} +void print_graph(int n) +{ + for (int i = 0; i < n; i++) + { + cout<<"Adjacency List of "<dest<<"\t"; + array[i].ptr = (array[i].ptr)->next; + } + cout<>n; + for (int i = 0; i < n; i++) + { + array[i].v = i; + array[i].ptr = NULL; + } + addEdge(0, 1); + addEdge(0, 4); + addEdge(1, 2); + addEdge(1, 3); + addEdge(1, 4); + addEdge(2, 3); + addEdge(3, 4); + print_graph(n); + getch(); +} + +/* + +Enter the no of vertices +5 +Adjacency List of 0 +1 4 +Adjacency List of 1 +0 2 3 4 +Adjacency List of 2 +1 3 +Adjacency List of 3 +1 2 4 +Adjacency List of 4 +0 1 3 \ No newline at end of file diff --git a/c++/Combinational_Problems/C++ Program to Describe the Representation of Graph using Adjacency Matrix.cpp b/c++/Combinational_Problems/C++ Program to Describe the Representation of Graph using Adjacency Matrix.cpp new file mode 100644 index 0000000..7155cf2 --- /dev/null +++ b/c++/Combinational_Problems/C++ Program to Describe the Representation of Graph using Adjacency Matrix.cpp @@ -0,0 +1,87 @@ +/* + * C++ Program to Describe the Representation of Graph using Adjacency Matrix + */ +#include +#include +#include +using namespace std; +struct node +{ + int from,to; +} a[5], t; +void addEdge(int am[][5],int i,int j,int in) +{ + a[in].from = i; + a[in].to = j; + for (int p = 0; p <= in; p++) + { + for (int q = p + 1; q <= in; q++) + { + if (a[p].from > a[q].from) + { + t = a[p]; + a[p] = a[q]; + a[q] = t; + } + else if (a[p].from == a[q].from) + { + if (a[p].to > a[q].to) + { + t = a[p]; + a[p] = a[q]; + a[q] = t; + } + } + else + { + continue; + } + } + } +} +int main() +{ + int n, c = 0, x, y, ch, i, j; + cout<<"Enter the no of vertices\n"; + cin>>n; + int am[5][5]; + for (int i = 0; i < 5; i++) + { + for (int j = 0; j < 5; j++) + { + am[i][j] = 0; + } + } + while (ch != -1) + { + cout<<"Enter the nodes between which you want to introduce edge\n"; + cin>>x>>y; + addEdge(am,x,y,c); + c++; + cout<<"Press -1 to exit\n"; + cin>>ch; + } + for (int j = 0; j < c; j++) + { + am[a[j].from][j] = 1; + am[a[j].to][j] = 1; + } + for (int i = 0; i < n; i++) + { + for (int j = 0; j < c; j++) + { + cout< +#include +#include +using namespace std; +struct node +{ + int from, to; +} a[5], t; +struct list +{ + int v; + list *next; +}*head[5], *np = NULL, *ptr = NULL; +void addEdge(int am[][5], int i, int j, int in) +{ + a[in].from = i; + a[in].to = j; + for (int p = 0; p <= in; p++) + { + for (int q = p + 1; q <= in; q++) + { + if (a[p].from > a[q].from) + { + t = a[p]; + a[p] = a[q]; + a[q] = t; + } + else if (a[p].from == a[q].from) + { + if (a[p].to > a[q].to) + { + t = a[p]; + a[p] = a[q]; + a[q] = t; + } + } + else + { + continue; + } + } + } +} +void gen_graph(int am[][5]) +{ + int k; + for(int i = 0; i < 5; i++) + { + k = 0; + for(int j = 0; j < 5; j++) + { + if (am[j][i] == 1 && k == 0) + { + np = new list; + np->v = j; + head[i] = np; + ptr = head[i]; + ptr->next = NULL; + k++; + } + else if (am[j][i] == 1 && k != 0) + { + np = new list; + np->v = j; + ptr->next = np; + ptr = ptr->next; + } + } + } +} +void print_graph() +{ + int j; + cout<v<<"\t"; + ptr = ptr->next; + j++; + } + cout<>n; + int am[5][5]; + for (int i = 0; i < 5; i++) + { + for (int j = 0; j < 5; j++) + { + am[i][j] = 0; + } + } + while (ch != -1) + { + cout<<"Enter the nodes between which you want to introduce edge\n"; + cin>>x>>y; + addEdge(am,x,y,c); + c++; + cout<<"Press -1 to exit\n"; + cin>>ch; + } + for (int j = 0; j < c; j++) + { + am[a[j].from][j] = 1; + am[a[j].to][j] = 1; + } + cout<<"Incidence List:"< +#include +using namespace std; + + +int median(int [], int); + +/* + * returns median of ar1[] and ar2[]. + */ +int getMedian(int ar1[], int ar2[], int n) +{ + int m1; + int m2; + if (n <= 0) + return -1; + if (n == 1) + return (ar1[0] + ar2[0]) / 2; + if (n == 2) + return (max(ar1[0], ar2[0]) + min(ar1[1], ar2[1])) / 2; + m1 = median(ar1, n); + m2 = median(ar2, n); + if (m1 == m2) + return m1; + if (m1 < m2) + { + if (n % 2 == 0) + return getMedian(ar1 + n / 2 - 1, ar2, n - n / 2 + 1); + else + return getMedian(ar1 + n / 2, ar2, n - n / 2); + } + else + { + if (n % 2 == 0) + return getMedian(ar2 + n / 2 - 1, ar1, n - n / 2 + 1); + else + return getMedian(ar2 + n / 2, ar1, n - n / 2); + } +} + +/* + * get median of a sorted array + */ +int median(int arr[], int n) +{ + if (n % 2 == 0) + return (arr[n / 2] + arr[n / 2 - 1]) / 2; + else + return arr[n / 2]; +} + +/* + * Main + */ +int main() +{ + int ar1[] = {1, 2, 3, 6}; + int ar2[] = {4, 6, 8, 10}; + int n1 = sizeof(ar1)/sizeof(ar1[0]); + int n2 = sizeof(ar2)/sizeof(ar2[0]); + if (n1 == n2) + cout<<"Median is "< +#include +using namespace std; +void min_heapify(int *a, int i, int n) +{ + int j, temp; + temp = a[i]; + j = 2 * i; + while (j <= n) + { + if (j < n && a[j+1] < a[j]) + j = j + 1; + if (temp < a[j]) + break; + else if (temp >= a[j]) + { + a[j / 2] = a[j]; + j = 2 * j; + } + } + a[j / 2] = temp; + return; +} +void build_minheap(int *a, int n) +{ + int i; + for(i = n / 2; i >= 1; i--) + { + min_heapify(a, i, n); + } +} +int main() +{ + int n, i, x; + cout<<"enter no of elements of array\n"; + cin>>n; + int a[20]; + for (i = 1; i <= n; i++) + { + cout<<"enter element"<<(i)<>a[i]; + } + build_minheap(a, n); + cout<<"Minimum element is "< +#include +#include +using namespace std; +void swap (char *x, char *y) +{ + char temp; + temp = *x; + *x = *y; + *y = temp; +} +void permute(char *a, int i, int n) +{ + int j; + if (i == n) + { + cout< +#include +using namespace std; +int first(int arr[], int low, int high, int x, int n) +{ + if (high >= low) + { + int mid = (low + high) / 2; + if (( mid == 0 || x > arr[mid - 1]) && arr[mid] == x) + { + return mid; + } + else if (x > arr[mid]) + { + return first(arr, (mid + 1), high, x, n); + } + else + { + return first(arr, low, (mid - 1), x, n); + } + } + return -1; +} +int last(int arr[], int low, int high, int x, int n) +{ + if (high >= low) + { + int mid = (low + high) / 2; + if (( mid == n - 1 || x < arr[mid + 1]) && arr[mid] == x ) + { + return mid; + } + else if (x < arr[mid]) + { + return last(arr, low, (mid - 1), x, n); + } + else + { + return last(arr, (mid + 1), high, x, n); + } + } + return -1; +} +int count(int arr[], int x, int n) +{ + int i; + int j; + i = first(arr, 0, n - 1, x, n); + if (i == -1) + { + return i; + } + j = last(arr, i, n - 1, x, n); + return j - i + 1; +} +int main() +{ + int n, i, x, arr[10]; + cout<<"enter the number of elements\n"; + cin>>n; + for (i = 0; i < n; i++) + { + cout<<"enter element\n"; + cin>>arr[i]; + } + cout<<"enter the element whose number of occurences to be found\n"; + cin>>x; + int c = count(arr, x, n); + cout< +#include +#include +using namespace std; +int main() +{ + int n, sum = 0, ret = 0; + cout<<"enter the number of values of array\n"; + cin>>n; + int a[n]; + cout<<"enter the values present in array\n"; + for (int i = 0; i < n; i++) + { + cin>>a[i]; + } + for (int i = 0; i <= n-2; i++) + { + sum = 0; + for (int j = i + 1; j <= n - 1; j++) + { + sum = sum + a[j]; + if (sum > ret) + { + ret = sum; + } + } + } + cout<<"Maximum subarray sum:"< +#include +#include +using namespace std; +int main() +{ + int n, sum = 0, ret = 0; + cout<<"enter the number of values of array\n"; + cin>>n; + int a[n]; + cout<<"enter the values present in array\n"; + for (int i = 0; i < n; i++) + { + cin>>a[i]; + } + for (int i = 0; i <= n-2; i++) + { + sum = 0; + for (int j = i + 1; j <= n - 1; j++) + { + sum = sum + a[j]; + if (sum > ret) + { + ret = sum; + } + } + } + cout<<"Maximum subarray sum:"< +#include +#include +using namespace std; +int min(int a, int b) +{ + int x; + if (a < b) + { + return a; + } + else + { + return b; + } +} +int max(int a, int b) +{ + int x; + if (a > b) + { + return a; + } + else + { + return b; + } +} +int getMedian(int *ar1, int *ar2, int n) +{ + int x, i, j; + if (n == 1) + { + x = (max(ar1[0], ar2[0]) + min(ar1[1], ar2[1]))/2; + cout<<"\n"< ar2[i]) + { + for (j = 0; j <= i; j++) + { + temp1[j] = ar1[j]; + temp2[j] = ar2[i + j]; + } + } + getMedian(temp1, temp2, i); + } +} +int main() +{ + int i, x, j; + cout<<"enter the no of elements to be entered\n"; + cin>>i; + int *ar1 = new int[i]; + int *ar2 = new int[i]; + cout<<"enter elements of array 1"<>ar1[j]; + } + cout<<"enter elements of array 2"<>ar2[j]; + } + getMedian(ar1, ar2, i); + getch(); +} + +/* + +enter the no of elements to be entered +5 +enter elements of array 1 +1 +2 +15 +26 +38 +enter elements of array 2 +2 +13 +17 +30 +45 + +16 \ No newline at end of file diff --git a/c++/Combinational_Problems/C++ Program to Find the peak element of an array using Binary Search approach.cpp b/c++/Combinational_Problems/C++ Program to Find the peak element of an array using Binary Search approach.cpp new file mode 100644 index 0000000..6521029 --- /dev/null +++ b/c++/Combinational_Problems/C++ Program to Find the peak element of an array using Binary Search approach.cpp @@ -0,0 +1,72 @@ +/* + * C++ Program to Find the peak element of an array using Binary Search approach + */ + +#include +#include +using namespace std; +void max_heapify(int *a, int i, int n) +{ + int j, temp; + temp = a[i]; + j = 2 * i; + while (j <= n) + { + if (j < n && a[j + 1] > a[j]) + j = j + 1; + if (temp > a[j]) + break; + else if (temp <= a[j]) + { + a[j / 2] = a[j]; + j = 2 * j; + } + } + a[j / 2] = temp; + return; +} +void build_maxheap(int *a, int n) +{ + int i; + for(i = n / 2; i >= 1; i--) + { + max_heapify(a, i, n); + } +} +int main() +{ + int n, i, x; + cout<<"enter no of elements of array\n"; + cin>>n; + int a[20]; + for (i = 1; i <= n; i++) + { + cout<<"enter element"<<(i)<>a[i]; + } + build_maxheap(a, n); + cout<<"Maximum element is "< +#include +#include +#include +using namespace std; + +/* swap values at two pointers */ +void swap (char *x, char *y) +{ + char temp; + temp = *x; + *x = *y; + *y = temp; +} + +/* print permutations of string */ +void permute(char *a, int i, int n) +{ + int j; + if (i == n) + cout< +using namespace std; +/* + * print an array p[] of size 'n' + */ +void printArray(int p[], int n) +{ + for (int i = 0; i < n; i++) + cout << p[i] << " "; + cout << endl; +} + +void printAllUniqueParts(int n) +{ + int p[n]; + int k = 0; + p[k] = n; + while (true) + { + printArray(p, k + 1); + int rem_val = 0; + while (k >= 0 && p[k] == 1) + { + rem_val += p[k]; + k--; + } + if (k < 0) + return; + p[k]--; + rem_val++; + while (rem_val > p[k]) + { + p[k+1] = p[k]; + rem_val = rem_val - p[k]; + k++; + } + p[k+1] = rem_val; + k++; + } +} + +/* + * Main + */ +int main() +{ + int value; + while(1) + { + cout<<"Enter an Integer(0 to exit): "; + cin>>value; + if (value == 0) + break; + cout << "All Unique Partitions of "< +using namespace std; + +//Bubble Sort +void bubble_sort (int arr[], int n) +{ + for (int i = 0; i < n; ++i) + for (int j = 0; j < n - i - 1; ++j) + if (arr[j] > arr[j + 1]) + { + int temp = arr[j]; + arr[j] = arr[j + 1]; + arr[j + 1] = temp; + } +} + +//Driver Function +int main() +{ + int input_ar[] = {10, 50, 21, 2, 6, 66, 802, 75, 24, 170}; + int n = sizeof (input_ar) / sizeof (input_ar[0]); + bubble_sort (input_ar, n); + cout << "Sorted Array : " << endl; + for (int i = 0; i < n; ++i) + cout << input_ar[i] << " "; + return 0; +} + +/* +Sorted Array : +2 6 10 21 24 50 66 75 170 802 \ No newline at end of file diff --git a/c++/Combinational_Problems/C++ Program to Implement Bucket Sort.cpp b/c++/Combinational_Problems/C++ Program to Implement Bucket Sort.cpp new file mode 100644 index 0000000..b17b641 --- /dev/null +++ b/c++/Combinational_Problems/C++ Program to Implement Bucket Sort.cpp @@ -0,0 +1,53 @@ +/*This C++ Program implements Bucket Sort Algorithm. +Bucket sort is a sorting algorithm. It partitions an array into number of buckets, sorting each bucket individually using any good sorting algorithm and then concatenating each bucket. + +The basic steps of Bucket Sort are : +1. Set up buckets +2. Scatter original array +3. Sort each bucket +4. Gather all elements + +Bucket sort excepts it’s input in a specific range. The size of bucket should be taken as 1 greater than the largest element in the bucket. + +It’s worst case time complexity is O(n^2) and space complexity is O(n.m), which occurs when every element of input array is in one bucket. Average case time complexity is O(n + m), m is the number of buckets.*/ + +//This is a C++ Program to Sort an Array using Bucket Sort +#include +using namespace std; + +//Bucket Sort +void bucket_sort (int arr[], int n) +{ + //Here range is [1,100] + int m = 101; + //Create m empty buckets + int buckets[m]; + //Intialize all buckets to 0 + for (int i = 0; i < m; ++i) + buckets[i] = 0; + //Increment the number of times each element is present in the input + //array. Insert them in the buckets + for (int i = 0; i < n; ++i) + ++buckets[arr[i]]; + //Sort using insertion sort and concatenate + for (int i = 0, j = 0; j < m; ++j) + for (int k = buckets[j]; k > 0; --k) + arr[i++] = j; +} + + +//Driver function to test above function +int main() +{ + int input_ar[] = {10, 24, 22, 62, 1, 50, 100, 75, 2, 3}; + int n = sizeof (input_ar) / sizeof (input_ar[0]); + bucket_sort (input_ar, n); + cout << "Sorted Array : " << endl; + for (int i = 0; i < n; ++i) + cout << input_ar[i] << " "; + return 0; +} + +/* +Sorted Array : +1 2 3 10 22 24 50 62 75 100 \ No newline at end of file diff --git a/c++/Combinational_Problems/C++ Program to Implement Heap Sort.cpp b/c++/Combinational_Problems/C++ Program to Implement Heap Sort.cpp new file mode 100644 index 0000000..a0b0b1d --- /dev/null +++ b/c++/Combinational_Problems/C++ Program to Implement Heap Sort.cpp @@ -0,0 +1,92 @@ +/* + * C++ Program to Implement Heap Sort + */ +#include +#include +using namespace std; +void max_heapify(int *a, int i, int n) +{ + int j, temp; + temp = a[i]; + j = 2*i; + while (j <= n) + { + if (j < n && a[j+1] > a[j]) + j = j+1; + if (temp > a[j]) + break; + else if (temp <= a[j]) + { + a[j/2] = a[j]; + j = 2*j; + } + } + a[j/2] = temp; + return; +} +void heapsort(int *a, int n) +{ + int i, temp; + for (i = n; i >= 2; i--) + { + temp = a[i]; + a[i] = a[1]; + a[1] = temp; + max_heapify(a, 1, i - 1); + } +} +void build_maxheap(int *a, int n) +{ + int i; + for(i = n/2; i >= 1; i--) + { + max_heapify(a, i, n); + } +} +int main() +{ + int n, i, x; + cout<<"enter no of elements of array\n"; + cin>>n; + int a[20]; + for (i = 1; i <= n; i++) + { + cout<<"enter element"<<(i)<>a[i]; + } + build_maxheap(a,n); + heapsort(a, n); + cout<<"sorted output\n"; + for (i = 1; i <= n; i++) + { + cout< +#include +using namespace std; +int main() +{ + int a[16], i, j, k, temp; + cout<<"enter the elements\n"; + for (i = 0; i < 16; i++) + { + cin>>a[i]; + } + for (i = 1; i < 16; i++) + { + for (j = i; j >= 1; j--) + { + if (a[j] < a[j-1]) + { + temp = a[j]; + a[j] = a[j-1]; + a[j-1] = temp; + } + else + break; + } + } + cout<<"sorted array\n"< +#include +#include +using namespace std; +/* + * Node Declaration + */ +struct node +{ + int data; + struct node* next; +}; + + +struct node* SortedMerge(node* a, node* b); +void FrontBackSplit(node* source, node** frontRef, node** backRef); + +/* sorts the linked list by changing next pointers (not data) */ +void MergeSort(struct node** headRef) +{ + node* head = *headRef; + node* a; + node* b; + if ((head == NULL) || (head->next == NULL)) + { + return; + } + FrontBackSplit(head, &a, &b); + MergeSort(&a); + MergeSort(&b); + *headRef = SortedMerge(a, b); +} +/* merge the sorted linked lists */ +node* SortedMerge(struct node* a, struct node* b) +{ + node* result = NULL; + if (a == NULL) + return b; + else if (b==NULL) + return a; + if (a->data <= b->data) + { + result = a; + result->next = SortedMerge(a->next, b); + } + else + { + result = b; + result->next = SortedMerge(a, b->next); + } + return result; +} + +/* Split the nodes of the given list into front and back halves*/ +void FrontBackSplit(node* source, node** frontRef, node** backRef) +{ + node* fast; + node* slow; + if (source==NULL || source->next==NULL) + { + *frontRef = source; + *backRef = NULL; + } + else + { + slow = source; + fast = source->next; + while (fast != NULL) + { + fast = fast->next; + if (fast != NULL) + { + slow = slow->next; + fast = fast->next; + } + } + *frontRef = source; + *backRef = slow->next; + slow->next = NULL; + } +} + +/* print nodes in a given linked list */ +void printList(node *node) +{ + while (node != NULL) + { + cout<data<next; + } +} + +/* insert a node at the beginging of the linked list */ +void push(node** head_ref, int new_data) +{ + node *new_node = new node; + new_node->data = new_data; + new_node->next = (*head_ref); + (*head_ref) = new_node; +} +/* Main */ +int main() +{ + node* res = NULL; + node* a = NULL; + push(&a, 15); + push(&a, 10); + push(&a, 5); + push(&a, 20); + push(&a, 3); + push(&a, 2); + MergeSort(&a); + cout<<"\n Sorted Linked List is: \n"; + printList(a); + return 0; +} + +/* +Sorted Linked List is: +2 +3 +5 +10 +15 +20 diff --git a/c++/Combinational_Problems/C++ Program to Implement Merge Sort.cpp b/c++/Combinational_Problems/C++ Program to Implement Merge Sort.cpp new file mode 100644 index 0000000..cc3a6f1 --- /dev/null +++ b/c++/Combinational_Problems/C++ Program to Implement Merge Sort.cpp @@ -0,0 +1,181 @@ +/* + * C++ Program to Implement Merge Sort + */ +#include +using namespace std; +#include +void merge(int *,int, int, int ); +void mergesort(int *a, int low, int high) +{ + int mid; + if (low < high) + { + mid=(low+high)/2; + mergesort(a,low,mid); + mergesort(a,mid+1,high); + merge(a,low,high,mid); + } + return; +} +void merge(int *a, int low, int high, int mid) +{ + int i, j, k, c[50]; + i = low; + k = low; + j = mid + 1; + while (i <= mid && j <= high) + { + if (a[i] < a[j]) + { + c[k] = a[i]; + k++; + i++; + } + else + { + c[k] = a[j]; + k++; + j++; + } + } + while (i <= mid) + { + c[k] = a[i]; + k++; + i++; + } + while (j <= high) + { + c[k] = a[j]; + k++; + j++; + } + for (i = low; i < k; i++) + { + a[i] = c[i]; + } +} +int main() +{ + int a[20], i, b[20]; + cout<<"enter the elements\n"; + for (i = 0; i < 5; i++) + { + cin>>a[i]; + } + mergesort(a, 0, 4); + cout<<"sorted array\n"; + for (i = 0; i < 5; i++) + { + cout<>b[i]; + } + mergesort(b, 0, 4); + cout<<"sorted array\n"; + for (i = 0; i < 5; i++) + { + cout< + using namespace std; +#include + void merge(int *,int, int, int ); + void mergesort(int *a, int low, int high) + { + int mid; + if (low < high) + { + mid=(low+high)/2; + mergesort(a,low,mid); + mergesort(a,mid+1,high); + merge(a,low,high,mid); + } + return; + } + void merge(int *a, int low, int high, int mid) + { + int i, j, k, c[50]; + i = low; + k = low; + j = mid + 1; + while (i <= mid && j <= high) + { + if (a[i] < a[j]) + { + c[k] = a[i]; + k++; + i++; + } + else + { + c[k] = a[j]; + k++; + j++; + } + } + while (i <= mid) + { + c[k] = a[i]; + k++; + i++; + } + while (j <= high) + { + c[k] = a[j]; + k++; + j++; + } + for (i = low; i < k; i++) + { + a[i] = c[i]; + } + } + int main() + { + int a[20], i, b[20]; + cout<<"enter the elements\n"; + for (i = 0; i < 5; i++) + { + cin>>a[i]; + } + mergesort(a, 0, 4); + cout<<"sorted array\n"; + for (i = 0; i < 5; i++) + { + cout<>b[i]; + } + mergesort(b, 0, 4); + cout<<"sorted array\n"; + for (i = 0; i < 5; i++) + { + cout< +#include +using namespace std; +/* + * get maximum value in arr[] + */ +int getMax(int arr[], int n) +{ + int max = arr[0]; + for (int i = 1; i < n; i++) + if (arr[i] > max) + max = arr[i]; + return max; +} +/* + * count sort of arr[] + */ +void countSort(int arr[], int n, int exp) +{ + int output[n]; + int i, count[10] = {0}; + for (i = 0; i < n; i++) + count[(arr[i] / exp) % 10]++; + for (i = 1; i < 10; i++) + count[i] += count[i - 1]; + for (i = n - 1; i >= 0; i--) + { + output[count[(arr[i] / exp) % 10] - 1] = arr[i]; + count[(arr[i] / exp) % 10]--; + } + for (i = 0; i < n; i++) + arr[i] = output[i]; +} +/* + * sorts arr[] of size n using Radix Sort + */ +void radixsort(int arr[], int n) +{ + int m = getMax(arr, n); + for (int exp = 1; m / exp > 0; exp *= 10) + countSort(arr, n, exp); +} + +/* + * Main + */ +int main() +{ + int arr[] = {170, 45, 75, 90, 802, 24, 2, 66}; + int n = sizeof(arr)/sizeof(arr[0]); + radixsort(arr, n); + for (int i = 0; i < n; i++) + cout << arr[i] << " "; + return 0; +} + +/* +2 24 45 66 75 90 170 802 + +------------------ +(program exited with code: 1) +Press return to continue \ No newline at end of file diff --git a/c++/Combinational_Problems/C++ Program to Implement Selection Sort.cpp b/c++/Combinational_Problems/C++ Program to Implement Selection Sort.cpp new file mode 100644 index 0000000..1cf4a5f --- /dev/null +++ b/c++/Combinational_Problems/C++ Program to Implement Selection Sort.cpp @@ -0,0 +1,62 @@ +/*This C++ Program implements Selection Sort Algorithm. +Selection sort is a in-place comparison sort. The sorted array is built from left to right. The algorithm finds the the index value or position of the minimum element present in the array. Initially it assume the first element of the array. Then it loops over the array and find if present the index or position of value less than the minimum taken previously. After this it swaps those values, giving us the output in sorted order + +It’s time complexity is O(n^2) with theta (n) swaps.*/ + +//This is a C++ Program to Sort an Array using Selection Sort + +#include +using namespace std; + +void print (int [], int); +void selection_sort (int [], int); + +//Driver Function +int main () +{ + int min_ele_loc; + int ar[] = {10, 2, 45, 18, 16, 30, 29, 1, 1, 100}; + cout << "Array initially : "; + print (ar, 10); + selection_sort (ar, 10); + cout << "Array after selection sort : "; + print (ar, 10); + return 0; +} + +// Selection Sort +void selection_sort (int ar[], int size) +{ + int min_ele_loc; + for (int i = 0; i < 9; ++i) + { + //Find minimum element in the unsorted array + //Assume it's the first element + min_ele_loc = i; + //Loop through the array to find it + for (int j = i + 1; j < 10; ++j) + { + if (ar[j] < ar[min_ele_loc]) + { + //Found new minimum position, if present + min_ele_loc = j; + } + } + //Swap the values + swap (ar[i], ar[min_ele_loc]); + } +} + +//Print the array +void print (int temp_ar[], int size) +{ + for (int i = 0; i < size; ++i) + { + cout << temp_ar[i] << " "; + } + cout << endl; +} + +/* +Array intially : 10 2 45 18 16 30 29 1 1 100 +Array after selection sort : 1 1 2 10 16 18 29 30 45 100 \ No newline at end of file diff --git a/c++/Combinational_Problems/C++ Program to Implement Shell Sort.cpp b/c++/Combinational_Problems/C++ Program to Implement Shell Sort.cpp new file mode 100644 index 0000000..6f139fc --- /dev/null +++ b/c++/Combinational_Problems/C++ Program to Implement Shell Sort.cpp @@ -0,0 +1,64 @@ +/*This C++ Program implements Shell Sort Algorithm. +Shell sort is a sorting algorithm. It is an in-place comparison sort and one of the oldest sorting algorithm. +Shell sort is a generalization of insertion sort that allows the exchange of items that are far apart. Shell sort is not stable sort. It takes O(1) extra space. The worst case time complexity of shell sort depends on the increment sequence. + +Shell sort steps are : +1. Compare elements that are far apart. +2. Compare elements that are less far apart. Narrower array. +3. Do this repeatedly, reach to a point where compare adjancent elements. +4. Now the elements will be sufficiently sorted that the running time of the final stage will be closer to O(N). + +It is also called diminishing increment sort. + +The program has an input array of size 10 initialized with 10 values. This returns the array in non decreasing order using Shell Sort algorithm.*/ + +//This is a C++ Program to Sort an Array using Shell Sort +#include +using namespace std; + +//Print values +void print_ar (int ar[], int size) +{ + for (int i = 0; i < size; ++i) + { + cout << ar[i] << " "; + } + cout << endl; +} + +//Shell sort function +void shell_sort (int ar[], int size) +{ + int j; + //Narrow the array by 2 everytime + for (int gap = size / 2; gap > 0; gap /= 2) + { + for (int i = gap; i < size; ++i) + { + int temp = ar[i]; + for (j = i; j >= gap && temp < ar[j - gap]; j -= gap) + { + ar[j] = ar[j - gap]; + } + ar[j] = temp; + } + } +} + +//Driver Functions +int main () +{ + int ar[] = {1, 4, 16, 30, 29, 18, 100, 2, 43, 1}; + cout << "Intial Array : "; + print_ar (ar, 10); + shell_sort (ar, 10); + cout << "Sorted Array : "; + print_ar (ar, 10); + return 0; +} + +/* + + +Intial Array : 1 4 16 30 29 18 100 2 43 1 +Sorted Array : 1 1 2 4 16 18 29 30 43 100 \ No newline at end of file diff --git a/c++/Combinational_Problems/C++ Program to Solve Palindrome Partitioning Problem.cpp b/c++/Combinational_Problems/C++ Program to Solve Palindrome Partitioning Problem.cpp new file mode 100644 index 0000000..2d5a915 --- /dev/null +++ b/c++/Combinational_Problems/C++ Program to Solve Palindrome Partitioning Problem.cpp @@ -0,0 +1,64 @@ +/* + * C++ Program to Solve Palindrome Partitioning Problem + */ +#include +#include +#include +#include +#include +#include +using namespace std; + +// get minimum of two integers +int min (int a, int b) +{ + return (a < b)? a : b; +} + +/* Returns the minimum number of cuts needed to partition a string + * such that every part is a palindrome + */ +int minPalPartion(char *str) +{ + int n = strlen(str); + int C[n][n]; + bool P[n][n]; + int i, j, k, L; + for (i = 0; i < n; i++) + { + P[i][i] = true; + C[i][i] = 0; + } + for (L = 2; L <= n; L++) + { + for (i = 0; i < n - L + 1; i++) + { + j = i + L - 1; + if (L == 2) + P[i][j] = (str[i] == str[j]); + else + P[i][j] = (str[i] == str[j]) && P[i + 1][j - 1]; + if (P[i][j] == true) + C[i][j] = 0; + else + { + C[i][j] = INT_MAX; + for (k = i; k <= j - 1; k++) + C[i][j] = min (C[i][j], C[i][k] + C[k + 1][j] + 1); + } + } + } + return C[0][n-1]; +} + +// Main +int main() +{ + char str[] = "ababbbabbababa"; + cout<<"Min cuts needed for Palindrome Partitioning is: "< +#include +#include +using namespace std; +int main() +{ + int n, x; + cout<<"\nEnter the No. of Disks: "; + cin>>n; + for (x = 1; x < (1 << n); x++) + { + printf("\nMove from Peg %i to Peg %i", (x&x-1)%3+1, ((x|x-1)+1)%3+1); + } + cout<<"\n"; + getch(); +} + +/* +Move from Peg 1 to Peg 3 +Move from Peg 1 to Peg 2 +Move from Peg 3 to Peg 2 +Move from Peg 1 to Peg 3 +Move from Peg 2 to Peg 1 +Move from Peg 2 to Peg 3 +Move from Peg 1 to Peg 3 +Move from Peg 1 to Peg 2 +Move from Peg 3 to Peg 2 +Move from Peg 3 to Peg 1 +Move from Peg 2 to Peg 1 +Move from Peg 3 to Peg 2 +Move from Peg 1 to Peg 3 +Move from Peg 1 to Peg 2 +Move from Peg 3 to Peg 2 \ No newline at end of file diff --git a/c++/Combinational_Problems/Linked List Representation of Linear Queue.cpp b/c++/Combinational_Problems/Linked List Representation of Linear Queue.cpp new file mode 100644 index 0000000..f29ec47 --- /dev/null +++ b/c++/Combinational_Problems/Linked List Representation of Linear Queue.cpp @@ -0,0 +1,81 @@ + + + #include + #include + using namespace std; + struct node { + int + data; + struct + node *next; + } + *front=NULL,*rear,*temp; + void ins() { + temp=new + node; + cout<<“Enter + data:”; + cin>>temp->data; + temp->next=NULL; + if(front==NULL) + front=rear=temp; + else { + rear->next=temp; + rear=temp; + } + cout<<“Node + has been insertedn”; + } + void del() { + if(front==NULL) + cout<<“Queue + is emptyn”; else { + temp=front; + front=front->next; + cout<<“Deleted + node is “<data<<“n”; + delete(temp); + } + } + void dis() { + if(front==NULL) + cout<<“Queue + is emptyn”; else { + temp=front; + while(temp->next!=NULL) { + cout<data<<“->”; + temp=temp->next; + } + cout<data; + } + } + main() { + int ch; + while(1) { + cout<<“n*** + Menu ***”<<“n1.Insertn2.Deleten3.Displayn4.Exit”; + cout<<“nnEnter + your choice(1-4):”; + cin>>ch; + cout<<“n”; + switch(ch) { + case + 1: ins(); + break; + case + 2: del(); + break; + case + 3: dis(); + break; + case + 4: exit(0); + break; + default: + cout<<“Wrong Choice!!!”; + } + } + return + 0; + } + diff --git a/c++/Combinational_Problems/perform a PUSH operation on a dynamically allocated stack.cpp b/c++/Combinational_Problems/perform a PUSH operation on a dynamically allocated stack.cpp new file mode 100644 index 0000000..f29ec47 --- /dev/null +++ b/c++/Combinational_Problems/perform a PUSH operation on a dynamically allocated stack.cpp @@ -0,0 +1,81 @@ + + + #include + #include + using namespace std; + struct node { + int + data; + struct + node *next; + } + *front=NULL,*rear,*temp; + void ins() { + temp=new + node; + cout<<“Enter + data:”; + cin>>temp->data; + temp->next=NULL; + if(front==NULL) + front=rear=temp; + else { + rear->next=temp; + rear=temp; + } + cout<<“Node + has been insertedn”; + } + void del() { + if(front==NULL) + cout<<“Queue + is emptyn”; else { + temp=front; + front=front->next; + cout<<“Deleted + node is “<data<<“n”; + delete(temp); + } + } + void dis() { + if(front==NULL) + cout<<“Queue + is emptyn”; else { + temp=front; + while(temp->next!=NULL) { + cout<data<<“->”; + temp=temp->next; + } + cout<data; + } + } + main() { + int ch; + while(1) { + cout<<“n*** + Menu ***”<<“n1.Insertn2.Deleten3.Displayn4.Exit”; + cout<<“nnEnter + your choice(1-4):”; + cin>>ch; + cout<<“n”; + switch(ch) { + case + 1: ins(); + break; + case + 2: del(); + break; + case + 3: dis(); + break; + case + 4: exit(0); + break; + default: + cout<<“Wrong Choice!!!”; + } + } + return + 0; + } + diff --git a/c++/Computational_Geometry/C++ Program to Apply Above-Below-on Test to Find the Position of a Point with respect to a Line.cpp b/c++/Computational_Geometry/C++ Program to Apply Above-Below-on Test to Find the Position of a Point with respect to a Line.cpp new file mode 100644 index 0000000..69c04ad --- /dev/null +++ b/c++/Computational_Geometry/C++ Program to Apply Above-Below-on Test to Find the Position of a Point with respect to a Line.cpp @@ -0,0 +1,54 @@ +/*This is a C++ Program to check whether point lies above, below or on the line. For any point t (xt, yt) on the plane, its position with respect to the line L connecting p and q is found by calculating the scalar s: +s = A xt + B yt + C +If s < 0, t lies in the clockwise halfplane of L; if s > 0, t lies on the counter-clockwise halfplane; if s = 0, t lies on L. +For example, the equation of the line connecting points (2, 2) and (4, 5) is -3x + 2y + 2 = 0. The point (6, 3) lies in the clockwise halfplane of this line, because (-3)(6) + (2)(3) + 2 = -10. Conversely, the point (0, 5) lies in the other halfplane as (-3)(0) +(2)(5) +2 = 12.*/ + +#include +#include +#include +#include + +using namespace std; +const int LOW = 0; +const int HIGH = 10; +int main(int argc, char **argv) +{ + time_t seconds; + time(&seconds); + srand((unsigned int) seconds); + int x1, x2, y1, y2; + x1 = rand() % (HIGH - LOW + 1) + LOW; + x2 = rand() % (HIGH - LOW + 1) + LOW; + y1 = rand() % (HIGH - LOW + 1) + LOW; + y2 = rand() % (HIGH - LOW + 1) + LOW; + cout << "The Equation of the 1st line is : (" << (y2 - y1) << ")x+(" << (x1 + - x2) << ")y+(" << (x2 * y1 - x1 * y2) << ") = 0\n"; + int x, y; + cout << "\nEnter the point:"; + cin >> x; + cin >> y; + int s = (y2 - y1) * x + (x1 - x2) * y + (x2 * y1 - x1 * y2); + if (s < 0) + cout << "The point lies below the line or left side of the line"; + else if (s > 0) + cout << "The point lies above the line or right side of the line"; + else + cout << "The point lies on the line"; + return 0; +} + +/* +The Equation of the 1st line is : (3)x+(0)y+(-3) = 0 + +Enter the point:1 4 +The point lies on the line + +The Equation of the 1st line is : (5)x+(-1)y+(-25) = 0 + +Enter the point:1 1 +The point lies below the line or left side of the line + +The Equation of the 1st line is : (-6)x+(8)y+(-24) = 0 + +Enter the point:19 21 +The point lies above the line or right side of the line \ No newline at end of file diff --git a/c++/Computational_Geometry/C++ Program to Check Whether a Given Points are Colinear or Not.cpp b/c++/Computational_Geometry/C++ Program to Check Whether a Given Points are Colinear or Not.cpp new file mode 100644 index 0000000..b9040d3 --- /dev/null +++ b/c++/Computational_Geometry/C++ Program to Check Whether a Given Points are Colinear or Not.cpp @@ -0,0 +1,38 @@ +#include +#include +#include + +using namespace std; + +const int LOW = 1; +const int HIGH = 10; + +int main(int argc, char **argv) +{ + int x, y, x1, x2, y1, y2; + time_t seconds; + time(&seconds); + srand((unsigned int) seconds); + x = rand() % (HIGH - LOW + 1) + LOW; + y = rand() % (HIGH - LOW + 1) + LOW; + x1 = rand() % (HIGH - LOW + 1) + LOW; + x2 = rand() % (HIGH - LOW + 1) + LOW; + y1 = rand() % (HIGH - LOW + 1) + LOW; + y2 = rand() % (HIGH - LOW + 1) + LOW; + cout << "The points are: (" << x << ", " << y << "), (" << x1 << ", " << y1 + << "), & (" << x2 << ", " << y2 << ")\n"; + cout << "The Equation of the line is : (" << (y2 - y1) << ")x+(" << (x1 + - x2) << ")y+(" << (x2 * y1 - x1 * y2) << ") = 0\n"; + int s = (y2 - y1) * x + (x1 - x2) * y + (x2 * y1 - x1 * y2); + if (s < 0) + cout << "The points are NOT colinear"; + else if (s > 0) + cout << "The points are NOT colinear"; + else + cout << "The points are colinear"; +} + +/* +The points are: (9, 5), (4, 6), & (1, 2) +The Equation of the line is : (-4)x+(3)y+(-2) = 0 +The points are NOT colinear \ No newline at end of file diff --git a/c++/Computational_Geometry/C++ Program to Check if a Point d lies Inside or Outside a Circle Defined by Points a, b, c in a Plane.cpp b/c++/Computational_Geometry/C++ Program to Check if a Point d lies Inside or Outside a Circle Defined by Points a, b, c in a Plane.cpp new file mode 100644 index 0000000..abdc1a9 --- /dev/null +++ b/c++/Computational_Geometry/C++ Program to Check if a Point d lies Inside or Outside a Circle Defined by Points a, b, c in a Plane.cpp @@ -0,0 +1,62 @@ +/*This is a C++ Program to Check if a Point d lies Inside or Outside a Circle Defined by Points a, b, c in a Plane. For any point t (xt, yt) on the plane, its position with respect to the circle defined by 3 points (x1, y1) , (x2, y2), (x3, y3). +s = (x-xt)^2 + (y-yt)^2 – r*r +If s < 0, t lies inside the circle; if s > 0, t lies outside the circle; if s = 0, t lies on the circle.*/ + +#include +#include +#include +#include + +using namespace std; +const int LOW = 0; +const int HIGH = 10; +int main(int argc, char **argv) +{ + time_t seconds; + time(&seconds); + srand((unsigned int) seconds); + double x1, x2, y1, y2, x3, y3; + double m1, m2, c1, c2, r; + x1 = rand() % (HIGH - LOW + 1) + LOW; + x2 = rand() % (HIGH - LOW + 1) + LOW; + x3 = rand() % (HIGH - LOW + 1) + LOW; + y1 = rand() % (HIGH - LOW + 1) + LOW; + y2 = rand() % (HIGH - LOW + 1) + LOW; + y3 = rand() % (HIGH - LOW + 1) + LOW; + m1 = (y1 - y2) / (x1 - x2); + m2 = (y3 - y2) / (x3 - x2); + c1 = ((m1 * m2 * (y3 - y1)) + (m1 * (x2 + x3)) - (m2 * (x1 + x2))) / (2 + * (m1 - m2)); + c2 = ((((x1 + x2) / 2) - c1) / (-1 * m1)) + ((y1 + y2) / 2); + r = sqrt(((x3 - c1) * (x3 - c1)) + ((y3 - c2) * (y3 - c2))); + cout << "The points on the circle are: (" << x1 << ", " << y1 << "), (" + << x2 << ", " << y2 << "), (" << x3 << ", " << y3 << ")"; + cout << "\nThe center of the circle is (" << c1 << ", " << c2 + << ") and radius is " << r; + cout << "\nEnter the point : ,"; + int x, y; + cin >> x; + cin >> y; + double s = ((x - c1) * (x - c1)) + ((y - c2) * (y - c1)) - (r * r); + if (s < 0) + cout << "\nThe point lies inside the circle"; + else if (s > 0) + cout << "\nThe point lies outside the circle"; + else + cout << "\nThe point lies on the circle"; + return 0; +} + +/* + +The points on the circle are: (2, 5), (10, 8), (3, 6) +The center of the circle is (8.7, 13.7) and radius is 9.58019 +Enter the point : , 1 2 + +The point lies outside the circle + +The points on the circle are: (0, 6), (9, 7), (6, 10) +The center of the circle is (4.6, 7.4) and radius is 2.95296 +Enter the point : ,6 5 + +The point lies inside the circle \ No newline at end of file diff --git a/c++/Computational_Geometry/C++ Program to Compute Cross Product of Two Vectors.cpp b/c++/Computational_Geometry/C++ Program to Compute Cross Product of Two Vectors.cpp new file mode 100644 index 0000000..c1ccd24 --- /dev/null +++ b/c++/Computational_Geometry/C++ Program to Compute Cross Product of Two Vectors.cpp @@ -0,0 +1,39 @@ +/*This is a C++ Program to find the cross product of two vectors. In mathematics, the cross product or vector product is a binary operation on two vectors in three-dimensional space. It results in a vector that is perpendicular to both and therefore normal to the plane containing them.*/ + +#include +#include +#include +#include + +using namespace std; +const int LOW = 0; +const int HIGH = 10; +int main(int argc, char **argv) +{ + time_t seconds; + time(&seconds); + srand((unsigned int) seconds); + int u1, u2, u3, v1, v2, v3; + u1 = rand() % (HIGH - LOW + 1) + LOW; + u2 = rand() % (HIGH - LOW + 1) + LOW; + u3 = rand() % (HIGH - LOW + 1) + LOW; + v1 = rand() % (HIGH - LOW + 1) + LOW; + v2 = rand() % (HIGH - LOW + 1) + LOW; + v3 = rand() % (HIGH - LOW + 1) + LOW; + int uvi, uvj, uvk; + uvi = u2 * v3 - v2 * u3; + uvj = v1 * u3 - u1 * v3; + uvk = u1 * v2 - v1 * u2; + cout << "The cross product of the 2 vectors \n u = " << u1 << "i + " << u2 + << "j + " << u3 << "k and \n v = " << u1 << "i + " << u2 << "j + " + << u3 << "k \n "; + cout << "u X v : " << uvi << "i +" << uvj << "j+ " << uvk << "k "; + return 0; +} + +/* + +The cross product of the 2 vectors + u = 6i + 9j + 9k and + v = 6i + 9j + 9k + u X v : 0i +6j+ -6k \ No newline at end of file diff --git a/c++/Computational_Geometry/C++ Program to Compute the Area of a Triangle Using Determinants.cpp b/c++/Computational_Geometry/C++ Program to Compute the Area of a Triangle Using Determinants.cpp new file mode 100644 index 0000000..21a787b --- /dev/null +++ b/c++/Computational_Geometry/C++ Program to Compute the Area of a Triangle Using Determinants.cpp @@ -0,0 +1,89 @@ +/*This is a C++ program to find the area of triangle using determinants. +Formula for the area of a triangle using determinants +x1 y1 1 +Area=±1/2 x2 y2 1 +x3 y3 1 +The plus/minus in this case is meant to take whichever sign is needed so the answer is positive (non-negative). Do not say the area is both positive and negative.*/ + +#include +#include +#include +#include + +using namespace std; + +double det(int n, double mat[3][3]) +{ + double submat[3][3]; + float d; + for (int c = 0; c < n; c++) + { + int subi = 0; //submatrix's i value + for (int i = 1; i < n; i++) + { + int subj = 0; + for (int j = 0; j < n; j++) + { + if (j == c) + continue; + submat[subi][subj] = mat[i][j]; + subj++; + } + subi++; + } + d = d + (pow(-1, c) * mat[0][c] * det(n - 1, submat)); + } + return d; +} + +int main(int argc, char **argv) +{ + cout << "Enter the points of the triangle:\n"; + int x1, x2, x3, y1, y2, y3; + cin >> x1; + cin >> y1; + cin >> x2; + cin >> y2; + cin >> x3; + cin >> y3; + double mat[3][3]; + mat[0][0] = x1; + mat[0][1] = y1; + mat[0][2] = 1; + mat[1][0] = x2; + mat[1][1] = y2; + mat[1][2] = 1; + mat[2][0] = x3; + mat[2][1] = y3; + mat[2][2] = 1; + cout << "\nMatrix formed by the points: \n"; + for (int i = 0; i < 3; i++) + { + for (int j = 0; j < 3; j++) + cout << mat[i][j] << " "; + cout << endl; + } + float determinant = det(3, mat)*0.5; + if (determinant < 0) + cout << "The Area of the triangle formed by (" << x1 << "," << y1 + << "), (" << x2 << "," << y2 << "), (" << x3 << "," << y3 + << ") = " << (determinant * -1); + else + cout << "The Area of the triangle formed by (" << x1 << "," << y1 + << "), (" << x2 << "," << y2 << "), (" << x3 << "," << y3 + << ") = " << determinant; + return 0; +} + +/* + +Enter the points of the triangle: +3 4 +6 4 +3 9 + +Matrix formed by the points: +3 4 1 +6 4 1 +3 9 1 +The Area of the triangle formed by (3,4), (6,4), (3,9) = 7.5 \ No newline at end of file diff --git a/c++/Computational_Geometry/C++ Program to Compute the Volume of a Tetrahedron Using Determinants.cpp b/c++/Computational_Geometry/C++ Program to Compute the Volume of a Tetrahedron Using Determinants.cpp new file mode 100644 index 0000000..d76e8f9 --- /dev/null +++ b/c++/Computational_Geometry/C++ Program to Compute the Volume of a Tetrahedron Using Determinants.cpp @@ -0,0 +1,133 @@ +/*This is a C++ Program to find the volume of tetrahedron. +Call the four vertices of the tetrahedron (a, b, c), (d, e, f), (g, h, i), and (p, q, r). Now create a 4-by-4 matrix in which the coordinate triples form the colums of the matrix, with a row of 1’s appended at the bottom: +a d g p +b e h q +c f i r +1 1 1 1 +The volume of the tetrahedron is 1/6 times the absolute value of the matrix determinant. For any 4-by-4 matrix that has a row of 1’s along the bottom, you can compute the determinant with a simplification formula that reduces the problem to a 3-by-3 matrix +a-p d-p g-p +b-q e-q h-q +c-r f-r i-r*/ + +#include +#include +#include +#include + +using namespace std; + +double det(int n, double mat[3][3]) +{ + double submat[3][3]; + float d; + for (int c = 0; c < n; c++) + { + int subi = 0; //submatrix's i value + for (int i = 1; i < n; i++) + { + int subj = 0; + for (int j = 0; j < n; j++) + { + if (j == c) + continue; + submat[subi][subj] = mat[i][j]; + subj++; + } + subi++; + } + d = d + (pow(-1, c) * mat[0][c] * det(n - 1, submat)); + } + return d; +} + +int main(int argc, char **argv) +{ + cout << "Enter the points of the triangle:\n"; + int x1, x2, x3, x4, y1, y2, y3, y4, z1, z2, z3, z4; + cin >> x1; + cin >> x2; + cin >> x3; + cin >> x4; + cin >> y1; + cin >> y2; + cin >> y3; + cin >> y4; + cin >> z1; + cin >> z2; + cin >> z3; + cin >> z4; + double mat[4][4]; + mat[0][0] = x1; + mat[0][1] = x2; + mat[0][2] = x3; + mat[0][3] = x4; + mat[1][0] = y1; + mat[1][1] = y2; + mat[1][2] = y3; + mat[1][3] = y4; + mat[2][0] = z1; + mat[2][1] = z2; + mat[2][2] = z3; + mat[2][3] = z4; + mat[3][0] = 1; + mat[3][1] = 1; + mat[3][2] = 1; + mat[3][3] = 1; + cout << "\nMatrix formed by the points: \n"; + for (int i = 0; i < 4; i++) + { + for (int j = 0; j < 4; j++) + { + cout << mat[i][j] << " "; + } + cout << endl; + } + double matrix[3][3]; + matrix[0][0] = x1 - x4; + matrix[0][1] = x2 - x4; + matrix[0][2] = x3 - x4; + matrix[1][0] = y1 - y4; + matrix[1][1] = y2 - y4; + matrix[1][2] = y3 - y4; + matrix[2][0] = z1 - z4; + matrix[2][1] = z2 - z4; + matrix[2][2] = z3 - z4; + for (int i = 0; i < 3; i++) + { + for (int j = 0; j < 3; j++) + { + cout << matrix[i][j] << " "; + } + cout << endl; + } + float determinant = det(3, matrix) / 6; + if (determinant < 0) + cout << "The Area of the tetrahedron formed by (" << x1 << "," << y1 + << "," << z1 << "), (" << x2 << "," << y2 << "," << z2 + << "), (" << x3 << "," << y3 << "," << z3 << "), (" << x4 << "," + << y4 << "," << z4 << ") = " << (determinant * -1); + else + cout << "The Area of the tetrahedron formed by (" << x1 << "," << y1 + << "," << z1 << "), (" << x2 << "," << y2 << "," << z2 + << "), (" << x3 << "," << y3 << "," << z3 << "), (" << x4 << "," + << y4 << "," << z4 << ") = " << determinant; + return 0; +} + +/* + +Enter the points of the triangle: +0 9 6 0 +4 2 1 1 +3 4 7 5 + +Matrix formed by the points: +0 9 6 0 +4 2 1 1 +3 4 7 5 +1 1 1 1 + +0 9 6 +3 1 0 +-2 -1 2 +The Area of the tetrahedron formed by (0,4,3), (9,2,4), (6,1,7), (0,1,5) = 10.0 \ No newline at end of file diff --git a/c++/Computational_Geometry/C++ Program to Find Largest Rectangular Area in a Histogram.cpp b/c++/Computational_Geometry/C++ Program to Find Largest Rectangular Area in a Histogram.cpp new file mode 100644 index 0000000..b2c3cb8 --- /dev/null +++ b/c++/Computational_Geometry/C++ Program to Find Largest Rectangular Area in a Histogram.cpp @@ -0,0 +1,115 @@ +/* + * C++ Program to Find Largest Rectangular Area in a Histogram + */ +#include +#include +#include +#include +#define max(x, y, z) max(max(x, y) , z) +using namespace std; +/* + * get minimum of two numbers in hist[] + */ +int minVal(int *hist, int i, int j) +{ + if (i == -1) + return j; + if (j == -1) + return i; + return (hist[i] < hist[j])? i : j; +} +/* + * get the middle index from corner indexes. + */ +int getMid(int s, int e) +{ + return s + (e -s)/2; +} + +/* + * get the index of minimum value in a given range of indexes. + */ +int RMQUtil(int *hist, int *st, int ss, int se, int qs, int qe, int index) +{ + if (qs <= ss && qe >= se) + return st[index]; + if (se < qs || ss > qe) + return -1; + int mid = getMid(ss, se); + return minVal(hist, RMQUtil(hist, st, ss, mid, qs, qe, 2 * index + 1), + RMQUtil(hist, st, mid + 1, se, qs, qe, 2 * index + 2)); +} +/* + * Return index of minimum element in range from index qs to qe + */ +int RMQ(int *hist, int *st, int n, int qs, int qe) +{ + if (qs < 0 || qe > n - 1 || qs > qe) + { + cout << "Invalid Input"; + return -1; + } + return RMQUtil(hist, st, 0, n - 1, qs, qe, 0); +} +/* + * constructs Segment Tree for hist[ss..se]. + */ +int constructSTUtil(int hist[], int ss, int se, int *st, int si) +{ + if (ss == se) + return (st[si] = ss); + int mid = getMid(ss, se); + st[si] = minVal(hist, constructSTUtil(hist, ss, mid, st, si * 2 + 1), + constructSTUtil(hist, mid + 1, se, st, si * 2 + 2)); + return st[si]; +} + +/* + * construct segment tree from given array. + */ +int *constructST(int hist[], int n) +{ + int x = (int)(ceil(log2(n))); + int max_size = 2 * (int)pow(2, x) - 1; + int *st = new int[max_size]; + constructSTUtil(hist, 0, n - 1, st, 0); + return st; +} + +/* + * find the maximum rectangular area. + */ +int getMaxAreaRec(int *hist, int *st, int n, int l, int r) +{ + if (l > r) + return INT_MIN; + if (l == r) + return hist[l]; + int m = RMQ(hist, st, n, l, r); + return max (getMaxAreaRec(hist, st, n, l, m - 1), + getMaxAreaRec(hist, st, n, m + 1, r), (r - l + 1) * (hist[m])); +} + +/* + * find max area + */ +int getMaxArea(int hist[], int n) +{ + int *st = constructST(hist, n); + return getMaxAreaRec(hist, st, n, 0, n - 1); +} + +/* + * Main + */ +int main() +{ + int hist[] = {6, 1, 5, 4, 5, 2, 6}; + int n = sizeof(hist)/sizeof(hist[0]); + cout << "Maximum area is " << getMaxArea(hist, n)< +#include +#include +#include + +void main() +{ + double y[20][20],x[20]; + /* ARRAY OF N*N ELEMENTS FOR BACKWARD DIFFERENCE TABLE */ + int i,j,k,n; + clrscr(); + printf("\n\tBACKWARD DIFFERENCES GENERATION FOR INTERPOLATION"); + printf("\n\n The form of equation is y = f(x)\n"); + printf("\n\nEnter the number of entries (max 20) = "); + scanf("%d",&n); /* ENTER NUMBER OF ENTRIES IN THE TABLE */ + for(i = 0; i < n; i++) + { + /* LOOP TO GET x AND y = f(x) IN THE TABLE */ + printf("x%d = ",i); + scanf("%lf",&x[i]); + printf(" y%d = ",i); + scanf("%lf",&y[i][0]); + } + k = 0; + for(j = 1; j < n; j++) + { + /* LOOP TO CALCULATE BACKWARD DIFFERENCES */ + k++; + for(i = n-1; i >= k; i--) + { + y[i][j] = y[i][j-1] - y[i-1][j-1]; + } + } + k = n ; + clrscr(); + printf("\n The backward difference table is as follows . . .\n"); + printf("\n\tx\ty\tDy\tD2y\tD3y\tD4y\tD5y\tD6y\n"); + for(i = 0; i < n; i++) + { + /* LOOP TO PRINT BACKWARD DIFFERENCES */ + printf("\nx%d = %4.2lf",i,x[i]); + for(j = 0; j < i+1; j++) + { + printf("\t%4.2lf ",y[i][j]); + } + printf("\n"); + } +} +/*------------------------------End of program-------------------------*/ \ No newline at end of file diff --git a/c++/Computational_Geometry/C++ Program to Implement BINARY SEARCH METHOD.cpp b/c++/Computational_Geometry/C++ Program to Implement BINARY SEARCH METHOD.cpp new file mode 100644 index 0000000..73b3d3f --- /dev/null +++ b/c++/Computational_Geometry/C++ Program to Implement BINARY SEARCH METHOD.cpp @@ -0,0 +1,87 @@ +/* */ +/* File name : bin_srch.cpp */ + +/*-------------------- BINARY SEARCH METHOD --------------------------*/ + +/* THIS PROGRAM SEARCHES A NUMBER IN THE SORTED ARRAY. + + INPUTS : 1) The total number of elements in the sorted array. + + 2) Array of numbers. + + 3) An element to be searched for. + + OUTPUTS : The position of the number in array. */ + +/*------------------------------ PROGRAM -------------------------*/ + +#include +#include +#include +#include + +void main() +{ + double x[100],y[100],z; /*DECLARATION OF ARRAY */ + int i,n,k,j,t; + clrscr(); + printf("\n Computational Techniques - J. S. CHITODE"); + printf("\n BINARY SEARCH METHOD\n"); + printf("\n\nEnter the total number of elements " + "in the array(max 100) = "); + scanf("%d",&n); /* ENTER THE NUMBER OF ELEMENTS IN THE ARRAY */ + for(i = 0; i < n; i++) + { + /* LOOP TO ENTER ACTUAL VALUES OF ARRAY ELEMENTS */ + printf("\nx%d = ",i); + scanf("%lf",&x[i]); + } + printf("\nEnter the number to be searched = "); + scanf("%lf",&z); /* NUMBER TO BE SEARCHED FOR */ + k = n/2; /* MIDDLE OF THE ARRAY */ + t = 0; + while(k >= 1) + { + if(x[0] == z) /* CHECK IF x[0] IS THE NUMBER TO BE SEARCHED */ + { + printf("match is found at key = 0"); + break; /* break IS USED TO GO OUT OF THE LOOP */ + } + if(x[n-1] == z) /* CHECK IF x[n-1] IS THE NUMBER TO BE SEARCHED*/ + { + printf("match is found at key = %d",n-1); + break; /* break IS USED TO GO OUT OF THE LOOP */ + } + if(x[k] > z) /* CHECK IN THE TOP HALF */ + { + k = (k+1)/2; + if(x[k] == z) + { + printf("match is found at key = %d",k); + break; + } + for(i = 0; i < k; i++) + { + y[i] = x[i]; + } + } + if(x[k] <= z) /* CHECK IN THE BOTTOM HALF */ + { + k = (k+1)/2; + if(x[k] == z) + { + printf("match is found at key = %d",n-k-1); + break; + } + for(i = k,j = 0; i < n; i++,j++) + { + y[j] = x[i]; + } + } + for(i = 0; i <= k; i++) + { + x[i] = y[i]; /*FORM THE NEW ARRAY OF k/2 ELEMENTS */ + } + } +} +/*------------------------ END OF PROGRAM ------------------------------*/ diff --git a/c++/Computational_Geometry/C++ Program to Implement BISECTION METHOD TO FIND ROOT OF AN EQUATION.cpp b/c++/Computational_Geometry/C++ Program to Implement BISECTION METHOD TO FIND ROOT OF AN EQUATION.cpp new file mode 100644 index 0000000..935f979 --- /dev/null +++ b/c++/Computational_Geometry/C++ Program to Implement BISECTION METHOD TO FIND ROOT OF AN EQUATION.cpp @@ -0,0 +1,74 @@ + + +/*------------ BISECTION METHOD TO FIND ROOT OF AN EQUATION ----------*/ + +/* THE EXPRESSION FOR AN EQUATION IS DEFINED IN function fx + YOU CAN WRITE DIFFERENT EQUATION IN function fx. + HERE, + f(x) = x*x*x - 1.8*x*x - 10*x - 17 + + INPUTS : 1) Initial interval [a,b] in which root is to + be found. + 2) Permissible error in the root. + + OUTPUTS : 1) Number of iterations for given interval and + permissible error. + 3) Value of the root in given interval. */ + +/*------------------------------ PROGRAM --------------------------*/ + +#include +#include +#include +#include + +void main() +{ + double fx ( double x); /* DECLARATION OF FUNCTION */ + double x,a,b,fa,fb,c,fc,err; + int n,i; + clrscr(); + printf("\n BISECTION METHOD TO FIND ROOT OF AN EQUATION"); + printf("\n\n f(x) = x*x*x - 1.8*x*x - 10*x - 17"); + printf("\n\nEnter an interval [a,b] in " + "which root is to be found"); + printf("\na = "); + scanf("%lf",&a); /* INTERVAL [a,b] IS TO BE ENTERED HERE */ + printf("b = "); + scanf("%lf",&b); + printf("\nEnter the value of permissible error = "); + scanf("%lf",&err); + n = (log10(abs(b - a)) - log10( err ) )/log10(2); + /* CALCULATION OF STEPS 'n' */ + n = n + 1; /* n SHOULD NOT BE A FRACTIONAL NUMBER; ADD '1' */ + i = 0; + printf("\nNumber of iterations for this error bound are = %d",n); + printf("\n\npress any key for step by step display of intervals"); + getch(); + printf("\n\n RESULTS OF BISECTION METHOD\n"); + while(n-- > 0) + { + fa = fx(a); /* CALCULATE f(x) AT x = a */ + fb = fx(b); /* CALCULATE f(x) AT x = b */ + c = (a + b)/2; /* CENTER OF THE INTERVAL */ + fc = fx(c); /* CALCULATE f(x) AT x = c */ + i++; + printf("\n\n%d a = %lf b = %lf c = %lf",i,a,b,c); + printf("\n f(a) = %lf f(b) = %lf f(c) = %lf",fa,fb,fc); + if( (fc*fa) < 0) b = c; /* IF f(c)f(a) < 0, NEW INTERVAL IS [a,c] */ + if( (fc*fb) < 0) a = c; /* IF f(c)f(b) < 0, NEW INTERVAL IS [b,c] */ + printf("\n interval : a = %lf b = %lf",a,b); + getch(); + } + x = a + (b - a)/2; /* ROOT = a + half interval [a,b] */ + printf("\nThe value of root is = %20.15lf",x); /* ROOT */ +} +/*---------- FUNCTION PROCEDURE TO CALCULATE VALUE OF EQUATION --------*/ + +double fx ( double x) +{ + double f; + f = x*x*x - 1.8*x*x - 10*x + 17; /* FUNCTION f(x) */ + return(f); +} +/*------------------------ END OF PROGRAM -----------------------------*/ diff --git a/c++/Computational_Geometry/C++ Program to Implement BUBBLE SORT METHOD.cpp b/c++/Computational_Geometry/C++ Program to Implement BUBBLE SORT METHOD.cpp new file mode 100644 index 0000000..fc81d90 --- /dev/null +++ b/c++/Computational_Geometry/C++ Program to Implement BUBBLE SORT METHOD.cpp @@ -0,0 +1,58 @@ + + +/*-------------------- BUBBLE SORT METHOD ----------------------------*/ + +/* THIS PROGRAM SORTS THE INPUT ARRAY INTO ASCENDING ORDER + USING BUBBLE SORT METHOD. + + INPUTS : 1) The total number of elements to be sorted. + + 2) Array of numbers. + + OUTPUTS : Sorted array of elements. */ + +/*------------------------------ PROGRAM ----------------------------*/ + +#include +#include +#include +#include + +void main() +{ + double x[100],z; /*DECLARATION OF ARRAY */ + int i,n,k; + clrscr(); + printf("\n Computational Techniques - J. S. CHITODE"); + printf("\n BUBBLE SORT METHOD\n"); + printf("\n\nEnter the total number of elements " + "to sorted (max 100) = "); + scanf("%d",&n); /* ENTER THE NUMBER OF ELEMENTS TO BE SORTED */ + for(i = 0; i < n; i++) + { + /* LOOP TO ENTER ACTUAL VALUES OF ARRAY ELEMENTS */ + printf("\nx%d = ",i); + scanf("%lf",&x[i]); + } + for(i = 0; i < n-1; i++) + { + /* LOOP TO SORT THE ARRAY */ + for(k = 0; k < n-1; k++) + { + if(x[k] > x[k+1]) + { + z = x[k]; + x[k] = x[k+1]; + x[k+1] = z; + } + } + } + printf("\nThe sorted array in ascending order is ....\n"); + for(i = 0; i < n; i++) + { + /* LOOP TO PRINT THE ARRAY */ + printf("\nx%d = %lf",i,x[i]); + } +} + +/*------------------------ END OF PROGRAM ------------------------------*/ diff --git a/c++/Computational_Geometry/C++ Program to Implement CALCULATION OF TRUNCATION ERROR OF SERIES APPROXIMATION.cpp b/c++/Computational_Geometry/C++ Program to Implement CALCULATION OF TRUNCATION ERROR OF SERIES APPROXIMATION.cpp new file mode 100644 index 0000000..38cd17f --- /dev/null +++ b/c++/Computational_Geometry/C++ Program to Implement CALCULATION OF TRUNCATION ERROR OF SERIES APPROXIMATION.cpp @@ -0,0 +1,66 @@ + + +/*----- CALCULATION OF TRUNCATION ERROR OF SERIES APPROXIMATION -------*/ + +/* EXPONENTIAL SERIES exp(x) IS USED HERE + + INPUTS : 1) The total number of terms to be computed + in series starting from first term. + 2) The value of 'x' in exp(x). + + OUTPUTS : 1) Computed value of series approximation of exp(x). + 2) Actual value of exp(x) function. + 3) Absolute error between series approximation and + actual value of exp(x) function. */ + +/*------------------------------ PROGRAM --------------------------*/ + +#include +#include +#include +#include + +void main() +{ + double fact ( int n); /* DECLARATION OF FACTORIAL FUNCTION */ + double x,sum,z,sum1; + int n,i; + clrscr(); + printf("\n\t\tCALCULATION OF TRUNCATION ERROR " + "OF SERIES APPROXIMATION"); + printf("\n\nGive number of terms " + "in series to be computed = "); + scanf("%d",&n); /* NUMBER OF TERMS TO BE COMPUTED IN SERIES */ + n = n - 1; /* TERMS ARE COMPUTED FROM ZERO HENCE 'n-1' */ + printf("\nGive value of x = "); + scanf("%lf",&x); /* VALUE OF 'x' */ + sum = 0; + sum1 = 0; + for(i = 0; i<=n; i++) + { + z = fact(i); + sum = pow(x,(double)i)/z; + sum1 = sum1 + sum; + } + printf("\nThe computed value of exp(x) " + "function is = %1.15lf",sum1); /* COMPUTED VALUE */ + printf("\n\nThe actual value of exp(x) " + "function is = %1.15lf",exp(x)); /* ACTUAL VALUE */ + printf("\n\nTruncation error in series " + "approximation is = %1.15lf", exp(x)-sum1); /* ERROR */ +} +/*------------- FUNCTION PROCEDURE TO CALCULATE FACTORIAL -------------*/ + +double fact( int n) +{ + double facto; + facto = 1; + if(n == 0) return( facto = 1); + do + { + facto = facto * n; + } + while(n-- > 1); + return(facto); +} +/*----------------------- END OF PROGRAM ----------------------------*/ diff --git a/c++/Computational_Geometry/C++ Program to Implement DIVIDED DIFFERENCES GENERATION FOR INTERPOLATION.cpp b/c++/Computational_Geometry/C++ Program to Implement DIVIDED DIFFERENCES GENERATION FOR INTERPOLATION.cpp new file mode 100644 index 0000000..cce08e4 --- /dev/null +++ b/c++/Computational_Geometry/C++ Program to Implement DIVIDED DIFFERENCES GENERATION FOR INTERPOLATION.cpp @@ -0,0 +1,68 @@ + + +/*-------------- DIVIDED DIFFERENCES GENERATION FOR INTERPOLATION -----*/ + +/* THE PROGRAM GENERATES A DIVIDED DIFFERENCES TABLE FROM GIVEN + + DATA. THE VALUES OF x AND CORRESPONDING y = f(x) ARE TO BE + + ENTERED IN THE ARRAY FORMAT. + + INPUTS : 1) Number of entries of the data. + + 2) Values of 'x' & corresponding y = f(x). + + OUTPUTS : divided difference table array. */ + +/*------------------------------ PROGRAM --------------------------*/ + +#include +#include +#include +#include + +void main() +{ + double y[20][20],x[20]; + /* ARRAY OF y[n][n] ELEMENTS FOR DIVIDED DIFFERENCE TABLE */ + int i,j,k,n; + clrscr(); + printf("\n\tDIVIDED DIFFERENCES GENERATION FOR INTERPOLATION"); + printf("\n\n The form of equation is y = f(x)\n"); + printf("\n\nEnter the number of entries (max 20) = "); + /* ENTER THE NUMBER OF ENTRIES IN THE TABLE */ + scanf("%d",&n); + for(i = 0; i < n; i++) + { + /* LOOP TO GET x AND y = f(x) IN THE TABLE */ + printf("x%d = ",i); + scanf("%lf",&x[i]); + printf(" y%d = ",i); + scanf("%lf",&y[i][0]); + } + k = n; + for(j = 1; j < n; j++) + { + /* LOOP TO CALCULATE DIVIDED DIFFERENCES IN THE TABLE*/ + k = k - 1; + for(i = 0; i < k; i++) + { + y[i][j] = (y[i+1][j-1] - y[i][j-1])/(x[i+j]-x[i]); + } + } + k = n; + clrscr(); + printf("\n The divided difference table is as follows . . .\n"); + printf("\n\tx\ty\tDy\tD2y\tD3y\tD4y\tD5y\tD6y\n"); + for(i = 0; i < n; i++) + { + /* LOOP TO PRINT DIVIDED DIFFERENCES IN THE TABLE */ + printf("\nx%d = %4.2lf",i,x[i]); + for(j = 0; j < k-i; j++) + { + printf("\t%4.2lf ",y[i][j]); + } + printf("\n"); + } +} +/*-------------------------------End of program -----------------------*/ diff --git a/c++/Computational_Geometry/C++ Program to Implement EULER'S METHOD TO SOLVE DIFFERENTIAL EQUATION.cpp b/c++/Computational_Geometry/C++ Program to Implement EULER'S METHOD TO SOLVE DIFFERENTIAL EQUATION.cpp new file mode 100644 index 0000000..97dd298 --- /dev/null +++ b/c++/Computational_Geometry/C++ Program to Implement EULER'S METHOD TO SOLVE DIFFERENTIAL EQUATION.cpp @@ -0,0 +1,61 @@ + + +/*-------------- EULER'S METHOD TO SOLVE DIFFERENTIAL EQUATION --------*/ + +/* THIS PROGRAM CALCULATES THE VALUE y AT GIVEN VALUE OF x + USING EULER'S METHOD. THE FUNCTION y' = f(x,y) IS + DEFINED IN THE PROGRAM. + + y' = x - y + Hence f(x,y) = x - y + + INPUTS : 1) Initial values of x and y. + + 2) Step size h. + + OUTPUTS : Calculated values of y at every step. */ + +/*------------------------------ PROGRAM --------------------------*/ + +#include +#include +#include +#include + +void main() +{ + double f (double x0,double y0); /* DECLARATION OF A FUNCTION f */ + double y0,y1,x0,x1,h,x; + int i,n,t; + clrscr(); + printf("\n EULER'S METHOD TO SOLVE DIFFERENTIAL EQUATION\n"); + printf("\n\nEnter x0 = "); + scanf("%lf",&x0); /* ENTER VALUE OF x0 */ + printf("\n\nEnter y0 = "); + scanf("%lf",&y0); /* ENTER VALUE OF y0 */ + printf("\n\nEnter the value of x at which y is to be found = "); + scanf("%lf",&x); /* ENTER VALUE OF x */ + printf("\n\nEnter the value of h = "); + scanf("%lf",&h); /* ENTER THE VALUE OF h */ + i = 0; + printf("\nPress any key to see step be step display of results...\n"); + while(x0 < x) /* LOOP TO CALCULATE y USING EULER'S FORMULA */ + { + i++; + x1 = x0 + h; + y1 = y0 + h * f(x0,y0); /* IMPLEMENTATION OF EULER'S FORMULA */ + printf("\nx%d = %lf y%d = %lf",i,x1,i,y1); + x0 = x1; + y0 = y1; + getch(); + } +} +/*---------------------------------------------------------------------*/ + +double f ( double x,double y) /* FUNCTION TO CALCULATE VALUE OF f(x,y)*/ +{ + double y_dash; + y_dash = x - y; /* function f(x,y) = y' = x - y */ + return(y_dash); +} +/*------------------------ END OF PROGRAM -----------------------------*/ diff --git a/c++/Computational_Geometry/C++ Program to Implement FORWARD DIFFERENCES GENERATION FOR INTERPOLATION.cpp b/c++/Computational_Geometry/C++ Program to Implement FORWARD DIFFERENCES GENERATION FOR INTERPOLATION.cpp new file mode 100644 index 0000000..b61751b --- /dev/null +++ b/c++/Computational_Geometry/C++ Program to Implement FORWARD DIFFERENCES GENERATION FOR INTERPOLATION.cpp @@ -0,0 +1,69 @@ + + +/*-------------- FORWARD DIFFERENCES GENERATION FOR INTERPOLATION -----*/ + +/* THE PROGRAM GENERATES A FORWARD DIFFERENCES TABLE FROM GIVEN + + DATA. THE VALUES OF x AND CORRESPONDING y = f(x) ARE TO BE + + ENTERED IN THE ARRAY FORMAT. + + INPUTS : 1) Number of entries of the data. + + 2) Values of 'x' & corresponding y = f(x). + + OUTPUTS : forward difference table array. */ + +/*------------------------------ PROGRAM --------------------------*/ + +#include +#include +#include +#include + +void main() +{ + double y[20][20],x[20]; + /* ARRAY OF y[n][n] ELEMENTS FOR FORWARD DIFFERENCE TABLE */ + int i,j,k,n; + clrscr(); + printf("\n\tFORWARD DIFFERENCES GENERATION FOR INTERPOLATION"); + printf("\n\n The form of equation is y = f(x)\n"); + printf("\n\nEnter the number of entries (max 20) = "); + /* ENTER THE NUMBER OF ENTRIES IN THE TABLE */ + scanf("%d",&n); + for(i = 0; i < n; i++) + { + /* LOOP TO GET x AND y = f(x) IN THE TABLE */ + printf("x%d = ",i); + scanf("%lf",&x[i]); + printf(" y%d = ",i); + scanf("%lf",&y[i][0]); + } + k = n; + for(j = 1; j < n; j++) + { + /* LOOP TO CALCULATE FORWARD DIFFERENCES IN THE TABLE */ + k = k - 1; + for(i = 0; i < k; i++) + { + y[i][j] = y[i+1][j-1] - y[i][j-1]; + } + } + k = n; + clrscr(); + printf("\n The forward difference table is as follows . . .\n"); + printf("\n\tx\ty\tDy\tD2y\tD3y\tD4y\tD5y\tD6y\n"); + for(i = 0; i < n; i++) + { + /* LOOP TO PRINT FORWARD DIFFERENCES IN THE TABLE */ + printf("\nx%d = %4.2lf",i,x[i]); + for(j = 0; j < k; j++) + { + printf("\t%4.2lf ",y[i][j]); + } + k = k - 1; + printf("\n"); + } +} +/*-------------------- End of program---------------------------------*/ diff --git a/c++/Computational_Geometry/C++ Program to Implement First Fit Decreasing for 1-D Objects and M Bins.cpp b/c++/Computational_Geometry/C++ Program to Implement First Fit Decreasing for 1-D Objects and M Bins.cpp new file mode 100644 index 0000000..2472fac --- /dev/null +++ b/c++/Computational_Geometry/C++ Program to Implement First Fit Decreasing for 1-D Objects and M Bins.cpp @@ -0,0 +1,74 @@ +#include +#include +#include + +using namespace std; + +void binPacking(int *a, int size, int n) +{ + int binCount = 0; + int binValues[n]; + for (int i = 0; i < n; i++) + binValues[i] = size; + for (int i = 0; i < n; i++) + for (int j = 0; j < n; j++) + { + if (binValues[j] - a[i] >= 0) + { + binValues[j] -= a[i]; + break; + } + } + for (int i = 0; i < n; i++) + if (binValues[i] != size) + binCount++; + cout << "Number of bins required using first fit decreasing algorithm is:" + << binCount; +} + +int* sort(int *sequence, int n) +{ + // Bubble Sort descending order + for (int i = 0; i < n; i++) + for (int j = 0; j < n - 1; j++) + if (sequence[j] < sequence[j + 1]) + { + sequence[j] = sequence[j] + sequence[j + 1]; + sequence[j + 1] = sequence[j] - sequence[j + 1]; + sequence[j] = sequence[j] - sequence[j + 1]; + } + return sequence; +} + +int main(int argc, char **argv) +{ + cout << "BIN - PACKING Algorithm 1D Objects(First Fit Decreasing)"; + cout << "Enter the number of items in Set: "; + int n; + cin >> n; + cout << "Enter " << n << " items:"; + int a[n]; + for (int i = 0; i < n; i++) + cin >> a[i]; + cout << "Enter the bin size: "; + int size; + cin >> size; + int *sequence = sort(a, n); + binPacking(sequence, size, n); +} + +/* + +BIN - PACKING Algorithm 1D Objects(First Fit Decreasing)Enter the number of items in Set: 9 +Enter 9 items: +4 +1 +2 +5 +3 +2 +3 +6 +3 +Enter the bin size: 6 +Number of bins required using first fit decreasing algorithm is:5 \ No newline at end of file diff --git a/c++/Computational_Geometry/C++ Program to Implement GAUSS ELIMINATION METHOD TO SOLVE LINEAR EQUATIONS.cpp b/c++/Computational_Geometry/C++ Program to Implement GAUSS ELIMINATION METHOD TO SOLVE LINEAR EQUATIONS.cpp new file mode 100644 index 0000000..e8db6c1 --- /dev/null +++ b/c++/Computational_Geometry/C++ Program to Implement GAUSS ELIMINATION METHOD TO SOLVE LINEAR EQUATIONS.cpp @@ -0,0 +1,78 @@ + + +/*-------- GAUSS ELIMINATION METHOD TO SOLVE LINEAR EQUATIONS ---------*/ + +/* THE PROGRAM SOLVES THE SYSTEM OF LINEAR EQUATIONS USING + + GAUSS ELIMINATION METHOD. + + INPUTS : 1) Number of variables in the equation. + + 2) Coefficient's of linear equations. + + OUTPUT : Calculated values of x1,x2,x3,...,xn etc. */ + +/*------------------------------ PROGRAM --------------------------*/ + +#include +#include +#include +#include + +void main() +{ + double a[10][10],x[10],ratio,coefsum; + /* ARRAY OF a[n][n] STORING COEFFICIENTS OF EQUATIONS */ + int i,j,n,k; + clrscr(); + printf("\n Computational Techniques - J. S. CHITODE"); + printf("\n GAUSS ELIMINATION METHOD TO SOLVE LINEAR EQUATIONS"); + printf("\n\n The form of equations is as follows\n\n" + " a11x1 + a12x2 + ... + a1nxn = b1\n" + " a21x1 + a22x2 + ... + a2nxn = b2\n" + " a31x1 + a32x2 + ... + a3nxn = b3\n" + " ................................\n" + " an1x1 + an2x2 + ... + annxn = bn\n" + "\n\nHere a11,a22,a33,a44,.....etc. should not be zero\n"); + printf("\n\nEnter the number of variables (max 10) = "); + /* ENTER THE NUMBER OF VARIABLES IN THE EQUATION */ + scanf("%d",&n); + for(i = 1; i <= n; i++) + { + /* LOOP TO GET COEFFICIENTS a11,a12...,ann & so on */ + for(j = 1; j <= n; j++) + { + printf("a%d%d = ",i,j); + scanf("%lf",&a[i][j]); + } + printf("b%d = ",i); + scanf("%lf",&a[i][j]); + x[i] = 0; + } + for(k = 1; k <= n-1; k++) + { + /* LOOP TO GENERATE UPPER TRIANGULAR SYSTEM */ + for(i = k+1; i <= n; i++) + { + ratio = a[i][k]/a[k][k]; + for(j = k+1; j <= n+1; j++) + { + a[i][j] = a[i][j] - ratio * a[k][j]; + } + } + for(i = k+1; i <= n; i++) a[i][k] = 0; + } + x[n] = a[n][n+1]/a[n][n]; + for(i = n-1; i >= 1; i--) + { + /* LOOP FOR BACKWARD SUBSTITUTION */ + coefsum = 0; + for(j = i+1; j <= n; j++) coefsum = coefsum + a[i][j] * x[j]; + x[i] = (a[i][n+1] - coefsum)/a[i][i]; + } + printf("\n\nThe values of variables in the given equations are " + "as follows....\n"); + for(i = 1; i <= n; i++) printf("\n x%d = %lf ",i,x[i]); + /* LOOP TO PRINT VALUES OF x1,x2,...xn etc */ +} +/*-------------------------------- END OF PROGRAM ----------------------*/ diff --git a/c++/Computational_Geometry/C++ Program to Implement GAUSS SIEDEL ITERATION METHOD TO SOLVE LINEAR EQUATIONS.cpp b/c++/Computational_Geometry/C++ Program to Implement GAUSS SIEDEL ITERATION METHOD TO SOLVE LINEAR EQUATIONS.cpp new file mode 100644 index 0000000..8a9e8bc --- /dev/null +++ b/c++/Computational_Geometry/C++ Program to Implement GAUSS SIEDEL ITERATION METHOD TO SOLVE LINEAR EQUATIONS.cpp @@ -0,0 +1,79 @@ + + +/*------- GAUSS SIEDEL ITERATION METHOD TO SOLVE LINEAR EQUATIONS -----*/ + +/* THE PROGRAM SOLVES THE SYSTEM OF LINEAR EQUATIONS USING + + GAUSS SIEDEL ITERATION METHOD. + + INPUTS : 1) Number of variables in the equation. + + 2) Coefficient's of linear equations. + + OUTPUTS : Results of every iteration till 'q' is pressed. */ + +/*------------------------------ PROGRAM --------------------------*/ + +#include +#include +#include +#include + +void main() +{ + double a[10][10],x[10],y[10]; + /* ARRAY OF a[n][n] STORING COEFFICIENTS OF EQUATIONS */ + int i,j,n; + char ch; + clrscr(); + printf("\n GAUSS SIEDEL METHOD TO SOLVE LINEAR EQUATIONS"); + printf("\n\n The form of equations is as follows\n\n" + " a11x1 + a12x2 + ... + a1nxn = b1\n" + " a21x1 + a22x2 + ... + a2nxn = b2\n" + " a31x1 + a32x2 + ... + a3nxn = b3\n" + " ................................\n" + " an1x1 + an2x2 + ... + annxn = bn\n"); + printf("\n\nEnter the number of variables (max 10) = "); + /* ENTER THE NUMBER OF VARIABLES IN THE EQUATION */ + scanf("%d",&n); + for(i = 1; i <= n; i++) + { + /* LOOP TO GET COEFFICIENTS a11,a12...,ann & so on */ + for(j = 1; j <= n; j++) + { + printf("a%d%d = ",i,j); + scanf("%lf",&a[i][j]); + } + printf("b%d = ",i); + scanf("%lf",&a[i][j]); + x[i] = y[i] = 0; + } + printf("\n\nThe results are as follows....\n\n" + "press 'enter' key to continue iterations &" + " press 'q' to stop iterations....\n\n"); + while(ch != 'q') + { + for(i = 1; i <= n; i++) + { + /* LOOP TO CALCULATE VALUES OF x1,x2,...,xn etc */ + for(j = 1; j <= n; j++) + { + if(i == j) continue; + x[i] = x[i] - a[i][j]*y[j]; + } + x[i] = x[i] + a[i][j]; + x[i] = x[i]/a[i][i]; + y[i] = x[i]; /* TAKE VALUES FROM CURRENT ITERATIONS */ + } + for(i = 1; i <= n; i++) + { + /* LOOP TO PRINT VALUES OF x1,x2,...xn etc */ + y[i] = x[i]; + printf("x%d = %lf ",i,x[i]); + x[i] = 0; + } + ch = getch(); + printf("\n\n"); + } +} +/*-------------------------------- END OF PROGRAM ---------------------*/ diff --git a/c++/Computational_Geometry/C++ Program to Implement Gift Wrapping Algorithm in Two Dimensions.cpp b/c++/Computational_Geometry/C++ Program to Implement Gift Wrapping Algorithm in Two Dimensions.cpp new file mode 100644 index 0000000..9b403f5 --- /dev/null +++ b/c++/Computational_Geometry/C++ Program to Implement Gift Wrapping Algorithm in Two Dimensions.cpp @@ -0,0 +1,86 @@ +/*This is a C++ Program to implement Gift Wrapping algorithm to find convex hull in two dimensional space. In computational geometry, the gift wrapping algorithm is an algorithm for computing the convex hull of a given set of points. In the two-dimensional case the algorithm is also known as Jarvis march, after R. A. Jarvis, who published it in 1973; it has O(nh) time complexity, where n is the number of points and h is the number of points on the convex hull. Its real-life performance compared with other convex hull algorithms is favorable when n is small or h is expected to be very small with respect to n. In general cases the algorithm is outperformed by many others.*/ + +// A C++ program to find convex hull of a set of points +// Refer http://www.geeksforgeeks.org/check-if-two-given-line-segments-intersect/ +// for explanation of orientation() +#include +using namespace std; + +// Define Infinite (Using INT_MAX caused overflow problems) +#define INF 10000 + +struct Point +{ + int x; + int y; +}; + +// To find orientation of ordered triplet (p, q, r). +// The function returns following values +// 0 --> p, q and r are colinear +// 1 --> Clockwise +// 2 --> Counterclockwise +int orientation(Point p, Point q, Point r) +{ + int val = (q.y - p.y) * (r.x - q.x) - (q.x - p.x) * (r.y - q.y); + if (val == 0) + return 0; // colinear + return (val > 0) ? 1 : 2; // clock or counterclock wise +} + +// Prints convex hull of a set of n points. +void convexHull(Point points[], int n) +{ + // There must be at least 3 points + if (n < 3) + return; + // Initialize Result + int next[n]; + for (int i = 0; i < n; i++) + next[i] = -1; + // Find the leftmost point + int l = 0; + for (int i = 1; i < n; i++) + if (points[i].x < points[l].x) + l = i; + // Start from leftmost point, keep moving counterclockwise + // until reach the start point again + int p = l, q; + do + { + // Search for a point 'q' such that orientation(p, i, q) is + // counterclockwise for all points 'i' + q = (p + 1) % n; + for (int i = 0; i < n; i++) + if (orientation(points[p], points[i], points[q]) == 2) + q = i; + next[p] = q; // Add q to result as a next point of p + p = q; // Set p as q for next iteration + } + while (p != l); + // Print Result + for (int i = 0; i < n; i++) + { + if (next[i] != -1) + cout << "(" << points[i].x << ", " << points[i].y << ")\n"; + } +} + +// Driver program to test above functions +int main() +{ + Point points[] = { { 0, 3 }, { 2, 2 }, { 1, 1 }, { 2, 1 }, { 3, 0 }, + { 0, 0 }, { 3, 3 } + }; + cout << "The points in the convex hull are: "; + int n = sizeof(points) / sizeof(points[0]); + convexHull(points, n); + return 0; +} + +/* + +The points in the convex hull are: (0, 3) +(3, 0) +(0, 0) +(3, 3) diff --git a/c++/Computational_Geometry/C++ Program to Implement Graham Scan Algorithm to Find the Convex Hull.cpp b/c++/Computational_Geometry/C++ Program to Implement Graham Scan Algorithm to Find the Convex Hull.cpp new file mode 100644 index 0000000..523af12 --- /dev/null +++ b/c++/Computational_Geometry/C++ Program to Implement Graham Scan Algorithm to Find the Convex Hull.cpp @@ -0,0 +1,124 @@ +/*This is a C++ Program to implement Graham Scan algorithm. Graham’s scan is a method of computing the convex hull of a finite set of points in the plane with time complexity O(n log n).*/ + +// A C++ program to find convex hull of a set of points +// Refer http://www.geeksforgeeks.org/check-if-two-given-line-segments-intersect/ +// for explanation of orientation() +#include +#include +#include +using namespace std; + +struct Point +{ + int x; + int y; +}; + +Point p0; + +// A utility function to find next to top in a stack +Point nextToTop(stack &S) +{ + Point p = S.top(); + S.pop(); + Point res = S.top(); + S.push(p); + return res; +} + +// A utility function to swap two points +int swap(Point &p1, Point &p2) +{ + Point temp = p1; + p1 = p2; + p2 = temp; +} + +// A utility function to return square of distance between p1 and p2 +int dist(Point p1, Point p2) +{ + return (p1.x - p2.x) * (p1.x - p2.x) + (p1.y - p2.y) * (p1.y - p2.y); +} + +int orientation(Point p, Point q, Point r) +{ + int val = (q.y - p.y) * (r.x - q.x) - (q.x - p.x) * (r.y - q.y); + if (val == 0) + return 0; // colinear + return (val > 0) ? 1 : 2; // clock or counterclock wise +} + +// A function used by library function qsort() to sort an array of +// points with respect to the first point +int compare(const void *vp1, const void *vp2) +{ + Point *p1 = (Point *) vp1; + Point *p2 = (Point *) vp2; + // Find orientation + int o = orientation(p0, *p1, *p2); + if (o == 0) + return (dist(p0, *p2) >= dist(p0, *p1)) ? -1 : 1; + return (o == 2) ? -1 : 1; +} + +// Prints convex hull of a set of n points. +void convexHull(Point points[], int n) +{ + // Find the bottommost point + int ymin = points[0].y, min = 0; + for (int i = 1; i < n; i++) + { + int y = points[i].y; + // Pick the bottom-most or chose the left most point in case of tie + if ((y < ymin) || (ymin == y && points[i].x < points[min].x)) + ymin = points[i].y, min = i; + } + // Place the bottom-most point at first position + swap(points[0], points[min]); + // Sort n-1 points with respect to the first point. A point p1 comes + // before p2 in sorted ouput if p2 has larger polar angle (in + // counterclockwise direction) than p1 + p0 = points[0]; + qsort(&points[1], n - 1, sizeof(Point), compare); + // Create an empty stack and push first three points to it. + stack S; + S.push(points[0]); + S.push(points[1]); + S.push(points[2]); + // Process remaining n-3 points + for (int i = 3; i < n; i++) + { + // Keep removing top while the angle formed by points next-to-top, + // top, and points[i] makes a non-left turn + while (orientation(nextToTop(S), S.top(), points[i]) != 2) + S.pop(); + S.push(points[i]); + } + // Now stack has the output points, print contents of stack + while (!S.empty()) + { + Point p = S.top(); + cout << "(" << p.x << ", " << p.y << ")" << endl; + S.pop(); + } +} + +// Driver program to test above functions +int main() +{ + Point points[] = { { 0, 3 }, { 1, 1 }, { 2, 2 }, { 4, 4 }, { 0, 0 }, + { 1, 2 }, { 3, 1 }, { 3, 3 } + }; + int n = sizeof(points) / sizeof(points[0]); + cout << "The points in the convex hull are: \n"; + convexHull(points, n); + return 0; +} + +/* + +The points in the convex hull are: +(0, 3) +(4, 4) +(3, 1) +(0, 0) diff --git a/c++/Computational_Geometry/C++ Program to Implement ILLUSTRATION OF LINKED LIST TO SIMULATE A QUEUE.cpp b/c++/Computational_Geometry/C++ Program to Implement ILLUSTRATION OF LINKED LIST TO SIMULATE A QUEUE.cpp new file mode 100644 index 0000000..701c0c1 --- /dev/null +++ b/c++/Computational_Geometry/C++ Program to Implement ILLUSTRATION OF LINKED LIST TO SIMULATE A QUEUE.cpp @@ -0,0 +1,73 @@ + + +/*------------ ILLUSTRATION OF LINKED LIST TO SIMULATE A QUEUE --------*/ + +/* THIS PROGRAM ILLUSTRATES THE USE OF LINKED LISTS TO IMPLEMENT + THE DATA STRUCTURES LIKE QUEUES. THE PROGRAM ACCEPTS THE WORDS + AND STORES THEM AT DIFFERENT NODES OF THE LINKED LIST. IT THEN + PRINTS THOSE WORDS ON FIFO BASIS. + + INPUTS : WORDS TO THE LINKED LIST. + + OUTPUTS : DISPLAY OF WORDS ON FIFO BASIS + +/*------------------------------ PROGRAM ----------------------------*/ +#include +#include +#include +#include + +#define NULL 0 /* NULL pointer for last node in the list */ + +struct list_element +{ + /* This structure contains data item and pointer to the next node */ + char item[40]; /* This is data item */ + struct list_element *next; /* This is pointer */ +}; +typedef struct list_element node; +/* define the structure 'list_element' of type node */ + +void main() +{ + node *start; /* declaration of the pointer to the nodes */ + void create (node *pt); /* function declaration */ + void display (node *pt); /* function declaration */ + clrscr(); + printf("\n Computational Techniques - J. S. CHITODE"); + printf("\n ILLUSTRATION OF LINKED LIST TO SIMULATE A QUEUE\n"); + start = (node *)malloc(sizeof(node)); + /*allocate the memory for starting node; start is memory address */ + create(start); /* create starting node */ + printf("\nThe contents of the link list are ...\n"); + display (start); /* display the contents of nodes */ +} +/*-----------------------------------------------------------------------*/ + +void create(node * record) /* This function creates nodes in the + link list till 'end' is entered */ +{ + printf("\ndata item = "); + scanf("%s",record->item); /* get the value of data item */ + if(strcmpi(record->item, "end") == 0) record->next = NULL; + /* check whether 'end is entered */ + else + { + record->next = (node *)malloc(sizeof(node)); + create(record->next); + } /* create new node by calling this function recursively */ + return; +} +/*-----------------------------------------------------------------------*/ + +void display (node *record) /* This function is used to display the + contents of linked list */ +{ + if(record->next != NULL) + { + printf("\n%s",record->item); + display(record->next); + } /* This function is called recursively to display all the items */ + return; +} +/*------------------------ END OF PROGRAM ------------------------------*/ diff --git a/c++/Computational_Geometry/C++ Program to Implement ITERATIVE METHOD TO FIND ROOT OF AN EQUATION.cpp b/c++/Computational_Geometry/C++ Program to Implement ITERATIVE METHOD TO FIND ROOT OF AN EQUATION.cpp new file mode 100644 index 0000000..7c39e18 --- /dev/null +++ b/c++/Computational_Geometry/C++ Program to Implement ITERATIVE METHOD TO FIND ROOT OF AN EQUATION.cpp @@ -0,0 +1,63 @@ + +/*-------------- ITERATIVE METHOD TO FIND ROOT OF AN EQUATION -------*/ + +/* THE FUNCTION p(x) FOR AN EQUATION IS DEFINED IN function fx + + THE EQUATION IS, + + x = 1 + 0.3*cos(x) + + p(x) = 1 + 0.3*cos(x) + + i.e. x = p(x) + + INPUTS : 1) Initial approximation x0 to the root. + + 2) Number of iterations. + + OUTPUTS : Value of the root. */ + +/*------------------------------ PROGRAM ----------------------------*/ + +#include +#include +#include +#include + +void main() +{ + double px ( double x); /* DECLARATION OF FUNCTION */ + double x0,x1,p0; + int n,i; + clrscr(); + printf("\n ITERATIVE METHOD TO FIND ROOT OF AN EQUATION"); + printf("\n\n x = 1 + 0.3*cos(x)\n" + " p(x) = 1 + 0.3*cos(x)\n"); + printf("\n\nEnter the value of initial " + "approximation x0 = "); + scanf("%lf",&x0); + /* INITIAL APPROXIMATION x0 IS TO BE ENTERED HERE */ + printf("\nEnter the number of iterations = "); + scanf("%d",&n); + printf("\npress any key for display of iterations...\n"); + getch(); + i = 0; + while(n-- > 0) + { + x1 = px(x0); /* CALCULATION OF NEXT APPROXIMATION */ + i++; + printf("\n%d x%d = %10.10lf",i,i,x1); + x0 = x1; + getch(); + } + printf("\n\nThe value of root is = %20.15lf",x1); /* ROOT */ +} +/*---------- FUNCTION PROCEDURE TO CALCULATE VALUE OF EQUATION --------*/ + +double px ( double x) +{ + double p; + p = 1 + 0.3*cos(x); /* FUNCTION p(x) */ + return(p); +} +/*----------------------------- END OF PROGRAM -------------------------*/ diff --git a/c++/Computational_Geometry/C++ Program to Implement JACOBI'S ITERATION METHOD TO SOLVE LINEAR EQUATIONS.cpp b/c++/Computational_Geometry/C++ Program to Implement JACOBI'S ITERATION METHOD TO SOLVE LINEAR EQUATIONS.cpp new file mode 100644 index 0000000..6230cac --- /dev/null +++ b/c++/Computational_Geometry/C++ Program to Implement JACOBI'S ITERATION METHOD TO SOLVE LINEAR EQUATIONS.cpp @@ -0,0 +1,79 @@ + + +/*----------- JACOBI'S ITERATION METHOD TO SOLVE LINEAR EQUATIONS -----*/ + +/* THE PROGRAM SOLVES THE SYSTEM OF LINEAR EQUATIONS USING + + JACOBI'S ITERATION METHOD. + + INPUTS : 1) Number of variables in the equation. + + 2) Coefficient's of linear equations. + + OUTPUTS : Results of every iteration till 'q' is pressed. */ + +/*--------------------------- PROGRAM -----------------------------*/ + +#include +#include +#include +#include + +void main() +{ + double a[10][10],x[10],y[10]; + /* ARRAY OF a[n][n] STORING COEFFICIENTS OF EQUATIONS */ + int i,j,n; + char ch; + clrscr(); + printf("\n Computational Techniques - J. S. CHITODE"); + printf("\n JACOBI'S ITERATION METHOD TO SOLVE LINEAR EQUATIONS"); + printf("\n\n The form of equations is as follows\n\n" + " a11x1 + a12x2 + ... + a1nxn = b1\n" + " a21x1 + a22x2 + ... + a2nxn = b2\n" + " a31x1 + a32x2 + ... + a3nxn = b3\n" + " ................................\n" + " an1x1 + an2x2 + ... + annxn = bn\n"); + printf("\n\nEnter the number of variables (max 10) = "); + /* ENTER THE NUMBER OF VARIABLES IN THE EQUATION */ + scanf("%d",&n); + for(i = 1; i <= n; i++) + { + /* LOOP TO GET COEFFICIENTS a11,a12...,ann & so on */ + for(j = 1; j <= n; j++) + { + printf("a%d%d = ",i,j); + scanf("%lf",&a[i][j]); + } + printf("b%d = ",i); + scanf("%lf",&a[i][j]); + x[i] = y[i] = 0; + } + printf("\n\nThe results are as follows....\n\n" + "press 'enter' key to continue iterations &" + " press 'q' to stop iterations....\n\n"); + while(ch != 'q') + { + for(i = 1; i <= n; i++) + { + /* LOOP TO CALCULATE VALUES OF x1,x2,...,xn etc */ + for(j = 1; j <= n; j++) + { + if(i == j) continue; + x[i] = x[i] - a[i][j]*y[j]; + } + x[i] = x[i] + a[i][j]; + x[i] = x[i]/a[i][i]; + } + for(i = 1; i <= n; i++) + { + /* LOOP TO PRINT VALUES OF x1,x2,...xn etc */ + y[i] = x[i]; + printf("x%d = %lf ",i,x[i]); + x[i] = 0; + } + ch = getch(); + printf("\n\n"); + } +} +/*-------------------------------- END OF PROGRAM -----------------------*/ diff --git a/c++/Computational_Geometry/C++ Program to Implement Jarvis March to Find the Convex Hull.cpp b/c++/Computational_Geometry/C++ Program to Implement Jarvis March to Find the Convex Hull.cpp new file mode 100644 index 0000000..cba9b0e --- /dev/null +++ b/c++/Computational_Geometry/C++ Program to Implement Jarvis March to Find the Convex Hull.cpp @@ -0,0 +1,85 @@ +/*This is a C++ Program to implement Jarvis March to find convex hull. The idea of Jarvis’s Algorithm is simple, we start from the leftmost point (or point with minimum x coordinate value) and we keep wrapping points in counterclockwise direction.*/ + +// A C++ program to find convex hull of a set of points +// Refer http://www.geeksforgeeks.org/check-if-two-given-line-segments-intersect/ +// for explanation of orientation() +#include +using namespace std; + +// Define Infinite (Using INT_MAX caused overflow problems) +#define INF 10000 + +struct Point +{ + int x; + int y; +}; + +// To find orientation of ordered triplet (p, q, r). +// The function returns following values +// 0 --> p, q and r are colinear +// 1 --> Clockwise +// 2 --> Counterclockwise +int orientation(Point p, Point q, Point r) +{ + int val = (q.y - p.y) * (r.x - q.x) - (q.x - p.x) * (r.y - q.y); + if (val == 0) + return 0; // colinear + return (val > 0) ? 1 : 2; // clock or counterclock wise +} + +// Prints convex hull of a set of n points. +void convexHull(Point points[], int n) +{ + // There must be at least 3 points + if (n < 3) + return; + // Initialize Result + int next[n]; + for (int i = 0; i < n; i++) + next[i] = -1; + // Find the leftmost point + int l = 0; + for (int i = 1; i < n; i++) + if (points[i].x < points[l].x) + l = i; + // Start from leftmost point, keep moving counterclockwise + // until reach the start point again + int p = l, q; + do + { + // Search for a point 'q' such that orientation(p, i, q) is + // counterclockwise for all points 'i' + q = (p + 1) % n; + for (int i = 0; i < n; i++) + if (orientation(points[p], points[i], points[q]) == 2) + q = i; + next[p] = q; // Add q to result as a next point of p + p = q; // Set p as q for next iteration + } + while (p != l); + // Print Result + for (int i = 0; i < n; i++) + { + if (next[i] != -1) + cout << "(" << points[i].x << ", " << points[i].y << ")\n"; + } +} + +// Driver program to test above functions +int main() +{ + Point points[] = { { 0, 3 }, { 2, 2 }, { 1, 1 }, { 2, 1 }, { 3, 0 }, + { 0, 0 }, { 3, 3 } + }; + cout << "The points in the convex hull are: "; + int n = sizeof(points) / sizeof(points[0]); + convexHull(points, n); + return 0; +} + +/* +The points in the convex hull are: (0, 3) +(3, 0) +(0, 0) +(3, 3) \ No newline at end of file diff --git a/c++/Computational_Geometry/C++ Program to Implement LAGRANGE'S INTERPOLATION METHOD.cpp b/c++/Computational_Geometry/C++ Program to Implement LAGRANGE'S INTERPOLATION METHOD.cpp new file mode 100644 index 0000000..ac49536 --- /dev/null +++ b/c++/Computational_Geometry/C++ Program to Implement LAGRANGE'S INTERPOLATION METHOD.cpp @@ -0,0 +1,58 @@ + + +/*----------------- LAGRANGE'S INTERPOLATION METHOD --------------------*/ + +/* THE PROGRAM CALCULATES THE VALUE OF f(x) AT GIVEN VALUE OF x + USING LAGRANGE'S INTERPOLATION METHOD. + + INPUTS : 1) Number of entries of the data. + + 2) Values of 'x' & corresponding y = f(x). + + 3) Value of 'xr' at which y = f(x) to be calculated. + + OUTPUTS : Interpolated value f(x) at x = xr. */ + +/*------------------------------ PROGRAM ----------------------------*/ + +#include +#include +#include +#include + +void main() +{ + double y[20],x[20],xr,fy,num,den; + int i,j,n; + clrscr(); + printf("\n LAGRANGE'S INTERPOLATION TECHNIQUE"); + printf("\n\nEnter the number of entries (max 20) = "); + /* ENTER THE NUMBER OF ENTRIES */ + scanf("%d",&n); + for(i = 0; i < n; i++) + { + /* LOOP TO GET x AND y = f(x) IN THE ARRAY */ + printf("x%d = ",i); + scanf("%lf",&x[i]); + printf(" y%d = ",i); + scanf("%lf",&y[i]); + } + printf("\nEnter the value of xr at which y = f(x)\n\t\t\t" + "is to be interpolated, xr = "); + scanf("%lf",&xr); + fy = 0; + for(j = 0; j < n; j++) + { + /* LOOP TO CALCULATE LAGRANGE'S INTERPOLATION */ + num = den = 1; + for(i = 0; i < n; i++) + { + if(i == j) continue; + num = num * (xr - x[i]); + den = den * (x[j] - x[i]); + } + fy = fy + ((num/den) * y[j]); + } + printf("\nThe value of y = f(x) at xr = %lf is yr = %lf", xr,fy); +} +/*--------------------------- END OF PROGRAM ----------------------------*/ diff --git a/c++/Computational_Geometry/C++ Program to Implement MODIFIED EULER'S METHOD TO SOLVE DIFFERENTIAL EQUATION.cpp b/c++/Computational_Geometry/C++ Program to Implement MODIFIED EULER'S METHOD TO SOLVE DIFFERENTIAL EQUATION.cpp new file mode 100644 index 0000000..03460b0 --- /dev/null +++ b/c++/Computational_Geometry/C++ Program to Implement MODIFIED EULER'S METHOD TO SOLVE DIFFERENTIAL EQUATION.cpp @@ -0,0 +1,71 @@ + + +/*------- MODIFIED EULER'S METHOD TO SOLVE DIFFERENTIAL EQUATION ------*/ + +/* THIS PROGRAM CALCULATES THE VALUE y AT GIVEN VALUE OF x + USING MODIFIED EULER'S METHOD. THE FUNCTION y' = f(x,y) IS + DEFINED IN THE PROGRAM. + + y' = x*x + y + Hence f(x,y) = x*x + y + + INPUTS : 1) Initial values of x and y. + + 2) Step size h. + + OUTPUTS : Calculated values of y at every step. */ + +/*------------------------------ PROGRAM --------------------------*/ + +#include +#include +#include +#include + +void main() +{ + double f (double x0,double y0); /* DECLARATION OF A FUNCTION f */ + double y0,y1,y10,x0,x1,h,x,diff; + int i,n; + clrscr(); + printf("\n\tMODIFIED EULER'S METHOD TO SOLVE DIFFERENTIAL EQUATION"); + printf("\n\nEnter x0 = "); + scanf("%lf",&x0); /* ENTER VALUE OF x0 */ + printf("\n\nEnter y0 = "); + scanf("%lf",&y0); /* ENTER VALUE OF y0 */ + printf("\n\nEnter the value of x at which y is to be found = "); + scanf("%lf",&x); /* ENTER VALUE OF x */ + printf("\n\nEnter the value of h = "); + scanf("%lf",&h); /* ENTER THE VALUE OF h */ + i = 0; + printf("\nPress any key to see step by step display of results...\n"); + while(x0 < x) /* LOOP TO CALCULATE y USING MODIFIED EULER'S FORMULA*/ + { + i++; + x1 = x0 + h; + y1 = y0 + h * f(x0,y0); /* PREDICTOR EQUATION */ + y10 = y1; + do /* LOOP TO IMPLEMENT CORRECTOR FORMULA */ + { + y1 = y0 + (h/2) * ( f(x0,y0) + f(x1,y10) ); + diff = fabs(y1 - y10); /* CHECK FOR HOW MANY DIGITS + ARE REPEATING AFTER DECIMAL POINT*/ + y10 = y1; + } + while( diff > 0.0001); + /*REMAIN IN LOOP TILL 3 DIGITS REPEAT AFTER DECIMAL POINT*/ + printf("\nx%d = %lf y%d = %lf",i,x1,i,y1); + x0 = x1; + y0 = y1; + getch(); + } +} +/*---------------------------------------------------------------------*/ + +double f ( double x,double y) /* FUNCTION TO CALCULATE VALUE OF f(x,y)*/ +{ + double y_dash; + y_dash = x*x + y; /* function f(x,y) = y' = x*x + y */ + return(y_dash); +} +/*------------------------ END OF PROGRAM -----------------------------*/ diff --git a/c++/Computational_Geometry/C++ Program to Implement NEWTON RAPHSON METHOD TO FIND ROOT OF AN EQUATION.cpp b/c++/Computational_Geometry/C++ Program to Implement NEWTON RAPHSON METHOD TO FIND ROOT OF AN EQUATION.cpp new file mode 100644 index 0000000..4c68384 --- /dev/null +++ b/c++/Computational_Geometry/C++ Program to Implement NEWTON RAPHSON METHOD TO FIND ROOT OF AN EQUATION.cpp @@ -0,0 +1,72 @@ + +/*----------- NEWTON RAPHSON METHOD TO FIND ROOT OF AN EQUATION -------*/ + +/* THE EXPRESSION FOR AN EQUATION IS DEFINED IN function fx + YOU CAN WRITE DIFFERENT EQUATION IN function fx. + HERE, + f(x) = x*x*x - 5*x + 3 + + INPUTS : 1) Initial approximation x0 to the root. + + 2) Number of iterations. + + OUTPUTS : Value of the root. */ + +/*------------------------------ PROGRAM ----------------------------*/ + +#include +#include +#include +#include + +void main() +{ + double fx ( double x); /* DECLARATION OF FUNCTION */ + double f_x ( double x); /* CALCULATION OF DERIVATIVE */ + double x0,x1,f_0,f0; + int n,i; + clrscr(); + printf("\n NEWTON RAPHSON METHOD TO FIND ROOT OF AN EQUATION"); + printf("\n\n f(x) = x*x*x - 5*x + 3"); + printf("\n\nEnter the value of initial " + "approximation x0 = "); + scanf("%lf",&x0); + /* INITIAL APPROXIMATION x0 IS TO BE ENTERED HERE */ + printf("\nEnter the number of iterations = "); + scanf("%d",&n); + printf("\npress any key for display of iterations...\n"); + getch(); + i = 0; + while(n-- > 0) + { + f0 = fx(x0); /* CALCULATE f(x) AT x = x0 */ + f_0 = f_x(x0); /* CALCULATE f'(x) AT x = x1 */ + x1 = x0 - (f0/f_0); + /* CALCULATION OF NEXT APPROXIMATION */ + i++; + printf("\n%d x%d = %lf \n" + "\n f%d = %lf f_%d = %lf x%d = %lf\n" + ,i,i-1,x0,i-1,f0,i-1,f_0,i,x1); + x0 = x1; + getch(); + } + printf("\n\nThe value of root is = %20.15lf",x1); /* ROOT */ +} +/*---------- FUNCTION PROCEDURE TO CALCULATE VALUE OF EQUATION --------*/ + +double fx ( double x) +{ + double f; + f = x*x*x - 5*x + 3; /* FUNCTION f(x) */ + return(f); +} + +/*---------- FUNCTION PROCEDURE TO CALCULATE f'(x0) --------------------*/ + +double f_x ( double x) +{ + double f_dash; + f_dash = 3*x*x - 5; /* DERIVATIVE OF f(x) i.e. f'(x) */ + return(f_dash); +} +/*--------------------- End of program --------------------------------*/ diff --git a/c++/Computational_Geometry/C++ Program to Implement NEWTON'S BACKWARD DIFFERENCES INTERPOLATION METHOD.cpp b/c++/Computational_Geometry/C++ Program to Implement NEWTON'S BACKWARD DIFFERENCES INTERPOLATION METHOD.cpp new file mode 100644 index 0000000..346158c --- /dev/null +++ b/c++/Computational_Geometry/C++ Program to Implement NEWTON'S BACKWARD DIFFERENCES INTERPOLATION METHOD.cpp @@ -0,0 +1,74 @@ + + +/*------ NEWTON'S BACKWARD DIFFERENCES INTERPOLATION METHOD -----------*/ + +/* THE PROGRAM GENERATES A BACKWARD DIFFERENCES TABLE FROM GIVEN + + DATA, & CALCULATES THE VALUE OF f(x) AT GIVEN VALUE OF x. + + INPUTS : 1) Number of entries of the data. + + 2) Values of 'x' & corresponding y = f(x). + + 3) Value of 'xr' at which y = f(x) to be calculated. + + OUTPUTS : Interpolated value f(x) at x = xr. */ + +/*------------------------------ PROGRAM ---------------------------*/ + +#include +#include +#include +#include + +void main() +{ + double y[20][20],x[20],xr,yr,h,r,sum,fy,facto; + int i,j,k,n,m,t; + clrscr(); + printf("\n\tNEWTON'S BACKWARD DIFFERENCES INTERPOLATION TECHNIQUE"); + printf("\n\nEnter the number of entries (max 20) = "); + /* ENTER THE NUMBER OF ENTRIES IN THE TABLE */ + scanf("%d",&n); + for(i = 0; i < n; i++) + { + /* LOOP TO GET x AND y = f(x) IN THE TABLE */ + printf("x%d = ",i); + scanf("%lf",&x[i]); + printf(" y%d = ",i); + scanf("%lf",&y[i][0]); + } + printf("\nEnter the value of xr at which y = f(x)\nis to be " + "interpolated, xr = "); + scanf("%lf",&xr); + h = x[1] - x[0]; + r = (xr - x[n-1])/h; /* CALCULATE VALUE OF 'r' */ + printf("\nThe value of h = %lf and value of r = %lf\n",h,r); + k = 0; + for(j = 1; j < n; j++) + { + /* LOOP TO CALCULATE BACKWARD DIFFERENCES */ + k++; + for(i = n-1; i >= k; i--) + { + y[i][j] = y[i][j-1] - y[i-1][j-1]; + } + } + sum = 0; + for(t = 1; t < n; t++) + { + /* LOOP FOR NEWTON'S BACKWARD DIFFERENCE INTERPOLATION FORMULA */ + fy = 1; + facto = 1; + for(m = 0; m < t; m++) + { + fy = fy * (r + m); + facto = facto * (m + 1); + } + fy = fy * (y[n-1][t]/facto); + sum = sum + fy; + } + yr = sum + y[n-1][0]; + printf("\nThe value of y = f(x) at xr = %lf is yr = %lf", xr,yr); +} +/*--------------------------- END OF PROGRAM ---------------------------*/ diff --git a/c++/Computational_Geometry/C++ Program to Implement NEWTON'S DIVIDED DIFFERENCES INTERPOLATION METHOD.cpp b/c++/Computational_Geometry/C++ Program to Implement NEWTON'S DIVIDED DIFFERENCES INTERPOLATION METHOD.cpp new file mode 100644 index 0000000..6d474f3 --- /dev/null +++ b/c++/Computational_Geometry/C++ Program to Implement NEWTON'S DIVIDED DIFFERENCES INTERPOLATION METHOD.cpp @@ -0,0 +1,74 @@ + + +/*------------ NEWTON'S DIVIDED DIFFERENCES INTERPOLATION METHOD --------*/ + +/* THE PROGRAM GENERATES A DIVIDED DIFFERENCES TABLE FROM GIVEN + + DATA, AND IT CALCULATES THE VALUE OF f(x) AT GIVEN VALUE + + OF xr. + + INPUTS : 1) Number of entries of the data. + + 2) Values of 'x' & corresponding y = f(x). + + 3) Value of xr at which f(x) is to be interpolated. + + VALUES OF x NEED NOT BE EQUALLY SPACED. + + OUTPUTS : Interpolated value of f(x) at x = xr. */ + +/*------------------------------ PROGRAM ----------------------------*/ + +#include +#include +#include +#include + +void main() +{ + double y[20][20],x[20],sum,fy,xr; + /* ARRAY OF y[n][n] ELEMENTS FOR DIVIDED DIFFERENCE TABLE */ + int i,j,k,n,t,m; + clrscr(); + printf("\n NEWTON'S DIVIDED DIFFERENCES INTERPOLATION METHOD"); + printf("\n\nEnter the number of entries (max 20) = "); + /* ENTER THE NUMBER OF ENTRIES IN THE TABLE */ + scanf("%d",&n); + for(i = 0; i < n; i++) + { + /* LOOP TO GET x AND y = f(x) IN THE TABLE */ + printf("x%d = ",i); + scanf("%lf",&x[i]); + printf(" y%d = ",i); + scanf("%lf",&y[i][0]); + } + printf("\nEnter the value of xr at which y = f(x) is to be" + " calculated xr = "); + scanf("%lf",&xr); + k = n; + for(j = 1; j < n; j++) + { + /* LOOP TO CALCULATE DIVIDED DIFFERENCES IN THE TABLE */ + k = k - 1; + for(i = 0; i < k; i++) + { + y[i][j] = (y[i+1][j-1] - y[i][j-1])/(x[i+j]-x[i]); + } + } + sum = 0; + for(t = 1; t < n; t++) + { + /* LOOP TO CALCULATE INTERPOLATED VALUE OF 'y' */ + fy = 1; + for(m = 0; m < t; m++) + { + fy = fy * (xr - x[m]); + } + sum = sum + (fy * y[0][t]); + } + sum = sum + y[0][0]; + printf("\nThe interpolated value of y at xr = %lf" + " is yr = %lf\n",xr,sum); +} +/*-------------------- END OF PROGRAM ---------------------------------*/ diff --git a/c++/Computational_Geometry/C++ Program to Implement NEWTON'S FORWARD DIFFERENCES INTERPOLATION METHOD.cpp b/c++/Computational_Geometry/C++ Program to Implement NEWTON'S FORWARD DIFFERENCES INTERPOLATION METHOD.cpp new file mode 100644 index 0000000..963b6e9 --- /dev/null +++ b/c++/Computational_Geometry/C++ Program to Implement NEWTON'S FORWARD DIFFERENCES INTERPOLATION METHOD.cpp @@ -0,0 +1,74 @@ + + +/*------ NEWTON'S FORWARD DIFFERENCES INTERPOLATION METHOD ------------*/ + +/* THE PROGRAM GENERATES A FORWARD DIFFERENCES TABLE FROM GIVEN + + DATA, & CALCULATES THE VALUE OF f(x) AT GIVEN VALUE OF x. + + INPUTS : 1) Number of entries of the data. + + 2) Values of 'x' & corresponding y = f(x). + + 3) Value of 'xr' at which y = f(x) to be calculated. + + OUTPUTS : Interpolated value f(x) at x = xr. */ + +/*------------------------------ PROGRAM ---------------------------*/ + +#include +#include +#include +#include + +void main() +{ + double y[20][20],x[20],xr,yr,h,r,sum,fy,facto; + int i,j,k,n,m,t; + clrscr(); + printf("\n\tNEWTON'S FORWARD DIFFERENCES INTERPOLATION TECHNIQUE"); + printf("\n\nEnter the number of entries (max 20) = "); + /* ENTER THE NUMBER OF ENTRIES IN THE TABLE */ + scanf("%d",&n); + for(i = 0; i < n; i++) + { + /* LOOP TO GET x AND y = f(x) IN THE TABLE */ + printf("x%d = ",i); + scanf("%lf",&x[i]); + printf(" y%d = ",i); + scanf("%lf",&y[i][0]); + } + printf("\nEnter the value of xr at which y = f(x) is to be " + "interpolated, xr = "); + scanf("%lf",&xr); + h = x[1] - x[0]; + r = (xr - x[0])/h; /* CALCULATE VALUE OF 'r' */ + printf("\nThe value of h = %lf and value of r = %lf\n",h,r); + k = n; + for(j = 1; j < n; j++) + { + /* LOOP TO CALCULATE FORWARD DIFFERENCES IN THE TABLE */ + k = k - 1; + for(i = 0; i < k; i++) + { + y[i][j] = y[i+1][j-1] - y[i][j-1]; + } + } + sum = 0; + for(t = 1; t < n; t++) + { + /* LOOP FOR NEWTON'S FORWARD DIFFERENCE INTERPOLATION FORMULA */ + fy = 1; + facto = 1; + for(m = 0; m < t; m++) + { + fy = fy * (r - m); + facto = facto * (m + 1); + } + fy = fy * (y[0][t]/facto); + sum = sum + fy; + } + yr = sum + y[0][0]; + printf("\nThe value of y = f(x) at xr = %lf is yr = %lf", xr,yr); +} +/*--------------------------- END OF PROGRAM --------------------------*/ diff --git a/c++/Computational_Geometry/C++ Program to Implement NUMERICAL INTEGRATION USING MONTE CARLO METHOD.cpp b/c++/Computational_Geometry/C++ Program to Implement NUMERICAL INTEGRATION USING MONTE CARLO METHOD.cpp new file mode 100644 index 0000000..753001d --- /dev/null +++ b/c++/Computational_Geometry/C++ Program to Implement NUMERICAL INTEGRATION USING MONTE CARLO METHOD.cpp @@ -0,0 +1,55 @@ + + +/*----------- NUMERICAL INTEGRATION USING MONTE CARLO METHOD ----------*/ + +/* THIS PROGRAM INTEGRATES A FUNCTION USING MONTE CARLO METHOD. + IT USES PSEUDORANDOM NUMBERS FOR INTEGRATION. + + f(x) = x*x*x + 7*x*x + 8*x + 1 + + INPUTS : Number of random numbers to be used for integration. + + OUTPUTS : Integration of f(x) over 0 to 1. */ + +/*------------------------------ PROGRAM ---------------------------*/ + +#include +#include +#include +#include + +void main() +{ + double f ( double x); /* FUNCTION TO EVALUATE f(x) */ + double x,sum,n,k; + clrscr(); + printf("\n Computational Techniques - J. S. CHITODE"); + printf("\n NUMERICAL INTEGRATION USING MONTE CARLO METHOD\n"); + printf("\n The function being integrated over" + " limits (0,1) is \n\n" + " f(x) = x*x*x + 7*x*x + 8*x + 1\n"); + randomize(); /* INITIALIZATION OF PSEUDORANDOM NUMBER GENERATOR */ + printf("\nEnter the number of pseudorandom numbers\nto be " + "used for monte carlo integration = "); + scanf("%lf",&n); + k = n; + sum = 0; + while(n-- > 0) + { + x = rand()/(RAND_MAX + 1.0); + /* CALLING PSEUDORANDOM NUMBER GENERATOR */ + sum = sum + f(x); + } + sum = sum/k; + printf("\nThe result of integration is = %lf",sum); +} +/*--------------------------------------------------------------------*/ + +double f ( double x) +{ + double fx; + fx = x*x*x + 7*x*x + 8*x + 1; + /* EVALUATION OF f(x) AT x = PSEUDORANDOM NUMBER */ + return(fx); +} +/*------------------------- END OF PROGRAM --------------------------*/ diff --git a/c++/Computational_Geometry/C++ Program to Implement PSEUDORANDOM NUMBER GENERATION.cpp b/c++/Computational_Geometry/C++ Program to Implement PSEUDORANDOM NUMBER GENERATION.cpp new file mode 100644 index 0000000..2e1564b --- /dev/null +++ b/c++/Computational_Geometry/C++ Program to Implement PSEUDORANDOM NUMBER GENERATION.cpp @@ -0,0 +1,47 @@ + + +/*------------------ PSEUDORANDOM NUMBER GENERATION -------------------*/ + +/* THIS PROGRAM GENERATES A PSEUDORANDOM NUMBER USING STANDARD + FUNCTIONS IN C. + + INPUTS : None + + OUTPUTS : Random numbers between 0 and 1. */ + +/*------------------------------ PROGRAM ---------------------------*/ + +#include +#include +#include +#include + +void main() +{ + double x; + int k; + char ch; + clrscr(); + printf("\n Computational Techniques - J. S. CHITODE"); + printf("\n PSEUDORANDOM NUMBER GENERATION\n"); + randomize(); /* INITIALIZATION OF PSEUDORANDOM NUMBER GENERATOR */ + printf("\nThe sequence of pesudorandom numbers between 0 & 1 " + "is displayed below.\nPress any key to continue and " + "press 'q' to stop....\n\n"); + k = 0; + while(ch != 'q') + { + x = rand()/(RAND_MAX + 1.0); + /* CALLING PSEUDORANDOM NUMBER GENERATOR */ + printf("%lf ",x); + k++; + if(k == 6) + { + /* TO PRINT 6 PSEUDORANDOM NUMBERS ON ONE LINE */ + printf("\n"); + k = 0; + } + ch = getch(); + } +} +/*------------------------- END OF PROGRAM ----------------------------*/ diff --git a/c++/Computational_Geometry/C++ Program to Implement REGULA FALSI METHOD TO FIND ROOT OF AN EQUATION.cpp b/c++/Computational_Geometry/C++ Program to Implement REGULA FALSI METHOD TO FIND ROOT OF AN EQUATION.cpp new file mode 100644 index 0000000..3ed87c7 --- /dev/null +++ b/c++/Computational_Geometry/C++ Program to Implement REGULA FALSI METHOD TO FIND ROOT OF AN EQUATION.cpp @@ -0,0 +1,74 @@ + +/*----------- REGULA FALSI METHOD TO FIND ROOT OF AN EQUATION --------*/ + +/* THE EXPRESSION FOR AN EQUATION IS DEFINED IN function fx + YOU CAN WRITE DIFFERENT EQUATION IN function fx. + HERE, + f(x) = exp(x) - 4*x + + INPUTS : 1) Initial interval [x0,x1] in which root is to + be found. + 2) Number of iterations for given interval and + permissible error. + + OUTPUTS : Value of the root in given interval. */ + +/*------------------------------ PROGRAM --------------------------*/ + +#include +#include +#include +#include + +void main() +{ + double fx ( double x); /* DECLARATION OF FUNCTION */ + double x0,x1,x2,f0,f1,f2,err; + int n,i; + clrscr(); + printf("\n REGULA FALSI METHOD TO FIND ROOT OF AN EQUATION"); + printf("\n\n f(x) = exp(x) - 4*x"); + printf("\n\nEnter an interval [x0,x1] in " + "which root is to be found"); + printf("\nx0 = "); + scanf("%lf",&x0); /* INTERVAL [x0,x1] IS TO BE ENTERED HERE */ + printf("x1 = "); + scanf("%lf",&x1); + printf("\nEnter the number of iterations = "); + scanf("%d",&n); + printf("\npress any key for display of iterations...\n"); + getch(); + i = 0; + while(n-- > 0) + { + f0 = fx(x0); /* CALCULATE f(x) AT x = x0 */ + f1 = fx(x1); /* CALCULATE f(x) AT x = x1 */ + x2 = x1 - ((x1 - x0)/(f1 - f0)) * f1; + /* CALCULATION OF NEXT APPROXIMATION */ + f2 = fx(x2); + i++; + printf("\n\n%d\tx[%d] = %lf\t\tx[%d] = %lf\tx[%d] = %lf\n" + "\tf[%d] = %lf\tf[%d] = %lf\t f[%d] = %lf\n" + ,i,i,x1,i-1,x0,i+1,x2,i,f1,i-1,f0,i+1,f2); + if((f0 * f2) < 0) x1 = x2; + if((f1 * f2) < 0) + { + x0 = x1; + x1 = x2; + } + printf("\nNew interval : x[%d] = %lf\t x[%d] = %lf" + ,i-1,x0,i+1,x1); + getch(); + } + printf("\n\nThe value of root is = %20.15lf",x2); /* ROOT */ +} +/*---------- FUNCTION PROCEDURE TO CALCULATE VALUE OF EQUATION --------*/ + +double fx ( double x) +{ + double f; + f = exp(x) - 4*x; /* FUNCTION f(x) */ + return(f); +} +/*------------------------- END OF PROGRAM ----------------------------*/ + diff --git a/c++/Computational_Geometry/C++ Program to Implement RUNG KUTTA METHOD TO SOLVE DIFFERENTIAL EQUATION.cpp b/c++/Computational_Geometry/C++ Program to Implement RUNG KUTTA METHOD TO SOLVE DIFFERENTIAL EQUATION.cpp new file mode 100644 index 0000000..2cbee78 --- /dev/null +++ b/c++/Computational_Geometry/C++ Program to Implement RUNG KUTTA METHOD TO SOLVE DIFFERENTIAL EQUATION.cpp @@ -0,0 +1,67 @@ + + +/*----------- RUNG KUTTA METHOD TO SOLVE DIFFERENTIAL EQUATION --------*/ + +/* THIS PROGRAM CALCULATES THE VALUE y AT GIVEN VALUE OF x + USING FOURTH ORDER RUNG KUTTA METHOD. THE FUNCTION y' = f(x,y) + IS DEFINED IN THE PROGRAM. + + y' = 1 + y*y + Hence f(x,y) = 1 + y*y + + INPUTS : 1) Initial values of x and y. + + 2) Step size h. + + OUTPUTS : Calculated values of y at every step. */ + +/*------------------------------ PROGRAM --------------------------*/ + +#include +#include +#include +#include + +void main() +{ + double f (double x0,double y0); /* DECLARATION OF A FUNCTION f */ + double y0,y1,x0,x1,h,x,k1,k2,k3,k4,k; + int i,n; + clrscr(); + printf("\n\tRUNG KUTTA METHOD TO SOLVE DIFFERENTIAL EQUATION\n"); + printf("\n\nEnter x0 = "); + scanf("%lf",&x0); /* ENTER VALUE OF x0 */ + printf("\n\nEnter y0 = "); + scanf("%lf",&y0); /* ENTER VALUE OF y0 */ + printf("\n\nEnter the value of x at which y is to be found = "); + scanf("%lf",&x); /* ENTER VALUE OF x */ + printf("\n\nEnter the value of h = "); + scanf("%lf",&h); /* ENTER THE VALUE OF h */ + i = 0; + printf("\nPress any key to see step by step display of results...\n"); + while(x0 < x) /* LOOP TO CALCULATE y USING RUNG KUTTA METHOD */ + { + i++; + k1 = f(x0,y0); + k2 = f(x0+h/2, y0+(h*k1/2)); + k3 = f(x0+h/2, y0+(h*k2/2)); + k4 = f(x0+h, y0+h*k3); + /* CALCULATION OF k USING RUNG KUTTA METHOD */ + y1 = y0 + (h/6)*(k1 + 2*k2 + 2*k3 + k4); + /* CALCULATION OF y FROM VALUES OF k */ + x1 = x0 + h; + printf("\nx%d = %lf y%d = %lf",i,x1,i,y1); + x0 = x1; + y0 = y1; + getch(); + } +} +/*---------------------------------------------------------------------*/ + +double f ( double x,double y) /* FUNCTION TO CALCULATE VALUE OF f(x,y)*/ +{ + double y_dash; + y_dash = 1 + y*y; /* function f(x,y) = y' = 1 + y*y */ + return(y_dash); +} +/*------------------------ END OF PROGRAM -----------------------------*/ diff --git a/c++/Computational_Geometry/C++ Program to Implement SECANT METHOD TO FIND ROOT OF AN EQUATION.cpp b/c++/Computational_Geometry/C++ Program to Implement SECANT METHOD TO FIND ROOT OF AN EQUATION.cpp new file mode 100644 index 0000000..6261f46 --- /dev/null +++ b/c++/Computational_Geometry/C++ Program to Implement SECANT METHOD TO FIND ROOT OF AN EQUATION.cpp @@ -0,0 +1,67 @@ + + +/*--------------- SECANT METHOD TO FIND ROOT OF AN EQUATION ----------*/ + +/* THE EXPRESSION FOR AN EQUATION IS DEFINED IN function fx + YOU CAN WRITE DIFFERENT EQUATION IN function fx. + HERE, + f(x) = x*x*x - 5*x - 7 + + INPUTS : 1) Initial interval [x0,x1] in which root is to + be found. + 2) Number of iterations for given interval and + permissible error. + + OUTPUTS : Value of the root in given interval. */ + +/*---------------Program starts here ----------------------------------*/ + +#include +#include +#include +#include + +void main() +{ + double fx ( double x); /* DECLARATION OF FUNCTION */ + double x0,x1,x2,f0,f1,f2,err; + int n,i; + clrscr(); + printf("\n SECANT METHOD TO FIND ROOT OF AN EQUATION"); + printf("\n\n f(x) = x*x*x - 5*x - 7"); + printf("\n\nEnter an interval [x0,x1] in " + "which root is to be found"); + printf("\nx0 = "); + scanf("%lf",&x0); /* INTERVAL [x0,x1] IS TO BE ENTERED HERE */ + printf("x1 = "); + scanf("%lf",&x1); + printf("\nEnter the number of iterations = "); + scanf("%d",&n); + printf("\npress any key for display of iterations...\n"); + getch(); + i = 0; + while(n-- > 0) + { + f0 = fx(x0); /* CALCULATE f(x) AT x = x0 */ + f1 = fx(x1); /* CALCULATE f(x) AT x = x1 */ + x2 = x1 - ((x1 - x0)/(f1 - f0)) * f1; + /* CALCULATION OF NEXT APPROXIMATION */ + i++; + printf("\n%d x[%d] = %lf x[%d] = %lf",i,i-1,x0,i,x1); + printf("\n f[%d] = %lf f[%d] = %lf",i-1,f0,i,f1); + printf("\n x[%d] = %lf",i+1,x2); + x0 = x1; + x1 = x2; + getch(); + } + printf("\n\nThe value of root is = %20.15lf",x2); /* ROOT */ +} +/*---------- FUNCTION PROCEDURE TO CALCULATE VALUE OF EQUATION --------*/ + +double fx ( double x) +{ + double f; + f = x*x*x - 5*x - 7; /* FUNCTION f(x) */ + return(f); +} +/*-------------------------- END OF PROGRAM ---------------------------*/ diff --git a/c++/Computational_Geometry/C++ Program to Implement SELECTION SORT METHOD.cpp b/c++/Computational_Geometry/C++ Program to Implement SELECTION SORT METHOD.cpp new file mode 100644 index 0000000..58a948e --- /dev/null +++ b/c++/Computational_Geometry/C++ Program to Implement SELECTION SORT METHOD.cpp @@ -0,0 +1,57 @@ + + +/*-------------------- SELECTION SORT METHOD -------------------------*/ + +/* THIS PROGRAM SORTS THE INPUT ARRAY INTO ASCENDING ORDER + USING SELECTION SORT METHOD. + + INPUTS : 1) The total number of elements to be sorted. + + 2) Array of numbers. + + OUTPUTS : Sorted array of elements. */ + +/*------------------------------ PROGRAM -------------------------*/ + +#include +#include +#include +#include + +void main() +{ + double x[100],z; /*DECLARATION OF ARRAY */ + int i,n,k; + clrscr(); + printf("\n Computational Techniques - J. S. CHITODE"); + printf("\n SELECTION SORT METHOD\n"); + printf("\n\nEnter the total number of elements " + "to sorted (max 100) = "); + scanf("%d",&n); /* ENTER THE NUMBER OF ELEMENTS TO BE SORTED */ + for(i = 0; i < n; i++) + { + /* LOOP TO ENTER ACTUAL VALUES OF ARRAY ELEMENTS */ + printf("\nx%d = ",i); + scanf("%lf",&x[i]); + } + for(i = 0; i < n-1; i++) + { + /* LOOP TO SORT THE ARRAY */ + for(k = i; k < n-1; k++) + { + if(x[i] > x[k+1]) + { + z = x[i]; + x[i] = x[k+1]; + x[k+1] = z; + } + } + } + printf("\nThe sorted array in ascending order is ....\n"); + for(i = 0; i < n; i++) + { + /* LOOP TO PRINT THE ARRAY */ + printf("\nx%d = %lf",i,x[i]); + } +} +/*------------------------ END OF PROGRAM ------------------------------*/ diff --git a/c++/Computational_Geometry/C++ Program to Implement SIMPSON'S (One Third) RULE OF INTEGRATION.cpp b/c++/Computational_Geometry/C++ Program to Implement SIMPSON'S (One Third) RULE OF INTEGRATION.cpp new file mode 100644 index 0000000..11061ba --- /dev/null +++ b/c++/Computational_Geometry/C++ Program to Implement SIMPSON'S (One Third) RULE OF INTEGRATION.cpp @@ -0,0 +1,64 @@ + + +/*----------------- SIMPSON'S 1/3 RULE OF INTEGRATION -----------------*/ + +/* THIS PROGRAM CALCULATES THE VALUE OF INTEGRATION USING + SIMPSON'S 1/3 RULE. THE FUNCTION TO BE INTEGRATED IS, + + f(x) = 1/(1+x) + + INPUTS : 1) Lower and upper limits of integration. + + 2) Number of intervals. + + OUTPUTS : Result of integration. */ + +/*------------------------------ PROGRAM --------------------------*/ + +#include +#include +#include +#include + +void main() +{ + double fx (double x0); /* DECLARATION OF A FUNCTION fx */ + double lo,up,f[20],h,x0,sum,result; + int i,n; + clrscr(); + printf("\n\t SIMPSON'S 1/3 RULE OF INTEGRATION"); + printf("\n\nEnter the lower limit of integration = "); + scanf("%lf",&lo); /* ENTER LOWER LIMIT OF INTEGRATION */ + printf("\n\nEnter the upper limit of integration = "); + scanf("%lf",&up); /* ENTER UPPER LIMIT OF INTEGRATION */ + printf("\n\nEnter the value of h = "); + scanf("%lf",&h); /* ENTER THE VALUE OF h */ + n = (up - lo)/h; /* CALCULATION VALUE OF n i.e.STRIPS */ + x0 = lo; + for(i = 0; i <= n; i++) /* LOOP TO CALCULATE VALUE OF f(x) */ + { + f[i] = fx(x0); /* FUNCTION fx IS CALLED HERE */ + x0 = x0 + h; /* NEXT VALUE OF x IS CALCULATED HERE */ + } + sum = 0; + for(i = 1; i <= n-1; i = i + 2) + { + sum = sum + 4*f[i]; /* THIS IS sum = 4 * ( odd ordinates ) */ + } + for(i = 2; i <= n-1; i = i + 2) + { + sum = sum + 2*f[i]; /* THIS IS sum = 2 * ( even ordinates ) */ + } + result = (h/3) * ( f[0] + f[n] + sum ); + /* Result = (h/3) * (4 * sum of odd ordinates + + 2 * sum of even rdinates ) */ + printf("\n\nThe result of integration is = %lf",result); +} + +double fx ( double x) /* FUNCTION TO CALCULATE VALUE OF f(x) */ +{ + double f; + f = 1/(1+x); /* function f(x) = 1(1 + x) */ + return(f); +} +/*------------------------ END OF PROGRAM -----------------------------*/ diff --git a/c++/Computational_Geometry/C++ Program to Implement SIMPSON'S (Three Eight) RULE OF INTEGRATION.cpp b/c++/Computational_Geometry/C++ Program to Implement SIMPSON'S (Three Eight) RULE OF INTEGRATION.cpp new file mode 100644 index 0000000..e2a8617 --- /dev/null +++ b/c++/Computational_Geometry/C++ Program to Implement SIMPSON'S (Three Eight) RULE OF INTEGRATION.cpp @@ -0,0 +1,65 @@ + + +/*----------------- SIMPSON'S 3/8 RULE OF INTEGRATION ----------------*/ + +/* THIS PROGRAM CALCULATES THE VALUE OF INTEGRATION USING + SIMPSON'S 3/8 RULE. THE FUNCTION TO BE INTEGRATED IS, + + f(x) = 4 + 2 sin x + + INPUTS : 1) Lower and upper limits of integration. + + 2) Number of intervals. + + OUTPUTS : Result of integration. */ + +/*------------------------------ PROGRAM -------------------------*/ + +#include +#include +#include +#include + +void main() +{ + double fx (double x0); /* DECLARATION OF A FUNCTION fx */ + double lo,up,f[20],h,x0,sum,result; + int i,n; + clrscr(); + printf("\n\t SIMPSON'S 3/8 RULE OF INTEGRATION"); + printf("\n\nEnter the lower limit of integration = "); + scanf("%lf",&lo); /* ENTER LOWER LIMIT OF INTEGRATION */ + printf("\n\nEnter the upper limit of integration = "); + scanf("%lf",&up); /* ENTER UPPER LIMIT OF INTEGRATION */ + printf("\n\nEnter the value of h = "); + scanf("%lf",&h); /* ENTER THE VALUE OF h */ + n = (up - lo)/h; /* CALCULATION VALUE OF n i.e.STRIPS */ + x0 = lo; + for(i = 0; i <= n; i++) /* LOOP TO CALCULATE VALUE OF f(x) */ + { + f[i] = fx(x0); /* FUNCTION fx IS CALLED HERE */ + x0 = x0 + h; /* NEXT VALUE OF x IS CALCULATED HERE */ + } + sum = 0; + for(i = 1; i <= n-1; i++) + { + if(i == 3*(i/3) ) continue; + sum = sum + 3*f[i]; /* 3 * SUM OF ORDINATES NOT MULTIPLE OF 3 */ + } + for(i = 3; i <= n-1; i = i + 3) + { + sum = sum + 2*f[i]; /*2 * SUM OF ORDINATES WHICH ARE MULTIPLE OF 3*/ + } + result = (3*h/8) * ( f[0] + f[n] + sum ); + /*Result = (3h/8) * (3 * sum of ordinates not multiple of 3 + + 2 * sum of ordinates which are multiple of 3 ) */ + printf("\n\nThe result of integration is = %lf",result); +} + +double fx ( double x) /* FUNCTION TO CALCULATE VALUE OF f(x) */ +{ + double f; + f = 4 + 2 * sin(x); /* function f(x) = 4 + 2 sin x */ + return(f); +} +/*------------------------ END OF PROGRAM ------------------------------*/ diff --git a/c++/Computational_Geometry/C++ Program to Implement Slicker Algorithm that avoids Triangulation to Find Area of a Polygon.cpp b/c++/Computational_Geometry/C++ Program to Implement Slicker Algorithm that avoids Triangulation to Find Area of a Polygon.cpp new file mode 100644 index 0000000..4fe109f --- /dev/null +++ b/c++/Computational_Geometry/C++ Program to Implement Slicker Algorithm that avoids Triangulation to Find Area of a Polygon.cpp @@ -0,0 +1,80 @@ +/*This is a C++ Program to find the area of ploygon using slicker algorithm. The algorithm assumes the usual mathematical convention that positive y points upwards. In computer systems where positive y is downwards (most of them) the easiest thing to do is list the vertices counter-clockwise using the “positive y down” coordinates. The two effects then cancel out to produce a positive area.*/ + +#include + +using namespace std; + +const int MAXPOLY = 200; +double EPSILON = 0.000001; + +class Point +{ +private: +public: + double x, y; +}; + +class Polygon +{ +private: +public: + Point p[MAXPOLY]; + int n; + + Polygon() + { + for (int i = 0; i < MAXPOLY; i++) + Point p[i];// = new Point(); + } +}; + +double area(Polygon p) +{ + double total = 0; + for (int i = 0; i < p.n; i++) + { + int j = (i + 1) % p.n; + total += (p.p[i].x * p.p[j].y) - (p.p[j].x * p.p[i].y); + } + return total / 2; +} + +int main(int argc, char **argv) +{ + Polygon p; + cout << "Enter the number of points in Polygon: "; + cin >> p.n; + cout << "Enter the coordinates of each point: "; + for (int i = 0; i < p.n; i++) + { + cin >> p.p[i].x; + cin >> p.p[i].y; + } + double a = area(p); + if (a > 0) + cout << "The Area of Polygon with " << (p.n) + << " points using Slicker Algorithm is : " << a; + else + cout << "The Area of Polygon with " << p.n + << " points using Slicker Algorithm is : " << (a * -1); +} + +/* + +Enter the number of points in Polygon: 4 +Enter the coordinates of each point: +1 1 +1 6 +6 6 +6 1 +The Area of Polygon with 4 points using Slicker Algorithm is : 25 + +Enter the number of points in Polygon: +5 +Enter the coordinates of each point: +1 2 +4 5 +9 8 +3 2 +1 5 +The Area of Polygon with 5points using Slicker Algorithm is : 6.0 \ No newline at end of file diff --git a/c++/Computational_Geometry/C++ Program to Implement TRAPEZOIDAL RULE OF INTEGRATION.cpp b/c++/Computational_Geometry/C++ Program to Implement TRAPEZOIDAL RULE OF INTEGRATION.cpp new file mode 100644 index 0000000..7d0580d --- /dev/null +++ b/c++/Computational_Geometry/C++ Program to Implement TRAPEZOIDAL RULE OF INTEGRATION.cpp @@ -0,0 +1,58 @@ + + +/*----------------- TRAPEZOIDAL RULE OF INTEGRATION -------------------*/ + +/* THIS PROGRAM CALCULATES THE VALUE OF INTEGRATION USING + TRAPEZIODAL RULE. THE FUNCTION TO BE INTEGRATED IS, + + f(x) = 1/x + + INPUTS : 1) Lower and upper limits of integration. + + 2) Number of intervals. + + OUTPUTS : Result of integration. */ + +/*------------------------------ PROGRAM --------------------------*/ + +#include +#include +#include +#include + +void main() +{ + double fx (double x0); + double lo,up,f[20],h,x0,sum,result; + int i,n; + clrscr(); + printf("\n\t TRAPEZOIDAL RULE OF INTEGRATION"); + printf("\n\nEnter the lower limit of integration = "); + scanf("%lf",&lo); /* ENTER LOWER LIMIT OF INTEGRATION */ + printf("\n\nEnter the upper limit of integration = "); + scanf("%lf",&up); /* ENTER UPPER LIMIT OF INTEGRATION */ + printf("\n\nEnter the value of h = "); + scanf("%lf",&h); /* ENTER THE VALUE OF h */ + n = (up - lo)/h; /* CALCULATION VALUE OF n */ + x0 = lo; + for(i = 0; i <= n; i++) /* LOOP TO CALCULATE VALUE OF f(x) */ + { + f[i] = fx(x0); /* FUNCTION fx IS CALLED HERE */ + x0 = x0 + h; /* NEXT VALUE OF x IS CALCULATED HERE */ + } + sum = 0; + for(i = 1; i <= n-1; i++) + { + sum = sum + 2*f[i]; /*SUMMATION OF ORDINATES FROM y(1) to y(n-1)*/ + } + result = (h/2) * ( f[0] + f[n] + sum ); /* RESULT OF INTEGRATION */ + printf("\n\nThe result of integration is = %lf",result); +} + +double fx ( double x) /* FUNCTION TO CALCULATE VALUE OF f(x) */ +{ + double f; + f = 1/x; + return(f); +} +/*------------------------ END OF PROGRAM ------------------------------*/ diff --git a/c++/Computational_Geometry/C++ Program to Show the Duality Transformation of Line and Point.cpp b/c++/Computational_Geometry/C++ Program to Show the Duality Transformation of Line and Point.cpp new file mode 100644 index 0000000..c71c5ad --- /dev/null +++ b/c++/Computational_Geometry/C++ Program to Show the Duality Transformation of Line and Point.cpp @@ -0,0 +1,58 @@ +#include +#include +#include + +using namespace std; + +void performLineTransformation(double a, double b) +{ + cout << "X: " << (b / a) << ", Y: " << (b * -1); +} + +void performPointTransformation(double x, double y) +{ + cout << "y=" << (-1 * y / x) << "x +" << (-1 * y); +} + +int main(int argc, char **argv) +{ + cout + << "Perform what transformation.\n1. Line Transformation\n2. Point Transformation"; + int option; + cin >> option; + switch (option) + { + case 1: + cout << "Enter the coefficients of line "; + double a, b; + cin >> a >> b; + performLineTransformation(a, b); + break; + case 2: + cout << "Enter the coordinate of point "; + double x, y; + cin >> x >> y; + performPointTransformation(x, y); + break; + default: + break; + } +} + +/* + +Perform what transformation. +1. Line Transformation +2. Point Transformation +1 +Enter the coefficients of line +1 2 +X: 2.0, Y: -2.0 + +Perform what transformation. +1. Line Transformation +2. Point Transformation +2 +Enter the coordinate of point +2 -2 +y=1.0x +2.0 \ No newline at end of file diff --git a/c++/Computational_Geometry/C++ Program to Solve N-Queen Problem.cpp b/c++/Computational_Geometry/C++ Program to Solve N-Queen Problem.cpp new file mode 100644 index 0000000..ac4d037 --- /dev/null +++ b/c++/Computational_Geometry/C++ Program to Solve N-Queen Problem.cpp @@ -0,0 +1,89 @@ +/* + * C++ Program to Solve N-Queen Problem + */ +#include +#include +#include +#define N 8 +using namespace std; + +/* print solution */ +void printSolution(int board[N][N]) +{ + for (int i = 0; i < N; i++) + { + for (int j = 0; j < N; j++) + cout<= 0 && j >= 0; i--, j--) + { + if (board[i][j]) + return false; + } + for (i = row, j = col; j >= 0 && i < N; i++, j--) + { + if (board[i][j]) + return false; + } + return true; +} + +/*solve N Queen problem */ +bool solveNQUtil(int board[N][N], int col) +{ + if (col >= N) + return true; + for (int i = 0; i < N; i++) + { + if ( isSafe(board, i, col) ) + { + board[i][col] = 1; + if (solveNQUtil(board, col + 1) == true) + return true; + board[i][col] = 0; + } + } + return false; +} + +/* solves the N Queen problem using Backtracking.*/ +bool solveNQ() +{ + int board[N][N] = {0}; + if (solveNQUtil(board, 0) == false) + { + cout<<"Solution does not exist"< +#include +#include +#include + +using namespace std; +const int LOW = 0; +const int HIGH = 10; +int main(int argc, char **argv) +{ + time_t seconds; + time(&seconds); + srand((unsigned int) seconds); + int x1, x2, y1, y2; + x1 = rand() % (HIGH - LOW + 1) + LOW; + x2 = rand() % (HIGH - LOW + 1) + LOW; + y1 = rand() % (HIGH - LOW + 1) + LOW; + y2 = rand() % (HIGH - LOW + 1) + LOW; + cout << "The Equation of the 1st line is : (" << (y2 - y1) << ")x+(" << (x1 + - x2) << ")y+(" << (x2 * y1 - x1 * y2) << ") = 0\n"; + int p1, p2, q1, q2; + p1 = rand() % (HIGH - LOW + 1) + LOW; + p2 = rand() % (HIGH - LOW + 1) + LOW; + q1 = rand() % (HIGH - LOW + 1) + LOW; + q2 = rand() % (HIGH - LOW + 1) + LOW; + cout << "The Equation of the 2nd line is : (" << (q2 - q1) << ")x+(" << (p1 + - p2) << ")y+(" << (p2 * q1 - p1 * q2) << ") = 0\n"; + int s1 = (y2 - y1) * p1 + (x1 - x2) * q1 + (x2 * y1 - x1 * y2); + if (s1 < 0) + { + int s2 = (y2 - y1) * p2 + (x1 - x2) * q2 + (x2 * y1 - x1 * y2); + if (s2 >= 0) + cout << "The lines intersect"; + else if (s2 < 0) + cout << "The lines doesn't intersect"; + } + else if (s1 > 0) + { + int s2 = (y2 - y1) * p2 + (x1 - x2) * q2 + (x2 * y1 - x1 * y2); + if (s2 <= 0) + cout << "The lines intersect"; + else if (s2 > 0) + cout << "The lines doesn't intersect"; + } + else + cout << "The point lies on the line"; + return 0; +} + +/* +The Equation of the 1st line is : (4)x+(1)y+(-6) = 0 +The Equation of the 2nd line is : (-1)x+(-9)y+(46) = 0 +The lines doesn't intersect + +The Equation of the 1st line is : (3)x+(7)y+(-59) = 0 +The Equation of the 2nd line is : (-8)x+(1)y+(56) = 0 +The lines intersect \ No newline at end of file diff --git a/c++/Hard_Graph_Problems/C++ Program to Check Whether Graph is DAG.cpp b/c++/Hard_Graph_Problems/C++ Program to Check Whether Graph is DAG.cpp new file mode 100644 index 0000000..5283c48 --- /dev/null +++ b/c++/Hard_Graph_Problems/C++ Program to Check Whether Graph is DAG.cpp @@ -0,0 +1,137 @@ +/*This is a C++ Program to check whether graph is DAG. In mathematics and computer science, a directed acyclic graph (DAG Listeni/’dæg/), is a directed graph with no directed cycles. That is, it is formed by a collection of vertices and directed edges, each edge connecting one vertex to another, such that there is no way to start at some vertex v and follow a sequence of edges that eventually loops back to v again.*/ + +#include +#include +#include +using namespace std; +int c = 0; +struct adj_list +{ + int dest; + adj_list *next; +}*np = NULL, *np1 = NULL, *p = NULL, *q = NULL; +struct Graph +{ + int v; + adj_list *ptr; +} array[6]; +void addReverseEdge(int src, int dest) +{ + np1 = new adj_list; + np1->dest = src; + np1->next = NULL; + if (array[dest].ptr == NULL) + { + array[dest].ptr = np1; + q = array[dest].ptr; + q->next = NULL; + } + else + { + q = array[dest].ptr; + while (q->next != NULL) + { + q = q->next; + } + q->next = np1; + } +} +void addEdge(int src, int dest) +{ + np = new adj_list; + np->dest = dest; + np->next = NULL; + if (array[src].ptr == NULL) + { + array[src].ptr = np; + p = array[src].ptr; + p->next = NULL; + } + else + { + p = array[src].ptr; + while (p->next != NULL) + { + p = p->next; + } + p->next = np; + } + //addReverseEdge(src, dest); +} +void print_graph(int n) +{ + for (int i = 0; i < n; i++) + { + cout << "Adjacency List of " << array[i].v << ": "; + while (array[i].ptr != NULL) + { + cout << (array[i].ptr)->dest << " "; + array[i].ptr = (array[i].ptr)->next; + } + cout << endl; + } +} + +int checkDAG(int n) +{ + int count = 0; + int size = n - 1; + for (int i = 0; i < n; i++) + { + //cout << "Adjacency List of " << array[i].v << ": "; + if (count == size) + { + return 1; + } + if (array[i].ptr == NULL) + { + count++; + for (int j = 0; j < n; j++) + { + while (array[j].ptr != NULL) + { + if ((array[j].ptr)->dest == (array[i].ptr)->dest) + { + (array[j].ptr)->dest = -1; + } + array[i].ptr = (array[i].ptr)->next; + } + } + } + } + return 0; +} +int main() +{ + int n = 6; + cout << "Number of vertices: " << n << endl; + for (int i = 0; i < n; i++) + { + array[i].v = i; + array[i].ptr = NULL; + } + addEdge(0, 1); + addEdge(1, 2); + addEdge(1, 3); + addEdge(3, 4); + addEdge(4, 5); + addEdge(5, 3); + addEdge(5, 2); + print_graph(n); + cout << "The given graph is 'Directed Acyclic Graph' :"; + if (checkDAG(n) == 1) + cout << " True"; + else + cout << " False"; +} + +/* + +Number of vertices: 6 +Adjacency List of 0: 1 +Adjacency List of 1: 2 3 +Adjacency List of 2: +Adjacency List of 3: 4 +Adjacency List of 4: 5 +Adjacency List of 5: 3 2 +The given graph is 'Directed Acyclic Graph' : True \ No newline at end of file diff --git a/c++/Hard_Graph_Problems/C++ Program to Find All the Cliques of a Given Size k.cpp b/c++/Hard_Graph_Problems/C++ Program to Find All the Cliques of a Given Size k.cpp new file mode 100644 index 0000000..fca9cab --- /dev/null +++ b/c++/Hard_Graph_Problems/C++ Program to Find All the Cliques of a Given Size k.cpp @@ -0,0 +1,261 @@ +/*This is a C++ Program to find the cliques of size k in a a graph. An undirected graph is formed by a finite set of vertices and a set of unordered pairs of vertices, which are called edges. By convention, in algorithm analysis, the number of vertices in the graph is denoted by n and the number of edges is denoted by m. A clique in a graph G is a complete subgraph of G; that is, it is a subset S of the vertices such that every two vertices in S are connected by an edge in G. A maximal clique is a clique to which no more vertices can be added; a maximum clique is a clique that includes the largest possible number of vertices, and the clique number ?(G) is the number of vertices in a maximum clique of G.*/ + +#include +#include +#include +#include +using namespace std; + +bool removable(vector neighbor, vector cover); +int max_removable(vector > neighbors, vector cover); +vector procedure_1(vector > neighbors, vector cover); +vector procedure_2(vector > neighbors, vector cover, + int k); +int cover_size(vector cover); +ifstream infile("graph.txt"); +ofstream outfile("cliques.txt"); + +int main() +{ + //Read Graph (note we work with the complement of the input graph) + cout << "Clique Algorithm." << endl; + int n, i, j, k, K, p, q, r, s, min, edge, counter = 0; + infile >> n; + vector > graph; + for (i = 0; i < n; i++) + { + vector row; + for (j = 0; j < n; j++) + { + infile >> edge; + if (edge == 0) + row.push_back(1); + else + row.push_back(0); + } + graph.push_back(row); + } + //Find Neighbors + vector > neighbors; + for (i = 0; i < graph.size(); i++) + { + vector neighbor; + for (j = 0; j < graph[i].size(); j++) + if (graph[i][j] == 1) + neighbor.push_back(j); + neighbors.push_back(neighbor); + } + cout << "Graph has n = " << n << " vertices." << endl; + //Read maximum size of Clique wanted + cout << "Find a Clique of size at least k = "; + cin >> K; + k = n - K; + //Find Cliques + bool found = false; + cout << "Finding Cliques..." << endl; + min = n + 1; + vector > covers; + vector allcover; + for (i = 0; i < graph.size(); i++) + allcover.push_back(1); + for (i = 0; i < allcover.size(); i++) + { + if (found) + break; + counter++; + cout << counter << ". "; + outfile << counter << ". "; + vector cover = allcover; + cover[i] = 0; + cover = procedure_1(neighbors, cover); + s = cover_size(cover); + if (s < min) + min = s; + if (s <= k) + { + outfile << "Clique (" << n - s << "): "; + for (j = 0; j < cover.size(); j++) + if (cover[j] == 0) + outfile << j + 1 << " "; + outfile << endl; + cout << "Clique Size: " << n - s << endl; + covers.push_back(cover); + found = true; + break; + } + for (j = 0; j < n - k; j++) + cover = procedure_2(neighbors, cover, j); + s = cover_size(cover); + if (s < min) + min = s; + outfile << "Clique (" << n - s << "): "; + for (j = 0; j < cover.size(); j++) + if (cover[j] == 0) + outfile << j + 1 << " "; + outfile << endl; + cout << "Clique Size: " << n - s << endl; + covers.push_back(cover); + if (s <= k) + { + found = true; + break; + } + } + //Pairwise Intersections + for (p = 0; p < covers.size(); p++) + { + if (found) + break; + for (q = p + 1; q < covers.size(); q++) + { + if (found) + break; + counter++; + cout << counter << ". "; + outfile << counter << ". "; + vector cover = allcover; + for (r = 0; r < cover.size(); r++) + if (covers[p][r] == 0 && covers[q][r] == 0) + cover[r] = 0; + cover = procedure_1(neighbors, cover); + s = cover_size(cover); + if (s < min) + min = s; + if (s <= k) + { + outfile << "Clique (" << n - s << "): "; + for (j = 0; j < cover.size(); j++) + if (cover[j] == 0) + outfile << j + 1 << " "; + outfile << endl; + cout << "Clique Size: " << n - s << endl; + found = true; + break; + } + for (j = 0; j < k; j++) + cover = procedure_2(neighbors, cover, j); + s = cover_size(cover); + if (s < min) + min = s; + outfile << "Clique (" << n - s << "): "; + for (j = 0; j < cover.size(); j++) + if (cover[j] == 0) + outfile << j + 1 << " "; + outfile << endl; + cout << "Clique Size: " << n - s << endl; + if (s <= k) + { + found = true; + break; + } + } + } + if (found) + cout << "Found Clique of size at least " << K << "." << endl; + else + cout << "Could not find Clique of size at least " << K << "." << endl + << "Maximum Clique size found is " << n - min << "." << endl; + cout << "See cliques.txt for results." << endl; + return 0; +} + +bool removable(vector neighbor, vector cover) +{ + bool check = true; + for (int i = 0; i < neighbor.size(); i++) + if (cover[neighbor[i]] == 0) + { + check = false; + break; + } + return check; +} + +int max_removable(vector > neighbors, vector cover) +{ + int r = -1, max = -1; + for (int i = 0; i < cover.size(); i++) + { + if (cover[i] == 1 && removable(neighbors[i], cover) == true) + { + vector temp_cover = cover; + temp_cover[i] = 0; + int sum = 0; + for (int j = 0; j < temp_cover.size(); j++) + if (temp_cover[j] == 1 && removable(neighbors[j], temp_cover) + == true) + sum++; + if (sum > max) + { + max = sum; + r = i; + } + } + } + return r; +} + +vector procedure_1(vector > neighbors, vector cover) +{ + vector temp_cover = cover; + int r = 0; + while (r != -1) + { + r = max_removable(neighbors, temp_cover); + if (r != -1) + temp_cover[r] = 0; + } + return temp_cover; +} + +vector procedure_2(vector > neighbors, vector cover, + int k) +{ + int count = 0; + vector temp_cover = cover; + int i = 0; + for (int i = 0; i < temp_cover.size(); i++) + { + if (temp_cover[i] == 1) + { + int sum = 0, index; + for (int j = 0; j < neighbors[i].size(); j++) + if (temp_cover[neighbors[i][j]] == 0) + { + index = j; + sum++; + } + if (sum == 1 && cover[neighbors[i][index]] == 0) + { + temp_cover[neighbors[i][index]] = 1; + temp_cover[i] = 0; + temp_cover = procedure_1(neighbors, temp_cover); + count++; + } + if (count > k) + break; + } + } + return temp_cover; +} + +int cover_size(vector cover) +{ + int count = 0; + for (int i = 0; i < cover.size(); i++) + if (cover[i] == 1) + count++; + return count; +} + +/* + +graph.txt: +4 +0 1 1 1 +1 0 1 1 +1 1 0 1 +1 1 1 0 + +cliques.txt: +Clique ( 4 ): 1 2 3 4 \ No newline at end of file diff --git a/c++/Hard_Graph_Problems/C++ Program to Find Hamiltonian Cycle.cpp b/c++/Hard_Graph_Problems/C++ Program to Find Hamiltonian Cycle.cpp new file mode 100644 index 0000000..5ac117b --- /dev/null +++ b/c++/Hard_Graph_Problems/C++ Program to Find Hamiltonian Cycle.cpp @@ -0,0 +1,111 @@ +/* + * C++ Program to Find Hamiltonian Cycle + */ +#include +#include +#include +#define V 5 +using namespace std; + +void printSolution(int path[]); + +/* + * check if the vertex v can be added at index 'pos' in the Hamiltonian Cycle + */ +bool isSafe(int v, bool graph[V][V], int path[], int pos) +{ + if (graph [path[pos-1]][v] == 0) + return false; + for (int i = 0; i < pos; i++) + if (path[i] == v) + return false; + return true; +} + +/* solve hamiltonian cycle problem */ +bool hamCycleUtil(bool graph[V][V], int path[], int pos) +{ + if (pos == V) + { + if (graph[ path[pos-1] ][ path[0] ] == 1) + return true; + else + return false; + } + for (int v = 1; v < V; v++) + { + if (isSafe(v, graph, path, pos)) + { + path[pos] = v; + if (hamCycleUtil (graph, path, pos+1) == true) + return true; + path[pos] = -1; + } + } + return false; +} + +/* solves the Hamiltonian Cycle problem using Backtracking.*/ +bool hamCycle(bool graph[V][V]) +{ + int *path = new int[V]; + for (int i = 0; i < V; i++) + path[i] = -1; + path[0] = 0; + if (hamCycleUtil(graph, path, 1) == false) + { + cout<<"\nSolution does not exist"< +#include +#include +#include +using namespace std; + +bool removable(vector neighbor, vector cover); +int max_removable(vector > neighbors, vector cover); +vector procedure_1(vector > neighbors, vector cover); +vector procedure_2(vector > neighbors, vector cover, + int k); +int cover_size(vector cover); +ifstream infile("graph.txt"); +ofstream outfile("sets.txt"); + +int main() +{ + //Read Graph + cout << "Independent Set Algorithm." << endl; + int n, i, j, k, K, p, q, r, s, min, edge, counter = 0; + infile >> n; + vector > graph; + for (i = 0; i < n; i++) + { + vector row; + for (j = 0; j < n; j++) + { + infile >> edge; + row.push_back(edge); + } + graph.push_back(row); + } + //Find Neighbors + vector > neighbors; + for (i = 0; i < graph.size(); i++) + { + vector neighbor; + for (j = 0; j < graph[i].size(); j++) + if (graph[i][j] == 1) + neighbor.push_back(j); + neighbors.push_back(neighbor); + } + cout << "Graph has n = " << n << " vertices." << endl; + //Read maximum size of Independent Set wanted + cout << "Find an Independent Set of size at least k = "; + cin >> K; + k = n - K; + //Find Independent Sets + bool found = false; + cout << "Finding Independent Sets..." << endl; + min = n + 1; + vector > covers; + vector allcover; + for (i = 0; i < graph.size(); i++) + allcover.push_back(1); + for (i = 0; i < allcover.size(); i++) + { + if (found) + break; + counter++; + cout << counter << ". "; + outfile << counter << ". "; + vector cover = allcover; + cover[i] = 0; + cover = procedure_1(neighbors, cover); + s = cover_size(cover); + if (s < min) + min = s; + if (s <= k) + { + outfile << "Independent Set (" << n - s << "): "; + for (j = 0; j < cover.size(); j++) + if (cover[j] == 0) + outfile << j + 1 << " "; + outfile << endl; + cout << "Independent Set Size: " << n - s << endl; + covers.push_back(cover); + found = true; + break; + } + for (j = 0; j < n - k; j++) + cover = procedure_2(neighbors, cover, j); + s = cover_size(cover); + if (s < min) + min = s; + outfile << "Independent Set (" << n - s << "): "; + for (j = 0; j < cover.size(); j++) + if (cover[j] == 0) + outfile << j + 1 << " "; + outfile << endl; + cout << "Independent Set Size: " << n - s << endl; + covers.push_back(cover); + if (s <= k) + { + found = true; + break; + } + } + //Pairwise Intersections + for (p = 0; p < covers.size(); p++) + { + if (found) + break; + for (q = p + 1; q < covers.size(); q++) + { + if (found) + break; + counter++; + cout << counter << ". "; + outfile << counter << ". "; + vector cover = allcover; + for (r = 0; r < cover.size(); r++) + if (covers[p][r] == 0 && covers[q][r] == 0) + cover[r] = 0; + cover = procedure_1(neighbors, cover); + s = cover_size(cover); + if (s < min) + min = s; + if (s <= k) + { + outfile << "Independent Set (" << n - s << "): "; + for (j = 0; j < cover.size(); j++) + if (cover[j] == 0) + outfile << j + 1 << " "; + outfile << endl; + cout << "Independent Set Size: " << n - s << endl; + found = true; + break; + } + for (j = 0; j < k; j++) + cover = procedure_2(neighbors, cover, j); + s = cover_size(cover); + if (s < min) + min = s; + outfile << "Independent Set (" << n - s << "): "; + for (j = 0; j < cover.size(); j++) + if (cover[j] == 0) + outfile << j + 1 << " "; + outfile << endl; + cout << "Independent Set Size: " << n - s << endl; + if (s <= k) + { + found = true; + break; + } + } + } + if (found) + cout << "Found Independent Set of size at least " << K << "." << endl; + else + cout << "Could not find Independent Set of size at least " << K << "." + << endl << "Maximum Independent Set size found is " << n - min + << "." << endl; + cout << "See sets.txt for results." << endl; + system("PAUSE"); + return 0; +} + +bool removable(vector neighbor, vector cover) +{ + bool check = true; + for (int i = 0; i < neighbor.size(); i++) + if (cover[neighbor[i]] == 0) + { + check = false; + break; + } + return check; +} + +int max_removable(vector > neighbors, vector cover) +{ + int r = -1, max = -1; + for (int i = 0; i < cover.size(); i++) + { + if (cover[i] == 1 && removable(neighbors[i], cover) == true) + { + vector temp_cover = cover; + temp_cover[i] = 0; + int sum = 0; + for (int j = 0; j < temp_cover.size(); j++) + if (temp_cover[j] == 1 && removable(neighbors[j], temp_cover) + == true) + sum++; + if (sum > max) + { + max = sum; + r = i; + } + } + } + return r; +} + +vector procedure_1(vector > neighbors, vector cover) +{ + vector temp_cover = cover; + int r = 0; + while (r != -1) + { + r = max_removable(neighbors, temp_cover); + if (r != -1) + temp_cover[r] = 0; + } + return temp_cover; +} + +vector procedure_2(vector > neighbors, vector cover, + int k) +{ + int count = 0; + vector temp_cover = cover; + int i = 0; + for (int i = 0; i < temp_cover.size(); i++) + { + if (temp_cover[i] == 1) + { + int sum = 0, index; + for (int j = 0; j < neighbors[i].size(); j++) + if (temp_cover[neighbors[i][j]] == 0) + { + index = j; + sum++; + } + if (sum == 1 && cover[neighbors[i][index]] == 0) + { + temp_cover[neighbors[i][index]] = 1; + temp_cover[i] = 0; + temp_cover = procedure_1(neighbors, temp_cover); + count++; + } + if (count > k) + break; + } + } + return temp_cover; +} + +int cover_size(vector cover) +{ + int count = 0; + for (int i = 0; i < cover.size(); i++) + if (cover[i] == 1) + count++; + return count; +} + +/* +graph.txt: +4 +0 1 1 1 +1 0 1 1 +1 1 0 1 +1 1 1 0 + +set.txt: +Independent Set ( 1 ): 2 \ No newline at end of file diff --git a/c++/Hard_Graph_Problems/C++ Program to Find Minimum Number of Edges to Cut to make the Graph Disconnected.cpp b/c++/Hard_Graph_Problems/C++ Program to Find Minimum Number of Edges to Cut to make the Graph Disconnected.cpp new file mode 100644 index 0000000..1e84642 --- /dev/null +++ b/c++/Hard_Graph_Problems/C++ Program to Find Minimum Number of Edges to Cut to make the Graph Disconnected.cpp @@ -0,0 +1,126 @@ +/*This is a C++ Program to find minimum number of edges to cut to make the graph disconnected. An edge in an undirected connected graph is a bridge if removing it disconnects the graph. For a disconnected undirected graph, definition is similar, a bridge is an edge removing which increases number of connected components.*/ + +// A C++ program to find bridges in a given undirected graph +#include +#include +#define NIL -1 +using namespace std; + +// A class that represents an undirected graph +class Graph +{ + int V; // No. of vertices + list *adj; // A dynamic array of adjacency lists + void bridgeUtil(int v, bool visited[], int disc[], int low[], + int parent[]); +public: + Graph(int V); // Constructor + void addEdge(int v, int w); // function to add an edge to graph + void bridge(); // prints all bridges +}; + +Graph::Graph(int V) +{ + this->V = V; + adj = new list [V]; +} + +void Graph::addEdge(int v, int w) +{ + adj[v].push_back(w); + adj[w].push_back(v); // Note: the graph is undirected +} + +void Graph::bridgeUtil(int u, bool visited[], int disc[], int low[], + int parent[]) +{ + // A static variable is used for simplicity, we can avoid use of static + // variable by passing a pointer. + static int time = 0; + // Mark the current node as visited + visited[u] = true; + // Initialize discovery time and low value + disc[u] = low[u] = ++time; + // Go through all vertices aadjacent to this + list::iterator i; + for (i = adj[u].begin(); i != adj[u].end(); ++i) + { + int v = *i; // v is current adjacent of u + // If v is not visited yet, then recur for it + if (!visited[v]) + { + parent[v] = u; + bridgeUtil(v, visited, disc, low, parent); + // Check if the subtree rooted with v has a connection to + // one of the ancestors of u + low[u] = min(low[u], low[v]); + // If the lowest vertex reachable from subtree under v is + // below u in DFS tree, then u-v is a bridge + if (low[v] > disc[u]) + cout << u << " " << v << endl; + } + // Update low value of u for parent function calls. + else if (v != parent[u]) + low[u] = min(low[u], disc[v]); + } +} + +// DFS based function to find all bridges. It uses recursive function bridgeUtil() +void Graph::bridge() +{ + // Mark all the vertices as not visited + bool *visited = new bool[V]; + int *disc = new int[V]; + int *low = new int[V]; + int *parent = new int[V]; + // Initialize parent and visited arrays + for (int i = 0; i < V; i++) + { + parent[i] = NIL; + visited[i] = false; + } + // Call the recursive helper function to find Bridges + // in DFS tree rooted with vertex 'i' + for (int i = 0; i < V; i++) + if (visited[i] == false) + bridgeUtil(i, visited, disc, low, parent); +} + +// Driver program to test above function +int main() +{ + // Create graphs given in above diagrams + cout << "\nBridges in first graph \n"; + Graph g1(5); + g1.addEdge(1, 0); + g1.addEdge(0, 2); + g1.addEdge(2, 1); + g1.addEdge(0, 3); + g1.addEdge(3, 4); + g1.bridge(); + cout << "\nBridges in second graph \n"; + Graph g2(4); + g2.addEdge(0, 1); + g2.addEdge(1, 2); + g2.addEdge(2, 3); + g2.bridge(); + cout << "\nBridges in third graph \n"; + Graph g3(7); + g3.addEdge(0, 1); + g3.addEdge(1, 2); + g3.addEdge(2, 0); + g3.addEdge(1, 3); + g3.addEdge(1, 4); + g3.addEdge(1, 6); + g3.addEdge(3, 5); + g3.addEdge(4, 5); + g3.bridge(); + return 0; +} + +/* +Bridges in first graph + +3 4 + + diff --git a/c++/Hard_Graph_Problems/C++ Program to Find Size of the Largest Independent Set(LIS) in a Given a Binary Tree.cpp b/c++/Hard_Graph_Problems/C++ Program to Find Size of the Largest Independent Set(LIS) in a Given a Binary Tree.cpp new file mode 100644 index 0000000..2f52a4c --- /dev/null +++ b/c++/Hard_Graph_Problems/C++ Program to Find Size of the Largest Independent Set(LIS) in a Given a Binary Tree.cpp @@ -0,0 +1,75 @@ +/*This is a C++ Program to find largest independent set in a binary tree. In graph theory, an independent set or stable set is a set of vertices in a graph, no two of which are adjacent. That is, it is a set I of vertices such that for every two vertices in I, there is no edge connecting the two. Equivalently, each edge in the graph has at most one endpoint in I. The size of an independent set is the number of vertices it contains. Independent sets have also been called internally stable sets. A maximal independent set is either an independent set such that adding any other vertex to the set forces the set to contain an edge or the set of all vertices of the empty graph.*/ + +/* Dynamic programming based program for Largest Independent Set problem */ +#include +#include +#include + +using namespace std; + +// A utility function to find max of two integers +int max(int x, int y) +{ + return (x > y) ? x : y; +} + +/* A binary tree node has data, pointer to left child and a pointer to + right child */ +struct node +{ + int data; + int liss; + struct node *left, *right; +}; + +// A memoization function returns size of the largest independent set in +// a given binary tree +int LISS(struct node *root) +{ + if (root == NULL) + return 0; + if (root->liss) + return root->liss; + if (root->left == NULL && root->right == NULL) + return (root->liss = 1); + // Caculate size excluding the current node + int liss_excl = LISS(root->left) + LISS(root->right); + // Calculate size including the current node + int liss_incl = 1; + if (root->left) + liss_incl += LISS(root->left->left) + LISS(root->left->right); + if (root->right) + liss_incl += LISS(root->right->left) + LISS(root->right->right); + // Return the maximum of two sizes + root->liss = max(liss_incl, liss_excl); + return root->liss; +} + +// A utility function to create a node +struct node* newNode(int data) +{ + struct node* temp = (struct node *) malloc(sizeof(struct node)); + temp->data = data; + temp->left = temp->right = NULL; + temp->liss = 0; + return temp; +} + +// Driver program to test above functions +int main() +{ + // Let us construct the tree given in the above diagram + struct node *root = newNode(20); + root->left = newNode(8); + root->left->left = newNode(4); + root->left->right = newNode(12); + root->left->right->left = newNode(10); + root->left->right->right = newNode(14); + root->right = newNode(22); + root->right->right = newNode(25); + cout<<"Size of the Largest Independent Set is "<< LISS(root); + return 0; +} + +/* +Size of the Largest Independent Set is 5 \ No newline at end of file diff --git a/c++/Hard_Graph_Problems/C++ Program to Find a Good Feedback Edge Set in a Graph.cpp b/c++/Hard_Graph_Problems/C++ Program to Find a Good Feedback Edge Set in a Graph.cpp new file mode 100644 index 0000000..b77a136 --- /dev/null +++ b/c++/Hard_Graph_Problems/C++ Program to Find a Good Feedback Edge Set in a Graph.cpp @@ -0,0 +1,157 @@ +#include +#include +#include +using namespace std; +int c = 0; +struct adj_list +{ + int dest; + adj_list *next; +}*np = NULL, *np1 = NULL, *p = NULL, *q = NULL; +struct Graph +{ + int v; + adj_list *ptr; +} array[6]; +void addReverseEdge(int src, int dest) +{ + np1 = new adj_list; + np1->dest = src; + np1->next = NULL; + if (array[dest].ptr == NULL) + { + array[dest].ptr = np1; + q = array[dest].ptr; + q->next = NULL; + } + else + { + q = array[dest].ptr; + while (q->next != NULL) + { + q = q->next; + } + q->next = np1; + } +} +void addEdge(int src, int dest) +{ + np = new adj_list; + np->dest = dest; + np->next = NULL; + if (array[src].ptr == NULL) + { + array[src].ptr = np; + p = array[src].ptr; + p->next = NULL; + } + else + { + p = array[src].ptr; + while (p->next != NULL) + { + p = p->next; + } + p->next = np; + } + //addReverseEdge(src, dest); +} +void print_graph(int n) +{ + for (int i = 0; i < n; i++) + { + cout << "Adjacency List of " << array[i].v << ": "; + while (array[i].ptr != NULL) + { + cout << (array[i].ptr)->dest << " "; + array[i].ptr = (array[i].ptr)->next; + } + cout << endl; + } +} + +int checkDAG(int n) +{ + int count = 0; + int size = n - 1; + for (int i = 0; i < n; i++) + { + if (count == size) + { + return 0; + } + if (array[i].ptr == NULL) + { + count++; + for (int j = 0; j < n; j++) + { + while (array[j].ptr != NULL) + { + if ((array[j].ptr)->dest == (array[i].ptr)->dest) + { + (array[j].ptr)->dest = -1; + } + array[i].ptr = (array[i].ptr)->next; + } + } + } + } + cout<<"after checking dag"; + int visited[n + 1]; + for (int i = 0; i < n; i++) + { + while (array[i].ptr != NULL) + { + cout << (array[i].ptr)->dest << " "; + visited[i] = 1; + for (int j = 0; j < n; j++) + { + while (array[j].ptr != NULL) + { + cout << (array[j].ptr)->dest << " "; + if (visited[array[j].v] == 1) + { + cout << array[i].v << " - " << array[j].v; + } + array[j].ptr = (array[j].ptr)->next; + } + cout << endl; + } + array[i].ptr = (array[i].ptr)->next; + } + cout << endl; + } + return 1; +} +int main() +{ + int n = 6; + cout << "Number of vertices: " << n << endl; + for (int i = 0; i < n; i++) + { + array[i].v = i; + array[i].ptr = NULL; + } + addEdge(0, 1); + addEdge(1, 2); + addEdge(1, 3); + addEdge(3, 4); + addEdge(4, 5); + addEdge(3, 5); + addEdge(5, 2); + print_graph(n); + cout << "Feedback arc Set: "; + if (checkDAG(n) == 0) + cout << " None"; +} + +/* + +Number of vertices: 6 +Adjacency List of 0: 1 +Adjacency List of 1: 2 3 +Adjacency List of 2: +Adjacency List of 3: 4 5 +Adjacency List of 4: 5 +Adjacency List of 5: 2 +Feedback arc Set: None \ No newline at end of file diff --git a/c++/Hard_Graph_Problems/C++ Program to Find a Good Feedback Vertex Set.cpp b/c++/Hard_Graph_Problems/C++ Program to Find a Good Feedback Vertex Set.cpp new file mode 100644 index 0000000..910d0e9 --- /dev/null +++ b/c++/Hard_Graph_Problems/C++ Program to Find a Good Feedback Vertex Set.cpp @@ -0,0 +1,157 @@ +#include +#include +#include +using namespace std; +int c = 0; +struct adj_list +{ + int dest; + adj_list *next; +}*np = NULL, *np1 = NULL, *p = NULL, *q = NULL; +struct Graph +{ + int v; + adj_list *ptr; +} array[6]; +void addReverseEdge(int src, int dest) +{ + np1 = new adj_list; + np1->dest = src; + np1->next = NULL; + if (array[dest].ptr == NULL) + { + array[dest].ptr = np1; + q = array[dest].ptr; + q->next = NULL; + } + else + { + q = array[dest].ptr; + while (q->next != NULL) + { + q = q->next; + } + q->next = np1; + } +} +void addEdge(int src, int dest) +{ + np = new adj_list; + np->dest = dest; + np->next = NULL; + if (array[src].ptr == NULL) + { + array[src].ptr = np; + p = array[src].ptr; + p->next = NULL; + } + else + { + p = array[src].ptr; + while (p->next != NULL) + { + p = p->next; + } + p->next = np; + } + //addReverseEdge(src, dest); +} +void print_graph(int n) +{ + for (int i = 0; i < n; i++) + { + cout << "Adjacency List of " << array[i].v << ": "; + while (array[i].ptr != NULL) + { + cout << (array[i].ptr)->dest << " "; + array[i].ptr = (array[i].ptr)->next; + } + cout << endl; + } +} + +int checkDAG(int n) +{ + int count = 0; + int size = n - 1; + for (int i = 0; i < n; i++) + { + if (count == size) + { + return 0; + } + if (array[i].ptr == NULL) + { + count++; + for (int j = 0; j < n; j++) + { + while (array[j].ptr != NULL) + { + if ((array[j].ptr)->dest == (array[i].ptr)->dest) + { + (array[j].ptr)->dest = -1; + } + array[i].ptr = (array[i].ptr)->next; + } + } + } + } + cout << "after checking dag"; + int visited[n + 1]; + for (int i = 0; i < n; i++) + { + while (array[i].ptr != NULL) + { + cout << (array[i].ptr)->dest << " "; + visited[i] = 1; + for (int j = 0; j < n; j++) + { + while (array[j].ptr != NULL) + { + cout << (array[j].ptr)->dest << " "; + if (visited[array[j].v] == 1) + { + cout << array[j].v; + } + array[j].ptr = (array[j].ptr)->next; + } + cout << endl; + } + array[i].ptr = (array[i].ptr)->next; + } + cout << endl; + } + return 1; +} +int main() +{ + int n = 6; + cout << "Number of vertices: " << n << endl; + for (int i = 0; i < n; i++) + { + array[i].v = i; + array[i].ptr = NULL; + } + addEdge(0, 1); + addEdge(1, 2); + addEdge(1, 3); + addEdge(3, 4); + addEdge(4, 5); + addEdge(3, 5); + addEdge(5, 2); + print_graph(n); + cout << "Feedback Vertex Set: "; + if (checkDAG(n) == 0) + cout << " None"; +} + +/* + +Number of vertices: 6 +Adjacency List of 0: 1 +Adjacency List of 1: 2 3 +Adjacency List of 2: +Adjacency List of 3: 4 5 +Adjacency List of 4: 5 +Adjacency List of 5: 2 +Feedback Vertex Set: None \ No newline at end of file diff --git a/c++/Hard_Graph_Problems/C++ Program to Find the Largest clique in a Planar Graph.cpp b/c++/Hard_Graph_Problems/C++ Program to Find the Largest clique in a Planar Graph.cpp new file mode 100644 index 0000000..fca9cab --- /dev/null +++ b/c++/Hard_Graph_Problems/C++ Program to Find the Largest clique in a Planar Graph.cpp @@ -0,0 +1,261 @@ +/*This is a C++ Program to find the cliques of size k in a a graph. An undirected graph is formed by a finite set of vertices and a set of unordered pairs of vertices, which are called edges. By convention, in algorithm analysis, the number of vertices in the graph is denoted by n and the number of edges is denoted by m. A clique in a graph G is a complete subgraph of G; that is, it is a subset S of the vertices such that every two vertices in S are connected by an edge in G. A maximal clique is a clique to which no more vertices can be added; a maximum clique is a clique that includes the largest possible number of vertices, and the clique number ?(G) is the number of vertices in a maximum clique of G.*/ + +#include +#include +#include +#include +using namespace std; + +bool removable(vector neighbor, vector cover); +int max_removable(vector > neighbors, vector cover); +vector procedure_1(vector > neighbors, vector cover); +vector procedure_2(vector > neighbors, vector cover, + int k); +int cover_size(vector cover); +ifstream infile("graph.txt"); +ofstream outfile("cliques.txt"); + +int main() +{ + //Read Graph (note we work with the complement of the input graph) + cout << "Clique Algorithm." << endl; + int n, i, j, k, K, p, q, r, s, min, edge, counter = 0; + infile >> n; + vector > graph; + for (i = 0; i < n; i++) + { + vector row; + for (j = 0; j < n; j++) + { + infile >> edge; + if (edge == 0) + row.push_back(1); + else + row.push_back(0); + } + graph.push_back(row); + } + //Find Neighbors + vector > neighbors; + for (i = 0; i < graph.size(); i++) + { + vector neighbor; + for (j = 0; j < graph[i].size(); j++) + if (graph[i][j] == 1) + neighbor.push_back(j); + neighbors.push_back(neighbor); + } + cout << "Graph has n = " << n << " vertices." << endl; + //Read maximum size of Clique wanted + cout << "Find a Clique of size at least k = "; + cin >> K; + k = n - K; + //Find Cliques + bool found = false; + cout << "Finding Cliques..." << endl; + min = n + 1; + vector > covers; + vector allcover; + for (i = 0; i < graph.size(); i++) + allcover.push_back(1); + for (i = 0; i < allcover.size(); i++) + { + if (found) + break; + counter++; + cout << counter << ". "; + outfile << counter << ". "; + vector cover = allcover; + cover[i] = 0; + cover = procedure_1(neighbors, cover); + s = cover_size(cover); + if (s < min) + min = s; + if (s <= k) + { + outfile << "Clique (" << n - s << "): "; + for (j = 0; j < cover.size(); j++) + if (cover[j] == 0) + outfile << j + 1 << " "; + outfile << endl; + cout << "Clique Size: " << n - s << endl; + covers.push_back(cover); + found = true; + break; + } + for (j = 0; j < n - k; j++) + cover = procedure_2(neighbors, cover, j); + s = cover_size(cover); + if (s < min) + min = s; + outfile << "Clique (" << n - s << "): "; + for (j = 0; j < cover.size(); j++) + if (cover[j] == 0) + outfile << j + 1 << " "; + outfile << endl; + cout << "Clique Size: " << n - s << endl; + covers.push_back(cover); + if (s <= k) + { + found = true; + break; + } + } + //Pairwise Intersections + for (p = 0; p < covers.size(); p++) + { + if (found) + break; + for (q = p + 1; q < covers.size(); q++) + { + if (found) + break; + counter++; + cout << counter << ". "; + outfile << counter << ". "; + vector cover = allcover; + for (r = 0; r < cover.size(); r++) + if (covers[p][r] == 0 && covers[q][r] == 0) + cover[r] = 0; + cover = procedure_1(neighbors, cover); + s = cover_size(cover); + if (s < min) + min = s; + if (s <= k) + { + outfile << "Clique (" << n - s << "): "; + for (j = 0; j < cover.size(); j++) + if (cover[j] == 0) + outfile << j + 1 << " "; + outfile << endl; + cout << "Clique Size: " << n - s << endl; + found = true; + break; + } + for (j = 0; j < k; j++) + cover = procedure_2(neighbors, cover, j); + s = cover_size(cover); + if (s < min) + min = s; + outfile << "Clique (" << n - s << "): "; + for (j = 0; j < cover.size(); j++) + if (cover[j] == 0) + outfile << j + 1 << " "; + outfile << endl; + cout << "Clique Size: " << n - s << endl; + if (s <= k) + { + found = true; + break; + } + } + } + if (found) + cout << "Found Clique of size at least " << K << "." << endl; + else + cout << "Could not find Clique of size at least " << K << "." << endl + << "Maximum Clique size found is " << n - min << "." << endl; + cout << "See cliques.txt for results." << endl; + return 0; +} + +bool removable(vector neighbor, vector cover) +{ + bool check = true; + for (int i = 0; i < neighbor.size(); i++) + if (cover[neighbor[i]] == 0) + { + check = false; + break; + } + return check; +} + +int max_removable(vector > neighbors, vector cover) +{ + int r = -1, max = -1; + for (int i = 0; i < cover.size(); i++) + { + if (cover[i] == 1 && removable(neighbors[i], cover) == true) + { + vector temp_cover = cover; + temp_cover[i] = 0; + int sum = 0; + for (int j = 0; j < temp_cover.size(); j++) + if (temp_cover[j] == 1 && removable(neighbors[j], temp_cover) + == true) + sum++; + if (sum > max) + { + max = sum; + r = i; + } + } + } + return r; +} + +vector procedure_1(vector > neighbors, vector cover) +{ + vector temp_cover = cover; + int r = 0; + while (r != -1) + { + r = max_removable(neighbors, temp_cover); + if (r != -1) + temp_cover[r] = 0; + } + return temp_cover; +} + +vector procedure_2(vector > neighbors, vector cover, + int k) +{ + int count = 0; + vector temp_cover = cover; + int i = 0; + for (int i = 0; i < temp_cover.size(); i++) + { + if (temp_cover[i] == 1) + { + int sum = 0, index; + for (int j = 0; j < neighbors[i].size(); j++) + if (temp_cover[neighbors[i][j]] == 0) + { + index = j; + sum++; + } + if (sum == 1 && cover[neighbors[i][index]] == 0) + { + temp_cover[neighbors[i][index]] = 1; + temp_cover[i] = 0; + temp_cover = procedure_1(neighbors, temp_cover); + count++; + } + if (count > k) + break; + } + } + return temp_cover; +} + +int cover_size(vector cover) +{ + int count = 0; + for (int i = 0; i < cover.size(); i++) + if (cover[i] == 1) + count++; + return count; +} + +/* + +graph.txt: +4 +0 1 1 1 +1 0 1 1 +1 1 0 1 +1 1 1 0 + +cliques.txt: +Clique ( 4 ): 1 2 3 4 \ No newline at end of file diff --git a/c++/Hard_Graph_Problems/C++ Program to Find the Longest Path in a DAG.cpp b/c++/Hard_Graph_Problems/C++ Program to Find the Longest Path in a DAG.cpp new file mode 100644 index 0000000..7fd28b6 --- /dev/null +++ b/c++/Hard_Graph_Problems/C++ Program to Find the Longest Path in a DAG.cpp @@ -0,0 +1,155 @@ +/*This is a C++ Program to find longest path in DAG. Given a Weighted Directed Acyclic Graph (DAG) and a source vertex s in it, find the longest distances from s to all other vertices in the given graph. Following is complete algorithm for finding longest distances. +1) Initialize dist[] = {NINF, NINF, ….} and dist[s] = 0 where s is the source vertex. Here NINF means negative infinite. +2) Create a toplogical order of all vertices. +3) Do following for every vertex u in topological order. +………..Do following for every adjacent vertex v of u +………………if (dist[v] < dist[u] + weight(u, v)) ………………………dist[v] = dist[u] + weight(u, v) */ + +// A C++ program to find single source longest distances in a DAG +#include +#include +#include +#include +#define NINF INT_MIN +using namespace std; + +// Graph is represented using adjacency list. Every node of adjacency list +// contains vertex number of the vertex to which edge connects. It also +// contains weight of the edge +class AdjListNode +{ + int v; + int weight; +public: + AdjListNode(int _v, int _w) + { + v = _v; + weight = _w; + } + int getV() + { + return v; + } + int getWeight() + { + return weight; + } +}; + +// Class to represent a graph using adjacency list representation +class Graph +{ + int V; // No. of vertices’ + + // Pointer to an array containing adjacency lists + list *adj; + + // A function used by longestPath + void topologicalSortUtil(int v, bool visited[], stack &Stack); +public: + Graph(int V); // Constructor + + // function to add an edge to graph + void addEdge(int u, int v, int weight); + + // Finds longest distances from given source vertex + void longestPath(int s); +}; + +Graph::Graph(int V) // Constructor +{ + this->V = V; + adj = new list [V]; +} + +void Graph::addEdge(int u, int v, int weight) +{ + AdjListNode node(v, weight); + adj[u].push_back(node); // Add v to u’s list +} + +// A recursive function used by longestPath. See below link for details +// http://www.geeksforgeeks.org/topological-sorting/ +void Graph::topologicalSortUtil(int v, bool visited[], stack &Stack) +{ + // Mark the current node as visited + visited[v] = true; + // Recur for all the vertices adjacent to this vertex + list::iterator i; + for (i = adj[v].begin(); i != adj[v].end(); ++i) + { + AdjListNode node = *i; + if (!visited[node.getV()]) + topologicalSortUtil(node.getV(), visited, Stack); + } + // Push current vertex to stack which stores topological sort + Stack.push(v); +} + +// The function to find longest distances from a given vertex. It uses +// recursive topologicalSortUtil() to get topological sorting. +void Graph::longestPath(int s) +{ + stack Stack; + int dist[V]; + // Mark all the vertices as not visited + bool *visited = new bool[V]; + for (int i = 0; i < V; i++) + visited[i] = false; + // Call the recursive helper function to store Topological Sort + // starting from all vertices one by one + for (int i = 0; i < V; i++) + if (visited[i] == false) + topologicalSortUtil(i, visited, Stack); + // Initialize distances to all vertices as infinite and distance + // to source as 0 + for (int i = 0; i < V; i++) + dist[i] = NINF; + dist[s] = 0; + // Process vertices in topological order + while (Stack.empty() == false) + { + // Get the next vertex from topological order + int u = Stack.top(); + Stack.pop(); + // Update distances of all adjacent vertices + list::iterator i; + if (dist[u] != NINF) + { + for (i = adj[u].begin(); i != adj[u].end(); ++i) + if (dist[i->getV()] < dist[u] + i->getWeight()) + dist[i->getV()] = dist[u] + i->getWeight(); + } + } + // Print the calculated longest distances + for (int i = 0; i < V; i++) + (dist[i] == NINF) ? cout << "INF " : cout << dist[i] << " "; +} + +// Driver program to test above functions +int main() +{ + // Create a graph given in the above diagram. Here vertex numbers are + // 0, 1, 2, 3, 4, 5 with following mappings: + // 0=r, 1=s, 2=t, 3=x, 4=y, 5=z + Graph g(6); + g.addEdge(0, 1, 5); + g.addEdge(0, 2, 3); + g.addEdge(1, 3, 6); + g.addEdge(1, 2, 2); + g.addEdge(2, 4, 4); + g.addEdge(2, 5, 2); + g.addEdge(2, 3, 7); + g.addEdge(3, 5, 1); + g.addEdge(3, 4, -1); + g.addEdge(4, 5, -2); + int s = 1; + cout << "Following are longest distances from source vertex " << s << " \n"; + g.longestPath(s); + return 0; +} + +/* + +Following are longest distances from source vertex 1 +INF 0 2 9 8 10 \ No newline at end of file diff --git a/c++/Hard_Graph_Problems/C++ Program to Find the Maximum Size Clique in a Graph.cpp b/c++/Hard_Graph_Problems/C++ Program to Find the Maximum Size Clique in a Graph.cpp new file mode 100644 index 0000000..fca9cab --- /dev/null +++ b/c++/Hard_Graph_Problems/C++ Program to Find the Maximum Size Clique in a Graph.cpp @@ -0,0 +1,261 @@ +/*This is a C++ Program to find the cliques of size k in a a graph. An undirected graph is formed by a finite set of vertices and a set of unordered pairs of vertices, which are called edges. By convention, in algorithm analysis, the number of vertices in the graph is denoted by n and the number of edges is denoted by m. A clique in a graph G is a complete subgraph of G; that is, it is a subset S of the vertices such that every two vertices in S are connected by an edge in G. A maximal clique is a clique to which no more vertices can be added; a maximum clique is a clique that includes the largest possible number of vertices, and the clique number ?(G) is the number of vertices in a maximum clique of G.*/ + +#include +#include +#include +#include +using namespace std; + +bool removable(vector neighbor, vector cover); +int max_removable(vector > neighbors, vector cover); +vector procedure_1(vector > neighbors, vector cover); +vector procedure_2(vector > neighbors, vector cover, + int k); +int cover_size(vector cover); +ifstream infile("graph.txt"); +ofstream outfile("cliques.txt"); + +int main() +{ + //Read Graph (note we work with the complement of the input graph) + cout << "Clique Algorithm." << endl; + int n, i, j, k, K, p, q, r, s, min, edge, counter = 0; + infile >> n; + vector > graph; + for (i = 0; i < n; i++) + { + vector row; + for (j = 0; j < n; j++) + { + infile >> edge; + if (edge == 0) + row.push_back(1); + else + row.push_back(0); + } + graph.push_back(row); + } + //Find Neighbors + vector > neighbors; + for (i = 0; i < graph.size(); i++) + { + vector neighbor; + for (j = 0; j < graph[i].size(); j++) + if (graph[i][j] == 1) + neighbor.push_back(j); + neighbors.push_back(neighbor); + } + cout << "Graph has n = " << n << " vertices." << endl; + //Read maximum size of Clique wanted + cout << "Find a Clique of size at least k = "; + cin >> K; + k = n - K; + //Find Cliques + bool found = false; + cout << "Finding Cliques..." << endl; + min = n + 1; + vector > covers; + vector allcover; + for (i = 0; i < graph.size(); i++) + allcover.push_back(1); + for (i = 0; i < allcover.size(); i++) + { + if (found) + break; + counter++; + cout << counter << ". "; + outfile << counter << ". "; + vector cover = allcover; + cover[i] = 0; + cover = procedure_1(neighbors, cover); + s = cover_size(cover); + if (s < min) + min = s; + if (s <= k) + { + outfile << "Clique (" << n - s << "): "; + for (j = 0; j < cover.size(); j++) + if (cover[j] == 0) + outfile << j + 1 << " "; + outfile << endl; + cout << "Clique Size: " << n - s << endl; + covers.push_back(cover); + found = true; + break; + } + for (j = 0; j < n - k; j++) + cover = procedure_2(neighbors, cover, j); + s = cover_size(cover); + if (s < min) + min = s; + outfile << "Clique (" << n - s << "): "; + for (j = 0; j < cover.size(); j++) + if (cover[j] == 0) + outfile << j + 1 << " "; + outfile << endl; + cout << "Clique Size: " << n - s << endl; + covers.push_back(cover); + if (s <= k) + { + found = true; + break; + } + } + //Pairwise Intersections + for (p = 0; p < covers.size(); p++) + { + if (found) + break; + for (q = p + 1; q < covers.size(); q++) + { + if (found) + break; + counter++; + cout << counter << ". "; + outfile << counter << ". "; + vector cover = allcover; + for (r = 0; r < cover.size(); r++) + if (covers[p][r] == 0 && covers[q][r] == 0) + cover[r] = 0; + cover = procedure_1(neighbors, cover); + s = cover_size(cover); + if (s < min) + min = s; + if (s <= k) + { + outfile << "Clique (" << n - s << "): "; + for (j = 0; j < cover.size(); j++) + if (cover[j] == 0) + outfile << j + 1 << " "; + outfile << endl; + cout << "Clique Size: " << n - s << endl; + found = true; + break; + } + for (j = 0; j < k; j++) + cover = procedure_2(neighbors, cover, j); + s = cover_size(cover); + if (s < min) + min = s; + outfile << "Clique (" << n - s << "): "; + for (j = 0; j < cover.size(); j++) + if (cover[j] == 0) + outfile << j + 1 << " "; + outfile << endl; + cout << "Clique Size: " << n - s << endl; + if (s <= k) + { + found = true; + break; + } + } + } + if (found) + cout << "Found Clique of size at least " << K << "." << endl; + else + cout << "Could not find Clique of size at least " << K << "." << endl + << "Maximum Clique size found is " << n - min << "." << endl; + cout << "See cliques.txt for results." << endl; + return 0; +} + +bool removable(vector neighbor, vector cover) +{ + bool check = true; + for (int i = 0; i < neighbor.size(); i++) + if (cover[neighbor[i]] == 0) + { + check = false; + break; + } + return check; +} + +int max_removable(vector > neighbors, vector cover) +{ + int r = -1, max = -1; + for (int i = 0; i < cover.size(); i++) + { + if (cover[i] == 1 && removable(neighbors[i], cover) == true) + { + vector temp_cover = cover; + temp_cover[i] = 0; + int sum = 0; + for (int j = 0; j < temp_cover.size(); j++) + if (temp_cover[j] == 1 && removable(neighbors[j], temp_cover) + == true) + sum++; + if (sum > max) + { + max = sum; + r = i; + } + } + } + return r; +} + +vector procedure_1(vector > neighbors, vector cover) +{ + vector temp_cover = cover; + int r = 0; + while (r != -1) + { + r = max_removable(neighbors, temp_cover); + if (r != -1) + temp_cover[r] = 0; + } + return temp_cover; +} + +vector procedure_2(vector > neighbors, vector cover, + int k) +{ + int count = 0; + vector temp_cover = cover; + int i = 0; + for (int i = 0; i < temp_cover.size(); i++) + { + if (temp_cover[i] == 1) + { + int sum = 0, index; + for (int j = 0; j < neighbors[i].size(); j++) + if (temp_cover[neighbors[i][j]] == 0) + { + index = j; + sum++; + } + if (sum == 1 && cover[neighbors[i][index]] == 0) + { + temp_cover[neighbors[i][index]] = 1; + temp_cover[i] = 0; + temp_cover = procedure_1(neighbors, temp_cover); + count++; + } + if (count > k) + break; + } + } + return temp_cover; +} + +int cover_size(vector cover) +{ + int count = 0; + for (int i = 0; i < cover.size(); i++) + if (cover[i] == 1) + count++; + return count; +} + +/* + +graph.txt: +4 +0 1 1 1 +1 0 1 1 +1 1 0 1 +1 1 1 0 + +cliques.txt: +Clique ( 4 ): 1 2 3 4 \ No newline at end of file diff --git a/c++/Hard_Graph_Problems/C++ Program to Implement Nearest Neighbour Algorithm.cpp b/c++/Hard_Graph_Problems/C++ Program to Implement Nearest Neighbour Algorithm.cpp new file mode 100644 index 0000000..57fd280 --- /dev/null +++ b/c++/Hard_Graph_Problems/C++ Program to Implement Nearest Neighbour Algorithm.cpp @@ -0,0 +1,61 @@ +/*This is a C++ Program to implement nearest neighbour algorithm to solve TSP. This C++ program implements the Travelling Salesman Problem which computes the minimum cost required to visit all the nodes by traversing across the edges only once.*/ + +#include +#include +#include + +using namespace std; + +int c = 0, cost = 999; +int graph[4][4] = { { 0, 10, 15, 20 }, { 10, 0, 35, 25 }, { 15, 35, 0, 30 }, { + 20, 25, 30, 0 + } +}; + +void swap(int *x, int *y) +{ + int temp; + temp = *x; + *x = *y; + *y = temp; +} +void copy_array(int *a, int n) +{ + int i, sum = 0; + for (i = 0; i <= n; i++) + { + sum += graph[a[i % 4]][a[(i + 1) % 4]]; + } + if (cost > sum) + { + cost = sum; + } +} +void permute(int *a, int i, int n) +{ + int j, k; + if (i == n) + { + copy_array(a, n); + } + else + { + for (j = i; j <= n; j++) + { + swap((a + i), (a + j)); + permute(a, i + 1, n); + swap((a + i), (a + j)); + } + } +} +int main() +{ + int i, j; + int a[] = { 0, 1, 2, 3 }; + permute(a, 0, 3); + cout << "minimum cost:" << cost << endl; +} + +/* + +minimum cost:80 \ No newline at end of file diff --git a/c++/Hard_Graph_Problems/C++ Program to Implement Traveling Salesman Problem using Nearest neighbour Algorithm.cpp b/c++/Hard_Graph_Problems/C++ Program to Implement Traveling Salesman Problem using Nearest neighbour Algorithm.cpp new file mode 100644 index 0000000..7b7c0fc --- /dev/null +++ b/c++/Hard_Graph_Problems/C++ Program to Implement Traveling Salesman Problem using Nearest neighbour Algorithm.cpp @@ -0,0 +1,60 @@ +/* +* C++ Program to Implement Traveling Salesman Problem using Nearest neighbour Algorithm + */ +#include +#include +#include +using namespace std; +int c = 0,cost = 999; +int graph[4][4] = { {0, 10, 15, 20}, + {10, 0, 35, 25}, + {15, 35, 0, 30}, + {20, 25, 30, 0} +}; +void swap (int *x, int *y) +{ + int temp; + temp = *x; + *x = *y; + *y = temp; +} +void copy_array(int *a, int n) +{ + int i, sum = 0; + for(i = 0; i <= n; i++) + { + sum += graph[a[i % 4]][a[(i + 1) % 4]]; + } + if (cost > sum) + { + cost = sum; + } +} +void permute(int *a, int i, int n) +{ + int j, k; + if (i == n) + { + copy_array(a, n); + } + else + { + for (j = i; j <= n; j++) + { + swap((a + i), (a + j)); + permute(a, i + 1, n); + swap((a + i), (a + j)); + } + } +} +int main() +{ + int i, j; + int a[] = {0, 1, 2, 3}; + permute(a, 0, 3); + cout<<"minimum cost:"< + # include + # include + + + + class Matrix + { + private: + float matrix_a[3][3]; + float matrix_b[3][3]; + float matrix_c[3][3]; + + public: + Matrix( ); + + void get_matrix_a( ); + void get_matrix_b( ); + void multiply_matrices( ); + void show_result_Matrix( ); + }; + + + + + Matrix::Matrix( ) + { + for(int i=0;i<3;i++) + { + for(int j=0;j<3;j++) + { + matrix_a[i][j]=0; + matrix_b[i][j]=0; + matrix_c[i][j]=0; + } + } + + gotoxy(1,1); + cout<<" +************************************************************************** +****"< + # include + + + //------------------------ Function +rototypes ------------------------// + + + + const long fibonacci(const int); + + + //----------------------------- +main( ) -------------------------------// + + + + int main() + { + clrscr( ); + + int number; + + cout<<" + Enter the number ( 1 - 25 ) = "; + cin>>number; + + number=((number>25)?25:number); + + cout<<" + + The "< +using namespace std; +void line(), message(); +int main() +{ + cout << "The program starts in main()." << endl; + line(); + message(); + line(); + cout << "At the end of main()." << endl; + return 0; +} +void line() +{ + cout << "line();" << endl; +} +void message() +{ + cout << "In function message()." << endl; +} diff --git a/c++/Others/A Class as a Member Variable of Another Class.cpp b/c++/Others/A Class as a Member Variable of Another Class.cpp new file mode 100644 index 0000000..74efb83 --- /dev/null +++ b/c++/Others/A Class as a Member Variable of Another Class.cpp @@ -0,0 +1,178 @@ +A Class as a Member Variable of Another Class +This is an example of one object (the shape class implements a rectangle) being a member variable of another object (a brick). + +Header File: shape.h + +#ifndef _SHAPE_H +#define _SHAPE_H + +class FRectangle +{ +public: + FRectangle(double l = 0, double w = 0) + : Length(l), Width(w) {} + void setLength(double lgt); + void setWidth(double wdt); + double getLength() const; + double getWidth() const; + double Perimeter() const; + double Area() const; + void Properties(); +private: + double Length; + double Width; +}; + +#endif // _SHAPE_H + +Source File: shape.cpp + +#include +#include "shape.h" + +void FRectangle::setLength(double lgt) +{ + Length = lgt; +} + +void FRectangle::setWidth(double wdt) +{ + Width = wdt; +} + +double FRectangle::getLength() const +{ + return Length; +} + +double FRectangle::getWidth() const +{ + return Width; +} + +double FRectangle::Perimeter() const +{ + return 2 * (Length + Width); +} + +double FRectangle::Area() const +{ + return Length * Width; +} + +void FRectangle::Properties() +{ + cout << "\nRectangle characteristics"; + cout << "\n\tLength = " << Length; + cout << "\n\tWidth = " << Width; + cout << "\n\tPerimeter = " << Perimeter(); + cout << "\n\tArea = " << Area() << endl; +} + +Header File: brick.h + +#ifndef BRICK_H_ +#define BRICK_H_ + +#include "shape.h" + +class Brick +{ +public: + Brick() {} + void setThickness(double Tck); + void setDimensions(double l, double w, double t); + void setColor(char* clr); + void setTexture(char* txr); + char* getColor() const; + char* getTexture() const; + double Volume() const; + void Display(); +private: + FRectangle shape; + char* Color; + char* Texture; + double Thickness; +}; + +#endif // BRICK_H_ + +Source File: brick.cpp + +#include +#include "brick.h" + +void Brick::setThickness(double Tck) +{ + Thickness = Tck; +} + +void Brick::setColor(char* clr) +{ + Color = clr; +} + +void Brick::setTexture(char* txr) +{ + Texture = txr; +} + +void Brick::setDimensions(double l, double w, double t) +{ + shape.setLength(l); + shape.setWidth(w); + setThickness(t); +} + +char* Brick::getColor() const +{ + return Color; +} + +char* Brick::getTexture() const +{ + return Texture; +} + +double Brick::Volume() const +{ + return shape.getLength() * shape.getWidth() * Thickness; +} + +void Brick::Display() +{ + cout << "\nBrick characteristics"; + cout << "\n\tLength = " << shape.getLength(); + cout << "\n\tWidth = " << shape.getWidth(); + cout << "\n\tArea = " << shape.Area(); + cout << "\n\tVolume = " << Volume(); + cout << "\n\tColor = " << getColor(); + cout << "\n\tTextture = " << getTexture(); + cout << endl; +} + +Main File: Exo.cpp + +#include "shape.h" +#include "brick.h" + +void main() +{ + Brick brick; + + brick.setDimensions(12.50, 8.75, 5.55); + brick.setColor("Bone White"); + brick.setTexture("Early Breeze"); + + brick.Display(); +} + +Here is an example of running the program: + +Brick characteristics + Length = 12.5 + Width = 8.75 + Area = 109.375 + Volume = 607.031 + Color = Bone White + Textture = Early Breeze diff --git a/c++/Others/A Closer Look at the IO Operators.cpp b/c++/Others/A Closer Look at the IO Operators.cpp new file mode 100644 index 0000000..8fcb91d --- /dev/null +++ b/c++/Others/A Closer Look at the IO Operators.cpp @@ -0,0 +1,26 @@ +A Closer Look at the I/O Operators +#include + +using namespace std; + +int main() +{ + + float f; + + char str[80]; + + double d; + + cout << "Enter two floating point numbers: "; + + cin >> f >> d; + + cout << "Enter a string: "; + + cin >> str; + + cout << f << " " << d << " " << str; + + return 0; +} diff --git a/c++/Others/A Simple for Statement - generate the square root of 1 to 10.cpp b/c++/Others/A Simple for Statement - generate the square root of 1 to 10.cpp new file mode 100644 index 0000000..c9df834 --- /dev/null +++ b/c++/Others/A Simple for Statement - generate the square root of 1 to 10.cpp @@ -0,0 +1,19 @@ +A Simple for Statement - generate the square root of 1 to 10 + +#include +#include // for newer compilers, use +using namespace std; + +int main() +{ + int num; + double sq_root; + + for(num=1; num < 10; num++) { + sq_root = sqrt((double) num); //casting num from integer to double + // then taking its square root + cout << num << " " << sq_root << '\n'; + } + + return 0; +} diff --git a/c++/Others/A Simple if Statement.cpp b/c++/Others/A Simple if Statement.cpp new file mode 100644 index 0000000..65bbff2 --- /dev/null +++ b/c++/Others/A Simple if Statement.cpp @@ -0,0 +1,22 @@ +A Simple if Statement +This program illustrates a simple if statement. +It reads in two integers and prints out a +message on the screen according to their values. + +#include +using namespace std; + +int main() +{ + int a, b; + + cout << "Enter first number: "; + cin >> a; + cout << "Enter second number: "; + cin >> b; + + if(a < b) + cout << "First number is less than second.\n"; + + return 0; +} diff --git a/c++/Others/A Simple program finding the absolute value of an integer.cpp b/c++/Others/A Simple program finding the absolute value of an integer.cpp new file mode 100644 index 0000000..520262b --- /dev/null +++ b/c++/Others/A Simple program finding the absolute value of an integer.cpp @@ -0,0 +1,60 @@ +A Simple program finding the absolute value of an integer +A Simple program without using functions + +This program find the absolute value of an integer without using a function + +#include +using namespace std; + +int main() +{ + int number; + int abs_number; + + // Ask for input + cout << "This program finds the absolute value of an integer." << endl; + cout << "Enter an integer (positive or negative): "; + cin >> number; + + // Find the absolute value + if(number >= 0) + { + abs_number = number; + } + else + abs_number = -number; + + // Print out output + cout << "The absolute value of " << number << " is " << abs_number; + cout << endl; + return 0; +} + +The same program using function + +This program finds the absolute value of an integer using a function + +int Abs(int i); // Function prototype +int main() +{ + int number; + int abs_number; + + cout << "This program finds the absolute value of an integer." << endl; + cout << "Enter an integer (positive or negative): "; + cin >> number; + + // Calling the function Abs() + abs_number = Abs(number); + cout << "The absolute value of " << number << " is " << abs_number; + cout << endl; + return 0; +} +// Function definition +int Abs(int i) +{ + if( i >= 0) + return i; + else + return -i; +} diff --git a/c++/Others/A base pointer to access derived objects.cpp b/c++/Others/A base pointer to access derived objects.cpp new file mode 100644 index 0000000..990b839 --- /dev/null +++ b/c++/Others/A base pointer to access derived objects.cpp @@ -0,0 +1,34 @@ +A base pointer to access derived objects +#include +using namespace std; +class BaseClass { + int i; +public: + void setInt(int num) { + i = num; + } + int getInt() { + return i; + } +}; +class derived: public BaseClass { + int j; +public: + void setJ(int num) { + j = num; + } + int getJ() { + return j; + } +}; +int main() +{ + BaseClass *baseClassPointer; + derived d; + baseClassPointer = &d; // BaseClass pointer points to derived object + // access derived object using BaseClass pointer + baseClassPointer->setInt(10); + cout << baseClassPointer->getInt() << " "; + + return 0; +} diff --git a/c++/Others/A classical stack operation using a string of char.cpp b/c++/Others/A classical stack operation using a string of char.cpp new file mode 100644 index 0000000..4dcb61f --- /dev/null +++ b/c++/Others/A classical stack operation using a string of char.cpp @@ -0,0 +1,63 @@ +A classical stack operation using a string of characters. +#include +#include +using namespace std; +#define maxlen 80 + +class stack { + char str1[maxlen]; + int first; +public: + void clear(void); + char top(void); + int empty(void); + int full(void); + void push(char chr); + char pop(void); +}; + +void stack::clear(void) +{ + first=0; +} + char stack::top(void) +{ + return (str1[first]); +} + +int stack::empty(void) +{ + return (first==0); +} + +int stack::full(void) +{ + return (first==maxlen-1); +} + +void stack::push(char chr) +{ + str1[++first]=chr; +} +char stack::pop(void) +{ + return (str1[first-1]); +} + +main( ) +{ + stack mystack; + char str[11]="0123456789"; + + mystack.clear( ); + + for(int i=0; (int) i +#include +using namespace std; +#define maxlen 80 + +class stack { + char str1[maxlen]; + int first; +public: + void clear(void); + char top(void); + int empty(void); + int full(void); + void push(char chr); + char pop(void); +}; + +void stack::clear(void) +{ + first=0; +} + char stack::top(void) +{ + return (str1[first]); +} + +int stack::empty(void) +{ + return (first==0); +} + +int stack::full(void) +{ + return (first==maxlen-1); +} + +void stack::push(char chr) +{ + str1[++first]=chr; +} +char stack::pop(void) +{ + return (str1[first-1]); +} + +main( ) +{ + stack mystack; + char str[11]="0123456789"; + + mystack.clear( ); + + for(int i=0; (int) i +#include +#include +using namespace std; + +class StringClass { + char *p; +public: + StringClass(char *s); // constructor + StringClass(const StringClass &o); // copy constructor + ~StringClass() { // destructor + delete [] p; + } + char *get() { + return p; + } +}; + + +StringClass::StringClass(char *s) // "Normal" constructor +{ + int l; + + l = strlen(s)+1; + + p = new char [l]; + if(!p) { + cout << "Allocation error\n"; + exit(1); + } + + strcpy(p, s); +} + + +StringClass::StringClass(const StringClass &o) // Copy constructor +{ + int l; + + l = strlen(o.p)+1; + + p = new char [l]; // allocate memory for new copy + if(!p) { + cout << "Allocation error\n"; + exit(1); + } + + strcpy(p, o.p); // copy string into copy +} + +void show(StringClass x) +{ + char *s; + + s = x.get(); + cout << s << endl; +} + +int main() +{ + StringClass a("Hello World"), b("Hello World"); + + show(a); + show(b); + + return 0; +} diff --git a/c++/Others/A filter to remove white-space characters at the ends of lines..cpp b/c++/Others/A filter to remove white-space characters at the ends of lines..cpp new file mode 100644 index 0000000..acd9441 --- /dev/null +++ b/c++/Others/A filter to remove white-space characters at the ends of lines..cpp @@ -0,0 +1,24 @@ +A filter to remove white-space characters at the ends of lines. +#include +#include +using namespace std; +void cutline( void ); +string line; +int main() +{ + while( getline(cin, line)) { + cutline(); + cout << line << endl; + } + return 0; +} + +void cutline() +{ + int i = line.size(); + + while( i-- >= 0 ) + if( line[i] != ' ' && line[i] != '\t' ) + break; + line.resize(++i); +} diff --git a/c++/Others/A four-function postfix calculator..cpp b/c++/Others/A four-function postfix calculator..cpp new file mode 100644 index 0000000..9c644a0 --- /dev/null +++ b/c++/Others/A four-function postfix calculator..cpp @@ -0,0 +1,91 @@ +A four-function postfix calculator. +#include +#include +#include +#include +using namespace std; + +int main() +{ + stack stackObject; + double a, b; + string s; + + do { + cout << ": "; + cin >> s; + switch( s[ 0 ]) { + case 'q': // quit the calculator + break; + case '.': // show top-of-stack + cout << stackObject.top() << endl; + break; + case '+': // add + if(stackObject.size() < 2) { + cout << "Operand Missing\n"; + break; + } + + a = stackObject.top(); + stackObject.pop(); + b = stackObject.top(); + stackObject.pop(); + cout << a + b << endl; + stackObject.push(a + b); + break; + case '-': // subtract + // see if user entering a negative number + if(s.size() != 1) { + // push value onto the stack + stackObject.push(atof(s.c_str())); + break; + } + + // otherwise, is a subtraction + if(stackObject.size() < 2) { + cout << "Operand Missing\n"; + break; + } + + a = stackObject.top(); + stackObject.pop(); + b = stackObject.top(); + stackObject.pop(); + cout << b - a << endl; + stackObject.push(b - a); + break; + case '*': // multiply + if(stackObject.size() < 2) { + cout << "Operand Missing\n"; + break; + } + + a = stackObject.top(); + stackObject.pop(); + b = stackObject.top(); + stackObject.pop(); + cout << a*b << endl; + stackObject.push(a*b); + break; + case '/': // divide + if(stackObject.size() < 2) { + cout << "Operand Missing\n"; + break; + } + + a = stackObject.top(); + stackObject.pop(); + b = stackObject.top(); + stackObject.pop(); + cout << b/a << endl; + stackObject.push(b/a); + break; + default: + // push value onto the stack + stackObject.push(atof(s.c_str())); + break; + } + } while(s != "q"); + + return 0; +} diff --git a/c++/Others/A function object that computes an integer sum..cpp b/c++/Others/A function object that computes an integer sum..cpp new file mode 100644 index 0000000..863a3f7 --- /dev/null +++ b/c++/Others/A function object that computes an integer sum..cpp @@ -0,0 +1,34 @@ +A function object that computes an integer sum. +#include +#include +#include +#include +using namespace std; + +class sum : unary_function { +public: + argument_type sum; + + sum() { sum = 0; } + + result_type operator()(argument_type i) { + sum += i; + } +}; + +int main() +{ + vector v; + + for(int i=1; i < 11; i++) v.push_back(i); + + for(unsigned i=0; i < v.size(); ++i){ + cout << v[i] << endl; + } + sum s; + + s = for_each(v.begin(), v.end(), sum()); + cout << "sum of v: " << s.sum << endl; + + return 0; +} diff --git a/c++/Others/A generic bubble sort..cpp b/c++/Others/A generic bubble sort..cpp new file mode 100644 index 0000000..aace5f3 --- /dev/null +++ b/c++/Others/A generic bubble sort..cpp @@ -0,0 +1,38 @@ +A generic bubble sort. +#include +using namespace std; + + +template void bubble(X *data, int size) +{ + register int a, b; + X t; + + for(a=1; a < size; a++) + for(b=size-1; b >= a; b--) + if(data[b-1] > data[b]) { + t = data[b-1]; + data[b-1] = data[b]; + data[b] = t; + } +} + +int main() +{ + int i[] = {3, 2, 5, 6, 1, 8, 9, 3, 6, 9}; + double d[] = {1.2, 5.5, 2.2, 3.3}; + int j; + + bubble(i, 10); // sort ints + bubble(d, 4); // sort doubles + + for(j=0; j<10; j++) + cout << i[j] << ' '; + cout << endl; + + for(j=0; j<4; j++) + cout << d[j] << ' '; + cout << endl; + + return 0; +} diff --git a/c++/Others/A generic mode finding function..cpp b/c++/Others/A generic mode finding function..cpp new file mode 100644 index 0000000..d0eb958 --- /dev/null +++ b/c++/Others/A generic mode finding function..cpp @@ -0,0 +1,37 @@ +A generic mode finding function. +#include +#include +using namespace std; + + +template X mode(X *data, int size) +{ + register int t, w; + X md, oldmd; + int count, oldcount; + + oldmd = 0; + oldcount = 0; + for(t=0; t oldcount) { + oldmd = md; + oldcount = count; + } + } + return oldmd; +} + +int main() +{ + int i[] = { 1, 2, 3, 4, 2, 3, 2, 2, 1, 5}; + char *p = "this is a test"; + + cout << "mode of i: " << mode(i, 10) << endl; + cout << "mode of p: " << mode(p, (int) strlen(p)); + + return 0; +} diff --git a/c++/Others/A generic stack class.cpp b/c++/Others/A generic stack class.cpp new file mode 100644 index 0000000..8417579 --- /dev/null +++ b/c++/Others/A generic stack class.cpp @@ -0,0 +1,213 @@ +A generic stack class + +#include +#include +#include +#include + +using namespace std; + +#if !defined __STACK_H +#define __STACK_H + +namespace stk{ + template + class Stack; // Forward declaration of Stack class for overloaded << +operator + + template + ostream& operator<<(ostream &,Stack &); // template declaration of +<< +operator + + template + class Stack{ + private: + T *p; + int top,length; + + string str()const; + public: + Stack(); + Stack(const int); + Stack(const Stack&); + ~Stack(); + + void push(T); + T pop(); + int get_length()const; + bool is_empty()const; + Stack operator=(const Stack&); + + // only for basic types + friend ostream& operator<< <>(ostream&,Stack &); + + class StackException{ + private: + string desc; + public: + StackException(string exp){ desc="Exception : "+exp; } + string get_exp(){ return desc; } + }; + }; + + template + Stack::Stack(){ + top=-1; + length=0; + p=0; + } + + template + Stack::Stack(const int size){ + top=-1; + length=size; + try{ + p=new T[length]; + }catch(bad_alloc ba){ + cout<<"Memory can not be alllocated +"; + return; + } + } + + template + Stack::Stack(const Stack &o){ + top=o.top; + length=o.length; + try{ + p=new T[length]; + }catch(bad_alloc ba){ + cout<<"Memory allocation failed +"; + return; + } + for(int i=0;i + Stack::~Stack(){ + if(p!=0) + delete [] p; + } + + template + void Stack::push(T elem){ + if(p==0){ + try{ + p=new T[1]; + }catch(bad_alloc ba){ + throw StackException("Memory fault +"); + } + length++; + top++; + p[top]=elem; + } + else if(top==(length-1)){ + T *q; + try{ + q=new T[length+1]; + }catch(bad_alloc ba1){ + throw StackException("Memory fault +"); + } + for(int i=0;i + T Stack::pop(){ + if(p==0 || top==-1){ + throw StackException("Stack empty! +"); + } + T ret=p[top]; + top--; + length--; + + if(top==-1){ + delete [] p; + p=0; + } + else{ + T *q; + try{ + q=new T[length]; + }catch(bad_alloc ba){ + throw StackException("Memory fault +"); + } + for(int i=0;i + int Stack::get_length()const{ + return length; + } + + template + bool Stack::is_empty()const{ + return ((p==0)? true : false); + } + + template + string Stack::str()const{ // private member function + if(p==0) + return string(""); + stringstream ss; + for(int i=0;i + Stack Stack::operator=(const Stack &stk){ + length=stk.length; + top=stk.top; + + if(p!=0) + delete [] p; + try{ + p=new T[length]; + }catch(bad_alloc ba){ + throw StackException("Memory fault in copying! +"); + } + for(int i=0;i + ostream& operator<<(ostream &o,Stack &s){ + o< +using namespace std; + +#define SIZE 10 + +template class stack { + StackType stck[SIZE][2]; + int topOfStack; + +public: + void init() { topOfStack = 0; } + void push(StackType ob, StackType object2); + StackType pop(StackType &object2); +}; + +template +void stack::push(StackType ob, StackType object2) +{ + if(topOfStack==SIZE) { + cout << "Stack is full.\n"; + return; + } + stck[topOfStack][0] = ob; + stck[topOfStack][1] = object2; + topOfStack++; +} + +template +StackType stack::pop(StackType &object2) +{ + if(topOfStack==0) { + cout << "Stack is empty.\n"; + return 0; + } + topOfStack--; + object2 = stck[topOfStack][1]; + return stck[topOfStack][0]; +} + +int main() +{ + stack stack1, stackObject2; + int i; + char ch; + + stack1.init(); + stackObject2.init(); + + stack1.push('a', 'b'); + stackObject2.push('x', 'z'); + stack1.push('b', 'd'); + stackObject2.push('y', 'e'); + stack1.push('c', 'a'); + stackObject2.push('z', 'x'); + + for(i = 0; i <3; i++) { + cout << "Pop stack1: " << stack1.pop(ch); + cout << ' ' << ch << endl; + } + for(i = 0; i <3; i++) { + cout << "Pop stackObject2: " << stackObject2.pop(ch); + cout << ' ' << ch << endl; + } + + // demonstrate double stacks + stack doubleValueStack1, doubleValueStack2; // create two stacks + double d; + + doubleValueStack1.init(); + doubleValueStack2.init(); + + doubleValueStack1.push(1.1, 2.0); + doubleValueStack2.push(2.2, 3.0); + doubleValueStack1.push(3.3, 4.0); + doubleValueStack2.push(4.4, 5.0); + doubleValueStack1.push(5.5, 6.0); + doubleValueStack2.push(6.6, 7.0); + + for(i = 0; i <3; i++) { + cout << "Pop doubleValueStack1: " << doubleValueStack1.pop(d); + cout << ' '<< d << endl; + } + + for(i = 0; i <3; i++) { + cout << "Pop doubleValueStack2: " << doubleValueStack2.pop(d); + cout << ' '<< d << endl; + } + + return 0; +} diff --git a/c++/Others/A generic stack that includes exception handling..cpp b/c++/Others/A generic stack that includes exception handling..cpp new file mode 100644 index 0000000..571a5eb --- /dev/null +++ b/c++/Others/A generic stack that includes exception handling..cpp @@ -0,0 +1,86 @@ +A generic stack that includes exception handling. +#include +using namespace std; + +#define SIZE 10 + +template class stack { + StackType stck[SIZE]; + int topOfStack; + +public: + void init() { + topOfStack = 0; + } + void push(StackType ch); + StackType pop(); +}; + +template +void stack::push(StackType ob) +{ + try { + if(topOfStack==SIZE) throw SIZE; + } catch(int) { + cout << "Stack is full.\n"; + return; + } + stck[topOfStack] = ob; + topOfStack++; +} + +template +StackType stack::pop() +{ + try { + if( topOfStack == 0) + throw 0; + } catch(int) { + cout << "Stack is empty.\n"; + return 0; + } + topOfStack--; + return stck[topOfStack]; +} + +int main() +{ + stack stack1, stack2; + int i; + + stack1.init(); + stack2.init(); + + stack1.push('a'); + stack2.push('x'); + stack1.push('b'); + stack2.push('y'); + stack1.push('c'); + stack2.push('z'); + + for(i = 0; i <3; i++) + cout << "Pop stack1: " << stack1.pop() << endl; + for(i = 0; i <4; i++) + cout << "Pop stack2: " << stack2.pop() << endl; + + // demonstrate double stacks + stack doubleValueStack1, doubleValueStack2; // create two stacks + + // initialize the stacks + doubleValueStack1.init(); + doubleValueStack2.init(); + + doubleValueStack1.push(1.1); + doubleValueStack2.push(2.2); + doubleValueStack1.push(3.3); + doubleValueStack2.push(4.4); + doubleValueStack1.push(5.5); + doubleValueStack2.push(6.6); + + for(i = 0; i <3; i++) + cout << "Pop doubleValueStack1: " << doubleValueStack1.pop() << endl; + for(i = 0; i <4; i++) + cout << "Pop doubleValueStack2: " << doubleValueStack2.pop() << endl; + + return 0; +} diff --git a/c++/Others/A generic version of myabs()..cpp b/c++/Others/A generic version of myabs()..cpp new file mode 100644 index 0000000..7250df8 --- /dev/null +++ b/c++/Others/A generic version of myabs()..cpp @@ -0,0 +1,21 @@ +A generic version of myabs(). +#include +using namespace std; + +template X myabs(X val) +{ + return val < 0 ? -val : val; +} + +int main() +{ + cout << myabs(-10) << '\n'; // integer abs + + cout << myabs(-10.0) << '\n'; // double abs + + cout << myabs(-10L) << '\n'; // long abs + + cout << myabs(-10.0F) << '\n'; // float abs + + return 0; +} diff --git a/c++/Others/A list splicing example..cpp b/c++/Others/A list splicing example..cpp new file mode 100644 index 0000000..ec8d752 --- /dev/null +++ b/c++/Others/A list splicing example..cpp @@ -0,0 +1,65 @@ +A list splicing example. +#include +#include +#include +#include +using namespace std; + +int main() +{ + list sentence; + list phrase; + list::iterator p; + + string s1[] = {"A", "B", ""}; + string s2[] = {"C", "D", ""}; + string s3[] = {"E", "F", "G.", ""}; + string s4[] = {"A", "C,", "E", "G", ""}; + int i; + + for(i = 0; s1[ i ] != ""; i++) + sentence.push_back(s1[i]); + + + for(i = 0; s2[ i ] != ""; i++) + phrase.push_back(s2[ i ]); + + cout << "Original sentence:\n"; + p = sentence.begin(); + while(p != sentence.end()) + cout << *p++ << " "; + cout << endl; + + sentence.splice(sentence.begin(), phrase); + + cout << "Sentence after splicing at the front:\n"; + p = sentence.begin(); + while(p != sentence.end()) + cout << *p++ << " "; + cout << endl; + + for(i = 0; s3[ i ] != ""; i++) + phrase.push_back(s3[ i ]); + + sentence.splice(sentence.end(), phrase); + + cout << "Sentence after splicing at the end:\n"; + p = sentence.begin(); + while(p != sentence.end()) + cout << *p++ << " "; + cout << endl; + + for(i = 0; s4[ i ] != ""; i++) + phrase.push_back(s4[ i ]); + + + p = find(sentence.begin(), sentence.end(), "or"); + sentence.splice(p, phrase); + + cout << "Sentence after splicing in the middle:\n"; + p = sentence.begin(); + while(p != sentence.end()) + cout << *p++ << " "; + + return 0; +} diff --git a/c++/Others/A map insert pair, find, end.cpp b/c++/Others/A map insert pair, find, end.cpp new file mode 100644 index 0000000..2e4ea34 --- /dev/null +++ b/c++/Others/A map insert pair, find, end.cpp @@ -0,0 +1,28 @@ +A map: insert pair, find, end +#include +#include +using namespace std; + +int main() +{ + map mapObject; + int i; + + for(i = 0; i <10; i++) { + mapObject.insert(pair('A'+i, i)); + } + + char ch; + cout << "Enter key: "; + cin >> ch; + + map::iterator p; + + p = mapObject.find(ch); + if(p != mapObject.end()) + cout << p->second; + else + cout << "Key not in map.\n"; + + return 0; +} diff --git a/c++/Others/A map of opposites..cpp b/c++/Others/A map of opposites..cpp new file mode 100644 index 0000000..ab2a622 --- /dev/null +++ b/c++/Others/A map of opposites..cpp @@ -0,0 +1,64 @@ +A map of opposites. +#include +#include +#include +using namespace std; + +class StringClass { + char str[20]; +public: + StringClass() { + strcpy(str, ""); + } + StringClass(char *s) { + strcpy(str, s); + } + char *get() { + return str; + } +}; + +// must define less than relative to StringClass objects +bool operator<(StringClass a, StringClass b) +{ + return strcmp(a.get(), b.get()) < 0; +} + +class opposite { + char str[20]; +public: + opposite() { + strcmp(str, ""); + } + opposite(char *s) { + strcpy(str, s); + } + char *get() { + return str; + } +}; + + +int main() +{ + map mapObject; + + mapObject.insert(pair(StringClass("yes"), opposite("no"))); + mapObject.insert(pair(StringClass("good"), opposite("bad"))); + mapObject.insert(pair(StringClass("left"), opposite("right"))); + mapObject.insert(pair(StringClass("up"), opposite("down"))); + + char str[80]; + cout << "Enter word: "; + cin >> str; + + map::iterator p; + + p = mapObject.find(StringClass(str)); + if(p != mapObject.end()) + cout << "Opposite: " << p->second.get(); + else + cout << "Word not in map.\n"; + + return 0; +} diff --git a/c++/Others/A map of word opposites, using strings..cpp b/c++/Others/A map of word opposites, using strings..cpp new file mode 100644 index 0000000..f1f5b8c --- /dev/null +++ b/c++/Others/A map of word opposites, using strings..cpp @@ -0,0 +1,30 @@ +A map of word opposites, using strings. +#include +#include +#include +using namespace std; + +int main() +{ + map mapObject; + int i; + + mapObject.insert(pair("yes", "no")); + mapObject.insert(pair("up", "down")); + mapObject.insert(pair("left", "right")); + mapObject.insert(pair("good", "bad")); + + string s; + cout << "Enter word: "; + cin >> s; + + map::iterator p; + + p = mapObject.find(s); + if(p != mapObject.end()) + cout << "Opposite: " << p->second; + else + cout << "Word not in map.\n"; + + return 0; +} diff --git a/c++/Others/A namespace can be nested within another.cpp b/c++/Others/A namespace can be nested within another.cpp new file mode 100644 index 0000000..35f718c --- /dev/null +++ b/c++/Others/A namespace can be nested within another.cpp @@ -0,0 +1,20 @@ +A namespace can be nested within another +#include +using namespace std; +namespace MyNameSpace1 { + int i; + namespace MyNameSpace2 { // a nested namespace + int j; + } +} +int main() +{ + MyNameSpace1::i = 19; + + MyNameSpace1::MyNameSpace2::j = 10; + cout << MyNameSpace1::i << " "<< MyNameSpace1::MyNameSpace2::j << "\n"; + + using namespace MyNameSpace1; + cout << i * MyNameSpace2::j; + return 0; +} diff --git a/c++/Others/A shared resource example..cpp b/c++/Others/A shared resource example..cpp new file mode 100644 index 0000000..de15cf6 --- /dev/null +++ b/c++/Others/A shared resource example..cpp @@ -0,0 +1,56 @@ +A shared resource example. +#include +#include +using namespace std; + +class output { + static char sharedResource[255]; // this is the shared resource + static int inuse; // buffer available if 0; in use otherwise + static int oindex; // index of sharedResource + char str[80]; + int i; // index of next char in str + int who; // identifies the object, must be > 0 +public: + output(int w, char *s) { + strcpy(str, s); + i = 0; + who = w; + } + + int putbuf() + { + if(!str[ i ]) { // done outputting + inuse = 0; // release buffer + return 0; // signal termination + } + if(!inuse) // get buffer + inuse = who; + if(inuse != who) // in use by someone else + return -1; + if(str[ i ]) { // still chars to output + sharedResource[oindex] = str[ i ]; + i++; oindex++; + sharedResource[oindex] = '\0';// always keep null-terminated + return 1; + } + return 0; + } + void show() { + cout << sharedResource << '\n'; + } +}; + +char output::sharedResource[255]; // this is the shared resource +int output::inuse = 0; // buffer available if 0; in use otherwise +int output::oindex = 0; // index of sharedResource + +int main() +{ + output object1(1, "This is a test"), object2(2, " of statics"); + + while(object1.putbuf() | object2.putbuf()) ; // output chars + + object1.show(); + + return 0; +} diff --git a/c++/Others/A short string demonstration..cpp b/c++/Others/A short string demonstration..cpp new file mode 100644 index 0000000..536270a --- /dev/null +++ b/c++/Others/A short string demonstration..cpp @@ -0,0 +1,38 @@ +A short string demonstration. +#include +#include +using namespace std; + +int main() +{ + string str1("A"); + string str2("B"); + string str3("O"); + string str4; + + str4 = str1; + cout << str1 << "\n" << str3 << "\n"; + + str4 = str1 + str2; + cout << str4 << "\n"; + + str4 = str1 + " to " + str3; + cout << str4 << "\n"; + + if(str3 > str1) + cout << "str3 > str1\n"; + if(str3 == str1+str2) + cout << "str3 == str1+str2\n"; + + str1 = "This is a null-terminated string.\n"; + cout << str1; + + string str5(str1); + cout << str5; + + cout << "Enter a string: "; + cin >> str5; + cout << str5; + + return 0; +} diff --git a/c++/Others/A simple bounded 2-d array example..cpp b/c++/Others/A simple bounded 2-d array example..cpp new file mode 100644 index 0000000..5aa9aea --- /dev/null +++ b/c++/Others/A simple bounded 2-d array example..cpp @@ -0,0 +1,60 @@ +A simple bounded 2-d array example. +#include +#include +using namespace std; + +class MyArray { + int isize, jsize; + int *p; +public: + MyArray(int i, int j); + int &put(int i, int j); + int get(int i, int j); +}; + +MyArray::MyArray(int i, int j) +{ + p = new int [i*j]; + if(!p) { + cout << "Allocation error\n"; + exit(1); + } + isize = i; + jsize = j; +} + +int &MyArray::put(int i, int j) +{ + if(i <0 || i>=isize || j<0 || j>=jsize) { + cout << "Bounds error!!!\n"; + exit(1); + } + return p[i*jsize + j]; +} + +int MyArray::get(int i, int j) +{ + if(i <0 || i>=isize || j<0 || j>=jsize) { + cout << "Bounds error!!!\n"; + exit(1); + } + return p[i*jsize +j]; +} + +int main() +{ + MyArray a(2, 3); + int i, j; + + for(i = 0; i <2; i++) + for(j=0; j<3; j++) + a.put(i, j) = i+j; + + for(i = 0; i <2; i++) + for(j=0; j<3; j++) + cout << a.get(i, j) << ' '; + + a.put(10, 10); + + return 0; +} diff --git a/c++/Others/A simple class called Point, with all necessary functions.cpp b/c++/Others/A simple class called Point, with all necessary functions.cpp new file mode 100644 index 0000000..c66410b --- /dev/null +++ b/c++/Others/A simple class called Point, with all necessary functions.cpp @@ -0,0 +1,60 @@ +A simple class called Point, with all necessary functions + +# include +# include +# include + +class point +{ + int x,y,z; +public: + point() + { + x=y=z=0; + } + point(int i,int j,int k) + { + x=i; + y=j; + z=k; + } + point(point &a) + { + x=a.x; + y=a.y; + z=a.z; + } + + negate() + { + x=-x; + y=-y; + z=-z; + } + void print() + { + cout<<"("< +using namespace std; + +class who { + char name; +public: + who(char c) { + name = c; + cout << "Constructing who"; + cout << name << endl; + } + ~who() { + cout << "Destructing who: " << name << endl; + } +}; + +who makewho() +{ + who temp('B'); + return temp; +} + +int main() +{ + who ob('A'); + + makewho(); + + return 0; +} diff --git a/c++/Others/A simple conversion function example..cpp b/c++/Others/A simple conversion function example..cpp new file mode 100644 index 0000000..2f5f9f3 --- /dev/null +++ b/c++/Others/A simple conversion function example..cpp @@ -0,0 +1,60 @@ +A simple class with member variable, constructor, destructor +#include +using namespace std; + +class who { + char name; +public: + who(char c) { + name = c; + cout << "Constructing who"; + cout << name << endl; + } + ~who() { + cout << "Destructing who: " << name << endl; + } +}; + +who makewho() +{ + who temp('B'); + return temp; +} + +int main() +{ + who ob('A'); + + makewho(); + + return 0; +} +A simple conversion function example. +#include +using namespace std; + +class MyClass { + int x, y; +public: + MyClass(int i, int j) { + x = i; + y = j; + } + operator int() { + return x*y; + } +}; + +int main() +{ + MyClass object1(2, 3), object2(4, 3); + int i; + + i = object1; // automatically convert to integer + cout << i << '\n'; + + i = 100 + object2; // convert object2 to integer + cout << i << '\n'; + + return 0; +} diff --git a/c++/Others/A simple example of inheritance..cpp b/c++/Others/A simple example of inheritance..cpp new file mode 100644 index 0000000..ef96642 --- /dev/null +++ b/c++/Others/A simple example of inheritance..cpp @@ -0,0 +1,49 @@ +A simple example of inheritance. +#include +using namespace std; + +class BaseClass { + int i; +public: + void setInt(int n); + int getInt(); +}; + +class DerivedClass : public BaseClass { + int j; +public: + void setJ(int n); + int mul(); +}; + +void BaseClass::setInt(int n) +{ + i = n; +} + +int BaseClass::getInt() +{ + return i; +} + +void DerivedClass::setJ(int n) +{ + j = n; +} + +int DerivedClass::mul() +{ + return j * getInt(); +} + +int main() +{ + DerivedClass ob; + + ob.setInt(10); // load i in BaseClass + ob.setJ(4); // load j in DerivedClass + + cout << ob.mul(); // displays 40 + + return 0; +} diff --git a/c++/Others/A simple example using a virtual function..cpp b/c++/Others/A simple example using a virtual function..cpp new file mode 100644 index 0000000..d869cc5 --- /dev/null +++ b/c++/Others/A simple example using a virtual function..cpp @@ -0,0 +1,55 @@ +A simple example using a virtual function. +#include +using namespace std; + +class BaseClass { +public: + int i; + BaseClass(int x) { + i = x; + } + virtual void myFunction() + { + cout << "Using BaseClass version of myFunction(): "; + cout << i << '\n'; + } +}; + +class DerivedClass1 : public BaseClass { +public: + DerivedClass1(int x) : BaseClass(x) {} + void myFunction() + { + cout << "Using DerivedClass1's version of myFunction(): "; + cout << i*i << '\n'; + } +}; + +class DerivedClass2 : public BaseClass { +public: + DerivedClass2(int x) : BaseClass(x) {} + void myFunction() + { + cout << "Using DerivedClass2's version of myFunction(): "; + cout << i+i << '\n'; + } +}; + +int main() +{ + BaseClass *p; + BaseClass ob(10); + DerivedClass1 derivedObject1(10); + DerivedClass2 derivedObject2(10); + + p = &ob; + p->myFunction(); // use BaseClass's myFunction() + + p = &derivedObject1; + p->myFunction(); // use DerivedClass1's myFunction() + + p = &derivedObject2; + p->myFunction(); // use DerivedClass2's myFunction() + + return 0; +} diff --git a/c++/Others/A simple generic linked list..cpp b/c++/Others/A simple generic linked list..cpp new file mode 100644 index 0000000..65ec44f --- /dev/null +++ b/c++/Others/A simple generic linked list..cpp @@ -0,0 +1,48 @@ +A simple generic linked list. +#include +using namespace std; + +template class list { + dataType data; + list *next; +public: + list(dataType d); + void add(list *node) { + node->next = this; + next = 0; + } + list *getnext() { + return next; + } + dataType getdata() { + return data; + } +}; + +template list::list(dataType d) +{ + data = d; + next = 0; +} + +int main() +{ + list start('a'); + list *p, *last; + int i; + + last = &start; + for(i=1; i <26; i++) { + p = new list ('a' + i); + p->add(last); + last = p; + } + + p = &start; + while(p) { + cout << p->getdata(); + p = p->getnext(); + } + + return 0; +} diff --git a/c++/Others/A simple map char and int.cpp b/c++/Others/A simple map char and int.cpp new file mode 100644 index 0000000..f121e8a --- /dev/null +++ b/c++/Others/A simple map char and int.cpp @@ -0,0 +1,28 @@ +A simple map: char and int +#include +#include +using namespace std; + +int main() +{ + map mapObject; + int i; + + for(i = 0; i <26; i++) { + mapObject.insert(pair('A'+i, 65+i)); + } + + char ch; + cout << "Enter key: "; + cin >> ch; + + map::iterator p; + + p = mapObject.find(ch); + if(p != mapObject.end()) + cout << "Its ASCII value is " << p->second; + else + cout << "Key not in map.\n"; + + return 0; +} diff --git a/c++/Others/A simple output manipulator sethex.cpp b/c++/Others/A simple output manipulator sethex.cpp new file mode 100644 index 0000000..f7fc8c1 --- /dev/null +++ b/c++/Others/A simple output manipulator sethex.cpp @@ -0,0 +1,20 @@ +A simple output manipulator: sethex +#include +#include +using namespace std; + + +ostream &sethex(ostream &stream) +{ + stream.setf(ios::showbase); + stream.setf(ios::hex, ios::basefield); + + return stream; +} + +int main() +{ + cout << 256 << " " << sethex << 256; + + return 0; +} diff --git a/c++/Others/A simple program demonstrating the use of pointers..cpp b/c++/Others/A simple program demonstrating the use of pointers..cpp new file mode 100644 index 0000000..a377ad1 --- /dev/null +++ b/c++/Others/A simple program demonstrating the use of pointers..cpp @@ -0,0 +1,47 @@ +A simple program demonstrating the use of pointers. + +#include +using namespace std; + +int main() +{ + // declare an integer and a float variable + int IntNum; + float FloatNum; + + // declare integer and float pointers + int *pIntNum; + float *pFloatNum; + + // initialize the integer and float variables + IntNum = 10; + FloatNum = 12.34; + + // store addresses in pointers + pIntNum = &IntNum; + pFloatNum = &FloatNum; + + // print out the original values + cout << "Before increment: " << endl; + cout << "\t IntNum is: " << IntNum << endl; + cout << "\t FloatNum is: " << FloatNum << endl; + + // note that we need to dereference a pointer in order + // to extract the value it contains. + cout << "\t pIntNum contains: " << *pIntNum << endl; + cout << "\t pFloatNum contains: " << *pFloatNum << endl; + + // increment values of the integer and float variables + (*pIntNum)++; // dereference and then increment + (*pFloatNum)++; + + // print out the values after increment + cout << "After increment: " << endl; + cout << "\t IntNum is: " << IntNum << endl; + cout << "\t FloatNum is: " << FloatNum << endl; + + cout << "\t pIntNum contains: " << *pIntNum << endl; + cout << "\t pFloatNum contains: " << *pFloatNum << endl; + + return 0; +} diff --git a/c++/Others/A simple program demonstrating the use of reference.cpp b/c++/Others/A simple program demonstrating the use of reference.cpp new file mode 100644 index 0000000..dd1ee47 --- /dev/null +++ b/c++/Others/A simple program demonstrating the use of reference.cpp @@ -0,0 +1,40 @@ +A simple program demonstrating the use of reference + +#include +using namespace std; + +int main() +{ + int Len, Wid; // declare int variables + + // Create references to int variables. + // Now rLen and Len are aliases to each other, + // and rWid and Wid are also aliases to each other. + int &rLen = Len; + int &rWid = Wid; + + // Initialized the two int variables + Len = 10; // rLen is also initialized to be 10 + Wid = 20; // rWid is also initialized to be 20 + + // Printing out the values for int and int references + cout << "Len is: " << Len << ", and Wid is: " << Wid << endl; + cout << "rLen is: " << rLen << ", and rWid is: " << rWid << endl; + cout << endl; + + // Printing out the address of int and references to int + cout << "Address of Len is: " << &Len << endl; + cout << "Address of rLen is: " << &rLen << endl; + if(&Len == &rLen) + { + cout << "Address of Len is equal to address of rLen!" << endl; + } + cout << "Address of Wid is: " << &Wid << endl; + cout << "Address of rWid is: " << &rWid << endl; + if(&Wid == &Wid) + { + cout << "Address of Wid is equal to address of rWid!" << endl; + } + + return 0; +} diff --git a/c++/Others/A simple program showing inheritance.cpp b/c++/Others/A simple program showing inheritance.cpp new file mode 100644 index 0000000..c655432 --- /dev/null +++ b/c++/Others/A simple program showing inheritance.cpp @@ -0,0 +1,31 @@ +A simple program showing inheritance + +#include +using namespace std; + +class base { + int i, j; +public: + void set(int a, int b) { i = a; j = b; } + void show() { cout << i << " " << j << "\n"; } +}; + +// inheritance +class derived : public base { + int k; +public: + derived(int x) { k = x; } + void showk() { cout << k << "\n"; } +}; + +int main() +{ + derived ob(3); + + ob.set(1, 2); // access member of base + ob.show(); // access member of base + + ob.showk(); // uses member of derived class + + return 0; +} diff --git a/c++/Others/A simple stack example push, empty, pop and top.cpp b/c++/Others/A simple stack example push, empty, pop and top.cpp new file mode 100644 index 0000000..6fa9d82 --- /dev/null +++ b/c++/Others/A simple stack example push, empty, pop and top.cpp @@ -0,0 +1,22 @@ +A simple stack example: push, empty, pop and top +#include +#include +using namespace std; + +int main() +{ + stack stackObject; + + stackObject.push('A'); + stackObject.push('B'); + stackObject.push('C'); + stackObject.push('D'); + + while(!stackObject.empty()) { + cout << "Popping: "; + cout << stackObject.top() << endl; + stackObject.pop(); + } + + return 0; +} diff --git a/c++/Others/A static member variable example..cpp b/c++/Others/A static member variable example..cpp new file mode 100644 index 0000000..d37dccf --- /dev/null +++ b/c++/Others/A static member variable example..cpp @@ -0,0 +1,29 @@ +A static member variable example. +#include +using namespace std; + +class myclass { + static int i; +public: + void setInt(int n) { + i = n; + } + int getInt() { + return i; + } +}; + + +int myclass::i; // Definition of myclass::i. i is still private to myclass. + +int main() +{ + myclass object1, object2; + + object1.setInt(10); + + cout << "object1.i: " << object1.getInt() << '\n'; // displays 10 + cout << "object2.i: " << object2.getInt() << '\n'; // also displays 10 + + return 0; +} diff --git a/c++/Others/A string demonstration assignment, concatenate, compare.cpp b/c++/Others/A string demonstration assignment, concatenate, compare.cpp new file mode 100644 index 0000000..0bbe7da --- /dev/null +++ b/c++/Others/A string demonstration assignment, concatenate, compare.cpp @@ -0,0 +1,42 @@ +A string demonstration: assignment, concatenate, compare +#include +#include +using namespace std; + +int main() +{ + string str1("Alpha"); + string str2("Beta"); + string str3("Omega"); + string str4; + + str4 = str1; + cout << str1 << endl << str3 << endl; + + + str4 = str1 + str2; // concatenate two strings + cout << str4 << endl; + + str4 = str1 + " to " + str3; + cout << str4 << endl; + + + if(str3 > str1) // compare strings + cout << "str3 > str1\n"; + if(str3 == str1 + str2) + cout << "str3 == str1+str2\n"; + + str1 = "This is a null-terminated string.\n"; + cout << str1; + + // create a string object using another string object + string str5(str1); + cout << str5; + + // input a string + cout << "Enter a string: "; + cin >> str5; + cout << str5; + + return 0; +} diff --git a/c++/Others/A switch statement in action.cpp b/c++/Others/A switch statement in action.cpp new file mode 100644 index 0000000..9cfacf5 --- /dev/null +++ b/c++/Others/A switch statement in action.cpp @@ -0,0 +1,31 @@ +A switch statement in action +#include +using namespace std; +int main(void) +{ + char grade; + cout << "Enter your grade: "; + cin >> grade; + switch (grade) + { + case 'A': + cout << "Your average must be between 90 - 100" + << endl; + break; + case 'B': + cout << "Your average must be between 80 - 89" + << endl; + break; + case 'C': + cout << "Your average must be between 70 - 79" + << endl; + break; + case 'D': + cout << "Your average must be between 60 - 69" + << endl; + break; + default: + cout << "Your average must be below 60" << endl; + } + return 0; +} diff --git a/c++/Others/A vector may allocate more memory than it currently needs..cpp b/c++/Others/A vector may allocate more memory than it currently needs..cpp new file mode 100644 index 0000000..729618f --- /dev/null +++ b/c++/Others/A vector may allocate more memory than it currently needs..cpp @@ -0,0 +1,33 @@ +A vector may allocate more memory than it currently needs. +#include +#include +using namespace std; + +int main() +{ + vector vectorObject(10); + + cout << "Initial size: " << vectorObject.size() << endl; + cout << "Initial capacity: " << vectorObject.capacity(); + cout << "\n\n"; + + vectorObject.push_back('X'); + + cout << "Size after push_back: " << vectorObject.size() << endl; + cout << "New capacity: " << vectorObject.capacity(); + cout << "\n\n"; + + vectorObject.resize(100); + + cout << "Size after resize: " << vectorObject.size() << endl; + cout << "Capacity after resize: " << vectorObject.capacity(); + cout << "\n\n"; + + vectorObject.push_back('Y'); + + cout << "Size after push_back: " << vectorObject.size() << endl; + cout << "New capacity: " << vectorObject.capacity(); + cout << "\n\n"; + + return 0; +} diff --git a/c++/Others/A while Loop - Generate a random number between 0 and 9.cpp b/c++/Others/A while Loop - Generate a random number between 0 and 9.cpp new file mode 100644 index 0000000..b70da08 --- /dev/null +++ b/c++/Others/A while Loop - Generate a random number between 0 and 9.cpp @@ -0,0 +1,38 @@ +A while Loop - Generate a random number between 0 and 9 +and let the user guess it. +Use a while loop. Exit when user guessed right. + +#include +// is needed in order to use the rand(). +// For older compilers, use +#include +using namespace std; + +int main() +{ + int magic; // magic number + int guess; // user's guess + + cout << "I will come up with a magic number between 0 and 9 "; + cout << "and ask you to guess it." << endl; + + magic = rand()%10; // get a random number between 0 and 9 + + cout << "Enter your guess: "; + cin >> guess; + + while (guess != magic) // as long as guess is incorrect + { + if(guess > magic) + { + cout << "Too big! Guess again..." << endl; + } + else // guess is less than magic + { + cout << "Too small! Guess again..." << endl; + } + cin >> guess; + } + cout << "You are RIGHT!" << endl;; + return 0; +} diff --git a/c++/Others/Absolute Value Calculation.cpp b/c++/Others/Absolute Value Calculation.cpp new file mode 100644 index 0000000..8724500 --- /dev/null +++ b/c++/Others/Absolute Value Calculation.cpp @@ -0,0 +1,29 @@ +Absolute Value Calculation +This is a simple function that calculates the absolute value of a number: + +#include +using namespace std; + +double Abs(double Nbr) +{ +// return (Nbr >= 0) ? Nbr : -Nbr; + if( Nbr >= 0 ) + return Nbr; + else + return -Nbr; +} + +int main() +{ + double Number = -88; + double Nbr = Abs(Number); + + cout << "The absolute value of " << Number << " is " << Nbr << endl; + + return 0; +} + +Here is an example of running the program: + +The absolute value of -88 is 88 + diff --git a/c++/Others/Abstract base class.cpp b/c++/Others/Abstract base class.cpp new file mode 100644 index 0000000..4270ea2 --- /dev/null +++ b/c++/Others/Abstract base class.cpp @@ -0,0 +1,36 @@ +Abstract base class +#include +using namespace std; + +class CPolygon { + protected: + int width, height; + public: + void set_values (int a, int b) + { width=a; height=b; } + virtual int area (void) =0; +}; + +class CRectangle: public CPolygon { + public: + int area (void) + { return (width * height); } +}; + +class CTriangle: public CPolygon { + public: + int area (void) + { return (width * height / 2); } +}; + +int main () { + CRectangle rect; + CTriangle trgl; + CPolygon * ppoly1 = ▭ + CPolygon * ppoly2 = &trgl; + ppoly1->set_values (4,5); + ppoly2->set_values (4,5); + cout << ppoly1->area() << endl; + cout << ppoly2->area() << endl; + return 0; +} diff --git a/c++/Others/Abstract classes by virtual function with no body.cpp b/c++/Others/Abstract classes by virtual function with no body.cpp new file mode 100644 index 0000000..324d18a --- /dev/null +++ b/c++/Others/Abstract classes by virtual function with no body.cpp @@ -0,0 +1,42 @@ +Abstract classes by virtual function with no body +#include +using namespace std; + +class Animal{ +public: + Animal(int health = 100); + virtual void Greet() const = 0; //pure virtual member function + virtual void DisplayHealth() const; + +protected: + int m_Health; +}; + +Animal::Animal(int health): m_Health(health){} +void Animal::DisplayHealth() const{ + cout << "Health: " << m_Health << endl; +} + +class Orc : public Animal{ +public: + Orc(int health = 120); + virtual void Greet() const; +}; + +Orc::Orc(int health): + Animal(health) +{} + +void Orc::Greet() const +{ + cout << "The orc grunts hello.\n"; +} + +int main() +{ + Animal* pAnimal = new Orc(); + pAnimal->Greet(); + pAnimal->DisplayHealth(); + + return 0; +} diff --git a/c++/Others/Access a vector using an iterator..cpp b/c++/Others/Access a vector using an iterator..cpp new file mode 100644 index 0000000..a18a6bd --- /dev/null +++ b/c++/Others/Access a vector using an iterator..cpp @@ -0,0 +1,25 @@ +Access a vector using an iterator. +#include +#include +using namespace std; + +int main() +{ + vector v; + int i; + + for(i = 0; i <10; i++) + v.push_back(i); + + for(i = 0; i <10; i++) + cout << v[ i ] << " "; + cout << endl; + + vector::iterator p = v.begin(); + while(p != v.end()) { + cout << *p << " "; + p++; + } + + return 0; +} diff --git a/c++/Others/Access control under inheritance.cpp b/c++/Others/Access control under inheritance.cpp new file mode 100644 index 0000000..c2d18e6 --- /dev/null +++ b/c++/Others/Access control under inheritance.cpp @@ -0,0 +1,40 @@ +Access control under inheritance +#include +using namespace std; + +class Enemy +{ +public: + Enemy(): m_Damage(10) {} + + void Attack() const + { cout << "Attack inflicts " << m_Damage << " damage points!\n"; } + +protected: + int m_Damage; +}; + +class Boss : public Enemy +{ +public: + Boss(): m_DamageMultiplier(3) {} + + void SpecialAttack() const + { cout << "Special Attack inflicts " << (m_DamageMultiplier * m_Damage); + cout << " damage points!\n"; } + +private: + int m_DamageMultiplier; +}; + +int main() +{ + Enemy enemy1; + enemy1.Attack(); + + Boss boss1; + boss1.Attack(); + boss1.SpecialAttack(); + + return 0; +} diff --git a/c++/Others/Access out-of-range element.cpp b/c++/Others/Access out-of-range element.cpp new file mode 100644 index 0000000..5e56eea --- /dev/null +++ b/c++/Others/Access out-of-range element.cpp @@ -0,0 +1,39 @@ +Access out-of-range element +#include +using std::cout; +using std::endl; + +#include // vector class-template definition +#include // copy algorithm +#include // ostream_iterator iterator +#include // out_of_range exception + +int main() +{ + int array[ 6 ] = { 1, 2, 3, 4, 5, 6 }; + std::vector< int > integers( array, array + 6 ); + std::ostream_iterator< int > output( cout, " " ); + + integers.push_back( 2 ); + integers.push_back( 3 ); + integers.push_back( 4 ); + + cout << "Vector integers contains: "; + std::copy( integers.begin(), integers.end(), output ); + + try + { + integers.at( 100 ) = 777; + } catch ( std::out_of_range outOfRange ) // out_of_range exception + { + cout << "\n\nException: " << outOfRange.what(); + } + + return 0; +} + + /* +Vector integers contains: 1 2 3 4 5 6 2 3 4 + +Exception: vector::_M_range_check + */ diff --git a/c++/Others/Access the elements of a vector through an iterator..cpp b/c++/Others/Access the elements of a vector through an iterator..cpp new file mode 100644 index 0000000..1876e8e --- /dev/null +++ b/c++/Others/Access the elements of a vector through an iterator..cpp @@ -0,0 +1,45 @@ +Access the elements of a vector through an iterator. +#include +#include +using namespace std; + +int main() +{ + vector vectorObject(10); + vector::iterator p; + int i; + + p = vectorObject.begin(); + i = 0; + while(p != vectorObject.end()) { + *p = i; + p++; + i++; + } + + + cout << "Original contents:\n"; + p = vectorObject.begin(); + while(p != vectorObject.end()) { + cout << *p << " "; + p++; + } + cout << "\n\n"; + + + p = vectorObject.begin(); + while(p != vectorObject.end()) { + *p = *p * 2; // change contents of vector + p++; + } + + cout << "Modified Contents:\n"; + p = vectorObject.begin(); + while(p != vectorObject.end()) { + cout << *p << " "; // display contents of vector + p++; + } + cout << endl; + + return 0; +} diff --git a/c++/Others/Accessing Character Elements of an STL String.cpp b/c++/Others/Accessing Character Elements of an STL String.cpp new file mode 100644 index 0000000..dfee64d --- /dev/null +++ b/c++/Others/Accessing Character Elements of an STL String.cpp @@ -0,0 +1,17 @@ +Accessing Character Elements of an STL String +#include +#include + +int main(){ + using namespace std; + + string str ("Hello String"); + + for(size_t i = 0; i < str.length(); ++ i){ + cout << "Character [" << i << "] is: "; + cout << str [i] << endl; + } + cout << endl; + + return 0; +} diff --git a/c++/Others/Accessing Characters In Strings.cpp b/c++/Others/Accessing Characters In Strings.cpp new file mode 100644 index 0000000..68f4b86 --- /dev/null +++ b/c++/Others/Accessing Characters In Strings.cpp @@ -0,0 +1,40 @@ +Accessing Characters In Strings +#include +#include +#include +using namespace std; +int main() +{ + string text; + + cout << "Counts words. Enter a text and terminate with a period and return:\n"; + + getline( cin, text, '.'); // Reads a text up to the first '.' + + int i, // Index + + numberOfWhiteSpace = 0, // Number of white spaces + + numberOfWords = 0; // Number of words + + bool fSpace = true; // Flag for white space + for( i = 0; i < text.length(); ++i) + { + if( isspace( text[i]) ) // white space? + { + ++numberOfWhiteSpace; + fSpace = true; + } + else if( fSpace) // At the beginning of a word? + { + ++numberOfWords; + fSpace = false; + } + } + cout << "\nYour text contains (without periods)" + << "\ncharacters: " << text.length() + << "\nwords: " << numberOfWords + << "\nwhite spaces: " << numberOfWhiteSpace + << endl; + return 0; +} diff --git a/c++/Others/Accessing Data in a File.cpp b/c++/Others/Accessing Data in a File.cpp new file mode 100644 index 0000000..f24fc35 --- /dev/null +++ b/c++/Others/Accessing Data in a File.cpp @@ -0,0 +1,47 @@ +Accessing Data in a File +#include +#include +#include +#include +#include +#include +#include + +using namespace std; + +template +void print(T& c){ + for( typename T::iterator i = c.begin(); i != c.end(); i++ ){ + std::cout << *i << endl; + } +} + +int main(){ + vector output_data( 10 ); + generate( output_data.begin(), output_data.end(), rand ); + + transform( output_data.begin(), output_data.end(),output_data.begin(), bind2nd( modulus(), 10 ) ); + + ofstream out( "data.txt" ); + if( !out ) + { + cout << "Couldn't open output file\n"; + return 0; + } + + copy( output_data.begin(), output_data.end(),ostream_iterator( out, "\n" ) ); + out.close(); + + ifstream in( "data.txt" ); + if( !in ) + { + cout << "Couldn't open input file\n"; + return 0; + } + + vector input_data( (istream_iterator( in )),istream_iterator() ); + in.close(); + + print( output_data ); + print( input_data ); +} diff --git a/c++/Others/Accessing Private Data Members in C++. This is a flaw in the language.cpp b/c++/Others/Accessing Private Data Members in C++. This is a flaw in the language.cpp new file mode 100644 index 0000000..729bad2 --- /dev/null +++ b/c++/Others/Accessing Private Data Members in C++. This is a flaw in the language.cpp @@ -0,0 +1,58 @@ +Accessing Private Data Members in C++. This is a flaw in the language + +#include +#include +#include + +class bestcoder +{ + private: + + char name[40]; + char grade; + int age; + + public: + + bestcoder(char* nam="Some Dude",char gr='A',int saal=25) + { + strcpy(name,nam); + grade=gr; + age=saal; + } + + friend ostream& operator <<(ostream& s,bestcoder b); +}; + +ostream& operator <<(ostream& s,bestcoder b) +{ + s<<"Best Coder :"<grade='F'; + bettercoder->age=56; + cout<name,"xxx"); + bettercoder->age=14; + bettercoder->grade='A'; + cout< +#include +#include +#include + +// Forward declarations of the error handler and message handler. + +int err_handler(PDBPROCESS, INT, INT, INT, LPCSTR, LPCSTR); +int msg_handler(PDBPROCESS, DBINT, INT, INT, LPCSTR, LPCSTR, +LPCSTR, DBUSMALLINT); +main() +{ + PDBPROCESS dbproc; // The connection with SQL Server. + PLOGINREC login; // The login information. + DBCHAR name[100]; + DBCHAR city[100]; + +// Install user-supplied error- and message-handling functions. + + dberrhandle (err_handler); + dbmsghandle (msg_handler); + +// Initialize DB-Library. + + dbinit (); + +// Get a LOGINREC. + + login = dblogin (); + DBSETLUSER (login, "my_login"); + DBSETLPWD (login, "my_password"); + DBSETLAPP (login, "example"); + +// Get a DBPROCESS structure for communication with SQL Server. + + dbproc = dbopen (login, "my_server"); + +// Retrieve some columns from the authors table in the +// pubs database. +// First, put the command into the command buffer. + + dbcmd (dbproc, "SELECT au_lname, city FROM pubs..authors"); + dbcmd (dbproc, " WHERE state = 'CA' "); + +// Send the command to SQL Server and start execution. + + dbsqlexec (dbproc); + +// Process the results. + + if (dbresults (dbproc) == SUCCEED) + { + +// Bind column to program variables. + + dbbind (dbproc, 1, NTBSTRINGBIND, 0, name); + dbbind (dbproc, 2, NTBSTRINGBIND, 0, city); + +// Retrieve and print the result rows. + + while (dbnextrow (dbproc) != NO_MORE_ROWS) + { + printf ("%s from %s\n", name, city); + } + } + +// Close the connection to SQL Server. + + dbexit (); + return (0); +} + +int err_handler (PDBPROCESS dbproc, INT severity, +INT dberr, INT oserr, LPCSTR dberrstr, LPCSTR oserrstr) +{ + printf ("DB-Library Error %i: %s\n", dberr, dberrstr); + if (oserr != DBNOERR) + { + printf ("Operating System Error %i: %s\n", oserr, oserrstr); + } + return (INT_CANCEL); +} + +int msg_handler (PDBPROCESS dbproc, DBINT msgno, INT msgstate, +INT severity, LPCSTR msgtext, LPCSTR server, +LPCSTR procedure, DBUSMALLINT line) +{ + printf ("SQL Server Message %ld: %s\n", msgno, msgtext); + return (0); +} diff --git a/c++/Others/Accessing a Vector Through an Iterator.cpp b/c++/Others/Accessing a Vector Through an Iterator.cpp new file mode 100644 index 0000000..c3c27de --- /dev/null +++ b/c++/Others/Accessing a Vector Through an Iterator.cpp @@ -0,0 +1,43 @@ +Accessing a Vector Through an Iterator +#include +#include +#include +using namespace std; +int main() +{ + vector vectorObject(10); + vector::iterator p; // create an iterator + int i; + + + p = vectorObject.begin(); + i = 0; + while(p != vectorObject.end()) { + *p = i + 'a'; + p++; + i++; + } + + cout << "Original contents:\n"; + p = vectorObject.begin(); + while(p != vectorObject.end()) { + cout << *p << " "; + p++; + } + cout << "\n\n"; + // change contents of vector + p = vectorObject.begin(); + while(p != vectorObject.end()) { + *p = toupper(*p); + p++; + } + // display contents of vector + cout << "Modified Contents:\n"; + p = vectorObject.begin(); + while(p != vectorObject.end()) { + cout << *p << " "; + p++; + } + cout << endl; + return 0; +} diff --git a/c++/Others/Accessing static members without an object..cpp b/c++/Others/Accessing static members without an object..cpp new file mode 100644 index 0000000..56ef21e --- /dev/null +++ b/c++/Others/Accessing static members without an object..cpp @@ -0,0 +1,44 @@ +Accessing static members without an object. +#include +using namespace std; +class Cat +{ +public: + Cat(int age):itsAge(age){count++; } + virtual ~Cat() { count--; } + virtual int GetAge() { return itsAge; } + virtual void SetAge(int age) { itsAge = age; } + static int count; + +private: + int itsAge; + +}; + +int Cat::count = 0; + +void TelepathicFunction(); + +int main() +{ + const int MaxCats = 5; int i; + Cat *CatHouse[MaxCats]; + for (i = 0; i +#include +#include +#include +using namespace std; + +double arithmeticMean(const vector& nums) +{ + double sum = accumulate(nums.begin(), nums.end(), 0); + return (sum / nums.size()); +} + +int product(int num1, int num2) +{ + return (num1 * num2); +} + +int main(int argc, char** argv) +{ + vector myVector; + + myVector.push_back(1); + myVector.push_back(2); + myVector.push_back(3); + myVector.push_back(4); + + cout << "The arithmetic mean is " << arithmeticMean(myVector) << endl; + + return (0); +} diff --git a/c++/Others/Add a friend extractor for objects of type MyClass..cpp b/c++/Others/Add a friend extractor for objects of type MyClass..cpp new file mode 100644 index 0000000..5d2551c --- /dev/null +++ b/c++/Others/Add a friend extractor for objects of type MyClass..cpp @@ -0,0 +1,43 @@ +Add a friend extractor for objects of type MyClass. +#include +using namespace std; + +class MyClass { + int x, y; +public: + MyClass() { + x = 0; + y = 0; + } + MyClass(int i, int j) { + x = i; + y = j; + } + friend ostream &operator<<(ostream &stream, MyClass ob); + friend istream &operator>>(istream &stream, MyClass &ob); +}; + +ostream &operator<<(ostream &stream, MyClass ob) +{ + stream << ob.x << ", " << ob.y << '\n'; + return stream; +} + +istream &operator>>(istream &stream, MyClass &ob) +{ + cout << "Enter MyClassinates: "; + stream >> ob.x >> ob.y; + return stream; +} + +int main() +{ + MyClass a(1, 1), b(10, 23); + + cout << a << b; + + cin >> a; + cout << a; + + return 0; +} diff --git a/c++/Others/Add an else part to the if statement.cpp b/c++/Others/Add an else part to the if statement.cpp new file mode 100644 index 0000000..454fb65 --- /dev/null +++ b/c++/Others/Add an else part to the if statement.cpp @@ -0,0 +1,14 @@ +Add an else part to the if statement +#include +using namespace std; +int main(void) +{ + int num; + cout << "Enter a whole number: "; + cin >> num; + if ( num % 2 == 0 ) + cout << "The number is even" << endl; + else + cout << "The number is odd" << endl; + return 0; +} diff --git a/c++/Others/Add elements in a list to a set.cpp b/c++/Others/Add elements in a list to a set.cpp new file mode 100644 index 0000000..78b6c2a --- /dev/null +++ b/c++/Others/Add elements in a list to a set.cpp @@ -0,0 +1,36 @@ + + +Add elements in a list to a set +#include +#include +#include +#include +#include +using namespace std; + +int main() +{ + string s("There is no distinctly native American criminal class"); + + + list list1(s.begin(), s.end()); + + // Put the characters in list1 into set1: + set set1; + list::iterator i; + + for (i = list1.begin(); i != list1.end(); ++i) + set1.insert(*i); + + set::iterator j; + + for (j = set1.begin(); j != set1.end(); ++j) + cout << *j; + + + return 0; +} + +/* + ATacdehilmnorstvy + */ diff --git a/c++/Others/Add elements in a multiset to a list.cpp b/c++/Others/Add elements in a multiset to a list.cpp new file mode 100644 index 0000000..0345578 --- /dev/null +++ b/c++/Others/Add elements in a multiset to a list.cpp @@ -0,0 +1,36 @@ +Add elements in a multiset to a list +#include +#include +#include +#include +#include +using namespace std; + +int main() +{ + string s("There is no distinctly native American criminal class"); + + list list1(s.begin(), s.end()); + + // Put the characters in list1 into multiset1: + multiset multiset1; + list::iterator i; + for (i = list1.begin(); i != list1.end(); ++i) + multiset1.insert(*i); + + // Put the characters in multiset1 into list2: + list list2; + multiset::iterator k; + for (k = multiset1.begin(); k != multiset1.end(); ++k) + list2.push_back(*k); + + + for (i = list2.begin(); i != list2.end(); ++i) + cout << *i; + + return 0; +} + +/* + ATaaaaccccdeeeehiiiiiiilllmmnnnnnorrrsssstttvy" + */ diff --git a/c++/Others/Add elements in a set to a list.cpp b/c++/Others/Add elements in a set to a list.cpp new file mode 100644 index 0000000..1900d5a --- /dev/null +++ b/c++/Others/Add elements in a set to a list.cpp @@ -0,0 +1,39 @@ +Add elements in a set to a list +#include +#include +#include +#include +#include +using namespace std; + +int main() +{ + string s("There is no distinctly native American criminal class"); + + + list list1(s.begin(), s.end()); + + // Put the characters in list1 into set1: + set set1; + list::iterator i; + + for (i = list1.begin(); i != list1.end(); ++i) + set1.insert(*i); + + set::iterator j; + + list list2; + set::iterator k; + for (k = set1.begin(); k != set1.end(); ++k) + list2.push_back(*k); + + + for (i = list2.begin(); i != list2.end(); ++i) + cout << *i; + + return 0; +} + +/* + ATacdehilmnorstvy + */ diff --git a/c++/Others/Adding Strings.cpp b/c++/Others/Adding Strings.cpp new file mode 100644 index 0000000..cb32f7a --- /dev/null +++ b/c++/Others/Adding Strings.cpp @@ -0,0 +1,11 @@ +Adding Strings +#include +#include +using namespace std; +int main(void) +{ + string firstName = "gggg"; + string lastName = "uuuut"; + cout << "Your name is " << firstName + lastName; + return 0; +} diff --git a/c++/Others/Addition operator in cout.cpp b/c++/Others/Addition operator in cout.cpp new file mode 100644 index 0000000..4fb601f --- /dev/null +++ b/c++/Others/Addition operator in cout.cpp @@ -0,0 +1,17 @@ +Addition operator in cout +#include +using namespace std; +int main(void) +{ + int total, added, dropped; + cout << "Enter total: "; + cin >> total; + cout << "Enter added: "; + cin >> added; + total = total + added; + cout << "Enter dropped "; + cin >> dropped; + total -= dropped; + cout << "Number: " << total << endl; + return 0; +} diff --git a/c++/Others/Additional meanings for the + and = operations.cpp b/c++/Others/Additional meanings for the + and = operations.cpp new file mode 100644 index 0000000..62d2de5 --- /dev/null +++ b/c++/Others/Additional meanings for the + and = operations.cpp @@ -0,0 +1,69 @@ +Additional meanings for the + and = operations +#include +#include +using namespace std; +class str_type { + char string[80]; +public: + str_type(char *str = "\0") { strcpy(string, str); } + + str_type operator+(str_type str); + str_type operator+(char *str); + + str_type operator=(str_type str); + str_type operator=(char *str); + + void show_str(void) { cout << string; } +} ; + +str_type str_type::operator+(str_type str) { + str_type temp; + + strcpy(temp.string, string); + strcat(temp.string, str.string); + return temp; +} + +str_type str_type::operator=(str_type str) { + strcpy(string, str.string); + return *this; +} + +str_type str_type::operator=(char *str) +{ + str_type temp; + + strcpy(string, str); + strcpy(temp.string, string); + return temp; +} + +str_type str_type::operator+(char *str) +{ + str_type temp; + + strcpy(temp.string, string); + strcat(temp.string, str); + return temp; +} + +main(void) +{ + str_type a("Hello "), b("There"), c; + + c = a + b; + + c.show_str(); + cout << "\n"; + + a = "to program in because"; + a.show_str(); + cout << "\n"; + + b = c = "C++ is fun"; + + c = c+" "+a+" "+b; + c.show_str(); + + return 0; +} diff --git a/c++/Others/Address class class definition and implementation.cpp b/c++/Others/Address class class definition and implementation.cpp new file mode 100644 index 0000000..44ada2f --- /dev/null +++ b/c++/Others/Address class class definition and implementation.cpp @@ -0,0 +1,44 @@ +Address class: class definition and implementation +#include +#include +using namespace std; + +class Address { + char name[40]; + char street[40]; + char city[30]; + char state[3]; + char zip[10]; +public: + void store(char *n, char *s, char *c, char *t, char *z); + void display(); +}; + +void Address::store(char *n, char *s, char *c, char *t, char *z) +{ + strcpy(name, n); + strcpy(street, s); + strcpy(city, c); + strcpy(state, t); + strcpy(zip, z); +} + +void Address::display() +{ + cout << name << endl; + cout << street << endl; + cout << city << endl; + cout << state << endl; + cout << zip << endl; +} + +int main() +{ + Address a; + + a.store("C", "11 Lane", "W", "In", "4"); + + a.display(); + + return 0; +} diff --git a/c++/Others/An Array of Pointers to Class.cpp b/c++/Others/An Array of Pointers to Class.cpp new file mode 100644 index 0000000..85d6547 --- /dev/null +++ b/c++/Others/An Array of Pointers to Class.cpp @@ -0,0 +1,66 @@ +An Array of Pointers to Class +This program is an example of using an array of pointers to a class. +After declaring the array, you can allocate memory for each element using the new operator. +To access a member variable or a method of an element, you can use the -> operator: + +#include +using namespace std; + +class CSquare +{ +public: + double Side; + + CSquare() : Side(0.00) {} + CSquare(double side) : Side(side) { } + ~CSquare() { } + + double getSide() const { return Side; } + void setSide(const double s) + { + if( s <= 0 ) + Side = 0.00; + else + Side = s; + } + + double Perimeter() { return Side * 4; } + double Area() { return Side * Side; } +}; + +int main() +{ + CSquare *sqr[4]; + + sqr[0] = new CSquare; + sqr[0]->setSide(24.55); + sqr[1] = new CSquare; + sqr[1]->setSide(15.08); + sqr[2] = new CSquare; + sqr[2]->setSide(8.212); + sqr[3] = new CSquare; + sqr[3]->setSide(202.24); + + cout << "Squares Characteristics" << endl; + cout << "Square 1" << endl; + cout << "Side: " << sqr[0]->getSide() << endl; + cout << "Perimeter: " << sqr[0]->Perimeter() << endl; + cout << "Area: " << sqr[0]->Area() << endl; + + cout << "Square 2" << endl; + cout << "Side: " << sqr[1]->getSide() << endl; + cout << "Perimeter: " << sqr[1]->Perimeter() << endl; + cout << "Area: " << sqr[1]->Area() << endl; + + cout << "Square 3" << endl; + cout << "Side: " << sqr[2]->getSide() << endl; + cout << "Perimeter: " << sqr[2]->Perimeter() << endl; + cout << "Area: " << sqr[2]->Area() << endl; + + cout << "Square 4" << endl; + cout << "Side: " << sqr[3]->getSide() << endl; + cout << "Perimeter: " << sqr[3]->Perimeter() << endl; + cout << "Area: " << sqr[3]->Area() << endl; + + return 0; +} diff --git a/c++/Others/An Example of Exception Handling.cpp b/c++/Others/An Example of Exception Handling.cpp new file mode 100644 index 0000000..6a808ca --- /dev/null +++ b/c++/Others/An Example of Exception Handling.cpp @@ -0,0 +1,39 @@ +An Example of Exception Handling +#include +using namespace std; + +int main() +{ + unsigned int TypeOfLoan = 0; + const char *LoanType[] = { "Personal", + "Car", + "Furniture", + "Musical Instrument", + "Boat" }; + + try { + cout << "Enter the type of loan\n"; + for(int i = 0; i < 4; i++) + cout << i + 1 << ") " << LoanType[i] << endl; + cout << "Your choice: "; + cin >> TypeOfLoan; + + if( TypeOfLoan < 1 || TypeOfLoan > 5 ) + throw "Number out of range\n"; + + cout << "\nType of Loan: " << LoanType[TypeOfLoan] << endl; + } + catch(const char* Msg) + { + cout << "Error: " << Msg << endl; + } + catch(...) + { + cout << "\nSomething went wrong\n\n"; + } + + return 0; +} + + + diff --git a/c++/Others/An Example with Two Generic Data Types.cpp b/c++/Others/An Example with Two Generic Data Types.cpp new file mode 100644 index 0000000..8565d34 --- /dev/null +++ b/c++/Others/An Example with Two Generic Data Types.cpp @@ -0,0 +1,23 @@ +An Example with Two Generic Data Types +#include +using namespace std; + +template class myclass +{ + Type1 i; + Type2 j; +public: + myclass(Type1 a, Type2 b) { i = a; j = b; } + void show() { cout << i << ' ' << j << '\n'; } +}; + +int main() +{ + myclass ob1(10, 0.23); + myclass ob2('X', "Templates add power."); + + ob1.show(); + ob2.show(); + + return 0; +} diff --git a/c++/Others/An array-based output stream.cpp b/c++/Others/An array-based output stream.cpp new file mode 100644 index 0000000..f1bfeb4 --- /dev/null +++ b/c++/Others/An array-based output stream.cpp @@ -0,0 +1,15 @@ +An array-based output stream +#include +#include +using namespace std; +int main() +{ + char str[80]; + ostrstream outs(str, sizeof(str)); + outs << "array-based I/O. "; + outs << 1024 << hex << " "; + outs.setf(ios::showbase); + outs << 100 << ' ' << 99.789 << ends; + cout << str; + return 0; +} diff --git a/c++/Others/An example that uses typeid for base and derived classes.cpp b/c++/Others/An example that uses typeid for base and derived classes.cpp new file mode 100644 index 0000000..27df9c3 --- /dev/null +++ b/c++/Others/An example that uses typeid for base and derived classes.cpp @@ -0,0 +1,42 @@ +An example that uses typeid for base and derived classes +#include +#include +using namespace std; + +class BaseClass { + virtual void f() {}; // make BaseClass polymorphic + +}; + +class Derived1: public BaseClass { + +}; + +class Derived2: public BaseClass { + +}; + +int main() +{ + int i; + BaseClass *p, baseob; + Derived1 object1; + Derived2 object2; + + cout << "Typeid of i is "; + cout << typeid(i).name() << endl; + + p = &baseob; + cout << "p is pointing to an object of type "; + cout << typeid(*p).name() << endl; + + p = &object1; + cout << "p is pointing to an object of type "; + cout << typeid(*p).name() << endl; + + p = &object2; + cout << "p is pointing to an object of type "; + cout << typeid(*p).name() << endl; + + return 0; +} diff --git a/c++/Others/An example that uses typeid on a polymorphic class hierarchy.cpp b/c++/Others/An example that uses typeid on a polymorphic class hierarchy.cpp new file mode 100644 index 0000000..2028238 --- /dev/null +++ b/c++/Others/An example that uses typeid on a polymorphic class hierarchy.cpp @@ -0,0 +1,35 @@ +An example that uses typeid on a polymorphic class hierarchy +#include +#include +using namespace std; +class Mammal { +public: + virtual bool laysEggs() { + return false; + } +}; +class Cat: public Mammal { +public: +}; +class Platypus: public Mammal { +public: + bool laysEggs() { + return true; + } +}; +int main() +{ + Mammal *p, AnyMammal; + Cat cat; + Platypus platypus; + p = &AnyMammal; + cout << "p is pointing to an object of type "; + cout << typeid(*p).name() << endl; + p = &cat; + cout << "p is pointing to an object of type "; + cout << typeid(*p).name() << endl; + p = &platypus; + cout << "p is pointing to an object of type "; + cout << typeid(*p).name() << endl; + return 0; +} diff --git a/c++/Others/An exception can be thrown from outside the try block.cpp b/c++/Others/An exception can be thrown from outside the try block.cpp new file mode 100644 index 0000000..c6fa7b8 --- /dev/null +++ b/c++/Others/An exception can be thrown from outside the try block.cpp @@ -0,0 +1,25 @@ +An exception can be thrown from outside the try block +#include +using namespace std; + +void myFunction(int test) +{ + cout << "Inside myFunction, test is: " << test << "\n"; + if(test) throw test; +} +int main() +{ + cout << "Start\n"; + try { + cout << "Inside try block\n"; + myFunction(0); + myFunction(1); + myFunction(2); + } + catch (int i) { + cout << "Caught an exception -- value is: "; + cout << i << "\n"; + } + cout << "End"; + return 0; +} diff --git a/c++/Others/An implementation of Stack data structure.cpp b/c++/Others/An implementation of Stack data structure.cpp new file mode 100644 index 0000000..1505d2e --- /dev/null +++ b/c++/Others/An implementation of Stack data structure.cpp @@ -0,0 +1,189 @@ +An implementation of Stack data structure + +#include +#include +#include +#include +using namespace std; + +#if !defined __STACK_H +#define __STACK_H + +namespace stk{ + class Stack{ + private: + int *p; + int top,length; + + string str()const; + public: + Stack(); + Stack(const int); + Stack(const Stack&); + ~Stack(); + + void push(int); + int pop(); + int get_length()const; + bool is_empty()const; + Stack operator=(const Stack&); + friend ostream& operator<<(ostream&,Stack&); + + class StackException{ + private: + string desc; + public: + StackException(string exp){ desc="Exception : "+exp; } + string get_exp(){ return desc; } + }; + }; + + Stack::Stack(){ + top=-1; + length=0; + p=0; + } + + Stack::Stack(const int size){ + top=-1; + length=size; + try{ + p=new int[length]; + }catch(bad_alloc ba){ + cout<<"Memory can not be alllocated +"; + return; + } + } + + Stack::Stack(const Stack &o){ + top=o.top; + length=o.length; + try{ + p=new int[length]; + }catch(bad_alloc ba){ + cout<<"Memory allocation failed +"; + return; + } + for(int i=0;i +using namespace std; +class Power { + double b; + int e; + double val; +public: + Power(double base, int exp); + Power operator+(Power o) { + double base; + int exp; + base = b + o.b; + exp = e + o.e; + Power temp(base, exp); + return temp; + } + operator double() { return val; } // convert to double +}; +Power::Power(double base, int exp) +{ + b = base; + e = exp; + val = 1; + if(exp==0) + return; + for( ; exp>0; exp--) + val = val * b; +} +int main() +{ + Power x(4.0, 2); + double a; + a = x; // convert to double + cout << x + 100.2; // convert x to double and add 100.2 + cout << "\n"; + Power y(3.3, 3), z(0, 0); + z = x + y; // no conversion + a = z; // convert to double + cout << a; + return 0; +} diff --git a/c++/Others/Another example of read() and write() and illustrates the use of gcount( ).cpp b/c++/Others/Another example of read() and write() and illustrates the use of gcount( ).cpp new file mode 100644 index 0000000..a3a44a2 --- /dev/null +++ b/c++/Others/Another example of read() and write() and illustrates the use of gcount( ).cpp @@ -0,0 +1,27 @@ +Another example of read() and write() and illustrates the use of gcount( ) +#include +#include +using namespace std; +int main() +{ + double doubleNumberArray[4] = {99.75, -34.4, 1776.0, 200.1}; + int i; + ofstream out("numbers", ios::out | ios::binary); + if(!out) { + cout << "Cannot open file."; + return 1; + } + out.write((char *) &doubleNumberArray, sizeof doubleNumberArray); + out.close(); + for(i=0; i<4; i++) // clear array + doubleNumberArray[i] = 0.0; + + ifstream in("numbers", ios::in | ios::binary); + in.read((char *) &doubleNumberArray, sizeof doubleNumberArray); + + cout << in.gcount() << " bytes read\n"; // see how many bytes have been read + for(i=0; i<4; i++) // show values read from file + cout << doubleNumberArray[i] << " "; + in.close(); + return 0; +} diff --git a/c++/Others/Append two strings.cpp b/c++/Others/Append two strings.cpp new file mode 100644 index 0000000..9293f6a --- /dev/null +++ b/c++/Others/Append two strings.cpp @@ -0,0 +1,27 @@ +Append two strings +#include +using std::cout; +using std::endl; + +#include +using std::string; + +int main() +{ + string string1( "cat" ); + string string3; + + string3.assign( string1 ); + + cout << "string1: " << string1 + << "\nstring3: " << string3 << "\n\n"; + + + string3 += "pet"; + string3.append( string1, 1, string1.length() - 1 ); + + cout << "string1: " << string1 + << "\nstring3: " << string3 << "\n\n"; + + return 0; +} diff --git a/c++/Others/Appending to the End of a File.cpp b/c++/Others/Appending to the End of a File.cpp new file mode 100644 index 0000000..fce06f4 --- /dev/null +++ b/c++/Others/Appending to the End of a File.cpp @@ -0,0 +1,46 @@ +Appending to the End of a File +#include + +#include +using namespace std; +int main(){ + char fileName[80]; + char buffer[255]; + cout << "Please re-enter the file name: "; + cin >> fileName; + + ifstream fin(fileName); + if (fin){ + char ch; + while (fin.get(ch)) + cout << ch; + } + fin.close(); + + cout << "in append mode...\n"; + + ofstream fout(fileName,ios::app); + if (!fout) + { + cout << "Unable to open for appending.\n"; + return(1); + } + + cout << "\nEnter text for the file: "; + cin.ignore(1,'\n'); + cin.getline(buffer,255); + fout << buffer << "\n"; + fout.close(); + + fin.open(fileName); + if (!fin) + { + cout << "Unable to open for reading.\n"; + return(1); + } + char ch; + while (fin.get(ch)) + cout << ch; + fin.close(); + return 0; +} diff --git a/c++/Others/Appending values to Vector Containers after sorting.cpp b/c++/Others/Appending values to Vector Containers after sorting.cpp new file mode 100644 index 0000000..37d5802 --- /dev/null +++ b/c++/Others/Appending values to Vector Containers after sorting.cpp @@ -0,0 +1,33 @@ +Appending values to Vector Containers after sorting +#include +#include +#include + +using namespace std; + +template +void print(T& c){ + for( typename T::iterator i = c.begin(); i != c.end(); i++ ){ + std::cout << *i << endl; + } +} + +int main( ){ + const char* names1[] = { "A", "B", "C" }; + const char* names2[] = { "D", "E", "F", "G" }; + + vector squad1( names1,names1 + sizeof( names1 ) / sizeof( names1[0] ) ); + vector squad2( names2,names2 + sizeof( names2 ) / sizeof( names2[0] ) ); + + sort( squad1.begin(), squad1.end() ); + + print( squad1); + sort( squad2.begin(), squad2.end() ); + print( squad2); + + squad1.insert( squad1.end(), squad2.begin(), squad2.end() ); + print( squad1); + + sort( squad1.begin(), squad1.end() ); + print( squad1); +} diff --git a/c++/Others/Applying Generic Functions A Generic Bubble Sort.cpp b/c++/Others/Applying Generic Functions A Generic Bubble Sort.cpp new file mode 100644 index 0000000..3a09cb0 --- /dev/null +++ b/c++/Others/Applying Generic Functions A Generic Bubble Sort.cpp @@ -0,0 +1,43 @@ +Applying Generic Functions: A Generic Bubble Sort +#include +using namespace std; + +template void bubble( + X *items, // pointer to array to be sorted + int count) // number of items in array +{ + register int a, b; + X t; + + for(a=1; a=a; b--) + if(items[b-1] > items[b]) { + // exchange elements + t = items[b-1]; + items[b-1] = items[b]; + items[b] = t; + } +} + +int main() +{ + int iarray[7] = {7, 5, 4, 3, 9, 8, 6}; + double darray[5] = {4.3, 2.5, -0.9, 100.2, 3.0}; + + for(int i=0; i<7; i++) + cout << iarray[i] << endl; + + for(int i=0; i<5; i++) + cout << darray[i] << endl; + + bubble(iarray, 7); + bubble(darray, 5); + + for(int i=0; i<7; i++) + cout << iarray[i] << endl; + + for(int i=0; i<5; i++) + cout << darray[i] << endl; + + return 0; +} diff --git a/c++/Others/Applying Template Classes A Generic Array Class.cpp b/c++/Others/Applying Template Classes A Generic Array Class.cpp new file mode 100644 index 0000000..efdd9fa --- /dev/null +++ b/c++/Others/Applying Template Classes A Generic Array Class.cpp @@ -0,0 +1,40 @@ +Applying Template Classes: A Generic Array Class +#include +#include +using namespace std; + +const int SIZE = 10; + +template class MyClass { + T a[SIZE]; +public: + MyClass() { + register int i; + for(i=0; i T &MyClass::operator[](int i) +{ + if(i<0 || i> SIZE-1) { + cout << "\nIndex value of "; + cout << i << " is out-of-bounds.\n"; + exit(1); + } + return a[i]; +} + +int main() +{ + MyClass intob; // integer array + MyClass doubleob; // double array + + for(int i=0; i +using namespace std; + +const double pi = 3.14159; + +int main() +{ +float length, width, area; + +cout << "Enter The Length Of The Rectangle: "; +cin >> length; +cout << "Enter The Width Of Rectangle: "; +cin >> width; +area = length*width; + +cout <<"The area of the rectangle is : "<< area << endl; + +return 0; +} diff --git a/c++/Others/Area overloded.cpp b/c++/Others/Area overloded.cpp new file mode 100644 index 0000000..a29624b --- /dev/null +++ b/c++/Others/Area overloded.cpp @@ -0,0 +1,39 @@ +Area overloded + +#include +#include +#define phi 3.14 +int area(int,int); +float area(int); +void main() +{ + int a,b,c,cho; + clrscr(); + cout<<"\t What do you want to do?\n"; + cout<<"1. area of rectangle"<>cho; + switch(cho) + { + case 1: + cout<<"Enter lengt and breath (with white space):"; + cin>>a>>b; + cout<<"Area of RECTANGLE:"<>c; + cout<<"Area of CIRCLE:"< +using namespace std; + +int main() { + int ans = 27; + + ans += 10; //same as: ans = ans + 10; + cout << ans << ", "; + ans -= 7; //same as: ans = ans - 7; + cout << ans << ", "; + ans *= 2; //same as: ans = ans * 2; + cout << ans << ", "; + ans /= 3; //same as: ans = ans / 3; + cout << ans << ", "; + ans %= 3; //same as: ans = ans % 3; + cout << ans << endl; + return 0; +} diff --git a/c++/Others/Array Initialization.cpp b/c++/Others/Array Initialization.cpp new file mode 100644 index 0000000..a9f424d --- /dev/null +++ b/c++/Others/Array Initialization.cpp @@ -0,0 +1,13 @@ +Array Initialization +#include + +using namespace std; + +int main () +{ + char name[ ] = {'J', 'e', 'f', 'f', '/0' }; + + cout << name; + + return 0; +} diff --git a/c++/Others/Array based on int pointer.cpp b/c++/Others/Array based on int pointer.cpp new file mode 100644 index 0000000..168b053 --- /dev/null +++ b/c++/Others/Array based on int pointer.cpp @@ -0,0 +1,50 @@ +Array based on int pointer +#include +#include +using namespace std; +class array +{ + int *p; + int size; + public: + array(int sz) { + p = new int[sz]; + if(!p) exit(1); + size = sz; + } + ~array() {delete [] p;} + array(const array &object); + void put(int i, int j){ + if(i>=0 && i=0; lcl_i--) + cout << num.get(lcl_i); + cout << endl; + + // Create another array using the copy constructor + array x=num; + for (lcl_i=0; lcl_i<10; lcl_i++) + cout << x.get(lcl_i); +} diff --git a/c++/Others/Array class for 10 int value with overloaded functions +, -, ==.cpp b/c++/Others/Array class for 10 int value with overloaded functions +, -, ==.cpp new file mode 100644 index 0000000..e897745 --- /dev/null +++ b/c++/Others/Array class for 10 int value with overloaded functions +, -, ==.cpp @@ -0,0 +1,97 @@ +Array class for 10 int value with overloaded functions: +, -, == +#include +using namespace std; + +class array { + int nums[10]; +public: + array(); + void set(int n[10]); + void show(); + array operator+(array object2); + array operator-(array object2); + int operator==(array object2); +}; + +array::array() +{ + int i; + for(i = 0; i <10; i++) nums[ i ] = 0; +} + +void array::set(int *n) +{ + int i; + + for(i = 0; i <10; i++) nums[ i ] = n[ i ]; +} + +void array::show() +{ + int i; + + for(i = 0; i <10; i++) + cout << nums[ i ] << ' '; + + cout << endl; +} + +array array::operator+(array object2) +{ + int i; + array temp; + + for(i = 0; i <10; i++) + temp.nums[ i ] = nums[ i ] + object2.nums[ i ]; + + return temp; +} + +array array::operator-(array object2) +{ + int i; + array temp; + + for(i = 0; i <10; i++) + temp.nums[ i ] = nums[ i ] - object2.nums[ i ]; + + return temp; +} + +int array::operator==(array object2) +{ + int i; + + for(i = 0; i <10; i++) + if(nums[ i ]!=object2.nums[ i ]) return 0; + + return 1; +} + +int main() +{ + array object1, object2, object3; + + int i[10] = { 1, 2, 3, 4, 5, 6, 7, 8, 9, 10 }; + + object1.set(i); + object2.set(i); + + object3 = object1 + object2; + object3.show(); + + object3 = object1 - object3; + object3.show(); + + if(object1==object2) + cout << "object1 equals object2\n"; + else + cout << "object1 does not equal object2\n"; + + if(object1==object3) + cout << "object1 equals object3\n"; + else + cout << "object1 does not equal object3\n"; + + return 0; +} diff --git a/c++/Others/Arrays of Objects.cpp b/c++/Others/Arrays of Objects.cpp new file mode 100644 index 0000000..41a3855 --- /dev/null +++ b/c++/Others/Arrays of Objects.cpp @@ -0,0 +1,23 @@ +Arrays of Objects +#include +using namespace std; +class MyClass { + int i; +public: + void setInt(int j) { + i=j; + } + int getInt() { + return i; + } +}; +int main() +{ + MyClass myObject[3]; + int i; + for(i=0; i<3; i++) + myObject[i].setInt(i+1); + for(i=0; i<3; i++) + cout << myObject[i].getInt() << "\n"; + return 0; +} diff --git a/c++/Others/Ask for a person's name, and generate a framed greeting.cpp b/c++/Others/Ask for a person's name, and generate a framed greeting.cpp new file mode 100644 index 0000000..ae1dc50 --- /dev/null +++ b/c++/Others/Ask for a person's name, and generate a framed greeting.cpp @@ -0,0 +1,25 @@ +Ask for a persons name, and generate a framed greeting +#include +#include + +int main() +{ + std::cout << "Please enter your first name: "; + std::string name; + std::cin >> name; + + const std::string greeting = "Hello, " + name + "!"; + const std::string spaces(greeting.size(), ' '); + const std::string second = "* " + spaces + " *"; + + const std::string first(second.size(), '*'); + + std::cout << std::endl; + std::cout << first << std::endl; + std::cout << second << std::endl; + std::cout << "* " << greeting << " *" << std::endl; + std::cout << second << std::endl; + std::cout << first << std::endl; + + return 0; +} diff --git a/c++/Others/Assign Items in int array to vector.cpp b/c++/Others/Assign Items in int array to vector.cpp new file mode 100644 index 0000000..930ae1a --- /dev/null +++ b/c++/Others/Assign Items in int array to vector.cpp @@ -0,0 +1,23 @@ +Assign Items in int array to vector +#include +#include +#include +#include // for accumulate +using namespace std; + +int main() +{ + int x[5] = {2, 3, 5, 7, 11}; + + vector vector1(&x[0], &x[5]); + + int sum = accumulate(vector1.begin(), vector1.end(), 0); + + cout << sum << endl; + return 0; +} + +/* +28 + + */ diff --git a/c++/Others/Assign elements in vector a value through an iterator.cpp b/c++/Others/Assign elements in vector a value through an iterator.cpp new file mode 100644 index 0000000..7d299ac --- /dev/null +++ b/c++/Others/Assign elements in vector a value through an iterator.cpp @@ -0,0 +1,24 @@ +Assign elements in vector a value through an iterator +#include +#include +#include +using namespace std; + +int main() +{ + vector v(10); // create a vector of length 10 + vector::iterator p; // create an iterator + int i; + + // assign elements in vector a value + p = v.begin(); + i = 0; + while(p != v.end()) { + *p = i + 'a'; + p++; + i++; + } + + + return 0; +} diff --git a/c++/Others/Assign object1 to object2.cpp b/c++/Others/Assign object1 to object2.cpp new file mode 100644 index 0000000..e281be5 --- /dev/null +++ b/c++/Others/Assign object1 to object2.cpp @@ -0,0 +1,44 @@ +Assign object1 to object2 +#include +using namespace std; + +class BaseClass { + int a; +public: + void load_a(int n) { + a = n; + } + int get_a() { + return a; + } +}; + +class DerivedClass : public BaseClass { + int b; +public: + void load_b(int n) { + b = n; + } + int get_b() { + return b; + } +}; + +int main() +{ + DerivedClass object1, object2; + + object1.load_a(5); + object1.load_b(10); + + + object2 = object1; + + cout << "Here is object1's a and b: "; + cout << object1.get_a() << ' ' << object1.get_b() << endl; + + cout << "Here is object2's a and b: "; + cout << object2.get_a() << ' ' << object2.get_b() << endl; + + return 0; +} diff --git a/c++/Others/Assign values using the member initialization syntax.cpp b/c++/Others/Assign values using the member initialization syntax.cpp new file mode 100644 index 0000000..bc88d55 --- /dev/null +++ b/c++/Others/Assign values using the member initialization syntax.cpp @@ -0,0 +1,25 @@ +Assign values using the member initialization syntax +#include + +using namespace std; + +class MyClass { + const int numA; // const member + const int numB; // const member +public: + // Initialize numA and numB using initialization syntax. + MyClass(int x, int y) : numA(x), numB(y) { } + int getNumA() { + return numA; + } + int getNumB() { + return numB; + } +}; +int main() +{ + MyClass object1(7, 9), object2(5, 2); + cout << "Values in object1 are " << object1.getNumB() << " and " << object1.getNumA() << endl; + cout << "Values in object2 are " << object2.getNumB() << " and " << object2.getNumA() << endl; + return 0; +} diff --git a/c++/Others/Assigning and Displaying Array Values.cpp b/c++/Others/Assigning and Displaying Array Values.cpp new file mode 100644 index 0000000..9057995 --- /dev/null +++ b/c++/Others/Assigning and Displaying Array Values.cpp @@ -0,0 +1,28 @@ +Assigning and Displaying Array Values +#include + +using namespace std; + +int main () +{ + int testScore[3]; + + cout << "Enter test score #1: "; + + cin >> testScore[0]; + + cout << "Enter test score #2: "; + + cin >> testScore[1]; + + cout << "Enter test score #3: "; + + cin >> testScore[2]; + + cout << "Test score #1: " << testScore[0] << endl; + + cout << "Test score #2: " << testScore[1] << endl; + + cout << "Test score #3: " << testScore[2] << endl; + return 0; +} diff --git a/c++/Others/Assigning deque objects..cpp b/c++/Others/Assigning deque objects..cpp new file mode 100644 index 0000000..3f989f3 --- /dev/null +++ b/c++/Others/Assigning deque objects..cpp @@ -0,0 +1,43 @@ +Assigning deque objects. +#include +#include +using namespace std; + +int main() +{ + deque dequeObject1(10), dequeObject2; + int i; + + for(i = 0; i <10; i++) + dequeObject1[i] = i + 'A'; + cout << "Contents of dequeObject1 are: "; + for(i = 0; i +#include +int Average(int i) +{ +static int sum = 0, count = 0; +sum = sum + i; +count++; +return sum / count; +} + +int main() +{ + +int num; +do{ + +cout<<"Enter numbers ( -1 to quit )"<>num; +/*if number is not -1 print the average*/ +if(num != -1) +cout<<"The average is "<-1); +return 0; +} diff --git a/c++/Others/Average.cpp b/c++/Others/Average.cpp new file mode 100644 index 0000000..3896680 --- /dev/null +++ b/c++/Others/Average.cpp @@ -0,0 +1,16 @@ +Average + +#include +#include +int main() +{ +int number1,number2,number3; +double average; + +cout<<"Enter three integers and I will display the average"<>number1>>number2>>number3; +average = (number1 + number2 + number3) / 3.0; +cout<<"The average is "< + + /** + * Implements an unbalanced Avl search tree. + * Note that all "matching" is based on the compares method. + */ + /** + * Construct the tree. + */ + template + AvlTree::AvlTree( const Comparable & notFound ) : + ITEM_NOT_FOUND( notFound ), root( NULL ) + { + } + + /** + * Copy constructor. + */ + template + AvlTree::AvlTree( const AvlTree & rhs ) : + ITEM_NOT_FOUND( rhs.ITEM_NOT_FOUND ), root( NULL ) + { + *this = rhs; + } + + /** + * Destructor for the tree. + */ + template + AvlTree::~AvlTree( ) + { + makeEmpty( ); + } + + /** + * Insert x into the tree; duplicates are ignored. + */ + template + void AvlTree::insert( const Comparable & x ) + { + insert( x, root ); + } + + /** + * Remove x from the tree. Nothing is done if x is not found. + */ + template + void AvlTree::remove( const Comparable & x ) + { + cout << "Sorry, remove unimplemented; " << x << + " still present" << endl; + } + + /** + * Find the smallest item in the tree. + * Return smallest item or ITEM_NOT_FOUND if empty. + */ + template + const Comparable & AvlTree::findMin( ) const + { + return elementAt( findMin( root ) ); + } + + /** + * Find the largest item in the tree. + * Return the largest item of ITEM_NOT_FOUND if empty. + */ + template + const Comparable & AvlTree::findMax( ) const + { + return elementAt( findMax( root ) ); + } + + /** + * Find item x in the tree. + * Return the matching item or ITEM_NOT_FOUND if not found. + */ + template + const Comparable & AvlTree:: + find( const Comparable & x ) const + { + return elementAt( find( x, root ) ); + } + + /** + * Make the tree logically empty. + */ + template + void AvlTree::makeEmpty( ) + { + makeEmpty( root ); + } + + /** + * Test if the tree is logically empty. + * Return true if empty, false otherwise. + */ + template + bool AvlTree::isEmpty( ) const + { + return root == NULL; + } + + /** + * Print the tree contents in sorted order. + */ + template + void AvlTree::printTree( ) const + { + if( isEmpty( ) ) + cout << "Empty tree" << endl; + else + printTree( root ); + } + + /** + * Deep copy. + */ + template + const AvlTree & + AvlTree:: + operator=( const AvlTree & rhs ) + { + if( this != &rhs ) + { + makeEmpty( ); + root = clone( rhs.root ); + } + return *this; + } + + /** + * Internal method to get element field in node t. + * Return the element field or ITEM_NOT_FOUND if t is NULL. + */ + template + const Comparable & AvlTree::elementAt( AvlNode *t ) const + { + if( t == NULL ) + return ITEM_NOT_FOUND; + else + return t->element; + } + + /** + * Internal method to insert into a subtree. + * x is the item to insert. + * t is the node that roots the tree. + */ + template + void AvlTree::insert( const Comparable & x, AvlNode * & t ) const + { + if( t == NULL ) + t = new AvlNode( x, NULL, NULL ); + else if( x < t->element ) + { + insert( x, t->left ); + if( height( t->left ) - height( t->right ) == 2 ) + if( x < t->left->element ) + rotateWithLeftChild( t ); + else + doubleWithLeftChild( t ); + } + else if( t->element < x ) + { + insert( x, t->right ); + if( height( t->right ) - height( t->left ) == 2 ) + if( t->right->element < x ) + rotateWithRightChild( t ); + else + doubleWithRightChild( t ); + } + else + ; // Duplicate; do nothing + t->height = max( height( t->left ), height( t->right ) ) + 1; + } + + /** + * Internal method to find the smallest item in a subtree t. + * Return node containing the smallest item. + */ + template + AvlNode * + AvlTree::findMin( AvlNode *t ) const + { + if( t == NULL) + return t; + + while( t->left != NULL ) + t = t->left; + return t; + } + + /** + * Internal method to find the largest item in a subtree t. + * Return node containing the largest item. + */ + template + AvlNode * + AvlTree::findMax( AvlNode *t ) const + { + if( t == NULL ) + return t; + + while( t->right != NULL ) + t = t->right; + return t; + } + + /** + * Internal method to find an item in a subtree. + * x is item to search for. + * t is the node that roots the tree. + * Return node containing the matched item. + */ + template + AvlNode * + AvlTree::find( const Comparable & x, AvlNode *t ) const + { + while( t != NULL ) + if( x < t->element ) + t = t->left; + else if( t->element < x ) + t = t->right; + else + return t; // Match + + return NULL; // No match + } + + /** + * Internal method to make subtree empty. + */ + template + void AvlTree::makeEmpty( AvlNode * & t ) const + { + if( t != NULL ) + { + makeEmpty( t->left ); + makeEmpty( t->right ); + delete t; + } + t = NULL; + } + + /** + * Internal method to clone subtree. + */ + template + AvlNode * + AvlTree::clone( AvlNode * t ) const + { + if( t == NULL ) + return NULL; + else + return new AvlNode( t->element, clone( t->left ), + clone( t->right ), t->height ); + } + + /** + * Return the height of node t or -1 if NULL. + */ + template + int AvlTree::height( AvlNode *t ) const + { + return t == NULL ? -1 : t->height; + } + + /** + * Return maximum of lhs and rhs. + */ + template + int AvlTree::max( int lhs, int rhs ) const + { + return lhs > rhs ? lhs : rhs; + } + + /** + * Rotate binary tree node with left child. + * For AVL trees, this is a single rotation for case 1. + * Update heights, then set new root. + */ + template + void AvlTree::rotateWithLeftChild( AvlNode * & k2 ) const + { + AvlNode *k1 = k2->left; + k2->left = k1->right; + k1->right = k2; + k2->height = max( height( k2->left ), height( k2->right ) ) + 1; + k1->height = max( height( k1->left ), k2->height ) + 1; + k2 = k1; + } + + /** + * Rotate binary tree node with right child. + * For AVL trees, this is a single rotation for case 4. + * Update heights, then set new root. + */ + template + void AvlTree::rotateWithRightChild( AvlNode * & k1 ) const + { + AvlNode *k2 = k1->right; + k1->right = k2->left; + k2->left = k1; + k1->height = max( height( k1->left ), height( k1->right ) ) + 1; + k2->height = max( height( k2->right ), k1->height ) + 1; + k1 = k2; + } + + /** + * Double rotate binary tree node: first left child. + * with its right child; then node k3 with new left child. + * For AVL trees, this is a double rotation for case 2. + * Update heights, then set new root. + */ + template + void AvlTree::doubleWithLeftChild( AvlNode * & k3 ) const + { + rotateWithRightChild( k3->left ); + rotateWithLeftChild( k3 ); + } + + /** + * Double rotate binary tree node: first right child. + * with its left child; then node k1 with new right child. + * For AVL trees, this is a double rotation for case 3. + * Update heights, then set new root. + */ + template + void AvlTree::doubleWithRightChild( AvlNode * & k1 ) const + { + rotateWithLeftChild( k1->right ); + rotateWithRightChild( k1 ); + } + + /** + * Internal method to print a subtree in sorted order. + * t points to the node that roots the tree. + */ + template + void AvlTree::printTree( AvlNode *t ) const + { + if( t != NULL ) + { + printTree( t->left ); + cout << t->element << endl; + printTree( t->right ); + } + } diff --git a/c++/Others/AvlTree.h - Header file for AVL tree.cpp b/c++/Others/AvlTree.h - Header file for AVL tree.cpp new file mode 100644 index 0000000..adf91fc --- /dev/null +++ b/c++/Others/AvlTree.h - Header file for AVL tree.cpp @@ -0,0 +1,86 @@ +AvlTree.h - Header file for AVL tree + + #ifndef AVL_TREE_H_ + #define AVL_TREE_H_ + + + // Node and forward declaration because g++ does + // not understand nested classes. + template + class AvlTree; + + template + class AvlNode + { + Comparable element; + AvlNode *left; + AvlNode *right; + int height; + + AvlNode( const Comparable & theElement, AvlNode *lt, AvlNode *rt, int h = 0 ) + : element( theElement ), left( lt ), right( rt ), height( h ) { } + friend class AvlTree; + }; + + #include "dsexceptions.h" + #include // For NULL + + // AvlTree class + // + // CONSTRUCTION: with ITEM_NOT_FOUND object used to signal failed finds + // + // ******************PUBLIC OPERATIONS********************* + // void insert( x ) --> Insert x + // void remove( x ) --> Remove x (unimplemented) + // Comparable find( x ) --> Return item that matches x + // Comparable findMin( ) --> Return smallest item + // Comparable findMax( ) --> Return largest item + // boolean isEmpty( ) --> Return true if empty; else false + // void makeEmpty( ) --> Remove all items + // void printTree( ) --> Print tree in sorted order + + template + class AvlTree + { + public: + explicit AvlTree( const Comparable & notFound ); + AvlTree( const AvlTree & rhs ); + ~AvlTree( ); + + const Comparable & findMin( ) const; + const Comparable & findMax( ) const; + const Comparable & find( const Comparable & x ) const; + bool isEmpty( ) const; + void printTree( ) const; + + void makeEmpty( ); + void insert( const Comparable & x ); + void remove( const Comparable & x ); + + const AvlTree & operator=( const AvlTree & rhs ); + + private: + AvlNode *root; + const Comparable ITEM_NOT_FOUND; + + const Comparable & elementAt( AvlNode *t ) const; + + void insert( const Comparable & x, AvlNode * & t ) const; + AvlNode * findMin( AvlNode *t ) const; + AvlNode * findMax( AvlNode *t ) const; + AvlNode * find( const Comparable & x, AvlNode *t ) const; + void makeEmpty( AvlNode * & t ) const; + void printTree( AvlNode *t ) const; + AvlNode * clone( AvlNode *t ) const; + + // Avl manipulations + int height( AvlNode *t ) const; + int max( int lhs, int rhs ) const; + void rotateWithLeftChild( AvlNode * & k2 ) const; + void rotateWithRightChild( AvlNode * & k1 ) const; + void doubleWithLeftChild( AvlNode * & k3 ) const; + void doubleWithRightChild( AvlNode * & k1 ) const; + }; + + #include "AvlTree.cpp" + #endif diff --git a/c++/Others/Banking Project.cpp b/c++/Others/Banking Project.cpp new file mode 100644 index 0000000..5596ecc --- /dev/null +++ b/c++/Others/Banking Project.cpp @@ -0,0 +1,518 @@ +Banking Project + +#include +#include +#include +#include +#include +#include +#include +#include +#include +#include + void punit (void); + void deposit(void); + void addrecord(); + void delrecord(); + void modrecord(); + void disprecord(); + void dispall(); + void withdraw(); + float w,z; + class account + { + int accountno,cls; + char name[30],type; + float deposit,withdraw; + public: + account() + { + deposit=withdraw=0; + } + int giveaccountno() + { + return accountno; + } + void getdata(int mrno) + { + accountno=mrno+1; + cout<<"ACCOUNT NUMBER :: "; + cout<>type; + cout<<" +"; + cout<<"ENTER INITIAL AMOUNT ::Rs ";cin>>deposit; + cout<<" +"; + } + void withdrawal(int m) + { + cout<<"AMOUNT BEFORE WITHDRAWING::Rs "<>menuch; + + switch(menuch) + { + + case 1:addrecord();break; + case 2:delrecord();break; + case 3:modrecord();break; + case 4:disprecord();break; + case 5:dispall();break; + case 6:withdraw();break; + case 7:deposit();break; + } + } + while(menuch!=8); + } + void addrecord() + { + account obj_1,obj_2; + fstream fout; + fout.open("banking.txt",ios::in|ios::binary); + if(!fout) + { + cout<<"FILE OPEN ERROR ";getch();return;} + int recsize=sizeof(account); + fout.seekg(0,ios::end); + fout.seekg(-1*recsize,ios::cur); + fout.read((char*)&obj_1,recsize); + int mrno=obj_1.giveaccountno(); + fout.close(); + clrscr(); + cout<<"ADD MENU + +"; + obj_2.getdata(mrno); + fout.open("banking.txt",ios::app|ios::binary); + if(!fout) + { + cout<<"FILE OPEN ERROR ";getch();return;} + fout.write((char*)&obj_2,recsize); + cout<<" + +RECORD ADDED TO DATABASE"<<" + Press any key to +continue... "; + getch(); + fout.close(); + } + void dispall() + { + account obj_3; + fstream fout; + int recsize=sizeof(account); + int countrec=0; + clrscr(); + cout<<" +DISPLAY ALL MENU + "; + fout.open("banking.txt",ios::in); + if(!fout) + { + cout<<"FILE OPEN ERROR ";getch();return;} + while(fout.read((char*)&obj_3,recsize)) + { + obj_3.dispdata(); + countrec++; + cout<<" + PRESS ANY KEY FOR NEXT...."; + getch(); + } + clrscr(); + cout<<" + +END OF FILE.TOTALNUMBER OF RECORDS..."<>mrno; + while(fout.read((char*)&obj_4,recsize)) + { + if (obj_4.giveaccountno()==mrno) +{ + obj_4.dispdata(); + cout<<" + +Press any key....."; + flag=1;break; + } + } + if(flag==0) + { + cout<<" + +NO SUCH ACCOUNT EXIST "; + cout<<" + +Press any key......"; + } + getch(); + fout.close(); + } + void delrecord() + { + account obj_5; + fstream fout,temp; + int mrno,flag; + int recsize=sizeof(account); + clrscr(); + cout<<" + + CLOSE ACCOUNT MENU + "; + fout.open("banking.txt",ios::in); + if(!fout) + { + cout<<"FILE OPEN ERROR "; + getch(); + return; + } + temp.open("temp.txt",ios::app|ios::binary); + if(!temp) + { + cout<<"FILE OPEN ERROR "; + getch(); + return; + } + cout<<" + + ENTER THE ACCOUNT NUMBER "; + cin>>mrno; + while(fout.read((char*)&obj_5,recsize)) + { + if(obj_5.giveaccountno()==mrno) + { + obj_5.dispdata(); + char confirm; + cout<<" + +ARE YOU SURE TO DELETE IT(Y/N)..";cin>>confirm; + if(confirm=='Y'||confirm=='y') + { + fout.read((char*)&obj_5,recsize); + cout<<" + +RECORD DELETED FORM DATABASE +"; + cout<<"press any key...."; + flag=1; + if(!fout) + break; + } + flag=1; + } + temp.write((char*)&obj_5,recsize);} + fout.close(); + temp.close(); + remove("banking.txt"); + rename("temp.txt","banking.txt"); + if(flag==0) + { + cout<<" + +NO SUCH ACCOUNT EXIST"; + cout<<"Press any key....."; + } + getch(); + } + void modrecord() + { + account obj_6; + fstream fout; + int mrno,flag=0; + int recsize=sizeof(account); + clrscr(); + cout<<" +MODIFY RECORD MENU + "; + fout.open("banking.txt",ios::in|ios::out|ios::binary); + if(!fout) + { + cout<<"FILE OPEN ERROR "; + getch(); + return; + } + fout.seekg(ios::beg); + cout<<" +ENTER RECORD NUMBER "; + cin>>mrno; + while(fout.read((char*)&obj_6,recsize)) + { + if(obj_6.giveaccountno()==mrno) + { + clrscr(); + cout<<" + +MODIFY MENU + +"; + obj_6.dispdata(); + int tmprno=obj_6.giveaccountno()-1; + account obj_7; + cout<<" + + ENTER NEW DATA +"; + obj_7.getdata(tmprno); + char confirm; + cout<<" + + ARE YOU SURE(Y/N) +"; + cin>>confirm; + if(confirm=='Y'||confirm=='y') + { + fout.seekg(-1*recsize,ios::cur); + fout.write((char*)&obj_7,recsize); + cout<<" + + RECORD MODIFIED + "; + cout<<"Press any key....."; + flag=1; + } + } + if(flag==0) + { + cout<<"NO SUCH RECORD EXIST +"; + cout<<"Press any key....."; + } + } + fout.close(); + getch(); + } + void withdraw() + { + account obj_9; + fstream fout; + int mrno=0; + int recsize=sizeof(account); + clrscr(); + cout<<" + +WITHDRAWAL MENU +"; + fout.open("banking.txt",ios::in|ios::out|ios::binary); + if(!fout) + { + cout<<"FILE OPEN ERROR ";getch();return;} + fout.seekg(ios::beg); + cout<<" +ENTER ACCOUNT NUMBER "; + cin>>mrno; + while(fout.read((char*)&obj_9,recsize)) + { + if(obj_9.giveaccountno()==mrno) + { + clrscr(); + cout<<" + +ENTER THE AMOUNT TO BE WITHDRAWED::Rs "; + cin>>w; + obj_9.withdrawal(w); + fout.seekg(-1*recsize,ios::cur); + fout.write((char*)&obj_9,recsize); + } + } + fout.close(); + getch(); + } + void punit(void) + { + + int gd=5, gm, errorcode; + int col,i=0,j; + initgraph(&gd, &gm, "c:\tc\bgi"); + while(5*i<=700) + { + setbkcolor(1); + setcolor(3); + rectangle(0+5*i,0+5*i,getmaxx()-5*i,getmaxy()-5*i); + i++; + } + i=0; + setcolor(4); + settextstyle(1,0,6); + + sleep(5); + cleardevice(); + while(5*i<=700) + { + setbkcolor(1); + setcolor(3); + circle(getmaxx()/2,getmaxy()/2,i*5); + i++; + } + setcolor(4); + settextstyle(0,0,6); + outtextxy(190 ,getmaxy()/2-85,"PROJECT"); + outtextxy(300,getmaxy()/2-25,"ON"); + + outtextxy(190,getmaxy()/2+25,"BANKING"); + sleep(3); + i=0; + while(i<=130) + { + setbkcolor(1); + setcolor(3); + line(i*3,0,i*3,getmaxy()); + line(getmaxx()-i*3,0,getmaxx()-i*3,getmaxy()); + i++; + } + sleep(1); + i=getmaxy(); + while(i>0) + { + line(getmaxx()/2,getmaxy(),getmaxx(),i-=10); + delay(10); + } + i=getmaxx(); + while(i>0) + { + line(getmaxx()/2,getmaxy(),i-=10,0); + delay(10); + } + i=0; + while(i>mrno; + while(fout.read((char*)&obj_10,recsize)) + { + if(obj_10.giveaccountno()==mrno) + { + clrscr(); + cout<<" + +ENTER THE AMOUNT TO BE DEPOSITED ::Rs "; + cin>>w; + obj_10.deposital(w); + fout.seekg(-1*recsize,ios::cur); + fout.write((char*)&obj_10,recsize); + } + } + fout.close(); + getch(); + } diff --git a/c++/Others/Binary Search Tree Program.cpp b/c++/Others/Binary Search Tree Program.cpp new file mode 100644 index 0000000..b5be1d4 --- /dev/null +++ b/c++/Others/Binary Search Tree Program.cpp @@ -0,0 +1,288 @@ +Binary Search Tree Program + +#include +#include +using namespace std; + +class BinarySearchTree +{ + private: + struct tree_node + { + tree_node* left; + tree_node* right; + int data; + }; + tree_node* root; + public: + BinarySearchTree() + { + root = NULL; + } + bool isEmpty() const { return root==NULL; } + void print_inorder(); + void inorder(tree_node*); + void print_preorder(); + void preorder(tree_node*); + void print_postorder(); + void postorder(tree_node*); + void insert(int); + void remove(int); +}; + +// Smaller elements go left +// larger elements go right +void BinarySearchTree::insert(int d) +{ + tree_node* t = new tree_node; + tree_node* parent; + t->data = d; + t->left = NULL; + t->right = NULL; + parent = NULL; + // is this a new tree? + if(isEmpty()) root = t; + else + { + //Note: ALL insertions are as leaf nodes + tree_node* curr; + curr = root; + // Find the Node's parent + while(curr) + { + parent = curr; + if(t->data > curr->data) curr = curr->right; + else curr = curr->left; + } + + if(t->data < parent->data) + parent->left = t; + else + parent->right = t; + } +} + +void BinarySearchTree::remove(int d) +{ + //Locate the element + bool found = false; + if(isEmpty()) + { + cout<<" This Tree is empty! "<data == d) + { + found = true; + break; + } + else + { + parent = curr; + if(d>curr->data) curr = curr->right; + else curr = curr->left; + } + } + if(!found) + { + cout<<" Data not found! "<left == NULL && curr->right != NULL)|| (curr->left != NULL +&& curr->right == NULL)) + { + if(curr->left == NULL && curr->right != NULL) + { + if(parent->left == curr) + { + parent->left = curr->right; + delete curr; + } + else + { + parent->right = curr->right; + delete curr; + } + } + else // left child present, no right child + { + if(parent->left == curr) + { + parent->left = curr->left; + delete curr; + } + else + { + parent->right = curr->left; + delete curr; + } + } + return; + } + + //We're looking at a leaf node + if( curr->left == NULL && curr->right == NULL) + { + if(parent->left == curr) parent->left = NULL; + else parent->right = NULL; + delete curr; + return; + } + + + //Node with 2 children + // replace node with smallest value in right subtree + if (curr->left != NULL && curr->right != NULL) + { + tree_node* chkr; + chkr = curr->right; + if((chkr->left == NULL) && (chkr->right == NULL)) + { + curr = chkr; + delete chkr; + curr->right = NULL; + } + else // right child has children + { + //if the node's right child has a left child + // Move all the way down left to locate smallest element + + if((curr->right)->left != NULL) + { + tree_node* lcurr; + tree_node* lcurrp; + lcurrp = curr->right; + lcurr = (curr->right)->left; + while(lcurr->left != NULL) + { + lcurrp = lcurr; + lcurr = lcurr->left; + } + curr->data = lcurr->data; + delete lcurr; + lcurrp->left = NULL; + } + else + { + tree_node* tmp; + tmp = curr->right; + curr->data = tmp->data; + curr->right = tmp->right; + delete tmp; + } + + } + return; + } + +} + +void BinarySearchTree::print_inorder() +{ + inorder(root); +} + +void BinarySearchTree::inorder(tree_node* p) +{ + if(p != NULL) + { + if(p->left) inorder(p->left); + cout<<" "<data<<" "; + if(p->right) inorder(p->right); + } + else return; +} + +void BinarySearchTree::print_preorder() +{ + preorder(root); +} + +void BinarySearchTree::preorder(tree_node* p) +{ + if(p != NULL) + { + cout<<" "<data<<" "; + if(p->left) preorder(p->left); + if(p->right) preorder(p->right); + } + else return; +} + +void BinarySearchTree::print_postorder() +{ + postorder(root); +} + +void BinarySearchTree::postorder(tree_node* p) +{ + if(p != NULL) + { + if(p->left) postorder(p->left); + if(p->right) postorder(p->right); + cout<<" "<data<<" "; + } + else return; +} + +int main() +{ + BinarySearchTree b; + int ch,tmp,tmp1; + while(1) + { + cout<>ch; + switch(ch) + { + case 1 : cout<<" Enter Number to be inserted : "; + cin>>tmp; + b.insert(tmp); + break; + case 2 : cout<>tmp1; + b.remove(tmp1); + break; + case 6 : system("pause"); + return 0; + break; + } + } +} diff --git a/c++/Others/Binary Search Tree.cpp b/c++/Others/Binary Search Tree.cpp new file mode 100644 index 0000000..a531800 --- /dev/null +++ b/c++/Others/Binary Search Tree.cpp @@ -0,0 +1,129 @@ +Binary Search Tree + +#include +#include +#include + +struct tree + { + int data; + tree *left; + tree *right; + }*sptr,*q; + void rightcheck(); + void leftcheck(); + void search(); + + int insdata; + tree *node; + void main() + { + clrscr(); + node=new tree; + cout<<" PLEASE PUT THE root->>"; + cin>>node->data; + sptr=node; + q=sptr; + node->left=NULL; + node->right=NULL; + cout<<" GIVE THE child->>"; + cin>>insdata; + search(); + while(insdata!=0) + { + if(insdata>sptr->data) + rightcheck(); + else + leftcheck(); + cout<<" GIVE THE child->>"; + cin>>insdata; + search(); + sptr=node; + } + getch(); + } + void rightcheck() + { + if(sptr->right==NULL) + { + cout<<" "<data<right=new tree; + sptr=sptr->right; + sptr->data=insdata; + sptr->left=NULL; + sptr->right=NULL; + q=node; + } + else + { + if(insdata>sptr->data) + { + sptr=sptr->right; + q=sptr; + if(insdata>sptr->data) + rightcheck(); + else + leftcheck(); + } + else + { + sptr=sptr->left; + q=sptr; + leftcheck(); + } + } + } + void leftcheck() + { + if(sptr->left==NULL) + { + cout<<" "<data<left=new tree; + sptr=sptr->left; + sptr->data=insdata; + sptr->right=NULL; + sptr->left=NULL; + q=node; + } + else{ + if(insdatadata) + { + sptr=sptr->left; + q=sptr; + if(insdata>sptr->data) + rightcheck(); + else + leftcheck(); + } + else + { + sptr=sptr->right; + q=sptr; + rightcheck();} + } + } + + void search() + { + sptr=node; + while(sptr!=NULL) + { + if(insdata==sptr->data) + { + cout<<"This is not insertable."; + cout<<"\nInsert child "; + cin>>insdata; + search(); + break; + } + else + { + if(insdata>sptr->data) + sptr=sptr->right; + else + sptr=sptr->left; + } + } + sptr=node; + + } diff --git a/c++/Others/Binary arithmatic.cpp b/c++/Others/Binary arithmatic.cpp new file mode 100644 index 0000000..d155975 --- /dev/null +++ b/c++/Others/Binary arithmatic.cpp @@ -0,0 +1,194 @@ +Binary arithmatic + +#include +#include +#include +#include + +void b_to_d(char result[]); //binary to decimal +void d_to_b(int dec,char binary[]); // decimal to binary + +main() +{ + int ch,n1,n2,i=0,j,k,l,carry,r,x1,x2,x; + char bn1[30],bn2[30],result[30],binary[30]; + char multi[30][30]; + clrscr(); + do + { + printf("<1> input first operand \n"); + printf("<2> input second operand \n"); + printf("<3> binary addition \n"); + printf("<4> binary subtraction \n"); + printf("<5> binary multiplation \n"); + printf("<6> result to decimal \n"); + printf("<7> Exit \n\n"); + do + { + printf("enter your choice "); + scanf("%d",&ch); + }while(ch>7 || ch<1); + switch (ch) + { + case 1: + printf("\n input first operand "); + scanf("%d",&n1); + x1=n1; + d_to_b(n1,binary); + for(i=0;binary[i]!='\0';++i) + bn1[i]=binary[i]; + bn1[i]='\0'; + break; + case 2: + printf("\n input second operand "); + scanf("%d",&n2); + x2=n2; + d_to_b(n2,binary); + for(i=0;binary[i]!='\0';++i) + bn2[i]=binary[i]; + bn2[i]='\0'; + break; + case 3: //addition + for(i=0;i<30;++i) //reset result + result[i]='\0'; + carry=0; + if(strlen(bn1)1) + carry=1; + else + carry=0; + if(carry==1) + result[i+1]=carry+48; + } + printf("\n%s\n",strrev(result)); + break; + case 4: //subtraction + for(i=0;i<30;++i) //reset result + result[i]='\0'; + carry=0; + if(strlen(bn1)1) + multi[0][i+1]+=((multi[0][i]-(multi[0][i]%2))/2); + printf("\n"); + for(i=29;i>=0;--i) // excluding first zero's (0's) of array + if(multi[0][i]!=0) + break; + j=0; + for(;i>=0;--i) // final calculations and print + if(multi[0][i]<48) + { + multi[0][i]%=2; + result[j++]=multi[0][i]+48; + // printf("%d",multi[0][i]); + } + printf("\n"); + printf("%s\n",result); + break; + case 6: //result in decimal + b_to_d(result); + printf("\n"); + break; + } + n1=x1; + d_to_b(n1,binary); + for(i=0;binary[i]!='\0';++i) + bn1[i]=binary[i]; + bn1[i]='\0'; + + n2=x2; + d_to_b(n2,binary); + for(i=0;binary[i]!='\0';++i) + bn2[i]=binary[i]; + bn2[i]='\0'; + + }while(ch!=7); + printf("\n\n i will wait for your mails"); + getch(); + return 0; +} + +void b_to_d(char result[]) //binary to decimal +{ + short int i; + long int dec=0; + strrev(result); + for(i=0;i0) + { + binary[i++]=dec%2+48; + binary[i]='\0'; + dec-=(dec%2); + dec/=2; + } +} diff --git a/c++/Others/BinaryHeap.cpp - Implementation for binary heap.cpp b/c++/Others/BinaryHeap.cpp - Implementation for binary heap.cpp new file mode 100644 index 0000000..4ab99f2 --- /dev/null +++ b/c++/Others/BinaryHeap.cpp - Implementation for binary heap.cpp @@ -0,0 +1,135 @@ +BinaryHeap.cpp - Implementation for binary heap + + #include "BinaryHeap.h" + + /** + * Construct the binary heap. + * capacity is the capacity of the binary heap. + */ + template + BinaryHeap::BinaryHeap( int capacity ) + : array( capacity + 1 ), currentSize( 0 ) + { + } + + /** + * Insert item x into the priority queue, maintaining heap order. + * Duplicates are allowed. + * Throw Overflow if container is full. + */ + template + void BinaryHeap::insert( const Comparable & x ) + { + if( isFull( ) ) + throw Overflow( ); + + // Percolate up + int hole = ++currentSize; + for( ; hole > 1 && x < array[ hole / 2 ]; hole /= 2 ) + array[ hole ] = array[ hole / 2 ]; + array[ hole ] = x; + } + + /** + * Find the smallest item in the priority queue. + * Return the smallest item, or throw Underflow if empty. + */ + template + const Comparable & BinaryHeap::findMin( ) const + { + if( isEmpty( ) ) + throw Underflow( ); + return array[ 1 ]; + } + + /** + * Remove the smallest item from the priority queue. + * Throw Underflow if empty. + */ + template + void BinaryHeap::deleteMin( ) + { + if( isEmpty( ) ) + throw Underflow( ); + + array[ 1 ] = array[ currentSize-- ]; + percolateDown( 1 ); + } + + /** + * Remove the smallest item from the priority queue + * and place it in minItem. Throw Underflow if empty. + */ + template + void BinaryHeap::deleteMin( Comparable & minItem ) + { + if( isEmpty( ) ) + throw Underflow( ); + + minItem = array[ 1 ]; + array[ 1 ] = array[ currentSize-- ]; + percolateDown( 1 ); + } + + /** + * Establish heap order property from an arbitrary + * arrangement of items. Runs in linear time. + */ + template + void BinaryHeap::buildHeap( ) + { + for( int i = currentSize / 2; i > 0; i-- ) + percolateDown( i ); + } + + /** + * Test if the priority queue is logically empty. + * Return true if empty, false otherwise. + */ + template + bool BinaryHeap::isEmpty( ) const + { + return currentSize == 0; + } + + /** + * Test if the priority queue is logically full. + * Return true if full, false otherwise. + */ + template + bool BinaryHeap::isFull( ) const + { + return currentSize == array.size( ) - 1; + } + + /** + * Make the priority queue logically empty. + */ + template + void BinaryHeap::makeEmpty( ) + { + currentSize = 0; + } + + /** + * Internal method to percolate down in the heap. + * hole is the index at which the percolate begins. + */ + template + void BinaryHeap::percolateDown( int hole ) + { +/* 1*/ int child; +/* 2*/ Comparable tmp = array[ hole ]; + +/* 3*/ for( ; hole * 2 <= currentSize; hole = child ) + { +/* 4*/ child = hole * 2; +/* 5*/ if( child != currentSize && array[ child + 1 ] < array[ child ] ) +/* 6*/ child++; +/* 7*/ if( array[ child ] < tmp ) +/* 8*/ array[ hole ] = array[ child ]; + else +/* 9*/ break; + } +/*10*/ array[ hole ] = tmp; + } diff --git a/c++/Others/BinaryHeap.h - Header file for binary heap.cpp b/c++/Others/BinaryHeap.h - Header file for binary heap.cpp new file mode 100644 index 0000000..b20573f --- /dev/null +++ b/c++/Others/BinaryHeap.h - Header file for binary heap.cpp @@ -0,0 +1,47 @@ +BinaryHeap.h - Header file for binary heap + + #ifndef BINARY_HEAP_H_ + #define BINARY_HEAP_H_ + + #include "dsexceptions.h" + #include "vector.h" + + // BinaryHeap class + // + // CONSTRUCTION: with an optional capacity (that defaults to 100) + // + // ******************PUBLIC OPERATIONS********************* + // void insert( x ) --> Insert x + // deleteMin( minItem ) --> Remove (and optionally return) smallest item + // Comparable findMin( ) --> Return smallest item + // bool isEmpty( ) --> Return true if empty; else false + // bool isFull( ) --> Return true if full; else false + // void makeEmpty( ) --> Remove all items + // ******************ERRORS******************************** + // Throws Underflow and Overflow as warranted + + template + class BinaryHeap + { + public: + explicit BinaryHeap( int capacity = 100 ); + + bool isEmpty( ) const; + bool isFull( ) const; + const Comparable & findMin( ) const; + + void insert( const Comparable & x ); + void deleteMin( ); + void deleteMin( Comparable & minItem ); + void makeEmpty( ); + + private: + int currentSize; // Number of elements in heap + vector array; // The heap array + + void buildHeap( ); + void percolateDown( int hole ); + }; + + #include "BinaryHeap.cpp" + #endif diff --git a/c++/Others/BinarySearchTree.cpp - Implementation for binary search tree.cpp b/c++/Others/BinarySearchTree.cpp - Implementation for binary search tree.cpp new file mode 100644 index 0000000..44e65cc --- /dev/null +++ b/c++/Others/BinarySearchTree.cpp - Implementation for binary search tree.cpp @@ -0,0 +1,309 @@ +BinarySearchTree.cpp - Implementation for binary search tree + + #include "BinarySearchTree.h" + #include + + /** + * Implements an unbalanced binary search tree. + * Note that all "matching" is based on the < method. + */ + + /** + * Construct the tree. + */ + template + BinarySearchTree::BinarySearchTree( const Comparable & notFound ) : + root( NULL ), ITEM_NOT_FOUND( notFound ) + { + } + + + /** + * Copy constructor. + */ + template + BinarySearchTree:: + BinarySearchTree( const BinarySearchTree & rhs ) : + root( NULL ), ITEM_NOT_FOUND( rhs.ITEM_NOT_FOUND ) + { + *this = rhs; + } + + /** + * Destructor for the tree. + */ + template + BinarySearchTree::~BinarySearchTree( ) + { + makeEmpty( ); + } + + /** + * Insert x into the tree; duplicates are ignored. + */ + template + void BinarySearchTree::insert( const Comparable & x ) + { + insert( x, root ); + } + + /** + * Remove x from the tree. Nothing is done if x is not found. + */ + template + void BinarySearchTree::remove( const Comparable & x ) + { + remove( x, root ); + } + + + /** + * Find the smallest item in the tree. + * Return smallest item or ITEM_NOT_FOUND if empty. + */ + template + const Comparable & BinarySearchTree::findMin( ) const + { + return elementAt( findMin( root ) ); + } + + /** + * Find the largest item in the tree. + * Return the largest item of ITEM_NOT_FOUND if empty. + */ + template + const Comparable & BinarySearchTree::findMax( ) const + { + return elementAt( findMax( root ) ); + } + + /** + * Find item x in the tree. + * Return the matching item or ITEM_NOT_FOUND if not found. + */ + template + const Comparable & BinarySearchTree:: + find( const Comparable & x ) const + { + return elementAt( find( x, root ) ); + } + + /** + * Make the tree logically empty. + */ + template + void BinarySearchTree::makeEmpty( ) + { + makeEmpty( root ); + } + + /** + * Test if the tree is logically empty. + * Return true if empty, false otherwise. + */ + template + bool BinarySearchTree::isEmpty( ) const + { + return root == NULL; + } + + /** + * Print the tree contents in sorted order. + */ + template + void BinarySearchTree::printTree( ) const + { + if( isEmpty( ) ) + cout << "Empty tree" << endl; + else + printTree( root ); + } + + /** + * Deep copy. + */ + template + const BinarySearchTree & + BinarySearchTree:: + operator=( const BinarySearchTree & rhs ) + { + if( this != &rhs ) + { + makeEmpty( ); + root = clone( rhs.root ); + } + return *this; + } + + /** + * Internal method to get element field in node t. + * Return the element field or ITEM_NOT_FOUND if t is NULL. + */ + template + const Comparable & BinarySearchTree:: + elementAt( BinaryNode *t ) const + { + if( t == NULL ) + return ITEM_NOT_FOUND; + else + return t->element; + } + + /** + * Internal method to insert into a subtree. + * x is the item to insert. + * t is the node that roots the tree. + * Set the new root. + */ + template + void BinarySearchTree:: + insert( const Comparable & x, BinaryNode * & t ) const + { + if( t == NULL ) + t = new BinaryNode( x, NULL, NULL ); + else if( x < t->element ) + insert( x, t->left ); + else if( t->element < x ) + insert( x, t->right ); + else + ; // Duplicate; do nothing + } + + /** + * Internal method to remove from a subtree. + * x is the item to remove. + * t is the node that roots the tree. + * Set the new root. + */ + template + void BinarySearchTree:: + remove( const Comparable & x, BinaryNode * & t ) const + { + if( t == NULL ) + return; // Item not found; do nothing + if( x < t->element ) + remove( x, t->left ); + else if( t->element < x ) + remove( x, t->right ); + else if( t->left != NULL && t->right != NULL ) // Two children + { + t->element = findMin( t->right )->element; + remove( t->element, t->right ); + } + else + { + BinaryNode *oldNode = t; + t = ( t->left != NULL ) ? t->left : t->right; + delete oldNode; + } + } + + /** + * Internal method to find the smallest item in a subtree t. + * Return node containing the smallest item. + */ + template + BinaryNode * + BinarySearchTree::findMin( BinaryNode *t ) const + { + if( t == NULL ) + return NULL; + if( t->left == NULL ) + return t; + return findMin( t->left ); + } + + /** + * Internal method to find the largest item in a subtree t. + * Return node containing the largest item. + */ + template + BinaryNode * + BinarySearchTree::findMax( BinaryNode *t ) const + { + if( t != NULL ) + while( t->right != NULL ) + t = t->right; + return t; + } + + /** + * Internal method to find an item in a subtree. + * x is item to search for. + * t is the node that roots the tree. + * Return node containing the matched item. + */ + template + BinaryNode * + BinarySearchTree:: + find( const Comparable & x, BinaryNode *t ) const + { + if( t == NULL ) + return NULL; + else if( x < t->element ) + return find( x, t->left ); + else if( t->element < x ) + return find( x, t->right ); + else + return t; // Match + } +/****** NONRECURSIVE VERSION************************* + template + BinaryNode * + BinarySearchTree:: + find( const Comparable & x, BinaryNode *t ) const + { + while( t != NULL ) + if( x < t->element ) + t = t->left; + else if( t->element < x ) + t = t->right; + else + return t; // Match + + return NULL; // No match + } +*****************************************************/ + + /** + * Internal method to make subtree empty. + */ + template + void BinarySearchTree:: + makeEmpty( BinaryNode * & t ) const + { + if( t != NULL ) + { + makeEmpty( t->left ); + makeEmpty( t->right ); + delete t; + } + t = NULL; + } + + /** + * Internal method to print a subtree rooted at t in sorted order. + */ + template + void BinarySearchTree::printTree( BinaryNode *t ) const + { + if( t != NULL ) + { + printTree( t->left ); + cout << t->element << endl; + printTree( t->right ); + } + } + + /** + * Internal method to clone subtree. + */ + template + BinaryNode * + BinarySearchTree::clone( BinaryNode * t ) const + { + if( t == NULL ) + return NULL; + else + return new BinaryNode( t->element, clone( t->left ), clone( t->right ) ); + } diff --git a/c++/Others/BinarySearchTree.h - Header file for binary search tree.cpp b/c++/Others/BinarySearchTree.h - Header file for binary search tree.cpp new file mode 100644 index 0000000..73984ef --- /dev/null +++ b/c++/Others/BinarySearchTree.h - Header file for binary search tree.cpp @@ -0,0 +1,78 @@ +BinarySearchTree.h - Header file for binary search tree + + #ifndef BINARY_SEARCH_TREE_H_ + #define BINARY_SEARCH_TREE_H_ + + #include "dsexceptions.h" + #include // For NULL + + // Binary node and forward declaration because g++ does + // not understand nested classes. + template + class BinarySearchTree; + + template + class BinaryNode + { + Comparable element; + BinaryNode *left; + BinaryNode *right; + + BinaryNode( const Comparable & theElement, BinaryNode *lt, BinaryNode *rt ) + : element( theElement ), left( lt ), right( rt ) { } + friend class BinarySearchTree; + }; + + + // BinarySearchTree class + // + // CONSTRUCTION: with ITEM_NOT_FOUND object used to signal failed finds + // + // ******************PUBLIC OPERATIONS********************* + // void insert( x ) --> Insert x + // void remove( x ) --> Remove x + // Comparable find( x ) --> Return item that matches x + // Comparable findMin( ) --> Return smallest item + // Comparable findMax( ) --> Return largest item + // boolean isEmpty( ) --> Return true if empty; else false + // void makeEmpty( ) --> Remove all items + // void printTree( ) --> Print tree in sorted order + + template + class BinarySearchTree + { + public: + explicit BinarySearchTree( const Comparable & notFound ); + BinarySearchTree( const BinarySearchTree & rhs ); + ~BinarySearchTree( ); + + const Comparable & findMin( ) const; + const Comparable & findMax( ) const; + const Comparable & find( const Comparable & x ) const; + bool isEmpty( ) const; + void printTree( ) const; + + void makeEmpty( ); + void insert( const Comparable & x ); + void remove( const Comparable & x ); + + const BinarySearchTree & operator=( const BinarySearchTree & rhs ); + + private: + BinaryNode *root; + const Comparable ITEM_NOT_FOUND; + + const Comparable & elementAt( BinaryNode *t ) const; + + void insert( const Comparable & x, BinaryNode * & t ) const; + void remove( const Comparable & x, BinaryNode * & t ) const; + BinaryNode * findMin( BinaryNode *t ) const; + BinaryNode * findMax( BinaryNode *t ) const; + BinaryNode * find( const Comparable & x, BinaryNode *t ) const; + void makeEmpty( BinaryNode * & t ) const; + void printTree( BinaryNode *t ) const; + BinaryNode * clone( BinaryNode *t ) const; + }; + + #include "BinarySearchTree.cpp" + #endif diff --git a/c++/Others/BinomialQueue.cpp - Implementation for binomial queue.cpp b/c++/Others/BinomialQueue.cpp - Implementation for binomial queue.cpp new file mode 100644 index 0000000..e2fae1b --- /dev/null +++ b/c++/Others/BinomialQueue.cpp - Implementation for binomial queue.cpp @@ -0,0 +1,301 @@ +BinomialQueue.cpp - Implementation for binomial queue + + #include "BinomialQueue.h" + #include "dsexceptions.h" + + static const int MAX_TREES = 14; + + /** + * Construct the binomial queue. + */ + template + BinomialQueue::BinomialQueue( ) : theTrees( MAX_TREES ) + { + for( int i = 0; i < theTrees.size( ); i++ ) + theTrees[ i ] = NULL; + currentSize = 0; + } + + /** + * Copy constructor is left as an exercise. + */ + template + BinomialQueue:: + BinomialQueue( const BinomialQueue & rhs ) + { + cout << "Copy constructor is unimplemented" << endl; + } + + /** + * Destroy the binomial queue. + */ + template + BinomialQueue::~BinomialQueue( ) + { + makeEmpty( ); + } + + /** + * Merge rhs into the priority queue. + * rhs becomes empty. rhs must be different from this. + * Throw Overflow if result exceeds capacity. + */ + template + void BinomialQueue::merge( BinomialQueue & rhs ) + { + if( this == &rhs ) // Avoid aliasing problems + return; + + if( currentSize + rhs.currentSize > capacity( ) ) + throw Overflow( ); + + currentSize += rhs.currentSize; + + BinomialNode *carry = NULL; + for( int i = 0, j = 1; j <= currentSize; i++, j *= 2 ) + { + BinomialNode *t1 = theTrees[ i ]; + BinomialNode *t2 = rhs.theTrees[ i ]; + + int whichCase = t1 == NULL ? 0 : 1; + whichCase += t2 == NULL ? 0 : 2; + whichCase += carry == NULL ? 0 : 4; + + switch( whichCase ) + { + case 0: /* No trees */ + case 1: /* Only this */ + break; + case 2: /* Only rhs */ + theTrees[ i ] = t2; + rhs.theTrees[ i ] = NULL; + break; + case 4: /* Only carry */ + theTrees[ i ] = carry; + carry = NULL; + break; + case 3: /* this and rhs */ + carry = combineTrees( t1, t2 ); + theTrees[ i ] = rhs.theTrees[ i ] = NULL; + break; + case 5: /* this and carry */ + carry = combineTrees( t1, carry ); + theTrees[ i ] = NULL; + break; + case 6: /* rhs and carry */ + carry = combineTrees( t2, carry ); + rhs.theTrees[ i ] = NULL; + break; + case 7: /* All three */ + theTrees[ i ] = carry; + carry = combineTrees( t1, t2 ); + rhs.theTrees[ i ] = NULL; + break; + } + } + + for( int k = 0; k < rhs.theTrees.size( ); k++ ) + rhs.theTrees[ k ] = NULL; + rhs.currentSize = 0; + } + + /** + * Return the result of merging equal-sized t1 and t2. + */ + template + BinomialNode * + BinomialQueue::combineTrees( BinomialNode *t1, + BinomialNode *t2 ) const + { + if( t2->element < t1->element ) + return combineTrees( t2, t1 ); + t2->nextSibling = t1->leftChild; + t1->leftChild = t2; + return t1; + } + + /** + * Insert item x into the priority queue, maintaining heap order. + * This implementation is not optimized for O(1) performance. + * Throw Overflow if capacity exceeded. + */ + template + void BinomialQueue::insert( const Comparable & x ) + { + BinomialQueue oneItem; + oneItem.currentSize = 1; + oneItem.theTrees[ 0 ] = new BinomialNode( x, NULL, NULL ); + + merge( oneItem ); + } + + /** + * Return the smallest item in the priority queue. + * Throw Underflow if empty. + */ + template + const Comparable & BinomialQueue::findMin( ) const + { + if( isEmpty( ) ) + throw Underflow( ); + + return theTrees[ findMinIndex( ) ]->element; + } + + + /** + * Find index of tree containing the smallest item in the priority queue. + * The priority queue must not be empty. + * Return the index of tree containing the smallest item. + */ + template + int BinomialQueue::findMinIndex( ) const + { + int i; + int minIndex; + + for( i = 0; theTrees[ i ] == NULL; i++ ) + ; + + for( minIndex = i; i < theTrees.size( ); i++ ) + if( theTrees[ i ] != NULL && + theTrees[ i ]->element < theTrees[ minIndex ]->element ) + minIndex = i; + + return minIndex; + } + + /** + * Remove the smallest item from the priority queue. + * Throw Underflow if empty. + */ + template + void BinomialQueue::deleteMin( ) + { + Comparable x; + deleteMin( x ); + } + + + /** + * Remove the smallest item from the priority queue, and + * copy it into minItem. Throw Underflow if empty. + */ + template + void BinomialQueue::deleteMin( Comparable & minItem ) + { + if( isEmpty( ) ) + throw Underflow( ); + + int minIndex = findMinIndex( ); + minItem = theTrees[ minIndex ]->element; + + BinomialNode *oldRoot = theTrees[ minIndex ]; + BinomialNode *deletedTree = oldRoot->leftChild; + delete oldRoot; + + BinomialQueue deletedQueue; + deletedQueue.currentSize = ( 1 << minIndex ) - 1; + for( int j = minIndex - 1; j >= 0; j-- ) + { + deletedQueue.theTrees[ j ] = deletedTree; + deletedTree = deletedTree->nextSibling; + deletedQueue.theTrees[ j ]->nextSibling = NULL; + } + + theTrees[ minIndex ] = NULL; + currentSize -= deletedQueue.currentSize + 1; + + merge( deletedQueue ); + } + + /** + * Test if the priority queue is logically empty. + * Return true if empty, false otherwise. + */ + template + bool BinomialQueue::isEmpty( ) const + { + return currentSize == 0; + } + + /** + * Test if the priority queue is logically full. + * Return true if full, false otherwise. + */ + template + bool BinomialQueue::isFull( ) const + { + return currentSize == capacity( ); + } + + /** + * Make the priority queue logically empty. + */ + template + void BinomialQueue::makeEmpty( ) + { + currentSize = 0; + for( int i = 0; i < theTrees.size( ); i++ ) + makeEmpty( theTrees[ i ] ); + } + + /** + * Deep copy. + */ + template + const BinomialQueue & + BinomialQueue:: + operator=( const BinomialQueue & rhs ) + { + if( this != &rhs ) + { + makeEmpty( ); + theTrees.resize( rhs.theTrees.size( ) ); // Just in case + for( int i = 0; i < rhs.theTrees.size( ); i++ ) + theTrees[ i ] = clone( rhs.theTrees[ i ] ); + currentSize = rhs.currentSize; + } + return *this; + } + + /** + * Return the capacity. + */ + template + int BinomialQueue::capacity( ) const + { + return ( 1 << theTrees.size( ) ) - 1; + } + + /** + * Make a binomial tree logically empty, and free memory. + */ + template + void BinomialQueue:: + makeEmpty( BinomialNode * & t ) const + { + if( t != NULL ) + { + makeEmpty( t->leftChild ); + makeEmpty( t->nextSibling ); + delete t; + t = NULL; + } + } + + + /** + * Internal method to clone subtree. + */ + template + BinomialNode * + BinomialQueue::clone( BinomialNode * t ) const + { + if( t == NULL ) + return NULL; + else + return new BinomialNode( t->element, + clone( t->leftChild ), clone( t->nextSibling ) ); + } + diff --git a/c++/Others/BinomialQueue.h - Header file for binomial queue.cpp b/c++/Others/BinomialQueue.h - Header file for binomial queue.cpp new file mode 100644 index 0000000..4e30f4f --- /dev/null +++ b/c++/Others/BinomialQueue.h - Header file for binomial queue.cpp @@ -0,0 +1,77 @@ +BinomialQueue.h - Header file for binomial queue + + #ifndef BINOMIAL_QUEUE_H_ + #define BINOMIAL_QUEUE_H_ + + #include + #include "vector.h" + + // Binomial queue class + // + // CONSTRUCTION: with no parameters + // + // ******************PUBLIC OPERATIONS********************* + // void insert( x ) --> Insert x + // deleteMin( ) --> Return and remove smallest item + // Comparable findMin( ) --> Return smallest item + // bool isEmpty( ) --> Return true if empty; else false + // bool isFull( ) --> Return true if full; else false + // void makeEmpty( ) --> Remove all items + // void merge( rhs ) --> Absorb rhs into this heap + // ******************ERRORS******************************** + // Throws Underflow and Overflow as warranted + + + // Node and forward declaration because g++ does + // not understand nested classes. + + template + class BinomialQueue; + + template + class BinomialNode + { + Comparable element; + BinomialNode *leftChild; + BinomialNode *nextSibling; + + BinomialNode( const Comparable & theElement, + BinomialNode *lt, BinomialNode *rt ) + : element( theElement ), leftChild( lt ), nextSibling( rt ) { } + friend class BinomialQueue; + }; + + template + class BinomialQueue + { + public: + BinomialQueue( ); + BinomialQueue( const BinomialQueue & rhs ); + ~BinomialQueue( ); + + bool isEmpty( ) const; + bool isFull( ) const; + const Comparable & findMin( ) const; + + void insert( const Comparable & x ); + void deleteMin( ); + void deleteMin( Comparable & minItem ); + void makeEmpty( ); + void merge( BinomialQueue & rhs ); + + const BinomialQueue & operator=( const BinomialQueue & rhs ); + + private: + int currentSize; // Number of items in the priority queue + vector *> theTrees; // An array of tree roots + + int findMinIndex( ) const; + int capacity( ) const; + BinomialNode * combineTrees( BinomialNode *t1, + BinomialNode *t2 ) const; + void makeEmpty( BinomialNode * & t ) const; + BinomialNode * clone( BinomialNode * t ) const; + }; + + #include "BinomialQueue.cpp" + #endif diff --git a/c++/Others/BuggyIntCell.cpp - Buggy IntCell class implementat.cpp b/c++/Others/BuggyIntCell.cpp - Buggy IntCell class implementat.cpp new file mode 100644 index 0000000..bee1395 --- /dev/null +++ b/c++/Others/BuggyIntCell.cpp - Buggy IntCell class implementat.cpp @@ -0,0 +1,43 @@ +BuggyIntCell.cpp - Buggy IntCell class implementation (Figs 1.14 and 1.15) + + #include + + /** + * Figure 1.14: missing the big three is a bug here. + */ + class IntCell + { + public: + explicit IntCell( int initialValue = 0 ) + { storedValue = new int( initialValue ); } + + int read( ) const + { return *storedValue; } + void write( int x ) + { *storedValue = x; } + private: + int *storedValue; + }; + + + /* + * Figure 1.15. + */ + int f( ) + { + IntCell a( 2 ); + IntCell b = a; + IntCell c; + + c = b; + a.write( 4 ); + cout << a.read( ) << endl << b.read( ) << endl << c.read( ) << endl; + return 0; + } + + + int main( ) + { + f( ); + return 0; + } diff --git a/c++/Others/Byte alignment in a struct.cpp b/c++/Others/Byte alignment in a struct.cpp new file mode 100644 index 0000000..0ae818b --- /dev/null +++ b/c++/Others/Byte alignment in a struct.cpp @@ -0,0 +1,96 @@ +Byte alignment in a struct + +#include + +#define ALIGN 8 +#pragma pack(ALIGN) + +/* Algorithm + +Byte offset between currentType and nextType = MIN( multiple of Byte +Alignment specified , multiple of size of nextType) +**/ + +int ALIGNOFFSET(int currRelativeAddess,int currrentTypeSize,int +nextTypeSize) +{ + + int nOffset = currrentTypeSize ;//this is size of the current +type.Offset will be minimum of this size. + currRelativeAddess += currrentTypeSize ; //cuurent address is +increased by size of current type. + if( nextTypeSize < ALIGN) // now alignment depens on the next type +and also alignment defined by #pragam pack(#) + { + // if the size of next type is less than byte alignment size +specified , then offset will be increased to the muliple of + // size of next type. + int nRemainder = currRelativeAddess % nextTypeSize ; + if(nRemainder != 0) + { + nOffset += nextTypeSize - nRemainder ;//this will +align boundary to next multiple of nextTypeSize + } + + } + else + { + // if the byte alignment size specified is less than size of +next type , then offset will be increased to the next muliple of + // size of byte alignment. + int nRemainder = currRelativeAddess % ALIGN ; + if(nRemainder != 0) + { + nOffset += ALIGN - nRemainder ;//this will align the +boundary to next multiple of ALIGN + } + } + return nOffset ; +} + + +struct S +{ + + char a[2]; + int b; + double c; + char d[1]; + int e; + double f; +}; + +void main() +{ + S sz; + cout << "size of struct :" << sizeof(sz) << endl; + cout << "address of size::a "<< &sz.a <<" Actual offset = " << +int(0) << " Calculated offset = " << 0 << endl; + + int offset = ((int)&sz.b)- (int)(&sz.a); + + + cout << "address of size::b " << &sz.b <<" Actual offset = " << +offset << " Calculated offset = " << ALIGNOFFSET((int)(&sz.a)- +(int)(&sz),sizeof(sz.a),sizeof(sz.b)) << endl; + offset = ((int)&sz.c)- (int)(&sz.b); + + cout << "address of size::c " << &sz.c <<" Actual offset = " << +offset << " Calculated offset = " << ALIGNOFFSET((int)(&sz.b) - +(int)(&sz),sizeof(sz.b),sizeof(sz.c)) << endl; + offset = ((int)&sz.d)- (int)(&sz.c); + + cout << "address of size::d " << &sz.d <<" Actual offset = " << +offset << " Calculated offset = " << ALIGNOFFSET((int)(&sz.c)- +(int)(&sz),sizeof(sz.c),sizeof(sz.d)) << endl; + + offset = ((int)&sz.e)- (int)(&sz.d); + + cout << "address of size::e " << &sz.e <<" Actual offset = " << +offset << " Calculated offset = " << ALIGNOFFSET((int)(&sz.d)- +(int)(&sz),sizeof(sz.d),sizeof(sz.e)) << endl; + offset = ((int)&sz.f)- (int)(&sz.e); + cout << "address of size::f " << &sz.f <<" Actual offset = " << +offset << " Calculated offset = " << ALIGNOFFSET((int)(&sz.e)- +(int)(&sz),sizeof(sz.e),sizeof(sz.f)) << endl; +} diff --git a/c++/Others/Cin example.cpp b/c++/Others/Cin example.cpp new file mode 100644 index 0000000..1a39325 --- /dev/null +++ b/c++/Others/Cin example.cpp @@ -0,0 +1,19 @@ +Cin example + +#include + +int main(void) +{ +int number,highNumber; + +cout<<"Please enter a whole number (ctrl q) to quit"; +while(cin>>number) +{ +if(number > highNumber) +highNumber = number; +cout<<"Please enter a whole number (ctrl q) to quit"; + +} +cout<<"High number is :"< + +int main(void) +{ +const SIZE = 100; +char msg[SIZE]; +cout<<"Enter a string."< +# include +// Creating a basic template for book and magazine +class lib +{ + private: + char title[20]; + char pub[20]; + unsigned int acc_no; + public: +//method for getting inputs + void get_details() + { + cout<<"Enter the book title"<>title; + cout<<"Enter the publisher name"<>pub; + cout<<"Enter the accession number"<>acc_no; + } +//method for showing output + void show_details() + { + cout<<"Title : "<>author; + } + void show_details() + { + lib::show_details(); + cout<<"Autohr : "<>editor; + } + void show_details() + { + lib::show_details(); + cout<<"editor : "< +# include // for strcpy +# include + +class person +{ + char name[20]; + int yob; //Year of birth + int yod; // Year of death +public: + person() + { strcpy(name,"N.A."); + yob=2000; yod=2000; + } + ~person() + { + delete []name; + } + void getdata() + { + cout<<" + +Enter the name : "; + cin.getline(name,19); + cout<<" +Enter the year of birth"; + cin>>yob; + cout<<" +Enter the year of death"; + cin>>yod; + } + void print() + { + cout<<" + +Name:"< +# include +# include + +class address +{ +char name[20]; +char houseno[10]; +char street[20]; +char city[20]; +long int pin; +public: +address() +{ + strcpy(name,"Unspecified"); + strcpy(houseno,"NA"); + strcpy(street,"NA"); + strcpy(city,"NA"); + pin=0; +} +void put_data() +{ +cout<<" +Enter the name of the person"; +cin.getline(name,19); +cout<<" +Enter the House number"; +cin.getline(houseno,9); +cout<<" +Enter the street address"; +cin.getline(street,19); +cout<<" +Enter the city"; +cin.getline(city,19); +cout<<" +Enter the pin code"; +cin>>pin; +} +void get_data() +{ +cout<<"***********************************************"< +#include +class Int +{ +int var; +public : + /* Here we try to overcome the problem of carbage value by + initializing the value by 0 */ + Int() + { + var =0; + } + + // Overloaded Constructor + Int(int a ) + { + var = a; + } + int add( Int b) // Note : Int , not int + { + var+=b.var; /* For ex. if the user enters + a.add(b); + then result will be + a = a + b; */ + return(var); + } + void disp() //again, Int + { + cout<>title; + cout<<"Enter the price : + "; cin>>price; + } + void putdata() + { + cout<<"The title is : "<>s1; + cout<<"Enter the sale of second month: +"; + cin>>s2; + cout<<"Enter the sale of third month: +"; + cin>>s3; + } + void putdata() + { + cout<<"Sale in first month : $"<>pages; + } + void putdata() + { + cout<<" BOOK DETAILS +"; + publication::putdata(); + cout<<"Number of pages : " <>time; + } + void putdata() + { + cout<<" TAPE DETAILS "; + publication::putdata(); + cout<<"Time length :"<< time< +#include +#include +#include + +class complex +{ + private: + float real; // Real Part + float imag; // Imaginary Part + + + public: + complex(float,float); + complex(complex&); + complex operator +(complex); + complex operator -(complex); + complex operator *(complex); + complex operator /(complex); + complex getconjugate(); + complex getreciprocal(); + float getmodulus(); + void setdata(float,float); + void getdata(); + float getreal(); + float getimaginary(); + bool operator ==(complex); + void operator =(complex); + friend ostream& operator <<(ostream &s,complex &c); +}; +// CONSTRUCTOR + complex::complex(float r=0.0f,float im=0.0f) + { + real=r; + imag=im; + } + +// COPY CONSTRUCTOR + complex::complex(complex &c) + { + this->real=c.real; + this->imag=c.imag; + } + + + void complex::operator =(complex c) + { + real=c.real; + imag=c.imag; + } + + + complex complex::operator +(complex c) + { + complex tmp; + tmp.real=this->real+c.real; + tmp.imag=this->imag+c.imag; + return tmp; + } + + complex complex::operator -(complex c) + { + complex tmp; + tmp.real=this->real - c.real; + tmp.imag=this->imag - c.imag; + return tmp; + } + + complex complex::operator *(complex c) + { + complex tmp; + tmp.real=(real*c.real)-(imag*c.imag); + tmp.imag=(real*c.imag)-(imag*c.real); + return tmp; + } + + complex complex::operator /(complex c) + { + float div=(c.real*c.real) + (c.imag*c.imag); + complex tmp; + tmp.real=(real*c.real)+(imag*c.imag); + tmp.real/=div; + tmp.imag=(imag*c.real)-(real*c.imag); + tmp.imag/=div; + return tmp; + } + + complex complex::getconjugate() + { + complex tmp; + tmp.real=this->real; + tmp.imag=this->imag * -1; + return tmp; + } + + complex complex::getreciprocal() + { + complex t; + t.real=real; + t.imag=imag * -1; + float div; + div=(real*real)+(imag*imag); + t.real/=div; + t.imag/=div; + return t; + } + + float complex::getmodulus() + { + float z; + z=(real*real)+(imag*imag); + z=sqrt(z); + return z; + } + + void complex::setdata(float r,float i) + { + real=r; + imag=i; + } + + void complex::getdata() + { + cout<<"Enter Real:"; + cin>>this->real; + cout<<"Enter Imaginary:"; + cin>>this->imag; + + } + + float complex::getreal() + { + return real; + } + + float complex::getimaginary() + { + return imag; + } + + bool complex::operator ==(complex c) + { + return (real==c.real)&&(imag==c.imag) ? 1 : 0; + } + + ostream& operator <<(ostream &s,complex &c) + { + s<<"Real Part = "< +#include +class complex +{ + private: + float real,img; + public: + void assign(float x,float y) + { + real=x; + img=y; + } + void print() + { if(img>=0) + cout<>a; + cout<<"imaginary part:"; + cin>>b; + cout<<" for complex 2:"; + cout<<"real part:"; + cin>>c; + cout<<"imaginary part:"; + cin>>d; + x.assign(a,b); + y.assign(c,d); + cout<<"**************original data:************\n"; + cout<<"Complex 1:\n";x.print(); + cout<<"\n Complex 2:\n";y.print(); + cout<<"\n************=================**********\n"; + cout<<"\n Addition:\n";add(a,b,c,d); + cout<<"\n Subtraction:\n";sub(a,b,c,d); + cout<<"\n Multipication:\n";mul(a,b,c,d); + } diff --git a/c++/Others/Concordance1.cpp - Concordance program using STL.cpp b/c++/Others/Concordance1.cpp - Concordance program using STL.cpp new file mode 100644 index 0000000..af9878c --- /dev/null +++ b/c++/Others/Concordance1.cpp - Concordance program using STL.cpp @@ -0,0 +1,68 @@ +Concordance1.cpp - Concordance program using STL + +#pragma warning (disable: 4786) + +#include +#include +#ifdef __GNUC__ + #include +#else +#ifdef __BORLANDC__ + #include +#else + #include +#endif +#endif +#include +#include +#include + +using namespace std; + +ostream & operator<<( ostream & out, const pair > & rhs ) +{ + out << rhs.first << ": " << '\t' << rhs.second[ 0 ]; + for( int i = 1; i < rhs.second.size( ); i++ ) + out << ", " << rhs.second[ i ]; + return out; +} + +int main( int argc, char *argv[ ] ) +{ + if( argc != 2 ) + { + cerr << "Usage: " << argv[ 0 ] << " filename" << endl; + return 1; + } + + ifstream inFile( argv[ 1 ] ); + if( !inFile ) + { + cerr << "Cannot open " << argv[ 1 ] << endl; + return 1; + } + + string oneLine; + map > concordance; + + // Read the words; add them to wordMap + for( int lineNum = 1; getline( inFile, oneLine ); lineNum++ ) + { +#if defined( __GNUC__ ) || defined ( __BORLANDC__ ) + istrstream st( oneLine.c_str( ), oneLine.length( ) ); +#else + istringstream st( oneLine ); +#endif + string word; + + while( st >> word ) + concordance[ word ].push_back( lineNum ); + } + + map >::iterator itr; + for( itr = concordance.begin( ); itr != concordance.end( ); itr++ ) + cout << *itr << endl; + + return 0; +} + diff --git a/c++/Others/Concordance2.cpp - Concordance program not using STL.cpp b/c++/Others/Concordance2.cpp - Concordance program not using STL.cpp new file mode 100644 index 0000000..dbcc767 --- /dev/null +++ b/c++/Others/Concordance2.cpp - Concordance program not using STL.cpp @@ -0,0 +1,89 @@ +Concordance2.cpp - Concordance program not using STL + +#include +#include +#ifdef unix + #include +#else + #include // on UNIX machines +#endif + +#include "mystring.h" +#include "AvlTree.h" +#include "LinkedList.h" + +struct WordEntry +{ + WordEntry( ) : word( "" ), lines( NULL ) + { } + + bool operator<( const WordEntry & rhs ) const + { return word < rhs.word; } + bool operator==( const WordEntry & rhs ) const + { return word == rhs.word; } + + string word; + List *lines; + ListItr *listEnd; +}; + +ostream & operator<<( ostream & out, const WordEntry & rhs ) +{ + out << rhs.word << ": "; + + if( rhs.lines != NULL && !rhs.lines->isEmpty( ) ) + { + ListItr itr = rhs.lines->first( ); + out << '\t' << itr.retrieve( ); + for( itr.advance( ); !itr.isPastEnd( ); itr.advance( ) ) + out << ", " << itr.retrieve( ); + } + return out; +} + +int main( int argc, char *argv[ ] ) +{ + if( argc != 2 ) + { + cerr << "Usage: " << argv[ 0 ] << " filename" << endl; + return 1; + } + + ifstream inFile( argv[ 1 ] ); + if( !inFile ) + { + cerr << "Cannot open " << argv[ 1 ] << endl; + return 1; + } + + const WordEntry ITEM_NOT_FOUND; // "" is the word member + AvlTree wordMap( ITEM_NOT_FOUND ); + string oneLine; + WordEntry entry; + + // Read the words; add them to wordMap + for( int lineNum = 1; getline( inFile, oneLine ); lineNum++ ) + { + istrstream st( (char *) oneLine.c_str( ) ); // Deprecated form of string streams + while( st >> entry.word ) + { + const WordEntry & match = wordMap.find( entry ); + if( match == ITEM_NOT_FOUND ) + { + entry.lines = new List; + entry.lines->insert( lineNum, entry.lines->zeroth( ) ); + entry.listEnd = new ListItr( entry.lines->first( ) ); + wordMap.insert( entry ); + } + else + { + match.lines->insert( lineNum, *match.listEnd ); + match.listEnd->advance( ); + } + } + } + + wordMap.printTree( ); + return 0; +} + diff --git a/c++/Others/Convert a number into words.cpp b/c++/Others/Convert a number into words.cpp new file mode 100644 index 0000000..d25f134 --- /dev/null +++ b/c++/Others/Convert a number into words.cpp @@ -0,0 +1,212 @@ +Convert a number into words + +#include // For getch() function only +#include +using namespace std; + + +void numword1(int); +void numword2(int); + +int main() +{ +long unsigned int number,temp; +int mult,i,digit,digits,last_two,hundred,thousand,lakh,crore; +digits=last_two=hundred=thousand=lakh=crore=0; + +cout<<"Enter a number(lesser than 99,99,99,999) +"; +cin>>number; + +if(number>999999999) +{ + cout<<"Number out of range!"; + getch(); + exit(0); +} + +if(number==0) +{ + cout<<"Zero"; + getch(); + exit(0); +} + +temp=number; + +digit=number%10; // Extracting last two digts +last_two=digit; +number=number/10; +digit=number%10; +last_two=(digit*10)+last_two; + + number=number/10; // Extract hundreds + digit=number%10; + hundred=digit; + + number=number/10; // Extract thousands + digit=number%10; + thousand=digit; + number=number/10; + digit=number%10; + thousand=(digit*10)+thousand; + + number=number/10; // Extract lakhs + digit=number%10; + lakh=digit; + number=number/10; + digit=number%10; + lakh=(digit*10)+lakh; + + number=number/10; // Extract crores + digit=number%10; + crore=digit; + number=number/10; + digit=number%10; + crore=(digit*10)+crore; + + + +while(temp!=0) // Calculate number of digits in the number +{ + temp=temp/10; + digits++; +} + +cout<<"The number in words is: +"; + + // Printing the number in words + +if(digits>=8) +{ + numword2(crore); + cout<<"crores "; +} +if(digits>=6) +{ + if(lakh!=0) + { + numword2(lakh); + cout<<"lakh "; + } +} +if(digits>=4) +{ +if(thousand!=0) +{ + numword2(thousand); + cout<<"Thousand "; +} +} +if(digits>=3) +{ +if(hundred!=0) +{ + numword2(hundred); + cout<<"Hundred "; +} +} + +numword2(last_two); + +getch(); +return 0; +} + + +void numword1(int num) +{ +switch(num) +{ + case 0: break; + + case 1: cout<<"One "; + break; + case 2: cout<<"Two "; + break; + case 3: cout<<"Three "; + break; + case 4: cout<<"Four "; + break; + case 5: cout<<"Five "; + break; + case 6: cout<<"Six "; + break; + case 7: cout<<"Seven "; + break; + case 8: cout<<"Eight "; + break; + case 9: cout<<"Nine "; + break; + case 10: cout<<"Ten "; + break; + case 11: cout<<"Eleven "; + break; + case 12: cout<<"Twelve "; + break; + case 13: cout<<"Thirteen "; + break; + case 14: cout<<"Fourteen "; + break; + case 15: cout<<"Fifteen "; + break; + case 16: cout<<"Sixteen "; + break; + case 17: cout<<"Seventeen "; + break; + case 18: cout<<"Eighteen "; + break; + case 19: cout<<"Nineteen "; + break; +} +return; +} + +void numword2(int num) +{ +if(num>=90) +{ + cout<<"Ninety "; + numword1(num-90); +} +else if(num>=80) +{ + cout<<"Eighty "; + numword1(num-80); +} +else if(num>=70) +{ + cout<<"Seventy "; + numword1(num-70); +} +else if(num>=60) +{ + cout<<"Sixty "; + numword1(num-60); +} +else if(num>=50) +{ + cout<<"Fifty "; + numword1(num-50); +} +else if(num>=40) +{ + cout<<"Fourty "; + numword1(num-40); +} +else if(num>=30) +{ + cout<<"Thirty "; + numword1(num-30); +} +else if(num>=20) +{ + cout<<"Twenty "; + numword1(num-20); +} +else + numword1(num); + +return; +} diff --git a/c++/Others/Converts Decimal Numbers to Binary.cpp b/c++/Others/Converts Decimal Numbers to Binary.cpp new file mode 100644 index 0000000..d38fd7b --- /dev/null +++ b/c++/Others/Converts Decimal Numbers to Binary.cpp @@ -0,0 +1,22 @@ +Converts Decimal Numbers to Binary + +#include +#include +void main() + + + { + + + + int i, ch; + cout<<"Enter an integer: "; + cin>>ch; + for(i=0x80;i;i=i>>1) + cout<<((ch&i)?'1':'0'); + + + getch(); + + cout< + +/* +BOOL Copy(char r_szPath[1024], char r_szDir[1024]) +{ + char l_szTemp[2048] = {0}; + sprintf(l_szTemp,"%s\%s"r_szPath,r_szDir); + + if(IsDirectory( +}*/ + +#include +#include + +BOOL __Copy(char r_szSrcPath[1024],char r_szDesPath[1024]) +{ + WIN32_FIND_DATA FindFileData; + HANDLE hFind; + char l_szTmp[1025] = {0}; + memcpy(l_szTmp,r_szSrcPath,1024); + + + char l_szSrcPath[1025] = {0}; + char l_szDesPath[1025] = {0}; + memcpy(l_szSrcPath,r_szSrcPath,1024); + memcpy(l_szDesPath,r_szDesPath,1024); + + char l_szNewSrcPath[1025] = {0}; + char l_szNewDesPath[1025] = {0}; + + strcat(l_szTmp,"*"); + + hFind = FindFirstFile(l_szTmp, &FindFileData); + if(hFind == NULL) return FALSE; + + do + { + + if(FindFileData.dwFileAttributes & FILE_ATTRIBUTE_DIRECTORY) + { + if(strcmp(FindFileData.cFileName,".")) + { + if(strcmp(FindFileData.cFileName,"..")) + { + printf ("The Directory found is %s +", FindFileData.cFileName); + +sprintf(l_szNewDesPath,"%s%s\",l_szDesPath,FindFileData.cFileName); + +sprintf(l_szNewSrcPath,"%s%s\",l_szSrcPath,FindFileData.cFileName); + CreateDirectory(l_szNewDesPath,NULL); + __Copy(l_szNewSrcPath,l_szNewDesPath); + } + } + } + else + { + printf ("The File found is %s +", FindFileData.cFileName); + char l_szSrcFile[1025] = {0}; + char l_szDesFile[1025] = {0}; + sprintf(l_szDesFile,"%s%s",l_szDesPath,FindFileData.cFileName); + sprintf(l_szSrcFile,"%s%s",l_szSrcPath,FindFileData.cFileName); + BOOL l_bRet = CopyFile(l_szSrcFile,l_szDesFile,TRUE); + + } + + + } + while(FindNextFile(hFind, &FindFileData)); + FindClose(hFind); + return TRUE; +} + + +int main(int argc, char *argv[]) +{ + __Copy("C:\fcdb\","E:\sowmya\"); + getch(); + return 0; +} + + diff --git a/c++/Others/Copying one or more than one file into one file.cpp b/c++/Others/Copying one or more than one file into one file.cpp new file mode 100644 index 0000000..40e2668 --- /dev/null +++ b/c++/Others/Copying one or more than one file into one file.cpp @@ -0,0 +1,69 @@ +Copying one or more than one file into one file + +#include + +void main(int argc,char *argv[]){ + int i=0, + is_copied=0; + + FILE *input, + *output; + + char ch; + + clrscr(); + + + if (argc>=3){ + + /* last file is the output file */ + output=fopen(argv[argc-1],"w+"); + if (output==NULL){ + gotoxy(10,1); + printf("Can't open output file :%s",argv[argc-1]); + getch(); + return; + } + + + /* input files */ + for(i=1;i +#include + +int main() +{ +char mychar[100]; +int i = 0; +//while the character is not a new line +while((mychar[i] = cin.get()) != '\n') +i++; + +mychar[i] = NULL; +//display characters +cout< +#include + +int main() +{ +char *url = "WWW"; +while(*url) +cout.put (*url++); + +cout< +#include +#include + +int main() +{ + +cout< +#include +#include + +class cpuschedule +{ + int n,Bu[20]; + float Twt,Awt,A[10],Wt[10],w; +public: + //Getting the No of processes & burst time + void Getdata(); + //First come First served Algorithm + void Fcfs(); + //Shortest job First Algorithm + void Sjf(); + //Shortest job First Algorithm with Preemption + void SjfP(); + //Shortest job First Algorithm with NonPreemption + void SjfNp(); + //Round Robin Algorithm + void RoundRobin(); + //Priority Algorithm + void Priority(); +}; +// Implementation file for Cpu scheduling + +#include "cpuh.h" +//Getting no of processes and Burst time +void cpuschedule::Getdata() +{ + int i; + cout<<" +Enter the no of processes:"; + cin>>n; + for(i=1;i<=n;i++) + { + cout<<" +Enter The BurstTime for Process p"<>Bu[i]; + } +} + +//First come First served Algorithm +void cpuschedule::Fcfs() +{ + int i,B[10]; + Twt=0.0; + for(i=1;i<=n;i++) + { + B[i]=Bu[i]; + cout<<" +Burst time for process p"<B[i] && S[i]=='T') + { + min=B[i]; + j=i; + } + i++; + } + i=j; + if(w==Time && start[i]=='T') + { + w=w+B[i]; + S[i]='F'; + } + else + { + Wt[i]=Wt[i]+w; + w=w+B[i]; + S[i]='F'; + } + } + +cout<<"Weight info +"; + + for(i=1;i<=n;i++) + cout<<" +WT["<>ch; + switch(ch) + { + case 1: + c.Getdata(); + break; + case 2: + cout<<"FIRST COME FIRST SERVED SCHEDULING +"; + c.Fcfs(); + break; + case 3: + cout<<"SHORTEST JOB FIRST SCHEDULING +"; + do + { + cout<<"1.SJF-Normel +"; + cout<<"2.SJF-Preemptive +"; + cout<<"3.SJF-NonPreemptive +"; + cout<<"Enter your choice +"; + cin>>cho; + switch(cho) + { + case 1: + c.Sjf(); + break; + case 2: + c.SjfP(); + break; + case 3: + c.SjfNp(); + break; + } + }while(cho<=3); + break; + case 4: + cout<<"ROUND ROBIN SCHEDULING +"; + c.RoundRobin(); + break; + case 5: + cout<<"PRIORITY SCHEDULING +"; + c.Priority(); + break; + case 6: + break; + } + }while(ch<=5); +} diff --git a/c++/Others/Creates a file using fstream.cpp b/c++/Others/Creates a file using fstream.cpp new file mode 100644 index 0000000..c3bea8e --- /dev/null +++ b/c++/Others/Creates a file using fstream.cpp @@ -0,0 +1,13 @@ +Creates a file using fstream + +//this example creates a file called myfile.txt +//and adds some text message to it +#include +int main() +{ +ofstream MyFile("myfile.txt"); +MyFile<<"This is some test message"; +MyFile.close(); + +return 0; +} diff --git a/c++/Others/CursorList.cpp - Implementation for cursor linked list.cpp b/c++/Others/CursorList.cpp - Implementation for cursor linked list.cpp new file mode 100644 index 0000000..c7332ed --- /dev/null +++ b/c++/Others/CursorList.cpp - Implementation for cursor linked list.cpp @@ -0,0 +1,199 @@ +CursorList.cpp - Implementation for cursor linked list + + #include "CursorList.h" + + /** + * Routine to initialize the cursorSpace. + */ + template + void List::initializeCursorSpace( ) + { + static int cursorSpaceIsInitialized = false; + + if( !cursorSpaceIsInitialized ) + { + cursorSpace.resize( 100 ); + for( int i = 0; i < cursorSpace.size( ); i++ ) + cursorSpace[ i ].next = i + 1; + cursorSpace[ cursorSpace.size( ) - 1 ].next = 0; + cursorSpaceIsInitialized = true; + } + } + + /** + * Allocate a CursorNode + */ + template + int List::alloc( ) + { + int p = cursorSpace[ 0 ].next; + cursorSpace[ 0 ].next = cursorSpace[ p ].next; + return p; + } + + /** + * Free a CursorNode + */ + template + void List::free( int p ) + { + cursorSpace[ p ].next = cursorSpace[ 0 ].next; + cursorSpace[ 0 ].next = p; + } + + + /** + * Construct the list + */ + template + List::List( ) + { + initializeCursorSpace( ); + header = alloc( ); + cursorSpace[ header ].next = 0; + } + + /** + * Copy constructor + */ + template + List::List( const List & rhs ) + { + initializeCursorSpace( ); + header = alloc( ); + cursorSpace[ header ].next = 0; + *this = rhs; + } + + /** + * Destroy the list + */ + template + List::~List( ) + { + makeEmpty( ); + free( header ); + } + + /** + * Test if the list is logically empty. + * return true if empty, false otherwise. + */ + template + bool List::isEmpty( ) const + { + return cursorSpace[ header ].next == 0; + } + + /** + * Make the list logically empty. + */ + template + void List::makeEmpty( ) + { + while( !isEmpty( ) ) + remove( first( ).retrieve( ) ); + } + + /** + * Return an iterator representing the header node. + */ + template + ListItr List::zeroth( ) const + { + return ListItr( header ); + } + + /** + * Return an iterator representing the first node in the list. + * This operation is valid for empty lists. + */ + template + ListItr List::first( ) const + { + return ListItr( cursorSpace[ header ].next ); + } + + /** + * Insert item x after p. + */ + template + void List::insert( const Object & x, const ListItr & p ) + { + if( p.current != 0 ) + { + int pos = p.current; + int tmp = alloc( ); + + cursorSpace[ tmp ] = CursorNode( x, cursorSpace[ pos ].next ); + cursorSpace[ pos ].next = tmp; + } + } + + /** + * Return iterator corresponding to the first node containing an item x. + * Iterator isPastEnd if item is not found. + */ + template + ListItr List::find( const Object & x ) const + { +/* 1*/ int itr = cursorSpace[ header ].next; + +/* 2*/ while( itr != 0 && cursorSpace[ itr ].element != x ) +/* 3*/ itr = cursorSpace[ itr ].next; + +/* 4*/ return ListItr( itr ); + } + + /** + * Return iterator prior to the first node containing an item x. + */ + template + ListItr List::findPrevious( const Object & x ) const + { +/* 1*/ int itr = header; + +/* 2*/ while( cursorSpace[ itr ].next != 0 && + cursorSpace[ cursorSpace[ itr ].next ].element != x ) +/* 3*/ itr = cursorSpace[ itr ].next; + +/* 4*/ return ListItr( itr ); + } + + /** + * Remove the first occurrence of an item x. + */ + template + void List::remove( const Object & x ) + { + ListItr p = findPrevious( x ); + int pos = p.current; + + if( cursorSpace[ pos ].next != 0 ) + { + int tmp = cursorSpace[ pos ].next; + cursorSpace[ pos ].next = cursorSpace[ tmp ].next; + free ( tmp ); + } + } + + + /** + * Deep copy of linked lists. + */ + template + const List & List::operator=( const List & rhs ) + { + ListItr ritr = rhs.first( ); + ListItr itr = zeroth( ); + + if( this != &rhs ) + { + makeEmpty( ); + for( ; !ritr.isPastEnd( ); ritr.advance( ), itr.advance( ) ) + insert( ritr.retrieve( ), itr ); + } + return *this; + } + + diff --git a/c++/Others/CursorList.h - Header file for cursor linked list.cpp b/c++/Others/CursorList.h - Header file for cursor linked list.cpp new file mode 100644 index 0000000..1f3725b --- /dev/null +++ b/c++/Others/CursorList.h - Header file for cursor linked list.cpp @@ -0,0 +1,111 @@ +CursorList.h - Header file for cursor linked list + + #ifndef CursorList_H + #define CursorList_H + +#define List CursorList + + #include "vector.h" + #include "dsexceptions.h" + + // LinkedList class using a cursor implementation + // + // CONSTRUCTION: with no initializer + // Access is via LinkedListItr class + // + // ******************PUBLIC OPERATIONS********************* + // boolean isEmpty( ) --> Return true if empty; else false + // void makeEmpty( ) --> Remove all items + // ListItr zeroth( ) --> Return position to prior to first + // ListItr first( ) --> Return first position + // void insert( x, p ) --> Insert x after current iterator position p + // void remove( x ) --> Remove x + // ListItr find( x ) --> Return position that views x + // ListItr findPrevious( x ) + // --> Return position prior to x + // ******************ERRORS******************************** + // No special errors + + template + class ListItr; // Incomplete declaration. + + template + class List + { + public: + List( ); + List( const List & rhs ); + ~List( ); + + bool isEmpty( ) const; + void makeEmpty( ); + ListItr zeroth( ) const; + ListItr first( ) const; + void insert( const Object & x, const ListItr & p ); + ListItr find( const Object & x ) const; + ListItr findPrevious( const Object & x ) const; + void remove( const Object & x ); + + public: + struct CursorNode + { + CursorNode( ) : next( 0 ) { } + + private: + CursorNode( const Object & theElement, int n ) + : element( theElement ), next( n ) { } + + Object element; + int next; + + friend class List; + friend class ListItr; + }; + + const List & operator=( const List & rhs ); + + private: + int header; + + static vector cursorSpace; + + static void initializeCursorSpace( ); + static int alloc( ); + static void free( int p ); + + friend class ListItr; + }; + + + // ListItr class; maintains "current position" + // + // CONSTRUCTION: Package friendly only, with an int + // + // ******************PUBLIC OPERATIONS********************* + // bool isPastEnd( ) --> True if at valid position in list + // void advance( ) --> Advance (if not already null) + // Object retrieve --> Return item in current position + + template + class ListItr + { + public: + ListItr( ) : current( 0 ) { } + bool isPastEnd( ) const + { return current == 0; } + void advance( ) + { if( !isPastEnd( ) ) current = List::cursorSpace[ current ].next; } + const Object & retrieve( ) const + { if( isPastEnd( ) ) throw BadIterator( ); + return List::cursorSpace[ current ].element; } + + private: + int current; // Current position + friend class List; + + ListItr( int theNode ) + : current( theNode ) { } + }; + + #include "CursorList.cpp" + #endif diff --git a/c++/Others/DSL.cpp - Implementation for deterministic skip list.cpp b/c++/Others/DSL.cpp - Implementation for deterministic skip list.cpp new file mode 100644 index 0000000..da1882e --- /dev/null +++ b/c++/Others/DSL.cpp - Implementation for deterministic skip list.cpp @@ -0,0 +1,214 @@ +DSL.cpp - Implementation for deterministic skip list + + #include "DSL.h" + + /** + * Construct the tree. + * inf is the largest Comparable + * and is used to signal failed finds. + */ + template + DSL::DSL( const Comparable & inf ) : INFINITY( inf ) + { + bottom = new SkipNode( ); + bottom->right = bottom->down = bottom; + tail = new SkipNode( INFINITY ); + tail->right = tail; + header = new SkipNode( INFINITY, tail, bottom ); + } + + /** + * Copy constructor. + * Left as an exercise. + */ + template + DSL::DSL( const DSL & rhs ) : INFINITY( rhs.INFINITY) + { + cout << "Copy constructor is unimplemented" << endl; + } + + /** + * Destructor. + */ + template + DSL::~DSL( ) + { + makeEmpty( ); + delete header; + delete tail; + delete bottom; + } + + /** + * Insert item x into the DSL. + */ + template + void DSL::insert( const Comparable & x ) + { + SkipNode *current = header; + + bottom->element = x; + while( current != bottom ) + { + while( current->element < x ) + current = current->right; + + // If gap size is 3 or at bottom level and + // must insert, then promote middle element + if( current->down->right->right->element < current->element ) + { + current->right = new SkipNode( current->element, + current->right, current->down->right->right ); + current->element = current->down->right->element; + } + else + current = current->down; + } + + // Raise height of DSL if necessary + if( header->right != tail ) + header = new SkipNode( INFINITY, tail, header ); + } + + /** + * Remove item x from the DSL. Unimplemented. + */ + template + void DSL::remove( const Comparable & x ) + { + cout << "Sorry, remove unimplemented; " << x << + " still present" << endl; + } + + /** + * Find the smallest item in the tree. + * Return smallest item or INFINITY if empty. + */ + template + const Comparable & DSL::findMin( ) const + { + if( isEmpty( ) ) + return INFINITY; + + SkipNode *current = header; + while( current->down != bottom ) + current = current->down; + + return elementAt( current ); + } + + /** + * Find the largest item in the tree. + * Return the largest item or INFINITY if empty. + */ + template + const Comparable & DSL::findMax( ) const + { + if( isEmpty( ) ) + return INFINITY; + + SkipNode *current = header; + for( ; ; ) + if( current->right->right != tail ) + current = current->right; + else if( current->down != bottom ) + current = current->down; + else + return elementAt( current ); + } + + /** + * Find item x in the tree. + * Return the matching item or INFINITY if not found. + */ + template + const Comparable & DSL::find( const Comparable & x ) const + { + SkipNode *current = header; + + bottom->element = x; + for( ; ; ) + if( x < current->element ) + current = current->down; + else if( current->element < x ) + current = current->right; + else + return elementAt( current ); + } + + /** + * Make the tree logically empty. + */ + template + void DSL::makeEmpty( ) + { + reclaimMemory( header ); + header->right = tail; + header->down = bottom; + } + + /** + * Test if the tree is logically empty. + * Return true if empty, false otherwise. + */ + template + bool DSL::isEmpty( ) const + { + return header->right == tail && header->down == bottom; + } + + /** + * Internal method to get element field from node t. + * Return the element field or INFINITY if t is at the bottom. + */ + template + const Comparable & DSL:: + elementAt( SkipNode *t ) const + { + if( t == bottom ) + return INFINITY; + else + return t->element; + } + + /** + * Print the DSL. + */ + template + void DSL::printList( ) const + { + SkipNode *current = header; + + while( current->down != bottom ) + current = current->down; + + while( current->right != tail ) + { + cout << current->element << endl; + current = current->right; + } + } + + /** + * Deep copy. Left as an exercise + */ + template + const DSL & + DSL::operator=( const DSL & rhs ) + { + if( this != &rhs ) + cout << "Sorry, operator= is unimplemented" << endl; + + return *this; + } + + /** + * reclaimMemory is left as an exercise. + * Hint: delete from top level to bottom level. + */ + template + void DSL::reclaimMemory( SkipNode *t ) const + { + if( t != bottom ) + cout << "reclaimMemory is unimplemented -- leaking!" << endl; + } diff --git a/c++/Others/DSL.h - Header file for deterministic skip list.cpp b/c++/Others/DSL.h - Header file for deterministic skip list.cpp new file mode 100644 index 0000000..ecd8f83 --- /dev/null +++ b/c++/Others/DSL.h - Header file for deterministic skip list.cpp @@ -0,0 +1,77 @@ +DSL.h - Header file for deterministic skip list + + #ifndef DSL_H_ + #define DSL_H_ + + #include "dsexceptions.h" + #include // For NULL + + // Deterministic skip list class class + // + // CONSTRUCTION: with INFINITY object that is + // also used to signal failed finds + // + // ******************PUBLIC OPERATIONS********************* + // void insert( x ) --> Insert x + // void remove( x ) --> Remove x (unimplemented) + // Comparable find( x ) --> Return item that matches x + // Comparable findMin( ) --> Return smallest item + // Comparable findMax( ) --> Return largest item + // boolean isEmpty( ) --> Return true if empty; else false + // void makeEmpty( ) --> Remove all items + // void printList( ) --> Print items in sorted order + + + // Node and forward declaration because g++ does + // not understand nested classes. + template + class DSL; + + template + class SkipNode + { + Comparable element; + SkipNode *right; + SkipNode *down; + + SkipNode( const Comparable & theElement = Comparable( ), + SkipNode *rt = NULL, SkipNode *dt = NULL ) + : element( theElement ), right( rt ), down( dt ) { } + + friend class DSL; + }; + + + template + class DSL + { + public: + explicit DSL( const Comparable & inf ); + DSL( const DSL & rhs ); + ~DSL( ); + + const Comparable & findMin( ) const; + const Comparable & findMax( ) const; + const Comparable & find( const Comparable & x ) const; + bool isEmpty( ) const; + void printList( ) const; + + void makeEmpty( ); + void insert( const Comparable & x ); + void remove( const Comparable & x ); + + const DSL & operator=( const DSL & rhs ); + private: + const Comparable INFINITY; + SkipNode *header; // The list + SkipNode *bottom; + SkipNode *tail; + + const Comparable & elementAt( SkipNode * t ) const; + + // Usual recursive stuff + void reclaimMemory( SkipNode *t ) const; + }; + + #include "DSL.cpp" + #endif diff --git a/c++/Others/Demonstrates the use of a simple C++ class.cpp b/c++/Others/Demonstrates the use of a simple C++ class.cpp new file mode 100644 index 0000000..e4e34de --- /dev/null +++ b/c++/Others/Demonstrates the use of a simple C++ class.cpp @@ -0,0 +1,31 @@ +Demonstrates the use of a simple C++ class + +#include +using namespace std; + +class cl { + int i; // private by default +public: + int get_i(); + void put_i(int j); +}; + +int cl::get_i() +{ + return i; +} + +void cl::put_i(int j) +{ + i = j; +} + +int main() +{ + cl s; + + s.put_i(10); + cout << s.get_i() < +#include +using namespace std; + +int main() +{ + // initialize an array of char pointers with five fortunes + const char* const Fortune[5] = + {" Earth is a great funhouse without the fun.", + " There is always more hell that needs raising.", + " Confession is good for the soul, but bad for the career.", + " Live in a world of your own, but always welcome visitors.", + " The man who laughs has not yet been told the terrible news." + }; + cout << "Here are the 5 fortunes: " << endl; + for(int i = 0; i < 5; i++) + { + cout << Fortune[i] << endl; + } + + +} diff --git a/c++/Others/Demonstrates the use of structure in C++..cpp b/c++/Others/Demonstrates the use of structure in C++..cpp new file mode 100644 index 0000000..e8e3e4e --- /dev/null +++ b/c++/Others/Demonstrates the use of structure in C++..cpp @@ -0,0 +1,34 @@ +Demonstrates the use of structure in C++. +Stores some personal data in a structure, then prints the info out. + +#include +using namespace std; + +int main() +{ + // Defining a structure + struct PersonalData + { + char *FirstName; + char *LastName; + char *Birthday; // in the format of 12/27/1978 + int PhoneNum; + }; // don't forget the ending ";" + + // Declaring a variable of type PersonalData + PersonalData PersonOne; + + // Populate PersonOne with data + PersonOne.FirstName = "Kyra"; + PersonOne.LastName = "Red"; + PersonOne.Birthday = "12/27/1978"; + PersonOne.PhoneNum = 5855555; + + // Print the data out + cout << "PersonOne's First name is: " << PersonOne.FirstName << endl; + cout << "PersonOne's Last name is: " << PersonOne.LastName<< endl; + cout << "PersonOne's Birthday is: " << PersonOne.Birthday<< endl; + cout << "PersonOne's Phone number is: " << PersonOne.PhoneNum<< endl; + + return 0; +} diff --git a/c++/Others/DisjSets.cpp - Efficient implementation of disjoint sets algorithm.cpp b/c++/Others/DisjSets.cpp - Efficient implementation of disjoint sets algorithm.cpp new file mode 100644 index 0000000..bde0540 --- /dev/null +++ b/c++/Others/DisjSets.cpp - Efficient implementation of disjoint sets algorithm.cpp @@ -0,0 +1,61 @@ +DisjSets.cpp - Efficient implementation of disjoint sets algorithm + +#include "DisjSets.h" + +/** + * Construct the disjoint sets object. + * numElements is the initial number of disjoint sets. + */ +DisjSets::DisjSets( int numElements ) : s( numElements ) +{ + for( int i = 0; i < s.size( ); i++ ) + s[ i ] = -1; +} + +/** + * Union two disjoint sets. + * For simplicity, we assume root1 and root2 are distinct + * and represent set names. + * root1 is the root of set 1. + * root2 is the root of set 2. + */ +void DisjSets::unionSets( int root1, int root2 ) +{ + if( s[ root2 ] < s[ root1 ] ) // root2 is deeper + s[ root1 ] = root2; // Make root2 new root + else + { + if( s[ root1 ] == s[ root2 ] ) + s[ root1 ]--; // Update height if same + s[ root2 ] = root1; // Make root1 new root + } +} + + +/** + * Perform a find. + * Error checks omitted again for simplicity. + * Return the set containing x. + */ +int DisjSets::find( int x ) const +{ + if( s[ x ] < 0 ) + return x; + else + return find( s[ x ] ); +} + + +/** + * Perform a find with path compression. + * Error checks omitted again for simplicity. + * Return the set containing x. + */ +int DisjSets::find( int x ) +{ + if( s[ x ] < 0 ) + return x; + else + return s[ x ] = find( s[ x ] ); +} + diff --git a/c++/Others/DisjSets.h - Header file for disjoint sets algorithms.cpp b/c++/Others/DisjSets.h - Header file for disjoint sets algorithms.cpp new file mode 100644 index 0000000..3cb4b54 --- /dev/null +++ b/c++/Others/DisjSets.h - Header file for disjoint sets algorithms.cpp @@ -0,0 +1,37 @@ +DisjSets.h - Header file for disjoint sets algorithms + +#ifndef DISJ_SETS_H +#define DISJ_SETS_H + +// DisjSets class +// +// CONSTRUCTION: with int representing initial number of sets +// +// ******************PUBLIC OPERATIONS********************* +// void union( root1, root2 ) --> Merge two sets +// int find( x ) --> Return set containing x +// ******************ERRORS******************************** +// No error checking is performed + +#include +using namespace std; + +/** + * Disjoint set class. + * Use union by rank and path compression. + * Elements in the set are numbered starting at 0. + */ +class DisjSets +{ + public: + explicit DisjSets( int numElements ); + + int find( int x ) const; + int find( int x ); + void unionSets( int root1, int root2 ); + + private: + vector s; +}; + +#endif diff --git a/c++/Others/Drawing Pad - An Easy way to create circles, recta.cpp b/c++/Others/Drawing Pad - An Easy way to create circles, recta.cpp new file mode 100644 index 0000000..972e8eb --- /dev/null +++ b/c++/Others/Drawing Pad - An Easy way to create circles, recta.cpp @@ -0,0 +1,484 @@ +Drawing Pad - An Easy way to create circles, rectangles etc. + + +#include +#include +#include +#include +#include +#include +#include +#include +#include + + class mouse + { + union REGS i, o; + public: + + mouse() + { + initmouse(); + showmouseptr(); + } + + void initmouse() + { + i.x.ax=0; + int86(0x33,&i,&o); + } + + void showmouseptr() + { + i.x.ax=1; + int86(0x33,&i,&o); + } + + void hidemouseptr() + { + i.x.ax=2; + int86(0x33,&i,&o); + } + + void getmousepos(int& button, int& x, int& y) + { + i.x.ax=3; + int86(0x33,&i,&o); + button=o.x.bx; + x=o.x.cx; + y=o.x.dx; + } + + void restrictmouseptr(int x1, int y1, int x2, int y2) + { + i.x.ax=7; + i.x.cx=x1; + i.x.dx=x2; + int86(0x33,&i,&o); + i.x.ax=8; + i.x.cx=y1; + i.x.dx=y2; + int86(0x33,&i,&o); + } + + }; + + class shapes + { + public: + + virtual void draw() + { + } + + virtual void save (ofstream &ft) + { + } + + virtual void open(ifstream &fs) + { + } + + }; + + class myline:public shapes + { + int sx,sy,ex,ey,color; + public: + + myline() + { + } + + myline(int x1,int y1,int x2,int y2,int clr) + { + sx=x1; + sy=y1; + ex=x2; + ey=y2; + color=clr; + } + + void draw() + { + setcolor(color); + moveto(sx,sy); + lineto(ex,ey); + } + + void save(ofstream &ft) + { + ft<<"L"<<" +"; + ft<>sx>>sy>>ex>>ey>>color; + } + + }; + + class myrectangle:public shapes + { + int sx,sy,ex,ey,color; + public: + + myrectangle() + { + } + + myrectangle(int x1,int y1,int x2,int y2,int clr) + { + sx=x1; + sy=y1; + ex=x2; + ey=y2; + color=clr; + } + + void draw() + { + setcolor(color); + rectangle(sx,sy,ex,ey); + } + + void save(ofstream &ft) + { + ft<<"R"<<" +"; + ft<>sx>>sy>>ex>>ey>>color; + } + + }; + + class mycircle:public shapes + { + int sx,sy,radius,color; + public: + + mycircle() + { + } + + mycircle(int x1,int y1,int r,int clr) + { + sx=x1; + sy=y1; + radius=r; + color=clr; + } + + void draw() + { + setcolor(color); + circle(sx,sy,radius); + } + + void save(ofstream &ft) + { + ft<<"C"<<" +"; + ft<>sx>>sy>>radius>>color; + } + + }; + + struct node + { + void *obj; + node *link; + }; + + class objarray + { + node *head; + public: + + objarray() + { + head =NULL; + } + + void add(void *o) + { + node *temp =new node; + temp->obj=o; + temp->link=NULL; + if(head==NULL) + head=temp; + else + { + node *q; + q=head; + while(q->link!=NULL) + q=q->link; + q->link=temp; + } + } + + void *getobj(int i) + { + node *q; + q=head; + for(int n=1; nlink; + return(q->obj); + } + + int getcount() + { + int n=0; + node *q; + q=head; + while(q!=NULL) + { + q=q->link; + n++; + } + return n; + } + + ~objarray() + { + node *q; + q=head; + while(q!=NULL) + { + head=head->link; + delete q; + q=head; + } + } + + }; + + void mainscreen() + { + cleardevice(); + rectangle(0,0,639,479); + line(0,30,640,30); + char *names[]={"Clear","Open","Save","Line","Rect","Circ","Exit"}; + int x,i; + for(x=5,i=0;x<=7*90;x+=90,i++) + { + setcolor(WHITE); + rectangle(x,5,x+70,25); + floodfill(x+1,6,WHITE); + settextstyle(1,0,3); + setcolor(BLACK); + outtextxy(x+10,0,names[i]); + } + } + void DisplayName(int ycor) + { + char *name[] = {"D","R","A","W","I","N","G"," ","P","A","D"}; + int i; + settextjustify(1,1); + settextstyle(4,0,7); + for(i=0;i<11;i++) + { + setcolor(i+2); + outtextxy(40+i*45,ycor, name[i]); + } + } + music() + { + int i ; + float octave[7] = { 830.81, 846.83, 864.81, 674.61, 596, 420, 1046.94 +} ; + for ( i = 0 ; i < 7 ; i++ ) + { + sound ( octave[i] * 5 ) ; + delay ( 30 ) ; + } + nosound(); + } + + void Welcome() + { + char pattern[8] = {0x00, 0x70, 0x12, 0x27, 0x00, 0x27, 0x20, 0x70}; + int i; + + setfillpattern(pattern,BLUE); + for(i=0;i<=320;i++) + { + bar(320-i,240-i*0.75,320+i,240+i*0.75); + delay (0.3) ; + } + settextjustify(1,1); + DisplayName(100); + settextstyle(5,0,4); + outtextxy(100,300,"Hello "); + settextstyle(7,0,6); + setcolor(11); + outtextxy(320,350,"World"); + music(); + delay(1000); + } + + void main() + { + ifstream fs; + ofstream ft; + int gd= DETECT,gm; + initgraph(&gd,&gm,"C:\tc\bgi"); + mainscreen(); + music(); + setviewport(1,31,638,478,1); + mouse m; + int button,x,y,flag=0; + int t,i,index; + int strptx,strpty,endptx,endpty; + objarray arr; + while(1) + { + button=0; + m.getmousepos(button,x,y); + if(((button &1)==1)&&(flag==0)) + for(t=5,i=0;t<=7*90;t+=90,i++) + if(x>=t && x<=t+70 && y>=5 && y<=25) + { + index=i; + flag=1; + break; + } + int clmum=random(16); + int sx=random(638); + int sy=random(478); + int ex=random(638); + int ey=random(478); + int r=random(200); + + switch(index) + { + case 0: + m.getmousepos(button,x,y); + if(((button &1)==0)&&(flag==1)) + { + clearviewport(); + flag=0; + } + break; + case 1: + m.getmousepos(button,x,y); + if(((button &1)==0)&&(flag==1)) + { + fs.open("output.txt",ios::in); + shapes *ptr; + char a[2]; + while(fs) + { + fs>>a; + if(strcmp(a,"L")==0) + { + myline *l=new myline(); + l->open(fs); + arr.add(l); + } + + if(strcmp(a,"R")==0) + { + myrectangle *r=new myrectangle(); + r->open(fs); + arr.add(r); + } + + if(strcmp(a,"C")==0) + { + mycircle *c=new mycircle(); + c->open(fs); + arr.add(c); + } + } + fs.close(); + int count=arr.getcount(); + for(int i=1;i<=count;i++) + { + ptr=(shapes*)arr.getobj(i); + ptr->draw(); + } + flag=0; + } + break; + case 2: + m.getmousepos(button,x,y); + if(((button &1)==0)&&(flag==1)) + { + ft.open("output.txt",ios::out); + int count=arr.getcount(); + shapes *ptr; + for(i=1;i<=count;i++) + { + ptr=(shapes*)arr.getobj(i); + ptr->save(ft); + } + ft.close(); + flag=0; + } + break; + + case 3: + m.getmousepos(button,x,y); + if(((button &1)==0)&&(flag==1)) + { + setcolor(clmum); + moveto(sx,sy); + lineto(ex,ey); + myline *l=new myline(sx,sy,ex,ey,clmum); + if(l==NULL) + exit(1); + arr.add(l); + flag=0; + } + break; + + case 4: + m.getmousepos(button,x,y); + if(((button &1)==0)&&(flag==1)) + { + setcolor(clmum); + rectangle(sx,sy,ex,ey); + myrectangle *r=new myrectangle(sx,sy,ex,ey,clmum); + if(r==NULL) + exit(1); + arr.add(r); + flag=0; + } + break; + + case 5: + m.getmousepos(button,x,y); + if(((button &1)==0)&&(flag==1)) + { + setcolor(clmum); + circle(sx,sy,r); + mycircle *c=new mycircle(sx,sy,r,clmum); + if(r==NULL) + exit(1); + arr.add(c); + flag=0; + } + break; + } + if(index==6) + break; + } + Welcome(); + closegraph(); + restorecrtmode(); + } diff --git a/c++/Others/Enum example.cpp b/c++/Others/Enum example.cpp new file mode 100644 index 0000000..a5b6eae --- /dev/null +++ b/c++/Others/Enum example.cpp @@ -0,0 +1,22 @@ +Enum example + +An enum example in C++ + +#include +int main() +{ +enum Days{Sunday,Monday,Tuesday,Wednesday,Thursday,Friday,Saturday}; + +Days TheDay; +int j; +cout<<"Please enter the day of the week (0 to 6)"; +cin>>j; +TheDay = Days(j); + +if(TheDay == Sunday || TheDay == Saturday) +cout<<"Hurray it is the weekend"< +# include + +class publication +{ + char title[30]; + float price; +public: + void getdata() + { + cout<<"Enter the title : + "; cin>>title; + cout<<"Enter the price : + "; cin>>price; + } + void putdata() + { + cout<<"The title is : "<>pages; + } + void putdata() + { + cout<<" BOOK DETAILS +"; + publication::putdata(); + cout<<"Number of pages : " <>time; + } + void putdata() + { + cout<<" TAPE DETAILS "; + publication::putdata(); + cout<<"Time length :"<< time< +#include +#include + +void c_to_f(void); +void f_to_c(void); + +void + main(void) +{ + int choice; + char again; + do + { + system("CLS"); + + cout << setw(10) <<" "<< "What conversion would you like to make?\n"; // menu + cout << setw(20) <<" "<< "1. Celsius to Fahrenheit\n\n"; // make a choice which function to use. + cout << setw(20) <<" "<< "2. Fahrenheit to celsius\n\n"; + cin >> choice; + + switch(choice) // go to chosen function. + { + case 1 : + { + c_to_f(); + break; + } + case 2 : + { + f_to_c(); + break; + } + default : + { + cout << setw(10) <<" "<< "you must enter 1 or 2 "<< endl ; // validate and correct input of function choice. + + } + + + } + + + + cout << setw(10) <<" "<< "Do you wish to do another conversion? y for yes, n for no "; // rerun loop on y for yes + cin >> again; + }while (again == 'Y' || again =='y'); + +} + + +void c_to_f(void) +{ + system("CLS"); // clear screen for function data. + int temp,fahrenheit; + + cout << "\n\n\n"; + cout << setw(10) <<" "<< "Enter the temperature in whole degrees celsius. \a"; + cin >> temp; + + fahrenheit = ((temp * 9) / 5) + 32; + cout << endl << setw(10) <<" "<< temp << " degrees celsius is " << fahrenheit << " degrees fahrenheit \a\n\n\n"; +} + +void f_to_c(void) +{ + system("CLS"); // clear screen for function data. + int temp,celsius; + + cout << "\n\n\n"; + cout << setw(10) <<" "<< "Enter the temperature in whole degrees fahrenheit. \a"; + cin >> temp; + + celsius = ((temp - 32) * 5) / 9; + + cout << endl < +int main() +{ +double fahr , celsius; +cout<<"Enter the temperature in degrees fahrenheit: "; +cin>>fahr; +//convert to celsius +celsius = (5.0 / 9.0) * (fahr - 32.0); +cout<<"The temperature in celsius is "< +#include + +main() +{ + const unsigned long limit=4294967295; + unsigned long next=0; + unsigned long last=1; + long sum; + + clrscr(); + + cout<<"\n\nThis program will print the Fibonacci series :\n\n "; + while(next + + int f( int x ) + { +/* 1*/ if( x == 0 ) +/* 2*/ return 0; + else +/* 3*/ return 2 * f( x - 1 ) + x * x; + } + + int main( ) + { + cout << "f(5) = " << f( 5 ) << endl; + return 0; + } diff --git a/c++/Others/Fig01_03.cpp - An example of infinite recursion.cpp b/c++/Others/Fig01_03.cpp - An example of infinite recursion.cpp new file mode 100644 index 0000000..0fe98e4 --- /dev/null +++ b/c++/Others/Fig01_03.cpp - An example of infinite recursion.cpp @@ -0,0 +1,17 @@ +Fig01_03.cpp - An example of infinite recursion + + #include + + int bad( int n ) + { +/* 1*/ if( n == 0 ) +/* 2*/ return 0; + else +/* 3*/ return bad( n / 3 + 1 ) + n - 1; + } + + int main( ) + { + cout << "bad is infinite recursion" << endl; + return 0; + } diff --git a/c++/Others/Fig01_04.cpp - Recursive routine to print numbers, with a test program.cpp b/c++/Others/Fig01_04.cpp - Recursive routine to print numbers, with a test program.cpp new file mode 100644 index 0000000..4229b21 --- /dev/null +++ b/c++/Others/Fig01_04.cpp - Recursive routine to print numbers, with a test program.cpp @@ -0,0 +1,24 @@ +Fig01_04.cpp - Recursive routine to print numbers, with a test program + + #include + + void printDigit( int n ) + { + cout << n; + } + +/* START: Fig01_04.txt */ + void printOut( int n ) // Print nonnegative n + { + if( n >= 10 ) + printOut( n / 10 ); + printDigit( n % 10 ); + } +/* END */ + + int main( ) + { + printOut( 1369 ); + cout << endl; + return 0; + } diff --git a/c++/Others/Fig01_05.cpp - Simplest IntCell class, with a test program.cpp b/c++/Others/Fig01_05.cpp - Simplest IntCell class, with a test program.cpp new file mode 100644 index 0000000..3c5965c --- /dev/null +++ b/c++/Others/Fig01_05.cpp - Simplest IntCell class, with a test program.cpp @@ -0,0 +1,49 @@ +Fig01_05.cpp - Simplest IntCell class, with a test program + + #include + + /** + * A class for simulating an integer memory cell. + */ + class IntCell + { + public: + /** + * Construct the IntCell. + * Initial value is 0. + */ + IntCell( ) + { storedValue = 0; } + + /** + * Construct the IntCell. + * Initial value is initialValue. + */ + IntCell( int initialValue ) + { storedValue = initialValue; } + + /** + * Return the stored value. + */ + int read( ) + { return storedValue; } + + /** + * Change the stored value to x. + */ + void write( int x ) + { storedValue = x; } + + private: + int storedValue; + }; + + int main( ) + { + IntCell m; + + m.write( 5 ); + cout << "Cell contents: " << m.read( ) << endl; + + return 0; + } diff --git a/c++/Others/Fig01_06.cpp - IntCell class with a few extras, with a test program.cpp b/c++/Others/Fig01_06.cpp - IntCell class with a few extras, with a test program.cpp new file mode 100644 index 0000000..a0edb0b --- /dev/null +++ b/c++/Others/Fig01_06.cpp - IntCell class with a few extras, with a test program.cpp @@ -0,0 +1,29 @@ +Fig01_06.cpp - IntCell class with a few extras, with a test program + + #include + + /** + * A class for simulating an integer memory cell. + */ + class IntCell + { + public: +/* 1*/ explicit IntCell( int initialValue = 0 ) +/* 2*/ : storedValue( initialValue ) { } +/* 3*/ int read( ) const +/* 4*/ { return storedValue; } +/* 5*/ void write( int x ) +/* 6*/ { storedValue = x; } + private: +/* 7*/ int storedValue; + }; + + int main( ) + { + IntCell m; + + m.write( 5 ); + cout << "Cell contents: " << m.read( ) << endl; + + return 0; + } diff --git a/c++/Others/Fig01_10.cpp - Illustration of using the vector class.cpp b/c++/Others/Fig01_10.cpp - Illustration of using the vector class.cpp new file mode 100644 index 0000000..42c4942 --- /dev/null +++ b/c++/Others/Fig01_10.cpp - Illustration of using the vector class.cpp @@ -0,0 +1,23 @@ +Fig01_10.cpp - Illustration of using the vector class + + #include + #include "vector.h" // vector (our version, in Appendix B) + #include "mystring.h" // string (our version, in Appendix B) + + int main( ) + { + vector v( 5 ); + int itemsRead = 0; + string x; + + while( cin >> x ) + { + if( itemsRead == v.size( ) ) + v.resize( v.size( ) * 2 ); + v[ itemsRead++ ] = x; + } + + for( int i = itemsRead - 1; i >= 0; i-- ) + cout << v[ i ] << endl; + return 0; + } diff --git a/c++/Others/Fig01_11.cpp - Dynamically allocating an IntCell object (lame).cpp b/c++/Others/Fig01_11.cpp - Dynamically allocating an IntCell object (lame).cpp new file mode 100644 index 0000000..d7511e1 --- /dev/null +++ b/c++/Others/Fig01_11.cpp - Dynamically allocating an IntCell object (lame).cpp @@ -0,0 +1,16 @@ +Fig01_11.cpp - Dynamically allocating an IntCell object (lame) + + #include + #include "IntCell.h" + + int main( ) + { +/* 1*/ IntCell *m; + +/* 2*/ m = new IntCell( 0 ); +/* 3*/ m->write( 5 ); +/* 4*/ cout << "Cell contents: " << m->read( ) << endl; + +/* 5*/ delete m; +/* 6*/ return 0; + } diff --git a/c++/Others/Fig01_16.cpp - IntCell class with pointers and Big Three.cpp b/c++/Others/Fig01_16.cpp - IntCell class with pointers and Big Three.cpp new file mode 100644 index 0000000..3d663e6 --- /dev/null +++ b/c++/Others/Fig01_16.cpp - IntCell class with pointers and Big Three.cpp @@ -0,0 +1,72 @@ +Fig01_16.cpp - IntCell class with pointers and Big Three + + #include + class IntCell + { + public: + explicit IntCell( int initialValue = 0 ); + + IntCell( const IntCell & rhs ); + ~IntCell( ); + const IntCell & operator=( const IntCell & rhs ); + + int read( ) const; + void write( int x ); + private: + int *storedValue; + }; + + IntCell::IntCell( int initialValue ) + { + storedValue = new int( initialValue ); + } + + IntCell::IntCell( const IntCell & rhs ) + { + storedValue = new int( *rhs.storedValue ); + } + + IntCell::~IntCell( ) + { + delete storedValue; + } + + const IntCell & IntCell::operator=( const IntCell & rhs ) + { + if( this != &rhs ) + *storedValue = *rhs.storedValue; + return *this; + } + + int IntCell::read( ) const + { + return *storedValue; + } + + void IntCell::write( int x ) + { + *storedValue = x; + } + + + /* + * Figure 1.15. + */ + int f( ) + { + IntCell a( 2 ); + IntCell b = a; + IntCell c; + + c = b; + a.write( 4 ); + cout << a.read( ) << endl << b.read( ) << endl << c.read( ) << endl; + return 0; + } + + + int main( ) + { + f( ); + return 0; + } diff --git a/c++/Others/Fig01_19.cpp - MemoryCell class template without separation.cpp b/c++/Others/Fig01_19.cpp - MemoryCell class template without separation.cpp new file mode 100644 index 0000000..be77583 --- /dev/null +++ b/c++/Others/Fig01_19.cpp - MemoryCell class template without separation.cpp @@ -0,0 +1,44 @@ +Fig01_19.cpp - MemoryCell class template without separation + + #include + #include "mystring.h" + + + /** + * A class for simulating a memory cell. + */ + template + class MemoryCell + { + public: + explicit MemoryCell( const Object & initialValue = Object( ) ) + : storedValue( initialValue ) { } + const Object & read( ) const + { return storedValue; } + void write( const Object & x ) + { storedValue = x; } + private: + Object storedValue; + }; + + // OOPS: I forgot to put a + operator in the string class. + // So it's here: + + string operator+( const string & lhs, const string & rhs ) + { + string result = lhs; + return result += rhs; + + } + + int main( ) + { + MemoryCell m1; + MemoryCell m2( "hello" ); + + m1.write( 37 ); + m2.write( m2.read( ) + " world" ); + cout << m1.read( ) << endl << m2.read( ) << endl; + + return 0; + } diff --git a/c++/Others/Fig01_23.cpp - Using Comparable templates - Employ.cpp b/c++/Others/Fig01_23.cpp - Using Comparable templates - Employ.cpp new file mode 100644 index 0000000..422cad8 --- /dev/null +++ b/c++/Others/Fig01_23.cpp - Using Comparable templates - Employ.cpp @@ -0,0 +1,58 @@ +Fig01_23.cpp - Using Comparable templates - Employee class example + + #include + #include "vector.h" + #include "mystring.h" + + class Employee + { + public: + void setValue( const string & n, double s ) + { name = n; salary = s; } + + void print( ostream & out ) const + { out << name << " (" << salary << ")"; } + bool operator< ( const Employee & rhs ) const + { return salary < rhs.salary; } + + // Other general accessors and mutators, not shown + private: + string name; + double salary; + }; + + // Define an output operator for Employee + ostream & operator<< ( ostream & out, const Employee & rhs ) + { + rhs.print( out ); + return out; + } + + /** + * Return the maximum item in array a. + * Assumes a.size( ) > 0. + * Comparable objects must provide + * copy constructor, operator<, operator= + */ + template + const Comparable & findMax( const vector & a ) + { +/* 1*/ int maxIndex = 0; + +/* 2*/ for( int i = 1; i < a.size( ); i++ ) +/* 3*/ if( a[ maxIndex ] < a[ i ] ) +/* 4*/ maxIndex = i; +/* 5*/ return a[ maxIndex ]; + } + + int main( ) + { + vector v( 3 ); + + v[0].setValue( "Bill Clinton", 200000.00 ); + v[1].setValue( "Bill Gates", 2000000000.00 ); + v[2].setValue( "Billy the Marlin", 60000.00 ); + cout << findMax( v ) << endl; + + return 0; + } diff --git a/c++/Others/Fig02_09.cpp - Test program for binary search.cpp b/c++/Others/Fig02_09.cpp - Test program for binary search.cpp new file mode 100644 index 0000000..c405f03 --- /dev/null +++ b/c++/Others/Fig02_09.cpp - Test program for binary search.cpp @@ -0,0 +1,45 @@ +Fig02_09.cpp - Test program for binary search + + #include + #include "vector.h" + + const int NOT_FOUND = -1; + +/* START: Fig02_09.txt*/ + /** + * Performs the standard binary search using two comparisons per level. + * Returns index where item is found or -1 if not found + */ + template + int binarySearch( const vector & a, const Comparable & x ) + { +/* 1*/ int low = 0, high = a.size( ) - 1; + +/* 2*/ while( low <= high ) + { +/* 3*/ int mid = ( low + high ) / 2; + +/* 4*/ if( a[ mid ] < x ) +/* 5*/ low = mid + 1; +/* 6*/ else if( a[ mid ] > x ) +/* 7*/ high = mid - 1; + else +/* 8*/ return mid; // Found + } +/* 9*/ return NOT_FOUND; // NOT_FOUND is defined as -1 + } +/* END */ + + // Test program + int main( ) + { + const int SIZE = 8; + vector a( SIZE ); + + for( int i = 0; i < SIZE; i++ ) + a[ i ] = i * 2; + + for( int j = 0; j < SIZE * 2; j++ ) + cout << "Found " << j << " at " << binarySearch( a, j ) << endl; + return 0; + } diff --git a/c++/Others/Fig02_10.cpp - Euclid's algorithm, with a test program.cpp b/c++/Others/Fig02_10.cpp - Euclid's algorithm, with a test program.cpp new file mode 100644 index 0000000..b68631c --- /dev/null +++ b/c++/Others/Fig02_10.cpp - Euclid's algorithm, with a test program.cpp @@ -0,0 +1,24 @@ +Fig02_10.cpp - Euclid's algorithm, with a test program + + #include + +/* START: Fig02_10.txt*/ + long gcd( long m, long n ) + { +/* 1*/ while( n != 0 ) + { +/* 2*/ long rem = m % n; +/* 3*/ m = n; +/* 4*/ n = rem; + } +/* 5*/ return m; + } +/* END */ + + // Test program + int main( ) + { + cout << "gcd( 45, 35 ) = " << gcd( 45, 35 ) << endl; + cout << "gcd( 1989, 1590 ) = " << gcd( 1989, 1590 ) << endl; + return 0; + } diff --git a/c++/Others/Fig02_11.cpp - Recursive exponentiation algorithm, with a test program.cpp b/c++/Others/Fig02_11.cpp - Recursive exponentiation algorithm, with a test program.cpp new file mode 100644 index 0000000..50924f4 --- /dev/null +++ b/c++/Others/Fig02_11.cpp - Recursive exponentiation algorithm, with a test program.cpp @@ -0,0 +1,30 @@ +Fig02_11.cpp - Recursive exponentiation algorithm, with a test program + + #include + + bool isEven( int n ) + { + return n % 2 == 0; + } + +/* START: Fig02_11.txt*/ + long pow( long x, int n ) + { +/* 1*/ if( n == 0 ) +/* 2*/ return 1; +/* 3*/ if( n == 1 ) +/* 4*/ return x; +/* 5*/ if( isEven( n ) ) +/* 6*/ return pow( x * x, n / 2 ); + else +/* 7*/ return pow( x * x, n / 2 ) * x; + } +/* END */ + + // Test program + int main( ) + { + cout << "2^21 = " << pow( 2, 21 ) << endl; + cout << "2^30 = " << pow( 2, 30 ) << endl; + return 0; + } diff --git a/c++/Others/Fig10_38.cpp - Simple matrix multiplication algori.cpp b/c++/Others/Fig10_38.cpp - Simple matrix multiplication algori.cpp new file mode 100644 index 0000000..c2726c1 --- /dev/null +++ b/c++/Others/Fig10_38.cpp - Simple matrix multiplication algori.cpp @@ -0,0 +1,43 @@ +Fig10_38.cpp - Simple matrix multiplication algorithm with a test program + + #include + #include "matrix.h" + +/* START: Fig10_38.txt */ + /** + * Standard matrix multiplication. + * Arrays start at 0. + * Assumes a and b are square. + */ + matrix operator*( const matrix & a, const matrix & b ) + { + int n = a.numrows( ); + matrix c( n, n ); + + int i; + for( i = 0; i < n; i++ ) // Initialization + for( int j = 0; j < n; j++ ) + c[ i ][ j ] = 0; + + for( i = 0; i < n; i++ ) + for( int j = 0; j < n; j++ ) + for( int k = 0; k < n; k++ ) + c[ i ][ j ] += a[ i ][ k ] * b[ k ][ j ]; + + return c; + } +/* END */ + + int main( ) + { + matrix a( 2, 2 ); + a[ 0 ][ 0 ] = 1; a[ 0 ][ 1 ] = 2; + a[ 1 ][ 0 ] = 3; a[ 1 ][ 1 ] = 4; + + matrix c = a * a; + + cout << c[ 0 ][ 0 ] << " " << c[ 0 ][ 1 ] << endl << + c[ 1 ][ 0 ] << " " << c[ 1 ][ 1 ] << endl; + + return 0; + } diff --git a/c++/Others/Fig10_40.cpp - Algorithms to compute Fibonacci numbers.cpp b/c++/Others/Fig10_40.cpp - Algorithms to compute Fibonacci numbers.cpp new file mode 100644 index 0000000..d4da5ff --- /dev/null +++ b/c++/Others/Fig10_40.cpp - Algorithms to compute Fibonacci numbers.cpp @@ -0,0 +1,45 @@ +Fig10_40.cpp - Algorithms to compute Fibonacci numbers + + #include + +/* START: Fig10_40.txt */ + /** + * Compute Fibonacci numbers as described in Chapter 1. + */ + int fib( int n ) + { + if( n <= 1 ) + return 1; + else + return fib( n - 1 ) + fib( n - 2 ); + } +/* END */ + +/* START: Fig10_41.txt */ + /** + * Compute Fibonacci numbers as described in Chapter 1. + */ + int fibonacci( int n ) + { + if( n <= 1 ) + return 1; + + int last = 1; + int nextToLast = 1; + int answer = 1; + for( int i = 2; i <= n; i++ ) + { + answer = last + nextToLast; + nextToLast = last; + last = answer; + } + return answer; + } +/* END */ + + int main( ) + { + cout << "fib( 7 ) = " << fib( 7 ) << endl; + cout << "fibonacci( 7 ) = " << fibonacci( 7 ) << endl; + return 0; + } diff --git a/c++/Others/Fig10_43.cpp - Inefficient recursive algorithm (see text).cpp b/c++/Others/Fig10_43.cpp - Inefficient recursive algorithm (see text).cpp new file mode 100644 index 0000000..bf3df9c --- /dev/null +++ b/c++/Others/Fig10_43.cpp - Inefficient recursive algorithm (see text).cpp @@ -0,0 +1,24 @@ +Fig10_43.cpp - Inefficient recursive algorithm (see text) + + #include + +/* START: Fig10_43.txt */ + double eval( int n ) + { + if( n == 0 ) + return 1.0; + else + { + double sum = 0.0; + for( int i = 0; i < n; i++ ) + sum += eval( i ); + return 2.0 * sum / n + n; + } + } +/* END */ + + int main( ) + { + cout << "eval( 10 ) = " << eval( 10 ) << endl; + return 0; + } diff --git a/c++/Others/Fig10_45.cpp - Better algorithm to replace fig10_43.c (see text).cpp b/c++/Others/Fig10_45.cpp - Better algorithm to replace fig10_43.c (see text).cpp new file mode 100644 index 0000000..dd07eb6 --- /dev/null +++ b/c++/Others/Fig10_45.cpp - Better algorithm to replace fig10_43.c (see text).cpp @@ -0,0 +1,28 @@ +Fig10_45.cpp - Better algorithm to replace fig10_43.c (see text) + + #include + #include "vector.h" + +/* START: Fig10_45.txt */ + double eval( int n ) + { + vector c( n + 1 ); + + c[ 0 ] = 1.0; + for( int i = 1; i <= n; i++ ) + { + double sum = 0.0; + for( int j = 0; j < i; j++ ) + sum += c[ j ]; + c[ i ] = 2.0 * sum / i + i; + } + + return c[ n ]; + } +/* END */ + + int main( ) + { + cout << "eval( 10 ) = " << eval( 10 ) << endl; + return 0; + } diff --git a/c++/Others/Fig10_46.cpp - Dynamic programming algorithm for optimal chain matrix multiplication,.cpp b/c++/Others/Fig10_46.cpp - Dynamic programming algorithm for optimal chain matrix multiplication,.cpp new file mode 100644 index 0000000..4f8372e --- /dev/null +++ b/c++/Others/Fig10_46.cpp - Dynamic programming algorithm for optimal chain matrix multiplication,.cpp @@ -0,0 +1,72 @@ +Fig10_46.cpp - Dynamic programming algorithm for optimal chain matrix multiplication, +with a test program + + #include + #include + #include "matrix.h" + +/* START: Fig10_46.txt */ + const long INFINITY = LONG_MAX; + + /** + * Compute optimal ordering of matrix multiplication. + * c contains the number of columns for each of the n matrices. + * c[ 0 ] is the number of rows in matrix 1. + * The minimum number of multiplications is left in m[ 1 ][ n ]. + * Actual ordering is computed via another procedure using lastChange. + * m and lastChange are indexed starting at 1, instead of 0. + * Note: Entries below main diagonals of m and lastChange + * are meaningless and uninitialized. + */ + void optMatrix( const vector & c, + matrix & m, matrix & lastChange ) + { + int n = c.size( ) - 1; + + for( int left = 1; left <= n; left++ ) + m[ left ][ left ] = 0; + for( int k = 1; k < n; k++ ) // k is right - left + for( int left = 1; left <= n - k; left++ ) + { + // For each position + int right = left + k; + m[ left ][ right ] = INFINITY; + for( int i = left; i < right; i++ ) + { + long thisCost = m[ left ][ i ] + m[ i + 1 ][ right ] + + c[ left - 1 ] * c[ i ] * c[ right ]; + if( thisCost < m[ left ][ right ] ) // Update min + { + m[ left ][ right ] = thisCost; + lastChange[ left ][ right ] = i; + } + } + } + } +/* END */ + + int main( ) + { + vector c( 5 ); + c[ 0 ] = 50; c[ 1 ] = 10; c[ 2 ] = 40; c[ 3 ] = 30; c[ 4 ] = 5; + matrix m( 5, 5 ); + matrixlastChange( 5, 5 ); + + optMatrix( c, m, lastChange ); + + int i; + for( i = 1; i < m.numrows( ); i++ ) + { + for( int j = 1; j < m.numcols( ); j++ ) + cout << m[ i ][ j ] << " "; + cout << endl; + } + for( i = 1; i < lastChange.numrows( ); i++ ) + { + for( int j = 1; j < lastChange.numcols( ); j++ ) + cout << lastChange[ i ][ j ] << " "; + cout << endl; + } + + return 0; + } diff --git a/c++/Others/Fig10_53.cpp - All-pairs algorithm, with a test program.cpp b/c++/Others/Fig10_53.cpp - All-pairs algorithm, with a test program.cpp new file mode 100644 index 0000000..5fed889 --- /dev/null +++ b/c++/Others/Fig10_53.cpp - All-pairs algorithm, with a test program.cpp @@ -0,0 +1,73 @@ +Fig10_53.cpp - All-pairs algorithm, with a test program + + #include + #include "matrix.h" + +/* START: Fig10_53.txt */ + const int NOT_A_VERTEX = -1; + + /** + * Compute all-shortest paths. + * a[ ][ ]contains the adjacency matrix with + * a[ i ][ i ] presumed to be zero. + * d[ ] contains the values of the shortest path. + * Vertices are numbered starting at 0; all arrays + * have equal dimension. A negative cycle exists if + * d[ i ][ i ] is set to a negative value. + * Actual path can be computed using path[ ][ ]. + * NOT_A_VERTEX is -1 + */ + void allPairs( const matrix & a, + matrix & d, matrix & path ) + { + int n = a.numrows( ); + + // Initialize d and path +/* 1*/ for( int i = 0; i < n; i++ ) +/* 2*/ for( int j = 0; j < n; j++ ) + { +/* 3*/ d[ i ][ j ] = a[ i ][ j ]; +/* 4*/ path[ i ][ j ] = NOT_A_VERTEX; + } + +/* 5*/ for( int k = 0; k < n; k++ ) + // Consider each vertex as an intermediate +/* 6*/ for( int i = 0; i < n; i++ ) +/* 7*/ for( int j = 0; j < n; j++ ) +/* 8*/ if( d[ i ][ k ] + d[ k ][ j ] < d[ i ][ j ] ) + { + // Update shortest path +/* 9*/ d[ i ][ j ] = d[ i ][ k ] + d[ k ][ j ]; +/*10*/ path[ i ][ j ] = k; + } + } +/* END */ + + int main( ) + { + matrix a( 4, 4 ); + a[ 0 ][0 ] = 0; a[ 0 ][ 1 ] = 2; a[ 0 ][ 2 ] = -2; a[ 0 ][ 3 ] = 2; + a[ 1 ][ 0 ] = 1000; a[ 1 ][ 1 ] = 0; a[ 1 ][ 2 ] = -3; a[ 1 ][ 3 ] = 1000; + a[ 2 ][ 0 ] = 4; a[ 2 ][ 1 ] = 1000; a[ 2 ][ 2 ] = 0; a[ 2 ][ 3 ] = 1000; + a[ 3 ][ 0 ] = 1000; a[ 3 ][ 1 ] = -2; a[ 3 ][ 2 ] = 3; a[ 3 ][ 3 ] = 0; + + matrix d( 4, 4 ); + matrix path( 4, 4 ); + + allPairs( a, d, path ); + int i; + for( i = 0; i < d.numrows( ); i++ ) + { + for( int j = 0; j < d.numcols( ); j++ ) + cout << d[ i ][ j ] << " " ; + cout << endl; + } + for( i = 0; i < path.numrows( ); i++ ) + { + for( int j = 0; j < path.numcols( ); j++ ) + cout << path[ i ][ j ] << " " ; + cout << endl; + } + + return 0; + } diff --git a/c++/Others/Fig10_62.cpp - Randomized primality testing algorithm, with a test program.cpp b/c++/Others/Fig10_62.cpp - Randomized primality testing algorithm, with a test program.cpp new file mode 100644 index 0000000..b0875a2 --- /dev/null +++ b/c++/Others/Fig10_62.cpp - Randomized primality testing algorithm, with a test program.cpp @@ -0,0 +1,65 @@ +Fig10_62.cpp - Randomized primality testing algorithm, with a test program + + #include + #include "Random.h" + + typedef int HugeInt; + +/* START: Fig10_62.txt */ + /** + * Method that implements the basic primality test. + * If witness does not return 1, n is definitely composite. + * Do this by computing a^i (mod n) and looking for + * non-trivial square roots of 1 along the way. + */ + HugeInt witness( const HugeInt & a, const HugeInt & i, const HugeInt & n ) + { + if( i == 0 ) + return 1; + + HugeInt x = witness( a, i / 2, n ); + if( x == 0 ) // If n is recursively composite, stop + return 0; + + // n is not prime if we find a non-trivial square root of 1 + HugeInt y = ( x * x ) % n; + if( y == 1 && x != 1 && x != n - 1 ) + return 0; + + if( i % 2 != 0 ) + y = ( a * y ) % n; + + return y; + } + + /** + * The number of witnesses queried in randomized primality test. + */ + const int TRIALS = 5; + + /** + * Randomized primality test. + * Adjust TRIALS to increase confidence level. + * n is the number to test. + * If return value is false, n is definitely not prime. + * If return value is true, n is probably prime. + */ + bool isPrime( const HugeInt & n ) + { + Random r; + + for( int counter = 0; counter < TRIALS; counter++ ) + if( witness( r.randomInt( 2, (int) n - 2 ), n - 1, n ) != 1 ) + return false; + + return true; + } + + int main( ) + { + for( int i = 101; i < 200; i += 2 ) + if( isPrime( i ) ) + cout << i << " is prime" << endl; + + return 0; + } diff --git a/c++/Others/File example using fstream.h functions.cpp b/c++/Others/File example using fstream.h functions.cpp new file mode 100644 index 0000000..ef62a23 --- /dev/null +++ b/c++/Others/File example using fstream.h functions.cpp @@ -0,0 +1,20 @@ +File example using fstream.h functions + +#include +#include +int main() + +{ +// first lets output to a file +ofstream fout("sample.txt"); +fout << "WWW" << endl; +fout.close(); +char str[20]; +//read in the file +ifstream fin("sample.txt"); +fin >> str; +fin.close(); +//display sample.txt contents +cout << "data read from file: " << str << endl; +return 0; +} diff --git a/c++/Others/Find shortest path using floyd warshall algorithm.cpp b/c++/Others/Find shortest path using floyd warshall algorithm.cpp new file mode 100644 index 0000000..34b53ba --- /dev/null +++ b/c++/Others/Find shortest path using floyd warshall algorithm.cpp @@ -0,0 +1,137 @@ +Find shortest path using floyd warshall algorithm + +Code : +#include +#include +#include +#include +class path +{ + int n; + int p[10][10]; + int a[10][10]; + int c[10][10]; + public: + void get(); + void pm(); + void ap(); + void disp(); +}; +void path::get() +{ + int i,j,k; + clrscr(); + cout<<"Enter the no. of nodes in the graph :"; + cin>>n; + cout<<" +Enter the adjacency matrix : +"; + for(i=1;i<=n;i++) + { + for(j=1;j<=n;j++) + { + // cout<<"a["<>a[i][j]; + p[i][j]=0; + } + } + cout<<" + +Enter The cost matrix is : + +"; + for(i=1;i<=n;i++) + { + for(j=1;j<=n;j++) + { + // cout<<"a["<>c[i][j]; + } + } + for(i=1;i<=n;i++) + { + for(j=1;j<=n;j++) + { + + p[i][j]=a[i][j]; + + } + } +} +void path::disp() +{ +// cout<<" + + The output matrix for the given graph is : +"; + for(int i=1;i<=n;i++) + { + for(int j=1;j<=n;j++) + { + cout< + #include "mystring.h" + #include "vector.h" + #include "IntCell.h" + // Figures 1.17 and 1.18, but with illegalities commented out + + + /** + * Return the maximum item in array a. + * Assumes a.size( ) > 0. + * Comparable objects must provide + * copy constructor, operator<, operator= + */ + template + const Comparable & findMax( const vector & a ) + { +/* 1*/ int maxIndex = 0; + +/* 2*/ for( int i = 1; i < a.size( ); i++ ) +/* 3*/ if( a[ maxIndex ] < a[ i ] ) +/* 4*/ maxIndex = i; +/* 5*/ return a[ maxIndex ]; + } + + int main( ) + { + vector v1( 37 ); + vector v2( 40 ); + vector v3( 80 ); +// vector v4( 75 ); + + // Additional code to fill in the vectors + + cout << findMax( v1 ) << endl; // OK: Comparable = int + cout << findMax( v2 ) << endl; // OK: Comparable = double + cout << findMax( v3 ) << endl; // OK: Comparable = string +// cout << findMax( v4 ) << endl; // Illegal; operator< undefined + + return 0; + }; diff --git a/c++/Others/Forever Calender in C++.cpp b/c++/Others/Forever Calender in C++.cpp new file mode 100644 index 0000000..02635af --- /dev/null +++ b/c++/Others/Forever Calender in C++.cpp @@ -0,0 +1,155 @@ +Forever Calender in C++ + +#include +#include + +int step1 (int); +void month_name(int); +int no_days(int,int); +int leap(int); + +void main() +{ + restart: + clrscr(); + cout<<"Enter year : "; + unsigned int y,m; + cin>>y; + int x; + x=step1(y); + int month[14][12]= {1,4,4,7,2,5,7,3,6,1,4,6, + 2,5,5,1,3,6,1,4,7,2,5,7, + 3,6,6,2,4,7,2,5,1,3,6,1, + 4,7,7,3,5,1,3,6,2,4,7,2, + 5,1,1,4,6,2,4,7,3,5,1,3, + 6,2,2,5,7,3,5,1,4,6,2,4, + 7,3,3,6,1,4,6,2,5,7,3,5, + 1,4,5,1,3,6,1,4,7,2,5,7, + 2,5,6,2,4,7,2,5,1,3,6,1, + 3,6,7,3,5,1,3,6,2,4,7,2, + 4,7,1,4,6,2,4,7,3,5,1,3, + 5,1,2,5,7,3,5,1,4,6,2,4, + 6,2,3,6,1,4,6,2,5,7,3,5, + 7,3,4,7,2,5,7,3,6,1,4,6}; + cout<<"Enter month (1 - 12) : "; + month_input: + cin>>m; + if(m<1 || m>12) + { + cout<<"Enter a valid month (1 - 12) : "; + goto month_input; + } + cout<<" + + "; + month_name(m); + cout<<' '<>ch; + if(ch=='y' || ch=='Y') + goto restart; +} +int step1 (int y) +{ + int x=y%7; + x+=(y-1)/4; + x-=(y-1)/100; + x+=(y-1)/400; + x=x%7; + if(x==0) + x=7; + if(leap(y)) + x+=7; + return x; +} +void month_name(int m) +{ + switch(m) + { + case 1 : cout<<"January"; + break; + case 2 : cout<<"February"; + break; + case 3 : cout<<"March"; + break; + case 4 : cout<<"April"; + break; + case 5 : cout<<"May"; + break; + case 6 : cout<<"June"; + break; + case 7 : cout<<"July"; + break; + case 8 : cout<<"August"; + break; + case 9 : cout<<"September"; + break; + case 10: cout<<"October"; + break; + case 11: cout<<"November"; + break; + case 12: cout<<"December"; + break; + } +} + +int no_days(int mon, int y) +{ + int d; + switch(mon) + { + case 1 : + case 3 : + case 5 : + case 7 : + case 8 : + case 10: + case 12: d=31; + break; + case 4 : + case 6 : + case 9 : + case 11: d=30; + break; + case 2 : if(leap(y)) + d=29; + else + d=28; + break; + } + return d; +} +int leap (int y) +{ + if (y%100==0) + if (y%400==0) + return 1; + else + return 0; + else + if (y%4==0) + return 1; + else + return 0; +} diff --git a/c++/Others/Frequency words,characters.cpp b/c++/Others/Frequency words,characters.cpp new file mode 100644 index 0000000..e3e422f --- /dev/null +++ b/c++/Others/Frequency words,characters.cpp @@ -0,0 +1,158 @@ +Frequency words,characters + +// ISO/ANSI C program +// 0 Errors and 0 Warnings on turboC 3.0 compilers +// borland 3.0 + +#include +#include +#include +main() +{ + int ch,i,j,k,l,fc[50][2],flag; + char line[50],fw[50][50]; + clrscr(); + do + { + printf("\n<1> Input a line"); + printf("\n<2> Number of characters"); + printf("\n<3> Number of words"); + printf("\n<4> Number of vowals"); + printf("\n<5> Frequency of characters"); + printf("\n<6> Frequency of words"); + printf("\n<7> Exit\n"); + do + { + printf("\n enter your choice "); + scanf("%d",&ch); + }while(ch>7 || ch<1); + switch (ch) + { + case 1: //input a line + printf("\n Enter a line "); + scanf("\n%[^\n]",line); + break; + case 2: //number of characters + j=0; + for(i=0;i64 && line[i]<93) + ++j; + else + if(line[i]>96 && line[i]<123) + ++j; + } + printf("total number of characters are %d",j); + break; + case 3: //number of words + j=0; + for(i=0;i1) + fw[k][0]='\0'; + } + } + if(fc[0][0]>0) + { + flag=0; + do + { + printf("%c",fw[i][flag]); + } while(fw[i][flag++]!='\0'); + if(fw[i][0]!='\0') + printf("%d\n",fc[0][0]); + } + fc[0][0]=0; + } + break; + } + }while(ch!=7); + printf("\n\n i will wait for your mails "); + getch(); + return ; +} diff --git a/c++/Others/Function example.cpp b/c++/Others/Function example.cpp new file mode 100644 index 0000000..8876d92 --- /dev/null +++ b/c++/Others/Function example.cpp @@ -0,0 +1,23 @@ +Function example + +Create your first function in C++ +#include +int AddIt(int x,int y) +{ +return (x + y); +} + +int main() +{ +int a,b,c; +cout<<"Please enter two integers to add :\n"; +//get the two integers +cin>>a; +cin>>b; +//call the AddIt function +c = AddIt(a , b); +//display the answer +cout<<"The answer is : "< +# include +# include +# include +# include +# include +static int cnt=0; +void main() +{ + clrscr(); + char film[150],ch,film2[150]; + int choi,len,res=0,dig=0,j,count=0,len1,flag=1,p; + cout<<"Enter 1 For HOLLYWOOD & 2 For BOLLYWOOD "; + cin>>choi; + cout<<" +ENTER THE NAME OF THE FILM +"; + gets(film); + len=strlen(film); + len1=len; + clrscr(); + flushall(); + gotoxy(15,10); + if(choi==1) + cout<<"HOLLYWOOD +"; + else + cout<<"BOLLYWOOD +"; + for(int i=0;i>ch; + film2[cnt]=ch; + if(cnt>=1) + { + for(int k=0;k +#include +#include +#include +void main() +{ +clrscr(); +int min,max,i,range,r,x; +unsigned first = time(NULL); +cout<<"FIRST = " << first <>min; +cout<<"ENTER THE MAXIMUM NUMBER :"; +cin>>max; +cout<<"ENTER THE NO.OF TERMS YOU WANT :"; +cin>>x; +range=max-min+1; +for(i=0;i +#include +#include +#include +int main(void) + +{ +OSVERSIONINFO osver; +osver.dwOSVersionInfoSize = sizeof(osver); +if (GetVersionEx(&osver)) + +{ +if (osver.dwPlatformId == VER_PLATFORM_WIN32s) +cout <<"Win32 "; +else if (osver.dwPlatformId == VER_PLATFORM_WIN32_WINDOWS) + +{ +if (osver.dwMinorVersion == 0 && (strchr(osver.szCSDVersion,'B') == NULL) +&& (strchr(osver.szCSDVersion,'C') == NULL)) +cout <<"Windows 95 "; +else if (osver.dwMinorVersion == 0 && (strchr(osver.szCSDVersion,'B') != NULL)) +cout <<"Windows 95 OSR 2 "; +else if (osver.dwMinorVersion == 0 && (strchr(osver.szCSDVersion,'C') != NULL)) +cout <<"Windows 95 OSR 2.5 "; +else if (osver.dwMinorVersion == 10 && (strchr(osver.szCSDVersion,'A') == NULL)) +cout <<"Windows 98 "; +else if (osver.dwMinorVersion == 10 && (strchr(osver.szCSDVersion,'A') != NULL)) +cout <<"Windows 98 Second Edition "; +else if (osver.dwMinorVersion == 90) +cout <<"Windows Millenium Edition "; +else +cout<<"Unknown Windows "; +} +else if (osver.dwPlatformId == VER_PLATFORM_WIN32_NT) +cout <<"Windows NT "; +cout < +#include +#include +#include +#include +#include +#include +#include +#include + +using namespace std; + +int INFINITY = INT_MAX; + +struct Vertex +{ + string name; // Vertex name + vector adj; // Adjacent vertices + int dist; // Cost + Vertex *path; // Previous vertex on shortest path + + Vertex( const string & nm ) : name( nm ) + { reset( ); } + + void reset( ) + { dist = INFINITY; path = NULL; } +}; + + +typedef map vmap; +typedef pair vpair; + + +class Graph +{ + public: + Graph( ) { } + ~Graph( ); + void addEdge( const string & sourceName, const string & destName ); + void printPath( const string & destName ) const; + void unweighted( const string & startName ); + + private: + Vertex * getVertex( const string & vertexName ); + void printPath( const Vertex & dest ) const; + void clearAll( ); + + vmap vertexMap; + vector allVertices; +}; + + + +void Graph::addEdge( const string & sourceName, const string & destName ) +{ + Vertex * v = getVertex( sourceName ); + Vertex * w = getVertex( destName ); + v->adj.push_back( w ); +} + +void Graph::printPath( const string & destName ) const +{ + vmap::const_iterator itr = vertexMap.find( destName ); + + if( itr == vertexMap.end( ) ) + { + cout << "Destination vertex not found" << endl; + return; + } + + const Vertex & w = *(*itr).second; + if( w.dist == INFINITY ) + cout << destName << " is unreachable"; + else + printPath( w ); + cout << endl; +} + +// If vertexName is not present, add it to vertexMap +// In either case, return the Vertex +Vertex * Graph::getVertex( const string & vertexName ) +{ + vmap::iterator itr = vertexMap.find( vertexName ); + + if( itr == vertexMap.end( ) ) + { + Vertex *newv = new Vertex( vertexName ); + allVertices.push_back( newv ); + vertexMap.insert( vpair( vertexName, newv ) ); + return newv; + } + return (*itr).second; +} + +void Graph::printPath( const Vertex & dest ) const +{ + if( dest.path != NULL ) + { + printPath( *dest.path ); + cout << " to "; + } + cout << dest.name; +} + +void Graph::clearAll( ) +{ + for( int i = 0; i < allVertices.size( ); i++ ) + allVertices[ i ]->reset( ); +} + +Graph::~Graph( ) +{ + for( int i = 0; i < allVertices.size( ); i++ ) + delete allVertices[ i ]; +} + + +void Graph::unweighted( const string & startName ) +{ + clearAll( ); + + vmap::iterator itr = vertexMap.find( startName ); + + if( itr == vertexMap.end( ) ) + { + cout << startName << " is not a vertex in this graph" << endl; + return; + } + + Vertex *start = (*itr).second; + list q; + q.push_back( start ); start->dist = 0; + + while( !q.empty( ) ) + { + Vertex *v = q.front( ); q.pop_front( ); + + for( int i = 0; i < v->adj.size( ); i++ ) + { + Vertex *w = v->adj[ i ]; + if( w->dist == INFINITY ) + { + w->dist = v->dist + 1; + w->path = v; + q.push_back( w ); + } + } + } +} + +/** + * Process a request; return false if end of file. + */ +bool processRequest( istream & in, Graph & g ) +{ + string startName; + string destName; + + cout << "Enter start node: "; + if( !( in >> startName ) ) + return false; + cout << "Enter destination node: "; + if( !( in >> destName ) ) + return false; + + g.unweighted( startName ); + g.printPath( destName ); + + return true; +} + + +/** + * A simple main that reads the file given by argv[1] + * and then calls processRequest to compute shortest paths. + * Skimpy error checking in order to concentrate on the basics. + */ +int main( int argc, char *argv[ ] ) +{ + Graph g; + + if( argc != 2 ) + { + cerr << "Usage: " << argv[ 0 ] << " graphfile" << endl; + return 1; + } + + ifstream inFile( argv[ 1 ] ); + if( !inFile ) + { + cerr << "Cannot open " << argv[ 1 ] << endl; + return 1; + } + + string oneLine; + + // Read the words; add them to wordMap + while( getline( inFile, oneLine ) ) + { + string source, dest; + + istringstream st( oneLine ); + st >> source; + st >> dest; + g.addEdge( source, dest ); + } + + cout << "File read" << endl; + while( processRequest( cin, g ) ) + ; + + return 0; +} + diff --git a/c++/Others/Graph2.cpp - Shortest path program not using STL.cpp b/c++/Others/Graph2.cpp - Shortest path program not using STL.cpp new file mode 100644 index 0000000..a0cd6b6 --- /dev/null +++ b/c++/Others/Graph2.cpp - Shortest path program not using STL.cpp @@ -0,0 +1,237 @@ +Graph2.cpp - Shortest path program not using STL + +#include +#include +#include +#ifdef unix + #include +#else + #include // on UNIX machines +#endif + +#include "mystring.h" +#include "SeparateChaining.h" +#include "LinkedList.h" +#include "QueueAr.h" + +int INFINITY = INT_MAX; + +struct Vertex +{ + string name; // Vertex name + List adj; // Adjacent vertices + int dist; // Cost + Vertex *path; // Previous vertex on shortest path + + Vertex( const string & nm ) : name( nm ) + { reset( ); } + + void reset( ) + { dist = INFINITY; path = NULL; } +}; + +struct MapEntry +{ + string vertexName; + Vertex *storedVertex; + + MapEntry( const string & name = "", Vertex * v = NULL ) + : vertexName( name ), storedVertex( v ) { } + bool operator!=( const MapEntry & rhs ) const + { return vertexName != rhs.vertexName; } + bool operator==( const MapEntry & rhs ) const + { return vertexName == rhs.vertexName; } +}; + +int hash( const MapEntry & x, int tableSize ) +{ + return hash( x.vertexName, tableSize ); +} + +class Graph +{ + public: + Graph( ) : vertexMap( MapEntry( ) ), numVertices( 0 ) { } + ~Graph( ); + void addEdge( const string & sourceName, const string & destName ); + void printPath( const string & destName ) const; + void unweighted( const string & startName ); + + private: + Vertex * getVertex( const string & vertexName ); + void printPath( const Vertex & dest ) const; + void clearAll( ); + + HashTable vertexMap; + List allVertices; + int numVertices; + const MapEntry ITEM_NOT_FOUND; +}; + + + +void Graph::addEdge( const string & sourceName, const string & destName ) +{ + Vertex * v = getVertex( sourceName ); + Vertex * w = getVertex( destName ); + v->adj.insert( w, v->adj.zeroth( ) ); +} + +void Graph::printPath( const string & destName ) const +{ + const MapEntry & match = vertexMap.find( MapEntry( destName ) ); + if( match == ITEM_NOT_FOUND ) + { + cout << "Destination vertex not found" << endl; + return; + } + + const Vertex & w = *match.storedVertex; + if( w.dist == INFINITY ) + cout << destName << " is unreachable"; + else + printPath( w ); + cout << endl; +} + +// If vertexName is not present, add it to vertexMap +// In either case, return the Vertex +Vertex * Graph::getVertex( const string & vertexName ) +{ + static MapEntry entry; + entry.vertexName = vertexName; + + const MapEntry & match = vertexMap.find( entry ); + if( match == ITEM_NOT_FOUND ) + { + entry.storedVertex = new Vertex( vertexName ); + allVertices.insert( entry.storedVertex, allVertices.zeroth( ) ); + numVertices++; + vertexMap.insert( entry ); + return entry.storedVertex; + } + return match.storedVertex; +} + +void Graph::printPath( const Vertex & dest ) const +{ + if( dest.path != NULL ) + { + printPath( *dest.path ); + cout << " to "; + } + cout << dest.name; +} + +void Graph::clearAll( ) +{ + ListItr itr; + for( itr = allVertices.first( ); !itr.isPastEnd( ); itr.advance( ) ) + itr.retrieve( )->reset( ); +} + +Graph::~Graph( ) +{ + ListItr itr; + for( itr = allVertices.first( ); !itr.isPastEnd( ); itr.advance( ) ) + delete itr.retrieve( ); +} + + +void Graph::unweighted( const string & startName ) +{ + clearAll( ); + + const MapEntry & match = vertexMap.find( MapEntry( startName ) ); + if( match == ITEM_NOT_FOUND ) + { + cout << startName << " is not a vertex in this graph" << endl; + return; + } + + Vertex *start = match.storedVertex; + Queue q( numVertices ); + q.enqueue( start ); start->dist = 0; + + while( !q.isEmpty( ) ) + { + Vertex *v = q.dequeue( ); + + ListItr itr; + for( itr = v->adj.first( ); !itr.isPastEnd( ); itr.advance( ) ) + { + Vertex *w = itr.retrieve( ); + if( w->dist == INFINITY ) + { + w->dist = v->dist + 1; + w->path = v; + q.enqueue( w ); + } + } + } +} + +/** + * Process a request; return false if end of file. + */ +bool processRequest( istream & in, Graph & g ) +{ + string startName; + string destName; + + cout << "Enter start node: "; + if( !( in >> startName ) ) + return false; + cout << "Enter destination node: "; + if( !( in >> destName ) ) + return false; + + g.unweighted( startName ); + g.printPath( destName ); + + return true; +} + + +/** + * A simple main that reads the file given by argv[1] + * and then calls processRequest to compute shortest paths. + * Skimpy error checking in order to concentrate on the basics. + */ +int main( int argc, char *argv[ ] ) +{ + Graph g; + + if( argc != 2 ) + { + cerr << "Usage: " << argv[ 0 ] << " graphfile" << endl; + return 1; + } + + ifstream inFile( argv[ 1 ] ); + if( !inFile ) + { + cerr << "Cannot open " << argv[ 1 ] << endl; + return 1; + } + + string oneLine; + + // Read the words; add them to wordMap + while( getline( inFile, oneLine ) ) + { + string source, dest; + + istrstream st( (char *) oneLine.c_str( ) ); // Deprecated form of string streams + st >> source; + st >> dest; + g.addEdge( source, dest ); + } + + cout << "File read" << endl; + while( processRequest( cin, g ) ) + ; + + return 0; +} + diff --git a/c++/Others/Graphic Simulation for Shortest & 2nd shortest path in a Weighted Graph.cpp b/c++/Others/Graphic Simulation for Shortest & 2nd shortest path in a Weighted Graph.cpp new file mode 100644 index 0000000..7b7e363 --- /dev/null +++ b/c++/Others/Graphic Simulation for Shortest & 2nd shortest path in a Weighted Graph.cpp @@ -0,0 +1,322 @@ +Graphic Simulation for Shortest & 2nd shortest path in a Weighted Graph + +#include +#include +#include +#include +float +sum=0,w=0,s,wn,v[8],td=0,e,i,j,n,w1[8],j1[8],arr[8],arr1[8],e1,count,d2,y1 +; +float var,a[8][8],d[8],p[8],n1,c,c1,w2; +void main() +{ +int gd=DETECT,gm; +clrscr(); +void draw(float,float); +void dijkstra(float s,float e,float v1[8],float d1[8],float p1[8],float +a1[8][8],float n); +void ssp(); +void path(); +void initial(); +printf("There are 8 routers in each subnet +"); +n=8; +for(i=0;ij1[v1]) +{ +line(x,y,x,y-1); +delay(10); +y=y-1; +} +else +{ +line(x,y,x,y+1); +delay(10); +y=y+1; +}}} +if(y==j1[v1]) +{ +while(x!=w1[v1]) +{ +if(x>w1[v1]) +{ +line(x,y,x-1,y); +delay(10); +x=x-1; +} +else +{ +line(x,y,x+1,y); +delay(10); +x=x+1; +}}} +if(xw1[v1]&&y>j1[v1]) +{ +while(x!=w1[v1]) +{ +line(x,y,x-1,y-s); +delay(10); +x=x-1; +y=y-s; +i=i+1; +}} +if(x>w1[v1]&&yj1[v1]) +{ +while(x!=w1[v1]) +{ +line(x,y,x+1,y-s); +delay(10); +x=x+1; +y=y-s; +i=i+1; +} +}} +void ssp() +{ +d2=y1=32767; +setcolor(RED); +e1=e; +for(i=0;i +#include +#include +#include + +// define maximum number of patients in a queue +#define MAXPATIENTS 100 + +// define structure for patient data +struct patient +{ + char FirstName[50]; + char LastName[50]; + char ID[20]; +}; + + +// define class for queue +class queue +{ + public: + queue (void); + int AddPatientAtEnd (patient p); + int AddPatientAtBeginning (patient p); + patient GetNextPatient (void); + int RemoveDeadPatient (patient * p); + void OutputList (void); + char DepartmentName[50]; + private: + int NumberOfPatients; + patient List[MAXPATIENTS]; +}; + + +// declare member functions for queue + +queue::queue () +{ + // constructor + NumberOfPatients = 0; +} + + +int queue::AddPatientAtEnd (patient p) +{ + // adds a normal patient to the end of the queue. + // returns 1 if successful, 0 if queue is full. + if (NumberOfPatients >= MAXPATIENTS) + { + // queue is full + return 0; + } + // put in new patient + else + List[NumberOfPatients] = p; NumberOfPatients++; + return 1; +} + + +int queue::AddPatientAtBeginning (patient p) +{ + // adds a critically ill patient to the beginning of the queue. + // returns 1 if successful, 0 if queue is full. + int i; + if (NumberOfPatients >= MAXPATIENTS) + { + // queue is full + return 0; + } + + // move all patients one position back in queue + for (i = NumberOfPatients-1; i >= 0; i--) + { + List[i+1] = List[i]; + } + // put in new patient + List[0] = p; NumberOfPatients++; + return 1; +} + + +patient queue::GetNextPatient (void) +{ + // gets the patient that is first in the queue. + // returns patient with no ID if queue is empty + + int i; patient p; + if (NumberOfPatients == 0) { + // queue is empty + strcpy(p.ID,""); + return p;} + // get first patient + p = List[0]; + // move all remaining patients one position forward in queue + NumberOfPatients--; + for (i=0; iID) == 0) + { + // patient found in queue + *p = List[i]; found = 1; + // move all following patients one position forward in queue + NumberOfPatients--; + for (j=i; jID[0]==0) + { + cout << " +No patient"; + return; + } + else + cout << " + +Patient data:"; + cout << " + +First name: " << p->FirstName; + cout << " + +Last name: " << p->LastName; + cout << " + +Social security number: " << p->ID; +} + + +int ReadNumber() +{ + // this function reads an integer number from the keyboard. + // it is used because input with cin >> doesn't work properly! + char buffer[20]; + cin.getline(buffer, sizeof(buffer)); + return atoi(buffer); +} + + +void DepartmentMenu (queue * q) +{ + // this function defines the user interface with menu for one +department + int choice = 0, success; patient p; + while (choice != 6) + { + // clear screen + clrscr(); + // print menu + cout << " + + +Welcome to department: " << q->DepartmentName; + cout << " + +Please enter your choice:"; + cout << " + +1: Add normal patient"; + cout << " +2: Add critically ill patient"; + cout << " +3: Take out patient for operation"; + cout << " +4: Remove dead patient from queue"; + cout << " +5: List queue"; + cout << " +6: Change department or exit +"; + // get user choice + choice = ReadNumber(); + // do indicated action + switch (choice) + { + case 1: // Add normal patient + p = InputPatient(); + if (p.ID[0]) + { + success = q->AddPatientAtEnd(p); + clrscr(); + if (success) + { + cout << " +Patient added: + +"; + + } + else + { + // error + cout << " + +Error: The queue is full. Cannot add patient:"; + } + OutputPatient(&p); + cout << " + +Press any key"; + getch(); + } + break; + + case 2: // Add critically ill patient + p = InputPatient(); + if (p.ID[0]) + { + success = q->AddPatientAtBeginning(p); + clrscr(); + if (success) + { + cout << " +Patient added: + +"; + } + else + { + // error + cout << " + +Error: The queue is full. Cannot add +patient:"; + } + + OutputPatient(&p); + cout << " + +Press any key"; + getch(); + } + break; + + case 3: // Take out patient for operation + p = q->GetNextPatient(); + clrscr(); + if (p.ID[0]) + { + cout << " +Patient to operate: + +"; + OutputPatient(&p);} + else + { + cout << " +There is no patient to operate."; + } + cout << " + +Press any key"; + getch(); + break; + + case 4: // Remove dead patient from queue + p = InputPatient(); + if (p.ID[0]) + { + success = q->RemoveDeadPatient(&p); + clrscr(); + if (success) + { + cout << " +Patient removed: + +"; + } + else + { + // error + cout << " + +Error: Cannot find patient: + +"; + } + OutputPatient(&p); + cout << " + +Press any key"; + getch(); + } + break; + + case 5: // List queue + clrscr(); + q->OutputList(); + cout << " + +Press any key"; + getch(); break; + } + } +} + + +// main function defining queues and main menu +void main () +{ + int i, MenuChoice = 0; + // define three queues + queue departments[3]; + // set department names + strcpy (departments[0].DepartmentName, "Heart clinic"); + strcpy (departments[1].DepartmentName, "Lung clinic"); + strcpy (departments[2].DepartmentName, "Plastic surgery"); + + while (MenuChoice != 4) + { + // clear screen + clrscr(); + // print menu + cout << " + + +Welcome to Software City Hospital"; + cout << " + +Please enter your choice: +"; + for (i = 0; i < 3; i++) + { + // write menu item for department i + cout << " +" << (i+1) << ": " << departments[i].DepartmentName; + } + cout << " +4: Exit +"; + // get user choice + MenuChoice = ReadNumber(); + // is it a department name? + if (MenuChoice >= 1 && MenuChoice <= 3) + { + // call submenu for department + // (using pointer arithmetics here:) + DepartmentMenu (departments + (MenuChoice-1)); + } + } +} + + diff --git a/c++/Others/If - Else example.cpp b/c++/Others/If - Else example.cpp new file mode 100644 index 0000000..38d62ef --- /dev/null +++ b/c++/Others/If - Else example.cpp @@ -0,0 +1,18 @@ +If - Else example + +#include +#include +int main() +{ +double radius; +//get user input +cout<<"Please enter the radius : "; +cin>>radius; +//act on user input +if(radius < 0.0) +cout<<"Cannot have a negative radius"< +# include +# define SIZE 20 + +class queue +{ + int a[SIZE]; + int front; + int rear; +public: + queue(); + ~queue(); + void insert(int i); + int remove(); + int isempty(); + int isfull(); +}; + +queue::queue() +{ +front=0; +rear=0; +} +queue::~queue() +{ +delete []a; +} +void queue::insert(int i) +{ +if(isfull()) +{ + cout<<" + +****** +Queue is FULL !!! +No insertion allowed further. +****** +"; + return; +} +a[rear] = i; +rear++; +} +int queue::remove() +{ +if(isempty()) +{ + cout<<" + +****** +Queue Empty !!! +Value returned will be garbage. +****** +"; + return (-9999); +} + +return(a[front++]); +} +int queue::isempty() +{ +if(front == rear) + return 1; +else + return 0; +} +int queue::isfull() +{ +if(rear == SIZE) + return 1; +else + return 0; +} + +void main() +{ +clrscr(); +queue q; +q.insert(1); +q.insert(2); +cout<<" +"< +# include +# define SIZE 20 + +class stack +{ +int a[SIZE]; +int tos; // Top of Stack +public: + stack(); + void push(int); + int pop(); + int isempty(); + int isfull(); +}; +stack::stack() +{ +tos=0; //Initialize Top of Stack +} + +int stack::isempty() +{ +return (tos==0?1:0); +} +int stack::isfull() +{ +return (tos==SIZE?1:0); +} + +void stack::push(int i) +{ + +if(!isfull()) +{ +cout<<"Pushing "< +struct element { + int number; + element *next; + }; + +/* the operators declared on the type list.*/ +void read(element *&list); +void write(element *list); +int length(element *list); +int position(element *list, int num); +void remove(element *&list,int position); +void insert(element *&list,int new_num,int position); +element *ele(element *list,int position); + +void add(int new_num,element *&list,element *this_el); + +void main() +{ + + element *list,*p,*q; + int leng; + + read(list); + write(list); + q = ele (list,3); + add (5,list,q); + write(list); + insert(list,10,2); + write(list); + remove(list,4); + write(list); + insert(list,12,1); + write(list); + leng = position(list,10); + cout<< " pos of 10 is " << leng <>p->number; + while (!cin.eof()) + { + p->next = new element; + last = p; + p = p->next; + cout<< " enter a number "; + cin>>p->number; + } + delete (p); + last->next = NULL; +} + +/* writing a list on the output */ +void write(element *list) +{ + element *p; + cout<number<<" "; + p=p->next; + } + cout<next; + } + return count; +} + +/*Gets an element and returns its positon in the list. If the element*/ +/*is not in the list, returns 0 */ + +int position(element *list,int num) +{ + element *p; + int i=1; + for (p=list;p!=NULL;p=p->next) + { + if ((p->number)==num) + return i; + i++; + } + return 0; +} + +/*Gets a number and removes the element that stays in this position */ +void remove(element *&list,int position) +{ + element *before,*p; + if (position==1) + { + before=list; + list = list->next; + delete (before); + } + else + { + before = ele (list,position-1); + if (before!=NULL) + { + p = before->next; + before->next = p->next; + delete (p); + } + } +} + +/* Insert a new element to be the i-th element of the list */ +/* the function uses the function add*/ +void insert(element *&list,int new_num,int position) +{ + element *p; + if (position==1) + add(new_num,list,NULL); + else + { + p = ele(list,position-1); + add(new_num,list,p); + } +} + +/* Gets a position in the list and returns a pointer to the element*/ +/* in this position*/ +element *ele(element *list,int position) +{ + element *p=list; + int i; + for (i=1;inext; + } + return p; +} + +/* Add a new element after a given element.If the given element is NULL*/ +/* Add the new element to be the first element*/ +void add(int new_num,element *&list,element *this_el) +{ + element *p; + if (list==NULL) + { + list = new element; + list->number = new_num; + list->next = NULL; + } + else + { + p = new element; + p->number = new_num; + if (this_el==NULL) + { + p->next = list; + list = p; + } + else + { + p->next=this_el->next; + this_el->next = p; + } + } +} diff --git a/c++/Others/Info person.cpp b/c++/Others/Info person.cpp new file mode 100644 index 0000000..f7f3944 --- /dev/null +++ b/c++/Others/Info person.cpp @@ -0,0 +1,40 @@ +Info person + +#include +#include +class person +{ + char *name,*add,*eadd; + long pno,ctzno; + public: + void info() + { + cout<<"Enter the name:"; + cin>>name; + cout<<"Enter the address:"; + cin>>add; + cout<<"Enter the email address:"; + cin>>eadd; + cout<<"Enter the phone no:"; + cin>>pno; + cout<<"Enter the citizenship no:"; + cin>>ctzno; + } + void PrintInfo() + { + cout<<"********************Person Data***************************"< children; +}; + +Person* Mother::hasBaby(const string& firstName); +{ + Person* newBaby = new Person(firstName, getLastName()); + children.pushback(newBaby); + return newBaby; +} + +int main(void) +{ + Mother sue("Sue", "Smith"); + Person joe = sue.hasBaby("Joe"); + Person kay = sue.hasBaby("Kay"); + + cout << "Baby Joe's last name is: " << joe.getLastName() << endl; + cout << "Baby Kay's last name is: " << kay.getLastName() << endl; + + return 0; +} diff --git a/c++/Others/IntCell.cpp - IntCell class implementation (Fig 1.8).cpp b/c++/Others/IntCell.cpp - IntCell class implementation (Fig 1.8).cpp new file mode 100644 index 0000000..b090ee7 --- /dev/null +++ b/c++/Others/IntCell.cpp - IntCell class implementation (Fig 1.8).cpp @@ -0,0 +1,27 @@ +IntCell.cpp - IntCell class implementation (Fig 1.8) + + #include "IntCell.h" + + /** + * Construct the IntCell with initialValue + */ + + IntCell::IntCell( int initialValue ) : storedValue( initialValue ) + { + } + + /** + * Return the stored value. + */ + int IntCell::read( ) const + { + return storedValue; + } + + /** + * Store x. + */ + void IntCell::write( int x ) + { + storedValue = x; + } diff --git a/c++/Others/IntCell.h - IntCell class interface (Fig 1.7).cpp b/c++/Others/IntCell.h - IntCell class interface (Fig 1.7).cpp new file mode 100644 index 0000000..d10a541 --- /dev/null +++ b/c++/Others/IntCell.h - IntCell class interface (Fig 1.7).cpp @@ -0,0 +1,19 @@ +IntCell.h - IntCell class interface (Fig 1.7) + + #ifndef IntCell_H_ + #define IntCell_H_ + + /** + * A class for simulating an integer memory cell. + */ + class IntCell + { + public: + explicit IntCell( int initialValue = 0 ); + int read( ) const; + void write( int x ); + private: + int storedValue; + }; + + #endif diff --git a/c++/Others/It evaluates the value of any polynomial of any degree, adds two poly.cpp b/c++/Others/It evaluates the value of any polynomial of any degree, adds two poly.cpp new file mode 100644 index 0000000..020a4ac --- /dev/null +++ b/c++/Others/It evaluates the value of any polynomial of any degree, adds two poly.cpp @@ -0,0 +1,116 @@ +It evaluates the value of any polynomial of any degree, adds two poly +and also multiplies them + +Code : + +/*evaluates, adds ,multiplies two polynomials p & f to evaluate poly of +deg > 20 manipulate const in size */ + +#include +using namespace std ; +void polyadd(float*a,int dega,float*b,int degb,float*sum) +{int i ; +if(dega>=degb) +{for (i=0;i<=dega;i++) +sum[i]=a[i]+b[i] ;} +if(degb >dega) +{for(i=0;i<=degb;i++) +sum[i]= a[i]+b[i] ; } +} +//******************************************** +/*void polymult(float*a,int dega,float*b,int degb,float*mult) +{int i,j; +if(dega<=degb) +for(i=0;i<=degb;i++) +{for(j=0;j<=i;j++) +mult[i]= mult[i] + a[j]*b[i-j] ; +mult[i] = mult[i] +a[i+1]*b[i+1] ; } +//mult[i] = mult[i] - a[0]*b[0] ; } +if (degb>deg ; +if(deg<0) +cout<<"go learn ur textbook"<=0) +{ +cout<<"give the value of the coefficients"<>a[j] ; +cout<<"give the value x"<>x ; +ans = power(a,deg,x); +cout<<"the value of p("<>a[j]; */ +cout<<" give in the degree of poly b"<>degb ; +cout<<"enter the values of the coefficient of polynomialb"<>b[j] ; +cout<<"give the value to be substituted in polynomialb"<>y ; +ans = power(b,degb,y) ; + +cout<<"the value of f("<>decision ; +if(decision =="a") +{ polyadd(a,dega,b,degb,sum); +if (dega>=degb) +{ans= power(sum,dega,x); +cout<<"the answer after addition of p("<=degb) +{ans= power(a,dega,x)*power(b,degb,y) ; + +//cout<<"the answer of multiplication"<dega) +//{ ans = power(mult,degb,x) ; +cout<<"the answer after multiplication of p("<>n; +for(i=0;i>p>>d>>t; +pt.d=d; +pt.p=p; +pt.t=t; +lst.push_back(pt); +} +int maxd=0; +lst.sort(); +lst.reverse(); +cout<<" +sorted list +"; +list :: iterator itr=lst.begin(); +while(itr!=lst.end()){ +pt=*itr; +if(maxd=pt.t) +min=pt.t; +else +min=pt.d; + +if(maxd>=min) + profit+=min*pt.p; + else + profit+=maxd*pt.p; + itr++;maxd=maxd-min; + +} +cout<<"profit is : "< +#include +#include +#include +#include +#include + +#define L 75 +#define R 77 +#define U 72 +#define D 80 + + #define __LARGE__ + int getboxpos(); + int check_box(); + void quit(void) ; + int finish(void); + + int x,y,d,locx,locy; + int tboxx[]={50,80,110,140,50,80,140,140,50,80,110,110,50,80,140}; + int +tboxy[]={200,200,200,200,235,235,235,270,270,270,305,270,305,305,305}; + int +winx[]={50,80,110,140,50,80,110,140,50,80,110,140,50,80,110}; + int +winy[]={200,200,200,200,235,235,235,235,270,270,270,270,305,305,305}; + int Vx[]={50,50,50,50,80,80,80,80,110,110,110,110,140,140,140}; + int Vy[]={200,235,270,305, 200,235,270,305, 200,235,270,305, +200,235,270}; + struct BOX{ + int boxx,boxy; + void *box; }b[15]; + int empty_x=110; + int empty_y=235; + int play=0; + char arrange; + void display(void) + { cleardevice(); + for(int q=0;q<15;q++) + putimage(b[q].boxx,b[q].boxy,b[q].box,1); + gotoxy(10,2);printf("Arrangement Range :[1 - %2d]",play); + if(arrange=='h'){ gotoxy(10,3);printf("Arrangement Style +:Horizontal");} + else { gotoxy(10,3);printf("Arrangement Style :Vertical");} + } + +void main(void) +{ char st[2]; + for(int q=0;q<15;q++) + b[q].boxx=b[q].boxy=NULL; + int driver=DETECT,mode; + int deck_color=0,no_color=0; + clrscr(); + dd: gotoxy(10,5); + printf("Deck Color :"); + scanf("%d",&deck_color); + gotoxy(10,6); + printf("No. Color :"); + scanf("%d",&no_color); + printf("Arrangement Range upto:[4,8,10,12,15]"); + scanf("%d",&play); + printf("Arrangement Style :[H]orizontal,[V]ertical"); + arrange=getche(); + if(deck_color==0 )goto dd; + else if(no_color==deck_color)goto dd; + if(play>15 || play<1)play=10; + if(arrange!='h' && arrange!='v')arrange='h'; + initgraph(&driver,&mode,""); + settextstyle(1,0,1); + + for(int j=0;j<15;j++) + { cleardevice(); + setcolor(deck_color); + for(int i=1;i<=25;i++) + rectangle(0,0,i,i); + itoa(j+1,st,10); + setcolor(no_color); + outtextxy(5,2,st); + b[j].box= malloc(imagesize(0,0,25,25)); +getimage(0,0,25,25,b[j].box); +} cleardevice(); + setlinestyle(SOLID_LINE,1,3); +setcolor(4); +rectangle(0,0,28,28); +void *select= malloc(imagesize(0,0,28,28)); +getimage(0,0,28,28,select); + + randomize(); + for(q=0;q<15;q++) + { aa: int s=rand()%16; + if(b[s].boxx==NULL){b[s].boxx=tboxx[q]; + b[s].boxy=tboxy[q]; + } + else goto aa; + } + locx=x=50;locy=y=200; + display(); + putimage(x,y,select,1); + char ch; + + while(1) + { int key=bioskey(2); + if((key & 0x40) && (key & 0x20))quit(); + int ans= finish(); + gotoxy(10,24);printf("Remaining :%2d",ans); + + if(!ans){ getch ();quit(); } + + xx: ch=NULL; + while(ch!=13){ + ch=getch(); + + + switch (ch) + {case L:x-=30;break; + case R:x+=30;break; + case D:y+=35;break; + case U:y-=35;break; + } + if(x>140)x=50;if(y>305)y=200; + if(x<50)x=140;if(y<200)y=305; + putimage(locx,locy,select,1); + d= getboxpos(); + putimage(locx,locy,select,1); + } + if(!check_box())goto xx; + putimage(locx,locy,b[d].box,1); + putimage(empty_x,empty_y,b[d].box,1); + b[d].boxx=empty_x;b[d].boxy=empty_y; + empty_x=locx; empty_y=locy; + } + + +} +/*~~~~~~~~~~~~~~~~~~~~~Subroutines~~~~~~~~~~~~~*/ + +int getboxpos() + { + for(int a=0;a<15;a++) + { if(x>=b[a].boxx && x<=b[a].boxx+25) {locx=b[a].boxx;break;} + else continue; + } + + for(a=0;a<15;a++) + { if(y>=b[a].boxy && y<=b[a].boxy+25) {locy=b[a].boxy;break;} + else continue; + } + for(a=0;a<15;a++) + { if(locx==b[a].boxx && locy==b[a].boxy)return a; + else continue; + } + return 0; + } + int check_box() + { + if(abs(locx-empty_x)==30 && abs(locy-empty_y)==0) + { + gotoxy(60,12); printf(" "); + + return 1; } + else if(abs(locx-empty_x)==0 && abs(locy-empty_y)==35) + { + gotoxy(40,16); printf(" "); + + return 1; } + + else + { + gotoxy(40,16); printf("Invalid Selection."); + + } + return 0; + } + void quit(void) { + + closegraph(); + restorecrtmode(); + printf(" + + + + Hoped you Enjoyed !"); +if(play!=15) printf(" + +Try arranging other ranges."); + exit(0); + } + int finish(void) + { if(arrange=='h'){ for(int t=0;t +#include +int main(void) +{ + +cout<<"Explorer will launch.\n"< + LeftistHeap::LeftistHeap( ) + { + root = NULL; + } + + /** + * Copy constructor. + */ + template + LeftistHeap::LeftistHeap( const LeftistHeap & rhs ) + { + root = NULL; + *this = rhs; + } + + + /** + * Destruct the leftist heap. + */ + template + LeftistHeap::~LeftistHeap( ) + { + makeEmpty( ); + } + + /** + * Merge rhs into the priority queue. + * rhs becomes empty. rhs must be different from this. + */ + template + void LeftistHeap::merge( LeftistHeap & rhs ) + { + if( this == &rhs ) // Avoid aliasing problems + return; + + root = merge( root, rhs.root ); + rhs.root = NULL; + } + + /** + * Internal method to merge two roots. + * Deals with deviant cases and calls recursive merge1. + */ + template + LeftistNode * + LeftistHeap::merge( LeftistNode * h1, + LeftistNode * h2 ) const + { + if( h1 == NULL ) + return h2; + if( h2 == NULL ) + return h1; + if( h1->element < h2->element ) + return merge1( h1, h2 ); + else + return merge1( h2, h1 ); + } + + /** + * Internal method to merge two roots. + * Assumes trees are not empty, and h1's root contains smallest item. + */ + template + LeftistNode * + LeftistHeap::merge1( LeftistNode * h1, + LeftistNode * h2 ) const + { + if( h1->left == NULL ) // Single node + h1->left = h2; // Other fields in h1 already accurate + else + { + h1->right = merge( h1->right, h2 ); + if( h1->left->npl < h1->right->npl ) + swapChildren( h1 ); + h1->npl = h1->right->npl + 1; + } + return h1; + } + + /** + * Swaps t's two children. + */ + template + void LeftistHeap::swapChildren( LeftistNode * t ) const + { + LeftistNode *tmp = t->left; + t->left = t->right; + t->right = tmp; + } + + /** + * Insert item x into the priority queue, maintaining heap order. + */ + template + void LeftistHeap::insert( const Comparable & x ) + { + root = merge( new LeftistNode( x ), root ); + } + + /** + * Find the smallest item in the priority queue. + * Return the smallest item, or throw Underflow if empty. + */ + template + const Comparable & LeftistHeap::findMin( ) const + { + if( isEmpty( ) ) + throw Underflow( ); + return root->element; + } + + /** + * Remove the smallest item from the priority queue. + * Throws Underflow if empty. + */ + template + void LeftistHeap::deleteMin( ) + { + if( isEmpty( ) ) + throw Underflow( ); + + LeftistNode *oldRoot = root; + root = merge( root->left, root->right ); + delete oldRoot; + } + + /** + * Remove the smallest item from the priority queue. + * Pass back the smallest item, or throw Underflow if empty. + */ + template + void LeftistHeap::deleteMin( Comparable & minItem ) + { + minItem = findMin( ); + deleteMin( ); + } + + /** + * Test if the priority queue is logically empty. + * Returns true if empty, false otherwise. + */ + template + bool LeftistHeap::isEmpty( ) const + { + return root == NULL; + } + + /** + * Test if the priority queue is logically full. + * Returns false in this implementation. + */ + template + bool LeftistHeap::isFull( ) const + { + return false; + } + + /** + * Make the priority queue logically empty. + */ + template + void LeftistHeap::makeEmpty( ) + { + reclaimMemory( root ); + root = NULL; + } + + /** + * Deep copy. + */ + template + const LeftistHeap & + LeftistHeap:: + operator=( const LeftistHeap & rhs ) + { + if( this != &rhs ) + { + makeEmpty( ); + root = clone( rhs.root ); + } + return *this; + } + + /** + * Internal method to make the tree empty. + * WARNING: This is prone to running out of stack space; + * exercises suggest a solution. + */ + template + void LeftistHeap::reclaimMemory( LeftistNode * t ) const + { + if( t != NULL ) + { + reclaimMemory( t->left ); + reclaimMemory( t->right ); + delete t; + } + } + + /** + * Internal method to clone subtree. + * WARNING: This is prone to running out of stack space. + * exercises suggest a solution. + */ + template + LeftistNode * + LeftistHeap::clone( LeftistNode * t ) const + { + if( t == NULL ) + return NULL; + else + return new LeftistNode( t->element, clone( t->left ), + clone( t->right ), t->npl ); + } diff --git a/c++/Others/LeftistHeap.h - Header file for leftist heap.cpp b/c++/Others/LeftistHeap.h - Header file for leftist heap.cpp new file mode 100644 index 0000000..4a07f58 --- /dev/null +++ b/c++/Others/LeftistHeap.h - Header file for leftist heap.cpp @@ -0,0 +1,76 @@ +LeftistHeap.h - Header file for leftist heap + + #ifndef BINARY_HEAP_H_ + #define BINARY_HEAP_H_ + + #include + + // Leftist heap class + // + // CONSTRUCTION: with no parameters + // + // ******************PUBLIC OPERATIONS********************* + // void insert( x ) --> Insert x + // deleteMin( minItem ) --> Remove (and optionally return) smallest item + // Comparable findMin( ) --> Return smallest item + // bool isEmpty( ) --> Return true if empty; else false + // bool isFull( ) --> Return true if full; else false + // void makeEmpty( ) --> Remove all items + // void merge( rhs ) --> Absorb rhs into this heap + // ******************ERRORS******************************** + // Throws Underflow and Overflow as warranted + + + // Node and forward declaration because g++ does + // not understand nested classes. + template + class LeftistHeap; + + template + class LeftistNode + { + Comparable element; + LeftistNode *left; + LeftistNode *right; + int npl; + + LeftistNode( const Comparable & theElement, LeftistNode *lt = NULL, + LeftistNode *rt = NULL, int np = 0 ) + : element( theElement ), left( lt ), right( rt ), npl( np ) { } + friend class LeftistHeap; + }; + + template + class LeftistHeap + { + public: + LeftistHeap( ); + LeftistHeap( const LeftistHeap & rhs ); + ~LeftistHeap( ); + + bool isEmpty( ) const; + bool isFull( ) const; + const Comparable & findMin( ) const; + + void insert( const Comparable & x ); + void deleteMin( ); + void deleteMin( Comparable & minItem ); + void makeEmpty( ); + void merge( LeftistHeap & rhs ); + + const LeftistHeap & operator=( const LeftistHeap & rhs ); + + private: + LeftistNode *root; + + LeftistNode * merge( LeftistNode *h1, + LeftistNode *h2 ) const; + LeftistNode * merge1( LeftistNode *h1, + LeftistNode *h2 ) const; + void swapChildren( LeftistNode * t ) const; + void reclaimMemory( LeftistNode * t ) const; + LeftistNode * clone( LeftistNode *t ) const; + }; + + #include "LeftistHeap.cpp" + #endif diff --git a/c++/Others/LinkedList.cpp - Implementation for linked list.cpp b/c++/Others/LinkedList.cpp - Implementation for linked list.cpp new file mode 100644 index 0000000..c9457e1 --- /dev/null +++ b/c++/Others/LinkedList.cpp - Implementation for linked list.cpp @@ -0,0 +1,145 @@ +LinkedList.cpp - Implementation for linked list + + #include "LinkedList.h" + + /** + * Construct the list + */ + template + List::List( ) + { + header = new ListNode; + } + + /** + * Copy constructor + */ + template + List::List( const List & rhs ) + { + header = new ListNode; + *this = rhs; + } + + /** + * Destructor + */ + template + List::~List( ) + { + makeEmpty( ); + delete header; + } + + /** + * Test if the list is logically empty. + * return true if empty, false otherwise. + */ + template + bool List::isEmpty( ) const + { + return header->next == NULL; + } + + /** + * Make the list logically empty. + */ + template + void List::makeEmpty( ) + { + while( !isEmpty( ) ) + remove( first( ).retrieve( ) ); + } + + /** + * Return an iterator representing the header node. + */ + template + ListItr List::zeroth( ) const + { + return ListItr( header ); + } + + /** + * Return an iterator representing the first node in the list. + * This operation is valid for empty lists. + */ + template + ListItr List::first( ) const + { + return ListItr( header->next ); + } + + /** + * Insert item x after p. + */ + template + void List::insert( const Object & x, const ListItr & p ) + { + if( p.current != NULL ) + p.current->next = new ListNode( x, p.current->next ); + } + + /** + * Return iterator corresponding to the first node containing an item x. + * Iterator isPastEnd if item is not found. + */ + template + ListItr List::find( const Object & x ) const + { +/* 1*/ ListNode *itr = header->next; + +/* 2*/ while( itr != NULL && itr->element != x ) +/* 3*/ itr = itr->next; + +/* 4*/ return ListItr( itr ); + } + + /** + * Return iterator prior to the first node containing an item x. + */ + template + ListItr List::findPrevious( const Object & x ) const + { +/* 1*/ ListNode *itr = header; + +/* 2*/ while( itr->next != NULL && itr->next->element != x ) +/* 3*/ itr = itr->next; + +/* 4*/ return ListItr( itr ); + } + + /** + * Remove the first occurrence of an item x. + */ + template + void List::remove( const Object & x ) + { + ListItr p = findPrevious( x ); + + if( p.current->next != NULL ) + { + ListNode *oldNode = p.current->next; + p.current->next = p.current->next->next; // Bypass deleted node + delete oldNode; + } + } + + /** + * Deep copy of linked lists. + */ + template + const List & List::operator=( const List & rhs ) + { + ListItr ritr = rhs.first( ); + ListItr itr = zeroth( ); + + if( this != &rhs ) + { + makeEmpty( ); + for( ; !ritr.isPastEnd( ); ritr.advance( ), itr.advance( ) ) + insert( ritr.retrieve( ), itr ); + } + return *this; + } + diff --git a/c++/Others/LinkedList.h - Header file for linked list.cpp b/c++/Others/LinkedList.h - Header file for linked list.cpp new file mode 100644 index 0000000..ada91be --- /dev/null +++ b/c++/Others/LinkedList.h - Header file for linked list.cpp @@ -0,0 +1,103 @@ +LinkedList.h - Header file for linked list + + #ifndef LinkedList_H + #define LinkedList_H + + #include "dsexceptions.h" + #include // For NULL + + // List class + // + // CONSTRUCTION: with no initializer + // Access is via ListItr class + // + // ******************PUBLIC OPERATIONS********************* + // boolean isEmpty( ) --> Return true if empty; else false + // void makeEmpty( ) --> Remove all items + // ListItr zeroth( ) --> Return position to prior to first + // ListItr first( ) --> Return first position + // void insert( x, p ) --> Insert x after current iterator position p + // void remove( x ) --> Remove x + // ListItr find( x ) --> Return position that views x + // ListItr findPrevious( x ) + // --> Return position prior to x + // ******************ERRORS******************************** + // No special errors + + template + class List; // Incomplete declaration. + + template + class ListItr; // Incomplete declaration. + + template + class ListNode + { + ListNode( const Object & theElement = Object( ), ListNode * n = NULL ) + : element( theElement ), next( n ) { } + + Object element; + ListNode *next; + + friend class List; + friend class ListItr; + }; + + + template + class List + { + public: + List( ); + List( const List & rhs ); + ~List( ); + + bool isEmpty( ) const; + void makeEmpty( ); + ListItr zeroth( ) const; + ListItr first( ) const; + void insert( const Object & x, const ListItr & p ); + ListItr find( const Object & x ) const; + ListItr findPrevious( const Object & x ) const; + void remove( const Object & x ); + + const List & operator=( const List & rhs ); + + private: + ListNode *header; + }; + + + // ListItr class; maintains "current position" + // + // CONSTRUCTION: Package friendly only, with a ListNode + // + // ******************PUBLIC OPERATIONS********************* + // bool isPastEnd( ) --> True if past end position in list + // void advance( ) --> Advance (if not already null) + // Object retrieve --> Return item in current position + + template + class ListItr + { + public: + ListItr( ) : current( NULL ) { } + bool isPastEnd( ) const + { return current == NULL; } + void advance( ) + { if( !isPastEnd( ) ) current = current->next; } + const Object & retrieve( ) const + { if( isPastEnd( ) ) throw BadIterator( ); + return current->element; } + + private: + ListNode *current; // Current position + + ListItr( ListNode *theNode ) + : current( theNode ) { } + + friend class List; // Grant access to constructor + }; + + #include "LinkedList.cpp" + #endif diff --git a/c++/Others/Matrix Multiplication.cpp b/c++/Others/Matrix Multiplication.cpp new file mode 100644 index 0000000..f24b1ae --- /dev/null +++ b/c++/Others/Matrix Multiplication.cpp @@ -0,0 +1,146 @@ +Matrix Multiplication + +void main() +{ + int row1=0, + col1=1, + row2=0, + col2=0, + **matrix1, + **matrix2, + **result; + + clrscr(); + printf(" Enter number of row for first matrix "); + scanf("%d",&row1); + + while (col1!=row2) + { + printf(" Enter number of column for first matrix "); + scanf("%d",&col1); + + printf(" Enter number of row for second matrix "); + scanf("%d",&row2); + + if (col1!=row2) + { + clrscr(); + printf("Column number of first matrix must be same as the row number of second matrix"); + } + + + } + + + printf(" Enter number of column for second matrix "); + scanf("%d",&col2); + + matrix1=init(matrix1,row1,col1); + matrix2=init(matrix2,row2,col2); + /* setting values in matrix */ + printf("First matrix \n"); + set(matrix1,row1,col1); + printf("Second matrix \n"); + set(matrix2,row2,col2); + /* printint matrix */ + clrscr(); + printf(" [ First matrix ]\n"); + get(matrix1,row1,col1); + printf(" [ Second matrix ]\n"); + get(matrix2,row2,col2); + + printf(" [ Multiplication Result ]\n"); + result=mul(matrix1,matrix2,row1,col2,col1); + get(result,row1,col2); + printf("\n\t\t Thanks from debmalya jash"); + getch(); + free(matrix1); + free(matrix2); + fress(result); + + +} /* end main */ + + +/* to initialize matrix */ +int** init(int** arr,int row,int col) +{ + int i=0, + j=0; + + arr=(int**)malloc(sizeof(int)*row*col); + + for(i=0;i + #include "vector.h" + +/* START: Fig02_05.txt */ + /** + * Cubic maximum contiguous subsequence sum algorithm. + */ + int maxSubSum1( const vector & a ) + { +/* 1*/ int maxSum = 0; + +/* 2*/ for( int i = 0; i < a.size( ); i++ ) +/* 3*/ for( int j = i; j < a.size( ); j++ ) + { +/* 4*/ int thisSum = 0; + +/* 5*/ for( int k = i; k <= j; k++ ) +/* 6*/ thisSum += a[ k ]; + +/* 7*/ if( thisSum > maxSum ) +/* 8*/ maxSum = thisSum; + } + +/* 9*/ return maxSum; + } +/* END */ + + +/* START: Fig02_06.txt */ + /** + * Quadratic maximum contiguous subsequence sum algorithm. + */ + int maxSubSum2( const vector & a ) + { +/* 1*/ int maxSum = 0; + +/* 2*/ for( int i = 0; i < a.size( ); i++ ) + { +/* 3*/ int thisSum = 0; +/* 4*/ for( int j = i; j < a.size( ); j++ ) + { +/* 5*/ thisSum += a[ j ]; + +/* 6*/ if( thisSum > maxSum ) +/* 7*/ maxSum = thisSum; + } + } + +/* 8*/ return maxSum; + } +/* END */ + + /** + * Return maximum of three integers. + */ + int max3( int a, int b, int c ) + { + return a > b ? a > c ? a : c : b > c ? b : c; + } + +/* START: Fig02_07.txt */ + /** + * Recursive maximum contiguous subsequence sum algorithm. + * Finds maximum sum in subarray spanning a[left..right]. + * Does not attempt to maintain actual best sequence. + */ + int maxSumRec( const vector & a, int left, int right ) + { +/* 1*/ if( left == right ) // Base case +/* 2*/ if( a[ left ] > 0 ) +/* 3*/ return a[ left ]; + else +/* 4*/ return 0; + +/* 5*/ int center = ( left + right ) / 2; +/* 6*/ int maxLeftSum = maxSumRec( a, left, center ); +/* 7*/ int maxRightSum = maxSumRec( a, center + 1, right ); + +/* 8*/ int maxLeftBorderSum = 0, leftBorderSum = 0; +/* 9*/ for( int i = center; i >= left; i-- ) + { +/*10*/ leftBorderSum += a[ i ]; +/*11*/ if( leftBorderSum > maxLeftBorderSum ) +/*12*/ maxLeftBorderSum = leftBorderSum; + } + +/*13*/ int maxRightBorderSum = 0, rightBorderSum = 0; +/*14*/ for( int j = center + 1; j <= right; j++ ) + { +/*15*/ rightBorderSum += a[ j ]; +/*16*/ if( rightBorderSum > maxRightBorderSum ) +/*17*/ maxRightBorderSum = rightBorderSum; + } + +/*18*/ return max3( maxLeftSum, maxRightSum, +/*19*/ maxLeftBorderSum + maxRightBorderSum ); + } + + /** + * Driver for divide-and-conquer maximum contiguous + * subsequence sum algorithm. + */ + int maxSubSum3( const vector & a ) + { + return maxSumRec( a, 0, a.size( ) - 1 ); + } +/* END */ + + +/* START: Fig02_08.txt */ + /** + * Linear-time maximum contiguous subsequence sum algorithm. + */ + int maxSubSum4( const vector & a ) + { +/* 1*/ int maxSum = 0, thisSum = 0; + +/* 2*/ for( int j = 0; j < a.size( ); j++ ) + { +/* 3*/ thisSum += a[ j ]; + +/* 4*/ if( thisSum > maxSum ) +/* 5*/ maxSum = thisSum; +/* 6*/ else if( thisSum < 0 ) +/* 7*/ thisSum = 0; + } + +/* 8*/ return maxSum; + } +/* END */ + + /** + * Simple test program. + */ + int main( ) + { + vector a( 8 ); + a[ 0 ] = 4; a[ 1 ] = -3; a[ 2 ] = 5; a[ 3 ] = -2; + a[ 4 ] = -1; a[ 5 ] = 2; a[ 6 ] = 6; a[ 7 ] = -2; + int maxSum; + + maxSum = maxSubSum1( a ); + cout << "Max sum is " << maxSum << endl; + maxSum = maxSubSum2( a ); + cout << "Max sum is " << maxSum << endl; + maxSum = maxSubSum3( a ); + cout << "Max sum is " << maxSum << endl; + maxSum = maxSubSum4( a ); + cout << "Max sum is " << maxSum << endl; + + return 0; + } diff --git a/c++/Others/MemoryCell.cpp - MemoryCell class implementation (Fig 1.21).cpp b/c++/Others/MemoryCell.cpp - MemoryCell class implementation (Fig 1.21).cpp new file mode 100644 index 0000000..29580f8 --- /dev/null +++ b/c++/Others/MemoryCell.cpp - MemoryCell class implementation (Fig 1.21).cpp @@ -0,0 +1,31 @@ +MemoryCell.cpp - MemoryCell class implementation (Fig 1.21) + + #include "MemoryCell.h" + + /** + * Construct the MemoryCell with initialValue + */ + template + MemoryCell::MemoryCell( const Object & initialValue ) + : storedValue( initialValue ) + { + } + + /** + * Return the stored value. + */ + template + const Object & MemoryCell::read( ) const + { + return storedValue; + } + + /** + * Store x. + */ + template + void MemoryCell::write( const Object & x ) + { + storedValue = x; + } + diff --git a/c++/Others/MemoryCell.h - MemoryCell class interface (Fig 1.20).cpp b/c++/Others/MemoryCell.h - MemoryCell class interface (Fig 1.20).cpp new file mode 100644 index 0000000..5134cf3 --- /dev/null +++ b/c++/Others/MemoryCell.h - MemoryCell class interface (Fig 1.20).cpp @@ -0,0 +1,22 @@ +MemoryCell.h - MemoryCell class interface (Fig 1.20) + + #ifndef MEMORY_CELL_H + #define MEMORY_CELL_H + + /** + * A class for simulating a memory cell. + */ + template + class MemoryCell + { + public: + explicit MemoryCell( const Object & initialValue = Object( ) ); + const Object & read( ) const; + void write( const Object & x ); + private: + Object storedValue; + }; + + #include "MemoryCell.cpp" // Because sep. compilation doesn't always work + + #endif diff --git a/c++/Others/Merge Sort.cpp b/c++/Others/Merge Sort.cpp new file mode 100644 index 0000000..b150a6d --- /dev/null +++ b/c++/Others/Merge Sort.cpp @@ -0,0 +1,89 @@ +Merge Sort + +#include +int a[50]; +void merge(int,int,int); +void merge_sort(int low,int high) +{ + int mid; + if(lowmid) + { + for(k=j;k<=high;k++) + { + b[i]=a[k]; + i++; + } + } + else + { + for(k=h;k<=mid;k++) + { + b[i]=a[k]; + i++; + } + } + for(k=low;k<=high;k++) a[k]=b[k]; +} +void main() +{ + int num,i; + +cout<<"******************************************************************* +*************"<>num; + cout<>a[i] ; + } + merge_sort(1,num); + cout< +#include +#include +#include +void main() +{ + ifstream infile; + ofstream outfile; + ofstream printer; + char filename[20]; + cout<<" +Enter the desired file to copy."; + cin>>filename; + infile.open(filename,ios::nocreate); + if(!infile) + { + cout<<"Input file can not be opened."< +#include +class college +{ + private: + char collegename[80]; + public: + college() + { + strcpy(collegename,"XXX"); + } + char * getcollegename() + { + return collegename; + } +}; +class student:public college +{ + private: + char studname[40]; + char address[80]; + public: + student(char *name) + { + strcpy(studname,name); + } + char * studentname() + { + return studname; + } + setaddress(char *add) + { + strcpy(address,add); + } + char * studentaddress() + { + return address; + } +}; + + +#include +#include +void main() +{ + clrscr(); + studentfile student; + student.studentname("XXX"); + getch(); +}; + + +#include +#include +#include +//Declare a function with one required parameter +void display(int number,...); +void main() +{ + int index=5; + int one=1,two=2; + clrscr(); + display(one,index); + getch(); +} +void display(int number,...) +{ + va_list para; + va_start(para,number); + cout<<"The parameters are:"< +#include +void main() + { + clrscr(); + printf("%d +%d",sizeof(NULL),sizeof("")); + getch(); + } + +#include +#include +void main() + { + int a=10,b=20; + clrscr(); + swapv(&a,&b); + printf(" + A=%d",a); + printf(" + B=%d",b); + getch(); + } + + swapv(int *x,int *y) + { + int t; + t=*x; + *x=*y; + *y=t; + return; + } + + +/* This is the program using pointer to swap values */ + +#include +#include +void main() + { + int a=10,b=20; + clrscr(); + nilesh(a,b); + printf(" + A=%d",a); + printf(" + B=%d",b); + getch(); + } + + nilesh(x,y) + { + int t; + t=x; + x=y; + y=t; + printf(" + X=%d",x); + printf(" + Y=%d",y); + return; + } diff --git a/c++/Others/Modification of previous program to handle 10 cust.cpp b/c++/Others/Modification of previous program to handle 10 cust.cpp new file mode 100644 index 0000000..c235d3c --- /dev/null +++ b/c++/Others/Modification of previous program to handle 10 cust.cpp @@ -0,0 +1,120 @@ +Modification of previous program to handle 10 customers + +# include +# include +# include + +class bank + { + char name[20]; + int acno; + char actype[4]; + float balance; + public: + void init(); + void deposit(); + void withdraw(); + void disp_det(); + }; +// member functions +void bank :: init() +{ +cout<<" + + New Account +"; +cout<<" + +Enter the Name of the depositor : "; +cin.get(name,19,' +'); +cout<<" +Enter the Account Number : "; +cin>>acno; +cout<<" +Enter the Account Type : (CURR/SAVG/FD/RD/DMAT) "; +cin>>actype; +cout<<" +Enter the Amount to Deposit : "; +cin >>balance; +} +void bank :: deposit() +{ +float more; +cout <<" + Depositing +"; +cout<<" + +Enter the amount to deposit : "; +cin>>more; +balance+=more; +} +void bank :: withdraw() +{ +float amt; +cout<<" + Withdrwal +"; +cout<<" + +Enter the amount to withdraw : "; +cin>>amt; +balance-=amt; +} +void bank :: disp_det() +{ +cout<<" + + Account Details + +"; +cout<<"Name of the depositor : "<> num; +cout<<" + +Enter 0 to exit + 1. Initialize a new acc. + 2. Deposit + 3.Withdraw + 4.See A/c Status"; +cin>>choice; +switch(choice) +{ + case 0 : + cout<<" + + EXITING PROGRAM."; + break; + case 1 : obj[num].init(); + break; + case 2: obj[num].deposit(); + break; + case 3 : obj[num].withdraw(); + break; + case 4: obj[num].disp_det(); + break; + default: cout<<" + +Illegal Option"< +#include +#include +#include +void main(){ + clrscr();_setcursortype(_NOCURSOR); + REGS regs; + //Initializing and showing mouse + regs.x.ax=0;int86(0x33,®s,®s); + regs.x.ax=1;int86(0x33,®s,®s); + //Reading mouse click + for( ; ; ){ + //Updating mouse motions + regs.x.ax=3;int86(0x33,®s,®s); + //Reading mouse click + if(regs.x.bx==1){ + gotoxy(2,2);textbackground(1);textcolor(15); + cprintf("Left Button Clicked!"); + delay(100); + } + if(regs.x.bx==2){ + gotoxy(2,2);textcolor(15);textbackground(1); + cprintf("Right Button Clicked!"); + delay(100); + } + gotoxy(1,2);textbackground(1);cprintf(" "); + //Printing mouse coordinates + gotoxy(1,1);textcolor(11);textbackground(6); + cprintf(" Mouse Position:(%3d,%3d)",regs.x.cx,regs.x.dx); + while(kbhit()){exit(0);} + } +} diff --git a/c++/Others/Movement of variables in Stack wihout any graphics.cpp b/c++/Others/Movement of variables in Stack wihout any graphics.cpp new file mode 100644 index 0000000..eff29f4 --- /dev/null +++ b/c++/Others/Movement of variables in Stack wihout any graphics.cpp @@ -0,0 +1,93 @@ +Movement of variables in Stack wihout any graphics + +Code : +#include +#include +#include +#include +void hori(int,int); +void para(int,int); +void vert(int,int); +static int x=3,y=15; +char ch; +void main() +{ clrscr(); + cout <<" +enter a character and see the path "; + cin >>ch; + gotoxy(x,y); + x++; + cout< +using namespace std; +int main() +{ +int number,power,count,i; + +cout << "Enter Number: "; cin >> number; +cout << "Enter the power: "; cin >> power; + +count = 1; +for (i=1; i <=power; i++) +count = count*number; + +cout << count << endl; + +return 0; +} diff --git a/c++/Others/Mutation strings This is a code just to find an unknown string.cpp b/c++/Others/Mutation strings This is a code just to find an unknown string.cpp new file mode 100644 index 0000000..da6b22e --- /dev/null +++ b/c++/Others/Mutation strings This is a code just to find an unknown string.cpp @@ -0,0 +1,90 @@ +Mutation strings - This is a code just to find an unknown string + +#include +#include +#include +class mutation +{ + public: + char id[10],p1[9],p2[9],p[9],str[4]; + int c,f; + void sign(); + void hack(); +}; + + + /*JUST LIKE THAT*/ +void mutation::sign() +{ +cout<<"welcome"<>id; + cout<<"Please enter desired password:"; + cin>>p1; + cout<<"Please confirm your password :"; + cin>>p2; + c=strcmp(p1,p2); /*c=0 if p1==p2 else any non zero number*/ + if(c==0) + cout<<"Your id has been confirmed."< +#include +void main() +{ +int s,a,t,o,x=2,c,r,i; +char ch; +s=t=0,r=22,c=2; +clrscr(); +cout<<" This is a computer Game. + +######################## + +There are 22 balls on a table,you can take +either a + "; +cout<<"maximum of 4 balls or a minimum of 1 at a time.If you take +"; +cout<<" the last ball from the table you will WIN other wise Computer +.. +"; +cout<<" +Either You or Coputer can Take First ,Enter yr choice +I(you)/C(computer) +"; +cin>>ch; +if (ch=='I'|| ch=='i') +{ +i=1,o=1; +s: +for (;i<17;i++) +{ +cout<<" + +You:"; +cin>>a; + switch(a) + { + case 1: + r=r-a; + s=s+a; + cout<<"Remaining ="< +#include +int main() +{ +cout<<"The decimal value of 15 is "<<15< + +int main() +{ +cout<<"The decimal value of 15 is "<<15< +#include +#include +#include +#include +int count =0; +class emp +{ +char name[40]; +char jobdeg[40],phno[20]; +float salary,srno; +public: +void getdata(void); +void display(void); +void mod_data(); +}; +void emp::getdata(void) +{ +char ch; +cin.get(ch); +clrscr(); +gotoxy(15,10); +cout<<"Add student data +"; +gotoxy(17,12); +cout<<"Record #"<<(++count)<>srno; +cout<<" + Enter Name"; +gets(name); +cout<<" + Enter Job designation";gets(jobdeg); +cout<<" + Enter Phone number";gets(phno); +cout<<" + Enter the Salary";cin>>salary; +cout<<" +"; +} +void emp::display(void) +{ +clrscr(); +gotoxy(15,10); +cout<<"Student Details + "; +gotoxy(1,12); +cout<<" + Sr. NO "<>sr; +cout<<" + Name";gets(nm); +cout<<" + Job designation ";gets(jd); +cout<<" + Salary";cin>>sal; +cout<<" + Phone number";gets(ph); +if(strlen(nm)!=0)strcpy(name,nm); +if(strlen(jd)!=0)strcpy(jobdeg,jd); +if(strlen(ph)!=0)strcpy(phno,ph); +if(sal>salary||salsrno||sr15;c=c-2) + { + delay(100); + gotoxy(c,20); + cout<<"*"; + } + + for(r=12;r<21;r++) + { + delay(100); + gotoxy(55,r); + cout<<"*"; + } + + for(r=12;r>4;r=r-1) + { + delay(100); + gotoxy(15,r); + cout<<"*"; + } + +for(r=8;r<=8;r++) + { + delay(10); + gotoxy(25,r); + cout<<"*"; + } + +for(r=8;r<=8;r++) + { + delay(10); + gotoxy(45,r); + cout<<"*"; + } + +for(r=16;r<=16;r++) + { + delay(10); + gotoxy(25,r); + cout<<"*"; + } + + for(r=16;r<=16;r++) + { + delay(10); + gotoxy(45,r); + cout<<"*"; + } + delay(1400); + clrscr(); +/* OFFICE MANAGEMENT */ +delay(300); + cout<<" + + + + + + + + + + O "; + delay(300); + cout<<"F "; + delay(300); + cout<<"F "; + delay(300); + cout<<"I "; + delay(300); + cout<<"C "; + delay(300); + cout<<"E "; + delay(300); + cout<<" M "; + delay(300); + cout<<"A "; + delay(300); + cout<<"N "; + delay(300); + cout<<"A "; + delay(300); + cout<<"G"; + delay(300); + cout<<" E"; + delay(300); + cout<<" M"; + delay(300); + cout<<" E"; + delay(300); + cout<<" N"; + delay(300); + cout<<" T "; + delay(300); + cout<<" ****** "; + delay(300); + cout<<" ... "; + delay(1400); +cout<<"a + + + + + + + + PRESS ANY KEY ........ "; + +for(c=1;c<80;c++) +{ + delay(10); + gotoxy(c,1); + cout<<"&"; + } + +for(r=1;r<26;r++) + { + delay(10); + gotoxy(1,r); + cout<<"&&"; + } + +for(c=26;c<102;c++) +{ + delay(10); + gotoxy(c,26); + cout<<"&"; +} + +for(r=1;r<26;r++) +{ + delay(10); + gotoxy(78,r); + cout<<"&&"; +} +getch(); +} +clrscr(); +textcolor(CYAN); +cout<<" + + + Main menu"; +cout<<" ______________"; +cout<<" + 1.Add record"; +cout<<" + 2.Modify record"; +cout<<" + 3.Display record"; +cout<<" + 4.Exit....... + "; +cin>>choice; +switch(choice) +{ +case 1:empl.getdata(); + merc=count; + offset=((merc-1)*sizeof(emp)); + finout.seekp(offset,ios::beg); + finout.write((char*) &empl,sizeof(emp)); + break; +case 2:if(!count) +{ gotoxy(20,20); + cout<<" No record has been added yet!!!! + plz run option 1 +first!!!!"; + cout<<"Press any key to continue........."; + getch(); + break; +} + cout<<"Modify which record"; + cin>>merc; + if( merc>count) +{ + cout<<" + + + Only "<>ans; + if(ans=='y'||ans=='Y') + { + cout<<"Enter new details"; + empl.mod_data(); + finout.seekp(offset,ios::beg); + finout.write((char*) &empl,sizeof(emp)); + cout<<"Record modified!!!!!"; + gotoxy(20,20); + cout<<"Press any key to continue!!!!!!!!"; + getch(); + } + break; + } +case 3: + if(!count) + { + cout<<" + + + No record has been added yet"; + cout<<"Please run the optionm 1 first on the main screen"; + gotoxy(10,20); + cout<<"press any key to continue"; + getch(); + break; + } + cout<<" + + Display which record"; + cin>>merc; + cout<count) +{ + cout<<" + + + Only "<=1&& choice<=3); +finout.close(); +return 0; +} + diff --git a/c++/Others/Open a file and display contents on the screen.cpp b/c++/Others/Open a file and display contents on the screen.cpp new file mode 100644 index 0000000..eedf41d --- /dev/null +++ b/c++/Others/Open a file and display contents on the screen.cpp @@ -0,0 +1,18 @@ +Open a file and display contents on the screen + +//this example opens a file called myfile.txt +//and reads the text message to it +#include +int main() +{ +ifstream MyFile("myfile.txt"); +char ch; + +while(!MyFile.eof()) +{ +MyFile.get (ch); +cout< + #include "vector.h" + + class Polynomial + { + enum { MAX_DEGREE = 100 }; + friend int main( ); // So I can do a quick test. + + public: + Polynomial( ); + void zeroPolynomial( ); + Polynomial operator+( const Polynomial & rhs ) const; + Polynomial operator*( const Polynomial & rhs ) const; + void print( ostream & out ) const; + + private: + vector coeffArray; + int highPower; + }; + + + int max( int a, int b ) + { + return a > b ? a : b; + } + + Polynomial::Polynomial( ) : coeffArray( MAX_DEGREE + 1 ) + { + zeroPolynomial( ); + } + + void Polynomial::zeroPolynomial( ) + { + for( int i = 0; i <= MAX_DEGREE; i++ ) + coeffArray[ i ] = 0; + highPower = 0; + } + + Polynomial Polynomial::operator+( const Polynomial & rhs ) const + { + Polynomial sum; + + sum.highPower = max( highPower, rhs.highPower ); + for( int i = sum.highPower; i >= 0; i-- ) + sum.coeffArray[ i ] = coeffArray[ i ] + rhs.coeffArray[ i ]; + return sum; + } + + Polynomial Polynomial::operator*( const Polynomial & rhs ) const + { + Polynomial product; + + product.highPower = highPower + rhs.highPower; + if( product.highPower > MAX_DEGREE ) + cerr << "operator* exceeded MAX_DEGREE" << endl; + for( int i = 0; i <= highPower; i++ ) + for( int j = 0; j <= rhs.highPower; j++ ) + product.coeffArray[ i + j ] += + coeffArray[ i ] * rhs.coeffArray[ j ]; + return product; + } + + void Polynomial::print( ostream & out ) const + { + for( int i = highPower; i > 0; i-- ) + out << coeffArray[ i ] << "x^" << i << " + "; + out << coeffArray[ 0 ] << endl; + } + + ostream & operator<<( ostream & out, const Polynomial & rhs ) + { + rhs.print( out ); + return out; + } + + int main( ) + { + Polynomial p; + Polynomial q; + + p.highPower = 1; p.coeffArray[ 0 ] = 1; p.coeffArray[ 1 ] = 1; + + q = p + p; + p = q * q; + q = p + p; + + cout << q << endl; + return 0; + } diff --git a/c++/Others/Program To Implement Tower Of Hanoi Alogithm Using Recursion.cpp b/c++/Others/Program To Implement Tower Of Hanoi Alogithm Using Recursion.cpp new file mode 100644 index 0000000..cb20541 --- /dev/null +++ b/c++/Others/Program To Implement Tower Of Hanoi Alogithm Using Recursion.cpp @@ -0,0 +1,128 @@ +Program To Implement Tower Of Hanoi Alogithm Using Recursion. +This program shows the movements of disk from one tower to another when a key is pressed. + +Code : + + +#include +#include +#include + +class tower +{ + int *t1,*t2,*t3; + int x,y,z; + public: + void disp_tower(); + void move_disk(int tx,int ty); + void toh(int n,int a,int b,int c); + tower(int no); + ~tower(); +}; + +tower :: tower(int no) +{ + t1 = new int[no+1]; + t2 = new int[no+1]; + t3 = new int[no+1]; + x = no; + y = z = 0; + + for(int i=0,j=no ; i=1) + { + toh(n-1,tx,tz,ty); + move_disk(tx,ty); //x to y + disp_tower(); + toh(n-1,tz,ty,tx); + } +} + +void tower :: move_disk(int tx,int ty) +{ + switch(tx) + { + case 1: + { + if(ty==2) + t2[y++] = t1[--x]; + else + t3[z++] = t1[--x]; + }break; + case 2: + { + if(ty==1) + t1[x++] = t2[--y]; + else + t3[z++] = t2[--y]; + }break; + case 3: + { + if(ty==1) + t1[x++] = t3[--z]; + else + t2[y++] = t3[--z]; + }break; + }//end of switch +} +//------------------------------------------------------------------------ +--- +int main(void) +{ + clrscr(); + cout<<"Enter the no. of disks::"; + int no; + cin>>no; + tower obj(no); + obj.disp_tower(); + obj.toh(no,1,2,3); + getch(); + return 0; +} +//------------------------------------------------------------------------ +--- + + diff --git a/c++/Others/Program To Know the Day of Birth from Date of Birt.cpp b/c++/Others/Program To Know the Day of Birth from Date of Birt.cpp new file mode 100644 index 0000000..fc16377 --- /dev/null +++ b/c++/Others/Program To Know the Day of Birth from Date of Birt.cpp @@ -0,0 +1,111 @@ +Program To Know the Day of Birth from Date of Birth + +#include +#include +#include + +main() +{ + clrscr(); + int d,m,y,year,month,day,i,n; + printf("Enter how many times you want to run this program : "); + scanf("%d",&n); + for(i=1;i<=n;i++) + { + printf(" + +Enter the date : "); + scanf("%d%d%d",&d,&m,&y); + if( d>31 || m>12 || (y<1900 || y>=2000) ) + { + printf(" + +INVALID INPUT +"); + getch(); + exit(0); + } + year = y-1900; + year = year/4; + year = year+y-1900; + switch(m) + { + case 1: + case 10: + month = 1; + break; + case 2: + case 3: + case 11: + month = 4; + break; + case 7: + case 4: + month = 0; + break; + case 5: + month = 2; + break; + case 6: + month = 5; + break; + case 8: + month = 3; + break; + case 9: + case 12: + month = 6; + break; + } + year = year+month; + year = year+d; + day = year%7; + switch(day) + { + case 0: + printf(" + +Day is SATURDAY +"); + break; + case 1: + printf(" + +Day is SUNDAY +"); + break; + case 2: + printf(" + +Day is MONDAY +"); + break; + case 3: + printf(" + +Day is TUESDAY +"); + break; + case 4: + printf(" + +Day is WEDNESDAY +"); + break; + case 5: + printf(" + +Day is THURSDAY +"); + break; + case 6: + printf(" + +Day is FRIDAY +"); + break; + } +} + getch(); + return 0; +} diff --git a/c++/Others/Program for Overloading the difference operator for complex arithmetic.cpp b/c++/Others/Program for Overloading the difference operator for complex arithmetic.cpp new file mode 100644 index 0000000..58a1e5c --- /dev/null +++ b/c++/Others/Program for Overloading the difference operator for complex arithmetic.cpp @@ -0,0 +1,57 @@ +Program for Overloading the difference operator for complex arithmetic + +#include +#include + +class complex +{ +float real; +float img; +public: + complex() + { + real = 0; img = 0; + } + complex(float a,float b) + { + real =a ; img = b; + } + complex operator -(complex ); + void disp(); +}; +// Fn.for overloading of - operator for complex arithmetic +complex complex::operator-(complex a) +{ + return complex(real-a.real,img-a.img); +} +// function for display of Real & Imaginary Parts +void complex::disp() +{ +cout<<" +The real part is : "< +#include +class book +{ +char name[30]; +long int tel; +public: +void read() +{ +cout<<" +name:" ; +cin>>name; +cout<>tel; +} +void disp() +{ +cout<<" +PURCHASER DETAILS : "; +cout<<" +Name : "<>bname; +cout<<" +ISBN NO. : "; +cin>>isbn; +cout<<" +Price of Book : Rs."; +cin>>price; +} +void disp() +{ +cout<<" + +BOOK DETAILS :"; +cout<<" +Book-Name :" <read(); +(*ptr).disp(); +((shop *)ptr)->disp(); +getch(); +} diff --git a/c++/Others/Program for rotation of a string.cpp b/c++/Others/Program for rotation of a string.cpp new file mode 100644 index 0000000..e78a054 --- /dev/null +++ b/c++/Others/Program for rotation of a string.cpp @@ -0,0 +1,39 @@ +Program for rotation of a string + +:#include +#include +#include +void main() +{ + clrscr(); + char name[40],bubble,temp[40]; + int loop,size,count; + printf(" + + Enter the word "); + scanf("%s",name); + printf(" + + "); + for(loop=0;loop +# include +int area(int side) +{ + return side*side; +} +int area(int l , int b) +{ + return l*b; +} + +void main() +{ +clrscr(); +int (*p1)(int); +int (*p2)(int,int); + +p1=area; +p2=area; + +cout<<"Address of area(int)="<<(unsigned int)p1< +void main() +{cout<<" xAA xAB xAC xAD xAE xAF +"; + cout<<" xBA xBB xBC xBD xBE xBF +"; + cout<<" xCA xCB xCC xCD xCE xCF +"; + cout<<" xDA xDB xDC xDD xDE xDF +"; + cout<<" xEA xEB xEC xED xEE xEF +"; + cout<<" xFA xFB xFC xFD xFE xFF +"; +} diff --git a/c++/Others/Program to calculate area of geometric figures.cpp b/c++/Others/Program to calculate area of geometric figures.cpp new file mode 100644 index 0000000..0c29eca --- /dev/null +++ b/c++/Others/Program to calculate area of geometric figures.cpp @@ -0,0 +1,59 @@ +Program to calculate area of geometric figures. + +#include +#include +void main() +{ + char character; + double area; + cout<<"circle(c) +"; + cout<<"square(s) +"; + cout<<"rectangle(r) +"; + cout<<"triangle(t) +"; + cout<<"Select c,s,r or t:"; +loop: + cin>>character; + if((character=='c')||(character=='C')) + { + double r; + const double pi=3.142; + cout<<"Enter radius:"; + cin>>r; + area=pi*pow(r,2); + } + else if((character=='s')||(character=='S')) + { + double l; + cout<<"Enter length:"; + cin>>l; + area=pow(l,2); + } + else if((character=='r')||(character=='R')) + { + double l,w; + cout<<"Enter length:"; + cin>>l; + cout<<"Enter width:"; + cin>>w; + area=l*w; + } + else if((character=='t')||(character=='T')) + { + double b,h; + cout<<"Enter base:"; + cin>>b; + cout<<"Enter height:"; + cin>>h; + area=h*b/2; + } + else + { + cout<<"Select only c,s,r or t:"; + goto loop; + } + cout<<"Area:"< +#include +int deci,bits=0,deci_x3,bits_x3; +int array[100][20]; +int array1[100][20]; +int array2[100][20]; +void binary(int [100][20],int,int,int); +void gray(int); +void display(int); +int find_bits(int); + +void main() +{ +textcolor(GREEN); +textbackground(BLUE); +clrscr(); +cout<<"Enter the no. upto which gray code and excess 3 code is to be +generated : "; +cin>>deci; +bits=find_bits(deci); +deci_x3=deci+3; +bits_x3=find_bits(deci_x3); +for(int i2=0;i2<=deci;i2++) +{ +for(int j2=0;j2<=bits;j2++) +{ +array[i2][j2]=0; +array1[i2][j2]=0; +} +} +array2[0][bits_x3-1]=1; +array2[0][bits_x3-2]=1; +for( i2=1;i2<=deci_x3;i2++) +{ +for(int j2=0;j2<=bits_x3;j2++) +{ +array2[i2][j2]=0; +} +} +cout<<" DECI NO. BINARY EQ. GRAY CODE EXCESS 3"; +cout< +# include +class time +{ + int hr,min,sec; + public: //don't forget it ! + time() + { + hr=min=sec=0; + cout<<" +Time reset to 00:00:00"; + } + time(int h,int m,int s) + { + hr =h; + min=m; + sec=s; + cout<<" +Time set to specified value."; + } + void display() + { + cout<<" +Time set is # "< 59) + {sec -=60; min++;} + min += t1.min +t2.min; //Note Operator Precedence + if(min>59) + {min-=60; hr++;} + hr += t1.hr + t2.hr; + // Excluding the possibility of hr being greater than + // 24. We do not want digression...! + } +}; +void main() +{ +clrscr(); +time a(12,11,33); +time b(10,34,50); +time c; +a.display(); +b.display(); +c.add(a,b); +c.display(); +getch(); +} diff --git a/c++/Others/Program to deal with denominations of any amount.cpp b/c++/Others/Program to deal with denominations of any amount.cpp new file mode 100644 index 0000000..57185de --- /dev/null +++ b/c++/Others/Program to deal with denominations of any amount.cpp @@ -0,0 +1,106 @@ +Program to deal with denominations of any amount + +//DENOMINATIONS +#include +#include +#include +#include +void main() +{ +clrscr(); +long r,x1,x2,d1,d2,d3,d4,d5,d6,d7,d8,d9,q1,q2,y1,y2,z1,z2,t1,t2, + p1,p2,s1,s2,k1,k2; +int li,lp; +for(li=10;li<71;li++) +{ +gotoxy(li,15); +delay(30); +printf("/"); +} +for(li=70;li>=10;li--) +{ +gotoxy(li,22); +delay(30); +printf("\"); +} +for(lp=16;lp<=21;lp++) +{ +gotoxy(10,lp); +delay(100); +printf("-"); +} +for(lp=21;lp>=16;lp--) +{ +gotoxy(70,lp); +delay(100); +printf("-"); + } +gotoxy(16,17); +textcolor(BLINK+YELLOW); +cprintf(" DENOMINATIONS"); +gotoxy(36,28); +textcolor(LIGHTGREEN); +gotoxy(44,48); +textcolor(WHITE); +cout<<" + please enter the number to be denominated:"; +cin>>r; +x1=r/1000; +x2=r%1000; +d1=x1*1000; +y1=x2/500; +y2=x2%500; +d2=y1*500; +z1=y2/100; +z2=y2%100; +d3=z1*100; +s1=z2/50; +s2=z2%50; +d4=s1*50; +t1=s2/20; +t2=s2%20; +d5=t1*20; +p1=t2/10; +p2=t2%10; +d6=p1*10; +k1=p2/5; +k2=p2%5; +d7=k1*5; +q1=k2/2; +q2=k2%2; +d8=q1*2; +d9=q2*1; +textmode(BW40); +cout<<" + The respective denomination is: + + + + +" + <<"1000 *"< +#include +#include +#include +#include +#include +main() +{ + clrscr(); + int c=0; + char ch,file[30]; + cout<<"Enter the name of the file:"; + gets(file); + fstream f1; + f1.open(file,ios::in); + if(f1.bad()) + { + cout<<"File can not be opened."; + exit(0); + } + if(f1.good()) + { + cout<<"The current contents of the file are: + +"; + while(f1) + { + f1.get(ch); + c++; + cout< +# include +# include +# include + +void main(int argc,char *argv[]) +{ +if(argc < 2) +{ + cerr<<"Illegal Usage +Correct Usage: size "; + exit(1); +} +ifstream in(argv[1],ios::in|ios::binary); +if(!in) +{ + cerr<<"Error opening the input file"; + exit(1); +} +long int size=0; +char ch; +while(!in.eof()) +{ + in>>ch; +// cout<>ch; + switch(ch) + { + case 1: + cout<<" +ADDITION OF TWO VECTORS. +"; + C = A + B; + cout<<" +The Value Of A+B Is: "<>k; + C = A * k; + cout<<" +The Value Of Ak Is (k Is the Scaler): "<>choice; + system("cls"); + }while(1); +} +////////////////////////////////////////////////////////////////////// +///////////////////////////////////////////////////////////////////// + //VECTOR.CPP + +#include"Vector.h" + + +Vector::Vector():x(0),y(0),z(0) +{ + //cout<<"This Is A Default Constructor."; +} + +Vector Vector::operator +(const Vector &v)const //Addition +{ + Vector res; + res.x = x + v.x; + res.y = y + v.y; + res.z = z + v.z; + return res; +} + +Vector Vector::operator -(const Vector &v)const //Subtraction +{ + Vector res; + res.x = x - v.x; + res.y = y - v.y; + res.z = z - v.z; + return res; +} + +Vector Vector::operator *(const int k)const //Multiplication By Scalar +{ + Vector res; + res.x = k * x; + res.y = k * y; + res.z = k * z; + return res; +} + +void Vector::GetData() //Input The Vector +{ + cout<<" +Enter The Value Of x : "; + cin>>x; + cout<<" +Enter The Value Of y : "; + cin>>y; + cout<<" +Enter The Value Of z : "; + cin>>z; +} + +Vector operator *(int k,const Vector &v) +{ + return v * k; +} + +Vector Vector::operator -()const //Negative Of A Vector +{ + Vector res; + res.x = -x; + res.y = -y; + res.z = -z; + return res; +} + +Vector Vector::operator *(const Vector &v)const //Cross (or Vector) +Product +{ + Vector res; + res.x = (y * v.z) - (z * v.y); + res.y = (z * v.x) - (x * v.z); + res.z = (x * v.y) - (y * v.x); + return res; +} + +void Vector::DotProd(Vector v2) //Dot(Or Scalar) Product +{ + int v1v2; + v1v2 = (x * v2.x)+(y * v2.y)+(z * v2.z); + cout<<" +The Value Of A.B Is: "<=0)) + out<=0) && (z<0)) + out<=0) && (z>=0)) + out<=0) && (y<0) && (z<0)) + out<=0) && (y<0) && (z>=0)) + out<=0) && (y>=0) && (z<0)) + out<=0) && (y>=0) && (z>=0)) + out< +#include +#include + +using namespace std; + +class Vector +{ +private: + int x,y,z; +public: + Vector(int,int,int); + Vector(); + void GetData(); + Vector operator+(const Vector &v)const; + Vector operator-(const Vector &v)const; + + Vector operator*(const int k)const; //Multiplication by Scalar + Vector operator*(const Vector &v)const; //Cross Product + Vector operator-()const; //Negative Of A Scaler + void DotProd(Vector); //Dot Product + + ostream & Show(ostream & out)const; + friend Vector operator*(const int k,const Vector &v); + friend ostream & operator<<(ostream & out,const Vector &v) + { + v.Show(out); + return out; + } +}; + + + diff --git a/c++/Others/Program to represent a bank account (implemented a.cpp b/c++/Others/Program to represent a bank account (implemented a.cpp new file mode 100644 index 0000000..fc89232 --- /dev/null +++ b/c++/Others/Program to represent a bank account (implemented a.cpp @@ -0,0 +1,114 @@ +Program to represent a bank account (implemented as a Class) + +# include +# include +# include + +class bank + { + char name[20]; + int acno; + char actype[4]; + float balance; + public: + void init(); + void deposit(); + void withdraw(); + void disp_det(); + }; +//member functions of bank class +void bank :: init() +{ +cout<<" + + New Account +"; +cout<<" + +Enter the Name of the depositor : "; +cin.get(name,19,' +'); +cout<<" +Enter the Account Number : "; +cin>>acno; +cout<<" +Enter the Account Type : (CURR/SAVG/FD/RD/DMAT) "; +cin>>actype; +cout<<" +Enter the Amount to Deposit : "; +cin >>balance; +} +void bank :: deposit() +{ +float more; +cout <<" + Depositing +"; +cout<<" + +Enter the amount to deposit : "; +cin>>more; +balance+=more; +} +void bank :: withdraw() +{ +float amt; +cout<<" + Withdrwal +"; +cout<<" + +Enter the amount to withdraw : "; +cin>>amt; +balance-=amt; +} +void bank :: disp_det() +{ +cout<<" + + Account Details + +"; +cout<<"Name of the depositor : "<>choice; +switch(choice) +{ + case 0 :obj.disp_det(); + cout<<" + + EXITING PROGRAM."; + break; + case 1 : obj.init(); + break; + case 2: obj.deposit(); + break; + case 3 : obj.withdraw(); + break; + case 4: obj.disp_det(); + break; + default: cout<<" + +Illegal Option"< -=:=- Escape"); + + while(1) + { + ch=getch(); + if(ch==0x1b) + break; + + switch(ch) + { + case 'c': + case 'C': + *memory1=*memory1 ^ 64; + break; + case 'n': + case 'N': + *memory1=*memory1 ^ 32; + break; + case 's': + case 'S': + *memory1=*memory1 ^ 16; + break; + } + } + } diff --git a/c++/Others/Project - Employees Management System.cpp b/c++/Others/Project - Employees Management System.cpp new file mode 100644 index 0000000..b795b9e --- /dev/null +++ b/c++/Others/Project - Employees Management System.cpp @@ -0,0 +1,644 @@ +Project - Employees Management System + +#include +#include +#include +#include +#include +#include +#define max 20 +struct employee +{ + char name[20]; + long int code; + char designation[20]; + int exp; + int age; +}; +int num; +employee emp[max],tempemp[max],sortemp[max],sortemp1[max]; +void main() +{ + clrscr(); + void build(); + void list(); + void insert(); + void deletes(); + void edit(); + void search(); + void sort(); + char option; + void menu(); + menu(); + while((option=cin.get())!='q') + { + switch(option) + { + case 'b': + build(); + break; + case 'l': + list(); + break; + case 'i': + insert(); + break; + case 'd': + deletes(); + break; + case 'e': + edit(); + break; + case 's': + search(); + break; + case 'n': + sort(); + break; + } + menu(); + } + } + void menu() + { + clrscr(); + highvideo(); +cout<<" "; +cprintf("*****WelCome To Employee Data Centre***** +"); +normvideo(); +cout<Built The Employee Table +"; +cout<<" "; +cout<<"Press l---->List The Employee Table +"; +cout<<" "; +cout<<"Press i---->Insert New Entry +"; +cout<<" "; +cout<<"Press d---->Delete An Entry +"; +cout<<" "; +cout<<"Press e---->Edit An Entry +"; +cout<<" "; +cout<<"Press s---->Search Arecord +"; +cout<<" "; +cout<<"Press n---->Sort The Table +"; +cout<<" "; +cout<<"Press q---------->QUIT +"; +cout<<" "; +cout<<"Option Please ----->"; +} + +void build() +{ + + clrscr(); + highvideo(); + cprintf("Build The Table +"); + cout< 20"<"; + cin>>num; + cout<<"Enter The Following Items +"; + for(int i=0;i<=num-1;i++) + { + cout<<" Name "; + cin>>emp[i].name; + cout<<"Code "; + cin>>emp[i].code; + cout<<"Designation "; + cin>>emp[i].designation; + cout<<"Years of Experience "; + cin>>emp[i].exp; + cout<<"Age "; + cin>>emp[i].age; + } + cout<<"going to main menu"; + delay(500); +} + +void list() +{ + clrscr(); + highvideo(); + cprintf(" ********List The Table********"); + cout<>emp[i].name; + cout<<"Code "; + cin>>emp[i].code; + cout<<"Designation "; + cin>>emp[i].designation; + cout<<"Years of Experience "; + cin>>emp[i].exp; + cout<<"Age "; + cin>>emp[i].age; + cout<>code; + int i; + for(i=0;i<=num-1;i++) + { + if(emp[i].code==code) + { + check=i; + } + } + for(i=0;i<=num-1;i++) + { + if(i==check) + { + continue; + } + else + { + if(i>check) + { + tempemp[i-1]=emp[i]; + } + else + { + tempemp[i]=emp[i]; + } + } + } + num--; + + for(i=0;i<=num-1;i++) + { + emp[i]=tempemp[i]; + } + } + +void edit() +{ + clrscr(); + int jobcode; + highvideo(); + cprintf(" Edit An Entry "); + cout<>jobcode; + editmenu(); + for(i=0;i<=num-1;i++) + { + if(emp[i].code==jobcode) + { + +while((option=cin.get())!='q') +{ + switch(option) + { + case 'n': + editname(i); + break; + case 'c': + editcode(i); + break; + case 'd': + editdes(i); + break; + case 'e': + editexp(i); + break; + case 'a': + editage(i); + break; + } + editmenu(); + } + } + } + } + void editmenu() + { + clrscr(); + cout<<" What Do You Want To edit +"; + cout<<" n--------->Name +"; + cout<<" c--------->Code +"; + cout<<" d--------->Designation +"; + cout<<" e--------->Experience +"; + cout<<" a--------->Age +"; + cout<<" q----->QUIT +"; + cout<<" Options Please ---->>> "; + } + void editname(int i) + { + cout<<"Enter New Name-----> "; + cin>>emp[i].name; + } + void editcode(int i) + { + cout<<"Enter New Job Code-----> "; + cin>>emp[i].code; + } + void editdes(int i) + { + cout<<"enter new designation-----> "; + cin>>emp[i].designation; + } + void editexp(int i) + { + cout<<"Enter new Years of Experience +"; + cin>>emp[i].exp; + } + void editage(int i) + { + cout<<"Enter new Age +"; + cin>>emp[i].age; + } + +void search() +{ + clrscr(); + highvideo(); + cprintf("Welcome To Search Of Employee Database +"); + normvideo(); + cout<>jobcode; + for(int i=0;i<=num-1;i++) + { + if(emp[i].code==jobcode) + { + + cout<<" Name Code Designation Years(EXP) Age +"; + cout<<" ------------------------------------------------------ +"; + cout<Name +"; + cout<<" c--------->Code +"; + cout<<" d--------->Designation +"; + cout<<" e--------->Experience +"; + cout<<" a--------->Age +"; + cout<<" q----->QUIT +"; + cout<<" Options Please ---->>> "; + } + + + +void sortname() +{ + clrscr(); + int i,j; + struct employee temp[max]; + for(i=0;i<=num-1;i++) + { + sortemp1[i]=emp[i]; + } + for(i=0;i<=num-1;i++) + { + for(j=0;j<=num-1;j++) + { + if(strcmp(sortemp1[i].name,sortemp1[j].name)<=0) + { + temp[i]=sortemp1[i]; + sortemp1[i]=sortemp1[j]; + sortemp1[j]=temp[i]; + } + } + } + + for( i=0;i<=num-1;i++) + { + + cout<<" Name Code Designation Years(EXP) Age +"; + cout<<" ------------------------------------------------------ +"; + for( i=0;i<=num-1;i++) + { + cout< +#include +using namespace std; +struct graphPoint{ + double x, y; + }; +class QuadraticEquation{ + public: + QuadraticEquation(double A = 0.0, double B = 0.0, double C = 0.0) : a(A), b(B), c(C){ + xintercepts[0].x = 0.0; + xintercepts[0].y = 0.0; + xintercepts[1].x = 0.0; + xintercepts[1].y = 0.0; + } + ~QuadraticEquation(){} + + + int getxintercepts(){ + + + double temp = (b * b) - (4 * a * c); + if(temp < 0){ + cout << "##-Square Root Error:\n" + << " ##- SquareRoot ( " << temp << " )\n"; + return 1; + } + + temp = sqrt ( temp ); + + xintercepts[0].x = (b * -1) - temp; + xintercepts[0].x = xintercepts[0].x / (2 * a); + + xintercepts[1].x = (b * -1) + temp; + xintercepts[1].x = xintercepts[1].x / (2 * a); + return 0; + } + + void displayequation(){ + if(a != 0){ + cout << a; + cout << "x^2";} + if(b >= 1 & a != 0) + cout << "+"; + if(b != 0) + cout << b << "x"; + if(c > 0) + cout << "+"; + if(c != 0) + cout << c; + if(a == 0 & b == 0 & c == 0) + cout << 0; + cout << "=0" << endl; + } + + double a, b, c; + graphPoint xintercepts[2]; + }; + + + + + + + +void creditsHelp(); +void wierdGetch(); + + + +int main(int argc, char *argv[]){ +cout << "@-Quadratic Equation Solver\n" + << " @-Karlan Mitchell karlanmitchell-at-comcast-dot-net\n" + << " @-For Credits/Help enter 0 for A\n"; + +double a,b,c; + +cout << "Enter in values for equation\n"; +for(;;){ + cout << "A: "; + cin >> a; + if(a == 0.0){ + creditsHelp(); + continue; + } + break; + } +cout << "B: "; +cin >> b; +cout << "C: "; +cin >> c; + +QuadraticEquation test(a,b,c);//create the class + +test.displayequation();//display the equation with the class function + +switch(test.getxintercepts()){/* I am using a switch here instead of + * an if because I constanly add/remove + * error messages to this function*/ + case 1: + cout << "!!-Equation not possible\n" + << " !!-If you know that it is possible, please contact me about a bug\n"; + exit(1); + break; + } + +cout << "x = " << test.xintercepts[0].x << " | " << test.xintercepts[1].x << endl; +cout << "(" << test.xintercepts[0].x << ", 0) & (" << test.xintercepts[1].x << ", 0)\n"; + + +wierdGetch(); +return 0; +} +void creditsHelp(){ + + cout << "\nThis program was created by me to make my math homework easier\n\n" + + << "What it does:\n" + << "It takes in the 'a', 'b', and 'c' values for a quadratic equation\n" + << "which equals zero.\n" + << "EX: \"x^2 - 3x + 2 = 0\" is equal to \"(x - 2)(x - 1) = 0\"\n" + << " ax^2 + bx + c = 0\n" + << " The 'a','b', and 'c' values for the equation would be 1, -3, and 2\n" + << " The x intercepts for this would be (2, 0) and (1, 0)\n" + << " 2^2 - 3(2) + 2 = 0 and 1^2 - 3(1) + 2 = 0\n\n" + + << "Why would I use this:\n" + << "1) You are in Algebra I/II or Geometry\n" + << "2) Your too lazy to do the quadratic equation on your own which is:\n" + << " x=( -b +/- sqrt(bb - 4ac) ) / (2a)\n"; + wierdGetch(); + exit(0); + } +void wierdGetch(){ + cout << "Press enter to exit..."; + getchar();getchar();//Why do I need, two? The world may never know + } diff --git a/c++/Others/QuadraticProbing.cpp - Implementation for quadratic probing hash table.cpp b/c++/Others/QuadraticProbing.cpp - Implementation for quadratic probing hash table.cpp new file mode 100644 index 0000000..6147da0 --- /dev/null +++ b/c++/Others/QuadraticProbing.cpp - Implementation for quadratic probing hash table.cpp @@ -0,0 +1,197 @@ +QuadraticProbing.cpp - Implementation for quadratic probing hash table + + #include "QuadraticProbing.h" + #include + + + /** + * Internal method to test if a positive number is prime. + * Not an efficient algorithm. + */ + bool isPrime( int n ) + { + if( n == 2 || n == 3 ) + return true; + + if( n == 1 || n % 2 == 0 ) + return false; + + for( int i = 3; i * i <= n; i += 2 ) + if( n % i == 0 ) + return false; + + return true; + } + + /** + * Internal method to return a prime number at least as large as n. + * Assumes n > 0. + */ + int nextPrime( int n ) + { + if( n % 2 == 0 ) + n++; + + for( ; !isPrime( n ); n += 2 ) + ; + + return n; + } + + /** + * Construct the hash table. + */ + template + HashTable::HashTable( const HashedObj & notFound, int size ) + : ITEM_NOT_FOUND( notFound ), array( nextPrime( size ) ) + { + makeEmpty( ); + } + + /** + * Insert item x into the hash table. If the item is + * already present, then do nothing. + */ + template + void HashTable::insert( const HashedObj & x ) + { + // Insert x as active + int currentPos = findPos( x ); + if( isActive( currentPos ) ) + return; + array[ currentPos ] = HashEntry( x, ACTIVE ); + + // Rehash; see Section 5.5 + if( ++currentSize > array.size( ) / 2 ) + rehash( ); + } + + /** + * Expand the hash table. + */ + template + void HashTable::rehash( ) + { + vector oldArray = array; + + // Create new double-sized, empty table + array.resize( nextPrime( 2 * oldArray.size( ) ) ); + for( int j = 0; j < array.size( ); j++ ) + array[ j ].info = EMPTY; + + // Copy table over + currentSize = 0; + for( int i = 0; i < oldArray.size( ); i++ ) + if( oldArray[ i ].info == ACTIVE ) + insert( oldArray[ i ].element ); + } + + /** + * Method that performs quadratic probing resolution. + * Return the position where the search for x terminates. + */ + template + int HashTable::findPos( const HashedObj & x ) const + { +/* 1*/ int collisionNum = 0; +/* 2*/ int currentPos = hash( x, array.size( ) ); + +/* 3*/ while( array[ currentPos ].info != EMPTY && + array[ currentPos ].element != x ) + { +/* 4*/ currentPos += 2 * ++collisionNum - 1; // Compute ith probe +/* 5*/ if( currentPos >= array.size( ) ) +/* 6*/ currentPos -= array.size( ); + } + +/* 7*/ return currentPos; + } + + + /** + * Remove item x from the hash table. + */ + template + void HashTable::remove( const HashedObj & x ) + { + int currentPos = findPos( x ); + if( isActive( currentPos ) ) + array[ currentPos ].info = DELETED; + } + + /** + * Find item x in the hash table. + * Return the matching item or ITEM_NOT_FOUND if not found + */ + template + const HashedObj & HashTable::find( const HashedObj & x ) const + { + int currentPos = findPos( x ); + if( isActive( currentPos ) ) + return array[ currentPos ].element; + else + return ITEM_NOT_FOUND; + } + + /** + * Make the hash table logically empty. + */ + template + void HashTable::makeEmpty( ) + { + currentSize = 0; + for( int i = 0; i < array.size( ); i++ ) + array[ i ].info = EMPTY; + } + + /** + * Deep copy. + */ + template + const HashTable & HashTable:: + operator=( const HashTable & rhs ) + { + if( this != &rhs ) + { + array = rhs.array; + currentSize = rhs.currentSize; + } + return *this; + } + + + /** + * Return true if currentPos exists and is active. + */ + template + bool HashTable::isActive( int currentPos ) const + { + return array[ currentPos ].info == ACTIVE; + } + + /** + * A hash routine for string objects. + */ + int hash( const string & key, int tableSize ) + { + int hashVal = 0; + + for( int i = 0; i < key.length( ); i++ ) + hashVal = 37 * hashVal + key[ i ]; + + hashVal %= tableSize; + if( hashVal < 0 ) + hashVal += tableSize; + + return hashVal; + } + + + /** + * A hash routine for ints. + */ + int hash( int key, int tableSize ) + { + if( key < 0 ) key = -key; + return key % tableSize; + } diff --git a/c++/Others/QuadraticProbing.h - Header file for quadratic pro.cpp b/c++/Others/QuadraticProbing.h - Header file for quadratic pro.cpp new file mode 100644 index 0000000..9b78ec0 --- /dev/null +++ b/c++/Others/QuadraticProbing.h - Header file for quadratic pro.cpp @@ -0,0 +1,61 @@ +QuadraticProbing.h - Header file for quadratic probing hash table + + #ifndef QUADRATIC_PROBING_H_ + #define QUADRATIC_PROBING_H_ + + #include "vector.h" + #include "mystring.h" + + // QuadraticProbing Hash table class + // + // CONSTRUCTION: an initialization for ITEM_NOT_FOUND + // and an approximate initial size or default of 101 + // + // ******************PUBLIC OPERATIONS********************* + // void insert( x ) --> Insert x + // void remove( x ) --> Remove x + // Hashable find( x ) --> Return item that matches x + // void makeEmpty( ) --> Remove all items + + template + class HashTable + { + public: + explicit HashTable( const HashedObj & notFound, int size = 101 ); + HashTable( const HashTable & rhs ) + : ITEM_NOT_FOUND( rhs.ITEM_NOT_FOUND ), + array( rhs.array ), currentSize( rhs.currentSize ) { } + + const HashedObj & find( const HashedObj & x ) const; + + void makeEmpty( ); + void insert( const HashedObj & x ); + void remove( const HashedObj & x ); + + const HashTable & operator=( const HashTable & rhs ); + + enum EntryType { ACTIVE, EMPTY, DELETED }; + private: + struct HashEntry + { + HashedObj element; + EntryType info; + + HashEntry( const HashedObj & e = HashedObj( ), EntryType i = EMPTY ) + : element( e ), info( i ) { } + }; + + vector array; + int currentSize; + const HashedObj ITEM_NOT_FOUND; + + bool isActive( int currentPos ) const; + int findPos( const HashedObj & x ) const; + void rehash( ); + }; + + int hash( const string & key, int tableSize ); + int hash( int key, int tableSize ); + + #include "QuadraticProbing.cpp" + #endif diff --git a/c++/Others/Queue Data Structure Class Example which uses Poly.cpp b/c++/Others/Queue Data Structure Class Example which uses Poly.cpp new file mode 100644 index 0000000..1be4608 --- /dev/null +++ b/c++/Others/Queue Data Structure Class Example which uses Poly.cpp @@ -0,0 +1,251 @@ +Queue Data Structure Class Example which uses Polymorphism + +#include +#include +#include +#include +#include + +#define MAX 5 // MAXIMUM CONTENTS IN QUEUE + +class task +{ + public: + virtual void dotask(){} + task(){} + int exists; + +}; + +class notep: public task +{ + + public: + notep(){exists=1;} + + void dotask() + { + system("notepad"); + } +}; + +class regt:public task +{ + public: + regt(){exists=1;} + + void dotask() + { + system("regedit"); + } +}; + +class winex:public task +{ + public: + winex(){exists=1;} + + void dotask() + { + system("explorer"); + } +}; + +class Bep:public task +{ + public: + Bep(){exists=1;} + + void dotask() + { + cout<<"a"; + } +}; + +class MsBox:public task +{ + private: + char* text; + char* caption; + int style; + + public: + MsBox(char* ext,char* cap,int no) + { + text=ext; + caption=cap; + exists=1; + style=no; + } + + void dotask() + { + MessageBox(0,text,caption,style); + } +}; + +class queue +{ + private: + task *t[MAX]; + int al; + int dl; + + public: + int opt,opt1,a; + char te[255],capt[40]; + + queue() + { + dl=-1; + al=-1; + } + +void del() +{ + task* tmp; + if(dl==-1) + { + cout<<"Queue is Empty"; + sleep(2); + } + else + { + t[dl]->exists=0; + for(int j=0;j<=al;j++) + { + if((j+1)<=al) + { + tmp=t[j+1]; + t[j]=tmp; + } + else + { + t[al]->exists=0; + al--; + + if(al==-1) + dl=-1; + else + dl=0; + } + } + } +} + +void menu() +{ + clrscr(); + cout<<"1) Add Task +2)Execute Tasks +3)Exit Program +"; +// int opt; + cin>>opt; + switch(opt) + { + case 1: + clrscr(); + cout<<"1) Open Notepad +"; + cout<<"2) Open Explorer +" + <<"3) Open Registry +" + <<"4) Sound a Beep +" + <<"5) MessageBox API +" + <<"6) Back +"; + + + cin>>opt1; + if(opt1!=6) + add(opt1); + break; + + case 2: + if(al!=-1 && dl!=-1) + { + for(int k=0;k<=al;k++) + { + if(t[k]->exists==1) + t[k]->dotask(); + t[k]->exists=0; + } + al=dl=-1; + } + else + { + cout<<"Queue is Empty"; + sleep(3); + } + break; + + case 3: + exit(0); + break; + } +} + +void add(int item) +{ + if(dl==-1 && al==-1) + { + dl++; + al++; + } + else + { + al++; + if(al>a; + t[al]=new MsBox("Task Performed.","Queue Implementation",a); + break; + + default: + cout<<"Programming Error"; // No Possibility of this executing + }; + } + +}; + +void main() +{ + queue a; + while(1) + { + a.menu(); + } +} diff --git a/c++/Others/QueueAr.cpp - Implementation for queue - array version.cpp b/c++/Others/QueueAr.cpp - Implementation for queue - array version.cpp new file mode 100644 index 0000000..371c895 --- /dev/null +++ b/c++/Others/QueueAr.cpp - Implementation for queue - array version.cpp @@ -0,0 +1,96 @@ +QueueAr.cpp - Implementation for queue - array version + + #include "QueueAr.h" + + /** + * Construct the queue. + */ + template + Queue::Queue( int capacity ) : theArray( capacity ) + { + makeEmpty( ); + } + + /** + * Test if the queue is logically empty. + * Return true if empty, false otherwise. + */ + template + bool Queue::isEmpty( ) const + { + return currentSize == 0; + } + + /** + * Test if the queue is logically full. + * Return true if full, false otherwise. + */ + template + bool Queue::isFull( ) const + { + return currentSize == theArray.size( ); + } + + /** + * Make the queue logically empty. + */ + template + void Queue::makeEmpty( ) + { + currentSize = 0; + front = 0; + back = -1; + } + + /** + * Get the least recently inserted item in the queue. + * Return the least recently inserted item in the queue + * or throw Underflow if empty. + */ + template + const Object & Queue::getFront( ) const + { + if( isEmpty( ) ) + throw Underflow( ); + return theArray[ front ]; + } + + /** + * Return and remove the least recently inserted item from the queue. + * Throw Underflow if empty. + */ + template + Object Queue::dequeue( ) + { + if( isEmpty( ) ) + throw Underflow( ); + + currentSize--; + Object frontItem = theArray[ front ]; + increment( front ); + return frontItem; + } + + /** + * Insert x into the queue. + * Throw Overflow if queue is full + */ + template + void Queue::enqueue( const Object & x ) + { + if( isFull( ) ) + throw Overflow( ); + increment( back ); + theArray[ back ] = x; + currentSize++; + } + + /** + * Internal method to increment x with wraparound. + */ + template + void Queue::increment( int & x ) + { + if( ++x == theArray.size( ) ) + x = 0; + } diff --git a/c++/Others/QueueAr.h - Header file for queue - array version.cpp b/c++/Others/QueueAr.h - Header file for queue - array version.cpp new file mode 100644 index 0000000..adb7a99 --- /dev/null +++ b/c++/Others/QueueAr.h - Header file for queue - array version.cpp @@ -0,0 +1,47 @@ +QueueAr.h - Header file for queue - array version + + #ifndef QUEUEAR_H + #define QUEUEAR_H + + #include "vector.h" + #include "dsexceptions.h" + + // Queue class -- array implementation + // + // CONSTRUCTION: with or without a capacity; default is 10 + // + // ******************PUBLIC OPERATIONS********************* + // void enqueue( x ) --> Insert x + // void dequeue( ) --> Return and remove least recently inserted item + // Object getFront( ) --> Return least recently inserted item + // bool isEmpty( ) --> Return true if empty; else false + // bool isFull( ) --> Return true if full; else false + // void makeEmpty( ) --> Remove all items + // ******************ERRORS******************************** + // Overflow and Underflow thrown as needed + + template + class Queue + { + public: + explicit Queue( int capacity = 10 ); + + bool isEmpty( ) const; + bool isFull( ) const; + const Object & getFront( ) const; + + void makeEmpty( ); + Object dequeue( ); + void enqueue( const Object & x ); + + private: + vector theArray; + int currentSize; + int front; + int back; + + void increment( int & x ); + }; + + #include "QueueAr.cpp" + #endif diff --git a/c++/Others/Railway seat reservation question which comes in s.cpp b/c++/Others/Railway seat reservation question which comes in s.cpp new file mode 100644 index 0000000..9b60c2c --- /dev/null +++ b/c++/Others/Railway seat reservation question which comes in s.cpp @@ -0,0 +1,115 @@ +Railway seat reservation question which comes in sapient + +#include +#include +#include + +struct rail +{ + + int seatNo; + int isEmpty; + +}seat[67]; + +void reserve(int n); +int arrRowState[15]; + +void main() +{ + for(int i = 0 ; i <67 ; i++) + { + seat[i].seatNo=(i+1); + seat[i].isEmpty=1; + } + for(i=0 ; i<13 ; i++) + arrRowState[i]=5; + + arrRowState[13]=2; + arrRowState[14]=67; + + char res='y'; + do + { + int n; + clrscr(); + cout<<"Enter d no of seats u want to reserve : "; + cin>>n; + reserve(n); + cout<<" + + +Do u want to reserve more seats?"; + res=getchar(); + }while(res!='n'); +} + +void reserve(int n) +{ + if(n>arrRowState[14]) + { + cout<<"Too large group to accomodate"; + getch(); + return; + } + + int flag=0; + int seatbook; + for(int i = 0 ; flag==0&&i<=13 ; i++) + { + if(arrRowState[i] >= n) + { + flag=1; + // cout<<"Following Seats Alloted"; + seatbook=(((i)*5)+(6-arrRowState[i])); + for(int j = 0 ; j < n ; j++) + { + cout<<" +"< max) + { + max=arrRowState[j]; + rowNo=j; + } + + } + if(n>max) + { + n=n-max; + seatbook=(((rowNo)*5)+(6-arrRowState[rowNo])); + arrRowState[rowNo]=arrRowState[rowNo]-max; + for( int j = 0 ; j= 0 ) + state = tmpState; + else + state = tmpState + M; + + return state; + } + + /** + * Return a pseudorandom int, and change the + * internal state. DOES NOT WORK. + */ + int Random::randomIntWRONG( ) + { + return state = ( A * state ) % M; + } + + /** + * Return a pseudorandom double in the open range 0..1 + * and change the internal state. + */ + double Random::random0_1( ) + { + return (double) randomInt( ) / M; + } + + /** + * Return an int in the closed range [low,high], and + * change the internal state. + */ + int Random::randomInt( int low, int high ) + { + double partitionSize = (double) M / ( high - low + 1 ); + + return (int) ( randomInt( ) / partitionSize ) + low; + } diff --git a/c++/Others/Random.h - Header file for random number class.cpp b/c++/Others/Random.h - Header file for random number class.cpp new file mode 100644 index 0000000..82e82f9 --- /dev/null +++ b/c++/Others/Random.h - Header file for random number class.cpp @@ -0,0 +1,33 @@ +Random.h - Header file for random number class + + #ifndef RANDOM_H_ + #define RANDOM_H_ + + // Random class + // This code assumes 32-bit ints, + // which are standard on modern compilers. + // + // CONSTRUCTION: with (a) no initializer or (b) an integer + // that specifies the initial state of the generator + // + // ******************PUBLIC OPERATIONS********************* + // Return a random number according to some distribution: + // int randomInt( ) --> Uniform, 1 to 2^31-1 + // int random0_1( ) --> Uniform, 0 to 1 + // int randomInt( int low, int high ) --> Uniform low..high + + class Random + { + public: + explicit Random( int initialValue = 1 ); + + int randomInt( ); + int randomIntWRONG( ); + double random0_1( ); + int randomInt( int low, int high ); + + private: + int state; + }; + + #endif diff --git a/c++/Others/Rational Mini Project. About overloading of operators.cpp b/c++/Others/Rational Mini Project. About overloading of operators.cpp new file mode 100644 index 0000000..5048425 --- /dev/null +++ b/c++/Others/Rational Mini Project. About overloading of operators.cpp @@ -0,0 +1,251 @@ +Rational Mini Project. About overloading of operators + +Code : + +//main subject:operator-overloading + +#include + +class rational +{ +private: + int a; + int b; +public: + rational(int=1,int=1); + void set_ab(int,int); + void print_fraction(); + void print_floating(); + rational operator+(rational object); + rational operator-(rational object); + rational operator*(rational object); + rational operator/(rational object); + rational operator=(rational object); + friend ostream &operator<<(ostream &,rational &); + friend istream &operator>>(istream &,rational &); + int operator==(rational object); + int operator!=(rational object); + int operator>(rational object); + int operator<(rational object); +}; + +/*--------------------------------------------------------*/ + +rational::rational(int m,int n) +{ + set_ab(m,n); +} + +/*--------------------------------------------------------*/ + +void rational::set_ab(int x,int y) +{ + int temporary,m,n; + m=x; + n=y; + if(n>m) + { + temporary=n; + n=m; + m=temporary; + } + while(m!=0 && n!=0) + { + if(m%n==0) + break; + temporary=m%n; + m=n; + n=temporary; + continue; + } + a=x/n; + b=y/n; + +} + +/*--------------------------------------------------------*/ + +void rational::print_fraction() +{ + cout<>(istream &input,rational &object) +{ + cout<<"Enter a,b:"<>object.a; + input>>object.b; + return input; +} + +/*--------------------------------------------------------*/ + +int rational::operator==(rational object) +{ + if(a==object.a && b==object.b) + return(1); + else + return(0); +} + +/*--------------------------------------------------------*/ + +int rational::operator!=(rational object) +{ + if(a!=object.a || b!=object.b) + return(1); + else + return(0); +} + +/*--------------------------------------------------------*/ + +int rational::operator>(rational object) +{ + return((a/b)>(object.a/object.b) ? 1:0); +} + +/*--------------------------------------------------------*/ + +int rational::operator<(rational object) +{ + return((a/b)<(object.a/object.b) ? 1:0); +} + +/*--------------------------------------------------------*/ + +int main() +{ + rational x(3,4),y(3,4),z1,z2,z3,z4,z5; + if(x==y) + {cout<<"These 2 fractions are equl."<y) + {cout<<"x is bigger than y."<l) + {cout<<"k is bigger than l."< +#include + +int main() +{ +char mychar[100]; +int i = 0; +//while the character is not a new line +while((mychar[i] = cin.get()) != '\n') +i++; + +mychar[i] = NULL; +//display characters +cout< +#include +#include +void main(){ + clrscr(); + //Floppy Drive Properties + struct fatinfo diskinfo; + getfat(1, &diskinfo); + cout<<"Floppy Disk Properties.. +--------------------------"; + cout<<" +Sectors per cluster:"< +#include +main() + { + int c,hr=1; + union REGS in; + clrscr(); + + while(!kbhit()) + { + in.h.ah=0x02; + int86(0x1a,&in,&in); + clrscr(); + hr=1; + printf("\n\n\n\t"); + fun(in.h.ch , hr); + printf(":"); + hr=0; + fun(in.h.cl,hr); + printf(":"); + fun(in.h.dh,hr); + delay(250); + } + + } + + +fun(int a,int j) + { + int i,k; + i=a; + a&=0x0f; + i&= 0xf0; + i>>=4; + /* if(j==0)*/ + printf("%d%d",i,a); +/* else + { + i=i<<4; + i=i|a; + i-=0x0c; + printf("%d",i-6); + }*/ + } diff --git a/c++/Others/RedBlackTree.h - Header file for top-down red black tree.cpp b/c++/Others/RedBlackTree.h - Header file for top-down red black tree.cpp new file mode 100644 index 0000000..96bd07d --- /dev/null +++ b/c++/Others/RedBlackTree.h - Header file for top-down red black tree.cpp @@ -0,0 +1,95 @@ +RedBlackTree.h - Header file for top-down red black tree + + #ifndef RED_BLACK_TREE_H_ + #define RED_BLACK_TREE_H_ + + #include "dsexceptions.h" + #include // For NULL + + // Red-black tree class + // + // CONSTRUCTION: with negative infinity object also + // used to signal failed finds + // + // ******************PUBLIC OPERATIONS********************* + // void insert( x ) --> Insert x + // void remove( x ) --> Remove x (unimplemented) + // Comparable find( x ) --> Return item that matches x + // Comparable findMin( ) --> Return smallest item + // Comparable findMax( ) --> Return largest item + // boolean isEmpty( ) --> Return true if empty; else false + // void makeEmpty( ) --> Remove all items + // void printTree( ) --> Print tree in sorted order + + + + // Node and forward declaration because g++ does + // not understand nested classes. + template + class RedBlackTree; + + template + class RedBlackNode + { + Comparable element; + RedBlackNode *left; + RedBlackNode *right; + int color; + + // c = 1 should be c = RedBlackTree::BLACK + // But Visual 5.0 does not comprehend it. + RedBlackNode( const Comparable & theElement = Comparable( ), + RedBlackNode *lt = NULL, RedBlackNode *rt = NULL, + int c = 1 ) + : element( theElement ), left( lt ), right( rt ), color( c ) { } + friend class RedBlackTree; + }; + + template + class RedBlackTree + { + public: + explicit RedBlackTree( const Comparable & negInf ); + RedBlackTree( const RedBlackTree & rhs ); + ~RedBlackTree( ); + + const Comparable & findMin( ) const; + const Comparable & findMax( ) const; + const Comparable & find( const Comparable & x ) const; + bool isEmpty( ) const; + void printTree( ) const; + + void makeEmpty( ); + void insert( const Comparable & x ); + void remove( const Comparable & x ); + + enum { RED, BLACK }; + + const RedBlackTree & operator=( const RedBlackTree & rhs ); + + private: + RedBlackNode *header; // The tree header (contains negInf) + const Comparable ITEM_NOT_FOUND; + RedBlackNode *nullNode; + + // Used in insert routine and its helpers (logically static) + RedBlackNode *current; + RedBlackNode *parent; + RedBlackNode *grand; + RedBlackNode *great; + + // Usual recursive stuff + void reclaimMemory( RedBlackNode *t ) const; + void printTree( RedBlackNode *t ) const; + RedBlackNode * clone( RedBlackNode * t ) const; + + // Red-black tree manipulations + void handleReorient( const Comparable & item ); + RedBlackNode * rotate( const Comparable & item, + RedBlackNode *parent ) const; + void rotateWithLeftChild( RedBlackNode * & k2 ) const; + void rotateWithRightChild( RedBlackNode * & k1 ) const; + }; + + #include "RedBlackTree.cpp" + #endif diff --git a/c++/Others/Regular exp to nfa.cpp b/c++/Others/Regular exp to nfa.cpp new file mode 100644 index 0000000..65a5f45 --- /dev/null +++ b/c++/Others/Regular exp to nfa.cpp @@ -0,0 +1,76 @@ +Regular exp to nfa + +# include +# include +# include +# include +// regular expression to nfa by g.ram kumar +// works for everything but produces excessive epsilon transitions +int ret[100]; +static int pos=0; +static int sc=0; +void nfa(int st,int p,char *s) +{ int i,sp,fs[15],fsc=0; + sp=st;pos=p;sc=st; + while(*s!=NULL) + {if(isalpha(*s)) + {ret[pos++]=sp; + ret[pos++]=*s; + ret[pos++]=++sc;} + if(*s=='.') + {sp=sc; + ret[pos++]=sc; + ret[pos++]=238; + ret[pos++]=++sc; + sp=sc;} + if(*s=='|') + {sp=st; + fs[fsc++]=sc;} + if(*s=='*') + {ret[pos++]=sc; + ret[pos++]=238; + ret[pos++]=sp; + ret[pos++]=sp; + ret[pos++]=238; + ret[pos++]=sc; + } + if (*s=='(') + {char ps[50]; + int i=0,flag=1; + s++; + while(flag!=0) + {ps[i++]=*s; + if (*s=='(') + flag++; + if (*s==')') + flag--; + s++;} + ps[--i]='\0'; + nfa(sc,pos,ps); + s--; + } + s++; + } + sc++; + for(i=0;i %d\n",ret[i],ret[i+1],ret[i+2]); + printf("\n"); + getch(); +} diff --git a/c++/Others/SeparateChaining.cpp - Implementation for separate chaining.cpp b/c++/Others/SeparateChaining.cpp - Implementation for separate chaining.cpp new file mode 100644 index 0000000..4113a03 --- /dev/null +++ b/c++/Others/SeparateChaining.cpp - Implementation for separate chaining.cpp @@ -0,0 +1,136 @@ +SeparateChaining.cpp - Implementation for separate chaining + + #include "SeparateChaining.h" + #include + + + /** + * Internal method to test if a positive number is prime. + * Not an efficient algorithm. + */ + bool isPrime( int n ) + { + if( n == 2 || n == 3 ) + return true; + + if( n == 1 || n % 2 == 0 ) + return false; + + for( int i = 3; i * i <= n; i += 2 ) + if( n % i == 0 ) + return false; + + return true; + } + + /** + * Internal method to return a prime number at least as large as n. + * Assumes n > 0. + */ + int nextPrime( int n ) + { + if( n % 2 == 0 ) + n++; + + for( ; !isPrime( n ); n += 2 ) + ; + + return n; + } + + /** + * Construct the hash table. + */ + template + HashTable::HashTable( const HashedObj & notFound, int size ) + : ITEM_NOT_FOUND( notFound ), theLists( nextPrime( size ) ) + { + } + + /** + * Insert item x into the hash table. If the item is + * already present, then do nothing. + */ + template + void HashTable::insert( const HashedObj & x ) + { + List & whichList = theLists[ hash( x, theLists.size( ) ) ]; + ListItr itr = whichList.find( x ); + + if( itr.isPastEnd( ) ) + whichList.insert( x, whichList.zeroth( ) ); + } + + /** + * Remove item x from the hash table. + */ + template + void HashTable::remove( const HashedObj & x ) + { + theLists[ hash( x, theLists.size( ) ) ].remove( x ); + } + + /** + * Find item x in the hash table. + * Return the matching item or ITEM_NOT_FOUND if not found + */ + template + const HashedObj & HashTable::find( const HashedObj & x ) const + { + ListItr itr; + itr = theLists[ hash( x, theLists.size( ) ) ].find( x ); + if( itr.isPastEnd( ) ) + return ITEM_NOT_FOUND; + else + return itr.retrieve( ); + } + + /** + * Make the hash table logically empty. + */ + template + void HashTable::makeEmpty( ) + { + for( int i = 0; i < theLists.size( ); i++ ) + theLists[ i ].makeEmpty( ); + } + + /** + * Deep copy. + */ + template + const HashTable & + HashTable::operator=( const HashTable & rhs ) + { + if( this != &rhs ) + theLists = rhs.theLists; + return *this; + } + + + /** + * A hash routine for string objects. + */ + int hash( const string & key, int tableSize ) + { + int hashVal = 0; + + for( int i = 0; i < key.length( ); i++ ) + hashVal = 37 * hashVal + key[ i ]; + + hashVal %= tableSize; + if( hashVal < 0 ) + hashVal += tableSize; + + return hashVal; + } + + + /** + * A hash routine for ints. + */ + int hash( int key, int tableSize ) + { + if( key < 0 ) key = -key; + return key % tableSize; + } diff --git a/c++/Others/SeparateChaining.h - Header file for separate chaining.cpp b/c++/Others/SeparateChaining.h - Header file for separate chaining.cpp new file mode 100644 index 0000000..7f9efea --- /dev/null +++ b/c++/Others/SeparateChaining.h - Header file for separate chaining.cpp @@ -0,0 +1,47 @@ +SeparateChaining.h - Header file for separate chaining + + #ifndef SEPARATE_CHAINING_H_ + #define SEPARATE_CHAINING_H_ + + #include "vector.h" + #include "mystring.h" + #include "LinkedList.h" + + // SeparateChaining Hash table class + // + // CONSTRUCTION: an initialization for ITEM_NOT_FOUND + // and an approximate initial size or default of 101 + // + // ******************PUBLIC OPERATIONS********************* + // void insert( x ) --> Insert x + // void remove( x ) --> Remove x + // Hashable find( x ) --> Return item that matches x + // void makeEmpty( ) --> Remove all items + // int hash( string str, int tableSize ) + // --> Global method to hash strings + + template + class HashTable + { + public: + explicit HashTable( const HashedObj & notFound, int size = 101 ); + HashTable( const HashTable & rhs ) + : ITEM_NOT_FOUND( rhs.ITEM_NOT_FOUND ), theLists( rhs.theLists ) { } + + const HashedObj & find( const HashedObj & x ) const; + + void makeEmpty( ); + void insert( const HashedObj & x ); + void remove( const HashedObj & x ); + + const HashTable & operator=( const HashTable & rhs ); + private: + vector > theLists; // The array of Lists + const HashedObj ITEM_NOT_FOUND; + }; + + int hash( const string & key, int tableSize ); + int hash( int key, int tableSize ); + + #include "SeparateChaining.cpp" + #endif diff --git a/c++/Others/Shows the number of wrods and characters entered.cpp b/c++/Others/Shows the number of wrods and characters entered.cpp new file mode 100644 index 0000000..e01f055 --- /dev/null +++ b/c++/Others/Shows the number of wrods and characters entered.cpp @@ -0,0 +1,27 @@ +Shows the number of wrods and characters entered + +#include +#include + +main() +{ + int chcount=0; + int wdcount=1; + char ch; + + clrscr(); + cout<<"\n \n This program will count the number of characters and words that u have entered"; + cout<<"\n Type whaterver u like to followed by an enter ....\n\n"; + + while ((ch=getche())!='\r') + { + if(ch==' ') + wdcount++; + else + chcount++; + } + + cout<<"\n\n The number of words are : "<=200;i=i-50) + { + sound(i); + delay(100); + } + nosound(); + break; + } + + //Numeric// + if((ch>='0')&&(ch<='9')) + { + if(i=200;i=i-50) + { + sound(i); + delay(100); + } + nosound(); + break; + } + + //Numeric// + if((ch>='0')&&(ch<='9')) + { + if(i +#include +#include +#include +#include + + +using namespace std; +int main(int argc, char* argv[]) +{ + + float input1; + float input2; + double output; + char what; + char num1[34]; + char num2[34]; + gotoxy(15,1); + cout<<"welcome to the calculater program"<>num1; + input1=atof(num1); + clrscr(); + cout<<"enter the second number:"<>num2; + input2=atof(num2); + clrscr(); + cout<<"enter +opearation ++.add +-.minus +*.multiply +/.divide +s.square +root +e.exitt"<>what; + switch(what) + { + case'+': + output=input1+input2; + clrscr(); + cout< +#include + +main() +{ + int x,y,ans,i; + int choice; + float div; + char loop; + ans=0; + + clrscr(); + + do + { + printf("\n Do you wish to continue (Y/N) : "); + scanf("%s",&loop); + + if (loop=='y' || loop=='Y') + { + clrscr(); + printf("\n Enter any two numbers "); + printf("\n --------------------- "); + + printf("\n\n Enter the first number : "); + scanf("%d",&x); + + printf("\n Enter the second number : "); + scanf("%d",&y); + + clrscr(); + printf("\n Select the operation to be carried out "); + printf("\n -------------------------------------- "); + + printf("\n 1. Addition "); + printf("\n 2. Substraction "); + printf("\n 3. Multiplication "); + printf("\n 4. Division "); + + printf("\n Enter your choice : "); + scanf("%d",&choice); + + switch(choice) + { + case 1 : + { + ans = x+y; + printf("\n Answer = %d",ans); + break; + } + case 2 : + { + ans = x-y; + printf("\n Answer = %d", ans); + break; + } + case 3 : + { + ans = x*y; + printf("\n Answer = %d", ans); + break; + } + case 4: + { + div = x/y; + printf("\n Answer = %.2f", div); + break; + } + default: + printf("\n\n Illegal operation......"); + break; + } + } + else + printf("\n Bye....... Bye..........."); + getch(); + }while(loop=='y' || loop=='Y'); +} diff --git a/c++/Others/Solar System - Demo of Graphics in C.cpp b/c++/Others/Solar System - Demo of Graphics in C.cpp new file mode 100644 index 0000000..4552de4 --- /dev/null +++ b/c++/Others/Solar System - Demo of Graphics in C.cpp @@ -0,0 +1,419 @@ +Solar System - Demo of Graphics in C. + +#include"stdio.h" +#include"graphics.h" +#include"conio.h" +#include"dos.h" +#include"math.h" +#include"stdlib.h" + + +void main() +{ + int gd=DETECT,gm; + float +i=0,j=100,me=75,ve=23,ma=105,ju=175,sa=10,ur=300,ne=200,pl=175,s=0; + int x,y,k,tri[8],si,sx=random(300),sy=random(400),X,Y,ss; + unsigned int +earth,moon,mercury,venus,mars,jupiter,saturn,uranus,neptune,pluto,sunsize, +ship,ship2; + void +*ear,*moo,*mer,*ven,*mar,*jup,*sat,*ura,*nep,*plu,*sun,*ships,*ships2; + x=300; + y=210; + + initgraph(&gd,&gm,"c:\tc\bgi"); + + setfillstyle(1,10); + setcolor(2); + fillellipse(50,50,13,13); + earth=imagesize(35,35,65,65); + ear=malloc(earth); + getimage(35,35,65,65,ear); + cleardevice(); + + setfillstyle(1,15); + setcolor(15); + fillellipse(25,25,5,5); + moon=imagesize(15,15,35,35); + moo=malloc(moon); + getimage(15,15,35,35,moo); + cleardevice(); + + setfillstyle(1,4); + setcolor(4); + fillellipse(15,15,4,4); + mercury=imagesize(10,10,20,20); + mer=malloc(mercury); + getimage(10,10,20,20,mer); + cleardevice(); + + + setfillstyle(1,11); + setcolor(11); + fillellipse(15,15,7,7); + venus=imagesize(7,7,23,23); + ven=malloc(venus); + getimage(7,7,23,23,ven); + cleardevice(); + + + setfillstyle(1,6); + setcolor(6); + fillellipse(20,20,14,14); + mars=imagesize(5,5,35,35); + mar=malloc(mars); + getimage(5,5,35,35,mar); + cleardevice(); + + + setfillstyle(1,7); + setcolor(7); + fillellipse(25,25,18,18); + jupiter=imagesize(5,5,45,45); + jup=malloc(jupiter); + getimage(5,5,45,45,jup); + cleardevice(); + + + setfillstyle(1,8); + setcolor(8); + fillellipse(50,50,12,12); + uranus=imagesize(35,35,65,65); + ura=malloc(uranus); + getimage(35,35,65,65,ura); + cleardevice(); + + setfillstyle(1,12); + setcolor(12); + fillellipse(50,50,11,11); + neptune=imagesize(35,35,65,65); + nep=malloc(neptune); + getimage(35,35,65,65,nep); + cleardevice(); + + setfillstyle(1,1); + setcolor(1); + fillellipse(50,50,8,8); + pluto=imagesize(35,35,65,65); + plu=malloc(pluto); + getimage(35,35,65,65,plu); + cleardevice(); + + + setcolor(14); + setfillstyle(1,14); + fillellipse(40,40,25,25); + for(si=0; si<25; si++) + { + tri[0]=(40+25*cos(s)); + tri[1]=(40+25*sin(s)); + s=s+0.3; + tri[2]=(40+25*cos(s)); + tri[3]=(40+25*sin(s)); + + tri[4]=(40+40*cos((2*s-0.3)/2)); + tri[5]=(40+40*sin((2*s-0.3)/2)); + + tri[6]=tri[0]; + tri[7]=tri[1]; + + fillpoly(4,tri); + + } + + sunsize=imagesize(0,0,80,80); + sun=malloc(sunsize); + getimage(0,0,80,80,sun); + cleardevice(); + + setfillstyle(1,15); + setcolor(15); + fillellipse(40,40,33,16); + fillellipse(40,25,15,10); + setfillstyle(1,2); + fillellipse(14,37,5,5); + fillellipse(35,40,5,5); + fillellipse(55,39,5,5); + setfillstyle(1,4); + fillellipse(25,39,5,5); + fillellipse(46,40,5,5); + fillellipse(65,37,5,5); + setfillstyle(1,0); + fillellipse(30,20,2,2); + fillellipse(35,20,2,2); + fillellipse(40,20,2,2); + fillellipse(45,20,2,2); + fillellipse(50,20,2,2); + ship=imagesize(0,0,80,80); + ships=malloc(ship); + getimage(0,0,80,80,ships); + cleardevice(); + + setfillstyle(1,15); + setcolor(15); + fillellipse(40,40,33,16); + fillellipse(40,25,15,10); + setfillstyle(1,4); + fillellipse(14,37,5,5); + fillellipse(35,40,5,5); + fillellipse(55,39,5,5); + setfillstyle(1,2); + fillellipse(25,39,5,5); + fillellipse(46,40,5,5); + fillellipse(65,37,5,5); + setfillstyle(1,0); + fillellipse(30,20,2,2); + fillellipse(35,20,2,2); + fillellipse(40,20,2,2); + fillellipse(45,20,2,2); + fillellipse(50,20,2,2); + ship2=imagesize(0,0,80,80); + ships2=malloc(ship2); + getimage(0,0,80,80,ships2); + cleardevice(); + + + + setfillstyle(1,9); + setcolor(9); + fillellipse(45,45,16,16); + setcolor(8); + ellipse(45,45,125,390,20,7); + setcolor(1); + ellipse(45,45,120,400,23,8); + setcolor(4); + ellipse(45,45,120,400,25,9); + setcolor(5); + ellipse(45,45,120,424,28,10); + setcolor(6); + ellipse(45,45,115,425,30,11); + saturn=imagesize(0,0,50,50); + sat=malloc(saturn); + getimage(0,0,75,75,sat); + cleardevice(); + setcolor(15); + + + for(i=0; i<1000 && !kbhit(); i++) + { + moveto(getmaxx()/2,getmaxy()/2); + +lineto(random(600)+random(600)*cos(i),random(600)+random(600)*sin(i)); +// setcolor(i); + delay(10); + } + cleardevice(); + + delay(300); + setlinestyle(0,0,3); + rectangle(0,0,getmaxx(),getmaxy()); + delay(700); + for(i=0; i<1000; i++) + { + putpixel(random(630),random(530),15); + putpixel(random(630),random(530),11); + delay(5); + } + setlinestyle(3,0,1); + +// ellipse(x,y,0,360,10+cos(0.2)+13,8+sin(0.2)+13); + setlinestyle(0,0,1); + + for(k=0; k<200; k++) + { + i=i+0.2; + j=j+0.7; + me=me+0.1; + ve=ve+0.3; + ma=ma+0.1; + ju=ju+0.08; + sa=sa+0.07; + ur=ur+0.06; + ne=ne+0.05; + pl=pl+0.04; + putpixel(x+100*cos(i)+13,y+80*sin(i)+13,10); +// +putpixel(x+(100*cos(i))+(30*cos(j))+5,y+(80*sin(i))+(25*sin(j))+5,1); + putpixel(x+60*cos(me)+4,y+40*sin(me)+4,4); + putpixel(x+80*cos(ve)+7,y+60*sin(ve)+7,3); + putpixel(x+125*cos(ma)+14,y+110*sin(ma)+14,6); + putpixel(x+165*cos(ju)+18,y+130*sin(ju)+18,7); + putpixel(x+220*cos(sa)+30+16,y+170*sin(sa)+30+16,9); + putpixel(x+250*cos(ur)+12,y+200*sin(ur)+12,8); + putpixel(x+280*cos(ne)+11,y+230*sin(ne)+11,12); + putpixel(x+310*cos(pl)+8,y+250*sin(pl)+8,1); + + + } + + + setfillstyle(1,14); + setcolor(14); + fillellipse(x,y,25,25); + delay(250); + putimage(x-40,y-40,sun,XOR_PUT); + setlinestyle(0,0,1); + setfillstyle(1,14); + setcolor(14); + fillellipse(x,y,25,25); + delay(250); + putimage(x+100*cos(i),y+80*sin(i),ear,XOR_PUT); + delay(250); + +putimage(x+(100*cos(i))+(30*cos(j)),y+(80*sin(i))+(25*sin(j)),moo,XOR_PUT) +; + delay(250); + putimage(x+60*cos(me),y+40*sin(me),mer,XOR_PUT); + delay(250); + putimage(x+80*cos(ve),y+60*sin(ve),ven,XOR_PUT); + delay(250); + putimage(x+125*cos(ma),y+110*sin(ma),mar,XOR_PUT); + delay(250); + putimage(x+165*cos(ju),y+130*sin(ju),jup,XOR_PUT); + delay(250); + putimage(x+220*cos(sa),y+170*sin(sa),sat,XOR_PUT); + delay(250); + putimage(x+250*cos(ur),y+200*sin(ur),ura,XOR_PUT); + delay(250); + putimage(x+280*cos(ne),y+230*sin(ne),nep,XOR_PUT); + delay(250); + putimage(x+310*cos(pl),y+250*sin(pl),plu,XOR_PUT); + + + putimage(x-40,y-40,sun,XOR_PUT); + setlinestyle(0,0,1); + setfillstyle(1,14); + setcolor(14); + fillellipse(x,y,25,25); + + putimage(x+100*cos(i),y+80*sin(i),ear,XOR_PUT); + +putimage(x+(100*cos(i))+(30*cos(j)),y+(80*sin(i))+(25*sin(j)),moo,XOR_PUT) +; + putimage(x+60*cos(me),y+40*sin(me),mer,XOR_PUT); + putimage(x+80*cos(ve),y+60*sin(ve),ven,XOR_PUT); + putimage(x+125*cos(ma),y+110*sin(ma),mar,XOR_PUT); + putimage(x+165*cos(ju),y+130*sin(ju),jup,XOR_PUT); + putimage(x+220*cos(sa),y+170*sin(sa),sat,XOR_PUT); + putimage(x+250*cos(ur),y+200*sin(ur),ura,XOR_PUT); + putimage(x+280*cos(ne),y+230*sin(ne),nep,XOR_PUT); + putimage(x+310*cos(pl),y+250*sin(pl),plu,XOR_PUT); + + for(k=0; k<200; k++) + { + i=i+0.2; + j=j+0.7; + me=me+0.1; + ve=ve+0.3; + ma=ma+0.1; + ju=ju+0.08; + sa=sa+0.07; + ur=ur+0.06; + ne=ne+0.05; + pl=pl+0.04; + putpixel(x+100*cos(i)+13,y+80*sin(i)+13,10); +// +putpixel(x+(100*cos(i))+(30*cos(j))+5,y+(80*sin(i))+(25*sin(j))+5,1); + putpixel(x+60*cos(me)+4,y+40*sin(me)+4,4); + putpixel(x+80*cos(ve)+7,y+60*sin(ve)+7,3); + putpixel(x+125*cos(ma)+14,y+110*sin(ma)+14,6); + putpixel(x+165*cos(ju)+18,y+130*sin(ju)+18,7); + putpixel(x+220*cos(sa)+30+16,y+170*sin(sa)+30+16,9); + putpixel(x+250*cos(ur)+12,y+200*sin(ur)+12,8); + putpixel(x+280*cos(ne)+11,y+230*sin(ne)+11,12); + putpixel(x+310*cos(pl)+8,y+250*sin(pl)+8,1); + + + } + + i=0;j=100;me=75;ve=23;ma=105;ju=175;sa=10;ur=300;ne=200;pl=175; + + + while(!kbhit()) + + { + i=i+0.2; + j=j+0.7; + me=me+0.1; + ve=ve+0.3; + ma=ma+0.1; + ju=ju+0.08; + sa=sa+0.07; + ur=ur+0.06; + ne=ne+0.05; + pl=pl+0.04; + + putimage(x-40,y-40,sun,XOR_PUT); + setlinestyle(0,0,1); + setfillstyle(1,14); + setcolor(14); + fillellipse(x,y,25,25); + + putimage(x+100*cos(i),y+80*sin(i),ear,XOR_PUT); + +putimage(x+(100*cos(i))+(30*cos(j)),y+(80*sin(i))+(25*sin(j)),moo,XOR_PUT) +; + putimage(x+60*cos(me),y+40*sin(me),mer,XOR_PUT); + putimage(x+80*cos(ve),y+60*sin(ve),ven,XOR_PUT); + putimage(x+125*cos(ma),y+110*sin(ma),mar,XOR_PUT); + putimage(x+165*cos(ju),y+130*sin(ju),jup,XOR_PUT); + putimage(x+220*cos(sa),y+170*sin(sa),sat,XOR_PUT); + putimage(x+250*cos(ur),y+200*sin(ur),ura,XOR_PUT); + putimage(x+280*cos(ne),y+230*sin(ne),nep,XOR_PUT); + putimage(x+310*cos(pl),y+250*sin(pl),plu,XOR_PUT); + + for(ss=0; ss<7; ss++) + { + X=random(10); + Y=random(10); + + if(X>3) + sx=sx+5; + else + sx=sx-5; + + if(Y>3) + sy=sy+5; + else + sy=sy-5; + + if(ss%2==0) + { + putimage(sx,sy,ships,XOR_PUT); + delay(100); + putimage(sx,sy,ships,XOR_PUT); + } + else + { + putimage(sx,sy,ships2,XOR_PUT); + delay(100); + putimage(sx,sy,ships2,XOR_PUT); + } + + } + if(sx>getmaxx() || sx<=0) + sx=random(300); + + if(sy>getmaxy() || sy<=0) + sy=random(300); + putimage(x+100*cos(i),y+80*sin(i),ear,XOR_PUT); + +putimage(x+(100*cos(i))+(30*cos(j)),y+(80*sin(i))+(25*sin(j)),moo,XOR_PUT) +; + putimage(x+60*cos(me),y+40*sin(me),mer,XOR_PUT); + putimage(x+80*cos(ve),y+60*sin(ve),ven,XOR_PUT); + putimage(x+125*cos(ma),y+110*sin(ma),mar,XOR_PUT); + putimage(x+165*cos(ju),y+130*sin(ju),jup,XOR_PUT); + putimage(x+220*cos(sa),y+170*sin(sa),sat,XOR_PUT); + putimage(x+250*cos(ur),y+200*sin(ur),ura,XOR_PUT); + putimage(x+280*cos(ne),y+230*sin(ne),nep,XOR_PUT); + putimage(x+310*cos(pl),y+250*sin(pl),plu,XOR_PUT); + + + } + + + getch(); + closegraph(); +} diff --git a/c++/Others/Sort.h - A collection of sorting and selection routines.cpp b/c++/Others/Sort.h - A collection of sorting and selection routines.cpp new file mode 100644 index 0000000..79e8a50 --- /dev/null +++ b/c++/Others/Sort.h - A collection of sorting and selection routines.cpp @@ -0,0 +1,362 @@ +Sort.h - A collection of sorting and selection routines + + #ifndef SORT_H_ + #define SORT_H_ + +#define merge Merge +#define swap Swap + /** + * Several sorting routines. + * Arrays are rearranged with smallest item first. + */ + + #include "vector.h" + + /** + * Simple insertion sort. + */ + template + void insertionSort( vector & a ) + { +/* 1*/ for( int p = 1; p < a.size( ); p++ ) + { +/* 2*/ Comparable tmp = a[ p ]; + + int j; +/* 3*/ for( j = p; j > 0 && tmp < a[ j - 1 ]; j-- ) +/* 4*/ a[ j ] = a[ j - 1 ]; +/* 5*/ a[ j ] = tmp; + } + } + + /** + * Shellsort, using Shell's (poor) increments. + */ + template + void shellsort( vector & a ) + { + for( int gap = a.size( ) / 2; gap > 0; gap /= 2 ) + for( int i = gap; i < a.size( ); i++ ) + { + Comparable tmp = a[ i ]; + int j = i; + + for( ; j >= gap && tmp < a[ j - gap ]; j -= gap ) + a[ j ] = a[ j - gap ]; + a[ j ] = tmp; + } + } + + /** + * Standard heapsort. + */ + template + void heapsort( vector & a ) + { +/* 1*/ for( int i = a.size( ) / 2; i >= 0; i-- ) /* buildHeap */ +/* 2*/ percDown( a, i, a.size( ) ); +/* 3*/ for( int j = a.size( ) - 1; j > 0; j-- ) + { +/* 4*/ swap( a[ 0 ], a[ j ] ); /* deleteMax */ +/* 5*/ percDown( a, 0, j ); + } + } + + /** + * Internal method for heapsort. + * i is the index of an item in the heap. + * Returns the index of the left child. + */ + inline int leftChild( int i ) + { + return 2 * i + 1; + } + + /** + * Internal method for heapsort that is used in + * deleteMax and buildHeap. + * i is the position from which to percolate down. + * n is the logical size of the binary heap. + */ + template + void percDown( vector & a, int i, int n ) + { + int child; + Comparable tmp; + +/* 1*/ for( tmp = a[ i ]; leftChild( i ) < n; i = child ) + { +/* 2*/ child = leftChild( i ); +/* 3*/ if( child != n - 1 && a[ child ] < a[ child + 1 ] ) +/* 4*/ child++; +/* 5*/ if( tmp < a[ child ] ) +/* 6*/ a[ i ] = a[ child ]; + else +/* 7*/ break; + } +/* 8*/ a[ i ] = tmp; + } + + /** + * Mergesort algorithm (driver). + */ + template + void mergeSort( vector & a ) + { + vector tmpArray( a.size( ) ); + + mergeSort( a, tmpArray, 0, a.size( ) - 1 ); + } + + /** + * Internal method that makes recursive calls. + * a is an array of Comparable items. + * tmpArray is an array to place the merged result. + * left is the left-most index of the subarray. + * right is the right-most index of the subarray. + */ + template + void mergeSort( vector & a, + vector & tmpArray, int left, int right ) + { + if( left < right ) + { + int center = ( left + right ) / 2; + mergeSort( a, tmpArray, left, center ); + mergeSort( a, tmpArray, center + 1, right ); + merge( a, tmpArray, left, center + 1, right ); + } + } + + /** + * Internal method that merges two sorted halves of a subarray. + * a is an array of Comparable items. + * tmpArray is an array to place the merged result. + * leftPos is the left-most index of the subarray. + * rightPos is the index of the start of the second half. + * rightEnd is the right-most index of the subarray. + */ + template + void merge( vector & a, vector & tmpArray, + int leftPos, int rightPos, int rightEnd ) + { + int leftEnd = rightPos - 1; + int tmpPos = leftPos; + int numElements = rightEnd - leftPos + 1; + + // Main loop + while( leftPos <= leftEnd && rightPos <= rightEnd ) + if( a[ leftPos ] <= a[ rightPos ] ) + tmpArray[ tmpPos++ ] = a[ leftPos++ ]; + else + tmpArray[ tmpPos++ ] = a[ rightPos++ ]; + + while( leftPos <= leftEnd ) // Copy rest of first half + tmpArray[ tmpPos++ ] = a[ leftPos++ ]; + + while( rightPos <= rightEnd ) // Copy rest of right half + tmpArray[ tmpPos++ ] = a[ rightPos++ ]; + + // Copy tmpArray back + for( int i = 0; i < numElements; i++, rightEnd-- ) + a[ rightEnd ] = tmpArray[ rightEnd ]; + } + + /** + * Quicksort algorithm (driver). + */ + template + void quicksort( vector & a ) + { + quicksort( a, 0, a.size( ) - 1 ); + } + + /** + * Standard swap + */ + template + inline void swap( Comparable & obj1, Comparable & obj2 ) + { + Comparable tmp = obj1; + obj1 = obj2; + obj2 = tmp; + } + + /** + * Return median of left, center, and right. + * Order these and hide the pivot. + */ + template + const Comparable & median3( vector & a, int left, int right ) + { + int center = ( left + right ) / 2; + if( a[ center ] < a[ left ] ) + swap( a[ left ], a[ center ] ); + if( a[ right ] < a[ left ] ) + swap( a[ left ], a[ right ] ); + if( a[ right ] < a[ center ] ) + swap( a[ center ], a[ right ] ); + + // Place pivot at position right - 1 + swap( a[ center ], a[ right - 1 ] ); + return a[ right - 1 ]; + } + + /** + * Internal quicksort method that makes recursive calls. + * Uses median-of-three partitioning and a cutoff of 10. + * a is an array of Comparable items. + * left is the left-most index of the subarray. + * right is the right-most index of the subarray. + */ + template + void quicksort( vector & a, int left, int right ) + { +/* 1*/ if( left + 10 <= right ) + { +/* 2*/ Comparable pivot = median3( a, left, right ); + + // Begin partitioning +/* 3*/ int i = left, j = right - 1; +/* 4*/ for( ; ; ) + { +/* 5*/ while( a[ ++i ] < pivot ) { } +/* 6*/ while( pivot < a[ --j ] ) { } +/* 7*/ if( i < j ) +/* 8*/ swap( a[ i ], a[ j ] ); + else +/* 9*/ break; + } + +/*10*/ swap( a[ i ], a[ right - 1 ] ); // Restore pivot + +/*11*/ quicksort( a, left, i - 1 ); // Sort small elements +/*12*/ quicksort( a, i + 1, right ); // Sort large elements + } + else // Do an insertion sort on the subarray +/*13*/ insertionSort( a, left, right ); + } + + /** + * Internal insertion sort routine for subarrays + * that is used by quicksort. + * a is an array of Comparable items. + * left is the left-most index of the subarray. + * right is the right-most index of the subarray. + */ + template + void insertionSort( vector & a, int left, int right ) + { + for( int p = left + 1; p <= right; p++ ) + { + Comparable tmp = a[ p ]; + int j; + + for( j = p; j > left && tmp < a[ j - 1 ]; j-- ) + a[ j ] = a[ j - 1 ]; + a[ j ] = tmp; + } + } + + /** + * Quick selection algorithm. + * Places the kth smallest item in a[k-1]. + * a is an array of Comparable items. + * k is the desired rank (1 is minimum) in the entire array. + */ + template + void quickSelect( vector & a, int k ) + { + quickSelect( a, 0, a.size( ) - 1, k ); + } + + + /** + * Internal selection method that makes recursive calls. + * Uses median-of-three partitioning and a cutoff of 10. + * Places the kth smallest item in a[k-1]. + * a is an array of Comparable items. + * left is the left-most index of the subarray. + * right is the right-most index of the subarray. + * k is the desired rank (1 is minimum) in the entire array. + */ + template + void quickSelect( vector & a, int left, int right, int k ) + { +/* 1*/ if( left + 10 <= right ) + { +/* 2*/ Comparable pivot = median3( a, left, right ); + + // Begin partitioning +/* 3*/ int i = left, j = right - 1; +/* 4*/ for( ; ; ) + { +/* 5*/ while( a[ ++i ] < pivot ) { } +/* 6*/ while( pivot < a[ --j ] ) { } +/* 7*/ if( i < j ) +/* 8*/ swap( a[ i ], a[ j ] ); + else +/* 9*/ break; + } + +/*10*/ swap( a[ i ], a[ right - 1 ] ); // Restore pivot + + // Recurse; only this part changes +/*11*/ if( k <= i ) +/*12*/ quickSelect( a, left, i - 1, k ); +/*13*/ else if( k > i + 1 ) +/*14*/ quickSelect( a, i + 1, right, k ); + } + else // Do an insertion sort on the subarray +/*15*/ insertionSort( a, left, right ); + } + + /** + * Class that wraps a pointer variable. + */ + template + class Pointer + { + public: + Pointer( Comparable *rhs = NULL ) : pointee( rhs ) { } + + bool operator<( const Pointer & rhs ) const + { return *pointee < *rhs.pointee; } + operator Comparable * ( ) const + { return pointee; } + private: + Comparable *pointee; + }; + + /** + * Sort objects -- even large ones -- + * with only N + ln N Comparable moves on average. + */ + template + void largeObjectSort( vector & a ) + { + vector > p( a.size( ) ); + int i, j, nextj; + + for( i = 0; i < a.size( ); i++ ) + p[ i ] = &a[ i ]; + + quicksort( p ); + + // Shuffle items in place + for( i = 0; i < a.size( ); i++ ) + if( p[ i ] != &a[ i ] ) + { + Comparable tmp = a[ i ]; + for( j = i; p[ j ] != &a[ i ]; j = nextj ) + { + nextj = p[ j ] - &a[ 0 ]; + a[ j ] = *p[ j ]; + p[ j ] = &a[ j ]; + } + a[ j ] = tmp; + p[ j ] = &a[ j ]; + } + } + + #endif diff --git a/c++/Others/SplayTree.cpp - Implementation for top-down splay tree.cpp b/c++/Others/SplayTree.cpp - Implementation for top-down splay tree.cpp new file mode 100644 index 0000000..91d6119 --- /dev/null +++ b/c++/Others/SplayTree.cpp - Implementation for top-down splay tree.cpp @@ -0,0 +1,348 @@ +SplayTree.cpp - Implementation for top-down splay tree + + #include + #include "SplayTree.h" + + /** + * Construct the tree. + */ + template + SplayTree::SplayTree( const Comparable & notFound ) + : ITEM_NOT_FOUND( notFound ) + { + nullNode = new BinaryNode; + nullNode->left = nullNode->right = nullNode; + nullNode->element = notFound; + root = nullNode; + } + + /** + * Copy constructor. + */ + template + SplayTree::SplayTree( const SplayTree & rhs ) + : ITEM_NOT_FOUND( rhs.ITEM_NOT_FOUND ) + { + nullNode = new BinaryNode; + nullNode->left = nullNode->right = nullNode; + nullNode->element = ITEM_NOT_FOUND; + root = nullNode; + *this = rhs; + } + + /** + * Destructor. + */ + template + SplayTree::~SplayTree( ) + { + makeEmpty( ); + delete nullNode; + } + + /** + * Insert x into the tree. + */ + template + void SplayTree::insert( const Comparable & x ) + { + static BinaryNode *newNode = NULL; + + if( newNode == NULL ) + newNode = new BinaryNode; + newNode->element = x; + + if( root == nullNode ) + { + newNode->left = newNode->right = nullNode; + root = newNode; + } + else + { + splay( x, root ); + if( x < root->element ) + { + newNode->left = root->left; + newNode->right = root; + root->left = nullNode; + root = newNode; + } + else + if( root->element < x ) + { + newNode->right = root->right; + newNode->left = root; + root->right = nullNode; + root = newNode; + } + else + return; + } + newNode = NULL; // So next insert will call new + } + + /** + * Remove x from the tree. + */ + template + void SplayTree::remove( const Comparable & x ) + { + BinaryNode *newTree; + + // If x is found, it will be at the root + splay( x, root ); + if( root->element != x ) + return; // Item not found; do nothing + + if( root->left == nullNode ) + newTree = root->right; + else + { + // Find the maximum in the left subtree + // Splay it to the root; and then attach right child + newTree = root->left; + splay( x, newTree ); + newTree->right = root->right; + } + delete root; + root = newTree; + } + + /** + * Find the smallest item in the tree. + * Not the most efficient implementation (uses two passes), but has correct + * amortized behavior. + * A good alternative is to first call Find with parameter + * smaller than any item in the tree, then call findMin. + * Return the smallest item or ITEM_NOT_FOUND if empty. + */ + template + const Comparable & SplayTree::findMin( ) + { + if( isEmpty( ) ) + return ITEM_NOT_FOUND; + + BinaryNode *ptr = root; + + while( ptr->left != nullNode ) + ptr = ptr->left; + + splay( ptr->element, root ); + return ptr->element; + } + + /** + * Find the largest item in the tree. + * Not the most efficient implementation (uses two passes), but has correct + * amortized behavior. + * A good alternative is to first call Find with parameter + * larger than any item in the tree, then call findMax. + * Return the largest item or ITEM_NOT_FOUND if empty. + */ + template + const Comparable & SplayTree::findMax( ) + { + if( isEmpty( ) ) + return ITEM_NOT_FOUND; + + BinaryNode *ptr = root; + + while( ptr->right != nullNode ) + ptr = ptr->right; + + splay( ptr->element, root ); + return ptr->element; + } + + /** + * Find item x in the tree. + * Return the matching item or ITEM_NOT_FOUND if not found. + */ + template + const Comparable & SplayTree::find( const Comparable & x ) + { + if( isEmpty( ) ) + return ITEM_NOT_FOUND; + splay( x, root ); + if( root->element != x ) + return ITEM_NOT_FOUND; + + return root->element; + } + + /** + * Make the tree logically empty. + */ + template + void SplayTree::makeEmpty( ) + { + /****************************** + * Comment this out, because it is prone to excessive + * recursion on degenerate trees. Use alternate algorithm. + + reclaimMemory( root ); + root = nullNode; + *******************************/ + findMax( ); // Splay max item to root + while( !isEmpty( ) ) + remove( root->element ); + } + + /** + * Test if the tree is logically empty. + * @return true if empty, false otherwise. + */ + template + bool SplayTree::isEmpty( ) const + { + return root == nullNode; + } + + /** + * Print the tree contents in sorted order. + */ + template + void SplayTree::printTree( ) const + { + if( isEmpty( ) ) + cout << "Empty tree" << endl; + else + printTree( root ); + } + + /** + * Deep copy. + */ + template + const SplayTree & + SplayTree::operator=( const SplayTree & rhs ) + { + if( this != &rhs ) + { + makeEmpty( ); + root = clone( rhs.root ); + } + + return *this; + } + + /** + * Internal method to perform a top-down splay. + * The last accessed node becomes the new root. + * This method may be overridden to use a different + * splaying algorithm, however, the splay tree code + * depends on the accessed item going to the root. + * x is the target item to splay around. + * t is the root of the subtree to splay. + */ + template + void SplayTree::splay( const Comparable & x, + BinaryNode * & t ) const + { + BinaryNode *leftTreeMax, *rightTreeMin; + static BinaryNode header; + + header.left = header.right = nullNode; + leftTreeMax = rightTreeMin = &header; + + nullNode->element = x; // Guarantee a match + + for( ; ; ) + if( x < t->element ) + { + if( x < t->left->element ) + rotateWithLeftChild( t ); + if( t->left == nullNode ) + break; + // Link Right + rightTreeMin->left = t; + rightTreeMin = t; + t = t->left; + } + else if( t->element < x ) + { + if( t->right->element < x ) + rotateWithRightChild( t ); + if( t->right == nullNode ) + break; + // Link Left + leftTreeMax->right = t; + leftTreeMax = t; + t = t->right; + } + else + break; + + leftTreeMax->right = t->left; + rightTreeMin->left = t->right; + t->left = header.right; + t->right = header.left; + } + + /** + * Rotate binary tree node with left child. + */ + template + void SplayTree::rotateWithLeftChild( BinaryNode * & k2 ) const + { + BinaryNode *k1 = k2->left; + k2->left = k1->right; + k1->right = k2; + k2 = k1; + } + + /** + * Rotate binary tree node with right child. + */ + template + void SplayTree::rotateWithRightChild( BinaryNode * & k1 ) const + { + BinaryNode *k2 = k1->right; + k1->right = k2->left; + k2->left = k1; + k1 = k2; + } + + /** + * Internal method to print a subtree t in sorted order. + * WARNING: This is prone to running out of stack space. + */ + template + void SplayTree::printTree( BinaryNode *t ) const + { + if( t != t->left ) + { + printTree( t->left ); + cout << t->element << endl; + printTree( t->right ); + } + } + + /** + * Internal method to reclaim internal nodes in subtree t. + * WARNING: This is prone to running out of stack space. + */ + template + void SplayTree::reclaimMemory( BinaryNode * t ) const + { + if( t != t->left ) + { + reclaimMemory( t->left ); + reclaimMemory( t->right ); + delete t; + } + } + + /** + * Internal method to clone subtree. + * WARNING: This is prone to running out of stack space. + */ + template + BinaryNode * + SplayTree::clone( BinaryNode * t ) const + { + if( t == t->left ) // Cannot test against nullNode!!! + return nullNode; + else + return new BinaryNode( t->element, clone( t->left ), clone( t->right ) ); + } diff --git a/c++/Others/SplayTree.h - Header file for top-down splay tree.cpp b/c++/Others/SplayTree.h - Header file for top-down splay tree.cpp new file mode 100644 index 0000000..61f520d --- /dev/null +++ b/c++/Others/SplayTree.h - Header file for top-down splay tree.cpp @@ -0,0 +1,82 @@ +SplayTree.h - Header file for top-down splay tree + + #ifndef SPLAY_TREE_H_ + #define SPLAY_TREE_H_ + + #include "dsexceptions.h" + #include // For NULL + + // SplayTree class + // + // CONSTRUCTION: with ITEM_NOT_FOUND object used to signal failed finds + // + // ******************PUBLIC OPERATIONS********************* + // void insert( x ) --> Insert x + // void remove( x ) --> Remove x + // Comparable find( x ) --> Return item that matches x + // Comparable findMin( ) --> Return smallest item + // Comparable findMax( ) --> Return largest item + // boolean isEmpty( ) --> Return true if empty; else false + // void makeEmpty( ) --> Remove all items + // void printTree( ) --> Print tree in sorted order + + + // Node and forward declaration because g++ does + // not understand nested classes. + template + class SplayTree; + + template + class BinaryNode + { + Comparable element; + BinaryNode *left; + BinaryNode *right; + + BinaryNode( ) : left( NULL ), right( NULL ) { } + BinaryNode( const Comparable & theElement, BinaryNode *lt, BinaryNode *rt ) + : element( theElement ), left( lt ), right( rt ) { } + + friend class SplayTree; + }; + + + template + class SplayTree + { + public: + explicit SplayTree( const Comparable & notFound ); + SplayTree( const SplayTree & rhs ); + ~SplayTree( ); + + const Comparable & findMin( ); + const Comparable & findMax( ); + const Comparable & find( const Comparable & x ); + bool isEmpty( ) const; + void printTree( ) const; + + void makeEmpty( ); + void insert( const Comparable & x ); + void remove( const Comparable & x ); + + const SplayTree & operator=( const SplayTree & rhs ); + + private: + BinaryNode *root; + BinaryNode *nullNode; + const Comparable ITEM_NOT_FOUND; + + const Comparable & elementAt( BinaryNode *t ) const; + + void reclaimMemory( BinaryNode * t ) const; + void printTree( BinaryNode *t ) const; + BinaryNode * clone( BinaryNode *t ) const; + + // Tree manipulations + void rotateWithLeftChild( BinaryNode * & k2 ) const; + void rotateWithRightChild( BinaryNode * & k1 ) const; + void splay( const Comparable & x, BinaryNode * & t ) const; + }; + + #include "SplayTree.cpp" + #endif diff --git a/c++/Others/Stack implementation as a class.cpp b/c++/Others/Stack implementation as a class.cpp new file mode 100644 index 0000000..5c977fd --- /dev/null +++ b/c++/Others/Stack implementation as a class.cpp @@ -0,0 +1,103 @@ +Stack implementation as a class + +# include +# include +# include +# define SIZE 20 + +class stack +{ +int a[SIZE]; +int tos; // Top of Stack +public: + stack(); + void push(int); + int pop(); + int isempty(); + int isfull(); +}; +stack::stack() +{ +tos=0; //Initialize Top of Stack +} + +int stack::isempty() +{ +return (tos==0?1:0); +} +int stack::isfull() +{ +return (tos==SIZE?1:0); +} + +void stack::push(int i) +{ +if(!isfull()) +{ +a[tos]=i; +tos++; +} +else +{ + cerr<<"Stack overflow error ! +Possible Data Loss !"; +} +} +int stack::pop() +{ +if(!isempty()) +{ +return(a[--tos]); +} +else +{ +cerr<<"Stack is empty! What to pop...!"; +} +return 0; +} + +void main() +{ +stack s; +int ch=1,num; +while(ch!=0) +{ + cout<<"Stack Operations Mani Menu +1.Push +2.Pop +3.IsEmpty +4.IsFull +0.Exit + +"; + cin>>ch; + switch(ch) + { + case 0: + exit(1); //Normal Termination of Program + case 1: + cout<<"Enter the number to push"; + cin>>num; + s.push(num); + break; + case 2: + cout<<"Number popped from the stack is: "< + Stack::Stack( int capacity ) : theArray( capacity ) + { + topOfStack = -1; + } + + /** + * Test if the stack is logically empty. + * Return true if empty, false otherwise. + */ + template + bool Stack::isEmpty( ) const + { + return topOfStack == -1; + } + + /** + * Test if the stack is logically full. + * Return true if full, false otherwise. + */ + template + bool Stack::isFull( ) const + { + return topOfStack == theArray.size( ) - 1; + } + + /** + * Make the stack logically empty. + */ + template + void Stack::makeEmpty( ) + { + topOfStack = -1; + } + + /** + * Get the most recently inserted item in the stack. + * Does not alter the stack. + * Return the most recently inserted item in the stack. + * Exception Underflow if stack is already empty. + */ + template + const Object & Stack::top( ) const + { + if( isEmpty( ) ) + throw Underflow( ); + return theArray[ topOfStack ]; + } + + /** + * Remove the most recently inserted item from the stack. + * Exception Underflow if stack is already empty. + */ + template + void Stack::pop( ) + { + if( isEmpty( ) ) + throw Underflow( ); + topOfStack--; + } + + /** + * Insert x into the stack, if not already full. + * Exception Overflow if stack is already full. + */ + template + void Stack::push( const Object & x ) + { + if( isFull( ) ) + throw Overflow( ); + theArray[ ++topOfStack ] = x; + } + + /** + * Return and remove most recently inserted item from the stack. + * Return most recently inserted item. + * Exception Underflow if stack is already empty. + */ + template + Object Stack::topAndPop( ) + { + if( isEmpty( ) ) + throw Underflow( ); + return theArray[ topOfStack-- ]; + } diff --git a/c++/Others/StackAr.cpp - Implementation for stack - array version.cpp b/c++/Others/StackAr.cpp - Implementation for stack - array version.cpp new file mode 100644 index 0000000..b27407d --- /dev/null +++ b/c++/Others/StackAr.cpp - Implementation for stack - array version.cpp @@ -0,0 +1,92 @@ +StackAr.cpp - Implementation for stack - array version + + #include "StackAr.h" + + /** + * Construct the stack. + */ + template + Stack::Stack( int capacity ) : theArray( capacity ) + { + topOfStack = -1; + } + + /** + * Test if the stack is logically empty. + * Return true if empty, false otherwise. + */ + template + bool Stack::isEmpty( ) const + { + return topOfStack == -1; + } + + /** + * Test if the stack is logically full. + * Return true if full, false otherwise. + */ + template + bool Stack::isFull( ) const + { + return topOfStack == theArray.size( ) - 1; + } + + /** + * Make the stack logically empty. + */ + template + void Stack::makeEmpty( ) + { + topOfStack = -1; + } + + /** + * Get the most recently inserted item in the stack. + * Does not alter the stack. + * Return the most recently inserted item in the stack. + * Exception Underflow if stack is already empty. + */ + template + const Object & Stack::top( ) const + { + if( isEmpty( ) ) + throw Underflow( ); + return theArray[ topOfStack ]; + } + + /** + * Remove the most recently inserted item from the stack. + * Exception Underflow if stack is already empty. + */ + template + void Stack::pop( ) + { + if( isEmpty( ) ) + throw Underflow( ); + topOfStack--; + } + + /** + * Insert x into the stack, if not already full. + * Exception Overflow if stack is already full. + */ + template + void Stack::push( const Object & x ) + { + if( isFull( ) ) + throw Overflow( ); + theArray[ ++topOfStack ] = x; + } + + /** + * Return and remove most recently inserted item from the stack. + * Return most recently inserted item. + * Exception Underflow if stack is already empty. + */ + template + Object Stack::topAndPop( ) + { + if( isEmpty( ) ) + throw Underflow( ); + return theArray[ topOfStack-- ]; + } diff --git a/c++/Others/StackAr.h - Header file for stack - array version.cpp b/c++/Others/StackAr.h - Header file for stack - array version.cpp new file mode 100644 index 0000000..ba74e2e --- /dev/null +++ b/c++/Others/StackAr.h - Header file for stack - array version.cpp @@ -0,0 +1,45 @@ +StackAr.h - Header file for stack - array version + + #ifndef STACKAR_H + #define STACKAR_H + + #include "vector.h" + #include "dsexceptions.h" + + // Stack class -- array implementation + // + // CONSTRUCTION: with or without a capacity; default is 10 + // + // ******************PUBLIC OPERATIONS********************* + // void push( x ) --> Insert x + // void pop( ) --> Remove most recently inserted item + // Object top( ) --> Return most recently inserted item + // Object topAndPop( ) --> Return and remove most recently inserted item + // bool isEmpty( ) --> Return true if empty; else false + // bool isFull( ) --> Return true if full; else false + // void makeEmpty( ) --> Remove all items + // ******************ERRORS******************************** + // Overflow and Underflow thrown as needed + + template + class Stack + { + public: + explicit Stack( int capacity = 10 ); + + bool isEmpty( ) const; + bool isFull( ) const; + const Object & top( ) const; + + void makeEmpty( ); + void pop( ); + void push( const Object & x ); + Object topAndPop( ); + + private: + vector theArray; + int topOfStack; + }; + + #include "StackAr.cpp" + #endif diff --git a/c++/Others/StackLi.cpp - Implementation for stack - list version.cpp b/c++/Others/StackLi.cpp - Implementation for stack - list version.cpp new file mode 100644 index 0000000..82bf0cb --- /dev/null +++ b/c++/Others/StackLi.cpp - Implementation for stack - list version.cpp @@ -0,0 +1,134 @@ +StackLi.cpp - Implementation for stack - list version + + #include "StackLi.h" + #include + + /** + * Construct the stack. + */ + template + Stack::Stack( ) + { + topOfStack = NULL; + } + + /** + * Copy constructor. + */ + template + Stack::Stack( const Stack & rhs ) + { + topOfStack = NULL; + *this = rhs; + } + + /** + * Destructor. + */ + template + Stack::~Stack( ) + { + makeEmpty( ); + } + + /** + * Test if the stack is logically full. + * Return false always, in this implementation. + */ + template + bool Stack::isFull( ) const + { + return false; + } + + /** + * Test if the stack is logically empty. + * Return true if empty, false otherwise. + */ + template + bool Stack::isEmpty( ) const + { + return topOfStack == NULL; + } + + /** + * Make the stack logically empty. + */ + template + void Stack::makeEmpty( ) + { + while( !isEmpty( ) ) + pop( ); + } + + /** + * Get the most recently inserted item in the stack. + * Return the most recently inserted item in the stack + * or throw an exception if empty. + */ + template + const Object & Stack::top( ) const + { + if( isEmpty( ) ) + throw Underflow( ); + return topOfStack->element; + } + + /** + * Remove the most recently inserted item from the stack. + * Exception Underflow if the stack is empty. + */ + template + void Stack::pop( ) + { + if( isEmpty( ) ) + throw Underflow( ); + + ListNode *oldTop = topOfStack; + topOfStack = topOfStack->next; + delete oldTop; + } + + /** + * Return and remove the most recently inserted item + * from the stack. + */ + template + Object Stack::topAndPop( ) + { + Object topItem = top( ); + pop( ); + return topItem; + } + + /** + * Insert x into the stack. + */ + template + void Stack::push( const Object & x ) + { + topOfStack = new ListNode( x, topOfStack ); + } + + /** + * Deep copy. + */ + template + const Stack & Stack:: + operator=( const Stack & rhs ) + { + if( this != &rhs ) + { + makeEmpty( ); + if( rhs.isEmpty( ) ) + return *this; + + ListNode *rptr = rhs.topOfStack; + ListNode *ptr = new ListNode( rptr->element ); + topOfStack = ptr; + + for( rptr = rptr->next; rptr != NULL; rptr = rptr->next ) + ptr = ptr->next = new ListNode( rptr->element ); + } + return *this; + } diff --git a/c++/Others/StackLi.h - Header file for stack - list version.cpp b/c++/Others/StackLi.h - Header file for stack - list version.cpp new file mode 100644 index 0000000..e261d5e --- /dev/null +++ b/c++/Others/StackLi.h - Header file for stack - list version.cpp @@ -0,0 +1,58 @@ +StackLi.h - Header file for stack - list version + + #ifndef STACKLI_H + #define STACKLI_H + + #include "dsexceptions.h" + #include // For NULL + + // Stack class -- linked list implementation + // + // CONSTRUCTION: with no parameters + // + // ******************PUBLIC OPERATIONS********************* + // void push( x ) --> Insert x + // void pop( ) --> Remove most recently inserted item + // Object top( ) --> Return most recently inserted item + // Object topAndPop( ) --> Return and remove most recently inserted item + // bool isEmpty( ) --> Return true if empty; else false + // bool isFull( ) --> Return true if full; else false + // void makeEmpty( ) --> Remove all items + // ******************ERRORS******************************** + // Overflow and Underflow thrown as needed + + template + class Stack + { + public: + Stack( ); + Stack( const Stack & rhs ); + ~Stack( ); + + bool isEmpty( ) const; + bool isFull( ) const; + const Object & top( ) const; + + void makeEmpty( ); + void pop( ); + void push( const Object & x ); + Object topAndPop( ); + + const Stack & operator=( const Stack & rhs ); + + private: + struct ListNode + { + Object element; + ListNode *next; + + ListNode( const Object & theElement, ListNode * n = NULL ) + : element( theElement ), next( n ) { } + }; + + ListNode *topOfStack; + }; + + #include "StackLi.cpp" + #endif + diff --git a/c++/Others/String Reverse code.cpp b/c++/Others/String Reverse code.cpp new file mode 100644 index 0000000..c9cc019 --- /dev/null +++ b/c++/Others/String Reverse code.cpp @@ -0,0 +1,30 @@ +String Reverse code + +# include +# include + +void reverseit(char array[],int no) +{ char c; int len,x, mid=0; + if(no==0) + {for(len=0,x=0; array[x] !='\x0';len++,x++); } + else + { len = 0; len = no; } + + mid = (len-1)/2; + + for(int i=0,j=len-1; i <=mid; i++,j--) + { c = array[i]; + array[i] = array[j]; + array[j] = c; + } + cout << endl<>nos; + reverseit(data,nos); +} diff --git a/c++/Others/String matching in linear-time.cpp b/c++/Others/String matching in linear-time.cpp new file mode 100644 index 0000000..7ad7b07 --- /dev/null +++ b/c++/Others/String matching in linear-time.cpp @@ -0,0 +1,114 @@ +String matching in linear-time + +#include +#include +#include +#include + +typedef std::vector int_vec; + +class string_search +{ + int_vec shifts; + void compute_shifts(const std::string &pattern); +public: + int find_first(const std::string &text, const std::string &pattern); + int_vec find_all(const std::string &text, const std::string &pattern); + +}; + +// create the shift-lookup-table +void string_search::compute_shifts(const std::string &pattern) +{ + int next_shift = 0; + shifts.clear(); + shifts.push_back(0); // shift to the first character + + // start with the second character, since the shift to the first is always 0 + for(int i = 1; i < pattern.length(); i++) + { + while(next_shift > 0 && pattern[next_shift] != pattern[i]) + next_shift = shifts[next_shift]; + + if(pattern[next_shift] == pattern[i]) + next_shift++; + + shifts.push_back(next_shift); + } +} + +// search the string and return when the first occurrence is found +int +string_search::find_first(const std::string &text, const std::string &pattern) +{ + int next_shift = 0; + compute_shifts(pattern); + for(int i = 0; i < text.length(); i++) + { + while(next_shift > 0 && pattern[next_shift] != text[i]) + next_shift = shifts[next_shift - 1]; + + if(pattern[next_shift] == text[i]) + next_shift++; + + if(next_shift == pattern.length()) + return i - (pattern.length() - 1); // found the first so return + } + return -1; +} + +// search the string and put every occurence in a vector +int_vec +string_search::find_all(const std::string &text, const std::string &pattern) +{ + int next_shift = 0; + int_vec positions; + compute_shifts(pattern); + for(int i = 0; i < text.length(); i++) + { + while(next_shift > 0 && pattern[next_shift] != text[i]) + next_shift = shifts[next_shift - 1]; + + if(pattern[next_shift] == text[i]) + next_shift++; + + if(next_shift == pattern.length()) + { + positions.push_back(i - (pattern.length() - 1)); // found one, put in list + next_shift = shifts[next_shift - 1]; // restart pattern with last shift + } + } + return positions; +} + +int main(int argc, char **argv) +{ + if(argc <= 2){ + cout << "Usage: " << argv[0] << " filename searchpattern" << endl; + return 0; + } + std::string pattern = argv[2]; + + // read the file. Since the file is read like this all white-characters + // are eaten, so a search including white-characters will fail... + fstream fs; + std::string text, temp; + fs.open(argv[1], ios::in); + while(!fs.eof()){ + fs >> temp; + text += temp; + } + fs.close(); + + // search the file + string_search search; + int_vec pos_list = search.find_all(text, pattern); + + // print out result + std::vector::iterator it; + cout << "Found " << pos_list.size() << " occurrences" << endl; + for(it = pos_list.begin(); it != pos_list.end(); it++){ + temp = text.substr(*it, pattern.length()); + cout << "Pos=" << *it << " == " << temp << endl; + } +} diff --git a/c++/Others/String operation.cpp b/c++/Others/String operation.cpp new file mode 100644 index 0000000..d0e8579 --- /dev/null +++ b/c++/Others/String operation.cpp @@ -0,0 +1,154 @@ +String operation + +#include +#include +#include +int STRLEN(char*); +int STRCPY(char*,char*); +int STRCMP(char*,char*); +int STRCAT(char*,char*,char*); +int STRREV(char*); +void main() +{ + int c; + char str[20],str1[10],str2[10],str3[20]; + clrscr(); + re: + printf(" +Enter choice=>"); + printf(" + 1:string len. + 2:string copy + 3:string +cmp. + 4:string cat. + 5:string rev."); + printf(" + 6:for exit=>"); + scanf("%d",&c);switch(c) + { + case 1: + printf("Enter the string=>"); + scanf("%s",&str1); + printf("string length=>%d +",STRLEN(str1)); + break; + case 2: + printf(" +Enter the string=>"); + scanf("%s",str1); + STRCPY(str2,str1); + printf("copied string=>"); + puts(str2); + break; + case 3: + printf("Enter two string=>"); + scanf("%s",&str1); + scanf("%s",&str2); + if(STRCMP(str2,str1)) + printf("string is equal"); + else + printf("String is not equal"); + break; + case 4: + printf("Enter two string=>"); + scanf("%s",str1); + scanf("%s",str2); + STRCAT(str3,str2,str1); + puts(str3); + break; + case 5: + printf("Enter the string=>"); + scanf("%s",str1); + STRREV(str1); + printf("Reverse stringis=>"); + puts(str1); + break; + default: + goto end; + } + goto re; +end: +getch(); +} +int STRLEN(char *s) +{ + int i=0; + while(*s!=NULL) + { + i++; + s++; + } + return i; +} +int STRCPY(char *s2,char *s1) +{ + while(*s1!=NULL) + { + *s2=*s1; + s2++; + s1++; + } + *s2=NULL; + return 1; +} +int STRCMP(char *s2,char *s1) +{ + int i=0,len1,len2; + len1=strlen(s1); + len2=strlen(s2); + if(len1==len2) + { + while(*s2==*s1 && *s2 != NULL && *s1!=NULL) + { + i++; + s1++; + s2++; + } + if(i==len1) + return 1; + else + return 0; + } + else + { + return 0; + } +} +int STRREV(char *s) +{ + int len; + char *s1; + char *ptr; + len=strlen(s); + s1=(char *)malloc(sizeof(char)); + strcpy(s1,s); + ptr=s1+len-1; + while(*s!=NULL) + { + *s=*ptr; + ptr--; + s++; + s1++; + } + *s=NULL; + return 1; +} +int STRCAT(char *s3,char *s2,char *s1) +{ + while(*s1!=NULL) + { + *s3=*s1; + s3++; + s1++; + } + s3++; + while(*s2!=NULL) + { + *s3=*s2; + s3++; + s2++; + } + *s3=NULL; + return 1; +} diff --git a/c++/Others/Structure.cpp b/c++/Others/Structure.cpp new file mode 100644 index 0000000..f7f0c71 --- /dev/null +++ b/c++/Others/Structure.cpp @@ -0,0 +1,36 @@ +Structure + +#include +#include +#include +#include + +typedef struct +{ + char name[6]; + int roll; +}student; +void main() +{ + student *p; + int n,i,temp; + FILE *k; + k=fopen("k.txt","w"); + printf("enter the numbe of students "); + scanf("%d",&n); + p=(student *)malloc(n*sizeof(student)); + for(i=0;iname); + printf("enter the roll number of student %d ",i+1); + scanf("%d",&(p+i)->roll); + } + for(i=0;iname); + printf("\n roll number of student %d is %d",i+1,(p+i)->roll); + } + getch(); + fclose(k); +} diff --git a/c++/Others/Student.cpp b/c++/Others/Student.cpp new file mode 100644 index 0000000..a7f39d3 --- /dev/null +++ b/c++/Others/Student.cpp @@ -0,0 +1,147 @@ +Student + +#include + +#define NUM_TEST 10 +#define NUM_STUDENTS 4 + +int test_grades [NUM_STUDENTS][NUM_TEST]; + +void enter_Grade() +{ + + int student, + test, + more=1, + grade; + + char yorn; + + cout << "\nenter a test grade\n"; + + while(more) + { + cout <<"\Student #"; + cin>>student; + cin.ignore(80,'\n'); + + cout << "\ntest #"; + cin>>test; + cin.ignore(80,'\n'); + + cout << "\ngrade #"; + cin>>grade; + cin.ignore(80,'\n'); + + test_grades[student-1][test-1] =grade; + + cout << "\nanother grade?"; + cin >>yorn; + cin.ignore(80,'\n'); + + if (yorn=='n') + more=0; + } +} + +void test_Avarege() +{ + int student=0, + anotherA=1, + testdid, + testNum, + Total; + + while(anotherA) + { + student=0; + Total=0; + testdid=0; + + cout << "\nTest Avarege\n\n"; + + cout << "\nNumber of the Student"; + cin >>student; + + for (testNum=0; testNum<=3; testNum++) + { + if (test_grades[student-1][testNum]) + { + testdid++; + Total+= test_grades[student-1][testNum]; + + cout << "\nTest #: "<>anotherA; + } + return; +} +get_Help() + +{ + cout << "\nThank you for enter this program. This is that way it works:"; + + cout << "\n\n1st Option, Enter Grade:"; + cout << "\nIf you choose this option you will be able to enter a gradeto a "; + cout << "\ndisere student, just remenber that is only 4 students"; + + cout << "\n\n2nd option, Test Avarege: "; + cout << "\nif you choose this option you will be anle to see the overroll "; + cout << "\navarege of the student that you chose"; + + cout << "\n\n3er option, Help:"; + cout << "\nif you chose this optionthe user will be able to see the insatruction"; + cout << "\nabout how this program works"; + + cout << "\n\n4th option, Exit"; + cout << "\nif you chosse this option the user will be able to exit the program"; + cout << "\nI hope you like what i did"; + return 0; +} + +int main() +{ + int option=0; + int hold; + + while (option!=4) + { + while ((option<1)||(option>4)) + { + + cout << "\nWelcome to my 3th program by Cecilio O. Uribe"; + cout << "\nChose any option follow by the enter key\n\n"; + cout << "\n1. Enter Grade"; + cout << "\n2. Test Avarege"; + cout << "\n3. Help"; + cout << "\n4. Exit\n\n"; + cin >> option; + } + if(option==1) + { + enter_Grade(); + option=0; + } + if(option==2) + { + test_Avarege(); + option=0; + } + if(option==3) + { + get_Help(); + option=0; + } + + } + cout << "LATER!"; + cin >> hold; + + return 0; +} diff --git a/c++/Others/Telephone.cpp b/c++/Others/Telephone.cpp new file mode 100644 index 0000000..8ca99df --- /dev/null +++ b/c++/Others/Telephone.cpp @@ -0,0 +1,204 @@ +Telephone + +#include +#include +main() +{ + FILE *t,*p; + char another,choice; + struct telephone + { + char name[30]; + long int code; + long int number; + }; + struct telephone data; + char custname[30]; + long int n; + long int recsize; + + t=fopen("TELEPHONE.DAT","rb+"); + if(t==NULL) + { + t=fopen("TELEPHONE.DAT","wb+"); + if(t==NULL) + { + printf("The File can't open\n"); + exit(); + } + } + printf(" TELEPHONE DIRECTORY \n"); + printf(" ******************* \n"); + + recsize=sizeof(data); + + while(1) + { + printf("\n\n"); + printf("1.Add Records\n"); + printf("2.List Records\n"); + printf("3.Modify Records\n"); + printf("4.Finding Number\n"); + printf("5.Finding Name\n"); + printf("6.Delete Records\n"); + printf("0.Exit\n"); + printf("Your Choice:"); + + fflush(stdin); + choice=getche(); + + switch(choice) + { + case '1': + + fseek(t,0,SEEK_END); + + another='y'; + + while(another=='y') + { + printf("\nEnter Customer name,Code number and Telephone number\n"); + scanf("%s %ld %ld",data.name,&data.code,&data.number); + fwrite(&data,recsize,1,t); + + printf("Add another data(y/n):"); + fflush(stdin); + another=getche(); + printf("\n"); + } + break; + + case '2': + + rewind(t); + printf("\n"); + printf("---------------------------------------------\n"); + printf("| CUSTOMER | CODE | TELEPHONE |\n"); + printf("---------------------------------------------\n"); + rewind(t); + + while(fread(&data,recsize,1,t)==1) + + printf("| %-18s %-2ld %12ld |\n\n",data.name,data.code,data.number); + printf("--------------------------------------------\n"); + getch(); + + + printf("\n"); + break; + + case '3': + another='y'; + while(another=='y') + { + printf("\nEnter name of customer to modify:"); + scanf("%s",custname); + rewind(t); + while(fread(&data,recsize,1,t)==1) + { + if(strcmp(data.name,custname)==0) + { + printf("\nEnter new name,code and telephone number\n"); + scanf("%s %ld &ld",data.name,&data.code,&data.number); + + fseek(t,-recsize,SEEK_CUR); + fwrite(&data,recsize,1,t); + break; + } + } + printf("Modify another record(y/n):"); + fflush(stdin); + another=getche(); + printf("\n"); + } + + break; + + + case '4': + + another='y'; + while(another=='y') + { + printf("\nEnter name of customer:"); + scanf("%s",custname); + + rewind(t); + while(fread(&data,recsize,1,t)==1) + { + if(strcmp(data.name,custname)==0) + { + printf("Telephone Number=%ld %ld\n",data.code,data.number); + getch(); + } + } + printf("Find another number(y/n)? "); + fflush(stdin); + another=getche(); + printf("\n"); + } + break; + + case '5': + + another='y'; + while(another=='y') + { + printf("\nEnter number of customer:"); + scanf("%ld",&n); + + rewind(t); + while(fread(&data,recsize,1,t)==1) + { + if(data.number==n) + { + printf("The Name is %s\n",data.name); + getch(); + } + } + printf("Find another name(y/n)? "); + fflush(stdin); + another=getche(); + printf("\n"); + } + break; + + case '6': + + another='y'; + while(another=='y') + { + printf("\nEnter name of customer to delete:"); + scanf("%s",custname); + + p=fopen("TEMP.DAT","wb"); + + rewind(t); + while(fread(&data,recsize,1,t)==1) + { + if(strcmp(data.name,custname)!=0) + fwrite(&data,recsize,1,p); + } + fclose(t); + fclose(p); + + remove("TELEPHONE.DAT"); + rename("TEMP.DAT","TELEPHONE.DAT"); + + t=fopen("TELEPHONE","rb+"); + + printf("Delete another record(y/n):"); + fflush(stdin); + another=getche(); + } + break; + + + case '0': + + printf("\n"); + fclose(t); + exit(); + } + } + } diff --git a/c++/Others/TestAvlTree.cpp - Test program for AVL trees.cpp b/c++/Others/TestAvlTree.cpp - Test program for AVL trees.cpp new file mode 100644 index 0000000..f0712ce --- /dev/null +++ b/c++/Others/TestAvlTree.cpp - Test program for AVL trees.cpp @@ -0,0 +1,34 @@ +TestAvlTree.cpp - Test program for AVL trees + + #include + #include "AvlTree.h" + + // Test program + int main( ) + { + const int ITEM_NOT_FOUND = -9999; + AvlTree t( ITEM_NOT_FOUND ), t2( ITEM_NOT_FOUND ); + int NUMS = 40000; + const int GAP = 37; + int i; + + cout << "Checking... (no more output means success)" << endl; + + for( i = GAP; i != 0; i = ( i + GAP ) % NUMS ) + t.insert( i ); + + if( NUMS < 40 ) + t.printTree( ); + if( t.findMin( ) != 1 || t.findMax( ) != NUMS - 1 ) + cout << "FindMin or FindMax error!" << endl; + + t2 = t; + + for( i = 1; i < NUMS; i++ ) + if( t2.find( i ) != i ) + cout << "Find error1!" << endl; + if( t2.find( 0 ) != ITEM_NOT_FOUND ) + cout << "ITEM_NOT_FOUND failed!" << endl; + + return 0; + } diff --git a/c++/Others/TestBinaryHeap.cpp - Test program for binary heaps.cpp b/c++/Others/TestBinaryHeap.cpp - Test program for binary heaps.cpp new file mode 100644 index 0000000..0530d6c --- /dev/null +++ b/c++/Others/TestBinaryHeap.cpp - Test program for binary heaps.cpp @@ -0,0 +1,34 @@ +TestBinaryHeap.cpp - Test program for binary heaps + + #include + #include "BinaryHeap.h" + #include "dsexceptions.h" + + // Test program + int main( ) + { + int numItems = 10000; + BinaryHeap h( numItems ); + int i = 37; + int x; + + try + { + for( i = 37; i != 0; i = ( i + 37 ) % numItems ) + h.insert( i ); + for( i = 1; i < numItems; i++ ) + { + h.deleteMin( x ); + if( x != i ) + cout << "Oops! " << i << endl; + } + for( i = 37; i != 0; i = ( i + 37 ) % numItems ) + h.insert( i ); + h.insert( 0 ); + h.insert( i = 999999 ); // Should overflow + } + catch( Overflow ) + { cout << "Overflow (expected)! " << i << endl; } + + return 0; + } diff --git a/c++/Others/TestBinarySearchTree.cpp - Test program for binary search tree.cpp b/c++/Others/TestBinarySearchTree.cpp - Test program for binary search tree.cpp new file mode 100644 index 0000000..bf82138 --- /dev/null +++ b/c++/Others/TestBinarySearchTree.cpp - Test program for binary search tree.cpp @@ -0,0 +1,53 @@ +TestBinarySearchTree.cpp - Test program for binary search tree + + #include + #include "BinarySearchTree.h" + + // Test program + int main( ) + { + const int ITEM_NOT_FOUND = -9999; + BinarySearchTree t( ITEM_NOT_FOUND ); + int NUMS = 4000; + const int GAP = 37; + int i; + + cout << "Checking... (no more output means success)" << endl; + + for( i = GAP; i != 0; i = ( i + GAP ) % NUMS ) + t.insert( i ); + + for( i = 1; i < NUMS; i+= 2 ) + t.remove( i ); + + if( NUMS < 40 ) + t.printTree( ); + if( t.findMin( ) != 2 || t.findMax( ) != NUMS - 2 ) + cout << "FindMin or FindMax error!" << endl; + + for( i = 2; i < NUMS; i+=2 ) + if( t.find( i ) != i ) + cout << "Find error1!" << endl; + + for( i = 1; i < NUMS; i+=2 ) + { + if( t.find( i ) != ITEM_NOT_FOUND ) + cout << "Find error2!" << endl; + } + + BinarySearchTree t2( ITEM_NOT_FOUND ); + t2 = t; + + for( i = 2; i < NUMS; i+=2 ) + if( t2.find( i ) != i ) + cout << "Find error1!" << endl; + + for( i = 1; i < NUMS; i+=2 ) + { + if( t2.find( i ) != ITEM_NOT_FOUND ) + cout << "Find error2!" << endl; + } + + + return 0; + } diff --git a/c++/Others/TestBinomialQueue.cpp - Test program for binomial queues.cpp b/c++/Others/TestBinomialQueue.cpp - Test program for binomial queues.cpp new file mode 100644 index 0000000..e0d1f3b --- /dev/null +++ b/c++/Others/TestBinomialQueue.cpp - Test program for binomial queues.cpp @@ -0,0 +1,36 @@ +TestBinomialQueue.cpp - Test program for binomial queues + + #include "BinomialQueue.h" + #include + + int main( ) + { + int numItems = 10000; + BinomialQueue h; + BinomialQueue h1; + BinomialQueue h2; + int i = 37; + + for( i = 37; i != 0; i = ( i + 37 ) % numItems ) + if( i % 2 == 0 ) + h1.insert( i ); + else + h.insert( i ); + + h.merge( h1 ); + h2 = h; + + for( i = 1; i < numItems; i++ ) + { + + int x; + h2.deleteMin( x ); + if( x != i ) + cout << "Oops! " << i << endl; + } + + if( !h1.isEmpty( ) ) + cout << "Oops! h1 should have been empty!" << endl; + + return 0; + } diff --git a/c++/Others/TestCursorList.cpp - Test program for cursor implementation of linked lists.cpp b/c++/Others/TestCursorList.cpp - Test program for cursor implementation of linked lists.cpp new file mode 100644 index 0000000..411e343 --- /dev/null +++ b/c++/Others/TestCursorList.cpp - Test program for cursor implementation of linked lists.cpp @@ -0,0 +1,50 @@ +TestCursorList.cpp - Test program for cursor implementation of linked lists + + #include + #include "CursorList.h" + + // Simple print method + template + void printList( const List & theList ) + { + if( theList.isEmpty( ) ) + cout << "Empty list" << endl; + else + { + ListItr itr = theList.first( ); + for( ; !itr.isPastEnd( ); itr.advance( ) ) + cout << itr.retrieve( ) << " "; + } + + cout << endl; + } + + vector::CursorNode> List::cursorSpace; + + int main( ) + { + List theList; + ListItr theItr = theList.zeroth( ); + int i; + + printList( theList ); + + for( i = 0; i < 10; i++ ) + { + theList.insert( i, theItr ); + printList( theList ); + theItr.advance( ); + } + + for( i = 0; i < 10; i += 2 ) + theList.remove( i ); + + for( i = 0; i < 10; i++ ) + if( ( i % 2 == 0 ) != ( theList.find( i ).isPastEnd( ) ) ) + cout << "Find fails!" << endl; + + cout << "Finished deletions" << endl; + printList( theList ); + + return 0; + } diff --git a/c++/Others/TestDSL.cpp - Test program for determinstic skip lists.cpp b/c++/Others/TestDSL.cpp - Test program for determinstic skip lists.cpp new file mode 100644 index 0000000..93d6049 --- /dev/null +++ b/c++/Others/TestDSL.cpp - Test program for determinstic skip lists.cpp @@ -0,0 +1,32 @@ +TestDSL.cpp - Test program for determinstic skip lists + + #include + #include "DSL.h" + + // Test program + int main( ) + { + const int ITEM_NOT_FOUND = 99999999; + DSL t( ITEM_NOT_FOUND ); + int NUMS = 3900; + const int GAP = 37; + int i; + + cout << "Checking... (no more output means success)" << endl; + + for( i = GAP; i != 0; i = ( i + GAP ) % NUMS ) + t.insert( i ); + + if( NUMS < 40 ) + t.printList( ); + if( t.findMin( ) != 1 || t.findMax( ) != NUMS - 1 ) + cout << "FindMin or FindMax error!" << endl; + + for( i = 1; i < NUMS; i++ ) + if( t.find( i ) != i ) + cout << "Find error1!" << endl; + if( t.find( 0 ) != ITEM_NOT_FOUND ) + cout << "ITEM_NOT_FOUND failed!" << endl; + + return 0; + } diff --git a/c++/Others/TestFastDisjSets.cpp - Test program for disjoint s.cpp b/c++/Others/TestFastDisjSets.cpp - Test program for disjoint s.cpp new file mode 100644 index 0000000..3296622 --- /dev/null +++ b/c++/Others/TestFastDisjSets.cpp - Test program for disjoint s.cpp @@ -0,0 +1,34 @@ +TestFastDisjSets.cpp - Test program for disjoint sets algorithm + + #include + #include "DisjSets.h" + + // Test main; all finds on same output line should be identical + int main( ) + { + int numElements = 128; + int numInSameSet = 16; + + DisjSets ds( numElements ); + int set1, set2; + + for( int k = 1; k < numInSameSet; k *= 2 ) + { + for( int j = 0; j + k < numElements; j += 2 * k ) + { + set1 = ds.find( j ); + set2 = ds.find( j + k ); + ds.unionSets( set1, set2 ); + } + } + + for( int i = 0; i < numElements; i++ ) + { + cout << ds.find( i ) << "*"; + if( i % numInSameSet == numInSameSet - 1 ) + cout << endl; + } + cout << endl; + + return 0; + } diff --git a/c++/Others/TestIntCell.cpp - IntCell test program (Fig 1.9).cpp b/c++/Others/TestIntCell.cpp - IntCell test program (Fig 1.9).cpp new file mode 100644 index 0000000..20f1d9a --- /dev/null +++ b/c++/Others/TestIntCell.cpp - IntCell test program (Fig 1.9).cpp @@ -0,0 +1,14 @@ +TestIntCell.cpp - IntCell test program (Fig 1.9) + + #include + #include "IntCell.h" + + int main( ) + { + IntCell m; // Or, IntCell m( 0 ); but not IntCell m( ); + + m.write( 5 ); + cout << "Cell contents: " << m.read( ) << endl; + + return 0; + } diff --git a/c++/Others/TestLeftistHeap.cpp - Test program for leftist heaps.cpp b/c++/Others/TestLeftistHeap.cpp - Test program for leftist heaps.cpp new file mode 100644 index 0000000..d276266 --- /dev/null +++ b/c++/Others/TestLeftistHeap.cpp - Test program for leftist heaps.cpp @@ -0,0 +1,34 @@ +TestLeftistHeap.cpp - Test program for leftist heaps + + #include "LeftistHeap.h" + #include + + int main( ) + { + int numItems = 10000; + LeftistHeap h; + LeftistHeap h1; + LeftistHeap h2; + int i = 37; + + for( i = 37; i != 0; i = ( i + 37 ) % numItems ) + if( i % 2 == 0 ) + h1.insert( i ); + else + h.insert( i ); + h.merge( h1 ); + h2 = h; + + for( i = 1; i < numItems; i++ ) + { + int x; + h2.deleteMin( x ); + if( x != i ) + cout << "Oops! " << i << endl; + } + + if( !h1.isEmpty( ) ) + cout << "Oops! h1 should have been empty!" << endl; + + return 0; + } diff --git a/c++/Others/TestLinkedList.cpp - Test program for linked list package.cpp b/c++/Others/TestLinkedList.cpp - Test program for linked list package.cpp new file mode 100644 index 0000000..ce09e02 --- /dev/null +++ b/c++/Others/TestLinkedList.cpp - Test program for linked list package.cpp @@ -0,0 +1,53 @@ +TestLinkedList.cpp - Test program for linked list package + + #include + #include "LinkedList.h" + + // Simple print method + template + void printList( const List & theList ) + { + if( theList.isEmpty( ) ) + cout << "Empty list" << endl; + else + { + ListItr itr = theList.first( ); + for( ; !itr.isPastEnd( ); itr.advance( ) ) + cout << itr.retrieve( ) << " "; + } + + cout << endl; + } + + + int main( ) + { + List theList; + ListItr theItr = theList.zeroth( ); + int i; + + printList( theList ); + + for( i = 0; i < 10; i++ ) + { + theList.insert( i, theItr ); + printList( theList ); + theItr.advance( ); + } + + for( i = 0; i < 10; i += 2 ) + theList.remove( i ); + + for( i = 0; i < 10; i++ ) + if( ( i % 2 == 0 ) != ( theList.find( i ).isPastEnd( ) ) ) + cout << "Find fails!" << endl; + + cout << "Finished deletions" << endl; + printList( theList ); + + List list2; + list2 = theList; + printList( list2 ); + + return 0; + } diff --git a/c++/Others/TestMemoryCell.cpp - MemoryCell test program (Fig 1.22).cpp b/c++/Others/TestMemoryCell.cpp - MemoryCell test program (Fig 1.22).cpp new file mode 100644 index 0000000..35e1e6d --- /dev/null +++ b/c++/Others/TestMemoryCell.cpp - MemoryCell test program (Fig 1.22).cpp @@ -0,0 +1,28 @@ +TestMemoryCell.cpp - MemoryCell test program (Fig 1.22) + + #include + #include "MemoryCell.h" + #include "mystring.h" + + + // OOPS: I forgot to put a + operator in the string class. + // So it's here: + + string operator+( const string & lhs, const string & rhs ) + { + string result = lhs; + return result += rhs; + + } + + int main( ) + { + MemoryCell m1; + MemoryCell m2( "hello" ); + + m1.write( 37 ); + m2.write( m2.read( ) + " world" ); + cout << m1.read( ) << endl << m2.read( ) << endl; + + return 0; + } diff --git a/c++/Others/TestQuadraticProbing.cpp - Test program for quadratic probing hash tables.cpp b/c++/Others/TestQuadraticProbing.cpp - Test program for quadratic probing hash tables.cpp new file mode 100644 index 0000000..45a1ee2 --- /dev/null +++ b/c++/Others/TestQuadraticProbing.cpp - Test program for quadratic probing hash tables.cpp @@ -0,0 +1,34 @@ +TestQuadraticProbing.cpp - Test program for quadratic probing hash tables + + #include + #include "QuadraticProbing.h" + + // Simple main + int main( ) + { + int ITEM_NOT_FOUND = -9999; + HashTable H( ITEM_NOT_FOUND ); + + const int NUMS = 4000; + const int GAP = 37; + int i; + + cout << "Checking... (no more output means success)" << endl; + + for( i = GAP; i != 0; i = ( i + GAP ) % NUMS ) + H.insert( i ); + for( i = 1; i < NUMS; i += 2 ) + H.remove( i ); + + for( i = 2; i < NUMS; i +=2 ) + if( H.find( i ) != i ) + cout << "Find fails " << i << endl; + + for( i = 1; i < NUMS; i += 2 ) + { + if( H.find( i ) != ITEM_NOT_FOUND ) + cout << "OOPS!!! " << i << endl; + } + + return 0; + } diff --git a/c++/Others/TestQueueAr.cpp - Test program for queues.cpp b/c++/Others/TestQueueAr.cpp - Test program for queues.cpp new file mode 100644 index 0000000..b4cf39b --- /dev/null +++ b/c++/Others/TestQueueAr.cpp - Test program for queues.cpp @@ -0,0 +1,20 @@ +TestQueueAr.cpp - Test program for queues + + #include + #include "QueueAr.h" + + int main( ) + { + Queue q; + + for( int j = 0; j < 5; j++ ) + { + for( int i = 0; i < 5; i++ ) + q.enqueue( i ); + + while( !q.isEmpty( ) ) + cout << q.dequeue( ) << endl; + } + + return 0; + } diff --git a/c++/Others/TestRandom.cpp - Test program for random number class.cpp b/c++/Others/TestRandom.cpp - Test program for random number class.cpp new file mode 100644 index 0000000..6968e8d --- /dev/null +++ b/c++/Others/TestRandom.cpp - Test program for random number class.cpp @@ -0,0 +1,15 @@ +TestRandom.cpp - Test program for random number class + + #include "Random.h" + #include + + // Test program + int main( ) + { + Random r( 1 ); + + for( int i = 0; i < 20; i++ ) + cout << r.randomInt( ) << endl; + + return 0; + } diff --git a/c++/Others/TestSeparateChaining.cpp - Test program for separate chaining hash tables.cpp b/c++/Others/TestSeparateChaining.cpp - Test program for separate chaining hash tables.cpp new file mode 100644 index 0000000..287e51a --- /dev/null +++ b/c++/Others/TestSeparateChaining.cpp - Test program for separate chaining hash tables.cpp @@ -0,0 +1,34 @@ +TestSeparateChaining.cpp - Test program for separate chaining hash tables + + #include + #include "SeparateChaining.h" + + // Simple main + int main( ) + { + int ITEM_NOT_FOUND = -9999; + HashTable H( ITEM_NOT_FOUND ); + + const int NUMS = 4000; + const int GAP = 37; + int i; + + cout << "Checking... (no more output means success)" << endl; + + for( i = GAP; i != 0; i = ( i + GAP ) % NUMS ) + H.insert( i ); + for( i = 1; i < NUMS; i += 2 ) + H.remove( i ); + + for( i = 2; i < NUMS; i += 2 ) + if( H.find( i ) != i ) + cout << "Find fails " << i << endl; + + for( i = 1; i < NUMS; i += 2 ) + { + if( H.find( i ) != ITEM_NOT_FOUND ) + cout << "OOPS!!! " << i << endl; + } + + return 0; + } diff --git a/c++/Others/TestSort.cpp - Test program for sorting and selection routines.cpp b/c++/Others/TestSort.cpp - Test program for sorting and selection routines.cpp new file mode 100644 index 0000000..6ba7393 --- /dev/null +++ b/c++/Others/TestSort.cpp - Test program for sorting and selection routines.cpp @@ -0,0 +1,67 @@ +TestSort.cpp - Test program for sorting and selection routines + + #include + #include "Sort.h" + #include "vector.h" + #include "Random.h" + + + void checkSort( const vector & a ) + { + for( int i = 0; i < a.size( ); i++ ) + if( a[ i ] != i ) + cout << "Error at " << i << endl; + cout << "Finished checksort" << endl; + } + + + void permute( vector & a ) + { + static Random r; + + for( int j = 1; j < a.size( ); j++ ) + swap( a[ j ], a[ r.randomInt( 0, j ) ] ); + } + + + int main( ) + { + const int NUM_ITEMS = 1000; + + vector a( NUM_ITEMS ); + for( int i = 0; i < a.size( ); i++ ) + a[ i ] = i; + + for( int theSeed = 0; theSeed < 20; theSeed++ ) + { + permute( a ); + insertionSort( a ); + checkSort( a ); + + permute( a ); + heapsort( a ); + checkSort( a ); + + permute( a ); + shellsort( a ); + checkSort( a ); + + permute( a ); + mergeSort( a ); + checkSort( a ); + + permute( a ); + quicksort( a ); + checkSort( a ); + + permute( a ); + largeObjectSort( a ); + checkSort( a ); + + permute( a ); + quickSelect( a, NUM_ITEMS / 2 ); + cout << a[ NUM_ITEMS / 2 - 1 ] << " " << NUM_ITEMS / 2 << endl; + } + + return 0; + } diff --git a/c++/Others/TestStackAr.cpp - Test program for (array-based) s.cpp b/c++/Others/TestStackAr.cpp - Test program for (array-based) s.cpp new file mode 100644 index 0000000..bbde25b --- /dev/null +++ b/c++/Others/TestStackAr.cpp - Test program for (array-based) s.cpp @@ -0,0 +1,17 @@ +TestStackAr.cpp - Test program for (array-based) stacks + + #include + #include "StackAr.h" + + int main( ) + { + Stack s; + + for( int i = 0; i < 10; i++ ) + s.push( i ); + + while( !s.isEmpty( ) ) + cout << s.topAndPop( ) << endl; + + return 0; + } diff --git a/c++/Others/TestStackLi.cpp - Test program for (list-based) stacks.cpp b/c++/Others/TestStackLi.cpp - Test program for (list-based) stacks.cpp new file mode 100644 index 0000000..d64bcdc --- /dev/null +++ b/c++/Others/TestStackLi.cpp - Test program for (list-based) stacks.cpp @@ -0,0 +1,24 @@ +TestStackLi.cpp - Test program for (list-based) stacks + + #include "StackLi.h" + #include + + int main( ) + { + Stack s, s1; + + for( int i = 0; i < 10; i++ ) + s.push( i ); + + s1 = s; + + cout << "s" << endl; + while( !s.isEmpty( ) ) + cout << s.topAndPop( ) << endl; + + cout << endl << "s1" << endl; + while( !s1.isEmpty( ) ) + cout << s1.topAndPop( ) << endl; + + return 0; + } diff --git a/c++/Others/This example show how to declare and use an array of an object.cpp b/c++/Others/This example show how to declare and use an array of an object.cpp new file mode 100644 index 0000000..b090cb1 --- /dev/null +++ b/c++/Others/This example show how to declare and use an array of an object.cpp @@ -0,0 +1,86 @@ +This example show how to declare and use an array of an object + +#include + +struct Paper +{ +public: + void GetDimensions(); + void Properties(); +private: + double Perimeter() const; + double Area() const; + double Height; + double Width; +}; + +void Paper::GetDimensions() +{ + cout << "Enter the dimensions of the label\n"; + cout << "Height: "; + cin >> Height; + cout << "Width: "; + cin >> Width; +} + +void Paper::Properties() +{ + cout << "\n\tHeight = " << Height; + cout << "\n\tWidth = " << Width; + cout << "\n\tPerimeter = " << Perimeter(); + cout << "\n\tArea = " << Area(); + cout << "\n\n"; +} + +double Paper::Perimeter() const +{ + return 2 + (Height * Width); +} + +double Paper::Area() const +{ + return Height * Width; +} + +void main() +{ + int Samples; + Paper Label[100]; + + cout << "How many sample labels do you want? "; + cin >> Samples; + + for(int i = 0; i < Samples; ++i) + Label[i].GetDimensions(); + + cout << "\n\nHere are the characteristics of your labels\n"; + for(int j = 0; j < Samples; ++j) + { + cout << "Label No. " << j; + Label[j].Properties(); + } +} + +Here is an example of running the program: + +How many sample labels do you want? 2 +Enter the dimensions of the label +Height: 3.25 +Width: 3.25 +Enter the dimensions of the label +Height: 2.15 +Width: 4.55 + + +Here are the characteristics of your labels +Label No. 0 + Height = 3.25 + Width = 3.25 + Perimeter = 12.5625 + Area = 10.5625 + +Label No. 1 + Height = 2.15 + Width = 4.55 + Perimeter = 11.7825 + Area = 9.7825 diff --git a/c++/Others/This is a program of matrix capable of doing sever.cpp b/c++/Others/This is a program of matrix capable of doing sever.cpp new file mode 100644 index 0000000..a89a1de --- /dev/null +++ b/c++/Others/This is a program of matrix capable of doing sever.cpp @@ -0,0 +1,239 @@ +This is a program of matrix capable of doing several works with two matrices. +It can add, subtract, multiply of two matrices and +if user wants to see the input entered in two matrices he can also see. It +provides the facility to user to do again some work on another matrix +without running the program twice. + +Code : +#include +#include +#include +#include +#define sk 100 +class matrix +{ +public: +int i,j,k,sum,r1,r2,c1,c2; +int m1[sk][sk],m2[sk][sk]; +char reply; +void getin(void); +void mply(void); +void add(void); +void minus(void); +void read(void); +void input(void); +}; +void matrix::getin() +{ +cout<<" + + WELCOME TO SOLUTION OF TWO MATRICRES "; +cout<<" + -------------------------------------"; + +cout<<" + + YOU CAN CALCULATE UPTO A LIMIT OF MATRIX 100 * 100 "; +cout<<" + + YOU CAN DO THE FOLLOWING : + + ADDITION + +SUBTRACTION +"; +cout<<" + MULTIPLICATION AND + READ ONLY "; +cout<<" + + + DO YOU WANT TO CONTINUE [Y/N] : "; +cin >>reply; +if(reply=='y'||reply=='Y') +{ +cout<<" + + Enter the number of rows and columns of matrix 1 : "; +cin>>r1>>c1; +cout<<" + Enter the value of matrix 1 : "<>m1[i][j]; +cout<<" + Enter the number of rows and columns of matrix 2 : "; +cin>>r2>>c2; +cout<<" + Enter the value of matrix 2 : "<>m2[i][j]; +} +else exit(0); +} +void matrix::mply() +{ +cout<<" + THE RESULT AFTER MULTIPLICATION IS : +"; +if(c1==r2) +{ +for(i=0;i>ans; +switch(ans) +{ +case 1 : m.add(); break; +case 2 : m.minus(); break; +case 3 : m.mply(); break; +case 4 : m.read(); break; +case 5 : goto exit ; +default : +{ +cout<<" + INVALID ENTRY + ENTER YOUR CHOICE AGAIN : "; +goto repeat; +} +} +cout<<" + DO YOU WANT TO DO IT FOR ANOTHER TIME [Y/N] : "; +cin>>response; +if(response=='y'||response=='Y') +{ +wrong: +cout<<" + Enter your choice in number +"; +cout<<" + 1.FOR Same matrix + 2.FOR Another matrix + + "; +cin>>option; +switch(option) +{ +case 1 : goto again; +case 2 : goto start; +default: cout<<" + + INVALID ENTRY "; goto wrong; +} +} +exit : +getch(); +} + + diff --git a/c++/Others/This is a very simple quiz with Ten questions in it and also is very easy to use.cpp b/c++/Others/This is a very simple quiz with Ten questions in it and also is very easy to use.cpp new file mode 100644 index 0000000..c0965d0 --- /dev/null +++ b/c++/Others/This is a very simple quiz with Ten questions in it and also is very easy to use.cpp @@ -0,0 +1,248 @@ +This is a very simple quiz with Ten questions in it and also is very easy to use. +This is mainly made for extreme begginers in C++. + +#include +#include + +void main() +{ + clrscr(); + int x,y,z; + x=y=z=0; + char ch1[100],ch2,ch3,ch4,ch5,ch6,ch7,ch8,ch9,ch10,ch11; + cout<<" Guest Enter Your Name +"; + cin>>ch1; + clrscr(); + cout<<" Welcome "<>ch2; + if(ch2=='a') + { + x=x+10; + cout<<"Good Job. +Your score is "<>ch2; + if(ch2=='c') + { + x=x+10; + cout<<"Good Job. +Your score is "<>ch2; + if(ch2=='b') + { + x=x+10; + cout<<"Good Job. +Your score is "<>ch2; + if(ch2=='b') + { + x=x+10; + cout<<" +Your score is "<>ch2; + if(ch2=='a') + { + x=x+10; + cout<<" +Your score is "<>ch2; + if(ch2=='a') + { + x=x+10; + cout<<" +Your score is "<>ch2; + if(ch2=='c') + { + x=x+10; + cout<<" +Your score is "<>ch2; + if(ch2=='b') + { + x=x+10; + cout<<" +Your score is "<>ch2; + if(ch2=='a') + { + x=x+10; + cout<<" +Your score is "<>ch2; + if(ch2=='c') + { + x=x+10; + cout<<" +Your score is "< +#include +#include +#include +#include +#include + + +class SHOP +{ + +private : + int z,P1,P2,P3,P4,P5,P6,P7,P8,totalP; + int S1,S2,S3,S4,S5,S6,S7,S8,S9,totalS; + int D1,D2,D3,D4,D5,D6,D7,D8,totalD; + int s1,s2,s3,s4,s5,s6,s7,s8,totals; + int p1,p2,p3,p4,p5,p6,p7,p8,totalp; + +public : + void FRONT() + { + totals=totalp=totalP=totalS=0; + P1=P2=P3=P4=P5=P6=P7=P8=0; + S1=S2=S3=S4=S5=S6=S7=S8=0; + p1=p2=p3=p4=p5=p6=p7=p8=0; + s1=s2=s3=s4=s5=s6=s7=s8=0; + z=0; + +//MAIN +SCREEN******************************************************************** + +switching: + + { + int gdriver = DETECT, gmode; + initgraph(&gdriver, &gmode, "C:\TC\BGI"); + cleardevice(); + setcolor(getmaxcolor()); + textcolor(getmaxcolor()); + settextjustify(CENTER_TEXT, CENTER_TEXT); + settextstyle(10,0,4); + outtextxy(320,25,"ZINNIA DISTRIBUTOR"); + setcolor(13); + rectangle(0,0,639,70); + rectangle(2,2,637,68); + rectangle(4,4,635,66); + rectangle(220,140,420,340); + rectangle(223,143,417,337); + gotoxy(33,12); + cout<<"1) PURCHASE"; + gotoxy(33,14); + cout<<"2) SALES"; + gotoxy(33,16); + cout<<"3) REPORT"; + gotoxy(33,18); + cout<<"4) EXIT"; + gotoxy(32,28); + cout<<"YOUR CHOICE IS : "; + rectangle(200,420,440,460); + rectangle(202,422,438,458); + setfillstyle(10,13); + floodfill(1,75,13); + cin>>z; + cleardevice(); + +switch(z) + + { +case 1: +//PURCHASE*************************************************************** + { + +cout<<" +_________________________________________________________________ +_______________"; + cout<<" + + SNO ITEM RATE QTY +AMOUNT "; + +cout<<" +_________________________________________________________________ +_______________"; + cout<<" + + 1] WHOLE 55 "; + cout<<" + + 2] PRE-CUT 60 "; + cout<<" + + 3] ASSORTED 35 "; + cout<<" + + 4] SOUP 10 "; + cout<<" + + 5] WINGS 55 "; + cout<<" + + 6] GIZZARD 45 "; + cout<<" + + 7] TWO LEGS 90 "; + cout<<" + + 8] FOUR DRUMS 30 "; + +cout<<" + +_______________________________________________________________ +_________________"; + cout<<" + + + TOTAL -----> +Rs."; + +cout<<" + +_______________________________________________________________ +_________________"; + rectangle(0,0,639,479); + rectangle(530,400,635,440); + settextstyle(10,0,4); + outtextxy(210,410,"PURCHASE"); + gotoxy(62,8); + cin>>P1; + p1=p1+P1; + gotoxy(62,10); + cin>>P2; + p2=p2+P2; + gotoxy(62,12); + cin>>P3; + p3=p3+P3; + gotoxy(62,14); + cin>>P4; + p4=p4+P4; + gotoxy(62,16); + cin>>P5; + p5=p5+P5; + gotoxy(62,18); + cin>>P6; + p6=p6+P6; + gotoxy(62,20); + cin>>P7; + p7=p7+P7; + gotoxy(62,22); + cin>>P8; + p8=p8+P8; + gotoxy(75,8); + D1=P1*55; + cout< +Rs."; + +cout<<" + +_______________________________________________________________ +_________________"; + rectangle(0,0,639,479); + rectangle(530,400,635,440); + settextstyle(10,0,4); + outtextxy(210,410,"SALES"); + gotoxy(62,8); + cin>>S1; + s1=s1+S1; + gotoxy(62,10); + cin>>S2; + s2=s2+S2; + gotoxy(62,12); + cin>>S3; + s3=s3+S3; + gotoxy(62,14); + cin>>S4; + s4=s4+S4; + gotoxy(62,16); + cin>>S5; + s5=s5+S5; + gotoxy(62,18); + cin>>S6; + s6=s6+S6; + gotoxy(62,20); + cin>>S7; + s7=s7+S7; + gotoxy(62,22); + cin>>S8; + s8=s8+S8; + gotoxy(75,8); + D1=S1*60; + cout< + +#include + +#include + + + +int main(void) + +{ + + HENV hEnv = NULL; +// Env Handle from SQLAllocEnv() + + HDBC hDBC = NULL; +// Connection handle + + HSTMT hStmt = NULL; +// Statement handle + + UCHAR szDSN[SQL_MAX_DSN_LENGTH] = +"db97"; // Data Source Name buffer +UCHAR* szUID = NULL; +// User ID buffer + + UCHAR* szPasswd = NULL; +// Password buffer + + UCHAR szModel[128]; +// Model buffer + + SDWORD cbModel; +// Model buffer bytes recieved + + UCHAR szSqlStr[] = "Select Model From +Makes Where Make='Vauxhall'"; // SQL string + + RETCODE retcode; +// Return code + + + + // Allocate memory for ODBC Environment handle + + SQLAllocEnv (&hEnv); + + + + // Allocate memory for the connection handle + + SQLAllocConnect (hEnv, &hDBC); + + + + // Connect to the data source "db97" using userid and +password. + + retcode = SQLConnect (hDBC, szDSN, SQL_NTS, szUID, +SQL_NTS, szPasswd, SQL_NTS); + + + + if (retcode == SQL_SUCCESS || retcode == +SQL_SUCCESS_WITH_INFO) + + { + + // Allocate memory for the statement +handle + + retcode = SQLAllocStmt (hDBC, &hStmt); + + + + // Prepare the SQL statement by +assigning +it to the statement handle + + retcode = SQLPrepare (hStmt, szSqlStr, +sizeof (szSqlStr)); + + + + // Execute the SQL statement handle + + retcode = SQLExecute (hStmt); + + + + // Project only column 1 which is the +models + + SQLBindCol (hStmt, 1, SQL_C_CHAR, +szModel, +sizeof(szModel), &cbModel); + + + + // Get row of data from the result set +defined above in the statement + + retcode = SQLFetch (hStmt); + + + + while (retcode == SQL_SUCCESS || +retcode +== SQL_SUCCESS_WITH_INFO) + + { + + printf (" %s +", +szModel); // Print row +(model) + + retcode = SQLFetch +(hStmt); // Fetch next row from result +set + + } + + + + // Free the allocated statement handle + + SQLFreeStmt (hStmt, SQL_DROP); + + + + // Disconnect from datasource + + SQLDisconnect (hDBC); + + } + + + + // Free the allocated connection handle + + SQLFreeConnect (hDBC); + + + + // Free the allocated ODBC environment handle + + SQLFreeEnv (hEnv); + + return 0; + +} diff --git a/c++/Others/This program finds the locations of placing n queens in a nn chessboard.cpp b/c++/Others/This program finds the locations of placing n queens in a nn chessboard.cpp new file mode 100644 index 0000000..6a617a0 --- /dev/null +++ b/c++/Others/This program finds the locations of placing n queens in a nn chessboard.cpp @@ -0,0 +1,68 @@ +This program finds the locations of placing n queens in a n*n chessboard +so that none attack any other + +Code : +#include +#include +#include +#include +#include +class queen +{ int n,x[100]; + public: + queen(); + void nqueen(int,int); + int place(int,int); +}; +queen::queen() +{ + int k=1; + textcolor(GREEN); + cprintf(" +Enter the number of queens:"); + cin>>n; + nqueen( k, n); +} +void queen::nqueen(int k,int n) +{ + for(int i=1;i<=n;i++) + { + if(place(k,i)) + { + x[k]=i; + clrscr(); + if(k==n) + { + for(int j=1;j<=n;j++) + {textcolor(x[j]); + gotoxy(1,j); + cprintf(" +queen %d : %d",j,x[j]); + } + getch(); + + break; + } + else + nqueen(k+1,n); + } + } + return; +} +int queen::place(int k,int i) +{ + int j; + for(j=1;j<=k;j++) + { + if((x[j]==i)||(abs(x[j]-i)==abs(j-k))) + return 0; + } + return 1; +} +void main() +{ + clrscr(); + queen q; +} + + diff --git a/c++/Others/This program illustrates a simple if-else statement..cpp b/c++/Others/This program illustrates a simple if-else statement..cpp new file mode 100644 index 0000000..915391f --- /dev/null +++ b/c++/Others/This program illustrates a simple if-else statement..cpp @@ -0,0 +1,22 @@ +This program illustrates a simple if-else statement. + +#include +using namespace std; + +int main() +{ + int a, b; + + cout << "Enter first number: "; + cin >> a; + cout << "Enter second number: "; + cin >> b; + + if(a < b) + cout << "First number is less than second.\n"; + else + cout << "First number is greater than or equal to second.\n"; + + return 0; + +} diff --git a/c++/Others/This program in CPP, demonstrates the array implem.cpp b/c++/Others/This program in CPP, demonstrates the array implem.cpp new file mode 100644 index 0000000..85b0f8e --- /dev/null +++ b/c++/Others/This program in CPP, demonstrates the array implem.cpp @@ -0,0 +1,126 @@ +This program in CPP, demonstrates the array implementation of Circular Queue. + +Code: + +#include +#include +#include +#include + +// Defining class CQUEUE +class cqueue + { + int q[10],num,front,rear; + public : + cqueue(); + void insert(); + void remove(); + void menu(); + void display(); + }; + +cqueue :: cqueue() + { + front=rear=0; + } + +void cqueue :: insert() + { + if(((rear+1)%10)==front) + { + cout<<"Queue is full +"; + } + else + { + cout<<"Please enter a number : +"; + cin>> + q[rear]; + rear=(rear+1)%10; + } + } + +void cqueue :: remove() + { + if(rear==front) + { + cout<<"Queue is empty +"; + } + else + { + int num=q[front]; + cout<<"You deleted "<>ch; + switch (ch) + { + case 1 : insert(); + break; + case 2 : remove(); + break; + case 3 : display(); + break; + case 0 : exit(0); + } + } + } + + +void main() + { + cout<<"Program to demonstrate Circular Queue +"; + cqueue q1; + q1.menu(); + } + + diff --git a/c++/Others/This virtual calender shows current month and user can navigate.cpp b/c++/Others/This virtual calender shows current month and user can navigate.cpp new file mode 100644 index 0000000..7bf0d9b --- /dev/null +++ b/c++/Others/This virtual calender shows current month and user can navigate.cpp @@ -0,0 +1,226 @@ +This virtual calender shows current month and user can navigate +through previous or next month / year using arrow keys + +Code : +#include "conio.h" +#include "stdlib.h" +#include "dos.h" +#include "string.h" +#include "stdio.h" + +void draw(int, int); //DRAWS BOX WITH MONTH & YEAR IN HEADER +void show_time(); //DISPLAYS CURRENT TIME IN FOOTER OF BOX +void print_cal( int, int); //PRINTS DATES WITHIN BOX +int getkey(); //SCANS USER KEY AND RETUEN ITS SCAN CODE +int first_day( int, int ); //DETEMINES FIRST DAY OF MONTH +int today; + +void main() +{ + int year, month; + char ch; + struct date d; + getdate(&d); //RETURNS CURRENT DATE + year = d.da_year; + month = d.da_mon - 1; + today = d.da_day - 1; //GET CURRENT DATE + print_cal(year, month); //PRINTS CALENDER OF CURRENT MONTH + flushall(); + while((ch = getkey()) != 1) //KEEP TRACK OF KEYS UNTILL 'ESC' PRESSED + { + switch(ch) + { + case 72: year++; //UP ARROW KEY + break; + case 80: year--; //DOWN ARROW KEY + break; + + case 77: month++; //RIGHT ARROW KEY + if(month > 11) + { + month = 0; + year++; + } + break; + case 75: month--; //LEFT ARROW KEY + if(month < 0) + { + month = 11; + year--; + } + break; + } + print_cal(year, month); //PRINTS CALENDER OF CHANGED MONTH OR YEAR + } +} +void show_time() +{ + struct time t; + while(!kbhit()) + { + textcolor(YELLOW); + gettime(&t); //GET CURRENT TIME + gotoxy(22,2); + if(t.ti_hour < 13) + printf(" CURRENT TIME => %2d:%02d:%02d AM",t.ti_hour, t.ti_min, +t.ti_sec); + else + { + t.ti_hour -= 12; + printf(" CURRENT TIME => %2d:%02d:%02d PM",t.ti_hour, t.ti_min, +t.ti_sec); + } + + delay(1000); + } +} + +int first_day(int year, int month) //DETEMINES FIRST DAY OF MONTH +{ + int mdays[] = { 0, 31, 59, 90, 120, 151, 181, 212, 243, 273, 304, +334}; + int lpyear = ((year-1900)/4) + ((year-1900)/400) - ((year-1900)/100); + long unsigned days = ((year-1900)*365) + lpyear + mdays[month]; + return days % 7; +} +int getkey() //SCANS USER KEY AND RETURN ITS SCAN CODE +{ + union REGS i,o; + while(!kbhit()) + ; + i.h.ah = 0; + int86(22,&i,&o); + return(o.h.ah); +} +void draw(int year, int month) //DRAWS BOX WITH MONTH & YEAR IN HEADER +{ + char *mo[] = { "January", "Feburary", "March", "April", + "May", "June", "July", "August", "September", + "October", "November", "December" }; + char *day[] = { "SUN", "MON", "TUE", "WED", "THU", "FRI", "SAT"}; + int i, j; + int ro = 205, co = 186; //GARPH CHAR 205 '�', 186 '�' + clrscr(); + gotoxy(16, 8); + printf("USE ARROW KEYS TO NAVIGATE AND ESC KEY TO CLOSE"); + for( i = 16; i <= 65; i++) + { gotoxy(i,10); + printf ("%c",ro); + gotoxy(i,14); + printf ("%c",ro); + gotoxy(i,36); + printf ("%c",ro); + gotoxy(i,40); + printf ("%c",ro); + } + for(i = 11; i <= 39; i++) + { gotoxy(15,i); + printf ("%c",co); + gotoxy(66,i); + printf ("%c",co); + } + gotoxy(15,10); + printf("%c",201); //GARPH CHAR 201 '�' + gotoxy(66,10); + printf("%c",187); //GARPH CHAR 187 '�' + gotoxy(15,40); + printf("%c",200); //GARPH CHAR 200 '�' + gotoxy(66,40); + printf("%c",188); //GARPH CHAR 188 '�' + gotoxy(15,14); + printf("%c",204); //GARPH CHAR 204 '�' + gotoxy(66,14); + printf("%c",185); //GARPH CHAR 185 '�' + gotoxy(15,36); + printf("%c",204); //GARPH CHAR 204 '�' + gotoxy(66,36); + printf("%c",185); //GARPH CHAR 185 '�' + + textcolor(YELLOW + BLINK); + int hed_sp = 16 +((49 - (strlen(mo[month]) + 5))/2); //ALLIGN HEADER +TO +CENTER + gotoxy(hed_sp,12); + cprintf("%s %d",mo[month],year); + window(16,15,65,35); + clrscr(); + for(i=1, j = 0; i<49; i+=7,j++) //PRINT DAY NAMES + { + if(i < 7) + textcolor(RED); // FOR SUNDAY + else + textcolor(YELLOW); //OTHER THAN SUNDAY + gotoxy(i,3); + cprintf("%5s",day[j]); + } +} +void print_cal(int year, int month) +{ + int i, j, start, count, limit; + textmode(64); + start = first_day(year, month); + count = 0, limit = 31; + draw(year, month); + if( month == 3 || month == 5 || month == 8 || month == 10 ) + limit = 30; //FOR APRIL, JUNE, SEPT, NOV + if(month == 1 ) //FOR FEB + limit = (year% 4==0 && year%100 != 0 || year%400==0)? 29: 28; + for(j=7; j< 20; j+=3) //ROW COUNTER + { + for(i=1; i<49; i+=7) //COLUMN COUNTER + { + if(i < 7) + textcolor(RED); //DATES ON SUNDAY + else + textcolor(YELLOW); + gotoxy(i,j); + if(start) + start--; //EMPTY SPACES TILL NUMBERING STARTS + else + { + if(count == today) //HILIGHT CURRENT DATE + { + textcolor(BLUE); + textbackground(YELLOW); + } + else + { + textcolor(YELLOW); + textbackground(BLACK); + } + cprintf("%4d",count+1); //PRINT DATE + count++; + } + if(count >= limit) + break; + } + } + if(count <= 30 && count < limit) //FOR PRINTING IN FIRST ROW IF ALL +ROWS +EXUASTED + { for(i=1; i<49; i+=7) + { + if(i < 7) + textcolor(RED); + else + textcolor(YELLOW); + gotoxy(i,7); + if(count == today) + { + textcolor(BLUE); + textbackground(YELLOW); + } + else + { + textcolor(YELLOW); + textbackground(BLACK); + } + cprintf("%4d",count+1); + count++; + if(count >= limit) + break; + } + } + window(16,37,65,39); //SETS WINDOW TO BOTTOM OF BOX + show_time(); //SHOWS TIME +} diff --git a/c++/Others/Time arithmatic.cpp b/c++/Others/Time arithmatic.cpp new file mode 100644 index 0000000..e964d64 --- /dev/null +++ b/c++/Others/Time arithmatic.cpp @@ -0,0 +1,115 @@ +Time arithmatic + +#include +#include + +typedef struct +{ + int hh,mm,ss; +}time; + +time add(time f,time s); +time sub(time f,time s); +time input(void); + +void main() +{ + time f,s,ans; + int ch; + clrscr(); + do + { + printf("\n <1> enter first operand "); + printf("\n <2> enter second operand "); + printf("\n <3> time addition "); + printf("\n <4> time subtraction "); + printf("\n <5> Exit \n\n"); + do + { + printf("enter your choice "); + scanf("%d",&ch); + }while(ch<1 || ch>5); + switch (ch) + { + case 1: + printf("\n enter the time(hh mm ss) "); + f=input(); + break; + case 2: + printf("\n enter the time(hh mm ss) "); + s=input(); + break; + case 3: + ans=add(f,s); + printf("\n time addition is %d %d %d",ans.hh,ans.mm,ans.ss); + break; + case 4: + ans=sub(f,s); + printf("\n time subtraction is %d %d %d",ans.hh,ans.mm,ans.ss); + break; + } + }while(ch!=5); +} + +time input(void) +{ + time temp; + do + { + printf("\n enter the hours : "); + scanf("%d",&temp.hh); + } + while(temp.hh<0 || temp.hh>12); + do + { + printf("\n enter the minutes : "); + scanf("%d",&temp.mm); + } + while(temp.mm<0 || temp.mm>=60); + do + { + printf("\n enter the seconds : "); + scanf("%d",&temp.ss); + } + while(temp.ss<0 || temp.ss>=60); + return temp; +} +time add(time x,time y) +{ + time a; + if(x.ss+y.ss>60) + ++x.mm,a.ss=(x.ss+y.ss)%60; + else + a.ss=x.ss+y.ss; + if(x.mm+y.mm>60) + ++x.hh,a.mm=(x.mm+y.mm)%60; + else + a.mm=x.mm+y.mm; + if(x.hh+y.hh>12) + a.hh=(x.hh+y.hh)%12; + else + a.hh=x.hh+y.hh; + if(a.hh==0) + a.hh=12; + return a; +} + +time sub(time x,time y) +{ + time a; + if(x.ss-y.ss<0) + --x.mm,a.ss=60+x.ss-y.ss; + else + a.ss=x.ss-y.ss; + if(x.mm-y.mm<0) + --x.hh,a.mm=60+x.mm-y.mm; + else + a.mm=x.mm-y.mm; + if(x.hh-y.hh<0) + a.hh=12+x.hh-y.hh; + else + a.hh=x.hh-y.hh; + if(a.hh==0) + a.hh=12; + return a; +} diff --git a/c++/Others/To calculate percentile.cpp b/c++/Others/To calculate percentile.cpp new file mode 100644 index 0000000..22c37bf --- /dev/null +++ b/c++/Others/To calculate percentile.cpp @@ -0,0 +1,63 @@ +To calculate percentile + +Write a program for the problem: the array of +inetegers indicating the marks of the students is +given, U have to calculate the percentile of the +students aaccording to this rule: the percentile of a +student is the %of no of student having marks less +then him. For eg: +suppose + +Student Marks +A 12 +B 60 +C 80 +D 71 +E 30 +F 45 + + +percentile of C = 5/5 *100 = 100 (out of 5 students 5 +are having marks less then him) + +percentile of B = 3/5*100 = 60% (out of 5, 3 have +markses less then him) + +percentile of A = 0/5*100 = 0%. + +#include +#include + + void main() + { + clrscr(); + int a[10],n,i,j; + int percent; + int count; + cout<<" + enter the size of array"; + cin>>n; + cout<<" + enter the values"; + for(i=0;i<=n-1;i++) + { + cout<<" a["<>a[i]; + } + + for( i=0;i<=n-1;i++) + { count=0; + for(j=0;j<=n-1;j++) + { if(a[i]>a[j]) + { + count=count+1; + } + } + percent=(count*100)/(n-1); + cout<<" + + the percentile of"<<"a["< +# include +# include + void main () +{ clrscr(); + int a,b=0,sum=0; + long int n; + cout<<"ENter the NO. : "; + cin>>n; + for(;n>0;) +//counts the digits + { a=n%10; + n=n/10; + b++; + } + for(;n>0;) + { a=n%10; + sum=sum+pow(a,b); + n=n/10; + } + if(sum==n) + { cout<<"IT IS AN ARMSTRONG NUMBER..."; + getch(); + } + else + { cout<<"IT IS NOT AN ARMSTRONG NUMBER..."; + getch(); + } +} diff --git a/c++/Others/To perform operations on complex number using operator.cpp b/c++/Others/To perform operations on complex number using operator.cpp new file mode 100644 index 0000000..0d7d28d --- /dev/null +++ b/c++/Others/To perform operations on complex number using operator.cpp @@ -0,0 +1,149 @@ +To perform operations on complex number using operator + +:#include +#include +#include +#include +class comp + { + private: + float real,image; + public: + comp operator +(comp a); + comp operator -(comp a); + comp operator *(comp a); + comp operator /(comp a); + void getdata(); + void show(); + }; +void comp :: getdata() + { + cout<<" + + Enter real part="; + cin>>real; + cout<<" + + Enter imaginary part="; + cin>>image; + } +void comp :: show() + { + cout.precision(2); + if(image<0) + cout<Addition"; + cout<<" + + 2>Subtraction"; + cout<<" + + 3>Multiplication"; + cout<<" + + 4>Division"; + cout<<" + + 5>Exit"; + d.getdata(); + e.getdata(); + cout<<" + + first no=>"; + d.show(); + cout<<" + + second no=>"; + e.show(); + cout<<" + + enter the choice=>"; + cin>>ch; + switch(ch) + { + case 1: + f=d-e; + cout<<" + + addition of two no=>"; + f.show(); + break; + case 2: + f=d-e; + cout<<" + + subtraction of two no=>"; + f.show(); + break; + case 3: + f=d*e; + cout<<" + + multiplication of two no=>"; + f.show(); + break; + case 4: + f=d/e; + cout<<" + + division of two no=>"; + f.show(); + break; + case 5: + exit(0); + break; + } + cout<<" + + do you want to continue(y/n)?="; + cin>>ans; + } + while(ans=='y'||ans=='Y'); + getch(); + } diff --git a/c++/Others/Treap.cpp - Implementation for treap.cpp b/c++/Others/Treap.cpp - Implementation for treap.cpp new file mode 100644 index 0000000..925e699 --- /dev/null +++ b/c++/Others/Treap.cpp - Implementation for treap.cpp @@ -0,0 +1,301 @@ +Treap.cpp - Implementation for treap + + #include "Treap.h" + #include + + /** + * Implements an unbalanced binary search tree. + * Note that all "matching" is based on the compares method. + */ + /** + * Construct the treap. + */ + template + Treap::Treap( const Comparable & notFound ) : + ITEM_NOT_FOUND( notFound ) + { + nullNode = new TreapNode; + nullNode->left = nullNode->right = nullNode; + nullNode->priority = INT_MAX; + root = nullNode; + } + + /** + * Copy constructor. + */ + template + Treap::Treap( const Treap & rhs ) + : ITEM_NOT_FOUND( rhs.ITEM_NOT_FOUND ) + { + nullNode = new TreapNode; + nullNode->left = nullNode->right = nullNode; + nullNode->priority = INT_MAX; + root = nullNode; + *this = rhs; + } + + /** + * Destructor for the tree. + */ + template + Treap::~Treap( ) + { + makeEmpty( ); + delete nullNode; + } + + /** + * Insert x into the tree; duplicates are ignored. + */ + template + void Treap::insert( const Comparable & x ) + { + insert( x, root ); + } + + /** + * Remove x from the tree. Nothing is done if x is not found. + */ + template + void Treap::remove( const Comparable & x ) + { + remove( x, root ); + } + + /** + * Find the smallest item in the tree. + * Return smallest item or ITEM_NOT_FOUND if empty. + */ + template + const Comparable & Treap::findMin( ) const + { + if( isEmpty( ) ) + return ITEM_NOT_FOUND; + + TreapNode *ptr = root; + while( ptr->left != nullNode ) + ptr = ptr->left; + + return ptr->element; + } + + /** + * Find the largest item in the tree. + * Return the largest item of ITEM_NOT_FOUND if empty. + */ + template + const Comparable & Treap::findMax( ) const + { + if( isEmpty( ) ) + return ITEM_NOT_FOUND; + + TreapNode *ptr = root; + while( ptr->right != nullNode ) + ptr = ptr->right; + + return ptr->element; + } + + /** + * Find item x in the tree. + * Return the matching item or ITEM_NOT_FOUND if not found. + */ + template + const Comparable & Treap:: + find( const Comparable & x ) const + { + TreapNode *current = root; + nullNode->element = x; + + for( ; ; ) + { + if( x < current->element ) + current = current->left; + else if( current->element < x ) + current = current->right; + else if( current != nullNode ) + return current->element; + else + return ITEM_NOT_FOUND; + } + } + + /** + * Make the tree logically empty. + */ + template + void Treap::makeEmpty( ) + { + makeEmpty( root ); + } + + /** + * Test if the tree is logically empty. + * Return true if empty, false otherwise. + */ + template + bool Treap::isEmpty( ) const + { + return root == nullNode; + } + + /** + * Print the tree contents in sorted order. + */ + template + void Treap::printTree( ) const + { + if( isEmpty( ) ) + cout << "Empty tree" << endl; + else + printTree( root ); + } + + + /** + * Deep copy. + */ + template + const Treap & + Treap::operator=( const Treap & rhs ) + { + if( this != &rhs ) + { + makeEmpty( ); + root = clone( rhs.root ); + } + + return *this; + } + + /** + * Internal method to insert into a subtree. + * x is the item to insert. + * t is the node that roots the tree. + * Set the new root. + */ + template + void Treap:: + insert( const Comparable & x, TreapNode * & t ) + { + if( t == nullNode ) + t = new TreapNode( x, nullNode, nullNode, + randomNums.randomInt( ) ); + else if( x < t->element ) + { + insert( x, t->left ); + if( t->left->priority < t->priority ) + rotateWithLeftChild( t ); + } + else if( t->element < x ) + { + insert( x, t->right ); + if( t->right->priority < t->priority ) + rotateWithRightChild( t ); + } + // else duplicate; do nothing + } + + /** + * Internal method to remove from a subtree. + * x is the item to remove. + * t is the node that roots the tree. + * Set the new root. + */ + template + void Treap::remove( const Comparable & x, + TreapNode * & t ) + { + if( t != nullNode ) + { + if( x < t->element ) + remove( x, t->left ); + else if( t->element < x ) + remove( x, t->right ); + else + { + // Match found + if( t->left->priority < t->right->priority ) + rotateWithLeftChild( t ); + else + rotateWithRightChild( t ); + + if( t != nullNode ) // Continue on down + remove( x, t ); + else + { + delete t->left; + t->left = nullNode; // At a leaf + } + } + } + } + + /** + * Internal method to make subtree empty. + */ + template + void Treap::makeEmpty( TreapNode * & t ) + { + if( t != nullNode ) + { + makeEmpty( t->left ); + makeEmpty( t->right ); + delete t; + } + t = nullNode; + } + + /** + * Internal method to print a subtree in sorted order. + * @param t the node that roots the tree. + */ + template + void Treap::printTree( TreapNode *t ) const + { + if( t != nullNode ) + { + printTree( t->left ); + cout << t->element << endl; + printTree( t->right ); + } + } + + + /** + * Internal method to clone subtree. + */ + template + TreapNode * + Treap::clone( TreapNode * t ) const + { + if( t == t->left ) // Cannot test against nullNode!!! + return nullNode; + else + return new TreapNode( t->element, clone( t->left ), + clone( t->right ), t->priority ); + } + + /** + * Rotate binary tree node with left child. + */ + template + void Treap::rotateWithLeftChild( TreapNode * & k2 ) const + { + TreapNode *k1 = k2->left; + k2->left = k1->right; + k1->right = k2; + k2 = k1; + } + + /** + * Rotate binary tree node with right child. + */ + template + void Treap::rotateWithRightChild( TreapNode * & k1 ) const + { + TreapNode *k2 = k1->right; + k1->right = k2->left; + k2->left = k1; + k1 = k2; + } diff --git a/c++/Others/Universal image format convertion.cpp b/c++/Others/Universal image format convertion.cpp new file mode 100644 index 0000000..810bd06 --- /dev/null +++ b/c++/Others/Universal image format convertion.cpp @@ -0,0 +1,127 @@ +Universal image format convertion + +typedef unsigned long ulong; +typedef unsigned short ushort; +typedef unsigned char uchar; + +struct UlFormatData +{ +public: + int BytesPP; + + ulong BitMask[4]; // A bit mask in source A8R8G8B8 picture. + int ShiftR[4]; // Can be < 0 for left shift operation. + +public: + ulong CreateBitMask(int aStartPosition, int aSize) + { + ulong result = 0; + UlFor (int i = 0; i < aSize; i++) + { + result = (result >> 1) | 0x80000000; + } + result = result >> aStartPosition; + return result; + } + + UlFormatData(const char *format_str) + { + BytesPP = 0; + for (int i = 0; i < 4; i++) + { + ShiftR[i] = 0; + BitMask[i] = 0; // Exclude color if not in use. + } + + // Count destination's bits per pixel. + int bitsPP = 0; + UlFor (const char *temp = format_str; *temp; temp++) + { + if ('0' <= *temp && *temp <= '9') + bitsPP += *temp - '0'; + } + + // Main loop: trace format_str and calculate masks and shifts. + int bitsPassed = 0; + int currentIndex = 0; // Index for any 'argb' order. + + while (*format_str) + { + char color = *(format_str++); + char numberOfBits = *(format_str++) - '0'; + + int sourceColorStart = + color == 'A' || color == 'X' ? 0 : + color == 'R' ? 8 : + color == 'G' ? 16 : + color == 'B' ? 24 : 32; + + BitMask[currentIndex] = CreateBitMask(sourceColorStart, numberOfBits); + ShiftR[currentIndex] = bitsPassed - sourceColorStart + (32 - bitsPP); + + bitsPassed += numberOfBits; + currentIndex++; + } + + BytesPP = bitsPP / 8; + } +}; + +//------------------------------------------------------------------------------ +// There is no 24-bit type in C++, so... + +struct UlBits24 +{ + char b[3]; +}; + +//------------------------------------------------------------------------------ +// Template function that will copy a line of image into destination with +// adequate conversion. + +template +static inline void CopyARGBLine(const ulong *srcline, dsttype *dstline, + const UlFormatData &aFormatData, int width) +{ + for (int x = 0; x < width; x++) + { + ulong temp = *(srcline++); + ulong result = 0; + UlFor (int i = 0; i < 4; i++) + { + result |= ((temp & aFormatData.BitMask[i]) >> + aFormatData.ShiftR[i]); + } + *(dstline++) = *(dsttype *)(&result); + } +} + +//------------------------------------------------------------------------------ +void ConvertFromA8R8G8B8(const ulong *aSource, int width, int height, + const UlFormatData &aFormatData, uchar *aData, int aPitch) +{ + for (int y = 0; y < height; y++) + { + const ulong *line = aSource + (y * width); + uchar *dstline = aData + (y * aPitch); + + switch (aFormatData.BytesPP) + { + case 1: + CopyARGBLine(line, (uchar *)dstline, aFormatData, width); + break; + case 2: + CopyARGBLine(line, (ushort *)dstline, aFormatData, width); + break; + case 3: + CopyARGBLine(line, (UlBits24 *)dstline, + aFormatData, width); + break; + case 4: + CopyARGBLine(line, (ulong *)dstline, aFormatData, width); + break; + default: + throw "Incorrect destination image format"; + } + } +} diff --git a/c++/Others/Using algorithm for code assignment to characters of varying probabilities.cpp b/c++/Others/Using algorithm for code assignment to characters of varying probabilities.cpp new file mode 100644 index 0000000..aa83d50 --- /dev/null +++ b/c++/Others/Using algorithm for code assignment to characters of varying probabilities.cpp @@ -0,0 +1,115 @@ +Using algorithm for code assignment to characters of varying probabilities + +#include +#include +#include +int temp,i,j,col=0,n=100,count=0,b[10][2]; +float a[10],sum=100; +char c[10][10]; +void main() +{ +void part(int,int); +clrscr(); +printf("Enter number of characters "); +while(n>10) +{ +printf("(Not more than 10) "); +scanf("%d",&n); +} +while(sum>1) +{ +printf("Enter their probabilities of occurences +"); +sum=0; +for(i=1;i<=n;i++) +{ +printf("."); +scanf("%f",&a[i]); +while(a[i]>=1) +a[i]=a[i]/10; +sum=sum+a[i]; +if(sum>1) +break; +} +if(sum>1) +printf("Sum of probabilities must be less than or equal to 1 ! +"); +} +for(i=0;i<10;i++) +{ +for(j=0;j<10;j++) +c[i][j]='*'; +} +for(i=0;i1) +{ +count++; +for(i=low-1;ib[i][0]) +{ +min=b[i][0]; +k=b[i][1]; +} +for(i=low-1;i +# include +# include +# include +# include + +int main(void) +{ + void drawgrid(int, int, int, int); + void encode(char *,char *, int, int, int, int); + void draw(int ,int ,char *, int); + + char *message; + int len; + + clrscr(); + cout << " +DIGITAL ENCODING TECHNIQUES"; + cout << " + + +Enter the data to be encoded (max 24 bits) : "; + + do{ + cin >> message; + len = strlen(message); + if(len>24) + cout << "Message is greater than 12 bits, please type new message: +"; + }while(len>24); + + char *o_mess =new char[len]; + char *e_mess =new char[len*2]; + strcpy(o_mess,message); + + int gd=DETECT, gm, i, x, y; + + initgraph(&gd,&gm,"..\BGI"); + setcolor(8); + settextstyle(DEFAULT_FONT,0,2); + outtextxy(100,10,"DIGITAL ENCODING TECHNIQUES"); + setcolor(YELLOW); + rectangle(0,30,630,450); + rectangle(1,31,629,449); + setcolor(WHITE); + settextstyle(DEFAULT_FONT,0,0); + drawgrid(120,60,len,20); + outtextxy(10,50, "Message"); + + x= 137; + for(i=0; i +#include +#include + + +int WINAPI WinMain(HINSTANCE hInstance,HINSTANCE hPrevInst, + LPSTR lpCmdLine,int nCmdShow) +{ + + LPITEMIDLIST pidl; + LPMALLOC lpMalloc; + char sz[MAX_PATH]; + + char *pErrMsg = "Error opening "Send to" folder."; + char *pCaption = "Send to"; + + if (NOERROR == SHGetSpecialFolderLocation( + NULL,CSIDL_SENDTO,&pidl)) + { + SHGetPathFromIDList(pidl,sz); + + if (NOERROR == SHGetMalloc(&lpMalloc)) + { + lpMalloc->lpVtbl->Free(lpMalloc,pidl); + lpMalloc->lpVtbl->Release(lpMalloc); + } + + if (32 >= +(int)ShellExecute(NULL,"open",sz,NULL,NULL,SW_SHOWNORMAL)) + MessageBox(NULL,pErrMsg,pCaption,MB_ICONEXCLAMATION); + } + + else + MessageBox(NULL,pErrMsg,pCaption,MB_ICONEXCLAMATION); + + return(0); + +} + + diff --git a/c++/Others/Which three balls move in three concentric oval orbit without ever colliding.cpp b/c++/Others/Which three balls move in three concentric oval orbit without ever colliding.cpp new file mode 100644 index 0000000..552ee05 --- /dev/null +++ b/c++/Others/Which three balls move in three concentric oval orbit without ever colliding.cpp @@ -0,0 +1,96 @@ +Which three balls move in three concentric oval orbit without ever colliding. + + +#define R 5 +#include +#include +#include +#include +#include +#include +void main() + + { + void orbit(void); + int d=DETECT,m; + initgraph(&d,&m,"e:\tcc\bgi"); + float xx,yy,aa=15,bb=50,x,y,X,Y,a=34,b=0,A=100,B=60,ex,sq; + setcolor(14); + // orbit(); + + for(float i=0;i<=720;i+=.1) + { + + + x=a*cos(i+10)-a*sin(i+10); + y=b*sin(i+10)+a*cos(i+10); + + X=A*cos(i+20)-B*sin(i+20+90); + Y=B*sin(i+20)+B*cos(i+20+90); + + xx=aa*cos(i); + yy=bb*sin(i); + + setcolor(14); + setfillstyle(1,14); + circle(x+100,y+100,R); + floodfill(x+100,y+100,14); + + setcolor(14); + setfillstyle(1,14); + circle(xx+100,yy+100,R); + floodfill(xx+100,yy+100,14); + + setcolor(14); + setfillstyle(1,14); + circle(X+100,Y+100,R); + floodfill(X+100,Y+100,14); + + putpixel(X+100,Y+100,4); + delay(100); + + setcolor(0); + setfillstyle(1,0); + circle(x+100,y+100,R); + floodfill(x+100,y+100,0); + + setcolor(0); + setfillstyle(1,0); + circle(xx+100,yy+100,R); + floodfill(xx+100,yy+100,0); + + setcolor(0); + setfillstyle(1,0); + circle(X+100,Y+100,R); + floodfill(X+100,Y+100,0); + + if(kbhit()) + exit(1); + orbit(); + } + + + getch(); + } + + void orbit() + { + for(float i=0;i<=60;i+=1) + { + float xx,yy,aa=15,bb=50,x,y,X,Y,a=34,b=0,A=100,B=60,ex,sq; + x=a*cos(i)-a*sin(i); + y=b*sin(i)+a*cos(i); + + X=A*cos(i)-B*sin(i+90); + Y=B*sin(i)+B*cos(i+90); + + xx=aa*cos(i); + yy=bb*sin(i); + + putpixel(x+100,y+100,14); + putpixel(X+100,Y+100,14); + putpixel(xx+100,yy+100,14); + + + } + } diff --git a/c++/Others/Word Frequency.cpp b/c++/Others/Word Frequency.cpp new file mode 100644 index 0000000..90c32ec --- /dev/null +++ b/c++/Others/Word Frequency.cpp @@ -0,0 +1,84 @@ +Word Frequency + +#include + +#define SIZE 80 +#define LEN 80 + + +int strword(char[],char[][]); +int strword_p(char*,char**); + + +void main(){ + char* s; + char** w; + char ch; + + do{ + clrscr(); + gotoxy(10,1); + printf("Enter a string :"); + gets(s); + gotoxy(10,2); + printf("\nNumber of words :%d",strword_p(s,w)); + gotoxy(10,24); + printf(" Continue(y/n)?"); + ch=getch(); + + } while (ch=='y' || ch=='Y'); +} + +int strword_p(char *s,char **w){ + int is_space=0, + i=0, + word_counter=0, + j=0, + is_printed=0, + frequency=0; + + while (*(s+i)!='\0'){ + if (*(s+i)==' ' || + *(s+i)==',' || + *(s+i)=='.' || + *(s+i)==':'){ + + if (is_space==0){ + *(*(w+word_counter)+j)='\0'; + word_counter++; + is_space=1; + j=0; + } + } + else{ + *(*(w+word_counter)+j)=*(s+i); + j++; + is_space=0; + } + i++; + } + if (is_space==0){ + *(*(w+word_counter)+j)='\0'; + word_counter++; + } + + for(j=0;j%d",j+1,w[j],frequency); + } + printf("\n"); + + + return word_counter; + + +} diff --git a/c++/Others/Write a character using cout.cpp b/c++/Others/Write a character using cout.cpp new file mode 100644 index 0000000..b1c3839 --- /dev/null +++ b/c++/Others/Write a character using cout.cpp @@ -0,0 +1,14 @@ +Write a character using cout + +#include +#include + +int main() +{ +char *url = "WWW"; +while(*url) +cout.put (*url++); + +cout< +#include +const char *FILENAME = "myfile.txt"; + +int main() +{ +//create output object associated w/ file +ofstream fout(FILENAME); +cout << "Enter your text: "; +char str[100]; +cin >> str; +//write the text to the file +fout << "here is your text\n"; +fout < +#include +using namespace std; +struct Msg +{ + char message[256]; + void show_message(void); +}; + + +struct UpperMsg +{ + char message[256]; + void show_message(void); +}; + + +void Msg::show_message(void) +{ + cout << message; +} + +void UpperMsg::show_message(void) +{ + cout << strupr(message); +} + +int main(void) +{ + Msg book = { "C\n" }; + UpperMsg book_upr = { "P\n" }; + + book.show_message(); + book_upr.show_message(); +} diff --git a/c++/Others/dsexceptions.h - Simple exception classes.cpp b/c++/Others/dsexceptions.h - Simple exception classes.cpp new file mode 100644 index 0000000..a42ec60 --- /dev/null +++ b/c++/Others/dsexceptions.h - Simple exception classes.cpp @@ -0,0 +1,11 @@ +dsexceptions.h - Simple exception classes + + #ifndef DSEXCEPTIONS_H_ + #define DSEXCEPTIONS_H_ + + class Underflow { }; + class Overflow { }; + class OutOfMemory { }; + class BadIterator { }; + + #endif diff --git a/c++/Others/matrix.h - Simple matrix class.cpp b/c++/Others/matrix.h - Simple matrix class.cpp new file mode 100644 index 0000000..0822c28 --- /dev/null +++ b/c++/Others/matrix.h - Simple matrix class.cpp @@ -0,0 +1,32 @@ +matrix.h - Simple matrix class + + #ifndef MATRIX_H + #define MATRIX_H + + #include "vector.h" + + template + class matrix + { + public: + matrix( int rows, int cols ) : array( rows ) + { + for( int i = 0; i < rows; i++ ) + array[ i ].resize( cols ); + } + matrix( const matrix & rhs ) : array( rhs.array ) { } + const vector & operator[]( int row ) const + { return array[ row ]; } + vector & operator[]( int row ) + { return array[ row ]; } + int numrows( ) const + { return array.size( ); } + int numcols( ) const + { return numrows( ) ? array[ 0 ].size( ) : 0; } + private: + vector< vector > array; + }; + + #endif + + diff --git a/c++/Others/mystring.h - If you don't have a string type.cpp b/c++/Others/mystring.h - If you don't have a string type.cpp new file mode 100644 index 0000000..07877c2 --- /dev/null +++ b/c++/Others/mystring.h - If you don't have a string type.cpp @@ -0,0 +1,51 @@ +mystring.h - If you don't have a string type + +#ifndef MY_STRING_H_ +#define MY_STRING_H_ + +#include + + +#define string String + +class StringIndexOutOfBounds { }; + +class string +{ + public: + string( const char *cstring = "" ); // Constructor + string( const string & str ); // Copy constructor + ~string( ) // Destructor + { delete [ ] buffer; } + + const string & operator= ( const string & rhs ); // Copy + const string & operator+=( const string & rhs ); // Append + + const char *c_str( ) const // Return C-style string + { return buffer; } + int length( ) const // Return string length + { return strLength; } + + char operator[]( int k ) const; // Accessor operator[] + char & operator[]( int k ); // Mutator operator[] + + enum { MAX_LENGTH = 1024 }; // Maximum length for input string + + private: + char *buffer; // storage for characters + int strLength; // length of string (# of characters) + int bufferLength; // capacity of buffer +}; + +ostream & operator<<( ostream & out, const string & str ); // Output +istream & operator>>( istream & in, string & str ); // Input +istream & getline( istream & in, string & str ); // Read line + +bool operator==( const string & lhs, const string & rhs ); // Compare == +bool operator!=( const string & lhs, const string & rhs ); // Compare != +bool operator< ( const string & lhs, const string & rhs ); // Compare < +bool operator<=( const string & lhs, const string & rhs ); // Compare <= +bool operator> ( const string & lhs, const string & rhs ); // Compare > +bool operator>=( const string & lhs, const string & rhs ); // Compare >= + +#endif diff --git a/c++/Others/simple adding of records using fstream.h.cpp b/c++/Others/simple adding of records using fstream.h.cpp new file mode 100644 index 0000000..dd828c1 --- /dev/null +++ b/c++/Others/simple adding of records using fstream.h.cpp @@ -0,0 +1,69 @@ +simple adding of records using fstream.h + +#include +#include +#include +#include +#include +#include + +add(); +main() +{ +ifstream input_stream("rec.dat"); +char p[30],ch,c; +int x,num; +clrscr(); + cout<<"[A]dd record "<>num; + for(x=1;x<=num;x++) + { + input_stream>>x; + input_stream>>p; + } + cout<<"Record number: "<>n; + { + y++; + } + out_stream< +#include "mystring.h" + +string::string( const char * cstring ) +{ + if( cstring == NULL ) + cstring = ""; + strLength = strlen( cstring ); + bufferLength = strLength + 1; + buffer = new char[ bufferLength ]; + strcpy( buffer, cstring ); +} + +string::string( const string & str ) +{ + strLength = str.length( ); + bufferLength = strLength + 1; + buffer = new char[ bufferLength ]; + strcpy( buffer,str.buffer ); +} + +const string & string::operator=( const string & rhs ) +{ + if( this != &rhs ) + { + if( bufferLength < rhs.length( ) + 1 ) + { + delete [ ] buffer; + bufferLength = rhs.length( ) + 1; + buffer = new char[ bufferLength ]; + } + strLength = rhs.length( ); + strcpy( buffer, rhs.buffer ); + } + return *this; +} + +const string & string::operator+=( const string & rhs ) +{ + if( this == &rhs ) + { + string copy( rhs ); + return *this += copy; + } + + int newLength = length( ) + rhs.length( ); + if( newLength >= bufferLength ) + { + bufferLength = 2 * ( newLength + 1 ); + + char *oldBuffer = buffer; + buffer = new char[ bufferLength ]; + strcpy( buffer, oldBuffer ); + delete [ ] oldBuffer; + } + + strcpy( buffer + length( ), rhs.buffer ); + strLength = newLength; + return *this; +} + +char & string::operator[ ]( int k ) +{ + if( k < 0 || k >= strLength ) + throw StringIndexOutOfBounds( ); + return buffer[ k ]; +} + +char string::operator[ ]( int k ) const +{ + if( k < 0 || k >= strLength ) + throw StringIndexOutOfBounds( ); + return buffer[ k ]; +} + +ostream & operator<<( ostream & out, const string & str ) +{ + return out << str.c_str(); +} + +istream & operator>>( istream & in, string & str ) +{ + char buf[ string::MAX_LENGTH + 1 ]; + in >> buf; + if( !in.fail( ) ) + str = buf; + return in; +} + +istream & getline( istream & in, string & str ) +{ + char buf[ string::MAX_LENGTH + 1 ]; + in.getline( buf, string::MAX_LENGTH ); + if( !in.fail( ) ) + str = buf; + return in; +} + +bool operator==( const string & lhs, const string & rhs ) +{ + return strcmp( lhs.c_str( ), rhs.c_str( ) ) == 0; +} + +bool operator!=( const string & lhs, const string & rhs ) +{ + return strcmp( lhs.c_str( ), rhs.c_str( ) ) != 0; +} + +bool operator<( const string & lhs, const string & rhs ) +{ + return strcmp( lhs.c_str( ), rhs.c_str( ) ) < 0; +} + +bool operator<=( const string & lhs, const string & rhs ) +{ + return strcmp( lhs.c_str( ), rhs.c_str( ) ) <= 0; +} + +bool operator>( const string & lhs, const string & rhs ) +{ + return strcmp( lhs.c_str( ), rhs.c_str( ) ) > 0; +} + +bool operator>=( const string & lhs, const string & rhs ) +{ + return strcmp( lhs.c_str( ), rhs.c_str( ) ) >= 0; +} diff --git a/c++/Others/vector.cpp - If you don't have a vector type.cpp b/c++/Others/vector.cpp - If you don't have a vector type.cpp new file mode 100644 index 0000000..3c190b4 --- /dev/null +++ b/c++/Others/vector.cpp - If you don't have a vector type.cpp @@ -0,0 +1,43 @@ +vector.cpp - If you don't have a vector type + +#ifndef VECTOR_CPP_ +#define VECTOR_CPP_ + +#include "vector.h" + +template +const vector & vector::operator=( const vector & rhs ) +{ + if( this != &rhs ) + { +#ifdef WIN32 + if( currentSize != 0 ) +#endif + delete [ ] objects; + currentSize = rhs.size( ); + objects = new Object[ currentSize ]; + for( int k = 0; k < currentSize; k++ ) + objects[ k ] = rhs.objects[ k ]; + } + return *this; +} + +template +void vector::resize( int newSize ) +{ + Object *oldArray = objects; + int numToCopy = newSize < currentSize ? newSize : currentSize; + + objects = new Object[ newSize ]; + + for( int k = 0; k < numToCopy; k++ ) + objects[ k ] = oldArray[ k ]; + +#ifdef WIN32 + if( currentSize != 0 ) +#endif + delete [ ] oldArray; + currentSize = newSize; +} + +#endif diff --git a/c++/Others/vector.h - If you don't have a vector type.cpp b/c++/Others/vector.h - If you don't have a vector type.cpp new file mode 100644 index 0000000..fa6a9d4 --- /dev/null +++ b/c++/Others/vector.h - If you don't have a vector type.cpp @@ -0,0 +1,57 @@ +vector.h - If you don't have a vector type + +#ifndef VECTOR_H +#define VECTOR_H + +#define vector Vector + +class ArrayIndexOutOfBounds { }; + +template +class vector +{ + public: + explicit vector( int theSize = 0 ) : currentSize( theSize ) + { objects = new Object[ currentSize ]; } + vector( const vector & rhs ) : objects( NULL ) + { operator=( rhs ); } + ~vector( ) +#ifndef WIN32 + { delete [ ] objects; } +#else + { if( currentSize != 0 ) delete [ ] objects; } +#endif + + int size( ) const + { return currentSize; } + + Object & operator[]( int index ) + { + #ifndef NO_CHECK + if( index < 0 || index >= currentSize ) + throw ArrayIndexOutOfBounds( ); + #endif + return objects[ index ]; + } + + const Object & operator[]( int index ) const + { + #ifndef NO_CHECK + if( index < 0 || index >= currentSize ) + throw ArrayIndexOutOfBounds( ); + #endif + return objects[ index ]; + } + + + const vector & operator = ( const vector & rhs ); + void resize( int newSize ); + private: + int currentSize; + Object * objects; +}; + +#include "vector.cpp" +#endif + + diff --git a/c++/_Basic/2D Array.cpp b/c++/_Basic/2D Array.cpp new file mode 100644 index 0000000..eecea09 --- /dev/null +++ b/c++/_Basic/2D Array.cpp @@ -0,0 +1,43 @@ +#include +#define size 16 +using namespace std; + +int main () +{ + int m,n; + int a[size][size]; + cout<<"Enter the number of rows"<>m; + cout<<"Enter the number of columns"<>n; + cout<<"Enter the Elements in Table"<>a[i][j]; + } + } +// output each array element"s value + for ( int i = 0; i < m; i++ ) + for ( int j = 0; j < n; j++ ) + { + cout << "a[" << i << "][" << j << "]: "; + cout << a[i][j]<< endl; + } + return 0; +} + +Output: +Enter the number of rows +2 +Enter the number of columns +3 +Enter the Elements in Table +1 2 3 4 5 6 +a[0][0]: 1 +a[0][1]: 2 +a[0][2]: 3 +a[1][0]: 4 +a[1][1]: 5 +a[1][2]: 6 \ No newline at end of file diff --git a/c++/_Basic/Add n numbers.cpp b/c++/_Basic/Add n numbers.cpp new file mode 100644 index 0000000..7c89624 --- /dev/null +++ b/c++/_Basic/Add n numbers.cpp @@ -0,0 +1,17 @@ +#include < iostream.h > + +int main() +{ + int n, sum = 0, c, value; + cout<<"Enter the number of integers you want to add\n"; + cin>>n; + cout<<"Enter"<>value; + sum = sum + value; + /*adding each no in sum*/ + } + cout<<"Sum of entered integers ="< + +int main() +{ + int first, second, add, subtract, multiply; + float divide; + cout<<"Enter two integers\n"; + cin>>first>>second; + add = first + second; + subtract = first - second; + multiply = first * second; + divide = first / (float)second; +//typecasting + cout<<"Sum = "< +int main() +{ + int n, sum = 0, remainder; + cout<<"Enter an integer\n"; + cin>>n; + while(n != 0) + { + remainder = n % 10; + /*stores unit place digit to remainder*/ + sum = sum + remainder; + n = n / 10; + /*dividing no to discard unit place digit*/ + } + cout<<"Sum of digits of entered number = "< + +int main() +{ + int m, n, c, d, first[10][10], second[10][10], sum[10][10]; + cout<<"Enter the number of rows and columns of matrix\n"; + cin>>m>>n; + cout<<"Enter the elements of first matrix\n"; + for ( c = 0 ; c < m ; c++ ) + for ( d = 0 ; d < n ; d++ ) + cin>>first[c][d]; + cout<<"Enter the elements of second matrix\n"; + for ( c = 0 ; c < m ; c++ ) + for ( d = 0 ; d < n ; d++ ) + cin>>second[c][d]; + for ( c = 0 ; c < m ; c++ ) + for ( d = 0 ; d < n ; d++ ) + sum[c][d] = first[c][d] + second[c][d]; + /* Matrix addition */ + cout<<"Sum of entered matrices:-\n"; + for ( c = 0 ; c < m ; c++ ) + { + for ( d = 0 ; d < n ; d++ ) + cout< + +void main() +{ + int height, base; + float ans;/*ans may come in fractions*/ + cout<<"Enter height and base"; + cin>>height>>base; + ans= (1/2)*height*base; + /* mathematical formula*/ + cout<<"Area if triangle is"< +#include +#include +using namespace std; + +typedef pair pii; +typedef vector > Graph; + +const int INF = INT_MAX / 3; + +bool bellmanFord(Graph &g, int s, vector &prio, vector &pred) { + int n = g.size(); + pred.assign(n, -1); + prio.assign(n, INF); + prio[s] = 0; + bool wasChanged = true; + for (int k = 0; k < n; k++) { + wasChanged = false; + for (int u = 0; u < n; u++) { + for (int i = 0; i < (int) g[u].size(); i++) { + int v = g[u][i].first; + int cost = g[u][i].second; + if (prio[v] > prio[u] + cost) { + prio[v] = prio[u] + cost; + pred[v] = u; + wasChanged = true; + } + } + } + if (!wasChanged) + break; + } + // wasChanged is true iff graph has a negative cycle + return wasChanged; +} + +vector findNegativeCycle(Graph &g) { + int n = g.size(); + vector pred(n, -1); + vector prio(n, INF); + prio[0] = 0; + int last = 0; + for (int k = 0; k < n; k++) { + last = -1; + for (int u = 0; u < n; u++) { + for (int i = 0; i < (int) g[u].size(); i++) { + int v = g[u][i].first; + int cost = g[u][i].second; + if (prio[v] > prio[u] + cost) { + prio[v] = prio[u] + cost; + pred[v] = u; + last = v; + } + } + } + if (last == -1) + return vector(); + } + + vector path(n); + vector pos(n, -1); + for (int i = 0;; i++) { + if (pos[last] != -1) + return vector(path.rend() - i, path.rend() - pos[last]); + path[i] = last; + pos[last] = i; + last = pred[last]; + } +} + +int main() { + Graph g(4); + g[0].push_back(make_pair(1, 1)); + g[1].push_back(make_pair(0, 1)); + g[1].push_back(make_pair(2, 1)); + g[2].push_back(make_pair(3, -10)); + g[3].push_back(make_pair(1, 1)); + + vector cycle = findNegativeCycle(g); + for (int i = 0; i < (int) cycle.size(); i++) + cout << cycle[i] << " "; +} diff --git a/c++/_Basic/Binary Operator Overloading.cpp b/c++/_Basic/Binary Operator Overloading.cpp new file mode 100644 index 0000000..5996375 --- /dev/null +++ b/c++/_Basic/Binary Operator Overloading.cpp @@ -0,0 +1,73 @@ +#include < iostream.h > +using namespace std; + +class Cube +{ +public: + + void setLength( double l ) + { + length = l; + } + + void setBreadth( double b ) + { + breadth = b; + } + + void setHeight( double h ) + { + height = h; + } + double getVolume(void) + { + return length * breadth * height; + } + +// Overload + operator to add two Cube objects. + Cube operator+(const Cube& b) + { + Cube C; + C.length = this->length + b.length; + C.breadth = this->breadth + b.breadth; + C.height = this->height + b.height; + return C; + } +private: + double length; // Length of a Cube + double breadth; // Breadth of a Cube + double height; // Height of a Cube +}; +// Main function for the program +int main( ) +{ + Cube C1; // Declare C1 of type Cube + Cube C2; // Declare C2 of type Cube + Cube C3; // Declare C3 of type Cube + double volume = 0.0; // Store the volume of a Cube here +// Cube 1 specification + C1.setLength(4.0); + C1.setBreadth(6.0); + C1.setHeight(5.0); +// Cube 2 specification + C2.setLength(8.0); + C2.setBreadth(4.0); + C2.setHeight(10.0); +// volume of Cube 1 + volume = C1.getVolume(); + cout << "Volume of Cube 1 : " << volume < +int main() +{ + int a[10],i,n,m,c,l,u; + cout<<"Enter the size of an array: "; + cin>>n; + cout<<"Enter the elements of the array: " ; + for(i=0; i < n; i++) + cin>>a[i]; + cout<<"Enter the number to be search: "; + cin>>m; + l=0,u=n-1; + c=binary(a,n,m,l,u); + if(c==0) + cout<<"Number is not found."; + else + cout<<"Number is found."; + return 0; +} + +/*Binary search will search element at middle, if element is not found and if element to be searched is less than middle then it will search only in lower part and if greater then in upper part */ + +int binary(int a[],int n,int m,int l,int u) +{ + int mid,c=0; + if(l < = u) + { + mid=(l+u)/2; + if(m==a[mid]) + { + c=1; + } + else if(m < a[mid]) + { + return binary(a,n,m,l,mid-1); + } + else + return binary(a,n,m,mid+1,u); + } + else + return c; +} + +Output: + +Enter the size of an array:4 +Enter the elements of the array:5 3 6 2 +Enter the number to be search:3 +Number is found. +Number is found. \ No newline at end of file diff --git a/c++/_Basic/Binary to Decimal.cpp b/c++/_Basic/Binary to Decimal.cpp new file mode 100644 index 0000000..e3974d5 --- /dev/null +++ b/c++/_Basic/Binary to Decimal.cpp @@ -0,0 +1,19 @@ +#include < iostream.h > + +void main() +{ + int num, binary_val, decimal_val = 0, base = 1, rem; + cout<<"Enter a binary number(1s and 0s) \n"; + cin>>amp num; + binary_val = num; + while (num > 0) + { + rem = num % 10; + decimal_val = decimal_val + rem * base; + num = num / 10 ; + num = num / 10 ; + base = base * 2; + } + cout<<"The Binary number is ="< + +int main() +{ + long int binaryval, hexadecimalval = 0, i = 1, remainder; + cout<<"Enter the binary number: "; + cin>>binaryval; + while (binaryval != 0) + { + remainder = binaryval % 10; + hexadecimalval = hexadecimalval + remainder * i; + i = i * 2; + binaryval = binaryval / 10; + } + cout<<"Equivalent hexadecimal value:"< + +int main() +{ + long int binarynum, octalnum = 0, j = 1, remainder; + cout<<"Enter the value for binary number: "; + cin>>binarynum; + while (binarynum != 0) + { + remainder = binarynum % 10; + octalnum = octalnum + remainder * j; + j = j * 2; + binarynum = binarynum / 10; + } + cout<<"Equivalent octal value:"< + +using namespace std; + +int pow(int x, int n, int MOD) { + long long y = x; + int res = 1; + for (; n > 0; n >>= 1) { + if (n & 1) + res = res * y % MOD; + y = y * y % MOD; + } + return res; +} + +int main() { + const int MOD = 1000000007; + int x = pow(2, 10, MOD); + cout << x << endl; +} diff --git a/c++/_Basic/Check Positive or Negative.cpp b/c++/_Basic/Check Positive or Negative.cpp new file mode 100644 index 0000000..6630240 --- /dev/null +++ b/c++/_Basic/Check Positive or Negative.cpp @@ -0,0 +1,20 @@ +#include +#include + +void main() +{ + clrscr(); //clear screen + int number; + cout<< "Enter an integer: "; + cin>> number; + if ( number >= 0) + { + cout << "You entered a positive integer: "< +#include +#include +using namespace std; + +struct item { + int x, y; + bool operator<(const item &o) const { + return x < o.x || x == o.x && y < o.y; + } +}; + +struct item_cmp { + bool operator()(const item &a, const item &b) { + return a.x < b.x || a.x == b.x && a.y < b.y; + } +}; + +bool cmp(const item &a, const item &b) { + return a.x < b.x || a.x == b.x && a.y < b.y; +} + +int main() { + item a[] = { { 2, 3 }, { 1, 2 } }; + //typedef set myset; + //myset s(a, a + 2, cmp); + //typedef set myset; + typedef set myset; + myset s(a, a + 2); + for (myset::iterator it = s.begin(); it != s.end(); it++) { + cout << it->x << " " << it->y << endl; + } + + sort(a, a + 2, cmp); + sort(a, a + 2, item_cmp()); + cout << a[0].x << " " << a[0].y << endl; +} diff --git a/c++/_Basic/ConvexHull.cpp b/c++/_Basic/ConvexHull.cpp new file mode 100644 index 0000000..0d07e77 --- /dev/null +++ b/c++/_Basic/ConvexHull.cpp @@ -0,0 +1,39 @@ +#include +#include + +using namespace std; + +typedef pair point; + +long long cross(const point &a, const point &b, const point &c) { + return (b.first - a.first) * (c.second - a.second) - (b.second - a.second) * (c.first - a.first); +} + +vector convexHull(vector points) { + if (points.size() <= 1) + return points; + sort(points.begin(), points.end()); + vector h; + for (auto p: points) { + while (h.size() >= 2 && cross(h.end()[-2], h.back(), p) >= 0) + h.pop_back(); + h.push_back(p); + } + reverse(points.begin(), points.end()); + int upper = h.size(); + for (auto p: points) { + while (h.size() > upper && cross(h.end()[-2], h.back(), p) >= 0) + h.pop_back(); + h.push_back(p); + } + h.resize(h.size() - 1 - (h[0] == h[1])); + return h; +} + +// Usage example +int main() { + vector hull1 = convexHull((vector) {point(0, 0), point(3, 0), point(0, 3), point(1, 1)}); + cout << (3 == hull1.size()) << endl; + vector hull2 = convexHull((vector) {point(0, 0), point(0, 0)}); + cout << (1 == hull2.size()) << endl; +} diff --git a/c++/_Basic/Current Date.cpp b/c++/_Basic/Current Date.cpp new file mode 100644 index 0000000..39b436c --- /dev/null +++ b/c++/_Basic/Current Date.cpp @@ -0,0 +1,14 @@ +#include +#include +using namespace std; + +int main() +{ + time_t t = time(0); // get time now + struct tm * now = localtime( & t ); + cout << "Current Date is : " + cout << now->tm_mday << '-'<< (now->tm_mon + 1) << '-' << (now->tm_year + 1900) << endl; +} + +Output +Current Date is : 16-6-2015 \ No newline at end of file diff --git a/c++/_Basic/Decimal to Binary.cpp b/c++/_Basic/Decimal to Binary.cpp new file mode 100644 index 0000000..50098dd --- /dev/null +++ b/c++/_Basic/Decimal to Binary.cpp @@ -0,0 +1,19 @@ +#include < iostream.h > + +int main() +{ + int n, c, k; + cout<<"Enter an integer in decimal number system\n"; + cin>>n; + cout<= 0; c--) + { + k = n >> c; + /*Right shift(Binary Divide by 2)*/ + if (k & 1)//k is logically ANDed with 1 + cout<<"1"; + else + cout<<"0"; + } + return 0; +} \ No newline at end of file diff --git a/c++/_Basic/Decimal to Octal.cpp b/c++/_Basic/Decimal to Octal.cpp new file mode 100644 index 0000000..1af5624 --- /dev/null +++ b/c++/_Basic/Decimal to Octal.cpp @@ -0,0 +1,18 @@ +#include + +void main() +{ + long num, decimal_num, remainder, base = 1, octal = 0; + cout<<"Enter a decimal integer \n"; + cin>>amp num; + decimal_num = num; + while (num > 0) + { + remainder = num % 8; + octal = octal + remainder * base; + num = num / 8; + base = base * 10; + } + cout<<"Input number is ="< +#include < string.h > + +int check_vowel(char); + +int main() +{ + char s[100], t[100]; + int i, j = 0; + cout<<"Enter a string to delete vowels\n"; + gets(s); + /* In the program we create a new string and process entered string character by character, and if a vowel is found it is not added to new string otherwise the character is added to new string, after the string ends we copy the new string into original string*/ + for(i = 0; s[i] != '\0'; i++) + { + if(check_vowel(s[i]) == 0) + { + /* not a vowel */ + t[j] = s[i]; + j++ + ; + } + } + t[j] = '\0'; + strcpy(s, t); + /* We are changing initial string */ + cout<<"String after deleting vowels:"<< s<<"\n"; + return 0; +} +int check_vowel(char c) +{ + switch(c) + { + case 'a': + case 'A': + case 'e': + case 'E': + case 'i': + case 'I': + case 'o': + case 'O': + case 'u': + case 'U': + return 1; + default: + return 0; + } +} \ No newline at end of file diff --git a/c++/_Basic/Diameter.cpp b/c++/_Basic/Diameter.cpp new file mode 100644 index 0000000..63f2f99 --- /dev/null +++ b/c++/_Basic/Diameter.cpp @@ -0,0 +1,67 @@ +#include +#include +#include +#include +using namespace std; + +typedef pair point; + +bool cw(const point &a, const point &b, const point &c) { + return (b.first - a.first) * (c.second - a.second) - (b.second - a.second) * (c.first - a.first) < 0; +} + +vector convexHull(vector p) { + int n = p.size(); + if (n <= 1) + return p; + int k = 0; + sort(p.begin(), p.end()); + vector q(n * 2); + for (int i = 0; i < n; q[k++] = p[i++]) + for (; k >= 2 && !cw(q[k - 2], q[k - 1], p[i]); --k) + ; + for (int i = n - 2, t = k; i >= 0; q[k++] = p[i--]) + for (; k > t && !cw(q[k - 2], q[k - 1], p[i]); --k) + ; + q.resize(k - 1 - (q[0] == q[1])); + return q; +} + +double area(const point &a, const point &b, const point &c) { + return abs((b.first - a.first) * (c.second - a.second) - (b.second - a.second) * (c.first - a.first)); +} + +double dist(const point &a, const point &b) { + return hypot(a.first - b.first, a.second - b.second); +} + +double diameter(const vector &p) { + vector h = convexHull(p); + int m = h.size(); + if (m == 1) + return 0; + if (m == 2) + return dist(h[0], h[1]); + int k = 1; + while (area(h[m - 1], h[0], h[(k + 1) % m]) > area(h[m - 1], h[0], h[k])) + ++k; + double res = 0; + for (int i = 0, j = k; i <= k && j < m; i++) { + res = max(res, dist(h[i], h[j])); + while (j < m && area(h[i], h[(i + 1) % m], h[(j + 1) % m]) > area(h[i], h[(i + 1) % m], h[j])) { + res = max(res, dist(h[i], h[(j + 1) % m])); + ++j; + } + } + return res; +} + +int main() { + vector points(4); + points[0] = point(0, 0); + points[1] = point(3, 0); + points[2] = point(0, 3); + points[3] = point(1, 1); + double d = diameter(points); + cout << d << endl; +} diff --git a/c++/_Basic/Dijkstra.cpp b/c++/_Basic/Dijkstra.cpp new file mode 100644 index 0000000..d59fe57 --- /dev/null +++ b/c++/_Basic/Dijkstra.cpp @@ -0,0 +1,73 @@ +#include +#include +#include +#include +#include +using namespace std; + +typedef pair pii; +typedef vector > Graph; + +void dijkstra(Graph &g, int s, vector &prio, vector &pred) { + int n = g.size(); + prio.assign(n, INT_MAX); + prio[s] = 0; + pred.assign(n, -1); + priority_queue , greater > q; + q.push(make_pair(prio[s], s)); + + while (!q.empty()) { + int d = q.top().first; + int u = q.top().second; + q.pop(); + if (d != prio[u]) + continue; + for (int i = 0; i < (int) g[u].size(); i++) { + int v = g[u][i].first; + int nprio = prio[u] + g[u][i].second; + if (prio[v] > nprio) { + prio[v] = nprio; + pred[v] = u; + q.push(make_pair(nprio, v)); + } + } + } +} + +void dijkstra2(Graph &g, int s, vector &prio, vector &pred) { + int n = g.size(); + prio.assign(n, INT_MAX); + prio[s] = 0; + pred.assign(n, -1); + set q; + q.insert(make_pair(prio[s], s)); + + while (!q.empty()) { + int u = q.begin()->second; + q.erase(q.begin()); + for (int i = 0; i < (int) g[u].size(); ++i) { + int v = g[u][i].first; + int nprio = prio[u] + g[u][i].second; + if (prio[v] > nprio) { + q.erase(make_pair(prio[v], v)); + prio[v] = nprio; + pred[v] = u; + q.insert(make_pair(prio[v], v)); + } + } + } +} + +int main() { + Graph g(3); + g[0].push_back(make_pair(1, 10)); + g[1].push_back(make_pair(2, -5)); + g[0].push_back(make_pair(2, 8)); + + vector prio; + vector pred; + dijkstra(g, 0, prio, pred); + + for (int i = 0; i < prio.size(); i++) + cout << prio[i] << endl; +} diff --git a/c++/_Basic/DijkstraHeap.cpp b/c++/_Basic/DijkstraHeap.cpp new file mode 100644 index 0000000..be30eed --- /dev/null +++ b/c++/_Basic/DijkstraHeap.cpp @@ -0,0 +1,123 @@ +#include +#include +#include +using namespace std; + +const int maxnodes = 200000; +const int maxedges = 1000000; + +// graph +int edges; +int last[maxnodes], head[maxedges], previous[maxedges], len[maxedges]; +int prio[maxnodes], pred[maxnodes]; + +void graphClear() { + fill(last, last + maxnodes, -1); + edges = 0; +} + +void addEdge(int u, int v, int length) { + head[edges] = v; + len[edges] = length; + previous[edges] = last[u]; + last[u] = edges++; +} + +// heap +int h[maxnodes]; +int pos2Id[maxnodes]; +int id2Pos[maxnodes]; +int hsize; + +void hswap(int i, int j) { + swap(h[i], h[j]); + swap(pos2Id[i], pos2Id[j]); + swap(id2Pos[pos2Id[i]], id2Pos[pos2Id[j]]); +} + +void moveUp(int pos) { + while (pos > 0) { + int parent = (pos - 1) >> 1; + if (h[pos] >= h[parent]) { + break; + } + hswap(pos, parent); + pos = parent; + } +} + +void add(int id, int prio) { + h[hsize] = prio; + pos2Id[hsize] = id; + id2Pos[id] = hsize; + moveUp(hsize++); +} + +void increasePriority(int id, int prio) { + int pos = id2Pos[id]; + h[pos] = prio; + moveUp(pos); +} + +void moveDown(int pos) { + while (pos < (hsize >> 1)) { + int child = 2 * pos + 1; + if (child + 1 < hsize && h[child + 1] < h[child]) { + ++child; + } + if (h[pos] <= h[child]) { + break; + } + hswap(pos, child); + pos = child; + } +} + +int removeMin() { + int res = pos2Id[0]; + int lastNode = h[--hsize]; + if (hsize > 0) { + h[0] = lastNode; + int id = pos2Id[hsize]; + id2Pos[id] = 0; + pos2Id[0] = id; + moveDown(0); + } + return res; +} + +void dijkstra(int s) { + fill(pred, pred + maxnodes, -1); + fill(prio, prio + maxnodes, INT_MAX); + prio[s] = 0; + hsize = 0; + add(s, prio[s]); + + while (hsize) { + int u = removeMin(); + for (int e = last[u]; e >= 0; e = previous[e]) { + int v = head[e]; + int nprio = prio[u] + len[e]; + if (prio[v] > nprio) { + if (prio[v] == INT_MAX) + add(v, nprio); + else + increasePriority(v, nprio); + prio[v] = nprio; + pred[v] = u; + } + } + } +} + +int main() { + graphClear(); + addEdge(0, 1, 10); + addEdge(1, 2, -5); + addEdge(0, 2, 8); + + dijkstra(0); + + for (int i = 0; i < 3; i++) + cout << prio[i] << endl; +} diff --git a/c++/_Basic/DisjointSets.cpp b/c++/_Basic/DisjointSets.cpp new file mode 100644 index 0000000..58430c2 --- /dev/null +++ b/c++/_Basic/DisjointSets.cpp @@ -0,0 +1,36 @@ +#include +#include + +using namespace std; + +const int maxn = 200000; +int Rank[maxn]; +int p[maxn]; +int n; + +void init(int n) { + ::n = n; + fill(Rank, Rank + n, 0); + for (int i = 0; i < n; i++) p[i] = i; +} + +int root(int x) { + return x == p[x] ? x : (p[x] = root(p[x])); +} + +void unite(int a, int b) { + a = root(a); + b = root(b); + if (a == b) return; + if (Rank[a] < Rank[b]) swap(a, b); + if (Rank[a] == Rank[b]) ++Rank[a]; + p[b] = a; +} + +int main() { + init(3); + unite(0, 2); + cout << (0 == root(0)) << endl; + cout << (1 == root(1)) << endl; + cout << (0 == root(2)) << endl; +} diff --git a/c++/_Basic/FFT.cpp b/c++/_Basic/FFT.cpp new file mode 100644 index 0000000..5f8c93f --- /dev/null +++ b/c++/_Basic/FFT.cpp @@ -0,0 +1,137 @@ +// https://web.stanford.edu/~liszt90/acm/notebook.html#file16 +// Fast Fourier Transform : Used in many applications(one is fast polynomial multiplication) + +#include +#include +#include + +struct cpx +{ + cpx(){} + cpx(double aa):a(aa),b(0){} + cpx(double aa, double bb):a(aa),b(bb){} + double a; + double b; + double modsq(void) const + { + return a * a + b * b; + } + cpx bar(void) const + { + return cpx(a, -b); + } +}; + +cpx operator +(cpx a, cpx b) +{ + return cpx(a.a + b.a, a.b + b.b); +} + +cpx operator *(cpx a, cpx b) +{ + return cpx(a.a * b.a - a.b * b.b, a.a * b.b + a.b * b.a); +} + +cpx operator /(cpx a, cpx b) +{ + cpx r = a * b.bar(); + return cpx(r.a / b.modsq(), r.b / b.modsq()); +} + +cpx EXP(double theta) +{ + return cpx(cos(theta),sin(theta)); +} + +const double two_pi = 4 * acos(0); + +// in: input array +// out: output array +// step: {SET TO 1} (used internally) +// size: length of the input/output {MUST BE A POWER OF 2} +// dir: either plus or minus one (direction of the FFT) +// RESULT: out[k] = \sum_{j=0}^{size - 1} in[j] * exp(dir * 2pi * i * j * k / size) +void FFT(cpx *in, cpx *out, int step, int size, int dir) +{ + if(size < 1) return; + if(size == 1) + { + out[0] = in[0]; + return; + } + FFT(in, out, step * 2, size / 2, dir); + FFT(in + step, out + size / 2, step * 2, size / 2, dir); + for(int i = 0 ; i < size / 2 ; i++) + { + cpx even = out[i]; + cpx odd = out[i + size / 2]; + out[i] = even + EXP(dir * two_pi * i / size) * odd; + out[i + size / 2] = even + EXP(dir * two_pi * (i + size / 2) / size) * odd; + } +} + +// Usage: +// f[0...N-1] and g[0..N-1] are numbers +// Want to compute the convolution h, defined by +// h[n] = sum of f[k]g[n-k] (k = 0, ..., N-1). +// Here, the index is cyclic; f[-1] = f[N-1], f[-2] = f[N-2], etc. +// Let F[0...N-1] be FFT(f), and similarly, define G and H. +// The convolution theorem says H[n] = F[n]G[n] (element-wise product). +// To compute h[] in O(N log N) time, do the following: +// 1. Compute F and G (pass dir = 1 as the argument). +// 2. Get H by element-wise multiplying F and G. +// 3. Get h by taking the inverse FFT (use dir = -1 as the argument) +// and *dividing by N*. DO NOT FORGET THIS SCALING FACTOR. + +int main(void) +{ + printf("If rows come in identical pairs, then everything works.\n"); + + cpx a[8] = {0, 1, cpx(1,3), cpx(0,5), 1, 0, 2, 0}; + cpx b[8] = {1, cpx(0,-2), cpx(0,1), 3, -1, -3, 1, -2}; + cpx A[8]; + cpx B[8]; + FFT(a, A, 1, 8, 1); + FFT(b, B, 1, 8, 1); + + for(int i = 0 ; i < 8 ; i++) + { + printf("%7.2lf%7.2lf", A[i].a, A[i].b); + } + printf("\n"); + for(int i = 0 ; i < 8 ; i++) + { + cpx Ai(0,0); + for(int j = 0 ; j < 8 ; j++) + { + Ai = Ai + a[j] * EXP(j * i * two_pi / 8); + } + printf("%7.2lf%7.2lf", Ai.a, Ai.b); + } + printf("\n"); + + cpx AB[8]; + for(int i = 0 ; i < 8 ; i++) + AB[i] = A[i] * B[i]; + cpx aconvb[8]; + FFT(AB, aconvb, 1, 8, -1); + for(int i = 0 ; i < 8 ; i++) + aconvb[i] = aconvb[i] / 8; + for(int i = 0 ; i < 8 ; i++) + { + printf("%7.2lf%7.2lf", aconvb[i].a, aconvb[i].b); + } + printf("\n"); + for(int i = 0 ; i < 8 ; i++) + { + cpx aconvbi(0,0); + for(int j = 0 ; j < 8 ; j++) + { + aconvbi = aconvbi + a[j] * b[(8 + i - j) % 8]; + } + printf("%7.2lf%7.2lf", aconvbi.a, aconvbi.b); + } + printf("\n"); + + return 0; +} \ No newline at end of file diff --git a/c++/_Basic/FenwickTree.cpp b/c++/_Basic/FenwickTree.cpp new file mode 100644 index 0000000..519a86f --- /dev/null +++ b/c++/_Basic/FenwickTree.cpp @@ -0,0 +1,47 @@ +#include +using namespace std; + +const int maxn = 200000; +int t[maxn]; + +void add(int t[], int i, int value) { + for (; i < maxn; i |= i + 1) + t[i] += value; +} + +// sum[0,i] +int sum(int t[], int i) { + int res = 0; + for (; i >= 0; i = (i & (i + 1)) - 1) + res += t[i]; + return res; +} + +// Returns min(p|sum[0,p]>=sum) +int lower_bound(int t[], int sum) { + --sum; + int pos = -1; + for (int blockSize = 1 << 30; blockSize != 0; blockSize >>= 1) { + if (blockSize > maxn) continue; + int nextPos = pos + blockSize; + if (nextPos < maxn && sum >= t[nextPos]) { + sum -= t[nextPos]; + pos = nextPos; + } + } + return pos + 1; +} + + +// Usage example +int main() { + add(t, 0, 4); + add(t, 1, 5); + add(t, 2, 5); + add(t, 2, 5); + + cout << (4 == sum(t, 0)) << endl; + cout << (19 == sum(t, 2)) << endl; + cout << (2 == lower_bound(t, 19)) << endl; + cout << (maxn == lower_bound(t, 20)) << endl; +} diff --git a/c++/_Basic/FenwickTreeOnMap.cpp b/c++/_Basic/FenwickTreeOnMap.cpp new file mode 100644 index 0000000..20fab29 --- /dev/null +++ b/c++/_Basic/FenwickTreeOnMap.cpp @@ -0,0 +1,31 @@ +#include +#include +using namespace std; + +const int n = 2000000000; + +void add(map &t, int i, int value) { + for (; i < n; i |= i + 1) + t[i] += value; +} + +// sum[0,i] +int sum(map &t, int i) { + int res = 0; + for (; i >= 0; i = (i & (i + 1)) - 1) + if (t.count(i)) res += t[i]; + return res; +} + +// Usage example +int main() { + map t; + add(t, 0, 4); + add(t, 1, 5); + add(t, 2, 5); + add(t, 2, 5); + + cout << (4 == sum(t, 0)) << endl; + cout << (19 == sum(t, 2)) << endl; + cout << (19 == sum(t, 1000000000)) << endl; +} diff --git a/c++/_Basic/Find ASCII value of a character.cpp b/c++/_Basic/Find ASCII value of a character.cpp new file mode 100644 index 0000000..aff89da --- /dev/null +++ b/c++/_Basic/Find ASCII value of a character.cpp @@ -0,0 +1,12 @@ +#include +#include + +void main() +{ + clrscr(); + cout << "Size of char: " << sizeof(char) << " byte" << endl; + cout << "Size of int: " << sizeof(int) << " bytes" << endl; + cout << "Size of float: " << sizeof(float) << " bytes" << endl; + cout << "Size of double: " << sizeof(double) << " bytes" << endl; + getch(); +} \ No newline at end of file diff --git a/c++/_Basic/FindIntersection.cpp b/c++/_Basic/FindIntersection.cpp new file mode 100644 index 0000000..d7cdbe9 --- /dev/null +++ b/c++/_Basic/FindIntersection.cpp @@ -0,0 +1,103 @@ +#include +#include +#include +using namespace std; + +typedef pair pii; + +int cross(int ax, int ay, int bx, int by, int cx, int cy) { + return (bx - ax) * (cy - ay) - (by - ay) * (cx - ax); +} + +int cross(pii a, pii b, pii c) { + return cross(a.first, a.second, b.first, b.second, c.first, c.second); +} + +class segment { + public: + pii a, b; + int id; + segment(pii a, pii b, int id) : + a(a), b(b), id(id) { + } + bool operator<(const segment &o) const { + if (a.first < o.a.first) { + int s = cross(a, b, o.a); + return (s > 0 || s == 0 && a.second < o.a.second); + } else if (a.first > o.a.first) { + int s = cross(o.a, o.b, a); + return (s < 0 || s == 0 && a.second < o.a.second); + } + return a.second < o.a.second; + } +}; + +class event { + public: + pii p; + int id; + int type; + event(pii p, int id, int type) : + p(p), id(id), type(type) { + } + bool operator<(const event &o) const { + return p.first < o.p.first || p.first == o.p.first && (type > o.type || type == o.type && p.second < o.p.second); + } +}; + +bool intersect(segment s1, segment s2) { + int x1 = s1.a.first, y1 = s1.a.second, x2 = s1.b.first, y2 = s1.b.second; + int x3 = s2.a.first, y3 = s2.a.second, x4 = s2.b.first, y4 = s2.b.second; + if (max(x1, x2) < min(x3, x4) || max(x3, x4) < min(x1, x2) || max(y1, y2) < min(y3, y4) || max(y3, y4) < min(y1, y2)) { + return false; + } + int z1 = (x3 - x1) * (y2 - y1) - (y3 - y1) * (x2 - x1); + int z2 = (x4 - x1) * (y2 - y1) - (y4 - y1) * (x2 - x1); + if (z1 < 0 && z2 < 0 || z1 > 0 && z2 > 0) { + return false; + } + int z3 = (x1 - x3) * (y4 - y3) - (y1 - y3) * (x4 - x3); + int z4 = (x2 - x3) * (y4 - y3) - (y2 - y3) * (x4 - x3); + if (z3 < 0 && z4 < 0 || z3 > 0 && z4 > 0) { + return false; + } + return true; +} + +pii findIntersection(vector s) { + int n = s.size(); + vector e; + for (int i = 0; i < n; ++i) { + if (s[i].a > s[i].b) + swap(s[i].a, s[i].b); + e.push_back(event(s[i].a, i, 1)); + e.push_back(event(s[i].b, i, -1)); + } + sort(e.begin(), e.end()); + + set q; + + for (int i = 0; i < n * 2; ++i) { + int id = e[i].id; + if (e[i].type == 1) { + set::iterator it = q.lower_bound(s[id]); + if (it != q.end() && intersect(*it, s[id])) + return make_pair(it->id, s[id].id); + if (it != q.begin() && intersect(*--it, s[id])) + return make_pair(it->id, s[id].id); + q.insert(s[id]); + } else { + set::iterator it = q.lower_bound(s[id]), next = it, prev = it; + if (it != q.begin() && it != --q.end()) { + ++next, --prev; + if (intersect(*next, *prev)) + return make_pair(next->id, prev->id); + } + q.erase(it); + } + } + return make_pair(-1, -1); +} + +int main() { +} diff --git a/c++/_Basic/Get IP Address.cpp b/c++/_Basic/Get IP Address.cpp new file mode 100644 index 0000000..715508f --- /dev/null +++ b/c++/_Basic/Get IP Address.cpp @@ -0,0 +1,8 @@ +#include + +int main() +{ + system("C:\\Windows\\System32\\ipconfig"); + /* ipconfig command to get ip of system */ + return 0; +} \ No newline at end of file diff --git a/c++/_Basic/Hcf & Lcm.cpp b/c++/_Basic/Hcf & Lcm.cpp new file mode 100644 index 0000000..effa3e5 --- /dev/null +++ b/c++/_Basic/Hcf & Lcm.cpp @@ -0,0 +1,36 @@ +#include < iostream.h > + +long gcd(long, long); +int main() +{ + long x, y, hcf, lcm; + cout<<"Enter two integers\n"; + cin>>x>>y; + hcf = gcd(x, y); + lcm = (x*y)/hcf; + cout<<"Greatest common divisor of "< y) + { + x = x - y; + } + else + { + y = y - x; + } + } + return x; +} \ No newline at end of file diff --git a/c++/_Basic/KdTree.cpp b/c++/_Basic/KdTree.cpp new file mode 100644 index 0000000..bee5ab4 --- /dev/null +++ b/c++/_Basic/KdTree.cpp @@ -0,0 +1,103 @@ +#include +#include +#include +#include +using namespace std; + +typedef pair pii; +typedef vector vpii; + +const int maxn = 100000; +int tx[maxn]; +int ty[maxn]; +bool divX[maxn]; + +bool cmpX(const pii &a, const pii &b) { + return a.first < b.first; +} + +bool cmpY(const pii &a, const pii &b) { + return a.second < b.second; +} + +void buildTree(int left, int right, pii points[]) { + if (left >= right) + return; + int mid = (left + right) >> 1; + + //sort(points + left, points + right + 1, divX ? cmpX : cmpY); + int minx = INT_MAX; + int maxx = INT_MIN; + int miny = INT_MAX; + int maxy = INT_MIN; + for (int i = left; i < right; i++) { + checkmin(minx, points[i].first); + checkmax(maxx, points[i].first); + checkmin(miny, points[i].second); + checkmax(maxy, points[i].second); + } + divX[mid] = (maxx - minx) >= (maxy - miny); + nth_element(points + left, points + mid, points + right, divX[mid] ? cmpX : cmpY); + + tx[mid] = points[mid].first; + ty[mid] = points[mid].second; + + if (left + 1 == right) + return; + buildTree(left, mid, points); + buildTree(mid + 1, right, points); +} + +long long closestDist; +int closestNode; + +void findNearestNeighbour(int left, int right, int x, int y) { + if (left >= right) + return; + int mid = (left + right) >> 1; + int dx = x - tx[mid]; + int dy = y - ty[mid]; + long long d = dx * (long long) dx + dy * (long long) dy; + if (closestDist > d && d) { + closestDist = d; + closestNode = mid; + } + if (left + 1 == right) + return; + + int delta = divX[mid] ? dx : dy; + long long delta2 = delta * (long long) delta; + int l1 = left; + int r1 = mid; + int l2 = mid + 1; + int r2 = right; + if (delta > 0) + swap(l1, l2), swap(r1, r2); + + findNearestNeighbour(l1, r1, x, y); + if (delta2 < closestDist) + findNearestNeighbour(l2, r2, x, y); +} + +int findNearestNeighbour(int n, int x, int y) { + closestDist = LLONG_MAX; + findNearestNeighbour(0, n, x, y); + return closestNode; +} + +int main() { + vpii p; + p.push_back(make_pair(0, 2)); + p.push_back(make_pair(0, 3)); + p.push_back(make_pair(-1, 0)); + + p.resize(unique(p.begin(), p.end()) - p.begin()); + + int n = p.size(); + buildTree(1, 0, n - 1, &(vpii(p)[0])); + int res = findNearestNeighbour(n, 0, 0); + + cout << p[res].first << " " << p[res].second << endl; + + return 0; +} diff --git a/c++/_Basic/Manacher.cpp b/c++/_Basic/Manacher.cpp new file mode 100644 index 0000000..019c57f --- /dev/null +++ b/c++/_Basic/Manacher.cpp @@ -0,0 +1,65 @@ +// Linear Time algorithms for longestPalindrome in a string problem. It is one of the standard algorithms but is not very intuitive. + +#include +#include +#include +using namespace std; + + +// Transform S into T. +// For example, S = "abba", T = "^#a#b#b#a#$". +// ^ and $ signs are sentinels appended to each end to avoid bounds checking + +string preProcess(string s) { + int n = s.length(); + if (n == 0) return "^$"; + string ret = "^"; + for (int i = 0; i < n; i++) + ret += "#" + s.substr(i, 1); + + ret += "#$"; + return ret; +} + +string longestPalindrome(string s) { + string T = preProcess(s); + int n = T.length(); + int *P = new int[n]; + int C = 0, R = 0; + for (int i = 1; i < n-1; i++) { + int i_mirror = 2*C-i; // equals to i' = C - (i-C) + + P[i] = (R > i) ? min(R-i, P[i_mirror]) : 0; + + // Attempt to expand palindrome centered at i + while (T[i + 1 + P[i]] == T[i - 1 - P[i]]) + P[i]++; + + // If palindrome centered at i expand past R, + // adjust center based on expanded palindrome. + if (i + P[i] > R) { + C = i; + R = i + P[i]; + } + } + + // Find the maximum element in P. + int maxLen = 0; + int centerIndex = 0; + for (int i = 1; i < n-1; i++) { + if (P[i] > maxLen) { + maxLen = P[i]; + centerIndex = i; + } + } + delete[] P; + + return s.substr((centerIndex - 1 - maxLen)/2, maxLen); +} + + +int main() { + string text = "babcbabcbaccba"; + std::cout << longestPalindrome(text)<< endl; + +} \ No newline at end of file diff --git a/c++/_Basic/Matrix.cpp b/c++/_Basic/Matrix.cpp new file mode 100644 index 0000000..af155bb --- /dev/null +++ b/c++/_Basic/Matrix.cpp @@ -0,0 +1,62 @@ +#include +#include +using namespace std; + +typedef vector vi; +typedef vector vvi; + +const int mod = 1234567891; + +vvi matrixUnit(int n) { + vvi res(n, vi(n)); + for (int i = 0; i < n; i++) + res[i][i] = 1; + return res; +} + +vvi matrixAdd(const vvi &a, const vvi &b) { + int n = a.size(); + int m = a[0].size(); + vvi res(n, vi(m)); + for (int i = 0; i < n; i++) + for (int j = 0; j < m; j++) + res[i][j] = (a[i][j] + b[i][j]) % mod; + return res; +} + +vvi matrixMul(const vvi &a, const vvi &b) { + int n = a.size(); + int m = a[0].size(); + int k = b[0].size(); + vvi res(n, vi(k)); + for (int i = 0; i < n; i++) + for (int j = 0; j < k; j++) + for (int p = 0; p < m; p++) + res[i][j] = (res[i][j] + (long long) a[i][p] * b[p][j]) % mod; + return res; +} + +vvi matrixPow(const vvi &a, int p) { + if (p == 0) + return matrixUnit(a.size()); + if (p & 1) + return matrixMul(a, matrixPow(a, p - 1)); + return matrixPow(matrixMul(a, a), p / 2); +} + +vvi matrixPowSum(const vvi &a, int p) { + int n = a.size(); + if (p == 0) + return vvi(n, vi(n)); + if (p % 2 == 0) + return matrixMul(matrixPowSum(a, p / 2), matrixAdd(matrixUnit(n), matrixPow(a, p / 2))); + return matrixAdd(a, matrixMul(matrixPowSum(a, p - 1), a)); +} + +int main() { + vvi a(2, vi(2)); + a[0][0] = 1; + a[0][1] = 1; + a[1][0] = 1; + vvi b = matrixPow(a, 10); +} diff --git a/c++/_Basic/MaxFlowDinic.cpp b/c++/_Basic/MaxFlowDinic.cpp new file mode 100644 index 0000000..6d66182 --- /dev/null +++ b/c++/_Basic/MaxFlowDinic.cpp @@ -0,0 +1,87 @@ +#include +#include +#include +#include +using namespace std; + +const int maxnodes = 5000; + +int nodes = maxnodes, src, dest; +int dist[maxnodes], q[maxnodes], work[maxnodes]; + +struct Edge { + int to, rev; + int f, cap; +}; + +vector g[maxnodes]; + +// Adds bidirectional edge +void addEdge(int s, int t, int cap){ + Edge a = {t, g[t].size(), 0, cap}; + Edge b = {s, g[s].size(), 0, cap}; + g[s].push_back(a); + g[t].push_back(b); +} + +bool dinic_bfs() { + fill(dist, dist + nodes, -1); + dist[src] = 0; + int qt = 0; + q[qt++] = src; + for (int qh = 0; qh < qt; qh++) { + int u = q[qh]; + for (int j = 0; j < (int) g[u].size(); j++) { + Edge &e = g[u][j]; + int v = e.to; + if (dist[v] < 0 && e.f < e.cap) { + dist[v] = dist[u] + 1; + q[qt++] = v; + } + } + } + return dist[dest] >= 0; +} + +int dinic_dfs(int u, int f) { + if (u == dest) + return f; + for (int &i = work[u]; i < (int) g[u].size(); i++) { + Edge &e = g[u][i]; + if (e.cap <= e.f) continue; + int v = e.to; + if (dist[v] == dist[u] + 1) { + int df = dinic_dfs(v, min(f, e.cap - e.f)); + if (df > 0) { + e.f += df; + g[v][e.rev].f -= df; + return df; + } + } + } + return 0; +} + +int maxFlow(int _src, int _dest) { + src = _src; + dest = _dest; + int result = 0; + while (dinic_bfs()) { + fill(work, work + nodes, 0); + while (int delta = dinic_dfs(src, INT_MAX)) + result += delta; + } + return result; +} + +int main() { + int n = 3; + nodes = n; + + int capacity[][3] = { { 0, 3, 2 }, { 0, 0, 2 }, { 0, 0, 0 } }; + for (int i = 0; i < n; i++) + for (int j = 0; j < n; j++) + if (capacity[i][j] != 0) + addEdge(i, j, capacity[i][j]); + cout << (4 == maxFlow(0, 2)) << endl; +} diff --git a/c++/_Basic/MaxMatching.cpp b/c++/_Basic/MaxMatching.cpp new file mode 100644 index 0000000..902ce0f --- /dev/null +++ b/c++/_Basic/MaxMatching.cpp @@ -0,0 +1,86 @@ +#include +#include + +using namespace std; + +const int MAXN1 = 50000; +const int MAXN2 = 50000; +const int MAXM = 150000; + +int n1, n2, edges, last[MAXN1], prev[MAXM], head[MAXM]; +int matching[MAXN2], dist[MAXN1], Q[MAXN1]; +bool used[MAXN1], vis[MAXN1]; + +void init(int _n1, int _n2) { + n1 = _n1; + n2 = _n2; + edges = 0; + fill(last, last + n1, -1); +} + +void addEdge(int u, int v) { + head[edges] = v; + prev[edges] = last[u]; + last[u] = edges++; +} + +void bfs() { + fill(dist, dist + n1, -1); + int sizeQ = 0; + for (int u = 0; u < n1; ++u) { + if (!used[u]) { + Q[sizeQ++] = u; + dist[u] = 0; + } + } + for (int i = 0; i < sizeQ; i++) { + int u1 = Q[i]; + for (int e = last[u1]; e >= 0; e = prev[e]) { + int u2 = matching[head[e]]; + if (u2 >= 0 && dist[u2] < 0) { + dist[u2] = dist[u1] + 1; + Q[sizeQ++] = u2; + } + } + } +} + +bool dfs(int u1) { + vis[u1] = true; + for (int e = last[u1]; e >= 0; e = prev[e]) { + int v = head[e]; + int u2 = matching[v]; + if (u2 < 0 || !vis[u2] && dist[u2] == dist[u1] + 1 && dfs(u2)) { + matching[v] = u1; + used[u1] = true; + return true; + } + } + return false; +} + +int maxMatching() { + fill(used, used + n1, false); + fill(matching, matching + n2, -1); + for (int res = 0;;) { + bfs(); + fill(vis, vis + n1, false); + int f = 0; + for (int u = 0; u < n1; ++u) + if (!used[u] && dfs(u)) + ++f; + if (!f) + return res; + res += f; + } +} + +int main() { + init(2, 2); + + addEdge(0, 0); + addEdge(0, 1); + addEdge(1, 1); + + cout << (2 == maxMatching()) << endl; +} diff --git a/c++/_Basic/MinCostFlow.cpp b/c++/_Basic/MinCostFlow.cpp new file mode 100644 index 0000000..55f8ed1 --- /dev/null +++ b/c++/_Basic/MinCostFlow.cpp @@ -0,0 +1,121 @@ +#include +#include +#include +#include +using namespace std; + +typedef long long ll; +typedef pair pii; + +const int maxnodes = 200000; + +int nodes = maxnodes; +int prio[maxnodes], curflow[maxnodes], prevedge[maxnodes], prevnode[maxnodes], q[maxnodes], pot[maxnodes]; +bool inqueue[maxnodes]; + +struct Edge { + int to, f, cap, cost, rev; +}; + +vector graph[maxnodes]; + +void addEdge(int s, int t, int cap, int cost) { + Edge a = {t, 0, cap, cost, graph[t].size()}; + Edge b = {s, 0, 0, -cost, graph[s].size()}; + graph[s].push_back(a); + graph[t].push_back(b); +} + +void bellmanFord(int s, int dist[]) { + fill(dist, dist + nodes, INT_MAX); + dist[s] = 0; + int qt = 0; + q[qt++] = s; + for (int qh = 0; (qh - qt) % nodes != 0; qh++) { + int u = q[qh % nodes]; + inqueue[u] = false; + for (int i = 0; i < (int) graph[u].size(); i++) { + Edge &e = graph[u][i]; + if (e.cap <= e.f) continue; + int v = e.to; + int ndist = dist[u] + e.cost; + if (dist[v] > ndist) { + dist[v] = ndist; + if (!inqueue[v]) { + inqueue[v] = true; + q[qt++ % nodes] = v; + } + } + } + } +} + +pii minCostFlow(int s, int t, int maxf) { + // bellmanFord can be safely commented if edges costs are non-negative + bellmanFord(s, pot); + int flow = 0; + int flowCost = 0; + while (flow < maxf) { + priority_queue, greater > q; + q.push(s); + fill(prio, prio + nodes, INT_MAX); + prio[s] = 0; + curflow[s] = INT_MAX; + while (!q.empty()) { + ll cur = q.top(); + int d = cur >> 32; + int u = cur; + q.pop(); + if (d != prio[u]) + continue; + for (int i = 0; i < (int) graph[u].size(); i++) { + Edge &e = graph[u][i]; + int v = e.to; + if (e.cap <= e.f) continue; + int nprio = prio[u] + e.cost + pot[u] - pot[v]; + if (prio[v] > nprio) { + prio[v] = nprio; + q.push(((ll) nprio << 32) + v); + prevnode[v] = u; + prevedge[v] = i; + curflow[v] = min(curflow[u], e.cap - e.f); + } + } + } + if (prio[t] == INT_MAX) + break; + for (int i = 0; i < nodes; i++) + pot[i] += prio[i]; + int df = min(curflow[t], maxf - flow); + flow += df; + for (int v = t; v != s; v = prevnode[v]) { + Edge &e = graph[prevnode[v]][prevedge[v]]; + e.f += df; + graph[v][e.rev].f -= df; + flowCost += df * e.cost; + } + } + return make_pair(flow, flowCost); +} + +// Usage example + +int main() { + int capacity[3][3] = { + { 0, 3, 2}, + { 0, 0, 2}, + { 0, 0, 0} + }; + nodes = 3; + for (int i = 0; i < nodes; i++) + for (int j = 0; j < nodes; j++) + if (capacity[i][j] != 0) + addEdge(i, j, capacity[i][j], 1); + int s = 0; + int t = 2; + pii res = minCostFlow(s, t, INT_MAX); + int flow = res.first; + int flowCost = res.second; + cout << (4 == flow) << endl; + cout << (6 == flowCost) << endl; +} diff --git a/c++/_Basic/MinCostFlowBF.cpp b/c++/_Basic/MinCostFlowBF.cpp new file mode 100644 index 0000000..14a8fb0 --- /dev/null +++ b/c++/_Basic/MinCostFlowBF.cpp @@ -0,0 +1,92 @@ +#include +#include +#include +#include +using namespace std; + +typedef long long ll; +typedef pair pii; + +const int maxnodes = 200000; + +int nodes = maxnodes; +int prio[maxnodes], curflow[maxnodes], prevedge[maxnodes], prevnode[maxnodes], q[maxnodes]; +bool inqueue[maxnodes]; + +struct Edge { + int to, f, cap, cost, rev; +}; + +vector graph[maxnodes]; + +void addEdge(int s, int t, int cap, int cost){ + Edge a = {t, 0, cap, cost, graph[t].size()}; + Edge b = {s, 0, 0, -cost, graph[s].size()}; + graph[s].push_back(a); + graph[t].push_back(b); +} + +void bellmanFord(int s) { + fill(prio, prio + nodes, INT_MAX); + prio[s] = 0; + int qt = 0; + q[qt++] = s; + for (int qh = 0; (qh - qt) % nodes != 0; qh++) { + int u = q[qh % nodes]; + inqueue[u] = false; + for (int i = 0; i < (int) graph[u].size(); i++) { + Edge &e = graph[u][i]; + if(e.cap <= e.f) continue; + int v = e.to; + int ndist = prio[u] + e.cost; + if (prio[v] > ndist) { + prio[v] = ndist; + prevnode[v] = u; + prevedge[v] = i; + curflow[v] = min(curflow[u], e.cap - e.f); + if (!inqueue[v]) { + inqueue[v] = true; + q[qt++ % nodes] = v; + } + } + } + } +} + +pii minCostFlow(int s, int t, int maxf) { + int flow = 0; + int flowCost = 0; + while (flow < maxf) { + curflow[s] = INT_MAX; + bellmanFord(s); + if (prio[t] == INT_MAX) + break; + int df = min(curflow[t], maxf - flow); + flow += df; + for (int v = t; v != s; v = prevnode[v]) { + Edge &e = graph[prevnode[v]][prevedge[v]]; + e.f += df; + graph[v][e.rev].f -= df; + flowCost += df * e.cost; + } + } + return make_pair(flow, flowCost); +} + +// Usage example +int main() { + int capacity[3][3] = { { 0, 3, 2 }, { 0, 0, 2 }, { 0, 0, 0 } }; + int n = 3; + nodes = n; + for (int i = 0; i < n; i++) + for (int j = 0; j < n; j++) + if (capacity[i][j] != 0) + addEdge(i, j, capacity[i][j], 1); + int s = 0; + int t = 2; + pii res = minCostFlow(s, t, INT_MAX); + int flow = res.first; + int flowCost = res.second; + cout << (4 == flow) << endl; + cout << (6 == flowCost) << endl; +} diff --git a/c++/_Basic/Odd or Even.cpp b/c++/_Basic/Odd or Even.cpp new file mode 100644 index 0000000..b45484b --- /dev/null +++ b/c++/_Basic/Odd or Even.cpp @@ -0,0 +1,19 @@ +#include +#include + +void main() +{ + clrscr(); + int n; + cout << "Enter an integer: "; + cin >> n; + if ( n%2 == 0) + { + cout << n << " is even."; + } + else + { + cout << n << " is odd."; + } + getch(); +} \ No newline at end of file diff --git a/c++/_Basic/Pattern 1.cpp b/c++/_Basic/Pattern 1.cpp new file mode 100644 index 0000000..14c8278 --- /dev/null +++ b/c++/_Basic/Pattern 1.cpp @@ -0,0 +1,18 @@ +#include +#include +void main() +{ + clrscr(); //clears the previous screen +//Printing first pattern (Floyds triangle) + int rows,i,j,k=0; + cout<<"Enter number of rows: "; + cin>>rows; + for(i=1; i<=rows; i++) + { + for(j=1; j<=i; ++j) + cout< +#include +void main() +{ + clrscr(); //clears the previous screen +//Printing pattern + int rows,i,j,space; + cout<<"Enter number of rows: "; + cin>>rows; + for(i=rows; i>=1; --i) + { + for(space=0; space +#include +void main() +{ + clrscr(); //clears the previous screen +//Printing first pattern (Pascals triangle) + int rows,coef=1,space,i,j; + cout<<"Enter number of rows: "; + cin>>rows; + for(i=0; i +#include +void main() +{ + clrscr(); //clears the previous screen +//Printing pattern + int i,j,rows; + cout<<"Enter the number of rows: "; + cin>>rows; + for(i=1; i<=rows; ++i) + { + for(j=1; j<=i; ++j) + { + cout<<"* "; + } + cout<<"\n"; + } + getch(); // wait for input +} + +/* +* +** +*** +**** +***** +*/ \ No newline at end of file diff --git a/c++/_Basic/Pattern 4.cpp b/c++/_Basic/Pattern 4.cpp new file mode 100644 index 0000000..b19e5bc --- /dev/null +++ b/c++/_Basic/Pattern 4.cpp @@ -0,0 +1,27 @@ +#include +#include +void main() +{ + clrscr(); //clears the previous screen +//Printing pattern + int i,j,rows; + cout<<"Enter the number of rows: "; + cin>>rows; + for(i=1; i<=rows; ++i) + { + for(j=1; j<=i; ++j) + { + cout< +#include +void main() +{ + clrscr(); //clears the previous screen +//Printing pattern + int i,j; + char input,temp='A'; + cout<<"Enter uppercase character you want in triange at last row: "; + cin>>input; + for(i=1; i<=(input-'A'+1); ++i) + { + for(j=1; j<=i; ++j) + cout< +#include +void main() +{ + clrscr(); //clears the previous screen +//Printing pattern + int i,j,rows; + cout<<"Enter the number of rows: "; + cin>>rows; + for(i=rows; i>=1; --i) + { + for(j=1; j<=i; ++j) + { + cout<<"* "; + } + cout<<"\n"; + } + getch(); // wait for input +} + +/* +***** +**** +*** +** +* +*/ \ No newline at end of file diff --git a/c++/_Basic/Pattern 7.cpp b/c++/_Basic/Pattern 7.cpp new file mode 100644 index 0000000..e0a3366 --- /dev/null +++ b/c++/_Basic/Pattern 7.cpp @@ -0,0 +1,27 @@ +#include +#include +void main() +{ + clrscr(); //clears the previous screen +//Printing pattern + int i,j,rows; + cout<<"Enter the number of rows: "; + cin>>rows; + for(i=rows; i>=1; --i) + { + for(j=1; j<=i; ++j) + { + cout< +#include +void main() +{ + clrscr(); //clears the previous screen +//Printing pattern + int i,space,rows,k=0; + cout<<"Enter the number of rows: "; + cin>>rows; + for(i=1; i<=rows; ++i) + { + for(space=1; space<=rows-i; ++space) + { + cout<<" "; + } + while(k!=2*i-1) + { + cout<<"* "; + ++k; + } + k=0; + cout<<"\n"; + } + getch(); // wait for input +} + +/* + * + *** + ***** + ******* + ********* + + */ \ No newline at end of file diff --git a/c++/_Basic/Pattern 9.cpp b/c++/_Basic/Pattern 9.cpp new file mode 100644 index 0000000..b37dc7b --- /dev/null +++ b/c++/_Basic/Pattern 9.cpp @@ -0,0 +1,44 @@ +#include +#include +void main() +{ + clrscr(); //clears the previous screen +//Printing pattern + int i,space,rows,k=0,count=0,count1=0; + cout<<"Enter the number of rows: "; + cin>>rows; + for(i=1; i<=rows; ++i) + { + for(space=1; space<=rows-i; ++space) + { + cout<<" "; + ++count; + } + while(k!=2*i-1) + { + if (count<=rows-1) + { + cout< +#include +#include +#include +using namespace std; + +typedef pair pii; +typedef vector > Graph; + +long long prim(Graph &g, vector &pred) { + int n = g.size(); + pred.assign(n, -1); + vector vis(n); + vector prio(n, INT_MAX); + prio[0] = 0; + priority_queue , greater > q; + q.push(make_pair(prio[0] , 0)); + long long res = 0; + + while (!q.empty()) { + int d = q.top().first; + int u = q.top().second; + q.pop(); + if (vis[u]) + continue; + vis[u] = true; + res += d; + for (int i = 0; i < (int) g[u].size(); i++) { + int v = g[u][i].first; + if (vis[v]) + continue; + int nprio = g[u][i].second; + if (prio[v] > nprio) { + prio[v] = nprio; + pred[v] = u; + q.push(make_pair(nprio, v)); + } + } + } + return res; +} + +int main() { + Graph g(3); + g[0].push_back(make_pair(1, 10)); + g[1].push_back(make_pair(0, 10)); + g[1].push_back(make_pair(2, 10)); + g[2].push_back(make_pair(1, 10)); + g[2].push_back(make_pair(0, 5)); + g[0].push_back(make_pair(2, 5)); + + vector pred; + long long res = prim(g, pred); + cout << res << endl; +} diff --git a/c++/_Basic/PrimesGenerator.cpp b/c++/_Basic/PrimesGenerator.cpp new file mode 100644 index 0000000..2bedb8a --- /dev/null +++ b/c++/_Basic/PrimesGenerator.cpp @@ -0,0 +1,43 @@ +#include +#include +using namespace std; + +vector getPrimes(int n) { + if (n <= 1) + return vector(); + vector prime(n + 1, true); + prime[0] = prime[1] = false; + vector primes; + for (int i = 2; i * i <= n; i++) + if (prime[i]) { + for (int j = i * i; j <= n; j += i) + prime[j] = false; + primes.push_back(i); + } + return primes; +} + +bool isPrime(long long n) { + if (n <= 1) + return false; + + for (long long i = 2; i * i <= n; i++) + if (n % i == 0) + return false; + + return true; +} + +int main() { + int n = 31; + vector primes = getPrimes(n); + + for (int i = 0; i < primes.size(); i++) + cout << primes[i] << " "; + + cout << endl; + + for (int i = 0; i <= n; i++) + if (isPrime(i)) + cout << i << " "; +} diff --git a/c++/_Basic/Scanner.cpp b/c++/_Basic/Scanner.cpp new file mode 100644 index 0000000..b6b81ad --- /dev/null +++ b/c++/_Basic/Scanner.cpp @@ -0,0 +1,53 @@ +#include +#include + +const int BUF_SIZE = 65536; +char input[BUF_SIZE]; + +struct Scanner { + char* curPos; + + Scanner() { + fread(input, 1, sizeof(input), stdin); + curPos = input; + } + + void ensureCapacity() { + int size = input + BUF_SIZE - curPos; + if (size < 100) { + memcpy(input, curPos, size); + fread(input + size, 1, BUF_SIZE - size, stdin); + curPos = input; + } + } + + int nextInt() { + ensureCapacity(); + while (*curPos <= ' ') + ++curPos; + bool sign = false; + if (*curPos == '-') { + sign = true; + ++curPos; + } + int res = 0; + while (*curPos > ' ') + res = res * 10 + (*(curPos++) & 15); + return sign ? -res : res; + } + + char nextChar() { + ensureCapacity(); + while (*curPos <= ' ') + ++curPos; + return *(curPos++); + } +}; + +int main() { + Scanner sc; + int a = sc.nextInt(); + char b = sc.nextChar(); + + printf("%d %c\n", a, b); +} diff --git a/c++/_Basic/Shutdown Computer.cpp b/c++/_Basic/Shutdown Computer.cpp new file mode 100644 index 0000000..2690b57 --- /dev/null +++ b/c++/_Basic/Shutdown Computer.cpp @@ -0,0 +1,14 @@ +/* for windows 7 only */ +#include < iostream.h > +#include < stdlib.h > + +main() +{ + char ch; + cout<<"Do you want to shutdown your computer now (y/n)\n"; + cin>>ch; + if (ch == 'y' || ch == 'Y') + system("C:\\WINDOWS\\System32\\shutdown /s"); + /*shutdown command*/ + return 0; +} \ No newline at end of file diff --git a/c++/_Basic/SuffixArrayLcp.cpp b/c++/_Basic/SuffixArrayLcp.cpp new file mode 100644 index 0000000..192c60a --- /dev/null +++ b/c++/_Basic/SuffixArrayLcp.cpp @@ -0,0 +1,162 @@ +#include +#include +#include +using namespace std; + +unsigned char mask[] = { 0x80, 0x40, 0x20, 0x10, 0x08, 0x04, 0x02, 0x01 }; +#define tget(i) ( (t[(i)/8]&mask[(i)%8]) ? 1 : 0 ) +#define tset(i, b) t[(i)/8]=(b) ? (mask[(i)%8]|t[(i)/8]) : ((~mask[(i)%8])&t[(i)/8]) +#define chr(i) (cs==sizeof(int)?((int*)s)[i]:((unsigned char *)s)[i]) +#define isLMS(i) (i>0 && tget(i) && !tget(i-1)) + +// find the start or end of each bucket +void getBuckets(unsigned char *s, int *bkt, int n, int K, int cs, bool end) { + int i, sum = 0; + for (i = 0; i <= K; i++) + bkt[i] = 0; // clear all buckets + for (i = 0; i < n; i++) + bkt[chr(i)]++; // compute the size of each bucket + for (i = 0; i <= K; i++) { + sum += bkt[i]; + bkt[i] = end ? sum : sum - bkt[i]; + } +} +// compute SAl +void induceSAl(unsigned char *t, int *SA, unsigned char *s, int *bkt, int n, int K, int cs, bool end) { + int i, j; + getBuckets(s, bkt, n, K, cs, end); // find starts of buckets + for (i = 0; i < n; i++) { + j = SA[i] - 1; + if (j >= 0 && !tget(j)) + SA[bkt[chr(j)]++] = j; + } +} +// compute SAs +void induceSAs(unsigned char *t, int *SA, unsigned char *s, int *bkt, int n, int K, int cs, bool end) { + int i, j; + getBuckets(s, bkt, n, K, cs, end); // find ends of buckets + for (i = n - 1; i >= 0; i--) { + j = SA[i] - 1; + if (j >= 0 && tget(j)) + SA[--bkt[chr(j)]] = j; + } +} + +// find the suffix array SA of s[0..n-1] in {1..K}^n +// require s[n-1]=0 (the sentinel!), n>=2 +// use a working space (excluding s and SA) of at most 2.25n+O(1) for a constant alphabet +void SA_IS(unsigned char *s, int *SA, int n, int K, int cs) { + int i, j; + unsigned char *t = (unsigned char *) malloc(n / 8 + 1); // LS-type array in bits + // Classify the type of each character + tset(n-2, 0); + tset(n-1, 1); // the sentinel must be in s1, important!!! + for (i = n - 3; i >= 0; i--) + tset(i, (chr(i) 0 && (isLMS(pos+d) || isLMS(prev+d))) + break; + if (diff) { + name++; + prev = pos; + } + pos = (pos % 2 == 0) ? pos / 2 : (pos - 1) / 2; + SA[n1 + pos] = name - 1; + } + for (i = n - 1, j = n - 1; i >= n1; i--) + if (SA[i] >= 0) + SA[j--] = SA[i]; + // stage 2: solve the reduced problem + // recurse if names are not yet unique + int *SA1 = SA, *s1 = SA + n - n1; + if (name < n1) + SA_IS((unsigned char*) s1, SA1, n1, name - 1, sizeof(int)); + else + // generate the suffix array of s1 directly + for (i = 0; i < n1; i++) + SA1[s1[i]] = i; + // stage 3: induce the result for the original problem + bkt = (int *) malloc(sizeof(int) * (K + 1)); // bucket array + // put all left-most S characters into their buckets + getBuckets(s, bkt, n, K, cs, true); // find ends of buckets + for (i = 1, j = 0; i < n; i++) + if (isLMS(i)) + s1[j++] = i; // get p1 + for (i = 0; i < n1; i++) + SA1[i] = s1[SA1[i]]; // get index in s + for (i = n1; i < n; i++) + SA[i] = -1; // init SA[n1..n-1] + for (i = n1 - 1; i >= 0; i--) { + j = SA[i]; + SA[i] = -1; + SA[--bkt[chr(j)]] = j; + } + induceSAl(t, SA, s, bkt, n, K, cs, false); + induceSAs(t, SA, s, bkt, n, K, cs, true); + free(bkt); + free(t); +} + +const int maxn = 200000; +int sa[maxn]; +int lcp[maxn]; +int Rank[maxn]; +unsigned char *s; +int n; + +void calc_lcp() { + for (int i = 0; i < n; i++) + Rank[sa[i]] = i; + for (int i = 0, h = 0; i < n; i++) { + if (Rank[i] < n - 1) { + for (int j = sa[Rank[i] + 1]; s[i + h] == s[j + h]; ++h) + ; + lcp[Rank[i]] = h; + if (h > 0) + --h; + } + } +} + +int main() { + string str = "abcab"; + n = str.size(); + s = (unsigned char*) str.c_str(); + SA_IS(s, sa, n + 1, 256, 1); + calc_lcp(); + + for (int i = 0; i < n; i++) { + cout << str.substr(sa[i + 1]); + if (i < n - 1) + cout << " " << lcp[i + 1]; + cout << endl; + } +} diff --git a/c++/_Basic/TreeIsomorphism.cpp b/c++/_Basic/TreeIsomorphism.cpp new file mode 100644 index 0000000..2c16596 --- /dev/null +++ b/c++/_Basic/TreeIsomorphism.cpp @@ -0,0 +1,164 @@ +#include +#include +#include + +using namespace std; + +typedef vector vi; +typedef vector vvi; + +vvi children, subtreeLabels, tree, L; +vi pred, map; +int n; + +bool compare(int a, int b) { + return subtreeLabels[a] < subtreeLabels[b]; +} + +bool equals(int a, int b) { + return subtreeLabels[a] == subtreeLabels[b]; +} + +void generateMapping(int r1, int r2) { + map.resize(n); + map[r1] = r2 - n; + sort(children[r1].begin(), children[r1].end(), compare); + sort(children[r2].begin(), children[r2].end(), compare); + for (int i = 0; i < (int) children[r1].size(); i++) { + int u = children[r1][i]; + int v = children[r2][i]; + generateMapping(u, v); + } +} + +vi findCenter(int offset = 0) { + int cnt = n; + vi a; + vi deg(n); + for (int i = 0; i < n; i++) { + deg[i] = tree[i + offset].size(); + if (deg[i] <= 1) { + a.push_back(i + offset); + --cnt; + } + } + while (cnt > 0) { + vi na; + for (int i = 0; i < (int) a.size(); i++) { + int u = a[i]; + for (int j = 0; j < (int) tree[u].size(); j++) { + int v = tree[u][j]; + if (--deg[v - offset] == 1) { + na.push_back(v); + --cnt; + } + } + } + a = na; + } + return a; +} + +int dfs(int u, int p = -1, int depth = 0) { + L[depth].push_back(u); + int h = 0; + for (int i = 0; i < (int) tree[u].size(); i++) { + int v = tree[u][i]; + if (v == p) + continue; + pred[v] = u; + children[u].push_back(v); + h = max(h, dfs(v, u, depth + 1)); + } + return h + 1; +} + +bool rootedTreeIsomorphism(int r1, int r2) { + L.assign(n, vi()); + pred.assign(2 * n, -1); + children.assign(2 * n, vi()); + + int h1 = dfs(r1); + int h2 = dfs(r2); + if (h1 != h2) + return false; + + int h = h1 - 1; + vi label(2 * n); + subtreeLabels.assign(2 * n, vi()); + + for (int i = h - 1; i >= 0; i--) { + for (int j = 0; j < (int) L[i + 1].size(); j++) { + int v = L[i + 1][j]; + subtreeLabels[pred[v]].push_back(label[v]); + } + + sort(L[i].begin(), L[i].end(), compare); + + for (int j = 0, cnt = 0; j < (int) L[i].size(); j++) { + if (j && !equals(L[i][j], L[i][j - 1])) + ++cnt; + label[L[i][j]] = cnt; + } + } + + if (!equals(r1, r2)) + return false; + + generateMapping(r1, r2); + return true; +} + +bool treeIsomorphism() { + vi c1 = findCenter(); + vi c2 = findCenter(n); + if (c1.size() == c2.size()) { + if (rootedTreeIsomorphism(c1[0], c2[0])) + return true; + else if (c1.size() > 1) + return rootedTreeIsomorphism(c1[1], c2[0]); + } + return false; +} + +int main() { + n = 5; + vvi t1(n); + t1[0].push_back(1); + t1[1].push_back(0); + t1[1].push_back(2); + t1[2].push_back(1); + t1[1].push_back(3); + t1[3].push_back(1); + t1[0].push_back(4); + t1[4].push_back(0); + + vvi t2(n); + t2[0].push_back(1); + t2[1].push_back(0); + t2[0].push_back(4); + t2[4].push_back(0); + t2[4].push_back(3); + t2[3].push_back(4); + t2[4].push_back(2); + t2[2].push_back(4); + + tree.assign(2 * n, vi()); + for (int u = 0; u < n; u++) { + for (int i = 0; i < t1[u].size(); i++) { + int v = t1[u][i]; + tree[u].push_back(v); + } + for (int i = 0; i < t2[u].size(); i++) { + int v = t2[u][i]; + tree[u + n].push_back(v + n); + } + } + + bool res = treeIsomorphism(); + cout << res << endl; + + if (res) + for (int i = 0; i < n; i++) + cout << map[i] << endl; +} diff --git a/c++/_Basic/bigint-full.cpp b/c++/_Basic/bigint-full.cpp new file mode 100644 index 0000000..ce1798a --- /dev/null +++ b/c++/_Basic/bigint-full.cpp @@ -0,0 +1,506 @@ +#include +#include +#include +#include +#include +#include +#include +#include +using namespace std; + +// base and base_digits must be consistent +const int base = 1000000000; +const int base_digits = 9; + +struct bigint { + vector a; + int sign; + + bigint() : + sign(1) { + } + + bigint(long long v) { + *this = v; + } + + bigint(const string &s) { + read(s); + } + + void operator=(const bigint &v) { + sign = v.sign; + a = v.a; + } + + void operator=(long long v) { + sign = 1; + if (v < 0) + sign = -1, v = -v; + a.clear(); + for (; v > 0; v = v / base) + a.push_back(v % base); + } + + bigint operator+(const bigint &v) const { + if (sign == v.sign) { + bigint res = v; + + for (int i = 0, carry = 0; i < (int) max(a.size(), v.a.size()) || carry; ++i) { + if (i == (int) res.a.size()) + res.a.push_back(0); + res.a[i] += carry + (i < (int) a.size() ? a[i] : 0); + carry = res.a[i] >= base; + if (carry) + res.a[i] -= base; + } + return res; + } + return *this - (-v); + } + + bigint operator-(const bigint &v) const { + if (sign == v.sign) { + if (abs() >= v.abs()) { + bigint res = *this; + for (int i = 0, carry = 0; i < (int) v.a.size() || carry; ++i) { + res.a[i] -= carry + (i < (int) v.a.size() ? v.a[i] : 0); + carry = res.a[i] < 0; + if (carry) + res.a[i] += base; + } + res.trim(); + return res; + } + return -(v - *this); + } + return *this + (-v); + } + + void operator*=(int v) { + if (v < 0) + sign = -sign, v = -v; + for (int i = 0, carry = 0; i < (int) a.size() || carry; ++i) { + if (i == (int) a.size()) + a.push_back(0); + long long cur = a[i] * (long long) v + carry; + carry = (int) (cur / base); + a[i] = (int) (cur % base); + //asm("divl %%ecx" : "=a"(carry), "=d"(a[i]) : "A"(cur), "c"(base)); + /* + int val; + __asm { + lea esi, cur + mov eax, [esi] + mov edx, [esi+4] + mov ecx, base + div ecx + mov carry, eax + mov val, edx; + } + a[i] = val; + */ + } + trim(); + } + + bigint operator*(int v) const { + bigint res = *this; + res *= v; + return res; + } + + friend pair divmod(const bigint &a1, const bigint &b1) { + int norm = base / (b1.a.back() + 1); + bigint a = a1.abs() * norm; + bigint b = b1.abs() * norm; + bigint q, r; + q.a.resize(a.a.size()); + + for (int i = a.a.size() - 1; i >= 0; i--) { + r *= base; + r += a.a[i]; + int s1 = r.a.size() <= b.a.size() ? 0 : r.a[b.a.size()]; + int s2 = r.a.size() <= b.a.size() - 1 ? 0 : r.a[b.a.size() - 1]; + int d = ((long long) base * s1 + s2) / b.a.back(); + r -= b * d; + while (r < 0) + r += b, --d; + q.a[i] = d; + } + + q.sign = a1.sign * b1.sign; + r.sign = a1.sign; + q.trim(); + r.trim(); + return make_pair(q, r / norm); + } + + bigint operator/(const bigint &v) const { + return divmod(*this, v).first; + } + + bigint operator%(const bigint &v) const { + return divmod(*this, v).second; + } + + void operator/=(int v) { + if (v < 0) + sign = -sign, v = -v; + for (int i = (int) a.size() - 1, rem = 0; i >= 0; --i) { + long long cur = a[i] + rem * (long long) base; + a[i] = (int) (cur / v); + rem = (int) (cur % v); + } + trim(); + } + + bigint operator/(int v) const { + bigint res = *this; + res /= v; + return res; + } + + int operator%(int v) const { + if (v < 0) + v = -v; + int m = 0; + for (int i = a.size() - 1; i >= 0; --i) + m = (a[i] + m * (long long) base) % v; + return m * sign; + } + + void operator+=(const bigint &v) { + *this = *this + v; + } + void operator-=(const bigint &v) { + *this = *this - v; + } + void operator*=(const bigint &v) { + *this = *this * v; + } + void operator/=(const bigint &v) { + *this = *this / v; + } + + bool operator<(const bigint &v) const { + if (sign != v.sign) + return sign < v.sign; + if (a.size() != v.a.size()) + return a.size() * sign < v.a.size() * v.sign; + for (int i = a.size() - 1; i >= 0; i--) + if (a[i] != v.a[i]) + return a[i] * sign < v.a[i] * sign; + return false; + } + + bool operator>(const bigint &v) const { + return v < *this; + } + bool operator<=(const bigint &v) const { + return !(v < *this); + } + bool operator>=(const bigint &v) const { + return !(*this < v); + } + bool operator==(const bigint &v) const { + return !(*this < v) && !(v < *this); + } + bool operator!=(const bigint &v) const { + return *this < v || v < *this; + } + + void trim() { + while (!a.empty() && a.back() == 0) + a.pop_back(); + if (a.empty()) + sign = 1; + } + + bool isZero() const { + return a.empty() || (a.size() == 1 && !a[0]); + } + + bigint operator-() const { + bigint res = *this; + res.sign = -sign; + return res; + } + + bigint abs() const { + bigint res = *this; + res.sign *= res.sign; + return res; + } + + long long longValue() const { + long long res = 0; + for (int i = a.size() - 1; i >= 0; i--) + res = res * base + a[i]; + return res * sign; + } + + friend bigint gcd(const bigint &a, const bigint &b) { + return b.isZero() ? a : gcd(b, a % b); + } + friend bigint lcm(const bigint &a, const bigint &b) { + return a / gcd(a, b) * b; + } + + void read(const string &s) { + sign = 1; + a.clear(); + int pos = 0; + while (pos < (int) s.size() && (s[pos] == '-' || s[pos] == '+')) { + if (s[pos] == '-') + sign = -sign; + ++pos; + } + for (int i = s.size() - 1; i >= pos; i -= base_digits) { + int x = 0; + for (int j = max(pos, i - base_digits + 1); j <= i; j++) + x = x * 10 + s[j] - '0'; + a.push_back(x); + } + trim(); + } + + friend istream& operator>>(istream &stream, bigint &v) { + string s; + stream >> s; + v.read(s); + return stream; + } + + friend ostream& operator<<(ostream &stream, const bigint &v) { + if (v.sign == -1) + stream << '-'; + stream << (v.a.empty() ? 0 : v.a.back()); + for (int i = (int) v.a.size() - 2; i >= 0; --i) + stream << setw(base_digits) << setfill('0') << v.a[i]; + return stream; + } + + static vector convert_base(const vector &a, int old_digits, int new_digits) { + vector p(max(old_digits, new_digits) + 1); + p[0] = 1; + for (int i = 1; i < (int) p.size(); i++) + p[i] = p[i - 1] * 10; + vector res; + long long cur = 0; + int cur_digits = 0; + for (int i = 0; i < (int) a.size(); i++) { + cur += a[i] * p[cur_digits]; + cur_digits += old_digits; + while (cur_digits >= new_digits) { + res.push_back(int(cur % p[new_digits])); + cur /= p[new_digits]; + cur_digits -= new_digits; + } + } + res.push_back((int) cur); + while (!res.empty() && res.back() == 0) + res.pop_back(); + return res; + } + + void fft(vector > & a, bool invert) const { + int n = (int) a.size(); + + for (int i = 1, j = 0; i < n; ++i) { + int bit = n >> 1; + for (; j >= bit; bit >>= 1) + j -= bit; + j += bit; + if (i < j) + swap(a[i], a[j]); + } + + for (int len = 2; len <= n; len <<= 1) { + double ang = 2 * 3.14159265358979323846 / len * (invert ? -1 : 1); + complex wlen(cos(ang), sin(ang)); + for (int i = 0; i < n; i += len) { + complex w(1); + for (int j = 0; j < len / 2; ++j) { + complex u = a[i + j]; + complex v = a[i + j + len / 2] * w; + a[i + j] = u + v; + a[i + j + len / 2] = u - v; + w *= wlen; + } + } + } + if (invert) + for (int i = 0; i < n; ++i) + a[i] /= n; + } + + void multiply_fft(const vector &a, const vector &b, vector &res) const { + vector > fa(a.begin(), a.end()); + vector > fb(b.begin(), b.end()); + int n = 1; + while (n < (int) max(a.size(), b.size())) + n <<= 1; + n <<= 1; + fa.resize(n); + fb.resize(n); + + fft(fa, false); + fft(fb, false); + for (int i = 0; i < n; ++i) + fa[i] *= fb[i]; + fft(fa, true); + + res.resize(n); + for (int i = 0, carry = 0; i < n; ++i) { + res[i] = int(fa[i].real() + 0.5) + carry; + carry = res[i] / 1000; + res[i] %= 1000; + } + } + + bigint operator*(const bigint &v) const { + bigint res; + res.sign = sign * v.sign; + multiply_fft(convert_base(a, base_digits, 3), convert_base(v.a, base_digits, 3), res.a); + res.a = convert_base(res.a, 3, base_digits); + res.trim(); + return res; + } + + bigint mul_simple(const bigint &v) const { + bigint res; + res.sign = sign * v.sign; + res.a.resize(a.size() + v.a.size()); + for (int i = 0; i < (int) a.size(); ++i) + if (a[i]) + for (int j = 0, carry = 0; j < (int) v.a.size() || carry; ++j) { + long long cur = res.a[i + j] + (long long) a[i] * (j < (int) v.a.size() ? v.a[j] : 0) + carry; + carry = (int) (cur / base); + res.a[i + j] = (int) (cur % base); + } + res.trim(); + return res; + } + + typedef vector vll; + + static vll karatsubaMultiply(const vll &a, const vll &b) { + int n = a.size(); + vll res(n + n); + if (n <= 32) { + for (int i = 0; i < n; i++) + for (int j = 0; j < n; j++) + res[i + j] += a[i] * b[j]; + return res; + } + + int k = n >> 1; + vll a1(a.begin(), a.begin() + k); + vll a2(a.begin() + k, a.end()); + vll b1(b.begin(), b.begin() + k); + vll b2(b.begin() + k, b.end()); + + vll a1b1 = karatsubaMultiply(a1, b1); + vll a2b2 = karatsubaMultiply(a2, b2); + + for (int i = 0; i < k; i++) + a2[i] += a1[i]; + for (int i = 0; i < k; i++) + b2[i] += b1[i]; + + vll r = karatsubaMultiply(a2, b2); + for (int i = 0; i < (int) a1b1.size(); i++) + r[i] -= a1b1[i]; + for (int i = 0; i < (int) a2b2.size(); i++) + r[i] -= a2b2[i]; + + for (int i = 0; i < (int) r.size(); i++) + res[i + k] += r[i]; + for (int i = 0; i < (int) a1b1.size(); i++) + res[i] += a1b1[i]; + for (int i = 0; i < (int) a2b2.size(); i++) + res[i + n] += a2b2[i]; + return res; + } + + bigint mul_karatsuba(const bigint &v) const { + vector a6 = convert_base(this->a, base_digits, 6); + vector b6 = convert_base(v.a, base_digits, 6); + vll a(a6.begin(), a6.end()); + vll b(b6.begin(), b6.end()); + while (a.size() < b.size()) + a.push_back(0); + while (b.size() < a.size()) + b.push_back(0); + while (a.size() & (a.size() - 1)) + a.push_back(0), b.push_back(0); + vll c = karatsubaMultiply(a, b); + bigint res; + res.sign = sign * v.sign; + for (int i = 0, carry = 0; i < (int) c.size(); i++) { + long long cur = c[i] + carry; + res.a.push_back((int) (cur % 1000000)); + carry = (int) (cur / 1000000); + } + res.a = convert_base(res.a, 6, base_digits); + res.trim(); + return res; + } +}; + +bigint getRandomBigint(int len) { + string s; + for (int i = 0; i < len; i++) + s += rand() % 10 + '0'; + return bigint(s); +} + +int main() { + srand(1); + bigint a("99999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999"); + bigint b("19999999999999999999999999999999999999999999999999999999999999999999999999999999999999998"); + cout << a * b << endl; + cout << a.mul_karatsuba(b) << endl; + cout << a / b << endl; + + for (int step = 0; step < 100; step++) { + bigint a = getRandomBigint(1000); + bigint b = getRandomBigint(1000); + + bigint x = a * b; + bigint y = a.mul_simple(b); + bigint z = a.mul_karatsuba(b); + + if (x != y || x != z) { + cout << a << " " << b << " " << x << " " << y << " " << z << endl; + } + } + + int steps = 1; + vector x(steps), y(steps); + for (int i = 0; i < steps; i++) { + x[i] = getRandomBigint(60000); + y[i] = getRandomBigint(60000); + } + + clock_t start = clock(); + for (int i = 0; i < steps; i++) + bigint z = x[i] * y[i]; + fprintf(stderr, "time=%.3lfsec\n", 0.001 * (clock() - start)); + + start = clock(); + for (int i = 0; i < steps; i++) + bigint z = x[i].mul_karatsuba(y[i]); + fprintf(stderr, "time=%.3lfsec\n", 0.001 * (clock() - start)); + + a = getRandomBigint(10000); + b = getRandomBigint(2000); + start = clock(); + bigint c = a / b; + fprintf(stderr, "time=%.3lfsec\n", 0.001 * (clock() - start)); + + bigint z = 5; + z = 6; + cout << z << endl; +} diff --git a/c++/_Basic/bigint.cpp b/c++/_Basic/bigint.cpp new file mode 100644 index 0000000..4eaed78 --- /dev/null +++ b/c++/_Basic/bigint.cpp @@ -0,0 +1,446 @@ +#include +#include +#include +#include +#include +#include +#include +#include +using namespace std; + +// base and base_digits must be consistent +const int base = 1000000000; +const int base_digits = 9; + +struct bigint { + vector z; + int sign; + + bigint() : + sign(1) { + } + + bigint(long long v) { + *this = v; + } + + bigint(const string &s) { + read(s); + } + + void operator=(const bigint &v) { + sign = v.sign; + z = v.z; + } + + void operator=(long long v) { + sign = 1; + if (v < 0) + sign = -1, v = -v; + z.clear(); + for (; v > 0; v = v / base) + z.push_back(v % base); + } + + bigint operator+(const bigint &v) const { + if (sign == v.sign) { + bigint res = v; + + for (int i = 0, carry = 0; i < (int) max(z.size(), v.z.size()) || carry; ++i) { + if (i == (int) res.z.size()) + res.z.push_back(0); + res.z[i] += carry + (i < (int) z.size() ? z[i] : 0); + carry = res.z[i] >= base; + if (carry) + res.z[i] -= base; + } + return res; + } + return *this - (-v); + } + + bigint operator-(const bigint &v) const { + if (sign == v.sign) { + if (abs() >= v.abs()) { + bigint res = *this; + for (int i = 0, carry = 0; i < (int) v.z.size() || carry; ++i) { + res.z[i] -= carry + (i < (int) v.z.size() ? v.z[i] : 0); + carry = res.z[i] < 0; + if (carry) + res.z[i] += base; + } + res.trim(); + return res; + } + return -(v - *this); + } + return *this + (-v); + } + + void operator*=(int v) { + if (v < 0) + sign = -sign, v = -v; + for (int i = 0, carry = 0; i < (int) z.size() || carry; ++i) { + if (i == (int) z.size()) + z.push_back(0); + long long cur = z[i] * (long long) v + carry; + carry = (int) (cur / base); + z[i] = (int) (cur % base); + //asm("divl %%ecx" : "=a"(carry), "=d"(a[i]) : "A"(cur), "c"(base)); + } + trim(); + } + + bigint operator*(int v) const { + bigint res = *this; + res *= v; + return res; + } + + friend pair divmod(const bigint &a1, const bigint &b1) { + int norm = base / (b1.z.back() + 1); + bigint a = a1.abs() * norm; + bigint b = b1.abs() * norm; + bigint q, r; + q.z.resize(a.z.size()); + + for (int i = a.z.size() - 1; i >= 0; i--) { + r *= base; + r += a.z[i]; + int s1 = b.z.size() < r.z.size() ? r.z[b.z.size()] : 0; + int s2 = b.z.size() - 1 < r.z.size() ? r.z[b.z.size() - 1] : 0; + int d = ((long long) s1 * base + s2) / b.z.back(); + r -= b * d; + while (r < 0) + r += b, --d; + q.z[i] = d; + } + + q.sign = a1.sign * b1.sign; + r.sign = a1.sign; + q.trim(); + r.trim(); + return make_pair(q, r / norm); + } + + friend bigint sqrt(const bigint &a1) { + bigint a = a1; + while (a.z.empty() || a.z.size() % 2 == 1) + a.z.push_back(0); + + int n = a.z.size(); + + int firstDigit = (int) sqrt((double) a.z[n - 1] * base + a.z[n - 2]); + int norm = base / (firstDigit + 1); + a *= norm; + a *= norm; + while (a.z.empty() || a.z.size() % 2 == 1) + a.z.push_back(0); + + bigint r = (long long) a.z[n - 1] * base + a.z[n - 2]; + firstDigit = (int) sqrt((double) a.z[n - 1] * base + a.z[n - 2]); + int q = firstDigit; + bigint res; + + for(int j = n / 2 - 1; j >= 0; j--) { + for(; ; --q) { + bigint r1 = (r - (res * 2 * base + q) * q) * base * base + (j > 0 ? (long long) a.z[2 * j - 1] * base + a.z[2 * j - 2] : 0); + if (r1 >= 0) { + r = r1; + break; + } + } + res *= base; + res += q; + + if (j > 0) { + int d1 = res.z.size() + 2 < r.z.size() ? r.z[res.z.size() + 2] : 0; + int d2 = res.z.size() + 1 < r.z.size() ? r.z[res.z.size() + 1] : 0; + int d3 = res.z.size() < r.z.size() ? r.z[res.z.size()] : 0; + q = ((long long) d1 * base * base + (long long) d2 * base + d3) / (firstDigit * 2); + } + } + + res.trim(); + return res / norm; + } + + bigint operator/(const bigint &v) const { + return divmod(*this, v).first; + } + + bigint operator%(const bigint &v) const { + return divmod(*this, v).second; + } + + void operator/=(int v) { + if (v < 0) + sign = -sign, v = -v; + for (int i = (int) z.size() - 1, rem = 0; i >= 0; --i) { + long long cur = z[i] + rem * (long long) base; + z[i] = (int) (cur / v); + rem = (int) (cur % v); + } + trim(); + } + + bigint operator/(int v) const { + bigint res = *this; + res /= v; + return res; + } + + int operator%(int v) const { + if (v < 0) + v = -v; + int m = 0; + for (int i = z.size() - 1; i >= 0; --i) + m = (z[i] + m * (long long) base) % v; + return m * sign; + } + + void operator+=(const bigint &v) { + *this = *this + v; + } + void operator-=(const bigint &v) { + *this = *this - v; + } + void operator*=(const bigint &v) { + *this = *this * v; + } + void operator/=(const bigint &v) { + *this = *this / v; + } + + bool operator<(const bigint &v) const { + if (sign != v.sign) + return sign < v.sign; + if (z.size() != v.z.size()) + return z.size() * sign < v.z.size() * v.sign; + for (int i = z.size() - 1; i >= 0; i--) + if (z[i] != v.z[i]) + return z[i] * sign < v.z[i] * sign; + return false; + } + + bool operator>(const bigint &v) const { + return v < *this; + } + bool operator<=(const bigint &v) const { + return !(v < *this); + } + bool operator>=(const bigint &v) const { + return !(*this < v); + } + bool operator==(const bigint &v) const { + return !(*this < v) && !(v < *this); + } + bool operator!=(const bigint &v) const { + return *this < v || v < *this; + } + + void trim() { + while (!z.empty() && z.back() == 0) + z.pop_back(); + if (z.empty()) + sign = 1; + } + + bool isZero() const { + return z.empty() || (z.size() == 1 && !z[0]); + } + + bigint operator-() const { + bigint res = *this; + res.sign = -sign; + return res; + } + + bigint abs() const { + bigint res = *this; + res.sign *= res.sign; + return res; + } + + long long longValue() const { + long long res = 0; + for (int i = z.size() - 1; i >= 0; i--) + res = res * base + z[i]; + return res * sign; + } + + friend bigint gcd(const bigint &a, const bigint &b) { + return b.isZero() ? a : gcd(b, a % b); + } + friend bigint lcm(const bigint &a, const bigint &b) { + return a / gcd(a, b) * b; + } + + void read(const string &s) { + sign = 1; + z.clear(); + int pos = 0; + while (pos < (int) s.size() && (s[pos] == '-' || s[pos] == '+')) { + if (s[pos] == '-') + sign = -sign; + ++pos; + } + for (int i = s.size() - 1; i >= pos; i -= base_digits) { + int x = 0; + for (int j = max(pos, i - base_digits + 1); j <= i; j++) + x = x * 10 + s[j] - '0'; + z.push_back(x); + } + trim(); + } + + friend istream& operator>>(istream &stream, bigint &v) { + string s; + stream >> s; + v.read(s); + return stream; + } + + friend ostream& operator<<(ostream &stream, const bigint &v) { + if (v.sign == -1) + stream << '-'; + stream << (v.z.empty() ? 0 : v.z.back()); + for (int i = (int) v.z.size() - 2; i >= 0; --i) + stream << setw(base_digits) << setfill('0') << v.z[i]; + return stream; + } + + static vector convert_base(const vector &a, int old_digits, int new_digits) { + vector p(max(old_digits, new_digits) + 1); + p[0] = 1; + for (int i = 1; i < (int) p.size(); i++) + p[i] = p[i - 1] * 10; + vector res; + long long cur = 0; + int cur_digits = 0; + for (int i = 0; i < (int) a.size(); i++) { + cur += a[i] * p[cur_digits]; + cur_digits += old_digits; + while (cur_digits >= new_digits) { + res.push_back(int(cur % p[new_digits])); + cur /= p[new_digits]; + cur_digits -= new_digits; + } + } + res.push_back((int) cur); + while (!res.empty() && res.back() == 0) + res.pop_back(); + return res; + } + + typedef vector vll; + + static vll karatsubaMultiply(const vll &a, const vll &b) { + int n = a.size(); + vll res(n + n); + if (n <= 32) { + for (int i = 0; i < n; i++) + for (int j = 0; j < n; j++) + res[i + j] += a[i] * b[j]; + return res; + } + + int k = n >> 1; + vll a1(a.begin(), a.begin() + k); + vll a2(a.begin() + k, a.end()); + vll b1(b.begin(), b.begin() + k); + vll b2(b.begin() + k, b.end()); + + vll a1b1 = karatsubaMultiply(a1, b1); + vll a2b2 = karatsubaMultiply(a2, b2); + + for (int i = 0; i < k; i++) + a2[i] += a1[i]; + for (int i = 0; i < k; i++) + b2[i] += b1[i]; + + vll r = karatsubaMultiply(a2, b2); + for (int i = 0; i < (int) a1b1.size(); i++) + r[i] -= a1b1[i]; + for (int i = 0; i < (int) a2b2.size(); i++) + r[i] -= a2b2[i]; + + for (int i = 0; i < (int) r.size(); i++) + res[i + k] += r[i]; + for (int i = 0; i < (int) a1b1.size(); i++) + res[i] += a1b1[i]; + for (int i = 0; i < (int) a2b2.size(); i++) + res[i + n] += a2b2[i]; + return res; + } + + bigint operator*(const bigint &v) const { + vector a6 = convert_base(this->z, base_digits, 6); + vector b6 = convert_base(v.z, base_digits, 6); + vll a(a6.begin(), a6.end()); + vll b(b6.begin(), b6.end()); + while (a.size() < b.size()) + a.push_back(0); + while (b.size() < a.size()) + b.push_back(0); + while (a.size() & (a.size() - 1)) + a.push_back(0), b.push_back(0); + vll c = karatsubaMultiply(a, b); + bigint res; + res.sign = sign * v.sign; + for (int i = 0, carry = 0; i < (int) c.size(); i++) { + long long cur = c[i] + carry; + res.z.push_back((int) (cur % 1000000)); + carry = (int) (cur / 1000000); + } + res.z = convert_base(res.z, 6, base_digits); + res.trim(); + return res; + } +}; + +bigint random_bigint(int n) { + string s; + for (int i = 0; i < n; i++) { + s += rand() % 10 + '0'; + } + return bigint(s); +} + +// random tests +int main() { + for(int i = 0; i < 1000; i++) { + cout << i << endl; + int n = rand() % 100 + 1; + bigint a = random_bigint(n); + bigint res = sqrt(a); + bigint xx = res * res; + bigint yy = (res + 1) * (res + 1); + + if (xx > a || yy <= a) { + cout << a << " " << res << endl; + break; + } + + int m = rand() % n + 1; + bigint b = random_bigint(m) + 1; + res = a / b; + xx = res * b; + yy = b * (res + 1); + + if (xx > a || yy <= a) { + cout << a << " " << b << " " << res << endl; + break; + } + } + + bigint a = random_bigint(10000); + bigint b = random_bigint(2000); + clock_t start = clock(); + bigint c = a / b; + fprintf(stdout, "time=%.3lfsec\n", 0.001 * (clock() - start)); + + bigint x = 5; + x = 6; + cout << x << endl; +} diff --git a/c++/_Basic/nCr & nPr.cpp b/c++/_Basic/nCr & nPr.cpp new file mode 100644 index 0000000..63754e3 --- /dev/null +++ b/c++/_Basic/nCr & nPr.cpp @@ -0,0 +1,41 @@ +#include < iostream.h > + +long factorial(int); +long find_ncr(int, int); +long find_npr(int, int); + +main() +{ + int n, r; + long ncr, npr; + cout<<"Enter the value of n and r\n"; + cin>>n>>r; + ncr = find_ncr(n, r); + npr = find_npr(n, r); + cout< +#include +#include +#include +using namespace std; + +typedef complex cdouble; +typedef vector poly; + +pair horner(const poly &a, cdouble x0) { + int n = a.size(); + poly b = poly(max(1, n - 1)); + + for(int i = n - 1; i > 0; i--) + b[i - 1] = a[i] + (i < n - 1 ? b[i] * x0 : 0); + return make_pair(b, a[0] + b[0] * x0); +} + +cdouble eval(const poly &p, cdouble x) { + return horner(p, x).second; +} + +poly derivative(const poly &p) { + int n = p.size(); + poly r = poly(max(1, n - 1)); + for(int i = 1; i < n; i++) + r[i - 1] = p[i] * cdouble(i); + return r; +} + +const double EPS = 1e-9; + +int cmp(cdouble x, cdouble y) { + double diff = abs(x) - abs(y); + return diff < -EPS ? -1 : (diff > EPS ? 1 : 0); +} + +cdouble find_one_root(const poly &p0, cdouble x) { + int n = p0.size() - 1; + poly p1 = derivative(p0); + poly p2 = derivative(p1); + for (int step = 0; step < 10000; step++) { + cdouble y0 = eval(p0, x); + if (cmp(y0, 0) == 0) break; + cdouble G = eval(p1, x) / y0; + cdouble H = G * G - eval(p2, x) - y0; + cdouble R = sqrt(cdouble(n - 1) * (H * cdouble(n) - G * G)); + cdouble D1 = G + R; + cdouble D2 = G - R; + cdouble a = cdouble(n) / (cmp(D1, D2) > 0 ? D1 : D2); + x -= a; + if (cmp(a, 0) == 0) break; + } + return x; +} + +vector find_all_roots(const poly &p) { + vector res; + poly q = p; + while (q.size() > 2) { + cdouble z(rand() / double(RAND_MAX), rand() / double(RAND_MAX)); + z = find_one_root(q, z); + z = find_one_root(p, z); + q = horner(q, z).first; + res.push_back(z); + } + res.push_back(-q[0] / q[1]); + return res; +} + +int main( int argc, char* argv[] ) { + poly p; + // x^3 - 8x^2 - 13x + 140 = (x+4)(x-5)(x-7) + p.push_back(140); + p.push_back(-13); + p.push_back(-8); + p.push_back(1); + + vector roots = find_all_roots(p); + + for(size_t i = 0; i < roots.size(); i++) { + if (abs(roots[i].real()) < EPS) roots[i] -= cdouble(roots[i].real(), 0); + if (abs(roots[i].imag()) < EPS) roots[i] -= cdouble(0, roots[i].imag()); + cout << setprecision(3) << roots[i] << endl; + } + + return 0; +} diff --git a/c-sharp/Arrays/C# Program to Convert a 2D Array into 1D Array.cs b/c-sharp/Arrays/C# Program to Convert a 2D Array into 1D Array.cs new file mode 100644 index 0000000..f39a280 --- /dev/null +++ b/c-sharp/Arrays/C# Program to Convert a 2D Array into 1D Array.cs @@ -0,0 +1,97 @@ +/* + * C# Program to Convert a 2D Array into 1D Array + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +namespace Program +{ +class twodmatrix +{ + int m, n; + int[,] a; + int[] b; + twodmatrix(int x, int y) + { + m = x; + n = y; + a = new int[m, n]; + b = new int[m * n]; + } + public void readmatrix() + { + for (int i = 0; i < m; i++) + { + for (int j = 0; j < n; j++) + { + Console.WriteLine("a[{0},{1}]=", i, j); + a[i, j] = Convert.ToInt32(Console.ReadLine()); + } + } + } + public void printd() + { + for (int i = 0; i < m; i++) + { + for (int j = 0; j < n; j++) + { + Console.Write("{0}\t", a[i, j]); + } + Console.Write("\n"); + } + } + public void convert() + { + int k = 0; + for (int i = 0; i < m; i++) + { + for (int j = 0; j < n; j++) + { + b[k++] = a[i, j]; + } + } + } + public void printoned() + { + for (int i = 0; i < m * n; i++) + { + Console.WriteLine("{0}\t", b[i]); + } + } + + + public static void Main(string[] args) + { + twodmatrix obj = new twodmatrix(2,3); + Console.WriteLine("Enter the Elements : "); + obj.readmatrix(); + Console.WriteLine("\t\t Given 2-D Array(Matrix) is : "); + obj.printd(); + obj.convert(); + Console.WriteLine("\t\t Converted 1-D Array is : "); + obj.printoned(); + Console.ReadLine(); + } +} +} + +/* +Enter the Elements : +a[0,0]=3 +a[0,1]=7 +a[0,2]=1 +a[1,0]=9 +a[1,1]=34 +a[1,2]=23 + Given 2-D Array(Matrix) is : +1 4 3 +7 3 8 + Converted 1-D Array is : +1 +4 +3 +7 +3 +8 \ No newline at end of file diff --git a/c-sharp/Arrays/C# Program to Copy a Section of One Array to Another.cs b/c-sharp/Arrays/C# Program to Copy a Section of One Array to Another.cs new file mode 100644 index 0000000..5dc258d --- /dev/null +++ b/c-sharp/Arrays/C# Program to Copy a Section of One Array to Another.cs @@ -0,0 +1,50 @@ +/* + * C# Program to Copy a Section of One Array to Another + */ +using System; +class Program +{ + static void Main() + { + int n, m, size; + Console.WriteLine("Enter the size of the Array : "); + n = Convert.ToInt32(Console.ReadLine()); + int [] a = new int[n]; + Console.WriteLine("Enter the Elements of the First Array :"); + for (int i = 0; i 0) + a[i] = -a[i]; + } + Console.WriteLine("Elements:"); + for (int i = 0; i < 5; i++) + { + Console.WriteLine(a[i]); + } + Console.ReadLine(); + } +} +} + +/* +Enter 5 Elements : +10 +7 +8 +45 +67 +Elements : +-10 +-7 +-8 +-45 +-67 \ No newline at end of file diff --git a/c-sharp/Arrays/C# Program to Reverse an Array.cs b/c-sharp/Arrays/C# Program to Reverse an Array.cs new file mode 100644 index 0000000..f14cbec --- /dev/null +++ b/c-sharp/Arrays/C# Program to Reverse an Array.cs @@ -0,0 +1,45 @@ +/* + * C# Program to Reverse an Array + */ +using System; +class Program +{ + static void Main() + { + int[] array = { 1, 2, 3,4,5,6,7,8,9,10 }; + foreach (int a in array) + { + Console.WriteLine(a); + } + Array.Reverse(array); + Console.WriteLine("Reversed Array : "); + foreach (int value in array) + { + Console.WriteLine(value); + } + Console.ReadLine(); + } +} + +/* +1 +2 +3 +4 +5 +6 +7 +8 +9 +10 +Reversed Array : +10 +9 +8 +7 +6 +5 +4 +3 +2 +1 \ No newline at end of file diff --git a/c-sharp/Arrays/C# Program to Search an Element in an Array.cs b/c-sharp/Arrays/C# Program to Search an Element in an Array.cs new file mode 100644 index 0000000..f708517 --- /dev/null +++ b/c-sharp/Arrays/C# Program to Search an Element in an Array.cs @@ -0,0 +1,23 @@ +/* + * C# Program to Search an Element in an Array + */ +using System; +using System.IO; +class Program +{ + static void Main() + { + string[] array1 = { "cat", "dogs", "donkey", "camel" }; + string v1 = Array.Find(array1, + element => element.StartsWith("cam", StringComparison.Ordinal)); + string v2 = Array.Find(array1, + element => element.Length == 3); + Console.WriteLine("The Elemnt that Starts with 'Cam' is : " +v1); + Console.WriteLine("3 Letter word in the Array is : " +v2); + Console.ReadLine(); + } +} + +/* +The Element that Starts With 'Cam' is : Camel +3 Letter Word in the Array is : cat \ No newline at end of file diff --git a/c-sharp/Arrays/C# Program to Search an element with Array Indices.cs b/c-sharp/Arrays/C# Program to Search an element with Array Indices.cs new file mode 100644 index 0000000..a8b1ebb --- /dev/null +++ b/c-sharp/Arrays/C# Program to Search an element with Array Indices.cs @@ -0,0 +1,50 @@ +/* + * C# Program to Search an element with Array Indices + */ +using System; + +class ArrayBinarySearch +{ + public static void Main() + { + int[] ints = { 0, 10, 100, 1000, 1000000 }; + Console.WriteLine("Array indices and elements: "); + for (int i = 0; i < ints.Length; i++) + { + Console.Write("[{0}]={1, -5}", i, ints[i]); + } + Console.WriteLine(); + FindObject(ints, 25); + FindObject(ints, 1000); + FindObject(ints, 2000000); + Console.ReadLine(); + } + + public static void FindObject(Array array, Object o) + { + int index = Array.BinarySearch(array, 0, array.Length, o); + Console.WriteLine(); + if (index > 0) + { + Console.WriteLine("Object: {0} found at [{1}]", o, index); + } + else if (~index == array.Length) + { + Console.WriteLine("Object: {0} not found. " + + "No array object has a greater value.", o); + Console.WriteLine(); + } + else + { + Console.WriteLine("Object: {0} not found. " + + "Next larger object found at [{1}].", o, ~index); + } + } +} + +/* +Array indices and elements: +[0]=0 [1]=10 [2]=100 [3]=1000 [4]=1000000 +Object: 25 not found. Next larger object found at [2]. +Object: 1000 found at [3] +Object: 2000000 not found. No array object has a greater value. \ No newline at end of file diff --git a/c-sharp/Arrays/C# Program to Sort a List of Names in Alphabetical Order.cs b/c-sharp/Arrays/C# Program to Sort a List of Names in Alphabetical Order.cs new file mode 100644 index 0000000..f5f4ab5 --- /dev/null +++ b/c-sharp/Arrays/C# Program to Sort a List of Names in Alphabetical Order.cs @@ -0,0 +1,33 @@ +/* + * C# Program to Sort a List of Names in Alphabetical Order + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +namespace ConsoleApplication1 +{ +class Program +{ + static void Main() + { + List names = new List(); + names.Add("Ram"); + names.Add("Rose"); + names.Add("Abs"); + names.Add("Edward"); + names.Add("Sita"); + names.Sort(); + foreach (string s in names) + Console.WriteLine(s); + Console.ReadLine(); + } +} +} + +/* +Abs +Edward +Ram +Rose +Sita \ No newline at end of file diff --git a/c-sharp/Arrays/C# Program to get the Length of the Array.cs b/c-sharp/Arrays/C# Program to get the Length of the Array.cs new file mode 100644 index 0000000..fb56f2a --- /dev/null +++ b/c-sharp/Arrays/C# Program to get the Length of the Array.cs @@ -0,0 +1,23 @@ +/* + * C# Program to get the Length of the Array + */ +using System; +class Program +{ + static void Main() + { + int[] arrayA = new int[5]; + int lengthA = arrayA.Length; + Console.WriteLine("Length of ArrayA : {0}", +lengthA); + long longLength = arrayA.LongLength; + Console.WriteLine("Length of the LongLength Array : {0}",longLength); + int[,] twoD = new int[5, 10]; + Console.WriteLine("The Size of 2D Array is : {0}",twoD.Length); + Console.ReadLine(); + } +} + +/* +Length of ArrayA : 5 +Length of the LongLength Array is :5 +The Size of 2D Array is : 50 \ No newline at end of file diff --git a/c-sharp/Arrays/C# Sharp for a 2D array of size 3x3 and print the matrix.cs b/c-sharp/Arrays/C# Sharp for a 2D array of size 3x3 and print the matrix.cs new file mode 100644 index 0000000..096129c --- /dev/null +++ b/c-sharp/Arrays/C# Sharp for a 2D array of size 3x3 and print the matrix.cs @@ -0,0 +1,29 @@ +using System; +public class Exercise14 +{ + public static void Main() + { + int i,j; + int[,] arr1 = new int[3,3]; + Console.Write("\n\nRead a 2D array of size 3x3 and print the matrix :\n"); + Console.Write("------------------------------------------------------\n"); + /* Stored values into the array*/ + Console.Write("Input elements in the matrix :\n"); + for(i=0; i<3; i++) + { + for(j=0; j<3; j++) + { + Console.Write("element - [{0},{1}] : ",i,j); + arr1[i,j] = Convert.ToInt32(Console.ReadLine()); + } + } + Console.Write("\nThe matrix is : \n"); + for(i=0; i<3; i++) + { + Console.Write("\n"); + for(j=0; j<3; j++) + Console.Write("{0}\t",arr1[i,j]); + } + Console.Write("\n\n"); + } +} \ No newline at end of file diff --git a/c-sharp/Arrays/C# Sharp for addition of two Matrices of same size.cs b/c-sharp/Arrays/C# Sharp for addition of two Matrices of same size.cs new file mode 100644 index 0000000..1582dca --- /dev/null +++ b/c-sharp/Arrays/C# Sharp for addition of two Matrices of same size.cs @@ -0,0 +1,60 @@ +using System; +public class Exercise14 +{ + public static void Main() + { + int i,j,n; + int[,] arr1 = new int[50,50]; + int[,] brr1 = new int[50,50]; + int[,] crr1 = new int[50,50]; + Console.Write("\n\naddition of two Matrices :\n"); + Console.Write("-----------------------------------------\n"); + Console.Write("Input the size of the square matrix (less than 5): "); + n = Convert.ToInt32(Console.ReadLine()); + /* Stored values into the array*/ + Console.Write("Input elements in the first matrix :\n"); + for(i=0; i((r*c)/2)) + { + Console.Write ("The given matrix is sparse matrix. \n"); + } + else + Console.Write ("The given matrix is not a sparse matrix.\n"); + Console.Write ("There are {0} number of zeros in the matrix.\n\n",ctr); + } +} \ No newline at end of file diff --git a/c-sharp/Arrays/C# Sharp to accept two matrices and check whether they are equal.cs b/c-sharp/Arrays/C# Sharp to accept two matrices and check whether they are equal.cs new file mode 100644 index 0000000..8c49723 --- /dev/null +++ b/c-sharp/Arrays/C# Sharp to accept two matrices and check whether they are equal.cs @@ -0,0 +1,76 @@ +using System; +public class Exercise30 +{ + public static void Main() + { + int[,] arr1 = new int[50,50]; + int[,] brr1 = new int[50,50]; + int i, j, r1, c1, r2, c2, flag =1; + Console.Write("\n\nAccept two matrices and check whether they are equal :\n "); + Console.Write("-----------------------------------------------------------\n"); + Console.Write("Input the number of rows in the 1st matrix : "); + r1 = Convert.ToInt32(Console.ReadLine()); + Console.Write("Input the number of columns in the 1st matrix : "); + c1 = Convert.ToInt32(Console.ReadLine()); + Console.Write("Input the number of rows in the 2nd matrix : "); + r2 = Convert.ToInt32(Console.ReadLine()); + Console.Write("Input the number of columns in the 2nd matrix : "); + c2 = Convert.ToInt32(Console.ReadLine()); + Console.Write("Input elements in the first matrix :\n"); + for(i=0; imx) + { + mx = arr1[i]; + } + if(arr1[i]arr1[i]) + { + sml=arr1[i]; + j = i; + } + } + /* ignore the smallest element and find the 2nd smallest element in the array */ + sml2nd=99999; + for(i=0; iarr1[i]) + { + sml2nd=arr1[i]; + } + } + } + Console.Write("The Second smallest element in the array is : {0} \n\n", sml2nd); + } +} \ No newline at end of file diff --git a/c-sharp/Arrays/C# Sharp to find sum of right diagonals of a matrix.cs b/c-sharp/Arrays/C# Sharp to find sum of right diagonals of a matrix.cs new file mode 100644 index 0000000..4959afa --- /dev/null +++ b/c-sharp/Arrays/C# Sharp to find sum of right diagonals of a matrix.cs @@ -0,0 +1,32 @@ +using System; +public class Exercise23 +{ + public static void Main() + + { + int i,j,sum=0,n; + int[,] arr1 = new int[50,50]; + Console.Write("\n\nFind sum of right diagonals of a matrix :\n"); + Console.Write("---------------------------------------\n"); + Console.Write("Input the size of the square matrix : "); + n=Convert.ToInt32(Console.ReadLine()); + Console.Write("Input elements in the first matrix :\n"); + for(i=0; i=p; i--) + arr1[i]= arr1[i-1]; + /* insert value at the proper position */ + arr1[p]=inval; + Console.Write("\n\nAfter Insert the list is :\n "); + for(i=0; i<=n; i++) + Console.Write("{0} ",arr1[i]); + Console.Write("\n"); + } +} \ No newline at end of file diff --git a/c-sharp/Arrays/C# Sharp to insert New value in the array (unsorted list ).cs b/c-sharp/Arrays/C# Sharp to insert New value in the array (unsorted list ).cs new file mode 100644 index 0000000..661d0b7 --- /dev/null +++ b/c-sharp/Arrays/C# Sharp to insert New value in the array (unsorted list ).cs @@ -0,0 +1,36 @@ +using System; +public class Exercise14 +{ + public static void Main() + { + int[] arr1 = new int[10]; + int i,n,p,x; + Console.Write("\n\nInsert New value in the unsorted array : \n"); + Console.Write("-----------------------------------------\n"); + Console.Write("Input the size of array : "); + n = Convert.ToInt32(Console.ReadLine()); + /* Stored values into the array*/ + Console.Write("Input {0} elements in the array in ascending order:\n",n); + for(i=0; i=p; i--) + arr1[i]= arr1[i-1]; + /* insert value at given position */ + arr1[p-1]=x; + Console.Write("\n\nAfter Insert the element the new list is :\n"); + for(i=0; i<=n; i++) + Console.Write("{0} ",arr1[i]); + Console.Write("\n\n"); + } +} \ No newline at end of file diff --git a/c-sharp/Arrays/C# Sharp to merge two arrays of same size sorted in ascending order.cs b/c-sharp/Arrays/C# Sharp to merge two arrays of same size sorted in ascending order.cs new file mode 100644 index 0000000..3b682ef --- /dev/null +++ b/c-sharp/Arrays/C# Sharp to merge two arrays of same size sorted in ascending order.cs @@ -0,0 +1,62 @@ +using System; +public class Exercise7 +{ + public static void Main() + { + int[] arr1 = new int[100]; + int[] arr2 = new int[100]; + int[] arr3 = new int[200]; + int s1, s2, s3; + int i, j, k; + Console.Write("\n\nMerge two arrays of same size sorted in ascending order.\n"); + Console.Write("------------------------------------------------------------\n"); + Console.Write("Input the number of elements to be stored in the first array :"); + s1 = Convert.ToInt32(Console.ReadLine()); + Console.Write("Input {0} elements in the array :\n",s1); + for(i=0; i=arr3[k+1]) + { + j=arr3[k+1]; + arr3[k+1]=arr3[k]; + arr3[k]=j; + } + } + } + /*--------------- Prints the merged array ------------------------------------*/ + Console.Write("\nThe merged array in ascending order is :\n"); + for(i=0; i=j) + Console.Write("{0} ",arr1[i,j]); + else + Console.Write("{0} ",0); + } + Console.Write("\n\n"); + } +} \ No newline at end of file diff --git a/c-sharp/Arrays/C# Sharp to read n number of values in an array and display it in reverse order.cs b/c-sharp/Arrays/C# Sharp to read n number of values in an array and display it in reverse order.cs new file mode 100644 index 0000000..2204d1f --- /dev/null +++ b/c-sharp/Arrays/C# Sharp to read n number of values in an array and display it in reverse order.cs @@ -0,0 +1,30 @@ +using System; +public class Exercise2 +{ + public static void Main() + { + int i,n; + int[] a= new int[100]; + Console.Write("\n\nRead n number of values in an array and display it in reverse order:\n"); + Console.Write("------------------------------------------------------------------------\n"); + Console.Write("Input the number of elements to store in the array :"); + n = Convert.ToInt32(Console.ReadLine()); + Console.Write("Input {0} number of elements in the array :\n",n); + for(i=0; i=0; i--) + { + Console.Write("{0} ",a[i]); + } + Console.Write("\n\n"); + } +} \ No newline at end of file diff --git a/c-sharp/Arrays/C# Sharp to separate odd and even integers in separate arrays.cs b/c-sharp/Arrays/C# Sharp to separate odd and even integers in separate arrays.cs new file mode 100644 index 0000000..eccb83d --- /dev/null +++ b/c-sharp/Arrays/C# Sharp to separate odd and even integers in separate arrays.cs @@ -0,0 +1,45 @@ +using System; +public class Exercise10 +{ + public static void Main() + { + int[] arr1 = new int[10]; + int[] arr2 = new int[10]; + int[] arr3 = new int[10]; + int i,j=0,k=0,n; + Console.Write("\n\nSeparate odd and even integers in separate arrays:\n"); + Console.Write("------------------------------------------------------\n"); + Console.Write("Input the number of elements to be stored in the array :"); + n = Convert.ToInt32(Console.ReadLine()); + Console.Write("Input {0} elements in the array :\n",n); + for(i=0; i 0 && i % 8 == 0) + res += " "; + res += t[i]; + } + return res; + } + static void Main(string[] args) + { + int little = 2777; + int big = ReverseBytes(little); + string sLittle = IntToBinaryString(little); + string sBig = IntToBinaryString(big); + int oLittle = ReverseBytes(big); + string oString = IntToBinaryString(oLittle); + Console.WriteLine("Original (Intel) little endian value = " + + little); + Console.WriteLine("Original value as binary string = " + + sLittle); + Console.WriteLine(""); + Console.WriteLine("Reversed big endian value = " + + big); + Console.WriteLine("Reversed value as string = " + + sBig); + Console.WriteLine(""); + Console.ReadLine(); + } +} +} + +/* + +Original (Intel) little endian value = 2777 +Original value as binary string = 00000000 00000000 00001010 11011001 + +Reversed big endian value = -653656064 +Reversed value as string = 11011001 00001010 00000000 00000000 \ No newline at end of file diff --git a/c-sharp/Conversions/C# Program to Convert Decimal to Binary.cs b/c-sharp/Conversions/C# Program to Convert Decimal to Binary.cs new file mode 100644 index 0000000..7777bdb --- /dev/null +++ b/c-sharp/Conversions/C# Program to Convert Decimal to Binary.cs @@ -0,0 +1,32 @@ +/* + * C# Program to Convert Decimal to Binary + */ +using System; +class myclass +{ + static void Main() + { + int num; + Console.Write("Enter a Number : "); + num = int.Parse(Console.ReadLine()); + int quot; + string rem = ""; + while (num >= 1) + { + quot = num / 2; + rem += (num % 2).ToString(); + num = quot; + } + string bin = ""; + for (int i = rem.Length - 1; i >= 0; i--) + { + bin = bin + rem[i]; + } + Console.WriteLine("The Binary format for given number is {0}", bin); + Console.Read(); + } +} + +/* +Enter the Number : 3 +Binary Format for the Given Number is : 11 \ No newline at end of file diff --git a/c-sharp/Conversions/C# Program to Convert Decimal to Octal.cs b/c-sharp/Conversions/C# Program to Convert Decimal to Octal.cs new file mode 100644 index 0000000..83a839f --- /dev/null +++ b/c-sharp/Conversions/C# Program to Convert Decimal to Octal.cs @@ -0,0 +1,30 @@ +/* + * C# Program to Convert Decimal to Octal + */ +using System; +class program +{ + public static void Main() + { + int decimalNumber, quotient, i = 1, j; + int[] octalNumber = new int[100]; + Console.WriteLine("Enter a Decimal Number :"); + decimalNumber = int.Parse(Console.ReadLine()); + quotient = decimalNumber; + while (quotient != 0) + { + octalNumber[i++] = quotient % 8; + quotient = quotient / 8; + } + Console.Write("Equivalent Octal Number is "); + for (j = i - 1; j > 0; j--) + Console.Write(octalNumber[j]); + Console.Read(); + } +} + +/* + +Enter a Decimal Number : +50 +Equivalent Octal Number is 62 \ No newline at end of file diff --git a/c-sharp/Conversions/C# Program to Convert Digits to Words.cs b/c-sharp/Conversions/C# Program to Convert Digits to Words.cs new file mode 100644 index 0000000..ddb733c --- /dev/null +++ b/c-sharp/Conversions/C# Program to Convert Digits to Words.cs @@ -0,0 +1,46 @@ +/* + * C# Program to Convert Digits to Words + */ +using System; + +public class ConvertDigitsToWords +{ + public static void Main() + { + int num; + int nextdigit; + int numdigits; + int[] n = new int[20]; + string[] digits = { "zero", "one", "two", + "three", "four", "five", + "six", "seven", "eight", + "nine" + }; + Console.WriteLine("Enter the number"); + num = Convert.ToInt32(Console.ReadLine()); + Console.WriteLine("Number: " + num); + Console.Write("Number in words: "); + nextdigit = 0; + numdigits = 0; + do + { + nextdigit = num % 10; + n[numdigits] = nextdigit; + numdigits++; + num = num / 10; + } + while(num > 0); + numdigits--; + for( ; numdigits >= 0; numdigits--) + Console.Write(digits[n[numdigits]] + " "); + Console.WriteLine(); + Console.ReadLine(); + } +} + +/* + +Enter the number +1548 +Number: 1548 +Number in words: one five four eight \ No newline at end of file diff --git a/c-sharp/Conversions/C# Program to Convert Fahrenheit to Celsius.cs b/c-sharp/Conversions/C# Program to Convert Fahrenheit to Celsius.cs new file mode 100644 index 0000000..e1cda03 --- /dev/null +++ b/c-sharp/Conversions/C# Program to Convert Fahrenheit to Celsius.cs @@ -0,0 +1,29 @@ +/* + * C# Program to Convert Fahrenheit to Celsius + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +namespace Celsius +{ +class Program +{ + static void Main(string[] args) + { + double celsius; + Console.Write("Enter Fahrenheit temperature : "); + double fahrenheit = Convert.ToDouble(Console.ReadLine()); + celsius = (fahrenheit - 32) * 5 / 9; + Console.WriteLine("The converted Celsius temperature is" + celsius); + Console.ReadLine(); + } +} +} + +/* + +Output: +Enter Fahrenheit temperature : 95.5 +The converted Celsius temperature is35.2777777777778 \ No newline at end of file diff --git a/c-sharp/Conversions/C# Program to Convert Infix to Postfix.cs b/c-sharp/Conversions/C# Program to Convert Infix to Postfix.cs new file mode 100644 index 0000000..bf5e28a --- /dev/null +++ b/c-sharp/Conversions/C# Program to Convert Infix to Postfix.cs @@ -0,0 +1,108 @@ +/* + * C# Program to Convert Infix to Postfix + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +namespace Infix +{ +class Program +{ + static bool convert(ref string infix, out string postfix) + { + int prio = 0; + postfix = ""; + Stack s1 = new Stack(); + for (int i = 0; i < infix.Length; i++) + { + char ch = infix[i]; + if (ch == '+' || ch == '-' || ch == '*' || ch == '/') + { + if (s1.Count <= 0) + s1.Push(ch); + else + { + if (s1.Peek() == '*' || s1.Peek() == '/') + prio = 1; + else + prio = 0; + if (prio == 1) + { + if (ch == '+' || ch == '-') + { + postfix += s1.Pop(); + i--; + } + else + { + postfix += s1.Pop(); + i--; + } + } + else + { + if (ch == '+' || ch == '-') + { + postfix += s1.Pop(); + s1.Push(ch); + } + else + s1.Push(ch); + } + } + } + else + { + postfix += ch; + } + } + int len = s1.Count; + for (int j = 0; j < len; j++) + postfix += s1.Pop(); + return true; + } + static void Main(string[] args) + { + string infix = ""; + string postfix = ""; + if (args.Length == 1) + { + infix = args[0]; + convert(ref infix, out postfix); + System.Console.WriteLine("InFix :\t" + infix); + System.Console.WriteLine("PostFix:\t" + postfix); + } + else + { + infix = "a+b*c-d"; + convert(ref infix, out postfix); + System.Console.WriteLine("InFix :\t" + infix); + System.Console.WriteLine("PostFix :\t" + postfix); + System.Console.WriteLine(); + infix = "a+b*c-d/e*f"; + convert(ref infix, out postfix); + System.Console.WriteLine("InFix :\t" + infix); + System.Console.WriteLine("PostFix :\t" + postfix); + System.Console.WriteLine(); + infix = "a-b/c*d-e--f/h*i++j-/k"; + convert(ref infix, out postfix); + System.Console.WriteLine("InFix :\t" + infix); + System.Console.WriteLine("PostFix :\t" + postfix); + System.Console.WriteLine(); + Console.ReadLine(); + } + } +} +} + +/* + +Infix : a+b*c-d +Postfix : abc*+d- + +Infix : a+b*c-d/e*f +Postfix : abc*+de/f*- + +Infix : a-b/c*d-e--f/h*I++j-/k +Postfix : abc/d*-e--fh/I*-=j=k/- \ No newline at end of file diff --git a/c-sharp/Conversions/C# Program to Convert a Given Number of Days in terms of Years, Weeks & Days.cs b/c-sharp/Conversions/C# Program to Convert a Given Number of Days in terms of Years, Weeks & Days.cs new file mode 100644 index 0000000..267bc92 --- /dev/null +++ b/c-sharp/Conversions/C# Program to Convert a Given Number of Days in terms of Years, Weeks & Days.cs @@ -0,0 +1,25 @@ +/* + * C# Program to Convert a Given Number of Days in terms of + * Years, Weeks & Days + */ +using System; +class program +{ + public static void Main() + { + int ndays, year, week, days, DAYSINWEEK=7; + Console.WriteLine("Enter the number of days"); + ndays = int.Parse(Console.ReadLine()); + year = ndays / 365; + week = (ndays % 365) / DAYSINWEEK; + days = (ndays % 365) % DAYSINWEEK; + Console.WriteLine("{0} is equivalent to {1}years, {2}weeks and {3}days", ndays, year, week, days); + Console.ReadLine(); + } +} + +/* + +Enter the number of days +1000 +1000 is equivalent to 2 years, 38 weeks and 4 days \ No newline at end of file diff --git a/c-sharp/Conversions/C# Program to Covert HexaDecimal Number to Decimal.cs b/c-sharp/Conversions/C# Program to Covert HexaDecimal Number to Decimal.cs new file mode 100644 index 0000000..6154a8f --- /dev/null +++ b/c-sharp/Conversions/C# Program to Covert HexaDecimal Number to Decimal.cs @@ -0,0 +1,27 @@ +/* + * C# Program to Covert HexaDecimal Number to Decimal + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +namespace ConsoleApplication +{ +class Program +{ + static void Main(string[] args) + { + string Input; + Console.WriteLine("Enter a Hexadecimal Number :"); + Input = Console.ReadLine(); + int Output = int.Parse(Input, System.Globalization.NumberStyles.HexNumber); + Console.WriteLine("The Decimal value is " + Output); + Console.Read(); + } +} +} + +/* +Enter a HexaDecimal Number : ABC +The Decimal value is : 2748 \ No newline at end of file diff --git a/c-sharp/Conversions/C# Program to Create a Gray Code.cs b/c-sharp/Conversions/C# Program to Create a Gray Code.cs new file mode 100644 index 0000000..566a53a --- /dev/null +++ b/c-sharp/Conversions/C# Program to Create a Gray Code.cs @@ -0,0 +1,43 @@ +/* + * C# Program to Create a Gray Code + */ +using System; +public class Gray +{ + public static ulong grayEncode(ulong n) + { + return n ^ (n >> 1); + } + + public static ulong grayDecode(ulong n) + { + ulong i = 1 << 8 * 64 - 2; //long is 64-bit + ulong p, b = p = n & i; + while ((i >>= 1) > 0) + b |= p = n & i ^ p >> 1; + return b; + } + + public static void Main(string[] args) + { + Console.WriteLine("Number\tGray"); + for (ulong i = 0; i < 10; i++) + { + Console.WriteLine(string.Format("{0}\t{1}", i, Convert.ToString((long)grayEncode(i), 2))); + } + Console.Read(); + } +} + +/* +Number Gray +0 0 +1 1 +2 11 +3 10 +4 110 +5 111 +6 101 +7 100 +8 1100 +9 1101 \ No newline at end of file diff --git a/c-sharp/Conversions/C# Program to Demonstrate DefaultIfEmpty case.cs b/c-sharp/Conversions/C# Program to Demonstrate DefaultIfEmpty case.cs new file mode 100644 index 0000000..d1e55c5 --- /dev/null +++ b/c-sharp/Conversions/C# Program to Demonstrate DefaultIfEmpty case.cs @@ -0,0 +1,64 @@ +/* + * C# Program to Demonstrate DefaultIfEmpty case + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +namespace program +{ +class student +{ + public string Name { get; set; } + public string stuID { get; set; } + +} +class studentdetails +{ + public string SID { get; set; } + public string City { get; set; } +} + +class Program +{ + static void Main(string[] args) + { + List objstudent = new List + { + new student{ Name="Bob",stuID="I001"}, + new student{ Name="Vijay",stuID="I002"}, + new student{ Name="Jerry",stuID="I003"}, + new student{ Name="Tom",stuID="I004"}, + new student{ Name="Senthil",stuID="I005"}, + }; + List objstudentdetails = new List + { + new studentdetails{ SID="I001",City="Delhi"}, + new studentdetails{ SID="I002",City="Mumbai"}, + new studentdetails{ SID="I007",City="Chennai"}, + new studentdetails{ SID="I008",City="Pune"}, + new studentdetails{ SID="I009",City=""}, + }; + var resultDefaultIfEmpty = from stu in objstudent + join studentdetails in objstudentdetails on stu.stuID equals studentdetails.SID into ResultEmpstudentdetails + from output in ResultEmpstudentdetails.DefaultIfEmpty() + select new + { + studentName = stu.Name, + City = output != null ? output.City : null + }; + Console.WriteLine(string.Join("\n", resultDefaultIfEmpty.Select(stu => " student Name = " + + stu.studentName + ", City Name = " + stu.City).ToArray())); + Console.ReadLine(); + } +} +} + +/* + + student Name = Bob, City Name = Delhi + student Name = Vijay, City Name = Mumbai + student Name = Jerry, City Name = + student Name = Tom, City Name = + student Name = Senthil, City Name = \ No newline at end of file diff --git a/c-sharp/Conversions/C# Program to Obtain the Character from the User and Convert the Case of the Character.cs b/c-sharp/Conversions/C# Program to Obtain the Character from the User and Convert the Case of the Character.cs new file mode 100644 index 0000000..090b48b --- /dev/null +++ b/c-sharp/Conversions/C# Program to Obtain the Character from the User and Convert the Case of the Character.cs @@ -0,0 +1,34 @@ +/* + * C# Program to Obtain the Character from the User and Convert the Case of the Character + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +namespace casechange +{ +class Program +{ + static void Main(string[] args) + { + char a; + int i; + Console.WriteLine("Enter the Character : "); + a = Convert.ToChar(Console.ReadLine()); + i=(int)a; + if (a >= 65 && a <= 90) + { + Console.WriteLine("The Character is : {0}", char.ToLower(a)); + } + else if (a >= 97 && a <= 122) + { + Console.WriteLine("The Character is : {0}", char.ToUpper(a)); + } + Console.ReadLine(); + } +} + +/* + +Enter the Character : a +The Character is : A \ No newline at end of file diff --git a/c-sharp/Conversions/C# Program to Perfom Currency Conversions.cs b/c-sharp/Conversions/C# Program to Perfom Currency Conversions.cs new file mode 100644 index 0000000..8a2ffb8 --- /dev/null +++ b/c-sharp/Conversions/C# Program to Perfom Currency Conversions.cs @@ -0,0 +1,60 @@ +/* + * C# Program to Perfom Currency Conversions + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +namespace Program +{ +class Program +{ + static void Main(string[] args) + { + int choice; + Console.WriteLine("Enter your Choice :\n 1- Dollar to Rupee \n 2- Euro to Rupee \n 3- Malaysian Ringgit to Rupee "); + choice = int.Parse(Console.ReadLine()); + switch (choice) + { + case 1: + Double dollar, rupee,val; + Console.WriteLine("Enter the Dollar Amount :"); + dollar = Double.Parse(Console.ReadLine()); + Console.WriteLine("Enter the Dollar Value :"); + val = double.Parse(Console.ReadLine()); + rupee = dollar * val; + Console.WriteLine("{0} Dollar Equals {1} Rupees", dollar, rupee); + break; + case 2: + Double Euro, rupe,valu; + Console.WriteLine("Enter the Euro Amount :"); + Euro = Double.Parse(Console.ReadLine()); + Console.WriteLine("Enter the Euro Value :"); + valu = double.Parse(Console.ReadLine()); + rupe = Euro * valu; + Console.WriteLine("{0} Euro Equals {1} Rupees", Euro, rupe); + break; + case 3: + Double ringit, rup,value; + Console.WriteLine("Enter the Ringgit Amount :"); + ringit = Double.Parse(Console.ReadLine()); + Console.WriteLine("Enter the Ringgit Value :"); + value = double.Parse(Console.ReadLine()); + rup = ringit * value; + Console.WriteLine("{0} Malaysian Ringgit Equals {1} Rupees", ringit, rup); + break; + } + Console.ReadLine(); + } +} +} + +/* +Enter the Choice : + 1 - Dollar to Rupee + 2 - Euro to Rupee + 3 - Malaysian Ringgit to Rupee +1 +Enter the Dollar Amount : 20 +Enter the Dollar Value : 62.58 +20 Dollar Equals 1251.6 Rupees diff --git a/c-sharp/Conversions/C# Program to Perform Binary to Decimal Conversion.cs b/c-sharp/Conversions/C# Program to Perform Binary to Decimal Conversion.cs new file mode 100644 index 0000000..0910fe6 --- /dev/null +++ b/c-sharp/Conversions/C# Program to Perform Binary to Decimal Conversion.cs @@ -0,0 +1,36 @@ +/* + * C# Program to Perform Binary to Decimal Conversion + */ +using System; +using System.Collections.Generic; +using System.Text; + +namespace Program +{ +class Program +{ + static void Main(string[] args) + { + int num, binary_val, decimal_val = 0, base_val = 1, rem; + Console.Write("Enter a Binary Number(1s and 0s) : "); + num = int.Parse(Console.ReadLine()); /* maximum five digits */ + binary_val = num; + while (num > 0) + { + rem = num % 10; + decimal_val = decimal_val + rem * base_val; + num = num / 10 ; + base_val = base_val * 2; + } + Console.Write("The Binary Number is : "+binary_val); + Console.Write("\nIts Decimal Equivalent is : "+decimal_val); + Console.ReadLine(); + } +} +} + +/* + +Enter a Binary Number(1s and 0s) : 101010 +The Binary Number is : 101010 +Its Decimal Equivalent is : 42 \ No newline at end of file diff --git a/c-sharp/Conversions/C# Program to Perform Celsius to Fahrenheit Conversion.cs b/c-sharp/Conversions/C# Program to Perform Celsius to Fahrenheit Conversion.cs new file mode 100644 index 0000000..8944668 --- /dev/null +++ b/c-sharp/Conversions/C# Program to Perform Celsius to Fahrenheit Conversion.cs @@ -0,0 +1,28 @@ +/* + * C# Program to Perform Celsius to Fahrenheit Conversion + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +namespace program +{ +class Program +{ + static void Main(string[] args) + { + int celsius, faren; + Console.WriteLine("Enter the Temperature in Celsius(°C) : "); + celsius = int.Parse(Console.ReadLine()); + faren = (celsius * 9) / 5 + 32; + Console.WriteLine("0Temperature in Fahrenheit is(°F) : " + faren); + Console.ReadLine(); + } +} +} + +/* + +Enter the Temperature in Celsius (°C) : 20 +Temperature in Fahrenheit(°F) is : 68 \ No newline at end of file diff --git a/c-sharp/Conversions/C# Program to Perform Conversions of Meter to Kilometer and viceversa.cs b/c-sharp/Conversions/C# Program to Perform Conversions of Meter to Kilometer and viceversa.cs new file mode 100644 index 0000000..f9f121d --- /dev/null +++ b/c-sharp/Conversions/C# Program to Perform Conversions of Meter to Kilometer and viceversa.cs @@ -0,0 +1,49 @@ +/* + * C# Program to Perform Conversions of Meter to Kilometer and viceversa + */ +using System; +class Program +{ + static void Main() + { + double m1 = 200; + Console.WriteLine("Meter :: Kilometer"); + double k1 = ConvertDistance.cMtK(m1); + Console.WriteLine("{0} :: {1}", m1, k1); + double m4 = 3107; + double k4 = ConvertDistance.cMtK(m4); + Console.WriteLine("{0} :: {1}", m4, k4); + double k3 = 5.1; + Console.WriteLine(); + Console.WriteLine("Kilometer :: Meter"); + double m3 = ConvertDistance.cKtM(k3); + Console.WriteLine("{0} :: {1}", k3, m3); + double k2 = 3.219; + double m2 = ConvertDistance.cKtM(k2); + Console.WriteLine("{0} :: {1}", k2, m2); + Console.Read(); + } +} + +public static class ConvertDistance +{ + public static double cMtK(double meters) + { + return meters / 1000; + } + + public static double cKtM(double kilometers) + { + return kilometers * 1000; + } +} + +/* + +Meter :: Kilometer +200 :: 0.200000 +3107 :: 3.107 + +Kilometer :: Meter +5.1 :: 5100 +3.219 :: 3219 \ No newline at end of file diff --git a/c-sharp/Conversions/C# Program to Perform Decimal to HexaDecimal Conversion.cs b/c-sharp/Conversions/C# Program to Perform Decimal to HexaDecimal Conversion.cs new file mode 100644 index 0000000..c4f2808 --- /dev/null +++ b/c-sharp/Conversions/C# Program to Perform Decimal to HexaDecimal Conversion.cs @@ -0,0 +1,38 @@ +/* + * C# Program to Perform Decimal to HexaDecimal Conversion + */ +using System; +class program +{ + public static void Main() + { + int decimalNumber, quotient; + int i = 1, j, temp = 0; + char[] hexadecimalNumber = new char[100]; + char temp1; + Console.WriteLine("Enter a Decimal Number :"); + decimalNumber = int.Parse(Console.ReadLine()); + quotient = decimalNumber; + while (quotient != 0) + { + temp = quotient % 16; + if (temp < 10) + temp = temp + 48; + else + temp = temp + 55; + temp1 = Convert.ToChar(temp); + hexadecimalNumber[i++] = temp1; + quotient = quotient / 16; + } + Console.Write("Equivalent HexaDecimal Number is "); + for (j = i - 1; j > 0; j--) + Console.Write(hexadecimalNumber[j]); + Console.Read(); + } +} + +/* + +Enter a Decimal Number : +45 +Equivalent HexaDecimal Number is 2D \ No newline at end of file diff --git a/c-sharp/DataStructures/C# Program to Create a Singly Linked Circular List.cs b/c-sharp/DataStructures/C# Program to Create a Singly Linked Circular List.cs new file mode 100644 index 0000000..4afc096 --- /dev/null +++ b/c-sharp/DataStructures/C# Program to Create a Singly Linked Circular List.cs @@ -0,0 +1,137 @@ +/* + * C# Program to Create a Singly Linked Circular List + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +namespace CSTest +{ +class Circlist +{ + private int currentdata; + private Circlist nextdata; + public Circlist() + { + currentdata = 0; + nextdata = this; + } + public Circlist(int value) + { + currentdata = value; + nextdata = this; + } + public Circlist Insdata(int value) + { + Circlist node = new Circlist(value); + if (this.nextdata == this) + { + node.nextdata = this; + this.nextdata = node; + } + else + { + Circlist temp = this.nextdata; + node.nextdata = temp; + this.nextdata = node; + } + return node; + } + public int Deldata() + { + if (this.nextdata == this) + { + System.Console.WriteLine("\nOnly one node!!!!"); + return 0; + } + Circlist node = this.nextdata; + this.nextdata = this.nextdata.nextdata; + node = null; + return 1; + } + public void Traverse() + { + Traverse(this); + } + public void Traverse(Circlist node) + { + if (node == null) + node = this; + System.Console.WriteLine("Forward Direction!!!!"); + Circlist snode = node; + do + { + System.Console.WriteLine(node.currentdata); + node = node.nextdata; + } + while (node != snode); + } + public int Gnodes() + { + return Gnodes(this); + } + public int Gnodes(Circlist node) + { + if (node == null) + node = this; + int count = 0; + Circlist snode = node; + do + { + count++; + node = node.nextdata; + } + while (node != snode); + System.Console.WriteLine("\nCurrent Node Value : " + node.currentdata.ToString()); + System.Console.WriteLine("\nTotal nodes :" + count.ToString()); + return count; + } + static void Main(string[] args) + { + Circlist node1 = new Circlist(1); + node1.Deldata(); + Circlist node2 = node1.Insdata(2); + node1.Deldata(); + node2 = node1.Insdata(2); + Circlist node3 = node2.Insdata(3); + Circlist node4 = node3.Insdata(4); + Circlist node5 = node4.Insdata(5); + node1.Gnodes(); + node3.Gnodes(); + node5.Gnodes(); + node1.Traverse(); + node3.Deldata(); + node2.Traverse(); + node1.Gnodes(); + node3.Gnodes(); + node5.Gnodes(); + Console.Read(); + } +} +} + +/* +Only one Node!!!!! +Current Node Value : 1 +Total nodes : 5 +Current Node Value : 3 +Total nodes : 5 +Current Node Value : 5 +Total nodes : 5 +Forward Direction!!!! +1 +2 +3 +4 +5 +Forward Direction!!!! +2 +3 +5 +1 +Current Node Value : 1 +Total nodes : 4 +Current Node Value : 3 +Total nodes : 4 +Current Node Value: 5 +Total nodes : 4 \ No newline at end of file diff --git a/c-sharp/DataStructures/C# Program to Create an Instance of StackTrace and to Get all Frames.cs b/c-sharp/DataStructures/C# Program to Create an Instance of StackTrace and to Get all Frames.cs new file mode 100644 index 0000000..9952b9b --- /dev/null +++ b/c-sharp/DataStructures/C# Program to Create an Instance of StackTrace and to Get all Frames.cs @@ -0,0 +1,30 @@ +/* + * C# Program to Create an Instance of StackTrace and to Get all Frames + */ +using System.Diagnostics; +using System; +class program +{ + public static void Main() + { + StackTrace stackTrace = new StackTrace(); + StackFrame[] stackFrames = stackTrace.GetFrames(); + // write call stack method names + Console.WriteLine("Method Names : "); + foreach (StackFrame stackFrame in stackFrames) + { + Console.WriteLine(stackFrame.GetMethod().Name); + } + Console.Read(); + } +} + +/* +Method Names : +Main +nExecuteAssembly +ExecuteAssembly +RunUsersAssembly +ThreadStart_Context +Run +ThreadStart \ No newline at end of file diff --git a/c-sharp/DataStructures/C# Program to Implement Binary Search Tree using Linked List.cs b/c-sharp/DataStructures/C# Program to Implement Binary Search Tree using Linked List.cs new file mode 100644 index 0000000..8cb114b --- /dev/null +++ b/c-sharp/DataStructures/C# Program to Implement Binary Search Tree using Linked List.cs @@ -0,0 +1,132 @@ +/* + * C# Program to Implement Binary Search Tree using Linked List + */ +using System; +using System.Collections.Generic; +using System.Text; +namespace TreeSort +{ +class Node +{ + public int item; + public Node leftc; + public Node rightc; + public void display() + { + Console.Write("["); + Console.Write(item); + Console.Write("]"); + } +} +class Tree +{ + public Node root; + public Tree() + { + root = null; + } + public Node ReturnRoot() + { + return root; + } + public void Insert(int id) + { + Node newNode = new Node(); + newNode.item = id; + if (root == null) + root = newNode; + else + { + Node current = root; + Node parent; + while (true) + { + parent = current; + if (id < current.item) + { + current = current.leftc; + if (current == null) + { + parent.leftc = newNode; + return; + } + } + else + { + current = current.rightc; + if (current == null) + { + parent.rightc = newNode; + return; + } + } + } + } + } + public void Preorder(Node Root) + { + if (Root != null) + { + Console.Write(Root.item + " "); + Preorder(Root.leftc); + Preorder(Root.rightc); + } + } + public void Inorder(Node Root) + { + if (Root != null) + { + Inorder(Root.leftc); + Console.Write(Root.item + " "); + Inorder(Root.rightc); + } + } + public void Postorder(Node Root) + { + if (Root != null) + { + Postorder(Root.leftc); + Postorder(Root.rightc); + Console.Write(Root.item + " "); + } + } +} +class Program +{ + static void Main(string[] args) + { + Tree theTree = new Tree(); + theTree.Insert(20); + theTree.Insert(25); + theTree.Insert(45); + theTree.Insert(15); + theTree.Insert(67); + theTree.Insert(43); + theTree.Insert(80); + theTree.Insert(33); + theTree.Insert(67); + theTree.Insert(99); + theTree.Insert(91); + Console.WriteLine("Inorder Traversal : "); + theTree.Inorder(theTree.ReturnRoot()); + Console.WriteLine(" "); + Console.WriteLine(); + Console.WriteLine("Preorder Traversal : "); + theTree.Preorder(theTree.ReturnRoot()); + Console.WriteLine(" "); + Console.WriteLine(); + Console.WriteLine("Postorder Traversal : "); + theTree.Postorder(theTree.ReturnRoot()); + Console.WriteLine(" "); + Console.ReadLine(); + } +} +} + +/* +Inorder Traversal : +15 20 25 33 43 45 67 67 80 91 99 +Preorder Traversal : +20 15 25 45 43 33 67 80 67 99 91 +Postorder Traversal : +15 33 43 67 91 99 80 67 45 25 20 \ No newline at end of file diff --git a/c-sharp/DataStructures/C# Program to Implement Stack with Push and Pop operations.cs b/c-sharp/DataStructures/C# Program to Implement Stack with Push and Pop operations.cs new file mode 100644 index 0000000..96a8919 --- /dev/null +++ b/c-sharp/DataStructures/C# Program to Implement Stack with Push and Pop operations.cs @@ -0,0 +1,149 @@ +/* + * C# Program to Implement Stack with Push and Pop operations + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +using System.Threading.Tasks; +namespace ConsoleApplication1 +{ +class Program +{ + static void Main(string[] args) + { + stack st = new stack(); + while (true) + { + Console.Clear(); + Console.WriteLine("\nStack MENU(size -- 10)"); + Console.WriteLine("1. Add an element"); + Console.WriteLine("2. See the Top element."); + Console.WriteLine("3. Remove top element."); + Console.WriteLine("4. Display stack elements."); + Console.WriteLine("5. Exit"); + Console.Write("Select your choice: "); + int choice = Convert.ToInt32(Console.ReadLine()); + switch (choice) + { + case 1: + Console.WriteLine("Enter an Element : "); + st.Push(Console.ReadLine()); + break; + case 2: + Console.WriteLine("Top element is: {0}", st.Peek()); + break; + case 3: + Console.WriteLine("Element removed: {0}", st.Pop()); + break; + case 4: + st.Display(); + break; + case 5: + System.Environment.Exit(1); + break; + } + Console.ReadKey(); + } + } +} + +interface StackADT +{ + Boolean isEmpty(); + void Push(Object element); + Object Pop(); + Object Peek(); + void Display(); +} +class stack : StackADT +{ + private int StackSize; + public int StackSizeSet + { + get { return StackSize; } + set { StackSize = value; } + } + public int top; + Object[] item; + public stack() + { + StackSizeSet = 10; + item = new Object[StackSizeSet]; + top = -1; + } + public stack(int capacity) + { + StackSizeSet = capacity; + item = new Object[StackSizeSet]; + top = -1; + } + public bool isEmpty() + { + if (top == -1) return true; + return false; + } + public void Push(object element) + { + if (top == (StackSize - 1)) + { + Console.WriteLine("Stack is full!"); + } + else + { + item[++top] = element; + Console.WriteLine("Item pushed successfully!"); + } + } + public object Pop() + { + if (isEmpty()) + { + Console.WriteLine("Stack is empty!"); + return "No elements"; + } + else + { + return item[top--]; + } + } + public object Peek() + { + if (isEmpty()) + { + Console.WriteLine("Stack is empty!"); + return "No elements"; + } + else + { + return item[top]; + } + } + + + public void Display() + { + for (int i = top; i > -1; i--) + { + Console.WriteLine("Item {0}: {1}", (i + 1), item[i]); + } + } +} +} + +/* +Stack MENU(size -- 10) +1. Add an element +2. See the Top Element +3. Remove the Top Element +4. Display Stack Elements +5. Exit +Select your Choice : 1 +Enter the Element : 25 +Item Pushed Successfully! +Select your choice :1 +Enter the Element : 26 +Item Pushed Successfully! +Select your choice : 4 +Item 2 :26 +Item 1 :25 \ No newline at end of file diff --git a/c-sharp/DataStructures/C# Program to Implement Traversal in Singly Linked List.cs b/c-sharp/DataStructures/C# Program to Implement Traversal in Singly Linked List.cs new file mode 100644 index 0000000..a63d758 --- /dev/null +++ b/c-sharp/DataStructures/C# Program to Implement Traversal in Singly Linked List.cs @@ -0,0 +1,90 @@ +/* + * C# Program to Implement Traversal in Singly Linked List + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +namespace Program +{ +class singlelist +{ + private int data; + private singlelist next; + public singlelist() + { + data = 0; + next = null; + } + public singlelist(int value) + { + data = value; + next = null; + } + public singlelist InsertNext(int value) + { + singlelist node = new singlelist(value); + if (this.next == null) + { + node.next = null; + this.next = node; + } + else + { + singlelist temp = this.next; + node.next = temp; + this.next = node; + } + return node; + } + public int DeleteNext() + { + if (next == null) + return 0; + singlelist node = this.next; + this.next = this.next.next; + node = null; + return 1; + } + public void Traverse(singlelist node) + { + if (node == null) + node = this; + System.Console.WriteLine("Traversing :"); + while (node != null) + { + System.Console.WriteLine(node.data); + node = node.next; + } + } +} +class Program +{ + static void Main(string[] args) + { + singlelist node1 = new singlelist(11); + singlelist node2 = node1.InsertNext(12); + singlelist node3 = node2.InsertNext(13); + singlelist node4 = node3.InsertNext(14); + singlelist node5 = node4.InsertNext(15); + node1.Traverse(null); + Console.WriteLine("Deleting !!"); + node3.DeleteNext(); + node2.Traverse(null); + System.Console.ReadLine(); + } +} +} + +/* +Traversing : +11 +12 +13 +14 +15 +Deleting!!! +Traversing : +12 +13 +14 \ No newline at end of file diff --git a/c-sharp/Delegates/C# Program to Call Math Operations using Delegates..txt b/c-sharp/Delegates/C# Program to Call Math Operations using Delegates..txt new file mode 100644 index 0000000..6ebc5cb --- /dev/null +++ b/c-sharp/Delegates/C# Program to Call Math Operations using Delegates..txt @@ -0,0 +1,59 @@ +/* + * C# Program to Call Math Operations using Delegates + */ + +using System; +public class MathOperations +{ + public static double Multiply(double value) + { + return value * 2; + } + + public static double Square(double value) + { + return value * value; + } +} + + +delegate double DoubleOp(double x); + +class Application +{ + static void Main() + { + DoubleOp[] operations = + { + MathOperations.Multiply, + MathOperations.Square + }; + for (int i = 0; i < operations.Length; i++) + { + Console.WriteLine("Operation[{0}]:", i); + ProcessAndDisplayNumber(operations[i], 5.0); + ProcessAndDisplayNumber(operations[i], 13.55); + ProcessAndDisplayNumber(operations[i], 1.732); + Console.WriteLine(); + } + Console.ReadLine(); + } + + static void ProcessAndDisplayNumber(DoubleOp action, double value) + { + double result = action(value); + Console.WriteLine( + "Value : {0} Result : {1}", value, result); + } +} +/* + +Operation[0]: +Value : 5 Result : 10 +Value : 13.55 Result : 27.1 +Value : 1.732 Result : 3.464 + +Operation[1]: +Value : 5 Result : 25 +Value : 13.55 Result : 183.6025 +Value : 1.732 Result : 2.999824 \ No newline at end of file diff --git a/c-sharp/Delegates/C# Program to Combine Two Delegates..txt b/c-sharp/Delegates/C# Program to Combine Two Delegates..txt new file mode 100644 index 0000000..b122235 --- /dev/null +++ b/c-sharp/Delegates/C# Program to Combine Two Delegates..txt @@ -0,0 +1,46 @@ +/* + * C# Program to Combine Two Delegates + */ +using System; +delegate void dele(string s); +class TestClass +{ + static void Good(string s) + { + System.Console.WriteLine(" Good, {0}!", s); + } + + static void Morning(string s) + { + System.Console.WriteLine(" Morning, {0}!", s); + } + + static void Main() + { + dele firstdel, secondDel, multiDel, multiMinusfirstdel; + firstdel = Good; + secondDel = Morning; + multiDel = firstdel + secondDel; + multiMinusfirstdel = multiDel - firstdel; + Console.WriteLine("Invoking delegate firstdel:"); + firstdel("A"); + Console.WriteLine("Invoking delegate secondDel:"); + secondDel("B"); + Console.WriteLine("Invoking delegate multiDel:"); + multiDel("C"); + Console.WriteLine("Invoking delegate multiMinusfirstdel:"); + multiMinusfirstdel("D"); + Console.ReadLine(); + } +} +/* + +Invoking delegate firstDel: + Good, A! +Invoking delegate SecondDel: + Morning, B! +Invoking delegate multiDel: + Good, C! + Morning, C! +Invoking delegate multiMinusFirstDel: + Morning, D! \ No newline at end of file diff --git a/c-sharp/Delegates/C# Program to Convert Feet to Inches using Delegates..txt b/c-sharp/Delegates/C# Program to Convert Feet to Inches using Delegates..txt new file mode 100644 index 0000000..76cece2 --- /dev/null +++ b/c-sharp/Delegates/C# Program to Convert Feet to Inches using Delegates..txt @@ -0,0 +1,27 @@ +/* + * C# Program to Convert Feet to Inches using Delegates + */ +using System; +public delegate double Conversion(double from); +class DelegateDemo +{ + public static double FeetToInches(double feet) + { + return feet * 12; + } + + static void Main() + { + Conversion doConversion = new Conversion(FeetToInches); + Console.Write("Enter Feet: "); + double feet = Double.Parse(Console.ReadLine()); + double inches = doConversion(feet); + Console.WriteLine("\n{0} Feet = {1} Inches.\n", feet, inches); + Console.ReadLine(); + } +} +/* + +Enter Feet: 50 + +50 Feet = 600 Inches. \ No newline at end of file diff --git a/c-sharp/Delegates/C# Program to Create Generic Delegate..txt b/c-sharp/Delegates/C# Program to Create Generic Delegate..txt new file mode 100644 index 0000000..04dd415 --- /dev/null +++ b/c-sharp/Delegates/C# Program to Create Generic Delegate..txt @@ -0,0 +1,43 @@ +/* + * C# Program to Create Generic Delegate + */ +using System; +using System.Collections.Generic; +delegate T NumberChanger(T n); +namespace GenericDelegateAppl +{ +class TestDelegate +{ + static int num = 10; + public static int AddNum(int p) + { + num += p; + return num; + } + + public static int MultNum(int q) + { + num *= q; + return num; + } + public static int getNum() + { + return num; + } + + static void Main(string[] args) + { + NumberChanger nc1 = new NumberChanger(AddNum); + NumberChanger nc2 = new NumberChanger(MultNum); + nc1(25); + Console.WriteLine("Value of Num: {0}", getNum()); + nc2(5); + Console.WriteLine("Value of Num: {0}", getNum()); + Console.ReadKey(); + } +} +} +/* + +Result of the Addition : 35 +Result of the Product : 350 \ No newline at end of file diff --git a/c-sharp/Delegates/C# Program to Declare and Instantiate Delegates..txt b/c-sharp/Delegates/C# Program to Declare and Instantiate Delegates..txt new file mode 100644 index 0000000..e128064 --- /dev/null +++ b/c-sharp/Delegates/C# Program to Declare and Instantiate Delegates..txt @@ -0,0 +1,17 @@ +/* + * C# Program to Declare and Instantiate Delegates + */ +using System; +delegate void dele1(); +public class Delegateintro +{ + static void Main() + { + dele1 del = new dele1(Write); + del(); + } + static void Write() + { + Console.WriteLine("Calling Write "); + } +} \ No newline at end of file diff --git a/c-sharp/Delegates/C# Program to Display Results using Delegates..txt b/c-sharp/Delegates/C# Program to Display Results using Delegates..txt new file mode 100644 index 0000000..0ea3fd9 --- /dev/null +++ b/c-sharp/Delegates/C# Program to Display Results using Delegates..txt @@ -0,0 +1,27 @@ +/* + * C# Program to Display Results using Delegates + */ +using System; +public class example +{ + public delegate int DelegateHandler(int a, int b); + static void Main(string[] args) + { + Results Results = new Results(); + DelegateHandler sum = new DelegateHandler(Results.sum); + int result = sum(50, 20); + Console.WriteLine("Result is: " + result); + Console.ReadLine(); + } +} + +public class Results +{ + public int sum(int a, int b) + { + return a + b; + } +} +/* + +Result is: 70 \ No newline at end of file diff --git a/c-sharp/Delegates/C# Program to Illustrate Array of Delegates..txt b/c-sharp/Delegates/C# Program to Illustrate Array of Delegates..txt new file mode 100644 index 0000000..7793c20 --- /dev/null +++ b/c-sharp/Delegates/C# Program to Illustrate Array of Delegates..txt @@ -0,0 +1,48 @@ +/* + * C# Program to Illustrate Array of Delegates + */ +using System; +delegate double Measure(double R); +public class Circle +{ + const double PI = 3.14159; + public double Diameter(double Radius) + { + return Radius * 2; + } + + public double Circumference(double Radius) + { + return Diameter(Radius) * PI; + } + + public double Area(double Radius) + { + return Radius * Radius * PI; + } +} +public static class Program +{ + static int Main() + { + double R = 10; + Circle circ = new Circle(); + Measure[] Calc = new Measure[3]; + Calc[0] = new Measure(circ.Diameter); + double D = Calc[0](R); + Calc[1] = new Measure(circ.Circumference); + double C = Calc[1](R); + Calc[2] = new Measure(circ.Area); + double A = Calc[2](R); + Console.WriteLine("Diameter: {0}", D); + Console.WriteLine("Circumference: {0}", C); + Console.WriteLine("Area: {0}\n", A); + Console.ReadLine(); + return 0; + } +} +/* + +Diameter : 20 +Circumference : 62.8318 +Area : 314.159 \ No newline at end of file diff --git a/c-sharp/Delegates/C# Program to Implement Arithmetic Operations using Delegates..txt b/c-sharp/Delegates/C# Program to Implement Arithmetic Operations using Delegates..txt new file mode 100644 index 0000000..7c830a4 --- /dev/null +++ b/c-sharp/Delegates/C# Program to Implement Arithmetic Operations using Delegates..txt @@ -0,0 +1,42 @@ +/* + * C# Program to Implement Arithmetic Operations using Delegates + */ +using System; +delegate int NumberChanger(int n); +namespace example +{ +class Delegate +{ + static int num = 10; + public static int AddNum(int a) + { + num += a; + return num; + } + + public static int MultNum(int b) + { + num *= b; + return num; + } + public static int getNum() + { + return num; + } + + static void Main(string[] args) + { + NumberChanger n1 = new NumberChanger(AddNum); + NumberChanger n2 = new NumberChanger(MultNum); + n1(25); + Console.WriteLine("Value of Num: {0}", getNum()); + n2(5); + Console.WriteLine("Value of Num: {0}", getNum()); + Console.ReadKey(); + } +} +} +/* + +Value of Num: 35 +Value of Num: 175 \ No newline at end of file diff --git a/c-sharp/Delegates/C# Program to Implement Delegates..txt b/c-sharp/Delegates/C# Program to Implement Delegates..txt new file mode 100644 index 0000000..00597ca --- /dev/null +++ b/c-sharp/Delegates/C# Program to Implement Delegates..txt @@ -0,0 +1,51 @@ +/* + * C# Program to Implement Delegates + */ +using System; +using System.IO; +delegate void delegatewriter(string message); +class delgwriter +{ + StreamWriter w; + public delgwriter(string path) + { + w = File.CreateText(path); + } + public void display(string msg) + { + w.WriteLine(msg); + } + public void Flush() + { + w.Flush(); + } + public void Close() + { + w.Close(); + } +} +class Test +{ + static delegatewriter delgwri; + static void display(string s) + { + Console.WriteLine(s); + } + static void Main(string[] arg) + { + delgwriter x = new delgwriter("log.txt"); + delgwri += new delegatewriter(display); + delgwri += new delegatewriter(x.display); + delgwri("C"); + delgwri("C++"); + delgwri("Java"); + x.Flush(); + x.Close(); + Console.Read(); + } +} +/* + +C +C++ +Java \ No newline at end of file diff --git a/c-sharp/Delegates/C# Program to Implement Multicast Delegates..txt b/c-sharp/Delegates/C# Program to Implement Multicast Delegates..txt new file mode 100644 index 0000000..871dd65 --- /dev/null +++ b/c-sharp/Delegates/C# Program to Implement Multicast Delegates..txt @@ -0,0 +1,34 @@ +/* + * C# Program to Implement Multicast Delegates + */ +using System; +delegate void dele(int a, int b); +public class Oper +{ + public static void Add(int a, int b) + { + Console.WriteLine("{0} + {1} = {2}", a, b, a + b); + } + + public static void Sub(int a, int b) + { + Console.WriteLine("{0} - {1} = {2}", a, b, a - b); + } +} +public class program +{ + static void Main() + { + dele del = new dele(Oper.Add); + del += new dele(Oper.Sub); + del(4, 2); + del -= new dele(Oper.Sub); + del(1, 9); + Console.Read(); + } +} +/* + +4 + 2 = 6 +4 - 2 = 2 +1 + 9 = 10 \ No newline at end of file diff --git a/c-sharp/Delegates/C# Program to Implement Principles of Delegates..txt b/c-sharp/Delegates/C# Program to Implement Principles of Delegates..txt new file mode 100644 index 0000000..6c3d673 --- /dev/null +++ b/c-sharp/Delegates/C# Program to Implement Principles of Delegates..txt @@ -0,0 +1,46 @@ +/* + * C# Program to Implement Principles of Delegates + */ + +using System; +class Program +{ + delegate string UppercaseDelegate(string input); + static string UppercaseFirst(string input) + { + char[] buffer = input.ToCharArray(); + buffer[0] = char.ToUpper(buffer[0]); + return new string(buffer); + } + static string UppercaseLast(string input) + { + char[] buffer = input.ToCharArray(); + buffer[buffer.Length - 1] = char.ToUpper(buffer[buffer.Length - 1]); + return new string(buffer); + } + static string UppercaseAll(string input) + { + return input.ToUpper(); + } + static void WriteOutput(string input, UppercaseDelegate del) + { + Console.WriteLine("Input String: {0}", input); + Console.WriteLine("Output String: {0}", del(input)); + } + static void Main() + { + WriteOutput("tom ", new UppercaseDelegate(UppercaseFirst)); + WriteOutput("tom", new UppercaseDelegate(UppercaseLast)); + WriteOutput("tom", new UppercaseDelegate(UppercaseAll)); + Console.ReadLine(); + } +} +/* + + +Input String: tom +Output String: Tom +Input String: tom +Output String: toM +Input String: tom +Output String: TOM \ No newline at end of file diff --git a/c-sharp/Delegates/C# Program to Use Delegate to Call 2 Methods within which First method Prints to Console and Second Method Prints to File..txt b/c-sharp/Delegates/C# Program to Use Delegate to Call 2 Methods within which First method Prints to Console and Second Method Prints to File..txt new file mode 100644 index 0000000..4772b21 --- /dev/null +++ b/c-sharp/Delegates/C# Program to Use Delegate to Call 2 Methods within which First method Prints to Console and Second Method Prints to File..txt @@ -0,0 +1,43 @@ +/* + * C# Program to Use Delegate to Call 2 Methods within which First method Prints to Console and Second Method Prints to File + */ +using System; +using System.IO; +namespace Program +{ +class PrintString +{ + static FileStream fs; + static StreamWriter sw; + public delegate void printString(string s); + public static void Screen(string str) + { + Console.WriteLine("The String is: {0}", str); + } + public static void File(string s) + { + fs = new FileStream("c:\\sri\\Message.txt", + FileMode.Append, FileAccess.Write); + sw = new StreamWriter(fs); + sw.WriteLine(s); + sw.Flush(); + sw.Close(); + fs.Close(); + } + public static void sendString(printString ps) + { + ps("C# Program to Use Delegate to Call 2 Methods within which First method Prints to Console and Second Method Prints to File"); + } + static void Main(string[] args) + { + printString ps1 = new printString(Screen); + printString ps2 = new printString(File); + sendString(ps1); + sendString(ps2); + Console.ReadKey(); + } +} +} +/* + +The String is : C# Program to Use Delegate to Call 2 Methods within which First method Prints to Console and Second Method Prints to File \ No newline at end of file diff --git a/c-sharp/Events/C# Program to Add Two TimeSpan.cs b/c-sharp/Events/C# Program to Add Two TimeSpan.cs new file mode 100644 index 0000000..bb527a8 --- /dev/null +++ b/c-sharp/Events/C# Program to Add Two TimeSpan.cs @@ -0,0 +1,15 @@ +/* + * C# Program to Add Two TimeSpan + */ +using System; +class Program +{ + static void Main() + { + TimeSpan s1 = new TimeSpan(5, 0, 0); + TimeSpan s2 = new TimeSpan(2, 0, 0); + TimeSpan s3 = s1.Add(s2); + Console.WriteLine(s3); + Console.Read(); + } +} \ No newline at end of file diff --git a/c-sharp/Events/C# Program to Create Input Box and Display the Text.cs b/c-sharp/Events/C# Program to Create Input Box and Display the Text.cs new file mode 100644 index 0000000..1438213 --- /dev/null +++ b/c-sharp/Events/C# Program to Create Input Box and Display the Text.cs @@ -0,0 +1,28 @@ +/* + * C# Program to Create Input Box and Display the Text + */ +using System; +using System.Collections.Generic; +using System.ComponentModel; +using System.Data; +using System.Drawing; +using System.Linq; +using System.Text; +using System.Windows.Forms; + +namespace WindowsFormsApplication6 +{ +public partial class Form1 : Form +{ + public Form1() + { + InitializeComponent(); + } + + private void button1_Click(object sender, EventArgs e) + { + MessageBox.Show(textBox1.Text); + Console.ReadLine(); + } +} +} \ No newline at end of file diff --git a/c-sharp/Events/C# Program to Create Radio Button and Demonstrate its Use.cs b/c-sharp/Events/C# Program to Create Radio Button and Demonstrate its Use.cs new file mode 100644 index 0000000..55015ee --- /dev/null +++ b/c-sharp/Events/C# Program to Create Radio Button and Demonstrate its Use.cs @@ -0,0 +1,30 @@ +/* + * C# Program to Create Radio Button and Demonstrate its Use + */ +using System; +using System.Collections.Generic; +using System.ComponentModel; +using System.Data; +using System.Drawing; +using System.Linq; +using System.Text; +using System.Windows.Forms; +namespace WindowsFormsApplication5 +{ +public partial class Form1 : Form +{ + public Form1() + { + InitializeComponent(); + } + + private void label1_Click(object sender, EventArgs e) + { + } + + private void button1_Click(object sender, EventArgs e) + { + MessageBox.Show("You Have Clicked Your Pet Animal Using Radio Button "); + } +} +} \ No newline at end of file diff --git a/c-sharp/Events/C# Program to Create Stop Watch.cs b/c-sharp/Events/C# Program to Create Stop Watch.cs new file mode 100644 index 0000000..e20ef63 --- /dev/null +++ b/c-sharp/Events/C# Program to Create Stop Watch.cs @@ -0,0 +1,25 @@ +/* + * C# Program to Create Stop Watch + */ +using System; +using System.Diagnostics; +using System.Threading; +class Program +{ + static void Main() + { + // Create new stopwatch + Stopwatch stopwatch = new Stopwatch(); + // Begin timing + stopwatch.Start(); + for (int i = 0; i < 10; i++) + { + Console.WriteLine("HI"); + } + // Stop timing + stopwatch.Stop(); + Console.WriteLine("Time Elapsed : {0}", + stopwatch.Elapsed); + Console.ReadLine(); + } +} \ No newline at end of file diff --git a/c-sharp/Events/C# Program to Create a Progress Bar Control.cs b/c-sharp/Events/C# Program to Create a Progress Bar Control.cs new file mode 100644 index 0000000..045f635 --- /dev/null +++ b/c-sharp/Events/C# Program to Create a Progress Bar Control.cs @@ -0,0 +1,42 @@ +/* + * C# Program to Create a Progress Bar Control + */ +using System; +using System.Collections.Generic; +using System.ComponentModel; +using System.Data; +using System.Drawing; +using System.Linq; +using System.Text; +using System.Windows.Forms; + +namespace ProgressBar +{ +public partial class Form1 : Form +{ + public Form1() + { + InitializeComponent(); + } + + private void backgroundWorker1_DoWork(object sender, DoWorkEventArgs e) + { + for (int i = 1; i <= 100; i++) + { + System.Threading.Thread.Sleep(100); + backgroundWorker1.ReportProgress(i); + } + } + + private void backgroundWorker1_ProgressChanged(object sender, ProgressChangedEventArgs e) + { + progressBar1.Value = e.ProgressPercentage; + this.Text = e.ProgressPercentage.ToString(); + } + + private void Form1_Load(object sender, EventArgs e) + { + backgroundWorker1.RunWorkerAsync(); + } +} +} \ No newline at end of file diff --git a/c-sharp/Events/C# Program to Demonstrate Trigger Concept.cs b/c-sharp/Events/C# Program to Demonstrate Trigger Concept.cs new file mode 100644 index 0000000..0380367 --- /dev/null +++ b/c-sharp/Events/C# Program to Demonstrate Trigger Concept.cs @@ -0,0 +1,63 @@ +/* + * C# Program to Demonstrate Trigger Concept + */ +using System; +delegate bool Condition(object obj); +delegate void Action(object obj); +class Counter +{ + int val = 0; + + public event Condition cond; + public event Action evn; + + public int Value { get { return val; } } + + public void addition(int x) + { + val += x; + Checkpoint(); + } + + public void Clearall() + { + val = 0; + Checkpoint(); + } + + void Checkpoint() + { + if (cond != null && evn != null && cond(this)) evn(this); + } +} +class Test +{ + static int hval = 0; + static bool CheckpointLimit(object ctr) + { + return (((Counter)ctr).Value > 100); + } + static void Alarm(object ctr) + { + Console.WriteLine("Counter Overflow"); + } + static void Reset(object ctr) + { + hval = ((Counter)ctr).Value; + Console.WriteLine("hval = " + hval); + ((Counter)ctr).Clearall(); + } + public static void Main() + { + Counter counter = new Counter(); + counter.cond += new Condition(CheckpointLimit); + counter.evn += new Action(Alarm); + counter.evn += new Action(Reset); + counter.addition(10); + counter.addition(20); + counter.addition(30); + counter.addition(40); + counter.addition(50); + Console.Read(); + } +} \ No newline at end of file diff --git a/c-sharp/Events/C# Program to Demonstrate Use of Clone.cs b/c-sharp/Events/C# Program to Demonstrate Use of Clone.cs new file mode 100644 index 0000000..bb544ac --- /dev/null +++ b/c-sharp/Events/C# Program to Demonstrate Use of Clone.cs @@ -0,0 +1,19 @@ +/* + * C# Program to Demonstrate Use of Clone + */ +using System; +class Program +{ + static void Main() + { + string[] names = { "San", "Csharp", "Linux" }; + string[] clonenames = names.Clone() as string[]; + Console.WriteLine(string.Join(",", names)); + Console.WriteLine(string.Join(",", clonenames)); + Console.WriteLine(); + clonenames[0] = "SanFoundry"; + Console.WriteLine(string.Join(",", names)); + Console.WriteLine(string.Join(",", clonenames)); + Console.Read(); + } +} \ No newline at end of file diff --git a/c-sharp/Events/C# Program to Detect Whether ENTER key is Pressed or Not.cs b/c-sharp/Events/C# Program to Detect Whether ENTER key is Pressed or Not.cs new file mode 100644 index 0000000..aef2d6d --- /dev/null +++ b/c-sharp/Events/C# Program to Detect Whether ENTER key is Pressed or Not.cs @@ -0,0 +1,27 @@ +/* + * C# Program to Detect Whether ENTER key is Pressed or Not + */ +using System; +using System.Collections.Generic; +using System.ComponentModel; +using System.Data; +using System.Drawing; +using System.Linq; +using System.Text; +using System.Windows.Forms; + +namespace WindowsFormsApplication12 +{ +public partial class Form1 : Form +{ + public Form1() + { + InitializeComponent(); + } + private void textBox1_KeyUp(object sender, KeyEventArgs e) + { + if (e.KeyValue == 13) + MessageBox.Show("Enter key pressed"); + } +} +} \ No newline at end of file diff --git a/c-sharp/Events/C# Program to Get the DayLight Saving Information.cs b/c-sharp/Events/C# Program to Get the DayLight Saving Information.cs new file mode 100644 index 0000000..221de7f --- /dev/null +++ b/c-sharp/Events/C# Program to Get the DayLight Saving Information.cs @@ -0,0 +1,17 @@ +/* + * C# Program to Get the DayLight Saving Information + */ +using System; +using System.Globalization; +class Program +{ + static void Main() + { + TimeZone z = TimeZone.CurrentTimeZone; + DaylightTime t = z.GetDaylightChanges(DateTime.Today.Year); + Console.WriteLine("Start Time: {0}", t.Start); + Console.WriteLine("Delta Time: {0}", t.Delta); + Console.WriteLine("End Time: {0}", t.End); + Console.ReadLine(); + } +} \ No newline at end of file diff --git a/c-sharp/Events/C# Program to Illustrate Actions.cs b/c-sharp/Events/C# Program to Illustrate Actions.cs new file mode 100644 index 0000000..d0e3f88 --- /dev/null +++ b/c-sharp/Events/C# Program to Illustrate Actions.cs @@ -0,0 +1,16 @@ +/* + * C# Program to Illustrate Actions + */ +using System; + +class Program +{ + static void Main() + { + Action action1 =(int x) => Console.WriteLine("OUTPUT {0}", x); + Action action2 =(x, y) => Console.WriteLine("OUTPUT {0} and {1}", x, y); + action1.Invoke(1111); + action2.Invoke(200, 3000); + Console.Read(); + } +} \ No newline at end of file diff --git a/c-sharp/Events/C# Program to Illustrate Elapsed Event.cs b/c-sharp/Events/C# Program to Illustrate Elapsed Event.cs new file mode 100644 index 0000000..fc6e32a --- /dev/null +++ b/c-sharp/Events/C# Program to Illustrate Elapsed Event.cs @@ -0,0 +1,22 @@ +/* + * C# Program to Illustrate Elapsed Event + */ +using System; +using System.Timers; +public class Program +{ + private static System.Timers.Timer Tim; + public static void Main() + { + Tim = new System.Timers.Timer(10); + Tim.Elapsed += new ElapsedEventHandler(OnTimedEvent); + Tim.Interval = 1000; + Tim.Enabled = true; + Console.WriteLine("Press Any Key to Exit else Elapsed Event will be Raised "); + Console.ReadLine(); + } + private static void OnTimedEvent(object source, ElapsedEventArgs e) + { + Console.WriteLine("The Elapsed event was Raised {0}", e.SignalTime); + } +} \ No newline at end of file diff --git a/c-sharp/Events/C# Program to Illustrate Predicate.cs b/c-sharp/Events/C# Program to Illustrate Predicate.cs new file mode 100644 index 0000000..b643113 --- /dev/null +++ b/c-sharp/Events/C# Program to Illustrate Predicate.cs @@ -0,0 +1,16 @@ +/* + * C# Program to Illustrate Predicate + */ +using System; + +class Program +{ + static void Main() + { + Predicate predicate = checkval => checkval == 6; + Console.WriteLine(predicate.Invoke(4)); + Console.WriteLine(predicate.Invoke(5)); + Console.WriteLine(predicate.Invoke(6)); + Console.Read(); + } +} \ No newline at end of file diff --git a/c-sharp/Events/C# Program to Perform Addition with MOUSEUP Event.cs b/c-sharp/Events/C# Program to Perform Addition with MOUSEUP Event.cs new file mode 100644 index 0000000..f7bcaf9 --- /dev/null +++ b/c-sharp/Events/C# Program to Perform Addition with MOUSEUP Event.cs @@ -0,0 +1,32 @@ +/* + * C# Program to Perform Addition with MOUSEUP Event + */ +using System; +using System.Collections.Generic; +using System.ComponentModel; +using System.Data; +using System.Drawing; +using System.Linq; +using System.Text; +using System.Windows.Forms; + +namespace WindowsFormsApplication14 +{ +public partial class Form1 : Form +{ + public Form1() + { + InitializeComponent(); + } + + private void button1_MouseUp(object sender, MouseEventArgs e) + { + int add; + add = Convert.ToInt32(textBox1.Text) +Convert.ToInt32(textBox2.Text); + textBox3.Text = Convert.ToString(add); + MessageBox.Show("Addition is performed with MouseUp Event"); + } +} +} + +/* diff --git a/c-sharp/Events/C# Program to Perform Subtraction with Key Up Event.cs b/c-sharp/Events/C# Program to Perform Subtraction with Key Up Event.cs new file mode 100644 index 0000000..a4e1b28 --- /dev/null +++ b/c-sharp/Events/C# Program to Perform Subtraction with Key Up Event.cs @@ -0,0 +1,30 @@ +/* + * C# Program to Perform Subtraction with Key Up Event + */ +using System; +using System.Collections.Generic; +using System.ComponentModel; +using System.Data; +using System.Drawing; +using System.Linq; +using System.Text; +using System.Windows.Forms; + +namespace WindowsFormsApplication14 +{ +public partial class Form1 : Form +{ + public Form1() + { + InitializeComponent(); + } + + private void button1_KeyUp(object sender, KeyEventArgs e) + { + int sub; + sub = Convert.ToInt32(textBox1.Text) - Convert.ToInt32(textBox2.Text); + textBox3.Text = Convert.ToString(sub); + MessageBox.Show("Subtraction is performed with KeyUp Event"); + } +} +} \ No newline at end of file diff --git a/c-sharp/Events/C# Program to get the Local Time.cs b/c-sharp/Events/C# Program to get the Local Time.cs new file mode 100644 index 0000000..24d2e4b --- /dev/null +++ b/c-sharp/Events/C# Program to get the Local Time.cs @@ -0,0 +1,14 @@ +/* + * C# Program to get the Local Time + */ +using System; +class Program +{ + static void Main() + { + TimeZone zone = TimeZone.CurrentTimeZone; + DateTime local = zone.ToLocalTime(DateTime.Now); + Console.WriteLine("The Local Time is : {0}",local); + Console.ReadLine(); + } +} \ No newline at end of file diff --git a/c-sharp/Events/C# Program to get the Universal Time.cs b/c-sharp/Events/C# Program to get the Universal Time.cs new file mode 100644 index 0000000..efac240 --- /dev/null +++ b/c-sharp/Events/C# Program to get the Universal Time.cs @@ -0,0 +1,14 @@ +/* + * C# Program to get the Universal Time + */ +using System; +class Program +{ + static void Main() + { + TimeZone zone = TimeZone.CurrentTimeZone; + DateTime univ = zone.ToUniversalTime(DateTime.Now); + Console.WriteLine("Universal Time is {0}",univ); + Console.Read(); + } +} \ No newline at end of file diff --git a/c-sharp/Exception/C# Program to Demonstrate DivideByZero Exception.cs b/c-sharp/Exception/C# Program to Demonstrate DivideByZero Exception.cs new file mode 100644 index 0000000..d9a91f3 --- /dev/null +++ b/c-sharp/Exception/C# Program to Demonstrate DivideByZero Exception.cs @@ -0,0 +1,20 @@ +/* + * C# Program to Demonstrate DivideByZero Exception + */ +using System; +class Program +{ + static void Main() + { + try + { + int result = 15 / int.Parse("0"); + Console.WriteLine(result); + } + catch (DivideByZeroException e) + { + Console.Write(e.Message); + Console.ReadLine(); + } + } +} \ No newline at end of file diff --git a/c-sharp/Exception/C# Program to Demonstrate Exception Handling for Stack Overflow.cs b/c-sharp/Exception/C# Program to Demonstrate Exception Handling for Stack Overflow.cs new file mode 100644 index 0000000..1cb9bbb --- /dev/null +++ b/c-sharp/Exception/C# Program to Demonstrate Exception Handling for Stack Overflow.cs @@ -0,0 +1,24 @@ +/* + * C# Program to Demonstrate Exception Handling for Stack Overflow + */ +using System; +class Program +{ + static void excep(int value) + { + Console.WriteLine(value); + excep(++value); + } + + static void Main() + { + try + { + excep(0); + } + catch (StackOverflowException e) + { + Console.WriteLine(e.Message); + } + } +} \ No newline at end of file diff --git a/c-sharp/Exception/C# Program to Demonstrate IndexOutOfRange Exception.cs b/c-sharp/Exception/C# Program to Demonstrate IndexOutOfRange Exception.cs new file mode 100644 index 0000000..0300728 --- /dev/null +++ b/c-sharp/Exception/C# Program to Demonstrate IndexOutOfRange Exception.cs @@ -0,0 +1,39 @@ +/* + * C# Program to Demonstrate IndexOutOfRange Exception + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +namespace differnce +{ +class arrayoutofindex +{ + public void calculatedifference() + { + int difference=0; + int [] number= new int[5] {1,2,3,4,5}; + try + { + for (int init =1; init <=5; init++) + { + difference= difference - number[init]; + } + Console.WriteLine("The difference of the array is:" + difference); + } + catch (IndexOutOfRangeException e) + { + Console.WriteLine(e.Message); + } + } +} +class classmain +{ + static void Main(string [] args) + { + arrayoutofindex obj = new arrayoutofindex(); + obj.calculatedifference(); + Console.ReadLine(); + } +} +} \ No newline at end of file diff --git a/c-sharp/Exception/C# Program to Demonstrate Multiple Exceptions.cs b/c-sharp/Exception/C# Program to Demonstrate Multiple Exceptions.cs new file mode 100644 index 0000000..604c006 --- /dev/null +++ b/c-sharp/Exception/C# Program to Demonstrate Multiple Exceptions.cs @@ -0,0 +1,64 @@ +/* + * C# Program to Demonstrate Multiple Exceptions + */ +using System; +class Exercise +{ + static void Main() + { + double Num1, Num2; + double Result = 0.00; + char op; + try + { + Console.Write("Enter your First Number : "); + Num1 = double.Parse(Console.ReadLine()); + Console.Write("Enter an Operator (+, -, * or /): "); + op = char.Parse(Console.ReadLine()); + if (op != '+' && op != '-' && + op != '*' && op != '/') + throw new Exception(op.ToString()); + Console.Write("Enter your Second Number :"); + Num2 = double.Parse(Console.ReadLine()); + if (op == '/') + if (Num2 == 0) + throw new DivideByZeroException("Division by zero is not allowed"); + Result = Calculator(Num1, Num2, op); + Console.WriteLine("\n{0} {1} {2} = {3}", Num1, op, Num2, Result); + } + catch (FormatException) + { + Console.WriteLine("The number you typed is not valid"); + } + catch (DivideByZeroException ex) + { + Console.WriteLine(ex.Message); + } + catch (Exception ex) + { + Console.WriteLine("Operation Error: {0} is not a valid op", ex.Message); + } + Console.Read(); + } + + static double Calculator(double v1, double v2, char op) + { + double Result = 0.00; + switch (op) + { + case '+': + Result = v1 + v2; + break; + case '-': + Result = v1 - v2; + break; + case '*': + Result = v1 * v2; + break; + case '/': + Result = v1 / v2; + break; + } + return Result; + } +} \ No newline at end of file diff --git a/c-sharp/Exception/C# Program to Illustrate Exception Handling for Invalid TypeCasting in UnBoxing.cs b/c-sharp/Exception/C# Program to Illustrate Exception Handling for Invalid TypeCasting in UnBoxing.cs new file mode 100644 index 0000000..4db65f7 --- /dev/null +++ b/c-sharp/Exception/C# Program to Illustrate Exception Handling for Invalid TypeCasting in UnBoxing.cs @@ -0,0 +1,21 @@ +/* + * C# Program to Illustrate Exception Handling for Invalid TypeCasting in UnBoxing + */ +class TestUnboxing +{ + static void Main() + { + int num = 123; + object obj = num; + try + { + int j = (short)obj; + System.Console.WriteLine("Unboxing"); + } + catch (System.InvalidCastException e) + { + System.Console.WriteLine("{0} Error: Incorrect unboxing", e.Message); + } + System.Console.Read(); + } +} \ No newline at end of file diff --git a/c-sharp/Exception/C# Program to Illustrate NullRefernce Exception.cs b/c-sharp/Exception/C# Program to Illustrate NullRefernce Exception.cs new file mode 100644 index 0000000..961be6b --- /dev/null +++ b/c-sharp/Exception/C# Program to Illustrate NullRefernce Exception.cs @@ -0,0 +1,23 @@ +/* + * C# Program to Illustrate NullRefernce Exception + */ +using System; +class Program +{ + static void Main() + { + try + { + string value = null; + if (value.Length == 0) + { + Console.WriteLine(value); + } + } + catch(NullReferenceException e) + { + Console.WriteLine(e.Message); + } + Console.Read(); + } +} \ No newline at end of file diff --git a/c-sharp/Files/C# Program to Calculate the Size of Folder.cs b/c-sharp/Files/C# Program to Calculate the Size of Folder.cs new file mode 100644 index 0000000..fbd821c --- /dev/null +++ b/c-sharp/Files/C# Program to Calculate the Size of Folder.cs @@ -0,0 +1,40 @@ +/* + * C# Program to Calculate the Size of Folder + */ +using System; +using System.Linq; +using System.IO; +namespace ConsoleApplication3 +{ +class Program +{ + static void Main(string[] args) + { + DirectoryInfo dInfo = new DirectoryInfo(@"C:/sri"); + long sizeOfDir = DirectorySize(dInfo, true); + Console.WriteLine("Directory size in Bytes : " + + "{0:N0} Bytes", sizeOfDir); + Console.WriteLine("Directory size in KB : " + + "{0:N2} KB", ((double)sizeOfDir) / 1024); + Console.WriteLine("Directory size in MB : " + + "{0:N2} MB", ((double)sizeOfDir) / (1024 * 1024)); + Console.ReadLine(); + } + static long DirectorySize(DirectoryInfo dInfo, bool includeSubDir) + { + long totalSize = dInfo.EnumerateFiles() + .Sum(file => file.Length); + if (includeSubDir) + { + totalSize += dInfo.EnumerateDirectories() + .Sum(dir => DirectorySize(dir, true)); + } + return totalSize; + } +} +} + +/* +Directory Size in Bytes : 1,482 Bytes +Directory Size in KB : 1.45 KB +Directory Size in MB : 0.00 MB \ No newline at end of file diff --git a/c-sharp/Files/C# Program to Check the Existence of a File.cs b/c-sharp/Files/C# Program to Check the Existence of a File.cs new file mode 100644 index 0000000..10f2053 --- /dev/null +++ b/c-sharp/Files/C# Program to Check the Existence of a File.cs @@ -0,0 +1,25 @@ +/* + * C# Program to Check the Existence of a File + */ +using System; +using System.IO; +class Program +{ + static void Main() + { + FileInfo info = new FileInfo("C:\\sri\\srip.txt"); + bool exists = info.Exists; + if (exists == true) + { + Console.WriteLine("The File Exists"); + } + else + { + Console.WriteLine("No Such File Found"); + } + Console.Read(); + } +} + +/* +File Exists \ No newline at end of file diff --git a/c-sharp/Files/C# Program to Copy the Contents from one File to another File.cs b/c-sharp/Files/C# Program to Copy the Contents from one File to another File.cs new file mode 100644 index 0000000..9ca4ac5 --- /dev/null +++ b/c-sharp/Files/C# Program to Copy the Contents from one File to another File.cs @@ -0,0 +1,19 @@ +/* + * C# Program to Print the Sum of all the Multiples of 3 and 5 + */ +using System; +using System.IO; +class Program +{ + static void Main() + { + File.Copy("sri.txt", "srip.txt"); + Console.WriteLine(File.ReadAllText("sri.txt")); + Console.WriteLine(File.ReadAllText("srip.txt")); + Console.Read(); + } +} + +/* +Contents of File S +Contents of File S \ No newline at end of file diff --git a/c-sharp/Files/C# Program to Create a Directory.cs b/c-sharp/Files/C# Program to Create a Directory.cs new file mode 100644 index 0000000..47fa254 --- /dev/null +++ b/c-sharp/Files/C# Program to Create a Directory.cs @@ -0,0 +1,17 @@ +/* + * C# Program to Create a Directory + */ +using System; +using System.IO; +class program +{ + public static void Main() + { + Directory.CreateDirectory("C:\\NewDirectory"); + Console.WriteLine("NewDirectory is Created in C Directory"); + Console.ReadLine(); + } +} + +/* +NewDirectory is Created in C Directory \ No newline at end of file diff --git a/c-sharp/Files/C# Program to Create a File.cs b/c-sharp/Files/C# Program to Create a File.cs new file mode 100644 index 0000000..ee454ed --- /dev/null +++ b/c-sharp/Files/C# Program to Create a File.cs @@ -0,0 +1,30 @@ +/* + * C# Program to Create a File + */ +using System; +using System.IO; +using System.Text; +class Test +{ + public static void Main() + { + string textpath = @"c:\sri\test.txt"; + using (FileStream fs = File.Create(textpath)) + { + Byte[] info = new UTF8Encoding(true).GetBytes("File is Created"); + fs.Write(info, 0, info.Length); + } + using (StreamReader sr = File.OpenText(textpath)) + { + string s = ""; + while ((s = sr.ReadLine()) != null) + { + Console.WriteLine(s); + } + } + Console.Read(); + } +} + +/* +File is Created \ No newline at end of file diff --git a/c-sharp/Files/C# Program to Demonstrate StringReader.cs b/c-sharp/Files/C# Program to Demonstrate StringReader.cs new file mode 100644 index 0000000..984a18d --- /dev/null +++ b/c-sharp/Files/C# Program to Demonstrate StringReader.cs @@ -0,0 +1,31 @@ +/* + * C# Program to Demonstrate StringReader + */ +using System; +using System.IO; + +class Program +{ + const string text = @"Sanfoundry + offers Training and Competency + development programs"; + static void Main() + { + using (StringReader reader = new StringReader(text)) + { + int count = 0; + string textline; + while ((textline = reader.ReadLine()) != null) + { + count++; + Console.WriteLine("Line {0}: {1}", count, textline); + } + Console.ReadLine(); + } + } +} + +/* +Line 1 : Sanfoundry +Line 2 : Offers Training and Competency +Line 3 : development programs \ No newline at end of file diff --git a/c-sharp/Files/C# Program to Get Content from a File and Read the Content 1 Byte at a Time.cs b/c-sharp/Files/C# Program to Get Content from a File and Read the Content 1 Byte at a Time.cs new file mode 100644 index 0000000..bb0b214 --- /dev/null +++ b/c-sharp/Files/C# Program to Get Content from a File and Read the Content 1 Byte at a Time.cs @@ -0,0 +1,23 @@ +/* + * C# Program to Get Content from a File and Read the Content 1 Byte at a Time + */ +using System; +using System.IO; +public sealed class Program +{ + public static void Main() + { + using (Stream s = new FileStream(@"c:\sri\srip.txt", FileMode.Open)) + { + int read; + while ((read = s.ReadByte()) != -1) + { + Console.Write("{0} ", read); + } + Console.ReadLine(); + } + } +} + +/* +71 79 79 68 77 79 82 78 73 78 71 \ No newline at end of file diff --git a/c-sharp/Files/C# Program to Get File Time using File Class.cs b/c-sharp/Files/C# Program to Get File Time using File Class.cs new file mode 100644 index 0000000..ba0bae6 --- /dev/null +++ b/c-sharp/Files/C# Program to Get File Time using File Class.cs @@ -0,0 +1,21 @@ +/* + * C# Program to Get File Time using File Class + */ +using System; +using System.IO; + +class Program +{ + static void Main() + { + FileInfo info = new FileInfo("C:\\srip.txt"); + DateTime time = info.CreationTime; + Console.WriteLine("File was Created at : "); + Console.Write(time); + Console.Read(); + } +} + +/* +File was Created at : +9/30/2013 12:15:44 PM \ No newline at end of file diff --git a/c-sharp/Files/C# Program to Illustrate Memory Stream Class.cs b/c-sharp/Files/C# Program to Illustrate Memory Stream Class.cs new file mode 100644 index 0000000..2805c49 --- /dev/null +++ b/c-sharp/Files/C# Program to Illustrate Memory Stream Class.cs @@ -0,0 +1,46 @@ +/* + * C# Program to Illustrate Memory Stream Class + */ +using System; +using System.IO; +using System.Text; +class MemStream +{ + static void Main() + { + int count; + byte[] byteArray; + char[] charArray; + UnicodeEncoding uniEncoding = new UnicodeEncoding(); + byte[] firstString = uniEncoding.GetBytes("Invalid file path characters are: "); + byte[] secondString = uniEncoding.GetBytes(Path.GetInvalidPathChars()); + using(MemoryStream memStream = new MemoryStream(100)) + { + memStream.Write(firstString, 0, firstString.Length); + count = 0; + while(count < secondString.Length) + { + memStream.WriteByte(secondString[count++]); + } + Console.WriteLine("Capacity = {0}, Length = {1}, Position = {2}\n", + memStream.Capacity.ToString(), + memStream.Length.ToString(), + memStream.Position.ToString()); + memStream.Seek(0, SeekOrigin.Begin); + byteArray = new byte[memStream.Length]; + count = memStream.Read(byteArray, 0, 20); + while (count < memStream.Length) + { + byteArray[count++] = Convert.ToByte(memStream.ReadByte()); + } + charArray = new char[uniEncoding.GetCharCount(byteArray, 0, count)]; + uniEncoding.GetDecoder().GetChars(byteArray, 0, count, charArray, 0); + Console.WriteLine(charArray); + Console.Read(); + } + } +} + +/* +Capacity = 256 Length = 140 Position =140 +Invalid File Path Characters are : "<>| \ No newline at end of file diff --git a/c-sharp/Files/C# Program to Illustrate Methods of FileInfo Class.cs b/c-sharp/Files/C# Program to Illustrate Methods of FileInfo Class.cs new file mode 100644 index 0000000..1ff7553 --- /dev/null +++ b/c-sharp/Files/C# Program to Illustrate Methods of FileInfo Class.cs @@ -0,0 +1,49 @@ +/* + * C# Program to Illustrate Methods of FileInfo Class + */ +using System; +using System.IO; +class Test +{ + public static void Main() + { + string path = Path.GetTempFileName(); + FileInfo fi1 = new FileInfo(path); + using (StreamWriter sw = fi1.CreateText()) + { + sw.WriteLine("This is"); + sw.WriteLine("Codenza"); + sw.WriteLine("Website"); + } + using (StreamReader sr = fi1.OpenText()) + { + string s = ""; + while ((s = sr.ReadLine()) != null) + { + Console.WriteLine(s); + } + } + try + { + string path2 = Path.GetTempFileName(); + FileInfo fi2 = new FileInfo(path2); + fi2.Delete(); + fi1.CopyTo(path2); + Console.WriteLine("{0} was copied to {1}.", path, path2); + fi2.Delete(); + Console.WriteLine("{0} was successfully deleted.", path2); + } + catch (Exception e) + { + Console.WriteLine("The process failed: {0}", e.ToString()); + } + Console.Read(); + } +} + +/* +This is +Codenza +Website. +C:\Users\win7\AppData\Local\Temp\tmpAEF8.tmp was copied to C:\users\Win7\AppData\Local\Temp\tmpAEF7.tmp +C:\users\Win7\AppData\Local\Temp\tmpAEF8.tmp was successfully deleted. \ No newline at end of file diff --git a/c-sharp/Files/C# Program to Illustrate StringBuilder.cs b/c-sharp/Files/C# Program to Illustrate StringBuilder.cs new file mode 100644 index 0000000..1c06aa0 --- /dev/null +++ b/c-sharp/Files/C# Program to Illustrate StringBuilder.cs @@ -0,0 +1,25 @@ +/* + * C# Program to Illustrate StringBuilder + */ +using System; +using System.Text; +class Program +{ + static void Main() + { + StringBuilder bd = new StringBuilder(); + bd.Append("1 "); + bd.Append("2 "); + bd.Append("3 "); + for (int i = 0; i < 5; i++) + { + bd.Append("z "); + } + string result = bd.ToString(); + Console.WriteLine(result); + Console.ReadLine(); + } +} + +/* +1 2 3 z z z z z \ No newline at end of file diff --git a/c-sharp/Files/C# Program to Illustrate StringWriter.cs b/c-sharp/Files/C# Program to Illustrate StringWriter.cs new file mode 100644 index 0000000..eee4936 --- /dev/null +++ b/c-sharp/Files/C# Program to Illustrate StringWriter.cs @@ -0,0 +1,44 @@ +/* + * C# Program to Illustrate StringWriter + */ +using System; +using System.IO; +using System.Text; +public class stringwrt +{ + StringBuilder sb = new StringBuilder(); + public stringwrt() + { + Writer(); + } + public static void Main() + { + stringwrt srw = new stringwrt(); + } + private void Writer() + { + StringWriter sw = new StringWriter(sb); + Console.WriteLine("STUDENT DETAILS : "); + Console.Write("Name :"); + string name = Console.ReadLine(); + sw.WriteLine("Name :" + name); + Console.Write("Department :"); + string Department = Console.ReadLine(); + sw.WriteLine("Department :" + Department); + Console.Write("College Name :"); + string CollegeName = Console.ReadLine(); + sw.WriteLine("College Name :" + CollegeName); + Console.WriteLine("Information Saved!"); + Console.WriteLine(); + sw.Flush(); + sw.Close(); + Console.ReadLine(); + } +} + +/* +STUDENT DETAILS : +Name : BOB +Department : IT +College Name : NIIT +Information Saved! \ No newline at end of file diff --git a/c-sharp/Files/C# Program to Implement BinaryReader.cs b/c-sharp/Files/C# Program to Implement BinaryReader.cs new file mode 100644 index 0000000..cb798cb --- /dev/null +++ b/c-sharp/Files/C# Program to Implement BinaryReader.cs @@ -0,0 +1,43 @@ +/* + * C# Program to Implement BinaryReader + */ +using System; +using System.IO; +class ConsoleApplication +{ + const string fileName = "program.dat"; + static void Main() + { + Write(); + Console.WriteLine("Using Binary Writer Class the Contents are Written "); + Display(); + } + public static void Write() + { + using (BinaryWriter writer = new BinaryWriter(File.Open(fileName, FileMode.Create))) + { + writer.Write(1.250F); + writer.Write(@"C:\Temp"); + } + } + public static void Display() + { + float aspectRatio; + string tempDirectory; + if (File.Exists(fileName)) + { + using (BinaryReader reader = new BinaryReader(File.Open(fileName, FileMode.Open))) + { + aspectRatio = reader.ReadSingle(); + tempDirectory = reader.ReadString(); + } + Console.WriteLine("Aspect Ratio Set to : " + aspectRatio); + Console.WriteLine("Temp Directory is : " + tempDirectory); + Console.Read(); + } + } +} +/* +Using Binary Writer Class the Contents are Written +Aspect Ratio set to : 1.25 +Temp Directory is : C:\Temp \ No newline at end of file diff --git a/c-sharp/Files/C# Program to List Disk Drives.cs b/c-sharp/Files/C# Program to List Disk Drives.cs new file mode 100644 index 0000000..04af43d --- /dev/null +++ b/c-sharp/Files/C# Program to List Disk Drives.cs @@ -0,0 +1,27 @@ +/* + * C# Program to List Disk Drives + */ +using System; +using System.IO; +class Test +{ + public static void Main() + { + DriveInfo[] driverslist = DriveInfo.GetDrives(); + foreach (DriveInfo d in driverslist) + { + Console.WriteLine("Drive {0}", d.Name); + Console.WriteLine(" File type: {0}", d.DriveType); + if (d.IsReady == true) + { + Console.WriteLine(" Total size of drive:{0, 15} bytes ",d.TotalSize); + Console.Read(); + } + } + } +} + +/* +Drive C:\ +File Type : Fixed +Total Size of Drive : 107268272128 \ No newline at end of file diff --git a/c-sharp/Files/C# Program to List the Files in a Directory.cs b/c-sharp/Files/C# Program to List the Files in a Directory.cs new file mode 100644 index 0000000..f994129 --- /dev/null +++ b/c-sharp/Files/C# Program to List the Files in a Directory.cs @@ -0,0 +1,25 @@ +/* + * C# Program to List the Files in a Directory + */ +using System; +using System.IO; +class Program +{ + static void Main() + { + string[] array1 = Directory.GetFiles(@"D:\"); + Console.WriteLine("Files in the Directory"); + foreach (string name in array1) + { + Console.WriteLine(name); + } + Console.Read(); + } +} + +/* +Files in the Directory +D:\demo1.cs +D:\demo1.exe +D:\msdia80.dll +D:\demo1.txt \ No newline at end of file diff --git a/c-sharp/Files/C# Program to Perform File Comparison.cs b/c-sharp/Files/C# Program to Perform File Comparison.cs new file mode 100644 index 0000000..45b5f50 --- /dev/null +++ b/c-sharp/Files/C# Program to Perform File Comparison.cs @@ -0,0 +1,66 @@ +/* + * C# Program to Perform File Comparison + */ +using System; +using System.Threading; +using System.IO; + +class Reader +{ + string fileName; + public string data; + + public Reader(string fn) + { + fileName = fn; + } + + public void Read() + { + FileStream s = new FileStream(fileName, FileMode.Open); + StreamReader r = new StreamReader(s); + data = r.ReadToEnd(); + r.Close(); + s.Close(); + } +} +class ThreadSample +{ + static void Main(string[] arg) + { + if (arg.Length == 2) + { + Reader a = new Reader(arg[0]); + Reader b = new Reader(arg[1]); + Thread ta = new Thread(new ThreadStart(a.Read)); + Thread tb = new Thread(new ThreadStart(b.Read)); + ta.Start(); + tb.Start(); + ta.Join(); + tb.Join(); + if (a.data.Length == b.data.Length) + { + int i = 0; + while (i < a.data.Length && a.data[i] == b.data[i]) i++; + if (i == a.data.Length) + Console.WriteLine("Files {0} and {1} are equal", arg[0], arg[1]); + else + Console.WriteLine("Files {0} and {1} are not equal", arg[0], arg[1]); + } + else + { + Console.WriteLine("Files {0} and {1} are not equal", arg[0], arg[1]); + } + } + else + { + Console.WriteLine("-- enter two file names"); + } + Console.ReadLine(); + } +} + +/* +D:\Desktop\c#\program codes>pgno382.exe d:\\sri\\File1.txt d:\\sri\\File1.txt +Files d:\\sri\\File1.txt and d:\\sri\\File1.txt +are equal \ No newline at end of file diff --git a/c-sharp/Files/C# Program to Perform Text Operations in a File.cs b/c-sharp/Files/C# Program to Perform Text Operations in a File.cs new file mode 100644 index 0000000..b5914d1 --- /dev/null +++ b/c-sharp/Files/C# Program to Perform Text Operations in a File.cs @@ -0,0 +1,29 @@ +/* + * C# Program to Perform Text Operations in a File + */ +using System; +using System.IO; +class Program +{ + static void Main() + { + FileInfo finfo = new FileInfo("C:\\sri\\srip.txt"); + using (StreamWriter writer = finfo.AppendText()) + { + writer.WriteLine("New File with various Text operations"); + } + finfo = new FileInfo("C:\\sri\\srip.txt"); + using (StreamWriter writer = finfo.CreateText()) + { + writer.WriteLine("New File with various Text operations"); + } + using (StreamReader reader = finfo.OpenText()) + { + Console.WriteLine(reader.ReadToEnd()); + } + Console.Read(); + } +} + +/* +New File with various Text operations \ No newline at end of file diff --git a/c-sharp/Files/C# Program to Read Data from Stream and Cast Data to Chars.cs b/c-sharp/Files/C# Program to Read Data from Stream and Cast Data to Chars.cs new file mode 100644 index 0000000..185025c --- /dev/null +++ b/c-sharp/Files/C# Program to Read Data from Stream and Cast Data to Chars.cs @@ -0,0 +1,23 @@ +/* + * C# Program to Read Data from Stream and Cast Data to Chars + */ +using System; +using System.IO; +public sealed class Program +{ + public static void Main() + { + using (Stream s = new FileStream(@"c:\sri\srip.txt", FileMode.Open)) + { + int read; + while ((read = s.ReadByte()) != -1) + { + Console.Write("{0} ", (char)read); + } + Console.ReadLine(); + } + } +} + +/* +G O O D M O R N I N G \ No newline at end of file diff --git a/c-sharp/Files/C# Program to Read Lines from a File until the End of File is Reached.cs b/c-sharp/Files/C# Program to Read Lines from a File until the End of File is Reached.cs new file mode 100644 index 0000000..9d94676 --- /dev/null +++ b/c-sharp/Files/C# Program to Read Lines from a File until the End of File is Reached.cs @@ -0,0 +1,44 @@ +/* + * C# Program to Read Lines from a File until the End of File is Reached + */ +using System; +using System.IO; +class Test +{ + public static void Main() + { + string path = @"c:\sri\srip.txt"; + try + { + if (File.Exists(path)) + { + File.Delete(path); + } + using (StreamWriter sw = new StreamWriter(path)) + { + sw.WriteLine("This"); + sw.WriteLine("text is"); + sw.WriteLine("to test"); + sw.WriteLine("Reading"); + } + using (StreamReader sr = new StreamReader(path)) + { + while (sr.Peek() >= 0) + { + Console.WriteLine(sr.ReadLine()); + } + } + } + catch (Exception e) + { + Console.WriteLine("The process failed: {0}", e.ToString()); + } + Console.Read(); + } +} + +/* +This +text is +to test +reading \ No newline at end of file diff --git a/c-sharp/Files/C# Program to Read the Contents of the File.cs b/c-sharp/Files/C# Program to Read the Contents of the File.cs new file mode 100644 index 0000000..0710c42 --- /dev/null +++ b/c-sharp/Files/C# Program to Read the Contents of the File.cs @@ -0,0 +1,31 @@ +/* + * C# Program to Read Contents of a File + */ +using System; +using System.IO; +class FileRead +{ + public void readdata() + { + FileStream fs = new FileStream("Myfile.txt", FileMode.Open, FileAccess.Read); + StreamReader sr = new StreamReader(fs);//Position the File Pointer at the Beginning of the File + sr.BaseStream.Seek(0, SeekOrigin.Begin);//Read till the End of the File is Encountered + string str = sr.ReadLine(); + while (str != null) + { + Console.WriteLine("{0}", str); + str = sr.ReadLine(); + } + //Close the Writer and File + sr.Close(); + fs.Close(); + } + public static void Main(String[] args) + { + FileRead fr = new FileRead(); + fr.readdata(); + } +} + +/* +The text which your are reading are read from the file named myfile.txt that is created already. \ No newline at end of file diff --git a/c-sharp/Files/C# Program to Search Directories and List Files.cs b/c-sharp/Files/C# Program to Search Directories and List Files.cs new file mode 100644 index 0000000..886e6fb --- /dev/null +++ b/c-sharp/Files/C# Program to Search Directories and List Files.cs @@ -0,0 +1,23 @@ +/* + * C# Program to Search Directories and List Files + */ +using System; +using System.IO; +class Program +{ + static void Main() + { + string[] Dirfile = Directory.GetFiles("C:\\sri\\","*.*",SearchOption.AllDirectories); + foreach (string file in Dirfile) + { + Console.WriteLine(file); + } + Console.Read(); + } +} + +/* +The List of Files in the Directory are : +C:\sri\message.txt +C:\sri\srip.txt +C:\sri\test.txt \ No newline at end of file diff --git a/c-sharp/Files/C# Program to Trap Events from File.cs b/c-sharp/Files/C# Program to Trap Events from File.cs new file mode 100644 index 0000000..047d0af --- /dev/null +++ b/c-sharp/Files/C# Program to Trap Events from File.cs @@ -0,0 +1,33 @@ +/* + * C# Program to Trap Events from File + */ +using System; +using System.IO; +class Test +{ + static void namechang(object sender, RenamedEventArgs evn) + { + Console.WriteLine("{0} NameChanged to {1}", evn.OldFullPath, evn.FullPath); + } + static void changed(object sender, FileSystemEventArgs evn) + { + Console.WriteLine(evn.FullPath + " " + evn.ChangeType); + } + static void Main(string[] arg) + { + FileSystemWatcher w = new FileSystemWatcher(); + w.Path = "d:\\srip"; + w.NotifyFilter = NotifyFilters.FileName | NotifyFilters.DirectoryName |NotifyFilters.LastAccess | NotifyFilters.LastWrite; + w.Filter = ""; + w.Created += new FileSystemEventHandler(changed); + w.Deleted += new FileSystemEventHandler(changed); + w.Changed += new FileSystemEventHandler(changed); + w.Renamed += new RenamedEventHandler(namechang); + w.EnableRaisingEvents = true; + Console.WriteLine("Press any key to quit"); + Console.Read(); + } +} + +/* +Press any key to quit \ No newline at end of file diff --git a/c-sharp/Files/C# Program to Use StreamReader to Read Entire Line.cs b/c-sharp/Files/C# Program to Use StreamReader to Read Entire Line.cs new file mode 100644 index 0000000..2c0fdc5 --- /dev/null +++ b/c-sharp/Files/C# Program to Use StreamReader to Read Entire Line.cs @@ -0,0 +1,26 @@ +/* + * C# Program to Use StreamReader to Read Entire Line + */ +using System; +using System.IO; +using System.IO.Compression; +using System.Text; +public sealed class Program +{ + public static void Main() + { + Stream s = new FileStream(@"c:\sri\srip.txt", FileMode.Open); + using (StreamReader sr = new StreamReader(s, Encoding.UTF8)) + { + string line; + while ((line = sr.ReadLine()) != null) + { + Console.WriteLine(line); + } + Console.ReadLine(); + } + } +} + +/* +StreamWriter writes text files. It enables easy and efficient text output. It is best placed in a using-statement to ensure it is removed from memory when no longer needed. It provides several constructors and many methods. \ No newline at end of file diff --git a/c-sharp/Files/C# Program to View the Date and time of Access of a File.cs b/c-sharp/Files/C# Program to View the Date and time of Access of a File.cs new file mode 100644 index 0000000..199ff7f --- /dev/null +++ b/c-sharp/Files/C# Program to View the Date and time of Access of a File.cs @@ -0,0 +1,23 @@ +/* + * C# Program to View the Date and time of Access of a File + */ +using System; +using System.IO; +class Program +{ + static void Main() + { + FileInfo info = new FileInfo("C:\\sri\\srip.txt"); + DateTime time = info.CreationTime; + Console.WriteLine("File Creation Time : {0}", time); + time = info.LastAccessTime; + Console.WriteLine("File Last Access Time : {0}", time); + time = info.LastWriteTime; + Console.WriteLine("File Last Write Time : {0} ", time); + Console.Read(); + } +} +/* +File Creation Time : 8/11/2013 7:17:20 PM +File Access Time : 8/15/2013 1:08:45 PM +File Last Write Time : 8/15/2013 1:37:36 PM \ No newline at end of file diff --git a/c-sharp/Files/C# Program to View the Information of the File.cs b/c-sharp/Files/C# Program to View the Information of the File.cs new file mode 100644 index 0000000..d7985a5 --- /dev/null +++ b/c-sharp/Files/C# Program to View the Information of the File.cs @@ -0,0 +1,18 @@ +/* + * C# Program to View the Information of the File + */ +using System; +using System.IO; +class Program +{ + static void Main() + { + FileInfo info = new FileInfo("C:\\sri\\srip.txt"); + FileAttributes attributes = info.Attributes; + Console.WriteLine("Nature(Attribute) of the File : {0}",attributes); + Console.Read(); + } +} + +/* +Nature(Attribute) of the File : Archive \ No newline at end of file diff --git a/c-sharp/Files/C# Sharp to append some text to an existing file.cs b/c-sharp/Files/C# Sharp to append some text to an existing file.cs new file mode 100644 index 0000000..aefba65 --- /dev/null +++ b/c-sharp/Files/C# Sharp to append some text to an existing file.cs @@ -0,0 +1,56 @@ +using System; +using System.IO; +using System.Text; + +class filexercise3 +{ + public static void Main() + { + string fileName = @"mytest.txt"; + try + { + // Delete the file if it exists. + if (File.Exists(fileName)) + { + File.Delete(fileName); + } + Console.Write("\n\n Append some text to an existing file :\n"); + Console.Write("--------------------------------------------\n"); + // Create the file. + using (StreamWriter fileStr = File.CreateText(fileName)) + { + fileStr.WriteLine(" Hello and Welcome"); + fileStr.WriteLine(" It is the first content"); + fileStr.WriteLine(" of the text file mytest.txt"); + } + using (StreamReader sr = File.OpenText(fileName)) + { + string s = ""; + Console.WriteLine(" Here is the content of the file mytest.txt : "); + while ((s = sr.ReadLine()) != null) + { + Console.WriteLine(s); + } + Console.WriteLine(""); + } + using (System.IO.StreamWriter file = new System.IO.StreamWriter(@"mytest.txt", true)) + { + file.WriteLine(" This is the line appended at last line."); + } + using (StreamReader sr = File.OpenText(fileName)) + { + string s = ""; + Console.WriteLine(" Here is the content of the file after appending the text : "); + while ((s = sr.ReadLine()) != null) + { + Console.WriteLine(s); + } + Console.WriteLine(""); + } + } + catch (Exception MyExcep) + { + Console.WriteLine(MyExcep.ToString()); + } + } +} \ No newline at end of file diff --git a/c-sharp/Files/C# Sharp to count the number of lines in a file.cs b/c-sharp/Files/C# Sharp to count the number of lines in a file.cs new file mode 100644 index 0000000..092a331 --- /dev/null +++ b/c-sharp/Files/C# Sharp to count the number of lines in a file.cs @@ -0,0 +1,49 @@ +using System; +using System.IO; +using System.Text; + +class filexercise3 +{ + public static void Main() + { + string fileName = @"mytest.txt"; + int count; + try + { + // Delete the file if it exists. + if (File.Exists(fileName)) + { + File.Delete(fileName); + } + Console.Write("\n\n Count the number of lines in a file :\n"); + Console.Write("------------------------------------------\n"); + // Create the file. + using (StreamWriter fileStr = File.CreateText(fileName)) + { + fileStr.WriteLine(" test line 1"); + fileStr.WriteLine(" test line 2"); + fileStr.WriteLine(" Test line 3"); + fileStr.WriteLine(" test line 4"); + fileStr.WriteLine(" test line 5"); + fileStr.WriteLine(" Test line 6"); + } + using (StreamReader sr = File.OpenText(fileName)) + { + string s = ""; + count=0; + Console.WriteLine(" Here is the content of the file mytest.txt : "); + while ((s = sr.ReadLine()) != null) + { + Console.WriteLine(s); + count++; + } + Console.WriteLine(""); + } + Console.Write(" The number of lines in the file {0} is : {1} \n\n",fileName,count); + } + catch (Exception MyExcep) + { + Console.WriteLine(MyExcep.ToString()); + } + } +} \ No newline at end of file diff --git a/c-sharp/Files/C# Sharp to create a file and move the file into the same directory to another name.cs b/c-sharp/Files/C# Sharp to create a file and move the file into the same directory to another name.cs new file mode 100644 index 0000000..5e8f82c --- /dev/null +++ b/c-sharp/Files/C# Sharp to create a file and move the file into the same directory to another name.cs @@ -0,0 +1,57 @@ +using System; +using System.IO; +using System.Text; + + +public class SimpleFileMove +{ + static void Main() + { + string sfileName = @"mytest.txt"; + string tfileName = @"mynewtest.txt"; + /* string sourcefolder = "path"; // you can mention the path of source folder + string targetfolder = "path"; // you can mention the path of target folder + string sourceFile = System.IO.Path.Combine(sourcefolder, sfileName); // combine the source file with path + string targetFile = System.IO.Path.Combine(targetfolder, tfileName); // combine the target file with path */ + if (File.Exists(sfileName)) + { + File.Delete(sfileName); + } + if (File.Exists(tfileName)) + { + File.Delete(tfileName); + } + Console.Write("\n\n Create a file and move the file in same folder to another name :\n"); + Console.Write("----------------------------------------------------------------------\n"); + // Create the file. + using (StreamWriter fileStr = File.CreateText(sfileName)) + { + fileStr.WriteLine(" Hello and Welcome"); + fileStr.WriteLine(" It is the first content"); + fileStr.WriteLine(" of the text file mytest.txt"); + } + using (StreamReader sr = File.OpenText(sfileName)) + { + string s = ""; + Console.WriteLine(" Here is the content of the file {0} : ",sfileName); + while ((s = sr.ReadLine()) != null) + { + Console.WriteLine(s); + } + Console.WriteLine(""); + } + System.IO.File.Move(sfileName, tfileName); // move a file to another name in same location: + Console.WriteLine(" The file {0} successfully moved to the name {1} in the same directory.",sfileName,tfileName ); + using (StreamReader sr = File.OpenText(tfileName)) + { + string s = ""; + Console.WriteLine(" Here is the content of the file {0} : ",tfileName); + while ((s = sr.ReadLine()) != null) + { + Console.WriteLine(s); + } + Console.WriteLine(""); + } + Console.ReadKey(); + } +} \ No newline at end of file diff --git a/c-sharp/Files/C# Sharp to create a file and write an array of strings to the file.cs b/c-sharp/Files/C# Sharp to create a file and write an array of strings to the file.cs new file mode 100644 index 0000000..2834ae5 --- /dev/null +++ b/c-sharp/Files/C# Sharp to create a file and write an array of strings to the file.cs @@ -0,0 +1,40 @@ +using System; +using System.IO; + + +class WriteTextFile +{ + static void Main() + { + string fileName = @"mytest.txt"; + string[] ArrLines ; + int n,i; + Console.Write("\n\n Create a file and write an array of strings :\n"); + Console.Write("---------------------------------------------------\n"); + if (File.Exists(fileName)) + { + File.Delete(fileName); + } + Console.Write(" Input number of lines to write in the file :"); + n= Convert.ToInt32(Console.ReadLine()); + ArrLines=new string[n]; + Console.Write(" Input {0} strings below :\n",n); + for(i=0; i=1 && l<=n) + { + Console.Write("\n The content of the last {0} lines of the file {1} is : \n",l,fileName); + if (File.Exists(fileName)) + { + for(i=n-l; i=1 && l<=n) + { + Console.Write("\n The content of the line {0} of the file {1} is : \n",l,fileName); + if (File.Exists(fileName)) + { + string[] lines = File.ReadAllLines(fileName); + Console.WriteLine(" {0}",lines[l-1]); + } + } + else + { + Console.WriteLine(" Please input the correct line no."); + } + Console.WriteLine(); + } +} \ No newline at end of file diff --git a/c-sharp/Files/C# Sharp to read the first line from a file.cs b/c-sharp/Files/C# Sharp to read the first line from a file.cs new file mode 100644 index 0000000..9c5bc40 --- /dev/null +++ b/c-sharp/Files/C# Sharp to read the first line from a file.cs @@ -0,0 +1,49 @@ +using System; +using System.IO; +using System.Text; + +class filexercise11 +{ + public static void Main() + { + string fileName = @"mytest.txt"; + try + { + // Delete the file if it exists. + if (File.Exists(fileName)) + { + File.Delete(fileName); + } + Console.Write("\n\n Read the first line from a file :\n"); + Console.Write("---------------------------------------\n"); + // Create the file. + using (StreamWriter fileStr = File.CreateText(fileName)) + { + fileStr.WriteLine(" test line 1"); + fileStr.WriteLine(" test line 2"); + fileStr.WriteLine(" Test line 3"); + } + using (StreamReader sr = File.OpenText(fileName)) + { + string s = ""; + Console.WriteLine(" Here is the content of the file mytest.txt : "); + while ((s = sr.ReadLine()) != null) + { + Console.WriteLine(s); + } + Console.WriteLine(""); + } + Console.Write("\n The content of the first line of the file is :\n"); + if (File.Exists(fileName)) + { + string[] lines = File.ReadAllLines(fileName); + Console.Write(lines[0]); + } + Console.WriteLine(); + } + catch (Exception MyExcep) + { + Console.WriteLine(MyExcep.ToString()); + } + } +} \ No newline at end of file diff --git a/c-sharp/Functions/C# Program Illustrate Method Hiding.cs b/c-sharp/Functions/C# Program Illustrate Method Hiding.cs new file mode 100644 index 0000000..a71d151 --- /dev/null +++ b/c-sharp/Functions/C# Program Illustrate Method Hiding.cs @@ -0,0 +1,45 @@ +/* + * C# Program Illustrate Method Hiding + */ +using System; +using System.Collections.Generic; +using System.Text; +namespace ConsoleApplication1 +{ +public class Demo +{ + public virtual double Area(double r) + { + return r * r; + } + public void func() + { + Console.WriteLine("Base Class"); + } +} +public class A : Demo +{ + public override double Area(double r) + { + return base.Area(r) * r; + } + public new void func() + { + Console.WriteLine("Derived Class"); + } +} +public class Test +{ + public static void Main(string[] args) + { + A o1 = new A(); + Console.WriteLine(o1.Area(20)); + o1.func(); + Console.ReadLine(); + } +} +} + +/* +8000 +Derived Class \ No newline at end of file diff --git a/c-sharp/Functions/C# Program to Create Anonymous Method.cs b/c-sharp/Functions/C# Program to Create Anonymous Method.cs new file mode 100644 index 0000000..34f7e8b --- /dev/null +++ b/c-sharp/Functions/C# Program to Create Anonymous Method.cs @@ -0,0 +1,29 @@ +/* + * C# Program to Create Anonymous Method + */ +using System; +delegate void Print(string s); +class TestClass +{ + static void Main() + { + Print obj = delegate(string j) + { + System.Console.WriteLine(j); + }; + obj("Delegate Using the Anonymous Method"); + obj = new Print(TestClass.named); + obj("Delegate Using the Named Method"); + Console.Read(); + } + static void named(string k) + { + System.Console.WriteLine(k); + } + +} + +/* + +Delegate Using the Anonymous Method +Delegate Using the Named Method \ No newline at end of file diff --git a/c-sharp/Functions/C# Program to Create Obsolete Class.cs b/c-sharp/Functions/C# Program to Create Obsolete Class.cs new file mode 100644 index 0000000..f23e315 --- /dev/null +++ b/c-sharp/Functions/C# Program to Create Obsolete Class.cs @@ -0,0 +1,24 @@ +/* + * C# Program to Create Obsolete Class + */ +using System; +class Program +{ + static void Main() + { + MethodA(); + MethodB(); + Console.Read(); + } + [Obsolete("Use MethodB Instead")] + static void MethodA() + { + } + static void MethodB() + { + Console.WriteLine(" MethodA shows an Warning when called and MethodB is not an Obsolete Method "); + } +} + +/* +MethodA shows an Warning when called and MethodB is not an Obsolete Method \ No newline at end of file diff --git a/c-sharp/Functions/C# Program to Demonstrate Abstract Properties.cs b/c-sharp/Functions/C# Program to Demonstrate Abstract Properties.cs new file mode 100644 index 0000000..1852440 --- /dev/null +++ b/c-sharp/Functions/C# Program to Demonstrate Abstract Properties.cs @@ -0,0 +1,121 @@ +/* + * CC# Program to Demonstrate Abstract Properties + */ +using System; + +public abstract class Shape +{ + private string myId; + + public Shape(string s) + { + Id = s; + } + + public string Id + { + get + { + return myId; + } + + set + { + myId = value; + } + } + public abstract double Area + { + get; + } + + public override string ToString() + { + return Id + " Area = " + string.Format("{0:F2}", Area); + } +} +public class Square : Shape +{ + private int mySide; + + public Square(int side, string id) + : base(id) + { + mySide = side; + } + + public override double Area + { + get + { + // Given the side, return the area of a square: + return mySide * mySide; + } + } +} + +public class Circle : Shape +{ + private int myRadius; + + public Circle(int radius, string id) + : base(id) + { + myRadius = radius; + } + + public override double Area + { + get + { + // Given the radius, return the area of a circle: + return myRadius * myRadius * System.Math.PI; + } + } +} + +public class Rectangle : Shape +{ + private int myWidth; + private int myHeight; + + public Rectangle(int width, int height, string id) + : base(id) + { + myWidth = width; + myHeight = height; + } + + public override double Area + { + get + { + // Given the width and height, return the area of a rectangle: + return myWidth * myHeight; + } + } +} +public class TestClass +{ + public static void Main() + { + Shape[] shapes = + { + new Square(5, "Square #1"), + new Circle(3, "Circle #1"), + new Rectangle( 4, 5, "Rectangle #1") + }; + System.Console.WriteLine("Shapes Collection"); + foreach (Shape s in shapes) + { + System.Console.WriteLine(s); + } + Console.ReadLine(); + } +} + +/* +Shapes Collection +Square #1 Area = 25.00 +Circle #1 Area = 28.27 +Rectangle #1 Area = 20.00 \ No newline at end of file diff --git a/c-sharp/Functions/C# Program to Demonstrate Boxing Operations.cs b/c-sharp/Functions/C# Program to Demonstrate Boxing Operations.cs new file mode 100644 index 0000000..85d7f04 --- /dev/null +++ b/c-sharp/Functions/C# Program to Demonstrate Boxing Operations.cs @@ -0,0 +1,39 @@ +/* + * C# Program to Demonstrate Boxing Operations + */ +using System; +class sample +{ + int x = 10; + object obj; + void boxmethod() + { + sample s= new sample(); + bool b; + object ob="CSHARP"; + b=s.obj is int; + Console.WriteLine(b); + s.obj = x; + b = s.obj is int; + Console.WriteLine("{0},{1},{2}",s.obj,s.x,b); + s.x = (int)s.obj; + s.x = 20; + b = s.obj is int; + Console.WriteLine("{0},{1},{2}", s.obj, s.x, b); + s.obj="CSHARP"; + b=s.obj is int; + Console.WriteLine("{0},{1},{2}",s.obj,s.x,b); + Console.ReadLine(); + } + public static void Main() + { + sample s=new sample(); + s.boxmethod(); + } +} + +/* +False +10,10,True +10,20,True +CSHARP,20,False \ No newline at end of file diff --git a/c-sharp/Functions/C# Program to Demonstrate Culture Names.cs b/c-sharp/Functions/C# Program to Demonstrate Culture Names.cs new file mode 100644 index 0000000..851f4f0 --- /dev/null +++ b/c-sharp/Functions/C# Program to Demonstrate Culture Names.cs @@ -0,0 +1,32 @@ +/* + * C# Program to Demonstrate Culture Names + */ +using System; +using System.Globalization; +using System.Threading; +public class Info : MarshalByRefObject +{ + public void ShowCurrentCulture() + { + Console.WriteLine("Culture of {0} in application domain {1}: {2}",Thread.CurrentThread.Name,AppDomain.CurrentDomain.FriendlyName,CultureInfo.CurrentCulture.Name); + } +} +public class Example +{ + public static void Main() + { + Info inf = new Info(); + Thread.CurrentThread.Name = "MainThread"; + Thread.CurrentThread.CurrentCulture = CultureInfo.CreateSpecificCulture("nl-NL"); + inf.ShowCurrentCulture(); + AppDomain ad = AppDomain.CreateDomain("Domain2"); + Info inf2 = (Info)ad.CreateInstanceAndUnwrap(typeof(Info).Assembly.FullName, "Info"); + inf2.ShowCurrentCulture(); + Console.ReadLine(); + } +} + +/* + +Culture of MainThread in application domain ConsoleApplication32.vshoot.exe : nl-NL +Culture of MainThread in application domain Domain2 : nl-NL \ No newline at end of file diff --git a/c-sharp/Functions/C# Program to Demonstrate Environment Type.cs b/c-sharp/Functions/C# Program to Demonstrate Environment Type.cs new file mode 100644 index 0000000..4b7fedc --- /dev/null +++ b/c-sharp/Functions/C# Program to Demonstrate Environment Type.cs @@ -0,0 +1,23 @@ +/* + * C# Program to Demonstrate Environment Type +using System; +class Program +{ + static void Main() + { + try + { + Environment.Exit(0); + } + finally + { + Console.WriteLine("Statement that is Never Reached"); + } + Console.Read(); + } +} + +/* +// No Output is obtained +// Calls the Environment.Exit method and returns a zero status code. +// The finally statement is never reached. \ No newline at end of file diff --git a/c-sharp/Functions/C# Program to Demonstrate New Modifier.cs b/c-sharp/Functions/C# Program to Demonstrate New Modifier.cs new file mode 100644 index 0000000..362b1e9 --- /dev/null +++ b/c-sharp/Functions/C# Program to Demonstrate New Modifier.cs @@ -0,0 +1,39 @@ +/* + * C# Program to Demonstrate New modifier + */ +using System; + +class TEST +{ + public void func() + { + Console.WriteLine("TEST.func"); + } +} + +class TEST1 : TEST +{ + public new void func() + { + Console.WriteLine("TEST1.func"); + } +} + +class Program +{ + static void Main() + { + TEST ref1 = new TEST(); + TEST ref2 = new TEST1(); + TEST1 ref3 = new TEST1(); + ref1.func(); + ref2.func(); + ref3.func(); + Console.Read(); + } +} + +/* +TEST.func +TEST.func +TEST1.func \ No newline at end of file diff --git a/c-sharp/Functions/C# Program to Demonstrate Pass by Reference Parameter.cs b/c-sharp/Functions/C# Program to Demonstrate Pass by Reference Parameter.cs new file mode 100644 index 0000000..e84b16d --- /dev/null +++ b/c-sharp/Functions/C# Program to Demonstrate Pass by Reference Parameter.cs @@ -0,0 +1,23 @@ +/* + * C# Program to Demonstrate Pass by Reference Parameter + */ +using System; +class Program +{ + static void Main(string[] args) + { + int val; + val = 4; + Console.WriteLine("Value Before : {0}", val); + square(ref val); + Console.WriteLine("Value After : {0}", val); + Console.Read(); + } + static void square(ref int refParam) + { + refParam *= refParam; + } +} +/* +Value Before : 4 +Value After : 16 \ No newline at end of file diff --git a/c-sharp/Functions/C# Program to Demonstrate Pass by Value Parameter.cs b/c-sharp/Functions/C# Program to Demonstrate Pass by Value Parameter.cs new file mode 100644 index 0000000..81314a6 --- /dev/null +++ b/c-sharp/Functions/C# Program to Demonstrate Pass by Value Parameter.cs @@ -0,0 +1,25 @@ +/* + * C# Program to Demonstrate Pass by Value Parameter + */ +using System; +class program +{ + static void Cube(int x) + { + x = x * x * x; + Console.WriteLine("Value Within the Cube method : {0}", x); + } + static void Main() + { + int num = 5; + Console.WriteLine("Value Before the Method is called : {0}", num); + Cube(num); + Console.WriteLine("Value After the Method is called : {0}", num); + Console.ReadKey(); + } +} + +/* +Value Before the Method is called : 5 +Value Within the Cube method : 125 +Value After the Method is called : 5 \ No newline at end of file diff --git a/c-sharp/Functions/C# Program to Demonstrate Properties of the Class.cs b/c-sharp/Functions/C# Program to Demonstrate Properties of the Class.cs new file mode 100644 index 0000000..29caf36 --- /dev/null +++ b/c-sharp/Functions/C# Program to Demonstrate Properties of the Class.cs @@ -0,0 +1,54 @@ +/* + * C# Program to Demonstrate Properties of the Class + */ +using System; +class Student +{ + private string myName = "N/A"; + private int myAge = 0; + public string Name + { + get + { + return myName; + } + set + { + myName = value; + } + } + public int Age + { + get + { + return myAge; + } + set + { + myAge = value; + } + } + + public override string ToString() + { + return "Name = " + Name + ", Age = " + Age; + } + + public static void Main() + { + Student Student = new Student(); + Console.WriteLine("Student details - {0}", Student); + Student.Name = "BOB"; + Student.Age = 99; + Console.WriteLine("Student details - {0}", Student); + Student.Age += 1; + Console.WriteLine("Student details - {0}", Student); + Console.ReadLine(); + } +} + +/* + +Student details - Name = N/A, Age = 0 +Student details - Name = BOB, Age = 99 +Student details - Name = BOB, Age = 100 \ No newline at end of file diff --git a/c-sharp/Functions/C# Program to Demonstrate iscollection.cs b/c-sharp/Functions/C# Program to Demonstrate iscollection.cs new file mode 100644 index 0000000..d07f111 --- /dev/null +++ b/c-sharp/Functions/C# Program to Demonstrate iscollection.cs @@ -0,0 +1,26 @@ +/* + * C# Program to Demonstrate iscollection.synchronised + */ +using System; +using System.Collections; + +public class CountArray +{ + public static void Main() + { + string[] strings = { "Ajax", "Atlas" }; + DisplayCollectionProperty(strings); + Console.ReadLine(); + } + + public static void DisplayCollectionProperty + (ICollection iCollection) + { + Console.WriteLine("IsSynchronized: {0}", + iCollection.IsSynchronized); + } +} + +/* + +IsSynchronized: False \ No newline at end of file diff --git a/c-sharp/Functions/C# Program to Demonstrate the Operations of C# Path Class.cs b/c-sharp/Functions/C# Program to Demonstrate the Operations of C# Path Class.cs new file mode 100644 index 0000000..11f223c --- /dev/null +++ b/c-sharp/Functions/C# Program to Demonstrate the Operations of C# Path Class.cs @@ -0,0 +1,38 @@ +/* + * C# Program to Demonstrate the Operations of C# Path Class + */ +using System; +using System.IO; +class Test +{ + public static void Main() + { + string p = @"c:\srip\sri.txt"; + string p2 = @"c:\srip\sri"; + string p3 = @"srip"; + if (Path.HasExtension(p)) + { + Console.WriteLine("{0} has an extension.", p); + } + if (!Path.HasExtension(p2)) + { + Console.WriteLine("{0} has no extension.", p2); + } + if (!Path.IsPathRooted(p3)) + { + Console.WriteLine("The string {0} contains no root information.", p3); + } + Console.WriteLine("Location for Temporary Files : {0}", Path.GetTempPath()); + Console.WriteLine("Full path of {0} is {1}.", p3, Path.GetFullPath(p3)); + Console.WriteLine("File available for Use : {0} ", Path.GetTempFileName()); + Console.Read(); + } +} + +/* +c:\srip\sri.txt has an extension. +c:\srip\sri has no extension. +The string srip contains no root information. +Location For Temporary Files : C:\Users\Win7\appdata\local\temp\ +Full Path of Temp : D:\sri\ConsoleApplication22\ConsoleApplication22\bin\Debug\srip. +File Available for Use : C:\Users\Win7\appdata\local\temp\trmpEB1B.tmp \ No newline at end of file diff --git a/c-sharp/Functions/C# Program to Demonstrate the Working #define Preprocessor.cs b/c-sharp/Functions/C# Program to Demonstrate the Working #define Preprocessor.cs new file mode 100644 index 0000000..012c303 --- /dev/null +++ b/c-sharp/Functions/C# Program to Demonstrate the Working #define Preprocessor.cs @@ -0,0 +1,22 @@ +/* + * C# Program to Demonstrate the Working #define Preprocessor + */ +#define B +#define A +#undef A +using System; +class Program +{ + static void Main() + { +#if A + Console.WriteLine("'A' is Displayed Based on the undef Directive "); +#elif B + Console.WriteLine("'B' is Displayed Based on the undef Directive"); +#endif + Console.ReadLine(); + } +} + +/* +'B' is Displayed Based on the undef Directive \ No newline at end of file diff --git a/c-sharp/Functions/C# Program to Demonstrate the icollection Count.cs b/c-sharp/Functions/C# Program to Demonstrate the icollection Count.cs new file mode 100644 index 0000000..26c2c90 --- /dev/null +++ b/c-sharp/Functions/C# Program to Demonstrate the icollection Count.cs @@ -0,0 +1,24 @@ +/* + * C# Program to Demonstrate the icollection Count + */ +using System; +using System.Collections; + +public class CountArray +{ + public static void Main() + { + string[] strings = { "Ajax", "Atlas","a","b"}; + DisplayCollectionProperty(strings); + Console.ReadLine(); + } + + public static void DisplayCollectionProperty + (ICollection iCollection) + { + Console.WriteLine("Count = {0}", iCollection.Count); + } +} + +/* +Count=4 \ No newline at end of file diff --git a/c-sharp/Functions/C# Program to Find Sum of Digits of a Number using Recursion.cs b/c-sharp/Functions/C# Program to Find Sum of Digits of a Number using Recursion.cs new file mode 100644 index 0000000..bed6cec --- /dev/null +++ b/c-sharp/Functions/C# Program to Find Sum of Digits of a Number using Recursion.cs @@ -0,0 +1,36 @@ +/* + * C# Program to Find Sum of Digits of a Number using Recursion + */ +using System; +class program +{ + public static void Main() + { + int num, result; + pro pg = new pro(); + Console.WriteLine("Enter the Number : "); + num=int.Parse(Console.ReadLine()); + result =pg.sum(num); + Console.WriteLine("Sum of Digits in {0} is {1}", num, result); + Console.ReadLine(); + } +} +class pro +{ + public int sum(int num) + { + if (num != 0) + { + return (num % 10 + sum(num / 10)); + } + else + { + return 0; + } + } +} + +/* +Enter the Number : +234 +Sum of Digits in 234 is 9 \ No newline at end of file diff --git a/c-sharp/Functions/C# Program to Illustrate Regular Expression Pattern.cs b/c-sharp/Functions/C# Program to Illustrate Regular Expression Pattern.cs new file mode 100644 index 0000000..d19c45c --- /dev/null +++ b/c-sharp/Functions/C# Program to Illustrate Regular Expression Pattern.cs @@ -0,0 +1,33 @@ +/* + * C# Program to Illustrate Regular Expression Pattern + */ +using System; +using System.Text.RegularExpressions; +namespace Application +{ +class Program +{ + private static void showMatch(string text, string expr) + { + Console.WriteLine("The Expression : " + expr); + MatchCollection m = Regex.Matches(text, expr); + foreach (Match m1 in m) + { + Console.WriteLine(m1); + } + } + static void Main(string[] args) + { + string str = "Sanfoundry , a high end Technology Training company"; + Console.WriteLine("Matching words that start with 'S': "); + showMatch(str, @"\bS\S*"); + Console.ReadKey(); + } +} +} + +/* + +Matching Words that Starts With 'S' : +The Expression : \bs\s* +Sanfoundry \ No newline at end of file diff --git a/c-sharp/Functions/C# Program to Illustrate the Concept of Goto.cs b/c-sharp/Functions/C# Program to Illustrate the Concept of Goto.cs new file mode 100644 index 0000000..b5a2219 --- /dev/null +++ b/c-sharp/Functions/C# Program to Illustrate the Concept of Goto.cs @@ -0,0 +1,44 @@ +/* + * C# Program to Illustrate the Concept of Goto + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +namespace Example +{ +class Program +{ + static void Main(string[] args) + { + int no, per, option; + float ans; +loop: + Console.Write("Enter a Number :\t"); + no = Convert.ToInt32(Console.ReadLine()); + Console.Write("\nEnter Percentage Value : \t"); + per = Convert.ToInt32(Console.ReadLine()); + ans = (float)(no * per) / 100; + Console.WriteLine("Percentage Value is:\t{0}", ans); + Console.Write("\nCalculate again press 1. To quit press digit:\t"); + option = Convert.ToInt32(Console.ReadLine()); + if (option == 1) + { + goto loop; + } + Console.WriteLine("Press Enter for quit"); + Console.ReadLine(); + } +} +} + +/* +Enter a number : 320 +Enter Percentage Value : 10 +Percentage value is : 32 +Calculate again press 1. To quit Press digit: 1 +Enter a number : 730 +Enter Percentage Value: 10 +Percentage value is: 73 +Calculate again press 1. To quit press digit: 6 +Press Enter for quit \ No newline at end of file diff --git a/c-sharp/Functions/C# Program to Illustrate the use of Conditional Logical Operator.cs b/c-sharp/Functions/C# Program to Illustrate the use of Conditional Logical Operator.cs new file mode 100644 index 0000000..81aaecc --- /dev/null +++ b/c-sharp/Functions/C# Program to Illustrate the use of Conditional Logical Operator.cs @@ -0,0 +1,20 @@ +/* + * C# Program to Illustrate the use of Conditional Logical Operator + */ +using System; +public class Program +{ + static void Main() + { + int age; + Console.WriteLine("Enter the Age :"); + age=int.Parse(Console.ReadLine()); + bool adult = age >= 18 ? true : false; + Console.WriteLine("Adult : {0}", adult); + Console.Read(); + } +} + +/* +Enter the Age : 10 +Adult : false \ No newline at end of file diff --git a/c-sharp/Functions/C# Program to Ilustrate Nullable Data Types.cs b/c-sharp/Functions/C# Program to Ilustrate Nullable Data Types.cs new file mode 100644 index 0000000..5e1513c --- /dev/null +++ b/c-sharp/Functions/C# Program to Ilustrate Nullable Data Types.cs @@ -0,0 +1,26 @@ +/* + * C# Program to Ilustrate Nullable Data Types + */ +using System; +namespace Application +{ +class Nullables +{ + static void Main(string[] args) + { + int? num1 = null; + int? num2 = 100; + double? num3 = new double?(); + double? num4 = 3.14157; + bool? boolval = new bool?(); + Console.WriteLine("Nullables : {0}, {1}, {2}, {3}", + num1, num2, num3, num4); + Console.WriteLine("A Nullable boolean value: {0}", boolval); + Console.ReadLine(); + } +} +} + +/* +Nullables : ,100,,3.1457 +A Nullable Boolean Value : \ No newline at end of file diff --git a/c-sharp/Functions/C# Program to Implement Namespaces.cs b/c-sharp/Functions/C# Program to Implement Namespaces.cs new file mode 100644 index 0000000..fea0a00 --- /dev/null +++ b/c-sharp/Functions/C# Program to Implement Namespaces.cs @@ -0,0 +1,25 @@ +/* + * C# Program to Implement Namespaces + */ +using System; +namespace Sanfoundry.Csharp.Codes +{ +class TestClass +{ + public TestClass() + { + Console.WriteLine("Class to Demonstrate Namespace"); + } +} +} +class MyClient +{ + public static void Main() + { + Sanfoundry.Csharp.Codes.TestClass mc = new Sanfoundry.Csharp.Codes.TestClass(); + Console.ReadLine(); + } +} + +/* +Class to Demonstrate Namespace \ No newline at end of file diff --git a/c-sharp/Functions/C# Program to Implement Static Method.cs b/c-sharp/Functions/C# Program to Implement Static Method.cs new file mode 100644 index 0000000..04ab85c --- /dev/null +++ b/c-sharp/Functions/C# Program to Implement Static Method.cs @@ -0,0 +1,35 @@ +/* + * C# Program to Implement Static Method + */ +using System; +class Program +{ + static void stamethod() + { + Console.WriteLine("Static Method"); + } + void MethodB() + { + Console.WriteLine("Instance Method"); + } + static char stamethod2() + { + Console.WriteLine("Static Method"); + return 'C'; + } + static void Main() + { + Program.stamethod(); + Console.WriteLine(Program.stamethod2()); + Program programInstance = new Program(); + programInstance.MethodB(); + Console.Read(); + } +} + +/* + +Static Method +Static Method +C +Instance Method \ No newline at end of file diff --git a/c-sharp/Functions/C# Program to Print Binary Equivalent of an Integer using Recursion.cs b/c-sharp/Functions/C# Program to Print Binary Equivalent of an Integer using Recursion.cs new file mode 100644 index 0000000..3c701c6 --- /dev/null +++ b/c-sharp/Functions/C# Program to Print Binary Equivalent of an Integer using Recursion.cs @@ -0,0 +1,44 @@ +/* + * C# Program to Print Binary Equivalent of an Integer using Recursion + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +class Program +{ + public static void Main(string[] args) + { + int num; + prog pg = new prog(); + Console.WriteLine("Enter a decimal number: "); + num = int.Parse(Console.ReadLine()); + Console.WriteLine("The binary equivalent of num is :"); + pg.binaryconversion(num); + Console.ReadLine(); + } +} +public class prog +{ + public int binaryconversion(int num) + { + int bin; + if (num != 0) + { + bin = (num % 2) + 10 * binaryconversion(num / 2); + Console.Write(bin); + return 0; + } + else + { + return 0; + } + } +} + +/* + +Enter a decimal number: +19 +The binary equivalent of num is : +10011 \ No newline at end of file diff --git a/c-sharp/Functions/C# Program to Print Hello World Without using WriteLine.cs b/c-sharp/Functions/C# Program to Print Hello World Without using WriteLine.cs new file mode 100644 index 0000000..24d382b --- /dev/null +++ b/c-sharp/Functions/C# Program to Print Hello World Without using WriteLine.cs @@ -0,0 +1,20 @@ +/* + * C# Program to Print Hello World Without using WriteLine + */ +using System; +class Program +{ + static void Main(string[] args) + { + if (System.Console.OpenStandardOutput().BeginWrite(new byte[] { 072, 101, 108, 108, 111, 032, 087, 111, 114, 108, 100, 0 },0, 12, null, null).AsyncWaitHandle.WaitOne()) + { + } + if (System.Console.ReadKey().Modifiers == 0) + { + } + } +} + +/* + +Hello World \ No newline at end of file diff --git a/c-sharp/Functions/C# Program to Produce a filtered sequence of elements that contain only one property of each Student.cs b/c-sharp/Functions/C# Program to Produce a filtered sequence of elements that contain only one property of each Student.cs new file mode 100644 index 0000000..579a42c --- /dev/null +++ b/c-sharp/Functions/C# Program to Produce a filtered sequence of elements that contain only one property of each Student.cs @@ -0,0 +1,97 @@ +/* + * C# Program to Produce a filtered sequence of elements that contain only one property of each Student + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +using System.Threading.Tasks; +class Programs +{ + public class Student + { + public string First { get; set; } + public string Last { get; set; } + public int ID { get; set; } + public List Marks; + public ContactInfo GetContactInfo(Programs pg, int id) + { + ContactInfo allinfo = + (from ci in pg.contactList + where ci.ID == id + select ci) + .FirstOrDefault(); + return allinfo; + } + + public override string ToString() + { + return First + "" + Last + " : " + ID; + } + } + + public class ContactInfo + { + public int ID { get; set; } + public string Email { get; set; } + public string Phone { get; set; } + public override string ToString() + { + return Email + "," + Phone; + } + } + + public class ScoreInfo + { + public double Average { get; set; } + public int ID { get; set; } + } + List students = new List() + { + new Student {First="Tom", Last=".S", ID=1, Marks= new List() + { + 97, 92, 81, 60 + }}, + new Student {First="Jerry", Last=".M", ID=2, Marks= new List() + { + 75, 84, 91, 39 + }}, + new Student {First="Bob", Last=".P", ID=3, Marks= new List() + { + 88, 94, 65, 91 + }}, + new Student {First="Mark", Last=".G", ID=4, Marks= new List() + { + 97, 89, 85, 82 + }}, + }; + List contactList = new List() + { + new ContactInfo {ID=111, Email="Tom@abc.com", Phone="9328298765"}, + new ContactInfo {ID=112, Email="Jerry123@aaa.com", Phone="9876543201"}, + new ContactInfo {ID=113, Email="Bobstar@aaa.com", Phone="9087467653"}, + new ContactInfo {ID=114, Email="Markantony@qqq.com", Phone="9870098761"} + }; + + + static void Main(string[] args) + { + Programs pg = new Programs(); + IEnumerable studentQuery2 = + from student in pg.students + where student.ID > 1 + select student.Last; + Console.WriteLine("\r\n studentQuery2: select range_variable.Property"); + foreach (string s in studentQuery2) + { + Console.WriteLine(s); + } + Console.ReadLine(); + } +} + +/* + studentQuery2: select range_variable.Property +.M +.P +.G \ No newline at end of file diff --git a/c-sharp/Functions/C# Program to Reverse a String with Predefined Function.cs b/c-sharp/Functions/C# Program to Reverse a String with Predefined Function.cs new file mode 100644 index 0000000..d0bb43a --- /dev/null +++ b/c-sharp/Functions/C# Program to Reverse a String with Predefined Function.cs @@ -0,0 +1,41 @@ +/* + * C# Program to Reverse a String with Predefined Function + */ +using System; +class linSearch +{ + public static void Main() + { + Console.WriteLine("Enter Number of Elements you Want to Hold in the Array ? "); + string s = Console.ReadLine(); + int x = Int32.Parse(s); + int[] a = new int[x]; + Console.WriteLine("\n Enter Array Elements : "); + for (int i = 0; i < x; i++) + { + string s1 = Console.ReadLine(); + a[i] = Int32.Parse(s1); + } + Array.Reverse(a); + Console.WriteLine("Reversed Array : "); + for (int i = 0; i < x; i++) + { + Console.WriteLine("Element {0} is {1}", i + 1, a[i]); + } + Console.Read(); + } +} + +/* +Enter Number of Elements you Want to Hold in the Array ? 5 +Enter Array Elements : 2 +3 +4 +5 +6 +Reversed Array : +Element is : 6 +Element is : 5 +Element is : 4 +Element is : 3 +Element is : 2 \ No newline at end of file diff --git a/c-sharp/Functions/C# Program to Sort a String using Predefined Function.cs b/c-sharp/Functions/C# Program to Sort a String using Predefined Function.cs new file mode 100644 index 0000000..3c757f2 --- /dev/null +++ b/c-sharp/Functions/C# Program to Sort a String using Predefined Function.cs @@ -0,0 +1,42 @@ +/* + * C# Program to Sort a String using Predefined Function + */ +using System; +class linSearch +{ + public static void Main() + { + Console.WriteLine("Enter Number of Elements you Want to Hold in the Array ? "); + string s = Console.ReadLine(); + int x = Int32.Parse(s); + int[] a = new int[x]; + Console.WriteLine("Enter Array Elements :"); + for (int i = 0; i < x; i++) + { + string s1 = Console.ReadLine(); + a[i] = Int32.Parse(s1); + } + Array.Sort(a); + Console.WriteLine("Sorted Array : "); + for (int i = 0; i < x; i++) + { + Console.WriteLine("{0}",a[i]); + } + Console.Read(); + } +} + +/* +Enter Number of Elements you Want to Hold in the Array ? 5 +Enter Array Elements : +2 +3 +1 +4 +5 +Sorted Array : +1 +2 +3 +4 +5 \ No newline at end of file diff --git a/c-sharp/Functions/C# Program to find Product of 2 Numbers using Recursion.cs b/c-sharp/Functions/C# Program to find Product of 2 Numbers using Recursion.cs new file mode 100644 index 0000000..1c493f5 --- /dev/null +++ b/c-sharp/Functions/C# Program to find Product of 2 Numbers using Recursion.cs @@ -0,0 +1,42 @@ +/* + * C# Program to find Product of 2 Numbers using Recursion + */ +using System; +class program +{ + public static void Main() + { + int a, b, result; + Console.WriteLine("Enter two numbers to find their product: "); + a = int.Parse(Console.ReadLine()); + b = int.Parse(Console.ReadLine()); + prog pg = new prog(); + result = pg.product(a, b); + Console.WriteLine("Product of {0} and {1} is {2}",a, b, result); + Console.ReadLine(); + } +} +class prog +{ + public int product(int a, int b) + { + if (a < b) + { + return product(b, a); + } + else if (b != 0) + { + return (a + product(a, b - 1)); + } + else + { + return 0; + } + } +} + +/* +Enter two numbers to find their product: +5 +6 +Product of 5 and 6 is 30 \ No newline at end of file diff --git a/c-sharp/Games_&_Threads/C# Program to Assign Name to Thread by using Name Property.cs b/c-sharp/Games_&_Threads/C# Program to Assign Name to Thread by using Name Property.cs new file mode 100644 index 0000000..d62e1f0 --- /dev/null +++ b/c-sharp/Games_&_Threads/C# Program to Assign Name to Thread by using Name Property.cs @@ -0,0 +1,25 @@ +/* + * C# Program to Assign Name to Thread by using Name Property + */ +using System; +using System.Threading; +class Name +{ + static void Main() + { + if (Thread.CurrentThread.Name == null) + { + Thread.CurrentThread.Name = "Main"; + Console.Write("Thread has been Named "); + } + else + { + Console.WriteLine("Unable to name a previously " + + "named thread."); + } + Console.ReadLine(); + } +} +/* + +Thread has been Named \ No newline at end of file diff --git a/c-sharp/Games_&_Threads/C# Program to Create Thread Pools.cs b/c-sharp/Games_&_Threads/C# Program to Create Thread Pools.cs new file mode 100644 index 0000000..d7d7acd --- /dev/null +++ b/c-sharp/Games_&_Threads/C# Program to Create Thread Pools.cs @@ -0,0 +1,47 @@ +/* + * C# Program to Create Thread Pools + */ +using System; +using System.Threading; +class ThreadPoolDemo +{ + public void task1(object obj) + { + for (int i = 0; i <= 2; i++) + { + Console.WriteLine("Task 1 is being executed"); + } + } + public void task2(object obj) + { + for (int i = 0; i <= 2; i++) + { + Console.WriteLine("Task 2 is being executed"); + } + } + + static void Main() + { + ThreadPoolDemo tpd = new ThreadPoolDemo(); + for (int i = 0; i < 2; i++) + { + ThreadPool.QueueUserWorkItem(new WaitCallback(tpd.task1)); + ThreadPool.QueueUserWorkItem(new WaitCallback(tpd.task2)); + } + Console.Read(); + } +} +/* + +Task 1 is being executed +Task 1 is being executed +Task 1 is being executed +Task 1 is being executed +Task 1 is being executed +Task 1 is being executed +Task 2 is being executed +Task 2 is being executed +Task 2 is being executed +Task 2 is being executed +Task 2 is being executed +Task 2 is being executed \ No newline at end of file diff --git a/c-sharp/Games_&_Threads/C# Program to Create a HangMan Game.cs b/c-sharp/Games_&_Threads/C# Program to Create a HangMan Game.cs new file mode 100644 index 0000000..c3894a8 --- /dev/null +++ b/c-sharp/Games_&_Threads/C# Program to Create a HangMan Game.cs @@ -0,0 +1,61 @@ +/* + * C# Program to Create a HangMan Game + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +namespace Hangman +{ +class Program +{ + static void Main(string[] args) + { + Console.WriteLine("Welcome to Hangman!!!!!!!!!!"); + string[] listwords = new string[10]; + listwords[0] = "sheep"; + listwords[1] = "goat"; + listwords[2] = "computer"; + listwords[3] = "america"; + listwords[4] = "watermelon"; + listwords[5] = "icecream"; + listwords[6] = "jasmine"; + listwords[7] = "pineapple"; + listwords[8] = "orange"; + listwords[9] = "mango"; + Random randGen = new Random(); + var idx = randGen.Next(0, 9); + string mysteryWord = listwords[idx]; + char[] guess = new char[mysteryWord.Length]; + Console.Write("Please enter your guess: "); + for (int p = 0; p < mysteryWord.Length; p++) + guess[p] = '*'; + while (true) + { + char playerGuess = char.Parse(Console.ReadLine()); + for (int j = 0; j < mysteryWord.Length; j++) + { + if (playerGuess == mysteryWord[j]) + guess[j] = playerGuess; + } + Console.WriteLine(guess); + } + } +} +} +/* + +Welcome to Hangman!!!!!!!!!! +Please enter your guess: i +**** +a +**a* +e +**a* +g +g*a* +o +goa* +t +goat \ No newline at end of file diff --git a/c-sharp/Games_&_Threads/C# Program to Create a Simple Thread.cs b/c-sharp/Games_&_Threads/C# Program to Create a Simple Thread.cs new file mode 100644 index 0000000..bbdf5b5 --- /dev/null +++ b/c-sharp/Games_&_Threads/C# Program to Create a Simple Thread.cs @@ -0,0 +1,35 @@ +/* + * C# Program to Create a Simple Thread + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +using System.Threading; +class program +{ + public void WorkThreadFunction() + { + for (int i = 0; i < 5; i++) + { + Console.WriteLine("Simple Thread"); + } + } +} +class threprog +{ + public static void Main() + { + program pg = new program(); + Thread thread = new Thread(new ThreadStart(pg.WorkThreadFunction)); + thread.Start(); + Console.Read(); + } +} +/* + +Simple Thread +Simple Thread +Simple Thread +Simple Thread +Simple Thread \ No newline at end of file diff --git a/c-sharp/Games_&_Threads/C# Program to Demonstrate Lock in Thread.cs b/c-sharp/Games_&_Threads/C# Program to Demonstrate Lock in Thread.cs new file mode 100644 index 0000000..067f1dc --- /dev/null +++ b/c-sharp/Games_&_Threads/C# Program to Demonstrate Lock in Thread.cs @@ -0,0 +1,40 @@ +/* + * C# Program to Demonstrate Lock in Thread + */ + +using System; +using System.Threading; + +class Program +{ + static readonly object _object = new object(); + + static void TEST() + { + lock (_object) + { + Thread.Sleep(100); + Console.WriteLine(Environment.TickCount); + } + } + static void Main() + { + for (int i = 0; i < 10; i++) + { + ThreadStart start = new ThreadStart(TEST); + new Thread(start).Start(); + } + } +} +/* + +900500 +900593 +900687 +900796 +900890 +900999 +901092 +901186 +901295 +901389 \ No newline at end of file diff --git a/c-sharp/Games_&_Threads/C# Program to Demonstrate Tower Of Hanoi.cs b/c-sharp/Games_&_Threads/C# Program to Demonstrate Tower Of Hanoi.cs new file mode 100644 index 0000000..f3a6f48 --- /dev/null +++ b/c-sharp/Games_&_Threads/C# Program to Demonstrate Tower Of Hanoi.cs @@ -0,0 +1,57 @@ +/* + * C# Program to Demonstrate Tower Of Hanoi + */ +using System; +class TowerOfHanoi +{ + int m_numdiscs; + public TowerOfHanoi() + { + numdiscs = 0; + } + public TowerOfHanoi(int newval) + { + numdiscs = newval; + } + public int numdiscs + { + get + { + return m_numdiscs; + } + set + { + if (value > 0) + m_numdiscs = value; + } + } + public void movetower(int n, int from, int to, int other) + { + if (n > 0) + { + movetower(n - 1, from, other, to); + Console.WriteLine("Move disk {0} from tower {1} to tower {2}", n, from, to); + movetower(n - 1, other, to, from); + } + } +} +class TowersOfHanoiApp +{ + public static int Main() + { + TowerOfHanoi T = new TowerOfHanoi(); + string cnumdiscs; + Console.Write("Enter the number of discs: "); + cnumdiscs = Console.ReadLine(); + T.numdiscs = Convert.ToInt32(cnumdiscs); + T.movetower(T.numdiscs, 1, 3, 2); + Console.ReadLine(); + return 0; + } +} +/* + +Enter the Number of Disks : 2 +Move Disk 1 from Tower 1 to Tower 2 +Move Disk 1 from Tower 1 to Tower 3 +Move Disk 1 from Tower 2 to Tower 3 \ No newline at end of file diff --git a/c-sharp/Games_&_Threads/C# Program to Display the Name of the Current Thread.cs b/c-sharp/Games_&_Threads/C# Program to Display the Name of the Current Thread.cs new file mode 100644 index 0000000..1a44bc9 --- /dev/null +++ b/c-sharp/Games_&_Threads/C# Program to Display the Name of the Current Thread.cs @@ -0,0 +1,27 @@ +/* + * C# Program to Display the Name of the Current Thread + */ +using System; +using System.Threading; + +namespace threading +{ +class Program +{ + static void Main(string[] args) + { + Console.WriteLine("Current information"); + Thread t = Thread.CurrentThread; + t.Name = "primarythread"; + Console.WriteLine("Thread Name: {0}", t.Name); + Console.WriteLine("Thread Status: {0}", t.IsAlive); + Console.ReadKey(); + } + +} +} +/* + +Current information +Thread Name: primarythread +Thread Status: True \ No newline at end of file diff --git a/c-sharp/Games_&_Threads/C# Program to Display the Priority of the Thread.cs b/c-sharp/Games_&_Threads/C# Program to Display the Priority of the Thread.cs new file mode 100644 index 0000000..6ed8af1 --- /dev/null +++ b/c-sharp/Games_&_Threads/C# Program to Display the Priority of the Thread.cs @@ -0,0 +1,28 @@ +/* + * C# Program to Display the Priority of the Thread + */ +using System; +using System.Threading; + +namespace threading +{ +class Program +{ + static void Main(string[] args) + { + Console.WriteLine("**********Current Thread Informations***************n"); + Thread t = Thread.CurrentThread; + t.Name = "Primary_Thread"; + Console.WriteLine("Thread Name: {0}", t.Name); + Console.WriteLine("Thread Status: {0}", t.IsAlive); + Console.WriteLine("Priority: {0}", t.Priority); + Console.ReadKey(); + } + +} +} +/* + +Thread Name: PrimaryThread +Thread Status: True +Priority: Normal \ No newline at end of file diff --git a/c-sharp/Games_&_Threads/C# Program to Find the Current Context id of the Thread.cs b/c-sharp/Games_&_Threads/C# Program to Find the Current Context id of the Thread.cs new file mode 100644 index 0000000..4360dd2 --- /dev/null +++ b/c-sharp/Games_&_Threads/C# Program to Find the Current Context id of the Thread.cs @@ -0,0 +1,28 @@ +/* + * C# Program to Find the Current Context id of the Thread + */ +using System; +using System.Threading; + +namespace threading +{ +class Program +{ + static void Main(string[] args) + { + Console.WriteLine("**********Current Thread Informations***************n"); + Thread t = Thread.CurrentThread; + t.Name = "Primary_Thread"; + Console.WriteLine("Thread Name: {0}", t.Name); + Console.WriteLine("Thread Status: {0}", t.IsAlive); + Console.WriteLine("Priority: {0}", t.Priority); + Console.ReadKey(); + } + +} +} +/* + +Thread Name: PrimaryThread +Thread Status: True +Context ID: 0 \ No newline at end of file diff --git a/c-sharp/Games_&_Threads/C# Program to Illustrate the Concept of Passing Parameter for Thread.cs b/c-sharp/Games_&_Threads/C# Program to Illustrate the Concept of Passing Parameter for Thread.cs new file mode 100644 index 0000000..2435d37 --- /dev/null +++ b/c-sharp/Games_&_Threads/C# Program to Illustrate the Concept of Passing Parameter for Thread.cs @@ -0,0 +1,29 @@ +/* + * C# Program to Illustrate the Concept of Passing Parameter for Thread + */ +using System; +using System.Threading; +public class pgm +{ + public static void Main() + { + Thread newThread = new Thread(pgm.work1); + newThread.Start(20); + pgm p = new pgm(); + newThread = new Thread(p.work2); + newThread.Start("Instance"); + Console.ReadLine(); + } + public static void work1(object data) + { + Console.WriteLine("Static Thread Procedure : Data ='{0}'",data); + } + public void work2(object data) + { + Console.WriteLine("Instance Thread Procedure : Data ='{0}'", data); + } +} +/* + +Static Thread Procedure : Data = '20' +Instance Thread Procedure : Data = 'Instance' \ No newline at end of file diff --git a/c-sharp/Games_&_Threads/C# Program to Implement Sleep method of Thread.cs b/c-sharp/Games_&_Threads/C# Program to Implement Sleep method of Thread.cs new file mode 100644 index 0000000..832c29e --- /dev/null +++ b/c-sharp/Games_&_Threads/C# Program to Implement Sleep method of Thread.cs @@ -0,0 +1,24 @@ +/* + * C# Program to Implement Sleep method of Thread + */ +using System; +using System.Diagnostics; +using System.Threading; +class Program +{ + static void Main() + { + var stopwatch = Stopwatch.StartNew(); + Thread.Sleep(500); + stopwatch.Stop(); + Console.WriteLine("Elapsed Milliseconds : {0}",stopwatch.ElapsedMilliseconds); + Console.WriteLine("Elapsed Ticks : {0}", stopwatch.ElapsedTicks); + Console.WriteLine("Present Date and Time : {0}",DateTime.Now.ToLongTimeString()); + Console.ReadLine(); + } +} +/* + +Elapsed Milliseconds : 498 +Elapsed Ticks : 1231409 +Present Date and Time : 8:36:06 PM \ No newline at end of file diff --git a/c-sharp/Games_&_Threads/C# Program to Kill a Thread.cs b/c-sharp/Games_&_Threads/C# Program to Kill a Thread.cs new file mode 100644 index 0000000..f7b553b --- /dev/null +++ b/c-sharp/Games_&_Threads/C# Program to Kill a Thread.cs @@ -0,0 +1,47 @@ +/* + * C# Program to Kill a Thread + */ +using System; +using System.Threading.Tasks; +using System.Threading; +class Program +{ + static void Main(string[] args) + { + ThreadingClass th = new ThreadingClass(); + Thread thread1 = new Thread(th.DoStuff); + thread1.Start(); + Console.WriteLine("Press any key to exit!!!"); + Console.ReadKey(); + th.Stop(); + thread1.Join(); + } +} +public class ThreadingClass +{ + private bool flag = false; + public void DoStuff() + { + while (!flag) + { + Console.WriteLine(" Thread is Still Working"); + Thread.Sleep(1000); + } + } + public void Stop() + { + flag = true; + } +} +/* + +Press any key to exit!!! + Thread is Still Working + Thread is Still Working + Thread is Still Working + Thread is Still Working + Thread is Still Working + Thread is Still Working + Thread is Still Working + Thread is Still Working + Thread is Still Working \ No newline at end of file diff --git a/c-sharp/Games_&_Threads/C# Program to Obtain Status of the Current Thread.cs b/c-sharp/Games_&_Threads/C# Program to Obtain Status of the Current Thread.cs new file mode 100644 index 0000000..5a0ac23 --- /dev/null +++ b/c-sharp/Games_&_Threads/C# Program to Obtain Status of the Current Thread.cs @@ -0,0 +1,27 @@ +/* + * C# Program to Obtain Status of the Current Thread + */ +using System; +using System.Threading; + +namespace threading +{ +class Program +{ + static void Main(string[] args) + { + Console.WriteLine("Current information"); + Thread t = Thread.CurrentThread; + t.Name = "primarythread"; + Console.WriteLine("Thread Name: {0}", t.Name); + Console.WriteLine("Thread Status: {0}", t.IsAlive); + Console.ReadKey(); + } + +} +} +/* + +Current information +Thread Name: primarythread +Thread Status: True \ No newline at end of file diff --git a/c-sharp/Games_&_Threads/C# Program to Pause a Thread.cs b/c-sharp/Games_&_Threads/C# Program to Pause a Thread.cs new file mode 100644 index 0000000..8ad1938 --- /dev/null +++ b/c-sharp/Games_&_Threads/C# Program to Pause a Thread.cs @@ -0,0 +1,27 @@ +/* + * C# Program to Pause a Thread + */ +using System; +using System.Threading; +class Example +{ + static void Main() + { + for (int i = 0; i < 5; i++) + { + Console.WriteLine("Sleep for 2 Seconds"); + Thread.Sleep(2000); + } + Console.WriteLine("Main thread Exits"); + Console.ReadLine(); + } +} +/* + +Sleep for 2 Seconds +Sleep for 2 Seconds +Sleep for 2 Seconds +Sleep for 2 Seconds +Sleep for 2 Seconds +Sleep for 2 Seconds +Main thread Exits \ No newline at end of file diff --git a/c-sharp/Games_&_Threads/C# Program to Perform a Number Guessing Game.cs b/c-sharp/Games_&_Threads/C# Program to Perform a Number Guessing Game.cs new file mode 100644 index 0000000..e8ec04b --- /dev/null +++ b/c-sharp/Games_&_Threads/C# Program to Perform a Number Guessing Game.cs @@ -0,0 +1,57 @@ +/* + * C# Program to Perform a Number Guessing Game + */ +using System; +using System.Collections.Generic; +using System.Text; +class Program +{ + static void Main(string[] args) + { + while (true) + { + int randno = Newnum(1, 101); + int count = 1; + while (true) + { + Console.Write("Enter a number between 1 and 100(0 to quit):"); + int input = Convert.ToInt32(Console.ReadLine()); + if (input == 0) + return; + else if (input < randno) + { + Console.WriteLine("Low, try again."); + ++count; + continue; + } + else if (input > randno) + { + Console.WriteLine("High, try again."); + ++count; + continue; + } + else + { + Console.WriteLine("You guessed it! The number was {0}!", randno); + Console.WriteLine("It took you {0} {1}.\n", count, count == 1 ? "try" : "tries"); + break; + } + } + } + } + static int Newnum(int min, int max) + { + Random random = new Random(); + return random.Next(min, max); + } +} +} +/* + +Enter a number between 1 and 100(0 to quit) : 56 +Low,try again. +Enter a number between 1 and 100(0 to quit): 67 +high,try again. +Enter a number between 1 and 100(0 to quit): 59 +You guessed it! The number was 59 +It took you 2 tries!!! \ No newline at end of file diff --git a/c-sharp/Games_&_Threads/C# Program to Prefix Game.cs b/c-sharp/Games_&_Threads/C# Program to Prefix Game.cs new file mode 100644 index 0000000..40d6478 --- /dev/null +++ b/c-sharp/Games_&_Threads/C# Program to Prefix Game.cs @@ -0,0 +1,68 @@ +/* + * C# Program to Prefix Game + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +namespace Project +{ +class Program +{ + static void Main(string[] args) + { + string[,] seq = new string[4, 3]; + int row = 0; + seq[row, 0] = "substring"; + seq[row, 1] = "sub"; + seq[row, 2] = "incorrect"; + row++; + seq[row, 0] = "input"; + seq[row, 1] = "in"; + seq[row, 2] = "incorrect"; + row++; + int numrows = 0; + play(seq, numrows); + Console.Write("Continue : Press 'y'"); + string next = Console.ReadLine(); + if (next.CompareTo("y") == 0) + { + Console.Clear(); + numrows += 2; + play(seq, numrows); + } + Console.ReadLine(); + } + static void play(string[,] seq, int rows) + { + Console.WriteLine("ENGLISH WORD PREFIX GAME"); + for (int i = rows; i dict = new Dictionary(); + dict["Tom"] = "Bob"; + WriteKeyA(dict); + SortedDictionary sort = new SortedDictionary(); + sort["Tom"] = "Jerry"; + WriteKeyA(sort); + Console.ReadLine(); + } + + static void WriteKeyA(IDictionary i) + { + Console.WriteLine(i["Tom"]); + } +} +/* + +Bob +Jerry \ No newline at end of file diff --git a/c-sharp/Inheritance_&_Interface/C# Program to Demonstrate iList Interface.cs b/c-sharp/Inheritance_&_Interface/C# Program to Demonstrate iList Interface.cs new file mode 100644 index 0000000..a13097f --- /dev/null +++ b/c-sharp/Inheritance_&_Interface/C# Program to Demonstrate iList Interface.cs @@ -0,0 +1,42 @@ +/* + * C# Program to Demonstrate iList Interface + */ +using System; +using System.Collections.Generic; + +class Program +{ + static void Main() + { + int[] a = new int[3]; + a[0] = 1; + a[1] = 2; + a[2] = 3; + Display(a); + List list = new List(); + list.Add(5); + list.Add(7); + list.Add(9); + Display(list); + Console.ReadLine(); + } + + static void Display(IList list) + { + Console.WriteLine("Count: {0}", list.Count); + foreach (int num in list) + { + Console.WriteLine(num); + } + } +} +/* + +Count: 3 +1 +2 +3 +Count: 3 +5 +7 +9 \ No newline at end of file diff --git a/c-sharp/Inheritance_&_Interface/C# Program to Display Cost of a Rectangle Plot Using Inheritance.cs b/c-sharp/Inheritance_&_Interface/C# Program to Display Cost of a Rectangle Plot Using Inheritance.cs new file mode 100644 index 0000000..e4264dd --- /dev/null +++ b/c-sharp/Inheritance_&_Interface/C# Program to Display Cost of a Rectangle Plot Using Inheritance.cs @@ -0,0 +1,57 @@ +/* + * C# Program to Display Cost of a Rectangle Plot Using Inheritance + */ +using System; +class Rectangle +{ + protected double length; + protected double width; + public Rectangle(double l, double w) + { + length = l; + width = w; + } + public double GetArea() + { + return length * width; + } + public void Display() + { + Console.WriteLine("Length: {0}", length); + Console.WriteLine("Width: {0}", width); + Console.WriteLine("Area: {0}", GetArea()); + } +} +class Tabletop : Rectangle +{ + private double cost; + public Tabletop(double l, double w) + : base(l, w) + { } + public double costcal() + { + double cost; + cost = GetArea() * 70; + return cost; + } + public void Display() + { + base.Display(); + Console.WriteLine("Cost: {0}", costcal()); + } +} +class CalRectangle +{ + static void Main(string[] args) + { + Tabletop t = new Tabletop(7.5, 8.03); + t.Display(); + Console.ReadLine(); + } +} + +/* +Length: 7.5 +Width: 8.03 +Area: 60.225 +Cost: 4215.75 \ No newline at end of file diff --git a/c-sharp/Inheritance_&_Interface/C# Program to IIlustrate Handling an Event Declared in an Interface.cs b/c-sharp/Inheritance_&_Interface/C# Program to IIlustrate Handling an Event Declared in an Interface.cs new file mode 100644 index 0000000..c4ac9ff --- /dev/null +++ b/c-sharp/Inheritance_&_Interface/C# Program to IIlustrate Handling an Event Declared in an Interface.cs @@ -0,0 +1,112 @@ +/* + * C# Program to IIlustrate Handling an Event Declared in an Interface + */ +namespace interfaceevents +{ +using System; + +public interface square +{ + event EventHandler Draw; +} +public interface rectangle +{ + event EventHandler Draw; +} +public class Shape : square, rectangle +{ + event EventHandler DrawEvent1; + event EventHandler DrawEvent2; + object objectLock = new Object(); + event EventHandler square.Draw + { + add + { + lock (objectLock) + { + DrawEvent1 += value; + } + } + remove + { + lock (objectLock) + { + DrawEvent1 -= value; + } + } + } + event EventHandler rectangle.Draw + { + add + { + DrawEvent2 += value; + } + remove + { + DrawEvent2 -= value; + + } + + } + public void Draw() + { + EventHandler handler = DrawEvent1; + if (handler != null) + { + handler(this, new EventArgs()); + } + Console.WriteLine("Drawing a shape."); + handler = DrawEvent2; + if (handler != null) + { + handler(this, new EventArgs()); + } + } +} +public class classA +{ + // References the shape object as an square + public classA(Shape shape) + { + square d = (square)shape; + d.Draw += new EventHandler(d_Draw); + } + + void d_Draw(object sender, EventArgs e) + { + Console.WriteLine("ClassA receives the square event."); + } +} +public class classB +{ + public classB(Shape shape) + { + rectangle d = (rectangle)shape; + d.Draw += new EventHandler(d_Draw); + } + + void d_Draw(object sender, EventArgs e) + { + Console.WriteLine("ClassB receives the rectangle event."); + } +} + +public class Program +{ + static void Main(string[] args) + { + Shape shape = new Shape(); + classA sub = new classA(shape); + classB sub2 = new classB(shape); + shape.Draw(); + System.Console.WriteLine("Press any key to exit."); + System.Console.ReadKey(); + } +} +} +/* + +ClassA receives the Square event. +Drawing a shape. +ClassB receives the Rectangle event. +Press any key to exit. \ No newline at end of file diff --git a/c-sharp/Inheritance_&_Interface/C# Program to Illustrate Hierarchical Inheritance.cs b/c-sharp/Inheritance_&_Interface/C# Program to Illustrate Hierarchical Inheritance.cs new file mode 100644 index 0000000..e542f59 --- /dev/null +++ b/c-sharp/Inheritance_&_Interface/C# Program to Illustrate Hierarchical Inheritance.cs @@ -0,0 +1,53 @@ +/* + * C# Program to Illustrate Hierarchical Inheritance + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +namespace Inheritance +{ +class Program +{ + static void Main(string[] args) + { + Principal g = new Principal(); + g.Monitor(); + Teacher d = new Teacher(); + d.Monitor(); + d.Teach(); + Student s = new Student(); + s.Monitor(); + s.Learn(); + Console.ReadKey(); + } + class Principal + { + public void Monitor() + { + Console.WriteLine("Monitor"); + } + } + class Teacher : Principal + { + public void Teach() + { + Console.WriteLine("Teach"); + } + } + class Student : Principal + { + public void Learn() + { + Console.WriteLine("Learn"); + } + } +} +} + +/* +Monitor +Monitor +Teach +Monitor +Learn \ No newline at end of file diff --git a/c-sharp/Inheritance_&_Interface/C# Program to Illustrate Multilevel Inheritance with Virtual Methods.cs b/c-sharp/Inheritance_&_Interface/C# Program to Illustrate Multilevel Inheritance with Virtual Methods.cs new file mode 100644 index 0000000..04fdd35 --- /dev/null +++ b/c-sharp/Inheritance_&_Interface/C# Program to Illustrate Multilevel Inheritance with Virtual Methods.cs @@ -0,0 +1,56 @@ +/* + * C# Program to Illustrate Multilevel Inheritance with Virtual Methods + */ +using System; +public class Person +{ + protected string RNO = "44"; + protected string name = "Ram"; + public virtual void GetInfo() + { + Console.WriteLine("Name: {0}", name); + Console.WriteLine("RNO: {0}", RNO); + Console.WriteLine(); + } +} +class Student : Person +{ + public string id = "ABC"; + public override void GetInfo() + { + base.GetInfo(); + Console.WriteLine("Student ID: {0}", id); + } +} +class Stud : Student +{ + private string StudentAddress = "USA"; + public void GetInfo() + { + base.GetInfo(); + Console.WriteLine("Student Address: {0}", StudentAddress); + } +} +class TestClass +{ + public static void Main() + { + Student E = new Student(); + E.GetInfo(); + Stud Stud = new Stud(); + Stud.GetInfo(); + Console.ReadLine(); + } +} + +/* + +Name : Ram +RNO : 44 + +Student ID : ABC +Name : Ram +RNO : 44 + +Student ID : ABC +Student Address : USA \ No newline at end of file diff --git a/c-sharp/Inheritance_&_Interface/C# Program to Illustrate Single Inheritance.cs b/c-sharp/Inheritance_&_Interface/C# Program to Illustrate Single Inheritance.cs new file mode 100644 index 0000000..ba94706 --- /dev/null +++ b/c-sharp/Inheritance_&_Interface/C# Program to Illustrate Single Inheritance.cs @@ -0,0 +1,41 @@ +/* + * C# Program to Illustrate Single Inheritance + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +namespace Inheritance +{ +class Program +{ + static void Main(string[] args) + { + Teacher d = new Teacher(); + d.Teach(); + Student s = new Student(); + s.Learn(); + s.Teach(); + Console.ReadKey(); + } + class Teacher + { + public void Teach() + { + Console.WriteLine("Teach"); + } + } + class Student : Teacher + { + public void Learn() + { + Console.WriteLine("Learn"); + } + } +} +} + +/* +Teach +Learn +Teach \ No newline at end of file diff --git a/c-sharp/Inheritance_&_Interface/C# Program to Implement IComparable Interface.cs b/c-sharp/Inheritance_&_Interface/C# Program to Implement IComparable Interface.cs new file mode 100644 index 0000000..ea308fe --- /dev/null +++ b/c-sharp/Inheritance_&_Interface/C# Program to Implement IComparable Interface.cs @@ -0,0 +1,69 @@ +/* + * C# Program to Implement IComparable Interface + */ +using System; +class Fraction : IComparable +{ + int z, n; + + public Fraction(int z, int n) + { + this.z = z; + this.n = n; + } + + public static Fraction operator +(Fraction a, Fraction b) + { + return new Fraction(a.z * b.n + a.n * b.z, a.n * b.n); + } + + public static Fraction operator *(Fraction a, Fraction b) + { + return new Fraction(a.z * b.z, a.n * b.n); + } + + public int CompareTo(object obj) + { + Fraction f = (Fraction)obj; + if ((float)z / n < (float)f.z / f.n) + return -1; + else if ((float)z / n > (float)f.z / f.n) + return 1; + else return 0; + } + + public override string ToString() + { + return z + "/" + n; + } +} + +class Test +{ + + static void Main(string[] arg) + { + Fraction[] a = + { + new Fraction(5,2), + new Fraction(29,6), + new Fraction(4,5), + new Fraction(10,8), + new Fraction(34,7) + }; + Array.Sort(a); + Console.WriteLine("Implementing the IComparable Interface in Displaying Fractions : "); + foreach (Fraction f in a) Console.WriteLine(f + " "); + Console.WriteLine(); + Console.ReadLine(); + } + +} +/* + +Implementing the IComparable Interface in Displaying Fractions : +4/5 +10/8 +5/2 +29/6 +34/7 \ No newline at end of file diff --git a/c-sharp/Inheritance_&_Interface/C# Program to Implement IEnumerable Interface using LINQ.cs b/c-sharp/Inheritance_&_Interface/C# Program to Implement IEnumerable Interface using LINQ.cs new file mode 100644 index 0000000..bb8198b --- /dev/null +++ b/c-sharp/Inheritance_&_Interface/C# Program to Implement IEnumerable Interface using LINQ.cs @@ -0,0 +1,40 @@ +/* + * C# Program to Implement IEnumerable Interface using LINQ + */ +using System; +using System.IO; +using System.Collections; +using System.Linq; +class program +{ + public static void Main(string[] args) + { + var t = typeof(IEnumerable); + var typesIEnum = AppDomain.CurrentDomain.GetAssemblies().SelectMany(x => x.GetTypes()).Where(x => t.IsAssignableFrom(x)); + foreach (var types in typesIEnum) + { + Console.WriteLine(types.FullName); + } + Console.ReadLine(); + } +} +/* + +System.Linq.Parallel.IndexedSelectQueryOperator`2 +System.Linq.Parallel.IndexedSelectQueryOperator`2+IndexedSelectQueryOperatorResults +System.Linq.Parallel.IndexedWhereQueryOperator`1 +System.Linq.Parallel.LastQueryOperator`1 +System.Linq.Parallel.ReverseQueryOperator`1 +System.Linq.Parallel.ReverseQueryOperator`1+ReverseQueryOperatorResults +System.Linq.Parallel.SelectManyQueryOperator`3 +System.Linq.Parallel.SelectQueryOperator`2 +System.Linq.Parallel.SelectQueryOperator`2+SelectQueryOperatorResults +System.Linq.Parallel.SingleQueryOperator`1 +System.Linq.Parallel.SortQueryOperator`2 +System.Linq.Parallel.SortQueryOperatorResults`2 +System.Linq.Parallel.TakeOrSkipQueryOperator`1 +System.Linq.Parallel.TakeOrSkipQueryOperator`1+TakeOrSkipQueryOperatorResults +System.Linq.Parallel.TakeOrSkipWhileQueryOperator`1 +System.Linq.Parallel.WhereQueryOperator`1 +System.Linq.Parallel.ListChunk`1 +System.Linq.Parallel.Lookup`2 \ No newline at end of file diff --git a/c-sharp/Linq/C# Program to Calculate Size of File using LINQ.cs b/c-sharp/Linq/C# Program to Calculate Size of File using LINQ.cs new file mode 100644 index 0000000..e758589 --- /dev/null +++ b/c-sharp/Linq/C# Program to Calculate Size of File using LINQ.cs @@ -0,0 +1,20 @@ +/* + * C# Program to Calculate Size of File using LINQ + */ +using System; +using System.Linq; +using System.IO; +class Program +{ + static void Main(string[] args) + { + string[] dirfiles = Directory.GetFiles("c:\\sri\\"); + var avg = dirfiles.Select(file =>new FileInfo(file).Length).Average(); + avg = Math.Round(avg / 10, 1); + Console.WriteLine("The Average file size is {0} MB",avg); + Console.ReadLine(); + } +} + +/* +The Average file size is 8.8 MB \ No newline at end of file diff --git a/c-sharp/Linq/C# Program to Count File Extensions and Group it using LINQ.cs b/c-sharp/Linq/C# Program to Count File Extensions and Group it using LINQ.cs new file mode 100644 index 0000000..42454b3 --- /dev/null +++ b/c-sharp/Linq/C# Program to Count File Extensions and Group it using LINQ.cs @@ -0,0 +1,32 @@ +/* + * C# Program to Count File Extensions and Group it using LINQ + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +using System.IO; +namespace ConsoleApplication9 +{ +class Program +{ + public static void Main() + { + string[] arr = { "aaa.txt", "bbb.TXT", "xyz.abc.pdf", "aaaa.PDF", "abc.xml", "ccc.txt", "zzz.txt" }; + var egrp = arr.Select(file => Path.GetExtension(file).TrimStart('.').ToLower()) + .GroupBy(x => x,(ext, extCnt) =>new + { + Extension = ext, + Count = extCnt.Count() + }); + foreach (var v in egrp) + Console.WriteLine("{0} File(s) with {1} Extension ",v.Count, v.Extension); + Console.ReadLine(); + } +} +} + +/* +4 File(s) with txt Extension +2 File(s) with pdf Extension +1 File(s) with xml Extension \ No newline at end of file diff --git a/c-sharp/Linq/C# Program to Display the Greatest numbers in an Array using WHERE Clause LINQ.cs b/c-sharp/Linq/C# Program to Display the Greatest numbers in an Array using WHERE Clause LINQ.cs new file mode 100644 index 0000000..11caddd --- /dev/null +++ b/c-sharp/Linq/C# Program to Display the Greatest numbers in an Array using WHERE Clause LINQ.cs @@ -0,0 +1,30 @@ +/* + * C# Program to Display the Greatest numbers in an Array using WHERE Clause LINQ + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +using System.Threading.Tasks; + +class Program +{ + static void Main() + { + int[] numbers = { 500, 344, 221, 4443, 229, 1008, 6000, 767, 256, 0 }; + var greaterNums = + from num in numbers + where num > 500 + select num; + Console.WriteLine("Numbers Greater than 500 :"); + foreach (var s in greaterNums) + { + Console.Write(s.ToString() + " "); + } + Console.Read(); + } +} + +/* +Numbers Greater than 500 : +4443 1008 6000 767 \ No newline at end of file diff --git a/c-sharp/Linq/C# Program to Display the Smallest numbers in an Array using FROM Clause LINQ.cs b/c-sharp/Linq/C# Program to Display the Smallest numbers in an Array using FROM Clause LINQ.cs new file mode 100644 index 0000000..4d8172e --- /dev/null +++ b/c-sharp/Linq/C# Program to Display the Smallest numbers in an Array using FROM Clause LINQ.cs @@ -0,0 +1,32 @@ +/* + * C# Program to Display the Smallest numbers in an Array using FROM Clause LINQ + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +using System.Threading.Tasks; + +namespace ConsoleApplication2 +{ +class program +{ + static void Main() + { + int[] numbers = { 50,30,45,10,60,100,500,300,40,22,44,55,66,1000 }; + var program = from num in numbers + where num < 50 + select num; + Console.WriteLine("Numbers less than 50 are :"); + foreach (int i in program) + { + Console.Write(i + " "); + } + Console.ReadLine(); + } +} +} + +/* +Numbers less than 50 are : +30 45 10 40 22 44 \ No newline at end of file diff --git a/c-sharp/Linq/C# Program to Display the Student Details using Select Clause LINQ.cs b/c-sharp/Linq/C# Program to Display the Student Details using Select Clause LINQ.cs new file mode 100644 index 0000000..b535803 --- /dev/null +++ b/c-sharp/Linq/C# Program to Display the Student Details using Select Clause LINQ.cs @@ -0,0 +1,97 @@ +/* + * C# Program to Display the Student Details using Select Clause LINQ + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +using System.Threading.Tasks; +class Programs +{ + public class Student + { + public string First { get; set; } + public string Last { get; set; } + public int ID { get; set; } + public List Marks; + public ContactInfo GetContactInfo(Programs pg, int id) + { + ContactInfo allinfo = + (from ci in pg.contactList + where ci.ID == id + select ci) + .FirstOrDefault(); + return allinfo; + } + + public override string ToString() + { + return First + "" + Last + " : " + ID; + } + } + + public class ContactInfo + { + public int ID { get; set; } + public string Email { get; set; } + public string Phone { get; set; } + public override string ToString() + { + return Email + "," + Phone; + } + } + + public class ScoreInfo + { + public double Average { get; set; } + public int ID { get; set; } + } + List students = new List() + { + new Student {First="Tom", Last=".S", ID=1, Marks= new List() + { + 97, 92, 81, 60 + }}, + new Student {First="Jerry", Last=".M", ID=2, Marks= new List() + { + 75, 84, 91, 39 + }}, + new Student {First="Bob", Last=".P", ID=3, Marks= new List() + { + 88, 94, 65, 91 + }}, + new Student {First="Mark", Last=".G", ID=4, Marks= new List() + { + 97, 89, 85, 82 + }}, + }; + List contactList = new List() + { + new ContactInfo {ID=111, Email="Tom@abc.com", Phone="9328298765"}, + new ContactInfo {ID=112, Email="Jerry123@aaa.com", Phone="9876543201"}, + new ContactInfo {ID=113, Email="Bobstar@aaa.com", Phone="9087467653"}, + new ContactInfo {ID=114, Email="Markantony@qqq.com", Phone="9870098761"} + }; + + + static void Main(string[] args) + { + Programs pg = new Programs(); + IEnumerable studentQuery1 = + from student in pg.students + where student.ID > 1 + select student; + Console.WriteLine("Query : Select range_variable"); + Console.WriteLine("Name : ID"); + foreach (Student s in studentQuery1) + { + Console.WriteLine(s.ToString()); + } + Console.ReadLine(); + } +} + +/* +Enter the Number : 2 +Enter the Exponent :3 +Result : 8 \ No newline at end of file diff --git a/c-sharp/Linq/C# Program to Divide Sequence into Groups using LINQ.cs b/c-sharp/Linq/C# Program to Divide Sequence into Groups using LINQ.cs new file mode 100644 index 0000000..d6c2a30 --- /dev/null +++ b/c-sharp/Linq/C# Program to Divide Sequence into Groups using LINQ.cs @@ -0,0 +1,34 @@ +/* + * C# Program to Divide Sequence into Groups using LINQ + */ +using System; +using System.Linq; +using System.IO; +class Program +{ + static void Main(string[] args) + { + var seq = Enumerable.Range(100, 100).Select(x => x / 10f); + var grps = from x in seq.Select((i, j) => new + { + i, Grp = j / 10 + }) + group x.i by x.Grp into y + select new { Min = y.Min(), Max = y.Max() }; + foreach (var grp in grps) + Console.WriteLine("Min: " + grp.Min + " Max:" + grp.Max); + Console.ReadLine(); + } +} + +/* +Min : 10 Max : 10.9 +Min : 11 Max : 11.9 +Min : 12 Max : 12.9 +Min : 13 Max : 13.9 +Min : 14 Max : 14.9 +Min : 15 Max : 15.9 +Min : 16 Max : 16.9 +Min : 17 Max : 17.9 +Min : 18 Max : 18.9 +Min : 19 Max : 19.9 \ No newline at end of file diff --git a/c-sharp/Linq/C# Program to Generate Odd Numbers in Parallel using LINQ.cs b/c-sharp/Linq/C# Program to Generate Odd Numbers in Parallel using LINQ.cs new file mode 100644 index 0000000..54d3988 --- /dev/null +++ b/c-sharp/Linq/C# Program to Generate Odd Numbers in Parallel using LINQ.cs @@ -0,0 +1,322 @@ +/* + * C# Program to Generate Odd Numbers in Parallel using LINQ + */ +using System; +using System.Linq; +using System.Collections.Generic; + +class Program +{ + static void Main(string[] args) + { + IEnumerable oddNums = ((ParallelQuery)ParallelEnumerable.Range(20, 2000)) + .Where(x => x % 2 != 0) + .Select(i => i); + foreach (int n in oddNums) + { + Console.WriteLine(n); + } + Console.ReadLine(); + } +} + +/* +871 +1371 +1871 +373 +873 +1373 +1873 +375 +875 +1375 +1875 +377 +877 +1377 +1877 +379 +879 +1379 +1879 +381 +881 +1381 +1881 +383 +883 +1383 +1883 +385 +885 +1385 +1885 +387 +887 +1387 +1887 +389 +889 +1389 +1889 +391 +891 +1391 +1891 +393 +893 +1393 +1893 +395 +895 +1395 +1895 +397 +897 +1397 +1897 +399 +899 +1399 +1899 +401 +901 +1401 +1901 +403 +903 +1403 +1903 +405 +905 +1405 +1905 +407 +907 +1407 +1907 +409 +909 +1409 +1909 +411 +911 +1411 +1911 +413 +913 +1413 +1913 +415 +915 +1415 +1915 +417 +917 +1417 +1917 +419 +919 +1419 +1919 +421 +921 +1421 +1921 +423 +923 +1423 +1923 +425 +925 +1425 +1925 +427 +927 +1427 +1927 +429 +929 +1429 +1929 +431 +931 +1431 +1931 +433 +933 +1433 +1933 +435 +935 +1435 +1935 +437 +937 +1437 +1937 +439 +939 +1439 +1939 +441 +941 +1441 +1941 +443 +943 +1443 +1943 +445 +945 +1445 +1945 +447 +947 +1447 +1947 +449 +949 +1449 +1949 +451 +951 +1451 +1951 +453 +953 +1453 +1953 +455 +955 +1455 +1955 +457 +957 +1457 +1957 +459 +959 +1459 +1959 +461 +961 +1461 +1961 +463 +963 +1463 +1963 +465 +965 +1465 +1965 +467 +967 +1467 +1967 +469 +969 +1469 +1969 +471 +971 +1471 +1971 +473 +973 +1473 +1973 +475 +975 +1475 +1975 +477 +977 +1477 +1977 +479 +979 +1479 +1979 +481 +981 +1481 +1981 +483 +983 +1483 +1983 +485 +985 +1485 +1985 +487 +987 +1487 +1987 +489 +989 +1489 +1989 +491 +991 +1491 +1991 +493 +993 +1493 +1993 +495 +995 +1495 +1995 +497 +997 +1497 +1997 +499 +999 +1499 +1999 +501 +1001 +1501 +2001 +503 +1003 +1503 +2003 +505 +1005 +1505 +2005 +507 +1007 +1507 +2007 +509 +1009 +1509 +2009 +511 +1011 +1511 +2011 +513 +1013 +1513 +2013 +515 +1015 +1515 +2015 +517 +1017 +1517 +2017 +519 +1019 +1519 +2019 \ No newline at end of file diff --git a/c-sharp/Linq/C# Program to Implement IEnumerable Interface using LINQ.cs b/c-sharp/Linq/C# Program to Implement IEnumerable Interface using LINQ.cs new file mode 100644 index 0000000..58e74b8 --- /dev/null +++ b/c-sharp/Linq/C# Program to Implement IEnumerable Interface using LINQ.cs @@ -0,0 +1,40 @@ +/* + * C# Program to Implement IEnumerable Interface using LINQ + */ +using System; +using System.IO; +using System.Collections; +using System.Linq; +class program +{ + public static void Main(string[] args) + { + var t = typeof(IEnumerable); + var typesIEnum = AppDomain.CurrentDomain.GetAssemblies().SelectMany(x => x.GetTypes()).Where(x => t.IsAssignableFrom(x)); + foreach (var types in typesIEnum) + { + Console.WriteLine(types.FullName); + } + Console.ReadLine(); + } +} + +/* +System.Linq.Parallel.IndexedSelectQueryOperator`2 +System.Linq.Parallel.IndexedSelectQueryOperator`2+IndexedSelectQueryOperatorResults +System.Linq.Parallel.IndexedWhereQueryOperator`1 +System.Linq.Parallel.LastQueryOperator`1 +System.Linq.Parallel.ReverseQueryOperator`1 +System.Linq.Parallel.ReverseQueryOperator`1+ReverseQueryOperatorResults +System.Linq.Parallel.SelectManyQueryOperator`3 +System.Linq.Parallel.SelectQueryOperator`2 +System.Linq.Parallel.SelectQueryOperator`2+SelectQueryOperatorResults +System.Linq.Parallel.SingleQueryOperator`1 +System.Linq.Parallel.SortQueryOperator`2 +System.Linq.Parallel.SortQueryOperatorResults`2 +System.Linq.Parallel.TakeOrSkipQueryOperator`1 +System.Linq.Parallel.TakeOrSkipQueryOperator`1+TakeOrSkipQueryOperatorResults +System.Linq.Parallel.TakeOrSkipWhileQueryOperator`1 +System.Linq.Parallel.WhereQueryOperator`1 +System.Linq.Parallel.ListChunk`1 +System.Linq.Parallel.Lookup`2 \ No newline at end of file diff --git a/c-sharp/Linq/C# Program to Implement Let Condition using LINQ.cs b/c-sharp/Linq/C# Program to Implement Let Condition using LINQ.cs new file mode 100644 index 0000000..e57dff0 --- /dev/null +++ b/c-sharp/Linq/C# Program to Implement Let Condition using LINQ.cs @@ -0,0 +1,45 @@ +/* + * C# Program to Implement Let Condition using LINQ + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +class Student +{ + public string Name { get; set; } + public string Regno { get; set; } + public int Marks { get; set; } + +} +class Program +{ + static void Main(string[] args) + { + //Object Initialization for Student class + List objStudent = new List + { + new Student{ Name="Tom",Regno="R001",Marks=80}, + new Student{ Name="Bob",Regno="R002",Marks=40}, + new Student{ Name="jerry",Regno="R003",Marks=25}, + new Student{ Name="Syed",Regno="R004",Marks=30}, + new Student{ Name="Mob",Regno="R005",Marks=70}, + }; + var objresult = from stu in objStudent + let totalMarks = objStudent.Sum(mark => mark.Marks) + let avgMarks = totalMarks / 5 + where avgMarks > stu.Marks + select stu; + foreach (var stu in objresult) + { + Console.WriteLine("Student: {0} {1}", stu.Name, stu.Regno); + } + Console.ReadLine(); + } +} + +/* +Student: Bob R002 +Student: jerry R003 +Student: Syed R004 \ No newline at end of file diff --git a/c-sharp/Linq/C# Sharp to Accept the members of a list through the keyboard and display the members more than a specific value.cs b/c-sharp/Linq/C# Sharp to Accept the members of a list through the keyboard and display the members more than a specific value.cs new file mode 100644 index 0000000..306e7aa --- /dev/null +++ b/c-sharp/Linq/C# Sharp to Accept the members of a list through the keyboard and display the members more than a specific value.cs @@ -0,0 +1,33 @@ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +class LinqExercise10 +{ + static void Main(string[] args) + { + int i=0; + int memlist,n,m; + List templist = new List(); + Console.Write("\nLINQ : Accept the members of a list and display the members more than a specific value : "); + Console.Write("\n----------------------------------------------------------------------------------------\n"); + Console.Write("Input the number of members on the List : "); + n= Convert.ToInt32(Console.ReadLine()); + for(i=0; i FilterList = templist.FindAll(x => x > m ? true : false); + Console.WriteLine("\nThe numbers greater than {0} are : ",m); + foreach (var num in FilterList) + { + Console.WriteLine(num); + } + Console.ReadLine(); + } +} \ No newline at end of file diff --git a/c-sharp/Linq/C# Sharp to Calculate Size of File using LINQ.cs b/c-sharp/Linq/C# Sharp to Calculate Size of File using LINQ.cs new file mode 100644 index 0000000..42b776d --- /dev/null +++ b/c-sharp/Linq/C# Sharp to Calculate Size of File using LINQ.cs @@ -0,0 +1,18 @@ +using System; +using System.Linq; +using System.IO; +class LinqExercise16 +{ + static void Main(string[] args) + { + string[] dirfiles = Directory.GetFiles("/home/w3r/abcd/"); + // there are three files in the directory abcd are : + // abcd.txt, simple_file.txt and xyz.txt + Console.Write("\nLINQ : Calculate the Size of File : "); + Console.Write("\n------------------------------------\n"); + var avgFsize = dirfiles.Select(file =>new FileInfo(file).Length).Average(); + avgFsize = Math.Round(avgFsize / 10, 1); + Console.WriteLine("The Average file size is {0} MB",avgFsize); + Console.ReadLine(); + } +} \ No newline at end of file diff --git a/c-sharp/Linq/C# Sharp to Remove Items from List by creating an object internally by filtering.cs b/c-sharp/Linq/C# Sharp to Remove Items from List by creating an object internally by filtering.cs new file mode 100644 index 0000000..fa8c102 --- /dev/null +++ b/c-sharp/Linq/C# Sharp to Remove Items from List by creating an object internally by filtering.cs @@ -0,0 +1,35 @@ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +class LinqExercise18 +{ + static void Main(string[] args) + { + List listOfString = new List(); + listOfString.Add("m"); + listOfString.Add("n"); + listOfString.Add("o"); + listOfString.Add("p"); + listOfString.Add("q"); + Console.Write("\nLINQ : Remove Items from List by creating object internally by filtering : "); + Console.Write("\n--------------------------------------------------------------------------\n"); + var _result1 = from y in listOfString + select y; + Console.Write("Here is the list of items : \n"); + foreach(var tchar in _result1) + { + Console.WriteLine("Char: {0} ", tchar); + } + listOfString.Remove(listOfString.FirstOrDefault(en => en == "p")); + var _result = from z in listOfString + select z; + Console.Write("\nHere is the list after removing the item 'p' from the list : \n"); + foreach(var rChar in _result) + { + Console.WriteLine("Char: {0} ", rChar); + } + Console.ReadLine(); + } +} \ No newline at end of file diff --git a/c-sharp/Linq/C# Sharp to Remove Items from List by passing filters.cs b/c-sharp/Linq/C# Sharp to Remove Items from List by passing filters.cs new file mode 100644 index 0000000..4228d4e --- /dev/null +++ b/c-sharp/Linq/C# Sharp to Remove Items from List by passing filters.cs @@ -0,0 +1,35 @@ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +class LinqExercise19 +{ + static void Main(string[] args) + { + List listOfString = new List(); + listOfString.Add("m"); + listOfString.Add("n"); + listOfString.Add("o"); + listOfString.Add("p"); + listOfString.Add("q"); + Console.Write("\nLINQ : Remove Items from List by passing filters : "); + Console.Write("\n--------------------------------------------------\n"); + var _result1 = from y in listOfString + select y; + Console.Write("Here is the list of items : \n"); + foreach(var tchar in _result1) + { + Console.WriteLine("Char: {0} ", tchar); + } + listOfString.RemoveAll(en => en == "q"); + var _result = from z in listOfString + select z; + Console.Write("\nHere is the list after removing item 'q' from the list : \n"); + foreach(var rChar in _result) + { + Console.WriteLine("Char: {0} ", rChar); + } + Console.ReadLine(); + } +} \ No newline at end of file diff --git a/c-sharp/Linq/C# Sharp to Remove Items from List by passing the item index.cs b/c-sharp/Linq/C# Sharp to Remove Items from List by passing the item index.cs new file mode 100644 index 0000000..568ae99 --- /dev/null +++ b/c-sharp/Linq/C# Sharp to Remove Items from List by passing the item index.cs @@ -0,0 +1,35 @@ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +class LinqExercise20 +{ + static void Main(string[] args) + { + List listOfString = new List(); + listOfString.Add("m"); + listOfString.Add("n"); + listOfString.Add("o"); + listOfString.Add("p"); + listOfString.Add("q"); + Console.Write("\nLINQ : Remove Items from List by passing item index : "); + Console.Write("\n--------------------------------------------------\n"); + var _result1 = from y in listOfString + select y; + Console.Write("Here is the list of items : \n"); + foreach(var tchar in _result1) + { + Console.WriteLine("Char: {0} ", tchar); + } + listOfString.RemoveAt(3); + var _result = from z in listOfString + select z; + Console.Write("\nHere is the list after removing item index 3 from the list : \n"); + foreach(var rChar in _result) + { + Console.WriteLine("Char: {0} ", rChar); + } + Console.ReadLine(); + } +} \ No newline at end of file diff --git a/c-sharp/Linq/C# Sharp to Remove Items from List using remove function by passing object.cs b/c-sharp/Linq/C# Sharp to Remove Items from List using remove function by passing object.cs new file mode 100644 index 0000000..539e6b3 --- /dev/null +++ b/c-sharp/Linq/C# Sharp to Remove Items from List using remove function by passing object.cs @@ -0,0 +1,36 @@ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +class LinqExercise17 +{ + static void Main(string[] args) + { + List listOfString = new List(); + listOfString.Add("m"); + listOfString.Add("n"); + listOfString.Add("o"); + listOfString.Add("p"); + listOfString.Add("q"); + Console.Write("\nLINQ : Remove Items from List using remove function : "); + Console.Write("\n----------------------------------------------------\n"); + var _result1 = from y in listOfString + select y; + Console.Write("Here is the list of items : \n"); + foreach(var tchar in _result1) + { + Console.WriteLine("Char: {0} ", tchar); + } + string newstr = listOfString.FirstOrDefault(en => en == "o"); + listOfString.Remove(newstr); + var _result = from z in listOfString + select z; + Console.Write("\nHere is the list after removing the item 'o' from the list : \n"); + foreach(var rChar in _result) + { + Console.WriteLine("Char: {0} ", rChar); + } + Console.ReadLine(); + } +} \ No newline at end of file diff --git a/c-sharp/Linq/C# Sharp to convert a string array to a string.cs b/c-sharp/Linq/C# Sharp to convert a string array to a string.cs new file mode 100644 index 0000000..5fb8c44 --- /dev/null +++ b/c-sharp/Linq/C# Sharp to convert a string array to a string.cs @@ -0,0 +1,30 @@ +using System; +using System.Linq; +using System.Collections.Generic; + +class LinqExercise13 +{ + static void Main(string[] args) + { + string[] arr1; + int n,i; + Console.Write("\nLINQ : Convert a string array to a string : "); + Console.Write("\n------------------------------------------\n"); + Console.Write("Input number of strings to store in the array :"); + n= Convert.ToInt32(Console.ReadLine()); + arr1=new string[n]; + Console.Write("Input {0} strings for the array :\n",n); + for(i=0; i s.ToString()) + .ToArray()); + Console.Write("\nHere is the string below created with elements of the above array :\n\n"); + Console.WriteLine(newstring); + Console.Write("\n"); + Console.ReadLine(); + } +} \ No newline at end of file diff --git a/c-sharp/Linq/C# Sharp to create a list of numbers and display the numbers greater than 80 as output.cs b/c-sharp/Linq/C# Sharp to create a list of numbers and display the numbers greater than 80 as output.cs new file mode 100644 index 0000000..46b7e2e --- /dev/null +++ b/c-sharp/Linq/C# Sharp to create a list of numbers and display the numbers greater than 80 as output.cs @@ -0,0 +1,34 @@ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +class LinqExercise9 +{ + static void Main(string[] args) + { + int i=0; + List templist = new List(); + templist.Add(55); + templist.Add(200); + templist.Add(740); + templist.Add(76); + templist.Add(230); + templist.Add(482); + templist.Add(95); + Console.Write("\nLINQ : Create a list of numbers and display the numbers greater than 80 : "); + Console.Write("\n-------------------------------------------------------------------------\n"); + Console.WriteLine("\nThe members of the list are : "); + foreach (var lstnum in templist) + { + Console.Write(lstnum+" "); + } + List FilterList = templist.FindAll(x => x > 80 ? true : false); + Console.WriteLine("\n\nThe numbers greater than 80 are : "); + foreach (var num in FilterList) + { + Console.WriteLine(num); + } + Console.ReadLine(); + } +} \ No newline at end of file diff --git a/c-sharp/Linq/C# Sharp to display numbers, multiplication of number with frequency and the frequency of number of giving array.cs b/c-sharp/Linq/C# Sharp to display numbers, multiplication of number with frequency and the frequency of number of giving array.cs new file mode 100644 index 0000000..d081bf7 --- /dev/null +++ b/c-sharp/Linq/C# Sharp to display numbers, multiplication of number with frequency and the frequency of number of giving array.cs @@ -0,0 +1,25 @@ +using System; +using System.Linq; +using System.Collections.Generic; + +class LinqExercise7 +{ + static void Main(string[] args) + { + int[] nums = new int[] { 5, 1, 9, 2, 3, 7, 4, 5, 6, 8, 7, 6, 3, 4, 5, 2 }; + Console.Write("\nLINQ : Display numbers, number*frequency and frequency : "); + Console.Write("\n-------------------------------------------------------\n"); + Console.Write("The numbers in the array are : \n"); + Console.Write(" 5, 1, 9, 2, 3, 7, 4, 5, 6, 8, 7, 6, 3, 4, 5, 2 \n\n"); + var m = from x in nums + group x by x into y + select y; + Console.Write("Number"+"\t"+"Number*Frequency"+"\t"+"Frequency"+"\n"); + Console.Write("------------------------------------------------\n"); + foreach (var arrEle in m) + { + Console.WriteLine(arrEle.Key + "\t" + arrEle.Sum()+"\t\t\t"+arrEle.Count()); + } + Console.WriteLine(); + } +} \ No newline at end of file diff --git a/c-sharp/Linq/C# Sharp to display the characters and frequency of character from giving string.cs b/c-sharp/Linq/C# Sharp to display the characters and frequency of character from giving string.cs new file mode 100644 index 0000000..b51d9df --- /dev/null +++ b/c-sharp/Linq/C# Sharp to display the characters and frequency of character from giving string.cs @@ -0,0 +1,24 @@ +using System; +using System.Linq; +using System.Collections.Generic; + +class LinqExercise5 +{ + static void Main(string[] args) + { + string str; + Console.Write("\nLINQ : Display the characters and frequency of character from giving string : "); + Console.Write("\n----------------------------------------------------------------------------\n"); + Console.Write("Input the string : "); + str= Console.ReadLine(); + Console.Write("\n"); + var FreQ = from x in str + group x by x into y + select y; + Console.Write("The frequency of the characters are :\n"); + foreach(var ArrEle in FreQ) + { + Console.WriteLine("Character "+ArrEle.Key + ": " + ArrEle.Count()+" times"); + } + } +} \ No newline at end of file diff --git a/c-sharp/Linq/C# Sharp to display the name of the days of a week.cs b/c-sharp/Linq/C# Sharp to display the name of the days of a week.cs new file mode 100644 index 0000000..5cbed89 --- /dev/null +++ b/c-sharp/Linq/C# Sharp to display the name of the days of a week.cs @@ -0,0 +1,21 @@ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +class LinqExercise6 +{ + static void Main(string[] args) + { + string[] dayWeek = { "Sunday", "Monday", "Tuesday", "Wednesday", "Thursday", "Friday", "Saturday" }; + Console.Write("\nLINQ : Display the name of the days of a week : "); + Console.Write("\n------------------------------------------------\n"); + var days = from WeekDay in dayWeek + select WeekDay; + foreach (var WeekDay in days) + { + Console.WriteLine(WeekDay); + } + Console.WriteLine(); + } +} \ No newline at end of file diff --git a/c-sharp/Linq/C# Sharp to display the number and frequency of number from given array.cs b/c-sharp/Linq/C# Sharp to display the number and frequency of number from given array.cs new file mode 100644 index 0000000..7d9dfcc --- /dev/null +++ b/c-sharp/Linq/C# Sharp to display the number and frequency of number from given array.cs @@ -0,0 +1,24 @@ +using System; +using System.Linq; +using System.Collections.Generic; + +class LinqExercise4 +{ + static void Main(string[] args) + { + int[] arr1 = new int[] { 5, 9, 1, 2, 3, 7, 5, 6, 7, 3, 7, 6, 8, 5, 4, 9, 6, 2 }; + Console.Write("\nLINQ : Display the number and frequency of number from given array : \n"); + Console.Write("---------------------------------------------------------------------\n"); + Console.Write("The numbers in the array are : \n"); + Console.Write(" 5, 9, 1, 2, 3, 7, 5, 6, 7, 3, 7, 6, 8, 5, 4, 9, 6, 2\n"); + var n = from x in arr1 + group x by x into y + select y; + Console.WriteLine("\nThe number and the Frequency are : \n"); + foreach (var arrNo in n) + { + Console.WriteLine("Number "+arrNo.Key + " appears " + arrNo.Count()+" times"); + } + Console.WriteLine("\n"); + } +} \ No newline at end of file diff --git a/c-sharp/Linq/C# Sharp to display the top nth records.cs b/c-sharp/Linq/C# Sharp to display the top nth records.cs new file mode 100644 index 0000000..a1eedfe --- /dev/null +++ b/c-sharp/Linq/C# Sharp to display the top nth records.cs @@ -0,0 +1,37 @@ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + + +class LinqExercise11 +{ + static void Main(string[] args) + { + List templist = new List(); + templist.Add(5); + templist.Add(7); + templist.Add(13); + templist.Add(24); + templist.Add(6); + templist.Add(9); + templist.Add(8); + templist.Add(7); + Console.Write("\nLINQ : Display top nth records from the list : "); + Console.Write("\n----------------------------------------------\n"); + Console.WriteLine("\nThe members of the list are : "); + foreach (var lstnum in templist) + { + Console.WriteLine(lstnum+" "); + } + Console.Write("How many records you want to display ? : "); + int n= Convert.ToInt32(Console.ReadLine()); + templist.Sort(); + templist.Reverse(); + Console.Write("The top {0} records from the list are : \n",n); + foreach (int topn in templist.Take(n)) + { + Console.WriteLine(topn); + } + } +} \ No newline at end of file diff --git a/c-sharp/Linq/C# Sharp to find the +ve numbers from a list of numbers using two where conditions in LINQ Query.cs b/c-sharp/Linq/C# Sharp to find the +ve numbers from a list of numbers using two where conditions in LINQ Query.cs new file mode 100644 index 0000000..f044f04 --- /dev/null +++ b/c-sharp/Linq/C# Sharp to find the +ve numbers from a list of numbers using two where conditions in LINQ Query.cs @@ -0,0 +1,26 @@ +using System; +using System.Linq; + +class LinqExercise2 +{ + static void Main() + { + int[] n1 = + { + 1, 3, -2, -4, -7, -3, -8, 12, 19, 6, 9, 10, 14 + }; + Console.Write("\nLINQ : Using multiple WHERE clause to find the +ve numbers within the list : "); + Console.Write("\n-----------------------------------------------------------------------------"); + var nQuery = + from VrNum in n1 + where VrNum > 0 + where VrNum < 12 + select VrNum; + Console.Write("\nThe numbers within the range of 1 to 11 are : \n"); + foreach(var VrNum in nQuery) + { + Console.Write("{0} ", VrNum); + } + Console.Write("\n\n"); + } +} \ No newline at end of file diff --git a/c-sharp/Linq/C# Sharp to find the n-th Maximum grade point achieved by the students from the list of students.cs b/c-sharp/Linq/C# Sharp to find the n-th Maximum grade point achieved by the students from the list of students.cs new file mode 100644 index 0000000..474585d --- /dev/null +++ b/c-sharp/Linq/C# Sharp to find the n-th Maximum grade point achieved by the students from the list of students.cs @@ -0,0 +1,50 @@ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +public class Students +{ + public string StuName { get; set; } + public int GrPoint { get; set; } + public int StuId { get; set; } + + public List GtStuRec() + { + List stulist = new List(); + stulist.Add(new Students { StuId = 1, StuName = " Joseph ", GrPoint = 800 }); + stulist.Add(new Students { StuId = 2, StuName = "Alex", GrPoint = 458 }); + stulist.Add(new Students { StuId = 3, StuName = "Harris", GrPoint = 900 }); + stulist.Add(new Students { StuId = 4, StuName = "Taylor", GrPoint = 900 }); + stulist.Add(new Students { StuId = 5, StuName = "Smith", GrPoint = 458 }); + stulist.Add(new Students { StuId = 6, StuName = "Natasa", GrPoint = 700 }); + stulist.Add(new Students { StuId = 7, StuName = "David", GrPoint = 750 }); + stulist.Add(new Students { StuId = 8, StuName = "Harry", GrPoint = 700 }); + stulist.Add(new Students { StuId = 9, StuName = "Nicolash", GrPoint = 597 }); + stulist.Add(new Students { StuId = 10, StuName = "Jenny", GrPoint = 750 }); + return stulist; + } +} +class LinqExercise14 +{ + static void Main(string[] args) + { + Students e= new Students(); + Console.Write("\nLINQ : Find the nth Maximum Grade Point achieved by the students from the list of student : "); + Console.Write("\n------------------------------------------------------------------------------------------\n"); + Console.Write("Which maximum grade point(1st, 2nd, 3rd, ...) you want to find : "); + int grPointRank = Convert.ToInt32(Console.ReadLine()); + Console.Write("\n"); + var stulist = e.GtStuRec(); + var students = (from stuMast in stulist + group stuMast by stuMast.GrPoint into g + orderby g.Key descending + select new + { + StuRecord = g.ToList() + }).ToList(); + students[grPointRank - 1].StuRecord + .ForEach(i => Console.WriteLine(" Id : {0}, Name : {1}, achieved Grade Point : {2}",i.StuId, i.StuName, i.GrPoint)); + Console.ReadKey(); + } +} \ No newline at end of file diff --git a/c-sharp/Linq/C# Sharp to find the number of an array and the square of each number which is more than 20.cs b/c-sharp/Linq/C# Sharp to find the number of an array and the square of each number which is more than 20.cs new file mode 100644 index 0000000..c5fc8e8 --- /dev/null +++ b/c-sharp/Linq/C# Sharp to find the number of an array and the square of each number which is more than 20.cs @@ -0,0 +1,21 @@ +using System; +using System.Linq; +using System.Collections.Generic; + +class LinqExercise3 +{ + static void Main(string[] args) + { + // code from DevCurry.com + var arr1 = new[] { 3, 9, 2, 8, 6, 5 }; + Console.Write("\nLINQ : Find the number and its square of an array which is more than 20 : "); + Console.Write("\n------------------------------------------------------------------------\n"); + var sqNo = from int Number in arr1 + let SqrNo = Number * Number + where SqrNo > 20 + select new { Number, SqrNo }; + foreach (var a in sqNo) + Console.WriteLine(a); + Console.ReadLine(); + } +} \ No newline at end of file diff --git a/c-sharp/Linq/C# Sharp to find the string which starts and ends with a specific character.cs b/c-sharp/Linq/C# Sharp to find the string which starts and ends with a specific character.cs new file mode 100644 index 0000000..2334575 --- /dev/null +++ b/c-sharp/Linq/C# Sharp to find the string which starts and ends with a specific character.cs @@ -0,0 +1,37 @@ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + + +class LinqExercise8 +{ + static void Main(string[] args) + { + string chst,chen; + char ch; + string[] cities = + { + "ROME","LONDON","NAIROBI","CALIFORNIA","ZURICH","NEW DELHI","AMSTERDAM","ABU DHABI", "PARIS" + }; + Console.Write("\nLINQ : Find the string which starts and ends with a specific character : "); + Console.Write("\n-----------------------------------------------------------------------\n"); + Console.Write("\nThe cities are : 'ROME','LONDON','NAIROBI','CALIFORNIA','ZURICH','NEW DELHI','AMSTERDAM','ABU DHABI','PARIS' \n"); + Console.Write("\nInput starting character for the string : "); + ch = (char)Console.Read(); + chst=ch.ToString(); + Console.Write("\nInput ending character for the string : "); + ch = (char)Console.Read(); + chen=ch.ToString(); + var _result = from x in cities + where x.StartsWith(chst) + where x.EndsWith(chen) + select x; + Console.Write("\n\n"); + foreach(var city in _result) + { + Console.Write("The city starting with {0} and ending with {1} is : {2} \n", chst,chen,city); + } + Console.ReadLine(); + } +} \ No newline at end of file diff --git a/c-sharp/Linq/C# Sharp to find the strings for a specific minimum length.cs b/c-sharp/Linq/C# Sharp to find the strings for a specific minimum length.cs new file mode 100644 index 0000000..6a26d3f --- /dev/null +++ b/c-sharp/Linq/C# Sharp to find the strings for a specific minimum length.cs @@ -0,0 +1,33 @@ +using System; +using System.Collections.Generic; +using System.Linq; + +class LinqExercise22 +{ + static void Main(string[] args) + { + string[] arr1; + int n,i,ctr; + Console.Write("\nLINQ : Find the strings for a specific minimum length : "); + Console.Write("\n------------------------------------------------------\n"); + Console.Write("Input number of strings to store in the array :"); + n= Convert.ToInt32(Console.ReadLine()); + arr1 =new string[n]; + Console.Write("\nInput {0} strings for the array :\n",n); + for(i=0; i objNew = from m in arr1 + where m.Length >= ctr + orderby m + select m; + Console.Write("\nThe items of minimum {0} characters are : \n",ctr); + foreach (string z in objNew) + Console.WriteLine("Item: {0}", z); + Console.ReadLine(); + } +} \ No newline at end of file diff --git a/c-sharp/Linq/C# Sharp to find the uppercase words in a string.cs b/c-sharp/Linq/C# Sharp to find the uppercase words in a string.cs new file mode 100644 index 0000000..b33beff --- /dev/null +++ b/c-sharp/Linq/C# Sharp to find the uppercase words in a string.cs @@ -0,0 +1,30 @@ +using System; +using System.Linq; +using System.Collections.Generic; + +class LinqExercise12 +{ + static void Main(string[] args) + { + Console.Write("\nLINQ : Find the uppercase words in a string : "); + Console.Write("\n----------------------------------------------\n"); + string strNew; + Console.Write("Input the string : "); + strNew= Console.ReadLine(); + var ucWord = WordFilt(strNew); + Console.Write("\nThe UPPER CASE words are :\n "); + foreach (string strRet in ucWord) + { + Console.WriteLine(strRet); + } + Console.ReadLine(); + } + + static IEnumerable WordFilt(string mystr) + { + var upWord = mystr.Split(' ') + .Where(x => String.Equals(x, x.ToUpper(), + StringComparison.Ordinal)); + return upWord; + } +} \ No newline at end of file diff --git a/c-sharp/Linq/C# Sharp to generate a Cartesian Product of three sets.cs b/c-sharp/Linq/C# Sharp to generate a Cartesian Product of three sets.cs new file mode 100644 index 0000000..6c5cd23 --- /dev/null +++ b/c-sharp/Linq/C# Sharp to generate a Cartesian Product of three sets.cs @@ -0,0 +1,25 @@ +using System; +using System.Linq; +using System.Collections.Generic; + +class LinqExercise24 +{ + public static void Main(string[] args) + { + char[] charset1 = { 'X', 'Y', 'Z' }; + int[] numset1 = { 1, 2, 3 }; + string[] colorset1 = { "Green", "Orange" }; + Console.Write("\nLINQ : Generate a Cartesian Product of three sets : "); + Console.Write("\n----------------------------------------------------\n"); + var cartesianProduct = from letter in charset1 + from number in numset1 + from colour in colorset1 + select new { letter, number, colour }; + Console.Write("The Cartesian Product are : \n"); + foreach (var ProductList in cartesianProduct) + { + Console.WriteLine(ProductList); + } + Console.ReadLine(); + } +} \ No newline at end of file diff --git a/c-sharp/Linq/C# Sharp to generate a Cartesian Product of two sets.cs b/c-sharp/Linq/C# Sharp to generate a Cartesian Product of two sets.cs new file mode 100644 index 0000000..83464b4 --- /dev/null +++ b/c-sharp/Linq/C# Sharp to generate a Cartesian Product of two sets.cs @@ -0,0 +1,23 @@ +using System; +using System.Linq; +using System.Collections.Generic; + +class LinqExercise23 +{ + public static void Main(string[] args) + { + char[] charset1 = { 'X', 'Y', 'Z' }; + int[] numset1 = { 1, 2, 3, 4 }; + Console.Write("\nLINQ : Generate a Cartesian Product of two sets : "); + Console.Write("\n------------------------------------------------\n"); + var cartesianProduct = from letterList in charset1 + from numberList in numset1 + select new { letterList, numberList }; + Console.Write("The Cartesian Product are : \n"); + foreach (var productItem in cartesianProduct) + { + Console.WriteLine(productItem); + } + Console.ReadLine(); + } +} \ No newline at end of file diff --git a/c-sharp/Linq/C# Sharp to generate an Inner Join between two data sets.cs b/c-sharp/Linq/C# Sharp to generate an Inner Join between two data sets.cs new file mode 100644 index 0000000..071a156 --- /dev/null +++ b/c-sharp/Linq/C# Sharp to generate an Inner Join between two data sets.cs @@ -0,0 +1,77 @@ +using System; +using System.Linq; +using System.Collections.Generic; + +class LinqExercise25 +{ + static void Main(string[] args) + { + List itemlist = new List + { + new Item_mast { ItemId = 1, ItemDes = "Biscuit " }, + new Item_mast { ItemId = 2, ItemDes = "Chocolate" }, + new Item_mast { ItemId = 3, ItemDes = "Butter " }, + new Item_mast { ItemId = 4, ItemDes = "Brade " }, + new Item_mast { ItemId = 5, ItemDes = "Honey " } + }; + List purchlist = new List + { + new Purchase { InvNo=100, ItemId = 3, PurQty = 800 }, + new Purchase { InvNo=101, ItemId = 2, PurQty = 650 }, + new Purchase { InvNo=102, ItemId = 3, PurQty = 900 }, + new Purchase { InvNo=103, ItemId = 4, PurQty = 700 }, + new Purchase { InvNo=104, ItemId = 3, PurQty = 900 }, + new Purchase { InvNo=105, ItemId = 4, PurQty = 650 }, + new Purchase { InvNo=106, ItemId = 1, PurQty = 458 } + }; + Console.Write("\nLINQ : Generate an Inner Join between two data sets : "); + Console.Write("\n--------------------------------------------------\n"); + Console.Write("Here is the Item_mast List : "); + Console.Write("\n-------------------------\n"); + foreach (var item in itemlist) + { + Console.WriteLine( + "Item Id: {0}, Description: {1}", + item.ItemId, + item.ItemDes); + } + Console.Write("\nHere is the Purchase List : "); + Console.Write("\n--------------------------\n"); + foreach (var item in purchlist) + { + Console.WriteLine( + "Invoice No: {0}, Item Id : {1}, Quantity : {2}", + item.InvNo, + item.ItemId, + item.PurQty); + } + Console.Write("\nHere is the list after joining : \n\n"); + var innerJoin = from e in itemlist + join d in purchlist on e.ItemId equals d.ItemId + select new + { + itid = e.ItemId, + itdes = e.ItemDes, + prqty = d.PurQty + }; + Console.WriteLine("Item ID\t\tItem Name\tPurchase Quantity"); + Console.WriteLine("-------------------------------------------------------"); + foreach (var data in innerJoin) + { + Console.WriteLine(data.itid + "\t\t" + data.itdes + "\t\t" + data.prqty); + } + Console.ReadLine(); + } +} +public class Item_mast +{ + public int ItemId { get; set; } + public string ItemDes { get; set; } +} + +public class Purchase +{ + public int InvNo { get; set; } + public int ItemId { get; set; } + public int PurQty { get; set; } +} \ No newline at end of file diff --git a/c-sharp/Linq/C# Sharp to remove a range of items from a list by passing the start index and number of elements to remove.cs b/c-sharp/Linq/C# Sharp to remove a range of items from a list by passing the start index and number of elements to remove.cs new file mode 100644 index 0000000..d7b4ff3 --- /dev/null +++ b/c-sharp/Linq/C# Sharp to remove a range of items from a list by passing the start index and number of elements to remove.cs @@ -0,0 +1,35 @@ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +class LinqExercise21 +{ + static void Main(string[] args) + { + List listOfString = new List(); + listOfString.Add("m"); + listOfString.Add("n"); + listOfString.Add("o"); + listOfString.Add("p"); + listOfString.Add("q"); + Console.Write("\nLINQ : Remove range of items from list by passing start index and number of elements to delete : "); + Console.Write("\n------------------------------------------------------------------------------------------------\n"); + var _result1 = from y in listOfString + select y; + Console.Write("Here is the list of items : \n"); + foreach(var tchar in _result1) + { + Console.WriteLine("Char: {0} ", tchar); + } + listOfString.RemoveRange(1, 3); + var _result = from z in listOfString + select z; + Console.Write("\nHere is the list after removing the three items starting from the item index 1 from the list : \n"); + foreach(var rChar in _result) + { + Console.WriteLine("Char: {0} ", rChar); + } + Console.ReadLine(); + } +} \ No newline at end of file diff --git a/c-sharp/Linq/C# Sharp to shows how the three parts of a query operation execute.cs b/c-sharp/Linq/C# Sharp to shows how the three parts of a query operation execute.cs new file mode 100644 index 0000000..6698adf --- /dev/null +++ b/c-sharp/Linq/C# Sharp to shows how the three parts of a query operation execute.cs @@ -0,0 +1,26 @@ +using System; +using System.Linq; + +class LinqExercise1 +{ + static void Main() + { + // The first part is Data source. + int[] n1 = new int[10] { 0, 1, 2, 3, 4, 5, 6, 7, 8, 9 }; + Console.Write("\nBasic structure of LINQ : "); + Console.Write("\n---------------------------"); + // The second part is Query creation. + // nQuery is an IEnumerable + var nQuery = + from VrNum in n1 + where (VrNum % 2) == 0 + select VrNum; + // The third part is Query execution. + Console.Write("\nThe numbers which produce the remainder 0 after divided by 2 are : \n"); + foreach (int VrNum in nQuery) + { + Console.Write("{0} ", VrNum); + } + Console.Write("\n\n"); + } +} \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Add 2 Complex Numbers.cs b/c-sharp/Mathematics/C# Program to Add 2 Complex Numbers.cs new file mode 100644 index 0000000..48a6b8f --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Add 2 Complex Numbers.cs @@ -0,0 +1,46 @@ +/* + * C# Program to Add 2 Complex Numbers + */ +using System; +public struct Complex +{ + public int real; + public int imaginary; + + public Complex(int real, int imaginary) + { + this.real = real; + this.imaginary = imaginary; + } + + + public static Complex operator +(Complex c1, Complex c2) + { + return new Complex(c1.real + c2.real, c1.imaginary + c2.imaginary); + } + + + public override string ToString() + { + return (String.Format("{0} + {1}i", real, imaginary)); + } +} + +class TestComplex +{ + static void Main() + { + Complex num1 = new Complex(2, 3); + Complex num2 = new Complex(3, 4); + Complex sum = num1 + num2; + Console.WriteLine("First Complex Number : {0}", num1); + Console.WriteLine("Second Complex Number : {0}", num2); + Console.WriteLine("The Sum of the Two Numbers : {0}", sum); + Console.ReadLine(); + } +} + +/* +First Complex Number : 2+3i +Second Complex Number : 3+4i +The Sum of the Two Numbers : 5+7i \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Add Two Dates.cs b/c-sharp/Mathematics/C# Program to Add Two Dates.cs new file mode 100644 index 0000000..dad0d40 --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Add Two Dates.cs @@ -0,0 +1,24 @@ +/* + * C# Program to Add Two Dates + */ +using System; +namespace DateAndTime +{ +class Program +{ + static int Main() + { + DateTime SDate = new DateTime(2010, 10, 7); + Console.WriteLine("Starting Date : {0}", SDate); + DateTime EDate = startDate.AddDays(10); + Console.WriteLine("Ending Date : {0}\n", EDate); + Console.ReadLine(); + return 0; + } +} +} + +/* + +Starting Date : 10/7/2010 12:00:00 AM +Ending Date : 10/17/2010 12:00:00 AM \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Calculate Area and Volume of a Cone.cs b/c-sharp/Mathematics/C# Program to Calculate Area and Volume of a Cone.cs new file mode 100644 index 0000000..5e5b8c5 --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Calculate Area and Volume of a Cone.cs @@ -0,0 +1,26 @@ +/* + * C# Program to Calculate Area and Volume of a Cone + */ +using System; +using System.IO; +class program +{ + public static void Main() + { + double r, h, surface_area, volume; + double PI = 3.14; + Console.WriteLine("Enter the Radius and Height of a cone : "); + r = Convert.ToDouble(Console.ReadLine()); + h = Convert.ToDouble(Console.ReadLine()); + surface_area = PI * r * (r + Math.Sqrt(r * r + h * h)); + volume = (1.0 / 3) * PI * r * r * h; + Console.WriteLine("Surface Area of cone is : {0} ", surface_area); + Console.WriteLine("Volume of Cone is : {0}", volume); + Console.Read(); + } +} + +/* +Enter the Radius and Height of a cone : 3 3 +Surface Area of cone is : 68.2256752726637 +Volume of Cone is : 28.26 \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Calculate Compound Interest.cs b/c-sharp/Mathematics/C# Program to Calculate Compound Interest.cs new file mode 100644 index 0000000..6586e9a --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Calculate Compound Interest.cs @@ -0,0 +1,36 @@ +/* + * C# Program to Calculate Compound Interest + */ +using System; +namespace compund +{ +class compound +{ + static void Main(string[] args) + { + double Total = 0, interestRate, years, annualCompound, Amount; + Console.Write("Enter the Initial Amount : "); + Amount = Convert.ToDouble(Console.ReadLine()); + Console.Write("Enter the Rate of Interest : "); + interestRate = Convert.ToDouble(Console.ReadLine()) / 100; + Console.Write("Enter the Number of Years : "); + years = Convert.ToDouble(Console.ReadLine()); + Console.Write("Number of Times the Interest will be Compounded : "); + annualCompound = Convert.ToDouble(Console.ReadLine()); + for (int t = 1; t < years + 1; t++) + { + Total = Amount * Math.Pow((1 + interestRate / annualCompound), (annualCompound * t)); + Console.Write("Your Total for Year {0} " + + "is {1:F0}. \n", t, Total); + } + Console.ReadLine(); + } +} +} +/* +Enter the Initial Amount : 1000 +Enter the Rate of Interest : 2 +Enter the Number of Years : 2 +Number of Times the Interest will be Compounded : 2 +Your Total for Year 1 is : 1020 +Your Total for Year 2 is : 1041 \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Calculate Fractional Power.cs b/c-sharp/Mathematics/C# Program to Calculate Fractional Power.cs new file mode 100644 index 0000000..4003ba8 --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Calculate Fractional Power.cs @@ -0,0 +1,22 @@ +/* + * C# Program to Calculate Fractional Powers + */ +using System; +class Program +{ + static void Main() + { + double value1 = Math.Pow(2, 2.1); + double value2 = Math.Pow(Math.E, 2); + double value3 = Math.Pow(Math.PI, 1); + Console.WriteLine("Result : {0}", value1); + Console.WriteLine("Result : {0}", value2); + Console.WriteLine("Result : {0}", value3); + Console.ReadLine(); + } +} + +/* +Result : 4.28709385014517 +Result : 7.38905609893065 +Result : 3.14159265358979 \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Calculate Perimeter of Circle and Rectangle.cs b/c-sharp/Mathematics/C# Program to Calculate Perimeter of Circle and Rectangle.cs new file mode 100644 index 0000000..819ce34 --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Calculate Perimeter of Circle and Rectangle.cs @@ -0,0 +1,33 @@ +/* + * C# Program to Calculate Perimeter of Circle and Rectangle + */ +using System; +using System.IO; +class program +{ + public static void Main() + { + double l,b,r,per_rect,per_cir; + double PI = 3.14; + Console.WriteLine("Enter the Length and Breadth : "); + l = Convert.ToDouble(Console.ReadLine()); + b = Convert.ToDouble(Console.ReadLine()); + per_rect = 2 * (l + b); + Console.WriteLine("Enter the radius of the circle : "); + r = Convert.ToDouble(Console.ReadLine()); + per_cir = 2 * PI * r; + Console.WriteLine("Perimeter of Rectangle : {0}", per_rect); + Console.WriteLine("Perimeter of Circle : {0}", per_cir); + Console.Read(); + } +} + +/* + +Enter the Length and Breadth : +3 +2 +Enter the radius of the circle : +4 +Perimeter of Rectangle : 10 +Perimeter of Circle : 25.12 \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Calculate Period Duration.cs b/c-sharp/Mathematics/C# Program to Calculate Period Duration.cs new file mode 100644 index 0000000..ca9dc31 --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Calculate Period Duration.cs @@ -0,0 +1,38 @@ +/* + * C# Program to Calculate Period Duration + */ +using System; +class CompareDates +{ + + public static void Main() + { + DateTime today = DateTime.Now; + DateTime yesterday = today - new TimeSpan(1, 0, 0, 0); + DateTime tomorrow = today + new TimeSpan(1, 0, 0, 0); + Console.WriteLine("Yesterday was {0}", yesterday); + Console.WriteLine("Today is {0}", today); + Console.WriteLine("Tomorrow will be {0}", tomorrow); + Console.WriteLine("\nIs yesterday less than today? {0}.", + yesterday < today); + Console.WriteLine("Is today the same as tomorrow ? {0}.", + today == tomorrow); + TimeSpan totalTimespan = new TimeSpan(3, 5, 24, 17) + + new TimeSpan(1, 18, 35, 43); + Console.WriteLine( + "\nThe length of the period is {0} days {1} hours" + + " {2} minutes {3} seconds.", + totalTimespan.Days, totalTimespan.Hours, + totalTimespan.Minutes, totalTimespan.Seconds); + Console.ReadLine(); + } + +} + +/* +Yesterday was 09-06-2014 15:52:34 +Today is 10-06-2014 15:52:34 +Tomorrow will be 11-06-2014 15:52:34 +Is yesterday less than today? True. +Is today the same as tomorrow ? False. +The length of the period is 5 days 0 hours 0 minutes 0 seconds. \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Calculate Power of Three.cs b/c-sharp/Mathematics/C# Program to Calculate Power of Three.cs new file mode 100644 index 0000000..0251e89 --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Calculate Power of Three.cs @@ -0,0 +1,39 @@ +/* + * C# Program to Calculate Power of Three + */ + + +using System; + +class Program +{ + static void Main(string[] args) + { + new GeneratePowers().RaiseToPower + (5, // 4 values per table + 3); + Console.ReadLine();// power to raise each value + } +} + +public class GeneratePowers +{ + public void RaiseToPower(int maxIterations, int power) + { + Console.WriteLine("{0,8}{1,16}", + "Number", "Power of " + power); + for (int i = 1; i <= maxIterations; ++i) + { + Console.Write("{0,5}{1,15}\n", i, + Math.Pow(i, power)); + } + } +} + +/* + Number Power of 3 + 1 1 + 2 8 + 3 27 + 4 64 + 5 125 \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Calculate Simple Interest.cs b/c-sharp/Mathematics/C# Program to Calculate Simple Interest.cs new file mode 100644 index 0000000..7460641 --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Calculate Simple Interest.cs @@ -0,0 +1,30 @@ +/* + * C# Program to Calculate Simple Interest + */ +using System; +namespace Interest +{ +class Program +{ + static void Main(string[] args) + { + int year; + double princamt,rate, interest, total_amt; + Console.Write("Enter The Loan Amount : "); + princamt = Convert.ToDouble(Console.ReadLine()); + Console.Write("Enter The Number of Years : "); + year = Convert.ToInt16(Console.ReadLine()); + Console.Write("Enter the Rate Of Interest : "); + rate = Convert.ToDouble(Console.ReadLine()); + interest = princamt * year * rate / 100; + total_amt = princamt + interest; + Console.WriteLine("Total Amount : {0}", total_amt); + Console.ReadLine(); + } +} +} +/* +Enter the Loan Amount : 1000 +Enter the Number of Years : 3 +Enter the Rate of Interest : 2 +Total Amount : 1060 \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Calculate nPr.cs b/c-sharp/Mathematics/C# Program to Calculate nPr.cs new file mode 100644 index 0000000..93e2730 --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Calculate nPr.cs @@ -0,0 +1,42 @@ +/* + * C# Program to Calculate nPr + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +namespace ConsoleApplication40 +{ +class Program +{ + static void Main(string[] args) + { + int n, r, per, fact, fact1; + Console.WriteLine("Enter the Value of 'n' and 'r' to find the Permutation :"); + n = Convert.ToInt32(Console.ReadLine()); + r = Convert.ToInt32(Console.ReadLine()); + fact = n; + for (int i = n - 1; i >= 1; i--) + { + fact = fact * i; + } + int number; + number = n - r; + fact1 = number; + for (int i = number - 1; i >= 1; i--) + { + fact1 = fact1 * i; + } + per = fact / fact1; + Console.WriteLine("Permutation : {0}",per); + Console.ReadLine(); + } +} +} + +/* +Enter the value of 'n' and 'r' to find the Permutation : +10 +5 +Permutation : 30240 \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Calculate the Distance Travelled by Reading Speed and Time.cs b/c-sharp/Mathematics/C# Program to Calculate the Distance Travelled by Reading Speed and Time.cs new file mode 100644 index 0000000..c4a9c76 --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Calculate the Distance Travelled by Reading Speed and Time.cs @@ -0,0 +1,23 @@ +/* + * C# Program to Calculate the Distance Travelled by Reading Speed and Time + */ +using System; +class program +{ + public static void Main() + { + int speed, distance, time; + Console.WriteLine("Enter the Speed(km/hr) : "); + speed = Convert.ToInt32(Console.ReadLine()); + Console.WriteLine("Enter the Time(hrs) : "); + time = Convert.ToInt32(Console.ReadLine()); + distance = speed * time; + Console.WriteLine("Distance Travelled (kms) : " + distance); + Console.ReadLine(); + } +} + +/* +Enter the Speed(km/hr) : 5 +Enter the Time(hrs) : 4 +Distance Travelled (kms) : 20 \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Calculate the Power Exponent Value.cs b/c-sharp/Mathematics/C# Program to Calculate the Power Exponent Value.cs new file mode 100644 index 0000000..d7060a0 --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Calculate the Power Exponent Value.cs @@ -0,0 +1,23 @@ +/* + * C# Program to Calculate the power exponent value + */ +using System; +class Program +{ + static void Main() + { + double m, n; + Console.WriteLine("Enter the Number : "); + m = double.Parse(Console.ReadLine()); + Console.WriteLine("Enter the Exponent : "); + n = double.Parse(Console.ReadLine()); + double value1 = Math.Pow(m, n); + Console.WriteLine("Result : {0}", value1); + Console.ReadLine(); + } +} + +/* +Enter the Number : 2 +Enter the Exponent :3 +Result : 8 \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Calculate the Value of nCr.cs b/c-sharp/Mathematics/C# Program to Calculate the Value of nCr.cs new file mode 100644 index 0000000..d9cc3c4 --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Calculate the Value of nCr.cs @@ -0,0 +1,47 @@ +/* + * C# Program to Calculate the Value of nCr + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +namespace ConsoleApplication +{ +class Program +{ + static void Main(string[] args) + { + int n, r,per,fact,fact1,fact2; + Console.WriteLine("Enter the Value of 'n' and 'r' to find the Permutation :"); + n = Convert.ToInt32(Console.ReadLine()); + r = Convert.ToInt32(Console.ReadLine()); + fact = n; + for (int i = n - 1; i >= 1; i--) + { + fact = fact * i; + } + fact2 = r; + for (int i = r - 1; i >= 1; i--) + { + fact2 = fact2 * i; + } + int number; + number = n - r; + fact1 = number; + for (int i = number - 1; i >= 1; i--) + { + fact1 = fact1 * i; + } + fact1 = fact2 * fact1; + per = fact / fact1; + Console.WriteLine("Combination : {0}",per); + Console.ReadLine(); + } +} +} + +/* +Enter the value of 'n' and 'r' to find the Permutation : +10 +5 +Combination : 252 \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Check Whether the Entered Number is a Amicable Number or Not.cs b/c-sharp/Mathematics/C# Program to Check Whether the Entered Number is a Amicable Number or Not.cs new file mode 100644 index 0000000..cdd7db5 --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Check Whether the Entered Number is a Amicable Number or Not.cs @@ -0,0 +1,52 @@ +/* + * C# Program Checks Whether the Entered Number is a Amicable Number or Not + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +namespace Program +{ +class Program +{ + public static void Main(String[] args) + { + int num1, num2, sum1 = 0, sum2 = 0, i; + Console.WriteLine("Enter First Number : "); + num1 = int.Parse(Console.ReadLine()); + Console.WriteLine("Enter Second Number : "); + num2 = int.Parse(Console.ReadLine()); + for (i = 1; i < num1; i++) + { + if (num1 % i == 0) + { + sum1 = sum1 + i; + } + } + for (i = 1; i < num2; i++) + { + if (num2 % i == 0) + { + sum2 = sum2 + i; + } + } + if (num1 == sum2 && num2 == sum1) + { + Console.WriteLine("They are a Pair of Amicable Numbers"); + Console.ReadLine(); + } + else + { + Console.WriteLine("They are not Amicable Numbers"); + Console.ReadLine(); + } + } +} +} + +/* + +Enter First Number : 220 +Enter Second Number :284 +They are a Pair Of Amicable Numbers \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Check Whether the Entered Number is a Perfect Number or Not.cs b/c-sharp/Mathematics/C# Program to Check Whether the Entered Number is a Perfect Number or Not.cs new file mode 100644 index 0000000..9b26fe2 --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Check Whether the Entered Number is a Perfect Number or Not.cs @@ -0,0 +1,43 @@ +/* + * C# Program to Check Whether the Entered Number is a Perfect Number or Not + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +namespace Program +{ +class Program +{ + static void Main(string[] args) + { + int number,sum=0,n; + Console.Write("enter the Number"); + number = int.Parse(Console.ReadLine()); + n = number; + for (int i = 1; i < number; i++) + { + if (number % i == 0) + { + sum=sum + i; + } + } + if (sum == n) + { + Console.WriteLine("\n Entered number is a perfect number"); + Console.ReadLine(); + } + else + { + Console.WriteLine("\n Entered number is not a perfect number"); + Console.ReadLine(); + } + } +} +} + +/* + +Enter the Number : 6 +Entered Number is a Perfect Number \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Check Whether the Entered Number is an Armstrong Number or Not.cs b/c-sharp/Mathematics/C# Program to Check Whether the Entered Number is an Armstrong Number or Not.cs new file mode 100644 index 0000000..0e5ae69 --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Check Whether the Entered Number is an Armstrong Number or Not.cs @@ -0,0 +1,37 @@ +/* + * C# Program to Check Whether the Entered Number is an Armstrong Number or Not + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +namespace ConsoleApplication6 +{ +class Program +{ + static void Main(string[] args) + { + int number, remainder, sum = 0; + Console.Write("enter the Number"); + number = int.Parse(Console.ReadLine()); + for (int i = number; i > 0; i = i / 10) + { + remainder = i % 10; + sum = sum + remainder*remainder*remainder; + } + if (sum == number) + { + Console.Write("Entered Number is an Armstrong Number"); + } + else + Console.Write("Entered Number is not an Armstrong Number"); + Console.ReadLine(); + } +} +} + +/* + +Enter the Number : 371 +Entered Number is an Armstrong Number \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Check Whether the Given Number is a Prime number if so then Display its Largest Facor.cs b/c-sharp/Mathematics/C# Program to Check Whether the Given Number is a Prime number if so then Display its Largest Facor.cs new file mode 100644 index 0000000..7f26f7f --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Check Whether the Given Number is a Prime number if so then Display its Largest Facor.cs @@ -0,0 +1,39 @@ +/* + * C# Program to Check Whether the Given Number is a Prime number if so then + * Display its Largest Factor + */ +using System; +namespace example +{ +class prime +{ + public static void Main() + { + Console.Write("Enter a Number : "); + int num; + num = Convert.ToInt32(Console.ReadLine()); + int k; + k = 0; + for (int i = 1; i <= num; i++) + { + if (num % i == 0) + { + k++; + } + } + if (k == 2) + { + Console.WriteLine("Entered Number is a Prime Number and the Largest Factor is {0}",num); + } + else + { + Console.WriteLine("Not a Prime Number"); + } + Console.ReadLine(); + } +} +} + +/* +Enter a Number : 23 +Entered Number is a Prime Number and the Largest Factor is 23 \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Check the Edge Values in Power Function.cs b/c-sharp/Mathematics/C# Program to Check the Edge Values in Power Function.cs new file mode 100644 index 0000000..b0f1882 --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Check the Edge Values in Power Function.cs @@ -0,0 +1,28 @@ +/* + * C# Program to Check the Edge Values in Power Function + */ +using System; +class Program +{ + static void Main() + { + double value1 = Math.Pow(double.MinValue, double.MaxValue); + double value2 = Math.Pow(double.MinValue, 0); + double value3 = Math.Pow(double.NaN, 2); + double value4 = Math.Pow(double.PositiveInfinity, 2); + double value5 = Math.Pow(double.NegativeInfinity, 2); + Console.WriteLine("Result : {0}", value1); + Console.WriteLine("Result : {0}", value2); + Console.WriteLine("Result : {0}", value3); + Console.WriteLine("Result : {0}", value4); + Console.WriteLine("Result : {0}", value5); + Console.ReadLine(); + } +} + +/* +Result : Infinity +Result : 1 +Result : NaN +Result : Infinity +Result : Infinity \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Display Absolute value of a Number.cs b/c-sharp/Mathematics/C# Program to Display Absolute value of a Number.cs new file mode 100644 index 0000000..1a6e59a --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Display Absolute value of a Number.cs @@ -0,0 +1,32 @@ +/* + * C# Program to Display Absolute value of a Number + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +namespace example +{ +internal class Program +{ + private static void Main(string[] args) + { + int num; + Console.Write("Enter a number:"); + num = Convert.ToInt32(Console.ReadLine()); + if (num < 0) + { + num = num * -1; + } + Console.WriteLine("Absolute value : " + num); + Console.ReadLine(); + } +} +} + +/* + +Output: +Enter a number:-50 +Absolute value : 50 \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Display Floyd’s Triangle with an Numeric Mode.cs b/c-sharp/Mathematics/C# Program to Display Floyd’s Triangle with an Numeric Mode.cs new file mode 100644 index 0000000..7d07b93 --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Display Floyd’s Triangle with an Numeric Mode.cs @@ -0,0 +1,32 @@ +/* + * C# Program to Display Floyd's Triangle with an Numeric Mode + */ +using System; +class Program +{ + static void Main(string[] args) + { + int i, j, k = 1; + for (i = 1; i <= 10; i++) + { + for (j = 1; j < i + 1; j++) + { + Console.Write(k++ + " "); + } + Console.Write("\n"); + } + Console.ReadLine(); + } +} + +/* +1 +2 3 +4 5 6 +7 8 9 10 +11 12 13 14 15 +16 17 18 19 20 21 +22 23 24 25 26 27 28 +29 30 31 32 33 34 35 36 +37 38 39 40 41 42 43 44 45 +46 47 48 49 50 51 52 53 54 55 \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Display the Factors of the Entered Number.cs b/c-sharp/Mathematics/C# Program to Display the Factors of the Entered Number.cs new file mode 100644 index 0000000..0d5327c --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Display the Factors of the Entered Number.cs @@ -0,0 +1,37 @@ +/* + * C# Program to Display the Factors of the Entered Number + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +namespace Program +{ +class Program +{ + static void Main(string[] args) + { + int num, x; + Console.WriteLine("Enter the Number "); + num = int.Parse(Console.ReadLine()); + Console.WriteLine("The Factors are : "); + for (x = 1; x <= num; x++) + { + if (num % x == 0) + { + Console.WriteLine(x); + } + } + Console.ReadLine(); + } +} +} + +/* +Enter the Number : 27 +The Factors are : +1 +3 +9 +27 \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Find LCM.cs b/c-sharp/Mathematics/C# Program to Find LCM.cs new file mode 100644 index 0000000..5dc088b --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Find LCM.cs @@ -0,0 +1,43 @@ +/* + * C# Program to Find and Display the L.C.M of a Given Number + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +namespace ConsoleApplication9 +{ +class Program +{ + public static void Main(string[] args) + { + int num1, num2, x, y, lcm = 0; + Console.Write("Enter the First Number : "); + num1 = int.Parse(Console.ReadLine()); + Console.Write("Enter the Second Number : "); + num2 = int.Parse(Console.ReadLine()); + x = num1; + y = num2; + while (num1 != num2) + { + if (num1 > num2) + { + num1 = num1 - num2; + } + else + { + num2 = num2 - num1; + } + } + lcm = (x * y) / num1; + Console.Write("Least Common Multiple is : " + lcm); + Console.Read(); + } +} +} + +/* + +Enter the First Number : 2 +Enter the Second Number : 4 +Least Common Multiple : 4 \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Find Multiplication of two Binary Numbers.cs b/c-sharp/Mathematics/C# Program to Find Multiplication of two Binary Numbers.cs new file mode 100644 index 0000000..dda09ed --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Find Multiplication of two Binary Numbers.cs @@ -0,0 +1,62 @@ +/* + * C# Program to Find Multiplication of two Binary Numbers + */ +using System; +class program +{ + public static void Main() + { + int binary1, binary2, multiply = 0; + int digit, factor = 1; + prog pg = new prog(); + Console.WriteLine("Enter the first binary number: "); + binary1 = int.Parse(Console.ReadLine()); + Console.WriteLine("Enter the second binary number: "); + binary2 = int.Parse(Console.ReadLine()); + while (binary2 != 0) + { + digit = binary2 % 10; + if (digit == 1) + { + binary1 = binary1 * factor; + multiply = pg.binaryproduct(binary1, multiply); + } + else + { + binary1 = binary1 * factor; + binary2 = binary2 / 10; + factor = 10; + } + Console.WriteLine("Product of two binary numbers: {0}", multiply); + Console.ReadLine(); + } + } + class prog + { + public int binaryproduct(int binary1, int binary2) + { + int i = 0, remainder = 0; + int[] sum = new int[20]; + int binaryprod = 0; + while (binary1 != 0 || binary2 != 0) + { + sum[i++] =(binary1 % 10 + binary2 % 10 + remainder) % 2; + remainder =(binary1 % 10 + binary2 % 10 + remainder) / 2; + binary1 = binary1 / 10; + binary2 = binary2 / 10; + } + if (remainder != 0) + sum[i++] = remainder; + --i; + while (i >= 0) + binaryprod = binaryprod * 10 + sum[i--]; + return binaryprod; + } + } + + /* + /* + + Enter the first binary number : 1010 + Enter the second binary number : 1011 + Product of two binary numbers : 1101110 diff --git a/c-sharp/Mathematics/C# Program to Find Power of 2 using Bitwise Operator.cs b/c-sharp/Mathematics/C# Program to Find Power of 2 using Bitwise Operator.cs new file mode 100644 index 0000000..1826935 --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Find Power of 2 using Bitwise Operator.cs @@ -0,0 +1,29 @@ +/* + * C# Program to Find Power of 2 using Bitwise Operator + */ +using System; +using System.Collections.Generic; +using System.Globalization; +using System.Linq; +using System.Text; + +namespace example +{ +internal class Program +{ + private static void Main(string[] args) + { + int num; + Console.Write("Enter a number:"); + num = Convert.ToInt32(Console.ReadLine()); + bool result = ((num & -num) == num); + Console.WriteLine(result); + Console.ReadLine(); + } +} +} + +/* + +Enter a number:16 +True \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Find Roots of a Quadratic Equation.cs b/c-sharp/Mathematics/C# Program to Find Roots of a Quadratic Equation.cs new file mode 100644 index 0000000..17f2eb0 --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Find Roots of a Quadratic Equation.cs @@ -0,0 +1,86 @@ +/* + * C# Program to Find Roots of a Quadratic Equation + */ +using System; + +namespace example +{ +class Quadraticroots +{ + double a, b, c; + + public void read() + { + Console.WriteLine(" \n To find the roots of a quadratic equation of the form a*x*x + b*x + c = 0"); + Console.Write("\n Enter value for a : "); + a = double.Parse(Console.ReadLine()); + Console.Write("\n Enter value for b : "); + b = double.Parse(Console.ReadLine()); + Console.Write("\n Enter value for c : "); + c = double.Parse(Console.ReadLine()); + } + public void compute() + { + int m; + double r1, r2, d1; + d1 = b * b - 4 * a * c; + if (a == 0) + m = 1; + else if (d1 > 0) + m = 2; + else if (d1 == 0) + m = 3; + else + m = 4; + switch (m) + { + case 1: + Console.WriteLine("\n Not a Quadratic equation, Linear equation"); + Console.ReadLine(); + break; + case 2: + Console.WriteLine("\n Roots are Real and Distinct"); + r1 = (-b + Math.Sqrt(d1)) / (2 * a); + r2 = (-b - Math.Sqrt(d1)) / (2 * a); + Console.WriteLine("\n First root is {0:#.##}", r1); + Console.WriteLine("\n Second root is {0:#.##}", r2); + Console.ReadLine(); + break; + case 3: + Console.WriteLine("\n Roots are Real and Equal"); + r1 = r2 = (-b) / (2 * a); + Console.WriteLine("\n First root is {0:#.##}", r1); + Console.WriteLine("\n Second root is {0:#.##}", r2); + Console.ReadLine(); + break; + case 4: + Console.WriteLine("\n Roots are Imaginary"); + r1 = (-b) / (2 * a); + r2 = Math.Sqrt(-d1) / (2 * a); + Console.WriteLine("\n First root is {0:#.##} + i {1:#.##}", r1, r2); + Console.WriteLine("\n Second root is {0:#.##} - i {1:#.##}", r1, r2); + Console.ReadLine(); + break; + } + } +} + +class Roots +{ + public static void Main() + { + Quadraticroots qr = new Quadraticroots(); + qr.read(); + qr.compute(); + } +} +} + +/* + To find the roots of a quadratic equation of the form a*x*x + b*x + c = 0 + Enter value for a : 3.5 + Enter value for b : 2.5 + Enter value for c : 1.0 + Roots are Imaginary + First root is -.36 + i .4 + Second root is -.36 - i .4 \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Find Square Root of a Given Number.cs b/c-sharp/Mathematics/C# Program to Find Square Root of a Given Number.cs new file mode 100644 index 0000000..ac2e9e7 --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Find Square Root of a Given Number.cs @@ -0,0 +1,21 @@ +/* + * C# Program to Find Square Root of a Given Number + */ +using System; +using System.Text; +using System.Collections; +using System.Data; +namespace Cons +{ +public class squareroot +{ + public static void Main() + { + Console.WriteLine("Enter a Number : "); + int Number = Convert.ToInt16(Console.ReadLine()); + double SqrtNumber = Math.Sqrt(Number); + Console.WriteLine("Square root of {0} is: {1}", Number, SqrtNumber); + Console.ReadLine(); + } +} +} \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Find and Display the H.C.cs b/c-sharp/Mathematics/C# Program to Find and Display the H.C.cs new file mode 100644 index 0000000..ef3b93b --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Find and Display the H.C.cs @@ -0,0 +1,38 @@ +/* + * C# Program to Find and Display the H.C.F of a Given Number + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +namespace Program +{ +class Program +{ + public static void Main(string[] args) + { + int num1,num2,i; + int hcf =0; + Console.Write("\nEnter the First Number : "); + num1 = int.Parse(Console.ReadLine()); + Console.Write("\nEnter the Second Number : "); + num2 = int.Parse(Console.ReadLine()); + for(i=1; i<=num1||i<=num2; ++i) + { + if(num1%i==0 && num2%i==0) + { + hcf=i; + } + } + Console.Write("\nCommon Factor is : "); + Console.WriteLine(hcf); + Console.Read(); + } +} +} + +/* +Enter the First Number : 12 +Enter the Second Number : 16 +Common Factor is : 4 \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Find and display the Multiplication Table.cs b/c-sharp/Mathematics/C# Program to Find and display the Multiplication Table.cs new file mode 100644 index 0000000..540aa3d --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Find and display the Multiplication Table.cs @@ -0,0 +1,38 @@ +/* + * C# Program to Find and display the Multiplication Table + */ +using System; +class Multipication +{ + static void Main() + { + int no; + Console.Write("Enter a no : "); + no = Convert.ToInt32(Console.ReadLine()); + while (no <= 0) + { + Console.WriteLine("You entered an invalid no"); + Console.Write("Enter a no great than 0: "); + no = Convert.ToInt32(Console.ReadLine()); + } + Console.WriteLine("Multiplication Table :"); + for (int i = 1; i <= no; i++) + { + Console.WriteLine("\n"); + for (int j = 1; j <= no; j++) + { + Console.Write("{0,6}", i * j); + } + } + Console.Read(); + } +} + +/* +Enter a No : 5 +Multiplication Table : + 1 2 3 4 5 + 2 4 6 8 10 + 3 6 9 12 15 + 4 8 12 16 20 + 5 10 15 20 25 \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Find the Cube Root of a Given Number.cs b/c-sharp/Mathematics/C# Program to Find the Cube Root of a Given Number.cs new file mode 100644 index 0000000..c70b3e2 --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Find the Cube Root of a Given Number.cs @@ -0,0 +1,20 @@ +/* + * C# Program to Find the Cube Root of a Given Number + */ +using System; +class CubeRoot +{ + public static void Main() + { + double num, res; + Console.Write("Enter the Number : "); + num = double.Parse(Console.ReadLine()); + res = Math.Ceiling(Math.Pow(num, (double)1 / 3)); + Console.Write("Cube Root : " + res); + } +} + +/* + +Enter the Number : 8 +Cube Root : 2 \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Find the Maximum Range of Values for Decimal,Float and Double Datatype.cs b/c-sharp/Mathematics/C# Program to Find the Maximum Range of Values for Decimal,Float and Double Datatype.cs new file mode 100644 index 0000000..402a397 --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Find the Maximum Range of Values for Decimal,Float and Double Datatype.cs @@ -0,0 +1,31 @@ +/* + * C# Program to Find the Maximum Range of Values for Decimal,Float and Double Datatype + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +namespace maxdatatype +{ +class Program +{ + static void Main(string[] args) + { + Console.WriteLine("The Maximum Range of the Decimal Data Type is : {0} ",Decimal.MaxValue); + Console.WriteLine("The Maximum Range of the Float Data Type is : {0} ",Single.MaxValue); + Console.WriteLine("The Maximum Range of the Decimal Data Type is : {0} ",Double.MaxValue); + Console.WriteLine("Exponent Form : The Maximum Range of Decimal Data Type is : {0:E}", Decimal.MaxValue); + Console.WriteLine("Exponent Form : The Maximum Range of Float Data Type is : {0:E}", Single.MaxValue); + Console.WriteLine("Exponent Form : The Maximum Range of Double Data Type is : {0:E}", Double.MaxValue); + Console.ReadLine(); + } +} +} + +/* +The Maximum Range of the Decimal Data Type is : 7922816251464337593543950335 +The Maximum Range of the Float Data Type is : 3.40282347E+38 +The Maximum Range of the Double Data Type is : 1.7976931348623157E+308 +Exponent Form : The Maximum Range of Decimal Data Type is : 7.922816E+028 +Exponent Form : The Maximum Range of Float Data Type is : 3.402823E+038 +Exponent Form : The Maximum Range of Decimal Data Type is : 1.797693E+308 \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Find the Mean of given Set of Numbers.cs b/c-sharp/Mathematics/C# Program to Find the Mean of given Set of Numbers.cs new file mode 100644 index 0000000..f543c0d --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Find the Mean of given Set of Numbers.cs @@ -0,0 +1,32 @@ +/* + * C# Program to Find the Mean of given Set of Numbers + */ +using System; +class avg +{ + public static void Main() + { + int n1, n2, n3, n4, n5, avg, sum; + Console.WriteLine("Enter 5 Numbers:"); + n1 = Convert.ToInt32(Console.ReadLine()); + n2 = Convert.ToInt32(Console.ReadLine()); + n3 = Convert.ToInt32(Console.ReadLine()); + n4 = Convert.ToInt32(Console.ReadLine()); + n5 = Convert.ToInt32(Console.ReadLine()); + sum = (n1 + n2 + n3 + n4 + n5); + avg = (sum / 5); + Console.WriteLine("Sum :" + sum); + Console.WriteLine("Average :" + avg); + Console.ReadLine(); + } +} + +/* +Enter 5 Numbers : +10 +10 +10 +10 +10 +Sum : 50 +Average : 10 \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Find the Minimum Range of Values for Decimal, Float and Double Datatype.cs b/c-sharp/Mathematics/C# Program to Find the Minimum Range of Values for Decimal, Float and Double Datatype.cs new file mode 100644 index 0000000..994cecd --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Find the Minimum Range of Values for Decimal, Float and Double Datatype.cs @@ -0,0 +1,31 @@ +/* + * C# Program to Find the Minimum Range of Values for Decimal,Float and Double Datatype + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +namespace maxdatatype +{ +class Program +{ + static void Main(string[] args) + { + Console.WriteLine("The Minimum Range of the Decimal Data Type is : {0} ",Decimal.MaxValue); + Console.WriteLine("The Minimum Range of the Float Data Type is : {0} ",Single.MaxValue); + Console.WriteLine("The Minimum Range of the Decimal Data Type is : {0} ",Double.MaxValue); + Console.WriteLine("Exponent Form : The Minimum Range of Decimal Data Type is : {0:E}", Decimal.MaxValue); + Console.WriteLine("Exponent Form : The Minimum Range of Float Data Type is : {0:E}", Single.MaxValue); + Console.WriteLine("Exponent Form : The Minimum Range of Double Data Type is : {0:E}", Double.MaxValue); + Console.ReadLine(); + } +} +} + +/* +The Minimum Range of the Decimal Data Type is : -7922816251464337593543950335 +The Minimum Range of the Float Data Type is : -3.40282347E+38 +The Minimum Range of the Double Data Type is : -1.7976931348623157E+308 +Exponent Form : The Minimum Range of Decimal Data Type is : -7.922816E+028 +Exponent Form : The Minimum Range of Float Data Type is : -3.402823E+038 +Exponent Form : The MinimumRange of Decimal Data Type is : -1.797693E+308 \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Find the Standard Deviation of a Set of Given Numbers.cs b/c-sharp/Mathematics/C# Program to Find the Standard Deviation of a Set of Given Numbers.cs new file mode 100644 index 0000000..bb87009 --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Find the Standard Deviation of a Set of Given Numbers.cs @@ -0,0 +1,72 @@ +/* + * C# Program to Find the Standard Deviation of a Set of Given Numbers + */ +using System; +using System.Collections.Generic; +namespace SampleApp +{ +internal class Program +{ + private static void Main() + { + List number = new List { 1, 2, 3, 4, 5, 6 }; + double mean = number.Mean(); + double variance = number.Variance(); + double sd = number.StandardDeviation(); + Console.WriteLine("Mean: {0} , Variance: {1} , SD: {2} ", mean, variance, sd); + Console.ReadKey(); + } +} +public static class list +{ + public static double Mean(this List values) + { + return values.Count == 0 ? 0 : values.Mean(0, values.Count); + } + + public static double Mean(this List values, int start, int end) + { + double s = 0; + for (int i = start; i < end; i++) + { + s += values[i]; + } + return s / (end - start); + } + + public static double Variance(this List values) + { + return values.Variance(values.Mean(), 0, values.Count); + } + + public static double Variance(this List values, double mean) + { + return values.Variance(mean, 0, values.Count); + } + + public static double Variance(this List values, double mean, int start, int end) + { + double variance = 0; + for (int i = start; i < end; i++) + { + variance += Math.Pow((values[i] - mean), 2); + } + int n = end - start; + if (start > 0) n -= 1; + return variance / (n); + } + public static double StandardDeviation(this List values) + { + return values.Count == 0 ? 0 : values.StandardDeviation(0, values.Count); + } + public static double StandardDeviation(this List values, int start, int end) + { + double mean = values.Mean(start, end); + double variance = values.Variance(mean, start, end); + return Math.Sqrt(variance); + } +} +} + +/* +Mean : 3.5 Variance : 2.916666666667 S.D = 1.7078251256993 \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Find the Sum of first 50 Natural Numbers using For Loop.cs b/c-sharp/Mathematics/C# Program to Find the Sum of first 50 Natural Numbers using For Loop.cs new file mode 100644 index 0000000..c88c90a --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Find the Sum of first 50 Natural Numbers using For Loop.cs @@ -0,0 +1,21 @@ +/* + * C# Program to Find the Sum of first 50 Natural Numbers + * using For Loop + */ +using System; +class program +{ + public static void Main() + { + int num, sum = 0; + for (num = 1; num <= 50; num++) + { + sum = sum + num; + } + Console.WriteLine("Sum = {0}", sum); + Console.ReadLine(); + } +} + +/* +Sum = 1275 \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Find the Sum of two Binary Numbers.cs b/c-sharp/Mathematics/C# Program to Find the Sum of two Binary Numbers.cs new file mode 100644 index 0000000..5e9adcc --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Find the Sum of two Binary Numbers.cs @@ -0,0 +1,44 @@ +/* + * C# Program to Find the Sum of two Binary Numbers */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +namespace ConsoleApplication +{ +class Program +{ + static void Main(string[] args) + { + int b1, b2; + int i = 0, rem = 0; + int[] sum = new int[20]; + Console.WriteLine("Enter the first binary number: "); + b1 = int.Parse(Console.ReadLine()); + Console.WriteLine("Enter the second binary number: "); + b2 = int.Parse(Console.ReadLine()); + while (b1 != 0 || b2 != 0) + { + sum[i++] = (b1 % 10 + b2 % 10 + rem) % 2; + rem = (b1 % 10 + b2 % 10 + rem) / 2; + b1 = b1 / 10; + b2 = b2 / 10; + } + if (rem != 0) + sum[i++] = rem; + --i; + Console.WriteLine("Sum of two binary numbers: "); + while (i >= 0) + Console.Write("{0}", sum[i--]); + Console.ReadLine(); + } +} +} + +/* +Enter the first binary number: +100 +Enter the second binary number: +110 +Sum of two binary numbers: +1010 \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Find the Value of Cos(x).cs b/c-sharp/Mathematics/C# Program to Find the Value of Cos(x).cs new file mode 100644 index 0000000..8a0d6b8 --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Find the Value of Cos(x).cs @@ -0,0 +1,37 @@ +/* + * C# Program to Find the Value of Cos(x) + */ +using System; +namespace ConsoleApplication1 +{ +class Program +{ + static void Main(string[] args) + { + for (double d = 0; d < 6.0; d += 0.5) + { + Console.WriteLine("The cosine of {0} = {1}", d, Math.Cos(d)); + Console.WriteLine("Calculated cosine of {0} = {1}", d, cos(d)); + Console.WriteLine(); + } + Console.ReadKey(); + } + + static double cos(double x) + { + double p = x * x; + double q = p * p; + return 1.0 - p / 2 + q / 24 - p * q / 720 + q * q / 40320 - p * q * q / 3628800; + } +} +} + +/* +The Cosine of 0 = 1 +Calculated Cosine of 0 = 1 +The Cosine of 0.5 = 0.877582561890373 +Calculated Cosine of 0.5 = 0.877582561889864 +The Cosine of 1.5 = 0.54030230586814 +Calculated Cosine of 1.5 = 0.540302303791887 +The Cosine of 2.0 = 0.0707372016677029 +Calculated Cosine of 2.0 = 0.0707369341169085 \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Find whether the Number is Divisible by 2.cs b/c-sharp/Mathematics/C# Program to Find whether the Number is Divisible by 2.cs new file mode 100644 index 0000000..f850d51 --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Find whether the Number is Divisible by 2.cs @@ -0,0 +1,36 @@ +/* + * C# Program to Find whether the Number is Divisible by 2 + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +using System.Threading.Tasks; + +namespace ConsoleApplication16 +{ +class Program +{ + static void Main(string[] args) + { + int n; + Console.WriteLine("Enter the Number :"); + n = int.Parse(Console.ReadLine()); + if (n % 2 == 0) + { + Console.WriteLine("Entered Number is Divisible by 2 "); + } + else + { + Console.WriteLine("Entered Number is Not Divisible by 2"); + } + Console.ReadLine(); + } +} +} + +/* + +Enter the Number : +45 +Entered Number is Not Divisible by 2 \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Generate Fibonacci Series.cs b/c-sharp/Mathematics/C# Program to Generate Fibonacci Series.cs new file mode 100644 index 0000000..60db1ca --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Generate Fibonacci Series.cs @@ -0,0 +1,46 @@ +/* + * C# Program to Generate Fibonacci Series + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +namespace fibonaci +{ +class Program +{ + static void Main(string[] args) + { + int i, count, f1 = 0, f2 = 1, f3 = 0; + Console.Write("Enter the Limit : "); + count = int.Parse(Console.ReadLine()); + Console.WriteLine(f1); + Console.WriteLine(f2); + for (i = 0; i <= count; i++) + { + f3 = f1 + f2; + Console.WriteLine(f3); + f1 = f2; + f2 = f3; + } + Console.ReadLine(); + } +} +} + +/* +Enter the Limit : 10 +0 +1 +1 +2 +3 +5 +8 +13 +21 +34 +55 +89 +144 \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Generate Register Number automatically for 100 Students using Static Constructor.cs b/c-sharp/Mathematics/C# Program to Generate Register Number automatically for 100 Students using Static Constructor.cs new file mode 100644 index 0000000..e1cbdd1 --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Generate Register Number automatically for 100 Students using Static Constructor.cs @@ -0,0 +1,38 @@ +/* + * C# Program to Generate Register Number automatically for 100 Students using Static Constructor + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +namespace staticprog +{ +class sample +{ + int regnumber; + static int nextnum; + static sample() + { + nextnum=1000; + } + sample() + { + regnumber=++nextnum; + } + public static void Main(string[] args) + { + sample s=new sample(); + Console.WriteLine("#1 : {0}",s.regnumber); + s=new sample(); + Console.WriteLine("#2 : {0}",s.regnumber); + s = new sample(); + Console.WriteLine("#3 : {0}", s.regnumber); + Console.ReadLine(); + } +} +} + +/* +#1 : 1001 +#2 : 1002 +#3 : 1003 \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Generate the Factorial of Given Number.cs b/c-sharp/Mathematics/C# Program to Generate the Factorial of Given Number.cs new file mode 100644 index 0000000..c0f7645 --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Generate the Factorial of Given Number.cs @@ -0,0 +1,32 @@ +/* + * C# Program to Generate the Factorial of Given Number + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +namespace factorial +{ +class Program +{ + static void Main(string[] args) + { + int i, number, fact; + Console.WriteLine("Enter the Number"); + number = int.Parse(Console.ReadLine()); + fact = number; + for (i = number - 1; i >= 1; i--) + { + fact = fact * i; + } + Console.WriteLine("\nFactorial of Given Number is: "+fact); + Console.ReadLine(); + } +} +} + +/* +Enter the Number +6 +Factorial of Given Number is: 720 \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Generate the Sum of N Numbers.cs b/c-sharp/Mathematics/C# Program to Generate the Sum of N Numbers.cs new file mode 100644 index 0000000..87d6049 --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Generate the Sum of N Numbers.cs @@ -0,0 +1,30 @@ +/* + * C# Program to Generate the Sum of N Numbers + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +namespace program +{ +class Program +{ + static void Main(string[] args) + { + int i, sum = 0,n; + Console.Write("Enter the Nth Number : "); + n = int.Parse(Console.ReadLine()); + for (i = 0; i <= n; i++) + { + sum = sum + i; + } + Console.WriteLine("\nSum of N Numbers : " + sum); + Console.ReadLine(); + } +} +} + +/* +Enter the Nth Number : 10 +Sum of N Numbers : 55 \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Illustrate Bitwise Operations.cs b/c-sharp/Mathematics/C# Program to Illustrate Bitwise Operations.cs new file mode 100644 index 0000000..85401f5 --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Illustrate Bitwise Operations.cs @@ -0,0 +1,38 @@ +/* + * C# Program to Illustrate Bitwise Operations + */ +using System; +class bitwise +{ + byte b1, b2; + int x; + long y; + bitwise() + { + b1 = 10; + b2 = 5; + x = 32; + y = 20; + } + public static void Main() + { + bitwise bit = new bitwise(); + byte p = (byte)(bit.b1 & bit.b2); + byte q = (byte)(bit.b1 | bit.b2); + byte r = (byte)(bit.b1 ^ bit.b2); + int z = (int)(bit.x & bit.y); + Console.WriteLine("b1={0},b2={1},x={2},y={3}", bit.b1, bit.b2, bit.x, bit.y); + Console.WriteLine("b1 & b2={0} : ", p); + Console.WriteLine("b1 | b2={0} : ", q); + Console.WriteLine("b1 ^ b2={0} : ", r); + Console.WriteLine("x & y = {0} : ", z); + Console.ReadLine(); + } +} + +/* +b1=10,b2=5,x=32,y=20 +b1 & b2 : 0 +b1 | b2 : 15 +b1 ^ b2 : 15 +x & y :0 \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Illustrate Pascal Triangle.cs b/c-sharp/Mathematics/C# Program to Illustrate Pascal Triangle.cs new file mode 100644 index 0000000..e623650 --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Illustrate Pascal Triangle.cs @@ -0,0 +1,39 @@ +/* + * C# Program to Illustrate Pascal Triangle + */ +using System; +class Pascal +{ + public static void Main() + { + int[,] arr = new int[8, 8]; + Console.WriteLine("Pascal Triangle : "); + for (int i = 0; i < 5; i++) + { + for (int k = 5; k > i; k--) + { + Console.Write(" "); + } + for (int j = 0; j < i; j++) + { + if (j == 0 || i == j) + { + arr[i, j] = 1; + } + else + { + arr[i, j] = arr[i - 1, j] + arr[i - 1, j - 1]; + } + Console.Write(arr[i, j] + " "); + } + Console.ReadLine(); + } + } +} + +/* +Pascal Triangle : + 1 + 1 1 + 1 2 1 + 1 3 3 1 \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Illustrate Trignometry Angles in Degrees.cs b/c-sharp/Mathematics/C# Program to Illustrate Trignometry Angles in Degrees.cs new file mode 100644 index 0000000..65c3697 --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Illustrate Trignometry Angles in Degrees.cs @@ -0,0 +1,30 @@ +/* + * C# Program to Illustrate Trignometry Angles in Degrees + */ +using System; +namespace trig +{ +class Program +{ + static void Main(string[] args) + { + Console.WriteLine("Trignometric values in Degree"); + Console.WriteLine("sin (60) = {0}", Math.Sin(60 * Math.PI / 180)); + Console.WriteLine("cos (60) = {0}", Math.Cos(60 * Math.PI / 180)); + Console.WriteLine("tan (60) = {0}", Math.Tan(60 * Math.PI / 180)); + Console.WriteLine("arcsin (1/2) = {0}", Math.Asin(0.5) * 180 / Math.PI); + Console.WriteLine("arccos (1/2) = {0}", Math.Acos(0.5) * 180 / Math.PI); + Console.WriteLine("arctan (1/2) = {0}", Math.Atan(0.5) * 180 / Math.PI); + Console.Read(); + } +} +} + +/* +Trignometric Values in Radians : +sin (pi/3) = 0.866025403784439 +cos (pi/3) = 0.5 +tan (pi/3) = 1.73205080756888 +arcsin (1/2) = 30 +arccos (1/2) = 60 +arctan (1/2) = 26.565051177078 \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Illustrate Trignometry Angles in Radians.cs b/c-sharp/Mathematics/C# Program to Illustrate Trignometry Angles in Radians.cs new file mode 100644 index 0000000..1cb0d1d --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Illustrate Trignometry Angles in Radians.cs @@ -0,0 +1,30 @@ +/* + * C# Program to Illustrate Trignometry Angles in Radians + */ +using System; +namespace trig +{ +class Program +{ + static void Main(string[] args) + { + Console.WriteLine("Trignometric Values in Radians : "); + Console.WriteLine("sin (pi/3) = {0}", Math.Sin(Math.PI / 3)); + Console.WriteLine("cos (pi/3) = {0}", Math.Cos(Math.PI / 3)); + Console.WriteLine("tan (pi/3) = {0}", Math.Tan(Math.PI / 3)); + Console.WriteLine("arcsin (1/2) = {0}", Math.Asin(0.5)); + Console.WriteLine("arccos (1/2) = {0}", Math.Acos(0.5)); + Console.WriteLine("arctan (1/2) = {0}", Math.Atan(0.5)); + Console.ReadLine(); + } +} +} + +/* +Trignometric Values in Radians : +sin (pi/3) = 0.866025403784439 +cos (pi/3) = 0.5 +tan (pi/3) = 1.73205080756888 +arcsin (1/2) = 0.523598775598299 +arccos (1/2) = 1.0471975511966 +arctan (1/2) = 0.463647609000806 \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Multiply given Number by 4 using Bitwise Operators.cs b/c-sharp/Mathematics/C# Program to Multiply given Number by 4 using Bitwise Operators.cs new file mode 100644 index 0000000..e37e133 --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Multiply given Number by 4 using Bitwise Operators.cs @@ -0,0 +1,29 @@ +/* + * C# Program to Multiply given Number by 4 using Bitwise Operators + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +namespace ConsoleApplication +{ +class Program +{ + static void Main(string[] args) + { + int number, tempnum; + Console.WriteLine("Enter an integer :"); + number = int.Parse(Console.ReadLine()); + tempnum = number; + number = number << 2; + Console.WriteLine("{0},{1}", tempnum, number); + Console.ReadLine(); + } +} +} + +/* +Enter an integer : +120 +120,480 \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Perform GCD.cs b/c-sharp/Mathematics/C# Program to Perform GCD.cs new file mode 100644 index 0000000..043ad24 --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Perform GCD.cs @@ -0,0 +1,36 @@ +/* + * C# Program to Perform GCD + */ +using System; +public class Program +{ + static int GCD(int num1, int num2) + { + int Remainder; + while (num2 != 0) + { + Remainder = num1 % num2; + num1 = num2; + num2 = Remainder; + } + return num1; + } + + static int Main(string[] args) + { + int x, y; + Console.Write("Enter the First Number : "); + x = int.Parse(Console.ReadLine()); + Console.Write("Enter the Second Number : "); + y = int.Parse(Console.ReadLine()); + Console.Write("\nThe Greatest Common Divisor of "); + Console.WriteLine("{0} and {1} is {2}", x, y, GCD(x, y)); + Console.ReadLine(); + return 0; + } +} + +/* +Enter the First Number : 12 +Enter the Second Number : 24 +The Greatest Common Divisor of 12 and 24 is : 12 \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Perform Multiplication of Exponents of Same Base.cs b/c-sharp/Mathematics/C# Program to Perform Multiplication of Exponents of Same Base.cs new file mode 100644 index 0000000..c844944 --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Perform Multiplication of Exponents of Same Base.cs @@ -0,0 +1,29 @@ +/* + * C# Program to Perform Multiplication of Exponents of Same Base + */ +using System; +class Program +{ + static void Main() + { + Console.WriteLine("Enter the Base : "); + double num = double.Parse(Console.ReadLine()); + Console.WriteLine("Enter the First Exponent :"); + double exp1 = double.Parse(Console.ReadLine()); + Console.WriteLine("Enter the Second Exponent :"); + double exp2 = double.Parse(Console.ReadLine()); + double mul; + mul = exp1 + exp2; + Console.WriteLine("Result is : {0}^{1} : {2}", num, mul, Math.Pow(num, mul)); + Console.ReadLine(); + } +} + +/* +Enter the Base : +2 +Enter the First Exponent : +3 +Enter the Second Exponent : +2 +Result is : 2^5 : 32 \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Perform all Basic Arithmetic Operations.cs b/c-sharp/Mathematics/C# Program to Perform all Basic Arithmetic Operations.cs new file mode 100644 index 0000000..58db0df --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Perform all Basic Arithmetic Operations.cs @@ -0,0 +1,63 @@ +/* + * C# Program to Perform all Basic Arithmetic Operations + */ +using System; +using System.Collections.Generic; +using System.Text; +namespace Program +{ +class Program +{ + static void Main(string[] args) + { + int Num1, Num2, result; + char option; + Console.Write("Enter the First Number : "); + Num1 = Convert.ToInt32(Console.ReadLine()); + Console.Write("Enter the Second Number : "); + Num2 = Convert.ToInt32(Console.ReadLine()); + Console.WriteLine("Main Menu"); + Console.WriteLine("1. Addition"); + Console.WriteLine("2. Subtraction"); + Console.WriteLine("3. Multiplication"); + Console.WriteLine("4. Division"); + Console.Write("Enter the Operation you want to perform : "); + option = Convert.ToChar(Console.ReadLine()); + switch (option) + { + case '1': + result = Num1 + Num2; + Console.WriteLine("The result of Addition is : {0}", result); + break; + case '2': + result = Num1 - Num2; + Console.WriteLine("The result of Subtraction is : {0}", result); + break; + case '3': + result = Num1 * Num2; + Console.WriteLine("The result of Multiplication is : {0}", result); + break; + case '4': + result = Num1 / Num2; + Console.WriteLine("The result of Division is : {0}", result); + break; + default: + Console.WriteLine("Invalid Option"); + break; + } + Console.ReadLine(); + } + +} +} + +/* +Enter the First Number : 100 +Enter the Second Number : 2 +Main Menu +1. Addition +2. Subtraction +3. Multiplication +4. Division +Enter the Operation you want to perform : 3 +The Result of Multiplication is : 200 diff --git a/c-sharp/Mathematics/C# Program to Print all the Multiples of 17 which are Less than 100.cs b/c-sharp/Mathematics/C# Program to Print all the Multiples of 17 which are Less than 100.cs new file mode 100644 index 0000000..15d5193 --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Print all the Multiples of 17 which are Less than 100.cs @@ -0,0 +1,30 @@ +/* + * C# Program to Print all the Multiples of 17 which are Less than 100 + */ +using System; +class program +{ + public static void Main() + { + int a,i; + Console.WriteLine("Multiples of 17 are : "); + for (i = 1; i < 100; i++) + { + a = i % 17; + if (a == 0) + { + Console.WriteLine(i); + } + } + Console.Read(); + } +} + +/* + +Multiples of 17 are : +17 +34 +51 +68 +85 \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Print the Sum of all the Multiples of 3 and 5.cs b/c-sharp/Mathematics/C# Program to Print the Sum of all the Multiples of 3 and 5.cs new file mode 100644 index 0000000..a59fe5d --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Print the Sum of all the Multiples of 3 and 5.cs @@ -0,0 +1,27 @@ +/* + *C# Program to Print the Sum of all the Multiples of 3 and 5 + */ +using System; +class program +{ + public static void Main() + { + int a, b, i, Sum = 0; + for (i = 1; i < 100; i++) + { + a = i % 3; + b = i % 5; + if (a == 0 || b == 0) + { + Console.Write("{0}\t", i); + Sum = Sum + i; + } + } + Console.WriteLine("\nThe Sum of all the Multiples of 3 or 5 Below 100 : {0}", Sum); + Console.Read(); + } +} + +/* +3 5 6 9 10 12 15 18 20 21 24 25 27 30 33 35 36 39 40 42 45 48 50 51 54 55 57 60 63 65 66 69 70 72 75 78 80 81 84 85 87 90 93 95 96 99 +The Sum of all the Multiples of 3 or 5 Below 100 : 2318 \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to Reverse a Number & Check if it is a Palindrome.cs b/c-sharp/Mathematics/C# Program to Reverse a Number & Check if it is a Palindrome.cs new file mode 100644 index 0000000..4b86ea0 --- /dev/null +++ b/c-sharp/Mathematics/C# Program to Reverse a Number & Check if it is a Palindrome.cs @@ -0,0 +1,34 @@ +/* + * C# Program to Reverse a Number & Check if it is a Palindrome + */ +using System; +class program +{ + public static void Main() + { + int num, temp, remainder, reverse = 0; + Console.WriteLine("Enter an integer \n"); + num = int.Parse(Console.ReadLine()); + temp = num; + while (num > 0) + { + remainder = num % 10; + reverse = reverse * 10 + remainder; + num /= 10; + } + Console.WriteLine("Given number is = {0}", temp); + Console.WriteLine("Its reverse is = {0}", reverse); + if (temp == reverse) + Console.WriteLine("Number is a palindrome \n"); + else + Console.WriteLine("Number is not a palindrome \n"); + Console.ReadLine(); + } +} + +/* +Enter an integer +343 +Given number is = 343 +Its reverse is = 343 +Number is a palindrome \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to calculate the series sin(x).cs b/c-sharp/Mathematics/C# Program to calculate the series sin(x).cs new file mode 100644 index 0000000..efa00b8 --- /dev/null +++ b/c-sharp/Mathematics/C# Program to calculate the series sin(x).cs @@ -0,0 +1,41 @@ +/* + * C# Program to calculate the series sin(x)=x-x^3/3!+x^5/!-x^7/7!+...... + */ +using System; +class sine +{ + int deg, n; + public void readdata() + { + Console.WriteLine("Enter the Number of Terms:"); + n = Convert.ToInt32(Console.ReadLine()); + Console.WriteLine("Enter the Angle in Degrees:"); + deg = Convert.ToInt32(Console.ReadLine()); + } + public void sineseries() + { + float x, s = 0.0f, t; + x = (float)Math.PI * deg / 180f; + s = x; + t = x; + for (int i = 1; i <= n; i++) + { + t = (-t * x * x) / ((2 * i) * (2 * i + 1)); + s = s + t; + } + Console.WriteLine("Sin({0})={1}", deg, s); + } + public static void Main() + { + sine s = new sine(); + s.readdata(); + s.sineseries(); + } +} + +/* +Enter the Number of Terms: +20 +Enter the Angle in Degrees: +90 +Sin(90)=0.99999994 \ No newline at end of file diff --git a/c-sharp/Mathematics/C# Program to find Volume and Surface Area of a Sphere.cs b/c-sharp/Mathematics/C# Program to find Volume and Surface Area of a Sphere.cs new file mode 100644 index 0000000..28d57e2 --- /dev/null +++ b/c-sharp/Mathematics/C# Program to find Volume and Surface Area of a Sphere.cs @@ -0,0 +1,25 @@ +/* + * C# Program to find Volume and Surface Area of a Sphere + */ +using System; +using System.IO; +class program +{ + public static void Main() + { + double r, surface_area, volume; + double PI = 3.14; + Console.WriteLine("Enter the Radius of the Sphere: "); + r = Convert.ToDouble(Console.ReadLine()); + surface_area = 4* PI * r * r; + volume = (4.0 / 3) * PI * r * r * r; + Console.WriteLine("Surface Area of Sphere is : {0} ", surface_area); + Console.WriteLine("Volume of Sphere is : {0}", volume); + Console.Read(); + } +} + +/* +Enter the Radius of Sphere : 5 +Surface Area of Sphere is : 314 +Volume of Sphere is : 523.333333333333333 \ No newline at end of file diff --git a/c-sharp/Matrix/C# Program to Check If a Given Matrix is an Identity Matrix.cs b/c-sharp/Matrix/C# Program to Check If a Given Matrix is an Identity Matrix.cs new file mode 100644 index 0000000..fb0dc1b --- /dev/null +++ b/c-sharp/Matrix/C# Program to Check If a Given Matrix is an Identity Matrix.cs @@ -0,0 +1,45 @@ +/* + * C# Program to Check If a Given Matrix is an Identity Matrix + */ +using System; +class pro +{ + public static void Main() + { + Console.WriteLine("Enter the order: "); + int n = int.Parse(Console.ReadLine()); + int[,] a = new int[3, 3]; + int i, j; + Console.WriteLine("\n Enter the matrix\n"); + for (i = 0; i < n; i++) + { + for (j = 0; j < n; j++) + { + a[i, j] = Convert.ToInt16(Console.ReadLine()); + } + } + for (i = 0; i < n; i++) + { + for (j = 0; j < n; j++) + { + if ((i == j && a[i, j] != 1) || (i != j && a[i, j] != 0)) + { + goto label; + } + } + } + Console.WriteLine("Identity Matrix"); + return; +label: + Console.WriteLine("\n Not an Identity Matrix"); + } +} + +/* +Enter the Order : 2 +Enter the Matrix : +1 +0 +0 +1 +Identity Matrix \ No newline at end of file diff --git a/c-sharp/Matrix/C# Program to Display Lower Triangular Matrix.cs b/c-sharp/Matrix/C# Program to Display Lower Triangular Matrix.cs new file mode 100644 index 0000000..a8b748c --- /dev/null +++ b/c-sharp/Matrix/C# Program to Display Lower Triangular Matrix.cs @@ -0,0 +1,68 @@ +/* + * C# Program to Display Lower Triangular Matrix + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +namespace ConsoleApplication8 +{ +class Program +{ + int x; + public static void Main(string[] args) + { + int m, n, i, j; + Console.Write("Enter Number Of Rows And Columns Of Matrices A and B : "); + m = Convert.ToInt16(Console.ReadLine()); + n = Convert.ToInt16(Console.ReadLine()); + int[,] A = new int[10, 10]; + Console.Write("\nEnter The First Matrix : "); + for (i = 0; i < m; i++) + { + for (j = 0; j < n; j++) + { + A[i, j] = Convert.ToInt16(Console.ReadLine()); + } + } + Console.Clear(); + Console.WriteLine("\nMatrix A : "); + for (i = 0; i < m; i++) + { + for (j = 0; j < n; j++) + { + Console.Write(A[i, j] + "\t"); + } + Console.WriteLine(); + } + Console.WriteLine("\n Setting Zero to illustrate Lower Triangular Matrix\n"); + for (i = 0; i < m; i++) + { + Console.Write("\n"); + for (j = 0; j < 3; j++) + { + if (i >= j) + Console.Write(A[i, j] + "\t"); + else + Console.Write("0\t"); + } + } + Console.ReadLine(); + } +} +} + +/* +Enter Number Of Rows And Columns Of Matrices A and B : 3 3 +Enter the First Matrix : +1 2 3 +2 3 4 +3 4 5 +Matrix A : +1 2 3 +2 3 4 +3 4 5 +Setting Zero to illustrate Lower Triangular Matrix : +1 0 0 +2 3 0 +3 4 5 \ No newline at end of file diff --git a/c-sharp/Matrix/C# Program to Display Upper Triangular Matrix.cs b/c-sharp/Matrix/C# Program to Display Upper Triangular Matrix.cs new file mode 100644 index 0000000..8615fed --- /dev/null +++ b/c-sharp/Matrix/C# Program to Display Upper Triangular Matrix.cs @@ -0,0 +1,68 @@ +/* + * C# Program to Display Upper Triangular Matrix + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +namespace ConsoleApplication8 +{ +class Program +{ + int x; + public static void Main(string[] args) + { + int m, n, i, j; + Console.Write("Enter Number Of Rows And Columns Of Matrices A and B : "); + m = Convert.ToInt16(Console.ReadLine()); + n = Convert.ToInt16(Console.ReadLine()); + int[,] A = new int[10, 10]; + Console.Write("\nEnter The First Matrix : "); + for (i = 0; i < m; i++) + { + for (j = 0; j < n; j++) + { + A[i, j] = Convert.ToInt16(Console.ReadLine()); + } + } + Console.Clear(); + Console.WriteLine("\nMatrix A : "); + for (i = 0; i < m; i++) + { + for (j = 0; j < n; j++) + { + Console.Write(A[i, j] + "\t"); + } + Console.WriteLine(); + } + Console.WriteLine("\n Setting Zero to illustrate Upper Triangular Matrix\n"); + for (i = 0; i < m; i++) + { + Console.Write("\n"); + for (j = 0; j < 3; j++) + { + if (i <= j) + Console.Write(A[i, j] + "\t"); + else + Console.Write("0\t"); + } + } + Console.ReadLine(); + } +} +} + +/* +Enter Number Of Rows And Columns Of Matrices A and B : 3 3 +Enter the First Matrix : +1 2 3 +2 3 4 +3 4 5 +Matrix A : +1 2 3 +2 3 4 +3 4 5 +Setting Zero to illustrate Upper Triangular Matrix : +1 2 3 +0 3 4 +0 0 5 \ No newline at end of file diff --git a/c-sharp/Matrix/C# Program to Find Largest Element in a Matrix.cs b/c-sharp/Matrix/C# Program to Find Largest Element in a Matrix.cs new file mode 100644 index 0000000..0be7a51 --- /dev/null +++ b/c-sharp/Matrix/C# Program to Find Largest Element in a Matrix.cs @@ -0,0 +1,55 @@ +/* + * C# Program to Find Largest Element in a Matrix + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +class arrsampl +{ + int[,]x; + arrsampl() + { + x = new int[,] { { 12, 21, 63 }, { 40, 15, 6 } }; + } + void printarray() + { + Console.WriteLine("Elements in the Given Matrix : "); + for (int i = 0; i < 2; i++) + { + for (int j = 0; j < 3; j++) + { + Console.Write(x[i, j] + "\t"); + } + Console.WriteLine("\n"); + } + } + int max() + { + int big = x[0, 0]; + for (int i = 0; i < 2; i++) + { + for (int j = 0; j < 3; j++) + { + if (big < x[i, j]) + { + big = x[i, j]; + } + } + } + return big; + } + public static void Main() + { + arrsampl obj = new arrsampl(); + obj.printarray(); + Console.WriteLine("Largest Element : {0}", obj.max()); + Console.ReadLine(); + } +} + +/* +Elements in the Given Matrix : +12 21 63 +40 15 6 +Largest Element : 63 \ No newline at end of file diff --git a/c-sharp/Matrix/C# Program to Find Smallest Element in a Matrix.cs b/c-sharp/Matrix/C# Program to Find Smallest Element in a Matrix.cs new file mode 100644 index 0000000..8142616 --- /dev/null +++ b/c-sharp/Matrix/C# Program to Find Smallest Element in a Matrix.cs @@ -0,0 +1,55 @@ +/* + * C# Program to Find Smallest Element in a Matrix + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +class arrsampl +{ + int[,]x; + arrsampl() + { + x = new int[,] { { 11, 2, 61 }, { 42, 50, 3 } }; + } + void printarray() + { + Console.WriteLine("Elements in the Given Matrix : "); + for (int i = 0; i < 2; i++) + { + for (int j = 0; j < 3; j++) + { + Console.Write(x[i, j] + "\t"); + } + Console.WriteLine("\n"); + } + } + int max() + { + int small = x[0, 0]; + for (int i = 0; i < 2; i++) + { + for (int j = 0; j < 3; j++) + { + if (small > x[i, j]) + { + small = x[i, j]; + } + } + } + return small; + } + public static void Main() + { + arrsampl obj = new arrsampl(); + obj.printarray(); + Console.WriteLine("Smallest Element : {0}", obj.max()); + Console.ReadLine(); + } +} + +/* +Elements in the Given Matrix : +11 2 61 +42 50 3 +Smallest Element : 2 \ No newline at end of file diff --git a/c-sharp/Matrix/C# Program to Find Sum of the Elements of each Column of the Given Matrix.cs b/c-sharp/Matrix/C# Program to Find Sum of the Elements of each Column of the Given Matrix.cs new file mode 100644 index 0000000..4498c94 --- /dev/null +++ b/c-sharp/Matrix/C# Program to Find Sum of the Elements of each Column of the Given Matrix.cs @@ -0,0 +1,78 @@ +/* + * C# Program to Find Sum of the Elements of each Column + * of the Given Matrix + */ +using System; +using System.Collections.Generic; +using System.Text; +namespace matrix_col +{ +class mat +{ + int i, j, m, n; + int[,] a = new int[20, 20]; + int[,] c = new int[20, 20]; + public void getmatrix() + { + Console.WriteLine("Enter the Number of Rows : "); + m = int.Parse(Console.ReadLine()); + Console.WriteLine("Enter the Number of Columns : "); + n = int.Parse(Console.ReadLine()); + Console.WriteLine("Enter the Elements"); + for (i = 1; i <= m; i++) + { + for (j = 1; j <= n; j++) + { + a[i, j] = int.Parse(Console.ReadLine()); + } + } + Console.WriteLine("Given Matrix"); + for (i = 1; i <= m; i++) + { + for (j = 1; j <= n; j++) + { + Console.Write("\t{0}", a[i, j]); + } + Console.WriteLine(); + } + } + + public void col() + { + int c; + for (i = 1; i <= n; i++) + { + c = 0; + for (j = 1; j <= m; j++) + { + c = c + a[j, i]; + } + Console.WriteLine("{0} Column Sum : {1}", i, c); + } + } +} +class matsum +{ + static void Main(string[] args) + { + mat ma = new mat(); + ma.getmatrix(); + ma.col(); + Console.ReadLine(); + } +} +} + +/* +Enter the Number of Rows : 2 +Enter the Number of Columns : 2 +Enter the Elements : +1 +2 +3 +4 +Given Matrix : + 1 2 + 3 4 +1 Column Sum : 4 +2 Column Sum : 6 \ No newline at end of file diff --git a/c-sharp/Matrix/C# Program to Find Sum of the Elements of each Row of the Given Matrix.cs b/c-sharp/Matrix/C# Program to Find Sum of the Elements of each Row of the Given Matrix.cs new file mode 100644 index 0000000..a955943 --- /dev/null +++ b/c-sharp/Matrix/C# Program to Find Sum of the Elements of each Row of the Given Matrix.cs @@ -0,0 +1,76 @@ +/* + * C# Program to Find Sum of the Elements of each Row + * of the Given Matrix + */ +using System; +using System.Collections.Generic; +using System.Text; +namespace matrix_row_sum +{ +class mat +{ + int i, j, m, n; + int[,] a = new int[20, 20]; + public void getmatrix() + { + Console.WriteLine("Enter The Number of Rows : "); + m = int.Parse(Console.ReadLine()); + Console.WriteLine("Enter The Number of Columns : "); + n = int.Parse(Console.ReadLine()); + Console.WriteLine("Enter the Elements"); + for (i = 1; i <= m; i++) + { + for (j = 1; j <= n; j++) + { + a[i, j] = int.Parse(Console.ReadLine()); + } + } + Console.WriteLine("Given Matrix"); + for (i = 1; i <= m; i++) + { + for (j = 1; j <= n; j++) + { + Console.Write("\t{0}", a[i, j]); + } + Console.WriteLine(); + } + } + public void row() + { + int r; + for (i = 1; i <= m; i++) + { + r = 0; + for (j = 1; j <= n; j++) + { + r = r + a[i, j]; + } + Console.WriteLine("{0} Row Sum : {1}", i, r); + } + } +} +class matrowsum +{ + static void Main(string[] args) + { + mat ma = new mat(); + ma.getmatrix(); + ma.row(); + Console.ReadLine(); + } +} +} + +/* +Enter the Number of Rows : 2 +Enter the Number of Columns : 2 +Enter the Elements : +1 +2 +3 +4 +Given Matrix : + 1 2 + 3 4 +1 Row Sum : 3 +2 Row Sum : 7 \ No newline at end of file diff --git a/c-sharp/Matrix/C# Program to Find the Sum of the Values on Diagonal of the Matrix.cs b/c-sharp/Matrix/C# Program to Find the Sum of the Values on Diagonal of the Matrix.cs new file mode 100644 index 0000000..380e83e --- /dev/null +++ b/c-sharp/Matrix/C# Program to Find the Sum of the Values on Diagonal of the Matrix.cs @@ -0,0 +1,82 @@ +/* + * C# Program to Find the Sum of the Values on + * Diagonal of the Matrix + */ +using System; +using System.Collections.Generic; +using System.Text; +class mat +{ + int i, j, m, n; + int[,] a = new int[20, 20]; + public void get() + { + Console.WriteLine("Enter Row Value"); + m = int.Parse(Console.ReadLine()); + Console.WriteLine("Enter Column Value"); + n = int.Parse(Console.ReadLine()); + Console.WriteLine("Enter Elements one by one"); + for (i = 1; i <= m; i++) + { + for (j = 1; j <= n; j++) + { + a[i, j] = int.Parse(Console.ReadLine()); + } + } + Console.WriteLine("Given Matrix"); + for (i = 1; i <= m; i++) + { + for (j = 1; j <= n; j++) + { + Console.Write("\t{0}", a[i, j]); + } + Console.WriteLine(); + } + } + public void diag() + { + int d; + d = 0; + if (m == n) + { + for (i = 1; i <= m; i++) + { + for (j = 1; j <= n; j++) + { + if (i == j) + { + d = d + a[i, j]; + } + } + } + Console.WriteLine("Diagonal Sum= {0}", d); + } + else + { + Console.WriteLine("Can't Perform Diagonal Sum"); + } + } + class matsum + { + static void Main(string[] args) + { + mat ma = new mat(); + ma.get(); + ma.diag(); + Console.Read(); + } + } +} + +/* +Enter Row Value : 2 +Enter Column Value : 2 +Enter Elements One by One : +2 +2 +2 +2 +Given Matrix : + 2 2 + 2 2 +Diagonal Sum :4 \ No newline at end of file diff --git a/c-sharp/Matrix/C# Program to Generate the Transpose of a Given Matrix.cs b/c-sharp/Matrix/C# Program to Generate the Transpose of a Given Matrix.cs new file mode 100644 index 0000000..06bdbcb --- /dev/null +++ b/c-sharp/Matrix/C# Program to Generate the Transpose of a Given Matrix.cs @@ -0,0 +1,62 @@ +/* + * C# Program to Generate the Transpose of a Given Matrix + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +namespace Program +{ +class Program +{ + public static void Main(string[] args) + { + int m, n, i, j; + Console.Write("Enter the Order of the Matrix : "); + m = Convert.ToInt16(Console.ReadLine()); + n = Convert.ToInt16(Console.ReadLine()); + int[,] A = new int[10, 10]; + Console.Write("\nEnter The Matrix Elements : "); + for (i = 0; i < m; i++) + { + for (j = 0; j < n; j++) + { + A[i, j] = Convert.ToInt16(Console.ReadLine()); + } + } + Console.Clear(); + Console.WriteLine("\nMatrix A : "); + for (i = 0; i < m; i++) + { + for (j = 0; j < n; j++) + { + Console.Write(A[i, j] + "\t"); + } + Console.WriteLine(); + } + Console.WriteLine("Transpose Matrix : "); + for (i = 0; i < m; i++) + { + for (j = 0; j < n; j++) + { + Console.Write(A[j, i] + "\t"); + } + Console.WriteLine(); + } + Console.Read(); + } +} +} + +/* +Enter the Order of the Matrix : 2 2 +Enter the Matrix Elements : +1 2 +3 4 +Matrix A : +1 2 +3 4 +Transpose Matrix : +1 3 +2 4 \ No newline at end of file diff --git a/c-sharp/Matrix/C# Program to Interchange any 2 Columns of Matrix.cs b/c-sharp/Matrix/C# Program to Interchange any 2 Columns of Matrix.cs new file mode 100644 index 0000000..4f66ab7 --- /dev/null +++ b/c-sharp/Matrix/C# Program to Interchange any 2 Columns of Matrix.cs @@ -0,0 +1,94 @@ +/* + * C# Program to Interchange any 2 Columns of a Matrix + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +class interchangecol +{ + int m, n; + int[,] a; + public interchangecol(int x, int y) + { + m = x; + n = y; + a = new int[m, n]; + } + public void readmatrix() + { + Console.WriteLine("Enter the Elements : "); + for (int i = 0; i < m; i++) + { + for (int j = 0; j < n; j++) + { + Console.WriteLine("a[{0},{1}] =", i, j); + a[i, j] = Convert.ToInt32(Console.ReadLine()); + } + } + } + public void printmax() + { + Console.WriteLine("Given Matrix : "); + for (int i = 0; i < m; i++) + { + for (int j = 0; j < n; j++) + { + Console.Write("{0}\t", a[i, j]); + } + Console.WriteLine(); + } + } + public void interchange() + { + Console.WriteLine("Enter the Column Number to Interchange : "); + int i = Convert.ToInt32(Console.ReadLine()); + Console.WriteLine("Enter the Column Number with which Interchange is to be Accomplished :"); + int j = Convert.ToInt32(Console.ReadLine()); + for (int k = 0; k < m; k++) + { + int temp = a[k, i-1]; + a[k, i-1] = a[k, j-1]; + a[k, j-1] = temp; + } + } + public static void Main() + { + int x, y; + interchangecol obj; + Console.Write("Enter the Number of Rows"); + x = Convert.ToInt32(Console.ReadLine()); + Console.Write("Enter the Number of Columns"); + y = Convert.ToInt32(Console.ReadLine()); + obj = new interchangecol(x, y); + obj.readmatrix(); + obj.printmax(); + obj.interchange(); + obj.printmax(); + Console.ReadLine(); + } +} + +/* +Enter the Number of Rows : 3 +Enter the Number of Columns : 3 +Enter the Elements : +a[0,0]=1 +a[0,1]=2 +a[0,2]=3 +a[1,0]=4 +a[1,1]=5 +a[1,2]=6 +a[2,0]=7 +a[2,1]=8 +a[2,2]=9 +Given Matrix is : +1 2 3 +4 5 6 +7 8 9 +Enter the Column Number to Interchange : 2 +Enter the Column Number with which Interchange is to be Accomplished : 3 +Given Matrix is : +1 3 2 +7 9 5 +4 6 8 \ No newline at end of file diff --git a/c-sharp/Matrix/C# Program to Interchange any 2 Rows of a Matrix.cs b/c-sharp/Matrix/C# Program to Interchange any 2 Rows of a Matrix.cs new file mode 100644 index 0000000..817e6ae --- /dev/null +++ b/c-sharp/Matrix/C# Program to Interchange any 2 Rows of a Matrix.cs @@ -0,0 +1,94 @@ +/* + * C# Program to Interchange any 2 Rows of a Matrix + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +class interchangerow +{ + int m, n; + int[,] a; + public interchangerow(int x, int y) + { + m = x; + n = y; + a = new int[m, n]; + } + public void readmatrix() + { + Console.WriteLine("Enter the Elements : "); + for (int i = 0; i < m; i++) + { + for (int j = 0; j < n; j++) + { + Console.WriteLine("a[{0},{1}]=", i, j); + a[i, j] = Convert.ToInt32(Console.ReadLine()); + } + } + } + public void printmax() + { + Console.WriteLine("Given Matrix : "); + for (int i = 0; i < m; i++) + { + for (int j = 0; j < n; j++) + { + Console.Write("{0}\t", a[i, j]); + } + Console.WriteLine(); + } + } + public void interchange() + { + Console.WriteLine("Enter the Row Number to Interchange : "); + int i = Convert.ToInt32(Console.ReadLine()); + Console.WriteLine("Enter the Row Number with which Interchange is to be Accomplished :"); + int j = Convert.ToInt32(Console.ReadLine()); + for (int k = 0; k < n; k++) + { + int temp = a[i - 1, k]; + a[i - 1, k] = a[j - 1, k]; + a[j - 1, k] = temp; + } + } + public static void Main() + { + int x, y; + interchangerow obj; + Console.Write("Enter the Number of Rows"); + x = Convert.ToInt32(Console.ReadLine()); + Console.Write("Enter the Number of Columns"); + y = Convert.ToInt32(Console.ReadLine()); + obj = new interchangerow(x, y); + obj.readmatrix(); + obj.printmax(); + obj.interchange(); + obj.printmax(); + Console.ReadLine(); + } +} + +/* +Enter the Number of Rows : 3 +Enter the Number of Columns : 3 +Enter the Elements : +a[0,0]=1 +a[0,1]=2 +a[0,2]=3 +a[1,0]=4 +a[1,1]=5 +a[1,2]=6 +a[2,0]=7 +a[2,1]=8 +a[2,2]=9 +Given Matrix is : +1 2 3 +4 5 6 +7 8 9 +Enter the Row Number to Interchange : 2 +Enter the Row Number with which Interchange is to be Accomplished : 3 +Given Matrix is : +1 2 3 +7 8 9 +4 5 6 \ No newline at end of file diff --git a/c-sharp/Matrix/C# Program to Perform Matrix Addition.cs b/c-sharp/Matrix/C# Program to Perform Matrix Addition.cs new file mode 100644 index 0000000..41ba760 --- /dev/null +++ b/c-sharp/Matrix/C# Program to Perform Matrix Addition.cs @@ -0,0 +1,99 @@ +/* + * C# Program to Perform Matrix Addition + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +namespace ConsoleApplication8 +{ +class Program +{ + public static void Main(string[] args) + { + int m, n,i,j; + Console.Write("Enter Number Of Rows And Columns Of Matrices A and B : "); + m = Convert.ToInt16(Console.ReadLine()); + n = Convert.ToInt16(Console.ReadLine()); + int[,] A = new int[10, 10]; + Console.Write("\nEnter The First Matrix : "); + for (i = 0; i < m; i++) + { + for (j = 0; j < n; j++) + { + A[i, j] = Convert.ToInt16(Console.ReadLine()); + } + } + int[,] B = new int[10, 10]; + Console.Write("\nEnter The Second Matrix:"); + for (i = 0; i < m; i++) + { + for (j = 0; j < n; j++) + { + B[i, j] = Convert.ToInt16(Console.ReadLine()); + } + } + Console.Clear(); + Console.WriteLine("\nMatrix A : "); + for (i = 0; i < m; i++) + { + for (j = 0; j < n; j++) + { + Console.Write(A[i, j] + "\t"); + } + Console.WriteLine(); + } + Console.WriteLine("\nMatrix B: "); + for (i = 0; i < m; i++) + { + for (j = 0; j < n; j++) + { + Console.Write(B[i, j] + "\t"); + } + Console.WriteLine(); + } + int[,] C = new int[10, 10]; + for (i = 0; i < m; i++) + { + for (j = 0; j < n; j++) + { + C[i, j] = A[i, j] + B[i, j]; + } + } + Console.Write("\nSum Matrix :"); + for (i = 0; i < m; i++) + { + for (j = 0; j < n; j++) + { + Console.Write(C[i, j] + "\t"); + } + Console.WriteLine(); + } + Console.Read(); + } +} +} + +/* +Enter Number Of Rows And Columns Of Matrices A and B : 3 3 +Enter the First Matrix : +1 2 3 +2 3 4 +3 4 5 +Enter the Second Matrix : +1 2 3 +2 1 4 +1 1 5 +Matrix A : +1 2 3 +2 3 4 +3 4 5 +Matrix B : +1 2 3 +2 1 4 +1 1 5 +Sum Matrix : +2 4 6 +4 4 8 +4 5 10 \ No newline at end of file diff --git a/c-sharp/Matrix/C# Program to Perform Matrix Multiplication.cs b/c-sharp/Matrix/C# Program to Perform Matrix Multiplication.cs new file mode 100644 index 0000000..29aa606 --- /dev/null +++ b/c-sharp/Matrix/C# Program to Perform Matrix Multiplication.cs @@ -0,0 +1,100 @@ +/* + * C# Program to Perform Matrix Multiplication + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +namespace matrix_multiplication +{ +class Program +{ + static void Main(string[] args) + { + int i, j,m,n; + Console.WriteLine("Enter the Number of Rows and Columns : "); + m = Convert.ToInt32(Console.ReadLine()); + n = Convert.ToInt32(Console.ReadLine()); + int[,] a = new int[m, n]; + Console.WriteLine("Enter the First Matrix"); + for (i = 0; i < m; i++) + { + for (j = 0; j < n; j++) + { + a[i, j] = int.Parse(Console.ReadLine()); + } + } + Console.WriteLine("First matrix is:"); + for (i = 0; i < m; i++) + { + for (j = 0; j < n; j++) + { + Console.Write(a[i, j] + "\t"); + } + Console.WriteLine(); + } + int[,] b = new int[m, n]; + Console.WriteLine("Enter the Second Matrix"); + for (i = 0; i < m; i++) + { + for (j = 0; j < n; j++) + { + b[i, j] = int.Parse(Console.ReadLine()); + } + } + Console.WriteLine("Second Matrix is :"); + for (i = 0; i < 2; i++) + { + for (j = 0; j < 2; j++) + { + Console.Write(b[i, j] + "\t"); + } + Console.WriteLine(); + } + Console.WriteLine("Matrix Multiplication is :"); + int[,] c = new int[m, n]; + for (i = 0; i < m; i++) + { + for (j = 0; j < n; j++) + { + c[i, j] = 0; + for (int k = 0; k < 2; k++) + { + c[i, j] += a[i, k] * b[k, j]; + } + } + } + for (i = 0; i < m; i++) + { + for (j = 0; j < n; j++) + { + Console.Write(c[i, j] + "\t"); + } + Console.WriteLine(); + } + Console.ReadKey(); + } +} +} + +/* +Enter the First Matrix +8 +7 +6 +10 +First Matrix is : +8 7 +6 10 +Enter the Second Matrix +4 +3 +2 +1 +Second Matrix is : +4 3 +2 1 +Matrix multiplication is : +46 31 +44 28 \ No newline at end of file diff --git a/c-sharp/Matrix/C# Program to Perform Matrix Subtraction.cs b/c-sharp/Matrix/C# Program to Perform Matrix Subtraction.cs new file mode 100644 index 0000000..eb6d0fb --- /dev/null +++ b/c-sharp/Matrix/C# Program to Perform Matrix Subtraction.cs @@ -0,0 +1,99 @@ +/* + * C# Program to Perform Matrix Subtraction + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +namespace Program +{ +class Program +{ + public static void Main(string[] args) + { + int m, n, i, j; + Console.Write("Enter Number Of Rows And Columns Of Matrices A and B : "); + m = Convert.ToInt16(Console.ReadLine()); + n = Convert.ToInt16(Console.ReadLine()); + int[,] A = new int[10, 10]; + Console.Write("\nEnter The First Matrix : "); + for (i = 0; i < m; i++) + { + for (j = 0; j < n; j++) + { + A[i, j] = Convert.ToInt16(Console.ReadLine()); + } + } + int[,] B = new int[10, 10]; + Console.Write("\nEnter The Second Matrix:"); + for (i = 0; i < m; i++) + { + for (j = 0; j < n; j++) + { + B[i, j] = Convert.ToInt16(Console.ReadLine()); + } + } + Console.Clear(); + Console.WriteLine("\nMatrix A : "); + for (i = 0; i < m; i++) + { + for (j = 0; j < n; j++) + { + Console.Write(A[i, j] + "\t"); + } + Console.WriteLine(); + } + Console.WriteLine("\nMatrix B: "); + for (i = 0; i < m; i++) + { + for (j = 0; j < n; j++) + { + Console.Write(B[i, j] + "\t"); + } + Console.WriteLine(); + } + int[,] C = new int[10, 10]; + for (i = 0; i < m; i++) + { + for (j = 0; j < n; j++) + { + C[i, j] = A[i, j] - B[i, j]; + } + } + Console.Write("\nDifference Matrix :"); + for (i = 0; i < m; i++) + { + for (j = 0; j < n; j++) + { + Console.Write(C[i, j] + "\t"); + } + Console.WriteLine(); + } + Console.Read(); + } +} +} + +/* +Enter Number Of Rows And Columns Of Matrices A and B : 3 3 +Enter the First Matrix : +9 8 7 +6 5 4 +7 8 9 +Enter the Second Matrix : +6 5 5 +3 4 2 +1 2 3 +Matrix A : +9 8 7 +6 5 4 +7 8 9 +Matrix B : +6 5 5 +3 4 2 +1 2 3 +Difference Matrix : +3 3 2 +3 1 2 +6 6 6 \ No newline at end of file diff --git a/c-sharp/Others/A hierarchy of timelines.cs b/c-sharp/Others/A hierarchy of timelines.cs new file mode 100644 index 0000000..160cc57 --- /dev/null +++ b/c-sharp/Others/A hierarchy of timelines.cs @@ -0,0 +1,47 @@ +A hierarchy of timelines + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + diff --git a/c-sharp/Others/A rectangle with curved corners.cs b/c-sharp/Others/A rectangle with curved corners.cs new file mode 100644 index 0000000..dd5a229 --- /dev/null +++ b/c-sharp/Others/A rectangle with curved corners.cs @@ -0,0 +1,10 @@ +A rectangle with curved corners + + + + + + \ No newline at end of file diff --git a/c-sharp/Others/About Dialog.cs b/c-sharp/Others/About Dialog.cs new file mode 100644 index 0000000..8bf98f3 --- /dev/null +++ b/c-sharp/Others/About Dialog.cs @@ -0,0 +1,22 @@ +About Dialog + + + + + + + + 1 + 2 + + + + + + You have successfully registered this product. + + diff --git a/c-sharp/Others/Add Image to Statusbar.cs b/c-sharp/Others/Add Image to Statusbar.cs new file mode 100644 index 0000000..f1d0634 --- /dev/null +++ b/c-sharp/Others/Add Image to Statusbar.cs @@ -0,0 +1,68 @@ +Add Image to Statusbar + + + + + + + + + + + + + + + diff --git a/c-sharp/Others/Add Thickness for Padding.cs b/c-sharp/Others/Add Thickness for Padding.cs new file mode 100644 index 0000000..353441c --- /dev/null +++ b/c-sharp/Others/Add Thickness for Padding.cs @@ -0,0 +1,57 @@ +Add Thickness for Padding + + + + + +//File:Window.xaml.cs +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Data; +using System.Windows.Documents; +using System.Windows.Input; +using System.Windows.Media; +using System.Windows.Media.Imaging; +using System.Windows.Navigation; +using System.Windows.Shapes; + +namespace WpfApplication1 +{ + + public partial class Window1 : Window + { + Button button1 = null; + Button button2 = null; + Button button3 = null; + + public Window1() + { + InitializeComponent(); + } + + private void Window_Loaded(object sender, RoutedEventArgs e) + { + button1 = new Button { Content = "Button", Width = 66, Height = 24 }; + Canvas.SetLeft(button1, 120); + Canvas.SetTop(button1, 36); + canvas1.Children.Add(button1); + button2 = new Button { Content = "Wider" }; + Canvas.SetLeft(button2, 48); + Canvas.SetTop(button2, 69); + canvas1.Children.Add(button2); + button3 = new Button { Content = "Button" }; + Canvas.SetLeft(button3, 72); + Canvas.SetTop(button3, 136); + button3.Padding = new Thickness(10, 2, 10, 2); + canvas1.Children.Add(button3); + } + } +} + diff --git a/c-sharp/Others/Add a control to a Panel.cs b/c-sharp/Others/Add a control to a Panel.cs new file mode 100644 index 0000000..ec5c2c3 --- /dev/null +++ b/c-sharp/Others/Add a control to a Panel.cs @@ -0,0 +1,45 @@ +Add a control to a Panel + + + + UI Element Collection - Methods + + + + Add Control + + + + + + + +//File:Window.xaml.cs +using System; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Documents; +using System.Windows.Navigation; +using System.Windows.Shapes; +using System.Windows.Data; +using System.Windows.Input; + +namespace ElemCollMethods +{ + + public partial class Pane1 : Page + { + System.Windows.Controls.Button btn, btn1, btn2, btn3; + + void AddButton(object sender, MouseButtonEventArgs e) + { + sp1.Children.Clear(); + btn = new Button(); + btn.Content = "New Button"; + sp1.Children.Add(btn); + } + } +} diff --git a/c-sharp/Others/Add buttons to a Canvas with code.cs b/c-sharp/Others/Add buttons to a Canvas with code.cs new file mode 100644 index 0000000..cc6ada6 --- /dev/null +++ b/c-sharp/Others/Add buttons to a Canvas with code.cs @@ -0,0 +1,57 @@ +Add buttons to a Canvas with code + + + + + +//File:Window.xaml.cs +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Data; +using System.Windows.Documents; +using System.Windows.Input; +using System.Windows.Media; +using System.Windows.Media.Imaging; +using System.Windows.Navigation; +using System.Windows.Shapes; + +namespace WpfApplication1 +{ + + public partial class Window1 : Window + { + Button button1 = null; + Button button2 = null; + Button button3 = null; + + public Window1() + { + InitializeComponent(); + } + + private void Window_Loaded(object sender, RoutedEventArgs e) + { + button1 = new Button { Content = "Button", Width = 80, Height = 24 }; + Canvas.SetLeft(button1, 120); + Canvas.SetTop(button1, 25); + canvas1.Children.Add(button1); + button2 = new Button { Content = "Wider" }; + Canvas.SetLeft(button2, 45); + Canvas.SetTop(button2, 68); + canvas1.Children.Add(button2); + button3 = new Button { Content = "Button" }; + Canvas.SetLeft(button3, 78); + Canvas.SetTop(button3, 120); + button3.Padding = new Thickness(9, 2, 9, 2); + canvas1.Children.Add(button3); + } + } +} + diff --git a/c-sharp/Others/Add child control.cs b/c-sharp/Others/Add child control.cs new file mode 100644 index 0000000..99d2ca8 --- /dev/null +++ b/c-sharp/Others/Add child control.cs @@ -0,0 +1,46 @@ +Add child control + + + + UI Element Collection - Methods + + + + Add Control + + + + + + +//File:Window.xaml.cs + +using System; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Documents; +using System.Windows.Navigation; +using System.Windows.Shapes; +using System.Windows.Data; +using System.Windows.Input; + +namespace ElemCollMethods +{ + + public partial class Pane1 : Page + { + System.Windows.Controls.Button btn, btn1, btn2, btn3; + + void AddButton(object sender, MouseButtonEventArgs e) + { + sp1.Children.Clear(); + btn = new Button(); + btn.Content = "New Button"; + sp1.Children.Add(btn); + } + } +} + diff --git a/c-sharp/Others/Add control to a form window.cs b/c-sharp/Others/Add control to a form window.cs new file mode 100644 index 0000000..3888ac3 --- /dev/null +++ b/c-sharp/Others/Add control to a form window.cs @@ -0,0 +1,43 @@ +Add control to a form window + +using System; +using System.Windows.Forms; +using System.Drawing; + +public class PushMe2 : Form { + + Button pushMeButton; + + public PushMe2() { + pushMeButton = new Button(); + pushMeButton.Text = "Push Me"; + pushMeButton.Height = 66; + pushMeButton.Width = 90; + pushMeButton.Top = 70; + pushMeButton.Left = 80; + + pushMeButton.Click += new EventHandler(ButtonClicked); + + this.Controls.Add(pushMeButton); + + this.Height = 240; + this.Width = 240; + this.StartPosition = FormStartPosition.CenterScreen; + this.Visible = true; + } + + public void ButtonClicked(object source, EventArgs e) { + Button b = (Button)source; + if ( b.Text == "Push Me" ) { + b.Text = "Ouch"; + } + else { + b.Text = "Push Me"; + } + } + + static void Main() { + Application.Run(new PushMe2()); + } +} + diff --git a/c-sharp/Others/Add control to a window.cs b/c-sharp/Others/Add control to a window.cs new file mode 100644 index 0000000..d3d6c05 --- /dev/null +++ b/c-sharp/Others/Add control to a window.cs @@ -0,0 +1,34 @@ +Add control to a window + +using System; +using System.Windows.Forms; + +public class MyForm : Form{ + + void btn1_onclick(object sender, EventArgs e) + { + Text = "Sender: " + sender.ToString() + " - Event: " + e.ToString(); + } + + void btn1_onclick2(object sender, EventArgs e){ + Console.WriteLine(String.Format("Sender: {0} - Event: {1}", sender.ToString(), e.ToString())); + } + + public MyForm() { + Text = "I am Superman"; + + Button btn1 = new Button(); + btn1.Text = "Click Me"; + this.Controls.Add(btn1); + + btn1.Click += new EventHandler(btn1_onclick); + btn1.Click += new EventHandler(btn1_onclick2); + } + + public static void Main() + { + Application.Run(new MyForm()); + } + +} + diff --git a/c-sharp/Others/Add image to Button.cs b/c-sharp/Others/Add image to Button.cs new file mode 100644 index 0000000..e32379b --- /dev/null +++ b/c-sharp/Others/Add image to Button.cs @@ -0,0 +1,53 @@ +Add image to Button + +using System; +using System.Collections.Generic; +using System.ComponentModel; +using System.Data; +using System.Drawing; +using System.Text; +using System.Windows.Forms; + +public class Form1 : Form +{ + private System.Windows.Forms.Button button1; + + public Form1() { + InitializeComponent(); + } + + private void InitializeComponent() + { + this.button1 = new System.Windows.Forms.Button(); + this.SuspendLayout(); + + this.button1.Image = new Bitmap("Sun.jpg"); + this.button1.ImageAlign = System.Drawing.ContentAlignment.TopRight; + this.button1.Location = new System.Drawing.Point(13, 96); + this.button1.Name = "button1"; + this.button1.Size = new System.Drawing.Size(120, 69); + this.button1.TabIndex = 1; + this.button1.Text = "button1"; + this.button1.TextAlign = System.Drawing.ContentAlignment.MiddleLeft; + this.button1.UseVisualStyleBackColor = true; + + this.AutoScaleDimensions = new System.Drawing.SizeF(6F, 13F); + this.AutoScaleMode = System.Windows.Forms.AutoScaleMode.Font; + this.ClientSize = new System.Drawing.Size(320, 250); + + this.Controls.Add(this.button1); + this.Font = new System.Drawing.Font("Arial", 8.25F, System.Drawing.FontStyle.Regular, System.Drawing.GraphicsUnit.Point, ((byte)(0))); + this.Name = "ImagesInCommonControls"; + this.Text = "ImagesInCommonControls"; + this.ResumeLayout(false); + + } + + [STAThread] + static void Main() + { + Application.EnableVisualStyles(); + Application.Run(new Form1()); + } + +} diff --git a/c-sharp/Others/Add items to combo box.cs b/c-sharp/Others/Add items to combo box.cs new file mode 100644 index 0000000..22a57a1 --- /dev/null +++ b/c-sharp/Others/Add items to combo box.cs @@ -0,0 +1,41 @@ +Add items to combo box + +using System; +using System.Drawing; +using System.Windows.Forms; +public class Select : Form { + private Button draw = new Button(); + private ComboBox color = new ComboBox(); + + public Select( ) { + draw.Text = "Draw"; + color.Text = "Choose a color"; + Size = new Size(400,240); + + int w = 20; + draw.Location = new Point(20,30); + color.Location = new Point(w += 10 + color.Width, 30); + + color.Items.Add("Black"); + color.Items.Add("Red"); + color.Items.Add("Blue"); + + Controls.Add(draw); + Controls.Add(color); + + draw.Click += new EventHandler(Draw_Click); + } + + protected void Draw_Click(Object sender, EventArgs e) { + if (color.SelectedItem.ToString() == "Red" ) + Console.WriteLine("It is red."); + else if (color.SelectedItem.ToString() == "Red") + Console.WriteLine("It is Red."); + else + Console.WriteLine("It is blue."); + } + static void Main() { + Application.Run(new Select()); + } +} + diff --git a/c-sharp/Others/Adding Hyperlink to TextBlock.cs b/c-sharp/Others/Adding Hyperlink to TextBlock.cs new file mode 100644 index 0000000..54bb7da --- /dev/null +++ b/c-sharp/Others/Adding Hyperlink to TextBlock.cs @@ -0,0 +1,16 @@ +Adding Hyperlink to TextBlock + + + + + This is a simple page. + Click here. + + + + + + diff --git a/c-sharp/Others/All Mouse Cursors.cs b/c-sharp/Others/All Mouse Cursors.cs new file mode 100644 index 0000000..a0ce20f --- /dev/null +++ b/c-sharp/Others/All Mouse Cursors.cs @@ -0,0 +1,77 @@ +All Mouse Cursors + +using System; +using System.Drawing; +using System.Windows.Forms; + +class MouseCursors: Form +{ + Cursor[] acursor = + { + Cursors.AppStarting, Cursors.Arrow, Cursors.Cross, + Cursors.Default, Cursors.Hand, Cursors.Help, + Cursors.HSplit, Cursors.IBeam, Cursors.No, + Cursors.NoMove2D, Cursors.NoMoveHoriz, Cursors.NoMoveVert, + Cursors.PanEast, Cursors.PanNE, Cursors.PanNorth, + Cursors.PanNW, Cursors.PanSE, Cursors.PanSouth, + Cursors.PanSW, Cursors.PanWest, Cursors.SizeAll, + Cursors.SizeNESW, Cursors.SizeNS, Cursors.SizeNWSE, + Cursors.SizeWE, Cursors.UpArrow, Cursors.VSplit, + Cursors.WaitCursor + }; + string[] astrCursor = + { + "AppStarting", "Arrow", "Cross", + "Default", "Hand", "Help", + "HSplit", "IBeam", "No", + "NoMove2D", "NoMoveHoriz", "NoMoveVert", + "PanEast", "PanNE", "PanNorth", + "PanNW", "PanSE", "PanSouth", + "PanSW", "PanWest", "SizeAll", + "SizeNESW", "SizeNS", "SizeNWSE", + "SizeWE", "UpArrow", "VSplit", + "WaitCursor" + }; + + public static void Main() + { + Application.Run(new MouseCursors()); + } + public MouseCursors() + { + Text = "Mouse Cursors"; + ResizeRedraw = true; + } + protected override void OnMouseMove(MouseEventArgs mea) + { + int x = Math.Max(0, Math.Min(3, mea.X / (ClientSize.Width / 4))); + int y = Math.Max(0, Math.Min(6, mea.Y / (ClientSize.Height / 7))); + + Cursor.Current = acursor[4 * y + x]; + } + protected override void OnPaint(PaintEventArgs pea) + { + Graphics grfx = pea.Graphics; + Brush brush = new SolidBrush(ForeColor); + Pen pen = new Pen(ForeColor); + StringFormat strfmt = new StringFormat(); + + strfmt.LineAlignment = strfmt.Alignment = StringAlignment.Center; + + for (int y = 0; y < 7; y++){ + for (int x = 0; x < 4; x++) + { + Rectangle rect = Rectangle.FromLTRB( + x * ClientSize.Width / 4, + y * ClientSize.Height / 7, + (x + 1) * ClientSize.Width / 4, + (y + 1) * ClientSize.Height / 7); + + grfx.DrawRectangle(pen, rect); + grfx.DrawString(astrCursor[4 * y + x], + Font, brush, rect, strfmt); + } + } + } +} + diff --git a/c-sharp/Others/An ellipse that has been scaled by 20%.cs b/c-sharp/Others/An ellipse that has been scaled by 20%.cs new file mode 100644 index 0000000..6e15e89 --- /dev/null +++ b/c-sharp/Others/An ellipse that has been scaled by 20%.cs @@ -0,0 +1,17 @@ +An ellipse that has been scaled by 20% + + + + + + + + + + + + + + diff --git a/c-sharp/Others/Anchor Two Buttons.cs b/c-sharp/Others/Anchor Two Buttons.cs new file mode 100644 index 0000000..cabf7df --- /dev/null +++ b/c-sharp/Others/Anchor Two Buttons.cs @@ -0,0 +1,46 @@ +Anchor Two Buttons + +using System; +using System.Drawing; +using System.Windows.Forms; + +class TwoButtonsAnchor: Form +{ + public static void Main() + { + Application.Run(new TwoButtonsAnchor()); + } + public TwoButtonsAnchor() + { + ResizeRedraw = true; + + int cxBtn = 5 * Font.Height; + int cyBtn = 2 * Font.Height; + int dxBtn = Font.Height; + + Button btn = new Button(); + btn.Parent = this; + btn.Text = "&Larger"; + btn.Location = new Point(dxBtn, dxBtn); + btn.Size = new Size(cxBtn, cyBtn); + btn.Click += new EventHandler(ButtonLargerOnClick); + + btn = new Button(); + btn.Parent = this; + btn.Text = "&Smaller"; + btn.Location = new Point(ClientSize.Width - cxBtn - dxBtn, + ClientSize.Height - cyBtn - dxBtn); + btn.Size = new Size(cxBtn, cyBtn); + btn.Anchor = AnchorStyles.Right | AnchorStyles.Bottom; + btn.Click += new EventHandler(ButtonSmallerOnClick); + } + void ButtonLargerOnClick(object obj, EventArgs ea) + { + Console.WriteLine("large"); + } + void ButtonSmallerOnClick(object obj, EventArgs ea) + { + Console.WriteLine("small"); + } +} + diff --git a/c-sharp/Others/Animate EndPoint.cs b/c-sharp/Others/Animate EndPoint.cs new file mode 100644 index 0000000..9c644cc --- /dev/null +++ b/c-sharp/Others/Animate EndPoint.cs @@ -0,0 +1,28 @@ +Animate EndPoint + + + + + + + + + + + + + + + + + + + + + + diff --git a/c-sharp/Others/Animate the background color.cs b/c-sharp/Others/Animate the background color.cs new file mode 100644 index 0000000..7e92a4b --- /dev/null +++ b/c-sharp/Others/Animate the background color.cs @@ -0,0 +1,20 @@ +Animate the background color + + + + + + + + + + + + + + + diff --git a/c-sharp/Others/Animation In Style.cs b/c-sharp/Others/Animation In Style.cs new file mode 100644 index 0000000..73e1190 --- /dev/null +++ b/c-sharp/Others/Animation In Style.cs @@ -0,0 +1,30 @@ +Animation In Style + + + + + + + + + + diff --git a/c-sharp/Others/Application Exit event.cs b/c-sharp/Others/Application Exit event.cs new file mode 100644 index 0000000..9998f07 --- /dev/null +++ b/c-sharp/Others/Application Exit event.cs @@ -0,0 +1,25 @@ +Application Exit event + + + +//File:Window.xaml.cs + +using System; +using System.Windows; +using System.Windows.Controls; + +namespace SimpleXamlApp +{ + public partial class MyApp : Application + { + void AppExit(object sender, ExitEventArgs e) + { + MessageBox.Show("App has exited"); + } + } +} + diff --git a/c-sharp/Others/Application Startup event.cs b/c-sharp/Others/Application Startup event.cs new file mode 100644 index 0000000..5b11e65 --- /dev/null +++ b/c-sharp/Others/Application Startup event.cs @@ -0,0 +1,30 @@ +Application Startup event + + + + +//File:Window.xaml.cs +using System; +using System.Windows; +using System.Data; +using System.Xml; +using System.Configuration; +using System.Windows.Media; + +namespace Microsoft.Samples.WinFX.AlarmClock +{ + + public partial class MyApp : Application + { + void AppStartup(object sender, StartupEventArgs e) + { + + } + + } +} + diff --git a/c-sharp/Others/Application.GetResourceStream.cs b/c-sharp/Others/Application.GetResourceStream.cs new file mode 100644 index 0000000..ab005b1 --- /dev/null +++ b/c-sharp/Others/Application.GetResourceStream.cs @@ -0,0 +1,47 @@ +Application.GetResourceStream + + + + + + +//File:Window.xaml.cs +using System; +using System.Collections.Generic; +using System.Text; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Data; +using System.Windows.Documents; +using System.Windows.Input; +using System.Windows.Media; +using System.Windows.Media.Imaging; +using System.Windows.Shapes; +using System.IO; +using System.Reflection; +using System.Diagnostics; +using System.Threading; +using System.Resources; +using System.Collections; +using System.Windows.Resources; + +namespace BinaryResources +{ + public partial class Window1 : System.Windows.Window + { + public Window1() + { + InitializeComponent(); + + Uri resourcePath = new Uri("file:///c:/image.gif", UriKind.Relative); + StreamResourceInfo ri = Application.GetResourceStream(resourcePath); + Stream data = ri.Stream; + + // data; + } + } +} + diff --git a/c-sharp/Others/Apply Syntax Highlighting in a Text Control.cs b/c-sharp/Others/Apply Syntax Highlighting in a Text Control.cs new file mode 100644 index 0000000..59ca8b4 --- /dev/null +++ b/c-sharp/Others/Apply Syntax Highlighting in a Text Control.cs @@ -0,0 +1,57 @@ +Apply Syntax Highlighting in a Text Control + + + + + + +//File:Window.xaml.cs +using System.Windows; +using System.Windows.Controls; +using System.Windows.Documents; +using System.Windows.Media; + +namespace WpfApplication1 +{ + + public partial class Window1 : Window + { + public Window1() + { + InitializeComponent(); + } + + private void RichTextBox_TextChanged(object sender, TextChangedEventArgs e) + { + + TextRange textRange = new TextRange(rtbTextContent.Document.ContentStart, rtbTextContent.Document.ContentEnd); + rtbTextContent.TextChanged -= RichTextBox_TextChanged; + textRange.ClearAllProperties(); + ApplyFormatting(); + rtbTextContent.TextChanged += RichTextBox_TextChanged; + } + + private void ApplyFormatting() + { + TextPointer tp = rtbTextContent.Document.ContentStart; + tp = FindNextString(tp); + + TextPointer textRangeEnd = tp.GetPositionAtOffset(1, LogicalDirection.Forward); + + TextRange tokenTextRange = new TextRange(tp, tp.GetPositionAtOffset(1, LogicalDirection.Forward)); + + tokenTextRange.ApplyPropertyValue(TextElement.ForegroundProperty, Brushes.Blue); + } + + private TextPointer FindNextString(TextPointer tp) + { + char[] buffer = new char[1]; + tp.GetTextInRun(LogicalDirection.Forward, buffer, 0, 1); + return tp; + } + } +} + diff --git a/c-sharp/Others/AssemblyInfo.cs b/c-sharp/Others/AssemblyInfo.cs new file mode 100644 index 0000000..9838d80 --- /dev/null +++ b/c-sharp/Others/AssemblyInfo.cs @@ -0,0 +1,36 @@ +using System.Reflection; +using System.Runtime.CompilerServices; +using System.Runtime.InteropServices; + +// General Information about an assembly is controlled through the following +// set of attributes. Change these attribute values to modify the information +// associated with an assembly. +[assembly: AssemblyTitle("data-structures-csharp")] +[assembly: AssemblyDescription("")] +[assembly: AssemblyConfiguration("")] +[assembly: AssemblyCompany("")] +[assembly: AssemblyProduct("data-structures-csharp")] +[assembly: AssemblyCopyright("Copyright © 2013")] +[assembly: AssemblyTrademark("")] +[assembly: AssemblyCulture("")] + +// Setting ComVisible to false makes the types in this assembly not visible +// to COM components. If you need to access a type in this assembly from +// COM, set the ComVisible attribute to true on that type. +[assembly: ComVisible(false)] + +// The following GUID is for the ID of the typelib if this project is exposed to COM +[assembly: Guid("0f8e9ce5-3006-4b10-b98b-65e55aa15862")] + +// Version information for an assembly consists of the following four values: +// +// Major Version +// Minor Version +// Build Number +// Revision +// +// You can specify all the values or you can default the Build and Revision Numbers +// by using the '*' as shown below: +// [assembly: AssemblyVersion("1.0.*")] +[assembly: AssemblyVersion("1.0.0.0")] +[assembly: AssemblyFileVersion("1.0.0.0")] diff --git a/c-sharp/Others/AutoScroll Window.cs b/c-sharp/Others/AutoScroll Window.cs new file mode 100644 index 0000000..32353b2 --- /dev/null +++ b/c-sharp/Others/AutoScroll Window.cs @@ -0,0 +1,34 @@ +AutoScroll Window + + using System; + using System.Drawing; + using System.Collections; + using System.ComponentModel; + using System.Windows.Forms; + using System.Data; + + public class Form1 : System.Windows.Forms.Form + { + private Button myButton; + + public Form1() + { + this.AutoScaleBaseSize = new System.Drawing.Size(8, 18); + this.ClientSize = new System.Drawing.Size(240, 280); + + this.AutoScroll=true; + + myButton = new Button(); + myButton.Text = "Superman"; + myButton.Location = new System.Drawing.Point(66, 36); + myButton.Size = new System.Drawing.Size(160, 75); + + Controls.Add(myButton); + } + + static void Main() + { + Application.Run(new Form1()); + } + } + diff --git a/c-sharp/Others/Automatic Width and Height.cs b/c-sharp/Others/Automatic Width and Height.cs new file mode 100644 index 0000000..08bd7d5 --- /dev/null +++ b/c-sharp/Others/Automatic Width and Height.cs @@ -0,0 +1,24 @@ +Automatic Width and Height + + + + + + + + + + + + + This is a test.: + This is a test + This is a test: + This is a test + This is a test: + This is a test + + + diff --git a/c-sharp/Others/BPlusTree.cs b/c-sharp/Others/BPlusTree.cs new file mode 100644 index 0000000..584b876 --- /dev/null +++ b/c-sharp/Others/BPlusTree.cs @@ -0,0 +1,56 @@ +using System; +using System.Diagnostics.Contracts; + + +namespace DataStructures.BPlusTreeSpace +{ + [Serializable] + public partial class BPlusTree + where TKey : IComparable + { + private INode root; + /// + /// the maximum number of key value pairs in the leaf node, M must be > 0 + /// + public readonly int NumberOfValuesInLeafNode; + /// + /// the maximum number of keys in inner node, the number of pointer is N+1, N must be > 2 + /// + public readonly int NumberOfKeysInIntermediateNode; + + [ContractInvariantMethod] + private void ObjectInvariant() + { + Contract.Invariant(NumberOfValuesInLeafNode > 0); + Contract.Invariant(NumberOfKeysInIntermediateNode > 2); + } + + public BPlusTree(int m, int n) + { + Contract.Requires(m > 0); + Contract.Requires(n > 2); + + NumberOfValuesInLeafNode = m; + NumberOfKeysInIntermediateNode = n; + } + + private bool Find(TKey key, INode node) + { + Contract.Requires(key != null); + Contract.Requires(node != null); + + if (node is LeafNode) + { + } + return false; + } + + [Pure] + public bool Find(TKey key) + { + Contract.Requires(key != null); + return Find(key, root); + } + + } +} diff --git a/c-sharp/Others/Basic DialogBox.cs b/c-sharp/Others/Basic DialogBox.cs new file mode 100644 index 0000000..1b2af66 --- /dev/null +++ b/c-sharp/Others/Basic DialogBox.cs @@ -0,0 +1,19 @@ +Basic DialogBox + + + + + + + + + + + + This is a test. + + + diff --git a/c-sharp/Others/Bind a TabControl to a data source.cs b/c-sharp/Others/Bind a TabControl to a data source.cs new file mode 100644 index 0000000..1e559e2 --- /dev/null +++ b/c-sharp/Others/Bind a TabControl to a data source.cs @@ -0,0 +1,79 @@ +Bind a TabControl to a data source + + + + + + + + + + + + + + + + + + +//File:Window.xaml.cs +using System; +using System.Collections.Generic; +using System.Text; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Data; +using System.Windows.Documents; +using System.Windows.Input; +using System.Windows.Media; +using System.Windows.Media.Imaging; +using System.Windows.Shapes; +using System.Collections.ObjectModel; +namespace TabControlUsingItemTemplate +{ + public partial class Window1 : System.Windows.Window + { + public Window1() + { + InitializeComponent(); + } + } + public class TabItemData + { + private string _header; + private string _content; + + public TabItemData(string header, string content) + { + _header = header; + _content = content; + } + public string Header + { + get { return _header; } + } + public string Content + { + get { return _content; } + } + } + public class TabList : ObservableCollection + { + public TabList(): base() + { + + Add(new TabItemData("Header 1", "Content 1")); + Add(new TabItemData("Header 2", "Content 2")); + Add(new TabItemData("Header 3", "Content 3")); + + } + } +} + diff --git a/c-sharp/Others/Bind current time to Button.cs b/c-sharp/Others/Bind current time to Button.cs new file mode 100644 index 0000000..68b8946 --- /dev/null +++ b/c-sharp/Others/Bind current time to Button.cs @@ -0,0 +1,13 @@ +Bind current time to Button + + + + + + + + + + + +//File:Window.xaml.cs +using System; +using System.Collections.Generic; +using System.Text; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Data; +using System.Windows.Documents; +using System.Windows.Input; +using System.Windows.Media; +using System.Windows.Media.Imaging; +using System.Windows.Shapes; + + +namespace WpfApplication1 +{ + public partial class Window1 : System.Windows.Window + { + + public Window1() + { + InitializeComponent(); + } + void ButtonClicked(object sender, RoutedEventArgs e) + { + MessageBox.Show("Button clicked"); + } + } +} + diff --git a/c-sharp/Others/Button Image, Size, Parent.cs b/c-sharp/Others/Button Image, Size, Parent.cs new file mode 100644 index 0000000..8c82672 --- /dev/null +++ b/c-sharp/Others/Button Image, Size, Parent.cs @@ -0,0 +1,63 @@ +Button Image, Size, Parent + +using System; +using System.Drawing; +using System.Windows.Forms; + +class BitmapButtons: Form +{ + int cxBtn, cyBtn, dxBtn; + Button btnLarger, btnSmaller; + + public static void Main() + { + Application.Run(new BitmapButtons()); + } + public BitmapButtons() + { + ResizeRedraw = true; + + dxBtn = Font.Height; + btnLarger = new Button(); + btnLarger.Parent = this; + btnLarger.Image = new Bitmap(GetType(), "LargerButton.bmp") ; + + cxBtn = btnLarger.Image.Width + 8; + cyBtn = btnLarger.Image.Height + 8; + + btnLarger.Size = new Size(cxBtn, cyBtn); + btnLarger.Click += new EventHandler(ButtonLargerOnClick); + + btnSmaller = new Button(); + btnSmaller.Parent = this; + btnSmaller.Image = new Bitmap(GetType(), "SmallerButton.bmp"); + btnSmaller.Size = new Size(cxBtn, cyBtn); + btnSmaller.Click += new EventHandler(ButtonSmallerOnClick); + + OnResize(EventArgs.Empty); + } + protected override void OnResize(EventArgs ea) + { + base.OnResize(ea); + + btnLarger.Location = new Point(ClientSize.Width / 2 - cxBtn - dxBtn / 2, + (ClientSize.Height - cyBtn) / 2); + btnSmaller.Location = new Point(ClientSize.Width / 2 + dxBtn / 2, + (ClientSize.Height - cyBtn) / 2); + } + void ButtonLargerOnClick(object obj, EventArgs ea) + { + Left = 40; + Top = 40; + Width = 40; + Height = 40; + } + void ButtonSmallerOnClick(object obj, EventArgs ea) + { + Left = 240; + Top = 240; + Width = 25; + Height = 25; + } +} + diff --git a/c-sharp/Others/Capture Mouse Ellipse.cs b/c-sharp/Others/Capture Mouse Ellipse.cs new file mode 100644 index 0000000..211b277 --- /dev/null +++ b/c-sharp/Others/Capture Mouse Ellipse.cs @@ -0,0 +1,96 @@ +Capture Mouse Ellipse + + + + + + + + +//File:Window.xaml.cs +using System; +using System.Collections.Generic; +using System.Text; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Data; +using System.Windows.Documents; +using System.Windows.Input; +using System.Windows.Media; +using System.Windows.Media.Imaging; +using System.Windows.Shapes; +using System.Diagnostics; + + +namespace WpfApplication1 +{ + public partial class Window1 : System.Windows.Window + { + public Window1() + { + InitializeComponent(); + + Ellipse.MouseDown += Ellipse_MouseDown; + + } + + void Ellipse_MouseDown(object sender, MouseButtonEventArgs e) + { + Mouse.Capture(Ellipse); + } + + + } +} + +Capture Mouse Ellipse + + + + + + + + +//File:Window.xaml.cs +using System; +using System.Collections.Generic; +using System.Text; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Data; +using System.Windows.Documents; +using System.Windows.Input; +using System.Windows.Media; +using System.Windows.Media.Imaging; +using System.Windows.Shapes; +using System.Diagnostics; + + +namespace WpfApplication1 +{ + public partial class Window1 : System.Windows.Window + { + public Window1() + { + InitializeComponent(); + + Ellipse.MouseDown += Ellipse_MouseDown; + + } + + void Ellipse_MouseDown(object sender, MouseButtonEventArgs e) + { + Mouse.Capture(Ellipse); + } + + + } +} + diff --git a/c-sharp/Others/Cast event sender to a control.cs b/c-sharp/Others/Cast event sender to a control.cs new file mode 100644 index 0000000..c0c9fb3 --- /dev/null +++ b/c-sharp/Others/Cast event sender to a control.cs @@ -0,0 +1,35 @@ +Cast event sender to a control + + + + + +//File:Window.xaml.cs +using System; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Input; + +namespace MyNameSpace.IncludeApplicationDefinition +{ + public partial class MyWindow : Window + { + public MyWindow() + { + InitializeComponent(); + } + void ButtonOnClick(object sender, RoutedEventArgs args) + { + Button btn = sender as Button; + MessageBox.Show(btn.Content + "'clicked."); + } + } +} + diff --git a/c-sharp/Others/Center form window.cs b/c-sharp/Others/Center form window.cs new file mode 100644 index 0000000..5df7c21 --- /dev/null +++ b/c-sharp/Others/Center form window.cs @@ -0,0 +1,34 @@ +Center form window + + using System; + using System.Drawing; + using System.Collections; + using System.ComponentModel; + using System.Windows.Forms; + using System.Data; + + public class Form1 : System.Windows.Forms.Form + { + private Button myButton; + + public Form1() + { + this.AutoScaleBaseSize = new System.Drawing.Size(8, 18); + this.ClientSize = new System.Drawing.Size(320, 260); + + this.StartPosition=FormStartPosition.CenterScreen; +// CenterToScreen(); + + myButton = new Button(); + myButton.Text = "Superman"; + myButton.Location = new System.Drawing.Point(69, 36); + myButton.Size = new System.Drawing.Size(140, 45); + + Controls.Add(myButton); + } + static void Main() + { + Application.Run(new Form1()); + } + } + diff --git a/c-sharp/Others/Change Button text.cs b/c-sharp/Others/Change Button text.cs new file mode 100644 index 0000000..8180c31 --- /dev/null +++ b/c-sharp/Others/Change Button text.cs @@ -0,0 +1,43 @@ +Change Button text + +using System; +using System.Windows.Forms; +using System.Drawing; + +public class PushMe2 : Form { + + Button pushMeButton; + + public PushMe2() { + pushMeButton = new Button(); + pushMeButton.Text = "Push Me"; + pushMeButton.Height = 50; + pushMeButton.Width = 96; + pushMeButton.Top = 70; + pushMeButton.Left = 70; + + pushMeButton.Click += new EventHandler(ButtonClicked); + + this.Controls.Add(pushMeButton); + + this.Height = 250; + this.Width = 250; + this.StartPosition = FormStartPosition.CenterScreen; + this.Visible = true; + } + + public void ButtonClicked(object source, EventArgs e) { + Button b = (Button)source; + if ( b.Text == "Push Me" ) { + b.Text = "Ouch"; + } + else { + b.Text = "Push Me"; + } + } + + static void Main() { + Application.Run(new PushMe2()); + } +} + diff --git a/c-sharp/Others/Change StackPanel Orientation.cs b/c-sharp/Others/Change StackPanel Orientation.cs new file mode 100644 index 0000000..0ccf5ab --- /dev/null +++ b/c-sharp/Others/Change StackPanel Orientation.cs @@ -0,0 +1,55 @@ +Change StackPanel Orientation + + + + + + + + + + + Use Vertical Orientation + + + + + +//File:Window.xaml.cs +using System; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Data; +using System.Windows.Documents; +using System.Windows.Media; +using System.Windows.Media.Imaging; +using System.Windows.Shapes; + +namespace LayoutPanels +{ + public partial class SimpleStack : Window + { + + public SimpleStack() + { + InitializeComponent(); + } + + private void chkVertical_Checked(object sender, RoutedEventArgs e) + { + stackPanel1.Orientation = Orientation.Horizontal; + } + + private void chkVertical_Unchecked(object sender, RoutedEventArgs e) + { + stackPanel1.Orientation = Orientation.Vertical; + } + } +} + diff --git a/c-sharp/Others/Check Spelling Error.cs b/c-sharp/Others/Check Spelling Error.cs new file mode 100644 index 0000000..f1b72f7 --- /dev/null +++ b/c-sharp/Others/Check Spelling Error.cs @@ -0,0 +1,59 @@ +Check Spelling Error + + + + + + "); + + XmlReader reader = XmlReader.Create(sr); + + Button dynamicButton = (Button)XamlReader.Load(reader); + + this.grid1.Children.Add(dynamicButton); + + dynamicButton.Click += button1_Click; + + } + + private void button1_Click(object sender, RoutedEventArgs e) + { + MessageBox.Show("Dynamic Button Loaded From XAML String"); + } + + } +} + diff --git a/c-sharp/Others/Create Full Color Bitmap.cs b/c-sharp/Others/Create Full Color Bitmap.cs new file mode 100644 index 0000000..4fb0323 --- /dev/null +++ b/c-sharp/Others/Create Full Color Bitmap.cs @@ -0,0 +1,40 @@ +Create Full Color Bitmap + +using System; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Input; +using System.Windows.Media; +using System.Windows.Media.Imaging; + + public class CreateFullColorBitmap : Window + { + [STAThread] + public static void Main() + { + Application app = new Application(); + app.Run(new CreateFullColorBitmap()); + } + public CreateFullColorBitmap() + { + int[] array = new int[256 * 256]; + + for (int x = 0; x < 256; x++) + for (int j = 0; j < 256; j++) + { + int b = x; + int g = 0; + int r = j; + + array[256 * j + x] = b | (g << 8) | (r << 16); + } + BitmapSource bitmap= BitmapSource.Create(256, 256, 96, 96, PixelFormats.Bgr32, + null, array, 256 * 4); + + Image img = new Image(); + img.Source = bitmap; + + Content = img; + } + } + diff --git a/c-sharp/Others/Create Indexed Bitmap.cs b/c-sharp/Others/Create Indexed Bitmap.cs new file mode 100644 index 0000000..c3f68f5 --- /dev/null +++ b/c-sharp/Others/Create Indexed Bitmap.cs @@ -0,0 +1,42 @@ +Create Indexed Bitmap + +using System; +using System.Collections.Generic; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Input; +using System.Windows.Media; +using System.Windows.Media.Imaging; + + public class CreateIndexedBitmap : Window + { + [STAThread] + public static void Main() + { + Application app = new Application(); + app.Run(new CreateIndexedBitmap()); + } + public CreateIndexedBitmap() + { + List colors = new List(); + + for (int r = 0; r < 256; r += 17) + for (int j = 0; j < 256; j += 17) + colors.Add(Color.FromRgb((byte)r, 0, (byte)j)); + + BitmapPalette palette = new BitmapPalette(colors); + + byte[] array = new byte[256 * 256]; + + for (int x = 0; x < 256; x++) + for (int y = 0; y < 256; y++) + array[256 * y + x] = (byte)(((int)Math.Round(y / 17.0) << 4) | + (int)Math.Round(x / 17.0)); + + BitmapSource bitmap = BitmapSource.Create(256, 256, 96, 96, PixelFormats.Indexed8,palette, array, 256); + Image img = new Image(); + img.Source = bitmap; + Content = img; + } + } + diff --git a/c-sharp/Others/Create RoutedCommand from InputGestureCollection.cs b/c-sharp/Others/Create RoutedCommand from InputGestureCollection.cs new file mode 100644 index 0000000..fd71745 --- /dev/null +++ b/c-sharp/Others/Create RoutedCommand from InputGestureCollection.cs @@ -0,0 +1,45 @@ +Create RoutedCommand from InputGestureCollection + + + + + + + + +//File:Window.xaml.cs + +using System; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Input; + +namespace Commands +{ + public partial class Window1 : Window + { + + RoutedCommand myCmd; + + Window1() + { + InputGestureCollection myInputs = new InputGestureCollection(); + myInputs.Add(new KeyGesture(Key.G,ModifierKeys.Control | ModifierKeys.Shift)); + myCmd = new RoutedCommand("Go", typeof(Window1), myInputs); + } + + private void ExecuteCommandClickEvent(object sender, RoutedEventArgs e) + { + myCmd.Execute(sender,null); + } + } +} + diff --git a/c-sharp/Others/Create a ProgressBar.cs b/c-sharp/Others/Create a ProgressBar.cs new file mode 100644 index 0000000..ce77b9e --- /dev/null +++ b/c-sharp/Others/Create a ProgressBar.cs @@ -0,0 +1,60 @@ +Create a ProgressBar + + + + + + + + + + diff --git a/c-sharp/Others/Create buttons using DrawingImage and GeometryDrawing.cs b/c-sharp/Others/Create buttons using DrawingImage and GeometryDrawing.cs new file mode 100644 index 0000000..6da9ded --- /dev/null +++ b/c-sharp/Others/Create buttons using DrawingImage and GeometryDrawing.cs @@ -0,0 +1,28 @@ +Create buttons using DrawingImage and GeometryDrawing + + + + + + diff --git a/c-sharp/Others/Create rectangles in WPF.cs b/c-sharp/Others/Create rectangles in WPF.cs new file mode 100644 index 0000000..12f6508 --- /dev/null +++ b/c-sharp/Others/Create rectangles in WPF.cs @@ -0,0 +1,24 @@ +Create rectangles in WPF + + + + + + + + + + + + + + diff --git a/c-sharp/Others/Cross Thread Exception Raising.cs b/c-sharp/Others/Cross Thread Exception Raising.cs new file mode 100644 index 0000000..33f79c7 --- /dev/null +++ b/c-sharp/Others/Cross Thread Exception Raising.cs @@ -0,0 +1,36 @@ +Cross Thread Exception Raising + + + + + +//File:Window.xaml.cs +using System; +using System.Threading; +using System.Windows; +using System.Windows.Threading; + +namespace WpfApplication1 +{ + public partial class SecondaryUiThreadWindow : Window + { + public SecondaryUiThreadWindow() + { + InitializeComponent(); + + this.Title = Thread.CurrentThread.ManagedThreadId+""; + } + void r(object sender, RoutedEventArgs e) + { + throw new Exception(Dispatcher.CurrentDispatcher.Thread.ManagedThreadId+""); + } + void SecondaryUiThreadWindow_Closed(object sender, EventArgs e) + { + Dispatcher.CurrentDispatcher.InvokeShutdown(); + } + } +} + diff --git a/c-sharp/Others/DateTemplate for String.cs b/c-sharp/Others/DateTemplate for String.cs new file mode 100644 index 0000000..73d7989 --- /dev/null +++ b/c-sharp/Others/DateTemplate for String.cs @@ -0,0 +1,24 @@ +DateTemplate for String + + + + + + + + + + + + + + + + + + + diff --git a/c-sharp/Others/Define Double value as resource.cs b/c-sharp/Others/Define Double value as resource.cs new file mode 100644 index 0000000..cc15632 --- /dev/null +++ b/c-sharp/Others/Define Double value as resource.cs @@ -0,0 +1,22 @@ +Define Double value as resource + + + + Times New Roman + 20 + Bold + + + + + + diff --git a/c-sharp/Others/Deque.cs b/c-sharp/Others/Deque.cs new file mode 100644 index 0000000..f7991b7 --- /dev/null +++ b/c-sharp/Others/Deque.cs @@ -0,0 +1,120 @@ +using System; +using System.Collections.Generic; +using System.Diagnostics.Contracts; +using System.Linq; + + +namespace DataStructures.QueueSpace +{ + /// + /// + /// + /// + [Serializable] + public class Deque : IEnumerable + { + private List internalList; + + public int Count { get { return internalList.Count; } } + public int Capacity { get { return internalList.Capacity; } } + public T PeekFirst + { + get + { + if (!internalList.Any()) + { + return default(T); + } + return internalList[0]; + } + } + public T PeekLast + { + get + { + if(!internalList.Any()) + { + return default(T); + } + return internalList[internalList.Count - 1]; + } + } + + /// + /// Creates a queue using default capacity + /// + public Deque() + { + internalList = new List(); + } + + /// + /// Creates a deque with default capacity + /// + /// Default capacity of deque + public Deque(int capacity) + { + Contract.Requires(capacity > 0); + + internalList = new List(capacity); + } + + public void AddFirst(T item) + { + Contract.Requires(item != null); + + internalList.Insert(0, item); + } + + /// + /// Adds an item to the last of deque + /// + /// + public void AddLast(T item) + { + Contract.Requires(item != null); + + internalList.Add(item); + } + + /// + /// + /// + /// Returns null if list is empty + public T RemoveFirst() + { + if (!internalList.Any()) + { + return default(T); + } + T element = internalList[0]; + internalList.RemoveAt(0); + return element; + } + + /// + /// + /// + /// Returns null if list is empty + public T RemoveLast() + { + if (!internalList.Any()) + { + return default(T); + } + T element = internalList[Count - 1]; + internalList.RemoveAt(Count - 1); + return element; + } + + public IEnumerator GetEnumerator() + { + return internalList.GetEnumerator(); + } + + System.Collections.IEnumerator System.Collections.IEnumerable.GetEnumerator() + { + return this.GetEnumerator(); + } + } +} diff --git a/c-sharp/Others/Desktop to AppWorkspace.cs b/c-sharp/Others/Desktop to AppWorkspace.cs new file mode 100644 index 0000000..e4d46ec --- /dev/null +++ b/c-sharp/Others/Desktop to AppWorkspace.cs @@ -0,0 +1,25 @@ +Desktop to AppWorkspace + + + + + + + + + + + diff --git a/c-sharp/Others/Desktop to Control.cs b/c-sharp/Others/Desktop to Control.cs new file mode 100644 index 0000000..415bab9 --- /dev/null +++ b/c-sharp/Others/Desktop to Control.cs @@ -0,0 +1,25 @@ +Desktop to Control + + + + + + + + + + + diff --git a/c-sharp/Others/Diagonal linear gradient - multiple colors.cs b/c-sharp/Others/Diagonal linear gradient - multiple colors.cs new file mode 100644 index 0000000..a22d061 --- /dev/null +++ b/c-sharp/Others/Diagonal linear gradient - multiple colors.cs @@ -0,0 +1,23 @@ +Diagonal linear gradient - multiple colors + + + + + + + + + + + + + + + + + diff --git a/c-sharp/Others/Digital Clock.cs b/c-sharp/Others/Digital Clock.cs new file mode 100644 index 0000000..0962a99 --- /dev/null +++ b/c-sharp/Others/Digital Clock.cs @@ -0,0 +1,48 @@ +Digital Clock + + + + + + + + + +//File:Window.xaml.cs +using System; +using System.Windows; +using System.Windows.Threading; + +namespace MyNameSpace.DigitalClock +{ + public class ClockTicker1 : DependencyObject + { + public static DependencyProperty DateTimeProperty = + DependencyProperty.Register("DateTime", typeof(DateTime), + typeof(ClockTicker1)); + + public DateTime DateTime + { + set { SetValue(DateTimeProperty, value); } + get { return (DateTime) GetValue(DateTimeProperty); } + } + + public ClockTicker1() + { + DispatcherTimer timer = new DispatcherTimer(); + timer.Tick += TimerOnTick; + timer.Interval = TimeSpan.FromSeconds(1); + timer.Start(); + } + + void TimerOnTick(object sender, EventArgs args) + { + DateTime = DateTime.Now; + } + } +} + diff --git a/c-sharp/Others/Disabled Button with ToolTipService.cs b/c-sharp/Others/Disabled Button with ToolTipService.cs new file mode 100644 index 0000000..eea7bc0 --- /dev/null +++ b/c-sharp/Others/Disabled Button with ToolTipService.cs @@ -0,0 +1,18 @@ +Disabled Button with ToolTipService + + + + + + + + diff --git a/c-sharp/Others/Display a Border.cs b/c-sharp/Others/Display a Border.cs new file mode 100644 index 0000000..f60e021 --- /dev/null +++ b/c-sharp/Others/Display a Border.cs @@ -0,0 +1,21 @@ +Display a Border + + + + + + + + + + + + diff --git a/c-sharp/Others/Display a Static Image.cs b/c-sharp/Others/Display a Static Image.cs new file mode 100644 index 0000000..d5b2c74 --- /dev/null +++ b/c-sharp/Others/Display a Static Image.cs @@ -0,0 +1,11 @@ +Display a Static Image + + + + + + + diff --git a/c-sharp/Others/Display a notification icon in the system tray.cs b/c-sharp/Others/Display a notification icon in the system tray.cs new file mode 100644 index 0000000..703f1b1 --- /dev/null +++ b/c-sharp/Others/Display a notification icon in the system tray.cs @@ -0,0 +1,39 @@ +Display a notification icon in the system tray + + + + + + + +//File:Window.xaml.cs +namespace NotificationIconSample +{ + using System; + using System.Windows; + using System.Windows.Forms; + using System.Drawing; + public partial class MainWindow : Window + { + NotifyIcon notifyIcon; + + public MainWindow() + { + InitializeComponent(); + } + + void click(object sender, RoutedEventArgs e) + { + this.notifyIcon = new NotifyIcon(); + this.notifyIcon.BalloonTipText = "Hello, NotifyIcon!"; + this.notifyIcon.Text = "Hello, NotifyIcon!"; + this.notifyIcon.Icon = new System.Drawing.Icon("NotifyIcon.ico"); + this.notifyIcon.Visible = true; + this.notifyIcon.ShowBalloonTip(1000); + } + } +} + diff --git a/c-sharp/Others/Dock StatusBar.cs b/c-sharp/Others/Dock StatusBar.cs new file mode 100644 index 0000000..b4fad64 --- /dev/null +++ b/c-sharp/Others/Dock StatusBar.cs @@ -0,0 +1,18 @@ +Dock StatusBar + + + + + + Ready + + + + + + diff --git a/c-sharp/Others/Dock Style Left.cs b/c-sharp/Others/Dock Style Left.cs new file mode 100644 index 0000000..1380fb6 --- /dev/null +++ b/c-sharp/Others/Dock Style Left.cs @@ -0,0 +1,37 @@ +Dock Style: Left + + using System; + using System.Drawing; + using System.Collections; + using System.ComponentModel; + using System.Windows.Forms; + using System.Data; + + public class AnchorForm : System.Windows.Forms.Form + { + private System.Windows.Forms.Button button1; + + public AnchorForm() + { + InitializeComponent(); + CenterToScreen(); + } + private void InitializeComponent() + { + this.button1 = new System.Windows.Forms.Button(); + this.Controls.AddRange(new System.Windows.Forms.Control[] {this.button1}); + this.Text = "Anchoring (and Docking) Controls"; + + // dock Left + + button1.Dock = DockStyle.Left; + button1.Text = "Anchor: " + button1.Anchor.ToString() + + "\nDock: " + button1.Dock.ToString(); + } + static void Main() + { + Application.Run(new AnchorForm()); + } + + } + diff --git a/c-sharp/Others/Dock Two Buttons.cs b/c-sharp/Others/Dock Two Buttons.cs new file mode 100644 index 0000000..bf3e455 --- /dev/null +++ b/c-sharp/Others/Dock Two Buttons.cs @@ -0,0 +1,40 @@ +Dock Two Buttons + +using System; +using System.Drawing; +using System.Windows.Forms; + +class TwoButtonsDock: Form +{ + public static void Main() + { + Application.Run(new TwoButtonsDock()); + } + public TwoButtonsDock() + { + ResizeRedraw = true; + + Button btn = new Button(); + btn.Parent = this; + btn.Text = "&Larger"; + btn.Height = 2 * Font.Height; + btn.Dock = DockStyle.Top; + btn.Click += new EventHandler(ButtonLargerOnClick); + + btn = new Button(); + btn.Parent = this; + btn.Text = "&Smaller"; + btn.Height = 2 * Font.Height; + btn.Dock = DockStyle.Bottom; + btn.Click += new EventHandler(ButtonSmallerOnClick); + } + void ButtonLargerOnClick(object obj, EventArgs ea) + { + Console.WriteLine("large"); + } + void ButtonSmallerOnClick(object obj, EventArgs ea) + { + Console.WriteLine("small"); + } +} + diff --git a/c-sharp/Others/Docking left and right before top and bottom.cs b/c-sharp/Others/Docking left and right before top and bottom.cs new file mode 100644 index 0000000..5bcbb44 --- /dev/null +++ b/c-sharp/Others/Docking left and right before top and bottom.cs @@ -0,0 +1,15 @@ +Docking left and right before top and bottom + + + + + + + + + + + diff --git a/c-sharp/Others/Document Styles.cs b/c-sharp/Others/Document Styles.cs new file mode 100644 index 0000000..47a5629 --- /dev/null +++ b/c-sharp/Others/Document Styles.cs @@ -0,0 +1,35 @@ +Document Styles + + + + + + + + + + + + + Chapter I + + + Chapter Head + + + this is a test + + + ... + + + + + diff --git a/c-sharp/Others/Double value as the Font size.cs b/c-sharp/Others/Double value as the Font size.cs new file mode 100644 index 0000000..11adb18 --- /dev/null +++ b/c-sharp/Others/Double value as the Font size.cs @@ -0,0 +1,28 @@ +Double value as the Font size + + + + Times New Roman + 100 + + + + + + + + + + asdf + + + + diff --git a/c-sharp/Others/DoubleHashedDictionary.cs b/c-sharp/Others/DoubleHashedDictionary.cs new file mode 100644 index 0000000..f0143ab --- /dev/null +++ b/c-sharp/Others/DoubleHashedDictionary.cs @@ -0,0 +1,13 @@ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +namespace DataStructures.Hash +{ + [Serializable] + public class DoubleHashedDictionary + { + + } +} diff --git a/c-sharp/Others/Draw Graphics On Bitmap.cs b/c-sharp/Others/Draw Graphics On Bitmap.cs new file mode 100644 index 0000000..32a1585 --- /dev/null +++ b/c-sharp/Others/Draw Graphics On Bitmap.cs @@ -0,0 +1,33 @@ +Draw Graphics On Bitmap + +using System; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Input; +using System.Windows.Media; +using System.Windows.Media.Imaging; + + public class DrawGraphicsOnBitmap : Window + { + [STAThread] + public static void Main() + { + Application app = new Application(); + app.Run(new DrawGraphicsOnBitmap()); + } + public DrawGraphicsOnBitmap() + { + Background = Brushes.Khaki; + RenderTargetBitmap renderbitmap = new RenderTargetBitmap(80, 80, 60, 60, PixelFormats.Default); + DrawingVisual drawvis = new DrawingVisual(); + DrawingContext dc = drawvis.RenderOpen(); + dc.DrawRoundedRectangle(Brushes.Blue, new Pen(Brushes.Red, 10),new Rect(20, 20, 60, 60), 10, 10); + dc.Close(); + renderbitmap.Render(drawvis); + Image img = new Image(); + img.Source = renderbitmap; + + Content = img; + } + } + diff --git a/c-sharp/Others/Draw second figure with NonZero FillRule.cs b/c-sharp/Others/Draw second figure with NonZero FillRule.cs new file mode 100644 index 0000000..f28873c --- /dev/null +++ b/c-sharp/Others/Draw second figure with NonZero FillRule.cs @@ -0,0 +1,25 @@ +Draw second figure with "NonZero" FillRule + + + + + + + + + + diff --git a/c-sharp/Others/Draws a circle with a blue interior.cs b/c-sharp/Others/Draws a circle with a blue interior.cs new file mode 100644 index 0000000..eeb5022 --- /dev/null +++ b/c-sharp/Others/Draws a circle with a blue interior.cs @@ -0,0 +1,16 @@ +Draws a circle with a blue interior + + + + + + + diff --git a/c-sharp/Others/Duplicate VisualBrush.cs b/c-sharp/Others/Duplicate VisualBrush.cs new file mode 100644 index 0000000..b151e48 --- /dev/null +++ b/c-sharp/Others/Duplicate VisualBrush.cs @@ -0,0 +1,46 @@ +Duplicate VisualBrush + + + + + + + + + + + + + diff --git a/c-sharp/Others/Dynamic Resource.cs b/c-sharp/Others/Dynamic Resource.cs new file mode 100644 index 0000000..60f1463 --- /dev/null +++ b/c-sharp/Others/Dynamic Resource.cs @@ -0,0 +1,50 @@ +Dynamic Resource + + + + + + + + + + +//File:Window.xaml.cs + +using System; +using System.Collections.Generic; +using System.Text; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Data; +using System.Windows.Documents; +using System.Windows.Input; +using System.Windows.Media; +using System.Windows.Media.Imaging; +using System.Windows.Shapes; + +namespace Resources +{ + public partial class DynamicResource : System.Windows.Window + { + public DynamicResource() + { + InitializeComponent(); + } + + private void cmdChange_Click(object sender, RoutedEventArgs e) + { + this.Resources["TileBrush"] = new SolidColorBrush(Colors.LightBlue); + + ImageBrush brush = (ImageBrush)this.Resources["TileBrush"]; + brush.Viewport = new Rect(0, 0, 8, 8); + } + } +} + diff --git a/c-sharp/Others/Ellipse Mouse Down event.cs b/c-sharp/Others/Ellipse Mouse Down event.cs new file mode 100644 index 0000000..34443e4 --- /dev/null +++ b/c-sharp/Others/Ellipse Mouse Down event.cs @@ -0,0 +1,48 @@ +Ellipse Mouse Down event + + + + + + + + +//File:Window.xaml.cs +using System; +using System.Collections.Generic; +using System.Text; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Data; +using System.Windows.Documents; +using System.Windows.Input; +using System.Windows.Media; +using System.Windows.Media.Imaging; +using System.Windows.Shapes; +using System.Diagnostics; + + +namespace WpfApplication1 +{ + public partial class Window1 : System.Windows.Window + { + public Window1() + { + InitializeComponent(); + + myEllipse.MouseDown += myEllipse_MouseDown; + + } + + void myEllipse_MouseDown(object sender, MouseButtonEventArgs e) + { + Mouse.Capture(myEllipse); + } + + + } +} + diff --git a/c-sharp/Others/EllipseGeometry.cs b/c-sharp/Others/EllipseGeometry.cs new file mode 100644 index 0000000..d7b9243 --- /dev/null +++ b/c-sharp/Others/EllipseGeometry.cs @@ -0,0 +1,14 @@ +EllipseGeometry + + + + + + + + + + diff --git a/c-sharp/Others/Elliptical Arc.cs b/c-sharp/Others/Elliptical Arc.cs new file mode 100644 index 0000000..75bc030 --- /dev/null +++ b/c-sharp/Others/Elliptical Arc.cs @@ -0,0 +1,31 @@ +Elliptical Arc + + + + + + + + + + + + + + + + + + + + + + + + + + diff --git a/c-sharp/Others/Embedded code for Application.cs b/c-sharp/Others/Embedded code for Application.cs new file mode 100644 index 0000000..b200d35 --- /dev/null +++ b/c-sharp/Others/Embedded code for Application.cs @@ -0,0 +1,15 @@ +Embedded code for Application + + + + void AppExit(object sender, ExitEventArgs e) + { + MessageBox.Show("App has exited"); + } + + + diff --git a/c-sharp/Others/Expander Header.cs b/c-sharp/Others/Expander Header.cs new file mode 100644 index 0000000..f960624 --- /dev/null +++ b/c-sharp/Others/Expander Header.cs @@ -0,0 +1,21 @@ +Expander Header + + + + + + + + + + + + + + + + diff --git a/c-sharp/Others/Expander control.cs b/c-sharp/Others/Expander control.cs new file mode 100644 index 0000000..110e652 --- /dev/null +++ b/c-sharp/Others/Expander control.cs @@ -0,0 +1,57 @@ +Expander control + + + + + + +//File:Window.xaml.cs + +using System; +using System.Collections.Generic; +using System.Text; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Data; +using System.Windows.Documents; +using System.Windows.Input; +using System.Windows.Media; +using System.Windows.Media.Imaging; +using System.Windows.Shapes; + + +namespace WpfApplication1 +{ + public partial class MainWindow : System.Windows.Window + { + public MainWindow() + { + InitializeComponent(); + lblInstructions.FontSize = 16; + btnPurchaseOptions.Click +=new RoutedEventHandler(btnPurchaseOptions_Click); + } + private void btnPurchaseOptions_Click(object sender, RoutedEventArgs e) + { + MessageBox.Show("Button has been clicked"); + } + } +} + diff --git a/c-sharp/Others/External Web Links.cs b/c-sharp/Others/External Web Links.cs new file mode 100644 index 0000000..3e9396a --- /dev/null +++ b/c-sharp/Others/External Web Links.cs @@ -0,0 +1,14 @@ +External Web Links + + + + Visit the website + www.happycodings.com. + + + + diff --git a/c-sharp/Others/File menu.cs b/c-sharp/Others/File menu.cs new file mode 100644 index 0000000..f965ea6 --- /dev/null +++ b/c-sharp/Others/File menu.cs @@ -0,0 +1,28 @@ +File menu + + + + + + + + + + + + + + + + + + + + + + + + diff --git a/c-sharp/Others/Find Control With Tag.cs b/c-sharp/Others/Find Control With Tag.cs new file mode 100644 index 0000000..d8e286e --- /dev/null +++ b/c-sharp/Others/Find Control With Tag.cs @@ -0,0 +1,35 @@ +Find Control With Tag + +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +using System.Windows; +using System.Windows.Media; + +static class common +{ + + public static T FindControlWithTag(this DependencyObject parent, string tag) where T : UIElement + { + List elements = new List(); + + int count = VisualTreeHelper.GetChildrenCount(parent); + if (count > 0) + { + for (int j = 0; j < count; j++) + { + DependencyObject child = VisualTreeHelper.GetChild(parent, j); + if (typeof(FrameworkElement).IsAssignableFrom(child.GetType()) + && ((string)((FrameworkElement)child).Tag == tag)) + { + return child as T; + } + var item = FindControlWithTag(child, tag); + if (item != null) return item as T; + } + } + return null; + } +} + diff --git a/c-sharp/Others/Find children.cs b/c-sharp/Others/Find children.cs new file mode 100644 index 0000000..ea5c894 --- /dev/null +++ b/c-sharp/Others/Find children.cs @@ -0,0 +1,48 @@ +Find children + +using System; +using System.Collections.Generic; +using System.Net; +using System.Windows; +using System.Windows.Browser; +using System.Windows.Controls; +using System.Windows.Documents; +using System.Windows.Ink; +using System.Windows.Input; +using System.Windows.Media; +using System.Windows.Media.Animation; +using System.Windows.Shapes; + + +public class UIHelper +{ + private static IEnumerable FindChildren(DependencyObject parent) where T : class + { + var count = VisualTreeHelper.GetChildrenCount(parent); + if (count > 0) + { + for (var j = 0; j < count; j++) + { + var child = VisualTreeHelper.GetChild(parent, j); + var t = child as T; + if (t != null) + yield return t; + + var children = FindChildren(child); + foreach (var item in children) + yield return item; + } + } + } + + public static void SetDataContext(DependencyObject parent, T dataContext) where T : class + { + var textBoxes = FindChildren(parent); + foreach (var item in textBoxes) + { + item.DataContext = dataContext; + } + } + +} + diff --git a/c-sharp/Others/Find enclosure component.cs b/c-sharp/Others/Find enclosure component.cs new file mode 100644 index 0000000..8cf2c03 --- /dev/null +++ b/c-sharp/Others/Find enclosure component.cs @@ -0,0 +1,47 @@ +Find enclosure component + + + + + + +//File:Window.xaml.cs +using System; +using System.Collections.Generic; +using System.Text; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Data; +using System.Windows.Documents; +using System.Windows.Input; +using System.Windows.Media; +using System.Windows.Media.Imaging; +using System.Windows.Shapes; + +namespace VisualTree +{ + public partial class Window1 : System.Windows.Window + { + public Window1() + { + InitializeComponent(); + } + void MyClickEvent(object sender, RoutedEventArgs e) + { + object desiredNode = btnGo.FindName("txt"); + if (desiredNode is TextBox) + { + TextBox desiredChild = desiredNode as TextBox; + desiredChild.Background = Brushes.Green; + } + } + + } +} + diff --git a/c-sharp/Others/Flow Document Reader.cs b/c-sharp/Others/Flow Document Reader.cs new file mode 100644 index 0000000..4ff7430 --- /dev/null +++ b/c-sharp/Others/Flow Document Reader.cs @@ -0,0 +1,37 @@ +Flow Document Reader + + + + + + Chapter I + + + Paragraph + + + this is a test + + + this is a test + this is a test + this is a test + this is a test + this is a test + this is a test + this is a test + this is a test + this is a test + this is a test + this is a test + this is a test + this is a test + + + ... + + + + + diff --git a/c-sharp/Others/FlowDocument with Section.cs b/c-sharp/Others/FlowDocument with Section.cs new file mode 100644 index 0000000..f598c5c --- /dev/null +++ b/c-sharp/Others/FlowDocument with Section.cs @@ -0,0 +1,10 @@ +FlowDocument with Section + + +
+ WPF Unleashed + Notes from Chapter 1 +
+
+ diff --git a/c-sharp/Others/Font Properties Moved.cs b/c-sharp/Others/Font Properties Moved.cs new file mode 100644 index 0000000..cf37b1a --- /dev/null +++ b/c-sharp/Others/Font Properties Moved.cs @@ -0,0 +1,24 @@ +Font Properties Moved + + + + + + + + 1 + 2 + + + + + + You have successfully registered this product. + + + diff --git a/c-sharp/Others/Font Viewer.cs b/c-sharp/Others/Font Viewer.cs new file mode 100644 index 0000000..0d2f550 --- /dev/null +++ b/c-sharp/Others/Font Viewer.cs @@ -0,0 +1,50 @@ +Font Viewer + + + + + + + + + Instructions: Type here to change the preview text. + + + The quick brown fox jumps over the lazy dog. + + + + + + + + + + diff --git a/c-sharp/Others/Format TextBox with MenuItem normal, bold, itali.cs b/c-sharp/Others/Format TextBox with MenuItem normal, bold, itali.cs new file mode 100644 index 0000000..33bc8c0 --- /dev/null +++ b/c-sharp/Others/Format TextBox with MenuItem normal, bold, itali.cs @@ -0,0 +1,78 @@ +Format TextBox with MenuItem: normal, bold, italic + + + + + + + + + + + + + + + + + + + + text + + + + +//File:Window.xaml.cs +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Data; +using System.Windows.Documents; +using System.Windows.Input; +using System.Windows.Media; +using System.Windows.Media.Imaging; +using System.Windows.Navigation; +using System.Windows.Shapes; + +namespace WpfApplication1 +{ + public partial class Window1 : Window + { + public Window1() + { + InitializeComponent(); + } + private void Clear_Click(object sender, RoutedEventArgs e) + { + txtTextBox.Clear(); + } + private void SelectAll_Click(object sender, RoutedEventArgs e) + { + txtTextBox.SelectAll(); + } + private void TextStyle_Click(object sender, RoutedEventArgs e) + { + if (sender == miNormal) + { + txtTextBox.FontWeight = FontWeights.Normal; + txtTextBox.FontStyle = FontStyles.Normal; + } + else if (sender == miBold) + { + txtTextBox.FontWeight = FontWeights.Bold; + } + else if (sender == miItalic) + { + txtTextBox.FontStyle = FontStyles.Italic; + } + } + } +} + diff --git a/c-sharp/Others/Four-quadrant Cartesian coordinate system.cs b/c-sharp/Others/Four-quadrant Cartesian coordinate system.cs new file mode 100644 index 0000000..d5bda80 --- /dev/null +++ b/c-sharp/Others/Four-quadrant Cartesian coordinate system.cs @@ -0,0 +1,38 @@ +Four-quadrant Cartesian coordinate system + + + + + + + + + + + + + + + + + + + + + + + + diff --git a/c-sharp/Others/Freezables and element.cs b/c-sharp/Others/Freezables and element.cs new file mode 100644 index 0000000..7dd53cd --- /dev/null +++ b/c-sharp/Others/Freezables and element.cs @@ -0,0 +1,26 @@ +Freezables and element + + + + + + + + + + + + + + + + + + diff --git a/c-sharp/Others/Geometry Transform for Rectangle.cs b/c-sharp/Others/Geometry Transform for Rectangle.cs new file mode 100644 index 0000000..151462b --- /dev/null +++ b/c-sharp/Others/Geometry Transform for Rectangle.cs @@ -0,0 +1,11 @@ +Geometry Transform for Rectangle + + + + + + + diff --git a/c-sharp/Others/Get RoutedEvent Name.cs b/c-sharp/Others/Get RoutedEvent Name.cs new file mode 100644 index 0000000..acbe453 --- /dev/null +++ b/c-sharp/Others/Get RoutedEvent Name.cs @@ -0,0 +1,64 @@ +Get RoutedEvent Name + + + + + + + + + + +//File:Window.xaml.cs +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Data; +using System.Windows.Documents; +using System.Windows.Input; +using System.Windows.Media; +using System.Windows.Media.Imaging; +using System.Windows.Navigation; +using System.Windows.Shapes; + +namespace WpfApplication1 +{ + public partial class Window1 : Window + { + private void Generic_MouseDown(object sender, MouseButtonEventArgs e) + { + Console.WriteLine(outputText.Text); + Console.WriteLine(e.RoutedEvent.Name); + Console.WriteLine(sender.ToString()); + Console.WriteLine(((FrameworkElement)e.Source).Name); + } + + private void Window_MouseUp(object sender, MouseButtonEventArgs e) + { + outputText.Text = outputText.Text; + } + + private void clickMeButton_Click(object sender, RoutedEventArgs e) + { + outputText.Text = "Button clicked:" + outputText.Text; + } + } +} + diff --git a/c-sharp/Others/Get Selected item from ComboBox.cs b/c-sharp/Others/Get Selected item from ComboBox.cs new file mode 100644 index 0000000..1eee24d --- /dev/null +++ b/c-sharp/Others/Get Selected item from ComboBox.cs @@ -0,0 +1,41 @@ +Get Selected item from ComboBox + +using System; +using System.Drawing; +using System.Windows.Forms; +public class Select : Form { + private Button draw = new Button(); + private ComboBox color = new ComboBox(); + + public Select( ) { + draw.Text = "Draw"; + color.Text = "Choose a color"; + Size = new Size(600,300); + + int w = 20; + draw.Location = new Point(30,40); + color.Location = new Point(w += 10 + color.Width, 30); + + color.Items.Add("Red"); + color.Items.Add("Green"); + color.Items.Add("Blue"); + + Controls.Add(draw); + Controls.Add(color); + + draw.Click += new EventHandler(Draw_Click); + } + + protected void Draw_Click(Object sender, EventArgs e) { + if (color.SelectedItem.ToString() == "Red" ) + Console.WriteLine("It is red."); + else if (color.SelectedItem.ToString() == "Green") + Console.WriteLine("It is green."); + else + Console.WriteLine("It is blue."); + } + static void Main() { + Application.Run(new Select()); + } +} + diff --git a/c-sharp/Others/Get all controls on a form window.cs b/c-sharp/Others/Get all controls on a form window.cs new file mode 100644 index 0000000..951d9a0 --- /dev/null +++ b/c-sharp/Others/Get all controls on a form window.cs @@ -0,0 +1,47 @@ +Get all controls on a form window + + using System; + using System.Drawing; + using System.Windows.Forms; + + class MyForm : Form + { + private TextBox firstNameBox = new TextBox(); + private Button btnShowControls = new Button(); + + MyForm() + { + this.Text = "Controls in the raw"; + + // Add a new text box. + firstNameBox.Text = "Superman"; + firstNameBox.Size = new Size(160, 60); + firstNameBox.Location = new Point(10, 10); + this.Controls.Add(firstNameBox); + + // Add a new button. + btnShowControls.Text = "Examine Controls collection"; + btnShowControls.Size = new Size(90, 90); + btnShowControls.Location = new Point(10, 70); + btnShowControls.Click += + new EventHandler(btnShowControls_Clicked); + this.Controls.Add(btnShowControls); + CenterToScreen(); + + } + protected void btnShowControls_Clicked(object sender, EventArgs e) + { + Control.ControlCollection coll = this.Controls; + foreach(Control c in coll) { + if(c != null) + Console.WriteLine(c.Text, "Index numb: " + coll.GetChildIndex(c, false)); + } + } + + public static int Main(string[] args) + { + Application.Run(new MyForm()); + return 0; + } + } + diff --git a/c-sharp/Others/Get all system installed font.cs b/c-sharp/Others/Get all system installed font.cs new file mode 100644 index 0000000..9b5d73f --- /dev/null +++ b/c-sharp/Others/Get all system installed font.cs @@ -0,0 +1,22 @@ +Get all system installed font + + using System; + using System.Drawing; + using System.Drawing.Text; + using System.Collections; + using System.ComponentModel; + using System.Windows.Forms; + using System.Data; + + + public class Test{ + static void Main() + { + InstalledFontCollection fonts = new InstalledFontCollection(); + for(int j = 0; j < fonts.Families.Length; j++) + { + Console.WriteLine(fonts.Families[j].Name); + } + } + } + diff --git a/c-sharp/Others/Get selected checkbox list items.cs b/c-sharp/Others/Get selected checkbox list items.cs new file mode 100644 index 0000000..c7af54e --- /dev/null +++ b/c-sharp/Others/Get selected checkbox list items.cs @@ -0,0 +1,72 @@ +Get selected checkbox list items + +using System; +using System.Drawing; +using System.Collections; +using System.ComponentModel; +using System.Windows.Forms; +using System.Data; + +public class Form1 : System.Windows.Forms.Form { + private System.Windows.Forms.CheckedListBox chkListPossibleValues; + private System.Windows.Forms.ListBox lstSelected; + private System.Windows.Forms.Button btnMove; + private System.ComponentModel.Container components=null; + + public Form1() { + InitializeComponent(); + this.chkListPossibleValues.Items.Add("Ten"); + } + + private void InitializeComponent() { + this.lstSelected = new System.Windows.Forms.ListBox(); + this.btnMove = new System.Windows.Forms.Button(); + this.chkListPossibleValues = new System.Windows.Forms.CheckedListBox(); + this.SuspendLayout(); + + this.lstSelected.Location = new System.Drawing.Point(240, 12); + this.lstSelected.Name = "lstSelected"; + this.lstSelected.Size = new System.Drawing.Size(150, 180); + this.lstSelected.TabIndex = 1; + + this.btnMove.Location = new System.Drawing.Point(160, 70); + this.btnMove.Name = "btnMove"; + this.btnMove.TabIndex = 3; + this.btnMove.Text = "Move"; + this.btnMove.Click += new System.EventHandler(this.btnMove_Click); + + this.chkListPossibleValues.CheckOnClick = true; + this.chkListPossibleValues.Items.AddRange(new object[] {"One", "Two", "Three", + "Four", "Five","Six","Seven", "Eight", "Nine"}); + this.chkListPossibleValues.Location = new System.Drawing.Point(8, 8); + this.chkListPossibleValues.Name = "chkListPossibleValues"; + this.chkListPossibleValues.Size = new System.Drawing.Size(136, 184); + this.chkListPossibleValues.TabIndex = 0; + + this.AutoScaleBaseSize = new System.Drawing.Size(5, 13); + this.ClientSize = new System.Drawing.Size(380, 200); + this.Controls.AddRange(new System.Windows.Forms.Control[] {this.btnMove, + this.lstSelected, this.chkListPossibleValues}); + this.Name = "Form1"; + this.Text = "List Boxes"; + this.ResumeLayout(false); + + } + + static void Main() { + Application.Run(new Form1()); + } + + private void btnMove_Click(object sender, System.EventArgs e) { + if (this.chkListPossibleValues.CheckedItems.Count > 0) { + this.lstSelected.Items.Clear(); + foreach (string item in this.chkListPossibleValues.CheckedItems) { + this.lstSelected.Items.Add(item.ToString()); + } + for (int i = 0; i < this.chkListPossibleValues.Items.Count; i++){ + this.chkListPossibleValues.SetItemChecked(i, false); + } + } + } +} + diff --git a/c-sharp/Others/Get the font in a FontDialog.cs b/c-sharp/Others/Get the font in a FontDialog.cs new file mode 100644 index 0000000..eef4784 --- /dev/null +++ b/c-sharp/Others/Get the font in a FontDialog.cs @@ -0,0 +1,23 @@ +Get the font in a FontDialog + +using System; +using System.Collections.Generic; +using System.ComponentModel; +using System.Data; +using System.Drawing; +using System.Text; +using System.Windows.Forms; + + +public class MainClass { + private FontDialog fontDlg = new FontDialog(); + private Font currFont = new Font("Arial", 16); + + public static void Main() { + FontDialog fontDlg = new FontDialog(); + if (fontDlg.ShowDialog() != DialogResult.Cancel) { + Console.WriteLine(fontDlg.Font); + } + } +} + diff --git a/c-sharp/Others/Glowing Effect with OuterGlowBitmapEffect.cs b/c-sharp/Others/Glowing Effect with OuterGlowBitmapEffect.cs new file mode 100644 index 0000000..24133d3 --- /dev/null +++ b/c-sharp/Others/Glowing Effect with OuterGlowBitmapEffect.cs @@ -0,0 +1,24 @@ +Glowing Effect with OuterGlowBitmapEffect + + + + + + + + + + + + + diff --git a/c-sharp/Others/Glyphs with ttf font file.cs b/c-sharp/Others/Glyphs with ttf font file.cs new file mode 100644 index 0000000..7230da3 --- /dev/null +++ b/c-sharp/Others/Glyphs with ttf font file.cs @@ -0,0 +1,13 @@ +Glyphs with ttf font file + + + + + + + diff --git a/c-sharp/Others/Gradient background button.cs b/c-sharp/Others/Gradient background button.cs new file mode 100644 index 0000000..204fe2e --- /dev/null +++ b/c-sharp/Others/Gradient background button.cs @@ -0,0 +1,58 @@ +Gradient background button + + + + + + + diff --git a/c-sharp/Others/Grid MouseMove.cs b/c-sharp/Others/Grid MouseMove.cs new file mode 100644 index 0000000..d018ca9 --- /dev/null +++ b/c-sharp/Others/Grid MouseMove.cs @@ -0,0 +1,62 @@ +Grid MouseMove + + + + + + + + + + + + +//File:Window.xaml.cs + +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Data; +using System.Windows.Documents; +using System.Windows.Input; +using System.Windows.Media; +using System.Windows.Media.Imaging; +using System.Windows.Navigation; +using System.Windows.Shapes; + +namespace WpfApplication1 +{ + public partial class Window1 : Window + { + public Window1() + { + InitializeComponent(); + } + + private void Grid_MouseLeftButtonDown(object sender, MouseButtonEventArgs e) + { + Console.WriteLine("left button down"); + } + + private void Grid_MouseLeftButtonUp(object sender, MouseButtonEventArgs e) + { + Console.WriteLine("left button up"); + } + + private void Grid_MouseMove(object sender, MouseEventArgs e) + { + Console.WriteLine("moving"); + } + + } +} + diff --git a/c-sharp/Others/Grid With Splitter.cs b/c-sharp/Others/Grid With Splitter.cs new file mode 100644 index 0000000..c6a7b97 --- /dev/null +++ b/c-sharp/Others/Grid With Splitter.cs @@ -0,0 +1,19 @@ +Grid With Splitter + + + + + + + + + + + + diff --git a/c-sharp/Others/GroupBox Header with mixed content.cs b/c-sharp/Others/GroupBox Header with mixed content.cs new file mode 100644 index 0000000..bb38292 --- /dev/null +++ b/c-sharp/Others/GroupBox Header with mixed content.cs @@ -0,0 +1,19 @@ +GroupBox Header with mixed content + + + + + + + + + + + +
+ diff --git a/c-sharp/Others/Insert Button to a Panel.cs b/c-sharp/Others/Insert Button to a Panel.cs new file mode 100644 index 0000000..8c3c921 --- /dev/null +++ b/c-sharp/Others/Insert Button to a Panel.cs @@ -0,0 +1,60 @@ +Insert Button to a Panel + + + + UI Element Collection - Methods + + + + + Insert Control + + + + + + + + +//File:Window.xaml.cs + +using System; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Documents; +using System.Windows.Navigation; +using System.Windows.Shapes; +using System.Windows.Data; +using System.Windows.Input; + +namespace ElemCollMethods +{ + + public partial class Pane1 : Page + { + System.Windows.Controls.Button btn, btn1, btn2, btn3; + + void InsertButton(object sender, MouseButtonEventArgs e) + { + sp1.Children.Clear(); + btn = new Button(); + btn.Content = "Click to insert button"; + sp1.Children.Add(btn); + btn.Click += (InsertControls); + btn1 = new Button(); + btn1.Content = "Click to insert button"; + sp1.Children.Add(btn1); + btn1.Click += (InsertControls); + } + void InsertControls(object sender, RoutedEventArgs e) + { + btn2 = new Button(); + btn2.Content = "Inserted Button"; + sp1.Children.Insert(1, btn2); + } + } +} + diff --git a/c-sharp/Others/Insert Row.cs b/c-sharp/Others/Insert Row.cs new file mode 100644 index 0000000..ce40b83 --- /dev/null +++ b/c-sharp/Others/Insert Row.cs @@ -0,0 +1,55 @@ +Insert Row + + + + + Grid Column and Row Collections + + + + + + + + + + + + + + + + + + + + + +//File:Window.xaml.cs + +using System; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Documents; + +namespace WpfApplication1 +{ + public partial class Window1 : Window + { + RowDefinition rowDef1; + ColumnDefinition colDef1; + + + private void insertRowAt(object sender, RoutedEventArgs e) + { + rowDef1 = new RowDefinition(); + grid1.RowDefinitions.Insert(grid1.RowDefinitions.Count, rowDef1); + Console.WriteLine(grid1.RowDefinitions.IndexOf(rowDef1).ToString()); + } + } +} + diff --git a/c-sharp/Others/IntermediateNode.cs b/c-sharp/Others/IntermediateNode.cs new file mode 100644 index 0000000..d2df25d --- /dev/null +++ b/c-sharp/Others/IntermediateNode.cs @@ -0,0 +1,57 @@ +using System; +using System.Diagnostics.Contracts; + + +namespace DataStructures.BPlusTreeSpace +{ + public partial class BPlusTree + where TKey : IComparable + { + [Serializable] + private class IntermediateNode : INode + where TKey : IComparable + { + private readonly int numberOfChildren; + private readonly TKey[] keys; + private readonly INode[] children; + + + public IntermediateNode(int numberOfChildren) + { + Contract.Requires(numberOfChildren > 2); + + keys = new TKey[numberOfChildren - 1]; + children = new INode[numberOfChildren]; + } + + //private int GetIndex(TKey key) + //{ + // // Simple linear search. Faster for small values of N or M + // for (int i = 0; i < num; i++) + // { + // if (keys[i].CompareTo(key) > 0) + // { + // return i; + // } + // } + // return num; + //} + + //public INode + + public int GetLocation(TKey key) + { + const int errorNum = -1; + // Simple linear search. Faster for small values of N or M + for (int i = 0; i < keys.Length; i++) + { + if (keys[i].CompareTo(key) > 0) + { + return i; + } + } + return errorNum; + } + } + } +} \ No newline at end of file diff --git a/c-sharp/Others/Is Logical Ancestor Of.cs b/c-sharp/Others/Is Logical Ancestor Of.cs new file mode 100644 index 0000000..8d261eb --- /dev/null +++ b/c-sharp/Others/Is Logical Ancestor Of.cs @@ -0,0 +1,27 @@ +Is Logical Ancestor Of + +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +using System.Windows; +using System.Windows.Media; + +public static class PopupHelper +{ + public static bool IsLogicalAncestorOf(this UIElement ancestor, UIElement child) + { + if (child != null) + { + FrameworkElement obj = child as FrameworkElement; + while (obj != null) + { + FrameworkElement parent = VisualTreeHelper.GetParent(obj) as FrameworkElement; + obj = parent == null ? obj.Parent as FrameworkElement : parent as FrameworkElement; + if (obj == ancestor) return true; + } + } + return false; + } +} + diff --git a/c-sharp/Others/Label with ControlTemplate.cs b/c-sharp/Others/Label with ControlTemplate.cs new file mode 100644 index 0000000..8f2424e --- /dev/null +++ b/c-sharp/Others/Label with ControlTemplate.cs @@ -0,0 +1,22 @@ +Label with ControlTemplate + + + + + + + + + + + + + + diff --git a/c-sharp/Others/Large ArcSegments.cs b/c-sharp/Others/Large ArcSegments.cs new file mode 100644 index 0000000..1b17036 --- /dev/null +++ b/c-sharp/Others/Large ArcSegments.cs @@ -0,0 +1,26 @@ +Large ArcSegments + + + + + + + + + + + + + + + + + + + + + + diff --git a/c-sharp/Others/LeafNode.cs b/c-sharp/Others/LeafNode.cs new file mode 100644 index 0000000..7dd940e --- /dev/null +++ b/c-sharp/Others/LeafNode.cs @@ -0,0 +1,53 @@ +using System; +using System.Diagnostics.Contracts; + + +namespace DataStructures.BPlusTreeSpace +{ + public partial class BPlusTree + where TKey : IComparable + { + [Serializable] + private class LeafNode : INode + where TKey : IComparable + { + private readonly TValue[] _values; + private readonly int _numberOfValues; + + public LeafNode(int numberOfValues) + { + Contract.Requires(numberOfValues > 0); + _numberOfValues = numberOfValues; + _values = new TValue[numberOfValues]; + } + + private int GetChildIndex(TKey key) + { + Contract.Requires(key != null); + Contract.Ensures(Contract.Result() >= 0); + Contract.Ensures(Contract.Result() <= _numberOfValues); + + // Simple linear search. Faster for small values of N or M, binary search would be faster for larger M / N + for (int i = 0; i < _numberOfValues; i++) + { + if (_values[i].Equals(key)) + { + return i; + } + } + return _numberOfValues; + } + + public TValue GetChild(TKey key) + { + Contract.Requires(key != null); + return _values[GetChildIndex(key)]; + } + + public int GetLocation(TKey key) + { + throw new NotImplementedException(); + } + } + } +} \ No newline at end of file diff --git a/c-sharp/Others/Left,Top,Right,Bottom for Padding.cs b/c-sharp/Others/Left,Top,Right,Bottom for Padding.cs new file mode 100644 index 0000000..414637f --- /dev/null +++ b/c-sharp/Others/Left,Top,Right,Bottom for Padding.cs @@ -0,0 +1,12 @@ +Left,Top,Right,Bottom for Padding + + + + + + + + + diff --git a/c-sharp/Others/Line with Path.cs b/c-sharp/Others/Line with Path.cs new file mode 100644 index 0000000..3f42f9f --- /dev/null +++ b/c-sharp/Others/Line with Path.cs @@ -0,0 +1,15 @@ +Line with Path + + + + + + + + + + diff --git a/c-sharp/Others/LineGeometry.cs b/c-sharp/Others/LineGeometry.cs new file mode 100644 index 0000000..5c2df24 --- /dev/null +++ b/c-sharp/Others/LineGeometry.cs @@ -0,0 +1,14 @@ +LineGeometry + + + + + + + + + + diff --git a/c-sharp/Others/LinearProbingDictionary.cs b/c-sharp/Others/LinearProbingDictionary.cs new file mode 100644 index 0000000..d664012 --- /dev/null +++ b/c-sharp/Others/LinearProbingDictionary.cs @@ -0,0 +1,277 @@ +using System; +using System.Collections.Generic; +using System.Diagnostics.Contracts; +using System.Linq; + + +namespace DataStructures.HashSpace +{ + /// + /// A hash table which uses user specified step size probing + /// + /// + /// + [Serializable] + public class LinearProbingDictionary : IDictionary + { + private const int DefaultCapacity = 1023; + private int capacity; + private readonly int stepSize; + private int count; + private Pair[] pairs; + + public ICollection Keys + { + get + { + return pairs.Where(p => (p != null)) + .Select(p => p.Key) + .ToList() + .AsReadOnly(); + } + } + + public ICollection Values + { + get + { + return pairs.Where(p => (p!=null)) + .Select(p => p.Value) + .ToList() + .AsReadOnly(); + } + } + + public int Count + { + get { return count; } + } + + public int Capacity + { + get { return capacity; } + } + + public bool IsReadOnly + { + get { throw new NotImplementedException(); } + } + + public LinearProbingDictionary(int capacity, int stepSize = 1) + { + Contract.Requires(capacity > 0); + Contract.Requires(stepSize > 0); + + this.capacity = capacity; + this.stepSize = stepSize; + pairs = new Pair[capacity]; + } + + public LinearProbingDictionary(int stepSize) + : this(DefaultCapacity, stepSize) + { + } + + public void Add(Tkey key, TValue value) + { + Pair pair = new Pair(key, value); + int pos = pair.GetHashCode(); + int visit = 0; + while(pairs[pos] != null) + { + if(visit >= capacity) + { + throw new Exception("Dictionary is full"); + } + pos = (pos+stepSize) % capacity; + visit++; + } + + pairs[pos] = pair; + count++; + } + + /// + /// Returns index of th item + /// + /// + /// -1 if not present + private int GetIndex(Tkey key) + { + if (key == null) + { + return -1; + } + + int index = key.GetHashCode() % capacity; + int currentIndex = index; + do + { + if (pairs[currentIndex] == null) + { + return -1; + } + if (pairs[currentIndex].Key.Equals(key)) + { + return currentIndex; + } + else + { + currentIndex = (currentIndex + stepSize) % capacity; + } + } while (currentIndex != index); + return -1; + } + + public bool ContainsKey(Tkey key) + { + return (GetIndex(key) != -1) ; + } + + public bool Remove(Tkey key) + { + Contract.Requires(key != null, "key"); + + int index; + if ((index = GetIndex(key)) != -1) + { + pairs[index] = null; + count--; + return true; + } + Remove(new KeyValuePair()); + return false; + + } + + public bool TryGetValue(Tkey key, out TValue value) + { + int index = GetIndex(key); + if (index != -1) + { + value = pairs[index].Value; + return true; + } + else + { + value = default(TValue); + return false; + } + } + + public TValue this[Tkey key] + { + get + { + var index = GetIndex(key); + + if(index == -1) + { + return default(TValue); + } + return pairs[index].Value; + } + set + { + var index = GetIndex(key) ; + if (index == -1) + { + Add(key, value); + } + else + { + pairs[index].Value = value; + } + } + } + + public void Add(KeyValuePair item) + { + Add(item.Key, item.Value); + } + + public void Clear() + { + count = 0; + pairs = new Pair[capacity]; + } + + public bool Contains(KeyValuePair item) + { + return ContainsKey(item.Key) ? item.Value.Equals(pairs[GetIndex(item.Key)].Value) : false; + } + + public void CopyTo(KeyValuePair[] array, int arrayIndex) + { + foreach (var pair in pairs) + { + if(pair != null) + { + array[arrayIndex] = new KeyValuePair(pair.Key, pair.Value); + arrayIndex++; + } + } + } + + public bool Remove(KeyValuePair item) + { + int index = GetIndex(item.Key); + if (index == -1) + { + return false; + } + pairs[index] = null; + count--; + return true; + } + + public IEnumerator> GetEnumerator() + { + foreach (var pair in pairs) + { + if(pair == null) + { + continue; + } + yield return new KeyValuePair(pair.Key, pair.Value); + } + } + + System.Collections.IEnumerator System.Collections.IEnumerable.GetEnumerator() + { + return this.GetEnumerator(); + } + + private class Pair + { + public Tkey Key { get; set; } + public TValue Value { get; set; } + + public Pair(Tkey key, TValue value) + { + Key = key; + Value = value; + } + + public override bool Equals(object obj) + { + if (obj == null || GetType() != obj.GetType()) + { + return false; + } + + return Key.Equals(obj); + } + + public override int GetHashCode() + { + int hash = 31; + unchecked + { + hash = hash + 17 * Key.GetHashCode(); + } + return hash; + } + } + } +} diff --git a/c-sharp/Others/Link To Another Page.cs b/c-sharp/Others/Link To Another Page.cs new file mode 100644 index 0000000..ed54e0b --- /dev/null +++ b/c-sharp/Others/Link To Another Page.cs @@ -0,0 +1,16 @@ +Link To Another Page + + + + + This is a simple page. + Click here. + + + + + + diff --git a/c-sharp/Others/LinkedDictionary.cs b/c-sharp/Others/LinkedDictionary.cs new file mode 100644 index 0000000..6415daa --- /dev/null +++ b/c-sharp/Others/LinkedDictionary.cs @@ -0,0 +1,216 @@ +using System; +using System.Collections; +using System.Linq; +using System.Collections.Generic; +using System.Diagnostics.Contracts; + + +namespace DataStructures.HashSpace +{ + /// + /// + /// + /// + /// + [Serializable] + public class LinkedDictionary : IDictionary where TValue : LinkedDictionary.Value + { + private Dictionary> dic; + private readonly Value headValue = new Value(default(TValue)); + private Value lastAdded; + private Pair lastAddedPair; + + public LinkedDictionary(int capacity) + { + Contract.Requires(capacity > 0); + + Dic = new Dictionary>(capacity); + lastAdded = headValue; + Dic.Add(default(TKey), headValue); + } + + public bool ContainsValue(TValue value) + { + return Dic.ContainsValue(new Value(value)); + } + + public void Add(TKey key, TValue value) + { + Contract.Requires(key != null); + + var newValue = new Value(value, lastAddedPair); + var newPair = new Pair(key, newValue); + lastAdded.next = newPair; + lastAdded = newValue; + lastAddedPair = newPair; + Dic.Add(newPair.key, newPair.value); + } + + public bool Remove(TKey key) + { + if (!Dic.ContainsKey(key)) + { + return false; + } + if (lastAdded.Equals(Dic[key])) + { + lastAddedPair = lastAdded.prev; + } + var prev = lastAdded.prev; + //TODO: remove element + return false; + } + + public bool ContainsKey(TKey key) + { + Contract.Requires(key != null); + + return Dic.ContainsKey(key); + } + + public ICollection Keys + { + get + { + return Dic.Keys; + } + } + + public bool Remove(KeyValuePair item) + { + if(!Dic.ContainsKey(item.Key)) + { + return false; + } + if(lastAdded.Equals(Dic[item.Key])) + { + lastAddedPair = lastAdded.prev; + } + var prev = lastAdded.prev; + //TODO: remove element + return false; + } + + public bool TryGetValue(TKey key, out TValue value) + { + value = default(TValue); + var valueDic = new Value(value); + return Dic.TryGetValue(key, out valueDic); + } + + public ICollection Values + { + //TODO: fix + get { return null; } + } + + public TValue this[TKey key] + { + get + { + Contract.Requires(key != null); + + return Dic[key].value; + } + set + { + Contract.Requires(key != null); + + Dic[key] = value; + } + } + + public void Add(KeyValuePair item) + { + Add(item.Key, item.Value); + } + + public void Clear() + { + Dic.Clear(); + lastAdded = headValue; + } + + public bool Contains(KeyValuePair item) + { + return (Dic.ContainsKey(item.Key) && Dic[item.Key].Equals(item.Value)); + } + + public void CopyTo(KeyValuePair[] array, int arrayIndex) + { + Contract.Requires(array.Length >= Dic.Count+arrayIndex); + } + + public int Count + { + get { return Dic.Count; } + } + + public bool IsReadOnly { get; private set; } + + public Dictionary> Dic + { + get { return dic; } + set { dic = value; } + } + + public IEnumerator> GetEnumerator() + { + var key = headValue.next; + while (key != null) + { + var tempKey = key; + key = key.value.next; + yield return new KeyValuePair(tempKey.key, Dic[tempKey.key].value); + } + } + + IEnumerator System.Collections.IEnumerable.GetEnumerator() + { + return GetEnumerator(); + } + + + + public class Pair where TValue : Value + { + public TKey key; + public Value value; + + public Pair(TKey key = default(TKey), Value value = null) + { + this.key = key; + this.value = value; + } + } + + public class Value where TValue:Value + { + public TValue value; + public Pair next; + public Pair prev; + + public Value(TValue value, Pair prev = null, Pair next = null) + { + this.value = value; + this.prev = prev; + this.next = next; + } + + public override int GetHashCode() + { + return value.GetHashCode(); + } + + public override bool Equals(object otherObj) + { + var otherKey = otherObj as Value; + if(otherKey == null) + { + return false; + } + return otherKey.value.Equals(value); + } + } + } +} diff --git a/c-sharp/Others/ListBox With Items Panel.cs b/c-sharp/Others/ListBox With Items Panel.cs new file mode 100644 index 0000000..1ffc5cd --- /dev/null +++ b/c-sharp/Others/ListBox With Items Panel.cs @@ -0,0 +1,28 @@ +ListBox With Items Panel + + + + + + + + + + + + Item 1 + Item 2 + Item 3 + Item 4 + Item 5 + Item 6 + Item 7 + Item 8 + Item 9 + Item 10 + + + + + diff --git a/c-sharp/Others/ListBox and SelectionMode.cs b/c-sharp/Others/ListBox and SelectionMode.cs new file mode 100644 index 0000000..57a792f --- /dev/null +++ b/c-sharp/Others/ListBox and SelectionMode.cs @@ -0,0 +1,55 @@ +ListBox and SelectionMode + + + + + Item 1 + Item 2 + Item 3 + Item 4 + Item 5 + Item 6 + Item 7 + Item 8 + + + + +//File:Window.xaml.cs + +using System; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Data; +using System.Windows.Documents; +using System.Windows.Media; +using System.Windows.Media.Imaging; +using System.Windows.Shapes; + +namespace ControlDemos +{ + public partial class listbox : Window + { + public listbox() + { + InitializeComponent(); + } + public void listBox1_SelectionChanged(object sender, SelectionChangedEventArgs args) + { + int nCount = listBox1.SelectedItems.Count; + for (int lp = 0; lp < nCount; lp++) + Console.WriteLine(listBox1.SelectedItems[lp].ToString()); + } + } +} + diff --git a/c-sharp/Others/ListBox with Image item.cs b/c-sharp/Others/ListBox with Image item.cs new file mode 100644 index 0000000..38be3f9 --- /dev/null +++ b/c-sharp/Others/ListBox with Image item.cs @@ -0,0 +1,42 @@ +ListBox with Image item + + + + + + + + + + +//File:Window.xaml.cs + +using System; +using System.Collections.Generic; +using System.Text; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Data; +using System.Windows.Documents; +using System.Windows.Input; +using System.Windows.Media; +using System.Windows.Media.Imaging; +using System.Windows.Shapes; + +namespace ClassicControls +{ + public partial class ImageList : System.Windows.Window + { + public ImageList() + { + InitializeComponent(); + } + private void lst_SelectionChanged(object sender, RoutedEventArgs e) + { + } + } +} + diff --git a/c-sharp/Others/Load Xaml Resource.cs b/c-sharp/Others/Load Xaml Resource.cs new file mode 100644 index 0000000..d4920fa --- /dev/null +++ b/c-sharp/Others/Load Xaml Resource.cs @@ -0,0 +1,50 @@ +Load Xaml Resource + + + + + + + + + Sunday + Monday + Tuesday + Wednesday + + + + +//File:Window.xaml.cs +using System; +using System.IO; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Markup; + +namespace MyNameSpace.LoadXamlResource +{ + public class LoadXamlResource : Window + { + + public LoadXamlResource() + { + Title = "Load Xaml Resource"; + + Uri uri = new Uri("pack://application:,,,/LoadXamlResource.xml"); + Stream stream = Application.GetResourceStream(uri).Stream; + FrameworkElement el = XamlReader.Load(stream) as FrameworkElement; + Content = el; + + Button btn = el.FindName("MyButton") as Button; + + if (btn != null) + btn.Click += ButtonOnClick; + } + void ButtonOnClick(object sender, RoutedEventArgs args) + { + Console.WriteLine(args.Source.ToString()); + } + } +} + diff --git a/c-sharp/Others/Load image source from a hard code directory.cs b/c-sharp/Others/Load image source from a hard code directory.cs new file mode 100644 index 0000000..862cc27 --- /dev/null +++ b/c-sharp/Others/Load image source from a hard code directory.cs @@ -0,0 +1,49 @@ +Load image source from a hard code directory + + + + + + + + +//File:Window.xaml.cs + +using System; +using System.Collections.Generic; +using System.Text; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Data; +using System.Windows.Documents; +using System.Windows.Input; +using System.Windows.Media; +using System.Windows.Media.Imaging; +using System.Windows.Shapes; +using System.Reflection; +using System.Resources; +using System.IO; +using System.Globalization; +using System.Windows.Resources; + +namespace AssemblyResources +{ + public partial class Window1 : System.Windows.Window + { + public Window1() + { + InitializeComponent(); + } + + private void cmdPlay_Click(object sender, RoutedEventArgs e) + { + img.Source = new BitmapImage(new Uri("file:///c:/image.jpg", UriKind.Relative)); + Sound.Stop(); + Sound.Play(); + } + } +} + diff --git a/c-sharp/Others/Logical Resources.cs b/c-sharp/Others/Logical Resources.cs new file mode 100644 index 0000000..a6caa74 --- /dev/null +++ b/c-sharp/Others/Logical Resources.cs @@ -0,0 +1,27 @@ +Logical Resources + + + + + + Cyan + Red + + + + + + + + + + + + + + diff --git a/c-sharp/Others/Margin Left,Top,Right,Bottom.cs b/c-sharp/Others/Margin Left,Top,Right,Bottom.cs new file mode 100644 index 0000000..66c332f --- /dev/null +++ b/c-sharp/Others/Margin Left,Top,Right,Bottom.cs @@ -0,0 +1,15 @@ +Margin: Left,Top,Right,Bottom + + + + + + + + + + + + diff --git a/c-sharp/Others/Markup Extensions for Button.cs b/c-sharp/Others/Markup Extensions for Button.cs new file mode 100644 index 0000000..3b5f9b0 --- /dev/null +++ b/c-sharp/Others/Markup Extensions for Button.cs @@ -0,0 +1,16 @@ +Markup Extensions for Button + + + + + + + + + + + + + + + + + + diff --git a/c-sharp/Others/Matrix3D RotateAt.cs b/c-sharp/Others/Matrix3D RotateAt.cs new file mode 100644 index 0000000..93c4c64 --- /dev/null +++ b/c-sharp/Others/Matrix3D RotateAt.cs @@ -0,0 +1,43 @@ +Matrix3D RotateAt + + + + + + + + + + + +//File:Window.xaml.cs +using System; +using System.Windows; +using System.Windows.Media; +using System.Windows.Media.Media3D; + +namespace WpfApplication1 +{ + public partial class Matrix3DTransforms : Window + { + public Matrix3DTransforms() + { + InitializeComponent(); + Matrix3D M = new Matrix3D(1, 4, 2, 4, + 4, 1, 0, 1, + 0, 0, 1, 0, + 1, 3, 3, 1); + + + tbOriginal.Text = "(" + M.ToString() + ")"; + + //Translation: + M.RotateAt(new Quaternion(new Vector3D(1, 2, 3), 45),new Point3D(15, 25, 40)); + tbResult.Text = "(" + M.ToString() + ")"; + } + } +} + diff --git a/c-sharp/Others/Matrix3D Translation.cs b/c-sharp/Others/Matrix3D Translation.cs new file mode 100644 index 0000000..adf325d --- /dev/null +++ b/c-sharp/Others/Matrix3D Translation.cs @@ -0,0 +1,44 @@ +Matrix3D Translation + + + + + + + + + + + +//File:Window.xaml.cs +using System; +using System.Windows; +using System.Windows.Media; +using System.Windows.Media.Media3D; + +namespace WpfApplication1 +{ + public partial class Matrix3DTransforms : Window + { + public Matrix3DTransforms() + { + InitializeComponent(); + Matrix3D M = new Matrix3D(1, 4, 3, 0, + 2, 2, 4, 0, + 0, 0, 4, 0, + 1, 3, 3, 1); + + + tbOriginal.Text = "(" + M.ToString() + ")"; + + //Translation: + M.Translate(new Vector3D(120, 200, 250)); + tbResult.Text = "(" + M.ToString() + ")"; + + } + } +} + diff --git a/c-sharp/Others/Matrix3D scale transformation.cs b/c-sharp/Others/Matrix3D scale transformation.cs new file mode 100644 index 0000000..4a85f25 --- /dev/null +++ b/c-sharp/Others/Matrix3D scale transformation.cs @@ -0,0 +1,45 @@ +Matrix3D scale transformation + + + + + + + + + + + +//File:Window.xaml.cs +using System; +using System.Windows; +using System.Windows.Media; +using System.Windows.Media.Media3D; + +namespace WpfApplication1 +{ + public partial class Matrix3DTransforms : Window + { + public Matrix3DTransforms() + { + InitializeComponent(); + Matrix3D M = new Matrix3D(1, 4, 2, 1, + 2, 4, 4, 3, + 2, 2, 1, 0, + 1, 3, 0, 1); + + + Matrix3D M1 = M; + tbOriginal.Text = "(" + M.ToString() + ")"; + + //Scale: + M.Scale(new Vector3D(0.5, 1.5, 2.5)); + tbResult.Text = "(" + M.ToString() + ")"; + + } + } +} + diff --git a/c-sharp/Others/MenuItems with Commands.cs b/c-sharp/Others/MenuItems with Commands.cs new file mode 100644 index 0000000..ae13bc9 --- /dev/null +++ b/c-sharp/Others/MenuItems with Commands.cs @@ -0,0 +1,20 @@ +MenuItems with Commands + + + + + + + + + + + + + + + + + diff --git a/c-sharp/Others/Message Only MessageBox.cs b/c-sharp/Others/Message Only MessageBox.cs new file mode 100644 index 0000000..b469d74 --- /dev/null +++ b/c-sharp/Others/Message Only MessageBox.cs @@ -0,0 +1,43 @@ +Message Only MessageBox + + + + + + + +//File:Window.xaml.cs + +using System; +using System.Collections.Generic; +using System.Text; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Data; +using System.Windows.Documents; +using System.Windows.Input; +using System.Windows.Media; +using System.Windows.Media.Imaging; +using System.Windows.Shapes; +using Microsoft.Win32; + +namespace Windows +{ + public partial class OpenFileTest : System.Windows.Window + { + public OpenFileTest() + { + InitializeComponent(); + } + + private void cmdOpen_Click(object sender, RoutedEventArgs e) + { + OpenFileDialog myDialog = new OpenFileDialog(); + + myDialog.Filter = "Image Files(*.BMP;*.JPG;*.GIF)|*.BMP;*.JPG;*.GIF|All files (*.*)|*.*"; + myDialog.CheckFileExists = true; + myDialog.Multiselect = true; + + if (myDialog.ShowDialog() == true) + { + lstFiles.Items.Clear(); + foreach (string file in myDialog.FileNames) + { + lstFiles.Items.Add(file); + } + } + } + } +} + diff --git a/c-sharp/Others/Page Loaded event.cs b/c-sharp/Others/Page Loaded event.cs new file mode 100644 index 0000000..ac42c73 --- /dev/null +++ b/c-sharp/Others/Page Loaded event.cs @@ -0,0 +1,34 @@ +Page Loaded event + + +//File:Window.xaml.cs + +using System; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Navigation; + +namespace WpfApplication1 +{ + public partial class StartPage : Page + { + TextBlock txtElement; + StackPanel rootPanel; + Button aButton; + void Init(object sender, EventArgs args) + { + rootPanel = new StackPanel(); + txtElement = new TextBlock(); + aButton = new Button(); + aButton.Content = "Press me"; + + rootPanel.Children.Add(txtElement); + rootPanel.Children.Add(aButton); + } + } +} + diff --git a/c-sharp/Others/Painting a 3D surface with a bitmap.cs b/c-sharp/Others/Painting a 3D surface with a bitmap.cs new file mode 100644 index 0000000..290e200 --- /dev/null +++ b/c-sharp/Others/Painting a 3D surface with a bitmap.cs @@ -0,0 +1,37 @@ +Painting a 3D surface with a bitmap + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + diff --git a/c-sharp/Others/Paints a rectangle with a checkered pattern.cs b/c-sharp/Others/Paints a rectangle with a checkered pattern.cs new file mode 100644 index 0000000..66eca02 --- /dev/null +++ b/c-sharp/Others/Paints a rectangle with a checkered pattern.cs @@ -0,0 +1,26 @@ +Paints a rectangle with a checkered pattern + + + + + + + + + + + + + + + + + + + + + diff --git a/c-sharp/Others/Paragraph FontWeight.cs b/c-sharp/Others/Paragraph FontWeight.cs new file mode 100644 index 0000000..55ad299 --- /dev/null +++ b/c-sharp/Others/Paragraph FontWeight.cs @@ -0,0 +1,49 @@ +Paragraph FontWeight + + + +
+ Superman + Superman +
+ Superman +
+ + Superman + + + Superman + + + Superman + + + Superman + + + sSuperman + + + Superman + + + Superman + + + The Middle Years + + + + + + Superman + + + Superman + +
+ diff --git a/c-sharp/Others/Password for PasswordBox.cs b/c-sharp/Others/Password for PasswordBox.cs new file mode 100644 index 0000000..a93ac78 --- /dev/null +++ b/c-sharp/Others/Password for PasswordBox.cs @@ -0,0 +1,20 @@ +Password for PasswordBox + + + + + + + + + + + + + + + diff --git a/c-sharp/Others/PasswordBox with Margin.cs b/c-sharp/Others/PasswordBox with Margin.cs new file mode 100644 index 0000000..1486994 --- /dev/null +++ b/c-sharp/Others/PasswordBox with Margin.cs @@ -0,0 +1,12 @@ +PasswordBox with Margin + + + + + + + diff --git a/c-sharp/Others/Path with ScaleTransformation.cs b/c-sharp/Others/Path with ScaleTransformation.cs new file mode 100644 index 0000000..2bca457 --- /dev/null +++ b/c-sharp/Others/Path with ScaleTransformation.cs @@ -0,0 +1,35 @@ +Path with ScaleTransformation + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + diff --git a/c-sharp/Others/PenLineCap.Round.cs b/c-sharp/Others/PenLineCap.Round.cs new file mode 100644 index 0000000..5f54c5a --- /dev/null +++ b/c-sharp/Others/PenLineCap.Round.cs @@ -0,0 +1,36 @@ +PenLineCap.Round + + + + + + + + + + + + + + + + + + diff --git a/c-sharp/Others/PenLineJoin.Bevel.cs b/c-sharp/Others/PenLineJoin.Bevel.cs new file mode 100644 index 0000000..d0d2ab3 --- /dev/null +++ b/c-sharp/Others/PenLineJoin.Bevel.cs @@ -0,0 +1,32 @@ +PenLineJoin.Bevel + + + + + + + + + + + + + + + + + diff --git a/c-sharp/Others/Play audio through event trigger.cs b/c-sharp/Others/Play audio through event trigger.cs new file mode 100644 index 0000000..f961bf1 --- /dev/null +++ b/c-sharp/Others/Play audio through event trigger.cs @@ -0,0 +1,24 @@ +Play audio through event trigger + + + + + + + diff --git a/c-sharp/Others/Play mp3 file.cs b/c-sharp/Others/Play mp3 file.cs new file mode 100644 index 0000000..fee242d --- /dev/null +++ b/c-sharp/Others/Play mp3 file.cs @@ -0,0 +1,45 @@ +Play mp3 file + + + + + + + + + + + + + + + diff --git a/c-sharp/Others/Ployline types do not require connecting ends.cs b/c-sharp/Others/Ployline types do not require connecting ends.cs new file mode 100644 index 0000000..fe7df37 --- /dev/null +++ b/c-sharp/Others/Ployline types do not require connecting ends.cs @@ -0,0 +1,12 @@ +Ployline types do not require connecting ends + + + + + + + diff --git a/c-sharp/Others/Polygon Mouse down event.cs b/c-sharp/Others/Polygon Mouse down event.cs new file mode 100644 index 0000000..625765d --- /dev/null +++ b/c-sharp/Others/Polygon Mouse down event.cs @@ -0,0 +1,43 @@ +Polygon Mouse down event + + + + + + + + +//File:Window.xaml.cs + +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Data; +using System.Windows.Documents; +using System.Windows.Input; +using System.Windows.Media; +using System.Windows.Media.Imaging; +using System.Windows.Shapes; + +namespace WpfApplication1 +{ + public partial class ShapesWindow : Window + { + public ShapesWindow() + { + InitializeComponent(); + } + + private void Polygon_MouseDown(object sender, MouseButtonEventArgs e) + { + MessageBox.Show("happycodings.com"); + } + } +} + diff --git a/c-sharp/Others/Polygon Stretch=Fill.cs b/c-sharp/Others/Polygon Stretch=Fill.cs new file mode 100644 index 0000000..f136748 --- /dev/null +++ b/c-sharp/Others/Polygon Stretch=Fill.cs @@ -0,0 +1,11 @@ +Polygon Stretch=Fill + + + + + + + diff --git a/c-sharp/Others/Polygon with Fill.cs b/c-sharp/Others/Polygon with Fill.cs new file mode 100644 index 0000000..f7c483a --- /dev/null +++ b/c-sharp/Others/Polygon with Fill.cs @@ -0,0 +1,17 @@ +Polygon with Fill + + + + + + + + + + + diff --git a/c-sharp/Others/Polyline by Points.cs b/c-sharp/Others/Polyline by Points.cs new file mode 100644 index 0000000..4003c3d --- /dev/null +++ b/c-sharp/Others/Polyline by Points.cs @@ -0,0 +1,10 @@ +Polyline by Points + + + + + + + diff --git a/c-sharp/Others/Print Custom Page.cs b/c-sharp/Others/Print Custom Page.cs new file mode 100644 index 0000000..92c727f --- /dev/null +++ b/c-sharp/Others/Print Custom Page.cs @@ -0,0 +1,62 @@ +Print Custom Page + + + + + this is a test + + + + +//File:Window.xaml.cs +using System; +using System.Collections.Generic; +using System.Text; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Data; +using System.Windows.Documents; +using System.Windows.Input; +using System.Windows.Media; +using System.Windows.Media.Imaging; +using System.Windows.Shapes; +using System.Globalization; + +namespace Printing +{ + public partial class PrintCustomPage : System.Windows.Window + { + public PrintCustomPage() + { + InitializeComponent(); + } + private void cmdPrint_Click(object sender, RoutedEventArgs e) + { + PrintDialog printDialog = new PrintDialog(); + if (printDialog.ShowDialog() == true) + { + DrawingVisual visual = new DrawingVisual(); + using (DrawingContext dc = visual.RenderOpen()) + { + FormattedText text = new FormattedText(txtContent.Text, + CultureInfo.CurrentCulture, FlowDirection.LeftToRight, + new Typeface("Calibri"), 20, Brushes.Black); + + text.MaxTextWidth = printDialog.PrintableAreaWidth / 2; + Point point = new Point(80,80); + + dc.DrawText(text, point); + + dc.DrawRectangle(null, new Pen(Brushes.Black, 1), + new Rect(180, 180, 60,60)); + } + + printDialog.PrintVisual(visual, "A Printed Page"); + } + } + } +} + diff --git a/c-sharp/Others/Print a WPF Visual.cs b/c-sharp/Others/Print a WPF Visual.cs new file mode 100644 index 0000000..09a8501 --- /dev/null +++ b/c-sharp/Others/Print a WPF Visual.cs @@ -0,0 +1,71 @@ +Print a WPF Visual + + + + + + + + + + + diff --git a/c-sharp/Others/Property Inheritance.cs b/c-sharp/Others/Property Inheritance.cs new file mode 100644 index 0000000..b97442e --- /dev/null +++ b/c-sharp/Others/Property Inheritance.cs @@ -0,0 +1,14 @@ +Property Inheritance + + + + TextBlock + + + + diff --git a/c-sharp/Others/Property changed callback.cs b/c-sharp/Others/Property changed callback.cs new file mode 100644 index 0000000..37dff6d --- /dev/null +++ b/c-sharp/Others/Property changed callback.cs @@ -0,0 +1,42 @@ +Property changed callback + + + + + + + + + + + +//File:Window1.xaml.cs +using System.Windows; +using System.Windows.Controls; +using System.Windows.Media; + +namespace WpfApplication1 +{ + public partial class Window1 : Window + { + public Window1() + { + InitializeComponent(); + DataContext = this; + } + private static void UserValue_PropertyChangedCallback(DependencyObject d, DependencyPropertyChangedEventArgs e) + { + Window1 window1 = d as Window1; + + if (window1 != null) + { + window1.uv.Foreground = Brushes.SeaGreen; + } + } + } +} + diff --git a/c-sharp/Others/Proportional Tiles.cs b/c-sharp/Others/Proportional Tiles.cs new file mode 100644 index 0000000..7aec1da --- /dev/null +++ b/c-sharp/Others/Proportional Tiles.cs @@ -0,0 +1,18 @@ +Proportional Tiles + + + + + Proportional Tiles + + + + + + + + diff --git a/c-sharp/Others/Put Canvas into ScrollViewer.cs b/c-sharp/Others/Put Canvas into ScrollViewer.cs new file mode 100644 index 0000000..1c75ba9 --- /dev/null +++ b/c-sharp/Others/Put Canvas into ScrollViewer.cs @@ -0,0 +1,28 @@ +Put Canvas into ScrollViewer + + + + + + + + + + + + + + + + + + + + + + + diff --git a/c-sharp/Others/Query Left or Right control key.cs b/c-sharp/Others/Query Left or Right control key.cs new file mode 100644 index 0000000..6630b22 --- /dev/null +++ b/c-sharp/Others/Query Left or Right control key.cs @@ -0,0 +1,45 @@ +Query Left / Right control key + + + + + + + + + + + +//File:Window.xaml.cs +using System; +using System.Collections.Generic; +using System.Text; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Data; +using System.Windows.Documents; +using System.Windows.Input; +using System.Windows.Media; +using System.Windows.Media.Imaging; +using System.Windows.Shapes; +using System.ComponentModel; + +namespace Windows +{ + public partial class CenterScreen : System.Windows.Window + { + public CenterScreen() + { + InitializeComponent(); + } + + private void cmdCenter_Click(object sender, RoutedEventArgs e) + { + double height = SystemParameters.WorkArea.Height; + double width = SystemParameters.WorkArea.Width; + this.Top = (height - this.Height) / 2; + this.Left = (width - this.Width) / 2; + + } + } +} + diff --git a/c-sharp/Others/Remove Animations with Storyboard.cs b/c-sharp/Others/Remove Animations with Storyboard.cs new file mode 100644 index 0000000..d786e58 --- /dev/null +++ b/c-sharp/Others/Remove Animations with Storyboard.cs @@ -0,0 +1,53 @@ +Remove Animations with Storyboard + + + + + + + + + + + + + + + + diff --git a/c-sharp/Others/Repetition count.cs b/c-sharp/Others/Repetition count.cs new file mode 100644 index 0000000..fe7cf80 --- /dev/null +++ b/c-sharp/Others/Repetition count.cs @@ -0,0 +1,27 @@ +Repetition count + + + + + + + + + + + + + + + + + + + + + + diff --git a/c-sharp/Others/Repetition duration.cs b/c-sharp/Others/Repetition duration.cs new file mode 100644 index 0000000..7fcd477 --- /dev/null +++ b/c-sharp/Others/Repetition duration.cs @@ -0,0 +1,26 @@ +Repetition duration + + + + + + + + + + + + + + + + + + + + + diff --git a/c-sharp/Others/Replease mouse with Mouse.Capture(null).cs b/c-sharp/Others/Replease mouse with Mouse.Capture(null).cs new file mode 100644 index 0000000..3809de3 --- /dev/null +++ b/c-sharp/Others/Replease mouse with Mouse.Capture(null).cs @@ -0,0 +1,48 @@ +Replease mouse with Mouse.Capture(null) + + + + + + + + +//File:Window.xaml.cs +using System; +using System.Collections.Generic; +using System.Text; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Data; +using System.Windows.Documents; +using System.Windows.Input; +using System.Windows.Media; +using System.Windows.Media.Imaging; +using System.Windows.Shapes; +using System.Diagnostics; + + +namespace WpfApplication1 +{ + public partial class Window1 : System.Windows.Window + { + public Window1() + { + InitializeComponent(); + + myEllipse.MouseUp += myEllipse_MouseUp; + + } + + void myEllipse_MouseUp(object sender, MouseButtonEventArgs e) + { + Mouse.Capture(null); + } + + + } +} + diff --git a/c-sharp/Others/Resource Lookup.cs b/c-sharp/Others/Resource Lookup.cs new file mode 100644 index 0000000..de83a82 --- /dev/null +++ b/c-sharp/Others/Resource Lookup.cs @@ -0,0 +1,34 @@ +Resource Lookup + + + + + + + + + + + + + + + + + + + + + diff --git a/c-sharp/Others/Rotate then Translate.cs b/c-sharp/Others/Rotate then Translate.cs new file mode 100644 index 0000000..d40181a --- /dev/null +++ b/c-sharp/Others/Rotate then Translate.cs @@ -0,0 +1,28 @@ +Rotate then Translate + + + + + + + + + + + + + + + + + + + + + diff --git a/c-sharp/Others/Rotating Popup.cs b/c-sharp/Others/Rotating Popup.cs new file mode 100644 index 0000000..712f8ed --- /dev/null +++ b/c-sharp/Others/Rotating Popup.cs @@ -0,0 +1,29 @@ +Rotating Popup + + + + + + + + + + Rotating Popup + + + + + + + + diff --git a/c-sharp/Others/Rounded Rectangle Corner radius of 100 (X) and 60 (Y).cs b/c-sharp/Others/Rounded Rectangle Corner radius of 100 (X) and 60 (Y).cs new file mode 100644 index 0000000..9371932 --- /dev/null +++ b/c-sharp/Others/Rounded Rectangle Corner radius of 100 (X) and 60 (Y).cs @@ -0,0 +1,16 @@ +Rounded Rectangle Corner radius of 100 (X) and 60 (Y) + + + + + + Corner radius of 100 (X) and 60 (Y). + + + + diff --git a/c-sharp/Others/RoutedEvents Drag And Drop.cs b/c-sharp/Others/RoutedEvents Drag And Drop.cs new file mode 100644 index 0000000..ddc4890 --- /dev/null +++ b/c-sharp/Others/RoutedEvents Drag And Drop.cs @@ -0,0 +1,61 @@ +RoutedEvents: Drag And Drop + + + + Drag from this TextBox + + + + + +//File:Window.xaml.cs + + +using System; +using System.Collections.Generic; +using System.Text; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Data; +using System.Windows.Documents; +using System.Windows.Input; +using System.Windows.Media; +using System.Windows.Media.Imaging; +using System.Windows.Shapes; + +namespace RoutedEvents +{ + public partial class DragAndDrop : System.Windows.Window + { + public DragAndDrop() + { + InitializeComponent(); + } + + private void lblSource_MouseDown(object sender, MouseButtonEventArgs e) + { + Label lbl = (Label)sender; + DragDrop.DoDragDrop(lbl, lbl.Content, DragDropEffects.Copy); + } + + private void lblTarget_Drop(object sender, DragEventArgs e) + { + ((Label)sender).Content = e.Data.GetData(DataFormats.Text); + } + + private void lblTarget_DragEnter(object sender, DragEventArgs e) + { + if (e.Data.GetDataPresent(DataFormats.Text)) + e.Effects = DragDropEffects.Copy; + else + e.Effects = DragDropEffects.None; + } + } +} + diff --git a/c-sharp/Others/ScrollViewer and Big Ellipse.cs b/c-sharp/Others/ScrollViewer and Big Ellipse.cs new file mode 100644 index 0000000..c877458 --- /dev/null +++ b/c-sharp/Others/ScrollViewer and Big Ellipse.cs @@ -0,0 +1,10 @@ +ScrollViewer and Big Ellipse + + + + + + + diff --git a/c-sharp/Others/Set AccessText for Label.cs b/c-sharp/Others/Set AccessText for Label.cs new file mode 100644 index 0000000..ce05453 --- /dev/null +++ b/c-sharp/Others/Set AccessText for Label.cs @@ -0,0 +1,20 @@ +Set AccessText for Label + + + + + + + + + + + diff --git a/c-sharp/Others/Set Binding ListView.ItemsSourceProperty to ListView.cs b/c-sharp/Others/Set Binding ListView.ItemsSourceProperty to ListView.cs new file mode 100644 index 0000000..2d6624f --- /dev/null +++ b/c-sharp/Others/Set Binding ListView.ItemsSourceProperty to ListView.cs @@ -0,0 +1,69 @@ +Set Binding ListView.ItemsSourceProperty to ListView + + + + + + + + + + + + + + + + + + + + + + +//File:Window.xaml.cs + + +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Data; +using System.Windows.Documents; +using System.Windows.Input; +using System.Windows.Media; +using System.Windows.Media.Imaging; +using System.Windows.Shapes; +using System.Diagnostics; + +namespace WpfApplication1 +{ + public partial class Monitor : Window + { + public Monitor() + { + InitializeComponent(); + BindProcessesToListView(); + } + + private void BindProcessesToListView() + { + ObjectDataProvider provider = new ObjectDataProvider(); + provider.ObjectType = typeof(Process); + provider.MethodName = "GetProcesses"; + Binding binding = new Binding(); + binding.Source = provider; + binding.Mode = BindingMode.OneWay; + + listView1.SetBinding(ListView.ItemsSourceProperty, binding); + } + } +} + diff --git a/c-sharp/Others/Set Border BorderBrush to ImageBrush.cs b/c-sharp/Others/Set Border BorderBrush to ImageBrush.cs new file mode 100644 index 0000000..8e2d21e --- /dev/null +++ b/c-sharp/Others/Set Border BorderBrush to ImageBrush.cs @@ -0,0 +1,20 @@ +Set Border's BorderBrush to ImageBrush + + + + + + + + + + This DockPanel has a border painted with an ImageBrush. + + + + + + diff --git a/c-sharp/Others/Set Grid Row and Column for a Button.cs b/c-sharp/Others/Set Grid Row and Column for a Button.cs new file mode 100644 index 0000000..edcd1fc --- /dev/null +++ b/c-sharp/Others/Set Grid Row and Column for a Button.cs @@ -0,0 +1,25 @@ +Set Grid Row and Column for a Button + + + + + + + diff --git a/c-sharp/Others/Set Message, Header, and Button for MessageBox.cs b/c-sharp/Others/Set Message, Header, and Button for MessageBox.cs new file mode 100644 index 0000000..79e477e --- /dev/null +++ b/c-sharp/Others/Set Message, Header, and Button for MessageBox.cs @@ -0,0 +1,44 @@ +Set Message, Header, and Button for MessageBox + + + + + + diff --git a/c-sharp/Others/Shape Union.cs b/c-sharp/Others/Shape Union.cs new file mode 100644 index 0000000..5dce42e --- /dev/null +++ b/c-sharp/Others/Shape Union.cs @@ -0,0 +1,24 @@ +Shape Union + + + + + + + + + + + + + + Union + + + + diff --git a/c-sharp/Others/Sharing a Style.cs b/c-sharp/Others/Sharing a Style.cs new file mode 100644 index 0000000..8a635e7 --- /dev/null +++ b/c-sharp/Others/Sharing a Style.cs @@ -0,0 +1,38 @@ +Sharing a Style + + + + + + + + + 2 + + + + 4 + + + 5 + + + + + + + diff --git a/c-sharp/Others/Shorthand Path data.cs b/c-sharp/Others/Shorthand Path data.cs new file mode 100644 index 0000000..61d7b6b --- /dev/null +++ b/c-sharp/Others/Shorthand Path data.cs @@ -0,0 +1,14 @@ +Shorthand Path data + + + + + + + + + + + diff --git a/c-sharp/Others/Simple Border.cs b/c-sharp/Others/Simple Border.cs new file mode 100644 index 0000000..803f0a3 --- /dev/null +++ b/c-sharp/Others/Simple Border.cs @@ -0,0 +1,17 @@ +Simple Border + + + + + + + + + + + diff --git a/c-sharp/Others/Simple WrapPanel.cs b/c-sharp/Others/Simple WrapPanel.cs new file mode 100644 index 0000000..3fc99a9 --- /dev/null +++ b/c-sharp/Others/Simple WrapPanel.cs @@ -0,0 +1,17 @@ +Simple WrapPanel + + + + + + + + + + + + + + diff --git a/c-sharp/Others/Simple underline decoration.cs b/c-sharp/Others/Simple underline decoration.cs new file mode 100644 index 0000000..d0b50b7 --- /dev/null +++ b/c-sharp/Others/Simple underline decoration.cs @@ -0,0 +1,36 @@ +Simple underline decoration + + + + + + +//File:Window.xaml.cs +using System; +using System.Collections.Generic; +using System.Text; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Data; +using System.Windows.Documents; +using System.Windows.Input; +using System.Windows.Media; +using System.Windows.Media.Imaging; +using System.Windows.Shapes; + + +namespace Decorations +{ + public partial class Window1 : System.Windows.Window + { + public Window1() + { + InitializeComponent(); + text.TextDecorations = TextDecorations.Underline; + } + } +} + diff --git a/c-sharp/Others/Skew the text using a TranslateTransform.cs b/c-sharp/Others/Skew the text using a TranslateTransform.cs new file mode 100644 index 0000000..7493315 --- /dev/null +++ b/c-sharp/Others/Skew the text using a TranslateTransform.cs @@ -0,0 +1,20 @@ +Skew the text using a TranslateTransform + + + + + + + + + + + + + + diff --git a/c-sharp/Others/SkipList.cs b/c-sharp/Others/SkipList.cs new file mode 100644 index 0000000..10b32d4 --- /dev/null +++ b/c-sharp/Others/SkipList.cs @@ -0,0 +1,255 @@ +using System; +using System.Collections.Generic; +using System.Diagnostics.Contracts; + + +namespace DataStructures.SkipListSpace +{ + /// + /// Key value pair implemented in Skip List + /// + /// Key in key value pair + /// Value in key value pair + [Serializable] + public partial class SkipList : IEnumerable, ICollection + where TKey : IComparable + { + private readonly object lockObject = new object(); + + private readonly int maxLevel; + private int level; + private SkipNode header; + private readonly NullSkipNode NullNode; + private double probability; + private const double Probability = 0.5; + private readonly Random random = new Random(); + + public int Count { get; private set; } + public bool IsSynchronized + { + get { return false; } + } + public object SyncRoot + { + get { return lockObject; } + } + + [ContractInvariantMethod] + private void ObjectInvariant() + { + Contract.Invariant(probability > 0); + Contract.Invariant(probability < 1); + Contract.Invariant(maxLevel > 0); + } + + private SkipList(double probable, int maxLevel) + { + Contract.Requires(maxLevel > 0); + Contract.Requires(probable < 1); + Contract.Requires(probable > 0); + + this.probability = probable; + this.maxLevel = maxLevel; + level = 0; + header = new SkipNode(maxLevel); + NullNode = new NullSkipNode(maxLevel); + //Initially all the forward links node of dummy header is NullNode + for (int i = 0; i < maxLevel; i++) + { + header.Links[i] = NullNode; + } + } + + public static SkipList CreateInstance(long maxNodes) + { + return new SkipList(Probability, (int)(Math.Ceiling(Math.Log(maxNodes) / + Math.Log(1 / Probability) - 1))); + } + + private int GetRandomLevel() + { + Contract.Ensures(Contract.Result() >= 0); + Contract.Ensures(Contract.Result() < maxLevel); + + int newLevel = 0; + double ran = random.NextDouble(); + while ((newLevel < maxLevel) && (ran < probability)) + { + newLevel++; + } + return newLevel; + } + + /// + /// Insert key value pair in list + /// + /// + /// + public void Insert(TKey key, TValue value) + { + Contract.Requires(key != null, "key"); + + SkipNode[] update = new SkipNode[maxLevel]; + //Start search for each level from dummy header node + SkipNode cursor = header; + + //Start from current max initialized header + for (int i = level; i >= 0; i--) + { + //Find the node which is previous node to current code in any level + while (cursor.Links[i].Key.CompareTo(key) == -1) + { + cursor = cursor.Links[i]; + } + //Put the predecessor node link in the level of update list + update[i] = cursor; + } + //Check level 0 next whether we already have that element + cursor = cursor.Links[0]; + if (cursor.Key.CompareTo(key) == 0) + { + //Assign new value to corresponding key + cursor.Value = value; + } + else + { + //If this is new node, then + //Find random level for insertion + int newLevel = GetRandomLevel(); + //New node level is greater then current level + //Update intermediate nodes + if (newLevel > level) + { + //This is a special case, where dummy header links aren't initialized yet + for (int i = level + 1; i < newLevel; i++) + { + //These levels of header aren't initialized yet + update[i] = header; + } + //update current level, until this level from bottom header link is initialized + level = newLevel; + } + //New node which will be inserted into new level, also needs newLevel number of forward edges + cursor = new SkipNode(newLevel, key, value); + //Insert the node + for (int i = 0; i < newLevel; i++) + { + //Update edges of all the levels below to that level + //New node is set to successor node its predecessor + cursor.Links[i] = update[i].Links[i]; + //Update forward edges of predecessor to currently inserted node + update[i].Links[i] = cursor; + } + Count++; + } + } + + /// + /// Delete from skip list if element exists + /// + /// Key to be deleted + public void Delete(TKey key) + { + Contract.Requires(key != null); + + SkipNode[] update = new SkipNode[maxLevel + 1]; + SkipNode cursor = header; + + for (int i = level; i >= 0; i--) + { + while (cursor.Links[i].Key.CompareTo(key) == -1) + { + cursor = cursor.Links[i]; + } + update[i] = cursor; + } + + cursor = cursor.Links[0]; + //Check is this the element we want to delete? + if (cursor.Key.CompareTo(key) == 0) + { + for (int i = 0; i < level; i++) + { + //If next element is our to be deleted element + //Check prev node point to next node + if (update[i].Links[i] == cursor) + { + update[i].Links[i] = cursor.Links[i]; + } + } + //Readjust levels of initialized links of dummy header + while ((level > 0) && (header.Links[level].Key.Equals(NullNode))) + { + level--; + } + Count--; + } + //Element isn't in the list, just return + } + + /// + /// Search for values, given a key + /// + /// Key to be searched + /// Value otherwise type default + public TValue Search(TKey key) + { + Contract.Requires(key != null); + + SkipNode cursor = header; + for (int i = 0; i < level; i++) + { + SkipNode nextElement = cursor.Links[i]; + while (nextElement.Key.CompareTo(key) == -1) + { + cursor = nextElement; + nextElement = cursor.Links[i]; + } + } + //Got previous element of current key in the list + //So next element must our searched element if list contains that element + cursor = cursor.Links[0]; + if (cursor.Key.Equals(key)) + { + return cursor.Value; + } + else + { + //Element is not in the list, return default + return default(TValue); + } + } + + public void CopyTo(Array array, int index) + { + Contract.Requires(array != null, "array"); + Contract.Requires(index >= 0, "index"); + Contract.Requires(array.Length < Count); + + int i = index; + + var node = header.Links[0]; + while (node != null) + { + array.SetValue(node.Value, i); + node = node.Links[0]; + i++; + } + } + + public IEnumerator GetEnumerator() + { + var node = header.Links[0]; + while (node != null) + { + yield return node.Value; + node = node.Links[0]; + } + } + + System.Collections.IEnumerator System.Collections.IEnumerable.GetEnumerator() + { + return this.GetEnumerator(); + } + } +} \ No newline at end of file diff --git a/c-sharp/Others/SkipNode.cs b/c-sharp/Others/SkipNode.cs new file mode 100644 index 0000000..f4faaee --- /dev/null +++ b/c-sharp/Others/SkipNode.cs @@ -0,0 +1,43 @@ +using System; +using System.Collections.Generic; +using System.Diagnostics.Contracts; + +namespace DataStructures.SkipListSpace +{ + public partial class SkipList : IEnumerable, ICollection + where TKey : IComparable + { + [Serializable] + private class SkipNode + where TKey : IComparable + { + public TKey Key { get; set; } + public TValue Value { get; set; } + //Each link contains next level successor in skip list + public IList> Links { get; private set; } + + [ContractInvariantMethod] + private void ObjectInvariant() + { + Contract.Invariant(Links != null); + Contract.Invariant(Links.Count > 0); + } + + public SkipNode(int level) + { + Contract.Requires(level > 0); + Links = new List>(level); + } + + public SkipNode(int level, TKey key, TValue value) + { + Contract.Requires(key != null); + Contract.Requires(level > 0); + + Key = key; + Value = value; + Links = new List>(level); + } + } + } +} \ No newline at end of file diff --git a/c-sharp/Others/Slider Attributes.cs b/c-sharp/Others/Slider Attributes.cs new file mode 100644 index 0000000..08f554a --- /dev/null +++ b/c-sharp/Others/Slider Attributes.cs @@ -0,0 +1,46 @@ +Slider Attributes + + + + + + + + +//File:Window.xaml.cs +using System; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Data; +using System.Windows.Documents; +using System.Windows.Media; +using System.Windows.Media.Imaging; +using System.Windows.Shapes; +using System.Windows.Input; +namespace ControlDemos +{ + + public partial class Label : Window + { + + public Label() + { + InitializeComponent(); + } + private void sl1_ValueChanged(object sender, EventArgs e) + { + if (sl1.Value < sl1.SelectionStart) + sl1.Value = sl1.SelectionStart; + + if (sl1.Value > sl1.SelectionEnd) + sl1.Value = sl1.SelectionEnd; + } + + } +} + diff --git a/c-sharp/Others/Solid Color Brush In Code with SolidColorBrush.cs b/c-sharp/Others/Solid Color Brush In Code with SolidColorBrush.cs new file mode 100644 index 0000000..0c5a9ca --- /dev/null +++ b/c-sharp/Others/Solid Color Brush In Code with SolidColorBrush.cs @@ -0,0 +1,49 @@ +Solid Color Brush In Code with SolidColorBrush + + + + + + +//File:Window.xaml.cs +using System.Windows; +using System.Windows.Documents; +using System.Windows.Controls; +using System.Windows.Media; +using System.Windows.Shapes; + +namespace WPFBrushes +{ + public partial class SolidColorBrushInCode : System.Windows.Window + { + public SolidColorBrushInCode() + { + InitializeComponent(); + this.Width = 600; + + StackPanel sp = new StackPanel(); + sp.Margin = new Thickness(4.0); + sp.HorizontalAlignment = HorizontalAlignment.Left; + sp.Orientation = Orientation.Vertical; + + TextBlock tb1 = new TextBlock(new Run(@"Brush from Predefined Color [ .Fill = new SolidColorBrush(Colors.Green); ]")); + Rectangle rect1 = new Rectangle(); + rect1.HorizontalAlignment = HorizontalAlignment.Left; + rect1.Width = 80; + rect1.Height = 25; + rect1.Fill = new SolidColorBrush(Colors.Green); + + sp.Children.Add(tb1); + sp.Children.Add(rect1); + + this.Content = sp; + + } + + } +} + diff --git a/c-sharp/Others/SolidColorBrush described using 8-digit hexadecimal notation.cs b/c-sharp/Others/SolidColorBrush described using 8-digit hexadecimal notation.cs new file mode 100644 index 0000000..9abf83e --- /dev/null +++ b/c-sharp/Others/SolidColorBrush described using 8-digit hexadecimal notation.cs @@ -0,0 +1,25 @@ +SolidColorBrush described using 8-digit hexadecimal notation + + + + + + + + + + + + + + diff --git a/c-sharp/Others/SortedList.cs b/c-sharp/Others/SortedList.cs new file mode 100644 index 0000000..ccf0314 --- /dev/null +++ b/c-sharp/Others/SortedList.cs @@ -0,0 +1,135 @@ +using System; +using System.Collections.Generic; +using System.Diagnostics.Contracts; + +namespace DataStructures.ListSpace +{ + /// + /// Use insertion sort for every element added + /// + /// + [Serializable] + public class SortedList : IEnumerable, ICollection + where T : IComparable + { + private List list; + + public int Capacity + { + get { return list.Capacity; } + } + + bool ICollection.Remove(T item) + { + var success = ((ICollection)list).Remove(item); + return success; + } + + public int Count + { + get { return list.Count; } + } + + public bool IsReadOnly { get; private set; } + public bool IsSynchronized { get { return false; } } + + [ContractInvariantMethod] + private void ObjectInvariant() + { + Contract.Invariant(Count >= 0); + Contract.Invariant(Capacity >= 0); + } + + public SortedList() + { + list = new List(); + } + + public SortedList(int capacity) + { + Contract.Requires(capacity > 0); + + list = new List(capacity); + } + + public SortedList(IEnumerable list) + { + Contract.Requires(list != null); + + this.list = new List(list); + this.list.Sort(); + } + + public void Add(T element) + { + Contract.Requires(element != null); + + var count = 0; + //search for the previous element only when there are other elements in the list + if(list.Count>0){ + for (var i = 0; i < list.Count; i++, count++) + { + if (element.CompareTo(list[i]) <= 0) + { + count = i; + break; + } + } + if(count>0) + Contract.Assert(list[count-1].CompareTo(element) <= 0); + } + list.Insert(count, element); + } + + public void Clear() + { + list = new List(); + } + + public bool Contains(T item) + { + return list.Contains(item); + } + + public void CopyTo(T[] array, int arrayIndex) + { + Contract.Requires(array != null, "array is null"); + Contract.Requires(arrayIndex >= 0, "arrayIndex less than 0"); + + for (var i = arrayIndex; i < list.Count; i++) + { + array[i] = list[i]; + } + } + + public void Remove(T element) + { + Contract.Requires(element != null); + + list.Remove(element); + } + + public void CopyTo(Array array, int index) + { + Contract.Requires(array != null, "array is null"); + Contract.Requires(index >= 0, "arrayIndex less than 0"); + Contract.Requires(array.Length < Count, "array not big enough"); + + int i = index; + foreach (T element in list) + { + array.SetValue(element, i++); + } + } + + public IEnumerator GetEnumerator() + { + return list.GetEnumerator(); + } + + System.Collections.IEnumerator System.Collections.IEnumerable.GetEnumerator() + { + return this.GetEnumerator(); + } + } +} diff --git a/c-sharp/Others/Span and FlowDocument.cs b/c-sharp/Others/Span and FlowDocument.cs new file mode 100644 index 0000000..de9e28a --- /dev/null +++ b/c-sharp/Others/Span and FlowDocument.cs @@ -0,0 +1,19 @@ +Span and FlowDocument + + + + bold + italic + underline + hyperlink + superscript + subscript + + + + + strikethrough + + + + diff --git a/c-sharp/Others/Split.cs b/c-sharp/Others/Split.cs new file mode 100644 index 0000000..d90af97 --- /dev/null +++ b/c-sharp/Others/Split.cs @@ -0,0 +1,13 @@ +using System; + + +namespace DataStructures.BPlusTreeSpace +{ + public partial class BPlusTree + where TKey : IComparable + { + internal class Split + { + } + } +} \ No newline at end of file diff --git a/c-sharp/Others/StackPanel in a ScrollViewer.cs b/c-sharp/Others/StackPanel in a ScrollViewer.cs new file mode 100644 index 0000000..6ebfa0c --- /dev/null +++ b/c-sharp/Others/StackPanel in a ScrollViewer.cs @@ -0,0 +1,25 @@ +StartupUri attribute + + + + +//File:Window.xaml.cs +using System; +using System.Windows; +using System.Windows.Controls; + +namespace SimpleXamlApp +{ + public partial class MyApp : Application + { + void AppExit(object sender, ExitEventArgs e) + { + MessageBox.Show("App has exited"); + } + } +} + diff --git a/c-sharp/Others/Stretch = None.cs b/c-sharp/Others/Stretch = None.cs new file mode 100644 index 0000000..695b2f0 --- /dev/null +++ b/c-sharp/Others/Stretch = None.cs @@ -0,0 +1,16 @@ +Stretch = None + + + + + + + + diff --git a/c-sharp/Others/Stretch = Uniform.cs b/c-sharp/Others/Stretch = Uniform.cs new file mode 100644 index 0000000..946372d --- /dev/null +++ b/c-sharp/Others/Stretch = Uniform.cs @@ -0,0 +1,16 @@ +Stretch = Uniform + + + + + + + + diff --git a/c-sharp/Others/Stretched GridSplitter.cs b/c-sharp/Others/Stretched GridSplitter.cs new file mode 100644 index 0000000..6c8eae4 --- /dev/null +++ b/c-sharp/Others/Stretched GridSplitter.cs @@ -0,0 +1,19 @@ +Stretched GridSplitter + + + + + + + + + + + + + + + + diff --git a/c-sharp/Others/Style With Data Trigger.cs b/c-sharp/Others/Style With Data Trigger.cs new file mode 100644 index 0000000..9ae1d60 --- /dev/null +++ b/c-sharp/Others/Style With Data Trigger.cs @@ -0,0 +1,28 @@ +Style With Data Trigger + + + + + + + + + + + diff --git a/c-sharp/Others/Style With MultiTrigger.cs b/c-sharp/Others/Style With MultiTrigger.cs new file mode 100644 index 0000000..8242156 --- /dev/null +++ b/c-sharp/Others/Style With MultiTrigger.cs @@ -0,0 +1,30 @@ +Style With MultiTrigger + + + + + + + + + + + + + + diff --git a/c-sharp/Others/Subclass CheckBox.cs b/c-sharp/Others/Subclass CheckBox.cs new file mode 100644 index 0000000..ba39334 --- /dev/null +++ b/c-sharp/Others/Subclass CheckBox.cs @@ -0,0 +1,59 @@ +Subclass CheckBox + +using System; +using System.Drawing; +using System.Windows.Forms; + +class CustomCheckBox: Form +{ + public static void Main() + { + Application.Run(new CustomCheckBox()); + } + public CustomCheckBox() + { + int cyText = Font.Height; + int cxText = cyText / 2; + FontStyle[] afs = { FontStyle.Bold, FontStyle.Italic, + FontStyle.Underline, FontStyle.Strikeout }; + + Label label = new Label(); + label.Parent = this; + label.Text = "I Love Clementine"; + label.AutoSize = true; + + for (int j = 0; j < 4; j++) + { + FontStyleCheckBox chkbox = new FontStyleCheckBox(); + chkbox.Parent = this; + chkbox.Text = afs[j].ToString(); + chkbox.fontstyle = afs[j]; + chkbox.Location = new Point(2 * cxText, + (4 + 3 * j) * cyText / 2); + chkbox.Size = new Size(12 * cxText, cyText); + chkbox.CheckedChanged += new EventHandler(CheckBoxOnCheckedChanged); + } + } + void CheckBoxOnCheckedChanged(object obj, EventArgs ea) + { + FontStyle fs = 0; + Label label = null; + + for (int j = 0; j < Controls.Count; j++) + { + Control ctrl = Controls[j]; + + if (ctrl.GetType() == typeof(Label)) + label = (Label) ctrl; + else if (ctrl.GetType() == typeof(FontStyleCheckBox)) + if (((FontStyleCheckBox) ctrl).Checked) + fs |= ((FontStyleCheckBox) ctrl).fontstyle; + } + label.Font = new Font(label.Font, fs); + } +} +class FontStyleCheckBox: CheckBox +{ + public FontStyle fontstyle; +} + diff --git a/c-sharp/Others/Suppress Keyboard and Mouse Events.cs b/c-sharp/Others/Suppress Keyboard and Mouse Events.cs new file mode 100644 index 0000000..0ff12c3 --- /dev/null +++ b/c-sharp/Others/Suppress Keyboard and Mouse Events.cs @@ -0,0 +1,38 @@ +Suppress Keyboard and Mouse Events + + + + + + + + + + _Text + + + I Love Clementine + + + + + + + Ellipse: + + + + +
+ diff --git a/c-sharp/Others/TabControl and Frame source.cs b/c-sharp/Others/TabControl and Frame source.cs new file mode 100644 index 0000000..820f179 --- /dev/null +++ b/c-sharp/Others/TabControl and Frame source.cs @@ -0,0 +1,24 @@ +TabControl and Frame source + + + + + + + + + + + + + + + + + + + diff --git a/c-sharp/Others/Text Wrapping Label.cs b/c-sharp/Others/Text Wrapping Label.cs new file mode 100644 index 0000000..3bfeb4c --- /dev/null +++ b/c-sharp/Others/Text Wrapping Label.cs @@ -0,0 +1,16 @@ +Text Wrapping Label + + + + + + + + + diff --git a/c-sharp/Others/TextBox KeyUp.cs b/c-sharp/Others/TextBox KeyUp.cs new file mode 100644 index 0000000..a49cfb6 --- /dev/null +++ b/c-sharp/Others/TextBox KeyUp.cs @@ -0,0 +1,37 @@ +TextBox KeyUp + + + + + + + + +//File:Window.xaml.cs +using System; +using System.Windows; +using System.Windows.Input; + +namespace WpfApplication1 +{ + public partial class Window1 : Window + { + public Window1() + { + InitializeComponent(); + } + + private void TextBox_KeyEvent(object sender, KeyEventArgs e) + { + String msg = String.Format("{0} - {1}\n",e.RoutedEvent.Name, e.Key); + + txtLog.Text += msg; + txtLog.ScrollToEnd(); + } + } +} + diff --git a/c-sharp/Others/TextBox Style.cs b/c-sharp/Others/TextBox Style.cs new file mode 100644 index 0000000..c4b2d3d --- /dev/null +++ b/c-sharp/Others/TextBox Style.cs @@ -0,0 +1,40 @@ +TextBox Style + + + + + + + + + + + + + + + CheckBox + TextBox + + + TextBlock + ComboBox + + + + diff --git a/c-sharp/Others/TextBox as Button Content.cs b/c-sharp/Others/TextBox as Button Content.cs new file mode 100644 index 0000000..d3ecacc --- /dev/null +++ b/c-sharp/Others/TextBox as Button Content.cs @@ -0,0 +1,15 @@ +TextBox as Button Content + + + + + + + + diff --git a/c-sharp/Others/The UniformGrid.cs b/c-sharp/Others/The UniformGrid.cs new file mode 100644 index 0000000..16c0b82 --- /dev/null +++ b/c-sharp/Others/The UniformGrid.cs @@ -0,0 +1,14 @@ +The UniformGrid + + + + + + + + + + diff --git a/c-sharp/Others/The same margin on all four sides.cs b/c-sharp/Others/The same margin on all four sides.cs new file mode 100644 index 0000000..c1cc7eb --- /dev/null +++ b/c-sharp/Others/The same margin on all four sides.cs @@ -0,0 +1,17 @@ +The same margin on all four sides + + + + + + + + + + + + + + diff --git a/c-sharp/Others/The same padding on all four sides.cs b/c-sharp/Others/The same padding on all four sides.cs new file mode 100644 index 0000000..21b5399 --- /dev/null +++ b/c-sharp/Others/The same padding on all four sides.cs @@ -0,0 +1,15 @@ +The same padding on all four sides + + + + + + + + + + + + diff --git a/c-sharp/Others/Throw Unhandled Exception.cs b/c-sharp/Others/Throw Unhandled Exception.cs new file mode 100644 index 0000000..7c780d8 --- /dev/null +++ b/c-sharp/Others/Throw Unhandled Exception.cs @@ -0,0 +1,34 @@ +Throw Unhandled Exception + + + + + CheckBox + TextBox + + + + + + + + + diff --git a/c-sharp/Others/ToolTip for Border.cs b/c-sharp/Others/ToolTip for Border.cs new file mode 100644 index 0000000..aaf1605 --- /dev/null +++ b/c-sharp/Others/ToolTip for Border.cs @@ -0,0 +1,25 @@ +ToolTip for Border + + + + + + + + + I Love Clementine + + (Hover Over Me) + + + + + + + + diff --git a/c-sharp/Others/Toolbar TraysToolbar Trays.cs b/c-sharp/Others/Toolbar TraysToolbar Trays.cs new file mode 100644 index 0000000..742b665 --- /dev/null +++ b/c-sharp/Others/Toolbar TraysToolbar Trays.cs @@ -0,0 +1,37 @@ +Toolbar Trays + + + + + + + + + + + + + + + + + + + + + + + + + + diff --git a/c-sharp/Others/Translate.cs b/c-sharp/Others/Translate.cs new file mode 100644 index 0000000..1eb8212 --- /dev/null +++ b/c-sharp/Others/Translate.cs @@ -0,0 +1,21 @@ +Translate + + + + + + + + + + + + + + + diff --git a/c-sharp/Others/TranslateTransform X 50 or Y 0.cs b/c-sharp/Others/TranslateTransform X 50 or Y 0.cs new file mode 100644 index 0000000..18ad0a5 --- /dev/null +++ b/c-sharp/Others/TranslateTransform X 50 or Y 0.cs @@ -0,0 +1,19 @@ +TranslateTransform X: 50 / Y: 0 + + + + + + + + + + + + + diff --git a/c-sharp/Others/TransposeList.cs b/c-sharp/Others/TransposeList.cs new file mode 100644 index 0000000..df533db --- /dev/null +++ b/c-sharp/Others/TransposeList.cs @@ -0,0 +1,28 @@ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +using System.Threading.Tasks; + +namespace DataStructures.TransposeListSpaceS +{ + public class TransposeList : IEnumerable + { + private List list = new List(); + + T Get(T element) + { + + } + + public IEnumerator GetEnumerator() + { + throw new NotImplementedException(); + } + + System.Collections.IEnumerator System.Collections.IEnumerable.GetEnumerator() + { + throw new NotImplementedException(); + } + } +} diff --git a/c-sharp/Others/Underline decoration with dashes.cs b/c-sharp/Others/Underline decoration with dashes.cs new file mode 100644 index 0000000..1486975 --- /dev/null +++ b/c-sharp/Others/Underline decoration with dashes.cs @@ -0,0 +1,28 @@ +Underline decoration with dashes + + + + + I Love Clementine + + + + + + + + + + + + + + + + diff --git a/c-sharp/Others/Use ArrayList as the ListView ItemSource.cs b/c-sharp/Others/Use ArrayList as the ListView ItemSource.cs new file mode 100644 index 0000000..806371a --- /dev/null +++ b/c-sharp/Others/Use ArrayList as the ListView ItemSource.cs @@ -0,0 +1,32 @@ +Use ArrayList as the ListView ItemSource + + + + + + + + + + + + + + + 2012/1/1 + 2012/1/2 + + + + + + diff --git a/c-sharp/Others/Use ControlTemplate and event handler.cs b/c-sharp/Others/Use ControlTemplate and event handler.cs new file mode 100644 index 0000000..732e97c --- /dev/null +++ b/c-sharp/Others/Use ControlTemplate and event handler.cs @@ -0,0 +1,54 @@ +Use ControlTemplate and event handler + + + + + + + + + + + + + + + +//File:Window.xaml.cs +using System; +using System.Collections.Generic; +using System.Text; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Data; +using System.Windows.Documents; +using System.Windows.Input; +using System.Windows.Media; +using System.Windows.Media.Imaging; +using System.Windows.Shapes; + + +namespace ControlTemplate +{ + public partial class Window1 : System.Windows.Window + { + + public Window1() + { + InitializeComponent(); + } + + private void button1_Click(object sender, RoutedEventArgs e) + { + MessageBox.Show("I Love Clementine"); + } + + } +} + diff --git a/c-sharp/Others/Use Font from Form to paint string on a form.cs b/c-sharp/Others/Use Font from Form to paint string on a form.cs new file mode 100644 index 0000000..2bd0775 --- /dev/null +++ b/c-sharp/Others/Use Font from Form to paint string on a form.cs @@ -0,0 +1,21 @@ +Use Font from Form to paint string on a form + +using System; +using System.Drawing; +using System.Windows.Forms; + +class InheritHelloWorld : Form { + public static void Main() { + Application.Run(new InheritHelloWorld()); + } + public InheritHelloWorld() { + Text = "Inherit " + Text; + } + protected override void OnPaint(PaintEventArgs pea) { + Graphics graphics = pea.Graphics; + + graphics.DrawString("I Love Clementine", + Font, Brushes.Black, 0, 100); + } +} + diff --git a/c-sharp/Others/Use Frame to Load another Xaml file.cs b/c-sharp/Others/Use Frame to Load another Xaml file.cs new file mode 100644 index 0000000..fd5af8d --- /dev/null +++ b/c-sharp/Others/Use Frame to Load another Xaml file.cs @@ -0,0 +1,19 @@ +Use Frame to Load another Xaml file + + + + + + + + + + + + + + diff --git a/c-sharp/Others/Use JpegBitmapDecoder.cs b/c-sharp/Others/Use JpegBitmapDecoder.cs new file mode 100644 index 0000000..a5e0775 --- /dev/null +++ b/c-sharp/Others/Use JpegBitmapDecoder.cs @@ -0,0 +1,18 @@ +Use JpegBitmapDecoder + +using System; +using System.Collections.Generic; +using System.Text; +using System.Windows.Media.Imaging; +using System.IO; + + class UseBitmapCodecs + { + static string GetCamera(string myJpegPath) + { + JpegBitmapDecoder decoder = new JpegBitmapDecoder(new Uri(myJpegPath),BitmapCreateOptions.None, BitmapCacheOption.None); + BitmapMetadata bmpData = (BitmapMetadata) decoder.Frames[0].Metadata; + return bmpData.CameraModel; + } + } + diff --git a/c-sharp/Others/Use LengthConverter.cs b/c-sharp/Others/Use LengthConverter.cs new file mode 100644 index 0000000..cb81510 --- /dev/null +++ b/c-sharp/Others/Use LengthConverter.cs @@ -0,0 +1,54 @@ +Use LengthConverter + + + + + I Love Clementine + + + + Auto + a + b + c + d + e + f + g + h + i + j + + + +//File:Window.xaml.cs + +using System; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Documents; +using System.Windows.Navigation; +using System.Windows.Shapes; +using System.Windows.Data; + +namespace Canvas_Positioning_Properties +{ + + public partial class Window1 : Window + { + public void ChangeLeft(object sender, SelectionChangedEventArgs args) + { + ListBoxItem li = ((sender as ListBox).SelectedItem as ListBoxItem); + LengthConverter myLengthConverter = new LengthConverter(); + Double db1 = (Double)myLengthConverter.ConvertFromString(li.Content.ToString()); + Canvas.SetLeft(text1, db1); + Console.WriteLine(myLengthConverter.ConvertToString(Canvas.GetLeft(text1))); + } + + + } +} + diff --git a/c-sharp/Others/Use ObservableCollection as Resource.cs b/c-sharp/Others/Use ObservableCollection as Resource.cs new file mode 100644 index 0000000..7336b21 --- /dev/null +++ b/c-sharp/Others/Use ObservableCollection as Resource.cs @@ -0,0 +1,67 @@ +Use ObservableCollection as Resource + + + + + + + + + + Item 1 + Item 2 + Item 3 + Item 4 + Item 5 + Item 6 + Item 7 + Item 8 + Item 9 + Item 10 + + + + +//File:Window.xaml.cs + +using System; +using System.ComponentModel; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Documents; +using System.Windows.Navigation; +using System.Windows.Shapes; +using System.Windows.Data; +using System.Windows.Media; +using System.Collections.ObjectModel; + +namespace ListBoxEvent +{ + public class myColors : ObservableCollection + { + public myColors() + { + Add("A"); + Add("B"); + Add("C"); + Add("D"); + Add("E"); + Add("F"); + } + } + public partial class Pane1 : Canvas + { + + public Pane1() : base(){ + InitializeComponent(); + } + void PrintText(object sender, SelectionChangedEventArgs args) + { + ListBoxItem lbi = ((sender as ListBox).SelectedItem as ListBoxItem); + tb.Text = " You selected " + lbi.Content.ToString() + "."; + } + } +} + diff --git a/c-sharp/Others/Use Popup to display a hyperlink.cs b/c-sharp/Others/Use Popup to display a hyperlink.cs new file mode 100644 index 0000000..a2d884d --- /dev/null +++ b/c-sharp/Others/Use Popup to display a hyperlink.cs @@ -0,0 +1,56 @@ +Use Popup to display a hyperlink + + + + text + link + + + + + check out + happycodings.com + + + + + +//File:Window.xaml.cs + +using System; +using System.Collections.Generic; +using System.Text; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Data; +using System.Windows.Documents; +using System.Windows.Input; +using System.Windows.Media; +using System.Windows.Media.Imaging; +using System.Windows.Shapes; +using System.Diagnostics; + +namespace ClassicControls +{ + public partial class PopupTest : System.Windows.Window + { + + public PopupTest() + { + InitializeComponent(); + } + + private void run_MouseEnter(object sender, MouseEventArgs e) + { + popLink.IsOpen = true; + } + private void lnk_Click(object sender, RoutedEventArgs e) + { + Process.Start(((Hyperlink)sender).NavigateUri.ToString()); + } + } +} + diff --git a/c-sharp/Others/Use Slider to control Drop Shadow.cs b/c-sharp/Others/Use Slider to control Drop Shadow.cs new file mode 100644 index 0000000..34837a7 --- /dev/null +++ b/c-sharp/Others/Use Slider to control Drop Shadow.cs @@ -0,0 +1,22 @@ +Use Slider to control Drop Shadow + + + + + + + + + + + + + + + diff --git a/c-sharp/Others/Use Slider to control the ScaleTransform.cs b/c-sharp/Others/Use Slider to control the ScaleTransform.cs new file mode 100644 index 0000000..a9777e3 --- /dev/null +++ b/c-sharp/Others/Use Slider to control the ScaleTransform.cs @@ -0,0 +1,40 @@ +Use Slider to control the ScaleTransform + + + + + diff --git a/c-sharp/Others/Use outter resource or inner resource.cs b/c-sharp/Others/Use outter resource or inner resource.cs new file mode 100644 index 0000000..f46b72a --- /dev/null +++ b/c-sharp/Others/Use outter resource or inner resource.cs @@ -0,0 +1,32 @@ +Use outter resource or inner resource + + + + + + + + + + + + + + + + diff --git a/c-sharp/Others/Using LinearGradientBrush to draw a 3D button.cs b/c-sharp/Others/Using LinearGradientBrush to draw a 3D button.cs new file mode 100644 index 0000000..f23fdc8 --- /dev/null +++ b/c-sharp/Others/Using LinearGradientBrush to draw a 3D button.cs @@ -0,0 +1,41 @@ +Using LinearGradientBrush to draw a 3D button + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + diff --git a/c-sharp/Others/Using MediaElement for Audio.cs b/c-sharp/Others/Using MediaElement for Audio.cs new file mode 100644 index 0000000..75a77a2 --- /dev/null +++ b/c-sharp/Others/Using MediaElement for Audio.cs @@ -0,0 +1,28 @@ +Using MediaElement for Audio + + + + + + diff --git a/c-sharp/Others/Using XmlDataProvider.cs b/c-sharp/Others/Using XmlDataProvider.cs new file mode 100644 index 0000000..c24d648 --- /dev/null +++ b/c-sharp/Others/Using XmlDataProvider.cs @@ -0,0 +1,42 @@ +Using XmlDataProvider + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + diff --git a/c-sharp/Others/Using a DispatcherTimer.cs b/c-sharp/Others/Using a DispatcherTimer.cs new file mode 100644 index 0000000..56afd56 --- /dev/null +++ b/c-sharp/Others/Using a DispatcherTimer.cs @@ -0,0 +1,47 @@ +Using a DispatcherTimer + + + + + + +//File:Window.xaml.cs +using System; +using System.Collections.Generic; +using System.Text; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Data; +using System.Windows.Documents; +using System.Windows.Input; +using System.Windows.Media; +using System.Windows.Media.Imaging; +using System.Windows.Shapes; +using System.Windows.Threading; + +namespace DispatcherExamples2 +{ + partial class MyWindow : Window + { + DispatcherTimer dt = new DispatcherTimer(); + public MyWindow() + { + InitializeComponent(); + dt.Tick += dt_Tick; + dt.Interval = TimeSpan.FromSeconds(2); + dt.Start(); + } + void dt_Tick(object sender, EventArgs e) + { + Random rnd = new Random(); + byte[] vals = new byte[3]; + rnd.NextBytes(vals); + Color c = Color.FromRgb(vals[0], vals[1], vals[2]); + this.Background = new SolidColorBrush(c); + } + } +} + diff --git a/c-sharp/Others/Using a Style resource.cs b/c-sharp/Others/Using a Style resource.cs new file mode 100644 index 0000000..a4a748e --- /dev/null +++ b/c-sharp/Others/Using a Style resource.cs @@ -0,0 +1,29 @@ +Using a Style resource + + + + + + + + + + + + + + diff --git a/c-sharp/Others/Using the Jpeg Image.cs b/c-sharp/Others/Using the Jpeg Image.cs new file mode 100644 index 0000000..bae704b --- /dev/null +++ b/c-sharp/Others/Using the Jpeg Image.cs @@ -0,0 +1,14 @@ +Using the Jpeg Image + + + + + + + + + diff --git a/c-sharp/Others/Velocity animation.cs b/c-sharp/Others/Velocity animation.cs new file mode 100644 index 0000000..85f4cb9 --- /dev/null +++ b/c-sharp/Others/Velocity animation.cs @@ -0,0 +1,63 @@ +Velocity animation + + + + + + + +//File:Window.xaml.cs + + +using System; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Data; +using System.Windows.Documents; +using System.Windows.Media; +using System.Windows.Navigation; +using System.Windows.Shapes; +using System.Windows.Media.Animation; + +namespace Microsoft.Samples.PerFrameAnimations +{ + public partial class FrameIndependentFollowExample : Page + { + private Vector _rectangleVelocity = new Vector(0, 0); + private Point _lastMousePosition = new Point(450, 450); + + private TimeSpan _lastRender; + + public FrameIndependentFollowExample(): base() + { + _lastRender = TimeSpan.FromTicks(DateTime.Now.Ticks); + CompositionTarget.Rendering += UpdateRectangle; + } + + private void UpdateRectangle(object sender, EventArgs e) + { + RenderingEventArgs renderArgs = (RenderingEventArgs)e; + Double deltaTime = (renderArgs.RenderingTime - _lastRender).TotalSeconds; + _lastRender = renderArgs.RenderingTime; + + Point location = new Point(0,0); + + Vector toMouse = _lastMousePosition - location; + + double followForce = 1.00; + _rectangleVelocity += toMouse * followForce; + + double drag = 0.9; + _rectangleVelocity *= drag; + + location += _rectangleVelocity * deltaTime; + + Canvas.SetLeft(followRectangle, location.X); + Canvas.SetTop(followRectangle, location.Y); + } + } +} + diff --git a/c-sharp/Others/Vertical Line.cs b/c-sharp/Others/Vertical Line.cs new file mode 100644 index 0000000..1b76a4d --- /dev/null +++ b/c-sharp/Others/Vertical Line.cs @@ -0,0 +1,31 @@ +Vertical Line + + + + + + + + + + + + + + + + + + + + + + + + + + diff --git a/c-sharp/Others/Vertical WrapPanel Window.cs b/c-sharp/Others/Vertical WrapPanel Window.cs new file mode 100644 index 0000000..4533f8a --- /dev/null +++ b/c-sharp/Others/Vertical WrapPanel Window.cs @@ -0,0 +1,26 @@ +Vertical WrapPanel Window + + + + + + + + + + + + + + + + + + + + + + diff --git a/c-sharp/Others/Vertical linear gradient.cs b/c-sharp/Others/Vertical linear gradient.cs new file mode 100644 index 0000000..04c2395 --- /dev/null +++ b/c-sharp/Others/Vertical linear gradient.cs @@ -0,0 +1,19 @@ +Vertical linear gradient + + + + + + + + + + + + + + + diff --git a/c-sharp/Others/Vertical or Horizontal Slider.cs b/c-sharp/Others/Vertical or Horizontal Slider.cs new file mode 100644 index 0000000..aa2a6e7 --- /dev/null +++ b/c-sharp/Others/Vertical or Horizontal Slider.cs @@ -0,0 +1,28 @@ +Vertical/Horizontal Slider + + + + + + + + + + + + + + + + + + + + + + + diff --git a/c-sharp/Others/VisualBrush and DrawingBrush.cs b/c-sharp/Others/VisualBrush and DrawingBrush.cs new file mode 100644 index 0000000..dd86636 --- /dev/null +++ b/c-sharp/Others/VisualBrush and DrawingBrush.cs @@ -0,0 +1,42 @@ +VisualBrush and DrawingBrush + + + + + + + + + + + + + + + + + + + + + + + + + Source Visual: + + + + + diff --git a/c-sharp/Others/WPF Threading.cs b/c-sharp/Others/WPF Threading.cs new file mode 100644 index 0000000..f280524 --- /dev/null +++ b/c-sharp/Others/WPF Threading.cs @@ -0,0 +1,45 @@ +WPF Threading + + + + + + + + + +//File:Window.xaml.cs + +using System.Windows; + +namespace WPFThreading +{ + public partial class BlockThread : System.Windows.Window + { + public BlockThread() + { + InitializeComponent(); + + this.UIThreadLabel.Content = this.Dispatcher.Thread.ManagedThreadId; + this.BackgroundThreadLabel.Content = "N/A"; + } + + private void button1_click(object sender, RoutedEventArgs e) + { + System.Threading.Thread.Sleep(5000); + this.textbox1.Text = "Done Sleeping..."; + } + + private void button2_click(object sender, RoutedEventArgs e) + { + this.textbox1.Text = "I Love Clementine"; + } + + } +} + diff --git a/c-sharp/Others/WeightedAdjacencyList.cs b/c-sharp/Others/WeightedAdjacencyList.cs new file mode 100644 index 0000000..933af33 --- /dev/null +++ b/c-sharp/Others/WeightedAdjacencyList.cs @@ -0,0 +1,136 @@ +using System; +using System.Collections.Generic; +using System.Diagnostics.Contracts; +using System.Linq; +using System.Text; + +namespace DataStructures.AdjacencyList +{ + [Serializable] + public class WeightedAdjacencyList + where T : class + { + private readonly Dictionary>> dict; + + public IList Vertices + { + get { return dict.Keys.ToList(); } + } + + public int Count + { + get { return dict.Count; } + } + + public WeightedAdjacencyList() + { + dict = new Dictionary>>(); + } + + public WeightedAdjacencyList(int capacity) + { + Contract.Requires(capacity > 0); + + dict = new Dictionary>>(capacity); + } + + public void AddVertex(T vertex) + { + Contract.Requires(vertex != null); + + if(dict.ContainsKey(vertex)) + { + return; + } + dict[vertex] = new HashSet>(); + } + + public Node[] AddEdge(T vertex1, T vertex2, double weight) + { + Contract.Requires(vertex1 != null); + Contract.Requires(vertex2 != null); + //need to return the nodes in order to allow the search for them later on + var weightedEdgeNodes = new Node[2]; + if(!dict.ContainsKey(vertex1)) + { + dict[vertex1] = new HashSet>(); + } + if(!dict.ContainsKey(vertex2)) + { + dict[vertex2] = new HashSet>(); + } + weightedEdgeNodes[0] = new Node(vertex2, weight); + weightedEdgeNodes[1] = new Node(vertex1, weight); + dict[vertex1].Add(weightedEdgeNodes[0]); + dict[vertex2].Add(weightedEdgeNodes[1]); + return weightedEdgeNodes; + } + + public bool IsNeighbourOf(T vertex, Node neighbour) + { + Contract.Requires(vertex != null); + Contract.Requires(neighbour != null); + + return dict.ContainsKey(vertex) && dict[vertex].Contains(neighbour); + } + + public IList GetAllWeights(T vertex) + { + Contract.Requires(vertex != null); + return dict.ContainsKey(vertex) ? + dict[vertex].Select(n =>n.weight).ToList() : + new List(); + } + + public IList> GetNeighbours(T vertex) + { + Contract.Requires(vertex != null); + + return dict.ContainsKey(vertex)? + dict[vertex].Select(n => new Tuple(n.item, n.weight)).ToList() : + new List>(); + } + + public class Node + where T : class + { + public T item; + public readonly double weight; + + public Node(T item, double weight) + { + this.item = item; + this.weight = weight; + } + + public bool Equals(T item) + { + return this.item.Equals(item); + } + + public bool Equals(Node node) + { + return this.item.Equals(node.item) && + (weight == node.weight); + } + + public override bool Equals(object obj) + { + if(obj is T) + { + return item.Equals(obj as T); + } + if(obj is Node) + { + return Equals(obj as Node); + } + return false; + } + + public override int GetHashCode() + { + return item.GetHashCode() ^ int.Parse(weight.ToString()); + } + } + } +} diff --git a/c-sharp/Others/Width and Height animation.cs b/c-sharp/Others/Width and Height animation.cs new file mode 100644 index 0000000..bb08ca7 --- /dev/null +++ b/c-sharp/Others/Width and Height animation.cs @@ -0,0 +1,57 @@ +Width and Height animation + + + + +//File:Window.xaml.cs +using System; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Data; +using System.Windows.Documents; +using System.Windows.Media; +using System.Windows.Shapes; +using System.Windows.Media.Animation; + +namespace _360Timer +{ + + public partial class Window1 : Window + { + public Window1() + { + InitializeComponent(); + + this.Show(); + + for (int i = 0; i < 24; ++i) + { + Ellipse e = new Ellipse(); + e.Stroke = new SolidColorBrush(Color.FromArgb(4 2, 240, 240)); + e.StrokeThickness = 20; + e.Width = 16.0; + e.Height = 32.0; + + this.MainCanvas.Children.Add(e); + + e.SetValue(Canvas.LeftProperty, 300); + e.SetValue(Canvas.TopProperty, 400); + + double duration = 6.0 ; + double delay = 1.0 ; + + DoubleAnimation sizeAnimation = new DoubleAnimation(0.0, 512.0, new Duration(TimeSpan.FromSeconds(duration))); + sizeAnimation.RepeatBehavior = RepeatBehavior.Forever; + sizeAnimation.BeginTime = TimeSpan.FromSeconds(delay); + e.BeginAnimation(Ellipse.WidthProperty, sizeAnimation); + e.BeginAnimation(Ellipse.HeightProperty, sizeAnimation); + + + } + } + } +} + diff --git a/c-sharp/Others/Window Closing and Closed event.cs b/c-sharp/Others/Window Closing and Closed event.cs new file mode 100644 index 0000000..a0c80ab --- /dev/null +++ b/c-sharp/Others/Window Closing and Closed event.cs @@ -0,0 +1,38 @@ +Window Closing and Closed event + + + + + + +//File:Window.xaml.cs +using System; +using System.ComponentModel; +using System.Windows; + +namespace ApplicationShutdownSample +{ + public partial class ChildWindow : Window + { + public ChildWindow() + { + InitializeComponent(); + } + + void ChildWindow_Closing(object sender, CancelEventArgs e) + { + Console.WriteLine("Closing"); + MessageBoxResult result = MessageBox.Show("Allow Shutdown?", "Application Shutdown Sample", MessageBoxButton.YesNo, MessageBoxImage.Question); + e.Cancel = (result == MessageBoxResult.No); + } + + void ChildWindow_Closed(object sender, EventArgs e) + { + Console.WriteLine("Closed"); + } + } +} + diff --git a/c-sharp/Others/Window On Mouse up event.cs b/c-sharp/Others/Window On Mouse up event.cs new file mode 100644 index 0000000..9db4858 --- /dev/null +++ b/c-sharp/Others/Window On Mouse up event.cs @@ -0,0 +1,63 @@ +Window On Mouse up event + + + + + + + + +//File:Window.xaml.cs +using System; +using System.Collections.Generic; +using System.Text; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Data; +using System.Windows.Documents; +using System.Windows.Input; +using System.Windows.Media; +using System.Windows.Media.Imaging; +using System.Windows.Shapes; +using System.Diagnostics; + + +namespace WpfApplication1 +{ + public partial class Window1 : System.Windows.Window + { + public Window1() + { + InitializeComponent(); + } + private void StartSlowWork() + { + Mouse.OverrideCursor = Cursors.AppStarting; + } + + private void SlowWorkCompleted() + { + Mouse.OverrideCursor = null; + } + + protected override void OnMouseDown(MouseButtonEventArgs e) + { + base.OnMouseDown(e); + if (e.Source != myEllipse) + { + StartSlowWork(); + } + } + + protected override void OnMouseUp(MouseButtonEventArgs e) + { + base.OnMouseUp(e); + SlowWorkCompleted(); + } + + } +} + diff --git a/c-sharp/Others/Window mouse up event.cs b/c-sharp/Others/Window mouse up event.cs new file mode 100644 index 0000000..48f52e6 --- /dev/null +++ b/c-sharp/Others/Window mouse up event.cs @@ -0,0 +1,64 @@ +Window mouse up event + + + + + + + + + + +//File:Window.xaml.cs +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +using System.Windows; +using System.Windows.Controls; +using System.Windows.Data; +using System.Windows.Documents; +using System.Windows.Input; +using System.Windows.Media; +using System.Windows.Media.Imaging; +using System.Windows.Navigation; +using System.Windows.Shapes; + +namespace WpfApplication1 +{ + public partial class Window1 : Window + { + private void Generic_MouseDown(object sender, MouseButtonEventArgs e) + { + Console.WriteLine(outputText.Text); + Console.WriteLine(e.RoutedEvent.Name); + Console.WriteLine(sender.ToString()); + Console.WriteLine(((FrameworkElement)e.Source).Name); + } + + private void Window_MouseUp(object sender, MouseButtonEventArgs e) + { + outputText.Text = outputText.Text; + } + + private void clickMeButton_Click(object sender, RoutedEventArgs e) + { + outputText.Text = "Button clicked:" + outputText.Text; + } + } +} + diff --git a/c-sharp/Others/WrapPanel and Windows Controls.cs b/c-sharp/Others/WrapPanel and Windows Controls.cs new file mode 100644 index 0000000..6e69be5 --- /dev/null +++ b/c-sharp/Others/WrapPanel and Windows Controls.cs @@ -0,0 +1,17 @@ +WrapPanel and Windows Controls + + + + + + + + + + + + + + diff --git a/c-sharp/Others/Write Jpeg file from BitmapSource.cs b/c-sharp/Others/Write Jpeg file from BitmapSource.cs new file mode 100644 index 0000000..b620c50 --- /dev/null +++ b/c-sharp/Others/Write Jpeg file from BitmapSource.cs @@ -0,0 +1,25 @@ +Write Jpeg file from BitmapSource + +using System; +using System.Collections.Generic; +using System.Text; +using System.Windows.Media.Imaging; +using System.IO; + + class UseBitmapCodecs + { + static void WriteJpeg(string fileName, int quality, BitmapSource bmp) + { + + JpegBitmapEncoder encoder = new JpegBitmapEncoder(); + BitmapFrame outputFrame = BitmapFrame.Create(bmp); + encoder.Frames.Add(outputFrame); + encoder.QualityLevel = quality; + + using (FileStream file = File.OpenWrite(fileName)) + { + encoder.Save(file); + } + } + } + diff --git a/c-sharp/Sorting/C# Program to Demonstrate Heap Sort.cs b/c-sharp/Sorting/C# Program to Demonstrate Heap Sort.cs new file mode 100644 index 0000000..01cca9a --- /dev/null +++ b/c-sharp/Sorting/C# Program to Demonstrate Heap Sort.cs @@ -0,0 +1,87 @@ +/* + * C# Program to Demonstrate Heap Sort + */ +using System; +class heap +{ + int[] r = { 2,5,1,10,6,9,3,7,4,8}; + public void hsort() + { + int i, t; + for (i = 5; i >= 0; i--) + { + adjust(i, 9); + } + for (i = 8; i >= 0; i--) + { + t = r[i + 1]; + r[i + 1] = r[0]; + r[0] = t; + adjust(0, i); + } + } + private void adjust(int i, int n) + { + int t, j; + try + { + t = r[i]; + j = 2 * i; + while (j <= n) + { + if (j < n && r[j] < r[j + 1]) + j++; + if (t >=r[j]) + break; + r[j / 2] = r[j]; + j *= 2; + } + r[j / 2] = t; + } + catch (IndexOutOfRangeException e) + { + Console.WriteLine("Array Out of Bounds ", e); + } + } + public void print() + { + for (int i = 0; i < 10; i++) + { + Console.WriteLine("{0}", r[i]); + } + } + public static void Main() + { + heap obj = new heap(); + Console.WriteLine("Elements Before sorting : "); + obj.print(); + obj.hsort(); + Console.WriteLine("Elements After sorting : "); + obj.print(); + Console.Read(); + } +} + +/* +Elements Before Sorting : +2 +5 +1 +10 +6 +9 +3 +7 +4 +8 +Elements After Sorting : +1 +2 +3 +4 +5 +6 +7 +8 +9 +10 \ No newline at end of file diff --git a/c-sharp/Sorting/C# Program to Implement Quick Sort.cs b/c-sharp/Sorting/C# Program to Implement Quick Sort.cs new file mode 100644 index 0000000..38414a1 --- /dev/null +++ b/c-sharp/Sorting/C# Program to Implement Quick Sort.cs @@ -0,0 +1,91 @@ +/* + * C# Program to Implement Quick Sort + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +namespace sortQuick +{ +class quickSort +{ + + private int[] array = new int[20]; + private int len; + + public void QuickSort() + { + sort(0, len - 1); + } + + public void sort(int left, int right) + { + int pivot, leftend, rightend; + leftend = left; + rightend = right; + pivot = array[left]; + while (left < right) + { + while ((array[right] >= pivot) && (left < right)) + { + right--; + } + if (left != right) + { + array[left] = array[right]; + left++; + } + while ((array[left] <= pivot) && (left < right)) + { + left++; + } + if (left != right) + { + array[right] = array[left]; + right--; + } + } + array[left] = pivot; + pivot = left; + left = leftend; + right = rightend; + if (left < pivot) + { + sort(left, pivot - 1); + } + if (right > pivot) + { + sort(pivot + 1, right); + } + } + + public static void Main() + { + quickSort q_Sort = new quickSort(); + int[] array = { 4, 3, 1, 4, 6, 7, 5, 4, 32, 5, 26, 187, 8 }; + q_Sort.array = array; + q_Sort.len = q_Sort.array.Length; + q_Sort.QuickSort(); + for (int j = 0; j < q_Sort.len; j++) + { + Console.WriteLine(q_Sort.array[j]); + } + Console.ReadKey(); + } +} +} +/* +1 +3 +4 +4 +4 +5 +5 +6 +7 +8 +26 +32 +187 \ No newline at end of file diff --git a/c-sharp/Sorting/C# Program to Perform Bubble Sort.cs b/c-sharp/Sorting/C# Program to Perform Bubble Sort.cs new file mode 100644 index 0000000..7d0dce8 --- /dev/null +++ b/c-sharp/Sorting/C# Program to Perform Bubble Sort.cs @@ -0,0 +1,47 @@ +/* + * C# Program to Perform Bubble Sort + */ +using System; +class bubblesort +{ + static void Main(string[] args) + { + int[] a = { 3, 2, 5, 4, 1 }; + int t; + Console.WriteLine("The Array is : "); + for (int i = 0; i < a.Length; i++) + { + Console.WriteLine(a[i]); + } + for (int j = 0; j <= a.Length - 2; j++) + { + for (int i = 0; i <= a.Length - 2; i++) + { + if (a[i] > a[i + 1]) + { + t = a[i + 1]; + a[i + 1] = a[i]; + a[i] = t; + } + } + } + Console.WriteLine("The Sorted Array :"); + foreach (int aray in a) + Console.Write(aray + " "); + Console.ReadLine(); + } +} + +/* +The Array is : +3 +2 +5 +4 +1 +The Sorted Array : +1 +2 +3 +4 +5 \ No newline at end of file diff --git a/c-sharp/Sorting/C# Program to Perform Insertion Sort.cs b/c-sharp/Sorting/C# Program to Perform Insertion Sort.cs new file mode 100644 index 0000000..63e3a7a --- /dev/null +++ b/c-sharp/Sorting/C# Program to Perform Insertion Sort.cs @@ -0,0 +1,62 @@ +/* + * C# Program to Perform Insertion Sort + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +using System.IO; +namespace ConsoleApplication1 +{ +class Program +{ + static void Main(string[] args) + { + int[] arr = new int[5] { 83, 12, 3, 34, 60 }; + int i; + Console.WriteLine("The Array is :"); + for (i = 0; i < 5; i++) + { + Console.WriteLine(arr[i]); + } + insertsort(arr, 5); + Console.WriteLine("The Sorted Array is :"); + for (i = 0; i < 5; i++) + Console.WriteLine(arr[i]); + Console.ReadLine(); + } + static void insertsort(int[] data, int n) + { + int i, j; + for (i = 1; i < n; i++) + { + int item = data[i]; + int ins = 0; + for (j = i - 1; j >= 0 && ins != 1; ) + { + if (item < data[j]) + { + data[j + 1] = data[j]; + j--; + data[j + 1] = item; + } + else ins = 1; + } + } + } +} +} + +/* +The Array is : +83 +12 +3 +34 +60 +The Sorted Array is : +3 +12 +34 +60 +83 \ No newline at end of file diff --git a/c-sharp/Sorting/C# Program to Perform Merge Sort.cs b/c-sharp/Sorting/C# Program to Perform Merge Sort.cs new file mode 100644 index 0000000..90cb54c --- /dev/null +++ b/c-sharp/Sorting/C# Program to Perform Merge Sort.cs @@ -0,0 +1,70 @@ +/* + * C# Program to Perform Merge Sort + */ +using System; +using System.Collections.Generic; +using System.Text; +namespace prog +{ +class Program +{ + static public void mergemethod(int [] numbers, int left, int mid, int right) + { + int [] temp = new int[25]; + int i, left_end, num_elements, tmp_pos; + left_end = (mid - 1); + tmp_pos = left; + num_elements = (right - left + 1); + while ((left <= left_end) && (mid <= right)) + { + if (numbers[left] <= numbers[mid]) + temp[tmp_pos++] = numbers[left++]; + else + temp[tmp_pos++] = numbers[mid++]; + } + while (left <= left_end) + temp[tmp_pos++] = numbers[left++]; + while (mid <= right) + temp[tmp_pos++] = numbers[mid++]; + for (i = 0; i < num_elements; i++) + { + numbers[right] = temp[right]; + right--; + } + } + static public void sortmethod(int [] numbers, int left, int right) + { + int mid; + if (right > left) + { + mid = (right + left) / 2; + sortmethod(numbers, left, mid); + sortmethod(numbers, (mid + 1), right); + mergemethod(numbers, left, (mid+1), right); + } + } + static void Main(string[] args) + + { + int[] numbers = { 3, 8, 7, 5, 2, 1, 9, 6, 4 }; + int len = 9; + Console.WriteLine("MergeSort :"); + sortmethod(numbers, 0, len - 1); + for (int i = 0; i < 9; i++) + Console.WriteLine(numbers[i]); + Console.Read(); + } +} +} + +/* +MergeSort : +1 +2 +3 +4 +5 +6 +7 +8 +9 \ No newline at end of file diff --git a/c-sharp/Sorting/C# Program to Perform Radix Sort.cs b/c-sharp/Sorting/C# Program to Perform Radix Sort.cs new file mode 100644 index 0000000..55cb5a0 --- /dev/null +++ b/c-sharp/Sorting/C# Program to Perform Radix Sort.cs @@ -0,0 +1,94 @@ +/* + * C# Program to Perform Radix Sort + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +namespace ConsoleApplication2 +{ +class Example +{ + private int[] data; + private IList> digits = new List>(); + private int maxLength = 0; + public Example() + { + for (int i = 0; i < 10; i++) + { + digits.Add(new List()); + } + Console.Write("Enter the Number of Records : "); + int count = int.Parse(Console.ReadLine()); + data = new int[count]; + Console.ReadLine(); + for (int i = 0; i < count; i++) + { + Console.Write("Enter Record {0} : ", i + 1); + data[i] = int.Parse(Console.ReadLine()); + if (maxLength < data[i].ToString().Length) + maxLength = data[i].ToString().Length; + } + } + + public void RadixSort() + { + for (int i = 0; i < maxLength; i++) + { + for (int j = 0; j < data.Length; j++) + { + int digit = (int)((data[j] % Math.Pow(10, i + 1)) / Math.Pow(10, i)); + digits[digit].Add(data[j]); + } + int index = 0; + for (int k = 0; k < digits.Count; k++) + { + IList selDigit = digits[k]; + for (int l = 0; l < selDigit.Count; l++) + { + data[index++] = selDigit[l]; + } + } + ClearDigits(); + } + printSortedData(); + } + + private void ClearDigits() + { + for (int k = 0; k < digits.Count; k++) + { + digits[k].Clear(); + } + } + + public void printSortedData() + { + Console.WriteLine("The Sorted Numbers are : "); + for (int i = 0; i < data.Length; i++) + { + Console.WriteLine(data[i]); + } + } + static void Main(string[] args) + { + new Example().RadixSort(); + Console.ReadLine(); + } +} +} + +/* +Enter the Number of Records : 5 +Enter Record 1 : 54 +Enter Record 2 : 53 +Enter Record 3 : 15 +Enter Record 4 : 27 +Enter Record 5 : 75 +The Sorted Numbers are : +15 +27 +53 +54 +75 \ No newline at end of file diff --git a/c-sharp/Sorting/C# Program to Perform a Selection Sort.cs b/c-sharp/Sorting/C# Program to Perform a Selection Sort.cs new file mode 100644 index 0000000..42d9e25 --- /dev/null +++ b/c-sharp/Sorting/C# Program to Perform a Selection Sort.cs @@ -0,0 +1,62 @@ +/* + * C# Program to Perform a Selection Sort + */ +using System; +class Program +{ + static void Main(string[] args) + { + int array_size = 10; + int[] array = new int[10] { 100, 50, 20, 40, 10, 60, 80, 70, 90, 30 }; + Console.WriteLine("The Array Before Selection Sort is: "); + for (int i = 0; i < array_size; i++) + { + Console.WriteLine(array[i]); + } + int tmp, min_key; + for (int j = 0; j < array_size - 1; j++) + { + min_key = j; + for (int k = j + 1; k < array_size; k++) + { + if (array[k] < array[min_key]) + { + min_key = k; + } + } + tmp = array[min_key]; + array[min_key] = array[j]; + array[j] = tmp; + } + Console.WriteLine("The Array After Selection Sort is: "); + for (int i = 0; i < 10; i++) + { + Console.WriteLine(array[i]); + } + Console.ReadLine(); + } +} + +/* +The Array Before Selection Sort is : +100 +50 +20 +40 +10 +60 +80 +70 +90 +30 +The Array After Selection Sort is : +10 +20 +30 +40 +50 +60 +70 +80 +90 +100 \ No newline at end of file diff --git a/c-sharp/Sorting/C# Sharp program to sort a list of elements using Bogosort sort.cs b/c-sharp/Sorting/C# Sharp program to sort a list of elements using Bogosort sort.cs new file mode 100644 index 0000000..44b853f --- /dev/null +++ b/c-sharp/Sorting/C# Sharp program to sort a list of elements using Bogosort sort.cs @@ -0,0 +1,80 @@ +using System; +using System.Collections.Generic; + +namespace Bogo_sort +{ +class Program +{ + static void Main(string[] args) + { + List list = new List() + { + 2, 1, 3, 0 + }; + Console.WriteLine("Sorting..."); + Bogo_sort(list, true, 5); + Console.WriteLine("Press any key to exit."); + Console.ReadKey(); + } + + static void Bogo_sort(List list, bool announce, int delay) + { + int iteration = 0; + while (!IsSorted(list)) + { + if (announce) + { + Print_Iteration(list, iteration); + } + if (delay != 0) + { + System.Threading.Thread.Sleep(Math.Abs(delay)); + } + list = Remap(list); + iteration++; + } + Print_Iteration(list, iteration); + Console.WriteLine(); + Console.WriteLine("Bogo_sort completed after {0} iterations.", iteration); + } + + static void Print_Iteration(List list, int iteration) + { + Console.Write("Bogo_sort iteration {0}: ", iteration); + for (int i = 0; i < list.Count; i++) + { + Console.Write(list[i]); + if (i < list.Count) + { + Console.Write(" "); + } + } + Console.WriteLine(); + } + static bool IsSorted(List list) + { + for (int i = 0; i < list.Count - 1; i++) + { + if (list[i] > list[i + 1]) + { + return false; + } + } + return true; + } + + static List Remap(List list) + { + int temp; + List newList = new List(); + Random r = new Random(); + while (list.Count > 0) + { + temp = (int)r.Next(list.Count); + newList.Add(list[temp]); + list.RemoveAt(temp); + } + return newList; + } +} +} \ No newline at end of file diff --git a/c-sharp/Sorting/C# Sharp program to sort a list of elements using Bubble sort.cs b/c-sharp/Sorting/C# Sharp program to sort a list of elements using Bubble sort.cs new file mode 100644 index 0000000..e754830 --- /dev/null +++ b/c-sharp/Sorting/C# Sharp program to sort a list of elements using Bubble sort.cs @@ -0,0 +1,28 @@ +using System; +public class Bubble_Sort +{ + public static void Main(string[] args) + { + int[] a = { 3, 0, 2, 5, -1, 4, 1 }; + int t; + Console.WriteLine("Original array :"); + foreach (int aa in a) + Console.Write(aa + " "); + for (int p = 0; p <= a.Length - 2; p++) + { + for (int i = 0; i <= a.Length - 2; i++) + { + if (a[i] > a[i + 1]) + { + t = a[i + 1]; + a[i + 1] = a[i]; + a[i] = t; + } + } + } + Console.WriteLine("\n"+"Sorted array :"); + foreach (int aa in a) + Console.Write(aa + " "); + Console.Write("\n"); + } +} \ No newline at end of file diff --git a/c-sharp/Sorting/C# Sharp program to sort a list of elements using Counting sort.cs b/c-sharp/Sorting/C# Sharp program to sort a list of elements using Counting sort.cs new file mode 100644 index 0000000..1e55b2d --- /dev/null +++ b/c-sharp/Sorting/C# Sharp program to sort a list of elements using Counting sort.cs @@ -0,0 +1,46 @@ +using System; +using System.Linq; +public class Counting_sort +{ + public static void Main() + { + int[] array = new int[10] + { + 2, 5, -4, 11, 0, 8, 22, 67, 51, 6 + }; + Console.WriteLine("\n"+"Original array :"); + foreach (int aa in array) + Console.Write(aa + " "); + int[] sortedArray = new int[array.Length]; + // find smallest and largest value + int minVal = array[0]; + int maxVal = array[0]; + for (int i = 1; i < array.Length; i++) + { + if (array[i] < minVal) minVal = array[i]; + else if (array[i] > maxVal) maxVal = array[i]; + } + // init array of frequencies + int[] counts = new int[maxVal - minVal + 1]; + // init the frequencies + for (int i = 0; i < array.Length; i++) + { + counts[array[i] - minVal]++; + } + // recalculate + counts[0]--; + for (int i = 1; i < counts.Length; i++) + { + counts[i] = counts[i] + counts[i - 1]; + } + // Sort the array + for (int i = array.Length - 1; i >= 0; i--) + { + sortedArray[counts[array[i] - minVal]--] = array[i]; + } + Console.WriteLine("\n"+"Sorted array :"); + foreach (int aa in sortedArray) + Console.Write(aa + " "); + Console.Write("\n"); + } +} \ No newline at end of file diff --git a/c-sharp/Sorting/C# Sharp program to sort a list of elements using Heap sort.cs b/c-sharp/Sorting/C# Sharp program to sort a list of elements using Heap sort.cs new file mode 100644 index 0000000..c0cb305 --- /dev/null +++ b/c-sharp/Sorting/C# Sharp program to sort a list of elements using Heap sort.cs @@ -0,0 +1,113 @@ +using System; + +namespace Heap_sort +{ +public class MainClass +{ + public static void Main (string[] args) + { + int[] mykeys = new int[] {2, 5, -4, 11, 0, 18, 22, 67, 51, 6}; + //double[] mykeys = new double[] {2.22, 0.5, 2.7, -1.0, 11.2}; + //string[] mykeys = new string[] {"Red", "White", "Black", "Green", "Orange"}; + Console.WriteLine("\nOriginal Array Elements :"); + printArray (mykeys); + heapSort (mykeys); + Console.WriteLine("\n\nSorted Array Elements :"); + printArray (mykeys); + Console.WriteLine("\n"); + } + +private static void heapSort (T[] array) where T : + IComparable + { + int heapSize = array.Length; + + buildMaxHeap (array); + + for (int i = heapSize-1; i >= 1; i--) + { + swap (array, i, 0); + heapSize--; + sink (array, heapSize, 0); + } + } + +private static void buildMaxHeap (T[] array) where T : + IComparable + { + int heapSize = array.Length; + + for (int i = (heapSize/2) - 1; i >= 0; i--) + { + sink (array, heapSize, i); + } + } + +private static void sink (T[] array, int heapSize, int toSinkPos) where T : + IComparable + { + if (getLeftKidPos (toSinkPos) >= heapSize) + { + // No left kid => no kid at all + return; + } + + + int largestKidPos; + bool leftIsLargest; + + if (getRightKidPos (toSinkPos) >= heapSize || array [getRightKidPos (toSinkPos)].CompareTo (array [getLeftKidPos (toSinkPos)]) < 0) + { + largestKidPos = getLeftKidPos (toSinkPos); + leftIsLargest = true; + } + else + { + largestKidPos = getRightKidPos (toSinkPos); + leftIsLargest = false; + } + + + + if (array [largestKidPos].CompareTo (array [toSinkPos]) > 0) + { + swap (array, toSinkPos, largestKidPos); + if (leftIsLargest) + { + sink (array, heapSize, getLeftKidPos (toSinkPos)); + } + else + { + sink (array, heapSize, getRightKidPos (toSinkPos)); + } + } + + } + + private static void swap (T[] array, int pos0, int pos1) + { + T tmpVal = array [pos0]; + array [pos0] = array [pos1]; + array [pos1] = tmpVal; + } + + private static int getLeftKidPos (int parentPos) + { + return (2 * (parentPos + 1)) - 1; + } + + private static int getRightKidPos (int parentPos) + { + return 2 * (parentPos + 1); + } + + private static void printArray (T[] array) + { + foreach (T t in array) + { + Console.Write(' '+t.ToString()+' '); + } + } +} + +} \ No newline at end of file diff --git a/c-sharp/Sorting/C# Sharp program to sort a list of elements using Insertion sort.cs b/c-sharp/Sorting/C# Sharp program to sort a list of elements using Insertion sort.cs new file mode 100644 index 0000000..9facbde --- /dev/null +++ b/c-sharp/Sorting/C# Sharp program to sort a list of elements using Insertion sort.cs @@ -0,0 +1,64 @@ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +namespace CommonInsertion_Sort +{ +class Program +{ + static void Main(string[] args) + { + int[] numbers = new int[10] {2, 5, -4, 11, 0, 18, 22, 67, 51, 6}; + Console.WriteLine("\nOriginal Array Elements :"); + PrintIntegerArray(numbers); + Console.WriteLine("\nSorted Array Elements :"); + PrintIntegerArray(InsertionSort(numbers)); + Console.WriteLine("\n"); + } + + static int[] InsertionSort(int[] inputArray) + { + for (int i = 0; i < inputArray.Length - 1; i++) + { + for (int j = i + 1; j > 0; j--) + { + if (inputArray[j - 1] > inputArray[j]) + { + int temp = inputArray[j - 1]; + inputArray[j - 1] = inputArray[j]; + inputArray[j] = temp; + } + } + } + return inputArray; + } + public static void PrintIntegerArray(int[] array) + { + foreach (int i in array) + { + Console.Write(i.ToString() + " "); + } + } + + + public static int[] InsertionSortByShift(int[] inputArray) + { + for (int i = 0; i < inputArray.Length - 1; i++) + { + int j; + var insertionValue = inputArray[i]; + for (j = i; j > 0; j--) + { + if (inputArray[j - 1] > insertionValue) + { + inputArray[j] = inputArray[j - 1]; + } + } + inputArray[j] = insertionValue; + } + return inputArray; + } + +} +} \ No newline at end of file diff --git a/c-sharp/Sorting/C# Sharp program to sort a list of elements using Merge sort.cs b/c-sharp/Sorting/C# Sharp program to sort a list of elements using Merge sort.cs new file mode 100644 index 0000000..00941f2 --- /dev/null +++ b/c-sharp/Sorting/C# Sharp program to sort a list of elements using Merge sort.cs @@ -0,0 +1,84 @@ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +namespace Merge_sort +{ +class Program +{ + static void Main(string[] args) + { + List unsorted = new List(); + List sorted; + Random random = new Random(); + Console.WriteLine("Original array elements:" ); + for(int i = 0; i< 10; i++) + { + unsorted.Add(random.Next(0,100)); + Console.Write(unsorted[i]+" "); + } + Console.WriteLine(); + sorted = MergeSort(unsorted); + Console.WriteLine("Sorted array elements: "); + foreach (int x in sorted) + { + Console.Write(x+" "); + } + Console.Write("\n"); + } + + + private static List MergeSort(List unsorted) + { + if (unsorted.Count <= 1) + return unsorted; + List left = new List(); + List right = new List(); + int middle = unsorted.Count / 2; + for (int i = 0; i < middle; i++) //Dividing the unsorted list + { + left.Add(unsorted[i]); + } + for (int i = middle; i < unsorted.Count; i++) + { + right.Add(unsorted[i]); + } + left = MergeSort(left); + right = MergeSort(right); + return Merge(left, right); + } + + private static List Merge(List left, List right) + { + List result = new List(); + while(left.Count > 0 || right.Count>0) + { + if (left.Count > 0 && right.Count > 0) + { + if (left.First() <= right.First()) //Comparing First two elements to see which is smaller + { + result.Add(left.First()); + left.Remove(left.First()); //Rest of the list minus the first element + } + else + { + result.Add(right.First()); + right.Remove(right.First()); + } + } + else if(left.Count>0) + { + result.Add(left.First()); + left.Remove(left.First()); + } + else if (right.Count > 0) + { + result.Add(right.First()); + right.Remove(right.First()); + } + } + return result; + } +} +} \ No newline at end of file diff --git a/c-sharp/Sorting/C# Sharp program to sort a list of elements using Permutation sort.cs b/c-sharp/Sorting/C# Sharp program to sort a list of elements using Permutation sort.cs new file mode 100644 index 0000000..ee496a9 --- /dev/null +++ b/c-sharp/Sorting/C# Sharp program to sort a list of elements using Permutation sort.cs @@ -0,0 +1,90 @@ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +namespace Permutation_Sort +{ +class Program +{ + static void Main(string[] args) + { + List listChar = new List(); + listChar.Add(new Caracter('A')); + listChar.Add(new Caracter('B')); + listChar.Add(new Caracter('C')); + Console.WriteLine("Combinations of A, B and C are"); + List permutation = Permutar(listChar, listChar.Count); + foreach (string p in permutation) + Console.WriteLine(p); + } + + public static List Permutar(List elem, int n) + { + List permutation = new List(); + Queue a1 = new Queue(); + List vacia = new List(); + a1.Enqueue(new Data(vacia, n)); + while (a1.Count > 0) + { + Data d = a1.Dequeue(); + if (d.n == 0) + { + string pActual = Concatenar(d.actual); + if (!permutation.Contains(pActual)) + { + permutation.Add(pActual); + } + } + else + { + for (int i = 0; i < elem.Count; i++) + { + if (!d.actual.Contains(elem[i])) + { + List lis = new List(); + for (int k = 0; k < d.actual.Count; k++) + { + lis.Add(d.actual[k]); + } + lis.Add(elem[i]); + Data d1 = new Data(lis, d.n - 1); + a1.Enqueue(d1); + } + } + } + } + return permutation; + } + + static string Concatenar(List listaCaracteres) + { + string cadena = ""; + for (int i = 0; i < listaCaracteres.Count; i++) + { + cadena += listaCaracteres[i].caracter; + } + return cadena; + } +} + +class Data +{ + public List actual; + public int n; + + public Data(List actual, int n) + { + this.actual = actual; + this.n = n; + } +} +class Caracter +{ + public char caracter; + public Caracter(char caracter) + { + this.caracter = caracter; + } +} +} \ No newline at end of file diff --git a/c-sharp/Sorting/C# Sharp program to sort a list of elements using Quick sort.cs b/c-sharp/Sorting/C# Sharp program to sort a list of elements using Quick sort.cs new file mode 100644 index 0000000..1919d9c --- /dev/null +++ b/c-sharp/Sorting/C# Sharp program to sort a list of elements using Quick sort.cs @@ -0,0 +1,71 @@ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +namespace Quick_Sort +{ +class Program +{ + private static void Quick_Sort(int[] arr, int left, int right) + { + if (left < right) + { + int pivot = Partition(arr, left, right); + if (pivot > 1) + { + Quick_Sort(arr, left, pivot - 1); + } + if (pivot + 1 < right) + { + Quick_Sort(arr, pivot + 1, right); + } + } + } + + private static int Partition(int[] arr, int left, int right) + { + int pivot = arr[left]; + while (true) + { + while (arr[left] < pivot) + { + left++; + } + while (arr[right] > pivot) + { + right--; + } + if (left < right) + { + if (arr[left] == arr[right]) return right; + int temp = arr[left]; + arr[left] = arr[right]; + arr[right] = temp; + } + else + { + return right; + } + } + } + static void Main(string[] args) + { + int[] arr = new int[] { 2, 5, -4, 11, 0, 18, 22, 67, 51, 6 }; + Console.WriteLine("Original array : "); + foreach (var item in arr) + { + Console.Write(" " + item); + } + Console.WriteLine(); + Quick_Sort(arr, 0, arr.Length-1); + Console.WriteLine(); + Console.WriteLine("Sorted array : "); + foreach (var item in arr) + { + Console.Write(" " + item); + } + Console.WriteLine(); + } +} +} \ No newline at end of file diff --git a/c-sharp/Sorting/C# Sharp program to sort a list of elements using Radix sort algorithm.cs b/c-sharp/Sorting/C# Sharp program to sort a list of elements using Radix sort algorithm.cs new file mode 100644 index 0000000..984e507 --- /dev/null +++ b/c-sharp/Sorting/C# Sharp program to sort a list of elements using Radix sort algorithm.cs @@ -0,0 +1,41 @@ +using System; +namespace Radix_Sort +{ +class Program +{ + static void Sort(int[] arr) + { + int i, j; + int[] tmp = new int[arr.Length]; + for (int shift = 31; shift > -1; --shift) + { + j = 0; + for (i = 0; i < arr.Length; ++i) + { + bool move = (arr[i] << shift) >= 0; + if (shift == 0 ? !move : move) + arr[i-j] = arr[i]; + else + tmp[j++] = arr[i]; + } + Array.Copy(tmp, 0, arr, arr.Length-j, j); + } + } + static void Main(string[] args) + { + int[] arr = new int[] { 2, 5, -4, 11, 0, 18, 22, 67, 51, 6 }; + Console.WriteLine("\nOriginal array : "); + foreach (var item in arr) + { + Console.Write(" " + item); + } + Sort(arr); + Console.WriteLine("\nSorted array : "); + foreach (var item in arr) + { + Console.Write(" " + item); + } + Console.WriteLine("\n"); + } +} +} \ No newline at end of file diff --git a/c-sharp/Sorting/C# Sharp program to sort a list of elements using Shell sort.cs b/c-sharp/Sorting/C# Sharp program to sort a list of elements using Shell sort.cs new file mode 100644 index 0000000..864e09f --- /dev/null +++ b/c-sharp/Sorting/C# Sharp program to sort a list of elements using Shell sort.cs @@ -0,0 +1,55 @@ +using System; +using System.Collections; + +namespace Shell_Sort +{ +public class SortShell +{ + static void Main(string[] args) + { + int[] arr = new int[] { 5, -4, 11, 0, 18, 22, 67, 51, 6 }; + int n; + n = arr.Length; + Console.WriteLine("Original Array Elements :"); + show_array_elements(arr); + shellSort(arr, n); + Console.WriteLine("\nSorted Array Elements :"); + show_array_elements(arr); + } + + static void shellSort(int[] arr, int array_size) + { + int i, j, inc, temp; + inc = 3; + while (inc > 0) + { + for (i = 0; i < array_size; i++) + { + j = i; + temp = arr[i]; + while ((j >= inc) && (arr[j - inc] > temp)) + { + arr[j] = arr[j - inc]; + j = j - inc; + } + arr[j] = temp; + } + if (inc / 2 != 0) + inc = inc / 2; + else if (inc == 1) + inc = 0; + else + inc = 1; + } + } + + static void show_array_elements(int[] arr) + { + foreach (var element in arr) + { + Console.Write(element + " "); + } + Console.Write("\n"); + } +} +} \ No newline at end of file diff --git a/c-sharp/Sorting/C# Sharp program to sort a list of elements using the selection sort algorithm.cs b/c-sharp/Sorting/C# Sharp program to sort a list of elements using the selection sort algorithm.cs new file mode 100644 index 0000000..01bdb29 --- /dev/null +++ b/c-sharp/Sorting/C# Sharp program to sort a list of elements using the selection sort algorithm.cs @@ -0,0 +1,67 @@ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +namespace Selection_Sort +{ +class Program +{ + static void Main(string[] args) + { + Selection_Sort selection = new Selection_Sort(10); + selection.Sort(); + } +} + +class Selection_Sort +{ + private int[] data; + private static Random generator = new Random(); + //Create an array of 10 random numbers + public Selection_Sort(int size) + { + data = new int[size]; + for (int i = 0; i < size; i++) + { + data[i] = generator.Next(20, 90); + } + } + + public void Sort() + { + Console.Write("\nSorted Array Elements :(Step by Step)\n\n"); + display_array_elements(); + int smallest; + for (int i = 0; i < data.Length - 1; i++) + { + smallest = i; + for (int index = i + 1; index < data.Length; index++) + { + if (data[index] < data[smallest]) + { + smallest = index; + } + } + Swap(i, smallest); + display_array_elements(); + } + } + + public void Swap(int first, int second) + { + int temporary = data[first]; + data[first] = data[second]; + data[second] = temporary; + } + + public void display_array_elements() + { + foreach (var element in data) + { + Console.Write(element + " "); + } + Console.Write("\n\n"); + } +} +} \ No newline at end of file diff --git a/c-sharp/Strings/AdjacencyList.cs b/c-sharp/Strings/AdjacencyList.cs new file mode 100644 index 0000000..d71c27f --- /dev/null +++ b/c-sharp/Strings/AdjacencyList.cs @@ -0,0 +1,107 @@ +using System; +using System.Collections.Generic; +using System.Diagnostics.Contracts; +using System.Linq; +using System.Text; + +//TODO: unweighted adjacency list and weighted adjacency list +namespace DataStructures.AdjacencyList +{ + [Serializable] + public class AdjacencyList + { + private readonly Dictionary> dict; + + public IList Vertices + { + get { return dict.Keys.ToList(); } + } + + public int Count + { + get { return dict.Count; } + } + + public AdjacencyList() + { + dict = new Dictionary>(); + } + + public AdjacencyList(int capacity) + { + Contract.Requires(capacity > 0); + + dict = new Dictionary>(capacity); + } + + public void AddVertex(T vertex) + { + Contract.Requires(vertex != null); + + if(dict.ContainsKey(vertex)) + { + return; + } + dict[vertex] = new HashSet(); + } + + public void AddEdge(T vertex1, T vertex2) + { + Contract.Requires(vertex1 != null); + Contract.Requires(vertex2 != null); + + if (!dict.ContainsKey(vertex1)) + { + dict[vertex1] = new HashSet(); + } + if (!dict.ContainsKey(vertex2)) + { + dict[vertex2] = new HashSet(); + } + dict[vertex1].Add(vertex2); + dict[vertex2].Add(vertex1); + } + + public bool IsNeighbourOf(T vertex, T neighbour) + { + Contract.Requires(vertex != null); + Contract.Requires(neighbour != null); + + return dict.ContainsKey(vertex) && dict[vertex].Contains(neighbour); + } + + public IList GetNeighbours(T vertex) + { + Contract.Requires(vertex != null); + + return dict.ContainsKey(vertex)? dict[vertex].ToList(): new List(); + } + + public IList this[T vertex] + { + get + { + return GetNeighbours(vertex); + } + set + { + Contract.Requires(vertex != null); + + dict[vertex] = new HashSet(value); + } + } + + public IList> GetEdgeList() + { + var list = new List>(); + + foreach (var entry in dict) + { + var key = entry.Key; + var hashSet = entry.Value; + list.AddRange(hashSet.Select(hashEntry => new Tuple(key, hashEntry))); + } + return list; + } + } +} diff --git a/c-sharp/Strings/C# Program to Concatenate Two Strings.cs b/c-sharp/Strings/C# Program to Concatenate Two Strings.cs new file mode 100644 index 0000000..8e5d0c7 --- /dev/null +++ b/c-sharp/Strings/C# Program to Concatenate Two Strings.cs @@ -0,0 +1,18 @@ +/* + * C# Program to Concatenate Two Strings + */ +using System; +class Program +{ + static void Main() + { + string s1 = "Good"; + string s2 ="Morning"; + string s3=string.Concat(s1, s2); + Console.WriteLine(s3); + Console.ReadLine(); + } +} + +/* +GoodMorning \ No newline at end of file diff --git a/c-sharp/Strings/C# Program to Convert Upper case to Lower Case.cs b/c-sharp/Strings/C# Program to Convert Upper case to Lower Case.cs new file mode 100644 index 0000000..172f81c --- /dev/null +++ b/c-sharp/Strings/C# Program to Convert Upper case to Lower Case.cs @@ -0,0 +1,18 @@ +/* + * C# Program to Convert Upper case to Lower Case + */ +using System; +public class Program +{ + public static void Main() + { + string str; + Console.WriteLine("Enter the String in Uppercase :"); + str = Console.ReadLine(); + Console.WriteLine("String in LowerCase : {0}", str.ToLower()); + Console.ReadLine(); + } +} +/* +Enter the String in Uppercase : ASDF +String in Lowercase :asdf \ No newline at end of file diff --git a/c-sharp/Strings/C# Program to Count Lines in a String.cs b/c-sharp/Strings/C# Program to Count Lines in a String.cs new file mode 100644 index 0000000..358aaf6 --- /dev/null +++ b/c-sharp/Strings/C# Program to Count Lines in a String.cs @@ -0,0 +1,28 @@ +/* + * C# Program to Count Lines in a String + */ +using System; +using System.Text.RegularExpressions; +class Program +{ + static void Main() + { + long a = countstring("This is \n Sanfoundry\n Website"); + Console.WriteLine("Number of Lines in the String : {0}",a); + Console.ReadLine(); + } + static long countstring(string s) + { + long count = 1; + int start = 0; + while ((start = s.IndexOf('\n', start)) != -1) + { + count++; + start++; + } + return count; + } +} + +/* +Number of Lines in the String : 3 \ No newline at end of file diff --git a/c-sharp/Strings/C# Program to Count number of Vowels and consonants from a given String.cs b/c-sharp/Strings/C# Program to Count number of Vowels and consonants from a given String.cs new file mode 100644 index 0000000..e103061 --- /dev/null +++ b/c-sharp/Strings/C# Program to Count number of Vowels and consonants from a given String.cs @@ -0,0 +1,48 @@ +/* + * C# Program to Count number of Vowels and consonants from a given String + */ +using System; +class program +{ + public static void Main() + { + char[] sentence = new char[100]; + int i, vowels = 0, consonants = 0, special = 0, n; + Console.WriteLine("Enter the Length of the sentence \n"); + n = int.Parse(Console.ReadLine()); + for (i = 0; i < n; i++) + { + sentence[i] = Convert.ToChar(Console.Read()); + } + for (i = 0; sentence[i] != '\0'; i++) + { + if ((sentence[i] == 'a' || sentence[i] == 'e' || sentence[i] == + 'i' || sentence[i] == 'o' || sentence[i] == 'u') || + (sentence[i] == 'A' || sentence[i] == 'E' || sentence[i] == + 'I' || sentence[i] == 'O' || sentence[i] == 'U')) + { + vowels = vowels + 1; + } + else + { + consonants = consonants + 1; + } + if (sentence[i] == 't' || sentence[i] == '\0' || sentence[i] == ' ') + { + special = special + 1; + } + } + consonants = consonants - special; + Console.WriteLine("No. of vowels {0}", vowels); + Console.WriteLine("No. of consonants {0}", consonants); + Console.ReadLine(); + Console.ReadLine(); + } +} + +/* +Enter the Length of the sentence +3 +san +No. of vowels 1 +No. of consonants 2 \ No newline at end of file diff --git a/c-sharp/Strings/C# Program to Display Date in String.cs b/c-sharp/Strings/C# Program to Display Date in String.cs new file mode 100644 index 0000000..c7e3b7a --- /dev/null +++ b/c-sharp/Strings/C# Program to Display Date in String.cs @@ -0,0 +1,23 @@ +/* + * C# Program to Display Date in String + */ +using System; +namespace DateAndTime +{ +class Program +{ + static int Main() + { + DateTime date = new DateTime(2013,6, 23); + string strDate = date.ToString("M"); + Console.WriteLine("Date and Time : {0}", date); + Console.WriteLine("Month and Date : {0}", strDate); + Console.Read(); + return 0; + } +} +} + +/* +Date and Time : 6/23/2013 12:00:00 AM +Month and Date : June 23 \ No newline at end of file diff --git a/c-sharp/Strings/C# Program to Display the Abbreviation of a Text.cs b/c-sharp/Strings/C# Program to Display the Abbreviation of a Text.cs new file mode 100644 index 0000000..8cf8d3e --- /dev/null +++ b/c-sharp/Strings/C# Program to Display the Abbreviation of a Text.cs @@ -0,0 +1,49 @@ +/* + * C# Program to Display the Abbreviation of a Text + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +class abbreviation +{ + string str; + public void readdata() + { + Console.WriteLine("Enter a String :"); + str=Console.In.ReadLine(); + } + public void abbre() + { + char[] c, result; + int j = 0; + c = new char[str.Length]; + result = new char[str.Length]; + c = str.ToCharArray(); + result[j++] = (char)((int)c[0] ^ 32); + result[j++] = '.'; + for (int i = 0; i < str.Length - 1; i++) + { + if (c[i] == ' ' || c[i] == '\t' || c[i] == '\n') + { + int k = (int)c[i + 1] ^ 32; + result[j++] = (char)k; + result[j++] = '.'; + } + } + Console.Write("The Abbreviation for {0} is ", str); + Console.WriteLine(result); + Console.ReadLine(); + } + public static void Main() + { + abbreviation obj=new abbreviation(); + obj.readdata(); + obj.abbre(); + } +} + +/* +Enter a String : +meenakshi sundarajan engineering college +The Abbreviation for meenakshi sundarajan engineering college is M.S.E.C. \ No newline at end of file diff --git a/c-sharp/Strings/C# Program to Encrypt Decrypt using Rijndael Key.cs b/c-sharp/Strings/C# Program to Encrypt Decrypt using Rijndael Key.cs new file mode 100644 index 0000000..ae57dae --- /dev/null +++ b/c-sharp/Strings/C# Program to Encrypt Decrypt using Rijndael Key.cs @@ -0,0 +1,91 @@ +/* + * C# Program to Encrypt/Decrypt using Rijndael Key + */ +using System; +using System.IO; +using System.Security.Cryptography; +namespace RijndaelManage +{ +class Rijndael +{ + public static void Main() + { + try + { + string original = "Data For Encryption!!!!!"; + using (RijndaelManaged myRijndael = new RijndaelManaged()) + { + myRijndael.GenerateKey(); + myRijndael.GenerateIV(); + byte[] encrypted = EncryptStringToBytes(original, myRijndael.Key, myRijndael.IV); + string aftdecryp = DecryptStringFromBytes(encrypted, myRijndael.Key, myRijndael.IV); + Console.WriteLine("Original: {0}", original); + Console.WriteLine("After Decryption: {0}", aftdecryp); + } + } + catch (Exception e) + { + Console.WriteLine("Error: {0}", e.Message); + } + } + static byte[] EncryptStringToBytes(string plainText, byte[] Key, byte[] IV) + { + if (plainText == null || plainText.Length <= 0) + throw new ArgumentNullException("plainText"); + if (Key == null || Key.Length <= 0) + throw new ArgumentNullException("Key"); + if (IV == null || IV.Length <= 0) + throw new ArgumentNullException("Key"); + byte[] encrypted; + using (RijndaelManaged rijAlg = new RijndaelManaged()) + { + rijAlg.Key = Key; + rijAlg.IV = IV; + ICryptoTransform encryptor = rijAlg.CreateEncryptor(rijAlg.Key, rijAlg.IV); + using (MemoryStream msEncrypt = new MemoryStream()) + { + using (CryptoStream csEncrypt = new CryptoStream(msEncrypt, encryptor, CryptoStreamMode.Write)) + { + using (StreamWriter swEncrypt = new StreamWriter(csEncrypt)) + { + swEncrypt.Write(plainText); + } + encrypted = msEncrypt.ToArray(); + } + } + } + return encrypted; + } + static string DecryptStringFromBytes(byte[] cipherText, byte[] Key, byte[] IV) + { + if (cipherText == null || cipherText.Length <= 0) + throw new ArgumentNullException("cipherText"); + if (Key == null || Key.Length <= 0) + throw new ArgumentNullException("Key"); + if (IV == null || IV.Length <= 0) + throw new ArgumentNullException("Key"); + string plaintext = null; + using (RijndaelManaged rijAlg = new RijndaelManaged()) + { + rijAlg.Key = Key; + rijAlg.IV = IV; + ICryptoTransform decryptor = rijAlg.CreateDecryptor(rijAlg.Key, rijAlg.IV); + using (MemoryStream msDecrypt = new MemoryStream(cipherText)) + { + using (CryptoStream csDecrypt = new CryptoStream(msDecrypt, decryptor, CryptoStreamMode.Read)) + { + using (StreamReader srDecrypt = new StreamReader(csDecrypt)) + { + plaintext = srDecrypt.ReadToEnd(); + } + } + } + } + return plaintext; + } +} +} + +/* +Original : Data for Encryption!!!!! +After Decryption : Data for Encryption!!!!! \ No newline at end of file diff --git a/c-sharp/Strings/C# Program to Generate the Marksheet of the Student.cs b/c-sharp/Strings/C# Program to Generate the Marksheet of the Student.cs new file mode 100644 index 0000000..a615b47 --- /dev/null +++ b/c-sharp/Strings/C# Program to Generate the Marksheet of the Student.cs @@ -0,0 +1,66 @@ +/* + * C# Program to Generate the Marksheet of the Student + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +namespace Marksheet1 +{ +class Program +{ + static void Main(string[] args) + { + int r, m1, m2, m3, t; + float p; + string n; + Console.WriteLine("Enter Roll Number :"); + r = Convert.ToInt32(Console.ReadLine()); + Console.WriteLine("Enter Student Name :"); + n = Console.ReadLine(); + Console.WriteLine("Mark of Subject1 : "); + m1 = Convert.ToInt32(Console.ReadLine()); + Console.WriteLine("Mark of Subject2 : "); + m2 = Convert.ToInt32(Console.ReadLine()); + Console.WriteLine("Mark of Subject3 : "); + m3 = Convert.ToInt32(Console.ReadLine()); + t = m1 + m2 + m3; + p = t / 3.0f; + Console.WriteLine("Total : " + t); + Console.WriteLine("Percentage : " + p); + if (p >= 35 && p < 50) + { + Console.WriteLine("Grade is C"); + } + if (p >= 50 && p <= 60) + { + Console.WriteLine("Grade is B"); + } + if (p > 60 && p <= 80) + { + Console.WriteLine("Grade is A"); + } + if (p > 80 && p <= 100) + { + Console.WriteLine("Grade is A+"); + } + Console.ReadLine(); + } +} +} + +/* +Enter RollNumber : +48 +Enter Student Name : +sri +Mark of Subject1 : +90 +Mark of Subject2 : +80 +Mark of Subject3 : +70 +Total : 240 +Percentage : 80 +Grade is A \ No newline at end of file diff --git a/c-sharp/Strings/C# Program to Illustrate Binary Writer.cs b/c-sharp/Strings/C# Program to Illustrate Binary Writer.cs new file mode 100644 index 0000000..d6f9609 --- /dev/null +++ b/c-sharp/Strings/C# Program to Illustrate Binary Writer.cs @@ -0,0 +1,25 @@ +/* + * C# Program to Illustrate Binary Writer + */ +using System; +using System.IO; +class ConsoleApplication +{ + const string fileName = "program.dat"; + static void Main() + { + Write(); + Console.WriteLine("Using Binary Writer Class the Contents are Written "); + } + public static void Write() + { + using (BinaryWriter writer = new BinaryWriter(File.Open(fileName, FileMode.Create))) + { + writer.Write(1.250F); + writer.Write(@"c:\Temp"); + } + } +} + +/* +Using Binary Writer Class the Contents are Written \ No newline at end of file diff --git a/c-sharp/Strings/C# Program to Implement String Splitter.cs b/c-sharp/Strings/C# Program to Implement String Splitter.cs new file mode 100644 index 0000000..a65fa42 --- /dev/null +++ b/c-sharp/Strings/C# Program to Implement String Splitter.cs @@ -0,0 +1,28 @@ +/* + * C# Program to Implement String Splitter + */ +using System; +using System.Text.RegularExpressions; +class Program +{ + static void Main() + { + string sentence = "School had 40 Rooms, 500 Boys, 500 Girls and 250 Teachers"; + string[] digits = Regex.Split(sentence, @"\D+"); + foreach (string value in digits) + { + int number; + if (int.TryParse(value, out number)) + { + Console.Write(value); + } + Console.ReadLine(); + } + } +} + +/* +40 +500 +500 +250 \ No newline at end of file diff --git a/c-sharp/Strings/C# Program to List all Substrings in a given String.cs b/c-sharp/Strings/C# Program to List all Substrings in a given String.cs new file mode 100644 index 0000000..1f3c597 --- /dev/null +++ b/c-sharp/Strings/C# Program to List all Substrings in a given String.cs @@ -0,0 +1,48 @@ +/* + * C# Program to List all Substrings in a given String + */ +using System; +namespace mismatch +{ +class Program +{ + string value, substring; + int j, i; + string[] a = new string[5]; + void input() + { + Console.WriteLine("Enter the String : "); + value = Console.ReadLine(); + Console.WriteLine("All Possible Substrings of the Given String are :"); + for (i = 1; i <=value.Length; i++) + { + for (j = 0; j <= value.Length - i; j++) + { + substring = value.Substring(j, i); + a[j] = substring; + Console.WriteLine(a[j]); + } + } + } + public static void Main() + { + Program pg = new Program(); + pg.input(); + Console.ReadLine(); + } +} +} + +/* +Enter the String : abab +All Possible Substrings of the Given String are : +a +b +a +b +ab +ba +ab +aba +bab +abab \ No newline at end of file diff --git a/c-sharp/Strings/C# Program to Perform Padding in the String.cs b/c-sharp/Strings/C# Program to Perform Padding in the String.cs new file mode 100644 index 0000000..c51e098 --- /dev/null +++ b/c-sharp/Strings/C# Program to Perform Padding in the String.cs @@ -0,0 +1,28 @@ +/* + * C# Program to Perform Padding in the String + */ +using System; +namespace padd +{ +class Program +{ + static void Main(string[] args) + { + string myString = "CSHARP"; + string newString; + System.Console.WriteLine("String Before Padding : "); + System.Console.WriteLine(myString); + System.Console.WriteLine("String After Padding : "); + newString = myString.PadLeft(10, ' '); + newString = newString.PadRight(20, '*'); + System.Console.Write("[" + newString + "]"); + Console.Read(); + } +} +} + +/* +String Before Padding : +CSHARP +String After Padding : +[ CSHARP**********] \ No newline at end of file diff --git a/c-sharp/Strings/C# Program to Perform Searching using Predefined Functions.cs b/c-sharp/Strings/C# Program to Perform Searching using Predefined Functions.cs new file mode 100644 index 0000000..fd1d36c --- /dev/null +++ b/c-sharp/Strings/C# Program to Perform Searching using Predefined Functions.cs @@ -0,0 +1,51 @@ +/* + * C# Program to Perform Searching using Predefined Functions + */ +using System; +class linSearch +{ + public static void Main() + { + Console.WriteLine("Enter Number of Elements you Want to Hold in the Array ? "); + string s = Console.ReadLine(); + int x = Int32.Parse(s); + int[] a = new int[x]; + Console.WriteLine("Enter Array Elements :"); + for (int i = 0; i < x; i++) + { + string s1 = Console.ReadLine(); + a[i] = Int32.Parse(s1); + } + Array.Sort(a); + Console.WriteLine("Sorted Array : "); + for (int i = 0; i < x; i++) + { + Console.WriteLine("{0}", a[i]); + } + Console.WriteLine("Enter the Element to be Searched : "); + string s3 = Console.ReadLine(); + int x2 = Int32.Parse(s3); + int x3 = Array.BinarySearch(a, (Object)x2); + Console.WriteLine("BinarySearch: " + x3); + Console.WriteLine("Element {0} is {1}", x3, a[x3]); + Console.Read(); + } +} + +/* +Enter Number of Elements you Want to Hold in the Array ? 5 +Enter Array Elements : +2 +3 +1 +4 +5 +Sorted Array : +1 +2 +3 +4 +5 +Enter the Element to be Searched : 4 +Binary Search : 3 +Element 3 is 4 \ No newline at end of file diff --git a/c-sharp/Strings/C# Program to Randomly Generate Strings.cs b/c-sharp/Strings/C# Program to Randomly Generate Strings.cs new file mode 100644 index 0000000..738812b --- /dev/null +++ b/c-sharp/Strings/C# Program to Randomly Generate Strings.cs @@ -0,0 +1,28 @@ +/* + * C# Program to Randomly Generate Strings + */ +using System; +using System.IO; +static class Random +{ + public static string GetRandomString() + { + string path = Path.GetRandomFileName(); + path = path.Replace(".", ""); + return path; + } +} +class Program +{ + static void Main() + { + Console.WriteLine(Random.GetRandomString()); + Console.WriteLine(Random.GetRandomString()); + Console.WriteLine(Random.GetRandomString()); + Console.Read(); + } +} +/* +g4jgtjvbs7hbf +jtwoj782hggjsi +3jbws63k \ No newline at end of file diff --git a/c-sharp/Strings/C# Program to Read a String and find the Sum of all Digits in the String.cs b/c-sharp/Strings/C# Program to Read a String and find the Sum of all Digits in the String.cs new file mode 100644 index 0000000..064a16d --- /dev/null +++ b/c-sharp/Strings/C# Program to Read a String and find the Sum of all Digits in the String.cs @@ -0,0 +1,39 @@ +/* + * C# Program to Read a String and find the Sum of all Digits in the String + */ +using System; +class program +{ + public static void Main() + { + char[] string1 = new char[20]; + int count, nc = 0, sum = 0, n, i; + Console.WriteLine("Enter the Length of the sentence :"); + n = int.Parse(Console.ReadLine()); + Console.WriteLine("Enter the string1 containing both digits and alphabet :"); + for (i = 0; i < n; i++) + { + string1[i] = Convert.ToChar(Console.Read()); + } + for (count = 0; string1[count] != '\0'; count++) + { + if ((string1[count] >= '0') && (string1[count] <= '9')) + { + nc += 1; + sum += (string1[count] - '0'); + } + } + Console.WriteLine("NO. of Digits in the string1 = {0}", nc); + Console.WriteLine("Sum of all digits = {0}", sum); + Console.ReadLine(); + Console.ReadLine(); + } +} + +/* +Enter the Length of the sentence : +6 +Enter the string1 containing both digits and alphabet : +SAN193 +NO. of Digits in the string1 = 3 +Sum of all digits = 13 \ No newline at end of file diff --git a/c-sharp/Strings/C# Program to Replace String in String.cs b/c-sharp/Strings/C# Program to Replace String in String.cs new file mode 100644 index 0000000..58749cf --- /dev/null +++ b/c-sharp/Strings/C# Program to Replace String in String.cs @@ -0,0 +1,19 @@ +/* + * C# Program to Replace String in String + */ +using System; +class Program +{ + static void Main() + { + const string s = "Sun Rises in the West"; + Console.WriteLine("Sentence Before Replacing : {0} ",s); + string s1 = s.Replace("West", "East"); + Console.WriteLine("Sentence After Replacing : {0} ",s1); + Console.ReadLine(); + } +} + +/* +Sentence Before Replacing : Sun Rises in the West +Sentence After Replacing : Sun Rises in the East \ No newline at end of file diff --git a/c-sharp/Strings/C# Program to Replace a Character with the String.cs b/c-sharp/Strings/C# Program to Replace a Character with the String.cs new file mode 100644 index 0000000..9b02bb4 --- /dev/null +++ b/c-sharp/Strings/C# Program to Replace a Character with the String.cs @@ -0,0 +1,17 @@ +/* + * C# Program to Replace a Character with the String + */ +using System; +class Program +{ + static void Main(string[] args) + { + string s = "".PadLeft(5, 'X').Replace("X", "Sanfoundry");; + Console.Write("The String After the Replacement :{0}",s); + Console.Read(); + } + +} + +/* +The String After the Replacement :SanfoundrySanfoundrySanfoundrySanfoundrySanfoundry \ No newline at end of file diff --git a/c-sharp/Strings/C# Program to Reverse a String without using Reverse function.cs b/c-sharp/Strings/C# Program to Reverse a String without using Reverse function.cs new file mode 100644 index 0000000..489bc77 --- /dev/null +++ b/c-sharp/Strings/C# Program to Reverse a String without using Reverse function.cs @@ -0,0 +1,26 @@ +/* + * C# Program to Reverse a String without using Reverse function + */ +using System; +class Program +{ + static void Main(string[] args) + { + string Str, reversestring = ""; + int Length; + Console.Write("Enter A String : "); + Str = Console.ReadLine(); + Length = Str.Length - 1; + while (Length >= 0) + { + reversestring = reversestring + Str[Length]; + Length--; + } + Console.WriteLine("Reverse String Is {0}", reversestring); + Console.ReadLine(); + } +} + +/* +Enter a String : sanfoundry +Reverse String is : yrdnuofnas \ No newline at end of file diff --git a/c-sharp/Strings/C# Program to Split a String Collections into Groups.cs b/c-sharp/Strings/C# Program to Split a String Collections into Groups.cs new file mode 100644 index 0000000..b4b810b --- /dev/null +++ b/c-sharp/Strings/C# Program to Split a String Collections into Groups.cs @@ -0,0 +1,33 @@ +/* + * C# Program to Split a String Collections into Groups + */ +using System; +using System.IO; +using System.Collections; +using System.Linq; +class program +{ + static void SendEmail(string email) + { + Console.WriteLine(email); + } + static void Main(string[] args) + { + string[] email = {"One@aaa.com", "Two@aaa.com", + "Three@aaa.com", "Four@aaa.com", + "Five@aaa.com", "Six@aaa.com", + "Seven@aaa.com", "Eight@aaa.com" + }; + var Grp = from i in Enumerable.Range(0, email.Length) + group email[i] by i / 3; + foreach (var mail in Grp) + SendEmail(string.Join(";", mail.ToArray())); + Console.ReadLine(); + } +} + +/* +One@aaa.com;Two@aaa.com; +Three@aaa.com;Four@aaa.com; +Five@aaa.com;Six@aaa.com; +Seven@aaa.com;Eight@aaa.com \ No newline at end of file diff --git a/c-sharp/Strings/C# Program to Trim the Given String.cs b/c-sharp/Strings/C# Program to Trim the Given String.cs new file mode 100644 index 0000000..22add63 --- /dev/null +++ b/c-sharp/Strings/C# Program to Trim the Given String.cs @@ -0,0 +1,21 @@ +/* + * C# Program to Trim the Given String + */ +using System; +namespace trim +{ +class Program +{ + static void Main(string[] args) + { + string myString = " CSHARP "; + System.Console.WriteLine("The String Before Trimming : (" + myString + ")"); + System.Console.WriteLine("The String After Trimming : (" + myString.Trim() + ")"); + Console.Read(); + } +} +} + +/* +The String Before Trimming : ( CSHARP ) +The String After Trimming : (CSHARP) \ No newline at end of file diff --git a/c-sharp/Strings/C# Program to calculate the length of the string.cs b/c-sharp/Strings/C# Program to calculate the length of the string.cs new file mode 100644 index 0000000..a0fd775 --- /dev/null +++ b/c-sharp/Strings/C# Program to calculate the length of the string.cs @@ -0,0 +1,19 @@ +/* + * C# Program to calculate the length of the string + */ +using System; +class Program +{ + static void Main() + { + string s1 = "Computer"; + Console.WriteLine("The Length of the First String is : " +s1.Length); + string s2 = ""; + Console.WriteLine("The Length of the Second String is : " +s2.Length); + Console.ReadLine(); + } +} + +/* +The Length of the First String is : 8 +The Length of the Second String is : 0 \ No newline at end of file diff --git a/c-sharp/Strings/C# Sharp program to check whether a given substring is present in the given string.cs b/c-sharp/Strings/C# Sharp program to check whether a given substring is present in the given string.cs new file mode 100644 index 0000000..8d18dd9 --- /dev/null +++ b/c-sharp/Strings/C# Sharp program to check whether a given substring is present in the given string.cs @@ -0,0 +1,20 @@ +using System; +public class exercise13 +{ + public static void Main() + { + string str1,str2; + bool m; + Console.Write("\n\nCheck whether a given substring is present in the given strig :\n"); + Console.Write("-------------------------------------------------------------------\n"); + Console.Write("Input the string : "); + str1 = Console.ReadLine(); + Console.Write("Input the substring to search : "); + str2 = Console.ReadLine(); + m=str1.Contains(str2); // boolean value tapped hare + if (m) // check boolean value is true or false. + Console.Write("The substring exists in the string.\n\n"); + else + Console.Write("The substring is not exists in the string. \n\n"); + } +} \ No newline at end of file diff --git a/c-sharp/Strings/C# Sharp program to compare (less than, greater than, equal to ) two substrings.cs b/c-sharp/Strings/C# Sharp program to compare (less than, greater than, equal to ) two substrings.cs new file mode 100644 index 0000000..78cfd41 --- /dev/null +++ b/c-sharp/Strings/C# Sharp program to compare (less than, greater than, equal to ) two substrings.cs @@ -0,0 +1,21 @@ +// Example for String.Compare(String, Int32, String, Int32, Int32) +using System; + +class Example21 +{ + public static void Main() + { +// 01234567 + String str1 = "computer"; + String str2 = "system"; + String str; + int result; + Console.WriteLine(); + Console.WriteLine("str1 = '{0}', str2 = '{1}'", str1, str2); + result = String.Compare(str1, 2, str2, 0, 2); + str = ((result < 0) ? "less than" : ((result > 0) ? "greater than" : "equal to")); + Console.Write("Substring '{0}' in '{1}' is ", str1.Substring(2, 2), str1); + Console.Write("{0} ", str); + Console.WriteLine("substring '{0}' in '{1}'.", str2.Substring(0, 2), str2); + } +} \ No newline at end of file diff --git a/c-sharp/Strings/C# Sharp program to compare the last names of two people.cs b/c-sharp/Strings/C# Sharp program to compare the last names of two people.cs new file mode 100644 index 0000000..1307985 --- /dev/null +++ b/c-sharp/Strings/C# Sharp program to compare the last names of two people.cs @@ -0,0 +1,23 @@ +using System; +using System.Globalization; + +public class Example24 +{ + public static void Main() + { + string name1 = "John Peterson"; + string name2 = "Michel Jhonson"; + // Get position of space character. + int index1 = name1.IndexOf(" "); + index1 = index1 < 0 ? 0 : index1--; + int index2 = name2.IndexOf(" "); + index1 = index1 < 0 ? 0 : index1--; + int length = Math.Max(name1.Length, name2.Length); + Console.WriteLine("Sorted alphabetically by last name:"); + if (String.Compare(name1, index1, name2, index2, length, + new CultureInfo("en-US"), CompareOptions.IgnoreCase) < 0) + Console.WriteLine("{0}\n{1}", name1, name2); + else + Console.WriteLine("{0}\n{1}", name2, name1); + } +} \ No newline at end of file diff --git a/c-sharp/Strings/C# Sharp program to compare three versions of the letter I.cs b/c-sharp/Strings/C# Sharp program to compare three versions of the letter I.cs new file mode 100644 index 0000000..c6d421c --- /dev/null +++ b/c-sharp/Strings/C# Sharp program to compare three versions of the letter I.cs @@ -0,0 +1,74 @@ +// This example demonstrates the +// System.String.Compare(String, String, StringComparison) method. + +using System; +using System.Threading; + +class Example29 +{ + public static void Main() + { + string intro = "Compare three versions of the letter I using different " + + "values of StringComparison."; +// Define an array of strings where each element contains a version of the +// letter I. (An array of strings is used so you can easily modify this +// code example to test additional or different combinations of strings.) + string[] threeIs = new string[3]; +// LATIN SMALL LETTER I (U+0069) + threeIs[0] = "\u0069"; +// LATIN SMALL LETTER DOTLESS I (U+0131) + threeIs[1] = "\u0131"; +// LATIN CAPITAL LETTER I (U+0049) + threeIs[2] = "\u0049"; + string[] unicodeNames = + { + "LATIN SMALL LETTER I (U+0069)", + "LATIN SMALL LETTER DOTLESS I (U+0131)", + "LATIN CAPITAL LETTER I (U+0049)" + }; + StringComparison[] scValues = + { + StringComparison.CurrentCulture, + StringComparison.CurrentCultureIgnoreCase, + StringComparison.InvariantCulture, + StringComparison.InvariantCultureIgnoreCase, + StringComparison.Ordinal, + StringComparison.OrdinalIgnoreCase + }; +// + Console.Clear(); + Console.WriteLine(intro); +// Display the current culture because the culture-specific comparisons +// can produce different results with different cultures. + Console.WriteLine("The current culture is {0}.\n", + Thread.CurrentThread.CurrentCulture.Name); +// Determine the relative sort order of three versions of the letter I. + foreach (StringComparison sc in scValues) + { + Console.WriteLine("StringComparison.{0}:", sc); +// LATIN SMALL LETTER I (U+0069) : LATIN SMALL LETTER DOTLESS I (U+0131) + Test(0, 1, sc, threeIs, unicodeNames); +// LATIN SMALL LETTER I (U+0069) : LATIN CAPITAL LETTER I (U+0049) + Test(0, 2, sc, threeIs, unicodeNames); +// LATIN SMALL LETTER DOTLESS I (U+0131) : LATIN CAPITAL LETTER I (U+0049) + Test(1, 2, sc, threeIs, unicodeNames); + Console.WriteLine(); + } + } + + protected static void Test(int x, int y, + StringComparison comparison, + string[] testI, string[] testNames) + { + string resultFmt = "{0} is {1} {2}"; + string result = "equal to"; + int cmpValue = 0; +// + cmpValue = String.Compare(testI[x], testI[y], comparison); + if (cmpValue < 0) + result = "less than"; + else if (cmpValue > 0) + result = "greater than"; + Console.WriteLine(resultFmt, testNames[x], result, testNames[y]); + } +} \ No newline at end of file diff --git a/c-sharp/Strings/C# Sharp program to compare two strings in following three different ways produce three different results.cs b/c-sharp/Strings/C# Sharp program to compare two strings in following three different ways produce three different results.cs new file mode 100644 index 0000000..2437755 --- /dev/null +++ b/c-sharp/Strings/C# Sharp program to compare two strings in following three different ways produce three different results.cs @@ -0,0 +1,45 @@ +using System; +using System.Globalization; + +public class Example28 +{ + public static void Main() + { + string str1 = "sister"; + string str2 = "Sister"; + string relation; + int result; + // Cultural (linguistic) comparison. + result = String.Compare(str1, str2, new CultureInfo("en-US"), + CompareOptions.None); + if (result > 0) + relation = "comes after"; + else if (result == 0) + relation = "is the same as"; + else + relation = "comes before"; + Console.WriteLine("'{0}' {1} '{2}'.", + str1, relation, str2); + // Cultural (linguistic) case-insensitive comparison. + result = String.Compare(str1, str2, new CultureInfo("en-US"), + CompareOptions.IgnoreCase); + if (result > 0) + relation = "comes after"; + else if (result == 0) + relation = "is the same as"; + else + relation = "comes before"; + Console.WriteLine("'{0}' {1} '{2}'.", + str1, relation, str2); + // Culture-insensitive ordinal comparison. + result = String.CompareOrdinal(str1, str2); + if (result > 0) + relation = "comes after"; + else if (result == 0) + relation = "is the same as"; + else + relation = "comes before"; + Console.WriteLine("'{0}' {1} '{2}'.", + str1, relation, str2); + } +} \ No newline at end of file diff --git a/c-sharp/Strings/C# Sharp program to compare two substrings that only differ in case.cs b/c-sharp/Strings/C# Sharp program to compare two substrings that only differ in case.cs new file mode 100644 index 0000000..442ad20 --- /dev/null +++ b/c-sharp/Strings/C# Sharp program to compare two substrings that only differ in case.cs @@ -0,0 +1,27 @@ +using System; +class Example22 +{ + public static void Main() + { +// 01234567 + String str1 = "COMPUTER"; + String str2 = "computer"; + String str; + int result; + Console.WriteLine(); + Console.WriteLine("str1 = '{0}', str2 = '{1}'", str1, str2); + Console.WriteLine("Ignore case:"); + result = String.Compare(str1, 2, str2, 2, 2, true); + str = ((result < 0) ? "less than" : ((result > 0) ? "greater than" : "equal to")); + Console.Write("Substring '{0}' in '{1}' is ", str1.Substring(2, 2), str1); + Console.Write("{0} ", str); + Console.WriteLine("substring '{0}' in '{1}'.", str2.Substring(2, 2), str2); + Console.WriteLine(); + Console.WriteLine("Honor case:"); + result = String.Compare(str1, 2, str2, 2, 2, false); + str = ((result < 0) ? "less than" : ((result > 0) ? "greater than" : "equal to")); + Console.Write("Substring '{0}' in '{1}' is ", str1.Substring(2, 2), str1); + Console.Write("{0} ", str); + Console.WriteLine("substring '{0}' in '{1}'.", str2.Substring(2, 2), str2); + } +} \ No newline at end of file diff --git a/c-sharp/Strings/C# Sharp program to compare two substrings using different cultures and ignoring the case of the substrings.cs b/c-sharp/Strings/C# Sharp program to compare two substrings using different cultures and ignoring the case of the substrings.cs new file mode 100644 index 0000000..b95017a --- /dev/null +++ b/c-sharp/Strings/C# Sharp program to compare two substrings using different cultures and ignoring the case of the substrings.cs @@ -0,0 +1,30 @@ +// Example for String.Compare(String, Int32, String, Int32, Int32, Boolean, CultureInfo) +using System; +using System.Globalization; + +class Example23 +{ + public static void Main() + { +// 01234567 + String str1 = "COMPUTER"; + String str2 = "computer"; + String str; + int result; + Console.WriteLine(); + Console.WriteLine("\n str1 = '{0}', str2 = '{1}'", str1, str2); + Console.WriteLine("Ignore case, Turkish culture:"); + result = String.Compare(str1, 4, str2, 4, 2, true, new CultureInfo("tr-TR")); + str = ((result < 0) ? "less than" : ((result > 0) ? "greater than" : "equal to")); + Console.Write("Substring '{0}' in '{1}' is ", str1.Substring(4, 2), str1); + Console.Write("{0} ", str); + Console.WriteLine("substring '{0}' in '{1}'.", str2.Substring(4, 2), str2); + Console.WriteLine(); + Console.WriteLine("Ignore case, invariant culture:"); + result = String.Compare(str1, 4, str2, 4, 2, true, CultureInfo.InvariantCulture); + str = ((result < 0) ? "less than" : ((result > 0) ? "greater than" : "equal to")); + Console.Write("Substring '{0}' in '{1}' is ", str1.Substring(4, 2), str1); + Console.Write("{0} ", str); + Console.WriteLine("substring '{0}' in '{1}'.\n\n", str2.Substring(4, 2), str2); + } +} \ No newline at end of file diff --git a/c-sharp/Strings/C# Sharp program to compares four sets of words by using each member of the StringComparison enumeration.cs b/c-sharp/Strings/C# Sharp program to compares four sets of words by using each member of the StringComparison enumeration.cs new file mode 100644 index 0000000..0e08b42 --- /dev/null +++ b/c-sharp/Strings/C# Sharp program to compares four sets of words by using each member of the StringComparison enumeration.cs @@ -0,0 +1,37 @@ +/* +Write a C# Sharp program to compares four sets of words by using each member of the StringComparison enumeration. The comparisons use the conventions of the English (United States) and Sami (Upper Sweden) cultures. +Note: that the strings "encyclopedia" and "encyclopedia" are considered equivalent in the en-US culture but not in the Sami (Northern Sweden) culture. +*/ + +using System; +using System.Globalization; +using System.Threading; + +public class Example25 +{ + public static void Main() + { + String[] cultureNames = { "en-AU", "sv-SE" }; + String[] strs1 = { "case", "encyclopedia", + "encyclopedia", "Archeology" + }; + String[] strs2 = { "Case", "encyclopedia", + "encyclopedia", "ARCHEOLOGY" + }; + StringComparison[] comparisons = (StringComparison[]) Enum.GetValues(typeof(StringComparison)); + foreach (var cultureName in cultureNames) + { + Thread.CurrentThread.CurrentCulture = CultureInfo.CreateSpecificCulture(cultureName); + Console.WriteLine("Current Culture: {0}", CultureInfo.CurrentCulture.Name); + for (int ctr = 0; ctr <= strs1.GetUpperBound(0); ctr++) + { + foreach (var comparison in comparisons) + Console.WriteLine(" {0} = {1} ({2}): {3}", strs1[ctr], + strs2[ctr], comparison, + String.Equals(strs1[ctr], strs2[ctr], comparison)); + Console.WriteLine(); + } + Console.WriteLine(); + } + } +} \ No newline at end of file diff --git a/c-sharp/Strings/C# Sharp program to demonstrate how culture can affect a comparison.cs b/c-sharp/Strings/C# Sharp program to demonstrate how culture can affect a comparison.cs new file mode 100644 index 0000000..a5e3122 --- /dev/null +++ b/c-sharp/Strings/C# Sharp program to demonstrate how culture can affect a comparison.cs @@ -0,0 +1,24 @@ +using System; +using System.Globalization; + +class Example27 +{ + public static void Main() + { + String str1 = "change"; + String str2 = "dollar"; + String relation = null; + relation = symbol( String.Compare(str1, str2, false, new CultureInfo("en-US")) ); + Console.WriteLine("\nFor en-US: {0} {1} {2}", str1, relation, str2); + relation = symbol( String.Compare(str1, str2, false, new CultureInfo("cs-CZ")) ); + Console.WriteLine("For cs-CZ: {0} {1} {2}\n", str1, relation, str2); + } + + private static String symbol(int r) + { + String s = "="; + if (r < 0) s = "<"; + else if (r > 0) s = ">"; + return s; + } +} \ No newline at end of file diff --git a/c-sharp/Strings/C# Sharp program to demonstrate that CompareOrdinal and Compare use different sort orders.cs b/c-sharp/Strings/C# Sharp program to demonstrate that CompareOrdinal and Compare use different sort orders.cs new file mode 100644 index 0000000..2e472a3 --- /dev/null +++ b/c-sharp/Strings/C# Sharp program to demonstrate that CompareOrdinal and Compare use different sort orders.cs @@ -0,0 +1,26 @@ +using System; +using System.Globalization; + +class Example30 +{ + public static void Main(String[] args) + { + String strLow = "xyz"; + String strCap = "XYZ"; + String result = "equal to "; + int x = 0; + int pos = 1; +// The Unicode codepoint for 'b' is greater than the codepoint for 'B'. + x = String.CompareOrdinal(strLow, pos, strCap, pos, 1); + if (x < 0) result = "less than"; + if (x > 0) result = "greater than"; + Console.WriteLine("CompareOrdinal(\"{0}\"[{2}], \"{1}\"[{2}]):", strLow, strCap, pos); + Console.WriteLine(" '{0}' is {1} '{2}'", strLow[pos], result, strCap[pos]); +// In U.S. English culture, 'b' is linguistically less than 'B'. + x = String.Compare(strLow, pos, strCap, pos, 1, false, new CultureInfo("en-US")); + if (x < 0) result = "less than"; + else if (x > 0) result = "greater than"; + Console.WriteLine("Compare(\"{0}\"[{2}], \"{1}\"[{2}]):", strLow, strCap, pos); + Console.WriteLine(" '{0}' is {1} '{2}'", strLow[pos], result, strCap[pos]); + } +} \ No newline at end of file diff --git a/c-sharp/Strings/C# Sharp program to demonstrate that the Compare(String, String, Boolean) method is equivalent to using ToUpper or ToLower when comparing strings.cs b/c-sharp/Strings/C# Sharp program to demonstrate that the Compare(String, String, Boolean) method is equivalent to using ToUpper or ToLower when comparing strings.cs new file mode 100644 index 0000000..42dc2af --- /dev/null +++ b/c-sharp/Strings/C# Sharp program to demonstrate that the Compare(String, String, Boolean) method is equivalent to using ToUpper or ToLower when comparing strings.cs @@ -0,0 +1,23 @@ +using System; + +class Example26 +{ + static void Main() + { + // Create upper-case characters from their Unicode code units. + String stringUpper = "\x0051\x0052\x0053"; + // Create lower-case characters from their Unicode code units. + String stringLower = "\x0071\x0072\x0073"; + // Display the strings. + Console.WriteLine("Comparing '{0}' and '{1}':", + stringUpper, stringLower); + // Compare the uppercased strings; the result is true. + Console.WriteLine("The Strings are equal when capitalized? {0}", + String.Compare(stringUpper.ToUpper(), stringLower.ToUpper()) == 0 + ? "true" : "false"); + // The previous method call is equivalent to this Compare method, which ignores case. + Console.WriteLine("The Strings are equal when case is ignored? {0}", + String.Compare(stringUpper, stringLower, true) == 0 + ? "true" : "false" ); + } +} \ No newline at end of file diff --git a/c-sharp/Strings/C# Sharp to check the username and password.cs b/c-sharp/Strings/C# Sharp to check the username and password.cs new file mode 100644 index 0000000..66df91e --- /dev/null +++ b/c-sharp/Strings/C# Sharp to check the username and password.cs @@ -0,0 +1,28 @@ +using System; +public class Exercise16 +{ + public static void Main() + { + string username, password; + int ctr = 0; + Console.Write("\n\nCheck username and password :\n"); + Console.Write("N.B. : Default user name and password is :abcd and 1234\n"); + Console.Write("------------------------------------------------------\n"); + do + { + Console.Write("Input a username: "); + username = Console.ReadLine(); + Console.Write("Input a password: "); + password = Console.ReadLine(); + if(username != "abcd" || password != "1234") + ctr++; + else + ctr=1; + } + while((username != "abcd" || password != "1234") && (ctr != 3)); + if (ctr == 3) + Console.Write("\nLogin attemp three or more times. Try later!\n\n"); + else + Console.Write("\nThe password entered successfully!\n\n"); + } +} \ No newline at end of file diff --git a/c-sharp/Strings/C# Sharp to check whether a character is an alphabet and not and if so, go to check for the case.cs b/c-sharp/Strings/C# Sharp to check whether a character is an alphabet and not and if so, go to check for the case.cs new file mode 100644 index 0000000..b1c5ed7 --- /dev/null +++ b/c-sharp/Strings/C# Sharp to check whether a character is an alphabet and not and if so, go to check for the case.cs @@ -0,0 +1,26 @@ +using System; +public class Exercise18 +{ + static void Main() + { + Console.Write("\n\nCheck whether a character is alphabet or not and if so, check for case :\n"); + Console.Write("-----------------------------------------------------------------------------\n"); + Console.Write("Input a character: "); + char ch = (char)Console.Read(); + if (Char.IsLetter(ch)) + { + if (Char.IsUpper(ch)) + { + Console.WriteLine("\nThe character is uppercase.\n"); + } + else + { + Console.WriteLine("\nThe character is lowercase.\n"); + } + } + else + { + Console.WriteLine("\nThe entered character is not an alphabetic character.\n"); + } + } +} \ No newline at end of file diff --git a/c-sharp/Strings/C# Sharp to compare two string without using string library functions.cs b/c-sharp/Strings/C# Sharp to compare two string without using string library functions.cs new file mode 100644 index 0000000..e65d87b --- /dev/null +++ b/c-sharp/Strings/C# Sharp to compare two string without using string library functions.cs @@ -0,0 +1,53 @@ +using System; +public class Exercise6 +{ + public static void Main() + { + string str1, str2; + int flg=0; + int i=0,l1,l2,yn=0; + Console.Write("\n\nCompare two string whether they are equal or not :\n"); + Console.Write("------------------------------------------------------\n"); + Console.Write("Input the 1st string : "); + str1 = Console.ReadLine(); + Console.Write("Input the 2nd string : "); + str2 = Console.ReadLine(); + l1=str1.Length; + l2=str2.Length; + /*compare checking when they are equal in length*/ + if(l1==l2) + { + for(i=0; i l2) + flg=1; + else if(l1 < l2) + flg=-1; + /*display the message where the strings are same or smaller or greater*/ + if(flg == 0) + { + if(yn==0) + Console.Write("\nThe length of both strings are equal and \nalso, both strings are same.\n\n"); + else + Console.Write("\nThe length of both strings are equal \nbut they are not same.\n\n"); + } + else if(flg == -1) + { + Console.Write("\nThe length of the first string is smaller than second.\n\n"); + } + else + { + Console.Write("\nThe length of the first string is greater than second.\n\n"); + } + } +} \ No newline at end of file diff --git a/c-sharp/Strings/C# Sharp to copy one string to another string.cs b/c-sharp/Strings/C# Sharp to copy one string to another string.cs new file mode 100644 index 0000000..dbaf83b --- /dev/null +++ b/c-sharp/Strings/C# Sharp to copy one string to another string.cs @@ -0,0 +1,26 @@ +using System; +public class Exercise8 +{ + public static void Main() + { + string str1; + int i,l; + Console.Write("\n\nCopy one string into another string :\n"); + Console.Write("-----------------------------------------\n"); + Console.Write("Input the string : "); + str1 = Console.ReadLine(); + l=str1.Length; + string[] str2=new string[l]; + /* Copies string1 to string2 character by character */ + i=0; + while(i='a' && str[i]<='z') || (str[i]>='A' && str[i]<='Z')) + { + alp++; + } + else if(str[i]>='0' && str[i]<='9') + { + digit++; + } + else + { + splch++; + } + i++; + } + Console.Write("Number of Alphabets in the string is : {0}\n", alp); + Console.Write("Number of Digits in the string is : {0}\n", digit); + Console.Write("Number of Special characters in the string is : {0}\n\n", splch); + } +} \ No newline at end of file diff --git a/c-sharp/Strings/C# Sharp to count a total number of vowel or consonant in a string.cs b/c-sharp/Strings/C# Sharp to count a total number of vowel or consonant in a string.cs new file mode 100644 index 0000000..3501b87 --- /dev/null +++ b/c-sharp/Strings/C# Sharp to count a total number of vowel or consonant in a string.cs @@ -0,0 +1,29 @@ +using System; +public class Exercise9 +{ + public static void Main() + { + string str; + int i, len, vowel, cons; + Console.Write("\n\nCount total number of vowel or consonant :\n"); + Console.Write("----------------------------------------------\n"); + Console.Write("Input the string : "); + str = Console.ReadLine(); + vowel = 0; + cons = 0; + len = str.Length; + for(i=0; i='a' && str[i]<='z') || (str[i]>='A' && str[i]<='Z')) + { + cons++; + } + } + Console.Write("\nThe total number of vowel in the string is : {0}\n", vowel); + Console.Write("The total number of consonant in the string is : {0}\n\n", cons); + } +} \ No newline at end of file diff --git a/c-sharp/Strings/C# Sharp to count the total number of words in a string.cs b/c-sharp/Strings/C# Sharp to count the total number of words in a string.cs new file mode 100644 index 0000000..476b5bd --- /dev/null +++ b/c-sharp/Strings/C# Sharp to count the total number of words in a string.cs @@ -0,0 +1,26 @@ +using System; +public class Exercise4 +{ + public static void Main() + { + string str; + int i, wrd,l; + Console.Write("\n\nCount the total number of words in a string :\n"); + Console.Write("------------------------------------------------------\n"); + Console.Write("Input the string : "); + str = Console.ReadLine(); + l = 0; + wrd = 1; + /* loop till end of string */ + while (l <= str.Length - 1) + { + /* check whether the current character is white space or new line or tab character*/ + if(str[l]==' ' || str[l]=='\n' || str[l]=='\t') + { + wrd++; + } + l++; + } + Console.Write("Total number of words in the string is : {0}\n", wrd); + } +} \ No newline at end of file diff --git a/c-sharp/Strings/C# Sharp to find maximum occurring character in a string.cs b/c-sharp/Strings/C# Sharp to find maximum occurring character in a string.cs new file mode 100644 index 0000000..8c1f1c1 --- /dev/null +++ b/c-sharp/Strings/C# Sharp to find maximum occurring character in a string.cs @@ -0,0 +1,39 @@ +using System; +public class Exercise10 +{ + public static void Main() + { + string str; + int[] ch_fre = new int[255]; + int i = 0, max,l; + int ascii; + Console.Write("\n\nFind maximum occurring character in a string :\n"); + Console.Write("--------------------------------------------------\n"); + Console.Write("Input the string : "); + str = Console.ReadLine(); + l=str.Length; + for(i=0; i<255; i++) //Set frequency of all characters to 0 + { + ch_fre[i] = 0; + } + /* Read for frequency of each characters */ + i=0; + while(i ch_fre[max]) + max = i; + } + } + Console.Write("The Highest frequency of character '{0}' is appearing for number of times : {1} \n\n", (char)max, ch_fre[max]); + } +} \ No newline at end of file diff --git a/c-sharp/Strings/C# Sharp to find the length of a string without using library function.cs b/c-sharp/Strings/C# Sharp to find the length of a string without using library function.cs new file mode 100644 index 0000000..3726600 --- /dev/null +++ b/c-sharp/Strings/C# Sharp to find the length of a string without using library function.cs @@ -0,0 +1,18 @@ +using System; +public class Exercise2 +{ + public static void Main() + { + string str; /* Declares a string of size 100 */ + int l= 0; + Console.Write("\n\nFind the length of a string :\n"); + Console.Write("---------------------------------\n"); + Console.Write("Input the string : "); + str = Console.ReadLine(); + foreach(char chr in str) + { + l += 1; + } + Console.Write("Length of the string is : {0}\n\n", l); + } +} \ No newline at end of file diff --git a/c-sharp/Strings/C# Sharp to find the number of times a substring appears in the given string.cs b/c-sharp/Strings/C# Sharp to find the number of times a substring appears in the given string.cs new file mode 100644 index 0000000..3f76baf --- /dev/null +++ b/c-sharp/Strings/C# Sharp to find the number of times a substring appears in the given string.cs @@ -0,0 +1,25 @@ +using System; +public class exercise19 +{ + public static void Main() + { + string str1; + string findstring; + int strt = 0; + int cnt = -1; + int idx = -1; + Console.Write("\n\nFind the number of times a specific string appears in a string :\n"); + Console.Write("--------------------------------------------------------------------\n"); + Console.Write("Input the original string : "); + str1 = Console.ReadLine(); + Console.Write("Input the string to be searched for : "); + findstring = Console.ReadLine(); + while (strt != -1) + { + strt = str1.IndexOf(findstring, idx + 1); + cnt += 1; + idx = strt; + } + Console.Write("The string '{0}' occurs " + cnt + " times.\n", findstring); + } +} \ No newline at end of file diff --git a/c-sharp/Strings/C# Sharp to insert a substring before the first occurrence of a string.cs b/c-sharp/Strings/C# Sharp to insert a substring before the first occurrence of a string.cs new file mode 100644 index 0000000..ac8cefd --- /dev/null +++ b/c-sharp/Strings/C# Sharp to insert a substring before the first occurrence of a string.cs @@ -0,0 +1,24 @@ +using System; + +public class Exercise20 +{ + public static void Main() + { + string str1; + string findstring; + string insertstring; + int i; + Console.Write("\n\nInsert a substing before the first occurence of a string :\n"); + Console.Write("--------------------------------------------------------------\n"); + Console.Write("Input the original string : "); + str1 = Console.ReadLine(); + Console.Write("Input the string to be searched for : "); + findstring = Console.ReadLine(); + Console.Write("Input the string to be inserted : "); + insertstring = Console.ReadLine(); + i=str1.IndexOf(findstring); // locate the position of the first occurence of the string + insertstring = " " + insertstring.Trim() + " "; + str1 = str1.Insert(i, insertstring); + Console.Write("The modified string is : {0}\n\n",str1); + } +} \ No newline at end of file diff --git a/c-sharp/Strings/C# Sharp to print individual characters of the string in reverse order.cs b/c-sharp/Strings/C# Sharp to print individual characters of the string in reverse order.cs new file mode 100644 index 0000000..db24d8f --- /dev/null +++ b/c-sharp/Strings/C# Sharp to print individual characters of the string in reverse order.cs @@ -0,0 +1,21 @@ +using System; +public class Exercise4 +{ + public static void Main() + { + string str; + int l=0; + Console.Write("\n\nprint individual characters of string in reverse order :\n"); + Console.Write("------------------------------------------------------\n"); + Console.Write("Input the string : "); + str = Console.ReadLine(); + l = str.Length - 1; + Console.Write("The characters of the string in reverse are : \n"); + while (l >= 0) + { + Console.Write("{0} ", str[l]); + l--; + } + Console.Write("\n\n"); + } +} \ No newline at end of file diff --git a/c-sharp/Strings/C# Sharp to read a sentence and replace lowercase characters by uppercase and vice-versa.cs b/c-sharp/Strings/C# Sharp to read a sentence and replace lowercase characters by uppercase and vice-versa.cs new file mode 100644 index 0000000..85aca55 --- /dev/null +++ b/c-sharp/Strings/C# Sharp to read a sentence and replace lowercase characters by uppercase and vice-versa.cs @@ -0,0 +1,28 @@ +using System; +public class exercise13 +{ + public static void Main() + { + string str1; + char[] arr1; + int l,i; + l=0; + char ch; + Console.Write("\n\nReplace lowercase characters by uppercase and vice-versa :\n"); + Console.Write("--------------------------------------------------------------\n"); + Console.Write("Input the string : "); + str1 = Console.ReadLine(); + l=str1.Length; + arr1 = str1.ToCharArray(0, l); // Converts string into char array. + Console.Write("\nAfter conversion, the string is : "); + for(i=0; i < l; i++) + { + ch=arr1[i]; + if (Char.IsLower(ch)) // check whether the character is lowercase + Console.Write(Char.ToUpper(ch)); // Converts lowercase character to uppercase. + else + Console.Write(Char.ToLower(ch)); // Converts uppercase character to lowercase. + } + Console.Write("\n\n"); + } +} \ No newline at end of file diff --git a/c-sharp/Strings/C# Sharp to read a string through the keyboard and sort it using bubble sort.cs b/c-sharp/Strings/C# Sharp to read a string through the keyboard and sort it using bubble sort.cs new file mode 100644 index 0000000..fb3a95c --- /dev/null +++ b/c-sharp/Strings/C# Sharp to read a string through the keyboard and sort it using bubble sort.cs @@ -0,0 +1,38 @@ +using System; +public class exercise12 +{ + public static void Main() + { + string[] arr1; + string temp; + int n,i,j,l; + Console.Write("\n\nSorts the strings of an array using bubble sort :\n"); + Console.Write("-----------------------------------------------------\n"); + Console.Write("Input number of strings :"); + n= Convert.ToInt32(Console.ReadLine()); + arr1=new string[n]; + Console.Write("Input {0} strings below :\n",n); + for(i=0; i 0) + { + temp = arr1[j]; + arr1[j] = arr1[j + 1]; + arr1[j + 1] = temp; + } + } + } + Console.Write("\n\nAfter sorting the array appears like : \n"); + for (i = 0; i < l; i++) + { + Console.WriteLine(arr1[i] + " "); + } + } +} \ No newline at end of file diff --git a/c-sharp/Strings/C# Sharp to search the position of a substring within a string.cs b/c-sharp/Strings/C# Sharp to search the position of a substring within a string.cs new file mode 100644 index 0000000..3b0be0f --- /dev/null +++ b/c-sharp/Strings/C# Sharp to search the position of a substring within a string.cs @@ -0,0 +1,22 @@ +using System; + +public class Exercise17 +{ + public static void Main() + { + string str1; + string findstr; + Console.Write("\n\nSearch the position of a substing within a string :\n"); + Console.Write("-------------------------------------------------------\n"); + Console.Write("Input a String: "); + str1 = Console.ReadLine(); + Console.Write("Input a substring to be found in the string: "); + findstr = Console.ReadLine(); + int index = str1.IndexOf(findstr); + if(index<0) + Console.WriteLine("The substring no found in the given string \n"); + else + Console.WriteLine("Found '{0}' in '{1}' at position {2}", + findstr, str1, index); + } +} \ No newline at end of file diff --git a/c-sharp/Strings/C# Sharp to separate the individual characters from a string.cs b/c-sharp/Strings/C# Sharp to separate the individual characters from a string.cs new file mode 100644 index 0000000..9af2e4d --- /dev/null +++ b/c-sharp/Strings/C# Sharp to separate the individual characters from a string.cs @@ -0,0 +1,20 @@ +using System; +public class Exercise3 +{ + public static void Main() + { + string str; + int l=0; + Console.Write("\n\nSeparate the individual characters from a string :\n"); + Console.Write("------------------------------------------------------\n"); + Console.Write("Input the string : "); + str = Console.ReadLine(); + Console.Write("The characters of the string are : "); + while (l <= str.Length - 1) + { + Console.Write("{0} ", str[l]); + l++; + } + Console.Write("\n\n"); + } +} \ No newline at end of file diff --git a/c-sharp/Strings/C# Sharp to sort a string array in ascending order.cs b/c-sharp/Strings/C# Sharp to sort a string array in ascending order.cs new file mode 100644 index 0000000..bbd9a27 --- /dev/null +++ b/c-sharp/Strings/C# Sharp to sort a string array in ascending order.cs @@ -0,0 +1,32 @@ +using System; +public class Exercise11 +{ + public static void Main() + { + string str; + char[] arr1; + char ch; + int i,j,l; + Console.Write("\n\nSort a string array in ascending order :\n"); + Console.Write("--------------------------------------------\n"); + Console.Write("Input the string : "); + str = Console.ReadLine(); + l=str.Length; + arr1 = str.ToCharArray(0, l); + for(i=1; iarr1[j+1]) + { + ch=arr1[j]; + arr1[j] = arr1[j+1]; + arr1[j+1]=ch; + } + Console.Write("After sorting the string appears like : \n"); + foreach (char c in arr1) + { + ch=c; + Console.Write("{0} ",ch); + } + Console.WriteLine("\n"); + } +} \ No newline at end of file diff --git a/c-sharp/Strings/StringUtils.cs b/c-sharp/Strings/StringUtils.cs new file mode 100644 index 0000000..2685e03 --- /dev/null +++ b/c-sharp/Strings/StringUtils.cs @@ -0,0 +1,31 @@ +using System; +using System.Diagnostics.Contracts; + + +namespace DataStructures.Utils +{ + public static class StringUtils + { + public static string CommonPrefix(this string str1, string str2) + { + Contract.Ensures(Contract.Result() != null); + return str1.Substring(0, str1.CommonPrefixLength(str2)); + } + + public static int CommonPrefixLength(this string str1, string str2) + { + Contract.Requires(str2 != null); + Contract.Ensures(Contract.Result() >= 0); + + int count = 0; + for (int i = 0; i < str1.Length && i < str2.Length; i++, count++) + { + if (str1[i] != str2[i]) + { + break; + } + } + return count; + } + } +} diff --git a/c-sharp/_Basic/C# Program to Accept a Number from the user and Display it if it is Positive.cs b/c-sharp/_Basic/C# Program to Accept a Number from the user and Display it if it is Positive.cs new file mode 100644 index 0000000..95685b9 --- /dev/null +++ b/c-sharp/_Basic/C# Program to Accept a Number from the user and Display it if it is Positive.cs @@ -0,0 +1,30 @@ +/* + * C# Program to Accept a Number from the user and Display it + * if it is Positive + */ +using System; +class program +{ + public static void Main(string[] args) + { + Console.WriteLine("Enter a number: "); + int number = Convert.ToInt32(Console.ReadLine()); + if (number > 0) + { + Console.WriteLine("Number is positive"); + } + else if (number == 0) + { + Console.WriteLine("Number is 0"); + } + else + { + Console.WriteLine("Number is negative"); + } + Console.ReadLine(); + } +} + +/* +Enter a Number : -4 +Number is Negative \ No newline at end of file diff --git a/c-sharp/_Basic/C# Program to Accept the Height of a Person & Categorize as Tall, Dwarf or Average.cs b/c-sharp/_Basic/C# Program to Accept the Height of a Person & Categorize as Tall, Dwarf or Average.cs new file mode 100644 index 0000000..43eaf08 --- /dev/null +++ b/c-sharp/_Basic/C# Program to Accept the Height of a Person & Categorize as Tall, Dwarf or Average.cs @@ -0,0 +1,27 @@ +/* + * C# Program to Accept the Height of a Person & Categorize as + * Tall, Dwarf or Average + */ +using System; +class program +{ + public static void Main() + { + float height; + Console.WriteLine("Enter the Height (in centimeters) \n"); + height = int.Parse(Console.ReadLine()); + if (height < 150.0) + Console.WriteLine("Dwarf \n"); + else if ((height >= 150.0) && (height <= 165.0)) + Console.WriteLine(" Average Height \n"); + else if ((height >= 165.0) && (height <= 195.0)) + Console.WriteLine("Taller \n"); + else + Console.WriteLine("Abnormal height \n"); + } +} + +/* +Enter the Height (in centimeters) +165 + Average Height \ No newline at end of file diff --git a/c-sharp/_Basic/C# Program to Calculate Acceleration.cs b/c-sharp/_Basic/C# Program to Calculate Acceleration.cs new file mode 100644 index 0000000..25719e7 --- /dev/null +++ b/c-sharp/_Basic/C# Program to Calculate Acceleration.cs @@ -0,0 +1,23 @@ +/* + * C# Program to Calculate Acceleration +using System; +class program +{ + static void Main(string[] args) + { + int v, t, acc; + Console.WriteLine("Enter the Velocity : "); + v = int.Parse(Console.ReadLine()); + Console.WriteLine("Enter the Time : "); + t = int.Parse(Console.ReadLine()); + acc = v / t; + Console.WriteLine("Acceleration : {0}", acc); + } +} + +/* +Enter the Velocity : +10 +Enter the Time : +2 +Acceleration : 5 \ No newline at end of file diff --git a/c-sharp/_Basic/C# Program to Check Whether the Entered Year is a Leap Year or Not.cs b/c-sharp/_Basic/C# Program to Check Whether the Entered Year is a Leap Year or Not.cs new file mode 100644 index 0000000..d0220a2 --- /dev/null +++ b/c-sharp/_Basic/C# Program to Check Whether the Entered Year is a Leap Year or Not.cs @@ -0,0 +1,42 @@ +/* + * C# Program to Check Whether the Entered Year is a Leap Year or Not + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +namespace Program +{ +class leapyear +{ + static void Main(string[] args) + { + leapyear obj = new leapyear(); + obj.readdata(); + obj.leap(); + } + int y; + public void readdata() + { + Console.WriteLine("Enter the Year in Four Digits : "); + y = Convert.ToInt32(Console.ReadLine()); + } + public void leap() + { + if ((y % 4 == 0 && y % 100 != 0) || (y % 400 == 0)) + { + Console.WriteLine("{0} is a Leap Year", y); + } + else + { + Console.WriteLine("{0} is not a Leap Year", y); + } + Console.ReadLine(); + } +} +} + +/* +Enter the Year in Four Digits : 1004 +1004 is a Leap Year \ No newline at end of file diff --git a/c-sharp/_Basic/C# Program to Check whether the Entered Number is Even or Odd.cs b/c-sharp/_Basic/C# Program to Check whether the Entered Number is Even or Odd.cs new file mode 100644 index 0000000..ccfb25d --- /dev/null +++ b/c-sharp/_Basic/C# Program to Check whether the Entered Number is Even or Odd.cs @@ -0,0 +1,34 @@ +/* + * C# Program to Check whether the Entered Number is Even or Odd + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +namespace check1 +{ +class Program +{ + static void Main(string[] args) + { + int i; + Console.Write("Enter a Number : "); + i = int.Parse(Console.ReadLine()); + if (i % 2 == 0) + { + Console.Write("Entered Number is an Even Number"); + Console.Read(); + } + else + { + Console.Write("Entered Number is an Odd Number"); + Console.Read(); + } + } +} +} + +/* +Enter a Number : 25 +Entered Number is an Odd Number \ No newline at end of file diff --git a/c-sharp/_Basic/C# Program to Check whether the given Integer has an Alternate Pattern.cs b/c-sharp/_Basic/C# Program to Check whether the given Integer has an Alternate Pattern.cs new file mode 100644 index 0000000..0f19804 --- /dev/null +++ b/c-sharp/_Basic/C# Program to Check whether the given Integer has an Alternate Pattern.cs @@ -0,0 +1,45 @@ +/* + * C# Program to Check whether the given Integer has an + * Alternate Pattern + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +class program +{ + public static void Main() + { + int num, x, y, count = 0; + Console.WriteLine("Enter the Number:"); + num = int.Parse(Console.ReadLine()); + x = num << 1; + y = x ^ num; + y = y + 1; + while ((y / 2) != 0) + { + if (y % 2 != 0) + { + count++; + break; + } + else + { + y = y / 2; + } + } + if (count == 1) + { + Console.WriteLine("false"); + } + else + { + Console.WriteLine("true"); + } + Console.Read(); + } +} + +/* +Enter the Number: 100 +false \ No newline at end of file diff --git a/c-sharp/_Basic/C# Program to Compare Two Dates.cs b/c-sharp/_Basic/C# Program to Compare Two Dates.cs new file mode 100644 index 0000000..ab6a902 --- /dev/null +++ b/c-sharp/_Basic/C# Program to Compare Two Dates.cs @@ -0,0 +1,26 @@ +/* + * C# Program to Campare Two Dates + */ +using System; +namespace DateAndTime +{ +class Program +{ + static int Main() + { + DateTime sd = new DateTime(2010, 10, 12); + Console.WriteLine("Starting Date : {0}", sd); + DateTime ed = sd.AddDays(10); + Console.WriteLine("Ending Date : {0}", ed); + if (sd < ed) + Console.WriteLine("{0} Occurs Before {1}", sd, ed); + Console.Read(); + return 0; + } +} +} + +/* +Starting Date : 10/11/2010 12:00:00 AM +Ending Date : 10/21/2010 12:00:00 AM +10/11/2010 12:00:00 Am Occurs Before 10/21/2010 12:00:00 AM \ No newline at end of file diff --git a/c-sharp/_Basic/C# Program to Compute Average for the Set of Values.cs b/c-sharp/_Basic/C# Program to Compute Average for the Set of Values.cs new file mode 100644 index 0000000..026f551 --- /dev/null +++ b/c-sharp/_Basic/C# Program to Compute Average for the Set of Values.cs @@ -0,0 +1,35 @@ +/* + * C# Program to Compute Average for the Set of Values + */ +using System; +class program +{ + public static void Main() + { + int m, i, sum = 0, avg = 0; + Console.WriteLine("Enter the Number of Terms in the Array "); + m = int.Parse(Console.ReadLine()); + int[] a = new int[m]; + Console.WriteLine("Enter the Array Elements "); + for (i = 0; i < m; i++) + { + a[i] = int.Parse(Console.ReadLine()); + } + for (i = 0; i < m; i++) + { + sum += a[i]; + } + avg = sum / m; + Console.WriteLine("Average is {0}", avg); + Console.ReadLine(); + } +} + +/* +Enter the Number of Terms in the Array : 4 +Enter the Elements +1 +2 +3 +4 +Average is 2 \ No newline at end of file diff --git a/c-sharp/_Basic/C# Program to Count the Number of 1’s in the Entered Number.cs b/c-sharp/_Basic/C# Program to Count the Number of 1’s in the Entered Number.cs new file mode 100644 index 0000000..60c4b5c --- /dev/null +++ b/c-sharp/_Basic/C# Program to Count the Number of 1’s in the Entered Number.cs @@ -0,0 +1,46 @@ +/* + * C# Program to Count the Number of 1's in the Entered Number + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +namespace ConsoleApplication16 +{ +class Program +{ + static void Main(string[] args) + { + int m, count = 0; + Console.WriteLine("Enter the Limit : "); + m = int.Parse(Console.ReadLine()); + int[] a = new int[m]; + Console.WriteLine("Enter the Numbers :"); + for (int i = 0; i < m; i++) + { + a[i] = Convert.ToInt32(Console.ReadLine()); + } + foreach (int o in a) + { + if (o == 1) + { + count++; + } + } + Console.WriteLine("Number of 1's in the Entered Number : "); + Console.WriteLine(count); + Console.ReadLine(); + } +} +} + +/* +Enter the Limit : 5 +Enter the Numbers : +1 +2 +1 +4 +1 +Number of 1's in the Entered Number : 3 \ No newline at end of file diff --git a/c-sharp/_Basic/C# Program to Create Sealed Class.cs b/c-sharp/_Basic/C# Program to Create Sealed Class.cs new file mode 100644 index 0000000..6dd6481 --- /dev/null +++ b/c-sharp/_Basic/C# Program to Create Sealed Class.cs @@ -0,0 +1,24 @@ +/* + * C# Program to Create Sealed Class + */ +using System; +sealed class SealedClass +{ + public int x; + public int y; +} + +class SealedTest +{ + static void Main() + { + SealedClass sc = new SealedClass(); + sc.x = 100; + sc.y = 180; + Console.WriteLine("x = {0}, y = {1}", sc.x, sc.y); + Console.ReadLine(); + } +} + +/* +x = 100 ,y = 180 \ No newline at end of file diff --git a/c-sharp/_Basic/C# Program to Display All the Prime Numbers Between 1 to 100.cs b/c-sharp/_Basic/C# Program to Display All the Prime Numbers Between 1 to 100.cs new file mode 100644 index 0000000..64c7c9a --- /dev/null +++ b/c-sharp/_Basic/C# Program to Display All the Prime Numbers Between 1 to 100.cs @@ -0,0 +1,41 @@ +/* + * C# Program to Display All the Prime Numbers Between 1 to 100 + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +namespace PrimeNumber +{ +class Program +{ + static void Main(string[] args) + { + bool isPrime = true; + Console.WriteLine("Prime Numbers : "); + for (int i = 2; i <= 100; i++) + { + for (int j = 2; j <= 100; j++) + { + if (i != j && i % j == 0) + { + isPrime = false; + break; + } + } + if (isPrime) + { + Console.Write("\t" +i); + } + isPrime = true; + } + Console.ReadKey(); + } +} +} + +/* +Prime Numbers : + 2 3 5 7 11 13 17 19 23 29 +31 37 41 43 47 53 59 61 67 71 +73 79 83 89 97 \ No newline at end of file diff --git a/c-sharp/_Basic/C# Program to Display Numbers in the form of Triangle.cs b/c-sharp/_Basic/C# Program to Display Numbers in the form of Triangle.cs new file mode 100644 index 0000000..3f3c88e --- /dev/null +++ b/c-sharp/_Basic/C# Program to Display Numbers in the form of Triangle.cs @@ -0,0 +1,42 @@ +/* + * C# Program to Display Numbers in the form of Triangle + */ +using System; +class Pascal +{ + public static void Main() + { + int[,] arr = new int[8, 8]; + for (int i = 0; i < 8; i++) + { + for (int k = 7; k > i; k--) + { + //For loop to print spaces + Console.Write(" "); + } + for (int j = 0; j < i; j++) + { + if (j == 0 || i == j) + { + arr[i, j] = 1; + } + else + { + arr[i, j] = arr[i - 1, j] + arr[i - 1, j - 1]; + } + Console.Write(arr[i, j] + " "); + } + Console.WriteLine(); + } + Console.ReadLine(); + } +} + +/* + 1 + 1 1 + 1 2 1 + 1 3 3 1 + 1 4 6 4 1 + 1 5 10 10 5 1 +1 6 15 20 15 6 1 \ No newline at end of file diff --git a/c-sharp/_Basic/C# Program to Display Squarefeet of a House.cs b/c-sharp/_Basic/C# Program to Display Squarefeet of a House.cs new file mode 100644 index 0000000..41418c6 --- /dev/null +++ b/c-sharp/_Basic/C# Program to Display Squarefeet of a House.cs @@ -0,0 +1,23 @@ +/* + * C# Program to Display Squarefeet of a House + */ +using System; +class pgm +{ + public static void Main() + { + int length, width, area; + Console.Write ("Enter length of room in feet: "); + length = Convert.ToInt32 (Console.ReadLine()); + Console.Write ( "Enter width of room in feet:"); + width = Convert.ToInt32(Console.ReadLine()); + area = length * width; + Console.WriteLine ("Floor is " + area + " square feet."); + Console.ReadLine(); + } +} + +/* +Enter Length of Room in Feet : 20 +Enter width of Room in Feet : 20 +Floor is 400 square feet. \ No newline at end of file diff --git a/c-sharp/_Basic/C# Program to Display the ATM Transaction.cs b/c-sharp/_Basic/C# Program to Display the ATM Transaction.cs new file mode 100644 index 0000000..12e1bed --- /dev/null +++ b/c-sharp/_Basic/C# Program to Display the ATM Transaction.cs @@ -0,0 +1,77 @@ +/* + * C# Program to Display the ATM Transaction + */ +using System; +class program +{ + public static void Main() + { + int amount = 1000, deposit, withdraw; + int choice, pin = 0, x = 0; + Console.WriteLine("Enter Your Pin Number "); + pin = int.Parse(Console.ReadLine()); + while (true) + { + Console.WriteLine("********Welcome to ATM Service**************\n"); + Console.WriteLine("1. Check Balance\n"); + Console.WriteLine("2. Withdraw Cash\n"); + Console.WriteLine("3. Deposit Cash\n"); + Console.WriteLine("4. Quit\n"); + Console.WriteLine("*********************************************\n\n"); + Console.WriteLine("Enter your choice: "); + choice = int.Parse(Console.ReadLine()); + switch (choice) + { + case 1: + Console.WriteLine("\n YOUR BALANCE IN Rs : {0} ", amount); + break; + case 2: + Console.WriteLine("\n ENTER THE AMOUNT TO WITHDRAW: "); + withdraw = int.Parse(Console.ReadLine()); + if (withdraw % 100 != 0) + { + Console.WriteLine("\n PLEASE ENTER THE AMOUNT IN MULTIPLES OF 100"); + } + else if (withdraw > (amount - 500)) + { + Console.WriteLine("\n INSUFFICENT BALANCE"); + } + else + { + amount = amount - withdraw; + Console.WriteLine("\n\n PLEASE COLLECT CASH"); + Console.WriteLine("\n YOUR CURRENT BALANCE IS {0}", amount); + } + break; + case 3: + Console.WriteLine("\n ENTER THE AMOUNT TO DEPOSIT"); + deposit = int.Parse(Console.ReadLine()); + amount = amount + deposit; + Console.WriteLine("YOUR BALANCE IS {0}", amount); + break; + case 4: + Console.WriteLine("\n THANK U USING ATM"); + break; + } + } + Console.WriteLine("\n\n THANKS FOR USING OUT ATM SERVICE"); + } +} + +/* +Enter Your Pin Number +123 +********Welcome to ATM Service************** + +1. Check Balance + +2. Withdraw Cash + +3. Deposit Cash + +4. Quit + +********************************************* +Enter your choice: +1 +YOUR BALANCE IN Rs : 1000 \ No newline at end of file diff --git a/c-sharp/_Basic/C# Program to Display the Date in Various Formats.cs b/c-sharp/_Basic/C# Program to Display the Date in Various Formats.cs new file mode 100644 index 0000000..3d3e761 --- /dev/null +++ b/c-sharp/_Basic/C# Program to Display the Date in Various Formats.cs @@ -0,0 +1,36 @@ +/* + * C# Program to Display the Date in Various Formats + */ +using System; +namespace DateAndTime +{ +class Program +{ + static int Main() + { + DateTime date = new DateTime(2013,6, 23); + Console.WriteLine("Some Date Formats : "); + Console.WriteLine("Date and Time: {0}", date); + Console.WriteLine(date.ToString("yyyy-MM-dd")); + Console.WriteLine(date.ToString("dd-MMM-yy")); + Console.WriteLine(date.ToString("M/d/yyyy")); + Console.WriteLine(date.ToString("M/d/yy")); + Console.WriteLine(date.ToString("MM/dd/yyyy")); + Console.WriteLine(date.ToString("MM/dd/yy")); + Console.WriteLine(date.ToString("yy/MM/dd")); + Console.Read(); + return 0; + } +} +} + +/* +Some Date Formats : +Date and Time : 6/23/2013 12:00:00 AM +2013-06-23 +23-Jun-13 +6/23/2013 +6/23/13 +06/23/2013 +06/23/13 +13/06/23 \ No newline at end of file diff --git a/c-sharp/_Basic/C# Program to Find Greatest among 2 numbers.cs b/c-sharp/_Basic/C# Program to Find Greatest among 2 numbers.cs new file mode 100644 index 0000000..bb4e35e --- /dev/null +++ b/c-sharp/_Basic/C# Program to Find Greatest among 2 numbers.cs @@ -0,0 +1,29 @@ +/* + * C# Program to Find Greatest among 2 numbers + */ +using System; +class prog +{ + public static void Main() + { + int a, b; + Console.WriteLine("Enter the Two Numbers : "); + a = Convert.ToInt32(Console.ReadLine()); + b = Convert.ToInt32(Console.ReadLine()); + if (a > b) + { + Console.WriteLine("{0} is the Greatest Number", a); + } + else + { + Console.WriteLine("{0} is the Greatest Number ", b); + } + Console.ReadLine(); + } +} + +/* +Enter the Two Numbers : +24 +34 +34 is the Greatest Number \ No newline at end of file diff --git a/c-sharp/_Basic/C# Program to Find Magnitude of Integer.cs b/c-sharp/_Basic/C# Program to Find Magnitude of Integer.cs new file mode 100644 index 0000000..003239c --- /dev/null +++ b/c-sharp/_Basic/C# Program to Find Magnitude of Integer.cs @@ -0,0 +1,26 @@ +/* + * C# Program to Find Magnitude of Integer + */ +using System; +public class Program +{ + public static void Main() + { + int num, mag=0; + Console.WriteLine("Enter the Number : "); + num = int.Parse(Console.ReadLine()); + Console.WriteLine("Number: " + num); + while (num > 0) + { + mag++; + num = num / 10; + }; + Console.WriteLine("Magnitude: " + mag); + Console.Read(); + } +} + +/* +Enter the Number : 3145678 +Number : 3145678 +Magnitude : 7 \ No newline at end of file diff --git a/c-sharp/_Basic/C# Program to Find a Number using Pythagoras Theorem.cs b/c-sharp/_Basic/C# Program to Find a Number using Pythagoras Theorem.cs new file mode 100644 index 0000000..6122fcf --- /dev/null +++ b/c-sharp/_Basic/C# Program to Find a Number using Pythagoras Theorem.cs @@ -0,0 +1,28 @@ +/* + * C# Program to Find a Number using Pythagoras Theorem + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +class Program +{ + static void Main(string[] args) + { + double a, b, c; + Console.WriteLine("Enter the First Value "); + a = double.Parse(Console.ReadLine()); + Console.WriteLine("Enter the Second Value "); + b = double.Parse(Console.ReadLine()); + c = Math.Sqrt(a * a + b * b); + Console.WriteLine("The Other Number is : {0}", c); + Console.ReadLine(); + } +} + +/* +Enter the First Value +3 +Enter the Second Value +4 +The Other Number is : 5 \ No newline at end of file diff --git a/c-sharp/_Basic/C# Program to Generate Random Numbers.cs b/c-sharp/_Basic/C# Program to Generate Random Numbers.cs new file mode 100644 index 0000000..ec53c24 --- /dev/null +++ b/c-sharp/_Basic/C# Program to Generate Random Numbers.cs @@ -0,0 +1,34 @@ +/* + * C# Program to Generate Random Numbers + */ +using System; +class Program +{ + static void Main() + { + Console.WriteLine("Some Random Numbers that are generated are : "); + for (int i = 1; i < 10; i++) + { + Randfunc(); + } + } + static Random r = new Random(); + static void Randfunc() + { + int n = r.Next(); + Console.WriteLine(n); + Console.ReadLine(); + } +} + +/* +Some Random Numbers that are generated are : +1234567 +8754352 +9864930 +8352048 +1920472 +2846104 +7649207 +4928756 +9261746 \ No newline at end of file diff --git a/c-sharp/_Basic/C# Program to Get a Number and Display the Number with its Reverse.cs b/c-sharp/_Basic/C# Program to Get a Number and Display the Number with its Reverse.cs new file mode 100644 index 0000000..c8e6b06 --- /dev/null +++ b/c-sharp/_Basic/C# Program to Get a Number and Display the Number with its Reverse.cs @@ -0,0 +1,31 @@ +/* + * C# Program to Get a Number and Display the Number with its Reverse + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +namespace Program +{ +class Program +{ + static void Main(string[] args) + { + int num, reverse = 0; + Console.WriteLine("Enter a Number : "); + num = int.Parse(Console.ReadLine()); + while (num != 0) + { + reverse = reverse * 10; + reverse = reverse + num % 10; + num = num / 10; + } + Console.WriteLine("Reverse of Entered Number is : "+reverse); + Console.ReadLine(); + } +} +} + +Enter a Number : 123 +Reverse of Entered Number : 321 \ No newline at end of file diff --git a/c-sharp/_Basic/C# Program to Get a Number and Display the Sum of the Digits.cs b/c-sharp/_Basic/C# Program to Get a Number and Display the Sum of the Digits.cs new file mode 100644 index 0000000..07f7583 --- /dev/null +++ b/c-sharp/_Basic/C# Program to Get a Number and Display the Sum of the Digits.cs @@ -0,0 +1,31 @@ +/* + * C# Program to Get a Number and Display the Sum of the Digits + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +namespace Program +{ +class Program +{ + static void Main(string[] args) + { + int num, sum = 0, r; + Console.WriteLine("Enter a Number : "); + num = int.Parse(Console.ReadLine()); + while (num != 0) + { + r = num % 10; + num = num / 10; + sum = sum + r; + } + Console.WriteLine("Sum of Digits of the Number : "+sum); + Console.ReadLine(); + } +} +} + +Enter a Number : 123 +Sum of Digits of the Number : 6 \ No newline at end of file diff --git a/c-sharp/_Basic/C# Program to Illustrate LeftShift Operations.cs b/c-sharp/_Basic/C# Program to Illustrate LeftShift Operations.cs new file mode 100644 index 0000000..08779a7 --- /dev/null +++ b/c-sharp/_Basic/C# Program to Illustrate LeftShift Operations.cs @@ -0,0 +1,28 @@ +/* + * C# Program to Illustrate LeftShift Operations + */ +using System; +class sample +{ + public static void Main() + { + int x = 1024 * 1024 * 1024; + uint p = 1024 * 1024 * 1024; + int y = -42; + Console.WriteLine("LEFT SHIFT OPERATIONS :"); + Console.WriteLine("{0},{1},{2}", x, x * 2, x << 1); + Console.WriteLine("{0},{1},{2}", p, p * 2, p << 1); + Console.WriteLine("{0},{1},{2}", x, x * 4, x << 2); + Console.WriteLine("{0},{1},{2}", p, p * 4, p << 2); + Console.WriteLine("{0},{1},{2}", y, y * 1024 * 1024 * 64, x << 26); + Console.ReadLine(); + } +} + +/* +LEFT SHIFT OPERATIONS : +1073741824,-2147483648,-2147483648 +1073741824,2147483648,2147483648 +1073741824,0,0 +1073741824,0,0 +-42,1476395008,0 \ No newline at end of file diff --git a/c-sharp/_Basic/C# Program to Illustrate the Use of Access Specifiers.cs b/c-sharp/_Basic/C# Program to Illustrate the Use of Access Specifiers.cs new file mode 100644 index 0000000..d7d0479 --- /dev/null +++ b/c-sharp/_Basic/C# Program to Illustrate the Use of Access Specifiers.cs @@ -0,0 +1,48 @@ +/* + * C# Program to Illustrate the Use of Access Specifiers + */ +using System; +namespace accessspecifier +{ +class Program +{ + static void Main(string[] args) + { + two B = new two(); + B.show(); + } +} +class one +{ + private int x; + protected int y; + internal int z; + public int a; + protected internal int b; +} +class two : one +{ + public void show() + { + Console.WriteLine("Values are : "); + //x=10; + y = 20; + z = 30; + a = 40; + b = 50; + // Console.WriteLine(+x); // Error x is not accessible + Console.WriteLine(y); + Console.WriteLine(z); + Console.WriteLine(a); + Console.WriteLine(b); + Console.ReadLine(); + } +} +} + +/* +Values are : +20 +30 +40 +50 \ No newline at end of file diff --git a/c-sharp/_Basic/C# Program to Implement PhoneBook.cs b/c-sharp/_Basic/C# Program to Implement PhoneBook.cs new file mode 100644 index 0000000..ed3cda3 --- /dev/null +++ b/c-sharp/_Basic/C# Program to Implement PhoneBook.cs @@ -0,0 +1,52 @@ +/* + * C# Program to Implement PhoneBook + */ +using System; +using System.Collections; +using System.IO; +class PhoneBook +{ + + static void Main(string[] arg) + { + Hashtable tab = new Hashtable(); + string fileName; + if + { + (arg.Length > 0) fileName = arg[0]; + } + else + { + fileName = "phoneBook.txt"; + } + StreamReader r = File.OpenText(fileName); + string line = r.ReadLine(); + while (line != null) + { + int pos = line.IndexOf('='); + string name = line.Substring(0, pos).Trim(); + long phone = Convert.ToInt64(line.Substring(pos + 1)); + tab[name] = phone; + line = r.ReadLine(); + } + r.Close(); + for (; ; ) + { + Console.Write("Name : "); + string name = Console.ReadLine().Trim(); + if (name == "") + break; + object phone = tab[name]; + if (phone == null) + Console.WriteLine("-- Not Found in Phone Book"); + else + Console.WriteLine(phone); + } + } +} + +/* +Name : Ram +9999945670 +Name : Raj +-- Not Found in Phone Book \ No newline at end of file diff --git a/c-sharp/_Basic/C# Program to Implement for-each in Inteface.cs b/c-sharp/_Basic/C# Program to Implement for-each in Inteface.cs new file mode 100644 index 0000000..8637230 --- /dev/null +++ b/c-sharp/_Basic/C# Program to Implement for-each in Inteface.cs @@ -0,0 +1,85 @@ +/* + * C# Program to Implement for-each in Inteface + */ +using System; +using System.Collections; +class GrowableArray : IEnumerable +{ + object[] a; + public GrowableArray(int size) + { + a = new object[size]; + } + public GrowableArray() : this(8) {} + void Grow() + { + object[] b = new object[2 * a.Length]; + Array.Copy(a, b, a.Length); + a = b; + } + public object this[int i] + { + set + { + if (i >= a.Length) Grow(); + a[i] = value; + } + get + { + if (i >= a.Length) Grow(); + return a[i]; + } + } + public IEnumerator GetEnumerator() + { + return new GAEnumerator(a); + } + class GAEnumerator : IEnumerator + { + object[] a; + int i = -1; + public GAEnumerator(object[] a) + { + this.a = a; + } + public object Current + { + get + { + return a[i]; + } + } + public void Reset() + { + i = -1; + } + public bool MoveNext() + { + do i++; + while (i < a.Length && a[i] == null); + if (i == a.Length) + return false; + else return true; + } + } + +} +class Test +{ + public static void Main() + { + GrowableArray a = new GrowableArray(2); + a[0] = 0; + a[1] = 1; + a[3] = 3; + foreach (object x in a) Console.Write(" " + x); + } + + /* + Demonstrating foreach Interface by Displaying Numbers from 100 to 105 : + 100 + 101 + 102 + 103 + 104 + 105 \ No newline at end of file diff --git a/c-sharp/_Basic/C# Program to Perform Division of Exponents of Same Base.cs b/c-sharp/_Basic/C# Program to Perform Division of Exponents of Same Base.cs new file mode 100644 index 0000000..64c5bde --- /dev/null +++ b/c-sharp/_Basic/C# Program to Perform Division of Exponents of Same Base.cs @@ -0,0 +1,29 @@ +/* + * C# Program to Perform Division of Exponents of Same Base + */ +using System; +class Program +{ + static void Main() + { + Console.WriteLine("Enter the Base : "); + double num = double.Parse(Console.ReadLine()); + Console.WriteLine("Enter the First Exponent :"); + double exp1 = double.Parse(Console.ReadLine()); + Console.WriteLine("Enter the Second Exponent :"); + double exp2 = double.Parse(Console.ReadLine()); + double div; + div = exp1 - exp2; + Console.WriteLine("Result is : {0}^{1} : {2}", num, div, Math.Pow(num, div)); + Console.ReadLine(); + } +} + +/* +Enter the Base : +2 +Enter the First Exponent : +4 +Enter the Second Exponent : +3 +Result is : 2^1 : 2 \ No newline at end of file diff --git a/c-sharp/_Basic/C# Program to Perform Unboxing Operation.cs b/c-sharp/_Basic/C# Program to Perform Unboxing Operation.cs new file mode 100644 index 0000000..cd2d9ca --- /dev/null +++ b/c-sharp/_Basic/C# Program to Perform Unboxing Operation.cs @@ -0,0 +1,29 @@ +/* + * C# Program to Perform Unboxing Operation + */ +using System; +class sample +{ + int data; + void insert(object x) + { + data = (int)x * 5; + } + object delete() + { + data=0; + return (object)data; + } + public static void Main() + { + sample s = new sample(); + s.insert(10); + Console.WriteLine("Data : {0}", s.data); + Console.WriteLine("Data : {0}", s.delete()); + Console.ReadLine(); + } +} + +/* +Data : 50 +Data : 0 \ No newline at end of file diff --git a/c-sharp/_Basic/C# Program to Print a BinaryTriangle.cs b/c-sharp/_Basic/C# Program to Print a BinaryTriangle.cs new file mode 100644 index 0000000..d8e3c5a --- /dev/null +++ b/c-sharp/_Basic/C# Program to Print a BinaryTriangle.cs @@ -0,0 +1,46 @@ +/* + * C# Program to Print a BinaryTriangle + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; + +namespace Program +{ +class Program +{ + public static void Main(String[] args) + { + int p, lastInt = 0, input; + Console.WriteLine("Enter the Number of Rows : "); + input = int.Parse(Console.ReadLine()); + for (int i = 1; i <= input; i++) + { + for (p = 1; p <= i; p++) + { + if (lastInt == 1) + { + Console.Write("0"); + lastInt = 0; + } + else if (lastInt == 0) + { + Console.Write("1"); + lastInt = 1; + } + } + Console.Write("\n"); + } + Console.ReadLine(); + } +} +} + +/* +Enter the Number of Rows : 5 +1 +01 +010 +1010 +10101 \ No newline at end of file diff --git a/c-sharp/_Basic/C# Program to Print a Diamond Using Nested Loop.cs b/c-sharp/_Basic/C# Program to Print a Diamond Using Nested Loop.cs new file mode 100644 index 0000000..e8f0c68 --- /dev/null +++ b/c-sharp/_Basic/C# Program to Print a Diamond Using Nested Loop.cs @@ -0,0 +1,43 @@ +/* + * C# Program to Print the Sum of all the Multiples of 3 and 5 + */ +using System; +class program +{ + public static void Main() + { + int number, i, k, count = 1; + Console.Write("Enter number of rows\n"); + number = int.Parse(Console.ReadLine()); + count = number - 1; + for (k = 1; k <= number; k++) + { + for (i = 1; i <= count; i++) + Console.Write(" "); + count--; + for (i = 1; i <= 2 * k - 1; i++) + Console.Write("*"); + Console.WriteLine(); + } + count = 1; + for (k = 1; k <= number - 1; k++) + { + for (i = 1; i <= count; i++) + Console.Write(" "); + count++; + for (i = 1; i <= 2 * (number - k) - 1; i++) + Console.Write("*"); + Console.WriteLine(); + } + Console.ReadLine(); + } +} + +/* +Enter number of rows +3 + * + *** +***** + *** + * \ No newline at end of file diff --git a/c-sharp/_Basic/C# Program to Read a Grade & Display the Equivalent Description.cs b/c-sharp/_Basic/C# Program to Read a Grade & Display the Equivalent Description.cs new file mode 100644 index 0000000..da509b5 --- /dev/null +++ b/c-sharp/_Basic/C# Program to Read a Grade & Display the Equivalent Description.cs @@ -0,0 +1,41 @@ +/* + * C# Program to Read a Grade & Display the Equivalent Description + */ +using System; +using System.IO; +class program +{ + public static void Main() + { + char grade; + Console.WriteLine("Enter the Grade in UpperCase \n"); + grade = Convert.ToChar(Console.ReadLine()); + switch (grade) + { + case 'S': + Console.WriteLine(" SUPER"); + break; + case 'A': + Console.WriteLine(" VERY GOOD"); + break; + case 'B': + Console.WriteLine(" FAIR"); + break; + case 'Y': + Console.WriteLine(" ABSENT"); + break; + case 'F': + Console.WriteLine(" FAIL"); + break; + default: + Console.WriteLine("ERROR IN GRADE \n"); + break; + Console.ReadLine(); + } + } +} + +/* +Enter the Grade in UpperCase +A + VERY GOOD \ No newline at end of file diff --git a/c-sharp/_Basic/C# Program to Swap 2 Numbers.cs b/c-sharp/_Basic/C# Program to Swap 2 Numbers.cs new file mode 100644 index 0000000..2f24378 --- /dev/null +++ b/c-sharp/_Basic/C# Program to Swap 2 Numbers.cs @@ -0,0 +1,35 @@ +/* + * C# Program to Swap two Numbers + */ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +namespace Program +{ +class Program +{ + static void Main(string[] args) + { + int num1, num2, temp; + Console.Write("\nEnter the First Number : "); + num1 = int.Parse(Console.ReadLine()); + Console.Write("\nEnter the Second Number : "); + num2 = int.Parse(Console.ReadLine()); + temp = num1; + num1 = num2; + num2 = temp; + Console.Write("\nAfter Swapping : "); + Console.Write("\nFirst Number : "+num1); + Console.Write("\nSecond Number : "+num2); + Console.Read(); + } +} +} + +/* +Enter the First Number : 23 +Enter the Second Number : 25 +After Swapping : +First Number : 25 +Second Number : 23 \ No newline at end of file diff --git a/c-sharp/_Basic/C# Program to Swap the Contents of two Numbers using Bitwise XOR Operation.cs b/c-sharp/_Basic/C# Program to Swap the Contents of two Numbers using Bitwise XOR Operation.cs new file mode 100644 index 0000000..61483e1 --- /dev/null +++ b/c-sharp/_Basic/C# Program to Swap the Contents of two Numbers using Bitwise XOR Operation.cs @@ -0,0 +1,27 @@ +/* + * C# Program to Swap the Contents of two Numbers using Bitwise XOR Operation + */ +using System; +class program +{ + public static void Main() + { + int i, k; + Console.WriteLine("Enter two integers \n"); + i = int.Parse(Console.ReadLine()); + k = int.Parse(Console.ReadLine()); + Console.WriteLine("\n Before swapping i= {0} and k = {1}", i, k); + i = i ^ k; + k = i ^ k; + i = i ^ k; + Console.WriteLine("\n After swapping i= {0} and k = {1}", i, k); + Console.ReadLine(); + } +} + +/* +Enter two integers +23 +34 +Before swapping i= 23 and k = 34 +After swapping i= 34 and k = 23 \ No newline at end of file diff --git a/c-sharp/_Basic/C# Sharp program that takes a number as input and print its multiplication table.cs b/c-sharp/_Basic/C# Sharp program that takes a number as input and print its multiplication table.cs new file mode 100644 index 0000000..52241fe --- /dev/null +++ b/c-sharp/_Basic/C# Sharp program that takes a number as input and print its multiplication table.cs @@ -0,0 +1,31 @@ +using System; +public class Exercise8 +{ + public static void Main() + { + int x; + int result; + Console.WriteLine("Enter a number:"); + x = Convert.ToInt32(Console.ReadLine() ); + result = x * 1; + Console.WriteLine("The table is : {0} x {1} = {2}", x, 1, result); + result = x * 2; + Console.WriteLine(" : {0} x {1} = {2}", x, 2, result); + result = x * 3; + Console.WriteLine(" : {0} x {1} = {2}", x, 3, result); + result = x * 4; + Console.WriteLine(" : {0} x {1} = {2}", x, 4, result); + result = x * 5; + Console.WriteLine(" : {0} x {1} = {2}", x, 5, result); + result = x * 6; + Console.WriteLine(" : {0} x {1} = {2}", x, 6, result); + result = x * 7; + Console.WriteLine(" : {0} x {1} = {2}", x, 7, result); + result = x * 8; + Console.WriteLine(" : {0} x {1} = {2}", x, 8, result); + result = x * 9; + Console.WriteLine(" : {0} x {1} = {2}", x, 9, result); + result = x * 10; + Console.WriteLine(" : {0} x {1} = {2}", x, 10, result); + } +} \ No newline at end of file diff --git a/c-sharp/_Basic/C# Sharp program that takes an age (for example 20) as input and prints something as.cs b/c-sharp/_Basic/C# Sharp program that takes an age (for example 20) as input and prints something as.cs new file mode 100644 index 0000000..cc0178b --- /dev/null +++ b/c-sharp/_Basic/C# Sharp program that takes an age (for example 20) as input and prints something as.cs @@ -0,0 +1,13 @@ +C# Sharp program that takes an age (for example 20) as input and prints something as "You look older than 20. + + using System; +public class Exercise11 +{ + public static void Main() + { + int age; + Console.Write("Enter your age "); + age = Convert.ToInt32(Console.ReadLine()); + Console.Write("You look younger than {0} ",age); + } +} \ No newline at end of file diff --git a/c-sharp/_Basic/C# Sharp program that takes four numbers as input to calculate and print the average.cs b/c-sharp/_Basic/C# Sharp program that takes four numbers as input to calculate and print the average.cs new file mode 100644 index 0000000..38f0a9b --- /dev/null +++ b/c-sharp/_Basic/C# Sharp program that takes four numbers as input to calculate and print the average.cs @@ -0,0 +1,19 @@ +using System; +public class Exercise9 +{ + public static void Main() + { + int number1,number2,number3,number4; + Console.Write("Enter the First number: "); + number1 = Convert.ToInt32(Console.ReadLine()); + Console.Write("Enter the Second number: "); + number2 = Convert.ToInt32(Console.ReadLine()); + Console.Write("Enter the third number: "); + number3 = Convert.ToInt32(Console.ReadLine()); + Console.Write("Enter the four number: "); + number4 = Convert.ToInt32(Console.ReadLine()); + int result = (number1 + number2 + number3 + number4) / 4; + Console.WriteLine("The average of {0} , {1} , {2} , {3} is: {4} ", + number1, number2, number3, number4, result); + } +} \ No newline at end of file diff --git a/c-sharp/_Basic/C# Sharp program to convert from celsius degrees to Kelvin and Fahrenheit.cs b/c-sharp/_Basic/C# Sharp program to convert from celsius degrees to Kelvin and Fahrenheit.cs new file mode 100644 index 0000000..5faec92 --- /dev/null +++ b/c-sharp/_Basic/C# Sharp program to convert from celsius degrees to Kelvin and Fahrenheit.cs @@ -0,0 +1,11 @@ +using System; +public class Exercise14 +{ + public static void Main( ) + { + Console.Write("Enter the amount of celsius: "); + int celsius = Convert.ToInt32(Console.ReadLine()); + Console.WriteLine("Kelvin = {0}", celsius + 273); + Console.WriteLine("Fahrenheit = {0}", celsius * 18 / 10 + 32); + } +} \ No newline at end of file diff --git a/c-sharp/_Basic/C# Sharp program to print Hello and your name in a separate line.cs b/c-sharp/_Basic/C# Sharp program to print Hello and your name in a separate line.cs new file mode 100644 index 0000000..d18d03b --- /dev/null +++ b/c-sharp/_Basic/C# Sharp program to print Hello and your name in a separate line.cs @@ -0,0 +1,12 @@ +public class Exercise1 +{ + public static void Main( ) + { + System.Console.WriteLine("Hello"); + System.Console.WriteLine("Alexandra Abramov!"); + } +} +Output : + +Hello +Alexandra Abramov \ No newline at end of file diff --git a/c-sharp/_Basic/C# Sharp program to print on screen the output of adding, subtracting, multiplying and dividing of two numbers which will be entered by the user.cs b/c-sharp/_Basic/C# Sharp program to print on screen the output of adding, subtracting, multiplying and dividing of two numbers which will be entered by the user.cs new file mode 100644 index 0000000..b1679f5 --- /dev/null +++ b/c-sharp/_Basic/C# Sharp program to print on screen the output of adding, subtracting, multiplying and dividing of two numbers which will be entered by the user.cs @@ -0,0 +1,16 @@ +using System; +public class Exercise7 +{ + public static void Main() + { + Console.Write("Enter a number: "); + int num1= Convert.ToInt32(Console.ReadLine()); + Console.Write("Enter another number: "); + int num2= Convert.ToInt32(Console.ReadLine()); + Console.WriteLine("{0} + {1} = {2}", num1, num2, num1+num2); + Console.WriteLine("{0} - {1} = {2}", num1, num2, num1-num2); + Console.WriteLine("{0} x {1} = {2}", num1, num2, num1*num2); + Console.WriteLine("{0} / {1} = {2}", num1, num2, num1/num2); + Console.WriteLine("{0} mod {1} = {2}", num1, num2, num1%num2); + } +} \ No newline at end of file diff --git a/c-sharp/_Basic/C# Sharp program to print the output of multiplication of three numbers which will be entered by the user.cs b/c-sharp/_Basic/C# Sharp program to print the output of multiplication of three numbers which will be entered by the user.cs new file mode 100644 index 0000000..3b54feb --- /dev/null +++ b/c-sharp/_Basic/C# Sharp program to print the output of multiplication of three numbers which will be entered by the user.cs @@ -0,0 +1,17 @@ +using System; +public class Exercise6 +{ + public static void Main() + { + int num1, num2, num3; + Console.Write("Input the first number to multiply: "); + num1 = Convert.ToInt32(Console.ReadLine()); + Console.Write("Input the second number to multiply: "); + num2 = Convert.ToInt32(Console.ReadLine()); + Console.Write("Input the third number to multiply: "); + num3 = Convert.ToInt32(Console.ReadLine()); + int result = num1 * num2 * num3; + Console.WriteLine("Output: {0} x {1} x {2} = {3}", + num1, num2, num3, result); + } +} \ No newline at end of file diff --git a/c-sharp/_Basic/C# Sharp program to print the result of dividing two numbers.cs b/c-sharp/_Basic/C# Sharp program to print the result of dividing two numbers.cs new file mode 100644 index 0000000..8a6df63 --- /dev/null +++ b/c-sharp/_Basic/C# Sharp program to print the result of dividing two numbers.cs @@ -0,0 +1,7 @@ +public class Exercise3 +{ + public static void Main() + { + System.Console.WriteLine(36/6); + } +} \ No newline at end of file diff --git a/c-sharp/_Basic/C# Sharp program to print the result of the specified operations.cs b/c-sharp/_Basic/C# Sharp program to print the result of the specified operations.cs new file mode 100644 index 0000000..618c43d --- /dev/null +++ b/c-sharp/_Basic/C# Sharp program to print the result of the specified operations.cs @@ -0,0 +1,32 @@ +/* + +Write a C# Sharp program to print the result of the specified operations. + +Test data: +• -1 + 4 * 6 +• ( 35+ 5 ) % 7 +• 14 + -4 * 6 / 11 +• 2 + 15 / 6 * 1 - 7 % 2 +Expected Output: + +23 +5 +12 +3 + +*/ + +public class Exercise4 +{ + public static void Main() + { + System.Console.WriteLine(-1+4*6); + //-1 + 24 = 23 + System.Console.WriteLine((35+5)%7); + //40 % 7 = 5 (remainder of 40/7) + System.Console.WriteLine(14+-4*6/11); + //14 - (24/11)= 14 - 2 = 12 + System.Console.WriteLine(2+15/6*1-7%2); + //2 + (15/6) - remainder of (7/2) = 2 + 2 - 1 = 4 - 1 = 3 + } +} \ No newline at end of file diff --git a/c-sharp/_Basic/C# Sharp program to print the sum of two numbers.cs b/c-sharp/_Basic/C# Sharp program to print the sum of two numbers.cs new file mode 100644 index 0000000..997157f --- /dev/null +++ b/c-sharp/_Basic/C# Sharp program to print the sum of two numbers.cs @@ -0,0 +1,7 @@ +public class Exercise2 +{ + public static void Main() + { + System.Console.WriteLine(15+17); + } +} \ No newline at end of file diff --git a/c-sharp/_Basic/C# Sharp program to swap two numbers.cs b/c-sharp/_Basic/C# Sharp program to swap two numbers.cs new file mode 100644 index 0000000..4478a67 --- /dev/null +++ b/c-sharp/_Basic/C# Sharp program to swap two numbers.cs @@ -0,0 +1,19 @@ +using System; +public class Exercise5 +{ + public static void Main(string[] args) + { + int number1, number2, temp; + Console.Write("\nInput the First Number : "); + number1 = int.Parse(Console.ReadLine()); + Console.Write("\nInput the Second Number : "); + number2 = int.Parse(Console.ReadLine()); + temp = number1; + number1 = number2; + number2 = temp; + Console.Write("\nAfter Swapping : "); + Console.Write("\nFirst Number : "+number1); + Console.Write("\nSecond Number : "+number2); + Console.Read(); + } +} \ No newline at end of file diff --git a/c-sharp/_Basic/C# Sharp program to that takes three numbers(x,y,z) as input and print the output of (x+y)úz and xúy + yúz.cs b/c-sharp/_Basic/C# Sharp program to that takes three numbers(x,y,z) as input and print the output of (x+y)úz and xúy + yúz.cs new file mode 100644 index 0000000..378744e --- /dev/null +++ b/c-sharp/_Basic/C# Sharp program to that takes three numbers(x,y,z) as input and print the output of (x+y)úz and xúy + yúz.cs @@ -0,0 +1,16 @@ +using System; +public class Exercise10 +{ + public static void Main() + { + int number1, number2, number3; + Console.Write("Enter first number - "); + number1 = Convert.ToInt32(Console.ReadLine()); + Console.Write("Enter second number - "); + number2 = Convert.ToInt32(Console.ReadLine()); + Console.Write("Enter third number - "); + number3 = Convert.ToInt32(Console.ReadLine()); + Console.Write("Result of specified numbers {0}, {1} and {2}, (x+y)·z is {3} and x·y + y·z is {4}\n\n", + number1, number2, number3, ((number1+number2)*number3), (number1*number2+number2*number3)); + } +} \ No newline at end of file diff --git a/c-sharp/_Basic/C# program that takes a number as input and then displays a rectangle of 3 columns wide and 5 rows tall using that digit.cs b/c-sharp/_Basic/C# program that takes a number as input and then displays a rectangle of 3 columns wide and 5 rows tall using that digit.cs new file mode 100644 index 0000000..e3b753c --- /dev/null +++ b/c-sharp/_Basic/C# program that takes a number as input and then displays a rectangle of 3 columns wide and 5 rows tall using that digit.cs @@ -0,0 +1,15 @@ +using System; +public class Exercise13 +{ + public static void Main() + { + int x; + Console.Write("Enter a number: "); + x=Convert.ToInt32(Console.ReadLine()); + Console.WriteLine("{0}{0}{0}",x); + Console.WriteLine("{0} {0}",x); + Console.WriteLine("{0} {0}",x); + Console.WriteLine("{0} {0}",x); + Console.WriteLine("{0}{0}{0}",x); + } +} \ No newline at end of file diff --git a/c-sharp/_Basic/C# program to that takes a number as input and display it four times in a row (separated by blank spaces), and then four times in the next row, with no separation.cs b/c-sharp/_Basic/C# program to that takes a number as input and display it four times in a row (separated by blank spaces), and then four times in the next row, with no separation.cs new file mode 100644 index 0000000..9726806 --- /dev/null +++ b/c-sharp/_Basic/C# program to that takes a number as input and display it four times in a row (separated by blank spaces), and then four times in the next row, with no separation.cs @@ -0,0 +1,29 @@ +using System; +public class Exercise12 +{ + public static void Main() + { + int num; + Console.WriteLine("Enter a digit: "); + num = Convert.ToInt32( Console.ReadLine() ); + // Part A: "num num num num" using Write + Console.Write( num ); + Console.Write(" "); + Console.Write( num ); + Console.Write(" "); + Console.Write( num ); + Console.Write(" "); + Console.Write( num ); + Console.WriteLine(); + // Part B: "numnumnumnum" using Write + Console.Write( num ); + Console.Write( num ); + Console.Write( num ); + Console.WriteLine( num ); + Console.WriteLine(); + // Part C: "num num num num" using {0} + Console.WriteLine("{0} {0} {0} {0}", num); + // Part D: "numnumnumnum" using {0} + Console.WriteLine("{0}{0}{0}{0}", num); + } +} \ No newline at end of file diff --git a/c/Arrays/C Program for Addition of all elements of array.c b/c/Arrays/C Program for Addition of all elements of array.c new file mode 100644 index 0000000..f877219 --- /dev/null +++ b/c/Arrays/C Program for Addition of all elements of array.c @@ -0,0 +1,19 @@ +/*Addition of all elements of array*/ +#include +#define MAX 100 +void main() +{ + int arr[MAX],n,i,sum=0; + printf("Enter size of Array: "); + scanf("%d",&n); + printf("Enter %d elements\n",n); + for(i=0; i +#include + +void main() +{ + char n[20] ; + int i, j ; + clrscr(); + printf("Enter a positive number having a decimal point: "); + gets(n); + for(i=0 ; n[i]!='\0' ; i++) ; + for(j=0 ; n[j]!='.' ; j++) ; + printf("Number of digits to the left of decimal point is %d \n", j) ; + printf("Number of digits to the right of decimal point is %d", i-j-1) ; + getch(); +} + + +/* +Output: + +Enter a positive number having a decimal point: 2451.87 +Number of digits to the left of decimal point is 4 +Number of digits to the right of decimal point is 2 +*/ diff --git a/c/Arrays/C Program that reads a number greater than or equal to 1000 from the user..c b/c/Arrays/C Program that reads a number greater than or equal to 1000 from the user..c new file mode 100644 index 0000000..cfeed24 --- /dev/null +++ b/c/Arrays/C Program that reads a number greater than or equal to 1000 from the user..c @@ -0,0 +1,26 @@ +/* String remove comma - Program that reads a number greater than or equal to 1000 from the user. The user enters a comma in the input. Print the number without the comma */ + +#include +#include + +void main() +{ + int i ; + char n[20] ; + clrscr() ; + printf("Enter a number greater than or equal to 1000: ") ; + gets(n) ; + printf("Number without comma is:") ; + for(i=0 ; n[i]!='\0' ; i++) + if(n[i] != ',') + putchar(n[i]) ; + getch(); +} + +/* +Output: + +Enter a number greater than or equal to 1000: 2,46,798 +Number without comma is:246798 +*/ + diff --git a/c/Arrays/C Program that will read a string and rewrite it in alphabetical order..c b/c/Arrays/C Program that will read a string and rewrite it in alphabetical order..c new file mode 100644 index 0000000..1d0687b --- /dev/null +++ b/c/Arrays/C Program that will read a string and rewrite it in alphabetical order..c @@ -0,0 +1,35 @@ +/* String Sort - Program that will read a string and rewrite it in alphabetical order. For example, the word 'string' should be written as 'ginrst' */ + +#include +#include +#include +#include + +void main() +{ + char x[50], temp ; + int i, j, n ; + clrscr(); + printf("Enter a string: ") ; + gets(x) ; + n=strlen(x) ; + for(i=0 ; i tolower(x[j+1]) ) + { + temp=x[j] ; + x[j]=x[j+1] ; + x[j+1]=temp ; + } + printf("Given string in alphabetical order is %s ", x) ; + getch(); +} + +/* +Output: + +Enter a string: Programming +Given string in alphabetical order is aggimmnoPrr +*/ + +/* The above output (look at P) shows that our logic of sorting is NOT CASE SENSITIVE */ \ No newline at end of file diff --git a/c/Arrays/C Program to Accept an Array & Swap Elements using Pointers.c b/c/Arrays/C Program to Accept an Array & Swap Elements using Pointers.c new file mode 100644 index 0000000..d1c7a9c --- /dev/null +++ b/c/Arrays/C Program to Accept an Array & Swap Elements using Pointers.c @@ -0,0 +1,52 @@ +/*This C Program accepts array & swap elements using pointers. The program is used to swap the elements of a given array and swapping is done using pointers.*/ + +/* + * C program to accept an array of 10 elements and swap 3rd element + * with 4th element using pointers and display the results. + */ +#include +void swap34(float *ptr1, float *ptr2); + +void main() +{ + float x[10]; + int i, n; + printf("How many Elements...\n"); + scanf("%d", &n); + printf("Enter Elements one by one\n"); + for (i = 0; i < n; i++) + { + scanf("%f", x + i); + } + /* Function call:Interchanging 3rd element by 4th */ + swap34(x + 2, x + 3); + printf("\nResultant Array...\n"); + for (i = 0; i < n; i++) + { + printf("X[%d] = %f\n", i, x[i]); + } +} +/* Function to swap the 3rd element with the 4th element in the array */ +void swap34(float *ptr1, float *ptr2 ) +{ + float temp; + temp = *ptr1; + *ptr1 = *ptr2; + *ptr2 = temp; +} + +/* + +How many Elements... +4 +Enter Elements one by one +23 +67 +45 +15 + +Resultant Array... +X[0] = 23.000000 +X[1] = 67.000000 +X[2] = 15.000000 +X[3] = 45.000000 \ No newline at end of file diff --git a/c/Arrays/C Program to Calculate Sum & Average of an Array.c b/c/Arrays/C Program to Calculate Sum & Average of an Array.c new file mode 100644 index 0000000..2821830 --- /dev/null +++ b/c/Arrays/C Program to Calculate Sum & Average of an Array.c @@ -0,0 +1,84 @@ +/*C Program to Calculate Sum & Average of an Array + +This C Program calculates the sum & average of an array. It declares an array and then add the array elements and finds the average of the array.*/ + +/* + * C program to read N integers into an array A and + * a) Find the sum of negative numbers + * b) Find the sum of positive numbers + * c) Find the average of all numbers + * Display the results with suitable headings + */ +#include +#define MAXSIZE 10 + +void main() +{ + int array[MAXSIZE]; + int i, num, negative_sum = 0, positive_sum = 0; + float total = 0.0, average; + printf ("Enter the value of N \n"); + scanf("%d", &num); + printf("Enter %d numbers (-ve, +ve and zero) \n", num); + for (i = 0; i < num; i++) + { + scanf("%d", &array[i]); + } + printf("Input array elements \n"); + for (i = 0; i < num; i++) + { + printf("%+3d\n", array[i]); + } + /* Summation starts */ + for (i = 0; i < num; i++) + { + if (array[i] < 0) + { + negative_sum = negative_sum + array[i]; + } + else if (array[i] > 0) + { + positive_sum = positive_sum + array[i]; + } + else if (array[i] == 0) + { + ; + } + total = total + array[i] ; + } + average = total / num; + printf("\n Sum of all negative numbers = %d\n", negative_sum); + printf("Sum of all positive numbers = %d\n", positive_sum); + printf("\n Average of all input numbers = %.2f\n", average); +} + +/* +Enter the value of N +10 +Enter 10 numbers (-ve, +ve and zero) +-8 +9 +-100 +-80 +90 +45 +-23 +-1 +0 +16 +Input array elements + -8 + +9 +-100 +-80 ++90 ++45 +-23 + -1 + +0 ++16 + +Sum of all negative numbers = -212 +Sum of all positive numbers = 160 + +Average of all input numbers = -5.20 \ No newline at end of file diff --git a/c/Arrays/C Program to Calculate Sum of all Elements of an Array using Pointers as Arguments.c b/c/Arrays/C Program to Calculate Sum of all Elements of an Array using Pointers as Arguments.c new file mode 100644 index 0000000..cf68c30 --- /dev/null +++ b/c/Arrays/C Program to Calculate Sum of all Elements of an Array using Pointers as Arguments.c @@ -0,0 +1,28 @@ +/*This C Program calculate sum of all elements of an array using pointers as arguments. The program calls a function to add the addition and passes the array argument as a pointer.*/ + +/* + * C program to find the sum of all elements of an array using + * pointers as arguments. + */ +#include + +void main() +{ + static int array[5] = { 200, 400, 600, 800, 1000 }; + int sum; + int addnum(int *ptr); + sum = addnum(array); + printf("Sum of all array elements = %5d\n", sum); +} +int addnum(int *ptr) +{ + int index, total = 0; + for (index = 0; index < 5; index++) + { + total += *(ptr + index); + } + return(total); +} + +/* +Sum of all array elements = 3000 \ No newline at end of file diff --git a/c/Arrays/C Program to Calculate median of an array of n numbers.c b/c/Arrays/C Program to Calculate median of an array of n numbers.c new file mode 100644 index 0000000..afe71ae --- /dev/null +++ b/c/Arrays/C Program to Calculate median of an array of n numbers.c @@ -0,0 +1,66 @@ +/* Median - Calculate median of an array of n numbers */ + +#include +#include +#include + +float median(int x[ ], int n) ; +void sort(int x[ ], int n) ; + +void main() +{ + int i, n, x[50] ; + clrscr(); + printf("Enter the number of elements: ") ; + scanf("%d", &n) ; + printf("Enter the elements: \n") ; + for(i=0 ; i x[j+1]) + { + temp=x[j] ; + x[j]=x[j+1] ; + x[j+1]=temp ; + } +} + +/* +Output1: + +Enter the number of elements: 5 +Enter the elements: +2 8 4 9 6 +The median of given numbers is 6.000000 + +Output2: + +Enter the number of elements: 6 +Enter the elements: +2 9 4 8 6 7 +The median of given numbers is 6.500000 +*/ + + + + diff --git a/c/Arrays/C Program to Calculate standard deviation of n numbers.c b/c/Arrays/C Program to Calculate standard deviation of n numbers.c new file mode 100644 index 0000000..75663d4 --- /dev/null +++ b/c/Arrays/C Program to Calculate standard deviation of n numbers.c @@ -0,0 +1,36 @@ +/* Standard Deviation - Calculate standard deviation of n numbers */ + +#include +#include +#include + +void main() +{ + int i, n, x[50] ; + float avg, std, sum = 0, s = 0 ; + clrscr() ; + printf("Enter the number of elements: ") ; + scanf("%d", &n) ; + printf("Enter the elements: \n") ; + for(i=0 ; i +#include + +void main() +{ + int i, n, less=0, more=0 ; + float x[50], sum=0, avg ; + clrscr() ; + printf("Enter the number of elements: ") ; + scanf("%d", &n) ; + printf("Enter the elements: \n") ; + for(i=0 ; iavg) + more++; + if(x[i] +#include + +void main() +{ + int i, n, sum = 0; + int *a; + printf("Enter the size of array A \n"); + scanf("%d", &n); + a = (int *) malloc(n * sizeof(int)); + printf("Enter Elements of First List \n"); + for (i = 0; i < n; i++) + { + scanf("%d", a + i); + } + + +int main(void) +{ + int array[5], b, c; + for (b = 0; b < 10 && (scanf("%d", &c)); b++) + array[b] = c; + for (b = 0; b < 15; b++) + printf("%d ", array[b]); + return 0; +} + +/* +12 +23 +56 +12 +14 +19 +23 +12 23 56 12 14 23 6 134513824 0 -1081194040 11672807 1 -1081193996 -1081193988 -1216161720 \ No newline at end of file diff --git a/c/Arrays/C Program to Compute the Sum of two One-Dimensional Arrays using Malloc.c b/c/Arrays/C Program to Compute the Sum of two One-Dimensional Arrays using Malloc.c new file mode 100644 index 0000000..f7d7141 --- /dev/null +++ b/c/Arrays/C Program to Compute the Sum of two One-Dimensional Arrays using Malloc.c @@ -0,0 +1,62 @@ +/*This C Program computes the sum of two one-dimensional arrays using malloc. The program allocates 2 one-dimentional arrays using malloc() call and then does the addition and stores the result into 3rd array. The 3rd array is also defined using malloc() call.*/ + +/* + * C program to find the sum of two one-dimensional arrays using + * Dynamic Memory Allocation + */ +#include +#include +#include + +void main() +{ + int i, n; + int *a, *b, *c; + printf("How many Elements in each array...\n"); + scanf("%d", &n); + a = (int *)malloc(n * sizeof(int)); + b = (int *)malloc(n * sizeof(int)); + c = (int *)malloc(n * sizeof(int)); + printf("Enter Elements of First List\n"); + for (i = 0; i < n; i++) + { + scanf("%d", a + i); + } + printf("Enter Elements of Second List\n"); + for (i = 0; i < n; i++) + { + scanf("%d", b + i); + } + for (i = 0; i < n; i++) + { + *(c + i) = *(a + i) + *(b + i); + } + printf("Resultant List is\n"); + for (i = 0; i < n; i++) + { + printf("%d\n", *(c + i)); + } +} + + +/* +How many Elements in each array... +5 +Enter Elements of First List +23 +45 +67 +12 +90 +Enter Elements of Second List +87 +56 +90 +45 +10 +Resultant List is +110 +101 +157 +57 +100 \ No newline at end of file diff --git a/c/Arrays/C Program to Concat Two Strings without Using Library Function.c b/c/Arrays/C Program to Concat Two Strings without Using Library Function.c new file mode 100644 index 0000000..641237d --- /dev/null +++ b/c/Arrays/C Program to Concat Two Strings without Using Library Function.c @@ -0,0 +1,23 @@ + #include + #include + void concat(char[], char[]); + int main() { + char s1[50], s2[30]; + printf("\nEnter String 1 :"); + gets(s1); + printf("\nEnter String 2 :"); + gets(s2); + concat(s1, s2); + printf("\nConcated string is :%s", s1); + return (0); + } + void concat(char s1[], char s2[]) { + int i, j; + i = strlen(s1); + for (j = 0; s2[j] != '\0'; i++, j++) { + s1[i] = s2[j]; + } + s1[i] = '\0'; + } + + diff --git a/c/Arrays/C Program to Cyclically Permute the Elements of an Array.c b/c/Arrays/C Program to Cyclically Permute the Elements of an Array.c new file mode 100644 index 0000000..2052059 --- /dev/null +++ b/c/Arrays/C Program to Cyclically Permute the Elements of an Array.c @@ -0,0 +1,42 @@ +/*This C Program cyclically permutes the elements of an array. This program first accepts an array. Assume there are 4 elements in an array. It takes 2 element as a first elment in an array and so on till the last element of the given array. Now here first element of an array becomes last element in an array during cyclical permutation.*/ + +/* + * C program to cyclically permute the elements of an array A. + * i.e. the content of A1 become that of A2. And A2 contains + * that of A3 & so on as An contains A1 + */ +#include + +void main () +{ + int i, n, number[30]; + printf("Enter the value of the n = "); + scanf("%d", &n); + printf("Enter the numbers\n"); + for (i = 0; i < n; ++i) + { + scanf("%d", &number[i]); + } + number[n] = number[0]; + for (i = 0; i < n; ++i) + { + number[i] = number[i + 1]; + } + printf("Cyclically permuted numbers are given below \n"); + for (i = 0; i < n; ++i) + printf("%d\n", number[i]); +} + +/* + +Enter the value of the n = 4 +Enter the numbers +3 +40 +100 +68 +Cyclically permuted numbers are given below +40 +100 +68 +3 \ No newline at end of file diff --git a/c/Arrays/C Program to Delete the Specified Integer from an Array.c b/c/Arrays/C Program to Delete the Specified Integer from an Array.c new file mode 100644 index 0000000..00e5556 --- /dev/null +++ b/c/Arrays/C Program to Delete the Specified Integer from an Array.c @@ -0,0 +1,69 @@ +/* + * C program to accept an array of integers and delete the + * specified integer from the list + */ +#include + +void main() +{ + int vectorx[10]; + int i, n, pos, element, found = 0; + printf("Enter how many elements\n"); + scanf("%d", &n); + printf("Enter the elements\n"); + for (i = 0; i < n; i++) + { + scanf("%d", &vectorx[i]); + } + printf("Input array elements are\n"); + for (i = 0; i < n; i++) + { + printf("%d\n", vectorx[i]); + } + printf("Enter the element to be deleted\n"); + scanf("%d", &element); + for (i = 0; i < n; i++) + { + if (vectorx[i] == element) + { + found = 1; + pos = i; + break; + } + } + if (found == 1) + { + for (i = pos; i < n - 1; i++) + { + vectorx[i] = vectorx[i + 1]; + } + printf("The resultant vector is \n"); + for (i = 0; i < n - 1; i++) + { + printf("%d\n", vectorx[i]); + } + } + else + printf("Element %d is not found in the vector\n", element); +} + +/* + +Enter how many elements +4 +Enter the elements +345 +234 +678 +987 +Input array elements are +345 +234 +678 +987 +Enter the element to be deleted +234 +The resultant vector is +345 +678 +987 \ No newline at end of file diff --git a/c/Arrays/C Program to Develop a function that takes as arguments 3 matrices a , b , c and 3 integer variables l,m,n..c b/c/Arrays/C Program to Develop a function that takes as arguments 3 matrices a , b , c and 3 integer variables l,m,n..c new file mode 100644 index 0000000..e22e87b --- /dev/null +++ b/c/Arrays/C Program to Develop a function that takes as arguments 3 matrices a , b , c and 3 integer variables l,m,n..c @@ -0,0 +1,87 @@ +/* Matrix multiplication - Develop a function that takes as arguments 3 matrices a , b , c and 3 integer variables l,m,n. Calculate product of a and b and store the result in c. Also write a main routine which will test whether the input matrices a and b are conformal to multiplication - May 2013 */ + +#include +#include + +void read(int x[ ][10], int nr, int nc) ; +void multiply(int a[ ][10], int b[ ][10], int c[ ][10], int l, int m, int n) ; +void show(int y[ ][10], int nr, int nc) ; + + +void main() +{ + int a[10][10], b[10][10], c[10][10], nra, nca, nrb, ncb ; + clrscr(); + printf("Enter the number of rows and columns of first matrix: "); + scanf("%d %d", &nra, &nca) ; + printf("Enter the number of rows and columns of second matrix: "); + scanf("%d %d", &nrb, &ncb) ; + if(nca==nrb) + { + printf("Enter elements of first matrix row-wise: \n"); + read(a,nra,nca); + printf("Enter elements of second matrix row-wise: \n"); + read(b,nrb,ncb); + multiply(a,b,c,nra,nca,ncb); + printf("Result of matrix multiplication is: \n"); + show(c,nra,ncb); + } + else + printf("Two given Matrices do not conform to multiplication"); + getch(); +} + +void read(int x[ ][10], int nr, int nc) +{ + int r, c ; + for(r=0 ; r + +int maximum_difference(int array[], int arr_size) +{ + int max_diff = array[1] - array[0]; + int i, j; + for (i = 0; i < arr_size; i++) + { + for (j = i + 1; j < arr_size; j++) + { + if (array[j] - array[i] > max_diff) + max_diff = array[j] - array[i]; + } + } + return max_diff; +} + +int main() +{ + int array[] = {10, 15, 90, 200, 110}; + printf("Maximum difference is %d", maximum_difference(array, 5)); + getchar(); + return 0; +} + +/* +Maximum difference is 190 \ No newline at end of file diff --git a/c/Arrays/C Program to Find Ceiling & Floor of X given a Sorted Array & a value X.c b/c/Arrays/C Program to Find Ceiling & Floor of X given a Sorted Array & a value X.c new file mode 100644 index 0000000..0c40f29 --- /dev/null +++ b/c/Arrays/C Program to Find Ceiling & Floor of X given a Sorted Array & a value X.c @@ -0,0 +1,42 @@ +/* + * C Program to Find Ceiling & Floor of X given a Sorted Array & a value X + */ +#include + +/* Function to get index of ceiling of x in arr[low..high] */ +int ceilSearch(int arr[], int low, int high, int x) +{ + int i; + /* If x is smaller than or equal to first element,then return the first element */ + if (x <= arr[low]) + return low; + /* Otherwise, linearly search for ceil value */ + for (i = low; i < high; i++) + { + if (arr[i] == x) + return i; + /* if x lies between arr[i] and arr[i+1] including arr[i+1], then return arr[i+1] */ + if (arr[i] < x && arr[i + 1] >= x) + return i + 1; + } + /* If we reach here then x is greater than the last element of the array, return -1 in this case */ + return -1; +} + +int main() +{ + int arr[] = {1, 2, 8, 10, 10, 12, 19}; + int n = sizeof(arr)/sizeof(arr[0]); + int x = 3; + int index = ceilSearch(arr, 0, n-1, x); + if (index == -1) + printf("Ceiling of %d doesn't exist in array ", x); + else + printf("ceiling of %d is %d", x, arr[index]); + getchar(); + return 0; +} + +/* + +ceiling of 3 is 8 \ No newline at end of file diff --git a/c/Arrays/C Program to Find Union & Intersection of 2 Arrays.c b/c/Arrays/C Program to Find Union & Intersection of 2 Arrays.c new file mode 100644 index 0000000..45d9f98 --- /dev/null +++ b/c/Arrays/C Program to Find Union & Intersection of 2 Arrays.c @@ -0,0 +1,197 @@ +/* + * C Program to Find Union & Intersection of 2 Arrays + */ +#include +#define SIZE 5 + +void get_value(int arr[]); +void print_value(int arr[], int n); +void function_sort(int arr[]); +int find_intersection(int array1[], int array2[], int intersection_array[]); +int find_union(int array1[], int array2[], int union_array[]); + +void main() +{ + int array1[SIZE], array2[SIZE], intersection_array[SIZE], union_array[SIZE*2]; + int num_elements; + //input elements of Array1 + printf("\n Enter the elements of Array 1: n"); + get_value(array1); + printf("\n\n Elements of Array 1: "); + print_value(array1, SIZE); + //Sort array 1 + function_sort(array1); + printf("nnSorted elements of Array 1: "); + print_value(array1, SIZE); + //input elements of Array2 + printf("nnEnter the elements of Array 2: n"); + get_value(array2); + printf("\n\n Elements of Array 2: "); + print_value(array2, SIZE); + //Sort array 2 + function_sort(array2); + printf("\n\nSorted elements of Array 2: "); + print_value(array2, SIZE); + //Find Intersection + num_elements = find_intersection(array1, array2, intersection_array); + printf("\n\n Intersection is: "); + print_value(intersection_array, num_elements); + //Find Union + num_elements = find_union(array1, array2, union_array); + printf("\n\n Union is: "); + print_value(union_array, num_elements); +} + +void get_value(int arr[]) +{ + int i, j; + for (i = 0; i < SIZE; i++) + { + j = i + 1; + printf("\n Enter element %d: ", j); + scanf("%d", &arr[i]); + } +} + +void print_value(int arr[], int n) +{ + int i; + printf("{ "); + for (i = 0; i < n; i++) + { + printf("%d ", arr[i]); + } + printf("}"); +} + +void function_sort(int arr[]) +{ + int i, j, temp, swapping; + for (i = 1; i < size; i++) + { + swapping = 0; + for (j = 0; j < size-i; j++) + { + if (arr[j] > arr[j+1]) + { + temp = arr[j]; + arr[j] = arr[j + 1]; + arr[j + 1] = temp; + swapping = 1; + } + } + if (swapping == 0) + { + break; + } + } +} + +int find_intersection(int array1[], int array2[], int intersection_array[]) +{ + int i = 0, j = 0, k = 0; + while ((i < size) && (j < size)) + { + if (array1[i] < array2[j]) + { + i++; + } + else if (array1[i] > array2[j]) + { + j++; + } + else + { + intersection_array[k] = array1[i]; + i++; + j++; + k++; + } + } + return(k); +} + +int find_union(int array1[], int array2[], int union_array[]) +{ + int i = 0, j = 0, k = 0; + while ((i < SIZE) && (j < SIZE)) + { + if (array1[i] < array2[j]) + { + union_array[k] = array1[i]; + i++; + k++; + } + else if (array1[i] > array2[j]) + { + union_array[k] = array2[j]; + j++; + k++; + } + else + { + union_array[k] = array1[i]; + i++; + j++; + k++; + } + } + if (i == SIZE) + { + while (j < SIZE) + { + union_array[k] = array2[j]; + j++; + k++; + } + } + else + { + while (i < SIZE) + { + union_array[k] = array1[i]; + i++; + k++; + } + } + return(k); +} + +/* +Enter the elements of Array 1: + +Enter element 1: 12 + +Enter element 2: 34 + +Enter element 3: 23 + +Enter element 4: 56 + +Enter element 5: 45 + + +Elements of Array 1: { 12 34 23 56 45 } + +Sorted elements of Array 1: { 12 23 34 45 56 } + +Enter the elements of Array 2: + +Enter element 1: 34 + +Enter element 2: 56 + +Enter element 3: 12 + +Enter element 4: 78 + +Enter element 5: 66 + + +Elements of Array 2: { 34 56 12 78 66 } + +Sorted elements of Array 2: { 12 34 56 66 78 } + +Intersection is: { 12 34 56 } + +Union is: { 12 23 34 45 56 66 78 } \ No newline at end of file diff --git a/c/Arrays/C Program to Find how many times a number present in array.c b/c/Arrays/C Program to Find how many times a number present in array.c new file mode 100644 index 0000000..ecbdb67 --- /dev/null +++ b/c/Arrays/C Program to Find how many times a number present in array.c @@ -0,0 +1,36 @@ +/*Find how many times a number present in array*/ +#include +#define MAX 100 +void main() +{ + int arr[MAX],n,i,item,count=0,a[MAX]; + printf("Enter size of Array: "); + scanf("%d",&n); + printf("Enter %d elements\n",n); + for(i=0; i +# define bool int + +bool Morenooftimes(int array[], int n, int x) +{ + int i; + int final_index = n % 2 ? n / 2 : (n / 2 + 1); + for (i = 0; i < final_index; i++) + { + /* check if x is presents more than n/2 times */ + if (array[i] == x && array[i + n / 2] == x) + return 1; + } + return 0; +} + +int main() +{ + int array[] = {10, 15, 15, 12, 17,15}; + int n = sizeof(array) / sizeof(array[0]); + int x = 15; + if (Morenooftimes(array, n, x)) + printf("The given no %d appears more than %d times in array[]", x, n/2); + else + printf("The given no %d does not appear more than %d times in array[]", x, n/2); + getchar(); + return 0; +} + +/* +The given no 15 appears more than 3 times in array[] \ No newline at end of file diff --git a/c/Arrays/C Program to Find maximum and second maximum in an array.c b/c/Arrays/C Program to Find maximum and second maximum in an array.c new file mode 100644 index 0000000..86c44cf --- /dev/null +++ b/c/Arrays/C Program to Find maximum and second maximum in an array.c @@ -0,0 +1,24 @@ +/*Find maximum and second maximum in an array*/ +#include +#define MAX 100 +void main() +{ + int arr[MAX],n,i,max,smax; + printf("Enter size of Array: "); + scanf("%d",&n); + printf("Enter %d elements\n",n); + for(i=0; imax) + { + smax=max; + max=arr[i]; + } + } + printf("Maximum : %d Second Maximum:%d ",max,smax); +} \ No newline at end of file diff --git a/c/Arrays/C Program to Find the Biggest Number in an Array of Numbers using Recursion.c b/c/Arrays/C Program to Find the Biggest Number in an Array of Numbers using Recursion.c new file mode 100644 index 0000000..ac20c66 --- /dev/null +++ b/c/Arrays/C Program to Find the Biggest Number in an Array of Numbers using Recursion.c @@ -0,0 +1,56 @@ +/* + * C Program to find the Biggest Number in an Array of Numbers using + * Recursion + */ +#include + +int large(int[], int, int); + +int main() +{ + int size; + int largest; + int list[20]; + int i; + printf("Enter size of the list:"); + scanf("%d", &size); + printf("Printing the list:\n"); + for (i = 0; i < size ; i++) + { + list[i] = rand() % size; + printf("%d\t", list[i]); + } + if (size == 0) + { + printf("Empty list\n"); + } + else + { + largest = list[0]; + largest = large(list, size - 1, largest); + printf("\nThe largest number in the list is: %d\n", largest); + } +} +int large(int list[], int size, int largest) +{ + if (size == 1) + return largest; + if (size > -1) + { + if (list[size] > largest) + { + largest = list[size]; + } + return(largest = large(list, size - 1, largest)); + } + else + { + return largest; + } +} + +/* +Enter size of the list:8 +Printing the list: +7 6 1 3 1 7 2 4 +The largest number in the list is: 7 diff --git a/c/Arrays/C Program to Find the Largest Number in an Array.c b/c/Arrays/C Program to Find the Largest Number in an Array.c new file mode 100644 index 0000000..1c20a41 --- /dev/null +++ b/c/Arrays/C Program to Find the Largest Number in an Array.c @@ -0,0 +1,33 @@ +/* + * C Program to Find the Largest Number in an Array + */ +#include + +int main() +{ + int array[50], size, i, largest; + printf("\n Enter the size of the array: "); + scanf("%d", &size); + printf("\n Enter %d elements of the array: ", size); + for (i = 0; i < size; i++) + scanf("%d", &array[i]); + largest = array[0]; + for (i = 1; i < size; i++) + { + if (largest < array[i]) + largest = array[i]; + } + printf("\n largest element present in the given array is : %d", largest); + return 0; +} + +/* +Enter the size of the array: 5 + +Enter 5 elements of the array: 12 +56 +34 +78 +100 + +largest element present in the given array is : 100 \ No newline at end of file diff --git a/c/Arrays/C Program to Find the Largest Two Numbers in a given Array.c b/c/Arrays/C Program to Find the Largest Two Numbers in a given Array.c new file mode 100644 index 0000000..1b2a5c5 --- /dev/null +++ b/c/Arrays/C Program to Find the Largest Two Numbers in a given Array.c @@ -0,0 +1,65 @@ +/*This C Program calculates the largest of two numbers in a given Array. First it accepts an array, then compares the elements and finds which is the largest two element in a given array.*/ + +/* + * C program to read in four integer numbers into an array and find the + * average of largest two of the given numbers without sorting the array. + * The program should output the given four numbers and the average. + */ +#include +#define MAX 4 + +void main() +{ + int array[MAX], i, largest1, largest2, temp; + printf("Enter %d integer numbers \n", MAX); + for (i = 0; i < MAX; i++) + { + scanf("%d", &array[i]); + } + printf("Input interger are \n"); + for (i = 0; i < MAX; i++) + { + printf("%5d", array[i]); + } + printf("\n"); + /* assume first element of array is the first larges t*/ + largest1 = array[0]; + /* assume first element of array is the second largest */ + largest2 = array[1]; + if (largest1 < largest2) + { + temp = largest1; + largest1 = largest2; + largest2 = temp; + } + for (i = 2; i < 4; i++) + { + if (array[i] >= largest1) + { + largest2 = largest1; + largest1 = array[i]; + } + else if (array[i] > largest2) + { + largest2 = array[i]; + } + } + printf("n%d is the first largest \n", largest1); + printf("%d is the second largest \n", largest2); + printf("nAverage of %d and %d = %d \n", largest1, largest2, + (largest1 + largest2) / 2); +} + +/* +Enter 4 integer numbers +80 +23 +79 +58 +Input interger are +80 23 79 58 + +80 is the first largest +79 is the second largest + +Average of 80 and 79 = 79 diff --git a/c/Arrays/C Program to Find the Median of the Elements after Merging these 2 Sorted Arrays with Same Size.c b/c/Arrays/C Program to Find the Median of the Elements after Merging these 2 Sorted Arrays with Same Size.c new file mode 100644 index 0000000..2f5e774 --- /dev/null +++ b/c/Arrays/C Program to Find the Median of the Elements after Merging these 2 Sorted Arrays with Same Size.c @@ -0,0 +1,57 @@ +/* + * C Program to Find the Median of the Elements after Merging these 2 Sorted Arrays with Same Size + */ +#include + +int getMedian(int array1[], int array2[], int n) +{ + int i = 0; /* Current index of i/p array array1[] */ + int j = 0; /* Current index of i/p array array2[] */ + int count; + int m1 = -1, m2 = -1; + for (count = 0; count <= n; count++) + { + if (i == n) + { + m1 = m2; + m2 = array2[0]; + break; + } + else if (j == n) + { + m1 = m2; + m2 = array1[0]; + break; + } + if (array1[i] < array2[j]) + { + m1 = m2; /* Store the prev median */ + m2 = array1[i]; + i++; + } + else + { + m1 = m2; /* Store the prev median */ + m2 = array2[j]; + j++; + } + } + return (m1 + m2)/2; +} + +int main() +{ + int array1[] = {20, 25, 35, 30, 38}; + int array2[] = {22, 53, 65, 72, 45}; + int n1 = sizeof(array1) / sizeof(array1[0]); + int n2 = sizeof(array2) / sizeof(array2[0]); + if (n1 == n2) + printf("Median is %d", getMedian(array1, array2, n1)); + else + printf("not possible to findout"); + getchar(); + return 0; +} + +/* +Median is 34 diff --git a/c/Arrays/C Program to Find the Number of Elements in an Array.c b/c/Arrays/C Program to Find the Number of Elements in an Array.c new file mode 100644 index 0000000..4532f23 --- /dev/null +++ b/c/Arrays/C Program to Find the Number of Elements in an Array.c @@ -0,0 +1,19 @@ +/* + * C Program to Find the Number of Elements in an Array + */ +#include +#include +#include + +int main() +{ + int array[] = {15, 50, 34, 20, 10, 79, 100}; + int n; + n = sizeof(array); + printf("Size of the given array is %d\n", n/sizeof(int)); + return 0; +} + +/* + +Size of the given array is 7 \ No newline at end of file diff --git a/c/Arrays/C Program to Find the Number of Non Repeated Elements in an Array.c b/c/Arrays/C Program to Find the Number of Non Repeated Elements in an Array.c new file mode 100644 index 0000000..1be41c3 --- /dev/null +++ b/c/Arrays/C Program to Find the Number of Non Repeated Elements in an Array.c @@ -0,0 +1,57 @@ +/* + * C Program to Find the Number of Non Repeated Elements in an Array + */ +#include +int main() +{ + int array[50]; + int *ptr; + int i, j, k, size, n; + printf("\n Enter size of the array: "); + scanf("%d", &n); + printf("\n Enter %d elements of an array: ", n); + for (i = 0; i < n; i++) + scanf("%d", &array[i]); + size = n; + ptr = array; + for (i = 0; i < size; i++) + { + for (j = 0; j < size; j++) + { + if (i == j) + { + continue; + } + else if (*(ptr + i) == *(ptr + j)) + { + k = j; + size--; + while (k < size) + { + *(ptr + k) = *(ptr + k + 1); + k++; + } + j = 0; + } + } + } + printf("\n The array after removing duplicates is: "); + for (i = 0; i < size; i++) + { + printf(" %d", array[i]); + } + return 0; +} + +/* + +Enter size of the array: 6 + +Enter 6 elements of an array: 12 +10 +4 +10 +12 +56 + +The array after removing duplicates is: 12 10 4 56 \ No newline at end of file diff --git a/c/Arrays/C Program to Find the Odd Element given an Array with only two Different Element.c b/c/Arrays/C Program to Find the Odd Element given an Array with only two Different Element.c new file mode 100644 index 0000000..a37138a --- /dev/null +++ b/c/Arrays/C Program to Find the Odd Element given an Array with only two Different Element.c @@ -0,0 +1,41 @@ +/* + * C Program to Find the Odd Element given an Array with only two Different Element + */ +#include + +void printodd(int array[], int size) +{ + int xor2 = array[0]; /* Will hold XOR of two odd occurring elements */ + int set; + int i; + int n = size - 2; + int x = 0, y = 0; + /* The xor will basically be xor of two odd occurring elements */ + for (i = 1; i < size; i++) + xor2 = xor2 ^ array[i]; + /* Get one set rightmost bit in the xor2. */ + set = xor2 & ~(xor2 - 1); + /* Now divide elements in two sets: */ + for (i = 0; i < size; i++) + { + /* XOR of first set is finally going to hold one odd occurring number x */ + if (array[i] & set) + x = x ^ array[i]; + /* XOR of second set is finally going to hold the other odd occurring number y */ + else + y = y ^ array[i]; + } + printf("\n The ODD elements are %d & %d ", x, y); +} + +int main() +{ + int array[] = {10, 3, 2, 10, 2, 8, 8, 7}; + int arr_size = sizeof(array) / sizeof(array[0]); + printodd(array, arr_size); + getchar(); + return 0; +} + +/* + The ODD elements are 7 & 3 \ No newline at end of file diff --git a/c/Arrays/C Program to Find the Second Largest & Smallest Elements in an Array.c b/c/Arrays/C Program to Find the Second Largest & Smallest Elements in an Array.c new file mode 100644 index 0000000..91609d4 --- /dev/null +++ b/c/Arrays/C Program to Find the Second Largest & Smallest Elements in an Array.c @@ -0,0 +1,71 @@ +/*This C Program finds second largest & smallest elements in an array. The program sorts the array in an descending order. Then it finds the second largest and smallest element in an array and also find the average of an array element. Later it checks if the resultant average number is present in a given array. If found, display appropriate message.*/ + +/* + * C program to accept a list of data items and find the second largest + * and smallest elements in it. Compute the average of both and search + * for the average value if it is present in the array. + * Display appropriate message on successful search. + */ +#include + +void main () +{ + int number[30]; + int i, j, a, n, counter, average; + printf("Enter the value of N\n"); + scanf("%d", &n); + printf("Enter the numbers \n"); + for (i = 0; i < n; ++i) + scanf("%d", &number[i]); + for (i = 0; i < n; ++i) + { + for (j = i + 1; j < n; ++j) + { + if (number[i] < number[j]) + { + a = number[i]; + number[i] = number[j]; + number[j] = a; + } + } + } + printf("The numbers arranged in descending order are given below \n"); + for (i = 0; i < n; ++i) + { + printf("%d\n", number[i]); + } + printf("The 2nd largest number is = %d\n", number[1]); + printf("The 2nd smallest number is = %d\n", number[n - 2]); + average = (number[1] + number[n - 2]) / 2; + counter = 0; + for (i = 0; i < n; ++i) + { + if (average == number[i]) + { + ++counter; + } + } + if (counter == 0 ) + printf("The average of %d and %d is = %d is not in the array \n", + number[1], number[n - 2], average); + else + printf("The average of %d and %d in array is %d in numbers \n", + number[1], number[n - 2], counter); +} + +/* +Enter the value of N +4 +Enter the numbers +450 +340 +120 +670 +The numbers arranged in descending order are given below +670 +450 +340 +120 +The 2nd largest number is = 450 +The 2nd smallest number is = 340 +The average of 450 and 340 is = 395 is not in the array diff --git a/c/Arrays/C Program to Find the Sum of Contiguous Subarray within a 1 – D Array of Numbers which has the Largest Sum.c b/c/Arrays/C Program to Find the Sum of Contiguous Subarray within a 1 – D Array of Numbers which has the Largest Sum.c new file mode 100644 index 0000000..e1cd63e --- /dev/null +++ b/c/Arrays/C Program to Find the Sum of Contiguous Subarray within a 1 – D Array of Numbers which has the Largest Sum.c @@ -0,0 +1,43 @@ +/*This C Program finds the sum of contiguous subarray within a 1 – D array of numbers which has the largest sum.*/ + +/* + * C Program to Find the Sum of Contiguous Subarray within a 1 - D Array of Numbers which has the Largest Sum + */ +#include +#include + +int maxSubArraySum(int a[], int size, int *begin, int *end) +{ + int max_so_far = 0, max_end = 0; + int i, current_index = 0; + for (i = 0; i < size; i++) + { + max_end = max_end + a[i]; + if (max_end <= 0) + { + max_end = 0; + current_index = i + 1; + } + else if (max_so_far < max_end) + { + max_so_far = max_end; + *begin = current_index; + *end = i; + } + } + return max_so_far; +} + +int main() +{ + int arr[] = {10, -2, 15, 9, -8, 12, 20, -5}; + int start = 0, end = 0; + int size = sizeof(arr) / sizeof(arr[0]); + printf(" The max sum is %d", maxSubArraySum(arr, size, &start, &end)); + printf(" The begin and End are %d & %d", start, end); + getchar(); + return 0; +} + +/* + The max sum is 56 The begin and End are 0 & 6 \ No newline at end of file diff --git a/c/Arrays/C Program to Find the Summation of Node values at Row or Level.c b/c/Arrays/C Program to Find the Summation of Node values at Row or Level.c new file mode 100644 index 0000000..44dc4cf --- /dev/null +++ b/c/Arrays/C Program to Find the Summation of Node values at Row or Level.c @@ -0,0 +1,215 @@ +/* +* C Program to Find the Summation of Node values at level/row and print it +*/ +#include +#include + +struct btnode +{ + int value; + struct btnode *r,*l; +}*root = NULL, *temp = NULL; + +void create(); +void insert(); +void add(struct btnode *t); +void computesum(struct btnode *t); +void display(); + +int count = 0, sum[100] = {0}, max = 0; + +void main() +{ + int ch; + printf("\n OPERATIONS ---"); + printf("\n 1] Insert an element into tree"); + printf("\n 2] Display the sum of the elements at the same level"); + printf("\n 3] Exit "); + while (1) + { + printf("\nEnter your choice : "); + scanf("%d", &ch); + switch (ch) + { + case 1: + insert(); + break; + case 2: + count = 0; + max = 0; + computesum(root); + display(); + break; + case 3: + exit(0); + default : + printf("Wrong choice, Please enter correct choice "); + break; + } + } +} + +/* To create a new node with the data from the user */ +void create() +{ + int data; + printf("Enter the data of node : "); + scanf("%d", &data); + temp = (struct btnode* ) malloc(1*(sizeof(struct btnode))); + temp->value = data; + temp->l = temp->r = NULL; +} + +/* To check for root node and then create it */ +void insert() +{ + create(); + if (root == NULL) + root = temp; + else + add(root); +} + +/* Search for the appropriate position to insert the new node */ +void add(struct btnode *t) +{ + if ((temp->value > t->value) && (t->r != NULL)) /* value more than root node value insert at right */ + add(t->r); + else if ((temp->value > t->value) && (t->r == NULL)) + t->r = temp; + else if ((temp->value < t->value) && (t->l != NULL)) /* value less than root node value insert at left */ + add(t->l); + else if ((temp->value < t->value) && (t->l==NULL)) + t->l = temp; +} + +/* Function to find the sum of nodes at same distance */ +void computesum(struct btnode *t) +{ + if (root == NULL) + { + printf("Tree is empty "); + return; + } + if (t->l != NULL) + { + count++; + computesum(t->l); + } + sum[count] = sum[count] + t->value; /* addition of elelment by row wise */ + if (max < count) + max = count; + if (t->r != NULL) + { + count++; + computesum(t->r); + } + count--; +} + +/* To display the sum of the nodes at the same distance */ +void display() +{ + int i; + printf("Sum of nodes : \n Level \t Sum "); + for (i = 0; i <= max; i++) + printf("\n %d \t: %d ", i, sum[i]); +} + +/* + +OPERATIONS --- + 1] Insert an element into tree + 2] Display the sum of the elements at the same level + 3] Exit + Enter your choice : 1 + Enter the data of node : 40 + + Enter your choice : 1 + Enter the data of node : 20 + + Enter your choice : 1 + Enter the data of node : 60 + + Enter your choice : 1 + Enter the data of node : 10 + + Enter your choice : 1 + Enter the data of node : 30 + + Enter your choice : 1 + Enter the data of node : 80 + + Enter your choice : 1 + Enter the data of node : 90 + + Enter your choice : 2 + Sum of nodes : + Level Sum + 0 : 40 + 1 : 80 + 2 : 120 + 3 : 90 + Enter your choice : 3 + + 40 + /\ + / \ + 20 60 + / \ \ + 10 30 80 + \ + 90 + + $ ./a.out + + OPERATIONS --- + 1] Insert an element into tree + 2] Display the sum of the elements at the same level + 3] Exit + Enter your choice : 1 + Enter the data of node : 50 + + Enter your choice : 1 + Enter the data of node : 30 + + Enter your choice : 1 + Enter the data of node : 20 + + Enter your choice : 1 + Enter the data of node : 40 + + Enter your choice : 1 + Enter the data of node : 35 + + Enter your choice : 1 + Enter the data of node : 100 + + Enter your choice : 1 + Enter the data of node : 70 + + Enter your choice : 1 + Enter the data of node : 120 + + Enter your choice : 1 + Enter the data of node : 140 + + Enter your choice : 2 + Sum of nodes : + Level Sum + 0 : 50 + 1 : 130 + 2 : 250 + 3 : 175 +Enter your choice : 3 + + + + 50 + /\ + / \ + 30 100 + / \ / \ + 20 40 70 120 + / \ + 35 140 \ No newline at end of file diff --git a/c/Arrays/C Program to Find the two Elements such that their Sum is Closest to Zero.c b/c/Arrays/C Program to Find the two Elements such that their Sum is Closest to Zero.c new file mode 100644 index 0000000..a24e624 --- /dev/null +++ b/c/Arrays/C Program to Find the two Elements such that their Sum is Closest to Zero.c @@ -0,0 +1,48 @@ +/* + * C Program to Find the two Elements such that their Sum is Closest to Zero + */ +# include +# include +# include + +void minabsvaluepair(int array[], int array_size) +{ + int count = 0; + int l, r, min_sum, sum, min_l, min_r; + /* Array should have at least two elements*/ + if (array_size < 2) + { + printf("Invalid Input"); + return; + } + /* Initialization of values */ + min_l = 0; + min_r = 1; + min_sum = array[0] + array[1]; + for (l = 0; l < array_size - 1; l++) + { + for (r = l + 1; r < array_size; r++) + { + sum = array[l] + array[r]; + if (abs(min_sum) > abs(sum)) + { + min_sum = sum; + min_l = l; + min_r = r; + } + } + } + printf(" The two elements whose sum is minimum are %d and %d", array[min_l], array[min_r]); +} + +int main() +{ + int array[] = {42, 15, -25, 30, -10, 35}; + minabsvaluepair(array, 6); + getchar(); + return 0; +} + +/* + +The two elements whose sum is minimum are 15 and -10 \ No newline at end of file diff --git a/c/Arrays/C Program to Generate Pascal Triangle 1 D Array.c b/c/Arrays/C Program to Generate Pascal Triangle 1 D Array.c new file mode 100644 index 0000000..b2e96c8 --- /dev/null +++ b/c/Arrays/C Program to Generate Pascal Triangle 1 D Array.c @@ -0,0 +1,40 @@ +/* + * C Program to Generate Pascal Triangle 1 D Array + */ +#include + +void main() +{ + int array[30], temp[30], i, j, k, l, num; //using 2 arrays + printf("Enter the number of lines to be printed: "); + scanf("%d", &num); + temp[0] = 1; + array[0] = 1; + for (j = 0; j < num; j++) + printf(" "); + printf(" 1\n"); + for (i = 1; i < num; i++) + { + for (j = 0; j < i; j++) + printf(" "); + for (k = 1; k < num; k++) + { + array[k] = temp[k - 1] + temp[k]; + } + array[i] = 1; + for (l = 0; l <= i; l++) + { + printf("%3d", array[l]); + temp[l] = array[l]; + } + printf("\n"); + } +} + +/* + +Enter the number of lines to be printed: 4 + 1 + 1 1 + 1 2 1 +1 3 3 1 \ No newline at end of file diff --git a/c/Arrays/C Program to Implement a Queue using an Array.c b/c/Arrays/C Program to Implement a Queue using an Array.c new file mode 100644 index 0000000..79ff7af --- /dev/null +++ b/c/Arrays/C Program to Implement a Queue using an Array.c @@ -0,0 +1,129 @@ +/*This C Program implements a queue using array. Queue is a is a particular kind of abstract data type or collection in which the entities in the collection are kept in order and the principal (or only) operations on the collection are the addition of entities to the rear terminal position and removal of entities from the front terminal position. This makes the queue a First-In-First-Out (FIFO) data structure.*/ + + +/* + * C Program to Implement a Queue using an Array + */ +#include + +#define MAX 50 +int queue_array[MAX]; +int rear = - 1; +int front = - 1; +main() +{ + int choice; + while (1) + { + printf("1.Insert element to queue \n"); + printf("2.Delete element from queue \n"); + printf("3.Display all elements of queue \n"); + printf("4.Quit \n"); + printf("Enter your choice : "); + scanf("%d", &choice); + switch (choice) + { + case 1: + insert(); + break; + case 2: + delete(); + break; + case 3: + display(); + break; + case 4: + exit(1); + default: + printf("Wrong choice \n"); + } /*End of switch*/ + } /*End of while*/ +} /*End of main()*/ +insert() +{ + int add_item; + if (rear == MAX - 1) + printf("Queue Overflow \n"); + else + { + if (front == - 1) + /*If queue is initially empty */ + front = 0; + printf("Inset the element in queue : "); + scanf("%d", &add_item); + rear = rear + 1; + queue_array[rear] = add_item; + } +} /*End of insert()*/ + +delete() +{ + if (front == - 1 || front > rear) + { + printf("Queue Underflow \n"); + return ; + } + else + { + printf("Element deleted from queue is : %d\n", queue_array[front]); + front = front + 1; + } +} /*End of delete() */ +display() +{ + int i; + if (front == - 1) + printf("Queue is empty \n"); + else + { + printf("Queue is : \n"); + for (i = front; i <= rear; i++) + printf("%d ", queue_array[i]); + printf("\n"); + } +} /*End of display() */ + +/* +1.Insert element to queue +2.Delete element from queue +3.Display all elements of queue +4.Quit +Enter your choice : 1 +Inset the element in queue : 10 +1.Insert element to queue +2.Delete element from queue +3.Display all elements of queue +4.Quit +Enter your choice : 1 +Inset the element in queue : 15 +1.Insert element to queue +2.Delete element from queue +3.Display all elements of queue +4.Quit +Enter your choice : 1 +Inset the element in queue : 20 +1.Insert element to queue +2.Delete element from queue +3.Display all elements of queue +4.Quit +Enter your choice : 1 +Inset the element in queue : 30 +1.Insert element to queue +2.Delete element from queue +3.Display all elements of queue +4.Quit +Enter your choice : 2 +Element deleted from queue is : 10 +1.Insert element to queue +2.Delete element from queue +3.Display all elements of queue +4.Quit +Enter your choice : 3 +Queue is : +15 20 30 +1.Insert element to queue +2.Delete element from queue +3.Display all elements of queue +4.Quit +Enter your choice : 4 + diff --git a/c/Arrays/C Program to Implement two Stacks using a Single Array & Check for Overflow & Underflow.c b/c/Arrays/C Program to Implement two Stacks using a Single Array & Check for Overflow & Underflow.c new file mode 100644 index 0000000..03fe753 --- /dev/null +++ b/c/Arrays/C Program to Implement two Stacks using a Single Array & Check for Overflow & Underflow.c @@ -0,0 +1,153 @@ +/*This C Program Implements two Stacks using a Single Array & Check for Overflow & Underflow. A Stack is a linear data structure in which a data item is inserted and deleted at one record. A stack is called a Last In First Out (LIFO) structure. Because the data item inserted last is the data item deleted first from the stack. +To implement two stacks in one array, there can be two methods. + +First is to divide the array in to two equal parts and then give one half two each stack. But this method wastes space. + +So a better way is to let the two stacks to push elements by comparing tops of each other, and not up to one half of the array. + +Push and Pop functions of both stack in the following code has their Time Complexity as O(1). They take constant time. + +Print is O(n), where n is the number of elements in the stack. + +The program has an array of size 10. 6 values are pushed in stack 1 and 4 in two. All conditions are being checked.*/ + + +//This is a C Program to Implement two Stacks using a Single Array & Check for Overflow & Underflow +#include +#define SIZE 10 + + +int ar[SIZE]; +int top1 = -1; +int top2 = SIZE; + +//Functions to push data +void push_stack1 (int data) +{ + if (top1 < top2 - 1) + { + ar[++top1] = data; + } + else + { + printf ("Stack Full! Cannot Push\n"); + } +} +void push_stack2 (int data) +{ + if (top1 < top2 - 1) + { + ar[--top2] = data; + } + else + { + printf ("Stack Full! Cannot Push\n"); + } +} + +//Functions to pop data +void pop_stack1 () +{ + if (top1 >= 0) + { + int popped_value = ar[top1--]; + printf ("%d is being popped from Stack 1\n", popped_value); + } + else + { + printf ("Stack Empty! Cannot Pop\n"); + } +} +void pop_stack2 () +{ + if (top2 < SIZE) + { + int popped_value = ar[top2++]; + printf ("%d is being popped from Stack 2\n", popped_value); + } + else + { + printf ("Stack Empty! Cannot Pop\n"); + } +} + +//Functions to Print Stack 1 and Stack 2 +void print_stack1 () +{ + int i; + for (i = top1; i >= 0; --i) + { + printf ("%d ", ar[i]); + } + printf ("\n"); +} +void print_stack2 () +{ + int i; + for (i = top2; i < SIZE; ++i) + { + printf ("%d ", ar[i]); + } + printf ("\n"); +} + +int main() +{ + int ar[SIZE]; + int i; + int num_of_ele; + printf ("We can push a total of 10 values\n"); + //Number of elements pushed in stack 1 is 6 + //Number of elements pushed in stack 2 is 4 + for (i = 1; i <= 6; ++i) + { + push_stack1 (i); + printf ("Value Pushed in Stack 1 is %d\n", i); + } + for (i = 1; i <= 4; ++i) + { + push_stack2 (i); + printf ("Value Pushed in Stack 2 is %d\n", i); + } + //Print Both Stacks + print_stack1 (); + print_stack2 (); + //Pushing on Stack Full + printf ("Pushing Value in Stack 1 is %d\n", 11); + push_stack1 (11); + //Popping All Elements From Stack 1 + num_of_ele = top1 + 1; + while (num_of_ele) + { + pop_stack1 (); + --num_of_ele; + } + //Trying to Pop From Empty Stack + pop_stack1 (); + return 0; +} + +/* + +We can push a total of 10 values +Value Pushed in Stack 1 is 1 +Value Pushed in Stack 1 is 2 +Value Pushed in Stack 1 is 3 +Value Pushed in Stack 1 is 4 +Value Pushed in Stack 1 is 5 +Value Pushed in Stack 1 is 6 +Value Pushed in Stack 2 is 1 +Value Pushed in Stack 2 is 2 +Value Pushed in Stack 2 is 3 +Value Pushed in Stack 2 is 4 +6 5 4 3 2 1 +4 3 2 1 +Pushing Value in Stack 1 is 11 +Stack Full! Cannot Push +6 is being popped from Stack 1 +5 is being popped from Stack 1 +4 is being popped from Stack 1 +3 is being popped from Stack 1 +2 is being popped from Stack 1 +1 is being popped from Stack 1 +Stack Empty! Cannot Pop \ No newline at end of file diff --git a/c/Arrays/C Program to Increment every Element of the Array by one & Print Incremented Array.c b/c/Arrays/C Program to Increment every Element of the Array by one & Print Incremented Array.c new file mode 100644 index 0000000..1ef8dfc --- /dev/null +++ b/c/Arrays/C Program to Increment every Element of the Array by one & Print Incremented Array.c @@ -0,0 +1,26 @@ +/* + * C Program to Increment every Element of the Array by one & Print Incremented Array + */ +#include + +void incrementArray(int[]); + +void main() +{ + int i; + int array[4] = {10, 20, 30, 40}; + incrementArray(array); + for (i = 0; i < 4; i++) + printf("%d\t", array[i]); // Prints 2, 3, 4, 5 +} + +void incrementArray(int arr[]) +{ + int i; + for (i = 0; i < 4; i++) + arr[i]++; // this alters values in array in main() +} + +/* + +11 21 31 \ No newline at end of file diff --git a/c/Arrays/C Program to Input a String & Store their Ascii Values in an Integer Array & Print the Array.c b/c/Arrays/C Program to Input a String & Store their Ascii Values in an Integer Array & Print the Array.c new file mode 100644 index 0000000..96d79de --- /dev/null +++ b/c/Arrays/C Program to Input a String & Store their Ascii Values in an Integer Array & Print the Array.c @@ -0,0 +1,35 @@ +/* + * C Program to Input a String & Store their Ascii Values in an Integer Array & Print the Array + */ +#include + +void main() +{ + char string[20]; + int n, count = 0; + printf("Enter the no of characters present in an array \n "); + scanf("%d", &n); + printf(" Enter the string of %d characters \n", n); + scanf("%s", string); + while (count < n) + { + printf(" %c = %d\n", string[count], string[count] ); + ++ count ; + } +} + +/* + +Enter the no of characters present in an array +10 + Enter the string of 10 characters +sanfoundry + s = 115 + a = 97 + n = 110 + f = 102 + o = 111 + u = 117 + n = 110 + d = 100 + r = 114 \ No newline at end of file diff --git a/c/Arrays/C Program to Input an Array, Store the Squares of these Elements in an Array & Print it.c b/c/Arrays/C Program to Input an Array, Store the Squares of these Elements in an Array & Print it.c new file mode 100644 index 0000000..6ce80c5 --- /dev/null +++ b/c/Arrays/C Program to Input an Array, Store the Squares of these Elements in an Array & Print it.c @@ -0,0 +1,29 @@ +/* + * C Program to Input an Array, Store the Squares of these Elements in an Array & Print it + */ +#include +#define MAX_ROWS 3 +#define MAX_COLS 4 + +void print_square(int [ ] ); + +void main (void) +{ + int i; + int num [MAX_ROWS][MAX_COLS] = { {10, 20, 30, 40}, {50, 60, 70, 80}, {90, 100, 110, 120} }; + for (i = 0; i < MAX_ROWS; i++) + print_square(num[i]); +} +void print_square(int x[ ]) +{ + int j; + for (j = 0; j < MAX_COLS; j++) + printf ("%d\t", x[j] * x[j]); + printf("\n"); +} + +/* + +100 400 900 1600 +2500 3600 4900 6400 +8100 10000 12100 14400 \ No newline at end of file diff --git a/c/Arrays/C Program to Insert an Element in a Specified Position in a given Array.c b/c/Arrays/C Program to Insert an Element in a Specified Position in a given Array.c new file mode 100644 index 0000000..1ef2072 --- /dev/null +++ b/c/Arrays/C Program to Insert an Element in a Specified Position in a given Array.c @@ -0,0 +1,103 @@ +/*This C Program inserts an element in a specified position in a given array. Program takes a user input and inserts the desired element in the specified position.*/ + +/* + * C program to insert a particular element in a specified position + * in a given array + */ +#include + +void main() +{ + int array[10]; + int i, j, n, m, temp, key, pos; + printf("Enter how many elements \n"); + scanf("%d", &n); + printf("Enter the elements \n"); + for (i = 0; i < n; i++) + { + scanf("%d", &array[i]); + } + printf("Input array elements are \n"); + for (i = 0; i < n; i++) + { + printf("%d\n", array[i]); + } + for (i = 0; i < n; i++) + { + for (j = i + 1; j < n; j++) + { + if (array[i] > array[j]) + { + temp = array[i]; + array[i] = array[j]; + array[j] = temp; + } + } + } + printf("Sorted list is \n"); + for (i = 0; i < n; i++) + { + printf("%d\n", array[i]); + } + printf("Enter the element to be inserted \n"); + scanf("%d", &key); + for (i = 0; i < n; i++) + { + if (key < array[i]) + { + pos = i; + break; + } + if (key > array[n-1]) + { + pos = n; + break; + } + } + if (pos != n) + { + m = n - pos + 1 ; + for (i = 0; i <= m; i++) + { + array[n - i + 2] = array[n - i + 1] ; + } + } + array[pos] = key; + printf("Final list is \n"); + for (i = 0; i < n + 1; i++) + { + printf("%d\n", array[i]); + } +} + +/* + +Enter how many elements +5 +Enter the elements +76 +90 +56 +78 +12 +Input array elements are +76 +90 +56 +78 +12 +Sorted list is +12 +56 +76 +78 +90 +Enter the element to be inserted +61 +Final list is +12 +56 +61 +76 +78 +90 \ No newline at end of file diff --git a/c/Arrays/C Program to Matrix transpose.c b/c/Arrays/C Program to Matrix transpose.c new file mode 100644 index 0000000..9da917f --- /dev/null +++ b/c/Arrays/C Program to Matrix transpose.c @@ -0,0 +1,107 @@ +/* Matrix transpose - Program to find transpose of a matrix m*n using functions to +1) Read elements of matrix +2) find transpose +3) Display elements of matrix +4) find transpose using single matrix. +May 2013 */ + +#include +#include + +void read(int x[ ][10], int nr, int nc) ; +void transpose(int x[ ][10], int y[ ][10], int nr, int nc) ; +void show(int y[ ][10], int nr, int nc) ; +void singletranspose(int x[ ][10], int nr, int nc) ; + +void main() +{ + int x[10][10], y[10][10], m, n ; + clrscr(); + printf("Enter the number of rows and columns: "); + scanf("%d %d", &m, &n) ; + printf("Enter elements of the matrix row-wise:\n") ; + read(x, m, n) ; + transpose(x, y, m, n) ; + printf("Transpose of given matrix is:\n") ; + show(y,n,m) ; + if(m==n) + { + singletranspose(x,m,n); + printf("Transpose using single matrix is:\n"); + show(x,n,m); + } + else + printf("The matrix is not a square matrix"); + getch(); +} + +void read(int x[ ][10], int nr, int nc) +{ + int r, c ; + for(r=0 ; r + +void Merge(int *, int, int, int ); + +void MergeSort(int *array, int left, int right) +{ + int middle = (left+right)/2; + /* We have to sort only when left + +void main() +{ + int array1[50], array2[50], array3[100], m, n, i, j, k = 0; + printf("\n Enter size of array Array 1: "); + scanf("%d", &m); + printf("\n Enter sorted elements of array 1: \n"); + for (i = 0; i < m; i++) + { + scanf("%d", &array1[i]); + } + printf("\n Enter size of array 2: "); + scanf("%d", &n); + printf("\n Enter sorted elements of array 2: \n"); + for (i = 0; i < n; i++) + { + scanf("%d", &array2[i]); + } + i = 0; + j = 0; + while (i < m && j < n) + { + if (array1[i] < array2[j]) + { + array3[k] = array1[i]; + i++; + } + else + { + array3[k] = array2[j]; + j++; + } + k++; + } + if (i >= m) + { + while (j < n) + { + array3[k] = array2[j]; + j++; + k++; + } + } + if (j >= n) + { + while (i < m) + { + array3[k] = array1[i]; + i++; + k++; + } + } + printf("\n After merging: \n"); + for (i = 0; i < m + n; i++) + { + printf("\n%d", array3[i]); + } +} + +/* + +Enter size of array Array 1: 4 + +Enter sorted elements of array 1: +12 +18 +40 +60 + +Enter size of array 2: 4 + +Enter sorted elements of array 2: +47 +56 +89 +90 + +After merging: + +12 +18 +40 +47 +56 +60 +89 +90 \ No newline at end of file diff --git a/c/Arrays/C Program to Print all the Repeated Numbers with Frequency in an Array.c b/c/Arrays/C Program to Print all the Repeated Numbers with Frequency in an Array.c new file mode 100644 index 0000000..2c33768 --- /dev/null +++ b/c/Arrays/C Program to Print all the Repeated Numbers with Frequency in an Array.c @@ -0,0 +1,32 @@ +/* + * C Program to Print all the Repeated Numbers with Frequency in an Array + */ +#include +#include + +void duplicate(int array[], int num) +{ + int *count = (int *)calloc(sizeof(int), (num - 2)); + int i; + printf("duplicate elements present in the given array are "); + for (i = 0; i < num; i++) + { + if (count[array[i]] == 1) + printf(" %d ", array[i]); + else + count[array[i]]++; + } +} + +int main() +{ + int array[] = {5, 10, 10, 2, 1, 4, 2}; + int array_freq = sizeof(array) / sizeof(array[0]); + duplicate(array, array_freq); + getchar(); + return 0; +} + +/* + +duplicate elements present in the given array are 10 2 \ No newline at end of file diff --git a/c/Arrays/C Program to Print odd and even numbers of an array separately.c b/c/Arrays/C Program to Print odd and even numbers of an array separately.c new file mode 100644 index 0000000..fe70dbf --- /dev/null +++ b/c/Arrays/C Program to Print odd and even numbers of an array separately.c @@ -0,0 +1,30 @@ +/*Print odd and even numbers of an array separately*/ +#include +#define MAX 100 +void main() +{ + int arr[MAX],n,i; + printf("Enter size of Array: "); + scanf("%d",&n); + printf("Enter %d positive elements\n",n); + for(i=0; i + +void main() +{ + int array[10]; + int i, j, temp; + printf("enter the element of an array \n"); + for (i = 0; i < 10; i++) + scanf("%d", &array[i]); + printf("Alternate elements of a given array \n"); + for (i = 0; i < 10; i += 2) + printf( "%d\n", array[i]) ; +} + +/* + +enter the element of an array +12 +23 +45 +57 +68 +73 +84 +97 +120 +125 +Alternate elements of a given array +12 +45 +68 +84 +120 \ No newline at end of file diff --git a/c/Arrays/C Program to Print the Number of Odd & Even Numbers in an Array.c b/c/Arrays/C Program to Print the Number of Odd & Even Numbers in an Array.c new file mode 100644 index 0000000..2239c46 --- /dev/null +++ b/c/Arrays/C Program to Print the Number of Odd & Even Numbers in an Array.c @@ -0,0 +1,46 @@ +/* + * C Program to Print the Number of Odd & Even Numbers in an Array + */ +#include + +void main() +{ + int array[100], i, num; + printf("Enter the size of an array \n"); + scanf("%d", &num); + printf("Enter the elements of the array \n"); + for (i = 0; i < num; i++) + { + scanf("%d", &array[i]); + } + printf("Even numbers in the array are - "); + for (i = 0; i < num; i++) + { + if (array[i] % 2 == 0) + { + printf("%d \t", array[i]); + } + } + printf("\n Odd numbers in the array are -"); + for (i = 0; i < num; i++) + { + if (array[i] % 2 != 0) + { + printf("%d \t", array[i]); + } + } +} + +/* + +Enter the size of an array +6 +Enter the elements of the array +12 +19 +45 +69 +98 +23 +Even numbers in the array are - 12 98 + Odd numbers in the array are - 19 45 69 23 \ No newline at end of file diff --git a/c/Arrays/C Program to Put Even & Odd Elements of an Array in 2 Separate Arrays.c b/c/Arrays/C Program to Put Even & Odd Elements of an Array in 2 Separate Arrays.c new file mode 100644 index 0000000..2a68ad0 --- /dev/null +++ b/c/Arrays/C Program to Put Even & Odd Elements of an Array in 2 Separate Arrays.c @@ -0,0 +1,65 @@ +/*This C Program puts even & odd elements of an array in 2 separate arrays. The program first finds the odd and even elements of the array. Then the odd elements of an array is stored in one array and even elements of an array is stored in another array.*/ + +/* + * C Program to accept N integer number and store them in an array AR. + * The odd elements in the AR are copied into OAR and other elements + * are copied into EAR. Display the contents of OAR and EAR. + */ +#include + +void main() +{ + long int ARR[10], OAR[10], EAR[10]; + int i, j = 0, k = 0, n; + printf("Enter the size of array AR \n"); + scanf("%d", &n); + printf("Enter the elements of the array \n"); + for (i = 0; i < n; i++) + { + scanf("%ld", &ARR[i]); + fflush(stdin); + } + /* Copy odd and even elements into their respective arrays */ + for (i = 0; i < n; i++) + { + if (ARR[i] % 2 == 0) + { + EAR[j] = ARR[i]; + j++; + } + else + { + OAR[k] = ARR[i]; + k++; + } + } + printf("The elements of OAR are \n"); + for (i = 0; i < j; i++) + { + printf("%ld\n", OAR[i]); + } + printf("The elements of EAR are \n"); + for (i = 0; i < k; i++) + { + printf("%ld\n", EAR[i]); + } +} + +/* +Enter the size of array AR +6 +Enter the elements of the array +34 +56 +78 +90 +12 +39 +The elements of OAR are +39 +1 +32768 +11542516 +11210377 +The elements of EAR are +34 \ No newline at end of file diff --git a/c/Arrays/C Program to Read an Array and Search for an Element.c b/c/Arrays/C Program to Read an Array and Search for an Element.c new file mode 100644 index 0000000..5a6c581 --- /dev/null +++ b/c/Arrays/C Program to Read an Array and Search for an Element.c @@ -0,0 +1,62 @@ +/* + * C program accept an array of N elements and a key to search. + * If the search is successful, it displays "SUCCESSFUL SEARCH". + * Otherwise, a message "UNSUCCESSFUL SEARCH" is displayed. + */ +#include + +void main() +{ + int array[20]; + int i, low, mid, high, key, size; + printf("Enter the size of an array\n"); + scanf("%d", &size); + printf("Enter the array elements\n"); + for (i = 0; i < size; i++) + { + scanf("%d", &array[i]); + } + printf("Enter the key\n"); + scanf("%d", &key); + /* search begins */ + low = 0; + high = (size - 1); + while (low <= high) + { + mid = (low + high) / 2; + if (key == array[mid]) + { + printf("SUCCESSFUL SEARCH\n"); + return; + } + if (key < array[mid]) + high = mid - 1; + else + low = mid + 1; + } + printf("UNSUCCESSFUL SEARCH\n"); +} + +/* +Enter the size of an array +4 +Enter the array elements +90 +560 +300 +390 +Enter the key +90 +SUCCESSFUL SEARCH + +$ a.out +Enter the size of an array +4 +Enter the array elements +100 +500 +580 +470 +Enter the key +300 +UNSUCCESSFUL SEARCH \ No newline at end of file diff --git a/c/Arrays/C Program to Segregate 0s on Left Side & 1s on right side of the Array.c b/c/Arrays/C Program to Segregate 0s on Left Side & 1s on right side of the Array.c new file mode 100644 index 0000000..a554080 --- /dev/null +++ b/c/Arrays/C Program to Segregate 0s on Left Side & 1s on right side of the Array.c @@ -0,0 +1,43 @@ +/* + * C Program to Segregate 0s on Left Side & 1s on right side of the Array (Traverse Array only once) + */ +#include + +/*Function to segregate all 0s on left and all 1s on right*/ +void segregate0and1(int array[], int size) +{ + int left = 0, right = size-1; + while (left < right) + { + /* Increment left index while we see 0 at left */ + while (array[left] == 0 && left < right) + left++; + /* Decrement right index while we see 1 at right */ + while (array[right] == 1 && left < right) + right--; + /* If left is smaller than right then there is a 1 at left and a 0 at right. Exchange it */ + if (left < right) + { + array[left] = 0; + array[right] = 1; + left++; + right--; + } + } +} + +int main() +{ + int arr[] = {0, 1, 0, 1, 1, 0}; + int array_size = 6, i = 0; + segregate0and1(arr, array_size); + printf("segregated array is "); + for (i = 0; i < 6; i++) + printf("%d ", arr[i]); + getchar(); + return 0; +} + +/* + +segregated array is 0 0 0 1 1 1 \ No newline at end of file diff --git a/c/Arrays/C Program to Sort N Numbers in Ascending Order using Bubble Sort.c b/c/Arrays/C Program to Sort N Numbers in Ascending Order using Bubble Sort.c new file mode 100644 index 0000000..de19a3e --- /dev/null +++ b/c/Arrays/C Program to Sort N Numbers in Ascending Order using Bubble Sort.c @@ -0,0 +1,70 @@ +/*This C Program sorts the numbers in ascending order using bubble sort. Bubble sort is a simple sorting algorithm that works by repeatedly stepping through the list to be sorted, comparing each pair of adjacent items and swapping them if they are in the wrong order. Here we need to sort a number in ascending order.*/ + +/* + * C program to sort N numbers in ascending order using Bubble sort + * and print both the given and the sorted array + */ +#include +#define MAXSIZE 10 + +void main() +{ + int array[MAXSIZE]; + int i, j, num, temp; + printf("Enter the value of num \n"); + scanf("%d", &num); + printf("Enter the elements one by one \n"); + for (i = 0; i < num; i++) + { + scanf("%d", &array[i]); + } + printf("Input array is \n"); + for (i = 0; i < num; i++) + { + printf("%d\n", array[i]); + } + /* Bubble sorting begins */ + for (i = 0; i < num; i++) + { + for (j = 0; j < (num - i - 1); j++) + { + if (array[j] > array[j + 1]) + { + temp = array[j]; + array[j] = array[j + 1]; + array[j + 1] = temp; + } + } + } + printf("Sorted array is...\n"); + for (i = 0; i < num; i++) + { + printf("%d\n", array[i]); + } +} + +/* + +Enter the value of num +6 +Enter the elements one by one +23 +45 +67 +89 +12 +34 +Input array is +23 +45 +67 +89 +12 +34 +Sorted array is... +12 +23 +34 +45 +67 +89 \ No newline at end of file diff --git a/c/Arrays/C Program to Sort the Array in Descending Order.c b/c/Arrays/C Program to Sort the Array in Descending Order.c new file mode 100644 index 0000000..c6b2c69 --- /dev/null +++ b/c/Arrays/C Program to Sort the Array in Descending Order.c @@ -0,0 +1,51 @@ +/* + * C program to accept a set of numbers and arrange them + * in a descending order + */ +#include + +void main () +{ + int number[30]; + int i, j, a, n; + printf("Enter the value of N\n"); + scanf("%d", &n); + printf("Enter the numbers \n"); + for (i = 0; i < n; ++i) + scanf("%d", &number[i]); + /* sorting begins ... */ + for (i = 0; i < n; ++i) + { + for (j = i + 1; j < n; ++j) + { + if (number[i] < number[j]) + { + a = number[i]; + number[i] = number[j]; + number[j] = a; + } + } + } + printf("The numbers arranged in descending order are given below\n"); + for (i = 0; i < n; ++i) + { + printf("%d\n", number[i]); + } +} + +/* + +Enter the value of N +5 +Enter the numbers +234 +780 +130 +56 +90 +The numbers arranged in descending order are given below +780 +234 +130 +90 +56 \ No newline at end of file diff --git a/c/Arrays/C Program to Sort the Array in an Ascending Order.c b/c/Arrays/C Program to Sort the Array in an Ascending Order.c new file mode 100644 index 0000000..9c17cf3 --- /dev/null +++ b/c/Arrays/C Program to Sort the Array in an Ascending Order.c @@ -0,0 +1,47 @@ +/* + * C program to accept N numbers and arrange them in an ascending order + */ +#include + +void main() +{ + int i, j, a, n, number[30]; + printf("Enter the value of N \n"); + scanf("%d", &n); + printf("Enter the numbers \n"); + for (i = 0; i < n; ++i) + scanf("%d", &number[i]); + for (i = 0; i < n; ++i) + { + for (j = i + 1; j < n; ++j) + { + if (number[i] > number[j]) + { + a = number[i]; + number[i] = number[j]; + number[j] = a; + } + } + } + printf("The numbers arranged in ascending order are given below \n"); + for (i = 0; i < n; ++i) + printf("%d\n", number[i]); +} + +/* +Enter the value of N +6 +Enter the numbers +3 +78 +90 +456 +780 +200 +The numbers arranged in ascending order are given below +3 +78 +90 +200 +456 +780 \ No newline at end of file diff --git a/c/Arrays/C Program to Sort the N Names in an Alphabetical Order.c b/c/Arrays/C Program to Sort the N Names in an Alphabetical Order.c new file mode 100644 index 0000000..acb9e66 --- /dev/null +++ b/c/Arrays/C Program to Sort the N Names in an Alphabetical Order.c @@ -0,0 +1,67 @@ +/*This C Program sorts the names in an alphabetical order. The program accepts names & then sorts the names in an alphabetical order using string operation.*/ + +/* + * C program to read N names, store them in the form of an array + * and sort them in alphabetical order. Output the given names and + * the sorted names in two columns side by side. + */ +#include +#include + +void main() +{ + char name[10][8], tname[10][8], temp[8]; + int i, j, n; + printf("Enter the value of n \n"); + scanf("%d", &n); + printf("Enter %d names n", \n); + for (i = 0; i < n; i++) + { + scanf("%s", name[i]); + strcpy(tname[i], name[i]); + } + for (i = 0; i < n - 1 ; i++) + { + for (j = i + 1; j < n; j++) + { + if (strcmp(name[i], name[j]) > 0) + { + strcpy(temp, name[i]); + strcpy(name[i], name[j]); + strcpy(name[j], temp); + } + } + } + printf("\n----------------------------------------\n"); + printf("Input NamestSorted names\n"); + printf("------------------------------------------\n"); + for (i = 0; i < n; i++) + { + printf("%s\t\t%s\n", tname[i], name[i]); + } + printf("------------------------------------------\n"); +} + +/* +Enter the value of n +7 +Enter 7 names +heap +stack +queue +object +class +program +project + +---------------------------------------- +Input Names Sorted names +------------------------------------------ +heap class +stack heap +queue object +object program +class project +program queue +project stack +------------------------------------------ \ No newline at end of file diff --git a/c/Arrays/C Program to Split an Array from Specified Position & Add First Part to the End.c b/c/Arrays/C Program to Split an Array from Specified Position & Add First Part to the End.c new file mode 100644 index 0000000..53256d1 --- /dev/null +++ b/c/Arrays/C Program to Split an Array from Specified Position & Add First Part to the End.c @@ -0,0 +1,49 @@ +/*This C Program splits an array from specified position & add first part to the end. This program first accepts an array. Then splits an array according to the user specification. Now it becomes 2 parts & then add first part of an array at the end of a second part.*/ + +/* + * C program to read an array, accept a key & split the array. + * Add the first half to the end of second half. + */ +#include + +void main () +{ + int number[30]; + int i, n, a, j; + printf("Enter the value of n\n"); + scanf("%d", &n); + printf("enter the numbers\n"); + for (i = 0; i < n; ++i) + scanf("%d", &number[i]); + printf("Enter the position of the element to split the array \n"); + scanf("%d", &a); + for (i = 0; i < a; ++i) + { + number[n] = number[0]; + for (j = 0; j < n; ++j) + { + number[j] = number[j + 1]; + } + } + printf("The resultant array is\n"); + for (i = 0; i < n; ++i) + { + printf("%d\n", number[i]); + } +} + +/* +Enter the value of n +4 +enter the numbers +3 +678 +345 +876 +Enter the position of the element to split the array +3 +The resultant array is +876 +3 +678 +345 diff --git a/c/Arrays/C Program to accept Sorted Array and do Search using Binary Search.c b/c/Arrays/C Program to accept Sorted Array and do Search using Binary Search.c new file mode 100644 index 0000000..9cb7827 --- /dev/null +++ b/c/Arrays/C Program to accept Sorted Array and do Search using Binary Search.c @@ -0,0 +1,114 @@ +/*This C Program accepts the sorted array and does search using Binary search. Binary search is an algorithm for locating the position of an item in a sorted array. A search of sorted data, in which the middle position is examined first. Search continues with either the left or the right portion of the data, thus eliminating half of the remaining search space. In other words, a search which can be applied to an ordered linear list to progressively divide the possible scope of a search in half until the search object is found.*/ + +/* + * C program to accept N numbers sorted in ascending order + * and to search for a given number using binary search. + * Report success or failure. + */ +#include + +void main() +{ + int array[10]; + int i, j, num, temp, keynum; + int low, mid, high; + printf("Enter the value of num \n"); + scanf("%d", &num); + printf("Enter the elements one by one \n"); + for (i = 0; i < num; i++) + { + scanf("%d", &array[i]); + } + printf("Input array elements \n"); + for (i = 0; i < num; i++) + { + printf("%d\n", array[i]); + } + /* Bubble sorting begins */ + for (i = 0; i < num; i++) + { + for (j = 0; j < (num - i - 1); j++) + { + if (array[j] > array[j + 1]) + { + temp = array[j]; + array[j] = array[j + 1]; + array[j + 1] = temp; + } + } + } + printf("Sorted array is...\n"); + for (i = 0; i < num; i++) + { + printf("%d\n", array[i]); + } + printf("Enter the element to be searched \n"); + scanf("%d", &keynum); + /* Binary searching begins */ + low = 1; + high = num; + do + { + mid = (low + high) / 2; + if (keynum < array[mid]) + high = mid - 1; + else if (keynum > array[mid]) + low = mid + 1; + } + while (keynum != array[mid] && low <= high); + if (keynum == array[mid]) + { + printf("SEARCH SUCCESSFUL \n"); + } + else + { + printf("SEARCH FAILED \n"); + } +} + +/* +Enter the value of num +5 +Enter the elements one by one +23 +90 +56 +15 +58 +Input array elements +23 +90 +56 +15 +58 +Sorted array is... +15 +23 +56 +58 +90 +Enter the element to be searched +58 +SEARCH SUCCESSFUL + +$ a.out +Enter the value of num +4 +Enter the elements one by one +1 +98 +65 +45 +Input array elements +1 +98 +65 +45 +Sorted array is... +1 +45 +65 +98 +Enter the element to be searched +6 +SEARCH FAILED \ No newline at end of file diff --git a/c/Arrays/C Program to calculate sum of list by passing an array to a function.c b/c/Arrays/C Program to calculate sum of list by passing an array to a function.c new file mode 100644 index 0000000..d559680 --- /dev/null +++ b/c/Arrays/C Program to calculate sum of list by passing an array to a function.c @@ -0,0 +1,39 @@ +/* Sum of list - Program to calculate sum of list by passing an array to a function - May 2013 */ + +#include +#include + +int findsum(int x[ ], int n) ; + +void main() +{ + int i, n, x[50] ; + clrscr() ; + printf("Enter the number of elements: ") ; + scanf("%d", &n) ; + printf("Enter the elements: \n") ; + for(i=0 ; i +#include + +int findsum(int x[ ], int n) ; + +void main() +{ + int i, n, x[50] ; + clrscr() ; + printf("Enter the number of elements: ") ; + scanf("%d", &n) ; + printf("Enter the elements: \n") ; + for(i=0 ; i +#include + +void main() +{ + int x[10][10], nr, nc, r, c, flag ; + clrscr() ; + printf("Enter the number of rows and columns: ") ; + scanf("%d %d", &nr, &nc) ; + if(nr==nc) /* checking for square matrix */ + { + printf("Enter elements of the matrix: \n") ; + for(r=0 ; r +#include + +void main() +{ + int x[10][10], nr, nc, r, c, flag ; + clrscr() ; + printf("Enter the number of rows and columns: ") ; + scanf("%d %d", &nr, &nc) ; + if(nr==nc) /* checking for square matrix */ + { + printf("Enter elements of the matrix row-wise: \n") ; + for(r=0 ; r +#include +#include +#include + +void main() +{ + char str[50] ; + int i, j, length, flag ; + clrscr() ; + printf("Enter a string: ") ; + gets(str) ; + length=strlen(str) ; + flag=1 ; /* assuming that the string is a palindrome */ + i=0 ; + j=length-1 ; + while(i +#include + +void main() +{ + float x[4][6] = {23.2, 31.5, 16.9, 28.0, 26.3, 28.2, 34.8, 45.2, 20.8, 39.4, 33.4, 36.8, 19.4, 50.6, 45.1, 20.8, 50.6, 13.4, 36.9, 42.7, 20.8, + 10.2, 16.8, 42.7 + } ; + float sum ; + int r, c ; + clrscr() ; + for(r=0 ; r<4 ; r++) + { + sum = 0 ; + for(c=0 ; c<6 ; c++) + sum = sum + x[r][c]; + printf("Test results average for experiment number %d is %f \n", r+1, sum/6 ); + } + getch(); +} + +/* +Output: + +Test results average for experiment number 1 is 25.683332 +Test results average for experiment number 2 is 35.066669 +Test results average for experiment number 3 is 33.316666 +Test results average for experiment number 4 is 28.350000 +*/ + diff --git a/c/Arrays/C Program to concatenate two strings and find string length using functions.c b/c/Arrays/C Program to concatenate two strings and find string length using functions.c new file mode 100644 index 0000000..15b2663 --- /dev/null +++ b/c/Arrays/C Program to concatenate two strings and find string length using functions.c @@ -0,0 +1,56 @@ +/* String concatenate and length - Program to concatenate two strings and find string length using functions */ + +#include +#include + +void concatenate(char str1[ ], char str2[ ]) ; +int stringlength(char str[ ]) ; + +void main() +{ + char str1[50], str2[50], str[50] ; + clrscr(); + printf("Performing string concatenation \n") ; + printf("Enter two strings:\n") ; + gets(str1) ; + gets(str2) ; + concatenate(str1,str2) ; + printf("Concatenated string is: ") ; + puts(str1); + printf("\nFinding string length \n") ; + printf("Enter a string: ") ; + gets(str) ; + printf("String length is: %d", stringlength(str) ) ; + getch(); +} + +void concatenate(char str1[ ], char str2[ ]) +{ + int i, j ; + for(i=0 ; str1[i]!='\0' ; i++) ; + for(j=0 ; str2[j]!='\0' ; j++, i++) + str1[i]=str2[j] ; + str1[i]='\0' ; +} + +int stringlength(char str[ ]) +{ + int i ; + for(i=0 ; str[i]!='\0' ; i++) ; + return i ; +} + +/* +Output: + +Performing string concatenation +Enter two strings: +New +York +Concatenated string is: NewYork + +Finding string length +Enter a string: Apple +String length is: 5 +*/ + diff --git a/c/Arrays/C Program to copy one string into another using a function.c b/c/Arrays/C Program to copy one string into another using a function.c new file mode 100644 index 0000000..8e638d3 --- /dev/null +++ b/c/Arrays/C Program to copy one string into another using a function.c @@ -0,0 +1,35 @@ +/* String Copying - Program to copy one string into another using a function */ + +#include +#include + +void copy(char str1[ ], char str2[ ]) ; +/* This function will copy contents of string 2 in string 1 */ + +void main() +{ + char str1[50], str2[50] ; + clrscr(); + printf("Enter source string: ") ; + gets(str2) ; + copy(str1,str2) ; + printf("Copied string: %s", str1) ; + getch(); +} + +void copy(char str1[ ], char str2[ ]) +{ + int i, j ; + for(i=0, j=0 ; str2[i]!='\0' ; j++, i++) + str1[j]=str2[i] ; + str1[j]='\0' ; +} + +/* +Output: + +Enter source string: SPA sem 2 +Copied string: SPA sem 2 +*/ + + diff --git a/c/Arrays/C Program to count frequency of a given character in a string.c b/c/Arrays/C Program to count frequency of a given character in a string.c new file mode 100644 index 0000000..206288c --- /dev/null +++ b/c/Arrays/C Program to count frequency of a given character in a string.c @@ -0,0 +1,29 @@ +/* String Frequency Count - Program to count frequency of a given character in a string */ + +#include +#include + +void main() +{ + char str[50], x ; + int i, count=0 ; + clrscr() ; + printf("Enter a string: ") ; + gets(str) ; + printf("Enter a character: ") ; + x=getchar() ; + for(i=0 ; str[i]!='\0' ; i++) + if(str[i]==x) + count++; + printf("Frequency of %c in %s is %d", x, str, count) ; + getch() ; +} + +/* +Output: + +Enter a string: programming +Enter a character: m +Frequency of m in programming is 2 +*/ + diff --git a/c/Arrays/C Program to count the number of vowels in a given string using switch statement.c b/c/Arrays/C Program to count the number of vowels in a given string using switch statement.c new file mode 100644 index 0000000..650765a --- /dev/null +++ b/c/Arrays/C Program to count the number of vowels in a given string using switch statement.c @@ -0,0 +1,41 @@ +/* String vowel count - Program to count the number of vowels in a given string using switch statement */ + +/* Assume y is not a vowel*/ +#include +#include +#include + +void main() +{ + char str[50], c ; + int i, v=0 ; + clrscr() ; + printf("Enter a string: ") ; + gets(str) ; + for(i=0 ; str[i]!='\0' ; i++) + { + c=tolower(str[i]) ; + switch(c) + { + case 'a': + case 'e': + case 'i': + case 'o': + case 'u': + v++ ; + break; + default: + break; + } + } + printf("Number of vowels in %s is %d", str, v) ; + getch() ; +} + +/* +Output: + +Enter a string: Umbrella is nice +Number of vowels in Umbrella is nice is 6 + +*/ diff --git a/c/Arrays/C Program to count the number of vowels in a given string.c b/c/Arrays/C Program to count the number of vowels in a given string.c new file mode 100644 index 0000000..0813795 --- /dev/null +++ b/c/Arrays/C Program to count the number of vowels in a given string.c @@ -0,0 +1,31 @@ +/* String vowel count - Program to count the number of vowels in a given string */ + +/* Assume y is not a vowel*/ +#include +#include +#include + +void main() +{ + char str[50], c ; + int i, v=0 ; + clrscr() ; + printf("Enter a string: ") ; + gets(str) ; + for(i=0 ; str[i]!='\0' ; i++) + { + c=tolower(str[i]) ; + if(c=='a' || c=='e' || c=='i' || c=='o' || c=='u') + v++ ; + } + printf("Number of vowels in %s is %d", str, v) ; + getch() ; +} + +/* +Output: + +Enter a string: Umbrella is nice +Number of vowels in Umbrella is nice is 6 + +*/ diff --git a/c/Arrays/C Program to count the number of whitespaces , digits , alphabets and other characters in a given string.c b/c/Arrays/C Program to count the number of whitespaces , digits , alphabets and other characters in a given string.c new file mode 100644 index 0000000..cabc1f3 --- /dev/null +++ b/c/Arrays/C Program to count the number of whitespaces , digits , alphabets and other characters in a given string.c @@ -0,0 +1,41 @@ +/* String Analysis - Program to count the number of whitespaces , digits , alphabets and other characters in a given string */ + +#include +#include + +void main() +{ + char str[50], c ; + int i, letter=0, digit=0, white=0, other=0 ; + clrscr(); + printf("Enter a string: ") ; + gets(str) ; + for(i=0 ; str[i]!='\0' ; i++) + { + c=str[i] ; + if( c>='0' && c<='9' ) + digit++ ; + else if( (c>='A' && c<='Z') || (c>='a' && c<='z') ) + letter++ ; + else if(c==' ' || c=='\t') + white++ ; + else + other++ ; + } + printf("There are %d alphabets in the given string \n", letter) ; + printf("There are %d digits in the given string \n", digit) ; + printf("There are %d whitespace characters in the given string \n", white) ; + printf("There are %d other characters in the given string", other) ; + getch(); +} +/* +Output: + +Enter a string: ab#2 @45 DM +There are 4 alphabets in the given string +There are 3 digits in the given string +There are 2 whitespace characters in the given string +There are 2 other characters in the given string +*/ +/* There is a tab between 2 and @ in the above output */ + diff --git a/c/Arrays/C Program to cyclically rotate elements in array..c b/c/Arrays/C Program to cyclically rotate elements in array..c new file mode 100644 index 0000000..3f54939 --- /dev/null +++ b/c/Arrays/C Program to cyclically rotate elements in array..c @@ -0,0 +1,83 @@ +/* Cyclic rotation of array elements - Program to cyclically rotate elements in array. Program should accept a choice that in which direction to rotate - left or right. Suppose array A contains elements {1,2,3,4,5} and if choice is right then o/p should be {5,1,2,3,4} and if choice is left then o/p should be {2,3,4,5,1} */ + +#include +#include + +void main() +{ + int i, n, t, x[50] ; + char choice; + clrscr() ; + printf("Enter the number of elements: ") ; + scanf("%d", &n) ; + printf("Enter the elements: \n") ; + for(i=0 ; i=1 ; i--) + x[i]=x[i-1] ; + x[0]=t ; + } + else if(choice=='L'||choice=='l') + { + /* Rotating elements to left */ + t=x[0] ; + for(i=0 ; i<=n-2 ; i++) + x[i]=x[i+1] ; + x[n-1]=t ; + } + else + printf("Wrong choice entered. \n") ; + printf("New array is as shown: \n") ; + for(i=0 ; i +#include + +void main() +{ + int i, key, n, position, flag, x[50] ; + clrscr() ; + printf("Enter the number of elements: ") ; + scanf("%d", &n) ; + printf("Enter the elements: \n") ; + for(i=0 ; i +#include + +void main() +{ + int i, j, k, m, n, x[50] ; + clrscr() ; + printf("Enter the number of elements: ") ; + scanf("%d", &n) ; + printf("Enter the elements: \n") ; + for(i=0 ; i +#include + +int sequential(int x[ ], int n, int key) ; + +void main() +{ + int i, n, x[20], key ; + clrscr() ; + printf("Enter the number of elements: ") ; + scanf("%d", &n) ; + printf("Enter the elements:\n") ; + for(i=0 ; i +#include + +void main() +{ + int x[10][10], nr, nc, r, c, min, max ; + clrscr() ; + printf("Enter the number of rows and columns: ") ; + scanf("%d %d", &nr, &nc) ; + printf("Enter elements of the matrix row-wise: \n") ; + for(r=0 ; rmax) + max=x[r][c]; + } + printf("Minimum is %d \n", min) ; + printf("Maximum is %d", max) ; + getch(); +} + +/* +Output: + +Enter the number of rows and columns: 2 3 +Enter elements of the matrix: +2 5 1 +8 6 4 +Minimum is 1 +Maximum is 8 +*/ + diff --git a/c/Arrays/C Program to find reverse of given string without using string library function.c b/c/Arrays/C Program to find reverse of given string without using string library function.c new file mode 100644 index 0000000..44fcf10 --- /dev/null +++ b/c/Arrays/C Program to find reverse of given string without using string library function.c @@ -0,0 +1,37 @@ +/* String Reverse - Program to find reverse of given string without using string library function */ + +#include +#include + +void reverse(char str1[ ], char str2[ ]) ; +/* This function will store reverse of string 1 in string 2 */ + +void main() +{ + char str1[50], str2[50] ; + clrscr(); + printf("Enter the string: ") ; + gets(str1) ; + reverse(str1,str2) ; + printf("Reversed string is: %s", str2) ; + getch(); +} + +void reverse(char str1[ ], char str2[ ]) +{ + int i, j ; + for(i=0 ; str1[i]!='\0' ; i++) ; + for(i=i-1, j=0 ; i>=0 ; i--, j++) + str2[j]=str1[i] ; + str2[j]='\0' ; +} + +/* +Output: + +Enter the string: Sandeep Gupta +Reversed string is: atpuG peednaS +*/ + + + diff --git a/c/Arrays/C Program to find sum and difference of two matrices.c b/c/Arrays/C Program to find sum and difference of two matrices.c new file mode 100644 index 0000000..2c28c3f --- /dev/null +++ b/c/Arrays/C Program to find sum and difference of two matrices.c @@ -0,0 +1,89 @@ +/* Matrix Sum and Difference - Program to find sum and difference of two matrices */ + +#include +#include + +void read(int x[ ][10], int nr, int nc) ; +void sumdiff(int a[ ][10], int b[ ][10], int s[ ][10], int d[ ][10], int nr, int nc) ; +void show(int y[ ][10], int nr, int nc) ; + + +void main() +{ + int a[10][10], b[10][10], s[10][10], d[10][10], nra, nca, nrb, ncb ; + clrscr(); + printf("Enter the number of rows and columns of first matrix: "); + scanf("%d %d", &nra, &nca) ; + printf("Enter the number of rows and columns of second matrix: "); + scanf("%d %d", &nrb, &ncb) ; + if(nra==nrb && nca==ncb) + { + printf("Enter elements of first matrix row-wise: \n") ; + read(a,nra,nca) ; + printf("Enter elements of second matrix row-wise: \n") ; + read(b,nrb,ncb) ; + sumdiff(a,b,s,d,nra,nca); + printf("Result of matrix addition is: \n") ; + show(s,nra,nca) ; + printf("Result of matrix subtraction is: \n") ; + show(d,nra,nca) ; + } + else + printf("Matrix addition and subtraction not possible."); + getch(); +} + +void read(int x[ ][10], int nr, int nc) +{ + int r, c ; + for(r=0 ; r +#include + +void main() +{ + int x[10][10], nr, nc, r, c, sum=0 ; + clrscr() ; + printf("Enter the number of rows and columns: ") ; + scanf("%d %d", &nr, &nc) ; + printf("Enter elements of the matrix row-wise: \n") ; + for(r=0 ; r +#include + +void main() +{ + int x[10][10], nr, nc, r, c, sum ; + clrscr() ; + printf("Enter the number of rows and columns: ") ; + scanf("%d %d", &nr, &nc) ; + printf("Enter elements of the matrix row-wise: \n") ; + for(r=0 ; r +#include + +void main() +{ + int x[10][10], nr, nc, r, c, sumd=0, suma=0, sumb=0 ; + clrscr() ; + printf("Enter the number of rows and columns: ") ; + scanf("%d %d", &nr, &nc) ; + printf("Enter elements of the matrix row-wise: \n") ; + for(r=0 ; rc) + sumb = sumb + x[r][c] ; + } + printf("The sum of all diagonal elements is %d \n", sumd) ; + printf("The sum of elements above diagonal is %d \n", suma) ; + printf("The sum of elements below diagonal is %d \n", sumb) ; + getch() ; +} + +/* The following logic is also correct + for(r=0 ; r +#include + +void sort(int x[ ], int n); + +void main() +{ + int i, n, x[50] ; + clrscr() ; + printf("Enter the number of elements: ") ; + scanf("%d", &n) ; + printf("Enter the elements: \n") ; + for(i=0 ; i +void main() +{ + int a[5],max,i; + printf("enter element for the array: "); + for(i=0; i<5; i++) + scanf("%d",&a[i]); + max=a[0]; + for(i=1; i<5; i++) + { + if(max + +void main() +{ + int n, i, j, c, t, b; + printf("Enter size of array : "); + scanf("%d", &n); + int array[n - 1]; /* array size-1 */ + printf("Enter elements into array : \n"); + for (i = 0; i < n - 1; i++) + scanf("%d", &array[i]); + b = array[0]; + for (i = 1; i < n - 1; i++) + b = b ^ array[i]; + for (i = 2, c = 1; i <= n; i++) + c = c ^ i; + c = c ^ b; + printf("Missing element is : %d \n", c); +} + +/* +Enter size of array : 6 +Enter elements into array : +1 +2 +3 +5 +6 +Missing element is : 4 \ No newline at end of file diff --git a/c/Arrays/C Program to perform matrix multiplication and transpose.c b/c/Arrays/C Program to perform matrix multiplication and transpose.c new file mode 100644 index 0000000..3b59cf9 --- /dev/null +++ b/c/Arrays/C Program to perform matrix multiplication and transpose.c @@ -0,0 +1,114 @@ +/* Matrix multiplication and Transpose - Program to perform matrix multiplication and transpose - May 2013 */ + +#include +#include + +void read(int x[ ][10], int nr, int nc) ; +void multiply(int a[ ][10], int b[ ][10], int c[ ][10], int l, int m, int n) ; +void transpose(int x[ ][10], int y[ ][10], int nr, int nc) ; +void show(int y[ ][10], int nr, int nc) ; + + +void main() +{ + int a[10][10], b[10][10], c[10][10], nra, nca, nrb, ncb ; + int x[10][10], y[10][10], m, n ; + clrscr(); + printf("Performing Matrix Multiplication \n \n") ; + printf("Enter the number of rows and columns of first matrix: ") ; + scanf("%d %d", &nra, &nca) ; + printf("Enter the number of rows and columns of second matrix: ") ; + scanf("%d %d", &nrb, &ncb) ; + if(nca==nrb) + { + printf("Enter elements of first matrix row-wise: \n") ; + read(a,nra,nca) ; + printf("Enter elements of second matrix row-wise: \n") ; + read(b,nrb,ncb) ; + multiply(a,b,c,nra,nca,ncb); + printf("Result of matrix multiplication is: \n") ; + show(c,nra,ncb) ; + } + else + printf("Matrices A and B do not conform to multiplication") ; + printf("\nPerforming Matrix transpose \n \n") ; + printf("Enter the number of rows and columns: ") ; + scanf("%d %d", &m, &n) ; + printf("Enter elements of the matrix row-wise:\n") ; + read(x, m, n) ; + transpose(x, y, m, n) ; + printf("Transpose of given matrix is:\n") ; + show(y,n,m) ; + getch() ; +} + +void read(int x[ ][10], int nr, int nc) +{ + int r, c ; + for(r=0 ; r +#include + +void main() +{ + char n[20] ; + int i; + clrscr(); + printf("Enter a positive integer: "); + gets(n); + printf("%s in words: ", n); + for(i=0 ; n[i]!='\0' ; i++) + { + switch(n[i]) + { + case '0': + printf("Zero "); + break; + case '1': + printf("One "); + break; + case '2': + printf("Two "); + break; + case '3': + printf("Three "); + break; + case '4': + printf("Four "); + break; + case '5': + printf("Five "); + break; + case '6': + printf("Six "); + break; + case '7': + printf("Seven "); + break; + case '8': + printf("Eight "); + break; + case '9': + printf("Nine "); + break; + } + } + getch(); +} + +/* +Output: + +Enter a positive integer: 1760 +1760 in words: One Seven Six Zero +*/ + diff --git a/c/Arrays/C Program to remove extra blank spaces from a string..c b/c/Arrays/C Program to remove extra blank spaces from a string..c new file mode 100644 index 0000000..ec0c95c --- /dev/null +++ b/c/Arrays/C Program to remove extra blank spaces from a string..c @@ -0,0 +1,34 @@ +/* String - Extra blank Spaces - Program to remove extra blank spaces from a string. For example , i/p: HellobbbWorld , o/p: HellobWorld , b - blank space */ + +#include +#include + +void main() +{ + char str[50] ; + int i ; + clrscr(); + printf("Enter a line: \n") ; + gets(str) ; + printf("Modified line is: \n") ; + for(i=0 ; str[i]!='\0' ; i++) + if(str[i]!=' ') + putchar(str[i]) ; + else + { + while(str[i]==' ') /* Skipping spaces */ + i++ ; + putchar(' ') ; + putchar(str[i]) ; + } + getch() ; +} +/* This program will not remove extra tabs since a tab is '\t' and we are checking only for blank space ( ' ' ) */ + +/* +Output: +Enter a line: +The boy ate the apple +Modified line is: +The boy ate the apple +*/ \ No newline at end of file diff --git a/c/Arrays/C Program to show sum of 10 elements of array & show the average.c b/c/Arrays/C Program to show sum of 10 elements of array & show the average.c new file mode 100644 index 0000000..5a53cfc --- /dev/null +++ b/c/Arrays/C Program to show sum of 10 elements of array & show the average.c @@ -0,0 +1,29 @@ +/*Program to show sum of 10 elements of array & show the average.*/ +#include +int main() +{ + int a[10],i,sum=0; + float av; + printf("enter elements of an aaray: "); + for(i=0; i<10; i++) + scanf("%d",&a[i]); + for(i=0; i<10; i++) + sum=sum+a[i]; + printf("sum=%d",sum); + av=sum/10; + printf("average=%.2f",av); + return 0; +} +Output: +enter elements of an array: 4 +4 +4 +4 +4 +4 +4 +4 +4 +4 +sum=40 + average=4.00 \ No newline at end of file diff --git a/c/Arrays/C Program to sort a list (array) of elements in descending order.c b/c/Arrays/C Program to sort a list (array) of elements in descending order.c new file mode 100644 index 0000000..ad3c81d --- /dev/null +++ b/c/Arrays/C Program to sort a list (array) of elements in descending order.c @@ -0,0 +1,47 @@ +/* Sorting (Bubble sort) - Program to sort a list (array) of elements in descending order - May 2013 */ + +#include +#include + +void sort(int x[ ], int n); + +void main() +{ + int i, n, x[50] ; + clrscr() ; + printf("Enter the number of elements: ") ; + scanf("%d", &n) ; + printf("Enter the elements: \n") ; + for(i=0 ; i x[j+1] */ + +/* +Output: + +Enter the number of elements: 5 +Enter the elements: +1 3 2 4 5 +Elements of list in descending order is as shown: +5 4 3 2 1 +*/ diff --git a/c/Arrays/C Program to sort the matrix rows and columns.c b/c/Arrays/C Program to sort the matrix rows and columns.c new file mode 100644 index 0000000..1d58133 --- /dev/null +++ b/c/Arrays/C Program to sort the matrix rows and columns.c @@ -0,0 +1,119 @@ +#include + +void main () { + + static int ma[10][10],mb[10][10]; + + int i,j,k,a,m,n; + + printf ("Enter the order of the matrix \n"); + + scanf ("%d %d", &m,&n); + + printf ("Enter co-efficients of the matrix \n"); + + for (i=0;i ma[i][k]) { + + a = ma[i][j]; + + ma[i][j] = ma[i][k]; + + ma[i][k] = a; + + } + + } + + } + + } + + /* End of outer for loop*/ + + for (i=0;i +#include + +void main() +{ + int m ; + char x[12][10] = {"January", "February", "March", "April", "May", "June", "July", "August", "September", "October", + "November", "December" + } ; + clrscr(); + printf("Enter the month number: ") ; + scanf("%d", &m) ; + printf("Month in words is: %s", x[m-1]) ; + getch(); +} + +/* +Output: + +Enter the month number: 7 +Month in words is: July +*/ + + + + diff --git a/c/Arrays/C program to Remove duplicate number from array.c b/c/Arrays/C program to Remove duplicate number from array.c new file mode 100644 index 0000000..0b0c3a5 --- /dev/null +++ b/c/Arrays/C program to Remove duplicate number from array.c @@ -0,0 +1,36 @@ +/*Remove duplicate number from array*/ +#include +#define MAX 100 +void main() +{ + int arr[MAX],n,i,j,k,temp,size=0; + printf("Enter size of Array: "); + scanf("%d",&n); + printf("Enter %d elements\n",n); + for(i=0; i +#define MAX 100 +void main() +{ + int arr[MAX],n,i,temp; + printf("Enter size of Array: "); + scanf("%d",&n); + printf("Enter %d elements\n",n); + for(i=0; i +void main() +{ + int a[10],b[10],c[10],i; + printf("Enter First array->"); + for(i=0; i<10; i++) + scanf("%d",&a[i]); + printf("\nEnter Second array->"); + for(i=0; i<10; i++) + scanf("%d",&b[i]); + printf("Arrays before swapping"); + printf("\nFirst array->"); + for(i=0; i<10; i++) + { + printf("%d",a[i]); + } + printf("\nSecond array->"); + for(i=0; i<10; i++) + { + printf("%d",b[i]); + } + for(i=0; i<10; i++) + { + //write any swapping technique + c[i]=a[i]; + a[i]=b[i]; + b[i]=c[i]; + } + printf("\nArrays after swapping"); + printf("\nFirst array->"); + for(i=0; i<10; i++) + { + printf("%d",a[i]); + } + printf("\nSecond array->"); + for(i=0; i<10; i++) + { + printf("%d",b[i]); + } +} \ No newline at end of file diff --git a/c/Arrays/Find the sum of two one-dimensional arrays using Dynamic Memory Allocation.c b/c/Arrays/Find the sum of two one-dimensional arrays using Dynamic Memory Allocation.c new file mode 100644 index 0000000..e916ce4 --- /dev/null +++ b/c/Arrays/Find the sum of two one-dimensional arrays using Dynamic Memory Allocation.c @@ -0,0 +1,28 @@ + #include + #include + #include + void main() { + int i,n; + int *a,*b,*c; + printf("How many Elements in each array...\n"); + scanf("%d", &n); + a = (int *) malloc(n*sizeof(int)); + b = (int *) malloc(n*sizeof(int)); + c =( int *) malloc(n*sizeof(int)); + printf("Enter Elements of First List\n"); + for (i=0;i + #define SIZE 12 + + int main() + { + int a[ SIZE ] = { 1, 3, 5, 4, 7, 2, 99, 16, 45, 67, 89, 45 }; + int i; + int total = 0; + + for ( i = 0; i < SIZE; i++ ) { + total += a[ i ]; + } + + printf( "Total of array element values is %d\n", total ); + + return 0; + + } \ No newline at end of file diff --git a/c/Arrays/To sort array of Structure.c b/c/Arrays/To sort array of Structure.c new file mode 100644 index 0000000..1cf0582 --- /dev/null +++ b/c/Arrays/To sort array of Structure.c @@ -0,0 +1,52 @@ + #include + #define M 50 + + struct state { + char name[50]; + long int population; + float literacyRate; + float income; + } st[M]; /* array of structure */ + + int main() { + int i, n, ml, mi, maximumLiteracyRate, maximumIncome; + float rate; + ml = mi = -1; + maximumLiteracyRate = maximumIncome = 0; + + printf("Enter how many states:"); + scanf("%d", &n); + + for (i = 0; i < n; i++) { + printf("\nEnter state %d details :", i); + + printf("\nEnter state name : "); + scanf("%s", &st[i].name); + + printf("\nEnter total population : "); + scanf("%ld", &st[i].population); + + printf("\nEnter total literary rate : "); + scanf("%f", &rate); + st[i].literacyRate = rate; + + printf("\nEnter total income : "); + scanf("%f", &st[i].income); + } + + for (i = 0; i < n; i++) { + if (st[i].literacyRate >= maximumLiteracyRate) { + maximumLiteracyRate = st[i].literacyRate; + ml++; + } + if (st[i].income > maximumIncome) { + maximumIncome = st[i].income; + mi++; + } + } + + printf("\nState with highest literary rate :%s", st[ml].name); + printf("\nState with highest income :%s", st[mi].name); + + return (0); + } \ No newline at end of file diff --git a/c/Arrays/WAP Mathematical Operations on an Array.c b/c/Arrays/WAP Mathematical Operations on an Array.c new file mode 100644 index 0000000..807be53 --- /dev/null +++ b/c/Arrays/WAP Mathematical Operations on an Array.c @@ -0,0 +1,32 @@ + #include + #define MAXSIZE 10 + void main() { + int array[MAXSIZE]; + int i, num, negative_sum = 0, positive_sum = 0; + float total = 0.0, average; + printf ("Enter the value of N \n"); + scanf("%d", &num); + printf("Enter %d numbers (-ve, +ve and zero) \n", num); + for (i = 0; i < num; i++) { + scanf("%d", &array[i]); + } + printf("Input array elements \n"); + for (i = 0; i < num; i++) { + printf("%+3d\n", array[i]); + } + /* Summation starts */ + for (i = 0; i < num; i++) { + if (array[i] < 0) { + negative_sum = negative_sum + array[i]; + } else if (array[i] > 0) { + positive_sum = positive_sum + array[i]; + } else if (array[i] == 0) { + ; + } + total = total + array[i] ; + } + average = total / num; + printf("\n Sum of all negative numbers = %d\n", negative_sum); + printf("Sum of all positive numbers = %d\n", positive_sum); + printf("\n Average of all input numbers = %.2f\n", average); + } \ No newline at end of file diff --git a/c/Bitwise/C Program To Identify the Missing Number in an Integer Array of Size N-1 with Numbers[1,N].c b/c/Bitwise/C Program To Identify the Missing Number in an Integer Array of Size N-1 with Numbers[1,N].c new file mode 100644 index 0000000..77d1fc0 --- /dev/null +++ b/c/Bitwise/C Program To Identify the Missing Number in an Integer Array of Size N-1 with Numbers[1,N].c @@ -0,0 +1,34 @@ +/* + * C Program To Identify the Missing Number in an Integer + * Array of Size N-1 with Numbers[1,N] + */ +#include +#define MAX 15 +int missing_number_array(int [],int); + +int main() +{ + int a[MAX], num, i, n; + printf("enter the range of array\n"); + scanf("%d", &n); + for (i = 0; i < n; i++) + { + printf("enter a[%d]element into the array:", i); + scanf("%d", &a[i]); + } + num = missing_number_array(a, n); + printf("The missing number -> %d\n", num); +} + +/* To find the missing number in array */ +int missing_number_array(int a[], int n) +{ + int i; + int s1 = 0; + int s2 = 0; + for (i = 0; i < n; i++) + s1 = s1 ^ a[i]; + for (i = 1; i <= n + 1; i++) + s2 = s2 ^ i; + return (s1 ^ s2); +} \ No newline at end of file diff --git a/c/Bitwise/C Program takes Byte as Input and returns all the Bits between given Positions.c b/c/Bitwise/C Program takes Byte as Input and returns all the Bits between given Positions.c new file mode 100644 index 0000000..ecb13af --- /dev/null +++ b/c/Bitwise/C Program takes Byte as Input and returns all the Bits between given Positions.c @@ -0,0 +1,36 @@ +/* + * C Program takes Byte as Input and returns all the Bits between + * given Positions + */ +#include + +int number_between_bit_positions(int,int,int); +int result = 0; + +int main() +{ + int number, start_pos, end_pos; + printf("\nEnter the number"); + scanf("%d", &number); + printf("\nEnter the position of a and b"); + scanf("%d %d", &start_pos, &end_pos); + result = number_between_bit_positions(number, start_pos, end_pos); + printf("Byte Equivalent of bits between %d and %d positions %d", start_pos, end_pos, result); +} + +int number_between_bit_positions(int number, int start_pos, int end_pos) +{ + int i, j, shift_num, res_val; + /* + * Right shift to the specified start position,take the corresponding bits using & + * Left shift to locate the bits in their respective positions + */ + for (i = start_pos, j = 0; i <= end_pos; i++,j++) + { + shift_num = number >> i; + res_val = shift_num & 1; + res_val = res_val << j; + result += res_val; + } + return result; +} \ No newline at end of file diff --git a/c/Bitwise/C Program that uses Function to return MSB position of unsigned Integer.c b/c/Bitwise/C Program that uses Function to return MSB position of unsigned Integer.c new file mode 100644 index 0000000..76f5d6d --- /dev/null +++ b/c/Bitwise/C Program that uses Function to return MSB position of unsigned Integer.c @@ -0,0 +1,34 @@ +/* + * C Program that uses Function to return MSB position of unsigned Integer + */ +#include +#define NUM_BITS_INT 32 +int int_msb_position(int n); + +void main() +{ + int n, pos; + printf("Enter a number : "); + scanf("%d", &n); + pos = int_msb_position(n); + printf("\nPosition of MSB bit = %d\n", NUM_BITS_INT - (pos + 1)); +} + +/* Function to find the MSB bit position */ +int int_msb_position(int n) +{ + int i = 0, bit; + while (i < NUM_BITS_INT) + { + bit = n & 0x80000000; + if (bit == -0x80000000) + { + bit = 1; + } + if (bit == 1) + break; + n = n << 1; + i++; + } + return i; +} \ No newline at end of file diff --git a/c/Bitwise/C Program to Check if All the Bits of a given Integer is One(1).c b/c/Bitwise/C Program to Check if All the Bits of a given Integer is One(1).c new file mode 100644 index 0000000..fe379e8 --- /dev/null +++ b/c/Bitwise/C Program to Check if All the Bits of a given Integer is One(1).c @@ -0,0 +1,40 @@ +/* + * C Program to check if all the bits of a given integer is one(1) + */ +#include + +int all_bits_one(int); +int count = 0; + +void main() +{ + int num; + printf("enter the number:"); + scanf("%d", &num); + num++; + all_bits_one(num); + if (count) + { + printf("false"); + } + else + { + printf("true"); + } +} + +/* checks whether all bits are 1 */ +int all_bits_one(int x) +{ + if (x == 1) + return 0; + if (x % 2 != 0) + { + count++; + } + else + { + x = x / 2; + all_bits_one(x); + } +} \ No newline at end of file diff --git a/c/Bitwise/C Program to Check if a given Bit Position is set to One or not.c b/c/Bitwise/C Program to Check if a given Bit Position is set to One or not.c new file mode 100644 index 0000000..386f177 --- /dev/null +++ b/c/Bitwise/C Program to Check if a given Bit Position is set to One or not.c @@ -0,0 +1,19 @@ +/* + * C Program to Check if a given Bit Position is set to One or not + */ +#include + +void main() +{ + unsigned int number; + int result, position; + printf("Enter the unsigned integer:\n"); + scanf("%d", &number); + printf("enter position to be searched\n"); + scanf("%d", &position); + result = (number >> (position)); + if (result & 1) + printf("TRUE\n"); + else + printf("FALSE\n"); +} \ No newline at end of file diff --git a/c/Bitwise/C Program to Check if a given Integer is Power of 2 using Bitwise Operators.c b/c/Bitwise/C Program to Check if a given Integer is Power of 2 using Bitwise Operators.c new file mode 100644 index 0000000..bdca8f7 --- /dev/null +++ b/c/Bitwise/C Program to Check if a given Integer is Power of 2 using Bitwise Operators.c @@ -0,0 +1,38 @@ +/* + * C Program to Check if a given Integer is Power of 2 using Bitwise Operators + */ +#include +#define NUM_BITS_INT (8*sizeof(int)) + +int power_of_2(unsigned int); + +int main() +{ + unsigned int num; + printf("\nEnter Number"); + scanf("%d", &num); + power_of_2(num); +} + +/* + * Finding the power of 2 using bit wise operators + */ +int power_of_2(unsigned int x) +{ + int i, count = 0, result, shift_num; + for (i = 0; i <= NUM_BITS_INT; i++) + { + shift_num = x >> i; + result = shift_num & 1; + if (res == 1) + count++; + } + /* + *If number of bits set to 1 are odd then the number is power of 2 + *If number of bits set to 0 are even then the number is not power of 2 + */ + if (count % 2 == 1) + printf("YES"); + else + printf("NO"); +} \ No newline at end of file diff --git a/c/Bitwise/C Program to Check if nth Bit in a 32-bit Integer is Set or not.c b/c/Bitwise/C Program to Check if nth Bit in a 32-bit Integer is Set or not.c new file mode 100644 index 0000000..ba67b33 --- /dev/null +++ b/c/Bitwise/C Program to Check if nth Bit in a 32-bit Integer is Set or not.c @@ -0,0 +1,29 @@ +/* + * C Program to Check if nth Bit in a 32-bit Integer is Set or not + */ +#include + +/* gloabal varaibles */ +int result,position; +/* function prototype */ +int n_bit_position(int x,int position); + +void main() +{ + unsigned int number; + printf("Enter the unsigned integer:\n"); + scanf("%d", &number); + printf("enter position\n"); + scanf("%d", &position); + n_bit_position(i, position); + if (result & 1) + printf("YES\n"); + else + printf("NO\n"); +} + +/* function to check whether the position is set to 1 or not */ +int n_bit_position(int number,int position) +{ + result = (number>>(position)); +} \ No newline at end of file diff --git a/c/Bitwise/C Program to Check whether the given Integer has an Alternate Pattern.c b/c/Bitwise/C Program to Check whether the given Integer has an Alternate Pattern.c new file mode 100644 index 0000000..5d81079 --- /dev/null +++ b/c/Bitwise/C Program to Check whether the given Integer has an Alternate Pattern.c @@ -0,0 +1,36 @@ +/* + * C Program to Check whether the given Integer has an Alternate + * Pattern + */ +#include + +void main() +{ + int num, x, y, count = 0; + printf("enter the number:"); + scanf("%d", &num); + x = num << 1; + y = x ^ num; + y = y + 1; + /* Checks if the number is in powers of 2 */ + while ((y / 2) != 0) + { + if (y % 2 != 0) + { + count++; + break; + } + else + { + y = y / 2; + } + } + if (count) + { + printf("false"); + } + else + { + printf("true"); + } +} \ No newline at end of file diff --git a/c/Bitwise/C Program to Check whether the given Number is Palindrome or not using Bitwise Operator.c b/c/Bitwise/C Program to Check whether the given Number is Palindrome or not using Bitwise Operator.c new file mode 100644 index 0000000..f39aecb --- /dev/null +++ b/c/Bitwise/C Program to Check whether the given Number is Palindrome or not using Bitwise Operator.c @@ -0,0 +1,57 @@ +/* + * C Program to Check whether the given Number is Palindrome + * or not using Bitwise Operator + */ +#include +#include +#define SIZE 8 +/* Function Prototype */ +int is_palindrome(unsigned char[]); + +void main() +{ + int num, num1 = 0, i = 0, j = SIZE - 1, res; + unsigned char c[SIZE]; + printf("Enter a number(max 255)"); + scanf("%d", &num); + num1 = num; + while (num != 0) + { + c[j] = num&1; + j--; + num = num>>1; /* Shifting right the given number by 1 bit */ + } + printf("The number %d in binary is:", num1); + for (i = 0; i < SIZE; i++) + { + printf("%d", c[i]); + } + res = is_palindrome(c); /* Calling Function */ + if (res == 0) + { + printf("\nNUMBER IS PALINDROME\n"); + } + else + { + printf("\nNUMBER IS NOT PALINDROME\n"); + } +} + +/* Code to check if the number is palindrome or not */ +int is_palindrome(unsigned char c[]) +{ + char temp[SIZE]; + int i, j, flag = 0; + for (i = 0, j = SIZE - 1; i < SIZE, j >= 0; i++, j--) + { + temp[j] = c[i]; + } + for (i = 0; i < SIZE; i++) + { + if (temp[i] != c[i]) + { + flag = 1; + } + } + return flag; +} \ No newline at end of file diff --git a/c/Bitwise/C Program to Count Number of bits set to 0 in an Integer.c b/c/Bitwise/C Program to Count Number of bits set to 0 in an Integer.c new file mode 100644 index 0000000..8df33d6 --- /dev/null +++ b/c/Bitwise/C Program to Count Number of bits set to 0 in an Integer.c @@ -0,0 +1,26 @@ +/* + * C Program to Count Number of bits set to 0 in a Integer x + */ +#include +#define NUM_BITS_INT (8*sizeof(int)) + +int count_unset(int); + +int main() +{ + int i, num, snum, res, count = 0; + printf("\nEnter the number"); + scanf("%d", &num); + /* + * Check each bit whether the bit is set or unset + * Uses >> and & operator for checking individual bits + */ + for (i = 0; i <= NUM_BITS_INT; i++) + { + snum = num >> i; + res = snum & 1; + if (res == 0) + count++; + } + printf("%d", count); +} \ No newline at end of file diff --git a/c/Bitwise/C Program to Count the Number of Bits needed to be Flipped to Integer X to Generate Integer Y.c b/c/Bitwise/C Program to Count the Number of Bits needed to be Flipped to Integer X to Generate Integer Y.c new file mode 100644 index 0000000..3c0396b --- /dev/null +++ b/c/Bitwise/C Program to Count the Number of Bits needed to be Flipped to Integer X to Generate Integer Y.c @@ -0,0 +1,24 @@ +/* + * C Program to Count the Number of Bits needed to be Flipped + * to Integer X to Generate Integer Y + */ +#include +#include +#define NUM_BITS_INT (sizeof(int)*8) + +void main() +{ + int n, m, i, count = 0, a, b; + printf("Enter the number\n"); + scanf("%d", &n); + printf("Enter another number\n"); + scanf("%d", &m); + for (i = NUM_BITS_INT-1; i >= 0; i--) + { + a = (n >> i)& 1; + b = (m >> i)& 1; + if (a != b) + count++; + } + printf("flip count = %d\n", count); +} \ No newline at end of file diff --git a/c/Bitwise/C Program to Count the Number of Bits set to One using Bitwise Operations.c b/c/Bitwise/C Program to Count the Number of Bits set to One using Bitwise Operations.c new file mode 100644 index 0000000..d294981 --- /dev/null +++ b/c/Bitwise/C Program to Count the Number of Bits set to One using Bitwise Operations.c @@ -0,0 +1,21 @@ +/* + * C Program to Count the Number of Bits set to One using + * Bitwise Operations + */ +#include + +int main() +{ + unsigned int number; + int count = 0; + printf("Enter the unsigned integer:\n"); + scanf("%d", &number); + while (number != 0) + { + if ((number & 1) == 1) + count++; + number = number >> 1; + } + printf("number of one's are :\n%d\n", count); + return 0; +} \ No newline at end of file diff --git a/c/Bitwise/C Program to Count the Number of Trailing Zeroes in Integer.c b/c/Bitwise/C Program to Count the Number of Trailing Zeroes in Integer.c new file mode 100644 index 0000000..c14d029 --- /dev/null +++ b/c/Bitwise/C Program to Count the Number of Trailing Zeroes in Integer.c @@ -0,0 +1,26 @@ +/* + * C Program to Count the Number of Trailing Zeroes in Integer + */ +#include + +void main() +{ + int j = 31, i, count = 0; + unsigned int num; + int b[32] = {0}; + printf("enter the number:"); + scanf("%d", &num); + while (num != 0) + { + if (num & 1 == 1) + { + break; + } + else + { + count++; + num = num >> 1; + } + } + printf("\n%d", count); +} \ No newline at end of file diff --git a/c/Bitwise/C Program to Find the Position of String of 1-bits in a Number for a given Length.c b/c/Bitwise/C Program to Find the Position of String of 1-bits in a Number for a given Length.c new file mode 100644 index 0000000..c976af0 --- /dev/null +++ b/c/Bitwise/C Program to Find the Position of String of 1-bits in a Number for a given Length.c @@ -0,0 +1,34 @@ +/* + * C Program to Find the Position of String of 1-bits in a Number + * for a given Length + */ +#include + +void main() +{ + int n, len, pos = 0, i = 0, count = 0; + printf("**Finding the position of 1-bits in a number for given length**\n"); + printf("enter a number\n"); + scanf("%d", &n); + printf("enter the length\n"); + scanf("%d", &len); + while (i <= 32) + { + if ((n & 1) == 1) //checking whether there is a 1-bit in the current position + { + count++;//counting the consecutive 1's in the integer + pos = i; + if (count == len) //checking whether the length matches + { + break; + } + } + if ((n & 1) == 0) + { + count = 0; + } + n = n>>1; + i++; + } + printf("the position of 1 in the string : %d\n", pos); +} \ No newline at end of file diff --git a/c/Bitwise/C Program to Perform Binary Addition of Strings and Print it.c b/c/Bitwise/C Program to Perform Binary Addition of Strings and Print it.c new file mode 100644 index 0000000..71d25e7 --- /dev/null +++ b/c/Bitwise/C Program to Perform Binary Addition of Strings and Print it.c @@ -0,0 +1,91 @@ +/* + * C Program to Perform Binary Addition of Strings and Print it + */ +#include +#include + +/* global variables */ +char s1[10], s2[10], s3[10]; +int i, k; +char carry = '0'; +/* function prototype */ +void binary_add(char *,char *); + +void main() +{ + printf("enter string1\n"); + scanf(" %[^\n]s", s1); + printf("enter string2\n"); + scanf(" %[^\n]s", s2); + binary_add(s1, s2); + printf("binary addition of number is\n"); + if (carry == '1') + { + s3[i] = '1'; + for (i = 1; i <= k + 1; i++) + printf("%c", s3[i]); + printf("\n"); + } + else + { + for (i = 1; i <= k + 1; i++) + printf("%c", s3[i]); + printf("\n"); + } +} + +/* function to add two binary numbers in a string */ +void binary_add(char *s1, char *s2) +{ + char *p1, *p2; + p1 = s1; + p2 = s2; + k = strlen(s1); + for (; *p1 != '\0' && *p2 != '\0'; p1++, p2++); + p1--; + p2--; + s3[k+1] = '\0'; + for (i = k + 1; i >= 1; i--, p1--, p2--) + { + if (*p1 == '0' && *p2 == '0'&& carry == '0') + { + s3[i] = (*p1 ^ *p2) ^ carry; + carry = '0'; + } + else if (*p1 == '0' && *p2 == '0' && carry == '1') + { + s3[i] = (*p1 ^ *p2)^ carry; + carry = '0'; + } + else if (*p1 == '0' && *p2 == '1' && carry == '0') + { + s3[i] = (*p1 ^ *p2)^ carry; + carry = '0'; + } + else if (*p1 == '0' && *p2 == '1' && carry == '1') + { + s3[i] = (*p1 ^ *p2)^ carry; + carry = '1'; + } + else if (*p1 == '1' && *p2 == '0' && carry == '0') + { + s3[i] = (*p1 ^ *p2)^ carry; + carry = '0'; + } + else if (*p1 == '1' && *p2 == '0' && carry == '1') + { + s3[i] = (*p1 ^ *p2)^ carry; + carry = '1'; + } + else if (*p1 == '1' && *p2 == '1' && carry == '0') + { + s3[i] = (*p1 ^ *p2)^ carry; + carry = '1'; + } + else + { + s3[i] = (*p1 ^ *p2)^ carry; + carry = '1'; + } + } +} \ No newline at end of file diff --git a/c/Bitwise/C Program to Print the Range of Fundamental Data Types.c b/c/Bitwise/C Program to Print the Range of Fundamental Data Types.c new file mode 100644 index 0000000..d194989 --- /dev/null +++ b/c/Bitwise/C Program to Print the Range of Fundamental Data Types.c @@ -0,0 +1,52 @@ +/* + * C Program to Print the Range + */ +#include +#define SIZE(x) sizeof(x)*8 + +void signed_one(int); +void unsigned_one(int); + +void main() +{ + printf("\nrange of int"); + signed_one(SIZE(int)); + printf("\nrange of unsigned int"); + unsigned_one(SIZE(unsigned int)); + printf("\nrange of char"); + signed_one(SIZE(char)); + printf("\nrange of unsigned char"); + unsigned_one(SIZE(unsigned char)); + printf("\nrange of short"); + signed_one(SIZE(short)); + printf("\nrange of unsigned short"); + unsigned_one(SIZE(unsigned short)); +} +/* RETURNS THE RANGE SIGNED*/ +void signed_one(int count) +{ + int min, max, pro; + pro = 1; + while (count != 1) + { + pro = pro << 1; + count--; + } + min = ~pro; + min = min + 1; + max = pro - 1; + printf("\n%d to %d", min, max); +} +/* RETURNS THE RANGE UNSIGNED */ +void unsigned_one(int count) +{ + unsigned int min, max, pro = 1; + while (count != 0) + { + pro = pro << 1; + count--; + } + min = 0; + max = pro - 1; + printf("\n%u to %u", min, max); +} \ No newline at end of file diff --git a/c/Bitwise/C Program to Replace Bits in Integer from Specified Positions from Another Integer.c b/c/Bitwise/C Program to Replace Bits in Integer from Specified Positions from Another Integer.c new file mode 100644 index 0000000..4235f68 --- /dev/null +++ b/c/Bitwise/C Program to Replace Bits in Integer from Specified Positions from Another Integer.c @@ -0,0 +1,50 @@ +/* + * C Program to Replace Bits in Integer from Specified Positions from + * Another Integer + */ +#include + +void replace_bits(int, int, int, int); + +int main() +{ + int number_x, number_y, start_pos, end_pos; + printf("\nEnter the number x in hexa decimal "); + scanf("%x", &number_x); + printf("\nEnter the number y in hexa decimal"); + scanf(" %x", &number_y); + printf("\nEnter value for a"); + scanf("%d", &start_pos); + printf("\nEnter value for b"); + scanf("%d", &end_pos); + replace_bits(number_x, number_y, start_pos, end_pos); +} +/* + * Replace bits in first number from specified position with bits in second number + */ +void replace_bits(int number_x, int number_y, int start_pos, int end_pos) +{ + int i, shift_y, ybit; + long int temp, t; + /* + * Replace the corresponding x bits by y bits + */ + for (i = start_pos; i <= end_pos; i++) + { + shift_y = number_y >> i; + ybit = shift_y & 1; + if (ybit == 1) + { + temp = 1 << i; + number_x = number_x | temp; + } + if (ybit == 0) + { + t = 0XFFFFFFFF; + temp = 1 << i; + start_pos = t ^ temp; + number_x = number_x & start_pos; + } + } + printf("%x", number_x); +} \ No newline at end of file diff --git a/c/Bitwise/C Program to Replace Bits in Integer x from Bit Position a to b from another Integer y.c b/c/Bitwise/C Program to Replace Bits in Integer x from Bit Position a to b from another Integer y.c new file mode 100644 index 0000000..5654623 --- /dev/null +++ b/c/Bitwise/C Program to Replace Bits in Integer x from Bit Position a to b from another Integer y.c @@ -0,0 +1,64 @@ +/* + * C Program to Replace Bits in Integer x from Bit Position a to b from another Integer y + */ +#include + +void changebits(int, int, int, int); + +int main() +{ + int num1, num2, pos1, pos2; + printf("**Replacing the bits in integer x from bit position a to b from another integer y**\n"); + printf("read number 1\n"); + scanf("%x", &num1); + printf("Read number 2:\n"); + scanf("%x", &num2); + printf("Read LSB postion:\n"); + scanf("%d", &pos1); + printf("MSB should always be greater than LSB\n"); + printf("Read MSB position:\n"); + scanf("%d", &pos2); + changebits(num1, num2, pos1, pos2); + return 0; +} + +/*Function to swap bits in given positions*/ + +void changebits(int num1, int num2, int pos1, int pos2) +{ + int temp1, temp_1, buffer2, bit1 = 0, bit2 = 0, counter = 0, a = 1; + temp1 = num1; + temp_1 = num1; + buffer2 = num2; + for (; pos1 <= pos2; pos1++) + { + a = 1; + num1 = temp_1; + num2 = buffer2; + while (counter <= pos1) + { + if (counter == pos1) + bit1 = (num1&1); //placing the bit of position 1 in bit1 + counter++; + num1>> = 1; + } + counter = 0; + while (counter <= pos1) + { + if (counter == pos1) + bit2 = (num2&1); //placing the bit of position 2 in bit2 + counter++; + num2 >>= 1; + } + counter = 0; + if (bit1 == bit2); + else + { + while (counter++ +#define NUM_BITS_INT sizeof(int)*8 + +void main() +{ + unsigned int number; + int i = 0, hexadecimal, rev = 0, bit; + printf("enter the hexdecimal value\n"); + scanf("0x%number", &hexadecimal); + while (i++ < NUM_BITS_INT) + { + bit = hexadecimal & 1; + hexadecimal = hexadecimal >> 1; + rev = rev ^ bit; + if (i < NUM_BITS_INT) + rev = rev << 1; + } + printf("reverse of hexadecimal value is 0x%number", rev); +} \ No newline at end of file diff --git a/c/Bitwise/C Program to Swap the ith and jth Bits for a 32-Bit Integer.c b/c/Bitwise/C Program to Swap the ith and jth Bits for a 32-Bit Integer.c new file mode 100644 index 0000000..1f1c1c5 --- /dev/null +++ b/c/Bitwise/C Program to Swap the ith and jth Bits for a 32-Bit Integer.c @@ -0,0 +1,63 @@ +/* + * C Program to Swap the ith and jth Bits for a 32-Bit Integer + */ +#include + +int swap(int,int); +int number, pos1, pos2; + +int main() +{ + int result, shift_pos1, shift_pos2; + printf("\nEnter Number"); + scanf("%d", &number); + printf("\nEnter bit positions to swap"); + scanf("%d %d", &pos1, &pos2); + shift_pos1 = number >> pos1; + shift_pos2 = number >> pos2; + result = swap(shift_pos1&1, shift_pos2&1); + printf("%d\n", result); +} + +int swap(int pos1_val, int pos2_val) +{ + int temp1, temp2; + long int base, base1; + /* + * If the pos1_val value is 1 then only pos2_val th bit is set to 1 by using << and + operators + */ + if (pos1_val == 1) + { + base1 = 1 << pos2; + number = number + base1; + } + /* + *If the pos2_val value is 1 then only pos2_val th bit is set to 1 by using << and + operators + */ + if (pos2_val == 1) + { + base1 = 1 << pos2; + number = number + base1; + } + /* + *If the pos1_val value is 0 then only pos2_val th bit is set to 0 using <<, ^ and & operators + */ + if (pos1_val == 0) + { + base = 0XFFFFFFFF; + base1 = 1 << pos2; + temp1 = base ^ base1; + number = number & temp1; + } + /* + *If the pos2_val value is 0 then only pos1_val th bit is set to 0 using <<, ^ and & operators + */ + if (pos2_val == 0) + { + base = 0XFFFFFFFF; + base1 = 1 << pos1; + temp2 = base ^ base1; + number = number & temp2; + } + return number; +} \ No newline at end of file diff --git a/c/Bitwise/C Program to Swap two Integers without using Temporary Variables and Bitwise Operations.c b/c/Bitwise/C Program to Swap two Integers without using Temporary Variables and Bitwise Operations.c new file mode 100644 index 0000000..7809d5f --- /dev/null +++ b/c/Bitwise/C Program to Swap two Integers without using Temporary Variables and Bitwise Operations.c @@ -0,0 +1,27 @@ +/* + * C Program to Swap two Integers without using Temporary Variables + * and Bitwise Operations + */ +#include + +// Function Prototype +void swap(int *, int *); + +void main() +{ + int x, y; + printf("Enter 2 nos: \n"); + scanf("%d %d", &x, &y); + printf("\nYou have entered x = %d y = %d \n", x, y); + swap(&x,&y); // passing the 2 nos to the swap function +} + +// function to swap the two numbers +void swap(int *a, int *b) +{ + *a = *a + *b; + *b = *a - *b; + *a = *a - *b; + printf("Swapped . . . .\n"); // printing the swapped numbers + printf("x = %d y = %d\n", *a, *b); +} \ No newline at end of file diff --git a/c/Bitwise/C Program to Swap two Numbers using Bitwise Operators.c b/c/Bitwise/C Program to Swap two Numbers using Bitwise Operators.c new file mode 100644 index 0000000..1761721 --- /dev/null +++ b/c/Bitwise/C Program to Swap two Numbers using Bitwise Operators.c @@ -0,0 +1,26 @@ +/* + * C Program to Swap two Numbers using Bitwise operators + */ +#include +#include + +/* Function Prototype */ +void swap(int*, int *); + +void main() +{ + int num1, num2; + printf("\nEnter two numbers:"); + scanf("%d %d", &num1, &num2); + printf("\nThe numbers before swapping are Number1= %d Number2 = %d", num1, num2); + swap(&num1, &num2); /* Call by Reference to function swap */ + printf("\nThe numbers after swapping are Number1= %d Number2 = %d", num1, num2); +} + +/* Code to swap two numbers using bitwise operator */ +void swap(int *x, int *y) +{ + *x = *x ^ *y; + *y = *x ^ *y; + *x = *x ^ *y; +} \ No newline at end of file diff --git a/c/Bitwise/C Program to Use Bitwise Operations to Count the Number of Leading Zero’s in a Number x.c b/c/Bitwise/C Program to Use Bitwise Operations to Count the Number of Leading Zero’s in a Number x.c new file mode 100644 index 0000000..2181e06 --- /dev/null +++ b/c/Bitwise/C Program to Use Bitwise Operations to Count the Number of Leading Zero’s in a Number x.c @@ -0,0 +1,83 @@ +/* + * C Program to Use Bitwise Operations to Count the Number of + * Leading Zero's in a Number x + */ +#include +#include +#define NUM_BITS_INT (sizeof(int)*8) +int find(int); + +void main() +{ + int n, i, a, count = 0, flag = 1, m = 1, j, cmp; + printf("Enter the number\n"); + scanf("%d", &n); + a = n >> 31 & 1; + if (a == 0) + { + for (i = (NUM_BITS_INT)-1; i >= 0; i--) + { + a = (n >> i)& 1; + if (a == 0) + { + count++; + } + else + { + for (j = n + 1;; j++) + { + cmp = find(j); + if (cmp == (((NUM_BITS_INT)-1) - count) + 1) + { + printf("next higher power -> %d\n", j); + break; + } + } + break; + } + } + } + else + { + for (i = (NUM_BITS_INT)-1; i >= 0; i--) + { + a = (n >> i)& 1; + if (a == 1) + { + count++; + } + else + { + for (j = n + 1;; j++) + { + cmp = find(j); + if (cmp == (((NUM_BITS_INT)- 1) - count)) + { + printf("next higher power -> %d\n", j); + break; + } + } + break; + } + } + } +} + +/* To find trailing zero's */ +int find(int n) +{ + int count = 0, a, flag = 1, i; + for (i = 0; i <= (NUM_BITS_INT) - 1; i++) + { + a = (n >> i) & 1; + if (a == 1 && flag == 1) + { + return count; + } + else + { + count++; + flag = 1; + } + } +} \ No newline at end of file diff --git a/c/Bitwise/C Program to find Next higher Value of N with same 1’s.c b/c/Bitwise/C Program to find Next higher Value of N with same 1’s.c new file mode 100644 index 0000000..40ebdd0 --- /dev/null +++ b/c/Bitwise/C Program to find Next higher Value of N with same 1’s.c @@ -0,0 +1,52 @@ +/* + * C Program to next higher value of n with same 1's + */ +#define NUM_BITS_INT 32 +#include +int newcount(int); + +void main() +{ + int count1 = 0, k = 0, j, t, n, bit, i = 1, count = 0; + printf("Enter a number : "); + scanf("%d", &n); + t = n; + while(t != 0) + { + bit = t & 0x80000000; + if (bit == -0x80000000) + { + bit = 1; + } + if (bit == 1) + count++; + t = t << 1; + } + for (k = n + 1;; k++) + { + count1 = newcount(k); + if (count1 == count) + { + printf("The next highest number is : %d ", k); + break; + } + } +} + +/* To count the no. of 1's in the no. */ +int newcount(int k) +{ + int bit, count = 0; + while (k != 0) + { + bit = k & 0x80000000; + if (bit == -0x80000000) + { + bit = 1; + } + if (bit == 1) + count++; + k = k << 1; + } + return(count); +} \ No newline at end of file diff --git a/c/Bitwise/C Program to find the Highest Bit Set for any given Integer.c b/c/Bitwise/C Program to find the Highest Bit Set for any given Integer.c new file mode 100644 index 0000000..cdb7478 --- /dev/null +++ b/c/Bitwise/C Program to find the Highest Bit Set for any given Integer.c @@ -0,0 +1,42 @@ +/* + * C Program to find the Highest Bit Set for any given Integer + */ +#include +#define NUM_BITS sizeof(int)*8 + +int highest_bit_set(int); +void display(int); +int i = NUM_BITS; + +void main() +{ + int num, pos; + printf("\nenter the number:"); + scanf("%d", &num); + display(num); + pos = highest_bit_set(num); + printf("\nthe position of the highest bit set is %d", pos); +} +/* RETURNS THE POSITION */ +int highest_bit_set(int num) +{ + int count = 0; + while (num >> 1 != 0) + { + count++; + num = num >> 1; + } + return(count); +} +/* DISPLAYS THE NUMBER IN BINARY REPRESENTATION */ +void display(int num) +{ + int c; + c = num & 1; + if (i > 0) + { + i--; + display(num >> 1); + } + printf("%d", c); +} \ No newline at end of file diff --git a/c/Bitwise/C Program to round Floor of integer to next Lower Power of 2.c b/c/Bitwise/C Program to round Floor of integer to next Lower Power of 2.c new file mode 100644 index 0000000..8b88c35 --- /dev/null +++ b/c/Bitwise/C Program to round Floor of integer to next Lower Power of 2.c @@ -0,0 +1,25 @@ +/* + * C Program to round floor of integer to next lower power of 2 + */ +#include +#define NUM_BITS_INT 32 +int count = 0; + +void main() +{ + int temp, n, bit, i = 0; + printf("Enter a number : "); + scanf("%d", &n); + temp = n; + while (i < NUM_BITS_INT) + { + bit = temp & 0x80000000; + if (bit == -0x80000000) + { + bit = 1; + } + printf("%d", bit); + temp = temp << 1; + i++; + } +} \ No newline at end of file diff --git a/c/Bitwise/C Program to use Bitwise Operations to Round(floor of) an Integer to next Lower Multiple of 2.c b/c/Bitwise/C Program to use Bitwise Operations to Round(floor of) an Integer to next Lower Multiple of 2.c new file mode 100644 index 0000000..9d86539 --- /dev/null +++ b/c/Bitwise/C Program to use Bitwise Operations to Round(floor of) an Integer to next Lower Multiple of 2.c @@ -0,0 +1,36 @@ +/* + * C Program to use Bitwise Operations to Round(floor of) an Integer + * to next Lower Multiple of 2 + */ +#include + +void main() +{ + int x = 1, i, n; + printf("enter the number :"); + scanf("%d", &n); + /* for positive values */ + if (n > 0) + { + for (; x <= n >> 1;) + { + x = x << 1; + } + n = x; + } + /* for negative values */ + else + { + n = ~n; + n = n + 1; + for (; x <= n >> 1;) + { + x = x << 1; + } + x = x << 1; + x = ~x; + x = x + 1; + n = x; + } + printf("%d", n); +} \ No newline at end of file diff --git a/c/Control_Statements/C Program to check whether a given number is prime or not..c b/c/Control_Statements/C Program to check whether a given number is prime or not..c new file mode 100644 index 0000000..c15850e --- /dev/null +++ b/c/Control_Statements/C Program to check whether a given number is prime or not..c @@ -0,0 +1,43 @@ +/* Prime number - Program to check whether a given number is prime or not */ + +/* Assume 2 is a prime number but 0 and 1 are not */ + +#include +#include + +void main() +{ + int p,d, flag ; + clrscr() ; + printf("Enter a number: ") ; + scanf("%d", &p) ; + flag=1 ; /* Assuming p is prime */ + for(d=2 ; d<=p-1 ; d++) /* d<=p/2 is also correct */ + if(p%d==0) /* True if number is not prime */ + { + flag=0 ; + break ; /* Loop terminates if p is not prime */ + } + if(flag==0 || p==1 || p==0 ) + printf("%d is not prime", p) ; + else + printf("%d is prime", p) ; + getch() ; +} + +/* +Output 1: + +Enter a number: 1 +1 is not prime + +Output 2: + +Enter a number: 7 +7 is prime + +Output 3: + +Enter a number: 9 +9 is not prime +*/ diff --git a/c/Control_Statements/C Program should read the units consumed for a customer and calculate the total bill...c b/c/Control_Statements/C Program should read the units consumed for a customer and calculate the total bill...c new file mode 100644 index 0000000..54e57c9 --- /dev/null +++ b/c/Control_Statements/C Program should read the units consumed for a customer and calculate the total bill...c @@ -0,0 +1,60 @@ +/* +An electric power distribution company charges its domestic consumer as follows: +Consumption Units Rate of Charge +0-200 0.50 per unit +201-400 Rs. 100 plus Rs. 0.65 per unit excess of 200 +401-600 Rs. 230 plus Rs. 0.85 per unit excess of 400 +601-above Rs. 390 plus Rs. 1.00 per unit excess of 600 +Program should read the units consumed for a customer and calculate the total bill. + */ + +#include +#include + +void main() +{ + int units ; + float amt ; + clrscr() ; + printf("Enter consumption units: ") ; + scanf("%d", &units) ; + if(units>=0 && units<=200) + { + amt = units * 0.50 ; + printf("The total billing amount is %f", amt) ; + } + else if(units>=201 && units<=400) + { + amt = 100 + (units-200) * 0.65 ; + printf("The total billing amount is %f", amt) ; + } + else if(units>=401 && units<=600) + { + amt = 230 + (units-400) * 0.85 ; + printf("The total billing amount is %f", amt) ; + } + else + { + amt = 390 + (units-600) * 1.00 ; + printf("The total billing amount is %f", amt) ; + } + getch() ; +} + +/* +Output 1: + +Enter consumption units: 300 +The total billing amount is 165.000000 + +Output 2: + +Enter consumption units: 450 +The total billing amount is 272.500000 + +Output 3: + +Enter consumption units: 620 +The total billing amount is 410.000000 +*/ + diff --git a/c/Control_Statements/C Program to check whether a given number is an armstrong number..c b/c/Control_Statements/C Program to check whether a given number is an armstrong number..c new file mode 100644 index 0000000..f0ba589 --- /dev/null +++ b/c/Control_Statements/C Program to check whether a given number is an armstrong number..c @@ -0,0 +1,39 @@ +/* Armstrong number - Program to check whether a given number is an armstrong number */ + +/* We consider an armstrong number to be a 3 digit number in which sum of cubes of digits is equal to number itself. An armstrong number can be defined in other ways too, but the above definition is the most popular one. */ + +#include +#include + +void main() +{ + int n, sum=0, r, temp ; + clrscr() ; + printf("Enter a number: ") ; + scanf("%d", &n) ; + temp=n ; + while(n!=0) + { + r=n%10 ; /* Extract the last digit */ + sum=sum+r*r*r ; /* Finding sum */ + n=n/10 ; /* Reduce number by 1 digit */ + } + if(sum==temp) + printf("%d is an armstrong number", temp) ; + else + printf("%d is not an armstrong number", temp) ; + getch() ; +} +/* +Output 1: + +Enter a number: 153 +153 is an armstrong number + +Output 2: + +Enter a number: 152 +152 is not an armstrong number +*/ + + diff --git a/c/Control_Statements/C Program to check whether a given number is divisible by both 5 and 2..c b/c/Control_Statements/C Program to check whether a given number is divisible by both 5 and 2..c new file mode 100644 index 0000000..6507277 --- /dev/null +++ b/c/Control_Statements/C Program to check whether a given number is divisible by both 5 and 2..c @@ -0,0 +1,29 @@ +/* Divisible - Program to check whether a given number is divisible by both 5 and 2 */ + +#include +#include + +void main() +{ + int n ; + clrscr() ; + printf("Enter any integer: ") ; + scanf("%d", &n) ; + if( (n%5 == 0) && (n%2 == 0) ) + printf("%d is divisible by both 5 and 2", n) ; + else + printf("%d is either not divisible by both 5 and 2 or one of them", n) ; + getch() ; +} + +/* +Output1: + +Enter any integer: 20 +20 is divisible by both 5 and 2 + +Output2: + +Enter any integer: 7 +7 is either not divisible by both 5 and 2 or one of them +*/ diff --git a/c/Control_Statements/C Program to check whether a given year is a leap year...c b/c/Control_Statements/C Program to check whether a given year is a leap year...c new file mode 100644 index 0000000..79b90aa --- /dev/null +++ b/c/Control_Statements/C Program to check whether a given year is a leap year...c @@ -0,0 +1,48 @@ +/* Leap year - Program to check whether a given year is a leap year. Centennial years are leap years only when they are divisible by 400 */ + +/* The program can give one of the following four outputs: + 1-- not a leap year + 2-- leap year + 3-- centennial but not a leap year + 4-- centennial and a leap year */ + +#include +#include + +void main() +{ + int y ; + clrscr() ; + printf("Enter any year: ") ; + scanf("%d", &y) ; + if(y%4 == 0) + { + if(y%100 != 0) /* checks whether y is not centennial */ + printf("%d is a leap year \n", y); + else if( y%400 == 0) /* checks whether centennial year is divisible by 400 */ + printf("%d is a centennial leap year \n", y); + else + printf("%d is a centennial but not a leap year \n", y); + } + else + printf("%d is not a leap year \n", y); + getch(); +} + +/* +4 Outputs: + +Enter any year: 2012 +2012 is a leap year + +Enter any year: 2013 +2013 is not a leap year + +Enter any year: 2000 +2000 is a centennial leap year + +Enter any year: 1900 +1900 is a centennial but not a leap year + +*/ + diff --git a/c/Control_Statements/C Program to count the number of digits in a given number..c b/c/Control_Statements/C Program to count the number of digits in a given number..c new file mode 100644 index 0000000..6ffa000 --- /dev/null +++ b/c/Control_Statements/C Program to count the number of digits in a given number..c @@ -0,0 +1,37 @@ +/* Digit Count - Program to count the number of digits in a given number */ + +#include +#include + +void main() +{ + int n, d=0, r, temp ; + clrscr() ; + printf("Enter a number: ") ; + scanf("%d", &n) ; + if(n==0) /* Special Case */ + printf("Number of digits in 0 is 1") ; + else + { + temp=n ; + while(n!=0) + { + ++d ; /* Counting */ + n=n/10 ; /* Reduce number by 1 digit */ + } + printf("Number of digits in %d is %d", temp, d) ; + } + getch() ; +} +/* +Output 1: + +Enter a number: 246 +Number of digits in 246 is 3 + +Output 2: + +Enter a number: 0 +Number of digits in 0 is 1 +*/ + diff --git a/c/Control_Statements/C Program to find GCD of two numbers using Euclid's algorithm and then find LCM..c b/c/Control_Statements/C Program to find GCD of two numbers using Euclid's algorithm and then find LCM..c new file mode 100644 index 0000000..55f9774 --- /dev/null +++ b/c/Control_Statements/C Program to find GCD of two numbers using Euclid's algorithm and then find LCM..c @@ -0,0 +1,45 @@ +/* GCD-LCD - Program to find GCD of two numbers using Euclid's algorithm and then find LCM */ + +#include +#include + +void main() +{ + int m, n, r, a, b ; + clrscr() ; + printf("Enter 2 numbers: ") ; + scanf("%d %d", &m, &n) ; + a=m ; + b=n ; + while(n>0) + { + r=m%n ; + m=n ; + n=r ; + } + printf("GCD is: %d \n", m) ; + printf("LCM is: %d", a*b/m) ; + getch() ; +} + +/* +Output 1: + +Enter 2 numbers: 24 18 +GCD is: 6 +LCM is: 72 + +Output 2: + +Enter 2 numbers: 18 24 +GCD is: 6 +LCM is: 72 + +Output 3: + +Enter 2 numbers: 9 7 +GCD is: 1 +LCM is: 63 +*/ + + diff --git a/c/Control_Statements/C Program to find factorial of a given number (using for loop)..c b/c/Control_Statements/C Program to find factorial of a given number (using for loop)..c new file mode 100644 index 0000000..f948093 --- /dev/null +++ b/c/Control_Statements/C Program to find factorial of a given number (using for loop)..c @@ -0,0 +1,31 @@ +/* Factorial - Program to find factorial of a given number (using for loop) */ + +#include +#include + +void main() +{ + int i, n ; + long f=1 ; /* Factorials are long numbers */ + clrscr() ; + printf("Enter an integer greater than or equal to zero: ") ; + scanf("%d", &n) ; + for(i=1 ; i<=n ; i++) + f=f*i ; + printf("Factorial of %d is %ld", n, f) ; + getch() ; +} +/* +Output 1: + +Enter an integer greater than or equal to zero: 0 +Factorial of 0 is 1 + +Output 2: + +Enter an integer greater than or equal to zero: 3 +Factorial of 3 is 6 +*/ + + + diff --git a/c/Control_Statements/C Program to find four digit perfect squares, where the the first two digits and the last two digits are also perfect squares...c b/c/Control_Statements/C Program to find four digit perfect squares, where the the first two digits and the last two digits are also perfect squares...c new file mode 100644 index 0000000..d2b553f --- /dev/null +++ b/c/Control_Statements/C Program to find four digit perfect squares, where the the first two digits and the last two digits are also perfect squares...c @@ -0,0 +1,44 @@ +/* Perfect Square - Program to find four digit perfect squares, where the number represented by the first two digits and the number represented by the last two digits are also perfect squares. */ + +/* For eg 1681=41^2 16=4^2 81=9^2 */ + +#include +#include +#include + +void main() +{ + int n, n1, n2, i, flag1, flag2, flag3 ; + clrscr() ; + printf("Four digit perfect squares with required property are as shown:\n"); + for(n=1000 ; n<=9999 ; n++) + { + n1=n%100 ; /*Extracting last two digits*/ + n2=n/100 ; /*Extracting first two digits*/ + /*Checking whether the first two digits are perfect squares*/ + flag1=0 ; + i=sqrt(n2) ; /* Remember i is integer whereas sqrt() returns double */ + if(n2==i*i) + flag1=1 ; + /*Checking whether the last two digits are perfect squares*/ + flag2=0 ; + i=sqrt(n1) ; + if(n1==i*i) + flag2=1 ; + /*Checking whether the number itself is a perfect square*/ + flag3=0 ; + i=sqrt(n) ; + if(n==i*i) + flag3=1 ; + if(flag1==1 && flag2 ==1 && flag3==1) + printf("%d ", n) ; + } + getch() ; +} + +/* +Output + +Four digit perfect squares with required property are as shown: +1600 1681 2500 3600 4900 6400 8100 +*/ diff --git a/c/Control_Statements/C Program to find reverse of a given number..c b/c/Control_Statements/C Program to find reverse of a given number..c new file mode 100644 index 0000000..b70a7df --- /dev/null +++ b/c/Control_Statements/C Program to find reverse of a given number..c @@ -0,0 +1,35 @@ +/* Reversing a number - Program to find reverse of a given number */ + +#include +#include + +void main() +{ + int n, rev=0, r, temp ; + clrscr() ; + printf("Enter a number: ") ; + scanf("%d", &n) ; + temp=n ; + while(n!=0) + { + r=n%10 ; /* Extract the last digit */ + rev=rev*10+r ; /* Find reverse */ + n=n/10 ; /* Reduce number by 1 digit */ + } + printf("Reverse of %d is %d", temp, rev) ; + getch() ; +} + +/* +Output 1: + +Enter a number: 246 +Reverse of 246 is 642 + +Output 2: + +Enter a number: 0 +Reverse of 0 is 0 +*/ + + diff --git a/c/Control_Statements/C Program to find roots of a quadartic equation..c b/c/Control_Statements/C Program to find roots of a quadartic equation..c new file mode 100644 index 0000000..86c1c9f --- /dev/null +++ b/c/Control_Statements/C Program to find roots of a quadartic equation..c @@ -0,0 +1,62 @@ +/* Quadratic Equation - Program to find roots of a quadartic equation */ + +#include +#include +#include /* for sqrt() */ +#include /* for abs() */ + +void main() +{ + float a, b, c, d, r, r1, r2, real, imag ; + clrscr() ; + printf("Enter three co-efficients: ") ; + scanf("%f %f %f", &a, &b, &c) ; + d=b*b-4*a*c ; + if(d==0) + { + printf("Root is real \n") ; + printf("Root is %f \n", -b/(2*a) ) ; + } + else if(d>0) + { + printf("Roots are real \n") ; + r=sqrt(d) ; + r1=(-b+r)/(2*a) ; + r2=(-b-r)/(2*a) ; + printf("Roots are %f and %f \n", r1, r2) ; + } + else + { + printf("Roots are imaginary \n") ; + r=sqrt(-d); + real=-b/(2*a) ; + imag=r/(2*a) ; + printf("Root1= %f + %f i \n", real, imag) ; + printf("Root2= %f - %f i \n", real, imag) ; + } + getch() ; +} +/* +Output 1: + +Enter three co-efficients: 1 2 1 +Root is real +Root is -1.000000 + +Output 2: + +Enter three co-efficients: 3 4 1 +Roots are real +Roots are -0.333333 and -1.000000 + + +Output 3: + +Enter three co-efficients: 2 2 1 +Roots are imaginary +Root1= -0.500000 + 0.500000 i +Root2= -0.500000 - 0.500000 i + +*/ + + diff --git a/c/Control_Statements/C Program to find sum of digits of a given number..c b/c/Control_Statements/C Program to find sum of digits of a given number..c new file mode 100644 index 0000000..04d345b --- /dev/null +++ b/c/Control_Statements/C Program to find sum of digits of a given number..c @@ -0,0 +1,28 @@ +/* Sum of digits - Program to find sum of digits of a given number */ + +#include +#include + +void main() +{ + int n, sum=0, r, temp ; + clrscr() ; + printf("Enter a number: ") ; + scanf("%d", &n) ; + temp=n ; + while(n!=0) + { + r=n%10 ; /* Extract the last digit */ + sum=sum+r ; /* Finding sum */ + n=n/10 ; /* Reduce number by 1 digit */ + } + printf("Sum of digits of %d is %d", temp, sum) ; + getch() ; +} +/* +Output + +Enter a number: 246 +Sum of digits of 246 is 12 +*/ + diff --git a/c/Control_Statements/C Program to generate factors of a given number..c b/c/Control_Statements/C Program to generate factors of a given number..c new file mode 100644 index 0000000..8e497c5 --- /dev/null +++ b/c/Control_Statements/C Program to generate factors of a given number..c @@ -0,0 +1,32 @@ +/* Factors of a number - Program to generate factors of a given number */ + +#include +#include + +void main() +{ + int i, n ; + clrscr() ; + printf("Enter the number: ") ; + scanf("%d", &n) ; + printf("Factors of given number are shown below: \n") ; + for(i=1 ; i<=n ; i++) + if(n%i==0) + printf("%d ", i) ; + getch(); +} + +/* +Output1: + +Enter the number: 20 +Factors of given number are shown below: +1 2 4 5 10 20 + +Output2: + +Enter the number: 7 +Factors of given number are shown below: +1 7 +*/ + diff --git a/c/Control_Statements/C Program to print 3 given numbers in ascending order using nested if-else...c b/c/Control_Statements/C Program to print 3 given numbers in ascending order using nested if-else...c new file mode 100644 index 0000000..982378f --- /dev/null +++ b/c/Control_Statements/C Program to print 3 given numbers in ascending order using nested if-else...c @@ -0,0 +1,37 @@ +/* Nested if-else - Program to print 3 given numbers in ascending order using nested if-else. Usage of && is not allowed */ + +#include +#include + +void main() +{ + int a, b, c ; + clrscr() ; + printf("Enter three numbers: ") ; + scanf("%d %d %d", &a, &b, &c) ; + printf("Three values in ascending order are: ") ; + if(a +#include + +void main() +{ + int i, n ; + clrscr() ; + printf("Enter the limit: ") ; + scanf("%d", &n) ; + printf("Four times table is as shown: \n") ; + for(i=1 ; i<=n ; i++) + printf("4 * %d = %d \n", i, 4*i ) ; + getch() ; +} + +/* +Output : + +Enter the limit: 3 +Four times table is as shown: +4 * 1 = 4 +4 * 2 = 8 +4 * 3 = 12 +*/ \ No newline at end of file diff --git a/c/Control_Statements/C Program to print first n prime numbers..c b/c/Control_Statements/C Program to print first n prime numbers..c new file mode 100644 index 0000000..9f8f3f5 --- /dev/null +++ b/c/Control_Statements/C Program to print first n prime numbers..c @@ -0,0 +1,42 @@ +/* Prime number - Program to print first n prime numbers */ + +/* Assume 2 is a prime number but 0 and 1 are not */ + +#include +#include + +void main() +{ + int i, n, p, d, flag ; + clrscr() ; + printf("Enter n: ") ; + scanf("%d",&n) ; + printf("First %d prime numbers are as follows: \n",n) ; + p=2 ; + i=1 ; + while(i<=n) + { + flag=1 ; + for(d=2 ; d<=p-1 ; d++) /* d<=p/2 is also correct */ + if(p%d==0) /* True if number is not prime */ + { + flag=0 ; + break ; /* Loop terminates if p is not prime */ + } + if(flag==1) + { + printf("%d ",p) ; + i++ ; + } + p++ ; + } + getch() ; +} + +/* +Output: + +Enter n: 7 +First 7 prime numbers are as follows: +2 3 5 7 11 13 17 +*/ diff --git a/c/Control_Statements/C Program to print prime numbers from 1 to n or between 1 and n or till n..c b/c/Control_Statements/C Program to print prime numbers from 1 to n or between 1 and n or till n..c new file mode 100644 index 0000000..ee6a2b8 --- /dev/null +++ b/c/Control_Statements/C Program to print prime numbers from 1 to n or between 1 and n or till n..c @@ -0,0 +1,48 @@ +/* Prime number - Program to print prime numbers from 1 to n or between 1 and n or till n */ + +/* Assume 2 is a prime number but 0 and 1 are not */ + +#include +#include + +void main() +{ + int n, p, d, flag ; + clrscr() ; + printf("Enter n: ") ; + scanf("%d", &n) ; + printf("Prime numbers till %d are as shown: \n", n) ; + for(p=2 ; p<=n ; p++) + { + flag=1 ; /* Assuming p is prime */ + for(d=2 ; d<=p-1 ; d++) /* d<=p/2 is also correct */ + if(p%d==0) /* True if number is not prime */ + { + flag=0 ; + break ; /* Inner Loop terminates if p is not prime */ + } + if(flag==1) + printf("%d ", p) ; + } + getch() ; +} + +/* +A Similar Program could be: +Program to read two natural numbers r1 and r2 where r2>r1 and generate all prime numbers between r1 and r2 both inclusive. +*/ + +/* +Output 1: + +Enter n: 13 +Prime numbers till 13 are as shown: +2 3 5 7 11 13 + +Output 2: + +Enter n: 14 +Prime numbers till 14 are as shown: +2 3 5 7 11 13 +*/ + diff --git a/c/Control_Statements/C Program to print the first n terms of fibonacci series..c b/c/Control_Statements/C Program to print the first n terms of fibonacci series..c new file mode 100644 index 0000000..ca2e712 --- /dev/null +++ b/c/Control_Statements/C Program to print the first n terms of fibonacci series..c @@ -0,0 +1,60 @@ +/* Fibonacci (first n) - Program to print the first n terms of fibonacci series */ + +/* We assume that the fibonacci series starts with 1 1 */ + +#include +#include + +void main() +{ + long a=1,b=1, c ; + int i, n ; + clrscr() ; + printf("Enter n: ") ; + scanf("%d", &n) ; + printf("Fibonacci series is as shown: \n") ; + if(n==1) + printf("%ld", a) ; + else if(n==2) + printf("%ld %ld", a, b) ; + else if(n>2) + { + printf("%ld %ld", a, b) ; + for(i=1 ; i<=n-2 ; i++) + { + c=a+b ; + printf(" %ld", c) ; + a=b ; + b=c ; + } + } + getch(); +} + +/* +Output 1: + +Enter n: 1 +Fibonacci series is as shown: +1 + +Output 2: + +Enter n: 2 +Fibonacci series is as shown: +1 1 + +Output 3: + +Enter n: 6 +Fibonacci series is as shown: +1 1 2 3 5 8 +*/ + +/* +Note: +If the fibonacci series starts with 0 1 then all we need to do is initialize a=0 instead of a=1 +*/ + + + diff --git a/c/Control_Statements/C Program to print those terms of fibonacci series which are between 1 and n..c b/c/Control_Statements/C Program to print those terms of fibonacci series which are between 1 and n..c new file mode 100644 index 0000000..2214190 --- /dev/null +++ b/c/Control_Statements/C Program to print those terms of fibonacci series which are between 1 and n..c @@ -0,0 +1,53 @@ +/* Fibonacci (1 to n) - Program to print those terms of fibonacci series which are between 1 and n */ + +/* We assume that the fibonacci series starts with 1 1 */ + +#include +#include + +void main() +{ + long a=1,b=1, c ; + int i, n ; + clrscr() ; + printf("Enter n: ") ; + scanf("%d", &n) ; + printf("Fibonacci series is as shown: \n") ; + if(n==1) + printf("%ld %ld ", a, b) ; + else if(n>1) + { + printf("%ld %ld ", a, b) ; + c=a+b ; + do + { + printf(" %ld ", c) ; + a=b ; + b=c ; + c=a+b ; + } + while(c<=n) ; + } + getch() ; +} + +/* +Output 1: + +Enter n: 1 +Fibonacci series is as shown: +1 1 + +Output 2: + +Enter n: 3 +Fibonacci series is as shown: +1 1 2 3 + +Output 3: + +Enter n: 4 +Fibonacci series is as shown: +1 1 2 3 +*/ + diff --git a/c/Control_Statements/C Program to read month number as input and display the month in words...c b/c/Control_Statements/C Program to read month number as input and display the month in words...c new file mode 100644 index 0000000..df106df --- /dev/null +++ b/c/Control_Statements/C Program to read month number as input and display the month in words...c @@ -0,0 +1,68 @@ +/* Month in words - Program to read month number as input and display the month in words. */ + +#include +#include + +void main() +{ + int m ; + clrscr() ; + printf("Enter a month number: ") ; + scanf("%d", &m) ; + printf("Month in words is: ") ; + switch(m) + { + case 1: + printf("January") ; + break ; + case 2: + printf("February") ; + break ; + case 3: + printf("March") ; + break ; + case 4: + printf("April") ; + break ; + case 5: + printf("May") ; + break ; + case 6: + printf("June") ; + break ; + case 7: + printf("July") ; + break ; + case 8: + printf("August") ; + break ; + case 9: + printf("September") ; + break ; + case 10: + printf("October") ; + break ; + case 11: + printf("November") ; + break ; + case 12: + printf("December") ; + break ; + default: + printf("\nWrong Input") ; + break ; + } + getch() ; +} + +/* +Output 1: + +Enter a month number: 7 +Month in words is: July + +Output 2: +Enter a month number: 13 +Month in words is: +Wrong Input +*/ diff --git a/c/Control_Statements/C Write a program which reads price of an article and the corresponding discount policy..c b/c/Control_Statements/C Write a program which reads price of an article and the corresponding discount policy..c new file mode 100644 index 0000000..154f7a7 --- /dev/null +++ b/c/Control_Statements/C Write a program which reads price of an article and the corresponding discount policy..c @@ -0,0 +1,54 @@ +/* Write a program which reads price of an article and the corresponding discount policy +If discount policy=1, discount=10% +If discount policy=2, discount=20% +If discount policy=3, discount=30% +For all other policies, discount=0 +Print the final price of the article */ + +#include +#include + +void main() +{ + float p, d, fp ; + int policy ; + clrscr() ; + printf("Enter price of article and corresponding discount policy: ") ; + scanf("%f %d", &p, &policy) ; + switch(policy) + { + case 1: + d=0.1*p ; + break ; + case 2: + d=0.2*p ; + break ; + case 3: + d=0.3*p ; + break ; + default: + d=0 ; + } + fp=p-d ; + printf("Final price of the article is %f",fp) ; + getch() ; +} + +/* +Output 1: + +Enter price of article and corresponding discount policy: 15 3 +Final price of the article is 10.500000 + +Output 2: + +Enter price of article and corresponding discount policy: 15 8 +Final price of the article is 15.000000 +*/ + + + + + + + diff --git a/c/Data_Input_Output/C Program Delete a specific Line from a Text File.c b/c/Data_Input_Output/C Program Delete a specific Line from a Text File.c new file mode 100644 index 0000000..9e55a69 --- /dev/null +++ b/c/Data_Input_Output/C Program Delete a specific Line from a Text File.c @@ -0,0 +1,56 @@ +/* + * C Program Delete a specific Line from a Text File + */ +#include + +int main() +{ + FILE *fileptr1, *fileptr2; + char filename[40]; + char ch; + int delete_line, temp = 1; + printf("Enter file name: "); + scanf("%s", filename); + //open file in read mode + fileptr1 = fopen(filename, "r"); + ch = getc(fileptr1); + ` while (ch != EOF) + { + printf("%c", ch); + ch = getc(fileptr1); + } + //rewind + rewind(fileptr1); + printf(" \n Enter line number of the line to be deleted:"); + scanf("%d", &delete_line); + //open new file in write mode + fileptr2 = fopen("replica.c", "w"); + ch = getc(fileptr1); + while (ch != EOF) + { + ch = getc(fileptr1); + if (ch == '\n') + temp++; + //except the line to be deleted + if (temp != delete_line) + { + //copy all lines in file replica.c + putc(ch, fileptr2); + } + } + fclose(fileptr1); + fclose(fileptr2); + remove(filename); + //rename the file replica.c to original name + rename("replica.c", filename); + printf("\n The contents of file after being modified are as follows:\n"); + fileptr1 = fopen(filename, "r"); + ch = getc(fileptr1); + while (ch != EOF) + { + printf("%c", ch); + ch = getc(fileptr1); + } + fclose(fileptr1); + return 0; +} \ No newline at end of file diff --git a/c/Data_Input_Output/C Program that Merges Lines Alternatively from 2 Files & Print Result.c b/c/Data_Input_Output/C Program that Merges Lines Alternatively from 2 Files & Print Result.c new file mode 100644 index 0000000..248ff93 --- /dev/null +++ b/c/Data_Input_Output/C Program that Merges Lines Alternatively from 2 Files & Print Result.c @@ -0,0 +1,51 @@ +/* + * C Program that Merges Lines Alternatively from 2 Files & Print Result + */ +#include +main() +{ + char file1[10], file2[10]; + puts("enter the name of file 1"); /*getting the names of file to be concatenated*/ + scanf("%s", file1); + puts("enter the name of file 2"); + scanf("%s", file2); + FILE *fptr1, *fptr2, *fptr3; + fptr1=fopen(file1, "r"); /*opening the files in read only mode*/ + fptr2=fopen(file2, "r"); + fptr3=fopen("merge2.txt", "w+"); /*opening a new file in write,update mode*/ + char str1[200]; + char ch1, ch2; + int n = 0, w = 0; + while (((ch1=fgetc(fptr1)) != EOF) && ((ch2 = fgetc(fptr2)) != EOF)) + { + if (ch1 != EOF) /*getting lines in alternately from two files*/ + { + ungetc(ch1, fptr1); + fgets(str1, 199, fptr1); + fputs(str1, fptr3); + if (str1[0] != 'n') + n++; /*counting no. of lines*/ + } + if (ch2 != EOF) + { + ungetc(ch2, fptr2); + fgets(str1, 199, fptr2); + fputs(str1, fptr3); + if (str1[0] != 'n') + n++; /*counting no.of lines*/ + } + } + rewind(fptr3); + while ((ch1 = fgetc(fptr3)) != EOF) /*countig no.of words*/ + { + ungetc(ch1, fptr3); + fscanf(fptr3, "%s", str1); + if (str1[0] != ' ' || str1[0] != 'n') + w++; + } + fprintf(fptr3, "\n\n number of lines = %d n number of words is = %d\n", n, w - 1); + /*appendig comments in the concatenated file*/ + fclose(fptr1); + fclose(fptr2); + fclose(fptr3); +} \ No newline at end of file diff --git a/c/Data_Input_Output/C Program to Append the Content of File at the end of Another.c b/c/Data_Input_Output/C Program to Append the Content of File at the end of Another.c new file mode 100644 index 0000000..89f0c48 --- /dev/null +++ b/c/Data_Input_Output/C Program to Append the Content of File at the end of Another.c @@ -0,0 +1,41 @@ +/* + * C Program to Append the Content of File at the end of Another + */ +#include +#include + +main() +{ + FILE *fsring1, *fsring2, *ftemp; + char ch, file1[20], file2[20], file3[20]; + printf("Enter name of first file "); + gets(file1); + printf("Enter name of second file "); + gets(file2); + printf("Enter name to store merged file "); + gets(file3); + fsring1 = fopen(file1, "r"); + fsring2 = fopen(file2, "r"); + if (fsring1 == NULL || fsring2 == NULL) + { + perror("Error has occured"); + printf("Press any key to exit...\n"); + exit(EXIT_FAILURE); + } + ftemp = fopen(file3, "w"); + if (ftemp == NULL) + { + perror("Error has occures"); + printf("Press any key to exit...\n"); + exit(EXIT_FAILURE); + } + while ((ch = fgetc(fsring1)) != EOF) + fputc(ch, ftemp); + while ((ch = fgetc(fsring2) ) != EOF) + fputc(ch, ftemp); + printf("Two files merged %s successfully.\n", file3); + fclose(fsring1); + fclose(fsring2); + fclose(ftemp); + return 0; +} \ No newline at end of file diff --git a/c/Data_Input_Output/C Program to Capitalize First Letter of every Word in a File.c b/c/Data_Input_Output/C Program to Capitalize First Letter of every Word in a File.c new file mode 100644 index 0000000..62b5be2 --- /dev/null +++ b/c/Data_Input_Output/C Program to Capitalize First Letter of every Word in a File.c @@ -0,0 +1,59 @@ +/* + * C Program to Capitalize First Letter of every Word in a File + */ +#include +#include +#include +int to_initcap_file(FILE *); + +void main(int argc, char * argv[]) +{ + FILE *fp1; + char fp[10]; + int p; + fp1 = fopen(argv[1], "r+"); + if (fp1 == NULL) + { + printf("cannot open the file "); + exit(0); + } + p = to_initcap_file(fp1); + if (p == 1) + { + printf("success"); + } + else + { + printf("failure"); + } + fclose(fp1); +} + +/* capitalizes first letter of every word */ +int to_initcap_file(FILE *fp) +{ + char c; + c = fgetc(fp); + if (c >= 'a' && c <= 'z') + { + fseek(fp, -1L, 1); + fputc(c - 32, fp); + } + while(c != EOF) + { + if (c == ' ' || c == '\n') + { + c = fgetc(fp); + if (c >= 'a' && c <= 'z') + { + fseek(fp, -1L, 1); + fputc(c - 32, fp); + } + } + else + { + c = fgetc(fp); + } + } + return 1; +} \ No newline at end of file diff --git a/c/Data_Input_Output/C Program to Collect Statistics of a Source File like Total Lines, Total no. of Blank Lines, Total no.c b/c/Data_Input_Output/C Program to Collect Statistics of a Source File like Total Lines, Total no. of Blank Lines, Total no.c new file mode 100644 index 0000000..64a9731 --- /dev/null +++ b/c/Data_Input_Output/C Program to Collect Statistics of a Source File like Total Lines, Total no. of Blank Lines, Total no.c @@ -0,0 +1,52 @@ +/* + * C Program to Collect Statistics of a Source File like Total Lines, + * Total no. of Blank Lines, Total no. of Lines ending with Semicolon + */ +#include +#include + +void main(int argc, char *argv[]) /* Command line Arguments */ +{ + int ncount = 0, ccount = 0, scount = 0, blank = 0; + char ch; + FILE *fp; + fp = fopen(argv[1], "r"); + if (fp == NULL) + { + perror("Error Occured"); + } + else + { + while(1) + { + ch = fgetc(fp); + if (ch == EOF) + { + break; + } + if (ch == 10) + { + ncount++; + if (ch = fgetc(fp) == '\n') + { + fseek(fp, -1, 1); /* shifting offset of the file to previous position */ + blank++; + } + } + else if (ch == 59) + { + scount++; + } + else if (ch == '/' || ch == '*') + { + ccount++; + } + } + } + printf("\nThe Total number of lines are %d", ncount); + printf("\nThe Total number of Commented lines are %d", ccount); + printf("\nThe Total number of blank lines are %d", blank); + printf("\nThe total number of lines that end with Semicolon %d", scount); + printf("\nThe length of Actual code is %d ", ncount-blank-ccount); + fclose(fp); +} \ No newline at end of file diff --git a/c/Data_Input_Output/C Program to Compare two Binary Files, Printing the First Byte Position where they Differ.c b/c/Data_Input_Output/C Program to Compare two Binary Files, Printing the First Byte Position where they Differ.c new file mode 100644 index 0000000..75cbe35 --- /dev/null +++ b/c/Data_Input_Output/C Program to Compare two Binary Files, Printing the First Byte Position where they Differ.c @@ -0,0 +1,75 @@ +/* + * C Program to Compare two Binary Files, Printing the First Byte + * Position where they Differ + */ +#include + +void compare_two_binary_files(FILE *,FILE *); + +int main(int argc, char *argv[]) +{ + FILE *fp1, *fp2; + if (argc < 3) + { + printf("\nInsufficient Arguments: \n"); + printf("\nHelp:./executable \n"); + return; + } + else + { + fp1 = fopen(argv[1], "r"); + if (fp1 == NULL) + { + printf("\nError in opening file %s", argv[1]); + return; + } + fp2 = fopen(argv[2], "r"); + if (fp2 == NULL) + { + printf("\nError in opening file %s", argv[2]); + return; + } + if ((fp1 != NULL) && (fp2 != NULL)) + { + compare_two_binary_files(fp1, fp2); + } + } +} + +/* + * compare two binary files character by character + */ +void compare_two_binary_files(FILE *fp1, FILE *fp2) +{ + char ch1, ch2; + int flag = 0; + while (((ch1 = fgetc(fp1)) != EOF) &&((ch2 = fgetc(fp2)) != EOF)) + { + /* + * character by character comparision + * if equal then continue by comparing till the end of files + */ + if (ch1 == ch2) + { + flag = 1; + continue; + } + /* + * If not equal then returns the byte position + */ + else + { + fseek(fp1, -1, SEEK_CUR); + flag = 0; + break; + } + } + if (flag == 0) + { + printf("Two files are not equal : byte poistion at which two files differ is %d\n", ftell(fp1)+1); + } + else + { + printf("Two files are Equal\n ", ftell(fp1)+1); + } +} \ No newline at end of file diff --git a/c/Data_Input_Output/C Program to Concate two file into third file.c b/c/Data_Input_Output/C Program to Concate two file into third file.c new file mode 100644 index 0000000..7e6c43a --- /dev/null +++ b/c/Data_Input_Output/C Program to Concate two file into third file.c @@ -0,0 +1,35 @@ +#include +#include +void main() +{ + FILE *fp1,*fp2,*fp3; + char ch; + int tc=0,tw=1; + fp1=fopen("file1.txt","r"); + if(fp1==NULL) + { + printf("File doesn't exist\n"); + exit(1); + } + fp2=fopen("file2.txt","r"); + if(fp2==NULL) + { + printf("File doesn't exist\n"); + exit(1); + } + fp3=fopen("file3.txt","w"); + while(!feof(fp1)) + { + ch=getc(fp1); + putc(ch,fp3); + } + fclose(fp1); + while(!feof(fp2)) + { + ch=getc(fp2); + putc(ch,fp3); + } + fclose(fp2); + fclose(fp3); + printf("file1 and file2 are concatenated in file3") +} \ No newline at end of file diff --git a/c/Data_Input_Output/C Program to Convert the Content of File to LowerCase.c b/c/Data_Input_Output/C Program to Convert the Content of File to LowerCase.c new file mode 100644 index 0000000..aae3a94 --- /dev/null +++ b/c/Data_Input_Output/C Program to Convert the Content of File to LowerCase.c @@ -0,0 +1,43 @@ +/* + * C Program to Convert the Content of File to LowerCase + */ +#include +#include + +int to_lower_file(FILE *); + +void main(int argc, char * argv[]) +{ + int op = -1; + char ch; + FILE *fp; + if (fp = fopen(argv[1], "r+")) + { + printf("FILE has been opened..!!!\n"); + op = to_lower_file(fp); + printf(" %d \n", op); + fclose(fp); + } + else + { + perror("Error Occured"); + printf(" %d\n ", op); + } +} + +int to_lower_file(FILE *f) +{ + int c; + char ch; + while ((ch = fgetc(f))! = EOF) + { + c = (int)ch; + if (c >= 65 && c <= 90) + { + ch = ch + 32; + fseek(f, -1L, 1); + fputc(ch, f); + } + } + return 0; +} \ No newline at end of file diff --git a/c/Data_Input_Output/C Program to Convert the Content of File to UpperCase.c b/c/Data_Input_Output/C Program to Convert the Content of File to UpperCase.c new file mode 100644 index 0000000..2d1e951 --- /dev/null +++ b/c/Data_Input_Output/C Program to Convert the Content of File to UpperCase.c @@ -0,0 +1,69 @@ +/* + * C Program to Convert the Content of File to UpperCase + */ +#include + +int to_upper_file(FILE *); + +int main(int argc,char *argv[]) +{ + FILE *fp; + int status; + if (argc == 1) + { + printf("Insufficient Arguments:"); + printf("No File name is provided at command line"); + return; + } + if (argc > 1) + { + fp = fopen(argv[1],"r+"); + status = to_upper_file(fp); + /* + *If the status returned is 0 then the coversion of file content was completed successfully + */ + if (status == 0) + { + printf("\n The content of \"%s\" file was successfully converted to upper case\n",argv[1]); + return; + } + /* + * If the status returnes is -1 then the conversion of file content was not done + */ + if (status == -1) + { + printf("\n Failed to convert"); + return; + } + } +} + +/* + * convert the file content to uppercase + */ +int to_upper_file(FILE *fp) +{ + char ch; + if (fp == NULL) + { + perror("Unable to open file"); + return -1; + } + else + { + /* + * Read the file content and convert to uppercase + */ + while (ch != EOF) + { + ch = fgetc(fp); + if ((ch >= 'a') && (ch <= 'z')) + { + ch = ch - 32; + fseek(fp,-1,SEEK_CUR); + fputc(ch,fp); + } + } + return 0; + } +} \ No newline at end of file diff --git a/c/Data_Input_Output/C Program to Copy File into Another File.c b/c/Data_Input_Output/C Program to Copy File into Another File.c new file mode 100644 index 0000000..ebce4cf --- /dev/null +++ b/c/Data_Input_Output/C Program to Copy File into Another File.c @@ -0,0 +1,30 @@ +/* + * C Program to Copy a File into Another File + */ +#include + +void main(int argc,char **argv) +{ + FILE *fp1, *fp2; + char ch; + int pos; + if ((fp1 = fopen(argv[1],"r")) == NULL) + { + printf("\nFile cannot be opened"); + return; + } + else + { + printf("\nFile opened for copy...\n "); + } + fp2 = fopen(argv[2], "w"); + fseek(fp1, 0L, SEEK_END); // file pointer at end of file + pos = ftell(fp1); + fseek(fp1, 0L, SEEK_SET); // file pointer set at start + while (pos--) + { + ch = fgetc(fp1); // copying file character by character + fputc(ch, fp2); + } + fcloseall(); +} \ No newline at end of file diff --git a/c/Data_Input_Output/C Program to Copy data from one file to other.c b/c/Data_Input_Output/C Program to Copy data from one file to other.c new file mode 100644 index 0000000..3ab0b2a --- /dev/null +++ b/c/Data_Input_Output/C Program to Copy data from one file to other.c @@ -0,0 +1,28 @@ +#include +void main() +{ + FILE *p,*q; + char file1[20],file2[20]; + char ch; + printf("\nEnter the source file name to be copied: "); + gets(file1); + p=fopen(file1,"r"); + if(p==NULL) + { + printf("cannot open %s",file1); + exit(0); + } + printf("\nEnter the destination file name: "); + gets(file2); + q=fopen(file2,"w"); + if(q==NULL) + { + printf("cannot open %s",file2); + exit(0); + } + while((ch=getc(p))!=EOF) + putc(ch,q); + printf("\nCOMPLETED"); + fclose(p); + fclose(q); +} \ No newline at end of file diff --git a/c/Data_Input_Output/C Program to Count No of Lines, Blank Lines, Comments in a given Program.c b/c/Data_Input_Output/C Program to Count No of Lines, Blank Lines, Comments in a given Program.c new file mode 100644 index 0000000..08e0ece --- /dev/null +++ b/c/Data_Input_Output/C Program to Count No of Lines, Blank Lines, Comments in a given Program.c @@ -0,0 +1,51 @@ +/* + * C Program to Count No of Lines, Blank Lines, Comments in a given Program + */ +#include + +void main(int argc, char* argv[]) +{ + int line_count = 0, n_o_c_l = 0, n_o_n_b_l = 0, n_o_b_l = 0, n_e_c = 0; + FILE *fp1; + char ch; + fp1 = fopen(argv[1], "r"); + while ((ch = fgetc(fp1))! = EOF) + { + if (ch == '\n') + { + line_count++; + } + if (ch == '\n') + { + if ((ch = fgetc(fp1)) == '\n') + { + fseek(fp1, -1, 1); + n_o_b_l++; + } + } + if (ch == ';') + { + if ((ch = fgetc(fp1)) == '\n') + { + fseek(fp1, -1, 1); + n_e_c++; + } + } + } + fseek(fp1, 0, 0); + while ((ch = fgetc(fp1))! = EOF) + { + if (ch == '/') + { + if ((ch = fgetc(fp1)) == '/') + { + n_o_c_l++; + } + } + } + printf("Total no of lines: %d\n", line_count); + printf("Total no of comment line: %d\n", n_o_c_l); + printf("Total no of blank lines: %d\n", n_o_b_l); + printf("Total no of non blank lines: %d\n", line_count-n_o_b_l); + printf("Total no of lines end with semicolon: %d\n", n_e_c); +} \ No newline at end of file diff --git a/c/Data_Input_Output/C Program to Count total number of character and word in a file.c b/c/Data_Input_Output/C Program to Count total number of character and word in a file.c new file mode 100644 index 0000000..56db7ba --- /dev/null +++ b/c/Data_Input_Output/C Program to Count total number of character and word in a file.c @@ -0,0 +1,24 @@ +#include +#include +void main() +{ + FILE *fp; + char ch; + int tc=0,tw=1; + fp=fopen("file.txt","r"); + if(fp==NULL) + { + printf("File doesn't exist\n"); + exit(1); + } + while(!feof(fp)) + { + ch=getc(fp); + tc++; + if(ch==' ') + { + tw++; + } + } + printf("Total character: %d \nTotal words: %d",tc,tw); +} \ No newline at end of file diff --git a/c/Data_Input_Output/C Program to Create Employee File Name Record that is taken from the Command-Line Argument.c b/c/Data_Input_Output/C Program to Create Employee File Name Record that is taken from the Command-Line Argument.c new file mode 100644 index 0000000..84db4a3 --- /dev/null +++ b/c/Data_Input_Output/C Program to Create Employee File Name Record that is taken from the Command-Line Argument.c @@ -0,0 +1,150 @@ +/* + * C Program to Create Employee File Name Record that is taken from the Command-Line Argument + */ +#include +#include +#include +#include + +struct emprec +{ + int empid; + char *name; +}; +typedef struct emprec emp; + +void insert(char *a); +void display(char *a); +void update(char *a); +int count; +void main(int argc, char *argv[]) +{ + int choice; + while (1) + { + printf("Enter the choice\n"); + printf("1-Insert a new record into file\n2-Display the records\n"); + printf("3-Update the record\n4-Exit\n"); + scanf("%d", &choice); + switch (choice) + { + case 1: + insert(argv[1]); + break; + case 2: + display(argv[1]); + break; + case 3: + update(argv[1]); + break; + case 4: + exit(0); + default: + printf("Enter the correct choice\n"); + } + } +} + +/* To insert a new recored into the file */ +void insert(char *a) +{ + FILE *fp1; + emp *temp1 = (emp *)malloc(sizeof(emp)); + temp1->name = (char *)malloc(200 * sizeof(char)); //allocating memory for pointer + fp1 = fopen(a, "a+"); + if (fp1 == NULL) + perror(""); + else + { + printf("Enter the employee id\n"); + scanf("%d", &temp1->empid); + fwrite(&temp1->empid, sizeof(int), 1, fp1); + printf("Enter the employee name\n"); + scanf(" %[^\n]s", temp1->name); + fwrite(temp1->name, 200, 1, fp1); + count++; + } + fclose(fp1); + free(temp1); + free(temp1->name); +} + +/* To display the records in the file */ +void display(char *a) +{ + FILE *fp1; + char ch; + int var = count; + emp *temp = (emp *)malloc(sizeof(emp)); + temp->name = (char *)malloc(200*sizeof(char)); + fp1 = fopen(a, "r"); + if (count == 0) + { + printf("no records to display\n"); + return; + } + if (fp1 == NULL) + perror(""); + else + { + while(var) // display the employee records + { + fread(&temp->empid, sizeof(int), 1, fp1); + printf("%d", temp->empid); + fread(temp->name, 200, 1, fp1); + printf(" %s\n", temp->name); + var--; + } + } + fclose(fp1); + free(temp); + free(temp->name); +} + +/* To Update the given record */ +void update(char *a) +{ + FILE *fp1; + char ch, name[200]; + int var = count, id, c; + emp *temp = (emp *)malloc(sizeof(emp)); + temp->name = (char *)malloc(200*sizeof(char)); + fp1 = fopen(a, "r+"); + if (fp1 == NULL) + perror(""); + else + { + while (var) //displaying employee records so that user enter correct employee id + { + fread(&temp->empid, sizeof(int), 1, fp1); + printf("%d", temp->empid); + fread(temp->name, 200, 1, fp1); + printf(" %s\n", temp->name); + var--; + } + printf("enter which employee id to be updated\n"); + scanf("%d", &id); + fseek(fp1, 0, 0); + var = count; + while(var) //loop to update the name of entered employeeid + { + fread(&temp->empid, sizeof(int), 1, fp1); + if (id == temp->empid) + { + printf("enter employee name for update:"); + scanf(" %[^\n]s", name); + c = fwrite(name, 200, 1, fp1); + break; + } + fread(temp->name, 200, 1, fp1); + var--; + } + if (c == 1) + printf("update of the record succesfully\n"); + else + printf("update unsuccesful enter correct id\n"); + fclose(fp1); + free(temp); + free(temp->name); + } +} \ No newline at end of file diff --git a/c/Data_Input_Output/C Program to Create Employee Record and Update it.c b/c/Data_Input_Output/C Program to Create Employee Record and Update it.c new file mode 100644 index 0000000..fc03ab9 --- /dev/null +++ b/c/Data_Input_Output/C Program to Create Employee Record and Update it.c @@ -0,0 +1,127 @@ +/* + * C Program to Create Employee Record and Update it + */ +#include +#include +#include +#define size 200 + +struct emp +{ + int id; + char *name; +}*emp1, *emp3; + +void display(); +void create(); +void update(); + +FILE *fp, *fp1; +int count = 0; + +void main(int argc, char **argv) +{ + int i, n, ch; + printf("1] Create a Record\n"); + printf("2] Display Records\n"); + printf("3] Update Records\n"); + printf("4] Exit"); + while (1) + { + printf("\nEnter your choice : "); + scanf("%d", &ch); + switch (ch) + { + case 1: + fp = fopen(argv[1], "a"); + create(); + break; + case 2: + fp1 = fopen(argv[1],"rb"); + display(); + break; + case 3: + fp1 = fopen(argv[1], "r+"); + update(); + break; + case 4: + exit(0); + } + } +} + +/* To create an employee record */ +void create() +{ + int i; + char *p; + emp1 = (struct emp *)malloc(sizeof(struct emp)); + emp1->name = (char *)malloc((size)*(sizeof(char))); + printf("Enter name of employee : "); + scanf(" %[^\n]s", emp1->name); + printf("Enter emp id : "); + scanf(" %d", &emp1->id); + fwrite(&emp1->id, sizeof(emp1->id), 1, fp); + fwrite(emp1->name, size, 1, fp); + count++; // count to number of entries of records + fclose(fp); +} + +/* Display the records in the file */ +void display() +{ + emp3=(struct emp *)malloc(1*sizeof(struct emp)); + emp3->name=(char *)malloc(size*sizeof(char)); + int i = 1; + if (fp1 == NULL) + printf("\nFile not opened for reading"); + while (i <= count) + { + fread(&emp3->id, sizeof(emp3->id), 1, fp1); + fread(emp3->name, size, 1, fp1); + printf("\n%d %s",emp3->id,emp3->name); + i++; + } + fclose(fp1); + free(emp3->name); + free(emp3); +} + +void update() +{ + int id, flag = 0, i = 1; + char s[size]; + if (fp1 == NULL) + { + printf("File cant be opened"); + return; + } + printf("Enter employee id to update : "); + scanf("%d", &id); + emp3 = (struct emp *)malloc(1*sizeof(struct emp)); + emp3->name=(char *)malloc(size*sizeof(char)); + while(i<=count) + { + fread(&emp3->id, sizeof(emp3->id), 1, fp1); + fread(emp3->name,size,1,fp1); + if (id == emp3->id) + { + printf("Enter new name of emplyee to update : "); + scanf(" %[^\n]s", s); + fseek(fp1, -204L, SEEK_CUR); + fwrite(&emp3->id, sizeof(emp3->id), 1, fp1); + fwrite(s, size, 1, fp1); + flag = 1; + break; + } + i++; + } + if (flag != 1) + { + printf("No employee record found"); + flag = 0; + } + fclose(fp1); + free(emp3->name); /* to free allocated memory */ + free(emp3); +} \ No newline at end of file diff --git a/c/Data_Input_Output/C Program to Create a File & Store Information.c b/c/Data_Input_Output/C Program to Create a File & Store Information.c new file mode 100644 index 0000000..6508c8e --- /dev/null +++ b/c/Data_Input_Output/C Program to Create a File & Store Information.c @@ -0,0 +1,30 @@ +/* + * C program to create a file called emp.rec and store information + * about a person, in terms of his name, age and salary. + */ +#include + +void main() +{ + FILE *fptr; + char name[20]; + int age; + float salary; + /* open for writing */ + fptr = fopen("emp.rec", "w"); + if (fptr == NULL) + { + printf("File does not exists \n"); + return; + } + printf("Enter the name \n"); + scanf("%s", name); + fprintf(fptr, "Name = %s\n", name); + printf("Enter the age\n"); + scanf("%d", &age); + fprintf(fptr, "Age = %d\n", age); + printf("Enter the salary\n"); + scanf("%f", &salary); + fprintf(fptr, "Salary = %.2f\n", salary); + fclose(fptr); +} \ No newline at end of file diff --git a/c/Data_Input_Output/C Program to Find Sum of Numbers given in Command Line Arguments Recursively.c b/c/Data_Input_Output/C Program to Find Sum of Numbers given in Command Line Arguments Recursively.c new file mode 100644 index 0000000..248eb7a --- /dev/null +++ b/c/Data_Input_Output/C Program to Find Sum of Numbers given in Command Line Arguments Recursively.c @@ -0,0 +1,30 @@ +/* + * C Program to Find Sum of Numbers given in Command Line Arguments + * Recursively + */ +#include + +int count, s = 0; +void sum(int *, int *); + +void main(int argc, char *argv[]) +{ + int i, ar[argc]; + count = argc; + for (i = 1; i < argc; i++) + { + ar[i - 1] = atoi(argv[i]); + } + sum(ar, ar + 1); + printf("%d", s); +} + +/* computes sum of two numbers recursively */ +void sum(int *a, int * b) +{ + if (count == 1) + return; + s = s + *a + *b; + count -= 2; + sum(a + 2, b + 2); +} \ No newline at end of file diff --git a/c/Data_Input_Output/C Program to Find the Number of Lines in a Text File.c b/c/Data_Input_Output/C Program to Find the Number of Lines in a Text File.c new file mode 100644 index 0000000..87ca8ef --- /dev/null +++ b/c/Data_Input_Output/C Program to Find the Number of Lines in a Text File.c @@ -0,0 +1,29 @@ +/* + * C Program to Find the Number of Lines in a Text File + */ +#include + +int main() +{ + FILE *fileptr; + int count_lines = 0; + char filechar[40], chr; + printf("Enter file name: "); + scanf("%s", filechar); + fileptr = fopen(filechar, "r"); + //extract character from file and store in chr + chr = getc(fileptr); + while (chr != EOF) + { + //Count whenever new line is encountered + if (chr == 'n') + { + count_lines = count_lines + 1; + } + //take next character from file. + chr = getc(fileptr); + } + fclose(fileptr); //close file. + printf("There are %d lines in %s in a file\n", count_lines, filechar); + return 0; +} \ No newline at end of file diff --git a/c/Data_Input_Output/C Program to Find the Size of File using File Handling Function.c b/c/Data_Input_Output/C Program to Find the Size of File using File Handling Function.c new file mode 100644 index 0000000..1e199ed --- /dev/null +++ b/c/Data_Input_Output/C Program to Find the Size of File using File Handling Function.c @@ -0,0 +1,20 @@ +/* + * C Program to Find the Size of File using File Handling Function + */ +#include + +void main(int argc, char **argv) +{ + FILE *fp; + char ch; + int size = 0; + fp = fopen(argv[1], "r"); + if (fp == NULL) + printf("\nFile unable to open "); + else + printf("\nFile opened "); + fseek(fp, 0, 2); /* file pointer at the end of file */ + size = ftell(fp); /* take a position of file pointer un size variable */ + printf("The size of given file is : %d\n", size); + fclose(fp); +} \ No newline at end of file diff --git a/c/Data_Input_Output/C Program to Illustrate Reading of Data from a File.c b/c/Data_Input_Output/C Program to Illustrate Reading of Data from a File.c new file mode 100644 index 0000000..2784b70 --- /dev/null +++ b/c/Data_Input_Output/C Program to Illustrate Reading of Data from a File.c @@ -0,0 +1,64 @@ +/* + * C program to illustrate how a file stored on the disk is read + + This C Program illustrates reading of data from a file. The program opens a file which is present. Once the file opens successfully, it uses libc fgetc() library call to read the content. + */ +#include +#include + +void main() +{ + FILE *fptr; + char filename[15]; + char ch; + printf("Enter the filename to be opened \n"); + scanf("%s", filename); + /* open the file for reading */ + fptr = fopen(filename, "r"); + if (fptr == NULL) + { + printf("Cannot open file \n"); + exit(0); + } + ch = fgetc(fptr); + while (ch != EOF) + { + printf ("%c", ch); + ch = fgetc(fptr); + } + fclose(fptr); +} + +/* +Enter the filename to be opened +pgm95.c +/* + * C program to create a file called emp.rec and store information + * about a person, in terms of his name, age and salary. + */ + +#include + +void main() +{ + FILE *fptr; + char name[20]; + int age; + float salary; + fptr = fopen ("emp.rec", "w"); /* open for writing*/ + if (fptr == NULL) + { + printf("File does not exists \n"); + return; + } + printf("Enter the name \n"); + scanf("%s", name); + fprintf(fptr, "Name = %s\n", name); + printf("Enter the age \n"); + scanf("%d", &age); + fprintf(fptr, "Age = %d\n", age); + printf("Enter the salary \n"); + scanf("%f", &salary); + fprintf(fptr, "Salary = %.2f\n", salary); + fclose(fptr); +} \ No newline at end of file diff --git a/c/Data_Input_Output/C Program to Join Lines of Two given Files and Store them in a New file.c b/c/Data_Input_Output/C Program to Join Lines of Two given Files and Store them in a New file.c new file mode 100644 index 0000000..71fb61d --- /dev/null +++ b/c/Data_Input_Output/C Program to Join Lines of Two given Files and Store them in a New file.c @@ -0,0 +1,155 @@ +/* + * C Program to Join Lines of Two given Files and + * Store them in a New file + */ +#include +#include + +/* Function Prototype */ +int joinfiles(FILE *, FILE *, FILE *); + +char ch; +int flag; + +void main(int argc, char *argv[]) +{ + FILE *file1, *file2, *target; + file1 = fopen(argv[1], "r"); + if (file1 == NULL) + { + perror("Error Occured!"); + } + file2 = fopen(argv[2], "r"); + if (file2 == NULL) + { + perror("Error Occured!"); + } + target = fopen(argv[3], "a"); + if (target == NULL) + { + perror("Error Occured!"); + } + joinfiles(file1, file2, target); /* Calling Function */ + if (flag == 1) + { + printf("The files have been successfully concatenated\n"); + } +} + +/* Code join the two given files line by line into a new file */ + +int joinfiles(FILE *file1, FILE *file2, FILE *target) +{ + while ((fgetc(file1) != EOF) || (fgetc(file2) != EOF)) + { + fseek(file1, -1, 1); + while ((ch = fgetc(file1)) != '\n') + { + if (ch == EOF) + { + break; + } + else + { + fputc(ch, target); + } + } + while ((ch = fgetc(file2)) != '\n') + { + if (ch == EOF) + { + break; + } + else + { + fputc(ch, target); + } + } + fputc('\n', target); + } + fclose(file1); + fclose(file2); + fclose(target); + return flag = 1; +} + +/* +The files have been successfully concatenated + +/* FIRST FILE */ + +/* +Hello!! +This is a C Program File. +Consider a code to Add two numbers +*/ + +#include +/* Function Prototype */ +int sum(int, int); +void main() +{ + int num1, num2; + printf("Enter Number1 and Number2:"); + scanf("%d %d ", num1, num2); + sum(num1, num2); +} + +int sum(int a, int b) +{ + return a + b; +} + +/* SECOND FILE */ + +/* + * this is temporary file for use in file handling + */ +#include + +int sqrt(int); +void main() +{ + int num; + printf("enter the number:"); + scanf("%d", &num); + sqrt(num); + printf("The square of the given number is:", num); +} +int sqrt(int num) +{ + return num*num; +} + +/* CONCATENATED FILE */ +/* +Hello!! * this is temporary file for use in file handling +This is a C Program File. * +Consider a code to Add two numbers */ +*/ +#include +#include +int sqrt(int); +/* Function Prototype */void main() +{ + int sum(int, int); + int num; + void main() printf("enter the number:"); + { + scanf("%d", &num); + int num1, num2; + sqrt(num); + printf("Enter Number1 and Number2:"); + printf("The square of the given number is:", num); + scanf("%d %d ", num1, num2); + } + sum(num1, num2); + int sqrt(int num) +} +{ + return num*num; + int sum(int a, int b) +} +{ + return a + b; +} \ No newline at end of file diff --git a/c/Data_Input_Output/C Program to Know the last date of modification of any file.c b/c/Data_Input_Output/C Program to Know the last date of modification of any file.c new file mode 100644 index 0000000..d0cfcff --- /dev/null +++ b/c/Data_Input_Output/C Program to Know the last date of modification of any file.c @@ -0,0 +1,12 @@ +#include +#include +#include +int main() +{ + struct stat s; + FILE *fp; + fp=fopen("exmple.txt","r"); + fstat(fileno(fp),&s); + printf("Last date of modification : %s",ctime(&s.st_ctime)); + return 0; +} \ No newline at end of file diff --git a/c/Data_Input_Output/C Program to Print Environment Variables.c b/c/Data_Input_Output/C Program to Print Environment Variables.c new file mode 100644 index 0000000..e5dbd51 --- /dev/null +++ b/c/Data_Input_Output/C Program to Print Environment Variables.c @@ -0,0 +1,13 @@ +/* + * C Program to Print Environment variables + */ +#include + +void main(int argc, char *argv[], char * envp[]) +{ + int i; + for (i = 0; envp[i] != NULL; i++) + { + printf("\n%s", envp[i]); + } +} \ No newline at end of file diff --git a/c/Data_Input_Output/C Program to Print first line of a file.c b/c/Data_Input_Output/C Program to Print first line of a file.c new file mode 100644 index 0000000..732c857 --- /dev/null +++ b/c/Data_Input_Output/C Program to Print first line of a file.c @@ -0,0 +1,16 @@ +#include +#include +void main() +{ + FILE *fp; + char str[50]; + fp=fopen("file.txt","r"); + if(fp==NULL) + { + printf("File doesn't exist\n"); + exit(1); + } + fscanf(fp,"%s",str); + printf("First line of the file: %s",str); + fclose(fp); +} \ No newline at end of file diff --git a/c/Data_Input_Output/C Program to Program to print square, cube and fourth power of a given number.c b/c/Data_Input_Output/C Program to Program to print square, cube and fourth power of a given number.c new file mode 100644 index 0000000..7f99a0a --- /dev/null +++ b/c/Data_Input_Output/C Program to Program to print square, cube and fourth power of a given number.c @@ -0,0 +1,28 @@ +/* pow() - program to print square, cube and fourth power of a given number without doing any unnecessary calculations */ + +#include +#include +#include + +void main() +{ + float x ; + clrscr() ; + printf("Enter a number: ") ; + scanf("%f", &x) ; + printf("Square = %f \n", pow(x,2) ) ; + printf("Cube = %f \n", pow(x,3) ) ; + printf("Fourth power = %f \n", pow(x,4) ) ; + getch() ; +} + +/* +Output: + +Enter a number: 2.5 +Square = 6.250000 +Cube = 15.625000 +Fourth power = 39.062500 + +*/ + diff --git a/c/Data_Input_Output/C Program to Program to swap values of two integers without using a temporary variable.c b/c/Data_Input_Output/C Program to Program to swap values of two integers without using a temporary variable.c new file mode 100644 index 0000000..7c3dffb --- /dev/null +++ b/c/Data_Input_Output/C Program to Program to swap values of two integers without using a temporary variable.c @@ -0,0 +1,30 @@ +/* swap - program to swap values of two integers without using a temporary variable */ + +#include +#include + +void main() +{ + int x, y ; + clrscr() ; + printf("Enter two integers: ") ; + scanf("%d %d", &x, &y) ; + printf("x=%d y=%d \n", x, y) ; + x=x+y ; + y=x-y ; + x=x-y ; + printf("After swapping: \n") ; + printf("x=%d y=%d", x, y) ; + getch() ; +} + +/* +Output: + +Enter two integers: 5 8 +x=5 y=8 +After swapping: +x=8 y=5 + +*/ + diff --git a/c/Data_Input_Output/C Program to Program which produces its own source code as its output.c b/c/Data_Input_Output/C Program to Program which produces its own source code as its output.c new file mode 100644 index 0000000..22471fa --- /dev/null +++ b/c/Data_Input_Output/C Program to Program which produces its own source code as its output.c @@ -0,0 +1,14 @@ +#include +void main() +{ + FILE *fp; + char c; + fp = fopen(__FILE__,"r"); + do + { + c= getc(fp); + putchar(c); + } + while(c!=EOF); + fclose(fp); +} \ No newline at end of file diff --git a/c/Data_Input_Output/C Program to Replace First Letter of every Word with Capital Letter.c b/c/Data_Input_Output/C Program to Replace First Letter of every Word with Capital Letter.c new file mode 100644 index 0000000..e8c153e --- /dev/null +++ b/c/Data_Input_Output/C Program to Replace First Letter of every Word with Capital Letter.c @@ -0,0 +1,51 @@ +/* + * C Program to replace first letter of every word with caps + */ +#include +#include + +void main(int argc, char *argv[]) +{ + FILE *fp1; + int return_val; + if ((fp1 = fopen(argv[1],"r+")) = = NULL) + { + printf("file cant be opened"); + exit(0); + } + return_val = init_cap_file(fp1); + if (return_val == 1) + { + printf("\nsuccess"); + } + else + { + printf("\n failure"); + } +} + +int init_cap_file(FILE *fp1) +{ + char ch; + ch = fgetc(fp1); + if (ch >= 97 && ch <= 122) + { + fseek(fp1, -1L, 1); + fputc(ch - 32, fp1); + } + while (ch != EOF) + { + if (ch = = ' '|| ch == '\n') + { + ch = fgetc(fp1); + if (ch >= 97 && ch <= 122) + { + fseek(fp1, -1L, 1); + fputc(ch - 32, fp1); + } + } + else + ch = fgetc(fp1); + } + return 1; +} \ No newline at end of file diff --git a/c/Data_Input_Output/C Program to Replace a specified Line in a Text File.c b/c/Data_Input_Output/C Program to Replace a specified Line in a Text File.c new file mode 100644 index 0000000..5bbaf02 --- /dev/null +++ b/c/Data_Input_Output/C Program to Replace a specified Line in a Text File.c @@ -0,0 +1,118 @@ +/* + * C Program to Replace a specified Line in a Text File + */ +#include + +int main(void) +{ + FILE *fileptr1, *fileptr2; + char filechar[40]; + char c; + int delete_line, temp = 1; + printf("Enter file name: "); + scanf("%s", filechar); + fileptr1 = fopen(filechar, "r"); + c = getc(fileptr1); + //print the contents of file . + while (c != EOF) + { + printf("%c", c); + c = getc(fileptr1); + } + printf(" \n Enter line number to be deleted and replaced"); + scanf("%d", &delete_line); + //take fileptr1 to start point. + rewind(fileptr1); + //open replica.c in write mode + fileptr2 = fopen("replica.c", "w"); + c = getc(fileptr1); + while (c != EOF) + { + if (c == 'n') + { + temp++; + } + //till the line to be deleted comes,copy the content to other + if (temp != delete_line) + { + putc(c, fileptr2); + } + else + { + while ((c = getc(fileptr1)) != 'n') + { + } + //read and skip the line ask for new text + printf("Enter new text"); + //flush the input stream + fflush(stdin); + putc('n', fileptr2); + //put 'n' in new file + while ((c = getchar()) != 'n') + putc(c, fileptr2); + //take the data from user and place it in new file + fputs("n", fileptr2); + temp++; + } + //continue this till EOF is encountered + c = getc(fileptr1); + } + fclose(fileptr1); + fclose(fileptr2); + remove(filechar); + rename("replica.c", filechar); + fileptr1 = fopen(filechar, "r"); + //reads the character from file + c = getc(fileptr1); + //until last character of file is encountered + while (c != EOF) + { + printf("%c", c); + //all characters are printed + c = getc(fileptr1); + } + fclose(fileptr1); + return 0; + /* + Enter file name: pgm3.c + /* + * C Program to Convert Octal to Decimal + */ +#include +#include + int main() + { + long int octal, decimal = 0; + int i = 0; + printf("Enter any octal number: "); + scanf("%ld", &octal); + while (octal != 0) + { + decimal = decimal +(octal % 10)* pow(8, i++); + octal = octal / 10; + } + printf("Equivalent decimal value: %ld",decimal); + return 0; + } + Enter line number to be deleted and replaced 13 replaced + Enter new text + /* + * C Program to Convert Octal to Decimal + */ +#include +#include + int main() + { + long int octal, decimal = 0; + int i = 0; + replaced + printf("Enter any octal number: "); + scanf("%ld", &octal); + while (octal != 0) + { + decimal = decimal +(octal % 10)* pow(8, i++); + octal = octal / 10; + } + printf("Equivalent decimal value: %ld",decimal); + return 0; + } \ No newline at end of file diff --git a/c/Data_Input_Output/C Program to Reverse the Contents of a File and Print it.c b/c/Data_Input_Output/C Program to Reverse the Contents of a File and Print it.c new file mode 100644 index 0000000..a2d1875 --- /dev/null +++ b/c/Data_Input_Output/C Program to Reverse the Contents of a File and Print it.c @@ -0,0 +1,69 @@ +/* + * C Program to Reverse the Contents of a File and Print it + */ +#include +#include + +long count_characters(FILE *); + +void main(int argc, char * argv[]) +{ + int i; + long cnt; + char ch, ch1; + FILE *fp1, *fp2; + if (fp1 = fopen(argv[1], "r")) + { + printf("The FILE has been opened...\n"); + fp2 = fopen(argv[2], "w"); + cnt = count_characters(fp1); // to count the total number of characters inside the source file + fseek(fp1, -1L, 2); // makes the pointer fp1 to point at the last character of the file + printf("Number of characters to be copied %d\n", ftell(fp1)); + while (cnt) + { + ch = fgetc(fp1); + fputc(ch, fp2); + fseek(fp1, -2L, 1); // shifts the pointer to the previous character + cnt--; + } + printf("\n**File copied successfully in reverse order**\n"); + } + else + { + perror("Error occured\n"); + } + fclose(fp1); + fclose(fp2); +} +// count the total number of characters in the file that *f points to +long count_characters(FILE *f) +{ + fseek(f, -1L, 2); + long last_pos = ftell(f); // returns the position of the last element of the file + last_pos++; + return last_pos; +} + +/* +$ gcc file12.c +$ cat test2 +The function STRERROR returns a pointer to an ERROR MSG STRING whose contents are implementation defined. +THE STRING is not MODIFIABLE and maybe overwritten by a SUBSEQUENT Call to the STRERROR function. +$ a.out test2 test_new +The FILE has been opened.. +Number of characters to be copied 203 + +**File copied successfully in reverse order** +$ cat test_new + +.noitcnuf RORRERTS eht ot llaC TNEUQESBUS a yb nettirwrevo ebyam dna ELBAIFIDOM ton si GNIRTS EHT +.denifed noitatnemelpmi era stnetnoc esohw GNIRTS GSM RORRE na ot retniop a snruter RORRERTS noitcnuf ehT +$ ./a.out test_new test_new_2 +The FILE has been opened.. +Number of characters to be copied 203 + +**File copied successfully in reverse order** +$ cat test_new_2 +The function STRERROR returns a pointer to an ERROR MSG STRING whose contents are implementation defined. +THE STRING is not MODIFIABLE and maybe overwritten by a SUBSEQUENT Call to the STRERROR function. +$ cmp test test_new_2 \ No newline at end of file diff --git a/c/Data_Input_Output/C Program to Update Details of Employee using Files.c b/c/Data_Input_Output/C Program to Update Details of Employee using Files.c new file mode 100644 index 0000000..b5fc441 --- /dev/null +++ b/c/Data_Input_Output/C Program to Update Details of Employee using Files.c @@ -0,0 +1,130 @@ +/* + * C Program to Update Details of Employee using Files + */ +#include +#include +#include +struct emp +{ + int empid; + char *name; +}; + +int count = 0; +void add_rec(char *a); +void display(char *a); +void update_rec(char *a); + +void main(int argc, char *argv[]) +{ + int choice; + while (1) + { + printf("MENU:\n"); + printf("1.Add a record\n"); + printf("2.Display the file\n"); + printf("3.Update the record\n"); + printf("Enter your choice:"); + scanf("%d", &choice); + switch(choice) + { + case 1: + add_rec(argv[1]); + break; + case 2: + display(argv[1]); + break; + case 3: + update_rec(argv[1]); + break; + case 4: + exit(0); + default: + printf("Wrong choice!!!\nEnter the correct choice\n"); + } + } +} + +void add_rec(char *a) +{ + FILE *fp; + fp = fopen(a, "a+"); + struct emp *temp = (struct emp *)malloc(sizeof(struct emp)); + temp->name = (char *)malloc(50*sizeof(char)); + if (fp == NULL) + printf("Error!!!"); + else + { + printf("Enter the employee id\n"); + scanf("%d", &temp->empid); + fwrite(&temp->empid, sizeof(int), 1, fp); + printf("enter the employee name\n"); + scanf(" %[^\n]s", temp->name); + fwrite(temp->name, 50, 1, fp); + count++; + } + fclose(fp); + free(temp); + free(temp->name); +} + +void display(char *a) +{ + FILE *fp; + char ch; + int rec = count; + fp = fopen(a, "r"); + struct emp *temp = (struct emp *)malloc(sizeof(struct emp)); + temp->name = (char *)malloc(50*sizeof(char)); + if (fp == NULL) + printf("Error!!"); + else + { + while (rec) + { + fread(&temp->empid, sizeof(int), 1, fp); + printf("%d", temp->empid); + fread(temp->name, 50, 1, fp); + printf(" %s\n", temp->name); + rec--; + } + } + fclose(fp); + free(temp); + free(temp->name); +} + +void update_rec(char *a) +{ + FILE *fp; + char ch, name[5]; + int rec, id, c; + fp = fopen(a, "r+"); + struct emp *temp = (struct emp *)malloc(sizeof(struct emp)); + temp->name = (char *)malloc(50*sizeof(char)); + printf("Enter the employee id to update:\n"); + scanf("%d", &id); + fseek(fp, 0, 0); + rec = count; + while (rec) + { + fread(&temp->empid, sizeof(int), 1, fp); + printf("%d", temp->empid); + if (id == temp->empid) + { + printf("Enter the employee name to be updated"); + scanf(" %[^\n]s", name); + c = fwrite(name, 50, 1, fp); + break; + } + fread(temp->name, 50, 1, fp); + rec--; + } + if (c == 1) + printf("Record updated\n"); + else + printf("Update not successful\n"); + fclose(fp); + free(temp); + free(temp->name); +} \ No newline at end of file diff --git a/c/Data_Input_Output/C Program to Write biodata of student created using nested structure in a file.c b/c/Data_Input_Output/C Program to Write biodata of student created using nested structure in a file.c new file mode 100644 index 0000000..69fd3d5 --- /dev/null +++ b/c/Data_Input_Output/C Program to Write biodata of student created using nested structure in a file.c @@ -0,0 +1,38 @@ +#include +typedef struct +{ + int day; + int month; + int year; +} date; +typedef struct +{ + char name[30]; + char place[30]; + int age; + date birthdate; +} biodata; +void main() +{ + FILE *fp; + biodata student; + int i; + fp=fopen("st.dat","w"); + printf("Enter name: "); + scanf(" %30[^\n]%*c",student.name); + printf("Enter place: "); + scanf(" %30[^\n]%*c",student.place); + printf("Enter age: "); + scanf("%d",&student.age); + printf("Enter birth date dd mm yy : "); + scanf("%d",&student.birthdate.day); + scanf("%d",&student.birthdate.month); + scanf("%d",&student.birthdate.year); + i =fprintf(fp,"Name :%s\nPlace: %s\nAge: %d \nDOB %d/%d/%d",student.name,student.place,student.age,student.birthdate.day, student.birthdate.month, + student.birthdate.year); + if(i!=0) + printf("Data stored"); + else + printf("failed"); + fclose(fp); +} \ No newline at end of file diff --git a/c/Data_Input_Output/C Program to Write entire array to a file.c b/c/Data_Input_Output/C Program to Write entire array to a file.c new file mode 100644 index 0000000..a3f3a81 --- /dev/null +++ b/c/Data_Input_Output/C Program to Write entire array to a file.c @@ -0,0 +1,18 @@ +#include +#include +int main() +{ + FILE *p; + int i,arr[10]; + if((p=fopen("demofile.txt", "wb"))==NULL) + { + printf("\nUnable to open file demofile.txt"); + exit(1); + } + printf("\nEnter ten values\n"); + for(i=0; i<10; i++) + scanf("%d",&arr[i]); + fwrite(arr,sizeof(arr),1,p); + fclose(p); + return 0; +} \ No newline at end of file diff --git a/c/Data_Input_Output/C program to Display the Function Names defined in C Source File.c b/c/Data_Input_Output/C program to Display the Function Names defined in C Source File.c new file mode 100644 index 0000000..5964eec --- /dev/null +++ b/c/Data_Input_Output/C program to Display the Function Names defined in C Source File.c @@ -0,0 +1,102 @@ +/* + * C program to Display the Function Names defined in C Source File + */ +#include +#include + +void check(char *c,int p1, int p2); +void display(char *c, int p1); + +void main(int argc, char **argv) +{ + FILE *fp; + char ch[100]; + char *pos1, *pos2, *pos3; + fp=fopen(argv[1], "r"); + if (fp == NULL) + { + printf("\nFile unable to open"); + return; + } + else + printf("\nFile Opened to display function names :\n"); + while (1) + { + if ((fgets(ch, 100, fp)) != NULL) + { + if ((strstr(ch, "/*")) == NULL) + { + pos1 = strchr(ch, '('); /* check opening brace */ + if (pos1) + { + pos2 = strchr(ch,')'); /* check oclosing brace */ + if (pos2) + { + pos3 = strchr(ch,';'); /* check for semicolon */ + if ((pos1 < pos2) && (pos3 == NULL) || (pos3 < pos1)) + { + check(ch, pos1 - ch, pos2 - ch); + } + else continue; + } + else continue; + } + else continue; + } + else continue; + } + else break; + } + fclose(fp); +} + +/* To check if it is a function */ +void check(char *c, int p1, int p2) +{ + int i, flag = 0, temp = p1; + if ((c[p1 + 1] == ')')) + { + display(c, p1); + return; + } + for (i = p1 + 1; i < p2; i++) + { + if ((c[i] != ' ') || (c[i] == ')')) + { + flag = 1; + } + if (flag == 0) + { + display(c, p1); + return; + } + else + { + flag = 0; + while (c[--temp] != ' '); + for (i = 0; i < temp; i++) + if (c[i]==' ') + { + flag = 1; + } + if (flag == 0) + { + display(c, p1); + return; + } + else + return; + } + } +} + +/* To display function name */ +void display(char *c,int p1) +{ + int temp = p1, i; + while (c[--temp] != ' '); + for (i = temp + 1; i < p1; i++) /* Print name of function character by character */ + printf("%c", c[i]); + printf("\n"); + return; +} \ No newline at end of file diff --git a/c/Data_Input_Output/C program to open a file and store data in it.c b/c/Data_Input_Output/C program to open a file and store data in it.c new file mode 100644 index 0000000..013b8f4 --- /dev/null +++ b/c/Data_Input_Output/C program to open a file and store data in it.c @@ -0,0 +1,11 @@ +#include +void main() +{ + FILE *fp; + char ch; + fp=fopen("file.txt","w"); + printf("\nEnter data to be stored in to the file: "); + while((ch=getchar())!=EOF) + putc(ch,fp); + fclose(fp); +} \ No newline at end of file diff --git a/c/Functions/C Program for Ackerman Problem..c b/c/Functions/C Program for Ackerman Problem..c new file mode 100644 index 0000000..319b32d --- /dev/null +++ b/c/Functions/C Program for Ackerman Problem..c @@ -0,0 +1,38 @@ +/* Ackerman Problem - Refer program for Question + +There is a recursive function called the ackermans function which is popular with the lecturers of computer science and can be defined like this +If m and n are integers greater than or equal to zero then +ack(m,n)=n+1, if m=0 +ack(m,n)=ack(m-1,1),if(n=0) and m>0 +ack(m,n)=ack(m-1,ack(m,n-1)),otherwise +write a recursive function to implement the above mentioned algorithm. */ + +#include +#include + +int ack(int m, int n) +{ + if(m==0) + return (n+1) ; + else if(n==0 && m>0) + return ( ack(m-1,1) ) ; + else + return ( ack(m-1, ack(m,n-1) ) ); +} + +void main() +{ + int m, n ; + clrscr() ; + printf("Enter two numbers: ") ; + scanf("%d %d", &m, &n) ; + printf("Solution is %d", ack(m,n) ) ; + getch() ; +} + +/* +Output: + +Enter two numbers: 2 3 +Solution is 9 +*/ diff --git a/c/Functions/C Program for Addition of two matrices using arrays source code.c b/c/Functions/C Program for Addition of two matrices using arrays source code.c new file mode 100644 index 0000000..e8cf923 --- /dev/null +++ b/c/Functions/C Program for Addition of two matrices using arrays source code.c @@ -0,0 +1,23 @@ +#include +void main() +{ + int a[3][3],b[3][3],c[3][3],i,j; + printf("Enter the First matrix: "); + for(i=0; i<3; i++) + for(j=0; j<3; j++) + scanf("%d",&a[i][j]); + printf("\nEnter the Second matrix : "); + for(i=0; i<3; i++) + for(j=0; j<3; j++) + scanf("%d",&b[i][j]); + for(i=0; i<3; i++) + for(j=0; j<3; j++) + c[i][j]=a[i][j]+b[i][j]; + printf("\nThe Addition of two matrix is\n"); + for(i=0; i<3; i++) + { + printf("\n"); + for(j=0; j<3; j++) + printf("%d\t",c[i][j]); + } +} \ No newline at end of file diff --git a/c/Functions/C Program for Armstrong number 1 to 1000..c b/c/Functions/C Program for Armstrong number 1 to 1000..c new file mode 100644 index 0000000..d5ff8ce --- /dev/null +++ b/c/Functions/C Program for Armstrong number 1 to 1000..c @@ -0,0 +1,43 @@ +/* Armstrong number 1 to 1000 - Write a function to check whether a given number is an armstrong number. Use this function to generate all armstrong numbers from 1 to 1000 */ + +#include +#include + +int check_armstrong(int n) ; + +void main() +{ + int n ; + clrscr() ; + printf("Armstrong numbers from 1 to 1000 are as shown: \n") ; + for(n=1 ; n<=1000 ; n++) + if(check_armstrong(n) == 1) + printf("%d ", n) ; + getch() ; +} + +int check_armstrong(int n) +{ + int sum=0, r, temp ; + temp=n ; + while(n!=0) + { + r=n%10 ; /* Extract the last digit */ + sum=sum+r*r*r ; /* Finding sum */ + n=n/10 ; /* Reduce number by 1 digit */ + } + if(sum==temp) + return 1 ; + else + return 0 ; +} + +/* +Output : + +Armstrong numbers from 1 to 1000 are as shown: +1 153 370 371 407 +*/ + + + diff --git a/c/Functions/C Program for Matrix multiplication in c..c b/c/Functions/C Program for Matrix multiplication in c..c new file mode 100644 index 0000000..cdb5306 --- /dev/null +++ b/c/Functions/C Program for Matrix multiplication in c..c @@ -0,0 +1,44 @@ +#include + +int main() +{ + int m, n, p, q, c, d, k, sum = 0; + int first[10][10], second[10][10], multiply[10][10]; + printf("Enter the number of rows and columns of first matrix\n"); + scanf("%d%d", &m, &n); + printf("Enter the elements of first matrix\n"); + for (c = 0; c < m; c++) + for (d = 0; d < n; d++) + scanf("%d", &first[c][d]); + printf("Enter the number of rows and columns of second matrix\n"); + scanf("%d%d", &p, &q); + if (n != p) + printf("Matrices with entered orders can't be multiplied with each other.\n"); + else + { + printf("Enter the elements of second matrix\n"); + for (c = 0; c < p; c++) + for (d = 0; d < q; d++) + scanf("%d", &second[c][d]); + for (c = 0; c < m; c++) + { + for (d = 0; d < q; d++) + { + for (k = 0; k < p; k++) + { + sum = sum + first[c][k]*second[k][d]; + } + multiply[c][d] = sum; + sum = 0; + } + } + printf("Product of entered matrices:-\n"); + for (c = 0; c < m; c++) + { + for (d = 0; d < q; d++) + printf("%d\t", multiply[c][d]); + printf("\n"); + } + } + return 0; +} \ No newline at end of file diff --git a/c/Functions/C Program for Sum of digits use recursive function to calculate sum of digits of an integer..c b/c/Functions/C Program for Sum of digits use recursive function to calculate sum of digits of an integer..c new file mode 100644 index 0000000..14f99de --- /dev/null +++ b/c/Functions/C Program for Sum of digits use recursive function to calculate sum of digits of an integer..c @@ -0,0 +1,29 @@ +/* Sum of digits use recursive function to calculate sum of digits of an integer*/ + +#include +#include + +int sum(int n) +{ + if(n==0) + return 0 ; + else + return( n%10 + sum(n/10) ) ; +} + +void main() +{ + int n ; + clrscr() ; + printf("Enter the number: ") ; + scanf("%d", &n) ; + printf("Sum of digits of %d is %d", n, sum(n) ) ; + getch() ; +} + +/* +Output: + +Enter the number: 246 +Sum of digits of 246 is 12 +*/ \ No newline at end of file diff --git a/c/Functions/C Program to Check whether character is upper case or lower case.c b/c/Functions/C Program to Check whether character is upper case or lower case.c new file mode 100644 index 0000000..1b6df49 --- /dev/null +++ b/c/Functions/C Program to Check whether character is upper case or lower case.c @@ -0,0 +1,16 @@ +#include +void check(char); +void main() +{ + char ch; + printf("enter any character"); + scanf("%c",&ch); + check(ch); +} +void check(char c) +{ + if(ch>=65&&ch<=90) + printf("char is upper case"); + else if(ch>=97&&ch<=122) + printf("character is lower case"); +} \ No newline at end of file diff --git a/c/Functions/C Program to Find largest of two numbers using functions.c b/c/Functions/C Program to Find largest of two numbers using functions.c new file mode 100644 index 0000000..90a62f4 --- /dev/null +++ b/c/Functions/C Program to Find largest of two numbers using functions.c @@ -0,0 +1,22 @@ +#include +void main() +{ + void max(); + max(); +} +void max() +{ + int a[5],max,n,i; + printf("How many no’s you want to enter: "); + scanf("%d",&n); + printf("Enter element for the array: "); + for(i=0; i +#include + +void addition(float a, float b); +void subtraction(float a, float b); +void multiplication(float a, float b); +void division(float a, float b); + +void main() +{ + char choice ; + float a,b ; + clrscr() ; + do + { + printf("\n Menu: \n") ; + printf("+ : Addition \n") ; + printf("- : Subtraction \n") ; + printf("* : Multiplication \n") ; + printf("/ : Division \n") ; + printf("Q : Quit \n") ; + printf("Enter your choice: ") ; + scanf(" %c", &choice) ; + if(choice=='+' || choice=='-' || choice=='*' || choice=='/') + { + printf("Enter 2 numbers: ") ; + scanf("%f %f", &a, &b); + } + switch(choice) + { + case '+' : + addition(a,b); + break; + case '-' : + subtraction(a,b); + break; + case '*' : + multiplication(a,b); + break; + case '/' : + division(a,b); + break; + case 'q' : + break; + case 'Q' : + break; + default : + printf("Invalid Choice. Enter again.\n"); + } + } + while(choice!='q' && choice!='Q'); + getch() ; +} + +void addition(float a, float b) +{ + printf("Sum of two numbers is: %f \n", a+b) ; +} + +void subtraction(float a, float b) +{ + printf("Diffrence of two numbers is: %f \n", a-b) ; +} + +void multiplication(float a, float b) +{ + printf("Product of two numbers is: %f \n", a*b) ; +} + +void division(float a, float b) +{ + printf("Result of division is: %f \n", a/b) ; +} + + +/* +Output: + + Menu: ++ : Addition +- : Subtraction +* : Multiplication +/ : Division +Q : Quit +Enter your choice: + +Enter 2 numbers: 2 5 +Sum of two numbers is: 7.000000 + + Menu: ++ : Addition +- : Subtraction +* : Multiplication +/ : Division +Q : Quit +Enter your choice: - +Enter 2 numbers: 2 5 +Diffrence of two numbers is: -3.000000 + + Menu: ++ : Addition +- : Subtraction +* : Multiplication +/ : Division +Q : Quit +Enter your choice: * +Enter 2 numbers: 2 5 +Product of two numbers is: 10.000000 + + Menu: ++ : Addition +- : Subtraction +* : Multiplication +/ : Division +Q : Quit +Enter your choice: / +Enter 2 numbers: 2 5 +Result of division is: 0.400000 + + Menu: ++ : Addition +- : Subtraction +* : Multiplication +/ : Division +Q : Quit +Enter your choice: % +Invalid Choice. Enter again. + + Menu: ++ : Addition +- : Subtraction +* : Multiplication +/ : Division +Q : Quit +Enter your choice: Q +*/ \ No newline at end of file diff --git a/c/Functions/C Program to Write a function to check whether a given integer is a square number or not..c b/c/Functions/C Program to Write a function to check whether a given integer is a square number or not..c new file mode 100644 index 0000000..e6d814e --- /dev/null +++ b/c/Functions/C Program to Write a function to check whether a given integer is a square number or not..c @@ -0,0 +1,46 @@ +/* Square number - Write a function to check whether a given integer is a square number or not. Eg. 4 , 9 , 16 , 25 etc */ + +#include +#include +#include + +int checksquare(int n) ; + +void main() +{ + int n, flag ; + clrscr(); + printf("Enter an integer: ") ; + scanf("%d", &n) ; + flag=checksquare(n) ; + if(flag==1) + printf("%d is a square number", n) ; + else + printf("%d is not a square number", n) ; + getch(); +} + +int checksquare(int n) +{ + double m; + int a; + m=sqrt(n); + a=m; + if(n==a*a) + return 1; + else + return 0; +} + +/* +Output1: + +Enter an integer: 16 +16 is a square number + +Output2: + +Enter an integer: 8 +8 is not a square number +*/ + diff --git a/c/Functions/C Program to Write a function to check whether a given number is a palindrome or not..c b/c/Functions/C Program to Write a function to check whether a given number is a palindrome or not..c new file mode 100644 index 0000000..dc6523d --- /dev/null +++ b/c/Functions/C Program to Write a function to check whether a given number is a palindrome or not..c @@ -0,0 +1,47 @@ +/* Palindrome Number - Write a function to check whether a given number is a palindrome or not , for example 1234321 */ + +#include +#include + +int palindrome(int n) +{ + int r, rev=0, temp ; + temp=n ; + while(n!=0) + { + r=n%10 ; + rev=rev*10+r ; + n=n/10 ; + } + if(rev==temp) + return 1 ; + else + return 0 ; +} + +void main() +{ + int n, flag ; + clrscr() ; + printf("Enter a number: ") ; + scanf("%d", &n) ; + flag=palindrome(n) ; + if(flag==1) + printf("%d is a palindrome", n) ; + else + printf("%d is not a palindrome", n) ; + getch() ; +} + +/* +Output1: + +Enter a number: 24542 +24542 is a palindrome + +Output2: + +Enter a number: 2464 +2464 is not a palindrome +*/ + diff --git a/c/Functions/C Program to Write a function to find factorial of a number...c b/c/Functions/C Program to Write a function to find factorial of a number...c new file mode 100644 index 0000000..9da05d5 --- /dev/null +++ b/c/Functions/C Program to Write a function to find factorial of a number...c @@ -0,0 +1,38 @@ +/* Binomial Coefficient - Write a function to find factorial of a number. Using this function, find value of binomial co-efficient (B) where B = n! / r! * (n-r)! where n and r are natural numbers. */ + +#include +#include + +long fact(int n) ; + +void main() +{ + int n, r ; + long f1, f2, f3, b ; + clrscr() ; + printf("Enter natural numbers n and r (n>r): ") ; + scanf("%d %d", &n, &r) ; + f1=fact(n) ; + f2=fact(r) ; + f3=fact(n-r) ; + b=f1/(f2*f3) ; + printf("Binomial Coefficient = %ld", b) ; + getch() ; +} + +long fact(int n) +{ + int i; + long f=1 ; + for(i=1 ; i<=n ; i++) + f=f*i ; + return f ; +} + + +/* +Output: + +Enter natural numbers n and r (n>r): 9 5 +Binomial Coefficient = 126 +*/ \ No newline at end of file diff --git a/c/Functions/C Program to Write a non-recursive function to find m^n where m is a real number and n is an integer..c b/c/Functions/C Program to Write a non-recursive function to find m^n where m is a real number and n is an integer..c new file mode 100644 index 0000000..ebebf83 --- /dev/null +++ b/c/Functions/C Program to Write a non-recursive function to find m^n where m is a real number and n is an integer..c @@ -0,0 +1,40 @@ +/* power(m,n) - Write a non-recursive function to find m^n where m is a real number and n is an integer */ + +#include +#include +#include + +float power(float m, int n) +{ + int i ; + float result=1 ; + for(i=1 ; i<=abs(n) ; i++) + result=result*m; + if(n<0) + return (1/result) ; + else + return result; +} + +void main() +{ + int n ; + float m ; + clrscr() ; + printf("Enter m and n: "); + scanf("%f %d", &m, &n); + printf("m raise to n is %f", power(m,n) ); + getch(); +} + +/* +Output1: + +Enter m and n: 2.5 3 +m raise to n is 15.625000 + +Output2: + +Enter m and n: 2 -3 +m raise to n is 0.125000 +*/ diff --git a/c/Functions/C Program to Write a program using recursive function 'power' to compute x^n..c b/c/Functions/C Program to Write a program using recursive function 'power' to compute x^n..c new file mode 100644 index 0000000..924091e --- /dev/null +++ b/c/Functions/C Program to Write a program using recursive function 'power' to compute x^n..c @@ -0,0 +1,37 @@ +/* +Write a program using recursive function 'power' to compute x^n +power(x,n) = 1 , if n = 0 +power(x,n) = x , if n = 1 +power(x,n) = x * power(x,n-1) , otherwise +*/ + +#include +#include + +float power(float x, int n) +{ + if(n==0) + return 1 ; + else if(n==1) + return x ; + else + return ( x * power(x, n-1) ) ; +} + +void main() +{ + float x ; + int n ; + clrscr() ; + printf("Enter x and n: ") ; + scanf("%f %d", &x, &n) ; + printf("x raise to n = %f", power(x,n) ) ; + getch() ; +} + +/* +Output: + +Enter x and n: 2.5 3 +x raise to n = 15.625000 +*/ diff --git a/c/Functions/C Program to Write a recursive function to calculate 1+2+3+...+n..c b/c/Functions/C Program to Write a recursive function to calculate 1+2+3+...+n..c new file mode 100644 index 0000000..0a811d8 --- /dev/null +++ b/c/Functions/C Program to Write a recursive function to calculate 1+2+3+...+n..c @@ -0,0 +1,29 @@ +/* Sum of natural numbers - Write a recursive function to calculate 1+2+3+...+n */ + +#include +#include + +long sum(int n) +{ + if(n==1) + return 1 ; + else + return ( n + sum(n-1) ) ; +} + +void main() +{ + int n ; + clrscr() ; + printf("Enter n: ") ; + scanf("%d", &n) ; + printf("Sum of first %d natural numbers is %ld", n, sum(n) ) ; + getch() ; +} + +/* +Output: + +Enter n: 3 +Sum of first 3 natural numbers is 6 +*/ diff --git a/c/Functions/C Program to Write a recursive function to find factorial of a given number n..c b/c/Functions/C Program to Write a recursive function to find factorial of a given number n..c new file mode 100644 index 0000000..2212f4c --- /dev/null +++ b/c/Functions/C Program to Write a recursive function to find factorial of a given number n..c @@ -0,0 +1,30 @@ +/* Factorial - Write a recursive function to find factorial of a given number n */ + +#include +#include + +long fact(int n) +{ + if(n==0) + return 1 ; + else + return ( n * fact(n-1) ) ; +} + +void main() +{ + int n ; + clrscr() ; + printf("Enter n:") ; + scanf("%d", &n) ; + printf("Factorial of %d is %ld", n, fact(n) ) ; + getch() ; +} + +/* +Output: + +Enter n:4 +Factorial of 4 is 24 +*/ + diff --git a/c/Functions/C Program to Write a recursive function to find the nth term of fibonacci series...c b/c/Functions/C Program to Write a recursive function to find the nth term of fibonacci series...c new file mode 100644 index 0000000..c8473e0 --- /dev/null +++ b/c/Functions/C Program to Write a recursive function to find the nth term of fibonacci series...c @@ -0,0 +1,49 @@ +/* Fibonacci - Write a recursive function to find the nth term of fibonacci series. Using this function print the first n terms of fibonacci series */ + +/* We assume that fibonacci series starts with 1 1 */ + +#include +#include + +long fibo(int n) +{ + if( (n==1) || (n==2) ) + return 1 ; + else + return( fibo(n-1) + fibo(n-2) ) ; +} + +void main() +{ + int i, n ; + clrscr() ; + printf("Enter n:") ; + scanf("%d", &n) ; + printf("First %d terms of fibonacci series are: \n", n) ; + for(i=1 ; i<=n ; i++) + printf("%ld ", fibo(i) ) ; + /* Dont write fibo(n) by mistake */ + getch() ; +} + +/* If fibonacci series starts with 0 1 then the following function should be given + +long fibo (int n) +{ + if(n==1) + return 0; + else if (n==2) + return 1; + else + return (fibo(n-1) + fibo(n-2)); +} + */ + +/* +Output: + +Enter n:4 +First 4 terms of fibonacci series are: +1 1 2 3 +*/ + diff --git a/c/Functions/C Program to Write recursive function to calculate gcd of 2 numbers using the following Euclid's recursive algorithm..c b/c/Functions/C Program to Write recursive function to calculate gcd of 2 numbers using the following Euclid's recursive algorithm..c new file mode 100644 index 0000000..6c1632f --- /dev/null +++ b/c/Functions/C Program to Write recursive function to calculate gcd of 2 numbers using the following Euclid's recursive algorithm..c @@ -0,0 +1,41 @@ +/* GCD Recursive - Write recursive function to calculate gcd of 2 numbers using the following Euclid's recursive algorithm: + + gcd(n,m) , if n>m +gcd(m,n) = m , if n=0 + gcd(n,m mod n) , otherwise +*/ + +#include +#include + +int gcd(int m, int n) +{ + if(n>m) + return ( gcd(n,m) ) ; + else if(n==0) + return m ; + else + return ( gcd(n,m%n) ) ; +} + +void main() +{ + int m, n ; + clrscr(); + printf("Enter 2 positive integers: ") ; + scanf("%d %d", &m, &n) ; + printf("GCD is: %d", gcd(m,n) ); + getch() ; +} + +/* +Output1: + +Enter 2 positive integers: 18 24 +GCD is: 6 + +Output2: + +Enter 2 positive integers: 5 3 +GCD is: 1 +*/ diff --git a/c/Functions/C Program to use recursive function to find value of m^n where m is a real number and n is an integer greater than or equal to zero..c b/c/Functions/C Program to use recursive function to find value of m^n where m is a real number and n is an integer greater than or equal to zero..c new file mode 100644 index 0000000..5dd9613 --- /dev/null +++ b/c/Functions/C Program to use recursive function to find value of m^n where m is a real number and n is an integer greater than or equal to zero..c @@ -0,0 +1,30 @@ +/* power(m,n) - Use recursive function to find value of m^n where m is a real number and n is an integer greater than or equal to zero */ + +#include +#include + +float power(float m, int n) +{ + if(n==0) + return 1 ; + else + return (m * power(m,n-1) ) ; +} + +void main() +{ + float m ; + int n ; + clrscr() ; + printf("Enter m and n: ") ; + scanf("%f %d", &m, &n) ; + printf("m raise to n = %f", power(m,n) ) ; + getch() ; +} + +/* +Output: + +Enter m and n: 2.5 3 +m raise to n = 15.625000 +*/ diff --git a/c/Functions/C Program - Using recursion write a program to find octal , binary and hexadecimal equivalent of the natural (decimal) number entered by the user..c b/c/Functions/C Program - Using recursion write a program to find octal , binary and hexadecimal equivalent of the natural (decimal) number entered by the user..c new file mode 100644 index 0000000..18c1e88 --- /dev/null +++ b/c/Functions/C Program - Using recursion write a program to find octal , binary and hexadecimal equivalent of the natural (decimal) number entered by the user..c @@ -0,0 +1,60 @@ +/* Decimal to Octal , Hexa , Binary - Using recursion write a program to find octal , binary and hexadecimal equivalent of the natural (decimal) number entered by the user */ + +#include +#include + +void octal(int n) +{ + if(n!=0) + { + octal(n/8) ; + printf("%d", n%8) ; + } +} + +void binary(int n) +{ + if(n!=0) + { + binary(n/2) ; + printf("%d", n%2) ; + } +} + +void hexa(int n) +{ + if(n!=0) + { + hexa(n/16) ; + if(n%16 < 10) + printf("%d", n%16) ; + else + printf("%c", n%16 + 55) ; + } +} + +void main() +{ + int n ; + clrscr() ; + printf("Enter a natural number: ") ; + scanf("%d", &n) ; + printf("Equivalent octal, binary and hexadecimal numbers are as shown: \n") ; + octal(n) ; + printf("\n") ; + binary(n) ; + printf("\n") ; + hexa(n) ; + printf("\n") ; + getch() ; +} + +/* +Output: + +Enter a natural number: 43 +Equivalent octal, binary and hexadecimal numbers are as shown: +53 +101011 +2B +*/ diff --git a/c/Functions/C Program to Calculate the Area of a Circle.c b/c/Functions/C Program to Calculate the Area of a Circle.c new file mode 100644 index 0000000..11123da --- /dev/null +++ b/c/Functions/C Program to Calculate the Area of a Circle.c @@ -0,0 +1,15 @@ +/* + * C program to find the area of a circle, given the radius + */ +#include +#include +#define PI 3.142 + +void main() +{ + float radius, area; + printf("Enter the radius of a circle \n"); + scanf("%f", &radius); + area = PI * pow(radius, 2); + printf("Area of a circle = %5.2f\n", area); +} \ No newline at end of file diff --git a/c/Functions/C Program to Calculate the Area of a Triangle.c b/c/Functions/C Program to Calculate the Area of a Triangle.c new file mode 100644 index 0000000..77fcfe7 --- /dev/null +++ b/c/Functions/C Program to Calculate the Area of a Triangle.c @@ -0,0 +1,16 @@ +/* + * C program to find the area of a triangle, given three sides + */ +#include +#include + +void main() +{ + int s, a, b, c, area; + printf("Enter the values of a, b and c \n"); + scanf("%d %d %d", &a, &b, &c); + /* compute s */ + s = (a + b + c) / 2; + area = sqrt(s * (s - a) * (s - b) * (s - c)); + printf("Area of a triangle = %d \n", area); +} \ No newline at end of file diff --git a/c/Functions/C Program to Calculate the Mean, Variance & Standard Deviation.c b/c/Functions/C Program to Calculate the Mean, Variance & Standard Deviation.c new file mode 100644 index 0000000..893db4b --- /dev/null +++ b/c/Functions/C Program to Calculate the Mean, Variance & Standard Deviation.c @@ -0,0 +1,37 @@ +/* + * C program to input real numbers and find the mean, variance + * and standard deviation + */ +#include +#include +#define MAXSIZE 10 + +void main() +{ + float x[MAXSIZE]; + int i, n; + float average, variance, std_deviation, sum = 0, sum1 = 0; + printf("Enter the value of N \n"); + scanf("%d", &n); + printf("Enter %d real numbers \n", n); + for (i = 0; i < n; i++) + { + scanf("%f", &x[i]); + } + /* Compute the sum of all elements */ + for (i = 0; i < n; i++) + { + sum = sum + x[i]; + } + average = sum / (float)n; + /* Compute variance and standard deviation */ + for (i = 0; i < n; i++) + { + sum1 = sum1 + pow((x[i] - average), 2); + } + variance = sum1 / (float)n; + std_deviation = sqrt(variance); + printf("Average of all elements = %.2f\n", average); + printf("variance of all elements = %.2f\n", variance); + printf("Standard deviation = %.2f\n", std_deviation); +} \ No newline at end of file diff --git a/c/Functions/C Program to Calculate the Simple Interest.c b/c/Functions/C Program to Calculate the Simple Interest.c new file mode 100644 index 0000000..c3249c3 --- /dev/null +++ b/c/Functions/C Program to Calculate the Simple Interest.c @@ -0,0 +1,18 @@ +/* + * C program to find the simple interest, given principal, + * rate of interest and time. + */ +#include + +void main() +{ + float principal_amt, rate, simple_interest; + int time; + printf("Enter the values of principal_amt, rate and time \n"); + scanf("%f %f %d", &principal_amt, &rate, &time); + simple_interest = (principal_amt * rate * time) / 100.0; + printf("Amount = Rs. %5.2f\n", principal_amt); + printf("Rate = Rs. %5.2f%\n", rate); + printf("Time = %d years\n", time); + printf("Simple interest = %5.2f\n", simple_interest); +} \ No newline at end of file diff --git a/c/Functions/C Program to Calculate the Sum of cos(x) Series.c b/c/Functions/C Program to Calculate the Sum of cos(x) Series.c new file mode 100644 index 0000000..48ab2b2 --- /dev/null +++ b/c/Functions/C Program to Calculate the Sum of cos(x) Series.c @@ -0,0 +1,33 @@ +/* + * C program to find the sum of cos(x) series + */ +#include +#include + +void main() +{ + int n, x1, i, j; + float x, sign, cosx, fact; + printf("Enter the number of the terms in a series\n"); + scanf("%d", &n); + printf("Enter the value of x(in degrees)\n"); + scanf("%f", &x); + x1 = x; + /* Degrees to radians */ + x = x * (3.142 / 180.0); + cosx = 1; + sign = -1; + for (i = 2; i <= n; i = i + 2) + { + fact = 1; + for (j = 1; j <= i; j++) + { + fact = fact * j; + } + cosx = cosx + (pow(x, i) / fact) * sign; + sign = sign * (-1); + } + printf("Sum of the cosine series = %7.2f\n", cosx); + printf("The value of cos(%d) using library function = %f\n", x1, + cos(x)); +} \ No newline at end of file diff --git a/c/Functions/C Program to Calculate the Value of cos(x).c b/c/Functions/C Program to Calculate the Value of cos(x).c new file mode 100644 index 0000000..6463960 --- /dev/null +++ b/c/Functions/C Program to Calculate the Value of cos(x).c @@ -0,0 +1,35 @@ +/* + * C program to find the value of cos(x) using the series + * up to the given accuracy (without using user defined function) + * also print cos(x) using library function. + */ +#include +#include +#include + +void main() +{ + int n, x1; + float accuracy, term, denominator, x, cosx, cosval; + printf("Enter the value of x (in degrees) \n"); + scanf("%f", &x); + x1 = x; + /* Converting degrees to radians */ + x = x * (3.142 / 180.0); + cosval = cos(x); + printf("Enter the accuracy for the result \n"); + scanf("%f", &accuracy); + term = 1; + cosx = term; + n = 1; + do + { + denominator = 2 * n * (2 * n - 1); + term = -term * x * x / denominator; + cosx = cosx + term; + n = n + 1; + } + while (accuracy <= fabs(cosval - cosx)); + printf("Sum of the cosine series = %f\n", cosx); + printf("Using Library function cos(%d) = %f\n", x1, cos(x)); +} \ No newline at end of file diff --git a/c/Functions/C Program to Calculate the Value of sin(x).c b/c/Functions/C Program to Calculate the Value of sin(x).c new file mode 100644 index 0000000..c683610 --- /dev/null +++ b/c/Functions/C Program to Calculate the Value of sin(x).c @@ -0,0 +1,35 @@ +/* + * C program to find the value of sin(x) using the series + * up to the given accuracy (without using user defined function) + * also print sin(x) using library function. + */ +#include +#include +#include + +void main() +{ + int n, x1; + float accuracy, term, denominator, x, sinx, sinval; + printf("Enter the value of x (in degrees) \n"); + scanf("%f", &x); + x1 = x; + /* Converting degrees to radians */ + x = x * (3.142 / 180.0); + sinval = sin(x); + printf("Enter the accuracy for the result \n"); + scanf("%f", &accuracy); + term = x; + sinx = term; + n = 1; + do + { + denominator = 2 * n * (2 * n + 1); + term = -term * x * x / denominator; + sinx = sinx + term; + n = n + 1; + } + while (accuracy <= fabs(sinval - sinx)); + printf("Sum of the sine series = %f \n", sinx); + printf("Using Library function sin(%d) = %f\n", x1, sin(x)); +} \ No newline at end of file diff --git a/c/Functions/C Program to Check if a given Number is Prime number.c b/c/Functions/C Program to Check if a given Number is Prime number.c new file mode 100644 index 0000000..a58ff0f --- /dev/null +++ b/c/Functions/C Program to Check if a given Number is Prime number.c @@ -0,0 +1,31 @@ +/* + * C program to check whether a given number is prime or not + * and output the given number with suitable message. + */ +#include +#include + +void main() +{ + int num, j, flag; + printf("Enter a number \n"); + scanf("%d", &num); + if (num <= 1) + { + printf("%d is not a prime numbers \n", num); + exit(1); + } + flag = 0; + for (j = 2; j <= num / 2; j++) + { + if ((num % j) == 0) + { + flag = 1; + break; + } + } + if (flag == 0) + printf("%d is a prime number \n", num); + else + printf("%d is not a prime number \n", num); +} \ No newline at end of file diff --git a/c/Functions/C Program to Compute the Surface Area & Volume of a Cube.c b/c/Functions/C Program to Compute the Surface Area & Volume of a Cube.c new file mode 100644 index 0000000..9f55114 --- /dev/null +++ b/c/Functions/C Program to Compute the Surface Area & Volume of a Cube.c @@ -0,0 +1,16 @@ +/* + * C program to compute the surface area and volume of a cube + */ +#include +#include + +void main() +{ + float side, surfacearea, volume; + printf("Enter the length of a side \n"); + scanf("%f", &side); + surfacearea = 6.0 * side * side; + volume = pow(side, 3); + printf("Surface area = %6.2f and Volume = %6.2f \n", surfacearea, + volume); +} \ No newline at end of file diff --git a/c/Functions/C Program to Compute the Value of X ^ N.c b/c/Functions/C Program to Compute the Value of X ^ N.c new file mode 100644 index 0000000..d37d5d3 --- /dev/null +++ b/c/Functions/C Program to Compute the Value of X ^ N.c @@ -0,0 +1,28 @@ +/* + * C program to compute the value of X ^ N given X and N as inputs + */ +#include +#include + +long int power(int x, int n); + +void main() +{ + long int x, n, xpown; + printf("Enter the values of X and N \n"); + scanf("%ld %ld", &x, &n); + xpown = power(x, n); + printf("X to the power N = %ld\n", xpown); +} +/* Recursive function to computer the X to power N */ +long int power(int x, int n) +{ + if (n == 1) + return(x); + else if (n % 2 == 0) + /* if n is even */ + return (pow(power(x, n/2), 2)); + else + /* if n is odd */ + return (x * power(x, n - 1)); +} \ No newline at end of file diff --git a/c/Functions/C Program to Display Floyd’s triangle.c b/c/Functions/C Program to Display Floyd’s triangle.c new file mode 100644 index 0000000..e7d13bc --- /dev/null +++ b/c/Functions/C Program to Display Floyd’s triangle.c @@ -0,0 +1,17 @@ +/* + * C Program to Display Floyd’s triangle + */ +#include + +main( ) +{ + int i, j, k = 1; + printf("floyds triangle is\n"); + for( i = 1; k <= 20; ++i ) + { + for( j = 1; j <= i; ++j ) + printf( "%d ", k++ ); + printf( "\n\n" ); + } + return 0; +} \ No newline at end of file diff --git a/c/Functions/C Program to Display Pascal triangle.c b/c/Functions/C Program to Display Pascal triangle.c new file mode 100644 index 0000000..0384cba --- /dev/null +++ b/c/Functions/C Program to Display Pascal triangle.c @@ -0,0 +1,29 @@ +/* + * C Program to Display Pascal triangle + */ +#include + +void main() +{ + int array[15][15], i, j, rows, num = 25, k; + printf("\n enter the number of rows:"); + scanf("%d", &rows); + for (i = 0; i < rows; i++) + { + for (k = num - 2 * i; k >= 0; k--) + printf(" "); + for (j = 0; j <= i; j++) + { + if (j == 0 || i == j) + { + array[i][j] = 1; + } + else + { + array[i][j] = array[i - 1][j - 1] + array[i - 1][j]; + } + printf("%4d", array[i][j]); + } + printf("\n"); + } +} \ No newline at end of file diff --git a/c/Functions/C Program to Evaluate the given Polynomial Equation.c b/c/Functions/C Program to Evaluate the given Polynomial Equation.c new file mode 100644 index 0000000..bd73c38 --- /dev/null +++ b/c/Functions/C Program to Evaluate the given Polynomial Equation.c @@ -0,0 +1,52 @@ +/* + * C program to evaluate a given polynomial by reading its coefficients + * in an array. + * P(x) = AnXn + An-1Xn-1 + An-2Xn-2+... +A1X + A0 + * + * The polynomial can be written as: + * P(x) = A0 + X(A1 + X(A2 + X(A3 + X(Q4 + X(...X(An-1 + XAn)))) + * and evaluated starting from the inner loop + */ +#include +#include +#define MAXSIZE 10 + +void main() +{ + int array[MAXSIZE]; + int i, num, power; + float x, polySum; + printf("Enter the order of the polynomial \n"); + scanf("%d", &num); + printf("Enter the value of x \n"); + scanf("%f", &x); + /* Read the coefficients into an array */ + printf("Enter %d coefficients \n", num + 1); + for (i = 0; i <= num; i++) + { + scanf("%d", &array[i]); + } + polySum = array[0]; + for (i = 1; i <= num; i++) + { + polySum = polySum * x + array[i]; + } + power = num; + printf("Given polynomial is: \n"); + for (i = 0; i <= num; i++) + { + if (power < 0) + { + break; + } + /* printing proper polynomial function */ + if (array[i] > 0) + printf(" + "); + else if (array[i] < 0) + printf(" - "); + else + printf(" "); + printf("%dx^%d ", abs(array[i]), power--); + } + printf("\n Sum of the polynomial = %6.2f \n", polySum); +} \ No newline at end of file diff --git a/c/Functions/C Program to Find & Display Multiplication table.c b/c/Functions/C Program to Find & Display Multiplication table.c new file mode 100644 index 0000000..c01ad4c --- /dev/null +++ b/c/Functions/C Program to Find & Display Multiplication table.c @@ -0,0 +1,19 @@ +/* + * C Program to Find & Display Multiplication table + */ +#include + +int main() +{ + int number, i = 1; + printf(" Enter the Number:"); + scanf("%d", &number); + printf("Multiplication table of %d:\n ", number); + printf("--------------------------\n"); + while (i <= 10) + { + printf(" %d x %d = %d \n ", number, i, number * i); + i++; + } + return 0; +} \ No newline at end of file diff --git a/c/Functions/C Program to Find Area of Parallelogram.c b/c/Functions/C Program to Find Area of Parallelogram.c new file mode 100644 index 0000000..8c232ff --- /dev/null +++ b/c/Functions/C Program to Find Area of Parallelogram.c @@ -0,0 +1,15 @@ +/* + * C Program to Find Area of Parallelogram + */ +#include + +int main() +{ + float base, altitude; + float area; + printf("Enter base and altitude of the given Parallelogram: \n "); + scanf("%f%f", &base, &altitude); + area = base * altitude; + printf("Area of Parallelogram is: %.3f\n", area); + return 0; +} \ No newline at end of file diff --git a/c/Functions/C Program to Find Area of Rhombus.c b/c/Functions/C Program to Find Area of Rhombus.c new file mode 100644 index 0000000..fe2b0f8 --- /dev/null +++ b/c/Functions/C Program to Find Area of Rhombus.c @@ -0,0 +1,15 @@ +/* + * C Program to Find Area of rhombus + */ +#include + +int main() +{ + float diagonal1, diagonal2; + float area; + printf("Enter diagonals of the given rhombus: \n "); + scanf("%f%f", &diagonal1, &diagonal2); + area = 0.5 * diagonal1 * diagonal2; + printf("Area of rhombus is: %.3f \n", area); + return 0; +} \ No newline at end of file diff --git a/c/Functions/C Program to Find Area of Trapezium.c b/c/Functions/C Program to Find Area of Trapezium.c new file mode 100644 index 0000000..7063cd7 --- /dev/null +++ b/c/Functions/C Program to Find Area of Trapezium.c @@ -0,0 +1,15 @@ +/* + * C Program to Find Area of Trapezium + */ +#include + +int main() +{ + float a, b, h; + float area; + printf("Enter the value for two bases & height of the trapezium: \n"); + scanf("%f%f%f", &a, &b, &h); + area = 0.5 * (a + b) * h ; + printf("Area of the trapezium is: %.3f", area); + return 0; +} \ No newline at end of file diff --git a/c/Functions/C Program to Find Area of a Right Angled Triangle.c b/c/Functions/C Program to Find Area of a Right Angled Triangle.c new file mode 100644 index 0000000..4477ecf --- /dev/null +++ b/c/Functions/C Program to Find Area of a Right Angled Triangle.c @@ -0,0 +1,15 @@ +/* + * C Program to Find Area of a Right Angled Triangle + */ +#include + +int main() +{ + float height, width; + float area; + printf("Enter height and width of the given triangle:\n "); + scanf("%f%f", &height, &width); + area = 0.5 * height * width; + printf("Area of right angled triangle is: %.3f\n", area); + return 0; +} \ No newline at end of file diff --git a/c/Functions/C Program to Find First N Fibonacci Numbers.c b/c/Functions/C Program to Find First N Fibonacci Numbers.c new file mode 100644 index 0000000..bc9f63c --- /dev/null +++ b/c/Functions/C Program to Find First N Fibonacci Numbers.c @@ -0,0 +1,24 @@ +/* + * C program to generate and print first N FIBONACCI numbers + * in the series. + */ +#include + +void main() +{ + int fib1 = 0, fib2 = 1, fib3, num, count = 0; + printf("Enter the value of num \n"); + scanf("%d", &num); + printf("First %d FIBONACCI numbers are ...\n", num); + printf("%d\n", fib1); + printf("%d\n", fib2); + count = 2; /* fib1 and fib2 are already used */ + while (count < num) + { + fib3 = fib1 + fib2; + count++; + printf("%d\n", fib3); + fib1 = fib2; + fib2 = fib3; + } +} \ No newline at end of file diff --git a/c/Functions/C Program to Find GCD of given Numbers using Recursion.c b/c/Functions/C Program to Find GCD of given Numbers using Recursion.c new file mode 100644 index 0000000..5e2e917 --- /dev/null +++ b/c/Functions/C Program to Find GCD of given Numbers using Recursion.c @@ -0,0 +1,32 @@ +/* + * C Program to find GCD of given Numbers using Recursion + */ +#include + +int gcd(int, int); + +int main() +{ + int a, b, result; + printf("Enter the two numbers to find their GCD: "); + scanf("%d%d", &a, &b); + result = gcd(a, b); + printf("The GCD of %d and %d is %d.\n", a, b, result); +} + +int gcd(int a, int b) +{ + while (a != b) + { + if (a > b) + { + return gcd(a - b, b); + } + else + { + return gcd(a, b - a); + } + } + return a; +} +} \ No newline at end of file diff --git a/c/Functions/C Program to Find LCM of a Number using Recursion.c b/c/Functions/C Program to Find LCM of a Number using Recursion.c new file mode 100644 index 0000000..5b70ce7 --- /dev/null +++ b/c/Functions/C Program to Find LCM of a Number using Recursion.c @@ -0,0 +1,29 @@ +/* + * C Program to Find LCM of a Number using Recursion + */ +#include + +int lcm(int, int); + +int main() +{ + int a, b, result; + int prime[100]; + printf("Enter two numbers: "); + scanf("%d%d", &a, &b); + result = lcm(a, b); + printf("The LCM of %d and %d is %d\n", a, b, result); + return 0; +} + +int lcm(int a, int b) +{ + static int common = 1; + if (common % a == 0 && common % b == 0) + { + return common; + } + common++; + lcm(a, b); + return common; +} \ No newline at end of file diff --git a/c/Functions/C Program to Find Prime Numbers in a given Range.c b/c/Functions/C Program to Find Prime Numbers in a given Range.c new file mode 100644 index 0000000..dd983a6 --- /dev/null +++ b/c/Functions/C Program to Find Prime Numbers in a given Range.c @@ -0,0 +1,42 @@ +/* + * C program to find prime numbers in a given range. + * Also print the number of prime numbers. + */ +#include +#include + +void main() +{ + int num1, num2, i, j, flag, temp, count = 0; + printf("Enter the value of num1 and num2 \n"); + scanf("%d %d", &num1, &num2); + if (num2 < 2) + { + printf("There are no primes upto %d\n", num2); + exit(0); + } + printf("Prime numbers are \n"); + temp = num1; + if ( num1 % 2 == 0) + { + num1++; + } + for (i = num1; i <= num2; i = i + 2) + { + flag = 0; + for (j = 2; j <= i / 2; j++) + { + if ((i % j) == 0) + { + flag = 1; + break; + } + } + if (flag == 0) + { + printf("%d\n", i); + count++; + } + } + printf("Number of primes between %d & %d = %d\n", temp, num2, count); +} \ No newline at end of file diff --git a/c/Functions/C Program to Find Sum of the Series 1by1! + 2by2! + 3by3! + ……1byN!.c b/c/Functions/C Program to Find Sum of the Series 1by1! + 2by2! + 3by3! + ……1byN!.c new file mode 100644 index 0000000..82bac33 --- /dev/null +++ b/c/Functions/C Program to Find Sum of the Series 1by1! + 2by2! + 3by3! + ……1byN!.c @@ -0,0 +1,26 @@ +/* + * C Program to Find find Sum of the Series 1/1! + 2/2! + 3/3! + ……1/N! + */ +#include + +double sumseries(double); + +main() +{ + double number,sum; + printf("\n Enter the value: "); + scanf("%lf", &number); + sum = sumseries(number); + printf("\n Sum of the above series = %lf ", sum); +} + +double sumseries(double m) +{ + double sum2 = 0, f = 1, i; + for (i = 1; i <= m; i++) + { + f = f * i; + sum2 = sum2 +(i / f); + } + return(sum2); +} \ No newline at end of file diff --git a/c/Functions/C Program to Find Volume and Surface Area of Sphere.c b/c/Functions/C Program to Find Volume and Surface Area of Sphere.c new file mode 100644 index 0000000..caf5f81 --- /dev/null +++ b/c/Functions/C Program to Find Volume and Surface Area of Sphere.c @@ -0,0 +1,18 @@ +/* + * C Program to Find Volume and Surface Area of Sphere + */ +#include +#include + +int main() +{ + float radius; + float surface_area, volume; + printf("Enter radius of the sphere : \n"); + scanf("%f", &radius); + surface_area = 4 * (22/7) * radius * radius; + volume = (4.0/3) * (22/7) * radius * radius * radius; + printf("Surface area of sphere is: %.3f", surface_area); + printf("\n Volume of sphere is : %.3f", volume); + return 0; +} \ No newline at end of file diff --git a/c/Functions/C Program to Find out the Roots of a Quadratic Equation.c b/c/Functions/C Program to Find out the Roots of a Quadratic Equation.c new file mode 100644 index 0000000..df75b5c --- /dev/null +++ b/c/Functions/C Program to Find out the Roots of a Quadratic Equation.c @@ -0,0 +1,50 @@ +/* + * C program to find out the roots of a quadratic equation + * for non-zero coefficients. In case of errors the program + * should report suitable error message. + */ +#include +#include +#include + +void main() +{ + float a, b, c, root1, root2; + float realp, imagp, disc; + printf("Enter the values of a, b and c \n"); + scanf("%f %f %f", &a, &b, &c); + /* If a = 0, it is not a quadratic equation */ + if (a == 0 || b == 0 || c == 0) + { + printf("Error: Roots cannot be determined \n"); + exit(1); + } + else + { + disc = b * b - 4.0 * a * c; + if (disc < 0) + { + printf("Imaginary Roots\n"); + realp = -b / (2.0 * a) ; + imagp = sqrt(abs(disc)) / (2.0 * a); + printf("Root1 = %f +i %f\n", realp, imagp); + printf("Root2 = %f -i %f\n", realp, imagp); + } + else if (disc == 0) + { + printf("Roots are real and equal\n"); + root1 = -b / (2.0 * a); + root2 = root1; + printf("Root1 = %f\n", root1); + printf("Root2 = %f\n", root2); + } + else if (disc > 0 ) + { + printf("Roots are real and distinct \n"); + root1 =(-b + sqrt(disc)) / (2.0 * a); + root2 =(-b - sqrt(disc)) / (2.0 * a); + printf("Root1 = %f \n", root1); + printf("Root2 = %f \n", root2); + } + } +} \ No newline at end of file diff --git a/c/Functions/C Program to Find the Areas of Different Geometrical Figures.c b/c/Functions/C Program to Find the Areas of Different Geometrical Figures.c new file mode 100644 index 0000000..25c3650 --- /dev/null +++ b/c/Functions/C Program to Find the Areas of Different Geometrical Figures.c @@ -0,0 +1,49 @@ +/* + * C program to find the areas of different geometrical shapes such as + * circle, square, rectangle etc using switch statements. + */ +#include + +void main() +{ + int fig_code; + float side, base, length, breadth, height, area, radius; + printf("-------------------------\n"); + printf(" 1 --> Circle\n"); + printf(" 2 --> Rectangle\n"); + printf(" 3 --> Triangle\n"); + printf(" 4 --> Square\n"); + printf("-------------------------\n"); + printf("Enter the Figure code\n"); + scanf("%d", &fig_code); + switch(fig_code) + { + case 1: + printf("Enter the radius\n"); + scanf("%f", &radius); + area = 3.142 * radius * radius; + printf("Area of a circle = %f\n", area); + break; + case 2: + printf("Enter the breadth and length\n"); + scanf("%f %f", &breadth, &length); + area = breadth * length; + printf("Area of a Reactangle = %f\n", area); + break; + case 3: + printf("Enter the base and height\n"); + scanf("%f %f", &base, &height); + area = 0.5 * base * height; + printf("Area of a Triangle = %f\n", area); + break; + case 4: + printf("Enter the side\n"); + scanf("%f", &side); + area = side * side; + printf("Area of a Square=%f\n", area); + break; + default: + printf("Error in figure code\n"); + break; + } +} \ No newline at end of file diff --git a/c/Functions/C Program to Find the Factorial of a Number using Recursion.c b/c/Functions/C Program to Find the Factorial of a Number using Recursion.c new file mode 100644 index 0000000..bbc5721 --- /dev/null +++ b/c/Functions/C Program to Find the Factorial of a Number using Recursion.c @@ -0,0 +1,35 @@ +/* + * C Program to find factorial of a given number using recursion + */ +#include + +int factorial(int); + +int main() +{ + int num; + int result; + printf("Enter a number to find it's Factorial: "); + scanf("%d", &num); + if (num < 0) + { + printf("Factorial of negative number not possible\n"); + } + else + { + result = factorial(num); + printf("The Factorial of %d is %d.\n", num, result); + } + return 0; +} +int factorial(int num) +{ + if (num == 0 || num == 1) + { + return 1; + } + else + { + return(num * factorial(num - 1)); + } +} \ No newline at end of file diff --git a/c/Functions/C Program to Find the GCD and LCM of Two Integers.c b/c/Functions/C Program to Find the GCD and LCM of Two Integers.c new file mode 100644 index 0000000..a711230 --- /dev/null +++ b/c/Functions/C Program to Find the GCD and LCM of Two Integers.c @@ -0,0 +1,32 @@ +/* + * C program to find the GCD and LCM of two integers using Euclids' algorithm + */ +#include + +void main() +{ + int num1, num2, gcd, lcm, remainder, numerator, denominator; + printf("Enter two numbers\n"); + scanf("%d %d", &num1, &num2); + if (num1 > num2) + { + numerator = num1; + denominator = num2; + } + else + { + numerator = num2; + denominator = num1; + } + remainder = numerator % denominator; + while (remainder != 0) + { + numerator = denominator; + denominator = remainder; + remainder = numerator % denominator; + } + gcd = denominator; + lcm = num1 * num2 / gcd; + printf("GCD of %d and %d = %d\n", num1, num2, gcd); + printf("LCM of %d and %d = %d\n", num1, num2, lcm); +} \ No newline at end of file diff --git a/c/Functions/C Program to Find the Nth Fibonacci Number using Recursion.c b/c/Functions/C Program to Find the Nth Fibonacci Number using Recursion.c new file mode 100644 index 0000000..6556702 --- /dev/null +++ b/c/Functions/C Program to Find the Nth Fibonacci Number using Recursion.c @@ -0,0 +1,38 @@ +/* + * C Program to find the nth number in Fibonacci series using recursion + */ +#include +int fibo(int); + +int main() +{ + int num; + int result; + printf("Enter the nth number in fibonacci series: "); + scanf("%d", &num); + if (num < 0) + { + printf("Fibonacci of negative number is not possible.\n"); + } + else + { + result = fibo(num); + printf("The %d number in fibonacci series is %d\n", num, result); + } + return 0; +} +int fibo(int num) +{ + if (num == 0) + { + return 0; + } + else if (num == 1) + { + return 1; + } + else + { + return(fibo(num - 1) + fibo(num - 2)); + } +} \ No newline at end of file diff --git a/c/Functions/C Program to Find the Perimeter of a Circle, Rectangle and Triangle.c b/c/Functions/C Program to Find the Perimeter of a Circle, Rectangle and Triangle.c new file mode 100644 index 0000000..0c73ad5 --- /dev/null +++ b/c/Functions/C Program to Find the Perimeter of a Circle, Rectangle and Triangle.c @@ -0,0 +1,54 @@ +/* + * C Program to Find the Perimeter of a Circle, Rectangle and Triangle + This C Program calculates the perimeter of a circle, rectangle and triangle. This program is used to find the perimeter of a circle, rectangle and triangle. The formula used in this program are +perimeter of rectangle: 2 * (a + b) +perimeter of General triangle: a + b + c +perimeter of Equilateral triangle: 3 * a +perimeter of Right angled triangle: width + height + sqrt(width ^ 2 + height ^ 2) +perimeter of circle: 2 * pi * r + */ +#include +#include + +int main() +{ + float radius, length, width, a, b, c, height; + int n; + float perimeter; + //Perimeter of rectangle + printf(" \n Perimeter of rectangle \n"); + printf("---------------------------\n"); + printf("\n Enter width and length of the rectangle : "); + scanf("%f%f", &width,& length); + perimeter = 2 * (width + length); + printf("Perimeter of rectangle is: %.3f", perimeter); + //Perimeter of triangle + printf("\n Perimeter of triangle n"); + printf("---------------------------n"); + printf("\n Enter the size of all sides of the triangle : "); + scanf("%f%f%f", &a, &b, &c); + perimeter = a + b + c; + printf("Perimeter of triangle is: %.3f", perimeter); + //Perimeter of circle + printf(" \n Perimeter of circle \n"); + printf("---------------------------\n"); + printf("\n Enter the radius of the circle : "); + scanf("%f", &radius); + perimeter = 2 * (22 / 7) * radius; + printf("Perimeter of circle is: %.3f", perimeter); + //Perimeter of equilateral triangle + printf(" \n Perimeter of equilateral triangle \n"); + printf("---------------------------\n"); + printf("\n Enter any side of the equilateral triangle : "); + scanf("%f", &a); + perimeter = 3 * a; + printf("Perimeter of equilateral triangle is: %.3f", perimeter); + //Perimeter of right angled triangle + printf(" \n Perimeter of right angled triangle \n"); + printf("---------------------------\n"); + printf("\n Enter the width and height of the right angled triangle : "); + scanf("%f%f", &width, &height); + perimeter = width + height + sqrt(width * width + height * height); + printf("Perimeter of right angled triangle is: %.3f", perimeter); + return 0; +} \ No newline at end of file diff --git a/c/Functions/C Program to Find the Sum of AP series.c b/c/Functions/C Program to Find the Sum of AP series.c new file mode 100644 index 0000000..2424d7c --- /dev/null +++ b/c/Functions/C Program to Find the Sum of AP series.c @@ -0,0 +1,28 @@ +/* + * C Program to Find the Sum of A.P Series + */ +#include +#include + +int main() +{ + int a, d, n, i, tn; + int sum = 0; + printf("Enter the first term value of the A.P. series: "); + scanf("%d", &a); + printf("Enter the total numbers in the A.P. series: "); + scanf("%d", &n); + printf("Enter the common difference of A.P. series: "); + scanf("%d", &d); + sum = (n * (2 * a + (n - 1)* d ))/ 2; + tn = a + (n - 1) * d; + printf("Sum of the A.P series is: "); + for (i = a; i <= tn; i = i + d ) + { + if (i != tn) + printf("%d + ", i); + else + printf("%d = %d ", i, sum); + } + return 0; +} \ No newline at end of file diff --git a/c/Functions/C Program to Find the Sum of First N Natural Numbers.c b/c/Functions/C Program to Find the Sum of First N Natural Numbers.c new file mode 100644 index 0000000..bb2d1a1 --- /dev/null +++ b/c/Functions/C Program to Find the Sum of First N Natural Numbers.c @@ -0,0 +1,16 @@ +/* + * C program to find the sum of 'N' natural numbers + */ +#include + +void main() +{ + int i, num, sum = 0; + printf("Enter an integer number \n"); + scanf ("%d", &num); + for (i = 1; i <= num; i++) + { + sum = sum + i; + } + printf ("Sum of first %d natural numbers = %d\n", num, sum); +} \ No newline at end of file diff --git a/c/Functions/C Program to Find the Sum of GP series.c b/c/Functions/C Program to Find the Sum of GP series.c new file mode 100644 index 0000000..5c53a0a --- /dev/null +++ b/c/Functions/C Program to Find the Sum of GP series.c @@ -0,0 +1,22 @@ +/* + * C Program to Find the Sum of G.P Series + */ +#include +#include + +int main() +{ + float a, r, i, last_term, sum = 0; + int n; + printf("Enter the first term of the G.P. series: "); + scanf("%f", &a); + printf("Enter the total numbers in the G.P. series: "); + scanf("%d", &n); + printf("Enter the common ratio of G.P. series: "); + scanf("%f", &r); + sum = (a *(1 - pow(r, n + 1))) / (1 - r); + last_term = a * pow(r, n - 1); + printf("last_term term of G.P.: %f", last_term); + printf("\n Sum of the G.P.: %f", sum); + return 0; +} \ No newline at end of file diff --git a/c/Functions/C Program to Find the Sum of HP series.c b/c/Functions/C Program to Find the Sum of HP series.c new file mode 100644 index 0000000..ab45fb1 --- /dev/null +++ b/c/Functions/C Program to Find the Sum of HP series.c @@ -0,0 +1,20 @@ +/* + * C Program to Find the Sum of H.P Series + */ +#include + +void main() +{ + int n; + float i, sum, term; + printf("1 + 1 / 2 + 1 / 3 +......+1 / n \n"); + printf("Enter the value of n \n"); + scanf("%d", &n); + sum = 0; + for (i = 1; i <= n; i++) + { + term = 1 / i; + sum = sum + term; + } + printf("the Sum of H.P Series is = %f", sum); +} \ No newline at end of file diff --git a/c/Functions/C Program to Find the Volume and Surface Area of Cuboids.c b/c/Functions/C Program to Find the Volume and Surface Area of Cuboids.c new file mode 100644 index 0000000..b5b8cb0 --- /dev/null +++ b/c/Functions/C Program to Find the Volume and Surface Area of Cuboids.c @@ -0,0 +1,22 @@ +/* + * C Program to Find the Volume and Surface Area of Cuboids + */ +#include +#include + +int main() +{ + float width, length, height; + float surfacearea, volume, space_diagonal; + printf("Enter value of width, length & height of the cuboids:\n"); + scanf("%f%f%f", &width, &length, &height); + surfacearea = 2 *(width * length + length * height + + height * width); + volume = width * length * height; + space_diagonal = sqrt(width * width + length * length + + height * height); + printf("Surface area of cuboids is: %.3f", surfacearea); + printf("\n Volume of cuboids is : %.3f", volume); + printf("\n Space diagonal of cuboids is : %.3f", space_diagonal); + return 0; +} \ No newline at end of file diff --git a/c/Functions/C Program to Find the Volume and Surface Area of cylinder.c b/c/Functions/C Program to Find the Volume and Surface Area of cylinder.c new file mode 100644 index 0000000..846d4af --- /dev/null +++ b/c/Functions/C Program to Find the Volume and Surface Area of cylinder.c @@ -0,0 +1,18 @@ +/* + * C Program to Find the Volume and Surface Area of cylinder + */ +#include +#include + +int main() +{ + float radius, height; + float surface_area, volume; + printf("Enter value for radius and height of a cylinder : \n"); + scanf("%f%f", &radius, &height); + surface_area = 2 * (22 / 7) * radius * (radius + height); + volume = (22 / 7) * radius * radius * height; + printf("Surface area of cylinder is: %.3f", surface_area); + printf("\n Volume of cylinder is : %.3f", volume); + return 0; +} \ No newline at end of file diff --git a/c/Functions/C Program to Find the volume and surface area of cone.c b/c/Functions/C Program to Find the volume and surface area of cone.c new file mode 100644 index 0000000..d307f91 --- /dev/null +++ b/c/Functions/C Program to Find the volume and surface area of cone.c @@ -0,0 +1,18 @@ +/* + * C Program to Find the volume and surface area of cone + */ +#include +#include + +int main() +{ + float radius, height; + float surface_area, volume; + printf("Enter value of radius and height of a cone :\n "); + scanf("%f%f", &radius, &height); + surface_area = (22 / 7) * radius * (radius + sqrt(radius * radius + height * height)); + volume = (1.0/3) * (22 / 7) * radius * radius * height; + printf("Surface area of cone is: %.3f", surface_area); + printf("\n Volume of cone is : %.3f", volume); + return 0; +} \ No newline at end of file diff --git a/c/Functions/C Program to Generate Fibonacci Series.c b/c/Functions/C Program to Generate Fibonacci Series.c new file mode 100644 index 0000000..4a41836 --- /dev/null +++ b/c/Functions/C Program to Generate Fibonacci Series.c @@ -0,0 +1,24 @@ +/* + * C program to generate Fibonacci Series. Fibonacci Series + * is 0 1 1 2 3 5 8 13 21 ... + */ +#include + +void main() +{ + int fib1 = 0, fib2 = 1, fib3, limit, count = 0; + printf("Enter the limit to generate the Fibonacci Series \n"); + scanf("%d", &limit); + printf("Fibonacci Series is ...\n"); + printf("%d\n", fib1); + printf("%d\n", fib2); + count = 2; + while (count < limit) + { + fib3 = fib1 + fib2; + count++; + printf("%d\n", fib3); + fib1 = fib2; + fib2 = fib3; + } +} \ No newline at end of file diff --git a/c/Functions/C Program to Implement a strpbrk() Function.c b/c/Functions/C Program to Implement a strpbrk() Function.c new file mode 100644 index 0000000..b273e45 --- /dev/null +++ b/c/Functions/C Program to Implement a strpbrk() Function.c @@ -0,0 +1,65 @@ +/* +* C Program to Implement a strpbrk() Function +*/ +#include + +char* strpbrk(char *, char *); + +int main() +{ + char string1[50], string2[50]; + char *pos; + printf("Enter the String: + "); + scanf(" %[^ + ]s", string1); + printf(" + Enter the Character Set: + "); + scanf(" %[^ + ]s", string2); + pos=strpbrk(string1, string2); + printf("%s", pos); +} + + /* Locates First occurrence in string s1 of any character in string s2, + * If a character from string s2 is found , + * a pointer to the character in string s1 is returned, + * otherwise, a NULL pointer is returned. + */ + char* strpbrk(char *string1, char *string2) +{ + int i, j, pos, flag = 0; + for (i = 0; string1[i] != ''; i++); + pos = i; + for (i = 0; string2[i] != ''; i++) + { + for (j = 0; string1[j] != ''; j++) + { + if (string2[i] == string1[j]) + { + if ( j <= p1) + { + pos = j; + flag = 1; + } + } + } + } + if (flag == 1) + { + return &string1[pos]; + } + else + { + return NULL; + } +} + + +Enter the String: +C programming Class + +Enter the Character Set: +mp +programming Class \ No newline at end of file diff --git a/c/Functions/C Program to Print the Factorial of a given Number.c b/c/Functions/C Program to Print the Factorial of a given Number.c new file mode 100644 index 0000000..26293c0 --- /dev/null +++ b/c/Functions/C Program to Print the Factorial of a given Number.c @@ -0,0 +1,21 @@ +/* + * C program to find the factorial of a given number + */ + +#include +void main() +{ + int i, fact = 1, num; + printf("Enter the number \n"); + scanf("%d", &num); + if (num <= 0) + fact = 1; + else + { + for (i = 1; i <= num; i++) + { + fact = fact * i; + } + } + printf("Factorial of %d = %5d\n", num, fact); +} \ No newline at end of file diff --git a/c/Functions/C Program to Read a Coordinate Point in a XY Coordinate System and Determine its Quadrant.c b/c/Functions/C Program to Read a Coordinate Point in a XY Coordinate System and Determine its Quadrant.c new file mode 100644 index 0000000..d631e9d --- /dev/null +++ b/c/Functions/C Program to Read a Coordinate Point in a XY Coordinate System and Determine its Quadrant.c @@ -0,0 +1,22 @@ +/* + * C program to accept a coordinate point in a XY coordinate system + * and determine its quadrant + */ +#include + +void main() +{ + int x, y; + printf("Enter the values for X and Y\n"); + scanf("%d %d", &x, &y); + if (x > 0 && y > 0) + printf("point (%d, %d) lies in the First quandrant\n"); + else if (x < 0 && y > 0) + printf("point (%d, %d) lies in the Second quandrant\n"); + else if (x < 0 && y < 0) + printf("point (%d, %d) lies in the Third quandrant\n"); + else if (x > 0 && y < 0) + printf("point (%d, %d) lies in the Fourth quandrant\n"); + else if (x == 0 && y == 0) + printf("point (%d, %d) lies at the origin\n"); +} \ No newline at end of file diff --git a/c/Functions/C Program to Simulate a Simple Calculator.c b/c/Functions/C Program to Simulate a Simple Calculator.c new file mode 100644 index 0000000..41c0ebb --- /dev/null +++ b/c/Functions/C Program to Simulate a Simple Calculator.c @@ -0,0 +1,37 @@ +/* + * C program to simulate a simple calculator to perform arithmetic + * operations like addition, subtraction, multiplication and division + */ +#include + +void main() +{ + char operator; + float num1, num2, result; + printf("Simulation of a Simple Calculator\n"); + printf("*********************************\n"); + printf("Enter two numbers \n"); + scanf("%f %f", &num1, &num2); + fflush(stdin); + printf("Enter the operator [+,-,*,/] \n"); + scanf("%s", &operator); + switch(operator) + { + case '+': + result = num1 + num2; + break; + case '-': + result = num1 - num2; + break; + case '*': + result = num1 * num2; + break; + case '/': + result = num1 / num2; + break; + default : + printf("Error in operationn"); + break; + } + printf("\n %5.2f %c %5.2f = %5.2f\n", num1, operator, num2, result); +} \ No newline at end of file diff --git a/c/Functions/C Program to find HCF of a given Number using Recursion.c b/c/Functions/C Program to find HCF of a given Number using Recursion.c new file mode 100644 index 0000000..ee50edd --- /dev/null +++ b/c/Functions/C Program to find HCF of a given Number using Recursion.c @@ -0,0 +1,31 @@ +/* + * C Program to find HCF of a given Number using Recursion + */ +#include + +int hcf(int, int); + +int main() +{ + int a, b, result; + printf("Enter the two numbers to find their HCF: "); + scanf("%d%d", &a, &b); + result = hcf(a, b); + printf("The HCF of %d and %d is %d.\n", a, b, result); +} + +int hcf(int a, int b) +{ + while (a != b) + { + if (a > b) + { + return hcf(a - b, b); + } + else + { + return hcf(a, b - a); + } + } + return a; +} \ No newline at end of file diff --git a/c/Functions/C Program to find HCF of a given Number without using Recursion.c b/c/Functions/C Program to find HCF of a given Number without using Recursion.c new file mode 100644 index 0000000..75f8e16 --- /dev/null +++ b/c/Functions/C Program to find HCF of a given Number without using Recursion.c @@ -0,0 +1,32 @@ +/* + * C Program to find HCF of a given Number without using Recursion + */ +#include + +int hcf(int, int); + +int main() +{ + int a, b, result; + printf("Enter the two numbers to find their HCF: "); + scanf("%d%d", &a, &b); + result = hcf(a, b); + printf("The HCF of %d and %d is %d.\n", a, b, result); + return 0; +} + +int hcf(int a, int b) +{ + while (a != b) + { + if (a > b) + { + a = a - b; + } + else + { + b = b - a; + } + } + return a; +} \ No newline at end of file diff --git a/c/Functions/C Program to find Power of a Number using Recursion.c b/c/Functions/C Program to find Power of a Number using Recursion.c new file mode 100644 index 0000000..8a77b9f --- /dev/null +++ b/c/Functions/C Program to find Power of a Number using Recursion.c @@ -0,0 +1,28 @@ +/* + * C Program to find Power of a Number using Recursion + */ +#include + +long power (int, int); + +int main() +{ + int pow, num; + long result; + printf("Enter a number: "); + scanf("%d", &num); + printf("Enter it's power: "); + scanf("%d", &pow); + result = power(num, pow); + printf("%d^%d is %ld", num, pow, result); + return 0; +} + +long power (int num, int pow) +{ + if (pow) + { + return (num * power(num, pow - 1)); + } + return 1; +} \ No newline at end of file diff --git a/c/Functions/C Program to find factorial of a number using functions.c b/c/Functions/C Program to find factorial of a number using functions.c new file mode 100644 index 0000000..25ae6b5 --- /dev/null +++ b/c/Functions/C Program to find factorial of a number using functions.c @@ -0,0 +1,18 @@ +#include +int findFactorial(int); +int main() +{ + int i,factorial,num; + printf("Enter a number: "); + scanf("%d",&num); + factorial = findFactorial(num); + printf("Factorial of %d is: %d",num,factorial); + return 0; +} +int findFactorial(int num) +{ + int i,f=1; + for(i=1; i<=num; i++) + f=f*i; + return f; +} \ No newline at end of file diff --git a/c/Functions/C Program to find square of a number using functions.c b/c/Functions/C Program to find square of a number using functions.c new file mode 100644 index 0000000..5238d68 --- /dev/null +++ b/c/Functions/C Program to find square of a number using functions.c @@ -0,0 +1,15 @@ +#include +void main() +{ + int rev(int); + int r,a; + clrscr(); + printf("enter any no: "); + scanf("%d",&a); + r=rev(a); + printf("square is : %d",r); +} +int rev(int x) +{ + return(x*x); +} \ No newline at end of file diff --git a/c/Functions/C Program to find the Sum of Series 1 + 1by2 + 1by3 + 1by4 + … + 1byN.c b/c/Functions/C Program to find the Sum of Series 1 + 1by2 + 1by3 + 1by4 + … + 1byN.c new file mode 100644 index 0000000..fa742c6 --- /dev/null +++ b/c/Functions/C Program to find the Sum of Series 1 + 1by2 + 1by3 + 1by4 + … + 1byN.c @@ -0,0 +1,22 @@ +/* + * C Program to find the Sum of Series 1 + 1/2 + 1/3 + 1/4 + ... + 1/N + */ +#include + +void main() +{ + double number, sum = 0, i; + printf("\n enter the number "); + scanf("%lf", &number); + for (i = 1; i <= number; i++) + { + sum = sum + (1 / i); + if (i == 1) + printf("\n 1 +"); + else if (i == number) + printf(" (1 / %lf)", i); + else + printf(" (1 / %lf) + ", i); + } + printf("\n The sum of the given series is %.2lf", sum); +} \ No newline at end of file diff --git a/c/Functions/C Program to find the sum of series 1^2 + 2^2 + ….c b/c/Functions/C Program to find the sum of series 1^2 + 2^2 + ….c new file mode 100644 index 0000000..3705ab0 --- /dev/null +++ b/c/Functions/C Program to find the sum of series 1^2 + 2^2 + ….c @@ -0,0 +1,22 @@ +/* + * C Program to find the sum of series 1^2 + 2^2 + …. + n^2. + */ +#include + +int main() +{ + int number, i; + int sum = 0; + printf("Enter maximum values of series number: "); + scanf("%d", &number); + sum = (number * (number + 1) * (2 * number + 1 )) / 6; + printf("Sum of the above given series : "); + for (i = 1; i <= number; i++) + { + if (i != number) + printf("%d^2 + ", i); + else + printf("%d^2 = %d ", i, sum); + } + return 0; +} \ No newline at end of file diff --git a/c/Functions/C Program to print Pascals triangle for n rows..c b/c/Functions/C Program to print Pascals triangle for n rows..c new file mode 100644 index 0000000..1d2aa76 --- /dev/null +++ b/c/Functions/C Program to print Pascals triangle for n rows..c @@ -0,0 +1,45 @@ +/* Pascal Triangle - Program to print Pascals triangle for n rows */ + +#include +#include + +long fact(int n) ; + +void main() +{ + int n, r, c, j ; + clrscr() ; + printf("Enter the number of rows: ") ; + scanf("%d", &n) ; + printf("Pascal triangle for %d rows is as shown: \n", n) ; + for(r=0 ; r +#include +void main() +{ + void table(); + table(); + getch(); +} +void table() +{ + int n,i,r; + printf("enter a no to know table: "); + scanf("%d",&n); + for(i=1; i<=10; i++) + { + r=n*i; + printf("%d*%d=%d\n",n,i,r); + } +} +Output: +enter a no to know table: 2 +2*1=2 + 2*2=4 + 2*3=6 + 2*4=8 + 2*5=10 + 2*6=12 + 2*7=14 + 2*8=16 + 2*9=18 + 2*10=20 \ No newline at end of file diff --git a/c/Functions/C Program to swap two numbers using functions.c b/c/Functions/C Program to swap two numbers using functions.c new file mode 100644 index 0000000..350c25c --- /dev/null +++ b/c/Functions/C Program to swap two numbers using functions.c @@ -0,0 +1,17 @@ +#include +void main() +{ + void swap(int,int); + int a,b,r; + printf("enter value for a&b: "); + scanf("%d%d",&a,&b); + swap(a,b); +} +void swap(int a,int b) +{ + int temp; + temp=a; + a=b; + b=temp; + printf("after swapping the value for a & b is : %d %d",a,b); +} \ No newline at end of file diff --git a/c/Functions/C program to Calculate the Value of nPr.c b/c/Functions/C program to Calculate the Value of nPr.c new file mode 100644 index 0000000..be86d1e --- /dev/null +++ b/c/Functions/C program to Calculate the Value of nPr.c @@ -0,0 +1,21 @@ +/* + * C program to Calculate the Value of nPr + */ +#include + +void main(void) +{ + printf("%d\n", fact(8)); + int n, r; + printf("Enter value for n and r\n"); + scanf("%d%d", &n, &r); + int npr = fact(n) / fact(n - r); + printf("\n Permutation values is = %d", npr); +} + +int fact(int x) +{ + if (x <= 1) + return 1; + return x * fact(x - 1); +} \ No newline at end of file diff --git a/c/Functions/C program to Calculate the value of nCr.c b/c/Functions/C program to Calculate the value of nCr.c new file mode 100644 index 0000000..9359433 --- /dev/null +++ b/c/Functions/C program to Calculate the value of nCr.c @@ -0,0 +1,32 @@ +/* + * C program to Calculate the value of nCr + */ +#include + +int fact(int z); + +void main() +{ + int n, r, ncr; + printf("\n Enter the value for N and R \n"); + scanf("%d%d", &n, &r); + ncr = fact(n) / (fact(r) * fact(n - r)); + printf("\n The value of ncr is: %d", ncr); +} + +int fact(int z) +{ + int f = 1, i; + if (z == 0) + { + return(f); + } + else + { + for (i = 1; i <= z; i++) + { + f = f * i; + } + } + return(f); +} \ No newline at end of file diff --git a/c/Functions/C program to add two complex numbers..c b/c/Functions/C program to add two complex numbers..c new file mode 100644 index 0000000..eb741ed --- /dev/null +++ b/c/Functions/C program to add two complex numbers..c @@ -0,0 +1,28 @@ +#include + +struct complex +{ + int real, img; +}; + +int main() +{ + struct complex a, b, c; + printf("Enter a and b where a + ib is the first complex number.\n"); + printf("a = "); + scanf("%d", &a.real); + printf("b = "); + scanf("%d", &a.img); + printf("Enter c and d where c + id is the second complex number.\n"); + printf("c = "); + scanf("%d", &b.real); + printf("d = "); + scanf("%d", &b.img); + c.real = a.real + b.real; + c.img = a.img + b.img; + if ( c.img >= 0 ) + printf("Sum of two complex numbers = %d + %di\n", c.real, c.img); + else + printf("Sum of two complex numbers = %d %di\n", c.real, c.img); + return 0; +} \ No newline at end of file diff --git a/c/Functions/C program to find ncr and npr..c b/c/Functions/C program to find ncr and npr..c new file mode 100644 index 0000000..7f25f05 --- /dev/null +++ b/c/Functions/C program to find ncr and npr..c @@ -0,0 +1,41 @@ +#include + +long factorial(int); +long find_ncr(int, int); +long find_npr(int, int); + +int main() +{ + int n, r; + long ncr, npr; + printf("Enter the value of n and r\n"); + scanf("%d%d",&n,&r); + ncr = find_ncr(n, r); + npr = find_npr(n, r); + printf("%dC%d = %ld\n", n, r, ncr); + printf("%dP%d = %ld\n", n, r, npr); + return 0; +} + +long find_ncr(int n, int r) +{ + long result; + result = factorial(n)/(factorial(r)*factorial(n-r)); + return result; +} + +long find_npr(int n, int r) +{ + long result; + result = factorial(n)/factorial(n-r); + return result; +} + +long factorial(int n) +{ + int c; + long result = 1; + for (c = 1; c <= n; c++) + result = result*c; + return result; +} \ No newline at end of file diff --git a/c/Functions/C program to generate random numbers..c b/c/Functions/C program to generate random numbers..c new file mode 100644 index 0000000..a3fb9d5 --- /dev/null +++ b/c/Functions/C program to generate random numbers..c @@ -0,0 +1,14 @@ +#include +#include + +int main() +{ + int c, n; + printf("Ten random numbers in [1,100]\n"); + for (c = 1; c <= 10; c++) + { + n = rand() % 100 + 1; + printf("%d\n", n); + } + return 0; +} \ No newline at end of file diff --git a/c/Functions/C program to merge two arrays..c b/c/Functions/C program to merge two arrays..c new file mode 100644 index 0000000..83f0e8d --- /dev/null +++ b/c/Functions/C program to merge two arrays..c @@ -0,0 +1,70 @@ +#include + +void merge(int [], int, int [], int, int []); + +int main() +{ + int a[100], b[100], m, n, c, sorted[200]; + printf("Input number of elements in first array\n"); + scanf("%d", &m); + printf("Input %d integers\n", m); + for (c = 0; c < m; c++) + { + scanf("%d", &a[c]); + } + printf("Input number of elements in second array\n"); + scanf("%d", &n); + printf("Input %d integers\n", n); + for (c = 0; c < n; c++) + { + scanf("%d", &b[c]); + } + merge(a, m, b, n, sorted); + printf("Sorted array:\n"); + for (c = 0; c < m + n; c++) + { + printf("%d\n", sorted[c]); + } + return 0; +} + +void merge(int a[], int m, int b[], int n, int sorted[]) +{ + int i, j, k; + j = k = 0; + for (i = 0; i < m + n;) + { + if (j < m && k < n) + { + if (a[j] < b[k]) + { + sorted[i] = a[j]; + j++; + } + else + { + sorted[i] = b[k]; + k++; + } + i++; + } + else if (j == m) + { + for (; i < m + n;) + { + sorted[i] = b[k]; + k++; + i++; + } + } + else + { + for (; i < m + n;) + { + sorted[i] = a[j]; + j++; + i++; + } + } + } +} \ No newline at end of file diff --git a/c/Matirix/C Program for Addition of two matrices using arrays source code.c b/c/Matirix/C Program for Addition of two matrices using arrays source code.c new file mode 100644 index 0000000..e8cf923 --- /dev/null +++ b/c/Matirix/C Program for Addition of two matrices using arrays source code.c @@ -0,0 +1,23 @@ +#include +void main() +{ + int a[3][3],b[3][3],c[3][3],i,j; + printf("Enter the First matrix: "); + for(i=0; i<3; i++) + for(j=0; j<3; j++) + scanf("%d",&a[i][j]); + printf("\nEnter the Second matrix : "); + for(i=0; i<3; i++) + for(j=0; j<3; j++) + scanf("%d",&b[i][j]); + for(i=0; i<3; i++) + for(j=0; j<3; j++) + c[i][j]=a[i][j]+b[i][j]; + printf("\nThe Addition of two matrix is\n"); + for(i=0; i<3; i++) + { + printf("\n"); + for(j=0; j<3; j++) + printf("%d\t",c[i][j]); + } +} \ No newline at end of file diff --git a/c/Matirix/C Program for Determinant of 3X3 matrix.c b/c/Matirix/C Program for Determinant of 3X3 matrix.c new file mode 100644 index 0000000..ac651a8 --- /dev/null +++ b/c/Matirix/C Program for Determinant of 3X3 matrix.c @@ -0,0 +1,20 @@ + +#include +void main() +{ + int a[3][3],i,j; + long determinant; + printf("Enter the 3*3 elements of matrix: "); + for(i=0; i<3; i++) + for(j=0; j<3; j++) + scanf("%d",&a[i][j]); + printf("\n Matrix is\n"); + for(i=0; i<3; i++) + { + printf("\n"); + for(j=0; j<3; j++) + printf("%d\t",a[i][j]); + } + determinant = a[0][0]*((a[1][1]*a[2][2]) - (a[2][1]*a[1][2])) -a[0][1]*(a[1][0]*a[2][2] - a[2][0]*a[1][2]) + a[0][2]*(a[1][0]*a[2][1] - a[2][0]*a[1][1]); + printf("\nDeterminant of 3X3 matrix: %ld",determinant); +} \ No newline at end of file diff --git a/c/Matirix/C Program for Multiplication of matrix.c b/c/Matirix/C Program for Multiplication of matrix.c new file mode 100644 index 0000000..868ebc0 --- /dev/null +++ b/c/Matirix/C Program for Multiplication of matrix.c @@ -0,0 +1,66 @@ +#include +void main () +{ + int a[5][5], b[5][5], c[5][5], i, j, k, sum = 0, m, n, o, p; + printf("\nEnter the row and column of first matrix"); + scanf("%d %d", &m, &n); + printf("\nEnter the row and column of second matrix"); + scanf("%d %d", &o, &p); + if (n != o) + { + printf("Matrix mutiplication is not possible"); + printf("\nColumn of first matrix must be same as row of second matrix"); + } + else + { + printf("\nEnter the First matrix: "); + for (i = 0; i < m; i++) + { + for (j = 0; j < n; j++) + { + scanf("%d", &a[i][j]); + } + } + printf("\nEnter the Second matrix: "); + for (i = 0; i < o; i++) + { + for (j = 0; j < p; j++) + { + scanf("%d", &b[i][j]); + } + } + for (i = 0; i < m; i++) + { + for (j = 0; j < p; j++) + { + c[i][j] = 0; + for (i = 0; i < m; i++) + { + //row of first matrix + { + for (j = 0; j < p; j++) + { + //column of second matrix + { + sum = 0; + for (k = 0; k < n; k++) + { + sum = sum + a[i][k] * b[k][j]; + } + c[i][j] = sum; + } + } + } + } + } + } + printf("\nThe multiplication of two matrix is\n"); + for (i = 0; i < m; i++) + { + printf("\n"); + for (j = 0; j < p; j++) + { + printf("%d\t", c[i][j]); + } + } + } \ No newline at end of file diff --git a/c/Matirix/C Program for Subtraction of matrix.c b/c/Matirix/C Program for Subtraction of matrix.c new file mode 100644 index 0000000..1c8513c --- /dev/null +++ b/c/Matirix/C Program for Subtraction of matrix.c @@ -0,0 +1,23 @@ +#include +void main() +{ + int a[3][3],b[3][3],c[3][3],i,j; + printf("Enter the First matrix: "); + for(i=0; i<3; i++) + for(j=0; j<3; j++) + scanf("%d",&a[i][j]); + printf("\nEnter the Second matrix: "); + for(i=0; i<3; i++) + for(j=0; j<3; j++) + scanf("%d",&b[i][j]); + for(i=0; i<3; i++) + for(j=0; j<3; j++) + c[i][j]=a[i][j]-b[i][j]; + printf("\nThe Subtraction of two matrix is\n"); + for(i=0; i<3; i++) + { + printf("\n"); + for(j=0; j<3; j++) + printf("%d\t",c[i][j]); + } +} \ No newline at end of file diff --git a/c/Matirix/C Program to Accept a Matrix of Order MxN & Interchange the Diagonals.c b/c/Matirix/C Program to Accept a Matrix of Order MxN & Interchange the Diagonals.c new file mode 100644 index 0000000..e939a6a --- /dev/null +++ b/c/Matirix/C Program to Accept a Matrix of Order MxN & Interchange the Diagonals.c @@ -0,0 +1,52 @@ +/* + * C program to accept a matrix of order M x N and store its elements + * and interchange the main diagonal elements of the matrix + * with that of the secondary diagonal elements + */ +#include + +void main () +{ + static int array[10][10]; + int i, j, m, n, a; + printf("Enter the order of the matix \n"); + scanf("%d %d", &m, &n); + if (m == n) + { + printf("Enter the co-efficients of the matrix\n"); + for (i = 0; i < m; ++i) + { + for (j = 0; j < n; ++j) + { + scanf("%dx%d", &array[i][j]); + } + } + printf("The given matrix is \n"); + for (i = 0; i < m; ++i) + { + for (j = 0; j < n; ++j) + { + printf(" %d", array[i][j]); + } + printf("\n"); + } + for (i = 0; i < m; ++i) + { + a = array[i][i]; + array[i][i] = array[i][m - i - 1]; + array[i][m - i - 1] = a; + } + printf("The matrix after changing the \n"); + printf("main diagonal & secondary diagonal\n"); + for (i = 0; i < m; ++i) + { + for (j = 0; j < n; ++j) + { + printf(" %d", array[i][j]); + } + printf("\n"); + } + } + else + printf("The given order is not square matrix\n"); +} \ No newline at end of file diff --git a/c/Matirix/C Program to Calculate the Addition or Subtraction & Trace of 2 Matrices.c b/c/Matirix/C Program to Calculate the Addition or Subtraction & Trace of 2 Matrices.c new file mode 100644 index 0000000..3294dda --- /dev/null +++ b/c/Matirix/C Program to Calculate the Addition or Subtraction & Trace of 2 Matrices.c @@ -0,0 +1,110 @@ +/* + * C program to read two matrices A(MxN) and B(MxN) and perform addition + * OR subtraction of A and B. Also, find the trace of the resultant + * matrix. Display the given matrices, their sum or differences and + * the trace. + */ +#include +void trace(int arr[][10], int m, int n); + +void main() +{ + int array1[10][10], array2[10][10], arraysum[10][10], + arraydiff[10][10]; + int i, j, m, n, option; + printf("Enter the order of the matrix array1 and array2 \n"); + scanf("%d %d", &m, &n); + printf("Enter the elements of matrix array1 \n"); + for (i = 0; i < m; i++) + { + for (j = 0; j < n; j++) + { + scanf("%d", &array1[i][j]); + } + } + printf("MATRIX array1 is \n"); + for (i = 0; i < m; i++) + { + for (j = 0; j < n; j++) + { + printf("%3d", array1[i][j]); + } + printf("\n"); + } + printf("Enter the elements of matrix array2 \n"); + for (i = 0; i < m; i++) + { + for (j = 0; j < n; j++) + { + scanf("%d", &array2[i][j]); + } + } + printf("MATRIX array2 is \n"); + for (i = 0; i < m; i++) + { + for (j = 0; j < n; j++) + { + printf("%3d", array2[i][j]); + } + printf("\n"); + } + printf("Enter your option: 1 for Addition and 2 for Subtraction \n"); + scanf("%d", &option); + switch (option) + { + case 1: + for (i = 0; i < m; i++) + { + for (j = 0; j < n; j++) + { + arraysum[i][j] = array1[i][j] + array2[i][j]; + } + } + printf("Sum matrix is \n"); + for (i = 0; i < m; i++) + { + for (j = 0; j < n; j++) + { + printf("%3d", arraysum[i][j]) ; + } + printf("\n"); + } + trace (arraysum, m, n); + break; + case 2: + for (i = 0; i < m; i++) + { + for (j = 0; j < n; j++) + { + arraydiff[i][j] = array1[i][j] - array2[i][j]; + } + } + printf("Difference matrix is \n"); + for (i = 0; i < m; i++) + { + for (j = 0; j < n; j++) + { + printf("%3d", arraydiff[i][j]) ; + } + printf("\n"); + } + trace (arraydiff, m, n); + break; + } +} +/* Function to find the trace of a given matrix and print it */ +void trace (int arr[][10], int m, int n) +{ + int i, j, trace = 0; + for (i = 0; i < m; i++) + { + for (j = 0; j < n; j++) + { + if (i == j) + { + trace = trace + arr[i][j]; + } + } + } + printf("Trace of the resultant matrix is = %d\n", trace); +} \ No newline at end of file diff --git a/c/Matirix/C Program to Calculate the Sum & Difference of the Matrices.c b/c/Matirix/C Program to Calculate the Sum & Difference of the Matrices.c new file mode 100644 index 0000000..4465726 --- /dev/null +++ b/c/Matirix/C Program to Calculate the Sum & Difference of the Matrices.c @@ -0,0 +1,131 @@ +/* + * C program to accept two matrices and find the sum + * and difference of the matrices + */ +#include +#include + +void readmatA(); +void printmatA(); +void readmatB(); +void printmatB(); +void sum(); +void diff(); + +int a[10][10], b[10][10], sumarray[10][10], arraydiff[10][10]; +int i, j, row1, column1, row2, column2; + +void main() +{ + printf("Enter the order of the matrix A \n"); + scanf("%d %d", &row1, &column1); + printf("Enter the order of the matrix B \n"); + scanf("%d %d", &row2, &column2); + if (row1 != row2 && column1 != column2) + { + printf("Addition and subtraction are possible \n"); + exit(1); + } + else + { + printf("Enter the elements of matrix A \n"); + readmatA(); + printf("MATRIX A is \n"); + printmatA(); + printf("Enter the elements of matrix B \n"); + readmatB(); + printf("MATRIX B is \n"); + printmatB(); + sum(); + diff(); + } +} +/* Function to read a matrix A */ +void readmatA() +{ + for (i = 0; i < row1; i++) + { + for (j = 0; j < column1; j++) + { + scanf("%d", &a[i][j]); + } + } + return; +} +/* Function to read a matrix B */ +void readmatB() +{ + for (i = 0; i < row2; i++) + { + for (j = 0; j < column2; j++) + { + scanf("%d", &b[i][j]); + } + } +} +/* Function to print a matrix A */ +void printmatA() +{ + for (i = 0; i < row1; i++) + { + for (j = 0; j < column1; j++) + { + printf("%3d", a[i][j]); + } + printf("\n"); + } +} +/* Function to print a matrix B */ +void printmatB() +{ + for (i = 0; i < row2; i++) + { + for (j = 0; j < column2; j++) + { + printf("%3d", b[i][j]); + } + printf("\n"); + } +} +/* Function to do the sum of elements of matrix A and Matrix B */ +void sum() +{ + for (i = 0; i < row1; i++) + { + for (j = 0; j < column2; j++) + { + sumarray[i][j] = a[i][j] + b[i][j]; + } + } + printf("Sum matrix is \n"); + for (i = 0; i < row1; i++) + { + for (j = 0; j < column2; j++) + { + printf("%3d", sumarray[i][j]) ; + } + printf("\n"); + } + return; +} +/* Function to do the difference of elements of matrix A and Matrix B */ +void diff() +{ + for (i = 0; i < row1; i++) + { + for (j = 0; j < column2; j++) + { + arraydiff[i][j] = a[i][j] - b[i][j]; + } + } + printf("Difference matrix is \n"); + for (i = 0; i < row1; i++) + { + for (j = 0; j < column2; j++) + { + printf("%3d", arraydiff[i][j]); + } + printf("\n"); + } + return; +} \ No newline at end of file diff --git a/c/Matirix/C Program to Calculate the Sum of the Elements of each Row & Column.c b/c/Matirix/C Program to Calculate the Sum of the Elements of each Row & Column.c new file mode 100644 index 0000000..33c4166 --- /dev/null +++ b/c/Matirix/C Program to Calculate the Sum of the Elements of each Row & Column.c @@ -0,0 +1,73 @@ +/* + * C program to read a matrix A (MxN) & find the following using + * functions a) Sum of the elements of each row + * b) Sum of the elements of each column + * c) Find the sum of all the elements of the matrix + * Output the computed results + */ +#include +int Addrow(int array1[10][10], int k, int c); +int Addcol(int array1[10][10], int k, int r); + +void main() +{ + int arr[10][10]; + int i, j, row, col, rowsum, colsum, sumall=0; + printf("Enter the order of the matrix \n"); + scanf("%d %d", &row, &col); + printf("Enter the elements of the matrix \n"); + for (i = 0; i < row; i++) + { + for (j = 0; j < col; j++) + { + scanf("%d", &arr[i][j]); + } + } + printf("Input matrix is \n"); + for (i = 0; i < row; i++) + { + for (j = 0; j < col; j++) + { + printf("%3d", arr[i][j]); + } + printf("\n"); + } + /* computing row sum */ + for (i = 0; i < row; i++) + { + rowsum = Addrow(arr, i, col); + printf("Sum of row %d = %d\n", i + 1, rowsum); + } + /* computing col sum */ + for (j = 0; j < col; j++) + { + colsum = Addcol(arr, j, row); + printf("Sum of column %d = %d\n", j + 1, colsum); + } + /* computation of all elements */ + for (j = 0; j < row; j++) + { + sumall = sumall + Addrow(arr, j, col); + } + printf("Sum of all elements of matrix = %d\n", sumall); +} +/* Function to add each row */ +int Addrow(int array1[10][10], int k, int c) +{ + int rsum = 0, i; + for (i = 0; i < c; i++) + { + rsum = rsum + array1[k][i]; + } + return(rsum); +} +/* Function to add each column */ +int Addcol(int array1[10][10], int k, int r) +{ + int csum = 0, j; + for (j = 0; j < r; j++) + { + csum = csum + array1[j][k]; + } + return(csum); +} \ No newline at end of file diff --git a/c/Matirix/C Program to Check if 2 Matrices are Equal.c b/c/Matirix/C Program to Check if 2 Matrices are Equal.c new file mode 100644 index 0000000..3d9e021 --- /dev/null +++ b/c/Matirix/C Program to Check if 2 Matrices are Equal.c @@ -0,0 +1,74 @@ +/* + * C Program to accept two matrices and check if they are equal + */ +#include +#include + +void main() +{ + int a[10][10], b[10][10]; + int i, j, row1, column1, row2, column2, flag = 1; + printf("Enter the order of the matrix A \n"); + scanf("%d %d", &row1, &column1); + printf("Enter the order of the matrix B \n"); + scanf("%d %d", &row2, &column2); + printf("Enter the elements of matrix A \n"); + for (i = 0; i < row1; i++) + { + for (j = 0; j < column1; j++) + { + scanf("%d", &a[i][j]); + } + } + printf("Enter the elements of matrix B \n"); + for (i = 0; i < row2; i++) + { + for (j = 0; j < column2; j++) + { + scanf("%d", &b[i][j]); + } + } + printf("MATRIX A is \n"); + for (i = 0; i < row1; i++) + { + for (j = 0; j < column1; j++) + { + printf("%3d", a[i][j]); + } + printf("\n"); + } + printf("MATRIX B is \n"); + for (i = 0; i < row2; i++) + { + for (j = 0; j < column2; j++) + { + printf("%3d", b[i][j]); + } + printf("\n"); + } + /* Comparing two matrices for equality */ + if (row1 == row2 && column1 == column2) + { + printf("Matrices can be compared \n"); + for (i = 0; i < row1; i++) + { + for (j = 0; j < column2; j++) + { + if (a[i][j] != b[i][j]) + { + flag = 0; + break; + } + } + } + } + else + { + printf(" Cannot be compared\n"); + exit(1); + } + if (flag == 1) + printf("Two matrices are equal \n"); + else + printf("But, two matrices are not equal \n"); +} \ No newline at end of file diff --git a/c/Matirix/C Program to Check if a given Matrix is an Identity Matrix.c b/c/Matirix/C Program to Check if a given Matrix is an Identity Matrix.c new file mode 100644 index 0000000..1352138 --- /dev/null +++ b/c/Matirix/C Program to Check if a given Matrix is an Identity Matrix.c @@ -0,0 +1,45 @@ +/* + * C Program to check if a given matrix is an identity matrix + */ +#include + +void main() +{ + int a[10][10]; + int i, j, row, column, flag = 1; + printf("Enter the order of the matrix A \n"); + scanf("%d %d", &row, &column); + printf("Enter the elements of matrix A \n"); + for (i = 0; i < row; i++) + { + for (j = 0; j < column; j++) + { + scanf("%d", &a[i][j]); + } + } + printf("MATRIX A is \n"); + for (i = 0; i < row; i++) + { + for (j = 0; j < column; j++) + { + printf("%3d", a[i][j]); + } + printf("\n"); + } + /* Check for unit (or identity) matrix */ + for (i = 0; i < row; i++) + { + for (j = 0; j < column; j++) + { + if (a[i][j] != 1 && a[j][i] != 0) + { + flag = 0; + break; + } + } + } + if (flag == 1 ) + printf("It is identity matrix \n"); + else + printf("It is not a identity matrix \n"); +} \ No newline at end of file diff --git a/c/Matirix/C Program to Compute the Product of Two Matrices.c b/c/Matirix/C Program to Compute the Product of Two Matrices.c new file mode 100644 index 0000000..84fbc63 --- /dev/null +++ b/c/Matirix/C Program to Compute the Product of Two Matrices.c @@ -0,0 +1,76 @@ +/* + * Develop functions to read a matrix, display a matrix and compute + * product of two matrices. + * Use these functions to read two MxN matrices and compute their + * product & display the result + */ +#include +#define MAXROWS 10 +#define MAXCOLS 10 + +void readMatrix(int arr[][MAXCOLS], int m, int n); +void printMatrix(int arr[][MAXCOLS], int m, int n); +void productMatrix(int array1[][MAXCOLS], int array2[][MAXCOLS], + int array3[][MAXCOLS], int m, int n); + +void main() +{ + int array1[MAXROWS][MAXCOLS], array2[MAXROWS][MAXCOLS], + array3[MAXROWS][MAXCOLS]; + int m, n; + printf("Enter the value of m and n \n"); + scanf("%d %d", &m, &n); + printf("Enter Matrix array1 \n"); + readMatrix(array1, m, n); + printf("Matrix array1 \n"); + printMatrix(array1, m, n); + printf("Enter Matrix array2 \n"); + readMatrix(array2, m, n); + printf("Matrix B \n"); + printMatrix(array2, m, n); + productMatrix(array1, array2, array3, m, n); + printf("The product matrix is \n"); + printMatrix(array3, m, n); +} +/* Input Matrix array1 */ +void readMatrix(int arr[][MAXCOLS], int m, int n) +{ + int i, j; + for (i = 0; i < m; i++) + { + for (j = 0; j < n; j++) + { + scanf("%d", &arr[i][j]); + } + } +} +void printMatrix(int arr[][MAXCOLS], int m, int n) +{ + int i, j; + for (i = 0; i < m; i++) + { + for (j = 0; j < n; j++) + { + printf("%3d", arr[i][j]); + } + printf("\n"); + } +} +/* Multiplication of matrices */ +void productMatrix(int array1[][MAXCOLS], int array2[][MAXCOLS], + int array3[][MAXCOLS], int m, int n) +{ + int i, j, k; + for (i = 0; i < m; i++) + { + for (j = 0; j < n; j++) + { + array3[i][j] = 0; + for (k = 0; k < n; k++) + { + array3[i][j] = array3[i][j] + array1[i][k] * + array2[k][j]; + } + } + } +} \ No newline at end of file diff --git a/c/Matirix/C Program to Determine if a given Matrix is a Sparse Matrix.c b/c/Matirix/C Program to Determine if a given Matrix is a Sparse Matrix.c new file mode 100644 index 0000000..fdd7ab1 --- /dev/null +++ b/c/Matirix/C Program to Determine if a given Matrix is a Sparse Matrix.c @@ -0,0 +1,33 @@ +/* + * C program to determine if a given matrix is a sparse matrix. + * Sparse martix has more zero elements than nonzero elements. + */ +#include + +void main () +{ + static int array[10][10]; + int i, j, m, n; + int counter = 0; + printf("Enter the order of the matix \n"); + scanf("%d %d", &m, &n); + printf("Enter the co-efficients of the matix \n"); + for (i = 0; i < m; ++i) + { + for (j = 0; j < n; ++j) + { + scanf("%d", &array[i][j]); + if (array[i][j] == 0) + { + ++counter; + } + } + } + if (counter > ((m * n) / 2)) + { + printf("The given matrix is sparse matrix \n"); + } + else + printf("The given matrix is not a sparse matrix \n"); + printf("There are %d number of zeros", counter); +} \ No newline at end of file diff --git a/c/Matirix/C Program to Display Lower Triangular Matrix.c b/c/Matirix/C Program to Display Lower Triangular Matrix.c new file mode 100644 index 0000000..b8e5f90 --- /dev/null +++ b/c/Matirix/C Program to Display Lower Triangular Matrix.c @@ -0,0 +1,31 @@ +/* + * C Program to Display Lower Triangular Matrix + */ +#include + +void main() +{ + int array[3][3], i, j, flag = 0 ; + printf("\n\t Enter the value of Matrix : "); + for (i = 0; i < 3; i++) + { + for (j = 0; j < 3; j++) + { + scanf("%d", &array[i][j]); + } + } + for (i = 0; i < 3; i++) + { + for (j = 0; j < 3; j++) + { + if (array[i] < array[j] && array[i][j] == 0) + { + flag = flag + 1; + } + } + } + if (flag == 3) + printf("\n\n Matrix is a Lower triangular matrix"); + else + printf("\n\n Matrix is not a lower triangular matrix"); +} \ No newline at end of file diff --git a/c/Matirix/C Program to Display Upper Triangular Matrix.c b/c/Matirix/C Program to Display Upper Triangular Matrix.c new file mode 100644 index 0000000..7d3becf --- /dev/null +++ b/c/Matirix/C Program to Display Upper Triangular Matrix.c @@ -0,0 +1,59 @@ +/* + * C Program to Display Upper Triangular Matrix + */ +#include + +void main() +{ + int i, j, r, c, array[10][10]; + printf("Enter the r and c value:"); + scanf("%d%d", &r, &c); + for (i = 1; i <= r; i++) + { + for (j = 1; j <= c; j++) + { + printf("array[%d][%d] = ", i, j); + scanf("%d", &array[i][j]); + } + } + printf("matrix is"); + for (i = 1; i <= r; i++) + { + for (j = 1; j <= c; j++) + { + printf("%d", array[i][j]); + } + printf("\n"); + } + for (i = 1; i <= r; i++) + { + printf("\n"); + for (j = 1; j <= c; j++) + { + if (i >= j) + { + printf("%d", array[i][j]); + } + else + { + printf("\t"); + } + } + } + printf("\n\n"); + for (i = 1; i <= r; i++) + { + printf("\n"); + for (j = 1; j <= c; j++) + { + if (j >= i) + { + printf("%d", array[i][j]); + } + else + { + //printf("\t"); + } + // printf("\n"); + } + } \ No newline at end of file diff --git a/c/Matirix/C Program to Find the Frequency of Odd & Even Numbers in the given Matrix.c b/c/Matirix/C Program to Find the Frequency of Odd & Even Numbers in the given Matrix.c new file mode 100644 index 0000000..5d6139a --- /dev/null +++ b/c/Matirix/C Program to Find the Frequency of Odd & Even Numbers in the given Matrix.c @@ -0,0 +1,38 @@ +/* + * C program to find the frequency of odd numbers + * and even numbers in the input of a matrix + */ +#include + +void main() +{ + static int array[10][10]; + int i, j, m, n, even = 0, odd = 0; + printf("Enter the order ofthe matrix \n"); + scanf("%d %d", &m, &n); + printf("Enter the coefficients of matrix \n"); + for (i = 0; i < m; ++i) + { + for (j = 0; j < n; ++j) + { + scanf("%d", &array[i][j]); + if ((array[i][j] % 2) == 0) + { + ++even; + } + else + ++odd; + } + } + printf("The given matrix is \n"); + for (i = 0; i < m; ++i) + { + for (j = 0; j < n; ++j) + { + printf(" %d", array[i][j]); + } + printf("\n"); + } + printf("\n The frequency of occurance of odd number = %d \n", odd); + printf("The frequency of occurance of even number = %d\n", even); +} \ No newline at end of file diff --git a/c/Matirix/C Program to Find the Sum of each Row & each Column of a MxN Matrix.c b/c/Matirix/C Program to Find the Sum of each Row & each Column of a MxN Matrix.c new file mode 100644 index 0000000..9826e9a --- /dev/null +++ b/c/Matirix/C Program to Find the Sum of each Row & each Column of a MxN Matrix.c @@ -0,0 +1,40 @@ +/* + * C program to accept a matrix of order M x N and find the sum + * of each row and each column of a matrix + */ +#include + +void main () +{ + static int array[10][10]; + int i, j, m, n, sum = 0; + printf("Enter the order of the matrix\n"); + scanf("%d %d", &m, &n); + printf("Enter the co-efficients of the matrix\n"); + for (i = 0; i < m; ++i) + { + for (j = 0; j < n; ++j) + { + scanf("%d", &array[i][j]); + } + } + for (i = 0; i < m; ++i) + { + for (j = 0; j < n; ++j) + { + sum = sum + array[i][j] ; + } + printf("Sum of the %d row is = %d\n", i, sum); + sum = 0; + } + sum = 0; + for (j = 0; j < n; ++j) + { + for (i = 0; i < m; ++i) + { + sum = sum + array[i][j]; + } + printf("Sum of the %d column is = %d\n", j, sum); + sum = 0; + } +} \ No newline at end of file diff --git a/c/Matirix/C Program to Find the Trace & Normal of a given Matrix.c b/c/Matirix/C Program to Find the Trace & Normal of a given Matrix.c new file mode 100644 index 0000000..d11fb3b --- /dev/null +++ b/c/Matirix/C Program to Find the Trace & Normal of a given Matrix.c @@ -0,0 +1,33 @@ +/* + * C program to find the trace and normal of a matrix + * + * Trace is defined as the sum of main diagonal elements and + * Normal is defined as square root of the sum of all the elements + */ +#include +#include + +void main () +{ + static int array[10][10]; + int i, j, m, n, sum = 0, sum1 = 0, a = 0, normal; + printf("Enter the order of the matrix\n"); + scanf("%d %d", &m, &n); + printf("Enter the n coefficients of the matrix \n"); + for (i = 0; i < m; ++i) + { + for (j = 0; j < n; ++j) + { + scanf("%d", &array[i][j]); + a = array[i][j] * array[i][j]; + sum1 = sum1 + a; + } + } + normal = sqrt(sum1); + printf("The normal of the given matrix is = %d\n", normal); + for (i = 0; i < m; ++i) + { + sum = sum + array[i][i]; + } + printf("Trace of the matrix is = %d\n", sum); +} \ No newline at end of file diff --git a/c/Matirix/C Program to Find the Transpose of a given Matrix.c b/c/Matirix/C Program to Find the Transpose of a given Matrix.c new file mode 100644 index 0000000..647a1d8 --- /dev/null +++ b/c/Matirix/C Program to Find the Transpose of a given Matrix.c @@ -0,0 +1,38 @@ +/* + * C program to accept a matrix of order MxN and find its transpose + */ +#include + +void main() +{ + static int array[10][10]; + int i, j, m, n; + printf("Enter the order of the matrix \n"); + scanf("%d %d", &m, &n); + printf("Enter the coefiicients of the matrix\n"); + for (i = 0; i < m; ++i) + { + for (j = 0; j < n; ++j) + { + scanf("%d", &array[i][j]); + } + } + printf("The given matrix is \n"); + for (i = 0; i < m; ++i) + { + for (j = 0; j < n; ++j) + { + printf(" %d", array[i][j]); + } + printf("\n"); + } + printf("Transpose of matrix is \n"); + for (j = 0; j < n; ++j) + { + for (i = 0; i < m; ++i) + { + printf(" %d", array[i][j]); + } + printf("\n"); + } +} \ No newline at end of file diff --git a/c/Matirix/C Program to Interchange any two Rows & Columns in the given Matrix.c b/c/Matirix/C Program to Interchange any two Rows & Columns in the given Matrix.c new file mode 100644 index 0000000..e43ea0c --- /dev/null +++ b/c/Matirix/C Program to Interchange any two Rows & Columns in the given Matrix.c @@ -0,0 +1,63 @@ +/* + * C program to accept a matrix of given order and interchange + * any two rows and columns in the original matrix + */ +#include + +void main() +{ + static int array1[10][10], array2[10][10]; + int i, j, m, n, a, b, c, p, q, r; + printf("Enter the order of the matrix \n"); + scanf("%d %d", &m, &n); + printf("Enter the co-efficents of the matrix \n"); + for (i = 0; i < m; ++i) + { + for (j = 0; j < n; ++j) + { + scanf("%d,", &array1[i][j]); + array2[i][j] = array1[i][j]; + } + } + printf("Enter the numbers of two rows to be exchanged \n"); + scanf("%d %d", &a, &b); + for (i = 0; i < m; ++i) + { + /* first row has index is 0 */ + c = array1[a - 1][i]; + array1[a - 1][i] = array1[b - 1][i]; + array1[b - 1][i] = c; + } + printf("Enter the numbers of two columns to be exchanged \n"); + scanf("%d %d", &p, &q); + printf("The given matrix is \n"); + for (i = 0; i < m; ++i) + { + for (j = 0; j < n; ++j) + printf(" %d", array2[i][j]); + printf("\n"); + } + for (i = 0; i < n; ++i) + { + /* first column index is 0 */ + r = array2[i][p - 1]; + array2[i][p - 1] = array2[i][q - 1]; + array2[i][q - 1] = r; + } + printf("The matix after interchanging the two rows(in the original matrix) \n"); + for (i = 0; i < m; ++i) + { + for (j = 0; j < n; ++j) + { + printf(" %d", array1[i][j]); + } + printf("\n"); + } + printf("The matix after interchanging the two columns(in the original matrix) \n"); + for (i = 0; i < m; ++i) + { + for (j = 0; j < n; ++j) + printf(" %d", array2[i][j]); + printf("\n"); + } +} \ No newline at end of file diff --git a/c/Matirix/C Program to Inverse of a 3x3 matrix.c b/c/Matirix/C Program to Inverse of a 3x3 matrix.c new file mode 100644 index 0000000..28b8f96 --- /dev/null +++ b/c/Matirix/C Program to Inverse of a 3x3 matrix.c @@ -0,0 +1,26 @@ +#include +int main() +{ + int a[3][3],i,j; + float determinant=0; + printf("Enter the 9 elements of matrix: "); + for(i=0; i<3; i++) + for(j=0; j<3; j++) + scanf("%d",&a[i][j]); + printf("\nThe matrix is\n"); + for(i=0; i<3; i++) + { + printf("\n"); + for(j=0; j<3; j++) + printf("%d\t",a[i][j]); + } + for(i=0; i<3; i++) + determinant = determinant + (a[0][i]*(a[1][(i+1)%3]*a[2][(i+2)%3] - a[1][(i+2)%3]*a[2][(i+1)%3])); + printf("\nInverse of matrix is: \n"); + for(i=0; i<3; i++) + { + for(j=0; j<3; j++) + printf("%.3f\t",((a[(i+1)%3][(j+1)%3] * a[(i+2)%3][(j+2)%3]) - (a[(i+1)%3][(j+2)%3]*a[(i+2)%3][(j+1)%3]))/ determinant); + printf("\n"); + } +} \ No newline at end of file diff --git a/c/Matirix/C Program to Perform Matrix Multiplication using Recursion.c b/c/Matirix/C Program to Perform Matrix Multiplication using Recursion.c new file mode 100644 index 0000000..9dc6fa0 --- /dev/null +++ b/c/Matirix/C Program to Perform Matrix Multiplication using Recursion.c @@ -0,0 +1,79 @@ +/* + * C Program to Perform Matrix Multiplication using Recursion + */ +#include + +void multiply(int, int, int [][10], int, int, int [][10], int [][10]); +void display(int, int, int[][10]); + +int main() +{ + int a[10][10], b[10][10], c[10][10] = {0}; + int m1, n1, m2, n2, i, j, k; + printf("Enter rows and columns for Matrix A respectively: "); + scanf("%d%d", &m1, &n1); + printf("Enter rows and columns for Matrix B respectively: "); + scanf("%d%d", &m2, &n2); + if (n1 != m2) + { + printf("Matrix multiplication not possible.\n"); + } + else + { + printf("Enter elements in Matrix A:\n"); + for (i = 0; i < m1; i++) + for (j = 0; j < n1; j++) + { + scanf("%d", &a[i][j]); + } + printf("\nEnter elements in Matrix B:\n"); + for (i = 0; i < m2; i++) + for (j = 0; j < n2; j++) + { + scanf("%d", &b[i][j]); + } + multiply(m1, n1, a, m2, n2, b, c); + } + printf("On matrix multiplication of A and B the result is:\n"); + display(m1, n2, c); +} + +void multiply (int m1, int n1, int a[10][10], int m2, int n2, int b[10][10], int c[10][10]) +{ + static int i = 0, j = 0, k = 0; + if (i >= m1) + { + return; + } + else if (i < m1) + { + if (j < n2) + { + if (k < n1) + { + c[i][j] += a[i][k] * b[k][j]; + k++; + multiply(m1, n1, a, m2, n2, b, c); + } + k = 0; + j++; + multiply(m1, n1, a, m2, n2, b, c); + } + j = 0; + i++; + multiply(m1, n1, a, m2, n2, b, c); + } +} + +void display(int m1, int n2, int c[10][10]) +{ + int i, j; + for (i = 0; i < m1; i++) + { + for (j = 0; j < n2; j++) + { + printf("%d ", c[i][j]); + } + printf("\n"); + } +} \ No newline at end of file diff --git a/c/Matirix/C Program to Sort Rows of the Matrix in Ascending & Columns in Descendng Order.c b/c/Matirix/C Program to Sort Rows of the Matrix in Ascending & Columns in Descendng Order.c new file mode 100644 index 0000000..5ffe1ac --- /dev/null +++ b/c/Matirix/C Program to Sort Rows of the Matrix in Ascending & Columns in Descendng Order.c @@ -0,0 +1,79 @@ +/* + * C program to accept a matrics of order MxN and sort all rows of the + * matrix in ascending order and all columns in descending order + */ +#include + +void main() +{ + static int array1[10][10], array2[10][10]; + int i, j, k, a, m, n; + printf("Enter the order of the matrix \n"); + scanf("%d %d", &m, &n); + printf("Enter co-efficients of the matrix \n"); + for (i = 0; i < m; ++i) + { + for (j = 0; j < n; ++j) + { + scanf("%d", &array1[i][j]); + array2[i][j] = array1[i][j]; + } + } + printf("The given matrix is \n"); + for (i = 0; i < m; ++i) + { + for (j = 0; j < n; ++j) + { + printf(" %d", array1[i][j]); + } + printf("\n"); + } + printf("After arranging rows in ascending order\n"); + for (i = 0; i < m; ++i) + { + for (j = 0; j < n; ++j) + { + for (k =(j + 1); k < n; ++k) + { + if (array1[i][j] > array1[i][k]) + { + a = array1[i][j]; + array1[i][j] = array1[i][k]; + array1[i][k] = a; + } + } + } + } + for (i = 0; i < m; ++i) + { + for (j = 0; j < n; ++j) + { + printf(" %d", array1[i][j]); + } + printf("\n"); + } + printf("After arranging the columns in descending order \n"); + for (j = 0; j < n; ++j) + { + for (i = 0; i < m; ++i) + { + for (k = i + 1; k < m; ++k) + { + if (array2[i][j] < array2[k][j]) + { + a = array2[i][j]; + array2[i][j] = array2[k][j]; + array2[k][j] = a; + } + } + } + } + for (i = 0; i < m; ++i) + { + for (j = 0; j < n; ++j) + { + printf(" %d", array2[i][j]); + } + printf("\n"); + } +} \ No newline at end of file diff --git a/c/Matirix/C Program to do the Sum of the Main & Opposite Diagonal Elements of a MxN Matrix.c b/c/Matirix/C Program to do the Sum of the Main & Opposite Diagonal Elements of a MxN Matrix.c new file mode 100644 index 0000000..07ef245 --- /dev/null +++ b/c/Matirix/C Program to do the Sum of the Main & Opposite Diagonal Elements of a MxN Matrix.c @@ -0,0 +1,42 @@ +/* + * C program to find accept a matrix of order M x N and find + * the sum of the main diagonal and off diagonal elements + */ +#include + +void main () +{ + static int array[10][10]; + int i, j, m, n, a = 0, sum = 0; + printf("Enetr the order of the matix \n"); + scanf("%d %d", &m, &n); + if (m == n ) + { + printf("Enter the co-efficients of the matrix\n"); + for (i = 0; i < m; ++i) + { + for (j = 0; j < n; ++j) + { + scanf("%d", &array[i][j]); + } + } + printf("The given matrix is \n"); + for (i = 0; i < m; ++i) + { + for (j = 0; j < n; ++j) + { + printf(" %d", array[i][j]); + } + printf("\n"); + } + for (i = 0; i < m; ++i) + { + sum = sum + array[i][i]; + a = a + array[i][m - i - 1]; + } + printf("\nThe sum of the main diagonal elements is = %d\n", sum); + printf("The sum of the off diagonal elemets is = %d\n", a); + } + else + printf("The given order is not square matrix\n"); +} \ No newline at end of file diff --git a/c/Matirix/C Program to find Sum of diagonal elements of a matrix.c b/c/Matirix/C Program to find Sum of diagonal elements of a matrix.c new file mode 100644 index 0000000..38fd11a --- /dev/null +++ b/c/Matirix/C Program to find Sum of diagonal elements of a matrix.c @@ -0,0 +1,29 @@ +#include +void main() +{ + int a[10][10],i,j,sum=0,m,n; + printf("\nEnter the row and column of matrix: "); + scanf("%d%d",&m,&n); + printf("\nEnter the elements of matrix: "); + for(i=0; i +main() +{ + int a[10][10],b[10][10],i,j,k=0,m,n; + printf("\nEnter the row and column of matrix"); + scanf("%d %d",&m,&n); + printf("\nEnter the First matrix: "); + for(i=0; i + +void main () { + + static int ma[10][10]; + + int i,j,m,n,even=0,odd=0; + + printf ("Enter the order ofthe matrix \n"); + + scanf ("%d %d",&m,&n); + + printf ("Enter the coefficients if matrix \n"); + + for (i=0;i + + void main () + { + static int m1[10][10]; + int i,j,m,n; + int counter=0; + + printf ("Enter the order of the matix\n"); + scanf ("%d %d",&m,&n); + + printf ("Enter the co-efficients of the matix\n"); + for (i=0;i((m*n)/2)) + { + printf ("The given matrix is sparse matrix \n"); + } + else { + printf ("The given matrix is not a sparse matrix \n"); + printf ("There are %d number of zeros",counter); + } /* ENd of main() */ \ No newline at end of file diff --git a/c/Numerical/C Program to Check Multiplicability of Two Matrices.c b/c/Numerical/C Program to Check Multiplicability of Two Matrices.c new file mode 100644 index 0000000..86c11ce --- /dev/null +++ b/c/Numerical/C Program to Check Multiplicability of Two Matrices.c @@ -0,0 +1,18 @@ +#include + +int main() +{ + int m, n; + int p, q; + printf("Enter the dimensions of first matrix: "); + scanf("%d%d", &m, &n); + printf("\nEnter the dimensions of second matrix: "); + scanf("%d%d", &p, &q); + if( n != p ) + { + printf("\nTwo matrices CANNOT be multiplied !!!"); + } + else + printf("\nTwo matrices meet the criteria for Multiplication !!!"); + return 0; +} \ No newline at end of file diff --git a/c/Numerical/C Program to Check if a Matrix is Invertible.c b/c/Numerical/C Program to Check if a Matrix is Invertible.c new file mode 100644 index 0000000..aeaeb7b --- /dev/null +++ b/c/Numerical/C Program to Check if a Matrix is Invertible.c @@ -0,0 +1,24 @@ +#include +int main() +{ + int a[3][3], i, j; + long determinant; + printf("Enter the 9 elements of matrix: "); + for(i = 0 ; i < 3; i++) + for(j = 0; j < 3; j++) + scanf("%d", &a[i][j]); + printf("\nThe matrix is\n"); + for(i = 0; i < 3; i++) + { + printf("\n"); + for(j = 0; j < 3; j++) + printf("%d\t", a[i][j]); + } + determinant = a[0][0] * ((a[1][1]*a[2][2]) - (a[2][1]*a[1][2])) -a[0][1] * (a[1][0] + * a[2][2] - a[2][0] * a[1][2]) + a[0][2] * (a[1][0] * a[2][1] - a[2][0] * a[1][1]); + if ( determinant == 0) + printf("\nMatrix is NOT invertible"); + else + printf("\nThe given matrix has an inverse!!!"); + return 0; +} \ No newline at end of file diff --git a/c/Numerical/C Program to Check if a Matrix is a Sparse Matrix.c b/c/Numerical/C Program to Check if a Matrix is a Sparse Matrix.c new file mode 100644 index 0000000..b5db139 --- /dev/null +++ b/c/Numerical/C Program to Check if a Matrix is a Sparse Matrix.c @@ -0,0 +1,32 @@ +/* + * C Program to check if a Matrix is a Sparse Matrix + */ +#include + +void main () +{ + int matrix[10][10]; + int i, j, m, n; + int sparse_counter = 0; + printf("Enter the order of the matix \n"); + scanf("%d %d", &m, &n); + printf("Enter the elements of the matix \n"); + for (i = 0; i < m; ++i) + { + for (j = 0; j < n; ++j) + { + scanf("%d", &matrix[i][j]); + if (matrix[i][j] == 0) + { + ++sparse_counter; + } + } + } + if (sparse_counter > ((m * n) / 2)) + { + printf("The given matrix is Sparse Matrix !!! \n"); + } + else + printf("The given matrix is not a Sparse Matrix \n"); + printf("There are %d number of Zeros.", sparse_counter); +} \ No newline at end of file diff --git a/c/Numerical/C Program to Compute Determinant of a Matrix.c b/c/Numerical/C Program to Compute Determinant of a Matrix.c new file mode 100644 index 0000000..ea74abc --- /dev/null +++ b/c/Numerical/C Program to Compute Determinant of a Matrix.c @@ -0,0 +1,22 @@ +#include + +int main() +{ + int a[3][3], i, j; + long determinant; + printf("Enter the 9 elements of matrix: "); + for(i = 0 ; i < 3; i++) + for(j = 0; j < 3; j++) + scanf("%d", &a[i][j]); + printf("\nThe matrix is\n"); + for(i = 0; i < 3; i++) + { + printf("\n"); + for(j = 0; j < 3; j++) + printf("%d\t", a[i][j]); + } + determinant = a[0][0] * ((a[1][1]*a[2][2]) - (a[2][1]*a[1][2])) -a[0][1] * (a[1][0] + * a[2][2] - a[2][0] * a[1][2]) + a[0][2] * (a[1][0] * a[2][1] - a[2][0] * a[1][1]); + printf("\nDeterminant of 3X3 matrix: %ld", determinant); + return 0; +} \ No newline at end of file diff --git a/c/Numerical/C Program to Emulate N Dice Roller.c b/c/Numerical/C Program to Emulate N Dice Roller.c new file mode 100644 index 0000000..ef5d8d4 --- /dev/null +++ b/c/Numerical/C Program to Emulate N Dice Roller.c @@ -0,0 +1,15 @@ +#include +#include +#include + +int main(int argc, char **argv) +{ + printf("Enter the number of dice: "); + int n, i; + scanf("%d", &n); + printf("The values on dice are: ( "); + for (i = 0; i < n; i++) + printf("%d ", (rand() % 6) + 1); + printf(")"); + return 0; +} \ No newline at end of file diff --git a/c/Numerical/C Program to Find Basis and Dimension of a Matrix.c b/c/Numerical/C Program to Find Basis and Dimension of a Matrix.c new file mode 100644 index 0000000..f123aa5 --- /dev/null +++ b/c/Numerical/C Program to Find Basis and Dimension of a Matrix.c @@ -0,0 +1,26 @@ +#include + +int main() +{ + int a[3][3], i, j; + long determinant; + printf("Enter the 9 elements of matrix: "); + for (i = 0; i < 3; i++) + for (j = 0; j < 3; j++) + scanf("%d", &a[i][j]); + printf("\nThe matrix is\n"); + for (i = 0; i < 3; i++) + { + printf("\n"); + for (j = 0; j < 3; j++) + printf("%d\t", a[i][j]); + } + determinant = a[0][0] * ((a[1][1] * a[2][2]) - (a[2][1] * a[1][2])) + - a[0][1] * (a[1][0] * a[2][2] - a[2][0] * a[1][2]) + a[0][2] + * (a[1][0] * a[2][1] - a[2][0] * a[1][1]); + if (determinant != 0) + printf("The vectors forms the basis of R %d as the determinant is non-zero", 3); + else + printf("The vectors doesn't form the basis of R %d as the determinant is zero", 3); + return 0; +} \ No newline at end of file diff --git a/c/Numerical/C Program to Find GCD of Two Numbers Using Recursive Euclid Algorithm.c b/c/Numerical/C Program to Find GCD of Two Numbers Using Recursive Euclid Algorithm.c new file mode 100644 index 0000000..3b689c9 --- /dev/null +++ b/c/Numerical/C Program to Find GCD of Two Numbers Using Recursive Euclid Algorithm.c @@ -0,0 +1,33 @@ +/* +This is a C Program to find GCD of two numbers using Recursive Euclid Algorithm. In mathematics, the Euclidean algorithm, or Euclid’s algorithm, is a method for computing the greatest common divisor (GCD) of two (usually positive) integers, also known as the greatest common factor (GCF) or highest common factor (HCF). It is named after the Greek mathematician Euclid, who described it in Books VII and X of his Elements. +The GCD of two positive integers is the largest integer that divides both of them without leaving a remainder (the GCD of two integers in general is defined in a more subtle way). +In its simplest form, Euclid’s algorithm starts with a pair of positive integers, and forms a new pair that consists of the smaller number and the difference between the larger and smaller numbers. The process repeats until the numbers in the pair are equal. That number then is the greatest common divisor of the original pair of integers. +The main principle is that the GCD does not change if the smaller number is subtracted from the larger number. For example, the GCD of 252 and 105 is exactly the GCD of 147 (= 252 – 105) and 105. Since the larger of the two numbers is reduced, repeating this process gives successively smaller numbers, so this repetition will necessarily stop sooner or later — when the numbers are equal (if the process is attempted once more, one of the numbers will become 0). +*/ + +#include + +int gcd_algorithm(int x, int y) +{ + if (y == 0) + { + return x; + } + else if (x >= y && y > 0) + { + return gcd_algorithm(y, (x % y)); + } +} + +int main(void) +{ + int num1, num2, gcd; + printf("\nEnter two numbers to find gcd using Euclidean algorithm: "); + scanf("%d%d", &num1, &num2); + gcd = gcd_algorithm(num1, num2); + if (gcd) + printf("\nThe GCD of %d and %d is %d\n", num1, num2, gcd); + else + printf("\nInvalid input!!!\n"); + return 0; +} \ No newline at end of file diff --git a/c/Numerical/C Program to Find Inverse of a Matrix.c b/c/Numerical/C Program to Find Inverse of a Matrix.c new file mode 100644 index 0000000..bd45fdd --- /dev/null +++ b/c/Numerical/C Program to Find Inverse of a Matrix.c @@ -0,0 +1,129 @@ +#include +#include +float determinant(float [][25], float); +void cofactor(float [][25], float); +void transpose(float [][25], float [][25], float); +int main() +{ + float a[25][25], k, d; + int i, j; + printf("Enter the order of the Matrix : "); + scanf("%f", &k); + printf("Enter the elements of %.0fX%.0f Matrix : \n", k, k); + for (i = 0; i < k; i++) + { + for (j = 0; j < k; j++) + { + scanf("%f", &a[i][j]); + } + } + d = determinant(a, k); + if (d == 0) + printf("\nInverse of Entered Matrix is not possible\n"); + else + cofactor(a, k); +} + +/*For calculating Determinant of the Matrix */ +float determinant(float a[25][25], float k) +{ + float s = 1, det = 0, b[25][25]; + int i, j, m, n, c; + if (k == 1) + { + return (a[0][0]); + } + else + { + det = 0; + for (c = 0; c < k; c++) + { + m = 0; + n = 0; + for (i = 0; i < k; i++) + { + for (j = 0 ; j < k; j++) + { + b[i][j] = 0; + if (i != 0 && j != c) + { + b[m][n] = a[i][j]; + if (n < (k - 2)) + n++; + else + { + n = 0; + m++; + } + } + } + } + det = det + s * (a[0][c] * determinant(b, k - 1)); + s = -1 * s; + } + } + return (det); +} + +void cofactor(float num[25][25], float f) +{ + float b[25][25], fac[25][25]; + int p, q, m, n, i, j; + for (q = 0; q < f; q++) + { + for (p = 0; p < f; p++) + { + m = 0; + n = 0; + for (i = 0; i < f; i++) + { + for (j = 0; j < f; j++) + { + if (i != q && j != p) + { + b[m][n] = num[i][j]; + if (n < (f - 2)) + n++; + else + { + n = 0; + m++; + } + } + } + } + fac[q][p] = pow(-1, q + p) * determinant(b, f - 1); + } + } + transpose(num, fac, f); +} +/*Finding transpose of matrix*/ +void transpose(float num[25][25], float fac[25][25], float r) +{ + int i, j; + float b[25][25], inverse[25][25], d; + for (i = 0; i < r; i++) + { + for (j = 0; j < r; j++) + { + b[i][j] = fac[j][i]; + } + } + d = determinant(num, r); + for (i = 0; i < r; i++) + { + for (j = 0; j < r; j++) + { + inverse[i][j] = b[i][j] / d; + } + } + printf("\n\n\nThe inverse of matrix is : \n"); + for (i = 0; i < r; i++) + { + for (j = 0; j < r; j++) + { + printf("\t%f", inverse[i][j]); + } + printf("\n"); + } +} \ No newline at end of file diff --git a/c/Numerical/C Program to Find the GCD and LCM of n Numbers.c b/c/Numerical/C Program to Find the GCD and LCM of n Numbers.c new file mode 100644 index 0000000..9ba1e1b --- /dev/null +++ b/c/Numerical/C Program to Find the GCD and LCM of n Numbers.c @@ -0,0 +1,41 @@ +#include +#include +#include + +int gcd(int x, int y) +{ + int r = 0, a, b; + a = (x > y) ? x : y; // a is greater number + b = (x < y) ? x : y; // b is smaller number + r = b; + while (a % b != 0) + { + r = a % b; + a = b; + b = r; + } + return r; +} + +int lcm(int x, int y) +{ + int a; + a = (x > y) ? x : y; // a is greater number + while (1) + { + if (a % x == 0 && a % y == 0) + return a; + ++a; + } +} + +int main(int argc, char **argv) +{ + printf("Enter the two numbers: "); + int x, y; + scanf("%d", &x); + scanf("%d", &y); + printf("The GCD of two numbers is: %d", gcd(x, y)); + printf("The LCM of two numbers is: %d", lcm(x, y)); + return 0; +} \ No newline at end of file diff --git a/c/Numerical/C Program to Generate N Number of Passwords of Length M Each.c b/c/Numerical/C Program to Generate N Number of Passwords of Length M Each.c new file mode 100644 index 0000000..b758ad0 --- /dev/null +++ b/c/Numerical/C Program to Generate N Number of Passwords of Length M Each.c @@ -0,0 +1,30 @@ +#include +#include +#include + +int main(void) +{ + /* Length of the password */ + int length; + int num; + int temp; + printf("Enter the length of the password: "); + scanf("%d", &length); + printf("\nEnter the number of passwords you want: "); + scanf("%d", &num); + /* Seed number for rand() */ + srand((unsigned int) time(0) + getpid()); + while(num--) + { + temp = length; + printf("\n"); + while(temp--) + { + putchar(rand() % 56 + 65); + srand(rand()); + } + temp = length; + } + printf("\n"); + return EXIT_SUCCESS; +} \ No newline at end of file diff --git a/c/Numerical/C Program to Generate Prime Numbers Between a Given Range Using the Sieve of Sundaram.c b/c/Numerical/C Program to Generate Prime Numbers Between a Given Range Using the Sieve of Sundaram.c new file mode 100644 index 0000000..bbc55ac --- /dev/null +++ b/c/Numerical/C Program to Generate Prime Numbers Between a Given Range Using the Sieve of Sundaram.c @@ -0,0 +1,54 @@ +#include + +int main() +{ + int arraySize, i, j, x; + int numberPrimes = 0; + printf("Input a positive integer to find all the prime numbers up to and including that number: "); + scanf("%d", &arraySize); + int n = arraySize / 2; + int size; + /* array to start off with that will eventually get + all the composite numbers removed and the remaining + ones output to the screen */ + int isPrime[arraySize + 1]; + int TheseArePrime = 0; + for (i = 0; i < n; ++i) + { + isPrime[i] = i; + } + for (i = 1; i < n; i++) + { + for (j = i; j <= (n - i) / (2 * i + 1); j++) + { + isPrime[i + j + 2 * i * j] = 0;/*From this list, remove all + numbers of the form i + j + 2ij */ + } + } + if (arraySize > 2) + { + isPrime[TheseArePrime++] = 2;/*this IF statement adds 2 to the output */ + } + for (i = 1; i < n; i++) + { + if (isPrime[i] != 0) + { + isPrime[TheseArePrime++] = i * 2 + 1; + } + } + size = sizeof isPrime / sizeof(int);//total size of array/size of array data type + for (x = 0; x <= size; x++) + { + if (isPrime[x] != 0) + { + printf("%d \t", isPrime[x]); + numberPrimes++;// the counter of the number of primes found + } + else + { + break; + } + } + printf("\nNumber of Primes: %d", numberPrimes); + return 0; +} \ No newline at end of file diff --git a/c/Numerical/C Program to Generate Random Hexadecimal Bytes.c b/c/Numerical/C Program to Generate Random Hexadecimal Bytes.c new file mode 100644 index 0000000..d16adcc --- /dev/null +++ b/c/Numerical/C Program to Generate Random Hexadecimal Bytes.c @@ -0,0 +1,19 @@ +#include +#include +#include + +int main(void) +{ + int length; + char str[] = "0123456789ABCDEF"; + /* Seed number for rand() */ + srand((unsigned int) time(0) + getpid()); + length = rand() % 15 + 8; + while(length--) + { + putchar(str[rand() % 16]); + srand(rand()); + } + printf("\n"); + return EXIT_SUCCESS; +} \ No newline at end of file diff --git a/c/Numerical/C Program to Generate Random Numbers Using Middle Square Method.c b/c/Numerical/C Program to Generate Random Numbers Using Middle Square Method.c new file mode 100644 index 0000000..722ffb1 --- /dev/null +++ b/c/Numerical/C Program to Generate Random Numbers Using Middle Square Method.c @@ -0,0 +1,53 @@ +#include +#include +#include +unsigned long long int randm(int n); +unsigned long long int von(unsigned long long int x, int n); + +int main(void) +{ + unsigned long long int x, s; + int n, i, r; + printf("Enter the number of digits in the seed value "); + scanf("%d", &n); + printf("\nEnter the total number of random numbers to be generated "); + scanf("%d", &r); + if (n >= 12) + { + printf("TOO LARGE!!"); + exit(0); + } + x = randm(n); + for(i = 0; i < r; i++) + { + s = von(x, n); + x = s; + printf("\nRandom Number generated: %lld\n", s); + } + return 0; +} + + +/*Generating Random Number of desired digit*/ + +unsigned long long int randm(int n) +{ + double x; + unsigned long long int y; + srand(getpid()); + x = rand() / (double)RAND_MAX; + y = (unsigned long long int) (x * pow(10.0, n*1.0)); + return y; +} + + +/*Calculating Random Number By Von Neumann Middle Square method*/ + +unsigned long long int von(unsigned long long int x, int n) +{ + unsigned long long int y; + int k; + k = n / 2; + y =(unsigned long long int)((x / pow(10.0, k * 1.0)) * x) % (unsigned long long int) (pow(10.0, n * 1.0)); + return y; +} \ No newline at end of file diff --git a/c/Numerical/C Program to Generate Random Numbers Using Multiply with Carry Method.c b/c/Numerical/C Program to Generate Random Numbers Using Multiply with Carry Method.c new file mode 100644 index 0000000..a0a5d4b --- /dev/null +++ b/c/Numerical/C Program to Generate Random Numbers Using Multiply with Carry Method.c @@ -0,0 +1,27 @@ +#include +#include +#include +static unsigned long Q[4096], c = 362436; +/* choose random initial c<809430660 and */ +/* 4096 random 32-bit integers for Q[] */ +unsigned long mwc(void) +{ + unsigned long long t, a = 18782LL; + static unsigned long i = 4095; + unsigned long x, r = 0xfffffffe; + i= (i+1)&4095; + t = a * Q[i] + c; + c=(t >> 32); + x = t + c; + if(x < c) + { + x++; + c++; + } + return (Q[i] = r - x); +} +int main(void) +{ + printf("\nRandom Number generated : %lld\n", mwc()); + return 0; +} \ No newline at end of file diff --git a/c/Numerical/C Program to Generate Random Numbers Using Probability Distribution Function.c b/c/Numerical/C Program to Generate Random Numbers Using Probability Distribution Function.c new file mode 100644 index 0000000..fd6d1cf --- /dev/null +++ b/c/Numerical/C Program to Generate Random Numbers Using Probability Distribution Function.c @@ -0,0 +1,27 @@ +#include +#include +#include +#include +#include + +//This is a sample program to generate a random numbers based on probability desity function of spiner +//pdf(x) = 1 if x>360 +// = 0 if x<0 +// = x/360 otherwise +int N = 10; +int main(int argc, char **argv) +{ + int p = 0, i; + for (i = 0; i < N; i++) + { + p = rand() % 400; + if (p > 360) + printf("%d ", 0); + else if (p < 0) + printf("%d ", 0); + else + printf("%f ", p * 0.1 / 360); + } + printf("..."); + return 0; +} \ No newline at end of file diff --git a/c/Numerical/C Program to Generate Randomized Sequence of Given Range of Numbers.c b/c/Numerical/C Program to Generate Randomized Sequence of Given Range of Numbers.c new file mode 100644 index 0000000..5a00b7b --- /dev/null +++ b/c/Numerical/C Program to Generate Randomized Sequence of Given Range of Numbers.c @@ -0,0 +1,21 @@ +#include +#include +#include + +const int LOW = 1; +const int HIGH = 32000; + +int main() +{ + int randomNumber, i; + time_t seconds; + time(&seconds); + srand((unsigned int) seconds); + for (i = 0; i < 10; i++) + { + randomNumber = rand() % (HIGH - LOW + 1) + LOW; + printf("%d ", randomNumber); + } + printf("..."); + return 0; +} \ No newline at end of file diff --git a/c/Numerical/C Program to Implement Booth’s Multiplication Algorithm for Multiplication of 2 signed Numbers.c b/c/Numerical/C Program to Implement Booth’s Multiplication Algorithm for Multiplication of 2 signed Numbers.c new file mode 100644 index 0000000..bd7f409 --- /dev/null +++ b/c/Numerical/C Program to Implement Booth’s Multiplication Algorithm for Multiplication of 2 signed Numbers.c @@ -0,0 +1,204 @@ +#include +#include + +int a = 0,b = 0, c = 0, a1 = 0, b1 = 0, com[5] = { 1, 0, 0, 0, 0}; +int anum[5] = {0}, anumcp[5] = {0}, bnum[5] = {0}; +int acomp[5] = {0}, bcomp[5] = {0}, pro[5] = {0}, res[5] = {0}; + +void binary() +{ + a1 = fabs(a); + b1 = fabs(b); + int r, r2, i, temp; + for (i = 0; i < 5; i++) + { + r = a1 % 2; + a1 = a1 / 2; + r2 = b1 % 2; + b1 = b1 / 2; + anum[i] = r; + anumcp[i] = r; + bnum[i] = r2; + if(r2 == 0) + { + bcomp[i] = 1; + } + if(r == 0) + { + acomp[i] =1; + } + } + //part for two's complementing + c = 0; + for ( i = 0; i < 5; i++) + { + res[i] = com[i]+ bcomp[i] + c; + if(res[i] >= 2) + { + c = 1; + } + else + c = 0; + res[i] = res[i] % 2; + } + for (i = 4; i >= 0; i--) + { + bcomp[i] = res[i]; + } + //in case of negative inputs + if (a < 0) + { + c = 0; + for (i = 4; i >= 0; i--) + { + res[i] = 0; + } + for ( i = 0; i < 5; i++) + { + res[i] = com[i] + acomp[i] + c; + if (res[i] >= 2) + { + c = 1; + } + else + c = 0; + res[i] = res[i]%2; + } + for (i = 4; i >= 0; i--) + { + anum[i] = res[i]; + anumcp[i] = res[i]; + } + } + if(b < 0) + { + for (i = 0; i < 5; i++) + { + temp = bnum[i]; + bnum[i] = bcomp[i]; + bcomp[i] = temp; + } + } +} +void add(int num[]) +{ + int i; + c = 0; + for ( i = 0; i < 5; i++) + { + res[i] = pro[i] + num[i] + c; + if (res[i] >= 2) + { + c = 1; + } + else + { + c = 0; + } + res[i] = res[i]%2; + } + for (i = 4; i >= 0; i--) + { + pro[i] = res[i]; + printf("%d",pro[i]); + } + printf(":"); + for (i = 4; i >= 0; i--) + { + printf("%d", anumcp[i]); + } +} +void arshift() //for arithmetic shift right +{ + int temp = pro[4], temp2 = pro[0], i; + for (i = 1; i < 5 ; i++) //shift the MSB of product + { + pro[i-1] = pro[i]; + } + pro[4] = temp; + for (i = 1; i < 5 ; i++) //shift the LSB of product + { + anumcp[i-1] = anumcp[i]; + } + anumcp[4] = temp2; + printf("\nAR-SHIFT: ");//display together + for (i = 4; i >= 0; i--) + { + printf("%d",pro[i]); + } + printf(":"); + for(i = 4; i >= 0; i--) + { + printf("%d", anumcp[i]); + } +} + +void main() +{ + int i, q = 0; + printf("\t\tBOOTH'S MULTIPLICATION ALGORITHM"); + printf("\nEnter two numbers to multiply: "); + printf("\nBoth must be less than 16"); + //simulating for two numbers each below 16 + do + { + printf("\nEnter A: "); + scanf("%d",&a); + printf("Enter B: "); + scanf("%d", &b); + } + while(a >=16 || b >=16); + printf("\nExpected product = %d", a * b); + binary(); + printf("\n\nBinary Equivalents are: "); + printf("\nA = "); + for (i = 4; i >= 0; i--) + { + printf("%d", anum[i]); + } + printf("\nB = "); + for (i = 4; i >= 0; i--) + { + printf("%d", bnum[i]); + } + printf("\nB'+ 1 = "); + for (i = 4; i >= 0; i--) + { + printf("%d", bcomp[i]); + } + printf("\n\n"); + for (i = 0; i < 5; i++) + { + if (anum[i] == q) //just shift for 00 or 11 + { + printf("\n-->"); + arshift(); + q = anum[i]; + } + else if(anum[i] == 1 && q == 0) //subtract and shift for 10 + { + printf("\n-->"); + printf("\nSUB B: "); + add(bcomp);//add two's complement to implement subtraction + arshift(); + q = anum[i]; + } + else //add ans shift for 01 + { + printf("\n-->"); + printf("\nADD B: "); + add(bnum); + arshift(); + q = anum[i]; + } + } + printf("\nProduct is = "); + for (i = 4; i >= 0; i--) + { + printf("%d", pro[i]); + } + for (i = 4; i >= 0; i--) + { + printf("%d", anumcp[i]); + } +} \ No newline at end of file diff --git a/c/Numerical/C Program to Implement Coppersmith Freivald’s Algorithm.c b/c/Numerical/C Program to Implement Coppersmith Freivald’s Algorithm.c new file mode 100644 index 0000000..7340267 --- /dev/null +++ b/c/Numerical/C Program to Implement Coppersmith Freivald’s Algorithm.c @@ -0,0 +1,99 @@ +#include +#include +#include +int main(int argc, char **argv) +{ + int i, j, k; + printf("Enter the dimension of the matrices: "); + int n; + scanf("%d", &n); + printf("Enter the 1st matrix: "); + double a[n][n]; + for (i = 0; i < n; i++) + { + for (j = 0; j < n; j++) + { + scanf("%f", &a[i][j]); + } + } + printf("Enter the 2nd matrix: "); + double b[n][n]; + for (i = 0; i < n; i++) + { + for (j = 0; j < n; j++) + { + scanf("%f", &b[i][j]); + } + } + printf("Enter the result matrix: "); + double c[n][n]; + for (i = 0; i < n; i++) + { + for (j = 0; j < n; j++) + { + scanf("%f", &c[i][j]); + } + } + //random generation of the r vector containing only 0/1 as its elements + double r[n][1]; + for (i = 0; i < n; i++) + { + r[i][0] = rand() % 2; + printf("%f ", r[i][0]); + } + //test A * (b*r) - (C*) = 0 + double br[n][1]; + for (i = 0; i < n; i++) + { + for (j = 0; j < 1; j++) + { + for (k = 0; k < n; k++) + { + br[i][j] = br[i][j] + b[i][k] * r[k][j]; + } + } + } + double cr[n][1]; + for (i = 0; i < n; i++) + { + for (j = 0; j < 1; j++) + { + for (k = 0; k < n; k++) + { + cr[i][j] = cr[i][j] + c[i][k] * r[k][j]; + } + } + } + double abr[n][1]; + for (i = 0; i < n; i++) + { + for (j = 0; j < 1; j++) + { + for (k = 0; k < n; k++) + { + abr[i][j] = abr[i][j] + a[i][k] * br[k][j]; + } + } + } + // br = multiplyVector(b, r, n); + // cr = multiplyVector(c, r, n); + // abr = multiplyVector(a, br, n); + //abr-cr + for (i = 0; i < n; i++) + { + abr[i][0] -= cr[i][0]; + } + int flag = 1; + for (i = 0; i < n; i++) + { + if (abr[i][0] == 0) + continue; + else + flag = 0; + } + if (flag == 1) + printf("Yes"); + else + printf("No"); + return 0; +} \ No newline at end of file diff --git a/c/Numerical/C Program to Implement Fisher-Yates Algorithm for Array Shuffling.c b/c/Numerical/C Program to Implement Fisher-Yates Algorithm for Array Shuffling.c new file mode 100644 index 0000000..f60206f --- /dev/null +++ b/c/Numerical/C Program to Implement Fisher-Yates Algorithm for Array Shuffling.c @@ -0,0 +1,44 @@ +/* +This C program implements Fisher-Yates algorithm for array shuffling. The Fisher–Yates shuffle (named after Ronald Fisher and Frank Yates), also known as the Knuth shuffle (after Donald Knuth), is an algorithm for generating a random permutation of a finite set—in plain terms, for randomly shuffling the set. A variant of the Fisher–Yates shuffle, known as Sattolo’s algorithm, may be used to generate random cycles of length n instead. The Fisher–Yates shuffle is unbiased, so that every permutation is equally likely. The modern version of the algorithm is also rather efficient, requiring only time proportional to the number of items being shuffled and no additional storage space +*/ + +#include +#include +#include + + +static int rand_int(int n) +{ + int limit = RAND_MAX - RAND_MAX % n; + int rnd; + do + { + rnd = rand(); + } + while (rnd >= limit); + return rnd % n; +} + +void shuffle(int *array, int n) +{ + int i, j, tmp; + for (i = n - 1; i > 0; i--) + { + j = rand_int(i + 1); + tmp = array[j]; + array[j] = array[i]; + array[i] = tmp; + } +} +int main(void) +{ + int i = 0; + int numbers[50]; + for (i = 0; i < 50; i++) + numbers[i]= i; + shuffle(numbers, 50); + printf("\nArray after shuffling is: \n"); + for ( i = 0; i < 50; i++) + printf("%d\n", numbers[i]); + return 0; +} \ No newline at end of file diff --git a/c/Numerical/C Program to Implement Gauss Jordan Elimination Method.c b/c/Numerical/C Program to Implement Gauss Jordan Elimination Method.c new file mode 100644 index 0000000..3595c68 --- /dev/null +++ b/c/Numerical/C Program to Implement Gauss Jordan Elimination Method.c @@ -0,0 +1,46 @@ +#include + +void solution( int a[][20], int var ); +int main() +{ + int a[ 20 ][ 20 ], var, i, j, k, l, n; + printf( "\nEnter the number of variables:\n" ); + scanf( "%d", &var ); + for ( i = 0; i < var; i++ ) + { + printf( "\nEnter the equation%d:\n", i + 1 ); + for ( j = 0; j < var; j++ ) + { + printf( "Enter the coefficient of x%d:\n", j + 1 ); + scanf( "%d", &a[ i ][ j ] ); + } + printf( "\nEnter the constant:\n" ); + scanf( "%d", &a[ i ][ var] ); + } + solution( a, var ); + return 0; +} + + + +void solution( int a[ 20 ][ 20 ], int var ) +{ + int k, i, l, j; + for ( k = 0; k < var; k++ ) + { + for ( i = 0; i <= var; i++ ) + { + l = a[ i ][ k ]; + for ( j = 0; j <= var; j++ ) + { + if ( i != k ) + a[i][j] = (a[k][k]*a[i][j])-(l*a[k][j]); + } + } + } + printf( "\nSolutions:" ); + for ( i = 0; i < var; i++ ) + { + printf( "\nTHE VALUE OF x%d IS %f\n", i + 1, ( float ) a[ i ][ var ] / ( float ) a[ i ][ i ] ); + } +} \ No newline at end of file diff --git a/c/Numerical/C Program to Implement Gauss Seidel Method.c b/c/Numerical/C Program to Implement Gauss Seidel Method.c new file mode 100644 index 0000000..451d490 --- /dev/null +++ b/c/Numerical/C Program to Implement Gauss Seidel Method.c @@ -0,0 +1,33 @@ +#include + +int main() +{ +//a sparse way of representing the equations + float eq[3][4]; + int i; + float x,y, z; + x = 1; + y = 1; + z = 2; //initial guess + eq[0][0] = 7/4.0; + eq[0][1] = 0; + eq[0][2] = 1/4.0; + eq[0][3]= -1/4.0; + eq[1][0] = 21/8.0; + eq[1][1] = 4/8.0; + eq[1][2] = 0; + eq[1][3]= 1/8.0; + eq[2][0] = 15/5.0; + eq[2][1] = 2/5.0; + eq[2][2] = -1/5.0; + eq[2][3]= 0; +//10 iterations of gauss-seidel + for (i = 0; i < 10; i++) + { + x = eq[0][0] + eq[0][2] * y + eq[0][3] * z; + y = eq[1][0] + eq[1][1] * x + eq[1][3] * z; + z = eq[2][0] + eq[2][1] * x + eq[2][2] * y; + printf("Output: \n%f %f %f\n", x, y, z); + } + return 0; +} \ No newline at end of file diff --git a/c/Numerical/C Program to Implement Naor-Reingold Pseudo Random Function.c b/c/Numerical/C Program to Implement Naor-Reingold Pseudo Random Function.c new file mode 100644 index 0000000..30f6a7e --- /dev/null +++ b/c/Numerical/C Program to Implement Naor-Reingold Pseudo Random Function.c @@ -0,0 +1,25 @@ +#include +#include +#include +#include + +int main(int argc, char **argv) +{ + int p = 7, l = 3, g = 2, n = 4, x, i, j, k; + int mul = 1; + int a[] = { 1, 2, 2, 1 }; + int bin[4]; + printf("The Random numbers are: "); + for (i = 0; i < 10; i++) + { + x = rand() % 16; + for (j = 3; j >= 0; j--) + { + bin[j] = x % 2; + x /= 2; + } + for (k = 0; k < 4; k++) + mul *= pow(a[k], bin[k]); + printf("%f ", pow(g, mul)); + } +} \ No newline at end of file diff --git a/c/Numerical/C Program to Implement Park-Miller Random Number Generation Algorithm.c b/c/Numerical/C Program to Implement Park-Miller Random Number Generation Algorithm.c new file mode 100644 index 0000000..2f645c3 --- /dev/null +++ b/c/Numerical/C Program to Implement Park-Miller Random Number Generation Algorithm.c @@ -0,0 +1,40 @@ +#include +#include +#include +#include + +#define RNG_M 2147483647L /* m = 2^31 - 1 */ +#define RNG_A 16807L +#define RNG_Q 127773L /* m div a */ +#define RNG_R 2836L /* m mod a */ + +/* 32 bit seed */ +static long rnd_seed; + +void set_rnd_seed (long seedval) +{ + /* set seed to value between 1 and m-1 */ + rnd_seed = (seedval % (RNG_M - 1)) + 1; +} + +/* returns a pseudo-random number from set 1, 2, ..., RNG_M - 1 */ +long rnd() +{ + register long low, high, test; + set_rnd_seed( (unsigned int) time(0) + getpid()); + high = rnd_seed / RNG_Q; + low = rnd_seed % RNG_Q; + test = RNG_A * low - RNG_R * high; + if (test > 0) + rnd_seed = test; + else + rnd_seed = test + RNG_M; + return rnd_seed; +} + + +int main(void) +{ + printf("Random number generated is %d\n", rnd()); + return 0; +} \ No newline at end of file diff --git a/c/Numerical/C Program to Implement Sieve of Atkin to Generate Prime Numbers Between Given Range.c b/c/Numerical/C Program to Implement Sieve of Atkin to Generate Prime Numbers Between Given Range.c new file mode 100644 index 0000000..38473fc --- /dev/null +++ b/c/Numerical/C Program to Implement Sieve of Atkin to Generate Prime Numbers Between Given Range.c @@ -0,0 +1,59 @@ +#include +#include + +int main() +{ + int limit; + int wlimit; + int i, j, k, x, y, z; + unsigned char *sieb; + printf("Please insert a number up to which all primes are calculated: "); + scanf("%d", &limit); + sieb = (unsigned char *) calloc(limit, sizeof(unsigned char)); + wlimit = sqrt(limit); + for (x = 1; x <= wlimit; x++) + { + for (y = 1; y <= wlimit; y++) + { + z = 4 * x * x + y * y; + if (z <= limit && (z % 60 == 1 || z % 60 == 13 || z % 60 == 17 || z + % 60 == 29 || z % 60 == 37 || z % 60 == 41 || z % 60 == 49 + || z % 60 == 53)) + { + sieb[z] = !sieb[z]; + } + z = 3 * x * x + y * y; + if (z <= limit && (z % 60 == 7 || z % 60 == 19 || z % 60 == 31 || z + % 60 == 43)) + { + sieb[z] = !sieb[z]; + } + z = 3 * x * x - y * y; + if (x > y && z <= limit && (z % 60 == 11 || z % 60 == 23 || z % 60 + == 47 || z % 60 == 59)) + { + sieb[z] = !sieb[z]; + } + } + } + for (i = 5; i <= wlimit; i++) + { + if (sieb[i] == 1) + { + for (j = 1; j * i * i <= limit; j++) + { + sieb[j * i * i] = 0; + } + } + } + printf("The following primes have been calculated:\n2\n3\n5"); + for (i = 5; i <= limit; i++) + { + if (sieb[i] == 1) + { + printf("\n%d", i); + } + } + scanf("%d", &i); + return 0; +} \ No newline at end of file diff --git a/c/Numerical/C Program to Implement Sieve of eratosthenes to Generate Prime Numbers Between Given Range.c b/c/Numerical/C Program to Implement Sieve of eratosthenes to Generate Prime Numbers Between Given Range.c new file mode 100644 index 0000000..b4bd327 --- /dev/null +++ b/c/Numerical/C Program to Implement Sieve of eratosthenes to Generate Prime Numbers Between Given Range.c @@ -0,0 +1,23 @@ +#include +#include + +#define limit 100 /*size of integers array*/ + +int main() +{ + unsigned long long int i,j; + int *primes; + int z = 1; + primes = malloc(sizeof(int) * limit); + for (i = 2; i < limit; i++) + primes[i] = 1; + for (i = 2; i < limit; i++) + if (primes[i]) + for (j = i; i * j < limit; j++) + primes[i * j] = 0; + printf("\nPrime numbers in range 1 to 100 are: \n"); + for (i = 2; i < limit; i++) + if (primes[i]) + printf("%d\n", i); + return 0; +} \ No newline at end of file diff --git a/c/Numerical/C Program to Implement Strassen’s Algorithm.c b/c/Numerical/C Program to Implement Strassen’s Algorithm.c new file mode 100644 index 0000000..e10226c --- /dev/null +++ b/c/Numerical/C Program to Implement Strassen’s Algorithm.c @@ -0,0 +1,70 @@ +/* +C code of two 2 by 2 matrix multiplication using Strassen's algorithm +*/ +#include +int main() +{ + int a[2][2], b[2][2], c[2][2], i, j; + int m1, m2, m3, m4, m5, m6, m7; + printf("Enter the 4 elements of first matrix: "); + for(i = 0; i < 2; i++) + for(j = 0; j < 2; j++) + scanf("%d", &a[i][j]); + printf("Enter the 4 elements of second matrix: "); + for(i = 0; i < 2; i++) + for(j = 0; j < 2; j++) + scanf("%d", &b[i][j]); + printf("\nThe first matrix is\n"); + for(i = 0; i < 2; i++) + { + printf("\n"); + for(j = 0; j < 2; j++) + printf("%d\t", a[i][j]); + } + printf("\nThe second matrix is\n"); + for(i = 0; i < 2; i++) + { + printf("\n"); + for(j = 0; j < 2; j++) + printf("%d\t", b[i][j]); + } + m1= (a[0][0] + a[1][1]) * (b[0][0] + b[1][1]); + m2= (a[1][0] + a[1][1]) * b[0][0]; + m3= a[0][0] * (b[0][1] - b[1][1]); + m4= a[1][1] * (b[1][0] - b[0][0]); + m5= (a[0][0] + a[0][1]) * b[1][1]; + m6= (a[1][0] - a[0][0]) * (b[0][0]+b[0][1]); + m7= (a[0][1] - a[1][1]) * (b[1][0]+b[1][1]); + c[0][0] = m1 + m4- m5 + m7; + c[0][1] = m3 + m5; + c[1][0] = m2 + m4; + c[1][1] = m1 - m2 + m3 + m6; + printf("\nAfter multiplication using Strassen's algorithm \n"); + for(i = 0; i < 2 ; i++) + { + printf("\n"); + for(j = 0; j < 2; j++) + printf("%d\t", c[i][j]); + } + return 0; +} + +/* +Enter the 4 elements of first matrix: +1 2 +3 4 +Enter the 4 elements of second matrix: +5 6 +7 8 +The first matrix is + +1 2 +3 4 +The second matrix is + +5 6 +7 8 +After multiplication using Strassen's algorithm + +19 22 +43 50 \ No newline at end of file diff --git a/c/Numerical/C Program to Implement the Bin Packing Algorithm.c b/c/Numerical/C Program to Implement the Bin Packing Algorithm.c new file mode 100644 index 0000000..0ee84c9 --- /dev/null +++ b/c/Numerical/C Program to Implement the Bin Packing Algorithm.c @@ -0,0 +1,42 @@ +/* +This is a C Program to implement Bin packing algorithm. This is a sample program to illustrate the Bin-Packing algorithm using next fit heuristics. In the bin packing problem, objects of different volumes must be packed into a finite number of bins or containers each of volume V in a way that minimizes the number of bins used. In computational complexity theory, it is a combinatorial NP-hard problem. +There are many variations of this problem, such as 2D packing, linear packing, packing by weight, packing by cost, and so on. They have many applications, such as filling up containers, loading trucks with weight capacity constraints, creating file backups in media and technology mapping in Field-programmable gate array semiconductor chip design. +*/ + +#include +void binPacking(int *a, int size, int n) +{ + int binCount = 1, i; + int s = size; + for (i = 0; i < n; i++) + { + if (s - *(a + i) > 0) + { + s -= *(a + i); + continue; + } + else + { + binCount++; + s = size; + i--; + } + } + printf("Number of bins required: %d", binCount); +} + +int main(int argc, char **argv) +{ + printf("Enter the number of items in Set: "); + int n; + int a[n], i; + int size; + scanf("%d", &n); + printf("Enter %d items:", n); + for (i = 0; i < n; i++) + scanf("%d", &a[i]); + printf("Enter the bin size: "); + scanf("%d", &size); + binPacking(a, size, n); + return 0; +} \ No newline at end of file diff --git a/c/Numerical/C Program to Implement the Rabin-Miller Primality Test to Check if a Given Number is Prime.c b/c/Numerical/C Program to Implement the Rabin-Miller Primality Test to Check if a Given Number is Prime.c new file mode 100644 index 0000000..a18ceca --- /dev/null +++ b/c/Numerical/C Program to Implement the Rabin-Miller Primality Test to Check if a Given Number is Prime.c @@ -0,0 +1,86 @@ +#include +#include +#include +/* + * calculates (a * b) % c taking into account that a * b might overflow + */ +long long mulmod(long long a, long long b, long long mod) +{ + long long x = 0,y = a % mod; + while (b > 0) + { + if (b % 2 == 1) + { + x = (x + y) % mod; + } + y = (y * 2) % mod; + b /= 2; + } + return x % mod; +} +/* + * modular exponentiation + */ +long long modulo(long long base, long long exponent, long long mod) +{ + long long x = 1; + long long y = base; + while (exponent > 0) + { + if (exponent % 2 == 1) + x = (x * y) % mod; + y = (y * y) % mod; + exponent = exponent / 2; + } + return x % mod; +} + +/* + * Miller-Rabin Primality test, iteration signifies the accuracy + */ +int Miller(long long p,int iteration) +{ + int i; + long long s; + if (p < 2) + { + return 0; + } + if (p != 2 && p % 2==0) + { + return 0; + } + s = p - 1; + while (s % 2 == 0) + { + s /= 2; + } + for (i = 0; i < iteration; i++) + { + long long a = rand() % (p - 1) + 1, temp = s; + long long mod = modulo(a, temp, p); + while (temp != p - 1 && mod != 1 && mod != p - 1) + { + mod = mulmod(mod, mod, p); + temp *= 2; + } + if (mod != p - 1 && temp % 2 == 0) + { + return 0; + } + } + return 1; +} +//Main +int main() +{ + int iteration = 5; + long long num; + printf("Enter integer to test primality: "); + scanf("%lld", &num); + if ( Miller( num, iteration)) + printf("\n%lld is prime\n", num); + else + printf("\n%lld is not prime\n", num); + return 0; +} \ No newline at end of file diff --git a/c/Numerical/C Program to Implement the Schonhage-Strassen Algorithm for Multiplication of Two Numbers.c b/c/Numerical/C Program to Implement the Schonhage-Strassen Algorithm for Multiplication of Two Numbers.c new file mode 100644 index 0000000..533fd6c --- /dev/null +++ b/c/Numerical/C Program to Implement the Schonhage-Strassen Algorithm for Multiplication of Two Numbers.c @@ -0,0 +1,67 @@ +/* +This is a C Program to multiply two given numbers using Schonhage-Strassen Algorithm. Suppose we are multiplying two numbers like 123 and 456 using long multiplication with base B digits, but without performing any carrying. The result might look something like this: +0 1 2 3 +× 4 5 6 +——————— +00 00 06 12 18 +00 05 10 15 00 +04 08 12 00 00 +——————— +04 13 28 27 18 +This sequence (4, 13, 28, 27, 18) is called the acyclic or linear convolution of the two original sequences (1,2,3) and (4,5,6). Once you have the acyclic convolution of two sequences, computing the product of the original numbers is easy: you just perform the carrying (for example, in the rightmost column, you’d keep the 8 and add the 1 to the column containing 27). In the example this yields the correct product 56088. +*/ + +int noOfDigit(long a) +{ + int n = 0; + while (a > 0) + { + a /= 10; + n++; + } + return n; +} +void schonhageStrassenMultiplication(long x, long y, int n, int m) +{ + int i, j; + int linearConvolution[n + m - 1]; + for (i = 0; i < (n + m - 1); i++) + linearConvolution[i] = 0; + long p = x; + for (i = 0; i < m; i++) + { + x = p; + for (j = 0; j < n; j++) + { + linearConvolution[i + j] += (y % 10) * (x % 10); + x /= 10; + } + y /= 10; + } + printf("The Linear Convolution is: ( "); + for (i = (n + m - 2); i >= 0; i--) + { + printf("%d ", linearConvolution[i]); + } + printf(")"); + long product = 0; + int nextCarry = 0, base = 1; + for (i = 0; i < n + m - 1; i++) + { + linearConvolution[i] += nextCarry; + product = product + (base * (linearConvolution[i] % 10)); + nextCarry = linearConvolution[i] / 10; + base *= 10; + } + printf("The Product of the numbers is: %ld", product); +} +int main(int argc, char **argv) +{ + printf("Enter the numbers:"); + long a, b; + scanf("%ld", &a); + scanf("%ld", &b); + int n = noOfDigit(a); + int m = noOfDigit(b); + schonhageStrassenMultiplication(a, b, n, m); +} \ No newline at end of file diff --git a/c/Numerical/C Program to Implement the linear congruential generator for Pseudo Random Number Generation.c b/c/Numerical/C Program to Implement the linear congruential generator for Pseudo Random Number Generation.c new file mode 100644 index 0000000..326baf7 --- /dev/null +++ b/c/Numerical/C Program to Implement the linear congruential generator for Pseudo Random Number Generation.c @@ -0,0 +1,39 @@ +#include + +/* always assuming int is at least 32 bits */ +int rand(); +int rseed = 0; + +inline void srand(int x) +{ + rseed = x; +} + +#ifndef MS_RAND +#define RAND_MAX ((1U << 31) - 1) + +inline int rand() +{ + return rseed = (rseed * 1103515245 + 12345) & RAND_MAX; +} + +#else /* MS rand */ + +#define RAND_MAX_32 ((1U << 31) - 1) +#define RAND_MAX ((1U << 15) - 1) + +inline int rand() +{ + return (rseed = (rseed * 214013 + 2531011) & RAND_MAX_32) >> 16; +} + +#endif/* MS_RAND */ + +int main() +{ + int i; + printf("rand max is %d\n", RAND_MAX); + for (i = 0; i < 10; i++) + printf("%d\n", rand()); + return 0; +} \ No newline at end of file diff --git a/c/Numerical/C Program to Implement wheel Sieve to Generate Prime Numbers Between Given Range.c b/c/Numerical/C Program to Implement wheel Sieve to Generate Prime Numbers Between Given Range.c new file mode 100644 index 0000000..f0a4aa9 --- /dev/null +++ b/c/Numerical/C Program to Implement wheel Sieve to Generate Prime Numbers Between Given Range.c @@ -0,0 +1,63 @@ +#include +#include + +#define MAX_NUM 50 +// array will be initialized to 0 being global +int primes[MAX_NUM]; + +void gen_sieve_primes(void) +{ + int p; + // mark all multiples of prime selected above as non primes + int c = 2; + int mul = p * c; + for (p = 2; p < MAX_NUM; p++) // for all elements in array + { + if (primes[p] == 0) // it is not multiple of any other prime + primes[p] = 1; // mark it as prime + for (; mul < MAX_NUM;) + { + primes[mul] = -1; + c++; + mul = p * c; + } + } +} + +void print_all_primes() +{ + int c = 0, i; + for (i = 0; i < MAX_NUM; i++) + { + if (primes[i] == 1) + { + c++; + if (c < 4) + { + switch (c) + { + case 1: + printf("%d st prime is: %d\n", c, i); + break; + case 2: + printf("%d nd prime is: %d\n", c, i); + break; + case 3: + printf("%d rd prime is: %d\n", c, i); + break; + default: + break; + } + } + else + printf("%d th prime is: %d\n", c, i); + } + } +} + +int main() +{ + gen_sieve_primes(); + print_all_primes(); + return 0; +} \ No newline at end of file diff --git a/c/Numerical/C Program to Optimize Wire Length in Electrical Circuit.c b/c/Numerical/C Program to Optimize Wire Length in Electrical Circuit.c new file mode 100644 index 0000000..7dd7a7c --- /dev/null +++ b/c/Numerical/C Program to Optimize Wire Length in Electrical Circuit.c @@ -0,0 +1,85 @@ +#include +#include + +#define V 9 + +int minDistance(int dist[], int sptSet[]) +{ + int min = INT_MAX, min_index; + int v; + for (v = 0; v < V; v++) + if (sptSet[v] == 0 && dist[v] <= min) + min = dist[v], min_index = v; + return min_index; +} + +int printSolution(int dist[], int n) +{ + printf("Vertex Distance from Source\n"); + int i; + for (i = 0; i < V; i++) + printf("%d \t\t %d\n", i, dist[i]); +} + +void shortestLength(int graph[V][V], int src) +{ + int dist[V]; + int i, count; + int sptSet[V]; + for (i = 0; i < V; i++) + { + dist[i] = INT_MAX; + sptSet[i] = 0; + } + dist[src] = 0; + for (count = 0; count < V - 1; count++) + { + int u = minDistance(dist, sptSet); + sptSet[u] = 1; + int v; + for (v = 0; v < V; v++) + if (!sptSet[v] && graph[u][v] && dist[u] != INT_MAX && dist[u] + + graph[u][v] < dist[v]) + dist[v] = dist[u] + graph[u][v]; + } + printSolution(dist, V); +} + +int main() +{ + printf( + "An electric circuit can be represented as Graph where components are nodes and wires are edges between them."); + int graph[V][V] = + { + { 0, 4, 0, 0, 0, 0, 0, 8, 0 }, + { 4, 0, 8, 0, 0, 0, 0, 11, 0 }, + { 0, 8, 0, 7, 0, 4, 0, 0, 2 }, + { 0, 0, 7, 0, 9, 14, 0, 0, 0 }, + { 0, 0, 0, 9, 0, 10, 0, 0, 0 }, + { 0, 0, 4, 0, 10, 0, 2, 0, 0 }, + { 0, 0, 0, 14, 0, 2, 0, 1, 6 }, + { 8, 11, 0, 0, 0, 0, 1, 0, 7 }, + { 0, 0, 2, 0, 0, 0, 6, 7, 0 } + }; + int c; + printf("Enter the component number from which you want to optimize wire lengths: "); + scanf("%d", &c); + printf("Optimized Lengths are: "); + shortestLength(graph, c); + return 0; +} + +/* +An electric circuit can be represented as Graph where components are nodes and wires are edges between them. +Enter the component number from which you want to optimize wire lengths: 3 +Optimized Lengths are: +Vertex Distance from Source +0 19 +1 15 +2 7 +3 0 +4 9 +5 11 +6 13 +7 14 +8 9 \ No newline at end of file diff --git a/c/Numerical/C Program to Perform Addition Operation Using Bitwise Operators.c b/c/Numerical/C Program to Perform Addition Operation Using Bitwise Operators.c new file mode 100644 index 0000000..9bc1775 --- /dev/null +++ b/c/Numerical/C Program to Perform Addition Operation Using Bitwise Operators.c @@ -0,0 +1,21 @@ +#include + +int bitwiseadd(int x, int y) +{ + while (y != 0) + { + int carry = x & y; + x = x ^ y; + y = carry << 1; + } + return x; +} + +int main() +{ + int num1, num2; + printf("\nEnter two numbers to perform addition using bitwise operators: "); + scanf("%d%d", &num1, &num2); + printf("\nSum is %d", bitwiseadd(num1, num2)); + return 0; +} \ No newline at end of file diff --git a/c/Numerical/C Program to Perform Complex Number Multiplication.c b/c/Numerical/C Program to Perform Complex Number Multiplication.c new file mode 100644 index 0000000..71afe94 --- /dev/null +++ b/c/Numerical/C Program to Perform Complex Number Multiplication.c @@ -0,0 +1,33 @@ +/* + * C Program to perform complex number multiplication + */ +#include +typedef struct COMPLEX +{ + int a; + int b; +} Complex; +Complex multiply(Complex, Complex); +int main() +{ + int a1, b1, a2, b2; + Complex x, y, z; + printf("Enter first complex number : "); + scanf("%d+%di", &a1, &b1); + printf("\nEnter second complex number : "); + scanf("%d+%di", &a2, &b2); + x.a = a1; + x.b = b1; + y.a = a2; + y.b = b2; + z = multiply(x, y); + printf("\nAfter multiplication: %d+%di", z.a, z.b); + return 0; +} +Complex multiply(Complex x, Complex y) +{ + Complex z; + z.a = x.a * y.a - x.b * y.b; + z.b = x.a * y.b + x.b * y.a; + return z; +} \ No newline at end of file diff --git a/c/Numerical/C Program to Perform Encoding of a Message Using Matrix Multiplication.c b/c/Numerical/C Program to Perform Encoding of a Message Using Matrix Multiplication.c new file mode 100644 index 0000000..87d4fc5 --- /dev/null +++ b/c/Numerical/C Program to Perform Encoding of a Message Using Matrix Multiplication.c @@ -0,0 +1,84 @@ +/* +Restriction: Input string has to be in lower case without any special characters +*/ +#include +#include +void mul(int first[3][3], int second[3][10], int result[3][10]) +{ + int c, d, sum, k; + int i, j; + for ( c = 0 ; c < 3 ; c++ ) + { + for ( d = 0 ; d < 10 ; d++ ) + { + sum = 0; + for ( k = 0 ; k < 3 ; k++ ) + { + sum = sum + first[c][k] * second[k][d]; + } + result[c][d] = sum; + } + } +} +int main() +{ + char str[29] = "this message is to be encoded"; + int len; + int i, j; + int result[3][10] = {0}; + int key[3][3] = + { + {-3, -3, -4}, + {0, 1, 1}, + {4, 3, 4} + }; + int inv_key[3][3] = + { + {1, 0, 1}, + {4, 4, 3}, + {-4, -3, -3} + }; + int encode[3][10] = {32}; + int decode[3][10] = {0}; + len = strlen(str); + for (i = 0; i < 10; i++) + { + for(j = 0; j < 3; j++) + { + if (str[j + i*3] >='a' && str[j + i*3] <='z') + { + encode[j][i] = str[j + i*3] - 96; + } + if (str[j + i*3] == 32) + { + encode[j][i] = 32; + } + if (str[j + i*3] == '\0') + break; + } + if (str[j + i*3] == '\0') + break; + } + mul( key, encode, result); + printf("\nEncoded message to be sent: "); + for (i = 0; i < 10; i++) + { + for ( j = 0 ; j < 3; j++) + printf("%d, ", result[j][i]); + } + printf("\nDecoded message is: "); + mul(inv_key, result, decode); + for (i = 0; i < 10; i++) + { + for ( j = 0; j < 3; j++) + { + if ( ((decode[j][i]+96)) >= 97 && ((decode[j][i]+96) <= 123)) + printf("%c", (decode[j][i] + 96) ); + else if ( decode[j][i] == 32) + printf(" "); + else + return; + } + } + return 0; +} \ No newline at end of file diff --git a/c/Numerical/C Program to Perform Fermat Primality Test.c b/c/Numerical/C Program to Perform Fermat Primality Test.c new file mode 100644 index 0000000..44e89c6 --- /dev/null +++ b/c/Numerical/C Program to Perform Fermat Primality Test.c @@ -0,0 +1,55 @@ +#include +#include + +#define ll long long +/* + * modular exponentiation + */ll modulo(ll base, ll exponent, ll mod) +{ + ll x = 1; + ll y = base; + while (exponent > 0) + { + if (exponent % 2 == 1) + x = (x * y) % mod; + y = (y * y) % mod; + exponent = exponent / 2; + } + return x % mod; +} + +/* + * Fermat's test for checking primality + */ +int Fermat(ll p, int iterations) +{ + int i; + if (p == 1) + { + return 0; + } + for (i = 0; i < iterations; i++) + { + ll a = rand() % (p - 1) + 1; + if (modulo(a, p - 1, p) != 1) + { + return 0; + } + } + return 1; +} +/* + * Main + */ +int main() +{ + int iteration = 50; + ll num; + printf("Enter integer to test primality: "); + scanf("%lld", &num); + if (Fermat(num, iteration) == 1) + printf("%lld is prime ", num); + else + printf("%lld is not prime ", num); + return 0; +} \ No newline at end of file diff --git a/c/Numerical/C Program to Perform LU Decomposition of any Matrix.c b/c/Numerical/C Program to Perform LU Decomposition of any Matrix.c new file mode 100644 index 0000000..b577f72 --- /dev/null +++ b/c/Numerical/C Program to Perform LU Decomposition of any Matrix.c @@ -0,0 +1,166 @@ +#include +#include +#include + +#define foreach(a, b, c) for (int a = b; a < c; a++) +#define for_i foreach(i, 0, n) +#define for_j foreach(j, 0, n) +#define for_k foreach(k, 0, n) +#define for_ij for_i for_j +#define for_ijk for_ij for_k +#define _dim int n +#define _swap(x, y) { typeof(x) tmp = x; x = y; y = tmp; } +#define _sum_k(a, b, c, s) { s = 0; foreach(k, a, b) s+= c; } + +typedef double **mat; + +#define _zero(a) mat_zero(a, n) +void mat_zero(mat x, int n) +{ + for_ij + x[i][j] = 0; +} + +#define _new(a) a = mat_new(n) +mat mat_new(_dim) +{ + mat x = malloc(sizeof(double*) * n); + x[0] = malloc(sizeof(double) * n * n); + for_i + x[i] = x[0] + n * i; + _zero(x); + return x; +} + +#define _copy(a) mat_copy(a, n) +mat mat_copy(void *s, _dim) +{ + mat x = mat_new(n); + for_ij + x[i][j] = ((double(*)[n]) s)[i][j]; + return x; +} + +#define _del(x) mat_del(x) +void mat_del(mat x) +{ + free(x[0]); + free(x); +} + +#define _QUOT(x) #x +#define QUOTE(x) _QUOT(x) +#define _show(a) printf(QUOTE(a)" =");mat_show(a, 0, n) +void mat_show(mat x, char *fmt, _dim) +{ + if (!fmt) + fmt = "%8.4g"; + for_i + { + printf(i ? " " : " [ "); + for_j { + printf(fmt, x[i][j]); + printf(j < n - 1 ? " " : i == n - 1 ? " ]\n" : "\n"); + } + } +} + +#define _mul(a, b) mat_mul(a, b, n) +mat mat_mul(mat a, mat b, _dim) +{ + mat c = _new(c); + for_ijk + c[i][j] += a[i][k] * b[k][j]; + return c; +} + +#define _pivot(a, b) mat_pivot(a, b, n) +void mat_pivot(mat a, mat p, _dim) +{ + for_ij + { + p[i][j] = (i == j); + } + for_i + { + int max_j = i; + foreach(j, i, n) + if (fabs(a[j][i]) > fabs(a[max_j][i])) + max_j = j; + + if (max_j != i) + for_k { + _swap(p[i][k], p[max_j][k]); + } + } +} + +#define _LU(a, l, u, p) mat_LU(a, l, u, p, n) +void mat_LU(mat A, mat L, mat U, mat P, _dim) +{ + _zero(L); + _zero(U); + _pivot(A, P); + mat Aprime = _mul(P, A); + for_i + { + L[i][i] = 1; + } + for_ij + { + double s; + if (j <= i) + { + _sum_k(0, j, L[j][k] * U[k][i], s) + U[j][i] = Aprime[j][i] - s; + } + if (j >= i) + { + _sum_k(0, i, L[j][k] * U[k][i], s); + L[j][i] = (Aprime[j][i] - s) / U[i][i]; + } + } + _del(Aprime); +} + +double A3[][3] = { { 1, 3, 5 }, { 2, 4, 7 }, { 1, 1, 0 } }; +double A4[][4] = { { 11, 9, 24, 2 }, { 1, 5, 2, 6 }, { 3, 17, 18, 1 }, { + 2, 5, + 7, 1 + } +}; + +int main() +{ + int n = 3; + mat A, L, P, U; + _new(L); + _new(P); + _new(U); + A = _copy(A3); + _LU(A, L, U, P); + _show(A); + _show(L); + _show(U); + _show(P); + _del(A); + _del(L); + _del(U); + _del(P); + printf("\n"); + n = 4; + _new(L); + _new(P); + _new(U); + A = _copy(A4); + _LU(A, L, U, P); + _show(A); + _show(L); + _show(U); + _show(P); + _del(A); + _del(L); + _del(U); + _del(P); + return 0; +} \ No newline at end of file diff --git a/c/Numerical/C Program to Perform Matrix Multiplication.c b/c/Numerical/C Program to Perform Matrix Multiplication.c new file mode 100644 index 0000000..4fd7b06 --- /dev/null +++ b/c/Numerical/C Program to Perform Matrix Multiplication.c @@ -0,0 +1,44 @@ +#include + +int main() +{ + int m, n, p, q, c, d, k, sum = 0; + int first[10][10], second[10][10], multiply[10][10]; + printf("Enter the number of rows and columns of first matrix\n"); + scanf("%d%d", &m, &n); + printf("Enter the elements of first matrix\n"); + for ( c = 0 ; c < m ; c++ ) + for ( d = 0 ; d < n ; d++ ) + scanf("%d", &first[c][d]); + printf("Enter the number of rows and columns of second matrix\n"); + scanf("%d%d", &p, &q); + if ( n != p ) + printf("Matrices with entered orders can't be multiplied with each other.\n"); + else + { + printf("Enter the elements of second matrix\n"); + for ( c = 0 ; c < p ; c++ ) + for ( d = 0 ; d < q ; d++ ) + scanf("%d", &second[c][d]); + for ( c = 0 ; c < m ; c++ ) + { + for ( d = 0 ; d < q ; d++ ) + { + for ( k = 0 ; k < p ; k++ ) + { + sum = sum + first[c][k]*second[k][d]; + } + multiply[c][d] = sum; + sum = 0; + } + } + printf("Product of entered matrices:-\n"); + for ( c = 0 ; c < m ; c++ ) + { + for ( d = 0 ; d < q ; d++ ) + printf("%d\t", multiply[c][d]); + printf("\n"); + } + } + return 0; +} \ No newline at end of file diff --git a/c/Numerical/C Program to Perform Optimal Paranthesization Using Dynamic Programming.c b/c/Numerical/C Program to Perform Optimal Paranthesization Using Dynamic Programming.c new file mode 100644 index 0000000..0b009fd --- /dev/null +++ b/c/Numerical/C Program to Perform Optimal Paranthesization Using Dynamic Programming.c @@ -0,0 +1,57 @@ +/* A naive recursive implementation that simply follows the above optimal + substructure property */ +#include +#include + +int MatrixChainOrder(int p[], int n) +{ + /* For simplicity of the program, one extra row and one extra column are + allocated in m[][]. 0th row and 0th column of m[][] are not used */ + int m[n][n]; + int s[n][n]; + int i, j, k, L, q; + /* m[i,j] = Minimum number of scalar multiplications needed to compute + the matrix A[i]A[i+1]...A[j] = A[i..j] where dimention of A[i] is + p[i-1] x p[i] */ + // cost is zero when multiplying one matrix. + for (i = 1; i < n; i++) + m[i][i] = 0; + // L is chain length. + for (L = 2; L < n; L++) + { + for (i = 1; i <= n - L + 1; i++) + { + j = i + L - 1; + m[i][j] = INT_MAX; + for (k = i; k <= j - 1; k++) + { + // q = cost/scalar multiplications + q = m[i][k] + m[k + 1][j] + p[i - 1] * p[k] * p[j]; + if (q < m[i][j]) + { + m[i][j] = q; + s[i][j] = k; + } + } + } + } + return m[1][n - 1]; +} +int main() +{ + printf( + "Enter the array p[], which represents the chain of matrices such that the ith matrix Ai is of dimension p[i-1] x p[i]"); + printf("Enter the total length:"); + int n; + scanf("%d", &n); + int array[n]; + printf("Enter the dimensions: "); + int var; + for (var = 0; var < n; ++var) + { + scanf("%d", array[var]); + } + printf("Minimum number of multiplications is: %d", + MatrixChainOrder(array, n)); + return 0; +} \ No newline at end of file diff --git a/c/Numerical/C Program to Perform Partition of an Integer in All Possible Ways.c b/c/Numerical/C Program to Perform Partition of an Integer in All Possible Ways.c new file mode 100644 index 0000000..be386ed --- /dev/null +++ b/c/Numerical/C Program to Perform Partition of an Integer in All Possible Ways.c @@ -0,0 +1,54 @@ +#include +void printarray(int p[], int n) +{ + int i; + for ( i = 0; i < n; i++) + printf("%d ", p[i]); + printf("\n"); +} + +void partition(int n) +{ + int p[n]; // An array to store a partition + int k = 0; // Index of last element in a partition + p[k] = n; // Initialize first partition as number itself + int rem_val; + // This loop first prints current partition, then generates next + // partition. The loop stops when the current partition has all 1s + while (1) + { + // print current partition + printarray(p, k+1); + rem_val = 0; + while (k >= 0 && p[k] == 1) + { + rem_val += p[k]; + k--; + } + // if k < 0, all the values are 1 so there are no more partitions + if (k < 0) return; + // Decrease the p[k] found above and adjust the rem_val + p[k]--; + rem_val++; + // If rem_val is more, then the sorted order is violated. Divide + // rem_val in different values of size p[k] and copy these values at + // different positions after p[k] + while (rem_val > p[k]) + { + p[k+1] = p[k]; + rem_val = rem_val - p[k]; + k++; + } + // Copy rem_val to next position and increment position + p[k+1] = rem_val; + k++; + } +} +int main() +{ + int num; + printf("\nEnter a number to perform integer partition: "); + scanf("%d", &num); + partition(num); + return 0; +} \ No newline at end of file diff --git a/c/Numerical/C Program to Perform a 2D FFT Inplace Given a Complex 2D Array.c b/c/Numerical/C Program to Perform a 2D FFT Inplace Given a Complex 2D Array.c new file mode 100644 index 0000000..47b0bf8 --- /dev/null +++ b/c/Numerical/C Program to Perform a 2D FFT Inplace Given a Complex 2D Array.c @@ -0,0 +1,71 @@ +#include +#include +#define PI 3.14159265 +int n; + +int main(int argc, char **argv) +{ + double realOut[n][n]; + double imagOut[n][n]; + double amplitudeOut[n][n]; + int height = n; + int width = n; + int yWave; + int xWave; + int ySpace; + int xSpace; + int i, j; + double inputData[n][n]; + printf("Enter the size: "); + scanf("%d", &n); + printf("Enter the 2D elements "); + for (i = 0; i < n; i++) + for (j = 0; j < n; j++) + scanf("%lf", &inputData[i][j]); + // Two outer loops iterate on output data. + for (yWave = 0; yWave < height; yWave++) + { + for (xWave = 0; xWave < width; xWave++) + { + // Two inner loops iterate on input data. + for (ySpace = 0; ySpace < height; ySpace++) + { + for (xSpace = 0; xSpace < width; xSpace++) + { + // Compute real, imag, and ampltude. + realOut[yWave][xWave] += (inputData[ySpace][xSpace] * cos( + 2 * PI * ((1.0 * xWave * xSpace / width) + (1.0 + * yWave * ySpace / height)))) / sqrt( + width * height); + imagOut[yWave][xWave] -= (inputData[ySpace][xSpace] * sin( + 2 * PI * ((1.0 * xWave * xSpace / width) + (1.0 + * yWave * ySpace / height)))) / sqrt( + width * height); + amplitudeOut[yWave][xWave] = sqrt( + realOut[yWave][xWave] * realOut[yWave][xWave] + + imagOut[yWave][xWave] + * imagOut[yWave][xWave]); + } + printf(" %e + %e i (%e)\n", realOut[yWave][xWave], + imagOut[yWave][xWave], amplitudeOut[yWave][xWave]); + } + } + } + return 0; +} + +/* +Enter the size: +2 +Enter the 2D elements +2 3 +4 2 + +2.5 + 0.0 i +5.5 + 0.0 i +-0.5 + -1.8369701987210297E-16 i +0.5 + -3.0616169978683826E-16 i +2.5 + 0.0 i +-0.5 + -3.6739403974420594E-16 i +-0.5 + -1.8369701987210297E-16 i +-1.5 + -1.8369701987210297E-16 i \ No newline at end of file diff --git a/c/Numerical/C Program to Perform the Unique Factorization of a Given Number.c b/c/Numerical/C Program to Perform the Unique Factorization of a Given Number.c new file mode 100644 index 0000000..8d56881 --- /dev/null +++ b/c/Numerical/C Program to Perform the Unique Factorization of a Given Number.c @@ -0,0 +1,54 @@ +#include +void printarray(int p[], int n) +{ + int i; + for (i = 0; i < n; i++) + printf("%d ", p[i]); + printf("\n"); +} +void partition(int n) +{ + int p[n]; // An array to store a partition + int k = 0; // Index of last element in a partition + p[k] = n; // Initialize first partition as number itself + int rem_val; + // This loop first prints current partition, then generates next + // partition. The loop stops when the current partition has all 1s + while (1) + { + // print current partition + printarray(p, k + 1); + rem_val = 0; + while (k >= 0 && p[k] == 1) + { + rem_val += p[k]; + k--; + } + // if k < 0, all the values are 1 so there are no more partitions + if (k < 0) + return; + // Decrease the p[k] found above and adjust the rem_val + p[k]--; + rem_val++; + // If rem_val is more, then the sorted order is violated. Divide + // rem_val in different values of size p[k] and copy these values at + // different positions after p[k] + while (rem_val > p[k]) + { + p[k + 1] = p[k]; + rem_val = rem_val - p[k]; + k++; + } + // Copy rem_val to next position and increment position + p[k + 1] = rem_val; + k++; + } +} +int main() +{ + int num; + printf("\nEnter a number to perform integer partition: "); + scanf("%d", &num); + partition(num); + return 0; +} \ No newline at end of file diff --git a/c/Numerical/C Program to Represent Linear Equations in Matrix Form.c b/c/Numerical/C Program to Represent Linear Equations in Matrix Form.c new file mode 100644 index 0000000..06ef09f --- /dev/null +++ b/c/Numerical/C Program to Represent Linear Equations in Matrix Form.c @@ -0,0 +1,34 @@ +#include +#include +int main(void) +{ + char var[] = { 'x', 'y', 'z', 'w' }; + printf("Enter the number of variables in the equations: "); + int n; + scanf("%d", &n); + printf("\nEnter the coefficients of each variable for each equations"); + printf("\nax + by + cz + ... = d"); + int mat[n][n]; + int constants[n][1]; + int i,j; + for (int i = 0; i < n; i++) + { + for (int j = 0; j < n; j++) + { + scanf("%d", &mat[i][j]); + } + scanf("%d", &constants[i][0]); + } + printf("Matrix representation is: "); + for (i = 0; i < n; i++) + { + for (j = 0; j < n; j++) + { + printf(" %f", mat[i][j]); + } + printf(" %f", var[i]); + printf(" = %f", constants[i][0]); + printf("\n"); + } + return 0; +} \ No newline at end of file diff --git a/c/Numerical/C Program to Solve Knapsack Problem Using Dynamic Programming.c b/c/Numerical/C Program to Solve Knapsack Problem Using Dynamic Programming.c new file mode 100644 index 0000000..dcb881a --- /dev/null +++ b/c/Numerical/C Program to Solve Knapsack Problem Using Dynamic Programming.c @@ -0,0 +1,36 @@ +#include + +int max(int a, int b) +{ + return (a > b)? a : b; +} +// Returns the maximum value that can be put in a knapsack of capacity W +int knapsack(int W, int wt[], int val[], int n) +{ + int i, w; + int K[n+1][W+1]; + // Build table K[][] in bottom up manner + for (i = 0; i <= n; i++) + { + for (w = 0; w <= W; w++) + { + if (i==0 || w==0) + K[i][w] = 0; + else if (wt[i-1] <= w) + K[i][w] = max(val[i-1] + K[i-1][w-wt[i-1]], K[i-1][w]); + else + K[i][w] = K[i-1][w]; + } + } + return K[n][W]; +} + +int main() +{ + int val[] = {60, 100, 120}; + int wt[] = {10, 20, 30}; + int W = 50; + int n = sizeof(val)/sizeof(val[0]); + printf("\nValue = %d", knapsack(W, wt, val, n)); + return 0; +} \ No newline at end of file diff --git a/c/Numerical/C Program to Solve any Linear Equation in One Variable.c b/c/Numerical/C Program to Solve any Linear Equation in One Variable.c new file mode 100644 index 0000000..553588f --- /dev/null +++ b/c/Numerical/C Program to Solve any Linear Equation in One Variable.c @@ -0,0 +1,16 @@ +#include +#include +float solve_for_y(float a, float b, float c) +{ + float Y = Y = -(b + c) / a; + return Y; +} +main() +{ + float a, b, c, Y; + printf("\nEnter a linear equation in one variable of the form aY + b + c = 0 "); + printf("\nEnter the value of a, b, c respectively: "); + scanf("%f%f%f", &a, &b, &c); + Y = solve_for_y(a, b, c); + printf("\nSolution is Y = %f", Y); +} \ No newline at end of file diff --git a/c/Numerical/C Program to Solve the 0-1 Knapsack Problem.c b/c/Numerical/C Program to Solve the 0-1 Knapsack Problem.c new file mode 100644 index 0000000..fe7e3a5 --- /dev/null +++ b/c/Numerical/C Program to Solve the 0-1 Knapsack Problem.c @@ -0,0 +1,95 @@ +#include +#include +#include + +typedef struct +{ + const char * name; + int weight, value; +} item_t; + +item_t item[] = +{ + {"map", 9, 150}, + {"compass", 13, 35}, + {"water", 153, 200}, + {"sandwich", 50, 160}, + {"glucose", 15, 60}, + {"tin", 68, 45}, + {"banana", 27, 60}, + {"apple", 39, 40}, + {"cheese", 23, 30}, + {"beer", 52, 10}, + {"suntancream", 11, 70}, + {"camera", 32, 30}, + {"T-shirt", 24, 15}, + {"trousers", 48, 10}, + {"umbrella", 73, 40}, + {"waterproof trousers", 42, 70}, + {"waterproof overclothes", 43, 75}, + {"note-case", 22, 80}, + {"sunglasses", 7, 20}, + {"towel", 18, 12}, + {"socks", 4, 50}, + {"book", 30, 10} +}; + +#define n_items (sizeof(item)/sizeof(item_t)) + +typedef struct +{ + uint32_t bits; /* 32 bits, can solve up to 32 items */ + int value; +} solution; + +void optimal(int weight, int idx, solution *s) +{ + solution v1, v2; + if (idx < 0) + { + s->bits = s->value = 0; + return; + } + if (weight < item[idx].weight) + { + optimal(weight, idx - 1, s); + return; + } + optimal(weight, idx - 1, &v1); + optimal(weight - item[idx].weight, idx - 1, &v2); + v2.value += item[idx].value; + v2.bits |= (1 << idx); + *s = (v1.value >= v2.value) ? v1 : v2; +} + +int main(void) +{ + int i = 0, w = 0; + solution s = {0, 0}; + optimal(400, n_items - 1, &s); + for (i = 0; i < n_items; i++) + { + if (s.bits & (1 << i)) + { + printf("%s\n", item[i].name); + w += item[i].weight; + } + } + printf("Total value: %d; weight: %d\n", s.value, w); + return 0; +} + +/* +map +compass +water +sandwich +glucose +banana +suntancream +waterproof trousers +waterproof overclothes +note-case +sunglasses +socks +Total value: 1030; weight: 396 \ No newline at end of file diff --git a/c/Numerical/C Program to Solve the Fractional Knapsack Problem.c b/c/Numerical/C Program to Solve the Fractional Knapsack Problem.c new file mode 100644 index 0000000..ad10e8b --- /dev/null +++ b/c/Numerical/C Program to Solve the Fractional Knapsack Problem.c @@ -0,0 +1,46 @@ +#include + +int n = 5; /* The number of objects */ +int c[10] = {12, 1, 2, 1, 4}; /* c[i] is the *COST* of the ith object; i.e. what + YOU PAY to take the object */ +int v[10] = {4, 2, 2, 1, 10}; /* v[i] is the *VALUE* of the ith object; i.e. + what YOU GET for taking the object */ +int W = 15; /* The maximum weight you can take */ + +void simple_fill() +{ + int cur_w; + float tot_v; + int i, maxi; + int used[10]; + for (i = 0; i < n; ++i) + used[i] = 0; /* I have not used the ith object yet */ + cur_w = W; + while (cur_w > 0) /* while there's still room*/ + { + /* Find the best object */ + maxi = -1; + for (i = 0; i < n; ++i) + if ((used[i] == 0) && + ((maxi == -1) || ((float)v[i]/c[i] > (float)v[maxi]/c[maxi]))) + maxi = i; + used[maxi] = 1; /* mark the maxi-th object as used */ + cur_w -= c[maxi]; /* with the object in the bag, I can carry less */ + tot_v += v[maxi]; + if (cur_w >= 0) + printf("Added object %d (%d$, %dKg) completely in the bag. Space left: %d.\n", maxi + 1, v[maxi], c[maxi], cur_w); + else + { + printf("Added %d%% (%d$, %dKg) of object %d in the bag.\n", (int)((1 + (float)cur_w/c[maxi]) * 100), v[maxi], c[maxi], maxi + 1); + tot_v -= v[maxi]; + tot_v += (1 + (float)cur_w/c[maxi]) * v[maxi]; + } + } + printf("Filled the bag with objects worth %.2f$.\n", tot_v); +} + +int main(int argc, char *argv[]) +{ + simple_fill(); + return 0; +} \ No newline at end of file diff --git a/c/Numerical/C Program to Use rand and srand Functions.c b/c/Numerical/C Program to Use rand and srand Functions.c new file mode 100644 index 0000000..d0b735e --- /dev/null +++ b/c/Numerical/C Program to Use rand and srand Functions.c @@ -0,0 +1,14 @@ +#include +#include +#include + +int main(void) +{ + int num; + /* Seed number for rand() */ + srand((unsigned int) time(0) + getpid()); + printf("\nGenerating a random number using srand and rand function.\n"); + num = rand(); + printf("%d\n", num); + return EXIT_SUCCESS; +} \ No newline at end of file diff --git a/c/Numerical/C program for BISECTION METHOD USING LOG10(X)-COS(X).c b/c/Numerical/C program for BISECTION METHOD USING LOG10(X)-COS(X).c new file mode 100644 index 0000000..11fcd49 --- /dev/null +++ b/c/Numerical/C program for BISECTION METHOD USING LOG10(X)-COS(X).c @@ -0,0 +1,109 @@ +#include +#include +#include +#define epsil 0.0001 + +int p,c[10]; + +void appro(); +void bisection(float,float,float,float); + +float fun(float x) +{ + int i; + float y=0.0; + y=log10(x)-cos(x); + return y; +} + +void main() +{ + int i; + clrscr(); + appro(); + getch(); +} + +void bisection(float x1,float x2,float fx1,float fx2) +{ + float x3,fx3; + int n=1; + if(fx1<0&&fx2>0||fx1>0&&fx2<0) + { + printf("******************************************************************\n"); + printf("\nIt x1 fx1 x2 fx2 x3 fx3\n"); + printf("******************************************************************\n"); + do + { + x3=(x1+x2)/2; + fx3=fun(x3); + if(fx3==0) + { + break; + } + if((fx1*fx3)>0) + { + x1=x3; + fx1=fx3; + } + else + { + x2=x3; + fx2=fx3; + } + printf("%d %.4f %.4f %.4f %.4f %.4f %.4f\n",n,x1,fx1,x2,fx2,x3,fx3); + n=n+1; + } + while((fabs(x1-x2)>epsil)&&(fx3!=0)); + printf("\n\t\t********************\n"); + printf("\n\t\tThe root is %.4f\n",x3); + printf("\t\t********************\n"); + } + else + { + clrscr(); + printf("\nError in the Initial approximation\n "); + printf("\nPlease enter right approximation\n\n"); + appro(); + } +} + +void appro() +{ + float x1,x2,x3,fx1,fx2,fx3; + printf("\nPlease Enter first approximation: "); + scanf("%f",&x1); + printf("\nPlease Enter first approximation: "); + scanf("%f",&x2); + fx1=fun(x1); + fx2=fun(x2); + bisection(x1,x2,fx1,fx2); +} +/*************************************OUTPUT************************************** + +Please Enter first approximation: 1 + +Please Enter first approximation: 2 +****************************************************************** + +It x1 fx1 x2 fx2 x3 fx3 +****************************************************************** +1 1.0000 -0.5403 1.5000 0.1054 1.5000 0.1054 +2 1.2500 -0.2184 1.5000 0.1054 1.2500 -0.2184 +3 1.3750 -0.0562 1.5000 0.1054 1.3750 -0.0562 +4 1.3750 -0.0562 1.4375 0.0247 1.4375 0.0247 +5 1.4062 -0.0157 1.4375 0.0247 1.4062 -0.0157 +6 1.4062 -0.0157 1.4219 0.0045 1.4219 0.0045 +7 1.4141 -0.0056 1.4219 0.0045 1.4141 -0.0056 +8 1.4180 -0.0006 1.4219 0.0045 1.4180 -0.0006 +9 1.4180 -0.0006 1.4199 0.0020 1.4199 0.0020 +10 1.4180 -0.0006 1.4189 0.0007 1.4189 0.0007 +11 1.4180 -0.0006 1.4185 0.0001 1.4185 0.0001 +12 1.4182 -0.0003 1.4185 0.0001 1.4182 -0.0003 +13 1.4183 -0.0001 1.4185 0.0001 1.4183 -0.0001 +14 1.4184 -0.0000 1.4185 0.0001 1.4184 -0.0000 + + ******************** + The root is 1.4184 + ******************** +************************************************************************/ \ No newline at end of file diff --git a/c/Numerical/C program for ADAM-BASHFORTH METHOD.c b/c/Numerical/C program for ADAM-BASHFORTH METHOD.c new file mode 100644 index 0000000..90397f6 --- /dev/null +++ b/c/Numerical/C program for ADAM-BASHFORTH METHOD.c @@ -0,0 +1,82 @@ +#include +#include +#include +#define MAX 20 + +float equation(float x,float y) +{ + return(1+(y*y)); +} + +void main() +{ + FILE *fp; + int i=0,count=-1; + float lower,upper,h,y1,xvalue[MAX],yvalue[MAX],result; + float function[MAX],search,final,temp; + fp=fopen("admbsh.dat","w"); + clrscr(); + printf("ADAM-BASHFORTH METHOD "); + fprintf(fp,"ADAM-BASHFORTH METHOD "); + printf("\n"); + fprintf(fp,"\n"); + printf("\nEnter the lower bound of x : "); + fprintf(fp,"\nEnter the lower bound of x : "); + scanf("%f",&lower); + fprintf(fp,"%f",lower); + printf("\nEnter the upper bound of x : "); + fprintf(fp,"\nEnter the upper bound of x : "); + scanf("%f",&upper); + fprintf(fp,"%f",upper); + printf("\nEnter the value of y(lower) : "); + fprintf(fp,"\nEnter the value of y(lower) : "); + scanf("%f",&y1); + fprintf(fp,"%f",y1); + printf("\nEnter the value of h : "); + fprintf(fp,"\nEnter the value of h : "); + scanf("%f",&h); + fprintf(fp,"%f",h); + printf("\nEnter the value of x for which you want to find y :"); + fprintf(fp,"\nEnter the value of x for which you want to find y :"); + scanf("%f",&search); + fprintf(fp,"%f",search); + xvalue[i]=lower; + yvalue[i]=y1; + for(i=0; xvalue[i]<=upper; i++) + { + xvalue[i+1]=xvalue[i]+h; + } + for(i=0; xvalue[i]<=upper; i++) + { + result=equation(xvalue[i],yvalue[i]); + yvalue[i+1]=yvalue[i]+(h*result); + } + printf("\n\n"); + fprintf(fp,"\n\n"); + printf("The table is "); + fprintf(fp,"The table is "); + printf("\n\n"); + fprintf(fp,"\n\n"); + printf(" i x y f(x,y) "); + fprintf(fp," i x y f(x,y) "); + printf("\n\n"); + fprintf(fp,"\n\n"); + for(i=0; xvalue[i]<=upper; i++) + { + function[i]=equation(xvalue[i],yvalue[i]); + printf(" %d. %.4f %.4f %.4f ",i,xvalue[i],yvalue[i],function[i]); + fprintf(fp," %d. %.4f %.4f %.4f ",i,xvalue[i],yvalue[i],function[i]); + count=count+1; + printf("\n"); + fprintf(fp,"\n"); + } + yvalue[search]=yvalue[count]+(h/24)*((-9*function[count-3])+(37*function[count-2])-(59*function[count-1])+(55*function[count])); + final=equation(search,yvalue[search]); + yvalue[search]=yvalue[count]+(h/24)*((function[count-2])-(5*function[count-1])+(19*function[count])+(9*final)); + printf("\n\n"); + fprintf(fp,"\n\n"); + printf("Approximate value is : %.4f ",yvalue[search]); + fprintf(fp,"Approximate value is : %.4f ",yvalue[search]); + fclose(fp); + getch(); +} \ No newline at end of file diff --git a/c/Numerical/C program for Graeffe Method.c b/c/Numerical/C program for Graeffe Method.c new file mode 100644 index 0000000..0122de0 --- /dev/null +++ b/c/Numerical/C program for Graeffe Method.c @@ -0,0 +1,48 @@ +#include +#include +#include +void main() +{ + float coe[10],sq[10],mul[10]= {0},ans[10],f_ans[10]; + float temp,div=0.5; + int c,po,ctr,ctr1,ctr2,N; + clrscr(); + printf("\nEnter the Highest Power::"); + flushall(); + scanf("%d",&po); + N=po; +//Scanning Equationfor(ctr=po;ctr>=0;ctr--) + { + printf("\nEnter the value of %d= ",ctr); + scanf("%f",&coe[ctr]); + } + do + { + c=po; +//Squaring the value:for(ctr=po;ctr>=0;ctr--) + { + sq[ctr]=coe[ctr]*coe[ctr]; + } +//Multiplying & placing in another arrayfor(ctr=po,ctr1=po-1;ctr>=0,ctr1>0;ctr--,ctr1--) + { + mul[ctr1]=(coe[ctr]*coe[ctr-2])*(-2); + } +//Adding the sq[] with mul[]for(ctr=po;ctr>=0;ctr--) + { + ans[ctr]=sq[ctr]+mul[ctr]; + } +//Dividing the valuesfor(ctr=0;ctr<=po;ctr++) + { + temp=ans[ctr]/ans[ctr+1]; + f_ans[ctr]=pow(temp,div); + } + for(ctr=0; ctr<=po; ctr++) + { + printf("\n%.4f",f_ans[ctr]); + } + div=div/2; + c--; + } + while(c!=0); + getch(); +} \ No newline at end of file diff --git a/c/Numerical/C program for SUCESSIVE APPROXIMATION METHOD.c b/c/Numerical/C program for SUCESSIVE APPROXIMATION METHOD.c new file mode 100644 index 0000000..619b4cc --- /dev/null +++ b/c/Numerical/C program for SUCESSIVE APPROXIMATION METHOD.c @@ -0,0 +1,80 @@ +#include +#include +#include +#include + +int user_power,i=0,cnt=0,flag=0; +int coef[10]= {0}; +float x1=0,x2=0,t=0; +float fx1=0,fdx1=0; + +void main() +{ + clrscr(); + printf("\n\n\t\t\t PROGRAM FOR SUCESSIVE APPROXIMATION"); + printf("\n\n\n\tENTER THE TOTAL NO. OF POWER:::: "); + scanf("%d",&user_power); + for(i=0; i<=user_power; i++) + { + printf("\n\t x^%d::",i); + scanf("%d",&coef[i]); + } + printf("\n"); + printf("\n\t THE POLYNOMIAL IS ::: "); + for(i=user_power; i>=0; i--) //printing coeff. + { + printf(" %dx^%d",coef[i],i); + } + printf("\n\tINTIAL X1---->"); + scanf("%f",&x1); + printf("\n ******************************************************"); + printf("\n ITERATION X1 FX1 F'X1 "); + printf("\n **********************************************************"); + do + { + cnt++; + fx1=fdx1=0; + t=x1; + for(i=user_power; i>=0; i--) + { + fdx1+=coef[i]* (i*pow(x1,(i-1))); + } + printf("\n %d %.3f %.3f %.3f ",cnt,x1,fx1,fdx1); + x1=fdx1; + } + while((fabs(t - x1))>=0.0001); + printf("\n\t THE ROOT OF EQUATION IS %f",x2); + getch(); +} + +/*******************************OUTPUT********************************** + + PROGRAM FOR NEWTON RAPHSON GENERAL + + + ENTER THE TOTAL NO. OF POWER:::: 3 + + x^0::-3 + + x^1::-1 + + x^2::0 + + x^3::1 + + + THE POLYNOMIAL IS ::: 1x^3 0x^2 -1x^1 -3x^0 + + INTIAL X1---->3 + + ************************************** + ITERATION X1 FX1 F'X1 + ************************************** + 1 2.192 21.000 26.000 + 2 1.794 5.344 13.419 + 3 1.681 0.980 8.656 + 4 1.672 0.068 7.475 + 5 1.672 0.000 7.384 + ************************************** + + THE ROOT OF EQUATION IS 1.671700 \ No newline at end of file diff --git a/c/Pattern_Programs/0 909 89098.c b/c/Pattern_Programs/0 909 89098.c new file mode 100644 index 0000000..07621cb --- /dev/null +++ b/c/Pattern_Programs/0 909 89098.c @@ -0,0 +1,27 @@ +/* +0 +909 +89098 +7890987 +678909876 +56789098765 +4567890987654 +345678909876543 +23456789098765432 +1234567890987654321 +*/ +#include +void main() +{ + int i,j; + printf("0\n"); + for(i=9; i>=1; i--) + { + for(j=i; j<=9; j++) + printf("%d",j); + printf("0"); + for(j=9; j>=i; j--) + printf("%d",j); + printf("\n"); + } +} \ No newline at end of file diff --git a/c/Pattern_Programs/1 12 123 1234.c b/c/Pattern_Programs/1 12 123 1234.c new file mode 100644 index 0000000..3212bc7 --- /dev/null +++ b/c/Pattern_Programs/1 12 123 1234.c @@ -0,0 +1,13 @@ +#include +void main() +{ + int i, j; + for(i=1; i<=5; i++) + { + for(j=1; j<=i; j++) + { + printf("%d",j); + } + printf("\n"); + } +} \ No newline at end of file diff --git a/c/Pattern_Programs/1 12 123....c b/c/Pattern_Programs/1 12 123....c new file mode 100644 index 0000000..dba2e07 --- /dev/null +++ b/c/Pattern_Programs/1 12 123....c @@ -0,0 +1,31 @@ +/* +1 1 +12 21 +123 321 +1234 4321 +1234554321 + +*/ +#include +void main() +{ + int i,j,k; + for(i=1; i<=5; i++) + { + for(j=1; j<=5; j++) + { + if(j<=i) + printf("%d",j); + else + printf(" "); + } + for(j=5; j>=1; j--) + { + if(j<=i) + printf("%d",j); + else + printf(" "); + } + printf("\n"); + } +} \ No newline at end of file diff --git a/c/Pattern_Programs/1 12 358 13 21 34 55.c b/c/Pattern_Programs/1 12 358 13 21 34 55.c new file mode 100644 index 0000000..bcf7015 --- /dev/null +++ b/c/Pattern_Programs/1 12 358 13 21 34 55.c @@ -0,0 +1,28 @@ +/* + 1 + 1 2 + 3 5 8 + 13 21 34 55 + 89 144 233 377 610 +*/ +#include +int fib(int); +void main() +{ + int i,j,k=1; + for(i=1; i<=5; i++) + { + for(j=1; j<=i; j++) + { + printf("%d ",fib(k++)); + } + printf("\n"); + } +} + +int fib(int n) +{ + if(n<=1) + return n; + return(fib(n-1)+fib(n-2)); +} \ No newline at end of file diff --git a/c/Pattern_Programs/1 121 12321 1234321 1234321 12321 121 1.c b/c/Pattern_Programs/1 121 12321 1234321 1234321 12321 121 1.c new file mode 100644 index 0000000..f03a5d9 --- /dev/null +++ b/c/Pattern_Programs/1 121 12321 1234321 1234321 12321 121 1.c @@ -0,0 +1,38 @@ +/* + 1 + 121 + 12321 + 1234321 + 123454321 + 1234321 + 12321 + 121 + 1 +*/ +#include +void main() +{ + int num,r,c,sp; + printf("Enter number of rows : "); + scanf("%d",&num); + for(r=1; r<=num; r++) + { + for(sp=num-r; sp>=1; sp--) + printf(" "); + for(c=1; c<=r; c++) + printf("%d",c); + for(c=r-1; c>=1; c--) + printf("%d",c); + printf("\n"); + } + for(r=1; r<=num; r++) + { + for(sp=r; sp>=1; sp--) + printf(" "); + for(c=1; c<=(num-r); c++) + printf("%d",c); + for(c=num-r-1; c>=1; c--) + printf("%d",c); + printf("\n"); + } +} \ No newline at end of file diff --git a/c/Pattern_Programs/1 121 12321 1234321.c b/c/Pattern_Programs/1 121 12321 1234321.c new file mode 100644 index 0000000..64a15b7 --- /dev/null +++ b/c/Pattern_Programs/1 121 12321 1234321.c @@ -0,0 +1,19 @@ +/* + 1 + 121 + 12321 + 1234321 +*/ +#include +void main() +{ + int i,j; + for(i=1; i<=4; i++) + { + for(j=1; j<=i; j++) + printf("%d",j); + for(j=i-1; j>=1; j--) + printf("%d",j); + printf("\n"); + } +} \ No newline at end of file diff --git a/c/Pattern_Programs/1 21 321 4321 54321.c b/c/Pattern_Programs/1 21 321 4321 54321.c new file mode 100644 index 0000000..e68995f --- /dev/null +++ b/c/Pattern_Programs/1 21 321 4321 54321.c @@ -0,0 +1,13 @@ +#include +void main() +{ + int i, j; + for(i=1; i<=5; i++) + { + for(j=i; j>=1; j--) + { + printf("%d",j); + } + printf("\n"); + } +} \ No newline at end of file diff --git a/c/Pattern_Programs/1 22 333 333 22 1.c b/c/Pattern_Programs/1 22 333 333 22 1.c new file mode 100644 index 0000000..8a70a6b --- /dev/null +++ b/c/Pattern_Programs/1 22 333 333 22 1.c @@ -0,0 +1,37 @@ +/* + 1 + 2*2 + 3*3*3 + 4*4*4*4 + 4*4*4*4 + 3*3*3 + 2*2 + 1 +*/ +#include +void main() +{ + int i,j; + for(i=1; i<=4; i++) + { + for(j=1; j<=i; j++) + { + if(j=1; i--) + { + for(j=1; j<=i; j++) + { + if(j +void main() +{ + int i, j; + for(i=1; i<=5; i++) + { + for(j=1; j<=i; j++) + { + printf("%d",i); + } + printf("\n"); + } +} \ No newline at end of file diff --git a/c/Pattern_Programs/1 24 135 2468 13579.c b/c/Pattern_Programs/1 24 135 2468 13579.c new file mode 100644 index 0000000..7c5806e --- /dev/null +++ b/c/Pattern_Programs/1 24 135 2468 13579.c @@ -0,0 +1,21 @@ +#include +void main() +{ + int i,j,k; + for(i=1; i<=5; i++) + { + if(i%2==0) + { + k=2; + } + else + { + k=1; + } + for(j=1; j<=i; j++,k+=2) + { + printf("%d ", k); + } + printf("\n"); + } +} \ No newline at end of file diff --git a/c/Pattern_Programs/1 24 369 4 8 12 16.c b/c/Pattern_Programs/1 24 369 4 8 12 16.c new file mode 100644 index 0000000..cf24da1 --- /dev/null +++ b/c/Pattern_Programs/1 24 369 4 8 12 16.c @@ -0,0 +1,25 @@ +/* + 1 + 2 4 + 3 6 9 + 4 8 12 16 + 5 10 15 20 25 + 6 12 18 24 30 36 + 7 14 21 28 35 42 49 + 8 16 24 32 40 48 56 64 + 9 18 27 36 45 54 63 72 81 + 10 20 30 40 50 60 70 80 90 100 +*/ +#include +void main() +{ + int i,j; + for(i=1; i<=10; i++) + { + for(j=1; j<=i; j++) + { + printf("%d ",i*j); + } + printf("\n"); + } +} \ No newline at end of file diff --git a/c/Pattern_Programs/1 257 9 22 13 15 17 19.c b/c/Pattern_Programs/1 257 9 22 13 15 17 19.c new file mode 100644 index 0000000..a35125a --- /dev/null +++ b/c/Pattern_Programs/1 257 9 22 13 15 17 19.c @@ -0,0 +1,17 @@ +/* + 1 + 3 5 7 + 9 11 13 15 17 19 +*/ +#include +void main() +{ + int n=2,r,c,z=3; + printf("1\n"); + for(r=1; r<=2; r++) + { + for(c=1; c<=r*3; c++,z=z+2) + printf("%d ",z); + printf("\n"); + } +} \ No newline at end of file diff --git a/c/Pattern_Programs/1..10 11...c b/c/Pattern_Programs/1..10 11...c new file mode 100644 index 0000000..15290ad --- /dev/null +++ b/c/Pattern_Programs/1..10 11...c @@ -0,0 +1,37 @@ +#include +void main() +{ + int a[10][10]= {0},i,j,low=0,top=9,n=1; + for(i=0; i<5; i++,low++,top--) + { + for(j=low; j<=top; j++,n++) + a[i][j]=n; + for(j=low+1; j<=top; j++,n++) + a[j][top]=n; + for(j=top-1; j>=low; j--,n++) + a[top][j]=n; + for(j=top-1; j>low; j--,n++) + a[j][low]=n; + } + printf("\t\t\tPerfect Square\n"); + for(i=0; i<10; i++) + { + printf("\n\n\t"); + for(j=0; j<10; j++) + { + printf("%6d",a[i][j]); + delay(300); + } + } + /* + 1 2 3 4 5 6 7 8 9 10 + 36 37 38 39 40 41 42 43 44 11 + 35 64 65 66 67 68 69 70 45 12 + 34 63 84 85 86 87 88 71 46 13 + 33 62 83 96 97 98 89 72 47 14 + 32 61 82 95 100 99 90 73 48 15 + 31 60 81 94 93 92 91 74 49 16 + 30 59 80 79 78 77 76 75 50 17 + 29 58 57 56 55 54 53 52 51 18 + 28 27 26 25 24 23 22 21 20 19 + */ \ No newline at end of file diff --git a/c/Pattern_Programs/1111 square.c b/c/Pattern_Programs/1111 square.c new file mode 100644 index 0000000..a4bcac7 --- /dev/null +++ b/c/Pattern_Programs/1111 square.c @@ -0,0 +1,23 @@ +/* + 11111 + 1 1 + 1 1 + 1 1 + 11111 +*/ +#include +void main() +{ + int i,j; + for(i=1; i<=5; i++) + { + for(j=1; j<=5; j++) + { + if(j==5 || j==1 || i==1 || i==5) + printf("1"); + else + printf(" "); + } + printf("\n"); + } +} \ No newline at end of file diff --git a/c/Pattern_Programs/11111 0000 111 00 1.c b/c/Pattern_Programs/11111 0000 111 00 1.c new file mode 100644 index 0000000..b61c48f --- /dev/null +++ b/c/Pattern_Programs/11111 0000 111 00 1.c @@ -0,0 +1,20 @@ +/* + 11111 + 0000 + 111 + 00 + 1 +*/ +#include +void main() +{ + int i, j; + for(i=5; i>=1; i--) + { + for(j=1; j<=i; j++) + { + printf("%d",i%2); + } + printf("\n"); + } +} \ No newline at end of file diff --git a/c/Pattern_Programs/12345 1234 123 12 1.c b/c/Pattern_Programs/12345 1234 123 12 1.c new file mode 100644 index 0000000..aecf3df --- /dev/null +++ b/c/Pattern_Programs/12345 1234 123 12 1.c @@ -0,0 +1,13 @@ +#include +void main() +{ + int i, j; + for(i=5; i>=1; i--) + { + for(j=1; j<=i; j++) + { + printf("%d",j); + } + printf("\n"); + } +} \ No newline at end of file diff --git a/c/Pattern_Programs/12345 2345 345 45 5.c b/c/Pattern_Programs/12345 2345 345 45 5.c new file mode 100644 index 0000000..384ac9b --- /dev/null +++ b/c/Pattern_Programs/12345 2345 345 45 5.c @@ -0,0 +1,13 @@ +#include +void main() +{ + int i, j; + for(i=1; i<=5; i++) + { + for(j=i; j<=5; j++) + { + printf("%d",j); + } + printf("\n"); + } +} \ No newline at end of file diff --git a/c/Pattern_Programs/5432 543 54.c b/c/Pattern_Programs/5432 543 54.c new file mode 100644 index 0000000..f6f993b --- /dev/null +++ b/c/Pattern_Programs/5432 543 54.c @@ -0,0 +1,23 @@ +/* + 5432* + 543*1 + 54*21 + 5*321 + *4321 +*/ +#include +void main() +{ + int i,j; + for(i=1; i<=5; i++) + { + for(j=5; j>=1; j--) + { + if(i==j) + printf("*"); + else + printf("%d",j); + } + printf("\n"); + } +} \ No newline at end of file diff --git a/c/Pattern_Programs/54321 4321 321 21 1.c b/c/Pattern_Programs/54321 4321 321 21 1.c new file mode 100644 index 0000000..a640bc2 --- /dev/null +++ b/c/Pattern_Programs/54321 4321 321 21 1.c @@ -0,0 +1,13 @@ +#include +void main() +{ + int i, j; + for(i=5; i>=1; i--) + { + for(j=i; j>=1; j--) + { + printf("%d",j); + } + printf("\n"); + } +} \ No newline at end of file diff --git a/c/Pattern_Programs/A AB ABCD ABCDE.c b/c/Pattern_Programs/A AB ABCD ABCDE.c new file mode 100644 index 0000000..f444ab0 --- /dev/null +++ b/c/Pattern_Programs/A AB ABCD ABCDE.c @@ -0,0 +1,14 @@ +#include +int main() +{ + int i, j; + for(i=1; i<=5; i++) + { + for(j=0; j +int main() +{ + int i, j; + for(i=0; i<=4; i++) + { + for(j=i; j>=0; j--) + { + printf("%c",'A' + j); + } + printf("\n"); + } + return 0; +} \ No newline at end of file diff --git a/c/Pattern_Programs/A BB CCC DDDD EEEEE.c b/c/Pattern_Programs/A BB CCC DDDD EEEEE.c new file mode 100644 index 0000000..581824b --- /dev/null +++ b/c/Pattern_Programs/A BB CCC DDDD EEEEE.c @@ -0,0 +1,14 @@ +#include +int main() +{ + int i, j; + for(i=0; i<=4; i++) + { + for(j=0; j<=i; j++) + { + printf("%c",'A' + i); + } + printf("\n"); + } + return 0; +} \ No newline at end of file diff --git a/c/Pattern_Programs/AAAAA BBBB CCC DD E.c b/c/Pattern_Programs/AAAAA BBBB CCC DD E.c new file mode 100644 index 0000000..7e1e93d --- /dev/null +++ b/c/Pattern_Programs/AAAAA BBBB CCC DD E.c @@ -0,0 +1,14 @@ +#include +int main() +{ + int i, j; + for(i=0; i<=4; i++) + { + for(j=4; j>=i; j--) + { + printf("%c",'A'+ i); + } + printf("\n"); + } + return 0; +} \ No newline at end of file diff --git a/c/Pattern_Programs/ABCDE ABCDE ABCDE.c b/c/Pattern_Programs/ABCDE ABCDE ABCDE.c new file mode 100644 index 0000000..4a8ccd8 --- /dev/null +++ b/c/Pattern_Programs/ABCDE ABCDE ABCDE.c @@ -0,0 +1,14 @@ +#include +int main() +{ + int i, j; + for(i=5; i>=1; i--) + { + for(j=0; j<5; j++) + { + printf("%c",'A' + j); + } + printf("\n"); + } + return 0; +} \ No newline at end of file diff --git a/c/Pattern_Programs/ABCDE BCDE CDE DE E.c b/c/Pattern_Programs/ABCDE BCDE CDE DE E.c new file mode 100644 index 0000000..985d7ad --- /dev/null +++ b/c/Pattern_Programs/ABCDE BCDE CDE DE E.c @@ -0,0 +1,14 @@ +#include +int main() +{ + int i, j; + for(i=0; i<=4; i++) + { + for(j=i; j<=4; j++) + { + printf("%c", 'A' + j); + } + printf("\n"); + } + return 0; +} \ No newline at end of file diff --git a/c/Pattern_Programs/E DD CCC BBBB AAAAA.c b/c/Pattern_Programs/E DD CCC BBBB AAAAA.c new file mode 100644 index 0000000..58433df --- /dev/null +++ b/c/Pattern_Programs/E DD CCC BBBB AAAAA.c @@ -0,0 +1,14 @@ +#include +int main() +{ + int i, j; + for(i=4; i>=0; i--) + { + for(j=4; j>=i; j--) + { + printf("%c",'A' + i); + } + printf("\n"); + } + return 0; +} \ No newline at end of file diff --git a/c/Pattern_Programs/E DE CDE BCDE.c b/c/Pattern_Programs/E DE CDE BCDE.c new file mode 100644 index 0000000..5f72865 --- /dev/null +++ b/c/Pattern_Programs/E DE CDE BCDE.c @@ -0,0 +1,14 @@ +#include +int main() +{ + int i, j; + for(i=4; i>=0; i - -) + { + for(j=i; j<5; j++) + { + printf("%c",'A' + j); + } + printf("\n"); + } + return 0; +} \ No newline at end of file diff --git a/c/Pattern_Programs/E ED EDC EDCB.c b/c/Pattern_Programs/E ED EDC EDCB.c new file mode 100644 index 0000000..f3c6b83 --- /dev/null +++ b/c/Pattern_Programs/E ED EDC EDCB.c @@ -0,0 +1,14 @@ +#include +int main() +{ + int i, j; + for(i=4; i>=0; i--) + { + for(j=4; j>=i; j--) + { + printf("%c",'A' + j); + } + printf("\n"); + } + return 0; +} \ No newline at end of file diff --git a/c/Pattern_Programs/EDCBA DCBA CBA BA A.c b/c/Pattern_Programs/EDCBA DCBA CBA BA A.c new file mode 100644 index 0000000..7c59e8d --- /dev/null +++ b/c/Pattern_Programs/EDCBA DCBA CBA BA A.c @@ -0,0 +1,14 @@ +#include +int main() +{ + int i, j; + for(i=4; i>=0; i--) + { + for(j=i; j>=0; j--) + { + printf("%c",'A'+ j); + } + printf("\n"); + } + return 0; +} \ No newline at end of file diff --git a/c/Pattern_Programs/EDCBA EDCB EDC ED E.c b/c/Pattern_Programs/EDCBA EDCB EDC ED E.c new file mode 100644 index 0000000..47b7df1 --- /dev/null +++ b/c/Pattern_Programs/EDCBA EDCB EDC ED E.c @@ -0,0 +1,14 @@ +#include +int main() +{ + int i, j; + for(i=0; i<=4; i++) + { + for(j=4; j>=i; j--) + { + printf("%c",'A' + j); + } + printf("\n"); + } + return 0; +} \ No newline at end of file diff --git a/c/Pattern_Programs/Floyds triangle.c b/c/Pattern_Programs/Floyds triangle.c new file mode 100644 index 0000000..5c2a266 --- /dev/null +++ b/c/Pattern_Programs/Floyds triangle.c @@ -0,0 +1,22 @@ +/*Floyd's triangle + Floyd's triangle is a right angled-triangle using the natural numbers. Examples of Floyd’s triangle: + Example + 1 + 2 3 + 4 5 6 + 7 8 9 10 +*/ +#include +void main() +{ + int i,j,r,k=1; + printf("Enter the range: "); + scanf("%d",&r); + printf("FLOYD'S TRIANGLE\n\n"); + for(i=1; i<=r; i++) + { + for(j=1; j<=i; j++,k++) + printf(" %d",k); + printf("\n"); + } +} \ No newline at end of file diff --git a/c/Pattern_Programs/P_111_333..c b/c/Pattern_Programs/P_111_333..c new file mode 100644 index 0000000..cdc0cce --- /dev/null +++ b/c/Pattern_Programs/P_111_333..c @@ -0,0 +1,49 @@ +/* Pattern Problem - Program to generate all combinations of 1 2 3 using for loop. (Eg Print 111(Row 1), (112)(Row 2), (113)(Row 3)...(333)(Last Row)) */ + +#include +#include + +void main() +{ + int i, j, k ; + clrscr() ; + printf("Required pattern is as follows:\n"); + for(i=1 ; i<=3 ; i++) + for(j=1 ; j<=3 ; j++) + for(k=1 ; k<=3 ; k++) + printf("%d %d %d \n", i, j, k) ; + getch(); +} + +/* +Output: + +Required pattern is as follows: +1 1 1 +1 1 2 +1 1 3 +1 2 1 +1 2 2 +1 2 3 +1 3 1 +1 3 2 +1 3 3 +2 1 1 +2 1 2 +2 1 3 +2 2 1 +2 2 2 +2 2 3 +2 3 1 +2 3 2 +2 3 3 +3 1 1 +3 1 2 +3 1 3 +3 2 1 +3 2 2 +3 2 3 +3 3 1 +3 3 2 +3 3 3 +*/ \ No newline at end of file diff --git a/c/Pattern_Programs/P_123_12_1..c b/c/Pattern_Programs/P_123_12_1..c new file mode 100644 index 0000000..338b451 --- /dev/null +++ b/c/Pattern_Programs/P_123_12_1..c @@ -0,0 +1,46 @@ +/* Pattern problem + ... + 1 2 3 4 + 1 2 3 + 1 2 + 1 +*/ + +#include +#include + +void main() +{ + int i, j, n ; + clrscr() ; + printf("Enter the number of lines: ") ; + scanf("%d", &n) ; + printf("Required pattern is as follows: \n") ; + for(i=n ; i>=1 ; i--) + { + for(j=1 ; j<=i ; j++) + printf("%d ", j) ; + printf("\n") ; + } + getch() ; +} +/* If the pattern is fixed then variable 'n' should not be read + +Space in printf should not be given if this is the pattern: +1234 +123 +12 +1 +*/ + +/* +Output: + +Enter the number of lines: 3 +Required pattern is as follows: +1 2 3 +1 2 +1 +*/ + + diff --git a/c/Pattern_Programs/P_123_23..c b/c/Pattern_Programs/P_123_23..c new file mode 100644 index 0000000..a0af520 --- /dev/null +++ b/c/Pattern_Programs/P_123_23..c @@ -0,0 +1,37 @@ +/* Pattern problem + ... + 1 2 3 4 + 2 3 4 + 3 4 + 4 +*/ + +#include +#include + +void main() +{ + int i, j, n ; + clrscr() ; + printf("Enter the number of lines: ") ; + scanf("%d", &n) ; + printf("Required pattern is as follows: \n") ; + for(i=n ; i>=1 ; i--) + { + for(j=i ; j>=1 ; j--) + printf("%d ", j) ; + printf("\n") ; + } + getch(); +} + +/* +Output: + +Enter the number of lines: 3 +Required pattern is as follows: +3 2 1 +2 1 +1 +*/ + diff --git a/c/Pattern_Programs/P_1_121..c b/c/Pattern_Programs/P_1_121..c new file mode 100644 index 0000000..ade9996 --- /dev/null +++ b/c/Pattern_Programs/P_1_121..c @@ -0,0 +1,51 @@ +/* Pattern Problem + 1 + 121 + 12321 +1234321 + ... +*/ + +#include +#include + +void main() +{ + int i, j, n ; + clrscr() ; + printf("Enter the number of lines: ") ; + scanf("%d", &n) ; + printf("Required pattern is as follows: \n") ; + for(i=1 ; i<=n ; i++) + { + /* Managing spaces */ + for(j=1 ; j<=n-i ; j++) + printf(" ") ; + /* Printing from left to Centre */ + for(j=1 ; j<=i ; j++) + printf("%d", j) ; + /* Printing to the right of Centre */ + for(j=i-1 ; j>=1 ; j--) + printf("%d", j) ; + printf("\n") ; + } + getch(); +} + +/* +Give one extra space in each printf() if the pattern is: + 1 + 1 2 1 +1 2 3 2 1 +*/ + +/* +Output: + +Enter the number of lines: 4 +Required pattern is as follows: + 1 + 121 + 12321 +1234321 +*/ diff --git a/c/Pattern_Programs/P_1_121_1..c b/c/Pattern_Programs/P_1_121_1..c new file mode 100644 index 0000000..eef7fdd --- /dev/null +++ b/c/Pattern_Programs/P_1_121_1..c @@ -0,0 +1,59 @@ +/* Pattern Problem + 1 + 121 + 12321 +1234321 + 12321 + 121 + 1 +*/ + +#include +#include + +void main() +{ + int i, j ; + clrscr() ; + printf("Required pattern is as follows: \n") ; + for(i=1 ; i<=4 ; i++) + { + /* Managing spaces */ + for(j=1 ; j<=4-i ; j++) + printf(" ") ; + /* Printing from left to Centre */ + for(j=1 ; j<=i ; j++) + printf("%d", j) ; + /* Printing to the right of Centre */ + for(j=i-1 ; j>=1 ; j--) + printf("%d", j) ; + printf("\n") ; + } + for(i=4-1 ; i>=1 ; i--) + { + /* Managing spaces */ + for(j=4-i ; j>=1 ; j--) + printf(" ") ; + /* Printing from left to Centre */ + for(j=1 ; j<=i ; j++) + printf("%d", j) ; + /* Printing to the right of Centre */ + for(j=i-1 ; j>=1 ; j--) + printf("%d", j) ; + printf("\n") ; + } + getch(); +} + +/* +Output: + +Required pattern is as follows: + 1 + 121 + 12321 +1234321 + 12321 + 121 + 1 +*/ diff --git a/c/Pattern_Programs/P_1_12A..c b/c/Pattern_Programs/P_1_12A..c new file mode 100644 index 0000000..112b377 --- /dev/null +++ b/c/Pattern_Programs/P_1_12A..c @@ -0,0 +1,42 @@ +/* Pattern Problem + 1 + 1 2 A + 1 2 3 A B + 1 2 3 4 A B C +*/ + +#include +#include + +void main() +{ + int i, j ; + clrscr(); + printf("Required Pattern is as follows:\n"); + for(i=1 ; i<=4 ; i++) + { + /* Managing spaces */ + for(j=1 ; j<=4-i ; j++) + printf(" ") ; + /* Prinitng digits*/ + for(j=1 ; j<=i ; j++) + printf("%d ", j) ; + /* Printing alphabets*/ + for(j=1 ; j +#include + +void main() +{ + int i, j, n ; + clrscr() ; + printf("Enter the number of lines: ") ; + scanf("%d", &n) ; + printf("Required pattern is as follows: \n") ; + for(i=1 ; i<=n ; i++) + { + for(j=1 ; j<=i ; j++) + printf("%d ", j) ; + printf("\n") ; + } + getch() ; +} +/* If the pattern is fixed then variable 'n' should not be read + +Space in printf should not be given if this is the pattern: +1 +12 +123 +1234 +*/ + +/* +Output: + +Enter the number of lines: 3 +Required pattern is as follows: +1 +1 2 +1 2 3 +*/ diff --git a/c/Pattern_Programs/P_1_21A..c b/c/Pattern_Programs/P_1_21A..c new file mode 100644 index 0000000..bb699a0 --- /dev/null +++ b/c/Pattern_Programs/P_1_21A..c @@ -0,0 +1,46 @@ +/* Pattern Problem + 1 + 21A + 321AB + 4321ABC +54321ABCD + */ + +#include +#include + +void main() +{ + int i, j ; + clrscr(); + printf("Required Pattern is as follows:\n"); + for(i=1; i<=5; i++) + { + /* Managing spaces */ + for(j=1 ; j<=5-i ; j++) + printf(" ") ; + /* Prinitng digits*/ + for(j=i ; j>=1 ; j--) + printf("%d", j) ; + /* Printing alphabets*/ + for(j=1 ; j +#include + +void main() +{ + int i, j ; + clrscr() ; + printf("Required pattern is as follows: \n") ; + for(i=1 ; i<=5 ; i++) + { + /* Managing spaces */ + for(j=1 ; j<=5-i ; j++) + printf(" ") ; + /* Printing from left to Centre */ + for(j=1 ; j<=i ; j++) + printf("%d ", i) ; + printf("\n") ; + } + getch(); +} + +/* +Output: + +Required pattern is as follows: + 1 + 2 2 + 3 3 3 + 4 4 4 4 +5 5 5 5 5 +*/ diff --git a/c/Pattern_Programs/P_1_22_333 Normal..c b/c/Pattern_Programs/P_1_22_333 Normal..c new file mode 100644 index 0000000..8ded74c --- /dev/null +++ b/c/Pattern_Programs/P_1_22_333 Normal..c @@ -0,0 +1,37 @@ +/* Pattern Problem + 1 + 2 2 + 3 3 3 + 4 4 4 4 + 5 5 5 5 5 +*/ + +#include +#include + +void main() +{ + int i, j ; + clrscr() ; + printf("Required pattern is as follows: \n") ; + for(i=1 ; i<=5 ; i++) + { + /* Printing from left to Centre */ + for(j=1 ; j<=i ; j++) + printf("%d ", i) ; + printf("\n") ; + } + getch(); +} + +/* +Output: + +Required pattern is as follows: +1 +2 2 +3 3 3 +4 4 4 4 +5 5 5 5 5 + +*/ diff --git a/c/Pattern_Programs/P_1_232_34543..c b/c/Pattern_Programs/P_1_232_34543..c new file mode 100644 index 0000000..1d60e6e --- /dev/null +++ b/c/Pattern_Programs/P_1_232_34543..c @@ -0,0 +1,46 @@ +/* Pattern Problem + 1 + 2 3 2 + 3 4 5 4 3 + 4 5 6 7 6 5 4 + +*/ + +#include +#include + +void main() +{ + int i, j, k, n ; + clrscr() ; + printf("Required pattern is as follows: \n") ; + for(i=1 ; i<=4 ; i++) + { + /* Managing spaces */ + for(j=1 ; j<=4-i ; j++) + printf(" ") ; + /* Printing from left to Centre */ + for(k=1, j=i ; k<=i ; k++, j++) + printf("%d ", j) ; + /* Printing to the right of Centre */ + for(k=1, j=j-2 ; k<=i-1 ; k++, j--) + printf("%d ", j) ; + printf("\n") ; + } + getch(); +} + +/* +Output: + +Required pattern is as follows: + 1 + 2 3 2 + 3 4 5 4 3 +4 5 6 7 6 5 4 + +*/ + + + + diff --git a/c/Pattern_Programs/P_1_23_456..c b/c/Pattern_Programs/P_1_23_456..c new file mode 100644 index 0000000..b84268c --- /dev/null +++ b/c/Pattern_Programs/P_1_23_456..c @@ -0,0 +1,35 @@ +/* Pattern problem + 1 + 2 3 + 4 5 6 + 7 8 9 10 + ... +*/ + +#include +#include + +void main() +{ + int i, j, k ; + clrscr() ; + printf("Required pattern is as follows: \n") ; + k=1 ; + for(i=1 ; i<=4 ; i++) + { + for(j=1 ; j<=i ; j++) + printf("%d ", k++) ; + printf("\n") ; + } + getch() ; +} + +/* +Output: + +Required pattern is as follows: +1 +2 3 +4 5 6 +7 8 9 10 +*/ diff --git a/c/Pattern_Programs/P_321_21_1..c b/c/Pattern_Programs/P_321_21_1..c new file mode 100644 index 0000000..6be67c5 --- /dev/null +++ b/c/Pattern_Programs/P_321_21_1..c @@ -0,0 +1,37 @@ +/* Pattern problem + ... + 4 3 2 1 + 3 2 1 + 2 1 + 1 +*/ + +#include +#include + +void main() +{ + int i, j, n ; + clrscr() ; + printf("Enter the number of lines: ") ; + scanf("%d", &n) ; + printf("Required pattern is as follows: \n") ; + for(i=n ; i>=1 ; i--) + { + for(j=i ; j>=1 ; j--) + printf("%d ", j) ; + printf("\n") ; + } + getch() ; +} + +/* +Output: + +Enter the number of lines: 3 +Required pattern is as follows: +3 2 1 +2 1 +1 +*/ + diff --git a/c/Pattern_Programs/P_432_43_4..c b/c/Pattern_Programs/P_432_43_4..c new file mode 100644 index 0000000..617b504 --- /dev/null +++ b/c/Pattern_Programs/P_432_43_4..c @@ -0,0 +1,46 @@ +/* Pattern problem + ... + 4 3 2 1 + 4 3 2 + 4 3 + 4 +*/ + +#include +#include + +void main() +{ + int i, j, n ; + clrscr() ; + printf("Enter the number of lines: ") ; + scanf("%d", &n) ; + printf("Required pattern is as follows: \n") ; + for(i=1 ; i<=n ; i++) + { + for(j=n ; j>=i ; j--) + printf("%d ", j) ; + printf("\n") ; + } + getch(); +} +/* If the pattern is fixed then variable 'n' should not be read + +Space in printf should not be given if this is the pattern: +4321 +432 +43 +4 +*/ + +/* +Output: + +Enter the number of lines: 3 +Required pattern is as follows: +3 2 1 +3 2 +3 + +*/ + diff --git a/c/Pattern_Programs/P_4_43..c b/c/Pattern_Programs/P_4_43..c new file mode 100644 index 0000000..5bf22fe --- /dev/null +++ b/c/Pattern_Programs/P_4_43..c @@ -0,0 +1,39 @@ +/* Pattern problem + 4 + 4 3 + 4 3 2 + 4 3 2 1 + ... +*/ + +#include +#include + +void main() +{ + int i, j, n ; + clrscr() ; + printf("Enter the number of lines: ") ; + scanf("%d", &n) ; + printf("Required pattern is as follows: \n") ; + for(i=n ; i>=1 ; i--) + { + for(j=n ; j>=i ; j--) + printf("%d ", j) ; + printf("\n") ; + } + getch(); +} + +/* +Output: + +Enter the number of lines: 3 +Required pattern is as follows: +3 +3 2 +3 2 1 +*/ + + + diff --git a/c/Pattern_Programs/P_5_44_333..c b/c/Pattern_Programs/P_5_44_333..c new file mode 100644 index 0000000..fdaf0a3 --- /dev/null +++ b/c/Pattern_Programs/P_5_44_333..c @@ -0,0 +1,37 @@ +/* Pattern problem + 5 + 4 4 + 3 3 3 + 2 2 2 2 + 1 1 1 1 1 +*/ + +#include +#include + +void main() +{ + int i, j ; + clrscr() ; + printf("Required pattern is as follows: \n") ; + for(i=5 ; i>=1 ; i--) + { + for(j=5 ; j>=i ; j--) + printf("%d ", i) ; + printf("\n") ; + } + getch() ; +} + +/* +Output: + +Required pattern is as follows: +5 +4 4 +3 3 3 +2 2 2 2 +1 1 1 1 1 + + +*/ \ No newline at end of file diff --git a/c/Pattern_Programs/P_ABC_AB_A..c b/c/Pattern_Programs/P_ABC_AB_A..c new file mode 100644 index 0000000..ef1c0d1 --- /dev/null +++ b/c/Pattern_Programs/P_ABC_AB_A..c @@ -0,0 +1,41 @@ +/* Pattern Problem +A B C D + A B C + A B + A +*/ + +#include +#include + +void main() +{ + int i, j ; + clrscr() ; + printf("Required pattern is as follows: \n") ; + for(i=4 ; i>=1 ; i--) + { + /* Managing spaces */ + for(j=4-i ; j>=1 ; j--) + printf(" ") ; + /* Printing from left to Centre */ + for(j=1 ; j<=i ; j++) + printf("%c ", j+64) ; + printf("\n") ; + } + getch(); +} + +/* +Output: + +Required pattern is as follows: +A B C D + A B C + A B + A +*/ + + + + diff --git a/c/Pattern_Programs/P_A_AB_ABC..c b/c/Pattern_Programs/P_A_AB_ABC..c new file mode 100644 index 0000000..b4742ea --- /dev/null +++ b/c/Pattern_Programs/P_A_AB_ABC..c @@ -0,0 +1,35 @@ +/* Pattern problem + A + A B + A B C + A B C D + A B C D E +*/ + +#include +#include + +void main() +{ + int i, j, n ; + clrscr() ; + printf("Required pattern is as follows: \n") ; + for(i=1 ; i<=5 ; i++) + { + for(j=1 ; j<=i ; j++) + printf("%c ", j+64) ; + printf("\n") ; + } + getch(); +} + +/* +Output: + +Required pattern is as follows: +A +A B +A B C +A B C D +A B C D E +*/ diff --git a/c/Pattern_Programs/P_A_BB_CCC..c b/c/Pattern_Programs/P_A_BB_CCC..c new file mode 100644 index 0000000..97e633e --- /dev/null +++ b/c/Pattern_Programs/P_A_BB_CCC..c @@ -0,0 +1,46 @@ +/* Pattern Problem + A + B B + C C C +D D D D + ... +*/ + +#include +#include + +void main() +{ + int i, j, n ; + clrscr() ; + printf("Enter the number of lines: ") ; + scanf("%d", &n) ; + printf("Required pattern is as follows: \n") ; + for(i=1 ; i<=n ; i++) + { + /* Managing spaces */ + for(j=1 ; j<=n-i ; j++) + printf(" ") ; + /* Printing from left to Centre */ + for(j=1 ; j<=i ; j++) + printf("%c ",i+64) ; + printf("\n") ; + } + getch(); +} + +/* +Output: + +Enter the number of lines: 4 +Required pattern is as follows: + A + B B + C C C +D D D D + +*/ + + + + diff --git a/c/Pattern_Programs/P_star..c b/c/Pattern_Programs/P_star..c new file mode 100644 index 0000000..71a5ecf --- /dev/null +++ b/c/Pattern_Programs/P_star..c @@ -0,0 +1,52 @@ +/* Pattern Problem + * + * * + * * * + * * + * +*/ + +#include +#include + +void main() +{ + int i, j ; + clrscr() ; + printf("Required pattern is as follows: \n") ; + for(i=1 ; i<=3 ; i++) + { + /* Managing spaces */ + for(j=1 ; j<=3-i ; j++) + printf(" ") ; + /* Printing from left to Centre */ + for(j=1 ; j<=i ; j++) + printf("* ") ; + printf("\n") ; + } + for(i=3-1 ; i>=1 ; i--) + { + /* Managing spaces */ + for(j=3-i ; j>=1 ; j--) + printf(" ") ; + /* Printing from left to Centre */ + for(j=1 ; j<=i ; j++) + printf("* ") ; + printf("\n") ; + } + getch(); +} + +/* +Output: + +Required pattern is as follows: + * + * * + * * * + * * + * + +*/ + + diff --git a/c/Pattern_Programs/P_x=1!..c b/c/Pattern_Programs/P_x=1!..c new file mode 100644 index 0000000..f9f93ad --- /dev/null +++ b/c/Pattern_Programs/P_x=1!..c @@ -0,0 +1,27 @@ +/* Pattern problem +x=1!+3!+5!+7!+9!+... +*/ + +#include +#include + +void main() +{ + int i, n ; + clrscr() ; + printf("Enter n:") ; + scanf("%d", &n) ; + printf("Required Pattern is as shown:\n") ; + printf("x=1!") ; + for(i=3 ; i<=2*n-1 ; i=i+2) + printf("+%d!", i) ; + getch() ; +} + +/* +Output: + +Enter n:3 +Required Pattern is as shown: +x=1!+3!+5! +*/ diff --git a/c/Pattern_Programs/Rhombus pattern with numbers.c b/c/Pattern_Programs/Rhombus pattern with numbers.c new file mode 100644 index 0000000..2f41012 --- /dev/null +++ b/c/Pattern_Programs/Rhombus pattern with numbers.c @@ -0,0 +1,37 @@ +/*design a number rhombus pattern + 1 1 + 2 2 +3 3 +4 4 +3 3 + 2 2 + 1 1 + +*/ +#include +void main() +{ + int num,i,c,s,n; + printf("Enter maximum number : "); + scanf("%d", &num); + for(i=1; i<=num; i++) + { + for(s=num-i; s>=1; s--) + printf(" "); + printf("%d", i); + for(s=i*2; s>1; s--) + printf(" "); + printf("%d", i); + printf("\n"); + } + for(i=1,n=num-1; i=1; s--) + printf(" "); + printf("%d",n); + for(s=n*2; s>1; s--) + printf(" "); + printf("%d", n); + printf("\n"); + } +} \ No newline at end of file diff --git a/c/Pattern_Programs/Square with numbers.c b/c/Pattern_Programs/Square with numbers.c new file mode 100644 index 0000000..595f4d1 --- /dev/null +++ b/c/Pattern_Programs/Square with numbers.c @@ -0,0 +1,34 @@ +/* + 4444444 + 4333334 + 4322234 + 4321234 + 4322234 + 4333334 + 4444444 +*/ +#include +void main() +{ + int i,j,k; + for(i=4; i>=1; i--) + { + for(j=4; j>=i; j--) + printf("%d",j); + for(j=1; j<(i*2)-1; j++) + printf("%d",i); + for(j=i+1; j<=4; j++) + printf("%d",j); + printf("\n"); + } + for(i=2; i<=4; i++) + { + for(j=4; j>=i; j--) + printf("%d",j); + for(j=1; j<(i*2)-1; j++) + printf("%d",i); + for(j=i+1; j<=4; j++) + printf("%d",j); + printf("\n"); + } +} \ No newline at end of file diff --git a/c/Pattern_Programs/Star 1.c b/c/Pattern_Programs/Star 1.c new file mode 100644 index 0000000..b98cb5c --- /dev/null +++ b/c/Pattern_Programs/Star 1.c @@ -0,0 +1,24 @@ +/*-- + + * + ** + *** + **** + ***** + +--*/ +#include +void main() +{ + int i, j, n; + printf("Enter no. of rows: "); + scanf("%d",&n); + for(i=1; i<=n; i++) + { + for(j=1; j<=i; j++) + { + printf("*"); + } + printf("\n"); + } +} \ No newline at end of file diff --git a/c/Pattern_Programs/Star 10.c b/c/Pattern_Programs/Star 10.c new file mode 100644 index 0000000..f10a520 --- /dev/null +++ b/c/Pattern_Programs/Star 10.c @@ -0,0 +1,28 @@ +/* + +* * * * + * * * + * * + * + +*/ +#include +int main() +{ + int i,j,n; + printf("Enter no. of row: "); + scanf("%d",&n); + for(i=1; i<=n; i++) + { + for(j=1; j +void main() +{ + int i, j, n; + printf("Enter no. of rows: "); + scanf("%d",&n); + for(i=n; i>=1; i--) + { + for(j=1; j=i; j--) + { + printf("*"); + } + printf("\n"); + } +} \ No newline at end of file diff --git a/c/Pattern_Programs/Star 3.c b/c/Pattern_Programs/Star 3.c new file mode 100644 index 0000000..ccb0c96 --- /dev/null +++ b/c/Pattern_Programs/Star 3.c @@ -0,0 +1,28 @@ +/*-- + + ***** + **** + *** + ** + * + +--*/ +#include +void main() +{ + int i, j,n; + printf("Enter no. of rows: "); + scanf("%d",&n); + for(i=n; i>=1; i--) + { + for(j=n; j>i; j--) + { + printf(" "); + } + for(j=1; j<=i; j++) + { + printf("*"); + } + printf("\n"); + } +} \ No newline at end of file diff --git a/c/Pattern_Programs/Star 4.c b/c/Pattern_Programs/Star 4.c new file mode 100644 index 0000000..15bbad6 --- /dev/null +++ b/c/Pattern_Programs/Star 4.c @@ -0,0 +1,28 @@ +/*-- + + * + *** + ***** + ******* + ********* + +--*/ +#include +void main() +{ + int i, j, n; + printf("Enter no. of rows: "); + scanf("%d",&n); + for(i=1; i<=n; i++) + { + for(j=i; j +void main() +{ + int i, j, k; + for(i=1; i<=5; i++) + { + for(j=1; j<=6-i; j++) + { + printf("*"); + } + for(k=1; k +void main() +{ + int num,r,j,s; + printf("Enter no of rows: "); + scanf("%d", &num); + printf("\n*\n"); + for(r=1; r<=num; r++) + { + printf("*"); + for(s=1; s +void main() +{ + int cols,rows,r,c,s; + printf("Enter no. of columns: "); + scanf("%d", &cols); + printf("Enter no. of rows: "); + scanf("%d", &rows); + for(r=1; r<=cols; r++) + printf("*"); + printf("\n"); + for(c=1; c<=rows-2; c++) + { + printf("*"); + for(s=1; s<=cols-2; s++) + printf(" "); + printf("*\n"); + } + for(r=1; r<=cols; r++) + printf("*"); +} \ No newline at end of file diff --git a/c/Pattern_Programs/Star 8.c b/c/Pattern_Programs/Star 8.c new file mode 100644 index 0000000..8f147b8 --- /dev/null +++ b/c/Pattern_Programs/Star 8.c @@ -0,0 +1,33 @@ +/* + +* * +** ** +* * * +* * +* * + + +/* print m shape pyramid in c*/ +#include +int main() +{ + int num=5,j,i; + for(i=1; i<=num; i++) + { + for(j=1; j<=num; j++) + { + if( (j==2 || j==3 || j==4) && (i==1) ) + printf(" "); + else if( (j==3) && (i==2) ) + printf(" "); + else if( (j==2 || j==4) && (i==3) ) + printf(" "); + else if( (j==2 || j==3 || j==4 ) && (i==4 || i==5) ) + printf(" "); + else + printf("*"); + } + printf("\n"); + } + return 0; +} \ No newline at end of file diff --git a/c/Pattern_Programs/Star 9.c b/c/Pattern_Programs/Star 9.c new file mode 100644 index 0000000..05712aa --- /dev/null +++ b/c/Pattern_Programs/Star 9.c @@ -0,0 +1,28 @@ +/* + + * + * * + * * * + * * * * + +*/ +#include +int main() +{ + int i,j,n; + printf("Enter value of n: "); + scanf("%d",&n); + for(i=1; i<=n; i++) + { + for(j=i; j<=n; j++) + { + printf(" "); + } + for(j=1; j<=i; j++) + { + printf("* "); + } + printf("\n"); + } + return 0; +} \ No newline at end of file diff --git a/c/Recursion/C Program Count the Number of Occurrences of an Element in the Linked List using Recursion.c b/c/Recursion/C Program Count the Number of Occurrences of an Element in the Linked List using Recursion.c new file mode 100644 index 0000000..d8314f6 --- /dev/null +++ b/c/Recursion/C Program Count the Number of Occurrences of an Element in the Linked List using Recursion.c @@ -0,0 +1,40 @@ +/* + * C program to find the number of occurences of a given number in a + * list + */ +#include + +void occur(int [], int, int, int, int *); + +int main() +{ + int size, key, count = 0; + int list[20]; + int i; + printf("Enter the size of the list: "); + scanf("%d", &size); + printf("Printing the list:\n"); + for (i = 0; i < size; i++) + { + list[i] = rand() % size; + printf("%d ", list[i]); + } + printf("\nEnter the key to find it's occurence: "); + scanf("%d", &key); + occur(list, size, 0, key, &count); + printf("%d occurs for %d times.\n", key, count); + return 0; +} + +void occur(int list[], int size, int index, int key, int *count) +{ + if (size == index) + { + return; + } + if (list[index] == key) + { + *count += 1; + } + occur(list, size, index + 1, key, count); +} \ No newline at end of file diff --git a/c/Recursion/C Program Find the Length of the Linked List using Recursion.c b/c/Recursion/C Program Find the Length of the Linked List using Recursion.c new file mode 100644 index 0000000..211d0f8 --- /dev/null +++ b/c/Recursion/C Program Find the Length of the Linked List using Recursion.c @@ -0,0 +1,25 @@ +/* + * C program to find the length of a string + */ +#include + +int length(char [], int); +int main() +{ + char word[20]; + int count; + printf("Enter a word to count it's length: "); + scanf("%s", word); + count = length(word, 0); + printf("The number of characters in %s are %d.\n", word, count); + return 0; +} + +int length(char word[], int index) +{ + if (word[index] == '\0') + { + return 0; + } + return (1 + length(word, index + 1)); +} \ No newline at end of file diff --git a/c/Recursion/C Program for Depth First Binary Tree Search using Recursion.c b/c/Recursion/C Program for Depth First Binary Tree Search using Recursion.c new file mode 100644 index 0000000..23e2988 --- /dev/null +++ b/c/Recursion/C Program for Depth First Binary Tree Search using Recursion.c @@ -0,0 +1,115 @@ +/* + * C Program for Depth First Binary Tree Search using Recursion + */ +#include +#include + +struct node +{ + int a; + struct node *left; + struct node *right; +}; + +void generate(struct node **, int); +void DFS(struct node *); +void delete(struct node **); + +int main() +{ + struct node *head = NULL; + int choice = 0, num, flag = 0, key; + do + { + printf("\nEnter your choice:\n1. Insert\n2. Perform DFS Traversal\n3. Exit\nChoice: "); + scanf("%d", &choice); + switch(choice) + { + case 1: + printf("Enter element to insert: "); + scanf("%d", &num); + generate(&head, num); + break; + case 2: + DFS(head); + break; + case 3: + delete(&head); + printf("Memory Cleared\nPROGRAM TERMINATED\n"); + break; + default: + printf("Not a valid input, try again\n"); + } + } + while (choice != 3); + return 0; +} + +void generate(struct node **head, int num) +{ + struct node *temp = *head, *prev = *head; + if (*head == NULL) + { + *head = (struct node *)malloc(sizeof(struct node)); + (*head)->a = num; + (*head)->left = (*head)->right = NULL; + } + else + { + while (temp != NULL) + { + if (num > temp->a) + { + prev = temp; + temp = temp->right; + } + else + { + prev = temp; + temp = temp->left; + } + } + temp = (struct node *)malloc(sizeof(struct node)); + temp->a = num; + if (num >= prev->a) + { + prev->right = temp; + } + else + { + prev->left = temp; + } + } +} + +void DFS(struct node *head) +{ + if (head) + { + if (head->left) + { + DFS(head->left); + } + if (head->right) + { + DFS(head->right); + } + printf("%d ", head->a); + } +} + +void delete(struct node **head) +{ + if (*head != NULL) + { + if ((*head)->left) + { + delete(&(*head)->left); + } + if ((*head)->right) + { + delete(&(*head)->right); + } + free(*head); + } +} \ No newline at end of file diff --git a/c/Recursion/C Program to Check Prime using Recursion.c b/c/Recursion/C Program to Check Prime using Recursion.c new file mode 100644 index 0000000..e76bfd8 --- /dev/null +++ b/c/Recursion/C Program to Check Prime using Recursion.c @@ -0,0 +1,28 @@ +#include +int checkprime(int,int); +int main() +{ + int num,prime; + printf("Enter a number: "); + scanf("%d",&num); + prime = checkprime(num,num/2); + if(prime==1) + printf("%d is a prime number",num); + else + printf("%d is not a prime number",num); + return 0; +} +int checkprime(int num,int i) +{ + if(i==1) + { + return 1; + } + else + { + if(num%i==0) + return 0; + else + checkprime(num,i-1); + } +} \ No newline at end of file diff --git a/c/Recursion/C Program to Check whether a given String is Palindrome or not using Recursion.c b/c/Recursion/C Program to Check whether a given String is Palindrome or not using Recursion.c new file mode 100644 index 0000000..6d7adfd --- /dev/null +++ b/c/Recursion/C Program to Check whether a given String is Palindrome or not using Recursion.c @@ -0,0 +1,36 @@ +/* + * C Program to Check whether a given String is Palindrome or not + * using Recursion + */ +#include +#include + +void check(char [], int); + +int main() +{ + char word[15]; + printf("Enter a word to check if it is a palindrome\n"); + scanf("%s", word); + check(word, 0); + return 0; +} + +void check(char word[], int index) +{ + int len = strlen(word) - (index + 1); + if (word[index] == word[len]) + { + if (index + 1 == len || index == len) + { + printf("The entered word is a palindrome\n"); + return; + } + check(word, index + 1); + } + else + { + printf("The entered word is not a palindrome\n"); + } +} +} \ No newline at end of file diff --git a/c/Recursion/C Program to Convert a Number Decimal System to Binary System using Recursion.c b/c/Recursion/C Program to Convert a Number Decimal System to Binary System using Recursion.c new file mode 100644 index 0000000..3301a55 --- /dev/null +++ b/c/Recursion/C Program to Convert a Number Decimal System to Binary System using Recursion.c @@ -0,0 +1,28 @@ +/* + * C Program to Convert a Number Decimal System to Binary System using Recursion + */ +#include + +int convert(int); + +int main() +{ + int dec, bin; + printf("Enter a decimal number: "); + scanf("%d", &dec); + bin = convert(dec); + printf("The binary equivalent of %d is %d.\n", dec, bin); + return 0; +} + +int convert(int dec) +{ + if (dec == 0) + { + return 0; + } + else + { + return (dec % 2 + 10 * convert(dec / 2)); + } +} \ No newline at end of file diff --git a/c/Recursion/C Program to Copy One String to Another using Recursion.c b/c/Recursion/C Program to Copy One String to Another using Recursion.c new file mode 100644 index 0000000..279c500 --- /dev/null +++ b/c/Recursion/C Program to Copy One String to Another using Recursion.c @@ -0,0 +1,26 @@ +/* + * C Program to Copy One String to Another using Recursion + */ +#include + +void copy(char [], char [], int); + +int main() +{ + char str1[20], str2[20]; + printf("Enter string to copy: "); + scanf("%s", str1); + copy(str1, str2, 0); + printf("Copying success.\n"); + printf("The first string is: %s\n", str1); + printf("The second string is: %s\n", str2); + return 0; +} + +void copy(char str1[], char str2[], int index) +{ + str2[index] = str1[index]; + if (str1[index] == '\0') + return; + copy(str1, str2, index + 1); +} \ No newline at end of file diff --git a/c/Recursion/C Program to Display all the Nodes in a Linked List using Recursion.c b/c/Recursion/C Program to Display all the Nodes in a Linked List using Recursion.c new file mode 100644 index 0000000..c668528 --- /dev/null +++ b/c/Recursion/C Program to Display all the Nodes in a Linked List using Recursion.c @@ -0,0 +1,66 @@ +/* + * Recursive C program to display members of a linked list + */ +#include +#include + +struct node +{ + int a; + struct node *next; +}; + +void generate(struct node **); +void display(struct node*); +void delete(struct node **); + +int main() +{ + struct node *head = NULL; + generate(&head); + display(head); + delete(&head); + return 0; +} + +void generate(struct node **head) +{ + int num = 10, i; + struct node *temp; + for (i = 0; i < num; i++) + { + temp = (struct node *)malloc(sizeof(struct node)); + temp->a = i; + if (*head == NULL) + { + *head = temp; + (*head)->next = NULL; + } + else + { + temp->next = *head; + *head = temp; + } + } +} + +void display(struct node *head) +{ + printf("%d ", head->a); + if (head->next == NULL) + { + return; + } + display(head->next); +} + +void delete(struct node **head) +{ + struct node *temp; + while (*head != NULL) + { + temp = *head; + *head = (*head)->next; + free(temp); + } +} \ No newline at end of file diff --git a/c/Recursion/C Program to Display the Nodes of a Linked List in Reverse using Recursion.c b/c/Recursion/C Program to Display the Nodes of a Linked List in Reverse using Recursion.c new file mode 100644 index 0000000..26d9408 --- /dev/null +++ b/c/Recursion/C Program to Display the Nodes of a Linked List in Reverse using Recursion.c @@ -0,0 +1,65 @@ +/* + * Recursive C program to reverse nodes of a linked list and display + * them + */ +#include +#include + +struct node +{ + int data; + struct node *next; +}; + +void print_reverse_recursive (struct node *); +void print (struct node *); +void create_new_node (struct node *, int ); + +//Driver Function +int main () +{ + struct node *head = NULL; + insert_new_node (&head, 1); + insert_new_node (&head, 2); + insert_new_node (&head, 3); + insert_new_node (&head, 4); + printf ("LinkedList : "); + print (head); + printf ("\nLinkedList in reverse order : "); + print_reverse_recursive (head); + printf ("\n"); + return 0; +} + +//Recursive Reverse +void print_reverse_recursive (struct node *head) +{ + if (head == NULL) + { + return; + } + //Recursive call first + print_reverse (head -> next); + //Print later + printf ("%d ", head -> data); +} + +//Print the linkedlist normal +void print (struct node *head) +{ + if (head == NULL) + { + return; + } + printf ("%d ", head -> data); + print (head -> next); +} + +//New data added in the start +void insert_new_node (struct node ** head_ref, int new_data) +{ + struct node * new_node = (struct node *) malloc (sizeof (struct node)); + new_node -> data = new_data; + new_node -> next = (*head_ref); + (*head_ref) = new_node; +} \ No newline at end of file diff --git a/c/Recursion/C Program to Factorial using recursion.c b/c/Recursion/C Program to Factorial using recursion.c new file mode 100644 index 0000000..bf0cb1e --- /dev/null +++ b/c/Recursion/C Program to Factorial using recursion.c @@ -0,0 +1,18 @@ +#include +int fact(int); +int main() +{ + int num,f; + printf("\nEnter a number: "); + scanf("%d",&num); + f=fact(num); + printf("\nFactorial of %d is: %d",num,f); + return 0; +} +int fact(int n) +{ + if(n==1) + return 1; + else + return (n*fact(n-1)); +} \ No newline at end of file diff --git a/c/Recursion/C Program to Find GCD of given Numbers using Recursion.c b/c/Recursion/C Program to Find GCD of given Numbers using Recursion.c new file mode 100644 index 0000000..5e2e917 --- /dev/null +++ b/c/Recursion/C Program to Find GCD of given Numbers using Recursion.c @@ -0,0 +1,32 @@ +/* + * C Program to find GCD of given Numbers using Recursion + */ +#include + +int gcd(int, int); + +int main() +{ + int a, b, result; + printf("Enter the two numbers to find their GCD: "); + scanf("%d%d", &a, &b); + result = gcd(a, b); + printf("The GCD of %d and %d is %d.\n", a, b, result); +} + +int gcd(int a, int b) +{ + while (a != b) + { + if (a > b) + { + return gcd(a - b, b); + } + else + { + return gcd(a, b - a); + } + } + return a; +} +} \ No newline at end of file diff --git a/c/Recursion/C Program to Find LCM of a Number using Recursion.c b/c/Recursion/C Program to Find LCM of a Number using Recursion.c new file mode 100644 index 0000000..5b70ce7 --- /dev/null +++ b/c/Recursion/C Program to Find LCM of a Number using Recursion.c @@ -0,0 +1,29 @@ +/* + * C Program to Find LCM of a Number using Recursion + */ +#include + +int lcm(int, int); + +int main() +{ + int a, b, result; + int prime[100]; + printf("Enter two numbers: "); + scanf("%d%d", &a, &b); + result = lcm(a, b); + printf("The LCM of %d and %d is %d\n", a, b, result); + return 0; +} + +int lcm(int a, int b) +{ + static int common = 1; + if (common % a == 0 && common % b == 0) + { + return common; + } + common++; + lcm(a, b); + return common; +} \ No newline at end of file diff --git a/c/Recursion/C Program to Find Sum of Digits of a Number using Recursion.c b/c/Recursion/C Program to Find Sum of Digits of a Number using Recursion.c new file mode 100644 index 0000000..69b3469 --- /dev/null +++ b/c/Recursion/C Program to Find Sum of Digits of a Number using Recursion.c @@ -0,0 +1,28 @@ +/* + * C Program to find Sum of Digits of a Number using Recursion + */ +#include + +int sum (int a); + +int main() +{ + int num, result; + printf("Enter the number: "); + scanf("%d", &num); + result = sum(num); + printf("Sum of digits in %d is %d\n", num, result); + return 0; +} + +int sum (int num) +{ + if (num != 0) + { + return (num % 10 + sum (num / 10)); + } + else + { + return 0; + } +} \ No newline at end of file diff --git a/c/Recursion/C Program to Find the Biggest Number in an Array of Numbers using Recursion.c b/c/Recursion/C Program to Find the Biggest Number in an Array of Numbers using Recursion.c new file mode 100644 index 0000000..cb56990 --- /dev/null +++ b/c/Recursion/C Program to Find the Biggest Number in an Array of Numbers using Recursion.c @@ -0,0 +1,50 @@ +/* + * C Program to find the Biggest Number in an Array of Numbers using + * Recursion + */ +#include + +int large(int[], int, int); + +int main() +{ + int size; + int largest; + int list[20]; + int i; + printf("Enter size of the list:"); + scanf("%d", &size); + printf("Printing the list:\n"); + for (i = 0; i < size ; i++) + { + list[i] = rand() % size; + printf("%d\t", list[i]); + } + if (size == 0) + { + printf("Empty list\n"); + } + else + { + largest = list[0]; + largest = large(list, size - 1, largest); + printf("\nThe largest number in the list is: %d\n", largest); + } +} +int large(int list[], int size, int largest) +{ + if (size == 1) + return largest; + if (size > -1) + { + if (list[size] > largest) + { + largest = list[size]; + } + return(largest = large(list, size - 1, largest)); + } + else + { + return largest; + } +} \ No newline at end of file diff --git a/c/Recursion/C Program to Find the Factorial of a Number using Recursion.c b/c/Recursion/C Program to Find the Factorial of a Number using Recursion.c new file mode 100644 index 0000000..bbc5721 --- /dev/null +++ b/c/Recursion/C Program to Find the Factorial of a Number using Recursion.c @@ -0,0 +1,35 @@ +/* + * C Program to find factorial of a given number using recursion + */ +#include + +int factorial(int); + +int main() +{ + int num; + int result; + printf("Enter a number to find it's Factorial: "); + scanf("%d", &num); + if (num < 0) + { + printf("Factorial of negative number not possible\n"); + } + else + { + result = factorial(num); + printf("The Factorial of %d is %d.\n", num, result); + } + return 0; +} +int factorial(int num) +{ + if (num == 0 || num == 1) + { + return 1; + } + else + { + return(num * factorial(num - 1)); + } +} \ No newline at end of file diff --git a/c/Recursion/C Program to Find the Length of the String using Recursion.c b/c/Recursion/C Program to Find the Length of the String using Recursion.c new file mode 100644 index 0000000..0298727 --- /dev/null +++ b/c/Recursion/C Program to Find the Length of the String using Recursion.c @@ -0,0 +1,68 @@ +/* + * Recursive C program to find length of a linked list + */ +#include +#include + +struct node +{ + int a; + struct node *next; +}; + +void generate(struct node **); +int length(struct node*); +void delete(struct node **); + +int main() +{ + struct node *head = NULL; + int count; + generate(&head); + count = length(head); + printf("The number of nodes are: %d\n", count); + delete(&head); + return 0; +} + +void generate(struct node **head) +{ + /* for unknown number of nodes use num = rand() % 20; */ + int num = 10, i; + struct node *temp; + for (i = 0; i < num; i++) + { + temp = (struct node *)malloc(sizeof(struct node)); + temp->a = i; + if (*head == NULL) + { + *head = temp; + (*head)->next = NULL; + } + else + { + temp->next = *head; + *head = temp; + } + } +} + +int length(struct node *head) +{ + if (head->next == NULL) + { + return 1; + } + return (1 + length(head->next)); +} + +void delete(struct node **head) +{ + struct node *temp; + while (*head != NULL) + { + temp = *head; + *head = (*head)->next; + free(temp); + } +} \ No newline at end of file diff --git a/c/Recursion/C Program to Find the NCr value by using recursive function.c b/c/Recursion/C Program to Find the NCr value by using recursive function.c new file mode 100644 index 0000000..7e0cefb --- /dev/null +++ b/c/Recursion/C Program to Find the NCr value by using recursive function.c @@ -0,0 +1,20 @@ +#include +int main() +{ + int n,r,ncr; + printf("Enter any two numbers->"); + scanf("%d %d",&n,&r); + ncr=fact(n)/(fact(r)*fact(n-r)); + printf("The NCR factor of %d and %d is %d",n,r,ncr); + return 0; +} +int fact(int n) +{ + int i=1; + while(n!=0) + { + i=i*n; + n--; + } + return i; +} \ No newline at end of file diff --git a/c/Recursion/C Program to Find the Nth Fibonacci Number using Recursion.c b/c/Recursion/C Program to Find the Nth Fibonacci Number using Recursion.c new file mode 100644 index 0000000..6556702 --- /dev/null +++ b/c/Recursion/C Program to Find the Nth Fibonacci Number using Recursion.c @@ -0,0 +1,38 @@ +/* + * C Program to find the nth number in Fibonacci series using recursion + */ +#include +int fibo(int); + +int main() +{ + int num; + int result; + printf("Enter the nth number in fibonacci series: "); + scanf("%d", &num); + if (num < 0) + { + printf("Fibonacci of negative number is not possible.\n"); + } + else + { + result = fibo(num); + printf("The %d number in fibonacci series is %d\n", num, result); + } + return 0; +} +int fibo(int num) +{ + if (num == 0) + { + return 0; + } + else if (num == 1) + { + return 1; + } + else + { + return(fibo(num - 1) + fibo(num - 2)); + } +} \ No newline at end of file diff --git a/c/Recursion/C Program to Find whether a Number is Prime or Not using Recursion.c b/c/Recursion/C Program to Find whether a Number is Prime or Not using Recursion.c new file mode 100644 index 0000000..42f2d56 --- /dev/null +++ b/c/Recursion/C Program to Find whether a Number is Prime or Not using Recursion.c @@ -0,0 +1,42 @@ +/* + * C Program to find whether a Number is Prime or Not using Recursion + */ +#include + +int primeno(int, int); + +int main() +{ + int num, check; + printf("Enter a number: "); + scanf("%d", &num); + check = primeno(num, num / 2); + if (check == 1) + { + printf("%d is a prime number\n", num); + } + else + { + printf("%d is not a prime number\n", num); + } + return 0; +} + +int primeno(int num, int i) +{ + if (i == 1) + { + return 1; + } + else + { + if (num % i == 0) + { + return 0; + } + else + { + return primeno(num, i - 1); + } + } +} \ No newline at end of file diff --git a/c/Recursion/C Program to Implement Selection Sort Recursively.c b/c/Recursion/C Program to Implement Selection Sort Recursively.c new file mode 100644 index 0000000..eb913bf --- /dev/null +++ b/c/Recursion/C Program to Implement Selection Sort Recursively.c @@ -0,0 +1,48 @@ +/* + * C Program to Implement Selection Sort Recursively + */ +#include + +void selection(int [], int, int, int, int); + +int main() +{ + int list[30], size, temp, i, j; + printf("Enter the size of the list: "); + scanf("%d", &size); + printf("Enter the elements in list:\n"); + for (i = 0; i < size; i++) + { + scanf("%d", &list[i]); + } + selection(list, 0, 0, size, 1); + printf("The sorted list in ascending order is\n"); + for (i = 0; i < size; i++) + { + printf("%d ", list[i]); + } + return 0; +} + +void selection(int list[], int i, int j, int size, int flag) +{ + int temp; + if (i < size - 1) + { + if (flag) + { + j = i + 1; + } + if (j < size) + { + if (list[i] > list[j]) + { + temp = list[i]; + list[i] = list[j]; + list[j] = temp; + } + selection(list, i, j + 1, size, 0); + } + selection(list, i + 1, 0, size, 1); + } +} \ No newline at end of file diff --git a/c/Recursion/C Program to Input Few Numbers & Perform Merge Sort on them using Recursion.c b/c/Recursion/C Program to Input Few Numbers & Perform Merge Sort on them using Recursion.c new file mode 100644 index 0000000..51b8ad3 --- /dev/null +++ b/c/Recursion/C Program to Input Few Numbers & Perform Merge Sort on them using Recursion.c @@ -0,0 +1,82 @@ +/* + * C Program to Input Few Numbers & Perform Merge Sort on them using Recursion + */ + +#include + +void mergeSort(int [], int, int, int); +void partition(int [],int, int); + +int main() +{ + int list[50]; + int i, size; + printf("Enter total number of elements:"); + scanf("%d", &size); + printf("Enter the elements:\n"); + for(i = 0; i < size; i++) + { + scanf("%d", &list[i]); + } + partition(list, 0, size - 1); + printf("After merge sort:\n"); + for(i = 0; i < size; i++) + { + printf("%d ",list[i]); + } + return 0; +} + +void partition(int list[],int low,int high) +{ + int mid; + if(low < high) + { + mid = (low + high) / 2; + partition(list, low, mid); + partition(list, mid + 1, high); + mergeSort(list, low, mid, high); + } +} + +void mergeSort(int list[],int low,int mid,int high) +{ + int i, mi, k, lo, temp[50]; + lo = low; + i = low; + mi = mid + 1; + while ((lo <= mid) && (mi <= high)) + { + if (list[lo] <= list[mi]) + { + temp[i] = list[lo]; + lo++; + } + else + { + temp[i] = list[mi]; + mi++; + } + i++; + } + if (lo > mid) + { + for (k = mi; k <= high; k++) + { + temp[i] = list[k]; + i++; + } + } + else + { + for (k = lo; k <= mid; k++) + { + temp[i] = list[k]; + i++; + } + } + for (k = low; k <= high; k++) + { + list[k] = temp[k]; + } +} \ No newline at end of file diff --git a/c/Recursion/C Program to Multiply using Recursion.c b/c/Recursion/C Program to Multiply using Recursion.c new file mode 100644 index 0000000..2c3f1ef --- /dev/null +++ b/c/Recursion/C Program to Multiply using Recursion.c @@ -0,0 +1,22 @@ +#include +int multiply(int,int); +int main() +{ + int a,b,p; + printf("Enter any two integers: "); + scanf("%d%d",&a,&b); + p = multiply(a,b); + printf("Multiplication of two integers is %d",p); + return 0; +} +int multiply(int a,int b) +{ + static int p=0,i=0; + if(i < a) + { + p = p+ b; + i++; + multiply(a,b); + } + return p; +} \ No newline at end of file diff --git a/c/Recursion/C Program to Perform Binary Search using Recursion.c b/c/Recursion/C Program to Perform Binary Search using Recursion.c new file mode 100644 index 0000000..9d50d61 --- /dev/null +++ b/c/Recursion/C Program to Perform Binary Search using Recursion.c @@ -0,0 +1,67 @@ +/* + * C Program to Perform Binary Search using Recursion + */ +#include + +void binary_search(int [], int, int, int); +void bubble_sort(int [], int); + +int main() +{ + int key, size, i; + int list[25]; + printf("Enter size of a list: "); + scanf("%d", &size); + printf("Generating random numbers\n"); + for(i = 0; i < size; i++) + { + list[i] = rand() % 100; + printf("%d ", list[i]); + } + bubble_sort(list, size); + printf("\n\n"); + printf("Enter key to search\n"); + scanf("%d", &key); + binary_search(list, 0, size, key); +} + +void bubble_sort(int list[], int size) +{ + int temp, i, j; + for (i = 0; i < size; i++) + { + for (j = i; j < size; j++) + { + if (list[i] > list[j]) + { + temp = list[i]; + list[i] = list[j]; + list[j] = temp; + } + } + } +} + +void binary_search(int list[], int lo, int hi, int key) +{ + int mid; + if (lo > hi) + { + printf("Key not found\n"); + return; + } + mid = (lo + hi) / 2; + if (list[mid] == key) + { + printf("Key found\n"); + } + else if (list[mid] > key) + { + binary_search(list, lo, mid - 1, key); + } + else if (list[mid] < key) + { + binary_search(list, mid + 1, hi, key); + } +} +} \ No newline at end of file diff --git a/c/Recursion/C Program to Perform Matrix Multiplication using Recursion.c b/c/Recursion/C Program to Perform Matrix Multiplication using Recursion.c new file mode 100644 index 0000000..9dc6fa0 --- /dev/null +++ b/c/Recursion/C Program to Perform Matrix Multiplication using Recursion.c @@ -0,0 +1,79 @@ +/* + * C Program to Perform Matrix Multiplication using Recursion + */ +#include + +void multiply(int, int, int [][10], int, int, int [][10], int [][10]); +void display(int, int, int[][10]); + +int main() +{ + int a[10][10], b[10][10], c[10][10] = {0}; + int m1, n1, m2, n2, i, j, k; + printf("Enter rows and columns for Matrix A respectively: "); + scanf("%d%d", &m1, &n1); + printf("Enter rows and columns for Matrix B respectively: "); + scanf("%d%d", &m2, &n2); + if (n1 != m2) + { + printf("Matrix multiplication not possible.\n"); + } + else + { + printf("Enter elements in Matrix A:\n"); + for (i = 0; i < m1; i++) + for (j = 0; j < n1; j++) + { + scanf("%d", &a[i][j]); + } + printf("\nEnter elements in Matrix B:\n"); + for (i = 0; i < m2; i++) + for (j = 0; j < n2; j++) + { + scanf("%d", &b[i][j]); + } + multiply(m1, n1, a, m2, n2, b, c); + } + printf("On matrix multiplication of A and B the result is:\n"); + display(m1, n2, c); +} + +void multiply (int m1, int n1, int a[10][10], int m2, int n2, int b[10][10], int c[10][10]) +{ + static int i = 0, j = 0, k = 0; + if (i >= m1) + { + return; + } + else if (i < m1) + { + if (j < n2) + { + if (k < n1) + { + c[i][j] += a[i][k] * b[k][j]; + k++; + multiply(m1, n1, a, m2, n2, b, c); + } + k = 0; + j++; + multiply(m1, n1, a, m2, n2, b, c); + } + j = 0; + i++; + multiply(m1, n1, a, m2, n2, b, c); + } +} + +void display(int m1, int n2, int c[10][10]) +{ + int i, j; + for (i = 0; i < m1; i++) + { + for (j = 0; j < n2; j++) + { + printf("%d ", c[i][j]); + } + printf("\n"); + } +} \ No newline at end of file diff --git a/c/Recursion/C Program to Perform Quick Sort on a set of Entries from a File using Recursion.c b/c/Recursion/C Program to Perform Quick Sort on a set of Entries from a File using Recursion.c new file mode 100644 index 0000000..0d997d9 --- /dev/null +++ b/c/Recursion/C Program to Perform Quick Sort on a set of Entries from a File using Recursion.c @@ -0,0 +1,60 @@ +/* +* C Program to Perform Quick Sort on a set of Entries from a File +* using Recursion +*/ +#include + +void quicksort (int [], int, int); + +int main() +{ + int list[50]; + int size, i; + printf("Enter the number of elements: "); + scanf("%d", &size); + printf("Enter the elements to be sorted:\n"); + for (i = 0; i < size; i++) + { + scanf("%d", &list[i]); + } + quicksort(list, 0, size - 1); + printf("After applying quick sort\n"); + for (i = 0; i < size; i++) + { + printf("%d ", list[i]); + } + printf("\n"); + return 0; +} +void quicksort(int list[], int low, int high) +{ + int pivot, i, j, temp; + if (low < high) + { + pivot = low; + i = low; + j = high; + while (i < j) + { + while (list[i] <= list[pivot] && i <= high) + { + i++; + } + while (list[j] > list[pivot] && j >= low) + { + j--; + } + if (i < j) + { + temp = list[i]; + list[i] = list[j]; + list[j] = temp; + } + } + temp = list[j]; + list[j] = list[pivot]; + list[pivot] = temp; + quicksort(list, low, j - 1); + quicksort(list, j + 1, high); + } +} \ No newline at end of file diff --git a/c/Recursion/C Program to Print Binary Equivalent of an Integer using Recursion.c b/c/Recursion/C Program to Print Binary Equivalent of an Integer using Recursion.c new file mode 100644 index 0000000..5e26e51 --- /dev/null +++ b/c/Recursion/C Program to Print Binary Equivalent of an Integer using Recursion.c @@ -0,0 +1,28 @@ +/* + * C Program to Print Binary Equivalent of an Integer using Recursion + */ +#include + +int binary_conversion(int); + +int main() +{ + int num, bin; + printf("Enter a decimal number: "); + scanf("%d", &num); + bin = binary_conversion(num); + printf("The binary equivalent of %d is %d\n", num, bin); +} + +int binary_conversion(int num) +{ + if (num == 0) + { + return 0; + } + else + { + return (num % 2) + 10 * binary_conversion(num / 2); + } +} +} \ No newline at end of file diff --git a/c/Recursion/C Program to Print the Alternate Nodes in a Linked List using Recursion.c b/c/Recursion/C Program to Print the Alternate Nodes in a Linked List using Recursion.c new file mode 100644 index 0000000..01bae46 --- /dev/null +++ b/c/Recursion/C Program to Print the Alternate Nodes in a Linked List using Recursion.c @@ -0,0 +1,73 @@ +/* + * C Program to Print the Alternate Nodes in a Linked List using Recursion + */ +#include +#include + +struct node +{ + int a; + struct node *next; +}; + +void generate(struct node **); +void display(struct node *); +void delete(struct node **); + +int main() +{ + struct node *head = NULL; + generate(&head); + printf("\nDisplaying the alternate nodes\n"); + display(head); + delete(&head); + return 0; +} + +void display(struct node *head) +{ + static flag = 0; + if(head != NULL) + { + if (!(flag % 2)) + { + printf("%d ", head->a); + } + flag++; + display(head->next); + } +} + +void generate(struct node **head) +{ + int num, i; + struct node *temp; + printf("Enter length of list: "); + scanf("%d", &num); + for (i = num; i > 0; i--) + { + temp = (struct node *)malloc(sizeof(struct node)); + temp->a = i; + if (*head == NULL) + { + *head = temp; + (*head)->next = NULL; + } + else + { + temp->next = *head; + *head = temp; + } + } +} + +void delete(struct node **head) +{ + struct node *temp; + while (*head != NULL) + { + temp = *head; + *head = (*head)->next; + free(temp); + } +} \ No newline at end of file diff --git a/c/Recursion/C Program to Reverse a Stack using Recursion.c b/c/Recursion/C Program to Reverse a Stack using Recursion.c new file mode 100644 index 0000000..2e7c910 --- /dev/null +++ b/c/Recursion/C Program to Reverse a Stack using Recursion.c @@ -0,0 +1,89 @@ +/* + * C Program to Reverse a Stack using Recursion + */ +#include +#include + +struct node +{ + int a; + struct node *next; +}; + +void generate(struct node **); +void display(struct node *); +void stack_reverse(struct node **, struct node **); +void delete(struct node **); + +int main() +{ + struct node *head = NULL; + generate(&head); + printf("\nThe sequence of contents in stack\n"); + display(head); + printf("\nInversing the contents of the stack\n"); + if (head != NULL) + { + stack_reverse(&head, &(head->next)); + } + printf("\nThe contents in stack after reversal\n"); + display(head); + delete(&head); + return 0; +} + +void stack_reverse(struct node **head, struct node **head_next) +{ + struct node *temp; + if (*head_next != NULL) + { + temp = (*head_next)->next; + (*head_next)->next = (*head); + *head = *head_next; + *head_next = temp; + stack_reverse(head, head_next); + } +} + +void display(struct node *head) +{ + if (head != NULL) + { + printf("%d ", head->a); + display(head->next); + } +} + +void generate(struct node **head) +{ + int num, i; + struct node *temp; + printf("Enter length of list: "); + scanf("%d", &num); + for (i = num; i > 0; i--) + { + temp = (struct node *)malloc(sizeof(struct node)); + temp->a = i; + if (*head == NULL) + { + *head = temp; + (*head)->next = NULL; + } + else + { + temp->next = *head; + *head = temp; + } + } +} + +void delete(struct node **head) +{ + struct node *temp; + while (*head != NULL) + { + temp = *head; + *head = (*head)->next; + free(temp); + } +} \ No newline at end of file diff --git a/c/Recursion/C Program to Reverse a number using recursion.c b/c/Recursion/C Program to Reverse a number using recursion.c new file mode 100644 index 0000000..57f53dd --- /dev/null +++ b/c/Recursion/C Program to Reverse a number using recursion.c @@ -0,0 +1,26 @@ +#include +int main() +{ + int num,reverse; + printf("Enter any number: "); + scanf("%d",&num); + reverse=rev(num); + printf("Reverse of number: %d",reverse); + return 0; +} +int rev(int num) +{ + static sum,r; + if(num) + { + r=num%10; + sum=sum*10+r; + rev(num/10); + } + else + return 0; + return sum; +} +Sample output: +Enter any number: 784 +Reverse of number: 48 \ No newline at end of file diff --git a/c/Recursion/C Program to Reverse a string by recursion.c b/c/Recursion/C Program to Reverse a string by recursion.c new file mode 100644 index 0000000..5f0cc1a --- /dev/null +++ b/c/Recursion/C Program to Reverse a string by recursion.c @@ -0,0 +1,23 @@ +#include +#define MAX 100 +char* reverse(char[]); +int main() +{ + char str[MAX],*rev; + printf("Enter any string: "); + scanf("%s",str); + rev = reverse(str); + printf("Reversed string is: %s",rev); + return 0; +} +char* reverse(char str[]) +{ + static int i=0; + static char rev[MAX]; + if(*str) + { + reverse(str+1); + rev[i++] = *str; + } + return rev; +} \ No newline at end of file diff --git a/c/Recursion/C Program to Reverse the String using Recursion.c b/c/Recursion/C Program to Reverse the String using Recursion.c new file mode 100644 index 0000000..e48fd83 --- /dev/null +++ b/c/Recursion/C Program to Reverse the String using Recursion.c @@ -0,0 +1,31 @@ +/* + * C Program to Reverse the String using Recursion + */ +#include +#include + +void reverse(char [], int, int); +int main() +{ + char str1[20]; + int size; + printf("Enter a string to reverse: "); + scanf("%s", str1); + size = strlen(str1); + reverse(str1, 0, size - 1); + printf("The string after reversing is: %s\n", str1); + return 0; +} + +void reverse(char str1[], int index, int size) +{ + char temp; + temp = str1[index]; + str1[index] = str1[size - index]; + str1[size - index] = temp; + if (index == size / 2) + { + return; + } + reverse(str1, index + 1, size); +} \ No newline at end of file diff --git a/c/Recursion/C Program to Solve Tower-of-Hanoi Problem using Recursion.c b/c/Recursion/C Program to Solve Tower-of-Hanoi Problem using Recursion.c new file mode 100644 index 0000000..0030ac7 --- /dev/null +++ b/c/Recursion/C Program to Solve Tower-of-Hanoi Problem using Recursion.c @@ -0,0 +1,39 @@ +/* + * C program for Tower of Hanoi using Recursion + */ +#include + +void towers(int, char, char, char); + +int main() +{ + int num; + printf("Enter the number of disks : "); + scanf("%d", &num); + printf("The sequence of moves involved in the Tower of Hanoi are :\n"); + towers(num, 'A', 'C', 'B'); + return 0; +} +void towers(int num, char frompeg, char topeg, char auxpeg) +{ + if (num == 1) + { + printf("\n Move disk 1 from peg %c to peg %c", frompeg, topeg); + return; + } + towers(num - 1, frompeg, auxpeg, topeg); + printf("\n Move disk %d from peg %c to peg %c", num, frompeg, topeg); + towers(num - 1, auxpeg, topeg, frompeg); +} + +/* +Enter the number of disks : 3 +The sequence of moves involved in the Tower of Hanoi are : + +Move disk 1 from peg A to peg C +Move disk 2 from peg A to peg B +Move disk 1 from peg C to peg B +Move disk 3 from peg A to peg C +Move disk 1 from peg B to peg A +Move disk 2 from peg B to peg C +Move disk 1 from peg A to peg C \ No newline at end of file diff --git a/c/Recursion/C Program to Sum of N numbers by recursion.c b/c/Recursion/C Program to Sum of N numbers by recursion.c new file mode 100644 index 0000000..ac00662 --- /dev/null +++ b/c/Recursion/C Program to Sum of N numbers by recursion.c @@ -0,0 +1,20 @@ +#include +int main() +{ + int n,sum; + printf("Enter the value of n: "); + scanf("%d",&n); + sum = getsum(n); + printf("Sum of n numbers: %d",sum); + return 0; +} +int getsum(n) +{ + static int sum=0; + if(n>0) + { + sum = sum + n; + getsum(n-1); + } + return sum; +} \ No newline at end of file diff --git a/c/Recursion/C Program to Traverse the Tree Recursively.c b/c/Recursion/C Program to Traverse the Tree Recursively.c new file mode 100644 index 0000000..9f0922d --- /dev/null +++ b/c/Recursion/C Program to Traverse the Tree Recursively.c @@ -0,0 +1,137 @@ +/* + * C Program to Traverse the Tree Recursively + */ +#include +#include + +struct node +{ + int a; + struct node *left; + struct node *right; +}; + +void generate(struct node **, int); +void infix(struct node *); +void postfix(struct node *); +void prefix(struct node *); +void delete(struct node **); + +int main() +{ + struct node *head = NULL; + int choice = 0, num, flag = 0, key; + do + { + printf("\nEnter your choice:\n1. Insert\n2. Traverse via infix\n3.Traverse via prefix\n4. Traverse via postfix\n5. Exit\nChoice: "); + scanf("%d", &choice); + switch(choice) + { + case 1: + printf("Enter element to insert: "); + scanf("%d", &num); + generate(&head, num); + break; + case 2: + infix(head); + break; + case 3: + prefix(head); + break; + case 4: + postfix(head); + break; + case 5: + delete(&head); + printf("Memory Cleared\nPROGRAM TERMINATED\n"); + break; + default: + printf("Not a valid input, try again\n"); + } + } + while (choice != 5); + return 0; +} + +void generate(struct node **head, int num) +{ + struct node *temp = *head, *prev = *head; + if (*head == NULL) + { + *head = (struct node *)malloc(sizeof(struct node)); + (*head)->a = num; + (*head)->left = (*head)->right = NULL; + } + else + { + while (temp != NULL) + { + if (num > temp->a) + { + prev = temp; + temp = temp->right; + } + else + { + prev = temp; + temp = temp->left; + } + } + temp = (struct node *)malloc(sizeof(struct node)); + temp->a = num; + if (num >= prev->a) + { + prev->right = temp; + } + else + { + prev->left = temp; + } + } +} + +void infix(struct node *head) +{ + if (head) + { + infix(head->left); + printf("%d ", head->a); + infix(head->right); + } +} + +void prefix(struct node *head) +{ + if (head) + { + printf("%d ", head->a); + prefix(head->left); + prefix(head->right); + } +} + +void postfix(struct node *head) +{ + if (head) + { + postfix(head->left); + postfix(head->right); + printf("%d ", head->a); + } +} + +void delete(struct node **head) +{ + if (*head != NULL) + { + if ((*head)->left) + { + delete(&(*head)->left); + } + if ((*head)->right) + { + delete(&(*head)->right); + } + free(*head); + } +} \ No newline at end of file diff --git a/c/Recursion/C Program to find HCF of a given Number using Recursion.c b/c/Recursion/C Program to find HCF of a given Number using Recursion.c new file mode 100644 index 0000000..ee50edd --- /dev/null +++ b/c/Recursion/C Program to find HCF of a given Number using Recursion.c @@ -0,0 +1,31 @@ +/* + * C Program to find HCF of a given Number using Recursion + */ +#include + +int hcf(int, int); + +int main() +{ + int a, b, result; + printf("Enter the two numbers to find their HCF: "); + scanf("%d%d", &a, &b); + result = hcf(a, b); + printf("The HCF of %d and %d is %d.\n", a, b, result); +} + +int hcf(int a, int b) +{ + while (a != b) + { + if (a > b) + { + return hcf(a - b, b); + } + else + { + return hcf(a, b - a); + } + } + return a; +} \ No newline at end of file diff --git a/c/Recursion/C Program to find LCM of two numbers by recursion.c b/c/Recursion/C Program to find LCM of two numbers by recursion.c new file mode 100644 index 0000000..01346b9 --- /dev/null +++ b/c/Recursion/C Program to find LCM of two numbers by recursion.c @@ -0,0 +1,23 @@ +#include +int findlcm(int,int); +int main() +{ + int a,b,l; + printf("Enter any two number "); + scanf("%d%d",&a,&b); + if(a>b) + l = findlcm(a,b); + else + l =findlcm(b,a); + printf("LCM of two number is %d",l); + return 0; +} +int findlcm(int a,int b) +{ + static int temp = 1; + if(temp % b == 0 && temp % a == 0) + return temp; + temp++; + findlcm(a,b); + return temp; +} \ No newline at end of file diff --git a/c/Recursion/C Program to find Largest Number of array using recursion.c b/c/Recursion/C Program to find Largest Number of array using recursion.c new file mode 100644 index 0000000..c75cdfd --- /dev/null +++ b/c/Recursion/C Program to find Largest Number of array using recursion.c @@ -0,0 +1,27 @@ +#include +int getmax(int []); +int size; +int main() +{ + int arr[100],max,i; + printf("Enter the size of the array: "); + scanf("%d",&size); + printf("Enter %d elements of array: ", size); + for(i=0; i + +long power (int, int); + +int main() +{ + int pow, num; + long result; + printf("Enter a number: "); + scanf("%d", &num); + printf("Enter it's power: "); + scanf("%d", &pow); + result = power(num, pow); + printf("%d^%d is %ld", num, pow, result); + return 0; +} + +long power (int num, int pow) +{ + if (pow) + { + return (num * power(num, pow - 1)); + } + return 1; +} \ No newline at end of file diff --git a/c/Recursion/C Program to find Product of 2 Numbers using Recursion.c b/c/Recursion/C Program to find Product of 2 Numbers using Recursion.c new file mode 100644 index 0000000..f1b754a --- /dev/null +++ b/c/Recursion/C Program to find Product of 2 Numbers using Recursion.c @@ -0,0 +1,32 @@ +/* + * C Program to find Product of 2 Numbers using Recursion + */ +#include + +int product(int, int); + +int main() +{ + int a, b, result; + printf("Enter two numbers to find their product: "); + scanf("%d%d", &a, &b); + result = product(a, b); + printf("Product of %d and %d is %d\n", a, b, result); + return 0; +} + +int product(int a, int b) +{ + if (a < b) + { + return product(b, a); + } + else if (b != 0) + { + return (a + product(a, b - 1)); + } + else + { + return 0; + } +} \ No newline at end of file diff --git a/c/Recursion/C Program to find Reverse of a Number using Recursion.c b/c/Recursion/C Program to find Reverse of a Number using Recursion.c new file mode 100644 index 0000000..303ad1f --- /dev/null +++ b/c/Recursion/C Program to find Reverse of a Number using Recursion.c @@ -0,0 +1,36 @@ +/* + * C program to find the reverse of a number using recursion + */ +#include +#include + +int rev(int, int); + +int main() +{ + int num, result; + int length = 0, temp; + printf("Enter an integer number to reverse: "); + scanf("%d", &num); + temp = num; + while (temp != 0) + { + length++; + temp = temp / 10; + } + result = rev(num, length); + printf("The reverse of %d is %d.\n", num, result); + return 0; +} + +int rev(int num, int len) +{ + if (len == 1) + { + return num; + } + else + { + return (((num % 10) * pow(10, len - 1)) + rev(num / 10, --len)); + } +} \ No newline at end of file diff --git a/c/Recursion/C Program to find Sum of N Numbers using Recursion.c b/c/Recursion/C Program to find Sum of N Numbers using Recursion.c new file mode 100644 index 0000000..a610461 --- /dev/null +++ b/c/Recursion/C Program to find Sum of N Numbers using Recursion.c @@ -0,0 +1,31 @@ +/* + * C Program to find Sum of N Numbers using Recursion + */ +#include + +void display(int); + +int main() +{ + int num, result; + printf("Enter the Nth number: "); + scanf("%d", &num); + display(num); + return 0; +} + +void display(int num) +{ + static int i = 1; + if (num == i) + { + printf("%d \n", num); + return; + } + else + { + printf("%d ", i); + i++; + display(num); + } +} \ No newline at end of file diff --git a/c/Recursion/C Program to find the First Capital Letter in a String using Recursion.c b/c/Recursion/C Program to find the First Capital Letter in a String using Recursion.c new file mode 100644 index 0000000..760ed91 --- /dev/null +++ b/c/Recursion/C Program to find the First Capital Letter in a String using Recursion.c @@ -0,0 +1,43 @@ +/* + * C Program to find the first capital letter in a string using + * Recursion + */ +#include +#include +#include + +char caps_check(char *); + +int main() +{ + char string[20], letter; + printf("Enter a string to find it's first capital letter: "); + scanf("%s", string); + letter = caps_check(string); + if (letter == 0) + { + printf("No capital letter is present in %s.\n", string); + } + else + { + printf("The first capital letter in %s is %c.\n", string, letter); + } + return 0; +} +char caps_check(char *string) +{ + static int i = 0; + if (i < strlen(string)) + { + if (isupper(string[i])) + { + return string[i]; + } + else + { + i = i + 1; + return caps_check(string); + } + } + else return 0; +} \ No newline at end of file diff --git a/c/Search_Sorting/C Program for Floyd’s Algorithm.C b/c/Search_Sorting/C Program for Floyd’s Algorithm.C new file mode 100644 index 0000000..dd081bb --- /dev/null +++ b/c/Search_Sorting/C Program for Floyd’s Algorithm.C @@ -0,0 +1,65 @@ +#include +#include +int min(int,int); +void floyds(int p[10][10],int n) +{ + int i,j,k; + for (k=1; k<=n; k++) + for (i=1; i<=n; i++) + for (j=1; j<=n; j++) + if(i==j) + p[i][j]=0; + else + p[i][j]=min(p[i][j],p[i][k]+p[k][j]); +} +int min(int a,int b) +{ + if(a=%d",i,j,p[i][j]); + } + getch(); +} \ No newline at end of file diff --git a/c/Search_Sorting/C Program for Knapsack Problem.C b/c/Search_Sorting/C Program for Knapsack Problem.C new file mode 100644 index 0000000..c0431fb --- /dev/null +++ b/c/Search_Sorting/C Program for Knapsack Problem.C @@ -0,0 +1,62 @@ +#include +#include +int w[10],p[10],v[10][10],n,i,j,cap,x[10]= {0}; +int max(int i,int j) +{ + return ((i>j)?i:j); +} +int knap(int i,int j) +{ + int value; + if(v[i][j]<0) + { + if(j +#include +void hanoi(char,char,char,int); +void main() +{ + int num; + clrscr(); + printf("\nENTER NUMBER OF DISKS: "); + scanf("%d",&num); + printf("\nTOWER OF HANOI FOR %d NUMBER OF DISKS:\n", num); + hanoi('A','B','C',num); + getch(); +} +void hanoi(char from,char to,char other,int n) +{ + if(n<=0) + printf("\nILLEGAL NUMBER OF DISKS"); + if(n==1) + printf("\nMOVE DISK FROM %c TO %c",from,other); + if(n>1) + { + hanoi(from,other,to,n-1); + hanoi(from,to,other,1); + hanoi(to,from,other,n-1); + } +} \ No newline at end of file diff --git a/c/Search_Sorting/C Program for Warshall’s Algorithm.C b/c/Search_Sorting/C Program for Warshall’s Algorithm.C new file mode 100644 index 0000000..6313065 --- /dev/null +++ b/c/Search_Sorting/C Program for Warshall’s Algorithm.C @@ -0,0 +1,55 @@ +#include +#include +#include +int max(int,int); +void warshal(int p[10][10],int n) +{ + int i,j,k; + for (k=1; k<=n; k++) + for (i=1; i<=n; i++) + for (j=1; j<=n; j++) + p[i][j]=max(p[i][j],p[i][k]&&p[k][j]); +} +int max(int a,int b) +{ + ; + if(a>b) + return(a); + else + return(b); +} +void main() +{ + int p[10][10]= + { + 0 + } + ,n,e,u,v,i,j; + clrscr(); + printf("\n Enter the number of vertices:"); + scanf("%d",&n); + printf("\n Enter the number of edges:"); + scanf("%d",&e); + for (i=1; i<=e; i++) + { + printf("\n Enter the end vertices of edge %d:",i); + scanf("%d%d",&u,&v); + p[u][v]=1; + } + printf("\n Matrix of input data: \n"); + for (i=1; i<=n; i++) + { + for (j=1; j<=n; j++) + printf("%d\t",p[i][j]); + printf("\n"); + } + warshal(p,n); + printf("\n Transitive closure: \n"); + for (i=1; i<=n; i++) + { + for (j=1; j<=n; j++) + printf("%d\t",p[i][j]); + printf("\n"); + } + getch(); +} \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Compare Binary and Sequential Search.c b/c/Search_Sorting/C Program to Compare Binary and Sequential Search.c new file mode 100644 index 0000000..5857bc5 --- /dev/null +++ b/c/Search_Sorting/C Program to Compare Binary and Sequential Search.c @@ -0,0 +1,61 @@ +#include +#define MAX 10 +int linearsearch(int numbers[], int key) +{ + int i; + for (i = 0; i < MAX; i++) + { + if (key == numbers[i]) + return i; + } + return -1; +} +int binarysearch(int numbers[], int key) +{ + int l = 0, u = MAX - 1; + int c, mid; + while (l <= u) + { + mid = (l + u) / 2; + if (key == numbers[mid]) + { + return mid; + } + else if (key < numbers[mid]) + { + u = mid - 1; + } + else + l = mid + 1; + } + return -1; +} +int main() +{ + int numbers[MAX]; + int i; + int index, key; + printf("Enter %d numbers : ", MAX); + for (i = 0; i < MAX; i++) + { + scanf("%d", &numbers[i]); + } + printf("\nEnter a key to find using linear search: "); + scanf("%d", &key); + index = linearsearch(numbers, key); + if ( index >= 0) + printf("\n%d found at index %d using linear search.", key, index); + else + printf("\nNot found!!"); + printf("\nEnter %d numbers in increasing order: ", MAX); + for (i = 0 ; i < MAX; i++) + scanf("%d", &numbers[i]); + printf("\nEnter a key to find using binary search: "); + scanf("%d", &key); + index = binarysearch(numbers, key); + if (index >= 0 ) + printf("Found at index %d", index); + else + printf("\nNot found!!!"); + return 0; +} \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Create a Random Graph Using Random Edge Generation.c b/c/Search_Sorting/C Program to Create a Random Graph Using Random Edge Generation.c new file mode 100644 index 0000000..acf671d --- /dev/null +++ b/c/Search_Sorting/C Program to Create a Random Graph Using Random Edge Generation.c @@ -0,0 +1,92 @@ +#include +#include +#include + +#define MAX_VERTICES 30 +#define MAX_EDGES 10 + +typedef unsigned char vertex; + +int main() +{ + /*number of nodes in a graph*/ + srand ( time(NULL) ); + int numberOfVertices = rand() % MAX_VERTICES; + /*number of maximum edges a vertex can have*/ + srand ( time(NULL) ); + int maxNumberOfEdges = rand() % MAX_EDGES; + /*graphs is 2 dimensional array of pointers*/ + if( numberOfVertices == 0) + numberOfVertices++; + vertex ***graph; + printf("Total Vertices = %d, Max # of Edges = %d\n",numberOfVertices, maxNumberOfEdges); + /*generate a dynamic array of random size*/ + if ((graph = (vertex ***) malloc(sizeof(vertex **) * numberOfVertices)) == NULL) + { + printf("Could not allocate memory for graph\n"); + exit(1); + } + /*generate space for edges*/ + int vertexCounter = 0; + /*generate space for vertices*/ + int edgeCounter = 0; + for (vertexCounter = 0; vertexCounter < numberOfVertices; vertexCounter++) + { + if ((graph[vertexCounter] = (vertex **) malloc(sizeof(vertex *) * maxNumberOfEdges)) == NULL) + { + printf("Could not allocate memory for edges\n"); + exit(1); + } + for (edgeCounter = 0; edgeCounter < maxNumberOfEdges; edgeCounter++) + { + if ((graph[vertexCounter][edgeCounter] = (vertex *) malloc(sizeof(vertex))) == NULL) + { + printf("Could not allocate memory for vertex\n"); + exit(1); + } + } + } + /*start linking the graph. All vetrices need not have same number of links*/ + vertexCounter = 0; + edgeCounter = 0; + for (vertexCounter = 0; vertexCounter < numberOfVertices; vertexCounter++) + { + printf("%d:\t",vertexCounter); + for (edgeCounter=0; edgeCounter < maxNumberOfEdges; edgeCounter++) + { + if (rand()%2 == 1) /*link the vertices*/ + { + int linkedVertex = rand() % numberOfVertices; + graph[vertexCounter][edgeCounter] = graph[linkedVertex]; + printf("%d, ", linkedVertex); + } + else /*make the link NULL*/ + { + graph[vertexCounter][edgeCounter] = NULL; + } + } + printf("\n"); + } + return 1; +} + +/* +Total Vertices = 18, Max # of Edges = 8 +0: 12, 9, 6, +1: 6, 1, +2: 7, 4, 1, 9, 3, 5, +3: 8, 13, 1, 12, 13, 6, +4: 5, 11, +5: 6, 6, 6, 5, 11, +6: 6, 5, 16, 10, 1, 13, +7: 14, 13, 13, 12, +8: 6, 12, 4, +9: 6, 17, 4, 10, +10: 6, 6, 11, 10, +11: 2, 16, +12: 3, 15, 7, +13: 6, 15, 3, 9, 15, +14: 4, 10, +15: 5, 4, 3, +16: 17, 11, +17: 0, 7, \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Find Maximum Element in an Array using Binary Search.c b/c/Search_Sorting/C Program to Find Maximum Element in an Array using Binary Search.c new file mode 100644 index 0000000..e75dfd6 --- /dev/null +++ b/c/Search_Sorting/C Program to Find Maximum Element in an Array using Binary Search.c @@ -0,0 +1,45 @@ +#include +void max_heapify(int *a, int i, int n) +{ + int j, temp; + temp = a[i]; + j = 2 * i; + while (j <= n) + { + if (j < n && a[j+1] > a[j]) + j = j + 1; + if (temp > a[j]) + break; + else if (temp <= a[j]) + { + a[j / 2] = a[j]; + j = 2 * j; + } + } + a[j/2] = temp; + return; +} +int binarysearchmax(int *a,int n) +{ + int i; + for(i = n/2; i >= 1; i--) + { + max_heapify(a,i,n); + } + return a[1]; +} +int main() +{ + int n, i, x, max; + int a[20]; + printf("Enter no of elements of array\n"); + scanf("%d", &n); + printf("\nEnter %d elements: ", n); + for (i = 1; i <= n; i++) + { + scanf("%d", &a[i]); + } + max = binarysearchmax(a, n); + printf("\nMaximum element is : %d", max); + return 0; +} \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Find Minimum Element in an Array using Linear Search.c b/c/Search_Sorting/C Program to Find Minimum Element in an Array using Linear Search.c new file mode 100644 index 0000000..901b02c --- /dev/null +++ b/c/Search_Sorting/C Program to Find Minimum Element in an Array using Linear Search.c @@ -0,0 +1,27 @@ +#include +#define MAX 10 +int min_linearsearch(int numbers[]) +{ + int min = numbers[0]; + int i; + for (i = 1; i < MAX; i++) + { + if (min > numbers[i]) + min = numbers[i]; + } + return min; +} +int main() +{ + int numbers[MAX]; + int i; + int min ; + printf("Enter %d numbers : ", MAX); + for (i = 0; i < MAX; i++) + { + scanf("%d", &numbers[i]); + } + min = min_linearsearch(numbers); + printf("\nMinimum number in the array is : %d\n", min); + return 0; +} \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Find Second Smallest of n Elements with Given Complexity Constraint.c b/c/Search_Sorting/C Program to Find Second Smallest of n Elements with Given Complexity Constraint.c new file mode 100644 index 0000000..feff225 --- /dev/null +++ b/c/Search_Sorting/C Program to Find Second Smallest of n Elements with Given Complexity Constraint.c @@ -0,0 +1,36 @@ +#include +#include + +main() +{ + int smallest, secondsmallest; + int array[100], size, i; + printf("\n How many elements do you want to enter: "); + scanf("%d", &size); + printf("\nEnter %d elements: ", size); + for (i = 0 ; i < size; i++) + scanf("%d", &array[i]); + if (array[0] < array[1]) + { + smallest = array[0]; + secondsmallest = array[1]; + } + else + { + smallest = array[1]; + secondsmallest = array[0]; + } + for (i = 2; i < size; i++) + { + if (array[i] < smallest) + { + secondsmallest = smallest; + smallest = array[i]; + } + else if (array[i] < secondsmallest) + { + secondsmallest = array[i]; + } + } + printf(" \nSecond smallest element is %d", secondsmallest); +} \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Find kth Largest Element in a Sequence.c b/c/Search_Sorting/C Program to Find kth Largest Element in a Sequence.c new file mode 100644 index 0000000..6dee8fc --- /dev/null +++ b/c/Search_Sorting/C Program to Find kth Largest Element in a Sequence.c @@ -0,0 +1,55 @@ +#include +#include +int partition(int* a, int low, int high) +{ + int left = low; + int pivotIdx = low + (high - low)/2; + int pivot = a[pivotIdx]; + a[pivotIdx] = a[high]; + a[high] = pivot; + pivotIdx = high; + int partitionIdx = low; + while (left < high) + { + if (a[left] < pivot) + { + int tmp = a[left]; + a[left] = a[partitionIdx]; + a[partitionIdx] = tmp; + ++partitionIdx; + } + ++left; + } + a[pivotIdx] = a[partitionIdx]; + a[partitionIdx] = pivot; + return partitionIdx; +} + +int quickselect(int* a, int low, int high, int k) +{ + if (low == high) + return a[low]; + int pivotIdx = partition(a, low, high); + int sizeOfLeftSubArray = pivotIdx - low + 1; + if (sizeOfLeftSubArray > k) + { + return quickselect(a, low, pivotIdx-1, k); + } + else if (sizeOfLeftSubArray < k) + { + return quickselect(a, pivotIdx+1, high, k-sizeOfLeftSubArray); + } + else + { + return a[pivotIdx]; + } +} +int main() +{ + int arr[] = {4, 5, 22, 49, 64, 43, 32, 323, 78, 90}; + int k; + printf("\nEnter the number 'k' to find the 'kth' largest element: "); + scanf("%d", &k); + printf("\nKth largest element is %d", quickselect(arr, 0, 9, k)); + return 0; +} \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Generate All Possible Combinations of a Given List of Numbers.c b/c/Search_Sorting/C Program to Generate All Possible Combinations of a Given List of Numbers.c new file mode 100644 index 0000000..27f0de8 --- /dev/null +++ b/c/Search_Sorting/C Program to Generate All Possible Combinations of a Given List of Numbers.c @@ -0,0 +1,34 @@ +#include +#include +#define N 10 + +void print(int *num, int n) +{ + int i; + for ( i = 0 ; i < n ; i++) + printf("%d ", num[i]); + printf("\n"); +} +int main() +{ + int num[N]; + int *ptr; + int temp; + int i, n, j; + printf("\nHow many number you want to enter: "); + scanf("%d", &n); + printf("\nEnter a list of numbers to see all combinations:\n"); + for (i = 0 ; i < n; i++) + scanf("%d", &num[i]); + for (j = 1; j <= n; j++) + { + for (i = 0; i < n-1; i++) + { + temp = num[i]; + num[i] = num[i+1]; + num[i+1] = temp; + print(num, n); + } + } + return 0; +} \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Generate All the Set Partitions of n Numbers Begining from 1 and so on.c b/c/Search_Sorting/C Program to Generate All the Set Partitions of n Numbers Begining from 1 and so on.c new file mode 100644 index 0000000..5eec825 --- /dev/null +++ b/c/Search_Sorting/C Program to Generate All the Set Partitions of n Numbers Begining from 1 and so on.c @@ -0,0 +1,85 @@ +#include +#include +typedef struct +{ + int first; + int n; + int level; +} Call; + + +void print(int n, int * a) +{ + int i ; + for (i = 0; i <= n; i++) + { + printf("%d", a[i]); + } + printf("\n"); +} + + +void integerPartition(int n, int * a) +{ + int first; + int i; + int top = 0; + int level = 0; + Call * stack = (Call * ) malloc (sizeof(Call) * 1000); + stack[0].first = -1; + stack[0].n = n; + stack[0].level = level; + while (top >= 0) + { + first = stack[top].first; + n = stack[top].n; + level = stack[top].level; + if (n >= 1) + { + if (first == - 1) + { + a[level] = n; + print(level, a); + first = (level == 0) ? 1 : a[level-1]; + i = first; + } + else + { + i = first; + i++; + } + if (i <= n / 2) + { + a[level] = i; + stack[top].first = i; + top++; + stack[top].first = -1; + stack[top].n = n - i; + stack[top].level = level + 1; + } + else + { + top--; + } + } + else + { + top --; + } + } +} + +int main() +{ + int N = 1; + int * a = (int * ) malloc(sizeof(int) * N); + int i; + printf("\nEnter a number N to generate all set partition from 1 to N: "); + scanf("%d", &N); + for ( i = 1; i <= N; i++) + { + printf("\nInteger partition for %d is: \n", i); + integerPartition (i, a); + } + return(0); +} \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Implement Bitonic sort.c b/c/Search_Sorting/C Program to Implement Bitonic sort.c new file mode 100644 index 0000000..82bb36a --- /dev/null +++ b/c/Search_Sorting/C Program to Implement Bitonic sort.c @@ -0,0 +1,99 @@ +/* + * C Program to Implement Bitonic sort + */ +#include +#include +#define MAX 8 +#define SWAP(x,y) t = x; x = y; y = t; + +void compare(); +void bitonicmerge(int, int, int); +void recbitonic(int, int, int); +void sort(); + +int data[MAX]; +int up = 1; +int down = 0; + +int main() +{ + int i; + printf("\nEnter the data"); + for (i = 0; i < MAX ; i++) + { + scanf("%d", &data[i]); + } + sort(); + for (i = 0; i < MAX; i++) + { + printf("%d ", data[i]); + } +} +/* + * compare and swap based on dir + */ +void compare(int i, int j, int dir) +{ + int t; + if (dir == (data[i] > data[j])) + { + SWAP(data[i], data[j]); + } +} +/* + * Sorts a bitonic sequence in ascending order if dir=1 + * otherwise in descending order + */ +void bitonicmerge(int low, int c, int dir) +{ + int k, i; + if (c > 1) + { + k = c / 2; + for (i = low; i < low+k ; i++) + compare(i, i+k, dir); + bitonicmerge(low, k, dir); + bitonicmerge(low+k, k, dir); + } +} +/* + * Generates bitonic sequence by sorting recursively + * two halves of the array in opposite sorting orders + * bitonicmerge will merge the resultant data + */ +void recbitonic(int low, int c, int dir) +{ + int k; + if (c > 1) + { + k = c / 2; + recbitonic(low, k, up); + recbitonic(low + k, k, down); + bitonicmerge(low, c, dir); + } +} + +/* + * Sorts the entire array + */ +void sort() +{ + recbitonic(0, MAX, up); +} +/* +*OUTPUT: +/*Average case + +Enter the data +3 5 8 9 7 4 2 1 +1 2 3 4 5 7 8 9 +$ a.out +/*Worst case +Enter the data +100 99 98 97 96 95 94 93 +93 94 95 96 97 98 99 100 +/*Best case +Enter the data +1111 2222 3333 4444 5555 6666 7777 8888 +1111 2222 3333 4444 5555 6666 7777 8888 +*/ \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Implement BogoSort in an Integer Array.c b/c/Search_Sorting/C Program to Implement BogoSort in an Integer Array.c new file mode 100644 index 0000000..8d05e0b --- /dev/null +++ b/c/Search_Sorting/C Program to Implement BogoSort in an Integer Array.c @@ -0,0 +1,115 @@ +/* + * C Program to Implement BogoSort in an Integer Array + */ +#include +#include + +#define size 7 +/* Function Prototypes */ + +int is_sorted(int *, int); +void shuffle(int *, int); +void bogosort(int *, int); + +int main() +{ + int numbers[size]; + int i; + printf("Enter the elements of array:"); + for (i = 0; i < size; i++) + { + scanf("%d", &numbers[i]); + } + bogosort(numbers, size); + printf("The array after sorting is:"); + for (i = 0; i < size; i++) + { + printf("%d\n", numbers[i]); + } + printf("\n"); +} + +/* Code to check if the array is sorted or not */ +int is_sorted(int *a, int n) +{ + while (--n >= 1) + { + if (a[n] < a[n - 1]) + { + return 0; + } + } + return 1; +} + +/* Code to shuffle the array elements */ +void shuffle(int *a, int n) +{ + int i, t, temp; + for (i = 0; i < n; i++) + { + t = a[i]; + temp = rand() % n; /* Shuffles the given array using Random function */ + a[i] = a[temp]; + a[temp] = t; + } +} + +/* Code to check if the array is sorted or not and if not sorted calls the shuffle function to shuffle the array elements */ +void bogosort(int *a, int n) +{ + while (!is_sorted(a, n)) + { + shuffle(a, n); + } +} +/* +*OUTPUT: +Average case: +Enter the elements of array:56 +34 +96 +26 +08 +87 +36 +The array after sorting is:8 +26 +34 +36 +56 +87 +96 + +Best case: +Enter the elements of array:12 +23 +34 +45 +56 +67 +78 +The array after sorting is:12 +23 +34 +45 +56 +67 +78 + +Worst case: +Enter the elements of array:984 +38 +983 +389 +37 +596 +483 +The array after sorting is:37 +38 +389 +483 +596 +983 +984 +*/ \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Implement CockTail Sort.c b/c/Search_Sorting/C Program to Implement CockTail Sort.c new file mode 100644 index 0000000..1955b2a --- /dev/null +++ b/c/Search_Sorting/C Program to Implement CockTail Sort.c @@ -0,0 +1,71 @@ +/* + * C Program to Implement CockTail Sort + */ +#include +#define MAX 8 + +int main() +{ + int data[MAX]; + int i, j, n, c; + printf("\nEnter the data"); + for (i = 0; i < MAX; i++) + { + scanf("%d", &data[i]); + } + n = MAX; + do + { + /* + * Rightward pass will shift the largest element to its correct place at the end + */ + for (i = 0; i < n - 1; i++) + { + if (data[i] > data[i + 1]) + { + data[i] = data[i] + data[i + 1]; + data[i + 1] = data[i] - data[i + 1]; + data[i] = data[i] - data[i + 1]; + } + } + n = n - 1; + /* + * Leftward pass will shift the smallest element to its correct place at the beginning + */ + for (i= MAX - 1, c = 0; i >= c; i--) + { + if(data[i] < data[i - 1]) + { + data[i] = data[i] + data[i - 1]; + data[i - 1] = data[i] - data[i - 1]; + data[i] = data[i] - data[i - 1]; + } + } + c = c + 1; + } + while (n != 0 && c != 0); + printf("The sorted elements are:"); + for (i = 0; i < MAX; i++) + { + printf("%d\t", data[i]); + } +} +/* +*OUTPUT: +/* +Average case + +Enter the data +9 6 2 12 11 9 3 7 +The sorted elements are:2 3 6 7 9 9 11 12 +/* +Worst case +Enter the data +8 7 6 5 4 3 2 1 +The sorted elements are:1 2 3 4 5 6 7 8 +/* +*Best case +Enter the data +1 2 3 4 5 6 7 8 +The sorted elements are:1 2 3 4 5 6 7 8 +*/ \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Implement Cyclesort.c b/c/Search_Sorting/C Program to Implement Cyclesort.c new file mode 100644 index 0000000..cc6e587 --- /dev/null +++ b/c/Search_Sorting/C Program to Implement Cyclesort.c @@ -0,0 +1,67 @@ +/* + * C Program to Implement Cyclesort + */ +#include + +#define MAX 8 + +void cycle_sort(int *); + +void main() +{ + int a[MAX],i; + printf("enter the elements into array :"); + for (i = 0; i < MAX; i++) + { + scanf("%d", &a[i]); + } + cycle_sort(a); + printf("sorted elements are :\n"); + for (i = 0; i < MAX; i++) + { + printf("%d", a[i]); + } +} + +/* sorts elements using cycle sort algorithm */ +void cycle_sort(int * a) +{ + int temp, item, pos, i, j, k; + for (i = 0; i < MAX; i++) + { + item = a[i]; + pos = i; + do + { + k = 0; + for (j = 0; j < MAX; j++) + { + if (pos != j && a[j] < item) + { + k++; + } + } + if (pos != k) + { + while (pos != k && item == a[k]) + { + k++; + } + temp = a[k]; + a[k] = item; + item = temp; + pos = k; + } + } + while (pos != i); + } +} +/* +*OUTPUT: +enter the elements into array :7 3 2 5 4 8 9 6 +sorted elements are : +23456789 +enter the elements into array :7 3 2 4 5 4 6 3 +sorted elements are : +23344567 +*/ \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Implement Heap’s Algorithm for Permutation of N Numbers.c b/c/Search_Sorting/C Program to Implement Heap’s Algorithm for Permutation of N Numbers.c new file mode 100644 index 0000000..7513657 --- /dev/null +++ b/c/Search_Sorting/C Program to Implement Heap’s Algorithm for Permutation of N Numbers.c @@ -0,0 +1,59 @@ +#include +#include +int len; +void swap (int *x, char *y) +{ + int temp; + temp = *x; + *x = *y; + *y = temp; +} +void print(const int *v) +{ + int i; + int size = len; + if (v != 0) + { + for ( i = 0; i < size; i++) + { + printf("%4d", v[i] ); + } + printf("\n"); + } +} +void heappermute(int v[], int n) +{ + int i; + if (n == 1) + { + print(v); + } + else + { + for (i = 0; i < n; i++) + { + heappermute(v, n-1); + if (n % 2 == 1) + { + swap(&v[0], &v[n-1]); + } + else + { + swap(&v[i], &v[n-1]); + } + } + } +} + +int main() +{ + int num[11]; + int i; + printf("How many numbers you want to enter: ", len); + scanf("%d", &len); + printf("\nEnter %d numbers: "); + for ( i = 0 ; i < len; i++) + scanf("%d", &num[i]); + heappermute(num, len); + return 0; +} \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Implement Insertion Sort.c b/c/Search_Sorting/C Program to Implement Insertion Sort.c new file mode 100644 index 0000000..9a85b6a --- /dev/null +++ b/c/Search_Sorting/C Program to Implement Insertion Sort.c @@ -0,0 +1,56 @@ +/* + * C Program to Implement Insertion Sort + */ +#include +#define MAX 7 + +void insertion_sort(int *); + +void main() +{ + int a[MAX], i; + printf("enter elements to be sorted:"); + for (i = 0; i < MAX; i++) + { + scanf("%d", &a[i]); + } + insertion_sort(a); + printf("sorted elements:\n"); + for (i = 0; i < MAX; i++) + { + printf(" %d", a[i]); + } +} + +/* sorts the input */ +void insertion_sort(int * x) +{ + int temp, i, j; + for (i = 1; i < MAX; i++) + { + temp = x[i]; + j = i - 1; + while (temp < x[j] && j >= 0) + { + x[j + 1] = x[j]; + j = j - 1; + } + x[j + 1] = temp; + } +} +/* +*OUTPUT: +enter elements to be sorted:8 2 4 9 3 6 1 +sorted elements: + 1 2 3 4 6 8 9 + + /*Best case +enter elements to be sorted:1 2 3 4 5 6 7 +sorted elements: + 1 2 3 4 5 6 7 + +/*Worst case +enter elements to be sorted:7 6 5 4 3 2 1 +sorted elements: + 1 2 3 4 5 6 7 + */ diff --git a/c/Search_Sorting/C Program to Implement Interpolation Search Algorithm.c b/c/Search_Sorting/C Program to Implement Interpolation Search Algorithm.c new file mode 100644 index 0000000..6c165f2 --- /dev/null +++ b/c/Search_Sorting/C Program to Implement Interpolation Search Algorithm.c @@ -0,0 +1,43 @@ +#include +#include +int interpolationsearch(int sortedArray[], int toFind, int len) +{ + int low = 0; + int high = len - 1; + int mid; + while (sortedArray[low] <= toFind && sortedArray[high] >= toFind) + { + if (sortedArray[high] - sortedArray[low] == 0) + return (low + high)/2; + mid = low + ((toFind - sortedArray[low]) * (high - low)) / (sortedArray[high] - sortedArray[low]); + if (sortedArray[mid] < toFind) + low = mid + 1; + else if (sortedArray[mid] > toFind) + high = mid - 1; + else + return mid; + } + if (sortedArray[low] == toFind) + return low; + else + return -1; +} +int main() +{ + int arr[200], len, number, i, pos; + printf("How many elements you want to enter: "); + scanf("%d", &len); + printf("\nEnter %d elements in increasing order: ", len); + for (i = 0; i < len; i++) + { + scanf("%d", &arr[i]); + } + printf("\nEnter an element to search: "); + scanf("%d", &number); + pos = interpolationsearch(arr, number, len); + if (pos != -1) + printf("\nElement found at postion %d . ", pos); + else + printf("\nElement NOT found!!!"); + return 0; +} \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Implement Linear Search.c b/c/Search_Sorting/C Program to Implement Linear Search.c new file mode 100644 index 0000000..3d53a0c --- /dev/null +++ b/c/Search_Sorting/C Program to Implement Linear Search.c @@ -0,0 +1,81 @@ +/* + * C program to input N numbers and store them in an array. + * Do a linear search for a given key and report success + * or failure. + */ +#include + +void main() +{ + int array[10]; + int i, num, keynum, found = 0; + printf("Enter the value of num \n"); + scanf("%d", &num); + printf("Enter the elements one by one \n"); + for (i = 0; i < num; i++) + { + scanf("%d", &array[i]); + } + printf("Input array is \n"); + for (i = 0; i < num; i++) + { + printf("%dn", array[i]); + } + printf("Enter the element to be searched \n"); + scanf("%d", &keynum); + /* Linear search begins */ + for (i = 0; i < num ; i++) + { + if (keynum == array[i] ) + { + found = 1; + break; + } + } + if (found == 1) + printf("Element is present in the array\n"); + else + printf("Element is not present in the array\n"); +} +/* +*OUTPUT: +Enter the value of num +5 +Enter the elements one by one +456 +78 +90 +40 +100 +Input array is +456 +78 +90 +40 +100 +Enter the element to be searched +70 +Element is not present in the array + +Enter the value of num +7 +Enter the elements one by one +45 +56 +89 +56 +90 +23 +10 +Input array is +45 +56 +89 +56 +90 +23 +10 +Enter the element to be searched +45 +Element is present in the array +*/ \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Implement Merge Sort Algorithm on Linked List.c b/c/Search_Sorting/C Program to Implement Merge Sort Algorithm on Linked List.c new file mode 100644 index 0000000..3efc2aa --- /dev/null +++ b/c/Search_Sorting/C Program to Implement Merge Sort Algorithm on Linked List.c @@ -0,0 +1,106 @@ +#include +#include + +struct node +{ + int data; + struct node* next; +}; + +struct node* sortedmerge(struct node* a, struct node* b); +void frontbacksplit(struct node* source, struct node** frontRef, struct node** backRef); + + +void mergesort(struct node** headRef) +{ + struct node* head = *headRef; + struct node* a; + struct node* b; + if ((head == NULL) || (head -> next == NULL)) + { + return; + } + frontbacksplit(head, &a, &b); + mergesort(&a); + mergesort(&b); + *headRef = sortedmerge(a, b); +} + +struct node* sortedmerge(struct node* a, struct node* b) +{ + struct node* result = NULL; + if (a == NULL) + return(b); + else if (b == NULL) + return(a); + if ( a-> data <= b -> data) + { + result = a; + result -> next = sortedmerge(a -> next, b); + } + else + { + result = b; + result -> next = sortedmerge(a, b -> next); + } + return(result); +} + +void frontbacksplit(struct node* source, struct node** frontRef, struct node** backRef) +{ + struct node* fast; + struct node* slow; + if (source==NULL || source->next==NULL) + { + *frontRef = source; + *backRef = NULL; + } + else + { + slow = source; + fast = source -> next; + while (fast != NULL) + { + fast = fast -> next; + if (fast != NULL) + { + slow = slow -> next; + fast = fast -> next; + } + } + *frontRef = source; + *backRef = slow -> next; + slow -> next = NULL; + } +} + +void printlist(struct node *node) +{ + while(node != NULL) + { + printf("%d ", node -> data); + node = node -> next; + } +} + +void push(struct node** head_ref, int new_data) +{ + struct node* new_node = (struct node*) malloc(sizeof(struct node)); + new_node -> data = new_data; + new_node->next = (*head_ref); + (*head_ref) = new_node; +} +int main() +{ + struct node* a = NULL; + push(&a, 15); + push(&a, 10); + push(&a, 5); + push(&a, 20); + push(&a, 3); + push(&a, 26775); + mergesort(&a); + printf("\n Sorted Linked List is: \n"); + printlist(a); + return 0; +} \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Implement Oddeven Sort.c b/c/Search_Sorting/C Program to Implement Oddeven Sort.c new file mode 100644 index 0000000..d016844 --- /dev/null +++ b/c/Search_Sorting/C Program to Implement Oddeven Sort.c @@ -0,0 +1,77 @@ +/* + * C Program to Implement Oddeven Sort + */ +#include +#define MAX 7 + +void swap(int *,int *); +void oddeven_sort(int *); + +void main() +{ + int a[MAX], i; + printf("enter the elements in to the matrix :"); + for (i = 0; i < MAX; i++) + { + scanf("%d", &a[i]); + } + printf("sorted elements are :\n"); + oddeven_sort(a); + for (i = 0; i < MAX; i++) + { + printf(" %d", a[i]); + } +} + +/* swaps the elements */ +void swap(int * x, int * y) +{ + int temp; + temp = *x; + *x = *y; + *y = temp; +} + +/* sorts the array using oddeven algorithm */ +void oddeven_sort(int * x) +{ + int sort = 0, i; + while (!sort) + { + sort = 1; + for (i = 1; i < MAX; i += 2) + { + if (x[i] > x[i+1]) + { + swap(&x[i], &x[i+1]); + sort = 0; + } + } + for (i = 0; i < MAX - 1; i += 2) + { + if (x[i] > x[i + 1]) + { + swap(&x[i], &x[i + 1]); + sort = 0; + } + } + } +} +/* +*OUTPUT: +/* average case +$ a.out +enter the elements in to the matrix :7 8 3 2 5 4 9 +sorted elements are : + 2 3 4 5 7 8 9 + +/* best case +enter the elements in to the matrix :1 2 3 4 5 6 7 +sorted elements are : + 1 2 3 4 5 6 7 + +/* worst case +enter the elements in to the matrix :7 6 5 4 3 2 1 +sorted elements are : + 1 2 3 4 5 6 7 + */ \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Implement Pancake Sort on Array of Integers.c b/c/Search_Sorting/C Program to Implement Pancake Sort on Array of Integers.c new file mode 100644 index 0000000..92cf1ea --- /dev/null +++ b/c/Search_Sorting/C Program to Implement Pancake Sort on Array of Integers.c @@ -0,0 +1,113 @@ +/* + * C Program to Implement Pancake Sort on Array of Integers + */ +#include +#include + +void do_flip(int *, int, int); + +/*Function to implement the pancake sort*/ +int pancake_sort(int *list, unsigned int length) +{ + if (length < 2) + return 0; + int i, a, max_num_pos, moves; + moves = 0; + for (i = length; i > 1; i--) + { + max_num_pos = 0; + for (a = 0; a < i; a++) + { + if (list[a] > list[max_num_pos]) + max_num_pos = a; + } + if (max_num_pos == i - 1) + continue; + if (max_num_pos) + { + moves++; + do_flip(list, length, max_num_pos + 1); + } + do_flip(list, length, i); + } + return moves; +} + +/*Function to do flips in the elements*/ +void do_flip(int *list, int length, int num) +{ + int swap; + int i = 0; + for (i; i < --num; i++) + { + swap = list[i]; + list[i] = list[num]; + list[num] = swap; + } +} + +/*Function to print the array*/ +void print_array(int list[], int length) +{ + int i; + for (i = 0; i < length; i++) + { + printf("%d ", list[i]); + } +} + +int main(int argc, char **argv) +{ + int list[9]; + int i; + printf("enter the 9 elements of array:\n"); + for (i = 0; i < 9; i++) + scanf("%d", &list[i]); + printf("\nOriginal: "); + print_array(list, 9); + int moves = pancake_sort(list, 9); + printf("\nSorted: "); + print_array(list, 9); + printf(" - with a total of %d moves\n", moves); +} +/* +*OUTPUT: +enter the 9 elements of array: +10 +9 +8 +7 +6 +5 +4 +3 +2 + +Original: 10 9 8 7 6 5 4 3 2 +Sorted: 2 3 4 5 6 7 8 9 10 - with a total of 0 moves +enter the 9 elements of array: +1 +2 +3 +4 +5 +6 +7 +8 +9 + +Original: 1 2 3 4 5 6 7 8 9 +Sorted: 1 2 3 4 5 6 7 8 9 - with a total of 0 moves +enter the 9 elements of array: +5 +6 +7 +8 +9 +1 +4 +2 +3 +Original: 5 6 7 8 9 1 4 2 3 +Sorted: 1 2 3 4 5 6 7 8 9 - with a total of 3 moves +*/ \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Implement Pigeonhole Sort.c b/c/Search_Sorting/C Program to Implement Pigeonhole Sort.c new file mode 100644 index 0000000..5515c07 --- /dev/null +++ b/c/Search_Sorting/C Program to Implement Pigeonhole Sort.c @@ -0,0 +1,79 @@ +/* + * C Program to Implement Pigeonhole Sort + */ +#include + +#define MAX 7 + +void pigeonhole_sort(int, int, int *); +void main() +{ + int a[MAX], i, min, max; + printf("enter the values into the matrix :"); + for (i = 0; i < MAX; i++) + { + scanf("%d", &a[i]); + } + min = a[0]; + max = a[0]; + for (i = 1; i < MAX; i++) + { + if (a[i] < min) + { + min = a[i]; + } + if (a[i] > max) + { + max = a[i]; + } + } + pigeonhole_sort(min, max, a); + printf("Sorted order is :\n"); + for (i = 0; i < MAX; i++) + { + printf("%d", a[i]); + } +} + +/* sorts the array using pigeonhole algorithm */ +void pigeonhole_sort(int mi, int ma, int * a) +{ + int size, count = 0, i; + int *current; + current = a; + size = ma - mi + 1; + int holes[size]; + for (i = 0; i < size; i++) + { + holes[i] = 0; + } + for (i = 0; i < size; i++, current++) + { + holes[*current-mi] += 1; + } + for (count = 0, current = &a[0]; count < size; count++) + { + while (holes[count]--> 0) + { + *current++ = count + mi; + } + } +} +/* +*OUTPUT: + +/* average case +enter the values into the matrix :7 3 8 2 5 4 9 +Sorted order is : +2345789 + +/* best case +enter the values into the matrix :1 2 3 4 5 6 7 +Sorted order is : +1234567 + +/* worst case +enter the values into the matrix :7 6 5 4 3 2 1 +Sorted order is : +1234567 +*/ \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Implement Postman Sort Algorithm.c b/c/Search_Sorting/C Program to Implement Postman Sort Algorithm.c new file mode 100644 index 0000000..1bce36a --- /dev/null +++ b/c/Search_Sorting/C Program to Implement Postman Sort Algorithm.c @@ -0,0 +1,131 @@ +/* + * C Program to Implement Postman Sort Algorithm + */ +#include + +void arrange(int,int); +int array[100], array1[100]; +int i, j, temp, max, count, maxdigits = 0, c = 0; + +void main() +{ + int t1, t2, k, t, n = 1; + printf("Enter size of array :"); + scanf("%d", &count); + printf("Enter elements into array :"); + for (i = 0; i < count; i++) + { + scanf("%d", &array[i]); + array1[i] = array[i]; + } + for (i = 0; i < count; i++) + { + t = array[i]; /*first element in t */ + while(t > 0) + { + c++; + t = t / 10; /* Find MSB */ + } + if (maxdigits < c) + maxdigits = c; /* number of digits of a each number */ + c = 0; + } + while(--maxdigits) + n = n * 10; + for (i = 0; i < count; i++) + { + max = array[i] / n; /* MSB - Dividnng by perticular base */ + t = i; + for (j = i + 1; j < count; j++) + { + if (max > (array[j] / n)) + { + max = array[j] / n; /* greatest MSB */ + t = j; + } + } + temp = array1[t]; + array1[t] = array1[i]; + array1[i] = temp; + temp = array[t]; + array[t] = array[i]; + array[i] = temp; + } + while (n >= 1) + { + for (i = 0; i < count;) + { + t1 = array[i] / n; + for (j = i + 1; t1 == (array[j] / n); j++); + arrange(i, j); + i = j; + } + n = n / 10; + } + printf("\nSorted Array (Postman sort) :"); + for (i = 0; i < count; i++) + printf("%d ", array1[i]); + printf("\n"); +} + +/* Function to arrange the of sequence having same base */ +void arrange(int k,int n) +{ + for (i = k; i < n - 1; i++) + { + for (j = i + 1; j < n; j++) + { + if (array1[i] > array1[j]) + { + temp = array1[i]; + array1[i] = array1[j]; + array1[j] = temp; + temp = (array[i] % 10); + array[i] = (array[j] % 10); + array[j] = temp; + } + } + } +} +/* +*OUTPUT: +/* Average case + +Enter size of array :8 +Enter elements into array :170 +45 +90 +75 +802 +24 +2 +66 + +Sorted Array (Postman sort) :2 24 45 66 75 90 170 802 + + +/* Best case +Enter size of array :7 +Enter elements into array :25 +64 +185 +136 +36 +3645 +45 + +Sorted Array (Postman sort) :25 36 45 64 136 185 3645 + +/* Worst case +Enter size of array :8 +Enter elements into array :15 +214 +166 +0836 +98 +6254 +73 +642 + +Sorted Array (Postman sort) :15 73 98 166 214 642 836 6254 +*/ \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Implement Quick Sort Using Randomization.c b/c/Search_Sorting/C Program to Implement Quick Sort Using Randomization.c new file mode 100644 index 0000000..2974e90 --- /dev/null +++ b/c/Search_Sorting/C Program to Implement Quick Sort Using Randomization.c @@ -0,0 +1,68 @@ +/* + * C Program to Implement Quick Sort Using Randomization + */ +#include +#include +#define MAX 100 +void random_shuffle(int arr[]) +{ + srand(time(NULL)); + int i, j, temp; + for (i = MAX - 1; i > 0; i--) + { + j = rand()%(i + 1); + temp = arr[i]; + arr[i] = arr[j]; + arr[j] = temp; + } +} + +void swap(int *a, int *b) +{ + int temp; + temp = *a; + *a = *b; + *b = temp; +} +int partion(int arr[], int p, int r) +{ + int pivotIndex = p + rand()%(r - p + 1); //generates a random number as a pivot + int pivot; + int i = p - 1; + int j; + pivot = arr[pivotIndex]; + swap(&arr[pivotIndex], &arr[r]); + for (j = p; j < r; j++) + { + if (arr[j] < pivot) + { + i++; + swap(&arr[i], &arr[j]); + } + } + swap(&arr[i+1], &arr[r]); + return i + 1; +} + +void quick_sort(int arr[], int p, int q) +{ + int j; + if (p < q) + { + j = partion(arr, p, q); + quick_sort(arr, p, j-1); + quick_sort(arr, j+1, q); + } +} +int main() +{ + int i; + int arr[MAX]; + for (i = 0; i < MAX; i++) + arr[i] = i; + random_shuffle(arr); //To randomize the array + quick_sort(arr, 0, MAX-1); //function to sort the elements of array + for (i = 0; i < MAX; i++) + printf("%d \n", arr[i]); + return 0; +} \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Implement Selection Sort Method using Functions.c b/c/Search_Sorting/C Program to Implement Selection Sort Method using Functions.c new file mode 100644 index 0000000..94ad060 --- /dev/null +++ b/c/Search_Sorting/C Program to Implement Selection Sort Method using Functions.c @@ -0,0 +1,78 @@ +/* + * C program for SELECTION sort which uses following functions + * a) To find maximum of elements + * b) To swap two elements + */ +#include + +int findmax(int b[10], int k); +void exchang(int b[10], int k); +void main() +{ + int array[10]; + int i, j, n, temp; + printf("Enter the value of n \n"); + scanf("%d", &n); + printf("Enter the elements one by one \n"); + for (i = 0; i < n; i++) + { + scanf("%d", &array[i]); + } + printf("Input array elements \n"); + for (i = 0; i < n ; i++) + { + printf("%d\n", array[i]); + } + /* Selection sorting begins */ + exchang(array, n); + printf("Sorted array is...\n"); + for (i = 0; i < n; i++) + { + printf("%d\n", array[i]); + } +} +/* function to find the maximum value */ +int findmax(int b[10], int k) +{ + int max = 0, j; + for (j = 1; j <= k; j++) + { + if (b[j] > b[max]) + { + max = j; + } + } + return(max); +} +void exchang(int b[10], int k) +{ + int temp, big, j; + for (j = k - 1; j >= 1; j--) + { + big = findmax(b, j); + temp = b[big]; + b[big] = b[j]; + b[j] = temp; + } + return; +} +/* +*OUTPUT: +Enter the value of n +4 +Enter the elements one by one +57 +90 +34 +78 +Input array elements +57 +90 +34 +78 +Sorted array is... +34 +57 +78 +90 +*/ \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Implement Selection Sort Recursively.c b/c/Search_Sorting/C Program to Implement Selection Sort Recursively.c new file mode 100644 index 0000000..9f8234e --- /dev/null +++ b/c/Search_Sorting/C Program to Implement Selection Sort Recursively.c @@ -0,0 +1,60 @@ +/* + * C Program to Implement Selection Sort Recursively + */ +#include + +void selection(int [], int, int, int, int); + +int main() +{ + int list[30], size, temp, i, j; + printf("Enter the size of the list: "); + scanf("%d", &size); + printf("Enter the elements in list:\n"); + for (i = 0; i < size; i++) + { + scanf("%d", &list[i]); + } + selection(list, 0, 0, size, 1); + printf("The sorted list in ascending order is\n"); + for (i = 0; i < size; i++) + { + printf("%d ", list[i]); + } + return 0; +} + +void selection(int list[], int i, int j, int size, int flag) +{ + int temp; + if (i < size - 1) + { + if (flag) + { + j = i + 1; + } + if (j < size) + { + if (list[i] > list[j]) + { + temp = list[i]; + list[i] = list[j]; + list[j] = temp; + } + selection(list, i, j + 1, size, 0); + } + selection(list, i + 1, 0, size, 1); + } +} +/* +*OUTPUT: +Enter the size of the list: 5 +Enter the elements in list: +23 +45 +64 +12 +34 +The sorted list in ascending order is +12 23 34 45 64 +*/ \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Implement Selection Sort.c b/c/Search_Sorting/C Program to Implement Selection Sort.c new file mode 100644 index 0000000..528bb25 --- /dev/null +++ b/c/Search_Sorting/C Program to Implement Selection Sort.c @@ -0,0 +1,38 @@ +/* + * C Program to Implement Selection Sort + */ +#include +void selectionSort(int arr[], int size) +{ + int i, j; + for (i = 0 ; i < size; i++) + { + for (j = i ; j < size; j++) + { + if (arr[i] > arr[j]) + swap(&arr[i], &arr[j]); + } + } +} +//fucntion to swap to variables +void swap(int *a, int *b) +{ + int temp; + temp = *a; + *a = *b; + *b = temp; +} +int main() +{ + int array[10], i, size; + printf("How many numbers you want to sort: "); + scanf("%d", &size); + printf("\nEnter %d number", size); + for (i = 0; i < size; i++) + scanf("%d", &array[i]); + selectionSort(array, size); + printf("\nSorted array is "); + for (i = 0; i < size; i++) + printf(" %d ", array[i]); + return 0; +} \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Implement Shell Sort.c b/c/Search_Sorting/C Program to Implement Shell Sort.c new file mode 100644 index 0000000..ab7ea21 --- /dev/null +++ b/c/Search_Sorting/C Program to Implement Shell Sort.c @@ -0,0 +1,42 @@ +/* + * C Program to sort an array using Shell Sort technique + */ +#include +void shellsort(int arr[], int num) +{ + int i, j, k, tmp; + for (i = num / 2; i > 0; i = i / 2) + { + for (j = i; j < num; j++) + { + for(k = j - i; k >= 0; k = k - i) + { + if (arr[k+i] >= arr[k]) + break; + else + { + tmp = arr[k]; + arr[k] = arr[k+i]; + arr[k+i] = tmp; + } + } + } + } +} +int main() +{ + int arr[30]; + int k, num; + printf("Enter total no. of elements : "); + scanf("%d", &num); + printf("\nEnter %d numbers: ", num); + for (k = 0 ; k < num; k++) + { + scanf("%d", &arr[k]); + } + shellsort(arr, num); + printf("\n Sorted array is: "); + for (k = 0; k < num; k++) + printf("%d ", arr[k]); + return 0; +} \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Implement Stooge Sort.c b/c/Search_Sorting/C Program to Implement Stooge Sort.c new file mode 100644 index 0000000..b5c3b5f --- /dev/null +++ b/c/Search_Sorting/C Program to Implement Stooge Sort.c @@ -0,0 +1,73 @@ +/* + * C Program to Implement Stooge Sort + */ +#include + +// Function Prototype +void stoogesort(int [], int, int); + +void main() +{ + int b[7], i; + printf("Enter the values you want to sort using STOOGE SORT!!!:\n"); + for (i = 0; i < 7; i++) + scanf(" %d", &b[i]); + stoogesort(b, 0, 6); + printf("sorted by stooge sort \n"); + for (i = 0; i < 7; i++) + { + printf("%d ", b[i]); + } + printf("\n"); +} + +// Function to implement STOOGE SORT +void stoogesort(int a[], int i, int j) +{ + int temp, k; + if (a[i] > a[j]) + { + temp = a[i]; + a[i] = a[j]; + a[j] = temp; + } + if ((i + 1) >= j) + return; + k = (int)((j - i + 1) / 3); + stoogesort(a, i, j - k); + stoogesort(a, i + k, j); + stoogesort(a, i, j - k); +} +/* +*OUTPUT: +Enter the values you want to sort using STOOGE SORT!!!: +6 +1 +5 +3 +8 +7 +2 +sorted by stooge sort +1 2 3 5 6 7 8 +Enter the values you want to sort using STOOGE SORT!!!: +7 +6 +5 +4 +3 +2 +1 +sorted by stooge sort +1 2 3 4 5 6 7 +Enter the values you want to sort using STOOGE SORT!!!: +1 +2 +3 +4 +5 +6 +7 +sorted by stooge sort +1 2 3 4 5 6 7 +*/ \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Implement qsort using Function Pointers.c b/c/Search_Sorting/C Program to Implement qsort using Function Pointers.c new file mode 100644 index 0000000..22c1436 --- /dev/null +++ b/c/Search_Sorting/C Program to Implement qsort using Function Pointers.c @@ -0,0 +1,72 @@ +/* + * C Program to Implement qsort using function pointers + */ +#include +#include +#include +#include + +struct s +{ + char empname[5]; + int empid; +}; + +/* To sort array elemets */ +int int_call(const void *a1,const void *b1) +{ + const int *a = (const int *)a1; + const int *b = (const int *)b1; + if (*a > *b) + return 1; + else + { + if (*a == *b) + return 0; + else + return -1; + } +} + +/* To sort structure elemets */ +int string_call(const void *a1, const void *b1) +{ + const char *a = (const char *)a1; + const char *b = (const char *)b1; + return(strcmp(a, b)); +} + +void main() +{ + int array1[5]= {20, 30, 50, 60, 10}; + struct s emprec[5]; + int i, j; + strcpy(emprec[0].empname, "bbb"); + emprec[0].empid = 100; + strcpy(emprec[1].empname, "ccc"); + emprec[1].empid = 200; + strcpy(emprec[2].empname, "eee"); + emprec[2].empid = 300; + strcpy(emprec[3].empname, "aaa"); + emprec[3].empid = 400; + strcpy(emprec[4].empname,"ddd"); + emprec[4].empid = 500; + qsort(array1, 5, sizeof(int), int_call); + qsort(emprec, 5, sizeof(struct s), string_call); + for (i = 0; i < 5; i++) + printf("%d\t", array1[i]); + printf("\nSorting of Structure elements "); + for (i = 0; i < 5; i++) + printf("\n%s\t%d", emprec[i].empname, emprec[i].empid); + printf("\n"); +} +/* +*OUTPUT: +10 20 30 50 60 +Sorting of Structure elements +aaa 400 +bbb 100 +ccc 200 +ddd 500 +eee 300 +*/ \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Implement the Alexander Bogomolny’s UnOrdered Permutation Algorithm for Elements From 1 to N.c b/c/Search_Sorting/C Program to Implement the Alexander Bogomolny’s UnOrdered Permutation Algorithm for Elements From 1 to N.c new file mode 100644 index 0000000..e374370 --- /dev/null +++ b/c/Search_Sorting/C Program to Implement the Alexander Bogomolny’s UnOrdered Permutation Algorithm for Elements From 1 to N.c @@ -0,0 +1,68 @@ +#include +void print(const int *v, const int size) +{ + int i; + if (v != 0) + { + for ( i = 0; i < size; i++) + { + printf("%4d", v[i] ); + } + printf("\n"); + } +} +void alexanderbogomolyn(int *Value, int N, int k) +{ + static level = -1; + int i; + level = level+1; + Value[k] = level; + if (level == N) + print(Value, N); + else + for (i = 0; i < N; i++) + if (Value[i] == 0) + alexanderbogomolyn(Value, N, i); + level = level-1; + Value[k] = 0; +} +int main() +{ + int N = 4; + int i; + int Value[N]; + for (i = 0; i < N; i++) + { + Value[i] = 0; + } + printf("\nPermutation using Alexander Bogomolyn's algorithm: "); + alexanderbogomolyn(Value, N, 0); + return 0; +} + +/* +Permutation using Alexander Bogomolyns algorithm: + 1 2 3 4 + 1 2 4 3 + 1 3 2 4 + 1 4 2 3 + 1 3 4 2 + 1 4 3 2 + 2 1 3 4 + 2 1 4 3 + 3 1 2 4 + 4 1 2 3 + 3 1 4 2 + 4 1 3 2 + 2 3 1 4 + 2 4 1 3 + 3 2 1 4 + 4 2 1 3 + 3 4 1 2 + 4 3 1 2 + 2 3 4 1 + 2 4 3 1 + 3 2 4 1 + 4 2 3 1 + 3 4 2 1 + 4 3 2 1 \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Input Few Numbers _ Perform Merge Sort on them using Recursion.c b/c/Search_Sorting/C Program to Input Few Numbers _ Perform Merge Sort on them using Recursion.c new file mode 100644 index 0000000..fba153e --- /dev/null +++ b/c/Search_Sorting/C Program to Input Few Numbers _ Perform Merge Sort on them using Recursion.c @@ -0,0 +1,94 @@ +/* + * C Program to Input Few Numbers & Perform Merge Sort on them using Recursion + */ + +#include + +void mergeSort(int [], int, int, int); +void partition(int [],int, int); + +int main() +{ + int list[50]; + int i, size; + printf("Enter total number of elements:"); + scanf("%d", &size); + printf("Enter the elements:\n"); + for(i = 0; i < size; i++) + { + scanf("%d", &list[i]); + } + partition(list, 0, size - 1); + printf("After merge sort:\n"); + for(i = 0; i < size; i++) + { + printf("%d ",list[i]); + } + return 0; +} + +void partition(int list[],int low,int high) +{ + int mid; + if(low < high) + { + mid = (low + high) / 2; + partition(list, low, mid); + partition(list, mid + 1, high); + mergeSort(list, low, mid, high); + } +} + +void mergeSort(int list[],int low,int mid,int high) +{ + int i, mi, k, lo, temp[50]; + lo = low; + i = low; + mi = mid + 1; + while ((lo <= mid) && (mi <= high)) + { + if (list[lo] <= list[mi]) + { + temp[i] = list[lo]; + lo++; + } + else + { + temp[i] = list[mi]; + mi++; + } + i++; + } + if (lo > mid) + { + for (k = mi; k <= high; k++) + { + temp[i] = list[k]; + i++; + } + } + else + { + for (k = lo; k <= mid; k++) + { + temp[i] = list[k]; + i++; + } + } + for (k = low; k <= high; k++) + { + list[k] = temp[k]; + } +} +/* +*OUTPUT: +Enter total number of elements:5 +Enter the elements: +12 +36 +22 +76 +54 +After merge sort: +12 22 36 54 76 +*/ \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Perform Binary Search using Recursion.c b/c/Search_Sorting/C Program to Perform Binary Search using Recursion.c new file mode 100644 index 0000000..45f918b --- /dev/null +++ b/c/Search_Sorting/C Program to Perform Binary Search using Recursion.c @@ -0,0 +1,77 @@ +/* + * C Program to Perform Binary Search using Recursion + */ +#include + +void binary_search(int [], int, int, int); +void bubble_sort(int [], int); + +int main() +{ + int key, size, i; + int list[25]; + printf("Enter size of a list: "); + scanf("%d", &size); + printf("Generating random numbers\n"); + for(i = 0; i < size; i++) + { + list[i] = rand() % 100; + printf("%d ", list[i]); + } + bubble_sort(list, size); + printf("\n\n"); + printf("Enter key to search\n"); + scanf("%d", &key); + binary_search(list, 0, size, key); +} + +void bubble_sort(int list[], int size) +{ + int temp, i, j; + for (i = 0; i < size; i++) + { + for (j = i; j < size; j++) + { + if (list[i] > list[j]) + { + temp = list[i]; + list[i] = list[j]; + list[j] = temp; + } + } + } +} + +void binary_search(int list[], int lo, int hi, int key) +{ + int mid; + if (lo > hi) + { + printf("Key not found\n"); + return; + } + mid = (lo + hi) / 2; + if (list[mid] == key) + { + printf("Key found\n"); + } + else if (list[mid] > key) + { + binary_search(list, lo, mid - 1, key); + } + else if (list[mid] < key) + { + binary_search(list, mid + 1, hi, key); + } +} +} +/* +*OUTPUT: +Enter size of a list: 10 +Generating random numbers +83 86 77 15 93 35 86 92 49 21 + +Enter key to search +21 +Key found +*/ \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Perform Comb Sort on Array of Integers.c b/c/Search_Sorting/C Program to Perform Comb Sort on Array of Integers.c new file mode 100644 index 0000000..4406d3f --- /dev/null +++ b/c/Search_Sorting/C Program to Perform Comb Sort on Array of Integers.c @@ -0,0 +1,108 @@ +/* + * C Program to Perform Comb Sort on Array of Integers + */ +#include +#include + +/*Function to find the new gap between the elements*/ +int newgap(int gap) +{ + gap = (gap * 10) / 13; + if (gap == 9 || gap == 10) + gap = 11; + if (gap < 1) + gap = 1; + return gap; +} + +/*Function to implement the combsort*/ +void combsort(int a[], int aSize) +{ + int gap = aSize; + int temp, i; + for (;;) + { + gap = newgap(gap); + int swapped = 0; + for (i = 0; i < aSize - gap; i++) + { + int j = i + gap; + if (a[i] > a[j]) + { + temp = a[i]; + a[i] = a[j]; + a[j] = temp; + swapped = 1; + } + } + if (gap == 1 && !swapped) + break; + } +} +int main () +{ + int n, i; + int *a; + printf("Please insert the number of elements to be sorted: "); + scanf("%d", &n); // The total number of elements + a = (int *)calloc(n, sizeof(int)); + for (i = 0; i< n; i++) + { + printf("Input element %d :", i); + scanf("%d", &a[i]); // Adding the elements to the array + } + printf("unsorted list"); // Displaying the unsorted array + for(i = 0; i < n; i++) + { + printf("%d", a[i]); + } + combsort(a, n); + printf("Sorted list:\n"); // Display the sorted array + for(i = 0; i < n; i++) + { + printf("%d ", (a[i])); + } + return 0; +} +/* +*OUTPUT: +Please insert the number of elements to be sorted: 10 +Input element 0 :5 +Input element 1 :6 +Input element 2 :1 +Input element 3 :3 +Input element 4 :4 +Input element 5 :7 +Input element 6 :8 +Input element 7 :9 +Input element 8 :0 +Input element 9 :6 +unsorted list5613478906Sorted list: +0 1 3 4 5 6 6 7 8 9 +Please insert the number of elements to be sorted: 10 +Input element 0 :1 +Input element 1 :2 +Input element 2 :3 +Input element 3 :4 +Input element 4 :5 +Input element 5 :6 +Input element 6 :7 +Input element 7 :8 +Input element 8 :9 +Input element 9 :10 +unsorted list12345678910Sorted list: +1 2 3 4 5 6 7 8 9 10 +Please insert the number of elements to be sorted: 10 +Input element 0 :10 +Input element 1 :9 +Input element 2 :8 +Input element 3 :7 +Input element 4 :6 +Input element 5 :5 +Input element 6 :4 +Input element 7 :3 +Input element 8 :2 +Input element 9 :1 +unsorted list10987654321Sorted list: +1 2 3 4 5 6 7 8 9 10 +*/ \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Perform Quick Sort on a set of Entries from a File using Recursion.c b/c/Search_Sorting/C Program to Perform Quick Sort on a set of Entries from a File using Recursion.c new file mode 100644 index 0000000..11cb04e --- /dev/null +++ b/c/Search_Sorting/C Program to Perform Quick Sort on a set of Entries from a File using Recursion.c @@ -0,0 +1,73 @@ +/* +* C Program to Perform Quick Sort on a set of Entries from a File +* using Recursion +*/ +#include + +void quicksort (int [], int, int); + +int main() +{ + int list[50]; + int size, i; + printf("Enter the number of elements: "); + scanf("%d", &size); + printf("Enter the elements to be sorted:\n"); + for (i = 0; i < size; i++) + { + scanf("%d", &list[i]); + } + quicksort(list, 0, size - 1); + printf("After applying quick sort\n"); + for (i = 0; i < size; i++) + { + printf("%d ", list[i]); + } + printf("\n"); + return 0; +} +void quicksort(int list[], int low, int high) +{ + int pivot, i, j, temp; + if (low < high) + { + pivot = low; + i = low; + j = high; + while (i < j) + { + while (list[i] <= list[pivot] && i <= high) + { + i++; + } + while (list[j] > list[pivot] && j >= low) + { + j--; + } + if (i < j) + { + temp = list[i]; + list[i] = list[j]; + list[j] = temp; + } + } + temp = list[j]; + list[j] = list[pivot]; + list[pivot] = temp; + quicksort(list, low, j - 1); + quicksort(list, j + 1, high); + } +} +/* +*OUTPUT: +Enter the number of elements: 6 +Enter the elements to be sorted: +67 +45 +24 +98 +12 +38 +After applying quick sort +12 24 38 45 67 98 +*/ \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Perform Shell Sort without using Recursion.c b/c/Search_Sorting/C Program to Perform Shell Sort without using Recursion.c new file mode 100644 index 0000000..2c96fc9 --- /dev/null +++ b/c/Search_Sorting/C Program to Perform Shell Sort without using Recursion.c @@ -0,0 +1,101 @@ +/* + * C Program to Perform Shell Sort without using Recursion + */ +#include +#define size 7 + +/* Function Prototype */ +int shell_sort(int []); + +void main() +{ + int arr[size], i; + printf("Enter the elements to be sorted:"); + for (i = 0; i < size; i++) + { + scanf("%d", &arr[i]); + } + shell_sort(arr); + printf("The array after sorting is:"); + for (i = 0; i < size; i++) + { + printf("\n%d", arr[i]); + } +} + +/* Code to sort array using shell sort */ +int shell_sort(int array[]) +{ + int i = 0, j = 0, k = 0, mid = 0; + for (k = size / 2; k > 0; k /= 2) + { + for (j = k; j < size; j++) + { + for (i = j - k; i >= 0; i -= k) + { + if (array[i + k] >= array[i]) + { + break; + } + else + { + mid = array[i]; + array[i] = array[i + k]; + array[i + k] = mid; + } + } + } + } + return 0; +} +/* +*OUTPUT: +Average case: +Enter the elements to be sorted:57 +67 +48 +93 +42 +84 +95 +The array after sorting is: +42 +48 +57 +67 +84 +93 +95 + +Best case: +Enter the elements of array:22 +33 +74 +85 +86 +87 +98 +The array after sorting is:22 +33 +74 +85 +86 +87 +98 + +Worst case: +Enter the elements of array:94 +92 +91 +89 +85 +80 +43 +The array after sorting is:43 +80 +85 +89 +91 +92 +94 +*/ \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Perform Stooge Sort.c b/c/Search_Sorting/C Program to Perform Stooge Sort.c new file mode 100644 index 0000000..150f9a1 --- /dev/null +++ b/c/Search_Sorting/C Program to Perform Stooge Sort.c @@ -0,0 +1,39 @@ +/* + * C Program to Perform Stooge Sort + */ +#include +void stoogesort(int [], int, int); + +void main() +{ + int arr[100], i, n; + printf("How many elements do you want to sort: "); + scanf("%d", &n); + for (i = 0; i < n; i++) + scanf(" %d", &arr[i]); + stoogesort(arr, 0, n - 1); + printf("Sorted array : \n"); + for (i = 0; i < n; i++) + { + printf("%d ", arr[i]); + } + printf("\n"); +} + + +void stoogesort(int arr[], int i, int j) +{ + int temp, k; + if (arr[i] > arr[j]) + { + temp = arr[i]; + arr[i] = arr[j]; + arr[j] = temp; + } + if ((i + 1) >= j) + return; + k = (int)((j - i + 1) / 3); + stoogesort(arr, i, j - k); + stoogesort(arr, i + k, j); + stoogesort(arr, i, j - k); +} \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Perform Uniform Binary Search.c b/c/Search_Sorting/C Program to Perform Uniform Binary Search.c new file mode 100644 index 0000000..c46f587 --- /dev/null +++ b/c/Search_Sorting/C Program to Perform Uniform Binary Search.c @@ -0,0 +1,55 @@ +#define LOG_N 42 + +static int delta[LOG_N]; + +void make_delta(int N) +{ + int power = 1; + int i = 0; + do + { + int half = power; + power <<= 1; + delta[i] = (N + half) / power; + } + while (delta[i++] != 0); +} + +int unisearch(int *a, int key) +{ + int i = delta[0]-1; /* midpoint of array */ + int d = 0; + while (1) + { + if (key == a[i]) + { + return i; + } + else if (delta[d] == 0) + { + return -1; + } + else + { + if (key < a[i]) + { + i -= delta[++d]; + } + else + { + i += delta[++d]; + } + } + } +} + +#define N 10 +int main(void) +{ + int num, a[N] = {1,3,5,6,7,9,14,15,17,19}; + make_delta(N); + printf("\nEnter an element to search: "); + scanf("%d", &num); + printf("%d is at index %d\n", num, unisearch(a, num)); + return 0; +} \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Perform integer Partition for a Specific Case.c b/c/Search_Sorting/C Program to Perform integer Partition for a Specific Case.c new file mode 100644 index 0000000..bc9906c --- /dev/null +++ b/c/Search_Sorting/C Program to Perform integer Partition for a Specific Case.c @@ -0,0 +1,79 @@ +#include +#include +typedef struct +{ + int first; + int n; + int level; +} Call; + + +void print(int n, int * a) +{ + int i ; + for (i = 0; i <= n; i++) + { + printf("%d", a[i]); + } + printf("\n"); +} + + +void integerPartition(int n, int * a) +{ + int first; + int i; + int top = 0; + int level = 0; + Call * stack = (Call * ) malloc (sizeof(Call) * 1000); + stack[0].first = -1; + stack[0].n = n; + stack[0].level = level; + while (top >= 0) + { + first = stack[top].first; + n = stack[top].n; + level = stack[top].level; + if (n >= 1) + { + if (first == - 1) + { + a[level] = n; + print(level, a); + first = (level == 0) ? 1 : a[level-1]; + i = first; + } + else + { + i = first; + i++; + } + if (i <= n / 2) + { + a[level] = i; + stack[top].first = i; + top++; + stack[top].first = -1; + stack[top].n = n - i; + stack[top].level = level + 1; + } + else + { + top--; + } + } + else + { + top --; + } + } +} + +int main() +{ + int n = 4; + int * a = (int * ) malloc(sizeof(int) * n); + printf("\nThe integer partition for %d is :\n", n); + integerPartition (n, a); + return(0); +} \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Perform the Shaker Sort.c b/c/Search_Sorting/C Program to Perform the Shaker Sort.c new file mode 100644 index 0000000..1ab43bd --- /dev/null +++ b/c/Search_Sorting/C Program to Perform the Shaker Sort.c @@ -0,0 +1,30 @@ +#include +void swap(int *a, int *b) +{ + int temp; + temp = *a; + *a = *b; + *b = temp; +} +void shakersort(int a[], int n) +{ + int p, i; + for (p = 1; p <= n / 2; p++) + { + for (i = p - 1; i < n - p; i++) + if (a[i] > a[i+1]) + swap(&a[i], &a[i + 1]); + for (i = n - p - 1; i >= p; i--) + if (a[i] < a[i-1]) + swap(&a[i], &a[i - 1]); + } +} +int main() +{ + int arr[10] = {43, 432, 36, 5, 6, 57, 94, 63, 3, 44}; + int i; + shakersort(arr, 10); + for (i = 0 ; i < 10; i++) + printf("%d ", arr[i]); + return 0; +} \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Perform the Sorting Using Counting Sort.c b/c/Search_Sorting/C Program to Perform the Sorting Using Counting Sort.c new file mode 100644 index 0000000..0cd1db4 --- /dev/null +++ b/c/Search_Sorting/C Program to Perform the Sorting Using Counting Sort.c @@ -0,0 +1,38 @@ +#include +void countingsort(int arr[], int k, int n) +{ + int i, j; + int B[15], C[100]; + for (i = 0; i <= k; i++) + C[i] = 0; + for (j =1; j <= n; j++) + C[arr[j]] = C[arr[j]] + 1; + for (i = 1; i <= k; i++) + C[i] = C[i] + C[i-1]; + for (j = n; j >= 1; j--) + { + B[C[arr[j]]] = arr[j]; + C[arr[j]] = C[arr[j]] - 1; + } + printf("\nThe Sorted array is :\n"); + for(i = 1; i <= n; i++) + printf(" %d", B[i]); +} + +int main() +{ + int n,i,k = 0, arr[15]; + printf("Enter the number of elements : "); + scanf("%d", &n); + printf("\n\nEnter the elements to be sorted :\n"); + for ( i = 1; i <= n; i++) + { + scanf("%d", &arr[i]); + if (arr[i] > k) + { + k = arr[i]; + } + } + countingsort(arr, k, n); + return 0; +} \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Permute All Letters of an Input String.c b/c/Search_Sorting/C Program to Permute All Letters of an Input String.c new file mode 100644 index 0000000..41c52f4 --- /dev/null +++ b/c/Search_Sorting/C Program to Permute All Letters of an Input String.c @@ -0,0 +1,36 @@ +#include +#include +void swap (char *x, char *y) +{ + char temp; + temp = *x; + *x = *y; + *y = temp; +} + +void permute(char *a, int i, int n) +{ + int j; + if (i == n) + printf("%s\n", a); + else + { + for (j = i; j <= n; j++) + { + swap((a + i), (a + j)); + permute(a, i + 1, n); + swap((a + i), (a + j)); //backtrack + } + } +} + +int main() +{ + char str[21]; + int len; + printf("\nEnter a string: "); + scanf("%s", str); + len = strlen(str); + permute(str, 0, len - 1); + return 0; +} \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Read an Array and Search for an Element.c b/c/Search_Sorting/C Program to Read an Array and Search for an Element.c new file mode 100644 index 0000000..7524e20 --- /dev/null +++ b/c/Search_Sorting/C Program to Read an Array and Search for an Element.c @@ -0,0 +1,62 @@ +/* + * C program accept an array of N elements and a key to search. + * If the search is successful, it displays "SUCCESSFUL SEARCH". + * Otherwise, a message "UNSUCCESSFUL SEARCH" is displayed. + */ +#include + +void main() +{ + int array[20]; + int i, low, mid, high, key, size; + printf("Enter the size of an array\n"); + scanf("%d", &size); + printf("Enter the array elements\n"); + for (i = 0; i < size; i++) + { + scanf("%d", &array[i]); + } + printf("Enter the key\n"); + scanf("%d", &key); + /* search begins */ + low = 0; + high = (size - 1); + while (low <= high) + { + mid = (low + high) / 2; + if (key == array[mid]) + { + printf("SUCCESSFUL SEARCH\n"); + return; + } + if (key < array[mid]) + high = mid - 1; + else + low = mid + 1; + } + printf("UNSUCCESSFUL SEARCH\n"); +} +/* +*OUTPUT: +Enter the size of an array +4 +Enter the array elements +90 +560 +300 +390 +Enter the key +90 +SUCCESSFUL SEARCH + +Enter the size of an array +4 +Enter the array elements +100 +500 +580 +470 +Enter the key +300 +UNSUCCESSFUL SEARCH +*/ \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Represent Graph Using Adjacency Matrix.c b/c/Search_Sorting/C Program to Represent Graph Using Adjacency Matrix.c new file mode 100644 index 0000000..1693852 --- /dev/null +++ b/c/Search_Sorting/C Program to Represent Graph Using Adjacency Matrix.c @@ -0,0 +1,104 @@ +//... A Program to represent a Graph by using an Adjacency Matrix method + +/* +This C program generates graph using Adjacency Matrix Method. +A graph G,consists of two sets V and E. V is a finite non-empty set of vertices.E is a set of pairs of vertices,these pairs are called as edges V(G) and E(G) will represent the sets of vertices and edges of graph G. +Undirected graph – It is a graph with V vertices and E edges where E edges are undirected. In undirected graph, each edge which is present between the vertices Vi and Vj,is represented by using a pair of round vertices (Vi,Vj). +Directed graph – It is a graph with V vertices and E edges where E edges are directed.In directed graph,if Vi and Vj nodes having an edge.than it is represented by a pair of triangular brackets Vi,Vj. +*/ +#include +#include +void main() +{ + int option; + do + { + printf("\n A Program to represent a Graph by using an "); + printf("Adjacency Matrix method \n "); + printf("\n 1. Directed Graph "); + printf("\n 2. Un-Directed Graph "); + printf("\n 3. Exit "); + printf("\n\n Select a proper option : "); + scanf("%d", &option); + switch(option) + { + case 1 : + dir_graph(); + break; + case 2 : + undir_graph(); + break; + case 3 : + exit(0); + } // switch + } + while(1); +} + +int dir_graph() +{ + int adj_mat[50][50]; + int n; + int in_deg, out_deg, i, j; + printf("\n How Many Vertices ? : "); + scanf("%d", &n); + read_graph(adj_mat, n); + printf("\n Vertex \t In_Degree \t Out_Degree \t Total_Degree "); + for (i = 1; i <= n ; i++ ) + { + in_deg = out_deg = 0; + for ( j = 1 ; j <= n ; j++ ) + { + if ( adj_mat[j][i] == 1 ) + in_deg++; + } + for ( j = 1 ; j <= n ; j++ ) + if (adj_mat[i][j] == 1 ) + out_deg++; + printf("\n\n %5d\t\t\t%d\t\t%d\t\t%d\n\n",i,in_deg,out_deg,in_deg+out_deg); + } + return; +} + +int undir_graph() +{ + int adj_mat[50][50]; + int deg, i, j, n; + printf("\n How Many Vertices ? : "); + scanf("%d", &n); + read_graph(adj_mat, n); + printf("\n Vertex \t Degree "); + for ( i = 1 ; i <= n ; i++ ) + { + deg = 0; + for ( j = 1 ; j <= n ; j++ ) + if ( adj_mat[i][j] == 1) + deg++; + printf("\n\n %5d \t\t %d\n\n", i, deg); + } + return; +} + +int read_graph ( int adj_mat[50][50], int n ) +{ + int i, j; + char reply; + for ( i = 1 ; i <= n ; i++ ) + { + for ( j = 1 ; j <= n ; j++ ) + { + if ( i == j ) + { + adj_mat[i][j] = 0; + continue; + } + printf("\n Vertices %d & %d are Adjacent ? (Y/N) :",i,j); + scanf("%c", &reply); + if ( reply == 'y' || reply == 'Y' ) + adj_mat[i][j] = 1; + else + adj_mat[i][j] = 0; + } + } + return; +} \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Represent Graph Using Incidence Matrix.c b/c/Search_Sorting/C Program to Represent Graph Using Incidence Matrix.c new file mode 100644 index 0000000..b98dfe1 --- /dev/null +++ b/c/Search_Sorting/C Program to Represent Graph Using Incidence Matrix.c @@ -0,0 +1,109 @@ +/* + * C Program to Describe the Representation of Graph using Incidence Matrix + */ +#include +struct node +{ + int from, to; +} a[5], t; +void addEdge(int am[][5], int i, int j, int in) +{ + int p, q; + a[in].from = i; + a[in].to = j; + for ( p = 0; p <= in; p++) + { + for (q = p + 1; q <= in; q++) + { + if (a[p].from > a[q].from) + { + t = a[p]; + a[p] = a[q]; + a[q] = t; + } + else if (a[p].from == a[q].from) + { + if (a[p].to > a[q].to) + { + t = a[p]; + a[p] = a[q]; + a[q] = t; + } + } + else + { + continue; + } + } + } +} +int main() +{ + int n, c = 0, x, y, ch, i, j; + int am[5][5]; + printf("Enter the no of vertices\n"); + scanf("%d", &n); + for (i = 0; i < 5; i++) + { + for (j = 0; j < 5; j++) + { + am[i][j] = 0; + } + } + while (ch != -1) + { + printf("Enter the nodes between which you want to introduce edge\n"); + scanf("%d%d", &x, &y); + addEdge(am, x, y, c); + c++; + printf("Press -1 to exit\n"); + scanf("%d", &ch); + } + for (j = 0; j < c; j++) + { + am[a[j].from][j] = 1; + am[a[j].to][j] = 1; + } + for (i = 0; i < n; i++) + { + for (j = 0; j < c; j++) + { + printf("%d\t",am[i][j]); + } + printf("\n"); + } +} + +/* +Enter the no of vertices +5 +Enter the nodes between which you want to introduce edge +0 +1 +Press -1 to exit +0 +Enter the nodes between which you want to introduce edge +0 +2 +Press -1 to exit +0 +Enter the nodes between which you want to introduce edge +2 +3 +Press -1 to exit +0 +Enter the nodes between which you want to introduce edge +1 +4 +Press -1 to exit +0 +Enter the nodes between which you want to introduce edge +0 +3 +Press -1 to exit +-1 +1 1 1 0 0 +1 0 0 1 0 +0 1 0 0 1 +0 0 1 0 1 +0 0 0 1 0 \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Search Sorted Sequence Using Divide and Conquer with the Aid of Fibonacci Numbers.c b/c/Search_Sorting/C Program to Search Sorted Sequence Using Divide and Conquer with the Aid of Fibonacci Numbers.c new file mode 100644 index 0000000..6d97408 --- /dev/null +++ b/c/Search_Sorting/C Program to Search Sorted Sequence Using Divide and Conquer with the Aid of Fibonacci Numbers.c @@ -0,0 +1,50 @@ +#include +#include + +int fibsearch(int a[], int n, long x) +{ + int inf = 0, pos, k; + static int kk= -1, nn = -1; + static int fib[]= {0, 1, 1, 2, 3, 5, 8, 13, 21, 34, 55, 89, 144, 233, 377, 610, 98, + 1597, 2584, 4181, 6765, 10946, 17711, 28657, 46368, 75025, 121393, 196418, 317811, + 514229, 832040, 1346269, 2178309, 3524578, 5702887, 9227465, 14930352, 24157817, + 39088169, 63245986, 102334155, 165580141 + }; + if (nn != n) + { + k = 0; + while (fib[k] < n) + k++; + kk = k; + nn = n; + } + else + k = kk; + while (k > 0) + { + pos = inf + fib[--k]; + if ((pos >= n) || (x < a[pos])); + else if (x > a[pos]) + { + inf = pos + 1; + k--; + } + else + { + return pos; + } + } + return -1; +} +main() +{ + int arr[] = {2, 3, 45, 56,67,78, 89, 99, 100, 101}; + int num, pos; + printf("\nEnter an element to search: "); + scanf("%d", &num); + pos = fibsearch(arr, 10, num); + if ( pos >= 0) + printf("\nElement is at index : %d", fibsearch(arr, 10, num)); + else + printf("\nElement NOT found!! "); +} \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Search for an Element in a Binary Search Tree.c b/c/Search_Sorting/C Program to Search for an Element in a Binary Search Tree.c new file mode 100644 index 0000000..ff6e85e --- /dev/null +++ b/c/Search_Sorting/C Program to Search for an Element in a Binary Search Tree.c @@ -0,0 +1,168 @@ +#include +#include +struct node +{ + int info; + struct node*left; + struct node*right; +}; +typedef struct node BST; +BST *LOC, *PAR; +void search(BST *root, int item) +{ + BST *save,*ptr; + if (root == NULL) + { + LOC = NULL; + PAR=NULL; + } + if (item == root -> info) + { + LOC = root; + PAR = NULL; + return; + } + if (item < root->info) + { + save = root; + ptr = root->left; + } + else + { + save = root; + ptr = root -> right; + } + while( ptr != NULL) + { + if (ptr -> info == item) + { + LOC = ptr; + PAR = save; + return; + } + if(item < ptr->info) + { + save = ptr; + ptr = ptr->left; + } + else + { + save = ptr; + ptr = ptr->right; + } + } + LOC = NULL; + PAR = save; + return; +} + +struct node* findmin(struct node*r) +{ + if (r == NULL) + return NULL; + else if (r->left!=NULL) + return findmin(r->left); + else if (r->left == NULL) + return r; +} +struct node*insert(struct node*r, int x) +{ + if (r == NULL) + { + r = (struct node*)malloc(sizeof(struct node)); + r->info = x; + r->left = r->right = NULL; + return r; + } + else if (x < r->info) + r->left = insert(r->left, x); + else if (x > r->info) + r->right = insert(r->right, x); + return r; +} + +struct node* del(struct node*r, int x) +{ + struct node *t; + if(r == NULL) + printf("\nElement not found"); + else if (x < r->info) + r->left = del(r->left, x); + else if (x > r->info) + r->right = del(r->right, x); + else if ((r->left != NULL) && (r->right != NULL)) + { + t = findmin(r->right); + r->info = t->info; + r->right = del(r->right, r->info); + } + else + { + t = r; + if (r->left == NULL) + r = r->right; + else if (r->right == NULL) + r = r->left; + free(t); + } + return r; +} + + +int main() +{ + struct node* root = NULL; + int x, c = 1, z; + int element; + char ch; + printf("\nEnter an element: "); + scanf("%d", &x); + root = insert(root, x); + printf("\nDo you want to enter another element :y or n"); + scanf(" %c",&ch); + while (ch == 'y') + { + printf("\nEnter an element:"); + scanf("%d", &x); + root = insert(root,x); + printf("\nPress y or n to insert another element: y or n: "); + scanf(" %c", &ch); + } + while(1) + { + printf("\n1 Insert an element "); + printf("\n2 Delete an element"); + printf("\n3 Search for an element "); + printf("\n4 Exit "); + printf("\nEnter your choice: "); + scanf("%d", &c); + switch(c) + { + case 1: + printf("\nEnter the item:"); + scanf("%d", &z); + root = insert(root,z); + break; + case 2: + printf("\nEnter the info to be deleted:"); + scanf("%d", &z); + root = del(root, z); + break; + case 3: + printf("\nEnter element to be searched: "); + scanf("%d", &element); + search(root, element); + if(LOC != NULL) + printf("\n%d Found in Binary Search Tree !!\n",element); + else + printf("\nIt is not present in Binary Search Tree\n"); + break; + case 4: + printf("\nExiting..."); + return; + default: + printf("Enter a valid choice: "); + } + } + return 0; +} \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Sort N Numbers in Ascending Order using Bubble Sort.c b/c/Search_Sorting/C Program to Sort N Numbers in Ascending Order using Bubble Sort.c new file mode 100644 index 0000000..1a8a6e8 --- /dev/null +++ b/c/Search_Sorting/C Program to Sort N Numbers in Ascending Order using Bubble Sort.c @@ -0,0 +1,68 @@ +/* + * C program to sort N numbers in ascending order using Bubble sort + * and print both the given and the sorted array + */ +#include +#define MAXSIZE 10 + +void main() +{ + int array[MAXSIZE]; + int i, j, num, temp; + printf("Enter the value of num \n"); + scanf("%d", &num); + printf("Enter the elements one by one \n"); + for (i = 0; i < num; i++) + { + scanf("%d", &array[i]); + } + printf("Input array is \n"); + for (i = 0; i < num; i++) + { + printf("%d\n", array[i]); + } + /* Bubble sorting begins */ + for (i = 0; i < num; i++) + { + for (j = 0; j < (num - i - 1); j++) + { + if (array[j] > array[j + 1]) + { + temp = array[j]; + array[j] = array[j + 1]; + array[j + 1] = temp; + } + } + } + printf("Sorted array is...\n"); + for (i = 0; i < num; i++) + { + printf("%d\n", array[i]); + } +} +/* +*OUTPUT: +Enter the value of num +6 +Enter the elements one by one +23 +45 +67 +89 +12 +34 +Input array is +23 +45 +67 +89 +12 +34 +Sorted array is... +12 +23 +34 +45 +67 +89 +*/ \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Sort an Array based on Heap Sort Algorithm.c b/c/Search_Sorting/C Program to Sort an Array based on Heap Sort Algorithm.c new file mode 100644 index 0000000..1f85bb6 --- /dev/null +++ b/c/Search_Sorting/C Program to Sort an Array based on Heap Sort Algorithm.c @@ -0,0 +1,105 @@ +/* + * C Program to sort an array based on heap sort algorithm(MAX heap) + */ +#include + +void main() +{ + int heap[10], no, i, j, c, root, temp; + printf("\n Enter no of elements :"); + scanf("%d", &no); + printf("\n Enter the nos : "); + for (i = 0; i < no; i++) + scanf("%d", &heap[i]); + for (i = 1; i < no; i++) + { + c = i; + do + { + root = (c - 1) / 2; + if (heap[root] < heap[c]) /* to create MAX heap array */ + { + temp = heap[root]; + heap[root] = heap[c]; + heap[c] = temp; + } + c = root; + } + while (c != 0); + } + printf("Heap array : "); + for (i = 0; i < no; i++) + printf("%d\t ", heap[i]); + for (j = no - 1; j >= 0; j--) + { + temp = heap[0]; + heap[0] = heap[j /* swap max element with rightmost leaf element */ + heap[j] = temp; + root = 0; + do + { + c = 2 * root + 1; /* left node of root element */ + if ((heap[c] < heap[c + 1]) && c < j-1) + c++; + if (heap[root] + +int min = 0, count = 0, array[100] = {0}, array1[100] = {0}; + +void main() +{ + int k, i, j, temp, t, n; + printf("Enter size of array :"); + scanf("%d", &count); + printf("Enter elements into array :"); + for (i = 0; i < count; i++) + { + scanf("%d", &array[i]); + array1[i] = array[i]; + } + for (k = 0; k < 3; k++) + { + for (i = 0; i < count; i++) + { + min = array[i] % 10; /* To find minimum lsd */ + t = i; + for (j = i + 1; j < count; j++) + { + if (min > (array[j] % 10)) + { + min = array[j] % 10; + t = j; + } + } + temp = array1[t]; + array1[t] = array1[i]; + array1[i] = temp; + temp = array[t]; + array[t] = array[i]; + array[i] = temp; + } + for (j = 0; j < count; j++) /*to find MSB */ + array[j] = array[j] / 10; + } + printf("Sorted Array (lSdradix sort) : "); + for (i = 0; i < count; i++) + printf("%d ", array1[i]); +} +/* +*OUTPUT: +/* Average Case +Enter size of array :7 +Enter elements into array :170 +45 +90 +75 +802 +24 +2 +Sorted Array (ladradix sort) : 2 24 45 75 90 170 802 + +/*Best case +Enter size of array :7 +Enter elements into array :22 +64 +121 +78 +159 +206 +348 +Sorted Array (ladradix sort) : 22 64 78 159 121 206 348 + +/* Worst case +Enter size of array :7 +Enter elements into array :985 +27 +64 +129 +345 +325 +091 +Sorted Array (ladradix sort) : 27 64 91 129 325 345 985 +*/ \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Sort the Array Elements using Gnome Sort.c b/c/Search_Sorting/C Program to Sort the Array Elements using Gnome Sort.c new file mode 100644 index 0000000..22971aa --- /dev/null +++ b/c/Search_Sorting/C Program to Sort the Array Elements using Gnome Sort.c @@ -0,0 +1,65 @@ +/* + * C Program to Sort the Array Elements using Gnome Sort + */ +#include + +void main() +{ + int i, temp, ar[10], n; + printf("\nenter the elemts number u would like to enter:"); + scanf("%d", &n); + printf("\nenter the elements to be sorted through gnome sort:\n"); + for (i = 0; i < n; i++) + scanf("%d", &ar[i]); + i = 0; + while (i < n) + { + if (i == 0 || ar[i - 1] <= ar[i]) + i++; + else + { + temp = ar[i-1]; + ar[i - 1] = ar[i]; + ar[i] = temp; + i = i - 1; + } + } + for (i = 0; i < n; i++) + printf("%d\t", ar[i]); +} +/* +*OUTPUT: +enter the elemts number u would like to enter:7 +enter the elements to be sorted through gnome sort: +6 +0 +9 +5 +2 +4 +3 +0 2 3 4 5 6 9 + +enter the elemts number u would like to enter:6 +enter the elements to be sorted through gnome sort: +1 +2 +4 +5 +6 +7 +1 2 4 5 6 7 + +enter the elemts number u would like to enter:9 +enter the elements to be sorted through gnome sort: +9 +8 +7 +6 +5 +4 +3 +3 +2 +2 3 3 4 5 6 7 8 9 +*/ \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Sort the Array in an Ascending Order.c b/c/Search_Sorting/C Program to Sort the Array in an Ascending Order.c new file mode 100644 index 0000000..4ba65f8 --- /dev/null +++ b/c/Search_Sorting/C Program to Sort the Array in an Ascending Order.c @@ -0,0 +1,48 @@ +/* + * C program to accept N numbers and arrange them in an ascending order + */ +#include + +void main() +{ + int i, j, a, n, number[30]; + printf("Enter the value of N \n"); + scanf("%d", &n); + printf("Enter the numbers \n"); + for (i = 0; i < n; ++i) + scanf("%d", &number[i]); + for (i = 0; i < n; ++i) + { + for (j = i + 1; j < n; ++j) + { + if (number[i] > number[j]) + { + a = number[i]; + number[i] = number[j]; + number[j] = a; + } + } + } + printf("The numbers arranged in ascending order are given below \n"); + for (i = 0; i < n; ++i) + printf("%d\n", number[i]); +} +/* +*OUTPUT: +Enter the value of N +6 +Enter the numbers +3 +78 +90 +456 +780 +200 +The numbers arranged in ascending order are given below +3 +78 +90 +200 +456 +780 +*/ \ No newline at end of file diff --git a/c/Search_Sorting/C Program to Sort the N Names in an Alphabetical Order.c b/c/Search_Sorting/C Program to Sort the N Names in an Alphabetical Order.c new file mode 100644 index 0000000..42c0abd --- /dev/null +++ b/c/Search_Sorting/C Program to Sort the N Names in an Alphabetical Order.c @@ -0,0 +1,66 @@ +/* + * C program to read N names, store them in the form of an array + * and sort them in alphabetical order. Output the given names and + * the sorted names in two columns side by side. + */ +#include +#include + +void main() +{ + char name[10][8], tname[10][8], temp[8]; + int i, j, n; + printf("Enter the value of n \n"); + scanf("%d", &n); + printf("Enter %d names n", \n); + for (i = 0; i < n; i++) + { + scanf("%s", name[i]); + strcpy(tname[i], name[i]); + } + for (i = 0; i < n - 1 ; i++) + { + for (j = i + 1; j < n; j++) + { + if (strcmp(name[i], name[j]) > 0) + { + strcpy(temp, name[i]); + strcpy(name[i], name[j]); + strcpy(name[j], temp); + } + } + } + printf("\n----------------------------------------\n"); + printf("Input NamestSorted names\n"); + printf("------------------------------------------\n"); + for (i = 0; i < n; i++) + { + printf("%s\t\t%s\n", tname[i], name[i]); + } + printf("------------------------------------------\n"); +} +/* +*OUTPUT: +Enter the value of n +7 +Enter 7 names +heap +stack +queue +object +class +program +project + +---------------------------------------- +Input Names Sorted names +------------------------------------------ +heap class +stack heap +queue object +object program +class project +program queue +project stack +------------------------------------------ +*/ \ No newline at end of file diff --git a/c/Search_Sorting/C Program to accept Sorted Array and do Search using Binary Search.c b/c/Search_Sorting/C Program to accept Sorted Array and do Search using Binary Search.c new file mode 100644 index 0000000..78fe7c9 --- /dev/null +++ b/c/Search_Sorting/C Program to accept Sorted Array and do Search using Binary Search.c @@ -0,0 +1,112 @@ +/* + * C program to accept N numbers sorted in ascending order + * and to search for a given number using binary search. + * Report success or failure. + */ +#include + +void main() +{ + int array[10]; + int i, j, num, temp, keynum; + int low, mid, high; + printf("Enter the value of num \n"); + scanf("%d", &num); + printf("Enter the elements one by one \n"); + for (i = 0; i < num; i++) + { + scanf("%d", &array[i]); + } + printf("Input array elements \n"); + for (i = 0; i < num; i++) + { + printf("%d\n", array[i]); + } + /* Bubble sorting begins */ + for (i = 0; i < num; i++) + { + for (j = 0; j < (num - i - 1); j++) + { + if (array[j] > array[j + 1]) + { + temp = array[j]; + array[j] = array[j + 1]; + array[j + 1] = temp; + } + } + } + printf("Sorted array is...\n"); + for (i = 0; i < num; i++) + { + printf("%d\n", array[i]); + } + printf("Enter the element to be searched \n"); + scanf("%d", &keynum); + /* Binary searching begins */ + low = 1; + high = num; + do + { + mid = (low + high) / 2; + if (keynum < array[mid]) + high = mid - 1; + else if (keynum > array[mid]) + low = mid + 1; + } + while (keynum != array[mid] && low <= high); + if (keynum == array[mid]) + { + printf("SEARCH SUCCESSFUL \n"); + } + else + { + printf("SEARCH FAILED \n"); + } +} +/* +*OUTPUT: +Enter the value of num +5 +Enter the elements one by one +23 +90 +56 +15 +58 +Input array elements +23 +90 +56 +15 +58 +Sorted array is... +15 +23 +56 +58 +90 +Enter the element to be searched +58 +SEARCH SUCCESSFUL + +Enter the value of num +4 +Enter the elements one by one +1 +98 +65 +45 +Input array elements +1 +98 +65 +45 +Sorted array is... +1 +45 +65 +98 +Enter the element to be searched +6 +SEARCH FAILED +*/ \ No newline at end of file diff --git a/c/Search_Sorting/C Program to demonstrate bucket sort.C b/c/Search_Sorting/C Program to demonstrate bucket sort.C new file mode 100644 index 0000000..676d5b8 --- /dev/null +++ b/c/Search_Sorting/C Program to demonstrate bucket sort.C @@ -0,0 +1,44 @@ +/* Program to demonstrate bucket sort */ + +/* Some textbooks and some teachers call radix sort as bucket sort i.e. they consider radix sort and bucket sort same. However, in some textbooks bucket sort is considered to be that sorting technique in which the numbers to be sorted must be of ONLY ONE DIGIT while radix sort can sort numbers with MULTIPLE DIGITS. Personally, I follow the practice in which they are considered different. You may follow what your college teachers tell you.*/ + +#include +#include + +void bucketsort(int x[ ], int n) ; + +void main() +{ + int i, n, x[20] ; + clrscr() ; + printf("Enter the number of elements: ") ; + scanf("%d",&n) ; + printf("Enter the elements:\n") ; + for(i=0 ; i +#include + +void radixsort(int x[ ], int n) ; +void show(int x[ ], int n) ; + +void main() +{ + int i, n, x[20] ; + clrscr() ; + printf("Enter the number of elements: ") ; + scanf("%d",&n) ; + printf("Enter the elements:\n") ; + for(i=0 ; imax) + max=x[i] ; + /* Finding the number of digits in largest number which will be equal to the total number of passes */ + passes=0 ; + while(max>0) + { + max=max/10 ; + passes++ ; + } + /* Starting radix sort */ + divisor = 1 ; + for(digit=1 ; digit<=passes ; digit++) + { + for(i=0 ; i<10 ; i++) + count[i]=0 ; + /* Copying elements from the array into the buckets */ + for(i=0 ; i +#define INTERVAL 5 +/* If interval is 5 then every 5th element of original array will be represented in index table */ + +/* We assume that the original array x is sorted in ascending order */ + +struct table +{ + int kindex, pindex ; +} ; + +int iss(int x[ ], int n, int key, struct table index[ ], int indexsize) ; + +void main() +{ + /* Size of index table is 1/5th the size of original array since interval is 5 */ + struct table index[10] ; + int i, n, key, indexsize, p, q, x[50] ; + clrscr() ; + printf("Enter the no of elements: ") ; + scanf("%d",&n) ; + printf("Enter the elements:\n") ; + for(i=0 ; ihighlimit) + return -1 ; + else + return j ; +} diff --git a/c/Search_Sorting/C Program to demonstrate Interpolation search.C b/c/Search_Sorting/C Program to demonstrate Interpolation search.C new file mode 100644 index 0000000..c6156ca --- /dev/null +++ b/c/Search_Sorting/C Program to demonstrate Interpolation search.C @@ -0,0 +1,46 @@ +/* Program to demonstrate Interpolation search */ + +/* We assume that the array is sorted in ascending order */ + +#include +#include + +int interpolation(int x[ ], int n, int key) ; + +void main() +{ + int i, n, x[20], key ; + clrscr() ; + printf("Enter the number of elements: ") ; + scanf("%d",&n) ; + printf("Enter the elements:\n") ; + for(i=0 ; i +#include + +void bubble(int x[ ], int n) ; +void show(int x[ ], int n) ; + +void main() +{ + int i, n, x[20] ; + clrscr() ; + printf("Enter the number of elements: ") ; + scanf("%d",&n) ; + printf("Enter the elements:\n") ; + for(i=0 ; ix[j+1]) + { + temp=x[j] ; + x[j]=x[j+1] ; + x[j+1]=temp ; + flag=1 ; + } + show(x,n) ; + } +} + +/* For descending order use x[j]x[j+1] */ + +/* This is modified bubble sort. There is something called classical bubble sort also. +Modified bubble sort has the ability to terminate the function earlier if the array gets sorted before reaching the last pass. +To convert modified bubble sort to classical bubble sort, just remove all the statements related with flag */ + +void show(int x[ ], int n) +{ + int i ; + for(i=0 ; i +#include +#include + +void quick(int x[], int lb, int ub) ; +int partition(int x[], int lb, int ub) ; +void show(int x[], int lb, int ub) ; + +void main() +{ + int i, n, x[20] ; + clrscr() ; + printf("Enter the number of elements: ") ; + scanf("%d",&n) ; + printf("Enter the elements:\n") ; + for(i=0; ia) + up-- ; + if(down +#include +#define size 10 + +/* The hashtable size is normally 5 times the size of original array. However, in this program I have taken the size of hashtable same as original array */ +int ht[size] ; + +void store(int x[ ], int n) ; +int modulodivision(int key) ; +int linearprobe(int address) ; +void hashsearch() ; + +void main() +{ + int i, n, x[10] ; + char ch ; + clrscr() ; + printf("Enter the number of elements: ") ; + scanf("%d",&n) ; + printf("Enter the elements:\n") ; + for(i=0 ; i +#include + +void heapsort(int x[ ], int n) ; +void heapup(int heap[ ], int newnode) ; +void heapdown(int heap[ ], int root, int last) ; +void show(int x[ ], int n) ; + +void main() +{ + int i, n, x[20] ; + clrscr() ; + printf("Enter the number of elements: ") ; + scanf("%d",&n) ; + printf("Enter the elements:\n") ; + for(i=0 ; i0 ; i--) + { + /* Swapping */ + temp=x[0] ; + x[0]=x[i] ; + x[i]=temp ; + show(x,n) ; + /* Applying rectification */ + heapdown(x,0,i-1) ; + show(x,n) ; + } +} + +void heapup(int heap[ ], int newnode) +{ + int parent, temp ; + if(newnode>0) + { + parent=(newnode-1)/2 ; + if(heap[newnode]>heap[parent]) + { + temp=heap[parent] ; + heap[parent]=heap[newnode] ; + heap[newnode]=temp ; + heapup(heap,parent) ; + } + } +} + +void heapdown(int heap[ ], int root, int last) +{ + int leftchild, rightchild, largerchild, temp ; + leftchild=2*root+1 ; + rightchild=2*root+2 ; + /* Checking whether leftchild exists */ + if(leftchild<=last) + { + /*Checking whether right child exists */ + if(rightchild<=last) + if(heap[leftchild]>heap[rightchild]) + largerchild=leftchild ; + else + largerchild=rightchild; + else + largerchild=leftchild; + if(heap[root] +#include + +int binary(int x[ ], int n, int key) ; + +void main() +{ + int i, n, x[20], key ; + clrscr() ; + printf("Enter the number of elements: ") ; + scanf("%d",&n) ; + printf("Enter the elements:\n") ; + for(i=0 ; ix[mid]) if array x is in descending order */ \ No newline at end of file diff --git a/c/Search_Sorting/C Program to demonstrate non recursive merge sort.C b/c/Search_Sorting/C Program to demonstrate non recursive merge sort.C new file mode 100644 index 0000000..6bb3bb3 --- /dev/null +++ b/c/Search_Sorting/C Program to demonstrate non recursive merge sort.C @@ -0,0 +1,70 @@ +/* Program to demonstrate non recursive merge sort */ + +#include +#include + +void mergesort(int x[ ], int n) ; +void show(int x[ ], int n) ; + +void main() +{ + int i, n, x[20] ; + clrscr() ; + printf("Enter the number of elements: ") ; + scanf("%d",&n) ; + printf("Enter the elements:\n") ; + for(i=0 ; i +#include +#define STACKSIZE 50 + +struct bounds +{ + int lb, ub ; +} ; + +struct stack +{ + int top ; + struct bounds items[STACKSIZE] ; +} ; + +void quick(int x[ ], int n) ; +int partition(int x[ ], int lb, int ub) ; +void show(int x[ ], int lb, int ub) ; + +void push(struct stack *ps, struct bounds x) ; +struct bounds pop(struct stack *ps) ; +int empty(struct stack *ps) ; + +void main() +{ + int i, n, x[20] ; + clrscr() ; + printf("Enter the number of elements: ") ; + scanf("%d",&n) ; + printf("Enter the elements:\n") ; + for(i=0 ; ib.lb) + { + j=partition(x,b.lb,b.ub) ; + if(j-b.lb>b.ub-j) + { + /* stack the lower sub-array */ + temp=b.ub; + b.ub=j-1; + push(&s,b); + /* Process the upper sub-array */ + b.lb=j+1; + b.ub=temp; + } + else + { + /* stack the upper sub-array */ + temp=b.lb; + b.lb=j+1; + push(&s,b); + /* Process the lower sub-array */ + b.ub=j-1; + b.lb=temp; + } + } + } +} + +int partition(int x[ ], int lb, int ub) +{ + int a, down, up, temp ; + a=x[lb] ; + up=ub ; + down=lb ; + while(downa) + up-- ; + if(downtop==STACKSIZE-1) + { + printf("Stack Overflow. Cannot push. \n") ; + getch() ; + exit(1) ; + } + ps->items[++(ps->top)]=x ; +} + +struct bounds pop(struct stack *ps) +{ + if(empty(ps)) + { + printf("Stack Underflow. Cannot pop. \n") ; + getch() ; + exit(1) ; + } + return(ps->items[(ps->top)--]) ; +} + +int empty(struct stack *ps) +{ + if(ps->top==-1) + return 1 ; + else + return 0 ; +} + + +/* The method show() is optional. It is written to show output of each pass. It may not be written in theory exam. It is required only in practical exams */ + + + + diff --git a/c/Search_Sorting/C Program to demonstrate quick sort (recursive).C b/c/Search_Sorting/C Program to demonstrate quick sort (recursive).C new file mode 100644 index 0000000..7917cab --- /dev/null +++ b/c/Search_Sorting/C Program to demonstrate quick sort (recursive).C @@ -0,0 +1,73 @@ +/* Program to demonstrate quick sort (recursive) */ + +#include +#include + +void quick(int x[ ], int lb, int ub) ; +int partition(int x[ ], int lb, int ub) ; +void show(int x[ ], int lb, int ub) ; + +void main() +{ + int i, n, x[20] ; + clrscr() ; + printf("Enter the number of elements: ") ; + scanf("%d",&n) ; + printf("Enter the elements:\n") ; + for(i=0; ia) + up-- ; + if(down +#include + +int binary(int x[ ], int low, int high, int key) ; + +void main() +{ + int i, n, x[20], key ; + clrscr() ; + printf("Enter the number of elements: ") ; + scanf("%d",&n) ; + printf("Enter the elements:\n") ; + for(i=0 ; ihigh) + return -1 ; + mid=(low+high)/2 ; + if(key==x[mid]) + return mid ; + else if(keyx[mid]) if array x is in descending order */ diff --git a/c/Search_Sorting/C Program to demonstrate recursive merge sort.C b/c/Search_Sorting/C Program to demonstrate recursive merge sort.C new file mode 100644 index 0000000..3abad24 --- /dev/null +++ b/c/Search_Sorting/C Program to demonstrate recursive merge sort.C @@ -0,0 +1,67 @@ +/* Program to demonstrate recursive merge sort */ + +#include +#include + +void mergesort(int x[ ], int lb, int ub) ; +void merge(int x[ ], int lb1, int ub1, int ub2) ; +void show(int x[ ], int lb, int ub) ; + +void main() +{ + int i, n, x[20] ; + clrscr() ; + printf("Enter the number of elements: ") ; + scanf("%d",&n) ; + printf("Enter the elements:\n") ; + for(i=0 ; i for descending order */ + temp[k++]=x[i++] ; + else + temp[k++]=x[j++] ; + while(i<=ub1) + temp[k++]=x[i++] ; + while(j<=ub2) + temp[k++]=x[j++] ; + for(i=lb1, j=0 ; i<=ub2 ; i++, j++) + x[i]=temp[j] ; + show(x,lb1,ub2) ; +} + +void show(int x[ ], int lb, int ub) +{ + int i ; + for(i=lb ; i<=ub ; i++) + printf("%d ", x[i]) ; + printf("\n\n") ; +} + +/* The method show() is optional. It is written to show output of each pass. It may not be written in theory exam. It is required only in practical exams */ + diff --git a/c/Search_Sorting/C Program to demonstrate sequential search or linear search.C b/c/Search_Sorting/C Program to demonstrate sequential search or linear search.C new file mode 100644 index 0000000..ca60b58 --- /dev/null +++ b/c/Search_Sorting/C Program to demonstrate sequential search or linear search.C @@ -0,0 +1,36 @@ +/* Program to demonstrate sequential search or linear search */ + +#include +#include + +int sequential(int x[ ], int n, int key) ; + +void main() +{ + int i, n, x[20], key ; + clrscr() ; + printf("Enter the number of elements: ") ; + scanf("%d",&n) ; + printf("Enter the elements:\n") ; + for(i=0 ; i +#include + +void shell(int x[],int n) ; +void show(int x[],int n) ; + +void main() +{ + int i, n, x[20] ; + clrscr() ; + printf("Enter the number of elements: ") ; + scanf("%d",&n) ; + printf("Enter the elements:\n") ; + for(i=0; i=1) + { + printf("incr=%d \n",incr) ; + /* Insertion sort*/ + for(i=incr ; i=0&&y +#include + +void insert(int x[ ], int n) ; +void show(int x[ ], int n) ; + +void main() +{ + int i, n, x[20] ; + clrscr() ; + printf("Enter the number of elements: ") ; + scanf("%d",&n) ; + printf("Enter the elements:\n") ; + for(i=0 ; i=0&&yx[j] */ + +/* The method show() is optional. It is written to show output of each pass. It may not be written in theory exam. It is required only in practical exams */ + diff --git a/c/Search_Sorting/C Program to demonstrate straight selection sort or push down sort.C b/c/Search_Sorting/C Program to demonstrate straight selection sort or push down sort.C new file mode 100644 index 0000000..03561a1 --- /dev/null +++ b/c/Search_Sorting/C Program to demonstrate straight selection sort or push down sort.C @@ -0,0 +1,54 @@ +/* Program to demonstrate straight selection sort or push down sort */ + +#include +#include + +void select(int x[ ], int n) ; +void show(int x[ ], int n) ; + +void main() +{ + int i, n, x[20] ; + clrscr() ; + printf("Enter the number of elements: ") ; + scanf("%d",&n) ; + printf("Enter the elements:\n") ; + for(i=0; i0 ; i--) + { + max=x[0] ; + index=0 ; + for(j=1 ; j<=i ; j++) + if(x[j]>max) + { + max=x[j] ; + index=j ; + } + x[index]=x[i] ; + x[i]=max ; + show(x,n) ; + } +} + +/* change x[j]>max to x[j] + +int search(int [], int, int); +int main() +{ + int size, index, key; + int list[20]; + int count = 0; + int i; + printf("Enter the size of the list: "); + scanf("%d", &size); + index = size; + printf("Printing the list:\n"); + for (i = 0; i < size; i++) + { + list[i] = rand() % size; + printf("%d\t", list[i]); + } + printf("\nEnter the key to search: "); + scanf("%d", &key); + while (index > 0) + { + index = search(list, index - 1, key); + /* In an array first position is indexed by 0 */ + printf("Key found at position: %d\n", index + 1); + count++; + } + if (!count) + printf("Key not found.\n"); + return 0; +} +int search(int array[], int size, int key) +{ + int location; + if (array[size] == key) + { + return size; + } + else if (size == -1) + { + return -1; + } + else + { + return (location = search(array, size - 1, key)); + } +} +/* +*OUTPUT: +Enter the size of the list: 10 + +Printing the list: +3 6 7 5 3 5 6 2 9 1 + +Enter the key to search: 5 + +Key found at position: 6 + +Key found at position: 4 +*/ \ No newline at end of file diff --git a/c/Series_Programs/C Program to calculate sum of series 1 - x^22! + x^44! - x^66! + x^88!..c b/c/Series_Programs/C Program to calculate sum of series 1 - x^22! + x^44! - x^66! + x^88!..c new file mode 100644 index 0000000..9f3cc88 --- /dev/null +++ b/c/Series_Programs/C Program to calculate sum of series 1 - x^22! + x^44! - x^66! + x^88!..c @@ -0,0 +1,61 @@ +/* Sum of series - Program to calculate sum of series 1 - x^2/2! + x^4/4! - x^6/6! + x^8/8! - ... */ + +#include +#include +#include + +long fact(int n) ; + +void main() +{ + int i, k, n ; + float x, sum=0 ; + clrscr() ; + printf("Enter the number of terms: ") ; + scanf("%d", &n) ; + printf("Enter the value of x: ") ; + scanf("%f", &x) ; + /* i keeps track of term count , whereas k is used for calculation purpose */ + for(i=1, k=0 ; i<=n ; i++, k=k+2) + { + if(i%2==1) + sum = sum + pow(x,k)/fact(k) ; + else + sum = sum - pow(x,k)/fact(k) ; + } + printf("Sum of the required series is %f", sum) ; + getch() ; +} + +long fact(int n) +{ + int i ; + long f=1; + for(i=1 ; i<=n ; i++) + f=f*i ; + return f ; +} + +/* +Output1 : + +Enter the number of terms: 1 +Enter the value of x: 8 +Sum of the required series is 1.000000 + +Output2: + +Enter the number of terms: 4 +Enter the value of x: 2 +Sum of the required series is -0.422222 + +Output3: + +Enter the number of terms: 3 +Enter the value of x: 5 +Sum of the required series is 14.541667 +*/ + + + + diff --git a/c/Series_Programs/C Program to calculate sum of series 12 + 34 + 56 + ....... + n..c b/c/Series_Programs/C Program to calculate sum of series 12 + 34 + 56 + ....... + n..c new file mode 100644 index 0000000..36e1298 --- /dev/null +++ b/c/Series_Programs/C Program to calculate sum of series 12 + 34 + 56 + ....... + n..c @@ -0,0 +1,28 @@ +/* Sum of series - Program to calculate sum of series 1/2 + 3/4 + 5/6 + ....... + n terms - May 2013 */ + +#include +#include + +void main() +{ + int i, n ; + float k, s=0 ; + clrscr() ; + printf("Enter n: ") ; + scanf("%d", &n) ; + /* i keeps track of term count , whereas k is used for calculation purpose */ + for(i=1, k=1 ; i<=n ; i++, k=k+2) + s=s+ k/(k+1) ; + /* k has to be float in the above expression. If k is int then s will remain zero */ + printf("Sum of the required series is %f", s) ; + getch() ; +} + +/* +Output : + +Enter n: 4 +Sum of the required series is 2.958333 + +*/ + diff --git a/c/Series_Programs/C Program to calculate sum of series 12 - 34 + 56 - 78 ....... upto n terms..c b/c/Series_Programs/C Program to calculate sum of series 12 - 34 + 56 - 78 ....... upto n terms..c new file mode 100644 index 0000000..c9f786d --- /dev/null +++ b/c/Series_Programs/C Program to calculate sum of series 12 - 34 + 56 - 78 ....... upto n terms..c @@ -0,0 +1,33 @@ +/* Sum of series - Program to calculate sum of series 1/2 - 3/4 + 5/6 - 7/8 ....... upto n terms - June 2014 */ + +#include +#include + +void main() +{ + int i, n ; + float k, s=0 ; + clrscr() ; + printf("Enter n: ") ; + scanf("%d", &n) ; + /* i keeps track of term count , whereas k is used for calculation purpose */ + for(i=1, k=1 ; i<=n ; i++, k=k+2) + { + if(i%2==1) + s=s + k/(k+1) ; + else + s=s - k/(k+1) ; + } + /* k has to be float in the above expression. If k is int then s will remain zero */ + printf("Sum of the required series is %f", s) ; + getch() ; +} + +/* +Output : + +Enter n: 4 +Sum of the required series is -0.291667 + +*/ + diff --git a/c/Series_Programs/C Program to find (1!(by)1) + (2!(by)2) + (3!(by)3) + (4!(by)4) + (5!(by)5) + ...c b/c/Series_Programs/C Program to find (1!(by)1) + (2!(by)2) + (3!(by)3) + (4!(by)4) + (5!(by)5) + ...c new file mode 100644 index 0000000..58758a6 --- /dev/null +++ b/c/Series_Programs/C Program to find (1!(by)1) + (2!(by)2) + (3!(by)3) + (4!(by)4) + (5!(by)5) + ...c @@ -0,0 +1,25 @@ +/*(1!/1) + (2!/2) + (3!/3) + (4!/4) + (5!/5) + ... + (n!/n)*/ +#include +long fact(int n) +{ + long i, f=1; + for(i=1; i<=n; i++) + { + f=f*i; + } + return f; +} + +int main() +{ + long i,n; + double sum=0; + printf("Enter value of n "); + scanf("%d",&n); + for(i=1; i<=n; i++) + { + sum=sum+(fact(i)/i); + } + printf("Sum: %lf",sum); + return 0; +} \ No newline at end of file diff --git a/c/Series_Programs/C Program to find (1^1) + (2^2) + (3^3) + (4^4) + (5^5) + ...c b/c/Series_Programs/C Program to find (1^1) + (2^2) + (3^3) + (4^4) + (5^5) + ...c new file mode 100644 index 0000000..1049ee2 --- /dev/null +++ b/c/Series_Programs/C Program to find (1^1) + (2^2) + (3^3) + (4^4) + (5^5) + ...c @@ -0,0 +1,25 @@ +/*(1^1) + (2^2) + (3^3) + (4^4) + (5^5) + ... + (n^n)*/ +#include +#include +long power(int a, int b) +{ + long i, p=1; + for(i=1; i<=b; i++) + { + p=p*a; + } + return p; +} + +int main() +{ + long i,n,sum=0; + printf("Enter value of n"); + scanf("%d",&n); + for(i=1; i<=n; i++) + { + sum=sum+power(i,i); + } + printf("Sum: %d",sum); + return 0; +} \ No newline at end of file diff --git a/c/Series_Programs/C Program to find Series and find sum of 1+3+5+...c b/c/Series_Programs/C Program to find Series and find sum of 1+3+5+...c new file mode 100644 index 0000000..9c91fa1 --- /dev/null +++ b/c/Series_Programs/C Program to find Series and find sum of 1+3+5+...c @@ -0,0 +1,19 @@ +/*Series and find sum of 1+3+5+...+n */ +#include +void main() +{ + int n,i,sum=0; + printf("Enter any no: "); + scanf("%d",&n); + for(i=1; i +#include +main() +{ + int n,i; + int sum=0; + printf("Enter the n i.e. max values of series: "); + scanf("%d",&n); + sum = pow(((n * (n + 1) ) / 2),2); + printf("Sum of the series : "); + for(i =1; i<=n; i++) + { + if (i != n) + printf("%d^3 + ",i); + else + printf("%d^3 = %d ",i,sum); + } +} \ No newline at end of file diff --git a/c/Series_Programs/C Program to find Sum of infinite GP series.c b/c/Series_Programs/C Program to find Sum of infinite GP series.c new file mode 100644 index 0000000..f92f1f6 --- /dev/null +++ b/c/Series_Programs/C Program to find Sum of infinite GP series.c @@ -0,0 +1,16 @@ +/*Sum of infinite GP series.*/ +#include +main() +{ + float a,r; + float sum=0; + printf("Enter the first number of the G.P. series: "); + scanf("%f",&a); + printf("Enter the common ratio of G.P. series: "); + scanf("%f",&r); + if(1 > r) + sum = a/(1-r); + else + sum = a/(r-1); + printf("\nSum of the infinite G.P. series: %f",sum); +} \ No newline at end of file diff --git a/c/Series_Programs/C Program to find Sum of series 1+1(by)2+1(by)3+....c b/c/Series_Programs/C Program to find Sum of series 1+1(by)2+1(by)3+....c new file mode 100644 index 0000000..7d84eb7 --- /dev/null +++ b/c/Series_Programs/C Program to find Sum of series 1+1(by)2+1(by)3+....c @@ -0,0 +1,19 @@ +/*Sum of series 1+1/2+1/3+....+1/n*/ +#include +void main() +{ + int n,i,sum=0; + printf("Enter any no: "); + scanf("%d",&n); + printf("1"); + for(i=2; i<=n-1; i++) + printf(" 1/%d +",i); + for(i=1; i<=n; i++) + sum=sum+i; + printf(" 1/%d",n); + printf("\nSum=1/%d",sum+1/n); +} +Output: +Enter any no: 7 +1 + 1/2 + 1/3 + 1/4 + 1/5 + 1/6 + 1/7 +Sum=1/28 \ No newline at end of file diff --git a/c/Series_Programs/C Program to find cos(x) using the series cos(x)..c b/c/Series_Programs/C Program to find cos(x) using the series cos(x)..c new file mode 100644 index 0000000..e4df087 --- /dev/null +++ b/c/Series_Programs/C Program to find cos(x) using the series cos(x)..c @@ -0,0 +1,45 @@ +/* Cosine Series - Program to find cos(x) using the series: cos(x) = 1 - (x^2) / 2! + (x^4) / 4! - (x^6) / 6! + .... Do calculations till the value of the next term is not lesser than 10^-5 */ + +/* We assume that the angle entered by user is between 0 and 2 pi radians (0 and 360 degrees) */ + +#include +#include +#define pi 3.141593 + +void main() +{ + double d, x, i=0, s=0, f=1, num, nt; + int tc=1 ; + /* s-sum , f-factorial , num - nemerator , nt - next term , tc - term count */ + clrscr() ; + printf("Enter the angle in degrees: ") ; + scanf("%lf", &d) ; + x=d*pi/180 ; /* converts angle to radians */ + num=1 ; + while(1) + { + f=f*i*(i-1) ; /* Calculates factorial */ + if(f==0) + f=1 ; + nt=num/f ; /* calculates next term */ + if(nt<0.00001) + break ; /* stops if next term is less than 10 raise to -5 */ + if(tc%2==1) /* alternating + and - */ + s=s+nt ; /* calculates sum*/ + else + s=s-nt ; + /* Preparation for next execution */ + i=i+2 ; + tc++ ; + num=num*x*x ; + } + printf("The cosine of angle %lf is %lf", d, s) ; + getch() ; +} + +/* +Output + +Enter the angle in degrees: 60 +The cosine of angle 60.000000 is 0.500000 +*/ diff --git a/c/Series_Programs/C Program to find sin(x) using the series sin(x)..c b/c/Series_Programs/C Program to find sin(x) using the series sin(x)..c new file mode 100644 index 0000000..a13bb49 --- /dev/null +++ b/c/Series_Programs/C Program to find sin(x) using the series sin(x)..c @@ -0,0 +1,45 @@ +/* Sine Series - Program to find sin(x) using the series: sin(x) = x - (x^3) / 3! + (x^5) / 5! - (x^7) / 7! + .... Do calculations till the value of the next term is not lesser than 10^-5 */ + +/* We assume that the angle entered by user is between 0 and 2 pi radians (0 and 360 degrees) */ + +#include +#include +#define pi 3.141593 + +void main() +{ + double d, x, i=1, s=0, f=1, num, nt; + int tc=1 ; + /* s-sum , f-factorial , num - nemerator , nt - next term , tc - term count */ + clrscr() ; + printf("Enter the angle in degrees: ") ; + scanf("%lf", &d) ; + x=d*pi/180 ; /* converts angle to radians */ + num=x ; + while(1) + { + f=f*i*(i-1) ; /* Calculates factorial */ + if(f==0) + f=1 ; + nt=num/f ; /* calculates next term */ + if(nt<0.00001) + break ; /* stops if next term is less than 10 raise to -5 */ + if(tc%2==1) /* alternating + and - */ + s=s+nt ; /* calculates sum*/ + else + s=s-nt ; + /* Preparation for next execution */ + i=i+2 ; + tc++ ; + num=num*x*x ; + } + printf("The sine of angle %lf is %lf", d, s) ; + getch() ; +} + +/* +Output + +Enter the angle in degrees: 30 +The sine of angle 30.000000 is 0.500002 +*/ diff --git a/c/Series_Programs/C Program to find sum of series 1 + 12 + 13 + ....... + 1n..c b/c/Series_Programs/C Program to find sum of series 1 + 12 + 13 + ....... + 1n..c new file mode 100644 index 0000000..dd2da27 --- /dev/null +++ b/c/Series_Programs/C Program to find sum of series 1 + 12 + 13 + ....... + 1n..c @@ -0,0 +1,26 @@ +/* Sum of series - Program to find sum of series 1 + 1/2 + 1/3 + ....... + 1/n */ + +#include +#include + +void main() +{ + int n ; + float i, s=0 ; + clrscr() ; + printf("Enter n: ") ; + scanf("%d", &n) ; + for(i=1 ; i<=n ; i++) + s=s+1/i ; + /* i has to be float in the above expression. If i is int then s is always 1.000000 since 1/i will be 0 for all i>1 */ + printf("Sum of the required series is %f", s) ; + getch() ; +} + +/* +Output : + +Enter n: 3 +Sum of the required series is 1.833333 +*/ + diff --git a/c/Series_Programs/C Program to find sum of series 1 + 12! + 13! + ....... + 1n!..c b/c/Series_Programs/C Program to find sum of series 1 + 12! + 13! + ....... + 1n!..c new file mode 100644 index 0000000..4525e5e --- /dev/null +++ b/c/Series_Programs/C Program to find sum of series 1 + 12! + 13! + ....... + 1n!..c @@ -0,0 +1,28 @@ +/* Sum of series - Program to find sum of series 1 + 1/2! + 1/3! + ....... + 1/n! */ + +#include +#include + +void main() +{ + int n ; + float i, f=1, s=0 ; + clrscr() ; + printf("Enter n: ") ; + scanf("%d", &n) ; + for(i=1 ; i<=n ; i++) + { + f=f*i ; + s=s+1/f ; + } + printf("Sum of the required series is %f", s) ; + getch() ; +} + +/* +Output : + +Enter n: 3 +Sum of the required series is 1.666667 +*/ + diff --git a/c/Series_Programs/C Program to find value of pi using the series pi^2 6 = 11^2 + 12^2 +..... + 11000^2..c b/c/Series_Programs/C Program to find value of pi using the series pi^2 6 = 11^2 + 12^2 +..... + 11000^2..c new file mode 100644 index 0000000..603f1d2 --- /dev/null +++ b/c/Series_Programs/C Program to find value of pi using the series pi^2 6 = 11^2 + 12^2 +..... + 11000^2..c @@ -0,0 +1,24 @@ +/* PI 's value - Program to find value of pi using the series : pi^2 / 6 = 1/1^2 + 1/2^2 +..... + 1/1000^2 */ + +#include +#include +#include + +void main() +{ + float s=0, pi, i ; + clrscr() ; + for(i=1 ; i<=1000 ; i++) + s=s+1/(i*i) ; /* Parentheses compulsory */ + pi=sqrt(s*6) ; + printf("The value of pi is %f", pi) ; + getch() ; +} + + +/* +Output : + +The value of pi is 3.140638 +*/ + diff --git a/c/Series_Programs/Exponential series of 1+x+x2(by)2!+x3(by)3!+.......c b/c/Series_Programs/Exponential series of 1+x+x2(by)2!+x3(by)3!+.......c new file mode 100644 index 0000000..21ade69 --- /dev/null +++ b/c/Series_Programs/Exponential series of 1+x+x2(by)2!+x3(by)3!+.......c @@ -0,0 +1,20 @@ +/*Exponential series of 1+x+x2/2!+x3/3!+.......+xn/n!*/ +#include +#include< math.h> +void main( ) +{ + int x, n, fact, i, j; + float sum=1; + printf("Enter the 'x' value:"); + scanf("%d",&x); + printf("\nEnter the 'n' value:"); + scanf("%d",&n); + for(i=1; i< =n ; i++) + { + fact=1; + for( j=i ; j >=1; j--) + fact=fact*j; + sum=sum+(pow(x,i )/ fact); + } + printf("\nSum of the series : %f ",sum); +} \ No newline at end of file diff --git a/c/Series_Programs/To print series using function in C.c b/c/Series_Programs/To print series using function in C.c new file mode 100644 index 0000000..3d86b4e --- /dev/null +++ b/c/Series_Programs/To print series using function in C.c @@ -0,0 +1,23 @@ + #include + #include + void main() + { + int num=9,i; + clrscr(); + printf("%d ",num); + for(i=4;i<=10;i++) + { + num=num+pow(2,i); + printf("%d ",num); + } + getch(); + } + pow(int a,int b) + { + int prod=1,j; + for(j=1;j<=b;j++) + prod=prod*a; + return(prod); + } + + diff --git a/c/Series_Programs/Write a c program to find out the sum of given A.P.c b/c/Series_Programs/Write a c program to find out the sum of given A.P.c new file mode 100644 index 0000000..6397903 --- /dev/null +++ b/c/Series_Programs/Write a c program to find out the sum of given A.P.c @@ -0,0 +1,21 @@ + #include + #include + int main() { + int a,d,n,i,tn; + int sum=0; + printf("Enter the first number of the A.P. series: "); + scanf("%d",&a); + printf("Enter the total numbers in the A.P. series: "); + scanf("%d",&n); + printf("Enter the common difference of A.P. series: "); + scanf("%d",&d); + sum = ( n * ( 2 * a + ( n -1 ) * d ) )/ 2; + tn = a + (n-1) * d; + printf("Sum of the series A.P.: "); + for (i=a;i<=tn; i= i + d ) { + if (i != tn) + printf("%d + ",i); else + printf("%d = %d ",i,sum); + } + return 0; + } \ No newline at end of file diff --git a/c/Series_Programs/Write a c program to find out the sum of given G.P.c b/c/Series_Programs/Write a c program to find out the sum of given G.P.c new file mode 100644 index 0000000..fbf9695 --- /dev/null +++ b/c/Series_Programs/Write a c program to find out the sum of given G.P.c @@ -0,0 +1,18 @@ + #include + #include + int main() { + float a,r,i,tn; + int n; + float sum=0; + printf("Enter the first number of the G.P. series: "); + scanf("%f",&a); + printf("Enter the total numbers in the G.P. series: "); + scanf("%d",&n); + printf("Enter the common ratio of G.P. series: "); + scanf("%f",&r); + sum = (a*(1 - pow(r,n+1)))/(1-r); + tn = a * (1 -pow(r,n-1)); + printf("tn term of G.P.: %f",tn); + printf("\nSum of the G.P.: %f",sum); + return 0; + } \ No newline at end of file diff --git a/c/Series_Programs/Write a c program to find out the sum of given H.P.c b/c/Series_Programs/Write a c program to find out the sum of given H.P.c new file mode 100644 index 0000000..25c550e --- /dev/null +++ b/c/Series_Programs/Write a c program to find out the sum of given H.P.c @@ -0,0 +1,18 @@ + #include + #include + void main() { + int n; + float i, sum, t; + printf("1+1/2+1/3+......+1/n\n"); + printf("Enter the value of n\n"); + scanf("%d",& + amp; + n); + sum=0; + for (i=1;i<=n;i++) { + t=1/i; + sum=sum+t; + } + printf("%f",sum); + getch(); + } \ No newline at end of file diff --git a/c/Series_Programs/Write a c program to find out the sum of series 1 + 2 + n.c b/c/Series_Programs/Write a c program to find out the sum of series 1 + 2 + n.c new file mode 100644 index 0000000..179df19 --- /dev/null +++ b/c/Series_Programs/Write a c program to find out the sum of series 1 + 2 + n.c @@ -0,0 +1,15 @@ + #include + int main() { + int n,i; + int sum=0; + printf("Enter the n i.e. max values of series: "); + scanf("%d",&n); + sum = (n * (n + 1)) / 2; + printf("Sum of the series: "); + for (i =1;i <= n;i++) { + if (i!=n) + printf("%d + ",i); else + printf("%d = %d ",i,sum); + } + return 0; + } \ No newline at end of file diff --git a/c/Series_Programs/Write a c program to find out the sum of series 12 + 22 + n2.c b/c/Series_Programs/Write a c program to find out the sum of series 12 + 22 + n2.c new file mode 100644 index 0000000..33ef680 --- /dev/null +++ b/c/Series_Programs/Write a c program to find out the sum of series 12 + 22 + n2.c @@ -0,0 +1,15 @@ + #include + int main() { + int n,i; + int sum=0; + printf("Enter the n i.e. max values of series: "); + scanf("%d",&n); + sum = (n * (n + 1) * (2 * n + 1 )) / 6; + printf("Sum of the series : "); + for (i =1;i<=n;i++) { + if (i != n) + printf("%d^2 + ",i); else + printf("%d^2 = %d ",i,sum); + } + return 0; + } \ No newline at end of file diff --git a/c/Series_Programs/Write a c program to find out the sum of series 13 + 23 + + n3.c b/c/Series_Programs/Write a c program to find out the sum of series 13 + 23 + + n3.c new file mode 100644 index 0000000..b4a615f --- /dev/null +++ b/c/Series_Programs/Write a c program to find out the sum of series 13 + 23 + + n3.c @@ -0,0 +1,16 @@ + #include + #include + int main() { + int n,i; + int sum=0; + printf("Enter the n i.e. max values of series: "); + scanf("%d",&n); + sum = pow(((n * (n + 1) ) / 2),2); + printf("Sum of the series : "); + for (i =1;i<=n;i++) { + if (i != n) + printf("%d^3 + ",i); else + printf("%d^3 = %d ",i,sum); + } + return 0; + } \ No newline at end of file diff --git a/c/String/C Program To Count the Occurence of a Substring in String.c b/c/String/C Program To Count the Occurence of a Substring in String.c new file mode 100644 index 0000000..bf575dd --- /dev/null +++ b/c/String/C Program To Count the Occurence of a Substring in String.c @@ -0,0 +1,50 @@ +/* +* C Program To Count the Occurence of a Substring in String + */ +#include +#include + +char str[100], sub[100]; +int count = 0, count1 = 0; + +void main() +{ + int i, j, l, l1, l2; + printf(" + Enter a string : "); + scanf("%[^ + ]s", str); + l1 = strlen(str); + printf(" + Enter a substring : "); + scanf(" %[^ + ]s", sub); + l2 = strlen(sub); + for (i = 0; i < l1;) + { + j = 0; + count = 0; + while ((str[i] == sub[j])) + { + count++; + i++; + j++; + } + if (count == l2) + { + count1++; + count = 0; + } + else + i++; + } + printf("%s occurs %d times in %s", sub, count1, str); +} + + +Enter a string : +prrrogram c prrrogramming + +Enter a substring : +rr +rr occurs 2 times in prrrogram c prrrogramming \ No newline at end of file diff --git a/c/String/C Program To Find the Highest Frequency Character in a String.c b/c/String/C Program To Find the Highest Frequency Character in a String.c new file mode 100644 index 0000000..a0ec2b6 --- /dev/null +++ b/c/String/C Program To Find the Highest Frequency Character in a String.c @@ -0,0 +1,66 @@ +/* +* C Program To Find the Highest Frequency Character in a String +*/ +#include +#include + +char string1[100], visited[100]; +int count[100] = {0}, flag = 0; + +void main() +{ + int i, j = 0, k = 0, l, max, index; + printf("Enter a string : "); + scanf("%[^ + ]s", string1); + l = strlen(string1); + for (i = 0; i < l; i++) + { + if (i == 0) + { + visited[j++] = string1[i]; + count[j - 1]++; + } + else + { + for (k = 0; k < j; k++) + { + if (string1[i] == visited[k]) + { + count[k]++; + flag = 1; + } + } + if (flag == 0) + { + visited[j++] = string1[i]; + count[j - 1]++; + } + flag = 0; + } + } + for (i = 0; i < j; i++) + { + if ((i == 0) && (visited[i] != ' ')) + { + max = count[i]; + continue; + } + if ((max < count[i]) && (visited[i] != ' ')) + { + max = count[i]; + index = i; + } + } + printf(" + Max repeated character in the string = %c ", visited[index]); + printf(" + It occurs %d times", count[index]); +} + + + Enter a string : + Welcome to your C Programming Class ! + + Max repeated character in the string = o + It occurs 4 times \ No newline at end of file diff --git a/c/String/C Program To Find the Sum of ASCII values of All Characters in a given String.c b/c/String/C Program To Find the Sum of ASCII values of All Characters in a given String.c new file mode 100644 index 0000000..7d2276a --- /dev/null +++ b/c/String/C Program To Find the Sum of ASCII values of All Characters in a given String.c @@ -0,0 +1,25 @@ +/* +* C Program To Find the Sum of ASCII values of All Characters in a + * given String +*/ +#include +#include + +void main() +{ + int sum = 0, i, len; + char string1[100]; + printf("Enter the string : "); + scanf("%[^]s", string1); + len = strlen(string1); + for (i = 0; i < len; i++) + { + sum = sum + string1[i]; + } + printf(" + Sum of all characters : %d ",sum); +} +/* + Enter the string : Welcome to Illumin8's C Programming Class, Welcome Again to C Class ! + +Sum of all characters : 6296 \ No newline at end of file diff --git a/c/String/C Program To Print Smallest and Biggest possible Word which is Palindrome in a given String.c b/c/String/C Program To Print Smallest and Biggest possible Word which is Palindrome in a given String.c new file mode 100644 index 0000000..5332652 --- /dev/null +++ b/c/String/C Program To Print Smallest and Biggest possible Word which is Palindrome in a given String.c @@ -0,0 +1,94 @@ +/* + * C Program To Print Smallest and Biggest possible Word + * which is Palindrome in a given String + */ +#include +#include +#include + +int main() +{ + int i = 0, l = 0, j, k, space = 0, count = 0, init = 0, min = 0, max = 0, len = 0, flag; + char a[100], b[30][20], c[30], d[30], minP[30], maxP[30]; + printf("Read a string:\n"); + fflush(stdin); + scanf("%[^\n]s", a); + for (i = 0; a[i] != '\0'; i++) + { + if (a[i] == ' ') + space++; + } + i = 0; + for (j = 0; j<(space+1); i++, j++) + { + k = 0; + while (a[i] != '\0') + { + if (a[i] == ' ') + { + break; + } + else + { + b[j][k++] = a[i]; + i++; + } + } + b[j][k] = '\0'; + } + for (j = 0; j < space + 1; j++) + printf("%s ", b[j]); + printf("\n"); + for (i = 0; i < space + 1; i++) + { + strcpy(c, b[i]); + count = strlen(b[i]); + k = 0; + for (l = count - 1; l >= 0; l--) + d[k++] = b[i][l]; + d[k] = '\0'; + if (strcmp(d, c) == 0) + { + flag = 1; + if (init < 1) + { + strcpy(minP, d); + strcpy(maxP, d); + min = strlen(minP); + max = strlen(maxP); + init++; + } + printf("String %s is a Palindrome\n", d); + len = strlen(d); + if (len >= max) + strcpy(maxP, d); + else if (len <= min) + strcpy(minP, d); + else + printf(""); + } + } + if (flag == 1) + { + printf("The minimum palindrome is %s\n", minP); + printf("The maximum palindrome is %s\n", maxP); + } + else + printf("given string has no pallindrome\n"); +} +/* +*OUTPUT: +Read a string: +aba abcba abcdcba bcd +aba abcba abcdcba bcd +String aba is a Palindrome +String abcba is a Palindrome +String abcdcba is a Palindrome +The minimum palindrome is aba +The maximum palindrome is abcdcba + +Read a string: +abc abcd +abc abcd +given string has no pallindrome +*/ \ No newline at end of file diff --git a/c/String/C Program to Accept 2 String & check whether all Characters in first String is Present in second String & Print.c b/c/String/C Program to Accept 2 String & check whether all Characters in first String is Present in second String & Print.c new file mode 100644 index 0000000..445899a --- /dev/null +++ b/c/String/C Program to Accept 2 String & check whether all Characters in first String is Present in second String & Print.c @@ -0,0 +1,80 @@ +/* +* C Program to Accept 2 String & check whether all Characters +* in first String is Present in second String & Print +*/ +#include +#include +#include +#include +#define CHAR_SIZE 26 + +void alphacheck(char *, int []); +void create(char *, int[]); + +int main() +{ + char str1[50], str2[50]; + int a1[CHAR_SIZE] = {0}, a2[CHAR_SIZE] = {0}, i; + char str1_alpha[CHAR_SIZE], str2_alpha[CHAR_SIZE]; + printf("Enter string1: "); + scanf("%s", str1); + printf("Enter string2: "); + scanf("%s", str2); + alphacheck(str1, a1); + alphacheck(str2, a2); + create(str1_alpha, a1); + create(str2_alpha, a2); + if (strcmp(str1_alpha, str2_alpha) == 0) + { + printf("All characters match in %s and %s. + ", str1, str2); + printf("The characters that match are: "); + for (i = 0; i < strlen(str1_alpha); i++) + { + printf("%c, ", str1_alpha[i]); + } + printf(" + "); + } + else + { + printf("All characters do not match in %s and %s. + ", str1, str2); + } + return 0; +} + +void alphacheck(char *str, int a[]) +{ + int i, index; + for (i = 0; i < strlen(str); i++) + { + str[i] = tolower(str[i]); + index = str[i] - 'a'; + if (!a[index]) + { + a[index] = 1; + } + } +} + +void create(char *str, int a[]) +{ + int i, j = 0; + for (i = 0; i < CHAR_SIZE; i++) + { + if (a[i]) + { + str[j++] = i + 'a'; + } + } + str[j] = ''; +} + +Enter string1: +aspired +Enter string2: +despair +All characters match in aspired and despair. +The characters that match are: +a, d, e, i, p, r, s, diff --git a/c/String/C Program to Accepts two Strings _ Compare them.c b/c/String/C Program to Accepts two Strings _ Compare them.c new file mode 100644 index 0000000..bc1126e --- /dev/null +++ b/c/String/C Program to Accepts two Strings _ Compare them.c @@ -0,0 +1,67 @@ +/* + * C Program to accepts two strings and compare them. Display + * the result whether both are equal, or first string is greater + * than the second or the first string is less than the second string + */ +#include + +void main() +{ + int count1 = 0, count2 = 0, flag = 0, i; + char string1[10], string2[10]; + printf("Enter a string:"); + gets(string1); + printf("Enter another string:"); + gets(string2); + /* Count the number of characters in string1 */ + while (string1[count1] != '\0') + count1++; + /* Count the number of characters in string2 */ + while (string2[count2] != '\0') + count2++; + i = 0; + while ((i < count1) && (i < count2)) + { + if (string1[i] == string2[i]) + { + i++; + continue; + } + if (string1[i] < string2[i]) + { + flag = -1; + break; + } + if (string1[i] > string2[i]) + { + flag = 1; + break; + } + } + if (flag == 0) + printf("Both strings are equal \n"); + if (flag == 1) + printf("String1 is greater than string2 \n", string1, string2); + if (flag == -1) + printf("String1 is less than string2 \n", string1, string2); +} +advertisements +$ cc pgm50.c +/$ a.out +Enter a string: +hello +Enter another string: +world +String1 is less than string2 + +$ a.out +Enter a string: +object +Enter another string: +class + String1 is greater than string2 + + $ a.out + Enter a string:object + Enter another string:object + Both strings are equal \ No newline at end of file diff --git a/c/String/C Program to Check if a String is a Palindrome without using the Built-in Function.c b/c/String/C Program to Check if a String is a Palindrome without using the Built-in Function.c new file mode 100644 index 0000000..ae94bfd --- /dev/null +++ b/c/String/C Program to Check if a String is a Palindrome without using the Built-in Function.c @@ -0,0 +1,51 @@ +/* + * C program to find the length of a string without using the + * built-in function also check whether it is a palindrome + */ +#include +#include + +void main() +{ + char string[25], reverse_string[25] = {'\0'}; + int i, length = 0, flag = 0; + printf("Enter a string \n"); + gets(string); + /* keep going through each character of the string till its end */ + for (i = 0; string[i] != '\0'; i++) + { + length++; + } + printf("The length of the string '%s' = %d\n", string, length); + for (i = length - 1; i >= 0 ; i--) + { + reverse_string[length - i - 1] = string[i]; + } + /* Check if the string is a Palindrome */ + for (flag = 1, i = 0; i < length ; i++) + { + if (reverse_string[i] != string[i]) + flag = 0; + } + if (flag == 1) + printf ("%s is a palindrome \n", string); + else + printf("%s is not a palindrome \n", string); +} +/* +*OUTPUT: +Enter a string +how are you +The length of the string 'how are you' = 12 +how are you is not a palindrome + +Enter a string +madam +The length of the string 'madam' = 5 +madam is a palindrome + +Enter a string +mam +The length of the string 'mam' = 3 +mam is a palindrome +*/ \ No newline at end of file diff --git a/c/String/C Program to Check if a given String is Palindrome.c b/c/String/C Program to Check if a given String is Palindrome.c new file mode 100644 index 0000000..379c15b --- /dev/null +++ b/c/String/C Program to Check if a given String is Palindrome.c @@ -0,0 +1,49 @@ +/* + * C program to read a string and check if it's a palindrome, without + * using library functions. Display the result. + */ +#include +#include + +void main() +{ + char string[25], reverse_string[25] = {'\0'}; + int i, length = 0, flag = 0; + fflush(stdin); + printf("Enter a string \n"); + gets(string); + /* keep going through each character of the string till its end */ + for (i = 0; string[i] != '\0'; i++) + { + length++; + } + for (i = length - 1; i >= 0; i--) + { + reverse_string[length - i - 1] = string[i]; + } + /* + * Compare the input string and its reverse. If both are equal + * then the input string is palindrome. + */ + for (i = 0; i < length; i++) + { + if (reverse_string[i] == string[i]) + flag = 1; + else + flag = 0; + } + if (flag == 1) + printf("%s is a palindrome \n", string); + else + printf("%s is not a palindrome \n", string); +} +/* +*OUTPUT: +Enter a string +sanfoundry +sanfoundry is not a palindrome + +Enter a string +malayalam +malayalam is a palindrome +*/ \ No newline at end of file diff --git a/c/String/C Program to Check if the Substring is present in the given String.c b/c/String/C Program to Check if the Substring is present in the given String.c new file mode 100644 index 0000000..dfae11f --- /dev/null +++ b/c/String/C Program to Check if the Substring is present in the given String.c @@ -0,0 +1,47 @@ +/* + * C program to accept a string and a substring and + * check if the substring is present in the given string + */ +#include + +void main() +{ + char str[80], search[10]; + int count1 = 0, count2 = 0, i, j, flag; + printf("Enter a string:"); + gets(str); + printf("Enter search substring:"); + gets(search); + while (str[count1] != '�') + count1++; + while (search[count2] != '�') + count2++; + for (i = 0; i <= count1 - count2; i++) + { + for (j = i; j < i + count2; j++) + { + flag = 1; + if (str[j] != search[j - i]) + { + flag = 0; + break; + } + } + if (flag == 1) + break; + } + if (flag == 1) + printf("SEARCH SUCCESSFUL!"); + else + printf("SEARCH UNSUCCESSFUL!"); +} +/* +*OUTPUT: +Enter a string: hello +Enter search substring: world +SEARCH UNSUCCESSFUL! + +Enter a string: helloworld +Enter search substring:ld +SEARCH SUCCESSFUL! +*/ \ No newline at end of file diff --git a/c/String/C Program to Check whether a given Character is present in a String, Find Frequency & Position of Occurrence.c b/c/String/C Program to Check whether a given Character is present in a String, Find Frequency & Position of Occurrence.c new file mode 100644 index 0000000..c7e12b7 --- /dev/null +++ b/c/String/C Program to Check whether a given Character is present in a String, Find Frequency & Position of Occurrence.c @@ -0,0 +1,43 @@ +/* +* C Program to Check whether a given Character is present in a +* String, Find Frequency & Position of Occurrence +*/ +#include +#include + +int main() +{ + char a, word[50]; + int i, freq = 0, flag = 0; + printf("Enter character: "); + scanf("%c", &a); + printf("Now enter the word: "); + scanf("%s", word); + printf("Positions of '%c' in %s are: ", a, word); + for (i = 0; i < strlen(word); i++) + { + if (word[i] == a) + { + flag = 1; + printf("%d ", i + 1); + freq++; + } + } + if (flag) + { + printf(" + Character '%c' occured for %d times. + ", a, freq); + } +else + { + printf("None + ");v } + return 0; + } +Enter character: +r +Now enter the word: +programming +Positions of 'r' in programming are: 2 5 +Character 'r' occured for 2 times. \ No newline at end of file diff --git a/c/String/C Program to Check whether a given String is Palindrome or not using Recursion.c b/c/String/C Program to Check whether a given String is Palindrome or not using Recursion.c new file mode 100644 index 0000000..1072302 --- /dev/null +++ b/c/String/C Program to Check whether a given String is Palindrome or not using Recursion.c @@ -0,0 +1,42 @@ +/* + * C Program to Check whether a given String is Palindrome or not + * using Recursion + */ +#include +#include + +void check(char [], int); + +int main() +{ + char word[15]; + printf("Enter a word to check if it is a palindrome\n"); + scanf("%s", word); + check(word, 0); + return 0; +} + +void check(char word[], int index) +{ + int len = strlen(word) - (index + 1); + if (word[index] == word[len]) + { + if (index + 1 == len || index == len) + { + printf("The entered word is a palindrome\n"); + return; + } + check(word, index + 1); + } + else + { + printf("The entered word is not a palindrome\n"); + } +} +} +/* +*OUTPUT: +Enter a word to check if it is a palindrome +malayalam +The entered word is a palindrome +*/ \ No newline at end of file diff --git a/c/String/C Program to Check whether two Strings are Anagrams.c b/c/String/C Program to Check whether two Strings are Anagrams.c new file mode 100644 index 0000000..0218bf8 --- /dev/null +++ b/c/String/C Program to Check whether two Strings are Anagrams.c @@ -0,0 +1,62 @@ +/* +* C Program to Check whether two Strings are Anagrams +*/ +#include + +int find_anagram(char [], char []); + +int main() +{ + char array1[100], array2[100]; + int flag; + printf("Enter the string + "); + gets(array1); + printf("Enter another string + "); + gets(array2); + flag = find_anagram(array1, array2); + if (flag == 1) + printf(""%s" and "%s" are anagrams. + ", array1, array2); + else + printf(""%s" and "%s" are not anagrams. + ", array1, array2); + return 0; + } + + int find_anagram(char array1[], char array2[]) +{ + int num1[26] = {0}, num2[26] = {0}, i = 0; + while (array1[i] != '') + { + num1[array1[i] - 'a']++; + i++; + } + i = 0; + while (array2[i] != '') + { + num2[array2[i] -'a']++; + i++; + } + for (i = 0; i < 26; i++) + { + if (num1[i] != num2[i]) + return 0; + } + return 1; +} + + + +Enter the string +abll +Enter another string +ball +"abll" and "ball" are anagrams. + +Enter the string +tall +Enter another string +all +"tall" and "all" are not anagrams. \ No newline at end of file diff --git a/c/String/C Program to Concatenate the given two Strings Lexically.c b/c/String/C Program to Concatenate the given two Strings Lexically.c new file mode 100644 index 0000000..d88ba7f --- /dev/null +++ b/c/String/C Program to Concatenate the given two Strings Lexically.c @@ -0,0 +1,119 @@ +/* +* C Program to Concatenate the given two Strings Lexically +*/ +#include +#include + +void sort(char *p); + +void main() +{ + char string1[100], string2[100]; + int i, len, j; + printf(" + Enter a string : "); + scanf("%[^ + ]s", string1); + printf(" + Enter another string to concat : "); + scanf(" %[^ + ]s", string2); + len = strlen(string1); + string1[len] = ' '; + for(i = 0, j = len + 1; i < strlen(string2); i++, j++) + string1[j] = string2[i]; + string1[j]=''; + sort(string1); +} + + /* Sorting to make concatenation lexical */ + void sort(char *p) +{ + char temp[100]; + char a[100][100]; + int t1, i, j = 0, k = 0, l = strlen(p), x = 0, y = 0, z = 0, count, l1, l2; + for (i = 0; i < l; i++) + { + if (p[i] != ' ') + { + a[k][j++] = p[i]; + } + else + { + a[k][j] = ''; + k++; + j = 0; + } + } + t1 = k; + k = 0; + for (i = 0; i < t1; i++) + { + for (j = i + 1; j <= t1; j++) + { + l1 = strlen(a[i]); + l2 = strlen(a[j]); + if (l1 > l2) + count = l1; + else + count = l2; + x = 0, y = 0; + while ((x < count) || (y < count)) + { + if (a[i][x] == a[j][y]) + { + x++; + y++; + continue; + } + else if (a[i][x] < a[j][y]) break; + else if (a[i][x] > a[j][y]) + { + for (z = 0; z < l2; z++) + { + temp[z] = a[j][z]; + a[j][z] = ''; + } + temp[z] = ''; + for (z = 0; z < l1; z++) + { + a[j][z] = a[i][z]; + a[i][z] = ''; + } + a[j][z] = ''; + for (z = 0; z < strlen(temp); z++) + { + a[i][z] = temp[z]; + } + break; + } + } + } + } + for (i = 0; i < l; i++) + p[i] = ''; + k = 0; + j = 0; + for (i = 0; i < l; i++) + { + if (a[k][j] != '') + { + p[i] = a[k][j++]; + } + else + { + k++; + j = 0; + p[i] = ' '; + } + } + puts(p); +} + + +Enter a string : +hello this + +Enter another string to concat : +is illuminate +hello is illuminate this \ No newline at end of file diff --git a/c/String/C Program to Concatenate two Strings Lexically.c b/c/String/C Program to Concatenate two Strings Lexically.c new file mode 100644 index 0000000..ba30dca --- /dev/null +++ b/c/String/C Program to Concatenate two Strings Lexically.c @@ -0,0 +1,115 @@ +/* + * C Program to Concatenate the given two Strings Lexically + */ +#include +#include + +void sort(char *p); + +void main() +{ + char string1[100], string2[100]; + int i, len, j; + printf("\nEnter a string : "); + scanf("%[^\n]s", string1); + printf("\nEnter another string to concat : "); + scanf(" %[^\n]s", string2); + len = strlen(string1); + string1[len] = ' '; + for(i = 0, j = len + 1; i < strlen(string2); i++, j++) + string1[j] = string2[i]; + string1[j]='\0'; + sort(string1); +} + +/* Sorting to make concatenation lexical */ +void sort(char *p) +{ + char temp[100]; + char a[100][100]; + int t1, i, j = 0, k = 0, l = strlen(p), x = 0, y = 0, z = 0, count, l1, l2; + for (i = 0; i < l; i++) + { + if (p[i] != ' ') + { + a[k][j++] = p[i]; + } + else + { + a[k][j] = '\0'; + k++; + j = 0; + } + } + t1 = k; + k = 0; + for (i = 0; i < t1; i++) + { + for (j = i + 1; j <= t1; j++) + { + l1 = strlen(a[i]); + l2 = strlen(a[j]); + if (l1 > l2) + count = l1; + else + count = l2; + x = 0, y = 0; + while ((x < count) || (y < count)) + { + if (a[i][x] == a[j][y]) + { + x++; + y++; + continue; + } + else if (a[i][x] < a[j][y]) break; + else if (a[i][x] > a[j][y]) + { + for (z = 0; z < l2; z++) + { + temp[z] = a[j][z]; + a[j][z] = '\0'; + } + temp[z] = '\0'; + for (z = 0; z < l1; z++) + { + a[j][z] = a[i][z]; + a[i][z] = '\0'; + } + a[j][z] = '\0'; + for (z = 0; z < strlen(temp); z++) + { + a[i][z] = temp[z]; + } + break; + } + } + } + } + for (i = 0; i < l; i++) + p[i] = '\0'; + k = 0; + j = 0; + for (i = 0; i < l; i++) + { + if (a[k][j] != '\0') + { + p[i] = a[k][j++]; + } + else + { + k++; + j = 0; + p[i] = ' '; + } + } + puts(p); +} +/* +*OUTPUT: + +Enter a string : hello this + +Enter another string to concat : is sanfoundry +hello is sanfoundry this +*/ \ No newline at end of file diff --git a/c/String/C Program to Copy One String to Another using Recursion.c b/c/String/C Program to Copy One String to Another using Recursion.c new file mode 100644 index 0000000..51e093c --- /dev/null +++ b/c/String/C Program to Copy One String to Another using Recursion.c @@ -0,0 +1,33 @@ +/* + * C Program to Copy One String to Another using Recursion + */ +#include + +void copy(char [], char [], int); + +int main() +{ + char str1[20], str2[20]; + printf("Enter string to copy: "); + scanf("%s", str1); + copy(str1, str2, 0); + printf("Copying success.\n"); + printf("The first string is: %s\n", str1); + printf("The second string is: %s\n", str2); + return 0; +} + +void copy(char str1[], char str2[], int index) +{ + str2[index] = str1[index]; + if (str1[index] == '\0') + return; + copy(str1, str2, index + 1); +} +/* +*OUTPUT: +Enter string to copy: sanfoundry +Copying success. +The first string is: sanfoundry +The second string is: sanfoundry +*/ \ No newline at end of file diff --git a/c/String/C Program to Count the Number of Vowels _ Consonants in a Sentence.c b/c/String/C Program to Count the Number of Vowels _ Consonants in a Sentence.c new file mode 100644 index 0000000..1d19ae8 --- /dev/null +++ b/c/String/C Program to Count the Number of Vowels _ Consonants in a Sentence.c @@ -0,0 +1,41 @@ +/* + * C program to read a sentence and count the total number of vowels + * and consonants in the sentence. + */ +#include + +void main() +{ + char sentence[80]; + int i, vowels = 0, consonants = 0, special = 0; + printf("Enter a sentence \n"); + gets(sentence); + for (i = 0; sentence[i] != '\0'; i++) + { + if ((sentence[i] == 'a' || sentence[i] == 'e' || sentence[i] == + 'i' || sentence[i] == 'o' || sentence[i] == 'u') || + (sentence[i] == 'A' || sentence[i] == 'E' || sentence[i] == + 'I' || sentence[i] == 'O' || sentence[i] == 'U')) + { + vowels = vowels + 1; + } + else + { + consonants = consonants + 1; + } + if (sentence[i] =='t' ||sentence[i] =='\0' || sentence[i] ==' ') + { + special = special + 1; + } + } + consonants = consonants - special; + printf("No. of vowels in %s = %d\n", sentence, vowels); + printf("No. of consonants in %s = %d\n", sentence, consonants); +} +/* +*OUTPUT: +Enter a sentence +welcome to sanfoundry +No. of vowels in welcome to sanfoundry = 7 +No. of consonants in welcome to sanfoundry = 12 +*/ \ No newline at end of file diff --git a/c/String/C Program to Count the Total Number of Words in the Sentence using Command Line Argument.c b/c/String/C Program to Count the Total Number of Words in the Sentence using Command Line Argument.c new file mode 100644 index 0000000..8b08ba2 --- /dev/null +++ b/c/String/C Program to Count the Total Number of Words in the Sentence using Command Line Argument.c @@ -0,0 +1,25 @@ +/* + * C Program to Count Number of Words in a given Text Or Sentence + */ +#include +#include + +void main() +{ + char s[200]; + int count = 0, i; + printf("enter the string\n"); + scanf("%[^\n]s", s); + for (i = 0; s[i] != '\0'; i++) + { + if (s[i] == ' ') + count++; + } + printf("number of words in given string are: %d\n", count + 1); +} +/* +*OUTPUT: +enter the string +welcome to sanfoundry's c-programming class! +number of words in given string are: 5 +*/ \ No newline at end of file diff --git a/c/String/C Program to Delete All Repeated Words in String.c b/c/String/C Program to Delete All Repeated Words in String.c new file mode 100644 index 0000000..de1eca7 --- /dev/null +++ b/c/String/C Program to Delete All Repeated Words in String.c @@ -0,0 +1,58 @@ +/* + * C Program to Delete All Repeated Words in String + */ +#include +#include + +void main() +{ + char a[100], b[20][20]; + int i, j = 0, k = 0, n, m; + printf("enter the string\n"); + scanf("%[^\n]s", a); + for (i = 0; a[i] != '\0'; i++) + { + if (a[i] == ' ') + { + b[k][j] = '\0'; + k++; + j = 0; + } + else + { + b[k][j] = a[i]; + j++; + } + } + b[k][j] = '\0'; + for (i = 0; i <= k; i++) + { + for (j = i + 1; j <= k; j++) + { + if (strcmp(b[i], b[j]) == 0) + { + for (m = j; m <= k; m++) + strcpy(b[m], b[m + 1]); + k--; + } + } + } + for (n = 0; n <= k; n++) + { + printf("%s\n", b[n]); + } +} +/* +*OUTPUT: +enter the string +welcome to sanfoundry's c programming class , welcome again to c class ! +welcome +to +sanfoundry's +c +programming +class +, +again +! +*/ \ No newline at end of file diff --git a/c/String/C Program to Determine if One String is a Circular Permutation of Another String.c b/c/String/C Program to Determine if One String is a Circular Permutation of Another String.c new file mode 100644 index 0000000..dba5435 --- /dev/null +++ b/c/String/C Program to Determine if One String is a Circular Permutation of Another String.c @@ -0,0 +1,68 @@ +/* +* C Program to Determine if One String is a Circular Permutation of +* Another String +*/ +#include +#include + +#include + +#include +#define CHAR_SIZE 26 + +void alphacheck(char *, int []); +void create(char [], char [], int[]); + +int main() + +{ + char str1[50], str2[50]; + int a1[CHAR_SIZE] = {0}; + char str2_rem[50]; + printf("Enter string1: "); + scanf("%s", str1); + printf("Enter string2: "); + scanf("%s", str2); + alphacheck(str1, a1); + create(str2_rem, str2, a1); + printf("On removing characters from second string we get: %s + ", str2_rem); + return 0; +} + +void alphacheck(char *str, int a[]) +{ + int i, index; + for (i = 0; i < strlen(str); i++) + { + str[i] = tolower(str[i]); + index = str[i] - 'a'; + if (!a[index]) + { + a[index] = 1; + } + } + printf(" + "); +} + +void create(char str_rem[], char str[], int list[]) +{ + int i, j = 0, index; + for (i = 0; i < strlen(str); i++) + { + index = str[i] - 'a'; + if (!list[index]) + { + str_rem[j++] = str[i]; + } + } + str_rem[j] = ''; +} + + +Enter string 1: +abcd +Enter string 2: +dabc +abcd & dabc are circular permutation of each other. diff --git a/c/String/C Program to Display Every Possible Combination of Two Words from the given 2 String without Displaying Repeated Combinations.c b/c/String/C Program to Display Every Possible Combination of Two Words from the given 2 String without Displaying Repeated Combinations.c new file mode 100644 index 0000000..f8be816 --- /dev/null +++ b/c/String/C Program to Display Every Possible Combination of Two Words from the given 2 String without Displaying Repeated Combinations.c @@ -0,0 +1,95 @@ +/* + * C Program to Display Every Possible Combination of Two Words + * from the given 2 String without Displaying Repeated Combinations + */ +#include +#include + +void main() +{ + char str1[50], str2[50], str3[100][100], str4[100][100]; + char str5[200][200], temp[200], str[200][200]; + int i, j = 0, k = 0, l = 0, m = 0, index = 0, n = 0; + printf("Enter first string + "); + scanf("%[^ + ]s", str1); + printf("Enter second string + "); + scanf(" %[^ + ]s", str2); + /* code to convert string in 2-D array */ + for (i = 0; str1[i] != ''; i++) + { + if ((str1[i] = = ' ') + { + str3[j][k] = ''; + j++; + k = 0; + } + else + { + str3[j][k] = str1[i]; + k++; + } + str3[j][k] = ''; + } + k = 0; + for (i = 0; str2[i] != ''; i++) + { + if ((str2[i] == ' ') + { + str4[l][k] = ''; + l++; + k = 0; + } + else + { + str4[l][k] = str2[i]; + k++; + } + str4[l][k] = ''; + } + /* Code to make the first string words combination with second */ + for (i = 0; i <= j; i++) + { + for (m = 0; m <= l; m++) + { + strcpy(temp, str3[i]); + strcat(temp, str4[m]); + strcpy(str5[index], temp); + index++; + } + } + /* Code to make the second string words combination with first */ + for (i = 0; i <= l; i++) + { + for (m = 0; m <= j; m++) + { + strcpy(temp, str4[m]); + strcat(temp, str3[i]); + strcpy(str5[index], temp); + index++; + } + } + /* Code to remove the repetitions */ + for (i = 0; i <= index; i++) + { + for (j = i + 1; j <= index; j++) + { + if ((strcmp(str5[i], str5[j]) == 0) + { + for (k = j; k <= index; k++) + { + strcpy(str5[k], str5[k + 1]); + } + index--; + } + } + } + for (i = 0; i <= index; i++) + { + printf("%s + ", str5[i]); + } +} diff --git a/c/String/C Program to Display every possible Combination of two Words or Strings from the input Strings without Repeated Combinations.c b/c/String/C Program to Display every possible Combination of two Words or Strings from the input Strings without Repeated Combinations.c new file mode 100644 index 0000000..5ce07cb --- /dev/null +++ b/c/String/C Program to Display every possible Combination of two Words or Strings from the input Strings without Repeated Combinations.c @@ -0,0 +1,94 @@ +/* + * C Program to Display every possible Combination of two Words + * or Strings from the input Strings without Repeated Combinations +*/ +#include +#include + +void main() +{ + int i, j = 0, k, k1 = 0, k2 = 0, row = 0; + char temp[50]; + char str[100], str2[100], str1[5][20], str3[6][20], str4[60][40]; + printf("enter the string :"); + scanf(" %[^ + ]s", &str); + printf("enter string:"); + scanf(" %[^ + ]s", &str2); + /* read strings into 2d character arrays */ + for (i = 0; str[i] != ''; i++) + { + if (str[i] == ' ') + { + str1[k1][j] = ''; + k1++; + j = 0; + } + else + { + str1[k1][j] = str[i]; + j++; + } + } + str1[k1][j] = ''; + j = 0; + for (i = 0; str2[i] != ''; i++) + { + if (str2[i] == ' ') + { + str3[k2][j] = ''; + k2++; + j = 0; + } + else + { + str3[k2][j] = str2[i]; + j++; + } + } + str3[k2][j] = ''; + /* concatenates string1 words with string2 and stores in 2d array */ + row = 0; + for (i = 0; i <= k1; i++) + { + for (j = 0; j <= k2; j++) + { + strcpy(temp, str1[i]); + strcat(temp, str3[j]); + strcpy(str4[row], temp); + row++; + } + } + for (i = 0; i <= k2; i++) + { + for (j = 0; j <= k1; j++) + { + strcpy(temp, str3[i]); + strcat(temp, str1[j]); + strcpy(str4[row], temp); + row++; + } + } + /* eliminates repeated combinations */ + for (i = 0; i < row; i++) + { + for (j = i + 1; j < row; j++) + { + if (strcmp(str4[i], str4[j]) == 0) + { + for (k = j; k <= row; k++) + { + strcpy(str4[k], str4[k + 1]); + } + row--; + } + } + } + /* displays the output */ + for (i = 0; i < row; i++) + { + printf(" + %s", str4[i]); + } +} diff --git a/c/String/C Program to Display the Characters in Prime Position a given String.c b/c/String/C Program to Display the Characters in Prime Position a given String.c new file mode 100644 index 0000000..cf692d5 --- /dev/null +++ b/c/String/C Program to Display the Characters in Prime Position a given String.c @@ -0,0 +1,48 @@ +/* +* C Program to Display the Characters in Prime Position a given String +*/ +#include +#include + +void main() +{ + int i, j, k, count = 0; + char str[50]; + printf("enter string + "); + scanf("%[^ + ]s", str); + k = strlen(str); + printf("prime characters in a string are + "); + for (i = 2; i <= k; i++) + { + count = 0; + for (j = 2; j <= k; j++) + { + if (i % j == 0) + { + count++; + } + } + if (count == 1) + { + printf("%c + ", str[i - 1]); + } + } +} + +enter string +get ready to get illuminted! +prime characters in a string are +e + +t +r +a +t + +u +i +d diff --git a/c/String/C Program to Find All Possible Subsets of given Length in String.c b/c/String/C Program to Find All Possible Subsets of given Length in String.c new file mode 100644 index 0000000..985965c --- /dev/null +++ b/c/String/C Program to Find All Possible Subsets of given Length in String.c @@ -0,0 +1,77 @@ +/* +* C Program to Find All Possible Subsets of given Length in String +*/ +#include +#include + +char a[20]; +int n, len, j; + +void main() +{ + int i, index = 0, start = 0; + printf("Enter the string + "); + scanf("%s", a); + n = strlen(a); + printf("enter input length + "); + scanf("%d", &len); + printf("The subsets are + "); + for (i = 1; i < = n; i++) + { + if (index - start + 1 == i) + { + if (i == len) + { + for (j = index; j < n; j++) + { + for (i = start; i < index; i++) + printf("%c", a[i]); + printf("%c + ", a[j]); + } + if (start != i) + { + start++; + index = start; + } + } + else + { + index++; + } + } + } +} + +/* +Enter the string +programming +enter input length +2 +The subsets are +pr +po +pg +pr +pa +pm +pm +pi +pn +pg +enter the string +programming +enter input length +4 +The subsets are +prog +pror +proa +prom +prom +proi +pron +prog diff --git a/c/String/C Program to Find Highest Frequency Character in a String.c b/c/String/C Program to Find Highest Frequency Character in a String.c new file mode 100644 index 0000000..dc275f0 --- /dev/null +++ b/c/String/C Program to Find Highest Frequency Character in a String.c @@ -0,0 +1,63 @@ +/* + * C Program To Find the Highest Frequency Character in a String + */ +#include +#include + +char string1[100], visited[100]; +int count[100] = {0}, flag = 0; + +void main() +{ + int i, j = 0, k = 0, l, max, index; + printf("Enter a string : "); + scanf("%[^\n]s", string1); + l = strlen(string1); + for (i = 0; i < l; i++) + { + if (i == 0) + { + visited[j++] = string1[i]; + count[j - 1]++; + } + else + { + for (k = 0; k < j; k++) + { + if (string1[i] == visited[k]) + { + count[k]++; + flag = 1; + } + } + if (flag == 0) + { + visited[j++] = string1[i]; + count[j - 1]++; + } + flag = 0; + } + } + for (i = 0; i < j; i++) + { + if ((i == 0) && (visited[i] != ' ')) + { + max = count[i]; + continue; + } + if ((max < count[i]) && (visited[i] != ' ')) + { + max = count[i]; + index = i; + } + } + printf("\nMax repeated character in the string = %c ", visited[index]); + printf("\nIt occurs %d times", count[index]); +} +/* +*OUTPUT: +Enter a string : Welcome to Sanfoundry's C Programming Class ! + +Max repeated character in the string = o +It occurs 4 times +*/ \ No newline at end of file diff --git a/c/String/C Program to Find the Consecutive Occurrence of any Vowel in a String.c b/c/String/C Program to Find the Consecutive Occurrence of any Vowel in a String.c new file mode 100644 index 0000000..43e270f --- /dev/null +++ b/c/String/C Program to Find the Consecutive Occurrence of any Vowel in a String.c @@ -0,0 +1,105 @@ +/* +* C Program to Find the Consecutive Occurrence of any Vowel +* in a String +*/ +#include +#include +#include + +struct detail +{ + char word[20]; +}; + +int update(struct detail [], const char [], int); +int vowelcheck(char); + +int main() +{ + struct detail s[10]; + char string[100], unit[20], c; + int i = 0, j = 0, count = 0; + printf("Enter string: "); + i = 0; + do + { + fflush(stdin); + c = getchar(); + string[i++] = c; + } + while (c != ' + '); + string[i - 1] = ''; + printf("The string entered is: %s + ", string); + for (i = 0; i < strlen(string); i++) + { + while (i < strlen(string) && string[i] != ' ' && isalnum(string[i])) + { + unit[j++] = string[i++]; + } + if (j != 0) + { + unit[j] = ''; + count = update(s, unit, count); + j = 0; + } + } + printf("**Words with consecutive vowel** + "); + for (i = 0; i < count; i++) + { + printf("%s + ", s[i].word); + } +return 0; +} + +int update(struct detail s[], const char unit[], int count) +{ + int i, j = 0; + for (i = 0; i < strlen(unit) - 1; i++) + { + if (vowelcheck(unit[i])) + { + if (vowelcheck(unit[i+ 1])) + { + /*To avoid duplicate strings*/ + while (j < count && strcmp(s[j].word, unit)) + { + j++; + } + if (j == count) + { + strcpy(s[j].word, unit); + return (count + 1); + } + } + } + } + return count; +} + +int vowelcheck(char c) +{ + char vowel[5] = {'a', 'e', 'i', 'o', 'u'}; + int i; + c = tolower(c); + for (i = 0; i < 5; i++) + { + if (c == vowel[i]) + { + return 1; + } + } + return 0; +} + + +Enter string: +Who will lead his team to victory +The string entered is: +Who will lead his team to victory +**Words with consecutive vowel** +lead +team \ No newline at end of file diff --git a/c/String/C Program to Find the Frequency of Every Word in a given String.c b/c/String/C Program to Find the Frequency of Every Word in a given String.c new file mode 100644 index 0000000..df7cb2e --- /dev/null +++ b/c/String/C Program to Find the Frequency of Every Word in a given String.c @@ -0,0 +1,76 @@ +/* + * C Program to Find the Frequency of Every Word in a + * given String + */ +#include +#include + +void main() +{ + int count = 0, c = 0, i, j = 0, k, space = 0; + char str[100], p[50][100], str1[20], ptr1[50][100]; + char *ptr; + printf("Enter the string\n"); + scanf(" %[^\n]s", str); + printf("string length is %d\n", strlen(str)); + for (i = 0; i %d times\n", ptr1[i], c); + c = 0; + } +} +/* +*OUTPUT: +Enter the string +welcome to sanfoundry's class, welcome to c class +string length is 48 +welcome -> 2 times +to -> 2 times +sanfoundry's -> 1 times +class -> 2 times +c -> 1 times +*/ \ No newline at end of file diff --git a/c/String/C Program to Find the Frequency of Substring in the given String.c b/c/String/C Program to Find the Frequency of Substring in the given String.c new file mode 100644 index 0000000..c82e96f --- /dev/null +++ b/c/String/C Program to Find the Frequency of Substring in the given String.c @@ -0,0 +1,52 @@ +/* + * C Program to Find the Frequency of Substring in + * the given String + */ +#include +#include + +void main() +{ + int count = 0, i, j = 0, k; + char str[100], str1[20]; + printf("Enter the string\n"); + scanf(" %[^\n]s", str); + printf("Enter the substring to be matched\n"); + scanf(" %[^\n]s", str1); + k = strlen(str1); + for (i = 0; str[i] != '\0';) + { + if (str[i] == ' ') + { + i++; + } + else + { + if (str[i] == str1[j]) + { + j++; + i++; + } + else if (j == k) + { + j = 0; + count++; + i--; + } + else + { + i++; + j = 0; + } + } + } + printf("No of matches of substring in main string is %d\n", count); +} +/* +*OUTPUT: +Enter the string +prrrogram is prrrogramming +Enter the substring to be matched +rr +No of matches of substring in main string is 4 +*/ \ No newline at end of file diff --git a/c/String/C Program to Find the Frequency of the Word ‘the’ in a given Sentence.c b/c/String/C Program to Find the Frequency of the Word ‘the’ in a given Sentence.c new file mode 100644 index 0000000..02f0e7a --- /dev/null +++ b/c/String/C Program to Find the Frequency of the Word ‘the’ in a given Sentence.c @@ -0,0 +1,36 @@ +/* + * C program to accept a string and find the number of times the word + * 'the' appears in that string + */ +#include + +void main() +{ + int count = 0, i, times = 0, t, h, e, space; + char string[100]; + puts("Enter a string:"); + gets(string); + /* Traverse the string to count the number of characters */ + while (string[count] != '\0') + { + count++; + } + /* Finding the frequency of the word 'the' */ + for (i = 0; i <= count - 3; i++) + { + t =(string[i] == 't' || string[i] == 'T'); + h =(string[i + 1] == 'h' || string[i + 1] == 'H'); + e =(string[i + 2] == 'e'|| string[i + 2] == 'E'); + space =(string[i + 3] == ' ' || string[i + 3] == '\0'); + if ((t && h && e && space) == 1) + times++; + } + printf("Frequency of the word 'the' is %d\n", times); +} +/* +*OUTPUT: +Enter a string: +The gandhi jayanthi is celeberated on october 2 is the day +that he has born. +Frequency of the word 'the' is 2 +*/ \ No newline at end of file diff --git a/c/String/C Program to Find the Largest & Smallest Word in a String.c b/c/String/C Program to Find the Largest & Smallest Word in a String.c new file mode 100644 index 0000000..5363e96 --- /dev/null +++ b/c/String/C Program to Find the Largest & Smallest Word in a String.c @@ -0,0 +1,58 @@ +/* + * C Program to Find the Largest & Smallest Word in a String + */ +#include +#include +#include + +int main() +{ + char string[100], word[20], max[20], min[20], c; + int i = 0, j = 0, flag = 0; + printf("Enter string: "); + i = 0; + do + { + fflush(stdin); + c = getchar(); + string[i++] = c; + } + while (c != ' + '); + string[i - 1] = ''; + for (i = 0; i < strlen(string); i++) + { + while (i < strlen(string) && !isspace(string[i]) && isalnum(string[i])) + { + word[j++] = string[i++]; + } + if (j != 0) + { + word[j] = ''; + if (!flag) + { + flag = !flag; + strcpy(max, word); + strcpy(min, word); + } + if (strlen(word) > strlen(max)) + { + strcpy(max, word); + } + if (strlen(word) < strlen(min)) + { + strcpy(min, word); + } + j = 0; + } + } + printf("The largest word is '%s' and smallest word is '%s' in '%s'. + ", max, min, string); + return 0; +} + + + +Enter string: +amazing programmers exists here +The largest word is 'programmers' and smallest word is 'here' in 'amazing programmers exists here'. diff --git a/c/String/C Program to Find the Largest _ Smallest Word in a String.c b/c/String/C Program to Find the Largest _ Smallest Word in a String.c new file mode 100644 index 0000000..96ea393 --- /dev/null +++ b/c/String/C Program to Find the Largest _ Smallest Word in a String.c @@ -0,0 +1,55 @@ +/* + * C Program to Find the Largest & Smallest Word in a String + */ +#include +#include +#include + +int main() +{ + char string[100], word[20], max[20], min[20], c; + int i = 0, j = 0, flag = 0; + printf("Enter string: "); + i = 0; + do + { + fflush(stdin); + c = getchar(); + string[i++] = c; + } + while (c != '\n'); + string[i - 1] = '\0'; + for (i = 0; i < strlen(string); i++) + { + while (i < strlen(string) && !isspace(string[i]) && isalnum(string[i])) + { + word[j++] = string[i++]; + } + if (j != 0) + { + word[j] = '\0'; + if (!flag) + { + flag = !flag; + strcpy(max, word); + strcpy(min, word); + } + if (strlen(word) > strlen(max)) + { + strcpy(max, word); + } + if (strlen(word) < strlen(min)) + { + strcpy(min, word); + } + j = 0; + } + } + printf("The largest word is '%s' and smallest word is '%s' in '%s'.\n", max, min, string); + return 0; +} +/* +*OUTPUT: +Enter string: amazing programmers exists here +The largest word is 'programmers' and smallest word is 'here' in 'amazing programmers exists here' +*/ \ No newline at end of file diff --git a/c/String/C Program to Find the Length of a String without using the Built-in Function.c b/c/String/C Program to Find the Length of a String without using the Built-in Function.c new file mode 100644 index 0000000..b141da8 --- /dev/null +++ b/c/String/C Program to Find the Length of a String without using the Built-in Function.c @@ -0,0 +1,27 @@ +/* + * C program to find the length of a string without using the + * built-in function + */ +#include + +void main() +{ + char string[50]; + int i, length = 0; + printf("Enter a string \n"); + gets(string); + /* keep going through each character of the string till its end */ + for (i = 0; string[i] != '\0'; i++) + { + length++; + } + printf("The length of a string is the number of characters in it \n"); + printf("So, the length of %s = %d\n", string, length); +} +/* +*OUTPUT: +Enter a string +Sanfoundry +The length of a string is the number of characters in it +So, the length of Sanfoundry = 10 +*/ \ No newline at end of file diff --git a/c/String/C Program to Find the Length of the Longest Repeating Sequence in a String.c b/c/String/C Program to Find the Length of the Longest Repeating Sequence in a String.c new file mode 100644 index 0000000..fd6333b --- /dev/null +++ b/c/String/C Program to Find the Length of the Longest Repeating Sequence in a String.c @@ -0,0 +1,92 @@ +/* + * C Program to Find the Length of the Longest Repeating Sequence in a String + */ +#include +#include + +char string[100], words[100][100]; +int len = 0, word_cnt = 0; + +int main() +{ + int i, j = 0, k, mlen = 0, rlen = 0, s = 0, c = 0; + printf("\nEnter the string"); + scanf(" %[^\n]s", string); + for (len = 0; string[len] != '\0'; len++); + /* + * Storing the individual words in an array + */ + for (k = 0; k < len; k++) + { + if (string[k] != ' ') + { + words[s][j] = string[k]; + j++; + } + if (string[k] == ' ') + { + words[s][j] = '\0'; + j = 0; + s++; + word_cnt++; + } + } + word_cnt++; + /* + * Compare on Word basis if same word is repeated then check next word and so on + * Increment a counter when consecutive words are repeated + */ + for (i = 0; i <= word_cnt; i++) + { + len = 0; + for (j = i+1; j <= word_cnt-1; j++) + { + if (strcmp(words[i], words[j]) != 0) + { + continue; + } + else if (strcmp(words[i], words[j]) == 0) + { + len++; + for (k = i+1, m = j+1; k < j; k++, m++) + { + if (strcmp(words[k], words[m]) == 0) + { + len++; + continue; + } + else + { + break; + } + } + if (rlen < len) + { + rlen = len; + len = 0; + } + len = 0; + } + /* + * Finding length of Longest Repeated Sequence + */ + if (mlen < rlen) + { + s = i; + mlen = rlen; + } + } + } + printf("\nLength of Longest Repeating Sequence:%d\n", mlen); + for (i = s, j = 0; j < mlen; i++, j++) + printf(" %s", words[i]); + printf("\n"); +} +/* +*OUTPUT: +Enter the string +Welcome to C Programming Class, Welcome Again to C Programming Class ! + +Length of Longest Repeating Sequence:4 +to C Programming Class +*/ \ No newline at end of file diff --git a/c/String/C Program to Find the MostLeast Repeated Character in the String.c b/c/String/C Program to Find the MostLeast Repeated Character in the String.c new file mode 100644 index 0000000..930a399 --- /dev/null +++ b/c/String/C Program to Find the MostLeast Repeated Character in the String.c @@ -0,0 +1,114 @@ +/* +*C Program to Find the Most/Least Repeated Character in the String +*/ +#include +#include +#include + +struct detail +{ + char c; + int freq; +}; + +int main() +{ + struct detail s[26]; + char string[100], c; + int max[26] = {0}, min[26] = {0}; + int i = 0, index, maxcount = 1, mincount = 1000, j; + for (i = 0; i < 26; i++) + { + s[i].c = i + 'a'; + s[i].freq = 0; + } + printf("Enter string: "); + i = 0; + do + { + fflush(stdin); + c = getchar(); + string[i++] = c; + if (c == ' + ') + { + break; + } + else if (!isalpha(c)) + { + continue; + } + c = tolower(c); + index = c - 'a'; + s[index].freq++; + } +while (1); + string[i - 1] = ''; + printf("The string entered is: %s + ", string); + for (i = 0; i < 26; i++) + { + if (s[i].freq) + { + if (maxcount < s[i].freq) + { + for (j = 0; j < 26; j++) + { + max[j] = 0; + } + max[i] = 1; + maxcount = s[i].freq; + } + else if (maxcount == s[i].freq) + { + max[i] = 1; + } + if (mincount >= s[i].freq) + { + if (mincount == s[i].freq) + { + min[i] = 1; + } + else + { + for (j = 0; j < 26; j++) + { + min[j] = 0; + } + min[i] = 1; + mincount = s[i].freq; + } + } + } + } + printf("The most repeated characters are: "); + for (i = 0; i < 26; i++) + { + if (max[i]) + { + printf("%c ", i + 'a'); + } + } + printf(" + The least repeated characters are: "); + for (i = 0; i < 26; i++) + { + if (min[i]) + { + printf("%c ", i + 'a'); + } + } + printf(" + "); + return 0; +} + + +Enter string: +I love C programming +The string entered is: +I love C programming +The most repeated characters are: +g i m o r +The least repeated characters are: +a c e l n p v diff --git a/c/String/C Program to Insert CharacterWord in any Desired Location in a String.c b/c/String/C Program to Insert CharacterWord in any Desired Location in a String.c new file mode 100644 index 0000000..84089d9 --- /dev/null +++ b/c/String/C Program to Insert CharacterWord in any Desired Location in a String.c @@ -0,0 +1,60 @@ +/* +* C Program to Insert Character/Word in any Desired Location +* in a String +*/ +#include +#include + +void main() +{ + int i, j, count = 0, pos, flag = 0; + char s1[100], s2[10], s3[100]; + char *ptr1, *ptr2, *ptr3; + printf(" + enter the String:"); + scanf(" %[^ + ]s", s1); + printf(" + enter the string to be inserted:"); + scanf(" %[^ + ]s", s2); + printf(" + enter the position you like to insert:"); + scanf("%d", &pos); + ptr1 = s1; + ptr3 = s3; + /*COPYING THE GIVEN STRING TO NEW ARRAY AND INSERTING THE STRING IN NEW ARRAY*/ + for (i = 0, j = 0; *ptr1 != ''; ptr1++, i++, j++, ptr3++) + { + s3[j] = s1[i]; + if (*ptr1 == ' ' && flag != 1) + ++count; + if (flag != 1 && count == pos - 1) + { + flag = 1; + for(ptr2 = s2; *ptr2 != ''; ptr2++) + { + s3[++j] = *ptr2; + ptr3++; + } + s3[++j] = ' '; + ptr3++; + } + } + s3[j] = ''; + printf(" + the string after modification is + %s + ", s3); +} + + + + enter the string: + Welcome to illuminates C Programming Class, Welcome Again to C Class! + enter the word to insert: + illumin8s + enter the position you like to insert:3 + the string after modification is + + Welcome to illumin8s illuminates C Programming Class, Welcome Again to C Class! diff --git a/c/String/C Program to List All Lines containing a given String.c b/c/String/C Program to List All Lines containing a given String.c new file mode 100644 index 0000000..e05d964 --- /dev/null +++ b/c/String/C Program to List All Lines containing a given String.c @@ -0,0 +1,72 @@ +/* +* C Program to List All Lines containing a given String +*/ +#include +#include +#include + +int search(FILE *, char *); + +void main(int argc, char * argv[]) +{ + FILE *fp1; + int p; + fp1 = fopen(argv[1], "r+"); + if (fp1 == NULL) + { + printf("cannot open the file "); + exit(0); + } + search(fp1, argv[2]); + fclose(fp1); +} + +/* Searches the lines */ +int search(FILE *fp, char * str) +{ + FILE *fp1; + fp1 = fopen("fp1","w"); + char s[10],c; + int len = strlen(str); + int i = 0; + int d; + int seek = fseek(fp, 0, 0); + c = fgetc(fp); + while (c != EOF) + { + if (c == ' ' || c == '') + { + s[i] = ''; + i = 0; + if (strcmp(s, str) == 0) + { + while (c = fgetc(fp) != '') + { + fseek(fp, -2L, 1); + d = ftell(fp); + } + while ((c = fgetc(fp)) != '') + { + fputc(c, fp1); + } + } + } + else + { + s[i] = c; + i++; + } + c = fgetc(fp); + } + return 1; +} + + +/* +hi hello everyone +again hi to the late comers +welcome to the class + + example hi +hi hello everyone +again hi to the late comers \ No newline at end of file diff --git a/c/String/C Program to Read a String and find the Sum of all Digits in the String.c b/c/String/C Program to Read a String and find the Sum of all Digits in the String.c new file mode 100644 index 0000000..f8b3c59 --- /dev/null +++ b/c/String/C Program to Read a String and find the Sum of all Digits in the String.c @@ -0,0 +1,28 @@ +/* + * C program to find the sum of all digits present in the string + */ +#include +void main() +{ + char string[80]; + int count, nc = 0, sum = 0; + printf("Enter the string containing both digits and alphabet \n"); + scanf("%s", string); + for (count = 0; string[count] != '\0'; count++) + { + if ((string[count] >= '0') && (string[count] <= '9')) + { + nc += 1; + sum += (string[count] - '0'); + } + } + printf("NO. of Digits in the string = %d\n", nc); + printf("Sum of all digits = %d\n", sum); +} +/* +*OUTPUT: +Enter the string containing both digits and alphabet +hello100 +NO. of Digits in the string = 3 +Sum of all digits = 1 +*/ \ No newline at end of file diff --git a/c/String/C Program to Remove all Characters in Second String which are present in First String.c b/c/String/C Program to Remove all Characters in Second String which are present in First String.c new file mode 100644 index 0000000..5d9217e --- /dev/null +++ b/c/String/C Program to Remove all Characters in Second String which are present in First String.c @@ -0,0 +1,63 @@ +/* + * C Program to Remove all Characters in Second String which are + * present in First String + */ +#include +#include +#include +#include +#define CHAR_SIZE 26 + +void alphacheck(char *, int []); +void create(char [], char [], int[]); + +int main() +{ + char str1[50], str2[50]; + int a1[CHAR_SIZE] = {0}; + char str2_rem[50]; + printf("Enter string1: "); + scanf("%s", str1); + printf("Enter string2: "); + scanf("%s", str2); + alphacheck(str1, a1); + create(str2_rem, str2, a1); + printf("On removing characters from second string we get: %s\n", str2_rem); + return 0; +} + +void alphacheck(char *str, int a[]) +{ + int i, index; + for (i = 0; i < strlen(str); i++) + { + str[i] = tolower(str[i]); + index = str[i] - 'a'; + if (!a[index]) + { + a[index] = 1; + } + } + printf("\n"); +} + +void create(char str_rem[], char str[], int list[]) +{ + int i, j = 0, index; + for (i = 0; i < strlen(str); i++) + { + index = str[i] - 'a'; + if (!list[index]) + { + str_rem[j++] = str[i]; + } + } + str_rem[j] = '\0'; +} +/* +* +Enter string1: programming +Enter string2: computer + +On removing characters from second string we get: cute +*/ \ No newline at end of file diff --git a/c/String/C Program to Remove given Word from a String.c b/c/String/C Program to Remove given Word from a String.c new file mode 100644 index 0000000..093afc0 --- /dev/null +++ b/c/String/C Program to Remove given Word from a String.c @@ -0,0 +1,54 @@ +/* + * C Program to Remove given Word from a String + */ +#include +#include + +void main() +{ + int i, j = 0, k = 0, count = 0; + char str[100], key[20]; + char str1[10][20]; + printf("enter string:"); + scanf("%[^\n]s",str); + /* Converts the string into 2D array */ + for (i = 0; str[i]!= '\0'; i++) + { + if (str[i]==' ') + { + str1[k][j] = '\0'; + k++; + j = 0; + } + else + { + str1[k][j] = str[i]; + j++; + } + } + str1[k][j] = '\0'; + printf("enter key:"); + scanf("%s", key); + /* Compares the string with given word */ + for (i = 0; i < k + 1; i++) + { + if (strcmp(str1[i], key) == 0) + { + for (j = i; j < k + 1; j++) + strcpy(str1[j], str1[j + 1]); + k--; + } + } + for (i = 0; i < k + 1; i++) + { + printf("%s ", str1[i]); + } +} +} +/* +*OUTPUT: +enter string:Welcome to Sanfoundry's C Programming Class, Welcome Again to C class + +enter key:Welcome +to Sanfoundry's C Programming Class, Again to C class +*/ \ No newline at end of file diff --git a/c/String/C Program to Replace Lowercase Characters by Uppercase _ Vice-Versa.c b/c/String/C Program to Replace Lowercase Characters by Uppercase _ Vice-Versa.c new file mode 100644 index 0000000..8d5da33 --- /dev/null +++ b/c/String/C Program to Replace Lowercase Characters by Uppercase _ Vice-Versa.c @@ -0,0 +1,37 @@ +/* + * C program to read an English sentence and replace + * lowercase characters by uppercase and vice-versa. + * Output the given sentence as well as the converted + * sentence on two different lines. + */ +#include +#include + +void main() +{ + char sentence[100]; + int count, ch, i; + printf("Enter a sentence \n"); + for (i = 0; (sentence[i] = getchar()) != '\n'; i++) + { + ; + } + sentence[i] = '\0'; + /* shows the number of chars accepted in a sentence */ + count = i; + printf("The given sentence is : %s", sentence); + printf("\n Case changed sentence is: "); + for (i = 0; i < count; i++) + { + ch = islower(sentence[i])? toupper(sentence[i]) : + tolower(sentence[i]); + putchar(ch); + } +} +/* +*OUTPUT: +Enter a sentence +wELCOME tO sANFOUNDRY +The given sentence is : wELCOME tO sANFOUNDRY +Case changed sentence is: Welcome To Sanfoundry +*/ \ No newline at end of file diff --git a/c/String/C Program to Replace all the Characters by Lowercase.c b/c/String/C Program to Replace all the Characters by Lowercase.c new file mode 100644 index 0000000..5374e7f --- /dev/null +++ b/c/String/C Program to Replace all the Characters by Lowercase.c @@ -0,0 +1,37 @@ +/* + * C Program to Replace all the Characters by Lowercase + */ +#include +#include + +void main(int argc, char* argv[]) +{ + FILE *fp1; + int ch; + if ((fp1 = fopen(argv[1], "r+")) == NULL) + { + printf("\nfile cant be opened"); + exit(0); + } + ch = fgetc(fp1); + while (ch != EOF) + { + if (ch >= 65 && ch <= 90) + { + fseek(fp1, -1L, 1); + fputc(ch + 32, fp1); + } + ch = fgetc(fp1); + } +} +/* +*OUTPUT: +$ cat file4test +CHANDANA chanikya +rAVELLA +$ cc file4.c +$ a.out file4test +$ cat file4test +chandana chanikya +ravella +*/ \ No newline at end of file diff --git a/c/String/C Program to Reverse every Word of given String.c b/c/String/C Program to Reverse every Word of given String.c new file mode 100644 index 0000000..e5e017f --- /dev/null +++ b/c/String/C Program to Reverse every Word of given String.c @@ -0,0 +1,49 @@ +/* + * C Program to Reverse every Word of given String + */ +#include +#include + +void main() +{ + int i, j = 0, k = 0, x, len; + char str[100], str1[10][20], temp; + printf("enter the string :"); + scanf("%[^\n]s", str); + /* reads into 2d character array */ + for (i = 0; str[i] != '\0'; i++) + { + if (str[i] == ' ') + { + str1[k][j]='\0'; + k++; + j=0; + } + else + { + str1[k][j]=str[i]; + j++; + } + } + str1[k][j] = '\0'; + /* reverses each word of a given string */ + for (i = 0; i <= k; i++) + { + len = strlen(str1[i]); + for (j = 0, x = len - 1; j < x; j++,x--) + { + temp = str1[i][j]; + str1[i][j] = str1[i][x]; + str1[i][x] = temp; + } + } + for (i = 0; i <= k; i++) + { + printf("%s ", str1[i]); + } +} +/* +*OUTPUT: +enter the string :C Programming Class +C gnimmargorP ssalC +*/ \ No newline at end of file diff --git a/c/String/C Program to Reverse the String using Both Recursion and Iteration.c b/c/String/C Program to Reverse the String using Both Recursion and Iteration.c new file mode 100644 index 0000000..3d61ff2 --- /dev/null +++ b/c/String/C Program to Reverse the String using Both Recursion and Iteration.c @@ -0,0 +1,52 @@ +/* + * C Program to Reverse the String using Both Recursion and Iteration + */ +#include +#include + +/* Function Prototype */ +void disp_str1_rec(char *); + +void main() +{ + char str1[100], *ptr; + int len1 = 0, i; + char ch; + printf("Enter the string:\n"); + scanf("%[^\n]s", str1); + ptr = str1; + len1 = strlen(str1); + printf("Using iteration:\n"); + for (i = len1 - 1; i >= 0; i--) /* Iterative loop */ + { + ch = str1[i]; + printf("%c", ch); + } + printf("Using recurssion:\n"); + disp_str1_rec(ptr); +} + +/* Code to reverse the string using Recursion */ +void disp_str1_rec(char *stng) +{ + char ch; + if (*stng != '\0') + { + ch = *stng; + stng++; + disp_str1_rec(stng); + printf("%c", ch); + } + else + return; +} +/* +*OUTPUT: +Enter the string: +welcome to sanfoundry's c programming class + +Using iteration: +ssalc gnimmargorp c s'yrdnuofnas ot emoclew +Using recurssion: +ssalc gnimmargorp c s'yrdnuofnas ot emoclewi +*/ \ No newline at end of file diff --git a/c/String/C Program to Reverse the String using Recursion.c b/c/String/C Program to Reverse the String using Recursion.c new file mode 100644 index 0000000..66542b5 --- /dev/null +++ b/c/String/C Program to Reverse the String using Recursion.c @@ -0,0 +1,39 @@ +/* + * C Program to Reverse the String using Recursion + */ +#include +#include + +void reverse(char [], int, int); +int main() +{ + char str1[20]; + int size; + printf("Enter a string to reverse: "); + scanf("%s", str1); + size = strlen(str1); + reverse(str1, 0, size - 1); + printf("The string after reversing is: %s\n", str1); + return 0; +} + +void reverse(char str1[], int index, int size) +{ + char temp; + temp = str1[index]; + str1[index] = str1[size - index]; + str1[size - index] = temp; + if (index == size / 2) + { + return; + } + reverse(str1, index + 1, size); +} +/* +*OUTPUT: +Enter a string to reverse: malayalam +The string after reversing is: malayalam + +Enter a string to reverse: cprogramming +The string after reversing is: gnimmargorpc +*/ \ No newline at end of file diff --git a/c/String/C Program to Sort Word in String.c b/c/String/C Program to Sort Word in String.c new file mode 100644 index 0000000..626011d --- /dev/null +++ b/c/String/C Program to Sort Word in String.c @@ -0,0 +1,57 @@ +/* + * C Program to Sort Word in String + */ +#include +#include + +void main() +{ + int count = 0, c = 0, i, j = 0, k, l, space = 0; + char str[100], p[50][100], str1[20], ptr1[50][100], cmp[50]; + printf("Enter the string + "); + scanf(" %[^ + ]s", str); + for (i = 0; i < strlen(str); i++) + { + if ((str[i] == ' ')||(str[i] == ', ')||(str[i] == '.')) + { + space++; + } + } + for (i = 0, j = 0, k = 0; j < strlen(str); j++) + { + if ((str[j] == ' ')||(str[j] == 44)||(str[j] == 46)) + { + p[i][k] = ''; + i++; + k = 0; + } + else + p[i][k++] = str[j]; + } + for (i = 0; i < space; i++) //loop for sorting + { + for (j = i + 1; j <= space; j++) + { + if ((strcmp(p[i], p[j]) > 0)) + { + strcpy(cmp, p[i]); + strcpy(p[i], p[j]); + strcpy(p[j], cmp); + } + } + } + printf("After sorting string is + "); + for (i = 0; i <= space; i++) + { + printf("%s ", p[i]); + } +} + + +Enter the string +welcome to illuminate's c programming app +After sorting string is +app c illuminate's programming to welcome \ No newline at end of file diff --git a/c/String/C Program to Sort the String(ignore spaces) and Repeated Characters should be present only Once.c b/c/String/C Program to Sort the String(ignore spaces) and Repeated Characters should be present only Once.c new file mode 100644 index 0000000..8ab5318 --- /dev/null +++ b/c/String/C Program to Sort the String(ignore spaces) and Repeated Characters should be present only Once.c @@ -0,0 +1,57 @@ +/* +* C Program to Sort the String(ignore spaces) and Repeated +* Characters should be present only Once +*/ +#include +#include + +void main() +{ + int i, j = 0, k = 0; + char str[100], str1[10][20], temp, min; + printf("enter the string:"); + scanf("%[^ + ]s", str); + /* ignores spaces */ + for (i = 0; str[i]!= ''; i++) + { + if (str[i] == ' ') + { + for (j = i; str[j] != ''; j++) + { + str[j] = str[j + 1]; + } + } + } + /* removes repeated characters */ + for (i = 0; str[i]!= ''; i++) + { + for (j = i + 1; str[j] != ''; j++) + { + if (str[i] == str[j]) + { + for (k = j; str[k] != ''; k++) + str[k] = str[k+1]; + j--; + } + } + } + /* sorts the string */ + for (i = 0; str[i] != ''; i++) + { + for (j = 0; str[j] != ''; j++) + { + if (str[j] > str[i]) + { + temp = str[i]; + str[i] = str[j]; + str[j] = temp; + } + } + } + printf("%s", str); +} + +enter the string: +abcde| bcd! abcdefg?? +!?abcdefg| \ No newline at end of file diff --git a/c/String/C Program to accepts two strings and compare them.c b/c/String/C Program to accepts two strings and compare them.c new file mode 100644 index 0000000..23ced7e --- /dev/null +++ b/c/String/C Program to accepts two strings and compare them.c @@ -0,0 +1,66 @@ +/* + * C Program to accepts two strings and compare them. Display + * the result whether both are equal, or first string is greater + * than the second or the first string is less than the second string + */ +#include +void main() +{ + int count1 = 0, count2 = 0, flag = 0, i; + char string1[10], string2[10]; + printf("Enter a string:"); + gets(string1); + printf("Enter another string:"); + gets(string2); + /* Count the number of characters in string1 */ + while (string1[count1] != '') + count1++; + /* Count the number of characters in string2 */ + while (string2[count2] != '') + count2++; + i = 0; + while ((i < count1) && (i < count2)) + { + if (string1[i] == string2[i]) + { + i++; + continue; + } + if (string1[i] < string2[i]) + { + flag = -1; + break; + } + if (string1[i] > string2[i]) + { + flag = 1; + break; + } + } + if (flag == 0) + printf("Both strings are equal + "); + if (flag == 1) + printf("String1 is greater than string2 + ", string1, string2); + if (flag == -1) + printf("String1 is less than string2 + ", string1, string2); + } + + + Enter a string: + hello + Enter another string: + world + String1 is less than string2 + + Enter a string: + object + Enter another string: + class + String1 is greater than string2 + + Enter a string:object + Enter another string:object + Both strings are equal diff --git a/c/String/C Program to find First and Last Occurrence of given Character in a String.c b/c/String/C Program to find First and Last Occurrence of given Character in a String.c new file mode 100644 index 0000000..ba754c2 --- /dev/null +++ b/c/String/C Program to find First and Last Occurrence of given Character in a String.c @@ -0,0 +1,46 @@ +/* +* C Program to find First and Last Occurrence of given + * Character in a String +*/ +#include +#include + +void main() +{ + int i, count = 0, pos1, pos2; + char str[50], key, a[10]; + printf("enter the string + "); + scanf(" %[^ + ]s", str); + printf("enter character to be searched + "); + scanf(" %c", &key); + for (i = 0; i <= strlen(str); i++) + { + if (key == str[i]) + { + count++; + if (count == 1) + { + pos1 = i; + pos2 = i; + printf("%d + ", pos1 + 1); + } + else + { + pos2 = i; + } + } + } + printf("%d + ", pos2 + 1); +} + + +enter the string +Get ready to get Illuminted +enter character to be searched +y +9 diff --git a/c/String/C Program to find Longer Repeating Sequence.c b/c/String/C Program to find Longer Repeating Sequence.c new file mode 100644 index 0000000..94b3d11 --- /dev/null +++ b/c/String/C Program to find Longer Repeating Sequence.c @@ -0,0 +1,84 @@ +/* + * C Program to find Longer Repeating Sequence + */ +#include +#include + +void main() +{ + char s1[100], ar[10][20], ar1[10][20], new[10]; + int i, j = 0, k = 0, l, count = 0, flag = 0, n, temp, len[20]; + printf("\nenter the string:"); + scanf(" %[^\n]s", s1); + /*COPYING GIVEN STRING TO 2D ARRAY*/ + for (i = 0; s1[i] != '\0'; i++,j++) + { + if (s1[i] >= 33 && s1[i] <= 64) + i++; + if (s1[i] == ' ') + { + ar[k][j] = '\0'; + k++; + i++; + j = 0; + } + ar[k][j] = s1[i]; + } + ar[k][j] = '\0'; + /*PLACING THE REPEATED WORDS AND LENGTHS INTO NEW ARRAY*/ + l = 0; + for (i = 0; i <= k; i++) + { + for (j = i + 1; j <= k; j++) + { + if (strcmp(ar[i], ar[j]) == 0) + { + for (n = 0; n < l && l != 0; n++) + { + if (strcmp(ar[i], ar1[k]) == 0) + { + flag = 1; + break; + } + } + if (flag != 1) + { + strcpy(ar1[l], ar[i]); + len[l] = strlen(ar1[l]); + l++; + } + flag = 0; + break; + } + } + } + printf("\n"); + /*SORTING IS DONE BASED ON THEIR LENGTHS*/ + for (i = 0; i < l; i++) + { + for (j = i + 1; j < l; j++) + { + if (len[i] < len[j]) + { + temp = len[i]; + strcpy(new, ar1[i]); + len[i] = len[j]; + strcpy(ar1[i], ar1[j]); + len[j] = temp; + strcpy(ar1[j], new); + } + } + } + maxlen = len[0]; + for (i = 0; i < l; i++) + { + if (len[i] == maxlen) + printf("\nthe longer repeating sequence of the given string is: %s", ar1[i]); + } +} +/* +*OUTPUT: +enter the string:Welcome to C Programming Class, Welcome Again to C Programming Class! + +the longer repeating sequence of the given string is: Programming +*/ \ No newline at end of file diff --git a/c/String/C Program to find the First Capital Letter in a String using Recursion.c b/c/String/C Program to find the First Capital Letter in a String using Recursion.c new file mode 100644 index 0000000..2f51188 --- /dev/null +++ b/c/String/C Program to find the First Capital Letter in a String using Recursion.c @@ -0,0 +1,48 @@ +/* + * C Program to find the first capital letter in a string using + * Recursion + */ +#include +#include +#include + +char caps_check(char *); + +int main() +{ + char string[20], letter; + printf("Enter a string to find it's first capital letter: "); + scanf("%s", string); + letter = caps_check(string); + if (letter == 0) + { + printf("No capital letter is present in %s.\n", string); + } + else + { + printf("The first capital letter in %s is %c.\n", string, letter); + } + return 0; +} +char caps_check(char *string) +{ + static int i = 0; + if (i < strlen(string)) + { + if (isupper(string[i])) + { + return string[i]; + } + else + { + i = i + 1; + return caps_check(string); + } + } + else return 0; +} +/* +*OUTPUT: +Enter a string to find it's first capital letter: iloveC +The first capital letter in iloveC is C. +*/ \ No newline at end of file diff --git a/c/String/C Program to find the First Capital Letter in a String without using Recursion.c b/c/String/C Program to find the First Capital Letter in a String without using Recursion.c new file mode 100644 index 0000000..50b9e07 --- /dev/null +++ b/c/String/C Program to find the First Capital Letter in a String without using Recursion.c @@ -0,0 +1,44 @@ +/* + * C Program to find the First Capital Letter in a String without + * using Recursion + */ +#include +#include +#include + +char caps_check(char *); + +int main() +{ + char string[20], letter; + printf("Enter a string to find it's first capital letter: "); + scanf("%s", string); + letter = caps_check(string); + if (letter == 0) + { + printf("No capital letter is present in %s.\n", string); + } + else + { + printf("The first capital letter in %s is %c.\n", string, letter); + } + return 0; +} +char caps_check(char *string) +{ + int i = 0; + while (string[i] != '\0') + { + if (isupper(string[i])) + { + return string[i]; + } + i++; + } + return 0; +} +/* +*OUTPUT: +Enter a string to find it's first capital letter: prOgraMmInG +The first capital letter in prOgraMmInG is O. +*/ \ No newline at end of file diff --git a/c/String/C Program to find the Length of the String using Recursion.c b/c/String/C Program to find the Length of the String using Recursion.c new file mode 100644 index 0000000..5f4c451 --- /dev/null +++ b/c/String/C Program to find the Length of the String using Recursion.c @@ -0,0 +1,72 @@ +/* + * Recursive C program to find length of a linked list + */ +#include +#include + +struct node +{ + int a; + struct node *next; +}; + +void generate(struct node **); +int length(struct node*); +void delete(struct node **); + +int main() +{ + struct node *head = NULL; + int count; + generate(&head); + count = length(head); + printf("The number of nodes are: %d\n", count); + delete(&head); + return 0; +} + +void generate(struct node **head) +{ + /* for unknown number of nodes use num = rand() % 20; */ + int num = 10, i; + struct node *temp; + for (i = 0; i < num; i++) + { + temp = (struct node *)malloc(sizeof(struct node)); + temp->a = i; + if (*head == NULL) + { + *head = temp; + (*head)->next = NULL; + } + else + { + temp->next = *head; + *head = temp; + } + } +} + +int length(struct node *head) +{ + if (head->next == NULL) + { + return 1; + } + return (1 + length(head->next)); +} + +void delete(struct node **head) +{ + struct node *temp; + while (*head != NULL) + { + temp = *head; + *head = (*head)->next; + free(temp); + } +} +/* +*OUTPUT: +The number of nodes are: 10 +*/ \ No newline at end of file diff --git a/c/String/C Program to find the possible subsets of the String.c b/c/String/C Program to find the possible subsets of the String.c new file mode 100644 index 0000000..8a8ad55 --- /dev/null +++ b/c/String/C Program to find the possible subsets of the String.c @@ -0,0 +1,287 @@ +/* + * C Program to find the possible subsets of the String + */ +#include + +char string[50], n; +void subset(int, int, int); + +int main() +{ + int i, len; + printf("Enter the len of main set : "); + scanf("%d", &len); + printf("Enter the elements of main set : "); + scanf("%s", string); + n = len; + printf("The subsets are :\n"); + for (i = 1; i <= n; i++) + subset(0, 0, i); +} + +/*Function to find the number of subsets in the given string*/ + +void subset(int start, int index, int num_sub) +{ + int i, j; + if (index - start + 1 == num_sub) + { + if (num_sub == 1) + { + for (i = 0; i < n; i++) + printf("%c\n", string[i]); + } + else + { + for (j = index; j < n; j++) + { + for (i = start; i < index; i++) + printf("%c", string[i]); + printf("%c\n", string[j]); + } + if (start != n - num_sub) + subset(start + 1, start + 1, num_sub); + } + } + else + { + subset(start, index + 1, num_sub); + } +} +/* +*OUTPUT: +Enter the len of main set : 11 +Enter the elements of main set : programming +The subsets are : +p +r +o +g +r +a +m +m +i +n +g +pr +po +pg +pr +pa +pm +pm +pi +pn +pg +ro +rg +rr +ra +rm +rm +ri +rn +rg +og +or +oa +om +om +oi +on +og +gr +ga +gm +gm +gi +gn +gg +ra +rm +rm +ri +rn +rg +am +am +ai +an +ag +mm +mi +mn +mg +mi +mn +mg +in +ig +ng +pro +prg +prr +pra +prm +prm +pri +prn +prg +rog +ror +roa +rom +rom +roi +ron +rog +ogr +oga +ogm +ogm +ogi +ogn +ogg +gra +grm +grm +gri +grn +grg +ram +ram +rai +ran +rag +amm +ami +amn +amg +mmi +mmn +mmg +min +mig +ing +prog +pror +proa +prom +prom +proi +pron +prog +rogr +roga +rogm +rogm +rogi +rogn +rogg +ogra +ogrm +ogrm +ogri +ogrn +ogrg +gram +gram +grai +gran +grag +ramm +rami +ramn +ramg +ammi +ammn +ammg +mmin +mmig +ming +progr +proga +progm +progm +progi +progn +progg +rogra +rogrm +rogrm +rogri +rogrn +rogrg +ogram +ogram +ograi +ogran +ograg +gramm +grami +gramn +gramg +rammi +rammn +rammg +ammin +ammig +mming +progra +progrm +progrm +progri +progrn +progrg +rogram +rogram +rograi +rogran +rograg +ogramm +ogrami +ogramn +ogramg +grammi +grammn +grammg +rammin +rammig +amming +program +program +prograi +progran +prograg +rogramm +rogrami +rogramn +rogramg +ogrammi +ogrammn +ogrammg +grammin +grammig +ramming +programm +programi +programn +programg +rogrammi +rogrammn +rogrammg +ogrammin +ogrammig +gramming +programmi +programmn +programmg +rogrammin +rogrammig +ogramming +programmin +programmig +rogramming +programming +*/ \ No newline at end of file diff --git a/c/String/C Program to read two Strings _ Concatenate the Strings.c b/c/String/C Program to read two Strings _ Concatenate the Strings.c new file mode 100644 index 0000000..2841921 --- /dev/null +++ b/c/String/C Program to read two Strings _ Concatenate the Strings.c @@ -0,0 +1,43 @@ +/* + * C program to read two strings and concatenate them, without using + * library functions. Display the concatenated string. + */ +#include +#include + +void main() +{ + char string1[20], string2[20]; + int i, j, pos; + /* Initialize the string to NULL values */ + memset(string1, 0, 20); + memset(string2, 0, 20); + printf("Enter the first string : "); + scanf("%s", string1); + printf("Enter the second string: "); + scanf("%s", string2); + printf("First string = %s\n", string1); + printf("Second string = %s\n", string2); + /* Concate the second string to the end of the first string */ + for (i = 0; string1[i] != '\0'; i++) + { + /* null statement: simply traversing the string1 */ + ; + } + pos = i; + for (j = 0; string2[j] != '\0'; i++) + { + string1[i] = string2[j++]; + } + /* set the last character of string1 to NULL */ + string1[i] = '\0'; + printf("Concatenated string = %s\n", string1); +} +/* +*OUTPUT: +Enter the first string : San +Enter the second string: foundry +First string = San +Second string = foundry +Concatenated string = Sanfoundry +*/ \ No newline at end of file diff --git a/c/String/C program to accept a string and find the number of times the word 'the' appears in that string.c b/c/String/C program to accept a string and find the number of times the word 'the' appears in that string.c new file mode 100644 index 0000000..07cc9fe --- /dev/null +++ b/c/String/C program to accept a string and find the number of times the word 'the' appears in that string.c @@ -0,0 +1,36 @@ +/* + * C program to accept a string and find the number of times the word + * 'the' appears in that string + */ +#include + +void main() +{ + int count = 0, i, times = 0, t, h, e, space; + char string[100]; + puts("Enter a string:"); + gets(string); + /* Traverse the string to count the number of characters */ + while (string[count] != '') + { + count++ + ; + } + /* Finding the frequency of the word 'the' */ + for (i = 0; i <= count - 3; i++) + { + t =(string[i] == 't' || string[i] == 'T'); + h =(string[i + 1] == 'h' || string[i + 1] == 'H'); + e =(string[i + 2] == 'e'|| string[i + 2] == 'E'); + space =(string[i + 3] == ' ' || string[i + 3] == ''); + if ((t && h && e && space) == 1) times++; + } + printf("Frequency of the word 'the' is %d + ", times); +} + + +Enter a string: +The gandhi jayanthi is celeberated on october 2 is the day +that he has born. +Frequency of the word 'the' is 2 \ No newline at end of file diff --git a/c/String/C program to check if a word is present in a string.c b/c/String/C program to check if a word is present in a string.c new file mode 100644 index 0000000..8651c7f --- /dev/null +++ b/c/String/C program to check if a word is present in a string.c @@ -0,0 +1,45 @@ +/* + * C program to accept a string and a substring and + * check if the substring is present in the given string + */ +#include + +void main() +{ + char str[80], search[10]; + int count1 = 0, count2 = 0, i, j, flag; + printf("Enter a string:"); + gets(str); + printf("Enter search substring:"); + gets(search); + while (str[count1] != '�') + count1++; + while (search[count2] != '�') + count2++; + for (i = 0; i <= count1 - count2; i++) + { + for (j = i; j < i + count2; j++) + { + flag = 1; + if (str[j] != search[j - i]) + { + flag = 0; + break; + } + } + if (flag == 1) + break; + } + if (flag == 1) + printf("SEARCH SUCCESSFUL!"); + else + printf("SEARCH UNSUCCESSFUL!"); +} + +Enter a string: +hello +Enter search substring: +world +SEARCH UNSUCCESSFUL! Enter a string: +helloworld Enter search substring: +ld SEARCH SUCCESSFUL! \ No newline at end of file diff --git a/c/String/C program to find the sum of all digits present in the string.c b/c/String/C program to find the sum of all digits present in the string.c new file mode 100644 index 0000000..d427f90 --- /dev/null +++ b/c/String/C program to find the sum of all digits present in the string.c @@ -0,0 +1,29 @@ +/* + * C program to find the sum of all digits present in the string + */ +#include +void main() +{ + char string[80]; + int count, nc = 0, sum = 0; + printf("Enter the string containing both digits and alphabet + "); + scanf("%s", string); + for (count = 0; string[count] != ''; count++) + { + if ((string[count] >= '0') && (string[count] <= '9')) + { + nc += 1; + sum += (string[count] - '0'); + } + } + printf("NO. of Digits in the string = %d + ", nc); + printf("Sum of all digits = %d + ", sum); +} + + Enter the string containing both digits and alphabet + hello100 + NO. of Digits in the string = 3 + Sum of all digits = 1 " android:lineSpacingExtra="5dp" \ No newline at end of file diff --git a/c/String/C program to read two strings and concatenate them.c b/c/String/C program to read two strings and concatenate them.c new file mode 100644 index 0000000..0916e9d --- /dev/null +++ b/c/String/C program to read two strings and concatenate them.c @@ -0,0 +1,44 @@ +/* + * C program to read two strings and concatenate them, without using + * library functions. Display the concatenated string. + */ +#include +#include + +void main() + +{ + char string1[20], string2[20]; + int i, j, pos; + /* Initialize the string to NULL values */ + memset(string1, 0, 20); + memset(string2, 0, 20); + printf("Enter the first string : "); + scanf("%s", string1); + printf("Enter the second string: "); + scanf("%s", string2); + printf("First string = %s", string1); + printf("Second string = %s", string2); + /* Concate the second string to the end of the first string */ + for (i = 0; string1[i] != ''; i++) + { + /* null statement: simply traversing the string1 */ + ; + } + pos = i; + for (j = 0; string2[j] != ''; i++) + { + string1[i] = string2[j++]; + } + /* set the last character of string1 to NULL */ + string1[i] = ''; + printf("Concatenated string = %s + ", string1); +} +/* + +Enter the first string : illumin8 +Enter the second string: ed +First string = illumin8 +Second string = ed +Concatenated string = illumin8ed diff --git a/c/Structures_and_unions/C Program for operations of Sequential file with records.c b/c/Structures_and_unions/C Program for operations of Sequential file with records.c new file mode 100644 index 0000000..cce91f6 --- /dev/null +++ b/c/Structures_and_unions/C Program for operations of Sequential file with records.c @@ -0,0 +1,64 @@ + #include + typedef struct { + int usn; + char name[25]; + int m1,m2,m3; + } + STD; + STD s; + void display(FILE *); + int search(FILE *,int); + void main() { + int i,n,usn_key,opn; + FILE *fp; + printf(" How many Records ? "); + scanf("%d",&n); + fp=fopen("stud.dat","w"); + for (i=0;i +#include +#include + +void main() +{ + struct hockey + { + char pname[20] ; + char cname[20] ; + int np ; + int ng ; + } ; + struct hockey player[50], temp ; + int i, j, n ; + clrscr(); + printf("Enter the number of players: ") ; + scanf("%d", &n) ; + printf("Enter player name , country name , number of matches played and no of goals scored for all players:\n\n") ; + for(i=0 ; i 0 ) + { + temp=player[j]; + player[j]=player[j+1]; + player[j+1]=temp; + } + printf("\nList in alphabetical order of country name is as shown:\n") ; + for(i=0 ; i 0 ) + { + temp=player[j]; + player[j]=player[j+1]; + player[j+1]=temp; + } + printf("\nList in alphabetical order of player name is as shown:\n") ; + for(i=0 ; i + struct stud { + int roll; + char name[10]; + int marks; + }; + int main() { + int size; + struct stud s; + size = sizeof(s); + printf("nSize of Structure : %d", size); + return(0); + } \ No newline at end of file diff --git a/c/Structures_and_unions/C Program to Maintain an Inventory of items in Online Store.c b/c/Structures_and_unions/C Program to Maintain an Inventory of items in Online Store.c new file mode 100644 index 0000000..478d584 --- /dev/null +++ b/c/Structures_and_unions/C Program to Maintain an Inventory of items in Online Store.c @@ -0,0 +1,47 @@ + #include + #include + void main() { + struct date { + int day; + int month; + int year; + }; + struct details { + char name[20]; + int price; + int code; + int qty; + struct date mfg; + }; + struct details item[50]; + int n,i; + clrscr(); + printf("Enter number of items:"); + scanf("%d",&n); + fflush(stdin); + for (i=0;i + #include + void main() { + char ch; + int count=0; + FILE *fptr; + clrscr(); + fptr=fopen("text.txt","w"); + if(fptr==NULL) { + printf("File can't be created\a"); + getch(); + exit(0); + } + printf("Enter some text and press enter key:\n"); + while((ch=getche())!='\r') { + fputc(ch,fptr); + } + fclose(fptr); + fptr=fopen("text.txt","r"); + printf("\nContents of the File is:"); + while((ch=fgetc(fptr))!=EOF) { + count++; + printf("%c",ch); + } + fclose(fptr); + printf("\nThe number of characters present in file is: %d",count); + getch(); + } \ No newline at end of file diff --git a/c/Structures_and_unions/C Program to create a record for an employee having name, code and salary...c b/c/Structures_and_unions/C Program to create a record for an employee having name, code and salary...c new file mode 100644 index 0000000..7d0ac50 --- /dev/null +++ b/c/Structures_and_unions/C Program to create a record for an employee having name, code and salary...c @@ -0,0 +1,40 @@ +/* Structure - Employee Salary - Program to create a record for an employee having name, code and salary. Read information for 30 employees and display details of all those employees having salary greater than 10000 */ + +#include +#include + +void main() +{ + struct employee + { + char name[20] ; + int code ; + float salary ; + } e[30] ; + /* Some compilers do not allow float member in a structure. In that case make salary to be of data type int */ + int i ; + clrscr() ; + printf("Enter employee name , code and salary for 30 employees: \n") ; + for(i=0 ; i<30 ; i++) + scanf("%s %d %f", e[i].name, &e[i].code, &e[i].salary) ; + printf("\nThe following employees have salary greater than 10000:\n") ; + for(i=0 ; i<30 ; i++) + if(e[i].salary>10000) + printf("%s %d %f \n", e[i].name, e[i].code, e[i].salary) ; + getch() ; +} + +/* +The following output is only for 3 employees: + +Enter employee name , code and salary for 30 employees: +Jack 123 12000.75 +Jill 456 9850.5 +Tim 789 17000.75 + +The following employees have salary greater than 10000: +Jack 123 12000.750000 +Tim 789 17000.750000 + +*/ + diff --git a/c/Structures_and_unions/C Program to create an array of structure to store details of almost 100 employees and sort it according to employee ID...c b/c/Structures_and_unions/C Program to create an array of structure to store details of almost 100 employees and sort it according to employee ID...c new file mode 100644 index 0000000..b1dc779 --- /dev/null +++ b/c/Structures_and_unions/C Program to create an array of structure to store details of almost 100 employees and sort it according to employee ID...c @@ -0,0 +1,52 @@ +/* Structure - Employee ID Sort - Program to create an array of structure to store details of almost 100 employees and sort it according to employee ID. Employee details are as follows: 1) Employee Name , 2) Employee ID and 3) Employee Salary */ + +#include +#include + +void main() +{ + struct employee + { + char name[20] ; + int id ; + float salary ; + } ; + /* Some compilers do not allow float member in a structure. In that case make salary to be of data type int */ + struct employee e[100], temp ; + int i, j, n ; + clrscr() ; + printf("Enter the number of employees: ") ; + scanf("%d", &n) ; + printf("Enter employee name , id and salary for all employees: \n") ; + for(i=0 ; i e[j+1].id) + { + temp=e[j]; + e[j]=e[j+1]; + e[j+1]=temp; + } + printf("\nList in ascending order of employee id is as shown:\n") ; + for(i=0 ; i +#include + +void main() +{ + struct point + { + int x, y ; + } ; + struct point p1, p2, p3 ; + clrscr(); + printf("Enter x and y co-ordinate for point 1: ") ; + scanf("%d %d", &p1.x, &p1.y) ; + printf("Enter x and y co-ordinate for point 2: ") ; + scanf("%d %d", &p2.x, &p2.y) ; + p3.x=p1.x+p2.x; + p3.y=p1.y+p2.y; + printf("The new point is (%d,%d)", p3.x, p3.y) ; + getch() ; +} + +/* +Output: + +Enter x and y co-ordinate for point 1: 2 6 +Enter x and y co-ordinate for point 2: 4 1 +The new point is (6,7) +*/ + diff --git a/c/Structures_and_unions/C program for Array of Structure.c b/c/Structures_and_unions/C program for Array of Structure.c new file mode 100644 index 0000000..2c6574e --- /dev/null +++ b/c/Structures_and_unions/C program for Array of Structure.c @@ -0,0 +1,26 @@ +/*Array of Structure*/ +#include +struct book +{ + int id; + char name[40]; +}; + +void main() +{ + struct book b[10]; + int i,n; + printf("Enter total number of book : "); + scanf("%d",&n); + for(i=0; i +#include + +void main() +{ + struct cricket + { + char pname[20] ; + char tname[20] ; + int np ; + float avg ; + }; + /* Some compilers do not allow float member in a structure. In that case make avg to be of data type int */ + struct cricket player[50], temp ; + int i, j ; + clrscr(); + printf("Enter player name , team name , number of matches played and batting average for 50 players:\n") ; + for(i=0 ; i<50 ; i++) + scanf("%s %s %d %f", player[i].pname, player[i].tname, &player[i].np, &player[i].avg) ; + for(i=0 ; i<50-1 ; i++) + for(j=0 ; j<50-1-i ; j++) + if(player[j].avg < player[j+1].avg ) + { + temp=player[j] ; + player[j]=player[j+1] ; + player[j+1]=temp ; + } + printf("\nList in descending order of batting average is as shown:\n") ; + for(i=0 ; i<50 ; i++) + printf("%s %s %d %f \n", player[i].pname, player[i].tname, player[i].np, player[i].avg) ; + getch(); +} + +/* +The following output is shown for 3 players only: + +Enter player name , team name , number of matches played and batting average for 50 players: +Jack Australia 202 67.5 +Sachin India 210 82.75 +Tim U.K. 205 76.25 + +List in descending order of batting average is as shown: +Sachin India 210 82.750000 +Tim U.K. 205 76.250000 +Jack Australia 202 67.500000 +*/ + diff --git a/c/Structures_and_unions/C program for HOSPITAL. (Structures).c b/c/Structures_and_unions/C program for HOSPITAL. (Structures).c new file mode 100644 index 0000000..dc80175 --- /dev/null +++ b/c/Structures_and_unions/C program for HOSPITAL. (Structures).c @@ -0,0 +1,57 @@ +/* Structure - Hospital - A hospital needs to maintain details of patients. Details to be maintained are first name, middle name, surname, date of birth and disease. Write a C program which will print list of all patients with given disease. */ + +#include +#include +#include + +void main() +{ + struct date + { + int d, m, y ; + } ; + struct hospital + { + char firstname[20], middlename[20], surname[20] ; + struct date dob ; + char disease[20]; + } ; + struct hospital h[50] ; + int i, j, n ; + char d[20] ; + clrscr(); + printf("Enter the number of patients: ") ; + scanf("%d", &n) ; + printf("Enter first name, middle name, surname, date of birth and disease for all patients: \n") ; + printf("Enter date of birth in d/m/y format. \n") ; + for(i=0 ; i +#include +#include + +void main() +{ + struct name + { + char fname[20] ; + char lname[20] ; + } ; + struct name x[50], temp ; + int i, j, n ; + clrscr() ; + printf("Enter the number of mobile customers: ") ; + scanf("%d", &n) ; + printf("Enter names of mobile customers in the format: \n") ; + printf("FIRST NAME LAST NAME \n") ; + for(i=0 ; i0 ) + { + temp=x[j] ; + x[j]=x[j+1] ; + x[j+1]=temp ; + } + printf("\nList sorted alphabetically as per last name is as shown:\n") ; + for(i=0; i +struct detail +{ + char name[10]; + float price; +}; +struct item +{ + int id; + struct detail d; +}; +void main() +{ + struct item itm; + printf("Enter item name, id and price "); + scanf("%s%d%f",itm.d.name,&itm.id,&itm.d.price); + printf("Entered details are:\n"); + printf("Id: %d\nName: %s Price: %f", itm.id, itm.d.name, itm.d.price); +} \ No newline at end of file diff --git a/c/Structures_and_unions/C program for Passing Array of Structure as function argument.c b/c/Structures_and_unions/C program for Passing Array of Structure as function argument.c new file mode 100644 index 0000000..6deb6a3 --- /dev/null +++ b/c/Structures_and_unions/C program for Passing Array of Structure as function argument.c @@ -0,0 +1,40 @@ +/*Passing Array of Structure as function argument*/ +#include +struct student +{ + char name[40]; + int marks; +}; +void display(struct student[],int); +void main() +{ + struct student s[3]; + int i; + printf("enter information of 3 students\n"); + for(i=0; i<3; i++) + { + printf("\nEnter name"); + scanf("%30[^\n]%*c",s[i].name);//you can use gets() + printf("\nEnter marks"); + scanf("%d",&s[i].marks); + } + display(s,3); +} +void display (struct student s[], int n) +{ + int i,count=0; + for(i=0; i=100) + { + printf("Required details are\n"); + printf("student name= %s",s[i].name); + printf(" student marks=%d\n",s[i].marks); + count++; + } + } + if(count==0) + { + printf("No details available for marks>100"); + } +} \ No newline at end of file diff --git a/c/Structures_and_unions/C program for Structure as Return type of a function.c b/c/Structures_and_unions/C program for Structure as Return type of a function.c new file mode 100644 index 0000000..f678ce9 --- /dev/null +++ b/c/Structures_and_unions/C program for Structure as Return type of a function.c @@ -0,0 +1,26 @@ +/*Structure as Return type of a function*/ +#include +struct book +{ + int id; + char name[40]; +}; +struct book getdata() +{ + struct book b; + printf("Enter book name and id"); + scanf("%s%d",&b.name,&b.id); + return b; +} +void display(struct book b) +{ + printf("\nDetails are:\n"); + printf("Book id = %d\n",b.id); + printf("Book name= %s",b.name); +} +void main() +{ + struct book b; + b=getdata(); + display(b); +} \ No newline at end of file diff --git a/c/Structures_and_unions/C program to read information of a book and display the information (Pointer to Structure as argument).c b/c/Structures_and_unions/C program to read information of a book and display the information (Pointer to Structure as argument).c new file mode 100644 index 0000000..4cacbb4 --- /dev/null +++ b/c/Structures_and_unions/C program to read information of a book and display the information (Pointer to Structure as argument).c @@ -0,0 +1,25 @@ +/*Pointer to Structure as argument*/ +/*Write a program to read information of a book and display the information.*/ + +#include +struct book +{ + int bno; + char name[40]; +}; +void display(struct book*); +void main() +{ + struct book b; + printf("\nEnter book no: "); + scanf("%d",&b.bno); + printf("Enter book name: "); + scanf("%s",b.name); + display(&b); +} +void display(struct book *b) +{ + printf("\nDetails are: "); + printf("Book number= %d \n",b->bno); + printf("Book name= %s",b->name); +} \ No newline at end of file diff --git a/c/Structures_and_unions/C program to read information of a book and display the information (Structure as argument).c b/c/Structures_and_unions/C program to read information of a book and display the information (Structure as argument).c new file mode 100644 index 0000000..271fd83 --- /dev/null +++ b/c/Structures_and_unions/C program to read information of a book and display the information (Structure as argument).c @@ -0,0 +1,25 @@ +/*Structure as argument*/ +/*Write a program to read information of a book and display the information.*/ +#include +#include +struct book +{ + int bno; + char name[40]; +}; +void display(struct book); +void main() +{ + struct book b; + printf("\nEnter book no: "); + scanf("%d",&b.bno); + printf("Enter book name: "); + scanf("%s",b.name); + display(b); +} +void display(struct book b) +{ + printf("\n details are: "); + printf("Book number=%d",b.bno); + printf("Book name=%s",b.name); +} \ No newline at end of file diff --git a/c/Structures_and_unions/write a c program which produces its own source code as its output.c b/c/Structures_and_unions/write a c program which produces its own source code as its output.c new file mode 100644 index 0000000..a315c55 --- /dev/null +++ b/c/Structures_and_unions/write a c program which produces its own source code as its output.c @@ -0,0 +1,15 @@ + #include + int main(){ + FILE *fp; + char c; + fp = fopen(__FILE__,"r"); + + do{ + c= getc(fp); + putchar(c); + } + + while(c!=EOF); + fclose(fp); + return 0; + } \ No newline at end of file diff --git a/c/Without_Recursion/C Program Count the Occurrences of an Element in the Linked List without using Recursion.c b/c/Without_Recursion/C Program Count the Occurrences of an Element in the Linked List without using Recursion.c new file mode 100644 index 0000000..341f30a --- /dev/null +++ b/c/Without_Recursion/C Program Count the Occurrences of an Element in the Linked List without using Recursion.c @@ -0,0 +1,40 @@ +/* + * C Program Count the Number of Occurrences of an Element in the Linked List + * without using Recursion + */ +#include + +int occur(int [], int, int); + +int main() +{ + int size, key, count; + int list[20]; + int i; + printf("Enter the size of the list: "); + scanf("%d", &size); + printf("Printing the list:\n"); + for (i = 0; i < size; i++) + { + list[i] = rand() % size; + printf("%d ", list[i]); + } + printf("\nEnter the key to find it's occurence: "); + scanf("%d", &key); + count = occur(list, size, key); + printf("%d occurs for %d times.\n", key, count); + return 0; +} + +int occur(int list[], int size, int key) +{ + int i, count = 0; + for (i = 0; i < size; i++) + { + if (list[i] == key) + { + count += 1; + } + } + return count; +} \ No newline at end of file diff --git a/c/Without_Recursion/C Program Find the Length of the Linked List without using Recursion.c b/c/Without_Recursion/C Program Find the Length of the Linked List without using Recursion.c new file mode 100644 index 0000000..e79da0c --- /dev/null +++ b/c/Without_Recursion/C Program Find the Length of the Linked List without using Recursion.c @@ -0,0 +1,71 @@ +/* + * C Program find the Length of the Linked List without using Recursion + */ +#include +#include + +struct node +{ + int a; + struct node *next; +}; + + +void generate(struct node **); +int length(struct node*); +void delete(struct node **); + +int main() +{ + struct node *head = NULL; + int count; + generate(&head); + count = length(head); + printf("The number of nodes are: %d\n", count); + delete(&head); + return 0; +} + +void generate(struct node **head) +{ + /* for unknown number of nodes use num = rand() % 20; */ + int num = 10, i; + struct node *temp; + for (i = 0; i < num; i++) + { + temp = (struct node *)malloc(sizeof(struct node)); + temp->a = i; + if (*head == NULL) + { + *head = temp; + (*head)->next = NULL; + } + else + { + temp->next = *head; + *head = temp; + } + } +} + +int length(struct node *head) +{ + int num = 0; + while (head != NULL) + { + num += 1; + head = head->next; + } + return num; +} + +void delete(struct node **head) +{ + struct node *temp; + while (*head != NULL) + { + temp = *head; + *head = (*head)->next; + free(temp); + } +} \ No newline at end of file diff --git a/c/Without_Recursion/C Program for Depth First Binary Tree Search without using Recursion.c b/c/Without_Recursion/C Program for Depth First Binary Tree Search without using Recursion.c new file mode 100644 index 0000000..3c6f317 --- /dev/null +++ b/c/Without_Recursion/C Program for Depth First Binary Tree Search without using Recursion.c @@ -0,0 +1,126 @@ +/* + * C Program for Depth First Binary Tree Search without using + * Recursion + */ +#include +#include + +struct node +{ + int a; + struct node *left; + struct node *right; + int visited; +}; + +void generate(struct node **, int); +void DFS(struct node *); +void delete(struct node **); + +int main() +{ + struct node *head = NULL; + int choice = 0, num, flag = 0, key; + do + { + printf("\nEnter your choice:\n1. Insert\n2. Perform DFS Traversal\n3. Exit\nChoice: "); + scanf("%d", &choice); + switch(choice) + { + case 1: + printf("Enter element to insert: "); + scanf("%d", &num); + generate(&head, num); + break; + case 2: + DFS(head); + break; + case 3: + delete(&head); + printf("Memory Cleared\nPROGRAM TERMINATED\n"); + break; + default: + printf("Not a valid input, try again\n"); + } + } + while (choice != 3); + return 0; +} + +void generate(struct node **head, int num) +{ + struct node *temp = *head, *prev = *head; + if (*head == NULL) + { + *head = (struct node *)malloc(sizeof(struct node)); + (*head)->a = num; + (*head)->visited = 0; + (*head)->left = (*head)->right = NULL; + } + else + { + while (temp != NULL) + { + if (num > temp->a) + { + prev = temp; + temp = temp->right; + } + else + { + prev = temp; + temp = temp->left; + } + } + temp = (struct node *)malloc(sizeof(struct node)); + temp->a = num; + temp->visited = 0; + if (temp->a >= prev->a) + { + prev->right = temp; + } + else + { + prev->left = temp; + } + } +} + +void DFS(struct node *head) +{ + struct node *temp = head, *prev; + printf("On DFS traversal we get:\n"); + while (temp && !temp->visited) + { + if (temp->left && !temp->left->visited) + { + temp = temp->left; + } + else if (temp->right && !temp->right->visited) + { + temp = temp->right; + } + else + { + printf("%d ", temp->a); + temp->visited = 1; + temp = head; + } + } +} + +void delete(struct node **head) +{ + if (*head != NULL) + { + if ((*head)->left) + { + delete(&(*head)->left); + } + if ((*head)->right) + { + delete(&(*head)->right); + } + free(*head); + } +} \ No newline at end of file diff --git a/c/Without_Recursion/C Program to Convert Binary Code of a Number into its Equivalent Gray’s Code using Recursion.c b/c/Without_Recursion/C Program to Convert Binary Code of a Number into its Equivalent Gray’s Code using Recursion.c new file mode 100644 index 0000000..152e79a --- /dev/null +++ b/c/Without_Recursion/C Program to Convert Binary Code of a Number into its Equivalent Gray’s Code using Recursion.c @@ -0,0 +1,40 @@ +/* + * C Program to Convert Binary Code of a Number into its Equivalent + * Gray's Code using Recursion + */ +#include + +int bintogray(int); + +int main () +{ + int bin, gray; + printf("Enter a binary number: "); + scanf("%d", &bin); + gray = bintogray(bin); + printf("The gray code of %d is %d\n", bin, gray); + return 0; +} + +int bintogray(int bin) +{ + int a, b, result = 0, i = 0; + if (!bin) + { + return 0; + } + else + { + a = bin % 10; + bin = bin / 10; + b = bin % 10; + if ((a && !b) || (!a && b)) + { + return (1 + 10 * bintogray(bin)); + } + else + { + return (10 * bintogray(bin)); + } + } +} \ No newline at end of file diff --git a/c/Without_Recursion/C Program to Convert Binary Code of a Number into its Equivalent Gray’s Code without using Recursion.c b/c/Without_Recursion/C Program to Convert Binary Code of a Number into its Equivalent Gray’s Code without using Recursion.c new file mode 100644 index 0000000..020d700 --- /dev/null +++ b/c/Without_Recursion/C Program to Convert Binary Code of a Number into its Equivalent Gray’s Code without using Recursion.c @@ -0,0 +1,35 @@ +/* + * C Program to Convert Binary Code of a Number into its Equivalent + * Gray's Code without using Recursion + */ +#include +#include + +int bintogray(int); + +int main () +{ + int bin, gray; + printf("Enter a binary number: "); + scanf("%d", &bin); + gray = bintogray(bin); + printf("The gray code of %d is %d\n", bin, gray); + return 0; +} + +int bintogray(int bin) +{ + int a, b, result = 0, i = 0; + while (bin != 0) + { + a = bin % 10; + bin = bin / 10; + b = bin % 10; + if ((a && !b) || (!a && b)) + { + result = result + pow(10, i); + } + i++; + } + return result; +} \ No newline at end of file diff --git a/c/Without_Recursion/C Program to Display all the Nodes in a Linked List without using Recursion.c b/c/Without_Recursion/C Program to Display all the Nodes in a Linked List without using Recursion.c new file mode 100644 index 0000000..54d6d22 --- /dev/null +++ b/c/Without_Recursion/C Program to Display all the Nodes in a Linked List without using Recursion.c @@ -0,0 +1,67 @@ +/* + * C Program to Display all the Nodes in a Linked List without using + * Recursion + */ +#include +#include + +struct node +{ + int a; + struct node *next; +}; + +void generate(struct node **); +void display(struct node*); +void delete(struct node **); + +int main() +{ + struct node *head = NULL; + generate(&head); + display(head); + delete(&head); + return 0; +} + +void generate(struct node **head) +{ + int num = 10, i; + struct node *temp; + for (i = 0; i < num; i++) + { + temp = (struct node *)malloc(sizeof(struct node)); + temp->a = i; + if (*head == NULL) + { + *head = temp; + (*head)->next = NULL; + } + else + { + temp->next = *head; + *head = temp; + } + } +} + +void display(struct node *head) +{ + while (head != NULL) + { + printf("%d ", head->a); + head = head->next; + } + printf("\n"); +} + +void delete(struct node **head) +{ + struct node *temp; + while (*head != NULL) + { + temp = *head; + *head = (*head)->next; + free(temp); + } +} \ No newline at end of file diff --git a/c/Without_Recursion/C Program to Display the Nodes of a Linked List in Reverse without using Recursion.c b/c/Without_Recursion/C Program to Display the Nodes of a Linked List in Reverse without using Recursion.c new file mode 100644 index 0000000..2697d29 --- /dev/null +++ b/c/Without_Recursion/C Program to Display the Nodes of a Linked List in Reverse without using Recursion.c @@ -0,0 +1,91 @@ +/* + * C Program to Display the Nodes of a Linked List in Reverse without + * using Recursion + */ + +#include +#include + +struct node +{ + int visited; + int a; + struct node *next; +}; + +void generate(struct node **); +void display(struct node *); +void linear(struct node *); +void delete(struct node **); + +int main() +{ + struct node *head = NULL; + generate(&head); + printf("\nPrinting the list in linear order\n"); + linear(head); + printf("\nPrinting the list in reverse order\n"); + display(head); + delete(&head); + return 0; +} + +void display(struct node *head) +{ + struct node *temp = head, *prev = head; + while (temp->visited == 0) + { + while (temp->next != NULL && temp->next->visited == 0) + { + temp = temp->next; + } + printf("%d ", temp->a); + temp->visited = 1; + temp = head; + } +} + +void linear(struct node *head) +{ + while (head != NULL) + { + printf("%d ", head->a); + head = head->next; + } + printf("\n"); +} + +void generate(struct node **head) +{ + int num, i; + struct node *temp; + printf("Enter length of list: "); + scanf("%d", &num); + for (i = num; i > 0; i--) + { + temp = (struct node *)malloc(sizeof(struct node)); + temp->a = i; + temp->visited = 0; + if (*head == NULL) + { + *head = temp; + (*head)->next = NULL; + } + else + { + temp->next = *head; + *head = temp; + } + } +} + +void delete(struct node **head) +{ + struct node *temp; + while (*head != NULL) + { + temp = *head; + *head = (*head)->next; + free(temp); + } +} \ No newline at end of file diff --git a/c/Without_Recursion/C Program to Find Product of 2 Numbers without using Recursion.c b/c/Without_Recursion/C Program to Find Product of 2 Numbers without using Recursion.c new file mode 100644 index 0000000..dbfc6c0 --- /dev/null +++ b/c/Without_Recursion/C Program to Find Product of 2 Numbers without using Recursion.c @@ -0,0 +1,28 @@ +/* + * C Program to find Product of 2 Numbers without using Recursion + */ + +#include + +int product(int, int); + +int main() +{ + int a, b, result; + printf("Enter two numbers to find their product: "); + scanf("%d%d", &a, &b); + result = product(a, b); + printf("Product of %d and %d is %d\n", a, b, result); + return 0; +} + +int product(int a, int b) +{ + int temp = 0; + while (b != 0) + { + temp += a; + b--; + } + return temp; +} \ No newline at end of file diff --git a/c/Without_Recursion/C Program to Print the Alternate Nodes in a Linked List without using Recursion.c b/c/Without_Recursion/C Program to Print the Alternate Nodes in a Linked List without using Recursion.c new file mode 100644 index 0000000..97beba7 --- /dev/null +++ b/c/Without_Recursion/C Program to Print the Alternate Nodes in a Linked List without using Recursion.c @@ -0,0 +1,75 @@ +/* + * C Program to Print the Alternate Nodes in a Linked List without + * using Recursion + */ +#include +#include + +struct node +{ + int a; + struct node *next; +}; + +void generate(struct node **); +void display(struct node *); +void delete(struct node **); + +int main() +{ + struct node *head = NULL; + generate(&head); + printf("\nDisplaying the alternate nodes\n"); + display(head); + delete(&head); + return 0; +} + +void display(struct node *head) +{ + int flag = 0; + while(head != NULL) + { + if (!(flag % 2)) + { + printf("%d ", head->a); + } + flag++; + head = head->next; + } +} + +void generate(struct node **head) +{ + int num, i; + struct node *temp; + printf("Enter length of list: "); + scanf("%d", &num); + for (i = num; i > 0; i--) + { + temp = (struct node *)malloc(sizeof(struct node)); + temp->a = i; + if (*head == NULL) + { + *head = temp; + (*head)->next = NULL; + } + else + { + temp->next = *head; + *head = temp; + } + } +} + +void delete(struct node **head) +{ + struct node *temp; + while (*head != NULL) + { + temp = *head; + *head = (*head)->next; + free(temp); + } +} +} \ No newline at end of file diff --git a/c/Without_Recursion/C Program to Reverse a Stack without using Recursion.c b/c/Without_Recursion/C Program to Reverse a Stack without using Recursion.c new file mode 100644 index 0000000..2775322 --- /dev/null +++ b/c/Without_Recursion/C Program to Reverse a Stack without using Recursion.c @@ -0,0 +1,108 @@ +/* + * C Program to Reverse a Stack without using Recursion + */ +#include +#include + +struct node +{ + int a; + struct node *next; +}; + +void generate(struct node **); +void display(struct node *); +void stack_reverse(struct node **); +void delete(struct node **); + +int main() +{ + struct node *head = NULL; + generate(&head); + printf("\nThe sequence of contents in stack\n"); + display(head); + printf("\nInversing the contents of the stack\n"); + stack_reverse(&head); + printf("\nThe contents in stack after reversal\n"); + display(head); + delete(&head); + return 0; +} + +void stack_reverse(struct node **head) +{ + struct node *temp, *prev; + if (*head == NULL) + { + printf("Stack does not exist\n"); + } + else if ((*head)->next == NULL) + { + printf("Single node stack reversal brings no difference\n"); + } + else if ((*head)->next->next == NULL) + { + (*head)->next->next = *head; + *head = (*head)->next; + (*head)->next->next = NULL; + } + else + { + prev = *head; + temp = (*head)->next; + *head = (*head)->next->next; + prev->next = NULL; + while ((*head)->next != NULL) + { + temp->next = prev; + prev = temp; + temp = *head; + *head = (*head)->next; + } + temp->next = prev; + (*head)->next = temp; + } +} + +void display(struct node *head) +{ + if (head != NULL) + { + printf("%d ", head->a); + display(head->next); + } +} + +void generate(struct node **head) +{ + int num, i; + struct node *temp; + printf("Enter length of list: "); + scanf("%d", &num); + for (i = num; i > 0; i--) + { + temp = (struct node *)malloc(sizeof(struct node)); + temp->a = i; + if (*head == NULL) + { + *head = temp; + (*head)->next = NULL; + } + else + { + temp->next = *head; + *head = temp; + } + } +} + +void delete(struct node **head) +{ + struct node *temp; + while (*head != NULL) + { + temp = *head; + *head = (*head)->next; + free(temp); + } +} \ No newline at end of file diff --git a/c/Without_Recursion/C Program to Search for an Element in the Linked List without using Recursion.c b/c/Without_Recursion/C Program to Search for an Element in the Linked List without using Recursion.c new file mode 100644 index 0000000..c967ff7 --- /dev/null +++ b/c/Without_Recursion/C Program to Search for an Element in the Linked List without using Recursion.c @@ -0,0 +1,79 @@ +/* + * C Program to Search for an Element in the Linked List without + * using Recursion + */ + +#include +#include + +struct node +{ + int a; + struct node *next; +}; + +void generate(struct node **, int); +void search(struct node *, int); +void delete(struct node **); + +int main() +{ + struct node *head = NULL; + int key, num; + printf("Enter the number of nodes: "); + scanf("%d", &num); + printf("\nDisplaying the list\n"); + generate(&head, num); + printf("\nEnter key to search: "); + scanf("%d", &key); + search(head, key); + delete(&head); + return 0; +} + +void generate(struct node **head, int num) +{ + int i; + struct node *temp; + for (i = 0; i < num; i++) + { + temp = (struct node *)malloc(sizeof(struct node)); + temp->a = rand() % num; + if (*head == NULL) + { + *head = temp; + temp->next = NULL; + } + else + { + temp->next = *head; + *head = temp; + } + printf("%d ", temp->a); + } +} + +void search(struct node *head, int key) +{ + while (head != NULL) + { + if (head->a == key) + { + printf("key found\n"); + return; + } + head = head->next; + } + printf("Key not found\n"); +} + +void delete(struct node **head) +{ + struct node *temp; + while (*head != NULL) + { + temp = *head; + *head = (*head)->next; + free(temp); + } +} \ No newline at end of file diff --git a/c/Without_Recursion/C Program to Solve the Magic Squares Puzzle without using Recursion.c b/c/Without_Recursion/C Program to Solve the Magic Squares Puzzle without using Recursion.c new file mode 100644 index 0000000..7e0206d --- /dev/null +++ b/c/Without_Recursion/C Program to Solve the Magic Squares Puzzle without using Recursion.c @@ -0,0 +1,61 @@ +/* + * C Program to Solve the Magic Squares Puzzle without using + * Recursion + */ +#include + +void magicsq(int, int [][10]); + +int main( ) +{ + int size; + int a[10][10]; + printf("Enter the size: "); + scanf("%d", &size); + if (size % 2 == 0) + { + printf("Magic square works for an odd numbered size\n"); + } + else + { + magicsq(size, a); + } + return 0; +} + +void magicsq(int size, int a[][10]) +{ + int sqr = size * size; + int i = 0, j = size / 2, k; + for (k = 1; k <= sqr; ++k) + { + a[i][j] = k; + i--; + j++; + if (k % size == 0) + { + i += 2; + --j; + } + else + { + if (j == size) + { + j -= size; + } + else if (i < 0) + { + i += size; + } + } + } + for (i = 0; i < size; i++) + { + for (j = 0; j < size; j++) + { + printf("%d ", a[i][j]); + } + printf("\n"); + } + printf("\n"); +} \ No newline at end of file diff --git a/c/Without_Recursion/C Program to Traverse the Tree Non-Recursively.c b/c/Without_Recursion/C Program to Traverse the Tree Non-Recursively.c new file mode 100644 index 0000000..04834a4 --- /dev/null +++ b/c/Without_Recursion/C Program to Traverse the Tree Non-Recursively.c @@ -0,0 +1,129 @@ +/* + * C Program to Traverse the Tree Non-Recursively + */ +#include +#include + +struct node +{ + int a; + struct node *left; + struct node *right; +}; + +void generate(struct node **, int); +int search(struct node *, int); +void delete(struct node **); + +int main() +{ + struct node *head = NULL; + int choice = 0, num, flag = 0, key; + do + { + printf("\nEnter your choice:\n1. Insert\n2. Search\n3. Exit\nChoice: "); + scanf("%d", &choice); + switch(choice) + { + case 1: + printf("Enter element to insert: "); + scanf("%d", &num); + generate(&head, num); + break; + case 2: + printf("Enter key to search: "); + scanf("%d", &key); + flag = search(head, key); + if (flag) + { + printf("Key found in tree\n"); + } + else + { + printf("Key not found\n"); + } + break; + case 3: + delete(&head); + printf("Memory Cleared\nPROGRAM TERMINATED\n"); + break; + default: + printf("Not a valid input, try again\n"); + } + } + while (choice != 3); + return 0; +} + +void generate(struct node **head, int num) +{ + struct node *temp = *head, *prev = *head; + if (*head == NULL) + { + *head = (struct node *)malloc(sizeof(struct node)); + (*head)->a = num; + (*head)->left = (*head)->right = NULL; + } + else + { + while (temp != NULL) + { + if (num > temp->a) + { + prev = temp; + temp = temp->right; + } + else + { + prev = temp; + temp = temp->left; + } + } + temp = (struct node *)malloc(sizeof(struct node)); + temp->a = num; + if (num >= prev->a) + { + prev->right = temp; + } + else + { + prev->left = temp; + } + } +} + +int search(struct node *head, int key) +{ + while (head != NULL) + { + if (key > head->a) + { + head = head->right; + } + else if (key < head->a) + { + head = head->left; + } + else + { + return 1; + } + } + return 0; +} + +void delete(struct node **head) +{ + if (*head != NULL) + { + if ((*head)->left) + { + delete(&(*head)->left); + } + if ((*head)->right) + { + delete(&(*head)->right); + } + free(*head); + } +} \ No newline at end of file diff --git a/c/Without_Recursion/C Program to find HCF of a given Number without using Recursion.c b/c/Without_Recursion/C Program to find HCF of a given Number without using Recursion.c new file mode 100644 index 0000000..75f8e16 --- /dev/null +++ b/c/Without_Recursion/C Program to find HCF of a given Number without using Recursion.c @@ -0,0 +1,32 @@ +/* + * C Program to find HCF of a given Number without using Recursion + */ +#include + +int hcf(int, int); + +int main() +{ + int a, b, result; + printf("Enter the two numbers to find their HCF: "); + scanf("%d%d", &a, &b); + result = hcf(a, b); + printf("The HCF of %d and %d is %d.\n", a, b, result); + return 0; +} + +int hcf(int a, int b) +{ + while (a != b) + { + if (a > b) + { + a = a - b; + } + else + { + b = b - a; + } + } + return a; +} \ No newline at end of file diff --git a/c/Without_Recursion/C Program to find the First Capital Letter in a String without using Recursion.c b/c/Without_Recursion/C Program to find the First Capital Letter in a String without using Recursion.c new file mode 100644 index 0000000..4bda840 --- /dev/null +++ b/c/Without_Recursion/C Program to find the First Capital Letter in a String without using Recursion.c @@ -0,0 +1,39 @@ +/* + * C Program to find the First Capital Letter in a String without + * using Recursion + */ +#include +#include +#include + +char caps_check(char *); + +int main() +{ + char string[20], letter; + printf("Enter a string to find it's first capital letter: "); + scanf("%s", string); + letter = caps_check(string); + if (letter == 0) + { + printf("No capital letter is present in %s.\n", string); + } + else + { + printf("The first capital letter in %s is %c.\n", string, letter); + } + return 0; +} +char caps_check(char *string) +{ + int i = 0; + while (string[i] != '\0') + { + if (isupper(string[i])) + { + return string[i]; + } + i++; + } + return 0; +} \ No newline at end of file diff --git a/c/_Basic/Accessing an array using pointers.c b/c/_Basic/Accessing an array using pointers.c new file mode 100644 index 0000000..295fd2c --- /dev/null +++ b/c/_Basic/Accessing an array using pointers.c @@ -0,0 +1,17 @@ + #include + + main(){ + int a[5]; + int i; + for(i = 0;i<5;i++){ + a[i]=i; + } + + int *b; + + b=a; + for(i = 0;i<5;i++){ + printf("value in array %d and address is %16lu\n",*b,b); + b=b+2; + } + } \ No newline at end of file diff --git a/c/_Basic/C Program to Accept the Height of a Person & Categorize as Taller, Dwarf & Average.c b/c/_Basic/C Program to Accept the Height of a Person & Categorize as Taller, Dwarf & Average.c new file mode 100644 index 0000000..053b281 --- /dev/null +++ b/c/_Basic/C Program to Accept the Height of a Person & Categorize as Taller, Dwarf & Average.c @@ -0,0 +1,21 @@ +/* + * C program to accept the height of a person in centimeter and + * categorize the person based on height as taller, dwarf and + * average height person + */ + +#include +void main() +{ + float height; + printf("Enter the Height (in centimetres) \n"); + scanf("%f", &height); + if (height < 150.0) + printf("Dwarf \n"); + else if ((height >= 150.0) && (height <= 165.0)) + printf(" Average Height \n"); + else if ((height >= 165.0) && (height <= 195.0)) + printf("Taller \n"); + else + printf("Abnormal height \n"); +} \ No newline at end of file diff --git a/c/_Basic/C Program to Accept two Integers and Check if they are Equal.c b/c/_Basic/C Program to Accept two Integers and Check if they are Equal.c new file mode 100644 index 0000000..5d06c95 --- /dev/null +++ b/c/_Basic/C Program to Accept two Integers and Check if they are Equal.c @@ -0,0 +1,14 @@ +/* + * C program to accept two integers and check if they are equal + */ +#include +void main() +{ + int m, n; + printf("Enter the values for M and N\n"); + scanf("%d %d", &m, &n); + if (m == n) + printf("M and N are equal\n"); + else + printf("M and N are not equal\n"); +} \ No newline at end of file diff --git a/c/_Basic/C Program to Add two Complex Numbers.c b/c/_Basic/C Program to Add two Complex Numbers.c new file mode 100644 index 0000000..ee35c48 --- /dev/null +++ b/c/_Basic/C Program to Add two Complex Numbers.c @@ -0,0 +1,31 @@ +/* + * C Program to Add two Complex Numbers + */ +#include + +struct complex +{ + int realpart, imaginary; +}; + +main() +{ + struct complex a, b, c; + printf("Enter value of a and b complex number a + ib.\n"); + printf("value of complex number a is = "); + scanf("%d", &a.realpart); + printf("value of complex number b is = "); + scanf("%d", &a.imaginary); + printf("Enter value of c and d complex number c + id.\n"); + printf("value of complex number c is = "); + scanf("%d", &b.realpart); + printf("value of complex number d is = "); + scanf("%d", &b.imaginary); + c.realpart = a.realpart + b.realpart; + c.imaginary = a.imaginary + b.imaginary; + if (c.imaginary >= 0) + printf("complex numbers sum is = %d + %di\n", c.realpart, c.imaginary); + else + printf("complex numbers sum = %d %di\n", c.realpart, c.imaginary); + return 0; +} \ No newline at end of file diff --git a/c/_Basic/C Program to Calculate the Sum of Odd & Even Numbers.c b/c/_Basic/C Program to Calculate the Sum of Odd & Even Numbers.c new file mode 100644 index 0000000..4db9d47 --- /dev/null +++ b/c/_Basic/C Program to Calculate the Sum of Odd & Even Numbers.c @@ -0,0 +1,20 @@ +/* + * C program to find the sum of odd and even numbers from 1 to N + */ +#include + +void main() +{ + int i, num, odd_sum = 0, even_sum = 0; + printf("Enter the value of num\n"); + scanf("%d", &num); + for (i = 1; i <= num; i++) + { + if (i % 2 == 0) + even_sum = even_sum + i; + else + odd_sum = odd_sum + i; + } + printf("Sum of all odd numbers = %d\n", odd_sum); + printf("Sum of all even numbers = %d\n", even_sum); +} \ No newline at end of file diff --git a/c/_Basic/C Program to Check if a given Integer is Odd or Even.c b/c/_Basic/C Program to Check if a given Integer is Odd or Even.c new file mode 100644 index 0000000..e48ef5b --- /dev/null +++ b/c/_Basic/C Program to Check if a given Integer is Odd or Even.c @@ -0,0 +1,16 @@ +/* + * C program to check whether a given integer is odd or even + */ +#include + +void main() +{ + int ival, remainder; + printf("Enter an integer : "); + scanf("%d", &ival); + remainder = ival % 2; + if (remainder == 0) + printf("%d is an even integer\n", ival); + else + printf("%d is an odd integer\n", ival); +} \ No newline at end of file diff --git a/c/_Basic/C Program to Check if a given Integer is Positive or Negative.c b/c/_Basic/C Program to Check if a given Integer is Positive or Negative.c new file mode 100644 index 0000000..7c8d8cd --- /dev/null +++ b/c/_Basic/C Program to Check if a given Integer is Positive or Negative.c @@ -0,0 +1,16 @@ +/* + * C program to check whether a given integer is positive + * or negative + */ +#include + +void main() +{ + int number; + printf("Enter a number \n"); + scanf("%d", &number); + if (number >= 0) + printf("%d is a positive number \n", number); + else + printf("%d is a negative number \n", number); +} \ No newline at end of file diff --git a/c/_Basic/C Program to Check whether a given Number is Armstrong.c b/c/_Basic/C Program to Check whether a given Number is Armstrong.c new file mode 100644 index 0000000..30d0649 --- /dev/null +++ b/c/_Basic/C Program to Check whether a given Number is Armstrong.c @@ -0,0 +1,24 @@ +/* + * C Program to Check whether a given Number is Armstrong + */ +#include +#include + +void main() +{ + int number, sum = 0, rem = 0, cube = 0, temp; + printf ("enter a number"); + scanf("%d", &number); + temp = number; + while (number != 0) + { + rem = number % 10; + cube = pow(rem, 3); + sum = sum + cube; + number = number / 10; + } + if (sum == temp) + printf ("The given no is armstrong no"); + else + printf ("The given no is not a armstrong no"); +} \ No newline at end of file diff --git a/c/_Basic/C Program to Check whether a given Number is Perfect Number.c b/c/_Basic/C Program to Check whether a given Number is Perfect Number.c new file mode 100644 index 0000000..491af60 --- /dev/null +++ b/c/_Basic/C Program to Check whether a given Number is Perfect Number.c @@ -0,0 +1,24 @@ +/* + * C Program to Check whether a given Number is Perfect Number + */ +#include + +int main() +{ + int number, rem, sum = 0, i; + printf("Enter a Number\n"); + scanf("%d", &number); + for (i = 1; i <= (number - 1); i++) + { + rem = number % i; + if (rem == 0) + { + sum = sum + i; + } + } + if (sum == number) + printf("Entered Number is perfect number"); + else + printf("Entered Number is not a perfect number"); + return 0; +} \ No newline at end of file diff --git a/c/_Basic/C Program to Check whether the given Number is Palindrome or not using Bitwise Operator.c b/c/_Basic/C Program to Check whether the given Number is Palindrome or not using Bitwise Operator.c new file mode 100644 index 0000000..4b9fe81 --- /dev/null +++ b/c/_Basic/C Program to Check whether the given Number is Palindrome or not using Bitwise Operator.c @@ -0,0 +1,70 @@ +/* +* C Program to Check whether the given Number is Palindrome +* or not using Bitwise Operator +*/ +#include +#include +#define SIZE 8 +/* Function Prototype */ +int is_palindrome(unsigned char[]); + +void main() +{ + int num, num1 = 0, i = 0, j = SIZE - 1, res; + unsigned char c[SIZE]; + printf("Enter a number(max 255)"); + scanf("%d", &num); + num1 = num; + while (num != 0) + { + c[j] = num&1; + j--; + num = num>>1; /* Shifting right the given number by 1 bit */ + } + printf("The number %d in binary is:", num1); + for (i = 0; i < SIZE; i++) + { + printf("%d", c[i]); + } + res = is_palindrome(c); /* Calling Function */ + if (res == 0) + { + printf(" + NUMBER IS PALINDROME + "); + } + else + { + printf(" + NUMBER IS NOT PALINDROME + "); + } +} + +/* Code to check if the number is palindrome or not */ +int is_palindrome(unsigned char c[]) +{ + char temp[SIZE]; + int i, j, flag = 0; + for (i = 0, j = SIZE - 1; i < SIZE, j >= 0; i++, j--) + { + temp[j] = c[i]; + } + for (i = 0; i < SIZE; i++) + { + if (temp[i] != c[i]) + { + flag = 1; + } + } + return flag; +} + + + +Enter a number(max 255)153 +The number 153 in binary is:10011001 +NUMBER IS PALINDROME +Enter a number(max 255)24 +The number 24 in binary is:00011000 +NUMBER IS PALINDROME \ No newline at end of file diff --git a/c/_Basic/C Program to Compute First N Fibonacci Numbers using Command Line Arguments.c b/c/_Basic/C Program to Compute First N Fibonacci Numbers using Command Line Arguments.c new file mode 100644 index 0000000..0c6340b --- /dev/null +++ b/c/_Basic/C Program to Compute First N Fibonacci Numbers using Command Line Arguments.c @@ -0,0 +1,34 @@ +/* + * C Program to Compute First N Fibonacci Numbers using Command Line Arguments + */ +#include + +/* Global Variable Declaration */ +int first = 0; +int second = 1; +int third; +/* Function Prototype */ +void rec_fibonacci(int); + +void main(int argc, char *argv[])/* Command line Arguments*/ +{ + int number = atoi(argv[1]); + printf("%d\t%d", first, second); /* To print first and second number of fibonacci series */ + rec_fibonacci(number); + printf("\n"); +} + +/* Code to print fibonacci series using recursive function */ +void rec_fibonacci(int num) +{ + if (num == 2) /* To exit the function as the first two numbers are already printed */ + { + return; + } + third = first + second; + printf("\t%d", third); + first = second; + second = third; + num--; + rec_fibonacci(num); +} \ No newline at end of file diff --git a/c/_Basic/C Program to Compute the Sum of Digits in a given Integer.c b/c/_Basic/C Program to Compute the Sum of Digits in a given Integer.c new file mode 100644 index 0000000..4c981a3 --- /dev/null +++ b/c/_Basic/C Program to Compute the Sum of Digits in a given Integer.c @@ -0,0 +1,20 @@ +/* + * C program to accept an integer & find the sum of its digits + */ +#include + +void main() +{ + long num, temp, digit, sum = 0; + printf("Enter the number \n"); + scanf("%ld", &num); + temp = num; + while (num > 0) + { + digit = num % 10; + sum = sum + digit; + num /= 10; + } + printf("Given number = %ld\n", temp); + printf("Sum of the digits %ld = %ld\n", temp, sum); +} \ No newline at end of file diff --git a/c/_Basic/C Program to Convert Binary Code of a Number into its Equivalent Gray’s Code using Recursion.c b/c/_Basic/C Program to Convert Binary Code of a Number into its Equivalent Gray’s Code using Recursion.c new file mode 100644 index 0000000..152e79a --- /dev/null +++ b/c/_Basic/C Program to Convert Binary Code of a Number into its Equivalent Gray’s Code using Recursion.c @@ -0,0 +1,40 @@ +/* + * C Program to Convert Binary Code of a Number into its Equivalent + * Gray's Code using Recursion + */ +#include + +int bintogray(int); + +int main () +{ + int bin, gray; + printf("Enter a binary number: "); + scanf("%d", &bin); + gray = bintogray(bin); + printf("The gray code of %d is %d\n", bin, gray); + return 0; +} + +int bintogray(int bin) +{ + int a, b, result = 0, i = 0; + if (!bin) + { + return 0; + } + else + { + a = bin % 10; + bin = bin / 10; + b = bin % 10; + if ((a && !b) || (!a && b)) + { + return (1 + 10 * bintogray(bin)); + } + else + { + return (10 * bintogray(bin)); + } + } +} \ No newline at end of file diff --git a/c/_Basic/C Program to Convert Binary Code of a Number into its Equivalent Gray’s Code without using Recursion.c b/c/_Basic/C Program to Convert Binary Code of a Number into its Equivalent Gray’s Code without using Recursion.c new file mode 100644 index 0000000..020d700 --- /dev/null +++ b/c/_Basic/C Program to Convert Binary Code of a Number into its Equivalent Gray’s Code without using Recursion.c @@ -0,0 +1,35 @@ +/* + * C Program to Convert Binary Code of a Number into its Equivalent + * Gray's Code without using Recursion + */ +#include +#include + +int bintogray(int); + +int main () +{ + int bin, gray; + printf("Enter a binary number: "); + scanf("%d", &bin); + gray = bintogray(bin); + printf("The gray code of %d is %d\n", bin, gray); + return 0; +} + +int bintogray(int bin) +{ + int a, b, result = 0, i = 0; + while (bin != 0) + { + a = bin % 10; + bin = bin / 10; + b = bin % 10; + if ((a && !b) || (!a && b)) + { + result = result + pow(10, i); + } + i++; + } + return result; +} \ No newline at end of file diff --git a/c/_Basic/C Program to Convert Binary to Hexadecimal.c b/c/_Basic/C Program to Convert Binary to Hexadecimal.c new file mode 100644 index 0000000..1b19012 --- /dev/null +++ b/c/_Basic/C Program to Convert Binary to Hexadecimal.c @@ -0,0 +1,20 @@ +/* + * C Program to Convert Binary to Hexadecimal + */ +#include + +int main() +{ + long int binaryval, hexadecimalval = 0, i = 1, remainder; + printf("Enter the binary number: "); + scanf("%ld", &binaryval); + while (binaryval != 0) + { + remainder = binaryval % 10; + hexadecimalval = hexadecimalval + remainder * i; + i = i * 2; + binaryval = binaryval / 10; + } + printf("Equivalent hexadecimal value: %lX", hexadecimalval); + return 0; +} \ No newline at end of file diff --git a/c/_Basic/C Program to Convert Binary to Octal.c b/c/_Basic/C Program to Convert Binary to Octal.c new file mode 100644 index 0000000..6c38d56 --- /dev/null +++ b/c/_Basic/C Program to Convert Binary to Octal.c @@ -0,0 +1,20 @@ +/* + * C Program to Convert Binary to Octal + */ +#include + +int main() +{ + long int binarynum, octalnum = 0, j = 1, remainder; + printf("Enter the value for binary number: "); + scanf("%ld", &binarynum); + while (binarynum != 0) + { + remainder = binarynum % 10; + octalnum = octalnum + remainder * j; + j = j * 2; + binarynum = binarynum / 10; + } + printf("Equivalent octal value: %lo", octalnum); + return 0; +} \ No newline at end of file diff --git a/c/_Basic/C Program to Convert Hexadecimal to Binary.c b/c/_Basic/C Program to Convert Hexadecimal to Binary.c new file mode 100644 index 0000000..890a63d --- /dev/null +++ b/c/_Basic/C Program to Convert Hexadecimal to Binary.c @@ -0,0 +1,91 @@ +/* + * C Program to Convert Hexadecimal to Binary + */ +#include +#define MAX 1000 + +int main() +{ + char binarynum[MAX], hexa[MAX]; + long int i = 0; + printf("Enter the value for hexadecimal "); + scanf("%s", hexa); + printf("\n Equivalent binary value: "); + while (hexa[i]) + { + switch (hexa[i]) + { + case '0': + printf("0000"); + break; + case '1': + printf("0001"); + break; + case '2': + printf("0010"); + break; + case '3': + printf("0011"); + break; + case '4': + printf("0100"); + break; + case '5': + printf("0101"); + break; + case '6': + printf("0110"); + break; + case '7': + printf("0111"); + break; + case '8': + printf("1000"); + break; + case '9': + printf("1001"); + break; + case 'A': + printf("1010"); + break; + case 'B': + printf("1011"); + break; + case 'C': + printf("1100"); + break; + case 'D': + printf("1101"); + break; + case 'E': + printf("1110"); + break; + case 'F': + printf("1111"); + break; + case 'a': + printf("1010"); + break; + case 'b': + printf("1011"); + break; + case 'c': + printf("1100"); + break; + case 'd': + printf("1101"); + break; + case 'e': + printf("1110"); + break; + case 'f': + printf("1111"); + break; + default: + printf("\n Invalid hexa digit %c ", hexa[i]); + return 0; + } + i++; + } + return 0; +} \ No newline at end of file diff --git a/c/_Basic/C Program to Convert Numbers to Roman Numerals.c b/c/_Basic/C Program to Convert Numbers to Roman Numerals.c new file mode 100644 index 0000000..b7f7f4f --- /dev/null +++ b/c/_Basic/C Program to Convert Numbers to Roman Numerals.c @@ -0,0 +1,125 @@ +/* + * C Program to Convert Numbers to Roman Numerals + */ +#include + +void predigit(char num1, char num2); +void postdigit(char c, int n); + +char romanval[1000]; +int i = 0; +int main() +{ + int j; + long number; + printf("Enter the number: "); + scanf("%d", &number); + if (number <= 0) + { + printf("Invalid number"); + return 0; + } + while (number != 0) + { + if (number >= 1000) + { + postdigit('M', number / 1000); + number = number - (number / 1000) * 1000; + } + else if (number >= 500) + { + if (number < (500 + 4 * 100)) + { + postdigit('D', number / 500); + number = number - (number / 500) * 500; + } + else + { + predigit('C','M'); + number = number - (1000-100); + } + } + else if (number >= 100) + { + if (number < (100 + 3 * 100)) + { + postdigit('C', number / 100); + number = number - (number / 100) * 100; + } + else + { + predigit('L', 'D'); + number = number - (500 - 100); + } + } + else if (number >= 50 ) + { + if (number < (50 + 4 * 10)) + { + postdigit('L', number / 50); + number = number - (number / 50) * 50; + } + else + { + predigit('X','C'); + number = number - (100-10); + } + } + else if (number >= 10) + { + if (number < (10 + 3 * 10)) + { + postdigit('X', number / 10); + number = number - (number / 10) * 10; + } + else + { + predigit('X','L'); + number = number - (50 - 10); + } + } + else if (number >= 5) + { + if (number < (5 + 4 * 1)) + { + postdigit('V', number / 5); + number = number - (number / 5) * 5; + } + else + { + predigit('I', 'X'); + number = number - (10 - 1); + } + } + else if (number >= 1) + { + if (number < 4) + { + postdigit('I', number / 1); + number = number - (number / 1) * 1; + } + else + { + predigit('I', 'V'); + number = number - (5 - 1); + } + } + } + printf("Roman number is: "); + for(j = 0; j < i; j++) + printf("%c", romanval[j]); + return 0; +} + +void predigit(char num1, char num2) +{ + romanval[i++] = num1; + romanval[i++] = num2; +} + +void postdigit(char c, int n) +{ + int j; + for (j = 0; j < n; j++) + romanval[i++] = c; +} \ No newline at end of file diff --git a/c/_Basic/C Program to Convert Octal to Binary.c b/c/_Basic/C Program to Convert Octal to Binary.c new file mode 100644 index 0000000..2894f21 --- /dev/null +++ b/c/_Basic/C Program to Convert Octal to Binary.c @@ -0,0 +1,49 @@ +/* + * C Program to Convert Octal to Binary + */ +#include +#define MAX 1000 + +int main() +{ + char octalnum[MAX]; + long i = 0; + printf("Enter any octal number: "); + scanf("%s", octalnum); + printf("Equivalent binary value: "); + while (octalnum[i]) + { + switch (octalnum[i]) + { + case '0': + printf("000"); + break; + case '1': + printf("001"); + break; + case '2': + printf("010"); + break; + case '3': + printf("011"); + break; + case '4': + printf("100"); + break; + case '5': + printf("101"); + break; + case '6': + printf("110"); + break; + case '7': + printf("111"); + break; + default: + printf("\n Invalid octal digit %c ", octalnum[i]); + return 0; + } + i++; + } + return 0; +} \ No newline at end of file diff --git a/c/_Basic/C Program to Convert Octal to Decimal.c b/c/_Basic/C Program to Convert Octal to Decimal.c new file mode 100644 index 0000000..a9da073 --- /dev/null +++ b/c/_Basic/C Program to Convert Octal to Decimal.c @@ -0,0 +1,20 @@ +/* + * C Program to Convert Octal to Decimal + */ +#include +#include + +int main() +{ + long int octal, decimal = 0; + int i = 0; + printf("Enter any octal number: "); + scanf("%ld", &octal); + while (octal != 0) + { + decimal = decimal +(octal % 10)* pow(8, i++); + octal = octal / 10; + } + printf("Equivalent decimal value: %ld",decimal); + return 0; +} diff --git a/c/_Basic/C Program to Convert Roman Number to Decimal Number.c b/c/_Basic/C Program to Convert Roman Number to Decimal Number.c new file mode 100644 index 0000000..3c942e8 --- /dev/null +++ b/c/_Basic/C Program to Convert Roman Number to Decimal Number.c @@ -0,0 +1,66 @@ +/* + * C Program to Convert Roman Number to Decimal Number + */ +#include +#include + +int digit(char); + +int main() +{ + char romanval[1000]; + int i = 0; + long int number = 0; + printf("Enter roman num (Valid digits are I, V, X, L, C, D, M):\n"); + scanf("%s", romanval); + while (romanval[i]) + { + if (digit(romanval[i]) 2) + { + if (digit(romanval[i]) = digit(romanval[i+1])) + number = number + digit(romanval[i]); + else + { + number = number + (digit(romanval[i + 1]) - + digit(romanval[i])); + i++; + } + i++; + } + printf("Its decimal value is : %ld", number); + return 0; + } + int digit(char c) + { + int value = 0; + switch (c) + { + case 'I': + value = 1; + break; + case 'V': + value = 5; + break; + case 'X': + value = 10; + break; + case 'L': + value = 50; + break; + case 'C': + value = 100; + break; + case 'D': + value = 500; + break; + case 'M': + value = 1000; + break; + case '0': + value = 0; + break; + default: + value = -1; + } + return value; + } \ No newline at end of file diff --git a/c/_Basic/C Program to Convert a Decimal Number to Binary & Count the Number of 1s.c b/c/_Basic/C Program to Convert a Decimal Number to Binary & Count the Number of 1s.c new file mode 100644 index 0000000..c595704 --- /dev/null +++ b/c/_Basic/C Program to Convert a Decimal Number to Binary & Count the Number of 1s.c @@ -0,0 +1,28 @@ +/* + * C program to accept a decimal number and convert it to binary + * and count the number of 1's in the binary number + */ +#include + +void main() +{ + long num, decimal_num, remainder, base = 1, binary = 0, no_of_1s = 0; + printf("Enter a decimal integer \n"); + scanf("%ld", &num); + decimal_num = num; + while (num > 0) + { + remainder = num % 2; + /* To count no.of 1s */ + if (remainder == 1) + { + no_of_1s++; + } + binary = binary + remainder * base; + num = num / 2; + base = base * 10; + } + printf("Input number is = %d\n", decimal_num); + printf("Its binary equivalent is = %ld\n", binary); + printf("No.of 1's in the binary number is = %d\n", no_of_1s); +} \ No newline at end of file diff --git a/c/_Basic/C Program to Convert a Given Number of Days in terms of Years, Weeks & Days.c b/c/_Basic/C Program to Convert a Given Number of Days in terms of Years, Weeks & Days.c new file mode 100644 index 0000000..7eac27f --- /dev/null +++ b/c/_Basic/C Program to Convert a Given Number of Days in terms of Years, Weeks & Days.c @@ -0,0 +1,19 @@ +/* + * C program to convert given number of days to a measure of time given + * in years, weeks and days. For example 375 days is equal to 1 year + * 1 week and 3 days (ignore leap year) + */ +#include +#define DAYSINWEEK 7 + +void main() +{ + int ndays, year, week, days; + printf("Enter the number of daysn"); + scanf("%d", &ndays); + year = ndays / 365; + week =(ndays % 365) / DAYSINWEEK; + days =(ndays % 365) % DAYSINWEEK; + printf ("%d is equivalent to %d years, %d weeks and %d daysn", + ndays, year, week, days); +} \ No newline at end of file diff --git a/c/_Basic/C Program to Convert a Number Decimal System to Binary System using Recursion.c b/c/_Basic/C Program to Convert a Number Decimal System to Binary System using Recursion.c new file mode 100644 index 0000000..3301a55 --- /dev/null +++ b/c/_Basic/C Program to Convert a Number Decimal System to Binary System using Recursion.c @@ -0,0 +1,28 @@ +/* + * C Program to Convert a Number Decimal System to Binary System using Recursion + */ +#include + +int convert(int); + +int main() +{ + int dec, bin; + printf("Enter a decimal number: "); + scanf("%d", &dec); + bin = convert(dec); + printf("The binary equivalent of %d is %d.\n", dec, bin); + return 0; +} + +int convert(int dec) +{ + if (dec == 0) + { + return 0; + } + else + { + return (dec % 2 + 10 * convert(dec / 2)); + } +} \ No newline at end of file diff --git a/c/_Basic/C Program to Convert the given Binary Number into Decimal.c b/c/_Basic/C Program to Convert the given Binary Number into Decimal.c new file mode 100644 index 0000000..866c02d --- /dev/null +++ b/c/_Basic/C Program to Convert the given Binary Number into Decimal.c @@ -0,0 +1,21 @@ +/* + * C program to convert the given binary number into decimal + */ +#include + +void main() +{ + int num, binary_val, decimal_val = 0, base = 1, rem; + printf("Enter a binary number(1s and 0s) \n"); + scanf("%d", &num); /* maximum five digits */ + binary_val = num; + while (num > 0) + { + rem = num % 10; + decimal_val = decimal_val + rem * base; + num = num / 10 ; + base = base * 2; + } + printf("The Binary number is = %d \n", binary_val); + printf("Its decimal equivalent is = %d \n", decimal_val); +} \ No newline at end of file diff --git a/c/_Basic/C Program to Count Number of Words in a given Text Or Sentence.c b/c/_Basic/C Program to Count Number of Words in a given Text Or Sentence.c new file mode 100644 index 0000000..9bd05de --- /dev/null +++ b/c/_Basic/C Program to Count Number of Words in a given Text Or Sentence.c @@ -0,0 +1,27 @@ +/* +* C Program to Count Number of Words in a given Text Or Sentence +*/ +#include +#include + +void main() +{ + char s[200]; + int count = 0, i; + printf("enter the string + "); + scanf("%[^ + ]s", s); + for (i = 0; s[i] != ''; i++) + { + if (s[i] == ' ') + count++; + } + printf("number of words in given string are: %d + ", count + 1); +} + + +enter the string +welcome to illuminate's c-programming app! +number of words in given string are: 5 \ No newline at end of file diff --git a/c/_Basic/C Program to Count the Number of Occurrence of each Character Ignoring the Case of Alphabets & Display them.c b/c/_Basic/C Program to Count the Number of Occurrence of each Character Ignoring the Case of Alphabets & Display them.c new file mode 100644 index 0000000..9c729d9 --- /dev/null +++ b/c/_Basic/C Program to Count the Number of Occurrence of each Character Ignoring the Case of Alphabets & Display them.c @@ -0,0 +1,86 @@ +/* +* C Program to Count the Number of Occurrence of +* each Character Ignoring the Case of Alphabets +* & Display them +*/ +#include +#include +#include + +struct detail +{ + char c; + int freq; +}; +int main() +{ + struct detail s[26]; + char string[100], c; + int i = 0, index; + for (i = 0; i < 26; i++) + { + s[i].c = i + 'a'; + s[i].freq = 0; + } + printf("Enter string: "); + i = 0; + do + { + fflush(stdin); + c = getchar(); + string[i++] = c; + if (c == ' + ') + { + break; + } + c = tolower(c); + index = c - 'a'; + s[index].freq++; + } +while (1); + string[i - 1] = ''; + printf("The string entered is: %s + ", string); + printf("************************* + Character Frequency + ************************* + "); + for (i = 0; i < 26; i++) + { + if (s[i].freq) + { + printf(" %c %d + ", s[i].c, s[i].freq); + } + } + return + 0; +} + + +Enter string: +A quIck brOwn fox JumpEd over a lazy dOg +The string entered is: +A quIck brOwn fox JumpEd over a lazy dOg +************************* +Character Frequency +********************* +a 3 +b 1 +c 1 +d 2 +e 2 +f 1 +g 1 +i 1 +j 1 +k 1 +l 1 +m 1 +n 1 +o 4 +p 1 +q 1 +r 2 +u 2 v 1 w 1 x 1 y 1 z 1 \ No newline at end of file diff --git a/c/_Basic/C Program to Count the Number of Unique Words.c b/c/_Basic/C Program to Count the Number of Unique Words.c new file mode 100644 index 0000000..aaf0ba5 --- /dev/null +++ b/c/_Basic/C Program to Count the Number of Unique Words.c @@ -0,0 +1,65 @@ +/* +* C Program to Count the Number of Unique Words +*/ +#include +#include +#include +int main() +{ + int i = 0, e, j, d, k, space = 0; + char a[50], b[15][20], c[15][20]; + printf("Read a string: + "); + fflush(stdin); + scanf("%[^ + ]s", a); + for (i = 0; a[i] != ''; i++) //loop to count no of words + { + if (a[i] = = ' ') + space++; + } + i = 0; + for (j = 0; j<(space + 1); i++, j++) //loop to store each word into an 2D array + { + k = 0; + while (a[i] != '') + { + if (a[i] == ' ') + { + break; + } + else + { + b[j][k++] = a[i]; + i++; + } + } + b[j][k] = ''; + } + i = 0; + strcpy(c[i], b[i]); + for (e = 1; e <= j; e++) //loop to check whether the string is already present in the 2D array or not + { + for (d = 0; d <= i; d++) + { + if (strcmp(c[i], b[e]) == 0) + break; + else + { + i++; + strcpy(c[i], b[e]); + break; + } + } + } + printf(" + Number of unique words in %s are:%d", a, i); + return 0; +} + + +Read a string: +Welcome to Illuminate's C-programming class, Welcome again to C class! +The length of input string is:70 + +Number of unique words in Welcome to ILLuminate's C-programming class, Welcome again to C class! are:12 \ No newline at end of file diff --git a/c/_Basic/C Program to Count the Occurrences of each C Keyword using Array Structure.c b/c/_Basic/C Program to Count the Occurrences of each C Keyword using Array Structure.c new file mode 100644 index 0000000..dc4f61b --- /dev/null +++ b/c/_Basic/C Program to Count the Occurrences of each C Keyword using Array Structure.c @@ -0,0 +1,104 @@ +/* +* C Program to Count the Occurrences of each C Keyword +* using Array Structure +*/ +#include +#include +#include +#define KEYMAX 32 + +struct keyword +{ + char word[10]; + int occur; +}; + +int binarysearch(char [], struct keyword[]); + +int main() +{ + int i = 0, j = 0, pos; + char string[100], unit[20], c; + struct keyword key[32] = {"auto", 0, "break", 0, "case", 0, + "char", 0, "const", 0, "continue", 0, + "default", 0, "do", 0, "double", 0, + "else", 0, "enum", 0, "extern", 0, + "float", 0, "for", 0, "goto", 0, + "if", 0, "int", 0, "long", 0, + "register", 0, "return", 0, "short", 0, + "signed", 0, "sizeof", 0, "static", 0, + "struct", 0, "switch", 0, "typedef", 0, + "union", 0, "unsigned", 0, "void", 0, + "volatile", 0, "while", 0, + }; + printf("Enter string: "); + do + { + fflush(stdin); + c = getchar(); + string[i++] = c; + } + while (c != ' + '); + string[i - 1] = ''; + printf("The string entered is: %s + ", string); + for (i = 0; i < strlen(string); i++) + { + while (i < strlen(string) && string[i] != ' ' && isalpha(string[i])) + { + unit[j++] = tolower(string[i++]); + } + if (j != 0) + { + unit[j] = ''; + pos = binarysearch(unit, key); + j = 0; + if (pos != -1) + { + key[pos].occur++; + } + } + } + printf("*********************** + Keyword Count + *********************** + "); + for (i = 0; i < KEYMAX; i++) + { + if (key[i].occur) + { + printf(" %s %d + ", key[i].word, key[i].occur); } + } + return 0; + } + int binarysearch(char *word, struct keyword key[]) + { + int low, high, mid; + low = 0; + high = KEYMAX - 1; + while (low <= high) + { + mid = (low + high) / 2; + if (strcmp(word, key[mid].word) < 0) + { + high = mid - 1; + } + else if (strcmp(word, key[mid].word) > 0) + { + low = mid + 1; + } + else + { + return mid; + } + } + return -1; + } + Enter string: break, float and double are c keywords. float and double are primitive data types. The string entered is: break, float and double are c keywords. float and double are primitive data types. *********************** + Keyword Count + *********************** + break 1 + double 2 + float 2 \ No newline at end of file diff --git a/c/_Basic/C Program to Display Function without using the Main Function.c b/c/_Basic/C Program to Display Function without using the Main Function.c new file mode 100644 index 0000000..341a41b --- /dev/null +++ b/c/_Basic/C Program to Display Function without using the Main Function.c @@ -0,0 +1,11 @@ +/* + * C Program to display function without using the Main Function + */ +#include +#define decode(s,t,u,m,p,e,d) m##s##u##t +#define begin decode(a,n,i,m,a,t,e) + +int begin() +{ + printf(" helloworld "); +} \ No newline at end of file diff --git a/c/_Basic/C Program to Display its own Source Code as its Output.c b/c/_Basic/C Program to Display its own Source Code as its Output.c new file mode 100644 index 0000000..3761ab8 --- /dev/null +++ b/c/_Basic/C Program to Display its own Source Code as its Output.c @@ -0,0 +1,19 @@ +/* + * C Program to Display its own Source Code as its Output + */ +#include + +int main() +{ + FILE *fp; + char ch; + fp = fopen(__FILE__,"r"); + do + { + ch = getc(fp); + putchar(ch); + } + while (ch != EOF); + fclose(fp); + return 0; +} \ No newline at end of file diff --git a/c/_Basic/C Program to Display the ATM Transaction.c b/c/_Basic/C Program to Display the ATM Transaction.c new file mode 100644 index 0000000..5bf2c56 --- /dev/null +++ b/c/_Basic/C Program to Display the ATM Transaction.c @@ -0,0 +1,72 @@ +/* + * C Program to Display the ATM Transaction + */ +#include + +unsigned long amount=1000, deposit, withdraw; +int choice, pin, k; +char transaction ='y'; + +void main() +{ + while (pin != 1520) + { + printf("ENTER YOUR SECRET PIN NUMBER:"); + scanf("%d", &pin); + if (pin != 1520) + printf("PLEASE ENTER VALID PASSWORD\n"); + } + do + { + printf("********Welcome to ATM Service**************\n"); + printf("1. Check Balance\n"); + printf("2. Withdraw Cash\n"); + printf("3. Deposit Cash\n"); + printf("4. Quit\n"); + printf("******************?**************************?*\n\n"); + printf("Enter your choice: "); + scanf("%d", &choice); + switch (choice) + { + case 1: + printf("\n YOUR BALANCE IN Rs : %lu ", amount); + break; + case 2: + printf("\n ENTER THE AMOUNT TO WITHDRAW: "); + scanf("%lu", &withdraw); + if (withdraw % 100 != 0) + { + printf("\n PLEASE ENTER THE AMOUNT IN MULTIPLES OF 100"); + } + else if (withdraw >(amount - 500)) + { + printf("\n INSUFFICENT BALANCE"); + } + else + { + amount = amount - withdraw; + printf("\n\n PLEASE COLLECT CASH"); + printf("\n YOUR CURRENT BALANCE IS%lu", amount); + } + break; + case 3: + printf("\n ENTER THE AMOUNT TO DEPOSIT"); + scanf("%lu", &deposit); + amount = amount + deposit; + printf("YOUR BALANCE IS %lu", amount); + break; + case 4: + printf("\n THANK U USING ATM"); + break; + default: + printf("\n INVALID CHOICE"); + } + printf("\n\n\n DO U WISH TO HAVE ANOTHER TRANSCATION?(y/n): \n"); + fflush(stdin); + scanf("%c", &transaction); + if (transaction == 'n'|| transaction == 'N') + k = 1; + } + while (!k); + printf("\n\n THANKS FOR USING OUT ATM SERVICE"); +} \ No newline at end of file diff --git a/c/_Basic/C Program to Display the IP Address of the System.c b/c/_Basic/C Program to Display the IP Address of the System.c new file mode 100644 index 0000000..cd17094 --- /dev/null +++ b/c/_Basic/C Program to Display the IP Address of the System.c @@ -0,0 +1,29 @@ +/* + * C Program to Get IP Address + */ +#include +#include +#include +#include +#include +#include +#include +#include +#include + +int main() +{ + int n; + struct ifreq ifr; + char array[] = "eth0"; + n = socket(AF_INET, SOCK_DGRAM, 0); + //Type of address to retrieve - IPv4 IP address + ifr.ifr_addr.sa_family = AF_INET; + //Copy the interface name in the ifreq structure + strncpy(ifr.ifr_name, array, IFNAMSIZ - 1); + ioctl(n, SIOCGIFADDR, &ifr); + close(n); + //display result + printf("IP Address is %s - %s\n", array, inet_ntoa(( (struct sockaddr_in *)&ifr.ifr_addr )->sin_addr) ); + return 0; +} \ No newline at end of file diff --git a/c/_Basic/C Program to Display the Inventory of Items in a Store.c b/c/_Basic/C Program to Display the Inventory of Items in a Store.c new file mode 100644 index 0000000..2743de2 --- /dev/null +++ b/c/_Basic/C Program to Display the Inventory of Items in a Store.c @@ -0,0 +1,62 @@ +/* + * C program to display the inventory of items in a store / shop + * The inventory maintains details such as name, price, quantity + * and manufacturing date of each item. + */ +#include + +void main() +{ + struct date + { + int day; + int month; + int year; + }; + struct details + { + char name[20]; + int price; + int code; + int qty; + struct date mfg; + }; + struct details item[50]; + int n, i; + printf("Enter number of items:"); + scanf("%d", &n); + fflush(stdin); + for (i = 0; i < n; i++) + { + fflush(stdin); + printf("Item name: \n"); + scanf("%s", item[i].name); + fflush(stdin); + printf("Item code: \n"); + scanf("%d", &item[i].code); + fflush(stdin); + printf("Quantity: \n"); + scanf("%d", &item[i].qty); + fflush(stdin); + printf("price: \n"); + scanf("%d", &item[i].price); + fflush(stdin); + printf("Manufacturing date(dd-mm-yyyy): \n"); + scanf("%d-%d-%d", &item[i].mfg.day, + &item[i].mfg.month, &item[i].mfg.year); + } + printf(" ***** INVENTORY ***** \n"); + printf("--------------------------------------------------------- + ---------\n"); + printf("S.N.| NAME | CODE | QUANTITY | PRICE + | MFG.DATE \n"); + printf("--------------------------------------------------------- + ---------\n"); + for (i = 0; i < n; i++) + printf("%d %-15s %-d %-5d %-5d + %d/%d/%d \n", i + 1, item[i].name, item[i].code, item[i].qty, + item[i].price, item[i].mfg.day, item[i].mfg.month, + item[i].mfg.year); + printf("--------------------------------------------------------- + ---------\n"); +} \ No newline at end of file diff --git a/c/_Basic/C Program to Extract Last two Digits of a given Year.c b/c/_Basic/C Program to Extract Last two Digits of a given Year.c new file mode 100644 index 0000000..264433f --- /dev/null +++ b/c/_Basic/C Program to Extract Last two Digits of a given Year.c @@ -0,0 +1,14 @@ +/* + * C Program to Extract Last two Digits of a given Year + */ +#include + +int main() +{ + int year, yr; + printf("Enter the year "); + scanf("%d", &year); + yr = year % 100; + printf("Last two digits of year is: %02d", yr); + return 0; +} \ No newline at end of file diff --git a/c/_Basic/C Program to Find Multiplication of two Binary Numbers.c b/c/_Basic/C Program to Find Multiplication of two Binary Numbers.c new file mode 100644 index 0000000..ee3c77e --- /dev/null +++ b/c/_Basic/C Program to Find Multiplication of two Binary Numbers.c @@ -0,0 +1,50 @@ +/* + * C Program to Find Multiplication of two Binary Numbers + */ +#include + +int binaryproduct(int, int); + +int main() +{ + long binary1, binary2, multiply = 0; + int digit, factor = 1; + printf("Enter the first binary number: "); + scanf("%ld", &binary1); + printf("Enter the second binary number: "); + scanf("%ld", &binary2); + while (binary2 != 0) + { + digit = binary2 % 10; + if (digit == 1) + { + binary1 = binary1 * factor; + multiply = binaryproduct(binary1, multiply); + } + else + binary1 = binary1 * factor; + binary2 = binary2 / 10; + factor = 10; + } + printf("Product of two binary numbers: %ld", multiply); + return 0; +} + +int binaryproduct(int binary1, int binary2) +{ + int i = 0, remainder = 0, sum[20]; + int binaryprod = 0; + while (binary1 != 0 || binary2 != 0) + { + sum[i++] =(binary1 % 10 + binary2 % 10 + remainder) % 2; + remainder =(binary1 % 10 + binary2 % 10 + remainder) / 2; + binary1 = binary1 / 10; + binary2 = binary2 / 10; + } + if (remainder != 0) + sum[i++] = remainder; + --i; + while (i >= 0) + binaryprod = binaryprod * 10 + sum[i--]; + return binaryprod; +} \ No newline at end of file diff --git a/c/_Basic/C Program to Find Product of 2 Numbers without using Recursion.c b/c/_Basic/C Program to Find Product of 2 Numbers without using Recursion.c new file mode 100644 index 0000000..dbfc6c0 --- /dev/null +++ b/c/_Basic/C Program to Find Product of 2 Numbers without using Recursion.c @@ -0,0 +1,28 @@ +/* + * C Program to find Product of 2 Numbers without using Recursion + */ + +#include + +int product(int, int); + +int main() +{ + int a, b, result; + printf("Enter two numbers to find their product: "); + scanf("%d%d", &a, &b); + result = product(a, b); + printf("Product of %d and %d is %d\n", a, b, result); + return 0; +} + +int product(int a, int b) +{ + int temp = 0; + while (b != 0) + { + temp += a; + b--; + } + return temp; +} \ No newline at end of file diff --git a/c/_Basic/C Program to Find Sum of Digits of a Number using Recursion.c b/c/_Basic/C Program to Find Sum of Digits of a Number using Recursion.c new file mode 100644 index 0000000..69b3469 --- /dev/null +++ b/c/_Basic/C Program to Find Sum of Digits of a Number using Recursion.c @@ -0,0 +1,28 @@ +/* + * C Program to find Sum of Digits of a Number using Recursion + */ +#include + +int sum (int a); + +int main() +{ + int num, result; + printf("Enter the number: "); + scanf("%d", &num); + result = sum(num); + printf("Sum of digits in %d is %d\n", num, result); + return 0; +} + +int sum (int num) +{ + if (num != 0) + { + return (num % 10 + sum (num / 10)); + } + else + { + return 0; + } +} \ No newline at end of file diff --git a/c/_Basic/C Program to Find if a given Year is a Leap Year.c b/c/_Basic/C Program to Find if a given Year is a Leap Year.c new file mode 100644 index 0000000..ca70afa --- /dev/null +++ b/c/_Basic/C Program to Find if a given Year is a Leap Year.c @@ -0,0 +1,17 @@ +/* + * C program to find whether a given year is leap year or not + */ +void main() +{ + int year; + printf("Enter a year \n"); + scanf("%d", &year); + if ((year % 400) == 0) + printf("%d is a leap year \n", year); + else if ((year % 100) == 0) + printf("%d is a not leap year \n", year); + else if ((year % 4) == 0) + printf("%d is a leap year \n", year); + else + printf("%d is not a leap year \n", year); +} \ No newline at end of file diff --git a/c/_Basic/C Program to Find the Biggest of 3 Numbers.c b/c/_Basic/C Program to Find the Biggest of 3 Numbers.c new file mode 100644 index 0000000..ae98224 --- /dev/null +++ b/c/_Basic/C Program to Find the Biggest of 3 Numbers.c @@ -0,0 +1,27 @@ +/* + * C program to find the biggest of three numbers + */ +#include + +void main() +{ + int num1, num2, num3; + printf("Enter the values of num1, num2 and num3\n"); + scanf("%d %d %d", &num1, &num2, &num3); + printf("num1 = %d\tnum2 = %d\tnum3 = %d\n", num1, num2, num3); + if (num1 > num2) + { + if (num1 > num3) + { + printf("num1 is the greatest among three \n"); + } + else + { + printf("num3 is the greatest among three \n"); + } + } + else if (num2 > num3) + printf("num2 is the greatest among three \n"); + else + printf("num3 is the greatest among three \n"); +} \ No newline at end of file diff --git a/c/_Basic/C Program to Find the First Occurence of the any Character of String2 in string1 & also its Position.c b/c/_Basic/C Program to Find the First Occurence of the any Character of String2 in string1 & also its Position.c new file mode 100644 index 0000000..1f35305 --- /dev/null +++ b/c/_Basic/C Program to Find the First Occurence of the any Character of String2 in string1 & also its Position.c @@ -0,0 +1,51 @@ +/* +/* +* C Program to Find the First Occurence of the any Character of +* String2 in string1 & also its Position +*/ +#include + +void main() +{ + char s1[50], s2[10]; + int i, flag = 0; + char *ptr1, *ptr2; + printf(" + enter the string1:"); + scanf(" %[^ + ]s", s1); + printf(" + enter the string2:"); + scanf(" %[^ + ]s", s2); + /*COMPARING THE STRING1 CHARACTER BY CHARACTER WITH ALL CHARACTERS OF STRING1*/ + for (i = 0, ptr1 = s1; *ptr1 != ''; ptr1++) + { + i++; + for (ptr2 = s2; *ptr2 != ''; ptr2++) + { + if (*ptr1 == *ptr2) + { + flag = 1; + break; + } + } + if (flag == 1) + break; + } + if (flag == 1) + printf(" + first occurance of character of string2 in string1 is at position:%d and character is %c", i, *ptr2); + else + printf(" + none of the characters of string1 match with mone of characters of string2"); + } + + + enter the string1: + C Programming Class + + enter the string2: + rnp + + first occurance of character of string2 in string1 is at position:3 and character is p \ No newline at end of file diff --git a/c/_Basic/C Program to Find the Number of Integers Divisible by 5.c b/c/_Basic/C Program to Find the Number of Integers Divisible by 5.c new file mode 100644 index 0000000..fb186f5 --- /dev/null +++ b/c/_Basic/C Program to Find the Number of Integers Divisible by 5.c @@ -0,0 +1,29 @@ +/* + * C program to find the number of integers divisible by + * 5 between the given range num1 and num2, where num1 < num2. + * + * Also find the sum of all these integer numbers which are divisible + * by 5 and display the total. + */ +#include + +void main() +{ + int i, num1, num2, count = 0, sum = 0; + printf("Enter the value of num1 and num2 \n"); + scanf("%d %d", &num1, &num2); + /* Count the number and compute their sum*/ + printf("Integers divisible by 5 are \n"); + for (i = num1; i < num2; i++) + { + if (i % 5 == 0) + { + printf("%3d,", i); + count++; + sum = sum + i; + } + } + printf("\n Number of integers divisible by 5 between %d and %d = + %d\n", num1, num2, count); + printf("Sum of all integers that are divisible by 5 = %d\n", sum); +} \ No newline at end of file diff --git a/c/_Basic/C Program to Find the Size of a Union.c b/c/_Basic/C Program to Find the Size of a Union.c new file mode 100644 index 0000000..c7b8b4e --- /dev/null +++ b/c/_Basic/C Program to Find the Size of a Union.c @@ -0,0 +1,23 @@ +/* + * C program to find the size of a union + */ +#include + +void main() +{ + union sample + { + int m; + float n; + char ch; + }; + union sample u; + printf("The size of union = %d\n", sizeof(u)); + /* initialization */ + u.m = 25; + printf("%d %f %c\n", u.m, u.n, u.ch); + u.n = 0.2; + printf("%d %f %c\n", u.m, u.n, u.ch); + u.ch = 'p'; + printf("%d %f %c\n", u.m, u.n, u.ch); +} \ No newline at end of file diff --git a/c/_Basic/C Program to Find the Sum of first 50 Natural Numbers using For Loop.c b/c/_Basic/C Program to Find the Sum of first 50 Natural Numbers using For Loop.c new file mode 100644 index 0000000..90405f7 --- /dev/null +++ b/c/_Basic/C Program to Find the Sum of first 50 Natural Numbers using For Loop.c @@ -0,0 +1,15 @@ +/* + * C program to find the sum of first 50 natural numbers + * using for loop + */ +#include + +void main() +{ + int num, sum = 0; + for (num = 1; num <= 50; num++) + { + sum = sum + num; + } + printf("Sum = %4d\n", sum); +} \ No newline at end of file diff --git a/c/_Basic/C Program to Find the Sum of two Binary Numbers.c b/c/_Basic/C Program to Find the Sum of two Binary Numbers.c new file mode 100644 index 0000000..b21c4f3 --- /dev/null +++ b/c/_Basic/C Program to Find the Sum of two Binary Numbers.c @@ -0,0 +1,28 @@ +/* + * C Program to Find the Sum of two Binary Numbers + */ +#include + +int main() +{ + long binary1, binary2; + int i = 0, remainder = 0, sum[20]; + printf("Enter the first binary number: "); + scanf("%ld", &binary1); + printf("Enter the second binary number: "); + scanf("%ld", &binary2); + while (binary1 != 0 || binary2 != 0) + { + sum[i++] =(binary1 % 10 + binary2 % 10 + remainder) % 2; + remainder =(binary1 % 10 + binary2 % 10 + remainder) / 2; + binary1 = binary1 / 10; + binary2 = binary2 / 10; + } + if (remainder != 0) + sum[i++] = remainder; + --i; + printf("Sum of two binary numbers: "); + while (i >= 0) + printf("%d", sum[i--]); + return 0; +} \ No newline at end of file diff --git a/c/_Basic/C Program to Find whether a Number is Prime or Not using Recursion.c b/c/_Basic/C Program to Find whether a Number is Prime or Not using Recursion.c new file mode 100644 index 0000000..42f2d56 --- /dev/null +++ b/c/_Basic/C Program to Find whether a Number is Prime or Not using Recursion.c @@ -0,0 +1,42 @@ +/* + * C Program to find whether a Number is Prime or Not using Recursion + */ +#include + +int primeno(int, int); + +int main() +{ + int num, check; + printf("Enter a number: "); + scanf("%d", &num); + check = primeno(num, num / 2); + if (check == 1) + { + printf("%d is a prime number\n", num); + } + else + { + printf("%d is not a prime number\n", num); + } + return 0; +} + +int primeno(int num, int i) +{ + if (i == 1) + { + return 1; + } + else + { + if (num % i == 0) + { + return 0; + } + else + { + return primeno(num, i - 1); + } + } +} \ No newline at end of file diff --git a/c/_Basic/C Program to Generate Fibonacci Series.c b/c/_Basic/C Program to Generate Fibonacci Series.c new file mode 100644 index 0000000..4a41836 --- /dev/null +++ b/c/_Basic/C Program to Generate Fibonacci Series.c @@ -0,0 +1,24 @@ +/* + * C program to generate Fibonacci Series. Fibonacci Series + * is 0 1 1 2 3 5 8 13 21 ... + */ +#include + +void main() +{ + int fib1 = 0, fib2 = 1, fib3, limit, count = 0; + printf("Enter the limit to generate the Fibonacci Series \n"); + scanf("%d", &limit); + printf("Fibonacci Series is ...\n"); + printf("%d\n", fib1); + printf("%d\n", fib2); + count = 2; + while (count < limit) + { + fib3 = fib1 + fib2; + count++; + printf("%d\n", fib3); + fib1 = fib2; + fib2 = fib3; + } +} \ No newline at end of file diff --git a/c/_Basic/C Program to Illustrate Pass by Reference.c b/c/_Basic/C Program to Illustrate Pass by Reference.c new file mode 100644 index 0000000..9606030 --- /dev/null +++ b/c/_Basic/C Program to Illustrate Pass by Reference.c @@ -0,0 +1,19 @@ +/* + * C Program to Illustrate Pass by Reference + */ +#include + +void cube( int *x); + +int main() +{ + int num = 10; + cube(&num); + printf("the cube of the given number is %d", num); + return 0; +} + +void cube(int *x) +{ + *x = (*x) * (*x) * (*x); +} \ No newline at end of file diff --git a/c/_Basic/C Program to Illustrate Pass by Value.c b/c/_Basic/C Program to Illustrate Pass by Value.c new file mode 100644 index 0000000..943bc16 --- /dev/null +++ b/c/_Basic/C Program to Illustrate Pass by Value.c @@ -0,0 +1,21 @@ +/* + * C Program to Illustrate Pass by Value. + */ +#include + +void swap(int a, int b) +{ + int temp; + temp = a; + a = b; + b = temp; +} + +int main() +{ + int num1 = 10, num2 = 20; + printf("Before swapping num1 = %d num2 = %d\n", num1, num2); + swap(num1, num2); + printf("After swapping num1 = %d num2 = %d \n", num2, num1); + return 0; +} \ No newline at end of file diff --git a/c/_Basic/C Program to Illustrate how User Authentication is Done.c b/c/_Basic/C Program to Illustrate how User Authentication is Done.c new file mode 100644 index 0000000..a860cb5 --- /dev/null +++ b/c/_Basic/C Program to Illustrate how User Authentication is Done.c @@ -0,0 +1,29 @@ +/* + * C program is to illustrate how user authentication is done. + * Program asks for the user name and password and displays + * the password as '*' character + */ +#include + +void main() +{ + char password[10], username[10], ch; + int i; + printf("Enter User name: "); + gets(username); + printf("Enter the password < any 8 characters>: "); + for (i = 0; i < 8; i++) + { + ch = getchar(); + password[i] = ch; + ch = '*' ; + printf("%c", ch); + } + password[i] = '\0'; + /* Original password can be printed, if needed */ + printf("\n Your password is :"); + for (i = 0; i < 8; i++) + { + printf("%c", password[i]); + } +} \ No newline at end of file diff --git a/c/_Basic/C Program to Illustrate the Concept of Unions.c b/c/_Basic/C Program to Illustrate the Concept of Unions.c new file mode 100644 index 0000000..3902e90 --- /dev/null +++ b/c/_Basic/C Program to Illustrate the Concept of Unions.c @@ -0,0 +1,20 @@ +/* + * C program to illustrate the concept of unions + */ +#include + +void main() +{ + union number + { + int n1; + float n2; + }; + union number x; + printf("Enter the value of n1: "); + scanf("%d", &x.n1); + printf("Value of n1 = %d", x.n1); + printf("\nEnter the value of n2: "); + scanf("%f", &x.n2); + printf("Value of n2 = %f\n", x.n2); +} \ No newline at end of file diff --git a/c/_Basic/C Program to Implements Regular Expression Matching.c b/c/_Basic/C Program to Implements Regular Expression Matching.c new file mode 100644 index 0000000..e6e5a26 --- /dev/null +++ b/c/_Basic/C Program to Implements Regular Expression Matching.c @@ -0,0 +1,295 @@ +/* +* C Program to Implements Regular Expression Matching +*/ +#include +#include +#define MATCH printf(" +The Text Matches The Regular Expression"); +#define NOTMATCH printf(" +The Text Doesn't match the Regular Expression"); + +char reg[20], text[20]; +int main() +{ + int i, rlen, tlen, f = 0; + char ans; + do + { + printf(" + Enter the Regular Expression + "); + scanf(" %[^ + ]s", reg); + for (rlen = 0; reg[rlen] != ''; rlen++); + printf(" + Enter the text + "); + scanf(" %[^ + ]s", text); + for (tlen = 0; text[tlen] != '' ; tlen++); + if (reg[0] == '*') + { + printf(" + Invalid regular expression"); + } + /* + *If the regular expression starts with Alphabet + */ + if ((reg[0] >= 65 && reg[0] <= 90) || (reg[0] >= 97 && reg[0] <=122)) + { + if (reg[0] == text [0]) + { + switch (reg[1]) + { + case '.' : + switch (reg[2]) + { + case '*': + if (tlen != 1) + { + if (reg[3] == text[tlen-1]) + { + MATCH; + } + else + { + NOTMATCH; + } + } + else + { + NOTMATCH; + } + break; + case '+': + if (text[1] != reg[3]) + { + if (reg[3] == text[tlen - 1]) + { + MATCH; + } + else + { + NOTMATCH; + } + } + break; + case '?': + if (text[1] == reg[3] || text[2] == reg[3]) + { + if (text[1] == reg[3] || text[2] == reg[3]) + { + MATCH; + } + else + { + NOTMATCH; + } + } + else + { + NOTMATCH; + } + break; + } + break; + case '*': + if (reg[rlen-1] == text[tlen-1]) + { + for (i = 0; i <= tlen-2; i++) + { + if(text[i] == reg[0]) + { + f = 1; + } + else + { + f = 0; + } + } + if ( f == 1) + { + MATCH; + } + else + { + NOTMATCH; + } + } + else + { + NOTMATCH; + } + break; + case '+' : + if (tlen <= 2) + { + NOTMATCH; + } + else if (reg[rlen-1] == text[tlen-1]) + { + for (i = 0; i < tlen-2; i++) + { + if (text[i] == reg[0]) + { + f = 1; + } + else + { + f = 0; + } + } + if (f == 1) + { + MATCH; + } + else + { + NOTMATCH; + } + } + break; + case '?': + if (reg[rlen -1] == text[tlen-1]) + { + MATCH; + } + else + { + NOTMATCH; + } + break; + } + } + else + printf("Does not match"); + } + /* + *If Regular Expression starts with '^' + */ + else if (reg[0] == '^') + { + if (reg[1] == text[0]) + { + MATCH; + } + else + { + NOTMATCH; + } + } + /* + *If Regular Expression Ends with '$' + */ + else if (reg[rlen-1] == '$') + { + if (reg[rlen-2] == text[rlen-1]) + { + MATCH; + } + else + { + NOTMATCH; + } + } + else + printf("Not Implemented"); + printf(" + Do you want to continue?(Y/N)"); + scanf(" %c", &ans); + } + while (ans == 'Y' || ans == 'y'); +} + + +Enter the Regular Expression +C.*g + +Enter the text +Cprogramming + +The Text Matches The Regular Expression +Do you want to continue?(Y/N)y + +Enter the Regular Expression +C*g + +Enter the text +Cprogramming + +The Text Doesn't match the Regular Expression +Do you want to continue?(Y/N)y + +Enter the Regular Expression +C?.*g + +Enter the text +Cprogramming + +The Text Matches The Regular Expression +Do you want to continue?(Y/N)y + +Enter the Regular Expression +C.?g + +Enter the text +Cprogramming + +The Text Doesn't match the Regular Expression +Do you want to continue?(Y/N)y + +Enter the Regular Expression +C.+g + +Enter the text +Cprogramming + +The Text Matches The Regular Expression +Do you want to continue?(Y/N)y + +Enter the Regular Expression +C+g + +Enter the text +Cprogramming + +The Text Doesn't match the Regular Expression +Do you want to continue?(Y/N)y + +Enter the Regular Expression + +^C.* + +Enter the text +Cprogramming + + +The Text Matches The Regular Expression +Do you want to continue?(Y/N)y + +Enter the Regular Expression +^p.* + +Enter the text +Cprogramming + +The Text Doesn't match the Regular Expression +Do you want to continue?(Y/N)y + +Enter the Regular Expression +C.*g$ + +Enter the text +Cprogramming + +The Text Matches The Regular Expression +Do you want to continue?(Y/N)y + +Enter the Regular Expression +C.*n$ + +Enter the text +Cprogramming + +The Text Doesn't match the Regular Expression +Do you want to continue?(Y/N)n \ No newline at end of file diff --git a/c/_Basic/C Program to Input 2 Binary Strings and Print their Binary Sum.c b/c/_Basic/C Program to Input 2 Binary Strings and Print their Binary Sum.c new file mode 100644 index 0000000..0ad47e1 --- /dev/null +++ b/c/_Basic/C Program to Input 2 Binary Strings and Print their Binary Sum.c @@ -0,0 +1,117 @@ +/* +* C Program to Input 2 Binary Strings and Print their Binary +* Sum +*/ +#include +#include +#include + +int bin_verify(char []); +void sum(char [], char [], char []); + +int main() +{ + char bin1[33], bin2[33], result[33]; + int len1, len2, check; + printf("Enter binary number 1: "); + scanf("%s", bin1); + printf("Enter binary number 2: "); + scanf("%s", bin2); + check = bin_verify(bin1); + if (check) + { + printf("Invalid binary number %s. + ", bin1); + exit(0); + } + check = bin_verify(bin2); + if (check) + { + printf("Invalid binary number %s. + ", bin2); + exit(0); + } + sum(bin1, bin2, result); + printf("%s + %s = %s + ", bin1, bin2, result); + return 0; +} + +int bin_verify(char str[]) +{ + int i; + for (i = 0; i < strlen(str); i++) + { + if ((str[i] - '0' != 1 ) && (str[i] - '0' != 0)) + { + return 1; + } + } + return 0; +} + +void sum(char bin1[], char bin2[], char result[]) +{ + int i = strlen(bin1) - 1; + int j = strlen(bin2) - 1; + int carry = 0, temp, num1, num2; + while (i > -1 && j > -1) + { + num1 = bin1[i] - '0'; + num2 = bin2[j] - '0'; + temp = num1 + num2 + carry; + if (temp / 2 == 1) + { + carry = 1; + temp %= 2; + } + if (i > j) + { + result[i + 1] = temp + '0'; + result[strlen(bin1) + 1] = ''; + } + else + { + result[j +1] = temp + '0'; + result[strlen(bin2) + 1] = ''; + } + i--; + j--; + } + while (i > -1) + { + temp = bin1[i] + carry - '0'; + if (temp / 2 == 1) + { + carry = 1; + temp %= 2; + } + result[i + 1] = temp + '0'; + i--; + } + while (j > -1) + { + temp = bin2[j] + carry - '0'; + if (temp / 2 == 1) + { + carry = 1; + temp %= 2; + } + result[j + 1] = temp + '0'; + j--; + } + if (carry) + { + result[0] = '1'; + } + else + { + result[0] = '0'; + } +} + + + +Enter binary number 1: 0110 +Enter binary number 2: 1011 +0110 + 1011 = 10001 diff --git a/c/_Basic/C Program to Input 3 Arguments and Operate Appropriately on the Numbers.c b/c/_Basic/C Program to Input 3 Arguments and Operate Appropriately on the Numbers.c new file mode 100644 index 0000000..7ef0d69 --- /dev/null +++ b/c/_Basic/C Program to Input 3 Arguments and Operate Appropriately on the Numbers.c @@ -0,0 +1,35 @@ +/* + * C Program to Input 3 Arguments and Operate Appropriately on the + * Numbers + */ +#include + +void main(int argc, char * argv[]) +{ + int a, b, result; + char ch; + printf("arguments entered: \n"); + a = atoi(argv[1]); + b = atoi(argv[2]); + ch = *argv[3]; + printf("%d %d %c", a, b, ch); + switch (ch) + { + case '+': + result = a + b; + break; + case '-': + result = a - b; + break; + case 'x': + result = a * b; + break; + case '/': + result = a / b; + break; + default: + printf("Enter a valid choice"); + } + printf("\nThe result of the operation is %d", result); + printf("\n"); +} \ No newline at end of file diff --git a/c/_Basic/C Program to Maintain an Inventory of items in Online Store.c b/c/_Basic/C Program to Maintain an Inventory of items in Online Store.c new file mode 100644 index 0000000..478d584 --- /dev/null +++ b/c/_Basic/C Program to Maintain an Inventory of items in Online Store.c @@ -0,0 +1,47 @@ + #include + #include + void main() { + struct date { + int day; + int month; + int year; + }; + struct details { + char name[20]; + int price; + int code; + int qty; + struct date mfg; + }; + struct details item[50]; + int n,i; + clrscr(); + printf("Enter number of items:"); + scanf("%d",&n); + fflush(stdin); + for (i=0;i + +void main() +{ + long number, tempnum; + printf("Enter an integer \n"); + scanf("%ld", &number); + tempnum = number; + /* left shift by two bits */ + number = number << 2; + printf("%ld x 4 = %ld\n", tempnum, number); +} \ No newline at end of file diff --git a/c/_Basic/C Program to Print Armstrong Number from 1 to 1000.c b/c/_Basic/C Program to Print Armstrong Number from 1 to 1000.c new file mode 100644 index 0000000..263eb55 --- /dev/null +++ b/c/_Basic/C Program to Print Armstrong Number from 1 to 1000.c @@ -0,0 +1,23 @@ +/* + * C Program to Print Armstrong Number from 1 to 1000 + */ +#include + +main() +{ + int number, temp, digit1, digit2, digit3; + printf("Print all Armstrong numbers between 1 and 1000:\n"); + number = 001; + while (number <= 900) + { + digit1 = number - ((number / 10) * 10); + digit2 = (number / 10) - ((number / 100) * 10); + digit3 = (number / 100) - ((number / 1000) * 10); + temp = (digit1 * digit1 * digit1) + (digit2 * digit2 * digit2) + (digit3 * digit3 * digit3); + if (temp == number) + { + printf("\n Armstrong no is:%d", temp); + } + number++; + } +} \ No newline at end of file diff --git a/c/_Basic/C Program to Print Binary Equivalent of an Integer using Recursion.c b/c/_Basic/C Program to Print Binary Equivalent of an Integer using Recursion.c new file mode 100644 index 0000000..5e26e51 --- /dev/null +++ b/c/_Basic/C Program to Print Binary Equivalent of an Integer using Recursion.c @@ -0,0 +1,28 @@ +/* + * C Program to Print Binary Equivalent of an Integer using Recursion + */ +#include + +int binary_conversion(int); + +int main() +{ + int num, bin; + printf("Enter a decimal number: "); + scanf("%d", &num); + bin = binary_conversion(num); + printf("The binary equivalent of %d is %d\n", num, bin); +} + +int binary_conversion(int num) +{ + if (num == 0) + { + return 0; + } + else + { + return (num % 2) + 10 * binary_conversion(num / 2); + } +} +} \ No newline at end of file diff --git a/c/_Basic/C Program to Print Combination of two Words of two given Strings without any Repetition.c b/c/_Basic/C Program to Print Combination of two Words of two given Strings without any Repetition.c new file mode 100644 index 0000000..ea4b4f0 --- /dev/null +++ b/c/_Basic/C Program to Print Combination of two Words of two given Strings without any Repetition.c @@ -0,0 +1,48 @@ +/* +* C Program to Print Combination of two Words of two +* given Strings without any Repetition +*/ +#include +#include + +void main() +{ + char string[100], str[10], c[10]; + int z, occ = 0, i = 0, j = 0, count = 0, len = 0; + printf("Enter a string:"); + scanf("%[^ + ]s", string); + printf("Enter the word to check its occurence:"); + scanf("%s", str); + len = strlen(str); + for (i = 0; string[i] != ''; i++) + { + count = 0; + for (j = 0, z = i; j < len; j++, z++) + { + c[j] = string[z]; + if (c[j] == str[j]) + { + count++; /* Incrementing the count if the characters of the main string match with the characters of the given word */ + } + } + if (count == len && string[z] == ' ') + { + occ++; /* Incrementing the occ if word matches completely and next character in string is space */ + } + } + printf("The number of occ is %d + ", occ); +} + +Enter a string: +welcome to illumin8's c programming class, welcome again to c class +Enter the word to check its occurence: +welcome +The number of occ is 2 + +Enter a string: +welcome to illumin8's c programming class, welcome again to c class +Enter the word to check its occurence: +c +The number of occ is 2 diff --git a/c/_Basic/C Program to Print Diamond Pattern.c b/c/_Basic/C Program to Print Diamond Pattern.c new file mode 100644 index 0000000..1687a5d --- /dev/null +++ b/c/_Basic/C Program to Print Diamond Pattern.c @@ -0,0 +1,42 @@ +/* + * C Program to Print Diamond Pattern + */ +#include + +int main() +{ + int number, i, k, count = 1; + printf("Enter number of rows\n"); + scanf("%d", &number); + count = number - 1; + for (k = 1; k <= number; k++) + { + for (i = 1; i <= count; i++) + printf(" "); + count--; + for (i = 1; i <= 2 * k - 1; i++) + printf("*"); + printf("\n"); + } + count = 1; + for (k = 1; k <= number - 1; k++) + { + for (i = 1; i <= count; i++) + printf(" "); + count++; + for (i = 1 ; i <= 2 *(number - k)- 1; i++) + printf("*"); + printf("\n"); + } + return 0; +} + +/* + * + *** + ***** + ******* +********* + ******* + ***** + *** \ No newline at end of file diff --git a/c/_Basic/C Program to Print a Semicolon without using a Semicolon anywhere in the Code.c b/c/_Basic/C Program to Print a Semicolon without using a Semicolon anywhere in the Code.c new file mode 100644 index 0000000..6bb4f8d --- /dev/null +++ b/c/_Basic/C Program to Print a Semicolon without using a Semicolon anywhere in the Code.c @@ -0,0 +1,14 @@ +/* + * C Program to Print a Semicolon without using a Semicolon + * anywhere in the code + */ +#include + +int main(void) +{ + //59 is the ascii value of semicolumn + if (printf("%c ", 59)) + { + } + return 0; +} \ No newline at end of file diff --git a/c/_Basic/C Program to Print any Print Statement without using Semicolon.c b/c/_Basic/C Program to Print any Print Statement without using Semicolon.c new file mode 100644 index 0000000..1c6472d --- /dev/null +++ b/c/_Basic/C Program to Print any Print Statement without using Semicolon.c @@ -0,0 +1,11 @@ +/* + * C Program to Print any Print Statement without using Semicolon + */ +#include + +void main() +{ + if(printf("Hi.. Welcome to sanfoundry")) + { + } +} \ No newline at end of file diff --git a/c/_Basic/C Program to Print the Program Name and All its Arguments.c b/c/_Basic/C Program to Print the Program Name and All its Arguments.c new file mode 100644 index 0000000..af6f1cd --- /dev/null +++ b/c/_Basic/C Program to Print the Program Name and All its Arguments.c @@ -0,0 +1,14 @@ +/* + * C Program to Print the Program Name and All its Arguments + */ +#include + +void main(int argc, char *argv[]) /* command line Arguments */ +{ + int i; + for (i = 0; i < argc; i++) + { + printf("%s ", argv[i]); /* Printing the string */ + } + printf("\n"); +} \ No newline at end of file diff --git a/c/_Basic/C Program to Print the Words Ending with Letter S.c b/c/_Basic/C Program to Print the Words Ending with Letter S.c new file mode 100644 index 0000000..46a8dc3 --- /dev/null +++ b/c/_Basic/C Program to Print the Words Ending with Letter S.c @@ -0,0 +1,38 @@ +/* + * C Program to Print the Words Ending with Letter S +*/ +#include +#include + +char str[100]; + +void main() +{ + int i, t, j, len; + printf("Enter a string : "); + scanf("%[^ + ]s", str); + len = strlen(str); + str[len] = ' '; + for (t = 0, i = 0; i < strlen(str); i++) + { + if ((str[i] == ' ') && (str[i - 1] == 's')) + { + for (j = t; j < i; j++) + printf("%c", str[j]); + t = i + 1; + printf(" + "); + } + else + { + if (str[i] == ' ') + { + t = i + 1; + } + } + } +} + +Enter a string : +Welcome to Illumin8's C Programming Class, Welcome Again to C Class ! Illumin8's Class \ No newline at end of file diff --git a/c/_Basic/C Program to Read Two Integers M and N & Swap their Values.c b/c/_Basic/C Program to Read Two Integers M and N & Swap their Values.c new file mode 100644 index 0000000..715268e --- /dev/null +++ b/c/_Basic/C Program to Read Two Integers M and N & Swap their Values.c @@ -0,0 +1,25 @@ +/* + * C program to read two integers M and N and to swap their values. + * Use a user-defined function for swapping. Output the values of M + * and N before and after swapping. + */ +#include +void swap(float *ptr1, float *ptr2); + +void main() +{ + float m, n; + printf("Enter the values of M and N \n"); + scanf("%f %f", &m, &n); + printf("Before Swapping:M = %5.2ftN = %5.2f\n", m, n); + swap(&m, &n); + printf("After Swapping:M = %5.2ftN = %5.2f\n", m, n); +} +/* Function swap - to interchanges the contents of two items */ +void swap(float *ptr1, float *ptr2) +{ + float temp; + temp = *ptr1; + *ptr1 = *ptr2; + *ptr2 = temp; +} \ No newline at end of file diff --git a/c/_Basic/C Program to Read a Grade & Display the Equivalent Description.c b/c/_Basic/C Program to Read a Grade & Display the Equivalent Description.c new file mode 100644 index 0000000..04a4516 --- /dev/null +++ b/c/_Basic/C Program to Read a Grade & Display the Equivalent Description.c @@ -0,0 +1,43 @@ +/* + * C Program to accept a grade and declare the equivalent description + * if code is S, then print SUPER + * if code is A, then print VERY GOOD + * if code is B, then print FAIR + * if code is Y, then print ABSENT + * if code is F, then print FAILS + */ +#include +#include +#include + +void main() +{ + char remark[15]; + char grade; + printf("Enter the grade \n"); + scanf("%c", &grade); + /* lower case letter to upper case */ + grade = toupper(grade); + switch(grade) + { + case 'S': + strcpy(remark, " SUPER"); + break; + case 'A': + strcpy(remark, " VERY GOOD"); + break; + case 'B': + strcpy(remark, " FAIR"); + break; + case 'Y': + strcpy(remark, " ABSENT"); + break; + case 'F': + strcpy(remark, " FAILS"); + break; + default : + strcpy(remark, "ERROR IN GRADE \n"); + break; + } + printf("RESULT : %s\n", remark); +} \ No newline at end of file diff --git a/c/_Basic/C Program to Reverse a Given Number.c b/c/_Basic/C Program to Reverse a Given Number.c new file mode 100644 index 0000000..93af145 --- /dev/null +++ b/c/_Basic/C Program to Reverse a Given Number.c @@ -0,0 +1,20 @@ +/* + * C program to accept an integer and reverse it + */ +#include + +void main() +{ + long num, reverse = 0, temp, remainder; + printf("Enter the number\n"); + scanf("%ld", &num); + temp = num; + while (num > 0) + { + remainder = num % 10; + reverse = reverse * 10 + remainder; + num /= 10; + } + printf("Given number = %ld\n", temp); + printf("Its reverse is = %ld\n", reverse); +} \ No newline at end of file diff --git a/c/_Basic/C Program to Reverse a Number & Check if it is a Palindrome.c b/c/_Basic/C Program to Reverse a Number & Check if it is a Palindrome.c new file mode 100644 index 0000000..e793701 --- /dev/null +++ b/c/_Basic/C Program to Reverse a Number & Check if it is a Palindrome.c @@ -0,0 +1,27 @@ +/* + * C program to reverse a given integer number and check + * whether it is a palindrome. Display the given number + * with appropriate message + */ +#include + +void main() +{ + int num, temp, remainder, reverse = 0; + printf("Enter an integer \n"); + scanf("%d", &num); + /* original number is stored at temp */ + temp = num; + while (num > 0) + { + remainder = num % 10; + reverse = reverse * 10 + remainder; + num /= 10; + } + printf("Given number is = %d\n", temp); + printf("Its reverse is = %d\n", reverse); + if (temp == reverse) + printf("Number is a palindrome \n"); + else + printf("Number is not a palindrome \n"); +} \ No newline at end of file diff --git a/c/_Basic/C Program to Search a Word & Replace it with the Specified Word.c b/c/_Basic/C Program to Search a Word & Replace it with the Specified Word.c new file mode 100644 index 0000000..d32ec6f --- /dev/null +++ b/c/_Basic/C Program to Search a Word & Replace it with the Specified Word.c @@ -0,0 +1,72 @@ +/* +* C Program to Search a Word & Replace it with the Specified Word +*/ +#include +#include +#include + +/*Function to replace a string with another string*/ + +char *rep_str(const char *s, const char *old, const char *new1) +{ + char *ret; + int i, count = 0; + int newlen = strlen(new1); + int oldlen = strlen(old); + for (i = 0; s[i] != ''; i++) + { + if (strstr(&s[i], old) == &s[i]) + { + count++; + i += oldlen - 1; + } + } + ret = (char *)malloc(i + count * (newlen - oldlen)); + if (ret == NULL) + exit(EXIT_FAILURE); + i = 0; + while (*s) + { + if (strstr(s, old) == s) //compare the substring with the newstring + { + strcpy(&ret[i], new1); + i += newlen; //adding newlength to the new string + s += oldlen;//adding the same old length the old string + } + else + ret[i++] = *s++; + } + ret[i] = ''; + return ret; +} + +int main(void) +{ + char mystr[100], c[10], d[10]; + printf("Enter a string along with characters to be rep_strd: + "); + gets(mystr); + printf("Enter the character to be rep_strd: + "); + scanf(" %s",c); + printf("Enter the new character: + "); + scanf(" %s",d); + char *newstr = NULL; + puts(mystr); + newstr = rep_str(mystr, c,d); + printf("%s + ", newstr); + free(newstr); + return 0; +} + + + Enter a string along with characters to be rep_strd: + prrrogram C prrrogramming + Enter the character to be rep_strd: + rr + Enter the new character: + mmm + prrrogram C prrrogramming + pmmmrogram C pmmmrogramming \ No newline at end of file diff --git a/c/_Basic/C Program to Shutdown or Turn Off the Computer in Linux.c b/c/_Basic/C Program to Shutdown or Turn Off the Computer in Linux.c new file mode 100644 index 0000000..a88db5b --- /dev/null +++ b/c/_Basic/C Program to Shutdown or Turn Off the Computer in Linux.c @@ -0,0 +1,10 @@ +/* + * C Program to Shutdown or Turn Off the Computer in Linux. + */ +#include + +int main() +{ + system("shutdown -P now"); + return 0; +} \ No newline at end of file diff --git a/c/_Basic/C Program to Swap the Contents of two Numbers using Bitwise XOR Operation.c b/c/_Basic/C Program to Swap the Contents of two Numbers using Bitwise XOR Operation.c new file mode 100644 index 0000000..09f7b13 --- /dev/null +++ b/c/_Basic/C Program to Swap the Contents of two Numbers using Bitwise XOR Operation.c @@ -0,0 +1,18 @@ +/* + * C program to swap the contents of two numbers using bitwise XOR + * operation. Don't use either the temporary variable or arithmetic + * operators + */ +#include + +void main() +{ + long i, k; + printf("Enter two integers \n"); + scanf("%ld %ld", &i, &k); + printf("\n Before swapping i= %ld and k = %ld", i, k); + i = i ^ k; + k = i ^ k; + i = i ^ k; + printf("\n After swapping i= %ld and k = %ld", i, k); +} \ No newline at end of file diff --git a/c/_Basic/C Program to Use Bitwise Operations to Count the Number of Leading Zero's in a Number x.c b/c/_Basic/C Program to Use Bitwise Operations to Count the Number of Leading Zero's in a Number x.c new file mode 100644 index 0000000..84eeefc --- /dev/null +++ b/c/_Basic/C Program to Use Bitwise Operations to Count the Number of Leading Zero's in a Number x.c @@ -0,0 +1,114 @@ +/* +* C Program to Use Bitwise Operations to Count the Number of +* Leading Zero's in a Number x +*/ +#include +#include +#define NUM_BITS_INT (sizeof(int)*8) +int find(int); + +void main() +{ + int n, i, a, count = 0, flag = 1, m = 1, j, cmp; + printf("Enter the number + "); + scanf("%d", &n); + a = n >> 31 & 1; + if (a == 0) + { + for (i = (NUM_BITS_INT)-1; i >= 0; i--) + { + a = (n >> i)& 1; + if (a == 0) + { + count++; + } + else + { + for (j = n + 1;; j++) + { + cmp = find(j); + if (cmp == (((NUM_BITS_INT)-1) - count) + 1) + { + printf("next higher power -> %d + ", j); + break; + } + } + break; + } + } + } + else + { + for (i = (NUM_BITS_INT)-1; i >= 0; i--) + { + a = (n >> i)& 1; + if (a == 1) + { + count++; + } + else + { + for (j = n + 1;; j++) + { + cmp = find(j); + if (cmp == (((NUM_BITS_INT)- 1) - count)) + { + printf("next higher power -> %d + ", j); + break; + } + } + break; + } + } + } +} + +/* To find trailing zero's */ +int find(int n) +{ + int count = 0, a, flag = 1, i; + for (i = 0; i <= (NUM_BITS_INT) - 1; i++) + { + a = (n >> i) & 1; + if (a == 1 && flag == 1) + { + return count; + } + else + { + count++; + flag = 1; + } + } +} + + +Enter the number +9 +next higher power -> 16 + +Enter the number +-20 +next higher power -> -16 +Enter the number +44 +next higher power -> 64 + +Enter the number +-7 +next higher power -> -4 + +Enter the number +-31 +next higher power -> -16 + +Enter the number +-56 +next higher power -> -32 + +Enter the number +34 +next higher power -> 64 diff --git a/c/_Basic/C Program to calculate the total execution time of a program.c b/c/_Basic/C Program to calculate the total execution time of a program.c new file mode 100644 index 0000000..4f64895 --- /dev/null +++ b/c/_Basic/C Program to calculate the total execution time of a program.c @@ -0,0 +1,19 @@ + #include + #include + int main() { + int i; + double total_time; + clock_t start, end; + start = clock(); + //time count starts + srand(time(NULL)); + for (i = 0; i < 25000; i++) { + printf("random_number[%d]= %d\n", i + 1, rand()); + } + end = clock(); + //time count stops + total_time = ((double) (end - start)) / CLK_TCK; + //calulate total time + printf("\nTime taken to print 25000 random number is: %f", total_time); + return 0; + } \ No newline at end of file diff --git a/c/_Basic/C Program to find Product of 2 Numbers using Recursion.c b/c/_Basic/C Program to find Product of 2 Numbers using Recursion.c new file mode 100644 index 0000000..f1b754a --- /dev/null +++ b/c/_Basic/C Program to find Product of 2 Numbers using Recursion.c @@ -0,0 +1,32 @@ +/* + * C Program to find Product of 2 Numbers using Recursion + */ +#include + +int product(int, int); + +int main() +{ + int a, b, result; + printf("Enter two numbers to find their product: "); + scanf("%d%d", &a, &b); + result = product(a, b); + printf("Product of %d and %d is %d\n", a, b, result); + return 0; +} + +int product(int a, int b) +{ + if (a < b) + { + return product(b, a); + } + else if (b != 0) + { + return (a + product(a, b - 1)); + } + else + { + return 0; + } +} \ No newline at end of file diff --git a/c/_Basic/C Program to find Reverse of a Number using Recursion.c b/c/_Basic/C Program to find Reverse of a Number using Recursion.c new file mode 100644 index 0000000..303ad1f --- /dev/null +++ b/c/_Basic/C Program to find Reverse of a Number using Recursion.c @@ -0,0 +1,36 @@ +/* + * C program to find the reverse of a number using recursion + */ +#include +#include + +int rev(int, int); + +int main() +{ + int num, result; + int length = 0, temp; + printf("Enter an integer number to reverse: "); + scanf("%d", &num); + temp = num; + while (temp != 0) + { + length++; + temp = temp / 10; + } + result = rev(num, length); + printf("The reverse of %d is %d.\n", num, result); + return 0; +} + +int rev(int num, int len) +{ + if (len == 1) + { + return num; + } + else + { + return (((num % 10) * pow(10, len - 1)) + rev(num / 10, --len)); + } +} \ No newline at end of file diff --git a/c/_Basic/C Program to find Sum of N Numbers using Recursion.c b/c/_Basic/C Program to find Sum of N Numbers using Recursion.c new file mode 100644 index 0000000..a610461 --- /dev/null +++ b/c/_Basic/C Program to find Sum of N Numbers using Recursion.c @@ -0,0 +1,31 @@ +/* + * C Program to find Sum of N Numbers using Recursion + */ +#include + +void display(int); + +int main() +{ + int num, result; + printf("Enter the Nth number: "); + scanf("%d", &num); + display(num); + return 0; +} + +void display(int num) +{ + static int i = 1; + if (num == i) + { + printf("%d \n", num); + return; + } + else + { + printf("%d ", i); + i++; + display(num); + } +} \ No newline at end of file diff --git a/c/_Basic/C Program to next higher value of n with same 1's.c b/c/_Basic/C Program to next higher value of n with same 1's.c new file mode 100644 index 0000000..dc956db --- /dev/null +++ b/c/_Basic/C Program to next higher value of n with same 1's.c @@ -0,0 +1,63 @@ +/* + +* C Program to next higher value of n with same 1's +*/ +#define NUM_BITS_INT 32 +#include +int newcount(int); + +void main() +{ + int count1 = 0, k = 0, j, t, n, bit, i = 1, count = 0; + printf("Enter a number : "); + scanf("%d", &n); + t = n; + while(t != 0) + { + bit = t & 0x80000000; + if (bit == -0x80000000) + { + bit = 1; + } + if (bit == 1) + count++; + t = t << 1; + } + for (k = n + 1;; k++) + { + count1 = newcount(k); + if (count1 == count) + { + printf("The next highest number is : %d ", k); + break; + } + } +} + +/* To count the no. of 1's in the no. */ +int newcount(int k) +{ + int bit, count = 0; + while (k != 0) + { + bit = k & 0x80000000; + if (bit == -0x80000000) + { + bit = 1; + } + if (bit == 1) + count++; + k = k << 1; + } + return(count); +} + + +Enter a number : 128 +The next highest number is : 256 +Enter a number : 127 +The next highest number is : 191 +Enter a number : 6 +The next highest number is : 9 +Enter a number : 12 +The next highest number is : 17 \ No newline at end of file diff --git a/c/_Basic/C Program to replace first letter of every word with caps.c b/c/_Basic/C Program to replace first letter of every word with caps.c new file mode 100644 index 0000000..77abf20 --- /dev/null +++ b/c/_Basic/C Program to replace first letter of every word with caps.c @@ -0,0 +1,61 @@ +/* +* C Program to replace first letter of every word with caps +*/ +#include +#include +void main(int argc, char *argv[]) +{ + FILE *fp1; + int return_val; + if ((fp1 = fopen(argv[1],"r+")) = = NULL) + { + printf("file cant be opened"); + exit(0); + } + return_val = init_cap_file(fp1); + if (return_val == 1) + { + printf(" + success"); + } + else + { + printf(" + failure"); + } +} +int init_cap_file(FILE *fp1) +{ + char ch; + ch = fgetc(fp1); + if (ch >= 97 && ch <= 122) + { + fseek(fp1, -1L, 1); + fputc(ch - 32, fp1); + } + while (ch != EOF) + { + if (ch = = ' '|| ch == ' + ') + { + ch = fgetc(fp1); + if (ch >= 97 && ch <= 122) + { + fseek(fp1, -1L, 1); + fputc(ch - 32, fp1); + } + } + else + ch = fgetc(fp1); + } + return 1; +} +chandana ravella +chanikya ravella +sree lakshmi ravella +sree ramulu ravella +cat file5test +Chandana Ravella +Chanikya Ravella +Sree Lakshmi Ravella +Sree Ramulu Ravella \ No newline at end of file diff --git a/c/_Basic/C Program to sort string ignoring whitespaces and repeating characters only once.c b/c/_Basic/C Program to sort string ignoring whitespaces and repeating characters only once.c new file mode 100644 index 0000000..c609be5 --- /dev/null +++ b/c/_Basic/C Program to sort string ignoring whitespaces and repeating characters only once.c @@ -0,0 +1,64 @@ + +/* +* C Program to sort string ignoring whitespaces and repeating characters only once +*/ +#include +#include + +#define SIZE 50 + +void main() +{ + char string[SIZE], string1[SIZE], string2[SIZE]; + int i, j = 0, a = 0, temp, len = 0, len1 = 0, k = 0; + printf(" + Enter a string:"); + scanf("%[^ + ]s", string1); + /* Code to remove whitespaces */ + for (i = 0; string1[i] != ''; i++) + { + if (string1[i] == ' ') + { + continue; + } + string[j++] = string1[i]; + } + /* Code to sort the string */ for (i = 0; string[i] != ''; i++) + { + for (j = i + 1; string[j] != ''; j++) + { + if (string[i] > string[j]) + { + temp = string[i]; + string[i] = string[j]; + string[j] = temp; + } + } + } + string[i] = ''; + len = strlen(string); + /* Code to remove redundant characters */ + for (i = 0; string[i] != ''; i++) + { + if (string[i] == string[i + 1] && string[i + 1] != '') + { + k++; + continue; + } + string2[a++] = string[i]; + string[a] = ''; + } + len1 = len - k; + printf("The sorted string is:"); + for (temp = 0; temp < len1; temp++) + { + printf("%c", string2[temp]); + } +} + + +Enter a string: +abcdel bcdl abcdefg +The sorted string is: +abcdefgl diff --git a/c/_Basic/C program for Binary to decimal conversion.c b/c/_Basic/C program for Binary to decimal conversion.c new file mode 100644 index 0000000..19ab181 --- /dev/null +++ b/c/_Basic/C program for Binary to decimal conversion.c @@ -0,0 +1,16 @@ +/*binary to decimal conversion:*/ +#include +void main() +{ + long int bn,dn=0,j=1,remainder; + printf("Enter any number any binary number: "); + scanf("%ld",&bn); + while(bn!=0) + { + remainder=bn%10; + dn=dn+remainder*j; + j=j*2; + bn=bn/10; + } + printf("Equivalent decimal value: %ld",dn); +} \ No newline at end of file diff --git a/c/_Basic/C program for decimal to octal converter.c b/c/_Basic/C program for decimal to octal converter.c new file mode 100644 index 0000000..e0a294b --- /dev/null +++ b/c/_Basic/C program for decimal to octal converter.c @@ -0,0 +1,17 @@ +#include +void main() +{ + long int dn,remainder,q; + int on[100],i=1,j; + printf("Enter any decimal number"); + scanf("%ld",&dn); + q = dn; + while(q!=0) + { + on[i++]= q % 8; + q = q/ 8; + } + printf("Equivalent octal value %d: ",dn); + for(j = i -1 ; j> 0; j--) + printf("%d",on[j]); +} \ No newline at end of file diff --git a/c/_Basic/C program for hexadecimal to binary conversion.c b/c/_Basic/C program for hexadecimal to binary conversion.c new file mode 100644 index 0000000..91b1d80 --- /dev/null +++ b/c/_Basic/C program for hexadecimal to binary conversion.c @@ -0,0 +1,85 @@ +#include +#define MAX 1000 +void main() +{ + char hd[MAX]; + long int i=0; + printf("Enter any hexadecimal number: "); + scanf("%s",hd); + printf("\nEquivalent binary value: "); + while(hd[i]) + { + switch(hd[i]) + { + case '0': + printf("0000"); + break; + case '1': + printf("0001"); + break; + case '2': + printf("0010"); + break; + case '3': + printf("0011"); + break; + case '4': + printf("0100"); + break; + case '5': + printf("0101"); + break; + case '6': + printf("0110"); + break; + case '7': + printf("0111"); + break; + case '8': + printf("1000"); + break; + case '9': + printf("1001"); + break; + case 'A': + printf("1010"); + break; + case 'B': + printf("1011"); + break; + case 'C': + printf("1100"); + break; + case 'D': + printf("1101"); + break; + case 'E': + printf("1110"); + break; + case 'F': + printf("1111"); + break; + case 'a': + printf("1010"); + break; + case 'b': + printf("1011"); + break; + case 'c': + printf("1100"); + break; + case 'd': + printf("1101"); + break; + case 'e': + printf("1110"); + break; + case 'f': + printf("1111"); + break; + default: + printf("\nInvalid hexadecimal digit %c ",hd[i]); + } + i++; + } +} \ No newline at end of file diff --git a/c/_Basic/C program to Convert Decimal to Hexadecimal.c b/c/_Basic/C program to Convert Decimal to Hexadecimal.c new file mode 100644 index 0000000..f75b9e5 --- /dev/null +++ b/c/_Basic/C program to Convert Decimal to Hexadecimal.c @@ -0,0 +1,27 @@ +/* + * C program to Convert Decimal to Hexadecimal + */ +#include + +int main() +{ + long decimalnum, quotient, remainder; + int i, j = 0; + char hexadecimalnum[100]; + printf("Enter decimal number: "); + scanf("%ld", &decimalnum); + quotient = decimalnum; + while (quotient != 0) + { + remainder = quotient % 16; + if (remainder < 10) + hexadecimalnum[j++] = 48 + remainder; + else + hexadecimalnum[j++] = 55 + remainder; + quotient = quotient / 16; + } + // display integer into character + for (i = j; i >= 0; i--) + printf("%c", hexadecimalnum[i]); + return 0; +} \ No newline at end of file diff --git a/c/_Basic/C program to Convert Decimal to Octal.c b/c/_Basic/C program to Convert Decimal to Octal.c new file mode 100644 index 0000000..0fe7667 --- /dev/null +++ b/c/_Basic/C program to Convert Decimal to Octal.c @@ -0,0 +1,22 @@ +/* + * C program to Convert Decimal to Octal + */ +#include + +int main() +{ + long decimalnum, remainder, quotient; + int octalNumber[100], i = 1, j; + printf("Enter the decimal number: "); + scanf("%ld", &decimalnum); + quotient = decimalnum; + while (quotient != 0) + { + octalNumber[i++] = quotient % 8; + quotient = quotient / 8; + } + printf("Equivalent octal value of decimal no %d: ", decimalnum); + for (j = i - 1; j > 0; j--) + printf("%d", octalNumber[j]); + return 0; +} \ No newline at end of file diff --git a/c/_Basic/C program to Increase 1 to all of the given Integer Digit.c b/c/_Basic/C program to Increase 1 to all of the given Integer Digit.c new file mode 100644 index 0000000..25055d3 --- /dev/null +++ b/c/_Basic/C program to Increase 1 to all of the given Integer Digit.c @@ -0,0 +1,19 @@ +/* + * C program to Increase 1 to all of the given Integer Digit + */ +#include + +int main() +{ + int number, sum = 0, remainder, count; + printf("Enter a number: "); + scanf("%d", &number); + while (number) + { + remainder = number % 10; + sum = sum + (remainder + 1); + number /= 10; + } + printf("increasing 1 to all digits: %d", sum); + return 0; +} \ No newline at end of file diff --git a/c/_Basic/C program to accept N numbers sorted in ascending order and to search for a given number using binary search..c b/c/_Basic/C program to accept N numbers sorted in ascending order and to search for a given number using binary search..c new file mode 100644 index 0000000..193d94c --- /dev/null +++ b/c/_Basic/C program to accept N numbers sorted in ascending order and to search for a given number using binary search..c @@ -0,0 +1,121 @@ +/* +* C program to accept N numbers sorted in ascending order +* and to search for a given number using binary search. +* Report success or failure. +*/ +#include + +void main() +{ + int array[10]; + int i, j, num, temp, keynum; + int low, mid, high; + printf("Enter the value of num + "); + scanf("%d", &num); + printf("Enter the elements one by one + "); + for (i = 0; i < num; i++) + { + scanf("%d", &array[i]); + } + printf("Input array elements + "); + for (i = 0; i < num; i++) + { + printf("%d + ", array[i]); + } +/* Bubble sorting begins */ +for (i = 0; i < num; i++) + { + for (j = 0; j < (num - i - 1); j++) + { + if (array[j] > array[j + 1]) + { + temp = array[j]; + array[j] = array[j + 1]; + array[j + 1] = temp; + } + } + } + printf("Sorted array is... + "); + for (i = 0; i < num; i++) + { + printf("%d + ", array[i]); + } +printf("Enter the element to be searched + "); + scanf("%d", &keynum); + /* Binary searching begins */ + low = 1; + high = num; + do + { + mid = (low + high) / 2; + if (keynum < array[mid]) + high = mid - 1; + else if (keynum > array[mid]) + low = mid + 1; + } + while (keynum != array[mid] && low <= high); + if (keynum == array[mid]) + { + printf("SEARCH SUCCESSFUL + "); + } + else + { + printf("SEARCH FAILED + "); + } +} + + +Enter the value of num +5 +Enter the elements one by one +23 +90 +56 +15 +58 +Input array elements +23 + +90 +56 +15 +58 +Sorted array is... +15 +23 +56 +58 +90 +Enter the element to be searched +58 +SEARCH SUCCESSFUL + +Enter the value of num +4 +Enter the elements one by one +1 +98 +65 +45 +Input array elements +1 +98 +65 +45 +Sorted array is... +1 +45 +65 +98 +Enter the element to be searched +6 +SEARCH FAILED \ No newline at end of file diff --git a/c/_Basic/C program to accept an array of 10 elements and swap 3rd element with 4th element using pointers and display the results..c b/c/_Basic/C program to accept an array of 10 elements and swap 3rd element with 4th element using pointers and display the results..c new file mode 100644 index 0000000..71692c5 --- /dev/null +++ b/c/_Basic/C program to accept an array of 10 elements and swap 3rd element with 4th element using pointers and display the results..c @@ -0,0 +1,47 @@ +/* * C program to accept an array of 10 elements and swap 3rd element * with 4th element using pointers and display the results. */ +#include +void swap34(float *ptr1, float *ptr2); +void main() +{ + float x[10]; + int i, n; + printf("How many Elements... + "); + scanf("%d", &n); + printf("Enter Elements one by one + "); + for (i = 0; i < n; i++) + { + scanf("%f", x + i); + } + /* Function call:Interchanging 3rd element by 4th */ + swap34(x + 2, x + 3); + printf(" + Resultant Array... + "); + for (i = 0; i < n; i++) + { + printf("X[%d] = %f + ", i, x[i]); + } +} +/* Function to swap the 3rd element with the 4th element in the array */ +void swap34(float *ptr1, float *ptr2 ) +{ + float temp; + temp = *ptr1; + *ptr1 = *ptr2; + *ptr2 = temp; +} +How many Elements... +4 +Enter Elements one by one +23 +67 +45 +15 +Resultant Array... +X[0] = 23.000000 + X[1] = 67.000000 + X[2] = 15.000000 + X[3] = 45.000000 \ No newline at end of file diff --git a/c/_Basic/C program to find the length of a string without using the built-in function also check whether it is a palindrome.c b/c/_Basic/C program to find the length of a string without using the built-in function also check whether it is a palindrome.c new file mode 100644 index 0000000..0333342 --- /dev/null +++ b/c/_Basic/C program to find the length of a string without using the built-in function also check whether it is a palindrome.c @@ -0,0 +1,47 @@ +/* + * C program to find the length of a string without using the + * built-in function also check whether it is a palindrome + */ +#include +#include + +void main() +{ + char string[25], reverse_string[25] = {''}; + int i, length = 0, flag = 0; + printf("Enter a string + "); + gets(string); + /* keep going through each character of the string till its end */ + for (i = 0; string[i] != ''; i++) + { + length++; + } +printf("The length of the string '%s' = %d + ", string, length); + for (i = length - 1; i >= 0 ; i--) + { + reverse_string[length - i - 1] = string[i]; + } + /* Check if the string is a Palindrome */ + for (flag = 1, i = 0; i < length ; i++) + { + if (reverse_string[i] != string[i]) + flag = 0; + } + if (flag == 1) + printf ("%s is a palindrome ", string); + else + printf("%s is not a palindrome ", string); + } + + +Enter a string +how are you +The length of the string 'how are you' = 12 + how are you is not a palindrome + + Enter a string + madam + The length of the string 'madam' = 5 + madam is a palindrome \ No newline at end of file diff --git a/c/_Basic/C program to find the number of occurences of a given number in a list.c b/c/_Basic/C program to find the number of occurences of a given number in a list.c new file mode 100644 index 0000000..9610b47 --- /dev/null +++ b/c/_Basic/C program to find the number of occurences of a given number in a list.c @@ -0,0 +1,50 @@ +/* +* C program to find the number of occurences of a given number in a +* list +*/ +#include + +void occur(int [], int, int, int, int *); + +int main() +{ + int size, key, count = 0; + int list[20]; + int i; + printf("Enter the size of the list: "); + scanf("%d", &size); + printf("Printing the list: + "); + for (i = 0; i < size; i++) + { + list[i] = rand() % size; + printf("%d ", list[i]); + } + printf(" + Enter the key to find it's occurence: "); + scanf("%d", &key); + occur(list, size, 0, key, &count); + printf("%d occurs for %d times. + ", key, count); + return 0; +} + + void occur(int list[], int size, int index, int key, int *count) +{ + if (size == index) + { + return; + } + if (list[index] == key) + { + *count += 1; + } + occur(list, size, index + 1, key, count); +} + + +Enter the size of the list: 7 +Printing the list: +1 4 2 5 1 3 3 +Enter the key to find it's occurence: 3 +3 occurs for 2 times. diff --git a/c/_Basic/C program to print hello world without using semicolon.c b/c/_Basic/C program to print hello world without using semicolon.c new file mode 100644 index 0000000..3f92150 --- /dev/null +++ b/c/_Basic/C program to print hello world without using semicolon.c @@ -0,0 +1,5 @@ + #include + void main(){ + if(printf("Hello world")){ + } + } \ No newline at end of file diff --git a/c/_Basic/C program to read an English sentence and replace lowercase characters by uppercase and vice-versa..c b/c/_Basic/C program to read an English sentence and replace lowercase characters by uppercase and vice-versa..c new file mode 100644 index 0000000..93d82ae --- /dev/null +++ b/c/_Basic/C program to read an English sentence and replace lowercase characters by uppercase and vice-versa..c @@ -0,0 +1,41 @@ +/* + * C program to read an English sentence and replace + * lowercase characters by uppercase and vice-versa. + * Output the given sentence as well as the converted + * sentence on two different lines. + */ +#include +#include + +void main() +{ + char sentence[100]; + int count, ch, i; + printf("Enter a sentence + "); + for (i = 0; (sentence[i] = getchar()) != ' + '; i++) + { + ; + } + sentence[i] = ''; + /* shows the number of chars accepted in a sentence */ + count = i; + printf("The given sentence is : %s", sentence); + printf(" + Case changed sentence is: "); + for (i = 0; i < count; i++) + { + ch = islower(sentence[i])? toupper(sentence[i]) : + tolower(sentence[i]); + putchar(ch); + } +} + + +Enter a sentence +gETTING iLLUMIN8ED +The given sentence is : +gETTING iLLUMIN8ED +Case changed sentence is: +GETTING ILLUMIN8ED \ No newline at end of file diff --git a/c/_Basic/C program to sort n given numbers using pointers.c b/c/_Basic/C program to sort n given numbers using pointers.c new file mode 100644 index 0000000..3f70e14 --- /dev/null +++ b/c/_Basic/C program to sort n given numbers using pointers.c @@ -0,0 +1,37 @@ +#include +#include +#include +void main() +{ + int n,*p,i,j,temp; + clrscr(); + printf("\nHOW MANY NUMBER: "); + scanf("%d",&n); + p=(int *) malloc(n*2); + if(p==NULL) + { + printf("\nMEMORY ALLOCATION UNSUCCESSFUL"); + exit(); + } + for(i=0;i + #include + #include + int main(int argc, char** argv) { + char** new_argv; + int i; + /* Since argv[0] through argv[argc] are all valid, the + program needs to allocate room for argc+1 pointers. */ + new_argv = (char**) calloc(argc+1, sizeof (char*)); + /* or malloc((argc+1) * sizeof (char*)) */ + printf("allocated room for %d pointers starting at %P\n", argc+1, new_argv); + /* now copy all the strings themselves + (argv[0] through argv[argc-1]) */ + for (i = 0; i < argc; ++i) { + /* make room for '' at end, too */ + new_argv[i] = (char*) malloc(strlen(argv[i]) + 1); + strcpy(new_argv[i], argv[i]); + printf(" + allocated %d bytes for new_argv[%d] at %P, " + " + copied \" + %s\" + \n" + , + strlen(argv[i]) + 1, i, new_argv[i], new_argv[i]); + } + new_argv[argc] = NULL; + /* To deallocate everything, get rid of the strings (in any + order), then the array of pointers. If you free the array + of pointers first, you lose all reference to the copied + strings. */ + for (i = 0; i < argc; ++i) { + free(new_argv[i]); + printf(" + freed new_argv[%d] at %P\n" + , i, new_argv[i]); + argv[i] = NULL; + } + free(new_argv); + printf(" + freed new_argv itself at %P\n" + , new_argv); + return 0; + } \ No newline at end of file diff --git a/c/_Basic/Create and Use Your Own Header File in C Programming.c b/c/_Basic/Create and Use Your Own Header File in C Programming.c new file mode 100644 index 0000000..0584bd9 --- /dev/null +++ b/c/_Basic/Create and Use Your Own Header File in C Programming.c @@ -0,0 +1,8 @@ + #include + #include "myfirstheader.h" + + void main() { + int num1 = 10, num2 = 10, num3; + num3 = add(num1, num2); + printf("Addition of Two numbers : %d", num3); + } \ No newline at end of file diff --git a/c/_Basic/Get Address of an array using Arrays and Pointers.c b/c/_Basic/Get Address of an array using Arrays and Pointers.c new file mode 100644 index 0000000..d7ad924 --- /dev/null +++ b/c/_Basic/Get Address of an array using Arrays and Pointers.c @@ -0,0 +1,14 @@ + #include + + int main(void) + { + char multiple[] = "My string"; + + char *p = &multiple[0]; + printf("\nThe address of the first array element : %p", p); + + p = multiple; + printf("\nThe address obtained from the array name: %p\n", p); + + return 0; + } \ No newline at end of file diff --git a/c/_Basic/Print mark-sheet of students.c b/c/_Basic/Print mark-sheet of students.c new file mode 100644 index 0000000..920ab9b --- /dev/null +++ b/c/_Basic/Print mark-sheet of students.c @@ -0,0 +1,43 @@ + #include + #include + #include + #include + void main() { + /*variable declaration part */ + int rl,s1,s2,s3,t; + float per; + char nm[25],div[10]; + clrscr(); + /*reading part */ + printf("Enter the Roll No : "); + scanf("%d",&rl); + printf("Enter Name : "); + fflush(stdin); + gets(nm); + printf("Enter Three Subject Marks :\n"); + scanf("%d%d%d",&s1,&s2,&s3); + /* processing part */ + t=s1+s2+s3; + per=t/3.0; + if(per>=75) + strcpy(div,"Honour"); else if( per>=60) + strcpy(div,"First"); else if( per>=48) + strcpy(div,"Second"); else if (per>=36) + strcpy(div,"Pass"); else + strcpy(div,"Fail"); + /* display part */ + printf("\t\tUniversity of Rajasthan\n"); + printf("\n\n"); + printf("Roll No: %d \t Name : %s\n",rl,nm); + printf("---------------------------------------------------\n"); + printf("Subject Max Min Obt.Marks\n"); + printf("---------------------------------------------------\n"); + printf("Hist 100 36 %d\n",s1); + printf("socio. 100 36 %d\n",s2); + printf("Hindi 100 36 %d\n",s3); + printf("---------------------------------------------------\n"); + printf(" Total %d\n",t); + printf("per %f\t\t\t div: %s \n",per,div); + printf("---------------------------------------------------\n"); + getch(); + } \ No newline at end of file diff --git a/c/_Basic/Reverse a string using pointers.c b/c/_Basic/Reverse a string using pointers.c new file mode 100644 index 0000000..993008d --- /dev/null +++ b/c/_Basic/Reverse a string using pointers.c @@ -0,0 +1,15 @@ + #include + #include + void main() + { + char *s; + int len,i; + clrscr(); + printf("\nENTER A STRING: "); + gets(s); + len=strlen(s); + printf("\nTHE REVERSE OF THE STRING IS:"); + for(i=len;i>=0;i--) + printf("%c",*(s+i)); + getch(); + } \ No newline at end of file diff --git a/c/_Basic/Reverse the order of each word of the string using pointers.c b/c/_Basic/Reverse the order of each word of the string using pointers.c new file mode 100644 index 0000000..3d59fc9 --- /dev/null +++ b/c/_Basic/Reverse the order of each word of the string using pointers.c @@ -0,0 +1,28 @@ + #include + #include + void main() + { + char *s; + int len,i,j,sp=0,start,end; + clrscr(); + printf("\nENTER A STRING: "); + gets(s); + printf("\nTHE STRING AFTER CHANGING THE ORDER OF EACH WORD:\n"); + len=strlen(s); + end=len-1; + for(i=len-1;i>=0;i--) + { + if(s[i]==32 || i==0) + { + if(i==0) + start=0; + else + start=i+1; + for(j=start;j<=end;j++) + printf("%c",s[j]); + end=i-1; + printf(" "); + } + } + getch(); + } \ No newline at end of file diff --git a/c/_Basic/Show the ticking of Clock.c b/c/_Basic/Show the ticking of Clock.c new file mode 100644 index 0000000..41ed0ae --- /dev/null +++ b/c/_Basic/Show the ticking of Clock.c @@ -0,0 +1,104 @@ + #include + #include + #include + #include + #include + // Calculates new co-ordinates of a figure after + // rotating it at an angle about a point (cx,cy) + void rotate( int figure[], int edges, double angle, int cx, int cy ) { + double x, y; + angle = -1 * (angle*3.14/180); + double cos_a = cos(angle); + double sin_a = sin(angle); + for (int i=0; i < edges; i++) { + x = figure[2*i] - cx; + y = figure[2*i+1] - cy; + figure[2*i] = floor( (x * cos_a) - (y * sin_a) + cx + 0.5 ); + figure[2*i+1] = floor( (x * sin_a)+(y * cos_a) + cy + 0.5 ); + } + } + void drawClock(int,int,int); + void main() { + int second_hand[4],minute_hand[4], hour_hand[4], edges = 2 ; + double angle; + int cx=300, cy=200; + int gd = DETECT, gm; + initgraph( &gd, &gm, "" ); + int max_y = getmaxy(); + clrscr(); + cleardevice(); + angle = -6; + // Set the initial position of the second, minute and the hour hands. + second_hand[0] = cx ; + second_hand[1] = max_y - cy; + second_hand[2] = cx; + second_hand[3] = max_y - 320; + hour_hand[0] = cx; + hour_hand[1] = max_y - cy; + hour_hand[2] = cx + 90; + hour_hand[3] = max_y - 200; + minute_hand[0] = cx; + minute_hand[1] = max_y - cy; + minute_hand[2] = cx; + minute_hand[3] = max_y - 310; + cleardevice(); + setbkcolor(WHITE); + // Draw the clock + drawClock(cx,max_y - cy,150); + setlinestyle(SOLID_FILL,0,1); + // Draw the minute and the hour hand + drawpoly(2,minute_hand); + drawpoly(2,hour_hand); + int i=0; + while(!kbhit()) { + setcolor(RED); + drawpoly(2,second_hand); + setcolor(GREEN); + drawpoly(2,minute_hand); + setcolor(BLUE); + drawpoly(2,hour_hand); + delay(1000); + // set delay(10) to tick the clock fast + setcolor(15); + drawpoly(2,second_hand); + rotate(second_hand,edges,angle,cx,max_y - cy); + i++; + // Reset the second hand and move the minute hand + // when the second hand has moved 60 times. + if(i%60 == 0) { + second_hand[0] = cx ; + second_hand[1] = max_y - cy; + second_hand[2] = cx; + second_hand[3] = max_y - 320; + drawpoly(2,minute_hand); + rotate(minute_hand,edges,angle,cx,max_y - cy); + } + // Move the minute hand + // when the second hand has moved 720 (60*12) times. + if(i%720 == 0) { + i = 0; + drawpoly(2,hour_hand); + rotate(hour_hand,edges,angle,cx,max_y - cy); + } + } + getch(); + } + // Function to draw the clock + void drawClock(int cx, int cy, int r) { + setcolor(GREEN); + setlinestyle(SOLID_FILL,0,3); + circle(cx,cy,r); + int max_y = getmaxy(); + int center[2] = { + cx, max_y - 340 + } + ; + for (int i=0; i<60; i++) { + if(i%5 == 0) { + circle(center[0],center[1],2); + } else { + circle(center[0],center[1],1); + } + rotate(center,1,-6,cx,cy); + } + } \ No newline at end of file diff --git a/c/_Basic/Time functions in c.c b/c/_Basic/Time functions in c.c new file mode 100644 index 0000000..1e22ad8 --- /dev/null +++ b/c/_Basic/Time functions in c.c @@ -0,0 +1,36 @@ + #include + #include + #include + void main() + { + time_t now; + clrscr(); + now = time((time_t *)NULL); + + printf("%s", ctime(&now)); + + time(&now); + + printf("%s", ctime(&now)); + { + struct tm *l_time; + + l_time = localtime(&now); + printf("%s", asctime(l_time)); + } + + time(&now); + printf("%s", asctime(localtime( &now ))); + { + + struct tm *l_time; + char string[20]; + + time(&now); + l_time = localtime(&now); + strftime(string, sizeof string, "%d-%b-%y\n", l_time); + printf("%s", string); + } + + getch(); + } \ No newline at end of file diff --git a/c/_Basic/To compute the average of n given numbers using pointers.c b/c/_Basic/To compute the average of n given numbers using pointers.c new file mode 100644 index 0000000..d277e16 --- /dev/null +++ b/c/_Basic/To compute the average of n given numbers using pointers.c @@ -0,0 +1,26 @@ + #include + #include + void main() + { + int n,*p,sum=0,i; + float avg; + clrscr(); + printf("\nHOW MANY NUMBERS: "); + scanf("%d",&n); + p=(int *) malloc(n*2); + if(p==NULL) + { + printf("\nMEMORY ALLOCATION UNSUCCCESSFUL"); + exit(); + } + for(i=0;i + #include + void main() + { + long unsigned age,sec; + clrscr(); + printf("\nENTER YOUR AGE: "); + scanf("%lu",&age); + sec=age*365*24*60*60; + printf("\nAGE IN SECONDS: %lu",sec); + getch(); + } \ No newline at end of file diff --git a/c/_Basic/To find the maximum number within n given numbers using pointers.c b/c/_Basic/To find the maximum number within n given numbers using pointers.c new file mode 100644 index 0000000..821f02f --- /dev/null +++ b/c/_Basic/To find the maximum number within n given numbers using pointers.c @@ -0,0 +1,28 @@ + #include + #include + void main() + { + int n,*p,i,h=0; + clrscr(); + printf("\nHOW MANY NUMBERS: "); + scanf("%d",&n); + p=(int *) malloc(n*2); + if(p==NULL) + { + printf("\nMEMORY ALLOCATION UNSUCCCESSFUL"); + exit(); + } + for(i=0;ih) + h=*(p+i); + } + printf("\nTHE HIGHEST NUMBER IS %d",h); + getch(); + } \ No newline at end of file diff --git a/c/_Basic/To swap the address of two variables using pointer.c b/c/_Basic/To swap the address of two variables using pointer.c new file mode 100644 index 0000000..4c99b7b --- /dev/null +++ b/c/_Basic/To swap the address of two variables using pointer.c @@ -0,0 +1,20 @@ + #include + #include + void swap(int *,int *); + void main() + { + int a=10,b=20; + clrscr(); + printf("\nVALUES OF a AND b BEFORE SWAPING ARE %d %d",a,b); + swap(&a,&b); + printf("\nVALUES OF a AND b AFTER SWAPING ARE %d %d",a,b); + getch(); + } + void swap(x,y) + int *x,*y; + { + int t; + t=*x; + *x=*y; + *y=t; + } \ No newline at end of file diff --git a/c/_Basic/What happens if you free a pointer twice.c b/c/_Basic/What happens if you free a pointer twice.c new file mode 100644 index 0000000..0e28b67 --- /dev/null +++ b/c/_Basic/What happens if you free a pointer twice.c @@ -0,0 +1,21 @@ + #include + #include + int main(int argc, char** argv) { + char** new_argv1; + char** new_argv2; + new_argv1 = calloc(argc+1, sizeof(char*)); + free(new_argv1); + /* freed once */ + new_argv2 = (char**) calloc(argc+1, sizeof(char*)); + if (new_argv1 == new_argv2) { + /* new_argv1 accidentally points to freeable memory */ + free(new_argv1); + /* freed twice */ + } else { + free(new_argv2); + } + new_argv1 = calloc(argc+1, sizeof(char*)); + free(new_argv1); + /* freed once again */ + return 0; + } \ No newline at end of file diff --git a/c/_Basic/Write a c program to check given string is palindrome number or not.c b/c/_Basic/Write a c program to check given string is palindrome number or not.c new file mode 100644 index 0000000..2fdf3ef --- /dev/null +++ b/c/_Basic/Write a c program to check given string is palindrome number or not.c @@ -0,0 +1,18 @@ + #include + #include + void main() { + char *a; + int i,len,flag=0; + clrscr(); + printf("\nENTER A STRING: "); + gets(a); + len=strlen(a); + for (i=0;i + struct circ_list { + char value[ 3 ]; + /* e.g., "st" (incl '') */ + struct circ_list *next; + } + ; + struct circ_list suffixes[] = { + "th", & suffixes[ 1 ], + /* 0th */ + "st", & suffixes[ 2 ], + /* 1st */ + "nd", & suffixes[ 3 ], + /* 2nd */ + "rd", & suffixes[ 4 ], + /* 3rd */ + "th", & suffixes[ 5 ], + /* 4th */ + "th", & suffixes[ 6 ], + /* 5th */ + "th", & suffixes[ 7 ], + /* 6th */ + "th", & suffixes[ 8 ], + /* 7th */ + "th", & suffixes[ 9 ], + /* 8th */ + "th", & suffixes[ 0 ], + /* 9th */ + } + ; + #define MAX 20 + int main() { + int i = 0; + struct circ_list *p = suffixes; + while (i value ); + ++i; + p = p->next; + } + return 0; + } \ No newline at end of file diff --git a/c/_Basic/null pointer in c.c b/c/_Basic/null pointer in c.c new file mode 100644 index 0000000..fee473f --- /dev/null +++ b/c/_Basic/null pointer in c.c @@ -0,0 +1,15 @@ + /* A simple program that prints all its arguments. + It doesn't use argc ("argument count"); instead, + it takes advantage of the fact that the last value + in argv ("argument vector") is a null pointer. */ + #include + #include + int + main( int argc, char **argv) { + int i; + printf("program name = \"%s\"\n", argv[0]); + for (i=1; argv[i] != NULL; ++i) + printf("argv[%d] = \"%s\"\n", i, argv[i]); + assert(i == argc); + return 0; + } \ No newline at end of file diff --git a/css/A CSS comment.html b/css/A CSS comment.html new file mode 100644 index 0000000..969805b --- /dev/null +++ b/css/A CSS comment.html @@ -0,0 +1,25 @@ + + + + + + CSS comment + + + + + +

CSS comment

+ +

I Love ClementineInner span +

+ + \ No newline at end of file diff --git a/css/A Hidden Control.html b/css/A Hidden Control.html new file mode 100644 index 0000000..abb044a --- /dev/null +++ b/css/A Hidden Control.html @@ -0,0 +1,24 @@ + + + + + + A hidden control + + + + + +Truly love you endlessly.
+Every day without you is like a book without pages.
+I love you, I will always do, for the rest of our earthly and heavenly life.
+

+F. Abahusain + + +
+ + +
+ + \ No newline at end of file diff --git a/css/A blockquote with a cite attribute.html b/css/A blockquote with a cite attribute.html new file mode 100644 index 0000000..d5cf41a --- /dev/null +++ b/css/A blockquote with a cite attribute.html @@ -0,0 +1,20 @@ + + + + + +A blockquote with a cite attribute + + + + +
+

code examples www.happycodings.com code examples

+
+ + \ No newline at end of file diff --git a/css/A link to send an Email.html b/css/A link to send an Email.html new file mode 100644 index 0000000..12c7bee --- /dev/null +++ b/css/A link to send an Email.html @@ -0,0 +1,12 @@ + + + + + + happycodings.com - A link to send an email + + + +

happycodings.com@gmail.com

+ + \ No newline at end of file diff --git a/css/A link with a title attribute.html b/css/A link with a title attribute.html new file mode 100644 index 0000000..12d2282 --- /dev/null +++ b/css/A link with a title attribute.html @@ -0,0 +1,12 @@ + + + + + + A link with a title attribute - see the tooltip when you hover over the link + + + +

HappyCodings.

+ + \ No newline at end of file diff --git a/css/A nested ordered list.html b/css/A nested ordered list.html new file mode 100644 index 0000000..c4b63c5 --- /dev/null +++ b/css/A nested ordered list.html @@ -0,0 +1,28 @@ + + + + + + Unordered Lists + + + + +

nested ordered list example:

+ +
    +
  1. apple
  2. +
  3. pear
  4. +
  5. pomegranate
  6. +
  7. +
      +
    1. watermelon
    2. +
    3. banana
    4. +
    5. cherry
    6. +
    +
  8. +
  9. mulberry
  10. +
+ + + diff --git a/css/A prepopulated text field with a maximum length.html b/css/A prepopulated text field with a maximum length.html new file mode 100644 index 0000000..4ce0b2e --- /dev/null +++ b/css/A prepopulated text field with a maximum length.html @@ -0,0 +1,16 @@ + + + + + A prepopulated text field with a maximum length + + + + +
+

+

+
+ + + \ No newline at end of file diff --git a/css/A tag active.html b/css/A tag active.html new file mode 100644 index 0000000..1538a04 --- /dev/null +++ b/css/A tag active.html @@ -0,0 +1,12 @@ + + +A Tag Active + + + +

Press tab key to bring the link into focus.

+happycodings.com Programming Code Examples + + \ No newline at end of file diff --git a/css/A tag datafld dataformatas datasrc.html b/css/A tag datafld dataformatas datasrc.html new file mode 100644 index 0000000..2c71514 --- /dev/null +++ b/css/A tag datafld dataformatas datasrc.html @@ -0,0 +1,14 @@ + + +datafld attribute Example + + + + + + + diff --git a/css/A tag visited hyperlink.html b/css/A tag visited hyperlink.html new file mode 100644 index 0000000..05ec3d5 --- /dev/null +++ b/css/A tag visited hyperlink.html @@ -0,0 +1,24 @@ + + + +A Tag Visited Hyperlink + + + + + +

Programming Code Examples - +Visited Link +

+ + + + \ No newline at end of file diff --git a/css/Absolute container and absolute children.html b/css/Absolute container and absolute children.html new file mode 100644 index 0000000..5e3848e --- /dev/null +++ b/css/Absolute container and absolute children.html @@ -0,0 +1,55 @@ + + + +CSS Positioning Example + + + + + +
+

CSS Positioning Example

+

This is paragraph one.

+ +Truly love you endlessly.
+Every day without you is like a book without pages.
+I love you, I will always do, for the rest of our earthly and heavenly life.
+

+ +F. Abahusain +

+

This is paragraph two.

+
+ + + + diff --git a/css/Absolute position offset no-width no-height.html b/css/Absolute position offset no-width no-height.html new file mode 100644 index 0000000..d4a5fee --- /dev/null +++ b/css/Absolute position offset no-width no-height.html @@ -0,0 +1,31 @@ + + + + Absolute Position Offset no-width no-height + + + +
+ True love is indescribable, yet self-explanatory.

+ Anonymous
+ +
+
+ A baby is born with a need to be loved - and never outgrows it.

+ Frank Howard Clark
+
+ + \ No newline at end of file diff --git a/css/Absolute position offset top right bottom left.html b/css/Absolute position offset top right bottom left.html new file mode 100644 index 0000000..f3934db --- /dev/null +++ b/css/Absolute position offset top right bottom left.html @@ -0,0 +1,37 @@ + + + + Absolute Position Offset Top Right Bottom Left + + + +
+ Arguments out of a pretty mouth are unanswerable.

+ Joseph Addison
+
+
+ If I don't know what true love is, how will I ever find it?

+ Anonymous
+
+ + \ No newline at end of file diff --git a/css/Absolute position to the bottom.html b/css/Absolute position to the bottom.html new file mode 100644 index 0000000..598dc1d --- /dev/null +++ b/css/Absolute position to the bottom.html @@ -0,0 +1,59 @@ + + + + + + Absolute position to the bottom + + + + + +
If I don't know what true love is, how will I ever find it?
+ Anonymous
+ +
A kiss is a lovely trick designed by nature to stop speech
+ when words become superfluous.
+ Ingrid Bergman
+ +
True love is just like rain; it touches us all.
+ Anonymous
+ +
In real love you want the other person's good.
+ In romantic love, you want the other person.
+ Margaret Anderson
+ + + + \ No newline at end of file diff --git a/css/Absolute position top right bottom.html b/css/Absolute position top right bottom.html new file mode 100644 index 0000000..f3811fa --- /dev/null +++ b/css/Absolute position top right bottom.html @@ -0,0 +1,38 @@ + + + + Absolute position top right bottom + + + +

+ True love is just like rain; it touches us all.
+ Anonymous +

+

+ Love grows by giving.
+ The love we give away is the only love we keep.
+ The only way to retain love is to give it away.

+ + Elbert Hubbard +

+ + diff --git a/css/Absolute positioning for header.html b/css/Absolute positioning for header.html new file mode 100644 index 0000000..f5676c6 --- /dev/null +++ b/css/Absolute positioning for header.html @@ -0,0 +1,46 @@ + + + + + + Absolute Positioning For Header + + + + +
Absolute Positioning For Header
+ +



+ +

A smile is nearly always inspired by another smile.
+anonymous

+ +For it was not into my ear you whispered, but into my heart.
+It was not my lips you kissed, but my soul.

+ +Judy Garland

+ + + + diff --git a/css/Acceptcharset nonstandard character sets.html b/css/Acceptcharset nonstandard character sets.html new file mode 100644 index 0000000..a8bd195 --- /dev/null +++ b/css/Acceptcharset nonstandard character sets.html @@ -0,0 +1,12 @@ + +Acceptcharset UTF-8 + +
+ +
+ + \ No newline at end of file diff --git a/css/Accesskey element.html b/css/Accesskey element.html new file mode 100644 index 0000000..a7fe93d --- /dev/null +++ b/css/Accesskey element.html @@ -0,0 +1,10 @@ + +Accesskey Attribute + +
+ +
+ + \ No newline at end of file diff --git a/css/Action element Attribute.html b/css/Action element Attribute.html new file mode 100644 index 0000000..e61202d --- /dev/null +++ b/css/Action element Attribute.html @@ -0,0 +1,14 @@ + +Action Attribute + +
+ Enter the your choice: + + +
+ + diff --git a/css/Action script and textfield.html b/css/Action script and textfield.html new file mode 100644 index 0000000..1d76da7 --- /dev/null +++ b/css/Action script and textfield.html @@ -0,0 +1,16 @@ + + + +
+ +Type your name: + +
Type your favorite movie: + +
+ + +
+ + + \ No newline at end of file diff --git a/css/Add background image, margin, padding DD.html b/css/Add background image, margin, padding DD.html new file mode 100644 index 0000000..dd51926 --- /dev/null +++ b/css/Add background image, margin, padding DD.html @@ -0,0 +1,17 @@ +Add background image, margin, padding DD + + + +Add background image margin padding DD + + + + + \ No newline at end of file diff --git a/css/Add border line to title text.html b/css/Add border line to title text.html new file mode 100644 index 0000000..91ec50e --- /dev/null +++ b/css/Add border line to title text.html @@ -0,0 +1,21 @@ + + + + + Add border line to title text + + + + +
+

Man loves little and often: Woman much and rarely.

+
+ + + \ No newline at end of file diff --git a/css/Add form controls to paragraph.html b/css/Add form controls to paragraph.html new file mode 100644 index 0000000..559bac6 --- /dev/null +++ b/css/Add form controls to paragraph.html @@ -0,0 +1,33 @@ +Add form controls to paragraph + + + + + + Add form controls to paragraph + + + + +
+
+

+ Your Name:
+ Your Email:
+ +

+
+
+ + + diff --git a/css/Add no repeat icon to title text.html b/css/Add no repeat icon to title text.html new file mode 100644 index 0000000..9b2367f --- /dev/null +++ b/css/Add no repeat icon to title text.html @@ -0,0 +1,31 @@ + + + + + Add no repeat icon to title text + + + + + +
+

One kiss breaches the distance between friendship and love.

+
+ + + \ No newline at end of file diff --git a/css/Add style to an anchor in a LI tag.html b/css/Add style to an anchor in a LI tag.html new file mode 100644 index 0000000..60e2deb --- /dev/null +++ b/css/Add style to an anchor in a LI tag.html @@ -0,0 +1,22 @@ + + +Add style to an anchor in a LI tag + + + +
    +
  • X
  • + +
  • Y
  • + +
  • Z
  • +
+ + \ No newline at end of file diff --git a/css/Add style to ul and li.html b/css/Add style to ul and li.html new file mode 100644 index 0000000..41afd08 --- /dev/null +++ b/css/Add style to ul and li.html @@ -0,0 +1,40 @@ +Add style to ul and li + + + + + +Add style to ul and li + + + + + +

Add style to ul and li

+

Sections:

+
    +
  • I love thee, I love but thee
  • +
  • With a love that shall not die
  • +
  • Till the sun grows cold
  • +
  • And the stars grow old
  • +
  • I Love Clementine
  • +
+

I love thee, I love but thee
+ With a love that shall not die
+ Till the sun grows cold
+ And the stars grow old.

+ + Willam Shakespeare

+ + + + + diff --git a/css/Adding a YouTube Video with object.html b/css/Adding a YouTube Video with object.html new file mode 100644 index 0000000..c80acde --- /dev/null +++ b/css/Adding a YouTube Video with object.html @@ -0,0 +1,18 @@ + + + + + + Adding a YouTube Video + + + + +

Embedding a YouTube Video

+ + + + + + + \ No newline at end of file diff --git a/css/Adding a flash movie with the object element.html b/css/Adding a flash movie with the object element.html new file mode 100644 index 0000000..1af37f4 --- /dev/null +++ b/css/Adding a flash movie with the object element.html @@ -0,0 +1,16 @@ + + + + + Adding a flash movie with the object element + + +

+ + + + + +

+ + \ No newline at end of file diff --git a/css/Adding an MP3 player using Flash.html b/css/Adding an MP3 player using Flash.html new file mode 100644 index 0000000..5d7264b --- /dev/null +++ b/css/Adding an MP3 player using Flash.html @@ -0,0 +1,20 @@ +Adding an MP3 player using Flash + + + + + + Adding an MP3 player using Flash + + + +

Flash MP3 Player Using object element

+ + + + + + + + diff --git a/css/Adding an MP3 without specifying player.html b/css/Adding an MP3 without specifying player.html new file mode 100644 index 0000000..0477428 --- /dev/null +++ b/css/Adding an MP3 without specifying player.html @@ -0,0 +1,16 @@ + + + + + Adding an MP3 without specifying player + + + + + + + + + + + \ No newline at end of file diff --git a/css/Adding an XHTML DOCTYPE declaration.html b/css/Adding an XHTML DOCTYPE declaration.html new file mode 100644 index 0000000..8f3cbe0 --- /dev/null +++ b/css/Adding an XHTML DOCTYPE declaration.html @@ -0,0 +1,14 @@ + + +XHTML 1.0 Strict : + + + + +XHTML 1.0 Frameset : + + + \ No newline at end of file diff --git a/css/Adding underline for labels.html b/css/Adding underline for labels.html new file mode 100644 index 0000000..336d26e --- /dev/null +++ b/css/Adding underline for labels.html @@ -0,0 +1,40 @@ + + + + +Adding underline for labels + + + + +
+ + + + + + + + + + + + + +
+ + + \ No newline at end of file diff --git a/css/Align baseline lowered raised.html b/css/Align baseline lowered raised.html new file mode 100644 index 0000000..27eaed4 --- /dev/null +++ b/css/Align baseline lowered raised.html @@ -0,0 +1,42 @@ + + + + + Align baseline lowered raised + + + +
+

+ Aligned to baseline. Sex is a momentary itch, love never lets you go. + Lowered relative to the baseline. Love can make you do things that you never thought possible. + Raised relative to... The kiss, a sweet discovery of oneself after a long search. + +

+ +
+ + + + diff --git a/css/Align in a row one by one for floating blocks.html b/css/Align in a row one by one for floating blocks.html new file mode 100644 index 0000000..8fe332b --- /dev/null +++ b/css/Align in a row one by one for floating blocks.html @@ -0,0 +1,44 @@ + + + + Align in a row one by one for floating blocks + + + +
+
+ You will find, as you look back upon your life,
+ that the moments when you really lived are the moments
+ when you have done things in the spirit of love.

+ + Henry Drummond +
+

+ I love thee, I love but thee
+ With a love that shall not die
+ Till the sun grows cold
+ And the stars grow old.

+ + Willam Shakespeare +

+
+ + \ No newline at end of file diff --git a/css/Align text block to the right with margin auto and background attachment.html b/css/Align text block to the right with margin auto and background attachment.html new file mode 100644 index 0000000..d10cb32 --- /dev/null +++ b/css/Align text block to the right with margin auto and background attachment.html @@ -0,0 +1,39 @@ + + + + Align text block to the right with margin auto and background-attachment + + + +

Opposites attract, but after marriage, opposites attack.
+ Most of the time, we are attracted to people who don't have
+ the things that we have.
+ Incompatibility is why we get married,
+ but it's also used as a reason to divorce.
+ Incompatibility is just a lack of communication.
+ If we just try to love [our spouse] the way we want to be loved,
+ we are in trouble.
+ Unless you communicate,
+ it's difficult to know how to love another person.

+ + Dr. Charles Lowery +

+ + + + diff --git a/css/Align the form controls with table.html b/css/Align the form controls with table.html new file mode 100644 index 0000000..7279583 --- /dev/null +++ b/css/Align the form controls with table.html @@ -0,0 +1,39 @@ + + + + + + + Align the form controls with table + + + +

Reply to seller

+

Use the following form to respond to seller:

+ +
+ + + + + + + + + + + + + + + + + +
+ + +
+ + + + diff --git a/css/Aligned and Offset Static Table.html b/css/Aligned and Offset Static Table.html new file mode 100644 index 0000000..ae36b89 --- /dev/null +++ b/css/Aligned and Offset Static Table.html @@ -0,0 +1,37 @@ + + + + + Aligned and Offset Static Table + + + + +
+
I love thee, I love but thee
+ With a love that shall not die
+ Till the sun grows cold
+ And the stars grow old.

+ + Willam Shakespeare
+
+ + + + + + diff --git a/css/Aligning labels with List.html b/css/Aligning labels with List.html new file mode 100644 index 0000000..0934259 --- /dev/null +++ b/css/Aligning labels with List.html @@ -0,0 +1,30 @@ + + + + + Aligning labels with List + + + + + +
+
    +
  • +
  • +
  • +
+
+ + + \ No newline at end of file diff --git a/css/Anchor background-color.html b/css/Anchor background-color.html new file mode 100644 index 0000000..caddc4b --- /dev/null +++ b/css/Anchor background-color.html @@ -0,0 +1,53 @@ + + + + +Anchor background-color + + + + + + + + diff --git a/css/Anchor background-position.html b/css/Anchor background-position.html new file mode 100644 index 0000000..bd4a246 --- /dev/null +++ b/css/Anchor background-position.html @@ -0,0 +1,54 @@ + + + + +Anchor background-position + + + + + + + + + diff --git a/css/Anchor background-repeat no-repeat.html b/css/Anchor background-repeat no-repeat.html new file mode 100644 index 0000000..b0623f9 --- /dev/null +++ b/css/Anchor background-repeat no-repeat.html @@ -0,0 +1,54 @@ + + + + +Anchor background-repeat no-repeat + + + + + + + + + diff --git a/css/Anchor based tab.html b/css/Anchor based tab.html new file mode 100644 index 0000000..e5e556c --- /dev/null +++ b/css/Anchor based tab.html @@ -0,0 +1,64 @@ + + + + + Anchor based tab + + + + + + +
+ + + +
+ + + + + + diff --git a/css/Anchor display block.html b/css/Anchor display block.html new file mode 100644 index 0000000..52cc218 --- /dev/null +++ b/css/Anchor display block.html @@ -0,0 +1,54 @@ + + + + +Anchor display block + + + + + + + + + diff --git a/css/Anchor float left.html b/css/Anchor float left.html new file mode 100644 index 0000000..f22e732 --- /dev/null +++ b/css/Anchor float left.html @@ -0,0 +1,53 @@ + + + + +Anchor float left + + + + + + + + diff --git a/css/Anchor font-family.html b/css/Anchor font-family.html new file mode 100644 index 0000000..76b5cb7 --- /dev/null +++ b/css/Anchor font-family.html @@ -0,0 +1,62 @@ + + + + +Anchor font-family + + + + + + + diff --git a/css/Anchor font-size.html b/css/Anchor font-size.html new file mode 100644 index 0000000..160cd95 --- /dev/null +++ b/css/Anchor font-size.html @@ -0,0 +1,62 @@ + + + + +Anchor font-size + + + + + + + \ No newline at end of file diff --git a/css/Anchor in a LI tag.html b/css/Anchor in a LI tag.html new file mode 100644 index 0000000..4420abb --- /dev/null +++ b/css/Anchor in a LI tag.html @@ -0,0 +1,45 @@ + + + + +Anchor in a LI tag + + + + + + + + \ No newline at end of file diff --git a/css/Anchors and Images.html b/css/Anchors and Images.html new file mode 100644 index 0000000..8e4d7bf --- /dev/null +++ b/css/Anchors and Images.html @@ -0,0 +1,24 @@ + + + +Anchors and Images + + + +
Anchors and Images
+
+

+ Button with a border
+ + Logo + +

+ Same button without a border
+ + Logo + +

+
+ + + diff --git a/css/Applet code element.html b/css/Applet code element.html new file mode 100644 index 0000000..3b5cff3 --- /dev/null +++ b/css/Applet code element.html @@ -0,0 +1,14 @@ + + +Applet Code Element + + + + + + + + \ No newline at end of file diff --git a/css/Applet tag.html b/css/Applet tag.html new file mode 100644 index 0000000..3da35b5 --- /dev/null +++ b/css/Applet tag.html @@ -0,0 +1,11 @@ + + +Applet Element Example + + + + + + + + \ No newline at end of file diff --git a/css/Area Element - clickable area on a graphic or image.html b/css/Area Element - clickable area on a graphic or image.html new file mode 100644 index 0000000..babb268 --- /dev/null +++ b/css/Area Element - clickable area on a graphic or image.html @@ -0,0 +1,18 @@ + + +Area Element Example + + + + + + + + + + + \ No newline at end of file diff --git a/css/Attribute Value Selectors for input controls.html b/css/Attribute Value Selectors for input controls.html new file mode 100644 index 0000000..4dfd43a --- /dev/null +++ b/css/Attribute Value Selectors for input controls.html @@ -0,0 +1,73 @@ + + + + Attribute Value Selectors for input controls + + + +
+
+ Example Form + + + + + + + + + + + + + + + +
+ + + +
+ + + +
+ + + +
+
+
+ + diff --git a/css/Autocomplete element.html b/css/Autocomplete element.html new file mode 100644 index 0000000..6ae5b0d --- /dev/null +++ b/css/Autocomplete element.html @@ -0,0 +1,9 @@ + +Autocomplete Example + +
+ + +
+ + \ No newline at end of file diff --git a/css/B emphasizes the text in boldface.html b/css/B emphasizes the text in boldface.html new file mode 100644 index 0000000..f088483 --- /dev/null +++ b/css/B emphasizes the text in boldface.html @@ -0,0 +1,13 @@ + + +b emphasizes the text in boldface + + + The Eskimo has fifty two names for snow because it is important to them,
+ there ought to be as many for love.

+ + Margaret Atwood + + + + diff --git a/css/B tag border solid.html b/css/B tag border solid.html new file mode 100644 index 0000000..66833bf --- /dev/null +++ b/css/B tag border solid.html @@ -0,0 +1,39 @@ + + + + +A Demonstration of the Box Model + + + + + + + +

Box Model Demonstration

+

each element is treated as if it lives in its own box.

+ A baby is born with a need to be loved - and never outgrows it.

+ + Frank Howard Clark + +

+

Every element has a border around it, and some boxes can contain other boxes.

+ In real love you want the other person's good.
+ In romantic love, you want the other person.

+ + Margaret Anderson + +

+ + \ No newline at end of file diff --git a/css/B tag outline dashed.html b/css/B tag outline dashed.html new file mode 100644 index 0000000..00d2932 --- /dev/null +++ b/css/B tag outline dashed.html @@ -0,0 +1,24 @@ + + + + + + b tag outline dashed + + + + + +

Inside this paragraph the word in bold is going to have an outline.

+ +Love grows by giving.
+The love we give away is the only love we keep.
+The only way to retain love is to give it away.

+ +Elbert Hubbard

+ + \ No newline at end of file diff --git a/css/Background RGB Colors.html b/css/Background RGB Colors.html new file mode 100644 index 0000000..43f5357 --- /dev/null +++ b/css/Background RGB Colors.html @@ -0,0 +1,24 @@ + + + + + background RGB Colors + + + +
There is no fear in love;
+ but perfect love casteth out fear:
+ because fear hath torment.
+ He that feareth is not made perfect in love.

+ + The Bible
+ +
+ + + diff --git a/css/Background attachment.html b/css/Background attachment.html new file mode 100644 index 0000000..7127d13 --- /dev/null +++ b/css/Background attachment.html @@ -0,0 +1,38 @@ + + +Background Attachment + + +
+ + To fall in love is to create a religion that has a fallible god.

+ + Jorge Luis Borges +
+



+
+ + background-attachment is fixed.

+ + My love, you know you are my best friend.
+ You know that I'd do anything for you
+ And my love, let nothing come between us.
+ My love for you is strong and true.

+ + Sarah McLachlan + +
+ + diff --git a/css/Background color font and border for form control.html b/css/Background color font and border for form control.html new file mode 100644 index 0000000..3d8bee8 --- /dev/null +++ b/css/Background color font and border for form control.html @@ -0,0 +1,30 @@ + + + + + background color font and border for form control + + + +
+
+ Personal information +


+

+


+

+


+

+
+
+ + + diff --git a/css/Background color for textarea.html b/css/Background color for textarea.html new file mode 100644 index 0000000..eba09bd --- /dev/null +++ b/css/Background color for textarea.html @@ -0,0 +1,33 @@ + + + + +background color for textarea + + + + +

+ +

+ + + + + + \ No newline at end of file diff --git a/css/Background color transparent.html b/css/Background color transparent.html new file mode 100644 index 0000000..4a9ba43 --- /dev/null +++ b/css/Background color transparent.html @@ -0,0 +1,43 @@ + + + + Background Color Transparent + + + +

+ Some love lasts a lifetime. True love lasts forever. , + A kiss makes the heart young again and wipes out the years. Rupert Brooke, + This is my commandment, that ye love one another Jesus + Love is the poetry of the senses. Honore de Balzac + A loving heart is the beginning of all knowledge. Thomas Carlyle +

+ + + diff --git a/css/Background color.html b/css/Background color.html new file mode 100644 index 0000000..5b93315 --- /dev/null +++ b/css/Background color.html @@ -0,0 +1,34 @@ + + + + Background Color + + + +
+ The night has a thousand eyes, And the day but one;
+ Yet the light of the bright world dies, With the dying sun.
+ The mind has a thousand eyes, And the heart but one;
+ Yet the light of a whole life dies, When love is done.

+ + Francis William Bourdillon + +
+ + + \ No newline at end of file diff --git a/css/Background for ul tag and li tag.html b/css/Background for ul tag and li tag.html new file mode 100644 index 0000000..b95ff67 --- /dev/null +++ b/css/Background for ul tag and li tag.html @@ -0,0 +1,31 @@ + + + + +background for ul tag and li tag + + + +
    +
  • I am you and you are love and that is what makes the world go 'round. Clive Barker
  • +
  • Let no one who loves be unhappy. Even love unreturned has its rainbow. James Matthew Barrie
  • +
  • I can live without money, but I cannot live without love. Judy Garland
  • +
  • Maybe love is like luck. You have to go all the way to find it. Robert Mitchum
  • +
+ + \ No newline at end of file diff --git a/css/Background image position left right top bottom.html b/css/Background image position left right top bottom.html new file mode 100644 index 0000000..6e8b77e --- /dev/null +++ b/css/Background image position left right top bottom.html @@ -0,0 +1,47 @@ + + + +background image position left right top bottom + + + +

Nothing is miserable unless you think it is so. Boethius

+

background-position: left; I can live without money, but I cannot live without love. Judy Garland

+

background-position: right; Sometimes the heart sees what is invisible to the eye. H. Jackson Brown, Jr.

+

background-position: bottom; Love ceases to be a pleasure, when it ceases to be a secret. Aphra Behn

+

background-position: center; What will survive of us is love Philip Larkin

+ + \ No newline at end of file diff --git a/css/Background image repeat and position for anchor link hover.html b/css/Background image repeat and position for anchor link hover.html new file mode 100644 index 0000000..ca32b01 --- /dev/null +++ b/css/Background image repeat and position for anchor link hover.html @@ -0,0 +1,26 @@ + + + + +background image repeat and position for anchor link hover + + + + + + happycodings + + + + diff --git a/css/Background is inherited.html b/css/Background is inherited.html new file mode 100644 index 0000000..d6238b1 --- /dev/null +++ b/css/Background is inherited.html @@ -0,0 +1,39 @@ + + + +Background is inherited + + + +
+

My most brilliant achievement was my ability to be able
+to persuade my wife to marry me.

+ +Winston Churchill

+
+ + \ No newline at end of file diff --git a/css/Background position bottom center.html b/css/Background position bottom center.html new file mode 100644 index 0000000..c071761 --- /dev/null +++ b/css/Background position bottom center.html @@ -0,0 +1,26 @@ + + + + Background Position Bottom Center + + + +
Outside are the storms and strangers:
+ We - Oh, close, safe and warm sleep I and she, I and she . . .

+ + Robert Browning +
+ + \ No newline at end of file diff --git a/css/Background position center and background repeat repeat-x.html b/css/Background position center and background repeat repeat-x.html new file mode 100644 index 0000000..192d3d4 --- /dev/null +++ b/css/Background position center and background repeat repeat-x.html @@ -0,0 +1,43 @@ + + + + background-position + + + +
+ One look
+ One smile
+ One touch
+ One embrace
+ One kiss
+ One love
+ Two people
+ Two minds
+ Two souls
+ Two destinies
+ One road
+ One journey
+ One ending
+ Together.

+ + Melissa Higgins + +
+ + + \ No newline at end of file diff --git a/css/Background position center background repeat.html b/css/Background position center background repeat.html new file mode 100644 index 0000000..59591e6 --- /dev/null +++ b/css/Background position center background repeat.html @@ -0,0 +1,62 @@ + + + + + background-position center background-repeat + + + + +

Love Sayings Love Quotes Love Proverbs

+ +

Outside are the storms and strangers: + We - Oh, close, safe and warm sleep I and she, I and she . . . + Robert Browning

+ +

Clarity of mind means clarity of passion, too; + this is why a great and clear mind loves ardently + and sees distinctly what it loves. + Blaise Pascal

+ +

A loving heart is the beginning of all knowledge. + Thomas Carlyle

+ +

Take away love, and our earth is a tomb. + Robert Browning

+ +

My bounty is as boundless as the sea, + My love as deep; + The more I give to thee + The more I have, + For both are infinite. + William Shakespeare

+ +

Love is always open arms. + If you close your arms about love, + you will find that you are left holding only yourself. + Leo Buscaglia

+ +

My heart to you is given: + Oh, do give yours to me; + We'll lock them up together, + And throw away the key. + Frederick Saunders

+ + + \ No newline at end of file diff --git a/css/Background position.html b/css/Background position.html new file mode 100644 index 0000000..c050bd8 --- /dev/null +++ b/css/Background position.html @@ -0,0 +1,33 @@ + + +background-position + + + +
+ Never pretend to a love which you do not actually feel,
+ for love is not ours to command.

+ Alan Watts +
+



+
+ True love comes quietly, without banners or flashing lights.
+ If you hear bells, get your ears checked.

+ Erich Segal +
+ + + diff --git a/css/Background repeat repeat x.html b/css/Background repeat repeat x.html new file mode 100644 index 0000000..338bc8a --- /dev/null +++ b/css/Background repeat repeat x.html @@ -0,0 +1,34 @@ + + + + background-repeat repeat x + + + + One look
+ One smile
+ One touch
+ One embrace
+ One kiss
+ One love
+ Two people
+ Two minds
+ Two souls
+ Two destinies
+ One road
+ One journey
+ One ending
+ Together.

+ + Melissa Higgins + + + \ No newline at end of file diff --git a/css/Balloontip with a picture.html b/css/Balloontip with a picture.html new file mode 100644 index 0000000..fa0adfd --- /dev/null +++ b/css/Balloontip with a picture.html @@ -0,0 +1,46 @@ + + + + +Balloontip With A Picture + + + + +
+

+ + Love is always open arms.
+ If you close your arms about love,
+ you will find that you are left holding only yourself.
+
+

+ Leo Buscaglia +
+ + + diff --git a/css/Banner header.html b/css/Banner header.html new file mode 100644 index 0000000..3bd8e98 --- /dev/null +++ b/css/Banner header.html @@ -0,0 +1,42 @@ + + +Banner header + + + + + + + + + \ No newline at end of file diff --git a/css/Base sets a base URL for the website.html b/css/Base sets a base URL for the website.html new file mode 100644 index 0000000..5320c39 --- /dev/null +++ b/css/Base sets a base URL for the website.html @@ -0,0 +1,11 @@ + + + base element - base sets a base URL for the website + + + +

+ happycodings code examples. +

+ + \ No newline at end of file diff --git a/css/Base tag.html b/css/Base tag.html new file mode 100644 index 0000000..d080852 --- /dev/null +++ b/css/Base tag.html @@ -0,0 +1,10 @@ + + + + Base tag + + + + + + \ No newline at end of file diff --git a/css/Basefont sets a default font face size and style for an entire web page.html b/css/Basefont sets a default font face size and style for an entire web page.html new file mode 100644 index 0000000..fd67933 --- /dev/null +++ b/css/Basefont sets a default font face size and style for an entire web page.html @@ -0,0 +1,15 @@ + + + basefont element example + + + +

Set by base font. + + For in all adversity of fortune the worst sort of
+ misery is to have been happy.

+ + Boethius
+

+ + \ No newline at end of file diff --git a/css/Basic XHTML table.html b/css/Basic XHTML table.html new file mode 100644 index 0000000..6846841 --- /dev/null +++ b/css/Basic XHTML table.html @@ -0,0 +1,47 @@ + + + + + A simple XHTML table + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +
Price of Phones
PhonePrice
Nokia$120
Apple$160
Lg$80
Sony Ericsson$140
Asus$200
+ + + \ No newline at end of file diff --git a/css/Begin element.html b/css/Begin element.html new file mode 100644 index 0000000..6cf8057 --- /dev/null +++ b/css/Begin element.html @@ -0,0 +1,19 @@ + + + + + + +

Love Sayings

+

A man reserves his true and deepest love not for the species of woman
+ in whose company he finds himself electrified and enkindled,
+ but for that one in whose company he may feel tenderly drowsy.

+ +George Jean Nathan .

+
+ + + diff --git a/css/Bgsound plays a sound while the user visits the page.html b/css/Bgsound plays a sound while the user visits the page.html new file mode 100644 index 0000000..f0fbcb9 --- /dev/null +++ b/css/Bgsound plays a sound while the user visits the page.html @@ -0,0 +1,23 @@ + + + bgsound element example + + + + + test the your wav file. +





+ + +
+ + + + diff --git a/css/Bidirectional override.html b/css/Bidirectional override.html new file mode 100644 index 0000000..361157a --- /dev/null +++ b/css/Bidirectional override.html @@ -0,0 +1,23 @@ + + + + + Bidirectional override + + + +

A passage of text containing one reversed word. + + I have learned not to worry about love;
+ but to honor its coming with all my heart.

+ + Alice Walker + + Alice Walker + +

+ + + + + diff --git a/css/Big Example.html b/css/Big Example.html new file mode 100644 index 0000000..6566720 --- /dev/null +++ b/css/Big Example.html @@ -0,0 +1,17 @@ + + + big element example + + +

+ + Love is born of faith, lives on hope, and dies of charity.Anonymous +

+ A woman would run through fire and water for such a kind heart.William Shakespeare +

+ There is no instinct like that of the heart.Lord Byron + +

+ + + diff --git a/css/Block Box.html b/css/Block Box.html new file mode 100644 index 0000000..6c8f758 --- /dev/null +++ b/css/Block Box.html @@ -0,0 +1,33 @@ + + + + +Block Box + + + + +
+
Before
+
Romantic love reaches out in little ways,
+ showing attention and admiration.
+ Romantic love remembers what pleases a woman,
+ what excites her, and what surprises her.
+ Its actions whisper:
+ you are the most special person in my life.

+ + Charles Stanley (A Man's Touch)
+
After
+
+ + \ No newline at end of file diff --git a/css/Block Quotation - Blockquote Tag.html b/css/Block Quotation - Blockquote Tag.html new file mode 100644 index 0000000..b6ea9b3 --- /dev/null +++ b/css/Block Quotation - Blockquote Tag.html @@ -0,0 +1,18 @@ + + + + + Block quotation + + + + +

Love Sayings

+

Whatever our souls are made of, his and mine are the same. Emily Bronte

+ +
+

Love is life. And if you miss love, you miss life. Leo Buscaglia

+
+ + + \ No newline at end of file diff --git a/css/Block divider.html b/css/Block divider.html new file mode 100644 index 0000000..c521ccc --- /dev/null +++ b/css/Block divider.html @@ -0,0 +1,30 @@ + + + + + Block divider + + + + +

There is no instinct like that of the heart. Lord Byron

+ +
+ +

We loved with a love that was more than love. Edgar Allan Poe

+ + \ No newline at end of file diff --git a/css/Block-level elements.html b/css/Block-level elements.html new file mode 100644 index 0000000..5854d0c --- /dev/null +++ b/css/Block-level elements.html @@ -0,0 +1,13 @@ + + + + + + Block and Inline Elements + + +

Block-Level Elements

+

Block-level elements The +

and

.

+ + \ No newline at end of file diff --git a/css/Blocked and preserved Code.html b/css/Blocked and preserved Code.html new file mode 100644 index 0000000..c88bacc --- /dev/null +++ b/css/Blocked and preserved Code.html @@ -0,0 +1,35 @@ + + + + + Blocked and preserved Code + + + +

+ + + *.blocked { display:block; } + *.preserved { white-space:pre; } + *.code { font-family:monospace; } + + A.style{text-decoration:none; font-size:14; font-family:Courier New; color:black} + A:Visited.style{color:black} + A:Hover.style{font-size:15; color:#204cef} + + + +

+ + + + diff --git a/css/Blockquote background-color.html b/css/Blockquote background-color.html new file mode 100644 index 0000000..79d2d3c --- /dev/null +++ b/css/Blockquote background-color.html @@ -0,0 +1,66 @@ + + + + +blockquote background-color + + + + + +

Perfect love is rare indeed - for to be a lover
+ will require that you continually have the subtlety
+ of the very wise, the flexibility of the child,
+ the sensitivity of the artist,
+ the understanding of the philosopher,
+ the acceptance of the saint,
+ the tolerance of the scholar and
+ the fortitude of the certain.

+ + Leo Buscaglia

+ +
+

We perceive when love begins and when it declines
+ by our embarrassment when alone together.

+ + Jean de la Bruyere

+
+ +

Love alone is capable of uniting living beings in such
+ a way as to complete and fulfill them,
+ for it alone takes them and joins them
+ by what is deepest in themselves.

+ + Pierre Teilhard de Chardin

+ +

Love is the big booming beat which covers up the noise of hate.

+ + Margaret Cho.

+ +

All thoughts, all passions, all delights Whatever stirs this mortal frame
+ All are but ministers of Love And feed his sacred flame.

+ + Samuel Taylor Coleridge

+ + \ No newline at end of file diff --git a/css/Blockquote float left.html b/css/Blockquote float left.html new file mode 100644 index 0000000..ce728a4 --- /dev/null +++ b/css/Blockquote float left.html @@ -0,0 +1,60 @@ + + + + +blockquote float left + + + + + +

All thoughts, all passions, all delights Whatever stirs this mortal frame
+ All are but ministers of Love And feed his sacred flame.

+ + Samuel Taylor Coleridge.

+ +
+

Never marry but for love; but see that thou lovest what is lovely.

+ + William Penn

+
+ +

Love withers with predictability;
+ its very essence is surprise and amazement.
+ To make love a prisoner of the mundane is to
+ take its passion and lose it forever.

+ + Leo Buscaglia

+ +

Whatever our souls are made of, his and mine are the same.

+ + Emily Bronte

+ +

Love means not ever having to say you're sorry.

+ + Erich Segal

+ + + + diff --git a/css/Blockquote p before blockquote p after.html b/css/Blockquote p before blockquote p after.html new file mode 100644 index 0000000..96e4276 --- /dev/null +++ b/css/Blockquote p before blockquote p after.html @@ -0,0 +1,45 @@ + + + + blockquote p before blockquote p after + + + + + + +
+

Such is the inconsistency of real love,
+ that it is always awake to suspicion, however unreasonable;
+ always requiring new assurances from the object of its interest.

+ + Ann Radcliffe, The Mysteries of Udolpho

+ Emerson +
+ + + + diff --git a/css/Blockquote with image.html b/css/Blockquote with image.html new file mode 100644 index 0000000..45ec9d4 --- /dev/null +++ b/css/Blockquote with image.html @@ -0,0 +1,60 @@ + + + + +blockquote with image + + + + + +

Love is life. And if you miss love, you miss life. Leo Buscaglia

+ +
+

To laugh often and love much... to appreciate beauty,
+ to find the best in others, to give one's self...
+ this is to have succeeded.

+ + Ralph Waldo Emerson

+
+ +

We waste time looking for the perfect lover,
+ instead of creating the perfect love.

+ + Tom Robbins

+ +

To love deeply in one direction makes us more loving in all others.

+ + Anne-Sophie Swetchine

+ +

Love is always bestowed as a gift - freely,
+ willingly and without expectation.
+ We don't love to be loved; we love to love.

+ + Leo Buscaglia

+ + \ No newline at end of file diff --git a/css/Body background-attachment scroll.html b/css/Body background-attachment scroll.html new file mode 100644 index 0000000..c623d2a --- /dev/null +++ b/css/Body background-attachment scroll.html @@ -0,0 +1,33 @@ + + + + + Body background-attachment: scroll + + + +

Love Sayings

+

Gravity. It keeps you rooted to the ground.
+ In space, there's not any gravity.
+ You just kind of leave your feet and go floating around.
+ Is that what being in love is like?

+ + Josh Brand and John Falsey +

+ + + + \ No newline at end of file diff --git a/css/Body border ridge.html b/css/Body border ridge.html new file mode 100644 index 0000000..707991f --- /dev/null +++ b/css/Body border ridge.html @@ -0,0 +1,27 @@ + + + + +Body border ridge + + + + +

Love Sayings

+

I will find out where she has gone,
+ And kiss her lips and take her hands.
+ And pluck till time and times are done
+ The silver apples of the moon,
+ The golden apples of the sun.

+ + William Butler Yeats +

+ + + \ No newline at end of file diff --git a/css/Body tag font-family.html b/css/Body tag font-family.html new file mode 100644 index 0000000..54cf213 --- /dev/null +++ b/css/Body tag font-family.html @@ -0,0 +1,44 @@ + + + + + + body tag font-family + + + + + + +

Font Properties

+

Love is always bestowed as a gift - freely,
+ willingly and without expectation.
+ We don't love to be loved; we love to love.

+ + Leo Buscaglia

+ +

Gravity. It keeps you rooted to the ground.
+ In space, there's not any gravity.
+ You just kind of leave your feet and go floating around.
+ Is that what being in love is like?

+ + Josh Brand and John Falsey

+ +

Love is always bestowed as a gift - freely,
+ willingly and without expectation.
+ We don't love to be loved; we love to love.

+ + Leo Buscaglia

+ + + diff --git a/css/Body tag font-size Percentange larger.html b/css/Body tag font-size Percentange larger.html new file mode 100644 index 0000000..d2c5e0b --- /dev/null +++ b/css/Body tag font-size Percentange larger.html @@ -0,0 +1,23 @@ + + + + body tag font-size Percentange larger + + + + To love deeply in one direction makes us more loving in all others.

+ Anne-Sophie Swetchine
+

+ Love is always bestowed as a gift - freely,
+ willingly and without expectation.
+ We don't love to be loved; we love to love.

+ + Leo Buscaglia +

+ + + diff --git a/css/Body tag top left value.html b/css/Body tag top left value.html new file mode 100644 index 0000000..d767d63 --- /dev/null +++ b/css/Body tag top left value.html @@ -0,0 +1,30 @@ + + + + +Body tag top left value + + + + + +

Love Sayings

+ +

Gravity. It keeps you rooted to the ground.
+ In space, there's not any gravity.
+ You just kind of leave your feet and go floating around.
+ Is that what being in love is like?

+ + Josh Brand and John Falsey

+ + + + diff --git a/css/Body tag.html b/css/Body tag.html new file mode 100644 index 0000000..ea36f3d --- /dev/null +++ b/css/Body tag.html @@ -0,0 +1,17 @@ + + + + Love Sayings + + + +I will find out where she has gone,
+And kiss her lips and take her hands.
+And pluck till time and times are done
+The silver apples of the moon,
+The golden apples of the sun.

+ +William Butler Yeats + + + \ No newline at end of file diff --git a/css/Body text-align center.html b/css/Body text-align center.html new file mode 100644 index 0000000..7d069a2 --- /dev/null +++ b/css/Body text-align center.html @@ -0,0 +1,26 @@ + + + +body text-align center + + + + +

Love is an energy - it can neither be created nor destroyed.
+ It just is and always will be,
+ giving meaning to life and direction to goodness...
+ Love will never die. (Celeste in "April Fools Day")

+ + Bryce Courtney +

+ + \ No newline at end of file diff --git a/css/Body text-align left.html b/css/Body text-align left.html new file mode 100644 index 0000000..8ad4113 --- /dev/null +++ b/css/Body text-align left.html @@ -0,0 +1,24 @@ + + +Body text-align left + + + + + + +

May your love soar on the wings of a dove in flight. + Debbie Crabtree

+ + diff --git a/css/Border Samples - Border styles color size.html b/css/Border Samples - Border styles color size.html new file mode 100644 index 0000000..22c47f4 --- /dev/null +++ b/css/Border Samples - Border styles color size.html @@ -0,0 +1,103 @@ + + +Border Samples - Border styles color size + + + +

Dotted - One's first love is always perfect until one meets one's second love. Elizabeth Aston

+ +

Dashed - One's first love is always perfect until one meets one's second love. Elizabeth Aston

+ +

Solid - One's first love is always perfect until one meets one's second love. Elizabeth Aston

+ +

Double - One's first love is always perfect until one meets one's second love. Elizabeth Aston

+ +

Groove - One's first love is always perfect until one meets one's second love. Elizabeth Aston

+ +

Ridge - One's first love is always perfect until one meets one's second love. Elizabeth Aston

+ +

Inset - One's first love is always perfect until one meets one's second love. Elizabeth Aston

+ +

Outset - One's first love is always perfect until one meets one's second love. Elizabeth Aston

+ + + + \ No newline at end of file diff --git a/css/Border bottom width.html b/css/Border bottom width.html new file mode 100644 index 0000000..34399e1 --- /dev/null +++ b/css/Border bottom width.html @@ -0,0 +1,19 @@ + + + + +border bottom width + + + +

Love SAyings

+

We are each of us angels with only one wing,
+ and we can only fly embracing each other.

+ + Liciano De Crescenzo

+ + diff --git a/css/Border left width.html b/css/Border left width.html new file mode 100644 index 0000000..351941c --- /dev/null +++ b/css/Border left width.html @@ -0,0 +1,32 @@ + + +border left width + + + +Move mouse in and out to see the style change. +
+ True love is eternal, infinite, and always like itself.
+ It is equal and pure, without violent demonstrations:
+ it is seen with white hairs and is always young in the heart.

+ + Honore de Balzac +
+ + \ No newline at end of file diff --git a/css/Border medium solid.html b/css/Border medium solid.html new file mode 100644 index 0000000..eb90379 --- /dev/null +++ b/css/Border medium solid.html @@ -0,0 +1,20 @@ + + + + border medium solid + + + +
+ Beloved, all that is harsh and difficult I want for myself,
+ and all that is gentle and sweet for thee.

+ + San Juan de la Cruz +
+ + \ No newline at end of file diff --git a/css/Border size pattern color padding overflow visible.html b/css/Border size pattern color padding overflow visible.html new file mode 100644 index 0000000..9533f2e --- /dev/null +++ b/css/Border size pattern color padding overflow visible.html @@ -0,0 +1,36 @@ + + + +border size pattern color padding overflow visible + + + + + +

Love Sayings

+ +
Man's love is of man's life a part;
+ It is a woman's whole existence.

+ + Lord Byron + +
+ + + \ No newline at end of file diff --git a/css/Border tag left-color solid.html b/css/Border tag left-color solid.html new file mode 100644 index 0000000..e531e21 --- /dev/null +++ b/css/Border tag left-color solid.html @@ -0,0 +1,26 @@ + + +border tag left-color solid + + + +Move mouse in and out to see the style change. +
One's first love is always perfect until one meets one's second love. Elizabeth Aston
+ + \ No newline at end of file diff --git a/css/Border width border style and border color for all input controls.html b/css/Border width border style and border color for all input controls.html new file mode 100644 index 0000000..d2702da --- /dev/null +++ b/css/Border width border style and border color for all input controls.html @@ -0,0 +1,30 @@ + + + + +border width border style and border color for all input controls + + + + +
+ +
+ +
+ +
+ + + \ No newline at end of file diff --git a/css/Border-bottom-style double solid dashed inset.html b/css/Border-bottom-style double solid dashed inset.html new file mode 100644 index 0000000..ea9a00f --- /dev/null +++ b/css/Border-bottom-style double solid dashed inset.html @@ -0,0 +1,30 @@ + + + + border-bottom-style double solid dashed inset + + + + + +
+ There's a lot to be said for self-delusionment
+ when it comes to matters of the heart.

+ + Diane Frolov and Andrew Schneider + +
+ + + \ No newline at end of file diff --git a/css/Border-right-style dashed solid double inset.html b/css/Border-right-style dashed solid double inset.html new file mode 100644 index 0000000..2d5bffa --- /dev/null +++ b/css/Border-right-style dashed solid double inset.html @@ -0,0 +1,29 @@ + + + + + border-right-style dashed solid double inset + + + + +
+ We are each of us angels with only one wing,
+ and we can only fly embracing each other.

+ + Liciano De Crescenzo +
+ + + \ No newline at end of file diff --git a/css/Border-spacing.html b/css/Border-spacing.html new file mode 100644 index 0000000..7b3753d --- /dev/null +++ b/css/Border-spacing.html @@ -0,0 +1,55 @@ + + + + border-spacing + + + + + + + + + + + + + + + + + + + + + + + + + + +
+ One's first love is always perfect until one meets one's second love. Elizabeth Aston +
Column 1Colunm 2Column 3
j1 x1 w1
j2 x2 w1
j3 x3 w3
+ + + diff --git a/css/Border-width thin medium thick.html b/css/Border-width thin medium thick.html new file mode 100644 index 0000000..16b1a17 --- /dev/null +++ b/css/Border-width thin medium thick.html @@ -0,0 +1,44 @@ + + + + border-width thin medium thick + + + + + +

+ There's a lot to be said for self-delusionment
+ when it comes to matters of the heart.

+ + Diane Frolov and Andrew Schneider +

+
+
thin
+
medium
+
thick
+
+ + \ No newline at end of file diff --git a/css/Borders with rounded corners.html b/css/Borders with rounded corners.html new file mode 100644 index 0000000..717e420 --- /dev/null +++ b/css/Borders with rounded corners.html @@ -0,0 +1,19 @@ + + + +borders with rounded corners + + + +

+Love is like the sun coming out of the clouds and warming your soul.

+

+One's first love is always perfect until one meets one's second love. Elizabeth Aston

+

+Fall not in love, therefore; it will stick to your face. National Lampoon, "Deteriorata"

+ + + diff --git a/css/Br tag adds a new line to the web page.html b/css/Br tag adds a new line to the web page.html new file mode 100644 index 0000000..6558f9c --- /dev/null +++ b/css/Br tag adds a new line to the web page.html @@ -0,0 +1,22 @@ + + +br tag adds a new line to the web page + + +

A kiss is a lovely trick designed by nature to stop speech
+ when words become superfluous.

+ + Ingrid Bergman +

+ Love, and do what you like.
+ Agostino
+
A true man does not need to romance a different girl every night,
+ a true man romances the same girl for the rest of her life.

+ Ana Alas +

+
+
+
+
+ + \ No newline at end of file diff --git a/css/Breadcrumbs.html b/css/Breadcrumbs.html new file mode 100644 index 0000000..185d94c --- /dev/null +++ b/css/Breadcrumbs.html @@ -0,0 +1,20 @@ + + + +breadcrumbs + + + + +
+ + \ No newline at end of file diff --git a/css/Button border-bottom solid.html b/css/Button border-bottom solid.html new file mode 100644 index 0000000..467c90f --- /dev/null +++ b/css/Button border-bottom solid.html @@ -0,0 +1,26 @@ + + +Button border-bottom solid + + + + + + + + + diff --git a/css/Button border-left border-right border-top border-bottom solid.html b/css/Button border-left border-right border-top border-bottom solid.html new file mode 100644 index 0000000..4af7625 --- /dev/null +++ b/css/Button border-left border-right border-top border-bottom solid.html @@ -0,0 +1,28 @@ + + +Button border-left border-right border-top border-bottom solid + + + + + + + + + + + diff --git a/css/Button color.html b/css/Button color.html new file mode 100644 index 0000000..a25ab43 --- /dev/null +++ b/css/Button color.html @@ -0,0 +1,27 @@ + + +Button color + + + + + + + + + + \ No newline at end of file diff --git a/css/Button element hover.html b/css/Button element hover.html new file mode 100644 index 0000000..add23b3 --- /dev/null +++ b/css/Button element hover.html @@ -0,0 +1,43 @@ + + + + + Button element hover + + + + + +
+ + + + + + +
+ + + + \ No newline at end of file diff --git a/css/Button font-weight color padding margin.html b/css/Button font-weight color padding margin.html new file mode 100644 index 0000000..def747d --- /dev/null +++ b/css/Button font-weight color padding margin.html @@ -0,0 +1,27 @@ + + + +Button font-weight color padding margin + + + + + + + + + \ No newline at end of file diff --git a/css/Button margin padding width color.html b/css/Button margin padding width color.html new file mode 100644 index 0000000..397896f --- /dev/null +++ b/css/Button margin padding width color.html @@ -0,0 +1,27 @@ + + + +Button margin padding width color + + + + + + + + + diff --git a/css/Button tag strong tag image tag.html b/css/Button tag strong tag image tag.html new file mode 100644 index 0000000..46fe674 --- /dev/null +++ b/css/Button tag strong tag image tag.html @@ -0,0 +1,29 @@ + + + + + button tag strong tag image tag + + + + + +
+ +
+ +
+ +
+ + + + \ No newline at end of file diff --git a/css/Button with anchor.html b/css/Button with anchor.html new file mode 100644 index 0000000..efebf07 --- /dev/null +++ b/css/Button with anchor.html @@ -0,0 +1,40 @@ + + + + +Button with anchor + + + + + +

CSS Button Example

+ + + + + diff --git a/css/Caption tag caption-side bottom.html b/css/Caption tag caption-side bottom.html new file mode 100644 index 0000000..9232566 --- /dev/null +++ b/css/Caption tag caption-side bottom.html @@ -0,0 +1,48 @@ + + + + + + Caption Tag Caption-side Bottom + + + + + + + + + + + + + + + + + + + + + + + + + + +
Phone Prices
BrandPrice
Nokia$200
Asus$150
LG$180
Apple$280
+ + + \ No newline at end of file diff --git a/css/Cascaded.html b/css/Cascaded.html new file mode 100644 index 0000000..8666e60 --- /dev/null +++ b/css/Cascaded.html @@ -0,0 +1,24 @@ + + + + Cascade Example + + + +
+ Arguments out of a pretty mouth are unanswerable.

+ + Joseph Addison + +
+ + \ No newline at end of file diff --git a/css/Center content layout.html b/css/Center content layout.html new file mode 100644 index 0000000..62b1d60 --- /dev/null +++ b/css/Center content layout.html @@ -0,0 +1,63 @@ + +Center content layout + + + + + +
+

Love Sayings

+

A kiss is a lovely trick designed by nature to stop speech
+ when words become superfluous.

+ + Ingrid Bergman +

+

A true man does not need to romance a different girl every night,
+ a true man romances the same girl for the rest of her life.

+ + Ana Alas +

+
+ + + \ No newline at end of file diff --git a/css/Center tag centers content.html b/css/Center tag centers content.html new file mode 100644 index 0000000..b1f6bfd --- /dev/null +++ b/css/Center tag centers content.html @@ -0,0 +1,38 @@ + + +center tag centers content + + +
+ + + + + + + + + + +
+ This table is centered within the margins of the page. +
not centered

+ The sweetest joy, the wildest woe is love

+ + Pearl Bailey +
centered

+ A kiss makes the heart young again and wipes out the years.

+ + Rupert Brooke +
centered
not centered
+
+
Centered
+
+ not centered

+ + Poetry is the song of the heart, molded by the mind.

+ + Roger W. Hancock + + + diff --git a/css/Centered Shrinkwrapped Table.html b/css/Centered Shrinkwrapped Table.html new file mode 100644 index 0000000..e78e350 --- /dev/null +++ b/css/Centered Shrinkwrapped Table.html @@ -0,0 +1,36 @@ + + + + + Centered Shrinkwrapped Table + + + + +
+
+ Clarity of mind means clarity of passion, too;
+ this is why a great and clear mind loves ardently
+ and sees distinctly what it loves.

+ + Blaise Pascal
+
+ + + + \ No newline at end of file diff --git a/css/Centered body.html b/css/Centered body.html new file mode 100644 index 0000000..0044d81 --- /dev/null +++ b/css/Centered body.html @@ -0,0 +1,25 @@ + + + + +Centered Body + + + + +

Love Sayings

+

Outside are the storms and strangers:
+ We - Oh, close, safe and warm sleep I and she, I and she . . .

+ + Robert Browning

+ + \ No newline at end of file diff --git a/css/Centered footer.html b/css/Centered footer.html new file mode 100644 index 0000000..1e1ea7f --- /dev/null +++ b/css/Centered footer.html @@ -0,0 +1,63 @@ + + + + +Centered Footer + + + + + + + + + \ No newline at end of file diff --git a/css/Centering a layout horizontally.html b/css/Centering a layout horizontally.html new file mode 100644 index 0000000..dd27b68 --- /dev/null +++ b/css/Centering a layout horizontally.html @@ -0,0 +1,35 @@ + + + + + + + Centering a layout horizontally + + + + + +
+

A loving heart is the beginning of all knowledge.

+ + Thomas Carlyle

+
+ + + diff --git a/css/Centre an element of no specified width.html b/css/Centre an element of no specified width.html new file mode 100644 index 0000000..f061ae2 --- /dev/null +++ b/css/Centre an element of no specified width.html @@ -0,0 +1,42 @@ + + + + +Centre an element of no specified width + + + + +

Love Sayings

+
+
+
+

Take away love, and our earth is a tomb.

+ + Robert Browning

+
+
+
+ + \ No newline at end of file diff --git a/css/Change Cursor.html b/css/Change Cursor.html new file mode 100644 index 0000000..e558757 --- /dev/null +++ b/css/Change Cursor.html @@ -0,0 +1,18 @@ + + +Change Cursor + + + + + +happycodings +
+android +
+ + + diff --git a/css/Change em font.html b/css/Change em font.html new file mode 100644 index 0000000..d3d2072 --- /dev/null +++ b/css/Change em font.html @@ -0,0 +1,19 @@ + + + + +Change em font + + + + + +

A loving heart is the beginning of all knowledge.Thomas Carlyle

+ + diff --git a/css/Change to wait cursor.html b/css/Change to wait cursor.html new file mode 100644 index 0000000..1971c4d --- /dev/null +++ b/css/Change to wait cursor.html @@ -0,0 +1,20 @@ + + + + Change to wait cursor + + + +
Take away love, and our earth is a tomb. Robert Browning
+ + + diff --git a/css/Character Set Description.html b/css/Character Set Description.html new file mode 100644 index 0000000..8bf5333 --- /dev/null +++ b/css/Character Set Description.html @@ -0,0 +1,29 @@ +Character Set Description + +ISO-8859-1 Latin alphabet part 1 Covering North America, Western Europe, Latin America, the Caribbean, Canada, Africa + +ISO-8859-2 Latin alphabet part 2 Covering Eastern Europe + +ISO-8859-3 Latin alphabet part 3 Covering SE Europe, Esperanto, miscellaneous others + +ISO-8859-4 Latin alphabet part 4 Covering Scandinavia/Baltics (and others not in ISO-8859-1) + +ISO-8859-5 Latin/Cyrillic alphabet part 5 + +ISO-8859-6 Latin/Arabic alphabet part 6 + +ISO-8859-7 Latin/Greek alphabet part 7 + +ISO-8859-8 Latin/Hebrew alphabet part 8 + +ISO-8859-9 Latin 5 alphabet part 9 (same as ISO-8859-1 except Turkish characters replace Icelandic ones) + +ISO-8859-10 Latin 6 Latin 6 Lappish, Nordic, and Eskimo + +ISO-8859-15 The same as ISO-8859-1 but with more characters added + +ISO-2022-JP Latin/Japanese alphabet part 1 + +ISO-2022-JP-2 Latin/Japanese alphabet part 2 + +ISO-2022-KR Latin/Korean alphabet part 1 diff --git a/css/Check box width.html b/css/Check box width.html new file mode 100644 index 0000000..71f4675 --- /dev/null +++ b/css/Check box width.html @@ -0,0 +1,27 @@ + + + + +Check Box Width + + + + +
+ +
+ +
+ +
+ +
+ + + diff --git a/css/CheckBox height width float margin.html b/css/CheckBox height width float margin.html new file mode 100644 index 0000000..0243281 --- /dev/null +++ b/css/CheckBox height width float margin.html @@ -0,0 +1,85 @@ + + + + +CheckBox height width float margin + + + +