{-# LANGUAGE TemplateHaskell, TypeFamilies, TypeOperators #-}
module Data.Units.US.Liquid where
import Data.Metrology
import Data.Metrology.TH
import Data.Units.US.Misc
import Language.Haskell.TH
declareDerivedUnit "Gallon" [t| Inch :^ Three |] 231 (Just "gal")
declareDerivedUnit "FluidOunce" [t| Gallon |] (1/128) (Just "floz")
declareDerivedUnit "Gill" [t| FluidOunce |] 4 (Just "gi")
declareDerivedUnit "Cup" [t| FluidOunce |] 8 (Just "cp")
declareDerivedUnit "Pint" [t| FluidOunce |] 16 (Just "pt")
declareDerivedUnit "Quart" [t| Gallon |] (1/4) (Just "qt")
declareDerivedUnit "Teaspoon" [t| FluidOunce |] (1/6) (Just "tsp")
declareDerivedUnit "Tablespoon" [t| Teaspoon |] 3 (Just "Tbsp")
declareDerivedUnit "Shot" [t| Tablespoon |] 3 (Just "jig")
declareDerivedUnit "Minim" [t| Teaspoon |] (1/80) (Just "min")
declareDerivedUnit "Dram" [t| Minim |] 60 (Just "fldr")
declareDerivedUnit "Hogshead" [t| Gallon |] 63 (Just "hogshead")
declareDerivedUnit "Barrel" [t| Hogshead |] (1/2) (Just "bbl")
declareDerivedUnit "OilBarrel" [t| Gallon |] 42 (Just "bbl")
commonLiquidMeasures :: [Name]
commonLiquidMeasures :: [Name]
commonLiquidMeasures = [ ''Teaspoon, ''Tablespoon, ''FluidOunce, ''Cup, ''Pint
, ''Quart, ''Gallon ]
otherLiquidMeasures :: [Name]
otherLiquidMeasures :: [Name]
otherLiquidMeasures = [ ''Minim, ''Dram, ''Shot, ''Gill, ''Barrel
, ''OilBarrel, ''Hogshead ]