home *** CD-ROM | disk | FTP | other *** search
/ Power-Programmierung / CD1.mdf / prolog / library / prolo_c / exampl56.pro < prev    next >
Text File  |  1986-10-06  |  1KB  |  57 lines

  1. /* Program 56 */
  2. /*
  3.   This program attempts to divide words into
  4.   syllables.  
  5. */  
  6.  
  7. domains
  8.     letter = char
  9.     word = letter*
  10.  
  11. predicates
  12.     divide(word,word,word,word)
  13.     vocal(letter)
  14.     consonant(letter)
  15.     string_word(string,word)
  16.     append(word,word,word)
  17.  
  18. goal
  19.     clearwindow(),
  20.     write("Write a word: "),
  21.     readln(S),
  22.     string_word(S,Word),
  23.     append(First,Second,Word),
  24.     divide(First,Second,Part1,Part2),
  25.     string_word(Syllable1,Part1),
  26.     string_word(Syllable2,Part2),
  27.     write("Division: ",Syllable1,"-",Syllable2),nl,
  28.     fail.
  29.  
  30. clauses
  31.     divide(Start,[T1,T2,T3|Rest],D1,[T2,T3|Rest]):-
  32.         vocal(T1),consonant(T2),vocal(T3),
  33.         append(Start,[T1],D1).
  34.     divide(Start,[T1,T2,T3,T4|Rest],D1,[T3,T4|Rest]):-
  35.         vocal(T1),consonant(T2),consonant(T3),vocal(T4),
  36.         append(Start,[T1,T2],D1).
  37.     divide(Start,[T1|Rest],D1,D2):-
  38.         append(Start,[T1],S),
  39.         divide(S,Rest,D1,D2).
  40.  
  41.     vocal('a').vocal('e').vocal('i').
  42.     vocal('o').vocal('u').vocal('y').
  43.  
  44.     consonant(B):-
  45.         not(vocal(B)), B <= 'z', 'a' <= B.
  46.  
  47.     string_word("",[]):-!.
  48.     string_word(Str,[H|T]):-
  49.         bound(Str),frontchar(Str,H,S),string_word(S,T).
  50.     string_word(Str,[H|T]):-
  51.         free(Str),bound(H),string_word(S,T),
  52.         frontchar(Str,H,S).
  53.  
  54.     append([],L,L):-!.
  55.     append([X|L1],L2,[X|L3]) :-
  56.         append(L1,L2,L3).
  57.