ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE-4/src/UseTheForce/DarkSide/sticky.F90
(Generate patch)

Comparing trunk/OOPSE-4/src/UseTheForce/DarkSide/sticky.F90 (file contents):
Revision 2189 by chuckv, Wed Apr 13 20:36:45 2005 UTC vs.
Revision 2232 by chrisfen, Wed May 18 19:06:22 2005 UTC

# Line 50 | Line 50
50   !! @author Matthew Meineke
51   !! @author Christopher Fennell
52   !! @author J. Daniel Gezelter
53 < !! @version $Id: sticky.F90,v 1.6 2005-04-13 20:36:45 chuckv Exp $, $Date: 2005-04-13 20:36:45 $, $Name: not supported by cvs2svn $, $Revision: 1.6 $
53 > !! @version $Id: sticky.F90,v 1.12 2005-05-18 19:06:22 chrisfen Exp $, $Date: 2005-05-18 19:06:22 $, $Name: not supported by cvs2svn $, $Revision: 1.12 $
54  
55   module sticky
56  
# Line 70 | Line 70 | module sticky
70    public :: newStickyType
71    public :: do_sticky_pair
72    public :: destroyStickyTypes
73 +  public :: do_sticky_power_pair
74  
75  
76    type :: StickyList
# Line 83 | Line 84 | module sticky
84       real( kind = dp ) :: rup = 0.0_dp
85       real( kind = dp ) :: rbig = 0.0_dp
86    end type StickyList
87 <  
87 >
88    type(StickyList), dimension(:),allocatable :: StickyMap
89  
90   contains
# Line 97 | Line 98 | contains
98      real( kind = dp ), intent(in) :: rlp, rup
99      integer :: nATypes, myATID
100  
101 <    
101 >
102      isError = 0
103      myATID = getFirstMatchingElement(atypes, "c_ident", c_ident)
104 <    
104 >
105      !! Be simple-minded and assume that we need a StickyMap that
106      !! is the same size as the total number of atom types
107  
# Line 129 | Line 130 | contains
130      StickyMap(myATID)%c_ident = c_ident
131  
132      ! we could pass all 5 parameters if we felt like it...
133 <    
133 >
134      StickyMap(myATID)%w0 = w0
135      StickyMap(myATID)%v0 = v0
136      StickyMap(myATID)%v0p = v0p
# Line 143 | Line 144 | contains
144      else
145         StickyMap(myATID)%rbig = StickyMap(myATID)%rup
146      endif
147 <  
147 >
148      return
149    end subroutine newStickyType
150  
151    subroutine do_sticky_pair(atom1, atom2, d, rij, r2, sw, vpair, fpair, &
152         pot, A, f, t, do_pot)
153 <    
153 >
154      !! This routine does only the sticky portion of the SSD potential
155      !! [Chandra and Ichiye, J. Chem. Phys. 111, 2701 (1999)].
156      !! The Lennard-Jones and dipolar interaction must be handled separately.
157 <    
157 >
158      !! We assume that the rotation matrices have already been calculated
159      !! and placed in the A array.
160  
# Line 187 | Line 188 | contains
188      real (kind=dp) :: radcomxj, radcomyj, radcomzj
189      integer :: id1, id2
190      integer :: me1, me2
191 <   real (kind=dp) :: w0, v0, v0p, rl, ru, rlp, rup, rbig
191 >    real (kind=dp) :: w0, v0, v0p, rl, ru, rlp, rup, rbig
192  
193 < if (.not.allocated(StickyMap)) then
193 >    if (.not.allocated(StickyMap)) then
194         call handleError("sticky", "no StickyMap was present before first call of do_sticky_pair!")
195         return
196      end if
197 <    
197 >
198   #ifdef IS_MPI
199      me1 = atid_Row(atom1)
200      me2 = atid_Col(atom2)
# Line 461 | Line 462 | if (.not.allocated(StickyMap)) then
462         id1 = atom1
463         id2 = atom2
464   #endif
465 <      
465 >
466         if (molMembershipList(id1) .ne. molMembershipList(id2)) then
467 <          
467 >
468            fpair(1) = fpair(1) + fxradial
469            fpair(2) = fpair(2) + fyradial
470            fpair(3) = fpair(3) + fzradial
471 <          
471 >
472         endif
473      endif
474    end subroutine do_sticky_pair
475  
476    !! calculates the switching functions and their derivatives for a given
477    subroutine calc_sw_fnc(r, rl, ru, rlp, rup, s, sp, dsdr, dspdr)
478 <    
478 >
479      real (kind=dp), intent(in) :: r, rl, ru, rlp, rup
480      real (kind=dp), intent(inout) :: s, sp, dsdr, dspdr
481 <    
481 >
482      ! distances must be in angstroms
483 <    
483 >
484      if (r.lt.rl) then
485         s = 1.0d0
486         dsdr = 0.0d0
# Line 503 | Line 504 | if (.not.allocated(StickyMap)) then
504              ((rup - rlp)**3)
505         dspdr = 6.0d0*(r-rup)*(r-rlp)/((rup - rlp)**3)      
506      endif
507 <    
507 >
508      return
509    end subroutine calc_sw_fnc
510  
511    subroutine destroyStickyTypes()  
512      if(allocated(StickyMap)) deallocate(StickyMap)
513    end subroutine destroyStickyTypes
514 +  
515 +    subroutine do_sticky_power_pair(atom1, atom2, d, rij, r2, sw, vpair, fpair, &
516 +       pot, A, f, t, do_pot, ebalance)
517 +    !! We assume that the rotation matrices have already been calculated
518 +    !! and placed in the A array.
519 +
520 +    !! i and j are pointers to the two SSD atoms
521 +
522 +    integer, intent(in) :: atom1, atom2
523 +    real (kind=dp), intent(inout) :: rij, r2
524 +    real (kind=dp), dimension(3), intent(in) :: d
525 +    real (kind=dp), dimension(3), intent(inout) :: fpair
526 +    real (kind=dp) :: pot, vpair, sw
527 +    real (kind=dp), dimension(9,nLocal) :: A
528 +    real (kind=dp), dimension(3,nLocal) :: f
529 +    real (kind=dp), dimension(3,nLocal) :: t
530 +    real (kind=dp), intent(in) :: ebalance
531 +    logical, intent(in) :: do_pot
532 +
533 +    real (kind=dp) :: xi, yi, zi, xj, yj, zj, xi2, yi2, zi2, xj2, yj2, zj2
534 +    real (kind=dp) :: xihat, yihat, zihat, xjhat, yjhat, zjhat
535 +    real (kind=dp) :: rI, rI2, rI3, rI4, rI5, rI6, rI7, s, sp, dsdr, dspdr
536 +    real (kind=dp) :: wi, wj, w, wi2, wj2
537 +    real (kind=dp) :: dwidx, dwidy, dwidz, dwjdx, dwjdy, dwjdz
538 +    real (kind=dp) :: dwidux, dwiduy, dwiduz, dwjdux, dwjduy, dwjduz
539 +    real (kind=dp) :: drdx, drdy, drdz
540 +    real (kind=dp) :: txi, tyi, tzi, txj, tyj, tzj
541 +    real (kind=dp) :: fxii, fyii, fzii, fxjj, fyjj, fzjj
542 +    real (kind=dp) :: fxij, fyij, fzij, fxji, fyji, fzji      
543 +    real (kind=dp) :: fxradial, fyradial, fzradial
544 +    real (kind=dp) :: rijtest, rjitest
545 +    real (kind=dp) :: radcomxi, radcomyi, radcomzi
546 +    real (kind=dp) :: radcomxj, radcomyj, radcomzj
547 +    integer :: id1, id2
548 +    integer :: me1, me2
549 +    real (kind=dp) :: w0, v0, v0p, rl, ru, rlp, rup, rbig
550 +    real (kind=dp) :: zi3, zi4, zi5, zj3, zj4, zj5
551 +    real (kind=dp) :: frac1, frac2
552 +          
553 +    if (.not.allocated(StickyMap)) then
554 +       call handleError("sticky", "no StickyMap was present before first call of do_sticky_power_pair!")
555 +       return
556 +    end if
557 +
558 + #ifdef IS_MPI
559 +    me1 = atid_Row(atom1)
560 +    me2 = atid_Col(atom2)
561 + #else
562 +    me1 = atid(atom1)
563 +    me2 = atid(atom2)
564 + #endif
565 +
566 +    if (me1.eq.me2) then
567 +       w0  = StickyMap(me1)%w0
568 +       v0  = StickyMap(me1)%v0
569 +       v0p = StickyMap(me1)%v0p
570 +       rl  = StickyMap(me1)%rl
571 +       ru  = StickyMap(me1)%ru
572 +       rlp = StickyMap(me1)%rlp
573 +       rup = StickyMap(me1)%rup
574 +       rbig = StickyMap(me1)%rbig
575 +    else
576 +       ! This is silly, but if you want 2 sticky types in your
577 +       ! simulation, we'll let you do it with the Lorentz-
578 +       ! Berthelot mixing rules.
579 +       ! (Warning: you'll be SLLLLLLLLLLLLLLLOOOOOOOOOOWWWWWWWWWWW)
580 +       rl   = 0.5_dp * ( StickyMap(me1)%rl + StickyMap(me2)%rl )
581 +       ru   = 0.5_dp * ( StickyMap(me1)%ru + StickyMap(me2)%ru )
582 +       rlp  = 0.5_dp * ( StickyMap(me1)%rlp + StickyMap(me2)%rlp )
583 +       rup  = 0.5_dp * ( StickyMap(me1)%rup + StickyMap(me2)%rup )
584 +       rbig = max(ru, rup)
585 +       w0  = sqrt( StickyMap(me1)%w0   * StickyMap(me2)%w0  )
586 +       v0  = sqrt( StickyMap(me1)%v0   * StickyMap(me2)%v0  )
587 +       v0p = sqrt( StickyMap(me1)%v0p  * StickyMap(me2)%v0p )
588 +    endif
589 +
590 +    if ( rij .LE. rbig ) then
591 +
592 +       rI = 1.0d0/rij
593 +       rI2 = rI*rI
594 +       rI3 = rI2*rI
595 +       rI4 = rI2*rI2
596 +       rI5 = rI3*rI2
597 +       rI6 = rI3*rI3
598 +       rI7 = rI4*rI3
599 +              
600 +       drdx = d(1) * rI
601 +       drdy = d(2) * rI
602 +       drdz = d(3) * rI
603 +
604 + #ifdef IS_MPI
605 +       ! rotate the inter-particle separation into the two different
606 +       ! body-fixed coordinate systems:
607 +
608 +       xi = A_row(1,atom1)*d(1) + A_row(2,atom1)*d(2) + A_row(3,atom1)*d(3)
609 +       yi = A_row(4,atom1)*d(1) + A_row(5,atom1)*d(2) + A_row(6,atom1)*d(3)
610 +       zi = A_row(7,atom1)*d(1) + A_row(8,atom1)*d(2) + A_row(9,atom1)*d(3)
611 +
612 +       ! negative sign because this is the vector from j to i:
613 +
614 +       xj = -(A_Col(1,atom2)*d(1) + A_Col(2,atom2)*d(2) + A_Col(3,atom2)*d(3))
615 +       yj = -(A_Col(4,atom2)*d(1) + A_Col(5,atom2)*d(2) + A_Col(6,atom2)*d(3))
616 +       zj = -(A_Col(7,atom2)*d(1) + A_Col(8,atom2)*d(2) + A_Col(9,atom2)*d(3))
617 + #else
618 +       ! rotate the inter-particle separation into the two different
619 +       ! body-fixed coordinate systems:
620 +
621 +       xi = a(1,atom1)*d(1) + a(2,atom1)*d(2) + a(3,atom1)*d(3)
622 +       yi = a(4,atom1)*d(1) + a(5,atom1)*d(2) + a(6,atom1)*d(3)
623 +       zi = a(7,atom1)*d(1) + a(8,atom1)*d(2) + a(9,atom1)*d(3)
624 +
625 +       ! negative sign because this is the vector from j to i:
626 +
627 +       xj = -(a(1,atom2)*d(1) + a(2,atom2)*d(2) + a(3,atom2)*d(3))
628 +       yj = -(a(4,atom2)*d(1) + a(5,atom2)*d(2) + a(6,atom2)*d(3))
629 +       zj = -(a(7,atom2)*d(1) + a(8,atom2)*d(2) + a(9,atom2)*d(3))
630 + #endif
631 +
632 +       xi2 = xi*xi
633 +       yi2 = yi*yi
634 +       zi2 = zi*zi
635 +       zi3 = zi2*zi
636 +       zi4 = zi2*zi2
637 +       zi5 = zi3*zi2
638 +       xihat = xi*rI
639 +       yihat = yi*rI
640 +       zihat = zi*rI
641 +      
642 +       xj2 = xj*xj
643 +       yj2 = yj*yj
644 +       zj2 = zj*zj
645 +       zj3 = zj2*zj
646 +       zj4 = zj2*zj2
647 +       zj5 = zj3*zj2
648 +       xjhat = xj*rI
649 +       yjhat = yj*rI
650 +       zjhat = zj*rI
651 +      
652 +       call calc_sw_fnc(rij, rl, ru, rlp, rup, s, sp, dsdr, dspdr)
653 +          
654 +       frac1 = 1.5d0
655 +       frac2 = 0.5d0
656 +      
657 +       wi = 2.0d0*(xi2-yi2)*zi*rI3
658 +       wj = 2.0d0*(xj2-yj2)*zj*rI3
659 +      
660 +       wi2 = wi*wi
661 +       wj2 = wj*wj
662 +
663 +       w = frac1*wi*wi2 + frac2*wi + frac1*wj*wj2 + frac2*wj
664 +
665 +       vpair = vpair + 0.5d0*(v0*s*w) + ebalance
666 +      
667 +       if (do_pot) then
668 + #ifdef IS_MPI
669 +         pot_row(atom1) = pot_row(atom1) + 0.25d0*(v0*s*w)*sw
670 +         pot_col(atom2) = pot_col(atom2) + 0.25d0*(v0*s*w)*sw
671 + #else
672 +         pot = pot + 0.5d0*(v0*s*w)*sw + ebalance
673 + #endif  
674 +       endif
675 +
676 +       dwidx = ( 4.0d0*xi*zi*rI3 - 6.0d0*xi*zi*(xi2-yi2)*rI5 )
677 +       dwidy = ( -4.0d0*yi*zi*rI3 - 6.0d0*yi*zi*(xi2-yi2)*rI5 )
678 +       dwidz = ( 2.0d0*(xi2-yi2)*rI3 - 6.0d0*zi2*(xi2-yi2)*rI5 )
679 +      
680 +       dwidx = frac1*3.0d0*wi2*dwidx + frac2*dwidx
681 +       dwidy = frac1*3.0d0*wi2*dwidy + frac2*dwidy
682 +       dwidz = frac1*3.0d0*wi2*dwidz + frac2*dwidz
683 +
684 +       dwjdx = ( 4.0d0*xj*zj*rI3  - 6.0d0*xj*zj*(xj2-yj2)*rI5 )
685 +       dwjdy = ( -4.0d0*yj*zj*rI3  - 6.0d0*yj*zj*(xj2-yj2)*rI5 )
686 +       dwjdz = ( 2.0d0*(xj2-yj2)*rI3  - 6.0d0*zj2*(xj2-yj2)*rI5 )
687 +
688 +       dwjdx = frac1*3.0d0*wj2*dwjdx + frac2*dwjdx
689 +       dwjdy = frac1*3.0d0*wj2*dwjdy + frac2*dwjdy
690 +       dwjdz = frac1*3.0d0*wj2*dwjdz + frac2*dwjdz
691 +      
692 +       dwidux = ( 4.0d0*(yi*zi2 + 0.5d0*yi*(xi2-yi2))*rI3 )
693 +       dwiduy = ( 4.0d0*(xi*zi2 - 0.5d0*xi*(xi2-yi2))*rI3 )
694 +       dwiduz = ( -8.0d0*xi*yi*zi*rI3 )
695 +
696 +       dwidux = frac1*3.0d0*wi2*dwidux + frac2*dwidux
697 +       dwiduy = frac1*3.0d0*wi2*dwiduy + frac2*dwiduy
698 +       dwiduz = frac1*3.0d0*wi2*dwiduz + frac2*dwiduz
699 +
700 +       dwjdux = ( 4.0d0*(yj*zj2 + 0.5d0*yj*(xj2-yj2))*rI3 )
701 +       dwjduy = ( 4.0d0*(xj*zj2 - 0.5d0*xj*(xj2-yj2))*rI3 )
702 +       dwjduz = ( -8.0d0*xj*yj*zj*rI3 )
703 +
704 +       dwjdux = frac1*3.0d0*wj2*dwjdux + frac2*dwjdux
705 +       dwjduy = frac1*3.0d0*wj2*dwjduy + frac2*dwjduy
706 +       dwjduz = frac1*3.0d0*wj2*dwjduz + frac2*dwjduz
707 +
708 +       ! do the torques first since they are easy:
709 +       ! remember that these are still in the body fixed axes
710 +
711 +       txi = 0.5d0*(v0*s*dwidux)*sw
712 +       tyi = 0.5d0*(v0*s*dwiduy)*sw
713 +       tzi = 0.5d0*(v0*s*dwiduz)*sw
714 +
715 +       txj = 0.5d0*(v0*s*dwjdux)*sw
716 +       tyj = 0.5d0*(v0*s*dwjduy)*sw
717 +       tzj = 0.5d0*(v0*s*dwjduz)*sw
718 +
719 +       ! go back to lab frame using transpose of rotation matrix:
720 +
721 + #ifdef IS_MPI
722 +       t_Row(1,atom1) = t_Row(1,atom1) + a_Row(1,atom1)*txi + &
723 +            a_Row(4,atom1)*tyi + a_Row(7,atom1)*tzi
724 +       t_Row(2,atom1) = t_Row(2,atom1) + a_Row(2,atom1)*txi + &
725 +            a_Row(5,atom1)*tyi + a_Row(8,atom1)*tzi
726 +       t_Row(3,atom1) = t_Row(3,atom1) + a_Row(3,atom1)*txi + &
727 +            a_Row(6,atom1)*tyi + a_Row(9,atom1)*tzi
728 +
729 +       t_Col(1,atom2) = t_Col(1,atom2) + a_Col(1,atom2)*txj + &
730 +            a_Col(4,atom2)*tyj + a_Col(7,atom2)*tzj
731 +       t_Col(2,atom2) = t_Col(2,atom2) + a_Col(2,atom2)*txj + &
732 +            a_Col(5,atom2)*tyj + a_Col(8,atom2)*tzj
733 +       t_Col(3,atom2) = t_Col(3,atom2) + a_Col(3,atom2)*txj + &
734 +            a_Col(6,atom2)*tyj + a_Col(9,atom2)*tzj
735 + #else
736 +       t(1,atom1) = t(1,atom1) + a(1,atom1)*txi + a(4,atom1)*tyi + a(7,atom1)*tzi
737 +       t(2,atom1) = t(2,atom1) + a(2,atom1)*txi + a(5,atom1)*tyi + a(8,atom1)*tzi
738 +       t(3,atom1) = t(3,atom1) + a(3,atom1)*txi + a(6,atom1)*tyi + a(9,atom1)*tzi
739 +
740 +       t(1,atom2) = t(1,atom2) + a(1,atom2)*txj + a(4,atom2)*tyj + a(7,atom2)*tzj
741 +       t(2,atom2) = t(2,atom2) + a(2,atom2)*txj + a(5,atom2)*tyj + a(8,atom2)*tzj
742 +       t(3,atom2) = t(3,atom2) + a(3,atom2)*txj + a(6,atom2)*tyj + a(9,atom2)*tzj
743 + #endif    
744 +       ! Now, on to the forces:
745 +
746 +       ! first rotate the i terms back into the lab frame:
747 +
748 +       radcomxi = (v0*s*dwidx)*sw
749 +       radcomyi = (v0*s*dwidy)*sw
750 +       radcomzi = (v0*s*dwidz)*sw
751 +
752 +       radcomxj = (v0*s*dwjdx)*sw
753 +       radcomyj = (v0*s*dwjdy)*sw
754 +       radcomzj = (v0*s*dwjdz)*sw
755 +
756 + #ifdef IS_MPI    
757 +       fxii = a_Row(1,atom1)*(radcomxi) + &
758 +            a_Row(4,atom1)*(radcomyi) + &
759 +            a_Row(7,atom1)*(radcomzi)
760 +       fyii = a_Row(2,atom1)*(radcomxi) + &
761 +            a_Row(5,atom1)*(radcomyi) + &
762 +            a_Row(8,atom1)*(radcomzi)
763 +       fzii = a_Row(3,atom1)*(radcomxi) + &
764 +            a_Row(6,atom1)*(radcomyi) + &
765 +            a_Row(9,atom1)*(radcomzi)
766 +
767 +       fxjj = a_Col(1,atom2)*(radcomxj) + &
768 +            a_Col(4,atom2)*(radcomyj) + &
769 +            a_Col(7,atom2)*(radcomzj)
770 +       fyjj = a_Col(2,atom2)*(radcomxj) + &
771 +            a_Col(5,atom2)*(radcomyj) + &
772 +            a_Col(8,atom2)*(radcomzj)
773 +       fzjj = a_Col(3,atom2)*(radcomxj)+ &
774 +            a_Col(6,atom2)*(radcomyj) + &
775 +            a_Col(9,atom2)*(radcomzj)
776 + #else
777 +       fxii = a(1,atom1)*(radcomxi) + &
778 +            a(4,atom1)*(radcomyi) + &
779 +            a(7,atom1)*(radcomzi)
780 +       fyii = a(2,atom1)*(radcomxi) + &
781 +            a(5,atom1)*(radcomyi) + &
782 +            a(8,atom1)*(radcomzi)
783 +       fzii = a(3,atom1)*(radcomxi) + &
784 +            a(6,atom1)*(radcomyi) + &
785 +            a(9,atom1)*(radcomzi)
786 +
787 +       fxjj = a(1,atom2)*(radcomxj) + &
788 +            a(4,atom2)*(radcomyj) + &
789 +            a(7,atom2)*(radcomzj)
790 +       fyjj = a(2,atom2)*(radcomxj) + &
791 +            a(5,atom2)*(radcomyj) + &
792 +            a(8,atom2)*(radcomzj)
793 +       fzjj = a(3,atom2)*(radcomxj)+ &
794 +            a(6,atom2)*(radcomyj) + &
795 +            a(9,atom2)*(radcomzj)
796 + #endif
797 +
798 +       fxij = -fxii
799 +       fyij = -fyii
800 +       fzij = -fzii
801 +
802 +       fxji = -fxjj
803 +       fyji = -fyjj
804 +       fzji = -fzjj
805 +
806 +       ! now assemble these with the radial-only terms:
807 +
808 +       fxradial = 0.5d0*(v0*dsdr*w*drdx + fxii + fxji + ebalance*xihat)
809 +       fyradial = 0.5d0*(v0*dsdr*w*drdy + fyii + fyji + ebalance*yihat)
810 +       fzradial = 0.5d0*(v0*dsdr*w*drdz + fzii + fzji + ebalance*zihat)
811 +
812 + #ifdef IS_MPI
813 +       f_Row(1,atom1) = f_Row(1,atom1) + fxradial
814 +       f_Row(2,atom1) = f_Row(2,atom1) + fyradial
815 +       f_Row(3,atom1) = f_Row(3,atom1) + fzradial
816 +
817 +       f_Col(1,atom2) = f_Col(1,atom2) - fxradial
818 +       f_Col(2,atom2) = f_Col(2,atom2) - fyradial
819 +       f_Col(3,atom2) = f_Col(3,atom2) - fzradial
820 + #else
821 +       f(1,atom1) = f(1,atom1) + fxradial
822 +       f(2,atom1) = f(2,atom1) + fyradial
823 +       f(3,atom1) = f(3,atom1) + fzradial
824 +
825 +       f(1,atom2) = f(1,atom2) - fxradial
826 +       f(2,atom2) = f(2,atom2) - fyradial
827 +       f(3,atom2) = f(3,atom2) - fzradial
828 + #endif
829 +
830 + #ifdef IS_MPI
831 +       id1 = AtomRowToGlobal(atom1)
832 +       id2 = AtomColToGlobal(atom2)
833 + #else
834 +       id1 = atom1
835 +       id2 = atom2
836 + #endif
837 +
838 +       if (molMembershipList(id1) .ne. molMembershipList(id2)) then
839 +
840 +          fpair(1) = fpair(1) + fxradial
841 +          fpair(2) = fpair(2) + fyradial
842 +          fpair(3) = fpair(3) + fzradial
843 +
844 +       endif
845 +    endif
846 +  end subroutine do_sticky_power_pair
847 +
848   end module sticky

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines