Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
Documentation
class Newtype o n | n -> o where Source #
The FunctionalDependencies
version of Newtype
type-class.
Since Cabal-3.0 class arguments are in a different order than in newtype
package.
This change is to allow usage with DeriveAnyClass
(and DerivingStrategies
, in GHC-8.2).
Unfortunately one have to repeat inner type.
newtype New = New Old deriving anyclass (Newtype Old)
Another approach would be to use TypeFamilies
(and possibly
compute inner type using GHC.Generics), but we think FunctionalDependencies
version gives cleaner type signatures.
Nothing
Instances
Newtype String FilePathNT # | |
Defined in Distribution.Parsec.Newtypes pack :: String -> FilePathNT Source # unpack :: FilePathNT -> String Source # | |
Newtype String Token' # | |
Newtype String Token # | |
Newtype a (Product a) # | |
Newtype a (Sum a) # | |
Newtype a (Identity a) # | |
Newtype a (MQuoted a) # | |
Newtype [a] (List sep wrapper a) # | |
Newtype (Set a) (Set' sep wrapper a) # | |
Newtype (Either Version VersionRange) SpecVersion # | |
Defined in Distribution.Parsec.Newtypes pack :: Either Version VersionRange -> SpecVersion Source # unpack :: SpecVersion -> Either Version VersionRange Source # | |
Newtype (Either License License) SpecLicense # | |
Defined in Distribution.Parsec.Newtypes | |
Newtype (CompilerFlavor, VersionRange) TestedWith # | |
Defined in Distribution.Parsec.Newtypes pack :: (CompilerFlavor, VersionRange) -> TestedWith Source # unpack :: TestedWith -> (CompilerFlavor, VersionRange) Source # | |
Newtype (a -> a) (Endo a) # | |
ala :: (Newtype o n, Newtype o' n') => (o -> n) -> ((o -> n) -> b -> n') -> b -> o' Source #
>>>
ala Sum foldMap [1, 2, 3, 4 :: Int]
10
Note: the user supplied function for the newtype is ignored.
>>>
ala (Sum . (+1)) foldMap [1, 2, 3, 4 :: Int]
10