| Safe Haskell | Safe-Inferred |
|---|---|
| Language | GHC2021 |
Elmental.Generate
Synopsis
- generateTypeDef :: forall {k} (x :: k). HasElmStructure k x => Text
- generateEncoder :: forall {k} (x :: k). HasElmStructure k x => Text
- generateDecoder :: forall {k} (x :: k). HasElmStructure k x => Text
- generateAll :: FilePath -> [SomeStructure] -> IO ()
- computeAll :: [SomeStructure] -> Map ModuleName ModuleDefinition
- mkSourceMap :: [SomeStructure] -> Map ModuleName Text
- include :: forall {k} x. HasElmStructure k x => SomeStructure
- outputModule :: FilePath -> (ModuleName, Text) -> IO ()
- data SomeStructure = forall x. SomeStructure (DatatypeStructure x)
- data ModuleDefinition = ModuleDefinition {}
Documentation
generateTypeDef :: forall {k} (x :: k). HasElmStructure k x => Text Source #
Generate a type definition
generateEncoder :: forall {k} (x :: k). HasElmStructure k x => Text Source #
Generate an encoder
generateDecoder :: forall {k} (x :: k). HasElmStructure k x => Text Source #
Generate a decoder
generateAll :: FilePath -> [SomeStructure] -> IO () Source #
mkSourceMap :: [SomeStructure] -> Map ModuleName Text Source #
include :: forall {k} x. HasElmStructure k x => SomeStructure Source #
outputModule :: FilePath -> (ModuleName, Text) -> IO () Source #
data SomeStructure Source #
Constructors
| forall x. SomeStructure (DatatypeStructure x) |
data ModuleDefinition Source #
Constructors
| ModuleDefinition | |
Instances
| Monoid ModuleDefinition Source # | |
Defined in Elmental.Generate Methods mappend :: ModuleDefinition -> ModuleDefinition -> ModuleDefinition # mconcat :: [ModuleDefinition] -> ModuleDefinition # | |
| Semigroup ModuleDefinition Source # | |
Defined in Elmental.Generate Methods (<>) :: ModuleDefinition -> ModuleDefinition -> ModuleDefinition # sconcat :: NonEmpty ModuleDefinition -> ModuleDefinition # stimes :: Integral b => b -> ModuleDefinition -> ModuleDefinition # | |
| Show ModuleDefinition Source # | |
Defined in Elmental.Generate Methods showsPrec :: Int -> ModuleDefinition -> ShowS # show :: ModuleDefinition -> String # showList :: [ModuleDefinition] -> ShowS # | |
| Eq ModuleDefinition Source # | |
Defined in Elmental.Generate Methods (==) :: ModuleDefinition -> ModuleDefinition -> Bool # (/=) :: ModuleDefinition -> ModuleDefinition -> Bool # | |