Autor Tema: Temporizador descendente Darkroom Timer  (Leído 4219 veces)

0 Usuarios y 1 Visitante están viendo este tema.

Desconectado BUSHELL

  • PIC10
  • *
  • Mensajes: 6
    • microcontroladorespic (de un amigo)
Temporizador descendente Darkroom Timer
« en: 08 de Agosto de 2009, 15:22:57 »
Saludos. Es mi primer post.

Este temporizador funciona bien. Hace lo que promete. Fue ideado para una insoladora, cuando llega al fin del temporizado, se apaga, a través de RB5.

http://www.electronics-lab.com/projects/oscillators_timers/019/index.html

Allí está el esquema.

O sea que al prender el bicho, inmediatamente se pone en alto RB5, y al llegar al fin del temporizado, se pone en bajo, apagándose, la lámpara que está conectada a través del opto+relé, etc.

Yo lo que quiero es que cuando se prenda el aparatito, RB5 permanezca en bajo y al llegar al fin del temporizado, se ponga en alto/bajo/alto/ bajo, hasta que se oprima el botón Stop/Star (trabaja por RB7) y ahí pasa de nuevo a bajo.

Es para poner un buzzer y que me avise que "el tiempo terminó".

La verdad, no sé mucho de pic. Apenas estoy aprendiendo y quiero enfrentar este proyecto, basándome en el que les adjunto.

La idea es que cuando llegue al final del temporizado, suene el buzzer pi- pi- pi… puede ser medio segundo ON medio segundo OFF.

De antemano, muchas gracias por la ayuda y orientación que me puedan brindar.

Este es el código, en Asm,  a ver si me dicen por dónde debo modificar.


;-------------------------------------------------------------------------
;                             Darkroom Timer                             
;               April '99  Stan Ockers (ockers@anl.gov)                   
;             Modified by Vassilis Papanikolaou, April '05                                         
;                                                                         
;       Counts down from 0-99 min and 0-59 sec giving an alarm at 0       
;     initial counts are held in data EEPROM setable with one button     
;                                                                         
;  RBO-RB3 to bases of transistors connect to common cathode of displays.
;  RA0-RA3 to 1,2,4,8 BCD inputs of CD4511 7 segment latch and driver.   
;  RB7 to start pushbutton used to start countdown and silence alarm.     
;  RB6 goes to time set pushbutton use to sucessively set the digits.     
;  RA4 with pull-up resistor goes to PB to select from 15 starting counts
;  RB4 goes to Dot Points                                     
;  RB5 goes to Relay                                             
;-------------------------------------------------------------------------

   PROCESSOR   PIC16F84A                           ; PIC type
    #INCLUDE   "P16f84A.INC"                        ; Include file
   __CONFIG    _XT_OSC & _WDT_OFF & _PWRTE_ON & _CP_OFF   ; Fuses
   ERRORLEVEL    -302                               ; No bank warnings

;-------------------------------------------------------------------------
;    Here we define our own personal registers and give them names       
;-------------------------------------------------------------------------

SEC          EQU H'0C'          ; this register holds the value of seconds
SEC10        EQU H'0D'          ; holds value of 10's of seconds
MIN         EQU H'0E'          ; holds value of minutes
MIN10        EQU H'0F'          ; holds value of 10's of minutes
DIGCTR       EQU H'10'          ; 8 bit counter, only 2 lowest bits actually used
DIGIT        EQU H'11'          ; hold digit number to access table
INTCNT       EQU H'12'          ; counts # interrupts to determine when 1 sec up
FUDGE        EQU H'13'          ; allows slight adjustment every 7 interrupts
RUNFLG       EQU H'14'          ; bit 0 only, tells if countdown in progress
W_TEMP       EQU H'15'          ; temporarily holds value of W
STATUS_TEMP EQU H'16'         ; temporarily holds value of STATUS
SECNT        EQU H'17'          ; used in counting 25, 20 msec delays for 1 sec
CNTMSEC      EQU H'18'          ; used in timing of milliseconds
ALARM        EQU H'19'          ; bit 0 only, used as flag for when to alarm
OFFSET       EQU H'1A'          ; hold offset of address in EEPROM
KEEP        EQU H'1B'         ; hold RB4 and RB5 state

;-------------------------------------------------------------------------
;    Here we give names to some numbers to make their use more clear     
;-------------------------------------------------------------------------

   #DEFINE   START_PB  D'7'
   #DEFINE   SET_PB    D'6'
   #DEFINE   SELECT_PB D'4'

   #DEFINE   RB0       D'0'
   #DEFINE   RB1       D'1'
   #DEFINE   RB2       D'2'
   #DEFINE   RB3       D'3'
   #DEFINE   RB4       D'4'
   #DEFINE   RB5       D'5'

;-------------------------------------------------------------------------
;         We set the start of code to orginate a location zero           
;-------------------------------------------------------------------------

      ORG 0

            GoTo MAIN                  ; jump to the main routine
            NOP                       
            NOP                       
            NOP                       
            GoTo INTERRUPT             ; interrupt routine

;-------------------------------------------------------------------------
;    This table is used to get a bit pattern that will turn on a digit   
;-------------------------------------------------------------------------

BITPAT      ADDWF PCL,f                ; get bit pattern for transistors
            RETLW H'0E'                ; a low, (0), turns the transistor on 
            RETLW H'0D'                 
            RETLW H'0B'                 
            RETLW H'07'                 

