Grosse MàJ

This commit is contained in:
olivier
2008-11-25 22:11:16 +01:00
parent 53195fdfcd
commit 3e719157ea
2980 changed files with 343846 additions and 0 deletions

BIN
P5B/cobol/exercices/carmag Normal file

Binary file not shown.

View File

@ -0,0 +1,163 @@
IDENTIFICATION DIVISION.
PROGRAM-ID. carmag0.
AUTHOR. OD.
***---------------------------------------------------------------
*----------------------------------------------------------------*
* PROGRAMME *
* CREATION TABLEAU IMPAIR *
*----------------------------------------------------------------*
ENVIRONMENT DIVISION.
***---------------------------------------------------------------
DATA DIVISION.
WORKING-STORAGE SECTION.
*--------------------------*
* DEFINITION DES VARIABLES *
*--------------------------*
* Nombre entre au clavier
77 NBR-DPRT PICTURE 999 VALUE ZERO.
* Tableau du carre magique
01 TABLE-CARMAG.
* - Numero de ligne
05 LGN OCCURS 25.
* - Colonnes de la ligne
10 CLN OCCURS 25.
* - - Contenu de chaque colonne : chiffre
15 CNTN PICTURE 999.
* Nombre pour verifier le nombre saisie
77 NBR PICTURE 999 VALUE ZERO.
88 IMPAIR VALUE 1.
* Valeur a inserer dans le tableau final
77 VALEUR PICTURE 999 VALUE 1.
* Curseur ligne
77 CRSR-LGN PICTURE 999 VALUE 1.
* Curseur colonne
77 CRSR-CLN PICTURE 999 VALUE 1.
* Total d'un calcul puis reutilisation pour diverses taches
77 TOTAL PICTURE 999 VALUE ZERO.
* Nombre de cases dans le tableau a afficher
77 NBR-CRR PICTURE 999 VALUE ZERO.
* Reste dans la division euclidienne
77 RST PICTURE 999 VALUE ZERO.
***---------------------------------------------------------------
PROCEDURE DIVISION.
*
* Nom du programme
*
PROGRAMME SECTION.
* Debut du programme (initialisation)
DEBUT.
DISPLAY "Debut de la saisie...".
PERFORM SAISIE UNTIL IMPAIR.
DISPLAY "Saisie terminee !".
* Corps du programme (contenu)
CORPS.
DISPLAY "Taille du tableau : " NBR-DPRT.
PERFORM REMPLISSAGE.
* Fin du programme
FIN.
DISPLAY "Carre magique fini !!!".
STOP RUN.
*
* Arborescence de niveau 2 : Saisie de l'utilisateur
*
SAISIR SECTION.
SAISIE.
DISPLAY "Saisissez un chiffre impair inferieur a 26 : "
WITH NO ADVANCING.
ACCEPT NBR-DPRT.
PERFORM VERIF.
VERIF.
DIVIDE NBR-DPRT BY 2 GIVING TOTAL REMAINDER RST.
IF (RST NOT EQUAL TO ZERO AND NBR-DPRT LESS THAN 26) THEN
MOVE 1 TO NBR.
*
* Arborescence niveau 2 : REMPLISSAGE PUIS AFFICHAGE
*
REMPLISSAGE SECTION.
* Affectation de la premiere valeur, ligne une, colonne du milieu
VAL-UNE.
DISPLAY "Affectation valeur une...".
* COMPUTE TOTAL ROUNDED = NBR-DPRT / 2.
DIVIDE 2 INTO NBR-DPRT GIVING TOTAL ROUNDED.
* Affectation de la premiere valeur a la colonne trouvee
MOVE 1 TO CNTN(1,TOTAL).
* Affectation du numero de colonne vers le curseur des colonnes
MOVE TOTAL TO CRSR-CLN.
DISPLAY "Affectation terminee ! Colonne actuelle : " TOTAL.
VAL-SUIV.
DISPLAY "Affectation des valeurs suivantes...".
MULTIPLY NBR-DPRT BY NBR-DPRT GIVING TOTAL.
MOVE TOTAL TO NBR-CRR.
PERFORM TRAITEMENT UNTIL VALEUR EQUAL TO NBR-CRR.
DISPLAY "Affectations terminees ! Total : " VALEUR.
AFFICHAGE.
DISPLAY "AFFICHAGE DU TABLEAU".
MOVE 1 TO CRSR-LGN.
MOVE 1 TO CRSR-CLN.
PERFORM PARCOURS VARYING CRSR-LGN FROM 1 BY 1 UNTIL CRSR-LGN
> NBR-DPRT.
* AFTER CRSR-CLN FROM 1 BY 1 UNTIL CRSR-CLN
* > NBR-DPRT.
DISPLAY "AFFICHAGE TERMINE".
*
* Arborescence niveau 3 : TRAITEMENT PLACEMENT
*
TRAITEMENT SECTION.
INCREMENTE.
ADD 1 TO VALEUR.
MLTPL.
DIVIDE VALEUR BY NBR-DPRT GIVING TOTAL REMAINDER RST.
IF (RST EQUAL TO 1) THEN
PERFORM SS-PLCMT
ELSE PERFORM SR-PLCMT.
VERIFICATION.
PERFORM VERIFIER.
PLACEMENT.
DISPLAY "|_Affectation de : " VALEUR.
MOVE VALEUR TO CNTN(CRSR-LGN,CRSR-CLN).
DISPLAY "| Affectee a : " CRSR-LGN ", "CRSR-CLN.
*
* Arborescence niveau 3 : Affichage du tableau
*
AFFICHER SECTION.
PARCOURS.
PERFORM AFFICHE VARYING CRSR-CLN FROM 1 BY 1
UNTIL CRSR-CLN >= NBR-DPRT.
DISPLAY "|" CNTN(CRSR-LGN,CRSR-CLN) "|".
AFFICHE.
DISPLAY "|" CNTN(CRSR-LGN,CRSR-CLN) "|"
WITH NO ADVANCING.
*
* Arborescence niveau 4 : MULIPLE + 1
*
MULTPL SECTION.
SS-PLCMT.
ADD 1 TO CRSR-LGN.
SR-PLCMT.
SUBTRACT 1 FROM CRSR-LGN.
SUBTRACT 1 FROM CRSR-CLN.
*
* Arborescence niveau 4 : VERIFICATION LIGNE / COLONNE
*
VERIFIER SECTION.
LIGNE.
IF (CRSR-LGN < 1) THEN
MOVE NBR-DPRT TO CRSR-LGN.
IF (CRSR-LGN > NBR-DPRT) THEN
MOVE 1 TO CRSR-LGN.
COLONNE.
IF (CRSR-CLN < 1) THEN
MOVE NBR-DPRT TO CRSR-CLN.
IF (CRSR-CLN > NBR-DPRT) THEN
MOVE 1 TO CRSR-CLN.

BIN
P5B/cobol/exercices/carmag0 Normal file

Binary file not shown.

View File

@ -0,0 +1,50 @@
IDENTIFICATION DIVISION.
PROGRAM-ID. carmag0.
AUTHOR. OD.
*----------------------------------------------------------------*
* PROGRAMME *
* CREATION TABLEAU IMPAIR *
*----------------------------------------------------------------*
ENVIRONMENT DIVISION.
DATA DIVISION.
WORKING-STORAGE SECTION.
*--------------------------*
* DEFINITION DES VARIABLES *
*--------------------------*
* Nombre entr<74>e
77 NBR-DPRT PICTURE 99 VALUE ZERO.
* Tableau du carr<72> magique
01 TABLE-CARMAG.
* - Num<75>ro de ligne
05 NM-LGN OCCURS 31.
* - Colonnes de la ligne
10 CLN OCCURS 31.
* - - Contenu de chaque colonne : chiffre
15 CNTN PICTURE 99.
* Curseur ligne
77 CRSR-LGN PICTURE 99 VALUE 1.
77 CRSR-CLN PICTURE 99 VALUE 1.
PROCEDURE DIVISION.
PROGRAMME SECTION.
DEBUT.
MOVE 3 TO NBR-DPRT.
CORPS.
DISPLAY "Taille du tableau : " NBR-DPRT.
PERFORM PARCOURS.
FIN.
DISPLAY "Carr<72> magique termin<69>.".
STOP RUN.
TRAITEMENTS SECTION.
PARCOURS.
PERFORM REMP VARYING CRSR-LGN FROM 1 BY 1 UNTIL CRSR-LGN
> NBR-DPRT AFTER CRSR-CLN FROM 1 BY 1 UNTIL CRSR-CLN
> NBR-DPRT.
REMP.
MOVE 1 TO CNTN(CRSR-LGN, CRSR-CLN).
DISPLAY "Coordonn<6E>es (" CRSR-LGN ", " CRSR-CLN ") : "
CNTN(CRSR-LGN, CRSR-CLN).

BIN
P5B/cobol/exercices/carmag1 Normal file

Binary file not shown.

View File

@ -0,0 +1,62 @@
IDENTIFICATION DIVISION.
PROGRAM-ID. carmag0.
AUTHOR. OD.
*----------------------------------------------------------------*
* PROGRAMME *
* CREATION TABLEAU IMPAIR *
*----------------------------------------------------------------*
ENVIRONMENT DIVISION.
DATA DIVISION.
WORKING-STORAGE SECTION.
*--------------------------*
* DEFINITION DES VARIABLES *
*--------------------------*
* Nombre entr<74>e
77 NBR-DPRT PICTURE 99 VALUE ZERO.
* Tableau du carr<72> magique
01 TABLE-CARMAG.
* - Num<75>ro de ligne
05 NM-LGN OCCURS 31.
* - Colonnes de la ligne
10 CLN OCCURS 31.
* - - Contenu de chaque colonne : chiffre
15 CNTN PICTURE 99.
* Curseur ligne
77 CRSR-LGN PICTURE 99 VALUE 1.
77 CRSR-CLN PICTURE 99 VALUE 1.
* Total d'un calcul
77 TOTAL PICTURE 99 VALUE ZERO.
PROCEDURE DIVISION.
* Nom du programme
PROGRAMME SECTION.
* D<>but du programme (initialisation)
DEBUT.
MOVE 3 TO NBR-DPRT.
* Corps du programme (contenu)
CORPS.
DISPLAY "Taille du tableau : " NBR-DPRT.
PERFORM REMPLI.
* Fin du programme
FIN.
DISPLAY "Carr<72> magique termin<69>.".
STOP RUN.
* Section dédiée aux traitements à effectuer
TRAITEMENTS SECTION.
* Remplissage du tableau
REMPLI.
COMPUTE TOTAL ROUNDED = NBR-DPRT / 2.
DISPLAY TOTAL.
MOVE 1 TO CNTN(1,TOTAL).
AFFICHAGE SECTION.
PARCOURS-TABLEAU.
PERFORM AFFICHE VARYING CRSR-LGN FROM 1 BY 1 UNTIL CRSR-LGN
> NBR-DPRT AFTER CRSR-CLN FROM 1 BY 1 UNTIL CRSR-CLN
> NBR-DPRT.
AFFICHE.
DISPLAY "Coordonnées (" CRSR-LGN ", " CRSR-CLN ") : "
CNTN(CRSR-LGN, CRSR-CLN).

BIN
P5B/cobol/exercices/conson Normal file

Binary file not shown.

View File

@ -0,0 +1,83 @@
IDENTIFICATION DIVISION.
PROGRAM-ID. conson.
AUTHOR. OD.
*----------------------------------------------*
* PROGRAMME QUI CONSONNE UN MOT (NORMALEMENT) *
*----------------------------------------------*
ENVIRONMENT DIVISION.
DATA DIVISION.
WORKING-STORAGE SECTION.
*--------------------------*
* DEFINITION DES VARIABLES *
*--------------------------*
77 MOT PICTURE X(30) VALUE SPACE.
77 RETOUR PICTURE X(30) VALUE SPACE.
77 RESULTAT PICTURE X(6) VALUE SPACE.
77 LETTRE PICTURE X VALUE SPACE.
77 CHIFFRE PICTURE 99 VALUE 2.
77 POINTEUR1 PICTURE 99 VALUE 2.
77 POINTEUR2 PICTURE 9 VALUE 2.
01 VOYELLES.
05 LTR-AMAJ PICTURE X VALUE "A".
05 LTR-EMAJ PICTURE X VALUE "E".
05 LTR-IMAJ PICTURE X VALUE "I".
05 LTR-OMAJ PICTURE X VALUE "O".
05 LTR-UMAJ PICTURE X VALUE "U".
05 LTR-YMAJ PICTURE X VALUE "Y".
05 LTR-AMIN PICTURE X VALUE "a".
05 LTR-EMIN PICTURE X VALUE "e".
05 LTR-IMIN PICTURE X VALUE "i".
05 LTR-OMIN PICTURE X VALUE "o".
05 LTR-UMIN PICTURE X VALUE "u".
05 LTR-YMIN PICTURE X VALUE "y".
01 ESPACES PICTURE X(12) VALUE SPACE.
PROCEDURE DIVISION.
*NOM DU PROGRAMME
PRINCIPAL SECTION.
DEBUT.
PERFORM SAISIE.
CORPS.
PERFORM TRAITEMENT.
FIN.
DISPLAY "Mot consonn<6E> : " RESULTAT.
DISPLAY "FIN DU TRAITEMENT". STOP RUN.
*SAISIE DU MOT
SAISIR SECTION.
SAISIE.
DISPLAY "Saisissez un mot : "
WITH NO ADVANCING.
ACCEPT MOT.
*TRAITEMENT DU MOT
TRAITER SECTION.
TRAITEMENT.
INSPECT MOT CONVERTING VOYELLES TO ESPACES AFTER MOT(1:1).
MOVE MOT(1:1) TO RETOUR.
PERFORM CONCATENER UNTIL CHIFFRE EQUAL TO 30.
PERFORM TRANSMISSION.
*CONCATENER LA CHAINE OBTENUE POUR SUPPRIMER LES ESPACES
CONCATENER.
MOVE MOT(CHIFFRE:1) TO LETTRE.
IF (POINTEUR1 < 10) THEN
MOVE POINTEUR1 TO POINTEUR2
END-IF
SUBTRACT 1 FROM POINTEUR2.
IF LETTRE IS EQUAL TO RETOUR(POINTEUR2:1) THEN
MOVE SPACE TO LETTRE.
IF (LETTRE IS NOT EQUAL TO SPACE OR POINTEUR1 IS EQUAL TO
6) THEN
STRING LETTRE(1:1) INTO RETOUR WITH POINTER POINTEUR1
END-IF.
ADD 1 TO CHIFFRE.
*TRANSMET LE RESULTAT DES 6 PREMIERS CARACTERES A LA VARIABLE
* RESULAT
TRANSMISSION.
MOVE RETOUR(1:6) TO RESULTAT.

BIN
P5B/cobol/exercices/impair Normal file

Binary file not shown.

View File

