ron-hs-0.4.0: RON format implementation in haskell
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Ron.Class.Deriving

Description

Allows deriving ron encoding-decoding instances with DerivingVia. See RonWith

Synopsis

Documentation

newtype RonWith s a Source #

Helper for deriving Ron instances. Use like this:

     data MyType = MyType {...}
         deriving (Eq, Show, Generic)
         deriving (ToRon, FromRon)
             via RonWith '[FieldsDropPrefix, EncodeWith SkipSingleConstructor] MyType

This is identical to

     data MyType = MyType {...}
         deriving (Eq, Show, Generic)
     instance ToRon MyType where
         toRon =
             let settings
                 = (s{encodeFlags} -> s{encodeFlags = encodeFlags{skipSingleConstructor = True}})
                 . (s{fieldModifier} -> s{dropPrefix . fieldModifier})
                 $ laxRonSettings
             in toRonGeneric settings

The options are applied left to right, and the starting options are laxRonSettings

All of built-in settings are documented in Deriving module. You can define your own settings by creating new datatypes and creating instances for ReflectSettingsOptions or ReflectFlagOptions

Constructors

RonWith a 

Instances

Instances details
(Generic a, GFromRon (Rep a), ReflectSettingsList s) => FromRon (RonWith s a) Source # 
Instance details

Defined in Data.Ron.Class.Deriving

(Generic a, GToRon (Rep a), ReflectSettingsList s) => ToRon (RonWith s a) Source # 
Instance details

Defined in Data.Ron.Class.Deriving

Methods

toRon :: RonWith s a -> Value Source #

Settings

data UseStrict Source #

Replace the current settings with strictRonSettings

Instances

Instances details
ReflectSettingsOptions UseStrict Source # 
Instance details

Defined in Data.Ron.Class.Deriving

data EncodeWith a Source #

Sets a flag in encodeFlags. Can set anything with ReflectFlagOptions instances, like ImplicitSome, SkipSingleConstructor

Instances

Instances details
ReflectFlagOptions a => ReflectSettingsOptions (EncodeWith a :: Type) Source # 
Instance details

Defined in Data.Ron.Class.Deriving

data DecodeWith a Source #

Sets a flag in decodeFlags. Can set anything with ReflectFlagOptions instances

Instances

Instances details
ReflectFlagOptions a => ReflectSettingsOptions (DecodeWith a :: Type) Source # 
Instance details

Defined in Data.Ron.Class.Deriving

data ConvertWith a Source #

Same as setting both EncodeWith and DecodeWith

Instances

Instances details
ReflectFlagOptions a => ReflectSettingsOptions (ConvertWith a :: Type) Source # 
Instance details

Defined in Data.Ron.Class.Deriving

data FieldsToSnakeCase Source #

Convert fields to snake case. If your field also has prefix, you want to have this option after FieldsDropPrefix, as options are applied left to right

data FieldsDropPrefix Source #

Drop the prefix that is usually used with lenses, that is an underscore followed by several lowercase letters; regex for this prefix is s/^_[[:lowercase:]]+([[:uppercase:]].*)/\1/. You probably want to use this field modifier before other field modifiers, as they are applied left to right

data ImplicitSome Source #

Encode or decode flag that sets implicitSome to True

Instances

Instances details
ReflectFlagOptions ImplicitSome Source # 
Instance details

Defined in Data.Ron.Class.Deriving

data NoImplicitSome Source #

Encode or decode flag that sets implicitSome to False

Instances

Instances details
ReflectFlagOptions NoImplicitSome Source # 
Instance details

Defined in Data.Ron.Class.Deriving

data SkipSingleConstructor Source #

Encode or decode flag that sets skipSingleConstructor to True

data NoSkipSingleConstructor Source #

Encode or decode flag that sets skipSingleConstructor to False

Undelying typeclasses

class ReflectSettingsOptions a where Source #

Typeclass for you to implement your own options. Here's how FieldsToSnakeCase uses it:

     instance ReflectSettingsOptions FieldsToSnakeCase where
         reflectS Proxy s@RonSettings {fieldModifier} = s
             { fieldModifier = toSnake . fieldModifier }

Be careful when composing functions to apply them after the already present, to preserve the left-to-right semantics of adding the options

class ReflectFlagOptions a where Source #

Typeclass for you to implement your own symmetric options. Here's how ImplicitSome uses it

     instance ReflectFlagOptions ImplicitSome where
         reflectF Proxy flags = flags { implicitSome = True }