[Haskell-cafe] Why this doesn't type checked
Daniel Fischer
daniel.is.fischer at web.de
Sun Jun 27 16:33:50 EDT 2010
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
More information about the Haskell-Cafe
mailing list