Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Derive Flow types using aeson Options
.
Does not currently support the unwrapUnaryRecords
option.
Synopsis
- class Typeable a => FlowTyped a where
- callType :: forall a. FlowTyped a => Proxy a -> FlowType
- data FlowTypeF a
- type FlowType = Fix FlowTypeF
- pattern FObject :: HashMap Text FlowType -> FlowType
- pattern FExactObject :: HashMap Text FlowType -> FlowType
- pattern FObjectMap :: Text -> FlowType -> FlowType -> FlowType
- pattern FArray :: FlowType -> FlowType
- pattern FTuple :: Vector FlowType -> FlowType
- pattern FLabelledTuple :: Vector (Maybe Text, FlowType) -> FlowType
- pattern FFun :: Vector (Text, FlowType) -> FlowType -> FlowType
- pattern FAlt :: FlowType -> FlowType -> FlowType
- pattern FPrim :: PrimType -> FlowType
- pattern FPrimBoolean :: FlowType
- pattern FPrimNumber :: FlowType
- pattern FPrimString :: FlowType
- pattern FPrimBottom :: FlowType
- pattern FPrimMixed :: FlowType
- pattern FPrimUnknown :: FlowType
- pattern FPrimNull :: FlowType
- pattern FPrimNever :: FlowType
- pattern FPrimUndefined :: FlowType
- pattern FPrimAny :: FlowType
- pattern FNullable :: FlowType -> FlowType
- pattern FOmitable :: FlowType -> FlowType
- pattern FLiteral :: Value -> FlowType
- pattern FTag :: Text -> FlowType
- pattern FName :: FlowName -> FlowType
- pattern FGenericParam :: Int -> FlowType
- pattern FCallType :: FlowName -> [FlowType] -> FlowType
- data Export
- export :: forall a. FlowTyped a => Export
- data RenderMode
- data RenderOptions = RenderOptions {
- renderMode :: !RenderMode
- data ModuleOptions = ModuleOptions {
- pragmas :: [Text]
- header :: [Text]
- exportDeps :: Bool
- computeDeps :: Bool
- renderOptions :: RenderOptions
- typeScriptModuleOptions :: ModuleOptions
- flowModuleOptions :: ModuleOptions
- generateModule :: ModuleOptions -> [Export] -> Text
- writeModule :: ModuleOptions -> FilePath -> [Export] -> IO ()
- showTypeAs :: RenderOptions -> Bool -> Text -> FlowType -> [Flowable] -> Text
- exportTypeAs :: RenderOptions -> Text -> FlowType -> [Flowable] -> Text
- data FlowTyFields :: * -> [k] -> * where
- FlowTyFields :: FlowTyFields k fs
- type family FlowDeconstructField (k :: t) :: (Symbol, *)
- showTypeScriptType :: FlowType -> [Flowable] -> Text
- showFlowType :: FlowType -> [Flowable] -> Text
- exportsDependencies :: [Export] -> Set FlowName
- dependencies :: FlowTyped a => Proxy a -> Set FlowName
- data FlowName where
- data Flowable where
- defaultFlowTypeName :: (Generic a, Rep a ~ D1 ('MetaData name mod pkg t) c, KnownSymbol name) => Proxy a -> Maybe Text
- defaultFlowType :: (HasDatatypeInfo a, All2 FlowTyped (Code a)) => Options -> Proxy a -> FlowType
AST types
class Typeable a => FlowTyped a where Source #
Nothing
flowType :: Proxy a -> FlowType Source #
flowTypeName :: Proxy a -> Maybe Text Source #
default flowTypeName :: (Generic a, Rep a ~ D1 ('MetaData name mod pkg t) c, KnownSymbol name) => Proxy a -> Maybe Text Source #
flowTypeVars :: Proxy a -> [Flowable] Source #
flowOptions :: Proxy a -> Options Source #
Instances
The main AST for flowtypes.
Instances
Foldable FlowTypeF Source # | |
Defined in Data.Aeson.Flow fold :: Monoid m => FlowTypeF m -> m # foldMap :: Monoid m => (a -> m) -> FlowTypeF a -> 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] # length :: FlowTypeF a -> Int # elem :: Eq a => a -> FlowTypeF a -> Bool # maximum :: Ord a => FlowTypeF a -> a # minimum :: Ord a => FlowTypeF a -> a # | |
Eq1 FlowTypeF Source # | |
Show1 FlowTypeF Source # | |
Traversable FlowTypeF Source # | |
Functor FlowTypeF Source # | |
Show a => Show (FlowTypeF a) Source # | |
Eq a => Eq (FlowTypeF a) Source # | |
pattern FPrimBoolean :: FlowType Source #
pattern FPrimNumber :: FlowType Source #
pattern FPrimString :: FlowType Source #
pattern FPrimBottom :: FlowType Source #
pattern FPrimMixed :: FlowType Source #
pattern FPrimUnknown :: FlowType Source #
pattern FPrimNever :: FlowType Source #
pattern FPrimUndefined :: FlowType Source #
pattern FGenericParam :: Int -> FlowType Source #
Code generation
Wholesale ES6flowtypescript modules
data RenderMode Source #
Instances
Show RenderMode Source # | |
Defined in Data.Aeson.Flow showsPrec :: Int -> RenderMode -> ShowS # show :: RenderMode -> String # showList :: [RenderMode] -> ShowS # | |
Eq RenderMode Source # | |
Defined in Data.Aeson.Flow (==) :: RenderMode -> RenderMode -> Bool # (/=) :: RenderMode -> RenderMode -> Bool # |
data RenderOptions Source #
Instances
Show RenderOptions Source # | |
Defined in Data.Aeson.Flow showsPrec :: Int -> RenderOptions -> ShowS # show :: RenderOptions -> String # showList :: [RenderOptions] -> ShowS # | |
Eq RenderOptions Source # | |
Defined in Data.Aeson.Flow (==) :: RenderOptions -> RenderOptions -> Bool # (/=) :: RenderOptions -> RenderOptions -> Bool # |
data ModuleOptions Source #
ModuleOptions | |
|
Instances
Show ModuleOptions Source # | |
Defined in Data.Aeson.Flow showsPrec :: Int -> ModuleOptions -> ShowS # show :: ModuleOptions -> String # showList :: [ModuleOptions] -> ShowS # | |
Eq ModuleOptions Source # | |
Defined in Data.Aeson.Flow (==) :: ModuleOptions -> ModuleOptions -> Bool # (/=) :: ModuleOptions -> ModuleOptions -> Bool # |
generateModule :: ModuleOptions -> [Export] -> Text Source #
writeModule :: ModuleOptions -> FilePath -> [Export] -> IO () Source #
showTypeAs :: RenderOptions -> Bool -> Text -> FlowType -> [Flowable] -> Text Source #
Generate a type
declaration, possibly an export.
exportTypeAs :: RenderOptions -> Text -> FlowType -> [Flowable] -> Text Source #
Generate a export type
declaration.
Convenience for generating flowtypes from other types
data FlowTyFields :: * -> [k] -> * where Source #
Useful for declaring flowtypes from type-level key/value sets, like
FlowTyFields :: FlowTyFields Person '['("name", String), '("email", String)]
FlowTyFields :: FlowTyFields k fs |
Instances
(FlowTyped a, ReifyFlowTyFields fs, Typeable fs, Typeable k) => FlowTyped (FlowTyFields a fs) Source # | |
Defined in Data.Aeson.Flow flowType :: Proxy (FlowTyFields a fs) -> FlowType Source # flowTypeName :: Proxy (FlowTyFields a fs) -> Maybe Text Source # flowTypeVars :: Proxy (FlowTyFields a fs) -> [Flowable] Source # flowOptions :: Proxy (FlowTyFields a fs) -> Options Source # |
type family FlowDeconstructField (k :: t) :: (Symbol, *) Source #
Instances
type FlowDeconstructField ('(a, b) :: (Symbol, Type)) Source # | |
Defined in Data.Aeson.Flow |
TS specific
showTypeScriptType :: FlowType -> [Flowable] -> Text Source #
Pretty-print a flowtype in flowtype syntax
Flow specific
Dependencies
dependencies :: FlowTyped a => Proxy a -> Set FlowName Source #
Compute all the dependencies of a FlowTyped
thing, including itself.
Utility
A name for a flowtyped data-type. These are returned by dependencies
.
defaultFlowTypeName :: (Generic a, Rep a ~ D1 ('MetaData name mod pkg t) c, KnownSymbol name) => Proxy a -> Maybe Text Source #
flowTypeName
using Generic
defaultFlowType :: (HasDatatypeInfo a, All2 FlowTyped (Code a)) => Options -> Proxy a -> FlowType Source #
flowType
using HasDatatypeInfo