;-------------------------------------------------------------------------
;          Initialization routine sets up ports and timer                 
;-------------------------------------------------------------------------

INIT        MOVLW H'C0'                ; PB6 & PB7 inputs all others outputs
            TRIS PORTB                 
            MOVLW H'10'                ; Port RA4 input, others outputs
            TRIS PORTA                 
            MOVLW H'03'                ; prescaler on TMR0 and 1:16
            OPTION                     
            MOVLW H'A0'                ; GIE & T0IE set T0IF cleared
            MOVWF INTCON               
            MOVLW H'F4'                ; initialize INTCNT
            MOVWF INTCNT               
            MOVLW H'06'                ; initialize FUDGE
            MOVWF FUDGE               
            CLRF OFFSET                ; initialize OFFSET
            Return                     

;-------------------------------------------------------------------------
;   This is the interrupt routine that is jumped to when TMR0 overflows   
;-------------------------------------------------------------------------

INTERRUPT   MOVWF W_TEMP               ; save W
            SWAPF STATUS,W             ; save status
            MOVWF STATUS_TEMP          ; without changing flags
            ;-------------------------------------------------------------
            MOVF PORTB,W            ; save PORTB
            ANDLW H'30'               ; mask out unwanted bits   
         MOVWF KEEP               ; save RB4 and RB5
            ;-------------------------------------------------------------
            INCF DIGCTR,f              ; next digit #
            MOVF DIGCTR,W              ; get it into W
            ANDLW H'03'                ; mask off 2 lowest bits
            MOVWF DIGIT                ; save it for later
            ADDLW H'0C'                ; point at register to display
            MOVWF FSR                  ; use as pointer
            MOVF INDF,W                ; get value of reg pointed to into W
            MOVWF PORTA                ; output to CD4511
            MOVF DIGIT,W               ; recall digit #
            Call BITPAT                ; get bit pattern
         ;-------------------------------------------------------------
            IORWF KEEP,W               ; restore RB4 and RB5
         MOVWF PORTB                ; select transistor
         ;-------------------------------------------------------------
            DECFSZ INTCNT,f            ; finished 1 sec ?
            GoTo RESTORE               ; not yet, return and enable inter.
            Call EVERYSEC              ; go to every second routine
            MOVLW H'F4'                ; reset INTCNT to normal value
            MOVWF INTCNT               
            DECFSZ FUDGE,f             ; time for fudge?
            GoTo RESTORE               ; not yet, continue on
            MOVLW H'06'                ; reset FUDGE to 6
            MOVWF FUDGE               
            INCF INTCNT,f              ; INTCNT to 245
RESTORE     SWAPF STATUS_TEMP,W        ; get original status back
            MOVWF STATUS               ; into status register
            SWAPF STATUS_TEMP,f        ; old no flags trick again
            SWAPF STATUS_TEMP,W        ; to restore W
            BCF INTCON,T0IF            ; clear the TMR0 interrupt flag
            RETFIE                     ; finished

;-------------------------------------------------------------------------
;       This routine is called by the interrupt routine every second     
;-------------------------------------------------------------------------

EVERYSEC    BTFSS RUNFLG,0             ; return if runflg not set
            Return   
         ;-------------------------------------------------------------           
            MOVLW  1 << 4               
           XORWF  PORTB, f            ; Toggle DPs
         ;-------------------------------------------------------------           
            DECF SEC,f                 ; decrement seconds digit
            INCFSZ SEC,W               ; test for underflow
            GoTo CKZERO               
            MOVLW H'09'                ; reset sec to 9
            MOVWF SEC                 
            DECF SEC10,f               ; decrement SEC10
            INCFSZ SEC10,W             ; check underflow
            GoTo CKZERO               
            MOVLW H'05'                 
            MOVWF SEC10               
            DECF MIN,f                 
            INCFSZ MIN,W               
            GoTo CKZERO               
            MOVLW H'09'             
            MOVWF MIN                 
            DECF MIN10,f               
CKZERO      MOVF SEC,f                 ; test SEC for zero
            BTFSS STATUS,Z             
            Return                     
            MOVF SEC10,f               ; check SEC10 for zero
            BTFSS STATUS,Z             
            Return                     
            MOVF MIN,f                 ; check MIN for zero
            BTFSS STATUS,Z             
            Return                     
            MOVF MIN10,f               ; check MIN10 for zero
            BTFSS STATUS,Z             
            Return                     
            CLRF RUNFLG                ; stop the countdown
            BSF ALARM, 0               ; set the alarm flag
            Return                     

;-------------------------------------------------------------------------
;          This is a routine to read a byte from the data EEPROM         
;-------------------------------------------------------------------------

READEE      MOVWF EEADR                ; set up eeprom address from W
            BSF STATUS,RP0             ; change to page 1
            BSF EECON1,RD              ; set the read bit
            BCF STATUS,RP0             ; back to page 0
            MOVF EEDATA,W              ; return value in W
            Return                     

;-------------------------------------------------------------------------
;         This routine fills the display registers from data EEPROM       
;-------------------------------------------------------------------------

GETEE       MOVLW H'01'                ; EEprom location 1 +
            ADDWF OFFSET,W             ; offset from start
            Call READEE                ; into W
            MOVWF SEC                  ; into SEC register
            MOVLW H'02'                ; location 2 +
            ADDWF OFFSET,W             ; offset from start
            Call READEE                ; into W
            MOVWF SEC10                ; into SEC10 register
            MOVLW H'03'                ; location 3 +
            ADDWF OFFSET,W             ; offset from start
            Call READEE                ; into W
            MOVWF MIN                  ; into MIN register
            MOVLW H'04'                ; location 4 +
            ADDWF OFFSET,W             ; offset from start
            Call READEE                ; into W
            MOVWF MIN10                ; into MIN10 register
            Return                     

;-------------------------------------------------------------------------
;              This routine writes a byte to data EEPROM                 
;-------------------------------------------------------------------------

WRITEEE     BSF STATUS,RP0             ; set up EEADR and EEDATA first
            CLRF EECON1               
            BSF EECON1,WREN            ; enable write
            MOVLW H'55'                ; magic sequence
            MOVWF EECON2               
            MOVLW H'AA'                 
            MOVWF EECON2               
            BSF EECON1,WR             
EELOOP      BTFSC EECON1,WR            ; wait for WR to go low
            GoTo EELOOP                ; not yet
            BSF EECON1,WREN           
            BCF EECON1,EEIF            ; clear the interrupt flag
            BCF STATUS,RP0             ; return to page 0
            Return                     

;-------------------------------------------------------------------------
;         This routine puts display registers into data EEPROM           
;-------------------------------------------------------------------------

PUTEE       MOVF SEC,W                 ; put digit registers into EEprom
            MOVWF EEDATA               
            MOVLW H'01'                ; EEPROM location 1 + 
            ADDWF OFFSET,W             ; offset from start
            MOVWF EEADR               
            Call WRITEEE               
            MOVF SEC10,W               
            MOVWF EEDATA               
            MOVLW H'02'                ; EEPROM location 2 + 
            ADDWF OFFSET,W             ; offset from start
            MOVWF EEADR               
            Call WRITEEE               
            MOVF MIN,W                 
            MOVWF EEDATA               
            MOVLW H'03'                ; EEPROM location 3 + 
            ADDWF OFFSET,W             ; offset from start
            MOVWF EEADR               
            Call WRITEEE               
            MOVF MIN10,W               
            MOVWF EEDATA               
            MOVLW H'04'                ; EEPROM location 4 + 
            ADDWF OFFSET,W             ; offset from start
            MOVWF EEADR               
            Call WRITEEE               
            Return                     

;-------------------------------------------------------------------------
;         This is the main routine, the program starts here               
;-------------------------------------------------------------------------

MAIN        Call INIT                  ; set up ports etc.

;-------------------------------------------------------------------------
;           We will return to this point when alarm is shut off.         
;-------------------------------------------------------------------------

EE2D        Call GETEE                 ; put eeprom in display regs.
            BCF RUNFLG, 0              ; clear run flag so no countdown
            BCF ALARM, 0               ; clear alarm flag
         ;-------------------------------------------------------------
            BCF PORTB,RB5              ; turn RELAY OFF   
            BSF PORTB,RB4              ; turn DPs ON
         ;-------------------------------------------------------------
            Call WAITSTARTUP           ; wait till no switches pressed
            Call WAITSETUP
            Call WAITSELECT

;-------------------------------------------------------------------------
;      This loop checks for either pushbutton and acts  accordingly       
;-------------------------------------------------------------------------

KEYCHKLOOP  BTFSS PORTB,START_PB       ; check for start pressed
            GoTo STARTCNT              ; yes, start count
            BTFSS PORTB,SET_PB         ; check for set pressed
            GoTo SETDISP               ; yes, set display
            BTFSS PORTA,SELECT_PB      ; check select pushbutton pressed
            GoTo SETSELECT             ; yes, select starting count
            GoTo KEYCHKLOOP            ; loop to catch key press

;-------------------------------------------------------------------------
;    If start key has been pressed then start countdown process,         
;    I initially released this code with only the setting of the         
;    run flag included.  If you think about it you must also reset       
;    TMR0 to zero.  TMR0 is free running and could have any value         
;    0-255 when the button in pressed. Also INTCNT has to be             
;    initialized because the previous count could have been cancelled.   
;-------------------------------------------------------------------------

STARTCNT    Call WAITSTARTUP           ; wait for release of start key
            MOVLW D'244'               ; reset INTCNT
            MOVWF INTCNT
            CLRF TMR0                  ; and clear timer 0
         ;-------------------------------------------------------------
            BSF PORTB,RB5              ; turn RELAY ON 
          ;-------------------------------------------------------------
            BSF RUNFLG, 0              ; start the countdown

;-------------------------------------------------------------------------
;        Once started just loop looking for cancel or reaching 0000       
;-------------------------------------------------------------------------

MAINLOOP    BTFSS PORTB,START_PB       ; countdown in progress, check start
            GoTo EE2D                  ; start over again if pressed
            BTFSC ALARM, 0             ; reached 0000 yet?       
            GoTo RELAYOFF              ; yes, turn RELAY OFF
            GoTo MAINLOOP              ; no start switch, continue looping

;-------------------------------------------------------------------------
;    This code sounds the alarm and waits on start to be pressed         
;-------------------------------------------------------------------------

RELAYOFF
FINALWAIT   ;-------------------------------------------------------------
          BCF PORTB,RB5              ; turn RELAY OFF
            BSF PORTB,RB4              ; turn DPs ON
         ;-------------------------------------------------------------
            BTFSC PORTB,START_PB       ; start button pressed
            GoTo  FINALWAIT            ; not yet
            Call DLY20                 ; debounce just to make sure
            BTFSC PORTB,START_PB       ; second look
            GoTo FINALWAIT             ; nah, keep waiting
            Call WAITSTARTUP           ; now wait for the switch up
            GoTo EE2D                  ; start all over again

