{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Barbies.TH (FieldNamesB(..)
  , LensB(..)
  , getLensB
  , AccessorsB(..)
  , declareBareB
  ) where
import Language.Haskell.TH hiding (cxt)
import Language.Haskell.TH.Syntax (VarBangType, Name(..), mkOccName, occString)
import Data.String
import Data.Foldable (foldl')
import Data.List (partition)
import Barbies
import Barbies.Constraints
import Barbies.Bare
import Data.Functor.Product
import GHC.Generics (Generic)
import Control.Applicative
import Data.Functor.Identity (Identity(..))
import Data.Functor.Compose (Compose(..))
import Data.List.Split
data LensB b a = LensB
  { LensB b a -> forall (h :: k -> *). b h -> h a
viewB :: forall h. b h -> h a
  , LensB b a -> forall (h :: k -> *). h a -> b h -> b h
setB :: forall h. h a -> b h -> b h
  }
getLensB :: Functor f => LensB b a -> (h a -> f (h a)) -> b h -> f (b h)
getLensB :: LensB b a -> (h a -> f (h a)) -> b h -> f (b h)
getLensB (LensB forall (h :: k -> *). b h -> h a
v forall (h :: k -> *). h a -> b h -> b h
s) h a -> f (h a)
f b h
b = (\h a
x -> h a -> b h -> b h
forall (h :: k -> *). h a -> b h -> b h
s h a
x b h
b) (h a -> b h) -> f (h a) -> f (b h)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> h a -> f (h a)
f (b h -> h a
forall (h :: k -> *). b h -> h a
v b h
b)
{-# INLINE getLensB #-}
class AccessorsB b where
  
  baccessors :: b (LensB b)
class FieldNamesB b where
  
  bfieldNames :: IsString a => b (Const a)
declareBareB :: DecsQ -> DecsQ
declareBareB :: DecsQ -> DecsQ
declareBareB DecsQ
decsQ = do
  [Dec]
decs <- DecsQ
decsQ
  [[Dec]]
decs' <- (Dec -> DecsQ) -> [Dec] -> Q [[Dec]]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Dec -> DecsQ
go [Dec]
decs
  [Dec] -> DecsQ
forall (m :: * -> *) a. Monad m => a -> m a
return ([Dec] -> DecsQ) -> [Dec] -> DecsQ
forall a b. (a -> b) -> a -> b
$ [[Dec]] -> [Dec]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[Dec]]
decs'
  where
    go :: Dec -> DecsQ
go (DataD Cxt
_ Name
dataName [TyVarBndr]
tvbs Maybe Kind
_ [con :: Con
con@(RecC Name
nDataCon [VarBangType]
fields)] [DerivClause]
classes) = do
      Name
nSwitch <- String -> Q Name
newName String
"sw"
      Name
nWrap <- String -> Q Name
newName String
"h"
      let xs :: [Name]
xs = String -> [VarBangType] -> [Name]
varNames String
"x" [VarBangType]
fields
      let ys :: [Name]
ys = String -> [VarBangType] -> [Name]
varNames String
"y" [VarBangType]
fields
      Name
nData <- String -> Q Name
newName String
"b"
      Name
nConstr <- String -> Q Name
newName String
"c"
      Name
nX <- String -> Q Name
newName String
"x"
      let transformed :: Con
transformed = Name -> Name -> Con -> Con
transformCon Name
nSwitch Name
nWrap Con
con
      let reconE :: [ExpQ] -> ExpQ
reconE = (ExpQ -> ExpQ -> ExpQ) -> ExpQ -> [ExpQ] -> ExpQ
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' ExpQ -> ExpQ -> ExpQ
appE (Name -> ExpQ
conE Name
nDataCon)
          
          fieldNamesE :: ExpQ
fieldNamesE = [ExpQ] -> ExpQ
reconE [[|Const $ fromString $(litE $ StringL $ nameBase name)|] | (Name
name, Bang
_, Kind
_) <- [VarBangType]
fields]
          accessors :: ExpQ
accessors = [ExpQ] -> ExpQ
reconE
            [ [|LensB
                $(varE name)
                (\ $(varP nX) $(varP nData) -> $(recUpdE (varE nData) [pure (name, VarE nX)])) |]
            | (Name
name, Bang
_, Kind
_) <- [VarBangType]
fields]
          
          
          
          varName :: TyVarBndr -> Name
varName (PlainTV Name
n) = Name
n
          varName (KindedTV Name
n Kind
_) = Name
n
          
          
          vanillaType :: TypeQ
vanillaType = (TypeQ -> TypeQ -> TypeQ) -> TypeQ -> [TypeQ] -> TypeQ
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' TypeQ -> TypeQ -> TypeQ
appT (Name -> TypeQ
conT Name
dataName) (Name -> TypeQ
varT (Name -> TypeQ) -> (TyVarBndr -> Name) -> TyVarBndr -> TypeQ
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TyVarBndr -> Name
varName (TyVarBndr -> TypeQ) -> [TyVarBndr] -> [TypeQ]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [TyVarBndr]
tvbs)
          
          typeChunks :: [[TypeQ]]
typeChunks = Int -> [TypeQ] -> [[TypeQ]]
forall e. Int -> [e] -> [[e]]
chunksOf Int
62 [Name -> TypeQ
varT Name
nConstr TypeQ -> TypeQ -> TypeQ
`appT` Kind -> TypeQ
forall (f :: * -> *) a. Applicative f => a -> f a
pure Kind
t | (Name
_, Bang
_, Kind
t) <- [VarBangType]
fields]
          mkConstraints :: t TypeQ -> TypeQ
mkConstraints t TypeQ
ps = (TypeQ -> TypeQ -> TypeQ) -> TypeQ -> t TypeQ -> TypeQ
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl TypeQ -> TypeQ -> TypeQ
appT (Int -> TypeQ
tupleT (Int -> TypeQ) -> Int -> TypeQ
forall a b. (a -> b) -> a -> b
$ t TypeQ -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length t TypeQ
ps) t TypeQ
ps
          allConstr :: TypeQ
allConstr = case [[TypeQ]]
typeChunks of
            [[TypeQ]
ps] -> [TypeQ] -> TypeQ
forall (t :: * -> *). Foldable t => t TypeQ -> TypeQ
mkConstraints [TypeQ]
ps
            [[TypeQ]]
pss -> [TypeQ] -> TypeQ
forall (t :: * -> *). Foldable t => t TypeQ -> TypeQ
mkConstraints ([TypeQ] -> TypeQ) -> [TypeQ] -> TypeQ
forall a b. (a -> b) -> a -> b
$ ([TypeQ] -> TypeQ) -> [[TypeQ]] -> [TypeQ]
forall a b. (a -> b) -> [a] -> [b]
map [TypeQ] -> TypeQ
forall (t :: * -> *). Foldable t => t TypeQ -> TypeQ
mkConstraints [[TypeQ]]
pss
      let datC :: TypeQ
datC = TypeQ
vanillaType TypeQ -> TypeQ -> TypeQ
`appT` Name -> TypeQ
conT ''Covered
      [Dec]
decs <- [d|
        instance BareB $(vanillaType) where
          bcover $(conP nDataCon $ map varP xs)
            = $(reconE $ appE (conE 'Identity) . varE <$> xs)
          {-# INLINE bcover #-}
          bstrip $(conP nDataCon $ map varP xs)
            = $(reconE $ appE (varE 'runIdentity) . varE <$> xs)
          {-# INLINE bstrip #-}
        instance FieldNamesB $(datC) where bfieldNames = $(fieldNamesE)
        instance AccessorsB $(datC) where baccessors = $(accessors)
        instance FunctorB $(datC) where
          bmap f $(conP nDataCon $ map varP xs)
            = $(reconE (appE (varE 'f) . varE <$> xs))
        instance DistributiveB $(datC) where
          bdistribute fb = $(reconE
              
              [ [| Compose ($(varE (unmangle fd)) <$> fb) |] | (fd, _, _) <- fields ]
            )
        instance TraversableB $(datC) where
          btraverse f $(conP nDataCon $ map varP xs) = $(fst $ foldl'
              (\(l, op) r -> (infixE (Just l) (varE op) (Just r), '(<*>)))
              (conE nDataCon, '(<$>))
              (appE (varE 'f) . varE <$> xs)
            )
          {-# INLINE btraverse #-}
        instance ConstraintsB $(datC) where
          type AllB $(varT nConstr) $(datC) = $(allConstr)
          baddDicts $(conP nDataCon $ map varP xs)
            = $(reconE $ map (\x -> [|Pair Dict $(varE x)|]) xs)
        instance ApplicativeB $(datC) where
          bpure $(varP nX) = $(reconE $ varE nX <$ xs)
          bprod $(conP nDataCon $ map varP xs) $(conP nDataCon $ map varP ys) = $(foldl'
            (\r (x, y) -> [|$(r) (Pair $(varE x) $(varE y))|])
            (conE nDataCon) (zip xs ys))
        |]
      
      let classes' :: [(Cxt, DerivClause)]
classes' = (DerivClause -> (Cxt, DerivClause))
-> [DerivClause] -> [(Cxt, DerivClause)]
forall a b. (a -> b) -> [a] -> [b]
map (\(DerivClause Maybe DerivStrategy
strat Cxt
cs) -> (Cxt -> DerivClause) -> (Cxt, Cxt) -> (Cxt, DerivClause)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Maybe DerivStrategy -> Cxt -> DerivClause
DerivClause Maybe DerivStrategy
strat) ((Cxt, Cxt) -> (Cxt, DerivClause))
-> (Cxt, Cxt) -> (Cxt, DerivClause)
forall a b. (a -> b) -> a -> b
$ (Kind -> Bool) -> Cxt -> (Cxt, Cxt)
forall a. (a -> Bool) -> [a] -> ([a], [a])
partition (Kind -> Kind -> Bool
forall a. Eq a => a -> a -> Bool
== Name -> Kind
ConT ''Generic) Cxt
cs) [DerivClause]
classes
      
      [[Dec]]
coverDrvs <- (TypeQ -> DecsQ) -> [TypeQ] -> Q [[Dec]]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (\TypeQ
cls ->
        [d|deriving via Barbie $(datC) $(varT nWrap)
            instance ($(cls) (Barbie $(datC) $(varT nWrap))) => $(cls) ($(datC) $(varT nWrap))|])
        [ Kind -> TypeQ
forall (f :: * -> *) a. Applicative f => a -> f a
pure Kind
t | (Cxt
_, DerivClause Maybe DerivStrategy
_ Cxt
preds) <- [(Cxt, DerivClause)]
classes', Kind
t <- Cxt
preds ]
      
      [Dec]
bareDrvs <- ((Maybe DerivStrategy, TypeQ) -> Q Dec)
-> [(Maybe DerivStrategy, TypeQ)] -> DecsQ
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (\(Maybe DerivStrategy
strat, TypeQ
cls) ->
        Maybe DerivStrategy -> CxtQ -> TypeQ -> Q Dec
standaloneDerivWithStrategyD Maybe DerivStrategy
strat (Cxt -> CxtQ
forall (f :: * -> *) a. Applicative f => a -> f a
pure []) [t|$(cls) ($(vanillaType) Bare Identity)|])
        [ (Maybe DerivStrategy
strat, Kind -> TypeQ
forall (f :: * -> *) a. Applicative f => a -> f a
pure Kind
t) | (Cxt
_, DerivClause Maybe DerivStrategy
strat Cxt
preds) <- [(Cxt, DerivClause)]
classes', Kind
t <- Cxt
preds ]
      [Dec] -> DecsQ
forall (m :: * -> *) a. Monad m => a -> m a
return ([Dec] -> DecsQ) -> [Dec] -> DecsQ
forall a b. (a -> b) -> a -> b
$ Cxt
-> Name
-> [TyVarBndr]
-> Maybe Kind
-> [Con]
-> [DerivClause]
-> Dec
DataD [] Name
dataName
        ([TyVarBndr]
tvbs [TyVarBndr] -> [TyVarBndr] -> [TyVarBndr]
forall a. [a] -> [a] -> [a]
++ [Name -> TyVarBndr
PlainTV Name
nSwitch, Name -> TyVarBndr
PlainTV Name
nWrap])
        Maybe Kind
forall a. Maybe a
Nothing
        [Con
transformed]
        [Maybe DerivStrategy -> Cxt -> DerivClause
DerivClause Maybe DerivStrategy
forall a. Maybe a
Nothing (Cxt -> DerivClause) -> Cxt -> DerivClause
forall a b. (a -> b) -> a -> b
$ ((Cxt, DerivClause) -> Cxt) -> [(Cxt, DerivClause)] -> Cxt
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Cxt, DerivClause) -> Cxt
forall a b. (a, b) -> a
fst [(Cxt, DerivClause)]
classes']
        Dec -> [Dec] -> [Dec]
forall a. a -> [a] -> [a]
: [Dec]
decs [Dec] -> [Dec] -> [Dec]
forall a. [a] -> [a] -> [a]
++ [[Dec]] -> [Dec]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[Dec]]
coverDrvs [Dec] -> [Dec] -> [Dec]
forall a. [a] -> [a] -> [a]
++ [Dec]
bareDrvs
    go Dec
d = [Dec] -> DecsQ
forall (f :: * -> *) a. Applicative f => a -> f a
pure [Dec
d]
varNames :: String -> [VarBangType] -> [Name]
varNames :: String -> [VarBangType] -> [Name]
varNames String
p [VarBangType]
vbt = [String -> Name
mkName (String
p String -> String -> String
forall a. [a] -> [a] -> [a]
++ Name -> String
nameBase (Name -> Name
unmangle Name
v)) | (Name
v, Bang
_, Kind
_) <- [VarBangType]
vbt]
transformCon :: Name 
  -> Name 
  -> Con 
  -> Con
transformCon :: Name -> Name -> Con -> Con
transformCon Name
switchName Name
wrapperName (RecC Name
name [VarBangType]
xs) = Name -> [VarBangType] -> Con
RecC Name
name
  [(Name -> Name
unmangle Name
v, Bang
b, Name -> Kind
ConT ''Wear
    Kind -> Kind -> Kind
`AppT` Name -> Kind
VarT Name
switchName
    Kind -> Kind -> Kind
`AppT` Name -> Kind
VarT Name
wrapperName
    Kind -> Kind -> Kind
`AppT` Kind
t)
  | (Name
v, Bang
b, Kind
t) <- [VarBangType]
xs
  ]
transformCon Name
var Name
w (ForallC [TyVarBndr]
tvbs Cxt
cxt Con
con) = [TyVarBndr] -> Cxt -> Con -> Con
ForallC [TyVarBndr]
tvbs Cxt
cxt (Con -> Con) -> Con -> Con
forall a b. (a -> b) -> a -> b
$ Name -> Name -> Con -> Con
transformCon Name
var Name
w Con
con
transformCon Name
_ Name
_ Con
con = String -> Con
forall a. HasCallStack => String -> a
error (String -> Con) -> String -> Con
forall a b. (a -> b) -> a -> b
$ String
"transformCon: unsupported " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Con -> String
forall a. Show a => a -> String
show Con
con
unmangle :: Name -> Name
unmangle :: Name -> Name
unmangle (Name OccName
occ NameFlavour
flavour) = OccName -> NameFlavour -> Name
Name OccName
occ' NameFlavour
flavour
  where
    occ' :: OccName
occ' = case (Char -> Bool) -> String -> [String]
forall a. (a -> Bool) -> [a] -> [[a]]
wordsBy (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
':') (OccName -> String
occString OccName
occ) of
        [String
"$sel", String
fd, String
_qual] -> String -> OccName
mkOccName String
fd
        [String]
_ -> OccName
occ