@ -0,0 +1,57 @@
IDENTIFICATION DIVISION.
PROGRAM-ID. multpl.
AUTHOR. OD.
*----------------------------------------------------------------*
* PROGRAMME *
* VERIFICATION NOMBRE MULTIPLE D'UN AUTRE (IMPAIR) *
*----------------------------------------------------------------*
ENVIRONMENT DIVISION.
DATA DIVISION.
WORKING-STORAGE SECTION.
*--------------------------*
* DEFINITION DES VARIABLES *
*--------------------------*
* Nombre de d<>part
77 NBR-DPRT PICTURE 99 VALUE ZERO.
* Resultat dans la division euclidienne
77 DV-ECLDN PICTURE 99 VALUE ZERO.
* Reste dans la division euclidienne par 2
77 RST PICTURE 9 VALUE ZERO.
* Nombre impair ou pas ? (simulation d'un bool<6F>en)
77 NBR PICTURE 99 VALUE ZERO.
88 IMPAIR VALUE 1.
* R<>sultat
77 RSLTT PICTURE X(30).
PROCEDURE DIVISION.
*--------------------*
* DEBUT DU PROGRAMME *
*--------------------*
PROGRAMME SECTION.
DEBUT.
PERFORM SAISIE UNTIL IMPAIR.
CORPS.
PERFORM PARITE.
FIN.
DISPLAY RSLTT.
STOP RUN.
SAISIR SECTION.
SAISIE.
DISPLAY "Saisissez un chiffre impair : "
WITH NO ADVANCING.
ACCEPT NBR-DPRT.
PERFORM VERIF.
VERIF.
DIVIDE NBR-DPRT BY 2 GIVING DV-ECLDN REMAINDER RST.
DISPLAY RST.
IF (RST NOT EQUAL TO ZERO) THEN
MOVE 1 TO NBR.
PARITE.
IF (IMPAIR) THEN
MOVE "Le nombre est impair." TO RSLTT
ELSE MOVE "Le nombre n'est pas impair." TO RSLTT.

BIN
P5B/cobol/exercices/insee Normal file

Binary file not shown.

View File

@ -0,0 +1,114 @@
IDENTIFICATION DIVISION.
PROGRAM-ID. insee.
AUTHOR. OD.
*---------------------------------------------------------------*
* PROGRAMME *
* CONTROLE VALIDITE NUMERO INSEE *
*---------------------------------------------------------------*
ENVIRONMENT DIVISION.
DATA DIVISION.
WORKING-STORAGE SECTION.
*--------------------------*
* DEFINITION DES VARIABLES *
*--------------------------*
01 CD-INSEE.
* Code Homme/Femme, 1 = homme, 2 = femme
05 CD-SX PICTURE 9 VALUE ZERO.
* Code ann<6E>e de naissance
05 CD-NSSNC PICTURE 99 VALUE ZERO.
* Code mois de naissance
05 CD-MS-NSSNC PICTURE 99 VALUE ZERO.
* Code d<>partement
* Enlever les d<>partements non existants, et 2A pour Corse,
* ainsi que 2B
05 CD-DPRTMNT PICTURE XX.
* Code commune
05 CD-CMMNE PICTURE 999 VALUE ZERO.
* Code registre
05 CD-RGSTR PICTURE 999 VALUE ZERO.
* Cl<43> de contr<74>le
05 CL-CTRL PICTURE 99 VALUE ZERO.
* ERREURS
* Bool<6F>en permettant de dire s'il y a erreur ou pas
* Initialis<69> <20> 0 pour l'instant
01 ERR-BLN PICTURE 9 VALUE LOW-VALUE.
* Nom erreur
01 ERR-NM PICTURE X(20) VALUE SPACE.
PROCEDURE DIVISION.
* Nom du programme, ici PROGRAMME
PROGRAMME SECTION.
* Demande du num<75>ro
DEBUT.
DISPLAY "Tapez votre num<75>ro INSEE : " WITH NO ADVANCING.
ACCEPT CD-INSEE.
* Affichage des valeurs entr<74>es
AFFICHAGE.
DISPLAY "Sexe : " CD-SX.
DISPLAY "Ann<6E>e de naissance : " CD-NSSNC.
DISPLAY "Mois de naissance : " CD-MS-NSSNC.
DISPLAY "D<>partement de naissance : " CD-DPRTMNT.
DISPLAY "Commune : " CD-CMMNE.
DISPLAY "Code registre : " CD-RGSTR.
DISPLAY "Cl<43> de contr<74>le : " CL-CTRL.
* STOP RUN.
* Contr<74>les de validit<69>
CONTROLE SECTION.
* Contr<74>le du sexe
SEXE.
IF NOT (CD-SX EQUAL TO 1 OR CD-SX EQUAL TO 2) THEN
MOVE HIGH-VALUE TO ERR-BLN
MOVE "sexe." TO ERR-NM.
* Contr<74>le sur type code sexe
SEXETYPE.
IF CD-SX IS NOT NUMERIC THEN
MOVE HIGH-VALUE TO ERR-BLN
MOVE "sexe non num<75>rique." TO ERR-NM.
* Contr<74>le sur mois de naissance
MOISNAISSANCE.
IF (CD-MS-NSSNC EQUAL TO 0 OR CD-MS-NSSNC GREATER THAN 12)
THEN
MOVE HIGH-VALUE TO ERR-BLN
MOVE "mois de naissance." TO ERR-NM.
* Contr<74>le sur type code mois de naissance
MOISNAISSANCETYPE.
IF CD-MS-NSSNC IS NOT NUMERIC THEN
MOVE HIGH-VALUE TO ERR-BLN
MOVE "ann<6E>e de naissance non num<75>rique." TO ERR-NM.
* Contr<74>le sur d<>partement
DEPARTEMENT.
IF CD-DPRTMNT EQUAL TO "2A" THEN
MOVE "19" TO CD-DPRTMNT
IF CD-DPRTMNT EQUAL TO "2B" THEN
MOVE "18" TO CD-DPRTMNT
IF (CD-DPRTMNT EQUAL TO "96" OR CD-DPRTMNT EQUAL TO 0)
THEN
MOVE HIGH-VALUE TO ERR-BLN
MOVE "mauvais d<>partement".
* Contr<74>le sur type code d<>partement
DEPARTEMENTTYPE.
IF CD-DPRTMNT IS NOT NUMERIC THEN
MOVE HIGH-VALUE TO ERR-BLN
MOVE
* Affichage du r<>sultat
RESULTAT SECTION.
* Affichage de l'erreur
ERREUR.
IF ERR-BLN EQUAL TO HIGH-VALUE THEN
DISPLAY "Erreur sur : " ERR-NM
ELSE
DISPLAY "Aucune erreur.".
STOP RUN.

Binary file not shown.

BIN
P5B/cobol/exercices/mult Normal file

Binary file not shown.

View File

@ -0,0 +1,24 @@
IDENTIFICATION DIVISION.
PROGRAM-ID. mult.
AUTHOR. GR.
* Ce programme effectue la multiplication de 2 entiers
*
ENVIRONMENT DIVISION.
DATA DIVISION.
WORKING-STORAGE SECTION.
77 Num1 PIC 999 VALUE ZERO.
77 Num2 PIC 999 VALUE ZERO.
77 Res PIC Z(5)9.
PROCEDURE DIVISION.
PROGRAMME SECTION.
P1.
DISPLAY "Taper le 1er nombre (<999) : " WITH NO ADVANCING.
ACCEPT Num1.
DISPLAY "Taper le second nombre : " WITH NO ADVANCING.
ACCEPT Num2.
MULTIPLY Num1 BY Num2 GIVING Res.
DISPLAY "R<>sultat = " Res.
STOP RUN.

BIN
P5B/cobol/exercices/multpl Normal file

Binary file not shown.

View File

@ -0,0 +1,64 @@
IDENTIFICATION DIVISION.
PROGRAM-ID. multpl.
AUTHOR. OD.
*----------------------------------------------------------------*
* PROGRAMME *
* VERIFICATION NOMBRE MULTIPLE D'UN AUTRE +1 *
*----------------------------------------------------------------*
ENVIRONMENT DIVISION.
DATA DIVISION.
WORKING-STORAGE SECTION.
*--------------------------*
* DEFINITION DES VARIABLES *
*--------------------------*
* Nombre de d<>part
77 NBR-DPRT PICTURE 99 VALUE ZERO.
* Nombre à tester
77 NBR-TEST PICTURE 99 VALUE ZERO.
* Resultat dans la division euclidienne
77 DV-ECLDN PICTURE 99 VALUE ZERO.
* Reste dans la division euclidienne par 2
77 RST PICTURE 9 VALUE ZERO.
* Nombre impair ou pas ? (simulation d'un bool<6F>en)
77 NBR PICTURE 99 VALUE ZERO.
88 MLTPL VALUE 1.
* R<>sultat
77 RSLTT PICTURE X(30).
PROCEDURE DIVISION.
*--------------------*
* DEBUT DU PROGRAMME *
*--------------------*
PROGRAMME SECTION.
DEBUT.
PERFORM SAISIE.
CORPS.
PERFORM PARITE.
FIN.
DISPLAY RSLTT.
STOP RUN.
SAISIR SECTION.
SAISIE.
DISPLAY "Saisissez un chiffre de base : "
WITH NO ADVANCING.
ACCEPT NBR-DPRT.
DISPLAY "Saisissez le chiffre suivant : "
WITH NO ADVANCING.
ACCEPT NBR-TEST.
PERFORM VERIF.
VERIF.
DIVIDE NBR-TEST BY NBR-DPRT GIVING DV-ECLDN REMAINDER RST.
DISPLAY "RESTE : " RST.
IF (RST EQUAL TO 1) THEN
MOVE 1 TO NBR.
PARITE.
IF (MLTPL) THEN
MOVE "Le nombre est un multiple incrément<6E>de un"
TO RSLTT
ELSE MOVE "Le nombre n'est pas un multiple incr<63>ment
- "<22> de un." TO RSLTT.

BIN
P5B/cobol/exercices/palind Normal file

Binary file not shown.

Binary file not shown.

View File

@ -0,0 +1,70 @@
IDENTIFICATION DIVISION.
PROGRAM-ID. palind.
AUTHOR. OD.
*-------------------------------------------*
* PROGRAMME DE VERIFICATION D'UN PALINDROME *
*-------------------------------------------*
ENVIRONMENT DIVISION.
DATA DIVISION.
WORKING-STORAGE SECTION.
*--------------------------*
* DEFINITION DES VARIABLES *
*--------------------------*
77 MOT PICTURE X(255) VALUE SPACE.
77 RESULTAT PICTURE X(30) VALUE SPACE.
77 DEBUT-MOT PICTURE 99 VALUE 1.
77 FIN-MOT PICTURE 99 VALUE 29.
77 LETTRE PICTURE X VALUE SPACE.
77 VALIDE PICTURE 9 VALUE 1.
88 CORRECT VALUE 1.
PROCEDURE DIVISION.
*NOM DU PROGRAMME
PRINCIPAL SECTION.
DEBUT.
PERFORM SAISIE.
CORPS.
PERFORM TRAITEMENT.
FIN.
DISPLAY RESULTAT.
DISPLAY "FIN DU TRAITEMENT".
STOP RUN.
*SAISIE DU MOT
SAISIR SECTION.
SAISIE.
DISPLAY "Saisissez une phrase : " WITH NO ADVANCING.
ACCEPT MOT.
*------*
* TEST *
*------*
DISPLAY MOT.
*TRAITEMENT DE LA PHRASE
TRAITEMENT SECTION.
TRAITER.
PERFORM PARCOURIR UNTIL VALIDE IS NOT EQUAL TO 1.
*PARCOURS DE LA CHAINE DE CARACT<43>RE, ET LONGUEUR DE CELLE CI
PARCOURIR.
MOVE ZERO TO VALIDE.
DISPLAY DEBUT-MOT.
DISPLAY FIN-MOT.
MOVE 1 TO VALIDE.
* IF (MOT(DEBUT-MOT:1) EQUAL TO SPACE) THEN
* ADD 1 TO DEBUT-MOT
* END-IF.
* MOVE MOT(FIN-MOT:1) TO LETTRE.
* PERFORM CAL-CHFFRE UNTIL LETTRE NOT EQUAL TO SPACE.
* IF (MOT(DEBUT-MOT:1) EQUAL TO MOT(FIN-MOT:1))
* MOVE 1 TO VALIDE
* END-IF.
*CALCUL DU CHIFFRE DE LA LETTRE <20> COMPARER
CAL-CHFFRE.
IF (MOT(FIN-MOT:1) EQUAL TO SPACE) THEN
SUBTRACT 1 FROM FIN-MOT
END-IF.

BIN
P5B/cobol/exercices/palind1 Normal file

Binary file not shown.

View File

@ -0,0 +1,90 @@
IDENTIFICATION DIVISION.
PROGRAM-ID. palind.
AUTHOR. OD.
*-------------------------------------------*
* PROGRAMME DE VERIFICATION D'UN PALINDROME *
*-------------------------------------------*
ENVIRONMENT DIVISION.
DATA DIVISION.
WORKING-STORAGE SECTION.
*--------------------------*
* DEFINITION DES VARIABLES *
*--------------------------*
* MOT DONNE PAR L'UTILISATEUR
77 MT-UTIL PICTURE X(255) VALUE SPACE.
* MOT SANS ESPACE
77 MT-SS-SPC PICTURE X(255) VALUE SPACE.
* MOT INVERSE
77 MT-INV PICTURE X(255) VALUE SPACE.
* RESULTAT DU PROGRAMME (ICI ON DIRA "CECI EST UN PALINDROME")
* OU PAS)
77 RESULTAT PICTURE X(30) VALUE SPACE.
* BOOLEEN
77 PLND PICTURE 9 VALUE ZERO.
* 88 EST VALUE ZERO.
* 88 ESTPAS VALUE 1.
* CURSEURS
* - CURSEUR-DEPART
77 CRSR-DP PICTURE 999 VALUE 1.
* - CURSEUR-ARRIVEE
77 CRSR-RRV PICTURE 999 VALUE 1.
PROCEDURE DIVISION.
*NOM DU PROGRAMME
PRINCIPAL SECTION.
DEBUT.
PERFORM SAISIE.
CORPS.
PERFORM TRAITER.
FIN.
DISPLAY RESULTAT.
DISPLAY "FIN DU TRAITEMENT".
STOP RUN.
*SAISIE DU MOT
SAISIR SECTION.
SAISIE.
DISPLAY "Saisissez une phrase : " WITH NO ADVANCING.
ACCEPT MT-UTIL.
DISPLAY "MOT SAISI : " MT-UTIL.
*TRAITEMENT DE LA PHRASE
TRAITEMENT SECTION.
TRAITER.
PERFORM SPPR-SPC UNTIL CRSR-DP EQUAL TO 255.
MOVE 255 TO CRSR-DP.
MOVE 1 TO CRSR-RRV.
PERFORM COPIER UNTIL CRSR-DP EQUAL TO ZERO.
PERFORM COMPARER.
PERFORM DEDUIRE.
*SUPPRESSION DES ESPACES DU MOT DE DEPART
SPPR-SPC.
IF (MT-UTIL(CRSR-DP:1) NOT EQUAL TO SPACE) THEN
STRING MT-UTIL(CRSR-DP:1) DELIMITED BY SIZE INTO
MT-SS-SPC WITH POINTER CRSR-RRV.
ADD 1 TO CRSR-DP.
*COPIE DE LA CHAINE DE DEPART VERS UNE CHAINE D'ARRIVEE
COPIER.
IF (MT-UTIL(CRSR-DP:1) NOT EQUAL TO SPACE) THEN
STRING MT-UTIL(CRSR-DP:1) DELIMITED BY SIZE INTO MT-INV
WITH POINTER CRSR-RRV.
SUBTRACT 1 FROM CRSR-DP.
*COMPARAISON DE LA CHAINE DE CARACT<43>RE
COMPARER.
DISPLAY "MOT DEPART : " MT-SS-SPC.
DISPLAY "MOT ARRIVEE : " MT-INV.
IF (MT-SS-SPC EQUAL TO MT-INV) THEN
MOVE 1 TO PLND
ELSE MOVE ZERO TO PLND.
*DEDUCTION LOGIQUE DU RESULTAT
DEDUIRE.
IF (PLND EQUAL ZERO) THEN
MOVE "CE N'EST PAS UN PALINDROME" TO RESULTAT
ELSE MOVE "C'EST UN PALINDROME" TO RESULTAT.

View File

@ -0,0 +1,91 @@
IDENTIFICATION DIVISION.
PROGRAM-ID. palind.
AUTHOR. OD.
*-------------------------------------------*
* PROGRAMME DE VERIFICATION D'UN PALINDROME *
*-------------------------------------------*
ENVIRONMENT DIVISION.
DATA DIVISION.
WORKING-STORAGE SECTION.
*--------------------------*
* DEFINITION DES VARIABLES *
*--------------------------*
* LE MOT DONNE PAR L'UTILISATEUR
77 MOT PICTURE X(255) VALUE SPACE.
* RESULTAT DU PROGRAMME (ICI ON DIRA "CECI EST UN PALINDROME")
* OU PAS)
77 RESULTAT PICTURE X(30) VALUE SPACE.
* DEBUT-MOT ET DBUT-FIN SUBISSENT UNE INCREMENTATION
* CE SONT LES CURSEURS
77 DEBUT-MOT PICTURE 99 VALUE 1.
77 FIN-MOT PICTURE 99 VALUE 30.
* LETTREG CONTIENDRA UNE LETTRE DU MOT, CELLE COTE GAUCHE
* LETTRED, CELLE COTE DROITE
77 LETTREG PICTURE X VALUE SPACE.
77 LETTRED PICTURE X VALUE SPACE.
* DEFINITION DE QUELQUES VALEUR NUMERIQUES
* POUR LES CONTROLES
01 ETUDE-ENONCE.
05 COMP-VALID PICTURE 9 VALUE 1.
88 COMP-CORRECT VALUE 1.
05 CARAC-DEB PICTURE 9 VALUE 1.
88 CARACD-CORRECT VALUE 1.
05 CARAC-FIN PICTURE 9 VALUE 1.
88 CARACF-CORRECT VALUE 1.
PROCEDURE DIVISION.
*NOM DU PROGRAMME
PRINCIPAL SECTION.
DEBUT.
PERFORM SAISIE.
CORPS.
PERFORM TRAITER.
FIN.
DISPLAY RESULTAT.
DISPLAY "FIN DU TRAITEMENT".
STOP RUN.
*SAISIE DU MOT
SAISIR SECTION.
SAISIE.
DISPLAY "Saisissez une phrase : " WITH NO ADVANCING.
ACCEPT MOT.
*------*
* TEST *
*------*
DISPLAY MOT.
*TRAITEMENT DE LA PHRASE
TRAITEMENT SECTION.
TRAITER.
PERFORM COMPARER UNTIL NOT COMP-CORRECT.
*VALIDE IS NOT EQUAL TO 1.
*COMPARAISON DE LA CHAINE DE CARACT<43>RE
COMPARER.
DISPLAY DEBUT-MOT.
DISPLAY FIN-MOT.
* PERFORM PARCOURS-FIN UNTIL NOT CARACF-CORRECT.
MOVE ZERO TO COMP-VALID.
*PARCOURS DE LA CHAINE DE FIN
PARCOURS-FIN.
DISPLAY "DERNIERE LETTRE DU MOT : " MOT(FIN-MOT:1).
IF (MOT(FIN-MOT:1) EQUAL TO SPACE) THEN
SUBTRACT 1 FROM FIN-MOT
ELSE MOVE 1 TO CARAC-FIN
END-IF.
* MOVE MOT(FIN-MOT:1) TO LETTRE.
* PERFORM CAL-CHFFRE UNTIL LETTRE NOT EQUAL TO SPACE.
* IF (MOT(DEBUT-MOT:1) EQUAL TO MOT(FIN-MOT:1))
* MOVE 1 TO VALIDE
* END-IF.
*CALCUL DU CHIFFRE DE LA LETTRE <20> COMPARER
CAL-CHFFRE.
IF (MOT(FIN-MOT:1) EQUAL TO SPACE) THEN
SUBTRACT 1 FROM FIN-MOT
END-IF.

BIN
P5B/cobol/exercices/vehic Normal file

Binary file not shown.

View File

@ -0,0 +1,138 @@
IDENTIFICATION DIVISION.
PROGRAM-ID. vehic.
AUTHOR. OD.
***---------------------------------------------------------------
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT ARTICLES ASSIGN TO "$fichier"
ORGANIZATION IS INDEXED
RECORD KEY IS MTRCL
ALTERNATE RECORD KEY IS NO-SMN WITH DUPLICATES
ALTERNATE RECORD KEY IS RSLT WITH DUPLICATES
FILE STATUS VAL-ERREUR.
***---------------------------------------------------------------
DATA DIVISION.
FILE SECTION.
FD ARTICLES.
* STRUCTURE FOURNIE DANS L'EXERCICE
01 VHCL.
05 INDICATIF.
10 MTRCL PIC X(8).
10 NO-SMN PIC 99.
05 FILLER PIC X(8).
05 RSLT OCCURS 7.
10 KM PIC 9(4) VALUE ZERO.
10 FRS PIC 9(4)V99 VALUE ZERO.
WORKING-STORAGE SECTION.
* VALEUR DE L'ERREUR POTENTIELLE DE TRAITEMENT DU FICHIER
77 VAL-ERREUR PIC 99 VALUE ZERO.
* VALEUR ENTR<54>E POUR LE CHOIX DU MENU
77 VAL-MENU PIC X.
88 MENU-O VALUE "O" "o".
88 MENU-N VALUE "N" "n".
88 MENU-UN VALUE "1".
88 MENU-DX VALUE "2".
88 MENU-TRS VALUE "3".
88 MENU-QTR VALUE "4".
88 MENU-QTT VALUE "0".
* LA SEMAINE !
01 SEMAINES.
05 FILLER PIC X(8) VALUE "LUNDI".
05 FILLER PIC X(8) VALUE "MARDI".
05 FILLER PIC X(8) VALUE "MERCREDI".
05 FILLER PIC X(8) VALUE "JEUDI".
05 FILLER PIC X(8) VALUE "VENDREDI".
05 FILLER PIC X(8) VALUE "SAMEDI".
05 FILLER PIC X(8) VALUE "DIMANCHE".
01 SEM-T REDEFINES SEMAINES.
05 JOURS PIC X(8) OCCURS 7.
77 ITERATION PIC 9 VALUE 1.
* SAISIE DE L'UTILISATEUR POUR LE MATRICULE
77 SAIS-MTRCL PIC X(8) VALUE "0000XX00".
* SAISIE DE L'UTILISATEUR POUR LE NUMERO DE SEMAINE
77 SAIS-NO-SMN PIC 99 VALUE 00.
* SAISIE DE L'UTILISATEUR POUR LE NOMBRE DE KILOMETRES
77 SAIS-KM PIC 9(4) VALUE ZERO.
* SAISIE DE L'UTILISATEUR POUR LES FRAIS
77 SAIS-FRS PIC 9(4)V99 VALUE ZERO.
* UTILISATION D'UN ESPACE VIDE POUR L'ENREGISTREMENT
77 SAIS-VIDE PIC X(8) VALUE SPACE.
***---------------------------------------------------------------
PROCEDURE DIVISION.
*
* SECTION PRINCIPAL, APPEL<45>E PROGRAMME
*
PROGRAMME SECTION.
INIT.
OPEN I-O ARTICLES.
DISPLAY VAL-ERREUR.
CORPS.
PERFORM MENU-DPRT UNTIL MENU-N.
FIN.
CLOSE ARTICLES.
DISPLAY "PROGRAMME TERMINE !".
STOP RUN.
*
* PERMET L'AFFICHAGE DU MENU
*
MENU SECTION.
MENU-DPRT.
DISPLAY "PROCEDER <20> UN TRAITEMENT ? (o/n) : "
WITH NO ADVANCING.
ACCEPT VAL-MENU.
IF MENU-O THEN
PERFORM MENU-AFFICHE.
MENU-AFFICHE.
DISPLAY "(1) - CONSULTER UN ARTICLE DONNE".
DISPLAY "(2) - AJOUT D'UN ARTICLE".
DISPLAY "(3) - CALCUL DU PRIX DE REVIENT".
DISPLAY "(4) - SEMAINE O<> PLUS ROUL<55>".
DISPLAY "(0) - QUITTER".
DISPLAY "VOTRE CHOIX : " WITH NO ADVANCING.
ACCEPT VAL-MENU.
IF MENU-UN THEN PERFORM CONSULTATION
ELSE IF MENU-DX THEN PERFORM AJOUT
ELSE IF MENU-TRS THEN PERFORM CALCUL
ELSE IF MENU-QTR THEN PERFORM ROULE
ELSE IF MENU-QTT THEN PERFORM FIN.
*
* PERMET LA CONSULTATION D'UN ARTICLE
*
CONSULTER SECTION.
CONSULTATION.
*
* PERMET L'AJOUT D'UN ARTICLE
*
AJOUTER SECTION.
AJOUT.
DISPLAY "NUMERO DE SEMAINE : " WITH NO ADVANCING.
ACCEPT NO-SMN.
DISPLAY "IMMATRICULATION : " WITH NO ADVANCING.
ACCEPT MTRCL.
PERFORM AJOUT-SEM UNTIL ITERATION EQUAL TO 8.
WRITE VHCL.
AJOUT-SEM.
DISPLAY JOURS(ITERATION).
DISPLAY "KILOMETRAGE : " WITH NO ADVANCING.
ACCEPT KM(ITERATION).
DISPLAY "FRAIS : " WITH NO ADVANCING.
ACCEPT FRS(ITERATION).
ADD 1 TO ITERATION.
*
* PERMET LE CALCUL DU PRIX DE REVIENT KILOM<4F>TRIQUE DEPUIS LE D<>BUT
* D'ANN<4E>E
*
CALCULER SECTION.
CALCUL.
*
* PERMET DE TROUVER LA SEMAINE O<> UN V<>HICULE A LE PLUS ROUL<55>
*
ROULER SECTION.
ROULE.

Binary file not shown.

Binary file not shown.

Binary file not shown.

BIN
P5B/cobol/exercices/vehic2 Normal file

Binary file not shown.

View File

@ -0,0 +1,40 @@
identification division.
program-id. vehic2.
author. od.
environment division.
input-output section.
file-control.
select articles assign to "$fichier"
organization is indexed
record key is mtrcl
alternate record key is no-smn with duplicates
alternate record key is rslt with duplicates
file status val-erreur.
***---------------------------------------------------------------
data division.
file section.
fd articles.
* structure fournie dans l'exercice
01 vhcl.
05 indicatif.
10 mtrcl pic x(8).
10 no-smn pic 99.
05 filler pic x(8).
05 rslt occurs 7.
10 km pic 9(4) value zero.
10 frs pic 9(4)v99 value zero.
working-storage section.
77 val-erreur pic 99 value zero.
77 enregistrement pic x(88) value zero.
procedure division.
programme section.
init.
open input articles.
display val-erreur.
corps.
read articles.
display mtrcl.
fin.
close articleS.
display "fin de traitement".
stop run.

View File

@ -0,0 +1,90 @@
EXEMPLES ET EXERCICES
1. adresses sites
Quelques adresses utiles :
http://www.rubycentral.com/book/ // le livre de reference
http://www.rubycentral.com/ref/ // ref. classes avec listes des fonctions par classe
http://www.ruby-doc.org/core/ // voir les classes IO File File::Stat Dir FileTest Process
2. exemples de scripts
NB: tester d'abord les exemples avant de faire les exercices propos<6F>s.
A. manipulation du SGF
======================
Bcp de classes participent <20> la manipulation des objets "syst<73>me" : File, Dir, IO, etc...
- exemple 1 : cr<63>ation d'un fichier et remplissage <20> partir d'infos saisies au clavier (testSgf_1.rb)
- exemple 2 : ouverture et affichage des informations sur un fichier (stat) (testSgf_2.rb)
- exemple 3 : ouverture d'un fichier avec v<>rification existence et recherche des lignes ou
apparait un motif donne .
Le nom du fichier et le motif sont pass<73>s en param<61>tres au script (testSgf_3.rb)
- exemple 4 : afficher la liste des fichiers d'un repertoire donne (testSgf_4.rb)
- Exercices <20> faire
- Exercice 1 : <20>crire un script < histo > qui construit et affiche l'histogramme de repartition
par taille des fichiers du repertoire <rep>.
Nous aimerions conna<6E>tre la taille totale de fichiers examin<69>s, le nombre total de ces derniers et le nombre total de blocs.
Ainsi que la taille moyenne d'un fichier.
On definit <nbclasses> classes de repartition de taille identique <20> <taille>
usage : histo.rb <repertoire > <nombre_de_classe> <taille_de_classe>
- Exercice 2 : <20>crire un script <cherche> qui recherche tous les fichiers contenant un motif donn<6E>.
On affichera le nom du fichier et la ligne contenant le motif. Attention,
si plusieurs lignes du m<>me fichier contiennent <motif>, on n'affichera qu'une fois
le chemin absolu du fichier.
usage : cherche <motif> [filtre] [path]
B. manipulation de processus, signaux
=====================================
- exemple 1 : cr<63>ation d'un processus fils (testProc_1.rb)
Si on comment les lignes if avec les exit, on obtient ceci :
Pere 28716 Grand pere 28715 pid fils1 : nil pid fils2 : nil
Pere 28715 Grand pere 28713 pid fils1 : nil pid fils2 : 28716
Pere 28717 Grand pere 28713 pid fils1 : 28715 pid fils2 : nil
Pere 28713 Grand pere 22590 pid fils1 : 28715 pid fils2 : 28717
Donc le petit fils ne connait pas les autres
Le fils 2 se connait
Le fils 1 aussi
Et le p<>re connait les fils 1 et 2
- exemple 2 : communication entre un proc. p<>re et un proc. fils avec un tube (testProc_2.rb)
- exemple 3 : communication entre un proc. p<>re et un proc. fils avec un tube (2) (testProc_3.rb)
Si on enl<6E>ve le wr.close du Process.fork, alors le programme bloque, car quelqu'un utilise toujours le WR !
- exemple 4 : chronom<6F>tre (testSig_1.rb)
- Exercices <20> faire
- Exercice 1 : <20>crire un script qui ex<65>cute la commande "ls -l" en affichant le r<>sultat
en majuscule. On utilisera 2 processus et un tube pour communiquer.
Le proc. fils ex<65>cute la commande et le proc. p<>re affiche en majuscule.
NB: pour passer en mode debug, lancer : ruby -r debug ./testFile.rb <liste_arg>

52
P5B/ruby/161007/histo.rb Normal file
View File

