mirror of
https://github.com/tfausak/witch.git
synced 2024-11-26 09:43:03 +03:00
Add some documentation
This commit is contained in:
parent
1b9a59e9d7
commit
c560919621
@ -10,6 +10,14 @@ import qualified Witch.Identity as Identity
|
||||
import qualified Witch.TryCast as TryCast
|
||||
import qualified Witch.Utility as Utility
|
||||
|
||||
-- | This is like 'Utility.unsafeCast' except that it works at compile time
|
||||
-- rather than runtime.
|
||||
--
|
||||
-- > -- Avoid this:
|
||||
-- > unsafeCast "some literal"
|
||||
-- >
|
||||
-- > -- Prefer this:
|
||||
-- > $$(liftedCast "some literal")
|
||||
liftedCast
|
||||
:: forall source target
|
||||
. ( TryCast.TryCast source target
|
||||
@ -22,6 +30,14 @@ liftedCast
|
||||
-> TH.Q (TH.TExp target)
|
||||
liftedCast = TH.liftTyped . Utility.unsafeCast
|
||||
|
||||
-- | This is like 'Utility.unsafeFrom' except that it works at compile time
|
||||
-- rather than runtime.
|
||||
--
|
||||
-- > -- Avoid this:
|
||||
-- > unsafeFrom @s "some literal"
|
||||
-- >
|
||||
-- > -- Prefer this:
|
||||
-- > $$(liftedCast @s "some literal")
|
||||
liftedFrom
|
||||
:: forall s target source
|
||||
. ( Identity.Identity s ~ source
|
||||
@ -35,6 +51,14 @@ liftedFrom
|
||||
-> TH.Q (TH.TExp target)
|
||||
liftedFrom = liftedCast
|
||||
|
||||
-- | This is like 'Utility.unsafeInto' except that it works at compile time
|
||||
-- rather than runtime.
|
||||
--
|
||||
-- > -- Avoid this:
|
||||
-- > unsafeInto @t "some literal"
|
||||
-- >
|
||||
-- > -- Prefer this:
|
||||
-- > $$(liftedCast @t "some literal")
|
||||
liftedInto
|
||||
:: forall t source target
|
||||
. ( Identity.Identity t ~ target
|
||||
|
@ -10,6 +10,14 @@ import qualified Witch.Identity as Identity
|
||||
import qualified Witch.TryCast as TryCast
|
||||
import qualified Witch.Utility as Utility
|
||||
|
||||
-- | This is like 'Utility.unsafeCast' except that it works at compile time
|
||||
-- rather than runtime.
|
||||
--
|
||||
-- > -- Avoid this:
|
||||
-- > unsafeCast "some literal"
|
||||
-- >
|
||||
-- > -- Prefer this:
|
||||
-- > $$(liftedCast "some literal")
|
||||
liftedCast
|
||||
:: forall source target
|
||||
. ( TryCast.TryCast source target
|
||||
@ -22,6 +30,14 @@ liftedCast
|
||||
-> TH.Q (TH.TExp target)
|
||||
liftedCast s = TH.unsafeTExpCoerce $ TH.lift (Utility.unsafeCast s :: target)
|
||||
|
||||
-- | This is like 'Utility.unsafeFrom' except that it works at compile time
|
||||
-- rather than runtime.
|
||||
--
|
||||
-- > -- Avoid this:
|
||||
-- > unsafeFrom @s "some literal"
|
||||
-- >
|
||||
-- > -- Prefer this:
|
||||
-- > $$(liftedCast @s "some literal")
|
||||
liftedFrom
|
||||
:: forall s target source
|
||||
. ( Identity.Identity s ~ source
|
||||
@ -35,6 +51,14 @@ liftedFrom
|
||||
-> TH.Q (TH.TExp target)
|
||||
liftedFrom = liftedCast
|
||||
|
||||
-- | This is like 'Utility.unsafeInto' except that it works at compile time
|
||||
-- rather than runtime.
|
||||
--
|
||||
-- > -- Avoid this:
|
||||
-- > unsafeInto @t "some literal"
|
||||
-- >
|
||||
-- > -- Prefer this:
|
||||
-- > $$(liftedCast @t "some literal")
|
||||
liftedInto
|
||||
:: forall t source target
|
||||
. ( Identity.Identity t ~ target
|
||||
|
@ -10,6 +10,14 @@ import qualified Witch.Identity as Identity
|
||||
import qualified Witch.TryCast as TryCast
|
||||
import qualified Witch.Utility as Utility
|
||||
|
||||
-- | This is like 'Utility.unsafeCast' except that it works at compile time
|
||||
-- rather than runtime.
|
||||
--
|
||||
-- > -- Avoid this:
|
||||
-- > unsafeCast "some literal"
|
||||
-- >
|
||||
-- > -- Prefer this:
|
||||
-- > $$(liftedCast "some literal")
|
||||
liftedCast
|
||||
:: forall source target m
|
||||
. ( TryCast.TryCast source target
|
||||
@ -23,6 +31,14 @@ liftedCast
|
||||
-> TH.Code m target
|
||||
liftedCast = TH.liftTyped . Utility.unsafeCast
|
||||
|
||||
-- | This is like 'Utility.unsafeFrom' except that it works at compile time
|
||||
-- rather than runtime.
|
||||
--
|
||||
-- > -- Avoid this:
|
||||
-- > unsafeFrom @s "some literal"
|
||||
-- >
|
||||
-- > -- Prefer this:
|
||||
-- > $$(liftedCast @s "some literal")
|
||||
liftedFrom
|
||||
:: forall s target m source
|
||||
. ( Identity.Identity s ~ source
|
||||
@ -37,6 +53,14 @@ liftedFrom
|
||||
-> TH.Code m target
|
||||
liftedFrom = liftedCast
|
||||
|
||||
-- | This is like 'Utility.unsafeInto' except that it works at compile time
|
||||
-- rather than runtime.
|
||||
--
|
||||
-- > -- Avoid this:
|
||||
-- > unsafeInto @t "some literal"
|
||||
-- >
|
||||
-- > -- Prefer this:
|
||||
-- > $$(liftedCast @t "some literal")
|
||||
liftedInto
|
||||
:: forall t source m target
|
||||
. ( Identity.Identity t ~ target
|
||||
|
144
src/lib/Witch.hs
144
src/lib/Witch.hs
@ -1,17 +1,153 @@
|
||||
-- | The Witch package is a library that allows you to confidently convert
|
||||
-- values between various types. This module exports everything you need to
|
||||
-- perform conversions or define your own. It is designed to be imported
|
||||
-- unqualified, so getting started is as easy as:
|
||||
--
|
||||
-- >>> import Witch
|
||||
module Witch
|
||||
( Witch.Utility.as
|
||||
, Witch.Cast.Cast(cast)
|
||||
( -- * Motivation
|
||||
-- | Haskell provides many ways to convert between common types, and core
|
||||
-- libraries add even more. It can be challenging to know which function to
|
||||
-- use when converting from some source type @a@ to some target type @b@. It
|
||||
-- can be even harder to know if that conversion is safe or if there are any
|
||||
-- pitfalls to watch out for.
|
||||
--
|
||||
-- This library tries to address that problem by providing a common
|
||||
-- interface for converting between types. The 'Witch.Cast.Cast' type class
|
||||
-- is for conversions that cannot fail, and the 'Witch.TryCast.TryCast' type
|
||||
-- class is for conversions that can fail. These type classes are inspired
|
||||
-- by the [@From@](https://doc.rust-lang.org/std/convert/trait.From.html)
|
||||
-- trait in Rust.
|
||||
|
||||
-- * Alternatives
|
||||
-- | Many Haskell libraries already provide similar functionality. How is
|
||||
-- this library different?
|
||||
--
|
||||
-- - [@Coercible@](https://hackage.haskell.org/package/base-4.15.0.0/docs/Data-Coerce.html#t:Coercible):
|
||||
-- This type class is solved by the compiler, but it only works for types
|
||||
-- that have the same runtime representation. This is very convenient for
|
||||
-- @newtype@s, but it does not work for converting between arbitrary types
|
||||
-- like @Int8@ and @Int16@.
|
||||
--
|
||||
-- - [@Convertible@](https://hackage.haskell.org/package/convertible-1.1.1.0/docs/Data-Convertible-Base.html#t:Convertible):
|
||||
-- This popular conversion type class is similar to what this library
|
||||
-- provides. The main difference is that it does not differentiate between
|
||||
-- conversions that can fail and those that cannot.
|
||||
--
|
||||
-- - [@From@](https://hackage.haskell.org/package/basement-0.0.11/docs/Basement-From.html#t:From):
|
||||
-- This type class is almost identical to what this library provides.
|
||||
-- Unfortunately it is part of the @basement@ package, which is an
|
||||
-- alternative standard library that some people may not want to depend
|
||||
-- on.
|
||||
--
|
||||
-- - [@Inj@](https://hackage.haskell.org/package/inj-1.0/docs/Inj.html#t:Inj):
|
||||
-- This type class requires instances to be an injection, which means that
|
||||
-- no two input values should map to the same output. That restriction
|
||||
-- prohibits many useful instances. Also many instances throw impure
|
||||
-- exceptions.
|
||||
--
|
||||
-- In addition to those general-purpose type classes, there are many
|
||||
-- alternatives for more specific conversions. How does this library compare
|
||||
-- to those?
|
||||
--
|
||||
-- - Monomorphic conversion functions like [@Data.Text.pack@](https://hackage.haskell.org/package/text-1.2.4.1/docs/Data-Text.html#v:pack)
|
||||
-- are explicit but not necessarily convenient. It can be tedious to
|
||||
-- manage the imports necessary to use the functions. And if you want to
|
||||
-- put them in a custom prelude, you will have to come up with your own
|
||||
-- names.
|
||||
--
|
||||
-- - Polymorphic conversion methods like 'toEnum' are more convenient but
|
||||
-- may have unwanted semantics or runtime behavior. For example the 'Enum'
|
||||
-- type class is more or less tied to the 'Int' data type and frequently
|
||||
-- throws impure exceptions.
|
||||
--
|
||||
-- - Polymorphic conversion functions like 'fromIntegral' are very
|
||||
-- convenient. Unfortunately it can be challenging to know which types
|
||||
-- have the instances necessary to make the conversion possible. And even
|
||||
-- if the conversion is possible, is it safe? For example converting a
|
||||
-- negative 'Int' into a 'Word' will overflow, which may be surprising.
|
||||
|
||||
-- * Instances
|
||||
-- | When should you add a 'Witch.Cast.Cast' (or 'Witch.TryCast.TryCast')
|
||||
-- instance for some pair of types? This is a surprisingly tricky question
|
||||
-- to answer precisely. Instances are driven more by guidelines than rules.
|
||||
--
|
||||
-- - Conversions must not throw impure exceptions. This means no 'undefined'
|
||||
-- or anything equivalent to it.
|
||||
--
|
||||
-- - Conversions should be unambiguous. If there are multiple reasonable
|
||||
-- ways to convert from @a@ to @b@, then you probably should not add a
|
||||
-- @Cast@ instance for them.
|
||||
--
|
||||
-- - Conversions should be lossless. If you have @Cast a b@ then no two @a@
|
||||
-- values should be converted to the same @b@ value.
|
||||
--
|
||||
-- - If you have both @Cast a b@ and @Cast b a@, then
|
||||
-- @cast \@b \@a . cast \@a \@b@ should be the same as 'id'. In other
|
||||
-- words, @a@ and @b@ are isomorphic.
|
||||
--
|
||||
-- - If you have both @Cast a b@ and @Cast b c@, then you could also have
|
||||
-- @Cast a c@ and it should be the same as @cast \@b \@c . cast \@a \@b@.
|
||||
-- In other words, @Cast@ is transitive.
|
||||
--
|
||||
-- In general if @s@ is a @t@, then you should add a 'Witch.Cast.Cast'
|
||||
-- instance for it. But if @s@ merely can be a @t@, then you could add a
|
||||
-- 'Witch.TryCast.TryCast' instance for it. And if it is technically
|
||||
-- possible to convert from @s@ to @t@ but there are a lot of caveats, you
|
||||
-- probably should not write any instances at all.
|
||||
|
||||
-- * Type applications
|
||||
-- | This library is designed to be used with the [@TypeApplications@](https://downloads.haskell.org/~ghc/9.0.1/docs/html/users_guide/exts/type_applications.html)
|
||||
-- language extension. Although it is not required for basic functionality,
|
||||
-- it is strongly encouraged. You can use 'Witch.Cast.cast',
|
||||
-- 'Witch.TryCast.tryCast', 'Witch.Utility.unsafeCast', and
|
||||
-- 'Witch.Lift.liftedCast' without type applications. Everything else
|
||||
-- requires a type application.
|
||||
|
||||
-- * Ambiguous types
|
||||
-- | You may see @Identity@ show up in some type signatures. Anywhere you see
|
||||
-- @Identity a@, you can mentally replace it with @a@. It is a type family
|
||||
-- used to trick GHC into requiring type applications for certain functions.
|
||||
-- If you forget to give a type application, you will see an error like
|
||||
-- this:
|
||||
--
|
||||
-- >>> from (1 :: Int8) :: Int16
|
||||
-- <interactive>:1:1: error:
|
||||
-- * Couldn't match type `Identity s0' with `Int8'
|
||||
-- arising from a use of `from'
|
||||
-- The type variable `s0' is ambiguous
|
||||
-- * In the expression: from (1 :: Int8) :: Int16
|
||||
-- In an equation for `it': it = from (1 :: Int8) :: Int16
|
||||
--
|
||||
-- You can fix the problem by giving a type application:
|
||||
--
|
||||
-- >>> from @Int8 1 :: Int16
|
||||
-- 1
|
||||
|
||||
-- * Type classes
|
||||
-- ** Cast
|
||||
Witch.Cast.Cast(cast)
|
||||
, Witch.Utility.from
|
||||
, Witch.Utility.into
|
||||
, Witch.Utility.over
|
||||
, Witch.Utility.via
|
||||
|
||||
-- ** TryCast
|
||||
, Witch.TryCast.TryCast(tryCast)
|
||||
, Witch.Utility.tryFrom
|
||||
, Witch.Utility.tryInto
|
||||
, Witch.TryCastException.TryCastException(..)
|
||||
|
||||
-- * Utilities
|
||||
, Witch.Utility.as
|
||||
, Witch.Utility.over
|
||||
, Witch.Utility.via
|
||||
, Witch.Utility.tryVia
|
||||
|
||||
-- ** Unsafe
|
||||
, Witch.Utility.unsafeCast
|
||||
, Witch.Utility.unsafeFrom
|
||||
, Witch.Utility.unsafeInto
|
||||
|
||||
-- ** Template Haskell
|
||||
, Witch.Lift.liftedCast
|
||||
, Witch.Lift.liftedFrom
|
||||
, Witch.Lift.liftedInto
|
||||
|
@ -5,7 +5,26 @@ module Witch.Cast where
|
||||
|
||||
import qualified Data.Coerce as Coerce
|
||||
|
||||
-- | This type class is for converting values from some @source@ type into
|
||||
-- some other @target@ type. The constraint @Cast source target@ measn that
|
||||
-- you can convert from a value of type @source@ into a value of type
|
||||
-- @target@.
|
||||
--
|
||||
-- This type class is for conversions that cannot fail. If your conversion can
|
||||
-- fail, consider implementing @TryCast@ instead.
|
||||
class Cast source target where
|
||||
-- | This method implements the conversion of a value between types. At call
|
||||
-- sites you will usually want to use @from@ or @into@ instead of this
|
||||
-- method.
|
||||
--
|
||||
-- The default implementation of this method simply calls 'Coerce.coerce',
|
||||
-- which works for types that have the same runtime representation. This
|
||||
-- means that for @newtype@s you do not need to implement this method at
|
||||
-- all. For example:
|
||||
--
|
||||
-- >>> newtype Name = Name String
|
||||
-- >>> instance Cast Name String
|
||||
-- >>> instance Cast String Name
|
||||
cast :: source -> target
|
||||
|
||||
default cast :: Coerce.Coercible source target => source -> target
|
||||
|
@ -2,8 +2,13 @@
|
||||
|
||||
module Witch.Identity where
|
||||
|
||||
-- | This is an ugly hack used to make GHC require type applications for
|
||||
-- certain functions. See this Twitter thread for a discussion:
|
||||
-- <https://twitter.com/taylorfausak/status/1329084033003782148>.
|
||||
type family Identity a where
|
||||
Identity Never = ()
|
||||
Identity a = a
|
||||
|
||||
-- | Never use this type for anything! It only exists to make the 'Identity'
|
||||
-- type family non-trivial.
|
||||
data Never
|
||||
|
@ -4,5 +4,15 @@ module Witch.TryCast where
|
||||
|
||||
import qualified Witch.TryCastException as TryCastException
|
||||
|
||||
-- | This type class is for converting values from some @source@ type into
|
||||
-- some other @target@ type. The constraint @TryCast source target@ means that
|
||||
-- you may be able to convert from a value of type @source@ into a value of
|
||||
-- type @target@, but that conversion may fail at runtime.
|
||||
--
|
||||
-- This type class is for conversions that can fail. If your conversion cannot
|
||||
-- fail, consider implementing @Cast@ instead.
|
||||
class TryCast source target where
|
||||
-- | This method implements the conversion of a value between types. At call
|
||||
-- sites you will usually want to use @tryFrom@ or @tryInto@ instead of this
|
||||
-- method.
|
||||
tryCast :: source -> Either (TryCastException.TryCastException source target) target
|
||||
|
@ -6,6 +6,9 @@ import qualified Control.Exception as Exception
|
||||
import qualified Data.Proxy as Proxy
|
||||
import qualified Data.Typeable as Typeable
|
||||
|
||||
-- | This exception is thrown when a @TryCast@ conversion fails. It has the
|
||||
-- original @source@ value that caused the failure and it knows the @target@
|
||||
-- type it was trying to convert into.
|
||||
newtype TryCastException source target
|
||||
= TryCastException source
|
||||
deriving Eq
|
||||
|
@ -12,9 +12,26 @@ import qualified Witch.Identity as Identity
|
||||
import qualified Witch.TryCast as TryCast
|
||||
import qualified Witch.TryCastException as TryCastException
|
||||
|
||||
-- | This is the same as 'id' except that it requires a type application. This
|
||||
-- can be an ergonomic way to pin down a polymorphic type in a function
|
||||
-- pipeline. For example:
|
||||
--
|
||||
-- > -- Avoid this:
|
||||
-- > f . (\ x -> x :: Int) . g
|
||||
-- >
|
||||
-- > -- Prefer this:
|
||||
-- > f . as @Int . g
|
||||
as :: forall s source . Identity.Identity s ~ source => source -> source
|
||||
as = id
|
||||
|
||||
-- | This is the same as 'Cast.cast' except that it requires a type
|
||||
-- application for the @source@ type.
|
||||
--
|
||||
-- > -- Avoid this:
|
||||
-- > cast (x :: s)
|
||||
-- >
|
||||
-- > -- Prefer this:
|
||||
-- > from @s x
|
||||
from
|
||||
:: forall s target source
|
||||
. (Identity.Identity s ~ source, Cast.Cast source target)
|
||||
@ -22,6 +39,14 @@ from
|
||||
-> target
|
||||
from = Cast.cast
|
||||
|
||||
-- | This is the same as 'Cast.cast' except that it requires a type
|
||||
-- application for the @target@ type.
|
||||
--
|
||||
-- > -- Avoid this:
|
||||
-- > cast x :: t
|
||||
-- >
|
||||
-- > -- Prefer this:
|
||||
-- > into @t x
|
||||
into
|
||||
:: forall t source target
|
||||
. (Identity.Identity t ~ target, Cast.Cast source target)
|
||||
@ -29,6 +54,16 @@ into
|
||||
-> target
|
||||
into = Cast.cast
|
||||
|
||||
-- | This function converts from some @source@ type into some @target@ type,
|
||||
-- applies the given function, then converts back into the @source@ type. This
|
||||
-- is useful when you have two types that are isomorphic but some function
|
||||
-- that only works with one of them.
|
||||
--
|
||||
-- > -- Avoid this:
|
||||
-- > from @t . f . from @s
|
||||
-- >
|
||||
-- > -- Prefer this:
|
||||
-- > over @t f
|
||||
over
|
||||
:: forall t source target
|
||||
. ( Identity.Identity t ~ target
|
||||
@ -40,6 +75,16 @@ over
|
||||
-> source
|
||||
over f = Cast.cast . f . Cast.cast
|
||||
|
||||
-- | This function first converts from some @source@ type into some @through@
|
||||
-- type, and then converts that into some @target@ type. Usually this is used
|
||||
-- when writing 'Cast.Cast' instances. Sometimes this can be used to work
|
||||
-- around the lack of an instance that should probably exist.
|
||||
--
|
||||
-- > -- Avoid this:
|
||||
-- > from @u . into @u
|
||||
-- >
|
||||
-- > -- Prefer this:
|
||||
-- > via @u
|
||||
via
|
||||
:: forall u source target through
|
||||
. ( Identity.Identity u ~ through
|
||||
@ -50,6 +95,14 @@ via
|
||||
-> target
|
||||
via = Cast.cast . (\x -> x :: through) . Cast.cast
|
||||
|
||||
-- | This is the same as 'TryCast.tryCast' except that it requires a type
|
||||
-- application for the @source@ type.
|
||||
--
|
||||
-- > -- Avoid this:
|
||||
-- > tryCast (x :: s)
|
||||
-- >
|
||||
-- > -- Prefer this:
|
||||
-- > tryFrom @s x
|
||||
tryFrom
|
||||
:: forall s target source
|
||||
. (Identity.Identity s ~ source, TryCast.TryCast source target)
|
||||
@ -57,6 +110,14 @@ tryFrom
|
||||
-> Either (TryCastException.TryCastException source target) target
|
||||
tryFrom = TryCast.tryCast
|
||||
|
||||
-- | This is the same as 'TryCast.tryCast' except that it requires a type
|
||||
-- application for the @target@ type.
|
||||
--
|
||||
-- > -- Avoid this:
|
||||
-- > tryCast x :: Either (TryCastException s t) t
|
||||
-- >
|
||||
-- > -- Prefer this:
|
||||
-- > tryInto @t x
|
||||
tryInto
|
||||
:: forall t source target
|
||||
. (Identity.Identity t ~ target, TryCast.TryCast source target)
|
||||
@ -64,6 +125,37 @@ tryInto
|
||||
-> Either (TryCastException.TryCastException source target) target
|
||||
tryInto = TryCast.tryCast
|
||||
|
||||
-- | This is similar to 'via' except that it works with 'TryCast.TryCast'
|
||||
-- instances instead. This function is especially convenient because juggling
|
||||
-- the types in the 'TryCastException.TryCastException' can be tedious.
|
||||
--
|
||||
-- > -- Avoid this:
|
||||
-- > fmap (tryFrom @u) . tryInto @u
|
||||
-- >
|
||||
-- > -- Prefer this:
|
||||
-- > tryVia @u
|
||||
tryVia
|
||||
:: forall u source target through
|
||||
. ( Identity.Identity u ~ through
|
||||
, TryCast.TryCast source through
|
||||
, TryCast.TryCast through target
|
||||
)
|
||||
=> source
|
||||
-> Either (TryCastException.TryCastException source target) target
|
||||
tryVia s = case TryCast.tryCast s of
|
||||
Left _ -> Left $ TryCastException.TryCastException s
|
||||
Right u -> case TryCast.tryCast (u :: through) of
|
||||
Left _ -> Left $ TryCastException.TryCastException s
|
||||
Right t -> Right t
|
||||
|
||||
-- | This function is like 'TryCast.tryCast' except that it will throw an
|
||||
-- impure exception if the conversion fails.
|
||||
--
|
||||
-- > -- Avoid this:
|
||||
-- > either throw id . cast
|
||||
-- >
|
||||
-- > -- Prefer this:
|
||||
-- > unsafeCast
|
||||
unsafeCast
|
||||
:: forall source target
|
||||
. ( Stack.HasCallStack
|
||||
@ -76,6 +168,14 @@ unsafeCast
|
||||
-> target
|
||||
unsafeCast = either Exception.throw id . TryCast.tryCast
|
||||
|
||||
-- | This function is like 'from' except that it will throw an impure
|
||||
-- exception if the conversion fails.
|
||||
--
|
||||
-- > -- Avoid this:
|
||||
-- > either throw id . from @s
|
||||
-- >
|
||||
-- > -- Prefer this:
|
||||
-- > unsafeFrom @s
|
||||
unsafeFrom
|
||||
:: forall s target source
|
||||
. ( Identity.Identity s ~ source
|
||||
@ -89,6 +189,14 @@ unsafeFrom
|
||||
-> target
|
||||
unsafeFrom = unsafeCast
|
||||
|
||||
-- | This function is like 'into' except that it will throw an impure
|
||||
-- exception if the conversion fails.
|
||||
--
|
||||
-- > -- Avoid this:
|
||||
-- > either throw id . into @t
|
||||
-- >
|
||||
-- > -- Prefer this:
|
||||
-- > unsafeInto @t
|
||||
unsafeInto
|
||||
:: forall t source target
|
||||
. ( Identity.Identity t ~ target
|
||||
|
Loading…
Reference in New Issue
Block a user