Find mutual element in different facts in swi-prolog

后端 未结 1 1874
青春惊慌失措
青春惊慌失措 2021-01-25 08:58

i am trying to have an input of a list of movies and find the actors who play at the same movies. Question : Given a list of movies, display their link by a set of stars using r

1条回答
  •  粉色の甜心
    2021-01-25 09:34

    Here is another one (I finally found a way)

    No recursion, just a relative of findall, setof/3:

    Given a database of "actors starring in movies":

    starsin(a,bob).
    starsin(c,bob).
    
    starsin(a,maria).
    starsin(b,maria).
    starsin(c,maria).
    
    starsin(a,george).
    starsin(b,george).
    starsin(c,george).
    starsin(d,george).
    

    We do some reflection (described in setof/3 inside setof/3 not working, but why?), and then:

    subselect(Ax,MovIn) :- 
       setof(Mx,starsin(Mx,Ax),MovAx), subset(MovIn, MovAx).
    actors_appearing_in_movies(MovIn,ActOut) :- 
       setof(Ax, subselect(Ax,MovIn) , ActOut).
    

    This has the right feel of being an RDBMS operation!

    Testing!

    Note that for the empty set of movies, we get all the actors. This is marginally right: all the actors star in all the movies of the empty set.

    Testing consists in running these goals and observing that they succeed:

    actors_appearing_in_movies([],ActOut),
    permutation([bob, george, maria],ActOut),!. 
    
    actors_appearing_in_movies([a],ActOut),
    permutation([bob, george, maria],ActOut),!.
    
    actors_appearing_in_movies([a,b],ActOut),
    permutation([george, maria],ActOut),!.
    
    actors_appearing_in_movies([a,b,c],ActOut),
    permutation([george, maria],ActOut),!.
    
    actors_appearing_in_movies([a,b,c,d],ActOut),
    permutation([george],ActOut),!.
    

    Bonus Round: In R

    Completely unrelated, but I thought about how to do that in R.

    After some fumbling:

    # Load tidyverse dplyr
    
    library(dplyr)
    
    # Create a data frame ("tibble") with our raw data using `tribble`
    
    t <- tribble(
            ~movie, ~actor
            ,"a"   , "bob"
            ,"c"   , "bob"
            ,"a"   , "maria"
            ,"b"   , "maria"
            ,"c"   , "maria"
            ,"a"   , "george"
            ,"b"   , "george"
            ,"c"   , "george"
            ,"d"   , "george")
    
    # The function!
    
    actors_appearing_in_movies <- function(data, movies_must) {
       # (movie,actor) pairs of actors active in movies we are interested in 
       t1 <- data %>% filter(is.element(movie, movies_must))
    
       # (actor, (movies)) pairs of actors and the movies they appear in
       # for movies we are interested in 
       t2 <- t1 %>% group_by(actor) %>% summarize(movies = list(unique(movie)))   
    
       # Retain only those which appear in all movies
       t3 <- t2 %>% rowwise() %>% filter(setequal(movies_must,movies))
    
       # Select only the actor column
       # ("Select" works columnwise, not rowwise as in SQL)   
       t4 <- t3 %>% select(actor)
    
       return(t4)
    }
    

    Results?

    The above approach has a different opinion on who is in the empty movie set:

    > actors_appearing_in_movies(t, c())
    # A tibble: 0 x 1
    # … with 1 variable: actor 
    

    But:

    > actors_appearing_in_movies(t, c("a"))
    
    # A tibble: 3 x 1
      actor 
       
    1 bob   
    2 george
    3 maria 
    
    > actors_appearing_in_movies(t, c("a","b"))
    
    # A tibble: 2 x 1
      actor 
       
    1 george
    2 maria 
    
    > actors_appearing_in_movies(t, c("a","b","c"))
    
    # A tibble: 2 x 1
      actor 
       
    1 george
    2 maria 
    
    > actors_appearing_in_movies(t, c("a","b","c","d"))
    
    # A tibble: 1 x 1
      actor 
       
    1 george
    

    0 讨论(0)
提交回复
热议问题