mirror of
https://github.com/github/semantic.git
synced 2024-12-23 14:54:16 +03:00
Move Newtype1 into its own module.
This commit is contained in:
parent
f4fcdfecf1
commit
11360000cb
@ -9,10 +9,10 @@ module Control.Abstract.Analysis
|
||||
) where
|
||||
|
||||
import Control.Effect as X
|
||||
import Control.Newtype1 as X
|
||||
import Control.Monad.Effect.Fail as X
|
||||
import Control.Monad.Effect.Reader as X
|
||||
import Control.Monad.Effect.State as X
|
||||
import Data.Coerce
|
||||
import Prologue
|
||||
|
||||
type family TermFor (m :: * -> *)
|
||||
@ -32,25 +32,3 @@ class Monad m => MonadAnalysis m where
|
||||
default evaluateTerm :: Recursive (TermFor m) => TermFor m -> m (ValueFor m)
|
||||
evaluateTerm = foldSubterms analyzeTerm
|
||||
|
||||
|
||||
class Newtype1 n where
|
||||
type O1 n :: * -> *
|
||||
|
||||
pack1 :: O1 n a -> n a
|
||||
default pack1 :: (Generic1 n, GNewtype1 (Rep1 n), O1 n ~ GO1 (Rep1 n)) => O1 n a -> n a
|
||||
pack1 = to1 . gpack1
|
||||
|
||||
unpack1 :: n a -> O1 n a
|
||||
default unpack1 :: (Generic1 n, GNewtype1 (Rep1 n), O1 n ~ GO1 (Rep1 n)) => n a -> O1 n a
|
||||
unpack1 = gunpack1 . from1
|
||||
|
||||
class GNewtype1 n where
|
||||
type GO1 n :: * -> *
|
||||
|
||||
gpack1 :: GO1 n a -> n a
|
||||
gunpack1 :: n a -> GO1 n a
|
||||
|
||||
instance GNewtype1 (D1 d (C1 c (S1 s (Rec1 a)))) where
|
||||
type GO1 (D1 d (C1 c (S1 s (Rec1 a)))) = a
|
||||
gpack1 = coerce
|
||||
gunpack1 = coerce
|
||||
|
@ -1 +1,29 @@
|
||||
module Control.Newtype1 where
|
||||
{-# LANGUAGE DefaultSignatures, TypeFamilies #-}
|
||||
module Control.Newtype1
|
||||
( Newtype1(..)
|
||||
) where
|
||||
|
||||
import Data.Coerce (coerce)
|
||||
import Prologue
|
||||
|
||||
class Newtype1 n where
|
||||
type O1 n :: * -> *
|
||||
|
||||
pack1 :: O1 n a -> n a
|
||||
default pack1 :: (Generic1 n, GNewtype1 (Rep1 n), O1 n ~ GO1 (Rep1 n)) => O1 n a -> n a
|
||||
pack1 = to1 . gpack1
|
||||
|
||||
unpack1 :: n a -> O1 n a
|
||||
default unpack1 :: (Generic1 n, GNewtype1 (Rep1 n), O1 n ~ GO1 (Rep1 n)) => n a -> O1 n a
|
||||
unpack1 = gunpack1 . from1
|
||||
|
||||
class GNewtype1 n where
|
||||
type GO1 n :: * -> *
|
||||
|
||||
gpack1 :: GO1 n a -> n a
|
||||
gunpack1 :: n a -> GO1 n a
|
||||
|
||||
instance GNewtype1 (D1 d (C1 c (S1 s (Rec1 a)))) where
|
||||
type GO1 (D1 d (C1 c (S1 s (Rec1 a)))) = a
|
||||
gpack1 = coerce
|
||||
gunpack1 = coerce
|
||||
|
Loading…
Reference in New Issue
Block a user