aeson-flowtyped-0.8.1: Create Flow type definitions from Haskell data types.

Safe HaskellNone
LanguageHaskell2010

Data.Aeson.Flow

Contents

Description

Derive Flow types using aeson Options.

Synopsis

AST types

class Typeable a => FlowTyped a where Source #

Instances

FlowTyped Bool Source # 
FlowTyped Char Source # 
FlowTyped Double Source # 
FlowTyped Float Source # 
FlowTyped Int Source # 
FlowTyped Int8 Source # 
FlowTyped Int16 Source # 
FlowTyped Int32 Source # 
FlowTyped Int64 Source # 
FlowTyped Word Source # 
FlowTyped Word8 Source # 
FlowTyped Word16 Source # 
FlowTyped Word32 Source # 
FlowTyped Word64 Source # 
FlowTyped () Source # 
FlowTyped Scientific Source # 
FlowTyped String Source # 
FlowTyped Text Source # 
FlowTyped UTCTime Source # 
FlowTyped Value Source # 
FlowTyped Text Source # 
FlowTyped Void Source # 
FlowTyped IntSet Source # 
FlowTyped a => FlowTyped [a] Source # 
FlowTyped a => FlowTyped (Maybe a) Source # 
Typeable * a => FlowTyped (Fixed a) Source # 
Typeable * a => FlowTyped (Tree a) Source #

This instance is defined recursively. You'll probably need to use dependencies to extract a usable definition

FlowTyped a => FlowTyped (Set a) Source # 
FlowTyped a => FlowTyped (HashSet a) Source # 
FlowTyped a => FlowTyped (Vector a) Source # 
FlowTyped a => FlowTyped (Vector a) Source # 
FlowTyped a => FlowTyped (Vector a) Source # 
(FlowTyped a, FlowTyped b) => FlowTyped (Either a b) Source # 
(FlowTyped a, FlowTyped b) => FlowTyped (a, b) Source # 

Methods

flowType :: Proxy * (a, b) -> FlowType Source #

flowTypeName :: Proxy * (a, b) -> Maybe Text Source #

flowTypeVars :: Proxy * (a, b) -> [TypeRep] Source #

flowOptions :: Proxy * (a, b) -> Options Source #

isPrim :: Proxy * (a, b) -> Bool Source #

FlowTyped a => FlowTyped (HashMap Text a) Source #

This is at odds with "aeson" which defines ToJSONKey

(Typeable k2 a, Typeable * k2) => FlowTyped (Var k2 a) Source # 
(FlowTyped a, FlowTyped b, FlowTyped c) => FlowTyped (a, b, c) Source # 

Methods

flowType :: Proxy * (a, b, c) -> FlowType Source #

flowTypeName :: Proxy * (a, b, c) -> Maybe Text Source #

flowTypeVars :: Proxy * (a, b, c) -> [TypeRep] Source #

flowOptions :: Proxy * (a, b, c) -> Options Source #

isPrim :: Proxy * (a, b, c) -> Bool Source #

newtype Fix f :: (* -> *) -> * #

Constructors

Fix (f (Fix f)) 

Instances

Eq1 f => Eq (Fix f) 

Methods

(==) :: Fix f -> Fix f -> Bool #

(/=) :: Fix f -> Fix f -> Bool #

(Typeable (* -> *) f, Data (f (Fix f))) => Data (Fix f) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Fix f -> c (Fix f) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Fix f) #

toConstr :: Fix f -> Constr #

dataTypeOf :: Fix f -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Fix f)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Fix f)) #

gmapT :: (forall b. Data b => b -> b) -> Fix f -> Fix f #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Fix f -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Fix f -> r #

gmapQ :: (forall d. Data d => d -> u) -> Fix f -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Fix f -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Fix f -> m (Fix f) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Fix f -> m (Fix f) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Fix f -> m (Fix f) #

Ord1 f => Ord (Fix f) 

Methods

compare :: Fix f -> Fix f -> Ordering #

(<) :: Fix f -> Fix f -> Bool #

(<=) :: Fix f -> Fix f -> Bool #

(>) :: Fix f -> Fix f -> Bool #

(>=) :: Fix f -> Fix f -> Bool #

max :: Fix f -> Fix f -> Fix f #

min :: Fix f -> Fix f -> Fix f #

Read1 f => Read (Fix f) 
Show1 f => Show (Fix f) 

Methods

showsPrec :: Int -> Fix f -> ShowS #

show :: Fix f -> String #

showList :: [Fix f] -> ShowS #

Functor f => Recursive (Fix f) 

Methods

project :: Fix f -> Base (Fix f) (Fix f) #

cata :: (Base (Fix f) a -> a) -> Fix f -> a #

para :: (Base (Fix f) (Fix f, a) -> a) -> Fix f -> a #

gpara :: (Corecursive (Fix f), Comonad w) => (forall b. Base (Fix f) (w b) -> w (Base (Fix f) b)) -> (Base (Fix f) (EnvT (Fix f) w a) -> a) -> Fix f -> a #

prepro :: Corecursive (Fix f) => (forall b. Base (Fix f) b -> Base (Fix f) b) -> (Base (Fix f) a -> a) -> Fix f -> a #

gprepro :: (Corecursive (Fix f), Comonad w) => (forall b. Base (Fix f) (w b) -> w (Base (Fix f) b)) -> (forall c. Base (Fix f) c -> Base (Fix f) c) -> (Base (Fix f) (w a) -> a) -> Fix f -> a #

Functor f => Corecursive (Fix f) 

Methods

embed :: Base (Fix f) (Fix f) -> Fix f #

ana :: (a -> Base (Fix f) a) -> a -> Fix f #

apo :: (a -> Base (Fix f) (Either (Fix f) a)) -> a -> Fix f #

postpro :: Recursive (Fix f) => (forall b. Base (Fix f) b -> Base (Fix f) b) -> (a -> Base (Fix f) a) -> a -> Fix f #

gpostpro :: (Recursive (Fix f), Monad m) => (forall b. m (Base (Fix f) b) -> Base (Fix f) (m b)) -> (forall c. Base (Fix f) c -> Base (Fix f) c) -> (a -> Base (Fix f) (m a)) -> a -> Fix f #

type Base (Fix f) 
type Base (Fix f) = f

data FlowTypeF a Source #

The main AST for flowtypes.

Instances

Functor FlowTypeF Source # 

Methods

fmap :: (a -> b) -> FlowTypeF a -> FlowTypeF b #

(<$) :: a -> FlowTypeF b -> FlowTypeF a #

Foldable FlowTypeF Source # 

Methods

fold :: Monoid m => FlowTypeF m -> m #

foldMap :: Monoid m => (a -> m) -> FlowTypeF a -> m #

foldr :: (a -> b -> b) -> b -> FlowTypeF a -> b #

foldr' :: (a -> b -> b) -> b -> FlowTypeF a -> b #

foldl :: (b -> a -> b) -> b -> FlowTypeF a -> b #

foldl' :: (b -> a -> b) -> b -> FlowTypeF a -> b #

foldr1 :: (a -> a -> a) -> FlowTypeF a -> a #

foldl1 :: (a -> a -> a) -> FlowTypeF a -> a #

toList :: FlowTypeF a -> [a] #

null :: FlowTypeF a -> Bool #

length :: FlowTypeF a -> Int #

elem :: Eq a => a -> FlowTypeF a -> Bool #

maximum :: Ord a => FlowTypeF a -> a #

minimum :: Ord a => FlowTypeF a -> a #

sum :: Num a => FlowTypeF a -> a #

product :: Num a => FlowTypeF a -> a #

Traversable FlowTypeF Source # 

Methods

traverse :: Applicative f => (a -> f b) -> FlowTypeF a -> f (FlowTypeF b) #

