{-# OPTIONS_GHC -fno-warn-redundant-constraints #-}

{-# LANGUAGE AllowAmbiguousTypes  #-}
{-# LANGUAGE DataKinds            #-}
{-# LANGUAGE DefaultSignatures    #-}
{-# LANGUAGE FlexibleContexts     #-}
{-# LANGUAGE FlexibleInstances    #-}
{-# LANGUAGE PolyKinds            #-}
{-# LANGUAGE TypeFamilies         #-}
{-# LANGUAGE TypeOperators        #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE UndecidableInstances #-}

{- | Generic conversion of Haskell data types to Elm types.
-}

module Elm.Generic
       ( -- * Main data type for the user
         Elm (..)
       , elmRef

         -- * Smart constructors
       , elmNewtype

         -- * Generic utilities
       , GenericElmDefinition (..)
       , GenericElmConstructors (..)
       , GenericElmFields (..)

       , GenericConstructor (..)
       , toElmConstructor

         -- * Type families for compile-time checks
       , HasNoTypeVars
       , TypeVarsError

       , HasLessThanEightUnnamedFields
       , FieldsError
       , CheckFields
       , Max

       , HasNoNamedSum
       , NamedSumError
       , CheckNamedSum
       , CheckConst

         -- * Internals
       , stripTypeNamePrefix
       ) where

import Data.Char (isLower, toLower)
import Data.Int (Int16, Int32, Int8)
import Data.Kind (Constraint, Type)
import Data.List.NonEmpty (NonEmpty (..))
import Data.Proxy (Proxy (..))
import Data.Text (Text)
import Data.Time.Clock (UTCTime)
import Data.Type.Bool (If, type (||))
import Data.Void (Void)
import Data.Word (Word16, Word32, Word8)
import GHC.Generics ((:*:), (:+:), C1, Constructor (..), D1, Datatype (..), Generic (..), M1 (..),
                     Meta (..), Rec0, S1, Selector (..), U1)
import GHC.TypeLits (ErrorMessage (..), Nat, TypeError)
import GHC.TypeNats (type (+), type (<=?))

import Elm.Ast (ElmAlias (..), ElmConstructor (..), ElmDefinition (..), ElmPrim (..),
                ElmRecordField (..), ElmType (..), TypeName (..), TypeRef (..), definitionToRef)

import qualified Data.Text as T
import qualified Data.Text.Lazy as LT (Text)
import qualified GHC.Generics as Generic (from)


{- | Typeclass that describes how Haskell data types are converted to Elm ones.
-}
class Elm a where
    toElmDefinition :: Proxy a -> ElmDefinition

    default toElmDefinition
        :: ( HasNoTypeVars a
           , HasLessThanEightUnnamedFields a
           , HasNoNamedSum a
           , Generic a
           , GenericElmDefinition (Rep a)
           )
        => Proxy a
        -> ElmDefinition
    toElmDefinition Proxy a
_ = Rep a Any -> ElmDefinition
forall k (f :: k -> *) (a :: k).
GenericElmDefinition f =>
f a -> ElmDefinition
genericToElmDefinition
        (Rep a Any -> ElmDefinition) -> Rep a Any -> ElmDefinition
forall a b. (a -> b) -> a -> b
$ a -> Rep a Any
forall a x. Generic a => a -> Rep a x
Generic.from ([Char] -> a
forall a. HasCallStack => [Char] -> a
error [Char]
"Proxy for generic elm was evaluated" :: a)

{- | Returns 'TypeRef' for the existing type. This function always returns the
name of the type without any type variables added.
-}
elmRef :: forall a . Elm a => TypeRef
elmRef :: TypeRef
elmRef = ElmDefinition -> TypeRef
definitionToRef (ElmDefinition -> TypeRef) -> ElmDefinition -> TypeRef
forall a b. (a -> b) -> a -> b
$ Proxy a -> ElmDefinition
forall a. Elm a => Proxy a -> ElmDefinition
toElmDefinition (Proxy a -> ElmDefinition) -> Proxy a -> ElmDefinition
forall a b. (a -> b) -> a -> b
$ Proxy a
forall k (t :: k). Proxy t
Proxy @a

----------------------------------------------------------------------------
-- Primitive instances
----------------------------------------------------------------------------

instance Elm ()   where toElmDefinition :: Proxy () -> ElmDefinition
toElmDefinition Proxy ()
_ = ElmPrim -> ElmDefinition
DefPrim ElmPrim
ElmUnit
instance Elm Void where toElmDefinition :: Proxy Void -> ElmDefinition
toElmDefinition Proxy Void
_ = ElmPrim -> ElmDefinition
DefPrim ElmPrim
ElmNever
instance Elm Bool where toElmDefinition :: Proxy Bool -> ElmDefinition
toElmDefinition Proxy Bool
_ = ElmPrim -> ElmDefinition
DefPrim ElmPrim
ElmBool
instance Elm Char where toElmDefinition :: Proxy Char -> ElmDefinition
toElmDefinition Proxy Char
_ = ElmPrim -> ElmDefinition
DefPrim ElmPrim
ElmChar

instance Elm Int    where toElmDefinition :: Proxy Int -> ElmDefinition
toElmDefinition Proxy Int
_ = ElmPrim -> ElmDefinition
DefPrim ElmPrim
ElmInt
instance Elm Int8   where toElmDefinition :: Proxy Int8 -> ElmDefinition
toElmDefinition Proxy Int8
_ = ElmPrim -> ElmDefinition
DefPrim ElmPrim
ElmInt
instance Elm Int16  where toElmDefinition :: Proxy Int16 -> ElmDefinition
toElmDefinition Proxy Int16
_ = ElmPrim -> ElmDefinition
DefPrim ElmPrim
ElmInt
instance Elm Int32  where toElmDefinition :: Proxy Int32 -> ElmDefinition
toElmDefinition Proxy Int32
_ = ElmPrim -> ElmDefinition
DefPrim ElmPrim
ElmInt
instance Elm Word   where toElmDefinition :: Proxy Word -> ElmDefinition
toElmDefinition Proxy Word
_ = ElmPrim -> ElmDefinition
DefPrim ElmPrim
ElmInt
instance Elm Word8  where toElmDefinition :: Proxy Word8 -> ElmDefinition
toElmDefinition Proxy Word8
_ = ElmPrim -> ElmDefinition
DefPrim ElmPrim
ElmInt
instance Elm Word16 where toElmDefinition :: Proxy Word16 -> ElmDefinition
toElmDefinition Proxy Word16
_ = ElmPrim -> ElmDefinition
DefPrim ElmPrim
ElmInt
instance Elm Word32 where toElmDefinition :: Proxy Word32 -> ElmDefinition
toElmDefinition Proxy Word32
_ = ElmPrim -> ElmDefinition
DefPrim ElmPrim
ElmInt

instance Elm Float  where toElmDefinition :: Proxy Float -> ElmDefinition
toElmDefinition Proxy Float
_ = ElmPrim -> ElmDefinition
DefPrim ElmPrim
ElmFloat
instance Elm Double where toElmDefinition :: Proxy Double -> ElmDefinition
toElmDefinition Proxy Double
_ = ElmPrim -> ElmDefinition
DefPrim ElmPrim
ElmFloat

instance Elm Text    where toElmDefinition :: Proxy Text -> ElmDefinition
toElmDefinition Proxy Text
_ = ElmPrim -> ElmDefinition
DefPrim ElmPrim
ElmString
instance Elm LT.Text where toElmDefinition :: Proxy Text -> ElmDefinition
toElmDefinition Proxy Text
_ = ElmPrim -> ElmDefinition
DefPrim ElmPrim
ElmString

-- TODO: should it be 'Bytes' from @bytes@ package?
-- https://package.elm-lang.org/packages/elm/bytes/latest/Bytes
-- instance Elm B.ByteString  where toElmDefinition _ = DefPrim ElmString
-- instance Elm LB.ByteString where toElmDefinition _ = DefPrim ElmString

instance Elm UTCTime where toElmDefinition :: Proxy UTCTime -> ElmDefinition
toElmDefinition Proxy UTCTime
_ = ElmPrim -> ElmDefinition
DefPrim ElmPrim
ElmTime

instance Elm a => Elm (Maybe a) where
    toElmDefinition :: Proxy (Maybe a) -> ElmDefinition
toElmDefinition Proxy (Maybe a)
_ = ElmPrim -> ElmDefinition
DefPrim (ElmPrim -> ElmDefinition) -> ElmPrim -> ElmDefinition
forall a b. (a -> b) -> a -> b
$ TypeRef -> ElmPrim
ElmMaybe (TypeRef -> ElmPrim) -> TypeRef -> ElmPrim
forall a b. (a -> b) -> a -> b
$ Elm a => TypeRef
forall a. Elm a => TypeRef
elmRef @a

instance (Elm a, Elm b) => Elm (Either a b) where
    toElmDefinition :: Proxy (Either a b) -> ElmDefinition
toElmDefinition Proxy (Either a b)
_ = ElmPrim -> ElmDefinition
DefPrim (ElmPrim -> ElmDefinition) -> ElmPrim -> ElmDefinition
forall a b. (a -> b) -> a -> b
$ TypeRef -> TypeRef -> ElmPrim
ElmResult (Elm a => TypeRef
forall a. Elm a => TypeRef
elmRef @a) (Elm b => TypeRef
forall a. Elm a => TypeRef
elmRef @b)

instance (Elm a, Elm b) => Elm (a, b) where
    toElmDefinition :: Proxy (a, b) -> ElmDefinition
toElmDefinition Proxy (a, b)
_ = ElmPrim -> ElmDefinition
DefPrim (ElmPrim -> ElmDefinition) -> ElmPrim -> ElmDefinition
forall a b. (a -> b) -> a -> b
$ TypeRef -> TypeRef -> ElmPrim
ElmPair (Elm a => TypeRef
forall a. Elm a => TypeRef
elmRef @a) (Elm b => TypeRef
forall a. Elm a => TypeRef
elmRef @b)

instance (Elm a, Elm b, Elm c) => Elm (a, b, c) where
    toElmDefinition :: Proxy (a, b, c) -> ElmDefinition
toElmDefinition Proxy (a, b, c)
_ = ElmPrim -> ElmDefinition
DefPrim (ElmPrim -> ElmDefinition) -> ElmPrim -> ElmDefinition
forall a b. (a -> b) -> a -> b
$ TypeRef -> TypeRef -> TypeRef -> ElmPrim
ElmTriple (Elm a => TypeRef
forall a. Elm a => TypeRef
elmRef @a) (Elm b => TypeRef
forall a. Elm a => TypeRef
elmRef @b) (Elm c => TypeRef
forall a. Elm a => TypeRef
elmRef @c)

instance Elm a => Elm [a] where
    toElmDefinition :: Proxy [a] -> ElmDefinition
toElmDefinition Proxy [a]
_ = ElmPrim -> ElmDefinition
DefPrim (ElmPrim -> ElmDefinition) -> ElmPrim -> ElmDefinition
forall a b. (a -> b) -> a -> b
$ TypeRef -> ElmPrim
ElmList (Elm a => TypeRef
forall a. Elm a => TypeRef
elmRef @a)

instance Elm a => Elm (NonEmpty a) where
    toElmDefinition :: Proxy (NonEmpty a) -> ElmDefinition
toElmDefinition Proxy (NonEmpty a)
_ = ElmPrim -> ElmDefinition
DefPrim (ElmPrim -> ElmDefinition) -> ElmPrim -> ElmDefinition
forall a b. (a -> b) -> a -> b
$ TypeRef -> ElmPrim
ElmList (Elm a => TypeRef
forall a. Elm a => TypeRef
elmRef @a)

----------------------------------------------------------------------------
-- Smart constructors
----------------------------------------------------------------------------

{- | This function can be used to create manual 'Elm' instances easily for
@newtypes@ where 'Generic' deriving doesn't work. This function can be used like
this:

@
__newtype__ Id a = Id { unId :: Text }

__instance__ Elm (Id a) __where__
    toElmDefinition _ = elmNewtype @Text "Id" "unId"
@
-}
elmNewtype :: forall a . Elm a => Text -> Text -> ElmDefinition
elmNewtype :: Text -> Text -> ElmDefinition
elmNewtype Text
typeName Text
fieldName = ElmAlias -> ElmDefinition
DefAlias (ElmAlias -> ElmDefinition) -> ElmAlias -> ElmDefinition
forall a b. (a -> b) -> a -> b
$ ElmAlias :: Text -> NonEmpty ElmRecordField -> Bool -> ElmAlias
ElmAlias
    { elmAliasName :: Text
elmAliasName      = Text
typeName
    , elmAliasFields :: NonEmpty ElmRecordField
elmAliasFields    = TypeRef -> Text -> ElmRecordField
ElmRecordField (Elm a => TypeRef
forall a. Elm a => TypeRef
elmRef @a) Text
fieldName ElmRecordField -> [ElmRecordField] -> NonEmpty ElmRecordField
forall a. a -> [a] -> NonEmpty a
:| []
    , elmAliasIsNewtype :: Bool
elmAliasIsNewtype = Bool
True
    }

----------------------------------------------------------------------------
-- Generic instances
----------------------------------------------------------------------------

{- | Generic typeclass to generate whole 'ElmDefinition'. It has only one
instance: for the first top-level metadata that contains metainformation about
data type like @data type name@. Then it collects all constructors of the data
type and decides what to generate.
-}
class GenericElmDefinition (f :: k -> Type) where
    genericToElmDefinition :: f a -> ElmDefinition

instance (Datatype d, GenericElmConstructors f) => GenericElmDefinition (D1 d f) where
    genericToElmDefinition :: D1 d f a -> ElmDefinition
genericToElmDefinition D1 d f a
datatype = case TypeName -> f a -> NonEmpty GenericConstructor
forall k (f :: k -> *) (a :: k).
GenericElmConstructors f =>
TypeName -> f a -> NonEmpty GenericConstructor
genericToElmConstructors (Text -> TypeName
TypeName Text
typeName) (D1 d f a -> f a
forall i (c :: Meta) k (f :: k -> *) (p :: k). M1 i c f p -> f p
unM1 D1 d f a
datatype) of
        GenericConstructor
c :| [] -> case GenericConstructor
-> Either (NonEmpty ElmRecordField) ElmConstructor
toElmConstructor GenericConstructor
c of
            Left NonEmpty ElmRecordField
fields -> ElmAlias -> ElmDefinition
DefAlias (ElmAlias -> ElmDefinition) -> ElmAlias -> ElmDefinition
forall a b. (a -> b) -> a -> b
$ Text -> NonEmpty ElmRecordField -> Bool -> ElmAlias
ElmAlias Text
typeName NonEmpty ElmRecordField
fields Bool
elmIsNewtype
            Right ElmConstructor
ctor  -> ElmType -> ElmDefinition
DefType (ElmType -> ElmDefinition) -> ElmType -> ElmDefinition
forall a b. (a -> b) -> a -> b
$ Text -> [Text] -> Bool -> NonEmpty ElmConstructor -> ElmType
ElmType Text
typeName [] Bool
elmIsNewtype (ElmConstructor
ctor ElmConstructor -> [ElmConstructor] -> NonEmpty ElmConstructor
forall a. a -> [a] -> NonEmpty a
:| [])
        GenericConstructor
c :| [GenericConstructor]
cs -> case (GenericConstructor -> Maybe ElmConstructor)
-> NonEmpty GenericConstructor -> Maybe (NonEmpty ElmConstructor)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (Either (NonEmpty ElmRecordField) ElmConstructor
-> Maybe ElmConstructor
forall l r. Either l r -> Maybe r
rightToMaybe (Either (NonEmpty ElmRecordField) ElmConstructor
 -> Maybe ElmConstructor)
-> (GenericConstructor
    -> Either (NonEmpty ElmRecordField) ElmConstructor)
-> GenericConstructor
-> Maybe ElmConstructor
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenericConstructor
-> Either (NonEmpty ElmRecordField) ElmConstructor
toElmConstructor) (GenericConstructor
c GenericConstructor
-> [GenericConstructor] -> NonEmpty GenericConstructor
forall a. a -> [a] -> NonEmpty a
:| [GenericConstructor]
cs) of
            -- TODO: this should be error but dunno what to do here
            Maybe (NonEmpty ElmConstructor)
Nothing    -> ElmType -> ElmDefinition
DefType (ElmType -> ElmDefinition) -> ElmType -> ElmDefinition
forall a b. (a -> b) -> a -> b
$ Text -> [Text] -> Bool -> NonEmpty ElmConstructor -> ElmType
ElmType (Text
"ERROR_" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
typeName) [] Bool
False (Text -> [TypeRef] -> ElmConstructor
ElmConstructor Text
"ERROR" [] ElmConstructor -> [ElmConstructor] -> NonEmpty ElmConstructor
forall a. a -> [a] -> NonEmpty a
:| [])
            Just NonEmpty ElmConstructor
ctors -> ElmType -> ElmDefinition
DefType (ElmType -> ElmDefinition) -> ElmType -> ElmDefinition
forall a b. (a -> b) -> a -> b
$ Text -> [Text] -> Bool -> NonEmpty ElmConstructor -> ElmType
ElmType Text
typeName [] Bool
elmIsNewtype NonEmpty ElmConstructor
ctors
      where
        typeName :: Text
        typeName :: Text
typeName = [Char] -> Text
T.pack ([Char] -> Text) -> [Char] -> Text
forall a b. (a -> b) -> a -> b
$ D1 d f a -> [Char]
forall k (d :: k) k1 (t :: k -> (k1 -> *) -> k1 -> *)
       (f :: k1 -> *) (a :: k1).
Datatype d =>
t d f a -> [Char]
datatypeName D1 d f a
datatype

        elmIsNewtype :: Bool
        elmIsNewtype :: Bool
elmIsNewtype = D1 d f a -> Bool
forall k (d :: k) k1 (t :: k -> (k1 -> *) -> k1 -> *)
       (f :: k1 -> *) (a :: k1).
Datatype d =>
t d f a -> Bool
isNewtype D1 d f a
datatype

rightToMaybe :: Either l r -> Maybe r
rightToMaybe :: Either l r -> Maybe r
rightToMaybe = (l -> Maybe r) -> (r -> Maybe r) -> Either l r -> Maybe r
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe r -> l -> Maybe r
forall a b. a -> b -> a
const Maybe r
forall a. Maybe a
Nothing) r -> Maybe r
forall a. a -> Maybe a
Just

{- | Intermediate data type to help with the conversion from Haskell
constructors to Elm AST. In Haskell constructor fields may have names but may
not have.
-}
data GenericConstructor = GenericConstructor
    { GenericConstructor -> Text
genericConstructorName   :: !Text
    , GenericConstructor -> [(TypeRef, Maybe Text)]
genericConstructorFields :: ![(TypeRef, Maybe Text)]
    }

{- | Generic constructor can be in one of the three states:

1. No fields: enum constructor.
2. All fields have names: record constructor.
3. Not all fields have names: plain constructor.
-}
toElmConstructor :: GenericConstructor -> Either (NonEmpty ElmRecordField) ElmConstructor
toElmConstructor :: GenericConstructor
-> Either (NonEmpty ElmRecordField) ElmConstructor
toElmConstructor GenericConstructor{[(TypeRef, Maybe Text)]
Text
genericConstructorFields :: [(TypeRef, Maybe Text)]
genericConstructorName :: Text
genericConstructorFields :: GenericConstructor -> [(TypeRef, Maybe Text)]
genericConstructorName :: GenericConstructor -> Text
..} = case [(TypeRef, Maybe Text)]
genericConstructorFields of
    []   -> ElmConstructor -> Either (NonEmpty ElmRecordField) ElmConstructor
forall a b. b -> Either a b
Right (ElmConstructor -> Either (NonEmpty ElmRecordField) ElmConstructor)
-> ElmConstructor
-> Either (NonEmpty ElmRecordField) ElmConstructor
forall a b. (a -> b) -> a -> b
$ Text -> [TypeRef] -> ElmConstructor
ElmConstructor Text
genericConstructorName []
    (TypeRef, Maybe Text)
f:[(TypeRef, Maybe Text)]
fs -> case ((TypeRef, Maybe Text) -> Maybe ElmRecordField)
-> NonEmpty (TypeRef, Maybe Text)
-> Maybe (NonEmpty ElmRecordField)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (TypeRef, Maybe Text) -> Maybe ElmRecordField
toRecordField ((TypeRef, Maybe Text)
f (TypeRef, Maybe Text)
-> [(TypeRef, Maybe Text)] -> NonEmpty (TypeRef, Maybe Text)
forall a. a -> [a] -> NonEmpty a
:| [(TypeRef, Maybe Text)]
fs) of
        Maybe (NonEmpty ElmRecordField)
Nothing     -> ElmConstructor -> Either (NonEmpty ElmRecordField) ElmConstructor
forall a b. b -> Either a b
Right (ElmConstructor -> Either (NonEmpty ElmRecordField) ElmConstructor)
-> ElmConstructor
-> Either (NonEmpty ElmRecordField) ElmConstructor
forall a b. (a -> b) -> a -> b
$ Text -> [TypeRef] -> ElmConstructor
ElmConstructor Text
genericConstructorName ([TypeRef] -> ElmConstructor) -> [TypeRef] -> ElmConstructor
forall a b. (a -> b) -> a -> b
$ ((TypeRef, Maybe Text) -> TypeRef)
-> [(TypeRef, Maybe Text)] -> [TypeRef]
forall a b. (a -> b) -> [a] -> [b]
map (TypeRef, Maybe Text) -> TypeRef
forall a b. (a, b) -> a
fst [(TypeRef, Maybe Text)]
genericConstructorFields
        Just NonEmpty ElmRecordField
fields -> NonEmpty ElmRecordField
-> Either (NonEmpty ElmRecordField) ElmConstructor
forall a b. a -> Either a b
Left NonEmpty ElmRecordField
fields
  where
    toRecordField :: (TypeRef, Maybe Text) -> Maybe ElmRecordField
    toRecordField :: (TypeRef, Maybe Text) -> Maybe ElmRecordField
toRecordField (TypeRef
typeRef, Maybe Text
maybeFieldName) = TypeRef -> Text -> ElmRecordField
ElmRecordField TypeRef
typeRef (Text -> ElmRecordField) -> Maybe Text -> Maybe ElmRecordField
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
maybeFieldName


{- | Typeclass to collect all constructors of the Haskell data type generically. -}
class GenericElmConstructors (f :: k -> Type) where
    genericToElmConstructors
        :: TypeName  -- ^ Name of the data type; to be stripped
        -> f a  -- ^ Generic value
        -> NonEmpty GenericConstructor  -- ^ List of the data type constructors

-- | If it's a sum type then just combine constructors
instance (GenericElmConstructors f, GenericElmConstructors g) => GenericElmConstructors (f :+: g) where
    genericToElmConstructors :: TypeName -> (:+:) f g a -> NonEmpty GenericConstructor
genericToElmConstructors TypeName
name (:+:) f g a
_ =
        TypeName -> f Any -> NonEmpty GenericConstructor
forall k (f :: k -> *) (a :: k).
GenericElmConstructors f =>
TypeName -> f a -> NonEmpty GenericConstructor
genericToElmConstructors TypeName
name ([Char] -> f p
forall a. HasCallStack => [Char] -> a
error [Char]
"'f :+:' is evaluated" :: f p)
     NonEmpty GenericConstructor
-> NonEmpty GenericConstructor -> NonEmpty GenericConstructor
forall a. Semigroup a => a -> a -> a
<> TypeName -> g Any -> NonEmpty GenericConstructor
forall k (f :: k -> *) (a :: k).
GenericElmConstructors f =>
TypeName -> f a -> NonEmpty GenericConstructor
genericToElmConstructors TypeName
name ([Char] -> g p
forall a. HasCallStack => [Char] -> a
error [Char]
"':+: g' is evaluated" :: g p)

-- | Create singleton list for case of a one constructor.
instance (Constructor c, GenericElmFields f) => GenericElmConstructors (C1 c f) where
    genericToElmConstructors :: TypeName -> C1 c f a -> NonEmpty GenericConstructor
genericToElmConstructors TypeName
name C1 c f a
constructor = GenericConstructor -> NonEmpty GenericConstructor
forall (f :: * -> *) a. Applicative f => a -> f a
pure (GenericConstructor -> NonEmpty GenericConstructor)
-> GenericConstructor -> NonEmpty GenericConstructor
forall a b. (a -> b) -> a -> b
$ Text -> [(TypeRef, Maybe Text)] -> GenericConstructor
GenericConstructor
        ([Char] -> Text
T.pack ([Char] -> Text) -> [Char] -> Text
forall a b. (a -> b) -> a -> b
$ C1 c f a -> [Char]
forall k (c :: k) k1 (t :: k -> (k1 -> *) -> k1 -> *)
       (f :: k1 -> *) (a :: k1).
Constructor c =>
t c f a -> [Char]
conName C1 c f a
constructor)
        (TypeName -> f a -> [(TypeRef, Maybe Text)]
forall k (f :: k -> *) (a :: k).
GenericElmFields f =>
TypeName -> f a -> [(TypeRef, Maybe Text)]
genericToElmFields TypeName
name (f a -> [(TypeRef, Maybe Text)]) -> f a -> [(TypeRef, Maybe Text)]
forall a b. (a -> b) -> a -> b
$ C1 c f a -> f a
forall i (c :: Meta) k (f :: k -> *) (p :: k). M1 i c f p -> f p
unM1 C1 c f a
constructor)

-- | Collect all fields when inside constructor.
class GenericElmFields (f :: k -> Type) where
    genericToElmFields
        :: TypeName  -- ^ Name of the data type; to be stripped
        -> f a  -- ^ Generic value
        -> [(TypeRef, Maybe Text)]

-- | If multiple fields then just combine all results.
instance (GenericElmFields f, GenericElmFields g) => GenericElmFields (f :*: g) where
    genericToElmFields :: TypeName -> (:*:) f g a -> [(TypeRef, Maybe Text)]
genericToElmFields TypeName
name (:*:) f g a
_ =
        TypeName -> f Any -> [(TypeRef, Maybe Text)]
forall k (f :: k -> *) (a :: k).
GenericElmFields f =>
TypeName -> f a -> [(TypeRef, Maybe Text)]
genericToElmFields TypeName
name ([Char] -> f p
forall a. HasCallStack => [Char] -> a
error [Char]
"'f :*:' is evaluated" :: f p)
     [(TypeRef, Maybe Text)]
-> [(TypeRef, Maybe Text)] -> [(TypeRef, Maybe Text)]
forall a. Semigroup a => a -> a -> a
<> TypeName -> g Any -> [(TypeRef, Maybe Text)]
forall k (f :: k -> *) (a :: k).
GenericElmFields f =>
TypeName -> f a -> [(TypeRef, Maybe Text)]
genericToElmFields TypeName
name ([Char] -> g p
forall a. HasCallStack => [Char] -> a
error [Char]
"':*: g' is evaluated" :: g p)

-- | Constructor without fields.
instance GenericElmFields U1 where
    genericToElmFields :: TypeName -> U1 a -> [(TypeRef, Maybe Text)]
genericToElmFields TypeName
_ U1 a
_ = []

-- | Single constructor field.
instance (Selector s, Elm a) => GenericElmFields (S1 s (Rec0 a)) where
    genericToElmFields :: TypeName -> S1 s (Rec0 a) a -> [(TypeRef, Maybe Text)]
genericToElmFields TypeName
typeName S1 s (Rec0 a) a
selector = case S1 s (Rec0 a) a -> [Char]
forall k (s :: k) k1 (t :: k -> (k1 -> *) -> k1 -> *)
       (f :: k1 -> *) (a :: k1).
Selector s =>
t s f a -> [Char]
selName S1 s (Rec0 a) a
selector of
        [Char]
""   -> [(Elm a => TypeRef
forall a. Elm a => TypeRef
elmRef @a, Maybe Text
forall a. Maybe a
Nothing)]
        [Char]
name -> [(Elm a => TypeRef
forall a. Elm a => TypeRef
elmRef @a, Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ TypeName -> Text -> Text
stripTypeNamePrefix TypeName
typeName (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ [Char] -> Text
T.pack [Char]
name)]

{- | Strips name of the type name from field name prefix.

>>> stripTypeNamePrefix (TypeName "User") "userName"
"name"

>>> stripTypeNamePrefix (TypeName "HealthReading") "healthReadingId"
"id"

>>> stripTypeNamePrefix (TypeName "RecordUpdate") "ruRows"
"rows"

>>> stripTypeNamePrefix (TypeName "Foo") "foo"
"foo"

>>> stripTypeNamePrefix (TypeName "Foo") "abc"
"abc"
-}
stripTypeNamePrefix :: TypeName -> Text -> Text
stripTypeNamePrefix :: TypeName -> Text -> Text
stripTypeNamePrefix (TypeName Text
typeName) Text
fieldName =
    case Text -> Text -> Maybe Text
T.stripPrefix (Text -> Text
headToLower Text
typeName) Text
fieldName of
        Just Text
rest -> Text -> Text
leaveIfEmpty Text
rest
        Maybe Text
Nothing   -> Text -> Text
leaveIfEmpty ((Char -> Bool) -> Text -> Text
T.dropWhile Char -> Bool
isLower Text
fieldName)
  where
    headToLower :: Text -> Text
    headToLower :: Text -> Text
headToLower Text
t = case Text -> Maybe (Char, Text)
T.uncons Text
t of
        Maybe (Char, Text)
Nothing      -> [Char] -> Text
forall a. HasCallStack => [Char] -> a
error [Char]
"Cannot use 'headToLower' on empty Text"
        Just (Char
x, Text
xs) -> Char -> Text -> Text
T.cons (Char -> Char
toLower Char
x) Text
xs

    -- if all lower case then leave field as it is
    leaveIfEmpty :: Text -> Text
    leaveIfEmpty :: Text -> Text
leaveIfEmpty Text
rest = if Text -> Bool
T.null Text
rest then Text
fieldName else Text -> Text
headToLower Text
rest

----------------------------------------------------------------------------
-- ~Magic~
----------------------------------------------------------------------------

{- | This type family checks whether data type has type variables and throws
custom compiler error if it has. Since there's no generic way to get all type
variables, current implementation is limited only to 6 variables. This looks
like a reasonable number.
-}
type family HasNoTypeVars (f :: k) :: Constraint where
    HasNoTypeVars (t a b c d e f) = TypeError (TypeVarsError t 6)
    HasNoTypeVars (t a b c d e)   = TypeError (TypeVarsError t 5)
    HasNoTypeVars (t a b c d)     = TypeError (TypeVarsError t 4)
    HasNoTypeVars (t a b c)       = TypeError (TypeVarsError t 3)
    HasNoTypeVars (t a b)         = TypeError (TypeVarsError t 2)
    HasNoTypeVars (t a)           = TypeError (TypeVarsError t 1)
    HasNoTypeVars t               = ()

type family TypeVarsError (t :: k) (n :: Nat) :: ErrorMessage where
    TypeVarsError t n =
             'Text "'elm-street' currently doesn't support Generic deriving of the 'Elm' typeclass"
        ':$$: 'Text "for data types with type variables. But '"
              ':<>: 'ShowType t ':<>: 'Text "' has " ':<>: 'ShowType n ':<>: 'Text " variables."
        ':$$: 'Text ""
        ':$$: 'Text "See the following issue for more details:"
        ':$$: 'Text "    * https://github.com/Holmusk/elm-street/issues/45"
        ':$$: 'Text ""

{- | This type family checks whether each constructor of the sum data type has
less than eight unnamed fields and throws custom compiler error if it has.
-}
type family HasLessThanEightUnnamedFields (f :: k) :: Constraint where
    HasLessThanEightUnnamedFields t =
        If (CheckFields (Rep t) <=? 8)
            (() :: Constraint)
            (TypeError (FieldsError t))

type family CheckFields (f :: k -> Type) :: Nat where
    CheckFields (D1 _ f) = CheckFields f
    CheckFields (f :+: g) = Max (CheckFields f) (CheckFields g)
    CheckFields (C1 _ f) = CheckFields f
    CheckFields (f :*: g) = CheckFields f + CheckFields g
    CheckFields (S1 ('MetaSel ('Just _ ) _ _ _) _) = 0
    CheckFields (S1 _ _) = 1
    CheckFields _ = 0

type family Max (x :: Nat) (y :: Nat) :: Nat where
    Max x y = If (x <=? y) y x

type family FieldsError (t :: k) :: ErrorMessage where
    FieldsError t =
             'Text "'elm-street' doesn't support Constructors with more than 8 unnamed fields."
        ':$$: 'Text "But '" ':<>: 'ShowType t ':<>: 'Text "' has more."

{- | This type family checks whether each constructor of the sum data type has
less than eight unnamed fields and throws custom compiler error if it has.
-}
type family HasNoNamedSum (f :: k) :: Constraint where
    HasNoNamedSum t =
        If (CheckNamedSum (Rep t))
            (TypeError (NamedSumError t))
            (() :: Constraint)

-- | Is the data type id Sum type with named fields?
type family CheckNamedSum (f :: k -> Type) :: Bool where
    CheckNamedSum (D1 _ f) = CheckNamedSum f
    CheckNamedSum (f :+: g) = CheckConst f || CheckConst g
    CheckNamedSum _ = 'False

-- | Check if Sum type has named fields at least for one of the Constructors.
type family CheckConst (f :: k -> Type) :: Bool where
    CheckConst (f :+: g) = CheckConst f || CheckConst g
    CheckConst (C1 _ f) = CheckConst f
    CheckConst (S1 ('MetaSel ('Just _ ) _ _ _) _) = 'True
    CheckConst (f :*: g) = CheckConst f || CheckConst g
    CheckConst _ = 'False

type family NamedSumError (t :: k) :: ErrorMessage where
    NamedSumError t =
             'Text "'elm-street' doesn't support Sum types with records."
        ':$$: 'Text "But '" ':<>: 'ShowType t ':<>: 'Text "' has records."