;-------------------------------------------------------------------------
;                    Wait for release of start button                     
;-------------------------------------------------------------------------

WAITSTARTUP BTFSS PORTB,START_PB       ; wait for release
            GoTo WAITSTARTUP           ; not released yet
            Call DLY20                 ; debounce release
            BTFSS PORTB,START_PB       ; 2nd check, make sure released
            GoTo WAITSTARTUP           ; keep checking
            Return

;-------------------------------------------------------------------------
;                    Wait for release of set button                       
;-------------------------------------------------------------------------

WAITSETUP   BTFSS PORTB,SET_PB         ; wait for release
            GoTo WAITSETUP             ; not yet
            Call DLY20                 ; debounce release
            BTFSS PORTB,SET_PB         ; 2nd check, make sure released
            GoTo WAITSETUP             ; keep checking
            Return

;-------------------------------------------------------------------------
;                    Wait for release of select button                   
;-------------------------------------------------------------------------

WAITSELECT  BTFSS PORTA,SELECT_PB      ; wait for release
            GoTo WAITSELECT            ; not yet
            Call DLY20                 ; debounce release
            BTFSS PORTA,SELECT_PB      ; 2nd check, make sure released
            GoTo WAITSELECT            ; keep checking
            Return

;-------------------------------------------------------------------------
;       Routine to follow sets the countdown time digit by digit         
;-------------------------------------------------------------------------

SETDISP     Call WAITSETUP             ; wait for set key to be released
            MOVLW H'0A'                ; put A's in digits, (no display)
            MOVWF MIN10                ; 10's of minutes
            MOVWF MIN                  ; minutes
            MOVWF SEC10                ; 10's of seconds
            MOVWF SEC                  ; seconds
STARTMIN10  CLRF  MIN10                ; 0 now in MIN10
MOREMIN10   MOVLW H'19'                ; 25 delays of 20 msec
            MOVWF SECNT                ; into counting register
WAIT1       Call DLY20                 
            BTFSS PORTB,SET_PB         ; set key pressed?
            GoTo MINSET                ; yes MIN10 now set
            DECFSZ  SECNT,f            ; finished 1 sec delay?
            GoTo WAIT1                 ; continue wait
            INCF MIN10,f               ; every second increment 10's MIN
            MOVLW H'0A'                ; reached 10?
            SUBWF MIN10,W             
            BTFSC STATUS,Z             ; Z set if reached 10
            GoTo STARTMIN10            ; start again with 0
            GoTo MOREMIN10             ; set up another 1 sec delay
MINSET      Call WAITSETUP             ; wait for release of set key
STARTMIN    CLRF MIN                   ; 0 into MIN
MOREMIN     MOVLW H'19'                ; 25 delays of 20 msec
            MOVWF SECNT                ; into counting register
WAIT2       Call DLY20                 
            BTFSS PORTB,SET_PB         ; set pressed?
            GoTo SETSEC10              ; yes, finished with MIN
            DECFSZ SECNT,f             ; finished 1 sec delay?
            GoTo WAIT2                 ; continue wait
            INCF MIN,f                 ; every second increment MIN
            MOVLW H'0A'                ; reached 10?
            SUBWF MIN,W             
            BTFSC STATUS,Z             ; Z set if reached 10
            GoTo STARTMIN              ; put zero in if Z set
            GoTo MOREMIN               ; set up another 1 sec delay
SETSEC10    Call WAITSETUP             ; wait release
STARTSEC10  CLRF SEC10                 ; 0 into SEC10
MORESEC10   MOVLW H'19'                ; 25 delays of 20 msec
            MOVWF SECNT                ; into counting register
WAIT3       Call DLY20                 
            BTFSS PORTB,SET_PB         ; set pressed?
            GoTo  SETSEC               ; yes quit incrementing
            DECFSZ SECNT,f             ; finished 1 sec delay?
            GoTo WAIT3                 ; continue wait
            INCF SEC10,f               ; every second increment 10's SEC
            MOVLW H'06'                ; reached 6?
            SUBWF SEC10,W             
            BTFSC STATUS,Z             ; Z set if reached 6
            GoTo STARTSEC10            ; put zero in if Z set
            GoTo MORESEC10             ; set up another 1 sec delay
SETSEC      Call WAITSETUP             ; wait for release
STARTSEC    CLRF SEC                   ; 0 into SEC
MORESEC     MOVLW H'19'                ; 25 delays of 20 msec
            MOVWF SECNT                ; into counting register
WAIT4       Call DLY20                 
            BTFSS PORTB,SET_PB         ; set button pressed?
            GoTo  FINSET               ; yes finished setting digits
            DECFSZ SECNT,f             ; finished 1 sec delay?
            GoTo WAIT4                 ; continue wait
            INCF SEC,f                 ; every second increment SEC
            MOVLW H'0A'                ; reached 10?
            SUBWF SEC,W             
            BTFSC STATUS,Z             ; Z set if reached 10
            GoTo STARTSEC              ; put zero in if Z set
            GoTo MORESEC               ; set up another 1 sec delay
FINSET      BCF INTCON, GIE            ; disable interrupts
            Call PUTEE                 ; put new digits into EEPROM
            BSF INTCON, GIE            ; re-enable interrupts
            Call WAITSETUP             ; make sure set switch up
            GoTo KEYCHKLOOP            ; start checking buttons again

