Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

Proper way to wrap selectively class instances (or "lift" functions like `sortBy`, `minimumBy`, ... automatically)

Let some type instanced to many classes. What is the proper way to replace, selectively, certain instances's behaviors?

One way to express it could be construct the by operator then

data Person ...

sort personList              -- default Ord instance
(sort `by` age) personList   -- `age` modify `Ord` instance

here, sort could be any function (e.g. minimum) with any arity (e.g. insert).

If we have a function like

reportPersons :: [Person] -> Report

and it functions use Ord (to sort list), Show (to format records), ... or other especific instances; using funcBy pattern we must to write

reportPersonsBy :: (Person -> Person -> Ordering) -> (Person -> String) -> ... -> [Person] -> Report

but we can use by to wrap each behavior with original reportPersons without refactor reportPersonsBy (explained example and not solved related problems at the end).

My toy (and not fully satisfactory) solution is (complete code at the end):

A class to wrap types into types to override instances

class Wrappable m where
    wrap   :: forall a . a -> m a
    unwrap :: forall a . m a -> a

and by function to wrap functions

-- wrap functions: f a -> g a
by :: (Functor f, Functor g, Wrappable m) => (f (m a) -> g (m a)) -> m a -> f a -> g a
by f _ = fmap unwrap . f . fmap wrap

-- wrap functions: a -> f a -> g a
by_ f m a = f (wrap a) `by` m

Now we can write (at the bottom complete example)

-- f a -> f a
mapM_ print $  sort           personList
mapM_ print $ (sort `by` age) personList

-- f a -> g a
print $  minimum           personList
print $ (minimum `by` age) personList

-- a -> f a -> f a
print $  insert            jane personList
print $ (insert `by_` age) jane personList

Ok, by, by_, ... works but, what is the correct way? how write complete polymorphic by?

I've tried but not work

class Wrappable m => By m x f i o where
    by :: f m x -> m x -> i m x -> o m x

to be able to write function instances as

instance (Wrappable m, Functor f, Functor g) => By m a (f (m a) -> g (m a)) (f a) (g a) where
    by :: (f (m a) -> g (m a)) -> m a -> f a -> g a
    by f _ = fmap unwrap . f . fmap wrap

Thank you!

Report example

Suppose exists one report function for persons (wrappable persons)

reportPersons :: (Wrappable m, Show (m Person), Ord (m Person)) => [m Person] -> Maybe String
reportPersons = Just . unlines . map show . sort

with carried behaviors for each instance (Ord and Show).

Let (not polymorphic by :( )

by' :: (Functor f, Functor g, Wrappable m) => (f (m a) -> g b) -> m a -> f a -> g b
by' f _ = f . fmap wrap

and a new Wrappable instance for Persons

newtype Format1 a = Format1 a deriving (Eq, Ord)
instance Show (Format1 Person) where show (Format1 (Person n a)) = "Name := " ++ n ++ " (" ++ show a ++ " years old)"
format1 :: Format1 Person; format1 = undefined
instance Wrappable Format1 where  wrap               = Format1
                                  unwrap (Format1 p) = p

now, we can report persons overlapping selectively behaviors

putStrLn $ fromJust $ (reportPersons `by'` age)     personList
putStrLn $ fromJust $ (reportPersons `by'` format1) personList

with output

ByAge (Person {personName = "John", personAge = 16})
ByAge (Person {personName = "Anne", personAge = 24})
ByAge (Person {personName = "Zorn", personAge = 37})
ByAge (Person {personName = "Peter", personAge = 42})

Name := Anne (24 years old)
Name := John (16 years old)
Name := Peter (42 years old)
Name := Zorn (37 years old)

using TypeFamilies or other feature probably, we can chain Wrappables, etc... (it's a toy!!! and I don't know how to do in a good way)

(complete sandbox code)

{-# LANGUAGE RankNTypes, FlexibleInstances #-}
import Data.Maybe
import Prelude hiding (minimum)
import Data.List hiding (minimum)
import System.Random

{- safe minimum -}
minimum [] = Nothing; minimum xs = listToMaybe $ sort xs

data Person = Person { personName :: String, personAge :: Int } deriving (Eq, Show, Ord)

personList = [Person "Anne" 24, Person "John" 16, Person "Peter" 42, Person "Zorn" 37]
jane       =  Person "Jane" 26


class Wrappable m where
    wrap   :: forall a . a -> m a
    unwrap :: forall a . m a -> a

-- wrap functions: f a -> g a
by :: (Functor f, Functor g, Wrappable m) => (f (m a) -> g (m a)) -> m a -> f a -> g a
by f _ = fmap unwrap . f . fmap wrap

-- wrap functions: a -> f a -> g a
by_ f m a = f (wrap a) `by` m

newtype ByAge a = ByAge a deriving (Eq, Show)
instance Ord (ByAge Person) where (ByAge (Person _ a)) `compare` (ByAge (Person _ b)) = a `compare` b
age :: ByAge Person; age = undefined
instance Wrappable ByAge where  wrap             = ByAge
                                unwrap (ByAge p) = p

main = do

    -- f a -> f a
    mapM_ print $  sort           personList
    mapM_ print $ (sort `by` age) personList

    -- f a -> g a
    print $  minimum           personList
    print $ (minimum `by` age) personList

    -- a -> f a -> f a
    print $  insert            jane personList
    print $ (insert `by_` age) jane personList
like image 931
josejuan Avatar asked Oct 31 '22 12:10

josejuan


1 Answers

Let some type instanced to many classes. What is the proper way to replace, selectively, certain instances's behaviors?

The proper way is to use plain old functions and use sortBy, maximumBy, groupBy etc. instead.

I think this is abuse of typeclasses. Keep it simple, stupid! Yes, this is opinion-based, let stackoverflow's voting system sort(By) it out.

like image 50
Franky Avatar answered Nov 15 '22 08:11

Franky