force-layout-0.3.0.6: Simple force-directed layout

Copyright(c) 2011 Brent Yorgey
LicenseBSD-style (see LICENSE)
Maintainerbyorgey@cis.upenn.edu
Safe HaskellNone
LanguageHaskell2010

Physics.ForceLayout

Contents

Description

A simple, Haskell-native simulator for doing force-directed layout, e.g. of trees or graphs.

To use, just create an Ensemble like so:

import           Physics.ForceLayout
import qualified Data.Map              as M
import           Data.AffineSpace.Point
import           Data.Default (def)

e :: Ensemble (Double, Double)
e = Ensemble [ (edges,    hookeForce 0.05 4)
             , (allPairs, coulombForce 1)
             ]
             particleMap
  where edges       = [(1,2), (2,3), (2,5), (3,5), (3,4), (4,5)]
        allPairs    = [(x,y) | x <- [1..4], y <- [x+1..5]]
        particleMap = M.fromList . zip [1..]
                    . map (initParticle . P)
                    $ [ (2.0, 3.1), (6.3, 7.2)
                      , (0.3, 4.2), (1.6, -1.1)
                      , (4.8, 2.9)
                      ]

Then run a simulation using either simulate (to get the list of all intermediate states) or forceLayout (to get only the ending state):

e' :: Ensemble (Double, Double)
e' = forceLayout (def & damping     .~ 0.8
                      & energyLimit .~ Just 0.001
                      & stepLimit   .~ Nothing
                 )
                 e

See the diagrams-contrib package (http://github.com/diagrams/diagrams-contrib/) for more examples.

Synopsis

Data structures

data Particle v Source

A particle has a current position, current velocity, and current force acting on it.

Constructors

Particle 

Fields

_pos :: Point v
 
_vel :: v
 
_force :: v
 

Instances

Eq v => Eq (Particle v) 
Show v => Show (Particle v) 

pos :: forall v. Lens' (Particle v) (Point v) Source

vel :: forall v. Lens' (Particle v) v Source

force :: forall v. Lens' (Particle v) v Source

initParticle :: AdditiveGroup v => Point v -> Particle v Source

Create an initial particle at rest at a particular location.

type PID = Int Source

Used to uniquely identify particles.

type Edge = (PID, PID) Source

An edge is a pair of particle identifiers.

data Ensemble v Source

An Ensemble is a physical configuration of particles. It consists of a mapping from particle IDs (unique integers) to particles, and a list of forces that are operative. Each force has a list of edges to which it applies, and is represented by a function giving the force between any two points.

Constructors

Ensemble 

Fields

_forces :: [([Edge], Point v -> Point v -> v)]
 
_particles :: Map PID (Particle v)
 

forces :: forall v. Lens' (Ensemble v) [([Edge], Point v -> Point v -> v)] Source

particles :: forall v. Lens' (Ensemble v) (Map PID (Particle v)) Source

Pre-defined forces

hookeForce :: (InnerSpace v, Floating (Scalar v)) => Scalar v -> Scalar v -> Point v -> Point v -> v Source

hookeForce k l p1 p2 computes the force on p1, assuming that p1 and p2 are connected by a spring with equilibrium length l and spring constant k.

coulombForce :: (InnerSpace v, Floating (Scalar v)) => Scalar v -> Point v -> Point v -> v Source

coulombForce k computes the electrostatic repulsive force between two charged particles, with constant of proportionality k.

distForce :: (InnerSpace v, Floating (Scalar v)) => (Scalar v -> Scalar v) -> Point v -> Point v -> v Source

distForce f p1 p2 computes the force between two points as a multiple of the unit vector in the direction from p1 to p2, given a function f which computes the force's magnitude as a function of the distance between the points.

Running simulations

data ForceLayoutOpts v Source

Options for customizing a simulation.

Constructors

FLOpts 

Fields

_damping :: Scalar v

Damping factor to be applied at each step. Should be between 0 and 1. The default is 0.8.

_energyLimit :: Maybe (Scalar v)

Kinetic energy below which simulation should stop. If Nothing, pay no attention to kinetic energy. The default is Just 0.001.

_stepLimit :: Maybe Int

Maximum number of simulation steps. If Nothing, pay no attention to the number of steps. The default is Just 1000.

simulate :: (InnerSpace v, Ord (Scalar v), Num (Scalar v)) => ForceLayoutOpts v -> Ensemble v -> [Ensemble v] Source

Simulate a starting ensemble according to the given options, producing a list of all the intermediate ensembles. Useful for, e.g., making an animation. Note that the resulting list could be infinite, if a stepLimit is not specified and either the kinetic energy never falls below the specified threshold, or no energy threshold is specified.

forceLayout :: (InnerSpace v, Ord (Scalar v), Num (Scalar v)) => ForceLayoutOpts v -> Ensemble v -> Ensemble v Source

Run a simluation from a starting ensemble, yielding either the first ensemble to have kinetic energy below the energyLimit (if given), or the ensemble that results after a number of steps equal to the stepLimit (if given), whichever comes first. Otherwise forceLayout will not terminate.

Internals

ensembleStep :: VectorSpace v => Scalar v -> Ensemble v -> Ensemble v Source

Simulate one time step for an entire ensemble, with the given damping factor.

particleStep :: VectorSpace v => Scalar v -> Particle v -> Particle v Source

Simulate one time step for a particle (assuming the force acting on it has already been computed), with the given damping factor.

recalcForces :: forall v. AdditiveGroup v => Ensemble v -> Ensemble v Source

Recalculate all the forces acting in the next time step of an ensemble.

kineticEnergy :: (InnerSpace v, Num (Scalar v)) => Ensemble v -> Scalar v Source

Compute the total kinetic energy of an ensemble.