Copyright | (c) Dominik Schrempf 2021 |
---|---|
License | GPL-3.0-or-later |
Maintainer | dominik.schrempf@gmail.com |
Stability | unstable |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Creation date: Sat Mar 21 13:56:03 2020.
A large collection of tools.
Synopsis
- alignRightWith :: Char -> Int -> ByteString -> ByteString
- alignRight :: Int -> ByteString -> ByteString
- alignLeftWith :: Char -> Int -> ByteString -> ByteString
- alignLeft :: Int -> ByteString -> ByteString
- splitGen :: PrimMonad m => Int -> Gen (PrimState m) -> m [Gen (PrimState m)]
- getChunks :: Int -> Int -> [Int]
- eps :: Double
- precision :: Int
- type ELynx a = ReaderT (Environment a) IO
- eLynxWrapper :: (Eq a, Show a, Reproducible a, Reproducible b, ToJSON a) => GlobalArguments -> b -> (b -> a) -> ELynx b () -> IO ()
- out :: Reproducible a => String -> ByteString -> String -> ELynx a ()
- outHandle :: Reproducible a => String -> String -> ELynx a Handle
- data Environment a = Environment {
- globalArguments :: GlobalArguments
- localArguments :: a
- logHandles :: [Handle]
- outLock :: MVar ()
- startingTime :: UTCTime
- initializeEnvironment :: GlobalArguments -> a -> IO (Environment a)
- closeEnvironment :: Environment s -> IO ()
- allEqual :: Eq a => [a] -> Bool
- allNearlyEqualWith :: Double -> [Double] -> Bool
- allNearlyEqual :: [Double] -> Bool
- nearlyEqWith :: Double -> Double -> Double -> Bool
- eps :: Double
- nearlyEq :: Double -> Double -> Bool
- (=~=) :: Double -> Double -> Bool
- nearlyEqListWith :: Double -> [Double] -> [Double] -> Bool
- nearlyEqList :: [Double] -> [Double] -> Bool
- nearlyEqVecWith :: Double -> Vector R -> Vector R -> Bool
- nearlyEqVec :: Vector R -> Vector R -> Bool
- nearlyEqMatWith :: Double -> Matrix R -> Matrix R -> Bool
- nearlyEqMat :: Matrix R -> Matrix R -> Bool
- data ExecutionMode
- openFileWithExecutionMode :: ExecutionMode -> FilePath -> IO Handle
- readGZFile :: FilePath -> IO ByteString
- writeGZFile :: ExecutionMode -> FilePath -> ByteString -> IO ()
- runParserOnFile :: Parser a -> FilePath -> IO (Either String a)
- parseFileWith :: Parser a -> FilePath -> IO a
- parseIOWith :: Parser a -> IO a
- parseFileOrIOWith :: Parser a -> Maybe FilePath -> IO a
- parseStringWith :: Parser a -> String -> a
- parseByteStringWith :: Parser a -> ByteString -> a
- matrixSeparateSymSkew :: Matrix R -> (Matrix R, Matrix R)
- matrixSetDiagToZero :: Matrix R -> Matrix R
- dispv :: Int -> Vector R -> String
- dispm :: Int -> Matrix R -> String
- dispmi :: Int -> Int -> Matrix R -> String
- sortListWithIndices :: Ord a => [a] -> [(a, Int)]
- randomInsertList :: PrimMonad m => a -> [a] -> Gen (PrimState m) -> m [a]
- shuffle :: PrimMonad m => [a] -> Gen (PrimState m) -> m [a]
- shuffleN :: [a] -> Int -> GenIO -> IO [[a]]
- grabble :: PrimMonad m => [a] -> Int -> Int -> Gen (PrimState m) -> m [[a]]
- data Verbosity
- class HasLock e where
- class HasLogHandles e where
- getLogHandles :: e -> [Handle]
- class HasStartingTime s where
- getStartingTime :: s -> UTCTime
- class HasVerbosity s where
- getVerbosity :: s -> Verbosity
- type Logger e a = ReaderT e IO a
- logOutB :: (HasLogHandles e, HasLock e) => ByteString -> ByteString -> Logger e ()
- logDebugB :: (HasLock e, HasLogHandles e, HasVerbosity e) => ByteString -> Logger e ()
- logDebugS :: (HasLock e, HasLogHandles e, HasVerbosity e) => String -> Logger e ()
- logWarnB :: (HasLock e, HasLogHandles e, HasVerbosity e) => ByteString -> Logger e ()
- logWarnS :: (HasLock e, HasLogHandles e, HasVerbosity e) => String -> Logger e ()
- logInfoB :: (HasLock e, HasLogHandles e, HasVerbosity e) => ByteString -> Logger e ()
- logInfoS :: (HasLock e, HasLogHandles e, HasVerbosity e) => String -> Logger e ()
- logHeader :: [String]
- logInfoHeader :: (HasLock e, HasLogHandles e, HasStartingTime e, HasVerbosity e) => String -> [String] -> Logger e ()
- logInfoFooter :: (HasLock e, HasLogHandles e, HasStartingTime e, HasVerbosity e) => Logger e ()
- logInfoNewSection :: (HasLock e, HasLogHandles e, HasVerbosity e) => String -> Logger e ()
- compose :: [a -> a] -> a -> a
- allValues :: (Bounded a, Enum a) => [a]
- harmonic :: Int -> Double
- roundN :: Int -> Double -> Double
- data SeedOpt
- seedOpt :: Parser SeedOpt
- executionModeOpt :: Parser ExecutionMode
- data GlobalArguments = GlobalArguments {}
- data Arguments a = Arguments {
- global :: GlobalArguments
- local :: a
- parseArguments :: forall a. Reproducible a => IO (Arguments a)
- elynxParserInfo :: [String] -> [String] -> Parser a -> ParserInfo a
- createCommandReproducible :: forall a b. Reproducible a => (a -> b) -> Mod CommandFields b
- createCommand :: String -> [String] -> [String] -> Parser a -> (a -> b) -> Mod CommandFields b
- elynxFooter :: [Doc]
- data SeedOpt
- class Reproducible a where
- getReproductionHash :: forall a. Reproducible a => Reproduction a -> String
- data Reproduction a = Reproduction {}
- writeReproduction :: forall a. (Eq a, Show a, Reproducible a, ToJSON a) => String -> a -> IO ()
- hashFile :: FilePath -> IO ByteString
- class Generic a
- class FromJSON a
- class ToJSON a
ByteString handling
alignRightWith :: Char -> Int -> ByteString -> ByteString Source #
For a given width, align string to the right; use given fill character; trim on the left if string is longer.
alignRight :: Int -> ByteString -> ByteString Source #
For a given width, align string to the right; trim on the left if string is longer.
alignLeftWith :: Char -> Int -> ByteString -> ByteString Source #
For a given width, align string to the left; use given fill character; trim on the right if string is longer.
alignLeft :: Int -> ByteString -> ByteString Source #
For a given width, align string to the left; trim on the right if string is longer.
MWC
splitGen :: PrimMonad m => Int -> Gen (PrimState m) -> m [Gen (PrimState m)] Source #
Split a generator.
Concurrent calculations
getChunks :: Int -> Int -> [Int] Source #
For a given number of capabilities and number of calculations, get chunk sizes. The chunk sizes will be as evenly distributed as possible and sum up to the number of calculations.
Definitions
type ELynx a = ReaderT (Environment a) IO Source #
ELynx transformer to be used with all executables.
eLynxWrapper :: (Eq a, Show a, Reproducible a, Reproducible b, ToJSON a) => GlobalArguments -> b -> (b -> a) -> ELynx b () -> IO () Source #
out :: Reproducible a => String -> ByteString -> String -> ELynx a () Source #
Write a result with a given name to file with given extension or standard output. Supports compression.
outHandle :: Reproducible a => String -> String -> ELynx a Handle Source #
Get an output handle, does not support compression. The handle has to be closed after use!
data Environment a Source #
The environment of an ELynx run.
Environment | |
|
Instances
Eq a => Eq (Environment a) Source # | |
Defined in ELynx.Tools.Environment (==) :: Environment a -> Environment a -> Bool # (/=) :: Environment a -> Environment a -> Bool # | |
HasVerbosity (Environment a) Source # | |
Defined in ELynx.Tools.Environment getVerbosity :: Environment a -> Verbosity Source # | |
HasStartingTime (Environment a) Source # | |
Defined in ELynx.Tools.Environment getStartingTime :: Environment a -> UTCTime Source # | |
HasLogHandles (Environment a) Source # | |
Defined in ELynx.Tools.Environment getLogHandles :: Environment a -> [Handle] Source # | |
HasLock (Environment a) Source # | |
Defined in ELynx.Tools.Environment getLock :: Environment a -> MVar () Source # |
initializeEnvironment :: GlobalArguments -> a -> IO (Environment a) Source #
Initialize the environment.
Open log file, get current time.
closeEnvironment :: Environment s -> IO () Source #
Close file handles.
Equality
allEqual :: Eq a => [a] -> Bool Source #
Test if all elements of a list are equal; returns True for empty list.
allNearlyEqualWith :: Double -> [Double] -> Bool Source #
Test if all elements of a list are nearly equal; returns True for empty list.
allNearlyEqual :: [Double] -> Bool Source #
Test if all elements of a list are nearly equal; returns True for empty list.
nearlyEqWith :: Double -> Double -> Double -> Bool Source #
Test for equality with given tolerance (needed because of machine precision).
nearlyEq :: Double -> Double -> Bool Source #
Test for equality with predefined tolerance eps
(needed because of
machine precision).
nearlyEqListWith :: Double -> [Double] -> [Double] -> Bool Source #
Test if two lists are nearly equal.
nearlyEqList :: [Double] -> [Double] -> Bool Source #
Test if two lists are nearly equal; use tolerance eps
.
nearlyEqVecWith :: Double -> Vector R -> Vector R -> Bool Source #
Test if two vectors are nearly equal.
nearlyEqVec :: Vector R -> Vector R -> Bool Source #
Test if two vectors are nearly equal; use tolerance eps
.
nearlyEqMatWith :: Double -> Matrix R -> Matrix R -> Bool Source #
Test if two vectors are nearly equal.
nearlyEqMat :: Matrix R -> Matrix R -> Bool Source #
Test if two vectors are nearly equal; use tolerance eps
.
Execution Mode
data ExecutionMode Source #
Overwrite existing output files or fail if output files exist.
Instances
Eq ExecutionMode Source # | |
Defined in ELynx.Tools.InputOutput (==) :: ExecutionMode -> ExecutionMode -> Bool # (/=) :: ExecutionMode -> ExecutionMode -> Bool # | |
Show ExecutionMode Source # | |
Defined in ELynx.Tools.InputOutput showsPrec :: Int -> ExecutionMode -> ShowS # show :: ExecutionMode -> String # showList :: [ExecutionMode] -> ShowS # | |
Generic ExecutionMode Source # | |
Defined in ELynx.Tools.InputOutput type Rep ExecutionMode :: Type -> Type # from :: ExecutionMode -> Rep ExecutionMode x # to :: Rep ExecutionMode x -> ExecutionMode # | |
ToJSON ExecutionMode Source # | |
Defined in ELynx.Tools.InputOutput toJSON :: ExecutionMode -> Value # toEncoding :: ExecutionMode -> Encoding # toJSONList :: [ExecutionMode] -> Value # toEncodingList :: [ExecutionMode] -> Encoding # | |
FromJSON ExecutionMode Source # | |
Defined in ELynx.Tools.InputOutput parseJSON :: Value -> Parser ExecutionMode # parseJSONList :: Value -> Parser [ExecutionMode] # | |
type Rep ExecutionMode Source # | |
openFileWithExecutionMode :: ExecutionMode -> FilePath -> IO Handle Source #
Open existing files only if Force
is true.
Input, output
readGZFile :: FilePath -> IO ByteString Source #
Read file. If file path ends with ".gz", assume gzipped file and decompress before read.
writeGZFile :: ExecutionMode -> FilePath -> ByteString -> IO () Source #
Write file. If file path ends with ".gz", assume gzipped file and compress before write.
Parsing
runParserOnFile :: Parser a -> FilePath -> IO (Either String a) Source #
Parse a possibly gzipped file.
parseFileWith :: Parser a -> FilePath -> IO a Source #
Parse a possibly gzipped file and extract the result.
parseIOWith :: Parser a -> IO a Source #
Parse standard input.
parseFileOrIOWith :: Parser a -> Maybe FilePath -> IO a Source #
Parse a possibly gzipped file, or standard input, and extract the result.
parseByteStringWith :: Parser a -> ByteString -> a Source #
Parse a ByteString
and extract the result.
Linear Algebra
matrixSeparateSymSkew :: Matrix R -> (Matrix R, Matrix R) Source #
Separate a square matrix into a symmetric and a skew-symmetric matrix.
dispmi :: Int -> Int -> Matrix R -> String Source #
Display a matrix with given precision and indent.
Lists
sortListWithIndices :: Ord a => [a] -> [(a, Int)] Source #
Sort a list and also return original indices.
randomInsertList :: PrimMonad m => a -> [a] -> Gen (PrimState m) -> m [a] Source #
Insert element into random position of list.
grabble :: PrimMonad m => [a] -> Int -> Int -> Gen (PrimState m) -> m [[a]] Source #
grabble xs m n
is O(m*n'), where n' = min n (length xs)
. Choose n'
elements from xs
, without replacement, and that m
times.
Verbosity levels.
Instances
class HasLock e where Source #
Types with an output lock for concurrent output.
Instances
HasLock (Environment a) Source # | |
Defined in ELynx.Tools.Environment getLock :: Environment a -> MVar () Source # |
class HasLogHandles e where Source #
Types with logging information.
getLogHandles :: e -> [Handle] Source #
Instances
HasLogHandles (Environment a) Source # | |
Defined in ELynx.Tools.Environment getLogHandles :: Environment a -> [Handle] Source # |
class HasStartingTime s where Source #
Types with starting time.
getStartingTime :: s -> UTCTime Source #
Instances
HasStartingTime (Environment a) Source # | |
Defined in ELynx.Tools.Environment getStartingTime :: Environment a -> UTCTime Source # |
class HasVerbosity s where Source #
Types with verbosity.
getVerbosity :: s -> Verbosity Source #
Instances
HasVerbosity (Environment a) Source # | |
Defined in ELynx.Tools.Environment getVerbosity :: Environment a -> Verbosity Source # |
type Logger e a = ReaderT e IO a Source #
Reader transformer used for logging to a file and to standard output.
:: (HasLogHandles e, HasLock e) | |
=> ByteString | Prefix. |
-> ByteString | Message. |
-> Logger e () |
Write to standard output and maybe to log file.
logDebugB :: (HasLock e, HasLogHandles e, HasVerbosity e) => ByteString -> Logger e () Source #
Log debug message.
logDebugS :: (HasLock e, HasLogHandles e, HasVerbosity e) => String -> Logger e () Source #
Log debug message.
logWarnB :: (HasLock e, HasLogHandles e, HasVerbosity e) => ByteString -> Logger e () Source #
Log warning message.
logWarnS :: (HasLock e, HasLogHandles e, HasVerbosity e) => String -> Logger e () Source #
Log warning message.
logInfoB :: (HasLock e, HasLogHandles e, HasVerbosity e) => ByteString -> Logger e () Source #
Log info message.
logInfoS :: (HasLock e, HasLogHandles e, HasVerbosity e) => String -> Logger e () Source #
Log info message.
logInfoHeader :: (HasLock e, HasLogHandles e, HasStartingTime e, HasVerbosity e) => String -> [String] -> Logger e () Source #
Log header.
logInfoFooter :: (HasLock e, HasLogHandles e, HasStartingTime e, HasVerbosity e) => Logger e () Source #
Log footer.
logInfoNewSection :: (HasLock e, HasLogHandles e, HasVerbosity e) => String -> Logger e () Source #
Unified way of creating a new section in the log.
Weird stuff
compose :: [a -> a] -> a -> a Source #
Chain a list of functions together. See https://wiki.haskell.org/Compose.
Numeric
Command options
Random or fixed seed.
Instances
Eq SeedOpt Source # | |
Show SeedOpt Source # | |
Generic SeedOpt Source # | |
ToJSON SeedOpt Source # | |
Defined in ELynx.Tools.Reproduction | |
FromJSON SeedOpt Source # | |
type Rep SeedOpt Source # | |
Defined in ELynx.Tools.Reproduction type Rep SeedOpt = D1 ('MetaData "SeedOpt" "ELynx.Tools.Reproduction" "elynx-tools-0.6.0.0-C9yWy4KiDAwCuzNwLVWAR7" 'False) (C1 ('MetaCons "RandomUnset" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "RandomSet" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector Word32))) :+: C1 ('MetaCons "Fixed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector Word32))))) |
Arguments
data GlobalArguments Source #
A set of global arguments used by all programs. The idea is to provide a common framework for shared arguments.
Instances
Argument skeleton to be used with all commands.
Arguments | |
|
Instances
Eq a => Eq (Arguments a) Source # | |
Show a => Show (Arguments a) Source # | |
Generic (Arguments a) Source # | |
ToJSON a => ToJSON (Arguments a) Source # | |
Defined in ELynx.Tools.Options | |
FromJSON a => FromJSON (Arguments a) Source # | |
Reproducible a => Reproducible (Arguments a) Source # | |
type Rep (Arguments a) Source # | |
Defined in ELynx.Tools.Options type Rep (Arguments a) = D1 ('MetaData "Arguments" "ELynx.Tools.Options" "elynx-tools-0.6.0.0-C9yWy4KiDAwCuzNwLVWAR7" 'False) (C1 ('MetaCons "Arguments" 'PrefixI 'True) (S1 ('MetaSel ('Just "global") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GlobalArguments) :*: S1 ('MetaSel ('Just "local") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))) |
Misc
parseArguments :: forall a. Reproducible a => IO (Arguments a) Source #
Parse arguments. Provide a global description, header, footer, and so on. Custom additional description (first argument) and footer (second argument) can be provided. print help if needed.
elynxParserInfo :: [String] -> [String] -> Parser a -> ParserInfo a Source #
ELynx parser info; convenience function.
createCommandReproducible :: forall a b. Reproducible a => (a -> b) -> Mod CommandFields b Source #
Create a command; convenience function.
createCommand :: String -> [String] -> [String] -> Parser a -> (a -> b) -> Mod CommandFields b Source #
Create a command; convenience function.
elynxFooter :: [Doc] Source #
Reproduction
Random or fixed seed.
Instances
Eq SeedOpt Source # | |
Show SeedOpt Source # | |
Generic SeedOpt Source # | |
ToJSON SeedOpt Source # | |
Defined in ELynx.Tools.Reproduction | |
FromJSON SeedOpt Source # | |
type Rep SeedOpt Source # | |
Defined in ELynx.Tools.Reproduction type Rep SeedOpt = D1 ('MetaData "SeedOpt" "ELynx.Tools.Reproduction" "elynx-tools-0.6.0.0-C9yWy4KiDAwCuzNwLVWAR7" 'False) (C1 ('MetaCons "RandomUnset" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "RandomSet" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector Word32))) :+: C1 ('MetaCons "Fixed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector Word32))))) |
class Reproducible a where Source #
Reproducible commands have - a set of input files to be checked for consistency, - a set of output suffixes which define output files to be checked for consistency, - a function to get the seed, if available, - a function to set the seed, if applicable, - a parser to read the command line, - a nice program name, description, and footer.
inFiles :: a -> [FilePath] Source #
outSuffixes :: a -> [String] Source #
getSeed :: a -> Maybe SeedOpt Source #
Instances
Reproducible a => Reproducible (Arguments a) Source # | |
getReproductionHash :: forall a. Reproducible a => Reproduction a -> String Source #
A unique hash of the reproduction data type.
data Reproduction a Source #
Necessary information for a reproducible run. Notably, the input files are checked for consistency!
Instances
writeReproduction :: forall a. (Eq a, Show a, Reproducible a, ToJSON a) => String -> a -> IO () Source #
Write an ELynx reproduction file.
Re-exports
Representable types of kind *
.
This class is derivable in GHC with the DeriveGeneric
flag on.
A Generic
instance must satisfy the following laws:
from
.to
≡id
to
.from
≡id
Instances
A type that can be converted from JSON, with the possibility of failure.
In many cases, you can get the compiler to generate parsing code for you (see below). To begin, let's cover writing an instance by hand.
There are various reasons a conversion could fail. For example, an
Object
could be missing a required key, an Array
could be of
the wrong size, or a value could be of an incompatible type.
The basic ways to signal a failed conversion are as follows:
fail
yields a custom error message: it is the recommended way of reporting a failure;empty
(ormzero
) is uninformative: use it when the error is meant to be caught by some(
;<|>
)typeMismatch
can be used to report a failure when the encountered value is not of the expected JSON type;unexpected
is an appropriate alternative when more than one type may be expected, or to keep the expected type implicit.
prependFailure
(or modifyFailure
) add more information to a parser's
error messages.
An example type and instance using typeMismatch
and prependFailure
:
-- Allow ourselves to writeText
literals. {-# LANGUAGE OverloadedStrings #-} data Coord = Coord { x :: Double, y :: Double } instanceFromJSON
Coord whereparseJSON
(Object
v) = Coord<$>
v.:
"x"<*>
v.:
"y" -- We do not expect a non-Object
value here. -- We could useempty
to fail, buttypeMismatch
-- gives a much more informative error message.parseJSON
invalid =prependFailure
"parsing Coord failed, " (typeMismatch
"Object" invalid)
For this common case of only being concerned with a single
type of JSON value, the functions withObject
, withScientific
, etc.
are provided. Their use is to be preferred when possible, since
they are more terse. Using withObject
, we can rewrite the above instance
(assuming the same language extension and data type) as:
instanceFromJSON
Coord whereparseJSON
=withObject
"Coord" $ \v -> Coord<$>
v.:
"x"<*>
v.:
"y"
Instead of manually writing your FromJSON
instance, there are two options
to do it automatically:
- Data.Aeson.TH provides Template Haskell functions which will derive an instance at compile time. The generated instance is optimized for your type so it will probably be more efficient than the following option.
- The compiler can provide a default generic implementation for
parseJSON
.
To use the second, simply add a deriving
clause to your
datatype and declare a Generic
FromJSON
instance for your datatype without giving
a definition for parseJSON
.
For example, the previous example can be simplified to just:
{-# LANGUAGE DeriveGeneric #-} import GHC.Generics data Coord = Coord { x :: Double, y :: Double } derivingGeneric
instanceFromJSON
Coord
The default implementation will be equivalent to
parseJSON =
; if you need different
options, you can customize the generic decoding by defining:genericParseJSON
defaultOptions
customOptions =defaultOptions
{fieldLabelModifier
=map
toUpper
} instanceFromJSON
Coord whereparseJSON
=genericParseJSON
customOptions
Instances
A type that can be converted to JSON.
Instances in general must specify toJSON
and should (but don't need
to) specify toEncoding
.
An example type and instance:
-- Allow ourselves to writeText
literals. {-# LANGUAGE OverloadedStrings #-} data Coord = Coord { x :: Double, y :: Double } instanceToJSON
Coord wheretoJSON
(Coord x y) =object
["x".=
x, "y".=
y]toEncoding
(Coord x y) =pairs
("x".=
x<>
"y".=
y)
Instead of manually writing your ToJSON
instance, there are two options
to do it automatically:
- Data.Aeson.TH provides Template Haskell functions which will derive an instance at compile time. The generated instance is optimized for your type so it will probably be more efficient than the following option.
- The compiler can provide a default generic implementation for
toJSON
.
To use the second, simply add a deriving
clause to your
datatype and declare a Generic
ToJSON
instance. If you require nothing other than
defaultOptions
, it is sufficient to write (and this is the only
alternative where the default toJSON
implementation is sufficient):
{-# LANGUAGE DeriveGeneric #-} import GHC.Generics data Coord = Coord { x :: Double, y :: Double } derivingGeneric
instanceToJSON
Coord wheretoEncoding
=genericToEncoding
defaultOptions
If on the other hand you wish to customize the generic decoding, you have to implement both methods:
customOptions =defaultOptions
{fieldLabelModifier
=map
toUpper
} instanceToJSON
Coord wheretoJSON
=genericToJSON
customOptionstoEncoding
=genericToEncoding
customOptions
Previous versions of this library only had the toJSON
method. Adding
toEncoding
had two reasons:
- toEncoding is more efficient for the common case that the output of
toJSON
is directly serialized to aByteString
. Further, expressing either method in terms of the other would be non-optimal. - The choice of defaults allows a smooth transition for existing users:
Existing instances that do not define
toEncoding
still compile and have the correct semantics. This is ensured by making the default implementation oftoEncoding
usetoJSON
. This produces correct results, but since it performs an intermediate conversion to aValue
, it will be less efficient than directly emitting anEncoding
. (this also means that specifying nothing more thaninstance ToJSON Coord
would be sufficient as a generically decoding instance, but there probably exists no good reason to not specifytoEncoding
in new instances.)