reflection-extras-0.1.1.0: Utilities for the reflection package

Safe HaskellNone

Data.Reflection.Extras

Synopsis

Documentation

using :: forall p a. ReifiableConstraint p => Def p a -> (p a => a) -> aSource

Choose a dictionary for a local type class instance.

>>> using (Monoid (+) 0) $ mempty <> 10 <> 12
> 12

usingT :: forall p f a. ReifiableConstraint p => Def p a -> (p a => f a) -> f aSource

reifyInstance :: Def p a -> (forall s. Reifies s (Def p a) => Proxy s -> r) -> rSource

with :: forall p a. Def p a -> (forall s. Reifies s (Def p a) => Lift p s a) -> aSource

data Lift p s a Source

Instances

Functor (Lift p s) 
Applicative (Lift p s) 
Reifies * s (Def Bounded a) => Bounded (Lift Bounded s a) 
Reifies * s (Def Enum a) => Enum (Lift Enum s a) 
Reifies * s (Def Eq a) => Eq (Lift Eq s a) 
Reifies * s (Def Ord a) => Eq (Lift Ord s a) 
Reifies * s (Def Real a) => Eq (Lift Real s a) 
Reifies * s (Def Num a) => Num (Lift Num s a) 
Reifies * s (Def Real a) => Num (Lift Real s a) 
Reifies * s (Def Ord a) => Ord (Lift Ord s a) 
Reifies * s (Def Real a) => Ord (Lift Real s a) 
Reifies * s (Def Read a) => Read (Lift Read s a) 
Reifies * s (Def Real a) => Real (Lift Real s a) 
Reifies * s (Def Show a) => Show (Lift Show s a) 
Reifies * s (Def ToJSON a) => ToJSON (Lift ToJSON s a) 
Reifies * s (Def FromJSON a) => FromJSON (Lift FromJSON s a) 
Reifies * s (Def Monoid a) => Monoid (Lift Monoid s a) 

class Reifies s a | s -> a where

Methods

reflect :: proxy s -> a

Recover a value inside a reify context, given a proxy for its reified type.

Instances

Reifies * Z Int 
Reifies * n Int => Reifies * (D n) Int 
Reifies * n Int => Reifies * (SD n) Int 
Reifies * n Int => Reifies * (PD n) Int 

class FromJSON a where

A type that can be converted from JSON, with the possibility of failure.

When writing an instance, use empty, mzero, or fail to make a conversion fail, e.g. if an Object is missing a required key, or the value is of the wrong type.

An example type and instance:

{-# LANGUAGE OverloadedStrings #-}

data Coord { x :: Double, y :: Double }

instance FromJSON Coord where
   parseJSON (Object v) = Coord    <$>
                          v .: "x" <*>
                          v .: "y"

-- A non-Object value is of the wrong type, so use mzero to fail.
   parseJSON _          = mzero

Note the use of the OverloadedStrings language extension which enables Text values to be written as string literals.

Instead of manually writing your FromJSON instance, there are three 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 will probably be more efficient than the following two options:
  • Data.Aeson.Generic provides a generic fromJSON function that parses to any type which is an instance of Data.
  • If your compiler has support for the DeriveGeneric and DefaultSignatures language extensions, parseJSON will have a default generic implementation.

To use this, simply add a deriving Generic clause to your datatype and declare a 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 { x :: Double, y :: Double } deriving Generic

instance FromJSON Coord

Note that, instead of using DefaultSignatures, it's also possible to parameterize the generic decoding using genericParseJSON applied to your encoding/decoding Options:

 instance FromJSON Coord where
     parseJSON = genericParseJSON defaultOptions

Methods

parseJSON :: Value -> Parser a

Instances

FromJSON Bool 
FromJSON Char 
FromJSON Double 
FromJSON Float 
FromJSON Int 
FromJSON Int8 
FromJSON Int16 
FromJSON Int32 
FromJSON Int64 
FromJSON Integer 
FromJSON Word 
FromJSON Word8 
FromJSON Word16 
FromJSON Word32 
FromJSON Word64 
FromJSON () 
FromJSON ByteString 
FromJSON ByteString 
FromJSON Number 
FromJSON Text 
FromJSON UTCTime 
FromJSON DotNetTime 
FromJSON Value 
FromJSON Text 
FromJSON IntSet 
FromJSON ZonedTime 
FromJSON [Char] 
FromJSON a => FromJSON [a] 
FromJSON (Ratio Integer) 
FromJSON a => FromJSON (Maybe a) 
HasResolution a => FromJSON (Fixed a) 
FromJSON a => FromJSON (Dual a) 
FromJSON a => FromJSON (First a) 
FromJSON a => FromJSON (Last a) 
FromJSON a => FromJSON (IntMap a) 
(Ord a, FromJSON a) => FromJSON (Set a) 
(Prim a, FromJSON a) => FromJSON (Vector a) 
(Storable a, FromJSON a) => FromJSON (Vector a) 
(Vector Vector a, FromJSON a) => FromJSON (Vector a) 
FromJSON a => FromJSON (Vector a) 
(Eq a, Hashable a, FromJSON a) => FromJSON (HashSet a) 
(FromJSON a, FromJSON b) => FromJSON (Either a b) 
(FromJSON a, FromJSON b) => FromJSON (a, b) 
FromJSON v => FromJSON (HashMap String v) 
FromJSON v => FromJSON (HashMap ByteString v) 
FromJSON v => FromJSON (HashMap ByteString v) 
FromJSON v => FromJSON (HashMap Text v) 
FromJSON v => FromJSON (HashMap Text v) 
FromJSON v => FromJSON (Map String v) 
FromJSON v => FromJSON (Map ByteString v) 
FromJSON v => FromJSON (Map ByteString v) 
FromJSON v => FromJSON (Map Text v) 
FromJSON v => FromJSON (Map Text v) 
(FromJSON a, FromJSON b, FromJSON c) => FromJSON (a, b, c) 
Reifies * s (Def FromJSON a) => FromJSON (Lift FromJSON s a) 
(FromJSON a, FromJSON b, FromJSON c, FromJSON d) => FromJSON (a, b, c, d) 

class ToJSON a where

A type that can be converted to JSON.

An example type and instance:

{-# LANGUAGE OverloadedStrings #-}

data Coord { x :: Double, y :: Double }

instance ToJSON Coord where
   toJSON (Coord x y) = object ["x" .= x, "y" .= y]

Note the use of the OverloadedStrings language extension which enables Text values to be written as string literals.

Instead of manually writing your ToJSON instance, there are three 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 will probably be more efficient than the following two options:
  • Data.Aeson.Generic provides a generic toJSON function that accepts any type which is an instance of Data.
  • If your compiler has support for the DeriveGeneric and DefaultSignatures language extensions (GHC 7.2 and newer), toJSON will have a default generic implementation.

To use the latter option, simply add a deriving Generic clause to your datatype and declare a ToJSON instance for your datatype without giving a definition for toJSON.

For example the previous example can be simplified to just:

{-# LANGUAGE DeriveGeneric #-}

import GHC.Generics

data Coord { x :: Double, y :: Double } deriving Generic

instance ToJSON Coord

Note that, instead of using DefaultSignatures, it's also possible to parameterize the generic encoding using genericToJSON applied to your encoding/decoding Options:

 instance ToJSON Coord where
     toJSON = genericToJSON defaultOptions

Methods

toJSON :: a -> Value

Instances