Skip to content

Instantly share code, notes, and snippets.

@bshlgrs
Last active June 7, 2020 05:42
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save bshlgrs/c8e6fea1818fdeb7dc461d5e0ff78c17 to your computer and use it in GitHub Desktop.
Save bshlgrs/c8e6fea1818fdeb7dc461d5e0ff78c17 to your computer and use it in GitHub Desktop.
{-# LANGUAGE MultiParamTypeClasses, GADTs, FlexibleInstances #-}
{-
Here's my summary of the structure of QFT.
Note that the way I've written things is probably deeply offensive to physicists, because I treat time separately from other dimensions.
I've done it this way because it makes the relationships between the ideas IMO more obvious.
TODO, other interesting things to try to mention:
- More about the restrictions on possible Lagrangians (from Lorentz invariance and renormalizeability)
- Gauge theories
- maybe try to talk about Feynman diagrams
-}
import Data.Complex
-- Theories give you a rule for evolving a state forward in time.
-- (More generally they're a rule that judges whether a trajectory is legitimate or not.)
newtype Theory s = Theory {
-- evolve a state forward for a given amount of time
evolve :: Float -> s -> s
}
type Position = (Float, Float, Float)
-- A field has a value at every position in space. Eg https://en.wikipedia.org/wiki/Vector_field, https://en.wikipedia.org/wiki/Scalar_field
type Field x = Position -> x
-- A wavefunction assigns a complex number to every value in some space.
-- One way of looking at this is thinking of x as the basis of the vector space of wavefunctions.
-- LAW: The sum of the squared norm of the wavefunction over its domain must equal 1.
type Wavefunction x = x -> Complex Float
-- In quantum mechanics, the Hamiltonian takes two "basis vectors" from the underlying space and tells you
-- the "energy between them". I don't know a good way to describe this.
type QMHamiltonian x = x -> x -> Float
qm :: QMHamiltonian x -> Theory (Wavefunction x)
-- The time independent Schrodinger equation tells us how to evolve a wavefunction through time.
qm = undefined -- https://en.wikipedia.org/wiki/Schr%C3%B6dinger_equation#Time-dependent_equation
--
qftHamiltonianFromLagrangianDensity :: LorentzTransformable x => LorentzScalarExpr x -> QMHamiltonian (Field x)
qftHamiltonianFromLagrangianDensity lagrangianDensity = undefined -- do the Legendre transform, integrate over space
-- We can evolve our quantum fields through time using the time-dependent Schrodinger equation, given a
-- Lagrangian density (which describes the local energy of a field).
-- For this to be relativistically valid, we need our field values to be Lorentz transformable. Otherwise our predictions
-- would definitely not be Loretz invariant.
qft :: LorentzTransformable x => LorentzScalarExpr x -> Theory (Wavefunction (Field x))
qft lagrangianDensity = qm (qftHamiltonianFromLagrangianDensity lagrangianDensity)
data LorentzTransformation = LorentzTransformation { lt :: Float, lx :: Float, ly :: Float, lz :: Float }
instance Semigroup LorentzTransformation where
(<>) = undefined
instance Monoid LorentzTransformation where
mempty = LorentzTransformation 0 0 0 0
class LorentzTransformable x where
-- Law: lorentzTransform t1 (lorentzTransform t2 x) == lorentTransform (t1 <> t2) x
lorentzTransform :: LorentzTransformation -> x -> x
instance (LorentzTransformable x, LorentzTransformable y) => LorentzTransformable (x, y) where
lorentzTransform l (x, y) = (lorentzTransform l x, lorentzTransform l y)
-- Other instances of LorentzTransformable:
-- - Scalars (spin 0 particles like Higgs boson, W and Z bosons)
instance LorentzTransformable Float where
lorentzTransform _ x = x
instance LorentzTransformable (Complex Float) where
lorentzTransform _ x = x
-- - Spinors (spin 1/2 particles like electrons, quarks, neutrinos)
-- - Vectors (spin 1 particles like photons, gluons)
data LorentzScalarExpr x where
-- LAW: To use f as a LorentzScalarExpr, you must have
-- f x = f (lorentzTransform t x)
LorentzScalarExpr :: (LorentzTransformable x) => (x -> Float) -> LorentzScalarExpr x
instance VectorSpace Float (LorentzScalarExpr x)
class VectorSpace scalar vector where
-- the obvious definition
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment