Copyright | (C) 2013 Richard Eisenberg |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | Richard Eisenberg (rae@cs.brynmawr.edu) |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
This module defines American customary units that don't fit into other categories.
Included are all units mentioned here: http://en.wikipedia.org/wiki/United_States_customary_units Where possible, conversion rates have been independently verified at a US government website. However, Wikipedia's base is much better organized than any government resource immediately available. The US government references used are as follows: http://nist.gov/pml/wmd/metric/upload/SP1038.pdf http://nist.gov/pml/wmd/pubs/upload/appc-14-hb44-final.pdf
Synopsis
- data Foot = Foot
- data Inch = Inch
- data Yard = Yard
- data Mile = Mile
- data Angstrom = Angstrom
- data Hand = Hand
- data Mil = Mil
- data Point = Point
- data Pica = Pica
- data Fathom = Fathom
- data Cable = Cable
- data NauticalMile = NauticalMile
- data Knot = Knot
- data Atmosphere = Atmosphere
- data Bar = Bar
- data MillimeterOfMercury = MillimeterOfMercury
- data Torr = Torr
- data Calorie = Calorie
- data FoodCalorie = FoodCalorie
- data Therm = Therm
- data Btu = Btu
- data Horsepower = Horsepower
- data Rankine = Rankine
- data PoundForce = PoundForce
- data Slug = Slug
- data Oersted = Oersted
- lengths :: [Name]
- data Maxwell = Maxwell
Documentation
Instances
Show Foot Source # | |
Unit Foot Source # | |
Defined in Data.Units.US.Misc conversionRatio :: Foot -> Rational # canonicalConvRatio :: Foot -> Rational | |
type UnitFactorsOf Foot Source # | |
Defined in Data.Units.US.Misc | |
type DimOfUnit Foot Source # | |
type BaseUnit Foot Source # | |
Defined in Data.Units.US.Misc |
Instances
Show Inch Source # | |
Unit Inch Source # | |
Defined in Data.Units.US.Misc conversionRatio :: Inch -> Rational # canonicalConvRatio :: Inch -> Rational | |
type UnitFactorsOf Inch Source # | |
Defined in Data.Units.US.Misc | |
type DimOfUnit Inch Source # | |
type BaseUnit Inch Source # | |
Defined in Data.Units.US.Misc |
Instances
Show Yard Source # | |
Unit Yard Source # | |
Defined in Data.Units.US.Misc conversionRatio :: Yard -> Rational # canonicalConvRatio :: Yard -> Rational | |
type UnitFactorsOf Yard Source # | |
Defined in Data.Units.US.Misc | |
type DimOfUnit Yard Source # | |
type BaseUnit Yard Source # | |
Defined in Data.Units.US.Misc |
Instances
Show Mile Source # | |
Unit Mile Source # | |
Defined in Data.Units.US.Misc conversionRatio :: Mile -> Rational # canonicalConvRatio :: Mile -> Rational | |
type UnitFactorsOf Mile Source # | |
Defined in Data.Units.US.Misc | |
type DimOfUnit Mile Source # | |
type BaseUnit Mile Source # | |
Defined in Data.Units.US.Misc |
Instances
Show Angstrom Source # | |
Unit Angstrom Source # | |
Defined in Data.Units.US.Misc conversionRatio :: Angstrom -> Rational # | |
type UnitFactorsOf Angstrom Source # | |
Defined in Data.Units.US.Misc type UnitFactorsOf Angstrom = If (IsCanonical Angstrom) '['F Angstrom One] (UnitFactorsOf (BaseUnit Angstrom)) | |
type DimOfUnit Angstrom Source # | |
type BaseUnit Angstrom Source # | |
Instances
Show Hand Source # | |
Unit Hand Source # | |
Defined in Data.Units.US.Misc conversionRatio :: Hand -> Rational # canonicalConvRatio :: Hand -> Rational | |
type UnitFactorsOf Hand Source # | |
Defined in Data.Units.US.Misc | |
type DimOfUnit Hand Source # | |
type BaseUnit Hand Source # | |
Defined in Data.Units.US.Misc |
Instances
Show Mil Source # | |
Unit Mil Source # | |
Defined in Data.Units.US.Misc conversionRatio :: Mil -> Rational # canonicalConvRatio :: Mil -> Rational | |
type UnitFactorsOf Mil Source # | |
Defined in Data.Units.US.Misc | |
type DimOfUnit Mil Source # | |
type BaseUnit Mil Source # | |
Defined in Data.Units.US.Misc |
Instances
Show Point Source # | |
Unit Point Source # | |
Defined in Data.Units.US.Misc conversionRatio :: Point -> Rational # canonicalConvRatio :: Point -> Rational | |
type UnitFactorsOf Point Source # | |
Defined in Data.Units.US.Misc | |
type DimOfUnit Point Source # | |
type BaseUnit Point Source # | |
Defined in Data.Units.US.Misc |
Instances
Show Pica Source # | |
Unit Pica Source # | |
Defined in Data.Units.US.Misc conversionRatio :: Pica -> Rational # canonicalConvRatio :: Pica -> Rational | |
type UnitFactorsOf Pica Source # | |
Defined in Data.Units.US.Misc | |
type DimOfUnit Pica Source # | |
type BaseUnit Pica Source # | |
Defined in Data.Units.US.Misc |
Instances
Show Fathom Source # | |
Unit Fathom Source # | |
Defined in Data.Units.US.Misc conversionRatio :: Fathom -> Rational # canonicalConvRatio :: Fathom -> Rational | |
type UnitFactorsOf Fathom Source # | |
Defined in Data.Units.US.Misc type UnitFactorsOf Fathom = If (IsCanonical Fathom) '['F Fathom One] (UnitFactorsOf (BaseUnit Fathom)) | |
type DimOfUnit Fathom Source # | |
type BaseUnit Fathom Source # | |
Defined in Data.Units.US.Misc |
Instances
Show Cable Source # | |
Unit Cable Source # | |
Defined in Data.Units.US.Misc conversionRatio :: Cable -> Rational # canonicalConvRatio :: Cable -> Rational | |
type UnitFactorsOf Cable Source # | |
Defined in Data.Units.US.Misc | |
type DimOfUnit Cable Source # | |
type BaseUnit Cable Source # | |
Defined in Data.Units.US.Misc |
data NauticalMile Source #
Instances
Show NauticalMile Source # | |
Defined in Data.Units.US.Misc showsPrec :: Int -> NauticalMile -> ShowS # show :: NauticalMile -> String # showList :: [NauticalMile] -> ShowS # | |
Unit NauticalMile Source # | |
Defined in Data.Units.US.Misc type BaseUnit NauticalMile # type DimOfUnit NauticalMile # type UnitFactorsOf NauticalMile :: [Factor Type] # | |
type UnitFactorsOf NauticalMile Source # | |
Defined in Data.Units.US.Misc type UnitFactorsOf NauticalMile = If (IsCanonical NauticalMile) '['F NauticalMile One] (UnitFactorsOf (BaseUnit NauticalMile)) | |
type DimOfUnit NauticalMile Source # | |
Defined in Data.Units.US.Misc | |
type BaseUnit NauticalMile Source # | |
Defined in Data.Units.US.Misc |
Instances
Show Knot Source # | |
Unit Knot Source # | |
Defined in Data.Units.US.Misc conversionRatio :: Knot -> Rational # canonicalConvRatio :: Knot -> Rational | |
type UnitFactorsOf Knot Source # | |
Defined in Data.Units.US.Misc | |
type DimOfUnit Knot Source # | |
type BaseUnit Knot Source # | |
Defined in Data.Units.US.Misc |
data Atmosphere Source #
Instances
Show Atmosphere Source # | |
Defined in Data.Units.US.Misc showsPrec :: Int -> Atmosphere -> ShowS # show :: Atmosphere -> String # showList :: [Atmosphere] -> ShowS # | |
Unit Atmosphere Source # | |
Defined in Data.Units.US.Misc type BaseUnit Atmosphere # type DimOfUnit Atmosphere # type UnitFactorsOf Atmosphere :: [Factor Type] # | |
type UnitFactorsOf Atmosphere Source # | |
Defined in Data.Units.US.Misc type UnitFactorsOf Atmosphere = If (IsCanonical Atmosphere) '['F Atmosphere One] (UnitFactorsOf (BaseUnit Atmosphere)) | |
type DimOfUnit Atmosphere Source # | |
Defined in Data.Units.US.Misc | |
type BaseUnit Atmosphere Source # | |
Defined in Data.Units.US.Misc |
data MillimeterOfMercury Source #
Instances
Show MillimeterOfMercury Source # | |
Defined in Data.Units.US.Misc showsPrec :: Int -> MillimeterOfMercury -> ShowS # show :: MillimeterOfMercury -> String # showList :: [MillimeterOfMercury] -> ShowS # | |
Unit MillimeterOfMercury Source # | |
Defined in Data.Units.US.Misc type BaseUnit MillimeterOfMercury # type DimOfUnit MillimeterOfMercury # type UnitFactorsOf MillimeterOfMercury :: [Factor Type] # | |
type UnitFactorsOf MillimeterOfMercury Source # | |
Defined in Data.Units.US.Misc | |
type DimOfUnit MillimeterOfMercury Source # | |
Defined in Data.Units.US.Misc | |
type BaseUnit MillimeterOfMercury Source # | |
Defined in Data.Units.US.Misc |
Instances
Show Torr Source # | |
Unit Torr Source # | |
Defined in Data.Units.US.Misc conversionRatio :: Torr -> Rational # canonicalConvRatio :: Torr -> Rational | |
type UnitFactorsOf Torr Source # | |
Defined in Data.Units.US.Misc | |
type DimOfUnit Torr Source # | |
type BaseUnit Torr Source # | |
Defined in Data.Units.US.Misc |
Instances
Show Calorie Source # | |
Unit Calorie Source # | |
Defined in Data.Units.US.Misc conversionRatio :: Calorie -> Rational # | |
type UnitFactorsOf Calorie Source # | |
Defined in Data.Units.US.Misc type UnitFactorsOf Calorie = If (IsCanonical Calorie) '['F Calorie One] (UnitFactorsOf (BaseUnit Calorie)) | |
type DimOfUnit Calorie Source # | |
type BaseUnit Calorie Source # | |
Defined in Data.Units.US.Misc |
data FoodCalorie Source #
Instances
Show FoodCalorie Source # | |
Defined in Data.Units.US.Misc showsPrec :: Int -> FoodCalorie -> ShowS # show :: FoodCalorie -> String # showList :: [FoodCalorie] -> ShowS # | |
Unit FoodCalorie Source # | |
Defined in Data.Units.US.Misc type BaseUnit FoodCalorie # type DimOfUnit FoodCalorie # type UnitFactorsOf FoodCalorie :: [Factor Type] # | |
type UnitFactorsOf FoodCalorie Source # | |
Defined in Data.Units.US.Misc type UnitFactorsOf FoodCalorie = If (IsCanonical FoodCalorie) '['F FoodCalorie One] (UnitFactorsOf (BaseUnit FoodCalorie)) | |
type DimOfUnit FoodCalorie Source # | |
Defined in Data.Units.US.Misc | |
type BaseUnit FoodCalorie Source # | |
Defined in Data.Units.US.Misc |
Instances
Show Btu Source # | |
Unit Btu Source # | |
Defined in Data.Units.US.Misc conversionRatio :: Btu -> Rational # canonicalConvRatio :: Btu -> Rational | |
type UnitFactorsOf Btu Source # | |
Defined in Data.Units.US.Misc | |
type DimOfUnit Btu Source # | |
type BaseUnit Btu Source # | |
Defined in Data.Units.US.Misc |
data Horsepower Source #
Instances
Show Horsepower Source # | |
Defined in Data.Units.US.Misc showsPrec :: Int -> Horsepower -> ShowS # show :: Horsepower -> String # showList :: [Horsepower] -> ShowS # | |
Unit Horsepower Source # | |
Defined in Data.Units.US.Misc type BaseUnit Horsepower # type DimOfUnit Horsepower # type UnitFactorsOf Horsepower :: [Factor Type] # | |
type UnitFactorsOf Horsepower Source # | |
Defined in Data.Units.US.Misc type UnitFactorsOf Horsepower = If (IsCanonical Horsepower) '['F Horsepower One] (UnitFactorsOf (BaseUnit Horsepower)) | |
type DimOfUnit Horsepower Source # | |
Defined in Data.Units.US.Misc | |
type BaseUnit Horsepower Source # | |
Defined in Data.Units.US.Misc |
Instances
Show Rankine Source # | |
Unit Rankine Source # | |
Defined in Data.Units.US.Misc conversionRatio :: Rankine -> Rational # | |
type UnitFactorsOf Rankine Source # | |
Defined in Data.Units.US.Misc type UnitFactorsOf Rankine = If (IsCanonical Rankine) '['F Rankine One] (UnitFactorsOf (BaseUnit Rankine)) | |
type DimOfUnit Rankine Source # | |
type BaseUnit Rankine Source # | |
Defined in Data.Units.US.Misc |
data PoundForce Source #
Instances
Show PoundForce Source # | |
Defined in Data.Units.US.Misc showsPrec :: Int -> PoundForce -> ShowS # show :: PoundForce -> String # showList :: [PoundForce] -> ShowS # | |
Unit PoundForce Source # | |
Defined in Data.Units.US.Misc type BaseUnit PoundForce # type DimOfUnit PoundForce # type UnitFactorsOf PoundForce :: [Factor Type] # | |
type UnitFactorsOf PoundForce Source # | |
Defined in Data.Units.US.Misc type UnitFactorsOf PoundForce = If (IsCanonical PoundForce) '['F PoundForce One] (UnitFactorsOf (BaseUnit PoundForce)) | |
type DimOfUnit PoundForce Source # | |
Defined in Data.Units.US.Misc | |
type BaseUnit PoundForce Source # | |
Defined in Data.Units.US.Misc |
Instances
Show Slug Source # | |
Unit Slug Source # | |
Defined in Data.Units.US.Misc conversionRatio :: Slug -> Rational # canonicalConvRatio :: Slug -> Rational | |
type UnitFactorsOf Slug Source # | |
Defined in Data.Units.US.Misc | |
type DimOfUnit Slug Source # | |
type BaseUnit Slug Source # | |
Defined in Data.Units.US.Misc |
Instances
Show Oersted Source # | |
Unit Oersted Source # | |
Defined in Data.Units.US.Misc conversionRatio :: Oersted -> Rational # | |
type UnitFactorsOf Oersted Source # | |
Defined in Data.Units.US.Misc type UnitFactorsOf Oersted = If (IsCanonical Oersted) '['F Oersted One] (UnitFactorsOf (BaseUnit Oersted)) | |
type DimOfUnit Oersted Source # | |
type BaseUnit Oersted Source # | |
Instances
Show Maxwell Source # | |
Unit Maxwell Source # | |
Defined in Data.Units.CGS conversionRatio :: Maxwell -> Rational # | |
type UnitFactorsOf Maxwell Source # | |
Defined in Data.Units.CGS type UnitFactorsOf Maxwell = If (IsCanonical Maxwell) '['F Maxwell One] (UnitFactorsOf (BaseUnit Maxwell)) | |
type DimOfUnit Maxwell Source # | |
type BaseUnit Maxwell Source # | |