@ -0,0 +1,52 @@
#!/usr/bin/ruby -w
# Affiche un histogramme du nombre de fichiers tri<72>s par classe de grandeur "tailleClasse" sur un nombre "nombreDeClasse".
# R<>cup<75>ration des argument
if ARGV.length < 3
puts "Utilisation : ./histo.rb < nomRep > < nbreDeClasse > < tailleClasse (en octet) >"
exit
end
# attribution d'<27>l<EFBFBD>ments
rep=ARGV[0]
nbr=ARGV[1].to_i
taille=ARGV[2].to_i
# initialisation de certaines variables
nbrFichiers = 0
tailleTotale = 0
tailleTotaleBlocs = 0
histogramme = []
for i in 0 ... nbr do
histogramme[i] = 0
end
# Nous allons dans le r<>pertoire courant
Dir.chdir(rep)
repertoireOuvert=Dir.open(rep)
repertoireOuvert.each do |entree|
if File.file?(entree)
fichier = File.open(entree,"r")
stats = fichier.stat
colonne = stats.size / taille
histogramme[colonne] = histogramme[colonne].to_i + 1
nbrFichiers = nbrFichiers + 1
tailleTotale = tailleTotale + stats.size
tailleTotaleBlocs = tailleTotaleBlocs + stats.blocks.to_i
end
end
histogramme.each do |element|
print(element.to_s, " | ")
end
puts "\nNombre total de fichiers examin<69>s : #{nbrFichiers}"
puts "Taille totale : #{tailleTotale}"
puts "Nombre total de blocs lus : #{tailleTotaleBlocs}"
tailleMoyenneFichier = tailleTotale / nbrFichiers
puts "Taille moyenne d'un fichier : #{tailleMoyenneFichier}"

View File

@ -0,0 +1,25 @@
#! /usr/bin/ruby -w
#
system("clear")
# creation d'un fils et d'un petit fils
pid1 = Process.fork
if pid1 == nil
Process.exit!(-1) #on sort si on est dans le fils
end
pid2 = Process.fork
if pid2 == nil # on sort si on est dans le fils
Process.exit!(0)
end
print "\nPere \t" , Process.pid , "\tGrand pere\t", Process.ppid(), "\tpid fils1 :\t" , pid1, "\tpid fils2 :\t" ,
pid2, "\n"
sleep 2.5
print "\nFin"

View File

@ -0,0 +1,22 @@
#!/usr/bin/ruby -w
# utilisation d'un tube entre 2 processus
rd, wr = IO.pipe # creation d'un tube avec 2 descripteurs pour lect/ecri
if fork # le pere ferme le desc. pour ecrire dans le tube
wr.close
ch=rd.read # est bloque tant que rien dans le tube
puts "message recu par le Pere : " + ch
rd.close
Process.wait # on attend la fin du fils
puts "le pere termine"
else # le fils
rd.close # ferme tube en lecture
puts "envoi d'un message "
wr.write "ceci est un test"
puts "le fils termine dans 2 secondes"
sleep 2
wr.close
end

View File

@ -0,0 +1,34 @@
#!/usr/bin/ruby -w
system("clear")
rd, wr = IO.pipe
print "\nPere : creation processus fils"
if Process.fork
wr.close
print "\nPere : lecture donnee depuis tube rd"
sleep 1
while ! rd.eof
c=rd.readchar
print "\ncaractere recu...."
putc c
print "\nattente...."
sleep 3
end
print "\nfin lecteur*\n"
rd.close
else
rd.close
sleep 1
print "\nFils : envoi donnee vers tube wr"
for i in 'a'..'g'
print "\n------>envoi du caractere ", i
wr.write i
sleep 1
end
print "\nfin redacteur*\n"
wr.close
end

View File

@ -0,0 +1,32 @@
#!/usr/bin/ruby -w
# lecture de donnee au clavier ou en redirigeant l'entree std
# fin de fichier provoquee par Ctrl D ou fin entree std
f = File.new("testfile","w+")
while s=gets do
f.write(s) # ou f.puts s
end
puts "\n\nrelecture du fichier \n"
f.rewind # revient au debut idem a f.lineno = 0
puts f.lineno
while not f.eof do
puts f.read
end
# insertion dans le fichier
f.seek(0, IO::SEEK_SET)
f.seek(100,IO::SEEK_CUR)
f.puts( "INSERTION A LA POSITION 100")
# verifier que l'insertion est bien effectuee en position 100
# utiliser la cde od -c testfile
puts "*stop*"

View File

@ -0,0 +1,22 @@
#!/usr/bin/ruby -w
# affichage infos sur un fichier
f = File.open("testfile","r")
# on recupere les infos grace a la methode stat -> objet aStat
s = f.stat
puts "\n\naffichage info fichier \n"
puts s # -> affiche reference memoire objet s !
puts "chemin absolu :" + File.expand_path(f.path)
puts "taille du fichier : " + s.size.to_s
puts "nombre de blocs : " + s.blocks.to_s
puts "fichier regulier: " + s.file?.to_s
puts "repertoire : " + s.directory?.to_s
puts "num<EFBFBD>ro de possesseur : " + s.uid.to_s

View File

@ -0,0 +1,32 @@
#!/usr/bin/ruby -w
# recherche d'une chaine dans un fichier donne
# nom et chaine sont passes en argument
if ARGV.length < 2
puts "usage : ./testFile_3 nom_fich motif"
exit
end
nomFich = ARGV[0]
motif = ARGV[1]
# test si fichier existe et fichier regulier
if not File.file?(nomFich)
puts "erreur fichier"
exit
end
f = File.open(nomFich,"r") # ouverture du fichier
puts "\n_______________________________________________\n"
puts "\n\naffichage des lignes du fichier contenant " + motif
puts "\n_______________________________________________\n"
f.grep(/#{motif}/) do |line|
puts line.chomp + " (" + f.lineno.to_s + " )" # On affiche la ligne et le motif
end
puts "fin"

View File

@ -0,0 +1,39 @@
#!/usr/bin/ruby -w
# affiche la liste des fichiers du repertoire en argument
if ARGV.length < 1
puts "usage : ./testSgf_4.rb < nomRep >"
exit
end
rep=ARGV[0]
#changement de repertoire
Dir.chdir(rep)
d=Dir.open(rep)
d.each { |u| puts u }
puts "_____________REPERTOIRE_______________"
# si on veut filter les fichiers du repertoire
Dir["*.rb"].each do |f|
puts f
end
puts "_____________ARBORESCENCE_____________"
# si on veut parcourir toute la sous-arborescence
Dir["**/*.rb"].each do |f|
puts f
end

View File

@ -0,0 +1,18 @@
#!/usr/bin/ruby -w
nsec=0
trap("SIGINT" ){ #attention a la place de la parenthese ouvrante
puts "\n"+nsec.to_s + " secondes ecoulees \n"
}
trap("SIGQUIT" ){ #attention a la place de la parenthese ouvrante
puts "\nFin du chronom<6F>tre "+nsec.to_s + " secondes ecoulees \n"
exit
}
while true
sleep 1
nsec = nsec + 1
end

BIN
P5B/ruby/161007/testfile Normal file

Binary file not shown.

10
P5B/ruby/161007/url.net Normal file
View File

@ -0,0 +1,10 @@
Quelques adresses utiles
http://www.rubycentral.com/book/ // le livre de reference
http://www.ruby-doc.org/docs/ProgrammingRuby/ // ref. classes avec listes des fonctions par classe
http://www.ruby-doc.org/core/ // voir les classes IO File File::Stat Dir FileTest Process

Binary file not shown.

Binary file not shown.

View File

@ -0,0 +1,211 @@
== Welcome to Rails
Rails is a web-application and persistence framework that includes everything
needed to create database-backed web-applications according to the
Model-View-Control pattern of separation. This pattern splits the view (also
called the presentation) into "dumb" templates that are primarily responsible
for inserting pre-built data in between HTML tags. The model contains the
"smart" domain objects (such as Account, Product, Person, Post) that holds all
the business logic and knows how to persist themselves to a database. The
controller handles the incoming requests (such as Save New Account, Update
Product, Show Post) by manipulating the model and directing data to the view.
In Rails, the model is handled by what's called an object-relational mapping
layer entitled Active Record. This layer allows you to present the data from
database rows as objects and embellish these data objects with business logic
methods. You can read more about Active Record in
link:files/vendor/rails/activerecord/README.html.
The controller and view are handled by the Action Pack, which handles both
layers by its two parts: Action View and Action Controller. These two layers
are bundled in a single package due to their heavy interdependence. This is
unlike the relationship between the Active Record and Action Pack that is much
more separate. Each of these packages can be used independently outside of
Rails. You can read more about Action Pack in
link:files/vendor/rails/actionpack/README.html.
== Getting started
1. At the command prompt, start a new rails application using the rails command
and your application name. Ex: rails myapp
(If you've downloaded rails in a complete tgz or zip, this step is already done)
2. Change directory into myapp and start the web server: <tt>script/server</tt> (run with --help for options)
3. Go to http://localhost:3000/ and get "Welcome aboard: Youre riding the Rails!"
4. Follow the guidelines to start developing your application
== Web Servers
By default, Rails will try to use Mongrel and lighttpd if they are installed, otherwise
Rails will use the WEBrick, the webserver that ships with Ruby. When you run script/server,
Rails will check if Mongrel exists, then lighttpd and finally fall back to WEBrick. This ensures
that you can always get up and running quickly.
Mongrel is a Ruby-based webserver with a C-component (which requires compilation) that is
suitable for development and deployment of Rails applications. If you have Ruby Gems installed,
getting up and running with mongrel is as easy as: <tt>gem install mongrel</tt>.
More info at: http://mongrel.rubyforge.org
If Mongrel is not installed, Rails will look for lighttpd. It's considerably faster than
Mongrel and WEBrick and also suited for production use, but requires additional
installation and currently only works well on OS X/Unix (Windows users are encouraged
to start with Mongrel). We recommend version 1.4.11 and higher. You can download it from
http://www.lighttpd.net.
And finally, if neither Mongrel or lighttpd are installed, Rails will use the built-in Ruby
web server, WEBrick. WEBrick is a small Ruby web server suitable for development, but not
for production.
But of course its also possible to run Rails on any platform that supports FCGI.
Apache, LiteSpeed, IIS are just a few. For more information on FCGI,
please visit: http://wiki.rubyonrails.com/rails/pages/FastCGI
== Debugging Rails
Sometimes your application goes wrong. Fortunately there are a lot of tools that
will help you debug it and get it back on the rails.
First area to check is the application log files. Have "tail -f" commands running
on the server.log and development.log. Rails will automatically display debugging
and runtime information to these files. Debugging info will also be shown in the
browser on requests from 127.0.0.1.
You can also log your own messages directly into the log file from your code using
the Ruby logger class from inside your controllers. Example:
class WeblogController < ActionController::Base
def destroy
@weblog = Weblog.find(params[:id])
@weblog.destroy
logger.info("#{Time.now} Destroyed Weblog ID ##{@weblog.id}!")
end
end
The result will be a message in your log file along the lines of:
Mon Oct 08 14:22:29 +1000 2007 Destroyed Weblog ID #1
More information on how to use the logger is at http://www.ruby-doc.org/core/
Also, Ruby documentation can be found at http://www.ruby-lang.org/ including:
* The Learning Ruby (Pickaxe) Book: http://www.ruby-doc.org/docs/ProgrammingRuby/
* Learn to Program: http://pine.fm/LearnToProgram/ (a beginners guide)
These two online (and free) books will bring you up to speed on the Ruby language
and also on programming in general.
== Breakpoints
Breakpoint support is available through the script/breakpointer client. This
means that you can break out of execution at any point in the code, investigate
and change the model, AND then resume execution! Example:
class WeblogController < ActionController::Base
def index
@posts = Post.find(:all)
breakpoint "Breaking out from the list"
end
end
So the controller will accept the action, run the first line, then present you
with a IRB prompt in the breakpointer window. Here you can do things like:
Executing breakpoint "Breaking out from the list" at .../webrick_server.rb:16 in 'breakpoint'
>> @posts.inspect
=> "[#<Post:0x14a6be8 @attributes={\"title\"=>nil, \"body\"=>nil, \"id\"=>\"1\"}>,
#<Post:0x14a6620 @attributes={\"title\"=>\"Rails you know!\", \"body\"=>\"Only ten..\", \"id\"=>\"2\"}>]"
>> @posts.first.title = "hello from a breakpoint"
=> "hello from a breakpoint"
...and even better is that you can examine how your runtime objects actually work:
>> f = @posts.first
=> #<Post:0x13630c4 @attributes={"title"=>nil, "body"=>nil, "id"=>"1"}>
>> f.
Display all 152 possibilities? (y or n)
Finally, when you're ready to resume execution, you press CTRL-D
== Console
You can interact with the domain model by starting the console through <tt>script/console</tt>.
Here you'll have all parts of the application configured, just like it is when the
application is running. You can inspect domain models, change values, and save to the
database. Starting the script without arguments will launch it in the development environment.
Passing an argument will specify a different environment, like <tt>script/console production</tt>.
To reload your controllers and models after launching the console run <tt>reload!</tt>
To reload your controllers and models after launching the console run <tt>reload!</tt>
== Description of contents
app
Holds all the code that's specific to this particular application.
app/controllers
Holds controllers that should be named like weblogs_controller.rb for
automated URL mapping. All controllers should descend from ApplicationController
which itself descends from ActionController::Base.
app/models
Holds models that should be named like post.rb.
Most models will descend from ActiveRecord::Base.
app/views
Holds the template files for the view that should be named like
weblogs/index.rhtml for the WeblogsController#index action. All views use eRuby
syntax.
app/views/layouts
Holds the template files for layouts to be used with views. This models the common
header/footer method of wrapping views. In your views, define a layout using the
<tt>layout :default</tt> and create a file named default.rhtml. Inside default.rhtml,
call <% yield %> to render the view using this layout.
app/helpers
Holds view helpers that should be named like weblogs_helper.rb. These are generated
for you automatically when using script/generate for controllers. Helpers can be used to
wrap functionality for your views into methods.
config
Configuration files for the Rails environment, the routing map, the database, and other dependencies.
components
Self-contained mini-applications that can bundle together controllers, models, and views.
db
Contains the database schema in schema.rb. db/migrate contains all
the sequence of Migrations for your schema.
doc
This directory is where your application documentation will be stored when generated
using <tt>rake doc:app</tt>
lib
Application specific libraries. Basically, any kind of custom code that doesn't
belong under controllers, models, or helpers. This directory is in the load path.
public
The directory available for the web server. Contains subdirectories for images, stylesheets,
and javascripts. Also contains the dispatchers and the default HTML files. This should be
set as the DOCUMENT_ROOT of your web server.
script
Helper scripts for automation and generation.
test
Unit and functional tests along with fixtures. When using the script/generate scripts, template
test files will be generated for you and placed in this directory.
vendor
External libraries that the application depends on. Also includes the plugins subdirectory.
This directory is in the load path.

View File

@ -0,0 +1,10 @@
# Add your own tasks in files placed in lib/tasks ending in .rake,
# for example lib/tasks/capistrano.rake, and they will automatically be available to Rake.
require(File.join(File.dirname(__FILE__), 'config', 'boot'))
require 'rake'
require 'rake/testtask'
require 'rake/rdoctask'
require 'tasks/rails'

View File

@ -0,0 +1,7 @@
# Filters added to this controller apply to all controllers in the application.
# Likewise, all the methods added will be available for all controllers.
class ApplicationController < ActionController::Base
# Pick a unique cookie name to distinguish our session data from others'
session :session_key => '_3dossmanno_annuaire_session_id'
end

View File

@ -0,0 +1,31 @@
# This controller handles the login/logout function of the site.
class SessionsController < ApplicationController
# Be sure to include AuthenticationSystem in Application Controller instead
include AuthenticatedSystem
# render new.rhtml
def new
end
def create
self.current_user = User.authenticate(params[:login], params[:password])
if logged_in?
if params[:remember_me] == "1"
self.current_user.remember_me
cookies[:auth_token] = { :value => self.current_user.remember_token , :expires => self.current_user.remember_token_expires_at }
end
redirect_back_or_default('/')
flash[:notice] = "Logged in successfully"
else
render :action => 'new'
end
end
def destroy
self.current_user.forget_me if logged_in?
cookies.delete :auth_token
reset_session
flash[:notice] = "You have been logged out."
redirect_back_or_default('/')
end
end

View File

@ -0,0 +1,30 @@
class UsersController < ApplicationController
# Be sure to include AuthenticationSystem in Application Controller instead
include AuthenticatedSystem
# render new.rhtml
def new
end
def create
cookies.delete :auth_token
reset_session
@user = User.new(params[:user])
@user.save!
self.current_user = @user
redirect_back_or_default('/')
flash[:notice] = "Thanks for signing up!"
rescue ActiveRecord::RecordInvalid
render :action => 'new'
end
def activate
self.current_user = params[:activation_code].blank? ? :false : User.find_by_activation_code(params[:activation_code])
if logged_in? && !current_user.activated?
current_user.activate
flash[:notice] = "Signup complete!"
end
redirect_back_or_default('/')
end
end

View File

@ -0,0 +1,79 @@
class UtilisateursController < ApplicationController
# GET /utilisateurs
# GET /utilisateurs.xml
def index
@utilisateurs = Utilisateur.find(:all)
respond_to do |format|
format.html # index.rhtml
format.xml { render :xml => @utilisateurs.to_xml }
end
end
# GET /utilisateurs/1
# GET /utilisateurs/1.xml
def show
@utilisateur = Utilisateur.find(params[:id])
respond_to do |format|
format.html # show.rhtml
format.xml { render :xml => @utilisateur.to_xml }
end
end
# GET /utilisateurs/new
def new
@utilisateur = Utilisateur.new
end
# GET /utilisateurs/1;edit
def edit
@utilisateur = Utilisateur.find(params[:id])
end
# POST /utilisateurs
# POST /utilisateurs.xml
def create
@utilisateur = Utilisateur.new(params[:utilisateur])
respond_to do |format|
if @utilisateur.save
flash[:notice] = 'Utilisateur was successfully created.'
format.html { redirect_to utilisateur_url(@utilisateur) }
format.xml { head :created, :location => utilisateur_url(@utilisateur) }
else
format.html { render :action => "new" }
format.xml { render :xml => @utilisateur.errors.to_xml }
end
end
end
# PUT /utilisateurs/1
# PUT /utilisateurs/1.xml
def update
@utilisateur = Utilisateur.find(params[:id])
respond_to do |format|
if @utilisateur.update_attributes(params[:utilisateur])
flash[:notice] = 'Utilisateur was successfully updated.'
format.html { redirect_to utilisateur_url(@utilisateur) }
format.xml { head :ok }
else
format.html { render :action => "edit" }
format.xml { render :xml => @utilisateur.errors.to_xml }
end
end
end
# DELETE /utilisateurs/1
# DELETE /utilisateurs/1.xml
def destroy
@utilisateur = Utilisateur.find(params[:id])
@utilisateur.destroy
respond_to do |format|
format.html { redirect_to utilisateurs_url }
format.xml { head :ok }
end
end
end

View File

@ -0,0 +1,3 @@
# Methods added to this helper will be available to all templates in the application.
module ApplicationHelper
end

View File

@ -0,0 +1,2 @@
module SessionsHelper
end

View File

@ -0,0 +1,2 @@
module UsersHelper
end

View File

@ -0,0 +1,2 @@
module UtilisateursHelper
end

View File

@ -0,0 +1,98 @@
require 'digest/sha1'
class User < ActiveRecord::Base
# Virtual attribute for the unencrypted password
attr_accessor :password
validates_presence_of :login, :email
validates_presence_of :password, :if => :password_required?
validates_presence_of :password_confirmation, :if => :password_required?
validates_length_of :password, :within => 4..40, :if => :password_required?
validates_confirmation_of :password, :if => :password_required?
validates_length_of :login, :within => 3..40
validates_length_of :email, :within => 3..100
validates_uniqueness_of :login, :email, :case_sensitive => false
before_save :encrypt_password
before_create :make_activation_code
# prevents a user from submitting a crafted form that bypasses activation
# anything else you want your user to change should be added here.
attr_accessible :login, :email, :password, :password_confirmation
# Activates the user in the database.
def activate
@activated = true
self.activated_at = Time.now.utc
self.activation_code = nil
save(false)
end
def activated?
# the existence of an activation code means they have not activated yet
activation_code.nil?
end
# Returns true if the user has just been activated.
def recently_activated?
@activated
end
# Authenticates a user by their login name and unencrypted password. Returns the user or nil.
def self.authenticate(login, password)
u = find :first, :conditions => ['login = ? and activated_at IS NOT NULL', login] # need to get the salt
u && u.authenticated?(password) ? u : nil
end
# Encrypts some data with the salt.
def self.encrypt(password, salt)
Digest::SHA1.hexdigest("--#{salt}--#{password}--")
end
# Encrypts the password with the user salt
def encrypt(password)
self.class.encrypt(password, salt)
end
def authenticated?(password)
crypted_password == encrypt(password)
end
def remember_token?
remember_token_expires_at && Time.now.utc < remember_token_expires_at
end
# These create and unset the fields required for remembering users between browser closes
def remember_me
remember_me_for 2.weeks
end
def remember_me_for(time)
remember_me_until time.from_now.utc
end
def remember_me_until(time)
self.remember_token_expires_at = time
self.remember_token = encrypt("#{email}--#{remember_token_expires_at}")
save(false)
end
def forget_me
self.remember_token_expires_at = nil
self.remember_token = nil
save(false)
end
protected
# before filter
def encrypt_password
return if password.blank?
self.salt = Digest::SHA1.hexdigest("--#{Time.now.to_s}--#{login}--") if new_record?
self.crypted_password = encrypt(password)
end
def password_required?
crypted_password.blank? || !password.blank?
end
def make_activation_code
self.activation_code = Digest::SHA1.hexdigest( Time.now.to_s.split(//).sort_by {rand}.join )
end
end

View File

@ -0,0 +1,24 @@
class UserMailer < ActionMailer::Base
def signup_notification(user)
setup_email(user)
@subject += 'Please activate your new account'
@body[:url] = "http://YOURSITE/activate/#{user.activation_code}"
end
def activation(user)
setup_email(user)
@subject += 'Your account has been activated!'
@body[:url] = "http://YOURSITE/"
end
protected
def setup_email(user)
@recipients = "#{user.email}"
@from = "ADMINEMAIL"
@subject = "[YOURSITE] "
@sent_on = Time.now
@body[:user] = user
end
end

View File

@ -0,0 +1,11 @@
class UserObserver < ActiveRecord::Observer
def after_create(user)
UserMailer.deliver_signup_notification(user)
end
def after_save(user)
UserMailer.deliver_activation(user) if user.recently_activated?
end
end

View File

@ -0,0 +1,2 @@
class Utilisateur < ActiveRecord::Base
end

View File

@ -0,0 +1,17 @@
<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN"
"http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd">
<html xmlns="http://www.w3.org/1999/xhtml" xml:lang="en" lang="en">
<head>
<meta http-equiv="content-type" content="text/html;charset=UTF-8" />
<title>Utilisateurs: <%= controller.action_name %></title>
<%= stylesheet_link_tag 'scaffold' %>
</head>
<body>
<p style="color: green"><%= flash[:notice] %></p>
<%= yield %>
</body>
</html>

View File

@ -0,0 +1,14 @@
<% form_tag session_path do -%>
<p><label for="login">Login</label><br/>
<%= text_field_tag 'login' %></p>
<p><label for="password">Password</label><br/>
<%= password_field_tag 'password' %></p>
<!-- Uncomment this if you want this functionality
<p><label for="remember_me">Remember me:</label>
<%= check_box_tag 'remember_me' %></p>
-->
<p><%= submit_tag 'Log in' %></p>
<% end -%>

View File

@ -0,0 +1,3 @@
<%= @user.login %>, your account has been activated. You may now start adding your plugins:
<%= @url %>

View File

@ -0,0 +1,8 @@
Your account has been created.
Username: <%= @user.login %>
Password: <%= @user.password %>
Visit this url to activate your account:
<%= @url %>

View File

@ -0,0 +1,16 @@
<%= error_messages_for :user %>
<% form_for :user, :url => users_path do |f| -%>
<p><label for="login">Login</label><br/>
<%= f.text_field :login %></p>
<p><label for="email">Email</label><br/>
<%= f.text_field :email %></p>
<p><label for="password">Password</label><br/>
<%= f.password_field :password %></p>
<p><label for="password_confirmation">Confirm Password</label><br/>
<%= f.password_field :password_confirmation %></p>
<p><%= submit_tag 'Sign up' %></p>
<% end -%>

View File

@ -0,0 +1,62 @@
<h1>Edition utilisateur</h1>
<%= error_messages_for :utilisateur %>
<% form_for(:utilisateur, :url => utilisateur_path(@utilisateur), :html => { :method => :put }) do |f| %>
<p>
<b>Nom</b><br />
<%= f.text_field :nom %>
</p>
<p>
<b>Pr<50>nom</b><br />
<%= f.text_field :prenom %>
</p>
<p>
<b>Classe</b><br />
<%= f.text_field :classe %>
</p>
<p>
<b>Adresse courriel</b><br />
<%= f.text_field :email %>
</p>
<p>
<b>Age</b><br />
<%= f.text_field :age %>
</p>
<p>
<b>Rue</b><br />
<%= f.text_field :rue %>
</p>
<p>
<b>Code postal</b><br />
<%= f.text_field :codePostal %>
</p>
<p>
<b>Ville</b><br />
<%= f.text_field :ville %>
</p>
<p>
<b>Photo</b><br />
<%= f.text_field :photo %>
</p>
<p>
<b>Type</b><br />
<%= f.text_field :type %>
</p>
<p>
<%= submit_tag "Mise <20> jour" %>
</p>
<% end %>
<%= link_to 'Montrer', utilisateur_path(@utilisateur) %> |
<%= link_to 'Retour', utilisateurs_path %>

View File

@ -0,0 +1,38 @@
<h1>Listing utilisateurs</h1>
<table>
<tr>
<th>Nom</th>
<th>Pr<50>nom</th>
<th>Classe</th>
<th>Email</th>
<th>Age</th>
<th>Rue</th>
<th>Code Postal</th>
<th>Ville</th>
<th>Photo</th>
<th>Type</th>
</tr>
<% for utilisateur in @utilisateurs %>
<tr>
<td><%=h utilisateur.nom %></td>
<td><%=h utilisateur.prenom %></td>
<td><%=h utilisateur.classe %></td>
<td><%=h utilisateur.email %></td>
<td><%=h utilisateur.age %></td>
<td><%=h utilisateur.rue %></td>
<td><%=h utilisateur.codePostal %></td>
<td><%=h utilisateur.ville %></td>
<td><%=h utilisateur.photo %></td>
<td><%=h utilisateur.type %></td>
<td><%= link_to 'Montrer', utilisateur_path(utilisateur) %></td>
<td><%= link_to 'Editer', edit_utilisateur_path(utilisateur) %></td>
<td><%= link_to 'Supprimer', utilisateur_path(utilisateur), :confirm => 'Etes vous s<>r ?', :method => :delete %></td>
</tr>
<% end %>
</table>
<br />
<%= link_to 'Nouvel utilisateur', new_utilisateur_path %>

View File

@ -0,0 +1,61 @@
<h1>New utilisateur</h1>
<%= error_messages_for :utilisateur %>
<% form_for(:utilisateur, :url => utilisateurs_path) do |f| %>
<p>
<b>Nom</b><br />
<%= f.text_field :nom %>
</p>
<p>
<b>Prenom</b><br />
<%= f.text_field :prenom %>
</p>
<p>
<b>Classe</b><br />
<%= f.text_field :classe %>
</p>
<p>
<b>Email</b><br />
<%= f.text_field :email %>
</p>
<p>
<b>Age</b><br />
<%= f.text_field :age %>
</p>
<p>
<b>Rue</b><br />
<%= f.text_field :rue %>
</p>
<p>
<b>Codepostal</b><br />
<%= f.text_field :codePostal %>
</p>
<p>
<b>Ville</b><br />
<%= f.text_field :ville %>
</p>
<p>
<b>Photo</b><br />
<%= f.text_field :photo %>
</p>
<p>
<b>Type</b><br />
<%= f.text_field :type %>
</p>
<p>
<%= submit_tag "Create" %>
</p>
<% end %>
<%= link_to 'Back', utilisateurs_path %>

View File

@ -0,0 +1,53 @@
<p>
<b>Nom:</b>
<%=h @utilisateur.nom %>
</p>
<p>
<b>Prenom:</b>
<%=h @utilisateur.prenom %>
</p>
<p>
<b>Classe:</b>
<%=h @utilisateur.classe %>
</p>
<p>
<b>Email:</b>
<%=h @utilisateur.email %>
</p>
<p>
<b>Age:</b>
<%=h @utilisateur.age %>
</p>
<p>
<b>Rue:</b>
<%=h @utilisateur.rue %>
</p>
<p>
<b>Codepostal:</b>
<%=h @utilisateur.codePostal %>
</p>
<p>
<b>Ville:</b>
<%=h @utilisateur.ville %>
</p>
<p>
<b>Photo:</b>
<%=h @utilisateur.photo %>
</p>
<p>
<b>Type:</b>
<%=h @utilisateur.type %>
</p>
<%= link_to 'Edit', edit_utilisateur_path(@utilisateur) %> |
<%= link_to 'Back', utilisateurs_path %>

View File

@ -0,0 +1,14 @@
development:
bucket_name: appname_development
access_key_id:
secret_access_key:
test:
bucket_name: appname_test
access_key_id:
secret_access_key:
production:
bucket_name: appname
access_key_id:
secret_access_key:

View File

@ -0,0 +1,39 @@
# Don't change this file. Configuration is done in config/environment.rb and config/environments/*.rb
RAILS_ROOT = "#{File.dirname(__FILE__)}/.." unless defined?(RAILS_ROOT)
unless defined?(Rails::Initializer)
if File.directory?("#{RAILS_ROOT}/vendor/rails")
require "#{RAILS_ROOT}/vendor/rails/railties/lib/initializer"
else
require 'rubygems'
rails_gem_version =
if defined? RAILS_GEM_VERSION
RAILS_GEM_VERSION
else
File.read("#{File.dirname(__FILE__)}/environment.rb") =~ /^[^#]*RAILS_GEM_VERSION\s+=\s+'([\d.]+)'/
$1
end
if rails_gem_version
rails_gem = Gem.cache.search('rails', "=#{rails_gem_version}.0").sort_by { |g| g.version.version }.last
if rails_gem
gem "rails", "=#{rails_gem.version.version}"
require rails_gem.full_gem_path + '/lib/initializer'
else
STDERR.puts %(Cannot find gem for Rails =#{rails_gem_version}.0:
Install the missing gem with 'gem install -v=#{rails_gem_version} rails', or
change environment.rb to define RAILS_GEM_VERSION with your desired version.
)
exit 1
end
else
gem "rails"
require 'initializer'
end
end
Rails::Initializer.run(:set_load_path)
end

View File

@ -0,0 +1,38 @@
# MySQL (default setup). Versions 4.1 and 5.0 are recommended.
#
# Install the MySQL driver:
# gem install mysql
# On MacOS X:
# gem install mysql -- --include=/usr/local/lib
# On Windows:
# gem install mysql
# Choose the win32 build.
# Install MySQL and put its /bin directory on your path.
#
# And be sure to use new-style password hashing:
# http://dev.mysql.com/doc/refman/5.0/en/old-client.html
development:
adapter: mysql
database: 073dossmanno_dev
username: 3dossmanno
password: 3dossmanno
host: pipit
encoding: utf8
# Warning: The database defined as 'test' will be erased and
# re-generated from your development database when you run 'rake'.
# Do not set this db to the same as development or production.
test:
adapter: mysql
database: 073dossmanno_test
username: 3dossmanno
password: 3dossmanno
host: pipit
encoding: utf8
production:
adapter: mysql
database: 3dossmanno_annuaire_production
username: root
password:
host: localhost

View File

@ -0,0 +1,60 @@
# Be sure to restart your web server when you modify this file.
# Uncomment below to force Rails into production mode when
# you don't control web/app server and can't set it the proper way
# ENV['RAILS_ENV'] ||= 'production'
# Specifies gem version of Rails to use when vendor/rails is not present
RAILS_GEM_VERSION = '1.2.5' unless defined? RAILS_GEM_VERSION
# Bootstrap the Rails environment, frameworks, and default configuration
require File.join(File.dirname(__FILE__), 'boot')
Rails::Initializer.run do |config|
# Settings in config/environments/* take precedence over those specified here
# Skip frameworks you're not going to use (only works if using vendor/rails)
# config.frameworks -= [ :action_web_service, :action_mailer ]
# Only load the plugins named here, by default all plugins in vendor/plugins are loaded
# config.plugins = %W( exception_notification ssl_requirement )
# Add additional load paths for your own custom dirs
# config.load_paths += %W( #{RAILS_ROOT}/extras )
# Force all environments to use the same logger level
# (by default production uses :info, the others :debug)
# config.log_level = :debug
# Use the database for sessions instead of the file system
# (create the session table with 'rake db:sessions:create')
# config.action_controller.session_store = :active_record_store
# Use SQL instead of Active Record's schema dumper when creating the test database.
# This is necessary if your schema can't be completely dumped by the schema dumper,
# like if you have constraints or database-specific column types
# config.active_record.schema_format = :sql
# Activate observers that should always be running
# config.active_record.observers = :cacher, :garbage_collector
# Make Active Record use UTC-base instead of local time
# config.active_record.default_timezone = :utc
# Add new inflection rules using the following format
# (all these examples are active by default):
# Inflector.inflections do |inflect|
# inflect.plural /^(ox)$/i, '\1en'
# inflect.singular /^(ox)en/i, '\1'
# inflect.irregular 'person', 'people'
# inflect.uncountable %w( fish sheep )
# end
# See Rails::Configuration for more options
end
# Add new mime types for use in respond_to blocks:
# Mime::Type.register "text/richtext", :rtf
# Mime::Type.register "application/x-mobile", :mobile
# Include your application configuration below

View File

@ -0,0 +1,21 @@
# Settings specified here will take precedence over those in config/environment.rb
# In the development environment your application's code is reloaded on
# every request. This slows down response time but is perfect for development
# since you don't have to restart the webserver when you make code changes.
config.cache_classes = false
# Log error messages when you accidentally call methods on nil.
config.whiny_nils = true
# Enable the breakpoint server that script/breakpointer connects to
config.breakpoint_server = true
# Show full error reports and disable caching
config.action_controller.consider_all_requests_local = true
config.action_controller.perform_caching = false
config.action_view.cache_template_extensions = false
config.action_view.debug_rjs = true
# Don't care if the mailer can't send
config.action_mailer.raise_delivery_errors = false

View File

@ -0,0 +1,18 @@
# Settings specified here will take precedence over those in config/environment.rb
# The production environment is meant for finished, "live" apps.
# Code is not reloaded between requests
config.cache_classes = true
# Use a different logger for distributed setups
# config.logger = SyslogLogger.new
# Full error reports are disabled and caching is turned on
config.action_controller.consider_all_requests_local = false
config.action_controller.perform_caching = true
# Enable serving of images, stylesheets, and javascripts from an asset server
# config.action_controller.asset_host = "http://assets.example.com"
# Disable delivery errors, bad email addresses will be ignored
# config.action_mailer.raise_delivery_errors = false

View File

@ -0,0 +1,19 @@
# Settings specified here will take precedence over those in config/environment.rb
# The test environment is used exclusively to run your application's
# test suite. You never need to work with it otherwise. Remember that
# your test database is "scratch space" for the test suite and is wiped
# and recreated between test runs. Don't rely on the data there!
config.cache_classes = true
# Log error messages when you accidentally call methods on nil.
config.whiny_nils = true
# Show full error reports and disable caching
config.action_controller.consider_all_requests_local = true
config.action_controller.perform_caching = false
# Tell ActionMailer not to deliver emails to the real world.
# The :test delivery method accumulates sent emails in the
# ActionMailer::Base.deliveries array.
config.action_mailer.delivery_method = :test

View File

@ -0,0 +1,28 @@
ActionController::Routing::Routes.draw do |map|
map.resources :utilisateurs
map.ressources :users
map.resource :session, :controller => 'sessions'
# The priority is based upon order of creation: first created -> highest priority.
# Sample of regular route:
# map.connect 'products/:id', :controller => 'catalog', :action => 'view'
# Keep in mind you can assign values other than :controller and :action
# Sample of named route:
# map.purchase 'products/:id/purchase', :controller => 'catalog', :action => 'purchase'
# This route can be invoked with purchase_url(:id => product.id)
# You can have the root of your site routed by hooking up ''
# -- just remember to delete public/index.html.
# map.connect '', :controller => "welcome"
# Allow downloading Web Service WSDL as a file with an extension
# instead of a file named 'wsdl'
#map.connect ':controller/service.wsdl', :action => 'wsdl'
# Install the default route as the lowest priority.
map.connect ':controller/:action/:id.:format'
map.connect ':controller/:action/:id'
end

View File

@ -0,0 +1,23 @@
class CreateUtilisateurs < ActiveRecord::Migration
db_name = ActiveRecord::Base::connection.current_database()
execute "ALTER DATABASE #{db_name} CHARACTER SET utf8 COLLATE utf8_general_ci"
def self.up
create_table :utilisateurs do |t|
t.column :nom, :string
t.column :prenom, :string
t.column :classe, :string
t.column :email, :string
t.column :age, :int[3]
t.column :rue, :string
t.column :codePostal, :int[5]
t.column :ville, :string
t.column :photo, :image
t.column :type, :string
end
end
def self.down
drop_table :utilisateurs
end
end

View File

@ -0,0 +1,21 @@
class CreateUsers < ActiveRecord::Migration
def self.up
create_table "users", :force => true do |t|
t.column :login, :string
t.column :email, :string
t.column :crypted_password, :string, :limit => 40
t.column :salt, :string, :limit => 40
t.column :created_at, :datetime
t.column :updated_at, :datetime
t.column :remember_token, :string
t.column :remember_token_expires_at, :datetime
t.column :activation_code, :string, :limit => 40
t.column :activated_at, :datetime
end
end
def self.down
drop_table "users"
end
end

View File

@ -0,0 +1,37 @@
# This file is autogenerated. Instead of editing this file, please use the
# migrations feature of ActiveRecord to incrementally modify your database, and
# then regenerate this schema definition.
ActiveRecord::Schema.define(:version => 6) do
create_table "addresses", :force => true do |t|
t.column "street", :text
t.column "postal_code", :string
t.column "city", :string
t.column "country", :string
end
create_table "customers", :force => true do |t|
t.column "firstname", :string
t.column "name", :string
end
create_table "products", :force => true do |t|
t.column "designation", :string
t.column "description", :text
t.column "created_at", :datetime
t.column "updated_at", :datetime
t.column "supplier_id", :integer
t.column "customer_id", :integer
t.column "type", :string
end
create_table "suppliers", :force => true do |t|
t.column "name", :string
t.column "description", :text
t.column "code", :string
t.column "created_at", :datetime
t.column "updated_at", :datetime
end
end

View File

@ -0,0 +1,2 @@
Use this README file to introduce your application and point to useful places in the API for learning more.
Run "rake appdoc" to generate API documentation for your models and controllers.

View File

@ -0,0 +1,127 @@
module AuthenticatedSystem
protected
# Returns true or false if the user is logged in.
# Preloads @current_user with the user model if they're logged in.
def logged_in?
current_user != :false
end
# Accesses the current user from the session. Set it to :false if login fails
# so that future calls do not hit the database.
def current_user
@current_user ||= (login_from_session || login_from_basic_auth || login_from_cookie || :false)
end
# Store the given user in the session.
def current_user=(new_user)
session[:user] = (new_user.nil? || new_user.is_a?(Symbol)) ? nil : new_user.id
@current_user = new_user
end
# Check if the user is authorized
#
# Override this method in your controllers if you want to restrict access
# to only a few actions or if you want to check if the user
# has the correct rights.
#
# Example:
#
# # only allow nonbobs
# def authorized?
# current_user.login != "bob"
# end
def authorized?
logged_in?
end
# Filter method to enforce a login requirement.
#
# To require logins for all actions, use this in your controllers:
#
# before_filter :login_required
#
# To require logins for specific actions, use this in your controllers:
#
# before_filter :login_required, :only => [ :edit, :update ]
#
# To skip this in a subclassed controller:
#
# skip_before_filter :login_required
#
def login_required
authorized? || access_denied
end
# Redirect as appropriate when an access request fails.
#
# The default action is to redirect to the login screen.
#
# Override this method in your controllers if you want to have special
# behavior in case the user is not authorized
# to access the requested action. For example, a popup window might
# simply close itself.
def access_denied
respond_to do |accepts|
accepts.html do
store_location
redirect_to :controller => '/sessions', :action => 'new'
end
accepts.xml do
headers["Status"] = "Unauthorized"
headers["WWW-Authenticate"] = %(Basic realm="Web Password")
render :text => "Could't authenticate you", :status => '401 Unauthorized'
end
end
false
end
# Store the URI of the current request in the session.
#
# We can return to this location by calling #redirect_back_or_default.
def store_location
session[:return_to] = request.request_uri
end
# Redirect to the URI stored by the most recent store_location call or
# to the passed default.
def redirect_back_or_default(default)
session[:return_to] ? redirect_to_url(session[:return_to]) : redirect_to(default)
session[:return_to] = nil
end
# Inclusion hook to make #current_user and #logged_in?
# available as ActionView helper methods.
def self.included(base)
base.send :helper_method, :current_user, :logged_in?
end
# Called from #current_user. First attempt to login by the user id stored in the session.
def login_from_session
self.current_user = User.find_by_id(session[:user]) if session[:user]
end
# Called from #current_user. Now, attempt to login by basic authentication information.
def login_from_basic_auth
username, passwd = get_auth_data
self.current_user = User.authenticate(username, passwd) if username && passwd
end
# Called from #current_user. Finaly, attempt to login by an expiring token in the cookie.
def login_from_cookie
user = cookies[:auth_token] && User.find_by_remember_token(cookies[:auth_token])
if user && user.remember_token?
user.remember_me
cookies[:auth_token] = { :value => user.remember_token, :expires => user.remember_token_expires_at }
self.current_user = user
end
end
private
@@http_auth_headers = %w(X-HTTP_AUTHORIZATION HTTP_AUTHORIZATION Authorization)
# gets BASIC auth info
def get_auth_data
auth_key = @@http_auth_headers.detect { |h| request.env.has_key?(h) }
auth_data = request.env[auth_key].to_s.split unless auth_key.blank?
return auth_data && auth_data[0] == 'Basic' ? Base64.decode64(auth_data[1]).split(':')[0..1] : [nil, nil]
end
end

View File

@ -0,0 +1,26 @@
module AuthenticatedTestHelper
# Sets the current user in the session from the user fixtures.
def login_as(user)
@request.session[:user] = user ? users(user).id : nil
end
def authorize_as(user)
@request.env["HTTP_AUTHORIZATION"] = user ? "Basic #{Base64.encode64("#{users(user).login}:test")}" : nil
end
# taken from edge rails / rails 2.0. Only needed on Rails 1.2.3
def assert_difference(expressions, difference = 1, message = nil, &block)
expression_evaluations = [expressions].flatten.collect{|expression| lambda { eval(expression, block.binding) } }
original_values = expression_evaluations.inject([]) { |memo, expression| memo << expression.call }
yield
expression_evaluations.each_with_index do |expression, i|
assert_equal original_values[i] + difference, expression.call, message
end
end
# taken from edge rails / rails 2.0. Only needed on Rails 1.2.3
def assert_no_difference(expressions, message = nil, &block)
assert_difference expressions, 0, message, &block
end
end

View File

@ -0,0 +1,344 @@
Processing UtilisateursController#index (for 127.0.0.1 at 2007-11-06 16:55:22) [GET]
Session ID: ebdec02688b41592bff1775fab8da692
Parameters: {"action"=>"index", "controller"=>"utilisateurs"}
SQL (0.000391) SET NAMES 'utf8'
SQL (0.000354) SET SQL_AUTO_IS_NULL=0
Utilisateur Load (0.002877) SELECT * FROM utilisateurs 
Rendering layoutfalsecontent_typetext/htmlactionindex within layouts/utilisateurs
Rendering utilisateurs/index
ActionView::TemplateError (undefined method `nom' for #<Utilisateur:0xb72d2eec>) on line #19 of app/views/utilisateurs/index.rhtml:
16:
17: <% for utilisateur in @utilisateurs %>
18: <tr>
19: <td><%=h utilisateur.nom %></td>
20: <td><%=h utilisateur.prenom %></td>
21: <td><%=h utilisateur.classe %></td>
22: <td><%=h utilisateur.email %></td>
/usr/lib/ruby/gems/1.8/gems/activerecord-1.15.5/lib/active_record/base.rb:1863:in `method_missing'
/home/3dossmanno/P5b/ruby/3dossmanno_annuaire/app/views/utilisateurs/index.rhtml:19:in `_run_rhtml_47app47views47utilisateurs47index46rhtml'
/home/3dossmanno/P5b/ruby/3dossmanno_annuaire/app/views/utilisateurs/index.rhtml:17:in `each'
/home/3dossmanno/P5b/ruby/3dossmanno_annuaire/app/views/utilisateurs/index.rhtml:17:in `_run_rhtml_47app47views47utilisateurs47index46rhtml'
/usr/lib/ruby/gems/1.8/gems/actionpack-1.13.5/lib/action_view/base.rb:325:in `send'
/usr/lib/ruby/gems/1.8/gems/actionpack-1.13.5/lib/action_view/base.rb:325:in `compile_and_render_template'
/usr/lib/ruby/gems/1.8/gems/actionpack-1.13.5/lib/action_view/base.rb:301:in `render_template'
/usr/lib/ruby/gems/1.8/gems/actionpack-1.13.5/lib/action_view/base.rb:260:in `render_file'
/usr/lib/ruby/gems/1.8/gems/actionpack-1.13.5/lib/action_controller/base.rb:812:in `render_file'
/usr/lib/ruby/gems/1.8/gems/actionpack-1.13.5/lib/action_controller/base.rb:744:in `render_with_no_layout'
/usr/lib/ruby/gems/1.8/gems/actionpack-1.13.5/lib/action_controller/base.rb:869:in `render_without_layout'
/usr/lib/ruby/gems/1.8/gems/actionpack-1.13.5/lib/action_controller/base.rb:804:in `render_action'
/usr/lib/ruby/gems/1.8/gems/actionpack-1.13.5/lib/action_controller/base.rb:754:in `render_with_no_layout'
/usr/lib/ruby/gems/1.8/gems/activesupport-1.4.4/lib/active_support/deprecation.rb:44:in `silence'
/usr/lib/ruby/gems/1.8/gems/actionpack-1.13.5/lib/action_controller/base.rb:753:in `render_with_no_layout'
/usr/lib/ruby/gems/1.8/gems/actionpack-1.13.5/lib/action_controller/layout.rb:244:in `render_without_benchmark'
/usr/lib/ruby/gems/1.8/gems/actionpack-1.13.5/lib/action_controller/benchmarking.rb:50:in `render'
/usr/lib/ruby/1.8/benchmark.rb:293:in `measure'
/usr/lib/ruby/gems/1.8/gems/actionpack-1.13.5/lib/action_controller/benchmarking.rb:50:in `render'
/home/3dossmanno/P5b/ruby/3dossmanno_annuaire/app/controllers/utilisateurs_controller.rb:7:in `index'
/usr/lib/ruby/gems/1.8/gems/actionpack-1.13.5/lib/action_controller/mime_responds.rb:167:in `call'
/usr/lib/ruby/gems/1.8/gems/actionpack-1.13.5/lib/action_controller/mime_responds.rb:167:in `respond'
/usr/lib/ruby/gems/1.8/gems/actionpack-1.13.5/lib/action_controller/mime_responds.rb:161:in `each'
/usr/lib/ruby/gems/1.8/gems/actionpack-1.13.5/lib/action_controller/mime_responds.rb:161:in `respond'
/usr/lib/ruby/gems/1.8/gems/actionpack-1.13.5/lib/action_controller/mime_responds.rb:105:in `respond_to'
/home/3dossmanno/P5b/ruby/3dossmanno_annuaire/app/controllers/utilisateurs_controller.rb:7:in `index'
/usr/lib/ruby/gems/1.8/gems/actionpack-1.13.5/lib/action_controller/base.rb:1101:in `send'
/usr/lib/ruby/gems/1.8/gems/actionpack-1.13.5/lib/action_controller/base.rb:1101:in `perform_action_without_filters'
/usr/lib/ruby/gems/1.8/gems/actionpack-1.13.5/lib/action_controller/filters.rb:696:in `call_filters'
/usr/lib/ruby/gems/1.8/gems/actionpack-1.13.5/lib/action_controller/filters.rb:688:in `perform_action_without_benchmark'
/usr/lib/ruby/gems/1.8/gems/actionpack-1.13.5/lib/action_controller/benchmarking.rb:66:in `perform_action_without_rescue'
/usr/lib/ruby/1.8/benchmark.rb:293:in `measure'
/usr/lib/ruby/gems/1.8/gems/actionpack-1.13.5/lib/action_controller/benchmarking.rb:66:in `perform_action_without_rescue'
/usr/lib/ruby/gems/1.8/gems/actionpack-1.13.5/lib/action_controller/rescue.rb:83:in `perform_action'
/usr/lib/ruby/gems/1.8/gems/actionpack-1.13.5/lib/action_controller/base.rb:435:in `send'
/usr/lib/ruby/gems/1.8/gems/actionpack-1.13.5/lib/action_controller/base.rb:435:in `process_without_filters'
/usr/lib/ruby/gems/1.8/gems/actionpack-1.13.5/lib/action_controller/filters.rb:684:in `process_without_session_management_support'
/usr/lib/ruby/gems/1.8/gems/actionpack-1.13.5/lib/action_controller/session_management.rb:114:in `process'
/usr/lib/ruby/gems/1.8/gems/actionpack-1.13.5/lib/action_controller/base.rb:334:in `process'
/usr/lib/ruby/gems/1.8/gems/rails-1.2.5/lib/dispatcher.rb:41:in `dispatch'
/usr/lib/ruby/gems/1.8/gems/rails-1.2.5/lib/webrick_server.rb:113:in `handle_dispatch'
/usr/lib/ruby/gems/1.8/gems/rails-1.2.5/lib/webrick_server.rb:79:in `service'
/usr/lib/ruby/1.8/webrick/httpserver.rb:104:in `service'
/usr/lib/ruby/1.8/webrick/httpserver.rb:65:in `run'
/usr/lib/ruby/1.8/webrick/server.rb:173:in `start_thread'
/usr/lib/ruby/1.8/webrick/server.rb:162:in `start'
/usr/lib/ruby/1.8/webrick/server.rb:162:in `start_thread'
/usr/lib/ruby/1.8/webrick/server.rb:95:in `start'
/usr/lib/ruby/1.8/webrick/server.rb:92:in `each'
/usr/lib/ruby/1.8/webrick/server.rb:92:in `start'
/usr/lib/ruby/1.8/webrick/server.rb:23:in `start'
/usr/lib/ruby/1.8/webrick/server.rb:82:in `start'
/usr/lib/ruby/gems/1.8/gems/rails-1.2.5/lib/webrick_server.rb:63:in `dispatch'
/usr/lib/ruby/gems/1.8/gems/rails-1.2.5/lib/commands/servers/webrick.rb:59
/usr/local/lib/site_ruby/1.8/rubygems/custom_require.rb:27:in `gem_original_require'
/usr/local/lib/site_ruby/1.8/rubygems/custom_require.rb:27:in `require'
/usr/lib/ruby/gems/1.8/gems/activesupport-1.4.4/lib/active_support/dependencies.rb:495:in `require'
/usr/lib/ruby/gems/1.8/gems/activesupport-1.4.4/lib/active_support/dependencies.rb:342:in `new_constants_in'
/usr/lib/ruby/gems/1.8/gems/activesupport-1.4.4/lib/active_support/dependencies.rb:495:in `require'
/usr/lib/ruby/gems/1.8/gems/rails-1.2.5/lib/commands/server.rb:39
/usr/local/lib/site_ruby/1.8/rubygems/custom_require.rb:27:in `gem_original_require'
/usr/local/lib/site_ruby/1.8/rubygems/custom_require.rb:27:in `require'
script/server:3
Rendering /usr/lib/ruby/gems/1.8/gems/actionpack-1.13.5/lib/action_controller/templates/rescues/layout.rhtml (500 Internal Error)
SQL (0.000346) SET NAMES 'utf8'
SQL (0.000330) SET SQL_AUTO_IS_NULL=0
SQL (0.000000) Mysql::Error: #42S01Table 'schema_info' already exists: CREATE TABLE schema_info (version int(11))
SQL (0.000000) Mysql::Error: #42S01Table 'schema_info' already exists: CREATE TABLE schema_info (version int(11))
SQL (0.022462) SELECT version FROM schema_info
SQL (0.000648) SELECT * FROM schema_info
SQL (0.001260) SHOW TABLES
SQL (0.004494) SHOW FIELDS FROM addresses
SQL (0.002046) SHOW KEYS FROM addresses
SQL (0.002521) SHOW FIELDS FROM customers
SQL (0.002087) SHOW KEYS FROM customers
SQL (0.003737) SHOW FIELDS FROM products
SQL (0.002598) SHOW KEYS FROM products
SQL (0.003038) SHOW FIELDS FROM suppliers
SQL (0.001972) SHOW KEYS FROM suppliers
SQL (0.002987) SHOW FIELDS FROM utilisateurs0
SQL (0.001915) SHOW KEYS FROM utilisateurs0
SQL (0.000324) SET NAMES 'utf8'
SQL (0.000273) SET SQL_AUTO_IS_NULL=0
SQL (0.000000) Mysql::Error: #42S01Table 'schema_info' already exists: CREATE TABLE schema_info (version int(11))
SQL (0.000000) Mysql::Error: #42S01Table 'schema_info' already exists: CREATE TABLE schema_info (version int(11))
SQL (0.000576) SELECT version FROM schema_info
SQL (0.001038) SELECT * FROM schema_info
SQL (0.000964) SHOW TABLES
SQL (0.002343) SHOW FIELDS FROM addresses
SQL (0.002067) SHOW KEYS FROM addresses
SQL (0.002952) SHOW FIELDS FROM customers
SQL (0.002650) SHOW KEYS FROM customers
SQL (0.002664) SHOW FIELDS FROM products
SQL (0.002058) SHOW KEYS FROM products
SQL (0.002585) SHOW FIELDS FROM suppliers
SQL (0.002202) SHOW KEYS FROM suppliers
SQL (0.003190) SHOW FIELDS FROM utilisateurs0
SQL (0.002052) SHOW KEYS FROM utilisateurs0
SQL (0.000327) SET NAMES 'utf8'
SQL (0.000335) SET SQL_AUTO_IS_NULL=0
SQL (0.000000) Mysql::Error: #42S01Table 'schema_info' already exists: CREATE TABLE schema_info (version int(11))
SQL (0.000000) Mysql::Error: #42S01Table 'schema_info' already exists: CREATE TABLE schema_info (version int(11))
SQL (0.000615) SELECT version FROM schema_info
SQL (0.000554) SELECT * FROM schema_info
SQL (0.001139) SHOW TABLES
SQL (0.002539) SHOW FIELDS FROM addresses
SQL (0.001794) SHOW KEYS FROM addresses
SQL (0.002117) SHOW FIELDS FROM customers
SQL (0.002836) SHOW KEYS FROM customers
SQL (0.005304) SHOW FIELDS FROM products
SQL (0.001824) SHOW KEYS FROM products
SQL (0.003148) SHOW FIELDS FROM suppliers
SQL (0.001822) SHOW KEYS FROM suppliers
SQL (0.000324) SET NAMES 'utf8'
SQL (0.000316) SET SQL_AUTO_IS_NULL=0
SQL (0.000321) SET NAMES 'utf8'
SQL (0.000577) SET SQL_AUTO_IS_NULL=0
SQL (0.000000) Mysql::Error: #42S01Table 'schema_info' already exists: CREATE TABLE schema_info (version int(11))
SQL (0.000000) Mysql::Error: #42S01Table 'schema_info' already exists: CREATE TABLE schema_info (version int(11))
SQL (0.000590) SELECT version FROM schema_info
SQL (0.000495) SELECT * FROM schema_info
SQL (0.001012) SHOW TABLES
SQL (0.002332) SHOW FIELDS FROM addresses
SQL (0.002280) SHOW KEYS FROM addresses
SQL (0.002149) SHOW FIELDS FROM customers
SQL (0.001880) SHOW KEYS FROM customers
SQL (0.004202) SHOW FIELDS FROM products
SQL (0.001842) SHOW KEYS FROM products
SQL (0.003232) SHOW FIELDS FROM suppliers
SQL (0.002026) SHOW KEYS FROM suppliers
SQL (0.000344) SET NAMES 'utf8'
SQL (0.000322) SET SQL_AUTO_IS_NULL=0
SQL (0.000000) Mysql::Error: #42S01Table 'schema_info' already exists: CREATE TABLE schema_info (version int(11))
SQL (0.000000) Mysql::Error: #42S01Table 'schema_info' already exists: CREATE TABLE schema_info (version int(11))
SQL (0.000619) SELECT version FROM schema_info
SQL (0.000462) SELECT * FROM schema_info
SQL (0.001309) SHOW TABLES
SQL (0.007139) SHOW FIELDS FROM addresses
SQL (0.003189) SHOW KEYS FROM addresses
SQL (0.003171) SHOW FIELDS FROM customers
SQL (0.003555) SHOW KEYS FROM customers
SQL (0.003635) SHOW FIELDS FROM products
SQL (0.001912) SHOW KEYS FROM products
SQL (0.002762) SHOW FIELDS FROM suppliers
SQL (0.001890) SHOW KEYS FROM suppliers
SQL (0.000317) SET NAMES 'utf8'
SQL (0.000278) SET SQL_AUTO_IS_NULL=0
SQL (0.000683) SET NAMES 'utf8'
SQL (0.000319) SET SQL_AUTO_IS_NULL=0
SQL (0.000329) SET NAMES 'utf8'
SQL (0.000274) SET SQL_AUTO_IS_NULL=0
SQL (0.000324) SET NAMES 'utf8'
SQL (0.000282) SET SQL_AUTO_IS_NULL=0
SQL (0.000000) Mysql::Error: #42S01Table 'schema_info' already exists: CREATE TABLE schema_info (version int(11))
SQL (0.000000) Mysql::Error: #42S01Table 'schema_info' already exists: CREATE TABLE schema_info (version int(11))
SQL (0.000521) SELECT DATABASE() as db
SQL (0.012236) ALTER DATABASE 073dossmanno_dev CHARACTER SET utf8 COLLATE utf8_general_ci
SQL (0.000509) SELECT version FROM schema_info
SQL (0.000509) SELECT * FROM schema_info
SQL (0.000950) SHOW TABLES
SQL (0.003472) SHOW FIELDS FROM addresses
SQL (0.002259) SHOW KEYS FROM addresses
SQL (0.002701) SHOW FIELDS FROM customers
SQL (0.002017) SHOW KEYS FROM customers
SQL (0.002611) SHOW FIELDS FROM products
SQL (0.001984) SHOW KEYS FROM products
SQL (0.002393) SHOW FIELDS FROM suppliers
SQL (0.002449) SHOW KEYS FROM suppliers
SQL (0.000329) SET NAMES 'utf8'
SQL (0.000316) SET SQL_AUTO_IS_NULL=0
SQL (0.000000) Mysql::Error: #42S01Table 'schema_info' already exists: CREATE TABLE schema_info (version int(11))
SQL (0.000000) Mysql::Error: #42S01Table 'schema_info' already exists: CREATE TABLE schema_info (version int(11))
SQL (0.000779) SELECT DATABASE() as db
SQL (0.000577) ALTER DATABASE 073dossmanno_dev CHARACTER SET utf8 COLLATE utf8_general_ci
SQL (0.000632) SELECT version FROM schema_info
SQL (0.000588) SELECT * FROM schema_info
SQL (0.001240) SHOW TABLES
SQL (0.003601) SHOW FIELDS FROM addresses
SQL (0.001946) SHOW KEYS FROM addresses
SQL (0.002402) SHOW FIELDS FROM customers
SQL (0.001833) SHOW KEYS FROM customers
SQL (0.002700) SHOW FIELDS FROM products
SQL (0.001880) SHOW KEYS FROM products
SQL (0.002815) SHOW FIELDS FROM suppliers
SQL (0.001944) SHOW KEYS FROM suppliers
SQL (0.000322) SET NAMES 'utf8'
SQL (0.000276) SET SQL_AUTO_IS_NULL=0
SQL (0.000000) Mysql::Error: #42S01Table 'schema_info' already exists: CREATE TABLE schema_info (version int(11))
SQL (0.000446) SELECT version FROM schema_info
SQL (0.000403) SELECT version FROM schema_info
SQL (0.000000) Mysql::Error: #42S01Table 'schema_info' already exists: CREATE TABLE schema_info (version int(11))
SQL (0.000623) SELECT DATABASE() as db
SQL (0.000526) ALTER DATABASE 073dossmanno_dev CHARACTER SET utf8 COLLATE utf8_general_ci
SQL (0.000530) SELECT version FROM schema_info
Migrating to CreateUtilisateurs (1)
SQL (0.000000) Mysql::Error: #42S02Unknown table 'utilisateurs': DROP TABLE utilisateurs
SQL (0.000317) SET NAMES 'utf8'
SQL (0.000281) SET SQL_AUTO_IS_NULL=0
SQL (0.000000) Mysql::Error: #42S01Table 'schema_info' already exists: CREATE TABLE schema_info (version int(11))
SQL (0.000000) Mysql::Error: #42S01Table 'schema_info' already exists: CREATE TABLE schema_info (version int(11))
SQL (0.000722) SELECT DATABASE() as db
SQL (0.000765) ALTER DATABASE 073dossmanno_dev CHARACTER SET utf8 COLLATE utf8_general_ci
SQL (0.000464) SELECT version FROM schema_info
SQL (0.000457) SELECT * FROM schema_info
SQL (0.000916) SHOW TABLES
SQL (0.002459) SHOW FIELDS FROM addresses
SQL (0.001870) SHOW KEYS FROM addresses
SQL (0.002171) SHOW FIELDS FROM customers
SQL (0.001915) SHOW KEYS FROM customers
SQL (0.002727) SHOW FIELDS FROM products
SQL (0.001986) SHOW KEYS FROM products
SQL (0.004044) SHOW FIELDS FROM suppliers
SQL (0.002829) SHOW KEYS FROM suppliers
Processing UtilisateursController#index (for 127.0.0.1 at 2007-11-06 17:19:40) [GET]
Session ID: ebdec02688b41592bff1775fab8da692
Parameters: {"action"=>"index", "controller"=>"utilisateurs"}
Utilisateur Load (0.000000) Mysql::Error: #42S02Table '073dossmanno_dev.utilisateurs' doesn't exist: SELECT * FROM utilisateurs 
ActiveRecord::StatementInvalid (Mysql::Error: #42S02Table '073dossmanno_dev.utilisateurs' doesn't exist: SELECT * FROM utilisateurs ):
/usr/lib/ruby/gems/1.8/gems/activerecord-1.15.5/lib/active_record/connection_adapters/abstract_adapter.rb:128:in `log'
/usr/lib/ruby/gems/1.8/gems/activerecord-1.15.5/lib/active_record/connection_adapters/mysql_adapter.rb:243:in `execute'
/usr/lib/ruby/gems/1.8/gems/activerecord-1.15.5/lib/active_record/connection_adapters/mysql_adapter.rb:399:in `select'
/usr/lib/ruby/gems/1.8/gems/activerecord-1.15.5/lib/active_record/connection_adapters/abstract/database_statements.rb:7:in `select_all'
/usr/lib/ruby/gems/1.8/gems/activerecord-1.15.5/lib/active_record/base.rb:427:in `find_by_sql'
/usr/lib/ruby/gems/1.8/gems/activerecord-1.15.5/lib/active_record/base.rb:997:in `find_every'
/usr/lib/ruby/gems/1.8/gems/activerecord-1.15.5/lib/active_record/base.rb:418:in `find'
/home/3dossmanno/P5b/ruby/3dossmanno_annuaire/app/controllers/utilisateurs_controller.rb:5:in `index'
/usr/lib/ruby/gems/1.8/gems/actionpack-1.13.5/lib/action_controller/base.rb:1101:in `send'
/usr/lib/ruby/gems/1.8/gems/actionpack-1.13.5/lib/action_controller/base.rb:1101:in `perform_action_without_filters'
/usr/lib/ruby/gems/1.8/gems/actionpack-1.13.5/lib/action_controller/filters.rb:696:in `call_filters'
/usr/lib/ruby/gems/1.8/gems/actionpack-1.13.5/lib/action_controller/filters.rb:688:in `perform_action_without_benchmark'
/usr/lib/ruby/gems/1.8/gems/actionpack-1.13.5/lib/action_controller/benchmarking.rb:66:in `perform_action_without_rescue'
/usr/lib/ruby/1.8/benchmark.rb:293:in `measure'
/usr/lib/ruby/gems/1.8/gems/actionpack-1.13.5/lib/action_controller/benchmarking.rb:66:in `perform_action_without_rescue'
/usr/lib/ruby/gems/1.8/gems/actionpack-1.13.5/lib/action_controller/rescue.rb:83:in `perform_action'
/usr/lib/ruby/gems/1.8/gems/actionpack-1.13.5/lib/action_controller/base.rb:435:in `send'
/usr/lib/ruby/gems/1.8/gems/actionpack-1.13.5/lib/action_controller/base.rb:435:in `process_without_filters'
/usr/lib/ruby/gems/1.8/gems/actionpack-1.13.5/lib/action_controller/filters.rb:684:in `process_without_session_management_support'
/usr/lib/ruby/gems/1.8/gems/actionpack-1.13.5/lib/action_controller/session_management.rb:114:in `process'
/usr/lib/ruby/gems/1.8/gems/actionpack-1.13.5/lib/action_controller/base.rb:334:in `process'
/usr/lib/ruby/gems/1.8/gems/rails-1.2.5/lib/dispatcher.rb:41:in `dispatch'
/usr/lib/ruby/gems/1.8/gems/rails-1.2.5/lib/webrick_server.rb:113:in `handle_dispatch'
/usr/lib/ruby/gems/1.8/gems/rails-1.2.5/lib/webrick_server.rb:79:in `service'
/usr/lib/ruby/1.8/webrick/httpserver.rb:104:in `service'
/usr/lib/ruby/1.8/webrick/httpserver.rb:65:in `run'
/usr/lib/ruby/1.8/webrick/server.rb:173:in `start_thread'
/usr/lib/ruby/1.8/webrick/server.rb:162:in `start'
/usr/lib/ruby/1.8/webrick/server.rb:162:in `start_thread'
/usr/lib/ruby/1.8/webrick/server.rb:95:in `start'
/usr/lib/ruby/1.8/webrick/server.rb:92:in `each'
/usr/lib/ruby/1.8/webrick/server.rb:92:in `start'
/usr/lib/ruby/1.8/webrick/server.rb:23:in `start'
/usr/lib/ruby/1.8/webrick/server.rb:82:in `start'
/usr/lib/ruby/gems/1.8/gems/rails-1.2.5/lib/webrick_server.rb:63:in `dispatch'
/usr/lib/ruby/gems/1.8/gems/rails-1.2.5/lib/commands/servers/webrick.rb:59
/usr/local/lib/site_ruby/1.8/rubygems/custom_require.rb:27:in `gem_original_require'
/usr/local/lib/site_ruby/1.8/rubygems/custom_require.rb:27:in `require'
/usr/lib/ruby/gems/1.8/gems/activesupport-1.4.4/lib/active_support/dependencies.rb:495:in `require'
/usr/lib/ruby/gems/1.8/gems/activesupport-1.4.4/lib/active_support/dependencies.rb:342:in `new_constants_in'
/usr/lib/ruby/gems/1.8/gems/activesupport-1.4.4/lib/active_support/dependencies.rb:495:in `require'
/usr/lib/ruby/gems/1.8/gems/rails-1.2.5/lib/commands/server.rb:39
/usr/local/lib/site_ruby/1.8/rubygems/custom_require.rb:27:in `gem_original_require'
/usr/local/lib/site_ruby/1.8/rubygems/custom_require.rb:27:in `require'
./script/server:3
Rendering /usr/lib/ruby/gems/1.8/gems/actionpack-1.13.5/lib/action_controller/templates/rescues/layout.rhtml (500 Internal Error)
SQL (0.000319) SET NAMES 'utf8'
SQL (0.000279) SET SQL_AUTO_IS_NULL=0
SQL (0.000000) Mysql::Error: #42S01Table 'schema_info' already exists: CREATE TABLE schema_info (version int(11))
SQL (0.000000) Mysql::Error: #42S01Table 'schema_info' already exists: CREATE TABLE schema_info (version int(11))
SQL (0.000713) SELECT DATABASE() as db
SQL (0.000554) ALTER DATABASE 073dossmanno_dev CHARACTER SET utf8 COLLATE utf8_general_ci
SQL (0.000445) SELECT version FROM schema_info
SQL (0.000507) SELECT * FROM schema_info
SQL (0.001107) SHOW TABLES
SQL (0.002537) SHOW FIELDS FROM addresses
SQL (0.001859) SHOW KEYS FROM addresses
SQL (0.002061) SHOW FIELDS FROM customers
SQL (0.001905) SHOW KEYS FROM customers
SQL (0.003183) SHOW FIELDS FROM products
SQL (0.002289) SHOW KEYS FROM products
SQL (0.002503) SHOW FIELDS FROM suppliers
SQL (0.001893) SHOW KEYS FROM suppliers
SQL (0.000364) SET NAMES 'utf8'
SQL (0.001224) SET SQL_AUTO_IS_NULL=0
SQL (0.000000) Mysql::Error: #42S01Table 'schema_info' already exists: CREATE TABLE schema_info (version int(11))
SQL (0.000000) Mysql::Error: #42S01Table 'schema_info' already exists: CREATE TABLE schema_info (version int(11))
SQL (0.000591) SELECT DATABASE() as db
SQL (0.000540) ALTER DATABASE 073dossmanno_dev CHARACTER SET utf8 COLLATE utf8_general_ci
SQL (0.000439) SELECT version FROM schema_info
SQL (0.000649) SELECT * FROM schema_info
SQL (0.000913) SHOW TABLES
SQL (0.002435) SHOW FIELDS FROM addresses
SQL (0.002132) SHOW KEYS FROM addresses
SQL (0.002260) SHOW FIELDS FROM customers
SQL (0.001886) SHOW KEYS FROM customers
SQL (0.003226) SHOW FIELDS FROM products
SQL (0.002654) SHOW KEYS FROM products
SQL (0.003384) SHOW FIELDS FROM suppliers
SQL (0.001831) SHOW KEYS FROM suppliers
SQL (0.000451) SET NAMES 'utf8'
SQL (0.000278) SET SQL_AUTO_IS_NULL=0
SQL (0.000000) Mysql::Error: #42S01Table 'schema_info' already exists: CREATE TABLE schema_info (version int(11))
SQL (0.000000) Mysql::Error: #42S01Table 'schema_info' already exists: CREATE TABLE schema_info (version int(11))
SQL (0.000537) SELECT DATABASE() as db
SQL (0.001057) ALTER DATABASE 073dossmanno_dev CHARACTER SET utf8 COLLATE utf8_general_ci
SQL (0.000505) SELECT version FROM schema_info
SQL (0.000430) SELECT * FROM schema_info
SQL (0.000894) SHOW TABLES
SQL (0.002388) SHOW FIELDS FROM addresses
SQL (0.001876) SHOW KEYS FROM addresses
SQL (0.002298) SHOW FIELDS FROM customers
SQL (0.002201) SHOW KEYS FROM customers
SQL (0.004052) SHOW FIELDS FROM products
SQL (0.002114) SHOW KEYS FROM products
SQL (0.002437) SHOW FIELDS FROM suppliers
SQL (0.002394) SHOW KEYS FROM suppliers

View File

@ -0,0 +1,40 @@
# General Apache options
AddHandler fastcgi-script .fcgi
AddHandler cgi-script .cgi
Options +FollowSymLinks +ExecCGI
# If you don't want Rails to look in certain directories,
# use the following rewrite rules so that Apache won't rewrite certain requests
#
# Example:
# RewriteCond %{REQUEST_URI} ^/notrails.*
# RewriteRule .* - [L]
# Redirect all requests not available on the filesystem to Rails
# By default the cgi dispatcher is used which is very slow
#
# For better performance replace the dispatcher with the fastcgi one
#
# Example:
# RewriteRule ^(.*)$ dispatch.fcgi [QSA,L]
RewriteEngine On
# If your Rails application is accessed via an Alias directive,
# then you MUST also set the RewriteBase in this htaccess file.
#
# Example:
# Alias /myrailsapp /path/to/myrailsapp/public
# RewriteBase /myrailsapp
RewriteRule ^$ index.html [QSA]
RewriteRule ^([^.]+)$ $1.html [QSA]
RewriteCond %{REQUEST_FILENAME} !-f
RewriteRule ^(.*)$ dispatch.cgi [QSA,L]
# In case Rails experiences terminal errors
# Instead of displaying this message you can supply a file here which will be rendered instead
#
# Example:
# ErrorDocument 500 /500.html
ErrorDocument 500 "<h2>Application error</h2>Rails application failed to start properly"

View File

@ -0,0 +1,30 @@
<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN"
"http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd">
<html xmlns="http://www.w3.org/1999/xhtml" xml:lang="en" lang="en">
<head>
<meta http-equiv="content-type" content="text/html; charset=UTF-8" />
<title>The page you were looking for doesn't exist (404)</title>
<style type="text/css">
body { background-color: #fff; color: #666; text-align: center; font-family: arial, sans-serif; }
div.dialog {
width: 25em;
padding: 0 4em;
margin: 4em auto 0 auto;
border: 1px solid #ccc;
border-right-color: #999;
border-bottom-color: #999;
}
h1 { font-size: 100%; color: #f00; line-height: 1.5em; }
</style>
</head>
<body>
<!-- This file lives in public/404.html -->
<div class="dialog">
<h1>The page you were looking for doesn't exist.</h1>
<p>You may have mistyped the address or the page may have moved.</p>
</div>
</body>
</html>

View File

@ -0,0 +1,30 @@
<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN"
"http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd">
<html xmlns="http://www.w3.org/1999/xhtml" xml:lang="en" lang="en">
<head>
<meta http-equiv="content-type" content="text/html; charset=UTF-8" />
<title>We're sorry, but something went wrong</title>
<style type="text/css">
body { background-color: #fff; color: #666; text-align: center; font-family: arial, sans-serif; }
div.dialog {
width: 25em;
padding: 0 4em;
margin: 4em auto 0 auto;
border: 1px solid #ccc;
border-right-color: #999;
border-bottom-color: #999;
}
h1 { font-size: 100%; color: #f00; line-height: 1.5em; }
</style>
</head>
<body>
<!-- This file lives in public/500.html -->
<div class="dialog">
<h1>We're sorry, but something went wrong.</h1>
<p>We've been notified about this issue and we'll take a look at it shortly.</p>
</div>
</body>
</html>

View File

@ -0,0 +1,10 @@
#!/usr/bin/ruby1.8
require File.dirname(__FILE__) + "/../config/environment" unless defined?(RAILS_ROOT)
# If you're using RubyGems and mod_ruby, this require should be changed to an absolute path one, like:
# "/usr/local/lib/ruby/gems/1.8/gems/rails-0.8.0/lib/dispatcher" -- otherwise performance is severely impaired
require "dispatcher"
ADDITIONAL_LOAD_PATHS.reverse.each { |dir| $:.unshift(dir) if File.directory?(dir) } if defined?(Apache::RubyRun)
Dispatcher.dispatch

View File

@ -0,0 +1,24 @@
#!/usr/bin/ruby1.8
#
# You may specify the path to the FastCGI crash log (a log of unhandled
# exceptions which forced the FastCGI instance to exit, great for debugging)
# and the number of requests to process before running garbage collection.
#
# By default, the FastCGI crash log is RAILS_ROOT/log/fastcgi.crash.log
# and the GC period is nil (turned off). A reasonable number of requests
# could range from 10-100 depending on the memory footprint of your app.
#
# Example:
# # Default log path, normal GC behavior.
# RailsFCGIHandler.process!
#
# # Default log path, 50 requests between GC.
# RailsFCGIHandler.process! nil, 50
#
# # Custom log path, normal GC behavior.
# RailsFCGIHandler.process! '/var/log/myapp_fcgi_crash.log'
#
require File.dirname(__FILE__) + "/../config/environment"
require 'fcgi_handler'
RailsFCGIHandler.process!

View File

@ -0,0 +1,10 @@
#!/usr/bin/ruby1.8
require File.dirname(__FILE__) + "/../config/environment" unless defined?(RAILS_ROOT)
# If you're using RubyGems and mod_ruby, this require should be changed to an absolute path one, like:
# "/usr/local/lib/ruby/gems/1.8/gems/rails-0.8.0/lib/dispatcher" -- otherwise performance is severely impaired
require "dispatcher"
ADDITIONAL_LOAD_PATHS.reverse.each { |dir| $:.unshift(dir) if File.directory?(dir) } if defined?(Apache::RubyRun)
Dispatcher.dispatch

Binary file not shown.

After

Width:  |  Height:  |  Size: 1.7 KiB

View File

@ -0,0 +1,277 @@
<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN"
"http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd">
<html>
<head>
<meta http-equiv="Content-type" content="text/html; charset=utf-8" />
<title>Ruby on Rails: Welcome aboard</title>
<style type="text/css" media="screen">
body {
margin: 0;
margin-bottom: 25px;
padding: 0;
background-color: #f0f0f0;
font-family: "Lucida Grande", "Bitstream Vera Sans", "Verdana";
font-size: 13px;
color: #333;
}
h1 {
font-size: 28px;
color: #000;
}
a {color: #03c}
a:hover {
background-color: #03c;
color: white;
text-decoration: none;
}
#page {
background-color: #f0f0f0;
width: 750px;
margin: 0;
margin-left: auto;
margin-right: auto;
}
#content {
float: left;
background-color: white;
border: 3px solid #aaa;
border-top: none;
padding: 25px;
width: 500px;
}
#sidebar {
float: right;
width: 175px;
}
#footer {
clear: both;
}
#header, #about, #getting-started {
padding-left: 75px;
padding-right: 30px;
}
#header {
background-image: url("images/rails.png");
background-repeat: no-repeat;
background-position: top left;
height: 64px;
}
#header h1, #header h2 {margin: 0}
#header h2 {
color: #888;
font-weight: normal;
font-size: 16px;
}
#about h3 {
margin: 0;
margin-bottom: 10px;
font-size: 14px;
}
#about-content {
background-color: #ffd;
border: 1px solid #fc0;
margin-left: -11px;
}
#about-content table {
margin-top: 10px;
margin-bottom: 10px;
font-size: 11px;
border-collapse: collapse;
}
#about-content td {
padding: 10px;
padding-top: 3px;
padding-bottom: 3px;
}
#about-content td.name {color: #555}
#about-content td.value {color: #000}
#about-content.failure {
background-color: #fcc;
border: 1px solid #f00;
}
#about-content.failure p {
margin: 0;
padding: 10px;
}
#getting-started {
border-top: 1px solid #ccc;
margin-top: 25px;
padding-top: 15px;
}
#getting-started h1 {
margin: 0;
font-size: 20px;
}
#getting-started h2 {
margin: 0;
font-size: 14px;
font-weight: normal;
color: #333;
margin-bottom: 25px;
}
#getting-started ol {
margin-left: 0;
padding-left: 0;
}
#getting-started li {
font-size: 18px;
color: #888;
margin-bottom: 25px;
}
#getting-started li h2 {
margin: 0;
font-weight: normal;
font-size: 18px;
color: #333;
}
#getting-started li p {
color: #555;
font-size: 13px;
}
#search {
margin: 0;
padding-top: 10px;
padding-bottom: 10px;
font-size: 11px;
}
#search input {
font-size: 11px;
margin: 2px;
}
#search-text {width: 170px}
#sidebar ul {
margin-left: 0;
padding-left: 0;
}
#sidebar ul h3 {
margin-top: 25px;
font-size: 16px;
padding-bottom: 10px;
border-bottom: 1px solid #ccc;
}
#sidebar li {
list-style-type: none;
}
#sidebar ul.links li {
margin-bottom: 5px;
}
</style>
<script type="text/javascript" src="javascripts/prototype.js"></script>
<script type="text/javascript" src="javascripts/effects.js"></script>
<script type="text/javascript">
function about() {
if (Element.empty('about-content')) {
new Ajax.Updater('about-content', 'rails/info/properties', {
method: 'get',
onFailure: function() {Element.classNames('about-content').add('failure')},
onComplete: function() {new Effect.BlindDown('about-content', {duration: 0.25})}
});
} else {
new Effect[Element.visible('about-content') ?
'BlindUp' : 'BlindDown']('about-content', {duration: 0.25});
}
}
window.onload = function() {
$('search-text').value = '';
$('search').onsubmit = function() {
$('search-text').value = 'site:rubyonrails.org ' + $F('search-text');
}
}
</script>
</head>
<body>
<div id="page">
<div id="sidebar">
<ul id="sidebar-items">
<li>
<form id="search" action="http://www.google.com/search" method="get">
<input type="hidden" name="hl" value="en" />
<input type="text" id="search-text" name="q" value="site:rubyonrails.org " />
<input type="submit" value="Search" /> the Rails site
</form>
</li>
<li>
<h3>Join the community</h3>
<ul class="links">
<li><a href="http://www.rubyonrails.org/">Ruby on Rails</a></li>
<li><a href="http://weblog.rubyonrails.org/">Official weblog</a></li>
<li><a href="http://lists.rubyonrails.org/">Mailing lists</a></li>
<li><a href="http://wiki.rubyonrails.org/rails/pages/IRC">IRC channel</a></li>
<li><a href="http://wiki.rubyonrails.org/">Wiki</a></li>
<li><a href="http://dev.rubyonrails.org/">Bug tracker</a></li>
</ul>
</li>
<li>
<h3>Browse the documentation</h3>
<ul class="links">
<li><a href="http://api.rubyonrails.org/">Rails API</a></li>
<li><a href="http://stdlib.rubyonrails.org/">Ruby standard library</a></li>
<li><a href="http://corelib.rubyonrails.org/">Ruby core</a></li>
</ul>
</li>
</ul>
</div>
<div id="content">
<div id="header">
<h1>Welcome aboard</h1>
<h2>You&rsquo;re riding the Rails!</h2>
</div>
<div id="about">
<h3><a href="rails/info/properties" onclick="about(); return false">About your application&rsquo;s environment</a></h3>
<div id="about-content" style="display: none"></div>
</div>
<div id="getting-started">
<h1>Getting started</h1>
<h2>Here&rsquo;s how to get rolling:</h2>
<ol>
<li>
<h2>Create your databases and edit <tt>config/database.yml</tt></h2>
<p>Rails needs to know your login and password.</p>
</li>
<li>
<h2>Use <tt>script/generate</tt> to create your models and controllers</h2>
<p>To see all available options, run it without parameters.</p>
</li>
<li>
<h2>Set up a default route and remove or rename this file</h2>
<p>Routes are setup in config/routes.rb.</p>
</li>
</ol>
</div>
</div>
<div id="footer">&nbsp;</div>
</div>
</body>
</html>

View File

@ -0,0 +1,2 @@
// Place your application-specific JavaScript functions and classes here
// This file is automatically included by javascript_include_tag :defaults

View File

@ -0,0 +1,833 @@
// Copyright (c) 2005, 2006 Thomas Fuchs (http://script.aculo.us, http://mir.aculo.us)
// (c) 2005, 2006 Ivan Krstic (http://blogs.law.harvard.edu/ivan)
// (c) 2005, 2006 Jon Tirsen (http://www.tirsen.com)
// Contributors:
// Richard Livsey
// Rahul Bhargava
// Rob Wills
//
// script.aculo.us is freely distributable under the terms of an MIT-style license.
// For details, see the script.aculo.us web site: http://script.aculo.us/
// Autocompleter.Base handles all the autocompletion functionality
// that's independent of the data source for autocompletion. This
// includes drawing the autocompletion menu, observing keyboard
// and mouse events, and similar.
//
// Specific autocompleters need to provide, at the very least,
// a getUpdatedChoices function that will be invoked every time
// the text inside the monitored textbox changes. This method
// should get the text for which to provide autocompletion by
// invoking this.getToken(), NOT by directly accessing
// this.element.value. This is to allow incremental tokenized
// autocompletion. Specific auto-completion logic (AJAX, etc)
// belongs in getUpdatedChoices.
//
// Tokenized incremental autocompletion is enabled automatically
// when an autocompleter is instantiated with the 'tokens' option
// in the options parameter, e.g.:
// new Ajax.Autocompleter('id','upd', '/url/', { tokens: ',' });
// will incrementally autocomplete with a comma as the token.
// Additionally, ',' in the above example can be replaced with
// a token array, e.g. { tokens: [',', '\n'] } which
// enables autocompletion on multiple tokens. This is most
// useful when one of the tokens is \n (a newline), as it
// allows smart autocompletion after linebreaks.
if(typeof Effect == 'undefined')
throw("controls.js requires including script.aculo.us' effects.js library");
var Autocompleter = {}
Autocompleter.Base = function() {};
Autocompleter.Base.prototype = {
baseInitialize: function(element, update, options) {
this.element = $(element);
this.update = $(update);
this.hasFocus = false;
this.changed = false;
this.active = false;
this.index = 0;
this.entryCount = 0;
if(this.setOptions)
this.setOptions(options);
else
this.options = options || {};
this.options.paramName = this.options.paramName || this.element.name;
this.options.tokens = this.options.tokens || [];
this.options.frequency = this.options.frequency || 0.4;
this.options.minChars = this.options.minChars || 1;
this.options.onShow = this.options.onShow ||
function(element, update){
if(!update.style.position || update.style.position=='absolute') {
update.style.position = 'absolute';
Position.clone(element, update, {
setHeight: false,
offsetTop: element.offsetHeight
});
}
Effect.Appear(update,{duration:0.15});
};
this.options.onHide = this.options.onHide ||
function(element, update){ new Effect.Fade(update,{duration:0.15}) };
if(typeof(this.options.tokens) == 'string')
this.options.tokens = new Array(this.options.tokens);
this.observer = null;
this.element.setAttribute('autocomplete','off');
Element.hide(this.update);
Event.observe(this.element, "blur", this.onBlur.bindAsEventListener(this));
Event.observe(this.element, "keypress", this.onKeyPress.bindAsEventListener(this));
},
show: function() {
if(Element.getStyle(this.update, 'display')=='none') this.options.onShow(this.element, this.update);
if(!this.iefix &&
(navigator.appVersion.indexOf('MSIE')>0) &&
(navigator.userAgent.indexOf('Opera')<0) &&
(Element.getStyle(this.update, 'position')=='absolute')) {
new Insertion.After(this.update,
'<iframe id="' + this.update.id + '_iefix" '+
'style="display:none;position:absolute;filter:progid:DXImageTransform.Microsoft.Alpha(opacity=0);" ' +
'src="javascript:false;" frameborder="0" scrolling="no"></iframe>');
this.iefix = $(this.update.id+'_iefix');
}
if(this.iefix) setTimeout(this.fixIEOverlapping.bind(this), 50);
},
fixIEOverlapping: function() {
Position.clone(this.update, this.iefix, {setTop:(!this.update.style.height)});
this.iefix.style.zIndex = 1;
this.update.style.zIndex = 2;
Element.show(this.iefix);
},
hide: function() {
this.stopIndicator();
if(Element.getStyle(this.update, 'display')!='none') this.options.onHide(this.element, this.update);
if(this.iefix) Element.hide(this.iefix);
},
startIndicator: function() {
if(this.options.indicator) Element.show(this.options.indicator);
},
stopIndicator: function() {
if(this.options.indicator) Element.hide(this.options.indicator);
},
onKeyPress: function(event) {
if(this.active)
switch(event.keyCode) {
case Event.KEY_TAB:
case Event.KEY_RETURN:
this.selectEntry();
Event.stop(event);
case Event.KEY_ESC:
this.hide();
this.active = false;
Event.stop(event);
return;
case Event.KEY_LEFT:
case Event.KEY_RIGHT:
return;
case Event.KEY_UP:
this.markPrevious();
this.render();
if(navigator.appVersion.indexOf('AppleWebKit')>0) Event.stop(event);
return;
case Event.KEY_DOWN:
this.markNext();
this.render();
if(navigator.appVersion.indexOf('AppleWebKit')>0) Event.stop(event);
return;
}
else
if(event.keyCode==Event.KEY_TAB || event.keyCode==Event.KEY_RETURN ||
(navigator.appVersion.indexOf('AppleWebKit') > 0 && event.keyCode == 0)) return;
this.changed = true;
this.hasFocus = true;
if(this.observer) clearTimeout(this.observer);
this.observer =
setTimeout(this.onObserverEvent.bind(this), this.options.frequency*1000);
},
activate: function() {
this.changed = false;
this.hasFocus = true;
this.getUpdatedChoices();
},
onHover: function(event) {
var element = Event.findElement(event, 'LI');
if(this.index != element.autocompleteIndex)
{
this.index = element.autocompleteIndex;
this.render();
}
Event.stop(event);
},
onClick: function(event) {
var element = Event.findElement(event, 'LI');
this.index = element.autocompleteIndex;
this.selectEntry();
this.hide();
},
onBlur: function(event) {
// needed to make click events working
setTimeout(this.hide.bind(this), 250);
this.hasFocus = false;
this.active = false;
},
render: function() {
if(this.entryCount > 0) {
for (var i = 0; i < this.entryCount; i++)
this.index==i ?
Element.addClassName(this.getEntry(i),"selected") :
Element.removeClassName(this.getEntry(i),"selected");
if(this.hasFocus) {
this.show();
this.active = true;
}
} else {
this.active = false;
this.hide();
}
},
markPrevious: function() {
if(this.index > 0) this.index--
else this.index = this.entryCount-1;
this.getEntry(this.index).scrollIntoView(true);
},
markNext: function() {
if(this.index < this.entryCount-1) this.index++
else this.index = 0;
this.getEntry(this.index).scrollIntoView(false);
},
getEntry: function(index) {
return this.update.firstChild.childNodes[index];
},
getCurrentEntry: function() {
return this.getEntry(this.index);
},
selectEntry: function() {
this.active = false;
this.updateElement(this.getCurrentEntry());
},
updateElement: function(selectedElement) {
if (this.options.updateElement) {
this.options.updateElement(selectedElement);
return;
}
var value = '';
if (this.options.select) {
var nodes = document.getElementsByClassName(this.options.select, selectedElement) || [];
if(nodes.length>0) value = Element.collectTextNodes(nodes[0], this.options.select);
} else
value = Element.collectTextNodesIgnoreClass(selectedElement, 'informal');
var lastTokenPos = this.findLastToken();
if (lastTokenPos != -1) {
var newValue = this.element.value.substr(0, lastTokenPos + 1);
var whitespace = this.element.value.substr(lastTokenPos + 1).match(/^\s+/);
if (whitespace)
newValue += whitespace[0];
this.element.value = newValue + value;
} else {
this.element.value = value;
}
this.element.focus();
if (this.options.afterUpdateElement)
this.options.afterUpdateElement(this.element, selectedElement);
},
updateChoices: function(choices) {
if(!this.changed && this.hasFocus) {
this.update.innerHTML = choices;
Element.cleanWhitespace(this.update);
Element.cleanWhitespace(this.update.down());
if(this.update.firstChild && this.update.down().childNodes) {
this.entryCount =
this.update.down().childNodes.length;
for (var i = 0; i < this.entryCount; i++) {
var entry = this.getEntry(i);
entry.autocompleteIndex = i;
this.addObservers(entry);
}
} else {
this.entryCount = 0;
}
this.stopIndicator();
this.index = 0;
if(this.entryCount==1 && this.options.autoSelect) {
this.selectEntry();
this.hide();
} else {
this.render();
}
}
},
addObservers: function(element) {
Event.observe(element, "mouseover", this.onHover.bindAsEventListener(this));
Event.observe(element, "click", this.onClick.bindAsEventListener(this));
},
onObserverEvent: function() {
this.changed = false;
if(this.getToken().length>=this.options.minChars) {
this.startIndicator();
this.getUpdatedChoices();
} else {
this.active = false;
this.hide();
}
},
getToken: function() {
var tokenPos = this.findLastToken();
if (tokenPos != -1)
var ret = this.element.value.substr(tokenPos + 1).replace(/^\s+/,'').replace(/\s+$/,'');
else
var ret = this.element.value;
return /\n/.test(ret) ? '' : ret;
},
findLastToken: function() {
var lastTokenPos = -1;
for (var i=0; i<this.options.tokens.length; i++) {
var thisTokenPos = this.element.value.lastIndexOf(this.options.tokens[i]);
if (thisTokenPos > lastTokenPos)
lastTokenPos = thisTokenPos;
}
return lastTokenPos;
}
}
Ajax.Autocompleter = Class.create();
Object.extend(Object.extend(Ajax.Autocompleter.prototype, Autocompleter.Base.prototype), {
initialize: function(element, update, url, options) {
this.baseInitialize(element, update, options);
this.options.asynchronous = true;
this.options.onComplete = this.onComplete.bind(this);
this.options.defaultParams = this.options.parameters || null;
this.url = url;
},
getUpdatedChoices: function() {
entry = encodeURIComponent(this.options.paramName) + '=' +
encodeURIComponent(this.getToken());
this.options.parameters = this.options.callback ?
this.options.callback(this.element, entry) : entry;
if(this.options.defaultParams)
this.options.parameters += '&' + this.options.defaultParams;
new Ajax.Request(this.url, this.options);
},
onComplete: function(request) {
this.updateChoices(request.responseText);
}
});
// The local array autocompleter. Used when you'd prefer to
// inject an array of autocompletion options into the page, rather
// than sending out Ajax queries, which can be quite slow sometimes.
//
// The constructor takes four parameters. The first two are, as usual,
// the id of the monitored textbox, and id of the autocompletion menu.
// The third is the array you want to autocomplete from, and the fourth
// is the options block.
//
// Extra local autocompletion options:
// - choices - How many autocompletion choices to offer
//
// - partialSearch - If false, the autocompleter will match entered
// text only at the beginning of strings in the
// autocomplete array. Defaults to true, which will
// match text at the beginning of any *word* in the
// strings in the autocomplete array. If you want to
// search anywhere in the string, additionally set
// the option fullSearch to true (default: off).
//
// - fullSsearch - Search anywhere in autocomplete array strings.
//
// - partialChars - How many characters to enter before triggering
// a partial match (unlike minChars, which defines
// how many characters are required to do any match
// at all). Defaults to 2.
//
// - ignoreCase - Whether to ignore case when autocompleting.
// Defaults to true.
//
// It's possible to pass in a custom function as the 'selector'
// option, if you prefer to write your own autocompletion logic.
// In that case, the other options above will not apply unless
// you support them.
Autocompleter.Local = Class.create();
Autocompleter.Local.prototype = Object.extend(new Autocompleter.Base(), {
initialize: function(element, update, array, options) {
this.baseInitialize(element, update, options);
this.options.array = array;
},
getUpdatedChoices: function() {
this.updateChoices(this.options.selector(this));
},
setOptions: function(options) {
this.options = Object.extend({
choices: 10,
partialSearch: true,
partialChars: 2,
ignoreCase: true,
fullSearch: false,
selector: function(instance) {
var ret = []; // Beginning matches
var partial = []; // Inside matches
var entry = instance.getToken();
var count = 0;
for (var i = 0; i < instance.options.array.length &&
ret.length < instance.options.choices ; i++) {
var elem = instance.options.array[i];
var foundPos = instance.options.ignoreCase ?
elem.toLowerCase().indexOf(entry.toLowerCase()) :
elem.indexOf(entry);
while (foundPos != -1) {
if (foundPos == 0 && elem.length != entry.length) {
ret.push("<li><strong>" + elem.substr(0, entry.length) + "</strong>" +
elem.substr(entry.length) + "</li>");
break;
} else if (entry.length >= instance.options.partialChars &&
instance.options.partialSearch && foundPos != -1) {
if (instance.options.fullSearch || /\s/.test(elem.substr(foundPos-1,1))) {
partial.push("<li>" + elem.substr(0, foundPos) + "<strong>" +
elem.substr(foundPos, entry.length) + "</strong>" + elem.substr(
foundPos + entry.length) + "</li>");
break;
}
}
foundPos = instance.options.ignoreCase ?
elem.toLowerCase().indexOf(entry.toLowerCase(), foundPos + 1) :
elem.indexOf(entry, foundPos + 1);
}
}
if (partial.length)
ret = ret.concat(partial.slice(0, instance.options.choices - ret.length))
return "<ul>" + ret.join('') + "</ul>";
}
}, options || {});
}
});
// AJAX in-place editor
//
// see documentation on http://wiki.script.aculo.us/scriptaculous/show/Ajax.InPlaceEditor
// Use this if you notice weird scrolling problems on some browsers,
// the DOM might be a bit confused when this gets called so do this
// waits 1 ms (with setTimeout) until it does the activation
Field.scrollFreeActivate = function(field) {
setTimeout(function() {
Field.activate(field);
}, 1);
}
Ajax.InPlaceEditor = Class.create();
Ajax.InPlaceEditor.defaultHighlightColor = "#FFFF99";
Ajax.InPlaceEditor.prototype = {
initialize: function(element, url, options) {
this.url = url;
this.element = $(element);
this.options = Object.extend({
paramName: "value",
okButton: true,
okText: "ok",
cancelLink: true,
cancelText: "cancel",
savingText: "Saving...",
clickToEditText: "Click to edit",
okText: "ok",
rows: 1,
onComplete: function(transport, element) {
new Effect.Highlight(element, {startcolor: this.options.highlightcolor});
},
onFailure: function(transport) {
alert("Error communicating with the server: " + transport.responseText.stripTags());
},
callback: function(form) {
return Form.serialize(form);
},
handleLineBreaks: true,
loadingText: 'Loading...',
savingClassName: 'inplaceeditor-saving',
loadingClassName: 'inplaceeditor-loading',
formClassName: 'inplaceeditor-form',
highlightcolor: Ajax.InPlaceEditor.defaultHighlightColor,
highlightendcolor: "#FFFFFF",
externalControl: null,
submitOnBlur: false,
ajaxOptions: {},
evalScripts: false
}, options || {});
if(!this.options.formId && this.element.id) {
this.options.formId = this.element.id + "-inplaceeditor";
if ($(this.options.formId)) {
// there's already a form with that name, don't specify an id
this.options.formId = null;
}
}
if (this.options.externalControl) {
this.options.externalControl = $(this.options.externalControl);
}
this.originalBackground = Element.getStyle(this.element, 'background-color');
if (!this.originalBackground) {
this.originalBackground = "transparent";
}
this.element.title = this.options.clickToEditText;
this.onclickListener = this.enterEditMode.bindAsEventListener(this);
this.mouseoverListener = this.enterHover.bindAsEventListener(this);
this.mouseoutListener = this.leaveHover.bindAsEventListener(this);
Event.observe(this.element, 'click', this.onclickListener);
Event.observe(this.element, 'mouseover', this.mouseoverListener);
Event.observe(this.element, 'mouseout', this.mouseoutListener);
if (this.options.externalControl) {
Event.observe(this.options.externalControl, 'click', this.onclickListener);
Event.observe(this.options.externalControl, 'mouseover', this.mouseoverListener);
Event.observe(this.options.externalControl, 'mouseout', this.mouseoutListener);
}
},
enterEditMode: function(evt) {
if (this.saving) return;
if (this.editing) return;
this.editing = true;
this.onEnterEditMode();
if (this.options.externalControl) {
Element.hide(this.options.externalControl);
}
Element.hide(this.element);
this.createForm();
this.element.parentNode.insertBefore(this.form, this.element);
if (!this.options.loadTextURL) Field.scrollFreeActivate(this.editField);
// stop the event to avoid a page refresh in Safari
if (evt) {
Event.stop(evt);
}
return false;
},
createForm: function() {
this.form = document.createElement("form");
this.form.id = this.options.formId;
Element.addClassName(this.form, this.options.formClassName)
this.form.onsubmit = this.onSubmit.bind(this);
this.createEditField();
if (this.options.textarea) {
var br = document.createElement("br");
this.form.appendChild(br);
}
if (this.options.okButton) {
okButton = document.createElement("input");
okButton.type = "submit";
okButton.value = this.options.okText;
okButton.className = 'editor_ok_button';
this.form.appendChild(okButton);
}
if (this.options.cancelLink) {
cancelLink = document.createElement("a");
cancelLink.href = "#";
cancelLink.appendChild(document.createTextNode(this.options.cancelText));
cancelLink.onclick = this.onclickCancel.bind(this);
cancelLink.className = 'editor_cancel';
this.form.appendChild(cancelLink);
}
},
hasHTMLLineBreaks: function(string) {
if (!this.options.handleLineBreaks) return false;
return string.match(/<br/i) || string.match(/<p>/i);
},
convertHTMLLineBreaks: function(string) {
return string.replace(/<br>/gi, "\n").replace(/<br\/>/gi, "\n").replace(/<\/p>/gi, "\n").replace(/<p>/gi, "");
},
createEditField: function() {
var text;
if(this.options.loadTextURL) {
text = this.options.loadingText;
} else {
text = this.getText();
}
var obj = this;
if (this.options.rows == 1 && !this.hasHTMLLineBreaks(text)) {
this.options.textarea = false;
var textField = document.createElement("input");
textField.obj = this;
textField.type = "text";
textField.name = this.options.paramName;
textField.value = text;
textField.style.backgroundColor = this.options.highlightcolor;
textField.className = 'editor_field';
var size = this.options.size || this.options.cols || 0;
if (size != 0) textField.size = size;
if (this.options.submitOnBlur)
textField.onblur = this.onSubmit.bind(this);
this.editField = textField;
} else {
this.options.textarea = true;
var textArea = document.createElement("textarea");
textArea.obj = this;
textArea.name = this.options.paramName;
textArea.value = this.convertHTMLLineBreaks(text);
textArea.rows = this.options.rows;
textArea.cols = this.options.cols || 40;
textArea.className = 'editor_field';
if (this.options.submitOnBlur)
textArea.onblur = this.onSubmit.bind(this);
this.editField = textArea;
}
if(this.options.loadTextURL) {
this.loadExternalText();
}
this.form.appendChild(this.editField);
},
getText: function() {
return this.element.innerHTML;
},
loadExternalText: function() {
Element.addClassName(this.form, this.options.loadingClassName);
this.editField.disabled = true;
new Ajax.Request(
this.options.loadTextURL,
Object.extend({
asynchronous: true,
onComplete: this.onLoadedExternalText.bind(this)
}, this.options.ajaxOptions)
);
},
onLoadedExternalText: function(transport) {
Element.removeClassName(this.form, this.options.loadingClassName);
this.editField.disabled = false;
this.editField.value = transport.responseText.stripTags();
Field.scrollFreeActivate(this.editField);
},
onclickCancel: function() {
this.onComplete();
this.leaveEditMode();
return false;
},
onFailure: function(transport) {
this.options.onFailure(transport);
if (this.oldInnerHTML) {
this.element.innerHTML = this.oldInnerHTML;
this.oldInnerHTML = null;
}
return false;
},
onSubmit: function() {
// onLoading resets these so we need to save them away for the Ajax call
var form = this.form;
var value = this.editField.value;
// do this first, sometimes the ajax call returns before we get a chance to switch on Saving...
// which means this will actually switch on Saving... *after* we've left edit mode causing Saving...
// to be displayed indefinitely
this.onLoading();
if (this.options.evalScripts) {
new Ajax.Request(
this.url, Object.extend({
parameters: this.options.callback(form, value),
onComplete: this.onComplete.bind(this),
onFailure: this.onFailure.bind(this),
asynchronous:true,
evalScripts:true
}, this.options.ajaxOptions));
} else {
new Ajax.Updater(
{ success: this.element,
// don't update on failure (this could be an option)
failure: null },
this.url, Object.extend({
parameters: this.options.callback(form, value),
onComplete: this.onComplete.bind(this),
onFailure: this.onFailure.bind(this)
}, this.options.ajaxOptions));
}
// stop the event to avoid a page refresh in Safari
if (arguments.length > 1) {
Event.stop(arguments[0]);
}
return false;
},
onLoading: function() {
this.saving = true;
this.removeForm();
this.leaveHover();
this.showSaving();
},
showSaving: function() {
this.oldInnerHTML = this.element.innerHTML;
this.element.innerHTML = this.options.savingText;
Element.addClassName(this.element, this.options.savingClassName);
this.element.style.backgroundColor = this.originalBackground;
Element.show(this.element);
},
removeForm: function() {
if(this.form) {
if (this.form.parentNode) Element.remove(this.form);
this.form = null;
}
},
enterHover: function() {
if (this.saving) return;
this.element.style.backgroundColor = this.options.highlightcolor;
if (this.effect) {
this.effect.cancel();
}
Element.addClassName(this.element, this.options.hoverClassName)
},
leaveHover: function() {
if (this.options.backgroundColor) {
this.element.style.backgroundColor = this.oldBackground;
}
Element.removeClassName(this.element, this.options.hoverClassName)
if (this.saving) return;
this.effect = new Effect.Highlight(this.element, {
startcolor: this.options.highlightcolor,
endcolor: this.options.highlightendcolor,
restorecolor: this.originalBackground
});
},
leaveEditMode: function() {
Element.removeClassName(this.element, this.options.savingClassName);
this.removeForm();
this.leaveHover();
this.element.style.backgroundColor = this.originalBackground;
Element.show(this.element);
if (this.options.externalControl) {
Element.show(this.options.externalControl);
}
this.editing = false;
this.saving = false;
this.oldInnerHTML = null;
this.onLeaveEditMode();
},
onComplete: function(transport) {
this.leaveEditMode();
this.options.onComplete.bind(this)(transport, this.element);
},
onEnterEditMode: function() {},
onLeaveEditMode: function() {},
dispose: function() {
if (this.oldInnerHTML) {
this.element.innerHTML = this.oldInnerHTML;
}
this.leaveEditMode();
Event.stopObserving(this.element, 'click', this.onclickListener);
Event.stopObserving(this.element, 'mouseover', this.mouseoverListener);
Event.stopObserving(this.element, 'mouseout', this.mouseoutListener);
if (this.options.externalControl) {
Event.stopObserving(this.options.externalControl, 'click', this.onclickListener);
Event.stopObserving(this.options.externalControl, 'mouseover', this.mouseoverListener);
Event.stopObserving(this.options.externalControl, 'mouseout', this.mouseoutListener);
}
}
};
Ajax.InPlaceCollectionEditor = Class.create();
Object.extend(Ajax.InPlaceCollectionEditor.prototype, Ajax.InPlaceEditor.prototype);
Object.extend(Ajax.InPlaceCollectionEditor.prototype, {
createEditField: function() {
if (!this.cached_selectTag) {
var selectTag = document.createElement("select");
var collection = this.options.collection || [];
var optionTag;
collection.each(function(e,i) {
optionTag = document.createElement("option");
optionTag.value = (e instanceof Array) ? e[0] : e;
if((typeof this.options.value == 'undefined') &&
((e instanceof Array) ? this.element.innerHTML == e[1] : e == optionTag.value)) optionTag.selected = true;
if(this.options.value==optionTag.value) optionTag.selected = true;
optionTag.appendChild(document.createTextNode((e instanceof Array) ? e[1] : e));
selectTag.appendChild(optionTag);
}.bind(this));
this.cached_selectTag = selectTag;
}
this.editField = this.cached_selectTag;
if(this.options.loadTextURL) this.loadExternalText();
this.form.appendChild(this.editField);
this.options.callback = function(form, value) {
return "value=" + encodeURIComponent(value);
}
}
});
// Delayed observer, like Form.Element.Observer,
// but waits for delay after last key input
// Ideal for live-search fields
Form.Element.DelayedObserver = Class.create();
Form.Element.DelayedObserver.prototype = {
initialize: function(element, delay, callback) {
this.delay = delay || 0.5;
this.element = $(element);
this.callback = callback;
this.timer = null;
this.lastValue = $F(this.element);
Event.observe(this.element,'keyup',this.delayedListener.bindAsEventListener(this));
},
delayedListener: function(event) {
if(this.lastValue == $F(this.element)) return;
if(this.timer) clearTimeout(this.timer);
this.timer = setTimeout(this.onTimerEvent.bind(this), this.delay * 1000);
this.lastValue = $F(this.element);
},
onTimerEvent: function() {
this.timer = null;
this.callback(this.element, $F(this.element));
}
};

View File

@ -0,0 +1,942 @@
// Copyright (c) 2005, 2006 Thomas Fuchs (http://script.aculo.us, http://mir.aculo.us)
// (c) 2005, 2006 Sammi Williams (http://www.oriontransfer.co.nz, sammi@oriontransfer.co.nz)
//
// script.aculo.us is freely distributable under the terms of an MIT-style license.
// For details, see the script.aculo.us web site: http://script.aculo.us/
if(typeof Effect == 'undefined')
throw("dragdrop.js requires including script.aculo.us' effects.js library");
var Droppables = {
drops: [],
remove: function(element) {
this.drops = this.drops.reject(function(d) { return d.element==$(element) });
},
add: function(element) {
element = $(element);
var options = Object.extend({
greedy: true,
hoverclass: null,
tree: false
}, arguments[1] || {});
// cache containers
if(options.containment) {
options._containers = [];
var containment = options.containment;
if((typeof containment == 'object') &&
(containment.constructor == Array)) {
containment.each( function(c) { options._containers.push($(c)) });
} else {
options._containers.push($(containment));
}
}
if(options.accept) options.accept = [options.accept].flatten();
Element.makePositioned(element); // fix IE
options.element = element;
this.drops.push(options);
},
findDeepestChild: function(drops) {
deepest = drops[0];
for (i = 1; i < drops.length; ++i)
if (Element.isParent(drops[i].element, deepest.element))
deepest = drops[i];
return deepest;
},
isContained: function(element, drop) {
var containmentNode;
if(drop.tree) {
containmentNode = element.treeNode;
} else {
containmentNode = element.parentNode;
}
return drop._containers.detect(function(c) { return containmentNode == c });
},
isAffected: function(point, element, drop) {
return (
(drop.element!=element) &&
((!drop._containers) ||
this.isContained(element, drop)) &&
((!drop.accept) ||
(Element.classNames(element).detect(
function(v) { return drop.accept.include(v) } ) )) &&
Position.within(drop.element, point[0], point[1]) );
},
deactivate: function(drop) {
if(drop.hoverclass)
Element.removeClassName(drop.element, drop.hoverclass);
this.last_active = null;
},
activate: function(drop) {
if(drop.hoverclass)
Element.addClassName(drop.element, drop.hoverclass);
this.last_active = drop;
},
show: function(point, element) {
if(!this.drops.length) return;
var affected = [];
if(this.last_active) this.deactivate(this.last_active);
this.drops.each( function(drop) {
if(Droppables.isAffected(point, element, drop))
affected.push(drop);
});
if(affected.length>0) {
drop = Droppables.findDeepestChild(affected);
Position.within(drop.element, point[0], point[1]);
if(drop.onHover)
drop.onHover(element, drop.element, Position.overlap(drop.overlap, drop.element));
Droppables.activate(drop);
}
},
fire: function(event, element) {
if(!this.last_active) return;
Position.prepare();
if (this.isAffected([Event.pointerX(event), Event.pointerY(event)], element, this.last_active))
if (this.last_active.onDrop)
this.last_active.onDrop(element, this.last_active.element, event);
},
reset: function() {
if(this.last_active)
this.deactivate(this.last_active);
}
}
var Draggables = {
drags: [],
observers: [],
register: function(draggable) {
if(this.drags.length == 0) {
this.eventMouseUp = this.endDrag.bindAsEventListener(this);
this.eventMouseMove = this.updateDrag.bindAsEventListener(this);
this.eventKeypress = this.keyPress.bindAsEventListener(this);
Event.observe(document, "mouseup", this.eventMouseUp);
Event.observe(document, "mousemove", this.eventMouseMove);
Event.observe(document, "keypress", this.eventKeypress);
}
this.drags.push(draggable);
},
unregister: function(draggable) {
this.drags = this.drags.reject(function(d) { return d==draggable });
if(this.drags.length == 0) {
Event.stopObserving(document, "mouseup", this.eventMouseUp);
Event.stopObserving(document, "mousemove", this.eventMouseMove);
Event.stopObserving(document, "keypress", this.eventKeypress);
}
},
activate: function(draggable) {
if(draggable.options.delay) {
this._timeout = setTimeout(function() {
Draggables._timeout = null;
window.focus();
Draggables.activeDraggable = draggable;
}.bind(this), draggable.options.delay);
} else {
window.focus(); // allows keypress events if window isn't currently focused, fails for Safari
this.activeDraggable = draggable;
}
},
deactivate: function() {
this.activeDraggable = null;
},
updateDrag: function(event) {
if(!this.activeDraggable) return;
var pointer = [Event.pointerX(event), Event.pointerY(event)];
// Mozilla-based browsers fire successive mousemove events with
// the same coordinates, prevent needless redrawing (moz bug?)
if(this._lastPointer && (this._lastPointer.inspect() == pointer.inspect())) return;
this._lastPointer = pointer;
this.activeDraggable.updateDrag(event, pointer);
},
endDrag: function(event) {
if(this._timeout) {
clearTimeout(this._timeout);
this._timeout = null;
}
if(!this.activeDraggable) return;
this._lastPointer = null;
this.activeDraggable.endDrag(event);
this.activeDraggable = null;
},
keyPress: function(event) {
if(this.activeDraggable)
this.activeDraggable.keyPress(event);
},
addObserver: function(observer) {
this.observers.push(observer);
this._cacheObserverCallbacks();
},
removeObserver: function(element) { // element instead of observer fixes mem leaks
this.observers = this.observers.reject( function(o) { return o.element==element });
this._cacheObserverCallbacks();
},
notify: function(eventName, draggable, event) { // 'onStart', 'onEnd', 'onDrag'
if(this[eventName+'Count'] > 0)
this.observers.each( function(o) {
if(o[eventName]) o[eventName](eventName, draggable, event);
});
if(draggable.options[eventName]) draggable.options[eventName](draggable, event);
},
_cacheObserverCallbacks: function() {
['onStart','onEnd','onDrag'].each( function(eventName) {
Draggables[eventName+'Count'] = Draggables.observers.select(
function(o) { return o[eventName]; }
).length;
});
}
}
/*--------------------------------------------------------------------------*/
var Draggable = Class.create();
Draggable._dragging = {};
Draggable.prototype = {
initialize: function(element) {
var defaults = {
handle: false,
reverteffect: function(element, top_offset, left_offset) {
var dur = Math.sqrt(Math.abs(top_offset^2)+Math.abs(left_offset^2))*0.02;
new Effect.Move(element, { x: -left_offset, y: -top_offset, duration: dur,
queue: {scope:'_draggable', position:'end'}
});
},
endeffect: function(element) {
var toOpacity = typeof element._opacity == 'number' ? element._opacity : 1.0;
new Effect.Opacity(element, {duration:0.2, from:0.7, to:toOpacity,
queue: {scope:'_draggable', position:'end'},
afterFinish: function(){
Draggable._dragging[element] = false
}
});
},
zindex: 1000,
revert: false,
scroll: false,
scrollSensitivity: 20,
scrollSpeed: 15,
snap: false, // false, or xy or [x,y] or function(x,y){ return [x,y] }
delay: 0
};
if(!arguments[1] || typeof arguments[1].endeffect == 'undefined')
Object.extend(defaults, {
starteffect: function(element) {
element._opacity = Element.getOpacity(element);
Draggable._dragging[element] = true;
new Effect.Opacity(element, {duration:0.2, from:element._opacity, to:0.7});
}
});
var options = Object.extend(defaults, arguments[1] || {});
this.element = $(element);
if(options.handle && (typeof options.handle == 'string'))
this.handle = this.element.down('.'+options.handle, 0);
if(!this.handle) this.handle = $(options.handle);
if(!this.handle) this.handle = this.element;
if(options.scroll && !options.scroll.scrollTo && !options.scroll.outerHTML) {
options.scroll = $(options.scroll);
this._isScrollChild = Element.childOf(this.element, options.scroll);
}
Element.makePositioned(this.element); // fix IE
this.delta = this.currentDelta();
this.options = options;
this.dragging = false;
this.eventMouseDown = this.initDrag.bindAsEventListener(this);
Event.observe(this.handle, "mousedown", this.eventMouseDown);
Draggables.register(this);
},
destroy: function() {
Event.stopObserving(this.handle, "mousedown", this.eventMouseDown);
Draggables.unregister(this);
},
currentDelta: function() {
return([
parseInt(Element.getStyle(this.element,'left') || '0'),
parseInt(Element.getStyle(this.element,'top') || '0')]);
},
initDrag: function(event) {
if(typeof Draggable._dragging[this.element] != 'undefined' &&
Draggable._dragging[this.element]) return;
if(Event.isLeftClick(event)) {
// abort on form elements, fixes a Firefox issue
var src = Event.element(event);
if(src.tagName && (
src.tagName=='INPUT' ||
src.tagName=='SELECT' ||
src.tagName=='OPTION' ||
src.tagName=='BUTTON' ||
src.tagName=='TEXTAREA')) return;
var pointer = [Event.pointerX(event), Event.pointerY(event)];
var pos = Position.cumulativeOffset(this.element);
this.offset = [0,1].map( function(i) { return (pointer[i] - pos[i]) });
Draggables.activate(this);
Event.stop(event);
}
},
startDrag: function(event) {
this.dragging = true;
if(this.options.zindex) {
this.originalZ = parseInt(Element.getStyle(this.element,'z-index') || 0);
this.element.style.zIndex = this.options.zindex;
}
if(this.options.ghosting) {
this._clone = this.element.cloneNode(true);
Position.absolutize(this.element);
this.element.parentNode.insertBefore(this._clone, this.element);
}
if(this.options.scroll) {
if (this.options.scroll == window) {
var where = this._getWindowScroll(this.options.scroll);
this.originalScrollLeft = where.left;
this.originalScrollTop = where.top;
} else {
this.originalScrollLeft = this.options.scroll.scrollLeft;
this.originalScrollTop = this.options.scroll.scrollTop;
}
}
Draggables.notify('onStart', this, event);
if(this.options.starteffect) this.options.starteffect(this.element);
},
updateDrag: function(event, pointer) {
if(!this.dragging) this.startDrag(event);
Position.prepare();
Droppables.show(pointer, this.element);
Draggables.notify('onDrag', this, event);
this.draw(pointer);
if(this.options.change) this.options.change(this);
if(this.options.scroll) {
this.stopScrolling();
var p;
if (this.options.scroll == window) {
with(this._getWindowScroll(this.options.scroll)) { p = [ left, top, left+width, top+height ]; }
} else {
p = Position.page(this.options.scroll);
p[0] += this.options.scroll.scrollLeft + Position.deltaX;
p[1] += this.options.scroll.scrollTop + Position.deltaY;
p.push(p[0]+this.options.scroll.offsetWidth);
p.push(p[1]+this.options.scroll.offsetHeight);
}
var speed = [0,0];
if(pointer[0] < (p[0]+this.options.scrollSensitivity)) speed[0] = pointer[0]-(p[0]+this.options.scrollSensitivity);
if(pointer[1] < (p[1]+this.options.scrollSensitivity)) speed[1] = pointer[1]-(p[1]+this.options.scrollSensitivity);
if(pointer[0] > (p[2]-this.options.scrollSensitivity)) speed[0] = pointer[0]-(p[2]-this.options.scrollSensitivity);
if(pointer[1] > (p[3]-this.options.scrollSensitivity)) speed[1] = pointer[1]-(p[3]-this.options.scrollSensitivity);
this.startScrolling(speed);
}
// fix AppleWebKit rendering
if(navigator.appVersion.indexOf('AppleWebKit')>0) window.scrollBy(0,0);
Event.stop(event);
},
finishDrag: function(event, success) {
this.dragging = false;
if(this.options.ghosting) {
Position.relativize(this.element);
Element.remove(this._clone);
this._clone = null;
}
if(success) Droppables.fire(event, this.element);
Draggables.notify('onEnd', this, event);
var revert = this.options.revert;
if(revert && typeof revert == 'function') revert = revert(this.element);
var d = this.currentDelta();
if(revert && this.options.reverteffect) {
this.options.reverteffect(this.element,
d[1]-this.delta[1], d[0]-this.delta[0]);
} else {
this.delta = d;
}
if(this.options.zindex)
this.element.style.zIndex = this.originalZ;
if(this.options.endeffect)
this.options.endeffect(this.element);
Draggables.deactivate(this);
Droppables.reset();
},
keyPress: function(event) {
if(event.keyCode!=Event.KEY_ESC) return;
this.finishDrag(event, false);
Event.stop(event);
},
endDrag: function(event) {
if(!this.dragging) return;
this.stopScrolling();
this.finishDrag(event, true);
Event.stop(event);
},
draw: function(point) {
var pos = Position.cumulativeOffset(this.element);
if(this.options.ghosting) {
var r = Position.realOffset(this.element);
pos[0] += r[0] - Position.deltaX; pos[1] += r[1] - Position.deltaY;
}
var d = this.currentDelta();
pos[0] -= d[0]; pos[1] -= d[1];
if(this.options.scroll && (this.options.scroll != window && this._isScrollChild)) {
pos[0] -= this.options.scroll.scrollLeft-this.originalScrollLeft;
pos[1] -= this.options.scroll.scrollTop-this.originalScrollTop;
}
var p = [0,1].map(function(i){
return (point[i]-pos[i]-this.offset[i])
}.bind(this));
if(this.options.snap) {
if(typeof this.options.snap == 'function') {
p = this.options.snap(p[0],p[1],this);
} else {
if(this.options.snap instanceof Array) {
p = p.map( function(v, i) {
return Math.round(v/this.options.snap[i])*this.options.snap[i] }.bind(this))
} else {
p = p.map( function(v) {
return Math.round(v/this.options.snap)*this.options.snap }.bind(this))
}
}}
var style = this.element.style;
if((!this.options.constraint) || (this.options.constraint=='horizontal'))
style.left = p[0] + "px";
if((!this.options.constraint) || (this.options.constraint=='vertical'))
style.top = p[1] + "px";
if(style.visibility=="hidden") style.visibility = ""; // fix gecko rendering
},
stopScrolling: function() {
if(this.scrollInterval) {
clearInterval(this.scrollInterval);
this.scrollInterval = null;
Draggables._lastScrollPointer = null;
}
},
startScrolling: function(speed) {
if(!(speed[0] || speed[1])) return;
this.scrollSpeed = [speed[0]*this.options.scrollSpeed,speed[1]*this.options.scrollSpeed];
this.lastScrolled = new Date();
this.scrollInterval = setInterval(this.scroll.bind(this), 10);
},
scroll: function() {
var current = new Date();
var delta = current - this.lastScrolled;
this.lastScrolled = current;
if(this.options.scroll == window) {
with (this._getWindowScroll(this.options.scroll)) {
if (this.scrollSpeed[0] || this.scrollSpeed[1]) {
var d = delta / 1000;
this.options.scroll.scrollTo( left + d*this.scrollSpeed[0], top + d*this.scrollSpeed[1] );
}
}
} else {
this.options.scroll.scrollLeft += this.scrollSpeed[0] * delta / 1000;
this.options.scroll.scrollTop += this.scrollSpeed[1] * delta / 1000;
}
Position.prepare();
Droppables.show(Draggables._lastPointer, this.element);
Draggables.notify('onDrag', this);
if (this._isScrollChild) {
Draggables._lastScrollPointer = Draggables._lastScrollPointer || $A(Draggables._lastPointer);
Draggables._lastScrollPointer[0] += this.scrollSpeed[0] * delta / 1000;
Draggables._lastScrollPointer[1] += this.scrollSpeed[1] * delta / 1000;
if (Draggables._lastScrollPointer[0] < 0)
Draggables._lastScrollPointer[0] = 0;
if (Draggables._lastScrollPointer[1] < 0)
Draggables._lastScrollPointer[1] = 0;
this.draw(Draggables._lastScrollPointer);
}
if(this.options.change) this.options.change(this);
},
_getWindowScroll: function(w) {
var T, L, W, H;
with (w.document) {
if (w.document.documentElement && documentElement.scrollTop) {
T = documentElement.scrollTop;
L = documentElement.scrollLeft;
} else if (w.document.body) {
T = body.scrollTop;
L = body.scrollLeft;
}
if (w.innerWidth) {
W = w.innerWidth;
H = w.innerHeight;
} else if (w.document.documentElement && documentElement.clientWidth) {
W = documentElement.clientWidth;
H = documentElement.clientHeight;
} else {
W = body.offsetWidth;
H = body.offsetHeight
}
}
return { top: T, left: L, width: W, height: H };
}
}
/*--------------------------------------------------------------------------*/
var SortableObserver = Class.create();
SortableObserver.prototype = {
initialize: function(element, observer) {
this.element = $(element);
this.observer = observer;
this.lastValue = Sortable.serialize(this.element);
},
onStart: function() {
this.lastValue = Sortable.serialize(this.element);
},
onEnd: function() {
Sortable.unmark();
if(this.lastValue != Sortable.serialize(this.element))
this.observer(this.element)
}
}
var Sortable = {
SERIALIZE_RULE: /^[^_\-](?:[A-Za-z0-9\-\_]*)[_](.*)$/,
sortables: {},
_findRootElement: function(element) {
while (element.tagName != "BODY") {
if(element.id && Sortable.sortables[element.id]) return element;
element = element.parentNode;
}
},
options: function(element) {
element = Sortable._findRootElement($(element));
if(!element) return;
return Sortable.sortables[element.id];
},
destroy: function(element){
var s = Sortable.options(element);
if(s) {
Draggables.removeObserver(s.element);
s.droppables.each(function(d){ Droppables.remove(d) });
s.draggables.invoke('destroy');
delete Sortable.sortables[s.element.id];
}
},
create: function(element) {
element = $(element);
var options = Object.extend({
element: element,
tag: 'li', // assumes li children, override with tag: 'tagname'
dropOnEmpty: false,
tree: false,
treeTag: 'ul',
overlap: 'vertical', // one of 'vertical', 'horizontal'
constraint: 'vertical', // one of 'vertical', 'horizontal', false
containment: element, // also takes array of elements (or id's); or false
handle: false, // or a CSS class
only: false,
delay: 0,
hoverclass: null,
ghosting: false,
scroll: false,
scrollSensitivity: 20,
scrollSpeed: 15,
format: this.SERIALIZE_RULE,
onChange: Prototype.emptyFunction,
onUpdate: Prototype.emptyFunction
}, arguments[1] || {});
// clear any old sortable with same element
this.destroy(element);
// build options for the draggables
var options_for_draggable = {
revert: true,
scroll: options.scroll,
scrollSpeed: options.scrollSpeed,
scrollSensitivity: options.scrollSensitivity,
delay: options.delay,
ghosting: options.ghosting,
constraint: options.constraint,
handle: options.handle };
if(options.starteffect)
options_for_draggable.starteffect = options.starteffect;
if(options.reverteffect)
options_for_draggable.reverteffect = options.reverteffect;
else
if(options.ghosting) options_for_draggable.reverteffect = function(element) {
element.style.top = 0;
element.style.left = 0;
};
if(options.endeffect)
options_for_draggable.endeffect = options.endeffect;
if(options.zindex)
options_for_draggable.zindex = options.zindex;
// build options for the droppables
var options_for_droppable = {
overlap: options.overlap,
containment: options.containment,
tree: options.tree,
hoverclass: options.hoverclass,
onHover: Sortable.onHover
}
var options_for_tree = {
onHover: Sortable.onEmptyHover,
overlap: options.overlap,
containment: options.containment,
hoverclass: options.hoverclass
}
// fix for gecko engine
Element.cleanWhitespace(element);
options.draggables = [];
options.droppables = [];
// drop on empty handling
if(options.dropOnEmpty || options.tree) {
Droppables.add(element, options_for_tree);
options.droppables.push(element);
}
(this.findElements(element, options) || []).each( function(e) {
// handles are per-draggable
var handle = options.handle ?
$(e).down('.'+options.handle,0) : e;
options.draggables.push(
new Draggable(e, Object.extend(options_for_draggable, { handle: handle })));
Droppables.add(e, options_for_droppable);
if(options.tree) e.treeNode = element;
options.droppables.push(e);
});
if(options.tree) {
(Sortable.findTreeElements(element, options) || []).each( function(e) {
Droppables.add(e, options_for_tree);
e.treeNode = element;
options.droppables.push(e);
});
}
// keep reference
this.sortables[element.id] = options;
// for onupdate
Draggables.addObserver(new SortableObserver(element, options.onUpdate));
},
// return all suitable-for-sortable elements in a guaranteed order
findElements: function(element, options) {
return Element.findChildren(
element, options.only, options.tree ? true : false, options.tag);
},
findTreeElements: function(element, options) {
return Element.findChildren(
element, options.only, options.tree ? true : false, options.treeTag);
},
onHover: function(element, dropon, overlap) {
if(Element.isParent(dropon, element)) return;
if(overlap > .33 && overlap < .66 && Sortable.options(dropon).tree) {
return;
} else if(overlap>0.5) {
Sortable.mark(dropon, 'before');
if(dropon.previousSibling != element) {
var oldParentNode = element.parentNode;
element.style.visibility = "hidden"; // fix gecko rendering
dropon.parentNode.insertBefore(element, dropon);
if(dropon.parentNode!=oldParentNode)
Sortable.options(oldParentNode).onChange(element);
Sortable.options(dropon.parentNode).onChange(element);
}
} else {
Sortable.mark(dropon, 'after');
var nextElement = dropon.nextSibling || null;
if(nextElement != element) {
var oldParentNode = element.parentNode;
element.style.visibility = "hidden"; // fix gecko rendering
dropon.parentNode.insertBefore(element, nextElement);
if(dropon.parentNode!=oldParentNode)
Sortable.options(oldParentNode).onChange(element);
Sortable.options(dropon.parentNode).onChange(element);
}
}
},
onEmptyHover: function(element, dropon, overlap) {
var oldParentNode = element.parentNode;
var droponOptions = Sortable.options(dropon);
if(!Element.isParent(dropon, element)) {
var index;
var children = Sortable.findElements(dropon, {tag: droponOptions.tag, only: droponOptions.only});
var child = null;
if(children) {
var offset = Element.offsetSize(dropon, droponOptions.overlap) * (1.0 - overlap);
for (index = 0; index < children.length; index += 1) {
if (offset - Element.offsetSize (children[index], droponOptions.overlap) >= 0) {
offset -= Element.offsetSize (children[index], droponOptions.overlap);
} else if (offset - (Element.offsetSize (children[index], droponOptions.overlap) / 2) >= 0) {
child = index + 1 < children.length ? children[index + 1] : null;
break;
} else {
child = children[index];
break;
}
}
}
dropon.insertBefore(element, child);
Sortable.options(oldParentNode).onChange(element);
droponOptions.onChange(element);
}
},
unmark: function() {
if(Sortable._marker) Sortable._marker.hide();
},
mark: function(dropon, position) {
// mark on ghosting only
var sortable = Sortable.options(dropon.parentNode);
if(sortable && !sortable.ghosting) return;
if(!Sortable._marker) {
Sortable._marker =
($('dropmarker') || Element.extend(document.createElement('DIV'))).
hide().addClassName('dropmarker').setStyle({position:'absolute'});
document.getElementsByTagName("body").item(0).appendChild(Sortable._marker);
}
var offsets = Position.cumulativeOffset(dropon);
Sortable._marker.setStyle({left: offsets[0]+'px', top: offsets[1] + 'px'});
if(position=='after')
if(sortable.overlap == 'horizontal')
Sortable._marker.setStyle({left: (offsets[0]+dropon.clientWidth) + 'px'});
else
Sortable._marker.setStyle({top: (offsets[1]+dropon.clientHeight) + 'px'});
Sortable._marker.show();
},
_tree: function(element, options, parent) {
var children = Sortable.findElements(element, options) || [];
for (var i = 0; i < children.length; ++i) {
var match = children[i].id.match(options.format);
if (!match) continue;
var child = {
id: encodeURIComponent(match ? match[1] : null),
element: element,
parent: parent,
children: [],
position: parent.children.length,
container: $(children[i]).down(options.treeTag)
}
/* Get the element containing the children and recurse over it */
if (child.container)
this._tree(child.container, options, child)
parent.children.push (child);
}
return parent;
},
tree: function(element) {
element = $(element);
var sortableOptions = this.options(element);
var options = Object.extend({
tag: sortableOptions.tag,
treeTag: sortableOptions.treeTag,
only: sortableOptions.only,
name: element.id,
format: sortableOptions.format
}, arguments[1] || {});
var root = {
id: null,
parent: null,
children: [],
container: element,
position: 0
}
return Sortable._tree(element, options, root);
},
/* Construct a [i] index for a particular node */
_constructIndex: function(node) {
var index = '';
do {
if (node.id) index = '[' + node.position + ']' + index;
} while ((node = node.parent) != null);
return index;
},
sequence: function(element) {
element = $(element);
var options = Object.extend(this.options(element), arguments[1] || {});
return $(this.findElements(element, options) || []).map( function(item) {
return item.id.match(options.format) ? item.id.match(options.format)[1] : '';
});
},
setSequence: function(element, new_sequence) {
element = $(element);
var options = Object.extend(this.options(element), arguments[2] || {});
var nodeMap = {};
this.findElements(element, options).each( function(n) {
if (n.id.match(options.format))
nodeMap[n.id.match(options.format)[1]] = [n, n.parentNode];
n.parentNode.removeChild(n);
});
new_sequence.each(function(ident) {
var n = nodeMap[ident];
if (n) {
n[1].appendChild(n[0]);
delete nodeMap[ident];
}
});
},
serialize: function(element) {
element = $(element);
var options = Object.extend(Sortable.options(element), arguments[1] || {});
var name = encodeURIComponent(
(arguments[1] && arguments[1].name) ? arguments[1].name : element.id);
if (options.tree) {
return Sortable.tree(element, arguments[1]).children.map( function (item) {
return [name + Sortable._constructIndex(item) + "[id]=" +
encodeURIComponent(item.id)].concat(item.children.map(arguments.callee));
}).flatten().join('&');
} else {
return Sortable.sequence(element, arguments[1]).map( function(item) {
return name + "[]=" + encodeURIComponent(item);
}).join('&');
}
}
}
// Returns true if child is contained within element
Element.isParent = function(child, element) {
if (!child.parentNode || child == element) return false;
if (child.parentNode == element) return true;
return Element.isParent(child.parentNode, element);
}
Element.findChildren = function(element, only, recursive, tagName) {
if(!element.hasChildNodes()) return null;
tagName = tagName.toUpperCase();
if(only) only = [only].flatten();
var elements = [];
$A(element.childNodes).each( function(e) {
if(e.tagName && e.tagName.toUpperCase()==tagName &&
(!only || (Element.classNames(e).detect(function(v) { return only.include(v) }))))
elements.push(e);
if(recursive) {
var grandchildren = Element.findChildren(e, only, recursive, tagName);
if(grandchildren) elements.push(grandchildren);
}
});
return (elements.length>0 ? elements.flatten() : []);
}
Element.offsetSize = function (element, type) {
return element['offset' + ((type=='vertical' || type=='height') ? 'Height' : 'Width')];
}

File diff suppressed because it is too large Load Diff

File diff suppressed because it is too large Load Diff

View File

@ -0,0 +1 @@
# See http://www.robotstxt.org/wc/norobots.html for documentation on how to use the robots.txt file

Some files were not shown because too many files have changed in this diff Show More