sequenceA :: Applicative f => FlowTypeF (f a) -> f (FlowTypeF a) #

mapM :: Monad m => (a -> m b) -> FlowTypeF a -> m (FlowTypeF b) #

sequence :: Monad m => FlowTypeF (m a) -> m (FlowTypeF a) #

Show1 FlowTypeF Source # 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> FlowTypeF a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [FlowTypeF a] -> ShowS #

Eq a => Eq (FlowTypeF a) Source # 

Methods

(==) :: FlowTypeF a -> FlowTypeF a -> Bool #

(/=) :: FlowTypeF a -> FlowTypeF a -> Bool #

Show a => Show (FlowTypeF a) Source # 

Code generation

Wholesale ES6/flow modules

data Export where Source #

Constructors

Export :: FlowTyped a => Proxy a -> Export 

exportFlowTypeAs :: Text -> FlowType -> Text Source #

Generate a export type declaration.

Utility functions

showFlowType :: FlowType -> Text Source #

Pretty-print a flowtype in flowtype syntax

dependencies :: FlowTyped a => Proxy a -> Set FlowName Source #

Compute all the dependencies of a FlowTyped thing, including itself.

Internals

defaultFlowTypeName :: (Generic a, Rep a ~ D1 (MetaData name mod pkg t) c, KnownSymbol name) => Proxy a -> Maybe Text Source #

data FlowName where Source #

A name for a flowtyped data-type. These are returned by dependencies.

Constructors

FlowName :: (Typeable a, FlowTyped a) => Proxy a -> Text -> FlowName 

class GFlowTyped g Source #

Minimal complete definition

gflowType

Instances

(KnownSymbol name, GFlowVal * * c) => GFlowTyped (D1 (MetaData name mod pkg t) c) Source # 

Methods

gflowType :: Options -> Proxy * (D1 (MetaData name mod pkg t) c x) -> FlowType

data Info a Source #

Constructors

Constr !Text FlowTypeI a 
NoInfo a 

Instances

Functor Info Source # 

Methods

fmap :: (a -> b) -> Info a -> Info b #

(<$) :: a -> Info b -> Info a #

Foldable Info Source # 

Methods

fold :: Monoid m => Info m -> m #

foldMap :: Monoid m => (a -> m) -> Info a -> m #

foldr :: (a -> b -> b) -> b -> Info a -> b #

foldr' :: (a -> b -> b) -> b -> Info a -> b #

foldl :: (b -> a -> b) -> b -> Info a -> b #

foldl' :: (b -> a -> b) -> b -> Info a -> b #

foldr1 :: (a -> a -> a) -> Info a -> a #

foldl1 :: (a -> a -> a) -> Info a -> a #

toList :: Info a -> [a] #

null :: Info a -> Bool #

length :: Info a -> Int #

elem :: Eq a => a -> Info a -> Bool #

maximum :: Ord a => Info a -> a #

minimum :: Ord a => Info a -> a #

sum :: Num a => Info a -> a #

product :: Num a => Info a -> a #

Traversable Info Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Info a -> f (Info b) #

sequenceA :: Applicative f => Info (f a) -> f (Info a) #

mapM :: Monad m => (a -> m b) -> Info a -> m (Info b) #

sequence :: Monad m => Info (m a) -> m (Info a) #

Show1 Info Source # 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Info a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Info a] -> ShowS #

Show a => Show (Info a) Source # 

Methods

showsPrec :: Int -> Info a -> ShowS #

show :: Info a -> String #

showList :: [Info a] -> ShowS #

data Var :: k -> Type where Source #

Constructors

Var :: Var a 

Instances

(Typeable k2 a, Typeable * k2) => FlowTyped (Var k2 a) Source # 

class Typeable k a #

The class Typeable allows a concrete representation of a type to be calculated.

Minimal complete definition

typeRep#

typeRep :: Typeable k a => proxy a -> TypeRep #

Takes a value of type a and returns a concrete representation of that type.

Since: 4.7.0.0