{-# LANGUAGE DeriveGeneric #-}
module Language.PureScript.Ide.Reexports
( resolveReexports
, prettyPrintReexportResult
, reexportHasFailures
, ReexportResult(..)
, resolveReexports'
) where
import Protolude hiding (moduleName)
import qualified Data.Map as Map
import qualified Language.PureScript as P
import Language.PureScript.Ide.Types
import Language.PureScript.Ide.Util
import Lens.Micro.Platform hiding ((&))
data ReexportResult a
= ReexportResult
{ reResolved :: a
, reFailed :: [(P.ModuleName, P.DeclarationRef)]
} deriving (Show, Eq, Functor, Generic)
instance NFData a => NFData (ReexportResult a)
prettyPrintReexportResult
:: (a -> Text)
-> ReexportResult a
-> Text
prettyPrintReexportResult f ReexportResult{..}
| null reFailed =
"Successfully resolved reexports for " <> f reResolved
| otherwise =
"Failed to resolve reexports for "
<> f reResolved
<> foldMap (\(mn, ref) -> P.runModuleName mn <> show ref) reFailed
reexportHasFailures :: ReexportResult a -> Bool
reexportHasFailures = not . null . reFailed
resolveReexports
:: ModuleMap [(P.ModuleName, P.DeclarationRef)]
-> ModuleMap [IdeDeclarationAnn]
-> ModuleMap (ReexportResult [IdeDeclarationAnn])
resolveReexports reexportRefs modules =
Map.mapWithKey (\moduleName decls ->
maybe (ReexportResult decls [])
(map (decls <>) . resolveReexports' modules)
(Map.lookup moduleName reexportRefs)) modules
resolveReexports'
:: ModuleMap [IdeDeclarationAnn]
-> [(P.ModuleName, P.DeclarationRef)]
-> ReexportResult [IdeDeclarationAnn]
resolveReexports' modules refs =
ReexportResult (concat resolvedRefs) failedRefs
where
(failedRefs, resolvedRefs) = partitionEithers (resolveRef' <$> refs)
resolveRef' x@(mn, r) = case Map.lookup mn modules of
Nothing -> Left x
Just decls' ->
let
setExportedFrom = set (idaAnnotation.annExportedFrom) . Just
in
bimap (mn,) (map (setExportedFrom mn)) (resolveRef decls' r)
resolveRef
:: [IdeDeclarationAnn]
-> P.DeclarationRef
-> Either P.DeclarationRef [IdeDeclarationAnn]
resolveRef decls ref = case ref of
P.TypeRef _ tn mdtors ->
case findRef (anyOf (_IdeDeclType . ideTypeName) (== tn))
<|> findRef (anyOf (_IdeDeclTypeSynonym . ideSynonymName) (== tn)) of
Nothing ->
Left ref
Just d -> Right $ d : case mdtors of
Nothing ->
findDtors tn
Just dtors -> mapMaybe lookupDtor dtors
P.ValueRef _ i ->
findWrapped (anyOf (_IdeDeclValue . ideValueIdent) (== i))
P.ValueOpRef _ name ->
findWrapped (anyOf (_IdeDeclValueOperator . ideValueOpName) (== name))
P.TypeOpRef _ name ->
findWrapped (anyOf (_IdeDeclTypeOperator . ideTypeOpName) (== name))
P.TypeClassRef _ name ->
findWrapped (anyOf (_IdeDeclTypeClass . ideTCName) (== name))
P.KindRef _ name ->
findWrapped (anyOf _IdeDeclKind (== name))
_ ->
Left ref
where
findWrapped = maybe (Left ref) (Right . pure) . findRef
findRef f = find (f . discardAnn) decls
lookupDtor name =
findRef (anyOf (_IdeDeclDataConstructor . ideDtorName) (== name))
findDtors tn = filter (anyOf
(idaDeclaration
. _IdeDeclDataConstructor
. ideDtorTypeName) (== tn)) decls