{-# LANGUAGE TemplateHaskell, TypeFamilies, TypeOperators #-}
module Data.Units.US.Misc (
module Data.Units.US.Misc,
Maxwell(..)
) where
import Data.Metrology
import Data.Metrology.TH
import Data.Units.SI
import Data.Units.SI.Prefixes
import Data.Units.CGS
import Data.Constants.Math
import Language.Haskell.TH
declareDerivedUnit "Inch" [t| Foot |] (1/12) (Just "in")
declareDerivedUnit "Yard" [t| Foot |] 3 (Just "yd")
declareDerivedUnit "Mile" [t| Foot |] 5280 (Just "mi")
declareDerivedUnit "Angstrom" [t| Nano :@ Meter |] 0.1 (Just "Å")
declareDerivedUnit "Hand" [t| Inch |] 4 (Just "hand")
declareDerivedUnit "Mil" [t| Inch |] 0.001 (Just "mil")
declareDerivedUnit "Point" [t| Inch |] 0.013837 (Just "p")
declareDerivedUnit "Pica" [t| Point |] 12 (Just "P")
declareDerivedUnit "Fathom" [t| Yard |] 2 (Just "ftm")
declareDerivedUnit "Cable" [t| Fathom |] 120 (Just "cb")
declareDerivedUnit "NauticalMile" [t| Kilo :@ Meter |] 1.852 (Just "NM")
declareDerivedUnit "Knot" [t| NauticalMile :/ Hour |] 1 (Just "kn")
declareDerivedUnit "Atmosphere" [t| Kilo :@ Pascal |] 101.325 (Just "atm")
declareDerivedUnit "Bar" [t| Kilo :@ Pascal |] 100 (Just "bar")
declareDerivedUnit "MillimeterOfMercury"
[t| Pascal |] 133.322387415 (Just "mmHg")
declareDerivedUnit "Torr" [t| Atmosphere |] (1/760) (Just "Torr")
declareDerivedUnit "Calorie" [t| Joule |] 4.184 (Just "cal")
declareDerivedUnit "FoodCalorie" [t| Kilo :@ Calorie |] 1 (Just "Cal")
declareDerivedUnit "Therm" [t| Mega :@ Joule |] 105.4804 (Just "thm")
declareDerivedUnit "Btu" [t| Joule |] 1055.05585262 (Just "btu")
declareDerivedUnit "Horsepower" [t| Watt |] 746 (Just "hp")
declareDerivedUnit "Rankine" [t| Kelvin |] (5/9) (Just "°R")
declareDerivedUnit "PoundForce" [t| Newton |] 4.4482216152605 (Just "lbf")
declareDerivedUnit "Slug" [t| PoundForce :* (Second :^ Two) :/ Foot |]
1 (Just "slug")
declareDerivedUnit "Oersted" [t| Ampere :/ Meter |]
(1000 / (4 * piR)) (Just "Oe")
lengths :: [Name]
lengths :: [Name]
lengths = [ ''Foot, ''Inch, ''Yard, ''Mile ]