$BJB9T%W%m%0%i%_%s%08@8l(B(2)/Concurrent Programming Languages(2)

$BJB9T%7%9%F%`(B

                               $B%7%9%F%`>pJs7O(B/$B>pJs9)3X0h(B,
			       $B%7%9%F%`>pJs9)3X8&5f72(B/$B>pJsM}9)3X0L%W%m%0%i%`(B
			       $B%7%9%F%`>pJs9)3X8&5f2J(B/$B%3%s%T%e!<%?%5%$%(%s%9@l96(B
                               $B?7>k(B $BLw(B
                               <yas@cs.tsukuba.ac.jp>

$B$3$N%Z!<%8$O!" https://www.cs.tsukuba.ac.jp/~yas/cs/csys-2025/2025-06-20
$B$"$k$$$O!" https://www.cs.tsukuba.ac.jp/~yas/cs/
https://www.cs.tsukuba.ac.jp/~yas/

$B"#O"Mm;v9`(B

$B"#:#F|$N=EMW$JOC(B

$B;29MJ88%(B References

$B"#JB9T%*%V%8%'%/%H;X8~%b%G%k(B/Concurrent object-oriented models.

$B%*%V%8%'%/%H;X8~$N0l
  • $B!JC` $BJB9T%*%V%8%'%/%H$O!"G=F0E*(B(active)$B$J%*%V%8%'%/%H$7$+$J$$!#?M4V$N$h(B $B$&$K!"Aj8_$K%a%C%;!<%8$rAw

    $B"!%"%/%?%b%G%k(B/The Actor models

    1977$BG/(B C.Hewitt $B$i$K$h$C$FDs>'$5$l$?JB9T7W;;%b%G%k!#(B $B%"%/%?$H8F$P$l$k7W;;

    $B8@8l$H$7$F$O!"2?

    $B8=:_$G$O!"%"%/%?$r!V(B($BJB9T(B)$B%*%V%8%'%/%H!W$HFI$_BX$($k$HJ,$+$j$d$9$$!#(B

    $B%

    $B?^(B? $B%"%/%?$N4pK\35G0(B/Basic concepts of the Actor model

    $B%"%/%?$O!"%a%C%;!<%8$r

  • $B%a%C%;!<%8$r!"<+J,<+?H!"$^$?$O!"B>$N%"%/%?$KAw?.$9$k!#(B
  • $B%"%/%?$r@8@.$9$k!#(B
  • $B $B%"%/%?$O!"%a%C%;!<%8$r@\FO$/$H$$$&$h$j$O!"%a!<%k%\%C%/%9$K4V@\E*$KFO(B $B$/!#%a!<%k%\%C%/%9$O!"%P%C%U%!%j%s%0$N5!G=$,$"$k!#%a!<%k%\%C%/%9$K$"$k(B $B%a%C%;!<%8$O!"(BFIFO $B$K=hM}$5$l$k$H$O8B$i$J$$!#(B

    $B%"%/%?$,%a%C%;!<%8$r

    $BMWAG(B

    • $B%W%j%_%F%#%V!&%"%/%?(B(primitive actor)$B!#%G!<%?$H $BHs%W%j%_%F%#%V%_%#%V%"%/%?(B
      • $B=guBVJQ?t$r;}$D!#(B
      • $BHs=g
      $B%"%/%?$O!"%a%C%;!<%8$rAw

      $B"!7QB3(B/Continuations

      $B7QB3(B(continuation$B!"7QB3E@$H$b$$$&(B)$B$rMQ$$$k!#(B $B5f6K$N(B goto $BJ8!#(BC $B8@8l$N4X?t$G(B
          goto f(1, 2, 3);
      
      $B$N$h$&$J$b$N!#(B

      $BDL>o$N3,>h(B(in Scheme)

      (define (fact n)
          (if (= n 0) 1
              (* n (fact (- n 1)))))
      
      $B7QB3$rh(B
      (define (fact-c n c)
        (if (= n 0)
            (c 1)
            (let ((c2 (lambda (x) (c (* n x)))))
              (fact-c (- n 1) c2))))
      

      $B > (fact 3)[$B 6 > (fact 4)[$B 24 > (fact-c 3 print)[$B 6> (fact-c 4 print)[$B 24> []

      $B"!3,>h(B/Factorial in Actor

      [Hewitt 77a]
      factorial$B-q&K(Bm.
        match m <n c>
          if n = 1 then
            (send c <1>)
          else if n > 1 then
            (send factorial <(n-1) ($B&K(Bk.(send c <n * k>))>)
      
      3$B$N3,>h$r7W;;$7$F!"7QB3(Bprint_answer$B$KAw$j$?$$;~$K$O!"(B $B (send factorial <3 print_answer>)

      $B"!3,>h(B/Factorial in Actor

      Gul Agha. 1986. An overview of actor languages. In Proceedings of the 1986 SIGPLAN workshop on Object-oriented programming (OOPWORK 86. Association for Computing Machinery',58-67. )
      (define (Factorial( ))
        (Is-Communication (a doit (with customer =m)
      		       (with number =n)) do
            (become Factorial)
            (if (NOT (= n 0))
      	(then (send m 1))
      	(else (let (x = (new FactCust (with customer m)
      			     (with number n)))
      		(send Factorial (a do (with customer x)
      				   (with number (- n 1)))))))))
      (define (FactCust (with customer =m)
      		  (with number =n))
        (Is-Communicaton (a number k) do
          (send m (* n k))))
      
      • 2$B$D$N%Q%i%a%?$r;}$D%a%C%;!<%8(B ((with customer x) (with number n)) $B$r (become Factorial) $B$G!"<+J,<+?H$r:F@8@.!#$=$&$G$J$$$H!"(B1$B8D$N(B Factorial $B$r7W;;$7$?$@$1$G%"%/%?$,>CLG$7$F$7$^$&!#(B
      • $B?7$7$$%"%/%?(B FactCust $B$r@8@.$7$F$$$k!#(B
      $B?6$kIq$$5-=R(B
          (define ($BL>A0(B (with id $B%Q%?%s(B))
            $BDL?.%O%s%I%i$NJB$S(B)
      
      $BDL?.%O%s%I%i(B
          (Is-Communication $B%Q%?%s(B do $B%3%^%s%I(B)
      
      let$B%3%^%s%I(B
          (let ($BJQ?tL>(B = $B<0(B) do $B%3%^%s%I(B)
      
      $B>r7o%3%^%s%I(B
          (if $B<0(B (then do $B%3%^%s%I$NJB$S(B) (else do $B%3%^%s%I$NJB$S(B))
      
      $B%a%C%;!<%8Aw?.%3%^%s%I(B
          (send $B%a!<%k%\%C%/%9(B $BCM(B)
      
      become$B%3%^%s%I(B
          (become $B<0(B)
      
      $B?7$7$$%"%/%?$N@8@.(B
        (new $B<0(B)
      
      

      $B"!6d9T8}:B(B/A bank account in Actor

      (define (Account (with Balance =b))
        (Is-Request (a Balance) do 
          (become (Account (with Balance b)))
          (reply b))
        (Is-Request (a Deposit (with Amount =a)) do
          (become (Account (with Balance (+ b a))))
          (reply (a Deposit-Receipt (with Amount a))))
        (Is-Request (a Withdrawal (with Amount =a)) do
          (if (> a b)
            (then do 
              (become (Account (with Balnce b)))
              (complain (an Overdraft)))
            (else do 
              (become (Account (with Balnce(- b a))))
      	(reply (a Withdrawal-Receipt (with Amount a)))))))
      
      • Is-Request $B$O!"(Bclient-server $B7?$N%a%C%;!<%8(B $B$N reply $B$O!"(BIs-Request $B$KBP$9$kDL>o$N1~Ez$rJV$9!#(B
      • complain $B$O!"(BIs-Request $B$KBP$9$kNc30$N1~Ez$rJV$9!#(B
      • become $B$H(B reply $B$O!"F1;~$K=hM}$G$-$k!#(B

      $B"!%+%&%s%?(B(Scala)/Counter actor in Scala

      $B=i4|$N(B Scala $B$K$O!"(BActor $B$N5!G=$,4^$^$l$F$$$F!"(B $B!V(B!$B!W$G!"%a%C%;!<%8$NAw)(B(deprecated)$B$K!#(B $B?7$7$/%W%m%0%i%`$r=q$/$J$i!"(B Akka$B$r;H$&!#(B Classic Actor$B$+$i(BTyped Actor $B$X$N0\9T$K$D$$$F(B by taketora $B;2>H!#(B
      import akka.actor.typed.scaladsl.Behaviors
      import akka.actor.typed.{ActorRef, Behavior}
      
      object Counter {
        sealed trait Command
        case object Increment                               extends Command
        final case class GetValue(replyTo: ActorRef[Value]) extends Command
        final case class Value(n: Int)
      
        def apply(): Behavior[Command] = counter(0)
      
        private def counter(n: Int): Behavior[Command] =
          Behaviors.receive { (context, message) => //$B"(#1(B
            message match {
              case Increment         =>
                val newValue = n + 1
                context.log.debug("Incremented counter to [{}]", newValue)
                counter(newValue) //$B"((B2
      
              case GetValue(replyTo) =>
                replyTo ! Value(n)
                Behaviors.same
            }
          }
      }
      
      • $B!V(B!$B!W$G!"%a%C%;!<%8$rAw?.$9$k!#(B
      • Behaviors.receive $B$G RPC $BE*$JF0$-$r

        $B"!%+%&%s%?(B(Kotlin)/Counter actor in Kotlin

        Shared mutable state and concurrency/Actors
        // This function launches a new counter actor
        fun CoroutineScope.counterActor() = actor<CounterMsg> {
            var counter = 0 // actor state
            for (msg in channel) { // iterate over incoming messages
                when (msg) {
                    is IncCounter -> counter++
                    is GetCounter -> msg.response.complete(counter)
                }
            }
        }
        
        fun main() = runBlocking {
            val counter = counterActor() // create the actor
            withContext(Dispatchers.Default) {
                massiveRun {
                    counter.send(IncCounter)
                }
            }
            // send a message to get a counter value from an actor
            val response = CompletableDeferred<Int>()
            counter.send(GetCounter(response))
            println("Counter = ${response.await()}")
            counter.close() // shutdown the actor
        }
        
        • a = actor {...}$B$G!"%"%/%?@8@.!#L58B%k!<%W4^$`!#(B
        • $BFbIt$N$B%3%k!<%A%s(B$B!#(B
        • a.send(...) $B$G!"%"%/%?$X%a%C%;!<%8Aw?.!#(B
        • $BJV$jCM$N

          $B"!%+%&%s%?(B(Elixir)/Counter actor in Elixir

          Concurrency and Actor Model
          defmodule Counter do
            def start(initial_count) do
              spawn fn -> listen(initial_count) end
            end
          
            def listen(count) do
              receive do
                :inc -> listen(count + 1)
                {sender, :val} ->
                  send sender, count
                  listen(count)
              end
            end
          end
          
          iex> counter_pid = Counter.start(10)
          #PID<...>
          
          iex> send counter_pid, :inc
          :inc
          iex> send counter_pid, :inc
          :inc
          iex> send counter_pid, :inc
          :inc
          iex> send counter_pid, {self, :val}
          {#PID<...>, :val}
          
          iex> receive do
          ...(13)>   value -> value
          ...(13)> end
          13
          
          • Elixir $B$O4X?t7?8@8l!#$=$l$@$1$G$O>uBV$r;}$D$3$H$,$G$-$J$$!#(B
          • Elixir $B$O!"%W%m%;%9$r@8@.$9$l$P!">uBV$rJ];}$G$-$k!#(B
          • $B:F5"8F$S=P$7$GL58B%k!<%W$rI=8=$9$k!#(B $B:F5"8F$S=P$7$N0z?t$G>uBV$r99?7$9$k!#(B
          Erlang $B$bF1$8!#(B Concurrency in Erlang & Scala: The Actor Model $B;2>H!#(B

          $B"!(BRuby 3.0 Ractor

          Ruby 3.0 (2021/12) $B$KF3F~$5$l$?5!G=(B Ractor (Ruby + actor) $B$r;H$&$H!"(B $BB?$/$N%W%i%C%H%U%)!<%`$G(B CPU $B%l%Y%k$NJBNs=hM}$,$G$-$k!#(B (Ruby $B$N%9%l%C%I(B$B$O!"(B Giant VM lock (GVL)/Global Interpreter Lock (GIL) $B$rJ];}$7$F

          $B%+%&%s%?$NNc!#(B

             1: #!/opt/local/bin/ruby3.0
             2: 
             3: Warning[:experimental] = false
             4: 
             5: class CounterActor
             6:     def initialize(val)
             7:         @r = Ractor.new(val) {|val|
             8:             loop {
             9:                 msg = Ractor.receive()
            10:                 case msg
            11:                 in [:inc]
            12:                     val += 1
            13:                 in [:getvalue, c]
            14:                     c.send(val)
            15:                 end
            16:             }
            17:         }
            18:     end
            19:     def send( msg )
            20:         @r.send( msg )
            21:     end
            22: end
            23: 
            24: c = CounterActor.new(10)
            25: 
            26: c.send([:inc])
            27: c.send([:inc])
            28: c.send([:getvalue, Ractor.current()])
            29: v = Ractor.receive()
            30: printf("Counter value == %d\n",v)
          
          $B $ ./ractor-counter.rb [$B Counter value == 12 $ [] Ruby 3.0 $B$N(B Ractor $B$NFCD'!#(B
          • CPU $B%l%Y%k$NJBNs=hM}$N$?$a$K@_7W$5$l$F$$$k!#(B $BC1$K%"%/%?!&%b%G%k$r;H$$$?$$$H$$$&L\E*$G$O!";H$$Fq$$!#(B
          • $BI8=`E*$J%"%/%?%b%G%k$HF1MM$K!"(B $BF~NOMQ$N%a!<%k%\%C%/%9$r;H$C$F(B send(), receive() $B$GDL?.$,$G$-$k!#(B
          • Ractor $BFH<+$NDL?.5!G=$H$7$F!"(B ($B=PNOMQ$N%a!<%k%\%C%/%9$r;H$C$F(B) yield() $B$H(B take() $B$GDL?.$G$-$k!#(B
          • Ractor $B4V$O3VN%$5$l$F$$$k!#(B $BB?$/$N%*%V%8%'%/%H$O!"(BRactor $B4V$G6&M-$G$-$J$$$N$G!"6%9g$O@8$8$J$$!#(B $B6&M-$G$-$k%*%V%8%'%/%H$K$O!"
          • $BITJQ%*%V%8%'%/%H!#(B
          • $B%/%i%9!?%b%8%e!<%k%*%V%8%'%/%H(B
          • $BFC
          • $stdin, $stdout, $stderr $BEy$O!"(BRactor local object$B!#(B $B%9%l%C%I8GM-%G!<%?(B(Thread specific data)$B$N$h$&$J$b$N!#(B Ractor $B$NCf$G(B printf() $B$OF0$/!#(B
          • Ractor.new() {} $B$NCf$N%V%m%C%/$G$O!"30B&$NJQ?t$,%"%/%;%9$G$-$J$$!#(B Ractor.new(v1,v2,v3) {|v1,v2,v3| ...} $B$N$h$&$KL@<(E*$KEO$9I,MW$,$"$k!#(B
          • send() $B$G$O!"%*%V%8%'%/%H$,%3%T!<$5$l$FEO$5$l$k$N$,4pK\!#(B
          • Ractor.receive_if{|msg| $B>r7o(B } $B$G!"%,!<%I$,=q$1$k!#(B
          $B?7>k$N%3%a%s%H!#(B
          • Ractor $B4V$G$NM-8B%P%C%U%!(B(channel)$B$K$h$kDL?.5!G=$,M_$7$$!#(B $BM-8B%P%C%U%!$r(B Ractor $B$G:n$l$k$N$@$m$&$,!"%Q%C%7%V%*%V%8%'%/%H$G:n$k$N$,<+A3$K;W$($k!#(B
          • $B%a%C%;!<%8$NAw$je$N%+%&%s%?(B $B$NNc$N$h$&$K!"$=$3$K7k2L$rAw$jJV$7$F$b$i$&$3$H$O$G$-$k!#$7$+$7!"(B1$B$D$N(B Ractor $B$,J#?t$N(B Ractor $B$KF1;~$KMW5a$rAw$C$?;~!"J#?t$N1~Ez$,:.$8$C(B $B$F$7$^$&!#(B
          • Elixir $B$N$h$&$K!"(Breceive $B$G%Q%?%s%^%C%A$,;H$($k$H!"(B $B%W%m%0%i%`$O=q$-$d$9$$$,@-G=$OMn$A$=$&!#(B

          $B"#JB9TO@M}7?%W%m%0%i%_%s%08@8l(B/Concurrent logic programming languages

          $B"!(BProlog

          Prolog (Programming in Logic) $B$O!"%U%i%s%9%^%k%;%$%fBg3X$N(B Alain Colmerauer $B$i$K$h$C$F3+H/$5$l$?8@8l!#(B $B#13,=R8lO@M}(B(first-order predicate logic)$B$K4p$E$$$F$$$k!#(B

          $B"!#13,=R8lO@M}(B/first-order predicate logic

          $B=R8lO@M}$G$O!"
        • $B=R8l(B P(t 1, t 2, ..., t n)
        • ($B"O(Bx)P(x)$B!#A4$F$N(Bx$B$K$D$$$F(BP(x)$B$,@.$jN)$D!#(B
        • ($B"P(Bx)P(x)$B!#(B $B$"$k(Bx$B$K$D$$$F(BP(x)$B$,@.$jN)$D!#(B
        • P$B"J(BQ$B!"(BP$B"K(BQ$B!"!A(BP$B!#(B and, or, not
        • P$B"+(BQ$B!#(BQ$B$,??$J$i$P(BP$B$b??!#(B

        $B#13,=R8lO@M}$NO@M}<0$O!"

        P 1 $B"K(B P 2 $B"K(B ... $B"K(B P n $B"+(B Q 1 $B"J(B Q 2 $B"J(B ... $B"J(B Q n.

        $B!V"+!W$N:8$,$?$+$@$+(B1$B8D$N$b$N$,%[!<%s@a(B(Horn clause)$B!#(B(OR$B$,J#?t=q$-$?$/(B $B$J$C$?$i!"J#?t9T$K$o$?$C$F=q$/(B)$B!#%[!<%s@a$K$O(B3$B

      • $BI=L@(B: P$B"+(B.
      • $B8xM}(B: P$B"+(B Q 1 $B"J(B Q 2 $B"J(B ... $B"J(B Q n.
      • $BL\I8(B: $B"+(B Q 1 $B"J(B Q 2 $B"J(B ... $B"J(B Q n.

      $B"!C1=c$J%b%G%k(B($B;v

      fatherof(isaac,abraham).  -- isaac $B$NIc$O(B abraham $B$G$"$k(B
      fatherof(ishmail,abraham).
      fatherof(shuah,abraham).
      fatherof(jacob,isaac).
      fatherof(esau,isaac).
      fatherof(reuben,jacob).
      fatherof(dinah,jacob).
      fatherof(dan,jacob).
      fatherof(asher,jacob).
      fatherof(joseph,jacob).
      motherof(isaac,sarah).  -- isaac $B$NJl$O(B sarah $B$G$"$k!#(B
      motherof(ishmail,hagar).
      motherof(shuah,ketura).
      motherof(jacob,rebeccah).
      motherof(easu,rebeccah).
      motherof(reuben,leah).
      motherof(dinah,leah).
      motherof(dan,bilhah).
      motherof(asher,zilpah).
      motherof(joseph,rachel).
      
      • "_" $B$O!"L5L>JQ?t!#CM$O;D$i$J$$!#(B
      • "motherof(isaac,_)?" $B$N"motherof(isaac,sarha)" $B$@$1$,%^%C%A$9$k!#(B
      • "fatherof(_,_)" $B$N"fatherof" $B$,%^%C(B $B%A$9$k!#(B
      • "fatherof(joseph,X)" $B$N"X=jacob" $B$N;~$K(B $B%^%C%A$9$k!#$3$N;~$KJQ?t(B "X" $B$O!"(B"jacob" $B$KB+G{(B(bind)$B$5$l$F$$$k!#(B
      • Prolog $B$NJQ?t$O!"F1$8%3%s%F%-%9%H$G$OC10lBeF~(B(single assignment)$B$G!"(B C $B8@8l$N(B x = x + 1 $B$N$h$&$J0UL#$G=q$-49$($i$l$k$3$H$O$J$$!#(B
      • "motherof(C,leah)?" $B$N"C=reuben" $B$H$$$&B+G{$,5/$-$?8e$K!"(B $B%P%C%/%H%i%C%/$,9T$o$l$F!"!VJL$N%3%s%F%-%9%H$G!W(B "C=dinah" $B$H$$$&B+G{$,5/$-$k$3$H$,$"$k!#(B
      • $BJQ?t$r4^$`%Q%?%s%^%C%A$O!"C10l2=(B(unification)$B$H8F$P$l$k!#(B

      $B"!5,B'(B/Rules

      parentof(C,P) :- motherof(C, P). -- P $B$,(B C $B$NJl$J$i!"(B P $B$O(B C $B$N?F$G$"$k!#(B
      parentof(C,P) :- fatherof(C, P). -- P $B$,(B C $B$NIc$J$i!"(B P $B$O(B C $B$N?F$G$"$k!#(B
      
      grandparentof(C,GP) :- parentof(C,P), parentof(P,GP).
                               -- C $B$N?F$,(B P $B$G!"$+$D!"(BP $B$N?F$,(B GP $B$J$i!"(BGP $B$O(B C $B$NADIcJl$G$"$k!#(B
      ancestor(C,A) :- parentof(C,A).
      ancestor(C,A) :- parentof(C,P), ancestor(P,A).
                               -- C $B$N?F$,(B P $B$G!"$+$D!"(BP $B$NAD@h$,(B A $B$J$i$P!"(BA $B$O(B C $B$NAD@h$G$"$k!#(B
      

      $B"!%j%9%H(B/Lists

      append([],Y,Y).
      append([A|B],Y,[A|B1]) :- append(B,Y,B1).  
      
      • append $B$O!"(B3 $B$D$N0z?t$,$"$k!#Bh(B1$B0z?t$N%j%9%H$H(B $BBh(B2$B0z?t$N%j%9%H$r(B append $B$7$F!"Bh(B3$B0z?t$KEz$($rJV$9!#(B ($B5UJ}8~$K$b;H$($k!#(B)
      • [] $B$O!"6u%j%9%H(B(nil)$B!#(B
      • [] $B$H(B Y $B$r(B append $B$7$?$b$N$O(B Y $B$G$"$k!#(B
      • [A|B] $B$H(B Y $B$r(B append $B$9$k$K$O!"$^$:!"(BB $B$H(B Y $B$r(B append $B$7$F!"$=$N7k(B $B2L$r(B B1 $B$H$7!"(BB1 $B$N@hF,$K(B A $B$rIU$1$k!#(B

      A$B!

      $B?^(B? Prolog $B$N(B append

      $B"!(BAND$BJBNs$H(BOR$BJBNs(B/and-parallelism and or-parallelism

      $BO@M}<0$NI>2A$K=gHV$N9M$(J}$O$J$$$N$G!"JBNs$K=hM}$r9T$C$F$b$h$$!#(B
      • AND $BJBNs@-(B(AND parallelism)$B!#(BProlog $B$N(B :- $B$N1&B&$rA4ItJBNs$K OR $BJBNs@-(B(OR parallelism)$B!#(BProlog $B$GF1$8F,$N=R8l$rA4ItJBNs$K OR$BJBNs$r9M$($k$H!"%P%C%/%H%i%C%/$H$$$&9M$($k$OB8:_$7$J$/$J$k!#(B

        $B"!(Bquicksort

        quicksort(List,Sorted) :- qsort(List, Sorted, []).
        qsort([],H,H).
        qsort([A|B],H,T) :-
            partition(B,A,S,L),
            qsort(S,H,[A|T1]), 
            qsort(L,T1,T). 
        partition([],X,[],[]).
        partition([A|B],X,[A|S],L) :- A<X, partition(B,X,S,L).
        partition([A|B],X,S,[A|L]) :- A>=X, partition(B,X,S,L).
        
        • quicksort() $B$O!"(B2$B0z?t!#Bh(B1$B0z?t$N%j%9%H$r%=!<%H$7$F!"Bh(B2$B0z?t$K7k2L(B $B$rJV$9!#(B
        • $B2<@A$1$N(B 3 $B0z?t$N(B qsort $B$r8F$V!#Bh(B1$B0z?t$,%=!<%H$9$Y$-%j%9%H!#Bh(B2$B0z(B $B?t$HBh(B3$B0z?t$N!V:9J,!W$,!"%=!<%H7k2L!#(B
        • $B6u%j%9%H$r%=!<%H$9$k$H!"6u%j%9%H$K$J$k!#Bh(B2$B0z?t$HBh(B3$B0z?t$,F1$8$J$N(B $B$G!":9J,%j%9%H(B H-H $B$O!"6u%j%9%H!#(B
        • $B%j%9%H(B [A|B] $B$r%=!<%H$9$k$K$O!"$^$:!"$=$N%j%9%H$r@hF,0J30$NItJ,(B B $B$r!"(BA $B$h$j>.$5$$ItJ,(B S $B$H(B A $B$h$jBg$-$$ItJ,(B L $B$KJ,3d$9$k!#(B
        • $B:F5"$G!"(BS $B$r%=!<%H$9$k!#7k2L$O!":9J,%j%9%H(B H-[A|T1]$B$GJ];}$9$k!#(B
        • $B:F5"$G!"(BL $B$r%=!<%H$9$k!#7k2L$O!":9J,%j%9%H(B T1-T $B$GJ];}$9$k!#(B
        • $B$=$l$>$l%=!<%H$7$?8e!"A4BN$N7k2L$O!":9J,%j%9%H(B H-T $B$GJV$9!#(B

        A$B!

        $B?^(B? Prolog $B$K$h$k%/%$%C%/%=!<%H(B

        quicksort $B$K$"$kJBNs@-!#(BParallelism in quicksort.
        • S $B$H(B L $B$N(B qsort $B$,JBNs$K partition $B$H(B sort $B$NJBNs@-(B($B%Q%$%W%i%$%s7?JBNs@-(B)$B!#(B $BJ,3d$,0lIt$@$1=*$o$C$?CJ3,$G%=!<%H$N:n6H$K

          $B"!(BGHC (Guarded Horn Clauses)

          Prolog $B$HF1MM$K!"#13,=R8lO@M}$K4p$E$$$F$$$k!#(B $BJBNs(B($BJB9T(B)$BO@M}7?8@8l!#(B
          • Prolog $B$G$O!"F~=PNO$,=q$1$J$$$,!"(BGHC $B$G$O$+$1$k!#(B
          • Prolog $B$G$O%P%C%/%H%i%C%/$GA42rC5:w$,$G$-$k$,!"(BGHC $B$G$O$G$-$J$$!#(B

          $B"!(BGHC$B$N9=J8(B/Syntax of GHC

          H :- G 1, G 2,...,G n | B 1, B 2, ..., B m.

          $B!V(B|$B!W$O!"%3%_%C%H1i;;;R!#(B G 1, G 2,...,G n $B$O%,!<%IIt!#(B B 1, B 2, ..., B m $B$O!"%\%G%#It!#(B
          append([A|X1],Y,Z) :- true | Z = [A|Z1], append(X1,Y,Z1).  
          append([],Y,Z) :- true | Z=Y.
          
          Prolog $B$J$i$3$&$J$k(B
          append([A|X1],Y,[A|Z1]) :- append(X1,Y,Z1).  
          append([],Y,Y).
          
          • GHC $B$G$O!"J}8~$,$"$k!#F~NO$H=PNO$,J,$+$l$k!#(B
          • GHC $B$G$O!"J#?t$N%,!<%IItJ,$rJBNs$K :- append(U,[4,5],W),U=[1,2,3]. $B$J$i!"(Bappend $B$N=hM}$O:G=i$OCfCG$9$k!#(BU $B$,6qBN2=$5$l$?8e$G:F3+$9$k!#(B
          • GHC $B$G$O!"%,!<%IItJ,$,@.8y$7$?@a$N$&$A#1$D$7$+;H$o$l$J$$!#(B ($BB>$N(B OR $B$N@a$N=hM}$OL5BL$K$J$k!#8zN($N$?$a$K$O;_$a$?J}$,NI$$$,!"(B $B;_$a$k%3%9%H$b%P%+$K$J$i$J$$$3$H$b$"$k!#(B $BF0$+$7$?$^$^$G$bEz$($OJQ$o$i$J$$!#(B OR$BItJ,$r#1$D$R$H$D
            quicksort(Xs,Ys) :- true | qsort(Xs, Ys-[]).
            qsort([X|Xs],Ys0-Ys3) :- true |
                partition(Xs,X,S,L),
                qsort(S,Ys0-Ys1), Ys1=[X|Ys2],
                qsort(L,Ys2-Ys3). 
            qsort([],Ys0-Ys1) :- true | Ys0 = Ys1.
            
            partition([X|Xs],A,S,L0) :- A<X  | L0=[X|L1], partition(Xs,A,S,L1).
            partition([X|Xs],A,S0,L) :- A>=X | S0=[X|S1], partition(Xs,A,S1,L).
            partition([],A,S,L) := true | S=[], L=[].
            
            • $B:9J,%j%9%H$NI=5-J}K!$H$7$F(B A-B $B$,;H$($k!#(B
            • $BJ#?t$N@a$,JBNs$K

              $B"#(BJini

              Jini ($B%8%K!<(B)$B$O!"(BJava $B$rCf3K$K$7$?!">pJs2HEE@=IJ$rAj8_@\B3$9$k$?$a$NDL(B $B?.5;=Q!#(B

              1999$BG/$K!"%5%s!&%^%$%/%m%7%9%F%`%:

              Jini $B$NL\I8$O!"%M%C%H%o!<%/$G(B Plug & Play $B$r

              $BL\I8(B

              • $B!V%5!<%S%9!W$NDs6!
              • (IP)$B%"%I%l%9(B
              • $BL>A0%5!<%P$N0LCV(B(/etc/resolv.conf)
            • $B%5!<%S%9$N0LCV$,$o$+$i$J$/$F$b$h$$!#(B
            • $B8EE5E*$J!V%M%C%H%o!<%/4IM} $B%5!<%S%9$K$O!"%O!<%IE*$J$b$N!J%W%j%s%?!"%G%#%8%?%k%+%a%i!"(BCD Player$B!K(B $B$NB>$K!"%=%U%HE*$J$b$N(B($B%9%Z%k%A%'%C%/!"K]Lu!"%"%I%l%9D"(B)$B$,$U$/$^$l$k!#(B

              JavaSpaces $B$O!"FbItE*$K(B Jini $B$N%k%C%/%"%C%W!&%5!<%S%9$N

              Jini $B$N%/%i%9%i%$%V%i%j$O!"(B JavaSpaces $B$N2s(B $B$G>R2p$7$?(B Apache River $B$,MxMQ$G$-$k!#(B

              $B"!(BUPnP (Universal Plug and Play)

              Microsoft $B$N!"(BJini $B$KBP93$7$?5;=Q!#(B

              $B"!%k%C%/%"%C%W!&%5!<%S%9(B/Loockup service in Jini

              Jini$BCf?4E*$J5;=Q$,!"%k%C%/%"%C%W!&%5!<%S%9!#(B

              $B%5!<%S%9$NEPO?$H8!:w(B

              • $B%$%s%?%U%'!<%9(B
              • $BB0@-(B

              $B%k%C%/%"%C%W!&%5!<%S%9<+?H$b!":G=i$+$iCN$i$l$F$$$kI,MW$O$J$$!#(B $B%M%C%H%o!<%/>e$G<+F0E*$KC5$5$l$k!#(B Discovery $B$H(B Join$B!#(B

              $B"!%j!<%9(B/Leasing

              $B%5!<%S%9$O!"1JB3E*$KEPO?$5$l$k$G$O$J$/$F!"(B $BFCDj$N;~4V$@$1MxMQ2DG=$K$J$k!#(B

              Java $B$N%*%V%8%'%/%H$,(B Lease$B!#(B

              $B%j!<%94|4V$O!"1dD9$9$k$3$H$,$G$-$k!#(B $B1dD9$5$l$J$+$C$?(B lease $B$O!"%k%C%/%"%C%W!&%5!<%S%9$+$i:o=|$5$l$k!#(B $BEPO?$5$l$F$$$k%5!<%S%9$rL@<(E*$K:o=|$9$k;EAH$_$O!"B8:_$7$J$$!#(B

              $B%5!<%S%9$,:o=|$5$l$?;~$K$O!"J,;67?%$%Y%s%HG[Aw%5!<%S%9$K$h$j4X78$7$F$$(B $B$k=j$KCN$i$5$l$k!#(B

              $B%H%i%s%6%/%7%g%s$N%$%s%?%U%'!<%9$ODj$a$i$l$F$$$k$,!"6qBNE*$J

              $B"!(BJini$B$r;H$&$N$KI,MW$H$5$l$F$$$k$b$N(B/Requirements to run Jini

              • Java JDK 1.2$B0J9_$N(B JavaVM
              • $B%M%C%H%o!<%/(B Networks
                • TCP/IP
                • $BL5@~(BLAN(wireless LAN)$B!"(BBluetooth
                • USB
              IP$B%"%I%l%9$N3d$jEv$F$O!"(BJini$B$N0lIt$G$O$J$$!#(B

              $B"!%5!<%S%9(B/Services

              $B%5!<%S%9$O!"(BJava $B$N%*%V%8%'%/%H$G

              $B%5!<%S%9$NDs6!

              ServiceIDLister $B%$%s%?%U%'!<%9$r(B implements $B$9$k!#(B

              package com.sun.jini.lookup;
              public interface ServiceIDListener extends java.util.EventListener {
                  void serviceIDNotify(net.jini.core.lookup.ServiceID serviceID);
              }
              
              $B%k%C%/%"%C%W!&%5!<%S%9$+$i%3!<%k%P%C%/$5$l$k!#(B

              $B"!(BDiscovery $B$H(B Join/Discovery and Join

              $B3F%M%C%H%o!<%/$K$O!"%k%C%/%"%C%W!&%5!<%P$rCV$/!#(B

              Discovery
              Jini $B$r;H$&$K$O!"$^$:!"%k%C%/%"%C%W!&%5!<%P$rC5$9!#(B
              Join
              $B%5!<%S%9$NDs6!

              Discovery $B$N

            • $B%^%k%A%-%c%9%H(B($B%0%k!<%WDL?.(B)$B!#(B UDP $B$G(B 224.0.1.85:4160 $B$KMW5a$rEj$2$k!#(B
            • $B%f%K%-%c%9%H(B(IP$B%"%I%l%9$r;vA0$KCN$C$F$$$kI,MW$,$"$k(B)$B!#(B $B%k!<%?$r1[$($F!"%^%k%A%-%c%9%H$,FO$+$J$$HO0O$G$b;H$($k!#(B
            $B%k%C%/%"%C%W!&%5!<%P$O!"5/F0;~!":F5/F0;~!"(B224.0.1.84:4160 $B$K(BMulticast Announcement Protocol $B$G!"MxMQ2DG=@-$r9-9p$9$k!#(B

            $B%5!<%S%9$NDs6!<T$,%M%C%H%o!<%/>e$N%k%C%/%

            $B?^(B1 $B%^%k%A%-%c%9%H$K$h$k(B Discovery/Discovery by multicast

            $B%5!<%S%9$NDs6!<T$,%k%C%/%

            $B?^(B2 Join

            $B"!%5!<%S%9$N%0%k!<%W(B/Grouping services

            $B%5!<%S%9$O!"#1$D0J>e$N%0%k!<%W$KB0$9$k!#(B

            $B%0%k!<%W$O!"L>A0(B($BJ8;zNs(B)$B$G6hJL$5$l$k!#(B

            • "Printer"
            • "Conference Room"
            • "public"
            $BL>A0$H$7$F$O!"(BDNS $BIw$NI=5-$N$b$N$,?d>)$5$l$F$$$k!#(B

            $B"!(BJoinManager($B%5!<%PB&(B)/JoinManager at the server-side

            Discovery $B$H(B Join $B$O!"5,3J>e$O!"%M%C%H%o!<%/!&%W%m%H%3%k$K$J$C$F$$$k!#(B

            Jini $B%Q%C%1!<%8$O!"(BJoinManager $B$H$$$&;2>H%/%i%9$r4^$`!#(B

                public JoinManager(Object obj,  Entry[] attrSets,
                                   ServiceIDListener callback,
                                   LeaseRenewalManager leaseMgr)
                    throws IOException
                public JoinManager(Object obj, Entry[] attrSets, String[] groups,
                                   LookupLocator[] locators,
                                   ServiceIDListener callback,
                                   LeaseRenewalManager leaseMgr )
                    throws IOException
            

            $B"!(BJini$B$N%5!<%P$NNc(B/Example of a Jini server

            import java.rmi.*;
            
            public interface RemoteBall extends Remote {
               public void hit() throws java.rmi.RemoteException;
            }
            
            import java.rmi.*;
            import java.rmi.server.*;
            import net.jini.core.lookup.*;
            import com.sun.jini.lookup.*;
            
            public class Ball extends UnicastRemoteObject 
                              implements RemoteBall, ServiceIDListener {
               public Ball() throws RemoteException {
                  super();
               }
               public void serviceIDNotify(ServiceID id) {
                  System.out.println("ServiceId is "+id);
               }
               public void hit() {
                  System.out.println("Ball has been hit");
               }
            }
            

            import java.rmi.*;
            import net.jini.core.entry.*;
            import net.jini.lookup.entry.*;
            import com.sun.jini.lookup.*;
            import com.sun.jini.lease.*;
            
            public class BallStarter {
               public static void main(String[] args) {
                  try {
                     System.setSecurityManager(new RMISecurityManager());
                     RemoteBall ball = (RemoteBall) new Ball();
                     LeaseRenewalManager renewal = new LeaseRenewalManager();
                     Entry[] attributes = new Entry [] { new Name("Jini enabled ball")};
                     JoinManager join = new JoinManager( ball, attributes, (Ball) ball, renewal );
                     System.out.println("Ball started and registered at Lookup-Server");
            
                  } catch (Exception e) {
                     e.printStackTrace();
                  }
               }
            }
            

            $B"!(BLookup($B%/%i%$%"%s%HB&(B)/Lockup in a client

            $B%/%i%$%"%s%H$O!"%5!<%S%9$rC5$9!#(B

            $B%5!<%S%9$NMxMQ<T$,%k%C%/%

            $B?^(B3 Lookup

            $B%5!<%S%9$O!"
          • ServiceID. 128$B%S%C%H!#%k%C%/%"%C%W!&%5!<%S%9$,@8@.$9$k!#(B
          • $B%$%s%?%U%'!<%9(B( Class $B%*%V%8%'%/%H(B )
          • $BB0@-!#(BJavaSpaces $B$N(B Entry $B%/%i%9$HF1$8!#(B
          $B%5!<%S%9$r8!:w$9$k;~$K(B ServiceTemplate $B$N%*%V%8%'%/%H$r:n@.$9$k!#(B JavaSpaces $B$N$h$&$K!"(Bnull $B$r;XDj$9$l$P!"%o%$%k%I%+!<%I$r0UL#$9$k!#(B
              public ServiceTemplate(ServiceID serviceID,
                                     Class[] serviceTypes,
                                     Entry[] attrSetTemplates)
          
          $B%5!<%S%9(B($B%*%V%8%'%/%H(B)$B$NC5$7J}(B
          1. LookupLocator $B$K$h$j!"%^%k%A%-%c%9%H!"$^$?$O!"(B $B%f%K%-%c%9%H$G(B $B%k%C%/%"%C%W!&%5!<%S%9$rC5$9!#(B
          2. $B%k%C%/%"%C%W!&%5!<%S%9$rMxMQ$9$k$?$a$N!"(BServiceRegistrar $B%*%V%8%'%/%H$r:n$k!#(B
          3. $B%F%s%W%l!<%H$r:n$j!"(BServiceRegistrar $B$KEO$9!#(B
          $B%5!<%S%9$r8+$D$1$k2aDx$G!"%5!<%S%9(B($B%*%V%8%'%/%H(B)$B$N(BRMI $B$N%9%?%V(B($B%/%i%$(B $B%"%s%HB&%9%?%V(B)$B$,E>Aw$5$l$k!#(B

          $B"!%5!<%S%9$NMxMQ(B/Using a service

          $B:G=*E*$K%/%i%$%"%s%H$O!"%5!<%S%9!&%W%m%P%$%@$r(B RMI $B$G8F$S=P$9!#(B

          $B%5!<%S%9$NMxMQ<T$,%5!<%S%9%*%V%8%'%/%H$rDL$8$F%5!<%P$rMxMQ$9$k!#(B

          $B?^(B4 Invoke

          $B"!(BJini$B$N%/%i%$%"%s%H$NNc(B/Example of a Jini client

          import java.rmi.*;
          import net.jini.core.discovery.*;
          import net.jini.core.lookup.*;
          
          public class Bat {
          
             public Ball ball;
          
             public void play(RemoteBall ball) {
                try {
                   ball.hit();
                   System.out.println("I hit the ball");
                } catch (RemoteException e) {
                   System.out.println(e);
                }
             }
          
             public static void main (String[] args) {
                Bat bat = new Bat();
                try {
                   System.setSecurityManager(new RMISecurityManager());
                   LookupLocator locator = new LookupLocator("jini://localhost");
                   ServiceRegistrar registrar = locator.getRegistrar();
                   Class[] classes = new Class[] { RemoteBall.class  };
                   ServiceTemplate template = new ServiceTemplate( null, classes, null);
                   RemoteBall remoteBall = (RemoteBall) registrar.lookup(template);
                   bat.play(remoteBall);
                } catch (Exception e) {
                   e.printStackTrace();
                }
             }
          }
          

          $B"!(BLeasing

          $B?.Mj@-$,Dc$$%M%C%H%o!<%/$H!"$I$&@o$&J}K!$N#1$D!#(B

          lease $B$K$O!"4|8B$,$"$k!#(B

          • $B1dD9$G$-$k(B($BDL>o(B)
          • $BC;=L$b$G$-$k(B

          $B4|8B$ND9$5$O!"8r>D2DG=!#(B $B4|8B$,C;$$(B(1$BJ,0J2

          $B%j!<%9$NMxE@(B

          • $B>pJs$r:G?7$N$b$N$K$G$-$k!#(B
          • $B8E$$>pJs$r0BA4$K>C$9$3$H$,$G$-$k!#(B

          Jini $B$N%5!<%S%9$rDs6!$7$F$$$k%*%V%8%'%/%H$O!"(BLease $B%$%s%?%U%'!<%9$r

          public interface Lease {
              long FOREVER = Long.MAX_VALUE;
          ...
              long getExpiration();
              void renew(long duration)
                  throws LeaseDeniedException, UnknownLeaseException, RemoteException;
              void cancel() throws UnknownLeaseException, RemoteException;
          ...
          }
          
          getExpiration() $B$G!"%j!<%9$N;D$j;~4V$,$o$+$k!#%_%jICC10L!#(B

          renew() $B$G1dD9$9$k!#(B $B1dD9$G$-$J$$;~$K$O!"(BLeaseDeniedException $B$,JV$5$l$k!#(B

          $B$b$&;H$o$J$/$J$C$?;~$K$O!"(Bcancel() $B$G$-$k!#(B $B4|8B@Z$l$HF1$8$3$H$K$J$k!#(B

          $B%j!<%9$N4IM}$K$O!"(BLeaseRenewalManager $B$r;H$&!#(B

          $B"#2A%"%s%1!<%H(B/Course Evaluation Questionnaire

          CS$B@l96!&>pJsM}9)3X0L%W%m%0%i%`$N653X%^%M%8%a%s%H0Q0w2q$G$O!"(B $B650i$N2~A1$N$?$a$K!"3X@8$N3'$5$s$K2A%"%s%1!<%H$r

          $B%"%s%1!<%H$O(BTWINS$B$+$i2sEz$7$F$/$@$5$$!#(B $B

          $BJ#?t$N650w$,9V5A$rC4Ev$7$F$$$k>l9g$O!"

          $B$J$*!"3'$5$s$NI>2A$,@.@S$K1F6A$9$k$3$H$O0l@Z$"$j$^$;$s!#(B $B$^$?!"I>2A7k2L$r650i$N2~A10J30$NL\E*$KMxMQ$9$k$3$H$O$"$j$^$;$s$7!"(B $BI>2A7k2L$r8x3+$9$k>l9g$K$O8D?M$rFCDj$G$-$k$h$&$J>pJs$O4^$a$^$;$s!#(B

          Department of Computer Science/Master's and Doctoral Programs in Computer Science conducts a survey of all students for the purpose of evaluating and improving instruction. Please complete this questionnaire on TWINS between June 20 and July 17.

          Please answer with respect to the overall impression of instruction given in the course regardless of the number of lecturers. Note that opinions or questions concerning individual instructors can be entered in the free-entry cell on the other side of this question sheet.

          These answers will not affect your academic grades. The result will not be used for any purpose other than instruction evaluation and its further improvement. When the summarized information of this questionnaire is released to the public (for FD activities), no private information about you will be included.

          $B"#N}=,LdBj(B(exercise)9 $BJB9T%W%m%0%i%_%s%08@8l(B(2)/Concurrent Programming Languages(2)

          $B!zLdBj(B(901) $B%"%/%?%b%G%k(B/The Actor models

          $B0J2<$NJ8$O!"(BActor $B%b%G%k$K$D$$$F@bL@$7$F$$$k!#(B $B@5$7$$J8$N@hF,$K(B Yes$B!"4V0c$C(B $B$?$b$N$K(B No $B=q$-$J$5$$!#(B

          The following sentences describe the Actor models. Write "Yes" at the beginning of each sentence if it is correct. Write "No" at the beginning of each sentence if it is incorrect.

          • $B%"%/%?$O!"%a%C%;!<%8$r An actor has exactly one mail box to receive messages.
          • $B%"%/%?$O!"%a%C%;!<%8$r An actor can have multiple mail boxes to receive messages.
          • $B%"%/%?$rJ#?t@8@.$9$k$3$H$G!"JB9T@-$r5-=R$G$-$k!#(B
            We can describe concurrency by creating multiple actors.
          • $B%"%/%?$O!"%a%C%;!<%8$r(B1$B$D When an actor receives a message, it cannot receive another message before it performs the "become" operation.

          $B!zLdBj(B(902) $B%"%/%?%b%G%k$NA`:n(B/The operations in the Actor models

          Scala, Kotlin, Elixir, $B$*$h$S(B Ruby Ractor $B$G$O!"(B $B$"$k$B%"%/%?%b%G%k(B $B$K4p$E$-%W%m%0%i%`$r5-=R$9$k$3$H$,$G$-$k!#(B $B$3$l$i$N8@8l$+$i#1$D$rA*$S!"$=$NCf$G%"%/%?%b%G%k$N0J2<$NA`:n$r$I$N$h$&$K5-=R$9$k$+=R$Y$J$5$$!#(B

          In Scala, Kotlin, Elixir, and Ruby Ractor, we can write a program based on a kind of the actor model. Choose one language from these languages, and provide how to describe the following operations in the language.

          • receive
          • send
          • become

          $B!zLdBj(B(903) Prolog$B%W%m%0%i%`Cf$NJBNs@-(B/Concurrency in a Prolog program

          quicksort $B$N%W%m%0%i%`$O!"quicksort program includes two types of parallelism.
          • 2 $B$D$N(B AND $B$G7k$P$l$?=R8l4V$NJBNs@-!#(B
            Parallelsim between two predicates that are connected with "AND".
          • $B%Q%$%W%i%$%sJBNs@-!#(B
            Pipeline parallelism$B!#(B
          $B3FJBNs@-$K$D$$$F!"$=$NJBNs@-$,B8:_$9$k>l=j$r(B1$B$D<($7$J$5$$!#(B For each parallelism, show one place where the parallelism exists.

          $B!zLdBj(B(904) Jini $B$NA`:n(B/Operations in Jini

          Jini$B$N%5!<%P$NNc(B $B$*$h$S(B Jini$B$N%/%i%$%"%s%H$NNc(B $B$N%W%m%0%i%`$+$i!"Example of a Jini server and Example of a Jini client) Example of a Jini client extract the lines that perform the following operations:
          • Join
          • Lookup
          • Invoke (RMI)

          $B!zLdBj(B(905) Jini $B$K$*$1$k%j!<%9(B/Leasing in Jini

          Jini $B$G$O!"%j!<%9$H$$$&9M$(J}$rMQ$$$k!#(B $B$=$NM}M3$r!"(B$BNc$rMQ$$$F(B $B4JC1$K@bL@$7$J$5$$!#(B

          The Jini technology uses the idea of leasing. Describe its reason by using an example.

          $B!zLdBj(B(906) $B2A%"%s%1!<%H(B/Course Evaluation Questionnaire

          $B2A%"%s%1!<%H$r2sEz$9$k(BWeb$B%5%$%H$rEz$($J$5$$!#(B Please provide the website for responding to the course evaluation survey.

          $B2A%"%s%1!<%H$N2sEz4|4V$rEz$($J$5$$!#(B Provide the response period for the course evaluation survey.

          $B2A%"%s%1!<%H$K$D$$$F!"<+J,$NBVEY$r

        • $B%"%s%1!<%H$K2sEz$7$?!#(B I have completed it.
        • $B$3$l$+$i%"%s%1!<%H$K2sEz$9$k!#(B I will completed it.
        • $B2sEz$7$J$$!#(BI will not completed it.
        • $B7h$a$F$$$J$$!#(BI have not decided.
        • $B$=$NB>!#(BOthers.

        Last updated: 2025/06/19 09:32:39
        Yasushi Shinjo / <yas@cs.tsukuba.ac.jp>