Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Data.Ron
Description
Most common ron definitions are collected in this module
Quick start
- Define a datatype which supports Ron serialization:
data MyType = Cons1 { _mtBool :: !Bool , _mtList :: ![Text] , _mtOtherValue :: !OtherType } | Cons2 Text Int deriving (Generic) deriving (ToRon
,FromRon
) viaRonWith
'[FieldsDropPrefix
] MyType
For more options, see Data.Ron.Class.
You will need to set DerivingStrategies, DerivingVia, DeriveGeneric,
DataKinds
for this to compile.
- Read a value of this type from a file with
decodeFile
:
myValue <- decodeFile
"path/to/file"
useMyValue myValue
- Write your value to a file with
encodeFile
encodeFile
haskellStyle
"path/to/file" myValue
For a type defined above, you can expect the serialized form to look like this:
Cons1 ( bool: false , list: [ "list" , "of" , "strings" ] , otherValue: OtherType (* something here *) )
Synopsis
- encode :: ToRon a => SerializeSettings -> a -> ByteString
- encodeFile :: ToRon a => SerializeSettings -> FilePath -> a -> IO ()
- decode :: FromRon a => ByteString -> Either String a
- decodeLazy :: FromRon a => ByteString -> Either String a
- decodeFile :: FromRon a => FilePath -> IO a
- haskellStyle :: SerializeSettings
- rustStyle :: SerializeSettings
- compactStyle :: SerializeSettings
- class ToRon a where
- class FromRon a where
- fromRon :: Value -> ParseResult a
- newtype RonWith s a = RonWith a
- data UseStrict
- data EncodeWith a
- data DecodeWith a
- data ConvertWith a
- data FieldsToSnakeCase
- data FieldsDropPrefix
- data ImplicitSome
- data NoImplicitSome
- data SkipSingleConstructor
- data NoSkipSingleConstructor
Serialize and deserialize
encode :: ToRon a => SerializeSettings -> a -> ByteString Source #
Serialize a value to a lazy bytestring. For settings you can use
haskellStyle
or rustStyle
or compactStyle
encodeFile :: ToRon a => SerializeSettings -> FilePath -> a -> IO () Source #
Serialize a value into a file. For settings you can use
haskellStyle
or rustStyle
or compactStyle
decode :: FromRon a => ByteString -> Either String a Source #
Parse a ByteString
to your type. The error is produced by attoparsec and is
not very useful.
decodeLazy :: FromRon a => ByteString -> Either String a Source #
Parse a lazy ByteString
to your type. The error is produced by
attoparsec and is not very useful.
decodeFile :: FromRon a => FilePath -> IO a Source #
Parse file content to your type. Throws ParseError
or DecodeError
on
errors.
Style options
haskellStyle :: SerializeSettings Source #
Style similar to what is produced in haskell with stylish-haskell or hindent.
- Uses indent size of 4
- Unpacks top level values
rustStyle :: SerializeSettings Source #
Style similar to what is produced by rustfmt, or by ron-rs itself
compactStyle :: SerializeSettings Source #
All whitespace is disabled. Does not unpack toplevel for compatability, so you can set that if you want an even compacter style that can't be read by ron-rs
Ron class and deriving
A class of values that can be encoded to RON format.
There are several ways to define an instance:
- By producing a
Value
by hand - By using
toRonGeneric
- By
DerivingVia
extension and usingRonWith
When using the second option, the encoding parameters are specified with
RonSettings
. With the third option, the same parameters are specified by a
list of settings found in Deriving
.
The default implementation uses generic encoding with laxRonSettings
. You
can use other settings like this:
instance ToRon MyType where toRon = toRonGeneric strictRonSettings { encodeFlags = RonFlags { implicitSome = True , skipSingleConstructor = True } }
Or like this:
deriving via (RonWith '[UseStrict, EncodeWith SkipSingleConstructor, EncodeWith ImplicitSome]) instance ToRon MyType
Minimal complete definition
Nothing
Methods
Instances
class FromRon a where Source #
A class of values that can be restored from RON format
There are several ways to define an instance:
- By deconstructing a
Value
by hand and producing a value of your type - By using
fromRonGeneric
- By
DerivingVia
extension and usingRonWith
The default implementation uses generic decoding with laxRonSettings
. You
can use other settings like this:
instance FromRon MyType where fromRon = fromRonGeneric strictRonSettings { decodeFlags = RonFlags { implicitSome = True , skipSingleConstructor = True } }
Or like this:
deriving via (RonWith '[UseStrict, DecodeWith SkipSingleConstructor, DecodeWith ImplicitSome]) instance FromRon MyType
Minimal complete definition
Nothing
Methods
fromRon :: Value -> ParseResult a Source #
Instances
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 |
Settings for deriving
Replace the current settings with strictRonSettings
Instances
ReflectSettingsOptions UseStrict Source # | |
Defined in Data.Ron.Class.Deriving Methods reflectS :: Proxy UseStrict -> RonSettings -> RonSettings Source # |
data EncodeWith a Source #
Sets a flag in encodeFlags
. Can set anything with ReflectFlagOptions
instances, like ImplicitSome
, SkipSingleConstructor
Instances
ReflectFlagOptions a => ReflectSettingsOptions (EncodeWith a :: Type) Source # | |
Defined in Data.Ron.Class.Deriving Methods reflectS :: Proxy (EncodeWith a) -> RonSettings -> RonSettings Source # |
data DecodeWith a Source #
Sets a flag in decodeFlags
. Can set anything with ReflectFlagOptions
instances
Instances
ReflectFlagOptions a => ReflectSettingsOptions (DecodeWith a :: Type) Source # | |
Defined in Data.Ron.Class.Deriving Methods reflectS :: Proxy (DecodeWith a) -> RonSettings -> RonSettings Source # |
data ConvertWith a Source #
Same as setting both EncodeWith
and DecodeWith
Instances
ReflectFlagOptions a => ReflectSettingsOptions (ConvertWith a :: Type) Source # | |
Defined in Data.Ron.Class.Deriving Methods reflectS :: Proxy (ConvertWith a) -> RonSettings -> RonSettings Source # |
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
Instances
ReflectSettingsOptions FieldsToSnakeCase Source # | |
Defined in Data.Ron.Class.Deriving Methods reflectS :: Proxy FieldsToSnakeCase -> RonSettings -> RonSettings Source # |
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
Instances
ReflectSettingsOptions FieldsDropPrefix Source # | |
Defined in Data.Ron.Class.Deriving Methods reflectS :: Proxy FieldsDropPrefix -> RonSettings -> RonSettings Source # |
data ImplicitSome Source #
Encode or decode flag that sets implicitSome
to True
Instances
ReflectFlagOptions ImplicitSome Source # | |
Defined in Data.Ron.Class.Deriving |
data NoImplicitSome Source #
Encode or decode flag that sets implicitSome
to False
Instances
data SkipSingleConstructor Source #
Encode or decode flag that sets skipSingleConstructor
to True
Instances
data NoSkipSingleConstructor Source #
Encode or decode flag that sets skipSingleConstructor
to False