Safe Haskell | None |
---|---|
Language | Haskell2010 |
The Shwifty library allows generation of
Swift types (structs and enums) from Haskell
ADTs, using Template Haskell. The main
entry point to the library should be the
documentation and examples of getShwifty
.
See also getShwiftyWith
and getShwiftyWithTags
.
This library is in alpha and there are a number of known bugs which shouldn't affect most users. See the issue tracker to see what those are.
There are probably many bugs/some weird behaviour when it comes to data families. Please report any issues on the issue tracker.
Synopsis
- class ToSwift a where
- class ToSwiftData a where
- toSwiftData :: Proxy a -> SwiftData
- getShwifty :: Name -> Q [Dec]
- getShwiftyWith :: Options -> Name -> Q [Dec]
- getShwiftyWithTags :: Options -> [Name] -> Name -> Q [Dec]
- getShwiftyCodec :: forall tag. ModifyOptions tag => Codec tag -> Name -> Q [Dec]
- getShwiftyCodecTags :: forall tag. ModifyOptions tag => Codec tag -> [Name] -> Name -> Q [Dec]
- data Ty
- data SwiftData
- = SwiftStruct {
- structName :: String
- structTyVars :: [String]
- structProtocols :: [Protocol]
- structFields :: [(String, Ty)]
- structPrivateTypes :: [SwiftData]
- structTags :: [Ty]
- | SwiftEnum {
- enumName :: String
- enumTyVars :: [String]
- enumProtocols :: [Protocol]
- enumCases :: [(String, [(Maybe String, Ty)])]
- enumRawValue :: Maybe Ty
- enumPrivateTypes :: [SwiftData]
- enumTags :: [Ty]
- | SwiftAlias { }
- = SwiftStruct {
- data Protocol
- data Options
- fieldLabelModifier :: Options -> String -> String
- constructorModifier :: Options -> String -> String
- optionalExpand :: Options -> Bool
- generateToSwift :: Options -> Bool
- generateToSwiftData :: Options -> Bool
- dataProtocols :: Options -> [Protocol]
- dataRawValue :: Options -> Maybe Ty
- typeAlias :: Options -> Bool
- newtypeTag :: Options -> Bool
- lowerFirstCase :: Options -> Bool
- lowerFirstField :: Options -> Bool
- omitFields :: Options -> [String]
- omitCases :: Options -> [String]
- makeBase :: Options -> (Bool, Maybe Ty, [Protocol])
- defaultOptions :: Options
- data Codec tag = Codec
- class ModifyOptions tag where
- modifyOptions :: Options -> Options
- type AsIs = ()
- data a & b
- data Label
- data Drop (label :: Label) (string :: Symbol)
- data DontGenerate (cls :: * -> Constraint)
- data Implement (protocol :: Protocol)
- data RawValue (ty :: Ty)
- class CanBeRawValue (ty :: Ty)
- data TypeAlias
- data NewtypeTag
- data DontLowercase (someKind :: Label)
- data OmitField (field :: Symbol)
- data OmitCase (cas :: Symbol)
- data MakeBase (rawValue :: Maybe Ty) (protocols :: [Protocol])
- prettyTy :: Ty -> String
- prettySwiftData :: SwiftData -> String
- type X = Void
Classes for conversion
class ToSwift a where Source #
The class for things which can be converted to
a Swift type (Ty
).
Typically the instance will be generated by
getShwifty
.
Instances
class ToSwiftData a where Source #
The class for things which can be converted to
SwiftData
.
Typically the instance will be generated by
getShwifty
.
Generating instances
getShwifty :: Name -> Q [Dec] Source #
Generate ToSwiftData
and ToSwift
instances
for your type. ToSwift
instances are typically
used to build cases or fields, whereas
ToSwiftData
instances are for building structs
and enums. Click the Examples
button to see
examples of what Swift gets generated in
different scenarios. To get access to the
generated code, you will have to use one of
the pretty-printing functions provided.
Examples
-- A simple sum type data SumType = Sum1 | Sum2 | Sum3 getShwifty ''SumType
enum SumType { case sum1 case sum2 case sum3 }
-- A simple product type data ProductType = ProductType { x :: Int, y :: Int } getShwifty ''ProductType
struct ProductType { let x: Int let y: Int }
-- A sum type with type variables data SumType a b = SumL a | SumR b getShwifty ''SumType
enum SumType<A, B> { case sumL(A) case sumR(B) }
-- A product type with type variables data ProductType a b = ProductType { aField :: a, bField :: b } getShwifty ''ProductType
struct ProductType<A, B> { let aField: A let bField: B }
-- A newtype newtype Newtype a = Newtype { getNewtype :: a } getShwifty ''Newtype
struct Newtype<A> { let getNewtype: A }
-- A type with a function field newtype Endo a = Endo { appEndo :: a -> a } getShwifty ''Endo
struct Endo<A> { let appEndo: ((A) -> A) }
-- A type with a kookier function field newtype Fun a = Fun { fun :: Int -> Char -> Bool -> String -> Maybe a } getShwifty ''Fun
struct Fun<A> { let fun: ((Int, Char, Bool, String) -> A?) }
-- A weird type with nested fields. Also note the Result's types being flipped from that of the Either. data YouveGotProblems a b = YouveGotProblems { field1 :: Maybe (Maybe (Maybe a)), field2 :: Either (Maybe a) (Maybe b) } getShwifty ''YouveGotProblems
struct YouveGotProblems<A, B> { let field1: Option<Option<Option<A>>> let field2: Result<Option<B>,Option<A>> }
-- A type with polykinded type variables -- Also note that there is no newline because -- of the absence of fields data PolyKinded (a :: k) = PolyKinded getShwifty ''PolyKinded
struct PolyKinded<A> { }
-- A sum type where constructors might be records data SumType a b (c :: k) = Sum1 Int a (Maybe b) | Sum2 b | Sum3 { x :: Int, y :: Int } getShwifty ''SumType
enum SumType<A, B, C> { case field1(Int, A, Optional<B>) case field2(B) case field3(_ x: Int, _ y: Int) }
-- A type containing another type with instance generated by 'getShwifty' newtype MyFirstType a = MyFirstType { getMyFirstType :: a } getShwifty ''MyFirstType data Contains a = Contains { x :: MyFirstType Int, y :: MyFirstType a } getShwifty ''Contains
struct MyFirstType<A> { let getMyFirstType: A } struct Contains<A> { let x: MyFirstType<Int> let y: MyFirstType<A> }
getShwiftyWith :: Options -> Name -> Q [Dec] Source #
Like getShwifty
, but lets you supply
your own Options
. Click the examples
for some clarification of what you can do.
Examples
data PrefixedFields = MkPrefixedFields { prefixedFieldsX :: Int, prefixedFieldsY :: Int } $(getShwiftyWith (defaultOptions { fieldLabelModifier = drop (length "PrefixedFields") }) ''PrefixedFields)
struct PrefixedFields { let x: Int let y: Int }
data PrefixedCons = MkPrefixedConsLeft | MkPrefixedConsRight $(getShwiftyWith (defaultOptions { constructorModifier = drop (length "MkPrefixedCons"), dataProtocols = [Codable] }) ''PrefixedCons)
enum PrefixedCons: Codable { case left case right }
getShwiftyWithTags :: Options -> [Name] -> Name -> Q [Dec] Source #
Like getShwiftyWith
, but lets you supply
tags. Tags are type-safe typealiases that
are akin to newtypes in Haskell. The
introduction of a struct around something
which is, say, a UUID in Swift means that
the default Codable instance will not work
correctly. So we introduce a tag(s). See the
examples to see how this looks. Also, see
https://github.com/pointfreeco/swift-tagged,
the library which these tags use. The library
is not included in any generated code.
Examples
-- Example of using the swift-tagged library: -- A type containing a database key data User = User { id :: UserId, name :: Text } -- the user key newtype UserId = UserId UUID $(getShwiftyWithTags defaultOptions [ ''UserId ] ''User) -- A type that also contains the UserId data UserDetails = UserDetails { id :: UserId, lastName :: Text } getShwifty ''UserDetails
struct User { let id: UserId let name: String typealias UserId = Tagged<User,UUID> } struct UserDetails { let id: User.UserId let lastName: String }
-- Example type with multiple tags newtype Name = MkName String newtype Email = MkEmail String data Person = Person { name :: Name, email :: Email } $(getShwiftyWithTags defaultOptions [ ''Name, ''Email ] ''Person)
struct Person { let name: Name let email: Email enum NameTag {} typealias Name = Tagged<NameTag, String> enum EmailTag {} typealias Email = Tagged<EmailTag, String> }
getShwiftyCodec :: forall tag. ModifyOptions tag => Codec tag -> Name -> Q [Dec] Source #
Like getShwiftyWith
, but with a Codec
instead of Options
.
getShwiftyCodecTags :: forall tag. ModifyOptions tag => Codec tag -> [Name] -> Name -> Q [Dec] Source #
Like getShwiftyWithTags
, but with a Codec
instead of Options
.
Types
An AST representing a Swift type.
Unit | Unit (called "Unit/Void" in swift). Empty struct type. |
Bool | Bool |
Character | Character |
Str | |
I | signed machine integer |
I8 | signed 8-bit integer |
I16 | signed 16-bit integer |
I32 | signed 32-bit integer |
I64 | signed 64-bit integer |
U | unsigned machine integer |
U8 | unsigned 8-bit integer |
U16 | unsigned 16-bit integer |
U32 | unsigned 32-bit integer |
U64 | unsigned 64-bit integer |
F32 | 32-bit floating point |
F64 | 64-bit floating point |
Decimal | Increased-precision floating point |
BigSInt32 | 32-bit big integer |
BigSInt64 | 64-bit big integer |
Tuple2 Ty Ty | 2-tuple |
Tuple3 Ty Ty Ty | 3-tuple |
Optional Ty | Maybe type |
Result Ty Ty | Either type Note: The error type in Swift must
implement the |
Set Ty | Set type |
Dictionary Ty Ty | Dictionary type |
Array Ty | array type |
App Ty Ty | function type |
Poly String | polymorphic type variable |
Concrete | a concrete type variable, and its
type variables. Will typically be generated
by |
| |
Tag | A See |
|
Instances
A Swift datatype, either a struct (product type) or enum (sum type). Haskll types are sums-of-products, so the way we differentiate when doing codegen, is that types with a single constructor will be converted to a struct, and those with two or more constructors will be converted to an enum. Types with 0 constructors will be converted to an empty enum.
SwiftStruct | A struct (product type) |
| |
SwiftEnum | An enum (sum type) |
| |
SwiftAlias | A top-level type alias |
Instances
Swift protocols. Only a few are supported right now.
Hashable | The |
Codable | The |
Equatable | The |
Options for encoding types
Option type
Options that specify how to
encode your SwiftData
to a swift type.
Options can be set using record syntax on
defaultOptions
with the fields below.
Actual Options
fieldLabelModifier :: Options -> String -> String Source #
Function applied to field labels.
Handy for removing common record prefixes,
for example. The default (id
) makes no
changes.
constructorModifier :: Options -> String -> String Source #
Function applied to value constructor names.
The default (id
) makes no changes.
optionalExpand :: Options -> Bool Source #
generateToSwift :: Options -> Bool Source #
Whether or not to generate a ToSwift
instance. Sometime this can be desirable
if you want to define the instance by hand,
or the instance exists elsewhere.
The default is True
, i.e., to generate
the instance.
generateToSwiftData :: Options -> Bool Source #
Whether or not to generate a ToSwiftData
instance. Sometime this can be desirable
if you want to define the instance by hand,
or the instance exists elsewhere.
The default is True
, i.e., to generate
the instance.
dataProtocols :: Options -> [Protocol] Source #
Protocols to add to a type.
The default ([]
) will add none.
dataRawValue :: Options -> Maybe Ty Source #
The rawValue of an enum. See https://developer.apple.com/documentation/swift/rawrepresentable/1540698-rawvalue
The default (Nothing
) will not
include any rawValue.
Typically, if the type does have
a rawValue
, the Ty
will be
I
or Str
.
Note: Currently, nothing will prevent you from putting something nonsensical here.
typeAlias :: Options -> Bool Source #
Whether or not to generate a newtype as
a type alias. Consider if you want this
or to use getShwiftyWithTags
instead.
The default (False
) will generate newtypes
as their own structs.
newtypeTag :: Options -> Bool Source #
Whether or not to generate a newtype as an empty enum with a tag. This is for type safety reasons, but with retaining the ability to have Codable conformance.
The default (False
) will not do this.
Note: This takes priority over typeAlias
.
Note: This option is not currently supported for newtype instances.
Examples
newtype NonEmptyText = MkNonEmptyText String $(getShwiftyWith (defaultOptions { newtypeTag = True }) ''NonEmpyText)
enum NonEmptyTextTag { typealias NonEmptyText = Tagged<NonEmptyTextTag, String> }
lowerFirstCase :: Options -> Bool Source #
Whether or not to lower-case the first character of a case after applying all modifiers to it.
The default (True
) will do so.
lowerFirstField :: Options -> Bool Source #
Whether or not to lower-case the first character of a field after applying all modifiers to it.
The default (True
) will do so.
omitFields :: Options -> [String] Source #
Fields to omit from a struct when generating types.
The default ([]
) will omit nothing.
omitCases :: Options -> [String] Source #
Cases to omit from an enum when generating types.
The default ([]
) will omit nothing.
Default Options
defaultOptions :: Options Source #
The default Options
.
defaultOptions :: Options defaultOptions = Options { typeConstructorModifier = id , fieldLabelModifier = id , constructorModifier = id , optionalExpand= False , generateToSwift = True , generateToSwiftData = True , dataProtocols = [] , dataRawValue = Nothing , typeAlias = False , newtypeTag = False , lowerFirstField = True , lowerFirstCase = True , omitFields = [] , omitCases = [] , makeBase = (False, Nothing, []) }
Codec options
A carrier for modifiers.
Instances
ModifyOptions tag => ModifyOptions (Codec tag :: Type) Source # | |
Defined in Shwifty.Codec modifyOptions :: Options -> Options Source # |
class ModifyOptions tag where Source #
Modify options.
modifyOptions :: Options -> Options Source #
Instances
Combine modifications.
Instances
(ModifyOptions a, ModifyOptions b) => ModifyOptions (a & b :: Type) Source # | |
Defined in Shwifty.Codec modifyOptions :: Options -> Options Source # |
Label modifiers.
data Drop (label :: Label) (string :: Symbol) Source #
Modify a label by dropping a string
Instances
KnownSymbol string => ModifyOptions (Drop TyCon string :: Type) Source # | |
Defined in Shwifty.Codec modifyOptions :: Options -> Options Source # | |
KnownSymbol string => ModifyOptions (Drop DataCon string :: Type) Source # | |
Defined in Shwifty.Codec modifyOptions :: Options -> Options Source # | |
KnownSymbol string => ModifyOptions (Drop Field string :: Type) Source # | |
Defined in Shwifty.Codec modifyOptions :: Options -> Options Source # |
data DontGenerate (cls :: * -> Constraint) Source #
Don't generate a specific class.
Instances
GenerateClass c => ModifyOptions (DontGenerate c :: Type) Source # | |
Defined in Shwifty.Codec modifyOptions :: Options -> Options Source # |
data Implement (protocol :: Protocol) Source #
Add protocols
Instances
ModifyOptions (Implement Hashable) Source # | |
Defined in Shwifty.Codec modifyOptions :: Options -> Options Source # | |
ModifyOptions (Implement Codable) Source # | |
Defined in Shwifty.Codec modifyOptions :: Options -> Options Source # | |
ModifyOptions (Implement Equatable) Source # | |
Defined in Shwifty.Codec modifyOptions :: Options -> Options Source # |
data RawValue (ty :: Ty) Source #
Add a rawValue
Instances
CanBeRawValue ty => ModifyOptions (RawValue ty :: Type) Source # | |
Defined in Shwifty.Codec modifyOptions :: Options -> Options Source # |
class CanBeRawValue (ty :: Ty) Source #
A Class that indicates that this swift type
can be a rawValue. The value of getRawValue
will be its actual rawValue.
getRawValue
Instances
CanBeRawValue Str Source # | |
Defined in Shwifty.Codec getRawValue :: Ty | |
CanBeRawValue I Source # | |
Defined in Shwifty.Codec getRawValue :: Ty | |
CanBeRawValue I8 Source # | |
Defined in Shwifty.Codec getRawValue :: Ty | |
CanBeRawValue I16 Source # | |
Defined in Shwifty.Codec getRawValue :: Ty | |
CanBeRawValue I32 Source # | |
Defined in Shwifty.Codec getRawValue :: Ty | |
CanBeRawValue I64 Source # | |
Defined in Shwifty.Codec getRawValue :: Ty | |
CanBeRawValue U Source # | |
Defined in Shwifty.Codec getRawValue :: Ty | |
CanBeRawValue U8 Source # | |
Defined in Shwifty.Codec getRawValue :: Ty | |
CanBeRawValue U16 Source # | |
Defined in Shwifty.Codec getRawValue :: Ty | |
CanBeRawValue U32 Source # | |
Defined in Shwifty.Codec getRawValue :: Ty | |
CanBeRawValue U64 Source # | |
Defined in Shwifty.Codec getRawValue :: Ty |
Make it a type alias (only applies to newtypes)
Instances
ModifyOptions TypeAlias Source # | |
Defined in Shwifty.Codec modifyOptions :: Options -> Options Source # |
data NewtypeTag Source #
Make it a newtype tag (only applies to newtype tags)
Instances
ModifyOptions NewtypeTag Source # | |
Defined in Shwifty.Codec modifyOptions :: Options -> Options Source # |
data DontLowercase (someKind :: Label) Source #
Dont lower-case fields/cases
Instances
(TypeError (Text "Cannot apply DontLowercase to TyCon") :: Constraint) => ModifyOptions (DontLowercase TyCon) Source # | |
Defined in Shwifty.Codec modifyOptions :: Options -> Options Source # | |
ModifyOptions (DontLowercase DataCon) Source # | |
Defined in Shwifty.Codec modifyOptions :: Options -> Options Source # | |
ModifyOptions (DontLowercase Field) Source # | |
Defined in Shwifty.Codec modifyOptions :: Options -> Options Source # |
data OmitField (field :: Symbol) Source #
Omit a field
Instances
KnownSymbol field => ModifyOptions (OmitField field :: Type) Source # | |
Defined in Shwifty.Codec modifyOptions :: Options -> Options Source # |
data OmitCase (cas :: Symbol) Source #
Omit a case
Instances
KnownSymbol cas => ModifyOptions (OmitCase cas :: Type) Source # | |
Defined in Shwifty.Codec modifyOptions :: Options -> Options Source # |
data MakeBase (rawValue :: Maybe Ty) (protocols :: [Protocol]) Source #
Make a base type
Instances
ProtocolList protocols => ModifyOptions (MakeBase (Nothing :: Maybe Ty) protocols :: Type) Source # | |
Defined in Shwifty.Codec modifyOptions :: Options -> Options Source # | |
(CanBeRawValue ty, ProtocolList protocols) => ModifyOptions (MakeBase (Just ty) protocols :: Type) Source # | |
Defined in Shwifty.Codec modifyOptions :: Options -> Options Source # |
Pretty-printing
Functions
Re-exports
A filler type to be used when pretty-printing. The codegen used by shwifty doesn't look at at what a type's type variables are instantiated to, but rather at the type's top-level definition. However, to make GHC happy, you will have to fill in type variables with unused types. To get around this, you could also use something like `-XQuantifiedConstraints`, or existential types, but we leave that to the user to handle.