
I've allways found code like
-- maxBound (undefined :: Int)
a bit strange as any usage of undefined is. Being Ruby on Rails developer I've personally found that one of the main Rails motos is being as readable as possible. Code must be as close to english as possible. Embeded DSLs like rspec are made mostly to made specs as close to english as possible. Having this in my mind I've decided that this code should be rewritten without undefined being mentioned. But I need some type signature and it should mention Int type. So I've got an idea about what I've called "fantom type functions". So wee need type families for it to work.
{-# LANGUAGE TypeFamilies #-} module Main where
import Data.Word
I want the code I've mentioned to be rewrited as something like
-- maxBound :: MaxBoundOf Int
As it is much more readable: "I want maxBound with the type of MaxBound Of Int". So here is the implementation of class Sizeable that implements sizeof operation. Which is type-indexed like maxBound is. sizeof returns number of bytes that occupy type when serialized to some binary stream.
class Sizeable sizeable where type Sizeof sizeable sizeof :: Sizeof sizeable
We should like to make a default type but GHC still doesn't support it.
-- type Sizeof sizeable = Int
Instances for all basic types
instance Sizeable Int where sizeof = 4
Even without defaults we get type safety in these instances
type Sizeof Int = Int
instance Sizeable Word8 where sizeof = 1 type Sizeof Word8 = Int
instance Sizeable Word16 where sizeof = 2 type Sizeof Word16 = Int
instance Sizeable Word32 where sizeof = 4 type Sizeof Word32 = Int
instance Sizeable Word64 where sizeof = 8 type Sizeof Word64 = Int
The annoyance is the need to instantiate Sizeof type family every time. It will disappear once associated types' defaults will be implemented in GHC. What we get with this instances is following code.
main = do print (sizeof :: Sizeof Word16)
Let's try it. $ runhaskell this.lhs this.lhs:78:14: Couldn't match expected type `Int' against inferred type `Sizeof sizeable' NB: `Sizeof' is a type function, and may not be injective In the first argument of `print', namely `(sizeof :: Sizeof Word16)' In the expression: print (sizeof :: Sizeof Word16) In the expression: do { print (sizeof :: Sizeof Word16) } What can I do with this code to make it type-check? -- Victor Nazarov

On Sunday 27 June 2010 21:52:18, Victor Nazarov wrote:
I've allways found code like
-- maxBound (undefined :: Int)
a bit strange
Well, that would indeed be a bit strange since maxBound :: (Bounded a) => a and function types aren't instances of Bounded, so it'd be maxBound :: Int maxBound :: Char maxBound :: Bool ...
as any usage of undefined is. Being Ruby on Rails developer I've personally found that one of the main Rails motos is being as readable as possible.
That's good.
Code must be as close to english as possible.
That not, not always, anyway. Mathematical algorithms for example tend to be obfuscated by englishifying.
Embeded DSLs like rspec are made mostly to made specs as close to english as possible.
What we get with this instances is following code.
main = do print (sizeof :: Sizeof Word16)
Let's try it.
$ runhaskell this.lhs this.lhs:78:14: Couldn't match expected type `Int' against inferred type `Sizeof sizeable' NB: `Sizeof' is a type function, and may not be injective In the first argument of `print', namely `(sizeof :: Sizeof Word16)' In the expression: print (sizeof :: Sizeof Word16) In the expression: do { print (sizeof :: Sizeof Word16) }
Right. Since Sizeof Word8 is Int too, the type can't help determining the value.
What can I do with this code to make it type-check?
newtype Size a = Size { unSize :: Int } class Sizeable a where sizeof :: Size a instance Sizeable Word8 where sizeof = Size 1 instance Sizeable Word16 where sizeof = Size 2 ... main = print . unSize $ sizeof :: Size Word16

On Mon, Jun 28, 2010 at 12:33 AM, Daniel Fischer
On Sunday 27 June 2010 21:52:18, Victor Nazarov wrote:
I've allways found code like
-- maxBound (undefined :: Int)
a bit strange
Well, that would indeed be a bit strange since
maxBound :: (Bounded a) => a
and function types aren't instances of Bounded, so it'd be
maxBound :: Int maxBound :: Char maxBound :: Bool ...
Yes, you are right. I've just tried to find some standard type-indexed function. Discard everything about maxBound.
as any usage of undefined is. Being Ruby on Rails developer I've personally found that one of the main Rails motos is being as readable as possible.
That's good.
Code must be as close to english as possible.
That not, not always, anyway. Mathematical algorithms for example tend to be obfuscated by englishifying.
I understand it, but RoR is trying to get as close to english as possible as I see it.
Embeded DSLs like rspec are made mostly to made specs as close to english as possible.
What we get with this instances is following code.
main = do print (sizeof :: Sizeof Word16)
Let's try it.
$ runhaskell this.lhs this.lhs:78:14: Couldn't match expected type `Int' against inferred type `Sizeof sizeable' NB: `Sizeof' is a type function, and may not be injective In the first argument of `print', namely `(sizeof :: Sizeof Word16)' In the expression: print (sizeof :: Sizeof Word16) In the expression: do { print (sizeof :: Sizeof Word16) }
Right. Since Sizeof Word8 is Int too, the type can't help determining the value.
Then it should be ambiguous type-parameter error or something like this, why Int is expected?
What can I do with this code to make it type-check?
newtype Size a = Size { unSize :: Int }
class Sizeable a where sizeof :: Size a
instance Sizeable Word8 where sizeof = Size 1
instance Sizeable Word16 where sizeof = Size 2
...
main = print . unSize $ sizeof :: Size Word16
Year this is good enough for me, thanx :) -- Victor Nazarov