;-------------------------------------------------------------------------
;        Selects starting count by changing EEPROM location 0             
;-------------------------------------------------------------------------

SETSELECT   MOVLW D'4'                 ; offset up 4
            ADDWF OFFSET,F             ; next offset position
            MOVLW D'60'                ; reached 16th yet?
            SUBWF OFFSET,W             ; will give zero if yes
            BTFSC STATUS,Z             ; skip if not 64
            CLRF  OFFSET               ; reset position to zero
            MOVLW 0                    ; EEPROM location
            MOVWF EEADR                ; set up address
            MOVF OFFSET,W              ; offset # into W
            MOVWF EEDATA               ; set up data
            BCF INTCON,GIE             ;  clear GIE, disable interrupts
            Call WRITEEE               ; save # in location 0
            BSF INTCON,GIE             ; re-enable interrupts
            Call GETEE                 ; get new start count into display
            Call WAITSELECT            ; make sure select switch is up
            GoTo KEYCHKLOOP            ; start checking buttons again

;-------------------------------------------------------------------------
;  The following are various delay routines based on instruction length.   
;  The instruction length is assumed to be 1 microsecond (4Mhz crystal). 
;-------------------------------------------------------------------------

DLY20       MOVLW 20                   ; delay for 20 milliseconds

; N millisecond delay routine

NMSEC       MOVWF CNTMSEC              ; delay for N (in W) milliseconds
MSECLOOP    MOVLW D'248'               ; load takes 1 microsec
            Call MICRO4                ; by itself CALL takes ...
                                       ; 2 + 247 X 4 + 3 + 2 = 995
            NOP                        ; 1 more microsec
            DECFSZ CNTMSEC,f           ; 1 when skip not taken, else 2
            GoTo MSECLOOP              ; 2 here: total 1000 per msecloop
            Return                     ; final time through takes 999 to here
                                       ; overhead in and out ignored

; 1 millisecond delay routine

ONEMSEC     MOVLW D'249'               ; 1 microsec for load W
                                       ; loops below take 248 X 4 + 3 = 995
MICRO4      ADDLW H'FF'                ; subtract 1 from 'W'
            BTFSS STATUS,Z             ; skip when you reach zero
            GoTo MICRO4                ; loops takes 4 microsec, 3 for last
            Return                     ; takes 2 microsec
                                       ; call + load  W + loops + return =
                                       ; 2 + 1 + 995 + 2 = 1000 microsec

;-------------------------------------------------------------------------
;    Here we set up the initial values of the digits in data EEPROM       
;-------------------------------------------------------------------------
           
        ORG H'2100'

          DE 0, 0, 3, 0, 0      ; 1st starting #
          DE    0, 0, 1, 0      ; 2nd starting #
          DE    0, 0, 2, 0      ; 3rd starting #
          DE    0, 0, 3, 0      ; 4th starting #
          DE    0, 0, 4, 0      ; 5th starting #
          DE    0, 0, 5, 0      ; 6th starting #
          DE    0, 0, 6, 0      ; 7th starting #
          DE    0, 0, 7, 0      ; 8th starting #
          DE    0, 0, 8, 0      ; 9th starting #
          DE    0, 0, 9, 0      ; 10th starting #
          DE    0, 0, 0, 1      ; 11th starting #
          DE    0, 0, 0, 2      ; 12th starting #
          DE    0, 0, 0, 3      ; 13th starting #
          DE    0, 0, 0, 4      ; 14th starting #
          DE    0, 0, 0, 5      ; 15th starting #

          END   



Desconectado mtristan

  • Colaborador
  • PIC18
  • *****
  • Mensajes: 395
Re: Temporizador descendente Darkroom Timer
« Respuesta #1 en: 08 de Agosto de 2009, 20:06:06 »
.

Ante nada, declaras los registros PDel0 y PDel1 al principio del programa.

Luego borras la línea
         BCF PORTB,RB5              ; turn RELAY OFF
Y pones en su lugar el trozo de código:
Código: [Seleccionar]
; INICIO RETARDO 1/2 SEG
        movlw     .239      ; 1 set numero de repeticion  (B)
        movwf     PDel0     ; 1 |
PLoop1  movlw     .232      ; 1 set numero de repeticion  (A)
        movwf     PDel1     ; 1 |
PLoop2  clrwdt              ; 1 clear watchdog
PDelL1  goto PDelL2         ; 2 ciclos delay
PDelL2  goto PDelL3         ; 2 ciclos delay
PDelL3  clrwdt              ; 1 ciclo delay
        decfsz    PDel1, 1  ; 1 + (1) es el tiempo 0  ? (A)
        goto      PLoop2    ; 2 no, loop
        decfsz    PDel0,  1 ; 1 + (1) es el tiempo 0  ? (B)
        goto      PLoop1    ; 2 no, loop
PDelL4  goto PDelL5         ; 2 ciclos delay
PDelL5  goto PDelL6         ; 2 ciclos delay
PDelL6  goto PDelL7         ; 2 ciclos delay
PDelL7  clrwdt              ; 1 ciclo delay

; FIN RETARDO

         BTFSC  PORTB,RB5    ; ESTE PEDACITO SE FIJA SI ESTA EN ALTO O EN BAJO RB5 E INVIERTE SU CONDICIÓN.
         GOTO  $+3
         BSF   PORTB,RB5
         GOTO  $+2
         BCF   PORTB,RB5

