| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Aeson.Flow
Description
Derive Flow types using aeson Options.
- class Typeable a => FlowTyped a where
- type FlowType = Fix FlowTypeF
- data FlowTypeF a
- data FlowModuleOptions = FlowModuleOptions {
- flowPragmas :: [Text]
- flowHeader :: [Text]
- defaultFlowModuleOptions :: FlowModuleOptions
- data Export where
- generateFlowModule :: FlowModuleOptions -> [Export] -> Text
- writeFlowModule :: FlowModuleOptions -> FilePath -> [Export] -> IO ()
- exportFlowTypeAs :: Text -> FlowType -> Text
- showFlowType :: FlowType -> Text
- dependencies :: FlowTyped a => Proxy a -> Set FlowName
- defaultFlowType :: (Generic a, GFlowTyped (Rep a)) => Options -> Proxy a -> FlowType
- defaultFlowTypeName :: (Generic a, Rep a ~ D1 (MetaData name mod pkg t) c, KnownSymbol name) => Proxy a -> Maybe Text
- data FlowName where
- data PrimType
- class GFlowTyped g
- type FlowTypeI = Fix (Info `Compose` FlowTypeF)
- data Info a
- newtype Var = Var {}
AST types
class Typeable a => FlowTyped a where Source #
Methods
flowType :: Proxy a -> FlowType Source #
flowTypeName :: Proxy a -> Maybe Text Source #
flowOptions :: Proxy a -> Options Source #
isPrim :: Proxy a -> Bool Source #
flowType :: (Generic a, GFlowTyped (Rep a)) => Proxy a -> FlowType Source #
flowTypeName :: (Generic a, Rep a ~ D1 (MetaData name mod pkg t) c, KnownSymbol name) => Proxy a -> Maybe Text 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 Scientific Source # | |
| FlowTyped String Source # | |
| FlowTyped Text Source # | |
| FlowTyped UTCTime Source # | |
| FlowTyped Value Source # | |
| FlowTyped Text Source # | |
| FlowTyped Void Source # | |
| FlowTyped a => FlowTyped [a] Source # | |
| FlowTyped a => FlowTyped (Maybe a) Source # | |
| Typeable * a => FlowTyped (Fixed 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 # | |
| (FlowTyped a, FlowTyped b, FlowTyped c) => FlowTyped (a, b, c) Source # | |
The main AST for flowtypes.
Code generation
Wholesale ES6/flow modules
data FlowModuleOptions Source #
Constructors
| FlowModuleOptions | |
Fields
| |
Instances
generateFlowModule :: FlowModuleOptions -> [Export] -> Text Source #
writeFlowModule :: FlowModuleOptions -> FilePath -> [Export] -> IO () Source #
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
defaultFlowType :: (Generic a, GFlowTyped (Rep a)) => Options -> Proxy a -> FlowType Source #
defaultFlowTypeName :: (Generic a, Rep a ~ D1 (MetaData name mod pkg t) c, KnownSymbol name) => Proxy a -> Maybe Text Source #
flowTypeName using Generic
A name for a flowtyped data-type. These are returned by dependencies.
A primitive flow/javascript type
class GFlowTyped g Source #
Minimal complete definition
gflowType
Instances
| (KnownSymbol name, GFlowVal * * c) => GFlowTyped (D1 (MetaData name mod pkg t) c) Source # | |