Improve documentation

This commit is contained in:
Taylor Fausak 2021-05-10 21:56:28 -04:00
parent a8c5fce4b6
commit 74b833fffb
8 changed files with 31 additions and 34 deletions

View File

@ -11,10 +11,10 @@ import qualified Witch.Utility as Utility
-- rather than runtime.
--
-- > -- Avoid this:
-- > unsafeFrom "some literal"
-- > unsafeFrom @s "some literal"
-- >
-- > -- Prefer this:
-- > $$(liftedFrom "some literal")
-- > $$(liftedFrom @s "some literal")
liftedFrom
:: forall source target
. ( TryFrom.TryFrom source target

View File

@ -11,10 +11,10 @@ import qualified Witch.Utility as Utility
-- rather than runtime.
--
-- > -- Avoid this:
-- > unsafeFrom "some literal"
-- > unsafeFrom @s "some literal"
-- >
-- > -- Prefer this:
-- > $$(liftedFrom "some literal")
-- > $$(liftedFrom @s "some literal")
liftedFrom
:: forall source target
. ( TryFrom.TryFrom source target

View File

@ -11,10 +11,10 @@ import qualified Witch.Utility as Utility
-- rather than runtime.
--
-- > -- Avoid this:
-- > unsafeFrom "some literal"
-- > unsafeFrom @s "some literal"
-- >
-- > -- Prefer this:
-- > $$(liftedFrom "some literal")
-- > $$(liftedFrom @s "some literal")
liftedFrom
:: forall source target m
. ( TryFrom.TryFrom source target

View File

@ -32,8 +32,8 @@ module Witch
-- a conversion is safe even though you can't prove it to the compiler, and
-- when you're alright with your program crashing if the conversion fails.
-- In all other cases you should prefer the normal conversion functions like
-- 'Witch.From.from'. And if you're converting a literal value, consider
-- using the Template Haskell conversion functions like
-- 'Witch.TryFrom.tryFrom'. And if you're converting a literal value,
-- consider using the Template Haskell conversion functions like
-- 'Witch.Lift.liftedFrom'.
, Witch.Utility.unsafeFrom
, Witch.Utility.unsafeInto

View File

@ -6,7 +6,7 @@ module Witch.From 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 @From source target@ measn that
-- some other @target@ type. The constraint @'From' source target@ means that
-- you can convert from a value of type @source@ into a value of type
-- @target@.
--
@ -14,8 +14,7 @@ import qualified Data.Coerce as Coerce
-- fail, consider implementing @TryFrom@ instead.
class From 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.
-- sites you will usually want to use @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
@ -23,8 +22,8 @@ class From source target where
-- all. For example:
--
-- >>> newtype Name = Name String
-- >>> instance From Name String
-- >>> instance From String Name
-- >>> instance 'From' Name String
-- >>> instance 'From' String Name
from :: source -> target
default from :: Coerce.Coercible source target => source -> target

View File

@ -897,13 +897,13 @@ instance From.From Rational Double where
-- Fixed
-- | Uses 'Fixed.MkFixed'. This means @from 2 :: Centi@ is @0.02@ rather than
-- @2.00@.
-- | Uses 'Fixed.MkFixed'. This means @from \@Integer \@Centi 2@ is @0.02@
-- rather than @2.00@.
instance From.From Integer (Fixed.Fixed a) where
from = Fixed.MkFixed
-- | Uses 'Fixed.MkFixed'. This means @from (3.00 :: Centi)@ is @300@ rather
-- than @3@.
-- | Uses 'Fixed.MkFixed'. This means @from \@Centi \@Integer 3.00@ is @300@
-- rather than @3@.
instance From.From (Fixed.Fixed a) Integer where
from (Fixed.MkFixed t) = t

View File

@ -5,16 +5,15 @@ module Witch.TryFrom where
import qualified Witch.TryFromException as TryFromException
-- | This type class is for converting values from some @source@ type into
-- some other @target@ type. The constraint @TryFrom 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.
-- some other @target@ type. The constraint @'TryFrom' 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 @From@ instead.
class TryFrom 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.
-- sites you will usually want to use @tryInto@ instead of this method.
--
-- Consider using @maybeTryFrom@ or @eitherTryFrom@ to implement this
-- method.

View File

@ -10,9 +10,8 @@ import qualified Witch.From as From
import qualified Witch.TryFrom as TryFrom
import qualified Witch.TryFromException as TryFromException
-- | 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:
-- | This is the same as 'id'. 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
@ -22,8 +21,8 @@ import qualified Witch.TryFromException as TryFromException
as :: forall source . source -> source
as = id
-- | This is the same as 'From.from' except that it requires a type
-- application for the @target@ type.
-- | This is the same as 'From.from' except that the type variables are in the
-- opposite order.
--
-- > -- Avoid this:
-- > from x :: t
@ -76,8 +75,8 @@ via
-> target
via = From.from . (\x -> x :: through) . From.from
-- | This is the same as 'TryFrom.tryFrom' except that it requires a type
-- application for the @target@ type.
-- | This is the same as 'TryFrom.tryFrom' except that the type variables are
-- in the opposite order.
--
-- > -- Avoid this:
-- > tryFrom x :: Either (TryFromException s t) t
@ -100,7 +99,7 @@ tryInto = TryFrom.tryFrom
-- > Left _ -> Left ...
-- > Right y -> case tryFrom @u y of
-- > Left _ -> Left ...
-- > Right z -> ...
-- > Right z -> Right z
-- >
-- > -- Prefer this:
-- > tryVia @u
@ -161,10 +160,10 @@ eitherTryFrom f s = case f s of
-- impure exception if the conversion fails.
--
-- > -- Avoid this:
-- > either throw id . from
-- > either throw id . tryFrom @s
-- >
-- > -- Prefer this:
-- > unsafeFrom
-- > unsafeFrom @s
unsafeFrom
:: forall source target
. ( Stack.HasCallStack
@ -177,11 +176,11 @@ unsafeFrom
-> target
unsafeFrom = either Exception.throw id . TryFrom.tryFrom
-- | This function is like 'into' except that it will throw an impure
-- | This function is like 'tryInto' except that it will throw an impure
-- exception if the conversion fails.
--
-- > -- Avoid this:
-- > either throw id . into @t
-- > either throw id . tryInto @t
-- >
-- > -- Prefer this:
-- > unsafeInto @t