{-# 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 Optics.Core
import Optics.Internal.Optic
import "generic-lens-core" Data.Generics.Internal.Wrapped (Context, derived)
_Unwrapped :: Wrapped s t a b => Iso s t a b
_Unwrapped = wrappedIso
{-# inline _Unwrapped #-}
_Wrapped :: Wrapped s t a b => Iso b a t s
_Wrapped = re wrappedIso
{-# inline _Wrapped #-}
class Wrapped s t a b | s -> a, t -> b where
wrappedIso :: Iso s t a b
wrappedTo :: forall s a. Wrapped s s a a => s -> a
wrappedTo s = view (wrappedIso @s @s @a @a) s
{-# INLINE wrappedTo #-}
wrappedFrom :: forall s a. Wrapped s s a a => a -> s
wrappedFrom a = view (re wrappedIso) a
{-# INLINE wrappedFrom #-}
instance Context s t a b => Wrapped s t a b where
wrappedIso = Optic derived
{-# INLINE wrappedIso #-}