Como ahí dice, primero genera un retadro (gracias al programita PicDel. IMPORTANTE: debes estar usando un cristal de 4Mhz para que el retardo sea de medio segundo), luego invierte la salida RB5, luego el programa sigue su curso, si no se pulsa el botón indicado vuelve a la parte del retardo y luego a invertir RB5 otra vez. Y así hasta la eternidad.. o hasta que se salga del lazo apretando el botón de salida, en tu caso es START_PB del puerto B.

Espero que te sirva, sino volvé a preguntar porque en algo me habré confundido. Saludos.

When you see a good move, look for a better one (Emanuel Lasker)

Desconectado BUSHELL

  • PIC10
  • *
  • Mensajes: 6
    • microcontroladorespic (de un amigo)
Re: Temporizador descendente Darkroom Timer
« Respuesta #2 en: 09 de Agosto de 2009, 12:49:57 »
Gracias, hermano...sos un genio!! Agradezco tu voluntad de ayudarme.

Voy a probar hoy en la noche y te mantendré informado. :-/


Desconectado BUSHELL

  • PIC10
  • *
  • Mensajes: 6
    • microcontroladorespic (de un amigo)
Re: Temporizador descendente Darkroom Timer
« Respuesta #3 en: 10 de Agosto de 2009, 16:44:11 »
.

Ante nada, declaras los registros PDel0 y PDel1 al principio del programa.

ok. lo hice asi:

PDel0   EQU H'1C'              ; Declaras los registros PDel0  posicion 28
PDel1        EQU H'1D'             ; y PDel1 al principio del programa. pos 29 (estan libres, creo)

Luego borras la línea
         BCF PORTB,RB5              ; turn RELAY OFF
Y pones en su lugar el trozo de código:
Código: [Seleccionar]
; INICIO RETARDO 1/2 SEG
        movlw     .239      ; 1 set numero de repeticion  (B)
        movwf     PDel0     ; 1 |
PLoop1  movlw     .232      ; 1 set numero de repeticion  (A)
        movwf     PDel1     ; 1 |
PLoop2  clrwdt              ; 1 clear watchdog
PDelL1  goto PDelL2         ; 2 ciclos delay
PDelL2  goto PDelL3         ; 2 ciclos delay
PDelL3  clrwdt              ; 1 ciclo delay
        decfsz    PDel1, 1  ; 1 + (1) es el tiempo 0  ? (A)
        goto      PLoop2    ; 2 no, loop
        decfsz    PDel0,  1 ; 1 + (1) es el tiempo 0  ? (B)
        goto      PLoop1    ; 2 no, loop
PDelL4  goto PDelL5         ; 2 ciclos delay
PDelL5  goto PDelL6         ; 2 ciclos delay
PDelL6  goto PDelL7         ; 2 ciclos delay
PDelL7  clrwdt              ; 1 ciclo delay

; FIN RETARDO

         BTFSC  PORTB,RB5    ; ESTE PEDACITO SE FIJA SI ESTA EN ALTO O EN BAJO RB5 E INVIERTE SU CONDICIÓN.
         GOTO  $+3
         BSF   PORTB,RB5
         GOTO  $+2
         BCF   PORTB,RB5


Como ahí dice, primero genera un retadro (gracias al programita PicDel. IMPORTANTE: debes estar usando un cristal de 4Mhz para que el retardo sea de medio segundo), luego invierte la salida RB5, luego el programa sigue su curso, si no se pulsa el botón indicado vuelve a la parte del retardo y luego a invertir RB5 otra vez. Y así hasta la eternidad.. o hasta que se salga del lazo apretando el botón de salida, en tu caso es START_PB del puerto B.

Espero que te sirva, sino volvé a preguntar porque en algo me habré confundido. Saludos.



Cuando dices que "invierte la salida RB5"... quién debe invertirla?..YO manulamente o el programita lo hace solito?
Yo quiero que a la salida de Rb5, permanezca en bajo desde el vamos. Que cuando llegue al fin del temporizado, cambie su estado a alto y que empiece un ciclo alto/bajo/alto/bajo, así, hasta el fin de los tiempos o hasta que yo venga con mi dedo indice y oprima la tecla que conecta RB7, que es la de Start/Stop

Yo quiero que a la salida de Rb5, permanezca en bajo desde el vamos. Que cuando llegue al fin del temporizado, cambie su estado a alto y que empiece un ciclo alto/bajo/alto/bajo, y así, hasta el fin de los tiempos o hasta que yo venga con mi dedo y oprima la tecla que conecta START del puerto B (RB7).

Con la modificación que amablemente me sugeriste, no hace nada nuevo. Ni siquiera titila el led. Yo conecté a la salida de RB5  una resistencia de 4.7k , un transistor bc548 emisor al led y colector a +5v.

Podrías darme otra manito?




Desconectado mtristan

  • Colaborador
  • PIC18
  • *****
  • Mensajes: 395
Re: Temporizador descendente Darkroom Timer
« Respuesta #4 en: 10 de Agosto de 2009, 19:28:51 »
.

Ahora que miro más detenidamente el programa, veo que la línea que yo te dije que cambiaras está repetida 2 veces en el código. Yo me refería a la que está luego de la etiqueta FINALWAIT (está justo debajo). La otra dejala como estaba.
En realidad este programa pretende mantener RB5 en bajo, luego ponerla en alto cuando se inicia la temporización y luego en bajo cuando termina. Si sigues al pie de la letra el esquemático en el link, pues debería de ser así. Pero me he dado cuenta que esta modificación que te propongo (eso si no me he confundido) hará que parpadee el relay junto con los leds, pues está conectado también a RB5.
Así que se me ocurren dos posibles cosas que puedes hacer:

1) Que dejes el programa como estaba y si quieres agregues el buzzer, lo único que cambiará será que en lugar de emitir pitidos, sonará de forma continua. Más adelante, cuando estés un poco más familiarizado con los pics, quizá quieras cambiar el 16F84 por un 16F628 y hacer uso de una de sus salidas (tiene más que el 84) para poner el buzzer independientemente del relay y los leds.

2) Sacrificar los 2 led que representan los puntos entre los minutos y los segundos (conectados a RB4) y poner el buzzer ahí (con su respectivo transistor, pues no creo que el pic solo aguante). Entonces tendrías que omitir las modificaciones que te había dicho, solo dejas los registros Pdel1 y Pdel0. Entonces borras la línea
            BSF PORTB,RB4              ; turn DPs ON
(La que está debajo de la etiqueta FINALWAIT) y colocas en su lugar el código:
Código: [Seleccionar]
; INICIO RETARDO 1/2 SEG
        movlw     .239      ; 1 set numero de repeticion  (B)
        movwf     PDel0     ; 1 |
PLoop1  movlw     .232      ; 1 set numero de repeticion  (A)
        movwf     PDel1     ; 1 |
PLoop2  clrwdt              ; 1 clear watchdog
PDelL1  goto PDelL2         ; 2 ciclos delay
PDelL2  goto PDelL3         ; 2 ciclos delay
PDelL3  clrwdt              ; 1 ciclo delay
        decfsz    PDel1, 1  ; 1 + (1) es el tiempo 0  ? (A)
        goto      PLoop2    ; 2 no, loop
        decfsz    PDel0,  1 ; 1 + (1) es el tiempo 0  ? (B)
        goto      PLoop1    ; 2 no, loop
PDelL4  goto PDelL5         ; 2 ciclos delay
PDelL5  goto PDelL6         ; 2 ciclos delay
PDelL6  goto PDelL7         ; 2 ciclos delay
PDelL7  clrwdt              ; 1 ciclo delay

; FIN RETARDO

         BTFSC  PORTB,RB4    ; ESTE PEDACITO SE FIJA SI ESTA EN ALTO O EN BAJO RB4 E INVIERTE SU CONDICIÓN.
         GOTO  $+3
         BSF   PORTB,RB4
         GOTO  $+2
         BCF   PORTB,RB4
Que es lo mismo que antes, pero con RB4.
Además tendrás que borrar la parte que dice:
            BSF PORTB,RB4              ; turn DPs ON
(luego de la etiqueta EE2D) y poner en su lugar:
            BCF PORTB,RB4              ; turn buzzer off
Y por último, borras las líneas:
         ;-------------------------------------------------------------           
            MOVLW  1 << 4               
           XORWF  PORTB, f            ; Toggle DPs
         ;-------------------------------------------------------------

Para evitar escuchar los pitidos cada segundo de la temporización.

Espero que te haya servido. Si tienes el circuito armado, podrías probar la modificación para usar el buzzer el RB4, haciendo que los leds entre los displays simulen el comportamiento del buzzer (apagados todo el tiempo y titilando cuando llega al fin). Luego me cuentas cómo te fué.
Saludos y suerte con el proyecto.


When you see a good move, look for a better one (Emanuel Lasker)

Desconectado BUSHELL

  • PIC10
  • *
  • Mensajes: 6
    • microcontroladorespic (de un amigo)
Re: Temporizador descendente Darkroom Timer
« Respuesta #5 en: 11 de Agosto de 2009, 00:59:17 »
Felicidad!!!!  :-/ Ahora si parpadea el led, cuando llega al final del temporizado!!! Ooops, perdona, olvidé decirte que yo anulé por completo la parte del relay, pues no lo necesito y solo dejaré en su lugar el buzzer. En su lugar, por ahora, tengo un led, comandado por un transistor.  O sea que este cambio nos facilitará las cosas.

En realidad este programa pretende mantener RB5 en bajo, luego ponerla en alto cuando se inicia la temporización y luego en bajo cuando termina.

Ahora hace justo eso que dices. Pero.....¿qué debo cambiar para que mantenga RB5 en bajo, luego permanecer en bajo durante todo el temporizado y que cuando termine, haga lo que ya logramos, alto/bajo/alto/bajo.  Estamos casi, casi...solo falta un cachito!!!!
Me das ánimo al ver que se ve la luz al final del túnel y que los pics son un mundo fascinante. Y que con práctica, se rinden a nuestros pies. Espero ansioso la estocada final, mtristan.
Te anexo el nuevo asm, con los cambios que hemos hecho.
« Última modificación: 11 de Agosto de 2009, 13:32:00 por BUSHELL »

Desconectado mtristan

  • Colaborador
  • PIC18
  • *****
  • Mensajes: 395
Re: Temporizador descendente Darkroom Timer
« Respuesta #6 en: 11 de Agosto de 2009, 16:27:07 »
.

¡Pues me alegro de que por fin haya funcionado! Aunque parezca algo fácil, hace poco que me inicié con los microcontroladores y es un reto lograr que el integrado haga lo que uno pretende.
Ahora, para el gran final, todo lo que hay que hacer es borrar la línea:
            BSF PORTB,RB5              ; turn RELAY ON
