{-# language CPP , FlexibleInstances , ScopedTypeVariables , TypeApplications #-} module Shwifty.Class ( ToSwift(..) , ToSwiftData(..) ) where import Data.List (intercalate) import Data.Proxy (Proxy(..)) import Control.Monad.Except import Data.CaseInsensitive (CI) import Data.Foldable (foldlM,foldr',foldl') import Data.Functor ((<&>)) import Data.Int (Int8,Int16,Int32,Int64) import Data.Kind (Constraint) import Data.List.NonEmpty ((<|), NonEmpty(..)) import Data.Maybe (mapMaybe, catMaybes) import Data.Proxy (Proxy(..)) import Data.Time (UTCTime) import Data.UUID.Types (UUID) import Data.Vector (Vector) import Data.Void (Void) import Data.Word (Word8,Word16,Word32,Word64) import GHC.TypeLits ( Symbol, KnownSymbol, symbolVal , TypeError, ErrorMessage(..) ) import Language.Haskell.TH hiding (stringE) import Language.Haskell.TH.Datatype import Prelude hiding (Enum(..)) import qualified Data.ByteString as BS import qualified Data.ByteString.Lazy as BL import qualified Data.Char as Char import qualified Data.HashMap.Strict as HM import qualified Data.List as L import qualified Data.List.NonEmpty as NE import qualified Data.Map as M import qualified Data.Text as TS import qualified Data.Text.Lazy as TL import qualified Data.Primitive as Prim import Shwifty.Types -- | The class for things which can be converted to -- 'SwiftData'. -- -- Typically the instance will be generated by -- 'getShwifty'. class ToSwiftData a where -- | Convert a type to 'SwiftData' toSwiftData :: Proxy a -> SwiftData -- | The class for things which can be converted to -- a Swift type ('Ty'). -- -- Typically the instance will be generated by -- 'getShwifty'. class ToSwift a where -- | Convert a type to its Swift 'Ty'. toSwift :: Proxy a -> Ty instance ToSwift () where toSwift = const Unit instance ToSwift Bool where toSwift = const Bool instance ToSwift UUID where toSwift = const (Concrete "UUID" []) instance ToSwift UTCTime where toSwift = const (Concrete "Date" []) instance forall a b. (ToSwift a, ToSwift b) => ToSwift (a -> b) where toSwift = const (App (toSwift (Proxy @a)) (toSwift (Proxy @b))) instance forall a. ToSwift a => ToSwift (Maybe a) where toSwift = const (Optional (toSwift (Proxy @a))) -- | /Note/: In Swift, the ordering of the type -- variables is flipped - Shwifty has made the -- design choice to flip them for you. If you -- take issue with this, please open an issue -- for discussion on GitHub. instance forall a b. (ToSwift a, ToSwift b) => ToSwift (Either a b) where toSwift = const (Result (toSwift (Proxy @b)) (toSwift (Proxy @a))) instance ToSwift Integer where toSwift = const #if WORD_SIZE_IN_BITS == 32 BigSInt32 #else BigSInt64 #endif instance ToSwift Int where toSwift = const I instance ToSwift Int8 where toSwift = const I8 instance ToSwift Int16 where toSwift = const I16 instance ToSwift Int32 where toSwift = const I32 instance ToSwift Int64 where toSwift = const I64 instance ToSwift Word where toSwift = const U instance ToSwift Word8 where toSwift = const U8 instance ToSwift Word16 where toSwift = const U16 instance ToSwift Word32 where toSwift = const U32 instance ToSwift Word64 where toSwift = const U64 instance ToSwift Float where toSwift = const F32 instance ToSwift Double where toSwift = const F64 instance ToSwift Char where toSwift = const Character instance forall a. (ToSwift a) => ToSwift (Prim.Array a) where toSwift = const (Array (toSwift (Proxy @a))) instance forall a. (ToSwift a) => ToSwift (Prim.SmallArray a) where toSwift = const (Array (toSwift (Proxy @a))) instance ToSwift Prim.ByteArray where toSwift = const (Array U8) instance forall a. (ToSwift a) => ToSwift (Prim.PrimArray a) where toSwift = const (Array (toSwift (Proxy @a))) instance forall a. ToSwift a => ToSwift (Vector a) where toSwift = const (Array (toSwift (Proxy @a))) instance {-# overlappable #-} forall a. ToSwift a => ToSwift [a] where toSwift = const (Array (toSwift (Proxy @a))) instance {-# overlapping #-} ToSwift [Char] where toSwift = const Str instance ToSwift TL.Text where toSwift = const Str instance ToSwift TS.Text where toSwift = const Str instance ToSwift BL.ByteString where toSwift = const (Array U8) instance ToSwift BS.ByteString where toSwift = const (Array U8) instance ToSwift (CI s) where toSwift = const Str instance forall k v. (ToSwift k, ToSwift v) => ToSwift (M.Map k v) where toSwift = const (Dictionary (toSwift (Proxy @k)) (toSwift (Proxy @v))) instance forall k v. (ToSwift k, ToSwift v) => ToSwift (HM.HashMap k v) where toSwift = const (Dictionary (toSwift (Proxy @k)) (toSwift (Proxy @v))) instance forall a b. (ToSwift a, ToSwift b) => ToSwift ((,) a b) where toSwift = const (Tuple2 (toSwift (Proxy @a)) (toSwift (Proxy @b))) instance forall a b c. (ToSwift a, ToSwift b, ToSwift c) => ToSwift ((,,) a b c) where toSwift = const (Tuple3 (toSwift (Proxy @a)) (toSwift (Proxy @b)) (toSwift (Proxy @c)))