{-# LANGUAGE NoFieldSelectors #-}
module Elmental.ElmStructure where
import Data.Text (Text)
data ElmMapping = ElmMapping
{ ElmMapping -> TypeName
typeName :: TypeName
, ElmMapping -> Maybe TypeName
moduleName :: Maybe ModuleName
, ElmMapping -> Maybe SymbolLocation
encoderLocation :: Maybe SymbolLocation
, ElmMapping -> Maybe SymbolLocation
decoderLocation :: Maybe SymbolLocation
, ElmMapping -> [ElmMapping]
args :: [ElmMapping]
, ElmMapping -> Bool
isTypeAlias :: Bool
, ElmMapping -> Maybe SymbolLocation
urlPiece :: Maybe SymbolLocation
, ElmMapping -> Maybe SymbolLocation
queryParam :: Maybe SymbolLocation
}
deriving (ElmMapping -> ElmMapping -> Bool
(ElmMapping -> ElmMapping -> Bool)
-> (ElmMapping -> ElmMapping -> Bool) -> Eq ElmMapping
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ElmMapping -> ElmMapping -> Bool
== :: ElmMapping -> ElmMapping -> Bool
$c/= :: ElmMapping -> ElmMapping -> Bool
/= :: ElmMapping -> ElmMapping -> Bool
Eq, Int -> ElmMapping -> ShowS
[ElmMapping] -> ShowS
ElmMapping -> String
(Int -> ElmMapping -> ShowS)
-> (ElmMapping -> String)
-> ([ElmMapping] -> ShowS)
-> Show ElmMapping
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ElmMapping -> ShowS
showsPrec :: Int -> ElmMapping -> ShowS
$cshow :: ElmMapping -> String
show :: ElmMapping -> String
$cshowList :: [ElmMapping] -> ShowS
showList :: [ElmMapping] -> ShowS
Show, Eq ElmMapping
Eq ElmMapping =>
(ElmMapping -> ElmMapping -> Ordering)
-> (ElmMapping -> ElmMapping -> Bool)
-> (ElmMapping -> ElmMapping -> Bool)
-> (ElmMapping -> ElmMapping -> Bool)
-> (ElmMapping -> ElmMapping -> Bool)
-> (ElmMapping -> ElmMapping -> ElmMapping)
-> (ElmMapping -> ElmMapping -> ElmMapping)
-> Ord ElmMapping
ElmMapping -> ElmMapping -> Bool
ElmMapping -> ElmMapping -> Ordering
ElmMapping -> ElmMapping -> ElmMapping
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ElmMapping -> ElmMapping -> Ordering
compare :: ElmMapping -> ElmMapping -> Ordering
$c< :: ElmMapping -> ElmMapping -> Bool
< :: ElmMapping -> ElmMapping -> Bool
$c<= :: ElmMapping -> ElmMapping -> Bool
<= :: ElmMapping -> ElmMapping -> Bool
$c> :: ElmMapping -> ElmMapping -> Bool
> :: ElmMapping -> ElmMapping -> Bool
$c>= :: ElmMapping -> ElmMapping -> Bool
>= :: ElmMapping -> ElmMapping -> Bool
$cmax :: ElmMapping -> ElmMapping -> ElmMapping
max :: ElmMapping -> ElmMapping -> ElmMapping
$cmin :: ElmMapping -> ElmMapping -> ElmMapping
min :: ElmMapping -> ElmMapping -> ElmMapping
Ord)
type ModuleName = Text
type SymbolName = Text
type TypeName = Text
type ConstructorName = Text
type FieldName = Text
type VarName = Text
data SymbolLocation = SymbolLocation
{ SymbolLocation -> TypeName
symbolName :: SymbolName
, SymbolLocation -> TypeName
symbolModuleName :: ModuleName
}
deriving (SymbolLocation -> SymbolLocation -> Bool
(SymbolLocation -> SymbolLocation -> Bool)
-> (SymbolLocation -> SymbolLocation -> Bool) -> Eq SymbolLocation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SymbolLocation -> SymbolLocation -> Bool
== :: SymbolLocation -> SymbolLocation -> Bool
$c/= :: SymbolLocation -> SymbolLocation -> Bool
/= :: SymbolLocation -> SymbolLocation -> Bool
Eq, Int -> SymbolLocation -> ShowS
[SymbolLocation] -> ShowS
SymbolLocation -> String
(Int -> SymbolLocation -> ShowS)
-> (SymbolLocation -> String)
-> ([SymbolLocation] -> ShowS)
-> Show SymbolLocation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SymbolLocation -> ShowS
showsPrec :: Int -> SymbolLocation -> ShowS
$cshow :: SymbolLocation -> String
show :: SymbolLocation -> String
$cshowList :: [SymbolLocation] -> ShowS
showList :: [SymbolLocation] -> ShowS
Show, Eq SymbolLocation
Eq SymbolLocation =>
(SymbolLocation -> SymbolLocation -> Ordering)
-> (SymbolLocation -> SymbolLocation -> Bool)
-> (SymbolLocation -> SymbolLocation -> Bool)
-> (SymbolLocation -> SymbolLocation -> Bool)
-> (SymbolLocation -> SymbolLocation -> Bool)
-> (SymbolLocation -> SymbolLocation -> SymbolLocation)
-> (SymbolLocation -> SymbolLocation -> SymbolLocation)
-> Ord SymbolLocation
SymbolLocation -> SymbolLocation -> Bool
SymbolLocation -> SymbolLocation -> Ordering
SymbolLocation -> SymbolLocation -> SymbolLocation
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: SymbolLocation -> SymbolLocation -> Ordering
compare :: SymbolLocation -> SymbolLocation -> Ordering
$c< :: SymbolLocation -> SymbolLocation -> Bool
< :: SymbolLocation -> SymbolLocation -> Bool
$c<= :: SymbolLocation -> SymbolLocation -> Bool
<= :: SymbolLocation -> SymbolLocation -> Bool
$c> :: SymbolLocation -> SymbolLocation -> Bool
> :: SymbolLocation -> SymbolLocation -> Bool
$c>= :: SymbolLocation -> SymbolLocation -> Bool
>= :: SymbolLocation -> SymbolLocation -> Bool
$cmax :: SymbolLocation -> SymbolLocation -> SymbolLocation
max :: SymbolLocation -> SymbolLocation -> SymbolLocation
$cmin :: SymbolLocation -> SymbolLocation -> SymbolLocation
min :: SymbolLocation -> SymbolLocation -> SymbolLocation
Ord)
data TyCon
= TyMapping ElmMapping
| TyVar VarName
deriving (TyCon -> TyCon -> Bool
(TyCon -> TyCon -> Bool) -> (TyCon -> TyCon -> Bool) -> Eq TyCon
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TyCon -> TyCon -> Bool
== :: TyCon -> TyCon -> Bool
$c/= :: TyCon -> TyCon -> Bool
/= :: TyCon -> TyCon -> Bool
Eq, Int -> TyCon -> ShowS
[TyCon] -> ShowS
TyCon -> String
(Int -> TyCon -> ShowS)
-> (TyCon -> String) -> ([TyCon] -> ShowS) -> Show TyCon
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TyCon -> ShowS
showsPrec :: Int -> TyCon -> ShowS
$cshow :: TyCon -> String
show :: TyCon -> String
$cshowList :: [TyCon] -> ShowS
showList :: [TyCon] -> ShowS
Show, Eq TyCon
Eq TyCon =>
(TyCon -> TyCon -> Ordering)
-> (TyCon -> TyCon -> Bool)
-> (TyCon -> TyCon -> Bool)
-> (TyCon -> TyCon -> Bool)
-> (TyCon -> TyCon -> Bool)
-> (TyCon -> TyCon -> TyCon)
-> (TyCon -> TyCon -> TyCon)
-> Ord TyCon
TyCon -> TyCon -> Bool
TyCon -> TyCon -> Ordering
TyCon -> TyCon -> TyCon
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: TyCon -> TyCon -> Ordering
compare :: TyCon -> TyCon -> Ordering
$c< :: TyCon -> TyCon -> Bool
< :: TyCon -> TyCon -> Bool
$c<= :: TyCon -> TyCon -> Bool
<= :: TyCon -> TyCon -> Bool
$c> :: TyCon -> TyCon -> Bool
> :: TyCon -> TyCon -> Bool
$c>= :: TyCon -> TyCon -> Bool
>= :: TyCon -> TyCon -> Bool
$cmax :: TyCon -> TyCon -> TyCon
max :: TyCon -> TyCon -> TyCon
$cmin :: TyCon -> TyCon -> TyCon
min :: TyCon -> TyCon -> TyCon
Ord)
data TyRef = TyRef
{ TyRef -> TyCon
tyCon :: TyCon
, TyRef -> [TyRef]
tyArgs :: [TyRef]
}
deriving (TyRef -> TyRef -> Bool
(TyRef -> TyRef -> Bool) -> (TyRef -> TyRef -> Bool) -> Eq TyRef
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TyRef -> TyRef -> Bool
== :: TyRef -> TyRef -> Bool
$c/= :: TyRef -> TyRef -> Bool
/= :: TyRef -> TyRef -> Bool
Eq, Int -> TyRef -> ShowS
[TyRef] -> ShowS
TyRef -> String
(Int -> TyRef -> ShowS)
-> (TyRef -> String) -> ([TyRef] -> ShowS) -> Show TyRef
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TyRef -> ShowS
showsPrec :: Int -> TyRef -> ShowS
$cshow :: TyRef -> String
show :: TyRef -> String
$cshowList :: [TyRef] -> ShowS
showList :: [TyRef] -> ShowS
Show, Eq TyRef
Eq TyRef =>
(TyRef -> TyRef -> Ordering)
-> (TyRef -> TyRef -> Bool)
-> (TyRef -> TyRef -> Bool)
-> (TyRef -> TyRef -> Bool)
-> (TyRef -> TyRef -> Bool)
-> (TyRef -> TyRef -> TyRef)
-> (TyRef -> TyRef -> TyRef)
-> Ord TyRef
TyRef -> TyRef -> Bool
TyRef -> TyRef -> Ordering
TyRef -> TyRef -> TyRef
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: TyRef -> TyRef -> Ordering
compare :: TyRef -> TyRef -> Ordering
$c< :: TyRef -> TyRef -> Bool
< :: TyRef -> TyRef -> Bool
$c<= :: TyRef -> TyRef -> Bool
<= :: TyRef -> TyRef -> Bool
$c> :: TyRef -> TyRef -> Bool
> :: TyRef -> TyRef -> Bool
$c>= :: TyRef -> TyRef -> Bool
>= :: TyRef -> TyRef -> Bool
$cmax :: TyRef -> TyRef -> TyRef
max :: TyRef -> TyRef -> TyRef
$cmin :: TyRef -> TyRef -> TyRef
min :: TyRef -> TyRef -> TyRef
Ord)
data DatatypeStructure a = DatatypeStructure
{ forall {k} (a :: k). DatatypeStructure a -> ElmMapping
mapping :: ElmMapping
, forall {k} (a :: k). DatatypeStructure a -> Integer
nParams :: Integer
, forall {k} (a :: k). DatatypeStructure a -> [Constructor]
constructors :: [Constructor]
}
deriving (DatatypeStructure a -> DatatypeStructure a -> Bool
(DatatypeStructure a -> DatatypeStructure a -> Bool)
-> (DatatypeStructure a -> DatatypeStructure a -> Bool)
-> Eq (DatatypeStructure a)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall k (a :: k).
DatatypeStructure a -> DatatypeStructure a -> Bool
$c== :: forall k (a :: k).
DatatypeStructure a -> DatatypeStructure a -> Bool
== :: DatatypeStructure a -> DatatypeStructure a -> Bool
$c/= :: forall k (a :: k).
DatatypeStructure a -> DatatypeStructure a -> Bool
/= :: DatatypeStructure a -> DatatypeStructure a -> Bool
Eq, Int -> DatatypeStructure a -> ShowS
[DatatypeStructure a] -> ShowS
DatatypeStructure a -> String
(Int -> DatatypeStructure a -> ShowS)
-> (DatatypeStructure a -> String)
-> ([DatatypeStructure a] -> ShowS)
-> Show (DatatypeStructure a)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall k (a :: k). Int -> DatatypeStructure a -> ShowS
forall k (a :: k). [DatatypeStructure a] -> ShowS
forall k (a :: k). DatatypeStructure a -> String
$cshowsPrec :: forall k (a :: k). Int -> DatatypeStructure a -> ShowS
showsPrec :: Int -> DatatypeStructure a -> ShowS
$cshow :: forall k (a :: k). DatatypeStructure a -> String
show :: DatatypeStructure a -> String
$cshowList :: forall k (a :: k). [DatatypeStructure a] -> ShowS
showList :: [DatatypeStructure a] -> ShowS
Show, Eq (DatatypeStructure a)
Eq (DatatypeStructure a) =>
(DatatypeStructure a -> DatatypeStructure a -> Ordering)
-> (DatatypeStructure a -> DatatypeStructure a -> Bool)
-> (DatatypeStructure a -> DatatypeStructure a -> Bool)
-> (DatatypeStructure a -> DatatypeStructure a -> Bool)
-> (DatatypeStructure a -> DatatypeStructure a -> Bool)
-> (DatatypeStructure a
-> DatatypeStructure a -> DatatypeStructure a)
-> (DatatypeStructure a
-> DatatypeStructure a -> DatatypeStructure a)
-> Ord (DatatypeStructure a)
DatatypeStructure a -> DatatypeStructure a -> Bool
DatatypeStructure a -> DatatypeStructure a -> Ordering
DatatypeStructure a -> DatatypeStructure a -> DatatypeStructure a
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall k (a :: k). Eq (DatatypeStructure a)
forall k (a :: k).
DatatypeStructure a -> DatatypeStructure a -> Bool
forall k (a :: k).
DatatypeStructure a -> DatatypeStructure a -> Ordering
forall k (a :: k).
DatatypeStructure a -> DatatypeStructure a -> DatatypeStructure a
$ccompare :: forall k (a :: k).
DatatypeStructure a -> DatatypeStructure a -> Ordering
compare :: DatatypeStructure a -> DatatypeStructure a -> Ordering
$c< :: forall k (a :: k).
DatatypeStructure a -> DatatypeStructure a -> Bool
< :: DatatypeStructure a -> DatatypeStructure a -> Bool
$c<= :: forall k (a :: k).
DatatypeStructure a -> DatatypeStructure a -> Bool
<= :: DatatypeStructure a -> DatatypeStructure a -> Bool
$c> :: forall k (a :: k).
DatatypeStructure a -> DatatypeStructure a -> Bool
> :: DatatypeStructure a -> DatatypeStructure a -> Bool
$c>= :: forall k (a :: k).
DatatypeStructure a -> DatatypeStructure a -> Bool
>= :: DatatypeStructure a -> DatatypeStructure a -> Bool
$cmax :: forall k (a :: k).
DatatypeStructure a -> DatatypeStructure a -> DatatypeStructure a
max :: DatatypeStructure a -> DatatypeStructure a -> DatatypeStructure a
$cmin :: forall k (a :: k).
DatatypeStructure a -> DatatypeStructure a -> DatatypeStructure a
min :: DatatypeStructure a -> DatatypeStructure a -> DatatypeStructure a
Ord)
type ElmField =
(Maybe FieldName, TyRef)
data Constructor = Constructor
{ Constructor -> TypeName
constructorName :: ConstructorName
, Constructor -> [ElmField]
constructorFields :: [ElmField]
}
deriving (Constructor -> Constructor -> Bool
(Constructor -> Constructor -> Bool)
-> (Constructor -> Constructor -> Bool) -> Eq Constructor
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Constructor -> Constructor -> Bool
== :: Constructor -> Constructor -> Bool
$c/= :: Constructor -> Constructor -> Bool
/= :: Constructor -> Constructor -> Bool
Eq, Int -> Constructor -> ShowS
[Constructor] -> ShowS
Constructor -> String
(Int -> Constructor -> ShowS)
-> (Constructor -> String)
-> ([Constructor] -> ShowS)
-> Show Constructor
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Constructor -> ShowS
showsPrec :: Int -> Constructor -> ShowS
$cshow :: Constructor -> String
show :: Constructor -> String
$cshowList :: [Constructor] -> ShowS
showList :: [Constructor] -> ShowS
Show, Eq Constructor
Eq Constructor =>
(Constructor -> Constructor -> Ordering)
-> (Constructor -> Constructor -> Bool)
-> (Constructor -> Constructor -> Bool)
-> (Constructor -> Constructor -> Bool)
-> (Constructor -> Constructor -> Bool)
-> (Constructor -> Constructor -> Constructor)
-> (Constructor -> Constructor -> Constructor)
-> Ord Constructor
Constructor -> Constructor -> Bool
Constructor -> Constructor -> Ordering
Constructor -> Constructor -> Constructor
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Constructor -> Constructor -> Ordering
compare :: Constructor -> Constructor -> Ordering
$c< :: Constructor -> Constructor -> Bool
< :: Constructor -> Constructor -> Bool
$c<= :: Constructor -> Constructor -> Bool
<= :: Constructor -> Constructor -> Bool
$c> :: Constructor -> Constructor -> Bool
> :: Constructor -> Constructor -> Bool
$c>= :: Constructor -> Constructor -> Bool
>= :: Constructor -> Constructor -> Bool
$cmax :: Constructor -> Constructor -> Constructor
max :: Constructor -> Constructor -> Constructor
$cmin :: Constructor -> Constructor -> Constructor
min :: Constructor -> Constructor -> Constructor
Ord)