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

Data.Ron

Description

Most common ron definitions are collected in this module

Quick start

  1. Define a datatype which supports Ron serialization:
     data MyType
         = Cons1
             { _mtBool :: !Bool
             , _mtList :: ![Text]
             , _mtOtherValue :: !OtherType
             }
         | Cons2 Text Int
         deriving (Generic)
         deriving (ToRon, FromRon)
             via RonWith '[FieldsDropPrefix] MyType

For more options, see Data.Ron.Class.

You will need to set DerivingStrategies, DerivingVia, DeriveGeneric, DataKinds for this to compile.

  1. Read a value of this type from a file with decodeFile:
     myValue <- decodeFile "path/to/file"
     useMyValue myValue
  1. 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

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

class ToRon a where Source #

A class of values that can be encoded to RON format.

There are several ways to define an instance:

  1. By producing a Value by hand
  2. By using toRonGeneric
  3. By DerivingVia extension and using RonWith

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

toRon :: a -> Value Source #

default toRon :: (Generic a, GToRon (Rep a)) => a -> Value Source #

Instances

Instances details
ToRon Int16 Source # 
Instance details

Defined in Data.Ron.Class

Methods

toRon :: Int16 -> Value Source #

ToRon Int32 Source # 
Instance details

Defined in Data.Ron.Class

Methods

toRon :: Int32 -> Value Source #

ToRon Int64 Source # 
Instance details

Defined in Data.Ron.Class

Methods

toRon :: Int64 -> Value Source #

ToRon Int8 Source # 
Instance details

Defined in Data.Ron.Class

Methods

toRon :: Int8 -> Value Source #

ToRon Word16 Source # 
Instance details

Defined in Data.Ron.Class

Methods

toRon :: Word16 -> Value Source #

ToRon Word32 Source # 
Instance details

Defined in Data.Ron.Class

Methods

toRon :: Word32 -> Value Source #

ToRon Word64 Source # 
Instance details

Defined in Data.Ron.Class

Methods

toRon :: Word64 -> Value Source #

ToRon Word8 Source # 
Instance details

Defined in Data.Ron.Class

Methods

toRon :: Word8 -> Value Source #

ToRon ByteString Source # 
Instance details

Defined in Data.Ron.Class

ToRon Scientific Source # 
Instance details

Defined in Data.Ron.Class

ToRon Text Source # 
Instance details

Defined in Data.Ron.Class

Methods

toRon :: Text -> Value Source #

ToRon Integer Source # 
Instance details

Defined in Data.Ron.Class

Methods

toRon :: Integer -> Value Source #

ToRon () Source # 
Instance details

Defined in Data.Ron.Class

Methods

toRon :: () -> Value Source #

ToRon Bool Source # 
Instance details

Defined in Data.Ron.Class

Methods

toRon :: Bool -> Value Source #

ToRon Char Source # 
Instance details

Defined in Data.Ron.Class

Methods

toRon :: Char -> Value Source #

ToRon Double Source # 
Instance details

Defined in Data.Ron.Class

Methods

toRon :: Double -> Value Source #

ToRon Float Source # 
Instance details

Defined in Data.Ron.Class

Methods

toRon :: Float -> Value Source #

ToRon Int Source # 
Instance details

Defined in Data.Ron.Class

Methods

toRon :: Int -> Value Source #

ToRon Word Source # 
Instance details

Defined in Data.Ron.Class

Methods

toRon :: Word -> Value Source #

ToRon a => ToRon (Complex a) Source # 
Instance details

Defined in Data.Ron.Class

Methods

toRon :: Complex a -> Value Source #

ToRon a => ToRon (NonEmpty a) Source # 
Instance details

Defined in Data.Ron.Class

Methods

toRon :: NonEmpty a -> Value Source #

ToRon a => ToRon (Seq a) Source # 
Instance details

Defined in Data.Ron.Class

Methods

toRon :: Seq a -> Value Source #

ToRon a => ToRon (Set a) Source # 
Instance details

Defined in Data.Ron.Class

Methods

toRon :: Set a -> Value Source #

ToRon a => ToRon (Vector a) Source # 
Instance details

Defined in Data.Ron.Class

Methods

toRon :: Vector a -> Value Source #

ToRon a => ToRon (Maybe a) Source # 
Instance details

Defined in Data.Ron.Class

Methods

toRon :: Maybe a -> Value Source #

ToRon [Char] Source # 
Instance details

Defined in Data.Ron.Class