Que aparece luego de la etiqueta STARTCNT. En tanto que RB5 ya había sido puesta en bajo al iniciar el programa, entonces no se activará sino hasta que se termine la temporización.
Ahora, seré curioso ¿qué es lo que estás haciendo con este programa?
Cambiá esto y contame como te fue. Saludos.

When you see a good move, look for a better one (Emanuel Lasker)

Desconectado BUSHELL

  • PIC10
  • *
  • Mensajes: 6
    • microcontroladorespic (de un amigo)
Re: Temporizador descendente Darkroom Timer
« Respuesta #7 en: 11 de Agosto de 2009, 19:29:33 »
 :-/  :lol:  :-/  :lol:  :-/  :lol:

FELICIDAD!!! FELICIDAD!! Funciona como queríamos mtristan!!! Eres un maestro!!! darte las gracias es poco para lo alegre que me has puesto!!

Te cuento, es para un hornito de pan. La idea es que el panadero programe el tiempo en el que más o menos él calcula que ya debe estar listo el pan. El objetivo es que al final del temporizado, no se apague nada (ni el quemador ni nada) sino que suene Pi-pi-pi-pi-pi-pi...entonces, como el pitido es enloquecedor, debe suspender lo que esté haciendo, sacar el pan y meter otros, crudos, volver a programar y listo. Práctico, bonito y eficaz.

Ahora que estamos, y solo por curiosidad, ¿se puede usar este mismo montaje y tan solo cambiando el programa, hacer que en vez de minutos/segundos, cuente horas/minutos?

Me gustaría saber cómo has hecho para en poco tiempo, haber logrado dominar tanto en esto de PIC. Yo llevo casi un año, y ya ves qué crudo estoy. Me han recomendado un libro y trataré de conseguirlo:
http://www.pic16f84a.org/   Para principiantes.
Quizá mi limitacion más grande es que no tengo estudios de electrónica. Solo lo que he aprendido de la red y de personas como vos, que de manera desinteresada, comparten sus conocimientos con paciencia.

De nuevo G R A C I A S.

Desconectado mtristan

  • Colaborador
  • PIC18
  • *****
  • Mensajes: 395
Re: Temporizador descendente Darkroom Timer
« Respuesta #8 en: 11 de Agosto de 2009, 21:41:45 »
.

¡Has visto qué alegría cuando se logra terminar un proyecto! Me alegro también yo, tanto por ti como por mí.
Ahoa si querés, podés hacerle esta modificación de min/seg a horas/min solo retocando el programa del microcontrolador. Si te animas a hacerlo te puedo dar alguna ayuda también.
Y la verdad que no soy un gran experto tampoco, solo tengo unos mínimos conocimientos en electrónica, pero esto de los pics me ha atraído tanto que le dedico prácticamente todo el tiempo libre que puedo. También empezé como autodidacta, leyendo el Curso práctico de Microcontroladores, de Cekit, pero tengo que admitir que no resultó muy claro y además trata otros tipos de microcontroladores, así que no les llega a prestar mucho espacio a ninguno.
En fin. ¡Enhorabuena! Y avísame por cualquier duda que tengas.
Saludos.

When you see a good move, look for a better one (Emanuel Lasker)

Desconectado BUSHELL

  • PIC10
  • *
  • Mensajes: 6
    • microcontroladorespic (de un amigo)
Re: Temporizador descendente Darkroom Timer
« Respuesta #9 en: 11 de Agosto de 2009, 22:16:30 »
Sería muy bueno implementarlo también como horas/minutos. Tendría infinidad de aplicaciones que a muchos serviría. O sea, el mismo hardware y tan solo cambiando el código se tendriá las dos opciones.
Entonces...sería de 99 horas y 99 minutos...(Eso son 4 días + 3 horas...y alguito más) una cosa de locos...muy bueno!!

Mira con despacio cómo seria el cambio, y lo posteas. Vale?

Je,je acabo de armar todo, puse el buzzer, le sumé un led rojo...y ni te imaginas lo lindo que se vé todo. Listo para montar en el horno. Ya no más panes quemados!!!  :-/

Te llegó mi MP?


Desconectado kito

  • PIC10
  • *
  • Mensajes: 1
Re: Temporizador descendente Darkroom Timer
« Respuesta #10 en: 01 de Febrero de 2010, 21:02:09 »
Hola gente y saludos a todos. Esta es mi primera participacion en un foro asi que pido disculpas de antemano. El asunto es el siguiente,no tengo mucha experiencia en esto de los pic, pero arme y puse en marcha el Temporizador descendente Darkroom Timer y funciona de maravillas. Me gustaria si alguien me puede ayudar a hacer algunos cambios al soft del temporizador.
Lo que mas me interesa es ver si es pocible que cuando el temporizador esta programado supongamos a 15 minutos y llega a 0 en el display aparesca ese número, osea 15, de nuevo a la espera de que se dispare el tempo nuevamente. Lo que ocurre es que cuando el tempo llega a 0 este se mantiene en 0 y para para que se dispare el tempo nuevamente hay que presionar 2 veces el boton Start, osea una ves para que pase de 0 a 15 y otra para disparar el tempo y asi iniciar nuevamente el conteo.
Espero puedan entender mi solicitud de ayuda. Recuerdo nuevamente que soy muy nuevo en esto de los foros a pesar de mi edad.
Si alguien puede ayudarme se los agradecere eternamente.
Saludos a todos y desde ya muchas gracias...


 

anything