[Haskell-cafe] Partially applied type synonyms

Richard Eisenberg lists at richarde.dev
Fri Oct 8 14:54:51 UTC 2021


Hello Tom,

Type synonyms must be fully applied. You could try

> newtype Foo (s :: * -> *) (x :: *) = MkFoo (Foo' (s x) x)

to make something that does not need to be fully applied -- but now you have to worry about the pesky MkFoo constructor.

It's hard for me to suggest something else without understanding your use-case better. Sorry!

Hope this helps,
Richard

> On Oct 7, 2021, at 10:15 PM, Ttt Mmm via Haskell-Cafe <haskell-cafe at haskell.org> wrote:
> 
> I was surprised to find the below code doesn't typecheck even with -XLiberalTypeSynonyms. Am I missing something or is this really not possible? 
> 
> Thanks, 
> Tom 
> 
> --- 
> 
> {-# LANGUAGE FlexibleInstances, KindSignatures, LiberalTypeSynonyms, StandaloneDeriving #-}
> -- This works: 
> data Foo s x = Foo (s x) x 
> deriving (Eq)
> -- This replacement doesn't: 
> {- 
> data Foo' sx x = Foo' sx x 
> deriving (Eq) 
> type Foo (s :: * -> *) (x :: *) = Foo' (s x) x 
> -}
> data Bar (m :: * -> *) = Bar (m Int)
> 
> -- Neither of these typecheck: 
> x :: Bar (Foo Maybe) 
> x = undefined 
> deriving instance Eq (Bar (Foo Maybe)) 
> 
> _______________________________________________
> Haskell-Cafe mailing list
> To (un)subscribe, modify options or view archives go to:
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
> Only members subscribed via the mailman list are allowed to post.



More information about the Haskell-Cafe mailing list