I have made dot sign for functors (○), but my application (↯) doesnt work, I have an error in test3
function declaration
{-# LANGUAGE TypeOperators #-}
module Main where
import Protolude
-- composition of functors, analog of .
infixr 9 ○
type (○) f g a = f (g a)
-- functor application, analog of $
infixr 0 ↯
type (↯) f a = f a
test :: [] (Maybe Int)
test = [Just 1]
test2 :: ([] ○ Maybe) Int
test2 = [Just 1]
test3 :: ([] ○ Maybe) ↯ Int -- error here
test3 = [Just 1]
main :: IO ()
main = do
print test
print test2
return ()
I have an error
[Error]• The type synonym ‘○’ should have 3 arguments, but has been given 2 • In the type signature: test3 :: ([] ○ Maybe) ↯ Int
What's wrong?
UPDATE
Here is the implementation using newtype, because type synonyms cannot be partially applied
(@M.Aroosi)
I don't like it because I have to wrap data with datatype constructor all the time
Is there a way to implement it without need to wrap data with Composition
or Apply
all the time?
{-# LANGUAGE TypeOperators #-}
module Main where
import Protolude
-- I can't use `type` here, because type synonyms cannot be partially applied
-- composition of functors, analog of .
infixr 9 ○
newtype (○) f g a = Composition (f (g a)) deriving (Show)
-- functor application, analog of $
infixr 0 ↯
newtype (↯) f a = Apply (f a) deriving (Show)
test :: [] (Maybe Int)
test = [Just 1]
test2 :: ([] ○ Maybe) Int
test2 = Composition [Just 1]
test2' :: [] ○ Maybe ↯ Int
test2' = Apply (Composition [Just 1])
test3 :: ([] ○ Maybe ○ Maybe) Int
test3 = Composition [Composition (Just (Just 1))]
test3' :: [] ○ Maybe ○ Maybe ↯ Int
test3' = Apply (Composition [Composition (Just (Just 1))])
main :: IO ()
main = do
print test
print test2
print test2'
print test3
print test3'
return ()
UPDATE
This can be done trivially in idris
module Main
test : List (Maybe Integer)
test = [Just 1]
-- using (.) from prelude
test1 : (List . Maybe) Integer
test1 = [Just 1]
-- using (.) and ($) from prelude
test2 : List . Maybe $ Integer
test2 = [Just 1]
main : IO ()
main = do
print test
print test1
print test2
UPDATE
composition with type
also works in purescript (YAY!)
module Main where
import Prelude
import Data.Maybe (Maybe(..))
import Control.Monad.Eff (Eff)
import Control.Monad.Eff.Console (CONSOLE, logShow)
type Composition f g a = f (g a)
infixr 9 type Composition as ○
type Apply f a = f a
infixr 0 type Apply as ↯
test1 :: (Array ○ Maybe) Int
test1 = [Just 1]
test2 :: Array ○ Maybe ↯ Int
test2 = [Just 1]
test3 :: (Array ○ Maybe ○ Maybe) Int
test3 = [Just (Just 1)]
test4 :: Array ○ Maybe ○ Maybe ↯ Int
test4 = [Just (Just 1)]
main :: forall e. Eff (console :: CONSOLE | e) Unit
main = do
logShow test1
logShow test2
logShow test3
logShow test4
UPDATE
there is an ongoing effort to make this possible in haskell
https://github.com/kcsongor/typelevel-prelude
Dollar sign. Since complex statements like a + b are pretty common and Haskellers don't really like parentheses, the dollar sign is used to avoid parentheses: f $ a + b is equivalent to the Haskell code f (a + b) and translates into f(a + b).
a -> b Bool means... forall (a :: *) (b :: * -> *). a -> b Bool. b is therefore a type constructor taking a single type argument. Examples of single-argument type constructors abound: Maybe , [] , IO are all examples of things which you could use to instantiate b .
In general terms, where f and g are functions, (f . g) x means the same as f (g x). In other words, the period is used to take the result from the function on the right, feed it as a parameter to the function on the left, and return a new function that represents this computation."
in goes along with let to name one or more local expressions in a pure function.
So as per your request, here's the solution involving type families. It is based around the idea behind the Fcf
package with an article explaining that idea here
Before I begin there's something in favor of using a normal data type/newtype: You can define functor instances for the composition type so it acts as a single unit, that is you can define instance (Functor f, Functor g) => Functor (Compose f g) where ..
which you can't do with the approach below.
There might be a library that allows you to do that with a list of types instead of just 2 (so something like Compose [Maybe, [], Either Int] a
), but I can't seem to find it right now, so if anyone knows it it's probably a better solution than the one I present below (in my opinion).
First we need some language extensions:
{-# LANGUAGE
TypeFamilies,
TypeInType,
TypeOperators
#-}
Let's also include Data.Kind
for Type
import Data.Kind (Type)
Let's define a type Exp a
which will represent a
.
We'll also define a type family Eval
which will let do the grunt work, it will take an Exp a
and give us an a
type Exp a = a -> Type
type family Eval (e :: Exp a) :: a
We can now define our operators (○)
and (↯)
(I'd prefer to use easier to type operators here, say # and $ instead, but I'll stick with the ones you picked for this answer).
We define these as empty data types. This is where TypeInType
comes in (and TypeOperators
but that's because we are using operators).
infixr 9 ○
data (○) :: (b -> c) -> (a -> Exp b) -> a -> Exp c
infixr 0 ↯
data (↯) :: (a -> Exp b) -> a -> Exp b
Notice how the final kind is Exp a
for them? that allows us to give them type instances for Eval
type instance Eval ((○) f g a) = f (Eval (g a))
type instance Eval ((↯) f a) = Eval (f a)
Now you may be wondering "(○)
's second argument is of kind a -> Exp b
, but I want to give it something like Maybe
which has kind * -> *
!", this is where we have 3 solutions to that problem:
(%)
which is just like (○)
but takes a second argument of kind a -> b
instead of a -> Exp b
. This only needs to replace the right-most composition operator. a -> b
into a -> Exp b
, I'll use a data type named Lift
for that. This only needs to be done to the rightmost type in the composition. a -> Exp b
, I'll call that Pure
. Here are the three solutions written in Haskell:
infixr 9 %
data (%) :: (b -> c) -> (a -> b) -> a -> Exp c
type instance Eval ((%) f g a) = f (g a)
data Lift :: (a -> b) -> a -> Exp b
type instance Eval (Lift f a) = f a
data Pure :: a -> Exp a
type instance Eval (Pure a) = a
One more thing we can do with this setup is make a type-level function datatype we call "Compose" which will take a list of types and produce their composition
data Compose :: [a -> a] -> a -> Exp a
type instance Eval (Compose '[] a) = a
type instance Eval (Compose (x:xs) a) = x (Eval (Compose xs a))
Now we can make our program, with some tests and a main
that just prints the values of the tests:
{-# LANGUAGE
TypeFamilies,
TypeInType,
TypeOperators
#-}
module Main where
import Data.Kind (Type)
type Exp a = a -> Type
type family Eval (e :: Exp a) :: a
infixr 9 ○
data (○) :: (b -> c) -> (a -> Exp b) -> a -> Exp c
infixr 0 ↯
data (↯) :: (a -> Exp b) -> a -> Exp b
type instance Eval ((○) f g a) = f (Eval (g a))
type instance Eval ((↯) f a) = Eval (f a)
infixr 9 %
data (%) :: (b -> c) -> (a -> b) -> a -> Exp c
type instance Eval ((%) f g a) = f (g a)
data Lift :: (a -> b) -> a -> Exp b
type instance Eval (Lift f a) = f a
data Pure :: a -> Exp a
type instance Eval (Pure a) = a
data Compose :: [a -> a] -> a -> Exp a
type instance Eval (Compose '[] a) = a
type instance Eval (Compose (x:xs) a) = x (Eval (Compose xs a))
test :: [] (Maybe Int)
test = [Just 1]
-- using %
test2 :: Eval (([] % Maybe) Int)
test2 = [Just 1]
test2' :: Eval ([] % Maybe ↯ Int)
test2' = [Just 1]
-- works for longer types too
test3 :: Eval (([] ○ Maybe % Maybe) Int)
test3 = [Just (Just 1)]
test3' :: Eval ([] ○ Maybe % Maybe ↯ Int)
test3' = [Just (Just 1)]
-- we can instead Lift the rightmost type
test4 :: Eval (([] ○ Maybe ○ Lift Maybe) Int)
test4 = [Just (Just 1)]
test4' :: Eval ([] ○ Maybe ○ Lift Maybe ↯ Int)
test4' = [Just (Just 1)]
-- an even longer type, with definition "matching" the type declaration
test5 :: Eval ([] ○ Maybe ○ Either Bool % Maybe ↯ Int)
test5 = (:[]) . Just . Right . Just $ 1
-- Same as above, but instead let's use Pure so we don't need to lift the Maybe or use %
test6 :: Eval ([] ○ Maybe ○ Either Bool ○ Maybe ○ Pure ↯ Int)
test6= (:[]) . Just . Right . Just $ 1
-- same as above, uses Compose
test7 :: Eval (Compose [[], Maybe, Either Bool, Maybe] Int)
test7= (:[]) . Just . Right . Just $ 1
main :: IO ()
main = do
print test
print test2
print test2'
print test3
print test3'
print test4
print test4'
print test5
print test6
print test7
return ()
If you love us? You can donate to us via Paypal or buy me a coffee so we can maintain and grow! Thank you!
Donate Us With