On Mon, Jun 28, 2010 at 08:51:45AM +0400, Victor Nazarov wrote:
What we get with this instances is following code.
main = do print (sizeof :: Sizeof Word16)
Let's try it.
$ runhaskell this.lhs this.lhs:78:14: Couldn't match expected type `Int' against inferred type `Sizeof sizeable' NB: `Sizeof' is a type function, and may not be injective In the first argument of `print', namely `(sizeof :: Sizeof Word16)' In the expression: print (sizeof :: Sizeof Word16) In the expression: do { print (sizeof :: Sizeof Word16) }
Right. Since Sizeof Word8 is Int too, the type can't help determining the value.
Then it should be ambiguous type-parameter error or something like this, why Int is expected?
It knows that Sizeof Word16 = Int which is why Int is expected. It also knows sizeof :: Sizeable sizeable => Sizeof sizeable so it tries to match 'Sizeof sizeable' with 'Int'. Unfortunately this is not enough information to figure out what 'sizeable' is supposed to be. There are quite a few options for sizeable that would make 'Sizeof sizeable = Int', and even if there were only one, type classes are open so there could always be another one added in another module somewhere. -Brent

On 28 June 2010 05:52, Victor Nazarov
Having this in my mind I've decided that this code should be rewritten without undefined being mentioned. But I need some type signature and it should mention Int type. So I've got an idea about what I've called "fantom type functions". So wee need type families for it to work.
Sounds like http://www.haskell.org/haskellwiki/Phantom_type But as Daniel said, you seem to be trying to solve a problem that doesn't exist! -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

On 6/27/10 21:52, Victor Nazarov wrote:
class Sizeable sizeable where type Sizeof sizeable sizeof :: Sizeof sizeable
This is where the type checker should complain. There is no valid way to call sizeof, regardless of what instances are available. The situation is similar to this:
class C a where x :: Int
In which case the compiler says:
The class method `x' mentions none of the type variables of the class C a When checking the class method: x :: Int In the class declaration for `C'
I thought there was already a trac ticket for this, but I can't find it right now. Martijn.
participants (5)
-
Brent Yorgey
-
Daniel Fischer
-
Ivan Miljenovic
-
Martijn van Steenbergen
-
Victor Nazarov