Methods

toRon :: [Char] -> Value Source #

ToRon a => ToRon [a] Source # 
Instance details

Defined in Data.Ron.Class

Methods

toRon :: [a] -> Value Source #

(ToRon a, ToRon b) => ToRon (Either a b) Source # 
Instance details

Defined in Data.Ron.Class

Methods

toRon :: Either a b -> Value Source #

(ToRon k, ToRon v) => ToRon (Map k v) Source # 
Instance details

Defined in Data.Ron.Class

Methods

toRon :: Map k v -> Value Source #

(ToRon a1, ToRon a2) => ToRon (a1, a2) Source # 
Instance details

Defined in Data.Ron.Class

Methods

toRon :: (a1, a2) -> Value Source #

(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 #

class FromRon a where Source #

A class of values that can be restored from RON format

There are several ways to define an instance:

  1. By deconstructing a Value by hand and producing a value of your type
  2. By using fromRonGeneric
  3. By DerivingVia extension and using RonWith

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 #

default fromRon :: (Generic a, GFromRon (Rep a)) => Value -> ParseResult a Source #

Instances

Instances details
FromRon Int16 Source # 
Instance details

Defined in Data.Ron.Class

FromRon Int32 Source # 
Instance details

Defined in Data.Ron.Class

FromRon Int64 Source # 
Instance details

Defined in Data.Ron.Class

FromRon Int8 Source # 
Instance details

Defined in Data.Ron.Class

FromRon Word16 Source # 
Instance details

Defined in Data.Ron.Class

FromRon Word32 Source # 
Instance details

Defined in Data.Ron.Class

FromRon Word64 Source # 
Instance details

Defined in Data.Ron.Class

FromRon Word8 Source # 
Instance details

Defined in Data.Ron.Class

FromRon ByteString Source # 
Instance details

Defined in Data.Ron.Class

FromRon Scientific Source # 
Instance details

Defined in Data.Ron.Class

FromRon Text Source # 
Instance details

Defined in Data.Ron.Class

FromRon Integer Source # 
Instance details

Defined in Data.Ron.Class

FromRon () Source # 
Instance details

Defined in Data.Ron.Class

Methods

fromRon :: Value -> ParseResult () Source #

FromRon Bool Source # 
Instance details

Defined in Data.Ron.Class

FromRon Char Source # 
Instance details

Defined in Data.Ron.Class

FromRon Double Source # 
Instance details

Defined in Data.Ron.Class

FromRon Float Source # 
Instance details

Defined in Data.Ron.Class

FromRon Int Source # 
Instance details

Defined in Data.Ron.Class

FromRon Word Source # 
Instance details

Defined in Data.Ron.Class

(Num a, FromRon a) => FromRon (Complex a) Source # 
Instance details

Defined in Data.Ron.Class

FromRon a => FromRon (NonEmpty a) Source # 
Instance details

Defined in Data.Ron.Class

FromRon a => FromRon (Seq a) Source # 
Instance details

Defined in Data.Ron.Class

Methods

fromRon :: Value -> ParseResult (Seq a) Source #

(FromRon a, Ord a) => FromRon (Set a) Source # 
Instance details

Defined in Data.Ron.Class

Methods

fromRon :: Value -> ParseResult (Set a) Source #

FromRon a => FromRon (Vector a) Source # 
Instance details

Defined in Data.Ron.Class

Methods

fromRon :: Value -> ParseResult (Vector a) Source #

FromRon a => FromRon (Maybe a) Source # 
Instance details

Defined in Data.Ron.Class

FromRon [Char] Source # 
Instance details

Defined in Data.Ron.Class

FromRon a => FromRon [a] Source # 
Instance details

Defined in Data.Ron.Class

Methods

fromRon :: Value -> ParseResult [a] Source #

(FromRon a, FromRon b) => FromRon (Either a b) Source # 
Instance details

Defined in Data.Ron.Class

Methods

fromRon :: Value -> ParseResult (Either a b) Source #

(FromRon k, FromRon v, Ord k) => FromRon (Map k v) Source # 
Instance details

Defined in Data.Ron.Class

Methods

fromRon :: Value -> ParseResult (Map k v) Source #

(FromRon a1, FromRon a2) => FromRon (a1, a2) Source # 
Instance details

Defined in Data.Ron.Class

Methods

fromRon :: Value -> ParseResult (a1, a2) Source #

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

Defined in Data.Ron.Class.Deriving

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 for deriving

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