----------------------------------------------------------------------------- -- -- Module : Data.Table.Identifier -- Copyright : (c) 2014-16 Brian W Bush -- License : MIT -- -- Maintainer : Brian W Bush -- Stability : Experimental -- Portability : Portable -- -- | Identifier for use in tables. -- ----------------------------------------------------------------------------- {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MonoLocalBinds #-} {-# OPTIONS_GHC -fno-warn-deprecations #-} module Data.Table.Identifier {-# DEPRECATED "This module will be replaced in a future release." #-} ( -- * Types Id(..) ) where import Data.String.Util (Stringy(..)) import Data.Table (Tabulatable(..)) -- | An identifier for a table. newtype Id a = Id {unId :: a} deriving (Read, Show) instance Stringy a => Tabulatable (Id a) where labels = const ["ID"] tabulation = (: []) . toString . unId untabulation = Id . fromString . head