{-# LANGUAGE PackageImports #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE TypeApplications #-}
{-# language ConstraintKinds #-}
{-# language DataKinds #-}
{-# language FlexibleContexts #-}
{-# language FlexibleInstances #-}
{-# language FunctionalDependencies #-}
{-# language MultiParamTypeClasses #-}
{-# language ScopedTypeVariables #-}
{-# language TypeFamilies #-}
{-# language TypeOperators #-}
{-# language UndecidableInstances #-}
module Data.Generics.Wrapped
( Wrapped (..)
, wrappedTo
, wrappedFrom
, _Unwrapped
, _Wrapped
)
where
import qualified "this" Data.Generics.Internal.VL.Iso as VL
import "generic-lens-core" Data.Generics.Internal.Wrapped (Context, derived)
import Control.Applicative (Const(..))
_Unwrapped :: Wrapped s t a b => VL.Iso s t a b
_Unwrapped = wrappedIso
{-# inline _Unwrapped #-}
_Wrapped :: Wrapped s t a b => VL.Iso b a t s
_Wrapped = VL.fromIso wrappedIso
{-# inline _Wrapped #-}
class Wrapped s t a b | s -> a, t -> b where
wrappedIso :: VL.Iso s t a b
wrappedTo :: forall s t a b. Wrapped s t a b => s -> a
wrappedTo a = view (wrappedIso @s @t @a @b) a
where view l s = getConst (l Const s)
{-# INLINE wrappedTo #-}
wrappedFrom :: forall s t a b. Wrapped s t a b => b -> t
wrappedFrom a = view (VL.fromIso (wrappedIso @s @t @a @b)) a
where view l s = getConst (l Const s)
{-# INLINE wrappedFrom #-}
instance Context s t a b => Wrapped s t a b where
wrappedIso = VL.iso2isovl derived
{-# INLINE wrappedIso #-}