Skip to content

Commit

Permalink
Add ability to set ShortName at Type (#84)
Browse files Browse the repository at this point in the history
  • Loading branch information
dwincort authored Aug 30, 2021
1 parent b571738 commit a8f66ee
Showing 1 changed file with 27 additions and 0 deletions.
27 changes: 27 additions & 0 deletions src/Options/Generic.hs
Original file line number Diff line number Diff line change
Expand Up @@ -310,6 +310,7 @@ module Options.Generic (
-- * Help
, type (<?>)(..)
, type (<!>)(..)
, type (<#>)(..)
, type (:::)
, Wrapped
, Unwrapped
Expand All @@ -330,6 +331,7 @@ import Control.Applicative
import Control.Monad.IO.Class (MonadIO(..))
import Data.Char (isUpper, toLower, toUpper)
import Data.Int (Int8, Int16, Int32, Int64)
import Data.Maybe (listToMaybe)
import Data.Monoid
import Data.List.NonEmpty (NonEmpty((:|)))
import Data.Proxy
Expand Down Expand Up @@ -683,6 +685,26 @@ instance (ParseFields a, KnownSymbol d) => ParseFields (a <!> d) where
parseFields h m c _ = DefValue <$> parseFields h m c (Just (symbolVal (Proxy :: Proxy d)))
instance (ParseFields a, KnownSymbol h) => ParseRecord (a <!> h)

{-| Use this to annotate a field with a type-level char (i.e. a `Symbol`)
representing the short name of the field (only the first character of the
symbol is used):
> data Example = Example
> { foo :: Int <#> "f"
> , bar :: Double <#> "b"
> } deriving (Generic, Show)
-}
newtype (<#>) (field :: *) (value :: Symbol) = ShortName { unShortName :: field } deriving (Generic, Show)

instance (ParseField a, KnownSymbol c) => ParseField (a <#> c) where
parseField h m _ d = ShortName <$> parseField h m (listToMaybe (symbolVal (Proxy :: Proxy c))) d
readField = ShortName <$> readField
metavar _ = metavar (Proxy :: Proxy a)

instance (ParseFields a, KnownSymbol c) => ParseFields (a <#> c) where
parseFields h m _ d = ShortName <$> parseFields h m (listToMaybe (symbolVal (Proxy :: Proxy c))) d
instance (ParseFields a, KnownSymbol h) => ParseRecord (a <#> h)

{-| A 1-tuple, used solely to translate `ParseFields` instances into
`ParseRecord` instances
-}
Expand Down Expand Up @@ -1172,6 +1194,7 @@ type instance Unwrapped ::: wrapped = Unwrap wrapped
type family Unwrap ty where
Unwrap (ty <?> helper) = Unwrap ty
Unwrap (ty <!> defVal) = Unwrap ty
Unwrap (ty <#> shrtNm) = Unwrap ty
Unwrap ty = ty

infixr 0 :::
Expand Down Expand Up @@ -1212,6 +1235,10 @@ instance GenericUnwrappable (K1 i field) (K1 i c)
=> GenericUnwrappable (K1 i (field <!> defVal)) (K1 i c) where
genericUnwrap (K1 c) = (genericUnwrap :: K1 i field p -> K1 i c p) (K1 (unDefValue c))

instance GenericUnwrappable (K1 i field) (K1 i c)
=> GenericUnwrappable (K1 i (field <#> defVal)) (K1 i c) where
genericUnwrap (K1 c) = (genericUnwrap :: K1 i field p -> K1 i c p) (K1 (unShortName c))

-- | Unwrap the fields of a constructor
unwrap :: forall f . Unwrappable f => f Wrapped -> f Unwrapped
unwrap = to . genericUnwrap . from
Expand Down

0 comments on commit a8f66ee

Please sign in to comment.